Skip to content

Commit

Permalink
Refactored access to sysinfodb using lens in CodeSpec
Browse files Browse the repository at this point in the history
  • Loading branch information
Xinlu-Y committed Sep 27, 2024
1 parent 6e7045b commit 10ae63b
Show file tree
Hide file tree
Showing 14 changed files with 136 additions and 132 deletions.
7 changes: 4 additions & 3 deletions code/drasil-code/lib/Language/Drasil/Code.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,8 +9,8 @@ module Language.Drasil.Code (
OptionalFeatures(..), makeOptFeats, ExtLib(..), ImplementationType(..), Logging(..),
Modularity(..), Structure(..), ConstantStructure(..), ConstantRepr(..),
CodeConcept(..), matchConcepts, SpaceMatch, matchSpaces, AuxFile(..),
getSampleData, Visibility(..), defaultChoices, CodeSpec(..), funcUID, asVC,
codeSpec, ($:=), Mod(Mod), StateVariable, Func, FuncStmt(..), pubStateVar,
getSampleData, Visibility(..), defaultChoices, CodeSpec(..), OldCodeSpec(..), codeSpec,
HasOldCodeSpec(..), funcUID, asVC, ($:=), Mod(Mod), StateVariable, Func, FuncStmt(..), pubStateVar,
privStateVar, fDecDef, ffor, fforRange, funcData, funcDef, packmod,
junkLine, multiLine, repeated, singleLine, singleton,
ExternalLibrary, Step, FunctionInterface, Argument, externalLib, choiceSteps,
Expand Down Expand Up @@ -93,7 +93,8 @@ import Language.Drasil.Choices (Choices(..), Comments(..), Verbosity(..),
makeDocConfig, makeLogConfig, LogConfig(..), OptionalFeatures(..),
makeOptFeats, ExtLib(..))

import Language.Drasil.CodeSpec (CodeSpec(..), funcUID, asVC, codeSpec)
import Language.Drasil.CodeSpec (CodeSpec(..), OldCodeSpec(..), HasOldCodeSpec(..),
codeSpec, funcUID, asVC)

import Language.Drasil.Mod (($:=), Mod(Mod), StateVariable, Func, FuncStmt(..),
pubStateVar, privStateVar, fDecDef, ffor, fforRange, funcData, funcDef, packmod)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ module Language.Drasil.Code.Imperative.Comments (
import Language.Drasil
import Database.Drasil (defTable)
import Language.Drasil.Code.Imperative.DrasilState (GenState, DrasilState(..))
import Language.Drasil.CodeSpec (CodeSpec(..))
import Language.Drasil.CodeSpec (HasOldCodeSpec(..))
import Language.Drasil.Printers (SingleLine(OneLine), sentenceDoc, unitDoc)

import qualified Data.Map as Map (lookup)
Expand All @@ -18,7 +18,7 @@ import Text.PrettyPrint.HughesPJ (Doc, (<+>), colon, empty, parens, render)
getTermDoc :: (CodeIdea c) => c -> GenState Doc
getTermDoc c = do
g <- get
let db = sysinfodb $ codeSpec g
let db = codeSpec g ^. sysinfodbO
return $ sentenceDoc db Implementation OneLine $ phraseNP $ codeChunk c ^. term

-- | Gets a plain rendering of the definition of a chunk, preceded by a colon
Expand All @@ -27,7 +27,7 @@ getTermDoc c = do
getDefnDoc :: (CodeIdea c) => c -> GenState Doc
getDefnDoc c = do
g <- get
let db = sysinfodb $ codeSpec g
let db = codeSpec g ^. sysinfodbO
return $ maybe empty ((<+>) colon . sentenceDoc db Implementation OneLine .
(^. defn) . fst) (Map.lookup (codeChunk c ^. uid) $ defTable db)

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ import Language.Drasil.Code.Imperative.DrasilState (GenState, DrasilState(..),
genICName)
import Language.Drasil.Choices (ImplementationType(..), Structure(..),
InternalConcept(..))
import Language.Drasil.CodeSpec (CodeSpec(..), sysInfo)
import Language.Drasil.CodeSpec (HasOldCodeSpec(..))
import Language.Drasil.Mod (Description)
import Language.Drasil.Printers (SingleLine(OneLine), sentenceDoc)

Expand All @@ -40,8 +40,8 @@ unmodularDesc = do
let spec = codeSpec g
implTypeStr Program = "program"
implTypeStr Library = "library"
return $ show $ sentenceDoc (sysinfodb spec) Implementation OneLine $ capSent $
foldlSent ([S "a", S (implTypeStr (implType g)), S "to"] ++ codeSpec g ^. sysInfo .purpose)
return $ show $ sentenceDoc (spec ^. sysinfodbO) Implementation OneLine $ capSent $
foldlSent ([S "a", S (implTypeStr (implType g)), S "to"] ++ codeSpec g ^. purpose)

-- | Returns description of what is contained in the Input Parameters module.
-- If user chooses the 'Bundled' input parameter, this module will include the structure for holding the
Expand Down Expand Up @@ -122,7 +122,7 @@ constModDesc = do
let cDesc [] = ""
cDesc _ = "the structure for holding constant values"
return $ cDesc $ filter (flip member (Map.filter (cname ==)
(clsMap g)) . codeName) (constants $ codeSpec g)
(clsMap g)) . codeName) (codeSpec g ^. constantsO)

-- | Returns a description of what is contained in the Output Format module,
-- if it exists.
Expand All @@ -146,9 +146,9 @@ inputClassDesc = do
inIPMap = filter ((`member` ipMap) . codeName)
inClassD True = ""
inClassD _ = "Structure for holding the " ++ stringList [
inPs $ inIPMap $ extInputs $ codeSpec g,
dVs $ inIPMap $ map quantvar $ derivedInputs $ codeSpec g,
cVs $ inIPMap $ map quantvar $ constants $ codeSpec g]
inPs $ inIPMap $ codeSpec g ^. extInputsO,
dVs $ inIPMap $ map quantvar $ codeSpec g ^. derivedInputsO,
cVs $ inIPMap $ map quantvar $ codeSpec g ^. constantsO]
inPs [] = ""
inPs _ = "input values"
dVs [] = ""
Expand All @@ -167,7 +167,7 @@ constClassDesc = do
let ccDesc [] = ""
ccDesc _ = "Structure for holding the constant values"
return $ ccDesc $ filter (flip member (Map.filter (cname ==)
(clsMap g)) . codeName) (constants $ codeSpec g)
(clsMap g)) . codeName) (codeSpec g ^. constantsO)

-- | Returns a description for the generated function that reads input from a
-- file, if it exists.
Expand Down Expand Up @@ -221,8 +221,8 @@ woFuncDesc = do
physAndSfwrCons :: GenState Description
physAndSfwrCons = do
g <- get
let cns = concat $ mapMaybe ((`Map.lookup` (cMap $ codeSpec g)) . (^. uid))
(inputs $ codeSpec g)
let cns = concat $ mapMaybe ((`Map.lookup` (codeSpec g ^. cMapO)) . (^. uid))
(codeSpec g ^. inputsO)
return $ stringList [
if not (any isPhysC cns) then "" else "physical constraints",
if not (any isSfwrC cns) then "" else "software constraints"]
36 changes: 18 additions & 18 deletions code/drasil-code/lib/Language/Drasil/Code/Imperative/DrasilState.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ import Language.Drasil.Choices (Choices(..), Architecture (..), DataInfo(..),
MatchedConceptMap, ConstantRepr, ConstantStructure(..), ConstraintBehaviour, Logging,
Structure(..), InternalConcept(..))
import Language.Drasil.CodeSpec (Input, Const, Derived, Output, Def,
CodeSpec(..), getConstraints)
CodeSpec(..), OldCodeSpec(..), getConstraints)
import Language.Drasil.Mod (Mod(..), Name, Version, Class(..),
StateVariable(..), fname)

Expand Down Expand Up @@ -100,23 +100,23 @@ addLoggedSpace s t = over loggedSpaces ((s,t):)

-- | Builds the module export map, mapping each function and state variable name
-- in the generated code to the name of the generated module that exports it.
modExportMap :: CodeSpec -> Choices -> [Mod] -> ModExportMap
modExportMap cs@CodeSpec {
pName = prn,
inputs = ins,
extInputs = extIns,
derivedInputs = ds,
constants = cns
modExportMap :: OldCodeSpec -> Choices -> [Mod] -> ModExportMap
modExportMap cs@OldCodeSpec {
_pName = prn,
_inputs = ins,
_extInputs = extIns,
_derivedInputs = ds,
_constants = cns
} chs@Choices {
architecture = m
} ms = fromList $ nubOrd $ concatMap mpair ms
++ getExpInput prn chs ins
++ getExpConstants prn chs cns
++ getExpDerived prn chs ds
++ getExpConstraints prn chs (getConstraints (cMap cs) ins)
++ getExpConstraints prn chs (getConstraints (_cMap cs) ins)
++ getExpInputFormat prn chs extIns
++ getExpCalcs prn chs (execOrder cs)
++ getExpOutput prn chs (outputs cs)
++ getExpCalcs prn chs (_execOrder cs)
++ getExpOutput prn chs (_outputs cs)
where mpair (Mod n _ _ cls fs) = map
(, defModName (modularity m) n)
(map className cls
Expand All @@ -127,17 +127,17 @@ modExportMap cs@CodeSpec {

-- | Builds the class definition map, mapping each generated method and state
-- variable name to the name of the generated class where it is defined.
clsDefMap :: CodeSpec -> Choices -> [Mod] -> ClassDefinitionMap
clsDefMap cs@CodeSpec {
inputs = ins,
extInputs = extIns,
derivedInputs = ds,
constants = cns
clsDefMap :: OldCodeSpec -> Choices -> [Mod] -> ClassDefinitionMap
clsDefMap cs@OldCodeSpec {
_inputs = ins,
_extInputs = extIns,
_derivedInputs = ds,
_constants = cns
} chs ms = fromList $ nub $ concatMap modClasses ms
++ getInputCls chs ins
++ getConstantsCls chs cns
++ getDerivedCls chs ds
++ getConstraintsCls chs (getConstraints (cMap cs) ins)
++ getConstraintsCls chs (getConstraints (_cMap cs) ins)
++ getInputFormatCls chs extIns
where modClasses (Mod _ _ _ cls _) = concatMap (\cl ->
let cln = className cl in
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ import Language.Drasil.Code.Imperative.DrasilState (GenState, DrasilState(..))
import Language.Drasil.Code.Imperative.GOOL.ClassInterface (AuxiliarySym(..))
import Language.Drasil.Code.Imperative.ReadMe.Import (ReadMeInfo(..))
import Language.Drasil.Choices (Comments(..), AuxFile(..))
import Language.Drasil.CodeSpec (CodeSpec(..))
import Language.Drasil.CodeSpec (HasOldCodeSpec(..))
import Language.Drasil.Mod (Name, Description, Import)

import Drasil.GOOL (VSType, SVariable, SValue, MSStatement, SMethod,
Expand All @@ -26,6 +26,7 @@ import Data.Bifunctor (second)
import qualified Data.Map as Map (lookup)
import Data.Maybe (catMaybes)
import Control.Monad.State (get, modify)
import Control.Lens ((^.))

-- | Defines a GOOL module. If the user chose 'CommentMod', the module will have
-- Doxygen comments. If the user did not choose 'CommentMod' but did choose
Expand All @@ -38,8 +39,7 @@ genModuleWithImports :: (OOProg r) => Name -> Description -> [Import] ->
genModuleWithImports n desc is maybeMs maybeCs = do
g <- get
modify (\s -> s { currentModule = n })
-- Below line of code cannot be simplified because authors has a generic type
let as = case codeSpec g of CodeSpec {authors = a} -> map name a
let as = map name (codeSpec g ^. authorsO )
cs <- sequence maybeCs
ms <- sequence maybeMs
let commMod | CommentMod `elem` commented g = OO.docMod desc
Expand All @@ -59,7 +59,7 @@ genModule n desc = genModuleWithImports n desc []
genDoxConfig :: (AuxiliarySym r) => GOOLState -> GenState (Maybe (r (Auxiliary r)))
genDoxConfig s = do
g <- get
let n = pName $ codeSpec g
let n = codeSpec g ^. pNameO
cms = commented g
v = doxOutput g
return $ if not (null cms) then Just (doxConfig n s v) else Nothing
Expand All @@ -68,7 +68,7 @@ genDoxConfig s = do
genReadMe :: (AuxiliarySym r) => ReadMeInfo -> GenState (Maybe (r (Auxiliary r)))
genReadMe rmi = do
g <- get
let n = pName $ codeSpec g
let n = codeSpec g ^. pNameO
return $ getReadMe (auxiliaries g) rmi {caseName = n}

-- | Helper for generating a README file.
Expand Down Expand Up @@ -179,8 +179,7 @@ genModuleWithImportsProc :: (ProcProg r) => Name -> Description -> [Import] ->
genModuleWithImportsProc n desc is maybeMs = do
g <- get
modify (\s -> s { currentModule = n })
-- Below line of code cannot be simplified because authors has a generic type
let as = case codeSpec g of CodeSpec {authors = a} -> map name a
let as = map name (codeSpec g ^. authorsO )
ms <- sequence maybeMs
let commMod | CommentMod `elem` commented g = Proc.docMod desc
as (date g)
Expand Down
54 changes: 27 additions & 27 deletions code/drasil-code/lib/Language/Drasil/Code/Imperative/Generator.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ 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(..), getODE, sysInfo)
import Language.Drasil.CodeSpec (CodeSpec(..), HasOldCodeSpec(..), getODE)
import Language.Drasil.Printers (SingleLine(OneLine), sentenceDoc)

import Drasil.GOOL (OOProg, VisibilityTag(..),
Expand Down Expand Up @@ -97,12 +97,12 @@ generator l dt sd chs spec = DrasilState {
((pth, elmap, lname), libLog) = runState (chooseODELib l $ getODE $ extLibs chs) []
els = map snd elmap
nms = [lname]
mem = modExportMap spec chs modules'
mem = modExportMap (spec ^. oldCodeSpec) chs modules'
lem = fromList (concatMap (^. modExports) els)
cdm = clsDefMap spec chs modules'
modules' = mods spec ++ concatMap (^. auxMods) els
cdm = clsDefMap (spec ^. oldCodeSpec) chs modules'
modules' = (spec ^. modsO) ++ concatMap (^. auxMods) els
nonPrefChs = choicesSent chs
des = vcat . map (sentenceDoc (sysinfodb spec) Implementation OneLine) $
des = vcat . map (sentenceDoc (spec ^. sysinfodbO) Implementation OneLine) $
(nonPrefChs ++ concLog ++ libLog)

-- OO Versions --
Expand Down Expand Up @@ -144,19 +144,19 @@ genPackage unRepr = do
(reprPD, s) = runState p info
pd = unRepr reprPD
m = makefile (libPaths g) (implType g) (commented g) s pd
as = case codeSpec g of CodeSpec {authors = a} -> map name a
cfp = configFiles $ codeSpec g
db = sysinfodb $ codeSpec g
as = map name (codeSpec g ^. authorsO)
cfp = codeSpec g ^. configFilesO
db = codeSpec g ^. sysinfodbO
-- prps = show $ sentenceDoc db Implementation OneLine
-- (foldlSent $ purpose $ codeSpec g)
prps = show $ sentenceDoc db Implementation OneLine
(foldlSent $ codeSpec g ^. sysInfo .purpose)
(foldlSent $ codeSpec g ^. purpose)
bckgrnd = show $ sentenceDoc db Implementation OneLine
(foldlSent $ codeSpec g ^. sysInfo . background)
(foldlSent $ codeSpec g ^. background)
mtvtn = show $ sentenceDoc db Implementation OneLine
(foldlSent $ codeSpec g ^. sysInfo . motivation)
(foldlSent $ codeSpec g ^. motivation)
scp = show $ sentenceDoc db Implementation OneLine
(foldlSent $ codeSpec g ^. sysInfo . scope)
(foldlSent $ codeSpec g ^. scope)
i <- genSampleInput
d <- genDoxConfig s
rm <- genReadMe ReadMeInfo {
Expand All @@ -182,8 +182,8 @@ genProgram :: (OOProg r) => GenState (OO.GSProgram r)
genProgram = do
g <- get
ms <- chooseModules $ modular g
let n = pName $ codeSpec g
let p = show $ sentenceDoc (sysinfodb $ codeSpec g) Implementation OneLine $ foldlSent $ codeSpec g ^. sysInfo .purpose
let n = codeSpec g ^. pNameO
let p = show $ sentenceDoc (codeSpec g ^. sysinfodbO) Implementation OneLine $ foldlSent $ codeSpec g ^. purpose
return $ OO.prog n p ms

-- | Generates either a single module or many modules, based on the users choice
Expand All @@ -200,11 +200,11 @@ genUnmodular = do
giName <- genICName GetInput
dvName <- genICName DerivedValuesFn
icName <- genICName InputConstraintsFn
let n = pName $ codeSpec g
let n = codeSpec g ^. pNameO
cls = any (`member` clsMap g) [giName, dvName, icName]
genModuleWithImports n umDesc (concatMap (^. imports) (elems $ extLibMap g))
(genMainFunc
: map (fmap Just) (map genCalcFunc (execOrder $ codeSpec g)
: map (fmap Just) (map genCalcFunc (codeSpec g ^. execOrderO)
++ concatMap genModFuncs (modules g))
++ ((if cls then [] else [genInputFormat Pub, genInputDerived Pub,
genInputConstraints Pub]) ++ [genOutputFormat]))
Expand Down Expand Up @@ -258,17 +258,17 @@ genPackageProc unRepr = do
(reprPD, s) = runState p info
pd = unRepr reprPD
m = makefile (libPaths g) (implType g) (commented g) s pd
as = case codeSpec g of CodeSpec {authors = a} -> map name a
cfp = configFiles $ codeSpec g
db = sysinfodb $ codeSpec g
as = map name (codeSpec g ^. authorsO)
cfp = codeSpec g ^. configFilesO
db = codeSpec g ^. sysinfodbO
prps = show $ sentenceDoc db Implementation OneLine
(foldlSent $ codeSpec g ^. sysInfo .purpose)
(foldlSent $ codeSpec g ^. purpose)
bckgrnd = show $ sentenceDoc db Implementation OneLine
(foldlSent $ codeSpec g ^. sysInfo . background)
(foldlSent $ codeSpec g ^. background)
mtvtn = show $ sentenceDoc db Implementation OneLine
(foldlSent $ codeSpec g ^. sysInfo . motivation)
(foldlSent $ codeSpec g ^. motivation)
scp = show $ sentenceDoc db Implementation OneLine
(foldlSent $ codeSpec g ^. sysInfo . scope)
(foldlSent $ codeSpec g ^. scope)
i <- genSampleInput
d <- genDoxConfig s
rm <- genReadMe ReadMeInfo {
Expand All @@ -294,8 +294,8 @@ genProgramProc :: (ProcProg r) => GenState (Proc.GSProgram r)
genProgramProc = do
g <- get
ms <- chooseModulesProc $ modular g
let n = pName $ codeSpec g
let p = show $ sentenceDoc (sysinfodb $ codeSpec g) Implementation OneLine $ foldlSent $ codeSpec g ^. sysInfo .purpose
let n = codeSpec g ^. pNameO
let p = show $ sentenceDoc (codeSpec g ^. sysinfodbO) Implementation OneLine $ foldlSent $ codeSpec g ^. purpose
return $ Proc.prog n p ms

-- | Generates either a single module or many modules, based on the users choice
Expand All @@ -312,12 +312,12 @@ genUnmodularProc = do
giName <- genICName GetInput
dvName <- genICName DerivedValuesFn
icName <- genICName InputConstraintsFn
let n = pName $ codeSpec g
let n = codeSpec g ^. pNameO
cls = any (`member` clsMap g) [giName, dvName, icName]
if cls then error "genUnmodularProc: Procedural renderers do not support classes"
else genModuleWithImportsProc n umDesc (concatMap (^. imports) (elems $ extLibMap g))
(genMainFuncProc
: map (fmap Just) (map genCalcFuncProc (execOrder $ codeSpec g)
: map (fmap Just) (map genCalcFuncProc (codeSpec g ^. execOrderO)
++ concatMap genModFuncsProc (modules g))
++ ([genInputFormatProc Pub, genInputDerivedProc Pub,
genInputConstraintsProc Pub] ++ [genOutputFormatProc]))
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -6,18 +6,19 @@ import Language.Drasil (UID, QuantityDict)
import Database.Drasil (symbResolve)
import Language.Drasil.Code.Imperative.DrasilState (DrasilState(..),
ScopeType(..))
import Language.Drasil.CodeSpec (CodeSpec(..))
import Language.Drasil.CodeSpec (HasOldCodeSpec(..))
import Drasil.GOOL (SharedProg, ScopeSym(..))

import Control.Monad.State (State)
import Control.Lens ((^.))

-- | Puts a state-dependent value into a singleton list.
liftS :: State a b -> State a [b]
liftS = fmap (: [])

-- | Gets the 'QuantityDict' corresponding to a 'UID'.
lookupC :: DrasilState -> UID -> QuantityDict
lookupC g = symbResolve (sysinfodb $ codeSpec g)
lookupC g = symbResolve (codeSpec g ^. sysinfodbO)

-- | Converts a 'ScopeType' to a 'Scope'
convScope :: (SharedProg r) => ScopeType -> r (Scope r)
Expand Down
Loading

0 comments on commit 10ae63b

Please sign in to comment.