{- | This module defines the @Accessor@ type. It should be imported with qualification. -} module Data.Accessor.Basic ( T, fromSetGet, fromLens, fromWrapper, self, null, result, set, (^=), compose, get, (^.), modify, (^:), (.>), (<.), ($%), ) where import qualified Data.Accessor.Private as A import Data.Accessor.Private (T(..), ) import Prelude hiding (null) -- * Define and construct accessors 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) {- | If an object is wrapped in a @newtype@, you can generate an @Accessor@ to the unwrapped data by providing a wrapper and an unwrapper function. The set function is simpler in this case, since no existing data must be kept. Since the information content of the wrapped and unwrapped data is equivalent, you can swap wrapper and unwrapper. This way you can construct an @Accessor@ that treats a record field containing an unwrapped object like a field containing a wrapped object. > newtype A = A {unA :: Int} > > access :: Accessor.T A Int > access = fromWrapper A unA -} fromWrapper :: (b -> a) -> (a -> b) -> T a b fromWrapper wrap unwrap = fromSetGet (const . wrap) unwrap {- newtype A = A {unA :: Int} access :: T A Int access = fromWrapper A unA -} -- Simple accessors {- | Access the record itself -} self :: T r r self = A.self -- self = fromSetGet const id {- | Access a (non-existing) element of type @()@ -} null :: T r () null = fromSetGet (flip const) (const ()) {- | @result a@ accesses the value of a function for argument @a@. Also see semantic editor combinators, that allow to modify all function values of a function at once. Cf. -} result :: Eq a => a -> T (a -> r) r result ai = fromSetGet (\r f a -> if a==ai then r else f a) ($ai) -- * Apply accessors, 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 8 ^. {- | 'get' as infix operator. This lets us write @record^.field^.subfield@. This imitates Modula II syntax. -} (^.) :: 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 @field^:subfield^:(2*) $ record@, @record$%field^:subfield^:(2*)@ or @record$%field^:subfield^:(const 1)@. -} (^:) :: T r a -> (a -> a) -> (r -> r) (^:) = modify {- | Flipped version of '($)'. -} ($%) :: a -> (a -> b) -> b ($%) = flip ($) -- * Accessor combinators 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 (.>) = A.compose {- This could be used for a Category instance of T. -} infixr 9 <. {- | Accessor composition the other direction. > (<.) = flip (.>) -} (<.) :: T b c -> T a b -> T a c (<.) = flip A.compose