Skip to content

Commit

Permalink
update GlassBR to generate output requirement
Browse files Browse the repository at this point in the history
  • Loading branch information
samm82 committed Jul 14, 2023
1 parent 35b261a commit c3f57fd
Show file tree
Hide file tree
Showing 19 changed files with 413 additions and 118 deletions.
6 changes: 3 additions & 3 deletions code/drasil-example/glassbr/lib/Drasil/GlassBR/Body.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ import Drasil.GlassBR.Assumptions (assumptionConstants, assumptions)
import Drasil.GlassBR.Changes (likelyChgs, unlikelyChgs)
import Drasil.GlassBR.Concepts (acronyms, blastRisk, glaPlane, glaSlab, glassBR,
ptOfExplsn, con, con', glass)
import Drasil.GlassBR.DataDefs (qDefns, configFp)
import Drasil.GlassBR.DataDefs (qDefns, configFp, r6DDs)
import qualified Drasil.GlassBR.DataDefs as GB (dataDefs)
import Drasil.GlassBR.Figures
import Drasil.GlassBR.Goals (goals)
Expand All @@ -44,7 +44,7 @@ import Drasil.GlassBR.Requirements (funcReqs, inReqDesc, funcReqsTables, nonfunc
import Drasil.GlassBR.Symbols (symbolsForTable, thisSymbols)
import Drasil.GlassBR.TMods (tMods)
import Drasil.GlassBR.Unitals (blast, blastTy, bomb, explosion, constants,
constrained, inputDataConstraints, inputs, outputs, specParamVals, glassTy,
constrained, inputDataConstraints, inputs, specParamVals, glassTy,
glassTypes, glBreakage, lateralLoad, load, loadTypes, pbTol, probBr, stressDistFac, probBreak,
sD, termsWithAccDefn, termsWithDefsOnly, terms)

Expand All @@ -70,7 +70,7 @@ si = SI {
_datadefs = GB.dataDefs,
_configFiles = configFp,
_inputs = inputs,
_outputs = outputs,
_outputs = map qw iMods ++ map qw r6DDs,
_defSequence = qDefns,
_constraints = constrained,
_constants = constants,
Expand Down
6 changes: 5 additions & 1 deletion code/drasil-example/glassbr/lib/Drasil/GlassBR/DataDefs.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
module Drasil.GlassBR.DataDefs (aspRat, dataDefs, dimLL, qDefns, glaTyFac,
hFromt, loadDF, nonFL, risk, standOffDis, strDisFac, tolPre, tolStrDisFac,
eqTNTWDD, probOfBreak, calofCapacity, calofDemand, pbTolUsr, qRef,configFp)
eqTNTWDD, probOfBreak, calofCapacity, calofDemand, pbTolUsr, qRef, configFp,
r6DDs)
where

import Control.Lens ((^.))
Expand Down Expand Up @@ -36,6 +37,9 @@ dataDefs = [risk, hFromt, loadDF, strDisFac, nonFL, glaTyFac,
dimLL, tolPre, tolStrDisFac, standOffDis, aspRat, eqTNTWDD, probOfBreak,
calofCapacity, calofDemand]

r6DDs :: [DataDefinition]
r6DDs = [risk, strDisFac, nonFL, glaTyFac, dimLL, tolPre, tolStrDisFac, hFromt, aspRat]

qDefns :: [Block SimpleQDef]
qDefns = Parallel hFromtQD {-DD2-} [glaTyFacQD {-DD6-}] : --can be calculated on their own
map (`Parallel` []) [dimLLQD {-DD7-}, strDisFacQD {-DD4-}, riskQD {-DD1-},
Expand Down
20 changes: 4 additions & 16 deletions code/drasil-example/glassbr/lib/Drasil/GlassBR/Requirements.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,6 @@ import Drasil.GlassBR.Assumptions (assumpSV, assumpGL, assumptionConstants)
import Drasil.GlassBR.Concepts (glass)
import Drasil.GlassBR.DataDefs (aspRat, dimLL, glaTyFac, hFromt, loadDF, nonFL,
risk, standOffDis, strDisFac, tolPre, tolStrDisFac)
import Drasil.GlassBR.IMods (iMods)
import Drasil.GlassBR.TMods (lrIsSafe, pbIsSafe)
import Drasil.GlassBR.Unitals (blast, isSafeLR, isSafePb, loadSF, notSafe,
pbTolfail, safeMessage)
Expand All @@ -34,19 +33,18 @@ import Drasil.GlassBR.Unitals (blast, isSafeLR, isSafePb, loadSF, notSafe,

funcReqs :: [ConceptInstance]
funcReqs = [sysSetValsFollowingAssumps, checkInputWithDataCons,
outputValsAndKnownValues, checkGlassSafety, outputValues]
outputValsAndKnownValues, checkGlassSafety]

funcReqsTables :: [LabelledContent]
funcReqsTables = [sysSetValsFollowingAssumpsTable, outputValuesTable]
funcReqsTables = [sysSetValsFollowingAssumpsTable]

sysSetValsFollowingAssumps, checkInputWithDataCons,
outputValsAndKnownValues, checkGlassSafety, outputValues :: ConceptInstance
outputValsAndKnownValues, checkGlassSafety :: ConceptInstance

sysSetValsFollowingAssumps = cic "sysSetValsFollowingAssumps" sysSetValsFollowingAssumpsDesc "System-Set-Values-Following-Assumptions" funcReqDom
checkInputWithDataCons = cic "checkInputWithDataCons" checkInputWithDataConsDesc "Check-Input-with-Data_Constraints" funcReqDom
outputValsAndKnownValues = cic "outputValsAndKnownValues" outputValsAndKnownValuesDesc "Output-Values-and-Known-Values" funcReqDom
checkGlassSafety = cic "checkGlassSafety" checkGlassSafetyDesc "Check-Glass-Safety" funcReqDom
outputValues = cic "outputValues" outputValuesDesc "Output-Values" funcReqDom

inReqDesc, sysSetValsFollowingAssumpsDesc, checkInputWithDataConsDesc, outputValsAndKnownValuesDesc, checkGlassSafetyDesc :: Sentence

Expand All @@ -60,7 +58,7 @@ sysSetValsFollowingAssumpsTable :: LabelledContent
sysSetValsFollowingAssumpsTable = mkValsSourceTable (mkQRTupleRef r2AQs r2ARs ++ mkQRTuple r2DDs) "ReqAssignments"
(S "Required Assignments" `follows` sysSetValsFollowingAssumps)
where
r2AQs = qw loadSF : map qw (take 4 assumptionConstants)
r2AQs = qw loadSF : map qw (take 4 assumptionConstants)
r2ARs = assumpGL : replicate 4 assumpSV
r2DDs = [loadDF, hFromt, glaTyFac, standOffDis, aspRat]

Expand All @@ -82,16 +80,6 @@ checkGlassSafetyDesc = foldlSent_ [S "If", eS $ sy isSafePb $&& sy isSafeLR,
S "If the", phrase condition, S "is false, then", phrase output_,
phraseNP (the message), Quote (notSafe ^. defn)]

outputValuesDesc :: Sentence
outputValuesDesc = foldlSent [titleize output_, pluralNP (the value), S "from the table for", namedRef outputValuesTable (S "Required Outputs")]

outputValuesTable :: LabelledContent
outputValuesTable = mkValsSourceTable (mkQRTuple iMods ++ mkQRTuple r6DDs) "ReqOutputs"
(S "Required" +:+ titleize' output_ `follows` outputValues)
where
r6DDs :: [DataDefinition]
r6DDs = [risk, strDisFac, nonFL, glaTyFac, dimLL, tolPre, tolStrDisFac, hFromt, aspRat]

{--Nonfunctional Requirements--}

nonfuncReqs :: [ConceptInstance]
Expand Down
9 changes: 5 additions & 4 deletions code/drasil-example/glassbr/lib/Drasil/GlassBR/Symbols.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,20 +3,21 @@ module Drasil.GlassBR.Symbols where
import Language.Drasil (QuantityDict, qw)
import Language.Drasil.Code (Mod(Mod), asVC)

import Drasil.GlassBR.DataDefs (r6DDs)
import Drasil.GlassBR.IMods (iMods)
import Drasil.GlassBR.ModuleDefs (allMods, implVars)
import Drasil.GlassBR.Unitals (inputDataConstraints, inputs, outputs,
specParamVals, symbols, symbolsWithDefns, unitless, tmSymbols, interps)
import Drasil.GlassBR.Unitals (inputDataConstraints, inputs,
specParamVals, symbols, symbolsWithDefns, unitless, tmSymbols, interps, probBr)

import Data.List ((\\))

symbolsForTable :: [QuantityDict]
symbolsForTable = inputs ++ outputs ++ tmSymbols ++ map qw specParamVals ++
symbolsForTable = inputs ++ map qw iMods ++ map qw r6DDs ++ tmSymbols ++ map qw specParamVals ++
map qw symbolsWithDefns ++ map qw symbols ++ map qw unitless ++
map qw inputDataConstraints ++ interps

thisSymbols :: [QuantityDict]
thisSymbols = map qw iMods
thisSymbols = qw probBr : map qw iMods ++ map qw r6DDs
-- include all module functions as symbols
++ (map asVC (concatMap (\(Mod _ _ _ _ l) -> l) allMods) \\ symbolsForTable)
++ map qw implVars ++ symbolsForTable
4 changes: 2 additions & 2 deletions code/drasil-example/glassbr/lib/Drasil/GlassBR/Unitals.hs
Original file line number Diff line number Diff line change
Expand Up @@ -115,8 +115,8 @@ glassTypeCon = constrainedNRV' (dqdNoUnit glassTy lG String)

{--}

outputs :: [QuantityDict]
outputs = map qw [isSafePb, isSafeLR] ++ [qw probBr, qw stressDistFac]
-- outputs :: [QuantityDict]
-- outputs = map qw [isSafePb, isSafeLR] ++ [qw probBr, qw stressDistFac]

tmSymbols :: [QuantityDict]
tmSymbols = map qw [probFail, pbTolfail] ++ map qw [isSafeProb, isSafeLoad]
Expand Down
28 changes: 14 additions & 14 deletions code/stable/glassbr/SRS/HTML/GlassBR_SRS.html

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

28 changes: 14 additions & 14 deletions code/stable/glassbr/SRS/JSON/GlassBR_SRS.ipynb

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

28 changes: 14 additions & 14 deletions code/stable/glassbr/SRS/PDF/GlassBR_SRS.tex

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion code/stable/glassbr/src/cpp/Control.cpp

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

Loading

2 comments on commit c3f57fd

@samm82
Copy link
Collaborator Author

@samm82 samm82 commented on c3f57fd Jul 14, 2023

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I also noticed that GlassBR, in addition to the main output requirement, also has the requirement to output the values that were input and the values for assigned constants:
image

Should these outputs be wrapped into the generated output, or should an issue be opened to potentially generate this requirement as well? Is this a requirement we should be adding to all our examples? @smiths (I personally think this would be a low priority change)

@smiths
Copy link
Collaborator

@smiths smiths commented on c3f57fd Jul 16, 2023

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

@samm82 it is a common, but by no means universal, practice in research software to output the inputs as part of the outputs. (The two outputs here are different, so we don't have a recursive statement.) 😄 The idea is for easy provenance/reproducibility. If someone is looking at their calculated outputs and they wonder where they came from, the information that is needed to reproduce the results is readily available.

Eventually I would see this as an option for users of Drasil. They could select to "output the inputs" if they want to. There is no compelling reason to force this change through all of our examples. It wouldn't be wrong, but it also wouldn't be worth the effort. It would also imply that this is something that should always be done. It would be better to have the flexibility to do it, but not to force it for every current and future example.

Please sign in to comment.