optics-core-0.3: Optics as an abstract interface: core definitions

Safe HaskellNone
LanguageHaskell2010

Optics.Internal.Indexed

Description

Internal implementation details of indexed optics.

This module is intended for internal use only, and may change without warning in subsequent releases.

Synopsis

Documentation

class is ~ NoIx => AcceptsEmptyIndices (f :: Symbol) (is :: IxList) Source #

Show useful error message when a function expects optics without indices.

Instances
AcceptsEmptyIndices f ([] :: [Type]) Source # 
Instance details

Defined in Optics.Internal.Indexed

((TypeError ((Text "\8216" :<>: Text f) :<>: Text "\8217 accepts only optics with no indices") :: Constraint), (x ': xs) ~ NoIx) => AcceptsEmptyIndices f (x ': xs) Source # 
Instance details

Defined in Optics.Internal.Indexed

class NonEmptyIndices (is :: IxList) Source #

Check whether a list of indices is not empty and generate sensible error message if it's not.

Instances
(TypeError (Text "Indexed optic is expected") :: Constraint) => NonEmptyIndices ([] :: [Type]) Source # 
Instance details

Defined in Optics.Internal.Indexed

NonEmptyIndices (x ': xs) Source # 
Instance details

Defined in Optics.Internal.Indexed

class is ~ '[i] => HasSingleIndex (is :: IxList) (i :: Type) Source #

Generate sensible error messages in case a user tries to pass either an unindexed optic or indexed optic with unflattened indices where indexed optic with a single index is expected.

Instances
((TypeError (Text "Indexed optic is expected") :: Constraint), ([] :: [Type]) ~ (i ': ([] :: [Type]))) => HasSingleIndex ([] :: [Type]) i Source # 
Instance details

Defined in Optics.Internal.Indexed

((TypeError (Text "Use icomposeN to flatten indices of type " :<>: ShowTypes is) :: Constraint), is ~ (i1 ': (i2 ': (i3 ': (i4 ': (i5 ': (i6 ': is')))))), is ~ (i ': ([] :: [Type]))) => HasSingleIndex (i1 ': (i2 ': (i3 ': (i4 ': (i5 ': (i6 ': is')))))) i Source # 
Instance details

Defined in Optics.Internal.Indexed

((TypeError (Text "Use icompose5 to flatten indices of type " :<>: ShowTypes is) :: Constraint), is ~ (i1 ': (i2 ': (i3 ': (i4 ': (i5 ': ([] :: [Type])))))), is ~ (i ': ([] :: [Type]))) => HasSingleIndex (i1 ': (i2 ': (i3 ': (i4 ': (i5 ': ([] :: [Type])))))) i Source # 
Instance details

Defined in Optics.Internal.Indexed

((TypeError (Text "Use icompose4 to combine indices of type " :<>: ShowTypes is) :: Constraint), is ~ (i1 ': (i2 ': (i3 ': (i4 ': ([] :: [Type]))))), is ~ (i ': ([] :: [Type]))) => HasSingleIndex (i1 ': (i2 ': (i3 ': (i4 ': ([] :: [Type]))))) i Source # 
Instance details

Defined in Optics.Internal.Indexed

((TypeError (Text "Use icompose3 to combine indices of type " :<>: ShowTypes is) :: Constraint), is ~ (i1 ': (i2 ': (i3 ': ([] :: [Type])))), is ~ (i ': ([] :: [Type]))) => HasSingleIndex (i1 ': (i2 ': (i3 ': ([] :: [Type])))) i Source # 
Instance details

Defined in Optics.Internal.Indexed

((TypeError (Text "Use (<%>) or icompose to combine indices of type " :<>: ShowTypes is) :: Constraint), is ~ (i1 ': (i2 ': ([] :: [Type]))), is ~ (i ': ([] :: [Type]))) => HasSingleIndex (i1 ': (i2 ': ([] :: [Type]))) i Source # 
Instance details

Defined in Optics.Internal.Indexed

HasSingleIndex (i ': ([] :: [Type])) i Source # 
Instance details

Defined in Optics.Internal.Indexed

type family ShowTypes (types :: [Type]) :: ErrorMessage where ... Source #

Equations

ShowTypes '[i] = QuoteType i 
ShowTypes '[i, j] = (QuoteType i :<>: Text " and ") :<>: QuoteType j 
ShowTypes (i ': is) = (QuoteType i :<>: Text ", ") :<>: ShowTypes is 

data IntT f a Source #

Constructors

IntT !Int (f a) 

unIntT :: IntT f a -> f a Source #

newtype Indexing f a Source #

Constructors

Indexing 

Fields

Instances
Functor f => Functor (Indexing f) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

fmap :: (a -> b) -> Indexing f a -> Indexing f b #

(<$) :: a -> Indexing f b -> Indexing f a #

Applicative f => Applicative (Indexing f) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

pure :: a -> Indexing f a #

(<*>) :: Indexing f (a -> b) -> Indexing f a -> Indexing f b #

liftA2 :: (a -> b -> c) -> Indexing f a -> Indexing f b -> Indexing f c #

(*>) :: Indexing f a -> Indexing f b -> Indexing f b #

(<*) :: Indexing f a -> Indexing f b -> Indexing f a #

indexing :: ((a -> Indexing f b) -> s -> Indexing f t) -> (Int -> a -> f b) -> s -> f t Source #

Index a traversal by position of visited elements.

conjoined :: is `HasSingleIndex` i => Optic k NoIx s t a b -> Optic k is s t a b -> Optic k is s t a b Source #

Construct a conjoined indexed optic that provides a separate code path when used without indices. Useful for defining indexed optics that are as efficient as their unindexed equivalents when used without indices.

Note: conjoined f g is well-defined if and only if f ≡ noIx g.