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

Safe HaskellSafe
LanguageHaskell2010

Optics.Internal.Optic.TypeLevel

Description

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

Synopsis

Documentation

type IxList = [Type] Source #

A list of index types, used for indexed optics.

Since: 0.2

type NoIx = ('[] :: IxList) Source #

An alias for an empty index-list

type WithIx i = ('[i] :: IxList) Source #

Singleton index list

type family QuoteType (x :: Type) :: ErrorMessage where ... Source #

Show a type surrounded by quote marks.

Equations

QuoteType x = (Text "\8216" :<>: ShowType x) :<>: Text "\8217" 

type family QuoteSymbol (x :: Symbol) :: ErrorMessage where ... Source #

Show a symbol surrounded by quote marks.

Equations

QuoteSymbol x = (Text "\8216" :<>: Text x) :<>: Text "\8217" 

type family ShowSymbolWithOrigin symbol origin :: ErrorMessage where ... Source #

Equations

ShowSymbolWithOrigin symbol origin = (((Text " " :<>: QuoteSymbol symbol) :<>: Text " (from ") :<>: Text origin) :<>: Text ")" 

type family ShowSymbolsWithOrigin (fs :: [(Symbol, Symbol)]) :: ErrorMessage where ... Source #

Equations

ShowSymbolsWithOrigin '['(symbol, origin)] = ShowSymbolWithOrigin symbol origin 
ShowSymbolsWithOrigin ('(symbol, origin) ': rest) = ShowSymbolWithOrigin symbol origin :$$: ShowSymbolsWithOrigin rest 

type family ShowOperators (ops :: [Symbol]) :: ErrorMessage where ... Source #

Equations

ShowOperators '[op] = QuoteSymbol op :<>: Text " (from Optics.Operators)" 
ShowOperators (op ': rest) = (QuoteSymbol op :<>: Text " ") :<>: ShowOperators rest 

type family AppendEliminations a b where ... Source #

Equations

AppendEliminations '(fs1, ops1) '(fs2, ops2) = '(Append fs1 fs2, Append ops1 ops2) 

type family ShowEliminations forms :: ErrorMessage where ... Source #

Equations

ShowEliminations '(fs, ops) = ShowSymbolsWithOrigin fs :$$: (Text " " :<>: ShowOperators ops) 

data RepDefined Source #

Constructors

RepDefined 

type family AnyHasRep (s :: Type -> Type) (t :: Type -> Type) :: RepDefined Source #

This type family should be called with applications of Rep on both sides, and will reduce to RepDefined if at least one of them is defined; otherwise it is stuck.

Instances
type AnyHasRep s (t x) Source # 
Instance details

Defined in Optics.Internal.Optic.TypeLevel

type AnyHasRep s (t x) = RepDefined
type AnyHasRep (s x) t Source # 
Instance details

Defined in Optics.Internal.Optic.TypeLevel

type AnyHasRep (s x) t = RepDefined

type family Curry (xs :: IxList) (y :: Type) :: Type where ... Source #

Curry a type-level list.

In pseudo (dependent-)Haskell:

Curry xs y = foldr (->) y xs

Equations

Curry '[] y = y 
Curry (x ': xs) y = x -> Curry xs y 

type family Append (xs :: [k]) (ys :: [k]) :: [k] where ... Source #

Append two type-level lists together.

Equations

Append '[] ys = ys 
Append xs '[] = xs 
Append (x ': xs) ys = x ': Append xs ys 

class CurryCompose xs where Source #

Class that is inhabited by all type-level lists xs, providing the ability to compose a function under Curry xs.

Methods

composeN :: (i -> j) -> Curry xs i -> Curry xs j Source #

Compose a function under Curry xs. This generalises (.) (aka fmap for (->)) to work for curried functions with one argument for each type in the list.

Instances
CurryCompose ([] :: [Type]) Source # 
Instance details

Defined in Optics.Internal.Optic.TypeLevel

Methods

composeN :: (i -> j) -> Curry [] i -> Curry [] j Source #

CurryCompose xs => CurryCompose (x ': xs) Source # 
Instance details

Defined in Optics.Internal.Optic.TypeLevel

Methods

composeN :: (i -> j) -> Curry (x ': xs) i -> Curry (x ': xs) j Source #