extensible-0.8.3: 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

Documentation

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

The extensible sum type

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

Constructors

EmbedAt :: !(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

Associated Types

type ExtensibleConstr (:/) xs h x Source #

Methods

pieceAt :: forall (xs :: [k0]) h (x :: k0). ExtensibleConstr (:/) 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 :: (xs :/ h) -> Q Exp #

liftTyped :: (xs :/ h) -> Q (TExp (xs :/ h)) #

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

Defined in Data.Extensible.Sum

Methods

minBound :: xs :/ Proxy #

maxBound :: xs :/ Proxy #

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

Defined in Data.Extensible.Sum

Methods

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

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

toEnum :: Int -> xs :/ Proxy #

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

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

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

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

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

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 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 Arbitrary h xs => Arbitrary (xs :/ h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

arbitrary :: Gen (xs :/ h) #

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

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 NFData h xs => NFData (xs :/ h) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

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

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 x. g x -> h x) -> (xs :/ g) -> xs :/ h Source #

Change the wrapper.

embed :: x xs => h x -> xs :/ h Source #

O(1) lift a value.

strike :: forall h x xs. x xs => (xs :/ h) -> Maybe (h x) Source #

Try to extract something you want.

strikeAt :: forall h x xs. Membership xs x -> (xs :/ h) -> Maybe (h x) Source #

Try to extract something you want.

(<:|) :: (h x -> r) -> ((xs :/ h) -> r) -> ((x ': xs) :/ h) -> r infixr 1 Source #

O(1) Naive pattern match

exhaust :: ('[] :/ h) -> r Source #

There is no empty union.

embedAssoc :: Lookup xs k a => h (k :> a) -> xs :/ h Source #

Embed a value, but focuses on its key.