extra-0.3.2: Extra functions I use.

Safe HaskellNone

Extra

Contents

Description

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 aSource

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.

setNumCapabilities :: Int -> IO ()

forkFinally :: IO a -> (Either SomeException a -> IO ()) -> IO ThreadId

data Lock Source

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

 lock <- newLock
 let output = withLock . 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 LockSource

Create a newLock.

withLock :: Lock -> IO a -> IO aSource

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 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 aSource

Read the current value of the Var.

modifyVar :: Var a -> (a -> IO (a, b)) -> IO bSource

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

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

Modify a Var, a restricted version of modifyVar.

withVar :: Var a -> (a -> IO b) -> IO bSource

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 :: Barrier a -> a -> IO ()Source

Write a value into the Barrier, releasing anyone at waitBarrier. Any subsequent attempts to signal the Barrier will be silently ignored.

waitBarrier :: Barrier a -> IO aSource

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.

retry :: Int -> IO a -> IO aSource

Retry an operation at most N times (N must be positive).

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

showException :: Show e => e -> IO StringSource

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 StringSource

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

 stringException ("test" ++ undefined)            == return "test<Exception>"
 stringException ("test" ++ undefined ++ "hello") == return "test<Exception>"
 stringException "test"                           == return "test"

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

Ignore any exceptions thrown by the action.

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

catch_ :: IO a -> (SomeException -> IO a) -> IO aSource

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

handle_ :: (SomeException -> IO a) -> IO a -> IO aSource

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 aSource

Like catch_ but for catchJust

handleJust_ :: (SomeException -> Maybe b) -> (b -> IO a) -> IO a -> IO aSource

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 aSource

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 $ return "")

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

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.

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

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

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

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

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.

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

A version of mapMaybe that works with a monadic predicate.

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

A looping operation, 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.

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 aSource

Like if, but where the test can be monadic.

notM :: Functor m => m Bool -> m BoolSource

Like not, but where the test can be monadic.

(||^) :: Monad m => m Bool -> m Bool -> m BoolSource

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 BoolSource

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 BoolSource

A version of or lifted to a moand. 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 BoolSource

A version of and lifted to a moand. 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 BoolSource

A version of any lifted to a moand. 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 BoolSource

A version of all lifted to a moand. 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)

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.

Data.Either.Extra

Extra functions available in Data.Either.Extra.

isLeft :: Either l r -> BoolSource

Test if an Either value is the Left constructor. Provided as standard with GHC 7.8 and above.

isRight :: Either l r -> BoolSource

Test if an Either value is the Right constructor. Provided as standard with GHC 7.8 and above.

fromLeft :: Either l r -> lSource

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 :: Either l r -> rSource

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

fromEither :: Either a a -> aSource

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

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

Data.IORef.Extra

Extra functions available in Data.IORef.Extra.

modifyIORef' :: IORef a -> (a -> a) -> IO ()

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

Evaluates the value before calling writeIORef

atomicModifyIORef' :: IORef a -> (a -> (a, b)) -> IO b

atomicWriteIORef :: IORef a -> a -> IO ()

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

Evaluates the value before calling atomicWriteIORef

Data.List.Extra

Extra functions available in Data.List.Extra.

lower :: String -> StringSource

Documentation about lowercase

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

upper :: String -> StringSource

trim :: String -> StringSource

trimStart :: String -> StringSource

trimEnd :: String -> StringSource

dropAround :: (a -> Bool) -> [a] -> [a]Source

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

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

list :: b -> (a -> [a] -> b) -> [a] -> bSource

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

uncons :: [a] -> Maybe (a, [a])Source

If the list is empty returns Nothing, otherwise returns the head and the tail.

 uncons "test" == Just ('t',"est")
 uncons ""     == Nothing
 \xs -> uncons xs == if null xs then Nothing else Just (head xs, tail 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)

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

groupSortOn :: Ord a => (k -> a) -> [(k, v)] -> [(k, [v])]Source

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

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

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

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

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

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

for :: [a] -> (a -> b) -> [b]Source

Flipped version of map.

 for [1,2,3] (+1) == [2,3,4]

disjoint :: Eq a => [a] -> [a] -> BoolSource

Are two lists disjoint, with no elements in common.

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

allSame :: Eq a => [a] -> BoolSource

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] -> BoolSource

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)

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

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

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")

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-> spanEnd f xs == swap (both reverse (span f (reverse xs)))

dropWhileEnd :: (a -> Bool) -> [a] -> [a]

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

A version of dropWhileEnd but with different strictness properties. Often outperforms if the list is short or the test is expensive.

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

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

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

Examples:

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

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

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

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

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

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

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

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

firstJust :: (a -> Maybe b) -> [a] -> Maybe bSource

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.

Examples:

 breakOn "::" "a::b::c" == ("a", "::b::c")
 breakOn "/" "foobar"   == ("foobar", "")

Laws:

 \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 :: 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.

Examples:

 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"    ""                 == [""]

and

 \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. eg.

 split (=='a') "aabbaca" == ["","","bb","c",""]
 split (=='a') ""        == [""]

chunksOf :: 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

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.

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

Update the second component of a pair.

(***) :: (a -> a') -> (b -> b') -> (a, b) -> (a', b')Source

(&&&) :: (a -> b) -> (a -> c) -> a -> (b, c)Source

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

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

fst3 :: (a, b, c) -> aSource

snd3 :: (a, b, c) -> bSource

thd3 :: (a, b, c) -> cSource

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

Update the first component of a triple.

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

Update the second component of a triple.

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

Update the third component of a triple.

dupe3 :: a -> (a, a, a)Source

both3 :: (a -> b) -> (a, a, a) -> (b, b, b)Source

Numeric.Extra

Extra functions available in Numeric.Extra.

showDP :: RealFloat a => Int -> a -> StringSource

Show a number to a number of decimal places.

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

intToDouble :: Int -> DoubleSource

Specialised numeric conversion.

intToFloat :: Int -> FloatSource

Specialised numeric conversion.

floatToDouble :: Float -> DoubleSource

Specialised numeric conversion.

doubleToFloat :: Double -> FloatSource

Specialised numeric conversion.

System.Directory.Extra

Extra functions available in System.Directory.Extra.

withCurrentDirectory :: FilePath -> IO a -> IO aSource

Remember that the current directory is a global variable, so calling this function multithreaded is almost certain to go wrong. Avoid changing the dir if you can.

getDirectoryContentsRecursive :: FilePath -> IO [FilePath]Source

Find all the files within a directory, including recursively. Looks through all folders, including those beginning with ..

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.

System.Environment.Extra

Extra functions available in System.Environment.Extra.

getExecutablePath :: IO FilePath

lookupEnv :: String -> IO (Maybe String)

System.Info.Extra

Extra functions available in System.Info.Extra.

System.IO.Extra

Extra functions available in System.IO.Extra.

readFileEncoding :: TextEncoding -> FilePath -> IO StringSource

readFileUTF8 :: FilePath -> IO StringSource

readFileBinary :: FilePath -> IO StringSource

readFile' :: FilePath -> IO StringSource

readFileEncoding' :: TextEncoding -> FilePath -> IO StringSource

readFileUTF8' :: FilePath -> IO StringSource

readFileBinary' :: FilePath -> IO StringSource

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

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

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

withTempFile :: (FilePath -> IO a) -> IO aSource

withTempDir :: (FilePath -> IO a) -> IO aSource

newTempFile :: (IO FilePath, FilePath -> IO ())Source

newTempDir :: (IO FilePath, FilePath -> IO ())Source

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

Capture the stdout and stderr of a computation.

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

withBuffering :: Handle -> BufferMode -> IO a -> IO aSource

System.Process.Extra

Extra functions available in System.Process.Extra.

system_ :: String -> IO ()Source

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

systemOutput_ :: String -> IO StringSource

System.Time.Extra

Extra functions available in System.Time.Extra.

type Seconds = DoubleSource

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) == return 1

subtractTime :: UTCTime -> UTCTime -> SecondsSource

Calculate the difference between two times in seconds. Usually the first time will be the end of an event, and the second time will be the beginning.

 \a b -> a > b ==> subtractTime a b > 0

showDuration :: Seconds -> StringSource

Show a number of seconds, typically a duration, in a suitable manner with responable 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. Values will usually increase, unless the system clock is updated (if you need the guarantee, see offsetTimeIncrease).

offsetTimeIncrease :: IO (IO Seconds)Source

Like offsetTime, but results will never decrease (though they may stay the same).

 do f <- offsetTimeIncrease; xs <- replicateM 10 f; return $ xs == sort xs

duration :: IO a -> IO (Seconds, a)Source

Record how long a computation takes in Seconds.