{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Pinch.Internal.FoldList
( FoldList
, map
, replicate
, replicateM
, F.foldl'
, F.foldr
, F.toList
, fromFoldable
, fromMap
, T.mapM
, T.sequence
) where
import Prelude hiding (foldr, map, mapM, replicate, sequence)
#if __GLASGOW_HASKELL__ < 709
import Control.Applicative
#endif
import Control.DeepSeq (NFData (..))
import Data.Hashable (Hashable (..))
import Data.List (intercalate)
import Data.Semigroup
import Data.Typeable (Typeable)
import qualified Control.Monad as M
import qualified Data.Foldable as F
import qualified Data.List as L
import qualified Data.Traversable as T
newtype FoldList a = FoldList (forall r. (r -> a -> r) -> r -> r)
deriving Typeable
fromMap
:: (forall r. (r -> k -> v -> r) -> r -> m k v -> r)
-> m k v
-> FoldList (k, v)
fromMap foldlWithKey m = FoldList (\k r -> foldlWithKey (go k) r m)
where
go k r a b = k r (a, b)
{-# INLINE go #-}
{-# INLINE fromMap #-}
fromFoldable :: F.Foldable f => f a -> FoldList a
fromFoldable l = FoldList (\k r -> F.foldl' k r l)
{-# INLINE fromFoldable #-}
map :: (a -> b) -> FoldList a -> FoldList b
map f (FoldList l) = FoldList $ \k r0 -> l (\r1 a -> k r1 (f a)) r0
{-# INLINE map #-}
replicate :: Int -> a -> FoldList a
replicate n a = fromFoldable (L.replicate n a)
{-# INLINE replicate #-}
replicateM :: Monad m => Int -> m a -> m (FoldList a)
replicateM n = M.liftM fromFoldable . M.replicateM n
{-# INLINE replicateM #-}
instance Show a => Show (FoldList a) where
show l = "[" ++ intercalate ", " (F.foldr go [] l) ++ "]"
where
go a xs = show a:xs
instance Functor FoldList where
fmap = map
{-# INLINE fmap #-}
instance F.Foldable FoldList where
foldMap f (FoldList l) = l (\r a -> r `mappend` f a) mempty
{-# INLINE foldMap #-}
foldl' f r (FoldList l) = l f r
{-# INLINE foldl' #-}
instance T.Traversable FoldList where
sequenceA (FoldList f) =
f (\l a -> go <$> l <*> a) (pure (FoldList (\_ r -> r)))
where
go (FoldList xs) x = FoldList (\k r -> k (xs k r) x)
{-# INLINE go #-}
{-# INLINE sequenceA #-}
instance Eq a => Eq (FoldList a) where
l == r = F.toList l == F.toList r
instance NFData a => NFData (FoldList a) where
rnf (FoldList l) = l (\() a -> rnf a `seq` ()) ()
instance Hashable a => Hashable (FoldList a) where
hashWithSalt s (FoldList l) = l hashWithSalt s
instance Semigroup (FoldList a) where
FoldList f1 <> FoldList f2 =
FoldList $ \cons nil -> f2 cons (f1 cons nil)
{-# INLINE (<>) #-}
instance Monoid (FoldList a) where
mempty = FoldList (\_ r -> r)
{-# INLINE mempty #-}
FoldList f1 `mappend` FoldList f2 = FoldList $ \cons nil -> f2 cons (f1 cons nil)
{-# INLINE mappend #-}