sized-0.8.0.0: Sized sequence data-types

Safe HaskellNone
LanguageHaskell2010

Data.Sized.Peano

Contents

Description

This module exports provides the functionality to make length-parametrized types from existing CFreeMonoid sequential types, parametrised with peano numeral Nat kind.

Most of the complexity of operations on Sized f n a are the same as original operations on f. For example, !! is O(1) for Sized Vector n a but O(i) for Sized [] n a.

This module also provides powerful view types and pattern synonyms to inspect the sized sequence. See Views and Patterns for more detail.

Synopsis

Main Data-types

type Sized = (Sized :: (Type -> Type) -> Nat -> Type -> Type) Source #

Sized wraps a sequential type f and makes length-parametrized version.

Here, f must satisfy CFreeMonoid f and Dom f a.

Since 0.2.0.0

type SomeSized f a = SomeSized' f Nat a Source #

Sized sequence 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.7.0.0

pattern SomeSized :: forall (f :: Type -> Type) a. forall (n :: Nat). SNat n -> Sized f n a -> SomeSized f a Source #

type Ordinal = (Ordinal :: Nat -> Type) Source #

class Dom f a => DomC f a Source #

Instances
Dom f a => DomC f a Source # 
Instance details

Defined in Data.Sized

Accessors

Length information

length :: (Dom f a, SingI n) => 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.8.0.0 (type changed)

sLength :: (Dom f a, SingI n) => Sized f n a -> SNat n Source #

Sing version of length.

Since 0.8.0.0 (type changed)

null :: (Dom f a, CFoldable f) => Sized f n a -> Bool Source #

Test if the sequence is empty or not.

Since 0.7.0.0

Indexing

(!!) :: (Dom f a, CFoldable f, (One <= m) ~ True) => Sized f m a -> Int -> a Source #

(Unsafe) indexing with Ints. If you want to check boundary statically, use %!! or sIndex.

Since 0.7.0.0

(%!!) :: (Dom f c, CFoldable f) => Sized f n c -> Ordinal n -> c Source #

Safe indexing with Ordinals.

Since 0.7.0.0

index :: (Dom f a, CFoldable f, (One <= m) ~ True) => Int -> Sized f m a -> a Source #

Flipped version of !!.

Since 0.7.0.0

sIndex :: (Dom f c, CFoldable f) => Ordinal n -> Sized f n c -> c Source #

Flipped version of %!!.

Since 0.7.0.0

head :: (Dom f a, CFoldable f, (Z < n) ~ True) => Sized f n a -> a 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.7.0.0

last :: (Dom f a, CFoldable f, (Z < n) ~ True) => Sized f n a -> a 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.7.0.0

uncons :: (Dom f a, SingI n, CFreeMonoid f, (Z < n) ~ True) => Sized f n a -> Uncons 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.7.0.0

uncons' :: (Dom f a, SingI n, CFreeMonoid f, (Z < n) ~ True) => Sized f n a -> Uncons f n a Source #

uncons with explicit specified length n

Since 0.7.0.0

type Uncons f (n :: Nat) a = Uncons f n a Source #

pattern Uncons :: forall (f :: Type -> Type) (n :: Nat) a. () => forall (n1 :: Nat). (n ~ Succ n1, SingI n1) => a -> Sized f n1 a -> Uncons f n a Source #

unsnoc :: (Dom f a, SingI n, CFreeMonoid f, (Z < n) ~ True) => Sized f n a -> Unsnoc f n a 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.7.0.0

unsnoc' :: (Dom f a, SingI n, CFreeMonoid f) => proxy n -> Sized f (S n) a -> Unsnoc f (S n) a Source #

unsnoc' with explicit specified length n

Since 0.7.0.0

type Unsnoc f (n :: Nat) a = Unsnoc f n a Source #

pattern Unsnoc :: forall (f :: Type -> Type) (n :: Nat) a. () => forall (n1 :: Nat). n ~ Succ n1 => Sized f n1 a -> a -> Unsnoc f n a Source #

Slicing

tail :: (Dom f a, CFreeMonoid f) => Sized f (One + n) a -> Sized f n 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.7.0.0

init :: (Dom f a, CFreeMonoid f) => Sized f (n + One) 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.7.0.0

take :: (Dom f a, CFreeMonoid f, (n <= m) ~ True) => SNat n -> 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.

Since 0.7.0.0

takeAtMost :: (Dom f a, CFreeMonoid f) => SNat n -> Sized f m a -> Sized f (Min n m) a Source #

takeAtMost k xs takes first at most k elements of xs.

Since 0.7.0.0

drop :: (Dom f a, CFreeMonoid f, (n <= m) ~ True) => SNat n -> 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.

Since 0.7.0.0

splitAt :: (Dom f a, CFreeMonoid f, (n <= m) ~ True) => SNat n -> 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.

Since 0.7.0.0

splitAtMost :: (Dom f a, CFreeMonoid f) => SNat n -> 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.

Since 0.7.0.0

Construction

Initialisation

empty :: (Dom f a, Monoid (f a)) => Sized f Z a Source #

Empty sequence.

Since 0.7.0.0 (type changed)

singleton :: (Dom f a, CFreeMonoid f) => a -> Sized f One a Source #

Sequence with one element.

Since 0.7.0.0

toSomeSized :: (Dom f a, CFoldable f) => f a -> SomeSized f a Source #

Consruct the Sized sequence from base type, but the length parameter is dynamically determined and existentially quantified; see also SomeSized'.

Since 0.7.0.0

replicate :: (Dom f a, CFreeMonoid f) => SNat n -> a -> Sized f n a Source #

Replicates the same value.

Since 0.7.0.0

replicate' :: (Dom f a, CFreeMonoid f, SingI n) => a -> Sized f n a Source #

replicate with the length inferred.

Since 0.7.0.0

generate :: (Dom f a, CFreeMonoid f) => SNat n -> (Ordinal n -> a) -> Sized f n a Source #

Construct a sequence of the given length by applying the function to each index.

Since 0.7.0.0

generate' :: forall f n a. (SingI n, Dom f a, CFreeMonoid f) => (Ordinal n -> a) -> Sized f n a Source #

generate with length inferred.

Since 0.8.0.0

Concatenation

cons :: (Dom f a, CFreeMonoid f) => a -> Sized f n a -> Sized f (S n) a Source #

Append an element to the head of sequence.

Since 0.7.0.0

(<|) :: (Dom f a, CFreeMonoid f) => a -> Sized f n a -> Sized f (S n) a Source #

Infix version of snoc.

Since 0.7.0.0

snoc :: (Dom f a, CFreeMonoid f) => Sized f n a -> a -> Sized f (n + One) a Source #

Append an element to the tail of sequence.

Since 0.7.0.0

(|>) :: (Dom f a, CFreeMonoid f) => Sized f n a -> a -> Sized f (n + One) a Source #

Append an element to the tail of sequence.

Since 0.7.0.0

append :: (Dom f a, CFreeMonoid f) => Sized f n a -> Sized f m a -> Sized f (n + m) a Source #

Append two lists.

Since 0.7.0.0

(++) :: (Dom f a, CFreeMonoid f) => Sized f n a -> Sized f m a -> Sized f (n + m) a Source #

Infix version of append.

Since 0.7.0.0

concat :: (Dom f a, Dom f' (f a), Dom f' (Sized f n a), CFreeMonoid f, CFunctor f', CFoldable f') => Sized f' m (Sized f n a) -> Sized f (m * n) a Source #

Concatenates multiple sequences into one.

Since 0.7.0.0

Zips

zip :: (Dom f a, Dom f b, Dom f (a, b), CZip f) => 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.7.0.0

zipSame :: (Dom f a, Dom f b, Dom f (a, b), CZip f) => Sized f n a -> Sized f n b -> Sized f n (a, b) Source #

zip for the sequences of the same length.

Since 0.7.0.0

zipWith :: (Dom f a, Dom f b, Dom f c, CZip f, CFreeMonoid f) => (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.7.0.0

zipWithSame :: (Dom f a, Dom f b, Dom f c, CZip f, CFreeMonoid f) => (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.7.0.0

unzip :: (Dom f a, Dom f b, Dom f (a, b), CUnzip f) => Sized f n (a, b) -> (Sized f n a, Sized f n b) Source #

Unzipping the sequence of tuples.

Since 0.7.0.0

unzipWith :: (Dom f a, Dom f b, Dom f c, CUnzip f) => (a -> (b, c)) -> Sized f n a -> (Sized f n b, Sized f n c) Source #

Unzipping the sequence of tuples.

Since 0.7.0.0

Transformation

map :: (Dom f a, Dom f b, CFreeMonoid f) => (a -> b) -> Sized f n a -> Sized f n b Source #

Map function.

Since 0.7.0.0

reverse :: (Dom f a, CFreeMonoid f) => Sized f n a -> Sized f n a Source #

Reverse function.

Since 0.7.0.0

intersperse :: (Dom f a, CFreeMonoid f) => a -> Sized f n a -> Sized f ((Two * n) -. One) a Source #

Intersperces.

Since 0.7.0.0

nub :: (Dom f a, Eq a, CFreeMonoid f) => Sized f n a -> SomeSized f a Source #

Remove all duplicates.

Since 0.7.0.0

sort :: (Dom f a, CFreeMonoid f, Ord a) => Sized f n a -> Sized f n a Source #

Sorting sequence by ascending order.

Since 0.7.0.0

sortBy :: (Dom f a, CFreeMonoid f) => (a -> a -> Ordering) -> Sized f n a -> Sized f n a Source #

Generalized version of sort.

Since 0.7.0.0

insert :: (Dom f a, CFreeMonoid f, Ord a) => a -> Sized f n a -> Sized f (S n) a Source #

Insert new element into the presorted sequence.

Since 0.7.0.0

insertBy :: (Dom f a, CFreeMonoid f) => (a -> a -> Ordering) -> a -> Sized f n a -> Sized f (S n) a Source #

Generalized version of insert.

Since 0.7.0.0

Conversion

List

toList :: (Dom f a, CFoldable f) => Sized f n a -> [a] Source #

Convert to list.

Since 0.7.0.0

fromList :: (Dom f a, CFreeMonoid f) => SNat n -> [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.7.0.0 (type changed)

fromList' :: (Dom f a, CFreeMonoid f, SingI n) => [a] -> Maybe (Sized f n a) Source #

fromList with the result length inferred.

Since 0.7.0.0

unsafeFromList :: (Dom f a, CFreeMonoid f) => SNat 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.7.0.0

unsafeFromList' :: (Dom f a, SingI n, CFreeMonoid f) => [a] -> Sized f n a Source #

unsafeFromList with the result length inferred.

Since 0.7.0.0

fromListWithDefault :: (Dom f a, CFreeMonoid f) => SNat 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.5.0.0 (type changed)

fromListWithDefault' :: (Dom f a, SingI n, CFreeMonoid f) => a -> [a] -> Sized f n a Source #

fromListWithDefault with the result length inferred.

Since 0.7.0.0

Base container

unsized :: Sized f n a -> f a Source #

Forget the length and obtain the wrapped base container.

Since 0.7.0.0

toSized :: (Dom f a, CFreeMonoid f) => SNat n -> 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.7.0.0

toSized' :: (Dom f a, CFreeMonoid f, SingI n) => f a -> Maybe (Sized f n a) Source #

toSized with the result length inferred.

Since 0.7.0.0

unsafeToSized :: SNat 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.7.0.0

unsafeToSized' :: (Dom f a, SingI n) => f a -> Sized f n a Source #

unsafeToSized with the result length inferred.

Since 0.7.0.0

toSizedWithDefault :: (Dom f a, CFreeMonoid f) => SNat n -> 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.7.0.0

toSizedWithDefault' :: (Dom f a, SingI n, CFreeMonoid f) => a -> f a -> Sized f n a Source #

toSizedWithDefault with the result length inferred.

Since 0.7.0.0

Querying

Partitioning

type Partitioned f (n :: Nat) a = Partitioned f n a 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 ls and rs, and their length are lenL and lenR resp.
  • lenL + lenR = n

Since 0.7.0.0

pattern Partitioned :: forall (f :: Type -> Type) (n :: Nat) a. () => forall (n1 :: Nat) (m :: Nat). (n ~ (n1 + m), Dom f a) => SNat n1 -> Sized f n1 a -> SNat m -> Sized f m a -> Partitioned f n a Source #

takeWhile :: (Dom f a, CFreeMonoid f) => (a -> Bool) -> Sized f n a -> SomeSized f a Source #

Take the initial segment as long as elements satisfys the predicate.

Since 0.7.0.0

dropWhile :: (Dom f a, CFreeMonoid f) => (a -> Bool) -> Sized f n a -> SomeSized f a Source #

Drop the initial segment as long as elements satisfys the predicate.

Since 0.7.0.0

span :: (Dom f a, CFreeMonoid f) => (a -> Bool) -> Sized f n a -> Partitioned f n a Source #

Split the sequence into the longest prefix of elements that satisfy the predicate and the rest.

Since 0.7.0.0

break :: (Dom f a, CFreeMonoid f) => (a -> Bool) -> Sized f n a -> Partitioned f n a Source #

Split the sequence into the longest prefix of elements that do not satisfy the predicate and the rest.

Since 0.7.0.0

partition :: (Dom f a, CFreeMonoid f) => (a -> Bool) -> Sized f n a -> Partitioned f n a Source #

Split the sequence in two parts, the first one containing those elements that satisfy the predicate and the second one those that don't.

Since 0.7.0.0

Searching

elem :: (Dom f a, CFoldable f, Eq a) => a -> Sized f n a -> Bool Source #

Membership test; see also notElem.

Since 0.7.0.0

notElem :: (Dom f a, CFoldable f, Eq a) => a -> Sized f n a -> Bool Source #

Negation of elem.

Since 0.7.0.0

find :: (Dom f a, CFoldable f) => (a -> Bool) -> Sized f n a -> Maybe a Source #

Find the element satisfying the predicate.

Since 0.7.0.0

findIndex :: (Dom f a, CFoldable f) => (a -> Bool) -> Sized f n a -> Maybe Int Source #

findIndex p xs find the element satisfying p and returns its index if exists.

Since 0.7.0.0

sFindIndex :: (Dom f a, SingI n, CFoldable f) => (a -> Bool) -> Sized f n a -> Maybe (Ordinal n) Source #

Ordinal version of findIndex.

Since 0.7.0.0

findIndices :: (Dom f a, CFoldable f) => (a -> Bool) -> Sized f n a -> [Int] Source #

findIndices p xs find all elements satisfying p and returns their indices.

Since 0.7.0.0

sFindIndices :: (Dom f a, CFoldable f, SingI n) => (a -> Bool) -> Sized f n a -> [Ordinal n] Source #

Ordinal version of findIndices.

Since 0.7.0.0

elemIndex :: (Dom f a, CFoldable f, Eq a) => a -> Sized f n a -> Maybe Int Source #

Returns the index of the given element in the list, if exists.

Since 0.7.0.0

sElemIndex :: (Dom f a, SingI n, CFoldable f, Eq a) => a -> Sized f n a -> Maybe (Ordinal n) Source #

Ordinal version of elemIndex. Since 0.7.0.0, we no longer do boundary check inside the definition.

Since 0.7.0.0

sUnsafeElemIndex :: (Dom f a, SingI n, CFoldable f, Eq a) => a -> Sized f n a -> Maybe (Ordinal n) Source #

Deprecated: Use sElemIndex instead

Ordinal version of elemIndex. Since 0.7.0.0, we no longer do boundary check inside the definition.

Since 0.7.0.0

elemIndices :: (Dom f a, CFoldable f, Eq a) => a -> Sized f n a -> [Int] Source #

Returns all indices of the given element in the list.

Since 0.8.0.0

sElemIndices :: (Dom f a, CFoldable f, SingI n, Eq a) => a -> Sized f n a -> [Ordinal n] Source #

Ordinal version of elemIndices

Since 0.8.0.0

Views and Patterns

With GHC's ViewPatterns and PatternSynonym extensions, we can pattern-match on arbitrary Sized f n a if f is list-like functor. Curretnly, there are two direction view and patterns: Cons and Snoc. Assuming underlying sequence type f has O(1) implementation for cnull, chead (resp. clast) and ctail (resp. cinit), We can view and pattern-match on cons (resp. snoc) of Sized f n a in O(1).

Views

With ViewPatterns extension, we can pattern-match on Sized value as follows:

slen :: (KnownNat n, 'Dom f a' f) => Sized f n a -> Sing n
slen (viewCons -> NilCV)    = SZ
slen (viewCons -> _ :- as) = SS (slen as)
slen _                          = error "impossible"

The constraint (KnownNat n, 'Dom f a' f) is needed for view function. In the above, we have extra wildcard pattern (_) at the last. Code compiles if we removed it, but current GHC warns for incomplete pattern, although we know first two patterns exhausts all the case.

Equivalently, we can use snoc-style pattern-matching:

slen :: (KnownNat n, 'Dom f a' f) => Sized f n a -> Sing n
slen (viewSnoc -> NilSV)     = SZ
slen (viewSnoc -> as -:: _) = SS (slen as)

Patterns

So we can pattern match on both end of sequence via views, but it is rather clumsy to nest it. For example:

nextToHead :: ('Dom f a' f, SingI n) => Sized f (S (S n)) a -> a
nextToHead (viewCons -> _ :- (viewCons -> a :- _)) = a

In such a case, with PatternSynonyms extension we can write as follows:

nextToHead :: ('Dom f a' f, SingI n) => Sized f (S (S n)) a -> a
nextToHead (_ :< a :< _) = a

Of course, we can also rewrite above slen example using PatternSynonyms:

slen :: (SingI n, 'Dom f a' f) => Sized f n a -> Sing n
slen Nil      = SZ
slen (_ :< as) = SS (slen as)
slen _           = error "impossible"

So, we can use :< and Nil (resp. :> and Nil) to pattern-match directly on cons-side (resp. snoc-side) as we usually do for lists. Nil, :<, and :> are neither functions nor data constructors, but pattern synonyms so we cannot use them in expression contexts. For more detail on pattern synonyms, see GHC Users Guide and HaskellWiki.

Definitions

viewCons :: (Dom f a, SingI n, CFreeMonoid f) => Sized f n a -> ConsView f n a Source #

Case analysis for the cons-side of sequence.

Since 0.5.0.0 (type changed)

type ConsView f (n :: Nat) a = ConsView f n a Source #

View of the left end of sequence (cons-side).

Since 0.7.0.0

pattern (:-) :: forall (f :: Type -> Type) n a. () => forall n1. (n ~ (One + n1), SingI n1) => a -> Sized f n1 a -> ConsView f n a infixr 9 Source #

Since 0.8.0.0

pattern NilCV :: forall (f :: Type -> Type) n a. () => n ~ Z => ConsView f n a Source #

Since 0.8.0.0

viewSnoc :: (Dom f a, SingI n, CFreeMonoid f) => Sized f n a -> ConsView f n a Source #

Case analysis for the snoc-side of sequence.

Since 0.8.0.0 (type changed)

type SnocView f (n :: Nat) a = SnocView f n a Source #

View of the left end of sequence (snoc-side).

Since 0.7.0.0

pattern (:-::) :: forall (f :: Type -> Type) n a. () => forall n1. (n ~ (n1 + One), SingI n1) => Sized f n1 a -> a -> SnocView f n a infixl 9 Source #

Since 0.8.0.0

pattern NilSV :: forall (f :: Type -> Type) n a. () => n ~ Z => SnocView f n a Source #

Since 0.8.0.0

pattern Nil :: forall (f :: Type -> Type) a n. (Dom f a, SingI n, CFreeMonoid f) => n ~ Z => Sized f n a Source #

Pattern synonym for a nil sequence.

pattern (:<) :: forall (f :: Type -> Type) a (n :: Nat). (Dom f a, SingI n, CFreeMonoid f) => forall (n1 :: Nat). (n ~ Succ n1, SingI n1) => a -> Sized f n1 a -> Sized f n a infixr 5 Source #

Pattern synonym for cons-side uncons.

pattern NilL :: forall f (n :: Nat) a. (SingI n, CFreeMonoid f, Dom f a) => n ~ Z => Sized f n a Source #

Pattern synonym for cons-side nil.

pattern (:>) :: forall (f :: Type -> Type) a (n :: Nat). (Dom f a, SingI n, CFreeMonoid f) => forall (n1 :: Nat). (n ~ (n1 + One), SingI n1) => Sized f n1 a -> a -> Sized f n a infixl 5 Source #

Pattern synonym for snoc-side unsnoc.

pattern NilR :: forall f (n :: Nat) a. (CFreeMonoid f, Dom f a, SingI n) => n ~ Z => Sized f n a Source #

Pattern synonym for snoc-side nil.