about summary refs log tree commit diff
path: root/users/wpcarro/scratch/haskell-programming-from-first-principles/monad-transformers.hs
blob: 3a780fc16c82769fa690c0834dd893258ef3bf48 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
module MonadTransformersScratch where

import Control.Monad
import qualified Control.Monad.Trans.Maybe as M
import qualified Control.Monad.Trans.Reader as R
import qualified Control.Monad.Trans.State as S
import Data.Function ((&))
--------------------------------------------------------------------------------

newtype MaybeT m a =
  MaybeT { runMaybeT :: m (Maybe a) }

instance (Functor f) => Functor (MaybeT f) where
  fmap f (MaybeT run) =
    MaybeT $ (fmap . fmap) f run

instance (Applicative m) => Applicative (MaybeT m) where
  pure x = x & pure & pure & MaybeT
  _ <*> _ = undefined

instance (Monad m) => Monad (MaybeT m) where
  return = pure
  (MaybeT ma) >>= f = MaybeT $ do
    maybeX <- ma
    case maybeX of
      Nothing -> pure Nothing
      Just x -> x & f & runMaybeT

--------------------------------------------------------------------------------

newtype EitherT e m a =
  EitherT { runEitherT :: m (Either e a) }

instance (Functor m) => Functor (EitherT e m) where
  fmap f (EitherT mEither) =
    EitherT $ (fmap . fmap) f mEither

instance (Applicative m) => Applicative (EitherT e m) where
  pure x = EitherT $ (pure . pure) x
  EitherT mEitherF <*> EitherT mEitherX =
    EitherT $ (fmap (<*>) mEitherF) <*> mEitherX

instance (Monad m) => Monad (EitherT e m) where
  return = pure
  EitherT mEitherX >>= f = EitherT $ do
    eitherX <- mEitherX
    case eitherX of
      Left x -> pure $ Left x
      Right x -> runEitherT $ f x

swapEither :: Either l r -> Either r l
swapEither (Left x) = Right x
swapEither (Right x) = Left x

swapEitherT :: (Functor m) => EitherT e m a -> EitherT a m e
swapEitherT (EitherT mEitherX) =
  EitherT $ fmap swapEither mEitherX

eitherT :: Monad m => (a -> m c) -> (b -> m c) -> EitherT a m b -> m c
eitherT aToMC bToMC (EitherT mEitherX) = do
  eitherX <- mEitherX
  case eitherX of
    Left x -> aToMC x
    Right x -> bToMC x

--------------------------------------------------------------------------------

newtype ReaderT r m a = ReaderT { runReaderT :: r -> m a }

instance (Functor m) => Functor (ReaderT r m) where
  fmap f (ReaderT rma) =
    ReaderT $ (fmap . fmap) f rma

instance (Applicative m) => Applicative (ReaderT r m) where
  pure x = x & pure & pure & ReaderT
  ReaderT f <*> ReaderT x = ReaderT $ fmap (<*>) f <*> x

-- instance (Monad m) => Monad (ReaderT r m) where
--   return = pure
--   ReaderT rma >>= f =
--     ReaderT $ \r -> do
--       a <- rma r
--       runReaderT (f a) r
-- --------------------------------------------------------------------------------

rDec :: Num a => R.Reader a a
rDec = R.ReaderT $ \x -> pure $ x + 1

rShow :: Show a => R.Reader a String
rShow = R.ReaderT $ \x -> pure $ show x

rPrintAndInc :: (Num a, Show a) => R.ReaderT a IO a
rPrintAndInc = R.ReaderT $ \x ->
  putStrLn ("Hi: " ++ show x) >> pure (x + 1)

sPrintIncAccum :: (Num a, Show a) => S.StateT a IO String
sPrintIncAccum = S.StateT $ \x -> do
  putStrLn ("Hi: " ++ show x)
  pure (show x, x + 1)

--------------------------------------------------------------------------------

isValid :: String -> Bool
isValid v = '!' `elem` v

maybeExcite :: M.MaybeT IO String
maybeExcite = M.MaybeT $ do
  x <- getLine
  putStrLn ""
  case isValid x of
    False -> pure Nothing
    True -> pure $ Just x

doExcite :: IO ()
doExcite = do
  putStr "Say something *exciting*: "
  excite <- M.runMaybeT maybeExcite
  case excite of
    Nothing -> putStrLn "Gonna need some more excitement..."
    Just x  -> putStrLn "Now THAT'S exciting...nice!"

--------------------------------------------------------------------------------

data Participant
  = Man
  | Machine
  deriving (Show, Eq)

newtype Hand = Hand (Integer, Integer) deriving (Show, Eq)

newtype Score = Score (Integer, Integer) deriving (Show, Eq)

getLineLn :: String -> IO String
getLineLn prompt = do
  putStr prompt
  x <- getLine
  putStrLn ""
  pure x

promptGuess :: IO Hand
promptGuess = do
  fingers <- getLineLn "How many fingers (0-5): "
  guess <- getLineLn "Guess: "
  pure $ Hand (read guess, read fingers)

aiGuess :: IO Hand
aiGuess = pure $ Hand (2, 3)

whoWon :: Hand -> Hand -> Maybe Participant
whoWon (Hand (guessA, fingersA)) (Hand (guessB, fingersB))
  | guessA == guessB && guessA == (fingersA + fingersB) = Nothing
  | guessA == (fingersA + fingersB) = Just Man
  | guessB == (fingersA + fingersB) = Just Machine
  | otherwise = Nothing

initScore :: Score
initScore = Score (0, 0)

printScore :: Score -> IO ()
printScore (Score (man, machine)) =
  putStrLn $ "Man: " ++ show man ++ " Machine: " ++ show machine

startMorra :: S.StateT Score IO ()
startMorra = S.StateT $ \(Score (man, machine)) -> do
  Hand (guessA, fingersA) <- promptGuess
  Hand (guessB, fingersB) <- aiGuess
  putStrLn $ "P: " ++ show fingersA ++ "," ++ show guessA
  putStrLn $ "C: " ++ show fingersB ++ "," ++ show guessB
  case whoWon (Hand (guessA, fingersA)) (Hand (guessB, fingersB)) of
    Nothing -> do
      putStrLn "Nobody won..."
      printScore (Score (man, machine))
      pure ((), Score (man, machine))
    Just Man -> do
      putStrLn "Man won!"
      printScore (Score (man + 1, machine))
      pure ((), Score (man + 1, machine))
    Just Machine -> do
      putStrLn "Oh no... Machine won..."
      printScore (Score (man, machine + 1))
      pure ((), Score (man, machine + 1))

playMorra = S.runStateT (forever startMorra) initScore