module Data.Label.Abstract where
import Control.Arrow
import Prelude hiding ((.), id)
import Control.Applicative
import Control.Category
data Point arr f i o = Point
{ _get :: f `arr` o
, _set :: (i, f) `arr` f
}
_modify :: ArrowApply arr => Point arr f i o -> (o `arr` i, f) `arr` f
_modify l = proc (m, f) -> do i <- m . _get l -<< f; _set l -< (i, f)
newtype Lens arr f a = Lens { unLens :: Point arr f a a }
lens :: (f `arr` a) -> ((a, f) `arr` f) -> Lens arr f a
lens g s = Lens (Point g s)
get :: Arrow arr => Lens arr f a -> f `arr` a
get = _get . unLens
set :: Arrow arr => Lens arr f a -> (a, f) `arr` f
set = _set . unLens
modify :: ArrowApply arr => Lens arr f o -> (o `arr` o, f) `arr` f
modify = _modify . unLens
instance ArrowApply arr => Category (Lens arr) where
id = lens id (arr fst)
Lens a . Lens b = lens (_get a . _get b) (_modify b . first (curryA (_set a)))
where curryA f = arr (\i -> f . arr (i,))
instance Arrow arr => Functor (Point arr f i) where
fmap f x = Point (arr f . _get x) (_set x)
instance Arrow arr => Applicative (Point arr f i) where
pure a = Point (arr (const a)) (arr snd)
a <*> b = Point (arr app . (_get a &&& _get b)) (_set b . (arr fst &&& _set a))
bimap :: Arrow arr => (o' `arr` o) -> (i `arr` i') -> Point arr f i' o' -> Point arr f i o
bimap f g l = Point (f . _get l) (_set l . first g)
infix 8 `for`
for :: Arrow arr => (i `arr` o) -> Lens arr f o -> Point arr f i o
for p = bimap id p . unLens
infix 8 `Bij`
data Bijection arr a b = Bij { fw :: a `arr` b, bw :: b `arr` a }
instance Category arr => Category (Bijection arr) where
id = Bij id id
Bij a b . Bij c d = a . c `Bij` d . b
liftBij :: Functor f => Bijection (->) a b -> Bijection (->) (f a) (f b)
liftBij a = fmap (fw a) `Bij` fmap (bw a)
infixr 8 `iso`
class Iso arr f where
iso :: Bijection arr a b -> f a `arr` f b
osi :: Iso arr f => Bijection arr b a -> f a `arr` f b
osi (Bij a b) = iso (Bij b a)
instance Arrow arr => Iso arr (Lens arr f) where
iso bi = arr ((\a -> lens (fw bi . _get a) (_set a . first (bw bi))) . unLens)
instance Arrow arr => Iso arr (Bijection arr a) where
iso = arr . (.)