Am I using type families well?

Hello, I'm trying to make a simple monad (built on operational's ProgramT) for resource loading. I have classes featuring type families : {-# LANGUAGE TypeFamilies, FlexibleContexts, GADTs #-} -- | A ResourceId is something that identifies a resource. -- It should be unique for one resource, and should be used to find the location (the path) of the resource, -- possibly by using a configuration datatype class (Ord id) => ResourceId id where type LocOf id type CfgOf id retrieveLoc :: CfgOf id -> id -> LocOf id -- | Class describing a resource of type @rsc@ class (ResourceId (IdOf rsc)) => Resource rsc where type IdOf rsc load :: LocOf (IdOf rsc) -> IO (Maybe rsc) -- ^ Called when a resource needs to be loaded unload :: rsc -> IO () -- ^ Idem for unloading -- | Then, the operations that the loader can perform data EDSL id a where Load :: id -> EDSL id () IsLoaded :: id -> EDSL id Bool Unload :: id -> EDSL id () -- | The loader monad itself type RscLoader rsc m a = ProgramT (EDSL (IdOf rsc)) m a -- | And finally, how to run a loader runLoader :: (Monad m, Resource rsc) => CfgOf (IdOf rsc) -> RscLoader rsc m a -> m a runLoader cfg loader = viewT loader >>= eval M.empty where eval :: (Monad m, Resource rsc) => M.Map (IdOf rsc) rsc -> ProgramViewT (EDSL rsc) m a -> m a eval _ (Return x) = return x eval rscs (instr :>>= k) = case instr of Load id -> do let loc = retrieveLoc cfg id -- open and load from loc will go here viewT (k ()) >>= eval rscs -- -- -- Other cases yet to come... Well, there is no way I can get it type-check. I think I must be misusing the type families (I tried with multi-param typeclasses and functional dependencies, but it ends up to be the same kind of nightmare...).

Hi, There's nothing wrong with your type families. The problem is that the compiler doesn't know that the m and rsc of eval are the same as m and rsc of runLoader. (Also you had a small bug in the type of eval) You need the ScopedTypeVariables extension, with a forall on runLoader to tell GHC that they should be scoped: runLoader :: forall m rsc a. (Monad m, Resource rsc) => CfgOf (IdOf rsc) -> RscLoader rsc m a -> m a runLoader cfg loader = viewT loader >>= eval M.empty where eval :: (Monad m, Resource rsc) => M.Map (IdOf rsc) rsc -> ProgramViewT (EDSL (IdOf rsc)) m a -> m a eval _ (Return x) = return x eval rscs (instr :>>= k) = case instr of Load id -> do let loc = retrieveLoc cfg id -- open and load from loc will go here viewT (k ()) >>= eval rscs -- -- -- Other cases yet to come... greetings, Sjoerd On Nov 1, 2010, at 1:53 AM, Yves Parès wrote:
Hello,
I'm trying to make a simple monad (built on operational's ProgramT) for resource loading. I have classes featuring type families :
{-# LANGUAGE TypeFamilies, FlexibleContexts, GADTs #-}
-- | A ResourceId is something that identifies a resource. -- It should be unique for one resource, and should be used to find the location (the path) of the resource, -- possibly by using a configuration datatype class (Ord id) => ResourceId id where type LocOf id type CfgOf id retrieveLoc :: CfgOf id -> id -> LocOf id
-- | Class describing a resource of type @rsc@ class (ResourceId (IdOf rsc)) => Resource rsc where type IdOf rsc load :: LocOf (IdOf rsc) -> IO (Maybe rsc) -- ^ Called when a resource needs to be loaded unload :: rsc -> IO () -- ^ Idem for unloading
-- | Then, the operations that the loader can perform data EDSL id a where Load :: id -> EDSL id () IsLoaded :: id -> EDSL id Bool Unload :: id -> EDSL id ()
-- | The loader monad itself type RscLoader rsc m a = ProgramT (EDSL (IdOf rsc)) m a
-- | And finally, how to run a loader runLoader :: (Monad m, Resource rsc) => CfgOf (IdOf rsc) -> RscLoader rsc m a -> m a runLoader cfg loader = viewT loader >>= eval M.empty where eval :: (Monad m, Resource rsc) => M.Map (IdOf rsc) rsc -> ProgramViewT (EDSL rsc) m a -> m a eval _ (Return x) = return x eval rscs (instr :>>= k) = case instr of Load id -> do let loc = retrieveLoc cfg id -- open and load from loc will go here viewT (k ()) >>= eval rscs -- -- -- Other cases yet to come...
Well, there is no way I can get it type-check. I think I must be misusing the type families (I tried with multi-param typeclasses and functional dependencies, but it ends up to be the same kind of nightmare...). _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Sjoerd Visscher sjoerd@w3future.com

Yes, I did make a small mistake in the type of eval.
In fact, through the compiler messages, I guessed that it was a problem of
matching between the 'rsc' type variable of runLoader and the 'rsc' of eval.
I thought that this kind of matching was automatic in Haskell, well I was
wrong... Thanks !
2010/11/1 Sjoerd Visscher
Hi,
There's nothing wrong with your type families. The problem is that the compiler doesn't know that the m and rsc of eval are the same as m and rsc of runLoader. (Also you had a small bug in the type of eval)
You need the ScopedTypeVariables extension, with a forall on runLoader to tell GHC that they should be scoped:
runLoader :: forall m rsc a. (Monad m, Resource rsc) => CfgOf (IdOf rsc) -> RscLoader rsc m a -> m a runLoader cfg loader = viewT loader >>= eval M.empty where eval :: (Monad m, Resource rsc) => M.Map (IdOf rsc) rsc -> ProgramViewT (EDSL (IdOf rsc)) m a -> m a eval _ (Return x) = return x eval rscs (instr :>>= k) = case instr of Load id -> do let loc = retrieveLoc cfg id -- open and load from loc will go here viewT (k ()) >>= eval rscs -- -- -- Other cases yet to come...
greetings, Sjoerd
On Nov 1, 2010, at 1:53 AM, Yves Parès wrote:
Hello,
I'm trying to make a simple monad (built on operational's ProgramT) for resource loading. I have classes featuring type families :
{-# LANGUAGE TypeFamilies, FlexibleContexts, GADTs #-}
-- | A ResourceId is something that identifies a resource. -- It should be unique for one resource, and should be used to find the location (the path) of the resource, -- possibly by using a configuration datatype class (Ord id) => ResourceId id where type LocOf id type CfgOf id retrieveLoc :: CfgOf id -> id -> LocOf id
-- | Class describing a resource of type @rsc@ class (ResourceId (IdOf rsc)) => Resource rsc where type IdOf rsc load :: LocOf (IdOf rsc) -> IO (Maybe rsc) -- ^ Called when a resource needs to be loaded unload :: rsc -> IO () -- ^ Idem for unloading
-- | Then, the operations that the loader can perform data EDSL id a where Load :: id -> EDSL id () IsLoaded :: id -> EDSL id Bool Unload :: id -> EDSL id ()
-- | The loader monad itself type RscLoader rsc m a = ProgramT (EDSL (IdOf rsc)) m a
-- | And finally, how to run a loader runLoader :: (Monad m, Resource rsc) => CfgOf (IdOf rsc) -> RscLoader rsc m a -> m a runLoader cfg loader = viewT loader >>= eval M.empty where eval :: (Monad m, Resource rsc) => M.Map (IdOf rsc) rsc -> ProgramViewT (EDSL rsc) m a -> m a eval _ (Return x) = return x eval rscs (instr :>>= k) = case instr of Load id -> do let loc = retrieveLoc cfg id -- open and load from loc will go here viewT (k ()) >>= eval rscs -- -- -- Other cases yet to come...
Well, there is no way I can get it type-check. I think I must be misusing the type families (I tried with multi-param typeclasses and functional dependencies, but it ends up to be the same kind of nightmare...). _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Sjoerd Visscher sjoerd@w3future.com

Hi Yves, On 11/01/2010 09:44 PM, Yves Parès wrote:
Yes, I did make a small mistake in the type of eval. In fact, through the compiler messages, I guessed that it was a problem of matching between the 'rsc' type variable of runLoader and the 'rsc' of eval. I thought that this kind of matching was automatic in Haskell, well I was wrong... Thanks !
Just out of curiosity: Does it work if you omit eval's type signature? -- Steffen
2010/11/1 Sjoerd Visscher
mailto:sjoerd@w3future.com> Hi,
There's nothing wrong with your type families. The problem is that the compiler doesn't know that the m and rsc of eval are the same as m and rsc of runLoader. (Also you had a small bug in the type of eval)
You need the ScopedTypeVariables extension, with a forall on runLoader to tell GHC that they should be scoped:
runLoader :: forall m rsc a. (Monad m, Resource rsc) => CfgOf (IdOf rsc) -> RscLoader rsc m a -> m a runLoader cfg loader = viewT loader >>= eval M.empty where eval :: (Monad m, Resource rsc) => M.Map (IdOf rsc) rsc -> ProgramViewT (EDSL (IdOf rsc)) m a -> m a eval _ (Return x) = return x eval rscs (instr :>>= k) = case instr of Load id -> do let loc = retrieveLoc cfg id -- open and load from loc will go here viewT (k ()) >>= eval rscs -- -- -- Other cases yet to come...
greetings, Sjoerd
On Nov 1, 2010, at 1:53 AM, Yves Parès wrote:
> Hello, > > I'm trying to make a simple monad (built on operational's ProgramT) for resource loading. > I have classes featuring type families : > > {-# LANGUAGE TypeFamilies, FlexibleContexts, GADTs #-} > > -- | A ResourceId is something that identifies a resource. > -- It should be unique for one resource, and should be used to find the location (the path) of the resource, > -- possibly by using a configuration datatype > class (Ord id) => ResourceId id where > type LocOf id > type CfgOf id > retrieveLoc :: CfgOf id -> id -> LocOf id > > -- | Class describing a resource of type @rsc@ > class (ResourceId (IdOf rsc)) => Resource rsc where > type IdOf rsc > load :: LocOf (IdOf rsc) -> IO (Maybe rsc) > -- ^ Called when a resource needs to be loaded > unload :: rsc -> IO () > -- ^ Idem for unloading > > -- | Then, the operations that the loader can perform > data EDSL id a where > Load :: id -> EDSL id () > IsLoaded :: id -> EDSL id Bool > Unload :: id -> EDSL id () > > -- | The loader monad itself > type RscLoader rsc m a = ProgramT (EDSL (IdOf rsc)) m a > > -- | And finally, how to run a loader > runLoader :: (Monad m, Resource rsc) => CfgOf (IdOf rsc) -> RscLoader rsc m a -> m a > runLoader cfg loader = viewT loader >>= eval M.empty > where > eval :: (Monad m, Resource rsc) => > M.Map (IdOf rsc) rsc > -> ProgramViewT (EDSL rsc) m a > -> m a > eval _ (Return x) = return x > eval rscs (instr :>>= k) = case instr of > Load id -> do let loc = retrieveLoc cfg id > -- open and load from loc will go here > viewT (k ()) >>= eval rscs > -- -- -- Other cases yet to come... > > > > Well, there is no way I can get it type-check. I think I must be misusing the type families (I tried with multi-param typeclasses and functional dependencies, but it ends up to be the same kind of nightmare...). > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org mailto:Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Sjoerd Visscher sjoerd@w3future.com mailto:sjoerd@w3future.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Just out of curiosity: Does it work if you omit eval's type signature?
In fact you can't omit it since EDSL is a GADT.
I don't know why there is this restriction, but it is written in
operational's documentation:
http://hackage.haskell.org/packages/archive/operational/0.2.0.1/doc/html/Con...
(At the very bottom of the page)
But there still must be something I don't get :
I tried to merge the two classes ResourceId and Resource in only one
Resource class, which leads to a few changes in runLoader :
{-# LANGUAGE TypeFamilies, FlexibleContexts, GADTs, ScopedTypeVariables #-}
import qualified Data.Map as M
import Control.Monad.Operational
-- | A ResourceId is something that identifies a resource.
-- It should be unique for one resource, and should be used to find the
location (the path) of the resource,
-- possibly by using a configuration datatype
--class (Ord id) => ResourceId id where
-- | Class describing a resource of type @rsc@
class (Ord (IdOf rsc)) => Resource rsc where
type IdOf rsc
type LocOf rsc
type CfgOf rsc
retrieveLoc :: CfgOf rsc -> IdOf rsc -> LocOf rsc
load :: LocOf rsc -> IO (Maybe rsc)
-- ^ Called when a resource needs to be loaded
unload :: rsc -> IO ()
-- ^ Idem for unloading
-- | Then, the operations that the loader can perform
data EDSL id a where
Load :: id -> EDSL id ()
IsLoaded :: id -> EDSL id Bool
Unload :: id -> EDSL id ()
-- | The loader monad itself
type RscLoader rsc m a = ProgramT (EDSL (IdOf rsc)) m a
-- | And finally, how to run a loader
runLoader :: forall m rsc a. (Monad m, Resource rsc)
=> CfgOf rsc -> RscLoader rsc m a -> m a
runLoader cfg loader = viewT loader >>= eval M.empty
where
eval :: (Monad m, Resource rsc)
=> M.Map (IdOf rsc) rsc
-> ProgramViewT (EDSL (IdOf rsc)) m a
-> m a
eval _ (Return x) = return x
eval rscs (instr :>>= k) = case instr of
* Load id -> do let loc = retrieveLoc cfg id*
-- open and load from loc will go here
viewT (k ()) >>= eval rscs
-- -- -- Other cases yet to come...
This leads to new errors with 'IdOf rsc' and 'CfgOf rsc' :
GameBasics/Resources.hs:46:42:
Couldn't match expected type `CfgOf rsc'
against inferred type `CfgOf rsc1'
NB: `CfgOf' is a type function, and may not be injective
In the first argument of `retrieveLoc', namely `cfg'
In the expression: retrieveLoc cfg id
In the definition of `loc': loc = retrieveLoc cfg id
GameBasics/Resources.hs:46:46:
Couldn't match expected type `IdOf rsc'
against inferred type `IdOf rsc1'
NB: `IdOf' is a type function, and may not be injective
In the second argument of `retrieveLoc', namely `id'
In the expression: retrieveLoc cfg id
In the definition of `loc': loc = retrieveLoc cfg id
Seems like the compiler still has a 'rsc1' type despite the scoped type
variable 'rsc'.
2010/11/1 Yves Parès
Yes, I did make a small mistake in the type of eval. In fact, through the compiler messages, I guessed that it was a problem of matching between the 'rsc' type variable of runLoader and the 'rsc' of eval. I thought that this kind of matching was automatic in Haskell, well I was wrong... Thanks !
2010/11/1 Sjoerd Visscher
Hi,
There's nothing wrong with your type families. The problem is that the compiler doesn't know that the m and rsc of eval are the same as m and rsc of runLoader. (Also you had a small bug in the type of eval)
You need the ScopedTypeVariables extension, with a forall on runLoader to tell GHC that they should be scoped:
runLoader :: forall m rsc a. (Monad m, Resource rsc) => CfgOf (IdOf rsc) -> RscLoader rsc m a -> m a runLoader cfg loader = viewT loader >>= eval M.empty where eval :: (Monad m, Resource rsc) => M.Map (IdOf rsc) rsc -> ProgramViewT (EDSL (IdOf rsc)) m a -> m a eval _ (Return x) = return x eval rscs (instr :>>= k) = case instr of Load id -> do let loc = retrieveLoc cfg id -- open and load from loc will go here viewT (k ()) >>= eval rscs -- -- -- Other cases yet to come...
greetings, Sjoerd
On Nov 1, 2010, at 1:53 AM, Yves Parès wrote:
Hello,
I'm trying to make a simple monad (built on operational's ProgramT) for resource loading. I have classes featuring type families :
{-# LANGUAGE TypeFamilies, FlexibleContexts, GADTs #-}
-- | A ResourceId is something that identifies a resource. -- It should be unique for one resource, and should be used to find the location (the path) of the resource, -- possibly by using a configuration datatype class (Ord id) => ResourceId id where type LocOf id type CfgOf id retrieveLoc :: CfgOf id -> id -> LocOf id
-- | Class describing a resource of type @rsc@ class (ResourceId (IdOf rsc)) => Resource rsc where type IdOf rsc load :: LocOf (IdOf rsc) -> IO (Maybe rsc) -- ^ Called when a resource needs to be loaded unload :: rsc -> IO () -- ^ Idem for unloading
-- | Then, the operations that the loader can perform data EDSL id a where Load :: id -> EDSL id () IsLoaded :: id -> EDSL id Bool Unload :: id -> EDSL id ()
-- | The loader monad itself type RscLoader rsc m a = ProgramT (EDSL (IdOf rsc)) m a
-- | And finally, how to run a loader runLoader :: (Monad m, Resource rsc) => CfgOf (IdOf rsc) -> RscLoader rsc m a -> m a runLoader cfg loader = viewT loader >>= eval M.empty where eval :: (Monad m, Resource rsc) => M.Map (IdOf rsc) rsc -> ProgramViewT (EDSL rsc) m a -> m a eval _ (Return x) = return x eval rscs (instr :>>= k) = case instr of Load id -> do let loc = retrieveLoc cfg id -- open and load from loc will go here viewT (k ()) >>= eval rscs -- -- -- Other cases yet to come...
Well, there is no way I can get it type-check. I think I must be misusing the type families (I tried with multi-param typeclasses and functional dependencies, but it ends up to be the same kind of nightmare...). _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Sjoerd Visscher sjoerd@w3future.com

This one is easy:
-- | Class describing a resource of type @rsc@ class (Ord (IdOf rsc)) => Resource rsc where type IdOf rsc type LocOf rsc type CfgOf rsc retrieveLoc :: CfgOf rsc -> IdOf rsc -> LocOf rsc load :: LocOf rsc -> IO (Maybe rsc) -- ^ Called when a resource needs to be loaded unload :: rsc -> IO () -- ^ Idem for unloading
Consider this: instance Resource () where type IdOf () = Int type LocOf () = String type CfgOf () = () retrieveLoc () n = "Unit_" ++ show n load = undefined unload = undefined instance Resource Int where type IdOf () = Int type LocOf () = String type CfgOf () = () retrieveLoc () n = "Int_ " ++ show n load = undefined unload = undefined foo = retrieveLoc :: () -> Int -> String -- which retrieveLoc is called here? The problem, in case you haven't surmised it, is that retrieveLoc is ambiguous; you can never call it! There's no way to know which instance you might be referring to. You can work around it by making one of the type families into a data family (which is injective; you know that if CfgOf x = CfgOf y, then x = y). Or you can add a proxy parameter to retrieveLoc:
data Proxy a = Proxy retrieveLoc :: Proxy rsc -> CfgOf rsc -> IdOf rsc -> LocOf rsc
now:
foo = retrieveLoc (Proxy :: Proxy ())
and ghc can correctly infer foo's type as
foo :: () -> Int -> String
and foo will call the retrieveLoc from the () instance. -- ryan

I understand your point Ryan, but in that case, why didn't the error occur when Resource and ResourceId were separated classes? BTW, I assume for your Int instance of Resource, you meant:
instance Resource Int where type IdOf *Int* = Int type LocOf *Int* = String type CfgOf *Int* = () retrieveLoc () n = "Int_ " ++ show n load = undefined unload = undefined
2010/11/2 Ryan Ingram
This one is easy:
-- | Class describing a resource of type @rsc@ class (Ord (IdOf rsc)) => Resource rsc where type IdOf rsc type LocOf rsc type CfgOf rsc retrieveLoc :: CfgOf rsc -> IdOf rsc -> LocOf rsc load :: LocOf rsc -> IO (Maybe rsc) -- ^ Called when a resource needs to be loaded unload :: rsc -> IO () -- ^ Idem for unloading
Consider this:
instance Resource () where type IdOf () = Int type LocOf () = String type CfgOf () = () retrieveLoc () n = "Unit_" ++ show n load = undefined unload = undefined
instance Resource Int where type IdOf () = Int type LocOf () = String type CfgOf () = () retrieveLoc () n = "Int_ " ++ show n load = undefined unload = undefined
foo = retrieveLoc :: () -> Int -> String -- which retrieveLoc is called here?
The problem, in case you haven't surmised it, is that retrieveLoc is ambiguous; you can never call it! There's no way to know which instance you might be referring to. You can work around it by making one of the type families into a data family (which is injective; you know that if CfgOf x = CfgOf y, then x = y). Or you can add a proxy parameter to retrieveLoc:
data Proxy a = Proxy retrieveLoc :: Proxy rsc -> CfgOf rsc -> IdOf rsc -> LocOf rsc
now:
foo = retrieveLoc (Proxy :: Proxy ())
and ghc can correctly infer foo's type as
foo :: () -> Int -> String
and foo will call the retrieveLoc from the () instance.
-- ryan

On Tue, Nov 2, 2010 at 12:32 AM, Yves Parès
I understand your point Ryan, but in that case, why didn't the error occur when Resource and ResourceId were separated classes?
Because there was only one "retrieveLoc" for a particular IdOf, even if resources shared an IdOf. i.e. instance ResourceId Int where type CfgOf Int = () type LocOf Int = String retreiveLoc () n = "IntId " ++ show n instance Resource () where type IdOf () = Int instance Resource Int where type IdOf Int = Int In this case retrieveLoc () (5 :: Int) = "IntId 5" without any ambiguity, whereas when it was all one class there could be a different method to retrieve the location for () and Int even if IdOf was both Int.
BTW, I assume for your Int instance of Resource, you meant:
instance Resource Int where type IdOf Int = Int type LocOf Int = String type CfgOf Int = ()
Yes, that's correct. Oops. -- ryan
participants (4)
-
Ryan Ingram
-
Sjoerd Visscher
-
Steffen Schuldenzucker
-
Yves Parès