miniutter-0.5.1.1: Simple English clause creation from arbitrary words

Safe HaskellSafe
LanguageHaskell2010

NLP.Miniutter.English

Description

Simple English clause creation parameterized by individual words. See the tests for example texts generated.

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

Car !Int

cardinal number, not spelled

Ws !Part

plural form of a phrase

CardinalAWs !Int !Part

plural prefixed with a cardinal, spelled, with "a" for 1 and "no" for 0

CardinalWs !Int !Part

plural prefixed with a cardinal, spelled

CarAWs !Int !Part

plural prefixed with a cardinal, not spelled, with "a" for 1 and "no" for 0

CarWs !Int !Part

plural prefixed with a cardinal, not spelled

Car1Ws !Int !Part

plural prefixed with a cardinal, not spelled, with no prefix at all for 1

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; one can also just 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 # 
Instance details

Defined in NLP.Miniutter.English

Methods

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

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

Ord Part Source # 
Instance details

Defined in NLP.Miniutter.English

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 # 
Instance details

Defined in NLP.Miniutter.English

Show Part Source # 
Instance details

Defined in NLP.Miniutter.English

Methods

showsPrec :: Int -> Part -> ShowS #

show :: Part -> String #

showList :: [Part] -> ShowS #

IsString Part Source # 
Instance details

Defined in NLP.Miniutter.English

Methods

fromString :: String -> Part #

Generic Part Source # 
Instance details

Defined in NLP.Miniutter.English

Associated Types

type Rep Part :: Type -> Type #

Methods

from :: Part -> Rep Part x #

to :: Rep Part x -> Part #

Semigroup Part Source # 
Instance details

Defined in NLP.Miniutter.English

Methods

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

sconcat :: NonEmpty Part -> Part #

stimes :: Integral b => b -> Part -> Part #

Monoid Part Source # 
Instance details

Defined in NLP.Miniutter.English

Methods

mempty :: Part #

mappend :: Part -> Part -> Part #

mconcat :: [Part] -> Part #

Binary Part Source # 
Instance details

Defined in NLP.Miniutter.English

Methods

put :: Part -> Put #

get :: Get Part #

putList :: [Part] -> Put #

type Rep Part Source # 
Instance details

Defined in NLP.Miniutter.English

type Rep Part = D1 (MetaData "Part" "NLP.Miniutter.English" "miniutter-0.5.1.1-1u6OBBzF8zkEgDLImmR5j8" False) ((((C1 (MetaCons "String" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String)) :+: (C1 (MetaCons "Text" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :+: C1 (MetaCons "Cardinal" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)))) :+: (C1 (MetaCons "Car" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) :+: (C1 (MetaCons "Ws" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)) :+: C1 (MetaCons "CardinalAWs" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part))))) :+: ((C1 (MetaCons "CardinalWs" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)) :+: (C1 (MetaCons "CarAWs" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)) :+: C1 (MetaCons "CarWs" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)))) :+: (C1 (MetaCons "Car1Ws" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)) :+: (C1 (MetaCons "Ordinal" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) :+: C1 (MetaCons "Ord" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)))))) :+: (((C1 (MetaCons "AW" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)) :+: (C1 (MetaCons "WWandW" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Part])) :+: C1 (MetaCons "WWxW" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Part])))) :+: (C1 (MetaCons "Wown" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)) :+: (C1 (MetaCons "WownW" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)) :+: C1 (MetaCons "Append" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part))))) :+: ((C1 (MetaCons "Phrase" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Part])) :+: (C1 (MetaCons "Capitalize" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)) :+: C1 (MetaCons "SubjectVerb" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Person) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Polarity)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part))))) :+: (C1 (MetaCons "SubjectVerbSg" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part)) :+: (C1 (MetaCons "SubjectVVxV" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Person)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Polarity) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Part])))) :+: C1 (MetaCons "SubjectVVandVSg" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Part) :*: S1 (MetaSel (Nothing :: Maybe 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 # 
Instance details

Defined in NLP.Miniutter.English

Methods

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

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

Ord Person Source # 
Instance details

Defined in NLP.Miniutter.English

Show Person Source # 
Instance details

Defined in NLP.Miniutter.English

Generic Person Source # 
Instance details

Defined in NLP.Miniutter.English

Associated Types

type Rep Person :: Type -> Type #

Methods

from :: Person -> Rep Person x #

to :: Rep Person x -> Person #

Binary Person Source # 
Instance details

Defined in NLP.Miniutter.English

Methods

put :: Person -> Put #

get :: Get Person #

putList :: [Person] -> Put #

type Rep Person Source # 
Instance details

Defined in NLP.Miniutter.English

type Rep Person = D1 (MetaData "Person" "NLP.Miniutter.English" "miniutter-0.5.1.1-1u6OBBzF8zkEgDLImmR5j8" False) (C1 (MetaCons "Sg1st" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Sg3rd" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PlEtc" PrefixI False) (U1 :: Type -> Type)))

data Polarity Source #

Generalized polarity: affirmative, negative, interrogative.

Constructors

Yes 
No 
Why 
Instances
Eq Polarity Source # 
Instance details

Defined in NLP.Miniutter.English

Ord Polarity Source # 
Instance details

Defined in NLP.Miniutter.English

Show Polarity Source # 
Instance details

Defined in NLP.Miniutter.English

Generic Polarity Source # 
Instance details

Defined in NLP.Miniutter.English

Associated Types

type Rep Polarity :: Type -> Type #

Methods

from :: Polarity -> Rep Polarity x #

to :: Rep Polarity x -> Polarity #

Binary Polarity Source # 
Instance details

Defined in NLP.Miniutter.English

Methods

put :: Polarity -> Put #

get :: Get Polarity #

putList :: [Polarity] -> Put #

type Rep Polarity Source # 
Instance details

Defined in NLP.Miniutter.English

type Rep Polarity = D1 (MetaData "Polarity" "NLP.Miniutter.English" "miniutter-0.5.1.1-1u6OBBzF8zkEgDLImmR5j8" False) (C1 (MetaCons "Yes" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "No" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Why" PrefixI False) (U1 :: Type -> Type)))

data Irregular Source #

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

Constructors

Irregular 

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) or the first ends or the last begins with whitespace.