Skip to content

Instantly share code, notes, and snippets.

@shapr
Created April 28, 2022 22:19
Show Gist options
  • Save shapr/065789011dcb1a79c8119010c7aa2bd6 to your computer and use it in GitHub Desktop.
Save shapr/065789011dcb1a79c8119010c7aa2bd6 to your computer and use it in GitHub Desktop.
module Demo where
-- notice many of these don't have type signatures.
-- Haskell is smart enough figure out 99% of the type signatures for you.
-- any type signatures here are just to add clarity.
-- number
somenumber = 1
-- string
somestring = "somestring"
-- type signature
add1 :: Int -> Int
-- function definition for that type sig
add1 x = x + 1
-- anonymous function (we give this one a name anyway)
add2 = (\x -> x + 2)
-- multi-arg function
add :: Int -> (Int -> Int)
add x y = x + y
-- since -> in a type signature is right associative
-- the type signature above really means add :: Int -> ( Int -> Int )
-- since the type of a function from a to b is (a -> b)
-- that means you can give one argument, and get back a new function
-- that's called partial application of a function
-- partial application
addOne :: Int -> Int
addOne = add 1
-- datatype
data Temp = Cold | Hot
data Season = Winter | Spring | Summer | Fall deriving (Show,Enum)
-- 'Show' is how you turn a value into a string for display
mySeason :: Season
mySeason = Summer
-- type aliases
type Name = String
type Age = Int
-- more complex types
data People = Person Name Age
-- polymorphic (parameterized) datatype
data Tree a = Nil | Node (Tree a) a (Tree a) deriving Show
myTree :: Tree Int
myTree = Node Nil 1 Nil
myOtherTree :: Tree Season
myOtherTree = Node Nil Winter (Node Nil Summer Nil)
-- pattern matching
-- each time the function is called, each line is tried in turn,
-- the first matching left hand side gets to execute its right hand side
mylength [] = 0
mylength (x:xs) = 1 + mylength xs
-- the second line with the (x:xs) construct above means that if a list is passed to mylength
-- the first item of the list is assigned to x, and the rest of the list is assigned to xs
-- you can try the mylength function above by typing this into hugs or ghci:
-- mylength [1,2,3]
-- more pattern matching
-- the underscore matches anything at all
weather :: Season -> Temp
weather Summer = Hot
weather _ = Cold
-- where clauses introduce definitions local to a function.
ackermann :: Int -> Int
ackermann n = ack n n -- (Peter's variant of the Ackermann function)
where
ack 0 m = m+1
ack n 0 = ack (n-1) 1
ack n m = ack (n-1) (ack n (m-1))
-- Typeclasses let you define the same operations on different types
-- the operators equal to ( == ) and not equal to ( /= ) are in the typeclass Eq
instance Eq Temp where
Cold == Cold = True
Hot == Hot = True
_ == _ = False
-- Eq is a built-in typeclass for checking equality, let's define our own typeclass
-- this isn't a very useful typeclass, because it can't sensibly be defined for anything other than Char
-- something like class XML would be more useful, and could be defined for every type
class CharExts a where
isVowel :: a -> Bool
isConsonant :: a -> Bool
instance CharExts Char where
isVowel a = elem a "aeiouAEIOU"
isConsonant a = elem a (filter (not . isVowel) ['A'..'Z'] ++ ['a'..'z'])
-- short demonstration of guards
-- each conditional expression is tried in turn
guard x | x == 0 = 4
| (x*x) < 64 = 5
| otherwise = 6
-- Lazy computation example
-- Evaluation will bounce back and forth between the two infinite lists computing each element.
ones = 1 : ones
odds = 1 : map (+1) evens
evens = map (+1) odds
-- Larger cheesy typeclass example
-- class XML a where
-- toXML :: a -> XML
-- sortBy (\(Person n a) (Person n a)->
-- --
-- birthday :: Person -> Person
-- birthday (Person n a) = Person n (a+1)
-- it doesn't exist
-- data Maybe a = Just a | Nothing
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment