module Language.Drasil.Code.Imperative.Generator (
generator, generateCode
) where
import Language.Drasil
import Language.Drasil.Code.Imperative.ConceptMatch (chooseConcept)
import Language.Drasil.Code.Imperative.Descriptions (unmodularDesc)
import Language.Drasil.Code.Imperative.SpaceMatch (chooseSpace)
import Language.Drasil.Code.Imperative.GenerateGOOL (ClassType(..),
genDoxConfig, genReadMe, genModuleWithImports)
import Language.Drasil.Code.Imperative.GenODE (chooseODELib)
import Language.Drasil.Code.Imperative.Helpers (liftS)
import Language.Drasil.Code.Imperative.Import (genModDef, genModFuncs,
genModClasses)
import Language.Drasil.Code.Imperative.Modules (chooseInModule, genConstClass,
genConstMod, genInputClass, genInputConstraints, genInputDerived,
genInputFormat, genMain, genMainFunc, genCalcMod, genCalcFunc,
genOutputFormat, genOutputMod, genSampleInput)
import Language.Drasil.Code.Imperative.DrasilState (GenState, DrasilState(..),
designLog, inMod, modExportMap, clsDefMap)
import Language.Drasil.Code.Imperative.GOOL.ClassInterface (ReadMeInfo(..),
PackageSym(..), AuxiliarySym(..))
import Language.Drasil.Code.Imperative.GOOL.Data (PackData(..), ad)
import Language.Drasil.Code.CodeGeneration (createCodeFiles, makeCode)
import Language.Drasil.Code.ExtLibImport (auxMods, imports, modExports)
import Language.Drasil.Code.Lang (Lang(..))
import Language.Drasil.Choices (Choices(..), Modularity(..), Architecture(..),
Visibility(..), DataInfo(..), Constraints(..), choicesSent, DocConfig(..),
LogConfig(..), OptionalFeatures(..))
import Language.Drasil.CodeSpec (CodeSpec(..), getODE)
import Language.Drasil.Printers (Linearity(Linear), sentenceDoc)
import GOOL.Drasil (GSProgram, SFile, OOProg, ProgramSym(..), ScopeTag(..),
ProgData(..), initialState, unCI)
import System.Directory (setCurrentDirectory, createDirectoryIfMissing,
getCurrentDirectory)
import Control.Lens ((^.))
import Control.Monad.State (get, evalState, runState)
import Data.List (nub)
import Data.Map (fromList, member, keys, elems)
import Data.Maybe (maybeToList, catMaybes)
import Text.PrettyPrint.HughesPJ (isEmpty, vcat)
generator :: Lang -> String -> [Expr] -> Choices -> CodeSpec -> DrasilState
generator :: Lang -> String -> [Expr] -> Choices -> CodeSpec -> DrasilState
generator l :: Lang
l dt :: String
dt sd :: [Expr]
sd chs :: Choices
chs spec :: CodeSpec
spec = DrasilState :: CodeSpec
-> Modularity
-> ImplementationType
-> Structure
-> ConstantStructure
-> ConstantRepr
-> MatchedConceptMap
-> MatchedSpaces
-> ConstraintBehaviour
-> ConstraintBehaviour
-> [Comments]
-> Verbosity
-> String
-> String
-> [Logging]
-> [AuxFile]
-> [Expr]
-> [Mod]
-> [(String, String)]
-> ExtLibMap
-> [String]
-> ModExportMap
-> ModExportMap
-> ModExportMap
-> [String]
-> String
-> String
-> Doc
-> [(Space, CodeType)]
-> DrasilState
DrasilState {
codeSpec :: CodeSpec
codeSpec = CodeSpec
spec,
modular :: Modularity
modular = Architecture -> Modularity
modularity (Architecture -> Modularity) -> Architecture -> Modularity
forall a b. (a -> b) -> a -> b
$ Choices -> Architecture
architecture Choices
chs,
inStruct :: Structure
inStruct = DataInfo -> Structure
inputStructure (DataInfo -> Structure) -> DataInfo -> Structure
forall a b. (a -> b) -> a -> b
$ Choices -> DataInfo
dataInfo Choices
chs,
conStruct :: ConstantStructure
conStruct = DataInfo -> ConstantStructure
constStructure (DataInfo -> ConstantStructure) -> DataInfo -> ConstantStructure
forall a b. (a -> b) -> a -> b
$ Choices -> DataInfo
dataInfo Choices
chs,
conRepr :: ConstantRepr
conRepr = DataInfo -> ConstantRepr
constRepr (DataInfo -> ConstantRepr) -> DataInfo -> ConstantRepr
forall a b. (a -> b) -> a -> b
$ Choices -> DataInfo
dataInfo Choices
chs,
concMatches :: MatchedConceptMap
concMatches = MatchedConceptMap
mcm,
spaceMatches :: MatchedSpaces
spaceMatches = Lang -> Choices -> MatchedSpaces
chooseSpace Lang
l Choices
chs,
implType :: ImplementationType
implType = Architecture -> ImplementationType
impType (Architecture -> ImplementationType)
-> Architecture -> ImplementationType
forall a b. (a -> b) -> a -> b
$ Choices -> Architecture
architecture Choices
chs,
onSfwrC :: ConstraintBehaviour
onSfwrC = Constraints -> ConstraintBehaviour
onSfwrConstraint (Constraints -> ConstraintBehaviour)
-> Constraints -> ConstraintBehaviour
forall a b. (a -> b) -> a -> b
$ Choices -> Constraints
srsConstraints Choices
chs,
onPhysC :: ConstraintBehaviour
onPhysC = Constraints -> ConstraintBehaviour
onPhysConstraint (Constraints -> ConstraintBehaviour)
-> Constraints -> ConstraintBehaviour
forall a b. (a -> b) -> a -> b
$ Choices -> Constraints
srsConstraints Choices
chs,
commented :: [Comments]
commented = DocConfig -> [Comments]
comments (DocConfig -> [Comments]) -> DocConfig -> [Comments]
forall a b. (a -> b) -> a -> b
$ OptionalFeatures -> DocConfig
docConfig (OptionalFeatures -> DocConfig) -> OptionalFeatures -> DocConfig
forall a b. (a -> b) -> a -> b
$ Choices -> OptionalFeatures
optFeats Choices
chs,
doxOutput :: Verbosity
doxOutput = DocConfig -> Verbosity
doxVerbosity (DocConfig -> Verbosity) -> DocConfig -> Verbosity
forall a b. (a -> b) -> a -> b
$ OptionalFeatures -> DocConfig
docConfig (OptionalFeatures -> DocConfig) -> OptionalFeatures -> DocConfig
forall a b. (a -> b) -> a -> b
$ Choices -> OptionalFeatures
optFeats Choices
chs,
date :: String
date = Visibility -> String
showDate (Visibility -> String) -> Visibility -> String
forall a b. (a -> b) -> a -> b
$ DocConfig -> Visibility
dates (DocConfig -> Visibility) -> DocConfig -> Visibility
forall a b. (a -> b) -> a -> b
$ OptionalFeatures -> DocConfig
docConfig (OptionalFeatures -> DocConfig) -> OptionalFeatures -> DocConfig
forall a b. (a -> b) -> a -> b
$ Choices -> OptionalFeatures
optFeats Choices
chs,
logKind :: [Logging]
logKind = LogConfig -> [Logging]
logging (LogConfig -> [Logging]) -> LogConfig -> [Logging]
forall a b. (a -> b) -> a -> b
$ OptionalFeatures -> LogConfig
logConfig (OptionalFeatures -> LogConfig) -> OptionalFeatures -> LogConfig
forall a b. (a -> b) -> a -> b
$ Choices -> OptionalFeatures
optFeats Choices
chs,
logName :: String
logName = LogConfig -> String
logFile (LogConfig -> String) -> LogConfig -> String
forall a b. (a -> b) -> a -> b
$ OptionalFeatures -> LogConfig
logConfig (OptionalFeatures -> LogConfig) -> OptionalFeatures -> LogConfig
forall a b. (a -> b) -> a -> b
$ Choices -> OptionalFeatures
optFeats Choices
chs,
auxiliaries :: [AuxFile]
auxiliaries = OptionalFeatures -> [AuxFile]
auxFiles (OptionalFeatures -> [AuxFile]) -> OptionalFeatures -> [AuxFile]
forall a b. (a -> b) -> a -> b
$ Choices -> OptionalFeatures
optFeats Choices
chs,
sampleData :: [Expr]
sampleData = [Expr]
sd,
modules :: [Mod]
modules = [Mod]
modules',
extLibNames :: [(String, String)]
extLibNames = [(String, String)]
nms,
extLibMap :: ExtLibMap
extLibMap = [(String, ExtLibState)] -> ExtLibMap
forall k a. Ord k => [(k, a)] -> Map k a
fromList [(String, ExtLibState)]
elmap,
libPaths :: [String]
libPaths = Maybe String -> [String]
forall a. Maybe a -> [a]
maybeToList Maybe String
pth,
eMap :: ModExportMap
eMap = ModExportMap
mem,
libEMap :: ModExportMap
libEMap = ModExportMap
lem,
clsMap :: ModExportMap
clsMap = ModExportMap
cdm,
defList :: [String]
defList = [String] -> [String]
forall a. Eq a => [a] -> [a]
nub ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ ModExportMap -> [String]
forall k a. Map k a -> [k]
keys ModExportMap
mem [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ ModExportMap -> [String]
forall k a. Map k a -> [k]
keys ModExportMap
cdm,
currentModule :: String
currentModule = "",
currentClass :: String
currentClass = "",
_designLog :: Doc
_designLog = Doc
des,
_loggedSpaces :: [(Space, CodeType)]
_loggedSpaces = []
}
where (mcm :: MatchedConceptMap
mcm, concLog :: [Sentence]
concLog) = State [Sentence] MatchedConceptMap
-> [Sentence] -> (MatchedConceptMap, [Sentence])
forall s a. State s a -> s -> (a, s)
runState (Choices -> State [Sentence] MatchedConceptMap
chooseConcept Choices
chs) []
showDate :: Visibility -> String
showDate Show = String
dt
showDate Hide = ""
((pth :: Maybe String
pth, elmap :: [(String, ExtLibState)]
elmap, lname :: (String, String)
lname), libLog :: [Sentence]
libLog) = State
[Sentence]
(Maybe String, [(String, ExtLibState)], (String, String))
-> [Sentence]
-> ((Maybe String, [(String, ExtLibState)], (String, String)),
[Sentence])
forall s a. State s a -> s -> (a, s)
runState (Lang
-> Maybe ODE
-> State
[Sentence]
(Maybe String, [(String, ExtLibState)], (String, String))
chooseODELib Lang
l (Maybe ODE
-> State
[Sentence]
(Maybe String, [(String, ExtLibState)], (String, String)))
-> Maybe ODE
-> State
[Sentence]
(Maybe String, [(String, ExtLibState)], (String, String))
forall a b. (a -> b) -> a -> b
$ [ExtLib] -> Maybe ODE
getODE ([ExtLib] -> Maybe ODE) -> [ExtLib] -> Maybe ODE
forall a b. (a -> b) -> a -> b
$ Choices -> [ExtLib]
extLibs Choices
chs) []
els :: [ExtLibState]
els = ((String, ExtLibState) -> ExtLibState)
-> [(String, ExtLibState)] -> [ExtLibState]
forall a b. (a -> b) -> [a] -> [b]
map (String, ExtLibState) -> ExtLibState
forall a b. (a, b) -> b
snd [(String, ExtLibState)]
elmap
nms :: [(String, String)]
nms = [(String, String)
lname]
mem :: ModExportMap
mem = CodeSpec -> Choices -> [Mod] -> ModExportMap
modExportMap CodeSpec
spec Choices
chs [Mod]
modules'
lem :: ModExportMap
lem = [(String, String)] -> ModExportMap
forall k a. Ord k => [(k, a)] -> Map k a
fromList ((ExtLibState -> [(String, String)])
-> [ExtLibState] -> [(String, String)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (ExtLibState
-> Getting [(String, String)] ExtLibState [(String, String)]
-> [(String, String)]
forall s a. s -> Getting a s a -> a
^. Getting [(String, String)] ExtLibState [(String, String)]
Lens' ExtLibState [(String, String)]
modExports) [ExtLibState]
els)
cdm :: ModExportMap
cdm = CodeSpec -> Choices -> [Mod] -> ModExportMap
clsDefMap CodeSpec
spec Choices
chs [Mod]
modules'
modules' :: [Mod]
modules' = CodeSpec -> [Mod]
mods CodeSpec
spec [Mod] -> [Mod] -> [Mod]
forall a. [a] -> [a] -> [a]
++ (ExtLibState -> [Mod]) -> [ExtLibState] -> [Mod]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (ExtLibState -> Getting [Mod] ExtLibState [Mod] -> [Mod]
forall s a. s -> Getting a s a -> a
^. Getting [Mod] ExtLibState [Mod]
Lens' ExtLibState [Mod]
auxMods) [ExtLibState]
els
nonPrefChs :: [Sentence]
nonPrefChs = Choices -> [Sentence]
choicesSent Choices
chs
des :: Doc
des = [Doc] -> Doc
vcat ([Doc] -> Doc) -> ([Sentence] -> [Doc]) -> [Sentence] -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Sentence -> Doc) -> [Sentence] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (ChunkDB -> Stage -> Linearity -> Sentence -> Doc
sentenceDoc (CodeSpec -> ChunkDB
sysinfodb CodeSpec
spec) Stage
Implementation Linearity
Linear) ([Sentence] -> Doc) -> [Sentence] -> Doc
forall a b. (a -> b) -> a -> b
$
([Sentence]
nonPrefChs [Sentence] -> [Sentence] -> [Sentence]
forall a. [a] -> [a] -> [a]
++ [Sentence]
concLog [Sentence] -> [Sentence] -> [Sentence]
forall a. [a] -> [a] -> [a]
++ [Sentence]
libLog)
generateCode :: (OOProg progRepr, PackageSym packRepr) => Lang ->
(progRepr (Program progRepr) -> ProgData) -> (packRepr (Package packRepr) ->
PackData) -> DrasilState -> IO ()
generateCode :: Lang
-> (progRepr (Program progRepr) -> ProgData)
-> (packRepr (Package packRepr) -> PackData)
-> DrasilState
-> IO ()
generateCode l :: Lang
l unReprProg :: progRepr (Program progRepr) -> ProgData
unReprProg unReprPack :: packRepr (Package packRepr) -> PackData
unReprPack g :: DrasilState
g = do
String
workingDir <- IO String
getCurrentDirectory
Bool -> String -> IO ()
createDirectoryIfMissing Bool
False (Lang -> String
getDir Lang
l)
String -> IO ()
setCurrentDirectory (Lang -> String
getDir Lang
l)
let (pckg :: packRepr (Package packRepr)
pckg, ds :: DrasilState
ds) = State DrasilState (packRepr (Package packRepr))
-> DrasilState -> (packRepr (Package packRepr), DrasilState)
forall s a. State s a -> s -> (a, s)
runState ((progRepr (Program progRepr) -> ProgData)
-> State DrasilState (packRepr (Package packRepr))
forall (progRepr :: * -> *) (packRepr :: * -> *).
(OOProg progRepr, PackageSym packRepr) =>
(progRepr (Program progRepr) -> ProgData)
-> GenState (packRepr (Package packRepr))
genPackage progRepr (Program progRepr) -> ProgData
unReprProg) DrasilState
g
code :: Code
code = [FileData] -> [AuxData] -> Code
makeCode (ProgData -> [FileData]
progMods (ProgData -> [FileData]) -> ProgData -> [FileData]
forall a b. (a -> b) -> a -> b
$ PackData -> ProgData
packProg (PackData -> ProgData) -> PackData -> ProgData
forall a b. (a -> b) -> a -> b
$ packRepr (Package packRepr) -> PackData
unReprPack packRepr (Package packRepr)
pckg)
([String -> Doc -> AuxData
ad "designLog.txt" (DrasilState
ds DrasilState -> Getting Doc DrasilState Doc -> Doc
forall s a. s -> Getting a s a -> a
^. Getting Doc DrasilState Doc
Lens' DrasilState Doc
designLog) | Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Doc -> Bool
isEmpty (Doc -> Bool) -> Doc -> Bool
forall a b. (a -> b) -> a -> b
$
DrasilState
ds DrasilState -> Getting Doc DrasilState Doc -> Doc
forall s a. s -> Getting a s a -> a
^. Getting Doc DrasilState Doc
Lens' DrasilState Doc
designLog] [AuxData] -> [AuxData] -> [AuxData]
forall a. [a] -> [a] -> [a]
++ PackData -> [AuxData]
packAux (packRepr (Package packRepr) -> PackData
unReprPack packRepr (Package packRepr)
pckg))
Code -> IO ()
createCodeFiles Code
code
String -> IO ()
setCurrentDirectory String
workingDir
genPackage :: (OOProg progRepr, PackageSym packRepr) =>
(progRepr (Program progRepr) -> ProgData) ->
GenState (packRepr (Package packRepr))
genPackage :: (progRepr (Program progRepr) -> ProgData)
-> GenState (packRepr (Package packRepr))
genPackage unRepr :: progRepr (Program progRepr) -> ProgData
unRepr = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
GS (CodeInfo (Program CodeInfo))
ci <- GenState (GS (CodeInfo (Program CodeInfo)))
forall (r :: * -> *). OOProg r => GenState (GSProgram r)
genProgram
GS (progRepr (Program progRepr))
p <- GenState (GS (progRepr (Program progRepr)))
forall (r :: * -> *). OOProg r => GenState (GSProgram r)
genProgram
let info :: GOOLState
info = CodeInfo GOOLState -> GOOLState
forall a. CodeInfo a -> a
unCI (CodeInfo GOOLState -> GOOLState)
-> CodeInfo GOOLState -> GOOLState
forall a b. (a -> b) -> a -> b
$ State GOOLState (CodeInfo GOOLState)
-> GOOLState -> CodeInfo GOOLState
forall s a. State s a -> s -> a
evalState GS (CodeInfo (Program CodeInfo))
State GOOLState (CodeInfo GOOLState)
ci GOOLState
initialState
(reprPD :: progRepr (Program progRepr)
reprPD, s :: GOOLState
s) = GS (progRepr (Program progRepr))
-> GOOLState -> (progRepr (Program progRepr), GOOLState)
forall s a. State s a -> s -> (a, s)
runState GS (progRepr (Program progRepr))
p GOOLState
info
pd :: ProgData
pd = progRepr (Program progRepr) -> ProgData
unRepr progRepr (Program progRepr)
reprPD
m :: packRepr (Auxiliary packRepr)
m = [String]
-> ImplementationType
-> [Comments]
-> GOOLState
-> ProgData
-> packRepr (Auxiliary packRepr)
forall (r :: * -> *).
AuxiliarySym r =>
[String]
-> ImplementationType
-> [Comments]
-> GOOLState
-> ProgData
-> r (Auxiliary r)
makefile (DrasilState -> [String]
libPaths DrasilState
g) (DrasilState -> ImplementationType
implType DrasilState
g) (DrasilState -> [Comments]
commented DrasilState
g) GOOLState
s ProgData
pd
as :: [String]
as = case DrasilState -> CodeSpec
codeSpec DrasilState
g of CodeSpec {authors :: ()
authors = [a]
a} -> (a -> String) -> [a] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map a -> String
forall n. HasName n => n -> String
name [a]
a
cfp :: [String]
cfp = CodeSpec -> [String]
configFiles (CodeSpec -> [String]) -> CodeSpec -> [String]
forall a b. (a -> b) -> a -> b
$ DrasilState -> CodeSpec
codeSpec DrasilState
g
Maybe (packRepr (Auxiliary packRepr))
i <- GenState (Maybe (packRepr (Auxiliary packRepr)))
forall (r :: * -> *).
AuxiliarySym r =>
GenState (Maybe (r (Auxiliary r)))
genSampleInput
Maybe (packRepr (Auxiliary packRepr))
d <- GOOLState -> GenState (Maybe (packRepr (Auxiliary packRepr)))
forall (r :: * -> *).
AuxiliarySym r =>
GOOLState -> GenState (Maybe (r (Auxiliary r)))
genDoxConfig GOOLState
s
Maybe (packRepr (Auxiliary packRepr))
rm <- ReadMeInfo -> GenState (Maybe (packRepr (Auxiliary packRepr)))
forall (r :: * -> *).
AuxiliarySym r =>
ReadMeInfo -> GenState (Maybe (r (Auxiliary r)))
genReadMe ReadMeInfo :: String
-> String
-> Maybe String
-> ImplementationType
-> [(String, String)]
-> [String]
-> [String]
-> [String]
-> String
-> ReadMeInfo
ReadMeInfo {
langName :: String
langName = "",
langVersion :: String
langVersion = "",
invalidOS :: Maybe String
invalidOS = Maybe String
forall a. Maybe a
Nothing,
implementType :: ImplementationType
implementType = DrasilState -> ImplementationType
implType DrasilState
g,
extLibNV :: [(String, String)]
extLibNV = DrasilState -> [(String, String)]
extLibNames DrasilState
g,
extLibFP :: [String]
extLibFP = DrasilState -> [String]
libPaths DrasilState
g,
contributors :: [String]
contributors = [String]
as,
configFP :: [String]
configFP = [String]
cfp,
caseName :: String
caseName = ""}
packRepr (Package packRepr)
-> GenState (packRepr (Package packRepr))
forall (m :: * -> *) a. Monad m => a -> m a
return (packRepr (Package packRepr)
-> GenState (packRepr (Package packRepr)))
-> packRepr (Package packRepr)
-> GenState (packRepr (Package packRepr))
forall a b. (a -> b) -> a -> b
$ ProgData
-> [packRepr (Auxiliary packRepr)] -> packRepr (Package packRepr)
forall (r :: * -> *).
PackageSym r =>
ProgData -> [r (Auxiliary r)] -> r (Package r)
package ProgData
pd (packRepr (Auxiliary packRepr)
mpackRepr (Auxiliary packRepr)
-> [packRepr (Auxiliary packRepr)]
-> [packRepr (Auxiliary packRepr)]
forall a. a -> [a] -> [a]
:[Maybe (packRepr (Auxiliary packRepr))]
-> [packRepr (Auxiliary packRepr)]
forall a. [Maybe a] -> [a]
catMaybes [Maybe (packRepr (Auxiliary packRepr))
i,Maybe (packRepr (Auxiliary packRepr))
rm,Maybe (packRepr (Auxiliary packRepr))
d])
genProgram :: (OOProg r) => GenState (GSProgram r)
genProgram :: GenState (GSProgram r)
genProgram = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
[FS (r (File r))]
ms <- Modularity -> GenState [FS (r (File r))]
forall (r :: * -> *). OOProg r => Modularity -> GenState [SFile r]
chooseModules (Modularity -> GenState [FS (r (File r))])
-> Modularity -> GenState [FS (r (File r))]
forall a b. (a -> b) -> a -> b
$ DrasilState -> Modularity
modular DrasilState
g
let n :: String
n = CodeSpec -> String
pName (CodeSpec -> String) -> CodeSpec -> String
forall a b. (a -> b) -> a -> b
$ DrasilState -> CodeSpec
codeSpec DrasilState
g
GSProgram r -> GenState (GSProgram r)
forall (m :: * -> *) a. Monad m => a -> m a
return (GSProgram r -> GenState (GSProgram r))
-> GSProgram r -> GenState (GSProgram r)
forall a b. (a -> b) -> a -> b
$ String -> [FS (r (File r))] -> GSProgram r
forall (r :: * -> *).
ProgramSym r =>
String -> [SFile r] -> GSProgram r
prog String
n [FS (r (File r))]
ms
chooseModules :: (OOProg r) => Modularity -> GenState [SFile r]
chooseModules :: Modularity -> GenState [SFile r]
chooseModules Unmodular = State DrasilState (SFile r) -> GenState [SFile r]
forall a b. State a b -> State a [b]
liftS State DrasilState (SFile r)
forall (r :: * -> *). OOProg r => GenState (SFile r)
genUnmodular
chooseModules (Modular _) = GenState [SFile r]
forall (r :: * -> *). OOProg r => GenState [SFile r]
genModules
genUnmodular :: (OOProg r) => GenState (SFile r)
genUnmodular :: GenState (SFile r)
genUnmodular = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
String
umDesc <- GenState String
unmodularDesc
let n :: String
n = CodeSpec -> String
pName (CodeSpec -> String) -> CodeSpec -> String
forall a b. (a -> b) -> a -> b
$ DrasilState -> CodeSpec
codeSpec DrasilState
g
cls :: Bool
cls = (String -> Bool) -> [String] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (String -> ModExportMap -> Bool
forall k a. Ord k => k -> Map k a -> Bool
`member` DrasilState -> ModExportMap
clsMap DrasilState
g)
["get_input", "derived_values", "input_constraints"]
String
-> String
-> [String]
-> [GenState (Maybe (SMethod r))]
-> [GenState (Maybe (SClass r))]
-> GenState (SFile r)
forall (r :: * -> *).
OOProg r =>
String
-> String
-> [String]
-> [GenState (Maybe (SMethod r))]
-> [GenState (Maybe (SClass r))]
-> GenState (SFile r)
genModuleWithImports String
n String
umDesc ((ExtLibState -> [String]) -> [ExtLibState] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (ExtLibState -> Getting [String] ExtLibState [String] -> [String]
forall s a. s -> Getting a s a -> a
^. Getting [String] ExtLibState [String]
Lens' ExtLibState [String]
imports) (ExtLibMap -> [ExtLibState]
forall k a. Map k a -> [a]
elems (ExtLibMap -> [ExtLibState]) -> ExtLibMap -> [ExtLibState]
forall a b. (a -> b) -> a -> b
$ DrasilState -> ExtLibMap
extLibMap DrasilState
g))
(GenState (Maybe (SMethod r))
forall (r :: * -> *). OOProg r => GenState (Maybe (SMethod r))
genMainFunc
GenState (Maybe (SMethod r))
-> [GenState (Maybe (SMethod r))] -> [GenState (Maybe (SMethod r))]
forall a. a -> [a] -> [a]
: (StateT DrasilState Identity (SMethod r)
-> GenState (Maybe (SMethod r)))
-> [StateT DrasilState Identity (SMethod r)]
-> [GenState (Maybe (SMethod r))]
forall a b. (a -> b) -> [a] -> [b]
map ((SMethod r -> Maybe (SMethod r))
-> StateT DrasilState Identity (SMethod r)
-> GenState (Maybe (SMethod r))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SMethod r -> Maybe (SMethod r)
forall a. a -> Maybe a
Just) ((CodeDefinition -> StateT DrasilState Identity (SMethod r))
-> [CodeDefinition] -> [StateT DrasilState Identity (SMethod r)]
forall a b. (a -> b) -> [a] -> [b]
map CodeDefinition -> StateT DrasilState Identity (SMethod r)
forall (r :: * -> *).
OOProg r =>
CodeDefinition -> GenState (SMethod r)
genCalcFunc (CodeSpec -> [CodeDefinition]
execOrder (CodeSpec -> [CodeDefinition]) -> CodeSpec -> [CodeDefinition]
forall a b. (a -> b) -> a -> b
$ DrasilState -> CodeSpec
codeSpec DrasilState
g)
[StateT DrasilState Identity (SMethod r)]
-> [StateT DrasilState Identity (SMethod r)]
-> [StateT DrasilState Identity (SMethod r)]
forall a. [a] -> [a] -> [a]
++ (Mod -> [StateT DrasilState Identity (SMethod r)])
-> [Mod] -> [StateT DrasilState Identity (SMethod r)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Mod -> [StateT DrasilState Identity (SMethod r)]
forall (r :: * -> *). OOProg r => Mod -> [GenState (SMethod r)]
genModFuncs (DrasilState -> [Mod]
modules DrasilState
g))
[GenState (Maybe (SMethod r))]
-> [GenState (Maybe (SMethod r))] -> [GenState (Maybe (SMethod r))]
forall a. [a] -> [a] -> [a]
++ ((if Bool
cls then [] else [ScopeTag -> GenState (Maybe (SMethod r))
forall (r :: * -> *).
OOProg r =>
ScopeTag -> GenState (Maybe (SMethod r))
genInputFormat ScopeTag
Pub, ScopeTag -> GenState (Maybe (SMethod r))
forall (r :: * -> *).
OOProg r =>
ScopeTag -> GenState (Maybe (SMethod r))
genInputDerived ScopeTag
Pub,
ScopeTag -> GenState (Maybe (SMethod r))
forall (r :: * -> *).
OOProg r =>
ScopeTag -> GenState (Maybe (SMethod r))
genInputConstraints ScopeTag
Pub]) [GenState (Maybe (SMethod r))]
-> [GenState (Maybe (SMethod r))] -> [GenState (Maybe (SMethod r))]
forall a. [a] -> [a] -> [a]
++ [GenState (Maybe (SMethod r))
forall (r :: * -> *). OOProg r => GenState (Maybe (SMethod r))
genOutputFormat]))
([ClassType -> GenState (Maybe (SClass r))
forall (r :: * -> *).
OOProg r =>
ClassType -> GenState (Maybe (SClass r))
genInputClass ClassType
Auxiliary, ClassType -> GenState (Maybe (SClass r))
forall (r :: * -> *).
OOProg r =>
ClassType -> GenState (Maybe (SClass r))
genConstClass ClassType
Auxiliary]
[GenState (Maybe (SClass r))]
-> [GenState (Maybe (SClass r))] -> [GenState (Maybe (SClass r))]
forall a. [a] -> [a] -> [a]
++ (StateT DrasilState Identity (SClass r)
-> GenState (Maybe (SClass r)))
-> [StateT DrasilState Identity (SClass r)]
-> [GenState (Maybe (SClass r))]
forall a b. (a -> b) -> [a] -> [b]
map ((SClass r -> Maybe (SClass r))
-> StateT DrasilState Identity (SClass r)
-> GenState (Maybe (SClass r))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SClass r -> Maybe (SClass r)
forall a. a -> Maybe a
Just) ((Mod -> [StateT DrasilState Identity (SClass r)])
-> [Mod] -> [StateT DrasilState Identity (SClass r)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Mod -> [StateT DrasilState Identity (SClass r)]
forall (r :: * -> *). OOProg r => Mod -> [GenState (SClass r)]
genModClasses ([Mod] -> [StateT DrasilState Identity (SClass r)])
-> [Mod] -> [StateT DrasilState Identity (SClass r)]
forall a b. (a -> b) -> a -> b
$ DrasilState -> [Mod]
modules DrasilState
g))
genModules :: (OOProg r) => GenState [SFile r]
genModules :: GenState [SFile r]
genModules = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
SFile r
mn <- GenState (SFile r)
forall (r :: * -> *). OOProg r => GenState (SFile r)
genMain
[SFile r]
inp <- InputModule -> GenState [SFile r]
forall (r :: * -> *). OOProg r => InputModule -> GenState [SFile r]
chooseInModule (InputModule -> GenState [SFile r])
-> InputModule -> GenState [SFile r]
forall a b. (a -> b) -> a -> b
$ DrasilState -> InputModule
inMod DrasilState
g
[SFile r]
con <- GenState [SFile r]
forall (r :: * -> *). OOProg r => GenState [SFile r]
genConstMod
SFile r
cal <- GenState (SFile r)
forall (r :: * -> *). OOProg r => GenState (SFile r)
genCalcMod
[SFile r]
out <- GenState [SFile r]
forall (r :: * -> *). OOProg r => GenState [SFile r]
genOutputMod
[SFile r]
moddef <- (Mod -> GenState (SFile r)) -> [Mod] -> GenState [SFile r]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Mod -> GenState (SFile r)
forall (r :: * -> *). OOProg r => Mod -> GenState (SFile r)
genModDef (DrasilState -> [Mod]
modules DrasilState
g)
[SFile r] -> GenState [SFile r]
forall (m :: * -> *) a. Monad m => a -> m a
return ([SFile r] -> GenState [SFile r])
-> [SFile r] -> GenState [SFile r]
forall a b. (a -> b) -> a -> b
$ SFile r
mn SFile r -> [SFile r] -> [SFile r]
forall a. a -> [a] -> [a]
: [SFile r]
inp [SFile r] -> [SFile r] -> [SFile r]
forall a. [a] -> [a] -> [a]
++ [SFile r]
con [SFile r] -> [SFile r] -> [SFile r]
forall a. [a] -> [a] -> [a]
++ SFile r
cal SFile r -> [SFile r] -> [SFile r]
forall a. a -> [a] -> [a]
: [SFile r]
out [SFile r] -> [SFile r] -> [SFile r]
forall a. [a] -> [a] -> [a]
++ [SFile r]
moddef
getDir :: Lang -> String
getDir :: Lang -> String
getDir Cpp = "cpp"
getDir CSharp = "csharp"
getDir Java = "java"
getDir Python = "python"
getDir Swift = "swift"