TSM - Functional Programming in Haskell (IV)

Mihai Maruseac - IxNovation

At the end of the latest issue we managed to write a basic application allowing information retrieval from 3 tables containing data about individuals (data being presented as a list of pairs). Starting from that code (which will be presented here as well) we"ll build the application of this article.

We start with some compiler extensions to allow more expressivity:

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}

Then, we define the data types involved:

type Name = String
type Age = Int
type Address = String
type PhoneNumber = Integer
newtype NameAgeTable = NAgT [(Name, Age)] deriving Show
newtype NameAddressTable = NAdT [(Name, Address)] deriving Show
newtype NamePhoneTable = NPT [(Name, PhoneNumber)] deriving Show

Remember that deriving Show clause hints the compiler to define a show method to convert each type to String.

Here are some test values for the 3 tables:

nameAge = NAgT [("Ana", 24), ("Gabriela", 21), ("Mihai", 25), ("Radu", 24)]
nameAddress = NAdT [("Mihai", "a random address"), ("Ion", "another address")]
namePhone = NPT [("Ana", 2472788), ("Mihai", 24828542)]

We define a class for searching based on name and we enroll the three types into this class. Because we don"t use deriving, we need to define the method ourselves. We"ll use the predefined lookup function for that.

class SearchableByName t a | t -> a where
search :: Name -> t -> Maybe a
instance SearchableByName NameAgeTable Age where
search name (NAgT l) = lookup name l
instance SearchableByName NameAddressTable Address where
search name (NAdT l) = lookup name l
instance SearchableByName NamePhoneTable Phone
Number where
search name (NPT l) = lookup name l

And now we can search the tables using a common API:

*Main> search "Ion" nameAge 
Nothing
*Main> search "Mihai" nameAge 
Just 25
*Main> search "Mihai" nameAddress 
Just "a random address"
*Main> search "Gabriela" nameAddress 
Nothing
*Main> search "Ionela" namePhone 
Nothing
*Main> search "Mihai" namePhone 
Just 24828542

This is where we stopped last time. Today we will simulate a join operation by writing a function getInfo which will return the age, the address and the phone number for a person as long as all three pieces of information are present. The naive approach is

getInfo1 name = 
case search name nameAge of 
Just age -> case search name nameAddress of 
Just address -> case search name namePhone of 
Just phone -> Just (age, address, phone) 
Nothing -> Nothing 
Nothing -> Nothing 
Nothing -> Nothing 

Observe the cascading effect of the test. This doesn"t look nice at all but we can rewrite the above code as:

getInfo2 name = do 
age <- search name nameAge 
address <- search name nameAddress 
phone <- search name namePhone 
return (age, address, phone) 

It looks like an imperative code and no Nothing tests seem to have survived the transformation. However, the code is still functional but with a higher focus on the declarative aspect: we only show what the function does and the boilerplate is hidden via syntactic sugar. The above code is in fact:

getInfo3 name = 
search name nameAge >>= age -> 
search name nameAddress >>= address -> 
search name namePhone >>= phone -> 
Just (age, address, phone)

It looks like function composition but using >>= to implement a pipelining of function results. This is why this operator gets the name of programmable semicolon; it works like ; from imperative programs but it has an associated semantics. In our case the handling of Nothing values.

We test the code:

*Main> getInfo1 "Mihai" 
Just (25,"a random address",24828542) 
*Main> getInfo2 "Mihai" 
Just (25,"a random address",24828542) 
*Main> getInfo3 "Mihai" 
Just (25,"a random address",24828542) 
*Main> getInfo3 "Ioana" 
Nothing 

At the end of the article we"ll present the magic behind which allows >>= to be the programmable semicolon. In fact, all can be explained by a single typeclass capturing another pattern of functional programming. We"ll start with the Functor typeclass first:

class Functor f where 
fmap :: (a -> b) -> f a -> f b 
Instance Functor [a] where 
fmap = map

It"s self evident that we can use fmap on trees, stacks, graphs, etc. This gives rise to the container analogy: fmap applies a function for all elements of a container and returns the results packed into a similar container.

The analogy breaks when we consider other valid cases:

*Main Control.Applicative> fmap (+1) (const 3) $ 5 
4 
*Main Control.Applicative> :t fmap (+1) fst 
fmap (+1) fst :: Num b => (b, b1) -> b 
*Main Control.Applicative> fmap (+1) fst $ (2, 5) 
3 
*Main Control.Applicative> :t fmap show fst 
fmap show fst :: Show a => (a, b) -> String 
*Main Control.Applicative> :t fmap show fst (2,3) 
fmap show fst (2,3) :: String 
*Main Control.Applicative> fmap show fst (2,3) 
"2" 

We must regard f from the type signature of Functor typeclass as a computational context which will be modified by fmap. Or, if looking from the point of view of curry functions, we get that fmap lifts a function from the normal case to the computational context/container level.

The interesting typeclass is Monad.

class Monad m where 
(>>=) :: m a -> (a -> m b) -> m b 
(>>) :: m a -> m b -> m b 
return :: a -> m a 

First observation is that return is only a function, not a language keyword. Its purpose is to lift a value to the needed computational context. For Maybe, return is the constructor named Just.

The other function is more important. The operator >>= pronounced bind is able to do something which fmap cannot: imagine we have a function receiving a normal value and returning some results into a context (let"s say a list of values). Doing a fmap with this function on these results will result into a context of contexts (list of lists of values) so we need another operation (concat) to strip down one layer. The bind operator does this work for us.

Knowing the definitions for Functor and Monad and the essential types of Haskell we can write enough code without requiring more advanced notions. However, if you feel intrigued, I recommend reading the Typeclassopedia of Brent Yorgey to see other interesting patterns of functional programming which are captured by typeclasses and are useful in some programming activities.