Hello,<br><br>I&#39;m trying to make a simple monad (built on operational&#39;s ProgramT) for resource loading.<br>I have classes featuring type families :<br><br>{-# LANGUAGE TypeFamilies, FlexibleContexts, GADTs #-}<br><br>
-- | A ResourceId is something that identifies a resource.<br>-- It should be unique for one resource, and should be used to find the location (the path) of the resource,<br>-- possibly by using a configuration datatype<br>
class (Ord id) =&gt; ResourceId id where<br>  type LocOf id<br>  type CfgOf id<br>  retrieveLoc :: CfgOf id -&gt; id -&gt; LocOf id<br><br>-- | Class describing a resource of type @rsc@<br>class (ResourceId (IdOf rsc)) =&gt; Resource rsc where<br>
  type IdOf rsc<br>  load   :: LocOf (IdOf rsc) -&gt; IO (Maybe rsc)<br>    -- ^ Called when a resource needs to be loaded<br>  unload :: rsc -&gt; IO ()<br>    -- ^ Idem for unloading<br><br>-- | Then, the operations that the loader can perform<br>
data EDSL id a where<br>  Load     :: id -&gt; EDSL id ()<br>  IsLoaded :: id -&gt; EDSL id Bool<br>  Unload   :: id -&gt; EDSL id ()<br><br>-- | The loader monad itself<br>type RscLoader rsc m a = ProgramT (EDSL (IdOf rsc)) m a<br>
<br>-- | And finally, how to run a loader<br>runLoader :: (Monad m, Resource rsc) =&gt; CfgOf (IdOf rsc) -&gt; RscLoader rsc m a -&gt; m a<br>runLoader cfg loader = viewT loader &gt;&gt;= eval M.empty<br>  where<br>    eval :: (Monad m, Resource rsc) =&gt;<br>
         M.Map (IdOf rsc) rsc<br>         -&gt; ProgramViewT (EDSL rsc) m a<br>         -&gt; m a<br>    eval _    (Return x)     = return x<br>    eval rscs (instr :&gt;&gt;= k) = case instr of<br>      Load id -&gt; do let loc = retrieveLoc cfg id<br>
                          -- open and load from loc will go here<br>                          viewT (k ()) &gt;&gt;= eval rscs<br>      -- -- -- Other cases yet to come...<br><br><br><br>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...).<br>