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

Copyright(c) Fumiaki Kinoshita 2017
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 k f p ((:|) k) Source # 

Associated Types

type ExtensibleConstr f (t :: (f -> *) -> [f] -> *) (h :: f -> *) (xs :: [f]) (x :: f) :: Constraint Source #

Methods

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

(∈) k (Last k xs) xs => Bounded ((:|) k (Proxy k) xs) Source # 

Methods

minBound :: (k :| Proxy k) xs #

maxBound :: (k :| Proxy k) xs #

Enum ((:|) k (Proxy k) xs) Source # 

Methods

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

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

toEnum :: Int -> (k :| Proxy k) xs #

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

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

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

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

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

type ExtensibleConstr k ((:|) k) h xs x Source # 
type ExtensibleConstr k ((:|) k) h xs x = ()

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 :: Associate k a xs => h (k :> a) -> h :| xs Source #

Embed a value, but focuses on its key.