misfortune-0.1.2.1: fortune-mod clone
Safe HaskellNone
LanguageHaskell2010

Data.Fortune

Synopsis

Documentation

data FortuneFile Source #

A handle to an open fortune database.

fortuneFilePath :: FortuneFile -> FilePath Source #

Get the path of the text part of an open fortune database.

fortuneIndexPath :: FortuneFile -> FilePath Source #

Get the path of the index part of an open fortune database.

openFortuneFile :: Char -> Bool -> FilePath -> IO FortuneFile Source #

openFortuneFile path delim writeMode: Open a fortune file at path, using delim as the character between strings, allowing writing if writeMode is set. If no file exists at the specified path, an error will be thrown or the file will be created, depending on writeMode.

closeFortuneFile :: FortuneFile -> IO () Source #

Close a fortune file. Subsequent accesses will fail.

getIndex :: FortuneFile -> IO Index Source #

Get the Index of a FortuneFile, opening it if necessary.

rebuildIndex :: FortuneFile -> IO () Source #

Clear a FortuneFiles Index and rebuild it from the contents of the text file.

getFortune :: FortuneFile -> Int -> IO Text Source #

getFortune f i retrieves the text of the i'th fortune (according to the order in the index file) in the FortuneFile f.

getFortunes :: FortuneFile -> IO [Text] Source #

Get the text of every fortune in a fortune file, in the order they occur in the file. Ignores the index entirely.

getNumFortunes :: FortuneFile -> IO Int Source #

Get the number of fortunes in a fortune file, as recorded in the index.

appendFortune :: FortuneFile -> Text -> IO () Source #

Append a fortune to a fortune file, inserting a delimiter if needed and updating the index.

data Index Source #

A handle to an open fortune index file.

openIndex :: FilePath -> Bool -> IO Index Source #

openIndex path writeMode: Opens the index file at path. The Index will be writable if writeMode is True. If there is no index file at that path, an error will be thrown or the index will be created, depending on writeMode.

createVirtualIndex :: IO Index Source #

Create an in-memory index - useful for working with files when, for whatever reason, you cannot create a valid index.

closeIndex :: Index -> IO () Source #

Close an index file. Subsequent accesses will fail.

getStats :: Index -> IO FortuneStats Source #

Get some cached stats about the fortunes indexed in this file.

data StatsProblem Source #

Errors that can be thrown when stats are read from an index file. These errors describe various logical inconsistencies that generally indicate that the index file is corrupted somehow.

data HeaderProblem Source #

An exception type indicating things that can be wrong about an index file's header.

checkIndex :: Index -> IO (Maybe IndexProblem) Source #

Force a consistency check on an index file.

data IndexEntry Source #

Conceptually, an Index file is just a header containing FortuneStats and an array of these entries. An IndexEntry stores the information needed to locate one string in the fortune fiel, as well as some basic stats about that one file (from which the FortuneStats will be derived).

Constructors

IndexEntry 

Fields

indexEntryStats :: IndexEntry -> FortuneStats Source #

Convert one index entry to a FortuneStats record describing it.

getEntries :: Index -> IO (Vector IndexEntry) Source #

Read all the entries in an Index

getEntry :: Index -> Int -> IO IndexEntry Source #

Read a specified entry from an Index.

unfoldEntries :: Index -> IO (Maybe IndexEntry) -> IO () Source #

Repeatedly invoke a generator for index entries until it returns Nothing, appending all entries returned to the index file.

appendEntries :: Index -> Vector IndexEntry -> IO () Source #

Append all the given entries to the Index file.

appendEntry :: Index -> IndexEntry -> IO () Source #

Append a single IndexEntry to an Index file.

clearIndex :: Index -> IO () Source #

Delete all entries from an Index.

rebuildStats :: Index -> IO () Source #

All the operations here should preserve correctness of stats, but just in case... This procedure forces the stats to be recomputed.

data FortuneStats Source #

Some statistics about the fortunes in a database. These are stored in the index file and used to speed up various calculations that would otherwise require re-reading lots of files.

numFortunes :: FortuneStats -> Int Source #

The number of fortune strings in the index

minChars :: FortuneStats -> Int Source #

The smallest number of characters in any string in the index

maxLines :: FortuneStats -> Int Source #

The greatest number of characters in any string in the index

minLines :: FortuneStats -> Int Source #

The smallest number of lines in any string in the index

maxChars :: FortuneStats -> Int Source #

The greatest number of lines in any string in the index

listFortuneFiles :: Bool -> FilePath -> IO [FilePath] Source #

List all the fortune files in a directory. The Bool value specifies whether to search subtrees as well.

Any file which does not have an extension of ".ix" or ".dat" will be reported as a fortune file (".dat" is not used by misfortune, but is ignored so that misfortune can share fortune databases with fortune).

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

List all the fortune files in several directories. Each directory will be searched by listFortuneFiles (using the corresponding Bool value to control whether the directory is searched recursively) and all results will be combined.

findFortuneFile :: Bool -> FilePath -> String -> IO [FilePath] Source #

Like listFortuneFiles except only returning paths with the specified file name.

findFortuneFileIn :: [(String, Bool)] -> String -> IO [FilePath] Source #

Like listFortuneFilesIn except only returning paths with the specified file name.

findFortuneFilesIn :: [(String, Bool)] -> [String] -> IO [FilePath] Source #

Like findFortuneFileIn but searches for multiple files in multiple directories.

data FortuneType Source #

Three different search paths are supported, depending on the "type" of fortune requested. These are the types that can be requested.

Constructors

All 
Normal 
Offensive 

Instances

Instances details
Bounded FortuneType Source # 
Instance details

Defined in Data.Fortune

Enum FortuneType Source # 
Instance details

Defined in Data.Fortune

Eq FortuneType Source # 
Instance details

Defined in Data.Fortune

Ord FortuneType Source # 
Instance details

Defined in Data.Fortune

Read FortuneType Source # 
Instance details

Defined in Data.Fortune

Show FortuneType Source # 
Instance details

Defined in Data.Fortune

getFortuneDir :: FortuneType -> IO FilePath Source #

Get the path of the directory containing built-in fortunes of the specified type.

defaultFortuneFiles :: FortuneType -> IO [FilePath] Source #

Get a list of all fortune files on the configured search path (see getFortuneSearchPath)

defaultFortuneSearchPath :: FortuneType -> IO [(FilePath, Bool)] Source #

Get the default search path for a specified fortune type (ignoring the MISFORTUNE_PATH environment variables)

getFortuneSearchPath :: FortuneType -> IO [(FilePath, Bool)] Source #

Get the configured search path for a specified fortune type. If the environment variable MISFORTUNE_PATH_TYPE is set, it will be used. Otherwise, if MISFORTUNE_PATH is set, it will be used. Otherwise, the defaultFortuneSearchPath will be used.

Environment variables are interpreted by splitting on : and checking for an optional + or - prefix on each component (where + indicates recursive search of that directory). The default is non-recursive search for each component.

resolveFortuneFile :: FortuneType -> String -> IO [FilePath] Source #

Search for all fortune files in the configured search path with the given name.

resolveFortuneFiles :: FortuneType -> [String] -> IO [FilePath] Source #

Search for all fortune files in the configured search path with any of the given names.

randomFortune :: [String] -> IO String Source #

Select a random fortune from all files matching any of a list of names (or if the list is empty, all fortune files on the search path). Every fortune string will have an equal probability of being selected.

randomFortuneFromRandomFile :: RVar FortuneFile -> IO String Source #

Select a random fortune file from a specified distribution and then select a random fortune from that file (unformly).

defaultFortuneDistribution :: [FortuneFile] -> IO (Categorical Float FortuneFile) Source #

Given a list of FortuneFiles, compute a distrubution over them weighted by the number of fortunes in each. If this distribution is used with randomFortuneFromRandomFile, the result will be a uniform selection over all the fortunes in all the files.

fortuneDistributionWhere :: (FortuneFile -> Int -> IndexEntry -> IO Bool) -> [FortuneFile] -> IO (Categorical Float (FortuneFile, Categorical Float Int)) Source #

Like defaultFortuneDistribution, but filtering the fortunes. In addition to the fortune file, the tuples in the distribution include a distribution over the matching fortune indices in that file, assigning equal weight to each.

withFortuneFile :: Char -> Bool -> FilePath -> (FortuneFile -> IO a) -> IO a Source #

Perform an action with an open FortuneFile, ensuring the file is closed when the action finishes.

withFortuneFiles :: Char -> Bool -> [FilePath] -> ([FortuneFile] -> IO a) -> IO a Source #

Perform an action with many open FortuneFiles, ensuring the files are closed when the action finishes.

mapFortunesWithIndexM :: (Num a, Enum a) => (a -> IndexEntry -> IO b) -> FortuneFile -> IO [b] Source #

mapFortunesWithIndex :: (Num a, Enum a) => (a -> IO b) -> FortuneFile -> IO [b] Source #