hkd-lens-0.0.1: Generic lens/prism/traversal-kinded data.

Safe HaskellSafe
LanguageHaskell2010

HKD.Lens

Contents

Synopsis

Lens Wrappers

LensOf, PrismOf, and TraversalOf wrap lenses, prisms, and traversals. 'LensOf s t n', for instance, wrapps some 'lens s s' a b', with 's\'', a, and b, determined by s, t, and n.

newtype LensOf s t n Source #

Constructors

LensOf 

Fields

  • getLensOf :: Lens s (SubSub s t n) (GetNProxyFrom s n) (GetNProxyFrom t n)
     

newtype PrismOf s t n Source #

Constructors

PrismOf 

Fields

  • getPrismOf :: Prism s (SubSub s t n) (GetNProxyFrom s n) (GetNProxyFrom t n)
     

newtype TraversalOf s t n Source #

Constructors

TraversalOf 

Fields

  • getTraversalOf :: Traversal s (SubSub s t n) (GetNProxyFrom s n) (GetNProxyFrom t n)
     

Type of Lens Kinded Data

LensesOf, PrismsOf, and TraversalsOf determine the appropriate "lens-kinded data" type.

type LensesOf (s :: Type) (t :: Type) (i :: Nat) = MakeNProxyHK (LensOf s t) s i Source #

type PrismsOf (s :: Type) (t :: Type) (i :: Nat) = MakeNProxyHK (PrismOf s t) s i Source #

type TraversalsOf (s :: Type) (t :: Type) (i :: Nat) = MakeNProxyHK (TraversalOf s t) s i Source #

Making Lens Kinded Data

Lens Kinded Data, or higher kinded data parameterized such that data fields are populated with lenses, are made with makeLensesOf, makePrismsOf, and makeTraversalOf

makeTraversalsOf :: forall c o s t i. (MakeLowerKinded o s ~ i, GetSourceAndTarget o ~ (s, t), Generic o, Generic s, Generic t, Generic i, GLensLike End c (TraversalOf s t) (Rep i) (Rep o)) => o Source #

makeLensesOf :: forall o s t i. (MakeLowerKinded o s ~ i, GetSourceAndTarget o ~ (s, t), Generic o, Generic s, Generic t, Generic i, GLensLike End "" (LensOf s t) (Rep i) (Rep o)) => o Source #

makePrismsOf :: forall c o s t i. (MakeLowerKinded o s ~ i, GetSourceAndTarget o ~ (s, t), Generic o, Generic s, Generic t, Generic i, GLensLike End c (PrismOf s t) (Rep i) (Rep o)) => o Source #

NProxyK

NProxyK is a multi-kinded data family that allows Nats to be used in place of types of any arity. They are used in this library to track data's parameters' occurences in their fields.

type family ToNProxyK (n :: Nat) (a :: k) :: k where ... Source #

Equations

ToNProxyK n (a :: Type) = NProxyK n a 
ToNProxyK n (a :: j -> k) = NProxyK n a 

data family NProxyK (n :: Nat) (a :: j) :: k Source #

Instances
data NProxyK n (a :: Type) Source # 
Instance details

Defined in HKD.Lens

data NProxyK n (a :: Type) = NProxyK0
data NProxyK n (f :: j -> k) Source # 
Instance details

Defined in HKD.Lens

data NProxyK n (f :: j -> k) = NProxyK1