- Functional
- Functions as first class
- evaluating expressions instead of executing instructions
- Statically typed
- Compile time safety
- Pure
- Virtue
- Immutable
- Return same value for given args
- Side effect free
- Why:
- Parallelise
- Reason easily, debug etc
- Equational reasoning and refactoring
- Virtue
- Lazy
- Expressions not evaluated until required
- infinite data structures
- Enables compositional programming [?]
- Difficult to reason w.r.t. space time usage
- Typed
- Documentation
- Compile time safety
- Thinking
- Wholemeal programming
- Think big. Develop solution space.
- Solve general problem extract specific bits by transforming general program into more specialized ones.
- Abstraction
- DRY
data Thing = Shoe | Ship (deriving Show)
data FailableDouble = Failure | OK Double (deriving Show)
Failure
and OK
are data constructors. OK
takes a param
FailableDouble
is a type constructor.
checkFav :: Person -> String
checkFav (Person n _ SealingWax) = n ++ ", you're my kind of person!"
checkFav (Person n _ _) = n ++ ", your favorite thing is lame."
case
statement.
case "hello" of
[] -> 3
('H':s) -> 10
_ -> 1
data IntList = Empty | Cons Int IntList
- Map
- Filter
- Fold
data List t = E | C t (List t)
t is a type variable
mapList :: (a -> b) -> List a -> List b
With polymorphic functions caller gets to pick types.
e.g. head is a partial function. crashes with an empty list.
Use the safe
package.
Anonymous function or lambda abstraction
(\x -> x > 100)
Operator section: if ? is an operator, then (?y) is equivalent to the function \x -> x ? y
.
functional composition
function arrows associate to the right, that is, W -> X -> Y -> Z
is equivalent to W -> (X -> (Y -> Z))
Function application, in turn, is left-associative. That is, f 3 2
is really shorthand for (f 3) 2
comp :: (b -> c) -> (a -> b) -> a -> c
comp f g x = f (g x)
comp f g = f . g
The arguments should be ordered from from “least to greatest variation”,
Currying - Represent multi argument functions as one-argument functions.
Alternatively, can pass a single paarameter to a function as a tuple. uncurry
can be used to unwrap a tuple into args.
eta reduction \x -> abs x
to abs
eta abstraction is the reverse
foldr f z [a,b,c] == a `f` (b `f` (c `f` z))
foldl f z [a,b,c] == ((z `f` a) `f` b) `f` c
e.g.
Hangs:
take 20 $ foldl (\acc s -> acc ++ [s]) [] [1..]
Runs to compleltion:
take 20 $ foldr (:) [] [1..]
Stack overflow:
foldr max 0 [1..]
Reducible expression redex . (+)
is not redex. max
[?]
GHC has a lazy reduction strategy. Use foldl' . See seq
which reduces first param before going for the rest.
Caller gets to choose type. What are other examples ? [?]
We say that a function like f :: a -> a -> a is parametric in the type a . Parametricity corresponds to guarantees not restrictions
Examples of parameteric types:
a -> a (id) a -> b (map) a -> b -> a (const) [a] -> [a] (list functions) (b -> c) -> (a -> b) -> (a -> c) (.) (a -> a) -> a -> a ($)
(+) :: Num a => a -> a -> a
Num, Eq, Ord, and Show are type classes, and we say that (==), (<), and (+) are “type-class polymorphic”. Intuitively, type classes correspond to sets of types which have certain operations defined for them, and type class polymorphic functions work only for types which are instances of the type class(es) in question.
Type classes are different from java interfaces. Type class instances are declared separately from the type classes. In another module as well. [?]
Multiple-dispatch : not possible in java. Depends on types of both a, b below
class Blerg a b where
blerg :: a -> b -> Bool
type class constraints can be on the instance as well as functions.
instance (Listable a, Listable b) => Listable (a,b) where
toList (x,y) = toList x ++ toList y
[?] Language extensions FlexibleInstances etc
When using newtype
, you're restricted to just one constructor with one field.
For Java, params are evaluated regardless of whether the method actually consumes the passed variables. Side-effect is a primary reason why strict param evaluation is needed.
For lazy, evaluation is delayed as long as possible. Unevaluated expressions are called as thunk
A trigger for evaluation could for e.g. be a pattern match. A Maybe
need not be evaluated if the method doesnt care of the shape of it. However if we pattern match to Nothing
or Just
then we need to know. The thunks are evaluated just enough.
GHC uses graph reduction . Expression represented as graph so that same expressions can be pointers and evaluated only once.
if' :: Bool -> a -> a -> a
if' True x _ = x
if' False _ y = y
(&&) :: Bool -> Bool -> Bool
True && x = x
False && _ = False
- Infinite data structures are effectively just thunks.
- With wholemeal programming, only those thunks that are needed are consumed.
- Can define our own control structures
- Dynamic programming [?]
exprTFold :: (Integer -> b) -> (b -> b -> b) -> (b -> b -> b) -> ExprT -> b
exprTFold f _ _ (Lit i) = f i
exprTFold f g h (Add e1 e2) = g (exprTFold f g h e1) (exprTFold f g h e2)
exprTFold f g h (Mul e1 e2) = h (exprTFold f g h e1) (exprTFold f g h e2)
fold-map fusion lets you replace such a definition by one that only involves foldr:
foldr op u . map f = foldr (op . f) u
Folds take an argument for each data constructor. Encodes it to a value of returned type. implementation deals with the recursive aspects.
Semigroups define a single <>
(mappend) operation which lets you combine two values of the type.
Monoids have an additional method mempty which defines the identity
mconcat
is available as a fold implementation. foldr <> mempty
There might be multiple Monoid implementations which might be possible. In that case its better to create a newtype
which instead provides the implementation of the monoid. E.g. Data.Semigroup.Sum
Monoid Laws
mempty `mappend` x = x
x `mappend` mempty = x
(x `mappend` y) `mappend` z = x `mappend` (y `mappend` z)
Monoids in Haskell Monoids tour Monoids and finger trees Finger tree example
class Functor f where
fmap :: (a -> b) -> f a -> f b
Defines a single fmap method which lets you transform the value inside a computation context. Defined for a type constructor of kind * -> *
map is fmap on lists.
Functor for a function is function composition.
instance Functor ((->) r) where
fmap = (.)
fmap :: (a -> b) -> (f a -> f b)
If we pass a single function to fmap
we get a function which accepts a functor and returns a different functor. Called lifting a function.
- Mapping
id
gives the same functor backfmap id = id
- Mapping a function composition over a functor is the same as mapping 1st function over a functor and then the second .
fmap (f . g) = fmap f . fmap g
Fmap doesn't let us map a function inside a functor with another functor.
class (Functor f) => Applicative f where
pure :: a -> f a
(<*>) :: f (a -> b) -> f a -> f b
Applicative takes a functor over a function and another functor and gives a functor with function applied over the value.
pure f <*> x <*> y <*> ... a
lets us wrap functions in a functor and apply it on values which are in functor contexts.
pure f <*> x
is the same as fmap f x
. which is equivalent to f <$> x
which is also provided by the Applicative module.
Examples:
instance Applicative [] where
pure x = [x]
fs <*> xs = [f x | f <- fs, x <- xs]
instance Applicative IO where
pure = return
a <*> b = do
f <- a
x <- b
return (f x)
liftA2 :: (Applicative f) => (a -> b -> c) -> f a -> f b -> f c
(>>=) :: (Monad m) => m a -> (a -> m b) -> m b
class Monad m where
return :: a -> m a
(>>=) :: m a -> (a -> m b) -> m b
(>>) :: m a -> m b -> m b
x >> y = x >>= \_ -> y
fail :: String -> m a
fail msg = error msg
Examples:
instance Monad Maybe where
return x = Just x
Nothing >>= f = Nothing
Just x >>= f = f x
fail _ = Nothing
instance Monad [] where
return x = [x]
xs >>= f = concat (map f xs)
fail _ = []
return 1 :: Maybe Int
Just 1
return 1 >>= \x -> Just (x + 1)
Just 2
return 1 >>= \x -> Just (x + 1) >> Nothing
Nothing
Using a do block:
blah = do
x <- Just 1
Just (x + 1)
Monad laws
return x >>= f -- same as f x
m >>= return -- same as m
(m >>= f) >>= g -- same as m >>= (\x -> f x >>= g)
(>>) :: IO a -> IO b -> IO b
also known as and then
Bind operator
(>>=) :: IO a -> (a -> IO b) -> IO b