miniutter-0.4.6.0: Simple English clause creation from arbitrary words

Safe HaskellSafe
LanguageHaskell2010

NLP.Miniutter.English

Description

Simple English clause creation parameterized by individual words.

Synopsis

Documentation

data Part Source #

Various basic and compound parts of English simple present tense clauses. Many of the possible nestings do not make sense. We don't care.

Constructors

String !String

handle for a String parameter

Text !Text

handle for a Text parameter

Cardinal !Int

cardinal number, spelled in full up to 10

Ws !Part

plural form of a phrase

CarWs !Int !Part

plural prefixed with a cardinal, not spelled

CardinalWs !Int !Part

plural prefixed with a cardinal, spelled

Ordinal !Int

ordinal number, spelled in full up to 10

Ord !Int

ordinal number, not spelled

AW !Part

phrase with indefinite article

WWandW ![Part]

enumeration

WWxW !Part ![Part]

collection

Wown !Part

non-premodifying possesive

WownW !Part !Part

attributive possesive

Append !Part !Part

no space in between

!Part :> !Part

no space in between -- deprecated, use <>

Phrase ![Part]

space-separated sequence

Capitalize !Part

make the first letter into a capital letter

SubjectVerb !Person !Polarity !Part !Part

conjugation according to polarity, with a default person (pronouns override it)

SubjectVerbSg !Part !Part

a shorthand for Sg3rd and Yes

SubjectVVxV !Part !Person !Polarity !Part ![Part]

conjugation of all verbs according to polarity, with a default person (pronouns override it)

SubjectVVandVSg !Part ![Part]

a shorthand for "and", Sg3rd and Yes

Instances

Eq Part Source # 

Methods

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

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

Ord Part Source # 

Methods

compare :: Part -> Part -> Ordering #

(<) :: Part -> Part -> Bool #

(<=) :: Part -> Part -> Bool #

(>) :: Part -> Part -> Bool #

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

max :: Part -> Part -> Part #

min :: Part -> Part -> Part #

Read Part Source # 
Show Part Source # 

Methods

showsPrec :: Int -> Part -> ShowS #

show :: Part -> String #

showList :: [Part] -> ShowS #

IsString Part Source # 

Methods

fromString :: String -> Part #

Generic Part Source # 

Associated Types

type Rep Part :: * -> * #

Methods

from :: Part -> Rep Part x #

to :: Rep Part x -> Part #

Monoid Part Source # 

Methods

mempty :: Part #

mappend :: Part -> Part -> Part #

mconcat :: [Part] -> Part #

Binary Part Source # 

Methods

put :: Part -> Put #

get :: Get Part #

putList :: [Part] -> Put #

type Rep Part Source # 
type Rep Part = D1 (MetaData "Part" "NLP.Miniutter.English" "miniutter-0.4.6.0-sE9LCzh8ew9HqyHwIsdAP" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "String" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String))) (C1 (MetaCons "Text" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))) ((:+:) (C1 (MetaCons "Cardinal" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))) ((:+:) (C1 (MetaCons "Ws" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part))) (C1 (MetaCons "CarWs" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part))))))) ((:+:) ((:+:) (C1 (MetaCons "CardinalWs" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)))) (C1 (MetaCons "Ordinal" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)))) ((:+:) (C1 (MetaCons "Ord" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))) ((:+:) (C1 (MetaCons "AW" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part))) (C1 (MetaCons "WWandW" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Part]))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "WWxW" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Part])))) (C1 (MetaCons "Wown" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)))) ((:+:) (C1 (MetaCons "WownW" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)))) ((:+:) (C1 (MetaCons "Append" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)))) (C1 (MetaCons ":>" (InfixI LeftAssociative 9) False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part))))))) ((:+:) ((:+:) (C1 (MetaCons "Phrase" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Part]))) ((:+:) (C1 (MetaCons "Capitalize" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part))) (C1 (MetaCons "SubjectVerb" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Person)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Polarity))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part))))))) ((:+:) (C1 (MetaCons "SubjectVerbSg" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)))) ((:+:) (C1 (MetaCons "SubjectVVxV" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Person))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Polarity)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Part])))))) (C1 (MetaCons "SubjectVVandVSg" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Part])))))))))

data Person Source #

Persons: singular 1st, singular 3rd and the rest.

Constructors

Sg1st 
Sg3rd 
PlEtc 

Instances

Eq Person Source # 

Methods

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

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

Ord Person Source # 
Show Person Source # 
Generic Person Source # 

Associated Types

type Rep Person :: * -> * #

Methods

from :: Person -> Rep Person x #

to :: Rep Person x -> Person #

Binary Person Source # 

Methods

put :: Person -> Put #

get :: Get Person #

putList :: [Person] -> Put #

type Rep Person Source # 
type Rep Person = D1 (MetaData "Person" "NLP.Miniutter.English" "miniutter-0.4.6.0-sE9LCzh8ew9HqyHwIsdAP" False) ((:+:) (C1 (MetaCons "Sg1st" PrefixI False) U1) ((:+:) (C1 (MetaCons "Sg3rd" PrefixI False) U1) (C1 (MetaCons "PlEtc" PrefixI False) U1)))

data Polarity Source #

Generalized polarity: affirmative, negative, interrogative.

Constructors

Yes 
No 
Why 

Instances

Eq Polarity Source # 
Ord Polarity Source # 
Show Polarity Source # 
Generic Polarity Source # 

Associated Types

type Rep Polarity :: * -> * #

Methods

from :: Polarity -> Rep Polarity x #

to :: Rep Polarity x -> Polarity #

Binary Polarity Source # 

Methods

put :: Polarity -> Put #

get :: Get Polarity #

putList :: [Polarity] -> Put #

type Rep Polarity Source # 
type Rep Polarity = D1 (MetaData "Polarity" "NLP.Miniutter.English" "miniutter-0.4.6.0-sE9LCzh8ew9HqyHwIsdAP" False) ((:+:) (C1 (MetaCons "Yes" PrefixI False) U1) ((:+:) (C1 (MetaCons "No" PrefixI False) U1) (C1 (MetaCons "Why" PrefixI False) U1)))

type Irregular = (Map Text Text, Map Text Text) Source #

Nouns with irregular plural form and nouns with irregular indefinite article.

makeSentence :: Irregular -> [Part] -> Text Source #

Realise a complete sentence, capitalized, ending with a dot.

makePhrase :: Irregular -> [Part] -> Text Source #

Realise a phrase. The spacing between parts resembles the semantics of (<+>), that is, it ignores empty words.

defIrregular :: Irregular Source #

Default set of words with irregular forms.

(<+>) :: Text -> Text -> Text infixr 6 #

Separated by space unless one of them is empty (in which case just the non-empty one).