Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
AsyncRattus.Strict
Description
This module contains strict versions of some standard data structures.
Synopsis
- data List a
- singleton :: a -> List a
- class IsList l where
- init' :: List a -> List a
- reverse' :: List a -> List a
- union' :: Eq a => List a -> List a -> List a
- unionBy' :: (a -> a -> Bool) -> List a -> List a -> List a
- nub' :: Eq a => List a -> List a
- nubBy' :: (a -> a -> Bool) -> List a -> List a
- filter' :: (a -> Bool) -> List a -> List a
- delete' :: Eq a => a -> List a -> List a
- deleteBy' :: (a -> a -> Bool) -> a -> List a -> List a
- (+++) :: List a -> List a -> List a
- listToMaybe' :: List a -> Maybe' a
- map' :: (a -> b) -> List a -> List b
- zip' :: List a -> List b -> List (a :* b)
- zipWith' :: (a -> b -> c) -> List a -> List b -> List c
- mapMaybe' :: (a -> Maybe' b) -> List a -> List b
- concatMap' :: (a -> List b) -> List a -> List b
- data a :* b = !a :* !b
- data Maybe' a
- maybe' :: b -> (a -> b) -> Maybe' a -> b
- fromMaybe' :: a -> Maybe' a -> a
- isJust' :: Maybe' a -> Bool
- fst' :: (a :* b) -> a
- snd' :: (a :* b) -> b
- curry' :: ((a :* b) -> c) -> a -> b -> c
- uncurry' :: (a -> b -> c) -> (a :* b) -> c
Documentation
Strict list type.
Instances
Foldable List Source # | |
Defined in AsyncRattus.Strict Methods fold :: Monoid m => List m -> m # foldMap :: Monoid m => (a -> m) -> List a -> m # foldMap' :: Monoid m => (a -> m) -> List a -> m # foldr :: (a -> b -> b) -> b -> List a -> b # foldr' :: (a -> b -> b) -> b -> List a -> b # foldl :: (b -> a -> b) -> b -> List a -> b # foldl' :: (b -> a -> b) -> b -> List a -> b # foldr1 :: (a -> a -> a) -> List a -> a # foldl1 :: (a -> a -> a) -> List a -> a # elem :: Eq a => a -> List a -> Bool # maximum :: Ord a => List a -> a # | |
Traversable List Source # | |
Functor List Source # | |
IsList (List a) Source # | |
Show a => Show (List a) Source # | |
Eq a => Eq (List a) Source # | |
type Item (List a) Source # | |
Defined in AsyncRattus.Strict |
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 (List 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 (Bag a) | |
IsList (Array a) | |
Prim a => IsList (PrimArray a) | Since: primitive-0.6.4.0 |
IsList (SmallArray a) | |
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)] # | |
IsList (Vector a) | |
Prim a => IsList (Vector a) | |
IsList (Vector a) | |
IsList [a] | Since: base-4.7.0.0 |
Ord k => IsList (Map k v) | Since: containers-0.5.6.2 |
init' :: List a -> List a Source #
Remove the last element from a list if there is one, otherwise
return Nil
.
listToMaybe' :: List a -> Maybe' a Source #
Strict pair type.
Constructors
!a :* !b infixr 2 |
Instances
Functor ((:*) a) Source # | |
(Show a, Show b) => Show (a :* b) Source # | |
(Eq a, Eq b) => Eq (a :* b) Source # | |
(VectorSpace v a, VectorSpace w a, Floating a, Eq a) => VectorSpace (v :* w) a Source # | |
Strict variant of Maybe
.
fromMaybe' :: a -> Maybe' a -> a Source #