-- (c) MP-I (1998/9-2006/7) and CP (2005/6-2013/4) module List where import Cp import Nat -- (1) Datatype definition ----------------------------------------------------- --- Haskell lists are already defined, so the following is a dummy, informal declaration: --- data [a] = [] | (a : [a]) inList = either nil cons where nil = const [] cons = uncurry (:) outList [] = i1 () outList (a:x) = i2(a,x) -- (2) Ana + cata + hylo ------------------------------------------------------- cataList g = g . recList (cataList g) . outList recList f = id -|- id >< f anaList g = inList . recList (anaList g) . g hyloList h g = cataList h . anaList g -- (3) Map --------------------------------------------------------------------- -- instance Functor [] -- where fmap f = cataList ( inList . (id -|- f >< id )) -- NB: already in the Haskell Prelude -- (4) Examples ---------------------------------------------------------------- -- (4.1) inversion ------------------------------------------------------------- invl = cataList (either nil snoc) where snoc(a,l) = l ++ [a] -- alternatively: snoc = conc . swap . (singl >< id) -- where singl a = [a] -- conc = uncurry (++) -- (4.2) Look-up function ------------------------------------------------------ look :: Eq a => a -> [(a,b)] -> Maybe b look k = cataList (either nothing aux) where nothing = const Nothing aux((a,b),r) | a == k = Just b | otherwise = r -- (4.3) Insertion sort -------------------------------------------------------- iSort :: Ord a => [a] -> [a] iSort = cataList (either nil insert) where insert(x,[]) = [x] insert(x,a:l) | x < a = [x,a]++l | otherwise = a:(insert(x,l)) -- also iSort = hyloList (either (const []) insert) outList -- (4.4) take (cf GHC.List.take) ----------------------------------------------- take' = curry (anaList aux) where aux(0,_) = i1() aux(_,[]) = i1() --- aux(n+1,x:xs) = i2(x,(n,xs)) aux(n,x:xs) = i2(x,(n-1,xs)) -- pointwise version: -- take 0 _ = [] -- take _ [] = [] -- take (n+1) (x:xs) = x : take n xs -- (4.5) Factorial-------------------------------------------------------------- fac = hyloList algMul nats -- where algMul = either (const 1) mul --mul = uncurry (*) nats = (id -|- (split succ id)) . outNat -- (4.5.1) Factorial (alternative) --------------------------------------------- fac' = hyloList (either (const 1) (mul . (succ >< id))) ((id -|- (split id id)) . outNat) {-- cf: fac' = hyloList (either (const 1) g) nats' where g(n,m) = (n+1) * m nats' 0 = i1 () nats' (n+1) = i2 (n,n) --} -- (4.6) Square function ------------------------------------------------------- {-- pointwise: sq 0 = 0 sq (n+1) = 2*n+1 + sq n cf. Newton's binomial: (n+1)^2 = n^2 + 2n + 1 --} sq = hyloList summing odds summing = either (const 0) add odds = (id -|- (split impar id)) . outNat where impar n = 2*n+1 {-- odds pointwise: odds 0 = i1 () odds (n+1) = i2 (2*n+1,n) --} -- (4.6.1) Square function reusing anaList of factorial ---------------------------- sq' = (cataList summing) . fmap (\n->2*n-1) . (anaList nats) -- (4.7) Prefixes and suffixes ------------------------------------------------- prefixes :: Eq a => [a] -> [[a]] prefixes = cataList (either (const [[]]) scan) where scan(a,l) = [[]] ++ (map (a:) l) suffixes = anaList g where g = (id -|- (split cons p2)).outList diff :: Eq a => [a] -> [a] -> [a] diff x l = cataList (either nil (g l)) x where g l (a,x) = if (a `elem` l) then x else (a:x) -- (4.8) Grouping -------------------------------------------------------------- --nest :: Int -> [a] -> [[a]] nest n = anaList (g n) where -- g n [] = i1() -- g n l = i2(take n l,drop n l) g n = cond (==[]) (i1.(!)) (i2.(split (take n)(drop n))) -- (4.9) Advanced -------------------------------------------------------------- -- (++) as a list cataListmorphism ------------------------------------------------ ccat :: [a] -> [a] -> [a] ccat = cataList (either (const id) compose). map (:) where -- compose(f,g) = f.g compose = curry(ap.(id>