Skip to content

Instantly share code, notes, and snippets.

@mkohlhaas
Created January 17, 2022 19:16
Show Gist options
  • Save mkohlhaas/6edfe4216e6c2cec91ff4942ebcc91a8 to your computer and use it in GitHub Desktop.
Save mkohlhaas/6edfe4216e6c2cec91ff4942ebcc91a8 to your computer and use it in GitHub Desktop.
module Ch19 where
import Prelude
import Data.Generic.Rep (class Generic)
import Data.Show.Generic (genericShow)
import Effect (Effect)
import Effect.Console (log)
-----------
-- Maybe --
-----------
-- Define data type
data Maybe a = Nothing | Just a
-- Create Show instance
derive instance genericMaybe :: Generic (Maybe a) _
instance showMaybe :: Show a => Show (Maybe a) where
show = genericShow
-- Create Functor instance
instance functorMaybe :: Functor Maybe where
map _ Nothing = Nothing
map f (Just a) = Just $ f a
-- Create Apply instance
instance applyMaybe :: Apply Maybe where
apply Nothing _ = Nothing
apply (Just f) x = f <$> x
-- Create Applicative instance
instance applicativeMaybe :: Applicative Maybe where
pure = Just
-- Create Bind instance
instance bindMaybe :: Bind Maybe where
bind Nothing _ = Nothing
bind (Just a) f = f a
-- Create Monad instance
instance monadMaybe :: Monad Maybe
------------
-- Either --
------------
-- Define data type
data Either a b = Left a | Right b
-- Create Show instance
derive instance genericEither :: Generic (Either a b) _
instance showEither :: (Show a, Show b) => Show (Either a b) where
show = genericShow
-- Derive Functor instance
derive instance functorEither :: Functor (Either a)
-- Create Apply instance
instance applyEither :: Apply (Either a) where
apply (Left x) _ = Left x
apply (Right f) y = f <$> y
-- Create Applicative instance
instance applicativeEither :: Applicative (Either a) where
pure = Right
-- Create Bind instance
instance bindEither :: Bind (Either a) where
bind (Left x) _ = Left x
bind (Right y) f = f y
-- Create Monad instance
instance monadEither :: Monad (Either a)
test :: Effect Unit
test = do
log "Ch. 19 Coding Monads."
log "-- Maybe Monad --"
log $ show $ Just (_ * 10) <*> Just 20
log $ show $ Just (_ * 10) <*> pure 20
log $ show $ Just 20 >>= pure <<< (_ * 10)
log $ show do
x <- Just 20
let y = x * 10
pure y
log $ show $ Just 20 >>= const Nothing >>= \y -> Just $ y + 42
log $ show do
_ <- Just 20
y <- Nothing
pure $ y + 42
log "-- Either Monad --"
log $ show $ Right (_ * 10) <*> (Right 20 :: Either Unit _)
log $ show $ Right (_ * 10) <*> (pure 20 :: Either Unit _)
log $ show $ (Right 20 :: Either Unit _) >>= pure <<< (_ * 10)
log $ show do
x <- Right 20 :: Either Unit _
let y = x * 10
pure y
log $ show $ Right 20 >>= const (Left "error") >>= \y -> Right $ y + 42
log $ show do
_ <- Right 20
y <- Left "error"
pure $ y + 42
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment