{-# LANGUAGE PostfixOperators #-}
module Drasil.SSP.GenDefs (normForcEq, bsShrFEq, resShr, mobShr,
  normShrR, generalDefinitions,
  normForcEqGD, bsShrFEqGD, resShrGD, mobShrGD, normShrRGD, momentEqlGD,
  mobShearWOGD, resShearWOGD, srfWtrFGD) where
import Prelude hiding (sin, cos, tan)
import qualified Data.List.NonEmpty as NE
import Language.Drasil
import Theory.Drasil
import Utils.Drasil (weave)
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.NounPhrase.Combinators as NP
import qualified Language.Drasil.Sentence.Combinators as S
import Drasil.DocLang.SRS as SRS (physSyst)
import Data.Drasil.SI_Units (metre, newton)
import Data.Drasil.Concepts.Documentation (analysis, assumption, component,
  constant, definition, method_, value)
import Data.Drasil.Concepts.Math (area, equation, zDir)
import Data.Drasil.Concepts.PhysicalProperties (len)
import Data.Drasil.Concepts.Physics (twoD, weight)
import Data.Drasil.Concepts.SolidMechanics (normForce, shearForce)
import Data.Drasil.Quantities.PhysicalProperties (specWeight)
import Data.Drasil.Quantities.Physics (displacement, force, height,
  pressure, torque)
import Data.Drasil.Theories.Physics (weightGD, hsPressureGD, torqueDD)
import Drasil.SSP.Assumptions (assumpFOSL, assumpSLH, assumpSP, assumpSLI,
  assumpINSFL, assumpPSC, assumpSBSBISL, assumpWIBE, assumpWISE, assumpNESSS,
  assumpHFSM)
import Drasil.SSP.BasicExprs (eqlExpr, eqlExprN, momExpr)
import Drasil.SSP.DataDefs (intersliceWtrF, angleA, angleB, lengthB, lengthLb,
  lengthLs, slcHeight, normStressDD, tangStressDD, ratioVariation)
import Drasil.SSP.Defs (intrslce, slice, slope, slopeSrf, slpSrf, soil,
  soilPrpty, waterTable)
import Drasil.SSP.Figures (figForceActing)
import Drasil.SSP.References (chen2005, fredlund1977, karchewski2012)
import Drasil.SSP.TMods (factOfSafety, equilibrium, mcShrStrgth, effStress)
import Drasil.SSP.Unitals (baseAngle, baseHydroForce, baseLngth, baseWthX,
  dryWeight, earthqkLoadFctr, effCohesion, fricAngle, fs, genericA, genericM,
  genericSpWght, impLoadAngle, intNormForce, intShrForce, index, inxi, inxiM1,
  midpntHght, mobShrI, momntArm, normToShear, nrmFSubWat, rotForce, satWeight,
  scalFunc, shearFNoIntsl, shrResI, shrStress, totNrmForce, shearRNoIntsl,
  slcWght, sliceHght, sliceHghtW, slipHght, slopeHght, surfHydroForce,
  surfAngle, surfLngth, surfLoad, watrForce, waterHght, waterWeight, dryVol,
  satVol, yi, zcoord)
generalDefinitions :: [GenDefn]
generalDefinitions :: [GenDefn]
generalDefinitions = [GenDefn
normForcEqGD, GenDefn
bsShrFEqGD, GenDefn
resShrGD, GenDefn
mobShrGD,
 GenDefn
effNormFGD, GenDefn
resShearWOGD, GenDefn
mobShearWOGD, GenDefn
normShrRGD, GenDefn
momentEqlGD, GenDefn
weightGD,
 GenDefn
sliceWghtGD, GenDefn
hsPressureGD, GenDefn
baseWtrFGD, GenDefn
srfWtrFGD]
normForcEqGD, bsShrFEqGD, resShrGD, mobShrGD, effNormFGD, resShearWOGD,
  mobShearWOGD, normShrRGD, momentEqlGD, sliceWghtGD, baseWtrFGD,
  srfWtrFGD :: GenDefn
normForcEqGD :: GenDefn
normForcEqGD = ModelKind ModelExpr
-> Maybe UnitDefn
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
forall u.
IsUnit u =>
ModelKind ModelExpr
-> Maybe u
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
gd (RelationConcept -> ModelKind ModelExpr
forall e. RelationConcept -> ModelKind e
othModel' RelationConcept
normForcEq) (UnitalChunk -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit UnitalChunk
totNrmForce)   (Derivation -> Maybe Derivation
forall a. a -> Maybe a
Just Derivation
nmFEqDeriv)
  [Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
chen2005]                      String
"normForcEq"  [Sentence
nmFEqDesc]
bsShrFEqGD :: GenDefn
bsShrFEqGD   = ModelKind ModelExpr
-> Maybe UnitDefn
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
forall u.
IsUnit u =>
ModelKind ModelExpr
-> Maybe u
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
gd (RelationConcept -> ModelKind ModelExpr
forall e. RelationConcept -> ModelKind e
othModel' RelationConcept
bsShrFEq)   (UnitalChunk -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit UnitalChunk
mobShrI)       (Derivation -> Maybe Derivation
forall a. a -> Maybe a
Just Derivation
bShFEqDeriv)
  [Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
chen2005]                      String
"bsShrFEq"    [Sentence
bShFEqDesc]
resShrGD :: GenDefn
resShrGD     = ModelKind ModelExpr
-> Maybe UnitDefn
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
forall u.
IsUnit u =>
ModelKind ModelExpr
-> Maybe u
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
gd (RelationConcept -> ModelKind ModelExpr
forall e. RelationConcept -> ModelKind e
othModel' RelationConcept
resShr)     (UnitalChunk -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit UnitalChunk
shrResI)       (Derivation -> Maybe Derivation
forall a. a -> Maybe a
Just Derivation
resShrDeriv)
  [Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
chen2005]                      String
"resShr"      [Sentence
resShrDesc]
mobShrGD :: GenDefn
mobShrGD     = ModelKind ModelExpr
-> Maybe UnitDefn
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
forall u.
IsUnit u =>
ModelKind ModelExpr
-> Maybe u
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
gd (RelationConcept -> ModelKind ModelExpr
forall e. RelationConcept -> ModelKind e
othModel' RelationConcept
mobShr)     (UnitalChunk -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit UnitalChunk
mobShrI)       (Derivation -> Maybe Derivation
forall a. a -> Maybe a
Just Derivation
mobShrDeriv)
  [Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
chen2005]                      String
"mobShr"      [Sentence
mobShrDesc]
effNormFGD :: GenDefn
effNormFGD   = ModelKind ModelExpr
-> Maybe UnitDefn
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
forall u.
IsUnit u =>
ModelKind ModelExpr
-> Maybe u
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
gd (RelationConcept -> ModelKind ModelExpr
forall e. RelationConcept -> ModelKind e
othModel' RelationConcept
effNormF)   (UnitalChunk -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit UnitalChunk
nrmFSubWat)    (Derivation -> Maybe Derivation
forall a. a -> Maybe a
Just Derivation
effNormFDeriv)
  [Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
chen2005]                      String
"effNormF"    [Sentence
effNormFDesc]
resShearWOGD :: GenDefn
resShearWOGD = ModelKind ModelExpr
-> Maybe UnitDefn
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
forall u.
IsUnit u =>
ModelKind ModelExpr
-> Maybe u
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
gd (RelationConcept -> ModelKind ModelExpr
forall e. RelationConcept -> ModelKind e
othModel' RelationConcept
resShearWO) (UnitalChunk -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit UnitalChunk
shearRNoIntsl) Maybe Derivation
forall a. Maybe a
Nothing
  ((Citation -> DecRef) -> [Citation] -> [DecRef]
forall a b. (a -> b) -> [a] -> [b]
map Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef[Citation
chen2005, Citation
karchewski2012]) String
"resShearWO"  [Sentence
resShearWODesc]
mobShearWOGD :: GenDefn
mobShearWOGD = ModelKind ModelExpr
-> Maybe UnitDefn
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
forall u.
IsUnit u =>
ModelKind ModelExpr
-> Maybe u
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
gd (RelationConcept -> ModelKind ModelExpr
forall e. RelationConcept -> ModelKind e
othModel' RelationConcept
mobShearWO) (UnitalChunk -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit UnitalChunk
shearFNoIntsl) Maybe Derivation
forall a. Maybe a
Nothing
  ((Citation -> DecRef) -> [Citation] -> [DecRef]
forall a b. (a -> b) -> [a] -> [b]
map Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef[Citation
chen2005, Citation
karchewski2012]) String
"mobShearWO"  [Sentence
mobShearWODesc]
normShrRGD :: GenDefn
normShrRGD   = ModelKind ModelExpr
-> Maybe UnitDefn
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
forall u.
IsUnit u =>
ModelKind ModelExpr
-> Maybe u
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
gd (QDefinition ModelExpr -> ModelKind ModelExpr
forall e. QDefinition e -> ModelKind e
equationalModel' QDefinition ModelExpr
normShrR)   (UnitalChunk -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit UnitalChunk
intShrForce)   Maybe Derivation
forall a. Maybe a
Nothing
  [Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
chen2005]                      String
"normShrR"    [Sentence
nmShrRDesc]
momentEqlGD :: GenDefn
momentEqlGD  = ModelKind ModelExpr
-> Maybe UnitDefn
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
forall u.
IsUnit u =>
ModelKind ModelExpr
-> Maybe u
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
gd ModelKind ModelExpr
momentEqlModel        (UnitDefn -> Maybe UnitDefn
forall a. a -> Maybe a
Just UnitDefn
newton)            (Derivation -> Maybe Derivation
forall a. a -> Maybe a
Just Derivation
momEqlDeriv)
  [Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
chen2005]                      String
"momentEql"   [Sentence
momEqlDesc]
sliceWghtGD :: GenDefn
sliceWghtGD  = ModelKind ModelExpr
-> Maybe UnitDefn
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
forall u.
IsUnit u =>
ModelKind ModelExpr
-> Maybe u
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
gd (RelationConcept -> ModelKind ModelExpr
forall e. RelationConcept -> ModelKind e
othModel' RelationConcept
sliceWght)  (UnitalChunk -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit UnitalChunk
slcWght)       (Derivation -> Maybe Derivation
forall a. a -> Maybe a
Just Derivation
sliceWghtDeriv)
  [Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
fredlund1977]                  String
"sliceWght"   [Sentence
sliceWghtNotes]
baseWtrFGD :: GenDefn
baseWtrFGD   = ModelKind ModelExpr
-> Maybe UnitDefn
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
forall u.
IsUnit u =>
ModelKind ModelExpr
-> Maybe u
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
gd (RelationConcept -> ModelKind ModelExpr
forall e. RelationConcept -> ModelKind e
othModel' RelationConcept
baseWtrF)   (UnitalChunk -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit UnitalChunk
baseHydroForce) (Derivation -> Maybe Derivation
forall a. a -> Maybe a
Just Derivation
bsWtrFDeriv)
  [Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
fredlund1977]                  String
"baseWtrF"    [Sentence
bsWtrFNotes]
srfWtrFGD :: GenDefn
srfWtrFGD    = ModelKind ModelExpr
-> Maybe UnitDefn
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
forall u.
IsUnit u =>
ModelKind ModelExpr
-> Maybe u
-> Maybe Derivation
-> [DecRef]
-> String
-> [Sentence]
-> GenDefn
gd (RelationConcept -> ModelKind ModelExpr
forall e. RelationConcept -> ModelKind e
othModel' RelationConcept
srfWtrF)    (UnitalChunk -> Maybe UnitDefn
forall u. MayHaveUnit u => u -> Maybe UnitDefn
getUnit UnitalChunk
surfHydroForce) (Derivation -> Maybe Derivation
forall a. a -> Maybe a
Just Derivation
srfWtrFDeriv)
  [Citation -> DecRef
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> DecRef
dRef Citation
fredlund1977]                  String
"srfWtrF"     [Sentence
srfWtrFNotes]
normForcEq :: RelationConcept
normForcEq :: RelationConcept
normForcEq = String -> NP -> Sentence -> Relation -> RelationConcept
forall e.
Express e =>
String -> NP -> Sentence -> e -> RelationConcept
makeRC String
"normForcEq" (String -> NP
nounPhraseSP String
"normal force equilibrium")
  Sentence
nmFEqDesc Relation
nmFEqRel
nmFEqRel :: Relation
nmFEqRel :: Relation
nmFEqRel = UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
totNrmForce Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$= (Relation -> Relation)
-> (Relation -> Relation)
-> (Relation -> Relation -> Relation)
-> Relation
forall r.
(ExprC r, LiteralC r) =>
(r -> r) -> (r -> r) -> (r -> r -> r) -> r
eqlExprN Relation -> Relation
forall r. ExprC r => r -> r
cos Relation -> Relation
forall r. ExprC r => r -> r
sin
  (\Relation
x Relation
y -> Relation
x Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$- UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
intShrForce Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+ UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
intShrForce Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+ Relation
y)
nmFEqDesc :: Sentence
nmFEqDesc :: Sentence
nmFEqDesc = [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"This equation satisfies", TheoryModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS TheoryModel
equilibrium Sentence -> Sentence -> Sentence
+:+.
  String -> Sentence
S String
"in the normal direction", SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List
  [UnitalChunk
slcWght UnitalChunk -> GenDefn -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` GenDefn
sliceWghtGD, UnitalChunk
surfHydroForce UnitalChunk -> GenDefn -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` GenDefn
srfWtrFGD,
  UnitalChunk
surfAngle UnitalChunk -> DataDefinition -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` DataDefinition
angleB, UnitalChunk
baseAngle UnitalChunk -> DataDefinition -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` DataDefinition
angleA]]
nmFEqDeriv :: Derivation
nmFEqDeriv :: Derivation
nmFEqDeriv = [Sentence] -> Derivation
mkDerivNoHeader [[Sentence] -> Sentence
foldlSent [RelationConcept -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart RelationConcept
normForcEq Sentence -> Sentence -> Sentence
`S.is`
  String -> Sentence
S String
"derived from the free body diagram" Sentence -> Sentence -> Sentence
`S.of_`
  (LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
figForceActing Sentence -> Sentence -> Sentence
`S.in_` Section -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ([Contents] -> [Section] -> Section
SRS.physSyst [] []))]]
bsShrFEq :: RelationConcept
bsShrFEq :: RelationConcept
bsShrFEq = String -> NP -> Sentence -> Relation -> RelationConcept
forall e.
Express e =>
String -> NP -> Sentence -> e -> RelationConcept
makeRC String
"bsShrFEq" (String -> NP
nounPhraseSP String
"base shear force equilibrium")
  Sentence
bShFEqDesc Relation
bShFEqRel
bShFEqRel :: Relation
bShFEqRel :: Relation
bShFEqRel = UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
mobShrI Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$= (Relation -> Relation)
-> (Relation -> Relation)
-> (Relation -> Relation -> Relation)
-> Relation
forall r.
(ExprC r, LiteralC r) =>
(r -> r) -> (r -> r) -> (r -> r -> r) -> r
eqlExpr Relation -> Relation
forall r. ExprC r => r -> r
sin Relation -> Relation
forall r. ExprC r => r -> r
cos
  (\Relation
x Relation
y -> Relation
x Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$- UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
intShrForce Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+ UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
intShrForce Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+ Relation
y)
bShFEqDesc :: Sentence
bShFEqDesc :: Sentence
bShFEqDesc = [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"This equation satisfies", TheoryModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS TheoryModel
equilibrium Sentence -> Sentence -> Sentence
+:+.
  String -> Sentence
S String
"in the shear direction", SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List [UnitalChunk
slcWght UnitalChunk -> GenDefn -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` GenDefn
sliceWghtGD,
  UnitalChunk
surfHydroForce UnitalChunk -> GenDefn -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` GenDefn
srfWtrFGD, UnitalChunk
surfAngle UnitalChunk -> DataDefinition -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` DataDefinition
angleB, 
  UnitalChunk
baseAngle UnitalChunk -> DataDefinition -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` DataDefinition
angleA]]
bShFEqDeriv :: Derivation
bShFEqDeriv :: Derivation
bShFEqDeriv = [Sentence] -> Derivation
mkDerivNoHeader [[Sentence] -> Sentence
foldlSent [RelationConcept -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart RelationConcept
bsShrFEq Sentence -> Sentence -> Sentence
`S.is`
  String -> Sentence
S String
"derived from the free body diagram" Sentence -> Sentence -> Sentence
`S.of_`
  (LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
figForceActing Sentence -> Sentence -> Sentence
`S.in_` Section -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ([Contents] -> [Section] -> Section
SRS.physSyst [] []))]]
shrResEqn :: Expr
shrResEqn :: Relation
shrResEqn = UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
nrmFSubWat Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* Relation -> Relation
forall r. ExprC r => r -> r
tan (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
fricAngle) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+ (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
effCohesion Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* 
  UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseLngth)
resShr :: RelationConcept
resShr :: RelationConcept
resShr = String -> NP -> Sentence -> Relation -> RelationConcept
forall e.
Express e =>
String -> NP -> Sentence -> e -> RelationConcept
makeRC String
"resShr" (String -> NP
nounPhraseSP String
"resistive shear force")
  Sentence
resShrDesc Relation
resShrRel 
resShrRel :: Relation
resShrRel :: Relation
resShrRel = UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
shrResI Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$= Relation
shrResEqn
resShrDesc :: Sentence
resShrDesc :: Sentence
resShrDesc = [Sentence] -> Sentence
foldlSent [UnitalChunk
baseLngth UnitalChunk -> DataDefinition -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` DataDefinition
lengthLb]
resShrDeriv :: Derivation
resShrDeriv :: Derivation
resShrDeriv = [Sentence] -> Derivation
mkDerivNoHeader [[Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"Derived by substituting",
  DataDefinition -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS DataDefinition
normStressDD Sentence -> Sentence -> Sentence
`S.and_` DataDefinition -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS DataDefinition
tangStressDD, String -> Sentence
S String
"into the Mohr-Coulomb", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
shrStress Sentence -> Sentence -> Sentence
`sC`
  TheoryModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS TheoryModel
mcShrStrgth Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"and multiplying both sides" Sentence -> Sentence -> Sentence
`S.ofThe` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
equation, 
  String -> Sentence
S String
"by", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk
genericA UnitalChunk -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` IdeaDict
slice) Sentence -> Sentence -> Sentence
`S.in_`
  String -> Sentence
S String
"the shear-" Sentence -> Sentence -> Sentence
:+: UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
zcoord Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"plane", String -> Sentence
S String
"Since", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
slope),
  String -> Sentence
S String
"is assumed to extend infinitely in", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
zDir),
  Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpPSC) Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"the resulting", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural UnitalChunk
force,
  String -> Sentence
S String
"are expressed per", UnitDefn -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitDefn
metre, String -> Sentence
S String
"in the" Sentence -> Sentence -> Sentence
+:+. ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
zDir, String -> Sentence
S String
"The",
  UncertQ -> Sentence
forall a. Quantity a => a -> Sentence
getTandS UncertQ
fricAngle Sentence -> Sentence -> Sentence
`S.andThe` UncertQ -> Sentence
forall a. Quantity a => a -> Sentence
getTandS UncertQ
effCohesion Sentence -> Sentence -> Sentence
`S.are` String -> Sentence
S String
"not indexed by",
  DefinedQuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch DefinedQuantityDict
index, String -> Sentence
S String
"because they are assumed to be isotropic",
  Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpSLI) Sentence -> Sentence -> Sentence
`S.andThe` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
soil Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"assumed to be",
  String -> Sentence
S String
"homogeneous" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"with", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
constant, IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
soilPrpty, String -> Sentence
S String
"throughout",
  Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpSLH Sentence -> Sentence -> Sentence
`sC` ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpSP)]]
mobShr :: RelationConcept
mobShr :: RelationConcept
mobShr = String -> NP -> Sentence -> Relation -> RelationConcept
forall e.
Express e =>
String -> NP -> Sentence -> e -> RelationConcept
makeRC String
"mobShr" (String -> NP
nounPhraseSP String
"mobilized shear force")
           Sentence
mobShrDesc Relation
mobShrRel
mobShrRel :: Relation
mobShrRel :: Relation
mobShrRel = UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
mobShrI Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$= UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
shrResI Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$/ ConstrConcept -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
fs Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$= Relation
shrResEqn Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$/ ConstrConcept -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy ConstrConcept
fs
mobShrDesc :: Sentence
mobShrDesc :: Sentence
mobShrDesc = (UnitalChunk
baseLngth UnitalChunk -> DataDefinition -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` DataDefinition
lengthLb !.)
mobShrDeriv :: Derivation
mobShrDeriv :: Derivation
mobShrDeriv = [Sentence] -> Derivation
mkDerivNoHeader [[Sentence] -> Sentence
foldlSent_ [UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart' UnitalChunk
mobShrI Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"derived by dividing",
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
definition Sentence -> Sentence -> Sentence
`S.the_ofThe` UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
shrResI, String -> Sentence
S String
"from", GenDefn -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS GenDefn
resShrGD,
  String -> Sentence
S String
"by", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict
definition IdeaDict -> ConstrConcept -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` ConstrConcept
fs), String -> Sentence
S String
"from" Sentence -> Sentence -> Sentence
+:+. TheoryModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS TheoryModel
factOfSafety,
  String -> Sentence
S String
"The", ConstrConcept -> Sentence
forall a. Quantity a => a -> Sentence
getTandS ConstrConcept
fs, String -> Sentence
S String
"is not indexed by", DefinedQuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch DefinedQuantityDict
index,
  String -> Sentence
S String
"because it" Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"assumed to be", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
constant Sentence -> Sentence -> Sentence
`S.for` String -> Sentence
S String
"the entire",
  ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
slpSrf Sentence -> Sentence -> Sentence
+:+. Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpFOSL)]]
effNormF :: RelationConcept
effNormF :: RelationConcept
effNormF = String -> NP -> Sentence -> Relation -> RelationConcept
forall e.
Express e =>
String -> NP -> Sentence -> e -> RelationConcept
makeRC String
"effNormF"
  (String -> NP
nounPhraseSP String
"effective normal force") Sentence
effNormFDesc Relation
effNormFRel
effNormFRel :: Relation
effNormFRel :: Relation
effNormFRel = UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
nrmFSubWat Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$= UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
totNrmForce Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$- UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseHydroForce
effNormFDesc :: Sentence
effNormFDesc :: Sentence
effNormFDesc = (UnitalChunk
baseHydroForce UnitalChunk -> GenDefn -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` GenDefn
baseWtrFGD !.)
effNormFDeriv :: Derivation
effNormFDeriv :: Derivation
effNormFDeriv = [Sentence] -> Derivation
mkDerivNoHeader [[Sentence] -> Sentence
foldlSent [
  String -> Sentence
S String
"Derived by substituting", DataDefinition -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS DataDefinition
normStressDD, String -> Sentence
S String
"into",
  TheoryModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS TheoryModel
effStress Sentence -> Sentence -> Sentence
`S.and_` String -> Sentence
S String
"multiplying both sides of", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
equation),
  String -> Sentence
S String
"by", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk
genericA UnitalChunk -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` IdeaDict
slice), String -> Sentence
S String
"in the shear-" Sentence -> Sentence -> Sentence
:+:
  UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
zcoord Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"plane", String -> Sentence
S String
"Since", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
slope),
  String -> Sentence
S String
"is assumed to extend infinitely in", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
zDir),
  Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpPSC) Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"the resulting", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural UnitalChunk
force,
  String -> Sentence
S String
"are expressed per", UnitDefn -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitDefn
metre, String -> Sentence
S String
"in", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
zDir)]]
normShrR :: ModelQDef
normShrR :: QDefinition ModelExpr
normShrR = UnitalChunk -> ModelExpr -> QDefinition ModelExpr
forall c e.
(Quantity c, MayHaveUnit c, Concept c) =>
c -> e -> QDefinition e
mkQuantDef UnitalChunk
intShrForce ModelExpr
PExpr
nmShrRExpr
nmShrRExpr :: PExpr
nmShrRExpr :: PExpr
nmShrRExpr = DefinedQuantityDict -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
normToShear r -> r -> r
forall r. ExprC r => r -> r -> r
$* DefinedQuantityDict -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
scalFunc r -> r -> r
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
intNormForce
nmShrRDesc :: Sentence
nmShrRDesc :: Sentence
nmShrRDesc = [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"Mathematical representation of the primary",
  CI -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase CI
assumption, String -> Sentence
S String
"for the Morgenstern-Price", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
method_ Sentence -> Sentence -> Sentence
+:+.
  Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpINSFL), DefinedQuantityDict
scalFunc DefinedQuantityDict -> DataDefinition -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` DataDefinition
ratioVariation]
resShearWO :: RelationConcept
resShearWO :: RelationConcept
resShearWO = String -> NP -> Sentence -> Relation -> RelationConcept
forall e.
Express e =>
String -> NP -> Sentence -> e -> RelationConcept
makeRC String
"resShearWO"
  (String -> NP
nounPhraseSP String
"resistive shear force, without interslice normal and shear forces") Sentence
resShearWODesc Relation
resShearWORel
resShearWORel :: Relation
resShearWORel :: Relation
resShearWORel = UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
shearRNoIntsl Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$=
  ((UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slcWght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+ (UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
surfHydroForce Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* Relation -> Relation
forall r. ExprC r => r -> r
cos (UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
surfAngle))) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* 
  Relation -> Relation
forall r. ExprC r => r -> r
cos (UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseAngle) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+ (Relation -> Relation
forall r. ExprC r => r -> r
neg (UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
watrForce) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+ UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
watrForce Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+
  (UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
surfHydroForce Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* Relation -> Relation
forall r. ExprC r => r -> r
sin (UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
surfAngle)) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* Relation -> Relation
forall r. ExprC r => r -> r
sin (UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseAngle) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$-
  UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseHydroForce) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* Relation -> Relation
forall r. ExprC r => r -> r
tan (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
fricAngle) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+ (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
effCohesion Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* 
  UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseLngth))
resShearWODesc :: Sentence
resShearWODesc :: Sentence
resShearWODesc = (SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List [UnitalChunk
slcWght UnitalChunk -> GenDefn -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` GenDefn
sliceWghtGD,
  UnitalChunk
surfHydroForce UnitalChunk -> GenDefn -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` GenDefn
srfWtrFGD,
  UnitalChunk
surfAngle UnitalChunk -> DataDefinition -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` DataDefinition
angleB,
  UnitalChunk
baseAngle UnitalChunk -> DataDefinition -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` DataDefinition
angleA,
  UnitalChunk
watrForce UnitalChunk -> DataDefinition -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` DataDefinition
intersliceWtrF,
  UnitalChunk
baseHydroForce UnitalChunk -> GenDefn -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` GenDefn
baseWtrFGD,
  UnitalChunk
baseLngth UnitalChunk -> DataDefinition -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` DataDefinition
lengthLb] !.)
mobShearWO :: RelationConcept
mobShearWO :: RelationConcept
mobShearWO = String -> NP -> Sentence -> Relation -> RelationConcept
forall e.
Express e =>
String -> NP -> Sentence -> e -> RelationConcept
makeRC String
"mobShearWO"
  (String -> NP
nounPhraseSP String
"mobilized shear force, without interslice normal and shear forces") Sentence
mobShearWODesc Relation
mobShearWORel
mobShearWORel :: Relation
mobShearWORel :: Relation
mobShearWORel = UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
shearFNoIntsl Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$= ((UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slcWght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+ (UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
surfHydroForce Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* 
  Relation -> Relation
forall r. ExprC r => r -> r
cos (UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
surfAngle))) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* Relation -> Relation
forall r. ExprC r => r -> r
sin (UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseAngle) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$- ((Relation -> Relation
forall r. ExprC r => r -> r
neg (UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
watrForce) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+
  UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
watrForce Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+ (UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
surfHydroForce Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* Relation -> Relation
forall r. ExprC r => r -> r
sin (UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
surfAngle))) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* Relation -> Relation
forall r. ExprC r => r -> r
cos (UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseAngle)))
mobShearWODesc :: Sentence
mobShearWODesc :: Sentence
mobShearWODesc = (SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List [UnitalChunk
slcWght UnitalChunk -> GenDefn -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` GenDefn
sliceWghtGD,
  UnitalChunk
surfHydroForce UnitalChunk -> GenDefn -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` GenDefn
srfWtrFGD,
  UnitalChunk
surfAngle UnitalChunk -> DataDefinition -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` DataDefinition
angleB,
  UnitalChunk
baseAngle UnitalChunk -> DataDefinition -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` DataDefinition
angleA,
  UnitalChunk
watrForce UnitalChunk -> DataDefinition -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` DataDefinition
intersliceWtrF] !.)
momentEqlModel :: ModelKind ModelExpr
momentEqlModel :: ModelKind ModelExpr
momentEqlModel = ConstraintSet ModelExpr -> ModelKind ModelExpr
forall e. ConstraintSet e -> ModelKind e
equationalConstraints' (ConstraintSet ModelExpr -> ModelKind ModelExpr)
-> ConstraintSet ModelExpr -> ModelKind ModelExpr
forall a b. (a -> b) -> a -> b
$
  ConceptChunk -> NonEmpty ModelExpr -> ConstraintSet ModelExpr
forall e. ConceptChunk -> NonEmpty e -> ConstraintSet e
mkConstraintSet (String -> NP -> Sentence -> ConceptChunk
dccWDS String
"momentEql" (String -> NP
nounPhraseSP String
"moment equilibrium") Sentence
momEqlDesc) (NonEmpty ModelExpr -> ConstraintSet ModelExpr)
-> NonEmpty ModelExpr -> ConstraintSet ModelExpr
forall a b. (a -> b) -> a -> b
$
  [ModelExpr] -> NonEmpty ModelExpr
forall a. HasCallStack => [a] -> NonEmpty a
NE.fromList [Relation -> ModelExpr
forall c. Express c => c -> ModelExpr
express Relation
momEqlExpr]
momEqlExpr :: Expr
momEqlExpr :: Relation
momEqlExpr = Integer -> Relation
forall r. LiteralC r => Integer -> r
exactDbl Integer
0 Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$= (Relation -> Relation -> Relation) -> Relation
forall r. (ExprC r, LiteralC r) => (r -> r -> r) -> r
momExpr (\ Relation
x Relation
y -> Relation
x Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+
  (Relation -> Relation
forall r. (ExprC r, LiteralC r) => r -> r
half (UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseWthX) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* (UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
intShrForce Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+ UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
intShrForce)) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+ Relation
y)
momEqlDesc :: Sentence
momEqlDesc :: Sentence
momEqlDesc = [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"This", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
equation, String -> Sentence
S String
"satisfies",
  TheoryModel -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS TheoryModel
equilibrium, String -> Sentence
S String
"for the net" Sentence -> Sentence -> Sentence
+:+. UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
genericM,
  SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List [UnitalChunk
baseWthX UnitalChunk -> DataDefinition -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` DataDefinition
lengthB,
  UnitalChunk
baseAngle UnitalChunk -> DataDefinition -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` DataDefinition
angleA,
  UnitalChunk
slcWght UnitalChunk -> GenDefn -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` GenDefn
sliceWghtGD,
  UnitalChunk
midpntHght UnitalChunk -> DataDefinition -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` DataDefinition
slcHeight,
  UnitalChunk
surfHydroForce UnitalChunk -> GenDefn -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` GenDefn
srfWtrFGD,
  UnitalChunk
surfAngle UnitalChunk -> DataDefinition -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` DataDefinition
angleB]]
momEqlDeriv :: Derivation
momEqlDeriv :: Derivation
momEqlDeriv = [Sentence] -> Derivation
mkDerivNoHeader ([[Sentence]] -> [Sentence]
forall a. [[a]] -> [a]
weave [[Sentence]
momEqlDerivSentences, [Sentence]
momEqlDerivEqns])
momEqlDerivSentences :: [Sentence]
momEqlDerivSentences :: [Sentence]
momEqlDerivSentences = ([Sentence] -> Sentence) -> [[Sentence]] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> Sentence
foldlSentCol [[Sentence]
momEqlDerivTorqueSentence,
  [Sentence]
momEqlDerivMomentSentence, [Sentence]
momEqlDerivNormaliSentence,
  [Sentence]
momEqlDerivNormaliM1Sentence, [Sentence]
momEqlDerivWateriSentence,
  [Sentence]
momEqlDerivWateriM1Sentence, [Sentence]
momEqlDerivSheariSentence,
  [Sentence]
momEqlDerivSheariM1Sentence, [Sentence]
momEqlDerivSeismicIntSentence,
  [Sentence]
momEqlDerivSeismicSentence, [Sentence]
momEqlDerivSeismicWSentence,
  [Sentence]
momEqlDerivHydroSentence, [Sentence]
momEqlDerivExtSentence, [Sentence]
momEqlDerivFinalSentence]
momEqlDerivEqns :: [Sentence]
momEqlDerivEqns :: [Sentence]
momEqlDerivEqns = (ModelExpr -> Sentence) -> [ModelExpr] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map ModelExpr -> Sentence
eS [ModelExpr
PExpr
momEqlDerivTorqueEqn, ModelExpr
PExpr
momEqlDerivMomentEqn,
  ModelExpr
PExpr
momEqlDerivNormaliEqn, ModelExpr
PExpr
momEqlDerivNormaliM1Eqn, ModelExpr
PExpr
momEqlDerivWateriEqn,
  ModelExpr
PExpr
momEqlDerivWateriM1Eqn, ModelExpr
PExpr
momEqlDerivSheariEqn,
  ModelExpr
PExpr
momEqlDerivSheariM1Eqn, ModelExpr
PExpr
momEqlDerivSeismicIntEqn,
  ModelExpr
PExpr
momEqlDerivSeismicEqn, ModelExpr
PExpr
momEqlDerivSeismicWEqn,
  ModelExpr
PExpr
momEqlDerivHydroEqn, ModelExpr
PExpr
momEqlDerivExtEqn,
  ModelExpr
PExpr
momEqlDerivFinalEqn]
momEqlDerivTorqueSentence, momEqlDerivMomentSentence,
  momEqlDerivNormaliSentence, momEqlDerivNormaliM1Sentence,
  momEqlDerivWateriSentence, momEqlDerivWateriM1Sentence,
  momEqlDerivSheariSentence, momEqlDerivSheariM1Sentence,
  momEqlDerivSeismicIntSentence, momEqlDerivSeismicSentence,
  momEqlDerivSeismicWSentence, momEqlDerivHydroSentence,
  momEqlDerivExtSentence, momEqlDerivFinalSentence :: [Sentence]
momEqlDerivTorqueEqn, momEqlDerivMomentEqn,
  momEqlDerivNormaliEqn, momEqlDerivNormaliM1Eqn, momEqlDerivWateriEqn,
  momEqlDerivWateriM1Eqn, momEqlDerivSheariEqn,
  momEqlDerivSheariM1Eqn, momEqlDerivSeismicIntEqn,
  momEqlDerivSeismicEqn, momEqlDerivSeismicWEqn,
  momEqlDerivHydroEqn, momEqlDerivExtEqn,
  momEqlDerivFinalEqn :: PExpr
momEqlDerivTorqueSentence :: [Sentence]
momEqlDerivTorqueSentence = [UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
atStart UnitalChunk
genericM, String -> Sentence
S String
"is equal to",
  UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
torque Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"so", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
equation), String -> Sentence
S String
"from", DataDefinition -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS DataDefinition
torqueDD,
  String -> Sentence
S String
"will be used to calculate", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural UnitalChunk
genericM]
momEqlDerivMomentSentence :: [Sentence]
momEqlDerivMomentSentence = [String -> Sentence
S String
"Considering one dimension, with",
  UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural UnitalChunk
genericM, String -> Sentence
S String
"in the clockwise direction as positive and",
  UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural UnitalChunk
genericM, String -> Sentence
S String
"in the counterclockwise direction as negative" Sentence -> Sentence -> Sentence
`sC`
  String -> Sentence
S String
"and replacing", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
torque), String -> Sentence
S String
"symbol with", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
genericM),
  String -> Sentence
S String
"symbol,", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
equation), String -> Sentence
S String
"simplifies to"]
momEqlDerivNormaliSentence :: [Sentence]
momEqlDerivNormaliSentence = [String -> Sentence
S String
"where", UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
rotForce Sentence -> Sentence -> Sentence
`S.isThe`
  UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
rotForce Sentence -> Sentence -> Sentence
`S.and_` UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
momntArm Sentence -> Sentence -> Sentence
`S.isThe` UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
momntArm Sentence -> Sentence -> Sentence
`sC`
  String -> Sentence
S String
"or the distance between", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
force) Sentence -> Sentence -> Sentence
`S.andThe` String -> Sentence
S String
"axis about" Sentence -> Sentence -> Sentence
+:+.
  String -> Sentence
S String
"which the rotation acts",
  String -> Sentence
S String
"To represent", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (GenDefn -> NP
forall t. NamedIdea t => t -> NP
the GenDefn
momentEqlGD) Sentence -> Sentence -> Sentence
`sC` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
genericM),
  String -> Sentence
S String
"from each", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
force, String -> Sentence
S String
"acting on a", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice Sentence -> Sentence -> Sentence
+:+.
  String -> Sentence
S String
"must be considered and added together", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP' (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
force),
  String -> Sentence
S String
"acting on a", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, String -> Sentence
S String
"are all shown in" Sentence -> Sentence -> Sentence
+:+.
  LabelledContent -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS LabelledContent
figForceActing,
  String -> Sentence
S String
"The midpoint of the base" Sentence -> Sentence -> Sentence
`S.ofA` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, String -> Sentence
S String
"is considered as the",
  String -> Sentence
S String
"axis of rotation, from which", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
momntArm) Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"is measured",
  String -> Sentence
S String
"Considering first", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NP -> NP
NP.the (IdeaDict -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI IdeaDict
intrslce ConceptChunk
normForce)),
  String -> Sentence
S String
"acting on", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, String -> Sentence
S String
"interface", DefinedQuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch DefinedQuantityDict
index Sentence -> Sentence -> Sentence
`sC`
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
genericM), String -> Sentence
S String
"is negative because", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
force),
  String -> Sentence
S String
"tends to rotate", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
slice), String -> Sentence
S String
"in a counterclockwise",
  String -> Sentence
S String
"direction" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"and", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
momntArm) Sentence -> Sentence -> Sentence
`S.is` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk
height UnitalChunk -> UnitalChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe`
  UnitalChunk
force), String -> Sentence
S String
"plus the difference" Sentence -> Sentence -> Sentence
`S.in_` String -> Sentence
S String
"height between the base at",
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, String -> Sentence
S String
"interface", DefinedQuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch DefinedQuantityDict
index Sentence -> Sentence -> Sentence
`S.andThe` String -> Sentence
S String
"base at the midpoint of",
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice Sentence -> Sentence -> Sentence
+:+. DefinedQuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch DefinedQuantityDict
index,
  String -> Sentence
S String
"Thus,", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
genericM), String -> Sentence
S String
"is expressed as"]
momEqlDerivNormaliM1Sentence :: [Sentence]
momEqlDerivNormaliM1Sentence = [String -> Sentence
S String
"For the", ModelExpr -> Sentence
eS (DefinedQuantityDict -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
index ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$- Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
int Integer
1) Sentence -> Sentence -> Sentence
:+: String -> Sentence
S String
"th",
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, String -> Sentence
S String
"interface" Sentence -> Sentence -> Sentence
`sC` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
genericM) Sentence -> Sentence -> Sentence
`S.is`
  String -> Sentence
S String
"similar but" Sentence -> Sentence -> Sentence
`S.inThe` String -> Sentence
S String
"opposite direction"]
momEqlDerivWateriSentence :: [Sentence]
momEqlDerivWateriSentence = [String -> Sentence
S String
"Next,", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
intrslce), String -> Sentence
S String
"normal water",
  UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
force Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"is considered", String -> Sentence
S String
"This", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
force, String -> Sentence
S String
"is zero at",
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk
height UnitalChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` ConceptChunk
waterTable) Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"then increases linearly towards",
  String -> Sentence
S String
"base" Sentence -> Sentence -> Sentence
`S.the_ofThe` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, String -> Sentence
S String
"due to the increasing water" Sentence -> Sentence -> Sentence
+:+.
  UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
pressure, String -> Sentence
S String
"For such a triangular distribution" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"the resultant",
  UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
force Sentence -> Sentence -> Sentence
+:+. (String -> Sentence
S String
"acts at one-third" Sentence -> Sentence -> Sentence
`S.ofThe` String -> Sentence
S String
"height"), String -> Sentence
S String
"Thus, for the",
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
intrslce, String -> Sentence
S String
"normal water", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
force, String -> Sentence
S String
"acting on", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice,
  String -> Sentence
S String
"interface", DefinedQuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch DefinedQuantityDict
index Sentence -> Sentence -> Sentence
`sC` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
genericM), String -> Sentence
S String
"is"]
momEqlDerivWateriM1Sentence :: [Sentence]
momEqlDerivWateriM1Sentence = [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
genericM), String -> Sentence
S String
"for the",
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
intrslce, String -> Sentence
S String
"normal water", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
force, String -> Sentence
S String
"acting on", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice,
  String -> Sentence
S String
"interface", ModelExpr -> Sentence
eS (DefinedQuantityDict -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
index ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$- Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
int Integer
1), String -> Sentence
S String
"is"]
momEqlDerivSheariSentence :: [Sentence]
momEqlDerivSheariSentence = [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
intrslce), ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
shearForce,
  String -> Sentence
S String
"at", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, String -> Sentence
S String
"interface", DefinedQuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch DefinedQuantityDict
index, String -> Sentence
S String
"tends to rotate in the",
  String -> Sentence
S String
"clockwise direction, and", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NP -> NP
NP.the (UnitalChunk
momntArm UnitalChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`isThe` ConceptChunk
len)),
  String -> Sentence
S String
"from", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
slice), String -> Sentence
S String
"edge to", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
slice), String -> Sentence
S String
"midpoint" Sentence -> Sentence -> Sentence
`sC`
  String -> Sentence
S String
"equivalent to half" Sentence -> Sentence -> Sentence
`S.of_` (String -> Sentence
S String
"width" Sentence -> Sentence -> Sentence
`S.the_ofThe` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice) Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"so the",
  UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
genericM, String -> Sentence
S String
"is"]
momEqlDerivSheariM1Sentence :: [Sentence]
momEqlDerivSheariM1Sentence = [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (NP -> NP
NP.the (IdeaDict -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI IdeaDict
intrslce ConceptChunk
shearForce)),
  String -> Sentence
S String
"at", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, String -> Sentence
S String
"interface", ModelExpr -> Sentence
eS (DefinedQuantityDict -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
index ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$- Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
int Integer
1), String -> Sentence
S String
"also tends to",
  String -> Sentence
S String
"rotate in the clockwise direction" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"and has the same", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
momntArm Sentence -> Sentence -> Sentence
`sC`
  String -> Sentence
S String
"so", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
genericM), String -> Sentence
S String
"is"]
momEqlDerivSeismicIntSentence :: [Sentence]
momEqlDerivSeismicIntSentence = [String -> Sentence
S String
"Seismic", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural UnitalChunk
force, String -> Sentence
S String
"act over the",
  String -> Sentence
S String
"entire height of the" Sentence -> Sentence -> Sentence
+:+. IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, String -> Sentence
S String
"For each horizontal segment"
  Sentence -> Sentence -> Sentence
`S.ofThe` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"the seismic", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
force Sentence -> Sentence -> Sentence
`S.is`
  ModelExpr -> Sentence
eS (DefinedQuantityDict -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
earthqkLoadFctr ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> ModelExpr
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slcWght), String -> Sentence
S String
"where", ModelExpr -> Sentence
eS (UnitalChunk -> ModelExpr
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slcWght),
  String -> Sentence
S String
"can be expressed as", ModelExpr -> Sentence
eS (UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
genericSpWght ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> ModelExpr
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseWthX ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
yi),
  String -> Sentence
S String
"using", GenDefn -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS GenDefn
weightGD, String -> Sentence
S String
"where", UnitalChunk -> Sentence
forall t. Express t => t -> Sentence
eS' UnitalChunk
yi, String -> Sentence
S String
"is the height of" Sentence -> Sentence -> Sentence
+:+.
  String -> Sentence
S String
"the segment under consideration", String -> Sentence
S String
"The corresponding", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
momntArm Sentence -> Sentence -> Sentence
`S.is`
  UnitalChunk -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch UnitalChunk
yi Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"the height from the base" Sentence -> Sentence -> Sentence
`S.of_` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
slice) Sentence -> Sentence -> Sentence
+:+.
  String -> Sentence
S String
"to the segment under consideration", String -> Sentence
S String
"In reality,", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
force),
  String -> Sentence
S String
"near the surface" Sentence -> Sentence -> Sentence
`S.of_` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
soil), String -> Sentence
S String
"mass are slightly different",
  String -> Sentence
S String
"due to the slope" Sentence -> Sentence -> Sentence
`S.ofThe` String -> Sentence
S String
"surface" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"but this difference is assumed to be",
  String -> Sentence
S String
"negligible" Sentence -> Sentence -> Sentence
+:+. Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpNESSS), String -> Sentence
S String
"The resultant",
  UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
genericM, String -> Sentence
S String
"from", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
force), String -> Sentence
S String
"on all of the segments",
  String -> Sentence
S String
"with an equivalent resultant", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
momntArm, String -> Sentence
S String
"is determined by",
  String -> Sentence
S String
"taking the integral over" Sentence -> Sentence -> Sentence
+:+. NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NP -> NP
NP.the (IdeaDict -> UnitalChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI IdeaDict
slice UnitalChunk
height)), NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP' (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
force), 
  String -> Sentence
S String
"tend to rotate" Sentence -> Sentence -> Sentence
`S.inThe` String -> Sentence
S String
"counterclockwise direction" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"so the",
  UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
genericM, String -> Sentence
S String
"is negative"]
momEqlDerivSeismicSentence :: [Sentence]
momEqlDerivSeismicSentence = [String -> Sentence
S String
"Solving the definite integral yields"]
momEqlDerivSeismicWSentence :: [Sentence]
momEqlDerivSeismicWSentence = [String -> Sentence
S String
"Using", GenDefn -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS GenDefn
weightGD,
  String -> Sentence
S String
"again to express", ModelExpr -> Sentence
eS (UnitalChunk -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
genericSpWght ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> ModelExpr
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseWthX ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> ModelExpr
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
midpntHght),
  String -> Sentence
S String
"as", ModelExpr -> Sentence
eS (UnitalChunk -> ModelExpr
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slcWght) Sentence -> Sentence -> Sentence
`sC` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
genericM), String -> Sentence
S String
"is"]
momEqlDerivHydroSentence :: [Sentence]
momEqlDerivHydroSentence = [String -> Sentence
S String
"The surface hydrostatic", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
force,
  String -> Sentence
S String
"acts into the midpoint" Sentence -> Sentence -> Sentence
`S.ofThe` String -> Sentence
S String
"surface of", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
slice) Sentence -> Sentence -> Sentence
+:+.
  Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpHFSM),
  String -> Sentence
S String
"Thus, the vertical", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict
component IdeaDict -> UnitalChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`ofThe` UnitalChunk
force),
  String -> Sentence
S String
"acts directly towards the point of rotation" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"and has a",
  UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
genericM Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"of zero", String -> Sentence
S String
"The horizontal", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict
component
  IdeaDict -> UnitalChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`ofThe` UnitalChunk
force), String -> Sentence
S String
"tends to rotate" Sentence -> Sentence -> Sentence
`S.in_` String -> Sentence
S String
"a clockwise direction" Sentence -> Sentence -> Sentence
`S.and_`
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
momntArm), String -> Sentence
S String
"is the entire height of the" Sentence -> Sentence -> Sentence
+:+. IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice,
  String -> Sentence
S String
"Thus,", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
genericM), String -> Sentence
S String
"is"]
momEqlDerivExtSentence :: [Sentence]
momEqlDerivExtSentence = [String -> Sentence
S String
"The external", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
force, String -> Sentence
S String
"again acts into",
  String -> Sentence
S String
"midpoint" Sentence -> Sentence -> Sentence
`S.the_ofThe` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, String -> Sentence
S String
"surface" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"so the vertical",
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
component, String -> Sentence
S String
"does not contribute to", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
genericM) Sentence -> Sentence -> Sentence
`sC`
  String -> Sentence
S String
"and", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
momntArm), String -> Sentence
S String
"is again the entire height of the" Sentence -> Sentence -> Sentence
+:+.
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
genericM), String -> Sentence
S String
"is"]
momEqlDerivFinalSentence :: [Sentence]
momEqlDerivFinalSentence = [String -> Sentence
S String
"The base hydrostatic", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk
force UnitalChunk -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_`
  IdeaDict
slice), ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
weight, String -> Sentence
S String
"both act in the direction" Sentence -> Sentence -> Sentence
`S.ofThe` String -> Sentence
S String
"point of",
  String -> Sentence
S String
"rotation", Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpHFSM) Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"therefore both have",
  UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural UnitalChunk
genericM Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"of zero", String -> Sentence
S String
"Thus, all of", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
genericM) Sentence -> Sentence -> Sentence
+:+.
  String -> Sentence
S String
"have been determined", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (GenDefn -> NP
forall t. NamedIdea t => t -> NP
the GenDefn
momentEqlGD) Sentence -> Sentence -> Sentence
`S.is`
  String -> Sentence
S String
"then represented by the sum of all", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural UnitalChunk
genericM]
momEqlDerivTorqueEqn :: PExpr
momEqlDerivTorqueEqn = UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
torque r -> r -> r
forall r. ExprC r => r -> r -> r
$= r -> r -> r
forall r. ExprC r => r -> r -> r
cross (UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
displacement) (UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
force)
momEqlDerivMomentEqn :: PExpr
momEqlDerivMomentEqn = UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
genericM r -> r -> r
forall r. ExprC r => r -> r -> r
$= UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
rotForce r -> r -> r
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
momntArm
momEqlDerivNormaliEqn :: PExpr
momEqlDerivNormaliEqn = r -> r
forall r. ExprC r => r -> r
neg (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
intNormForce) r -> r -> r
forall r. ExprC r => r -> r -> r
$* (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
sliceHght r -> r -> r
forall r. ExprC r => r -> r -> r
$+
  (r -> r
forall r. (ExprC r, LiteralC r) => r -> r
half (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseWthX) r -> r -> r
forall r. ExprC r => r -> r -> r
$* r -> r
forall r. ExprC r => r -> r
tan (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseAngle)))
momEqlDerivNormaliM1Eqn :: PExpr
momEqlDerivNormaliM1Eqn = UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
intNormForce r -> r -> r
forall r. ExprC r => r -> r -> r
$* (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
sliceHght r -> r -> r
forall r. ExprC r => r -> r -> r
$-
  (r -> r
forall r. (ExprC r, LiteralC r) => r -> r
half (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseWthX) r -> r -> r
forall r. ExprC r => r -> r -> r
$* r -> r
forall r. ExprC r => r -> r
tan (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseAngle)))
momEqlDerivWateriEqn :: PExpr
momEqlDerivWateriEqn = r -> r
forall r. ExprC r => r -> r
neg (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
watrForce) r -> r -> r
forall r. ExprC r => r -> r -> r
$* (Integer -> Integer -> r
forall r. (ExprC r, LiteralC r) => Integer -> Integer -> r
frac Integer
1 Integer
3 r -> r -> r
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
sliceHghtW r -> r -> r
forall r. ExprC r => r -> r -> r
$+
  (r -> r
forall r. (ExprC r, LiteralC r) => r -> r
half (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseWthX) r -> r -> r
forall r. ExprC r => r -> r -> r
$* r -> r
forall r. ExprC r => r -> r
tan (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseAngle)))
momEqlDerivWateriM1Eqn :: PExpr
momEqlDerivWateriM1Eqn = UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
watrForce r -> r -> r
forall r. ExprC r => r -> r -> r
$* (Integer -> Integer -> r
forall r. (ExprC r, LiteralC r) => Integer -> Integer -> r
frac Integer
1 Integer
3 r -> r -> r
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
sliceHghtW r -> r -> r
forall r. ExprC r => r -> r -> r
$+
  (r -> r
forall r. (ExprC r, LiteralC r) => r -> r
half (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseWthX) r -> r -> r
forall r. ExprC r => r -> r -> r
$* r -> r
forall r. ExprC r => r -> r
tan (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseAngle)))
momEqlDerivSheariEqn :: PExpr
momEqlDerivSheariEqn = UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
intShrForce r -> r -> r
forall r. ExprC r => r -> r -> r
$* r -> r
forall r. (ExprC r, LiteralC r) => r -> r
half (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseWthX)
momEqlDerivSheariM1Eqn :: PExpr
momEqlDerivSheariM1Eqn = UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
intShrForce r -> r -> r
forall r. ExprC r => r -> r -> r
$* r -> r
forall r. (ExprC r, LiteralC r) => r -> r
half (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseWthX)
momEqlDerivSeismicIntEqn :: PExpr
momEqlDerivSeismicIntEqn = r -> r
forall r. ExprC r => r -> r
neg (r -> r) -> r -> r
forall a b. (a -> b) -> a -> b
$ Symbol -> r -> r -> r -> r
forall r. ExprC r => Symbol -> r -> r -> r -> r
defint (UnitalChunk -> Symbol
forall q. HasSymbol q => q -> Symbol
eqSymb UnitalChunk
yi) (Integer -> r
forall r. LiteralC r => Integer -> r
exactDbl Integer
0) (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
midpntHght)
  (DefinedQuantityDict -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
earthqkLoadFctr r -> r -> r
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
genericSpWght r -> r -> r
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseWthX r -> r -> r
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
yi)
momEqlDerivSeismicEqn :: PExpr
momEqlDerivSeismicEqn = r -> r
forall r. ExprC r => r -> r
neg (r -> r) -> r -> r
forall a b. (a -> b) -> a -> b
$ DefinedQuantityDict -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
earthqkLoadFctr r -> r -> r
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
genericSpWght r -> r -> r
forall r. ExprC r => r -> r -> r
$* 
  UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseWthX r -> r -> r
forall r. ExprC r => r -> r -> r
$* r -> r
forall r. (ExprC r, LiteralC r) => r -> r
half (r -> r
forall r. (ExprC r, LiteralC r) => r -> r
square (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
midpntHght))
momEqlDerivSeismicWEqn :: PExpr
momEqlDerivSeismicWEqn = r -> r
forall r. ExprC r => r -> r
neg (r -> r) -> r -> r
forall a b. (a -> b) -> a -> b
$ DefinedQuantityDict -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
earthqkLoadFctr r -> r -> r
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slcWght r -> r -> r
forall r. ExprC r => r -> r -> r
$* 
  r -> r
forall r. (ExprC r, LiteralC r) => r -> r
half (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
midpntHght)
momEqlDerivHydroEqn :: PExpr
momEqlDerivHydroEqn = UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
surfHydroForce r -> r -> r
forall r. ExprC r => r -> r -> r
$* r -> r
forall r. ExprC r => r -> r
sin (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
surfAngle) r -> r -> r
forall r. ExprC r => r -> r -> r
$* 
  UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
midpntHght
momEqlDerivExtEqn :: PExpr
momEqlDerivExtEqn = UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
surfLoad r -> r -> r
forall r. ExprC r => r -> r -> r
$* r -> r
forall r. ExprC r => r -> r
sin (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
impLoadAngle) r -> r -> r
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
midpntHght
momEqlDerivFinalEqn :: PExpr
momEqlDerivFinalEqn = Integer -> r
forall r. LiteralC r => Integer -> r
exactDbl Integer
0 r -> r -> r
forall r. ExprC r => r -> r -> r
$= (r -> r -> r) -> r
forall r. (ExprC r, LiteralC r) => (r -> r -> r) -> r
momExpr (\ r
x r
y -> r
x r -> r -> r
forall r. ExprC r => r -> r -> r
$+
  (r -> r
forall r. (ExprC r, LiteralC r) => r -> r
half (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseWthX) r -> r -> r
forall r. ExprC r => r -> r -> r
$* (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
intShrForce r -> r -> r
forall r. ExprC r => r -> r -> r
$+ UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
intShrForce)) r -> r -> r
forall r. ExprC r => r -> r -> r
$+ r
y)
sliceWght :: RelationConcept
sliceWght :: RelationConcept
sliceWght = String -> NP -> Sentence -> Relation -> RelationConcept
forall e.
Express e =>
String -> NP -> Sentence -> e -> RelationConcept
makeRC String
"sliceWght" (String -> NP
nounPhraseSP String
"slice weight") Sentence
sliceWghtNotes
  Relation
sliceWghtEqn
sliceWghtEqn :: Expr
sliceWghtEqn :: Relation
sliceWghtEqn = UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slcWght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$= UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseWthX Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* Relation
PExpr
oneHalf Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* [(Relation, Relation)] -> Relation
forall r. ExprC r => [(r, r)] -> r
completeCase [(Relation, Relation)
case1, (Relation, Relation)
case2, (Relation, Relation)
case3]
  where case1 :: (Relation, Relation)
case1 = (((UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
slopeHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$- UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slipHght) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+
          (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
slopeHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$- UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
slipHght)) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* UncertQ -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
satWeight,
          (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
waterHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$> UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
slopeHght) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$||
          (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
waterHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$> UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
slopeHght))
        case2 :: (Relation, Relation)
case2 = (((UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
slopeHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$- UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
waterHght) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+
          (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
slopeHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$- UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
waterHght)) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* UncertQ -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
dryWeight Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+
          (((UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
waterHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$- UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slipHght) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+
          (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
waterHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$- UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
slipHght)) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* UncertQ -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
satWeight),
          (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
slopeHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$>= UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
waterHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$>= UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slipHght) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$&&
          (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
slopeHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$>= UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
waterHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$>= UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
slipHght))
        case3 :: (Relation, Relation)
case3 = (((UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
slopeHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$- UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slipHght) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+
          (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
slopeHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$- UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
slipHght)) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* UncertQ -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
dryWeight,
          (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
waterHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$< UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slipHght) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$||
          (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
waterHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$< UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
slipHght))
sliceWghtNotes :: Sentence
sliceWghtNotes :: Sentence
sliceWghtNotes = [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"This", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
equation, String -> Sentence
S String
"is based on the",
  CI -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase CI
assumption, String -> Sentence
S String
"that the surface and the base" Sentence -> Sentence -> Sentence
`S.ofA` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice,
  String -> Sentence
S String
"are straight lines" Sentence -> Sentence -> Sentence
+:+. Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpSBSBISL), String -> Sentence
S String
"The",
  UncertQ -> Sentence
forall a. Quantity a => a -> Sentence
getTandS UncertQ
dryWeight Sentence -> Sentence -> Sentence
`S.andThe` UncertQ -> Sentence
forall a. Quantity a => a -> Sentence
getTandS UncertQ
satWeight, String -> Sentence
S String
"are not indexed by",
  DefinedQuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch DefinedQuantityDict
index, String -> Sentence
S String
"because", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
soil), String -> Sentence
S String
"is assumed to be homogeneous" Sentence -> Sentence -> Sentence
`sC`
  String -> Sentence
S String
"with", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (IdeaDict -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI IdeaDict
constant IdeaDict
soilPrpty), String -> Sentence
S String
"throughout" Sentence -> Sentence -> Sentence
+:+.
  Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpSLH), UnitalChunk
baseWthX UnitalChunk -> DataDefinition -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` DataDefinition
lengthB]
sliceWghtDeriv :: Derivation
sliceWghtDeriv :: Derivation
sliceWghtDeriv = [Sentence] -> Derivation
mkDerivNoHeader ([[Sentence]] -> [Sentence]
forall a. [[a]] -> [a]
weave [[Sentence]
sliceWghtDerivSentences, [Sentence]
sliceWghtDerivEqns])
sliceWghtDerivEqns :: [Sentence]
sliceWghtDerivEqns :: [Sentence]
sliceWghtDerivEqns = (ModelExpr -> Sentence) -> [ModelExpr] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map ModelExpr -> Sentence
eS [ModelExpr
PExpr
sliceWghtDerivSatCaseWeightEqn,
  ModelExpr
PExpr
sliceWghtDerivSatCaseSliceEqn, ModelExpr
PExpr
sliceWghtDerivDryCaseWeightEqn,
  ModelExpr
PExpr
sliceWghtDerivDryCaseSliceEqn, ModelExpr
PExpr
sliceWghtDerivMixCaseWeightEqn,
  ModelExpr
PExpr
sliceWghtDerivMixCaseSliceEqn]
sliceWghtDerivSentences :: [Sentence]
sliceWghtDerivSentences :: [Sentence]
sliceWghtDerivSentences = ([Sentence] -> Sentence) -> [[Sentence]] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> Sentence
foldlSentCol [[Sentence]
sliceWghtDerivSatCaseIntroSentence,
  [Sentence]
sliceWghtDerivSatCase2DSentence, [Sentence]
sliceWghtDerivDryCaseIntroSentence,
  [Sentence]
sliceWghtDerivDryCase2DSentence, [Sentence]
sliceWghtDerivMixCaseIntroSentence,
  [Sentence]
sliceWghtDerivMixCase2DSentence]
sliceWghtDerivSatCaseIntroSentence, sliceWghtDerivSatCase2DSentence,
  sliceWghtDerivDryCaseIntroSentence, sliceWghtDerivDryCase2DSentence,
  sliceWghtDerivMixCaseIntroSentence,
  sliceWghtDerivMixCase2DSentence :: [Sentence]
sliceWghtDerivSatCaseWeightEqn, sliceWghtDerivSatCaseSliceEqn,
  sliceWghtDerivDryCaseWeightEqn, sliceWghtDerivDryCaseSliceEqn,
  sliceWghtDerivMixCaseWeightEqn, sliceWghtDerivMixCaseSliceEqn :: PExpr
sliceWghtDerivSatCaseIntroSentence :: [Sentence]
sliceWghtDerivSatCaseIntroSentence = [String -> Sentence
S String
"For the case where the",
  ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
waterTable, String -> Sentence
S String
"is above", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
slopeSrf) Sentence -> Sentence -> Sentence
`sC`
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
slcWght), String -> Sentence
S String
"come from", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
weight Sentence -> Sentence -> Sentence
`S.the_ofThe` String -> Sentence
S String
"saturated" Sentence -> Sentence -> Sentence
+:+.
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
soil,
  String -> Sentence
S String
"Substituting", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
value, String -> Sentence
S String
"for saturated", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
soil, String -> Sentence
S String
"into the",
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk
equation ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`for` ConceptChunk
weight), String -> Sentence
S String
"from", GenDefn -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS GenDefn
weightGD,
  String -> Sentence
S String
"yields"]
sliceWghtDerivSatCase2DSentence :: [Sentence]
sliceWghtDerivSatCase2DSentence = [String -> Sentence
S String
"Due to", ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpPSC Sentence -> Sentence -> Sentence
`sC`
  String -> Sentence
S String
"only two dimensions are considered, so", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
area) Sentence -> Sentence -> Sentence
`S.of_`
  String -> Sentence
S String
"saturated", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
soil, String -> Sentence
S String
"are considered instead of the" Sentence -> Sentence -> Sentence
+:+.
  UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
satVol,
  String -> Sentence
S String
"Any given", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"has a trapezoidal shape",
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
area) Sentence -> Sentence -> Sentence
`S.ofA` String -> Sentence
S String
"trapezoid" Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"the average of",
  ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
len Sentence -> Sentence -> Sentence
`S.the_ofThe` String -> Sentence
S String
"parallel sides multiplied by", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
len) Sentence -> Sentence -> Sentence
+:+.
  String -> Sentence
S String
"between the parallel sides", String -> Sentence
S String
"The parallel sides in this case are the",
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
intrslce, String -> Sentence
S String
"edges and", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
len), String -> Sentence
S String
"between them" Sentence -> Sentence -> Sentence
`S.isThe`
  String -> Sentence
S String
"width of the" Sentence -> Sentence -> Sentence
+:+. IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, String -> Sentence
S String
"Thus" Sentence -> Sentence -> Sentence
`sC` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
slcWght),
  String -> Sentence
S String
"are defined as"]
sliceWghtDerivSatCaseWeightEqn :: PExpr
sliceWghtDerivSatCaseWeightEqn = UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slcWght r -> r -> r
forall r. ExprC r => r -> r -> r
$= UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
satVol r -> r -> r
forall r. ExprC r => r -> r -> r
$* UncertQ -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
satWeight
sliceWghtDerivSatCaseSliceEqn :: PExpr
sliceWghtDerivSatCaseSliceEqn = UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slcWght r -> r -> r
forall r. ExprC r => r -> r -> r
$= UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseWthX r -> r -> r
forall r. ExprC r => r -> r -> r
$* r
PExpr
oneHalf r -> r -> r
forall r. ExprC r => r -> r -> r
$* 
  ((UncertQ -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
slopeHght r -> r -> r
forall r. ExprC r => r -> r -> r
$- UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slipHght) r -> r -> r
forall r. ExprC r => r -> r -> r
$+ (UncertQ -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
slopeHght r -> r -> r
forall r. ExprC r => r -> r -> r
$- UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
slipHght)) r -> r -> r
forall r. ExprC r => r -> r -> r
$* UncertQ -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
satWeight
sliceWghtDerivDryCaseIntroSentence :: [Sentence]
sliceWghtDerivDryCaseIntroSentence = [String -> Sentence
S String
"For the case where the",
  ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
waterTable, String -> Sentence
S String
"is below", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
slpSrf) Sentence -> Sentence -> Sentence
`sC`
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
slcWght), String -> Sentence
S String
"come from", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
weight Sentence -> Sentence -> Sentence
`S.the_ofThe` String -> Sentence
S String
"dry" Sentence -> Sentence -> Sentence
+:+. IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
soil,
  String -> Sentence
S String
"Substituting", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
value, String -> Sentence
S String
"for dry", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
soil, String -> Sentence
S String
"into the",
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk
equation ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`for` ConceptChunk
weight), String -> Sentence
S String
"from", GenDefn -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS GenDefn
weightGD,
  String -> Sentence
S String
"yields"]
sliceWghtDerivDryCase2DSentence :: [Sentence]
sliceWghtDerivDryCase2DSentence = [ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpPSC, String -> Sentence
S String
"again allows for",
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (CI -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI CI
twoD IdeaDict
analysis), String -> Sentence
S String
"so", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
area) Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S String
"dry",
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
soil, String -> Sentence
S String
"are considered instead of the" Sentence -> Sentence -> Sentence
+:+. UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
dryVol,
  String -> Sentence
S String
"The trapezoidal", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice,
  String -> Sentence
S String
"shape" Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"the same as in the previous case" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"so", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
slcWght),
  String -> Sentence
S String
"are defined as"]
sliceWghtDerivDryCaseWeightEqn :: PExpr
sliceWghtDerivDryCaseWeightEqn = UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slcWght r -> r -> r
forall r. ExprC r => r -> r -> r
$= UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
dryVol r -> r -> r
forall r. ExprC r => r -> r -> r
$* UncertQ -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
dryWeight
sliceWghtDerivDryCaseSliceEqn :: PExpr
sliceWghtDerivDryCaseSliceEqn = UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slcWght r -> r -> r
forall r. ExprC r => r -> r -> r
$= UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseWthX r -> r -> r
forall r. ExprC r => r -> r -> r
$* r
PExpr
oneHalf r -> r -> r
forall r. ExprC r => r -> r -> r
$* 
  ((UncertQ -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
slopeHght r -> r -> r
forall r. ExprC r => r -> r -> r
$- UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slipHght) r -> r -> r
forall r. ExprC r => r -> r -> r
$+ (UncertQ -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
slopeHght r -> r -> r
forall r. ExprC r => r -> r -> r
$- UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
slipHght)) r -> r -> r
forall r. ExprC r => r -> r -> r
$* UncertQ -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
dryWeight
sliceWghtDerivMixCaseIntroSentence :: [Sentence]
sliceWghtDerivMixCaseIntroSentence = [String -> Sentence
S String
"For the case where the",
  ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
waterTable, String -> Sentence
S String
"is between", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NP -> NP
NP.the (IdeaDict
slopeSrf IdeaDict -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_`
  ConceptChunk
slpSrf)) Sentence -> Sentence -> Sentence
`sC` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
slcWght), String -> Sentence
S String
"are the sums of",
  ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
weight Sentence -> Sentence -> Sentence
`S.the_ofThe` String -> Sentence
S String
"dry portions" Sentence -> Sentence -> Sentence
`S.and_` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
weight Sentence -> Sentence -> Sentence
`S.ofThe`
  String -> Sentence
S String
"saturated portions of the" Sentence -> Sentence -> Sentence
+:+. IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
soil,
  String -> Sentence
S String
"Substituting", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
value, String -> Sentence
S String
"for dry and saturated", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
soil,
  String -> Sentence
S String
"into", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NP -> NP
NP.the (ConceptChunk
equation ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`for` ConceptChunk
weight)),
  String -> Sentence
S String
"from", GenDefn -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS GenDefn
weightGD, String -> Sentence
S String
"and adding them together yields"]
sliceWghtDerivMixCase2DSentence :: [Sentence]
sliceWghtDerivMixCase2DSentence = [ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpPSC, String -> Sentence
S String
"again allows for",
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (CI -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
combineNINI CI
twoD IdeaDict
analysis), String -> Sentence
S String
"so", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
area) Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S String
"dry",
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
soil Sentence -> Sentence -> Sentence
`S.and_` ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural ConceptChunk
area Sentence -> Sentence -> Sentence
`S.of_` String -> Sentence
S String
"saturated", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
soil,
  String -> Sentence
S String
"are considered instead of the" Sentence -> Sentence -> Sentence
+:+. NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk
dryVol UnitalChunk -> UnitalChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_` UnitalChunk
satVol),
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
waterTable) Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"assumed to only intersect a", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice,
  String -> Sentence
S String
"surface or base at a", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, String -> Sentence
S String
"edge",
  Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpWISE Sentence -> Sentence -> Sentence
`sC` ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpWIBE) Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"so the" Sentence -> Sentence -> Sentence
+:+.
  String -> Sentence
S String
"dry and saturated portions each have trapezoidal shape", String -> Sentence
S String
"For the dry",
  String -> Sentence
S String
"portion, the parallel sides of the trapezoid are", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
len),
  String -> Sentence
S String
"between", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (NP -> NP
NP.the (IdeaDict
slopeSrf IdeaDict -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_` ConceptChunk
waterTable)), String -> Sentence
S String
"at the",
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"edges", String -> Sentence
S String
"For the saturated portion" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"the parallel",
  String -> Sentence
S String
"sides of the trapezoid are", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
len), String -> Sentence
S String
"between the",
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk
waterTable ConceptChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`and_` ConceptChunk
slpSrf), String -> Sentence
S String
"at", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
slice) Sentence -> Sentence -> Sentence
+:+.
  String -> Sentence
S String
"edges", String -> Sentence
S String
"Thus" Sentence -> Sentence -> Sentence
`sC` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
slcWght), String -> Sentence
S String
"are defined as"]
sliceWghtDerivMixCaseWeightEqn :: PExpr
sliceWghtDerivMixCaseWeightEqn = UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slcWght r -> r -> r
forall r. ExprC r => r -> r -> r
$= UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
dryVol r -> r -> r
forall r. ExprC r => r -> r -> r
$* UncertQ -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
dryWeight r -> r -> r
forall r. ExprC r => r -> r -> r
$+
  (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
satVol r -> r -> r
forall r. ExprC r => r -> r -> r
$* UncertQ -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
satWeight)
sliceWghtDerivMixCaseSliceEqn :: PExpr
sliceWghtDerivMixCaseSliceEqn = UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slcWght r -> r -> r
forall r. ExprC r => r -> r -> r
$= (UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseWthX r -> r -> r
forall r. ExprC r => r -> r -> r
$* r
PExpr
oneHalf r -> r -> r
forall r. ExprC r => r -> r -> r
$* 
  (((UncertQ -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
slopeHght r -> r -> r
forall r. ExprC r => r -> r -> r
$- UncertQ -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
waterHght) r -> r -> r
forall r. ExprC r => r -> r -> r
$+
  (UncertQ -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
slopeHght r -> r -> r
forall r. ExprC r => r -> r -> r
$- UncertQ -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
waterHght)) r -> r -> r
forall r. ExprC r => r -> r -> r
$* UncertQ -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
dryWeight r -> r -> r
forall r. ExprC r => r -> r -> r
$+
  (((UncertQ -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
waterHght r -> r -> r
forall r. ExprC r => r -> r -> r
$- UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slipHght) r -> r -> r
forall r. ExprC r => r -> r -> r
$+
  (UncertQ -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
waterHght r -> r -> r
forall r. ExprC r => r -> r -> r
$- UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
slipHght)) r -> r -> r
forall r. ExprC r => r -> r -> r
$* UncertQ -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
satWeight)))
baseWtrF :: RelationConcept
baseWtrF :: RelationConcept
baseWtrF = String -> NP -> Sentence -> Relation -> RelationConcept
forall e.
Express e =>
String -> NP -> Sentence -> e -> RelationConcept
makeRC String
"baseWtrF" (String -> NP
nounPhraseSP String
"base hydrostatic force")
  Sentence
bsWtrFNotes Relation
bsWtrFEqn
bsWtrFEqn :: Expr
bsWtrFEqn :: Relation
bsWtrFEqn = UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseHydroForce Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$= UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseLngth Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* UncertQ -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
waterWeight Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* Relation
PExpr
oneHalf Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* 
  [(Relation, Relation)] -> Relation
forall r. ExprC r => [(r, r)] -> r
completeCase [(Relation, Relation)
case1, (Relation, Relation)
case2]
  where case1 :: (Relation, Relation)
case1 = ((UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
waterHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$- UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slipHght) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+
          (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
waterHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$- UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
slipHght),
          (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
waterHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$> UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slipHght) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$||
          (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
waterHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$> UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
slipHght))
        case2 :: (Relation, Relation)
case2 = (Integer -> Relation
forall r. LiteralC r => Integer -> r
exactDbl Integer
0, (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
waterHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$<= UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slipHght) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$&&
          (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
waterHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$<= UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
slipHght))
bsWtrFNotes :: Sentence
bsWtrFNotes :: Sentence
bsWtrFNotes = [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"This", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
equation, String -> Sentence
S String
"is based on the",
  CI -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase CI
assumption, String -> Sentence
S String
"that the base" Sentence -> Sentence -> Sentence
`S.ofA` IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice,
  String -> Sentence
S String
"is a straight line" Sentence -> Sentence -> Sentence
+:+. Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpSBSBISL),
  UnitalChunk
baseLngth UnitalChunk -> DataDefinition -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` DataDefinition
lengthLb]
bsWtrFDeriv :: Derivation
bsWtrFDeriv :: Derivation
bsWtrFDeriv = [Sentence] -> Derivation
mkDerivNoHeader ([[Sentence]] -> [Sentence]
forall a. [[a]] -> [a]
weave [[Sentence]
bsWtrFDerivSentences, [Sentence]
bsWtrFDerivEqns] [Sentence] -> [Sentence] -> [Sentence]
forall a. [a] -> [a] -> [a]
++
  [Sentence]
bsWtrFDerivEndSentence)
bsWtrFDerivEqns :: [Sentence]
bsWtrFDerivEqns :: [Sentence]
bsWtrFDerivEqns = (ModelExpr -> Sentence) -> [ModelExpr] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map ModelExpr -> Sentence
eS [ModelExpr
PExpr
bsWtrFDerivWeightEqn, ModelExpr
PExpr
bsWtrFDerivHeightEqn,
  ModelExpr
PExpr
bsWtrFDerivSliceEqn]
bsWtrFDerivSentences :: [Sentence]
bsWtrFDerivSentences :: [Sentence]
bsWtrFDerivSentences = ([Sentence] -> Sentence) -> [[Sentence]] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> Sentence
foldlSentCol [[Sentence]
bsWtrFDerivIntroSentence,
  [Sentence]
bsWtrFDerivHeightSentence, [Sentence]
bsWtrFDeriv2DSentence]
bsWtrFDerivIntroSentence, bsWtrFDerivHeightSentence, bsWtrFDeriv2DSentence,
  bsWtrFDerivEndSentence :: [Sentence]
bsWtrFDerivWeightEqn, bsWtrFDerivHeightEqn, bsWtrFDerivSliceEqn :: PExpr
bsWtrFDerivIntroSentence :: [Sentence]
bsWtrFDerivIntroSentence = [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
baseHydroForce), String -> Sentence
S String
"come from the",
  String -> Sentence
S String
"hydrostatic", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
pressure, String -> Sentence
S String
"exerted by the water above the base of",
  String -> Sentence
S String
"each" Sentence -> Sentence -> Sentence
+:+. IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice,
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
equation), String -> Sentence
S String
"for hydrostatic", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
pressure,
  String -> Sentence
S String
"from", GenDefn -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS GenDefn
hsPressureGD, String -> Sentence
S String
"is"]
bsWtrFDerivHeightSentence :: [Sentence]
bsWtrFDerivHeightSentence = [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
specWeight), String -> Sentence
S String
"in this case is",
  String -> Sentence
S String
"the" Sentence -> Sentence -> Sentence
+:+. UncertQ -> Sentence
forall a. Quantity a => a -> Sentence
getTandS UncertQ
waterWeight,
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
height), String -> Sentence
S String
"in this case" Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"the height from", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
slice),
  String -> Sentence
S String
"base to the" Sentence -> Sentence -> Sentence
+:+. ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
waterTable,
  String -> Sentence
S String
"This", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
height, String -> Sentence
S String
"is measured from", String -> Sentence
S String
"midpoint" Sentence -> Sentence -> Sentence
`S.the_ofThe`
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, String -> Sentence
S String
"because the resultant hydrostatic", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
force,
  String -> Sentence
S String
"is assumed to act at", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
slice), String -> Sentence
S String
"midpoint" Sentence -> Sentence -> Sentence
+:+.
  Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpHFSM),
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
height), String -> Sentence
S String
"at the midpoint" Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"the average of the",
  UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
height, String -> Sentence
S String
"at", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, String -> Sentence
S String
"interface", DefinedQuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch DefinedQuantityDict
index Sentence -> Sentence -> Sentence
`S.andThe`
  UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
height, String -> Sentence
S String
"at", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, String -> Sentence
S String
"interface", ModelExpr -> Sentence
eS (DefinedQuantityDict -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
index ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$- Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
int Integer
1)]
bsWtrFDeriv2DSentence :: [Sentence]
bsWtrFDeriv2DSentence = [String -> Sentence
S String
"Due to", ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpPSC Sentence -> Sentence -> Sentence
`sC`
  String -> Sentence
S String
"only two dimensions" Sentence -> Sentence -> Sentence
`S.are` String -> Sentence
S String
"considered" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"so", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
baseHydroForce),
  String -> Sentence
S String
"are expressed as", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural UnitalChunk
force Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"per meter",
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP' (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
pressure), String -> Sentence
S String
"acting on", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
slice), String -> Sentence
S String
"can thus be converted",
  String -> Sentence
S String
"to", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
baseHydroForce, String -> Sentence
S String
"by multiplying by the corresponding",
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk
len ConceptChunk -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`ofThe` IdeaDict
slice), String -> Sentence
S String
"base", ModelExpr -> Sentence
eS (UnitalChunk -> ModelExpr
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseLngth) Sentence -> Sentence -> Sentence
`sC`
  String -> Sentence
S String
"assuming", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
waterTable), String -> Sentence
S String
"does not intersect a", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice,
  String -> Sentence
S String
"base except at a", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, String -> Sentence
S String
"edge" Sentence -> Sentence -> Sentence
+:+.
  Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpWIBE),
  String -> Sentence
S String
"Thus, in the case where", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk
height UnitalChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` ConceptChunk
waterTable),
  String -> Sentence
S String
"is above", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk
height UnitalChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` ConceptChunk
slpSrf) Sentence -> Sentence -> Sentence
`sC`
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
baseHydroForce), String -> Sentence
S String
"are defined as"]
bsWtrFDerivEndSentence :: [Sentence]
bsWtrFDerivEndSentence = [[Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"This", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
equation Sentence -> Sentence -> Sentence
`S.is`
  String -> Sentence
S String
"the non-zero case of" Sentence -> Sentence -> Sentence
+:+. GenDefn -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS GenDefn
baseWtrFGD,
  String -> Sentence
S String
"The zero case is when", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk
height UnitalChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` ConceptChunk
waterTable),
  String -> Sentence
S String
"is below", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk
height UnitalChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` ConceptChunk
slpSrf) Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"so there is no",
  String -> Sentence
S String
"hydrostatic", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
force]]
bsWtrFDerivWeightEqn :: PExpr
bsWtrFDerivWeightEqn = UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
pressure r -> r -> r
forall r. ExprC r => r -> r -> r
$= UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
specWeight r -> r -> r
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
height
bsWtrFDerivHeightEqn :: PExpr
bsWtrFDerivHeightEqn = r
PExpr
oneHalf r -> r -> r
forall r. ExprC r => r -> r -> r
$* ((UncertQ -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
waterHght r -> r -> r
forall r. ExprC r => r -> r -> r
$- UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
slipHght) r -> r -> r
forall r. ExprC r => r -> r -> r
$+ (UncertQ -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
waterHght r -> r -> r
forall r. ExprC r => r -> r -> r
$- UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UnitalChunk
slipHght))
bsWtrFDerivSliceEqn :: PExpr
bsWtrFDerivSliceEqn = UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseHydroForce r -> r -> r
forall r. ExprC r => r -> r -> r
$= UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
baseLngth r -> r -> r
forall r. ExprC r => r -> r -> r
$* UncertQ -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
waterWeight r -> r -> r
forall r. ExprC r => r -> r -> r
$* 
  r
PExpr
bsWtrFDerivHeightEqn
srfWtrF :: RelationConcept
srfWtrF :: RelationConcept
srfWtrF = String -> NP -> Sentence -> Relation -> RelationConcept
forall e.
Express e =>
String -> NP -> Sentence -> e -> RelationConcept
makeRC String
"srfWtrF" (String -> NP
nounPhraseSP String
"surface hydrostatic force")
  Sentence
srfWtrFNotes Relation
srfWtrFEqn
srfWtrFEqn :: Relation
srfWtrFEqn :: Relation
srfWtrFEqn = UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
surfHydroForce Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$= UnitalChunk -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
surfLngth Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* UncertQ -> Relation
forall c. (HasUID c, HasSymbol c) => c -> Relation
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
waterWeight Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* Relation
PExpr
oneHalf Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$* 
  [(Relation, Relation)] -> Relation
forall r. ExprC r => [(r, r)] -> r
completeCase [(Relation, Relation)
case1, (Relation, Relation)
case2]
  where case1 :: (Relation, Relation)
case1 = ((UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
waterHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$- UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
slopeHght) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$+
          (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
waterHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$- UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
slopeHght),
          (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
waterHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$> UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
slopeHght) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$||
          (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
waterHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$> UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
slopeHght))
        case2 :: (Relation, Relation)
case2 = (Integer -> Relation
forall r. LiteralC r => Integer -> r
exactDbl Integer
0, (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
waterHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$<= UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
slopeHght) Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$&&
          (UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
waterHght Relation -> Relation -> Relation
forall r. ExprC r => r -> r -> r
$<= UncertQ -> Relation
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
slopeHght))
srfWtrFNotes :: Sentence
srfWtrFNotes :: Sentence
srfWtrFNotes = [Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"This", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
equation, String -> Sentence
S String
"is based on the",
  CI -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase CI
assumption, String -> Sentence
S String
"that the surface of a", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice,
  String -> Sentence
S String
"is a straight line" Sentence -> Sentence -> Sentence
+:+. Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpSBSBISL), 
  UnitalChunk
surfLngth UnitalChunk -> DataDefinition -> Sentence
forall q r.
(HasSymbol q, HasUID q, Referable r, HasShortName r) =>
q -> r -> Sentence
`definedIn'''` DataDefinition
lengthLs]
srfWtrFDeriv :: Derivation
srfWtrFDeriv :: Derivation
srfWtrFDeriv = [Sentence] -> Derivation
mkDerivNoHeader ([[Sentence]] -> [Sentence]
forall a. [[a]] -> [a]
weave [[Sentence]
srfWtrFDerivSentences, [Sentence]
srfWtrFDerivEqns] [Sentence] -> [Sentence] -> [Sentence]
forall a. [a] -> [a] -> [a]
++
  [Sentence]
srfWtrFDerivEndSentence)
srfWtrFDerivEqns :: [Sentence]
srfWtrFDerivEqns :: [Sentence]
srfWtrFDerivEqns = (ModelExpr -> Sentence) -> [ModelExpr] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map ModelExpr -> Sentence
eS [ModelExpr
PExpr
srfWtrFDerivWeightEqn, ModelExpr
PExpr
srfWtrFDerivHeightEqn,
  ModelExpr
PExpr
srfWtrFDerivSliceEqn]
srfWtrFDerivSentences :: [Sentence]
srfWtrFDerivSentences :: [Sentence]
srfWtrFDerivSentences = ([Sentence] -> Sentence) -> [[Sentence]] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map [Sentence] -> Sentence
foldlSentCol [[Sentence]
srfWtrFDerivIntroSentence,
  [Sentence]
srfWtrFDerivHeightSentence, [Sentence]
srfWtrFDeriv2DSentence]
srfWtrFDerivIntroSentence, srfWtrFDerivHeightSentence, srfWtrFDeriv2DSentence,
  srfWtrFDerivEndSentence :: [Sentence]
srfWtrFDerivWeightEqn, srfWtrFDerivHeightEqn, srfWtrFDerivSliceEqn :: PExpr
srfWtrFDerivIntroSentence :: [Sentence]
srfWtrFDerivIntroSentence = [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
surfHydroForce), String -> Sentence
S String
"come from the",
  String -> Sentence
S String
"hydrostatic", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
pressure, String -> Sentence
S String
"exerted by the water above the surface",
  String -> Sentence
S String
"of each" Sentence -> Sentence -> Sentence
+:+. IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice,
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
equation), String -> Sentence
S String
"for hydrostatic", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
pressure, String -> Sentence
S String
"from",
  GenDefn -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS GenDefn
hsPressureGD, String -> Sentence
S String
"is"]
srfWtrFDerivHeightSentence :: [Sentence]
srfWtrFDerivHeightSentence = [NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
specWeight), String -> Sentence
S String
"in this case is",
  String -> Sentence
S String
"the" Sentence -> Sentence -> Sentence
+:+. UncertQ -> Sentence
forall a. Quantity a => a -> Sentence
getTandS UncertQ
waterWeight,
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
height), String -> Sentence
S String
"in this case" Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"the height from", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
slice),
  String -> Sentence
S String
"surface to the" Sentence -> Sentence -> Sentence
+:+. ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
waterTable,
  String -> Sentence
S String
"This", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
height Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"measured from", String -> Sentence
S String
"midpoint" Sentence -> Sentence -> Sentence
`S.the_ofThe`
  IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, String -> Sentence
S String
"because the resultant hydrostatic", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
force,
  String -> Sentence
S String
"is assumed to act at", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
slice), String -> Sentence
S String
"midpoint" Sentence -> Sentence -> Sentence
+:+.
  Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpHFSM),
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
atStartNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
height), String -> Sentence
S String
"at the midpoint" Sentence -> Sentence -> Sentence
`S.is` String -> Sentence
S String
"the average" Sentence -> Sentence -> Sentence
`S.ofThe`
  UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
height, String -> Sentence
S String
"at", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, String -> Sentence
S String
"interface", DefinedQuantityDict -> Sentence
forall c. (HasUID c, HasSymbol c) => c -> Sentence
ch DefinedQuantityDict
index Sentence -> Sentence -> Sentence
`S.andThe`
  UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
height, String -> Sentence
S String
"at", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, String -> Sentence
S String
"interface", ModelExpr -> Sentence
eS (DefinedQuantityDict -> ModelExpr
forall c. (HasUID c, HasSymbol c) => c -> ModelExpr
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy DefinedQuantityDict
index ModelExpr -> ModelExpr -> ModelExpr
forall r. ExprC r => r -> r -> r
$- Integer -> ModelExpr
forall r. LiteralC r => Integer -> r
int Integer
1)]
srfWtrFDeriv2DSentence :: [Sentence]
srfWtrFDeriv2DSentence = [String -> Sentence
S String
"Due to", ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpPSC Sentence -> Sentence -> Sentence
`sC`
  String -> Sentence
S String
"only two dimensions" Sentence -> Sentence -> Sentence
`S.are` String -> Sentence
S String
"considered" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"so", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
surfHydroForce),
  String -> Sentence
S String
"are expressed as", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural UnitalChunk
force Sentence -> Sentence -> Sentence
+:+. String -> Sentence
S String
"per meter", String -> Sentence
S String
"The",
  UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
plural UnitalChunk
pressure, String -> Sentence
S String
"acting on", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
pluralNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
slice), String -> Sentence
S String
"can thus be converted",
  String -> Sentence
S String
"to", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
surfHydroForce, String -> Sentence
S String
"by multiplying by the corresponding",
  ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
len Sentence -> Sentence -> Sentence
`S.of_` NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (IdeaDict -> NP
forall t. NamedIdea t => t -> NP
the IdeaDict
slice), String -> Sentence
S String
"surface", ModelExpr -> Sentence
eS (UnitalChunk -> ModelExpr
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
surfLngth) Sentence -> Sentence -> Sentence
`sC`
  String -> Sentence
S String
"assuming", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (ConceptChunk -> NP
forall t. NamedIdea t => t -> NP
the ConceptChunk
waterTable), String -> Sentence
S String
"does not intersect a", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice,
  String -> Sentence
S String
"surface except at a", IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
slice, String -> Sentence
S String
"edge" Sentence -> Sentence -> Sentence
+:+.
  Sentence -> Sentence
sParen (ConceptInstance -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS ConceptInstance
assumpWISE),
  String -> Sentence
S String
"Thus, in the case where", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk
height UnitalChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` ConceptChunk
waterTable),
  String -> Sentence
S String
"is above", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk
height UnitalChunk -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` IdeaDict
slopeSrf) Sentence -> Sentence -> Sentence
`sC`
  NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk -> NP
forall t. NamedIdea t => t -> NP
the UnitalChunk
surfHydroForce), String -> Sentence
S String
"are defined as"]
srfWtrFDerivEndSentence :: [Sentence]
srfWtrFDerivEndSentence = [[Sentence] -> Sentence
foldlSent [String -> Sentence
S String
"This" Sentence -> Sentence -> Sentence
+:+ ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
equation Sentence -> Sentence -> Sentence
`S.is`
  String -> Sentence
S String
"the non-zero case of" Sentence -> Sentence -> Sentence
+:+. GenDefn -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence
refS GenDefn
srfWtrFGD,
  String -> Sentence
S String
"The zero case is when", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk
height UnitalChunk -> ConceptChunk -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` ConceptChunk
waterTable),
  String -> Sentence
S String
"is below", NP -> Sentence
forall n. NounPhrase n => n -> Sentence
phraseNP (UnitalChunk
height UnitalChunk -> IdeaDict -> NP
forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP
`the_ofThe` IdeaDict
slopeSrf) Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"so there is no",
  String -> Sentence
S String
"hydrostatic", UnitalChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase UnitalChunk
force]]
srfWtrFDerivWeightEqn :: PExpr
srfWtrFDerivWeightEqn = UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
pressure r -> r -> r
forall r. ExprC r => r -> r -> r
$= UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
specWeight r -> r -> r
forall r. ExprC r => r -> r -> r
$* UnitalChunk -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UnitalChunk
height
srfWtrFDerivHeightEqn :: PExpr
srfWtrFDerivHeightEqn = r
PExpr
oneHalf r -> r -> r
forall r. ExprC r => r -> r -> r
$* ((UncertQ -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
waterHght r -> r -> r
forall r. ExprC r => r -> r -> r
$- UncertQ -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UncertQ
slopeHght) r -> r -> r
forall r. ExprC r => r -> r -> r
$+ (UncertQ -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
waterHght r -> r -> r
forall r. ExprC r => r -> r -> r
$- UncertQ -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxiM1 UncertQ
slopeHght))
srfWtrFDerivSliceEqn :: PExpr
srfWtrFDerivSliceEqn = UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
surfHydroForce r -> r -> r
forall r. ExprC r => r -> r -> r
$= UnitalChunk -> r
forall r e. (ExprC r, LiteralC r, Quantity e) => e -> r
inxi UnitalChunk
surfLngth r -> r -> r
forall r. ExprC r => r -> r -> r
$* UncertQ -> r
forall c. (HasUID c, HasSymbol c) => c -> r
forall r c. (ExprC r, HasUID c, HasSymbol c) => c -> r
sy UncertQ
waterWeight r -> r -> r
forall r. ExprC r => r -> r -> r
$* 
  r
PExpr
srfWtrFDerivHeightEqn