extensible-0.5.1: Extensible, efficient, optics-friendly data types and effects

Copyright(c) Fumiaki Kinoshita 2018
LicenseBSD3
MaintainerFumiaki Kinoshita <fumiexcel@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Data.Extensible.Sum

Description

 
Synopsis

Documentation

data (h :: k -> *) :| (s :: [k]) where Source #

The extensible sum type

(:|) :: (k -> *) -> [k] -> *

Constructors

EmbedAt :: !(Membership xs x) -> h x -> h :| xs 
Instances
(Applicative f, Choice p) => Extensible f p ((:|) :: (k -> Type) -> [k] -> Type) Source # 
Instance details

Defined in Data.Extensible.Sum

Associated Types

type ExtensibleConstr (:|) h xs x :: Constraint Source #

Methods

pieceAt :: ExtensibleConstr (:|) h xs x => Membership xs x -> Optic' p f (h :| xs) (h x) Source #

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

Defined in Data.Extensible.Sum

Methods

minBound :: Proxy :| xs #

maxBound :: Proxy :| xs #

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

Defined in Data.Extensible.Sum

Methods

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

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

toEnum :: Int -> Proxy :| xs #

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

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

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

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

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

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

Defined in Data.Extensible.Dictionary

Methods

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

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

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

Defined in Data.Extensible.Dictionary

Methods

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

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

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

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

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

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

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

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

Defined in Data.Extensible.Dictionary

Methods

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

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

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

WrapForall Lift h xs => Lift (h :| xs) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

lift :: (h :| xs) -> Q Exp #

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

Defined in Data.Extensible.Dictionary

Methods

arbitrary :: Gen (h :| xs) #

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

WrapForall Hashable h xs => Hashable (h :| xs) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Methods

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

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

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

Defined in Data.Extensible.Dictionary

Methods

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

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

Defined in Data.Extensible.Dictionary

Methods

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

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

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

Defined in Data.Extensible.Sum

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

hoist :: (forall x. g x -> h x) -> (g :| xs) -> h :| xs Source #

Change the wrapper.

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

O(1) lift a value.

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

Try to extract something you want.

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

Try to extract something you want.

(<:|) :: (h x -> r) -> ((h :| xs) -> r) -> (h :| (x ': xs)) -> 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) -> h :| xs Source #

Embed a value, but focuses on its key.