Skip to content

Commit

Permalink
[Small PR] Added Notes to Glass DD6 (#933)
Browse files Browse the repository at this point in the history
* Added glass type notes to DD6 - closes #751

* Renamed t1 and t2 to pb and lr in function names as per comments on #914
  • Loading branch information
samm82 authored and JacquesCarette committed Jul 23, 2018
1 parent 90836ea commit 5480c6c
Show file tree
Hide file tree
Showing 5 changed files with 58 additions and 29 deletions.
8 changes: 4 additions & 4 deletions code/drasil-example/Drasil/GlassBR/Body.hs
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,7 @@ import Drasil.GlassBR.DataDefs (aspRat, dataDefns, gbQDefns, hFromt, strDisFac,
import Drasil.GlassBR.ModuleDefs (allMods)
import Drasil.GlassBR.References (rbrtsn2012)
import Drasil.GlassBR.Symbols (this_symbols)
import Drasil.GlassBR.TMods (tModels, t1SafetyReq, t2SafetyReq, t1IsSafe, t2IsSafe)
import Drasil.GlassBR.TMods (tModels, pbSafetyReq, lrSafetyReq, pbIsSafe, lrIsSafe)
import Drasil.GlassBR.IMods (iModels, calOfCap, calOfDe, probOfBr, probOfBreak,
calofCapacity, calofDemand)

Expand Down Expand Up @@ -130,7 +130,7 @@ mkSRS = RefSec (RefProg intro [TUnits, tsymb [TSPurpose, SymbOrder], TAandA]) :
, SSDSolChSpec
(SCSProg
[ Assumptions
, TMs ([Label] ++ stdFields) [t1IsSafe, t2IsSafe]
, TMs ([Label] ++ stdFields) [pbIsSafe, lrIsSafe]
, GDs [] [] HideDerivation -- No Gen Defs for GlassBR
, DDs' ([Label, Symbol, Units] ++ stdFields) dataDefns ShowDerivation
, IMs ([Label, Input, Output, InConstraints, OutConstraints] ++ stdFields) [probOfBreak, calofCapacity, calofDemand] HideDerivation
Expand Down Expand Up @@ -543,8 +543,8 @@ req4Desc = foldlSent [titleize output_, S "the", plural inQty,
S "from", acroR 2]

req5Desc cmd = foldlSent_ [S "If", (ch is_safe1), S "", (ch is_safe2),
sParen (S "from" +:+ (makeRef (reldefn t1SafetyReq))
`sAnd` (makeRef (reldefn t2SafetyReq))), S "are true" `sC`
sParen (S "from" +:+ (makeRef (reldefn pbSafetyReq))
`sAnd` (makeRef (reldefn lrSafetyReq))), S "are true" `sC`
phrase cmd, S "the", phrase message, Quote (safeMessage ^. defn),
S "If the", phrase condition, S "is false, then", phrase cmd,
S "the", phrase message, Quote (notSafe ^. defn)]
Expand Down
14 changes: 12 additions & 2 deletions code/drasil-example/Drasil/GlassBR/DataDefs.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ import Language.Drasil
import Prelude hiding (log, exp, sqrt)
import Drasil.DocLang (refA)

import Drasil.GlassBR.Concepts (annealed, fullyT, heatS)
import Drasil.GlassBR.Unitals (actualThicknesses, aspectR,
demand, dimlessLoad, gTF, glassTypeAbbrsStr, glassTypeFactors, glass_type,
lDurFac, load_dur, mod_elas, nom_thick, nominalThicknesses, nonFactorL, pb_tol,
Expand Down Expand Up @@ -115,7 +116,7 @@ glaTyFac = mkDataDef gTF glaTyFac_eq

glaTyFacDD :: DataDefinition
glaTyFacDD = mkDD glaTyFac [{-references-}] [{-derivation-}] ""--temporary
Nothing
(Just $ anGlass : ftGlass : hsGlass : [])

--DD7--

Expand Down Expand Up @@ -185,18 +186,27 @@ aspRatDD = mkDD aspRat [{-references-}] [{-derivation-}] ""--temporary
--Additional Notes--

aGrtrThanB :: Sentence
aGrtrThanB = ((ch plate_len) `sC` (ch plate_width) +:+
aGrtrThanB = (ch plate_len `sC` ch plate_width +:+
S "are" +:+ plural dimension +:+ S "of the plate" `sC` S "where" +:+.
sParen (E (sy plate_len $> sy plate_width)))

anGlass :: Sentence
anGlass = (getAcc annealed +:+ S "is" +:+ phrase annealed +:+ S "glass")

arRef :: Sentence
arRef = (ch aspectR +:+ S "is the" +:+ phrase aspectR +:+.
S "defined in DD11")

ftGlass :: Sentence
ftGlass = (getAcc fullyT +:+ S "is" +:+ phrase fullyT +:+ S "glass")

hRef :: Sentence
hRef = (ch min_thick +:+ S "is the minimum thickness" `sC`
S "which is based on the nominal thicknesses" +:+. S "as shown in DD2")

hsGlass :: Sentence
hsGlass = (getAcc heatS +:+ S "is" +:+ phrase heatS +:+ S "glass")

ldfRef :: Sentence
ldfRef = (ch lDurFac +:+ S "is the" +:+ phrase lDurFac +:+.
S "as defined by DD3")
Expand Down
45 changes: 22 additions & 23 deletions code/drasil-example/Drasil/GlassBR/TMods.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Drasil.GlassBR.TMods (tModels, t1SafetyReq, t2SafetyReq,t1IsSafe,t2IsSafe) where
module Drasil.GlassBR.TMods (tModels, pbSafetyReq, lrSafetyReq, pbIsSafe, lrIsSafe) where

import Drasil.GlassBR.Unitals (demand, demandq, is_safe1, is_safe2, lRe,
pb_tol, prob_br)
Expand All @@ -13,48 +13,47 @@ import Data.Drasil.SentenceStructures (foldlSent, isThe, sAnd)
{--}

tModels :: [RelationConcept]
tModels = [t1SafetyReq, t2SafetyReq]
tModels = [pbSafetyReq, lrSafetyReq]

-- FIXME: This is a hack to see if TheoryModel printing will work. This chunk
-- needs to be updated properly.
-- this is the new function but it still uses the t1SafetyReq,
-- so basiclly we have to combine the old function with the new function
-- this is the new function but it still uses the pbSafetyReq,
-- so basically we have to combine the old function with the new function

t1IsSafe :: TheoryModel
t1IsSafe = tm' (cw t1SafetyReq)
pbIsSafe :: TheoryModel
pbIsSafe = tm' (cw pbSafetyReq)
(tc' "isSafe" [qw is_safe1, qw prob_br, qw pb_tol] ([] :: [ConceptChunk])
[] [TCon Invariant $ (sy is_safe1) $= (sy prob_br) $< (sy pb_tol)] [])
"isSafe" --shortname
[t1descr]
[pbSafeDescr]

t1SafetyReq :: RelationConcept
t1SafetyReq = makeRC "safetyReqPb" (nounPhraseSP "Safety Req-Pb")
t1descr ((sy is_safe1) $= (sy prob_br) $< (sy pb_tol))
pbSafetyReq :: RelationConcept
pbSafetyReq = makeRC "safetyReqPb" (nounPhraseSP "Safety Req-Pb")
pbSafeDescr ((sy is_safe1) $= (sy prob_br) $< (sy pb_tol))

t1descr :: Sentence
t1descr = tDescr (is_safe1) s ending
pbSafeDescr :: Sentence
pbSafeDescr = tDescr (is_safe1) s ending
where
s = (ch is_safe1) `sAnd` (ch is_safe2) +:+ sParen (S "from" +:+
(ref t2SafetyReq))
(ref lrSafetyReq))
ending = ((ch prob_br) `isThe` (phrase prob_br)) `sC` S "as calculated in" +:+.
(ref probOfBr) +:+ (ch pb_tol) `isThe` (phrase pb_tol) +:+ S "entered by the user"


t2IsSafe :: TheoryModel
t2IsSafe = tm' (cw t2SafetyReq)
lrIsSafe :: TheoryModel
lrIsSafe = tm' (cw lrSafetyReq)
(tc' "isSafe2" [qw is_safe2, qw lRe, qw demand] ([] :: [ConceptChunk])
[] [TCon Invariant $ (sy is_safe2) $= (sy lRe) $> (sy demand)] []) "isSafe2"
[t2descr]
[lrSafeDescr]

t2SafetyReq :: RelationConcept
t2SafetyReq = makeRC "safetyReqLR" (nounPhraseSP "Safety Req-LR")
t2descr ( (sy is_safe2) $= (sy lRe) $> (sy demand))
lrSafetyReq :: RelationConcept
lrSafetyReq = makeRC "safetyReqLR" (nounPhraseSP "Safety Req-LR")
lrSafeDescr ( (sy is_safe2) $= (sy lRe) $> (sy demand))

t2descr :: Sentence
t2descr = tDescr (is_safe2) s ending
lrSafeDescr :: Sentence
lrSafeDescr = tDescr (is_safe2) s ending
where
s = ((ch is_safe1) +:+ sParen (S "from" +:+ (makeRef ((Definition . Theory)
t1SafetyReq))) `sAnd` (ch is_safe2))
pbSafetyReq))) `sAnd` (ch is_safe2))
ending = (short lResistance) `isThe` (phrase lResistance) +:+
sParen (S "also called capacity") `sC` S "as defined in" +:+.
(ref calOfCap) +:+ (ch demand) +:+ sParen (S "also referred as the" +:+
Expand Down
4 changes: 4 additions & 0 deletions code/stable/glassbr/SRS/GlassBR_SRS.tex
Original file line number Diff line number Diff line change
Expand Up @@ -612,6 +612,10 @@ \subsubsection{Data Definitions}
\item{$g$ is the glass type $g\in{}\{AN,FT,HS\}$ (Unitless)}
\end{symbDescription}
\\ \midrule \\
Notes & AN is annealed glass
FT is fully tempered glass
HS is heat strengthened glass
\\ \midrule \\
Source &
\\ \midrule \\
RefBy & FIXME: This needs to be filled in
Expand Down
16 changes: 16 additions & 0 deletions code/stable/glassbr/Website/GlassBR_SRS.html
Original file line number Diff line number Diff line change
Expand Up @@ -1993,6 +1993,22 @@ <h3>
</tr>
<tr>
<th>
Notes
</th>
<td>
<p class="paragraph">
AN is annealed glass
</p>
<p class="paragraph">
FT is fully tempered glass
</p>
<p class="paragraph">
HS is heat strengthened glass
</p>
</td>
</tr>
<tr>
<th>
Source
</th>
<td>
Expand Down

0 comments on commit 5480c6c

Please sign in to comment.