L08. Typeclasses

{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
 
{-
(A) Ad-hoc polymorphism:
   "Ad-hoc polymorphism is obtained when a function works, or appears to work,
   on several different types (which may not exhibit a common structure)
   and may behave in unrelated ways for each type." – Strachey 1967
 
(B) Subtype polymorphism:
  A type S (subtype) is related to another type T (supertype) by some
  notion of substitutability, meaning that functions written to operate on
  elements of type T(supertype), can also operate on elements of type S (subtype)
 
(C) parametric polymorphism:
 
  Functions or datatypes can be defined generically, so that they
  can work "identically" on families of types, without depending on them.
 
  Examples: list operations such as:
     - length, reverse, map, should work in the same way, no matter if
     they are lists of integers, string, char, etc.
-}
 
 
data TList = Void | Cons Char TList
 
data Tree = TVoid | Node Tree Char Tree
 
 
-- tshow :: a -> String
-- different implementations of tshow are necessary
 
class TShow a where        -- TShow is a family of types a which have something in common:
    tshow :: a -> String   -- function tshow may be called on them
 
instance TShow TList where -- type TList is a member of class TShow (hence it is Show-able)
    tshow Void = "[]"
    tshow (Cons x xs) = x:':':(tshow xs)
 
instance TShow Tree where
    tshow TVoid = ""
    tshow (Node l k r) = "<"++(tshow l)++[k]++(tshow r)++">"
 
-- In Haskell we have a predefined class Show, which works exactly as the above.
-- we make ADT values show-able by enrolling them in class Show, or by using:
-- deriving Show.
 
data List a = PVoid | PCons a (List a)
 
-- instance Show (List a) where   -- this definition will not work as type a must be itself show-able
 
instance (Show a) => Show (List a) where -- type constraint
 show PVoid = "[]"
 show (PCons x xs) = (show x)++":"++(show xs)
                      -- a specific show method defined somewhere for x
                                    -- our recursive definition of this particular show
 
-- exercise: enroll functions in class Show. 
instance Show (a->b) where
    show f = "Function"
 
-- equality of types:
instance Eq TList where
    Void == Void = True
    Cons x xs == Cons y ys = x == y && xs == ys
 
-- minimal definition. \= is implemented relying on ==
-- read the docs: https://hackage.haskell.org/package/base-4.15.0.0/docs/Data-Eq.html
 
-- exercise: enroll type List a in class eq
 
-- class Num: enrolling String and making (+) as concatenation
 
instance Num String where
    (+) = (++) 
 
-- it works but there may be problems with other implementations.
 
 
-- Most used classes:
-- Show, Eq, Num, Ord
 
-- Foldable - discussed in the next lecture
 
 
-- when to use type-classes
-- <aexpr> ::= <value> | <variable> | <aexpr> + <aexpr>
 
type Value = Integer
type Variable = String
 
data AritmExpr = AVal Value | AVar Variable | Plus AritmExpr AritmExpr deriving Show
 
a = (AVal 1) 0080lus0032(AVar "x")
 
-- <bexpr> ::= <aexpr> == <aexpr> | !<bexpr> | <bexpr> && <bexpr>
data BoolExpr = Equals AritmExpr AritmExpr | BNot BoolExpr | And BoolExpr BoolExpr deriving Show
 
b = ((AVal 1) 0080lus0032(AVal 2)) 0069quals0032(AVal 2)
 
-- we ignore variables for now. We need to add a mapping for them
eval_aritm_expr :: AritmExpr -> Integer 
eval_aritm_expr (AVal v) = v
eval_aritm_expr (Plus e e') = foldr (+) 0 $ map eval_aritm_expr [e,e']
 
eval_bool_expr :: BoolExpr -> Bool
eval_bool_expr (Equals e e') = (eval_aritm_expr e) == (eval_aritm_expr e')
eval_bool_expr (BNot e) = not $ eval_bool_expr e
eval_bool_expr (And e e') = (eval_bool_expr e) && (eval_bool_expr e')
 
-- code becomes heavy and we need to keep track of which function evaluates each particular type
-- a more elegant way is to use typeclasses
 
-- a will be, for our example, AritmExpr and BoolExpr
-- but we also need to express what each expression returns
class Eval a b where
    eval :: a -> b
 
instance Eval AritmExpr Integer where -- AritmExpr evaluates to an integer
    eval = eval_aritm_expr
 
instance Eval BoolExpr Bool where -- BoolExpr evaluates to a boolean
    eval (Equals e e') = ((eval e) :: Integer) == (eval e')
    eval (BNot e) = not $ eval e
    eval (And e e') = (eval e) && (eval e')
 
-- another alternative:
 
data ExprResult = I Integer | B Bool
 
class Evalp a where
    evalp :: a -> ExprResult
 
instance Evalp AritmExpr where
    evalp (AVal x) = I x 
    evalp (Plus e e') = case (evalp e, evalp e') of
                            (I i1,I i2) -> I (i1 + i2)
 
instance Evalp BoolExpr where
    evalp (Equals e e') = case (evalp e, evalp e') of
                            (I i1, I i2) -> B (i1 == i2)
    evalp (And e e') = case (evalp e, evalp e') of
                            (B b1, B b2) -> B (b1 && b2)
    evalp (BNot e) = case evalp e of
                        B b -> B $ not b
 
{-
   Approach 1:
   Pros:
     - more concise and easy to use
   Cons:
     - requires extensions
     - requires keeping track of the return type for eval, when enrolling a new type
     - it is possible to have enrolments like:
          instance BoolExpr Bool
          and
          instance BoolExpr Integer
 
          which do not make sense for our application
 
   Approach 2:
   Pros:
     - simpler implementation, no extensions
   Cons:
     - requires boxing/unboxing of ExprResult values
     - may be unsafe. Programmers are allowed to return (I x) values when booleans are expected
       In other words, type verification becomes the task of the programmer
 
-}