Skip to content

Commit

Permalink
Merge pull request #2213 from JacquesCarette/design_log_mess
Browse files Browse the repository at this point in the history
Design log mess
  • Loading branch information
JacquesCarette authored Feb 24, 2021
2 parents 74c715b + d0bf375 commit d839c2c
Show file tree
Hide file tree
Showing 39 changed files with 859 additions and 36 deletions.
91 changes: 85 additions & 6 deletions code/drasil-code/Language/Drasil/Choices.hs
Original file line number Diff line number Diff line change
@@ -1,13 +1,14 @@
-- | Defines the design language for SCS.
module Language.Drasil.Choices (
Choices(..), Modularity(..), InputModule(..), inputModule, Structure(..),
ConstantStructure(..), ConstantRepr(..), MatchedConceptMap, CodeConcept(..),
matchConcepts, SpaceMatch, matchSpaces, ImplementationType(..),
ConstantStructure(..), ConstantRepr(..), ConceptMatchMap, MatchedConceptMap,
CodeConcept(..), matchConcepts, SpaceMatch, matchSpaces, ImplementationType(..),
ConstraintBehaviour(..), Comments(..), Verbosity(..), Visibility(..),
Logging(..), AuxFile(..), getSampleData, hasSampleInput, defaultChoices
) where
Logging(..), AuxFile(..), getSampleData, hasSampleInput, defaultChoices,
choicesSent, showChs) where

import Language.Drasil
import Utils.Drasil (foldlSent_)

import Language.Drasil.Code.Code (spaceToCodeType)
import Language.Drasil.Code.Lang (Lang(..))
Expand Down Expand Up @@ -67,10 +68,20 @@ data Choices = Choices {
auxFiles :: [AuxFile]
}

class RenderChoices a where
showChs :: a -> Sentence
showChsList :: [a] -> Sentence
showChsList lst = foldlSent_ (map showChs lst)

data Modularity = Modular InputModule -- Different modules for: controller,
-- input, calculations, output.
| Unmodular -- All generated code is in one module/file.

instance RenderChoices Modularity where
showChs Unmodular = S "Unmodular"
showChs (Modular Combined) = S "Modular Combined"
showChs (Modular Separated)= S "Modular Separated"

data InputModule = Combined -- Input-related functions combined in one module
| Separated -- Input-related functions each in own module

Expand All @@ -85,14 +96,28 @@ inputModule c = inputModule' $ modularity c
data Structure = Unbundled -- Individual variables
| Bundled -- Variables bundled in a class

instance RenderChoices Structure where
showChs Unbundled = S "Unbundled"
showChs Bundled = S "Bundled"

data ConstantStructure = Inline -- Inline values for constants
| WithInputs -- Store constants with inputs
| Store Structure -- Store constants separately from
-- inputs, whether bundled or unbundled

instance RenderChoices ConstantStructure where
showChs Inline = S "Inline"
showChs WithInputs = S "WithInputs"
showChs (Store Unbundled) = S "Store Unbundled"
showChs (Store Bundled) = S "Store Bundled"

data ConstantRepr = Var -- Constants represented as regular variables
| Const -- Use target language's mechanism for defining constants.

instance RenderChoices ConstantRepr where
showChs Var = S "Var"
showChs Const = S "Const"

-- | Specifies matches between chunks and CodeConcepts, meaning the target
-- language's pre-existing definition of the concept should be used instead of
-- defining a new variable for the concept in the generated code.
Expand All @@ -102,7 +127,10 @@ type ConceptMatchMap = Map UID [CodeConcept]
type MatchedConceptMap = Map UID CodeConcept

-- Currently we only support one code concept, more will be added later
data CodeConcept = Pi
data CodeConcept = Pi deriving Eq

instance RenderChoices CodeConcept where
showChs Pi = S "Pi"

-- | Builds a ConceptMatchMap from an association list of chunks and CodeConcepts
matchConcepts :: (HasUID c) => [(c, [CodeConcept])] -> ConceptMatchMap
Expand All @@ -127,32 +155,62 @@ matchSpaces spMtchs = matchSpaces' spMtchs spaceToCodeType
data ImplementationType = Library -- Generated code does not include Controller
| Program -- Generated code includes Controller

instance RenderChoices ImplementationType where
showChs Library = S "Library"
showChs Program = S "Program"


data ConstraintBehaviour = Warning -- Print warning when constraint violated
| Exception -- Throw exception when constraint violated

instance RenderChoices ConstraintBehaviour where
showChs Warning = S "Warning"
showChs Exception = S "Exception"

data Comments = CommentFunc -- Function/method-level comments
| CommentClass -- class-level comments
| CommentMod -- File/Module-level comments
deriving Eq

instance RenderChoices Comments where
showChs CommentFunc = S "CommentFunc"
showChs CommentClass = S "CommentClass"
showChs CommentMod = S "CommentMod"

data Verbosity = Verbose | Quiet

instance RenderChoices Verbosity where
showChs Verbose = S "Verbose"
showChs Quiet = S "Quiet"

data Visibility = Show
| Hide

instance RenderChoices Visibility where
showChs Show = S "Show"
showChs Hide = S "Hide"

-- Eq instances required for Logging and Comments because generator needs to
-- check membership of these elements in lists
data Logging = LogFunc -- Log messages generated for function calls
| LogVar -- Log messages generated for variable assignments
deriving Eq

instance RenderChoices Logging where
showChs LogFunc = S "LogFunc"
showChs LogVar = S "LogVar"

-- Currently we only support one kind of auxiliary file: sample input file
-- To generate a sample input file compatible with the generated program
-- FilePath is the path to the user-provided file containing a sample set of input data
data AuxFile = SampleInput FilePath
| ReadME
deriving Eq

instance RenderChoices AuxFile where
showChs (SampleInput fp) = S "SampleInput" +:+ S fp
showChs ReadME = S "ReadME"

-- Gets the file path to a sample input data set from a Choices structure, if
-- the user chose to generate a sample input file.
getSampleData :: Choices -> Maybe FilePath
Expand Down Expand Up @@ -189,4 +247,25 @@ defaultChoices = Choices {
auxFiles = [ReadME],
odeLib = [],
odes = []
}
}

choicesSent :: Choices -> [Sentence]
choicesSent chs = map chsFieldSent [
(S "Languages", foldlSent_ $ map (S . show) $ lang chs)
, (S "Modularity", showChs $ modularity chs)
, (S "Input Structure", showChs $ inputStructure chs)
, (S "Constant Structure", showChs $ constStructure chs)
, (S "Constant Representation", showChs $ constRepr chs)
, (S "Implementation Type", showChs $ impType chs)
, (S "Software Constraint Behaviour", showChs $ onSfwrConstraint chs)
, (S "Physical Constraint Behaviour", showChs $ onPhysConstraint chs)
, (S "Comments", showChsList $ comments chs)
, (S "Dox Verbosity", showChs $ doxVerbosity chs)
, (S "Dates", showChs $ dates chs)
, (S "Log File Name", S $ logFile chs)
, (S "Logging", showChsList $ logging chs)
, (S "Auxiliary Files", showChsList $ auxFiles chs)
]

chsFieldSent :: (Sentence, Sentence) -> Sentence
chsFieldSent (rec, chc) = rec +:+ S "selected as" +:+. chc
28 changes: 17 additions & 11 deletions code/drasil-code/Language/Drasil/Code/Imperative/ConceptMatch.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,25 +3,31 @@ module Language.Drasil.Code.Imperative.ConceptMatch (
chooseConcept, conceptToGOOL
) where

import Language.Drasil.Choices (Choices(..), CodeConcept(..), MatchedConceptMap)
import Language.Drasil (UID, Sentence(S), (+:+), (+:+.))

import Language.Drasil.Choices (Choices(..), CodeConcept(..),
MatchedConceptMap, showChs)

import GOOL.Drasil (SValue, OOProg, MathConstant(..))

import Prelude hiding (pi)
import qualified Data.Map as Map (map)
import Control.Monad.State (State)
import Text.PrettyPrint.HughesPJ (Doc)
import qualified Data.Map as Map (mapWithKey)
import Control.Monad.State (State, modify)

-- | Concretizes the ConceptMatchMap in Choices to a MatchedConceptMap.
-- Currently we don't have any Choices that would prevent a CodeConcept from
-- being mapped, so we just take the head of the list of CodeConcepts
chooseConcept :: Choices -> State Doc MatchedConceptMap
chooseConcept chs = sequence $ Map.map (chooseConcept' chs) (conceptMatch chs)
where chooseConcept' _ [] = error $ "Empty list of CodeConcepts in the " ++
-- The conceptMatchMap from choices is passed to chooseConept' internally, this way
-- any codeconcept list can be matched to its appropiate UID

chooseConcept :: Choices -> State [Sentence] MatchedConceptMap
chooseConcept chs = sequence $ Map.mapWithKey chooseConcept' (conceptMatch chs)
where chooseConcept' :: UID -> [CodeConcept] -> State [Sentence] CodeConcept
chooseConcept' _ [] = error $ "Empty list of CodeConcepts in the " ++
"ConceptMatchMap"
chooseConcept' _ cs = return $ head cs
chooseConcept' uid (c:_) = do
modify (++ [S "Code Concept" +:+ S uid +:+ S "selected as" +:+. showChs c])
return c

-- | Maps CodeConcepts to corresponding GOOL values
conceptToGOOL :: (OOProg r) => CodeConcept -> SValue r
conceptToGOOL Pi = pi

conceptToGOOL Pi = pi
35 changes: 23 additions & 12 deletions code/drasil-code/Language/Drasil/Code/Imperative/GenODE.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@ module Language.Drasil.Code.Imperative.GenODE (
chooseODELib
) where

import Language.Drasil (Sentence(..), (+:+.))
import Language.Drasil.Code.ExtLibImport (ExtLibState(..),
genExternalLibraryCall)
import Language.Drasil.Code.Lang (Lang(..))
Expand All @@ -12,28 +13,38 @@ import Language.Drasil.Data.ODEInfo (ODEInfo)
import Language.Drasil.Data.ODELibPckg (ODELibPckg(..))

import Control.Monad.State (State, modify)
import Text.PrettyPrint.HughesPJ (Doc, ($$), text)

type ODEGenInfo = (Maybe FilePath, [(Name, ExtLibState)], (Name,Version))

-- Chooses the first ODELibPckg from the list specified by the user that is
-- compatible with the current target Lang.
-- Interprets the ExternalLibrary and ExternalLibraryCall for the selected
-- ODELibPckg by concretizing the ExternalLibraryCall with each of the ODEInfos
chooseODELib :: Lang -> [ODELibPckg] -> [ODEInfo] -> State Doc ODEGenInfo
-- chooseODELib' is keeps a read only preference list and a currently considered
-- preference list (which can change), this facilitates the firstChoiceODELib check
chooseODELib :: Lang -> [ODELibPckg] -> [ODEInfo] -> State [Sentence] ODEGenInfo
chooseODELib _ _ [] = return (Nothing, [], ("",""))
chooseODELib l olps odes = chooseODELib' olps
where chooseODELib' :: [ODELibPckg] -> State Doc ODEGenInfo
chooseODELib' [] = error $ "None of the chosen ODE libraries are " ++
chooseODELib l olps odes = chooseODELib' olps olps
where chooseODELib' :: [ODELibPckg] -> [ODELibPckg] -> State [Sentence] ODEGenInfo
chooseODELib' _ [] = error $ "None of the chosen ODE libraries are " ++
"compatible with " ++ show l
chooseODELib' (o:os) = if l `elem` compatibleLangs o
then return (libPath o, map (\ode -> (codeName $ odeDef ode,
genExternalLibraryCall (libSpec o) $ libCall o ode)) odes,
chooseODELib' prefLibList (o:os) = if l `elem` compatibleLangs o
then do
modify (++ [firstChoiceODELib prefLibList o])
return (libPath o, map (\ode -> (codeName $ odeDef ode,
genExternalLibraryCall (libSpec o) $ libCall o ode)) odes,
(libName o, libVers o))
else modify ($$ incompatibleLib l o) >> chooseODELib' os
else modify (++ [incompatibleLib l o]) >> chooseODELib' prefLibList os

-- Defines a design log message based on an incompatibility between the given
-- Lang and chosen ODELibPckg.
incompatibleLib :: Lang -> ODELibPckg -> Doc
incompatibleLib lng lib = text $ "Language " ++ show lng ++ " is not " ++
"compatible with chosen library " ++ libName lib ++ ", trying next choice."
incompatibleLib :: Lang -> ODELibPckg -> Sentence
incompatibleLib lng lib = S $ "Language " ++ show lng ++ " is not " ++
"compatible with chosen library " ++ libName lib ++ ", trying next choice."

-- Defines a design log message if the first choice ODE Library, which is the head of
-- the preference list that the user selected, is compatible with the given Lang.
firstChoiceODELib :: [ODELibPckg] -> ODELibPckg -> Sentence
firstChoiceODELib prefer olp = if libName (head prefer) == libName olp then
S "Successfully selected first choice ODE Library package" +:+. S (libName olp)
else S "ODE Library package selected as" +:+. S (libName olp)
15 changes: 10 additions & 5 deletions code/drasil-code/Language/Drasil/Code/Imperative/Generator.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,8 +25,10 @@ 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(..), Visibility(..))
import Language.Drasil.Choices (Choices(..), Modularity(..), Visibility(..),
choicesSent)
import Language.Drasil.CodeSpec (CodeSpec(..))
import Language.Drasil.Printers (Linearity(Linear), sentenceDoc)

import GOOL.Drasil (GSProgram, SFile, OOProg, ProgramSym(..), ScopeTag(..),
ProgData(..), initialState, unCI)
Expand All @@ -38,7 +40,7 @@ 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 (($$), empty, isEmpty)
import Text.PrettyPrint.HughesPJ (isEmpty, vcat)

-- | Initializes the generator's DrasilState.
-- String parameter is a string representing the date.
Expand Down Expand Up @@ -75,20 +77,23 @@ generator l dt sd chs spec = DrasilState {
-- stateful
currentModule = "",
currentClass = "",
_designLog = concLog $$ libLog,
_designLog = des,
_loggedSpaces = [] -- Used to prevent duplicate logs added to design log
}
where (mcm, concLog) = runState (chooseConcept chs) empty
where (mcm, concLog) = runState (chooseConcept chs) []
showDate Show = dt
showDate Hide = ""
((pth, elmap, lname), libLog) = runState (chooseODELib l (odeLib chs)
(odes chs)) empty
(odes chs)) []
els = map snd elmap
nms = [lname]
mem = modExportMap spec chs modules'
lem = fromList (concatMap (^. modExports) els)
cdm = clsDefMap spec chs modules'
modules' = mods spec ++ concatMap (^. auxMods) els
nonPrefChs = choicesSent chs
des = vcat . map (sentenceDoc (sysinfodb spec) Implementation Linear) $
(nonPrefChs ++ concLog ++ libLog)

-- | Generates a package with the given DrasilState. The passed
-- un-representation functions determine which target language the package will
Expand Down
10 changes: 8 additions & 2 deletions code/drasil-code/Language/Drasil/Code/Imperative/SpaceMatch.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,10 @@ chooseSpace lng chs = \s -> selectType lng s (spaceMatch chs s)
addToDesignLog s Float (incompatibleType Python s Float))
selectType Python s ts
-- In all other cases, just select first choice
selectType _ _ (t:_) = return t
selectType _ s (t:_) = do
modify (addLoggedSpace s t .
addToDesignLog s t (successLog s t))
return t
selectType l s [] = error $ "Chosen CodeType matches for Space " ++
show s ++ " are not compatible with target language " ++ show l

Expand All @@ -32,4 +35,7 @@ chooseSpace lng chs = \s -> selectType lng s (spaceMatch chs s)
incompatibleType :: Lang -> Space -> CodeType -> Doc
incompatibleType l s t = text $ "Language " ++ show l ++ " does not support "
++ "code type " ++ show t ++ ", chosen as the match for the " ++ show s ++
" space. Trying next choice."
" space. Trying next choice."

successLog :: Space -> CodeType -> Doc
successLog s t = text ("Successfully matched "++show s ++ " with "++ show t ++".")
23 changes: 23 additions & 0 deletions code/stable/glassbr/src/cpp/designLog.txt
Original file line number Diff line number Diff line change
@@ -0,0 +1,23 @@
Languages selected as Python Cpp CSharp Java Swift.
Modularity selected as Modular Separated.
Input Structure selected as Bundled.
Constant Structure selected as Inline.
Constant Representation selected as Const.
Implementation Type selected as Program.
Software Constraint Behaviour selected as Exception.
Physical Constraint Behaviour selected as Exception.
Comments selected as CommentFunc CommentClass CommentMod.
Dox Verbosity selected as Quiet.
Dates selected as Hide.
Log File Name selected as log.txt.
Logging selected as LogVar LogFunc.
Auxiliary Files selected as SampleInput ../../datafiles/GlassBR/sampleInput.txt ReadME.
Successfully matched String with String.
Successfully matched Actor "Constants" with Object "Constants".
Successfully matched Actor "InputParameters" with Object "InputParameters".
Successfully matched Real with Double.
Successfully matched Rational with Double.
Successfully matched Boolean with Boolean.
Successfully matched Vect Real with List Double.
Successfully matched Vect (Vect Real) with List (List Double).
Successfully matched Natural with Integer.
23 changes: 23 additions & 0 deletions code/stable/glassbr/src/csharp/designLog.txt
Original file line number Diff line number Diff line change
@@ -0,0 +1,23 @@
Languages selected as Python Cpp CSharp Java Swift.
Modularity selected as Modular Separated.
Input Structure selected as Bundled.
Constant Structure selected as Inline.
Constant Representation selected as Const.
Implementation Type selected as Program.
Software Constraint Behaviour selected as Exception.
Physical Constraint Behaviour selected as Exception.
Comments selected as CommentFunc CommentClass CommentMod.
Dox Verbosity selected as Quiet.
Dates selected as Hide.
Log File Name selected as log.txt.
Logging selected as LogVar LogFunc.
Auxiliary Files selected as SampleInput ../../datafiles/GlassBR/sampleInput.txt ReadME.
Successfully matched String with String.
Successfully matched Actor "Constants" with Object "Constants".
Successfully matched Actor "InputParameters" with Object "InputParameters".
Successfully matched Real with Double.
Successfully matched Rational with Double.
Successfully matched Boolean with Boolean.
Successfully matched Vect Real with List Double.
Successfully matched Vect (Vect Real) with List (List Double).
Successfully matched Natural with Integer.
Loading

0 comments on commit d839c2c

Please sign in to comment.