Skip to content

Commit

Permalink
Merge pull request #3812 from JacquesCarette/mergeAddMul
Browse files Browse the repository at this point in the history
Merged AddRe, MulRe, AddI and MulI into Add and Mul
  • Loading branch information
JacquesCarette authored Jun 20, 2024
2 parents e0a0658 + 3d1c042 commit 45fb986
Show file tree
Hide file tree
Showing 62 changed files with 820 additions and 890 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -72,11 +72,11 @@ scipyCall info = externalLibCall [
(returnExprListFill $ odeSyst info)],
uncurry choiceStepFill (chooseMethod $ solveMethod $ odeOpts info),
mandatoryStepsFill [callStepFill $ libCallFill $ map basicArgFill
[matrix[initVal info], tInit info],
initSolListWithValFill (depVar info) (matrix[initVal info]),
[matrix [initVal info], tInit info],
initSolListWithValFill (depVar info) (matrix [initVal info]),
solveAndPopulateWhileFill (libCallFill []) (tFinal info)
(libCallFill [basicArgFill (addI (field r t) (stepSize (odeOpts info)))])
(depVar info)]]
(libCallFill [basicArgFill (field r t $+ stepSize (odeOpts info))])
(depVar info)]]
where chooseMethod Adams = (0, solveMethodFill)
chooseMethod BDF = (1, solveMethodFill)
chooseMethod RK45 = (2, solveMethodFill)
Expand Down Expand Up @@ -182,7 +182,7 @@ oslo = externalLib [

osloCall :: ODEInfo -> ExternalLibraryCall
osloCall info = externalLibCall [
mandatoryStepFill $ callStepFill $ libCallFill [basicArgFill $ matrix[initVal info]],
mandatoryStepFill $ callStepFill $ libCallFill [basicArgFill $ matrix [initVal info]],
choiceStepFill (chooseMethod $ solveMethod $ odeOpts info) $ callStepFill $
libCallFill [basicArgFill $ tInit info,
functionArgFill (map unnamedParamFill [indepVar info, vecDepVar info]) $
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -199,7 +199,7 @@ getConstantsCls chs cs = cnCls (constStructure $ dataInfo chs) (inputStructure $
where cnCls (Store Bundled) _ = zipCs Constants
cnCls WithInputs Bundled = zipCs InputParameters
cnCls _ _ = []
zipCs ic = zip (map codeName cs) $ repeat (icNames chs ic)
zipCs ic = map ((, icNames chs ic) . codeName) cs

-- | Get derived input functions (for @derived_values@).
-- If there are no derived inputs, a derived inputs function is not generated.
Expand Down
10 changes: 4 additions & 6 deletions code/drasil-code/lib/Language/Drasil/Code/Imperative/Import.hs
Original file line number Diff line number Diff line change
Expand Up @@ -292,12 +292,10 @@ convExpr (Lit (Perc a b)) = do
getLiteral Float = litFloat . realToFrac
getLiteral _ = error "convExpr: Rational space matched to invalid CodeType; should be Double or Float"
return $ getLiteral sm (fromIntegral a / (10 ** fromIntegral b))
convExpr (AssocA AddI l) = foldl1 (#+) <$> mapM convExpr l
convExpr (AssocA AddRe l) = foldl1 (#+) <$> mapM convExpr l
convExpr (AssocA MulI l) = foldl1 (#*) <$> mapM convExpr l
convExpr (AssocA MulRe l) = foldl1 (#*) <$> mapM convExpr l
convExpr (AssocB And l) = foldl1 (?&&) <$> mapM convExpr l
convExpr (AssocB Or l) = foldl1 (?||) <$> mapM convExpr l
convExpr (AssocA Add l) = foldl1 (#+) <$> mapM convExpr l
convExpr (AssocA Mul l) = foldl1 (#*) <$> mapM convExpr l
convExpr (AssocB And l) = foldl1 (?&&) <$> mapM convExpr l
convExpr (AssocB Or l) = foldl1 (?||) <$> mapM convExpr l
convExpr (C c) = do
g <- get
let v = quantvar (lookupC g c)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ import qualified Data.Drasil.Quantities.PhysicalProperties as QPP (density,

-- * Weight equation derivation
weightDerivAccelEqn, weightDerivNewtonEqn, weightDerivReplaceMassEqn, weightDerivSpecWeightEqn :: ModelExpr
weightDerivNewtonEqn = sy QP.weight $= mulRe (sy QPP.mass) (sy QP.gravitationalAccel)
weightDerivReplaceMassEqn = sy QP.weight $= mulRe (sy QPP.density) (sy QPP.vol `mulRe` sy QP.gravitationalAccel)
weightDerivSpecWeightEqn = sy QP.weight $= mulRe (sy QPP.vol) (sy QPP.specWeight)
weightDerivAccelEqn = sy QP.acceleration $= vec2D (exactDbl 0) (sy QP.gravitationalAccel `mulRe` sy QM.unitVectj)
weightDerivNewtonEqn = sy QP.weight $= sy QPP.mass $* sy QP.gravitationalAccel
weightDerivReplaceMassEqn = sy QP.weight $= sy QPP.density $* sy QPP.vol $* sy QP.gravitationalAccel
weightDerivSpecWeightEqn = sy QP.weight $= sy QPP.vol $* sy QPP.specWeight
weightDerivAccelEqn = sy QP.acceleration $= vec2D (exactDbl 0) (sy QP.gravitationalAccel $* sy QM.unitVectj)
Original file line number Diff line number Diff line change
Expand Up @@ -13,9 +13,9 @@ import Data.Drasil.Concepts.Documentation (body, constant)
-- * Equations

weightEqn, newtonSLEqn, hsPressureEqn, speedEqn :: ExprC r => r
newtonSLEqn = sy QPP.mass `mulRe` sy QP.acceleration
weightEqn = sy QPP.vol `mulRe` sy QPP.specWeight
hsPressureEqn = sy QPP.specWeight `mulRe` sy QP.height
newtonSLEqn = sy QPP.mass $* sy QP.acceleration
weightEqn = sy QPP.vol $* sy QPP.specWeight
hsPressureEqn = sy QPP.specWeight $* sy QP.height
speedEqn = norm (sy QP.velocity)

velocityEqn, accelerationEqn :: ModelExpr
Expand Down
2 changes: 1 addition & 1 deletion code/drasil-data/lib/Data/Drasil/Theories/Physics.hs
Original file line number Diff line number Diff line change
Expand Up @@ -131,7 +131,7 @@ newtonSLRQD :: ModelQDef
newtonSLRQD = mkQuantDef' QP.torque (nounPhraseSP "Newton's second law for rotational motion") newtonSLRExpr

newtonSLRExpr :: ExprC r => r
newtonSLRExpr = sy QP.momentOfInertia `mulRe` sy QP.angularAccel
newtonSLRExpr = sy QP.momentOfInertia $* sy QP.angularAccel

newtonSLRNotes :: [Sentence]
newtonSLRNotes = [foldlSent
Expand Down
8 changes: 4 additions & 4 deletions code/drasil-example/dblpend/lib/Drasil/DblPend/DataDefs.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ positionXQD_1 :: SimpleQDef
positionXQD_1 = mkQuantDef xPos_1 positionXEqn_1

positionXEqn_1 :: PExpr
positionXEqn_1 = sy lenRod_1 `mulRe` sin (sy pendDisAngle_1)
positionXEqn_1 = sy lenRod_1 $* sin (sy pendDisAngle_1)

positionXFigRef_1 :: Sentence
positionXFigRef_1 = ch xPos_1 `S.is` S "shown in" +:+. refS figMotion
Expand All @@ -55,7 +55,7 @@ positionYQD_1 :: SimpleQDef
positionYQD_1 = mkQuantDef yPos_1 positionYEqn_1

positionYEqn_1 :: PExpr
positionYEqn_1 = neg (sy lenRod_1 `mulRe` cos (sy pendDisAngle_1))
positionYEqn_1 = neg (sy lenRod_1 $* cos (sy pendDisAngle_1))

positionYFigRef_1 :: Sentence
positionYFigRef_1 = ch yPos_1 `S.is` S "shown in" +:+. refS figMotion
Expand All @@ -73,7 +73,7 @@ positionXQD_2 :: SimpleQDef
positionXQD_2 = mkQuantDef xPos_2 positionXEqn_2

positionXEqn_2 :: PExpr
positionXEqn_2 = sy (positionXDD_1 ^. defLhs) `addRe` (sy lenRod_2 `mulRe` sin (sy pendDisAngle_2))
positionXEqn_2 = sy (positionXDD_1 ^. defLhs) $+ (sy lenRod_2 $* sin (sy pendDisAngle_2))

positionXFigRef_2 :: Sentence
positionXFigRef_2 = ch xPos_2 `S.is` S "shown in" +:+. refS figMotion
Expand All @@ -91,7 +91,7 @@ positionYQD_2 :: SimpleQDef
positionYQD_2 = mkQuantDef yPos_2 positionYEqn_2

positionYEqn_2 :: PExpr
positionYEqn_2 = sy (positionYDD_1 ^. defLhs) `addRe` neg (sy lenRod_2 `mulRe` cos (sy pendDisAngle_2))
positionYEqn_2 = sy (positionYDD_1 ^. defLhs) $+ neg (sy lenRod_2 $* cos (sy pendDisAngle_2))

positionYFigRef_2 :: Sentence
positionYFigRef_2 = ch yPos_2 `S.is` S "shown in" +:+. refS figMotion
Expand Down
68 changes: 34 additions & 34 deletions code/drasil-example/dblpend/lib/Drasil/DblPend/Derivations.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,12 +19,12 @@ velDerivEqn1, velXDerivEqn2_1, velXDerivEqn3_1, velXDerivEqn4_1 :: ModelExpr
velDerivEqn1 = sy velocity $= positionGQD ^. defnExpr
velXDerivEqn2_1 = sy xPos_1 $= positionXEqn_1
velXDerivEqn3_1 = sy xVel_1 $= deriv positionXEqn_1 time
velXDerivEqn4_1 = sy xVel_1 $= sy lenRod_1 `mulRe` deriv (sin (sy pendDisAngle_1)) time
velXDerivEqn4_1 = sy xVel_1 $= sy lenRod_1 $* deriv (sin (sy pendDisAngle_1)) time

velYDerivEqn2_1,velYDerivEqn3_1,velYDerivEqn4_1 :: ModelExpr
velYDerivEqn2_1 = sy yPos_1 $= express (positionYQD_1 ^. defnExpr)
velYDerivEqn3_1 = sy yVel_1 $= neg (deriv (sy lenRod_1 `mulRe` cos (sy pendDisAngle_1)) time)
velYDerivEqn4_1 = sy yVel_1 $= neg (sy lenRod_1 `mulRe` deriv (cos (sy pendDisAngle_1)) time)
velYDerivEqn3_1 = sy yVel_1 $= neg (deriv (sy lenRod_1 $* cos (sy pendDisAngle_1)) time)
velYDerivEqn4_1 = sy yVel_1 $= neg (sy lenRod_1 $* deriv (cos (sy pendDisAngle_1)) time)

-- Velocity X/Y Second Object
velXDerivEqn2_2, velXDerivEqn3_2 :: ModelExpr
Expand All @@ -39,14 +39,14 @@ velYDerivEqn3_2 = sy yVel_2 $= neg (deriv positionYEqn_2 time)

accelDerivEqn1, accelXDerivEqn3_1, accelXDerivEqn4_1 :: ModelExpr
accelDerivEqn1 = sy acceleration $= accelGQD ^. defnExpr
accelXDerivEqn3_1 = sy xAccel_1 $= deriv (sy angularVel_1 `mulRe` sy lenRod_1 `mulRe` cos (sy pendDisAngle_1)) time
accelXDerivEqn4_1 = sy xAccel_1 $= deriv (sy angularVel_1) time `mulRe` sy lenRod_1 `mulRe` cos (sy pendDisAngle_1)
$- (sy angularVel_1 `mulRe` sy lenRod_1 `mulRe` sin (sy pendDisAngle_1) `mulRe` deriv (sy pendDisAngle_1) time)
accelXDerivEqn3_1 = sy xAccel_1 $= deriv (sy angularVel_1 $* sy lenRod_1 $* cos (sy pendDisAngle_1)) time
accelXDerivEqn4_1 = sy xAccel_1 $= deriv (sy angularVel_1) time $* sy lenRod_1 $* cos (sy pendDisAngle_1)
$- (sy angularVel_1 $* sy lenRod_1 $* sin (sy pendDisAngle_1) $* deriv (sy pendDisAngle_1) time)

accelYDerivEqn3_1, accelYDerivEqn4_1 :: ModelExpr
accelYDerivEqn3_1 = sy yAccel_1 $= deriv (sy angularVel_1 `mulRe` sy lenRod_1 `mulRe` sin (sy pendDisAngle_1)) time
accelYDerivEqn4_1 = sy yAccel_1 $= deriv (sy angularVel_1) time `mulRe` sy lenRod_1 `mulRe` sin (sy pendDisAngle_1)
`addRe` (sy angularVel_1 `mulRe` sy lenRod_1 `mulRe` cos (sy pendDisAngle_1) `mulRe` deriv (sy pendDisAngle_1) time)
accelYDerivEqn3_1 = sy yAccel_1 $= deriv (sy angularVel_1 $* sy lenRod_1 $* sin (sy pendDisAngle_1)) time
accelYDerivEqn4_1 = sy yAccel_1 $= deriv (sy angularVel_1) time $* sy lenRod_1 $* sin (sy pendDisAngle_1)
$+ (sy angularVel_1 $* sy lenRod_1 $* cos (sy pendDisAngle_1) $* deriv (sy pendDisAngle_1) time)

-- Acceleration X/Y Second Object
accelXDerivEqn3_2 :: ModelExpr
Expand All @@ -63,32 +63,32 @@ angularAccelDerivEqns = [angularAccelDerivEqn1, angularAccelDerivEqn2, angularAc

angularAccelDerivEqn1, angularAccelDerivEqn2, angularAccelDerivEqn3, angularAccelDerivEqn4,
angularAccelDerivEqn5, angularAccelDerivEqn6, angularAccelDerivEqn7, angularAccelDerivEqn8 :: ModelExpr
angularAccelDerivEqn1 = sy massObj_1 `mulRe` sy xAccel_1 $=
neg (sy tension_1) `mulRe` sin (sy pendDisAngle_1) $- (sy massObj_2 `mulRe` sy xAccel_2)
angularAccelDerivEqn2 = sy massObj_1 `mulRe` sy yAccel_1 $=
sy tension_1 `mulRe` cos (sy pendDisAngle_1) $- (sy massObj_2 `mulRe` sy yAccel_2) $-
(sy massObj_2 `mulRe` sy gravitationalMagnitude) $- (sy massObj_1 `mulRe` sy gravitationalMagnitude)
angularAccelDerivEqn3 = sy tension_1 `mulRe` sin (sy pendDisAngle_1) `mulRe` cos (sy pendDisAngle_1) $=
neg (cos (sy pendDisAngle_1)) `mulRe`
((sy massObj_1 `mulRe` sy xAccel_1) `addRe` (sy massObj_2 `mulRe` sy xAccel_2))
angularAccelDerivEqn4 = sy tension_1 `mulRe` sin (sy pendDisAngle_1) `mulRe` cos (sy pendDisAngle_1) $=
sin (sy pendDisAngle_1) `mulRe`
angularAccelDerivEqn1 = sy massObj_1 $* sy xAccel_1 $=
neg (sy tension_1) $* sin (sy pendDisAngle_1) $- (sy massObj_2 $* sy xAccel_2)
angularAccelDerivEqn2 = sy massObj_1 $* sy yAccel_1 $=
sy tension_1 $* cos (sy pendDisAngle_1) $- (sy massObj_2 $* sy yAccel_2) $-
(sy massObj_2 $* sy gravitationalMagnitude) $- (sy massObj_1 $* sy gravitationalMagnitude)
angularAccelDerivEqn3 = sy tension_1 $* sin (sy pendDisAngle_1) $* cos (sy pendDisAngle_1) $=
neg (cos (sy pendDisAngle_1)) $*
((sy massObj_1 $* sy xAccel_1) $+ (sy massObj_2 $* sy xAccel_2))
angularAccelDerivEqn4 = sy tension_1 $* sin (sy pendDisAngle_1) $* cos (sy pendDisAngle_1) $=
sin (sy pendDisAngle_1) $*
(
(sy massObj_1 `mulRe` sy yAccel_1) `addRe` (sy massObj_2 `mulRe` sy yAccel_2) `addRe`
(sy massObj_2 `mulRe` sy gravitationalMagnitude) `addRe` (sy massObj_1 `mulRe` sy gravitationalMagnitude)
(sy massObj_1 $* sy yAccel_1) $+ (sy massObj_2 $* sy yAccel_2) $+
(sy massObj_2 $* sy gravitationalMagnitude) $+ (sy massObj_1 $* sy gravitationalMagnitude)
)
angularAccelDerivEqn5 = sin (sy pendDisAngle_1) `mulRe`
angularAccelDerivEqn5 = sin (sy pendDisAngle_1) $*
(
(sy massObj_1 `mulRe` sy yAccel_1) `addRe` (sy massObj_2 `mulRe` sy yAccel_2) `addRe`
(sy massObj_2 `mulRe` sy gravitationalMagnitude) `addRe` (sy massObj_1 `mulRe` sy gravitationalMagnitude)
(sy massObj_1 $* sy yAccel_1) $+ (sy massObj_2 $* sy yAccel_2) $+
(sy massObj_2 $* sy gravitationalMagnitude) $+ (sy massObj_1 $* sy gravitationalMagnitude)
) $=
neg (cos (sy pendDisAngle_1)) `mulRe`
((sy massObj_1 `mulRe` sy xAccel_1) `addRe` (sy massObj_2 `mulRe` sy xAccel_2))
angularAccelDerivEqn6 = sy tension_2 `mulRe` sin(sy pendDisAngle_2) `mulRe` cos (sy pendDisAngle_2) $=
neg (cos (sy pendDisAngle_2)) `mulRe` sy massObj_2 `mulRe` sy xAccel_2
angularAccelDerivEqn7 = sy tension_1 `mulRe` sin (sy pendDisAngle_2 ) `mulRe` cos (sy pendDisAngle_2) $=
sin (sy pendDisAngle_2) `mulRe`
((sy massObj_2 `mulRe` sy yAccel_2) `addRe` (sy massObj_2 `mulRe` sy gravitationalMagnitude))
angularAccelDerivEqn8 = sin (sy pendDisAngle_2) `mulRe`
((sy massObj_2 `mulRe` sy yAccel_2) `addRe` (sy massObj_2 `mulRe` sy gravitationalMagnitude)) $=
neg (cos (sy pendDisAngle_2)) `mulRe` sy massObj_2 `mulRe` sy xAccel_2
neg (cos (sy pendDisAngle_1)) $*
((sy massObj_1 $* sy xAccel_1) $+ (sy massObj_2 $* sy xAccel_2))
angularAccelDerivEqn6 = sy tension_2 $* sin(sy pendDisAngle_2) $* cos (sy pendDisAngle_2) $=
neg (cos (sy pendDisAngle_2)) $* sy massObj_2 $* sy xAccel_2
angularAccelDerivEqn7 = sy tension_1 $* sin (sy pendDisAngle_2 ) $* cos (sy pendDisAngle_2) $=
sin (sy pendDisAngle_2) $*
((sy massObj_2 $* sy yAccel_2) $+ (sy massObj_2 $* sy gravitationalMagnitude))
angularAccelDerivEqn8 = sin (sy pendDisAngle_2) $*
((sy massObj_2 $* sy yAccel_2) $+ (sy massObj_2 $* sy gravitationalMagnitude)) $=
neg (cos (sy pendDisAngle_2)) $* sy massObj_2 $* sy xAccel_2
Loading

0 comments on commit 45fb986

Please sign in to comment.