{-# LANGUAGE
FlexibleInstances
, MultiParamTypeClasses
, TypeOperators
#-}
module Data.Label.Mono
( Lens
, lens
, get
, modify
, point
, set
, iso
, (:->)
, (:~>)
)
where
import Control.Category
import Control.Arrow
import Data.Label.Point (Point, Iso (..), Total, Partial)
import Prelude ()
import qualified Data.Label.Poly as Poly
{-# INLINE lens #-}
{-# INLINE get #-}
{-# INLINE modify #-}
{-# INLINE set #-}
{-# INLINE point #-}
{-# INLINE iso #-}
type Lens cat f o = Poly.Lens cat (f -> f) (o -> o)
lens :: cat f o
-> (cat (cat o o, f) f)
-> Lens cat f o
lens = Poly.lens
get :: Lens cat f o -> cat f o
get = Poly.get
modify :: Lens cat f o -> cat (cat o o, f) f
modify = Poly.modify
set :: Arrow arr => Lens arr f o -> arr (o, f) f
set = Poly.set
point :: Point cat f o f o -> Lens cat f o
point = Poly.point
iso :: ArrowApply cat => Iso cat f o -> Lens cat f o
iso (Iso f b) = lens f (app . arr (\(m, v) -> (b . m . f, v)))
type f :-> o = Lens Total f o
type f :~> o = Lens Partial f o