LoginSignup
1

More than 5 years have passed since last update.

Type Class Notes

Posted at

Haskell's typeclasses

Haskell's Functor is a type class. Any type constructor that implements Functor's fmap is a functor. To be more technical, the type constructor + implementation of fmap is an endofunctor on Hask.

If ((,) e) is a type constructor, it means a tuple type of two elements with the first being e while the second is a type variable.

Note that ((,) 1) is a function. It's type is not Num a => ((,) a)

For Monad, think of m a as a computation with a being the return result. return means "null computation" which accepts a and returns a in the computation context. >>= composes two computation into another computation.

Based on this, it's easy to understand the reader Monad.

ReaderMonad.hs

const a b = a

instance Monad ((->) e) where
  return = const
  m >>= f = \x -> f (m x) x

Here, const will return a computation which simply ignores the arguments passed in and return value passed to return. m is a computation. >>= combines one computation with another computation generator, that is f. f generates another computation based on the result of computation m.

What can be a reader monad? Every function that accepts an argument and returns a value can be a reader monad. For example, sometimes the argument passed in can be an environment. The function will lookup some variable in the environment and return it directly or modify it in the environment.

How to prove two laws are equivalent?

No Idea

We already have fmap, why do we still need liftM?

Theoretically, every Monad is also a Functor. So 'fmap == liftM'. However, in haskell's standard library, Monad type class doesn't require Functor instance. So we have 'liftM' to avoid an explicit 'Functor' constraint.

Multi-parameter type class and Functional Dependencies.

Take type class Eq as an example, Haskell's type class declaration is like:


class Eq a where
  (==) :: a -> a -> Bool

The declaration can be read as:

Type a is a member of type class Eq

So Haskell's type class is like a set of types with the types (also called instance) follow the constraint of the class by implementing all the function declared.


instance Eq Bool where
  a == b = if a then b else not b

Here, we declare that Bool belongs to set Eq, or $ Bool \in Eq $. The curry style declaration is a little misleading.

We can also declare one type class as the super class of another.


class Eq a => Ord a where
  (<), (<=) :: a -> a -> Bool

This declaration can be read as

Type class Ord implies Type class Eq
Or, if a type is a member of Ord, then it must be a member of Eq
Or, Eq is a super class of Ord

Super class declaration makes sure that one type class can inherit the constraint of another type class.

Haskell also allows multi-parameter type class. One classical example is to implement uniform interfaces for Collection.


class Collection e ce where
  empty :: ce
  insert :: e -> ce -> ce
  member :: e -> ce -> Bool

List is an instance of Collection type class.


instance Collection Int [Int] where
  empty = []
  insert = (:)
  member = elem

Run a small program to check out type class


demo = let x :: Int
            x = 3
         in insert x empty

main = print demo

Compile it with GHC, it will report some scary errors:



multi-param.hs:67:12:
    No instance for (Collection Int a0) arising from a use of insert
    The type variable a0 is ambiguous
    Relevant bindings include demo :: a0 (bound at multi-param.hs:65:1)
    Note: there is a potential instance available:
      instance Collection Int [Int] -- Defined at multi-param.hs:59:10
    In the expression: insert x empty
    In the expression:
      let
        x :: Int
        x = 3
      in insert x empty
    In an equation for demo:
        demo
          = let
              x :: Int
              x = 3
            in insert x empty

...

The reason is that when GHC evaluating insert x empty, it will firstly infer the types of expressions involved and then find the instance by unifying the types of expressions.


x :: Int
empty :: Collection e ce => ce
insert :: Collection e ce => e -> ce -> ce

Apparently, x's type is known because we have explicitly annotated it. However, type of empty is unknown, so GHC directly represents it as a type variable $ \alpha $. Based on x and empty, we will get type of insert : $ Collection \space Int \space \alpha => Int \rightarrow \alpha \rightarrow \alpha $. We haven't declared the instance $ Collection \space Int \space \alpha $, which leads GHC to complain.

Faced with the problem, you might be tempted to annotate type of empty explicitly.


demo = let x :: Int
           x = 3
           ec :: [Int]
           ec = empty
        in insert x ec

This still doesn't work since the empty function has an ambiguous type: empty : Collection e [Int] => [Int] since type variable e appears on the left of => symbol(See qualified types). (I don't quite get this, maybe I will read the paper first). Also the instance Collection e [Int] => [Int] is also not defined, which is just what GHC reports.

We can solve this by replacing empty with [], but this makes empty function meaningless. Functional dependency is one reasonable solution.

class Collection e ce | ce -> e where
  empty :: ce
  insert :: e -> ce -> ce
  member :: e -> ce -> Bool


instance Collection Int [Int] where
  empty = []
  insert = (:)
  member = elem


demo = let x :: Int
           x = 3
           ec :: [Int]
           ec = empty
        in insert x empty

Here, ce -> e is functional dependency. It means that ce determines e. Or, if you have already determined ce, then e is determined. Or, for if ce is determined, there is only one corresponding instance implementation.

The annotation is quite intuitive. ce -> e looks like a function, whose definition requires for each ce there is only one corresponding e.

Unfortunately, we still can't write code like:

demo = let x :: Int
           x = 3
        in insert x empty

Since without explicit annotation, the type of empty is still unknown, which leads to wrong inferred instance: Collection Int a.)

OCaml's Modules are claimed to be much more expressive than type class.

ReaderT

ask :: (Monad m) => ReaderT r m r
ask = ReaderT return

return is a polymorphic function with type: a -> m a, which just fits in ReaderT's constructor. The type of m depends on how you defines it. A small demo to show how ask works:


demo = let y :: Int
           y = 3
           x :: Either String Int
           x = runReaderT (ReaderT return) y
        in x

Here, I define m as Either Monad. You can also define it as Maybe Monad or whatever you want.

Continuation Monad

take function square as an example


square x = x*x

-- change it into continuation passing style

square_cont x = \k -> k (square x)

The return value of square_cont is called suspended computation. After passing a continuation:k to suspended computation, it will calculate the intermediate result(returned by square function). The return value of k is the return value of the suspended computation.

Suspended computation "wraps" all the computation of "square" and pass the result to "future computation"/Continuation of square:k. The main responsibility of suspended computation is getting k, conducting the wrapped computation and passing computation result to k.
Get a sense of suspended computation through following examples:


main = let suspended_computation = square_cont 3
        in do
          print $ suspended_computation (*2)
          print $ suspended_computation (*3)

Continuation Monad is just the suspended computation. Continuation monad can be used to compose functions in continuation passing style.


newtype Cont a r = Cont {runCont :: (a->r) -> r}

for example:


import Control.Monad.Identity
import Control.Monad.Cont

square:: (Num a) => a -> a
square x = x*x


square_cont :: (Num a) => a -> Cont b a
square_cont x = cont $ \k -> k (square x)

main = print $ runCont (square_cont 4) show

cont construct a continuation monad. runCont execute the continuation monad after passing continuation to it.

For Cont b a, b is final result type(return type of future continuation), a is intermediate result type.

A continuation monad transformer can bind a future continuation with a monadic computation to form a continuation monad. The future continuation accepts the result of monadic computation and return a monadic computation with new result.

callCC

callCC or call-with-current-continuation, gives explicit control of continuation.


foo = callCC $ \k -> (k "hello world") >> (return "never printed")

main = print $ runCont foo show

callCC returns a suspended computation, which is often called "callCC computation". For whatever value passed to k is captured in the callCC computation, and the computation after k is ignored.


-- callCC accepts a function f and return a Continuation Monad.
-- f accepts a function k as arguments
-- f :: (a -> ContT r m b) -> ContT r m a
-- k :: a -> ContT r m b
-- x :: a
-- c :: a -> m r

callCC::((a -> ContT r m b) -> ContT r m a) -> ContT r m a
callCC f = ContT $ \ c -> runContT (f (\ x -> ContT $ \ _ -> c x)) c

In callCC, c is actually "current continuation", i.e, the continuation of the callCC expression, or, what the program will do after the callCC is called. So, you can see, it's called "call with current continuation" not without reason.

All the magic of callCC starts with the function f that Haskell programmer has to implement. callCC passes another function k to f. As you can see, the implementation of k is simple but very confusing.

k.hs

-- sub function extracted from callCC
k :: a -> ContT r m b
k = \ x -> ContT $ \ _ -> c x

In the example above, x is "hello world". k simply returns a special suspended computation which ignores following continuation and replace it with c. So when the Continuation Monad returned by calling k with "hello world" is bound(i.e, >>=) with another Continuation Monad : (return "never printed), the continuation encapsulated in it will not be executed. Also, running ContT $ \ _ -> c x with another Continuation will lead the continuation ignored. So runContT (f (\ x -> ContT $ \ _ -> c x)) c simply executes c x.

In function f, k may not be called. In this case, body of f will be executed until the last expression. Then runContT (f (\ x -> ContT $ \ _ -> c x)) c will pass c as continuation to the Continuation Monad returned by f.

Foldable

type of foldMap . foldMap is (a -> m) -> t1 (t2 a) -> m. type of foldMap is (a -> m) -> t2 a -> m. So you can think of foldMap as a function which transforms a function of type (a->m) to type (t2 a -> m). So for foldMap . foldMap, the right foldMap transforms a->m to t2 a -> m, then the left foldMap transforms t2 a -> m to t1 (t2 a) -> m.

Register as a new user and use Qiita more conveniently

  1. You get articles that match your needs
  2. You can efficiently read back useful information
  3. You can use dark theme
What you can do with signing up
1