barbies-0.1.2.0: Classes for working with types that can change clothes.

Safe HaskellNone
LanguageHaskell2010

Data.Barbie.Internal.Bare

Synopsis

Documentation

type family Wear f a where ... Source #

The Wear type-function allows one to define a Barbie-type as

data B f
  = B { f1 :: Wear f Int
      , f2 :: Wear f Bool
      }

This way, one can use Bare as a phantom that denotes no functor around the typw:

B { f1 :: 5, f2 = True } :: B Bare

Equations

Wear Bare a = a 
Wear (Target f) a = Target (W f) a 
Wear f a = f a 

data Bare a Source #

Bare is the only type such that Wear Bare a ~ a'.

class FunctorB b => BareB b where Source #

Class of Barbie-types defined using Wear and can therefore have Bare versions. Must satisfy:

bcover . bstrip = id
bstrip . bcover = id

bstripFrom :: BareB b => (forall a. f a -> a) -> b f -> b Bare Source #

Generalization of bstrip to arbitrary functors

bcoverWith :: BareB b => (forall a. a -> f a) -> b Bare -> b f Source #

Generalization of bcover to arbitrary functors

class Gbstrip rep where Source #

Minimal complete definition

gbstrip

Methods

gbstrip :: rep x -> Repl (Target I) (Target B) rep x Source #

Instances

Gbstrip (V1 *) Source # 

Methods

gbstrip :: V1 * x -> Repl (Target I) (Target B) (V1 *) x Source #

Gbstrip (U1 *) Source # 

Methods

gbstrip :: U1 * x -> Repl (Target I) (Target B) (U1 *) x Source #

(~) (* -> *) (K1 * i c) (Repl (Target I) (Target B) (K1 * i c)) => Gbstrip (K1 * i c) Source # 

Methods

gbstrip :: K1 * i c x -> Repl (Target I) (Target B) (K1 * i c) x Source #

(Gbstrip l, Gbstrip r) => Gbstrip ((:+:) * l r) Source # 

Methods

gbstrip :: (* :+: l) r x -> Repl (Target I) (Target B) ((* :+: l) r) x Source #

(Gbstrip l, Gbstrip r) => Gbstrip ((:*:) * l r) Source # 

Methods

gbstrip :: (* :*: l) r x -> Repl (Target I) (Target B) ((* :*: l) r) x Source #

Gbstrip x => Gbstrip (M1 * i c x) Source # 

Methods

gbstrip :: M1 * i c x x -> Repl (Target I) (Target B) (M1 * i c x) x Source #

gbstripDefault :: CanDeriveGenericInstance b => b Identity -> b Bare Source #

Default implementatio of bstrip based on Generic.

gbcoverDefault :: CanDeriveGenericInstance' b => b Bare -> b Identity Source #

Default implementatio of bstrip based on Generic.

type CanDeriveGenericInstance b = (Generic (b (Target I)), Generic (b (Target B)), Gbstrip (Rep (b (Target I))), Rep (b (Target B)) ~ Repl (Target I) (Target B) (Rep (b (Target I)))) Source #

All types that admit a generic FunctorB' instance, and have all their occurrences of f under a Wear admit a generic BareB instance.

type CanDeriveGenericInstance' b = (Generic (b (Target I)), Generic (b (Target B)), Gbcover (Rep (b (Target B))), Rep (b (Target I)) ~ Repl (Target B) (Target I) (Rep (b (Target B)))) Source #