-- | Defines various chunk combinators. The full naming scheme can be found
-- in the [Wiki](https://github.com/JacquesCarette/Drasil/wiki/Combinator-Documentation).
-- For convenience, here is a summary:
--
--    * Combinators that conflict with haskell-native functions have an underscore appended.
--    * Default plural case for combinators will be first term singular, second term plural.
--    * @P@ and @S@ denote the plural case of the combinator when it does not follow the above default.
--    * @Gen@ denotes the general function case.
--    * Although this should eventually be phased out, @T@ denotes a combinator meant for use with titles.
--    * @NI@ and @NP@ denote whether something must be a part of the 'NamedIdea' or 'NounPhrase' class.
module Language.Drasil.Chunk.Concept.NamedCombinators (
  -- * Prepositions
  -- ** \"The\" Combinators
  the, theGen,
  -- ** \"A\" Combinators
  a_, a_Gen,
  -- * Conjunctions
  -- ** \"And\" Combinators
  and_, and_PS, and_PP, and_TGen, and_Gen,
  andIts, andThe,
  -- ** \"Of\" Combinators
  of_, of_NINP, of_PSNPNI, of_PS, ofA, ofAPS, ofThe, ofThePS,
  -- ** \"The\" Combinators
  the_ofThe, the_ofThePS, onThe, onThePS, onThePP,
  inThe, inThePS, inThePP, isThe, toThe,
  -- ** \"For\" Combinators
  for, forTGen,
  -- ** \"In\" Combinators
  in_, in_PS, inA,
  -- ** Other Combinators
  is, with,
  -- * Direct Term Combinators
  -- | Some are specific to 'IdeaDict's.
  compoundNC, compoundNCPP, compoundNCGen,
  compoundNCPS, compoundNCPSPP, compoundNCGenP,
  combineNINP, combineNPNI, combineNINI) where

import Language.Drasil.Chunk.NamedIdea ( IdeaDict, ncUID )
import Language.Drasil.Classes ( Idea, NamedIdea(..) )
import Language.Drasil.Development.Sentence ( phrase, plural )
import Language.Drasil.NounPhrase
    ( NP,
      CapitalizationRule(CapWords, Replace, CapFirst),
      NounPhrase(phraseNP, pluralNP),
      nounPhrase'',
      compoundPhrase,
      compoundPhrase'',
      compoundPhrase''' )
import Language.Drasil.Sentence ( Sentence(S), (+:+) )
import Language.Drasil.UID ( (+++!) )
import qualified Language.Drasil.NounPhrase as D
    ( NounPhrase(pluralNP, phraseNP) )
import Control.Lens ((^.))

import qualified Language.Drasil.Sentence.Combinators as S (and_, andIts, andThe, of_, ofA,
  ofThe, the_ofThe, onThe, for, inThe, in_, is, toThe, isThe)


-- | Creates a 'NP' by combining two 'NamedIdea's with the word "and" between
-- their terms. Plural case is @(phrase t1) "and" (plural t2)@.
and_ :: (NamedIdea c, NamedIdea d) => c -> d -> NP
and_ :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
and_ c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase''
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.and_` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.and_` forall n. NamedIdea n => n -> Sentence
plural d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Creates a 'NP' by combining two 'NamedIdea's with the word "and" between
-- their terms. Plural case is @(plural t1) "and" (phrase t2)@.
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 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase''
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.and_` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
plural c
t1 Sentence -> Sentence -> Sentence
`S.and_` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Creates a 'NP' by combining two 'NamedIdea's with the word "and" between
-- their terms. Plural case is @(plural t1) "and" (plural t2)@.
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 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase''
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.and_` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
plural c
t1 Sentence -> Sentence -> Sentence
`S.and_` forall n. NamedIdea n => n -> Sentence
plural d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Customizable `and_` combinator. Both plural and singular cases are dermined by the two given functions
and_Gen :: (c -> Sentence) -> (d -> Sentence) -> c -> d -> NP
and_Gen :: forall c d. (c -> Sentence) -> (d -> Sentence) -> c -> d -> NP
and_Gen c -> Sentence
f1 d -> Sentence
f2 c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase''
  (c -> Sentence
f1 c
t1 Sentence -> Sentence -> Sentence
`S.and_` d -> Sentence
f2 d
t2)
  (c -> Sentence
f1 c
t1 Sentence -> Sentence -> Sentence
`S.and_` d -> Sentence
f2 d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Customizable `and_` combinator (takes two title case capitalization rules and two 'NamedIdeas').
and_TGen :: (NamedIdea c, NamedIdea d) => 
  (c -> Sentence) -> (d -> Sentence) -> c -> d -> NP
and_TGen :: forall c d.
(NamedIdea c, NamedIdea d) =>
(c -> Sentence) -> (d -> Sentence) -> c -> d -> NP
and_TGen c -> Sentence
f1 d -> Sentence
f2 c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase''
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.and_` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.and_` forall n. NamedIdea n => n -> Sentence
plural d
t2)
  CapitalizationRule
CapFirst
  (Sentence -> CapitalizationRule
Replace (c -> Sentence
f1 c
t1 Sentence -> Sentence -> Sentence
`S.and_` d -> Sentence
f2 d
t2))

-- | Creates a 'NP' by combining two 'NamedIdea's with the words "and its" between
-- their terms. Plural case is @(phrase t1) "and its" (plural t2)@.
andIts :: (NamedIdea c, NamedIdea d) => c -> d -> NP
andIts :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
andIts c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase''
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.andIts` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.andIts` forall n. NamedIdea n => n -> Sentence
plural d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Creates a 'NP' by combining two 'NamedIdea's with the words "and the" between
-- their terms. Plural case is @(phrase t1) "and the" (plural t2)@.
andThe :: (NamedIdea c, NamedIdea d) => c -> d -> NP
andThe :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
andThe c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase''
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.andThe` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.andThe` forall n. NamedIdea n => n -> Sentence
plural d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Case with "T1s with T2", as opposed to "T1 with T2", i.e.
-- singular case is @(plural t1) "with" (phrase t2)@ while the plural case pluralizes the first.
with :: (NamedIdea c, NamedIdea d) => c -> d -> NP
with :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
with c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase''
  (forall n. NamedIdea n => n -> Sentence
plural c
t1 Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"with" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
plural c
t1 Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"with" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Creates a 'NP' by combining two 'NamedIdea's with the word "of" between
-- their terms. Plural case is @(phrase t1) "of" (plural t2)@.
of_ :: (NamedIdea c, NamedIdea d) => c -> d -> NP
of_ :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
of_ c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.of_` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.of_` forall n. NamedIdea n => n -> Sentence
plural d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Same as 'of_' but second argument is a `NounPhrase`.
of_NINP :: (NamedIdea c, NounPhrase d) => c -> d -> NP
of_NINP :: forall c d. (NamedIdea c, NounPhrase d) => c -> d -> NP
of_NINP c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.of_` forall n. NounPhrase n => n -> Sentence
phraseNP d
t2)
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.of_` forall n. NounPhrase n => n -> Sentence
pluralNP d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Same as 'of_' but first argument is a `NounPhrase` 
-- and plural case is @(plural t1) "of" (phrase t2)@.
of_PSNPNI :: (NounPhrase c, NamedIdea d) => c -> d -> NP
of_PSNPNI :: forall c d. (NounPhrase c, NamedIdea d) => c -> d -> NP
of_PSNPNI c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NounPhrase n => n -> Sentence
phraseNP c
t1 Sentence -> Sentence -> Sentence
`S.of_` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NounPhrase n => n -> Sentence
pluralNP c
t1 Sentence -> Sentence -> Sentence
`S.of_` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Same as 'of_', except plural case is @(plural t1) "of" (phrase t2)@.
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 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.of_` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
plural c
t1 Sentence -> Sentence -> Sentence
`S.of_` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Same as 'of_PS', except combining 'Sentence' piece is "of a".
ofA :: (NamedIdea c, NamedIdea d) => c -> d -> NP
ofA :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
ofA c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.ofA` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
plural c
t1 Sentence -> Sentence -> Sentence
`S.ofA` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Same as 'ofA', except phrase case is @(plural t1) "of a" (phrase t2)@.
ofAPS :: (NamedIdea c, NamedIdea d) => c -> d -> NP
ofAPS :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
ofAPS c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.ofA` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
plural c
t1 Sentence -> Sentence -> Sentence
`S.ofA` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Same as 'of_', except combining 'Sentence' piece is "of the". Plural case is @(phrase t1) `S.ofThe` (plural t2)@.
ofThe :: (NamedIdea c, NamedIdea d) => c -> d -> NP
ofThe :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
ofThe c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.ofThe` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.ofThe` forall n. NamedIdea n => n -> Sentence
plural d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Same as 'ofThe', except plural case is @(plural t1) `S.ofThe` (phrase t2)@.
ofThePS :: (NamedIdea c, NamedIdea d) => c -> d -> NP
ofThePS :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
ofThePS c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.ofThe` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
plural c
t1 Sentence -> Sentence -> Sentence
`S.ofThe` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Same as 'ofThe', except prepends "the".
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 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.the_ofThe` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.the_ofThe` forall n. NamedIdea n => n -> Sentence
plural d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Same as 'the_ofThe', except plural case is @(plural t1) `S.the_ofThe` (phrase t2)@
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 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.the_ofThe` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
plural c
t1 Sentence -> Sentence -> Sentence
`S.the_ofThe` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Same as 'of_', except combining Sentence piece is "on the".
onThe :: (NamedIdea c, NamedIdea d) => c -> d -> NP
onThe :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
onThe c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.onThe` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.onThe` forall n. NamedIdea n => n -> Sentence
plural d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Same as 'onThe', except plural case is (plural t1) S.onThe (phrase t2)
onThePS :: (NamedIdea c, NamedIdea d) => c -> d -> NP
onThePS :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
onThePS c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.onThe` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
plural c
t1 Sentence -> Sentence -> Sentence
`S.onThe` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Same as 'onThe', except plural case is (plural t1) S.onThe (plural t2)
onThePP :: (NamedIdea c, NamedIdea d) => c -> d -> NP
onThePP :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
onThePP c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.onThe` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
plural c
t1 Sentence -> Sentence -> Sentence
`S.onThe` forall n. NamedIdea n => n -> Sentence
plural d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Creates a 'NP' by combining two 'NamedIdea's with the words "in the" between
-- their terms. Plural case is @(phrase t1) "in the" (plural t2)@.
inThe :: (NamedIdea c, NamedIdea d) => c -> d -> NP
inThe :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
inThe c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.inThe` forall n. NamedIdea n => n -> Sentence
phrase d
t2) 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.inThe` forall n. NamedIdea n => n -> Sentence
plural d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Creates a 'NP' by combining two 'NamedIdea's with the words "in the" between
-- their terms. Plural case is @(plural t1) "in the" (phrase t2)@.
inThePS :: (NamedIdea c, NamedIdea d) => c -> d -> NP
inThePS :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
inThePS c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.inThe` forall n. NamedIdea n => n -> Sentence
phrase d
t2) 
  (forall n. NamedIdea n => n -> Sentence
plural c
t1 Sentence -> Sentence -> Sentence
`S.inThe` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Creates a 'NP' by combining two 'NamedIdea's with the words "in the" between
-- their terms. Plural case is @(plural t1) "in the" (plural t2)@.
inThePP :: (NamedIdea c, NamedIdea d) => c -> d -> NP
inThePP :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
inThePP c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.inThe` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
plural c
t1 Sentence -> Sentence -> Sentence
`S.inThe` forall n. NamedIdea n => n -> Sentence
plural d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Creates a 'NP' by combining two 'NamedIdea's with the words "is the" between
-- their terms. Plural case is @(phrase t1) "is the" (plural t2)@.
isThe :: (NamedIdea c, NamedIdea d) => c -> d -> NP
isThe :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
isThe c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.isThe` forall n. NamedIdea n => n -> Sentence
phrase d
t2) 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.isThe` forall n. NamedIdea n => n -> Sentence
plural d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Creates a 'NP' by combining two 'NamedIdea's with the words "to the" between
-- their terms. Plural case is @(phrase t1) "to the" (plural t2)@.
toThe :: (NamedIdea c, NamedIdea d) => c -> d -> NP
toThe :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
toThe c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.toThe` forall n. NamedIdea n => n -> Sentence
phrase d
t2) 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.toThe` forall n. NamedIdea n => n -> Sentence
plural d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

--FIXME: As mentioned in issue #487, the following should be re-examined later,
--       as they may embody a deeper idea in some cases.

-- we might want to eventually restrict the use of these via
-- some kind of type system, which asserts that:
-- 1. t1 `for` t2 means that t1 is a view of part of the reason behind t2
-- 2. t1 `of_` t2 means that t1 is a view of part of the structure of t2

-- | Creates a 'NP' by combining two 'NamedIdea's with the word "for" between
-- their terms. Plural case is @(phrase t1) "for" (plural t2)@.
for :: (NamedIdea c, NamedIdea d) => c -> d -> NP
for :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
for c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.for` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.for` forall n. NamedIdea n => n -> Sentence
plural d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Similar to 'for', but takes two functions that determine the 'titleCase'.
forTGen :: (NamedIdea c, Idea d) => (c -> Sentence) -> (d -> Sentence) -> c -> d -> NP
forTGen :: forall c d.
(NamedIdea c, Idea d) =>
(c -> Sentence) -> (d -> Sentence) -> c -> d -> NP
forTGen c -> Sentence
f1 d -> Sentence
f2 c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.for` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
plural c
t1 Sentence -> Sentence -> Sentence
`S.for` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  CapitalizationRule
CapFirst
  (Sentence -> CapitalizationRule
Replace (c -> Sentence
f1 c
t1 Sentence -> Sentence -> Sentence
`S.for` d -> Sentence
f2 d
t2))

-- | Creates a 'NP' by combining two 'NamedIdea's with the word "in" between
-- their terms. Plural case is @(phrase t1) "in" (plural 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 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.in_` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.in_` forall n. NamedIdea n => n -> Sentence
plural d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Same as 'in_', except plural case is @(plural t1) "in" (phrase t2)@.
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 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.in_` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
plural c
t1 Sentence -> Sentence -> Sentence
`S.in_` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Creates a 'NP' by combining two 'NamedIdea's with the words "in a" between
-- their terms. Plural case is @(phrase t1) "in a" (plural t2)@.
inA :: (NamedIdea c, NamedIdea d) => c -> d -> NP
inA :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
inA c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"in a" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase d
t2) 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"in a" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
plural d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Creates a 'NP' by combining two 'NamedIdea's with the word "is" between
-- their terms. Plural case is @(phrase t1) "is" (plural t2)@.
is :: (NamedIdea c, NamedIdea d) => c -> d -> NP
is :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
is c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' 
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.is` forall n. NamedIdea n => n -> Sentence
phrase d
t2)
  (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
`S.is` forall n. NamedIdea n => n -> Sentence
plural d
t2)
  CapitalizationRule
CapFirst
  CapitalizationRule
CapWords

-- | Prepends "the" to a 'NamedIdea'.
the :: (NamedIdea t) => t -> NP
the :: forall t. NamedIdea t => t -> NP
the t
t = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' (String -> Sentence
S String
"the" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase t
t) (String -> Sentence
S String
"the" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
plural t
t) CapitalizationRule
CapFirst CapitalizationRule
CapWords

-- | A customizable version of 'the'. The given function is applied to both singular and plural cases.
theGen :: (t -> Sentence) -> t -> NP
theGen :: forall t. (t -> Sentence) -> t -> NP
theGen t -> Sentence
f t
t = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' (String -> Sentence
S String
"the" Sentence -> Sentence -> Sentence
+:+ t -> Sentence
f t
t) (String -> Sentence
S String
"the" Sentence -> Sentence -> Sentence
+:+ t -> Sentence
f t
t) CapitalizationRule
CapFirst CapitalizationRule
CapWords

-- | Prepends "a" to a 'NamedIdea' (similar to 'the').
a_ :: (NamedIdea c) => c -> NP
a_ :: forall t. NamedIdea t => t -> NP
a_ c
t = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' (String -> Sentence
S String
"a" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase c
t) (String -> Sentence
S String
"a" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
plural c
t) CapitalizationRule
CapFirst CapitalizationRule
CapWords

-- | Customizable version of 'a'.
a_Gen :: (c -> Sentence) -> c -> NP
a_Gen :: forall t. (t -> Sentence) -> t -> NP
a_Gen c -> Sentence
f c
t = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' (String -> Sentence
S String
"a" Sentence -> Sentence -> Sentence
+:+ c -> Sentence
f c
t) (String -> Sentence
S String
"a" Sentence -> Sentence -> Sentence
+:+ c -> Sentence
f c
t) CapitalizationRule
CapFirst CapitalizationRule
CapWords

-- | Combinator for combining two 'NamedIdeas's into a 'IdeaDict'. 
-- Plural case only makes second term plural. 
-- See 'compoundPhrase' for more on plural behaviour.
-- /Does not preserve abbreviations/.
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 forall a b. (HasUID a, HasUID b) => a -> b -> UID
+++! b
t2) (forall a b. (NounPhrase a, NounPhrase b) => a -> b -> NP
compoundPhrase (a
t1 forall s a. s -> Getting a s a -> a
^. forall c. NamedIdea c => Lens' c NP
term) (b
t2 forall s a. s -> Getting a s a -> a
^. forall c. NamedIdea c => Lens' c NP
term))

-- | Similar to 'compoundNC' but both terms are pluralized for plural case.
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 forall a b. (HasUID a, HasUID b) => a -> b -> UID
+++! b
t2) ((NP -> Sentence) -> (NP -> Sentence) -> NP -> NP -> NP
compoundPhrase'' forall n. NounPhrase n => n -> Sentence
D.pluralNP forall n. NounPhrase n => n -> Sentence
D.pluralNP (a
t1 forall s a. s -> Getting a s a -> a
^. forall c. NamedIdea c => Lens' c NP
term) (b
t2 forall s a. s -> Getting a s a -> a
^. forall c. NamedIdea c => Lens' c NP
term))

-- | Similar to 'compoundNC', except plural cases are customizable.
compoundNCGen :: (NamedIdea a, NamedIdea b) => 
  (NP -> Sentence) -> (NP -> Sentence) -> a -> b -> IdeaDict
compoundNCGen :: forall a b.
(NamedIdea a, NamedIdea b) =>
(NP -> Sentence) -> (NP -> Sentence) -> a -> b -> IdeaDict
compoundNCGen NP -> Sentence
f1 NP -> Sentence
f2 a
t1 b
t2 = UID -> NP -> IdeaDict
ncUID
  (a
t1 forall a b. (HasUID a, HasUID b) => a -> b -> UID
+++! b
t2)
  ((NP -> Sentence) -> (NP -> Sentence) -> NP -> NP -> NP
compoundPhrase'' NP -> Sentence
f1 NP -> Sentence
f2 (a
t1 forall s a. s -> Getting a s a -> a
^. forall c. NamedIdea c => Lens' c NP
term) (b
t2 forall s a. s -> Getting a s a -> a
^. forall c. NamedIdea c => Lens' c NP
term))

-- | Similar to 'compoundNC', except for plural case, where first parameter gets pluralized while second one stays singular.
compoundNCPS :: IdeaDict -> IdeaDict -> IdeaDict
compoundNCPS :: IdeaDict -> IdeaDict -> IdeaDict
compoundNCPS = forall a b.
(NamedIdea a, NamedIdea b) =>
(NP -> Sentence) -> (NP -> Sentence) -> a -> b -> IdeaDict
compoundNCGen forall n. NounPhrase n => n -> Sentence
D.pluralNP forall n. NounPhrase n => n -> Sentence
D.phraseNP

-- hack for Solution Characteristics Specification, calling upon plural will pluralize
-- Characteristics as it is the end of the first term (solutionCharacteristic)
-- | Similar to 'compoundNC', but takes a function that is applied to the first term (eg. 'short' or 'plural').
compoundNCGenP :: (NamedIdea a, NamedIdea b) => (NP -> Sentence) -> a -> b -> IdeaDict
compoundNCGenP :: forall a b.
(NamedIdea a, NamedIdea b) =>
(NP -> Sentence) -> a -> b -> IdeaDict
compoundNCGenP NP -> Sentence
f1 a
t1 b
t2 = UID -> NP -> IdeaDict
ncUID
  (a
t1 forall a b. (HasUID a, HasUID b) => a -> b -> UID
+++! b
t2) ((NP -> Sentence) -> NP -> NP -> NP
compoundPhrase''' NP -> Sentence
f1 (a
t1 forall s a. s -> Getting a s a -> a
^. forall c. NamedIdea c => Lens' c NP
term) (b
t2 forall s a. s -> Getting a s a -> a
^. forall c. NamedIdea c => Lens' c NP
term))

-- FIXME: Same as above function
-- | Similar to 'compoundNCGenP' but sets first parameter function to plural.
compoundNCPSPP :: IdeaDict -> IdeaDict -> IdeaDict
compoundNCPSPP :: IdeaDict -> IdeaDict -> IdeaDict
compoundNCPSPP = forall a b.
(NamedIdea a, NamedIdea b) =>
(NP -> Sentence) -> a -> b -> IdeaDict
compoundNCGenP forall n. NounPhrase n => n -> Sentence
D.pluralNP

-- | Helper function that combines a 'NamedIdea' and a 'NP' without any words in between.
-- Plural case is @(phrase t1) +:+ (pluralNP t2)@.
combineNINP :: (NamedIdea c) => c -> NP -> NP
combineNINP :: forall c. NamedIdea c => c -> NP -> NP
combineNINP c
t1 NP
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
+:+ forall n. NounPhrase n => n -> Sentence
phraseNP NP
t2) (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
+:+ forall n. NounPhrase n => n -> Sentence
pluralNP NP
t2) CapitalizationRule
CapFirst CapitalizationRule
CapWords

-- | Similar to 'combineNINP' but takes in a 'NP' first and a 'NamedIdea' second.
combineNPNI :: (NamedIdea c) => NP -> c -> NP
combineNPNI :: forall c. NamedIdea c => NP -> c -> NP
combineNPNI NP
t1 c
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' (forall n. NounPhrase n => n -> Sentence
phraseNP NP
t1 Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase c
t2) (forall n. NounPhrase n => n -> Sentence
phraseNP NP
t1 Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
plural c
t2) CapitalizationRule
CapFirst CapitalizationRule
CapWords

-- | Similar to 'combineNINP' but takes two 'NamedIdea's.
combineNINI :: (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI :: forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI c
t1 d
t2 = Sentence
-> Sentence -> CapitalizationRule -> CapitalizationRule -> NP
nounPhrase'' (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase d
t2) (forall n. NamedIdea n => n -> Sentence
phrase c
t1 Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
plural d
t2) CapitalizationRule
CapFirst CapitalizationRule
CapWords