| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
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
- type List1 = NonEmpty
- type String1 = List1 Char
- foldr :: (a -> b -> b) -> (a -> b) -> List1 a -> b
- concat :: [List1 a] -> [a]
- catMaybes :: List1 (Maybe a) -> [a]
- mapMaybe :: (a -> Maybe b) -> List1 a -> [b]
- lefts :: List1 (Either a b) -> [a]
- rights :: List1 (Either a b) -> [b]
- partitionEithers :: List1 (Either a b) -> ([a], [b])
- union :: Eq a => List1 a -> List1 a -> List1 a
- zipWithM :: Applicative m => (a -> b -> m c) -> List1 a -> List1 b -> m (List1 c)
- zipWithM_ :: Applicative m => (a -> b -> m c) -> List1 a -> List1 b -> m ()
- snoc :: [a] -> a -> List1 a
- ifNull :: [a] -> b -> (List1 a -> b) -> b
- initLast :: List1 a -> ([a], a)
- groupOn :: Ord b => (a -> b) -> [a] -> [List1 a]
- last2 :: List1 a -> Maybe (a, a)
- ifNotNull :: [a] -> (List1 a -> b) -> b -> b
- unlessNull :: Null m => [a] -> (List1 a -> m) -> m
- breakAfter :: (a -> Bool) -> List1 a -> (List1 a, [a])
- groupBy' :: forall a. (a -> a -> Bool) -> [a] -> [List1 a]
- allEqual :: Eq a => List1 a -> Bool
- nubM :: Monad m => (a -> a -> m Bool) -> List1 a -> m (List1 a)
- wordsBy :: (a -> Bool) -> [a] -> [List1 a]
- toList' :: Maybe (List1 a) -> [a]
- fromListSafe :: List1 a -> [a] -> List1 a
- groupOn1 :: Ord b => (a -> b) -> List1 a -> List1 (List1 a)
- concatMap1 :: (a -> List1 b) -> List1 a -> List1 b
- data NonEmpty a = a :| [a]
- xor :: NonEmpty Bool -> Bool
- zipWith :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c
- sortBy :: (a -> a -> Ordering) -> NonEmpty a -> NonEmpty a
- length :: NonEmpty a -> Int
- head :: NonEmpty a -> a
- group :: (Foldable f, Eq a) => f a -> [NonEmpty a]
- groupBy :: Foldable f => (a -> a -> Bool) -> f a -> [NonEmpty a]
- filter :: (a -> Bool) -> NonEmpty a -> [a]
- unfoldr :: (a -> (b, Maybe a)) -> a -> NonEmpty b
- transpose :: NonEmpty (NonEmpty a) -> NonEmpty (NonEmpty a)
- cycle :: NonEmpty a -> NonEmpty a
- zip :: NonEmpty a -> NonEmpty b -> NonEmpty (a, b)
- map :: (a -> b) -> NonEmpty a -> NonEmpty b
- uncons :: NonEmpty a -> (a, Maybe (NonEmpty a))
- tail :: NonEmpty a -> [a]
- last :: NonEmpty a -> a
- init :: NonEmpty a -> [a]
- scanl :: Foldable f => (b -> a -> b) -> b -> f a -> NonEmpty b
- scanl1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty a
- scanr :: Foldable f => (a -> b -> b) -> b -> f a -> NonEmpty b
- scanr1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty a
- iterate :: (a -> a) -> a -> NonEmpty a
- repeat :: a -> NonEmpty a
- takeWhile :: (a -> Bool) -> NonEmpty a -> [a]
- dropWhile :: (a -> Bool) -> NonEmpty a -> [a]
- take :: Int -> NonEmpty a -> [a]
- drop :: Int -> NonEmpty a -> [a]
- splitAt :: Int -> NonEmpty a -> ([a], [a])
- span :: (a -> Bool) -> NonEmpty a -> ([a], [a])
- break :: (a -> Bool) -> NonEmpty a -> ([a], [a])
- reverse :: NonEmpty a -> NonEmpty a
- (!!) :: HasCallStack => NonEmpty a -> Int -> a
- unzip :: Functor f => f (a, b) -> (f a, f b)
- isPrefixOf :: Eq a => [a] -> NonEmpty a -> Bool
- nub :: Eq a => NonEmpty a -> NonEmpty a
- nubBy :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty a
- intersperse :: a -> NonEmpty a -> NonEmpty a
- partition :: (a -> Bool) -> NonEmpty a -> ([a], [a])
- insert :: (Foldable f, Ord a) => a -> f a -> NonEmpty a
- inits :: Foldable f => f a -> NonEmpty [a]
- tails :: Foldable f => f a -> NonEmpty [a]
- sort :: Ord a => NonEmpty a -> NonEmpty a
- singleton :: a -> NonEmpty a
- unfold :: (a -> (b, Maybe a)) -> a -> NonEmpty b
- nonEmpty :: [a] -> Maybe (NonEmpty a)
- (<|) :: a -> NonEmpty a -> NonEmpty a
- cons :: a -> NonEmpty a -> NonEmpty a
- inits1 :: NonEmpty a -> NonEmpty (NonEmpty a)
- tails1 :: NonEmpty a -> NonEmpty (NonEmpty a)
- some1 :: Alternative f => f a -> f (NonEmpty a)
- groupWith :: (Foldable f, Eq b) => (a -> b) -> f a -> [NonEmpty a]
- groupAllWith :: Ord b => (a -> b) -> [a] -> [NonEmpty a]
- group1 :: Eq a => NonEmpty a -> NonEmpty (NonEmpty a)
- groupBy1 :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty (NonEmpty a)
- groupWith1 :: Eq b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
- groupAllWith1 :: Ord b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
- sortWith :: Ord o => (a -> o) -> NonEmpty a -> NonEmpty a
- append :: NonEmpty a -> NonEmpty a -> NonEmpty a
- appendList :: NonEmpty a -> [a] -> NonEmpty a
- prependList :: [a] -> NonEmpty a -> NonEmpty a
- class IsList l where
- type family Item l
Documentation
foldr :: (a -> b -> b) -> (a -> b) -> List1 a -> b Source #
List foldr but with a base case for the singleton list.
partitionEithers :: List1 (Either a b) -> ([a], [b]) Source #
Like partitionEithers.
union :: Eq a => List1 a -> List1 a -> List1 a Source #
Like union.  Duplicates in the first list are not removed.
 O(nm).
zipWithM :: Applicative m => (a -> b -> m c) -> List1 a -> List1 b -> m (List1 c) Source #
Like zipWithM.
unlessNull :: Null m => [a] -> (List1 a -> m) -> m Source #
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])
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).
nubM :: Monad m => (a -> a -> m Bool) -> List1 a -> m (List1 a) Source #
Non-efficient, monadic nub.
 O(n²).
Arguments
| :: List1 a | Default value if convertee is empty. | 
| -> [a] | List to convert, supposedly non-empty. | 
| -> List1 a | Converted list. | 
Safe version of fromList.
Non-empty (and non-strict) list type.
Since: base-4.9.0.0
Constructors
| a :| [a] infixr 5 | 
Instances
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 xsxs that do not satisfy p.
cycle :: NonEmpty a -> NonEmpty a #
cycle xsxs:
cycle (1 :| [2,3]) = 1 :| [2,3,1,2,3,...]
zip :: NonEmpty a -> NonEmpty b -> NonEmpty (a, b) #
The zip function takes two streams and returns a stream of
 corresponding pairs.
uncons :: NonEmpty a -> (a, Maybe (NonEmpty a)) #
uncons produces the first element of the stream, and a stream of the
 remaining elements, if any.
iterate :: (a -> a) -> a -> NonEmpty a #
iterate f xf to x.
iterate f x = x :| [f x, f (f x), ..]
takeWhile :: (a -> Bool) -> NonEmpty a -> [a] #
takeWhile p xsxs for which the predicate p holds.
drop :: Int -> NonEmpty a -> [a] #
drop n xsn elements off the front of
 the sequence xs.
splitAt :: Int -> NonEmpty a -> ([a], [a]) #
splitAt n xsxs
 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 xsspan :: (a -> Bool) -> NonEmpty a -> ([a], [a]) #
span p xsxs 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(!!) :: HasCallStack => 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.
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]
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)insert :: (Foldable f, Ord a) => a -> f a -> NonEmpty a #
insert x xsx 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.
some1 :: Alternative f => f a -> f (NonEmpty a) #
some1 xx one or more times.
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
groupWith1 :: Eq b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a) #
groupWith1 is to group1 as groupWith is to group
groupAllWith1 :: Ord b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a) #
groupAllWith1 is to groupWith1 as groupAllWith is to groupWith
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
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
The IsList class and its methods are intended to be used in
   conjunction with the OverloadedLists extension.
Since: base-4.7.0.0
Methods
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
The toList function extracts a list of Item l from the structure l.
   It should satisfy fromList . toList = id.
Instances
| IsList ByteArray | Since: base-4.17.0.0 | 
| IsList Version | Since: base-4.8.0.0 | 
| IsList CallStack | Be aware that 'fromList . toList = id' only for unfrozen  Since: base-4.9.0.0 | 
| IsList ByteString | Since: bytestring-0.10.12.0 | 
| Defined in Data.ByteString.Internal.Type Associated Types type Item ByteString # Methods fromList :: [Item ByteString] -> ByteString # fromListN :: Int -> [Item ByteString] -> ByteString # toList :: ByteString -> [Item ByteString] # | |
| IsList ByteString | Since: bytestring-0.10.12.0 | 
| Defined in Data.ByteString.Lazy.Internal Associated Types type Item ByteString # Methods fromList :: [Item ByteString] -> ByteString # fromListN :: Int -> [Item ByteString] -> ByteString # toList :: ByteString -> [Item ByteString] # | |
| IsList ShortByteString | Since: bytestring-0.10.12.0 | 
| Defined in Data.ByteString.Short.Internal Associated Types type Item ShortByteString # Methods fromList :: [Item ShortByteString] -> ShortByteString # fromListN :: Int -> [Item ShortByteString] -> ShortByteString # toList :: ShortByteString -> [Item ShortByteString] # | |
| IsList IntSet | Since: containers-0.5.6.2 | 
| IsList ShortText | |
| IsList (List2 a) Source # | 
 | 
| IsList (ZipList a) | Since: base-4.15.0.0 | 
| IsList (NonEmpty a) | Since: base-4.9.0.0 | 
| IsList (IntMap a) | Since: containers-0.5.6.2 | 
| IsList (Seq a) | |
| Ord a => IsList (Set a) | Since: containers-0.5.6.2 | 
| IsList (DNonEmpty a) | |
| IsList (DList a) | |
| (Eq a, Hashable a) => IsList (HashSet a) | |
| IsList (Array a) | |
| Prim a => IsList (PrimArray a) | |
| IsList (SmallArray a) | |
| IsList (KeyMap v) | |
| IsList (Vector a) | |
| Prim a => IsList (Vector a) | |
| Storable a => IsList (Vector a) | |
| IsList [a] | Since: base-4.7.0.0 | 
| Ord k => IsList (Map k v) | Since: containers-0.5.6.2 | 
| (Eq k, Hashable k) => IsList (HashMap k v) | |
The Item type function returns the type of items of the structure
   l.
Instances
| type Item ByteArray | |
| Defined in Data.Array.Byte | |
| type Item Version | |
| Defined in GHC.IsList | |
| type Item CallStack | |
| Defined in GHC.IsList | |
| type Item ByteString | |
| Defined in Data.ByteString.Internal.Type | |
| type Item ByteString | |
| Defined in Data.ByteString.Lazy.Internal | |
| type Item ShortByteString | |
| Defined in Data.ByteString.Short.Internal | |
| type Item IntSet | |
| Defined in Data.IntSet.Internal | |
| type Item Text | |
| type Item Text | |
| Defined in Data.Text.Lazy | |
| type Item ShortText | |
| Defined in Data.Text.Short.Internal | |
| type Item (List2 a) Source # | |
| Defined in Agda.Utils.List2 | |
| type Item (ZipList a) | |
| Defined in GHC.IsList | |
| type Item (NonEmpty a) | |
| Defined in GHC.IsList | |
| type Item (IntMap a) | |
| Defined in Data.IntMap.Internal | |
| type Item (Seq a) | |
| Defined in Data.Sequence.Internal | |
| type Item (Set a) | |
| Defined in Data.Set.Internal | |
| type Item (DNonEmpty a) | |
| Defined in Data.DList.DNonEmpty.Internal type Item (DNonEmpty a) = a | |
| type Item (DList a) | |
| Defined in Data.DList.Internal type Item (DList a) = a | |
| type Item (HashSet a) | |
| Defined in Data.HashSet.Internal type Item (HashSet a) = a | |
| type Item (Array a) | |
| Defined in Data.Primitive.Array type Item (Array a) = a | |
| type Item (PrimArray a) | |
| Defined in Data.Primitive.PrimArray type Item (PrimArray a) = a | |
| type Item (SmallArray a) | |
| Defined in Data.Primitive.SmallArray type Item (SmallArray a) = a | |
| type Item (KeyMap v) | |
| Defined in Data.Aeson.KeyMap | |
| type Item (Vector a) | |
| Defined in Data.Vector type Item (Vector a) = a | |
| type Item (Vector a) | |
| Defined in Data.Vector.Primitive type Item (Vector a) = a | |
| type Item (Vector a) | |
| Defined in Data.Vector.Storable type Item (Vector a) = a | |
| type Item (Vector e) | |
| Defined in Data.Vector.Unboxed type Item (Vector e) = e | |
| type Item [a] | |
| Defined in GHC.IsList type Item [a] = a | |
| type Item (Map k v) | |
| Defined in Data.Map.Internal | |
| type Item (HashMap k v) | |
| Defined in Data.HashMap.Internal type Item (HashMap k v) = (k, v) | |