
On Tue, Dec 29, 2009 at 7:58 AM, CK Kashyap
I'd appreciate answers to the following queries - 1. Comments about the functions I've written
{-# LANGUAGE UnicodeSyntax #-} import Monad ( MonadPlus(..) ) data List α = Cons α (List α) | Empty deriving Show If you look at your definitions of 'myMap', 'myAppend' and 'myConcat' you will notice that they all follow a similar pattern which can be abstracted in a so called "catamorphism" (or in normal Haskell a "fold"): myFoldr ∷ (α → β → β) → β → List α → β myFoldr f z = myFoldr_f_z where myFoldr_f_z Empty = z myFoldr_f_z (Cons x xs) = f x $ myFoldr_f_z xs myMap ∷ (α → β) → List α → List β myMap f = myFoldr (Cons . f) Empty myAppend ∷ List α → List α → List α myAppend xs ys = myFoldr Cons ys xs myConcat ∷ List (List α) → List α myConcat = myFoldr myAppend Empty instance Monad List where return a = Cons a Empty l >>= f = myConcat $ myMap f l instance MonadPlus List where mplus = myAppend mzero = Empty list2myList ∷ [α] → List α list2myList = foldr Cons Empty regards, Bas