Skip to content

Instantly share code, notes, and snippets.

@wuct
Created October 24, 2017 16:53
Show Gist options
  • Save wuct/ee09d118ecf6ef499501cc10f99c1a24 to your computer and use it in GitHub Desktop.
Save wuct/ee09d118ecf6ef499501cc10f99c1a24 to your computer and use it in GitHub Desktop.
This is a Reader Monad implementation without introduction Monad Transformer
module Main where
import Prelude
import Control.Monad.Reader.Class
import Control.Monad.Eff.Console (logShow)
import TryPureScript
newtype Reader r a = Reader (r -> a)
runReader :: forall r a. Reader r a -> r -> a
runReader (Reader f) = f
instance functorReader :: Functor (Reader r) where
map g (Reader f) = Reader (g <<< f)
instance applyReader :: Apply (Reader r) where
apply (Reader g) (Reader f) = Reader \r -> (g r) (f r)
instance applicativeReader :: Applicative (Reader r) where
pure a = Reader \_ -> a
instance bindReader :: Bind (Reader r) where
bind (Reader f) h = Reader \r -> runReader (h (f r)) r
instance monadReader :: Monad (Reader r)
instance monadAskReader :: MonadAsk r (Reader r) where
ask = Reader \r -> r
main = do
logShow $ flip runReader "@" $ (\r -> r <> "1") <$> (Reader \r -> r <>"a")
logShow $ flip runReader "@" $ (Reader \r r2 -> r <> r2 <> "2") <*> (Reader \r -> r <>"b")
logShow $ flip runReader "@" $ do
a <- (Reader \r -> r <> "c")
b <- (Reader \r -> r <> "4")
pure (a <> b)
logShow $ flip runReader "@" $ do
r <- ask
pure (r <> "d")
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment