-- | Defines generation functions for SCS code packages.
module Language.Drasil.Code.Imperative.Generator (
  generator, generateCode, generateCodeProc
) 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, genModuleWithImportsProc)
import Language.Drasil.Code.Imperative.GenODE (chooseODELib)
import Language.Drasil.Code.Imperative.Helpers (liftS)
import Language.Drasil.Code.Imperative.Import (genModDef, genModDefProc,
  genModFuncs, genModFuncsProc, genModClasses)
import Language.Drasil.Code.Imperative.Modules (genInputMod, genInputModProc,
  genConstClass, genConstMod, checkConstClass, genInputClass,
  genInputConstraints, genInputConstraintsProc, genInputDerived,
  genInputDerivedProc, genInputFormat, genInputFormatProc, genMain, genMainProc,
  genMainFunc, genMainFuncProc, genCalcMod, genCalcModProc, genCalcFunc,
  genCalcFuncProc, genOutputFormat, genOutputFormatProc, genOutputMod,
  genOutputModProc, genSampleInput)
import Language.Drasil.Code.Imperative.DrasilState (GenState, DrasilState(..),
  ScopeType(..), designLog, modExportMap, clsDefMap, genICName)
import Language.Drasil.Code.Imperative.GOOL.ClassInterface (PackageSym(..), AuxiliarySym(..))
import Language.Drasil.Code.Imperative.ReadMe.Import (ReadMeInfo(..))
import Language.Drasil.Code.Imperative.GOOL.Data (PackData(..), ad)
import Language.Drasil.Code.Imperative.GOOL.LanguageRenderer(sampleInputName)
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(..), InternalConcept(..))
import Language.Drasil.CodeSpec (CodeSpec(..), HasOldCodeSpec(..), getODE)
import Language.Drasil.Printers (SingleLine(OneLine), sentenceDoc)

import Drasil.GOOL (OOProg, VisibilityTag(..),
  ProgData(..), initialState)
import qualified Drasil.GOOL as OO (GSProgram, SFile, ProgramSym(..), unCI)
import Drasil.GProc (ProcProg)
import qualified Drasil.GProc as Proc (GSProgram, SFile, ProgramSym(..), unCI)
import SysInfo.Drasil hiding (sysinfodb)

import System.Directory (setCurrentDirectory, createDirectoryIfMissing,
  getCurrentDirectory)
import Control.Lens ((^.))
import Control.Monad.State (get, evalState, runState)
import qualified Data.Set as Set (fromList)
import Data.Map (fromList, member, keys, elems)
import Data.Maybe (maybeToList, catMaybes)
import Text.PrettyPrint.HughesPJ (isEmpty, vcat)

-- | Initializes the generator's 'DrasilState'.
-- 'String' parameter is a string representing the date.
-- \['Expr'\] parameter is the sample input values provided by the user.
generator :: Lang -> String -> [Expr] -> Choices -> CodeSpec -> DrasilState
generator :: Lang -> String -> [Expr] -> Choices -> CodeSpec -> DrasilState
generator Lang
l String
dt [Expr]
sd Choices
chs CodeSpec
spec = DrasilState {
  -- constants
  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,
  dsICNames :: InternalConcept -> String
dsICNames = Choices -> InternalConcept -> String
icNames Choices
chs,
  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,
  defSet :: Set String
defSet = [String] -> Set String
forall a. Ord a => [a] -> Set a
Set.fromList ([String] -> Set String) -> [String] -> Set 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,
  getVal :: Int
getVal = Choices -> Int
folderVal Choices
chs,
  -- stateful
  currentModule :: String
currentModule = String
"",
  currentClass :: String
currentClass = String
"",
  _designLog :: Doc
_designLog = Doc
des,
  _loggedSpaces :: [(Space, CodeType)]
_loggedSpaces = [], -- Used to prevent duplicate logs added to design log
  currentScope :: ScopeType
currentScope = ScopeType
Global
}
  where (MatchedConceptMap
mcm, [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 Visibility
Show = String
dt
        showDate Visibility
Hide = String
""
        ((Maybe String
pth, [(String, ExtLibState)]
elmap, (String, String)
lname), [Sentence]
libLog) = State [Sentence] ODEGenInfo
-> [Sentence] -> (ODEGenInfo, [Sentence])
forall s a. State s a -> s -> (a, s)
runState (Lang -> Maybe ODE -> State [Sentence] ODEGenInfo
chooseODELib Lang
l (Maybe ODE -> State [Sentence] ODEGenInfo)
-> Maybe ODE -> State [Sentence] ODEGenInfo
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 = OldCodeSpec -> Choices -> [Mod] -> ModExportMap
modExportMap (CodeSpec
spec CodeSpec -> Getting OldCodeSpec CodeSpec OldCodeSpec -> OldCodeSpec
forall s a. s -> Getting a s a -> a
^. Getting OldCodeSpec CodeSpec OldCodeSpec
forall c. HasOldCodeSpec c => Lens' c OldCodeSpec
Lens' CodeSpec OldCodeSpec
oldCodeSpec) 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 = OldCodeSpec -> Choices -> [Mod] -> ModExportMap
clsDefMap (CodeSpec
spec CodeSpec -> Getting OldCodeSpec CodeSpec OldCodeSpec -> OldCodeSpec
forall s a. s -> Getting a s a -> a
^. Getting OldCodeSpec CodeSpec OldCodeSpec
forall c. HasOldCodeSpec c => Lens' c OldCodeSpec
Lens' CodeSpec OldCodeSpec
oldCodeSpec) Choices
chs [Mod]
modules'
        modules' :: [Mod]
modules' = (CodeSpec
spec CodeSpec -> Getting [Mod] CodeSpec [Mod] -> [Mod]
forall s a. s -> Getting a s a -> a
^. Getting [Mod] CodeSpec [Mod]
forall c. HasOldCodeSpec c => Lens' c [Mod]
Lens' CodeSpec [Mod]
modsO) [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 -> SingleLine -> Sentence -> Doc
sentenceDoc (CodeSpec
spec CodeSpec -> Getting ChunkDB CodeSpec ChunkDB -> ChunkDB
forall s a. s -> Getting a s a -> a
^. Getting ChunkDB CodeSpec ChunkDB
forall c. HasOldCodeSpec c => Lens' c ChunkDB
Lens' CodeSpec ChunkDB
sysinfodbO) Stage
Implementation SingleLine
OneLine) ([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)

-- OO Versions --

-- | Generates a package with the given 'DrasilState'. The passed
-- un-representation functions determine which target language the package will
-- be generated in.
generateCode :: (OOProg progRepr, PackageSym packRepr) => Lang ->
  (progRepr (OO.Program progRepr) -> ProgData) -> (packRepr (Package packRepr) ->
  PackData) -> DrasilState -> IO ()
generateCode :: forall (progRepr :: * -> *) (packRepr :: * -> *).
(OOProg progRepr, PackageSym packRepr) =>
Lang
-> (progRepr (Program progRepr) -> ProgData)
-> (packRepr (Package packRepr) -> PackData)
-> DrasilState
-> IO ()
generateCode Lang
l progRepr (Program progRepr) -> ProgData
unReprProg packRepr (Package packRepr) -> PackData
unReprPack 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 (packRepr (Package packRepr)
pckg, 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
      baseAux :: [AuxData]
baseAux = [String -> Doc -> AuxData
ad String
"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)
      aux :: [AuxData]
aux
        | Lang
l Lang -> Lang -> Bool
forall a. Eq a => a -> a -> Bool
== Lang
Python = String -> Doc -> AuxData
ad String
"__init__.py" Doc
forall a. Monoid a => a
mempty AuxData -> [AuxData] -> [AuxData]
forall a. a -> [a] -> [a]
: [AuxData]
baseAux
        | Bool
otherwise   = [AuxData]
baseAux
      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) [AuxData]
aux
  Code -> IO ()
createCodeFiles Code
code
  String -> IO ()
setCurrentDirectory String
workingDir

-- | Generates a package, including a Makefile, sample input file, and Doxygen
-- configuration file (all subject to the user's choices).
-- The passed un-representation function determines which target language the
-- package will be generated in.
-- GOOL's static code analysis interpreter is called to initialize the state
-- used by the language renderer.
genPackage :: (OOProg progRepr, PackageSym packRepr) =>
  (progRepr (OO.Program progRepr) -> ProgData) ->
  GenState (packRepr (Package packRepr))
genPackage :: forall (progRepr :: * -> *) (packRepr :: * -> *).
(OOProg progRepr, PackageSym packRepr) =>
(progRepr (Program progRepr) -> ProgData)
-> GenState (packRepr (Package packRepr))
genPackage progRepr (Program progRepr) -> ProgData
unRepr = do
  DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
  State GOOLState (CodeInfoOO GOOLState)
ci <- StateT
  DrasilState Identity (State GOOLState (CodeInfoOO GOOLState))
GenState (GSProgram CodeInfoOO)
forall (r :: * -> *). OOProg r => GenState (GSProgram r)
genProgram
  State GOOLState (progRepr (Program progRepr))
p <- GenState (State GOOLState (progRepr (Program progRepr)))
forall (r :: * -> *). OOProg r => GenState (GSProgram r)
genProgram
  let info :: GOOLState
info = CodeInfoOO GOOLState -> GOOLState
forall a. CodeInfoOO a -> a
OO.unCI (CodeInfoOO GOOLState -> GOOLState)
-> CodeInfoOO GOOLState -> GOOLState
forall a b. (a -> b) -> a -> b
$ State GOOLState (CodeInfoOO GOOLState)
-> GOOLState -> CodeInfoOO GOOLState
forall s a. State s a -> s -> a
evalState State GOOLState (CodeInfoOO GOOLState)
ci GOOLState
initialState
      (progRepr (Program progRepr)
reprPD, GOOLState
s) = State GOOLState (progRepr (Program progRepr))
-> GOOLState -> (progRepr (Program progRepr), GOOLState)
forall s a. State s a -> s -> (a, s)
runState State GOOLState (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 = (Person -> String) -> [Person] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Person -> String
forall n. HasName n => n -> String
name (DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting [Person] CodeSpec [Person] -> [Person]
forall s a. s -> Getting a s a -> a
^. Getting [Person] CodeSpec [Person]
forall c. HasOldCodeSpec c => Lens' c [Person]
Lens' CodeSpec [Person]
authorsO)
      cfp :: [String]
cfp = DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting [String] CodeSpec [String] -> [String]
forall s a. s -> Getting a s a -> a
^. Getting [String] CodeSpec [String]
forall c. HasOldCodeSpec c => Lens' c [String]
Lens' CodeSpec [String]
configFilesO
      db :: ChunkDB
db = DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting ChunkDB CodeSpec ChunkDB -> ChunkDB
forall s a. s -> Getting a s a -> a
^. Getting ChunkDB CodeSpec ChunkDB
forall c. HasOldCodeSpec c => Lens' c ChunkDB
Lens' CodeSpec ChunkDB
sysinfodbO
      -- prps = show $ sentenceDoc db Implementation OneLine
      --   (foldlSent $ purpose $ codeSpec g)
      prps :: String
prps = Doc -> String
forall a. Show a => a -> String
show (Doc -> String) -> Doc -> String
forall a b. (a -> b) -> a -> b
$ ChunkDB -> Stage -> SingleLine -> Sentence -> Doc
sentenceDoc ChunkDB
db Stage
Implementation SingleLine
OneLine 
        ([Sentence] -> Sentence
foldlSent ([Sentence] -> Sentence) -> [Sentence] -> Sentence
forall a b. (a -> b) -> a -> b
$ DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting [Sentence] CodeSpec [Sentence] -> [Sentence]
forall s a. s -> Getting a s a -> a
^. Getting [Sentence] CodeSpec [Sentence]
forall c. HasSystemInformation c => Lens' c [Sentence]
Lens' CodeSpec [Sentence]
purpose)  
      bckgrnd :: String
bckgrnd = Doc -> String
forall a. Show a => a -> String
show (Doc -> String) -> Doc -> String
forall a b. (a -> b) -> a -> b
$ ChunkDB -> Stage -> SingleLine -> Sentence -> Doc
sentenceDoc ChunkDB
db Stage
Implementation SingleLine
OneLine
        ([Sentence] -> Sentence
foldlSent ([Sentence] -> Sentence) -> [Sentence] -> Sentence
forall a b. (a -> b) -> a -> b
$ DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting [Sentence] CodeSpec [Sentence] -> [Sentence]
forall s a. s -> Getting a s a -> a
^. Getting [Sentence] CodeSpec [Sentence]
forall c. HasSystemInformation c => Lens' c [Sentence]
Lens' CodeSpec [Sentence]
background)
      mtvtn :: String
mtvtn = Doc -> String
forall a. Show a => a -> String
show (Doc -> String) -> Doc -> String
forall a b. (a -> b) -> a -> b
$ ChunkDB -> Stage -> SingleLine -> Sentence -> Doc
sentenceDoc ChunkDB
db Stage
Implementation SingleLine
OneLine
        ([Sentence] -> Sentence
foldlSent ([Sentence] -> Sentence) -> [Sentence] -> Sentence
forall a b. (a -> b) -> a -> b
$ DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting [Sentence] CodeSpec [Sentence] -> [Sentence]
forall s a. s -> Getting a s a -> a
^. Getting [Sentence] CodeSpec [Sentence]
forall c. HasSystemInformation c => Lens' c [Sentence]
Lens' CodeSpec [Sentence]
motivation)
      scp :: String
scp = Doc -> String
forall a. Show a => a -> String
show (Doc -> String) -> Doc -> String
forall a b. (a -> b) -> a -> b
$ ChunkDB -> Stage -> SingleLine -> Sentence -> Doc
sentenceDoc ChunkDB
db Stage
Implementation SingleLine
OneLine
        ([Sentence] -> Sentence
foldlSent ([Sentence] -> Sentence) -> [Sentence] -> Sentence
forall a b. (a -> b) -> a -> b
$ DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting [Sentence] CodeSpec [Sentence] -> [Sentence]
forall s a. s -> Getting a s a -> a
^. Getting [Sentence] CodeSpec [Sentence]
forall c. HasSystemInformation c => Lens' c [Sentence]
Lens' CodeSpec [Sentence]
scope)
  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 {
        langName :: String
langName = String
"",
        langVersion :: String
langVersion = String
"",
        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 = String
"",
        examplePurpose :: String
examplePurpose = String
prps,
        exampleDescr :: String
exampleDescr = String
bckgrnd,
        exampleMotivation :: String
exampleMotivation = String
mtvtn,
        exampleScope :: String
exampleScope = String
scp,
        folderNum :: Int
folderNum = DrasilState -> Int
getVal DrasilState
g,
        inputOutput :: (String, String)
inputOutput = (String
sampleInputName, String
"output.txt")} -- This needs a more permanent solution
  packRepr (Package packRepr)
-> GenState (packRepr (Package packRepr))
forall a. a -> StateT DrasilState Identity a
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])

-- | Generates an SCS program based on the problem and the user's design choices.
genProgram :: (OOProg r) => GenState (OO.GSProgram r)
genProgram :: forall (r :: * -> *). OOProg r => 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 -> StateT DrasilState Identity [FS (r (File r))]
forall (r :: * -> *). OOProg r => Modularity -> GenState [SFile r]
chooseModules (Modularity -> StateT DrasilState Identity [FS (r (File r))])
-> Modularity -> StateT DrasilState Identity [FS (r (File r))]
forall a b. (a -> b) -> a -> b
$ DrasilState -> Modularity
modular DrasilState
g
  let n :: String
n = DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting String CodeSpec String -> String
forall s a. s -> Getting a s a -> a
^. Getting String CodeSpec String
forall c. HasOldCodeSpec c => Lens' c String
Lens' CodeSpec String
pNameO 
  let p :: String
p = Doc -> String
forall a. Show a => a -> String
show (Doc -> String) -> Doc -> String
forall a b. (a -> b) -> a -> b
$ ChunkDB -> Stage -> SingleLine -> Sentence -> Doc
sentenceDoc (DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting ChunkDB CodeSpec ChunkDB -> ChunkDB
forall s a. s -> Getting a s a -> a
^. Getting ChunkDB CodeSpec ChunkDB
forall c. HasOldCodeSpec c => Lens' c ChunkDB
Lens' CodeSpec ChunkDB
sysinfodbO) Stage
Implementation SingleLine
OneLine (Sentence -> Doc) -> Sentence -> Doc
forall a b. (a -> b) -> a -> b
$ [Sentence] -> Sentence
foldlSent ([Sentence] -> Sentence) -> [Sentence] -> Sentence
forall a b. (a -> b) -> a -> b
$ DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting [Sentence] CodeSpec [Sentence] -> [Sentence]
forall s a. s -> Getting a s a -> a
^. Getting [Sentence] CodeSpec [Sentence]
forall c. HasSystemInformation c => Lens' c [Sentence]
Lens' CodeSpec [Sentence]
purpose
  GSProgram r -> GenState (GSProgram r)
forall a. a -> StateT DrasilState Identity a
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 -> String -> [FS (r (File r))] -> GSProgram r
forall (r :: * -> *).
ProgramSym r =>
String -> String -> [SFile r] -> GSProgram r
OO.prog String
n String
p [FS (r (File r))]
ms

-- | Generates either a single module or many modules, based on the users choice
-- of modularity.
chooseModules :: (OOProg r) => Modularity -> GenState [OO.SFile r]
chooseModules :: forall (r :: * -> *). OOProg r => Modularity -> GenState [SFile r]
chooseModules Modularity
Unmodular = State DrasilState (FS (r (File r)))
-> StateT DrasilState Identity [FS (r (File r))]
forall a b. State a b -> State a [b]
liftS State DrasilState (FS (r (File r)))
forall (r :: * -> *). OOProg r => GenState (SFile r)
genUnmodular
chooseModules Modularity
Modular = StateT DrasilState Identity [FS (r (File r))]
forall (r :: * -> *). OOProg r => GenState [SFile r]
genModules

-- | Generates an entire SCS program as a single module.
genUnmodular :: (OOProg r) => GenState (OO.SFile r)
genUnmodular :: forall (r :: * -> *). OOProg r => 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
  String
giName <- InternalConcept -> GenState String
genICName InternalConcept
GetInput
  String
dvName <- InternalConcept -> GenState String
genICName InternalConcept
DerivedValuesFn
  String
icName <- InternalConcept -> GenState String
genICName InternalConcept
InputConstraintsFn
  let n :: String
n = DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting String CodeSpec String -> String
forall s a. s -> Getting a s a -> a
^. Getting String CodeSpec String
forall c. HasOldCodeSpec c => Lens' c String
Lens' CodeSpec String
pNameO
      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) [String
giName, String
dvName, String
icName]
  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 a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
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 (DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec
-> Getting [CodeDefinition] CodeSpec [CodeDefinition]
-> [CodeDefinition]
forall s a. s -> Getting a s a -> a
^. Getting [CodeDefinition] CodeSpec [CodeDefinition]
forall c. HasOldCodeSpec c => Lens' c [CodeDefinition]
Lens' CodeSpec [CodeDefinition]
execOrderO)
        [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 [VisibilityTag -> GenState (Maybe (SMethod r))
forall (r :: * -> *).
OOProg r =>
VisibilityTag -> GenState (Maybe (SMethod r))
genInputFormat VisibilityTag
Pub, VisibilityTag -> GenState (Maybe (SMethod r))
forall (r :: * -> *).
OOProg r =>
VisibilityTag -> GenState (Maybe (SMethod r))
genInputDerived VisibilityTag
Pub,
        VisibilityTag -> GenState (Maybe (SMethod r))
forall (r :: * -> *).
OOProg r =>
VisibilityTag -> GenState (Maybe (SMethod r))
genInputConstraints VisibilityTag
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 a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
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))

-- | Generates all modules for an SCS program.
genModules :: (OOProg r) => GenState [OO.SFile r]
genModules :: forall (r :: * -> *). OOProg r => 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    <- GenState [SFile r]
forall (r :: * -> *). OOProg r => GenState [SFile r]
genInputMod
  [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)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Mod -> GenState (SFile r)
forall (r :: * -> *). OOProg r => Mod -> GenState (SFile r)
genModDef (DrasilState -> [Mod]
modules DrasilState
g) -- hack ?
  [SFile r] -> GenState [SFile r]
forall a. a -> StateT DrasilState Identity a
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

-- Procedural Versions --
-- | Generates a package with the given 'DrasilState'. The passed
-- un-representation functions determine which target language the package will
-- be generated in.
generateCodeProc :: (ProcProg progRepr, PackageSym packRepr) => Lang ->
  (progRepr (Proc.Program progRepr) -> ProgData) -> (packRepr (Package packRepr) ->
  PackData) -> DrasilState -> IO ()
generateCodeProc :: forall (progRepr :: * -> *) (packRepr :: * -> *).
(ProcProg progRepr, PackageSym packRepr) =>
Lang
-> (progRepr (Program progRepr) -> ProgData)
-> (packRepr (Package packRepr) -> PackData)
-> DrasilState
-> IO ()
generateCodeProc Lang
l progRepr (Program progRepr) -> ProgData
unReprProg packRepr (Package packRepr) -> PackData
unReprPack 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 (packRepr (Package packRepr)
pckg, 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 :: * -> *).
(ProcProg progRepr, PackageSym packRepr) =>
(progRepr (Program progRepr) -> ProgData)
-> GenState (packRepr (Package packRepr))
genPackageProc progRepr (Program progRepr) -> ProgData
unReprProg) DrasilState
g
      baseAux :: [AuxData]
baseAux = [String -> Doc -> AuxData
ad String
"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 :: 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) [AuxData]
baseAux
  Code -> IO ()
createCodeFiles Code
code
  String -> IO ()
setCurrentDirectory String
workingDir

-- | Generates a package, including a Makefile, sample input file, and Doxygen
-- configuration file (all subject to the user's choices).
-- The passed un-representation function determines which target language the
-- package will be generated in.
-- GOOL's static code analysis interpreter is called to initialize the state
-- used by the language renderer.
genPackageProc :: (ProcProg progRepr, PackageSym packRepr) =>
  (progRepr (Proc.Program progRepr) -> ProgData) ->
  GenState (packRepr (Package packRepr))
genPackageProc :: forall (progRepr :: * -> *) (packRepr :: * -> *).
(ProcProg progRepr, PackageSym packRepr) =>
(progRepr (Program progRepr) -> ProgData)
-> GenState (packRepr (Package packRepr))
genPackageProc progRepr (Program progRepr) -> ProgData
unRepr = do
  DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
  State GOOLState (CodeInfoProc GOOLState)
ci <- StateT
  DrasilState Identity (State GOOLState (CodeInfoProc GOOLState))
GenState (GSProgram CodeInfoProc)
forall (r :: * -> *). ProcProg r => GenState (GSProgram r)
genProgramProc
  State GOOLState (progRepr (Program progRepr))
p <- GenState (State GOOLState (progRepr (Program progRepr)))
forall (r :: * -> *). ProcProg r => GenState (GSProgram r)
genProgramProc
  let info :: GOOLState
info = CodeInfoProc GOOLState -> GOOLState
forall a. CodeInfoProc a -> a
Proc.unCI (CodeInfoProc GOOLState -> GOOLState)
-> CodeInfoProc GOOLState -> GOOLState
forall a b. (a -> b) -> a -> b
$ State GOOLState (CodeInfoProc GOOLState)
-> GOOLState -> CodeInfoProc GOOLState
forall s a. State s a -> s -> a
evalState State GOOLState (CodeInfoProc GOOLState)
ci GOOLState
initialState
      (progRepr (Program progRepr)
reprPD, GOOLState
s) = State GOOLState (progRepr (Program progRepr))
-> GOOLState -> (progRepr (Program progRepr), GOOLState)
forall s a. State s a -> s -> (a, s)
runState State GOOLState (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 = (Person -> String) -> [Person] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Person -> String
forall n. HasName n => n -> String
name (DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting [Person] CodeSpec [Person] -> [Person]
forall s a. s -> Getting a s a -> a
^. Getting [Person] CodeSpec [Person]
forall c. HasOldCodeSpec c => Lens' c [Person]
Lens' CodeSpec [Person]
authorsO)
      cfp :: [String]
cfp = DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting [String] CodeSpec [String] -> [String]
forall s a. s -> Getting a s a -> a
^. Getting [String] CodeSpec [String]
forall c. HasOldCodeSpec c => Lens' c [String]
Lens' CodeSpec [String]
configFilesO
      db :: ChunkDB
db = DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting ChunkDB CodeSpec ChunkDB -> ChunkDB
forall s a. s -> Getting a s a -> a
^. Getting ChunkDB CodeSpec ChunkDB
forall c. HasOldCodeSpec c => Lens' c ChunkDB
Lens' CodeSpec ChunkDB
sysinfodbO
      prps :: String
prps = Doc -> String
forall a. Show a => a -> String
show (Doc -> String) -> Doc -> String
forall a b. (a -> b) -> a -> b
$ ChunkDB -> Stage -> SingleLine -> Sentence -> Doc
sentenceDoc ChunkDB
db Stage
Implementation SingleLine
OneLine
        ([Sentence] -> Sentence
foldlSent ([Sentence] -> Sentence) -> [Sentence] -> Sentence
forall a b. (a -> b) -> a -> b
$ DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting [Sentence] CodeSpec [Sentence] -> [Sentence]
forall s a. s -> Getting a s a -> a
^. Getting [Sentence] CodeSpec [Sentence]
forall c. HasSystemInformation c => Lens' c [Sentence]
Lens' CodeSpec [Sentence]
purpose)
      bckgrnd :: String
bckgrnd = Doc -> String
forall a. Show a => a -> String
show (Doc -> String) -> Doc -> String
forall a b. (a -> b) -> a -> b
$ ChunkDB -> Stage -> SingleLine -> Sentence -> Doc
sentenceDoc ChunkDB
db Stage
Implementation SingleLine
OneLine
        ([Sentence] -> Sentence
foldlSent ([Sentence] -> Sentence) -> [Sentence] -> Sentence
forall a b. (a -> b) -> a -> b
$ DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting [Sentence] CodeSpec [Sentence] -> [Sentence]
forall s a. s -> Getting a s a -> a
^. Getting [Sentence] CodeSpec [Sentence]
forall c. HasSystemInformation c => Lens' c [Sentence]
Lens' CodeSpec [Sentence]
background)
      mtvtn :: String
mtvtn = Doc -> String
forall a. Show a => a -> String
show (Doc -> String) -> Doc -> String
forall a b. (a -> b) -> a -> b
$ ChunkDB -> Stage -> SingleLine -> Sentence -> Doc
sentenceDoc ChunkDB
db Stage
Implementation SingleLine
OneLine
        ([Sentence] -> Sentence
foldlSent ([Sentence] -> Sentence) -> [Sentence] -> Sentence
forall a b. (a -> b) -> a -> b
$ DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting [Sentence] CodeSpec [Sentence] -> [Sentence]
forall s a. s -> Getting a s a -> a
^. Getting [Sentence] CodeSpec [Sentence]
forall c. HasSystemInformation c => Lens' c [Sentence]
Lens' CodeSpec [Sentence]
motivation)
      scp :: String
scp = Doc -> String
forall a. Show a => a -> String
show (Doc -> String) -> Doc -> String
forall a b. (a -> b) -> a -> b
$ ChunkDB -> Stage -> SingleLine -> Sentence -> Doc
sentenceDoc ChunkDB
db Stage
Implementation SingleLine
OneLine
        ([Sentence] -> Sentence
foldlSent ([Sentence] -> Sentence) -> [Sentence] -> Sentence
forall a b. (a -> b) -> a -> b
$ DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting [Sentence] CodeSpec [Sentence] -> [Sentence]
forall s a. s -> Getting a s a -> a
^. Getting [Sentence] CodeSpec [Sentence]
forall c. HasSystemInformation c => Lens' c [Sentence]
Lens' CodeSpec [Sentence]
scope)
  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 {
        langName :: String
langName = String
"",
        langVersion :: String
langVersion = String
"",
        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 = String
"",
        examplePurpose :: String
examplePurpose = String
prps,
        exampleDescr :: String
exampleDescr = String
bckgrnd,
        exampleMotivation :: String
exampleMotivation = String
mtvtn,
        exampleScope :: String
exampleScope = String
scp,
        folderNum :: Int
folderNum = DrasilState -> Int
getVal DrasilState
g,
        inputOutput :: (String, String)
inputOutput = (String
sampleInputName, String
"output.txt")} -- This needs a more permanent solution
  packRepr (Package packRepr)
-> GenState (packRepr (Package packRepr))
forall a. a -> StateT DrasilState Identity a
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])

-- | Generates an SCS program based on the problem and the user's design choices.
genProgramProc :: (ProcProg r) => GenState (Proc.GSProgram r)
genProgramProc :: forall (r :: * -> *). ProcProg r => GenState (GSProgram r)
genProgramProc = do
  DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
  [FS (r (File r))]
ms <- Modularity -> StateT DrasilState Identity [FS (r (File r))]
forall (r :: * -> *).
ProcProg r =>
Modularity -> GenState [SFile r]
chooseModulesProc (Modularity -> StateT DrasilState Identity [FS (r (File r))])
-> Modularity -> StateT DrasilState Identity [FS (r (File r))]
forall a b. (a -> b) -> a -> b
$ DrasilState -> Modularity
modular DrasilState
g
  let n :: String
n = DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting String CodeSpec String -> String
forall s a. s -> Getting a s a -> a
^. Getting String CodeSpec String
forall c. HasOldCodeSpec c => Lens' c String
Lens' CodeSpec String
pNameO
  let p :: String
p = Doc -> String
forall a. Show a => a -> String
show (Doc -> String) -> Doc -> String
forall a b. (a -> b) -> a -> b
$ ChunkDB -> Stage -> SingleLine -> Sentence -> Doc
sentenceDoc (DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting ChunkDB CodeSpec ChunkDB -> ChunkDB
forall s a. s -> Getting a s a -> a
^. Getting ChunkDB CodeSpec ChunkDB
forall c. HasOldCodeSpec c => Lens' c ChunkDB
Lens' CodeSpec ChunkDB
sysinfodbO) Stage
Implementation SingleLine
OneLine (Sentence -> Doc) -> Sentence -> Doc
forall a b. (a -> b) -> a -> b
$ [Sentence] -> Sentence
foldlSent ([Sentence] -> Sentence) -> [Sentence] -> Sentence
forall a b. (a -> b) -> a -> b
$ DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting [Sentence] CodeSpec [Sentence] -> [Sentence]
forall s a. s -> Getting a s a -> a
^. Getting [Sentence] CodeSpec [Sentence]
forall c. HasSystemInformation c => Lens' c [Sentence]
Lens' CodeSpec [Sentence]
purpose
  GSProgram r -> GenState (GSProgram r)
forall a. a -> StateT DrasilState Identity a
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 -> String -> [FS (r (File r))] -> GSProgram r
forall (r :: * -> *).
ProgramSym r =>
String -> String -> [SFile r] -> GSProgram r
Proc.prog String
n String
p [FS (r (File r))]
ms

-- | Generates either a single module or many modules, based on the users choice
-- of modularity.
chooseModulesProc :: (ProcProg r) => Modularity -> GenState [Proc.SFile r]
chooseModulesProc :: forall (r :: * -> *).
ProcProg r =>
Modularity -> GenState [SFile r]
chooseModulesProc Modularity
Unmodular = State DrasilState (FS (r (File r)))
-> StateT DrasilState Identity [FS (r (File r))]
forall a b. State a b -> State a [b]
liftS State DrasilState (FS (r (File r)))
forall (r :: * -> *). ProcProg r => GenState (SFile r)
genUnmodularProc
chooseModulesProc Modularity
Modular = StateT DrasilState Identity [FS (r (File r))]
forall (r :: * -> *). ProcProg r => GenState [SFile r]
genModulesProc

-- | Generates an entire SCS program as a single module.
genUnmodularProc :: (ProcProg r) => GenState (Proc.SFile r)
genUnmodularProc :: forall (r :: * -> *). ProcProg r => GenState (SFile r)
genUnmodularProc = do
  DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
  String
umDesc <- GenState String
unmodularDesc
  String
giName <- InternalConcept -> GenState String
genICName InternalConcept
GetInput
  String
dvName <- InternalConcept -> GenState String
genICName InternalConcept
DerivedValuesFn
  String
icName <- InternalConcept -> GenState String
genICName InternalConcept
InputConstraintsFn
  let n :: String
n = DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting String CodeSpec String -> String
forall s a. s -> Getting a s a -> a
^. Getting String CodeSpec String
forall c. HasOldCodeSpec c => Lens' c String
Lens' CodeSpec String
pNameO
      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) [String
giName, String
dvName, String
icName]
  if Bool
cls then String -> GenState (SFile r)
forall a. HasCallStack => String -> a
error String
"genUnmodularProc: Procedural renderers do not support classes"
  else String
-> String
-> [String]
-> [GenState (Maybe (SMethod r))]
-> GenState (SFile r)
forall (r :: * -> *).
ProcProg r =>
String
-> String
-> [String]
-> [GenState (Maybe (SMethod r))]
-> GenState (SFile r)
genModuleWithImportsProc 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 :: * -> *). SharedProg r => GenState (Maybe (SMethod r))
genMainFuncProc
          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 a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
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 :: * -> *).
SharedProg r =>
CodeDefinition -> GenState (SMethod r)
genCalcFuncProc (DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec
-> Getting [CodeDefinition] CodeSpec [CodeDefinition]
-> [CodeDefinition]
forall s a. s -> Getting a s a -> a
^. Getting [CodeDefinition] CodeSpec [CodeDefinition]
forall c. HasOldCodeSpec c => Lens' c [CodeDefinition]
Lens' CodeSpec [CodeDefinition]
execOrderO)
            [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 :: * -> *). SharedProg r => Mod -> [GenState (SMethod r)]
genModFuncsProc (DrasilState -> [Mod]
modules DrasilState
g))
          [GenState (Maybe (SMethod r))]
-> [GenState (Maybe (SMethod r))] -> [GenState (Maybe (SMethod r))]
forall a. [a] -> [a] -> [a]
++ ([VisibilityTag -> GenState (Maybe (SMethod r))
forall (r :: * -> *).
SharedProg r =>
VisibilityTag -> GenState (Maybe (SMethod r))
genInputFormatProc VisibilityTag
Pub, VisibilityTag -> GenState (Maybe (SMethod r))
forall (r :: * -> *).
SharedProg r =>
VisibilityTag -> GenState (Maybe (SMethod r))
genInputDerivedProc VisibilityTag
Pub,
              VisibilityTag -> GenState (Maybe (SMethod r))
forall (r :: * -> *).
SharedProg r =>
VisibilityTag -> GenState (Maybe (SMethod r))
genInputConstraintsProc VisibilityTag
Pub] [GenState (Maybe (SMethod r))]
-> [GenState (Maybe (SMethod r))] -> [GenState (Maybe (SMethod r))]
forall a. [a] -> [a] -> [a]
++ [GenState (Maybe (SMethod r))
forall (r :: * -> *). SharedProg r => GenState (Maybe (SMethod r))
genOutputFormatProc]))

-- | Generates all modules for an SCS program.
genModulesProc :: (ProcProg r) => GenState [Proc.SFile r]
genModulesProc :: forall (r :: * -> *). ProcProg r => GenState [SFile r]
genModulesProc = do
  DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
  SFile r
mn     <- GenState (SFile r)
forall (r :: * -> *). ProcProg r => GenState (SFile r)
genMainProc
  [SFile r]
inp    <- GenState [SFile r]
forall (r :: * -> *). ProcProg r => GenState [SFile r]
genInputModProc
  Bool
con    <- GenState Bool
checkConstClass
  SFile r
cal    <- GenState (SFile r)
forall (r :: * -> *). ProcProg r => GenState (SFile r)
genCalcModProc
  [SFile r]
out    <- GenState [SFile r]
forall (r :: * -> *). ProcProg r => GenState [SFile r]
genOutputModProc
  [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)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Mod -> GenState (SFile r)
forall (r :: * -> *). ProcProg r => Mod -> GenState (SFile r)
genModDefProc (DrasilState -> [Mod]
modules DrasilState
g) -- hack ?
  if Bool
con then String -> GenState [SFile r]
forall a. HasCallStack => String -> a
error String
"genModulesProc: Procedural renderers do not support classes"
  else [SFile r] -> GenState [SFile r]
forall a. a -> StateT DrasilState Identity a
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
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

-- | Private utilities used in 'generateCode'.
getDir :: Lang -> String
getDir :: Lang -> String
getDir Lang
Cpp = String
"cpp"
getDir Lang
CSharp = String
"csharp"
getDir Lang
Java = String
"java"
getDir Lang
Python = String
"python"
getDir Lang
Swift = String
"swift"
getDir Lang
Julia = String
"julia"