Copyright | (C) Frank Staals |
---|---|
License | see the LICENSE file |
Maintainer | Frank Staals |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data LSeq (n :: Nat) a where
- toSeq :: LSeq n a -> Seq a
- empty :: LSeq 0 a
- fromList :: Foldable f => f a -> LSeq 0 a
- fromNonEmpty :: NonEmpty a -> LSeq 1 a
- fromSeq :: Seq a -> LSeq 0 a
- (<|) :: a -> LSeq n a -> LSeq (1 + n) a
- (|>) :: LSeq n a -> a -> LSeq (1 + n) a
- (><) :: LSeq n a -> LSeq m a -> LSeq (n + m) a
- eval :: forall proxy n m a. KnownNat n => proxy n -> LSeq m a -> Maybe (LSeq n a)
- index :: LSeq n a -> Int -> a
- adjust :: (a -> a) -> Int -> LSeq n a -> LSeq n a
- partition :: (a -> Bool) -> LSeq n a -> (LSeq 0 a, LSeq 0 a)
- mapWithIndex :: (Int -> a -> b) -> LSeq n a -> LSeq n b
- take :: Int -> LSeq n a -> LSeq 0 a
- drop :: Int -> LSeq n a -> LSeq 0 a
- unstableSort :: Ord a => LSeq n a -> LSeq n a
- unstableSortBy :: (a -> a -> Ordering) -> LSeq n a -> LSeq n a
- head :: LSeq (1 + n) a -> a
- tail :: LSeq (1 + n) a -> LSeq n a
- last :: LSeq (1 + n) a -> a
- init :: LSeq (1 + n) a -> LSeq n a
- append :: LSeq n a -> LSeq m a -> LSeq (n + m) a
- data ViewL n a where
- viewl :: LSeq (1 + n) a -> ViewL (1 + n) a
- data ViewR n a where
- viewr :: LSeq (1 + n) a -> ViewR (1 + n) a
- zipWith :: (a -> b -> c) -> LSeq n a -> LSeq n b -> LSeq n c
- promise :: forall m n a. LSeq m a -> LSeq n a
- forceLSeq :: KnownNat n => proxy n -> LSeq m a -> LSeq n a
Documentation
data LSeq (n :: Nat) a where Source #
LSeq n a certifies that the sequence has *at least* n items
pattern EmptyL :: LSeq n a | The empty sequence. |
pattern (:<|) :: a -> LSeq n a -> LSeq (1 + n) a infixr 5 | A bidirectional pattern synonym viewing the front of a non-empty sequence. |
pattern (:<<) :: a -> LSeq 0 a -> LSeq n a infixr 5 | A unidirectional pattern synonym viewing the front of a non-empty sequence. |
pattern (:|>) :: forall n a. LSeq n a -> a -> LSeq (1 + n) a infixl 5 | A bidirectional pattern synonym viewing the rear of a non-empty sequence. |
Instances
Functor (LSeq n) Source # | |
Foldable (LSeq n) Source # | |
Defined in Data.LSeq fold :: Monoid m => LSeq n m -> m # foldMap :: Monoid m => (a -> m) -> LSeq n a -> m # foldMap' :: Monoid m => (a -> m) -> LSeq n a -> m # foldr :: (a -> b -> b) -> b -> LSeq n a -> b # foldr' :: (a -> b -> b) -> b -> LSeq n a -> b # foldl :: (b -> a -> b) -> b -> LSeq n a -> b # foldl' :: (b -> a -> b) -> b -> LSeq n a -> b # foldr1 :: (a -> a -> a) -> LSeq n a -> a # foldl1 :: (a -> a -> a) -> LSeq n a -> a # elem :: Eq a => a -> LSeq n a -> Bool # maximum :: Ord a => LSeq n a -> a # minimum :: Ord a => LSeq n a -> a # | |
Traversable (LSeq n) Source # | |
1 <= n => Traversable1 (LSeq n) Source # | |
1 <= n => Foldable1 (LSeq n) Source # | |
Eq a => Eq (LSeq n a) Source # | |
Ord a => Ord (LSeq n a) Source # | |
Read a => Read (LSeq n a) Source # | |
Show a => Show (LSeq n a) Source # | |
Generic (LSeq n a) Source # | |
Semigroup (LSeq n a) Source # | |
Monoid (LSeq 0 a) Source # | |
(KnownNat n, Arbitrary a) => Arbitrary (LSeq n a) Source # | |
ToJSON a => ToJSON (LSeq n a) Source # | |
FromJSON a => FromJSON (LSeq n a) Source # | |
NFData a => NFData (LSeq n a) Source # | |
Ixed (LSeq n a) Source # | |
type Rep (LSeq n a) Source # | |
type Index (LSeq n a) Source # | |
type IxValue (LSeq n a) Source # | |
toSeq :: LSeq n a -> Seq a Source #
\( O(1) \) Convert to a sequence by dropping the type-level size.
fromList :: Foldable f => f a -> LSeq 0 a Source #
\( O(n) \). Create an l-sequence from a finite list of elements.
fromNonEmpty :: NonEmpty a -> LSeq 1 a Source #
\( O(n) \). Create an l-sequence from a non-empty list.
(<|) :: a -> LSeq n a -> LSeq (1 + n) a infixr 5 Source #
\( O(1) \) Add an element to the left end of a sequence. Mnemonic: a triangle with the single element at the pointy end.
(|>) :: LSeq n a -> a -> LSeq (1 + n) a infixl 5 Source #
\( O(1) \) Add an element to the right end of a sequence. Mnemonic: a triangle with the single element at the pointy end.
(><) :: LSeq n a -> LSeq m a -> LSeq (n + m) a infix 5 Source #
\( O(log(min(n,m))) \) Concatenate two sequences.
eval :: forall proxy n m a. KnownNat n => proxy n -> LSeq m a -> Maybe (LSeq n a) Source #
\( O(1) \) Prove a sequence has at least n
elements.
>>>
eval (Proxy :: Proxy 3) (fromList [1,2,3])
Just (LSeq (fromList [1,2,3]))>>>
eval (Proxy :: Proxy 3) (fromList [1,2])
Nothing>>>
eval (Proxy :: Proxy 3) (fromList [1..10])
Just (LSeq (fromList [1,2,3,4,5,6,7,8,9,10]))
index :: LSeq n a -> Int -> a Source #
\( O(log(min(i,n-i))) \) Get the element with index i, counting from the left and starting at 0.
adjust :: (a -> a) -> Int -> LSeq n a -> LSeq n a Source #
\( O(log(min(i,n−i))) \) Update the element at the specified position. If the position is out of range, the original sequence is returned. adjust can lead to poor performance and even memory leaks, because it does not force the new value before installing it in the sequence. adjust' should usually be preferred.
partition :: (a -> Bool) -> LSeq n a -> (LSeq 0 a, LSeq 0 a) Source #
\( O(n) \) The partition function takes a predicate p and a sequence xs and returns sequences of those elements which do and do not satisfy the predicate.
mapWithIndex :: (Int -> a -> b) -> LSeq n a -> LSeq n b Source #
A generalization of fmap
, mapWithIndex
takes a mapping
function that also depends on the element's index, and applies it to every
element in the sequence.
take :: Int -> LSeq n a -> LSeq 0 a Source #
\( O(\log(\min(i,n-i))) \). The first i
elements of a sequence.
If i
is negative,
yields the empty sequence.
If the sequence contains fewer than take
i si
elements, the whole sequence
is returned.
drop :: Int -> LSeq n a -> LSeq 0 a Source #
\( O(\log(\min(i,n-i))) \). Elements of a sequence after the first i
.
If i
is negative,
yields the whole sequence.
If the sequence contains fewer than drop
i si
elements, the empty sequence
is returned.
unstableSort :: Ord a => LSeq n a -> LSeq n a Source #
\( O(n \log n) \). unstableSort
sorts the specified LSeq
by
the natural ordering of its elements, but the sort is not stable.
This algorithm is frequently faster and uses less memory than sort
.
unstableSortBy :: (a -> a -> Ordering) -> LSeq n a -> LSeq n a Source #
\( O(n \log n) \). A generalization of unstableSort
, unstableSortBy
takes an arbitrary comparator and sorts the specified sequence.
The sort is not stable. This algorithm is frequently faster and
uses less memory than sortBy
.
head :: LSeq (1 + n) a -> a Source #
Gets the first element of the LSeq
>>>
head $ forceLSeq (Proxy :: Proxy 3) $ fromList [1,2,3]
1
tail :: LSeq (1 + n) a -> LSeq n a Source #
Get the LSeq without its first element -- >>> head $ forceLSeq (Proxy :: Proxy 3) $ fromList [1,2,3] LSeq (fromList [2,3])
last :: LSeq (1 + n) a -> a Source #
Get the last element of the LSeq
>>>
last $ forceLSeq (Proxy :: Proxy 3) $ fromList [1,2,3]
3
init :: LSeq (1 + n) a -> LSeq n a Source #
The sequence without its last element
>>>
init $ forceLSeq (Proxy :: Proxy 3) $ fromList [1,2,3]
LSeq (fromList [1,2])
View of the left end of a sequence.
Instances
Functor (ViewL n) Source # | |
Foldable (ViewL n) Source # | |
Defined in Data.LSeq fold :: Monoid m => ViewL n m -> m # foldMap :: Monoid m => (a -> m) -> ViewL n a -> m # foldMap' :: Monoid m => (a -> m) -> ViewL n a -> m # foldr :: (a -> b -> b) -> b -> ViewL n a -> b # foldr' :: (a -> b -> b) -> b -> ViewL n a -> b # foldl :: (b -> a -> b) -> b -> ViewL n a -> b # foldl' :: (b -> a -> b) -> b -> ViewL n a -> b # foldr1 :: (a -> a -> a) -> ViewL n a -> a # foldl1 :: (a -> a -> a) -> ViewL n a -> a # elem :: Eq a => a -> ViewL n a -> Bool # maximum :: Ord a => ViewL n a -> a # minimum :: Ord a => ViewL n a -> a # | |
Traversable (ViewL n) Source # | |
1 <= n => Traversable1 (ViewL n) Source # | |
1 <= n => Foldable1 (ViewL n) Source # | |
Eq a => Eq (ViewL n a) Source # | |
Ord a => Ord (ViewL n a) Source # | |
Defined in Data.LSeq | |
Show a => Show (ViewL n a) Source # | |
Semigroup (ViewL n a) Source # | |
View of the right end of a sequence.
Instances
Functor (ViewR n) Source # | |
Foldable (ViewR n) Source # | |
Defined in Data.LSeq fold :: Monoid m => ViewR n m -> m # foldMap :: Monoid m => (a -> m) -> ViewR n a -> m # foldMap' :: Monoid m => (a -> m) -> ViewR n a -> m # foldr :: (a -> b -> b) -> b -> ViewR n a -> b # foldr' :: (a -> b -> b) -> b -> ViewR n a -> b # foldl :: (b -> a -> b) -> b -> ViewR n a -> b # foldl' :: (b -> a -> b) -> b -> ViewR n a -> b # foldr1 :: (a -> a -> a) -> ViewR n a -> a # foldl1 :: (a -> a -> a) -> ViewR n a -> a # elem :: Eq a => a -> ViewR n a -> Bool # maximum :: Ord a => ViewR n a -> a # minimum :: Ord a => ViewR n a -> a # | |
Traversable (ViewR n) Source # | |
Eq a => Eq (ViewR n a) Source # | |
Ord a => Ord (ViewR n a) Source # | |
Defined in Data.LSeq | |
Show a => Show (ViewR n a) Source # | |
Semigroup (ViewR n a) Source # | |