Compare commits
2 commits
b68b19572f
...
38185725db
Author | SHA1 | Date | |
---|---|---|---|
38185725db | |||
5b6f60b381 |
3 changed files with 2 additions and 158 deletions
2
.gitignore
vendored
Normal file
2
.gitignore
vendored
Normal file
|
@ -0,0 +1,2 @@
|
|||
.direnv
|
||||
dist-newstyle
|
|
@ -1,48 +0,0 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE InstanceSigs #-}
|
||||
{-# OPTIONS_GHC -Wno-unused-top-binds #-}
|
||||
|
||||
module ApplicativeChapter () where
|
||||
|
||||
import Data.Function (const)
|
||||
import GHC.Base ( id, Functor(..) )
|
||||
import Data.Maybe (Maybe(..))
|
||||
import Data.Function (($))
|
||||
import Data.List (zipWith)
|
||||
|
||||
liftA2 :: ApplicativeChapter.Applicative f => (a -> b -> c) -> f a -> f b -> f c
|
||||
liftA2 f x = (<*>) (fmap f x)
|
||||
|
||||
class Functor f => Applicative f where
|
||||
pure :: a -> f a
|
||||
infixl 4 <*>, *>
|
||||
(<*>) :: f (a -> b) -> f a -> f b
|
||||
|
||||
(*>) :: f a -> f b -> f b
|
||||
a1 *> a2 = (id <$ a1) <*> a2
|
||||
|
||||
(<*) :: f a -> f b -> f a
|
||||
(<*) = liftA2 const
|
||||
|
||||
-- ??
|
||||
|
||||
-- Maybe is Applicative
|
||||
|
||||
instance Applicative Maybe where
|
||||
(<*>) :: Maybe (a -> b) -> Maybe a -> Maybe b
|
||||
(<*>) Nothing _ = Nothing
|
||||
(<*>) (Just f) x = fmap f x
|
||||
|
||||
pure :: a -> Maybe a
|
||||
pure = Just
|
||||
|
||||
-- List can be Applicative in 2 different ways
|
||||
|
||||
newtype ZipList a = ZipList { getZipList :: [a] }
|
||||
|
||||
instance Applicative ZipList where
|
||||
pure :: a -> ZipList a
|
||||
pure a = ZipList [a]
|
||||
|
||||
(<*>) :: ZipList (a -> b) -> ZipList a -> ZipList b
|
||||
(ZipList gs) <*> (ZipList xs) = ZipList (zipWith ($) gs xs)
|
|
@ -1,110 +0,0 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{-# LANGUAGE InstanceSigs #-}
|
||||
{-# OPTIONS_GHC -Wno-unused-top-binds #-}
|
||||
|
||||
module FunctorChapter () where
|
||||
|
||||
import Data.Either (Either(..))
|
||||
import Data.Function (($))
|
||||
import Data.Int
|
||||
import Data.Maybe ( Maybe, Maybe(..) )
|
||||
|
||||
const :: a -> b -> a
|
||||
const a _ = a
|
||||
|
||||
class Functor f where
|
||||
fmap :: (a -> b) -> f a -> f b
|
||||
(<$) :: a -> f b -> f a
|
||||
{-# MINIMAL fmap #-}
|
||||
(<$) a = fmap (const a)
|
||||
|
||||
-- 1
|
||||
instance Functor (Either e) where
|
||||
fmap :: (a -> b) -> Either e a -> Either e b
|
||||
fmap f (Right ex) = Right $ f ex
|
||||
fmap _ (Left x) = Left x
|
||||
|
||||
(.) :: (b -> c) -> (a -> b) -> (a -> c)
|
||||
(.) fbc fab x = fbc (fab x)
|
||||
|
||||
-- 1bis
|
||||
instance Functor ((->) e) where
|
||||
fmap :: (a -> b) -> (e -> a) -> (e -> b)
|
||||
fmap fab fea = fab . fea
|
||||
|
||||
-- 2
|
||||
instance Functor ((,) e) where
|
||||
fmap :: (a -> b) -> (e, a) -> (e, b)
|
||||
fmap f (e, bx) = (e, f bx)
|
||||
|
||||
data Pair a = Pair a a
|
||||
|
||||
instance Functor Pair where
|
||||
fmap :: (a -> b) -> Pair a -> Pair b
|
||||
fmap f (Pair ax ay) = Pair (f ax) (f ay)
|
||||
|
||||
-- Differences: Pair is a concrete type while ((,) e) isn't
|
||||
-- Moreover both the wrapped values in Pair have the same type
|
||||
-- and we have to wrap both if we want to return a Pair b
|
||||
-- Instead for ((,) e) we don't know anything about e so we
|
||||
-- cannot apply any function to it
|
||||
|
||||
data ITree a = Leaf (Int -> a)
|
||||
| Node [ITree a]
|
||||
|
||||
-- 3
|
||||
|
||||
instance Functor [] where
|
||||
fmap :: (a -> b) -> [] a -> [] b
|
||||
fmap fab (x:xs) = fab x : fmap fab xs
|
||||
fmap _ [] = []
|
||||
|
||||
instance Functor ITree where
|
||||
fmap :: (a -> b) -> ITree a -> ITree b
|
||||
fmap fab (Leaf fia) = Leaf $ fab . fia
|
||||
fmap fab (Node ts) = Node (fmap (fmap fab) ts)
|
||||
|
||||
-- 4 ???
|
||||
-- data Foo a = Foo
|
||||
|
||||
-- instance Functor Foo where
|
||||
-- fmap :: (b -> c) -> Foo b -> Foo c
|
||||
-- fmap fbc (Foo) = Foo
|
||||
|
||||
-- 5
|
||||
newtype ListMaybe a = ListMaybe [Maybe a]
|
||||
|
||||
instance Functor Maybe where
|
||||
fmap :: (a -> b) -> Maybe a -> Maybe b
|
||||
fmap _ Nothing = Nothing
|
||||
fmap fab (Just a) = Just $ fab a
|
||||
|
||||
instance Functor ListMaybe where
|
||||
fmap :: (a -> b) -> ListMaybe a -> ListMaybe b
|
||||
fmap fab (ListMaybe ms) = ListMaybe (fmap (fmap fab) ms)
|
||||
|
||||
-- 1
|
||||
|
||||
data Maybe' a = Just' a | Nothing'
|
||||
|
||||
instance Functor Maybe' where
|
||||
fmap :: (a -> b) -> Maybe' a -> Maybe' b
|
||||
fmap _ _ = Nothing'
|
||||
|
||||
-- fmap id = \x -> Nothing' != id
|
||||
-- fmap f . fmap g = \x -> Nothing' = fmap (f . g)
|
||||
|
||||
-- 2
|
||||
-- (evilFmap id) [1] = [1 1]
|
||||
-- then evilFmap id != id
|
||||
|
||||
-- fmap id x:xs =
|
||||
-- (id x):(id x):(fmap id xs) = # function application
|
||||
-- x:x:(fmap id xs) = # associativity
|
||||
-- x:( x:(fmap id xs) ) = # definition (list, well defined Functor []): fmap id xs = x: fmap id xs
|
||||
-- x:( fmap id (x:xs) ) =
|
||||
-- x:( id (x:xs) ) = # identity law substitution (fmap id = id)
|
||||
-- (x:) . (id $ (:) x xs) = # rewrite using composition (.)
|
||||
-- (x:) . id . (x:) xs = # rewrite using composition (.)
|
||||
-- (x:) . id . (x:) = # eta reduction
|
||||
-- != id
|
Loading…
Add table
Add a link
Reference in a new issue