Hi, Dennis,

the problem is that you are attempting to "partially apply" the type synonym Er, which is problematic [1].
One solution is to wrap up the type synonym in a newtype wrapper and then define everything on this new data type, e.g.

newtype Er a = Er { unEr :: ErrorT String (State RandState) a }

instance Monad Er where
-- insert definitions here or use "GeneralizedNewtypeDeriving" and derive Monad automatically

instance RandMonad Er where
  putGen g = Er $ put (RandState g)
  getGen   = Er $ do RandState g <- get
                     return g

Best regards,

Nikita

[1] http://stackoverflow.com/questions/4922560/why-doesnt-typesynonyminstances-allow-partially-applied-type-synonyms-to-be-use

On 28/03/14 10:10, Dennis Raddle wrote:
I'm writing a program which uses a lot of pseudorandom numbers, and for that reason it would be nice to put the StdGen in a state monad.

like let's say I want to combine error handling and storing the StdGen state.

import Control.Monad.Error
import Control.Monad.State

data RandState = RandState StdGen
-- Er is a monad that combines error handling and pseudorandom state
type Er a = ErrorT String (State RandState) a

-- to access random numbers, I could define things like


erRandomR :: Random r => (r,r) -> Er r
erRandomR (lo, hi) = do
  RandState g <- get
  let (value, g') = randomR (lo, hi) g
  put $ RandState g'
  return value


erRandoms :: Random r => Er [r]
erRandoms = do
  RandState g <- get
  let (g1, g2) = split g
  let values = randoms g1
  put $ RandState g2
  return values


erRandomRs :: Random r => (r,r) -> Er [r]
erRandomRs (lo,hi) = do
  RandState g <- get
  let (g1, g2) = split g
  let values = randomRs (lo,hi) g1
  put $ RandState g2
  return values

-- I could define new ways of using random values, like choosing a random element of a list

erChooseList :: [a] -> Er a
erChooseList xs = do
  let l = length xs
  when (l==0) (throwError "in randomChooseList, passed null list")
  idx <- erRandomR (0,l-1)
  return $ xs !! idx

However, after I got done with that, I realized that I wanted to add additional state, maybe a ReaderT , stuff like that--different in different parts of the program. But I always want access to random numbers with the same functions: erRandomR, erRandoms, etc.

So I thought

class Monad m => RandMonad m where
  putGen ::  StdGen -> m ()
  getGen :: m StdGen

Then I could make Er an instance of RandMonad, like this

type Er a = ErrorT String (State RandState) a
instance RandMonad Er where
  putGen g = put (RandState g)
  getGen = do RandState g <- get
              return g

Clearly I don't know what I'm doing, because when I tried to run this much I got the error

"Type synonym Er should have 1 argument, but has been given none."

I tried a bunch of variations of this but got nowhere. Can someone explain how I should conceive of this?
                    



_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


-- 
Dipl.-Math. Nikita Danilenko
Research group:
Computer Aided Program Development
Kiel University
Olshausenstr. 40, D-24098 Kiel
Phone: +49 431 880 7275
URL: https://www.informatik.uni-kiel.de/index.php?id=nikita