Skip to content

Commit

Permalink
properly use the new instance model constructors. This seems to point…
Browse files Browse the repository at this point in the history
… out all sorts of oddities. Regularized some (SSP and SWHS) and left some in (GlassBR and GamePhysics). Unclear what is really going on, need to get @smiths to take a good look.
  • Loading branch information
JacquesCarette committed Jan 1, 2019
1 parent 560d776 commit f23bf7b
Show file tree
Hide file tree
Showing 19 changed files with 203 additions and 125 deletions.
6 changes: 4 additions & 2 deletions code/drasil-example/Drasil/GamePhysics/Body.hs
Original file line number Diff line number Diff line change
Expand Up @@ -195,11 +195,13 @@ chipUnits :: [UnitDefn] -- FIXME
chipUnits = map unitWrapper [metre, kilogram, second] ++ map unitWrapper [newton, radian]

everything :: ChunkDB
everything = cdb cpSymbolsAll (map nw cpSymbolsAll ++ map nw cpAcronyms ++ map nw prodtcon
everything = cdb (map qw iModels_new ++ map qw cpSymbolsAll)
(map nw cpSymbolsAll ++ map nw cpAcronyms ++ map nw prodtcon ++ map nw iModels_new
++ map nw softwarecon ++ map nw doccon ++ map nw doccon' ++ map nw CP.physicCon
++ map nw educon ++ [nw algorithm] ++ map nw derived ++ map nw fundamentals
++ map nw CM.mathcon ++ map nw CM.mathcon')
(map cw gamephySymbols ++ srsDomains) chipUnits game_label game_refby
(map cw gamephySymbols ++ srsDomains ++ map cw iModels_new)
chipUnits game_label game_refby
game_datadefn game_insmodel game_gendef game_theory game_assump game_concins
game_section []

Expand Down
49 changes: 26 additions & 23 deletions code/drasil-example/Drasil/GamePhysics/IMods.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Drasil.GamePhysics.IMods (iModels, iModels_new, im1_new, im2_new, im3_new) where
module Drasil.GamePhysics.IMods (iModels_new, im1_new, im2_new, im3_new) where

import Language.Drasil
import Language.Drasil.Development (MayHaveUnit)
Expand All @@ -16,30 +16,30 @@ import qualified Data.Drasil.Quantities.Physics as QP (acceleration,
import Data.Drasil.SentenceStructures (foldlSent, foldlSent_)
import Data.Drasil.Utils (fmtU, foldle1)

iModels :: [RelationConcept]
iModels = [transMot, rotMot, col2D]

iModels_new :: [InstanceModel]
iModels_new = [im1_new, im2_new, im3_new]

{-- Force on the translational motion --}
im1_new :: InstanceModel
im1_new = im' transMot [qw vel_i, qw QP.time, qw QP.gravitationalAccel, qw force_i, qw mass_i]
im1_new = eqModel transMot
[qw vel_i, qw QP.time, qw QP.gravitationalAccel, qw force_i, qw mass_i]
[sy vel_i $> 0, sy QP.time $> 0, sy QP.gravitationalAccel $> 0,
sy force_i $> 0, sy mass_i $> 0 ] (qw acc_i) [] [] "transMot" [transMotDesc]
sy force_i $> 0, sy mass_i $> 0 ] (qw acc_i) [] [] [] "transMot" [transMotDesc]

transMot :: RelationConcept
transMot = makeRC "transMot" transMotNP (transMotDesc +:+ transMotLeg) transMotRel
transMot :: QDefinition
transMot = fromEqn' "transMot" transMotNP (transMotDesc +:+ transMotLeg)
(eqSymb acc_i) transMotEqn

transMotNP :: NP
transMotNP = nounPhraseSP "Force on the translational motion of a set of 2d rigid bodies"

transMotRel :: Relation -- FIXME: add proper equation
transMotRel = (sy acc_i) $= (deriv (apply1 vel_i QP.time) QP.time)
$= (sy QP.gravitationalAccel) + ((apply1 force_i QP.time) / (sy mass_i))
-- FIXME: the 'equation' used to be a sequence of equations
transMotEqn :: Expr
transMotEqn = (deriv (apply1 vel_i QP.time) QP.time)
-- $= (sy QP.gravitationalAccel) + ((apply1 force_i QP.time) / (sy mass_i))


--fixme: need referencing
-- FIXME: need referencing
transMotDesc, transMotLeg :: Sentence
transMotDesc = foldlSent [S "The above equation expresses the total",
(phrase QP.acceleration), S "of the", (phrase CP.rigidBody),
Expand All @@ -57,21 +57,23 @@ transMotLeg = foldle1 (+:+) (+:+) $ map defList transMotLegTerms
{-- Rotational Motion --}

im2_new :: InstanceModel
im2_new = im' rotMot [qw QP.angularVelocity, qw QP.time, qw torque_i, qw QP.momentOfInertia]
[sy QP.angularVelocity $> 0, sy QP.time $> 0, sy torque_i $> 0, sy QP.momentOfInertia $> 0]
(qw QP.angularAccel) [sy QP.angularAccel $> 0] [] "rotMot"
im2_new = eqModel rotMot
[qw QP.angularVelocity, qw QP.time, qw torque_i, qw QP.momentOfInertia]
[sy QP.angularVelocity $> 0, sy QP.time $> 0, sy torque_i $> 0, sy QP.momentOfInertia $> 0]
(qw QP.angularAccel) [sy QP.angularAccel $> 0] [] [] "rotMot"
[rotMotDesc]

rotMot :: RelationConcept
rotMot = makeRC "rotMot" (rotMotNP) (rotMotDesc +:+ rotMotLeg) rotMotRel
rotMot :: QDefinition
rotMot = fromEqn' "rotMot" (rotMotNP) (rotMotDesc +:+ rotMotLeg)
(eqSymb QP.angularAccel) rotMotEqn

rotMotNP :: NP
rotMotNP = nounPhraseSP "Force on the rotational motion of a set of 2D rigid body"

rotMotRel :: Relation
rotMotRel = (sy QP.angularAccel) $= deriv
(apply1 QP.angularVelocity QP.time) QP.time $=
((apply1 torque_i QP.time) / (sy QP.momentOfInertia))
-- FIXME: the 'equation' used to be a sequence of equations
rotMotEqn :: Expr
rotMotEqn = deriv (apply1 QP.angularVelocity QP.time) QP.time
-- $= ((apply1 torque_i QP.time) / (sy QP.momentOfInertia))

--fixme: need referencing
rotMotDesc, rotMotLeg :: Sentence
Expand All @@ -87,10 +89,11 @@ rotMotLeg = foldle1 (+:+) (+:+) $ map defList rotMotLegTerms

{-- 2D Collision --}

-- FIXME: othModel because it should be a Functional Model
im3_new :: InstanceModel
im3_new = im' col2D [qw QP.time, qw QP.impulseS, qw mass_A, qw normalVect]
im3_new = othModel col2D [qw QP.time, qw QP.impulseS, qw mass_A, qw normalVect]

This comment has been minimized.

Copy link
@samm82

samm82 Aug 6, 2019

Collaborator

What was the reasoning behind making this an OthModel? Is it not an EquationalModel? @JacquesCarette

This comment has been minimized.

Copy link
@JacquesCarette

JacquesCarette Aug 9, 2019

Author Owner

Because the 'equations' depend on time, i.e. they define a function, not just a value. And I think EquationalModel makes assumptions about its lhs, i.e. that it's just a name for a value.

[sy QP.time $> 0, sy QP.impulseS $> 0, sy mass_A $> 0, sy normalVect $> 0]
(qw time_c) [sy vel_A $> 0, sy time_c $> 0] [] "col2D"
(qw time_c) [sy vel_A $> 0, sy time_c $> 0] [] [] "col2D"
[col2DDesc]

col2D :: RelationConcept
Expand Down
12 changes: 6 additions & 6 deletions code/drasil-example/Drasil/GlassBR/IMods.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,18 +20,18 @@ glassBRsymb :: [DefinedQuantityDict]
glassBRsymb = map dqdWr [plate_len, plate_width, char_weight, standOffDist] ++
[dqdQd (qw calofDemand) demandq]


{--}

calofDemandi :: InstanceModel
calofDemandi = im' calofDemand_RCi [qw demand, qw eqTNTWeight, qw standOffDist]
calofDemandi = eqModel calofDemand_defn [qw demand, qw eqTNTWeight, qw standOffDist]
[sy demand $> 0, sy eqTNTWeight $> 0, sy standOffDist $> 0] (qw demand) []
[astm2009] "calOfDemand"
[astm2009] [] "calOfDemand"
[calofDemandDesc]

calofDemand_RCi :: RelationConcept
calofDemand_RCi = makeRC "calofDemand_RC" (nounPhraseSP "Calculation of Demand")
calofDemandDesc ( (sy demand) $= apply2 demand eqTNTWeight standOffDist)
-- FIXME, see comment below
calofDemand_defn :: QDefinition
calofDemand_defn = fromEqn' "calofDemand" (demand ^. term)
calofDemandDesc (eqSymb demand) (apply2 demand eqTNTWeight standOffDist)
--calofDemandDesc $ (C demand) $= FCall (asExpr interpY) [V "TSD.txt", sy standOffDist, sy eqTNTWeight]

calofDemandDesc :: Sentence
Expand Down
2 changes: 1 addition & 1 deletion code/drasil-example/Drasil/NoPCM/IMods.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ import Drasil.NoPCM.GenDefs (rocTempSimp)
---------
-- FIXME: comment on reference?
eBalanceOnWtr :: InstanceModel
eBalanceOnWtr = im'' eBalanceOnWtr_rc [qw temp_C, qw temp_init, qw time_final,
eBalanceOnWtr = deModel eBalanceOnWtr_rc [qw temp_C, qw temp_init, qw time_final,
qw coil_SA, qw coil_HTC, qw htCap_W, qw w_mass]
[sy temp_init $<= sy temp_C] (qw temp_W)
--Tw(0) cannot be presented, there is one more constraint Tw(0) = Tinit
Expand Down
5 changes: 3 additions & 2 deletions code/drasil-example/Drasil/SSP/Body.hs
Original file line number Diff line number Diff line change
Expand Up @@ -187,13 +187,14 @@ ssppriorityNFReqs = [correctness, understandability, reusability,

-- SYMBOL MAP HELPERS --
sspSymMap :: ChunkDB
sspSymMap = cdb sspSymbols (map nw sspSymbols ++ map nw acronyms ++
sspSymMap = cdb (map qw sspIMods ++ map qw sspSymbols)
(map nw sspSymbols ++ map nw acronyms ++ map nw sspIMods ++
map nw doccon ++ map nw prodtcon ++ map nw sspdef ++ map nw sspdef'
++ map nw softwarecon ++ map nw physicCon ++ map nw mathcon
++ map nw mathcon' ++ map nw solidcon ++ map nw physicalcon
++ map nw doccon' ++ map nw derived ++ map nw fundamentals
++ map nw educon ++ map nw compcon ++ [nw algorithm, nw ssp] ++ map nw this_si)
(map cw sspSymbols ++ srsDomains) this_si ssp_label ssp_refby
(map cw sspIMods ++ map cw sspSymbols ++ srsDomains) this_si ssp_label ssp_refby
ssp_datadefn ssp_insmodel ssp_gendef ssp_theory ssp_assump ssp_concins
ssp_section []

Expand Down
56 changes: 28 additions & 28 deletions code/drasil-example/Drasil/SSP/IMods.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,10 @@
module Drasil.SSP.IMods where

import Prelude hiding (tan, product, sin, cos)
import Control.Lens ((^.))

import Language.Drasil
import Language.Drasil.ShortHands (lU, lV) -- local (bound) variables
import Language.Drasil.ShortHands (lI, lU, lV) -- index and local (bound) variables

import Data.Drasil.Utils (eqUnR', weave)

Expand Down Expand Up @@ -44,14 +45,14 @@ sspIMods = [fctSfty, nrmShrFor, intsliceFs, crtSlpId]

--
fctSfty :: InstanceModel
fctSfty = im'' fctSfty_rc [qw slopeDist, qw slopeHght, qw waterHght, qw cohesion, qw fricAngle, qw dryWeight, qw satWeight, qw waterWeight, qw slipDist, qw slipHght, qw constF]
fctSfty = eqModel fctSfty_defn [qw slopeDist, qw slopeHght, qw waterHght, qw cohesion, qw fricAngle, qw dryWeight, qw satWeight, qw waterWeight, qw slipDist, qw slipHght, qw constF]
[] (qw fs) [] [chen2005, karchewski2012] fctSftyDeriv "fctSfty" [fcSfty_desc]

fctSfty_rc :: RelationConcept
fctSfty_rc = makeRC "fctSfty_rc" factorOfSafety fcSfty_desc fcSfty_rel -- fctSftyL
fctSfty_defn :: QDefinition
fctSfty_defn = fromEqn' "fctSftyc" factorOfSafety fcSfty_desc (eqSymb fs) fcSfty

fcSfty_rel :: Relation
fcSfty_rel = sy fs $= sumOp shearRNoIntsl / sumOp shearFNoIntsl
fcSfty :: Expr
fcSfty = sumOp shearRNoIntsl / sumOp shearFNoIntsl
where prodOp = defprod lU (sy index) (sy numbSlices - 1)
(idx (sy mobShrC) (sy varblU))
sumOp sym = (defsum lV 1 (sy numbSlices - 1)
Expand All @@ -62,18 +63,18 @@ fcSfty_desc = foldlSent_ []

--
nrmShrFor :: InstanceModel
nrmShrFor = im'' nrmShrFor_rc [qw baseWthX, qw scalFunc,
nrmShrFor = eqModel nrmShrFor_defn [qw baseWthX, qw scalFunc,
qw watrForce, qw baseAngle, qw midpntHght,
qw earthqkLoadFctr, qw slcWght, qw surfHydroForce]
[sy fixme1 $< sy fixme1] (qw shearFunc)
[0 $< sy fixme1 $< sy fixme1] [chen2005] nrmShrDeriv "nrmShrFor" [nrmShrF_desc]

nrmShrFor_rc :: RelationConcept
nrmShrFor_rc = makeRC "nrmShrFor_rc" (nounPhraseSP "normal/shear force ratio")
nrmShrF_desc nrmShrF_rel -- nrmShrForL
nrmShrFor_defn :: QDefinition
nrmShrFor_defn = fromEqn' "nrmShrFor" (normFunc ^. term)
nrmShrF_desc (eqSymb normFunc) nrmShrF

nrmShrF_rel :: Relation
nrmShrF_rel = (sy normFunc) $= case_ [case1,case2,case3] $=
nrmShrF :: Expr
nrmShrF = case_ [case1,case2,case3] $=
sy shearFunc $= case_ [
(indx1 baseWthX * indx1 scalFunc * indx1 intNormForce, sy index $= 1),
(inxi baseWthX * (inxi scalFunc * inxi intNormForce +
Expand Down Expand Up @@ -110,16 +111,17 @@ nrmShrF_desc = foldlSent [ch normToShear `isThe` S "magnitude ratio",
--

intsliceFs :: InstanceModel
intsliceFs = im'' intsliceFs_rc [qw index, qw fs, qw shearRNoIntsl, qw shearFNoIntsl,
intsliceFs = eqModel intsliceFs_defn [qw index, qw fs, qw shearRNoIntsl, qw shearFNoIntsl,
qw mobShrC, qw shrResC]
[] (qw intNormForce) [] [chen2005] intrSlcDeriv "intsliceFs" [sliceFs_desc]

intsliceFs_rc :: RelationConcept
intsliceFs_rc = makeRC "intsliceFs_rc" (nounPhraseSP "interslice forces")
sliceFs_desc sliceFs_rel -- inslideFxL
-- Symbol hack
intsliceFs_defn :: QDefinition
intsliceFs_defn = fromEqn' "intsliceFs" (nounPhraseSP "interslice forces")
sliceFs_desc (sub (eqSymb intNormForce) lI) sliceFs_eq -- inslideFxL

sliceFs_rel :: Relation
sliceFs_rel = inxi intNormForce $= case_ [
sliceFs_eq :: Expr
sliceFs_eq = case_ [
(((sy fs) * indx1 shearFNoIntsl - indx1 shearRNoIntsl) / indx1 shrResC,
sy index $= 1),
((inxiM1 mobShrC * inxiM1 intNormForce +
Expand All @@ -138,15 +140,15 @@ sliceFs_desc = foldlSent_ [S "The value of the interslice normal force",

--
crtSlpId :: InstanceModel
crtSlpId = im' crtSlpId_rc [] [] (qw fs_min) [] [li2010] "crtSlpId" [crtSlpId_desc]
crtSlpId = eqModel crtSlpId_defn [] [] (qw fs_min) [] [li2010] [] "crtSlpId" [crtSlpId_desc]

crtSlpId_rc :: RelationConcept
crtSlpId_rc = makeRC "crtSlpId_rc" (nounPhraseSP "critical slip identification")
crtSlpId_desc crtSlpId_rel -- crtSlpIdL
crtSlpId_defn :: QDefinition
crtSlpId_defn = fromEqn' "crtSlpId" (nounPhraseSP "critical slip identification")
crtSlpId_desc (eqSymb fs_min) crtSlpId_eq -- crtSlpIdL

-- FIXME: horrible hack. This is short an argument... that was never defined!
crtSlpId_rel :: Relation
crtSlpId_rel = (sy fs_min) $= (apply1 minFunction critCoords) -- sy inputHack])
crtSlpId_eq :: Expr
crtSlpId_eq = apply1 minFunction critCoords -- sy inputHack])
--FIXME: add subscript to fs

crtSlpId_desc :: Sentence
Expand Down Expand Up @@ -224,7 +226,7 @@ fctSftyDerivEqns1 = [fctSftyDerivEqn1, fctSftyDerivEqn2, fctSftyDerivEqn3,
fctSftyDerivEqns2 :: [Expr]
fctSftyDerivEqns2 = [fctSftyDerivEqn11, fctSftyDerivEqn12, fctSftyDerivEqn13,
fctSftyDerivEqn14, fctSftyDerivEqn15, fctSftyDerivEqn16, fctSftyDerivEqn17,
fctSftyDerivEqn18, fcSfty_rel]
fctSftyDerivEqn18, fcSfty]

fctSftyDerivSentence1 :: [Sentence]
fctSftyDerivSentence1 = [S "The" +:+ phrase mobShrI +:+ S "defined in",
Expand Down Expand Up @@ -642,9 +644,7 @@ fctSftyDerivation = [foldlSP [S "Using", eqN 21, S "from", makeRef2S intsliceFs
S "rearranging, and", boundaryCon `sC` S "an", phrase equation,
S "for the", phrase fs, S "is found as", eqN 12 `sC`
S "also seen in", makeRef2S fctSfty],

eqUnR' fcSfty_rel,

eqUnR' fcSfty,
fUnknownsCon]

nrmShrDerivation = [
Expand Down
2 changes: 1 addition & 1 deletion code/drasil-example/Drasil/SSP/Unitals.hs
Original file line number Diff line number Diff line change
Expand Up @@ -289,7 +289,7 @@ sliceHght = uc' "z_i" (cn "center of slice height")
"of the slice to the height of the centers of slice")
(lZ) metre

normFunc = uc' "C1_i" (cn "interslice normal force function")
normFunc = uc' "normShrFor" (cn "interslice normal force function")
"the normal force at the interslice interface for slice i"
(sub (Concat [cC, Atomic "1"]) lI) momentOfForceU

Expand Down
6 changes: 4 additions & 2 deletions code/drasil-example/Drasil/SWHS/Body.hs
Original file line number Diff line number Diff line change
Expand Up @@ -117,13 +117,15 @@ resourcePath :: String
resourcePath = "../../../datafiles/SWHS/"

swhsSymMap :: ChunkDB
swhsSymMap = cdb swhsSymbolsAll (map nw swhsSymbols ++ map nw acronymsFull
swhsSymMap = cdb (qw heatEInPCM : swhsSymbolsAll) -- heatEInPCM ?
(nw heatEInPCM : map nw swhsSymbols ++ map nw acronymsFull
++ map nw thermocon ++ map nw this_si ++ map nw [m_2, m_3]
++ map nw physicscon ++ map nw doccon ++ map nw softwarecon ++ map nw doccon' ++ map nw swhscon
++ map nw prodtcon ++ map nw physicCon ++ map nw mathcon ++ map nw mathcon' ++ map nw specParamValList
++ map nw fundamentals ++ map nw derived ++ map nw physicalcon ++ map nw swhsUC
++ [nw swhs_pcm, nw algorithm] ++ map nw compcon)
(map cw swhsSymbols ++ srsDomains) (this_si ++ [m_2, m_3]) swhs_label swhs_refby
(cw heatEInPCM : map cw swhsSymbols ++ srsDomains) -- FIXME: heatEInPCM?
(this_si ++ [m_2, m_3]) swhs_label swhs_refby
swhs_datadefn swhs_insmodel swhs_gendef swhs_theory swhs_assump swhs_concins
swhs_section swhs_labcon

Expand Down
24 changes: 13 additions & 11 deletions code/drasil-example/Drasil/SWHS/IMods.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,17 +19,19 @@ import Drasil.SWHS.TMods (sensHtE, latentHtE)
import Drasil.SWHS.Unitals (coil_HTC, coil_SA, eta, ht_flux_C, ht_flux_P, htCap_L_P,
htCap_S_P, htCap_W, htFusion, latentE_P, melt_frac, pcm_E, pcm_HTC, pcm_initMltE,
pcm_mass, pcm_SA, pcm_vol, t_init_melt, tau_L_P, tau_S_P, tau_W, temp_C, temp_init,
temp_melt_P, temp_PCM, temp_W, time_final, vol_ht_gen, w_E, w_mass, w_vol)
temp_melt_P, temp_PCM, temp_W, time_final, vol_ht_gen, w_E, w_mass, w_vol)
import Drasil.SWHS.GenDefs (rocTempSimp)

import Control.Lens ((^.))

swhsIMods :: [InstanceModel]
swhsIMods = [eBalanceOnWtr, eBalanceOnPCM, heatEInWtr, heatEInPCM]

---------
-- IM1 --
---------
eBalanceOnWtr :: InstanceModel
eBalanceOnWtr = im'' eBalanceOnWtr_rc [qw w_mass, qw htCap_W, qw coil_HTC, qw pcm_SA,
eBalanceOnWtr = deModel eBalanceOnWtr_rc [qw w_mass, qw htCap_W, qw coil_HTC, qw pcm_SA,
qw pcm_HTC, qw coil_SA, qw temp_PCM, qw time_final, qw temp_C, qw temp_init]
[sy temp_init $< sy temp_C] (qw temp_W)
[0 $< sy time $< sy time_final] [koothoor2013] eBalanceOnWtrDeriv
Expand Down Expand Up @@ -194,7 +196,7 @@ eBalanceOnWtr_deriv_eqns__im1 = [eBalanceOnWtrDerivEqn1, eBalanceOnWtrDerivEqn2,
-- IM2 --
---------
eBalanceOnPCM :: InstanceModel
eBalanceOnPCM = im'' eBalanceOnPCM_rc [qw temp_melt_P, qw time_final, qw temp_init, qw pcm_SA,
eBalanceOnPCM = deModel eBalanceOnPCM_rc [qw temp_melt_P, qw time_final, qw temp_init, qw pcm_SA,
qw pcm_HTC, qw pcm_mass, qw htCap_S_P, qw htCap_L_P]
[sy temp_init $< sy temp_melt_P] (qw temp_PCM)
[0 $< sy time $< sy time_final] [koothoor2013] eBalanceOnPCMDeriv
Expand Down Expand Up @@ -354,8 +356,9 @@ eBalanceOnPCM_deriv_eqns__im2 = [eBalanceOnPCM_Eqn1, eBalanceOnPCM_Eqn2,
---------
-- IM3 --
---------
-- FIXME: this is an 'other' model because we don't have Functional models yet
heatEInWtr :: InstanceModel
heatEInWtr = im'' heatEInWtr_rc [qw temp_init, qw w_mass, qw htCap_W, qw w_mass]
heatEInWtr = othModel heatEInWtr_rc [qw temp_init, qw w_mass, qw htCap_W, qw w_mass]
[] (qw w_E) [0 $< sy time $< sy time_final] [koothoor2013] [] "heatEInWtr"
[htWtrDesc]

Expand Down Expand Up @@ -387,18 +390,17 @@ htWtrDesc = foldlSent [S "The above", phrase equation, S "is derived using" +:+.
-- IM4 --
---------
heatEInPCM :: InstanceModel
heatEInPCM = im' heatEInPCM_rc [qw temp_melt_P, qw time_final, qw temp_init, qw pcm_SA,
heatEInPCM = eqModel heatEInPCM_defn [qw temp_melt_P, qw time_final, qw temp_init, qw pcm_SA,
qw pcm_HTC, qw pcm_mass, qw htCap_S_P, qw htCap_L_P, qw temp_PCM, qw htFusion, qw t_init_melt]
[sy temp_init $< sy temp_melt_P] (qw pcm_E)
[0 $< sy time $< sy time_final] [koothoor2013]
[0 $< sy time $< sy time_final] [koothoor2013] []
"heatEInPCM" [htPCMDesc]

heatEInPCM_rc :: RelationConcept
heatEInPCM_rc = makeRC "heatEInPCM_rc" (nounPhraseSP "Heat energy in the PCM")
htPCMDesc htPCM_Rel
heatEInPCM_defn :: QDefinition
heatEInPCM_defn = fromEqn' "heatEInPCM" (pcm_E ^. term) htPCMDesc (eqSymb pcm_E) htPCM

htPCM_Rel :: Relation
htPCM_Rel = sy pcm_E $= case_ [case1, case2, case3, case4]
htPCM :: Expr
htPCM = case_ [case1, case2, case3, case4]
where case1 = (sy htCap_S_P * sy pcm_mass * ((apply1 temp_PCM time) -
sy temp_init), real_interval temp_PCM (UpTo (Exc, sy temp_melt_P)))

Expand Down
3 changes: 2 additions & 1 deletion code/drasil-example/Drasil/SWHS/Unitals.hs
Original file line number Diff line number Diff line change
Expand Up @@ -407,7 +407,7 @@ w_E = cuc' "w_E" (nounPhraseSP "change in heat energy in the water")
[physc $ UpFrom (Inc,0)] (dbl 0)

-- Constraint 21
pcm_E = cuc' "pcm_E" (nounPhraseSP "change in heat energy in the PCM")
pcm_E = cuc' "heatEInPCM" (nounPhraseSP "change in heat energy in the PCM")
"Change in thermal energy within the phase change material"
(sub (eqSymb sens_heat) cP) joule Rational
[physc $ UpFrom (Inc, 0)] (dbl 0)
Expand Down Expand Up @@ -549,3 +549,4 @@ pcm_HTC_max = mkQuantDef (unitary "pcm_HTC_max"
time_final_max = mkQuantDef (unitary "time_final_max"
(nounPhraseSP "maximum final time")
(sup (eqSymb time_final) (Atomic "max")) second Rational) 86400

Loading

1 comment on commit f23bf7b

@smiths
Copy link
Collaborator

@smiths smiths commented on f23bf7b Jan 22, 2019

Choose a reason for hiding this comment

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

@JacquesCarette, I'd be happy to look at the oddities that you mentioned. When you get a chance, maybe you could list some specific examples for us to focus on?

Please sign in to comment.