[Haskell-cafe] need help understanding how to specify constraints on monads

Paolino paolo.veronelli at gmail.com
Thu Jun 28 13:28:09 UTC 2018


All you need is the state to have different "aspects"

You can express this with parameters to your stateful computations

Here's an (uncompiled) sketch covering part of your case, using lenses

{-# language TemplateHaskell #-}

import Control.Lens (Lens', set, makeLenses)
import System.Random
import Control.Monad.State

-- a user of any state 's' which has  a StdGen aspect, see the 's' is free
here so putGen is polymorphic in it
putGen :: Lens' s StdGen -> StdGen -> State s  ()
putGen l g = modify $ set l g
-- or for shorter see Control.Lens.Setter
-- putGen = (.=)

...
...

-- a state as a record with all aspects
data S = S {
  .... :: ....
 , _generator :: StdGen
  ..... :: ..
}

makeLenses ''S -- automatically derive the lenses for you (generator
function in example)
-- equivalent at least  to something like
-- generator f g s = (\g' -> s{_generator = g'}) <$> f g

main = do
  g0 <- newStdGen
  print $ evalState (putGen generator g >> ....) $ S ... g0 ..

(This leaves you the burden of passing lenses around (one for each aspect)
which you could alleviate with different techniques, if this is ever a
concern)

As Tom said, typeclasses are not that good for this cases as it might seem
at first glance

HTH

Best

paolino

On Thu, 28 Jun 2018 at 07:23, Dennis Raddle <dennis.raddle at gmail.com> wrote:

> I'm writing a program with several functions, some of which depend on
> certain fields in a state monad, others of which depend on others, but no
> routine needs all the fields.
>
> So I thought I would declare a two classes, one for each type of data need
> that a function has:
>
> -- as an aside, here's an example of data which is parameterized by two
> types.
>
> data ReportData t1 t2 = ...
>
> -- this is rolling my own state monad with a random generator
> class Monad m => RandMonad m where
>    getGen :: m StdGen
>    putGen :: StdGen -> ()
>
> -- this is a class of state monad which logs ReportData:
>
> class Monad m => LogMonad m where
>    putReport :: ReportData t1 t2 -> m ()
>
> For a particular use case, I declare a type of State monad:
>
> data MyStateData t1 t2 = MyStateData t1 t2
>   { theGen :: StdGen
>   , theReports :: [StepReport t1 t2]
>   }
>
> type MyState t1 t2 = State (MyStateData t1 t2)
>
> And I try to define my instances:
>
> instance RandMonad (MyState t1 t2) where
>   getGen = gets theGen
>   putGen g = modify (\s -> s { theGen = g})
>
> instance LogMonad (MyState t1 t2) where
>   putReport r = modify (\s -> s { theReports = r : theReports s})
>
> I get an error on the LogMonad instance, saying that there's no instance
> for (MonadState (MyState t1 t2) (StateT (MyState t1 t2) Identity))
>
> I guess I don't really understand typeclasses once you start using higher
> kinded types, so please enlighten me. Any reading on this subject would be
> helpful, too.
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20180628/18e6b72c/attachment.html>


More information about the Haskell-Cafe mailing list