Copyright | (c) Atze van der Ploeg 2014 |
---|---|
License | BSD-style |
Maintainer | atzeus@gmail.org |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell98 |
A type class for type aligned sequences: heterogeneous sequences where the types enforce the element order.
Type aligned sequences are best explained by an example: a type aligned sequence of functions is a sequence f 1 , f 2 , f 3 ... f n such that the composition of these functions f 1 ◦ f 2 ◦ f 3 ◦ ... ◦ f n is well typed. In other words: the result type of each function in the sequence must be the same as the argument type of the next function (if any). In general, the elements of a type aligned sequence do not have to be functions, i.e. values of type a → b, but can be values of type (c a b), for some binary type constructor c. Hence, we define a type aligned sequence to be a sequence of elements of the type (c a_i b_i ) with the side-condition b_i−1 = a_i . If s is the type of a type aligned sequence data structure, then (s c a b) is the type of a type aligned sequence where the first element has type (c a x), for some x, and the last element has type (c y b), for some y.
The simplest type aligned sequence data structure is a list, see Data.TASequence.ConsList. The other modules give various other type aligned sequence data structures. The data structure Data.TASequence.FastCatQueue supports the most operations in worst case constant time.
See the paper Reflection without Remorse: Revealing a hidden sequence to speed up Monadic Reflection, Atze van der Ploeg and Oleg Kiselyov, Haskell Symposium 2014 for more details.
Paper: http://homepages.cwi.nl/~ploeg/zseq.pdf Talk : http://www.youtube.com/watch?v=_XoI65Rxmss
- class TASequence s where
- data TAViewL s c x y where
- data TAViewR s c x y where
Documentation
class TASequence s where Source
A type class for type aligned sequences
Minimal complete defention: tempty
and tsingleton
and (tviewl
or tviewr
) and (><
or |>
or <|
)
Instances should satisfy the following laws:
Category laws:
tempty >< x == x x >< tempty == x (x >< y) >< z = x >< (y >< z)
Observation laws:
tviewl (tsingleton e >< s) == e :< s tviewl tempty == TAEmptyL
The behaviour of <|
,|>
, tmap
and tviewr
is implied by the above laws and their default definitions.
tsingleton :: c x y -> s c x y Source
(><) :: s c x y -> s c y z -> s c x z infix 5 Source
Append two type aligned sequences
tviewl :: s c x y -> TAViewL s c x y Source
View a type aligned sequence from the left
tviewr :: s c x y -> TAViewR s c x y Source
View a type aligned sequence from the right
Default definition:
tviewr q = case tviewl q of TAEmptyL -> TAEmptyR h :< t -> case tviewr t of TAEmptyR -> tempty :> h p :> l -> (h <| p) :> l
(|>) :: s c x y -> c y z -> s c x z infixl 5 Source
Append a single element to the right
Default definition:
l |> r = l >< tsingleton r
(<|) :: c x y -> s c y z -> s c x z infixr 5 Source
Append a single element to the left
Default definition:
l <| r = tsingleton l >< r
tmap :: (forall x y. c x y -> d x y) -> s c x y -> s d x y Source
Apply a function to all elements in a type aligned sequence
Default definition:
tmap f q = case tviewl q of TAEmptyL -> tempty h :< t -> f h <| tmap f t