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
sjo...@w3future.com



_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to