Bilal Syed Hussain
Bilal Syed Hussain

Reputation: 9204

How to patten match on a field of a state monad?

Is it possible to write write the function a using pattens matching/guards?

{-# LANGUAGE PatternGuards #-}
import Control.Monad.State.Strict(State, gets, runStateT)
data MyState = MyState
    { counter :: Int
    } deriving (Show)


a :: State MyState String
a = do
    i <- gets counter
    case i of
        0 -> return "hello"
        1 -> return "bye"

run = runStateT a ( MyState{counter=0} )

I tried writing a as

a' :: State MyState String
a' | i <- gets counter, i == 0 = return "hello"

but got the errors:

No instance for (Control.Monad.State.Class.MonadState MyState m0)
  arising from a use of ‘gets’
The type variable ‘m0’ is ambiguous
Note: there are several potential instances:
  instance Control.Monad.State.Class.MonadState s m =>
           Control.Monad.State.Class.MonadState
             s (Control.Monad.Trans.Cont.ContT r m)
    -- Defined in ‘Control.Monad.State.Class’
  instance (Control.Monad.Trans.Error.Error e,
            Control.Monad.State.Class.MonadState s m) =>
           Control.Monad.State.Class.MonadState
             s (Control.Monad.Trans.Error.ErrorT e m)
    -- Defined in ‘Control.Monad.State.Class’
  instance Control.Monad.State.Class.MonadState s m =>
           Control.Monad.State.Class.MonadState
             s (Control.Monad.Trans.Except.ExceptT e m)
    -- Defined in ‘Control.Monad.State.Class’
  ...plus 12 others
In a stmt of a pattern guard for
               an equation for ‘a'’:
  i <- gets counter
In an equation for ‘a'’:
    a' | i <- gets counter, i == 0 = return "hello"

No instance for (Eq (m0 Int)) arising from a use of ‘==’
The type variable ‘m0’ is ambiguous
Relevant bindings include
  i :: m0 Int (bound at src/TestGen/Arbitrary/Helpers/Z.hs:18:6)
Note: there are several potential instances:
  instance Eq a => Eq (GHC.Real.Ratio a) -- Defined in ‘GHC.Real’
  instance (Eq e, Data.Functor.Classes.Eq1 m, Eq a) =>
           Eq (Control.Monad.Trans.Error.ErrorT e m a)
    -- Defined in ‘Control.Monad.Trans.Error’
  ...plus 118 others
In the expression: i == 0
In a stmt of a pattern guard for
               an equation for ‘a'’:
  i == 0
In an equation for ‘a'’:
    a' | i <- gets counter, i == 0 = return "hello"

Upvotes: 2

Views: 833

Answers (4)

dfeuer
dfeuer

Reputation: 48591

Yes, this is possible, but I would advise you not to do it—it's hard to keep track of which piece goes where.

import Control.Monad.State.Strict(StateT(..))
import Data.Functor.Identity(Identity(..))

data MyState = MyState
    { counter :: Int
    } deriving (Show)

a :: StateT MyState Identity String
a = StateT $ \ s@(MyState i) -> Identity $
  case i of
    0 -> ("hello", s)
    1 -> ("bye", s)

Upvotes: 1

CR Drost
CR Drost

Reputation: 9807

No. There are some really fundamental conceptual mismatches here.

Pattern matching only works when the topmost part of the expression is a constructor function, but the head of a do-style block is going to be a normal function (in this case the function >>= defined in the typeclasss Monad).

Guards expect a value of type Bool but the value you're going to hand them will have to be of type State MyState Bool (since one of the distinctive things about monads is that you cannot escape from them). So guards will also never work.

You can however reach for the functor instance. Functors are defined in the Prelude; there is an infix form of fmap called <$> in Control.Applicative. You would use this by saying:

a' = process <$> gets counter
    where 
        process 0 = "hello"
        process _ = "bye"

or doing whatever you want with the process function. To get something more like >>= you could also define your own operator as flip fmap and then you can write, say, gets counter >= \x -> case x of ....

Upvotes: 3

Roman Cheplyaka
Roman Cheplyaka

Reputation: 38718

This is not possible. Left arrow in the pattern guard syntax is mostly unrelated to the left arrow in the do-notation.

You can use the new lambda-case extension if you like:

{-# LANGUAGE LambdaCase #-}
a :: State MyState String
a = gets counter >>= \case
        0 -> return "hello"
        1 -> return "bye"

Or multi-way if, perhaps?

{-# LANGUAGE MultiWayIf #-}
a :: State MyState String
a = do
    i <- gets counter
    if
      | i == 0 -> return "hello"
      | i == 1 -> return "bye"

Upvotes: 8

bheklilr
bheklilr

Reputation: 54058

Why not write a helper?

pureA :: MyState -> String
pureA (MyState 0) = "hello"
pureA (MyState 1) = "bye"
pureA _           = ""

a :: State MyState String
a = fmap doA get

This also follows the philosophy of separating concerns of pure logic from your impure logic.

Upvotes: 2

Related Questions