GHC Language extensions

Background: Monad transformers

Using StateT

Exercise: Implement get and put

newtype StateT s m a = StateT { runStateT :: s -> m (a,s) }

instance (Monad m) => Monad (StateT s m) where
    return a = StateT $ \s -> return (a, s)
    m >>= k  = StateT $ \s0 -> do          -- in monad m
                 ~(a, s1) <- runStateT m s0
                 runStateT (k a) s1
get :: (Monad m) => StateT s m s


put :: (Monad m) => s -> StateT s m ()

Exercise: Implement get and put

newtype StateT s m a = StateT { runStateT :: s -> m (a,s) }

instance (Monad m) => Monad (StateT s m) where
    return a = StateT $ \s -> return (a, s)
    m >>= k  = StateT $ \s0 -> do          -- in monad m
                 ~(a, s1) <- runStateT m s0
                 runStateT (k a) s1
get :: (Monad m) => StateT s m s
get = StateT $ \s -> return (s, s)

put :: (Monad m) => s -> StateT s m ()
put s = StateT $ \_ -> return ((), s)

The MonadIO class

class (Monad m) => MonadIO m where
    liftIO :: IO a -> m a

instance MonadIO IO where
    liftIO = id

Background: recursive bindings

Recursion and monadic bindings

The RecursiveDo extension

Example uses of mfix and rec

Implementing mfix

fixIOIO Monad fixed point

A generic mfix is not possible

MonadFix instance for StateT

Review: Type classes

MultiParamTypeClasses extension

FlexibleInstances extension

OverlappingInstances extension

Most specific instances

A case against OverlappingInstances

module Help where
    class MyShow a where
      myshow :: a -> String
    instance MyShow a => MyShow [a] where
      myshow xs = concatMap myshow xs

    showHelp :: MyShow a => [a] -> String
    showHelp xs = myshow xs     -- doesn't see overlapping instance

module Main where
    import Help

    data T = MkT
    instance MyShow T where
      myshow x = "Used generic instance"
    instance MyShow [T] where
      myshow xs = "Used more specific instance"

    main = do { print (myshow [MkT]); print (showHelp [MkT]) }
*Main> main
"Used more specific instance"
"Used generic instance"

Aside: How Show actually works

class Show a where
  show :: a -> String
  showList :: [a] -> ShowS
  showList as = '[' : intercalate ", " (map show as) ++ "]"
  -- Note actual implementation more efficient but equivalent

instance (Show a) => Show [a] where
  show as = showList as

FlexibleContexts extension

Monad classes

Problem: we’ve defeated type inference

FunctionalDependencies extension

Sufficient conditions of decidable instances

  1. The Paterson Conditions: for each assertion in the context

    1. No type variable has more occurrences in the assertion than in the head

      class Class a b
      instance (Class a a) => Class [a] Bool  -- bad: 2 * a > 1 * a
      instance (Class a b) => Class [a] Bool  -- bad: 1 * b > 0 * b
    2. The assertion has fewer constructors and variables than the head

      instance (Class a Int) => Class a Integer   -- bad: 2 >= 2
  2. The Coverage Condition: For each fundep left -> right, the types in right cannot have type variables not mentioned in left

    class Class a b | a -> b
    instance Class a (Maybe a)       -- ok: a "covered" by left
    instance Class Int (Maybe b)     -- bad: b not covered
    instance Class a (Either a b)    -- bad: b not covered

Undecidable vs. exponential – who cares?

UndecidableInstances extension

MonadIO revisited

Summary of extensions

Warm-up: Type-level booleans

data HFalse = HFalse deriving Show
data HTrue = HTrue deriving Show

class HNot a b | a -> b where hNot :: a -> b
instance HNot HFalse HTrue where hNot _ = HTrue
instance HNot HTrue HFalse where hNot _ = HFalse
*Main> hNot HTrue
HFalse
*Main> hNot HFalse
HTrue

Computing over types

The utility of TypeEq

Heterogeneous lists

Operations on heterogeneous lists

Object-oriented programming

“Tying the recursive knot”