module Data.Parameterized.TraversableFC
( TestEqualityFC(..)
, OrdFC(..)
, ShowFC(..)
, HashableFC(..)
, FunctorFC(..)
, FoldableFC(..)
, TraversableFC(..)
, traverseFC_
, forMFC_
, fmapFCDefault
, foldMapFCDefault
, allFC
, anyFC
, lengthFC
) where
import Control.Applicative (Const(..) )
import Control.Monad.Identity ( Identity (..) )
import Data.Coerce
import Data.Monoid
import GHC.Exts (build)
import Data.Type.Equality
import Data.Parameterized.Classes
class FunctorFC m where
fmapFC :: forall f g. (forall x . f x -> g x) ->
(forall x . m f x -> m g x)
class ShowFC (t :: (k -> *) -> l -> *) where
showFC :: forall f. (forall x. f x -> String)
-> (forall x. t f x -> String)
showFC sh x = showsPrecFC (\_prec z rest -> sh z ++ rest) 0 x []
showsPrecFC :: forall f. (forall x. Int -> f x -> ShowS) ->
(forall x. Int -> t f x -> ShowS)
showsPrecFC sh _prec x rest = showFC (\z -> sh 0 z []) x ++ rest
class HashableFC (t :: (k -> *) -> l -> *) where
hashWithSaltFC :: forall f. (forall x. Int -> f x -> Int) ->
(forall x. Int -> t f x -> Int)
class TestEqualityFC (t :: (k -> *) -> l -> *) where
testEqualityFC :: forall f. (forall x y. f x -> f y -> (Maybe (x :~: y))) ->
(forall x y. t f x -> t f y -> (Maybe (x :~: y)))
class TestEqualityFC t => OrdFC (t :: (k -> *) -> l -> *) where
compareFC :: forall f. (forall x y. f x -> f y -> OrderingF x y) ->
(forall x y. t f x -> t f y -> OrderingF x y)
(#.) :: Coercible b c => (b -> c) -> (a -> b) -> (a -> c)
(#.) _f = coerce
class FoldableFC (t :: (k -> *) -> l -> *) where
foldMapFC :: Monoid m => (forall s . e s -> m) -> t e c -> m
foldMapFC f = foldrFC (mappend . f) mempty
foldrFC :: (forall s . e s -> b -> b) -> b -> t e c -> b
foldrFC f z t = appEndo (foldMapFC (Endo #. f) t) z
foldlFC :: (forall s . b -> e s -> b) -> b -> t e c -> b
foldlFC f z t = appEndo (getDual (foldMapFC (\e -> Dual (Endo (\r -> f r e))) t)) z
foldrFC' :: (forall s . e s -> b -> b) -> b -> t e c -> b
foldrFC' f0 z0 xs = foldlFC (f' f0) id xs z0
where f' f k x z = k $! f x z
foldlFC' :: (forall s . b -> e s -> b) -> b -> t e c -> b
foldlFC' f0 z0 xs = foldrFC (f' f0) id xs z0
where f' f x k z = k $! f z x
toListFC :: (forall tp . f tp -> a) -> t f c -> [a]
toListFC f t = build (\c n -> foldrFC (\e v -> c (f e) v) n t)
allFC :: FoldableFC t => (forall tp . f tp -> Bool) -> t f c -> Bool
allFC p = getAll #. foldMapFC (All #. p)
anyFC :: FoldableFC t => (forall tp . f tp -> Bool) -> t f c -> Bool
anyFC p = getAny #. foldMapFC (Any #. p)
lengthFC :: FoldableFC t => t e c -> Int
lengthFC = foldrFC (const (+1)) 0
class (FunctorFC t, FoldableFC t) => TraversableFC t where
traverseFC :: Applicative m
=> (forall s . e s -> m (f s))
-> t e c
-> m (t f c)
fmapFCDefault :: TraversableFC t => (forall s . e s -> f s) -> t e c -> t f c
fmapFCDefault = \f -> runIdentity . traverseFC (Identity . f)
foldMapFCDefault :: (TraversableFC t, Monoid m) => (forall s . e s -> m) -> t e c -> m
foldMapFCDefault = \f -> getConst . traverseFC (Const . f)
traverseFC_ :: (FoldableFC t, Applicative f) => (forall s . e s -> f ()) -> t e c -> f ()
traverseFC_ f = foldrFC (\e r -> f e *> r) (pure ())
forMFC_ :: (FoldableFC t, Applicative f) => t e c -> (forall s . e s -> f ()) -> f ()
forMFC_ v f = traverseFC_ f v