Skip to content

Commit

Permalink
WIP making ODEs work in Julia
Browse files Browse the repository at this point in the history
  • Loading branch information
B-rando1 committed Aug 21, 2024
1 parent d16e874 commit c024497
Show file tree
Hide file tree
Showing 47 changed files with 895 additions and 286 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,8 @@
module Data.Drasil.ExternalLibraries.ODELibraries (
-- * SciPy Library (Python)
scipyODEPckg, scipyODESymbols,
-- DifferentialEquations.jl Library (Julia)
jlODEPckg, jlODESymbols,
-- * Oslo Library (C#)
osloPckg, osloSymbols, arrayVecDepVar,
-- * Apache Commons (Java)
Expand All @@ -23,7 +25,7 @@ import Language.Drasil.Code (Lang(..), ExternalLibrary, Step, Argument,
lockedNamedArg, inlineArg, inlineNamedArg, preDefinedArg, functionArg,
customObjArg, recordArg, lockedParam, unnamedParam, customClass,
implementation, constructorInfo, methodInfo, methodInfoNoReturn,
appendCurrSol, populateSolList, assignArrayIndex, assignSolFromObj,
appendCurrSol, populateSolList, populateSolList', assignArrayIndex, assignSolFromObj,
initSolListFromArray, initSolListWithVal, solveAndPopulateWhile,
returnExprList, fixedReturn',
ExternalLibraryCall, externalLibCall, choiceStepsFill, choiceStepFill,
Expand Down Expand Up @@ -164,6 +166,88 @@ odeintFunc = quantfunc $ implVar "odeint_scipy" (nounPhrase
"method that solves a system of ODE using lsoda from the FORTRAN library odepack.")
(Array Real) (label "odeint")

-- DifferentialEquations.jl Library (Julia)
jlODEPckg :: ODELibPckg
jlODEPckg = mkODELibNoPath "DifferentialEquations.jl" "7.13.0" jlODE jlODECall [Julia]

jlODESymbols :: [QuantityDict]
jlODESymbols = map qw [jlMthdArg, jlRelTolArg, jlAbsTolArg, jlSaveAtArg] ++
map qw [jlR, jlP, t_span, jlSol, jlMthd, jlSp] ++
map qw [jlODEProblem, jlF, jlODESolve, jlODEDP5]

jlODE :: ExternalLibrary
jlODE = externalLib [
mandatorySteps $ [
callStep $ libFunctionWithResult jlODEImport
jlODEProblem [
functionArg jlF (map unnamedParam [Array Real, Real, Real])
returnExprList, inlineArg (Array Real), preDefinedArg t_span] jlR,
callStep $ libFunctionWithResult jlODEImport
jlODEDP5 [] jlMthd,
callStep $ libFunctionWithResult jlODEImport
jlODESolve [lockedArg (sy jlR), lockedNamedArg jlMthdArg (sy jlMthd),
inlineNamedArg jlRelTolArg Real, inlineNamedArg jlAbsTolArg Real,
inlineNamedArg jlSaveAtArg Real] jlSol] ++
populateSolList' jlSol jlSp] -- TODO: this should probably be populateSolList, but we don't have structs

jlODECall :: ODEInfo -> ExternalLibraryCall
jlODECall info = [
mandatoryStepsFill $ [
callStepFill $ libCallFill (functionArgFill
(map unnamedParamFill [depVar info, jlP, indepVar info])
(returnExprListFill $ odeSyst info) : map (basicArgFill . matrix)
[[initVal info], [[tInit info, tFinal info]]]),
callStepFill $ libCallFill [],
callStepFill $ libCallFill $ map basicArgFill
[relTol $ odeOpts info, absTol $ odeOpts info, stepSize $ odeOpts info]] ++
populateSolListFill (depVar info)]

jlODEImport :: String
jlODEImport = "DifferentialEquations"

jlMthdArg, jlRelTolArg, jlAbsTolArg, jlSaveAtArg :: NamedArgument
jlMthdArg = narg $ implVar "mthd_arg_jlODE" (nounPhrase
"chosen method for solving ODE" "chosen methods for solving ODE")
String (label "alg")
jlRelTolArg = narg $ implVar "jl_arg_reltol" (nounPhrase
"Chosen relative tolerance" "Chosen relative tolerances")
Real (label "reltol")
jlAbsTolArg = narg $ implVar "jl_arg_abstol" (nounPhrase
"Chosen absolute tolerance" "Chosen absolute tolerances")
Real (label "abstol")
jlSaveAtArg = narg $ implVar "jl_arg_saveat" (nounPhrase
"Chosen time step" "Chosen time step")
Real (label "saveat")

jlR, jlP, t_span, jlSol, jlMthd, jlSp :: CodeVarChunk
jlR = quantvar $ implVar "r" (nounPhrase "ODE struct" "ODE structs")
odeT2 (label "r")
jlP = quantvar $ implVar "params" (nounPhrase "param?" "params?")
Void (label "p") -- TODO: this should be a struct of some sort
t_span = quantvar $ implVar "t_span" (nounPhrase "Timespan" "Timespans")
(Array Real) (label "t_span")
jlSol = quantvar $ implVar "jl_solve" (nounPhrase "Solution" "Solutions")
Void (label "sol") -- TODO: this should be a struct of some sort
jlMthd = quantvar $ implVar "jl_method" (nounPhrase
"chosen method for solving ODE" "chosen methods for solving ODE")
String (label "algorithm")
jlSp = quantvar $ implVar "sp_julia" (nounPhrase "ODE solution point"
"ODE solution points") Real (label "sp")

jlF, jlODEProblem, jlODESolve, jlODEDP5 :: CodeFuncChunk
jlF = quantfunc $ implVar "f_jlODE" (nounPhrase "function representing ODE system"
"functions representing ODE system") (Array Real) (label "f")
jlODEProblem = quantfunc $ implVar "jl_ode_problem" (nounPhrase
"function for defining an ODE for jlODE"
"functions for defining an ODE for jlODE") odeT2 (label "ODEProblem")
jlODESolve = quantfunc $ implVar "jl_ode_solve" (nounPhrase
"function for solving an ODE for jlODE"
"functions for solving an ODE for jlODE") odeT2 (label "solve")
jlODEDP5 = quantfunc $ implVar "jl_ode_dp5" (nounPhrase "DP5" "DP5s") odeT2 (label "DP5")

odeT2 :: Space
odeT2 = Void -- TODO: this should be a struct/function? of some sort

-- Oslo Library (C#)

-- | [Oslo](https://www.microsoft.com/en-us/research/project/open-solving-library-for-odes/) ODE library package.
Expand Down
4 changes: 2 additions & 2 deletions code/drasil-code/lib/Language/Drasil/Code.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ module Language.Drasil.Code (
inlineArg, inlineNamedArg, preDefinedArg, preDefinedNamedArg, functionArg,
customObjArg, recordArg, lockedParam, unnamedParam, customClass,
implementation, constructorInfo, methodInfo, methodInfoNoReturn,
appendCurrSol, populateSolList, assignArrayIndex, assignSolFromObj,
appendCurrSol, populateSolList, populateSolList', assignArrayIndex, assignSolFromObj,
initSolListFromArray, initSolListWithVal, solveAndPopulateWhile,
returnExprList, fixedReturn, fixedReturn', initSolWithVal,
ExternalLibraryCall, StepGroupFill(..), StepFill(..), FunctionIntFill(..),
Expand Down Expand Up @@ -67,7 +67,7 @@ import Language.Drasil.Code.ExternalLibrary (ExternalLibrary, Step,
inlineArg, inlineNamedArg, preDefinedArg, preDefinedNamedArg, functionArg,
customObjArg, recordArg, lockedParam, unnamedParam, customClass,
implementation, constructorInfo, methodInfo, methodInfoNoReturn,
appendCurrSol, populateSolList, assignArrayIndex, assignSolFromObj,
appendCurrSol, populateSolList, populateSolList', assignArrayIndex, assignSolFromObj,
initSolListFromArray, initSolListWithVal, solveAndPopulateWhile,
returnExprList, fixedReturn, fixedReturn', initSolWithVal)
import Language.Drasil.Code.ExternalLibraryCall (ExternalLibraryCall,
Expand Down
13 changes: 12 additions & 1 deletion code/drasil-code/lib/Language/Drasil/Code/ExternalLibrary.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ module Language.Drasil.Code.ExternalLibrary (ExternalLibrary, Step(..),
lockedNamedArg, inlineArg, inlineNamedArg, preDefinedArg, preDefinedNamedArg,
functionArg, customObjArg, recordArg, lockedParam, unnamedParam, customClass,
implementation, constructorInfo, methodInfo, methodInfoNoReturn,
appendCurrSol, populateSolList, assignArrayIndex, assignSolFromObj,
appendCurrSol, populateSolList, populateSolList', assignArrayIndex, assignSolFromObj,
initSolListFromArray, initSolListWithVal, solveAndPopulateWhile,
returnExprList, fixedReturn, fixedReturn', initSolWithVal
) where
Expand Down Expand Up @@ -260,6 +260,17 @@ populateSolList arr el fld = [statementStep (\cdchs es -> case (cdchs, es) of
(_,_) -> error popErr)]
where popErr = "Fill for populateSolList should provide one CodeChunk and no Exprs"

-- | Specifies a statement where a solution list is populated by iterating
-- through a solution array.
populateSolList' :: CodeVarChunk -> CodeVarChunk -> [Step]
populateSolList' arr el = [statementStep (\cdchs es -> case (cdchs, es) of
([s], []) -> FAsg s (Matrix [[]])
(_,_) -> error popErr),
statementStep (\cdchs es -> case (cdchs, es) of
([s], []) -> FForEach el (sy arr) [FAppend (sy s) (sy el)]
(_,_) -> error popErr)]
where popErr = "Fill for populateSolList' should provide one CodeChunk and no Exprs"

-- | Specifies statements where every index of an array is assigned a value.
assignArrayIndex :: Step
assignArrayIndex = statementStep (\cdchs es -> case (cdchs, es) of
Expand Down
7 changes: 4 additions & 3 deletions code/drasil-example/swhsnopcm/lib/Drasil/SWHSNoPCM/Body.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ import Data.Drasil.Concepts.Thermodynamics (heatCapSpec, htFlux, phaseChange,
temp, thermalAnalysis, thermalConduction, thermocon)

import Data.Drasil.ExternalLibraries.ODELibraries (scipyODESymbols, osloSymbols,
arrayVecDepVar, apacheODESymbols, odeintSymbols)
arrayVecDepVar, apacheODESymbols, odeintSymbols, jlODESymbols)

import qualified Data.Drasil.Quantities.Thermodynamics as QT (temp,
heatCapSpec, htFlux, sensHeat)
Expand Down Expand Up @@ -94,8 +94,9 @@ symbolsAll :: [QuantityDict] --FIXME: Why is PCM (swhsSymbolsAll) here?
--FOUND LOC OF ERROR: Instance Models
symbolsAll = map qw symbols ++ map qw specParamValList ++
[qw coilSAMax, qw tauW] ++ map qw [absTol, relTol] ++
scipyODESymbols ++ osloSymbols ++ apacheODESymbols ++ odeintSymbols
++ map qw [listToArray $ quantvar tempW, arrayVecDepVar noPCMODEInfo]
scipyODESymbols ++ jlODESymbols ++ osloSymbols ++ apacheODESymbols ++
odeintSymbols ++
map qw [listToArray $ quantvar tempW, arrayVecDepVar noPCMODEInfo]

concepts :: [UnitalChunk]
concepts = map ucw [density, tau, inSA, outSA,
Expand Down
9 changes: 5 additions & 4 deletions code/drasil-example/swhsnopcm/lib/Drasil/SWHSNoPCM/Choices.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ import Language.Drasil.Code (Choices(..), CodeSpec, codeSpec, Comments(..),
ExtLib(..))

import Data.Drasil.ExternalLibraries.ODELibraries (scipyODEPckg, osloPckg,
apacheODEPckg, odeintPckg)
apacheODEPckg, odeintPckg, jlODEPckg)
import Drasil.SWHSNoPCM.Body (noPCMODEInfo, fullSI)

code :: CodeSpec
Expand All @@ -17,13 +17,14 @@ code = codeSpec fullSI choices []

choices :: Choices
choices = defaultChoices {
lang = [Python, Cpp, CSharp, Java],
lang = [Python, Cpp, CSharp, Java, Julia],
architecture = makeArchit Modular Program,
dataInfo = makeData Unbundled (Store Bundled) Const,
dataInfo = makeData Unbundled (Store Unbundled) Const,
optFeats = makeOptFeats
(makeDocConfig [CommentFunc, CommentClass, CommentMod] Quiet Hide)
(makeLogConfig [] "log.txt")
[SampleInput "../../datafiles/swhsnopcm/sampleInput.txt", ReadME],
srsConstraints = makeConstraints Warning Warning,
extLibs = [Math (makeODE [noPCMODEInfo] [scipyODEPckg, osloPckg, apacheODEPckg, odeintPckg])]
extLibs = [Math (makeODE [noPCMODEInfo] [scipyODEPckg, osloPckg,
apacheODEPckg, odeintPckg, jlODEPckg])]
}
2 changes: 1 addition & 1 deletion code/drasil-gool/lib/Drasil/GOOL/InterfaceCommon.hs
Original file line number Diff line number Diff line change
Expand Up @@ -502,7 +502,7 @@ convType (Func ps r) = funcType (map convType ps) (convType r)
convType Void = void
convType InFile = infile
convType OutFile = outfile
convType (Object _) = error "Objects not supported"
convType (Object n) = error $ "convType: Objects not supported (name: '" ++ n ++ "')"

convScope :: (ScopeSym r) => ScopeData -> r (Scope r)
convScope (SD {scopeTag = Global}) = global
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -418,7 +418,7 @@ multiReturn f vs = do
returnStmt $ mkStateVal IC.void $ f $ valueList vs'

listDec :: (CommonRenderSym r) => SVariable r -> r (Scope r) -> MSStatement r
listDec v scp = IC.varDecDef v scp $ IC.litList (onStateValue variableType v) []
listDec v scp = listDecDef v scp []

funcDecDef :: (OORenderSym r) => SVariable r -> r (Scope r) -> [SVariable r] ->
MSBody r -> MSStatement r
Expand Down
28 changes: 19 additions & 9 deletions code/drasil-gool/lib/Drasil/GOOL/LanguageRenderer/JuliaRenderer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,8 @@ import Drasil.GOOL.RendererClassesProc (ProcRenderSym, RenderFile(..),
RenderMod(..), ModuleElim, ProcRenderMethod(..))
import qualified Drasil.GOOL.RendererClassesProc as RC (module')
import Drasil.GOOL.LanguageRenderer (printLabel, listSep, listSep',
variableList, parameterList, forLabel, inLabel, tryLabel, catchLabel)
variableList, parameterList, forLabel, inLabel, tryLabel, catchLabel,
valueList)
import qualified Drasil.GOOL.LanguageRenderer as R (sqrt, abs, log10, log,
exp, sin, cos, tan, asin, acos, atan, floor, ceil, multiStmt, body,
addComments, blockCmt, docCmt, commentedMod, listSetFunc, commentedItem,
Expand All @@ -60,7 +61,7 @@ import qualified Drasil.GOOL.LanguageRenderer.LanguagePolymorphic as G (
emptyStmt, print, comment, valStmt, returnStmt, param, docFunc, throw, arg,
argsList, ifCond, smartAdd, local, var)
import qualified Drasil.GOOL.LanguageRenderer.CommonPseudoOO as CP (bool,
boolRender, extVar, funcType, litArray, listDec, listDecDef, listAccessFunc,
boolRender, extVar, funcType, listDec, listDecDef, listAccessFunc,
listSetFunc, notNull, extFuncAppMixedArgs, functionDoc, listSize, listAdd,
listAppend, intToIndex', indexToInt', inOutFunc, docInOutFunc', forLoopError,
varDecDef, openFileR', openFileW', openFileA', multiReturn, multiAssign,
Expand Down Expand Up @@ -138,10 +139,11 @@ instance RenderFile JuliaCode where
instance ImportSym JuliaCode where
type Import JuliaCode = Doc
langImport n = let modName = text n
fileName = text $ n ++ '.' : jlExt
in toCode $ importLabel <+> modName
modImport n = let modName = text n
fileName = text $ n ++ '.' : jlExt
in toCode $ vcat [includeLabel <> parens (doubleQuotes fileName),
importLabel <+> text "." <> modName] -- TODO: we want a dot only when the import is locally defined.
modImport = langImport
importLabel <+> text "." <> modName]

instance ImportElim JuliaCode where
import' = unJLC
Expand Down Expand Up @@ -257,7 +259,7 @@ instance ScopeElim JuliaCode where
instance VariableSym JuliaCode where
type Variable JuliaCode = VarData
var = G.var
constant = var -- TODO: add `const` keyword in global scope, and follow Python for local
constant = var
extVar l n t = modify (addModuleImportVS l) >> CP.extVar l n t
arrayElem i = A.arrayElem (litInt i)

Expand Down Expand Up @@ -289,8 +291,8 @@ instance Literal JuliaCode where
litFloat = jlLitFloat
litInt = G.litInt
litString = G.litString
litArray = CP.litArray brackets
litList = litArray
litArray = litList
litList = jlLitList

instance MathConstant JuliaCode where
pi :: SValue JuliaCode
Expand Down Expand Up @@ -661,6 +663,14 @@ jlClassError = "Classes are not supported in Julia"
jlLitFloat :: (CommonRenderSym r) => Float -> SValue r
jlLitFloat f = mkStateVal float (text jlFloatConc <> parens (D.float f))

jlLitList :: (CommonRenderSym r) => VSType r -> [SValue r] -> SValue r
jlLitList t' es = do
t <- t'
let lt' = listType t'
elems <- sequence es
let typeDec = if null es then RC.type' t else empty
mkStateVal lt' (typeDec <> brackets (valueList elems))

jlCast :: (CommonRenderSym r) => VSType r -> SValue r -> SValue r
jlCast t' v' = do
t <- t'
Expand Down Expand Up @@ -962,7 +972,7 @@ jlModStart n = jlMod <+> text n
using :: Doc
using = text "using"

usingModule :: Label -> Doc -- TODO: see if you need to add context for package vs file
usingModule :: Label -> Doc
usingModule n = using <+> text n

-- IO
Expand Down
2 changes: 0 additions & 2 deletions code/drasil-lang/lib/Language/Drasil/CodeExpr/Class.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,6 @@ import Language.Drasil.UID (HasUID(..))
import Language.Drasil.Symbol (HasSymbol)
import Language.Drasil.Space (Space(Actor), HasSpace(..))
import Language.Drasil.Chunk.CodeVar (CodeIdea, CodeVarChunk)
import Language.Drasil.Expr.Class (ExprC(..))
import Language.Drasil.CodeExpr.Lang (CodeExpr(FCall, New, Message, Field))

import Control.Lens ( (^.) )
Expand Down Expand Up @@ -57,6 +56,5 @@ instance CodeExprC CodeExpr where
"Actor space"

-- | Similar to 'apply', but takes a relation to apply to 'FCall'.
applyWithNamedArgs f [] [] = sy f
applyWithNamedArgs f ps ns = FCall (f ^. uid) ps (zip (map ((^. uid) . fst) ns)
(map snd ns))
4 changes: 2 additions & 2 deletions code/stable-website/index.html

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion code/stable/gooltest/julia/FileTests/FileTests.jl

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

26 changes: 13 additions & 13 deletions code/stable/gooltest/julia/HelloWorld/HelloWorld.jl

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

Loading

0 comments on commit c024497

Please sign in to comment.