Copyright | (c) Paweł Nowak |
---|---|
License | MIT |
Maintainer | Paweł Nowak <pawel834@gmail.com> |
Stability | provisional |
Safe Haskell | None |
Language | Haskell2010 |
Data.Tuple.Morph
Description
Allows you to flatten, unflatten and morph tuples of matching types.
Note: by design units are ignored. For example (Int, (), Char)
is the same as (Int, Char)
.
- morph :: forall a b. (HFoldable a, HUnfoldable b, Rep a ~ Rep b) => a -> b
- sizeLimit :: Int
- type family Rep tuple :: [*]
- class HFoldable t where
- class HUnfoldable t where
- fromHList :: HList (Rep t) -> t
- hListParser :: HParser (Rep t) t
- newtype HParser rep val = HParser {
- runHParser :: forall leftover. HList (rep ++ leftover) -> (val, HList leftover)
- class MonoidIndexedMonad m where
Morphing tuples.
morph :: forall a b. (HFoldable a, HUnfoldable b, Rep a ~ Rep b) => a -> b Source
Morph a tuple to some isomorphic tuple with the same order of types.
Works with arbitrary nested tuples, each tuple can have size up to sizeLimit
.
>>>
morph ("a", ("b", "c")) :: (String, String, String)
("a","b","c")
>>>
morph ((1 :: Int, 2 :: Int), 3 :: Double) :: (Int, (Int, Double))
(1,(2,3.0))
>>>
morph ("a", (), (5 :: Int, (), "c")) :: ((), (String, Int), String)
((),("a",5),"c")
>>>
morph (((("a", "b"), "c"), "d"), "e") :: ((String, String), (String, (String, String)))
(("a","b"),("c",("d","e")))
Size of the largest tuple that this library will work with. Equal to 13.
Note that size of ((((((1, 1), 1), 1), 1), 1), 1) is 2, not 7.
Converting between tuples and HLists.
type family Rep tuple :: [*] Source
Recurisvely break down a tuple type, representing it as a type list.
Equations
Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) = (++) (Rep a) ((++) (Rep b) ((++) (Rep c) ((++) (Rep d) ((++) (Rep e) ((++) (Rep f) ((++) (Rep g) ((++) (Rep h) ((++) (Rep i) ((++) (Rep j) ((++) (Rep k) ((++) (Rep l) (Rep m)))))))))))) | |
Rep (a, b, c, d, e, f, g, h, i, j, k, l) = (++) (Rep a) ((++) (Rep b) ((++) (Rep c) ((++) (Rep d) ((++) (Rep e) ((++) (Rep f) ((++) (Rep g) ((++) (Rep h) ((++) (Rep i) ((++) (Rep j) ((++) (Rep k) (Rep l))))))))))) | |
Rep (a, b, c, d, e, f, g, h, i, j, k) = (++) (Rep a) ((++) (Rep b) ((++) (Rep c) ((++) (Rep d) ((++) (Rep e) ((++) (Rep f) ((++) (Rep g) ((++) (Rep h) ((++) (Rep i) ((++) (Rep j) (Rep k)))))))))) | |
Rep (a, b, c, d, e, f, g, h, i, j) = (++) (Rep a) ((++) (Rep b) ((++) (Rep c) ((++) (Rep d) ((++) (Rep e) ((++) (Rep f) ((++) (Rep g) ((++) (Rep h) ((++) (Rep i) (Rep j))))))))) | |
Rep (a, b, c, d, e, f, g, h, i) = (++) (Rep a) ((++) (Rep b) ((++) (Rep c) ((++) (Rep d) ((++) (Rep e) ((++) (Rep f) ((++) (Rep g) ((++) (Rep h) (Rep i)))))))) | |
Rep (a, b, c, d, e, f, g, h) = (++) (Rep a) ((++) (Rep b) ((++) (Rep c) ((++) (Rep d) ((++) (Rep e) ((++) (Rep f) ((++) (Rep g) (Rep h))))))) | |
Rep (a, b, c, d, e, f, g) = (++) (Rep a) ((++) (Rep b) ((++) (Rep c) ((++) (Rep d) ((++) (Rep e) ((++) (Rep f) (Rep g)))))) | |
Rep (a, b, c, d, e, f) = (++) (Rep a) ((++) (Rep b) ((++) (Rep c) ((++) (Rep d) ((++) (Rep e) (Rep f))))) | |
Rep (a, b, c, d, e) = (++) (Rep a) ((++) (Rep b) ((++) (Rep c) ((++) (Rep d) (Rep e)))) | |
Rep (a, b, c, d) = (++) (Rep a) ((++) (Rep b) ((++) (Rep c) (Rep d))) | |
Rep (a, b, c) = (++) (Rep a) ((++) (Rep b) (Rep c)) | |
Rep (a, b) = (++) (Rep a) (Rep b) | |
Rep () = `[]` | |
Rep a = `[a]` |
class HFoldable t where Source
Types that can be flattened to a heterogenous list.
Instances
class HUnfoldable t where Source
Types that can be built from a heterogenous list.
Minimal complete definition
Methods
fromHList :: HList (Rep t) -> t Source
Build a structure from a heterogenous list.
hListParser :: HParser (Rep t) t Source
Builds a structure from a heterogenous list and yields the leftovers.
Instances
HList parser.
newtype HParser rep val Source
A function that parses some value val
with representation rep
from a heterogenous list and returns the parsed value and leftovers.
Constructors
HParser | |
Fields
|
Instances