{- | This module defines the @Accessor@ type. It should be imported with qualification. -} module Data.Accessor.Basic ( T, fromSetGet, fromLens, set, setMany, compose, (^=), get, (^.), modify, (^:), ($%), (<.), (.>), ) where {- | The access functions we propose, look very similar to those needed for List.mapAccumL (but parameter order is swapped) and State monad. They get the new value of the field and the record and return the old value of the field and the record with the updated field. -} newtype T r a = Cons {decons :: a -> r -> (a, r)} fromSetGet :: (a -> r -> r) -> (r -> a) -> T r a fromSetGet setF getF = Cons $ \x r -> (getF r, setF x r) fromLens :: (r -> (a, a -> r)) -> T r a fromLens lens = Cons $ \ x r -> let (y,f) = lens r in (y, f x) {- * Access helper functions similar to State methods -} {- | Set the value of a field. -} set :: T r a -> a -> r -> r set f x = snd . decons f x infixr 5 ^=, ^: infixl 0 $% {- | 'set' as infix operator. This lets us write @first ^= 2+3 $ second ^= 5+7 $ record@. -} (^=) :: T r a -> a -> (r -> r) (^=) = set {- | Set many fields at once. This function could also be used for initialisation of record, if record value with undefined fields is provided. Drawback: Since all types in a list must have the same type, you can set only values of the same type. -} setMany :: [r -> (a, r)] -> r -> r setMany = flip (foldl (\x f -> snd (f x))) {- | This is a general function, but it is especially useful for setting many values of different type at once. -} compose :: [r -> r] -> r -> r compose = flip (foldl (flip id)) {- | Get the value of a field. -} get :: T r a -> r -> a get f = fst . decons f undefined infixl 9 ^. {- | 'get' as infix operator. This lets us write @record^.field^.subfield@ -} (^.) :: r -> T r a -> a (^.) = flip get {- | Transform the value of a field by a function. -} modify :: T r a -> (a -> a) -> (r -> r) modify f g rOld = let (a,rNew) = decons f (g a) rOld in rNew {- | 'modify' as infix operator. This lets us write @record$%field^:subfield^:(1+)@ or @record$%field^:subfield^:(const 1)@. -} (^:) :: T r a -> (a -> a) -> (r -> r) (^:) = modify {- | Flipped version of '($)'. -} ($%) :: a -> (a -> b) -> b ($%) = flip ($) infixl 9 .> {- | Accessor composition: Combine an accessor with an accessor to a sub-field. Speak \"stack\". -} (.>) :: T a b -> T b c -> T a c (.>) f g = Cons $ \ cNew aOld -> let (bOld, aNew) = decons f bNew aOld (cOld, bNew) = decons g cNew bOld in (cOld, aNew) infixr 9 <. {- | Accessor composition the other direction. > (<.) = flip (.>) -} (<.) :: T b c -> T a b -> T a c (<.) = flip (.>)