{-# LANGUAGE
FlexibleInstances
, GADTs
, MultiParamTypeClasses
, TypeOperators #-}
module Data.Label.Poly
(
Lens
, lens
, point
, get
, modify
, set
, iso
, (>-)
, for
)
where
import Control.Category
import Control.Arrow
import Prelude ()
import Data.Label.Point (Point (Point), Iso(..), identity, compose)
import qualified Data.Label.Point as Point
{-# INLINE lens #-}
{-# INLINE get #-}
{-# INLINE modify #-}
{-# INLINE set #-}
{-# INLINE (>-) #-}
{-# INLINE point #-}
{-# INLINE unpack #-}
data Lens cat f o where
Lens :: !(Point cat g i f o) -> Lens cat (f -> g) (o -> i)
Id :: ArrowApply cat => Lens cat f f
lens :: cat f o
-> cat (cat o i, f) g
-> Lens cat (f -> g) (o -> i)
lens g m = Lens (Point g m)
point :: Point cat g i f o -> Lens cat (f -> g) (o -> i)
point = Lens
get :: Lens cat (f -> g) (o -> i) -> cat f o
get = Point.get . unpack
modify :: Lens cat (f -> g) (o -> i) -> cat (cat o i, f) g
modify = Point.modify . unpack
set :: Arrow arr => Lens arr (f -> g) (o -> i) -> arr (i, f) g
set = Point.set . unpack
iso :: ArrowApply cat => Iso cat f o -> Iso cat g i -> Lens cat (f -> g) (o -> i)
iso (Iso f _) (Iso _ y) = lens f (app . arr (\(m, v) -> (y . m . f, v)))
instance ArrowApply arr => Category (Lens arr) where
id = Id
Lens f . Lens g = Lens (compose f g)
Id . u = u
u . Id = u
{-# INLINE id #-}
{-# INLINE (.) #-}
infix 7 >-
(>-) :: Arrow arr => Lens arr (j -> a) (i -> b) -> Lens arr (f -> g) (o -> i) -> Point arr g j f o
(>-) (Lens (Point f _)) (Lens l) = Point (Point.get l) (Point.modify l . first (arr (f .)))
(>-) (Lens (Point f _)) Id = Point id (app . first (arr (f .)))
(>-) Id l = unpack l
infix 7 `for`
for :: Arrow arr => Lens arr (j -> a) (i -> b) -> Lens arr (f -> g) (o -> i) -> Point arr g j f o
for = (>-)
unpack :: Lens cat (f -> g) (o -> i) -> Point cat g i f o
unpack Id = identity
unpack (Lens p) = p