Skip to content

Commit

Permalink
Merge master in.
Browse files Browse the repository at this point in the history
  • Loading branch information
zhaoy148 committed Nov 22, 2018
2 parents 8f39148 + 8f4a567 commit 441b995
Show file tree
Hide file tree
Showing 45 changed files with 530 additions and 282 deletions.
4 changes: 4 additions & 0 deletions code/drasil-data/Data/Drasil/Concepts/Computation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,10 @@ algorithm = dcc "algorithm" (cn' "algorithm")
mod_calc_desc :: Sentence -> ConceptChunk
mod_calc_desc defnFromEx = dccWDS "mod_calc_desc" (cn' "calculation") defnFromEx

compcon :: [NamedChunk]
compcon = [application, computer, structure, dataStruct, dataStruct', dataType, dataType',
inDatum, outDatum, inParam, inVar, inValue, inQty, computerLiteracy, computerApp]

application, computer, structure :: NamedChunk
os :: CI
-------------------------------------------------------------------------------
Expand Down
44 changes: 39 additions & 5 deletions code/drasil-data/Data/Drasil/Concepts/Documentation.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,47 @@
module Data.Drasil.Concepts.Documentation where

import Language.Drasil hiding (organization)
import Language.Drasil hiding (organization, year)

import Data.Drasil.Concepts.Math (graph)
import Data.Drasil.Phrase (andRT, and_, and_', ofA, of_, of_', of__, theCustom,
compoundNC, compoundNC', compoundNCP1)
import Data.Drasil.IdeaDicts
ofN_, compoundNC, compoundNC', compoundNCP1)
import Data.Drasil.IdeaDicts (softEng, documentc)

import Control.Lens ((^.))

doccon :: [NamedChunk]
doccon = [abbreviation, analysis, appendix, aspect, body, characteristic, class_, client,
code, column, company, component, concept, condition, connection, constant,
constraint, consumer, content, context, coordinate, customer, datum, decision,
definition, dependency, description, design, document, documentation, effect,
element, emphasis, endUser, environment, failure, figure, first, form, full,
functional, game, general, goal, guide, implementation, individual, information,
interest, interface, input_, instance_, intReader, introduction, issue, item,
loss, label, library, limitation, literacy, material_, message, method_, module_,
model, name_, nonfunctional, object, offShelf, open, organization, output_,
physics, physical, plan, practice, priority, problem, product_, project,
property, purpose, quantity, realtime, reference, requirement_, response,
result, reviewer, safety, scope, second_, section_, scenario, source,
simulation, software, solution, specific, specification, stakeholder,
standard, statement, symbol_, system, table_, task, template, term_,
terminology, theory, traceyGraph, traceyMatrix, type_, uncertainty, user,
useCase, validation, value, variable, video, verification, year,
orgOfDoc, prpsOfDoc, refmat, scpOfReq, consVals,
termAndDef, tOfSymb, traceyMandG, corSol, charOfIR, propOfCorSol,
vav, designDoc, fullForm, generalSystemDescription, indPRCase,
physicalConstraint, physicalSystem, problemDescription, prodUCTable,
specificsystemdescription, systemdescription, systemConstraint, sysCont,
userCharacteristic, datumConstraint, functionalRequirement,
nonfunctionalRequirement, safetyReq, softwareConstraint, softwareDoc,
softwareReq, softwareSys, softwareVerif, softwareVAV, solutionCharSpec,
solutionCharacteristic, offShelfSolution, physicalSim, productUC,
useCaseTable, physicalProperty, vavPlan, uncertCol, userInput,
scpOfTheProjS]

doccon' :: [CI]
doccon' = [assumption, dataDefn, desSpec, genDefn, goalStmt, dataConst, inModel, likelyChg,
unlikelyChg, physSyst, requirement, thModel, mg, notApp, srs, typUnc]

assumption, dataDefn, desSpec, genDefn, goalStmt, dataConst, inModel, likelyChg,
unlikelyChg, physSyst, requirement, thModel, mg, notApp, srs, typUnc, sec :: CI

Expand Down Expand Up @@ -180,6 +213,7 @@ variable = nc "variable" (cn' "variable" )
verification = nc "verification" (cn' "verification" )
video = nc "video" (cn' "video" )
year = nc "year" (cn' "year" )
scpOfTheProjS = nc "scpOfTheProj" (cn' "scope of the project") -- temporary generated for test


orgOfDoc, prpsOfDoc, refmat, scpOfReq, consVals,
Expand All @@ -200,7 +234,7 @@ vav = nc "vav" (verification `and_` validation)
consVals = nc "consVals" (cn "values of auxiliary constants")

scpOfTheProj :: (NamedChunk -> Sentence) -> NamedChunk
scpOfTheProj oper = nc "scpOfTheProj" (scope `of_` theCustom oper project) -- reasonable hack?
scpOfTheProj oper = nc "scpOfTheProj" (scope `ofN_` theCustom oper project) -- reasonable hack?

-- compounds

Expand Down Expand Up @@ -279,4 +313,4 @@ srsDomains = [reqDom, funcReqDom, assumpDom, likeChgDom, unlikeChgDom]
-- ideas themselves. Ex. @fterms compoundPhrase t1 t2@ instead of
-- @compoundPhrase (t1 ^. term) (t2 ^. term)@
fterms :: (NamedIdea c, NamedIdea d) => (NP -> NP -> t) -> c -> d -> t
fterms f a b = f (a ^. term) (b ^. term)
fterms f a b = f (a ^. term) (b ^. term)
7 changes: 7 additions & 0 deletions code/drasil-data/Data/Drasil/Concepts/Education.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,13 @@ import Data.Drasil.Concepts.Documentation as Doc (first, physics, second_, year)
import Data.Drasil.Concepts.PhysicalProperties (solid)
import Data.Drasil.Phrase (compoundNC)

educon :: [NamedChunk]
educon = [calculus, civil, degree_, engineering, structural, mechanics,
undergraduate, highSchool, physical_, chemistry, undergradDegree,
scndYrCalculus, solidMechanics, secondYear, structuralEng,
structuralMechanics, civilEng, highSchoolCalculus, highSchoolPhysics,
frstYr, physChem]

calculus, civil, degree_, engineering, structural, mechanics,
undergraduate, highSchool, physical_, chemistry :: NamedChunk

Expand Down
10 changes: 9 additions & 1 deletion code/drasil-data/Data/Drasil/Concepts/Math.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,18 @@
module Data.Drasil.Concepts.Math where

import Language.Drasil
import Language.Drasil hiding (number)
import Control.Lens ((^.))
import Data.Drasil.IdeaDicts

import Data.Drasil.Phrase(of_)
mathcon :: [ConceptChunk]
mathcon = [angle, area, calculation, diameter, equation, euclidN, euclidSpace, gradient,
graph, law, matrix, norm, normal, normalV, number, orient, parameter, perp,
perpV, probability, shape, surArea, surface, unit_, unitV, vector, rate,
change, rOfChng, constraint]

mathcon' :: [CI]
mathcon' = [pde, ode, de]

angle, area, calculation, diameter, equation, euclidN, euclidSpace, gradient,
graph, law, matrix, norm, normal, normalV, number, orient, parameter, perp,
Expand Down
4 changes: 4 additions & 0 deletions code/drasil-data/Data/Drasil/Concepts/PhysicalProperties.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,10 @@ import Language.Drasil
import Data.Drasil.Concepts.Documentation (material_, property)
import Data.Drasil.Phrase (compoundNC)

physicalcon :: [ConceptChunk]
physicalcon = [gaseous, liquid, solid, ctrOfMass, density, mass, len, dimension,
vol, flexure]

gaseous, liquid, solid, ctrOfMass, density, mass, len, dimension,
vol, flexure :: ConceptChunk

Expand Down
11 changes: 10 additions & 1 deletion code/drasil-data/Data/Drasil/Concepts/Physics.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,13 +4,22 @@ module Data.Drasil.Concepts.Physics
, momentOfInertia, force, impulseS, impulseV, displacement
, gravitationalAccel, gravitationalConst, position, distance
, time, torque, fbd, angular, linear, tension, compression, stress, strain
, angDisp, angVelo, angAccel, linDisp, linVelo, linAccel, joint, damping
, angDisp, angVelo, angAccel, linDisp, linVelo, linAccel, joint, damping, physicCon
) where
--This is obviously a bad name, but for now it will do until we come
-- up with a better one.
import Language.Drasil
import Control.Lens((^.)) --need for parametrization hack

physicCon :: [ConceptChunk]
physicCon = [rigidBody, velocity, friction, elasticity, energy, mech_energy, collision, space,
cartesian, rightHand, restitutionCoef, acceleration,
momentOfInertia, force, impulseS, impulseV, displacement,
gravitationalAccel, gravitationalConst, position, distance,
time, torque, fbd, linear, angular, tension, compression, stress,
strain, angDisp, angVelo, angAccel, linDisp, linVelo, linAccel,
joint, damping, pressure]

rigidBody, velocity, friction, elasticity, energy, mech_energy, collision, space,
cartesian, rightHand, restitutionCoef, acceleration,
momentOfInertia, force, impulseS, impulseV, displacement,
Expand Down
5 changes: 5 additions & 0 deletions code/drasil-data/Data/Drasil/Concepts/Software.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,11 @@ import Data.Drasil.Concepts.Documentation (srs)
import Data.Drasil.SentenceStructures (foldlSent)
import Control.Lens ((^.))

softwarecon :: [ConceptChunk]
softwarecon = [correctness, verifiability, physLib,
understandability, reusability, maintainability, portability,
performance, program, errMsg, accuracy, correctness, reliability]

c, errMsg, physLib, program :: ConceptChunk

c = dcc "c" (pn "C")
Expand Down
5 changes: 4 additions & 1 deletion code/drasil-data/Data/Drasil/Concepts/SolidMechanics.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,9 @@ import Data.Drasil.Concepts.Physics (force, friction, strain, stress)

--FIXME: add "shear stress" and "shear strain" when we have adjectives
-- to make a combined "mobilized shear force" for example
solidcon :: [ConceptChunk]
solidcon = [elastMod, mobShear, normForce, nrmStrss, poissnsR, shearForce,
shearRes, stffness]

elastMod, mobShear, normForce, nrmStrss, poissnsR, shearForce,
shearRes, stffness :: ConceptChunk
Expand All @@ -29,7 +32,7 @@ poissnsR = dccWDS "poissnsR" (nounPhraseSP "Poisson's ratio")
(S "The ratio of perpendicular" +:+ phrase strain +:+
S "to parallel" +:+. phrase strain)

shearRes = dccWDS "shearRes" (cn "shear resistance")
shearRes = dccWDS "shearRes" (cn "resistive shear force")
(S "The resulting" +:+ phrase friction +:+
S "caused by a shear" +:+. phrase stress)

Expand Down
5 changes: 5 additions & 0 deletions code/drasil-data/Data/Drasil/Concepts/Thermodynamics.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,11 @@ import Data.Drasil.Concepts.Physics (energy)

import Control.Lens((^.))

thermocon :: [ConceptChunk]
thermocon = [boiling, boil_pt, degree_', law_cons_energy, law_conv_cooling, latent_heat, melting, melt_pt, phase_change,
sens_heat, temp, thermal_analysis, thermal_conduction, thermal_energy,
thermal_conductor, heat, heat_cap_spec, ht_flux, heat_trans, ht_trans_theo, ener_src]

boiling, boil_pt, degree_', law_cons_energy, law_conv_cooling, latent_heat, melting, melt_pt, phase_change,
sens_heat, temp, thermal_analysis, thermal_conduction, thermal_energy,
thermal_conductor, heat, heat_cap_spec, ht_flux, heat_trans, ht_trans_theo, ener_src :: ConceptChunk
Expand Down
28 changes: 18 additions & 10 deletions code/drasil-data/Data/Drasil/Phrase.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,6 +47,13 @@ of_ t1 t2 = nounPhrase''
(Replace ((at_start t1) +:+ S "of" +:+ (phrase t2)))
(Replace ((titleize t1) +:+ S "of" +:+ (titleize t2)))

ofN_ :: (NamedIdea c, NounPhrase d) => c -> d -> NP
ofN_ t1 t2 = nounPhrase''
((phrase t1) +:+ S "of" +:+ (phraseNP t2))
((phrase t1) +:+ S "of" +:+ (pluralNP t2))
(Replace ((at_start t1) +:+ S "of" +:+ (phraseNP t2)))
(Replace ((titleize t1) +:+ S "of" +:+ (titleizeNP t2)))

-- | Creates a noun phrase by combining two 'NamedIdea's with the word "of" between
-- them. 'phrase' is defaulted to @(phrase t1) "of" (plural t2)@. Plural is the same.
of_' :: (NamedIdea c, NamedIdea d) => c -> d -> NP
Expand Down Expand Up @@ -103,13 +110,14 @@ for' t1 t2 = (titleize t1) +:+ S "for" +:+ (short t2)
for'' :: (NamedIdea c, NamedIdea d) => (c -> Sentence) -> (d -> Sentence) -> c -> d -> Sentence
for'' f1 f2 t1 t2 = (f1 t1) +:+ S "for" +:+ (f2 t2)

the :: (NamedIdea t) => t -> NamedChunk
the t = nc ("the" ++ t ^. uid)
(nounPhrase'' (S "the" +:+ phrase t) (S "the" +:+ plural t) CapFirst CapWords)
the' :: (NamedIdea t) => t -> NP
the' t = nounPhrase'' (S "the" +:+ titleize t) (S "the" +:+ titleize' t) CapWords CapWords

the :: (NamedIdea t) => t -> NP
the t = nounPhrase'' (S "the" +:+ phrase t) (S "the" +:+ plural t) CapWords CapWords

theCustom :: (NamedIdea t) => (t -> Sentence) -> t -> NamedChunk
theCustom f t = nc ("the" ++ t ^. uid) (nounPhrase''(S "the" +:+ f t)
(S "the" +:+ f t) CapFirst CapWords)
theCustom :: (NamedIdea t) => (t -> Sentence) -> t -> NP
theCustom f t = nounPhrase''(S "the" +:+ f t) (S "the" +:+ f t) CapFirst CapWords

-- | Combinator for combining two 'NamedChunk's into one.
-- /Does not preserve abbreviations/
Expand All @@ -119,18 +127,18 @@ compoundNC t1 t2 = nc

compoundNC' :: (NamedIdea a, NamedIdea b) => a -> b -> NamedChunk
compoundNC' t1 t2 = nc
(t1^.uid ++ t2^.uid) (compoundPhrase'' D.plural D.plural (t1 ^. term) (t2 ^. term))
(t1^.uid ++ t2^.uid) (compoundPhrase'' D.pluralNP D.pluralNP (t1 ^. term) (t2 ^. term))

compoundNC'' :: (NamedIdea a, NamedIdea b) =>
(NP -> Sentence) -> (NP -> Sentence) -> a -> b -> NamedChunk
compoundNC'' f1 f2 t1 t2 = nc
(t1 ^. uid ++ t2 ^. uid) (compoundPhrase'' f1 f2 (t1 ^. term) (t2 ^. term))

compoundNCPlPh :: NamedChunk -> NamedChunk -> NamedChunk
compoundNCPlPh = compoundNC'' D.plural D.phrase
compoundNCPlPh = compoundNC'' D.pluralNP D.phraseNP

compoundNCPlPl :: NamedChunk -> NamedChunk -> NamedChunk
compoundNCPlPl = compoundNC'' D.plural D.plural
compoundNCPlPl = compoundNC'' D.pluralNP D.pluralNP

-- hack for Solution Characteristics Specification, calling upon plural will pluralize
-- Characteristics as it is the end of the first term (solutionCharacteristic)
Expand All @@ -139,5 +147,5 @@ compoundNC''' f1 t1 t2 = nc
(t1^.uid ++ t2^.uid) (compoundPhrase''' f1 (t1 ^. term) (t2 ^. term))

compoundNCP1 :: NamedChunk -> NamedChunk -> NamedChunk
compoundNCP1 = compoundNC''' D.plural
compoundNCP1 = compoundNC''' D.pluralNP

50 changes: 28 additions & 22 deletions code/drasil-data/Data/Drasil/Quantities/Physics.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
module Data.Drasil.Quantities.Physics where

import Language.Drasil
import Data.Drasil.Concepts.Physics as CP (angAccel, angDisp, angVelo,
import qualified Data.Drasil.Concepts.Physics as CP (angAccel, angDisp, angVelo,
acceleration, displacement, distance, energy, force, gravitationalAccel,
gravitationalConst, impulseS, impulseV, linAccel, linDisp, linVelo,
momentOfInertia, position, pressure, restitutionCoef, time, torque, velocity)
Expand All @@ -12,29 +12,35 @@ import Data.Drasil.Units.Physics (accelU, angAccelU, angVelU, gravConstU,
restitutionCoef :: DefinedQuantityDict
restitutionCoef = dqd' CP.restitutionCoef (const $ sub cC cR) Real Nothing

physicscon :: [UnitalChunk]
physicscon = [angularAccel, angularDisplacement, angularVelocity, acceleration, displacement,
distance, energy, force, gravitationalAccel, gravitationalConst, impulseS,
impulseV, linearAccel, linearDisplacement, linearVelocity, momentOfInertia,
position, pressure, time, torque, velocity]

angularAccel, angularDisplacement, angularVelocity, acceleration, displacement,
distance, energy, force, gravitationalAccel, gravitationalConst, impulseS,
impulseV, linearAccel, linearDisplacement, linearVelocity, momentOfInertia,
position, pressure, time, torque, velocity :: UnitalChunk

angularAccel = uc CP.angAccel lAlpha angAccelU
angularDisplacement = uc CP.angDisp lTheta radian
angularVelocity = uc CP.angVelo lOmega angVelU
acceleration = uc CP.acceleration (vec lA) accelU
displacement = uc CP.displacement (vec lR) metre
distance = uc CP.distance lR metre
energy = uc CP.energy cE joule
force = uc CP.force (vec cF) newton
gravitationalAccel = uc CP.gravitationalAccel lG accelU
gravitationalConst = uc CP.gravitationalConst cG gravConstU
impulseS = uc CP.impulseS lJ impulseU
impulseV = uc CP.impulseV (vec cJ) impulseU
linearAccel = uc CP.linAccel (Concat [(vec lA), Atomic "(", lT, Atomic ")"]) accelU
linearDisplacement = uc CP.linDisp (Concat [(vec lR), Atomic "(",lT, Atomic ")"]) metre
linearVelocity = uc CP.linVelo (Concat [(vec lV), Atomic "(", lT, Atomic ")"]) velU
momentOfInertia = uc CP.momentOfInertia (vec cI) momtInertU
position = uc CP.position (vec lP) metre
pressure = uc CP.pressure lP pascal
time = uc CP.time lT second
torque = uc CP.torque lTau torqueU
velocity = uc CP.velocity (vec lV) velU
angularAccel = uc CP.angAccel lAlpha angAccelU
angularDisplacement = uc CP.angDisp lTheta radian
angularVelocity = uc CP.angVelo lOmega angVelU
acceleration = uc CP.acceleration (vec lA) accelU
displacement = uc CP.displacement (vec lR) metre
distance = uc CP.distance lR metre
energy = uc CP.energy cE joule
force = uc CP.force (vec cF) newton
gravitationalAccel = uc CP.gravitationalAccel lG accelU
gravitationalConst = uc CP.gravitationalConst cG gravConstU
impulseS = uc CP.impulseS lJ impulseU
impulseV = uc CP.impulseV (vec cJ) impulseU
linearAccel = uc CP.linAccel (Concat [(vec lA), Atomic "(", lT, Atomic ")"]) accelU
linearDisplacement = uc CP.linDisp (Concat [(vec lR), Atomic "(",lT, Atomic ")"]) metre
linearVelocity = uc CP.linVelo (Concat [(vec lV), Atomic "(", lT, Atomic ")"]) velU
momentOfInertia = uc CP.momentOfInertia (vec cI) momtInertU
position = uc CP.position (vec lP) metre
pressure = uc CP.pressure lP pascal
time = uc CP.time lT second
torque = uc CP.torque lTau torqueU
velocity = uc CP.velocity (vec lV) velU
3 changes: 3 additions & 0 deletions code/drasil-data/Data/Drasil/Software/Products.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,9 @@ import Data.Drasil.Concepts.Software (program)
import Data.Drasil.IdeaDicts


prodtcon :: [NamedChunk]
prodtcon = [sciCompS, videoGame, openSource, compPro]

matlab :: CI
matlab = commonIdeaWithDict "matlab" (pn' "MATLAB programming language") "MATLAB" [progLanguage]

Expand Down
6 changes: 3 additions & 3 deletions code/drasil-docLang/Drasil/DocLang/SRS.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ import qualified Data.Drasil.Concepts.Documentation as Doc (appendix,
solutionCharSpec, specificsystemdescription, srs, stakeholder, sysCont,
systemConstraint, termAndDef, terminology, thModel, traceyMandG, tOfSymb,
userCharacteristic)
import Data.Drasil.Phrase (for'', the)
import Data.Drasil.Phrase (for'', the, the')

-- Local function to keep things looking clean, not exported.
forTT :: (NamedIdea c, NamedIdea d) => c -> d -> Sentence
Expand Down Expand Up @@ -53,8 +53,8 @@ charOfIR cs ss = section' (titleize' Doc.charOfIR) cs ss "ReaderChars"
orgOfDoc cs ss = section' (titleize Doc.orgOfDoc) cs ss "DocOrg"

stakeholder cs ss = section' (titleize' Doc.stakeholder) cs ss "Stakeholder"
theCustomer cs ss = section' (titleize $ the Doc.customer) cs ss "Customer"
theClient cs ss = section' (titleize $ the Doc.client) cs ss "Client"
theCustomer cs ss = section' (titleizeNP $ the' Doc.customer) cs ss "Customer"
theClient cs ss = section' (titleizeNP $ the' Doc.client) cs ss "Client"

genSysDes cs ss = section' (titleize Doc.generalSystemDescription) cs ss "GenSysDesc"
sysCont cs ss = section' (titleize Doc.sysCont) cs ss "SysContext"
Expand Down
2 changes: 1 addition & 1 deletion code/drasil-docLang/Drasil/DocumentLanguage.hs
Original file line number Diff line number Diff line change
Expand Up @@ -272,7 +272,7 @@ mkRefSec si (RefProg c l) = section'' (titleize refmat) [c]
(nub v))
at_start] []
mkSubRef SI {_concepts = cccs} (TSymb' f con) = mkTSymb cccs f con
mkSubRef SI {_sysinfodb = db} TAandA =
mkSubRef SI {_usedinfodb = db} TAandA =
table_of_abb_and_acronyms $ nub $ Map.elems (db ^. termTable)

-- | Helper for creating the table of symbols
Expand Down
8 changes: 4 additions & 4 deletions code/drasil-docLang/Drasil/Sections/Stakeholders.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,20 +20,20 @@ stakehldrGeneral kWord clientDetails = (SRS.stakeholder) [stakeholderIntro] subs
stakeholderIntro :: Contents
stakeholderIntro = foldlSP [S "This", (phrase section_),
S "describes the" +: (plural stakeholder), S "the people who have an",
(phrase interest), S "in", (phrase $ the product_)]
(phrase interest), S "in", (phraseNP $ the product_)]

tClientF :: (Idea a) => a -> Sentence -> Section
tClientF kWord details = SRS.theClient [clientIntro kWord details] []

clientIntro :: (Idea a) => a -> Sentence -> Contents
clientIntro kWord details = foldlSP [(at_start $ the client),
clientIntro kWord details = foldlSP [(at_startNP $ the client),
S "for", (short kWord), S "is" +:+. details,
(at_start $ the client), S "has the final say on acceptance of the",
(at_startNP $ the client), S "has the final say on acceptance of the",
(phrase product_)]

tCustomerF :: (Idea a) => a -> Section
tCustomerF kWord = SRS.theCustomer [customerIntro kWord] []

customerIntro :: (Idea a) => a -> Contents
customerIntro kWord = foldlSP [(at_start' $ the customer),
customerIntro kWord = foldlSP [(at_startNP' $ the customer),
S "are the", (phrase endUser), S "of", (short kWord)]
Loading

0 comments on commit 441b995

Please sign in to comment.