| Copyright | (c) Atze van der Ploeg 2014 |
|---|---|
| License | BSD-style |
| Maintainer | atzeus@gmail.org |
| Stability | provisional |
| Portability | portable |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Data.SequenceClass
Description
A type class for sequences.
See the package type-aligned for a generalization of this type class sequences.
Documentation
class (Foldable s, Functor s) => Sequence s where Source #
A type class for (finite) sequences
Instances should be free monoids
(ignoring issues with infinite and partially defined structures),
just like lists, with singleton as the canonical injection and foldMap
factoring functions. In particular, they should satisfy the following laws:
Semigroup and Monoid laws:
(><) == (Data.Semigroup.<>) empty == mempty
In particular, this requires that
empty >< x == x x >< empty == x (x >< y) >< z = x >< (y >< z)
FoldMap/singleton laws:
For any Monoid m and any function f :: c -> m,
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.
Warning: the default definitions are typically awful. Check them carefully
before relying on them. In particular, they may well work in O(n^2) time (or
worse?) when even definitions that convert to and from lists would work in
O(n) time. Exceptions: for sequences with constant time concatenation, the
defaults for <| and |> are okay. For sequences with constant time |>,
the default for fromList is okay.
Methods
singleton :: c -> s c Source #
(><) :: 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
fromList :: [c] -> s c Source #
Convert a list to a sequence
Default definition:
fromList = foldl' (|>) empty
Instances
| Sequence [] Source # | |
| Sequence Seq Source # | |
Defined in Data.SequenceClass | |
| Sequence Queue Source # | |
| Sequence FastQueue Source # | |
Defined in Data.Sequence.FastQueue.Internal | |
| Sequence BSeq Source # | |
Defined in Data.Sequence.BSeq.Internal | |
| Sequence q => Sequence (ToCatQueue q) Source # | |
Defined in Data.Sequence.ToCatQueue.Internal Methods empty :: ToCatQueue q c Source # singleton :: c -> ToCatQueue q c Source # (><) :: ToCatQueue q c -> ToCatQueue q c -> ToCatQueue q c Source # viewl :: ToCatQueue q c -> ViewL (ToCatQueue q) c Source # viewr :: ToCatQueue q c -> ViewR (ToCatQueue q) c Source # (|>) :: ToCatQueue q c -> c -> ToCatQueue q c Source # (<|) :: c -> ToCatQueue q c -> ToCatQueue q c Source # fromList :: [c] -> ToCatQueue q c Source # | |
A view of the left end of a Sequence.
A view of the right end of a Sequence.