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

Dennis Raddle dennis.raddle at gmail.com
Thu Jun 28 05:22:46 UTC 2018


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.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20180627/d1380a3c/attachment.html>


More information about the Haskell-Cafe mailing list