libGenI-0.16ContentsIndex
NLP.GenI.Configuration
Synopsis
data Params = Prms {
grammarType :: GrammarType
builderType :: BuilderType
geniFlags :: [Flag]
}
data GrammarType
= GeniHand
| PreCompiled
| PreAnchored
data BuilderType
= NullBuilder
| SimpleBuilder
| SimpleOnePhaseBuilder
| CkyBuilder
| EarleyBuilder
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
data Optimisation
= PolOpts
| AdjOpts
| Polarised
| NoConstraints
| RootCatFiltered
| SemFiltered
| Iaf
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
module System.Console.GetOpt
Typeable
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
Prms
grammarType :: GrammarType
builderType :: BuilderType
geniFlags :: [Flag]
show/hide Instances
data GrammarType
Constructors
GeniHandgeni's text format
PreCompiledbuilt into geni, no parsing needed
PreAnchoredlexical selection already done
show/hide Instances
data BuilderType
Constructors
NullBuilder
SimpleBuilder
SimpleOnePhaseBuilder
CkyBuilder
EarleyBuilder
show/hide Instances
type Instruction = (FilePath, Maybe [String])
data Flag
show/hide Instances
data BatchDirFlg
Constructors
BatchDirFlg FilePath
show/hide Instances
data DisableGuiFlg
Constructors
DisableGuiFlg ()
show/hide Instances
data EarlyDeathFlg
Constructors
EarlyDeathFlg ()
show/hide Instances
data ExtraPolaritiesFlg
Constructors
ExtraPolaritiesFlg (Map String Interval)
show/hide Instances
data FromStdinFlg
Constructors
FromStdinFlg ()
show/hide Instances
data HelpFlg
Constructors
HelpFlg ()
show/hide Instances
data IgnoreSemanticsFlg
Constructors
IgnoreSemanticsFlg ()
show/hide Instances
data InstructionsFileFlg
Constructors
InstructionsFileFlg FilePath
show/hide Instances
data LexiconFlg
Constructors
LexiconFlg FilePath
show/hide Instances
data MacrosFlg
Constructors
MacrosFlg FilePath
show/hide Instances
data MaxTreesFlg
Constructors
MaxTreesFlg Int
show/hide Instances
data MetricsFlg
Constructors
MetricsFlg [String]
show/hide Instances
data MorphCmdFlg
Constructors
MorphCmdFlg String
show/hide Instances
data MorphInfoFlg
Constructors
MorphInfoFlg FilePath
show/hide Instances
data MorphLexiconFlg
Constructors
MorphLexiconFlg FilePath
show/hide Instances
data NoLoadTestSuiteFlg
Constructors
NoLoadTestSuiteFlg ()
show/hide Instances
data OptimisationsFlg
Constructors
OptimisationsFlg [Optimisation]
show/hide Instances
data OutputFileFlg
Constructors
OutputFileFlg String
show/hide Instances
data PartialFlg
Constructors
PartialFlg ()
show/hide Instances
data RegressionTestModeFlg
Constructors
RegressionTestModeFlg ()
show/hide Instances
data RootFeatureFlg
Constructors
RootFeatureFlg Flist
show/hide Instances
data StatsFileFlg
Constructors
StatsFileFlg FilePath
show/hide Instances
data TestCaseFlg
Constructors
TestCaseFlg String
show/hide Instances
data TestInstructionsFlg
Constructors
TestInstructionsFlg [Instruction]
show/hide Instances
data TestSuiteFlg
Constructors
TestSuiteFlg FilePath
show/hide Instances
data TimeoutFlg
Constructors
TimeoutFlg Integer
show/hide Instances
data TracesFlg
Constructors
TracesFlg FilePath
show/hide Instances
data VerboseModeFlg
Constructors
VerboseModeFlg ()
show/hide Instances
data ViewCmdFlg
Constructors
ViewCmdFlg String
show/hide 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
show/hide 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]
Uses the GetOpt library to process the command line arguments. Note that we divide them into basic and advanced usage.
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)flag
-> (String -> x)string reader for flag (probably |id| if already a String)
-> Stringdescription
-> ArgDescr Flag
optArg
:: forall f x . (Eq f, Show f, Typeable f, Eq x, Show x, Typeable x)
=> (x -> f)flag
-> xdefault value
-> (String -> x)string reader (as in reqArg)
-> Stringdescription
-> ArgDescr Flag
parseFlagWithParsec :: String -> CharParser () b -> String -> b
module System.Console.GetOpt
Typeable
Produced by Haddock version 0.8