Agda-2.6.2.2.20221106: A dependently typed functional programming language and proof assistant
Safe HaskellSafe-Inferred
LanguageHaskell2010

Agda.Utils.List1

Description

Non-empty lists.

Better name List1 for non-empty lists, plus missing functionality.

Import: @

{-# LANGUAGE PatternSynonyms #-}

import Agda.Utils.List1 (List1, pattern (:|)) import qualified Agda.Utils.List1 as List1

@

Synopsis

Documentation

fromListSafe Source #

Arguments

:: List1 a

Default value if convertee is empty.

-> [a]

List to convert, supposedly non-empty.

-> List1 a

Converted list.

Safe version of fromList.

initLast :: List1 a -> ([a], a) Source #

Return the last element and the rest.

snoc :: [a] -> a -> List1 a Source #

Build a list with one element.

More precise type for snoc.

groupBy' :: forall a. (a -> a -> Bool) -> [a] -> [List1 a] Source #

More precise type for groupBy'.

A variant of groupBy which applies the predicate to consecutive pairs. O(n).

wordsBy :: (a -> Bool) -> [a] -> [List1 a] Source #

Split a list into sublists. Generalisation of the prelude function words. Same as wordsBy and wordsBy, but with the non-emptyness guarantee on the chunks. O(n).

words xs == wordsBy isSpace xs

breakAfter :: (a -> Bool) -> List1 a -> (List1 a, [a]) Source #

Breaks a list just after an element satisfying the predicate is found.

>>> breakAfter even [1,3,5,2,4,7,8]
([1,3,5,2],[4,7,8])

concat :: [List1 a] -> [a] Source #

Concatenate one or more non-empty lists.

union :: Eq a => List1 a -> List1 a -> List1 a Source #

Like union. Duplicates in the first list are not removed. O(nm).

ifNull :: [a] -> b -> (List1 a -> b) -> b Source #

ifNotNull :: [a] -> (List1 a -> b) -> b -> b Source #

unlessNull :: Null m => [a] -> (List1 a -> m) -> m Source #

allEqual :: Eq a => List1 a -> Bool Source #

Checks if all the elements in the list are equal. Assumes that the Eq instance stands for an equivalence relation. O(n).

catMaybes :: List1 (Maybe a) -> [a] Source #

Like catMaybes.

mapMaybe :: (a -> Maybe b) -> List1 a -> [b] Source #

Like filter.

lefts :: List1 (Either a b) -> [a] Source #

Like lefts.

rights :: List1 (Either a b) -> [b] Source #

Like rights.

nubM :: Monad m => (a -> a -> m Bool) -> List1 a -> m (List1 a) Source #

Non-efficient, monadic nub. O(n²).

zipWithM :: Applicative m => (a -> b -> m c) -> List1 a -> List1 b -> m (List1 c) Source #

Like zipWithM.

zipWithM_ :: Applicative m => (a -> b -> m c) -> List1 a -> List1 b -> m () Source #

Like zipWithM.

foldr :: (a -> b -> b) -> (a -> b) -> List1 a -> b Source #

List foldr but with a base case for the singleton list.

data NonEmpty a #

Non-empty (and non-strict) list type.

Since: base-4.9.0.0

Constructors

a :| [a] infixr 5 

Instances

Instances details
NumHoles NameParts Source # 
Instance details

Defined in Agda.Syntax.Concrete.Name

FromJSON1 NonEmpty 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (NonEmpty a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [NonEmpty a] #

ToJSON1 NonEmpty 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> NonEmpty a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [NonEmpty a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> NonEmpty a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [NonEmpty a] -> Encoding #

MonadFix NonEmpty

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> NonEmpty a) -> NonEmpty a #

Foldable NonEmpty

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => NonEmpty m -> m #

foldMap :: Monoid m => (a -> m) -> NonEmpty a -> m #

foldMap' :: Monoid m => (a -> m) -> NonEmpty a -> m #

foldr :: (a -> b -> b) -> b -> NonEmpty a -> b #

foldr' :: (a -> b -> b) -> b -> NonEmpty a -> b #

foldl :: (b -> a -> b) -> b -> NonEmpty a -> b #

foldl' :: (b -> a -> b) -> b -> NonEmpty a -> b #

foldr1 :: (a -> a -> a) -> NonEmpty a -> a #

foldl1 :: (a -> a -> a) -> NonEmpty a -> a #

toList :: NonEmpty a -> [a] #

null :: NonEmpty a -> Bool #

length :: NonEmpty a -> Int #

elem :: Eq a => a -> NonEmpty a -> Bool #

maximum :: Ord a => NonEmpty a -> a #

minimum :: Ord a => NonEmpty a -> a #

sum :: Num a => NonEmpty a -> a #

product :: Num a => NonEmpty a -> a #

Eq1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> NonEmpty a -> NonEmpty b -> Bool #

Ord1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> NonEmpty a -> NonEmpty b -> Ordering #

Read1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (NonEmpty a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [NonEmpty a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (NonEmpty a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [NonEmpty a] #

Show1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NonEmpty a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [NonEmpty a] -> ShowS #

Traversable NonEmpty

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> NonEmpty a -> f (NonEmpty b) #

sequenceA :: Applicative f => NonEmpty (f a) -> f (NonEmpty a) #

mapM :: Monad m => (a -> m b) -> NonEmpty a -> m (NonEmpty b) #

sequence :: Monad m => NonEmpty (m a) -> m (NonEmpty a) #

Applicative NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

pure :: a -> NonEmpty a #

(<*>) :: NonEmpty (a -> b) -> NonEmpty a -> NonEmpty b #

liftA2 :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c #

(*>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

(<*) :: NonEmpty a -> NonEmpty b -> NonEmpty a #

Functor NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

fmap :: (a -> b) -> NonEmpty a -> NonEmpty b #

(<$) :: a -> NonEmpty b -> NonEmpty a #

Monad NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(>>=) :: NonEmpty a -> (a -> NonEmpty b) -> NonEmpty b #

(>>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

return :: a -> NonEmpty a #

NFData1 NonEmpty

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> NonEmpty a -> () #

Hashable1 NonEmpty 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> NonEmpty a -> Int

Generic1 NonEmpty 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 NonEmpty :: k -> Type #

Methods

from1 :: forall (a :: k). NonEmpty a -> Rep1 NonEmpty a #

to1 :: forall (a :: k). Rep1 NonEmpty a -> NonEmpty a #

Singleton a (NonEmpty a) Source # 
Instance details

Defined in Agda.Utils.Singleton

Methods

singleton :: a -> NonEmpty a Source #

Lift a => Lift (NonEmpty a :: Type)

Since: template-haskell-2.15.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => NonEmpty a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => NonEmpty a -> Code m (NonEmpty a) #

Pretty a => Pretties (List1 a) Source # 
Instance details

Defined in Agda.Compiler.JS.Pretty

Methods

pretties :: (Nat, Bool) -> List1 a -> [Doc] Source #

SubstExpr a => SubstExpr (List1 a) Source # 
Instance details

Defined in Agda.Syntax.Abstract

Methods

substExpr :: [(Name, Expr)] -> List1 a -> List1 a Source #

DeclaredNames a => DeclaredNames (List1 a) Source # 
Instance details

Defined in Agda.Syntax.Abstract.Views

Methods

declaredNames :: Collection KName m => List1 a -> m Source #

ExprLike a => ExprLike (List1 a) Source # 
Instance details

Defined in Agda.Syntax.Abstract.Views

ExprLike a => ExprLike (List1 a) Source # 
Instance details

Defined in Agda.Syntax.Concrete.Generic

Methods

mapExpr :: (Expr -> Expr) -> List1 a -> List1 a Source #

foldExpr :: Monoid m => (Expr -> m) -> List1 a -> m Source #

traverseExpr :: Monad m => (Expr -> m Expr) -> List1 a -> m (List1 a) Source #

CPatternLike p => CPatternLike (List1 p) Source # 
Instance details

Defined in Agda.Syntax.Concrete.Pattern

Methods

foldrCPattern :: Monoid m => (Pattern -> m -> m) -> List1 p -> m Source #

traverseCPatternA :: (Applicative m, Functor m) => (Pattern -> m Pattern -> m Pattern) -> List1 p -> m (List1 p) Source #

traverseCPatternM :: Monad m => (Pattern -> m Pattern) -> (Pattern -> m Pattern) -> List1 p -> m (List1 p) Source #

NamesIn a => NamesIn (List1 a) Source # 
Instance details

Defined in Agda.Syntax.Internal.Names

Methods

namesAndMetasIn' :: Monoid m => (Either QName MetaId -> m) -> List1 a -> m Source #

HasRange a => HasRange (List1 a) Source #

Precondition: The ranges of the list elements must point to the same file (or be empty).

Instance details

Defined in Agda.Syntax.Position

Methods

getRange :: List1 a -> Range Source #

KillRange a => KillRange (List1 a) Source # 
Instance details

Defined in Agda.Syntax.Position

ToConcrete a => ToConcrete (List1 a) Source # 
Instance details

Defined in Agda.Syntax.Translation.AbstractToConcrete

Associated Types

type ConOfAbs (List1 a) Source #

ToAbstract c => ToAbstract (List1 c) Source # 
Instance details

Defined in Agda.Syntax.Translation.ConcreteToAbstract

Associated Types

type AbsOfCon (List1 c) Source #

ToAbstract (List1 (QNamed Clause)) Source # 
Instance details

Defined in Agda.Syntax.Translation.ReflectedToAbstract

Associated Types

type AbsOfRef (List1 (QNamed Clause)) Source #

EmbPrj a => EmbPrj (List1 a) Source # 
Instance details

Defined in Agda.TypeChecking.Serialise.Instances.Common

Methods

icode :: List1 a -> S Int32 Source #

icod_ :: List1 a -> S Int32 Source #

value :: Int32 -> R (List1 a) Source #

Pretty a => Pretty (List1 a) Source # 
Instance details

Defined in Agda.Utils.Pretty

Sized (List1 a) Source # 
Instance details

Defined in Agda.Utils.Size

Methods

size :: List1 a -> Int Source #

FromJSON a => FromJSON (NonEmpty a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (NonEmpty a) #

parseJSONList :: Value -> Parser [NonEmpty a] #

ToJSON a => ToJSON (NonEmpty a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Semigroup (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: NonEmpty a -> NonEmpty a -> NonEmpty a #

sconcat :: NonEmpty (NonEmpty a) -> NonEmpty a #

stimes :: Integral b => b -> NonEmpty a -> NonEmpty a #

IsList (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Exts

Associated Types

type Item (NonEmpty a) #

Methods

fromList :: [Item (NonEmpty a)] -> NonEmpty a #

fromListN :: Int -> [Item (NonEmpty a)] -> NonEmpty a #

toList :: NonEmpty a -> [Item (NonEmpty a)] #

Generic (NonEmpty a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (NonEmpty a) :: Type -> Type #

Methods

from :: NonEmpty a -> Rep (NonEmpty a) x #

to :: Rep (NonEmpty a) x -> NonEmpty a #

Read a => Read (NonEmpty a)

Since: base-4.11.0.0

Instance details

Defined in GHC.Read

Show a => Show (NonEmpty a)

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> NonEmpty a -> ShowS #

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Binary a => Binary (NonEmpty a)

Since: binary-0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: NonEmpty a -> Put #

get :: Get (NonEmpty a) #

putList :: [NonEmpty a] -> Put #

NFData a => NFData (NonEmpty a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: NonEmpty a -> () #

Eq a => Eq (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(==) :: NonEmpty a -> NonEmpty a -> Bool #

(/=) :: NonEmpty a -> NonEmpty a -> Bool #

Ord a => Ord (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

compare :: NonEmpty a -> NonEmpty a -> Ordering #

(<) :: NonEmpty a -> NonEmpty a -> Bool #

(<=) :: NonEmpty a -> NonEmpty a -> Bool #

(>) :: NonEmpty a -> NonEmpty a -> Bool #

(>=) :: NonEmpty a -> NonEmpty a -> Bool #

max :: NonEmpty a -> NonEmpty a -> NonEmpty a #

min :: NonEmpty a -> NonEmpty a -> NonEmpty a #

Hashable a => Hashable (NonEmpty a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> NonEmpty a -> Int

hash :: NonEmpty a -> Int

AddContext (List1 Name, Dom Type) Source # 
Instance details

Defined in Agda.TypeChecking.Monad.Context

AddContext (List1 (Arg Name), Type) Source # 
Instance details

Defined in Agda.TypeChecking.Monad.Context

Methods

addContext :: MonadAddContext m => (List1 (Arg Name), Type) -> m a -> m a Source #

contextSize :: (List1 (Arg Name), Type) -> Nat Source #

AddContext (List1 (NamedArg Name), Type) Source # 
Instance details

Defined in Agda.TypeChecking.Monad.Context

AddContext (List1 (WithHiding Name), Dom Type) Source # 
Instance details

Defined in Agda.TypeChecking.Monad.Context

type Rep1 NonEmpty

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type ConOfAbs (List1 a) Source # 
Instance details

Defined in Agda.Syntax.Translation.AbstractToConcrete

type ConOfAbs (List1 a) = List1 (ConOfAbs a)
type AbsOfCon (List1 c) Source # 
Instance details

Defined in Agda.Syntax.Translation.ConcreteToAbstract

type AbsOfCon (List1 c) = List1 (AbsOfCon c)
type AbsOfRef (List1 (QNamed Clause)) Source # 
Instance details

Defined in Agda.Syntax.Translation.ReflectedToAbstract

type Item (NonEmpty a) 
Instance details

Defined in GHC.Exts

type Item (NonEmpty a) = a
type Rep (NonEmpty a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

zipWith :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c #

The zipWith function generalizes zip. Rather than tupling the elements, the elements are combined using the function passed as the first argument.

zip :: NonEmpty a -> NonEmpty b -> NonEmpty (a, b) #

The zip function takes two streams and returns a stream of corresponding pairs.

xor :: NonEmpty Bool -> Bool #

Compute n-ary logic exclusive OR operation on NonEmpty list.

unzip :: Functor f => f (a, b) -> (f a, f b) #

The unzip function is the inverse of the zip function.

unfoldr :: (a -> (b, Maybe a)) -> a -> NonEmpty b #

The unfoldr function is analogous to Data.List's unfoldr operation.

unfold :: (a -> (b, Maybe a)) -> a -> NonEmpty b #

unfold produces a new stream by repeatedly applying the unfolding function to the seed value to produce an element of type b and a new seed value. When the unfolding function returns Nothing instead of a new seed value, the stream ends.

uncons :: NonEmpty a -> (a, Maybe (NonEmpty a)) #

uncons produces the first element of the stream, and a stream of the remaining elements, if any.

transpose :: NonEmpty (NonEmpty a) -> NonEmpty (NonEmpty a) #

transpose for NonEmpty, behaves the same as transpose The rows/columns need not be the same length, in which case > transpose . transpose /= id

takeWhile :: (a -> Bool) -> NonEmpty a -> [a] #

takeWhile p xs returns the longest prefix of the stream xs for which the predicate p holds.

take :: Int -> NonEmpty a -> [a] #

take n xs returns the first n elements of xs.

tails :: Foldable f => f a -> NonEmpty [a] #

The tails function takes a stream xs and returns all the suffixes of xs.

tail :: NonEmpty a -> [a] #

Extract the possibly-empty tail of the stream.

splitAt :: Int -> NonEmpty a -> ([a], [a]) #

splitAt n xs returns a pair consisting of the prefix of xs of length n and the remaining stream immediately following this prefix.

'splitAt' n xs == ('take' n xs, 'drop' n xs)
xs == ys ++ zs where (ys, zs) = 'splitAt' n xs

span :: (a -> Bool) -> NonEmpty a -> ([a], [a]) #

span p xs returns the longest prefix of xs that satisfies p, together with the remainder of the stream.

'span' p xs == ('takeWhile' p xs, 'dropWhile' p xs)
xs == ys ++ zs where (ys, zs) = 'span' p xs

sortWith :: Ord o => (a -> o) -> NonEmpty a -> NonEmpty a #

sortWith for NonEmpty, behaves the same as:

sortBy . comparing

sortBy :: (a -> a -> Ordering) -> NonEmpty a -> NonEmpty a #

sortBy for NonEmpty, behaves the same as sortBy

sort :: Ord a => NonEmpty a -> NonEmpty a #

Sort a stream.

some1 :: Alternative f => f a -> f (NonEmpty a) #

some1 x sequences x one or more times.

singleton :: a -> NonEmpty a #

Construct a NonEmpty list from a single element.

Since: base-4.15

scanr1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty a #

scanr1 is a variant of scanr that has no starting value argument.

scanr :: Foldable f => (a -> b -> b) -> b -> f a -> NonEmpty b #

scanr is the right-to-left dual of scanl. Note that

head (scanr f z xs) == foldr f z xs.

scanl1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty a #

scanl1 is a variant of scanl that has no starting value argument:

scanl1 f [x1, x2, ...] == x1 :| [x1 `f` x2, x1 `f` (x2 `f` x3), ...]

scanl :: Foldable f => (b -> a -> b) -> b -> f a -> NonEmpty b #

scanl is similar to foldl, but returns a stream of successive reduced values from the left:

scanl f z [x1, x2, ...] == z :| [z `f` x1, (z `f` x1) `f` x2, ...]

Note that

last (scanl f z xs) == foldl f z xs.

reverse :: NonEmpty a -> NonEmpty a #

reverse a finite NonEmpty stream.

repeat :: a -> NonEmpty a #

repeat x returns a constant stream, where all elements are equal to x.

prependList :: [a] -> NonEmpty a -> NonEmpty a #

Attach a list at the beginning of a NonEmpty.

>>> prependList [] (1 :| [2,3])
1 :| [2,3]
>>> prependList [negate 1, 0] (1 :| [2, 3])
-1 :| [0,1,2,3]

Since: base-4.16

partition :: (a -> Bool) -> NonEmpty a -> ([a], [a]) #

The partition function takes a predicate p and a stream xs, and returns a pair of lists. The first list corresponds to the elements of xs for which p holds; the second corresponds to the elements of xs for which p does not hold.

'partition' p xs = ('filter' p xs, 'filter' (not . p) xs)

nubBy :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty a #

The nubBy function behaves just like nub, except it uses a user-supplied equality predicate instead of the overloaded == function.

nub :: Eq a => NonEmpty a -> NonEmpty a #

The nub function removes duplicate elements from a list. In particular, it keeps only the first occurrence of each element. (The name nub means 'essence'.) It is a special case of nubBy, which allows the programmer to supply their own inequality test.

nonEmpty :: [a] -> Maybe (NonEmpty a) #

nonEmpty efficiently turns a normal list into a NonEmpty stream, producing Nothing if the input is empty.

map :: (a -> b) -> NonEmpty a -> NonEmpty b #

Map a function over a NonEmpty stream.

length :: NonEmpty a -> Int #

Number of elements in NonEmpty list.

last :: NonEmpty a -> a #

Extract the last element of the stream.

iterate :: (a -> a) -> a -> NonEmpty a #

iterate f x produces the infinite sequence of repeated applications of f to x.

iterate f x = x :| [f x, f (f x), ..]

isPrefixOf :: Eq a => [a] -> NonEmpty a -> Bool #

The isPrefixOf function returns True if the first argument is a prefix of the second.

intersperse :: a -> NonEmpty a -> NonEmpty a #

'intersperse x xs' alternates elements of the list with copies of x.

intersperse 0 (1 :| [2,3]) == 1 :| [0,2,0,3]

insert :: (Foldable f, Ord a) => a -> f a -> NonEmpty a #

insert x xs inserts x into the last position in xs where it is still less than or equal to the next element. In particular, if the list is sorted beforehand, the result will also be sorted.

inits :: Foldable f => f a -> NonEmpty [a] #

The inits function takes a stream xs and returns all the finite prefixes of xs.

init :: NonEmpty a -> [a] #

Extract everything except the last element of the stream.

head :: NonEmpty a -> a #

Extract the first element of the stream.

groupWith1 :: Eq b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a) #

groupWith :: (Foldable f, Eq b) => (a -> b) -> f a -> [NonEmpty a] #

groupWith operates like group, but uses the provided projection when comparing for equality

groupBy1 :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty (NonEmpty a) #

groupBy1 is to group1 as groupBy is to group.

groupBy :: Foldable f => (a -> a -> Bool) -> f a -> [NonEmpty a] #

groupBy operates like group, but uses the provided equality predicate instead of ==.

groupAllWith :: Ord b => (a -> b) -> [a] -> [NonEmpty a] #

groupAllWith operates like groupWith, but sorts the list first so that each equivalence class has, at most, one list in the output

group1 :: Eq a => NonEmpty a -> NonEmpty (NonEmpty a) #

group1 operates like group, but uses the knowledge that its input is non-empty to produce guaranteed non-empty output.

group :: (Foldable f, Eq a) => f a -> [NonEmpty a] #

The group function takes a stream and returns a list of streams such that flattening the resulting list is equal to the argument. Moreover, each stream in the resulting list contains only equal elements. For example, in list notation:

'group' $ 'cycle' "Mississippi"
  = "M" : "i" : "ss" : "i" : "ss" : "i" : "pp" : "i" : "M" : "i" : ...

filter :: (a -> Bool) -> NonEmpty a -> [a] #

filter p xs removes any elements from xs that do not satisfy p.

dropWhile :: (a -> Bool) -> NonEmpty a -> [a] #

dropWhile p xs returns the suffix remaining after takeWhile p xs.

drop :: Int -> NonEmpty a -> [a] #

drop n xs drops the first n elements off the front of the sequence xs.

cycle :: NonEmpty a -> NonEmpty a #

cycle xs returns the infinite repetition of xs:

cycle (1 :| [2,3]) = 1 :| [2,3,1,2,3,...]

cons :: a -> NonEmpty a -> NonEmpty a #

Synonym for <|.

break :: (a -> Bool) -> NonEmpty a -> ([a], [a]) #

The break p function is equivalent to span (not . p).

appendList :: NonEmpty a -> [a] -> NonEmpty a #

Attach a list at the end of a NonEmpty.

>>> appendList (1 :| [2,3]) []
1 :| [2,3]
>>> appendList (1 :| [2,3]) [4,5]
1 :| [2,3,4,5]

Since: base-4.16

append :: NonEmpty a -> NonEmpty a -> NonEmpty a #

A monomorphic version of <> for NonEmpty.

>>> append (1 :| []) (2 :| [3])
1 :| [2,3]

Since: base-4.16

(<|) :: a -> NonEmpty a -> NonEmpty a infixr 5 #

Prepend an element to the stream.

(!!) :: NonEmpty a -> Int -> a infixl 9 #

xs !! n returns the element of the stream xs at index n. Note that the head of the stream has index 0.

Beware: a negative or out-of-bounds index will cause an error.

class IsList l where #

The IsList class and its methods are intended to be used in conjunction with the OverloadedLists extension.

Since: base-4.7.0.0

Minimal complete definition

fromList, toList

Associated Types

type Item l #

The Item type function returns the type of items of the structure l.

Methods

fromList :: [Item l] -> l #

The fromList function constructs the structure l from the given list of Item l

fromListN :: Int -> [Item l] -> l #

The fromListN function takes the input list's length and potentially uses it to construct the structure l more efficiently compared to fromList. If the given number does not equal to the input list's length the behaviour of fromListN is not specified.

fromListN (length xs) xs == fromList xs

toList :: l -> [Item l] #

The toList function extracts a list of Item l from the structure l. It should satisfy fromList . toList = id.

Instances

Instances details
IsList Version

Since: base-4.8.0.0

Instance details

Defined in GHC.Exts

Associated Types

type Item Version #

IsList CallStack

Be aware that 'fromList . toList = id' only for unfrozen CallStacks, since toList removes frozenness information.

Since: base-4.9.0.0

Instance details

Defined in GHC.Exts

Associated Types

type Item CallStack #

IsList ByteString

Since: bytestring-0.10.12.0

Instance details

Defined in Data.ByteString.Internal

Associated Types

type Item ByteString #

IsList ByteString

Since: bytestring-0.10.12.0

Instance details

Defined in Data.ByteString.Lazy.Internal

Associated Types

type Item ByteString #

IsList ShortByteString

Since: bytestring-0.10.12.0

Instance details

Defined in Data.ByteString.Short.Internal

Associated Types

type Item ShortByteString #

IsList IntSet

Since: containers-0.5.6.2

Instance details

Defined in Data.IntSet.Internal

Associated Types

type Item IntSet #

IsList ByteArray 
Instance details

Defined in Data.Primitive.ByteArray

Associated Types

type Item ByteArray #

Methods

fromList :: [Item ByteArray] -> ByteArray #

fromListN :: Int -> [Item ByteArray] -> ByteArray #

toList :: ByteArray -> [Item ByteArray] #

IsList ShortText 
Instance details

Defined in Data.Text.Short.Internal

Associated Types

type Item ShortText #

Methods

fromList :: [Item ShortText] -> ShortText #

fromListN :: Int -> [Item ShortText] -> ShortText #

toList :: ShortText -> [Item ShortText] #

IsList (List2 a) Source #

fromList is unsafe.

Instance details

Defined in Agda.Utils.List2

Associated Types

type Item (List2 a) #

Methods

fromList :: [Item (List2 a)] -> List2 a #

fromListN :: Int -> [Item (List2 a)] -> List2 a #

toList :: List2 a -> [Item (List2 a)] #

IsList (KeyMap v) 
Instance details

Defined in Data.Aeson.KeyMap

Associated Types

type Item (KeyMap v) #

Methods

fromList :: [Item (KeyMap v)] -> KeyMap v #

fromListN :: Int -> [Item (KeyMap v)] -> KeyMap v #

toList :: KeyMap v -> [Item (KeyMap v)] #

IsList (ZipList a)

Since: base-4.15.0.0

Instance details

Defined in GHC.Exts

Associated Types

type Item (ZipList a) #

Methods

fromList :: [Item (ZipList a)] -> ZipList a #

fromListN :: Int -> [Item (ZipList a)] -> ZipList a #

toList :: ZipList a -> [Item (ZipList a)] #

IsList (IntMap a)

Since: containers-0.5.6.2

Instance details

Defined in Data.IntMap.Internal

Associated Types

type Item (IntMap a) #

Methods

fromList :: [Item (IntMap a)] -> IntMap a #

fromListN :: Int -> [Item (IntMap a)] -> IntMap a #

toList :: IntMap a -> [Item (IntMap a)] #

IsList (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Item (Seq a) #

Methods

fromList :: [Item (Seq a)] -> Seq a #

fromListN :: Int -> [Item (Seq a)] -> Seq a #

toList :: Seq a -> [Item (Seq a)] #

Ord a => IsList (Set a)

Since: containers-0.5.6.2

Instance details

Defined in Data.Set.Internal

Associated Types

type Item (Set a) #

Methods

fromList :: [Item (Set a)] -> Set a #

fromListN :: Int -> [Item (Set a)] -> Set a #

toList :: Set a -> [Item (Set a)] #

IsList (DNonEmpty a) 
Instance details

Defined in Data.DList.DNonEmpty.Internal

Associated Types

type Item (DNonEmpty a) #

Methods

fromList :: [Item (DNonEmpty a)] -> DNonEmpty a #

fromListN :: Int -> [Item (DNonEmpty a)] -> DNonEmpty a #

toList :: DNonEmpty a -> [Item (DNonEmpty a)] #

IsList (DList a) 
Instance details

Defined in Data.DList.Internal

Associated Types

type Item (DList a) #

Methods

fromList :: [Item (DList a)] -> DList a #

fromListN :: Int -> [Item (DList a)] -> DList a #

toList :: DList a -> [Item (DList a)] #

IsList (Array a) 
Instance details

Defined in Data.Primitive.Array

Associated Types

type Item (Array a) #

Methods

fromList :: [Item (Array a)] -> Array a #

fromListN :: Int -> [Item (Array a)] -> Array a #

toList :: Array a -> [Item (Array a)] #

Prim a => IsList (PrimArray a) 
Instance details

Defined in Data.Primitive.PrimArray

Associated Types

type Item (PrimArray a) #

Methods

fromList :: [Item (PrimArray a)] -> PrimArray a #

fromListN :: Int -> [Item (PrimArray a)] -> PrimArray a #

toList :: PrimArray a -> [Item (PrimArray a)] #

IsList (SmallArray a) 
Instance details

Defined in Data.Primitive.SmallArray

Associated Types

type Item (SmallArray a) #

Methods

fromList :: [Item (SmallArray a)] -> SmallArray a #

fromListN :: Int -> [Item (SmallArray a)] -> SmallArray a #

toList :: SmallArray a -> [Item (SmallArray a)] #

(Eq a, Hashable a) => IsList (HashSet a) 
Instance details

Defined in Data.HashSet.Internal

Associated Types

type Item (HashSet a) #

Methods

fromList :: [Item (HashSet a)] -> HashSet a #

fromListN :: Int -> [Item (HashSet a)] -> HashSet a #

toList :: HashSet a -> [Item (HashSet a)] #

IsList (Vector a) 
Instance details

Defined in Data.Vector

Associated Types

type Item (Vector a) #

Methods

fromList :: [Item (Vector a)] -> Vector a #

fromListN :: Int -> [Item (Vector a)] -> Vector a #

toList :: Vector a -> [Item (Vector a)] #

Prim a => IsList (Vector a) 
Instance details

Defined in Data.Vector.Primitive

Associated Types

type Item (Vector a) #

Methods

fromList :: [Item (Vector a)] -> Vector a #

fromListN :: Int -> [Item (Vector a)] -> Vector a #

toList :: Vector a -> [Item (Vector a)] #

Storable a => IsList (Vector a) 
Instance details

Defined in Data.Vector.Storable

Associated Types

type Item (Vector a) #

Methods

fromList :: [Item (Vector a)] -> Vector a #

fromListN :: Int -> [Item (Vector a)] -> Vector a #

toList :: Vector a -> [Item (Vector a)] #

IsList (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Exts

Associated Types

type Item (NonEmpty a) #

Methods

fromList :: [Item (NonEmpty a)] -> NonEmpty a #

fromListN :: Int -> [Item (NonEmpty a)] -> NonEmpty a #

toList :: NonEmpty a -> [Item (NonEmpty a)] #

IsList [a]

Since: base-4.7.0.0

Instance details

Defined in GHC.Exts

Associated Types

type Item [a] #

Methods

fromList :: [Item [a]] -> [a] #

fromListN :: Int -> [Item [a]] -> [a] #

toList :: [a] -> [Item [a]] #

Ord k => IsList (Map k v)

Since: containers-0.5.6.2

Instance details

Defined in Data.Map.Internal

Associated Types

type Item (Map k v) #

Methods

fromList :: [Item (Map k v)] -> Map k v #

fromListN :: Int -> [Item (Map k v)] -> Map k v #

toList :: Map k v -> [Item (Map k v)] #

(Eq k, Hashable k) => IsList (HashMap k v) 
Instance details

Defined in Data.HashMap.Internal

Associated Types

type Item (HashMap k v) #

Methods

fromList :: [Item (HashMap k v)] -> HashMap k v #

fromListN :: Int -> [Item (HashMap k v)] -> HashMap k v #

toList :: HashMap k v -> [Item (HashMap k v)] #

type family Item l #

The Item type function returns the type of items of the structure l.

Instances

Instances details
type Item Version 
Instance details

Defined in GHC.Exts

type Item CallStack 
Instance details

Defined in GHC.Exts

type Item ByteString 
Instance details

Defined in Data.ByteString.Internal

type Item ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

type Item ShortByteString 
Instance details

Defined in Data.ByteString.Short.Internal

type Item IntSet 
Instance details

Defined in Data.IntSet.Internal

type Item IntSet = Key
type Item ByteArray 
Instance details

Defined in Data.Primitive.ByteArray

type Item ByteArray = Word8
type Item Text 
Instance details

Defined in Data.Text

type Item Text = Char
type Item Text 
Instance details

Defined in Data.Text.Lazy

type Item Text = Char
type Item ShortText 
Instance details

Defined in Data.Text.Short.Internal

type Item ShortText = Char
type Item (List2 a) Source # 
Instance details

Defined in Agda.Utils.List2

type Item (List2 a) = a
type Item (KeyMap v) 
Instance details

Defined in Data.Aeson.KeyMap

type Item (KeyMap v) = (Key, v)
type Item (ZipList a) 
Instance details

Defined in GHC.Exts

type Item (ZipList a) = a
type Item (IntMap a) 
Instance details

Defined in Data.IntMap.Internal

type Item (IntMap a) = (Key, a)
type Item (Seq a) 
Instance details

Defined in Data.Sequence.Internal

type Item (Seq a) = a
type Item (Set a) 
Instance details

Defined in Data.Set.Internal

type Item (Set a) = a
type Item (DNonEmpty a) 
Instance details

Defined in Data.DList.DNonEmpty.Internal

type Item (DNonEmpty a) = a
type Item (DList a) 
Instance details

Defined in Data.DList.Internal

type Item (DList a) = a
type Item (Array a) 
Instance details

Defined in Data.Primitive.Array

type Item (Array a) = a
type Item (PrimArray a) 
Instance details

Defined in Data.Primitive.PrimArray

type Item (PrimArray a) = a
type Item (SmallArray a) 
Instance details

Defined in Data.Primitive.SmallArray

type Item (SmallArray a) = a
type Item (HashSet a) 
Instance details

Defined in Data.HashSet.Internal

type Item (HashSet a) = a
type Item (Vector a) 
Instance details

Defined in Data.Vector

type Item (Vector a) = a
type Item (Vector a) 
Instance details

Defined in Data.Vector.Primitive

type Item (Vector a) = a
type Item (Vector a) 
Instance details

Defined in Data.Vector.Storable

type Item (Vector a) = a
type Item (Vector e) 
Instance details

Defined in Data.Vector.Unboxed

type Item (Vector e) = e
type Item (NonEmpty a) 
Instance details

Defined in GHC.Exts

type Item (NonEmpty a) = a
type Item [a] 
Instance details

Defined in GHC.Exts

type Item [a] = a
type Item (Map k v) 
Instance details

Defined in Data.Map.Internal

type Item (Map k v) = (k, v)
type Item (HashMap k v) 
Instance details

Defined in Data.HashMap.Internal

type Item (HashMap k v) = (k, v)