module Language.Drasil.Chunk.Concept.NamedCombinators (
the, theGen,
a_, a_Gen,
and_, and_PS, and_PP, and_TGen,
andIts, andThe,
of_, of_NINP, of_PSNPNI, of_PS, ofA, ofAPS, ofThe, ofThePS,
the_ofThe, the_ofThePS, onThe, onThePS, onThePP,
inThe, inThePS, inThePP, isThe, toThe,
for, forTGen,
in_, in_PS, inA,
is, with,
compoundNC, compoundNCPP, compoundNCGen,
compoundNCPS, compoundNCPSPP, compoundNCGenP,
combineNINP, combineNINI) where
import Language.Drasil.Chunk.NamedIdea ( IdeaDict, ncUID )
import Language.Drasil.Classes ( Idea, NamedIdea(..) )
import Language.Drasil.NounPhrase
( NP,
CapitalizationRule(CapWords, Replace, CapFirst),
NounPhrase(phraseNP, pluralNP),
nounPhrase'',
compoundPhrase,
compoundPhrase'',
compoundPhrase''' )
import Language.Drasil.NounPhrase.Core (NPStruct(S,(:+:)))
import Drasil.Database.UID ( (+++!) )
import qualified Language.Drasil.NounPhrase as D
( NounPhrase(pluralNP, phraseNP) )
import Control.Lens ((^.))
import qualified Language.Drasil.NounPhrase.Combinators as NP (
insertString, insertStringOp, insertStringGen)
phrase, plural :: NamedIdea n => n -> NPStruct
phrase :: forall n. NamedIdea n => n -> NPStruct
phrase n
k = NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
phraseNP (NP -> NPStruct) -> NP -> NPStruct
forall a b. (a -> b) -> a -> b
$ n
k n -> Getting NP n NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP n NP
forall c. NamedIdea c => Lens' c NP
Lens' n NP
term
plural :: forall n. NamedIdea n => n -> NPStruct
plural n
k = NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
pluralNP (NP -> NPStruct) -> NP -> NPStruct
forall a b. (a -> b) -> a -> b
$ n
k n -> Getting NP n NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP n NP
forall c. NamedIdea c => Lens' c NP
Lens' n NP
term
and_ :: (NamedIdea c, NamedIdea d) => c -> d -> NP
and_ :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
and_ c
t1 d
t2 = String -> NP -> NP -> NP
NP.insertString String
"and" (c
t1 c -> Getting NP c NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP c NP
forall c. NamedIdea c => Lens' c NP
Lens' c NP
term) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
and_PS :: (NamedIdea c, NamedIdea d) => c -> d -> NP
and_PS :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
and_PS c
t1 d
t2 = String -> NP -> NP -> NP
NP.insertStringOp String
"and" (c
t1 c -> Getting NP c NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP c NP
forall c. NamedIdea c => Lens' c NP
Lens' c NP
term) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
and_PP :: (NamedIdea c, NamedIdea d) => c -> d -> NP
and_PP :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
and_PP c
t1 d
t2 = NPStruct
-> NPStruct -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase''
(c -> NPStruct
forall n. NamedIdea n => n -> NPStruct
phrase c
t1 NPStruct -> NPStruct -> NPStruct
:+: String -> NPStruct
S String
"and" NPStruct -> NPStruct -> NPStruct
:+: d -> NPStruct
forall n. NamedIdea n => n -> NPStruct
phrase d
t2)
(c -> NPStruct
forall n. NamedIdea n => n -> NPStruct
plural c
t1 NPStruct -> NPStruct -> NPStruct
:+: String -> NPStruct
S String
"and" NPStruct -> NPStruct -> NPStruct
:+: d -> NPStruct
forall n. NamedIdea n => n -> NPStruct
plural d
t2)
CapitalizationRule
CapFirst
CapitalizationRule
CapWords
and_TGen :: (NamedIdea c, NamedIdea d) =>
(c -> NPStruct) -> (d -> NPStruct) -> c -> d -> NP
and_TGen :: forall c d.
(NamedIdea c, NamedIdea d) =>
(c -> NPStruct) -> (d -> NPStruct) -> c -> d -> NP
and_TGen c -> NPStruct
f1 d -> NPStruct
f2 c
t1 d
t2 = NPStruct
-> NPStruct -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase''
(c -> NPStruct
forall n. NamedIdea n => n -> NPStruct
phrase c
t1 NPStruct -> NPStruct -> NPStruct
:+: String -> NPStruct
S String
"and" NPStruct -> NPStruct -> NPStruct
:+: d -> NPStruct
forall n. NamedIdea n => n -> NPStruct
phrase d
t2)
(c -> NPStruct
forall n. NamedIdea n => n -> NPStruct
plural c
t1 NPStruct -> NPStruct -> NPStruct
:+: String -> NPStruct
S String
"and" NPStruct -> NPStruct -> NPStruct
:+: d -> NPStruct
forall n. NamedIdea n => n -> NPStruct
plural d
t2)
CapitalizationRule
CapFirst
(NPStruct -> CapitalizationRule
Replace (c -> NPStruct
f1 c
t1 NPStruct -> NPStruct -> NPStruct
:+: String -> NPStruct
S String
"and" NPStruct -> NPStruct -> NPStruct
:+: d -> NPStruct
f2 d
t2))
andIts :: (NamedIdea a, NamedIdea b) => a -> b -> NP
andIts :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
andIts a
t1 b
t2 = String -> NP -> NP -> NP
NP.insertString String
"and its" (a
t1 a -> Getting NP a NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP a NP
forall c. NamedIdea c => Lens' c NP
Lens' a NP
term) (b
t2 b -> Getting NP b NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP b NP
forall c. NamedIdea c => Lens' c NP
Lens' b NP
term)
andThe :: (NamedIdea c, NamedIdea d) => c -> d -> NP
andThe :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
andThe c
t1 d
t2 = String -> NP -> NP -> NP
NP.insertString String
"and the" (c
t1 c -> Getting NP c NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP c NP
forall c. NamedIdea c => Lens' c NP
Lens' c NP
term) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
with :: (NamedIdea c, NamedIdea d) => c -> d -> NP
with :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
with c
t1 d
t2 = String -> NP -> NP -> NP
NP.insertString String
"with" (c
t1 c -> Getting NP c NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP c NP
forall c. NamedIdea c => Lens' c NP
Lens' c NP
term) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
of_ :: (NamedIdea c, NamedIdea d) => c -> d -> NP
of_ :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
of_ c
t1 d
t2 = String -> NP -> NP -> NP
NP.insertString String
"of" (c
t1 c -> Getting NP c NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP c NP
forall c. NamedIdea c => Lens' c NP
Lens' c NP
term) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
of_NINP :: (NamedIdea c) => c -> NP -> NP
of_NINP :: forall c. NamedIdea c => c -> NP -> NP
of_NINP c
t1 = String -> NP -> NP -> NP
NP.insertString String
"of" (c
t1 c -> Getting NP c NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP c NP
forall c. NamedIdea c => Lens' c NP
Lens' c NP
term)
of_PSNPNI :: (NamedIdea d) => NP -> d -> NP
of_PSNPNI :: forall d. NamedIdea d => NP -> d -> NP
of_PSNPNI NP
t1 d
t2 = String -> NP -> NP -> NP
NP.insertStringOp String
"of" NP
t1 (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
of_PS :: (NamedIdea c, NamedIdea d) => c -> d -> NP
of_PS :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
of_PS c
t1 d
t2 = String -> NP -> NP -> NP
NP.insertStringOp String
"of" (c
t1 c -> Getting NP c NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP c NP
forall c. NamedIdea c => Lens' c NP
Lens' c NP
term) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
ofA :: (NamedIdea c, NamedIdea d) => c -> d -> NP
ofA :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
ofA c
t1 d
t2 = String -> NP -> NP -> NP
NP.insertStringOp String
"of a" (c
t1 c -> Getting NP c NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP c NP
forall c. NamedIdea c => Lens' c NP
Lens' c NP
term) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
ofAPS :: (NamedIdea c, NamedIdea d) => c -> d -> NP
ofAPS :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
ofAPS c
t1 d
t2 = String -> NP -> NP -> NP
NP.insertStringOp String
"of a" (c
t1 c -> Getting NP c NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP c NP
forall c. NamedIdea c => Lens' c NP
Lens' c NP
term) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
ofThe :: (NamedIdea c, NamedIdea d) => c -> d -> NP
ofThe :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
ofThe c
t1 d
t2 = String -> NP -> NP -> NP
NP.insertString String
"of the" (c
t1 c -> Getting NP c NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP c NP
forall c. NamedIdea c => Lens' c NP
Lens' c NP
term) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
ofThePS :: (NamedIdea c, NamedIdea d) => c -> d -> NP
ofThePS :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
ofThePS c
t1 d
t2 = String -> NP -> NP -> NP
NP.insertStringOp String
"of the" (c
t1 c -> Getting NP c NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP c NP
forall c. NamedIdea c => Lens' c NP
Lens' c NP
term) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
the_ofThe :: (NamedIdea c, NamedIdea d) => c -> d -> NP
the_ofThe :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
the_ofThe c
t1 d
t2 = String -> NP -> NP -> NP
NP.insertString String
"of the" (c -> NP
forall t. NamedIdea t => t -> NP
the c
t1) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
the_ofThePS :: (NamedIdea c, NamedIdea d) => c -> d -> NP
the_ofThePS :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
the_ofThePS c
t1 d
t2 = String -> NP -> NP -> NP
NP.insertStringOp String
"of the" (c -> NP
forall t. NamedIdea t => t -> NP
the c
t1) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
onThe :: (NamedIdea a, NamedIdea b) => a -> b -> NP
onThe :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
onThe a
t1 b
t2 = String -> NP -> NP -> NP
NP.insertString String
"on the" (a
t1 a -> Getting NP a NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP a NP
forall c. NamedIdea c => Lens' c NP
Lens' a NP
term) (b
t2 b -> Getting NP b NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP b NP
forall c. NamedIdea c => Lens' c NP
Lens' b NP
term)
onThePS :: (NamedIdea a, NamedIdea b) => a -> b -> NP
onThePS :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
onThePS a
t1 b
t2 = String -> NP -> NP -> NP
NP.insertStringOp String
"on the" (a
t1 a -> Getting NP a NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP a NP
forall c. NamedIdea c => Lens' c NP
Lens' a NP
term) (b
t2 b -> Getting NP b NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP b NP
forall c. NamedIdea c => Lens' c NP
Lens' b NP
term)
onThePP :: (NamedIdea c, NamedIdea d) => c -> d -> NP
onThePP :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
onThePP c
t1 d
t2 = String -> (NP -> NPStruct) -> (NP -> NPStruct) -> NP -> NP -> NP
NP.insertStringGen String
"on the" NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
pluralNP NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
pluralNP (c
t1 c -> Getting NP c NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP c NP
forall c. NamedIdea c => Lens' c NP
Lens' c NP
term) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
inThe :: (NamedIdea c, NamedIdea d) => c -> d -> NP
inThe :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
inThe c
t1 d
t2 = String -> NP -> NP -> NP
NP.insertString String
"in the" (c
t1 c -> Getting NP c NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP c NP
forall c. NamedIdea c => Lens' c NP
Lens' c NP
term) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
inThePS :: (NamedIdea c, NamedIdea d) => c -> d -> NP
inThePS :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
inThePS c
t1 d
t2 = String -> NP -> NP -> NP
NP.insertStringOp String
"in the" (c
t1 c -> Getting NP c NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP c NP
forall c. NamedIdea c => Lens' c NP
Lens' c NP
term) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
inThePP :: (NamedIdea c, NamedIdea d) => c -> d -> NP
inThePP :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
inThePP c
t1 d
t2 = String -> (NP -> NPStruct) -> (NP -> NPStruct) -> NP -> NP -> NP
NP.insertStringGen String
"in the" NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
pluralNP NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
pluralNP (c
t1 c -> Getting NP c NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP c NP
forall c. NamedIdea c => Lens' c NP
Lens' c NP
term) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
isThe :: (NamedIdea c, NamedIdea d) => c -> d -> NP
isThe :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
isThe c
t1 d
t2 = String -> NP -> NP -> NP
NP.insertString String
"is the" (c
t1 c -> Getting NP c NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP c NP
forall c. NamedIdea c => Lens' c NP
Lens' c NP
term) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
toThe :: (NamedIdea c, NamedIdea d) => c -> d -> NP
toThe :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
toThe c
t1 d
t2 = String -> NP -> NP -> NP
NP.insertString String
"to the" (c
t1 c -> Getting NP c NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP c NP
forall c. NamedIdea c => Lens' c NP
Lens' c NP
term) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
for :: (NamedIdea c, NamedIdea d) => c -> d -> NP
for :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
for c
t1 d
t2 = String -> NP -> NP -> NP
NP.insertString String
"for" (c
t1 c -> Getting NP c NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP c NP
forall c. NamedIdea c => Lens' c NP
Lens' c NP
term) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
forTGen :: (NamedIdea c, Idea d) => (c -> NPStruct) -> (d -> NPStruct) -> c -> d -> NP
forTGen :: forall c d.
(NamedIdea c, Idea d) =>
(c -> NPStruct) -> (d -> NPStruct) -> c -> d -> NP
forTGen c -> NPStruct
f1 d -> NPStruct
f2 c
t1 d
t2 = NPStruct
-> NPStruct -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase''
(c -> NPStruct
forall n. NamedIdea n => n -> NPStruct
phrase c
t1 NPStruct -> NPStruct -> NPStruct
:+: String -> NPStruct
S String
"for" NPStruct -> NPStruct -> NPStruct
:+: d -> NPStruct
forall n. NamedIdea n => n -> NPStruct
phrase d
t2)
(c -> NPStruct
forall n. NamedIdea n => n -> NPStruct
plural c
t1 NPStruct -> NPStruct -> NPStruct
:+: String -> NPStruct
S String
"for" NPStruct -> NPStruct -> NPStruct
:+: d -> NPStruct
forall n. NamedIdea n => n -> NPStruct
phrase d
t2)
CapitalizationRule
CapFirst
(NPStruct -> CapitalizationRule
Replace (c -> NPStruct
f1 c
t1 NPStruct -> NPStruct -> NPStruct
:+: String -> NPStruct
S String
"for" NPStruct -> NPStruct -> NPStruct
:+: d -> NPStruct
f2 d
t2))
in_ :: (NamedIdea c, NamedIdea d) => c -> d -> NP
in_ :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
in_ c
t1 d
t2 = String -> NP -> NP -> NP
NP.insertString String
"in" (c
t1 c -> Getting NP c NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP c NP
forall c. NamedIdea c => Lens' c NP
Lens' c NP
term) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
in_PS :: (NamedIdea c, NamedIdea d) => c -> d -> NP
in_PS :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
in_PS c
t1 d
t2 = String -> NP -> NP -> NP
NP.insertStringOp String
"in" (c
t1 c -> Getting NP c NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP c NP
forall c. NamedIdea c => Lens' c NP
Lens' c NP
term) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
inA :: (NamedIdea c, NamedIdea d) => c -> d -> NP
inA :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
inA c
t1 d
t2 = String -> NP -> NP -> NP
NP.insertString String
"in a" (c
t1 c -> Getting NP c NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP c NP
forall c. NamedIdea c => Lens' c NP
Lens' c NP
term) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
is :: (NamedIdea c, NamedIdea d) => c -> d -> NP
is :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
is c
t1 d
t2 = String -> NP -> NP -> NP
NP.insertString String
"is" (c
t1 c -> Getting NP c NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP c NP
forall c. NamedIdea c => Lens' c NP
Lens' c NP
term) (d
t2 d -> Getting NP d NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP d NP
forall c. NamedIdea c => Lens' c NP
Lens' d NP
term)
the :: (NamedIdea t) => t -> NP
the :: forall t. NamedIdea t => t -> NP
the t
t = NPStruct
-> NPStruct -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' (String -> NPStruct
S String
"the" NPStruct -> NPStruct -> NPStruct
:+: t -> NPStruct
forall n. NamedIdea n => n -> NPStruct
phrase t
t) (String -> NPStruct
S String
"the" NPStruct -> NPStruct -> NPStruct
:+: t -> NPStruct
forall n. NamedIdea n => n -> NPStruct
plural t
t) CapitalizationRule
CapFirst CapitalizationRule
CapWords
theGen :: (t -> NPStruct) -> t -> NP
theGen :: forall t. (t -> NPStruct) -> t -> NP
theGen t -> NPStruct
f t
t = NPStruct
-> NPStruct -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' (String -> NPStruct
S String
"the" NPStruct -> NPStruct -> NPStruct
:+: t -> NPStruct
f t
t) (String -> NPStruct
S String
"the" NPStruct -> NPStruct -> NPStruct
:+: t -> NPStruct
f t
t) CapitalizationRule
CapFirst CapitalizationRule
CapWords
a_ :: (NamedIdea c) => c -> NP
a_ :: forall t. NamedIdea t => t -> NP
a_ c
t = NPStruct
-> NPStruct -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' (String -> NPStruct
S String
"a" NPStruct -> NPStruct -> NPStruct
:+: c -> NPStruct
forall n. NamedIdea n => n -> NPStruct
phrase c
t) (String -> NPStruct
S String
"a" NPStruct -> NPStruct -> NPStruct
:+: c -> NPStruct
forall n. NamedIdea n => n -> NPStruct
plural c
t) CapitalizationRule
CapFirst CapitalizationRule
CapWords
a_Gen :: (c -> NPStruct) -> c -> NP
a_Gen :: forall t. (t -> NPStruct) -> t -> NP
a_Gen c -> NPStruct
f c
t = NPStruct
-> NPStruct -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' (String -> NPStruct
S String
"a" NPStruct -> NPStruct -> NPStruct
:+: c -> NPStruct
f c
t) (String -> NPStruct
S String
"a" NPStruct -> NPStruct -> NPStruct
:+: c -> NPStruct
f c
t) CapitalizationRule
CapFirst CapitalizationRule
CapWords
compoundNC :: (NamedIdea a, NamedIdea b) => a -> b -> IdeaDict
compoundNC :: forall a b. (NamedIdea a, NamedIdea b) => a -> b -> IdeaDict
compoundNC a
t1 b
t2 = UID -> NP -> IdeaDict
ncUID
(a
t1 a -> b -> UID
forall a b. (HasUID a, HasUID b) => a -> b -> UID
+++! b
t2) (NP -> NP -> NP
forall a b. (NounPhrase a, NounPhrase b) => a -> b -> NP
compoundPhrase (a
t1 a -> Getting NP a NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP a NP
forall c. NamedIdea c => Lens' c NP
Lens' a NP
term) (b
t2 b -> Getting NP b NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP b NP
forall c. NamedIdea c => Lens' c NP
Lens' b NP
term))
compoundNCPP :: (NamedIdea a, NamedIdea b) => a -> b -> IdeaDict
compoundNCPP :: forall a b. (NamedIdea a, NamedIdea b) => a -> b -> IdeaDict
compoundNCPP a
t1 b
t2 = UID -> NP -> IdeaDict
ncUID
(a
t1 a -> b -> UID
forall a b. (HasUID a, HasUID b) => a -> b -> UID
+++! b
t2) ((NP -> NPStruct) -> (NP -> NPStruct) -> NP -> NP -> NP
compoundPhrase'' NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
D.pluralNP NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
D.pluralNP (a
t1 a -> Getting NP a NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP a NP
forall c. NamedIdea c => Lens' c NP
Lens' a NP
term) (b
t2 b -> Getting NP b NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP b NP
forall c. NamedIdea c => Lens' c NP
Lens' b NP
term))
compoundNCGen :: (NamedIdea a, NamedIdea b) =>
(NP -> NPStruct) -> (NP -> NPStruct) -> a -> b -> IdeaDict
compoundNCGen :: forall a b.
(NamedIdea a, NamedIdea b) =>
(NP -> NPStruct) -> (NP -> NPStruct) -> a -> b -> IdeaDict
compoundNCGen NP -> NPStruct
f1 NP -> NPStruct
f2 a
t1 b
t2 = UID -> NP -> IdeaDict
ncUID
(a
t1 a -> b -> UID
forall a b. (HasUID a, HasUID b) => a -> b -> UID
+++! b
t2)
((NP -> NPStruct) -> (NP -> NPStruct) -> NP -> NP -> NP
compoundPhrase'' NP -> NPStruct
f1 NP -> NPStruct
f2 (a
t1 a -> Getting NP a NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP a NP
forall c. NamedIdea c => Lens' c NP
Lens' a NP
term) (b
t2 b -> Getting NP b NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP b NP
forall c. NamedIdea c => Lens' c NP
Lens' b NP
term))
compoundNCPS :: IdeaDict -> IdeaDict -> IdeaDict
compoundNCPS :: IdeaDict -> IdeaDict -> IdeaDict
compoundNCPS = (NP -> NPStruct)
-> (NP -> NPStruct) -> IdeaDict -> IdeaDict -> IdeaDict
forall a b.
(NamedIdea a, NamedIdea b) =>
(NP -> NPStruct) -> (NP -> NPStruct) -> a -> b -> IdeaDict
compoundNCGen NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
D.pluralNP NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
D.phraseNP
compoundNCGenP :: (NamedIdea a, NamedIdea b) => (NP -> NPStruct) -> a -> b -> IdeaDict
compoundNCGenP :: forall a b.
(NamedIdea a, NamedIdea b) =>
(NP -> NPStruct) -> a -> b -> IdeaDict
compoundNCGenP NP -> NPStruct
f1 a
t1 b
t2 = UID -> NP -> IdeaDict
ncUID
(a
t1 a -> b -> UID
forall a b. (HasUID a, HasUID b) => a -> b -> UID
+++! b
t2) ((NP -> NPStruct) -> NP -> NP -> NP
compoundPhrase''' NP -> NPStruct
f1 (a
t1 a -> Getting NP a NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP a NP
forall c. NamedIdea c => Lens' c NP
Lens' a NP
term) (b
t2 b -> Getting NP b NP -> NP
forall s a. s -> Getting a s a -> a
^. Getting NP b NP
forall c. NamedIdea c => Lens' c NP
Lens' b NP
term))
compoundNCPSPP :: IdeaDict -> IdeaDict -> IdeaDict
compoundNCPSPP :: IdeaDict -> IdeaDict -> IdeaDict
compoundNCPSPP = (NP -> NPStruct) -> IdeaDict -> IdeaDict -> IdeaDict
forall a b.
(NamedIdea a, NamedIdea b) =>
(NP -> NPStruct) -> a -> b -> IdeaDict
compoundNCGenP NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
D.pluralNP
combineNINP :: (NamedIdea c) => c -> NP -> NP
combineNINP :: forall c. NamedIdea c => c -> NP -> NP
combineNINP c
t1 NP
t2 = NPStruct
-> NPStruct -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' (c -> NPStruct
forall n. NamedIdea n => n -> NPStruct
phrase c
t1 NPStruct -> NPStruct -> NPStruct
:+: NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
phraseNP NP
t2) (c -> NPStruct
forall n. NamedIdea n => n -> NPStruct
phrase c
t1 NPStruct -> NPStruct -> NPStruct
:+: NP -> NPStruct
forall n. NounPhrase n => n -> NPStruct
pluralNP NP
t2) CapitalizationRule
CapFirst CapitalizationRule
CapWords
combineNINI :: (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI c
t1 d
t2 = NPStruct
-> NPStruct -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' (c -> NPStruct
forall n. NamedIdea n => n -> NPStruct
phrase c
t1 NPStruct -> NPStruct -> NPStruct
:+: d -> NPStruct
forall n. NamedIdea n => n -> NPStruct
phrase d
t2) (c -> NPStruct
forall n. NamedIdea n => n -> NPStruct
phrase c
t1 NPStruct -> NPStruct -> NPStruct
:+: d -> NPStruct
forall n. NamedIdea n => n -> NPStruct
plural d
t2) CapitalizationRule
CapFirst CapitalizationRule
CapWords