| Safe Haskell | Unsafe |
|---|---|
| Language | Haskell2010 |
Universum.Unsafe
Description
Unsafe functions to work with lists and Maybe.
Sometimes unavoidable but better don't use them. This module
is intended to be imported qualified and it's not even included
in default prelude exports.
import qualified Universum.Unsafe as Unsafe foo :: [a] -> a foo = Unsafe.head
Synopsis
- head :: [a] -> a
- tail :: [a] -> [a]
- init :: [a] -> [a]
- last :: [a] -> a
- at :: Int -> [a] -> a
- (!!) :: [a] -> Int -> a
- fromJust :: HasCallStack => Maybe a -> a
- foldr1 :: Foldable t => (a -> a -> a) -> t a -> a
- foldl1 :: Foldable t => (a -> a -> a) -> t a -> a
- minimum :: (Foldable t, Ord a) => t a -> a
- maximum :: (Foldable t, Ord a) => t a -> a
- minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
- maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
Documentation
\(\mathcal{O}(1)\). Extract the first element of a list, which must be non-empty.
>>>head [1, 2, 3]1>>>head [1..]1>>>head []*** Exception: Prelude.head: empty list
\(\mathcal{O}(1)\). Extract the elements after the head of a list, which must be non-empty.
>>>tail [1, 2, 3][2,3]>>>tail [1][]>>>tail []*** Exception: Prelude.tail: empty list
\(\mathcal{O}(n)\). Return all the elements of a list except the last one. The list must be non-empty.
>>>init [1, 2, 3][1,2]>>>init [1][]>>>init []*** Exception: Prelude.init: empty list
\(\mathcal{O}(n)\). Extract the last element of a list, which must be finite and non-empty.
>>>last [1, 2, 3]3>>>last [1..]* Hangs forever *>>>last []*** Exception: Prelude.last: empty list
(!!) :: [a] -> Int -> a infixl 9 #
List index (subscript) operator, starting from 0.
It is an instance of the more general genericIndex,
which takes an index of any integral type.
>>>['a', 'b', 'c'] !! 0'a'>>>['a', 'b', 'c'] !! 2'c'>>>['a', 'b', 'c'] !! 3*** Exception: Prelude.!!: index too large>>>['a', 'b', 'c'] !! (-1)*** Exception: Prelude.!!: negative index
fromJust :: HasCallStack => Maybe a -> a #
foldr1 :: Foldable t => (a -> a -> a) -> t a -> a #
A variant of foldr that has no base case,
and thus may only be applied to non-empty structures.
This function is non-total and will raise a runtime exception if the structure happens to be empty.
Examples
Basic usage:
>>>foldr1 (+) [1..4]10
>>>foldr1 (+) []Exception: Prelude.foldr1: empty list
>>>foldr1 (+) Nothing*** Exception: foldr1: empty structure
>>>foldr1 (-) [1..4]-2
>>>foldr1 (&&) [True, False, True, True]False
>>>foldr1 (||) [False, False, True, True]True
>>>foldr1 (+) [1..]* Hangs forever *
foldl1 :: Foldable t => (a -> a -> a) -> t a -> a #
A variant of foldl that has no base case,
and thus may only be applied to non-empty structures.
This function is non-total and will raise a runtime exception if the structure happens to be empty.
foldl1f =foldl1f .toList
Examples
Basic usage:
>>>foldl1 (+) [1..4]10
>>>foldl1 (+) []*** Exception: Prelude.foldl1: empty list
>>>foldl1 (+) Nothing*** Exception: foldl1: empty structure
>>>foldl1 (-) [1..4]-8
>>>foldl1 (&&) [True, False, True, True]False
>>>foldl1 (||) [False, False, True, True]True
>>>foldl1 (+) [1..]* Hangs forever *
minimum :: (Foldable t, Ord a) => t a -> a #
The least element of a non-empty structure.
This function is non-total and will raise a runtime exception if the structure happens to be empty. A structure that supports random access and maintains its elements in order should provide a specialised implementation to return the minimum in faster than linear time.
Examples
Basic usage:
>>>minimum [1..10]1
>>>minimum []*** Exception: Prelude.minimum: empty list
>>>minimum Nothing*** Exception: minimum: empty structure
WARNING: This function is partial for possibly-empty structures like lists.
Since: base-4.8.0.0
maximum :: (Foldable t, Ord a) => t a -> a #
The largest element of a non-empty structure.
This function is non-total and will raise a runtime exception if the structure happens to be empty. A structure that supports random access and maintains its elements in order should provide a specialised implementation to return the maximum in faster than linear time.
Examples
Basic usage:
>>>maximum [1..10]10
>>>maximum []*** Exception: Prelude.maximum: empty list
>>>maximum Nothing*** Exception: maximum: empty structure
WARNING: This function is partial for possibly-empty structures like lists.
Since: base-4.8.0.0
minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a #
The least element of a non-empty structure with respect to the given comparison function.
Examples
Basic usage:
>>>minimumBy (compare `on` length) ["Hello", "World", "!", "Longest", "bar"]"!"
WARNING: This function is partial for possibly-empty structures like lists.
maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a #
The largest element of a non-empty structure with respect to the given comparison function.
Examples
Basic usage:
>>>maximumBy (compare `on` length) ["Hello", "World", "!", "Longest", "bar"]"Longest"
WARNING: This function is partial for possibly-empty structures like lists.