class: center, middle, transition, intro # A Taste of Haskell for
Scala Programmers .caption[Daniel Beskin] ??? - This talk will be about the language Haskell - I'm a bit ambitious with what I want to show you today, so be prepared to be fire-hosed with lots of code - Hopefully, this will give you a taste of what it feels like to program in Haskell --- class: center, middle, transition .xkcd[![](xkcd.png)] ??? - Here's the mandatory XKCD comic - It's a common misconception that Haskell is this ivory tower language, that has no practical use - So to sort this point out --- class: center, middle .bigCode[`main = putStrLn "Hello World!"`] ??? - This code does exactly what you'd expect - Which proves once and for all that Haskell really is a practical language --- layout: true ## What? --- - Haskell is a standardized, general-purpose purely functional programming language, with non-strict semantics and strong static typing ??? - Although very accurate, it doesn't really convey the spirit of the language - It makes it more academic rather than a real programming language --- - ~~Haskell is a standardized, general-purpose purely functional programming language, with non-strict semantics and strong static typing~~ ??? - Let's try again -- - Haskell is a programming language, you can Get Stuff Done™ with it --- layout: false ## Why? - Influence on Scala - The "missing documentation" for Scalaz - Better suited for pure functional programming - A reading language ??? - There is quite a bit of influence Haskell on Scala, e.g. the type system or for comprehensions - Learning Haskell might improve one's understanding of these concepts in Scala - Many things in Scalaz are ports of similar Haskell code, learning Haskell can help with figuring out Scalaz - For example, theres's a Haskell site called Typeclassopedia that can help with the Scalaz typeclass hierarchy - Since Haskell does not try to blend FP with OO, it's much better suited for pure FP than Scala - Sometimes it's easier to figure out some FP concept in Haskell and then port it to Scala, rather than trying to learn it directly in Scala - Because of the above, a lot of FP related advances (research or just blog posts) are being done in Haskell - Learning to read Haskell can open up a whole world of reading material on these topics --- ## How? - A toy regex engine - `twitter-grep`, a small server that: * Accepts GET (@twitter-name, regex) * Fetches @twitter-name timeline * Filters timeline with the regex expression * Serves an HTML page with the results - No Fibonacci! ??? - This is going to be an example driven tutorial - The aim is not to be a comprehensive introduction to Haskell, but rather to convey the feeling of programming in Haskell - The talk will be in two parts, first the more instructive one, where we'll implement some well known stuff on our own - Specifically, we'll write our own toy regex engine, this will be most of the talk - This will give us an opportunity to do some non-trivial Haskell code - Then we'll try to build a "real world" application, with all sorts of side effects and things - The application: accepts GET requests with a Twitter user name and a regex-like expression - Fetches the user's Twitter timeline via the Twitter API - Filters out the tweets that do not match the regex expression - Produces an HTML page with the resulting tweets - In the second part, where we actually setup our server, we'll be using any available library that fits our purposes - Despite the stereotypes, this is rather simple, so it won't take us much to implement - So no Fibonacci --- class: center, middle, transition Haskell Syntax Primer .tweet[![](tweet_syntax.png)] ??? - But first, a quick tour of Haskell syntax - This by no means a full introduction to Haskell syntax - It should be enough that you'll be able to follow along with the examples we're going to see further down the road --- ## Definitions ``` x = 3 y = 3 + x name = "Keyser Soze" {{content}} ``` ??? - A Haskell program is made up of definitions - The simplest kind are just constants -- addLists ls1 ls2 = ls1 ++ ls2 {{content}} ??? - Next there are functions - Note that function arguments do not require parentheses -- addLists [1, 2, 3] [4, 5] -- [1, 2, 3, 4, 5] {{content}} ??? - We apply functions by juxtaposition - A double dash is a comment in Haskell -- map f ls = case ls of [] -> [] h:t -> f h : map f t {{content}} ??? - We can define the familiar `map` function - Haskell has built-in syntax for lists, and we can do pattern matching on using a `case` expression -- map f [] = [] map f (h:t) = f h : map f t ??? - Another way of doing pattern matching, is by splitting the function definitions into the relevant cases - Both ways are equivalent - So far, we didn't mention any types anywhere - This is possible, since unlike Scala, Haskell has *global* type inference - So it is almost always possible (but not always recommended) to omit type signatures and the compiler just infers it - If we actually let the compiler infer the types we get the following: --- ## Definitions ``` x :: Integer x = 3 y :: Integer y = 3 + x name :: [Char] name = "Keyser Soze" addLists :: [a] -> [a] -> [a] addLists ls1 ls2 = ls1 ++ ls2 addLists [1, 2, 3] [4, 5] -- [1, 2, 3, 4, 5] map :: (a -> b) -> [a] -> [b] map f ls = case ls of [] -> [] h:t -> f h : map f t map :: (a -> b) -> [a] -> [b] map f [] = [] map f (h:t) = f h : map f t ``` ??? - From which we can learn a number of things - Type signatures use a double colon and are written separately - The default Haskell strings are just lists of characters, and can be treated as such (`String` is just a synonym for `[Char]`) - Lower case letters in a type signature act as type parameters - From the signature of both `addLists` and `map` we see that the functions in Haskell are curried by default - This actually works very nicely with function application syntax - Let's see an example --- ## Partial Application ``` map :: (a -> b) -> [a] -> [b] mapPlusTwo :: [Integer] -> [Integer] mapPlusTwo = map (\x -> x + 2) {{content}} ``` ??? - Here we apply `map` to its first argument - The slash syntax stands for an anonymous function - As we can see, this produces a new function, where we already used `map`'s first argument - There a nicer way to write the same thing -- mapPlusTwo = map (+ 2) {{content}} ??? - The parenthesis partially applies the `+` operator - And we can apply `mapPlusTwo` to a list and get the expected result - Let's move on to some more syntax - We've seen a number of operators thus far, Haskell actually lets us define operators on our own -- mapPlusTwo [1, 2, 3] -- [3, 4, 5] --- ## Custom Operators ``` ($) :: (a -> b) -> a -> b f $ x = f x {{content}} ``` ??? - We can define custom operator in Haskell, just like any function - This is the function application operator, it's defined in Haskell Prelude (which is like Scala's Predef) and imported by default - It might seem useless, but because of its defined with low precedence, and this allows us to save some parenthesis - Suppose we want to write: -- map (+ 2) (filter (3 <) [1, 2, 3, 4, 5]) -- [6, 7] {{content}} ??? - Here we are first filtering a list and then mapping it - With the application operator we can write: -- map (+ 2) $ filter (3 <) [1, 2, 3, 4, 5] ??? - This concludes the basic syntax - Let's move on to type definitions - There are a number of ways to define types in Haskell - But first let's start with a Scala example --- ## Algebraic Data Types ```scala type User = String sealed trait TwitterAPI case class Timeline(user: User, count: Int) extends TwitterAPI case class StatusUpdate(user: User, status: String) extends TwitterAPI case class Search(query: String) extends TwitterAPI ``` ??? - This should be fairly familiar code - We have a type synonym and an algebraic data type - In this case this is a simplistic representation of the Twitter API - We have three cases, each corresponds to an action in the API - Each action takes some arguments - Now for the (sort of) equivalent Haskell code --- ## Algebraic Data Types ``` type User = String data TwitterAPI = Timeline User Integer | StatusUpdate User String | Search String deriving (Eq, Show) {{content}} ``` ??? - There's a lot less noise here - The `deriving` bit is optional, but is provides the Haskell equivalent of `toString` and `equals` - This is done via typeclasses, which we'll discuss soon - Each case defines a constructor function, taking arguments of the specified types - They can be used as follows - We also get pattern matching for free (just like with case classes) -- timeline :: TwitterAPI timeline = Timeline "Keyser" 15 update :: TwitterAPI update = StatusUpdate "Keyser" "And like that... he's gone" search :: TwitterAPI search = Search "Who is Keyser Soze?" ??? - Note that, unlike Scala, there is no subtyping here, so all values have the same type, `TwitterAPI` - Let's move on to typeclasses - But first, a reminder of typeclasses in Scala - We can encode typeclasses in Scala in the following way - Suppose we want a `Functor` typeclass --- ## Typeclasses ```scala trait Functor[F[_]] { def map[A, B](fa: F[A])(f: A => B): F[B] } def addWorld[F[_]](fs: F[String])(implicit f: Functor[F]): F[String] = f.map(fs)(_ + " World!") {{content}} ``` ??? - First we define a trait with the `Functor` methods - In this case, mapping inside some container-like type - And now we can write a method that is generic in the `Functor` instance -- implicit val optionFunctor = new Functor[Option] { def map[A, B](opt: Option[A])(f: A => B) = opt map f } addWorld(Option("Hello")) // Some(Hello World!) ??? - Next we create an instance of the typeclass for the `Option` type constructor - And use it with the generic function - Typeclasses were actually invented for Haskell, and so it has special syntax for it - For example, the `Functor` typeclass is the defined as follows --- ## Typeclasses ``` class Functor f where fmap :: (a -> b) -> f a -> f b {{content}} ``` ??? - This can be read as: the typeclass `Functor` accepts a type constructor `f` and has one method, `fmap` - `fmap` take a function from `a` to `b`, then an instance of `f` of `a`, and produces an `f` of `b` - Note that Haskell is inferring that `f` is a type constructor and not a simple type, it can be seen from the usage of `f` in `fmap` - The name of `fmap` is not `map` for historical reasons - This typeclass is part of the standard library - As in the Scala case, we can write a function that is generic in the typeclass instance -- addWorld :: Functor f => f String -> f String addWorld fs = fmap (++ " World!") fs {{content}} ??? - The part before the thick arrow is the typeclass constraint - Which can be read as: given that there is an instance of `Functor` for `f`, do the following - When we specify the typeclass constraint it automatically brings the relevant methods into scope - So we have access to `fmap`, which is chosen by the compiler to be the right one - Similar to how Scala's implicits work -- data Maybe a = Just a | Nothing deriving (Eq, Show) instance Functor Maybe where fmap f (Just x) = Just $ f x fmap _ Nothing = Nothing addWorld $ Just "Hello" -- Just "Hello World!" ??? - We can now make an instance of `Functor` for `Maybe` the Haskell equivalent of `Option` - First the definition of `Maybe`, which is the same as the algebraic data types we've seen before, except that it has a type parameter - We just go by cases of `Maybe`, and apply `f` when it's possible - Let's do a slightly more complicated example - The `Applicative` typeclass, it's not that common in Scala, probably because the syntax does not work that well with it - But it is the typeclasses behind Scalaz's `Validation` - It is roughly defined like this: --- ## More Typeclasses ``` class Functor f => Applicative f where pure :: a -> f a (<*>) :: f (a -> b) -> f a -> f b {{content}} ``` ??? - It actually has more methods, but they have default implementations - We see that `Applicative` has a typeclass constraint of its own, `Functor` - Which means that every `Applicative` is also a `Functor`, that is, `Functor` generalizes `Applicative` - If we think of `f` as some sort of a container with an effect, than `pure` takes a plain value a puts in the container - The `<*>` is called "sequential application" the signature tells us what it does - If we have a function inside the "container", we can use sequential application to apply the function to another value inside another container - Of course, like many standard typeclasses, `Applicative` has some laws that it needs to obey, but we won't be going into them now - Let's implement this class for `Maybe` -- instance Applicative Maybe where pure x = Just x Just f <*> Just x = Just $ f x _ <*> _ = Nothing ??? - This is the obvious implementation, in the sense that there are some rules that `Applicative` should obey, and this is the only reasonable way to obey them - `pure` just wraps a value in a `Just` - The application operator is non-trivial only when both sides are `Just`s, then we apply the function - In all other cases we just return `Nothing` - Let's see what can we do with it --- ## Using `Applicative` ``` Search :: String -> TwitterAPI pure Search :: Maybe (String -> TwitterAPI) pure Search <*> Just "Who is Keyser Soze?" -- Just (Search "Who is Keyser Soze?") {{content}} ``` ??? - `Search` is function that takes a string, we lift it into our `Applicative` - Then we apply it a `Just` value - But the whole `pure ... <*>`, is just a map - We can define an operator that does this and this becomes -- Search <$> Just "Who is Keyser Soze?" ??? - The `<$>` stands for `fmap` - Let's try a more complicated example --- ## Using `Applicative` ``` Timeline :: User -> Integer -> TwitterAPI pure Timeline :: Maybe (User -> Integer -> TwitterAPI) pure Timeline <*> Just "Keyser" :: Maybe (Integer -> TwitterAPI) {{content}} ``` ??? - In this case lift the `Timeline` function, which takes two arguments - So if apply it with one sequential application operator, we still have one argument missing - We can then sequentially apply one more time -- pure Timeline <*> Just "Keyser" <*> Just 5 -- Just (Timeline "Keyser" 5) pure Timeline <*> Nothing <*> Just 5 -- Nothing {{content}} ??? - So we use the sequential application operator to two values - But if any of the values is missing, the whole thing fails - We can again use the `<$>` dollar operator to make this look nicer -- Timeline <$> Just "Keyser" <*> Just 5 ??? - Which is a very neat way to apply function inside of containers or contexts - Because of currying this pattern works for any number of arguments and for any `Applicative` -- ``` f <$> x1 <*> x2 <*> ... <*> xn ``` ??? - If you're familiar with Scalaz's `Validation`, this should look familiar - With all this in hand we are ready to start implementing our toy regex engine - Any questions so far? --- class: center, middle, transition # The Parser .tweet[![](tweet_regex.png)] ??? - As I said before, we'll be implementing a (simplified) regex engine - To do this, we'll use parser combinators, which you may be familiar with from Scala - Of course, Haskell has some very good parser combinators libraries - But instead of using them, we'll quickly implement one on our own - For what we need, it's actually not that much of an effort --- ## The Parsing Function ``` String -> [(a, String)] {{content}} ``` ??? - A parser is a function that takes a string (or rather, a stream of characters), which is the current state of parsing, and produces a list of pairs - Each pair designates a possible parsing of the string - The first item in the pair, of type `a`, is the result of parsing - The second item is the remaining characters, that is, the new state of the parser - If the list of results is empty, then there is no way to parse the string - To actually run the parser, we apply the function to a string and see the results -- newtype Parser a = Parser { parse :: String -> [(a, String)] } ??? - We'll wrap the function in a new type - `newtype` is like `data` but wraps a single value - You can think of it as a type tag, which the compiler optimizes away at compile time - It's a bit of boilerplate that allows to define new typeclasses for our function - We name the wrapped value `parse`, this generates a getter function called `parse` that unwraps the value when we need it (though we also have pattern matching) -- Advancing the stream: ``` satisfy :: (Char -> Bool) -> Parser String satisfy predicate = Parser $ \s -> case s of [] -> [] c:cs -> if predicate c then [([c], cs)] else [] ``` ??? - This is the main function we'll use to parse something - It takes a predicate and creates a new parsing function - The parser takes one character from the input - If the character matches the predicate, the result is a string with this character - The new state is the input minus the first character - If the predicate fails, the whole parse fails, so the result is the empty list - With this function in hand, we can implement a number of simple parsers --- ## Some Simple Parsers ``` char :: Char -> Parser String char c = satisfy (c ==) {{content}} ``` ??? - This function takes a single character and checks whether the next character in the string matches it - In the same vain, we can write more parsers -- dot = satisfy $ const True alphaNum = satisfy isAlphaNum oneOf, noneOf :: [Char] -> Parser String oneOf cs = satisfy $ \c -> elem c cs noneOf cs = satisfy $ \c -> notElem c cs ??? - `dot` matches any character - The expression `const True` return a function that return `True` on any input - `alphaNum` matches any alphanumeric character - In `oneOf` and `noneOf` we are taking a list of characters and creating a predicate that checks the presence (or abscence) of any of the characters in the stream --- ## Using the Parsers ``` p1 = char 'a' p2 = oneOf "abc" parse p1 "abc" -- [("a","bc")] parse p2 "cde" -- [("c","de")] parse p2 "def" -- [] ``` ??? - We can create simple parsers with what we have - The `parse` function unwraps our parsing function, and we can apply it to the input - In the first two cases there is only possible parsing, and we consume one character leaving the rest of the string - In the last case there are no parsings, so the result is empty - So far we have a bunch of simple parsers, but we don't have any way to combine them into more complicated parsers - Since we want parser combinators we'll need to write some combinators to go along with the parsers - To do this, we'll need some infrastructure, and for this we are going to implement a number of typeclasses - We start with `Functor` --- ## The Infrastructure ``` instance Functor Parser where fmap f (Parser p) = Parser $ \s -> [(f a, s') | (a, s') <- p s] {{content}} ``` ??? - There's a bit of new syntax here, it's called "list comprehensions". It's like Scala's for comprehensions but specialized to lists - What's to the left of the vertical bar is the result of the whole thing, to the right are the generators - So, given a mapping function (`f`) and a parser, we first deconstruct the parser and extract the parsing function (`p`), we then create a new parser function - In this function, we run the original function on the incoming string - Then we run over the results and apply `f` in the appropriate place - Next we have the `Applicative` instance -- instance Applicative Parser where pure a = Parser $ \s -> [(a, s)] Parser pf <*> Parser pa = Parser $ \s -> [(f a, s'') | (f, s') <- pf s, (a, s'') <- pa s'] ??? - First there's `pure`, which just takes a value and creates a new parsing function around it - Sequential application is quite similar to `fmap` from before, except that we now have two parser functions to deal with - In the first step we unwrap the function hidden in the first parser, in the second we unwrap the value hidden in the second - Then we apply the function to the value - Notice that we are careful to propagate the state of the parser between the first parser and the second to the final result - When we use sequential application, we run both parsers one after the other - This gives us a way to combine two parser into a new one, let's see an example --- ## Combining Parsers ``` (&) :: Parser String -> Parser String -> Parser String (&) pa pb = (++) <$> pa <*> pb (++) :: String -> String -> String char 'a' & char 'b' {{content}} ``` ??? - Here we are defining an operator that takes two parsers and runs them one after the other and concatenates the results - Notice the applicative syntax - In here the `++` operator is used as a two arguments function, we `fmap` and sequential application to apply this operator inside the parsers - Using `&` we can define the `string` function that matches a whole string -- string :: String -> Parser String string "" = pure "" string (c:cs) = char c & string cs -- string "abc" = char 'a' & char 'b' & char 'c' & pure "" ??? - The `string` parser takes a string and creates a parser that matches it in the input - The empty string creates a trivial parser that matches anything - In case the string is not empty, we are deconstructing it into the first character and the rest - We create a parser with the first character and combine it using `&` with a parser created with the rest of the characters - We'll need another typeclass to continue, the `Alternative` class --- ## More Infrastructure ``` class Applicative f => Alternative f where empty :: f a (<|>) :: f a -> f a -> f a many :: f a -> f [a] some :: f a -> f [a] {{content}} ``` ??? - The definition of the class is approximately this - Given that `f` has an instance of `Applicative`, we define the `Alternative` instance - In the context of parsing, `empty` is a failed parse, i.e. the empty list - The `<|>` operator, is the alternation operator, it takes two parsers and runs them in parallel - `many` and `some` run a single parser as many times as possible and aggregate the results into a list - `many` runs the parser zero or more times, while `some` runs it at least once - Let's see the implementation -- instance Alternative Parser where empty = Parser $ \s -> [] Parser pa <|> Parser pb = Parser $ \s -> pa s ++ pb s ??? - So `empty` is like we said - And the alternative creates a new function that runs the parsers on the same input, and concatenates the results - This provides backtracking in case we have many possible parsings - We don't need to implement `some` and `many` since they have default implementation in terms of the alternation operator - With this in hand we can combine parsers in a new way, for example -- Using the new combinators: ``` string "Keyser" <|> string "Soze" {{content}} ``` ??? - This matches either the string "Keyser" or "Soze" -- star, plus :: Parser String -> Parser String star p = concat <$> many p plus p = concat <$> some p {{content}} ??? - `star` takes a parser and applies it zero or more times using `many` - The result is a list of strings, we than map the the concatenation function into the parser, which gives a single long string - `plus` is the same thing, but applies the operator one or more times --- ## Running a Parser ``` match :: Parser a -> String -> [a] ``` ??? - `match` takes any parser and a string and produces a list of results - It's a simple function, you can see its implementation in the code repo - These are all the combinators we'll need - To see that it actually works, we can run an example -- A bigger example: ``` p = oneOf "Kk" & string "eyser" & plus dot & oneOf "Ss" & string "oze" -- [Kk]eyser.+[Ss]oze match p "Keyser Soze" -- ["Keyser Soze"] match p "No Keyser" -- [] match p "Keyser soze" -- ["Keyser soze"] match p "KeyserSoze" -- [] ``` ??? - A larger example, we combine a number of parsers together - They are equivalent to this regular expression - As you can see, we wrote a small domain specific language for parsers - And they work as expected - With this, we have the foundation to implement our little regular expressions engine - Also, if you're considering using regular expressions for something complicated, consider using parser combinators - They are reusable, and you can write and test parts of an expression in isolation, and then compose the results --- class: center, middle, transition # The regex-like language .tweet[![](tweet_adt.png)] ??? - Before we start our regex engine, we need to specify what exactly we need - This tip is actually very good, and works in both Scala and Haskell - So let's write down an algebraic data type for our regex-like language and see where it leads us --- ## The `Regex` ADT ``` data Regex = Str String | Dot | OneOf [Char] | NoneOf [Char] | Star Regex | Plus Regex | Or Regex Regex | And Regex Regex deriving (Eq, Show) ``` ??? - So this is what we'll be implementing, it should be pretty readable - Each constructor represents some part of our language - `Str` represents the string it gets as an argument - `Dot` is the dot regex and that will match any character - `OneOf` and `NoneOf` match a set of characters (or their complement) - `Star` and `Plus` match a given regex a number of times - `Or` and `And` match either or both of the given regexes - For example, the regex we seen before can be written as follows -- For example: ``` -- [Kk]eyser.+[Ss]oze And (OneOf "Kk") (And (Str "eyser") (And (Plus Dot) (And (OneOf "Ss") (Str "oze")))) ``` ??? - With this specification, let's see what we actually need --- ## What We need ``` strToRegex :: String -> Maybe Regex evalRegex :: Regex -> Parser String grep :: String -> String -> Bool ``` ??? - We'll need to implement 3 functions - `strToRegex` takes a string and tries to parse an instance of a `Regex` data type from it - We'll do this by creating a `Parser` that recognizes regular expressions and converts them into `Regex` instances - `evalRegex` will evaluate the `Regex` instance, into a `Parser` that matches the regular expression represented by this instance - The `grep` function will join these two functions into a single process, so it takes a string with a regular expression, and tests whether a target string contains this expression - The simplest part is the evaluator - With what we already implemented it almost writes itself --- ## The Evaluator ``` evalRegex :: Regex -> Parser String evalRegex regex = case regex of Str s -> string s Dot -> dot OneOf cs -> oneOf cs NoneOf cs -> noneOf cs Star r -> star $ evalRegex r Plus r -> plus $ evalRegex r Or r1 r2 -> evalRegex r1 <|> evalRegex r2 And r1 r2 -> evalRegex r1 & evalRegex r2 ``` ??? - So no surprises here, each case does the obvious thing - Note the recursion in the `Star`, `Plus`, `Or` and `And` - We can use it on the regex from before -- Running it: ``` -- [Kk]eyser.+[Ss]oze regex = And (OneOf "Kk") (And (Str "eyser") (And (Plus Dot) (And (OneOf "Ss") (Str "oze")))) p = evalRegex regex match p "Keyser Soze" -- ["Keyser Soze"] match p "Keyser oze" -- [] ``` ??? - Now comes the more difficult part, we need to write a parser that takes a regex string and convert it into a `Regex` ADT value - Let's do it step by step --- ## Parsing `Regex` .codeFloatRight[`[Kk]eyser.+[Ss]oze|[^abc].*ton`] ``` regexString :: Parser Regex regexString = Str <$> plus alphaNum {{content}} ``` ??? - This matches at least one alphanumeric and wraps the resulting string `Str` constructor -- regexDot = Dot <$ char '.' {{content}} ??? - The `<$` operator is like `fmap`, but ignores it input and returns what's on the left - So this matches a single dot, and places the `Dot` constructor instead of the matched dot -- regexOneOf = OneOf <$> (char '[' *> plus alphaNum <* char ']') regexNoneOf = NoneOf <$> (string "[^" *> plus alphaNum <* char ']') {{content}} ??? - We have a couple of new operators here, which are sequencing operators, both of them are defined in the standard library for `Applicative`s - The `*>` runs the first parser, discards its result, and then runs the second parser, and produces its result - The `<*` does the opposite, runs the first parser, keeps its result, then runs the second parser and discards its result - First we match a bracket and discard it, then we match an alphanumeric string, which is the result of the parser, then we match another bracket and discard it - We then wrap the resulting string in a `OneOf` constructor - The `NoneOf` case is similar, except that first we match a `[^` -- regexStar = Star <$> singleCharRegex <* char '*' regexPlus = Plus <$> singleCharRegex <* char '+' {{content}} ??? - `singleCharRegex`, which I'll define later, is an aggregate parser, that matches any of the single character patterns above - So in this case we match a single character, then match either a `*` or a `+` and discard it - We then wrap the single chararcter pattern in a `Star` or `Plus` constructor -- regexAnd = And <$> simpleRegex <*> (simpleRegex <|> regexAnd) {{content}} ??? - This case is a bit tricky since we need to handle the precedence between `And` and `Or` - The details don't really matter, but the result is the following: - `simpleRegex` aggregates all the parsers so far, we'll see its definition in a moment - First we match any simple expression we can, then we go on matching another one or possibly another `And` case - This provides the two arguments that we need for `And`, which we indeed apply on the right -- regexOr = Or <$> simpleRegexAnd <* char '|' <*> regexParser {{content}} ??? - The `Or` case is similar to `And`, except that it has lower precedence - Again, the details don't really matter - `simpleRegexAnd` is the same as the parenthesized expression in the `And` case - Then we match and discard a single pipe - And then we recursively match the whole regex parser, which we'll define now -- regexParser = simpleRegex <|> regexAnd <|> regexOr {{content}} ??? - So the full regex parser is either a simple expression, an `And`, or an `Or` case - If you're still following, you might notice the strange recursion pattern here - `regexAnd` is defined in terms of itself - And `regexOr` references `regexParser` which in turn references `regexOr` - This should've led to infinite recursion, but it doesn't - The reason is, that I didn't mention it this far, but by default, all definitions in Haskell are lazy - So neither of these expressions is actually evaluated until we call it - We could've achieved something similar with Scala's lazy variable or by-name parameters - But in order to do that, we need to explicitly ask for it, Haskell does it by default - Here are the missing definitions -- simpleRegex = regexString <|> regexDot <|> regexOneOf <|> regexNoneOf <|> regexStar <|> regexPlus singleCharRegex = regexChar <|> regexDot <|> regexOneOf <|> regexNoneOf simpleRegexAnd = simpleRegex <|> regexAnd ??? - This just matches any of the patterns from before that match a single character - This matches any of the simple parsers from above --- ## Combining All Together ``` regexParser :: Parser Regex strToRegex :: String -> Maybe Regex strToRegex str = safeHead $ match regexParser str strToRegex "[Kk]eyser.+[Ss]oze" -- Just (And (OneOf "Kk") (And (Str "eyser") -- (And (Plus Dot) (And (OneOf "Ss") (Str "oze"))))) {{content}} ``` ??? - We can now combine everything together - In `strToRegex` we use our `regexParser` to parse a regex string - This yields a list of results, we then take the head of the results with `safeHead`, if there aren't any result, we return `Nothing` - We can run in on the example string from before, and the result is what we'd expect -- evalRegex :: Regex -> Parser String match :: Parser String -> String -> [String] grep :: String -> String -> Bool ??? - We can now easily combine our the functions from above to create the `grep` function - `grep` uses `strToRegex`, `evalRegex` and `match` to compile and match the regular expression in the target string - You can see the actual implementation in the code repo, they are just a few line of code - If the pattern is contained anywhere inside the input, `grep` returns true - Let's run some examples -- Running it: ``` grep "[Kk]eyser.+[Ss]oze|[^abc].*ton" "I am Keyser Soze..." -- True grep "[Kk]eyser.+[Ss]oze|[^abc].*ton" "Or Keaton, maybe" -- True grep "[Kk]eyser.+[Ss]oze|[^abc].*ton" "But so is Kobayashi" -- False ``` ??? - This concludes our venture into parser combinators - Of course there's a lot more that can be implemented with these tools - But I hope that this gave a taste of what it looks like in Haskell - I think that most important thing to take away from this is how much you can gain by tapping into the standard typeclasses - By defining only a few typeclass functions, out of the box, we got a bunch of generic combinators that just work - I find it quite amazing that in about 100 lines of code, we've managed to implement a small, but non-trivial language - Any questions so far? - Let's move on --- class: center, middle, transition # IO .tweet[![](tweet_imperative.png)] ??? - So far, everything we've done is pure - But I've promised you "real world" stuff, and that comes with side effects - As we'll see, Haskell is good at doing side effects, which is the reason for this quote - So let's do that --- ## Side Effects In Haskell - Haskell is lazy - Laziness does not work with side effects ??? - But we have a problem - As I mentioned when we wrote the regex parser, Haskell is lazy by default - In a lazy setting, running something that has side effects is not recommended, since it's very hard to predict when the side effects will run -- - The solution: IO actions ??? - The solution comes in the form of IO actions, let's see it with an example --- ## IO Actions ``` hello :: IO () hello = putStrLn "Hello" {{content}} ``` ??? - This is an action of type `()`, so it's a pure side effect that doesn't produce a meaningful result - An IO action is a description of some IO action that we may want to perform, it's not the action itself - Writing the code above does nothing, it just defines a new IO value - Since these are values we can manipulate them as such -- world :: IO () world = putStrLn "World!" helloWorld :: IO () helloWorld = hello *> world {{content}} ??? - We are using the fact that `IO` has an `Applicative` instance - So we can create a couple of `IO` values and sequence them one after the other - In this case we first run the `hello` action, and then the `world` action - The result is a composite action that prints both strings - We can also have actions that produce some value -- getName :: IO String getName = getLine {{content}} ??? - This action reads a string from standard input and return the result - We can use `fmap` to manipulate the result -- addGreeting :: IO String addGreeting = fmap ("Hello " ++) getName ??? - `fmap` gets access to the string inside the action and can apply a function to it, yielding a new action - But what if we want something more complicated, like reading a string and then using it to print a response? - `Functor` and `Applicative` don't have any functions that can do that - Enter the dreaded `Monad` --- ## The `Monad` Class ``` class Applicative m => Monad m where return :: a -> m a (>>=) :: m a -> (a -> m b) -> m b {{content}} ``` ??? - This is (approximately) the `Monad` definition - `return` is a constructor function, like `pure` in `Applicative` - The `>>=` symbol is called `bind` and it's like Scala's `flatMap` - `IO` has a monad instance, so we can use these functions to do some more complicated chaining -- (>>=) :: IO String -> (String -> IO ()) -> IO () getNameAndGreet :: IO () getNameAndGreet = getName >>= \name -> putStrLn $ "Hello " ++ name {{content}} ??? - Here we created a more complicated action, it reads a line from the standard input and uses the result to print something - This is something that we couldn't have done only with `Applicative` - Note that the `putStrLn` action cannot run before `getName` since it has to wait for the `name` argument provided by `getName` - But as we know from Scala, once you start using monads we get a whole lot of `bind` applications - Just like in Scala, Haskell special syntactic sugar monads, it's called `do` notation -- getNameAndGreet = do name <- getName putStrLn $ "Hello " ++ name ??? - Although `do` notation is similar to Scala's `for` comprehensions, but there are some differences that makes quite a bit nicer - We won't get into the details, but we can give an example --- ## `do` Notation ``` script :: IO () script = do cd "/tmp" mkdir "test" output "test/foo" "Hello, world!" stdout (input "test/foo") rm "test/foo" rmdir "test" ``` .footnote[http://www.haskellforall.com/2015/01/use-haskell-for-shell-scripting.html] ??? - This is real code, using a library called Turtle - The Turtle library let's you do shell scripting in Haskell - As you can see, this codes reads pretty much like an imperative language - If we had something similar implemented with Scala's `for` comprehensions, you'd have something like this -- ```scala val script = for { _ <- cd("/tmp") _ <- mkdir("test") _ <- output("test/foo", "Hello, world!") _ <- stdout(input("test/foo")) _ <- rm("test/foo") _ <- rmdir("test") } yield () ``` ??? - Which also reads as an imperative program, but it's not as nice as the Haskell version - Back to our issue with side effects - So far, all we have is a way to create IO actions, but as we said before, they are not doing anything, they are just values - How do we run them? --- ## Running IO ``` main :: IO () main = putStrLn "Hello World!" ``` ??? - This is the code from one of the first slides - If we run this program, it actually prints to standard output -- - The runtime executes the `main` action - `>>=` takes care of sequencing in a lazy environment ??? - What happens is that when the Haskell runtime sees definition called `main` with type `IO ()`, it takes the action and actually executes it - Because we are using `bind`, effects are sequenced in the right order - And that's all we need to build programs that actually do stuff --- ## Living in `IO` - An effects system - `IO` values `=` code as data - Hard to reason inside `IO` - No effect granularity ??? - To recap - We actually has some very nice properties here - First, side effecting code is marked as such by the compiler, if we don't see the `IO` type in the signature then it's pure - Since working inside IO is somewhat harder than in regular code, this gives us good incentive to separate pure and impure code, as much as possible - Second, because `IO` are just plain values, we can manipulate them as we want, giving us the power of "code as data" - But since `IO` can be very imperative, inside an `IO` it's hard to reason about code - `IO` is a catch-all for all possible effects, if we want to allow just some side effect (but not launching missiles), we need some other type - Anyways, we are now ready to write our server application --- class: center, middle, transition # Haskell in the Real World .tweet[![](tweet_lambda.png)] ??? - So far we've been reinventing wheels, and implemented everything on our own - In this part of the talk we'll be doing some real coding, and will leverage any library that we get our hands on - You might suspect, especially if you used Scalaz, that if "real world" stuff is happening in monads, that our code is going to get scary - That's actually not the case, Haskell's syntax and type inference makes things like the above non-existant - As a reminder, what we want to do is to have a server fetching tweets from the Twitter API and grepping - Let's start with the data model --- ## The Data Model ``` data Tweet = Tweet { text :: String , id_str :: String } deriving (Show, Generic) instance FromJSON Tweet {{content}} ``` ??? - We have some new syntax here, it's called record syntax - We give names to the fields, and it automatically generates getter functions with these names - Since we are going to get tweets from the Twitter API, we'll need some JSON support here - We'll use a JSON library called `aeson` - That's why we have the typeclass instance here, it's magically create JSON deserializers for us - All that's needed is to add the `deriving Generic` clause here, the compiler and the library takes care of the rest - The core functionality of the application is grepping, and we need one function for this -- grepTweets :: String -> [Tweet] -> [Tweet] grepTweets pattern = filter $ (grep pattern) . text ??? - We have a new operator here, `.`, which is function composition - It reads as follows: given a pattern create a function that turns a list of tweets into a new list of tweets - We do so by partially applying the `filter` function - On the right is the filter - The filter extracts the `text` of the tweet, and then greps it with the pattern - Any tweets that don't pass the grep will be filtered out - Now we need some way of fetching the tweets --- ## Fetching the Tweets ``` timeline :: Config -> String -> IO (Maybe [Tweet]) timeline config user = do req <- parseUrl $ feedUrl user signedReq <- signOAuth (oauth config) (credential config) req resp <- withManager $ httpLbs signedReq let body = responseBody resp return $ decode body ``` ??? - So that's the function, I won't show the full implementation of the other parts (you can see the full implementation on Github) - I want to get a feel for how one does dirty stuff like network communication in Haskell - Let's see how it works - Since we want to call the outside world, we have to create an IO action - It reads like imperative code: - Create an http request for the feed of the user - Sign the request with the credentials that we get from a configuration object - Make the actual request - Extract the request body - Use the JSON decoder to decode it into a list of `Tweet`s wrapped in a `Maybe` - Again, we are just describing what we need here, we are not actually running the action - Note that the Twitter API limits the result set to 200 tweets - Now we need to hook up a server --- ## Scotty ``` main = scotty 3000 $ do get "/" $ do html "Hello World!" ``` ??? - We'll be using the Scotty web framework, it's a minimalistic web framework inspired by Ruby's Sinatra - This is a "hello world" in Scotty - It matches the GET request on the root path and responds with "hello world", simple as that - Our application is only slightly more complicated than this --- ## The `twitter-grep` Server ``` main :: IO () main = do config <- readConf scotty 3000 $ do get "/grep-tweets/:user" $ do user <- param "user" pattern <- param "pattern" maybeTweets <- liftIO $ timeline config user let response = case maybeTweets of Nothing -> h1 "Failed to fetch tweets" Just tweets -> htmlTemplate $ grepTweets pattern tweets asHtml response get "/twitter.js" $ file "twitter.js" ``` ??? - First we read the configuration for the application, it's in a file, so we are doing IO in the process - Then we start the server - Let's start from the bottom, we are serving a static JavaScript file, this will be used for nice rendering of the tweets we'll be serving - On the top we are responding to GET requests on the `grep-tweets` path - We extract the `user` and `pattern` parameters from the current request - Next, we fetch the user's timeline - The `liftIO` call is a bit of boilerplate needed since Scotty does not live directly in the IO monad, but in some intermediate structure - Next we handle the tweets, the first case handles failure, the second applies our grep function and puts in an HTML template - The HTML template is actually written in pure Haskell, but we'll skip it for now - We then render the response as an HTML response - And that's it, our application is finished and ready to run --- ## A Running Example .center[.twitter-grep[![](twitter_grep.png)]] ??? - In here we are querying the user `implict_ly`, which tweets about Scala related software releases - We are filtering down to releses that mention Specs2 2.4 and Scalaz - Let's do another one --- ## A Running Example .center[.twitter-grep-fibs[![](twitter_grep_fibs.png)]] When I said no Fibonacci, I lied... ??? - Because you can't give an introduction to Haskell without mentioning Fibonacci - This concludes our exploration of Haskell - I hope that you got some feeling of what it's like to program in Haskell - The blend of pure FP with code that can do "real world" stuff is very powerful - You can achieve quite a lot this way without losing the elegance that so characteristic of functional programming --- ## Resources The full code and presentation: .center[https://github.com/ncreep/taste_of_haskell] .gap[] Further reading: - Learn You a Haskell ([free online book](http://learnyouahaskell.com/)) - Real World Haskell ([free online book](http://book.realworldhaskell.org/read/)) - A brief introduction to Haskell ([FP in Scala wiki](https://github.com/fpinscala/fpinscala/wiki/A-brief-introduction-to-Haskell,-and-why-it-matters)) - Typeclassopedia ([wiki](https://wiki.haskell.org/Typeclassopedia)) - Haskell For All ([blog](http://www.haskellforall.com/)) - The turtle library ([tutorial](http://hackage.haskell.org/package/turtle-1.0.0/docs/Turtle-Tutorial.html)) .center[.questions[Questions?]]