{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
module Data.Parameterized.All
( All(..)
, allConst
) where
import Data.Functor.Const (Const(..))
import Data.Parameterized.Classes
import Data.Parameterized.TraversableF
newtype All (f :: k -> *) = All { All f -> forall (x :: k). f x
getAll :: forall x. f x }
instance FunctorF All where
fmapF :: (forall (x :: k). f x -> g x) -> All f -> All g
fmapF forall (x :: k). f x -> g x
f (All forall (x :: k). f x
a) = (forall (x :: k). g x) -> All g
forall k (f :: k -> *). (forall (x :: k). f x) -> All f
All (f x -> g x
forall (x :: k). f x -> g x
f f x
forall (x :: k). f x
a)
instance FoldableF All where
foldMapF :: (forall (s :: k). e s -> m) -> All e -> m
foldMapF forall (s :: k). e s -> m
toMonoid (All forall (x :: k). e x
x) = e Any -> m
forall (s :: k). e s -> m
toMonoid e Any
forall (x :: k). e x
x
instance ShowF f => Show (All f) where
show :: All f -> String
show (All forall (x :: k). f x
fa) = f Any -> String
forall k (f :: k -> *) (tp :: k). ShowF f => f tp -> String
showF f Any
forall (x :: k). f x
fa
instance EqF f => Eq (All f) where
(All forall (x :: k). f x
x) == :: All f -> All f -> Bool
== (All forall (x :: k). f x
y) = f Any -> f Any -> Bool
forall k (f :: k -> *) (a :: k). EqF f => f a -> f a -> Bool
eqF f Any
forall (x :: k). f x
x f Any
forall (x :: k). f x
y
allConst :: a -> All (Const a)
allConst :: a -> All (Const a)
allConst a
a = (forall (x :: k). Const a x) -> All (Const a)
forall k (f :: k -> *). (forall (x :: k). f x) -> All f
All (a -> Const a x
forall k a (b :: k). a -> Const a b
Const a
a)