extra-1.7.14: Extra functions I use.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Extra

Description

Deprecated: This module is provided as documentation of all new functions, you should import the more specific modules directly.

This module documents all the functions available in this package.

Most users should import the specific modules (e.g. Data.List.Extra), which also reexport their non-Extra modules (e.g. Data.List).

Synopsis

Control.Concurrent.Extra

Extra functions available in Control.Concurrent.Extra.

withNumCapabilities :: Int -> IO a -> IO a Source #

On GHC 7.6 and above with the -threaded flag, brackets a call to setNumCapabilities. On lower versions (which lack setNumCapabilities) this function just runs the argument action.

once :: IO a -> IO (IO a) Source #

Given an action, produce a wrapped action that runs at most once. If the function raises an exception, the same exception will be reraised each time.

let x ||| y = do t1 <- onceFork x; t2 <- onceFork y; t1; t2
\(x :: IO Int) -> void (once x) == pure ()
\(x :: IO Int) -> join (once x) == x
\(x :: IO Int) -> (do y <- once x; y; y) == x
\(x :: IO Int) -> (do y <- once x; y ||| y) == x

onceFork :: IO a -> IO (IO a) Source #

Like once, but immediately starts running the computation on a background thread.

\(x :: IO Int) -> join (onceFork x) == x
\(x :: IO Int) -> (do a <- onceFork x; a; a) == x

data Lock Source #

Like an MVar, but has no value. Used to guarantee single-threaded access, typically to some system resource. As an example:

lock <- newLock
let output = withLock lock . putStrLn
forkIO $ do ...; output "hello"
forkIO $ do ...; output "world"

Here we are creating a lock to ensure that when writing output our messages do not get interleaved. This use of MVar never blocks on a put. It is permissible, but rare, that a withLock contains a withLock inside it - but if so, watch out for deadlocks.

newLock :: IO Lock Source #

Create a new Lock.

withLock :: Lock -> IO a -> IO a Source #

Perform some operation while holding Lock. Will prevent all other operations from using the Lock while the action is ongoing.

withLockTry :: Lock -> IO a -> IO (Maybe a) Source #

Like withLock but will never block. If the operation cannot be executed immediately it will return Nothing.

data Var a Source #

Like an MVar, but must always be full. Used to operate on a mutable variable in a thread-safe way. As an example:

hits <- newVar 0
forkIO $ do ...; modifyVar_ hits (+1); ...
i <- readVar hits
print ("HITS",i)

Here we have a variable which we modify atomically, so modifications are not interleaved. This use of MVar never blocks on a put. No modifyVar operation should ever block, and they should always complete in a reasonable timeframe. A Var should not be used to protect some external resource, only the variable contained within. Information from a readVar should not be subsequently inserted back into the Var.

newVar :: a -> IO (Var a) Source #

Create a new Var with a value.

readVar :: Var a -> IO a Source #

Read the current value of the Var.

writeVar :: Var a -> a -> IO () Source #

Write a value to become the new value of Var.

writeVar' :: Var a -> a -> IO () Source #

Strict variant of writeVar

modifyVar :: Var a -> (a -> IO (a, b)) -> IO b Source #

Modify a Var producing a new value and a return result.

modifyVar' :: Var a -> (a -> IO (a, b)) -> IO b Source #

Strict variant of modifyVar'

modifyVar_ :: Var a -> (a -> IO a) -> IO () Source #

Modify a Var, a restricted version of modifyVar.

modifyVar_' :: Var a -> (a -> IO a) -> IO () Source #

Strict variant of modifyVar_

withVar :: Var a -> (a -> IO b) -> IO b Source #

Perform some operation using the value in the Var, a restricted version of modifyVar.

data Barrier a Source #

Starts out empty, then is filled exactly once. As an example:

bar <- newBarrier
forkIO $ do ...; val <- ...; signalBarrier bar val
print =<< waitBarrier bar

Here we create a barrier which will contain some computed value. A thread is forked to fill the barrier, while the main thread waits for it to complete. A barrier has similarities to a future or promise from other languages, has been known as an IVar in other Haskell work, and in some ways is like a manually managed thunk.

newBarrier :: IO (Barrier a) Source #

Create a new Barrier.

signalBarrier :: Partial => Barrier a -> a -> IO () Source #

Write a value into the Barrier, releasing anyone at waitBarrier. Any subsequent attempts to signal the Barrier will throw an exception.

waitBarrier :: Barrier a -> IO a Source #

Wait until a barrier has been signaled with signalBarrier.

waitBarrierMaybe :: Barrier a -> IO (Maybe a) Source #

A version of waitBarrier that never blocks, returning Nothing if the barrier has not yet been signaled.

Control.Exception.Extra

Extra functions available in Control.Exception.Extra.

type Partial = HasCallStack Source #

A constraint which documents that a function is partial, and on GHC 8.0 and above produces a stack trace on failure. For example:

myHead :: Partial => [a] -> a
myHead [] = error "bad"
myHead (x:xs) = x

When using Partial with GHC 7.8 or below you need to enable the language feature ConstraintKinds, e.g. {-# LANGUAGE ConstraintKinds #-} at the top of the file.

retry :: Int -> IO a -> IO a Source #

Retry an operation at most n times (n must be positive). If the operation fails the nth time it will throw that final exception.

retry 1 (print "x")  == print "x"
retry 3 (fail "die") == fail "die"

retryBool :: Exception e => (e -> Bool) -> Int -> IO a -> IO a Source #

Retry an operation at most n times (n must be positive), while the exception value and type match a predicate. If the operation fails the nth time it will throw that final exception.

errorWithoutStackTrace :: forall (r :: RuntimeRep) (a :: TYPE r). [Char] -> a #

A variant of error that does not produce a stack trace.

Since: base-4.9.0.0

showException :: Show e => e -> IO String Source #

Show a value, but if the result contains exceptions, produce <Exception>. Defined as stringException . show. Particularly useful for printing exceptions to users, remembering that exceptions can themselves contain undefined values.

stringException :: String -> IO String Source #

Fully evaluate an input String. If the String contains embedded exceptions it will produce <Exception>.

stringException "test"                           == pure "test"
stringException ("test" ++ undefined)            == pure "test<Exception>"
stringException ("test" ++ undefined ++ "hello") == pure "test<Exception>"
stringException ['t','e','s','t',undefined]      == pure "test<Exception>"

errorIO :: Partial => String -> IO a Source #

An IO action that when evaluated calls error, in the IO monad. Note that while fail in IO raises an IOException, this function raises an ErrorCall exception with a call stack.

catch (errorIO "Hello") (\(ErrorCall x) -> pure x) == pure "Hello"
seq (errorIO "foo") (print 1) == print 1

assertIO :: Partial => Bool -> IO () Source #

An IO action that when evaluated calls assert in the IO monad, which throws an AssertionFailed exception if the argument is False. With optimizations enabled (and -fgnore-asserts) this function ignores its argument and does nothing.

catch (assertIO True  >> pure 1) (\(x :: AssertionFailed) -> pure 2) == pure 1
seq (assertIO False) (print 1) == print 1

ignore :: IO () -> IO () Source #

Ignore any exceptions thrown by the action.

ignore (print 1)    == print 1
ignore (fail "die") == pure ()

catch_ :: IO a -> (SomeException -> IO a) -> IO a Source #

A version of catch without the Exception context, restricted to SomeException, so catches all exceptions.

handle_ :: (SomeException -> IO a) -> IO a -> IO a Source #

Like catch_ but for handle

try_ :: IO a -> IO (Either SomeException a) Source #

Like catch_ but for try

catchJust_ :: (SomeException -> Maybe b) -> IO a -> (b -> IO a) -> IO a Source #

Like catch_ but for catchJust

handleJust_ :: (SomeException -> Maybe b) -> (b -> IO a) -> IO a -> IO a Source #

Like catch_ but for handleJust

tryJust_ :: (SomeException -> Maybe b) -> IO a -> IO (Either b a) Source #

Like catch_ but for tryJust

catchBool :: Exception e => (e -> Bool) -> IO a -> (e -> IO a) -> IO a Source #

Catch an exception if the predicate passes, then call the handler with the original exception. As an example:

readFileExists x == catchBool isDoesNotExistError (readFile "myfile") (const $ pure "")

handleBool :: Exception e => (e -> Bool) -> (e -> IO a) -> IO a -> IO a Source #

Like catchBool but for handle.

tryBool :: Exception e => (e -> Bool) -> IO a -> IO (Either e a) Source #

Like catchBool but for try.

Control.Monad.Extra

Extra functions available in Control.Monad.Extra.

whenJust :: Applicative m => Maybe a -> (a -> m ()) -> m () Source #

Perform some operation on Just, given the field inside the Just. This is a specialized for_.

whenJust Nothing  print == pure ()
whenJust (Just 1) print == print 1

whenJustM :: Monad m => m (Maybe a) -> (a -> m ()) -> m () Source #

Like whenJust, but where the test can be monadic.

pureIf :: Alternative m => Bool -> a -> m a Source #

Return either a pure value if a condition is True, otherwise empty.

pureIf @Maybe True  5 == Just 5
pureIf @Maybe False 5 == Nothing
pureIf @[]    True  5 == [5]
pureIf @[]    False 5 == []

whenMaybe :: Applicative m => Bool -> m a -> m (Maybe a) Source #

Like when, but return either Nothing if the predicate was False, of Just with the result of the computation.

whenMaybe True  (print 1) == fmap Just (print 1)
whenMaybe False (print 1) == pure Nothing

whenMaybeM :: Monad m => m Bool -> m a -> m (Maybe a) Source #

Like whenMaybe, but where the test can be monadic.

unit :: m () -> m () Source #

The identity function which requires the inner argument to be (). Useful for functions with overloaded return types.

\(x :: Maybe ()) -> unit x == x

maybeM :: Monad m => m b -> (a -> m b) -> m (Maybe a) -> m b Source #

Monadic generalisation of maybe.

fromMaybeM :: Monad m => m a -> m (Maybe a) -> m a Source #

Monadic generalisation of fromMaybe.

eitherM :: Monad m => (a -> m c) -> (b -> m c) -> m (Either a b) -> m c Source #

Monadic generalisation of either.

loop :: (a -> Either a b) -> a -> b Source #

A looping operation, where the predicate returns Left as a seed for the next loop or Right to abort the loop.

loop (\x -> if x < 10 then Left $ x * 2 else Right $ show x) 1 == "16"

loopM :: Monad m => (a -> m (Either a b)) -> a -> m b Source #

A monadic version of loop, where the predicate returns Left as a seed for the next loop or Right to abort the loop.

whileM :: Monad m => m Bool -> m () Source #

Keep running an operation until it becomes False. As an example:

whileM $ do sleep 0.1; notM $ doesFileExist "foo.txt"
readFile "foo.txt"

If you need some state persisted between each test, use loopM.

whileJustM :: (Monad m, Monoid a) => m (Maybe a) -> m a Source #

Keep running an operation until it becomes a Nothing, accumulating the monoid results inside the Justs as the result of the overall loop.

untilJustM :: Monad m => m (Maybe a) -> m a Source #

Keep running an operation until it becomes a Just, then return the value inside the Just as the result of the overall loop.

partitionM :: Monad m => (a -> m Bool) -> [a] -> m ([a], [a]) Source #

A version of partition that works with a monadic predicate.

partitionM (Just . even) [1,2,3] == Just ([2], [1,3])
partitionM (const Nothing) [1,2,3] == Nothing

concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b] Source #

A version of concatMap that works with a monadic predicate.

concatForM :: Monad m => [a] -> (a -> m [b]) -> m [b] Source #

Like concatMapM, but has its arguments flipped, so can be used instead of the common fmap concat $ forM pattern.

mconcatMapM :: (Monad m, Monoid b) => (a -> m b) -> [a] -> m b Source #

A version of mconcatMap that works with a monadic predicate.

mapMaybeM :: Monad m => (a -> m (Maybe b)) -> [a] -> m [b] Source #

A version of mapMaybe that works with a monadic predicate.

findM :: Monad m => (a -> m Bool) -> [a] -> m (Maybe a) Source #

Like find, but where the test can be monadic.

findM (Just . isUpper) "teST"             == Just (Just 'S')
findM (Just . isUpper) "test"             == Just Nothing
findM (Just . const True) ["x",undefined] == Just (Just "x")

firstJustM :: Monad m => (a -> m (Maybe b)) -> [a] -> m (Maybe b) Source #

Like findM, but also allows you to compute some additional information in the predicate.

fold1M :: (Partial, Monad m) => (a -> a -> m a) -> [a] -> m a Source #

A variant of foldM that has no base case, and thus may only be applied to non-empty lists.

fold1M (\x y -> Just x) [] == undefined
fold1M (\x y -> Just $ x + y) [1, 2, 3] == Just 6

fold1M_ :: (Partial, Monad m) => (a -> a -> m a) -> [a] -> m () Source #

Like fold1M but discards the result.

whenM :: Monad m => m Bool -> m () -> m () Source #

Like when, but where the test can be monadic.

unlessM :: Monad m => m Bool -> m () -> m () Source #

Like unless, but where the test can be monadic.

ifM :: Monad m => m Bool -> m a -> m a -> m a Source #

Like if, but where the test can be monadic.

notM :: Functor m => m Bool -> m Bool Source #

Like not, but where the test can be monadic.

(||^) :: Monad m => m Bool -> m Bool -> m Bool Source #

The lazy || operator lifted to a monad. If the first argument evaluates to True the second argument will not be evaluated.

Just True  ||^ undefined  == Just True
Just False ||^ Just True  == Just True
Just False ||^ Just False == Just False

(&&^) :: Monad m => m Bool -> m Bool -> m Bool Source #

The lazy && operator lifted to a monad. If the first argument evaluates to False the second argument will not be evaluated.

Just False &&^ undefined  == Just False
Just True  &&^ Just True  == Just True
Just True  &&^ Just False == Just False

orM :: Monad m => [m Bool] -> m Bool Source #

A version of or lifted to a monad. Retains the short-circuiting behaviour.

orM [Just False,Just True ,undefined] == Just True
orM [Just False,Just False,undefined] == undefined
\xs -> Just (or xs) == orM (map Just xs)

andM :: Monad m => [m Bool] -> m Bool Source #

A version of and lifted to a monad. Retains the short-circuiting behaviour.

andM [Just True,Just False,undefined] == Just False
andM [Just True,Just True ,undefined] == undefined
\xs -> Just (and xs) == andM (map Just xs)

anyM :: Monad m => (a -> m Bool) -> [a] -> m Bool Source #

A version of any lifted to a monad. Retains the short-circuiting behaviour.

anyM Just [False,True ,undefined] == Just True
anyM Just [False,False,undefined] == undefined
\(f :: Int -> Maybe Bool) xs -> anyM f xs == orM (map f xs)

allM :: Monad m => (a -> m Bool) -> [a] -> m Bool Source #

A version of all lifted to a monad. Retains the short-circuiting behaviour.

allM Just [True,False,undefined] == Just False
allM Just [True,True ,undefined] == undefined
\(f :: Int -> Maybe Bool) xs -> anyM f xs == orM (map f xs)

Data.Either.Extra

Extra functions available in Data.Either.Extra.

fromLeft :: a -> Either a b -> a #

Return the contents of a Left-value or a default value otherwise.

Examples

Expand

Basic usage:

>>> fromLeft 1 (Left 3)
3
>>> fromLeft 1 (Right "foo")
1

Since: base-4.10.0.0

fromRight :: b -> Either a b -> b #

Return the contents of a Right-value or a default value otherwise.

Examples

Expand

Basic usage:

>>> fromRight 1 (Right 3)
3
>>> fromRight 1 (Left "foo")
1

Since: base-4.10.0.0

fromEither :: Either a a -> a Source #

Pull the value out of an Either where both alternatives have the same type.

\x -> fromEither (Left x ) == x
\x -> fromEither (Right x) == x

fromLeft' :: Partial => Either l r -> l Source #

The fromLeft' function extracts the element out of a Left and throws an error if its argument is Right. Much like fromJust, using this function in polished code is usually a bad idea.

\x -> fromLeft' (Left  x) == x
\x -> fromLeft' (Right x) == undefined

fromRight' :: Partial => Either l r -> r Source #

The fromRight' function extracts the element out of a Right and throws an error if its argument is Left. Much like fromJust, using this function in polished code is usually a bad idea.

\x -> fromRight' (Right x) == x
\x -> fromRight' (Left  x) == undefined

eitherToMaybe :: Either a b -> Maybe b Source #

Given an Either, convert it to a Maybe, where Left becomes Nothing.

\x -> eitherToMaybe (Left x) == Nothing
\x -> eitherToMaybe (Right x) == Just x

maybeToEither :: a -> Maybe b -> Either a b Source #

Given a Maybe, convert it to an Either, providing a suitable value for the Left should the value be Nothing.

\a b -> maybeToEither a (Just b) == Right b
\a -> maybeToEither a Nothing == Left a

mapLeft :: (a -> c) -> Either a b -> Either c b Source #

The mapLeft function takes a function and applies it to an Either value iff the value takes the form Left _.

mapLeft show (Left 1) == Left "1"
mapLeft show (Right True) == Right True

mapRight :: (b -> c) -> Either a b -> Either a c Source #

The mapRight function takes a function and applies it to an Either value iff the value takes the form Right _.

mapRight show (Left 1) == Left 1
mapRight show (Right True) == Right "True"

Data.IORef.Extra

Extra functions available in Data.IORef.Extra.

writeIORef' :: IORef a -> a -> IO () Source #

Evaluates the value before calling writeIORef.

atomicWriteIORef' :: IORef a -> a -> IO () Source #

Evaluates the value before calling atomicWriteIORef.

atomicModifyIORef_ :: IORef a -> (a -> a) -> IO () Source #

Variant of atomicModifyIORef which ignores the return value

atomicModifyIORef'_ :: IORef a -> (a -> a) -> IO () Source #

Variant of atomicModifyIORef' which ignores the return value

Data.List.Extra

Extra functions available in Data.List.Extra.

lower :: String -> String Source #

Convert a string to lower case.

lower "This is A TEST" == "this is a test"
lower "" == ""

upper :: String -> String Source #

Convert a string to upper case.

upper "This is A TEST" == "THIS IS A TEST"
upper "" == ""

trim :: String -> String Source #

Remove spaces from either side of a string. A combination of trimEnd and trimStart.

trim      "  hello   " == "hello"
trimStart "  hello   " == "hello   "
trimEnd   "  hello   " == "  hello"
\s -> trim s == trimEnd (trimStart s)

trimStart :: String -> String Source #

Remove spaces from the start of a string, see trim.

trimEnd :: String -> String Source #

Remove spaces from the end of a string, see trim.

word1 :: String -> (String, String) Source #

Split the first word off a string. Useful for when starting to parse the beginning of a string, but you want to accurately preserve whitespace in the rest of the string.

word1 "" == ("", "")
word1 "keyword rest of string" == ("keyword","rest of string")
word1 "  keyword\n  rest of string" == ("keyword","rest of string")
\s -> fst (word1 s) == concat (take 1 $ words s)
\s -> words (snd $ word1 s) == drop 1 (words s)

line1 :: String -> (String, String) Source #

Split the first line off a string.

line1 "" == ("", "")
line1 "test" == ("test","")
line1 "test\n" == ("test","")
line1 "test\nrest" == ("test","rest")
line1 "test\nrest\nmore" == ("test","rest\nmore")

escapeHTML :: String -> String Source #

Escape a string such that it can be inserted into an HTML document or " attribute without any special interpretation. This requires escaping the <, >, & and " characters. Note that it will escape " and ' even though that is not required in an HTML body (but is not harmful).

escapeHTML "this is a test" == "this is a test"
escapeHTML "<b>\"g&t\"</n>" == "&lt;b&gt;&quot;g&amp;t&quot;&lt;/n&gt;"
escapeHTML "t'was another test" == "t&#39;was another test"

escapeJSON :: String -> String Source #

Escape a string so it can form part of a JSON literal. This requires escaping the special whitespace and control characters. Additionally, Note that it does not add quote characters around the string.

escapeJSON "this is a test" == "this is a test"
escapeJSON "\ttab\nnewline\\" == "\\ttab\\nnewline\\\\"
escapeJSON "\ESC[0mHello" == "\\u001b[0mHello"

unescapeHTML :: String -> String Source #

Invert of escapeHTML (does not do general HTML unescaping)

\xs -> unescapeHTML (escapeHTML xs) == xs

unescapeJSON :: String -> String Source #

General JSON unescaping, inversion of escapeJSON and all other JSON escapes.

\xs -> unescapeJSON (escapeJSON xs) == xs

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

Drop a number of elements from the end of the list.

dropEnd 3 "hello"  == "he"
dropEnd 5 "bye"    == ""
dropEnd (-1) "bye" == "bye"
\i xs -> dropEnd i xs `isPrefixOf` xs
\i xs -> length (dropEnd i xs) == max 0 (length xs - max 0 i)
\i -> take 3 (dropEnd 5 [i..]) == take 3 [i..]

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

Take a number of elements from the end of the list.

takeEnd 3 "hello"  == "llo"
takeEnd 5 "bye"    == "bye"
takeEnd (-1) "bye" == ""
\i xs -> takeEnd i xs `isSuffixOf` xs
\i xs -> length (takeEnd i xs) == min (max 0 i) (length xs)

splitAtEnd :: Int -> [a] -> ([a], [a]) Source #

splitAtEnd n xs returns a split where the second element tries to contain n elements.

splitAtEnd 3 "hello" == ("he","llo")
splitAtEnd 3 "he"    == ("", "he")
\i xs -> uncurry (++) (splitAt i xs) == xs
\i xs -> splitAtEnd i xs == (dropEnd i xs, takeEnd i xs)

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

Break, but from the end.

breakEnd isLower "youRE" == ("you","RE")
breakEnd isLower "youre" == ("youre","")
breakEnd isLower "YOURE" == ("","YOURE")
\f xs -> breakEnd (not . f) xs == spanEnd f  xs

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

Span, but from the end.

spanEnd isUpper "youRE" == ("you","RE")
spanEnd (not . isSpace) "x y z" == ("x y ","z")
\f xs -> uncurry (++) (spanEnd f xs) == xs
\f xs -> spanEnd f xs == swap (both reverse (span f (reverse xs)))

dropWhileEnd' :: (a -> Bool) -> [a] -> [a] Source #

A version of dropWhileEnd but with different strictness properties. The function dropWhileEnd can be used on an infinite list and tests the property on each character. In contrast, dropWhileEnd' is strict in the spine of the list but only tests the trailing suffix. This version usually outperforms dropWhileEnd if the list is short or the test is expensive. Note the tests below cover both the prime and non-prime variants.

dropWhileEnd  isSpace "ab cde  " == "ab cde"
dropWhileEnd' isSpace "ab cde  " == "ab cde"
last (dropWhileEnd  even [undefined,3]) == undefined
last (dropWhileEnd' even [undefined,3]) == 3
head (dropWhileEnd  even (3:undefined)) == 3
head (dropWhileEnd' even (3:undefined)) == undefined

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

A version of takeWhile operating from the end.

takeWhileEnd even [2,3,4,6] == [4,6]

stripSuffix :: Eq a => [a] -> [a] -> Maybe [a] Source #

Return the prefix of the second list if its suffix matches the entire first list.

Examples:

stripSuffix "bar" "foobar" == Just "foo"
stripSuffix ""    "baz"    == Just "baz"
stripSuffix "foo" "quux"   == Nothing

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

Return the the string before and after the search string, or Nothing if the search string is not present.

Examples:

stripInfix "::" "a::b::c" == Just ("a", "b::c")
stripInfix "/" "foobar"   == Nothing

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

Similar to stripInfix, but searches from the end of the string.

stripInfixEnd "::" "a::b::c" == Just ("a::b", "c")

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

Drops the given prefix from a list. It returns the original sequence if the sequence doesn't start with the given prefix.

dropPrefix "Mr. " "Mr. Men" == "Men"
dropPrefix "Mr. " "Dr. Men" == "Dr. Men"

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

Drops the given suffix from a list. It returns the original sequence if the sequence doesn't end with the given suffix.

dropSuffix "!" "Hello World!"  == "Hello World"
dropSuffix "!" "Hello World!!" == "Hello World!"
dropSuffix "!" "Hello World."  == "Hello World."

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

A variant of words with a custom test. In particular, adjacent separators are discarded, as are leading or trailing separators.

wordsBy (== ':') "::xyz:abc::123::" == ["xyz","abc","123"]
\s -> wordsBy isSpace s == words s

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

A variant of lines with a custom test. In particular, if there is a trailing separator it will be discarded.

linesBy (== ':') "::xyz:abc::123::" == ["","","xyz","abc","","123",""]
\s -> linesBy (== '\n') s == lines s
linesBy (== ';') "my;list;here;" == ["my","list","here"]

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

Find the first instance of needle in haystack. The first element of the returned tuple is the prefix of haystack before needle is matched. The second is the remainder of haystack, starting with the match. If you want the remainder without the match, use stripInfix.

breakOn "::" "a::b::c" == ("a", "::b::c")
breakOn "/" "foobar"   == ("foobar", "")
\needle haystack -> let (prefix,match) = breakOn needle haystack in prefix ++ match == haystack

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

Similar to breakOn, but searches from the end of the string.

The first element of the returned tuple is the prefix of haystack up to and including the last match of needle. The second is the remainder of haystack, following the match.

breakOnEnd "::" "a::b::c" == ("a::b::", "c")

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

Break a list into pieces separated by the first list argument, consuming the delimiter. An empty delimiter is invalid, and will cause an error to be raised.

splitOn "\r\n" "a\r\nb\r\nd\r\ne" == ["a","b","d","e"]
splitOn "aaa"  "aaaXaaaXaaaXaaa"  == ["","X","X","X",""]
splitOn "x"    "x"                == ["",""]
splitOn "x"    ""                 == [""]
\s x -> s /= "" ==> intercalate s (splitOn s x) == x
\c x -> splitOn [c] x                           == split (==c) x

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

Splits a list into components delimited by separators, where the predicate returns True for a separator element. The resulting components do not contain the separators. Two adjacent separators result in an empty component in the output.

split (== 'a') "aabbaca" == ["","","bb","c",""]
split (== 'a') ""        == [""]
split (== ':') "::xyz:abc::123::" == ["","","xyz","abc","","123","",""]
split (== ',') "my,list,here" == ["my","list","here"]

chunksOf :: Partial => Int -> [a] -> [[a]] Source #

Split a list into chunks of a given size. The last chunk may contain fewer than n elements. The chunk size must be positive.

chunksOf 3 "my test" == ["my ","tes","t"]
chunksOf 3 "mytest"  == ["myt","est"]
chunksOf 8 ""        == []
chunksOf 0 "test"    == undefined

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

A total head with a default value.

headDef 1 []      == 1
headDef 1 [2,3,4] == 2
\x xs -> headDef x xs == fromMaybe x (listToMaybe xs)

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

A total last with a default value.

lastDef 1 []      == 1
lastDef 1 [2,3,4] == 4
\x xs -> lastDef x xs == last (x:xs)

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

A total variant of the list index function (!!).

[2,3,4] !? 1    == Just 3
[2,3,4] !? (-1) == Nothing
[]      !? 0    == Nothing

notNull :: [a] -> Bool Source #

A composition of not and null.

notNull []  == False
notNull [1] == True
\xs -> notNull xs == not (null xs)

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

Non-recursive transform over a list, like maybe.

list 1 (\v _ -> v - 2) [5,6,7] == 3
list 1 (\v _ -> v - 2) []      == 1
\nil cons xs -> maybe nil (uncurry cons) (uncons xs) == list nil cons xs

unsnoc :: [a] -> Maybe ([a], a) Source #

If the list is empty returns Nothing, otherwise returns the init and the last.

unsnoc "test" == Just ("tes",'t')
unsnoc ""     == Nothing
\xs -> unsnoc xs == if null xs then Nothing else Just (init xs, last xs)

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

Append an element to the start of a list, an alias for (:).

cons 't' "est" == "test"
\x xs -> uncons (cons x xs) == Just (x,xs)

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

Append an element to the end of a list, takes O(n) time.

snoc "tes" 't' == "test"
\xs x -> unsnoc (snoc xs x) == Just (xs,x)

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

Equivalent to drop 1, but likely to be faster and a single lexeme.

drop1 ""         == ""
drop1 "test"     == "est"
\xs -> drop 1 xs == drop1 xs

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

Equivalent to dropEnd 1, but likely to be faster and a single lexeme.

dropEnd1 ""         == ""
dropEnd1 "test"     == "tes"
\xs -> dropEnd 1 xs == dropEnd1 xs

mconcatMap :: Monoid b => (a -> b) -> [a] -> b Source #

Version on concatMap generalised to a Monoid rather than just a list.

mconcatMap Sum [1,2,3] == Sum 6
\f xs -> mconcatMap f xs == concatMap f xs

compareLength :: (Ord b, Num b, Foldable f) => f a -> b -> Ordering Source #

Lazily compare the length of a Foldable with a number.

compareLength [1,2,3] 1 == GT
compareLength [1,2] 2 == EQ
\(xs :: [Int]) n -> compareLength xs n == compare (length xs) n
compareLength (1:2:3:undefined) 2 == GT

comparingLength :: (Foldable f1, Foldable f2) => f1 a -> f2 b -> Ordering Source #

Lazily compare the length of two Foldables. > comparingLength [1,2,3] [False] == GT > comparingLength [1,2] "ab" == EQ > (xs :: [Int]) (ys :: [Int]) -> comparingLength xs ys == Data.Ord.comparing length xs ys > comparingLength 1,2 == LT > comparingLength (1:2:3:undefined) [1,2] == GT

enumerate :: (Enum a, Bounded a) => [a] Source #

Enumerate all the values of an Enum, from minBound to maxBound.

enumerate == [False, True]

groupSort :: Ord k => [(k, v)] -> [(k, [v])] Source #

A combination of group and sort.

groupSort [(1,'t'),(3,'t'),(2,'e'),(2,'s')] == [(1,"t"),(2,"es"),(3,"t")]
\xs -> map fst (groupSort xs) == sort (nub (map fst xs))
\xs -> concatMap snd (groupSort xs) == map snd (sortOn fst xs)

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

A combination of group and sort, using a part of the value to compare on.

groupSortOn length ["test","of","sized","item"] == [["of"],["test","item"],["sized"]]

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

A combination of group and sort, using a predicate to compare on.

groupSortBy (compare `on` length) ["test","of","sized","item"] == [["of"],["test","item"],["sized"]]

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

O(n log n). The nubOrd function removes duplicate elements from a list. In particular, it keeps only the first occurrence of each element. Unlike the standard nub operator, this version requires an Ord instance and consequently runs asymptotically faster.

nubOrd "this is a test" == "this ae"
nubOrd (take 4 ("this" ++ undefined)) == "this"
\xs -> nubOrd xs == nub xs

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

A version of nubOrd with a custom predicate.

nubOrdBy (compare `on` length) ["a","test","of","this"] == ["a","test","of"]

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

A version of nubOrd which operates on a portion of the value.

nubOrdOn length ["a","test","of","this"] == ["a","test","of"]

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

Deprecated: Use nubOrdOn, since this function is O(n^2)

DEPRECATED Use nubOrdOn, since this function is _O(n^2)_.

A version of nub where the equality is done on some extracted value. nubOn f is equivalent to nubBy ((==) on f), but has the performance advantage of only evaluating f once for each element in the input list.

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

A version of group where the equality is done on some extracted value.

groupOn abs [1,-1,2] == [[1,-1], [2]]

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

A version of groupOn which pairs each group with its "key" - the extracted value used for equality testing.

groupOnKey abs [1,-1,2] == [(1, [1,-1]), (2, [2])]

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

O(n log n). The nubSort function sorts and removes duplicate elements from a list. In particular, it keeps only the first occurrence of each element.

nubSort "this is a test" == " aehist"
\xs -> nubSort xs == nub (sort xs)

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

A version of nubSort with a custom predicate.

nubSortBy (compare `on` length) ["a","test","of","this"] == ["a","of","test"]

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

A version of nubSort which operates on a portion of the value.

nubSortOn length ["a","test","of","this"] == ["a","of","test"]

maximumOn :: (Partial, Ord b) => (a -> b) -> [a] -> a Source #

A version of maximum where the comparison is done on some extracted value. Raises an error if the list is empty. Only calls the function once per element.

maximumOn id [] == undefined
maximumOn length ["test","extra","a"] == "extra"

minimumOn :: (Partial, Ord b) => (a -> b) -> [a] -> a Source #

A version of minimum where the comparison is done on some extracted value. Raises an error if the list is empty. Only calls the function once per element.

minimumOn id [] == undefined
minimumOn length ["test","extra","a"] == "a"

sum' :: Num a => [a] -> a Source #

A strict version of sum. Unlike sum this function is always strict in the Num argument, whereas the standard version is only strict if the optimiser kicks in.

sum' [1, 2, 3] == 6

product' :: Num a => [a] -> a Source #

A strict version of product.

product' [1, 2, 4] == 8

sumOn' :: Num b => (a -> b) -> [a] -> b Source #

A strict version of sum, using a custom valuation function.

sumOn' read ["1", "2", "3"] == 6

productOn' :: Num b => (a -> b) -> [a] -> b Source #

A strict version of product, using a custom valuation function.

productOn' read ["1", "2", "4"] == 8

disjoint :: Eq a => [a] -> [a] -> Bool Source #

Are two lists disjoint, with no elements in common.

disjoint [1,2,3] [4,5] == True
disjoint [1,2,3] [4,1] == False

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

O((m+n) log m), m <= n. Are two lists disjoint, with no elements in common.

disjointOrd is more strict than disjoint. For example, disjointOrd cannot terminate if both lists are infinite, while disjoint can.

disjointOrd [1,2,3] [4,5] == True
disjointOrd [1,2,3] [4,1] == False

disjointOrdBy :: (a -> a -> Ordering) -> [a] -> [a] -> Bool Source #

A version of disjointOrd with a custom predicate.

disjointOrdBy (compare `on` (`mod` 7)) [1,2,3] [4,5] == True
disjointOrdBy (compare `on` (`mod` 7)) [1,2,3] [4,8] == False

allSame :: Eq a => [a] -> Bool Source #

Are all elements the same.

allSame [1,1,2] == False
allSame [1,1,1] == True
allSame [1]     == True
allSame []      == True
allSame (1:1:2:undefined) == False
\xs -> allSame xs == (length (nub xs) <= 1)

anySame :: Eq a => [a] -> Bool Source #

Is there any element which occurs more than once.

anySame [1,1,2] == True
anySame [1,2,3] == False
anySame (1:2:1:undefined) == True
anySame [] == False
\xs -> anySame xs == (length (nub xs) < length xs)

repeatedly :: ([a] -> (b, [a])) -> [a] -> [b] Source #

Apply some operation repeatedly, producing an element of output and the remainder of the list.

When the empty list is reached it is returned, so the operation is never applied to the empty input. That fact is encoded in the type system with repeatedlyNE

\xs -> repeatedly (splitAt 3) xs  == chunksOf 3 xs
\xs -> repeatedly word1 (trim xs) == words xs
\xs -> repeatedly line1 xs == lines xs

repeatedlyNE :: (NonEmpty a -> (b, [a])) -> [a] -> [b] Source #

Apply some operation repeatedly, producing an element of output and the remainder of the list.

Identical to repeatedly, but has a more precise type signature.

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

Find the first element of a list for which the operation returns Just, along with the result of the operation. Like find but useful where the function also computes some expensive information that can be reused. Particular useful when the function is monadic, see firstJustM.

firstJust id [Nothing,Just 3]  == Just 3
firstJust id [Nothing,Nothing] == Nothing

concatUnzip :: [([a], [b])] -> ([a], [b]) Source #

A merging of unzip and concat.

concatUnzip [("a","AB"),("bc","C")] == ("abc","ABC")

concatUnzip3 :: [([a], [b], [c])] -> ([a], [b], [c]) Source #

A merging of unzip3 and concat.

concatUnzip3 [("a","AB",""),("bc","C","123")] == ("abc","ABC","123")

zipFrom :: Enum a => a -> [b] -> [(a, b)] Source #

zip against an enumeration. Truncates the output if the enumeration runs out.

\i xs -> zip [i..] xs == zipFrom i xs
zipFrom False [1..3] == [(False,1),(True, 2)]

zipWithFrom :: Enum a => (a -> b -> c) -> a -> [b] -> [c] Source #

zipFrom generalised to any combining operation. Truncates the output if the enumeration runs out.

\i xs -> zipWithFrom (,) i xs == zipFrom i xs

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

Like zipWith, but keep going to the longest value. The function argument will always be given at least one Just, and while both lists have items, two Just values.

zipWithLongest (,) "a" "xyz" == [(Just 'a', Just 'x'), (Nothing, Just 'y'), (Nothing, Just 'z')]
zipWithLongest (,) "a" "x" == [(Just 'a', Just 'x')]
zipWithLongest (,) "" "x" == [(Nothing, Just 'x')]

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

Replace a subsequence everywhere it occurs.

replace "el" "_" "Hello Bella" == "H_lo B_la"
replace "el" "e" "Hello"       == "Helo"
replace "" "x" "Hello"         == "xHxexlxlxox"
replace "" "x" ""              == "x"
\xs ys -> replace xs xs ys == ys

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

Merge two lists which are assumed to be ordered.

merge "ace" "bd" == "abcde"
\xs ys -> merge (sort xs) (sort ys) == sort (xs ++ ys)

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

Like merge, but with a custom ordering function.

Data.List.NonEmpty.Extra

Extra functions available in Data.List.NonEmpty.Extra.

(|:) :: [a] -> a -> NonEmpty a infixl 5 Source #

O(n). Append an element to a list.

[1,2,3] |: 4 |> 5 == 1 :| [2,3,4,5]

(|>) :: NonEmpty a -> a -> NonEmpty a infixl 5 Source #

O(n). Append an element to a non-empty list.

(1 :| [2,3]) |> 4 |> 5 == 1 :| [2,3,4,5]

appendl :: NonEmpty a -> [a] -> NonEmpty a Source #

Append a list to a non-empty list.

appendl (1 :| [2,3]) [4,5] == 1 :| [2,3,4,5]

appendr :: [a] -> NonEmpty a -> NonEmpty a Source #

Append a non-empty list to a list.

appendr [1,2,3] (4 :| [5]) == 1 :| [2,3,4,5]

maximum1 :: Ord a => NonEmpty a -> a Source #

The largest element of a non-empty list.

minimum1 :: Ord a => NonEmpty a -> a Source #

The least element of a non-empty list.

maximumBy1 :: (a -> a -> Ordering) -> NonEmpty a -> a Source #

The largest element of a non-empty list with respect to the given comparison function.

minimumBy1 :: (a -> a -> Ordering) -> NonEmpty a -> a Source #

The least element of a non-empty list with respect to the given comparison function.

maximumOn1 :: Ord b => (a -> b) -> NonEmpty a -> a Source #

A version of maximum1 where the comparison is done on some extracted value.

minimumOn1 :: Ord b => (a -> b) -> NonEmpty a -> a Source #

A version of minimum1 where the comparison is done on some extracted value.

Data.Monoid.Extra

Extra functions available in Data.Monoid.Extra.

mwhen :: Monoid a => Bool -> a -> a Source #

Like when, but operating on a Monoid. If the first argument is True returns the second, otherwise returns mempty.

mwhen True  "test" == "test"
mwhen False "test" == ""

Data.Tuple.Extra

Extra functions available in Data.Tuple.Extra.

first :: (a -> a') -> (a, b) -> (a', b) Source #

Update the first component of a pair.

first succ (1,"test") == (2,"test")

second :: (b -> b') -> (a, b) -> (a, b') Source #

Update the second component of a pair.

second reverse (1,"test") == (1,"tset")

(***) :: (a -> a') -> (b -> b') -> (a, b) -> (a', b') infixr 3 Source #

Given two functions, apply one to the first component and one to the second. A specialised version of ***.

(succ *** reverse) (1,"test") == (2,"tset")

(&&&) :: (a -> b) -> (a -> c) -> a -> (b, c) infixr 3 Source #

Given two functions, apply both to a single argument to form a pair. A specialised version of &&&.

(succ &&& pred) 1 == (2,0)

dupe :: a -> (a, a) Source #

Duplicate a single value into a pair.

dupe 12 == (12, 12)

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

Apply a single function to both components of a pair.

both succ (1,2) == (2,3)

firstM :: Functor m => (a -> m a') -> (a, b) -> m (a', b) Source #

Update the first component of a pair.

firstM (\x -> [x-1, x+1]) (1,"test") == [(0,"test"),(2,"test")]

secondM :: Functor m => (b -> m b') -> (a, b) -> m (a, b') Source #

Update the second component of a pair.

secondM (\x -> [reverse x, x]) (1,"test") == [(1,"tset"),(1,"test")]

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

Extract the fst of a triple.

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

Extract the snd of a triple.

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

Extract the final element of a triple.

first3 :: (a -> a') -> (a, b, c) -> (a', b, c) Source #

Update the first component of a triple.

first3 succ (1,1,1) == (2,1,1)

second3 :: (b -> b') -> (a, b, c) -> (a, b', c) Source #

Update the second component of a triple.

second3 succ (1,1,1) == (1,2,1)

third3 :: (c -> c') -> (a, b, c) -> (a, b, c') Source #

Update the third component of a triple.

third3 succ (1,1,1) == (1,1,2)

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

Converts an uncurried function to a curried function.

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

Converts a curried function to a function on a triple.

Data.Version.Extra

Extra functions available in Data.Version.Extra.

readVersion :: Partial => String -> Version Source #

Read a Version or throw an exception.

\x -> readVersion (showVersion x) == x
readVersion "hello" == undefined

Numeric.Extra

Extra functions available in Numeric.Extra.

showDP :: RealFloat a => Int -> a -> String Source #

Show a number to a fixed number of decimal places.

showDP 4 pi == "3.1416"
showDP 0 pi == "3"
showDP 2 3  == "3.00"

intToDouble :: Int -> Double Source #

Specialised numeric conversion, type restricted version of fromIntegral.

intToFloat :: Int -> Float Source #

Specialised numeric conversion, type restricted version of fromIntegral.

floatToDouble :: Float -> Double Source #

Specialised numeric conversion, type restricted version of realToFrac.

doubleToFloat :: Double -> Float Source #

Specialised numeric conversion, type restricted version of realToFrac.

System.Directory.Extra

Extra functions available in System.Directory.Extra.

withCurrentDirectory #

Arguments

:: FilePath

Directory to execute in

-> IO a

Action to be executed

-> IO a 

Run an IO action with the given working directory and restore the original working directory afterwards, even if the given action fails due to an exception.

The operation may fail with the same exceptions as getCurrentDirectory and setCurrentDirectory.

Since: directory-1.2.3.0

createDirectoryPrivate :: String -> IO () Source #

Create a directory with permissions so that only the current user can view it. On Windows this function is equivalent to createDirectory.

listContents :: FilePath -> IO [FilePath] Source #

List the files and directories directly within a directory. Each result will be prefixed by the query directory, and the special directories . and .. will be ignored. Intended as a cleaned up version of getDirectoryContents.

withTempDir $ \dir -> do writeFile (dir </> "test.txt") ""; (== [dir </> "test.txt"]) <$> listContents dir
let touch = mapM_ $ \x -> createDirectoryIfMissing True (takeDirectory x) >> writeFile x ""
let listTest op as bs = withTempDir $ \dir -> do touch $ map (dir </>) as; res <- op dir; pure $ map (drop (length dir + 1)) res == bs
listTest listContents ["bar.txt","foo/baz.txt","zoo"] ["bar.txt","foo","zoo"]

listDirectories :: FilePath -> IO [FilePath] Source #

Like listContents, but only returns the directories in a directory, not the files. Each directory will be prefixed by the query directory.

listTest listDirectories ["bar.txt","foo/baz.txt","zoo"] ["foo"]

listFiles :: FilePath -> IO [FilePath] Source #

Like listContents, but only returns the files in a directory, not other directories. Each file will be prefixed by the query directory.

listTest listFiles ["bar.txt","foo/baz.txt","zoo"] ["bar.txt","zoo"]

listFilesInside :: (FilePath -> IO Bool) -> FilePath -> IO [FilePath] Source #

Like listFilesRecursive, but with a predicate to decide where to recurse into. Typically directories starting with . would be ignored. The initial argument directory will have the test applied to it.

listTest (listFilesInside $ pure . not . isPrefixOf "." . takeFileName)
    ["bar.txt","foo" </> "baz.txt",".foo" </> "baz2.txt", "zoo"] ["bar.txt","zoo","foo" </> "baz.txt"]
listTest (listFilesInside $ const $ pure False) ["bar.txt"] []

listFilesRecursive :: FilePath -> IO [FilePath] Source #

Like listFiles, but goes recursively through all subdirectories. This function will follow symlinks, and if they form a loop, this function will not terminate.

listTest listFilesRecursive ["bar.txt","zoo","foo" </> "baz.txt"] ["bar.txt","zoo","foo" </> "baz.txt"]

System.Info.Extra

Extra functions available in System.Info.Extra.

isWindows :: Bool Source #

Return True on Windows and False otherwise. A runtime version of #ifdef minw32_HOST_OS. Equivalent to os == "mingw32", but: more efficient; doesn't require typing an easily mistypeable string; actually asks about your OS not a library; doesn't bake in 32bit assumptions that are already false. </rant>

isWindows == (os == "mingw32")

isMac :: Bool Source #

Return True on Mac OS X and False otherwise.

System.IO.Extra

Extra functions available in System.IO.Extra.

captureOutput :: IO a -> IO (String, a) Source #

Capture the stdout and stderr of a computation.

captureOutput (print 1) == pure ("1\n",())

withBuffering :: Handle -> BufferMode -> IO a -> IO a Source #

Execute an action with a custom BufferMode, a wrapper around hSetBuffering.

readFileEncoding :: TextEncoding -> FilePath -> IO String Source #

Like readFile, but setting an encoding.

readFileUTF8 :: FilePath -> IO String Source #

Like readFile, but with the encoding utf8.

readFileBinary :: FilePath -> IO String Source #

Like readFile, but for binary files.

readFile' :: FilePath -> IO String #

The readFile' function reads a file and returns the contents of the file as a string. The file is fully read before being returned, as with getContents'.

Since: base-4.15.0.0

readFileEncoding' :: TextEncoding -> FilePath -> IO String Source #

A strict version of readFileEncoding, see readFile' for details.

readFileUTF8' :: FilePath -> IO String Source #

A strict version of readFileUTF8, see readFile' for details.

readFileBinary' :: FilePath -> IO String Source #

A strict version of readFileBinary, see readFile' for details.

writeFileEncoding :: TextEncoding -> FilePath -> String -> IO () Source #

Write a file with a particular encoding.

writeFileUTF8 :: FilePath -> String -> IO () Source #

Write a file with the utf8 encoding.

\s -> withTempFile $ \file -> do writeFileUTF8 file s; fmap (== s) $ readFileUTF8' file

writeFileBinary :: FilePath -> String -> IO () Source #

Write a binary file.

\(ASCIIString s) -> withTempFile $ \file -> do writeFileBinary file s; fmap (== s) $ readFileBinary' file

withTempFile :: (FilePath -> IO a) -> IO a Source #

Create a temporary file in the temporary directory. The file will be deleted after the action completes (provided the file is not still open). The FilePath will not have any file extension, will exist, and will be zero bytes long. If you require a file with a specific name, use withTempDir.

withTempFile doesFileExist == pure True
(doesFileExist =<< withTempFile pure) == pure False
withTempFile readFile' == pure ""

withTempDir :: (FilePath -> IO a) -> IO a Source #

Create a temporary directory inside the system temporary directory. The directory will be deleted after the action completes.

withTempDir doesDirectoryExist == pure True
(doesDirectoryExist =<< withTempDir pure) == pure False
withTempDir listFiles == pure []

newTempFile :: IO (FilePath, IO ()) Source #

Provide a function to create a temporary file, and a way to delete a temporary file. Most users should use withTempFile which combines these operations.

newTempDir :: IO (FilePath, IO ()) Source #

Provide a function to create a temporary directory, and a way to delete a temporary directory. Most users should use withTempDir which combines these operations.

newTempFileWithin :: FilePath -> IO (FilePath, IO ()) Source #

Like newTempFile but using a custom temporary directory.

newTempDirWithin :: FilePath -> IO (FilePath, IO ()) Source #

Like newTempDir but using a custom temporary directory.

fileEq :: FilePath -> FilePath -> IO Bool Source #

Returns True if both files have the same content. Raises an error if either file is missing.

fileEq "does_not_exist1" "does_not_exist2" == undefined
fileEq "does_not_exist" "does_not_exist" == undefined
withTempFile $ \f1 -> fileEq "does_not_exist" f1 == undefined
withTempFile $ \f1 -> withTempFile $ \f2 -> fileEq f1 f2
withTempFile $ \f1 -> withTempFile $ \f2 -> writeFile f1 "a" >> writeFile f2 "a" >> fileEq f1 f2
withTempFile $ \f1 -> withTempFile $ \f2 -> writeFile f1 "a" >> writeFile f2 "b" >> notM (fileEq f1 f2)

System.Process.Extra

Extra functions available in System.Process.Extra.

system_ :: Partial => String -> IO () Source #

A version of system that throws an error if the ExitCode is not ExitSuccess.

systemOutput :: String -> IO (ExitCode, String) Source #

A version of system that also captures the output, both stdout and stderr. Returns a pair of the ExitCode and the output.

systemOutput_ :: Partial => String -> IO String Source #

A version of system that captures the output (both stdout and stderr) and throws an error if the ExitCode is not ExitSuccess.

System.Time.Extra

Extra functions available in System.Time.Extra.

type Seconds = Double Source #

A type alias for seconds, which are stored as Double.

sleep :: Seconds -> IO () Source #

Sleep for a number of seconds.

fmap (round . fst) (duration $ sleep 1) == pure 1

timeout :: Seconds -> IO a -> IO (Maybe a) Source #

A version of timeout that takes Seconds and never overflows the bounds of an Int. In addition, the bug that negative timeouts run for ever has been fixed.

timeout (-3) (print 1) == pure Nothing
timeout 0.1  (print 1) == fmap Just (print 1)
do (t, _) <- duration $ timeout 0.1 $ sleep 1000; print t; pure $ t < 1
timeout 0.1  (sleep 2 >> print 1) == pure Nothing

showDuration :: Seconds -> String Source #

Show a number of seconds, typically a duration, in a suitable manner with reasonable precision for a human.

showDuration 3.435   == "3.44s"
showDuration 623.8   == "10m24s"
showDuration 62003.8 == "17h13m"
showDuration 1e8     == "27777h47m"

offsetTime :: IO (IO Seconds) Source #

Call once to start, then call repeatedly to get the elapsed time since the first call. The time is guaranteed to be monotonic. This function is robust to system time changes.

do f <- offsetTime; xs <- replicateM 10 f; pure $ xs == sort xs

offsetTimeIncrease :: IO (IO Seconds) Source #

Deprecated: Use offsetTime instead, which is guaranteed to always increase.

A synonym for offsetTime.

duration :: MonadIO m => m a -> m (Seconds, a) Source #

Record how long a computation takes in Seconds.

do (a,_) <- duration $ sleep 1; pure $ a >= 1 && a <= 1.5