GenI-0.20.1: A natural language generator (specifically, an FB-LTAG surface realiser)Source codeContentsIndex
NLP.GenI.Configuration
Contents
flags
Synopsis
data Params = Prms {
grammarType :: GrammarType
builderType :: BuilderType
geniFlags :: [Flag]
}
data GrammarType
= GeniHand
| PreCompiled
| PreAnchored
data BuilderType
= NullBuilder
| SimpleBuilder
| SimpleOnePhaseBuilder
type Instruction = (FilePath, Maybe [String])
data Flag
data BatchDirFlg = BatchDirFlg FilePath
data DetectPolaritiesFlg = DetectPolaritiesFlg (Set PolarityAttr)
data DisableGuiFlg = DisableGuiFlg ()
data DumpDerivationFlg = DumpDerivationFlg ()
data EarlyDeathFlg = EarlyDeathFlg ()
data ExtraPolaritiesFlg = ExtraPolaritiesFlg (Map PolarityKey Interval)
data FromStdinFlg = FromStdinFlg ()
data HelpFlg = HelpFlg ()
data InstructionsFileFlg = InstructionsFileFlg FilePath
data LexiconFlg = LexiconFlg FilePath
data MacrosFlg = MacrosFlg FilePath
data MetricsFlg = MetricsFlg [String]
data MorphCmdFlg = MorphCmdFlg String
data MorphInfoFlg = MorphInfoFlg FilePath
data NoLoadTestSuiteFlg = NoLoadTestSuiteFlg ()
data OptimisationsFlg = OptimisationsFlg [Optimisation]
data OutputFileFlg = OutputFileFlg String
data PartialFlg = PartialFlg ()
data RankingConstraintsFlg = RankingConstraintsFlg FilePath
data RegressionTestModeFlg = RegressionTestModeFlg ()
data RootFeatureFlg = RootFeatureFlg Flist
data RunUnitTestFlg = RunUnitTestFlg ()
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 VersionFlg = VersionFlg ()
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
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
| SemFiltered
| Iaf
| EarlyNa
emptyParams :: Params
defineParams :: [Flag] -> Params -> Params
treatArgs :: [OptDescr Flag] -> [String] -> IO Params
treatArgsWithParams :: [OptDescr Flag] -> [String] -> Params -> IO Params
usage :: [OptSection] -> String -> String
basicSections :: [OptSection]
optionsSections :: [OptSection]
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
class Typeable a
Documentation
data Params Source
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 Source
Constructors
GeniHandgeni's text format
PreCompiledbuilt into geni, no parsing needed
PreAnchoredlexical selection already done
show/hide Instances
data BuilderType Source
Constructors
NullBuilder
SimpleBuilder
SimpleOnePhaseBuilder
show/hide Instances
type Instruction = (FilePath, Maybe [String])Source
data Flag Source
show/hide Instances
flags
data BatchDirFlg Source
Constructors
BatchDirFlg FilePath
show/hide Instances
data DetectPolaritiesFlg Source
Constructors
DetectPolaritiesFlg (Set PolarityAttr)
show/hide Instances
data DisableGuiFlg Source
Constructors
DisableGuiFlg ()
show/hide Instances
data DumpDerivationFlg Source
Constructors
DumpDerivationFlg ()
show/hide Instances
data EarlyDeathFlg Source
Constructors
EarlyDeathFlg ()
show/hide Instances
data ExtraPolaritiesFlg Source
Constructors
ExtraPolaritiesFlg (Map PolarityKey Interval)
show/hide Instances
data FromStdinFlg Source
Constructors
FromStdinFlg ()
show/hide Instances
data HelpFlg Source
Constructors
HelpFlg ()
show/hide Instances
data InstructionsFileFlg Source
Constructors
InstructionsFileFlg FilePath
show/hide Instances
data LexiconFlg Source
Constructors
LexiconFlg FilePath
show/hide Instances
data MacrosFlg Source
Constructors
MacrosFlg FilePath
show/hide Instances
data MetricsFlg Source
Constructors
MetricsFlg [String]
show/hide Instances
data MorphCmdFlg Source
Constructors
MorphCmdFlg String
show/hide Instances
data MorphInfoFlg Source
Constructors
MorphInfoFlg FilePath
show/hide Instances
data NoLoadTestSuiteFlg Source
Constructors
NoLoadTestSuiteFlg ()
show/hide Instances
data OptimisationsFlg Source
Constructors
OptimisationsFlg [Optimisation]
show/hide Instances
data OutputFileFlg Source
Constructors
OutputFileFlg String
show/hide Instances
data PartialFlg Source
Constructors
PartialFlg ()
show/hide Instances
data RankingConstraintsFlg Source
Constructors
RankingConstraintsFlg FilePath
show/hide Instances
data RegressionTestModeFlg Source
Constructors
RegressionTestModeFlg ()
show/hide Instances
data RootFeatureFlg Source
Constructors
RootFeatureFlg Flist
show/hide Instances
data RunUnitTestFlg Source
Constructors
RunUnitTestFlg ()
show/hide Instances
data StatsFileFlg Source
Constructors
StatsFileFlg FilePath
show/hide Instances
data TestCaseFlg Source
Constructors
TestCaseFlg String
show/hide Instances
data TestInstructionsFlg Source
Constructors
TestInstructionsFlg [Instruction]
show/hide Instances
data TestSuiteFlg Source
Constructors
TestSuiteFlg FilePath
show/hide Instances
data TimeoutFlg Source
Constructors
TimeoutFlg Integer
show/hide Instances
data TracesFlg Source
Constructors
TracesFlg FilePath
show/hide Instances
data VerboseModeFlg Source
Constructors
VerboseModeFlg ()
show/hide Instances
data VersionFlg Source
Constructors
VersionFlg ()
show/hide Instances
data ViewCmdFlg Source
Constructors
ViewCmdFlg String
show/hide Instances
mainBuilderTypes :: [BuilderType]Source
getFlagP :: (Show f, Show x, Typeable f, Typeable x) => (x -> f) -> Params -> Maybe xSource
getListFlagP :: (Show f, Show x, Typeable f, Typeable x) => ([x] -> f) -> Params -> [x]Source
setFlagP :: (Eq f, Show f, Show x, Typeable f, Typeable x) => (x -> f) -> x -> Params -> ParamsSource
hasFlagP :: (Typeable f, Typeable x) => (x -> f) -> Params -> BoolSource
deleteFlagP :: (Typeable f, Typeable x) => (x -> f) -> Params -> ParamsSource
hasOpt :: Optimisation -> Params -> BoolSource
getFlag :: (Show f, Show x, Typeable f, Typeable x) => (x -> f) -> [Flag] -> Maybe xSource
setFlag :: (Eq f, Show f, Show x, Typeable f, Typeable x) => (x -> f) -> x -> [Flag] -> [Flag]Source
hasFlag :: (Typeable f, Typeable x) => (x -> f) -> [Flag] -> BoolSource
data Optimisation Source
Constructors
PolOpts
AdjOpts
Polarised
NoConstraints
SemFiltered
Iafone phase only!
EarlyNa
show/hide Instances
emptyParams :: ParamsSource
The default parameters configuration
defineParams :: [Flag] -> Params -> ParamsSource
treatArgs :: [OptDescr Flag] -> [String] -> IO ParamsSource
treatArgsWithParams :: [OptDescr Flag] -> [String] -> Params -> IO ParamsSource
usageSource
:: [OptSection]options
-> Stringprog name
-> String
Print out a GenI-style usage message with options divided into sections
basicSections :: [OptSection]Source
optionsSections :: [OptSection]Source
processInstructions :: Params -> IO ParamsSource
Update the internal instructions list, test suite and case according to the contents of an instructions file.
optionsForStandardGenI :: [OptDescr Flag]Source
Uses the GetOpt library to process the command line arguments. Note that we divide them into basic and advanced usage.
optionsForBasicStuff :: [OptDescr Flag]Source
optionsForOptimisation :: [OptDescr Flag]Source
optionsForMorphology :: [OptDescr Flag]Source
optionsForInputFiles :: [OptDescr Flag]Source
optionsForBuilder :: [OptDescr Flag]Source
optionsForTesting :: [OptDescr Flag]Source
nubBySwitches :: [OptDescr a] -> [OptDescr a]Source
noArg :: forall f. (Eq f, Show f, Typeable f) => (() -> f) -> ArgDescr FlagSource
reqArgSource
:: forall f x . (Eq f, Show f, Typeable f, Eq x, Show x, Typeable x)
=> x -> fflag
-> String -> xstring reader for flag (probably |id| if already a String)
-> Stringdescription
-> ArgDescr Flag
optArgSource
:: forall f x . (Eq f, Show f, Typeable f, Eq x, Show x, Typeable x)
=> x -> fflag
-> xdefault value
-> String -> xstring reader (as in reqArg)
-> Stringdescription
-> ArgDescr Flag
parseFlagWithParsec :: String -> CharParser () b -> String -> bSource
module System.Console.GetOpt
class Typeable a Source
The class Typeable allows a concrete representation of a type to be calculated.
show/hide Instances
Typeable Bool
Typeable Char
Typeable Double
Typeable Float
Typeable Int
Typeable Int8
Typeable Int16
Typeable Int32
Typeable Int64
Typeable Integer
Typeable Ordering
Typeable RealWorld
Typeable Word
Typeable Word8
Typeable Word16
Typeable Word32
Typeable Word64
Typeable ()
Typeable HUnitFailure
Typeable Handle
Typeable Handle__
Typeable Exception
Typeable DataType
Typeable ThreadId
Typeable BlockedIndefinitelyOnMVar
Typeable BlockedIndefinitelyOnSTM
Typeable Deadlock
Typeable AssertionFailed
Typeable AsyncException
Typeable ArrayException
Typeable ExitCode
Typeable Dynamic
Typeable CChar
Typeable CSChar
Typeable CUChar
Typeable CShort
Typeable CUShort
Typeable CInt
Typeable CUInt
Typeable CLong
Typeable CULong
Typeable CLLong
Typeable CULLong
Typeable CFloat
Typeable CDouble
Typeable CPtrdiff
Typeable CSize
Typeable CWchar
Typeable CSigAtomic
Typeable CClock
Typeable CTime
Typeable CIntPtr
Typeable CUIntPtr
Typeable CIntMax
Typeable CUIntMax
Typeable IOException
Typeable SomeException
Typeable ErrorCall
Typeable ArithException
Typeable TypeRep
Typeable TyCon
Typeable ByteString
Typeable ByteString
Typeable JSValue
Typeable JSString
Typeable LocalTime
Typeable ZonedTime
Typeable PolarityAttr
Typeable PolarityKey
Typeable TimeOut
Typeable GeniVal
Typeable AvPair
Typeable GType
Typeable GNode
Typeable ILexEntry
Typeable Ptype
Typeable TagElem
Typeable TagSite
Typeable WeirdFlg
Typeable GrammarTypeFlg
Typeable BuilderFlg
Typeable ViewCmdFlg
Typeable VersionFlg
Typeable VerboseModeFlg
Typeable TimeoutFlg
Typeable TestSuiteFlg
Typeable TestInstructionsFlg
Typeable TestCaseFlg
Typeable StatsFileFlg
Typeable NoLoadTestSuiteFlg
Typeable RunUnitTestFlg
Typeable RootFeatureFlg
Typeable RegressionTestModeFlg
Typeable RankingConstraintsFlg
Typeable PartialFlg
Typeable OutputFileFlg
Typeable OptimisationsFlg
Typeable MorphInfoFlg
Typeable MorphCmdFlg
Typeable MetricsFlg
Typeable TracesFlg
Typeable MacrosFlg
Typeable LexiconFlg
Typeable InstructionsFileFlg
Typeable HelpFlg
Typeable FromStdinFlg
Typeable ExtraPolaritiesFlg
Typeable EarlyDeathFlg
Typeable DumpDerivationFlg
Typeable DetectPolaritiesFlg
Typeable DisableGuiFlg
Typeable BatchDirFlg
Typeable Flag
Typeable GrammarType
Typeable BuilderType
Typeable Optimisation
Typeable UninflectedDisjunction
Typeable SimpleGuiItem
(Typeable1 s, Typeable a) => Typeable (s a)
Produced by Haddock version 2.6.0