L09. Type constructors

{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
 
 
data Tree a = TVoid | Node (Tree a) a (Tree a)
 
data List a = LVoid | Cons a (List a)
 
-- member :: Container of a's -> a -> Bool
-- attempt1:
 
class Contains a b where
	member :: a -> b -> Bool
 
instance Contains Char (List Char) where
	member _ _ = False -- stub implementation
{-This implementation is very particular.-}
 
 
instance Eq a => Contains a (List a) where
	member _ LVoid = False
	member y (Cons x xs) = x == y || member y xs
{- This implementation works, however, it raises issues regarding other possible
   instances of Contains. For example:
 
instance Contains Char (List Integer) where
	...
 
   is possible but makes no sense. We need a way to avoid this.
   -}
 
{-
   suppose we would like to define an operation:
 
   mapp :: (a -> b) -> Container of a's -> Container of b's
-}
 
class Mapp a b ca cb where
	mapp :: (a -> b) -> ca -> cb 
 
instance Mapp a b (Tree a) (Tree b) where
	mapp f TVoid = TVoid	
 
{-
   The same problem appears, only in a more complicated form. Mapp is not a relation over
   over 4 types, but a property of CONTAINERS!
 
 
   t :: * -> *
-}
 
class Functorr t where
	fmapp :: (a -> b) -> t a -> t b
 
instance Functorr List where
	fmapp f LVoid = LVoid
	fmapp f (Cons x xs) = Cons (f x) $ fmapp f xs
 
instance Functorr Tree where
	fmapp f TVoid = TVoid
	fmapp f (Node l k r) = Node (fmapp f l) (f k) (fmapp f r)
 
{- Functors are objects which can be tranformed via a function f.
   List, Tree are Functors.
 
   On the other hand, there is a class called Foldable, which includes
   other functions. Let us define it:
-}
 
class Foldablee t where
	foldrr :: (a -> b -> b) -> b -> t a -> b
	elemm :: (Eq a) => a -> t a -> Bool
	elemm x = foldrr ((&&).(==x)) False --foldrr op False
				{-
				where op y False = x == y 
				      op y True = True
 
				we take the first parameter, compare it to x,
				then return a function which expects an accumulator and performs "&&"
				with it.      
-}
 
instance Foldablee List where
	foldrr op acc LVoid = acc
	foldrr op acc (Cons x xs) = x 0111p0032foldrr op acc xs
 
instance Foldablee Tree where
	foldrr op acc TVoid = acc
	foldrr op acc (Node l k r) = k 0111p0032(foldrr op (foldrr op acc l) r)
 
 
{- Examples of type constructors which are not functors, nor Foldables -}
data Set a = Set (a -> Bool)
 
{- Examples of other type constructors which are functors -}
 
data Result a = Error String | Value a
 
instance Functorr Result where
	fmapp f (Error m) = Error m
	fmapp f (Value x) = Value $ f x
 
-- But which can also be foldable.
instance Foldable Result where
	foldr op acc (Error _) = acc
	foldr op acc (Value x) = op x acc
 
 
instance Functor ((->) Int) where
	fmap f g = f.g