Skip to content

Commit

Permalink
SSP Surface Hydrostatic Force Derivation (#1286)
Browse files Browse the repository at this point in the history
* Added some generic concepts and quantities needed for the derivation

* Added weight DD needed for derivation

* Added the derivation

* Updated stable

* Moved references to unit weights to correct DDs

* Made first derivation equation indexed

* Moved Newton's 2nd law to drasil data so I can re-use it in SSP

* Imported the Newtons 2nd law TM in SSP

* Changed surface hydro force from DD to GD

* Changed weight DD to a GD in drasil-data

* Updated stable

* Added derivation of weight GD and added Theories file in drasil-data which I forgot to add many commits ago

* Added new assumption and used it in derivation for surfHydroForce

* Removed left and right surf hydro force DDs, combined everything in the new GD

* Fixed warning

* Added missing source to new weight GD

* Updated stable

* Updated conditions for surface hydro force equation cases

* Updated derivation of weight to explain how newton's 2nd law specializes

* Updated stable
  • Loading branch information
bmaclach authored and JacquesCarette committed May 14, 2019
1 parent 27acedc commit ce28891
Show file tree
Hide file tree
Showing 20 changed files with 1,345 additions and 1,156 deletions.
27 changes: 14 additions & 13 deletions code/drasil-data/Data/Drasil/Concepts/PhysicalProperties.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,27 +5,28 @@ import Data.Drasil.Concepts.Documentation (material_, property)
import Data.Drasil.Phrase (compoundNC)

physicalcon :: [ConceptChunk]
physicalcon = [gaseous, liquid, solid, ctrOfMass, density, mass, len, dimension,
vol, flexure]
physicalcon = [gaseous, liquid, solid, ctrOfMass, density, specWeight, mass,
len, dimension, vol, flexure]

gaseous, liquid, solid, ctrOfMass, density, mass, len, dimension,
gaseous, liquid, solid, ctrOfMass, density, specWeight, mass, len, dimension,
vol, flexure :: ConceptChunk

gaseous = dcc "gaseous" (cn''' "gas" ) "gaseous state"
liquid = dcc "liquid" (cn' "liquid" ) "liquid state"
solid = dcc "solid" (cn' "solid" ) "solid state"
ctrOfMass = dcc "ctrOfMass" (cn "centre of mass") --FIXME: Plural?
gaseous = dcc "gaseous" (cn''' "gas" ) "gaseous state"
liquid = dcc "liquid" (cn' "liquid" ) "liquid state"
solid = dcc "solid" (cn' "solid" ) "solid state"
ctrOfMass = dcc "ctrOfMass" (cn "centre of mass" ) --FIXME: Plural?
"The mean location of the distribution of mass of the object."
dimension = dcc "dimension" (cn' "dimension" )
dimension = dcc "dimension" (cn' "dimension" )
"any of a set of basic kinds of quantity, as mass, length, and time"
density = dcc "density" (cnIES "density" ) "mass per unit volume"
flexure = dcc "flexure" (cn' "flexure" ) "a bent or curved part"
len = dcc "length" (cn' "length" )
density = dcc "density" (cnIES "density" ) "mass per unit volume"
specWeight = dcc "specWeight" (cn' "specific weight") "weight per unit volume"
flexure = dcc "flexure" (cn' "flexure" ) "a bent or curved part"
len = dcc "length" (cn' "length" )
("the straight-line distance between two points along an object. " ++
"typically used to represent the size of an object from one end to the other.")
mass = dcc "mass" (cn''' "mass" )
mass = dcc "mass" (cn''' "mass" )
"the quantity of matter in a body"
vol = dcc "volume" (cn' "volume" )
vol = dcc "volume" (cn' "volume" )
"the amount of space that a substance or object occupies."


Expand Down
13 changes: 8 additions & 5 deletions code/drasil-data/Data/Drasil/Concepts/Physics.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,9 +3,9 @@ module Data.Drasil.Concepts.Physics
, cartesian, rightHand, restitutionCoef, acceleration, pressure
, momentOfInertia, force, impulseS, impulseV, displacement
, gravitationalAccel, gravitationalConst, position, distance
, time, torque, fbd, angular, linear, tension, compression, stress, strain
, angDisp, angVelo, angAccel, linDisp, linVelo, linAccel, joint, damping
, cohesion, isotropy, twoD, threeD, physicCon, physicCon', kEnergy
, time, torque, weight, fbd, angular, linear, tension, compression, stress
, strain , angDisp, angVelo, angAccel, linDisp, linVelo, linAccel, joint
, damping , cohesion, isotropy, twoD, threeD, physicCon, physicCon', kEnergy
) where
--This is obviously a bad name, but for now it will do until we come
-- up with a better one.
Expand All @@ -20,7 +20,7 @@ physicCon = [rigidBody, velocity, friction, elasticity, energy, mechEnergy, coll
cartesian, rightHand, restitutionCoef, acceleration,
momentOfInertia, force, impulseS, impulseV, displacement,
gravitationalAccel, gravitationalConst, position, distance,
time, torque, fbd, linear, angular, tension, compression, stress,
time, torque, weight, fbd, linear, angular, tension, compression, stress,
strain, angDisp, angVelo, angAccel, linDisp, linVelo, linAccel,
joint, damping, pressure, cohesion, isotropy, kEnergy]

Expand All @@ -32,7 +32,7 @@ rigidBody, velocity, friction, elasticity, energy, mechEnergy, collision, space,
cartesian, rightHand, restitutionCoef, acceleration,
momentOfInertia, force, impulseS, impulseV, displacement,
gravitationalAccel, gravitationalConst, position, distance,
time, torque, fbd, linear, angular, tension, compression, stress,
time, torque, weight, fbd, linear, angular, tension, compression, stress,
strain, angDisp, angVelo, angAccel, linDisp, linVelo, linAccel,
joint, damping, pressure,cohesion, isotropy, kEnergy :: ConceptChunk

Expand Down Expand Up @@ -138,6 +138,9 @@ time = dcc "time" (cn' "time")
torque = dcc "torque" (cn' "torque")
"A twisting force that tends to cause rotation"

weight = dcc "weight" (cn' "weight")
"The gravitational force acting on an object"

fbd = dcc "FBD" (cn' "free body diagram")
"A graphical illustration used to visualize the applied forces, movements, and resulting reactions on a body in a steady state condition"

Expand Down
4 changes: 3 additions & 1 deletion code/drasil-data/Data/Drasil/Quantities/Math.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,12 +7,14 @@ import Data.Drasil.Concepts.Math as CM (area, diameter, euclidN, gradient,
normalV, orient, perpV, pi_, surArea, surface, unitV)
import Data.Drasil.SI_Units (metre, m_2, radian)

gradient, normalVect, unitVect, euclidNorm, perpVect, pi_, uNormalVect :: DefinedQuantityDict
gradient, normalVect, unitVect, unitVectj, euclidNorm, perpVect, pi_,
uNormalVect :: DefinedQuantityDict

gradient = dqd' CM.gradient (const $ lNabla) Real Nothing
normalVect = dqd' CM.normalV (const $ vec $ lN) Real Nothing
uNormalVect = dqd' CM.normalV (const $ vec $ hat lN) Real Nothing
unitVect = dqd' CM.unitV (const $ vec $ hat lI) Real Nothing
unitVectj = dqd' CM.unitV (const $ vec $ hat lJ) Real Nothing
perpVect = dqd' CM.perpV (const $ vec $ lN) Real Nothing
pi_ = dqd' CM.pi_ (const $ lPi) Real Nothing
euclidNorm = dqd' CM.euclidN (const $ Concat [Atomic "||", (vec lR), Atomic "||"])
Expand Down
18 changes: 10 additions & 8 deletions code/drasil-data/Data/Drasil/Quantities/PhysicalProperties.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,16 @@
module Data.Drasil.Quantities.PhysicalProperties where

import Language.Drasil
import Language.Drasil.ShortHands (lM, cL, cV, lRho)
import Language.Drasil.ShortHands (lM, cL, cV, lGamma, lRho)

import Data.Drasil.Concepts.PhysicalProperties as CPP (density, len, mass, vol)
import Data.Drasil.SI_Units (kilogram, metre, m_3)
import Data.Drasil.Concepts.PhysicalProperties as CPP (density, specWeight, len,
mass, vol)
import Data.Drasil.SI_Units (kilogram, metre, m_3, specificWeight)
import Data.Drasil.Units.PhysicalProperties (densityU)

density, mass, len, vol :: UnitalChunk
density = uc CPP.density lRho densityU
mass = uc CPP.mass lM kilogram
len = uc CPP.len cL metre
vol = uc CPP.vol cV m_3
density, specWeight, mass, len, vol :: UnitalChunk
density = uc CPP.density lRho densityU
specWeight = uc CPP.specWeight lGamma specificWeight
mass = uc CPP.mass lM kilogram
len = uc CPP.len cL metre
vol = uc CPP.vol cV m_3
7 changes: 4 additions & 3 deletions code/drasil-data/Data/Drasil/Quantities/Physics.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ import Language.Drasil.ShortHands
import qualified Data.Drasil.Concepts.Physics as CP (angAccel, angDisp, angVelo,
acceleration, displacement, distance, energy, force, gravitationalAccel,
gravitationalConst, impulseS, impulseV, linAccel, linDisp, linVelo,
momentOfInertia, position, pressure, restitutionCoef, time, torque, velocity, kEnergy)
momentOfInertia, position, pressure, restitutionCoef, time, torque, velocity, weight, kEnergy)
import Data.Drasil.SI_Units (joule, metre, newton, pascal, radian, second)
import Data.Drasil.Units.Physics (accelU, angAccelU, angVelU, gravConstU,
impulseU, momtInertU, torqueU, velU)
Expand All @@ -17,12 +17,12 @@ physicscon :: [UnitalChunk]
physicscon = [angularAccel, angularDisplacement, angularVelocity, acceleration, displacement,
distance, energy, force, gravitationalAccel, gravitationalConst, impulseS,
impulseV, linearAccel, linearDisplacement, linearVelocity, momentOfInertia,
position, pressure, time, torque, velocity, kEnergy]
position, pressure, time, torque, velocity, weight, kEnergy]

angularAccel, angularDisplacement, angularVelocity, acceleration, displacement,
distance, energy, force, gravitationalAccel, gravitationalConst, impulseS,
impulseV, linearAccel, linearDisplacement, linearVelocity, momentOfInertia,
position, pressure, time, torque, velocity, kEnergy :: UnitalChunk
position, pressure, time, torque, velocity, weight, kEnergy :: UnitalChunk

angularAccel = uc CP.angAccel lAlpha angAccelU
angularDisplacement = uc CP.angDisp lTheta radian
Expand All @@ -46,3 +46,4 @@ pressure = uc CP.pressure lP pascal
time = uc CP.time lT second
torque = uc CP.torque lTau torqueU
velocity = uc CP.velocity (vec lV) velU
weight = uc CP.weight cW newton
102 changes: 102 additions & 0 deletions code/drasil-data/Data/Drasil/Theories/Physics.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,102 @@
module Data.Drasil.Theories.Physics where

import Language.Drasil
import Theory.Drasil (GenDefn, gd)
import Data.Drasil.Utils (weave)
import Data.Drasil.SentenceStructures (foldlSent, foldlSentCol, ofThe, sAnd,
sOf)
import Data.Drasil.Concepts.Documentation (body, component, constant, value)
import Data.Drasil.Concepts.Math (vector)
import Data.Drasil.Concepts.Physics (cartesian, twoD)
import qualified Data.Drasil.Quantities.Math as QM (unitVectj)
import qualified Data.Drasil.Quantities.PhysicalProperties as QPP (density,
mass, specWeight, vol)
import qualified Data.Drasil.Quantities.Physics as QP (acceleration, force,
gravitationalAccel, weight)

physicsTMs :: [TheoryModel]
physicsTMs = [newtonSL]

newtonSL :: TheoryModel
newtonSL = tmNoRefs (cw newtonSLRC)
[qw QP.force, qw QPP.mass, qw QP.acceleration] ([] :: [ConceptChunk])
[] [(sy QP.force) $= (sy QPP.mass) * (sy QP.acceleration)] []
"NewtonSecLawMot" [newtonSLDesc]

newtonSLRC :: RelationConcept
newtonSLRC = makeRC "newtonSL" (nounPhraseSP "Newton's second law of motion")
newtonSLDesc newtonSLRel

newtonSLRel :: Relation
newtonSLRel = (sy QP.force) $= (sy QPP.mass) * (sy QP.acceleration)

newtonSLDesc :: Sentence
newtonSLDesc = foldlSent [S "The net", (phrase QP.force), (ch QP.force),
(sParen $ Sy $ unit_symb QP.force), S "on a", phrase body,
S "is proportional to the", (phrase QP.acceleration),
(ch QP.acceleration), (sParen $ Sy $ unit_symb QP.acceleration),
S "of the", phrase body `sC` S "where", (ch QPP.mass),
(sParen $ Sy $ unit_symb QPP.mass), S "denotes", (phrase QPP.mass) `ofThe`
phrase body, S "as the", phrase constant `sOf` S "proportionality"]

--

weightGD :: GenDefn
weightGD = gd weightRC (getUnit QP.weight) weightDeriv [weightSrc]
"weight" [{-Notes-}]

weightRC :: RelationConcept
weightRC = makeRC "weight" (nounPhraseSP "weight") EmptyS weightEqn

weightEqn :: Relation
weightEqn = sy QP.weight $= sy QPP.vol * sy QPP.specWeight

weightSrc :: Reference
weightSrc = makeURI "weightSrc" "https://en.wikipedia.org/wiki/Weight" $
shortname' "Definition of Weight"

weightDeriv :: Derivation
weightDeriv = weave [weightDerivSentences, weightDerivEqns]

weightDerivSentences, weightDerivEqns :: [Sentence]
weightDerivSentences = map foldlSentCol [weightDerivAccelSentence,
weightDerivNewtonSentence, weightDerivReplaceMassSentence,
weightDerivSpecWeightSentence]
weightDerivEqns = map E [weightDerivAccelEqn, weightDerivNewtonEqn,
weightDerivReplaceMassEqn, weightDerivSpecWeightEqn]

weightDerivAccelSentence :: [Sentence]
weightDerivAccelSentence = [S "Under the influence of gravity" `sC`
S "and assuming a", short twoD, phrase cartesian,
S "with down as positive" `sC` S "an object has an", phrase QP.acceleration,
phrase vector, S "of"]

weightDerivNewtonSentence :: [Sentence]
weightDerivNewtonSentence = [S "Since there is only one non-zero",
phrase vector, phrase component `sC` S "the scalar", phrase value,
ch QP.weight, S "will be used for the" +:+. phrase QP.weight,
S "In this scenario" `sC` phrase newtonSL, S "from", makeRef2S newtonSL,
S "can be expressed as"]

weightDerivReplaceMassSentence :: [Sentence]
weightDerivReplaceMassSentence = [at_start QPP.mass, S "can be expressed as",
phrase QPP.density, S "multiplied by", phrase QPP.vol `sC` S "resulting in"]

weightDerivSpecWeightSentence :: [Sentence]
weightDerivSpecWeightSentence = [S "Substituting", phrase QPP.specWeight,
S "as the product of", phrase QPP.density `sAnd` phrase QP.gravitationalAccel,
S "yields"]

weightDerivAccelEqn :: Expr
weightDerivAccelEqn = sy QP.acceleration $= vec2D 0 (sy QP.gravitationalAccel *
sy QM.unitVectj)

weightDerivNewtonEqn :: Expr
weightDerivNewtonEqn = sy QP.weight $= sy QPP.mass * sy QP.gravitationalAccel

weightDerivReplaceMassEqn :: Expr
weightDerivReplaceMassEqn = sy QP.weight $= sy QPP.density * sy QPP.vol * sy QP.gravitationalAccel

weightDerivSpecWeightEqn :: Expr
weightDerivSpecWeightEqn = sy QP.weight $= sy QPP.vol * sy QPP.specWeight

4 changes: 3 additions & 1 deletion code/drasil-data/drasil-data.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,7 @@ library
Data.Drasil.Units.PhysicalProperties
Data.Drasil.Units.Physics
Data.Drasil.Units.SolidMechanics
Data.Drasil.Theories.Physics

Build-Depends:
base >= 4.7,
Expand All @@ -46,7 +47,8 @@ library
parsec >= 3.1.9,
data-fix (>= 0.0.4 && <= 1.0),
Decimal >= 0.5.1,
drasil-lang >= 0.1.56
drasil-lang >= 0.1.56,
drasil-theory >= 0.1.0
default-language: Haskell2010
ghc-options: -Wall -Wredundant-constraints

Expand Down
6 changes: 2 additions & 4 deletions code/drasil-example/Drasil/GamePhysics/Body.hs
Original file line number Diff line number Diff line change
Expand Up @@ -63,8 +63,7 @@ import Drasil.GamePhysics.IMods (iModelsNew, instModIntro)
import Drasil.GamePhysics.References (cpCitations, parnas1972, parnasClements1984)
import Drasil.GamePhysics.Requirements (funcReqsContent, funcReqs, nonfuncReqs,
propsDeriv, requirements)
import Drasil.GamePhysics.TMods (t1NewtonSL_new, t2NewtonTL_new,
t3NewtonLUG_new, t4ChaslesThm_new, t5NewtonSLR_new, cpTModsNew)
import Drasil.GamePhysics.TMods (cpTModsNew)
import Drasil.GamePhysics.Unitals (cpSymbolsAll, cpOutputConstraints,
inputSymbols, outputSymbols, cpInputConstraints, gamephySymbols)

Expand Down Expand Up @@ -96,8 +95,7 @@ mkSRS = [RefSec $ RefProg intro [TUnits, tsymb tableOfSymbols, TAandA],
SSDSec $ SSDProg [SSDSubVerb problemDescriptionSection
, SSDSolChSpec $ SCSProg
[ Assumptions
, TMs [] (Label : stdFields)
[t1NewtonSL_new, t2NewtonTL_new, t3NewtonLUG_new, t4ChaslesThm_new, t5NewtonSLR_new]
, TMs [] (Label : stdFields) cpTModsNew
, GDs [] [] [] HideDerivation -- No Gen Defs for Gamephysics
, DDs [] ([Label, Symbol, Units] ++ stdFields) dataDefns ShowDerivation
, IMs [instModIntro] ([Label, Input, Output, InConstraints, OutConstraints] ++ stdFields)
Expand Down
35 changes: 6 additions & 29 deletions code/drasil-example/Drasil/GamePhysics/TMods.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Drasil.GamePhysics.TMods (cpTMods, t1NewtonSL_new, t2NewtonTL_new,
module Drasil.GamePhysics.TMods (cpTMods, t2NewtonTL_new,
t3NewtonLUG_new, t4ChaslesThm_new, t5NewtonSLR_new, cpTModsNew) where

import Language.Drasil
Expand All @@ -12,45 +12,22 @@ import Drasil.GamePhysics.Unitals (dispNorm, dispUnit, force_1, force_2,
import Data.Drasil.SentenceStructures (foldlSent)
import qualified Data.Drasil.Concepts.Physics as CP (rigidBody)
import qualified Data.Drasil.Quantities.PhysicalProperties as QPP (mass)
import qualified Data.Drasil.Quantities.Physics as QP (acceleration,
angularAccel, angularVelocity, displacement, force, gravitationalConst,
import qualified Data.Drasil.Quantities.Physics as QP (angularAccel,
angularVelocity, displacement, force, gravitationalConst,
momentOfInertia, torque, velocity)
import qualified Data.Drasil.Theories.Physics as TP (newtonSL, newtonSLRC)

----- Theoretical Models -----

cpTMods :: [RelationConcept]
cpTMods = [newtonSL, newtonTL, newtonLUG, chaslesThm, newtonSLR]
cpTMods = [TP.newtonSLRC, newtonTL, newtonLUG, chaslesThm, newtonSLR]

cpTModsNew :: [TheoryModel]
cpTModsNew = [t1NewtonSL_new, t2NewtonTL_new, t3NewtonLUG_new,
cpTModsNew = [TP.newtonSL, t2NewtonTL_new, t3NewtonLUG_new,
t4ChaslesThm_new, t5NewtonSLR_new]

-- T1 : Newton's second law of motion --

t1NewtonSL_new :: TheoryModel
t1NewtonSL_new = tmNoRefs (cw newtonSL)
[qw QP.force, qw QPP.mass, qw QP.acceleration] ([] :: [ConceptChunk])
[] [(sy QP.force) $= (sy QPP.mass) * (sy QP.acceleration)] []
"NewtonSecLawMot" [newtonSLDesc]

newtonSL :: RelationConcept
newtonSL = makeRC "newtonSL" (nounPhraseSP "Newton's second law of motion")
newtonSLDesc newtonSLRel

newtonSLRel :: Relation
newtonSLRel = (sy QP.force) $= (sy QPP.mass) * (sy QP.acceleration)

newtonSLDesc :: Sentence
newtonSLDesc = foldlSent [S "The net", (phrase QP.force), (ch QP.force),
(sParen $ Sy $ unit_symb QP.force), S "on a", (phrase CP.rigidBody),
S "is proportional to the", (phrase QP.acceleration),
(ch QP.acceleration), (sParen $ Sy $ unit_symb QP.acceleration),
S "of the", (phrase CP.rigidBody) `sC`
S "where", (ch QPP.mass), (sParen $ Sy $ unit_symb QPP.mass),
S "denotes the", (phrase QPP.mass), S "of the",
(phrase $ CP.rigidBody),
S "as the constant of proportionality"]

-- T2 : Newton's third law of motion --

t2NewtonTL_new :: TheoryModel
Expand Down
15 changes: 10 additions & 5 deletions code/drasil-example/Drasil/SSP/Assumptions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ module Drasil.SSP.Assumptions where
import Language.Drasil

import Drasil.SSP.Defs (plnStrn, slpSrf, slopeSrf, slope,
soil, soilPrpty, intrslce, slice)
soil, soilPrpty, intrslce, slice, waterTable)
import Drasil.SSP.Unitals (effCohesion, fricAngle, intNormForce, intShrForce,
normToShear, numbSlices, scalFunc, shrStress, slipDist, slipHght, surfLoad,
xi, zcoord)
Expand All @@ -20,11 +20,11 @@ import Data.Drasil.Concepts.Math (surface, unit_)
assumptions :: [ConceptInstance]
assumptions = [assumpSSC, assumpFOSL, assumpSLH, assumpSP, assumpSLI,
assumpINSFL, assumpPSC, assumpENSL, assumpSBSBISL, assumpES, assumpSF,
assumpSL]
assumpSL, assumpWISE]

assumpSSC, assumpFOSL, assumpSLH, assumpSP, assumpSLI, assumpINSFL,
assumpPSC, assumpENSL, assumpSBSBISL, assumpES, assumpSF,
assumpSL :: ConceptInstance
assumpSL, assumpWISE :: ConceptInstance

assumpSSC = cic "assumpSSC" monotonicF "Slip-Surface-Concave" assumpDom
assumpFOSL = cic "assumpFOS" slopeS "Factor-of-Safety" assumpDom
Expand All @@ -38,9 +38,11 @@ assumpSBSBISL = cic "assumpSBSBISL" straightS "Surface-Base-Slice-between-Inters
assumpES = cic "assumpES" edgeS "Edge-Slices" assumpDom
assumpSF = cic "assumpSF" seismicF "Seismic-Force" assumpDom
assumpSL = cic "assumpSL" surfaceL "Surface-Load" assumpDom
assumpWISE = cic "assumpWISE" waterIntersect "Water-Intersects-Slice-Edge"
assumpDom

monotonicF, slopeS, homogeneousL, isotropicP, linearS,
planeS, largeN, straightS, propertiesS, edgeS, seismicF, surfaceL :: Sentence
monotonicF, slopeS, homogeneousL, isotropicP, linearS, planeS, largeN,
straightS, propertiesS, edgeS, seismicF, surfaceL, waterIntersect :: Sentence

monotonicF = foldlSent [S "The", phrase slpSrf,
S "is concave with respect to", S "the" +:+. phrase slopeSrf, S "The",
Expand Down Expand Up @@ -87,3 +89,6 @@ seismicF = foldlSent [S "There is no seismic", phrase force, S "acting on the",

surfaceL = foldlSent [S "There is no imposed", phrase surface, S "load" `sC`
S "and therefore no", phrase surfLoad `sC` S "acting on the", phrase slope]

waterIntersect = foldlSent [S "The", phrase waterTable, S "only intersects the",
phrase slopeSrf, S "at the edge of a", phrase slice]
Loading

0 comments on commit ce28891

Please sign in to comment.