What this document is about
These notes are not a Haskell tutorial. They serve me primarily as a memory aid. They can be useful only if you already know some Haskell. They are neither quite exact, nor complete, nor necessarily up-to-date, so use with care.
I revised these notes a bit in 2020, mainly to introduce some fancy notation and quoting mechanisms. These notes are getting old, so many things may have changed, especially in the runtime environments. Contact me if you care about anything that should be fixed.
A few features of Haskell:
-
Purely functional language
-
Lazy evaluation
-
Statically typed
-
Uses type inference
Notation
In this text, I may use a number of perhaps unconventional notations that make things clearer for me.
Metasyntactic variables
In order not to distract from what is trying to be shown, many of the example code snippets use meaningless variable names. In the past, you may have seen elsewhere variables named like this:
foo bar baz quux
Here, I will use these, selecting one or the other arbitrarily:
bar yob
foo cov
jub guh
niy kiz
reh oom
viq ste
zem wos
Indented comments
To make it easier to ignore comments when reading code or other stuff, I indent the comments one shift-width relative to what is being commented on. For example, instead of this:
-- From Data.Maybe.
catMaybes :: [Maybe a] -> [a]
-- Only the elements of ms that match constructors 'Just x' will
-- be bound.
catMaybes ms = [ x | Just x <- ms ]
I may use this:
-- From Data.Maybe.
catMaybes :: [Maybe a] -> [a]
-- Only the elements of ms that match constructors 'Just x' will
-- be bound.
catMaybes ms = [ x | Just x <- ms ]
Also, in some places the indented comments will not have the --
(or
whatever) prefix to mark them as comments. So you can’t just
copy/paste those things without editing them a bit if you need to run
them.
Description and example quotes
Instead of the frequently used < and > characters, I prefer to use 「 and 」 to surround descriptions. For example:
Instead of this…
ghc --make <Source file> -o <Output file>
…I will use this.
ghc --make 「Source file」 -o 「Output file」
I use ⦃ and ⦄ to surround concrete examples of what could be used in an expression. For example:
ghc --make ⦃foo.hs⦄ -o ⦃foo⦄
Code to run; big examples
I use ▸ to represent a prompt at the command line in your terminal. This for example is something that can be run from the terminal (after having replaced the example strings with the ones you want):
▸ ghc --make ⦃foo.hs⦄ -o ⦃foo⦄
When there are many lines, the ▸ may be used like this:
▸
ghc --make ⦃foo.hs⦄ -o ⦃foo⦄
⋯
Similarly, a big example paragraph may be shown like this:
⦃⦄
data Person = Person {
name :: String,
age :: Int
} deriving (Show)
What do I need to run Haskell programs?
I installed the Haskell Platform. It comes with:
-
ghc
: compiler -
ghci
: interactive interpreter -
cabal
: package manager -
runghc
: implemented by calling GHCi, loading a requested module, and invoking main
Project skeleton, by Taylor Fausak.
Environment
These files are useful:
editMode: Vi
historyDuplicates: IgnoreConsecutive
import Some.Module
-- ...
:set prompt "λ "
-- Allow multiline input to GHCi.
:set \+m
:set prompt2 "λ| "
-- ...
ghc
Compile a program.
▸ ghc --make ⦃foo.hs⦄ -o ⦃foo⦄
Some pragmas:
⦃⦄
{-# OPTIONS_GHC -fwarn-incomplete-patterns #-}
{-# OPTIONS_GHC -Wall #-}
{-# OPTIONS_GHC -Werror #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-warn-missing-methods #-}
ghci
At the ghci
prompt (I set it to "λ "
), you can enter expressions, and
the interpreter will print out what they evaluate to. For example:
Import one or more modules.
Load some modules.
λ :m + Data.List Data.Map Data.Set
Show the type of an expression.
λ :t 2 + 3
2 + 3 :: Num a => a
Print out type information after evaluating an expression.
λ :set +t
Unset that.
λ :unset +t
Inspect operator properties.
λ :info (+)
The ghci-specific let
command can be used to assign session-held
values to variables.
When evaluating I/O actions, ghci prints out their result, unless it’s ().
There is a special ghci-only variable, it
, which is set to the value
of the last expression evaluated.
ghci operates in the IO monad environment.
cabal
Note that cabal
can also install other stuff, darcs
for example.
Installation tutorial for Haskell Platform, talks a lot about cabal.
Update the package list (in ~/.cabal/...):
cabal update
Building a Haskell application
To set up a sandbox for application work:
Set up and move to the application directory.
APP_NAME=real-world-haskell
APP_DIR=~/app/$APP_NAME
mkdir $APP_DIR
cd $APP_DIR
Or use 'cabal init' to interactively create its config file.
Or make one by copying/editing an existing one.
vi $APP_NAME.cabal
Initialize and build a sandbox, to keep things local.
cabal sandbox init
cabal build
Install required package into the sandbox.
cabal install --only-dependencies
Install test packages into the sandbox.
cabal install --enable-tests
It may be necessary to install other cabal packages:
Install a package and all its dependencies
cabal install bit-vector
cabal install $SOME_PKG
Examples.
cabal install tasty
cabal install tasty-hunit
List names of packages having a given component in their name.
cabal list vector
To produce the PDF files from *.lhs.
cabal install lhs2tex
The Cabal of Cabal, Albert Y.C. Lai
To enable profiling in cabal, add -prof to ghc-opts. See Profiling Cabal projects, by Nikita Volkov.
How I Develop with Nix, by Oliver Charles.
Haskell development with Nix, by Pavel Kogan.
Backpack blog entries, by Edward Z. Yang.
How we might abolish Cabal Hell, part 1, by Duncan Coutts. How we might abolish Cabal Hell, part 1, by Duncan Coutts (part 2).
Haskell programs
Structure
At the topmost level, a Haskell program is a set of modules, which are collections of declarations. We find expressions, which denote a value and have a static type.
A module is structured like this:
-- Compiler pragmas. {-# OPTIONS_GHC -Wall #-} ... -- Export only symbols shown. module Foo ( exported1, exported2, -- Export all its value constructors. Point (..), -- Export none of its value constructors. Blomp, -- Export only some of its value constructors. Glorp (Flump, ...), ... ) where -- Import only symbols shown. import Bar (fromBar1, fromBar2, ...) -- Import all but some. import Bar.Baz hiding (someFunc, ...) -- Import everything module exports. import Bar.Quux -- Will need to use for example "Data.Map.filter ...". import qualified Data.Map -- Like this, we can do instead "M.filter...". import qualified Data.Map as M exported1 :: ... exported1 = ... ... r1 = Rectangle 2 3 ... main = runGraphics $ do w <- openWindow "Blah" (300,300) drawInWindow w $ text (100, 200) "Hello" k <- getKey w spaceClose w
Module names follow directory hierarchy.
Comments
-- Till end of line. {- Bracketed. {- They nest. -} -} {-# COMPILER PRAGMAS #-}
Identifiers
Six kinds of names in haskell:
What Start with Refer to
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Variables lower Value
Constructors Upper Value
Type variables lower Type system
Type constructors Upper Type system
Type classes Upper Type system
Module names Upper Module name
Constructor operators: start with ':'
Variable operators : don't start with ':'
An identifier can contain single quotes.
An identifier must not be used as the name of a type constructor and the name of a class in the same scope.
Identifiers start with a letter, followed by zero or more letters, digits, underscores, or single quotes. The underscore is treated as a lowercase letter.
Layout
Generally speaking, Haskell code layout is freeform.
Long logical lines can be split and continued on arbitrarily indented subsequent ones:
data Board = Board Int Int CellMap deriving (Eq, Show) -- Same as this (just an example!). data Board = Board Int Int CellMap deriving ( Eq , Show ) -- But often presented like this. data Board = Board Int Int CellMap deriving (Eq, Show)
Logically separate lines can be physically placed on the same line by separating them with a semicolon:
florb 'O' = Mimp florb '.' = Mump -- Same as this. florb 'O' = Mimp ; florb '.' = Mump
Keywords where
, of
, let
, and do
introduce structures that
require brackets and maybe semicolons, both of which may be avoided by
using instead proper indentation.
... where { d1 ; ... ; dn } (case e) of { p1 -> m1 ; ... ; pn -> mn } let { d1 ; ... ; dn } in e do { s1 ; ... ; sn }
When one of those four keywords is not followed by {, one will be added immediately in front of the next lexeme, whether on the same line or not. The column at which that lexeme started sets the indentation level for the construct. Following lines, if they start farther than the indentation level, are continuation lines; if they start at the indentation level, a ; is added immediately in front; if they start before the indentation level, a closing } is added. A few examples:
-- Start on next line: ... where y = z * 2 z = x -3 foo = ... -- Resolves to this. ... where {y = z * 2 ;z = x -3 }foo = ... -- Start on same line: ... where y = z * 2 z = x -3 foo = ... -- Resolves to this. ... where {y = z * 2 ;z = x -3 }foo = ... -- Incorrect indentation. ... where y = z * 2 z = x -3 foo = ... -- Resolves to this, which will complain of a 'parse error on -- input "z"': ... where {y = z * 2 }z = x -3 foo = ... -- Also incorrect indentation. ... where y = z * 2 z = x -3 foo = ... -- Resolves to this, which will also complain. ... where {y = z * 2 z = x -3 }foo = ...
Extensions
Used like this for example:
{-# LANGUAGE FlexibleInstances, TypeSynonymInstances #-}
Some of them:
- GeneralizedNewtypeDeriving
-
…
- EmptyDataDecls
-
…
- TypeSynonymInstances
-
Without this, we can make instances only of things declared with data or newtype, not type. This forbids
String
, but not[Char]
. See here for more discussion. - FlexibleInstances
-
Without this, instances can only mention one type that isn’t a variable, and only that type can be used as a type constructor. This forbids
Maybe Int
andf Int
, but notMaybe a
. - FlexibleContexts
-
…
- ScopedTypeVariables
-
…
See discussion here for example.
Haskell language.
Keywords
! > as import
' ? case, of infix, infixl, infixr
'' # class instance
- * data let, in
-- @ data family mdo
-< [|, |] data instance module
-<< \ default newtype
-> _ deriving proc
:: ` deriving instance qualified
; {, } do rec
<- {-, -} forall type
, | foreign type family
= ~ hiding type instance
=> if, then, else where
UTF-8
λ "é" ++ "sdf"
"\233sdf"
λ putStrLn $ "é" ++ "sdf"
ésdf
Binding values to variables.
foo = "Foo"
bar = 42
x = (1, 'a')
(x, y) = ((1, 2), [1,2,3])
baz x = x * 2
Lambdas
Example:
foo1 x y = x + 5 * y
foo2 = \ x y -> x + 5 * y
Numbers
There are many number types. Dangling decimal point not allowed, so for example, can’t use ".5" or "3.".
3.1415
0.31415e+1
31415e-04
Characters, strings
-
Characters:
'a'
,'\n'
,'λ'
. -
Strings:
"abc"
, actually lists of characters:[a, b, c]
.
Precedence, associativity
Function application is left associative and has higher precedence
than operators. One way to find out the precedence and associativity
of an operator is to use :info
in GHCi. Precedence levels of
operators go from 0 to 9, the higher the tighter. Level 10 is reserved
for function application. Associativity of operators can be either
left-associative (infixl), right-associative (infixr), or
non-associative (infix). Non-associative operators cannot be combined.
λ :info (*)
class Num a where
...
(*) :: a -> a -> a
...
-- Defined in `GHC.Num'
infixl 7 *
Set the fixity of an operator something like this:
infixl 7 `op`
A function can be converted to a precedence 4 (by default) operator, and an operator into a function:
x `foo` y
(+) x y
So, expressions are composed of a sequence of possibly parentheses-grouped tokens representing functions or operators. , values (V), or left-, right-, or none-associative infix operators of a given precedence level. If a F is followed by another F or a V, or a V followed by another V, we infer that between them is the "function application" left-associative and precedence 10 operator. Here are some of the many operators found in Haskell:
func : 10 L
. : 9 iR
^ : 8 iR
* : 7 iL
+ : 6 iL
++ : 5 iR
: : 5 iR
> < >= <=
: 4 i-
$ : 0 iR
Okay.
1 + length "abc"
F 6L F F
Nope.
1 + length $ tail "abc"
F 6L F OR F 10L F
((F 6L F ) OR (F 10L F ))
((1 + length) (tail "abc"))
(1 + length) (tail "abc")
Okay.
1 + (length $ tail "abc")
F 6L (F 0L F F)
2 + 4 * 5
F O F O F
(*) (+) 2 4 5
(+) 2 $ (*) 5 4
F F 0L F F F
map (\l@(x:xs) -> (x,length l)) . group . sort $ [1,1,2,2,1,4,4,1,1,4,2]
F 10L F 9R F 9R F 0R F
((F 10L F) 9R (F 9R F)) 0R F
Map.map (*100) $ Map.fromList [(1,1),(2,4),(3,9)]
F F 0L F F
F 10L F 0L F F
(F 10L F) (F F)
uncurry moreFun . treeFold nextLevel
F 10L F 9R F 10L F
You can’t always just replace parentheses with $
. Compare the
derivations for these two expressions for example:
42 : foo (div 42 2)
42 : foo $ div 42 2
The first one makes sense:
42 : foo (div 42 2)
F 5R F 10L (F 10L F 10L F)
(F 5R (F 10L ((F 10L F ) 10L F)))
(42 : (foo ((div 42) 2)))
(42 : (foo ((div 42) 2)))
The second one doesn’t:
42 : foo $ div 42 2
((F 5R F ) 0L ((F 10L F ) 10L F))
((42 : foo) $ ((div 42) 2))
((42 : foo) $ ((div 42) 2))
The ($) operator.
It is defined in the Prelude:
($) :: (a -> b) -> a -> b f $ x = f x
The operator has precedence 0, and right fixity, which can make it useful to avoid a level of parentheses. For example, these are equivalent:
head (tail "abc")
head $ tail "abc"
Lists
Lists can be empty ([]
), and they must be homogeneous (all their
elements of the same type), like [1, 2, 3]
.
List comparison is done element by element.
[3,1] > [2,4,5]
True
[[3,1], [2]] > [[3,1], [2,4,5]]
False
These list functions raise an exception if the list is empty: head
,
tail
, last
, init
.
Ranges
Allow making lists of enumerable types.
λ [3..6]
[3,4,5,6]
λ ['d'..'g']
"defg"
You can specify a step, the difference between the first two elements, and the list will go up at most to the last element:
λ [2,5..10]
[2,5,8]
λ ['a','d'..'k']
"adgj"
Avoid ranges on floats, because of their imprecise representation in binary.
Infinite lists.
Haskell’s lazy infinite lists can be very practical. For example, to get a list of the first twelve multiples of 13:
-- Perhaps this.
λ take 12 [13,26..]
-- Instead of this.
λ [13,26..12*13]
cycle
and repeat
are functions that produce infinite lists.
List comprehension
Structured like this:
[ <output_function> | <var> <- <input_set>, ..., <predicate>, ... ]
Some examples:
-- [6, 12, 18, 24, ...] [x * 2 | x <- [1..], mod x 3 == 0] -- [(1,1), (1,2), (1,3), ...] [(x, y) | x <- [1..], y <- [1..]] -- [[(1,1), (2,1)], [(1,2), (2,2)], [(1,3), (2,3)], ...] [ [ (i,j) | i <- [1,2] ] | j <- [1..] ] -- [(2,1), (3,1), (3,2), (4,1), (4,3), (5,1), ...] [ (i,j) | i <- [1..], j <- [1..i-1], gcd i j == 1 ]
Tuples
Tuples can be heterogeneous and they must have at least two elements. For example:
('a', 4, "foo")
A pair is a two-element tuple.
Use tuples when you know in advance how many components some piece of data should have.
Pair tuples are actually constructed from the (,)
operator. Longer tuples,
from longer comma operators, like (,,)
, (,,,)
, …
(,,) :: a -> b -> c -> (a, b, c)
Tuples have a type dependent on their length and the types of their contents.
The empty tuple () has a single possible value, ().
Operator section
When one operand of a binary operator is supplied inside the parentheses, we call it an operator section. Note that they take a single argument. For example:
(== 0)
(1 +)
Some common types
- Int
-
Used for whole numbers, values bounded by machine precisison.
- Integer
-
Unbounded whole numbers.
- Float
-
Single precisions floating number (but use Double, they’re usually better implemented).
- Double
-
Double precisions floating number.
- Bool
-
Boolean type; two values: True False
Conversions
-- String to number read "42" -- Number to string show 42 toInteger toRational toEnum
See Converting numbers.
Type classes
In the following, "Eq a" is called a "class constraint". Eq is a "type class".
(==) :: Eq a => a -> a -> Bool
Some basic type classes:
- Eq
-
(
==
,/=
) Used for types whose values can be compared for equality. All standard Haskell types except for IO and functions are a part of the Eq type class. - Ord
-
(
>
,>=
,<
,⇐
,compare
,min
,max
) Used for types whose values have an ordering. Those types must be part of theEq
type class.
λ :t (==)
(==) :: Eq a => a -> a -> Bool
λ :t compare
compare :: Ord a => a -> a -> Ordering
λ compare 3 4
LT
Ordering
is a type whose values can be LT
, EQ
, or GT
.
- Show
-
(
show
) Values of types belonging to this type class can be presented as strings. - Read
-
(
read
) Values of types belonging to this type class can be converted from a string to some value.
λ show 42
"42"
λ read "True" || False
True
λ read "[1,2,3,4]" ++ [3]
[1,2,3,4,3]
-- This fails, because the resulting type cannot be inferred.
λ read "4"
We can use explicit type annotations to disambiguate:
λ read "[1,2,3,4]" :: [Int]
[1,2,3,4]
λ read "(3, 'a')" :: (Int, Char)
(3, 'a')
- Enum
-
(
toEnum
,fromEnum
,succ
,pred
, …) Values of types belonging to this type class can be sequentially ordered.
λ fromEnum True
1
λ toEnum 42 :: Char
'*'
λ toEnum 1 && True
True
- Bounded
-
(
minBound
,maxBound
) Members have an upper and a lower bound.
λ minBound :: Int
-2147483648
-- Raises an exception, since Integer is not bounded.
λ minBound :: Integer
- Num
-
(
(
)+,(\*)
,abs
,signum
,fromInteger
,negate
,(-)
)) Its members behave like numbers.
λ :t (*)
(*) :: (Num a) => a -> a -> a
- Integral
-
Includes only whole numbers. It is in the Eq (equality) class and the Ord (ordered) class.
- Floating
-
Includes only floating numbers, so
Float
andDouble
.
The fromIntegral
function turns an integral number into a more
general type.
λ :t fromIntegral
fromIntegral :: (Num b, Integral a) => a -> b
λ fromIntegral (length [1,2,3,4]) + 3.2
7.2
Syntax in Functions
Pattern matching
Useful discussion here.
Matching can occur only on constructors. Wherever you can bind variables, you can pattern match.
The _
keyword matches anything.
where bindings are a syntactic construct that let you bind to variables at the end of a function and the whole function can see them, including all the guards.
let bindings let you bind to variables anywhere and are expressions themselves, but are very local, so they don’t span across guards.
let bindings are expressions themselves. where bindings are just syntactic constructs.
The names defined in a let inside a list comprehension are visible to the output function (the part before the |) and all predicates and sections that come after of the binding.
let ...; ... in ...
foo :: (Integral a) => a -> a foo 1 = 42 foo 2 = 23 foo x = x + 1 factorial :: (Integral a) => a -> a factorial 0 = 1 factorial n = n * factorial (n - 1) factorial' :: (Integral a) => a -> a factorial' n | n == 0 = 1 | otherwise = n * factorial' (n - 1) addVectors :: (Num a) => (a, a) -> (a, a) -> (a, a) addVectors a b = (fst a + fst b, snd a + snd b) -- Match directly on tuples. addVectors' :: (Num a) => (a, a) -> (a, a) -> (a, a) addVectors' (x1, y1) (x2, y2) = (x1 + x2, y1 + y2) -- Match in a list comprehension. λ let xs = [(1,3), (4,3), (2,4), (5,3), (5,6), (3,1)] λ [a+b | (a,b) <- xs] [4,7,6,8,11,4] -- From Data.Maybe. catMaybes :: [Maybe a] -> [a] -- Only the elements of ms that match constructors 'Just x' will -- be bound. catMaybes ms = [ x | Just x <- ms ] λ let x = y + 3 where (_:y:_) = [5,6,7,8] λ x 9
Case expressions
These are equivalent:
head' :: [a] -> a
head' [] = error "No head for empty lists!"
head' (x:_) = x
head'' :: [a] -> a
head'' xs = case xs of
[] -> error "No head for empty lists!"
(x:_) -> x
As are these:
describeList :: [a] -> String
describeList xs = "The list is " ++ case xs of
[] -> "empty."
[x] -> "a singleton list."
xs -> "a longer list."
describeList' :: [a] -> String
describeList' xs = "The list is " ++ what xs
where what [] = "empty."
what [x] = "a singleton list."
what xs = "a longer list."
Custom types and type classes
Examples:
data Point = Point Float Float deriving (Show)
data Shape =
Circle Point Float |
Rectangle Point Point
deriving (Show)
Point and Shape are datatypes, Point (in a different namespace), Circle, and Rectangle are value constructors. The deriving (Show) instructs Haskell to make the datatypes part of the Show type class.
Circle :: Point → Float → Shape
The constructors can (as usual) be used for pattern matching:
surface :: Shape -> Float surface Circle _ r = pi * r ^ 2 -- Note the constructor operator. data Tree a = Leaf a | Tree a :^: Tree a
Record syntax
-- Instead of this; data Person = Person String Int deriving (Show) name :: Person -> String name = (Person name _) = name age :: Person -> Int age = (Person _ age) = age -- we can more simply do: data Person = Person { name :: String, age :: Int } deriving (Show) -- Don't need to be in order. guy = Person {age = 42, name = "Fred} -- Still possible, but order must be respected. gal = Person "Rita" 24 name guy == "Fred" -- Change one or more fields: newGuy = guy {name = "Joe"}
Type parameters
data Maybe a = Nothing | Just a
Usually type parameters are used when our data type would work regardless of the type of the value it then holds inside it.
Don’t put type constraints into data declarations even if it seems to
make sense, because you’ll have to put them into the function type
declarations that require the constraint anyway, and will be hampered
by those that don’t. So we have for example data Map k v
instead of
data (Ord k) ⇒ k v
, which allows us to have simply toList :: Map k
a → [(k, a)]
Derived instances
Haskell can automatically make our types instances of one of these
type classes, by using the deriving
construction:
Eq
Ord
Enum
Ix
Bounded
Read
Show
For example, we can have our Person datatype derive these:
data Person = Person {
name :: String,
age :: Int
} deriving (Eq, Show, Read)
For this to work, all the types used in the value constructors must already derive the requested type classes (and Ord, Enum, and Bounded are thus excluded). We can use them like this:
We need to annotate for the type here.
joe = read "Person {name = \"Joe\", age = 42}" :: Person
Type is inferred here.
joe == read "Person {name = \"Joe\", age = 42}"
Parameterized types can be read too, but we need to supply the parameter types:
read "Just 't'" :: Maybe Char
Here is a type that derives Ord, Enum, and Bounded as well:
data Merp = A1 | A2 | A3
deriving (Eq, Show, Read, Enum, Ord, Bounded)
m1 = A1
m2 = A2
m3 = A3
m2 `compare` m1
A2 == m2
minBound :: Merp
An enumeration consists of one or more nullary, non-GADT constructors.
We can also have this (not sure how/when it’s usable):
{-# LANGUAGE GeneralizedNewtypeDeriving #-} newtype Foo = ... deriving (..., Num)
{-# OPTIONS_GHC -fno-warn-missing-methods #-}
Type synonyms
type String = [Char]
type PhoneNumber = String
type Name = String
type PhoneBook = [(Name,PhoneNumber)]
Type synonyms can be parameterized:
type AssocList k v = [(k,v)]
type IntMap v = Map Int v
type IntMap = Map Int
Recursive datatypes
An example:
data Tree a = EmptyTree | Node a (Tree a) (Tree a) deriving (Show, Read, Eq) singleton :: a -> Tree a singleton x = Node x EmptyTree EmptyTree treeInsert :: (Ord a) => a -> Tree a -> Tree a treeInsert x EmptyTree = singleton x treeInsert x (Node a left right) | x == a = Node x left right | x < a = Node a (treeInsert x left) right | x > a = Node a left (treeInsert x right) treeElem :: (Ord a) => a -> Tree a -> Bool treeElem x EmptyTree = False treeElem x (Node a left right) | x == a = True | x < a = treeElem x left | x > a = treeElem x right
Making type classes
Instead of using deriving (Eq)
, we will manually make a TrafficLight
datatype an instance of the Eq
type class.
This is how the Eq
type class is defined:
class Eq a where (==) :: a -> a -> Bool (/=) :: a -> a -> Bool x == y = not (x /= y) x /= y = not (x == y)
It turns out that the the minimal complete definition for an
instance of the Eq
type class is to have either the ==
or the /=
function defined. That way the undefined one can use the default
definition supplied by the type class definition.
Here is our TrafficLight
datatype:
data TrafficLight = Red | Yellow | Green instance Eq TrafficLight where Red == Red = True Green == Green = True Yellow == Yellow = True _ == _ = False
Here is how the Maybe m
datatype is made an instance of the Eq
type class:
instance (Eq m) => Eq (Maybe m) where Just x == Just y = x == y Nothing == Nothing = True _ == _ = False
A YesNo
type class and some of its instances we can make:
class YesNo a where yesno :: a -> Bool instance YesNo Int where yesno 0 = False yesno _ = True instance YesNo [a] where yesno [] = False yesno _ = True instance YesNo Bool where yesno = id instance YesNo (Maybe a) where yesno (Just _) = True yesno Nothing = False instance YesNo (Tree a) where yesno EmptyTree = False yesno _ = True instance YesNo TrafficLight where yesno Red = False yesno _ = True yesnoIf :: (YesNo y) => y -> a -> a -> a yesnoIf yesnoVal yesResult noResult = if yesno yesnoVal then yesResult else noResult
The Functor type class
Defined like this:
class Functor f where fmap :: (a -> b) -> f a -> f b
Some examples:
instance Functor [] where fmap = map instance Functor Maybe where fmap f (Just x) = Just (f x) fmap f Nothing = Nothing instance Functor Tree where fmap f EmptyTree = EmptyTree fmap f (Node x leftsub rightsub) = Node (f x) (fmap f leftsub) (fmap f rightsub) instance Functor (Either a) where fmap f (Right x) = Right (f x) fmap f (Left x) = Left x -- 'map' here is the one defined in Data.Map, not the one used for lists. -- Data.Map.map :: (a -> b) -> Map k a -> Map k b instance Functor (Map k) where fmap f m = map f m
A tutorial by bitemyapp:
Solving type signatures
(W x >>= f) >>= g
= (f x) >>= g
W x >>= (\x -> f x >>= g)
= (\x -> f x >>= g) x
= f x >>= g
Incidentally, you can get a long way with these problems by not thinking about what’s going on! Instead, just write out the type signatures of all of the functions involved and try to stick them together like a jigsaw puzzle so that the final result has the right type. At each stage the arguments of each function must match the signature of the function so it really is like fitting the shapes of jigsaw pieces together. This isn’t a foolproof strategy, but it often works.
Kinds
A kind is more or less the type of a type. GHCi can tell us the
kind of a type with its :k
command. For example:
λ :k Int
Int :: *
λ :k Maybe
Maybe :: * -> *
λ :k Maybe Int
Maybe Int :: *
The * means concrete type, so Int
is a concrete type, and Maybe
is a type that takes a concrete type as argument and evaluates to a
concrete type, and Maybe Int
is a concrete type.
Given:
class Tofu t where tofu :: j a -> t a j
we can infer that:
a : *
j : * -> *
t : * -> (* -> *) -> *
so:
λ :k Tofu
Tofu :: (* -> (* -> *) -> *) -> Constraint
A datatype that can use this type class, with the kind * → (* → *) → *
:
λ data F a b = F {foo :: b a} deriving (Show)
λ :t F {foo = Just "HAHA"}
F {foo = Just "HAHA"} :: F [Char] Maybe
λ :t F {foo = Node 'a' EmptyTree EmptyTree}
F {foo = Node 'a' EmptyTree EmptyTree} :: F Char Tree
λ :t F {foo = "YES"}
F {foo = "YES"} :: F Char []
instance Tofu F where
tofu x = F x
λ tofu (Just 'a') :: F Char Maybe
F {foo = Just 'a'}
λ tofu ["HELLO"] :: F [Char] []
F {foo = ["HELLO"]}
Now let’s make this datatype an instance of Functor
:
data B t k p = B { yoo :: p, doo :: t k }
We can infer its kind is (* → *) → * → * → *
, so:
instance Functor (B a b) where
fmap f (B {yoo = x, doo = y}) = B {yoo = f x, doo = y}
Sorting
-- Data.List sort :: Ord a => [a] -> [a] sortBy :: (a -> a -> Ordering) -> [a] -> [a] -- Prelude/Data.Ord compare :: Ord a => a -> a -> Ordering -- Data.Function on :: (b -> b -> c) -> (a -> b) -> a -> a -> c -- Some examples. -- [1, 2, 3] sort [3, 1, 2] nums = [(1,5), (3,2), (1,1), (8,0), (2,4)] -- [(1,1), (3,2), (1,5), (2,4), (8,0)] sortBy (\ (a,b) (c,d) -> compare (a+b) (c+d) ) nums sortBy (compare `on` (\ (a,b) -> a + b)) nums
Testing
Test.Framework
import Test.Tasty import Test.Tasty.HUnit import Test.Tasty.QuickCheck import qualified Test.Tasty.SmallCheck as SC arith :: Integer -> Integer -> Property arith x y = (x > 0) && (y > 0) ==> (x+y)^2 > x^2 + y^2 negation :: Integer -> Bool negation x = abs (x^2) >= x suite :: TestTree suite = testGroup "Test Suite" [ testGroup "Units" [ testCase "Equality" $ True @=? True , testCase "Assertion" $ assert $ (length [1,2,3]) == 3 ], testGroup "QuickCheck tests" [ testProperty "Quickcheck test" arith ], testGroup "SmallCheck tests" [ SC.testProperty "Negation" negation ] ] main :: IO () main = defaultMain suite
Results in:
$ runhaskell TestSuite.hs
Unit tests
Units
Equality: OK
Assertion: OK
QuickCheck tests
Quickcheck test: OK
+++ OK, passed 100 tests.
SmallCheck tests
Negation: OK
11 tests completed
Haskell testing workflow discussion on stackoverflow.
Testing with Test.HUnit
Articles by Jan Stolarek:
Test.HUnit on Hoogle.
With Test.HUnit
, tests are specified compositionally. Assertion
(which have type IO ()
) are combined to make a TestCase
. and test
cases are combined into Test
. HUnit also provides advanced features
for more convenient test specification.
import Test.HUnit -- type Assertion = IO () -- data Test -- = TestCase Assertion -- | TestList [Test] -- | TestLabel String Test main = do runTestTT «test» runTestTT «test» «assertion» = do assertFailure "Always fails." assertString "Fails if this is an empty string." assertEqual "Fails if the expected is not equal to the obtained." «expect» «obtain» assertBool "Fails if the expression is false." «expression» «obtain» @?= «expect» «expect» @=? «obtain» «expression» @? "Fails if the expression is false." «test» = TestCase «assertion» «test» = «obtain» ~?= «expect» «test» = «expect» ~=? «obtain» «test» = «expression» ~? "Fails if the expression is false." «test» = [«test», ...] Adding labels to tests. «test» = TestLabel «string» «test» «test» = «string» ~: «test» «test» = «string» ~: «assertion»
Testing for exceptions (FIXME — just copied this here, not sure how it works):
import Control.Exception testNegCursor = TestCase $ do handleJust errorCalls (\_ -> return ()) performCall where performCall = do evaluate ( findIdentifier "a" (-1,-1) ) assertFailure "Cursor position (-1,-1) must throw an error"
Test.HUnit synopsis
data Test = TestCase Assertion | TestList [Test] | TestLabel String Test -- «expected» ~=? «actual» (~=?) :: (Eq a, Show a) => a -> a -> Test -- «actual» ~?= «expected» (~?=) :: (Eq a, Show a) => a -> a -> Test (~:) :: Testable t => String -> t -> Test (~?) :: AssertionPredicable t => t -> String -> Test -- «msg» -- Unconditional failure. assertFailure :: String -> Assertion -- «msgPfx» -> «shouldBeTrue» assertBool :: String -> Bool -> Assertion -- «msgPfx» -> «expected» -> «actual» assertEqual :: (Eq a, Show a) => String -> a -> a -> Assertion assertString :: String -> Assertion type Assertion = IO () -- «expected» @=? «actual» (@=?) :: (Eq a, Show a) => a -> a -> Assertion -- «actual» @?= «expected» (@?=) :: (Eq a, Show a) => a -> a -> Assertion (@?) :: AssertionPredicable t => t -> String -> Assertion class Assertable t where assert :: t -> Assertion class ListAssertable t where listAssert :: [t] -> Assertion type AssertionPredicate = IO Bool class AssertionPredicable t where assertionPredicate :: t -> AssertionPredicate class Testable t where test :: t -> Test data State = State { path :: Path counts :: Counts } data Counts = Counts { cases :: Int tried :: Int errors :: Int failures :: Int } type Path = [Node] data Node = ListItem Int | Label String testCasePaths :: Test -> [Path] testCaseCount :: Test -> Int type ReportStart us = State -> us -> IO us type ReportProblem us = String -> State -> us -> IO us performTest :: ReportStart us -> ReportProblem us -> ReportProblem us -> us -> Test -> IO (Counts, us)
Test.HUnit.Text synopsis
data PutText st = PutText (String -> Bool -> st -> IO st) st putTextToHandle :: Handle -> Bool -> PutText Int putTextToShowS :: PutText ShowS runTestText :: PutText st -> Test -> IO (Counts, st) showPath :: Path -> String showCounts :: Counts -> String runTestTT :: Test -> IO Counts
Exception handling.
For reporting errors:
error :: [Char] -> a
It will abort the program after printing its message, but note that it
evaluates to type a
, which means that it can be used anywhere.
Debugging
Debugging, on the Haskell wiki.
trace
takes a string and some value and prints the string and
evaluates to the value.
-- Debug.Trace.trace:
trace :: String -> a -> a
IO
An I/O action (IOA) is something that when performed will carry out an action with a side-effect (for example, reading and writing) and will also contain some kind of return value inside it.
An IOA will be performed when we give it a name of main
and then run
our program. main
always has a type signature of IO
some_concrete_type
, but we don’t usually specify it.
type IO a = RealWorld -> (a, RealWorld)
The do
keyword allows us to sequence several expressions evaluating
to IOAs — and let
expressions — into a single one. The result type
of the sequence is the result type of the last action of the sequence.
The result type of an IOA (except the last one of a sequence — explained later) can be bound to a variable with the ←
keyword:
name <- getLine
We can explicitly make an IOA out of a pure value with the
return
function, which does nothing except set the IOA’s
result type.
So ←
and result
can be combined like foo ← return "Foo"
to
bind a value to a variable, but let
expressions are probably
clearer.
Some I/O actions:
Print stuff to STDOUT.
putChar :: Char -> IO ()
putStr :: String -> IO ()
putStrLn :: String -> IO ()
print :: Show a => a -> IO ()
Read stuff from STDIN.
getChar :: IO Char
getLine :: IO String -- The newline is discarded.
If boolean is true, evaluate given IOA, else do "return ()".
when :: Monad m => Bool -> m () -> m ()
Takes a list of IOAs and evaluates to a single one that performs
them in order, with a result that is a list of the results of each
IOA itself.
sequence :: Monad m => [m a] -> m [a]
Similar, but discards results.
sequence_ :: Monad m => [m a] -> m ()
Map a function over a list of IOA, then sequence it, with the
result being a list of the individual results; mapM_ discards the
result. forM/forM_ have the parameters swapped.
mapM :: Monad m => (a -> m b) -> [a] -> m [b]
mapM_ :: Monad m => (a -> m b) -> [a] -> m ()
forM :: Monad m => [a] -> (a -> m b) -> m [b]
forM_ :: Monad m => [a] -> (a -> m b) -> m ()
Takes an IOA and evaluates to one that repeats the original one
forever.
forever :: Monad m => m a -> m b
Files and streams
Reads from STDIN till EOF.
getContents :: IO String
Applies function to string read from STDIN stream and prints it
out.
interact :: (String -> String) -> IO ()
openFile :: FilePath -> IOMode -> IO Handle
Slurp in file contents from handle.
hGetContents :: Handle -> IO String
Close stream bound to handle.
hClose :: Handle -> IO ()
Note the IOMode`s:
data IOMode = ReadMode | WriteMode | AppendMode | ReadWriteMode
withFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
An implementation of withFile:
withFile' :: FilePath -> IOMode -> (Handle -> IO a) -> IO a
withFile' path mode f = do
handle <- openFile path mode
result <- f handle
hClose handle
return result
Analog to their non-stream counterparts:
hGetChar
hGetLine
hPutStr
hPutStrLn
readFile :: FilePath -> IO String
writeFile :: FilePath -> String -> IO ()
appendFile :: FilePath -> String -> IO ()
Set buffering mode.
hSetBuffering :: Handle -> BufferMode -> IO ()
Buffering mode is one of:
NoBuffering
LineBuffering
BlockBuffering (Maybe Int)
hFlush :: Handle -> IO ()
Arguments are: directory where to create the temp file, and
some base name to use for it (some random characters will be
added to it to make it unique).
openTempFile :: FilePath -> String -> IO (FilePath, Handle)
removeFile :: FilePath -> IO ()
renameFile :: FilePath -> FilePath -> IO ()
Command line arguments
These functions, from System.Environment
:
getArgs :: IO [String]
getProgName :: IO String
Prelude synopsis
data Bool :: * = False | True (&&) :: Bool -> Bool -> Bool (||) :: Bool -> Bool -> Bool not :: Bool -> Bool otherwise :: Bool data Maybe a = Nothing | Just a -- «default» -> «func» -> «func_arg» -> «result» maybe :: b -> (a -> b) -> Maybe a -> b data Either a b = Left a | Right b either :: (a -> c) -> (b -> c) -> Either a b -> c data Ordering :: * = LT | EQ | GT data Char :: * type String = [Char] -- First element of a pair. fst :: (a, b) -> a -- Second element of a pair. snd :: (a, b) -> b curry :: ((a, b) -> c) -> a -> b -> c uncurry :: (a -> b -> c) -> (a, b) -> c class Eq a where (==) :: a -> a -> Bool (/=) :: a -> a -> Bool class Eq a => Ord a where compare :: a -> a -> Ordering (<) :: a -> a -> Bool (>=) :: a -> a -> Bool (>) :: a -> a -> Bool (<=) :: a -> a -> Bool max :: a -> a -> a min :: a -> a -> a class Enum a where succ :: a -> a pred :: a -> a toEnum :: Int -> a fromEnum :: a -> Int enumFrom :: a -> [a] enumFromThen :: a -> a -> [a] enumFromTo :: a -> a -> [a] enumFromThenTo :: a -> a -> a -> [a] class Bounded a where minBound, maxBound :: a data Int :: * data Integer :: * data Float :: * data Double :: * type Rational = Ratio Integer class Num a where (+), (*), (-) :: a -> a -> a negate :: a -> a abs :: a -> a signum :: a -> a fromInteger :: Integer -> a class (Num a, Ord a) => Real a where toRational :: a -> Rational class (Real a, Enum a) => Integral a where quot :: a -> a -> a rem :: a -> a -> a div :: a -> a -> a mod :: a -> a -> a quotRem :: a -> a -> (a, a) divMod :: a -> a -> (a, a) toInteger :: a -> Integer class Num a => Fractional a where (/) :: a -> a -> a recip :: a -> a fromRational :: Rational -> a class Fractional a => Floating a where pi :: a exp, sqrt, log :: a -> a (**), logBase :: a -> a -> a sin, tan, cos :: a -> a asin, atan, acos :: a -> a sinh, tanh, cosh :: a -> a asinh, atanh, acosh :: a -> a class (Real a, Fractional a) => RealFrac a where properFraction :: Integral b => a -> (b, a) truncate :: Integral b => a -> b round :: Integral b => a -> b ceiling :: Integral b => a -> b -- Largest integer not exceeding argument. floor :: Integral b => a -> b class (RealFrac a, Floating a) => RealFloat a where floatRadix :: a -> Integer floatDigits :: a -> Int floatRange :: a -> (Int, Int) decodeFloat :: a -> (Integer, Int) encodeFloat :: Integer -> Int -> a exponent :: a -> Int significand :: a -> a scaleFloat :: Int -> a -> a isNaN :: a -> Bool isInfinite :: a -> Bool isDenormalized :: a -> Bool isNegativeZero :: a -> Bool isIEEE :: a -> Bool atan2 :: a -> a -> a subtract :: Num a => a -> a -> a even :: Integral a => a -> Bool odd :: Integral a => a -> Bool gcd :: Integral a => a -> a -> a lcm :: Integral a => a -> a -> a -- Raise to a non-negative integral power. (^) :: (Num a, Integral b) => a -> b -> a -- Raise to an integral power. (^^) :: (Fractional a, Integral b) => a -> b -> a fromIntegral :: (Integral a, Num b) => a -> b realToFrac :: (Real a, Fractional b) => a -> b class Monad m where (>>=) :: forall a b. m a -> (a -> m b) -> m b (>>) :: forall a b. m a -> m b -> m b return :: a -> m a fail :: String -> m a class Functor f where fmap :: (a -> b) -> f a -> f b mapM :: Monad m => (a -> m b) -> [a] -> m [b] mapM_ :: Monad m => (a -> m b) -> [a] -> m () sequence :: Monad m => [m a] -> m [a] sequence_ :: Monad m => [m a] -> m () (=<<) :: Monad m => (a -> m b) -> m a -> m b -- Identity function. id :: a -> a const :: a -> b -> a -- Functional composition. (.) :: (b -> c) -> (a -> b) -> a -> c flip :: (a -> b -> c) -> b -> a -> c ($) :: (a -> b) -> a -> b until :: (a -> Bool) -> (a -> a) -> a -> a asTypeOf :: a -> a -> a error :: [Char] -> a undefined :: a seq :: a -> b -> b ($!) :: (a -> b) -> a -> b map :: (a -> b) -> [a] -> [b] -- List concatenation. (++) :: [a] -> [a] -> [a] filter :: (a -> Bool) -> [a] -> [a] -- First element of list. head :: [a] -> a -- Last element of list. last :: [a] -> a -- All but first element of list. tail :: [a] -> [a] -- All but last element of list. init :: [a] -> [a] -- True if list is empty, False otherwise. null :: [a] -> Bool -- Number of elements in a list. length :: [a] -> Int -- 0-based indexing. (!!) :: [a] -> Int -> a -- Reverse a list. reverse :: [a] -> [a] -- foldl op init (x1:x2:...:xn:[]) -- foldl (\ accum x -> ...) ... -- (... ((init `op` x1) `op` x2) ...) `op` xn -- op (... (op (op init x1) x2) ...) xn foldl :: (b -> a -> b) -> b -> [a] -> b foldl1 :: (a -> a -> a) -> [a] -> a -- foldr op init (x1:x2:...:xn:[]) -- foldr (\ x accum -> ...) ... -- x1 `op` (x2 `op` (... (xn `op` init) ...)) -- op x1 (op x2 (... (op xn init) ...)) foldr :: (a -> b -> b) -> b -> [a] -> b foldr1 :: (a -> a -> a) -> [a] -> a and :: [Bool] -> Bool or :: [Bool] -> Bool any :: (a -> Bool) -> [a] -> Bool all :: (a -> Bool) -> [a] -> Bool -- Sum of list of numbers. sum :: Num a => [a] -> a -- Product of list of numbers. product :: Num a => [a] -> a -- Concatenates lists. It's like: foldr (++) [] concat :: [[a]] -> [a] concatMap :: (a -> [b]) -> [a] -> [b] -- Biggest element of list. maximum :: Ord a => [a] -> a -- Smallest element of list. minimum :: Ord a => [a] -> a scanl :: (b -> a -> b) -> b -> [a] -> [b] scanl1 :: (a -> a -> a) -> [a] -> [a] scanr :: (a -> b -> b) -> b -> [a] -> [b] scanr1 :: (a -> a -> a) -> [a] -> [a] iterate :: (a -> a) -> a -> [a] -- Repeat an element to infinity. repeat :: a -> [a] -- Repeat an element a given number of times. replicate :: Int -> a -> [a] -- Cycles a list to infinity. cycle :: [a] -> [a] -- Keep given number of elements from beginning of list. take :: Int -> [a] -> [a] -- Drop given number of elements from beginning of list. drop :: Int -> [a] -> [a] splitAt :: Int -> [a] -> ([a], [a]) takeWhile :: (a -> Bool) -> [a] -> [a] dropWhile :: (a -> Bool) -> [a] -> [a] span :: (a -> Bool) -> [a] -> ([a], [a]) -- Break list into two parts, at point where predicate is true. break :: (a -> Bool) -> [a] -> ([a], [a]) -- True if element appears in list, False otherwise. elem :: Eq a => a -> [a] -> Bool notElem :: Eq a => a -> [a] -> Bool lookup :: Eq a => a -> [(a, b)] -> Maybe b -- Zip lists together; miscorresponding elements are discarded. zip :: [a] -> [b] -> [(a, b)] zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] unzip :: [(a, b)] -> ([a], [b]) unzip3 :: [(a, b, c)] -> ([a], [b], [c]) -- Extract lines (last trailing newline is ignored). lines :: String -> [String] -- Extract words. words :: String -> [String] -- Concatenates strings,each of which has a newline appended. -- It's like: concat . map(++ "\n") unlines :: [String] -> String unwords :: [String] -> String type ShowS = String -> String class Show a where showsPrec :: Int -> a -> ShowS -- Convert non-string to string. show :: a -> String showList :: [a] -> ShowS shows :: Show a => a -> ShowS showChar :: Char -> ShowS showString :: String -> ShowS showParen :: Bool -> ShowS -> ShowS type ReadS a = String -> [(a, String)] class Read a where readsPrec :: Int -> ReadS a readList :: ReadS [a] reads :: Read a => ReadS a readParen :: Bool -> ReadS a -> ReadS a -- Convert string to non-string, if it makes sense. read :: Read a => String -> a lex :: ReadS String data IO a :: * -> * putChar :: Char -> IO () putStr :: String -> IO () putStrLn :: String -> IO () print :: Show a => a -> IO () getChar :: IO Char getLine :: IO String getContents :: IO String interact :: (String -> String) -> IO () type FilePath = String readFile :: FilePath -> IO String writeFile :: FilePath -> String -> IO () appendFile :: FilePath -> String -> IO () readIO :: Read a => String -> IO a readLn :: Read a => IO a type IOError = IOException ioError :: IOError -> IO a userError :: String -> IOError
Data.List synopsis
(++) :: [a] -> [a] -> [a] head :: [a] -> a last :: [a] -> a tail :: [a] -> [a] init :: [a] -> [a] null :: [a] -> Bool length :: [a] -> Int map :: (a -> b) -> [a] -> [b] reverse :: [a] -> [a] -- Puts an element between each pair of elements of a list. intersperse :: a -> [a] -> [a] -- Inserts a list between each pair of lists elements of a list, -- flattens result. intercalate :: [a] -> [[a]] -> [a] -- Columns become rows, and vice versa. transpose :: [[a]] -> [[a]] subsequences :: [a] -> [[a]] permutations :: [a] -> [[a]] foldl :: (b -> a -> b) -> b -> [a] -> b -- Strict, non-lazy version of foldl. foldl' :: (b -> a -> b) -> b -> [a] -> b foldl1 :: (a -> a -> a) -> [a] -> a foldl1' :: (a -> a -> a) -> [a] -> a foldr :: (a -> b -> b) -> b -> [a] -> b foldr1 :: (a -> a -> a) -> [a] -> a -- Flattens a list of lists and concatenates into a single list. concat :: [[a]] -> [a] -- Applies function to list elements, then does a concat. concatMap :: (a -> [b]) -> [a] -> [b] and :: [Bool] -> Bool or :: [Bool] -> Bool any :: (a -> Bool) -> [a] -> Bool -- Evaluates to True if all elements of list satisfy the given -- predicate. all :: (a -> Bool) -> [a] -> Bool sum :: Num a => [a] -> a product :: Num a => [a] -> a maximum :: Ord a => [a] -> a minimum :: Ord a => [a] -> a scanl :: (b -> a -> b) -> b -> [a] -> [b] scanl1 :: (a -> a -> a) -> [a] -> [a] scanr :: (a -> b -> b) -> b -> [a] -> [b] scanr1 :: (a -> a -> a) -> [a] -> [a] mapAccumL :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y]) mapAccumR :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y]) -- Applies function to value, then to result, and so on, places all -- results in (infinite) list. iterate :: (a -> a) -> a -> [a] repeat :: a -> [a] replicate :: Int -> a -> [a] cycle :: [a] -> [a] unfoldr :: (b -> Maybe (a, b)) -> b -> [a] take :: Int -> [a] -> [a] drop :: Int -> [a] -> [a] -- Evaluates to two lists from a given one split at a given -- 0-based index. splitAt :: Int -> [a] -> ([a], [a]) -- Evaluates to a list of the initial elements that satisfy the given -- predicate. takeWhile :: (a -> Bool) -> [a] -> [a] -- Evaluates to the list remaining after dropping the initial -- elements that satisfy the given predicate. dropWhile :: (a -> Bool) -> [a] -> [a] -- Similar to dropWhile, but starts at the end of the list. dropWhileEnd :: (a -> Bool) -> [a] -> [a] -- "span p" is equivalent to "break (not . p)". span :: (a -> Bool) -> [a] -> ([a], [a]) break :: (a -> Bool) -> [a] -> ([a], [a]) stripPrefix :: Eq a => [a] -> [a] -> Maybe [a] -- Groups adjacent elements into sublists if they are equal. group :: Eq a => [a] -> [[a]] -- A list of increasingly long inits. inits :: [a] -> [[a]] -- A list of increasingly short tails. tails :: [a] -> [[a]] -- True if sublist is present at beginning of list. isPrefixOf :: Eq a => [a] -> [a] -> Bool -- True if sublist is present at end of list. isSuffixOf :: Eq a => [a] -> [a] -> Bool -- True if sublist is present somewhere in list. isInfixOf :: Eq a => [a] -> [a] -> Bool -- True if element is present in list. elem :: Eq a => a -> [a] -> Bool -- True if element is absent in list. notElem :: Eq a => a -> [a] -> Bool lookup :: Eq a => a -> [(a, b)] -> Maybe b -- Searches for element satisfying predicate in list, wrapped in a -- Maybe. find :: (a -> Bool) -> [a] -> Maybe a filter :: (a -> Bool) -> [a] -> [a] -- Evaluates to two lists: the first is the list of the elements -- satisfying the given predicate, the second, those that don't. partition :: (a -> Bool) -> [a] -> ([a], [a]) (!!) :: [a] -> Int -> a -- Index of present element in list, maybe. elemIndex :: Eq a => a -> [a] -> Maybe Int -- Indices of all elements matching in list. elemIndices :: Eq a => a -> [a] -> [Int] -- Index of element matching predicate in list, maybe. findIndex :: (a -> Bool) -> [a] -> Maybe Int -- Indices of all elements matching predicate in list. findIndices :: (a -> Bool) -> [a] -> [Int] -- Zip lists together. zip :: [a] -> [b] -> [(a, b)] zip3 :: [a] -> [b] -> [c] -> [(a, b, c)] ... zip7 :: [a] -> [b] -> [c] -> ... -> [(a, b, c, d, e, f, g)] -- Zip lists together, using function. zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] ... zipWith7 :: (a -> b -> c -> d ...) -> [a] -> [b] -> ... -> [h] unzip :: [(a, b)] -> ([a], [b]) unzip3 :: [(a, b, c)] -> ([a], [b], [c]) ... unzip7 :: [(a, b, ...)] -> ([a], [b], ..., [g]) -- Splits string at newlines. lines :: String -> [String] -- Split string at whitespaces. words :: String -> [String] -- Joins strings with newlines. unlines :: [String] -> String -- Joins strings with spaces. unwords :: [String] -> String -- Remove duplicate elements from a list. nub :: Eq a => [a] -> [a] -- Remove first instance of matching element from a list. delete :: Eq a => a -> [a] -> [a] -- List difference: removes from first list one of each elements of second. (\\) :: Eq a => [a] -> [a] -> [a] -- Add to first list all elements from second not already present. union :: Eq a => [a] -> [a] -> [a] -- List of elements common to two lists. intersect :: Eq a => [a] -> [a] -> [a] sort :: Ord a => [a] -> [a] -- Insert element in front of first element where it is smaller or -- equal to next one. insert :: Ord a => a -> [a] -> [a] -- Similar to corresponding 'By'-less functions, but using a -- predicate. nubBy :: (a -> a -> Bool) -> [a] -> [a] deleteBy :: (a -> a -> Bool) -> a -> [a] -> [a] deleteFirstsBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] unionBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] intersectBy :: (a -> a -> Bool) -> [a] -> [a] -> [a] groupBy :: (a -> a -> Bool) -> [a] -> [[a]] sortBy :: (a -> a -> Ordering) -> [a] -> [a] insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a] maximumBy :: (a -> a -> Ordering) -> [a] -> a minimumBy :: (a -> a -> Ordering) -> [a] -> a -- Similar to corresponding 'generic'-less functions, but using Num -- or Integral instead of Int. genericLength :: Num i => [a] -> i genericTake :: Integral i => i -> [a] -> [a] genericDrop :: Integral i => i -> [a] -> [a] genericSplitAt :: Integral i => i -> [a] -> ([a], [a]) genericIndex :: Integral i => [a] -> i -> a genericReplicate :: Integral i => i -> a -> [a]
Data.Char synopsis
data Char :: * isControl :: Char -> Bool isSpace :: Char -> Bool isLower :: Char -> Bool isUpper :: Char -> Bool isAlpha :: Char -> Bool isAlphaNum :: Char -> Bool isPrint :: Char -> Bool isDigit :: Char -> Bool isOctDigit :: Char -> Bool isHexDigit :: Char -> Bool isLetter :: Char -> Bool isMark :: Char -> Bool isNumber :: Char -> Bool isPunctuation :: Char -> Bool isSymbol :: Char -> Bool isSeparator :: Char -> Bool isAscii :: Char -> Bool isLatin1 :: Char -> Bool isAsciiUpper :: Char -> Bool isAsciiLower :: Char -> Bool data GeneralCategory = UppercaseLetter | LowercaseLetter | TitlecaseLetter | ModifierLetter | OtherLetter | NonSpacingMark | SpacingCombiningMark | EnclosingMark | DecimalNumber | LetterNumber | OtherNumber | ConnectorPunctuation | DashPunctuation | OpenPunctuation | ClosePunctuation | InitialQuote | FinalQuote | OtherPunctuation | MathSymbol | CurrencySymbol | ModifierSymbol | OtherSymbol | Space | LineSeparator | ParagraphSeparator | Control | Format | Surrogate | PrivateUse | NotAssigned generalCategory :: Char -> GeneralCategory toUpper :: Char -> Char toLower :: Char -> Char toTitle :: Char -> Char digitToInt :: Char -> Int intToDigit :: Int -> Char ord :: Char -> Int chr :: Int -> Char showLitChar :: Char -> ShowS lexLitChar :: ReadS String readLitChar :: ReadS Char
Data.Function synopsis
id :: a -> a const :: a -> b -> a (.) :: (b -> c) -> (a -> b) -> a -> c flip :: (a -> b -> c) -> b -> a -> c ($) :: (a -> b) -> a -> b fix :: (a -> a) -> a (*) `on` f = \x y -> f x * f y on :: (b -> b -> c) -> (a -> b) -> a -> a -> c
Data.Map
Construct from a list:
let dMap = fromList [('a',1), ('b',2)]
Evaluates to a Maybe:
lookup 'a' dMap
Its show
function represents it with the string "fromlist " followed
by a list representation.
λ Data.Map.empty
fromlist []
Know at least about these functions:
fromList / toList
empty
insert
null
size
singleton
lookup
member
map
filter
keys / elems
fromListWith
insertWith
Data.Map synopsis
module Data.Map.Lazy insertWith' :: Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a insertWithKey' :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a insertLookupWithKey' :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> (Maybe a, Map k a) fold :: (a -> b -> b) -> b -> Map k a -> b foldWithKey :: (k -> a -> b -> b) -> b -> Map k a -> b
Data.Map.Lazy synopsis
data Map k a (!) :: Ord k => Map k a -> k -> a (\\) :: Ord k => Map k a -> Map k b -> Map k a null :: Map k a -> Bool size :: Map k a -> Int member :: Ord k => k -> Map k a -> Bool notMember :: Ord k => k -> Map k a -> Bool lookup :: Ord k => k -> Map k a -> Maybe a findWithDefault :: Ord k => a -> k -> Map k a -> a lookupLT :: Ord k => k -> Map k v -> Maybe (k, v) lookupGT :: Ord k => k -> Map k v -> Maybe (k, v) lookupLE :: Ord k => k -> Map k v -> Maybe (k, v) lookupGE :: Ord k => k -> Map k v -> Maybe (k, v) empty :: Map k a singleton :: k -> a -> Map k a insert :: Ord k => k -> a -> Map k a -> Map k a insertWith :: Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a insertWithKey :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a insertLookupWithKey :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> (Maybe a, Map k a) delete :: Ord k => k -> Map k a -> Map k a adjust :: Ord k => (a -> a) -> k -> Map k a -> Map k a adjustWithKey :: Ord k => (k -> a -> a) -> k -> Map k a -> Map k a update :: Ord k => (a -> Maybe a) -> k -> Map k a -> Map k a updateWithKey :: Ord k => (k -> a -> Maybe a) -> k -> Map k a -> Map k a updateLookupWithKey :: Ord k => (k -> a -> Maybe a) -> k -> Map k a -> (Maybe a, Map k a) alter :: Ord k => (Maybe a -> Maybe a) -> k -> Map k a -> Map k a union :: Ord k => Map k a -> Map k a -> Map k a unionWith :: Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a unionWithKey :: Ord k => (k -> a -> a -> a) -> Map k a -> Map k a -> Map k a unions :: Ord k => [Map k a] -> Map k a unionsWith :: Ord k => (a -> a -> a) -> [Map k a] -> Map k a difference :: Ord k => Map k a -> Map k b -> Map k a differenceWith :: Ord k => (a -> b -> Maybe a) -> Map k a -> Map k b -> Map k a differenceWithKey :: Ord k => (k -> a -> b -> Maybe a) -> Map k a -> Map k b -> Map k a intersection :: Ord k => Map k a -> Map k b -> Map k a intersectionWith :: Ord k => (a -> b -> c) -> Map k a -> Map k b -> Map k c intersectionWithKey :: Ord k => (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c mergeWithKey :: Ord k => (k -> a -> b -> Maybe c) -> (Map k a -> Map k c) -> (Map k b -> Map k c) -> Map k a -> Map k b -> Map k c map :: (a -> b) -> Map k a -> Map k b mapWithKey :: (k -> a -> b) -> Map k a -> Map k b traverseWithKey :: Applicative t => (k -> a -> t b) -> Map k a -> t (Map k b) mapAccum :: (a -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) mapAccumWithKey :: (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) mapAccumRWithKey :: (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) mapKeys :: Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a mapKeysWith :: Ord k2 => (a -> a -> a) -> (k1 -> k2) -> Map k1 a -> Map k2 a mapKeysMonotonic :: (k1 -> k2) -> Map k1 a -> Map k2 a foldr :: (a -> b -> b) -> b -> Map k a -> b foldl :: (a -> b -> a) -> a -> Map k b -> a foldrWithKey :: (k -> a -> b -> b) -> b -> Map k a -> b foldlWithKey :: (a -> k -> b -> a) -> a -> Map k b -> a foldMapWithKey :: Monoid m => (k -> a -> m) -> Map k a -> m foldr' :: (a -> b -> b) -> b -> Map k a -> b foldl' :: (a -> b -> a) -> a -> Map k b -> a foldrWithKey' :: (k -> a -> b -> b) -> b -> Map k a -> b foldlWithKey' :: (a -> k -> b -> a) -> a -> Map k b -> a elems :: Map k a -> [a] keys :: Map k a -> [k] assocs :: Map k a -> [(k, a)] keysSet :: Map k a -> Set k fromSet :: (k -> a) -> Set k -> Map k a toList :: Map k a -> [(k, a)] fromList :: Ord k => [(k, a)] -> Map k a -- (n*log n). Build a map from a list of key/value pairs with a combining function. fromListWith :: Ord k => (a -> a -> a) -> [(k, a)] -> Map k a fromListWithKey :: Ord k => (k -> a -> a -> a) -> [(k, a)] -> Map k a toAscList :: Map k a -> [(k, a)] toDescList :: Map k a -> [(k, a)] fromAscList :: Eq k => [(k, a)] -> Map k a fromAscListWith :: Eq k => (a -> a -> a) -> [(k, a)] -> Map k a fromAscListWithKey :: Eq k => (k -> a -> a -> a) -> [(k, a)] -> Map k a fromDistinctAscList :: [(k, a)] -> Map k a filter :: (a -> Bool) -> Map k a -> Map k a filterWithKey :: (k -> a -> Bool) -> Map k a -> Map k a partition :: (a -> Bool) -> Map k a -> (Map k a, Map k a) partitionWithKey :: (k -> a -> Bool) -> Map k a -> (Map k a, Map k a) mapMaybe :: (a -> Maybe b) -> Map k a -> Map k b mapMaybeWithKey :: (k -> a -> Maybe b) -> Map k a -> Map k b mapEither :: (a -> Either b c) -> Map k a -> (Map k b, Map k c) mapEitherWithKey :: (k -> a -> Either b c) -> Map k a -> (Map k b, Map k c) split :: Ord k => k -> Map k a -> (Map k a, Map k a) splitLookup :: Ord k => k -> Map k a -> (Map k a, Maybe a, Map k a) splitRoot :: Map k b -> [Map k b] isSubmapOf :: (Ord k, Eq a) => Map k a -> Map k a -> Bool isSubmapOfBy :: Ord k => (a -> b -> Bool) -> Map k a -> Map k b -> Bool isProperSubmapOf :: (Ord k, Eq a) => Map k a -> Map k a -> Bool isProperSubmapOfBy :: Ord k => (a -> b -> Bool) -> Map k a -> Map k b -> Bool lookupIndex :: Ord k => k -> Map k a -> Maybe Int findIndex :: Ord k => k -> Map k a -> Int elemAt :: Int -> Map k a -> (k, a) updateAt :: (k -> a -> Maybe a) -> Int -> Map k a -> Map k a deleteAt :: Int -> Map k a -> Map k a findMin :: Map k a -> (k, a) findMax :: Map k a -> (k, a) deleteMin :: Map k a -> Map k a deleteMax :: Map k a -> Map k a deleteFindMin :: Map k a -> ((k, a), Map k a) deleteFindMax :: Map k a -> ((k, a), Map k a) updateMin :: (a -> Maybe a) -> Map k a -> Map k a updateMax :: (a -> Maybe a) -> Map k a -> Map k a updateMinWithKey :: (k -> a -> Maybe a) -> Map k a -> Map k a updateMaxWithKey :: (k -> a -> Maybe a) -> Map k a -> Map k a minView :: Map k a -> Maybe (a, Map k a) maxView :: Map k a -> Maybe (a, Map k a) minViewWithKey :: Map k a -> Maybe ((k, a), Map k a) maxViewWithKey :: Map k a -> Maybe ((k, a), Map k a) showTree :: (Show k, Show a) => Map k a -> String showTreeWith :: (k -> a -> String) -> Bool -> Bool -> Map k a -> String valid :: Ord k => Map k a -> Bool
Data.Set synopsis
Know at least about these functions:
fromList / toList
intersection / difference
union
empty
insert
null
size
member
singleton
delete
map / filter
data Set a (\\) :: Ord a => Set a -> Set a -> Set a null :: Set a -> Bool size :: Set a -> Int member :: Ord a => a -> Set a -> Bool notMember :: Ord a => a -> Set a -> Bool lookupLT :: Ord a => a -> Set a -> Maybe a lookupGT :: Ord a => a -> Set a -> Maybe a lookupLE :: Ord a => a -> Set a -> Maybe a lookupGE :: Ord a => a -> Set a -> Maybe a isSubsetOf :: Ord a => Set a -> Set a -> Bool isProperSubsetOf :: Ord a => Set a -> Set a -> Bool empty :: Set a singleton :: a -> Set a insert :: Ord a => a -> Set a -> Set a delete :: Ord a => a -> Set a -> Set a union :: Ord a => Set a -> Set a -> Set a unions :: Ord a => [Set a] -> Set a difference :: Ord a => Set a -> Set a -> Set a intersection :: Ord a => Set a -> Set a -> Set a filter :: (a -> Bool) -> Set a -> Set a partition :: (a -> Bool) -> Set a -> (Set a, Set a) split :: Ord a => a -> Set a -> (Set a, Set a) splitMember :: Ord a => a -> Set a -> (Set a, Bool, Set a) splitRoot :: Set a -> [Set a] lookupIndex :: Ord a => a -> Set a -> Maybe Int findIndex :: Ord a => a -> Set a -> Int elemAt :: Int -> Set a -> a deleteAt :: Int -> Set a -> Set a map :: Ord b => (a -> b) -> Set a -> Set b mapMonotonic :: (a -> b) -> Set a -> Set b foldr :: (a -> b -> b) -> b -> Set a -> b foldl :: (a -> b -> a) -> a -> Set b -> a foldr' :: (a -> b -> b) -> b -> Set a -> b foldl' :: (a -> b -> a) -> a -> Set b -> a fold :: (a -> b -> b) -> b -> Set a -> b findMin :: Set a -> a findMax :: Set a -> a deleteMin :: Set a -> Set a deleteMax :: Set a -> Set a deleteFindMin :: Set a -> (a, Set a) deleteFindMax :: Set a -> (a, Set a) maxView :: Set a -> Maybe (a, Set a) minView :: Set a -> Maybe (a, Set a) elems :: Set a -> [a] toList :: Set a -> [a] fromList :: Ord a => [a] -> Set a toAscList :: Set a -> [a] toDescList :: Set a -> [a] fromAscList :: Eq a => [a] -> Set a fromDistinctAscList :: [a] -> Set a showTree :: Show a => Set a -> String showTreeWith :: Show a => Bool -> Bool -> Set a -> String valid :: Ord a => Set a -> Bool
References and Documentation
I need to study
Modules:
Prelude
Data.[String Char List Map Maybe]
System.[IO Directory Environment]
Abbreviations
- GADT
-
Generalized algebraic data type. An Alg.DT can have more than one value constructor.
- WHNF
-
http://stackoverflow.com/questions/6872898/haskell-what-is-weak-head-normal-form [Weak head normal form], stackoverflow explanation.
Community
Haskellers Montreal Google group.
There is a #haskell channel on irc.freenode.net. lambdabot can respond to requests:
@help
@where exercises
...
:t pure
Applicative f => a -> f a
Evaluate expression.
> 1 + 4
5
@src foldr
foldr f z [] = z
foldr f z (x:xs) = f x (foldr f z xs)
Attempt to convert to point free.
@pl foldr (\a b -> f a : b) []
foldr ((:) . f) []
Given a type, it generates a value of that type.
?djinn a -> (b -> a) -> Maybe b -> a
16:01 < quchen> ?djinn a -> (b -> a) -> Maybe b -> a
16:01 < lambdabot> f a b c =
16:01 < lambdabot> case c of
16:01 < lambdabot> Nothing -> a
16:01 < lambdabot> Just d -> b d
16:01 < sinelaw> @djinn (a->b) -> (a->c) -> (a,a) -> (b,c)
16:01 < lambdabot> f a b (c, _) = (a c, b c)
16:01 < ReinH> @djinn (a -> b -> c) -> (a -> b) -> (a -> c)
16:01 < lambdabot> f a b c = a c (b c)
16:02 < ReinH> Here's (<*>) for ((->) e)
16:02 < ReinH> @. pl djinn (a -> b -> c) -> (a -> b) -> (a -> c)
16:02 < lambdabot> f = ap
Folds
Folds and parallelism, by Bryan O’Sullivan.
References
Hayoo!, Haskell API Search, searches more packages than Hoogle.
"A History of Haskell: Being Lazy With Class" "This paper describes the history of Haskell, including its genesis and principles, technical contributions, implementations and tools, and applications and impact."
GHC latest doc: links to "User’s Guide", librairies, API (older GHC 7.4 docs for example).
Hackage, Haskell package repo.
A curated list of Haskell frameworks, libraries and software.
C.A.McCann provides well written Haskell information at StackOverflow.
An upcoming book by Chris Allen
Tools
The Haskell Platform, "a comprehensive, robust development environment for programming in Haskell".
Vim add-on, by Marc Weber
Lambda Bubble Pop!, nice interactive tool.
Various topics
Algorithm Design" is the best guide to how to "think" like a haskeller.
Write You a Monad for No Particular Reason at All!, by Dmitry Geurkov.
Haskell retrospective, ~2005, by Simon Peyton-Jones.
Haskell IO Without the M-word, by Kevin Mahoney.
"Combinator libraries (also, comonads!)", presentation by Samuel Gélineau.
Functors, by Bartosz Milewski.
Announcing the first class records library, by Nikita Volkov.
Currying tutorial slides.
Techniques for Embedding Postfix Languages in Haskell, by Chris Okasaki.
How to desugar Haskell code, by Gabriel Gonzalez.
Theorems for free!, by Philip Wadler.
On roles and GeneralizedNewtypeDeriving, by Richard Eisenberg. make GND type-safe.
The Functor Design Pattern, by Gabriel Gonzalez.
Equational reasoning at scale, by Gabriel Gonzalez.
Towards understanding Haskell’s monomorphism restriction, by Jan Stolarek.
Yet Another Monad Tutorial, by Mike Vanier.
Monad transformers talk at Austin, TX Haskell meetup, given by Chris Allen.
Monoids: Theme and Variations (Functional Pearl), uses examples taken from the diagrams vector graphics framework.
Haskell cast #5 (1h05m), with Brent Yorgey (rendu à 6m49s).
Learning
Foldable and Traversable, by Jakub Arnold.
Uses JavaScript.
http://drboolean.gitbooks.io/mostly-adequate-guide/content/
http://unbui.lt/?escaped_fragment=/post/haskell-language-extensions/#!/post/haskell-language-extensions/
Reflex: Practical Functional Reactive Programming (part 1), a talk by Ryan Trinkle. (part 2)
"How to Sell Excellence", Chicago Haskell Meetup presentation slides by Michael O. Church, March 19, 2015.
"Yet Another Haskell Tutorial", by Hal Daumé III.
CIS 194: Introduction to Haskell (Spring 2013), by Brent Yorgey.
Brent Yorgey’s Introduction to Haskell.
Tony Morris course.
"Learn you a Haskell for Great Good — A Beginner’s Guide", by Miran Lipovača.
Typeclassopedia, by Brent Yorgey.
Solutions to some exercises in the Typeclassopedia.
"Real World Haskell", by Bryan O’Sullivan, Don Stewart, and John Goerzen.
Tutorial by Chris Allen.
"What I Wish I Knew When Learning Haskell 2.1", by Stephen Diehl.