Skip to content

Instantly share code, notes, and snippets.

@tokiwoousaka
Created October 1, 2014 05:44
Show Gist options
  • Save tokiwoousaka/944425424107f0f578a3 to your computer and use it in GitHub Desktop.
Save tokiwoousaka/944425424107f0f578a3 to your computer and use it in GitHub Desktop.
Eff.StateをMonadStateのインスタンスにすればLensが使える
{-# LANGUAGE FlexibleContexts, ScopedTypeVariables #-}
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, UndecidableInstances #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE TemplateHaskell #-}
module Main where
import Data.Typeable
import Control.Eff
import Control.Eff.State.Lazy as EST
import Control.Monad.State.Class (MonadState(..))
import Control.Lens
instance (Typeable x, Member (State x) r) => MonadState x (Eff r) where
get = EST.get
put = EST.put
----
data Foo = Foo
{ _hoge :: Int
, _piyo :: String
, _fuga :: Bool
} deriving (Show, Typeable)
makeLenses ''Foo
proc :: (Member (State Foo) r) => Eff r ()
proc = do
hoge *= 2
p <- use $ piyo
piyo .= "[" ++ p ++ "]"
fuga .= True
----
main = do
let foo = Foo
{ _hoge = 100
, _piyo = "Hello"
, _fuga = False
}
print . run $ execState foo proc
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment