| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Sized.Peano
Description
This module exports type specialized to
type-level Peano numeral Sized.Nat
Synopsis
- type Ordinal (n :: Nat) = Ordinal n
- type Sized f (n :: Nat) = Sized f n
- type ListLikeF f = (Functor f, Forall (LLF f))
- instLL :: forall f a. ListLikeF f :- ListLike (f a) a
- instFunctor :: ListLikeF f :- Functor f
- withListLikeF :: forall pxy f a b. ListLikeF f => pxy (f a) -> ((Functor f, ListLike (f a) a) => b) -> b
- withListLikeF' :: ListLikeF f => f a -> ((Functor f, ListLike (f a) a) => b) -> b
- data SnocView f n a where
- data ConsView f n a where
- data Partitioned f n a where
- Partitioned :: ListLike (f a) a => Sing n -> Sized f (n :: Nat) a -> Sing m -> Sized f (m :: Nat) a -> Partitioned f (n + m) a
- data SomeSized f nat a where
- length :: ListLike (f a) a => Sized f n a -> Int
- sLength :: forall f (n :: nat) a. (HasOrdinal nat, ListLike (f a) a) => Sized f n a -> Sing n
- null :: ListLike (f a) a => Sized f n a -> Bool
- (!!) :: ListLike (f a) a => Sized f (Succ m) a -> Int -> a
- (%!!) :: (HasOrdinal nat, ListLike (f c) c) => Sized f n c -> Ordinal (n :: nat) -> c
- index :: ListLike (f a) a => Int -> Sized f (Succ m) a -> a
- sIndex :: (HasOrdinal nat, ListLike (f c) c) => Ordinal (n :: nat) -> Sized f n c -> c
- head :: (HasOrdinal nat, ListLike (f a) b, (Zero nat < n) ~ True) => Sized f n a -> b
- last :: (HasOrdinal nat, (Zero nat < n) ~ True, ListLike (f a) b) => Sized f n a -> b
- uncons :: ListLike (f a) b => Sized f (Succ n) a -> (b, Sized f n a)
- uncons' :: ListLike (f a) b => proxy n -> Sized f (Succ n) a -> (b, Sized f n a)
- unsnoc :: ListLike (f a) b => Sized f (Succ n) a -> (Sized f n a, b)
- unsnoc' :: ListLike (f a) b => proxy n -> Sized f (Succ n) a -> (Sized f n a, b)
- tail :: (HasOrdinal nat, ListLike (f a) a) => Sized f (Succ n) a -> Sized f (n :: nat) a
- init :: ListLike (f a) a => Sized f (Succ n) a -> Sized f n a
- take :: (ListLike (f a) a, (n <= m) ~ True, HasOrdinal nat) => Sing (n :: nat) -> Sized f m a -> Sized f n a
- takeAtMost :: (ListLike (f a) a, HasOrdinal nat) => Sing (n :: nat) -> Sized f m a -> Sized f (Min n m) a
- drop :: (HasOrdinal nat, ListLike (f a) a, (n <= m) ~ True) => Sing (n :: nat) -> Sized f m a -> Sized f (m - n) a
- splitAt :: (ListLike (f a) a, (n <= m) ~ True, HasOrdinal nat) => Sing (n :: nat) -> Sized f m a -> (Sized f n a, Sized f (m -. n) a)
- splitAtMost :: (HasOrdinal nat, ListLike (f a) a) => Sing (n :: nat) -> Sized f m a -> (Sized f (Min n m) a, Sized f (m -. n) a)
- empty :: forall f a. (HasOrdinal nat, ListLike (f a) a) => Sized f (Zero nat :: nat) a
- singleton :: forall f a. ListLike (f a) a => a -> Sized f 1 a
- toSomeSized :: forall nat f a. (HasOrdinal nat, ListLike (f a) a) => f a -> SomeSized f nat a
- replicate :: forall f (n :: nat) a. (HasOrdinal nat, ListLike (f a) a) => Sing n -> a -> Sized f n a
- replicate' :: (HasOrdinal nat, SingI (n :: nat), ListLike (f a) a) => a -> Sized f n a
- generate :: forall (nat :: Type) (n :: nat) (a :: Type) f. (ListLike (f a) a, HasOrdinal nat) => Sing n -> (Ordinal n -> a) -> Sized f n a
- cons :: ListLike (f a) b => b -> Sized f n a -> Sized f (Succ n) a
- (<|) :: ListLike (f a) b => b -> Sized f n a -> Sized f (Succ n) a
- snoc :: ListLike (f a) b => Sized f n a -> b -> Sized f (Succ n) a
- (|>) :: ListLike (f a) b => Sized f n a -> b -> Sized f (Succ n) a
- append :: ListLike (f a) a => Sized f n a -> Sized f m a -> Sized f (n + m) a
- (++) :: ListLike (f a) a => Sized f n a -> Sized f m a -> Sized f (n + m) a
- concat :: forall f f' m n a. (Functor f', Foldable f', ListLike (f a) a) => Sized f' m (Sized f n a) -> Sized f (m * n) a
- zip :: (ListLike (f a) a, ListLike (f b) b, ListLike (f (a, b)) (a, b)) => Sized f n a -> Sized f m b -> Sized f (Min n m) (a, b)
- zipSame :: (ListLike (f a) a, ListLike (f b) b, ListLike (f (a, b)) (a, b)) => Sized f n a -> Sized f n b -> Sized f n (a, b)
- zipWith :: (ListLike (f a) a, ListLike (f b) b, ListLike (f c) c) => (a -> b -> c) -> Sized f n a -> Sized f m b -> Sized f (Min n m) c
- zipWithSame :: (ListLike (f a) a, ListLike (f b) b, ListLike (f c) c) => (a -> b -> c) -> Sized f n a -> Sized f n b -> Sized f n c
- unzip :: (ListLike (f a) a, ListLike (f b) b, ListLike (f (a, b)) (a, b)) => Sized f n (a, b) -> (Sized f n a, Sized f n b)
- map :: (ListLike (f a) a, ListLike (f b) b) => (a -> b) -> Sized f n a -> Sized f n b
- fmap :: forall f n a b. Functor f => (a -> b) -> Sized f n a -> Sized f n b
- reverse :: ListLike (f a) a => Sized f n a -> Sized f n a
- intersperse :: ListLike (f a) a => a -> Sized f n a -> Sized f ((FromInteger 2 * n) -. 1) a
- nub :: (HasOrdinal nat, ListLike (f a) a, Eq a) => Sized f n a -> SomeSized f nat a
- sort :: (ListLike (f a) a, Ord a) => Sized f n a -> Sized f n a
- sortBy :: ListLike (f a) a => (a -> a -> Ordering) -> Sized f n a -> Sized f n a
- insert :: (ListLike (f a) a, Ord a) => a -> Sized f n a -> Sized f (Succ n) a
- insertBy :: ListLike (f a) a => (a -> a -> Ordering) -> a -> Sized f n a -> Sized f (Succ n) a
- toList :: ListLike (f a) a => Sized f n a -> [a]
- fromList :: forall f n a. (HasOrdinal nat, ListLike (f a) a) => Sing (n :: nat) -> [a] -> Maybe (Sized f n a)
- fromList' :: (ListLike (f a) a, SingI (n :: Nat)) => [a] -> Maybe (Sized f n a)
- unsafeFromList :: forall (nat :: Type) f (n :: nat) a. ListLike (f a) a => Sing n -> [a] -> Sized f n a
- unsafeFromList' :: (SingI (n :: Nat), ListLike (f a) a) => [a] -> Sized f n a
- fromListWithDefault :: forall f (n :: nat) a. (HasOrdinal nat, ListLike (f a) a) => Sing n -> a -> [a] -> Sized f n a
- fromListWithDefault' :: (SingI (n :: Nat), ListLike (f a) a) => a -> [a] -> Sized f n a
- unsized :: Sized f n a -> f a
- toSized :: (HasOrdinal nat, ListLike (f a) a) => Sing (n :: nat) -> f a -> Maybe (Sized f n a)
- toSized' :: (ListLike (f a) a, SingI (n :: Nat)) => f a -> Maybe (Sized f n a)
- unsafeToSized :: Sing n -> f a -> Sized f n a
- unsafeToSized' :: (SingI (n :: Nat), ListLike (f a) a) => f a -> Sized f n a
- toSizedWithDefault :: (HasOrdinal nat, ListLike (f a) a) => Sing (n :: nat) -> a -> f a -> Sized f n a
- toSizedWithDefault' :: (SingI (n :: Nat), ListLike (f a) a) => a -> f a -> Sized f n a
- takeWhile :: (HasOrdinal nat, ListLike (f a) a) => (a -> Bool) -> Sized f n a -> SomeSized f nat a
- dropWhile :: (HasOrdinal nat, ListLike (f a) a) => (a -> Bool) -> Sized f n a -> SomeSized f nat a
- span :: ListLike (f a) a => (a -> Bool) -> Sized f n a -> Partitioned f n a
- break :: ListLike (f a) a => (a -> Bool) -> Sized f n a -> Partitioned f n a
- partition :: ListLike (f a) a => (a -> Bool) -> Sized f n a -> Partitioned f n a
- elem :: (ListLike (f a) a, Eq a) => a -> Sized f n a -> Bool
- notElem :: (ListLike (f a) a, Eq a) => a -> Sized f n a -> Bool
- find :: Foldable f => (a -> Bool) -> Sized f n a -> Maybe a
- findF :: Foldable f => (a -> Bool) -> Sized f n a -> Maybe a
- findIndex :: ListLike (f a) a => (a -> Bool) -> Sized f n a -> Maybe Int
- sFindIndex :: (SingI (n :: nat), ListLike (f a) a, HasOrdinal nat) => (a -> Bool) -> Sized f n a -> Maybe (Ordinal n)
- findIndexIF :: FoldableWithIndex i f => (a -> Bool) -> Sized f n a -> Maybe i
- sFindIndexIF :: (FoldableWithIndex i f, Integral i, HasOrdinal nat, SingI n) => (a -> Bool) -> Sized f (n :: nat) a -> Maybe (Ordinal n)
- findIndices :: ListLike (f a) a => (a -> Bool) -> Sized f n a -> [Int]
- findIndicesIF :: FoldableWithIndex i f => (a -> Bool) -> Sized f n a -> [i]
- sFindIndices :: (HasOrdinal nat, SingI (n :: nat), ListLike (f a) a) => (a -> Bool) -> Sized f n a -> [Ordinal n]
- sFindIndicesIF :: (FoldableWithIndex i f, Integral i, HasOrdinal nat, SingI n) => (a -> Bool) -> Sized f (n :: nat) a -> [Ordinal n]
- elemIndex :: (Eq a, ListLike (f a) a) => a -> Sized f n a -> Maybe Int
- sElemIndex :: forall (n :: nat) f a. (SingI n, ListLike (f a) a, Eq a, HasOrdinal nat) => a -> Sized f n a -> Maybe (Ordinal n)
- sUnsafeElemIndex :: forall (n :: nat) f a. (SingI n, ListLike (f a) a, Eq a, HasOrdinal nat) => a -> Sized f n a -> Maybe (Ordinal n)
- elemIndices :: (ListLike (f a) a, Eq a) => a -> Sized f n a -> [Int]
- sElemIndices :: (HasOrdinal nat, SingI (n :: nat), ListLike (f a) a, Eq a) => a -> Sized f n a -> [Ordinal n]
- viewCons :: forall f a (n :: nat). (HasOrdinal nat, ListLike (f a) a) => Sized f n a -> ConsView f n a
- viewSnoc :: forall f (n :: nat) a. (HasOrdinal nat, ListLike (f a) a) => Sized f n a -> SnocView f n a
- pattern (:<) :: forall f (n :: Nat) a. ListLike (f a) a => forall (n1 :: Nat). (n ~ Succ n1, SingI n1) => a -> Sized f n1 a -> Sized f n a
- pattern NilL :: forall f (n :: Nat) a. ListLike (f a) a => n ~ Z => Sized f n a
- pattern (:>) :: forall f (n :: Nat) a. ListLike (f a) a => forall (n1 :: Nat). (n ~ Succ n1, SingI n1) => Sized f n1 a -> a -> Sized f n a
- pattern NilR :: forall f (n :: Nat) a. ListLike (f a) a => n ~ Z => Sized f n a
Documentation
type ListLikeF f = (Functor f, Forall (LLF f)) Source #
Functor f such that there is instance ListLike (f a) a for any a.
Since 0.1.0.0
withListLikeF :: forall pxy f a b. ListLikeF f => pxy (f a) -> ((Functor f, ListLike (f a) a) => b) -> b Source #
data Partitioned f n a where Source #
The type Partitioned f n a represents partitioned sequence of length n.
Value Partitioned lenL ls lenR rs stands for:
- Entire sequence is divided into
lsandrs, and their length arelenLandlenRresp. lenL + lenR = n
Since 0.1.0.0
Constructors
| Partitioned :: ListLike (f a) a => Sing n -> Sized f (n :: Nat) a -> Sing m -> Sized f (m :: Nat) a -> Partitioned f (n + m) a |
data SomeSized f nat a where Source #
Sized vector with the length is existentially quantified.
This type is used mostly when the return type's length cannot
be statically determined beforehand.
SomeSized sn xs :: SomeSized f a stands for the Sized sequence
xs of element type a and length sn.
Since 0.1.0.0
length :: ListLike (f a) a => Sized f n a -> Int Source #
Returns the length of wrapped containers.
If you use unsafeFromList or similar unsafe functions,
this function may return different value from type-parameterized length.
Since 0.1.0.0
sLength :: forall f (n :: nat) a. (HasOrdinal nat, ListLike (f a) a) => Sized f n a -> Sing n Source #
Sing version of length.
Since 0.2.0.0
null :: ListLike (f a) a => Sized f n a -> Bool Source #
Test if the sequence is empty or not.
Since 0.1.0.0
(%!!) :: (HasOrdinal nat, ListLike (f c) c) => Sized f n c -> Ordinal (n :: nat) -> c Source #
Safe indexing with Ordinals.
Since 0.1.0.0
index :: ListLike (f a) a => Int -> Sized f (Succ m) a -> a Source #
Flipped version of !!.
Since 0.1.0.0
sIndex :: (HasOrdinal nat, ListLike (f c) c) => Ordinal (n :: nat) -> Sized f n c -> c Source #
Flipped version of %!!.
Since 0.1.0.0
head :: (HasOrdinal nat, ListLike (f a) b, (Zero nat < n) ~ True) => Sized f n a -> b Source #
Take the first element of non-empty sequence. If you want to make case-analysis for general sequence, see Views and Patterns section.
Since 0.1.0.0
last :: (HasOrdinal nat, (Zero nat < n) ~ True, ListLike (f a) b) => Sized f n a -> b Source #
Take the last element of non-empty sequence. If you want to make case-analysis for general sequence, see Views and Patterns section.
Since 0.1.0.0
uncons :: ListLike (f a) b => Sized f (Succ n) a -> (b, Sized f n a) Source #
Take the head and tail of non-empty sequence.
If you want to make case-analysis for general sequence,
see Views and Patterns section.
Since 0.1.0.0
unsnoc :: ListLike (f a) b => Sized f (Succ n) a -> (Sized f n a, b) Source #
Take the init and last of non-empty sequence.
If you want to make case-analysis for general sequence,
see Views and Patterns section.
Since 0.1.0.0
tail :: (HasOrdinal nat, ListLike (f a) a) => Sized f (Succ n) a -> Sized f (n :: nat) a Source #
Take the tail of non-empty sequence. If you want to make case-analysis for general sequence, see Views and Patterns section.
Since 0.1.0.0
init :: ListLike (f a) a => Sized f (Succ n) a -> Sized f n a Source #
Take the initial segment of non-empty sequence. If you want to make case-analysis for general sequence, see Views and Patterns section.
Since 0.1.0.0
take :: (ListLike (f a) a, (n <= m) ~ True, HasOrdinal nat) => Sing (n :: nat) -> Sized f m a -> Sized f n a Source #
take k xs takes first k element of xs where
the length of xs should be larger than k.
It is really sad, that this function
takes at least O(k) regardless of base container.
Since 0.1.0.0
takeAtMost :: (ListLike (f a) a, HasOrdinal nat) => Sing (n :: nat) -> Sized f m a -> Sized f (Min n m) a Source #
take k xs takes first k element of xs at most.
It is really sad, that this function
takes at least O(k) regardless of base container.
Since 0.1.0.0
drop :: (HasOrdinal nat, ListLike (f a) a, (n <= m) ~ True) => Sing (n :: nat) -> Sized f m a -> Sized f (m - n) a Source #
drop k xs drops first k element of xs and returns
the rest of sequence, where the length of xs should be larger than k.
It is really sad, that this function
takes at least O(k) regardless of base container.
Since 0.1.0.0
splitAt :: (ListLike (f a) a, (n <= m) ~ True, HasOrdinal nat) => Sing (n :: nat) -> Sized f m a -> (Sized f n a, Sized f (m -. n) a) Source #
splitAt k xs split xs at k, where
the length of xs should be less than or equal to k.
It is really sad, that this function
takes at least O(k) regardless of base container.
Since 0.1.0.0
splitAtMost :: (HasOrdinal nat, ListLike (f a) a) => Sing (n :: nat) -> Sized f m a -> (Sized f (Min n m) a, Sized f (m -. n) a) Source #
splitAtMost k xs split xs at k.
If k exceeds the length of xs, then the second result value become empty.
It is really sad, that this function
takes at least O(k) regardless of base container.
Since 0.1.0.0
empty :: forall f a. (HasOrdinal nat, ListLike (f a) a) => Sized f (Zero nat :: nat) a Source #
Empty sequence.
Since 0.1.0.0
singleton :: forall f a. ListLike (f a) a => a -> Sized f 1 a Source #
Sequence with one element.
Since 0.1.0.0
toSomeSized :: forall nat f a. (HasOrdinal nat, ListLike (f a) a) => f a -> SomeSized f nat a Source #
replicate :: forall f (n :: nat) a. (HasOrdinal nat, ListLike (f a) a) => Sing n -> a -> Sized f n a Source #
Replicates the same value.
Since 0.1.0.0
replicate' :: (HasOrdinal nat, SingI (n :: nat), ListLike (f a) a) => a -> Sized f n a Source #
replicate with the length inferred.
Since 0.1.0.0
generate :: forall (nat :: Type) (n :: nat) (a :: Type) f. (ListLike (f a) a, HasOrdinal nat) => Sing n -> (Ordinal n -> a) -> Sized f n a Source #
cons :: ListLike (f a) b => b -> Sized f n a -> Sized f (Succ n) a Source #
Append an element to the head of sequence.
Since 0.1.0.0
(<|) :: ListLike (f a) b => b -> Sized f n a -> Sized f (Succ n) a infixr 5 Source #
Infix version of cons.
Since 0.1.0.0
snoc :: ListLike (f a) b => Sized f n a -> b -> Sized f (Succ n) a Source #
Append an element to the tail of sequence.
Since 0.1.0.0
(|>) :: ListLike (f a) b => Sized f n a -> b -> Sized f (Succ n) a infixl 5 Source #
Infix version of snoc.
Since 0.1.0.0
append :: ListLike (f a) a => Sized f n a -> Sized f m a -> Sized f (n + m) a Source #
Append two lists.
Since 0.1.0.0
(++) :: ListLike (f a) a => Sized f n a -> Sized f m a -> Sized f (n + m) a infixr 5 Source #
Infix version of append.
Since 0.1.0.0
concat :: forall f f' m n a. (Functor f', Foldable f', ListLike (f a) a) => Sized f' m (Sized f n a) -> Sized f (m * n) a Source #
Concatenates multiple sequences into one.
Since 0.1.0.0
zip :: (ListLike (f a) a, ListLike (f b) b, ListLike (f (a, b)) (a, b)) => Sized f n a -> Sized f m b -> Sized f (Min n m) (a, b) Source #
Zipping two sequences. Length is adjusted to shorter one.
Since 0.1.0.0
zipSame :: (ListLike (f a) a, ListLike (f b) b, ListLike (f (a, b)) (a, b)) => Sized f n a -> Sized f n b -> Sized f n (a, b) Source #
zip for the sequences of the same length.
Since 0.1.0.0
zipWith :: (ListLike (f a) a, ListLike (f b) b, ListLike (f c) c) => (a -> b -> c) -> Sized f n a -> Sized f m b -> Sized f (Min n m) c Source #
Zipping two sequences with funtion. Length is adjusted to shorter one.
Since 0.1.0.0
zipWithSame :: (ListLike (f a) a, ListLike (f b) b, ListLike (f c) c) => (a -> b -> c) -> Sized f n a -> Sized f n b -> Sized f n c Source #
zipWith for the sequences of the same length.
Since 0.1.0.0
unzip :: (ListLike (f a) a, ListLike (f b) b, ListLike (f (a, b)) (a, b)) => Sized f n (a, b) -> (Sized f n a, Sized f n b) Source #
Unzipping the sequence of tuples.
Since 0.1.0.0
map :: (ListLike (f a) a, ListLike (f b) b) => (a -> b) -> Sized f n a -> Sized f n b Source #
Map function.
Since 0.1.0.0
intersperse :: ListLike (f a) a => a -> Sized f n a -> Sized f ((FromInteger 2 * n) -. 1) a Source #
Intersperces.
Since 0.1.0.0
nub :: (HasOrdinal nat, ListLike (f a) a, Eq a) => Sized f n a -> SomeSized f nat a Source #
Remove all duplicates.
Since 0.1.0.0
sort :: (ListLike (f a) a, Ord a) => Sized f n a -> Sized f n a Source #
Sorting sequence by ascending order.
Since 0.1.0.0
sortBy :: ListLike (f a) a => (a -> a -> Ordering) -> Sized f n a -> Sized f n a Source #
Generalized version of sort.
Since 0.1.0.0
insert :: (ListLike (f a) a, Ord a) => a -> Sized f n a -> Sized f (Succ n) a Source #
Insert new element into the presorted sequence.
Since 0.1.0.0
insertBy :: ListLike (f a) a => (a -> a -> Ordering) -> a -> Sized f n a -> Sized f (Succ n) a Source #
Generalized version of insert.
Since 0.1.0.0
fromList :: forall f n a. (HasOrdinal nat, ListLike (f a) a) => Sing (n :: nat) -> [a] -> Maybe (Sized f n a) Source #
If the given list is shorter than n, then returns Nothing
Otherwise returns Sized f n a consisting of initial n element
of given list.
Since 0.1.0.0
fromList' :: (ListLike (f a) a, SingI (n :: Nat)) => [a] -> Maybe (Sized f n a) Source #
fromList with the result length inferred.
Since 0.1.0.0
unsafeFromList :: forall (nat :: Type) f (n :: nat) a. ListLike (f a) a => Sing n -> [a] -> Sized f n a Source #
Unsafe version of fromList. If the length of the given list does not
equal to n, then something unusual happens.
Since 0.1.0.0
unsafeFromList' :: (SingI (n :: Nat), ListLike (f a) a) => [a] -> Sized f n a Source #
unsafeFromList with the result length inferred.
Since 0.1.0.0
fromListWithDefault :: forall f (n :: nat) a. (HasOrdinal nat, ListLike (f a) a) => Sing n -> a -> [a] -> Sized f n a Source #
Construct a Sized f n a by padding default value if the given list is short.
Since 0.1.0.0
fromListWithDefault' :: (SingI (n :: Nat), ListLike (f a) a) => a -> [a] -> Sized f n a Source #
fromListWithDefault with the result length inferred.
Since 0.1.0.0
unsized :: Sized f n a -> f a Source #
Forget the length and obtain the wrapped base container.
Since 0.1.0.0
toSized :: (HasOrdinal nat, ListLike (f a) a) => Sing (n :: nat) -> f a -> Maybe (Sized f n a) Source #
If the length of the input is shorter than n, then returns Nothing.
Otherwise returns Sized f n a consisting of initial n element
of the input.
Since 0.1.0.0
toSized' :: (ListLike (f a) a, SingI (n :: Nat)) => f a -> Maybe (Sized f n a) Source #
toSized with the result length inferred.
Since 0.1.0.0
unsafeToSized :: Sing n -> f a -> Sized f n a Source #
Unsafe version of toSized. If the length of the given list does not
equal to n, then something unusual happens.
Since 0.1.0.0
unsafeToSized' :: (SingI (n :: Nat), ListLike (f a) a) => f a -> Sized f n a Source #
unsafeToSized with the result length inferred.
Since 0.1.0.0
toSizedWithDefault :: (HasOrdinal nat, ListLike (f a) a) => Sing (n :: nat) -> a -> f a -> Sized f n a Source #
Construct a Sized f n a by padding default value if the given list is short.
Since 0.1.0.0
toSizedWithDefault' :: (SingI (n :: Nat), ListLike (f a) a) => a -> f a -> Sized f n a Source #
toSizedWithDefault with the result length inferred.
Since 0.1.0.0
takeWhile :: (HasOrdinal nat, ListLike (f a) a) => (a -> Bool) -> Sized f n a -> SomeSized f nat a Source #
Take the initial segment as long as elements satisfys the predicate.
Since 0.1.0.0
dropWhile :: (HasOrdinal nat, ListLike (f a) a) => (a -> Bool) -> Sized f n a -> SomeSized f nat a Source #
Drop the initial segment as long as elements satisfys the predicate.
Since 0.1.0.0
span :: ListLike (f a) a => (a -> Bool) -> Sized f n a -> Partitioned f n a Source #
Invariant: instance must be implemented
to satisfy the following property:
ListLike (f a) alength (fst (span p xs)) + length (snd (span p xs)) == length xs
Otherwise, this function introduces severe contradiction.
Since 0.1.0.0
break :: ListLike (f a) a => (a -> Bool) -> Sized f n a -> Partitioned f n a Source #
Invariant: instance must be implemented
to satisfy the following property:
ListLike (f a) alength (fst (break p xs)) + length (snd (break p xs)) == length xs
Otherwise, this function introduces severe contradiction.
Since 0.1.0.0
partition :: ListLike (f a) a => (a -> Bool) -> Sized f n a -> Partitioned f n a Source #
Invariant: instance must be implemented
to satisfy the following property:
ListLike (f a) alength (fst (partition p xs)) + length (snd (partition p xs)) == length xs
Otherwise, this function introduces severe contradiction.
Since 0.1.0.0
elem :: (ListLike (f a) a, Eq a) => a -> Sized f n a -> Bool Source #
Membership test; see also notElem.
Since 0.1.0.0
notElem :: (ListLike (f a) a, Eq a) => a -> Sized f n a -> Bool Source #
Negation of elem.
Since 0.1.0.0
find :: Foldable f => (a -> Bool) -> Sized f n a -> Maybe a Source #
Find the element satisfying the predicate.
Since 0.1.0.0
findIndex :: ListLike (f a) a => (a -> Bool) -> Sized f n a -> Maybe Int Source #
find the element satisfying findIndex p xsp and returns its index if exists.
Since 0.1.0.0
sFindIndex :: (SingI (n :: nat), ListLike (f a) a, HasOrdinal nat) => (a -> Bool) -> Sized f n a -> Maybe (Ordinal n) Source #
Ordinal version of findIndex.
Since 0.1.0.0
findIndexIF :: FoldableWithIndex i f => (a -> Bool) -> Sized f n a -> Maybe i Source #
implemented in terms of findIndexFoldableWithIndex
sFindIndexIF :: (FoldableWithIndex i f, Integral i, HasOrdinal nat, SingI n) => (a -> Bool) -> Sized f (n :: nat) a -> Maybe (Ordinal n) Source #
implemented in terms of sFindIndexFoldableWithIndex
findIndices :: ListLike (f a) a => (a -> Bool) -> Sized f n a -> [Int] Source #
find all elements satisfying findIndices p xsp and returns their indices.
Since 0.1.0.0
findIndicesIF :: FoldableWithIndex i f => (a -> Bool) -> Sized f n a -> [i] Source #
implemented in terms of findIndicesFoldableWithIndex
sFindIndices :: (HasOrdinal nat, SingI (n :: nat), ListLike (f a) a) => (a -> Bool) -> Sized f n a -> [Ordinal n] Source #
Ordinal version of findIndices.
Since 0.1.0.0
sFindIndicesIF :: (FoldableWithIndex i f, Integral i, HasOrdinal nat, SingI n) => (a -> Bool) -> Sized f (n :: nat) a -> [Ordinal n] Source #
elemIndex :: (Eq a, ListLike (f a) a) => a -> Sized f n a -> Maybe Int Source #
Returns the index of the given element in the list, if exists.
Since 0.1.0.0
sElemIndex :: forall (n :: nat) f a. (SingI n, ListLike (f a) a, Eq a, HasOrdinal nat) => a -> Sized f n a -> Maybe (Ordinal n) Source #
Ordinal version of elemIndex
It statically checks boundary invariants.
If you don't internal structure on ,
then Sized is much faster and
also safe for most cases.sUnsafeElemIndex
Since 0.1.0.0
sUnsafeElemIndex :: forall (n :: nat) f a. (SingI n, ListLike (f a) a, Eq a, HasOrdinal nat) => a -> Sized f n a -> Maybe (Ordinal n) Source #
elemIndices :: (ListLike (f a) a, Eq a) => a -> Sized f n a -> [Int] Source #
Returns all indices of the given element in the list.
Since 0.1.0.0
sElemIndices :: (HasOrdinal nat, SingI (n :: nat), ListLike (f a) a, Eq a) => a -> Sized f n a -> [Ordinal n] Source #
Ordinal version of elemIndices
Since 0.1.0.0
viewCons :: forall f a (n :: nat). (HasOrdinal nat, ListLike (f a) a) => Sized f n a -> ConsView f n a Source #
Case analysis for the cons-side of sequence.
Since 0.1.0.0
viewSnoc :: forall f (n :: nat) a. (HasOrdinal nat, ListLike (f a) a) => Sized f n a -> SnocView f n a Source #
Case analysis for the snoc-side of sequence.
Since 0.1.0.0
pattern (:<) :: forall f (n :: Nat) a. ListLike (f a) a => forall (n1 :: Nat). (n ~ Succ n1, SingI n1) => a -> Sized f n1 a -> Sized f n a infixr 5 Source #