Skip to content

Commit

Permalink
Turn all possible-changed references to use Ref2 in every case (#1053)
Browse files Browse the repository at this point in the history
* Update RefProg language and renderer.

* Silence some warnings.

* Add rProg to Referable and have makeRef2 use that. Use snref for Ref2 in TeX printer.

* Use makeRef2 for ConceptInstance in GlassBR

* Turn all references of AssumpChunk to use makeRef2.

* Turn TM related references to use makeRef2.

* Make GenDef to use new ref2, but there is no GD for GlassBr.

* Turn DD related references to use new ref2.

* Turn IM related references to use new ref2.

* Make RefProg for LabelledContent.

* Implement RefProg for Citation.

* Apply new conceptDomain for Citation.

* Use Ref2 in GamePhysics.

* Use Ref2 in NoPCM.

* Use Ref2 in SSP.

* Use Ref2 in SWHS.
  • Loading branch information
Yuzhi Zhao authored and JacquesCarette committed Nov 23, 2018
1 parent c3cf8e0 commit c03126c
Show file tree
Hide file tree
Showing 26 changed files with 354 additions and 355 deletions.
8 changes: 4 additions & 4 deletions code/drasil-example/Drasil/GamePhysics/Body.hs
Original file line number Diff line number Diff line change
Expand Up @@ -667,16 +667,16 @@ traceMatInstaModelRef, traceMatAssumpRef, traceMatFuncReqRef, traceMatGoalStmtRe
traceMatLikelyChgRef, traceMatDataRef :: [Sentence]

traceMatInstaModel = ["IM1", "IM2", "IM3"]
traceMatInstaModelRef = map makeRefS iModels_new
traceMatInstaModelRef = map makeRef2S iModels_new

traceMatTheoryModel = ["T1", "T2", "T3", "T4", "T5"]
traceMatTheoryModelRef = map makeRefS cpTMods_new
traceMatTheoryModelRef = map makeRef2S cpTMods_new

traceMatDataDef = ["DD1","DD2","DD3","DD4","DD5","DD6","DD7","DD8"]
traceMatDataDefRef = map makeRefS dataDefns
traceMatDataDefRef = map makeRef2S dataDefns

traceMatAssump = ["A1", "A2", "A3", "A4", "A5", "A6", "A7"]
traceMatAssumpRef = map makeRefS newAssumptions
traceMatAssumpRef = map makeRef2S newAssumptions

traceMatFuncReq = ["R1","R2","R3", "R4", "R5", "R6", "R7", "R8"]
traceMatFuncReqRef = map makeRef2S functional_requirements_list'
Expand Down
6 changes: 3 additions & 3 deletions code/drasil-example/Drasil/GamePhysics/Changes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,13 +40,13 @@ likelyChangesStmt1 = (S "internal" +:+ (getAcc CM.ode) :+:

likelyChangesStmt2 = (phrase library) `maybeExpanded`
(S "to deal with edge-to-edge and vertex-to-vertex" +:+
plural CP.collision) +:+ makeRefS newA5
plural CP.collision) +:+ makeRef2S newA5

likelyChangesStmt3 = (phrase library) `maybeExpanded` (
S "to include motion with" +:+ (phrase CP.damping)) +:+ makeRefS newA6
S "to include motion with" +:+ (phrase CP.damping)) +:+ makeRef2S newA6

likelyChangesStmt4 = (phrase library) `maybeExpanded` (S "to include" +:+
(plural CP.joint) `sAnd` (plural CM.constraint)) +:+ (makeRefS newA7)
(plural CP.joint) `sAnd` (plural CM.constraint)) +:+ (makeRef2S newA7)

lcVODES, lcEC, lcID, lcIJC :: ConceptInstance

Expand Down
16 changes: 8 additions & 8 deletions code/drasil-example/Drasil/GamePhysics/DataDefs.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@ cpQDefs = map (\x -> Parallel x []) cpDDefs

ctrOfMassDD :: DataDefinition
ctrOfMassDD = mkDD ctrOfMass [{-- References --}] [{-- Derivation --}] "ctrOfMass"
[makeRefS newA1, makeRefS newA2]
[makeRef2S newA1, makeRef2S newA2]

ctrOfMass :: QDefinition
ctrOfMass = mkQuantDef pos_CM ctrOfMassEqn
Expand Down Expand Up @@ -59,7 +59,7 @@ linDispQDef = foldl (+:+) (EmptyS) def

linDispDD :: DataDefinition
linDispDD = mkDD linDisp [{-- References --}] [{-- Derivation --}] "linDisp"
[makeRefS newA1, makeRefS newA2, makeRefS newA6]
[makeRef2S newA1, makeRef2S newA2, makeRef2S newA6]

linDisp :: QDefinition
linDisp = mkQuantDef QP.linearDisplacement dispEqn
Expand Down Expand Up @@ -89,7 +89,7 @@ linVelQDef = foldl (+:+) (EmptyS) def

linVelDD :: DataDefinition
linVelDD = mkDD linVel [{-- References --}] [{-- Derivation --}] "linVel"
[makeRefS newA1, makeRefS newA2, makeRefS newA6]
[makeRef2S newA1, makeRef2S newA2, makeRef2S newA6]

linVel :: QDefinition
linVel = mkQuantDef QP.linearVelocity velEqn
Expand All @@ -108,7 +108,7 @@ dd3descr = S "linear" +:+ (QP.velocity ^. term) +:+ S "of a" +:+

linAccDD :: DataDefinition
linAccDD = mkDD linAcc [{-- References --}] [{-- Derivation --}] "linAcc"
[makeRefS newA1, makeRefS newA2, makeRefS newA6]
[makeRef2S newA1, makeRef2S newA2, makeRef2S newA6]

linAcc :: QDefinition
linAcc = mkQuantDef QP.linearAccel accelEqn
Expand All @@ -127,7 +127,7 @@ dd4descr = S "linear" +:+ (accel ^. term) +:+ S "of a" +:+

angDispDD :: DataDefinition
angDispDD = mkDD angDisp [{-- References --}] [{-- Derivation --}] "angDisp"
[makeRefS newA1, makeRefS newA2, makeRefS newA6]
[makeRef2S newA1, makeRef2S newA2, makeRef2S newA6]

angDisp :: QDefinition
angDisp = mkQuantDef QP.angularDisplacement angDispEqn
Expand All @@ -146,7 +146,7 @@ dd5descr = (QP.angularDisplacement ^. term) +:+ S "of a" +:+

angVelDD :: DataDefinition
angVelDD = mkDD angVel [{-- References --}] [{-- Derivation --}] "angVel"
[makeRefS newA1, makeRefS newA2, makeRefS newA6]
[makeRef2S newA1, makeRef2S newA2, makeRef2S newA6]

angVel :: QDefinition
angVel = mkQuantDef QP.angularVelocity angVelEqn
Expand All @@ -165,7 +165,7 @@ dd6descr = ((QP.angularVelocity ^. term)) +:+ S "of a" +:+

angAccelDD :: DataDefinition
angAccelDD = mkDD angAccel [{-- References --}] [{-- Derivation --}] "angAccel"
[makeRefS newA1, makeRefS newA2, makeRefS newA6]
[makeRef2S newA1, makeRef2S newA2, makeRef2S newA6]

angAccel :: QDefinition
angAccel = mkQuantDef QP.angularAccel angAccelEqn
Expand All @@ -187,7 +187,7 @@ dd7descr = (QP.angularAccel ^. term) +:+ S "of a" +:+

impulseDD :: DataDefinition
impulseDD = mkDD impulse [{-- References --}] [{-- Derivation --}] "impulse"
[makeRefS newA1, makeRefS newA2, makeRefS newA4, makeRefS newA5]
[makeRef2S newA1, makeRef2S newA2, makeRef2S newA4, makeRef2S newA5]

impulse :: QDefinition
impulse = mkQuantDef QP.impulseS impulseEqn
Expand Down
30 changes: 15 additions & 15 deletions code/drasil-example/Drasil/GamePhysics/IMods.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,14 +50,14 @@ transMotRel = (sy acc_i) $= (deriv (apply1 vel_i QP.time) QP.time)
transMotDesc, transMotLeg :: Sentence
transMotDesc = foldlSent [S "The above equation expresses the total",
(phrase QP.acceleration), S "of the", (phrase CP.rigidBody),
makeRefS newA1, makeRefS newA2, S "i as the sum of",
makeRef2S newA1, makeRef2S newA2, S "i as the sum of",
(phrase QP.gravitationalAccel),
S "(GD3) and", (phrase QP.acceleration), S "due to applied",
(phrase QP.force), S "Fi(t) (T1). The resultant outputs are",
S "then obtained from this equation using", makeRefS linDispDD,
makeRefS linVelDD +:+. makeRefS linAccDD, S" It is currently",
S "assumed that there is no damping", makeRefS newA6,
S "or constraints", makeRefS newA7 +:+. S "involved", makeRefS ctrOfMassDD]
S "then obtained from this equation using", makeRef2S linDispDD,
makeRef2S linVelDD +:+. makeRef2S linAccDD, S" It is currently",
S "assumed that there is no damping", makeRef2S newA6,
S "or constraints", makeRef2S newA7 +:+. S "involved", makeRef2S ctrOfMassDD]

transMotLeg = foldle1 (+:+) (+:+) $ map defList transMotLegTerms

Expand All @@ -83,12 +83,12 @@ rotMotRel = (sy QP.angularAccel) $= deriv
--fixme: need referencing
rotMotDesc, rotMotLeg :: Sentence
rotMotDesc = foldlSent_ [S "The above equation for the total angular acceleration",
S "of the rigid body", makeRefS newA1, makeRefS newA2,
S "of the rigid body", makeRef2S newA1, makeRef2S newA2,
S "i is derived from T5, and the resultant outputs",
S "are then obtained from this equation using", makeRefS angDispDD,
makeRefS angVelDD +:+. makeRefS angAccelDD, S "It is",
S "currently assumed that there is no damping", makeRefS newA6,
S "or constraints", makeRefS newA7 +:+. S "involved", makeRefS newA4]
S "are then obtained from this equation using", makeRef2S angDispDD,
makeRef2S angVelDD +:+. makeRef2S angAccelDD, S "It is",
S "currently assumed that there is no damping", makeRef2S newA6,
S "or constraints", makeRef2S newA7 +:+. S "involved", makeRef2S newA4]

rotMotLeg = foldle1 (+:+) (+:+) $ map defList rotMotLegTerms

Expand Down Expand Up @@ -124,11 +124,11 @@ col2DRel = (apply1 vel_A time_c) $= (apply1 vel_A QP.time) +
--fixme: need referencing
col2DDesc, col2DLeg :: Sentence
col2DDesc = foldlSent_ [S "This instance model is based on our assumptions",
S "regarding rigid body", makeRefS newA1, makeRefS newA2,
S "collisions", makeRefS newA5, S "Again, this does not take",
S "damping", makeRefS newA6, S "or constraints",
makeRefS newA7 +:+. S "into account" +:+. makeRefS newA4,
makeRefS ctrOfMassDD, makeRefS impulseDD]
S "regarding rigid body", makeRef2S newA1, makeRef2S newA2,
S "collisions", makeRef2S newA5, S "Again, this does not take",
S "damping", makeRef2S newA6, S "or constraints",
makeRef2S newA7 +:+. S "into account" +:+. makeRef2S newA4,
makeRef2S ctrOfMassDD, makeRef2S impulseDD]


{--S "Ik is the moment of inertia of the k-th rigid body (kg m2)",
Expand Down
4 changes: 2 additions & 2 deletions code/drasil-example/Drasil/GamePhysics/TMods.hs
Original file line number Diff line number Diff line change
Expand Up @@ -156,7 +156,7 @@ chaslesThmRel = (sy vel_B) $= (sy vel_O) + (cross (sy QP.angularVelocity) (sy r
chaslesThmDesc :: Sentence
chaslesThmDesc = foldlSent [S "The linear", (phrase QP.velocity),
(ch vel_B), (sParen $ Sy $ unit_symb vel_B), S "of any point B in a",
(phrase CP.rigidBody), makeRefS newA1, S "is the sum of the linear",
(phrase CP.rigidBody), makeRef2S newA1, S "is the sum of the linear",
(phrase QP.velocity), (ch vel_O),
(sParen $ Sy $ unit_symb vel_O), S "of the", (phrase $ CP.rigidBody),
S "at the origin (axis of rotation) and the",
Expand Down Expand Up @@ -197,4 +197,4 @@ newtonSLRDesc = foldlSent [S "The net", (phrase QP.torque),
S "denotes the", (phrase QP.momentOfInertia), S "of the" +:+.
(phrase CP.rigidBody), S "We also assume that all",
(plural CP.rigidBody), S "involved are two-dimensional",
makeRefS newA2]
makeRef2S newA2]
30 changes: 15 additions & 15 deletions code/drasil-example/Drasil/NoPCM/Body.hs
Original file line number Diff line number Diff line change
Expand Up @@ -270,7 +270,7 @@ scopeReqEnd tem te wa = foldlSent_ [S "predicts the",
orgDocEnd :: CI -> CI -> CI -> Sentence
orgDocEnd im_ od pro = foldlSent_ [S "The", phrase im_,
sParen (makeRefS SRS.inModelLabel),
S "to be solved is referred to as" +:+. makeRefS eBalanceOnWtr,
S "to be solved is referred to as" +:+. makeRef2S eBalanceOnWtr,
S "The", phrase im_, S "provides the",
titleize od, sParen (short od), S "that model the"
+:+. phrase pro, short pro, S "solves this", short od]
Expand Down Expand Up @@ -417,13 +417,13 @@ iModDesc1 roc temw en wa vo wv ma wm hcw ht hfc csa ta purin _ vhg _ =
`sC` S "over area") +:+. ch csa, S "No",
phrase ht, S "occurs to", (S "outside" `ofThe`
phrase ta) `sC` S "since it has been assumed to be",
phrase purin +:+. sParen (makeRefS newA11), S "Assuming no",
phrase vhg +:+. (sParen (makeRefS newA12) `sC`
phrase purin +:+. sParen (makeRef2S newA11), S "Assuming no",
phrase vhg +:+. (sParen (makeRef2S newA12) `sC`
E (sy vhg $= 0)), S "Therefore, the", phrase M.equation, S "for",
makeRefS rocTempSimp, S "can be written as"]
makeRef2S rocTempSimp, S "can be written as"]

iModDesc2 :: DataDefinition -> [Sentence]
iModDesc2 d1hf = [S "Using", (makeRefS d1hf) `sC` S "this can be written as"]
iModDesc2 d1hf = [S "Using", (makeRef2S d1hf) `sC` S "this can be written as"]

iModDesc3 :: UnitalChunk -> UncertQ -> [Sentence]
iModDesc3 wm hcw = [S "Dividing (3) by", ch wm :+: ch hcw `sC`
Expand Down Expand Up @@ -499,8 +499,8 @@ reqIIV = cic "reqIIV" (titleize input_ +:+ S "the" +:+ plural quantity +:+
plural tank_para `sC` S "material" +:+ plural property +:+
S "and initial" +:+. plural condition) "Input-Inital-Values" funcReqDom
reqFM = cic "reqFM" (S "Use the" +:+ plural input_ +:+ S "in" +:+ makeRef2S reqIIV +:+
S "to find the" +:+ phrase mass +:+ S "needed for" +:+ makeRefS eBalanceOnWtr +:+
S "to" +:+ makeRefS eBalanceOnPCM `sC` S "as follows, where" +:+ ch w_vol `isThe`
S "to find the" +:+ phrase mass +:+ S "needed for" +:+ makeRef2S eBalanceOnWtr +:+
S "to" +:+ makeRef2S eBalanceOnPCM `sC` S "as follows, where" +:+ ch w_vol `isThe`
phrase w_vol +:+ S "and" +:+ (ch tank_vol `isThe` phrase tank_vol) :+:
S ":" +:+ E reqFMExpr) "Find-Mass" funcReqDom -- FIXME: Equation shouldn't be inline.
reqCISPC = cic "reqCISPC" (S "Verify that the" +:+ plural input_ +:+
Expand All @@ -512,14 +512,14 @@ reqOIDQ = cic "reqOIDQ" (titleize' output_ `sAnd` plural input_
S "and derived" +:+ plural quantity +:+ S "in the following list: the" +:+
plural quantity +:+ S "from" +:+ (makeRef2S reqIIV) `sC` S "the" +:+
phrase mass +:+ S "from" +:+ makeRef2S reqFM `sAnd` ch tau_W +:+.
sParen (S "from" +:+ makeRefS eBalanceOnWtr)) "Output-Input-Derivied-Quantities" funcReqDom
sParen (S "from" +:+ makeRef2S eBalanceOnWtr)) "Output-Input-Derivied-Quantities" funcReqDom
reqCTWOT = cic "reqCTWOT" (S "Calculate and output the" +:+ phrase temp_W +:+
sParen (ch temp_W :+: sParen (ch time)) +:+ S "over the" +:+
phrase sim_time) "Calculate-Temperature-Water-Over-Time" funcReqDom
reqCCHEWT = cic "reqCCHEWT"
(S "Calculate and" +:+ phrase output_ +:+ S "the" +:+
phrase w_E +:+ sParen (ch w_E :+: sParen (ch time)) +:+ S "over the" +:+
phrase sim_time +:+. sParen (S "from" +:+ makeRefS heatEInWtr))
phrase sim_time +:+. sParen (S "from" +:+ makeRef2S heatEInWtr))
"Calculate-Change-Heat_Energy-Water-Time" funcReqDom

reqIVRTable :: LabelledContent
Expand Down Expand Up @@ -555,7 +555,7 @@ likelyChgs = [likeChgTCVOD, likeChgTCVOL, likeChgDT, likeChgTLH]

likeChgDT :: ConceptInstance
likeChgDT = cic "likeChgDT" (
(makeRefS newA9NoPCM) :+: S "- The" +:+ phrase model +:+
(makeRef2S newA9NoPCM) :+: S "- The" +:+ phrase model +:+
S "currently only accounts for charging of the tank. That is, increasing the" +:+ phrase temp +:+
S "of the water to match the" +:+ phrase temp +:+ S "of the coil. A more complete"
+:+ phrase model +:+. S "would also account for discharging of the tank")
Expand Down Expand Up @@ -633,7 +633,7 @@ traceDataRef, traceFuncReqRef, traceInstaModelRef, traceAssumpRef, traceTheories
traceDataDefRef, traceLikelyChgRef, traceGenDefRef :: [Sentence]

traceInstaModel = ["IM1", "IM2"]
traceInstaModelRef = map makeRefS [eBalanceOnWtr, heatEInWtr]
traceInstaModelRef = map makeRef2S [eBalanceOnWtr, heatEInWtr]

traceFuncReq = ["R1", "R2", "R3", "R4", "R5", "R6"]
traceFuncReqRef = map makeRef2S reqs
Expand All @@ -643,16 +643,16 @@ traceDataRef = [makeRefS dataConstTable1] --FIXME: Reference section?

traceAssump = ["A1", "A2", "A3", "A4", "A5", "A6", "A7", "A8", "A9", "A10",
"A11", "A12", "A13", "A14"]
traceAssumpRef = map makeRefS assumps_Nopcm_list_new
traceAssumpRef = map makeRef2S assumps_Nopcm_list_new

traceTheories = ["T1"]
traceTheoriesRef = map makeRefS [consThermE]
traceTheoriesRef = map makeRef2S [consThermE]

traceGenDefs = ["GD1", "GD2"]
traceGenDefRef = map makeRefS swhsGDs
traceGenDefRef = map makeRef2S swhsGDs

traceDataDefs = ["DD1"]
traceDataDefRef = map makeRefS [dd1HtFluxC]
traceDataDefRef = map makeRef2S [dd1HtFluxC]

traceLikelyChg = ["LC1", "LC2", "LC3", "LC4"]
traceLikelyChgRef = map makeRef2S likelyChgs
Expand Down
8 changes: 4 additions & 4 deletions code/drasil-example/Drasil/SSP/Changes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ likelyChgCISL :: ConceptInstance
likelyChgCISL = cic "LC_inhomogeneous" lcCISLDesc "Calculate-Inhomogeneous-Soil-Layers" likeChgDom

lcCISLDesc :: Sentence
lcCISLDesc = foldlSent [(makeRefS newA3) +:+ S "- The",
lcCISLDesc = foldlSent [(makeRef2S newA3) +:+ S "- The",
phrase system +:+. S "currently assumes the different layers of the soil are homogeneous",
S "In the future,", plural calculation,
S "can be added for inconsistent soil properties throughout"]
Expand All @@ -40,12 +40,12 @@ unlikelyChg2AO = cic "UC_2donly" uc2AODesc "2D-Analysis-Only"

ucNASLODesc, uc2AODesc :: Sentence

ucNASLODesc = foldlSent [S "Changes related to", (makeRefS newA5) `sAnd`
(makeRefS newA6), S "are not possible due to the dependency",
ucNASLODesc = foldlSent [S "Changes related to", (makeRef2S newA5) `sAnd`
(makeRef2S newA6), S "are not possible due to the dependency",
S "of the", plural calculation, S "on the linear relationship between",
S "interslice normal and shear forces"]

uc2AODesc = foldlSent [makeRefS newA8, S "allows for 2D analysis" +:+.
uc2AODesc = foldlSent [makeRef2S newA8, S "allows for 2D analysis" +:+.
S "with these models only because stress along z-direction is zero",
S "These models do not take into account stress in the z-direction, and",
S "therefore cannot be without manipulation to attempt 3d analysis"]
Expand Down
Loading

0 comments on commit c03126c

Please sign in to comment.