Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- catMaybes :: List1 (Maybe a) -> [a]
- zipWithM :: Applicative m => (a -> b -> m c) -> List1 a -> List1 b -> m (List1 c)
- partitionEithers :: List1 (Either a b) -> ([a], [b])
- zipWithM_ :: Applicative m => (a -> b -> m c) -> List1 a -> List1 b -> m ()
- type String1 = List1 Char
- ifNull :: [a] -> b -> (List1 a -> b) -> b
- union :: Eq a => List1 a -> List1 a -> List1 a
- mapMaybe :: (a -> Maybe b) -> List1 a -> [b]
- initLast :: List1 a -> ([a], a)
- find :: (a -> Bool) -> List1 a -> Maybe a
- lefts :: List1 (Either a b) -> [a]
- snoc :: [a] -> a -> List1 a
- updateHead :: (a -> a) -> List1 a -> List1 a
- updateLast :: (a -> a) -> List1 a -> List1 a
- concat :: [List1 a] -> [a]
- unwords :: List1 String -> String
- foldr :: (a -> b -> b) -> (a -> b) -> List1 a -> b
- rights :: List1 (Either a b) -> [b]
- last2 :: List1 a -> Maybe (a, a)
- ifNotNull :: [a] -> (List1 a -> b) -> b -> b
- unlessNull :: Null m => [a] -> (List1 a -> m) -> m
- liftList1 :: (List1 a -> List1 b) -> [a] -> [b]
- breakAfter :: (a -> Bool) -> List1 a -> (List1 a, [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
- groupOn :: Ord b => (a -> b) -> [a] -> [List1 a]
- groupOn1 :: Ord b => (a -> b) -> List1 a -> List1 (List1 a)
- groupBy' :: (a -> a -> Bool) -> [a] -> [List1 a]
- groupByFst :: Eq a => [(a, b)] -> [(a, List1 b)]
- groupByFst1 :: Eq a => List1 (a, b) -> List1 (a, List1 b)
- concatMap1 :: (a -> List1 b) -> List1 a -> List1 b
- lensHead :: Functor f => (a -> f a) -> List1 a -> f (List1 a)
- lensLast :: Functor f => (a -> f a) -> List1 a -> f (List1 a)
- xor :: NonEmpty Bool -> Bool
- data NonEmpty a = a :| [a]
- group :: (Foldable f, Eq a) => f a -> [NonEmpty a]
- (!!) :: HasCallStack => NonEmpty a -> Int -> a
- sortBy :: (a -> a -> Ordering) -> NonEmpty a -> NonEmpty a
- isPrefixOf :: Eq a => [a] -> NonEmpty a -> Bool
- partition :: (a -> Bool) -> NonEmpty a -> ([a], [a])
- singleton :: a -> NonEmpty a
- (<|) :: a -> NonEmpty a -> NonEmpty a
- map :: (a -> b) -> NonEmpty a -> NonEmpty b
- insert :: (Foldable f, Ord a) => a -> f a -> NonEmpty a
- sort :: Ord a => NonEmpty a -> NonEmpty a
- sortOn :: Ord b => (a -> b) -> NonEmpty a -> NonEmpty a
- transpose :: NonEmpty (NonEmpty a) -> NonEmpty (NonEmpty a)
- head :: NonEmpty a -> a
- length :: NonEmpty a -> Int
- nonEmpty :: [a] -> Maybe (NonEmpty a)
- tails :: Foldable f => f a -> NonEmpty [a]
- unfoldr :: (a -> (b, Maybe a)) -> a -> NonEmpty b
- filter :: (a -> Bool) -> NonEmpty a -> [a]
- drop :: Int -> NonEmpty a -> [a]
- splitAt :: Int -> NonEmpty a -> ([a], [a])
- break :: (a -> Bool) -> NonEmpty a -> ([a], [a])
- cycle :: NonEmpty a -> NonEmpty a
- dropWhile :: (a -> Bool) -> NonEmpty a -> [a]
- init :: NonEmpty a -> [a]
- iterate :: (a -> a) -> a -> NonEmpty a
- last :: NonEmpty a -> a
- repeat :: a -> NonEmpty a
- reverse :: NonEmpty a -> NonEmpty 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
- span :: (a -> Bool) -> NonEmpty a -> ([a], [a])
- tail :: NonEmpty a -> [a]
- take :: Int -> NonEmpty a -> [a]
- takeWhile :: (a -> Bool) -> NonEmpty a -> [a]
- zipWith :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c
- zip :: NonEmpty a -> NonEmpty b -> NonEmpty (a, b)
- cons :: a -> NonEmpty a -> NonEmpty a
- uncons :: NonEmpty a -> (a, Maybe (NonEmpty a))
- intersperse :: a -> NonEmpty a -> NonEmpty a
- groupBy :: Foldable f => (a -> a -> Bool) -> f a -> [NonEmpty a]
- inits :: Foldable f => f a -> NonEmpty [a]
- nub :: Eq a => NonEmpty a -> NonEmpty a
- nubBy :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty a
- permutations :: [a] -> NonEmpty [a]
- append :: NonEmpty a -> NonEmpty a -> NonEmpty a
- tails1 :: NonEmpty a -> NonEmpty (NonEmpty a)
- unfold :: (a -> (b, Maybe a)) -> a -> NonEmpty b
- inits1 :: NonEmpty a -> NonEmpty (NonEmpty a)
- groupWith :: (Foldable f, Eq b) => (a -> b) -> f a -> [NonEmpty a]
- sortWith :: Ord o => (a -> o) -> NonEmpty a -> NonEmpty a
- appendList :: NonEmpty a -> [a] -> NonEmpty a
- group1 :: Eq a => NonEmpty a -> NonEmpty (NonEmpty a)
- groupAllWith :: Ord b => (a -> b) -> [a] -> [NonEmpty a]
- groupAllWith1 :: Ord b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
- groupBy1 :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty (NonEmpty a)
- groupWith1 :: Eq b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
- permutations1 :: NonEmpty a -> NonEmpty (NonEmpty a)
- prependList :: [a] -> NonEmpty a -> NonEmpty a
- some1 :: Alternative f => f a -> f (NonEmpty a)
- class IsList l where
- type family Item l
- unzip :: Functor f => f (a, b) -> (f a, f b)
Documentation
zipWithM :: Applicative m => (a -> b -> m c) -> List1 a -> List1 b -> m (List1 c) Source #
Like zipWithM
.
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).
updateHead :: (a -> a) -> List1 a -> List1 a Source #
Update the first element of a non-empty list. O(1).
updateLast :: (a -> a) -> List1 a -> List1 a Source #
Update the last element of a non-empty list. O(n).
foldr :: (a -> b -> b) -> (a -> b) -> List1 a -> b Source #
List foldr
but with a base case for the singleton list.
unlessNull :: Null m => [a] -> (List1 a -> m) -> m Source #
liftList1 :: (List1 a -> List1 b) -> [a] -> [b] Source #
Lift a function on non-empty lists to a function on lists.
This is in essence fmap
for Maybe
, if we take [a] = Maybe (List1 a)
.
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²).
:: List1 a | Default value if convertee is empty. |
-> [a] | List to convert, supposedly non-empty. |
-> List1 a | Converted list. |
Safe version of fromList
.
groupByFst :: Eq a => [(a, b)] -> [(a, List1 b)] Source #
Group consecutive items that share the same first component.
groupByFst1 :: Eq a => List1 (a, b) -> List1 (a, List1 b) Source #
Group consecutive items that share the same first component.
lensHead :: Functor f => (a -> f a) -> List1 a -> f (List1 a) Source #
Focus on the first element of a non-empty list. O(1).
lensLast :: Functor f => (a -> f a) -> List1 a -> f (List1 a) Source #
Focus on the last element of a non-empty list. O(n).
a :| [a] |
Instances
NumHoles NameParts Source # | |||||
Defined in Agda.Syntax.Concrete.Name | |||||
MonadZip NonEmpty | |||||
Foldable1 NonEmpty | |||||
Defined in Data.Foldable1 fold1 :: Semigroup m => NonEmpty m -> m foldMap1 :: Semigroup m => (a -> m) -> NonEmpty a -> m foldMap1' :: Semigroup m => (a -> m) -> NonEmpty a -> m toNonEmpty :: NonEmpty a -> NonEmpty a maximum :: Ord a => NonEmpty a -> a minimum :: Ord a => NonEmpty a -> a foldrMap1 :: (a -> b) -> (a -> b -> b) -> NonEmpty a -> b foldlMap1' :: (a -> b) -> (b -> a -> b) -> NonEmpty a -> b foldlMap1 :: (a -> b) -> (b -> a -> b) -> NonEmpty a -> b foldrMap1' :: (a -> b) -> (a -> b -> b) -> NonEmpty a -> b | |||||
Eq1 NonEmpty | |||||
Defined in Data.Functor.Classes | |||||
Ord1 NonEmpty | |||||
Defined in Data.Functor.Classes liftCompare :: (a -> b -> Ordering) -> NonEmpty a -> NonEmpty b -> Ordering | |||||
Read1 NonEmpty | |||||
Defined in Data.Functor.Classes 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 | |||||
Defined in Data.Functor.Classes liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NonEmpty a -> ShowS liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [NonEmpty a] -> ShowS | |||||
NFData1 NonEmpty | |||||
Defined in Control.DeepSeq | |||||
Applicative NonEmpty | |||||
Functor NonEmpty | |||||
Monad NonEmpty | |||||
MonadFix NonEmpty | |||||
Defined in GHC.Internal.Control.Monad.Fix | |||||
Foldable NonEmpty | |||||
Defined in GHC.Internal.Data.Foldable 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 elem :: Eq a => a -> NonEmpty a -> Bool maximum :: Ord a => NonEmpty a -> a minimum :: Ord a => NonEmpty a -> a | |||||
IsString String1 | |||||
Defined in Agda.Utils.String fromString :: String -> String1 | |||||
Traversable NonEmpty | |||||
Hashable1 NonEmpty | |||||
Defined in Data.Hashable.Class liftHashWithSalt :: (Int -> a -> Int) -> Int -> NonEmpty a -> Int | |||||
FromJSON1 NonEmpty | |||||
Defined in Data.Aeson.Types.FromJSON | |||||
ToJSON1 NonEmpty | |||||
Defined in Data.Aeson.Types.ToJSON liftToJSON :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> NonEmpty a -> Value # liftToJSONList :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> [NonEmpty a] -> Value # liftToEncoding :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> NonEmpty a -> Encoding # liftToEncodingList :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> [NonEmpty a] -> Encoding # liftOmitField :: (a -> Bool) -> NonEmpty a -> Bool # | |||||
Generic1 NonEmpty | |||||
Defined in GHC.Internal.Generics
| |||||
Singleton a (NonEmpty a) Source # | |||||
Defined in Agda.Utils.Singleton | |||||
Lift a => Lift (NonEmpty a :: Type) | |||||
Pretty a => Pretties (List1 a) Source # | |||||
Defined in Agda.Compiler.JS.Pretty | |||||
SubstExpr a => SubstExpr (List1 a) Source # | |||||
DeclaredNames a => DeclaredNames (List1 a) Source # | |||||
Defined in Agda.Syntax.Abstract.Views declaredNames :: Collection KName m => List1 a -> m Source # | |||||
ExprLike a => ExprLike (List1 a) Source # | |||||
Defined in Agda.Syntax.Abstract.Views recurseExpr :: RecurseExprFn m (List1 a) Source # foldExpr :: FoldExprFn m (List1 a) Source # traverseExpr :: TraverseExprFn m (List1 a) Source # | |||||
Pretty a => Pretty (List1 a) Source # | |||||
ExprLike a => ExprLike (List1 a) Source # | |||||
FoldDecl a => FoldDecl (List1 a) Source # | |||||
Defined in Agda.Syntax.Concrete.Generic foldDecl :: Monoid m => (Declaration -> m) -> List1 a -> m Source # | |||||
TraverseDecl a => TraverseDecl (List1 a) Source # | |||||
Defined in Agda.Syntax.Concrete.Generic preTraverseDecl :: Monad m => (Declaration -> m Declaration) -> List1 a -> m (List1 a) Source # | |||||
CPatternLike p => CPatternLike (List1 p) Source # | |||||
Defined in Agda.Syntax.Concrete.Pattern 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 # | |||||
Defined in Agda.Syntax.Internal.Names | |||||
HasRange a => HasRange (List1 a) Source # | Precondition: The ranges of the list elements must point to the same file (or be empty). | ||||
KillRange a => KillRange (List1 a) Source # | |||||
Defined in Agda.Syntax.Position killRange :: KillRangeT (List1 a) Source # | |||||
SetBindingSite a => SetBindingSite (List1 a) Source # | |||||
Defined in Agda.Syntax.Scope.Base | |||||
ToConcrete a => ToConcrete (List1 a) Source # | |||||
Defined in Agda.Syntax.Translation.AbstractToConcrete
| |||||
ToAbstract c => ToAbstract (List1 c) Source # | |||||
Defined in Agda.Syntax.Translation.ConcreteToAbstract
| |||||
ToAbstract (List1 (QNamed Clause)) Source # | |||||
Defined in Agda.Syntax.Translation.ReflectedToAbstract | |||||
EmbPrj a => EmbPrj (List1 a) Source # | |||||
Sized (List1 a) Source # | |||||
Binary a => Binary (NonEmpty a) | |||||
ToMarkup (NonEmpty Char) | |||||
Defined in Text.Blaze toMarkup :: NonEmpty Char -> Markup preEscapedToMarkup :: NonEmpty Char -> Markup | |||||
ToValue (NonEmpty Char) | |||||
Defined in Text.Blaze toValue :: NonEmpty Char -> AttributeValue preEscapedToValue :: NonEmpty Char -> AttributeValue | |||||
NFData a => NFData (NonEmpty a) | |||||
Defined in Control.DeepSeq | |||||
Semigroup (NonEmpty a) | |||||
Generic (NonEmpty a) | |||||
Defined in GHC.Internal.Generics
| |||||
IsList (NonEmpty a) | |||||
Read a => Read (NonEmpty a) | |||||
Defined in GHC.Internal.Read | |||||
Show a => Show (NonEmpty a) | |||||
Eq a => Eq (NonEmpty a) | |||||
Ord a => Ord (NonEmpty a) | |||||
Defined in GHC.Internal.Base | |||||
Hashable a => Hashable (NonEmpty a) | |||||
Defined in Data.Hashable.Class hashWithSalt :: Int -> NonEmpty a -> Int | |||||
FromJSON a => FromJSON (NonEmpty a) | |||||
Defined in Data.Aeson.Types.FromJSON | |||||
ToJSON a => ToJSON (NonEmpty a) | |||||
Defined in Data.Aeson.Types.ToJSON | |||||
AddContext (List1 Name, Dom Type) Source # | |||||
Defined in Agda.TypeChecking.Monad.Context | |||||
AddContext (List1 (Arg Name), Type) Source # | |||||
Defined in Agda.TypeChecking.Monad.Context | |||||
AddContext (List1 (NamedArg Name), Type) Source # | |||||
Defined in Agda.TypeChecking.Monad.Context | |||||
AddContext (List1 (WithHiding Name), Dom Type) Source # | |||||
Defined in Agda.TypeChecking.Monad.Context addContext :: MonadAddContext m => (List1 (WithHiding Name), Dom Type) -> m a -> m a Source # contextSize :: (List1 (WithHiding Name), Dom Type) -> Nat Source # | |||||
type Rep1 NonEmpty | |||||
Defined in GHC.Internal.Generics type Rep1 NonEmpty = D1 ('MetaData "NonEmpty" "GHC.Internal.Base" "ghc-internal" 'False) (C1 ('MetaCons ":|" ('InfixI 'RightAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 []))) | |||||
type ConOfAbs (List1 a) Source # | |||||
Defined in Agda.Syntax.Translation.AbstractToConcrete | |||||
type AbsOfCon (List1 c) Source # | |||||
Defined in Agda.Syntax.Translation.ConcreteToAbstract | |||||
type AbsOfRef (List1 (QNamed Clause)) Source # | |||||
type Rep (NonEmpty a) | |||||
Defined in GHC.Internal.Generics type Rep (NonEmpty a) = D1 ('MetaData "NonEmpty" "GHC.Internal.Base" "ghc-internal" 'False) (C1 ('MetaCons ":|" ('InfixI 'RightAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a]))) | |||||
type Item (NonEmpty a) | |||||
Defined in GHC.Internal.IsList |
(!!) :: HasCallStack => NonEmpty a -> Int -> a #
isPrefixOf :: Eq a => [a] -> NonEmpty a -> Bool #
intersperse :: a -> NonEmpty a -> NonEmpty a #
permutations :: [a] -> NonEmpty [a] #
appendList :: NonEmpty a -> [a] -> NonEmpty a #
groupAllWith :: Ord b => (a -> b) -> [a] -> [NonEmpty a] #
groupAllWith1 :: Ord b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a) #
groupWith1 :: Eq b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a) #
permutations1 :: NonEmpty a -> NonEmpty (NonEmpty a) #
prependList :: [a] -> NonEmpty a -> NonEmpty a #
Instances
IsList ByteArray | |||||
IsList ByteString | |||||
IsList ByteString | |||||
IsList ShortByteString | |||||
Defined in Data.ByteString.Short.Internal
| |||||
IsList IntSet | |||||
IsList Version | |||||
IsList CallStack | |||||
IsList ShortText | |||||
IsList (List2 a) Source # |
| ||||
IsList (IntMap a) | |||||
IsList (Seq a) | |||||
Ord a => IsList (Set a) | |||||
IsList (DNonEmpty a) | |||||
IsList (DList a) | |||||
IsList (NonEmpty a) | |||||
IsList (ZipList 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] | |||||
Ord k => IsList (Map k v) | |||||
(Eq k, Hashable k) => IsList (HashMap k v) | |||||
Instances
type Item ByteArray | |
Defined in Data.Array.Byte type Item ByteArray = Word8 | |
type Item ByteString | |
Defined in Data.ByteString.Internal.Type type Item ByteString = Word8 | |
type Item ByteString | |
Defined in Data.ByteString.Lazy.Internal type Item ByteString = Word8 | |
type Item ShortByteString | |
Defined in Data.ByteString.Short.Internal type Item ShortByteString = Word8 | |
type Item IntSet | |
Defined in Data.IntSet.Internal type Item IntSet = Key | |
type Item Version | |
Defined in GHC.Internal.IsList type Item Version = Int | |
type Item CallStack | |
Defined in GHC.Internal.IsList | |
type Item Text | |
type Item Text | |
Defined in Data.Text.Lazy type Item Text = Char | |
type Item ShortText | |
Defined in Data.Text.Short.Internal type Item ShortText = Char | |
type Item (List2 a) Source # | |
Defined in Agda.Utils.List2 | |
type Item (IntMap a) | |
Defined in Data.IntMap.Internal type Item (IntMap a) = (Key, a) | |
type Item (Seq a) | |
Defined in Data.Sequence.Internal type Item (Seq a) = a | |
type Item (Set a) | |
Defined in Data.Set.Internal type Item (Set a) = a | |
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 (NonEmpty a) | |
Defined in GHC.Internal.IsList | |
type Item (ZipList a) | |
Defined in GHC.Internal.IsList type Item (ZipList 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.Internal.IsList type Item [a] = a | |
type Item (Map k v) | |
Defined in Data.Map.Internal type Item (Map k v) = (k, v) | |
type Item (HashMap k v) | |
Defined in Data.HashMap.Internal type Item (HashMap k v) = (k, v) |