dictionaries-0.2.0.3: Tools to handle StarDict dictionaries.

Copyright(c) 2016 Al Zohali
LicenseBSD3
MaintainerAl Zohali <zohl@fmap.me>
Stabilityexperimental
Safe HaskellSafe
LanguageHaskell2010

NLP.Dictionary.StarDict.Common

Description

Description

Common functions and types for StarDict dictionaries.

Synopsis

Documentation

data StarDictException Source #

Exceptions that are thrown when something with this module went wrong.

Constructors

WrongIfoFormat FilePath String

Thrown when information file (.ifo) has unsupported format.

IndexNotFound FilePath

Thrown when index file (.idx, .idx.gz) is not found.

WrongIndexFormat FilePath String

Thrown when index file has unsupported format.

DictionaryNotFound FilePath

Thrown when dictionary file (.dict, .dict.dz) has unsupported format.

checkFiles :: IfoFilePath -> [FilePath] -> IO (Maybe FilePath) Source #

Given .ifo file name and list of extensions, returns first existing file with the same basename.

checkGZFiles :: IfoFilePath -> [FilePath] -> [FilePath] -> IO (Maybe (Either FilePath FilePath)) Source #

Given .ifo file name and two lists of extensions, returns first existing file with with the same basename and extension from the first list or (if such file doesn't exists) from the second list.

data IfoFile Source #

Representation of .ifo file.

Constructors

IfoFile 

Fields

Instances

Eq IfoFile Source # 

Methods

(==) :: IfoFile -> IfoFile -> Bool #

(/=) :: IfoFile -> IfoFile -> Bool #

Show IfoFile Source # 
Generic IfoFile Source # 

Associated Types

type Rep IfoFile :: * -> * #

Methods

from :: IfoFile -> Rep IfoFile x #

to :: Rep IfoFile x -> IfoFile #

NFData IfoFile Source # 

Methods

rnf :: IfoFile -> () #

type Rep IfoFile Source # 
type Rep IfoFile = D1 (MetaData "IfoFile" "NLP.Dictionary.StarDict.Common" "dictionaries-0.2.0.3-IjMwGyDtWBO2HdjNmLpHkP" False) (C1 (MetaCons "IfoFile" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "ifoMagicData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)) ((:*:) (S1 (MetaSel (Just Symbol "ifoVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "ifoBookName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "ifoWordCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "ifoIdxFileSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) ((:*:) (S1 (MetaSel (Just Symbol "ifoIdxOffsetBits") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int))) (S1 (MetaSel (Just Symbol "ifoSynWordCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "ifoAuthor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "ifoEmail") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "ifoWebsite") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "ifoDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "ifoDate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe UTCTime)))) ((:*:) (S1 (MetaSel (Just Symbol "ifoSameTypeSequence") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String))) (S1 (MetaSel (Just Symbol "ifoDictType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String))))))))

type IfoFilePath = FilePath Source #

Type synonym to distinguish usage of paths.

ifoDateFormat :: String Source #

Date format of ifoDate in IfoFile.

readIfoFile :: (MonadThrow m, MonadIO m) => FilePath -> m IfoFile Source #

Read .ifo file at the given path.

renderIfoFile :: IfoFile -> Text Source #

Generates .ifo file contents based on IfoFile

type IndexEntry = (Text, (Int, Int)) Source #

Representation of an .idx file entry.

readIndexFile :: (MonadThrow m, MonadIO m) => IfoFilePath -> Get Int -> m [IndexEntry] Source #

Read .idx (.idx.gz) file.

renderIndexFile :: [IndexEntry] -> (Int -> Builder) -> ByteString Source #

Generates .idx file contents based on Index.

getIndexNumber :: Maybe Int -> Get Int Source #

Get 32-bit or 64-bit integer depending on description in the .ifo file.

putIndexNumber :: Maybe Int -> Int -> Builder Source #

Put 32-bit or 64-bit integer depending on description in the .ifo file.

checkDataFile :: (MonadThrow m, MonadIO m) => IfoFilePath -> m FilePath Source #

Returns path of decompressed dictionary.

type Renderer = DataEntry -> Text Source #

Type of function to transform dictionary entries to a text.

mkDataParser :: Maybe String -> Get [DataEntry] Source #

Returns parser based on description in .ifo file.

class Dictionary d => StarDict d where Source #

Classtype for stardict dictionaries.

Minimal complete definition

getIfoFile, mkDictionary