Reference card
General Syntax[edit]
Comments[edit]
{- A multiline comment which can continue for many lines -}
-- a single line comment
Conditionals[edit]
if[edit]
if conditional then truePart else falsePart if a == 12 then 14 else 22
case[edit]
case exp of Pattern1 -> action1 Pattern2 -> action2 _ -> else_action
case x of [] -> 0 [x] -> 1 _ -> -1
Function pattern matching[edit]
f [ ] = 0 f [x] = 1 f _ = -1
Function conditionals (guards)[edit]
f x | x == [] = 1 | length x == 12 = 15 | otherwise = -1
Saving work[edit]
where[edit]
f x = i * i where i = g x
let in[edit]
f x = let i = g x in i * i
Declaring types[edit]
data[edit]
data List = Cons Int List | Nil deriving (Eq, Show, Ord)
type (type synonymns)[edit]
type String = [Char] type Name = TypeValue
class[edit]
class Check a where test :: a -> Bool force :: a -> a
instance[edit]
instance Show List where show x = "No show"
Calling functions[edit]
Named functions[edit]
myFunc :: Int -> Int -> Int result = myFunc 1 2 result = 1 `myFunc` 2 result = (myFunc 1) 2 result = (`myFunc` 2) 1
Operators (and sections)[edit]
(+) :: Int -> Int -> Int result = 1 + 2 result = (+) 1 2 result = (1 +) 2 result = (+ 2) 1
Useful functions[edit]
myFunc 1 2 == (flip myFunc) 2 1 (f . g) x == f (g x) f (a+b) == f $ a+b
Lambda Expressions[edit]
myFunc = (\ a b -> a + b) result = map (\x -> head x) xs
List Expressions[edit]
..[edit]
[1..] = [1,2,3,4,5,6... [1..5] = [1,2,3,4,5] [1,3..5] = [1,3,5]
List Comprehensions[edit]
[ x*x | x <- [1..3] ] ==> [1,4,9] [ (x, y) | x <- [1..3], y <- "ab"] ==> [(1,'a'),(1,'b'),(2,'a'),(2,'b'),(3,'a'),(3,'b')] [ (x,y) | x <- [1..4], even x, y <- "ab" ] ==> [(2,'a'),(2,'b'),(4,'a'),(4,'b')] map f xs ==> [ f x | x <- xs ] filter p xs ==> [ x | x <- xs, p x ]
Hello World[edit]
main = putStrLn "Hello World"
Snippets[edit]
fst3 :: (a, b, c) -> a[edit]
snd3 :: (a, b, c) -> b thd3 :: (a, b, c) -> c
fst3 (x,_,_) = x snd3 (_,x,_) = x thd3 (_,_,x) = x
ordPair :: Ord a => a -> a -> (a, a)[edit]
ordPair x y = if x < y then (x, y) else (y, x)
lenXX# :: [a] -> Bool[edit]
lenEq0 = null lenNe0 = not . null
lenEq1 [x] = True lenEq1 _ = False
lenGt1 [x] = False lenGt1 [ ] = False lenGt1 _ = True
sortUnique :: Ord a => [a] -> [a][edit]
sortUnique [] = [] sortUnique [x] = [x] sortUnique xs = mergeUnique (sortUnique a) (sortUnique b) where (a,b) = split xs
split :: [a] -> ([a], [a])[edit]
split [] = ([], []) split [a] = ([a], []) split (a:b:xs) = (a:as, b:bs) where (as,bs) = split xs
mergeUnique :: Ord a => [a] -> [a] -> [a][edit]
Precondition:
isUnique(#1) && isUnique(#2)
mergeUnique a [] = a mergeUnique [] b = b mergeUnique (a:as) (b:bs) = case compare a b of EQ -> a: mergeUnique as bs LT -> a: mergeUnique as (b:bs) GT -> b: mergeUnique (a:as) bs
fix :: Eq a => (a -> a) -> a -> a
fix f x = if x == x' then x else fix f x' where x' = f x
Command lines[edit]
For hmake[edit]
hmake Test hmake -realclean Test
Where Test is the name of the executable you want to build, i.e. where Test.hs contains the main function.
For ghc --make[edit]
ghc --make MainModule.hs -o ModuleExec ghc --make Module.hs
Where ModuleExec is the name of the output binary you want to make (if main is exported). Module.o will be output for Module.hs, if main is not exported.
Others[edit]
runhaskell Test.hs
echo main | ghci -v0 Test.hs
#! notation[edit]
You can also just make single Haskell main modules executable, using a combination of runhaskell and #! notation:
#!/usr/bin/env runhaskell main = putStrLn "hello"
Save this to a .hs file and then make this file executable:
chmod +x Test.hs
You can now execute this as a normal `script' file:
$ ./Test.hs hello