Skip to content

Instantly share code, notes, and snippets.

@tokiwoousaka
Created October 1, 2014 06:51
Show Gist options
  • Save tokiwoousaka/1a8b72044f6e3a7b5b93 to your computer and use it in GitHub Desktop.
Save tokiwoousaka/1a8b72044f6e3a7b5b93 to your computer and use it in GitHub Desktop.
Eff.Choose + Eff.State + 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.Eff.Choose
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 Choose r, Member (State Foo) r) => Eff r Foo
proc = do
hoge *= 2
s <- choose ["+++", "---", "***"]
p <- use $ piyo
piyo .= s ++ p ++ s
fuga .= True
(res :: Foo) <- EST.get
return res
----
main = do
let foo = Foo
{ _hoge = 100
, _piyo = "Hello"
, _fuga = False
}
print . run $ runChoice (execState foo proc)
-- 実行結果
-- [ Foo {_hoge = 200, _piyo = "+++Hello+++", _fuga = True}
-- , Foo {_hoge = 200, _piyo = "---Hello---", _fuga = True}
-- , Foo {_hoge = 200, _piyo = "***Hello***", _fuga = True}]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment