Copyright | (c) 2016-2024 Rudy Matela |
---|---|
License | 3-Clause BSD (see the file LICENSE) |
Maintainer | Rudy Matela <rudy@matela.com.br> |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module is part of Speculate.
Exports utility functions of all utils sub-modules.
This is not intended to be used by users of Speculate, only by modules of Speculate itself. Expect symbols exported here to come and go with every minor version.
Synopsis
- undefined1 :: a
- undefined2 :: a
- thn :: Ordering -> Ordering -> Ordering
- reportCountsBy :: (Eq b, Show b) => (a -> b) -> [a] -> IO ()
- maybesToMaybe :: [Maybe a] -> Maybe a
- maybe2 :: c -> (a -> b -> c) -> Maybe a -> Maybe b -> c
- iterateUntil :: (a -> a -> Bool) -> (a -> a) -> a -> a
- iterateUntilLimit :: Int -> (a -> a -> Bool) -> (a -> a) -> a -> a
- showRatio :: (Integral a, Show a) => Ratio a -> String
- percent :: Integral a => Ratio a -> a
- putLines :: [String] -> IO ()
- (.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
- (..:) :: (d -> e) -> (a -> b -> c -> d) -> a -> b -> c -> e
- beside :: String -> String -> String
- above :: String -> String -> String
- table :: String -> [[String]] -> String
- spaces :: String -> [String]
- module Data.Tuple
- fst3 :: (a, b, c) -> a
- fst4 :: (a, b, c, d) -> a
- snd3 :: (a, b, c) -> b
- snd4 :: (a, b, c, d) -> b
- trd3 :: (a, b, c) -> c
- trd4 :: (a, b, c, d) -> c
- fth4 :: (a, b, c, d) -> d
- curry3 :: ((a, b, c) -> d) -> a -> b -> c -> d
- curry4 :: ((a, b, c, d) -> e) -> a -> b -> c -> d -> e
- uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d
- uncurry4 :: (a -> b -> c -> d -> e) -> (a, b, c, d) -> e
- uncurry5 :: (a -> b -> c -> d -> e -> f) -> (a, b, c, d, e) -> f
- uncurry6 :: (a -> b -> c -> d -> e -> f -> g) -> (a, b, c, d, e, f) -> g
- uncurry7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> (a, b, c, d, e, f, g) -> h
- uncurry8 :: (a -> b -> c -> d -> e -> f -> g -> h -> i) -> (a, b, c, d, e, f, g, h) -> i
- uncurry9 :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j) -> (a, b, c, d, e, f, g, h, i) -> j
- uncurry10 :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k) -> (a, b, c, d, e, f, g, h, i, j) -> k
- uncurry11 :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l) -> (a, b, c, d, e, f, g, h, i, j, k) -> l
- uncurry12 :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> m
- first :: (a -> a') -> (a, b) -> (a', b)
- second :: (b -> b') -> (a, b) -> (a, b')
- both :: (a -> b) -> (a, a) -> (b, b)
- (***) :: (a -> b) -> (c -> d) -> (a, c) -> (b, d)
- catPairs :: [(a, a)] -> [a]
- module Data.String
- module Data.Char
- unquote :: String -> String
- indent :: Int -> String -> String
- alignRight :: Int -> String -> String
- alignLeft :: Int -> String -> String
- splitAtCommas :: String -> [String]
- pairsThat :: (a -> a -> Bool) -> [a] -> [(a, a)]
- count :: Eq a => a -> [a] -> Int
- counts :: Eq a => [a] -> [(a, Int)]
- countsOn :: Eq b => (a -> b) -> [a] -> [(b, Int)]
- countsBy :: (a -> a -> Bool) -> [a] -> [(a, Int)]
- firsts :: Eq a => [a] -> [a]
- nubSort :: Ord a => [a] -> [a]
- nubSortBy :: (a -> a -> Ordering) -> [a] -> [a]
- (+++) :: Ord a => [a] -> [a] -> [a]
- nubMerge :: Ord a => [a] -> [a] -> [a]
- nubMergeBy :: (a -> a -> Ordering) -> [a] -> [a] -> [a]
- nubMergeOn :: Ord b => (a -> b) -> [a] -> [a] -> [a]
- nubMerges :: Ord a => [[a]] -> [a]
- nubMergesBy :: Ord a => (a -> a -> Ordering) -> [[a]] -> [a]
- nubMergeMap :: Ord b => (a -> [b]) -> [a] -> [b]
- ordIntersect :: Ord a => [a] -> [a] -> [a]
- ordIntersectBy :: (a -> a -> Ordering) -> [a] -> [a] -> [a]
- ordered :: Ord a => [a] -> Bool
- orderedBy :: (a -> a -> Bool) -> [a] -> Bool
- orderedOn :: Ord b => (a -> b) -> [a] -> Bool
- strictlyOrdered :: Ord a => [a] -> Bool
- strictlyOrderedOn :: Ord b => (a -> b) -> [a] -> Bool
- areAll :: [a] -> (a -> Bool) -> Bool
- areAny :: [a] -> (a -> Bool) -> Bool
- allLater :: (a -> a -> Bool) -> [a] -> Bool
- (+-) :: Eq a => [a] -> [a] -> [a]
- sortOn :: Ord b => (a -> b) -> [a] -> [a]
- groupOn :: Eq b => (a -> b) -> [a] -> [[a]]
- classifyOn :: Ord b => (a -> b) -> [a] -> [[a]]
- classifyBy :: (a -> a -> Ordering) -> [a] -> [[a]]
- classifyWith :: Ord b => (a -> b) -> (a -> c) -> (b -> [c] -> d) -> [a] -> [d]
- classifySndByFst :: Ord a => [(a, b)] -> [(a, [b])]
- discard :: (a -> Bool) -> [a] -> [a]
- discardLater :: (a -> a -> Bool) -> [a] -> [a]
- discardEarlier :: (a -> a -> Bool) -> [a] -> [a]
- discardOthers :: (a -> a -> Bool) -> [a] -> [a]
- discardByOthers :: (a -> [a] -> Bool) -> [a] -> [a]
- allUnique :: Ord a => [a] -> Bool
- chain :: [a -> a] -> a -> a
- zipWithReverse :: (a -> a -> b) -> [a] -> [b]
- medianate :: (a -> a -> b) -> [a] -> [b]
- takeGreaterHalf :: [a] -> [a]
- accum :: Num a => [a] -> [a]
- partitionByMarkers :: Eq a => a -> a -> [a] -> ([a], [a])
- (!) :: [[a]] -> Int -> [a]
- halve :: [a] -> ([a], [a])
- none :: (a -> Bool) -> [a] -> Bool
- productsList :: [[a]] -> [[a]]
- mapTMaybe :: (a -> Maybe b) -> [[a]] -> [[b]]
- uptoT :: Int -> [[a]] -> [a]
- filterTS :: (Int -> a -> Bool) -> [[a]] -> [[a]]
- discardTS :: (Int -> a -> Bool) -> [[a]] -> [[a]]
- timeoutToNothing :: RealFrac s => s -> a -> Maybe a
- fromTimeout :: RealFrac s => s -> a -> a -> a
- timeoutToFalse :: RealFrac s => s -> Bool -> Bool
- timeoutToTrue :: RealFrac s => s -> Bool -> Bool
- timeoutToError :: RealFrac s => s -> a -> a
- module Data.Ord
- compareIndex :: Eq a => [a] -> a -> a -> Ordering
- memory :: (Listable a, Ord a) => (a -> b) -> Map a b
- memory2 :: (Listable a, Listable b, Ord a, Ord b) => (a -> b -> c) -> Map (a, b) c
- memoryFor :: (Listable a, Ord a) => Int -> (a -> b) -> Map a b
- memory2For :: (Listable a, Listable b, Ord a, Ord b) => Int -> (a -> b -> c) -> Map (a, b) c
- withMemory :: Ord a => (a -> b) -> Map a b -> a -> b
- withMemory2 :: (Ord a, Ord b) => (a -> b -> c) -> Map (a, b) c -> a -> b -> c
Documentation
undefined1 :: a Source #
undefined2 :: a Source #
maybesToMaybe :: [Maybe a] -> Maybe a Source #
iterateUntil :: (a -> a -> Bool) -> (a -> a) -> a -> a Source #
iterateUntilLimit :: Int -> (a -> a -> Bool) -> (a -> a) -> a -> a Source #
beside :: String -> String -> String Source #
Appends two Strings side by side, line by line
beside ["asdf\nqw\n","zxvc\nas"] == "asdfzxvc\n\ \qw as\n"
above :: String -> String -> String Source #
Append two Strings on top of each other, adding line breaks *when needed*.
table :: String -> [[String]] -> String Source #
Formats a table. Examples:
table "l l l" [ ["asdf", "qwer", "zxvc\nzxvc"] , ["0", "1", "2"] , ["123", "456\n789", "3"] ] == "asdf qwer zxvc\n\ \ zxvc\n\ \0 1 2\n\ \123 456 3\n\ \ 789\n"
table "r l l" [ ["asdf", "qwer", "zxvc\nzxvc"] , ["0", "1", "2"] , ["123", "456\n789", "3"] ] == "asdf qwer zxvc\n\ \ zxvc\n\ \ 0 1 2\n\ \ 123 456 3\n\ \ 789\n"
table "r r l" [ ["asdf", "qwer", "zxvc\nzxvc"] , ["0", "1", "2"] , ["123", "456\n789", "3"] ] == "asdf qwer zxvc\n\ \ zxvc\n\ \ 0 1 2\n\ \ 123 456 3\n\ \ 789\n"
module Data.Tuple
uncurry9 :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j) -> (a, b, c, d, e, f, g, h, i) -> j Source #
uncurry10 :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k) -> (a, b, c, d, e, f, g, h, i, j) -> k Source #
uncurry11 :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l) -> (a, b, c, d, e, f, g, h, i, j, k) -> l Source #
uncurry12 :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> m Source #
first :: (a -> a') -> (a, b) -> (a', b) Source #
Applies a function to the first element of a pair.
Often known on the wild as mapFst
.
> first (*10) (1,2) (10,2)
second :: (b -> b') -> (a, b) -> (a, b') Source #
Applies a function to the second element of a pair.
Often known on the wild as mapSnd
.
> second (*100) (1,2) (1,200)
module Data.String
module Data.Char
Unquotes a string if possible, otherwise, this is just an identity.
> unquote "\"string\"" "string"
> unquote "something else" "something else"
splitAtCommas :: String -> [String] Source #
counts :: Eq a => [a] -> [(a, Int)] #
Returns the counts of each value in a list.
> counts "Mississippi" [('M',1),('i',4),('s',4),('p',2)]
Values are returned in the order they appear.
countsOn :: Eq b => (a -> b) -> [a] -> [(b, Int)] #
Returns the counts of each value in a list based on a projection.
> countsOn length ["sheep", "chip", "ship", "cheap", "Mississippi"] [(5,2),(4,2),(11,1)]
countsBy :: (a -> a -> Bool) -> [a] -> [(a, Int)] #
Returns the counts of each value in a list using a given comparison function.
nubSort :: Ord a => [a] -> [a] #
O(n log n).
Sorts and remove repetitions.
Equivalent to nub . sort
.
> nubSort [1,2,3] [1,2,3] > nubSort [3,2,1] [1,2,3] > nubSort [3,2,1,3,2,1] [1,2,3] > nubSort [3,3,1,1,2,2] [1,2,3]
(+++) :: Ord a => [a] -> [a] -> [a] infixr 5 #
Merges two lists discarding repeated elements.
The argument lists need to be in order.
> [1,10,100] +++ [9,10,11] [1,9,10,11,100]
nubMergeBy :: (a -> a -> Ordering) -> [a] -> [a] -> [a] Source #
nubMergeOn :: Ord b => (a -> b) -> [a] -> [a] -> [a] Source #
nubMergesBy :: Ord a => (a -> a -> Ordering) -> [[a]] -> [a] Source #
nubMergeMap :: Ord b => (a -> [b]) -> [a] -> [b] Source #
ordIntersect :: Ord a => [a] -> [a] -> [a] Source #
ordIntersectBy :: (a -> a -> Ordering) -> [a] -> [a] -> [a] Source #
strictlyOrdered :: Ord a => [a] -> Bool Source #
strictlyOrderedOn :: Ord b => (a -> b) -> [a] -> Bool Source #
(+-) :: Eq a => [a] -> [a] -> [a] Source #
xs +- ys
superimposes xs
over ys
.
- 1,2,3
- +- [0,0,0,0,0,0,0] == [1,2,3,0,0,0,0]
- x,y,z
- +- [a,b,c,d,e,f,g] == [x,y,z,d,e,f,g] "asdf" +- "this is a test" == "asdf is a test"
sortOn :: Ord b => (a -> b) -> [a] -> [a] #
Sort a list by comparing the results of a key function applied to each
element.
is equivalent to sortOn
f
, but has the
performance advantage of only evaluating sortBy
(comparing
f)f
once for each element in the
input list. This is called the decorate-sort-undecorate paradigm, or
Schwartzian transform.
Elements are arranged from lowest to highest, keeping duplicates in the order they appeared in the input.
>>>
sortOn fst [(2, "world"), (4, "!"), (1, "Hello")]
[(1,"Hello"),(2,"world"),(4,"!")]
The argument must be finite.
Since: base-4.8.0.0
classifyOn :: Ord b => (a -> b) -> [a] -> [[a]] Source #
classifyBy :: (a -> a -> Ordering) -> [a] -> [[a]] Source #
classifyWith :: Ord b => (a -> b) -> (a -> c) -> (b -> [c] -> d) -> [a] -> [d] Source #
classifySndByFst :: Ord a => [(a, b)] -> [(a, [b])] Source #
discardLater :: (a -> a -> Bool) -> [a] -> [a] Source #
discardEarlier :: (a -> a -> Bool) -> [a] -> [a] Source #
discardOthers :: (a -> a -> Bool) -> [a] -> [a] Source #
discardByOthers :: (a -> [a] -> Bool) -> [a] -> [a] Source #
zipWithReverse :: (a -> a -> b) -> [a] -> [b] Source #
takeGreaterHalf :: [a] -> [a] Source #
partitionByMarkers :: Eq a => a -> a -> [a] -> ([a], [a]) Source #
none :: (a -> Bool) -> [a] -> Bool #
Determines whether no element of the given list satisfies the predicate.
> none even [3,5,7,11,13] True
> none even [7,5,3,2] False
productsList :: [[a]] -> [[a]] Source #
timeoutToNothing :: RealFrac s => s -> a -> Maybe a Source #
Returns Nothing if value cannot be evaluated to WHNF in a given number of seconds
fromTimeout :: RealFrac s => s -> a -> a -> a Source #
timeoutToError :: RealFrac s => s -> a -> a Source #
module Data.Ord
compareIndex :: Eq a => [a] -> a -> a -> Ordering Source #
memory2For :: (Listable a, Listable b, Ord a, Ord b) => Int -> (a -> b -> c) -> Map (a, b) c Source #
withMemory :: Ord a => (a -> b) -> Map a b -> a -> b Source #