Abbie's Haskell compiler
You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
 
 

37 lines
745 B

{-# LANGUAGE RankNTypes #-}
module Ahc.Data.Lens where
import Control.Applicative
import Data.Functor.Identity
type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t
type Lens' s a = Lens s s a a
get :: Lens s t a b -> s -> a
get l = getConst . l Const
over :: Lens s t a b -> (a -> b) -> s -> t
over l m = runIdentity . l (Identity . m)
set :: Lens s t a b -> b -> s -> t
set l b a = over l (const b) a
(.~) :: Lens s t a b -> b -> s -> t
(.~) = set
infixr 4 .~
(%~) :: Lens s t a b -> (a -> b) -> s -> t
(%~) = over
infixr 4 %~
(^.) :: s -> Lens s t a b -> a
x ^. l = get l x
(&) :: t1 -> (t1 -> t2) -> t2
x & f = f x
infixr 0 &
lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b
lens sa sbt afb s = sbt s <$> afb (sa s)