Skip to content

Commit

Permalink
Used quantPlate for Aux Consts; some quants added to NoPCM ToS
Browse files Browse the repository at this point in the history
  • Loading branch information
samm82 committed Jul 11, 2019
1 parent c7bf0cf commit be8aa64
Show file tree
Hide file tree
Showing 3 changed files with 89 additions and 7 deletions.
15 changes: 8 additions & 7 deletions code/drasil-docLang/Drasil/DocumentLanguage.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,12 +9,12 @@ module Drasil.DocumentLanguage where

import Drasil.DocDecl (SRSDecl, mkDocDesc)
import Drasil.DocumentLanguage.Core (AppndxSec(..), AuxConstntSec(..),
DerivationDisplay(..), DLPlate(docSec, scsSub), DocDesc, DocSection(..),
OffShelfSolnsSec(..), GSDSec(..), GSDSub(..), IntroSec(..), IntroSub(..),
LCsSec(..), LFunc(..), Literature(..), PDSub(..), ProblemDescription(..),
RefSec(..), RefTab(..), ReqrmntSec(..), ReqsSub(..), SCSSub(..), StkhldrSec(..), StkhldrSub(..), SolChSpec(..),
SSDSec(..), SSDSub(..), TConvention(..), TraceabilitySec(..), TraceConfig(..),
TSIntro(..), TUIntro(..), UCsSec(..))
DerivationDisplay(..), DLPlate(auxConsSec, docSec, scsSub), DocDesc,
DocSection(..), OffShelfSolnsSec(..), GSDSec(..), GSDSub(..), IntroSec(..),
IntroSub(..), LCsSec(..), LFunc(..), Literature(..), PDSub(..), ProblemDescription(..),
RefSec(..), RefTab(..), ReqrmntSec(..), ReqsSub(..), SCSSub(..), StkhldrSec(..),
StkhldrSub(..), SolChSpec(..), SSDSec(..), SSDSub(..), TConvention(..),
TraceabilitySec(..), TraceConfig(..), TSIntro(..), TUIntro(..), UCsSec(..))
import Drasil.DocumentLanguage.Definitions (ddefn, derivation, instanceModel,
gdefn, tmodel, helperRefs)
import Drasil.ExtractDocDesc (getDocDesc, egetDocDesc)
Expand Down Expand Up @@ -145,7 +145,8 @@ quantPlate = preorderFold $ purePlate {
scsSub = Constant <$> \case
(Constraints _ c) -> map qw c
(CorrSolnPpties c _) -> map qw c
_ -> mempty
_ -> mempty,
auxConsSec = Constant <$> \(AuxConsProg _ c) -> map qw c
}

-- | table of symbols constructor
Expand Down
22 changes: 22 additions & 0 deletions code/stable/nopcm/SRS/NoPCM_SRS.tex
Original file line number Diff line number Diff line change
Expand Up @@ -66,6 +66,8 @@ \subsection{Table of Symbols}
\endhead
${A_{C}}$ & Heating coil surface area & $\text{m}^{2}$
\\
${{A_{C}}^{max}}$ & Maximum surface area of coil & $\text{m}^{2}$
\\
${A_{in}}$ & Surface area over which heat is transferred in & $\text{m}^{2}$
\\
${A_{out}}$ & Surface area over which heat is transferred out & $\text{m}^{2}$
Expand All @@ -74,8 +76,14 @@ \subsection{Table of Symbols}
\\
${C^{L}}$ & Specific heat capacity of a liquid & $\frac{\text{J}}{(\text{kg}{}^{\circ}\text{C})}$
\\
${C_{tol}}$ & Relative tolerance for conservation of energy & --
\\
${C_{W}}$ & Specific heat capacity of water & $\frac{\text{J}}{(\text{kg}{}^{\circ}\text{C})}$
\\
${{C_{W}}^{max}}$ & Maximum specific heat capacity of water & $\frac{\text{J}}{(\text{kg}{}^{\circ}\text{C})}$
\\
${{C_{W}}^{min}}$ & Minimum specific heat capacity of water & $\frac{\text{J}}{(\text{kg}{}^{\circ}\text{C})}$
\\
$D$ & Diameter of tank & m
\\
$E$ & Sensible heat & J
Expand All @@ -88,8 +96,16 @@ \subsection{Table of Symbols}
\\
${h_{C}}$ & Convective heat transfer coefficient between coil and water & $\frac{\text{W}}{(\text{m}^{2}{}^{\circ}\text{C})}$
\\
${{h_{C}}^{max}}$ & Maximum convective heat transfer coefficient between coil and water & $\frac{\text{W}}{(\text{m}^{2}{}^{\circ}\text{C})}$
\\
${{h_{C}}^{min}}$ & Minimum convective heat transfer coefficient between coil and water & $\frac{\text{W}}{(\text{m}^{2}{}^{\circ}\text{C})}$
\\
$L$ & Length of tank & m
\\
${L_{max}}$ & Maximum length of tank & m
\\
${L_{min}}$ & Minimum length of tank & m
\\
$m$ & Mass & kg
\\
${m_{W}}$ & Mass of water & kg
Expand Down Expand Up @@ -124,6 +140,8 @@ \subsection{Table of Symbols}
\\
${t_{final}}$ & Final time & s
\\
${{t_{final}}^{max}}$ & Maximum final time & s
\\
${t_{step}}$ & Time step for simulation & s
\\
$V$ & Volume & $\text{m}^{3}$
Expand All @@ -136,6 +154,10 @@ \subsection{Table of Symbols}
\\
${ρ_{W}}$ & Density of water & $\frac{\text{kg}}{\text{m}^{3}}$
\\
${{ρ_{W}}^{max}}$ & Maximum density of water & $\frac{\text{kg}}{\text{m}^{3}}$
\\
${{ρ_{W}}^{min}}$ & Minimum density of water & $\frac{\text{kg}}{\text{m}^{3}}$
\\
${τ_{W}}$ & ODE parameter for water & s
\\
$$ & Gradient & --
Expand Down
59 changes: 59 additions & 0 deletions code/stable/nopcm/Website/NoPCM_SRS.html
Original file line number Diff line number Diff line change
Expand Up @@ -86,6 +86,11 @@ <h2>Table of Symbols</h2>
<td>Heating coil surface area</td>
<td>m<sup>2</sup></td>
</tr>
<tr>
<td><em>A<sub>C</sub><sup>max</sup></em></td>
<td>Maximum surface area of coil</td>
<td>m<sup>2</sup></td>
</tr>
<tr>
<td><em>A<sub>in</sub></em></td>
<td>Surface area over which heat is transferred in</td>
Expand All @@ -106,11 +111,26 @@ <h2>Table of Symbols</h2>
<td>Specific heat capacity of a liquid</td>
<td>J/(kg&sdot;&deg;C)</td>
</tr>
<tr>
<td><em>C<sub>tol</sub></em></td>
<td>Relative tolerance for conservation of energy</td>
<td>--</td>
</tr>
<tr>
<td><em>C<sub>W</sub></em></td>
<td>Specific heat capacity of water</td>
<td>J/(kg&sdot;&deg;C)</td>
</tr>
<tr>
<td><em>C<sub>W</sub><sup>max</sup></em></td>
<td>Maximum specific heat capacity of water</td>
<td>J/(kg&sdot;&deg;C)</td>
</tr>
<tr>
<td><em>C<sub>W</sub><sup>min</sup></em></td>
<td>Minimum specific heat capacity of water</td>
<td>J/(kg&sdot;&deg;C)</td>
</tr>
<tr>
<td><em>D</em></td>
<td>Diameter of tank</td>
Expand Down Expand Up @@ -143,11 +163,35 @@ <h2>Table of Symbols</h2>
</td>
<td>W/(m<sup>2</sup>&sdot;&deg;C)</td>
</tr>
<tr>
<td><em>h<sub>C</sub><sup>max</sup></em></td>
<td>
Maximum convective heat transfer coefficient between coil and water
</td>
<td>W/(m<sup>2</sup>&sdot;&deg;C)</td>
</tr>
<tr>
<td><em>h<sub>C</sub><sup>min</sup></em></td>
<td>
Minimum convective heat transfer coefficient between coil and water
</td>
<td>W/(m<sup>2</sup>&sdot;&deg;C)</td>
</tr>
<tr>
<td><em>L</em></td>
<td>Length of tank</td>
<td>m</td>
</tr>
<tr>
<td><em>L<sub>max</sub></em></td>
<td>Maximum length of tank</td>
<td>m</td>
</tr>
<tr>
<td><em>L<sub>min</sub></em></td>
<td>Minimum length of tank</td>
<td>m</td>
</tr>
<tr>
<td><em>m</em></td>
<td>Mass</td>
Expand Down Expand Up @@ -233,6 +277,11 @@ <h2>Table of Symbols</h2>
<td>Final time</td>
<td>s</td>
</tr>
<tr>
<td><em>t<sub>final</sub><sup>max</sup></em></td>
<td>Maximum final time</td>
<td>s</td>
</tr>
<tr>
<td><em>t<sub>step</sub></em></td>
<td>Time step for simulation</td>
Expand Down Expand Up @@ -263,6 +312,16 @@ <h2>Table of Symbols</h2>
<td>Density of water</td>
<td>kg/m<sup>3</sup></td>
</tr>
<tr>
<td><em>ρ<sub>W</sub><sup>max</sup></em></td>
<td>Maximum density of water</td>
<td>kg/m<sup>3</sup></td>
</tr>
<tr>
<td><em>ρ<sub>W</sub><sup>min</sup></em></td>
<td>Minimum density of water</td>
<td>kg/m<sup>3</sup></td>
</tr>
<tr>
<td><em>τ<sub>W</sub></em></td>
<td>ODE parameter for water</td>
Expand Down

15 comments on commit be8aa64

@samm82
Copy link
Collaborator Author

@samm82 samm82 commented on be8aa64 Jul 11, 2019

Choose a reason for hiding this comment

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

@Mornix I think I've done all I can do on this branch (at least for now) - quantPlate is used for Constraints, Props of Correct Solution, and Aux Consts. It uses qw, and so misses all terms with definitions. I think that's enough information to log for the future? Should this be made into an issue? I'm not really sure how to proceed.

@Mornix
Copy link
Collaborator

@Mornix Mornix commented on be8aa64 Jul 12, 2019

Choose a reason for hiding this comment

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

This is dependent on #1658.

@samm82
Copy link
Collaborator Author

@samm82 samm82 commented on be8aa64 Jul 12, 2019

Choose a reason for hiding this comment

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

Yeah sorry, I marked the first commit and forgot about the others 😬

@JacquesCarette
Copy link
Owner

Choose a reason for hiding this comment

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

So why did new quantities 'appear' in NoPCM? If they are not actually used in NoPCM, they shouldn't appear here; if they were used but not appearing, that was a bug. Either case is interesting.

@Mornix
Copy link
Collaborator

@Mornix Mornix commented on be8aa64 Jul 13, 2019

Choose a reason for hiding this comment

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

The existing passes for DocLang introspection operate on Sentence and Expr which catch almost all of the symbols, however if we have QuantityDict (such as the new constraint tables or AuxConstProg), we don’t gather the symbols of the actual QuantityDict.

@JacquesCarette
Copy link
Owner

Choose a reason for hiding this comment

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

Right, so we should probably do this kind of pass on a properly elaborated document? Or teach the passes how to figure out which symbols to grab?

@Mornix
Copy link
Collaborator

@Mornix Mornix commented on be8aa64 Jul 15, 2019

Choose a reason for hiding this comment

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

I would tend to agree. I think an appropriate place would be a post DocDesc, but pre-Document structure such that the flow becomes:
SRSDecl --> DocDesc --> PreDoc --> Document.

The traceability matrix would still be expanded from DocDesc as we have all the references and sections (or at least stubs), whereas anything (i.e. Table of Symbols, Table of Acronyms), in the Intro Section would be in PreDoc due to "only" requiring traversal of Sentence and Expr.

I'm not too sure whether this is "worth it" at the moment due to only applying to three sections, one of which is new to this PR and two of which were missed in all prior pass implementations (oops).

@JacquesCarette
Copy link
Owner

Choose a reason for hiding this comment

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

I doesn't seem worth it yet, I agree.

@samm82
Copy link
Collaborator Author

@samm82 samm82 commented on be8aa64 Aug 12, 2019

Choose a reason for hiding this comment

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

@Mornix what's the status of this branch? It's been so long I've forgotten. Right now, the log differences are quantities missing from the Table of Symbols: "Cartesian Position Coordinates" in SSP and "Final time" and "Time step for simulation" in SWHS. The SSP one makes sense, as it only appears in the FRs (which aren't searched by quantPlate yet), but tfinal and tstep both appear in the Properties of Correct Solution table, which is searched by quantPlate.

props of correct

It seems that at some point, we should search the FR tables for quantities, which would potentially be related to the work done on #1697 which is currently held up by a lack of general "theory" type. This also would leave the bug that not all quantities are being pulled out that should be.

@samm82
Copy link
Collaborator Author

@samm82 samm82 commented on be8aa64 Aug 15, 2019

Choose a reason for hiding this comment

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

@Mornix I'm not sure if I should make an issue for this, but I've described the issue above. I've messed around and I can't seem to find the source of it. Reading through the inputs from SystemDescription in docLang still misses these quantities.

@Mornix
Copy link
Collaborator

@Mornix Mornix commented on be8aa64 Aug 15, 2019

Choose a reason for hiding this comment

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

Right. I recall now. This is because the Tables are stored by DocDesc as Content. Content has not concept of QuantityDict since it is Document structure related. To properly extract these, the quantity or whatever "supertype" of QuantityDict would need to be passed in and stored in DocDesc for introspection to detect.

@samm82
Copy link
Collaborator Author

@samm82 samm82 commented on be8aa64 Aug 15, 2019

Choose a reason for hiding this comment

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

I'm pretty sure the the values are stored as either a (Quantity q, MayHaveUnit q) or a QDefinition (which is an instance of the aforementioned classes. The [Contents] in CorrSolnPpties is for extra properties of a correct solution (in the form of an explanation).

-- | Solution Characteristics Specification subsections
data SCSSub where
Assumptions :: [ConceptInstance] -> SCSSub
TMs :: [Sentence] -> Fields -> [TheoryModel] -> SCSSub
GDs :: [Sentence] -> Fields -> [GenDefn] -> DerivationDisplay -> SCSSub
DDs :: [Sentence] -> Fields -> [DataDefinition] -> DerivationDisplay -> SCSSub --FIXME: Need DD intro
IMs :: [Sentence] -> Fields -> [InstanceModel] -> DerivationDisplay -> SCSSub
Constraints :: (HasUncertainty c, Quantity c, Constrained c, HasReasVal c, MayHaveUnit c) => Sentence -> [c] -> SCSSub
-- Sentence -> [LabelledContent] Fields -> [UncertainWrapper] -> [ConstrainedChunk] -> SCSSub --FIXME: temporary definition?
--FIXME: Work in Progress ^
CorrSolnPpties :: (Quantity c, Constrained c) => [c] -> [Contents] -> SCSSub

data AuxConstntSec = AuxConsProg CI [QDefinition]

@Mornix
Copy link
Collaborator

@Mornix Mornix commented on be8aa64 Aug 15, 2019

Choose a reason for hiding this comment

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

Ah. I re-read your earlier message. Do the examples missing things use the TSymb' constructor? If so, that is why.

@samm82
Copy link
Collaborator Author

@samm82 samm82 commented on be8aa64 Aug 15, 2019

Choose a reason for hiding this comment

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

Yup, they both do. Any idea what the correct fix would be?

@Mornix
Copy link
Collaborator

@Mornix Mornix commented on be8aa64 Aug 16, 2019

Choose a reason for hiding this comment

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

Resolving #1658.

Please sign in to comment.