{-# LANGUAGE TypeOperators #-} module Main where -- import the main Thrist module import Data.Thrist -- identity function on thrists in terms of foldrThrist: idThrist :: Thrist arr a c -> Thrist arr a c idThrist = foldrThrist Cons Nil -- Explore creating a reverse function using foldlThrist: -- The function takes a Thrist of tuples and reverses it (also swapping the -- fst and snd values). We use the Flipped newtype to allow us to pass the -- reversed Thrist through the foldl function, and then unwrap it at the end: reverseTuples :: Thrist (,) a b -> Thrist (,) b a reverseTuples = unflip . foldlThrist rev (Flipped Nil) where rev (Flipped t) (a, b) = Flipped $ Cons (b, a) t -- Composing a thrist of functions: -- Shows one way of composing a thrist of functions (a -> b) using foldl func :: [(Int, Char)] -> Int func = foldlThrist (flip(.)) id thristOfFuncs -- ...and here is our type-threaded list of functions: where thristOfFuncs :: Thrist (->) [(Int, Char)] Int thristOfFuncs = Cons head $ Cons fst $ Cons (+2) Nil -- type-checker infers Integer here, instead of a polymorphic Num class unless -- I explicitly put it in the signature. Is that normal? Interesting? --funcPoly :: (Num a) => [(a, b)] -> a funcPoly = foldlThrist (flip(.)) id thristOfFuncs where thristOfFuncs :: (Num a) => Thrist (->) [(a, b)] a thristOfFuncs = Cons head $ Cons fst $ Cons (+2) Nil -- a demo of the `appendThrist` function: appendedThrists :: (Num a) => Thrist (->) [(a, b)] a appendedThrists = (Cons head Nil) `appendThrist` (Cons fst Nil) `appendThrist` (Cons (+2) Nil) `appendThrist` Nil