extensible-0.9.2: Extensible, efficient, optics-friendly data types and effects
Copyright(c) Fumiaki Kinoshita 2018
LicenseBSD3
MaintainerFumiaki Kinoshita <[email protected]>
Safe HaskellNone
LanguageHaskell2010

Data.Extensible.Sum

Description

 
Synopsis
  • data (xs :: [k]) :/ (h :: k -> Type) where
  • hoist :: forall {k} g h (xs :: [k]). (forall (x :: k). g x -> h x) -> (xs :/ g) -> xs :/ h
  • embed :: forall {k} (x :: k) (xs :: [k]) h. x xs => h x -> xs :/ h
  • strike :: forall {k} h (x :: k) (xs :: [k]). x xs => (xs :/ h) -> Maybe (h x)
  • strikeAt :: forall {k} h (x :: k) (xs :: [k]). Membership xs x -> (xs :/ h) -> Maybe (h x)
  • (<:|) :: forall {k} h (x :: k) r (xs :: [k]). (h x -> r) -> ((xs :/ h) -> r) -> ((x ': xs) :/ h) -> r
  • exhaust :: forall {k} (h :: k -> Type) r. (('[] :: [k]) :/ h) -> r
  • embedAssoc :: forall {k1} {v} (xs :: [Assoc k1 v]) (k2 :: k1) (a :: v) h. Lookup xs k2 a => h (k2 ':> a) -> xs :/ h

Documentation

data (xs :: [k]) :/ (h :: k -> Type) where Source #

The extensible sum type

(:/) :: [k] -> (k -> Type) -> Type

Constructors

EmbedAt :: forall {k} (xs :: [k]) (x :: k) (h :: k -> Type). !(Membership xs x) -> h x -> xs :/ h 

Instances

Instances details
(Applicative f, Choice p) => Extensible f p ((:/) :: [k] -> (k -> Type) -> Type) Source # 
Instance details

Defined in Data.Extensible.Sum

Methods

pieceAt :: forall (xs :: [k]) h (x :: k). ExtensibleConstr ((:/) :: [k] -> (k -> Type) -> Type) xs h x => Membership xs x -> Optic' p f (xs :/ h) (h x) Source #

WrapForall (Lift :: Type -> Constraint) h xs => Lift (xs :/ h :: Type) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

lift :: Quote m => (xs :/ h) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (xs :/ h) -> Code m (xs :/ h) #

WrapForall Arbitrary h xs => Arbitrary (xs :/ h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

arbitrary :: Gen (xs :/ h) #

shrink :: (xs :/ h) -> [xs :/ h] #

Last xs xs => Bounded (xs :/ (Proxy :: k -> Type)) Source # 
Instance details

Defined in Data.Extensible.Sum

Methods

minBound :: xs :/ (Proxy :: k -> Type) #

maxBound :: xs :/ (Proxy :: k -> Type) #

Enum (xs :/ (Proxy :: k -> Type)) Source # 
Instance details

Defined in Data.Extensible.Sum

Methods

succ :: (xs :/ (Proxy :: k -> Type)) -> xs :/ (Proxy :: k -> Type) #

pred :: (xs :/ (Proxy :: k -> Type)) -> xs :/ (Proxy :: k -> Type) #

toEnum :: Int -> xs :/ (Proxy :: k -> Type) #

fromEnum :: (xs :/ (Proxy :: k -> Type)) -> Int #

enumFrom :: (xs :/ (Proxy :: k -> Type)) -> [xs :/ (Proxy :: k -> Type)] #

enumFromThen :: (xs :/ (Proxy :: k -> Type)) -> (xs :/ (Proxy :: k -> Type)) -> [xs :/ (Proxy :: k -> Type)] #

enumFromTo :: (xs :/ (Proxy :: k -> Type)) -> (xs :/ (Proxy :: k -> Type)) -> [xs :/ (Proxy :: k -> Type)] #

enumFromThenTo :: (xs :/ (Proxy :: k -> Type)) -> (xs :/ (Proxy :: k -> Type)) -> (xs :/ (Proxy :: k -> Type)) -> [xs :/ (Proxy :: k -> Type)] #

WrapForall Show h xs => Show (xs :/ h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

showsPrec :: Int -> (xs :/ h) -> ShowS #

show :: (xs :/ h) -> String #

showList :: [xs :/ h] -> ShowS #

WrapForall NFData h xs => NFData (xs :/ h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

rnf :: (xs :/ h) -> () #

WrapForall Eq h xs => Eq (xs :/ h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

(==) :: (xs :/ h) -> (xs :/ h) -> Bool #

(/=) :: (xs :/ h) -> (xs :/ h) -> Bool #

(Eq (xs :/ h), WrapForall Ord h xs) => Ord (xs :/ h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

compare :: (xs :/ h) -> (xs :/ h) -> Ordering #

(<) :: (xs :/ h) -> (xs :/ h) -> Bool #

(<=) :: (xs :/ h) -> (xs :/ h) -> Bool #

(>) :: (xs :/ h) -> (xs :/ h) -> Bool #

(>=) :: (xs :/ h) -> (xs :/ h) -> Bool #

max :: (xs :/ h) -> (xs :/ h) -> xs :/ h #

min :: (xs :/ h) -> (xs :/ h) -> xs :/ h #

(WrapForall Eq h xs, WrapForall Hashable h xs) => Hashable (xs :/ h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

hashWithSalt :: Int -> (xs :/ h) -> Int #

hash :: (xs :/ h) -> Int #

WrapForall Pretty h xs => Pretty (xs :/ h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

pretty :: (xs :/ h) -> Doc ann #

prettyList :: [xs :/ h] -> Doc ann #

type ExtensibleConstr ((:/) :: [k] -> (k -> Type) -> Type) (xs :: [k]) (h :: k -> Type) (x :: k) Source # 
Instance details

Defined in Data.Extensible.Sum

type ExtensibleConstr ((:/) :: [k] -> (k -> Type) -> Type) (xs :: [k]) (h :: k -> Type) (x :: k) = ()

hoist :: forall {k} g h (xs :: [k]). (forall (x :: k). g x -> h x) -> (xs :/ g) -> xs :/ h Source #

Change the wrapper.

embed :: forall {k} (x :: k) (xs :: [k]) h. x xs => h x -> xs :/ h Source #

O(1) lift a value.

strike :: forall {k} h (x :: k) (xs :: [k]). x xs => (xs :/ h) -> Maybe (h x) Source #

Try to extract something you want.

strikeAt :: forall {k} h (x :: k) (xs :: [k]). Membership xs x -> (xs :/ h) -> Maybe (h x) Source #

Try to extract something you want.

(<:|) :: forall {k} h (x :: k) r (xs :: [k]). (h x -> r) -> ((xs :/ h) -> r) -> ((x ': xs) :/ h) -> r infixr 1 Source #

O(1) Naive pattern match

exhaust :: forall {k} (h :: k -> Type) r. (('[] :: [k]) :/ h) -> r Source #

There is no empty union.

embedAssoc :: forall {k1} {v} (xs :: [Assoc k1 v]) (k2 :: k1) (a :: v) h. Lookup xs k2 a => h (k2 ':> a) -> xs :/ h Source #

Embed a value, but focuses on its key.