Functional programming
($) :: (a -> b) -> a -> b
($) f x = f x
> square $ 5 -- 25
> (^2) $ 5 -- 25
> (+1) $ 5 -- 6
inc :: [Int] -> [Int]
inc [] = []
inc (n:ns) = n+1 : inc ns
sqr :: [Int] -> [Int]
sqr [] = []
sqr (n:ns) = n^2 : sqr ns
map :: (a -> b) -> [a] -> [b]
map f [] = []
map f (x:xs) = f x : map f xs
inc = map (+1)
sqr = map (^2)
class Functor f where
fmap :: (a -> b) -> f a -> f b
instance Functor [] where
-- fmap :: (a -> b) -> [a] -> [b]
fmap = map
instance Functor Maybe where
-- fmap :: (a -> b) -> Maybe a -> Maybe b
fmap _ Nothing = Nothing
fmap g (Just x) = Just (g x)
fmap (+1) [3, 5, 8] -- [4, 6, 9]
fmap (^2) [] -- []
fmap (+1) Nothing -- Nothing
fmap (^2) (Just 3) -- Just 9
fmap not (Just False) -- Just True
fmap id == id
fmap (f . g) == fmap f . fmap g
fmap0 :: a -> f a
fmap1 :: (a -> b) -> f a -> f b
fmap2 :: (a -> b -> c) -> f a -> f b -> f c
fmap3 :: (a -> b -> c -> d) -> f a -> f b -> f c -> f d
...
> fmap2 (+) (Just 1) (Just 2)
($) :: (a -> b) -> a -> b
(<*>) :: f (a -> b) -> f a -> f b
class Functor f => Applicative f where
pure :: a -> f a
(<*>) :: f (a -> b) -> f a -> f b
instance Applicative Maybe where
-- pure :: a -> Maybe a
pure = Just
-- (<*>) :: Maybe (a -> b) -> Maybe a -> Maybe b
Nothing <*> _ = Nothing
(Just g) <*> mx = fmap g mx
> pure (+1) <*> Just 1 -- Just 2
> pure (+) <*> Just 1 <*> Just 2 -- Just 3
> pure (+) <*> Nothing <*> Just 2 -- Nothing
instance Applicative [] where
-- pure :: a -> [a]
pure x = [x]
-- (<*>) :: [a -> b] -> [a] -> [b]
gs <*> xs = [g x | g <- gs, x <- xs]
> pure (+1) <*> [1,2,3] -- [2,3,4]
> pure (+) <*> [1] <*> [2] -- [3]
> pure (*) <*> [1,2] <*> [3,4] -- [3,4,6,8]
5 `div` 0 -- *** Exception: divide by zero
safediv :: Int -> Int -> Maybe Int
safediv x y | y == 0 = Nothing
| otherwise = Just (x `div` y)
> 5 `safediv` 0
Nothing
> (5 `safediv` 2) + (9 `safediv` 3) -- error
> pure (+) <*> (5 `safediv` 2) <*> (9 `safediv` 3)
Just 5
> pure (+) <*> (5 `safediv` 0) <*> (9 `safediv` 3)
Nothing
quad :: Double -> Double -> Double -> [Double]
quad a b c | discr < 0 = []
| discr == 0 = [-(b/(2*a))]
| discr > 0 = [-((b + sqrt discr) / (2*a)),
-((b - sqrt discr) / (2*a))]
where discr = b^2 - 4*a*c
> (*10) <$> quad 1 2 1
[-10.0]
> (*10) <$> quad 5 25 30
[-30.0,-20.0]
> (*10) <$> quad 1 1 1
[]
pure id <*> v == v
pure (.) <*> u <*> v <*> w == u <*> (v <*> w)
pure f <*> pure x == pure (f x)
u <*> pure y == pure ($ y) <*> u
sequenceA :: Applicative f => [f a] -> f [a]
sequenceA [] = pure []
sequenceA (x:xs) = pure (:) <*> x <*> sequenceA xs
> sequenceA [Just 1, Just 2, Just 3] -- Just [1, 2, 3]
getChars :: Int -> IO String
getChars n = sequenceA (replicate n getChar)
data Expr = Val Int | Div Expr Expr
eval :: Expr -> Int
eval (Val n) = n
eval (Div x y) = eval x `div` eval y
> eval (Div (Val 1) (Val 0)) -- *** Exception: divide by zero
eval :: Expr -> Maybe Int
eval (Val n) = Just n
eval (Div x y) = case eval x of
Nothing -> Nothing
Just n -> case eval y of
Nothing -> Nothing
Just m -> safediv n m
eval :: Expr -> Maybe Int
eval (Val n) = pure n
eval (Div x y) = pure safediv <*> eval x <*> eval y
But safediv
is not pure!
(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b
mx >>= f = case mx of
Nothing -> Nothing
Just x -> f x
eval :: Expr -> Maybe Int
eval (Val n) = Just n
eval (Div x y) = eval x >>= \n ->
eval y >>= \m ->
safediv n m
class Applicative m => Monad m where
return :: a -> m a
(>>=) :: m a -> (a -> m b) -> m b
return = pure
data Tree a = Leaf a | Node (Tree a) (Tree a)
deriving Show
tree :: Tree Char
tree = Node (Node (Leaf 'a') (Leaf 'b')) (Leaf 'c')
> fst (rlabel tree 0)
Node (Node (Leaf 0) (Leaf 1)) (Leaf 2)
rlabel :: Tree a -> Int -> (Tree Int, Int)
rlabel (Leaf _) n = (Leaf n, n+1)
rlabel (Node l r) n = (Node l' r', n'')
where
(l',n') = rlabel l n
(r',n'') = rlabel r n'
type State = Int
type ST = State -> State
type ST a = State -> (a, State)
newtype ST a = S (State -> (a,State))
runState :: ST a -> State -> (a,State)
runState (S st) x = st x
instance Functor ST where
-- fmap :: (a -> b) -> ST a -> ST b
fmap g st = S (\s -> let (x,s') = runState st s
in (g x, s'))
instance Applicative ST where
-- pure :: a -> ST a
pure x = S (\s -> (x,s))
-- (<*>) :: ST (a -> b) -> ST a -> ST b
stf <*> stx = S (\s ->
let (f,s') = runState stf s
(x,s'') = runState stx s' in (f x, s''))
fresh :: ST Int
fresh = S (\n -> (n, n+1))
alabel :: Tree a -> ST (Tree Int)
alabel (Leaf _) = Leaf <$> fresh
alabel (Node l r) = Node <$> alabel l <*> alabel r
instance Monad ST where
-- (>>=) :: ST a -> (a -> ST b) -> ST b
st >>= f = S (\s -> let (x,s') = runState st s
in runState (f x) s')
mlabel :: Tree a -> ST (Tree Int)
mlabel (Leaf _) = do
n <- fresh
return (Leaf n)
mlabel (Node l r) = do
l' <- mlabel l
r' <- mlabel r
return (Node l' r')
return a >>= k == k a
m >>= return == m
m >>= (\x -> k x >>= h) == (m >>= k) >>= h
mapM :: Monad m => (a -> m b) -> [a] -> m [b]
mapM f [] = return []
mapM f (x:xs) = do
y <- f x
ys <- mapM f xs
return (y:ys)
conv :: Char -> Maybe Int
conv c | isDigit c = Just (digitToInt c)
| otherwise = Nothing
> mapM conv "1234"
Just [1,2,3,4]
> mapM conv "123a"
Nothing
readSingleFile :: FilePath -> IO [String]
readNamesFromFiles :: [FilePath] -> IO [String]
readNamesFromFiles files =
(fmap concat) $ mapM readSingleFile files