eliminators-0.9.5: Dependently typed elimination functions using singletons
Copyright(C) 2021 Ryan Scott
LicenseBSD-style (see the file LICENSE)
MaintainerRyan Scott
StabilityExperimental
PortabilityGHC
Safe HaskellTrustworthy
LanguageGHC2021

Data.Eliminator.Semigroup

Description

Eliminator functions for data types in Data.Semigroup. All of these are re-exported from Data.Eliminator with the following exceptions:

Documentation

elimAll :: forall (p :: All ~> Type) (s :: All). Sing s -> (forall (f0 :: Bool). Sing f0 -> Apply p ('All f0)) -> Apply p s Source #

type family ElimAll (p :: All ~> Type) (s :: All) (p1 :: forall (f0 :: Bool) -> Apply p ('All f0)) :: Apply p s where ... Source #

Equations

ElimAll p ('All s0) (useThis :: forall (f0 :: Bool) -> Apply p ('All f0)) = useThis s0 

elimAny :: forall (p :: Any ~> Type) (s :: Any). Sing s -> (forall (f0 :: Bool). Sing f0 -> Apply p ('Any f0)) -> Apply p s Source #

type family ElimAny (p :: Any ~> Type) (s :: Any) (p1 :: forall (f0 :: Bool) -> Apply p ('Any f0)) :: Apply p s where ... Source #

Equations

ElimAny p ('Any s0) (useThis :: forall (f0 :: Bool) -> Apply p ('Any f0)) = useThis s0 

elimArg :: forall a b (p :: Arg a b ~> Type) (s :: Arg a b). Sing s -> (forall (f0 :: a). Sing f0 -> forall (f1 :: b). Sing f1 -> Apply p ('Arg f0 f1)) -> Apply p s Source #

type family ElimArg (p :: Arg a b ~> Type) (s :: Arg a b) (p1 :: forall (f0 :: a) (f1 :: b) -> Apply p ('Arg f0 f1)) :: Apply p s where ... Source #

Equations

ElimArg (p :: Arg a b ~> Type) ('Arg s0 s1 :: Arg a b) (useThis :: forall (f0 :: a) (f1 :: b) -> Apply p ('Arg f0 f1)) = useThis s0 s1 

elimDual :: forall a (p :: Dual a ~> Type) (s :: Dual a). Sing s -> (forall (f0 :: a). Sing f0 -> Apply p ('Dual f0)) -> Apply p s Source #

type family ElimDual (p :: Dual a ~> Type) (s :: Dual a) (p1 :: forall (f0 :: a) -> Apply p ('Dual f0)) :: Apply p s where ... Source #

Equations

ElimDual (p :: Dual a ~> Type) ('Dual s0 :: Dual a) (useThis :: forall (f0 :: a) -> Apply p ('Dual f0)) = useThis s0 

elimFirst :: forall a (p :: First a ~> Type) (s :: First a). Sing s -> (forall (f0 :: a). Sing f0 -> Apply p ('First f0)) -> Apply p s Source #

type family ElimFirst (p :: First a ~> Type) (s :: First a) (p1 :: forall (f0 :: a) -> Apply p ('First f0)) :: Apply p s where ... Source #

Equations

ElimFirst (p :: First a ~> Type) ('First s0 :: First a) (useThis :: forall (f0 :: a) -> Apply p ('First f0)) = useThis s0 

elimLast :: forall a (p :: Last a ~> Type) (s :: Last a). Sing s -> (forall (f0 :: a). Sing f0 -> Apply p ('Last f0)) -> Apply p s Source #

type family ElimLast (p :: Last a ~> Type) (s :: Last a) (p1 :: forall (f0 :: a) -> Apply p ('Last f0)) :: Apply p s where ... Source #

Equations

ElimLast (p :: Last a ~> Type) ('Last s0 :: Last a) (useThis :: forall (f0 :: a) -> Apply p ('Last f0)) = useThis s0 

elimMax :: forall a (p :: Max a ~> Type) (s :: Max a). Sing s -> (forall (f0 :: a). Sing f0 -> Apply p ('Max f0)) -> Apply p s Source #

type family ElimMax (p :: Max a ~> Type) (s :: Max a) (p1 :: forall (f0 :: a) -> Apply p ('Max f0)) :: Apply p s where ... Source #

Equations

ElimMax (p :: Max a ~> Type) ('Max s0 :: Max a) (useThis :: forall (f0 :: a) -> Apply p ('Max f0)) = useThis s0 

elimMin :: forall a (p :: Min a ~> Type) (s :: Min a). Sing s -> (forall (f0 :: a). Sing f0 -> Apply p ('Min f0)) -> Apply p s Source #

type family ElimMin (p :: Min a ~> Type) (s :: Min a) (p1 :: forall (f0 :: a) -> Apply p ('Min f0)) :: Apply p s where ... Source #

Equations

ElimMin (p :: Min a ~> Type) ('Min s0 :: Min a) (useThis :: forall (f0 :: a) -> Apply p ('Min f0)) = useThis s0 

elimProduct :: forall a (p :: Product a ~> Type) (s :: Product a). Sing s -> (forall (f0 :: a). Sing f0 -> Apply p ('Product f0)) -> Apply p s Source #

type family ElimProduct (p :: Product a ~> Type) (s :: Product a) (p1 :: forall (f0 :: a) -> Apply p ('Product f0)) :: Apply p s where ... Source #

Equations

ElimProduct (p :: Product a ~> Type) ('Product s0 :: Product a) (useThis :: forall (f0 :: a) -> Apply p ('Product f0)) = useThis s0 

elimSum :: forall a (p :: Sum a ~> Type) (s :: Sum a). Sing s -> (forall (f0 :: a). Sing f0 -> Apply p ('Sum f0)) -> Apply p s Source #

type family ElimSum (p :: Sum a ~> Type) (s :: Sum a) (p1 :: forall (f0 :: a) -> Apply p ('Sum f0)) :: Apply p s where ... Source #

Equations

ElimSum (p :: Sum a ~> Type) ('Sum s0 :: Sum a) (useThis :: forall (f0 :: a) -> Apply p ('Sum f0)) = useThis s0 

elimWrappedMonoid :: forall m (p :: WrappedMonoid m ~> Type) (s :: WrappedMonoid m). Sing s -> (forall (f0 :: m). Sing f0 -> Apply p ('WrapMonoid f0)) -> Apply p s Source #

type family ElimWrappedMonoid (p :: WrappedMonoid m ~> Type) (s :: WrappedMonoid m) (p1 :: forall (f0 :: m) -> Apply p ('WrapMonoid f0)) :: Apply p s where ... Source #

Equations

ElimWrappedMonoid (p :: WrappedMonoid m ~> Type) ('WrapMonoid s0 :: WrappedMonoid m) (useThis :: forall (f0 :: m) -> Apply p ('WrapMonoid f0)) = useThis s0