polh-lexicon-0.2.2: A library for manipulating the historical dictionary of Polish (deprecated)

Safe HaskellNone

NLP.Polh.Binary

Description

The module provides functions for working with the binary representation of the historical dictionary of Polish.

Synopsis

Documentation

data BinEntry Source

Entry in the binary dictionary consists of the lexical entry and corresponding unique identifier.

Constructors

BinEntry 

Fields

entry :: LexEntry

Lexical entry.

uid :: Int

Unique identifier among lexical entries with the same first form (see Key data type).

data Key Source

A dictionary key which uniquely identifies the lexical entry.

Constructors

Key 

Fields

keyForm :: Text

First form (presumably lemma) of the lexical entry.

keyUid :: Int

Unique identifier among lexical entries with the same keyForm.

Instances

data Rule Source

A rule for translating a form into a binary dictionary key.

Constructors

Rule 

Fields

cut :: !Int

Number of characters to cut from the end of the form.

suffix :: !Text

A suffix to paste.

ruleUid :: !Int

Unique identifier of the entry.

Instances

proxyForm :: LexEntry -> TextSource

Form representing the lexical entry.

binKey :: BinEntry -> KeySource

Key assigned to the binary entry.

between :: Text -> Key -> RuleSource

Make a rule which translates between the string and the key.

apply :: Rule -> Text -> KeySource

Apply the rule.

savePolh :: FilePath -> Polh -> IO ()Source

Save the polh dictionary in the empty directory.

loadPolh :: FilePath -> IO (Maybe [BinEntry])Source

Load dictionary from a disk in a lazy manner. Return Nothing if the path doesn't correspond to a binary representation of the dictionary.

data PolhT m a Source

A Polh monad transformer.

Instances

runPolhT :: MonadIO m => FilePath -> PolhT m a -> m (Maybe a)Source

Execute the Polh monad transformer against the binary Polh representation located in the given directory. Return Nothing if the directory doesnt' exist or if it doesn't look like a Polh dictionary.

type PolhM a = PolhT IO aSource

A Polh monad is a Polh monad transformer over the hidden IO monad.

runPolh :: FilePath -> PolhM a -> IO (Maybe a)Source

Execute the Polh monad against the binary Polh representation located in the given directory. Return Nothing if the directory doesnt' exist or if it doesn't look like a Polh dictionary.

index :: (Applicative m, MonadIO m) => PolhT m [Key]Source

List of dictionary keys.

withKey :: (Applicative m, MonadIO m) => Key -> PolhT m (Maybe BinEntry)Source

Extract lexical entry with the given key.

lookup :: (Applicative m, MonadIO m) => Text -> PolhT m [BinEntry]Source

Lookup the form in the dictionary.