-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Utility libraries for the advanced IRC bot, Lambdabot -- -- Lambdabot is an IRC bot written over several years by those on the -- #haskell IRC channel. -- -- Our own custom libraries for various plugin functions. -- -- AltTime.hs: alternate version of the time library -- -- MiniHTTP.hs: a mini http server -- -- Process.hs: a wrapper over System.Process -- -- Regex.hsc: a fast packed string regex library -- -- Serial.hs:: a serialisation API -- -- Util.hs: miscellaneous string, and other, functions @package lambdabot-utils @version 4.2.2 -- | String and other utilities module Lambdabot.Util -- | concatWith joins lists with the given glue elements. Example: -- --
--   concatWith ", " ["one","two","three"] ===> "one, two, three"
--   
concatWith :: [a] -> [[a]] -> [a] -- | Split a list into pieces that were held together by glue. Example: -- --
--   split ", " "one, two, three" ===> ["one","two","three"]
--   
split :: Eq a => [a] -> [a] -> [[a]] split2 :: Char -> Int -> String -> [String] -- | 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")
--   
breakOnGlue :: Eq a => [a] -> [a] -> ([a], [a]) -- | clean takes a Char x and returns [x] unless the Char is '\CR' -- in case [] is returned. clean :: Char -> [Char] -- | dropSpace takes as input a String and strips spaces from the -- prefix as well as the suffix of the String. Example: -- --
--   dropSpace "   abc  " ===> "abc"
--   
dropSpace :: [Char] -> [Char] -- | Drop space from the end of the string dropSpaceEnd :: [Char] -> [Char] dropNL :: [Char] -> [Char] -- | Reverse cons. Add an element to the back of a list. Example: -- --
--   snoc 3 [2, 1] ===> [2, 1, 3]
--   
snoc :: a -> [a] -> [a] -- | 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"
--   
after :: String -> 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)
--   
splitFirstWord :: String -> (String, String) -- | Get the first word of a string. Example: -- --
--   first_word "This is a fine day" ===> "This"
--   
firstWord :: String -> String -- | debugStr checks if we have the verbose flag turned on. If we -- have it outputs the String given. Else, it is a no-op. debugStr :: MonadIO m => String -> m () -- | debugStrLn is a version of debugStr that adds a newline -- to the end of the string outputted. debugStrLn :: MonadIO m => [Char] -> m () -- | lowerCaseString transforms the string given to lower case. -- --
--   Example: lowerCaseString "MiXeDCaSe" ===> "mixedcase"
--   
lowerCaseString :: String -> String -- | upperCaseString transforms the string given to upper case. -- --
--   Example: upperCaseString "MiXeDcaSe" ===> "MIXEDCASE"
--   
upperCaseString :: String -> String -- | upperize forces the first char of a string to be uppercase. if -- the string is empty, the empty string is returned. upperize :: String -> String -- | lowerize forces the first char of a string to be lowercase. if -- the string is empty, the empty string is returned. lowerize :: String -> String -- | quote puts a string into quotes but does not escape quotes in -- the string itself. quote :: String -> String timeStamp :: ClockTime -> String -- | Form a list of terms using a single conjunction. Example: -- --
--   listToStr "and" ["a", "b", "c"] ===> "a, b and c"
--   
listToStr :: String -> [String] -> String -- | Show a number, padded to the left with zeroes up to the specified -- width showWidth :: Int -> Int -> String -- | Like listToMaybe, but take a function to use in case of a -- non-null list. I.e. listToMaybe = listToMaybeWith head listToMaybeWith :: ([a] -> b) -> [a] -> Maybe b -- |
--   listToMaybeAll = listToMaybeWith id
--   
listToMaybeAll :: [a] -> Maybe [a] -- | 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 getRandItem :: RandomGen g => [a] -> g -> (a, g) -- | 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. stdGetRandItem :: [a] -> IO a randomElem :: [a] -> IO a -- | show a list without heavyweight formatting showClean :: Show a => [a] -> String -- | untab an string expandTab :: String -> String -- | 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 closest :: String -> [String] -> (Int, String) closests :: String -> [String] -> (Int, [String]) -- | Thread-safe modification of an MVar. withMWriter :: MVar a -> (a -> (a -> IO ()) -> IO b) -> IO b parIO :: IO a -> IO a -> IO a -- | run an action with a timeout timeout :: Int -> IO a -> IO (Maybe a) choice :: (r -> Bool) -> (r -> a) -> (r -> a) -> (r -> a) arePrefixesWithSpaceOf :: [String] -> String -> Bool arePrefixesOf :: [String] -> String -> Bool -- | /, . : join two path components () :: FilePath -> FilePath -> FilePath -- | /, . : join two path components (<.>) :: FilePath -> FilePath -> FilePath -- | /, . : join two path components (<+>) :: FilePath -> FilePath -> FilePath -- | /, . : join two path components (<>) :: FilePath -> FilePath -> FilePath -- | /, . : join two path components (<$>) :: 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 -- | Data.Maybe.mapMaybe for Maps mapMaybeMap :: Ord k => (a -> Maybe b) -> Map k a -> Map k b -- | This makes way more sense than insertWith because we don't -- need to remember the order of arguments of f. insertUpd :: Ord k => (a -> a) -> k -> a -> Map k a -> Map k a pprKeys :: Show k => Map k a -> String -- | Two functions that really should be in Data.Either isLeft :: Either a b -> Bool -- | Two functions that really should be in Data.Either isRight :: Either a b -> Bool -- | Another useful Either function to easily get out of an Either unEither :: Either a a -> a io :: MonadIO m => IO a -> m a random :: MonadIO m => [a] -> m a insult :: [String] confirmation :: [String] -- | Serialisation module Lambdabot.Serial data Serial s Serial :: (s -> Maybe ByteString) -> (ByteString -> Maybe s) -> Serial s serialize :: Serial s -> s -> Maybe ByteString deserialize :: Serial s -> ByteString -> Maybe s -- | Default `instance' for a Serial stdSerial :: (Show s, Read s) => Serial s -- | Serializes a Map type if both the key and the value are -- instances of Read and Show. The serialization is done by converting -- the map to and from lists. Results are saved line-wise, for better -- editing and revison control. mapSerial :: (Ord k, Show k, Show v, Read k, Read v) => Serial (Map k v) -- | Serialize a list of as. As for the mapSerializer, -- its output is line-wise. listSerial :: (Read a, Show a) => Serial [a] mapPackedSerial :: Serial (Map ByteString ByteString) assocListPackedSerial :: Serial ([(ByteString, ByteString)]) mapListPackedSerial :: Serial (Map ByteString [ByteString]) -- | readM behaves like read, but catches failure in a monad. this -- allocates a 20-30 M on startup... readM :: (Monad m, Read a) => String -> m a class Packable t readPacked :: Packable t => ByteString -> t showPacked :: Packable t => t -> ByteString packedListSerial :: Serial [ByteString] readOnly :: (ByteString -> b) -> Serial b gzip :: ByteString -> ByteString gunzip :: ByteString -> ByteString instance Packable (Map ByteString (Bool, [(String, Int)])) instance Packable [(ByteString, ByteString)] instance Packable (Map ByteString ByteString) instance Packable (Map ByteString [ByteString]) module Lambdabot.Regex regex :: ByteString -> Regex matches :: Regex -> ByteString -> Bool regex' :: String -> Regex matches' :: Regex -> String -> Bool -- | A Posix.popen compatibility mapping. module Lambdabot.Process -- | popen lets you run a binary with specified arguments. This bypasses -- the shell. | It'll also terminate (SIGTERM) the spawned process in -- case of | exception, this is very important if the timeout for a -- Plugin | expires while it is waiting for the result of a looping -- process. | It's fundamental to link the final executable with -- -threaded. popen :: FilePath -> [String] -> Maybe String -> IO (String, String, ExitCode) run :: FilePath -> String -> (String -> String) -> IO String -- | HTTP protocol binding. -- http://homepages.paradise.net.nz/warrickg/haskell/http/ -- http://www.dtek.chalmers.se/~d00bring/haskell-xml-rpc/http.html module Lambdabot.MiniHTTP type Proxy = Maybe (String, Integer) mkPost :: URI -> String -> [String] readPage :: Proxy -> URI -> [String] -> String -> IO [String] readNBytes :: Int -> Proxy -> URI -> [String] -> String -> IO [String] urlEncode :: String -> String urlDecode :: String -> String -- | URL Utility Functions module Lambdabot.Url -- | Fetch the contents of a URL following HTTP redirects. It returns a -- list of strings comprising the server response which includes the -- status line, response headers, and body. getHtmlPage :: URI -> WebReq [String] -- | Retrieve the specified header from the server response being careful -- to strip the trailing carriage return. I swiped this code from -- Search.hs, but had to modify it because it was not properly stripping -- off the trailing CR (must not have manifested itself as a bug in that -- code; however, parseURI will fail against CR-terminated strings. getHeader :: String -> [String] -> Maybe String -- | Fetches a page title for the specified URL. This function should only -- be used by other plugins if and only if the result is not to be -- displayed in an IRC channel. Instead, use urlPageTitle. rawPageTitle :: String -> WebReq (Maybe String) -- | Fetches a page title suitable for display. Ideally, other plugins -- should make use of this function if the result is to be displayed in -- an IRC channel because it ensures that a consistent look is used (and -- also lets the URL plugin effectively ignore contextual URLs that might -- be generated by another instance of lambdabot; the URL plugin matches -- on urlTitlePrompt). urlPageTitle :: String -> WebReq (Maybe String) -- | The string that I prepend to the quoted page title. urlTitlePrompt :: String runWebReq :: WebReq a -> Proxy -> IO a module Lambdabot.FixPrecedence withPrecExp :: PrecedenceData -> HsExp -> HsExp withPrecDecl :: PrecedenceData -> HsDecl -> (PrecedenceData, HsDecl) precTable :: PrecedenceData class FixPrecedence a fixPrecedence :: FixPrecedence a => a -> a instance FixPrecedence HsDecl instance FixPrecedence HsExp module Lambdabot.Parser parseExpr :: String -> Either String HsExp parseDecl :: String -> Either String HsDecl withParsed :: (forall a. (Data a, Eq a) => a -> a) -> String -> String prettyPrintInLine :: Pretty a => a -> String module Lambdabot.Pointful pointful :: String -> String -- | The result of a parse. data ParseResult a :: * -> * -- | The parse succeeded, yielding a value. ParseOk :: a -> ParseResult a -- | The parse failed at the specified source location, with an error -- message. ParseFailed :: SrcLoc -> String -> ParseResult a test :: String -> IO () main :: IO () combinatorModule :: String -- | Error utilities module Lambdabot.Error -- | catchErrorJust is an error catcher for the Maybe type. As input -- is given a deciding function, a monad and a handler. When an error is -- caught, the decider is executed to decide if the error should be -- handled or not. Then the handler is eventually called to handle the -- error. catchErrorJust :: MonadError e m => (e -> Maybe b) -> m a -> (b -> m a) -> m a -- | handleError is the flipped version of catchError. handleError :: MonadError e m => (e -> m a) -> m a -> m a -- | handleErrorJust is the flipped version of -- catchErrorJust. handleErrorJust :: MonadError e m => (e -> Maybe b) -> (b -> m a) -> m a -> m a -- | tryError uses Either to explicitly define the outcome of a -- monadic operation. An error is caught and placed into Right, whereas -- successful operation is placed into Left. tryError :: MonadError e m => m a -> m (Either e a) -- | tryErrorJust is the catchErrorJust version of -- tryError given is a decider guarding whether or not the error -- should be handled. The handler will always Right and no errors are -- Left'ed through. If the decider returns Nothing, the error will be -- thrown further up. tryErrorJust :: MonadError e m => (e -> Maybe b) -> m a -> m (Either b a) -- | finallyError is a monadic version of the classic UNWIND-PROTECT -- of lisp fame. Given parameters m and after (both monads) we proceed to -- work on m. If an error is caught, we execute the out-guard, after, -- before rethrowing the error. If m does not fail, after is executed and -- the value of m is returned. finallyError :: MonadError e m => m a -> m b -> m a -- | bracketError is the monadic version of DYNAMIC-WIND from Scheme -- fame. Parameters are: before, after and m. before is the in-guard -- being executed before m. after is the out-guard and protects fails of -- the m. In the Haskell world, this scheme is called a bracket and is -- often seen employed to manage resources. bracketError :: MonadError e m => m a -> (a -> m b) -> (a -> m c) -> m c -- | bracketError_ is the non-bound version of bracketError. -- The naming scheme follows usual Haskell convention. bracketError_ :: MonadError e m => m a -> m b -> m c -> m c -- | The signal story. Posix signals are external events that invoke signal -- handlers in Haskell. The signal handlers in turn throw dynamic -- exceptions. Our instance of MonadError for LB maps the dynamic -- exceptions to SignalCaughts, which can then be caught by a normal -- catchIrc or handleIrc module Lambdabot.Signals newtype SignalException SignalException :: Signal -> SignalException withHandler :: (MonadIO m, MonadError e m) => Signal -> Handler -> m () -> m () withHandlerList :: (MonadError e m, MonadIO m) => [Signal] -> (Signal -> Handler) -> m () -> m () ircSignalsToCatch :: [Signal] ircSignalMessage :: Signal -> [Char] ircSignalHandler :: ThreadId -> Signal -> Handler -- | Release all signal handlers releaseSignals :: IO () catchLock :: MVar () -- | Register signal handlers to catch external signals withIrcSignalCatch :: (MonadError e m, MonadIO m) => m () -> m () instance Typeable SignalException instance Show SignalException instance Exception SignalException -- | Time compatibility layer module Lambdabot.AltTime -- | Wrapping ClockTime (which doesn't provide a Read instance!) seems -- easier than talking care of the serialization of UserStatus ourselves. data ClockTime -- | Retrieve the current clocktime getClockTime :: IO ClockTime -- | Difference of two clock times diffClockTimes :: ClockTime -> ClockTime -> TimeDiff -- | addToClockTime d t adds a time difference d -- and a -- clock time t to yield a new clock time. addToClockTime :: TimeDiff -> ClockTime -> ClockTime -- | Pretty-print a TimeDiff. Both positive and negative Timediffs produce -- the same output. -- -- 14d 17h 8m 53s timeDiffPretty :: TimeDiff -> String instance Binary TimeDiff instance Binary ClockTime instance Read ClockTime instance Show ClockTime instance Eq ClockTime