Reputation: 873
I have a Haskell typeclass question. I can't munge the syntax to get this (seemingly reasonable) program to compile under GHC.
import Control.Concurrent.MVar
blah1 :: [a] -> IO ([a])
blah1 = return
blah2 :: [a] -> IO (MVar [a])
blah2 = newMVar
class Blah b where
blah :: [a] -> IO (b a)
instance Blah [] where
blah = blah1
-- BOOM
instance Blah (MVar []) where
blah = blah2
main :: IO ()
main = do
putStrLn "Ok"
I get the following error message, which kind of makes sense, but I don't know how to fix it:
`[]' is not applied to enough type arguments
Expected kind `*', but `[]' has kind `* -> *'
In the type `MVar []'
In the instance declaration for `Blah (MVar [])'
Upvotes: 8
Views: 970
Reputation: 15772
I was reading about Conal Elliott's TypeCompose library, and was reminded of this question. Here's an example of how you can do type-level composition.
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Main where
...
import Control.Compose
...
instance Blah (MVar `O` []) where
blah = liftM O . blah2
...
Upvotes: 2
Reputation: 204718
What you want isn't directly expressible. This is probably as close as you'll get:
newtype MVarList a = MVarList (MVar [a])
instance Blah MVarList where
blah = fmap MVarList . newMVar
Upvotes: 12