{-# LANGUAGE
TypeOperators
, Arrows
, FlexibleInstances
, MultiParamTypeClasses
, TypeSynonymInstances #-}
module Data.Label.Point
(
Point (Point)
, get
, modify
, set
, identity
, compose
, Iso (..)
, inv
, Total
, Partial
, Failing
, ArrowFail (..)
)
where
import Control.Arrow
import Control.Applicative
import Control.Category
import Data.Orphans ()
import Prelude hiding ((.), id, const, curry, uncurry)
{-# INLINE get #-}
{-# INLINE modify #-}
{-# INLINE set #-}
{-# INLINE identity #-}
{-# INLINE compose #-}
{-# INLINE inv #-}
{-# INLINE const #-}
{-# INLINE curry #-}
data Point cat g i f o = Point (cat f o) (cat (cat o i, f) g)
get :: Point cat g i f o -> cat f o
get (Point g _) = g
modify :: Point cat g i f o -> cat (cat o i, f) g
modify (Point _ m) = m
set :: Arrow arr => Point arr g i f o -> arr (i, f) g
set p = modify p . first (arr const)
identity :: ArrowApply arr => Point arr f f o o
identity = Point id app
compose :: ArrowApply cat
=> Point cat t i b o
-> Point cat g t f b
-> Point cat g i f o
compose (Point f m) (Point g n)
= Point (f . g) (uncurry (curry n . curry m))
instance Arrow arr => Functor (Point arr f i f) where
fmap f x = pure f <*> x
{-# INLINE fmap #-}
instance Arrow arr => Applicative (Point arr f i f) where
pure a = Point (const a) (arr snd)
a <*> b = Point (arr app . (get a &&& get b)) $
proc (t, p) -> do (f, v) <- get a &&& get b -< p
q <- modify a -< (t . arr ($ v), p)
modify b -< (t . arr f, q)
{-# INLINE pure #-}
{-# INLINE (<*>) #-}
instance Alternative (Point Partial f view f) where
empty = Point zeroArrow zeroArrow
Point a b <|> Point c d = Point (a <|> c) (b <|> d)
infix 8 `Iso`
data Iso cat i o = Iso { fw :: cat i o, bw :: cat o i }
instance Category cat => Category (Iso cat) where
id = Iso id id
Iso a b . Iso c d = Iso (a . c) (d . b)
{-# INLINE id #-}
{-# INLINE (.) #-}
inv :: Iso cat i o -> Iso cat o i
inv i = Iso (bw i) (fw i)
type Total = (->)
type Partial = Kleisli Maybe
type Failing e = Kleisli (Either e)
class Arrow a => ArrowFail e a where
failArrow :: a e c
instance ArrowFail e Partial where
failArrow = Kleisli (const Nothing)
{-# INLINE failArrow #-}
instance ArrowFail e (Failing e) where
failArrow = Kleisli Left
{-# INLINE failArrow #-}
const :: Arrow arr => c -> arr b c
const a = arr (\_ -> a)
curry :: Arrow cat => cat (a, b) c -> (a -> cat b c)
curry m i = m . (const i &&& id)
uncurry :: ArrowApply cat => (a -> cat b c) -> cat (a, b) c
uncurry a = app . arr (first a)