Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
).
- getNumCapabilities :: IO Int
- setNumCapabilities :: Int -> IO ()
- withNumCapabilities :: Int -> IO a -> IO a
- forkFinally :: IO a -> (Either SomeException a -> IO ()) -> IO ThreadId
- once :: IO a -> IO (IO a)
- onceFork :: IO a -> IO (IO a)
- data Lock
- newLock :: IO Lock
- withLock :: Lock -> IO a -> IO a
- withLockTry :: Lock -> IO a -> IO (Maybe a)
- data Var a
- newVar :: a -> IO (Var a)
- readVar :: Var a -> IO a
- writeVar :: Var a -> a -> IO ()
- modifyVar :: Var a -> (a -> IO (a, b)) -> IO b
- modifyVar_ :: Var a -> (a -> IO a) -> IO ()
- withVar :: Var a -> (a -> IO b) -> IO b
- data Barrier a
- newBarrier :: IO (Barrier a)
- signalBarrier :: Barrier a -> a -> IO ()
- waitBarrier :: Barrier a -> IO a
- waitBarrierMaybe :: Barrier a -> IO (Maybe a)
- retry :: Int -> IO a -> IO a
- retryBool :: Exception e => (e -> Bool) -> Int -> IO a -> IO a
- errorWithoutStackTrace :: String -> a
- showException :: Show e => e -> IO String
- stringException :: String -> IO String
- errorIO :: String -> IO a
- displayException :: Exception e => e -> String
- ignore :: IO () -> IO ()
- catch_ :: IO a -> (SomeException -> IO a) -> IO a
- handle_ :: (SomeException -> IO a) -> IO a -> IO a
- try_ :: IO a -> IO (Either SomeException a)
- catchJust_ :: (SomeException -> Maybe b) -> IO a -> (b -> IO a) -> IO a
- handleJust_ :: (SomeException -> Maybe b) -> (b -> IO a) -> IO a -> IO a
- tryJust_ :: (SomeException -> Maybe b) -> IO a -> IO (Either b a)
- catchBool :: Exception e => (e -> Bool) -> IO a -> (e -> IO a) -> IO a
- handleBool :: Exception e => (e -> Bool) -> (e -> IO a) -> IO a -> IO a
- tryBool :: Exception e => (e -> Bool) -> IO a -> IO (Either e a)
- whenJust :: Applicative m => Maybe a -> (a -> m ()) -> m ()
- whenJustM :: Monad m => m (Maybe a) -> (a -> m ()) -> m ()
- unit :: m () -> m ()
- maybeM :: Monad m => m b -> (a -> m b) -> m (Maybe a) -> m b
- eitherM :: Monad m => (a -> m c) -> (b -> m c) -> m (Either a b) -> m c
- loopM :: Monad m => (a -> m (Either a b)) -> a -> m b
- whileM :: Monad m => m Bool -> m ()
- partitionM :: Monad m => (a -> m Bool) -> [a] -> m ([a], [a])
- concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b]
- concatForM :: Monad m => [a] -> (a -> m [b]) -> m [b]
- mconcatMapM :: (Monad m, Monoid b) => (a -> m b) -> [a] -> m b
- mapMaybeM :: Monad m => (a -> m (Maybe b)) -> [a] -> m [b]
- findM :: Monad m => (a -> m Bool) -> [a] -> m (Maybe a)
- firstJustM :: Monad m => (a -> m (Maybe b)) -> [a] -> m (Maybe b)
- whenM :: Monad m => m Bool -> m () -> m ()
- unlessM :: Monad m => m Bool -> m () -> m ()
- ifM :: Monad m => m Bool -> m a -> m a -> m a
- notM :: Functor m => m Bool -> m Bool
- (||^) :: Monad m => m Bool -> m Bool -> m Bool
- (&&^) :: Monad m => m Bool -> m Bool -> m Bool
- orM :: Monad m => [m Bool] -> m Bool
- andM :: Monad m => [m Bool] -> m Bool
- anyM :: Monad m => (a -> m Bool) -> [a] -> m Bool
- allM :: Monad m => (a -> m Bool) -> [a] -> m Bool
- isLeft :: Either a b -> Bool
- isRight :: Either a b -> Bool
- fromLeft :: a -> Either a b -> a
- fromRight :: b -> Either a b -> b
- fromEither :: Either a a -> a
- fromLeft' :: Either l r -> l
- fromRight' :: Either l r -> r
- eitherToMaybe :: Either a b -> Maybe b
- maybeToEither :: a -> Maybe b -> Either a b
- modifyIORef' :: IORef a -> (a -> a) -> IO ()
- writeIORef' :: IORef a -> a -> IO ()
- atomicModifyIORef' :: IORef a -> (a -> (a, b)) -> IO b
- atomicWriteIORef :: IORef a -> a -> IO ()
- atomicWriteIORef' :: IORef a -> a -> IO ()
- lower :: String -> String
- upper :: String -> String
- trim :: String -> String
- trimStart :: String -> String
- trimEnd :: String -> String
- word1 :: String -> (String, String)
- line1 :: String -> (String, String)
- dropEnd :: Int -> [a] -> [a]
- takeEnd :: Int -> [a] -> [a]
- splitAtEnd :: Int -> [a] -> ([a], [a])
- breakEnd :: (a -> Bool) -> [a] -> ([a], [a])
- spanEnd :: (a -> Bool) -> [a] -> ([a], [a])
- dropWhileEnd :: (a -> Bool) -> [a] -> [a]
- dropWhileEnd' :: (a -> Bool) -> [a] -> [a]
- takeWhileEnd :: (a -> Bool) -> [a] -> [a]
- stripSuffix :: Eq a => [a] -> [a] -> Maybe [a]
- stripInfix :: Eq a => [a] -> [a] -> Maybe ([a], [a])
- stripInfixEnd :: Eq a => [a] -> [a] -> Maybe ([a], [a])
- wordsBy :: (a -> Bool) -> [a] -> [[a]]
- linesBy :: (a -> Bool) -> [a] -> [[a]]
- breakOn :: Eq a => [a] -> [a] -> ([a], [a])
- breakOnEnd :: Eq a => [a] -> [a] -> ([a], [a])
- splitOn :: Eq a => [a] -> [a] -> [[a]]
- split :: (a -> Bool) -> [a] -> [[a]]
- chunksOf :: Int -> [a] -> [[a]]
- list :: b -> (a -> [a] -> b) -> [a] -> b
- uncons :: [a] -> Maybe (a, [a])
- unsnoc :: [a] -> Maybe ([a], a)
- cons :: a -> [a] -> [a]
- snoc :: [a] -> a -> [a]
- drop1 :: [a] -> [a]
- mconcatMap :: Monoid b => (a -> b) -> [a] -> b
- groupSort :: Ord k => [(k, v)] -> [(k, [v])]
- groupSortOn :: Ord b => (a -> b) -> [a] -> [[a]]
- groupSortBy :: (a -> a -> Ordering) -> [a] -> [[a]]
- nubOrd :: Ord a => [a] -> [a]
- nubOrdBy :: (a -> a -> Ordering) -> [a] -> [a]
- nubOrdOn :: Ord b => (a -> b) -> [a] -> [a]
- nubOn :: Eq b => (a -> b) -> [a] -> [a]
- groupOn :: Eq b => (a -> b) -> [a] -> [[a]]
- sortOn :: Ord b => (a -> b) -> [a] -> [a]
- disjoint :: Eq a => [a] -> [a] -> Bool
- allSame :: Eq a => [a] -> Bool
- anySame :: Eq a => [a] -> Bool
- repeatedly :: ([a] -> (b, [a])) -> [a] -> [b]
- for :: [a] -> (a -> b) -> [b]
- firstJust :: (a -> Maybe b) -> [a] -> Maybe b
- concatUnzip :: [([a], [b])] -> ([a], [b])
- concatUnzip3 :: [([a], [b], [c])] -> ([a], [b], [c])
- zipFrom :: Enum a => a -> [b] -> [(a, b)]
- zipWithFrom :: Enum a => (a -> b -> c) -> a -> [b] -> [c]
- replace :: Eq a => [a] -> [a] -> [a] -> [a]
- merge :: Ord a => [a] -> [a] -> [a]
- mergeBy :: (a -> a -> Ordering) -> [a] -> [a] -> [a]
- first :: (a -> a') -> (a, b) -> (a', b)
- second :: (b -> b') -> (a, b) -> (a, b')
- (***) :: (a -> a') -> (b -> b') -> (a, b) -> (a', b')
- (&&&) :: (a -> b) -> (a -> c) -> a -> (b, c)
- dupe :: a -> (a, a)
- both :: (a -> b) -> (a, a) -> (b, b)
- fst3 :: (a, b, c) -> a
- snd3 :: (a, b, c) -> b
- thd3 :: (a, b, c) -> c
- typeRep :: Typeable k a => proxy a -> TypeRep
- data a :~: b :: k -> k -> * where
- data Proxy t :: k -> * = Proxy
- makeVersion :: [Int] -> Version
- readVersion :: String -> Version
- showDP :: RealFloat a => Int -> a -> String
- intToDouble :: Int -> Double
- intToFloat :: Int -> Float
- floatToDouble :: Float -> Double
- doubleToFloat :: Double -> Float
- withCurrentDirectory :: FilePath -> IO a -> IO a
- createDirectoryPrivate :: String -> IO ()
- listContents :: FilePath -> IO [FilePath]
- listFiles :: FilePath -> IO [FilePath]
- listFilesInside :: (FilePath -> IO Bool) -> FilePath -> IO [FilePath]
- listFilesRecursive :: FilePath -> IO [FilePath]
- getExecutablePath :: IO FilePath
- lookupEnv :: String -> IO (Maybe String)
- isWindows :: Bool
- isMac :: Bool
- captureOutput :: IO a -> IO (String, a)
- withBuffering :: Handle -> BufferMode -> IO a -> IO a
- readFileEncoding :: TextEncoding -> FilePath -> IO String
- readFileUTF8 :: FilePath -> IO String
- readFileBinary :: FilePath -> IO String
- readFile' :: FilePath -> IO String
- readFileEncoding' :: TextEncoding -> FilePath -> IO String
- readFileUTF8' :: FilePath -> IO String
- readFileBinary' :: FilePath -> IO String
- writeFileEncoding :: TextEncoding -> FilePath -> String -> IO ()
- writeFileUTF8 :: FilePath -> String -> IO ()
- writeFileBinary :: FilePath -> String -> IO ()
- withTempFile :: (FilePath -> IO a) -> IO a
- withTempDir :: (FilePath -> IO a) -> IO a
- newTempFile :: IO (FilePath, IO ())
- newTempDir :: IO (FilePath, IO ())
- fileEq :: FilePath -> FilePath -> IO Bool
- system_ :: String -> IO ()
- systemOutput :: String -> IO (ExitCode, String)
- systemOutput_ :: String -> IO String
- type Seconds = Double
- sleep :: Seconds -> IO ()
- timeout :: Seconds -> IO a -> IO (Maybe a)
- subtractTime :: UTCTime -> UTCTime -> Seconds
- showDuration :: Seconds -> String
- offsetTime :: IO (IO Seconds)
- offsetTimeIncrease :: IO (IO Seconds)
- duration :: IO a -> IO (Seconds, a)
Control.Concurrent.Extra
Extra functions available in Control.Concurrent.Extra
.
Returns the number of Haskell threads that can run truly
simultaneously (on separate physical processors) at any given time. To change
this value, use setNumCapabilities
.
Since: 4.4.0.0
setNumCapabilities :: Int -> IO ()
Set the number of Haskell threads that can run truly simultaneously
(on separate physical processors) at any given time. The number
passed to forkOn
is interpreted modulo this value. The initial
value is given by the +RTS -N
runtime flag.
This is also the number of threads that will participate in parallel garbage collection. It is strongly recommended that the number of capabilities is not set larger than the number of physical processor cores, and it may often be beneficial to leave one or more cores free to avoid contention with other processes in the machine.
Since: 4.5.0.0
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.
forkFinally :: IO a -> (Either SomeException a -> IO ()) -> IO ThreadId
fork a thread and call the supplied function when the thread is about to terminate, with an exception or a returned value. The function is called with asynchronous exceptions masked.
forkFinally action and_then = mask $ \restore -> forkIO $ try (restore action) >>= and_then
This function is useful for informing the parent when a child terminates, for example.
Since: 4.6.0.0
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) == return () \(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
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.
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.
modifyVar :: Var a -> (a -> IO (a, b)) -> IO b Source
Modify a Var
producing a new value and a return result.
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 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
.
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 :: String -> a Source
A variant of error
that does not produce a stack trace.
showException :: Show e => e -> IO String Source
Show a value, but if the result contains exceptions, produce
<Exception>
. Defined as
.
Particularly useful for printing exceptions to users, remembering that exceptions
can themselves contain undefined values.stringException
. show
stringException :: String -> IO String Source
Fully evaluate an input String. If the String contains embedded exceptions it will produce <Exception>
.
stringException "test" == return "test" stringException ("test" ++ undefined) == return "test<Exception>" stringException ("test" ++ undefined ++ "hello") == return "test<Exception>" stringException ['t','e','s','t',undefined] == return "test<Exception>"
errorIO :: String -> IO a Source
Like error, but in the IO
monad.
Note that while fail
in IO
raises an IOException
, this function raises an ErrorCall
exception.
try (errorIO "Hello") == return (Left (ErrorCall "Hello"))
displayException :: Exception e => e -> String
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 a Source
A version of catch
without the Exception
context, restricted to SomeException
,
so catches all exceptions.
catchJust_ :: (SomeException -> Maybe b) -> IO a -> (b -> IO a) -> IO a Source
handleJust_ :: (SomeException -> Maybe b) -> (b -> IO a) -> IO a -> IO a Source
Like catch_
but for handleJust
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 $ return "")
Control.Monad.Extra
Extra functions available in Control.Monad.Extra
.
whenJust :: Applicative m => Maybe a -> (a -> m ()) -> m () Source
whenJustM :: Monad m => m (Maybe a) -> (a -> m ()) -> m () Source
Like whenJust
, but where the test can be monadic.
The identity function which requires the inner argument to be ()
. Useful for functions
with overloaded return types.
\(x :: Maybe ()) -> unit x == x
eitherM :: Monad m => (a -> m c) -> (b -> m c) -> m (Either a b) -> m c Source
Monadic generalisation of either
.
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.
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
.
Return True
if the given value is a Left
-value, False
otherwise.
Examples
Basic usage:
>>>
isLeft (Left "foo")
True>>>
isLeft (Right 3)
False
Assuming a Left
value signifies some sort of error, we can use
isLeft
to write a very simple error-reporting function that does
absolutely nothing in the case of success, and outputs "ERROR" if
any error occurred.
This example shows how isLeft
might be used to avoid pattern
matching when one does not care about the value contained in the
constructor:
>>>
import Control.Monad ( when )
>>>
let report e = when (isLeft e) $ putStrLn "ERROR"
>>>
report (Right 1)
>>>
report (Left "parse error")
ERROR
Since: 4.7.0.0
Return True
if the given value is a Right
-value, False
otherwise.
Examples
Basic usage:
>>>
isRight (Left "foo")
False>>>
isRight (Right 3)
True
Assuming a Left
value signifies some sort of error, we can use
isRight
to write a very simple reporting function that only
outputs "SUCCESS" when a computation has succeeded.
This example shows how isRight
might be used to avoid pattern
matching when one does not care about the value contained in the
constructor:
>>>
import Control.Monad ( when )
>>>
let report e = when (isRight e) $ putStrLn "SUCCESS"
>>>
report (Left "parse error")
>>>
report (Right 1)
SUCCESS
Since: 4.7.0.0
fromLeft :: a -> Either a b -> a Source
Return the contents of a Left
-value or a default value otherwise.
fromLeft 1 (Left 3) == 3 fromLeft 1 (Right "foo") == 1
fromRight :: b -> Either a b -> b Source
Return the contents of a Right
-value or a default value otherwise.
fromRight 1 (Right 3) == 3 fromRight 1 (Left "foo") == 1
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
fromRight' :: 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
maybeToEither :: a -> Maybe b -> Either a b Source
Data.IORef.Extra
Extra functions available in Data.IORef.Extra
.
modifyIORef' :: IORef a -> (a -> a) -> IO ()
Strict version of modifyIORef
Since: 4.6.0.0
writeIORef' :: IORef a -> a -> IO () Source
Evaluates the value before calling writeIORef
.
atomicModifyIORef' :: IORef a -> (a -> (a, b)) -> IO b
Strict version of atomicModifyIORef
. This forces both the value stored
in the IORef
as well as the value returned.
Since: 4.6.0.0
atomicWriteIORef :: IORef a -> a -> IO ()
Variant of writeIORef
with the "barrier to reordering" property that
atomicModifyIORef
has.
Since: 4.6.0.0
atomicWriteIORef' :: IORef a -> a -> IO () Source
Evaluates the value before calling atomicWriteIORef
.
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 "" == ""
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 perserve 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")
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
returns a split where the second element tries to
contain splitAtEnd
n xsn
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]
The dropWhileEnd
function drops the largest suffix of a list
in which the given predicate holds for all elements. For example:
dropWhileEnd isSpace "foo\n" == "foo" dropWhileEnd isSpace "foo bar" == "foo bar" dropWhileEnd isSpace ("foo\n" ++ undefined) == "foo" ++ undefined
Since: 4.5.0.0
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 string if its suffix matches the entire first string.
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")
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 patch, 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 :: 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 :: 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
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
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)
Equivalent to drop 1
, but likely to be faster and a single lexeme.
drop1 "" == "" drop1 "test" == "est" \xs -> drop 1 xs == drop1 xs
mconcatMap :: Monoid b => (a -> b) -> [a] -> b Source
groupSortOn :: Ord b => (a -> b) -> [a] -> [[a]] Source
groupSortBy :: (a -> a -> Ordering) -> [a] -> [[a]] Source
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"]
groupOn :: Eq b => (a -> b) -> [a] -> [[a]] Source
A version of group
where the equality is done on some extracted value.
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.
Since: 4.8.0.0
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
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.
\xs -> repeatedly (splitAt 3) xs == chunksOf 3 xs \xs -> repeatedly word1 (trim xs) == words xs \xs -> repeatedly line1 xs == lines xs
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
concatUnzip3 :: [([a], [b], [c])] -> ([a], [b], [c]) Source
zipFrom :: Enum a => a -> [b] -> [(a, b)] Source
zip
against an enumeration.
Never truncates the output - raises an error if the enumeration runs out.
\i xs -> zip [i..] xs == zipFrom i xs zipFrom False [1..3] == undefined
zipWithFrom :: Enum a => (a -> b -> c) -> a -> [b] -> [c] Source
zipFrom
generalised to any combining operation.
\i xs -> zipWithFrom (,) i xs == zipFrom i xs
replace :: Eq a => [a] -> [a] -> [a] -> [a] Source
Replace a subsequence everywhere it occurs. The first argument must not be the empty list.
replace "el" "_" "Hello Bella" == "H_lo B_la" replace "el" "e" "Hello" == "Helo" replace "" "e" "Hello" == undefined \xs ys -> not (null xs) ==> 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.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)
both :: (a -> b) -> (a, a) -> (b, b) Source
Apply a single function to both components of a pair.
both succ (1,2) == (2,3)
Data.Typeable.Extra
Extra functions available in Data.Typeable.Extra
.
typeRep :: Typeable k a => proxy a -> TypeRep
Takes a value of type a
and returns a concrete representation
of that type.
Since: 4.7.0.0
data a :~: b :: k -> k -> * where infix 4
Propositional equality. If a :~: b
is inhabited by some terminating
value, then the type a
is the same as the type b
. To use this equality
in practice, pattern-match on the a :~: b
to get out the Refl
constructor;
in the body of the pattern-match, the compiler knows that a ~ b
.
Since: 4.7.0.0
data Proxy t :: k -> *
A concrete, poly-kinded proxy type
Monad (Proxy *) | |
Functor (Proxy *) | |
Applicative (Proxy *) | |
Foldable (Proxy *) | |
Traversable (Proxy *) | |
Bounded (Proxy k s) | |
Enum (Proxy k s) | |
Eq (Proxy k s) | |
Ord (Proxy k s) | |
Read (Proxy k s) | |
Show (Proxy k s) | |
Ix (Proxy k s) | |
Generic (Proxy * t) | |
Monoid (Proxy k s) | |
type Rep (Proxy k t) = D1 D1Proxy (C1 C1_0Proxy U1) |
Data.Version.Extra
Extra functions available in Data.Version.Extra
.
makeVersion :: [Int] -> Version
Construct tag-less Version
Since: 4.8.0.0
readVersion :: 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 :: FilePath -> IO a -> IO a Source
Set the current directory, perform an operation, then change back. Remember that the current directory is a global variable, so calling this function multithreaded is almost certain to go wrong. Avoid changing the current directory if you can.
withTempDir $ \dir -> do writeFile (dir </> "foo.txt") ""; withCurrentDirectory dir $ doesFileExist "foo.txt"
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; return $ map (drop (length dir + 1)) res == bs listTest listContents ["bar.txt","foo/baz.txt","zoo"] ["bar.txt","foo","zoo"]
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 $ return . not . isPrefixOf "." . takeFileName) ["bar.txt","foo" </> "baz.txt",".foo" </> "baz2.txt", "zoo"] ["bar.txt","zoo","foo" </> "baz.txt"] listTest (listFilesInside $ const $ return 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.Environment.Extra
Extra functions available in System.Environment.Extra
.
getExecutablePath :: IO FilePath
Returns the absolute pathname of the current executable.
Note that for scripts and interactive sessions, this is the path to the interpreter (e.g. ghci.)
Since: 4.6.0.0
lookupEnv :: String -> IO (Maybe String)
Return the value of the environment variable var
, or Nothing
if
there is no such value.
For POSIX users, this is equivalent to getEnv
.
Since: 4.6.0.0
System.Info.Extra
Extra functions available in System.Info.Extra
.
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")
System.IO.Extra
Extra functions available in System.IO.Extra
.
captureOutput :: IO a -> IO (String, a) Source
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.
readFile' :: FilePath -> IO String Source
A strict version of readFile
. When the string is produced, the entire
file will have been read into memory and the file handle will have been closed.
Closing the file handle does not rely on the garbage collector.
\(filter isHexDigit -> s) -> fmap (== s) $ withTempFile $ \file -> do writeFile file s; readFile' file
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.
\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 == return True (doesFileExist =<< withTempFile return) == return False withTempFile readFile' == return ""
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 == return True (doesDirectoryExist =<< withTempDir return) == return False withTempDir listFiles == return []
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.
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_ :: String -> IO () Source
A version of system
that throws an error if the ExitCode
is not ExitSuccess
.
systemOutput_ :: 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
.
sleep :: Seconds -> IO () Source
Sleep for a number of seconds.
fmap (round . fst) (duration $ sleep 1) == return 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) == return Nothing timeout 0.1 (print 1) == fmap Just (print 1) do (t, _) <- duration $ timeout 0.1 $ sleep 1000; print t; return $ t < 1 timeout 0.1 (sleep 2 >> print 1) == return Nothing
subtractTime :: UTCTime -> UTCTime -> Seconds Source
Deprecated: Function is being retired - use diffUTCTime directly.
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.
showDuration :: Seconds -> String Source
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. The time is guaranteed to be monotonic. This function is robust to system time changes.
do f <- offsetTime; xs <- replicateM 10 f; return $ xs == sort xs
offsetTimeIncrease :: IO (IO Seconds) Source
Deprecated: Use offsetTime instead, which is guaranteed to always increase.
A synonym for offsetTime
.