- Date created: April-2021
- Last updated: Nov-2021
Based on:
- NPTEL course Functional programming in Haskell by Madhav Mukund and S. P. Suresh from Chennai Mathematical Institute, Chennai (YouTube playlist)
- Functional programming course ⁹ ¹⁰ by Piyush Kurur from IIT Palakkad
Intro
Functions
Transforms inputs to outputs.
Program
Rules to produce output from input.
Computation
Process of applying the rules specified by the program.
Building up programs
We got to start from somewhere => built-in functions.
Use these built-in stuff to build more complex stuff.
Basic operation is function composition.
Function composition
In these examples, assume that inputs are whole numbers.
Example: Applying same function twice
succ n = n + 1 = succ (succ n) plusTwo n
Example: Composing with two different functions
= succ (plusTwo n) plusThree n
Defining plus
An inductive/recursive function definition.
- A base case is specified.
- Then we define the value for larger arguments in terms of the value for smaller arguments.
0 = n
plus n = succ (plus n m-1) plus n m
Defining mult
0 = 0
mult n = plus n (mult n m-1) mult n m
Data types
Haskell is strongly typed.
A type is just a set of permissible values.
The real successor function mean the next whole number.
ie,
succ 2.6
is3
succ 2.3
is3
succ 2
is3
Representation of integers and real numbers are different in computers. So we use different data types.
Any function that we define in Haskell must have a well defined type.
The constructor names of haskell algebraic data types must start with an upper case letter. Otherwise, you'll be an error saying: Not a data constructor
Type of a function
A function that accepts input of type A
and outputs a value of type B
has type A → B
.
f: S → T
- Domain: S
- Codomain: T
- Range ⊆ Codomain
Collections
- Collections of values of a given type.
- Often convenient to deal with this subset of the collection's type.
- All values of a collection are of the same type.
- Examples:
- a list of integers
- a sequence of strings
- pairs of numbers (coordinates of a point)
id
: Identity function
> id 3
λ3
> id "Hello"
λ"Hello"
Haskell
Essentially a programming language for describing functions.
A function description consists of two parts:
- type of inputs and outputs
- rules for computing outputs from inputs
Example Haskell function description
The ::
indicates that it is a type definition.
sqr :: Int -> Int -- Type definition
= n * n -- Computation rule sqr n
Basic types in Haskell
Convention: All type names start with a capital letter.
- Integers (
Int
)- Operations:
- +, -, \*, /
- / gives a float. Not int.
- Eg: 5 / 3 => 1.66666
- Functions:
- div, mod
- div gives Int itself.
- Eg: div 5 3 => 1
- Operations:
- Float (
Float
): real numbers - Characters (
Char
)- Enclosed in single quotes
- Boolean (
Bool
):True
,False
Operators
Boolean operators
- &&
- || (actually, the inclusive or. True if one or more input is true).
not
: a function that takes a single argument
Relational operators
==
/=
(not equal to)<
<=
>
>=
An xor function
xor :: Bool -> Bool -> Bool
= (a && (not b)) ||
xor a b not a) && b) -- Only Boolean expressions are involved here. ((
'inorder' function
Check if three integers are in ascending order.
inorder :: Int -> Int -> Int -> Bool
= (x <= y) && (y <= z) inorder x y z
Pattern matching
Let's rewrite our xor function example with pattern matching.
xor :: Bool -> Bool -> Bool
True False = True
xor False True = True
xor = False xor a b
The definition with the first matching pattern would be used. Top to bottom.
If argument in function definition is:
- a constant: the same constant must appear in the function call.
- a variable: any value can appear in the function call.
An 'or' function
or :: Bool -> Bool -> Bool
or True x = True
or x True = True
or x y = False
A 'different' definition of 'and' function
and :: Bool -> Bool -> Bool
and True b = b
and False b = False
Wild cards
We could also write the above 'and' function definition using wild cards.
A special notation.
Essentially don't cares.
The value is not captured.
and :: Bool -> Bool -> Bool
and True b = b
and False _ = False
Similarly for the 'or' function,
or :: Bool -> Bool -> Bool
or True _ = True
or _ True = True
or _ _ = False
Recursive definitions
- Base case
- Inductive step (value for larger values in terms of smaller values)
A function for factorial
fact :: Int -> Int 0 = 1 fact = n * (fact (n - 1)) -- Note the usage of parenthesis here. fact n -- Because fact n - 1 would have been read as -- (fact n) - 1, resulting in infinite recursion.
But here the computation will not terminate if argument is a negative integer.
We can fix this using conditional definitions.
Conditional definitions
fact :: Int -> Int
fact :: Int -> Int
0 = 1 -- this is pattern match
fact
fact n| n < 0 = fact (-n) -- just to make this more complete
| n >= 0 = n * (fact (n - 1))
(Here, there are 'two' definitions.
The vertical bar signifies options aka guards.
'Guarded' by a conditional expressions.
Guards are tested from top to bottom.
Indentation matters here.
Guards can overlap
Since they are evaluated from top to bottom.
fact :: Int -> Int fact n| n < 0 = fact (-n) -- just to make this more complete | n > 1 = n * (fact (n - 1)) | n >= 0 = 1
But guards need not cover all cases. In such a case, we may get pattern match failure errors.
otherwise
to cover remaining casesfact :: Int -> Int fact n| n == 0 = 1 | n > 0 = n * (fact (n-1)) | otherwise = (fact (-n))
- Catches all conditions. As if always True.
- Its use ensures, for a given argument value, at least one condition would match.
- Helps us avoid pattern match failure errors.
ghci
Colon (:
) commands like :load
perform internal actions of ghci. Other commands are Haskell.
Arity of a function
Number of arguments that the function accepts.
Currying
- Named after Haskell Curry.
- 'All functions take just one argument'.
- A sequence of functions get created instead of a single multiple argument function.
- Each argument transforms the function by internalizing that argument inside the function. A new function is created. That argument is hard-wired in this new function.
Some examples
Euclid's gcd algorithm
gcd :: Int -> Int -> Int
gcd a 0 = a
gcd a b
| a >= b = gcd b (mod a b)
| otherwise = gcd b a -- call it in the right order
Largest divisor of a number
Other than the number itself.
largestdiv :: Int -> Int
= divsearch n (n-1)
largestdiv n
-- auxiliary function
divsearch :: Int -> Int -> Int
divsearch m n| (mod m i) == 0 = i
| otherwise = divsearch m (i-1)
Here we used an auxiliary function.
Integer logarithm
-- IGNORE THIS BLOCK
log :: Int -> Int -> Fractional
log k n = multsearch k n 0
multsearch :: Int -> Int -> Int -> Fractional
multsearch k n i| k ** i == n = i
| otherwise = multsearch k n (i+1)
-- IGNORE THIS BLOCK
-- logk n = y mean k^y = n
log :: Int -> Int -> Fractional
log k n = divsearch k n 0
divsearch :: Int -> Int -> Int -> Fractional
divsearch k n| n / k == 1 = k
|
-- intlog
intlog :: Int -> Int -> Int
1 = 0
intlog k
intlog k n| n >= k = 1 + intlog k (div n k)
| otherwise = 0
Reverse digits of an integer
-- intlog
intlog :: Int -> Int -> Int
1 = 0
intlog k
intlog k n| n >= k = 1 + intlog k (div n k)
| otherwise = 0
-- myversion. Probably missed something.
intreverse :: Int -> Int
intreverse n| n > 0 = (mod n 10) * (10 ^ (intlog 10 n)) + intreverse (div n 10)
| otherwise = 0
-- Madhav sir's version
intlog :: Int -> Int -> Int
1 = 0
intlog k
intlog k n| n >= k = 1 + intlog k (div n k)
| otherwise = 0
power :: Int -> Int -> Int
0 = 1
power n = n * (power n (k-1))
power n k
intreverse :: Int -> Int
intreverse n| n < 10 = n
| otherwise = (intreverse (div n 10)) +
mod n 10) * (power 10 (intlog 10 n)) (
Lists
The main data structure that Haskell uses to 'store' or collect values. All elements of a list have the same type.
1,2,3,11] :: [Int]
[True,False,True] :: [Bool] [
The type []
denotes empty list, no type name there.
:
is right associative.
Head and tail of a list
head (x:xs) -- x
tail (x:xs) -- xs
Types:
head :: [a] -> a
tail :: [a] -> [a]
Both head
and tail
are undefined when the argument is an empty list.
Functions on list
Induction helps.
Example: Find length of a list
listLength :: [a] -> Int = 0 listLength [] = 1 + listLength (tail x) listLength x
Or with
listLength :: [a] -> Int = 0 listLength [] :xs) = 1 + listLength xs listLength (x
We need the parenthesis in
listLength (x:xs)
as function application (:
here) has a higher precedence.Example: Sum of values in a list
mySum :: [Int] -> Int = 0 mySum [] :xs) = x + mySum xs mySum (x
List indexing
- Indexing starts from 0.
- Can be indexed like list[j].
- list[j] takes time proportional to the index j.
- Needs to apply the
:
function j times. - Not really random access unlike in the case of arrays.
- Lists are internally represented in a 'canonical way', using the
:
function to build them up.
List notation
- [m..n] gives [m, m+1, m+2, …, n-1, n]
- Inclusive of both limits.
- Empty list if n<m.
- Eg: [1..4] -> [1,2,3,4]
With step value
'Lead by example'. :-)
Like,
1,3,..8] -- [1,3,5,7] [8.2,8.1..7.8] -- [8.2,8.1,8.0,7.9,7.800000000000001] [5,3..(-1)] -- [5,3,1,-1]. Note the need for parenthesis here or haskell [-- will complain saying it doesn't know a variable -- named '..-'.
Example: Append an element to the right of a list
appendr :: Int -> [Int] -> [Int] = [x] appendr x [] :ys) = y : (appendr x ys) appendr x (y
Example: Merge two lists
mrge :: [a] -> [a] -> [a] = l mrge [] l :xs) l = x:(mrge xs l) mrge (x
Appending lists
Via the ++
function.
1,2] ++ [3,4] -- [1,2,3,4] [
I guess ++
would implemented as something like
applists :: [a] -> [a] -> [a]
= y
applists [] y :xs) y = x : (applists xs y)
applists (x3] f [] [
Example: Reverse a list
revlist :: [a] -> [a] = [] revlist [] :xs) = (revlist xs) ++ [x] revlist (x
Example: Check if an integer list is sorted in ascending order
ascending :: [Int] -> Bool = True ascending [] = True ascending [x] :y:ys) = (x <= y) && ascending (y:ys) ascending (x
Example: Check if an integer list is alternatively increase and decrease
My attempt (works only when the list starts uphill):
alternating :: [Int] -> Bool = helper x True alternating x helper :: [Int] -> Bool -> Bool = True helper [] up = True helper [x] up :y:ys) up = ((up && x<y) || (not up && x>y)) && (helper (y:ys) (not up)) helper (x
As in lecture (a mutually recursive version):
alternating :: [Int] -> Bool = (downup l) || (updown l) alternating l downup :: [Int] -> Bool = True downup [] = True downup [x] :y:ys) = (x < y) && (updown (y:ys)) downup (x updown :: [Int] -> Bool = True updown [] = True updown [x] :y:ys) = (x > y) && (downup (y:ys)) updown (x
Some built-in list functions
init
Returns all except the last element.
last :: [a] -> [a] init [1,2,3] -- [1,2]
last
Returns the last element.
last :: [a] -> a last [1,2,3] -- 1
take
take :: Int [a] -> [a] take 3 [1,2,3,4,5] -- [1,2,3]
Splits the list at position (not index) n and takes the first part.
drop
drop :: Int [a] -> [a] drop 3 [1,2,3,4,5] -- [4,5]
Splits the list at position (not index) n and drops the first part.
This means that for any list lst,
= (take n lst) ++ (drop n lst) lst
Other functions
sum
length
reverse
Example: a custom take function
mytake :: Int -> [a] -> [a] = [] mytake _ [] :xs) mytake n (x| n == 0 = [] | n > 0 = x : (mytake (n-1) xs) | otherwise = []
Example: a custom drop function
mydrop :: Int -> [a] -> [a] = [] mydrop _ [] :xs) mydrop n (x| n <= 0 = x:xs | otherwise = mydrop (n-1) xs
Characters and strings
ord
and chr
from Data.Char
.
Example: Capitalize a letter
import Data.Char
capitalize :: Char -> Char
capitalize ch| ('a' <= ch && ch <= 'z') =
chr (ord ch - ((ord 'a') - (ord 'A')))
| otherwise = ch
Example: Check if a character occurs in a string
My attempt (seems to work):
occurs :: Char -> String -> Bool
"" = False
occurs _ :xs) = (ch == x) || (occurs ch xs) occurs ch (x
Function in lecture:
occurs :: Char -> String -> Bool
"" = False
occurs _ :xs)
occurs ch (x| ch == x = True
| otherwise = occurs ch xs
Example: Convert a function to uppercase
import Data.Char
toupper :: String -> String
"" = ""
toupper :xs) = (capitalize x) : (toupper xs)
toupper (x
capitalize :: Char -> Char
capitalize ch| (ch>='a' && ch<='z') = chr ((ord ch) - ((ord 'a') - (ord 'A')))
| otherwise = ch
Example: Find first index of a char in a string
My attempt (seems to work):
-- Indexing starts from 0
find :: Char -> String -> Int
= helper ch str 0
find ch str
helper :: Char -> String -> Int -> Int
"" _ = -1
helper _ :xs) idx
helper ch (x| x == ch = idx
| otherwise = helper ch xs (idx+1)
Version in lecture:
find :: Char -> String -> Int
"" = -1
find _ :xs)
find ch (x| ch == x = 0
| otherwise = 1 + (find ch xs)
Example: Count number of words in string
My attempt (seems to work but considers only spaces):
countwords :: String -> Int
"" = 0
countwords :xs)
countwords (x| xs == [] = 1
| x == ' ' = 1 + (countwords xs)
| otherwise = countwords xs
Lecture version:
countwords :: String -> Int
whitespace :: Char -> Bool
whitespace x| x == ' ' = True
| x == '\t' = True
| x == '\n' = True
| otherwise = False
Tuples
Collection of values of different types.
3, -12) :: (Int, Int)
(
13, True, 42) :: (Int, Bool, Int)
(
1,2], 7) :: ([Int], Int) ([
case
expressions
Allows us to do pattern matching even when not inside a function.
Syntax:
case <scrutinee-expr> of
-> value1
choice1 -> value2
choice2 ...
-> valuen choicen
Kind
A kind is a type of types.
The 'basic' kind (ie, monotypes) is star written as *
.
Eg:
Bool
,Integer
, etc have kind*
.- <--Type constructors like-->
Maybe
is of kind* -> *
.
Fun fact: We can use :k
or :kind
in ghci to get the kind of a type.
> :k Maybe
λMaybe :: * -> *
> :k Monad
λMonad :: (* -> *) -> Constraint
-- What is 'Constraint'?
Reference: link
Type classes
Type classes are used when we find a common functionality that is repeated across multiple types.
Reference: CIS194 course, UPENN
For example, in
(==) :: Eq a => a -> a -> Bool
the part to the left of the =>
are type constraints (the one to its right is, of course, the type).
Also checkout: l8
Defining a type class
A type class definition consists of a set of functions with just their types. ie, without a definition.
Example,
class Eq a where
(==) :: a -> a -> Bool
(/=) :: a -> a -> Bool
Then we can make an instance of this type class
instance Eq Integer
Functor
Reference: learnyouahaskell.com
- Things that can be mapped over.
- Has
fmap
function. <$> :: Functor f => (a -> b) -> f a -> f b
- Allows applying a pure function inside a parametric type like list.
- List is a type accepting one parameter, the type of the list.
- Values are wrapped in a context.
- Eg:
Maybe
class Functor f where
fmap :: (a -> b) -> f a -> f b
<$>
function
<$>
is just the infix version offmap
.- A shorthand for
fmap
f <$> x
≡fmap f x
- ~<$>
- (Functor f) => (a -> b) -> f a -> f b~
fmap
on functions
Reference: https://adit.io/posts/2013-04-17-functors,_applicatives,_and_monads_in_pictures.html
instance Functor ((->) a) where
fmap f g = f . g
ie, fmap
on functions is just function composition.
> let foo = fmap (+3) (+2)
λ> foo 3
λ8
-- which is same as
> ((+3) <$> (+2)) 3
λ8
'Laws' of functors
Reference: l3
fmap id = id
fmap (f . g) = (fmap f) . (fmap g)
Examples
Maybe
instance Functor Maybe where fmap f (Just x) = Just (f x) fmap _ Nothing = Nothing
Haskell lists
instance Functor [] where fmap = map
Binary tree
data Tree a = EmptyTree | Node a (Tree a) (Tree a) deriving (Show, Read, Eq) instance Functor Tree where fmap f EmptyTree = EmptyTree fmap f (Node x left right) = Node (f x) (fmap f left) (fmap f right)
An 'either' type
data Either a b = Left a | Right b deriving (Show, Eq, Ord) -- '(Either a)' is used after 'Functor' as only one argument allowed here. instance Functor (Either a) where fmap f (Right x) = Right (f x) fmap f (Left x) = Left x -- not applied here. -- Here, 'f' is of type (b -> c) as 'a' is already used. -- So 'f' can be used only with 'Right' as 'b' in 'Either a b' corresponds to 'Right'. -- And 'f' cannot be applied on 'Left x' as 'x' is of type 'a'.
Notice that in the above example
f
would effectively be of the type(b -> c) -> Either a b -> Either a c
(which is same as(b -> c) -> (Either a) b -> (Either a) c
).Functor
needs a type which can take just one type as parameter. ButEither
takes two (a
andb
). So we sort of keepa
constant and makeb
the parameter type.This means that
f
can act only on values associated with typeb
, which in turn meansRight b
and notLeft a
. Hencef
is not applied on theLeft
value.
Applicative functors
- aka applicatives.
- defined in
Control.Applicative
- defines two functions:
pure
: takes something and wraps it up in applicative functor- ~pure
- Applicative f => a -> f a
- Injects a pure value into what
f
represents. - Puts a value in a default context (ie, wraps the value in context)
- Effectively same as
return
.
<*>
: extracts a function (the 1st arg) out of the context and applies it on 2nd arg- Both parameters are functors.
<*> :: Applicative f :; f (a -> b) -> f a -> f b
- In addition to value, functions are also wrapped up in a context.
Control.Applicative
class (Functor f) => Applicative f where
pure :: a -> f a
<*> :: f (a -> b) -> f a -> f b
Some samples:
> Just (+4) <*> Just 2
λJust 6
> (*) <$> Just 3
λJust (*3)
> Just (*3) <*> Just 4
λJust 12
-- liftA2 function from Control.Applicative does the same thing
> import Control.Applicative
λ> liftA2 (*) (Just 3) (Just 4)
λJust 12
'Laws' of applicatives
Reference: l2
<-- - ~pure f <*> x~ ≡ ~fmap f x~-->
- Identity
pure id <*> v = v
- Homomorphism
pure f <*> pure x ≡ pure (f x)
- Interchange
u <*> pure y ≡ pure ($ y) <*> u
- Composition
pure (.) <*> u <*> v <*> w ≡ u <*> (v <*> w)
Examples
Maybe
instance Applicative Maybe where pure = Just -- same as: pure x = Just x Nothing <*> _ = Nothing -- cannot extract a function out of 'Nothing' Just f) <*> something = fmap f something (
Lists
instance Applicative [] where pure x = [x] <*> x = fmap f x????????????? f
Monads
Monad ⊂ Applicatives ⊂ Functors
- Applicative functors that allow us to depend on the previous actions (in the case of IO monads).
- Allows us to do sequencing (still in the case of IO monads).
- Monads ⊆ applicatives ⊆ functors
- Applies a function that returns a 'wrapped value'.
= Monad
is yet another type class (like Functor
and Applicative
).
class Monad m where
(>>=) :: m a -> (a -> m b) -> m b
- ~(>>=)
- t a -> (a -> t b) -> t b~ : bind operator
- Allows us to temporarily pull values out from the functor context??
instance Monad Maybe where
>>=) (Just x) f = f x
(>>=) Nothing _ = Nothing (
Some samples:
> half x = if x >= 0 then Just (x `div` 2)
λ> else Nothing
λ> Just 100 >>= half
λJust 50
> Just 100 >>= half >>= half
λJust 25
Haskell doesn't give a way to pull the value out of an IO monad.
getInt :: IO int
can't get the int part out.
getInt :: IO int
print :: int -> IO ()
>>= print getInt
do notation
- Essentially just syntactic sugar.
- We could think of the
<-
as something like an assignment.
https://en.wikibooks.org/wiki/Haskell/do_notation#Translating_the_bind_operator
Examples
Capitalize input
import Data.Char getContents :: String -> IO String toUpper :: Char -> Char capitalize :: String -> String = map toUpper capitalize main :: IO () = (capitalize <$> getContents) >>= putStr main -- Lesson: You don't take value out of the IO monad. We use bind -- for that.
Reading 2 ints and finding sum
>>= \x -> (getInt >>= \y -> print (x + y)) getInt -- or use do notation and make it look more readable -- indentation matters here do x <- getInt <- getInt y print $ x+y -- or if you don't like indentation do { x <- getInt; <- getInt; y print $ x+y }
Read n ints and find sum
do n <- getInt
Expression
data Maybe a = Just a | Nothing data Expr = Const Int | Plus Expr Expr | Mult Expr Expr | Div Expr Expr eval :: Expr -> Maybe Double -- one version (INCOMPLETE) Const x) = Just x eval (Plus x y) = case eval x eval (Nothing => Nothing Just xx => case eval y Nothing -> Nothing Just yy -> xx + yy -- another version (INCOMPLETE) Const x) = Just x eval (Plus x y) = (>>=) eval x <*> \x1 eval ( -- another version with do notation -- No need to explicitly worry about the Nothing case! -- Feels natural. Const x) = Just x eval (Plus x y) = do xx <- eval x eval (<- eval y yy pure (xx + yy) -- yet another way (INCOMPLETE) instance Monad Maybe where >>=) (Just x) fmaybe = fmaybe x (>>=) Nothing fmaybe = Nothing (
IO monad
(>>=) :: IO a -> (a -> IO b) -> IO b
Can't give definition for this as
IO
is effectively a blackbox.-- a standalone haskell program -- getContents :: IO string main :: IO () = do inp <- getContents main
Parser combinator??
data Result a = OK a String | Error String newtype Parser a = Parser {runParser :: String -> Result a} instance Functor Result where fmap f (OK a s) = OK (f a) s fmap _ (Error s) = Error s instance Applicative Parser where -- INCOMPLETE instance Monad Parser where -- INCOMPLETE
TODO: Look at parsec (Wikipedia), megaparsec, attoparsec (parser combinator libraries? for haskell)
IO
monad
Three functions:
- ~getLine
- IO String~ :: Read a line from stdin. Accepts no parameters.
- ~readFile
- FilePath -> IO String~ :: Accepts the path to a file and returns its contents.
- ~putStrLn
- String -> IO ()~ :: Accepts a string and prints it to stdout.
So,
getLine >>= readFile >>= putStrLn
can be used to accept a file name, read that file and print its contents.
(>>)
(then)
(>>) :: Monad m => m a -> m b -> m b
- Like
(>>=)
except that state is not carried over - Kind of a sequencing operation
A do notation that doesn't use <-
is desugared using >>
instead of >>=
.
do
action1
action2
action3
is same as:
action1 >> action2 >> action3
https://en.wikibooks.org/wiki/Haskell/do_notation#Translating_the_then_operator
—
Prelude> [1,2] >> [3,4]
[3,4,3,4]
Looks like for each element in [1,2]
, the [3,4]
is done.
- Modeling of non-determinism at play.
State monad
- 'wraps computations in the context of reading and modifying a global state object.' ¹⁷
- State is sort of made part of type.
-- State is a predefined type
-- https://hackage.haskell.org/package/mtl-2.3.1/docs/Control-Monad-State-Lazy.html#t:State
-- state
-- |
get :: State s s
-- |
-- rv
put :: State s ()
-- Get both final state and final result
runState :: s -> State s a -> (a, s)
-- Get just final result
evalState :: s -> State s a -> a
-- Get just final state
execState :: s -> State s a -> s
Refs:
- https://mmhaskell.com/monads/state
- https://wiki.haskell.org/State_Monad
- https://hackage.haskell.org/package/mtl-2.3.1/docs/Control-Monad-State-Lazy.html
Fun facts
Kinds
A kind is type of a type.
Can be seen in ghci with :k
.
Concrete type
- A type that isn't parametrized.
- Values of this type can only have types that are concrete.
Position of argument to partially applied functions matters
> ("hi"++) "hello"
λ"hihello"
> (++"hi") "hello" λ
More built-in functions
flip
Takes a function taking two arguments along with those two arguments and reverses the order of arguments before passing them to the function.
-- flip :: (a -> b -> c) -> b -> a -> c
> flip (-) 3 2
λ-1
newtype
vs data
Difference is that types defined with newtype
would be 'erased' at compile time.
data IntPair = IPair Int Int
IPair 3 2
would be like ⁶
IPair
/\
/ \
3 2
whereas
-- Constructor for a 'newtype' can have only one field.
-- So a tuple is used instead.
newtype IntPair = IPair (Int, Int)
would be something like
( , ) /\
/ \
3 2
as if the IPair
part never existed.
newtype |
data |
---|---|
Erased at compile-time | Remains after compilation |
Faster. Less overhead | Slower. More overhead |
Only single constructor | No limit on constructor count |
Strict / eager evaluation | Lazy evaluation |
An example of the eager evaluation of newtype
'constructors' and lazy evaluation of data
constructors ⁷:
data DUndef = Dundef Int
deriving Show
newtype NUndef = Nundef Int
and doing Dundef undefined
will cause exception. But doing Nundef undefined
won't. Because the evaluation is done eagerly in the case of DUndef
values but lazily on NUndef
values.
> Dundef undefined
λDundef *** Exception: Prelude.undefined
CallStack (from HasCallStack):
error, called at libraries/base/GHC/Err.hs:79:14 in base:GHC.Err
undefined, called at <interactive>:5:8 in interactive:Ghci2
> a=Nundef undefined λ
Type constructors
For example, Maybe
is not a proper type of its own, but is rather a type constructor.
We got to apply Maybe
to a proper type to get another proper type out of it. Like Maybe Bool
.
Data constructors
These seem to be the kind of constructors that we commonly refer to when we just say 'constructors'.
For example, Nothing
and Just
are data constructors of Maybe
.
Reference: CIS194
Type class reference
GADT (extension)
https://wiki.haskell.org/GADTs_for_dummies
data T a where
D1 :: Int -> T String
D2 :: T Bool
D3 :: (a,a) -> T [a]
ie, you can sort of specify the type family to which individual constructors belong. Kinda like in Coq.
References
Unsorted examples
> :t max
λmax :: Ord a => a -> a -> a
> max 3 4
λ4
> max <$> Just 3
λ> -- Just (max 3)
λ> -- of type Maybe (Int -> Int)
λ
> max <$> Just 3 <*> Just 4
λ> -- ie, (max <$> Just 3) <*> Just 4
λJust 4
Custom Maybe
data CMaybe a = CJust a
| CNothing
deriving Show
instance Functor CMaybe where
-- fmap :: (a -> b) -> CMaybe a -> CMaybe b
fmap f (CJust x) = CJust (f x)
fmap _ CNothing = CNothing
-- λ> (+5) <$> CJust 3
-- CJust 8
instance Applicative CMaybe where
-- pure :: a -> CMaybe a
pure x = CJust x
-- (<*>) :: CMaybe (a -> b) -> CMaybe a -> CMaybe b
<*>) (CJust f) (CJust x) = CJust (f x)
(<*>) (CJust f) CNothing = CNothing
(<*>) CNothing _ = CNothing
(
-- λ> max <$> CJust 3 <*> CJust 4
-- CJust 4
instance Monad CMaybe where
-- (>>=) :: CMaybe a -> (a -> CMaybe b) -> CMaybe b
>>=) (CJust x) f = f x
(>>=) CNothing _ = CNothing
(
-- Correct type: testfn :: (Show a) => a -> CMaybe a -- ✓
-- Wrong type: testfn :: Int -> CMaybe String -- ✗
= CJust (show x)
testfn x
{-
λ> tesfn 3
CJust "3"
λ> tesfn 3.14
CJust "3.14"
λ> tesfn "pi"
CJust "\"pi\""
λ> CJust 3 >>= testfn
CJust "3"
λ> CNothing >>= testfn
CNothing
-}
Quiz 4 questions
1
Consider the binary tree data type given by
data Tree a = Empty | Node (Tree a) a (Tree a)
Similar to the
ZipList
instance give anApplicative
instance for binary trees where thetf (<*>) tx
applies the functions at each node in the treetf : Tree (a -> b)
to the corresponding node in the treetx : Tree a
(shown pictorially below).f₁ x₁ f₁x₁ / \ <*> / \ = / \ f₂ f₃ x₂ x₃ f₂x₂ f₃x₃
data Tree a = Empty | Node (Tree a) a (Tree a) deriving Show instance Functor Tree where -- fmap :: (a -> b) -> Tree a -> Tree b fmap f (Node left val right) = Node (fmap f left) (f val) (fmap f right) fmap _ Empty = Empty instance Applicative Tree where -- pure :: a -> Tree a pure x = Node Empty x Empty -- <*> :: Tree (a -> b) -> Tree a -> Tree b -- ie, a tree where each leaf node is a function from a to b <*>) (Node fleft f fright) (Node left val right) = Node (fleft <*> left) (f val) (fright <*> right) (<*>) Empty _ = Empty (<*>) _ Empty = Empty ( instance Monad Tree where -- (>>=) :: Tree a -> (a -> Tree b) -> Tree b >>=) (Node left val right) f = Node (left >>= f) (f val) (right >>= f) (>>=) Empty _ = Empty ( = Node Empty (+) Empty ftree = Node Empty 3 Empty tree1 = Node Empty 5 Empty tree2 = Node (Node Empty 5 Empty) 6 Empty tree3 {- λ> (+3) <$> tree1 Node Empty 6 Empty λ> (+) <$> tree1 <*> tree2 Node Empty 8 Empty λ> ftree <*> tree1 <*> tree2 Node Empty 8 Empty λ> ftree <*> tree1 <*> tree3 Node Empty 9 Empty -}
Leafy binary tree
data LTree a = Leaf a
| Node (LTree a) (Ltree a)
deriving Show
instance Functor LTree where
-- fmap :: (a -> b) -> a -> b
fmap f (Node left right) = Node (f <$> left) (f <$> right)
fmap f (Leaf x) = f x
instance Applicative LTree where
-- pure :: a -> LTree a
pure x = Leaf x
-- <*> :: LTree (a -> b) -> LTree a -> LTree b
<*>) (Node fleft fright) (Node left right) = Node (fleft <*> left) (fright <*> right)
(<*>) (Leaf fx) (Leaf x) = fx x
(<*>) _ Empty = Empty
(<*>) Empty _ = Empty
(
instance Monad LTree where
-- (>>=) :: LTree a -> (a -> LTree b) -> LTree b
>>=) (Node left right) f = Node (left >>= f) (right >>= f)
(>>=) (Leaf x) f = Leaf (f x)
(
-- tree1 = Node (Node Empty 3 Empty) 4 (Node Empty 5 Empty)
A Result type
data Result err ok = Error err
| Okay ok
instance Functor (Result err) where
-- fmap :: (a -> b) -> Result err a -> Result err b
fmap f (Error e) = Error e
fmap f (Okay x) = Okay (f x)
instance Applicative (Result err) where
-- pure :: a -> Result err a
pure (Error e) = Error e
pure (Okay e) = Error e
Prime number generation
-- Magic of laziness! :)
-- | Not! Eratosthenes sieve.
-- http://www.cs.hmc.edu/~oneill/papers/Sieve-JFP.pdf
sieve :: [Int] -> [Int]
= []
sieve [] :ns) = n : (sieve $ filter (\x -> mod x n /= 0) ns)
sieve (n-- λ> sieve [2,3..50]
-- [2,3,5,7,11,13,17,19,23,29,31,37,41,43,47
-- | Find nth prime number
primes :: Int -- ^ n
-> Int -- ^ nth prime number
= (sieve [2..]) !! n
primes n -- λ> primes 8
-- 23
-- | Find first n prime numbers
firstnprimes :: Int -- ^ n
-> [Int] -- ^ list of first n prime numbers
= take n $ sieve [2..]
firstnprimes n -- λ> firstnprimes 10
-- [2,3,5,7,11,13,17,19,23,29]
Some builtin type classes
- Enum: enumerate all values from the (finite) typ
- Ord: total ordering?
Some functions
unwords
: Take a list of strings and make a single space separated string.
> unwords ["hello", "world"]
λ"hello world"
Haddock
https://haskell-haddock.readthedocs.io/en/latest/markup.html
|
^
{-# .... #-}
: Module attributesVerbatim:
@<text>@
Linkable code reference:
'var_name'
Doubt
Monad
has kind(* -> *) -> Constraint
. What isConstraint
?