Safe Haskell | None |
---|
Module Data.Fieldwise provides Fieldwise
typeclass for operations
of fields of records treated as independent components.
- class Fieldwise r where
- type UnliftedRecord r
- sequenceR :: Applicative f => r f -> f (UnliftedRecord r)
- hoistR :: (forall a. f a -> g a) -> r f -> r g
- zipWithR :: (forall a. f a -> g a -> h a) -> r f -> r g -> r h
- appR :: (forall a. f a -> (UnliftedRecord r -> a) -> g a) -> r f -> r g
- liftR :: Applicative f => UnliftedRecord r -> r f
- deriveFieldwise :: Name -> (String -> String) -> Q [Dec]
Documentation
Fieldwise class provides some operations for record fields treated as independent pieces of data. See individual methods.
type UnliftedRecord r Source
UnliftedRecord points to original data structures.
For example:
data T = T Int String data T_f f = T (f Int) (f String)
Then r = T_f
and UnliftedRecord r = T
sequenceR :: Applicative f => r f -> f (UnliftedRecord r)Source
This function is similar to sequenceA
, it composes fields
using <*>
operator.
Example:
sequenceR (T_f (Just 1) (Just "abc")) = Just (T 1 "abc")
hoistR :: (forall a. f a -> g a) -> r f -> r gSource
This function can replace field wrapper.
Example:
hoistR maybeToList (T_f (Just 1) (Just "abc")) = T_f [1] ["abc"]
zipWithR :: (forall a. f a -> g a -> h a) -> r f -> r g -> r hSource
This function zips respective field values uzing zipper function,
Example:
zipWithR mappend (T_f (Just 1) Nothing) (T_f Nothing (Just "c") = T_f (Just 1) (Just "c")
appR :: (forall a. f a -> (UnliftedRecord r -> a) -> g a) -> r f -> r gSource
This function uses a function to compose fields of a lifted record with selectors of original record.
Note that this is so complicated to support records with many constructors.
liftR :: Applicative f => UnliftedRecord r -> r fSource
deriveFieldwise :: Name -> (String -> String) -> Q [Dec]Source
Automatically derive lifted record type and Monoid
and
Fieldwise
instances for it.
First argument is the name of Haskell data type that should serve as basis for derivation, second argument tell how to tranform names in that type. Names need to be transformed if you want to derive fieldwise in the same module as original data type.
Conceptually for a data type T
a derived data T_f
has type for
each field wrapped in a type constructor. T
is semantically equal
to T_f Id
.
For example for data type:
data Test1 = Test1 Int String | Test2 { test2Char :: Char, test2IntList :: [Int], test2Func :: (Int -> Int) }
$(deriveFieldwise ''Test1 (++ "_f"))
Will produce the following splice:
data Test1_f f = Test1_f (f Int) (f String) | Test2_f {test2Char_f :: f Char, test2IntList_f :: f [Int], test2Func_f :: f (Int -> Int)} instance Alternative f => Monoid (Test1_f f) where mempty = Test1_f empty empty mappend (Test1_f l1 l2) (Test1_f r1 r2) = Test1_f (l1 <|> r1) (l2 <|> r2) mappend (Test2_f l1 l2 l3) (Test2_f r1 r2 r3) = Test2_f (l1 <|> r1) (l2 <|> r2) (l3 <|> r3) instance Fieldwise Test1_f where type instance UnliftedRecord Test1_f = Test1 sequenceR (Test1_f l1 l2) = (((pure Test1) <*> l1) <*> l2) hoistR fg (Test1_f l1 l2) = Test1_f (fg l1) (fg l2) hoistR fg (Test2_f l1 l2 l3) = Test2_f (fg l1) (fg l2) (fg l3) zipWithR fg (Test1_f l1 l2) (Test1_f r1 r2) = Test1_f (fg l1 r1) (fg l2 r2) zipWithR fg (Test2_f l1 l2 l3) (Test2_f r1 r2 r3) = Test2_f (fg l1 r1) (fg l2 r2) (fg l3 r3) appR fg (Test1_f l1 l2) = Test1_f (fg l1 (\ (Test1 q_ahwb _) -> q_ahwb)) (fg l2 (\ (Test1 _ q_ahwb) -> q_ahwb)) appR fg (Test2_f l1 l2 l3) = Test2_f (fg l1 test2Char) (fg l2 test2IntList) (fg l3 test2Func) liftR (Test1 l1 l2) = Test1_f (pure l1) (pure l2) liftR (Test2 l1 l2 l3) = Test2_f (pure l1) (pure l2) (pure l3)