speculate-0.4.20: discovery of properties about Haskell functions
Copyright(c) 2016-2024 Rudy Matela
License3-Clause BSD (see the file LICENSE)
MaintainerRudy Matela <rudy@matela.com.br>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.Speculate.Utils

Description

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

Documentation

thn :: Ordering -> Ordering -> Ordering infixr 8 Source #

reportCountsBy :: (Eq b, Show b) => (a -> b) -> [a] -> IO () Source #

maybe2 :: c -> (a -> b -> c) -> Maybe a -> Maybe b -> c Source #

iterateUntil :: (a -> a -> Bool) -> (a -> a) -> a -> a Source #

iterateUntilLimit :: Int -> (a -> a -> Bool) -> (a -> a) -> a -> a Source #

percent :: Integral a => Ratio a -> a Source #

(.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> d Source #

(..:) :: (d -> e) -> (a -> b -> c -> d) -> a -> b -> c -> e 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

fst3 :: (a, b, c) -> a Source #

fst4 :: (a, b, c, d) -> a Source #

snd3 :: (a, b, c) -> b Source #

snd4 :: (a, b, c, d) -> b Source #

trd3 :: (a, b, c) -> c Source #

trd4 :: (a, b, c, d) -> c Source #

fth4 :: (a, b, c, d) -> d Source #

curry3 :: ((a, b, c) -> d) -> a -> b -> c -> d Source #

curry4 :: ((a, b, c, d) -> e) -> a -> b -> c -> d -> e Source #

uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d Source #

uncurry4 :: (a -> b -> c -> d -> e) -> (a, b, c, d) -> e Source #

uncurry5 :: (a -> b -> c -> d -> e -> f) -> (a, b, c, d, e) -> f Source #

uncurry6 :: (a -> b -> c -> d -> e -> f -> g) -> (a, b, c, d, e, f) -> g Source #

uncurry7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> (a, b, c, d, e, f, g) -> h Source #

uncurry8 :: (a -> b -> c -> d -> e -> f -> g -> h -> i) -> (a, b, c, d, e, f, g, h) -> i Source #

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)

both :: (a -> b) -> (a, a) -> (b, b) Source #

(***) :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) Source #

catPairs :: [(a, a)] -> [a] Source #

module Data.Char

unquote :: String -> String #

Unquotes a string if possible, otherwise, this is just an identity.

> unquote "\"string\""
"string"
> unquote "something else"
"something else"

pairsThat :: (a -> a -> Bool) -> [a] -> [(a, a)] Source #

count :: Eq a => a -> [a] -> Int 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.

firsts :: Eq a => [a] -> [a] Source #

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]

nubSortBy :: (a -> a -> Ordering) -> [a] -> [a] #

Like nubSort but allows providing a function to compare values.

(+++) :: 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]

nubMerge :: Ord a => [a] -> [a] -> [a] Source #

nubMergeBy :: (a -> a -> Ordering) -> [a] -> [a] -> [a] Source #

nubMergeOn :: Ord b => (a -> b) -> [a] -> [a] -> [a] Source #

nubMerges :: Ord 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 #

ordered :: Ord a => [a] -> Bool Source #

orderedBy :: (a -> a -> Bool) -> [a] -> Bool Source #

orderedOn :: Ord b => (a -> b) -> [a] -> Bool Source #

strictlyOrderedOn :: Ord b => (a -> b) -> [a] -> Bool Source #

areAll :: [a] -> (a -> Bool) -> Bool Source #

areAny :: [a] -> (a -> Bool) -> Bool Source #

allLater :: (a -> a -> Bool) -> [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. sortOn f is equivalent to sortBy (comparing f), but has the performance advantage of only evaluating 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

groupOn :: Eq b => (a -> b) -> [a] -> [[a]] Source #

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 #

discard :: (a -> Bool) -> [a] -> [a] 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 #

allUnique :: Ord a => [a] -> Bool Source #

chain :: [a -> a] -> a -> a Source #

zipWithReverse :: (a -> a -> b) -> [a] -> [b] Source #

medianate :: (a -> a -> b) -> [a] -> [b] Source #

takeGreaterHalf :: [a] -> [a] Source #

accum :: Num a => [a] -> [a] Source #

partitionByMarkers :: Eq a => a -> a -> [a] -> ([a], [a]) Source #

(!) :: [[a]] -> Int -> [a] Source #

halve :: [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 #

mapTMaybe :: (a -> Maybe b) -> [[a]] -> [[b]] Source #

uptoT :: Int -> [[a]] -> [a] Source #

filterTS :: (Int -> a -> Bool) -> [[a]] -> [[a]] Source #

discardTS :: (Int -> a -> Bool) -> [[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 #

memory :: (Listable a, Ord a) => (a -> b) -> Map a b Source #

memory2 :: (Listable a, Listable b, Ord a, Ord b) => (a -> b -> c) -> Map (a, b) c Source #

memoryFor :: (Listable a, Ord a) => Int -> (a -> b) -> Map a b 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 #

withMemory2 :: (Ord a, Ord b) => (a -> b -> c) -> Map (a, b) c -> a -> b -> c Source #