I saw that to write liftQD you decontruct (unwrap) the type and reconstruct it.
I don't know if I can do that for my Exp (which is a full DSL)...
Anyway, there should be a way to encode the Effect/NoEffect semantic at type level...
Using Oleg's parametrized monad idea (
http://hackage.haskell.org/package/monad-param-0.0.2/docs/Control-Monad-Parameterized.html), I tried:
> {-# LANGUAGE KindSignatures, DataKinds, ScopedTypeVariables, GADTs
> MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, UndecidableInstances #-}
> module DSLEffects where
> import Prelude hiding (return, (>>), (>>=))
> import Control.Monad.ParameterizedThis data type will be promoted to kind level (thanks to DataKinds):
> data Eff = Effect | NoEffectThis class allows to specify the semantic on Effects (Effect + NoEffect = Effect):
> class Effects (m :: Eff) (n::Eff) (r::Eff) | m n -> r
> instance Effects Effect n Effect
> instance Effects NoEffect n nThis is the DSL:
> data Exp :: Eff -> * -> * where
> ReadAccount :: Exp NoEffect Int --ReadAccount has no effect
> WriteAccount :: Int -> Exp Effect () --WriteAccount has effect
> Const :: a -> Exp r a
> Bind :: Effects m n r => Exp m a -> (a -> Exp n b) -> Exp r b --Bind comes with a semantic on effects
> Fmap :: (a -> b) -> Exp m a -> Exp m b
> instance Functor (Exp r) where
> fmap = Fmap
> instance Return (Exp r) where
> returnM = Const
> instance (Effects m n r) => Bind (Exp m) (Exp n) (Exp r) where
> (>>=) = Bind
> noEff :: Exp NoEffect ()
> noEff = returnM ()
> hasEffect :: Exp Effect ()
> hasEffect = ReadAccount >> (returnM () :: Exp Effect ())This is working more or less, however I am obliged to put the type signature on the returnM (last line): why?