{-# LANGUAGE ExistentialQuantification, FlexibleContexts #-} {-# OPTIONS_GHC -Wall #-} ---------------------------------------------------------------------- -- | -- Module : Data.Zip.FoldR -- Copyright : (c) Conal Elliott 2008 -- License : BSD3 -- -- Maintainer : conal@conal.net -- Stability : experimental -- -- Zipping of non-strict right folds. -- -- See . Inspired by "Beautiful Folds" by -- Max Rabkin ---------------------------------------------------------------------- module Data.Zip.FoldR ( FoldR(..), cfoldr , WithCont, FoldRC, cfoldrc ) where import Prelude hiding (zip) -- From TypeCompose import Data.Zip import Data.WithCont -- foldr :: (b -> a -> a) -> a -> [b] -> a -- | Data representation of a right fold data FoldR b a = F (b -> a -> a) a -- | Interpretation of a 'FoldR' as non-strict cfoldr :: FoldR b a -> [b] -> a cfoldr ~(F op e) = foldr op e -- Non-strict right-fold zipping zipF :: FoldR b a -> FoldR b a' -> FoldR b (a,a') ~(F op e) `zipF` ~(F op' e') = F op'' (e,e') where b `op''` ~(a,a') = (b `op` a, b `op'` a') instance Zip (FoldR b) where zip = zipF -- | Non-strict right fold with continuation. type FoldRC b = WithCont (FoldR b) -- | Interpretation of a 'FoldRC' cfoldrc :: FoldRC b a -> [b] -> a cfoldrc (WC f k) = fmap k (cfoldr f)