lambdabot-utils-4.2: Utility libraries for the advanced IRC bot, LambdabotSource codeContentsIndex
Lambdabot.Util
Description
String and other utilities
Synopsis
concatWith :: [a] -> [[a]] -> [a]
split :: Eq a => [a] -> [a] -> [[a]]
split2 :: Char -> Int -> String -> [String]
breakOnGlue :: Eq a => [a] -> [a] -> ([a], [a])
clean :: Char -> [Char]
dropSpace :: [Char] -> [Char]
dropSpaceEnd :: [Char] -> [Char]
dropNL :: [Char] -> [Char]
snoc :: a -> [a] -> [a]
after :: String -> String -> String
splitFirstWord :: String -> (String, String)
firstWord :: String -> String
debugStr :: MonadIO m => String -> m ()
debugStrLn :: MonadIO m => [Char] -> m ()
lowerCaseString :: String -> String
upperCaseString :: String -> String
upperize :: String -> String
lowerize :: String -> String
quote :: String -> String
timeStamp :: ClockTime -> String
listToStr :: String -> [String] -> String
showWidth :: Int -> Int -> String
listToMaybeWith :: ([a] -> b) -> [a] -> Maybe b
listToMaybeAll :: [a] -> Maybe [a]
getRandItem :: RandomGen g => [a] -> g -> (a, g)
stdGetRandItem :: [a] -> IO a
randomElem :: [a] -> IO a
showClean :: Show a => [a] -> String
expandTab :: String -> String
closest :: String -> [String] -> (Int, String)
closests :: String -> [String] -> (Int, [String])
withMWriter :: MVar a -> (a -> (a -> IO ()) -> IO b) -> IO b
parIO :: IO a -> IO a -> IO a
timeout :: Int -> IO a -> IO (Maybe a)
choice :: (r -> Bool) -> (r -> a) -> (r -> a) -> r -> a
arePrefixesWithSpaceOf :: [String] -> String -> Bool
arePrefixesOf :: [String] -> String -> Bool
(</>) :: FilePath -> FilePath -> FilePath
(<.>) :: FilePath -> FilePath -> FilePath
(<+>) :: FilePath -> FilePath -> FilePath
(<>) :: FilePath -> FilePath -> FilePath
(<$>) :: FilePath -> FilePath -> FilePath
basename :: FilePath -> FilePath
dirname :: FilePath -> FilePath
dropSuffix :: FilePath -> FilePath
joinPath :: FilePath -> FilePath -> FilePath
addList :: Ord k => [(k, a)] -> Map k a -> Map k a
mapMaybeMap :: Ord k => (a -> Maybe b) -> Map k a -> Map k b
insertUpd :: Ord k => (a -> a) -> k -> a -> Map k a -> Map k a
pprKeys :: Show k => Map k a -> String
isLeft :: Either a b -> Bool
isRight :: Either a b -> Bool
unEither :: Either a a -> a
io :: MonadIO m => IO a -> m a
random :: MonadIO m => [a] -> m a
insult :: [String]
confirmation :: [String]
Documentation
concatWithSource
::
=> [a]Glue to join with
-> [[a]]Elements to glue together
-> [a]Result: glued-together list

concatWith joins lists with the given glue elements. Example:

 concatWith ", " ["one","two","three"] ===> "one, two, three"
splitSource
:: Eq a
=> [a]Glue that holds pieces together
-> [a]List to break into pieces
-> [[a]]Result: list of pieces

Split a list into pieces that were held together by glue. Example:

 split ", " "one, two, three" ===> ["one","two","three"]
split2 :: Char -> Int -> String -> [String]Source
breakOnGlueSource
:: Eq a
=> [a]Glue that holds pieces together
-> [a]List from which to break off a piece
-> ([a], [a])Result: (first piece, glue ++ rest of list)

Break off the first piece of a list held together by glue, leaving the glue attached to the remainder of the list. Example: Like break, but works with a [a] match.

 breakOnGlue ", " "one, two, three" ===> ("one", ", two, three")
clean :: Char -> [Char]Source
clean takes a Char x and returns [x] unless the Char is '\CR' in case [] is returned.
dropSpace :: [Char] -> [Char]Source

dropSpace takes as input a String and strips spaces from the prefix as well as the suffix of the String. Example:

 dropSpace "   abc  " ===> "abc"
dropSpaceEnd :: [Char] -> [Char]Source
Drop space from the end of the string
dropNL :: [Char] -> [Char]Source
snocSource
::
=> aElement to be added
-> [a]List to add to
-> [a]Result: List ++ [Element]

Reverse cons. Add an element to the back of a list. Example:

 snoc 3 [2, 1] ===> [2, 1, 3]
afterSource
:: StringPrefix string
-> StringData string
-> StringResult: Data string with Prefix string and excess whitespace removed

after takes 2 strings, called the prefix and data. A necessary precondition is that

 Data.List.isPrefixOf prefix data ===> True

after returns a string based on data, where the prefix has been removed as well as any excess space characters. Example:

 after "This is" "This is a string" ===> "a string"
splitFirstWordSource
:: StringString to be broken
-> (String, String)

Break a String into it's first word, and the rest of the string. Example:

 split_first_word "A fine day" ===> ("A", "fine day)
firstWord :: String -> StringSource

Get the first word of a string. Example:

 first_word "This is a fine day" ===> "This"
debugStr :: MonadIO m => String -> m ()Source
debugStr checks if we have the verbose flag turned on. If we have it outputs the String given. Else, it is a no-op.
debugStrLn :: MonadIO m => [Char] -> m ()Source
debugStrLn is a version of debugStr that adds a newline to the end of the string outputted.
lowerCaseString :: String -> StringSource

lowerCaseString transforms the string given to lower case.

 Example: lowerCaseString "MiXeDCaSe" ===> "mixedcase"
upperCaseString :: String -> StringSource

upperCaseString transforms the string given to upper case.

 Example: upperCaseString "MiXeDcaSe" ===> "MIXEDCASE"
upperize :: String -> StringSource
upperize forces the first char of a string to be uppercase. if the string is empty, the empty string is returned.
lowerize :: String -> StringSource
lowerize forces the first char of a string to be lowercase. if the string is empty, the empty string is returned.
quote :: String -> StringSource
quote puts a string into quotes but does not escape quotes in the string itself.
timeStamp :: ClockTime -> StringSource
listToStr :: String -> [String] -> StringSource

Form a list of terms using a single conjunction. Example:

 listToStr "and" ["a", "b", "c"] ===> "a, b and c"
showWidthSource
:: IntWidth to fill to
-> IntNumber to show
-> StringPadded string
Show a number, padded to the left with zeroes up to the specified width
listToMaybeWith :: ([a] -> b) -> [a] -> Maybe bSource
Like listToMaybe, but take a function to use in case of a non-null list. I.e. listToMaybe = listToMaybeWith head
listToMaybeAll :: [a] -> Maybe [a]Source
listToMaybeAll = listToMaybeWith id
getRandItemSource
:: RandomGen g
=> [a]The list to pick a random item from
-> gThe RNG to use
-> (a, g)A pair of the item, and the new RNG seed
getRandItem takes as input a list and a random number generator. It then returns a random element from the list, paired with the altered state of the RNG
stdGetRandItem :: [a] -> IO aSource
stdGetRandItem is the specialization of getRandItem to the standard RNG embedded within the IO monad. The advantage of using this is that you use the Operating Systems provided RNG instead of rolling your own and the state of the RNG is hidden, so one don't need to pass it explicitly.
randomElem :: [a] -> IO aSource
showClean :: Show a => [a] -> StringSource
show a list without heavyweight formatting
expandTab :: String -> StringSource
untab an string
closest :: String -> [String] -> (Int, String)Source
Find string in list with smallest levenshtein distance from first argument, return the string and the distance from pat it is. Will return the alphabetically first match if there are multiple matches (this may not be desirable, e.g. mroe -> moo, not more
closests :: String -> [String] -> (Int, [String])Source
withMWriter :: MVar a -> (a -> (a -> IO ()) -> IO b) -> IO bSource
Thread-safe modification of an MVar.
parIO :: IO a -> IO a -> IO aSource
timeout :: Int -> IO a -> IO (Maybe a)Source
run an action with a timeout
choice :: (r -> Bool) -> (r -> a) -> (r -> a) -> r -> aSource
arePrefixesWithSpaceOf :: [String] -> String -> BoolSource
arePrefixesOf :: [String] -> String -> BoolSource
(</>) :: FilePath -> FilePath -> FilePathSource
(<.>) :: FilePath -> FilePath -> FilePathSource
/>, <. : join two path components
(<+>) :: FilePath -> FilePath -> FilePathSource
(<>) :: FilePath -> FilePath -> FilePathSource
(<$>) :: FilePath -> FilePath -> FilePathSource
basename :: FilePath -> FilePathSource
dirname :: FilePath -> FilePathSource
dropSuffix :: FilePath -> FilePathSource
joinPath :: FilePath -> FilePath -> FilePathSource
addList :: Ord k => [(k, a)] -> Map k a -> Map k aSource
mapMaybeMap :: Ord k => (a -> Maybe b) -> Map k a -> Map k bSource
Data.Maybe.mapMaybe for Maps
insertUpd :: Ord k => (a -> a) -> k -> a -> Map k a -> Map k aSource
This makes way more sense than insertWith because we don't need to remember the order of arguments of f.
pprKeys :: Show k => Map k a -> StringSource
isLeft :: Either a b -> BoolSource
isRight :: Either a b -> BoolSource
Two functions that really should be in Data.Either
unEither :: Either a a -> aSource
Another useful Either function to easily get out of an Either
io :: MonadIO m => IO a -> m aSource
random :: MonadIO m => [a] -> m aSource
insult :: [String]Source
confirmation :: [String]Source
Produced by Haddock version 2.4.2