-- This file contains both notes and code that you can compile and play with. -- Use ghci, the interactive version of the ghc compiler, to load this file and -- play around: run "ghci " from your terminal -- -- In ghci you can execute expressions, make definitions, and ask about -- information about definitions. typing ":i Monoid" after loading this file -- will report all the information about the Monoid definition. ":t listSum" -- will give you the type of the listSum definition. -- -- You can also execute a Haskell file by running "runhaskell ". If -- you run this file you should see "Help I'm stuck in a monad!" printed to -- your terminal. -- -- The next three paragraphs are just comments about why these lines exist, but -- they aren't necessary for you to read. -- -- Start reading just after "import Data.Char" -- -- Author: David Darais -- Date: 4/12/2013 for cs152 -- ---------------------------------------------------------------------------- -- -- This line enables a Haskell extension which allows you to make type classes -- instances over type synonyms. It's used in this file to make String a -- monoid. Use of extensions like this is standard, and the type checker will -- tell you exactly which extension to enable if you leave this line out (try -- it!). It is common to need to use extensions because Haskell as defined is -- very different from advanced Haskell compilers today, and people still want -- to know if a Haskell file is compatible with the old standard or not. {-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-} -- The Prelude module is implicitly imported by every Haskell program. It -- contains all the very basic functions and types you would expect to come -- with a language, like numbers and lists. -- -- Here, we are explicitly importing the Prelude, which is redundant, but -- specifically hiding certain types that it exports. This is because we will -- be giving our definitions for these types. The definitions we will give are -- identical to the ones in the Prelude; we do it only for demonstration. import Prelude hiding (Maybe(..),Functor(..),lookup) -- One example uses toUpper from Data.Char import Data.Char -- The Maybe type represents failure or a successful result of type 'a'. -- -- In OCaml, this would be written: -- > type 'a option = None | Some of 'a data Maybe a = Nothing | Just a -- A quick note. Haskell has a 'type' declaration in addition to 'data'. -- 'type' is a type _alias_, not a declaration of a new datatype, similar to an -- OCaml type where you don't define constructors. -- -- In OCaml, this would be written: -- > type int_list = int list type IntList = [Int] -- The Haskell list type is special syntax. If we could define it it would look -- like this, but we can't because the syntax isn't supported: -- > data [a] = [] | a : [a] -- -- In Haskell you can use any function infix: -- > x `op` y == op x y -- -- and you can use infix operators prefix: -- > (+) x y == x + y -- -- In Haskell, :: used for 'of type' and : for list construction. -- OCaml uses : for 'of type' and :: for list construction -- (OCaml is the better design here IMO) -- A recursive function adding numbers in a list listSum :: [Integer] -> Integer listSum [] = 0 listSum (x:xs) = x + listSum xs -- This style, giving a new function definition for each case, is the idiomatic -- way to define recursive functions in Haskell. -- -- It is just sugar for the the following: listSum' :: [Integer] -> Integer listSum' lst = case lst of [] -> 0 x:xs -> x + listSum' xs -- Also note that Haskell is whitespace sensitive, like python, so we don't -- need to put any | delimiters in the case expression. An OCaml version of -- the above function would look like: -- > let listSum (xs:int list) : int = -- > match xs with -- > | [] -> 0 -- > | x :: xs -> x + listSum xs -- or -- > let listSum = function -- > | [] -> 0 -- > | x :: xs -> x + listSum xs ----- Monoids ----- -- Monoids are the abstract idea of something having a kind of addition, and a -- unit element for the addition. If you know what a group is, a monoid is a -- group without an inverse. class Monoid g where mempty :: g mappend :: g -> g -> g -- Don't forget the laws! -- left identity : mappend mempty x = x -- right identity : mappend x mempty = x -- associativity : mappend (mappend x y) z = mappend x (mappend y z) -- What are the types of mempty and mappend? -- in ghci, the interactive interpreter, -- type ":t mempty" and ":t mappend" -- -- mempty :: (Monoid g) => g -- mappend :: (Monoid g) => g -> g -> g -- The instance for Int being a monoid over addition instance Monoid Integer where mempty = 0 mappend x y = x + y -- The instance for String being a monoid over concatenation instance Monoid String where mempty = "" mappend x y = x ++ y -- There are many many more monoids. Booleans, finite sets, the list goes -- on... -- We now get overloading ten :: Integer ten = mappend 2 8 helloWorld :: String helloWorld = mappend "hello" "world" -- Even better, we are able to abstract over monoidal arguments -- Consider the two functions which look exactly the same: listSumAgain :: [Integer] -> Integer listSumAgain [] = mempty listSumAgain (x:xs) = x `mappend` listSumAgain xs listCat :: [String] -> String listCat [] = mempty listCat (x:xs) = x `mappend` listCat xs -- We only need to write this function once, and it will work for all monoids. mconcat :: (Monoid g) => [g] -> g mconcat [] = mempty mconcat (x:xs) = x `mappend` mconcat xs -- Question: what is the type of (mconcat [])? type ":t (mconcat [])" into ghci -- to find out! ----- Functors ----- -- Functors are containers which can contain any other type. Functors are not -- yet types until they are applied to another type. For example, Maybe is a -- functor, but there are no values of type Maybe, there are only values of -- type (Maybe Int) or (Maybe a) for any type a. Functors are these -- not-yet-fully-types that allow you to manipulate the element(s) inside. class Functor t where fmap :: (a -> b) -> t a -> t b -- Don't forget the laws! -- identity : fmap id = id -- composition : fmap g . fmap f = fmap (g . f) -- There are tons of functors! instance Functor Maybe where fmap f Nothing = Nothing fmap f (Just a) = Just (f a) instance Functor [] where fmap f [] = [] fmap f (x:xs) = f x:fmap f xs -- There are many more functors. Finite sets and maps, conjunctions, -- disjunctions; even functions themselves are functors! -- Using the overloaded fmap function squares :: [Int] squares = fmap (\x -> x * x) [1, 2, 3] -- Note than in Haskell String = [Char] -- -- toUpper :: Char -> Char upperCase :: String -> String upperCase = fmap toUpper -- Again, type classes give you more than just overloading double :: (Monoid g, Functor t) => t g -> t g double t = fmap (\x -> x `mappend` x) t -- double (Just 3) = (Just 6) -- double ["Hello","World"] = ["HelloHello","WorldWorld"] ----- Monads ----- -- "A Monad is just a monoid in the category of endofunctors" -- --James Iry (fictional attribution to Wadler) -- "We should have called them 'warm-fuzzy-things'" --Simon Peyton-Jones -- -- If functors are an abstraction for containers, monads are an abstraction for -- computations; in particular, for computations that may have effects. -- Haskell is a pure functional language, which means arbitrary functions can't -- have arbitrary effects. If you want to have an effect in Haskell you have to -- use a monad, which forces the effect to show up in the type of the function -- (a good thing). -- -- I can't hide the definition of Monad from the Prelude and introduce it here -- because Haskell do-notation (introduced in a bit) desugars to the definition -- of Monad in the Prelude. If we did define Monad here it would look like this: -- -- > class Monad m where -- > return :: a -> m a -- > (>>=) :: m a -> (a -> m b) -> m b -- -- The (>>=) operator is called bind. -- -- It's worth noting that if you flip the arguments of bind and you get -- something that looks very close to functor: -- > extend :: (a -> m b) -> m a -> m b -- Don't forget the laws! -- left identity : bind (return x) k = k x -- right identity : bind aM return = aM -- associativity : bind (bind aM j) k = bind aM (\a -> bind (j a) k) -- -- -- aside... -- If you think the fact that both Monoids and Monads have the same three laws -- is a coincidence, it's not. Monads are Monoids in the category of -- endofunctors, and you can actually define Monoid in a sufficiently general -- way so that Monads pop out as an instance specialized to endofunctors. -- Monads look weird. Why would you ever use them? -- Here is an example that is begging for using the Maybe monad. salaryDiff :: String -> String -> [(String, Integer)]-> Maybe Integer salaryDiff p1 p2 salaries = case lookup p1 salaries of Nothing -> Nothing Just s1 -> case lookup p2 salaries of Nothing -> Nothing Just s2 -> Just (abs (s1 - s2)) -- We still need to define lookup. It does what you expect. The (Eq k) -- constraint requires that the key type is comparable. lookup :: (Eq k) => k -> [(k,v)] -> Maybe v lookup _ [] = Nothing lookup k ((k',v'):kvs) = if k == k' then Just v' else lookup k kvs -- This is ugly and boring. What is the pattern? -- > case e of -- > Nothing -> Nothing -- > Just x -> f x -- Let's define the combinator: callMeMaybe :: Maybe a -> (a -> Maybe b) -> Maybe b callMeMaybe e f = case e of Nothing -> Nothing Just x -> f x instance Monad Maybe where return = Just (>>=) = callMeMaybe -- Let's rewrite salaryDiff using callMeMaybe: salaryDiff' :: String -> String -> [(String, Integer)] -> Maybe Integer salaryDiff' p1 p2 salaries = lookup p1 salaries `callMeMaybe` \ s1 -> lookup p2 salaries `callMeMaybe` \ s2 -> Just (abs (s1 - s2)) -- Let's add just a bit more syntactic sugar: do-notation. -- do-notation is purely syntactic, and expands as follows: -- -- do e1 >>= \ x -> -- x <- e1 => do -- e2 e2 -- -- and -- -- do e => e -- remember, everything is still pure, and partiality is specified in the type -- (as opposed to a solution with exceptions) salaryDiff'' :: String -> String -> [(String, Integer)] -> Maybe Integer salaryDiff'' p1 p2 salaries = do s1 <- lookup p1 salaries s2 <- lookup p2 salaries return (abs (s1 - s2)) -- That looks so much better! -- There are so many more monads. State, Reader, Writer, Continuation, Error, -- IO, Nondeterminism, Probability... the list goes on. -- -- The next assignment will involve programming with monads in Haskell, so make -- sure you understand everything this file covers. -- The execution of a Haskell file always calls main, which is expected to be -- of type "IO ()". IO is the monad that gets to interact with the outside -- world, such as printing. -- -- putStrLn is the printing function that also appends a newline after it -- prints. -- putStrLn :: String -> IO () main :: IO () main = putStrLn "Help I'm stuck in a monad!"