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 sequences.
See the package type-aligned for a generalization of this type class sequences.
Documentation
class (Functor s, Foldable s) => Sequence s where Source
A type class for (finite) sequences
Minimal complete defention: empty
and singleton
and (viewl
or viewr
) and (><
or |>
or <|
)
Instances should satisfy the following laws:
Monoid laws:
empty >< x == x x >< empty == x (x >< y) >< z = x >< (y >< z)
Observation laws:
viewl (singleton e >< s) == e :< s viewl empty == EmptyL
The behaviour of <|
,|>
, and viewr
is implied by the above laws and their default definitions.
(><) :: s c -> s c -> s c infix 5 Source
Append two sequences
viewl :: s c -> ViewL s c Source
View a sequence from the left
viewr :: s c -> ViewR s c Source
View a sequence from the right
Default definition:
viewr q = case viewl q of EmptyL -> EmptyR h :< t -> case viewr t of EmptyR -> empty :> h p :> l -> (h <| p) :> l
(|>) :: s c -> c -> s c infixl 5 Source
Append a single element to the right
Default definition:
l |> r = l >< singleton r
(<|) :: c -> s c -> s c infixr 5 Source
Append a single element to the left
Default definition:
l <| r = singleton l >< r