 | libGenI-0.16.1: A natural language generator (specifically, an FB-LTAG surface realiser) | Contents | Index |
|
|
|
|
| Synopsis |
|
| data Params = Prms {} | | | | | | | type Instruction = (FilePath, Maybe [String]) | | | data Flag | | | data BatchDirFlg = BatchDirFlg FilePath | | | data DisableGuiFlg = DisableGuiFlg () | | | data EarlyDeathFlg = EarlyDeathFlg () | | | data ExtraPolaritiesFlg = ExtraPolaritiesFlg Map String Interval | | | data FromStdinFlg = FromStdinFlg () | | | data HelpFlg = HelpFlg () | | | data IgnoreSemanticsFlg = IgnoreSemanticsFlg () | | | data InstructionsFileFlg = InstructionsFileFlg FilePath | | | data LexiconFlg = LexiconFlg FilePath | | | data MacrosFlg = MacrosFlg FilePath | | | data MaxTreesFlg = MaxTreesFlg Int | | | data MetricsFlg = MetricsFlg [String] | | | data MorphCmdFlg = MorphCmdFlg String | | | data MorphInfoFlg = MorphInfoFlg FilePath | | | data MorphLexiconFlg = MorphLexiconFlg FilePath | | | data NoLoadTestSuiteFlg = NoLoadTestSuiteFlg () | | | data OptimisationsFlg = OptimisationsFlg [Optimisation] | | | data OutputFileFlg = OutputFileFlg String | | | data PartialFlg = PartialFlg () | | | data RegressionTestModeFlg = RegressionTestModeFlg () | | | data RootFeatureFlg = RootFeatureFlg Flist | | | data StatsFileFlg = StatsFileFlg FilePath | | | data TestCaseFlg = TestCaseFlg String | | | data TestInstructionsFlg = TestInstructionsFlg [Instruction] | | | data TestSuiteFlg = TestSuiteFlg FilePath | | | data TimeoutFlg = TimeoutFlg Integer | | | data TracesFlg = TracesFlg FilePath | | | data VerboseModeFlg = VerboseModeFlg () | | | data ViewCmdFlg = ViewCmdFlg String | | | mainBuilderTypes :: [BuilderType] | | | getFlagP :: (Show f, Show x, Typeable f, Typeable x) => (x -> f) -> Params -> Maybe x | | | getListFlagP :: (Show f, Show x, Typeable f, Typeable x) => ([x] -> f) -> Params -> [x] | | | setFlagP :: (Eq f, Show f, Show x, Typeable f, Typeable x) => (x -> f) -> x -> Params -> Params | | | hasFlagP :: (Typeable f, Typeable x) => (x -> f) -> Params -> Bool | | | deleteFlagP :: (Typeable f, Typeable x) => (x -> f) -> Params -> Params | | | hasOpt :: Optimisation -> Params -> Bool | | | polarised :: Params -> Bool | | | getFlag :: (Show f, Show x, Typeable f, Typeable x) => (x -> f) -> [Flag] -> Maybe x | | | setFlag :: (Eq f, Show f, Show x, Typeable f, Typeable x) => (x -> f) -> x -> [Flag] -> [Flag] | | | hasFlag :: (Typeable f, Typeable x) => (x -> f) -> [Flag] -> Bool | | | | | rootcatfiltered :: Params -> Bool | | | semfiltered :: Params -> Bool | | | isIaf :: Params -> Bool | | | emptyParams :: Params | | | defineParams :: [Flag] -> Params -> Params | | | treatArgs :: [OptDescr Flag] -> [String] -> IO Params | | | treatStandardArgs :: [String] -> IO Params | | | treatArgsWithParams :: [OptDescr Flag] -> [String] -> Params -> IO Params | | | treatStandardArgsWithParams :: [String] -> Params -> IO Params | | | processInstructions :: Params -> IO Params | | | optionsForStandardGenI :: [OptDescr Flag] | | | optionsForBasicStuff :: [OptDescr Flag] | | | optionsForOptimisation :: [OptDescr Flag] | | | optionsForMorphology :: [OptDescr Flag] | | | optionsForInputFiles :: [OptDescr Flag] | | | optionsForBuilder :: [OptDescr Flag] | | | optionsForTesting :: [OptDescr Flag] | | | nubBySwitches :: [OptDescr a] -> [OptDescr a] | | | noArg :: forall f. (Eq f, Show f, Typeable f) => (() -> f) -> ArgDescr Flag | | | reqArg :: forall f x. (Eq f, Show f, Typeable f, Eq x, Show x, Typeable x) => x -> f -> String -> x -> String -> ArgDescr Flag | | | optArg :: forall f x. (Eq f, Show f, Typeable f, Eq x, Show x, Typeable x) => x -> f -> x -> String -> x -> String -> ArgDescr Flag | | | parseFlagWithParsec :: String -> CharParser () b -> String -> b |
|
|
| Documentation |
|
| data Params |
| Holds the specification for how Geni should be run, its input
files, etc. This is the stuff that would normally be found in
the configuration file.
| | Constructors | | Instances | |
|
|
| data GrammarType |
| Constructors | | GeniHand | geni's text format
| | PreCompiled | built into geni, no parsing needed
| | PreAnchored | lexical selection already done
|
| Instances | |
|
|
| data BuilderType |
| Constructors | | NullBuilder | | | SimpleBuilder | | | SimpleOnePhaseBuilder | | | CkyBuilder | | | EarleyBuilder | |
| Instances | |
|
|
| type Instruction = (FilePath, Maybe [String]) |
|
| data Flag |
Instances | |
|
|
| data BatchDirFlg |
| Constructors | | Instances | |
|
|
| data DisableGuiFlg |
| Constructors | | Instances | |
|
|
| data EarlyDeathFlg |
| Constructors | | Instances | |
|
|
| data ExtraPolaritiesFlg |
| Constructors | | Instances | |
|
|
| data FromStdinFlg |
| Constructors | | Instances | |
|
|
| data HelpFlg |
| Constructors | | Instances | |
|
|
| data IgnoreSemanticsFlg |
| Constructors | | Instances | |
|
|
| data InstructionsFileFlg |
| Constructors | | Instances | |
|
|
| data LexiconFlg |
| Constructors | | Instances | |
|
|
| data MacrosFlg |
| Constructors | | Instances | |
|
|
| data MaxTreesFlg |
| Constructors | | Instances | |
|
|
| data MetricsFlg |
| Constructors | | Instances | |
|
|
| data MorphCmdFlg |
| Constructors | | Instances | |
|
|
| data MorphInfoFlg |
| Constructors | | Instances | |
|
|
| data MorphLexiconFlg |
| Constructors | | Instances | |
|
|
| data NoLoadTestSuiteFlg |
| Constructors | | Instances | |
|
|
| data OptimisationsFlg |
| Constructors | | Instances | |
|
|
| data OutputFileFlg |
| Constructors | | Instances | |
|
|
| data PartialFlg |
| Constructors | | Instances | |
|
|
| data RegressionTestModeFlg |
| Constructors | | Instances | |
|
|
| data RootFeatureFlg |
| Constructors | | Instances | |
|
|
| data StatsFileFlg |
| Constructors | | Instances | |
|
|
| data TestCaseFlg |
| Constructors | | Instances | |
|
|
| data TestInstructionsFlg |
| Constructors | | Instances | |
|
|
| data TestSuiteFlg |
| Constructors | | Instances | |
|
|
| data TimeoutFlg |
| Constructors | | Instances | |
|
|
| data TracesFlg |
| Constructors | | Instances | |
|
|
| data VerboseModeFlg |
| Constructors | | Instances | |
|
|
| data ViewCmdFlg |
| Constructors | | Instances | |
|
|
| mainBuilderTypes :: [BuilderType] |
|
| getFlagP :: (Show f, Show x, Typeable f, Typeable x) => (x -> f) -> Params -> Maybe x |
|
| getListFlagP :: (Show f, Show x, Typeable f, Typeable x) => ([x] -> f) -> Params -> [x] |
|
| setFlagP :: (Eq f, Show f, Show x, Typeable f, Typeable x) => (x -> f) -> x -> Params -> Params |
|
| hasFlagP :: (Typeable f, Typeable x) => (x -> f) -> Params -> Bool |
|
| deleteFlagP :: (Typeable f, Typeable x) => (x -> f) -> Params -> Params |
|
| hasOpt :: Optimisation -> Params -> Bool |
|
| polarised :: Params -> Bool |
|
| getFlag :: (Show f, Show x, Typeable f, Typeable x) => (x -> f) -> [Flag] -> Maybe x |
|
| setFlag :: (Eq f, Show f, Show x, Typeable f, Typeable x) => (x -> f) -> x -> [Flag] -> [Flag] |
|
| hasFlag :: (Typeable f, Typeable x) => (x -> f) -> [Flag] -> Bool |
|
| data Optimisation |
| Constructors | | PolOpts | | | AdjOpts | | | Polarised | | | NoConstraints | | | RootCatFiltered | | | SemFiltered | | | Iaf | |
| Instances | |
|
|
| rootcatfiltered :: Params -> Bool |
|
| semfiltered :: Params -> Bool |
|
| isIaf :: Params -> Bool |
|
| emptyParams :: Params |
| The default parameters configuration
|
|
| defineParams :: [Flag] -> Params -> Params |
|
| treatArgs :: [OptDescr Flag] -> [String] -> IO Params |
|
| treatStandardArgs :: [String] -> IO Params |
|
| treatArgsWithParams :: [OptDescr Flag] -> [String] -> Params -> IO Params |
|
| treatStandardArgsWithParams :: [String] -> Params -> IO Params |
|
| processInstructions :: Params -> IO Params |
|
| optionsForStandardGenI :: [OptDescr Flag] |
|
| optionsForBasicStuff :: [OptDescr Flag] |
|
| optionsForOptimisation :: [OptDescr Flag] |
|
| optionsForMorphology :: [OptDescr Flag] |
|
| optionsForInputFiles :: [OptDescr Flag] |
|
| optionsForBuilder :: [OptDescr Flag] |
|
| optionsForTesting :: [OptDescr Flag] |
|
| nubBySwitches :: [OptDescr a] -> [OptDescr a] |
|
| noArg :: forall f. (Eq f, Show f, Typeable f) => (() -> f) -> ArgDescr Flag |
|
| reqArg |
|
|
| optArg |
|
|
| parseFlagWithParsec :: String -> CharParser () b -> String -> b |
|
| Produced by Haddock version 2.1.0 |