1

I am trying to define instances for Applicative and Monad of RWS, but there must be something that I am missing. For pure, I am getting an occurs check error. It must have something to do with the fact that I give RWS f as the result of pure, despite f having the type a. I don't understand how to access the other arguments of RWS (r, w and s). I would appreciate it if someone explained some of the notions in detail, such as the newtype definition. As I understand it, we define a new type RWS which has 4 arguments (r, w, s and a). This type is defined using a constructor (fromRWS), that does something with the arguments. Correct me if I am wrong. If this is correct, is RWS defined by the 4 arguments or by fromRWS?

Moving further, the implementation for <*> produces a type error. It says that fromRWS2 is applied to too few arguments. I don't see the issue, though, since I have used the same where clause approach to solve a similar problem for a variable environment. What alternatives do can I use?

When defining Monad, I just got a parse error on input RWS

Please help me define the instances.

Here is my code:

module RWS where

newtype RWS r w s a = RWS { fromRWS :: r -> s -> (a, s, w) }

instance Functor (RWS r w s) where
  fmap f (RWS rws) = RWS $ \r s -> let (a,s',w) = rws r s in (f a, s', w)

instance Monoid w => Applicative (RWS r w s) where
    -- pure a -> RWS r w s a
    pure f = RWS f
    -- (<*>) :: RWS r w s (a -> b) -> RWS r w s a -> RWS r w s b 
    RWS f <*> RWS a = RWS fromRWS2
                            where fromRWS2 r1 s1 = f a

instance Monoid w => Monad (RWS r w s) where
   --return :: a -> RWS r w s a
   return x = RWS x
   --(>>=)  :: (RWS r w s a) -> (a -> (RWS r w s b)) -> (RWS r w s b)
  RWS fr >>= f = f fr
duplode
  • 33,731
  • 7
  • 79
  • 150
andy_bruja
  • 21
  • 4

2 Answers2

1

Maybe it is clearer if we write RWS as

newtype RWS r w s a = MakeRWS { fromRWS :: (r -> s -> (a, s, w)) }

This definition gets you three things:

  • A type constructor RWS taking the four r w s a arguments.
  • A data constructor MakeRWS of type (r -> s -> (a, s, w)) -> RWS r w s a
  • A field accessor fromRWS of type RWS r w s a -> (r -> s -> (a, s, w))

As we can see the data constructor MakeRWS should be applied to a function to construct the value of type RWS r w s a.

In your pure implementation you apply MakeRWS to a value of type a not a function. This is what goes wrong with you pure implementation.

As you note in the comment the type of pure should be

a -> RWS r w s a

but your implementation would have had this type if it worked:

(r -> s -> (a, s, w)) -> RWS r w s a

The correct implementation is

pure a = MakeRWS (\_r s -> (a, s, mempty)

Your monad implementation fails parsing because you don't have the same indentation on the return line as the line starting RWS.

ase
  • 13,231
  • 4
  • 34
  • 46
  • 1
    I managed to fix ```pure```. Still having trouble with ```<*>``` and Monad, after the indentation changes. Where can I update the code after making changes? Is this allowed in the original post? – andy_bruja Nov 28 '20 at 10:15
  • @andy_bruja edits must not invalidate the answer(s), so probably, don't edit it. :) – Will Ness Nov 28 '20 at 11:08
1

Just follow the type(s). We can only do so much with any given thing:

-- newtype RWS r w s a  =  RWS { fromRWS :: r -> s -> (a, s, w) }

-- .....

    RWS tf <*> RWS ta  =  RWS tfa
        where 
        tfa r1 s1  =  (f a, s?, w2 ?? w3)  -- what is ?
           where                           -- what is ??
           (f, s2, w2) = tf r1 s1 
           (a, s3, w3) = ta r1 s2 

Similarly for the monad. First of all return = pure and the other answer shows you how to define that:

    pure a  =  RWS ta
        where
        ta _r s  =  (a, s, mempty)

Then the bind is

   --(>>=)  :: (RWS r w s a) -> (a -> (RWS r w s b)) -> (RWS r w s b)
  (RWS f) >>= k  =  RWS g
       where
       -- RWS f :: RWS r w s a
       --     f :: r -> s -> (a, s, w)
       -- RWS g :: RWS r w s b
       --     g :: r -> s -> (b, s, w)
       g r1 s1  =  ???                     -- what is ???
            where
            (a, s2, w2) = f r1 s1
            (RWS h)     = k a
            -- RWS h :: RWS r w s b
            --     h :: r -> s -> (b, s, w)
            (b, s3, w3) = h r1 s????       -- what is ????
Will Ness
  • 70,110
  • 9
  • 98
  • 181