[Haskell-cafe] Unable to make a HList-like to deal with Kleisli Arrows and State

adam vogt vogt.adam at gmail.com
Thu Jun 12 01:42:43 UTC 2014


Hi Gautier,

It seems like `type State s = StateT s Identity` causes the problem.
You could supply Identity as an argument:

data REnv (ts :: [*])
          (i :: *)
          (o :: *)
          (s :: * -> (* -> *) -> * -> *)
          (k :: (* -> *) -> * -> * -> *) where
  Last  :: k (s t Identity) i o -> REnv (t ': '[]) i o s k
  RCons :: k (s t Identity) i o' -> REnv ts o' o s k -> REnv (t ': ts) i o s k


Or I guess you could keep the original REnv, and require a newtype

newtype MyState s a = MyState (State s a)
   deriving (MonadState s, Monad)

Regards,
Adam


On Wed, Jun 11, 2014 at 3:31 PM, Gautier DI FOLCO
<gautier.difolco at gmail.com> wrote:
> Hi all,
>
> My goal is to compose Kleisli arrows with (State s) as parameteric Monadic
> type.
> So, I end up with the following code:
>
> data REnv :: [*] -> * -> * -> (* -> * -> *) -> ((* -> *) -> * -> * -> *) ->
> * where
>   Last  :: k (s t) i o -> REnv (t ': '[]) i o s k
>   RCons :: k (s t) i o' -> REnv ts o' o s k -> REnv (t ': ts) i o s k
>
>
> Which, of course, gives me the following error when I try to play with it:
>
> *H> :t Last genRanking
>
> <interactive>:1:6:
>     Kind incompatibility when matching types:
>       s :: * -> * -> *
>       StateT Ranking :: (* -> *) -> * -> *
>     Expected type: Kleisli (s t) Ticket Ranking
>       Actual type: Kleisli (State Ranking) Ticket Ranking
>     In the first argument of ‘Last’, namely ‘genRanking’
>     In the expression: Last genRanking
>
> <interactive>:1:6:
>     Kind incompatibility when matching types:
>       t :: *
>       Data.Functor.Identity.Identity :: * -> *
>     Expected type: Kleisli (s t) Ticket Ranking
>       Actual type: Kleisli (State Ranking) Ticket Ranking
>     In the first argument of ‘Last’, namely ‘genRanking’
>     In the expression: Last genRanking
> *H> :t Last
> Last :: k (s t) i o -> REnv '[t] i o s k
> *H> :t genRanking
> genRanking :: Kleisli (State Ranking) Ticket Ranking
>
>
> I understand why it fails (State is * -> * -> *, while s is * -> *), but I
> can't figure out how to write this, I tried (s t o), but it isn't correct
> because k waits for a (* -> *).
>
>
> If you have any ideas, I'm curious to read them.
>
> Thanks in advance for your help.
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list