From 93813f1e7565078966ab6b0b67c913a91eeff02b Mon Sep 17 00:00:00 2001 From: muhammad ali Date: Fri, 26 Jun 2020 14:02:11 -0400 Subject: [PATCH 1/9] Adding design log sucess messages --- code/drasil-code/Language/Drasil/Choices.hs | 90 ++++++++++++++++++- .../Drasil/Code/Imperative/ConceptMatch.hs | 19 ++-- .../Language/Drasil/Code/Imperative/GenODE.hs | 25 ++++-- .../Drasil/Code/Imperative/Generator.hs | 6 +- .../Drasil/Code/Imperative/SpaceMatch.hs | 10 ++- 5 files changed, 126 insertions(+), 24 deletions(-) diff --git a/code/drasil-code/Language/Drasil/Choices.hs b/code/drasil-code/Language/Drasil/Choices.hs index abbe94c65e..654a7640f9 100644 --- a/code/drasil-code/Language/Drasil/Choices.hs +++ b/code/drasil-code/Language/Drasil/Choices.hs @@ -1,10 +1,11 @@ -- | 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, hasReadMe, defaultChoices + Logging(..), AuxFile(..), getSampleData, hasSampleInput, hasReadMe, defaultChoices, + choicesDoc, showChs ) where import Language.Drasil @@ -18,6 +19,7 @@ import GOOL.Drasil (CodeType) import Control.Lens ((^.)) import Data.Map (Map, fromList) +import Text.PrettyPrint.HughesPJ (Doc, text, vcat) data Choices = Choices { -- Global design choices (affect entire program) @@ -67,10 +69,20 @@ data Choices = Choices { auxFiles :: [AuxFile] } +class ChsShow a where + showChs :: a -> String + showChsList :: [a] -> String + showChsList lst = show $ map showChs lst + data Modularity = Modular InputModule -- Different modules for: controller, -- input, calculations, output. | Unmodular -- All generated code is in one module/file. +instance ChsShow Modularity where + showChs Unmodular = "Unmodular" + showChs (Modular Combined) = "Modular Combined" + showChs (Modular Separated)= "Modular Separated" + data InputModule = Combined -- Input-related functions combined in one module | Separated -- Input-related functions each in own module @@ -85,14 +97,28 @@ inputModule c = inputModule' $ modularity c data Structure = Unbundled -- Individual variables | Bundled -- Variables bundled in a class +instance ChsShow Structure where + showChs Unbundled = "Unbundled" + showChs Bundled = "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 ChsShow ConstantStructure where + showChs Inline = "Inline" + showChs WithInputs = "WithInputs" + showChs (Store Unbundled) = "Store Unbundled" + showChs (Store Bundled) = "Store Bundled" + data ConstantRepr = Var -- Constants represented as regular variables | Const -- Use target language's mechanism for defining constants. +instance ChsShow ConstantRepr where + showChs Var = "Var" + showChs Const = "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. @@ -104,6 +130,9 @@ type MatchedConceptMap = Map UID CodeConcept -- Currently we only support one code concept, more will be added later data CodeConcept = Pi +instance ChsShow CodeConcept where + showChs Pi = "Pi" + -- | Builds a ConceptMatchMap from an association list of chunks and CodeConcepts matchConcepts :: (HasUID c) => [(c, [CodeConcept])] -> ConceptMatchMap matchConcepts = fromList . map (\(cnc,cdc) -> (cnc ^. uid, cdc)) @@ -127,25 +156,51 @@ matchSpaces spMtchs = matchSpaces' spMtchs spaceToCodeType data ImplementationType = Library -- Generated code does not include Controller | Program -- Generated code includes Controller +instance ChsShow ImplementationType where + showChs Library = "Library" + showChs Program = "Program" + + data ConstraintBehaviour = Warning -- Print warning when constraint violated | Exception -- Throw exception when constraint violated +instance ChsShow ConstraintBehaviour where + showChs Warning = "Warning" + showChs Exception = "Exception" + data Comments = CommentFunc -- Function/method-level comments | CommentClass -- class-level comments | CommentMod -- File/Module-level comments deriving Eq +instance ChsShow Comments where + showChs CommentFunc = "CommentFunc" + showChs CommentClass = "CommentClass" + showChs CommentMod = "CommentMod" + data Verbosity = Verbose | Quiet +instance ChsShow Verbosity where + showChs Verbose = "Verbose" + showChs Quiet = "Quiet" + data Visibility = Show | Hide +instance ChsShow Visibility where + showChs Show = "Show" + showChs Hide = "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 ChsShow Logging where + showChs LogFunc = "LogFunc" + showChs LogVar = "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 @@ -153,6 +208,10 @@ data AuxFile = SampleInput FilePath | ReadME deriving Eq +instance ChsShow AuxFile where + showChs (SampleInput fp) = "SampleInput"++fp + showChs ReadME = "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 @@ -194,4 +253,27 @@ defaultChoices = Choices { auxFiles = [ReadME], odeLib = [], odes = [] -} \ No newline at end of file +} + +choicesDoc :: Choices -> Doc +choicesDoc chs = (vcat. map chsFieldDoc) [ + ("Languages", show $ lang chs) + , ("Modularity", showChs $ modularity chs) + , ("Input Structure", showChs $ inputStructure chs) + , ("Constant Structure", showChs $ constStructure chs) + , ("Constant Representation", showChs $ constRepr chs) + , ("Implementation Type", showChs $ impType chs) + , ("Software Constraint Behaviour", showChs $ onSfwrConstraint chs) + , ("Physical Constraint Behavior", showChs $ onPhysConstraint chs) + , ("Comments", showChsList $ comments chs) + , ("Dox Verbosity", showChs $ doxVerbosity chs) + , ("Dates", showChs $ dates chs) + , ("Log File Name", logFile chs) + , ("Logging", showChsList $ logging chs) + , ("Auxiliary Files", showChsList $ auxFiles chs) +-- , ("ODE Libraries", odeLib chs) +-- , ("ODE's", odes chs) along with conceptmatch and speace match + ] + +chsFieldDoc :: (String, String) -> Doc +chsFieldDoc (rec, chc) = text $ rec ++ " selected as " ++ chc \ No newline at end of file diff --git a/code/drasil-code/Language/Drasil/Code/Imperative/ConceptMatch.hs b/code/drasil-code/Language/Drasil/Code/Imperative/ConceptMatch.hs index c9fe089f00..b931d75f28 100644 --- a/code/drasil-code/Language/Drasil/Code/Imperative/ConceptMatch.hs +++ b/code/drasil-code/Language/Drasil/Code/Imperative/ConceptMatch.hs @@ -3,23 +3,28 @@ module Language.Drasil.Code.Imperative.ConceptMatch ( chooseConcept, conceptToGOOL ) where -import Language.Drasil.Choices (Choices(..), CodeConcept(..), MatchedConceptMap) +import Language.Drasil.Choices (Choices(..), CodeConcept(..), ConceptMatchMap, + 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 (map, keys) +import Control.Monad.State (State, modify) +import Text.PrettyPrint.HughesPJ (Doc, text, ($$)) -- | 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 " ++ +chooseConcept chs = sequence $ Map.map (chooseConcept' chs $ conceptMatch chs) (conceptMatch chs) + where chooseConcept' :: Choices -> ConceptMatchMap-> [CodeConcept] -> State Doc CodeConcept + chooseConcept' _ _ [] = error $ "Empty list of CodeConcepts in the " ++ "ConceptMatchMap" - chooseConcept' _ cs = return $ head cs + chooseConcept' _ cmm cs = do + let uid = (head . Map.keys) cmm + modify ($$ (text $ "Code Concept "++ uid ++" selected as " ++ showChs (head cs))) + return $ head cs -- | Maps CodeConcepts to corresponding GOOL values conceptToGOOL :: (OOProg r) => CodeConcept -> SValue r diff --git a/code/drasil-code/Language/Drasil/Code/Imperative/GenODE.hs b/code/drasil-code/Language/Drasil/Code/Imperative/GenODE.hs index 118505e4db..209cf97dbe 100644 --- a/code/drasil-code/Language/Drasil/Code/Imperative/GenODE.hs +++ b/code/drasil-code/Language/Drasil/Code/Imperative/GenODE.hs @@ -12,7 +12,7 @@ import Language.Drasil.Data.ODEInfo (ODEInfo) import Language.Drasil.Data.ODELibPckg (ODELibPckg(..)) import Control.Monad.State (State, modify) -import Text.PrettyPrint.HughesPJ (Doc, ($$), text) +import Text.PrettyPrint.HughesPJ (Doc, ($$), text, empty) type ODEGenInfo = (Maybe FilePath, [(Name, ExtLibState)], (Name,Version)) @@ -22,18 +22,25 @@ type ODEGenInfo = (Maybe FilePath, [(Name, ExtLibState)], (Name,Version)) -- ODELibPckg by concretizing the ExternalLibraryCall with each of the ODEInfos chooseODELib :: Lang -> [ODELibPckg] -> [ODEInfo] -> State Doc 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 Doc 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' initLib (o:os) = if l `elem` compatibleLangs o + then do + modify ($$ firstChoiceODELib initLib 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' initLib 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." \ No newline at end of file + "compatible with chosen library " ++ libName lib ++ ", trying next choice." + +firstChoiceODELib :: [ODELibPckg] -> ODELibPckg -> Doc +firstChoiceODELib prefer olp = if libName (head prefer) == libName olp then + text $ "Successfully " ++"selected first choice ODELibPckg "++ + libName olp else empty \ No newline at end of file diff --git a/code/drasil-code/Language/Drasil/Code/Imperative/Generator.hs b/code/drasil-code/Language/Drasil/Code/Imperative/Generator.hs index 6e0b99f330..7b72570751 100644 --- a/code/drasil-code/Language/Drasil/Code/Imperative/Generator.hs +++ b/code/drasil-code/Language/Drasil/Code/Imperative/Generator.hs @@ -25,7 +25,8 @@ 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(..), + choicesDoc) import Language.Drasil.CodeSpec (CodeSpec(..)) import GOOL.Drasil (GSProgram, SFile, OOProg, ProgramSym(..), ScopeTag(..), @@ -75,7 +76,7 @@ generator l dt sd chs spec = DrasilState { -- stateful currentModule = "", currentClass = "", - _designLog = concLog $$ libLog, + _designLog = nonPrefChs $$ concLog $$ libLog, _loggedSpaces = [] -- Used to prevent duplicate logs added to design log } where (mcm, concLog) = runState (chooseConcept chs) empty @@ -89,6 +90,7 @@ generator l dt sd chs spec = DrasilState { lem = fromList (concatMap (^. modExports) els) cdm = clsDefMap spec chs modules' modules' = mods spec ++ concatMap (^. auxMods) els + nonPrefChs = choicesDoc chs -- | Generates a package with the given DrasilState. The passed -- un-representation functions determine which target language the package will diff --git a/code/drasil-code/Language/Drasil/Code/Imperative/SpaceMatch.hs b/code/drasil-code/Language/Drasil/Code/Imperative/SpaceMatch.hs index afe82b54d0..e96db73640 100644 --- a/code/drasil-code/Language/Drasil/Code/Imperative/SpaceMatch.hs +++ b/code/drasil-code/Language/Drasil/Code/Imperative/SpaceMatch.hs @@ -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 @@ -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." \ No newline at end of file + " space. Trying next choice." + +successLog :: Space -> CodeType -> Doc +successLog s t = text $ "Successfully matched "++show s ++ " with "++ show t \ No newline at end of file From 661c23f2279a0dc35cd42c091af45a8bda2f7e15 Mon Sep 17 00:00:00 2001 From: muhammad ali Date: Mon, 6 Jul 2020 11:09:31 -0400 Subject: [PATCH 2/9] Adding comments and readibility to chooseODELib --- code/drasil-code/Language/Drasil/Choices.hs | 28 +++++++++---------- .../Language/Drasil/Code/Imperative/GenODE.hs | 12 +++++--- 2 files changed, 22 insertions(+), 18 deletions(-) diff --git a/code/drasil-code/Language/Drasil/Choices.hs b/code/drasil-code/Language/Drasil/Choices.hs index 654a7640f9..11671f9daa 100644 --- a/code/drasil-code/Language/Drasil/Choices.hs +++ b/code/drasil-code/Language/Drasil/Choices.hs @@ -69,7 +69,7 @@ data Choices = Choices { auxFiles :: [AuxFile] } -class ChsShow a where +class RenderChoices a where showChs :: a -> String showChsList :: [a] -> String showChsList lst = show $ map showChs lst @@ -78,7 +78,7 @@ data Modularity = Modular InputModule -- Different modules for: controller, -- input, calculations, output. | Unmodular -- All generated code is in one module/file. -instance ChsShow Modularity where +instance RenderChoices Modularity where showChs Unmodular = "Unmodular" showChs (Modular Combined) = "Modular Combined" showChs (Modular Separated)= "Modular Separated" @@ -97,7 +97,7 @@ inputModule c = inputModule' $ modularity c data Structure = Unbundled -- Individual variables | Bundled -- Variables bundled in a class -instance ChsShow Structure where +instance RenderChoices Structure where showChs Unbundled = "Unbundled" showChs Bundled = "Bundled" @@ -106,7 +106,7 @@ data ConstantStructure = Inline -- Inline values for constants | Store Structure -- Store constants separately from -- inputs, whether bundled or unbundled -instance ChsShow ConstantStructure where +instance RenderChoices ConstantStructure where showChs Inline = "Inline" showChs WithInputs = "WithInputs" showChs (Store Unbundled) = "Store Unbundled" @@ -115,7 +115,7 @@ instance ChsShow ConstantStructure where data ConstantRepr = Var -- Constants represented as regular variables | Const -- Use target language's mechanism for defining constants. -instance ChsShow ConstantRepr where +instance RenderChoices ConstantRepr where showChs Var = "Var" showChs Const = "Const" @@ -130,7 +130,7 @@ type MatchedConceptMap = Map UID CodeConcept -- Currently we only support one code concept, more will be added later data CodeConcept = Pi -instance ChsShow CodeConcept where +instance RenderChoices CodeConcept where showChs Pi = "Pi" -- | Builds a ConceptMatchMap from an association list of chunks and CodeConcepts @@ -156,7 +156,7 @@ matchSpaces spMtchs = matchSpaces' spMtchs spaceToCodeType data ImplementationType = Library -- Generated code does not include Controller | Program -- Generated code includes Controller -instance ChsShow ImplementationType where +instance RenderChoices ImplementationType where showChs Library = "Library" showChs Program = "Program" @@ -164,7 +164,7 @@ instance ChsShow ImplementationType where data ConstraintBehaviour = Warning -- Print warning when constraint violated | Exception -- Throw exception when constraint violated -instance ChsShow ConstraintBehaviour where +instance RenderChoices ConstraintBehaviour where showChs Warning = "Warning" showChs Exception = "Exception" @@ -173,21 +173,21 @@ data Comments = CommentFunc -- Function/method-level comments | CommentMod -- File/Module-level comments deriving Eq -instance ChsShow Comments where +instance RenderChoices Comments where showChs CommentFunc = "CommentFunc" showChs CommentClass = "CommentClass" showChs CommentMod = "CommentMod" data Verbosity = Verbose | Quiet -instance ChsShow Verbosity where +instance RenderChoices Verbosity where showChs Verbose = "Verbose" showChs Quiet = "Quiet" data Visibility = Show | Hide -instance ChsShow Visibility where +instance RenderChoices Visibility where showChs Show = "Show" showChs Hide = "Hide" @@ -197,7 +197,7 @@ data Logging = LogFunc -- Log messages generated for function calls | LogVar -- Log messages generated for variable assignments deriving Eq -instance ChsShow Logging where +instance RenderChoices Logging where showChs LogFunc = "LogFunc" showChs LogVar = "LogVar" @@ -208,7 +208,7 @@ data AuxFile = SampleInput FilePath | ReadME deriving Eq -instance ChsShow AuxFile where +instance RenderChoices AuxFile where showChs (SampleInput fp) = "SampleInput"++fp showChs ReadME = "ReadME" @@ -264,7 +264,7 @@ choicesDoc chs = (vcat. map chsFieldDoc) [ , ("Constant Representation", showChs $ constRepr chs) , ("Implementation Type", showChs $ impType chs) , ("Software Constraint Behaviour", showChs $ onSfwrConstraint chs) - , ("Physical Constraint Behavior", showChs $ onPhysConstraint chs) + , ("Physical Constraint Behaviour", showChs $ onPhysConstraint chs) , ("Comments", showChsList $ comments chs) , ("Dox Verbosity", showChs $ doxVerbosity chs) , ("Dates", showChs $ dates chs) diff --git a/code/drasil-code/Language/Drasil/Code/Imperative/GenODE.hs b/code/drasil-code/Language/Drasil/Code/Imperative/GenODE.hs index 209cf97dbe..75a43b64f8 100644 --- a/code/drasil-code/Language/Drasil/Code/Imperative/GenODE.hs +++ b/code/drasil-code/Language/Drasil/Code/Imperative/GenODE.hs @@ -20,19 +20,21 @@ type ODEGenInfo = (Maybe FilePath, [(Name, ExtLibState)], (Name,Version)) -- 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' 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 Doc ODEGenInfo chooseODELib _ _ [] = return (Nothing, [], ("","")) chooseODELib l olps odes = chooseODELib' olps olps - where chooseODELib' :: [ODELibPckg] -> [ODELibPckg]->State Doc ODEGenInfo + where chooseODELib' :: [ODELibPckg] -> [ODELibPckg] -> State Doc ODEGenInfo chooseODELib' _ [] = error $ "None of the chosen ODE libraries are " ++ "compatible with " ++ show l - chooseODELib' initLib (o:os) = if l `elem` compatibleLangs o + chooseODELib' prefLibList (o:os) = if l `elem` compatibleLangs o then do - modify ($$ firstChoiceODELib initLib o) + 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' initLib 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. @@ -40,6 +42,8 @@ incompatibleLib :: Lang -> ODELibPckg -> Doc incompatibleLib lng lib = text $ "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 -> Doc firstChoiceODELib prefer olp = if libName (head prefer) == libName olp then text $ "Successfully " ++"selected first choice ODELibPckg "++ From befe50308837f8456606b6434f463e2bdb6a3fc8 Mon Sep 17 00:00:00 2001 From: muhammad ali Date: Mon, 6 Jul 2020 11:59:21 -0400 Subject: [PATCH 3/9] Making choose automatically find uid's --- code/drasil-code/Language/Drasil/Choices.hs | 2 +- .../Language/Drasil/Code/Imperative/ConceptMatch.hs | 11 +++++++++-- .../Language/Drasil/Code/Imperative/GenODE.hs | 2 +- 3 files changed, 11 insertions(+), 4 deletions(-) diff --git a/code/drasil-code/Language/Drasil/Choices.hs b/code/drasil-code/Language/Drasil/Choices.hs index 11671f9daa..df49fef041 100644 --- a/code/drasil-code/Language/Drasil/Choices.hs +++ b/code/drasil-code/Language/Drasil/Choices.hs @@ -128,7 +128,7 @@ 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 = "Pi" diff --git a/code/drasil-code/Language/Drasil/Code/Imperative/ConceptMatch.hs b/code/drasil-code/Language/Drasil/Code/Imperative/ConceptMatch.hs index b931d75f28..2d3e9be76c 100644 --- a/code/drasil-code/Language/Drasil/Code/Imperative/ConceptMatch.hs +++ b/code/drasil-code/Language/Drasil/Code/Imperative/ConceptMatch.hs @@ -3,26 +3,30 @@ module Language.Drasil.Code.Imperative.ConceptMatch ( chooseConcept, conceptToGOOL ) where +import Language.Drasil (UID) + import Language.Drasil.Choices (Choices(..), CodeConcept(..), ConceptMatchMap, MatchedConceptMap, showChs) import GOOL.Drasil (SValue, OOProg, MathConstant(..)) import Prelude hiding (pi) -import qualified Data.Map as Map (map, keys) +import qualified Data.Map as Map (map, keys, lookup) import Control.Monad.State (State, modify) import Text.PrettyPrint.HughesPJ (Doc, text, ($$)) -- | 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 +-- The conceptMatchMap from choices is passed to chooseConept' internally, this way +-- any codeconcept list can be matched to its appropiate UID chooseConcept :: Choices -> State Doc MatchedConceptMap chooseConcept chs = sequence $ Map.map (chooseConcept' chs $ conceptMatch chs) (conceptMatch chs) where chooseConcept' :: Choices -> ConceptMatchMap-> [CodeConcept] -> State Doc CodeConcept chooseConcept' _ _ [] = error $ "Empty list of CodeConcepts in the " ++ "ConceptMatchMap" chooseConcept' _ cmm cs = do - let uid = (head . Map.keys) cmm + let uid = findUid (Map.keys cmm) cmm cs modify ($$ (text $ "Code Concept "++ uid ++" selected as " ++ showChs (head cs))) return $ head cs @@ -30,3 +34,6 @@ chooseConcept chs = sequence $ Map.map (chooseConcept' chs $ conceptMatch chs) ( conceptToGOOL :: (OOProg r) => CodeConcept -> SValue r conceptToGOOL Pi = pi +findUid :: [UID] -> ConceptMatchMap -> [CodeConcept] -> UID +findUid [] _ _ = error "CodeConcept not in Concept Match Map" +findUid (x:xs) mapp cs = if Map.lookup x mapp == (Just cs) then x else findUid xs mapp cs \ No newline at end of file diff --git a/code/drasil-code/Language/Drasil/Code/Imperative/GenODE.hs b/code/drasil-code/Language/Drasil/Code/Imperative/GenODE.hs index 75a43b64f8..742ed92af6 100644 --- a/code/drasil-code/Language/Drasil/Code/Imperative/GenODE.hs +++ b/code/drasil-code/Language/Drasil/Code/Imperative/GenODE.hs @@ -46,5 +46,5 @@ incompatibleLib lng lib = text $ "Language " ++ show lng ++ " is not " ++ -- the preference list that the user selected, is compatible with the given Lang. firstChoiceODELib :: [ODELibPckg] -> ODELibPckg -> Doc firstChoiceODELib prefer olp = if libName (head prefer) == libName olp then - text $ "Successfully " ++"selected first choice ODELibPckg "++ + text $ "Successfully " ++"selected first choice ODE Library package "++ libName olp else empty \ No newline at end of file From 45793b53c4fc67ec03849386827977d655935fcb Mon Sep 17 00:00:00 2001 From: muhammad ali Date: Wed, 8 Jul 2020 16:01:12 -0400 Subject: [PATCH 4/9] Matching UID to CodeConcept --- .../Drasil/Code/Imperative/ConceptMatch.hs | 29 +++++++++---------- 1 file changed, 14 insertions(+), 15 deletions(-) diff --git a/code/drasil-code/Language/Drasil/Code/Imperative/ConceptMatch.hs b/code/drasil-code/Language/Drasil/Code/Imperative/ConceptMatch.hs index 2d3e9be76c..0d90764b33 100644 --- a/code/drasil-code/Language/Drasil/Code/Imperative/ConceptMatch.hs +++ b/code/drasil-code/Language/Drasil/Code/Imperative/ConceptMatch.hs @@ -5,13 +5,13 @@ module Language.Drasil.Code.Imperative.ConceptMatch ( import Language.Drasil (UID) -import Language.Drasil.Choices (Choices(..), CodeConcept(..), ConceptMatchMap, +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, keys, lookup) +import qualified Data.Map as Map (map, mapWithKey) import Control.Monad.State (State, modify) import Text.PrettyPrint.HughesPJ (Doc, text, ($$)) @@ -20,20 +20,19 @@ import Text.PrettyPrint.HughesPJ (Doc, text, ($$)) -- being mapped, so we just take the head of the list of CodeConcepts -- The conceptMatchMap from choices is passed to chooseConept' internally, this way -- any codeconcept list can be matched to its appropiate UID + chooseConcept :: Choices -> State Doc MatchedConceptMap -chooseConcept chs = sequence $ Map.map (chooseConcept' chs $ conceptMatch chs) (conceptMatch chs) - where chooseConcept' :: Choices -> ConceptMatchMap-> [CodeConcept] -> State Doc CodeConcept - chooseConcept' _ _ [] = error $ "Empty list of CodeConcepts in the " ++ +chooseConcept chs = sequence . addMatchLog $ Map.map (chooseConcept' chs) (conceptMatch chs) + where chooseConcept' _ [] = error $ "Empty list of CodeConcepts in the " ++ "ConceptMatchMap" - chooseConcept' _ cmm cs = do - let uid = findUid (Map.keys cmm) cmm cs - modify ($$ (text $ "Code Concept "++ uid ++" selected as " ++ showChs (head cs))) - return $ head cs + chooseConcept' _ cs = return $ head cs + addMatchLog = Map.mapWithKey addMessage + +addMessage :: UID -> State Doc CodeConcept -> State Doc CodeConcept +addMessage uid s' = do + s <- s' + modify ($$ (text $ "Code Concept "++ uid ++" selected as " ++ showChs s)) + return s --- | Maps CodeConcepts to corresponding GOOL values conceptToGOOL :: (OOProg r) => CodeConcept -> SValue r -conceptToGOOL Pi = pi - -findUid :: [UID] -> ConceptMatchMap -> [CodeConcept] -> UID -findUid [] _ _ = error "CodeConcept not in Concept Match Map" -findUid (x:xs) mapp cs = if Map.lookup x mapp == (Just cs) then x else findUid xs mapp cs \ No newline at end of file +conceptToGOOL Pi = pi \ No newline at end of file From 4c1320f0e1c6481fb814a13fb87a1279dc27250c Mon Sep 17 00:00:00 2001 From: muhammad ali Date: Fri, 17 Jul 2020 14:50:00 -0400 Subject: [PATCH 5/9] Making the states of log messages use sentences instead of docs --- code/drasil-code/Language/Drasil/Choices.hs | 102 +++++++++--------- .../Drasil/Code/Imperative/ConceptMatch.hs | 23 ++-- .../Language/Drasil/Code/Imperative/GenODE.hs | 20 ++-- .../Drasil/Code/Imperative/Generator.hs | 15 +-- .../Drasil/Code/Imperative/SpaceMatch.hs | 2 +- 5 files changed, 79 insertions(+), 83 deletions(-) diff --git a/code/drasil-code/Language/Drasil/Choices.hs b/code/drasil-code/Language/Drasil/Choices.hs index df49fef041..4eb4fcae0b 100644 --- a/code/drasil-code/Language/Drasil/Choices.hs +++ b/code/drasil-code/Language/Drasil/Choices.hs @@ -5,10 +5,11 @@ module Language.Drasil.Choices ( CodeConcept(..), matchConcepts, SpaceMatch, matchSpaces, ImplementationType(..), ConstraintBehaviour(..), Comments(..), Verbosity(..), Visibility(..), Logging(..), AuxFile(..), getSampleData, hasSampleInput, hasReadMe, defaultChoices, - choicesDoc, showChs + choicesSent, showChs ) where import Language.Drasil +import Utils.Drasil (foldlSent) import Language.Drasil.Code.Code (spaceToCodeType) import Language.Drasil.Code.Lang (Lang(..)) @@ -19,7 +20,6 @@ import GOOL.Drasil (CodeType) import Control.Lens ((^.)) import Data.Map (Map, fromList) -import Text.PrettyPrint.HughesPJ (Doc, text, vcat) data Choices = Choices { -- Global design choices (affect entire program) @@ -70,18 +70,18 @@ data Choices = Choices { } class RenderChoices a where - showChs :: a -> String - showChsList :: [a] -> String - showChsList lst = show $ map showChs lst + 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 = "Unmodular" - showChs (Modular Combined) = "Modular Combined" - showChs (Modular Separated)= "Modular Separated" + 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 @@ -98,8 +98,8 @@ data Structure = Unbundled -- Individual variables | Bundled -- Variables bundled in a class instance RenderChoices Structure where - showChs Unbundled = "Unbundled" - showChs Bundled = "Bundled" + showChs Unbundled = S "Unbundled" + showChs Bundled = S "Bundled" data ConstantStructure = Inline -- Inline values for constants | WithInputs -- Store constants with inputs @@ -107,17 +107,17 @@ data ConstantStructure = Inline -- Inline values for constants -- inputs, whether bundled or unbundled instance RenderChoices ConstantStructure where - showChs Inline = "Inline" - showChs WithInputs = "WithInputs" - showChs (Store Unbundled) = "Store Unbundled" - showChs (Store Bundled) = "Store Bundled" + 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 = "Var" - showChs Const = "Const" + 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 @@ -131,7 +131,7 @@ type MatchedConceptMap = Map UID CodeConcept data CodeConcept = Pi deriving Eq instance RenderChoices CodeConcept where - showChs Pi = "Pi" + showChs Pi = S "Pi" -- | Builds a ConceptMatchMap from an association list of chunks and CodeConcepts matchConcepts :: (HasUID c) => [(c, [CodeConcept])] -> ConceptMatchMap @@ -157,16 +157,16 @@ data ImplementationType = Library -- Generated code does not include Controller | Program -- Generated code includes Controller instance RenderChoices ImplementationType where - showChs Library = "Library" - showChs Program = "Program" + 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 = "Warning" - showChs Exception = "Exception" + showChs Warning = S "Warning" + showChs Exception = S "Exception" data Comments = CommentFunc -- Function/method-level comments | CommentClass -- class-level comments @@ -174,22 +174,22 @@ data Comments = CommentFunc -- Function/method-level comments deriving Eq instance RenderChoices Comments where - showChs CommentFunc = "CommentFunc" - showChs CommentClass = "CommentClass" - showChs CommentMod = "CommentMod" + showChs CommentFunc = S "CommentFunc" + showChs CommentClass = S "CommentClass" + showChs CommentMod = S "CommentMod" data Verbosity = Verbose | Quiet instance RenderChoices Verbosity where - showChs Verbose = "Verbose" - showChs Quiet = "Quiet" + showChs Verbose = S "Verbose" + showChs Quiet = S "Quiet" data Visibility = Show | Hide instance RenderChoices Visibility where - showChs Show = "Show" - showChs Hide = "Hide" + 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 @@ -198,8 +198,8 @@ data Logging = LogFunc -- Log messages generated for function calls deriving Eq instance RenderChoices Logging where - showChs LogFunc = "LogFunc" - showChs LogVar = "LogVar" + 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 @@ -209,8 +209,8 @@ data AuxFile = SampleInput FilePath deriving Eq instance RenderChoices AuxFile where - showChs (SampleInput fp) = "SampleInput"++fp - showChs ReadME = "ReadME" + 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. @@ -255,25 +255,23 @@ defaultChoices = Choices { odes = [] } -choicesDoc :: Choices -> Doc -choicesDoc chs = (vcat. map chsFieldDoc) [ - ("Languages", show $ lang chs) - , ("Modularity", showChs $ modularity chs) - , ("Input Structure", showChs $ inputStructure chs) - , ("Constant Structure", showChs $ constStructure chs) - , ("Constant Representation", showChs $ constRepr chs) - , ("Implementation Type", showChs $ impType chs) - , ("Software Constraint Behaviour", showChs $ onSfwrConstraint chs) - , ("Physical Constraint Behaviour", showChs $ onPhysConstraint chs) - , ("Comments", showChsList $ comments chs) - , ("Dox Verbosity", showChs $ doxVerbosity chs) - , ("Dates", showChs $ dates chs) - , ("Log File Name", logFile chs) - , ("Logging", showChsList $ logging chs) - , ("Auxiliary Files", showChsList $ auxFiles chs) --- , ("ODE Libraries", odeLib chs) --- , ("ODE's", odes chs) along with conceptmatch and speace match +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) ] -chsFieldDoc :: (String, String) -> Doc -chsFieldDoc (rec, chc) = text $ rec ++ " selected as " ++ chc \ No newline at end of file +chsFieldSent :: (Sentence, Sentence) -> Sentence +chsFieldSent (rec, chc) = rec +:+ S "selected as" +:+. chc \ No newline at end of file diff --git a/code/drasil-code/Language/Drasil/Code/Imperative/ConceptMatch.hs b/code/drasil-code/Language/Drasil/Code/Imperative/ConceptMatch.hs index 0d90764b33..bb642a8c23 100644 --- a/code/drasil-code/Language/Drasil/Code/Imperative/ConceptMatch.hs +++ b/code/drasil-code/Language/Drasil/Code/Imperative/ConceptMatch.hs @@ -3,7 +3,7 @@ module Language.Drasil.Code.Imperative.ConceptMatch ( chooseConcept, conceptToGOOL ) where -import Language.Drasil (UID) +import Language.Drasil (UID, Sentence(S), (+:+), (+:+.)) import Language.Drasil.Choices (Choices(..), CodeConcept(..), MatchedConceptMap, showChs) @@ -11,9 +11,8 @@ import Language.Drasil.Choices (Choices(..), CodeConcept(..), import GOOL.Drasil (SValue, OOProg, MathConstant(..)) import Prelude hiding (pi) -import qualified Data.Map as Map (map, mapWithKey) +import qualified Data.Map as Map (mapWithKey) import Control.Monad.State (State, modify) -import Text.PrettyPrint.HughesPJ (Doc, text, ($$)) -- | Concretizes the ConceptMatchMap in Choices to a MatchedConceptMap. -- Currently we don't have any Choices that would prevent a CodeConcept from @@ -21,18 +20,14 @@ import Text.PrettyPrint.HughesPJ (Doc, text, ($$)) -- The conceptMatchMap from choices is passed to chooseConept' internally, this way -- any codeconcept list can be matched to its appropiate UID -chooseConcept :: Choices -> State Doc MatchedConceptMap -chooseConcept chs = sequence . addMatchLog $ Map.map (chooseConcept' chs) (conceptMatch chs) - where chooseConcept' _ [] = error $ "Empty list of CodeConcepts in the " ++ +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 - addMatchLog = Map.mapWithKey addMessage - -addMessage :: UID -> State Doc CodeConcept -> State Doc CodeConcept -addMessage uid s' = do - s <- s' - modify ($$ (text $ "Code Concept "++ uid ++" selected as " ++ showChs s)) - return s + chooseConcept' uid (c:_) = do + modify (++ [S "Code Concept" +:+ S uid +:+ S "selected as" +:+. showChs c]) + return c conceptToGOOL :: (OOProg r) => CodeConcept -> SValue r conceptToGOOL Pi = pi \ No newline at end of file diff --git a/code/drasil-code/Language/Drasil/Code/Imperative/GenODE.hs b/code/drasil-code/Language/Drasil/Code/Imperative/GenODE.hs index 742ed92af6..8318a04cb1 100644 --- a/code/drasil-code/Language/Drasil/Code/Imperative/GenODE.hs +++ b/code/drasil-code/Language/Drasil/Code/Imperative/GenODE.hs @@ -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(..)) @@ -12,7 +13,6 @@ import Language.Drasil.Data.ODEInfo (ODEInfo) import Language.Drasil.Data.ODELibPckg (ODELibPckg(..)) import Control.Monad.State (State, modify) -import Text.PrettyPrint.HughesPJ (Doc, ($$), text, empty) type ODEGenInfo = (Maybe FilePath, [(Name, ExtLibState)], (Name,Version)) @@ -22,29 +22,29 @@ type ODEGenInfo = (Maybe FilePath, [(Name, ExtLibState)], (Name,Version)) -- ODELibPckg by concretizing the ExternalLibraryCall with each of the ODEInfos -- 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 Doc ODEGenInfo +chooseODELib :: Lang -> [ODELibPckg] -> [ODEInfo] -> State [Sentence] ODEGenInfo chooseODELib _ _ [] = return (Nothing, [], ("","")) chooseODELib l olps odes = chooseODELib' olps olps - where chooseODELib' :: [ODELibPckg] -> [ODELibPckg] -> State Doc ODEGenInfo + where chooseODELib' :: [ODELibPckg] -> [ODELibPckg] -> State [Sentence] ODEGenInfo chooseODELib' _ [] = error $ "None of the chosen ODE libraries are " ++ "compatible with " ++ show l chooseODELib' prefLibList (o:os) = if l `elem` compatibleLangs o then do - modify ($$ firstChoiceODELib prefLibList o) + 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' prefLibList 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 " ++ +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 -> Doc +firstChoiceODELib :: [ODELibPckg] -> ODELibPckg -> Sentence firstChoiceODELib prefer olp = if libName (head prefer) == libName olp then - text $ "Successfully " ++"selected first choice ODE Library package "++ - libName olp else empty \ No newline at end of file + S "Successfully selected first choice ODE Library package" +:+. S (libName olp) + else S "ODE Library package selected as" +:+. S (libName olp) \ No newline at end of file diff --git a/code/drasil-code/Language/Drasil/Code/Imperative/Generator.hs b/code/drasil-code/Language/Drasil/Code/Imperative/Generator.hs index 05428b4032..c3da587223 100644 --- a/code/drasil-code/Language/Drasil/Code/Imperative/Generator.hs +++ b/code/drasil-code/Language/Drasil/Code/Imperative/Generator.hs @@ -26,8 +26,9 @@ 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(..), - choicesDoc) + choicesSent) import Language.Drasil.CodeSpec (CodeSpec(..)) +import Language.Drasil.Printers (Linearity(Linear), sentenceDoc) import GOOL.Drasil (GSProgram, SFile, OOProg, ProgramSym(..), ScopeTag(..), ProgData(..), initialState, unCI) @@ -39,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. @@ -76,21 +77,23 @@ generator l dt sd chs spec = DrasilState { -- stateful currentModule = "", currentClass = "", - _designLog = nonPrefChs $$ 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 = choicesDoc chs + 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 diff --git a/code/drasil-code/Language/Drasil/Code/Imperative/SpaceMatch.hs b/code/drasil-code/Language/Drasil/Code/Imperative/SpaceMatch.hs index e96db73640..5a3cd2202d 100644 --- a/code/drasil-code/Language/Drasil/Code/Imperative/SpaceMatch.hs +++ b/code/drasil-code/Language/Drasil/Code/Imperative/SpaceMatch.hs @@ -38,4 +38,4 @@ incompatibleType l s t = text $ "Language " ++ show l ++ " does not support " " space. Trying next choice." successLog :: Space -> CodeType -> Doc -successLog s t = text $ "Successfully matched "++show s ++ " with "++ show t \ No newline at end of file +successLog s t = text ("Successfully matched "++show s ++ " with "++ show t ++".") \ No newline at end of file From dd53246f5f7caddc047942847991965991065c55 Mon Sep 17 00:00:00 2001 From: muhammad ali Date: Fri, 17 Jul 2020 15:15:37 -0400 Subject: [PATCH 6/9] Adding the designlog to stable --- code/stable/glassbr/src/cpp/designLog.txt | 24 ++++++++++++++ code/stable/glassbr/src/csharp/designLog.txt | 24 ++++++++++++++ code/stable/glassbr/src/java/designLog.txt | 24 ++++++++++++++ code/stable/glassbr/src/python/designLog.txt | 24 ++++++++++++++ code/stable/glassbr/src/swift/designLog.txt | 24 ++++++++++++++ code/stable/nopcm/src/cpp/designLog.txt | 27 ++++++++++++++++ code/stable/nopcm/src/csharp/designLog.txt | 27 ++++++++++++++++ code/stable/nopcm/src/java/designLog.txt | 31 +++++++++++++++++++ code/stable/nopcm/src/python/designLog.txt | 26 ++++++++++++++++ .../src/cpp/designLog.txt | 20 ++++++++++++ .../src/csharp/designLog.txt | 20 ++++++++++++ .../src/java/designLog.txt | 20 ++++++++++++ .../src/python/designLog.txt | 20 ++++++++++++ .../src/swift/designLog.txt | 20 ++++++++++++ .../src/cpp/designLog.txt | 18 +++++++++++ .../src/csharp/designLog.txt | 18 +++++++++++ .../src/java/designLog.txt | 18 +++++++++++ .../src/python/designLog.txt | 18 +++++++++++ .../src/swift/designLog.txt | 18 +++++++++++ .../src/cpp/designLog.txt | 20 ++++++++++++ .../src/csharp/designLog.txt | 20 ++++++++++++ .../src/java/designLog.txt | 20 ++++++++++++ .../src/python/designLog.txt | 20 ++++++++++++ .../src/swift/designLog.txt | 20 ++++++++++++ .../src/cpp/designLog.txt | 20 ++++++++++++ .../src/csharp/designLog.txt | 20 ++++++++++++ .../src/java/designLog.txt | 20 ++++++++++++ .../src/python/designLog.txt | 20 ++++++++++++ .../src/swift/designLog.txt | 20 ++++++++++++ .../src/cpp/designLog.txt | 20 ++++++++++++ .../src/csharp/designLog.txt | 20 ++++++++++++ .../src/java/designLog.txt | 20 ++++++++++++ .../src/python/designLog.txt | 20 ++++++++++++ .../src/swift/designLog.txt | 20 ++++++++++++ 34 files changed, 721 insertions(+) create mode 100644 code/stable/glassbr/src/cpp/designLog.txt create mode 100644 code/stable/glassbr/src/csharp/designLog.txt create mode 100644 code/stable/glassbr/src/java/designLog.txt create mode 100644 code/stable/glassbr/src/python/designLog.txt create mode 100644 code/stable/glassbr/src/swift/designLog.txt create mode 100644 code/stable/nopcm/src/python/designLog.txt create mode 100644 code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/cpp/designLog.txt create mode 100644 code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/csharp/designLog.txt create mode 100644 code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/java/designLog.txt create mode 100644 code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/python/designLog.txt create mode 100644 code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/swift/designLog.txt create mode 100644 code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/cpp/designLog.txt create mode 100644 code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/csharp/designLog.txt create mode 100644 code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/java/designLog.txt create mode 100644 code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/swift/designLog.txt create mode 100644 code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/cpp/designLog.txt create mode 100644 code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/csharp/designLog.txt create mode 100644 code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/java/designLog.txt create mode 100644 code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/python/designLog.txt create mode 100644 code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/swift/designLog.txt create mode 100644 code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/cpp/designLog.txt create mode 100644 code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/csharp/designLog.txt create mode 100644 code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/java/designLog.txt create mode 100644 code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/swift/designLog.txt create mode 100644 code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/cpp/designLog.txt create mode 100644 code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/csharp/designLog.txt create mode 100644 code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/java/designLog.txt create mode 100644 code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/python/designLog.txt create mode 100644 code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/swift/designLog.txt diff --git a/code/stable/glassbr/src/cpp/designLog.txt b/code/stable/glassbr/src/cpp/designLog.txt new file mode 100644 index 0000000000..8d5330da2c --- /dev/null +++ b/code/stable/glassbr/src/cpp/designLog.txt @@ -0,0 +1,24 @@ +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 Integer with Integer. +Successfully matched Natural with Integer. +Successfully matched Vect Real with List Double. +Successfully matched Vect (Vect Real) with List (List Double). diff --git a/code/stable/glassbr/src/csharp/designLog.txt b/code/stable/glassbr/src/csharp/designLog.txt new file mode 100644 index 0000000000..8d5330da2c --- /dev/null +++ b/code/stable/glassbr/src/csharp/designLog.txt @@ -0,0 +1,24 @@ +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 Integer with Integer. +Successfully matched Natural with Integer. +Successfully matched Vect Real with List Double. +Successfully matched Vect (Vect Real) with List (List Double). diff --git a/code/stable/glassbr/src/java/designLog.txt b/code/stable/glassbr/src/java/designLog.txt new file mode 100644 index 0000000000..8d5330da2c --- /dev/null +++ b/code/stable/glassbr/src/java/designLog.txt @@ -0,0 +1,24 @@ +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 Integer with Integer. +Successfully matched Natural with Integer. +Successfully matched Vect Real with List Double. +Successfully matched Vect (Vect Real) with List (List Double). diff --git a/code/stable/glassbr/src/python/designLog.txt b/code/stable/glassbr/src/python/designLog.txt new file mode 100644 index 0000000000..8d5330da2c --- /dev/null +++ b/code/stable/glassbr/src/python/designLog.txt @@ -0,0 +1,24 @@ +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 Integer with Integer. +Successfully matched Natural with Integer. +Successfully matched Vect Real with List Double. +Successfully matched Vect (Vect Real) with List (List Double). diff --git a/code/stable/glassbr/src/swift/designLog.txt b/code/stable/glassbr/src/swift/designLog.txt new file mode 100644 index 0000000000..8d5330da2c --- /dev/null +++ b/code/stable/glassbr/src/swift/designLog.txt @@ -0,0 +1,24 @@ +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 Integer with Integer. +Successfully matched Natural with Integer. +Successfully matched Vect Real with List Double. +Successfully matched Vect (Vect Real) with List (List Double). diff --git a/code/stable/nopcm/src/cpp/designLog.txt b/code/stable/nopcm/src/cpp/designLog.txt index 176372885b..885f72ec61 100644 --- a/code/stable/nopcm/src/cpp/designLog.txt +++ b/code/stable/nopcm/src/cpp/designLog.txt @@ -1,3 +1,30 @@ +Languages selected as Python Cpp CSharp Java.. +Modularity selected as Modular Combined. +Input Structure selected as Unbundled. +Constant Structure selected as Store Bundled. +Constant Representation selected as Const. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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. +Auxiliary Files selected as SampleInput ../../datafiles/NoPCM/sampleInput.txt ReadME.. Language Cpp is not compatible with chosen library SciPy, trying next choice. Language Cpp is not compatible with chosen library OSLO, trying next choice. Language Cpp is not compatible with chosen library Apache, trying next choice. +ODE Library package selected as odeint. +Successfully matched String with String. +Successfully matched Actor "Constants" with Object "Constants". +Successfully matched Actor "InputParameters" with Object "InputParameters". +Successfully matched Rational with Double. +Successfully matched Real with Double. +Successfully matched Vect Rational with List Double. +Successfully matched Actor "ODE" with Object "ODE". +Successfully matched Vect Real with List Double. +Successfully matched Actor "Populate" with Object "Populate". +Successfully matched Actor "boost::numeric::odeint::runge_kutta_dopri5>" with Object "boost::numeric::odeint::runge_kutta_dopri5>". +Successfully matched Actor "auto" with Object "auto". +Successfully matched Void with Void. diff --git a/code/stable/nopcm/src/csharp/designLog.txt b/code/stable/nopcm/src/csharp/designLog.txt index 006ff6d2eb..e7cd5050a6 100644 --- a/code/stable/nopcm/src/csharp/designLog.txt +++ b/code/stable/nopcm/src/csharp/designLog.txt @@ -1 +1,28 @@ +Languages selected as Python Cpp CSharp Java.. +Modularity selected as Modular Combined. +Input Structure selected as Unbundled. +Constant Structure selected as Store Bundled. +Constant Representation selected as Const. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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. +Auxiliary Files selected as SampleInput ../../datafiles/NoPCM/sampleInput.txt ReadME.. Language CSharp is not compatible with chosen library SciPy, trying next choice. +ODE Library package selected as OSLO. +Successfully matched String with String. +Successfully matched Actor "Constants" with Object "Constants". +Successfully matched Actor "InputParameters" with Object "InputParameters". +Successfully matched Rational with Double. +Successfully matched Real with Double. +Successfully matched Vect Rational with List Double. +Successfully matched Actor "Vector" with Object "Vector". +Successfully matched Array Rational with Array Double. +Successfully matched Actor "Options" with Object "Options". +Successfully matched Actor "IEnumerable" with Object "IEnumerable". +Successfully matched Array Real with Array Double. +Successfully matched Actor "SolPoint" with Object "SolPoint". diff --git a/code/stable/nopcm/src/java/designLog.txt b/code/stable/nopcm/src/java/designLog.txt index a0b2cd33cf..819944a55f 100644 --- a/code/stable/nopcm/src/java/designLog.txt +++ b/code/stable/nopcm/src/java/designLog.txt @@ -1,2 +1,33 @@ +Languages selected as Python Cpp CSharp Java.. +Modularity selected as Modular Combined. +Input Structure selected as Unbundled. +Constant Structure selected as Store Bundled. +Constant Representation selected as Const. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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. +Auxiliary Files selected as SampleInput ../../datafiles/NoPCM/sampleInput.txt ReadME.. Language Java is not compatible with chosen library SciPy, trying next choice. Language Java is not compatible with chosen library OSLO, trying next choice. +ODE Library package selected as Apache. +Successfully matched String with String. +Successfully matched Actor "Constants" with Object "Constants". +Successfully matched Actor "InputParameters" with Object "InputParameters". +Successfully matched Rational with Double. +Successfully matched Real with Double. +Successfully matched Vect Rational with List Double. +Successfully matched Actor "ODEStepHandler" with Object "ODEStepHandler". +Successfully matched Actor "ODE" with Object "ODE". +Successfully matched Array Real with Array Double. +Successfully matched Actor "FirstOrderIntegrator" with Object "FirstOrderIntegrator". +Successfully matched Actor "DormandPrince54Integrator" with Object "DormandPrince54Integrator". +Successfully matched Void with Void. +Successfully matched Natural with Integer. +Successfully matched Array Rational with Array Double. +Successfully matched Actor "StepInterpolator" with Object "StepInterpolator". +Successfully matched Boolean with Boolean. diff --git a/code/stable/nopcm/src/python/designLog.txt b/code/stable/nopcm/src/python/designLog.txt new file mode 100644 index 0000000000..58323a2b87 --- /dev/null +++ b/code/stable/nopcm/src/python/designLog.txt @@ -0,0 +1,26 @@ +Languages selected as Python Cpp CSharp Java.. +Modularity selected as Modular Combined. +Input Structure selected as Unbundled. +Constant Structure selected as Store Bundled. +Constant Representation selected as Const. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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. +Auxiliary Files selected as SampleInput ../../datafiles/NoPCM/sampleInput.txt ReadME.. +Successfully selected first choice ODE Library package SciPy. +Successfully matched String with String. +Successfully matched Actor "Constants" with Object "Constants". +Successfully matched Actor "InputParameters" with Object "InputParameters". +Successfully matched Rational with Double. +Successfully matched Real with Double. +Successfully matched Vect Rational with List Double. +Successfully matched Array Real with Array Double. +Successfully matched Actor "ode" with Object "ode". +Successfully matched Void with Void. +Successfully matched Vect Real with List Double. +Successfully matched Boolean with Boolean. diff --git a/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/cpp/designLog.txt b/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/cpp/designLog.txt new file mode 100644 index 0000000000..7c065d42b7 --- /dev/null +++ b/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/cpp/designLog.txt @@ -0,0 +1,20 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Modular Combined. +Input Structure selected as Bundled. +Constant Structure selected as Store Unbundled. +Constant Representation selected as Var. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched String with String. +Successfully matched Actor "Constants" with Object "Constants". +Successfully matched Real with Double. +Successfully matched Rational with Double. +Successfully matched Actor "InputParameters" with Object "InputParameters". diff --git a/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/csharp/designLog.txt b/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/csharp/designLog.txt new file mode 100644 index 0000000000..7c065d42b7 --- /dev/null +++ b/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/csharp/designLog.txt @@ -0,0 +1,20 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Modular Combined. +Input Structure selected as Bundled. +Constant Structure selected as Store Unbundled. +Constant Representation selected as Var. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched String with String. +Successfully matched Actor "Constants" with Object "Constants". +Successfully matched Real with Double. +Successfully matched Rational with Double. +Successfully matched Actor "InputParameters" with Object "InputParameters". diff --git a/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/java/designLog.txt b/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/java/designLog.txt new file mode 100644 index 0000000000..7c065d42b7 --- /dev/null +++ b/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/java/designLog.txt @@ -0,0 +1,20 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Modular Combined. +Input Structure selected as Bundled. +Constant Structure selected as Store Unbundled. +Constant Representation selected as Var. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched String with String. +Successfully matched Actor "Constants" with Object "Constants". +Successfully matched Real with Double. +Successfully matched Rational with Double. +Successfully matched Actor "InputParameters" with Object "InputParameters". diff --git a/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/python/designLog.txt b/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/python/designLog.txt new file mode 100644 index 0000000000..7c065d42b7 --- /dev/null +++ b/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/python/designLog.txt @@ -0,0 +1,20 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Modular Combined. +Input Structure selected as Bundled. +Constant Structure selected as Store Unbundled. +Constant Representation selected as Var. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched String with String. +Successfully matched Actor "Constants" with Object "Constants". +Successfully matched Real with Double. +Successfully matched Rational with Double. +Successfully matched Actor "InputParameters" with Object "InputParameters". diff --git a/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/swift/designLog.txt b/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/swift/designLog.txt new file mode 100644 index 0000000000..7c065d42b7 --- /dev/null +++ b/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/swift/designLog.txt @@ -0,0 +1,20 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Modular Combined. +Input Structure selected as Bundled. +Constant Structure selected as Store Unbundled. +Constant Representation selected as Var. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched String with String. +Successfully matched Actor "Constants" with Object "Constants". +Successfully matched Real with Double. +Successfully matched Rational with Double. +Successfully matched Actor "InputParameters" with Object "InputParameters". diff --git a/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/cpp/designLog.txt b/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/cpp/designLog.txt new file mode 100644 index 0000000000..73bc9d351e --- /dev/null +++ b/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/cpp/designLog.txt @@ -0,0 +1,18 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Modular Separated. +Input Structure selected as Unbundled. +Constant Structure selected as Store Unbundled. +Constant Representation selected as Var. +Implementation Type selected as Library. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched Real with Float. +Successfully matched String with String. +Successfully matched Rational with Float. diff --git a/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/csharp/designLog.txt b/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/csharp/designLog.txt new file mode 100644 index 0000000000..73bc9d351e --- /dev/null +++ b/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/csharp/designLog.txt @@ -0,0 +1,18 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Modular Separated. +Input Structure selected as Unbundled. +Constant Structure selected as Store Unbundled. +Constant Representation selected as Var. +Implementation Type selected as Library. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched Real with Float. +Successfully matched String with String. +Successfully matched Rational with Float. diff --git a/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/java/designLog.txt b/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/java/designLog.txt new file mode 100644 index 0000000000..73bc9d351e --- /dev/null +++ b/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/java/designLog.txt @@ -0,0 +1,18 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Modular Separated. +Input Structure selected as Unbundled. +Constant Structure selected as Store Unbundled. +Constant Representation selected as Var. +Implementation Type selected as Library. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched Real with Float. +Successfully matched String with String. +Successfully matched Rational with Float. diff --git a/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/python/designLog.txt b/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/python/designLog.txt index 6e232c6bfa..c5469b2d38 100644 --- a/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/python/designLog.txt +++ b/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/python/designLog.txt @@ -1,2 +1,20 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Modular Separated. +Input Structure selected as Unbundled. +Constant Structure selected as Store Unbundled. +Constant Representation selected as Var. +Implementation Type selected as Library. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. Language Python does not support code type Float, chosen as the match for the Real space. Trying next choice. +Successfully matched Real with Double. +Successfully matched String with String. Language Python does not support code type Float, chosen as the match for the Rational space. Trying next choice. +Successfully matched Rational with Double. diff --git a/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/swift/designLog.txt b/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/swift/designLog.txt new file mode 100644 index 0000000000..73bc9d351e --- /dev/null +++ b/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/swift/designLog.txt @@ -0,0 +1,18 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Modular Separated. +Input Structure selected as Unbundled. +Constant Structure selected as Store Unbundled. +Constant Representation selected as Var. +Implementation Type selected as Library. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched Real with Float. +Successfully matched String with String. +Successfully matched Rational with Float. diff --git a/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/cpp/designLog.txt b/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/cpp/designLog.txt new file mode 100644 index 0000000000..4cb5136969 --- /dev/null +++ b/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/cpp/designLog.txt @@ -0,0 +1,20 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Unmodular. +Input Structure selected as Bundled. +Constant Structure selected as Store Bundled. +Constant Representation selected as Const. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched Real with Double. +Successfully matched String with String. +Successfully matched Actor "InputParameters" with Object "InputParameters". +Successfully matched Rational with Double. +Successfully matched Actor "Constants" with Object "Constants". diff --git a/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/csharp/designLog.txt b/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/csharp/designLog.txt new file mode 100644 index 0000000000..4cb5136969 --- /dev/null +++ b/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/csharp/designLog.txt @@ -0,0 +1,20 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Unmodular. +Input Structure selected as Bundled. +Constant Structure selected as Store Bundled. +Constant Representation selected as Const. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched Real with Double. +Successfully matched String with String. +Successfully matched Actor "InputParameters" with Object "InputParameters". +Successfully matched Rational with Double. +Successfully matched Actor "Constants" with Object "Constants". diff --git a/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/java/designLog.txt b/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/java/designLog.txt new file mode 100644 index 0000000000..4cb5136969 --- /dev/null +++ b/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/java/designLog.txt @@ -0,0 +1,20 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Unmodular. +Input Structure selected as Bundled. +Constant Structure selected as Store Bundled. +Constant Representation selected as Const. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched Real with Double. +Successfully matched String with String. +Successfully matched Actor "InputParameters" with Object "InputParameters". +Successfully matched Rational with Double. +Successfully matched Actor "Constants" with Object "Constants". diff --git a/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/python/designLog.txt b/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/python/designLog.txt new file mode 100644 index 0000000000..4cb5136969 --- /dev/null +++ b/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/python/designLog.txt @@ -0,0 +1,20 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Unmodular. +Input Structure selected as Bundled. +Constant Structure selected as Store Bundled. +Constant Representation selected as Const. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched Real with Double. +Successfully matched String with String. +Successfully matched Actor "InputParameters" with Object "InputParameters". +Successfully matched Rational with Double. +Successfully matched Actor "Constants" with Object "Constants". diff --git a/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/swift/designLog.txt b/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/swift/designLog.txt new file mode 100644 index 0000000000..4cb5136969 --- /dev/null +++ b/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/swift/designLog.txt @@ -0,0 +1,20 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Unmodular. +Input Structure selected as Bundled. +Constant Structure selected as Store Bundled. +Constant Representation selected as Const. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched Real with Double. +Successfully matched String with String. +Successfully matched Actor "InputParameters" with Object "InputParameters". +Successfully matched Rational with Double. +Successfully matched Actor "Constants" with Object "Constants". diff --git a/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/cpp/designLog.txt b/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/cpp/designLog.txt new file mode 100644 index 0000000000..0d72e800c9 --- /dev/null +++ b/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/cpp/designLog.txt @@ -0,0 +1,20 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Unmodular. +Input Structure selected as Bundled. +Constant Structure selected as WithInputs. +Constant Representation selected as Var. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched Real with Float. +Successfully matched Rational with Float. +Successfully matched String with String. +Successfully matched Actor "InputParameters" with Object "InputParameters". +Successfully matched Actor "Constants" with Object "Constants". diff --git a/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/csharp/designLog.txt b/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/csharp/designLog.txt new file mode 100644 index 0000000000..0d72e800c9 --- /dev/null +++ b/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/csharp/designLog.txt @@ -0,0 +1,20 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Unmodular. +Input Structure selected as Bundled. +Constant Structure selected as WithInputs. +Constant Representation selected as Var. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched Real with Float. +Successfully matched Rational with Float. +Successfully matched String with String. +Successfully matched Actor "InputParameters" with Object "InputParameters". +Successfully matched Actor "Constants" with Object "Constants". diff --git a/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/java/designLog.txt b/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/java/designLog.txt new file mode 100644 index 0000000000..0d72e800c9 --- /dev/null +++ b/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/java/designLog.txt @@ -0,0 +1,20 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Unmodular. +Input Structure selected as Bundled. +Constant Structure selected as WithInputs. +Constant Representation selected as Var. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched Real with Float. +Successfully matched Rational with Float. +Successfully matched String with String. +Successfully matched Actor "InputParameters" with Object "InputParameters". +Successfully matched Actor "Constants" with Object "Constants". diff --git a/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/python/designLog.txt b/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/python/designLog.txt index 6e232c6bfa..94919cf79e 100644 --- a/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/python/designLog.txt +++ b/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/python/designLog.txt @@ -1,2 +1,22 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Unmodular. +Input Structure selected as Bundled. +Constant Structure selected as WithInputs. +Constant Representation selected as Var. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. Language Python does not support code type Float, chosen as the match for the Real space. Trying next choice. +Successfully matched Real with Double. Language Python does not support code type Float, chosen as the match for the Rational space. Trying next choice. +Successfully matched Rational with Double. +Successfully matched String with String. +Successfully matched Actor "InputParameters" with Object "InputParameters". +Successfully matched Actor "Constants" with Object "Constants". diff --git a/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/swift/designLog.txt b/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/swift/designLog.txt new file mode 100644 index 0000000000..0d72e800c9 --- /dev/null +++ b/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/swift/designLog.txt @@ -0,0 +1,20 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Unmodular. +Input Structure selected as Bundled. +Constant Structure selected as WithInputs. +Constant Representation selected as Var. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched Real with Float. +Successfully matched Rational with Float. +Successfully matched String with String. +Successfully matched Actor "InputParameters" with Object "InputParameters". +Successfully matched Actor "Constants" with Object "Constants". diff --git a/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/cpp/designLog.txt b/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/cpp/designLog.txt new file mode 100644 index 0000000000..01170220d8 --- /dev/null +++ b/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/cpp/designLog.txt @@ -0,0 +1,20 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Unmodular. +Input Structure selected as Unbundled. +Constant Structure selected as WithInputs. +Constant Representation selected as Var. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched String with String. +Successfully matched Actor "Constants" with Object "Constants". +Successfully matched Real with Double. +Successfully matched Rational with Double. +Successfully matched Actor "InputParameters" with Object "InputParameters". diff --git a/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/csharp/designLog.txt b/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/csharp/designLog.txt new file mode 100644 index 0000000000..01170220d8 --- /dev/null +++ b/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/csharp/designLog.txt @@ -0,0 +1,20 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Unmodular. +Input Structure selected as Unbundled. +Constant Structure selected as WithInputs. +Constant Representation selected as Var. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched String with String. +Successfully matched Actor "Constants" with Object "Constants". +Successfully matched Real with Double. +Successfully matched Rational with Double. +Successfully matched Actor "InputParameters" with Object "InputParameters". diff --git a/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/java/designLog.txt b/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/java/designLog.txt new file mode 100644 index 0000000000..01170220d8 --- /dev/null +++ b/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/java/designLog.txt @@ -0,0 +1,20 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Unmodular. +Input Structure selected as Unbundled. +Constant Structure selected as WithInputs. +Constant Representation selected as Var. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched String with String. +Successfully matched Actor "Constants" with Object "Constants". +Successfully matched Real with Double. +Successfully matched Rational with Double. +Successfully matched Actor "InputParameters" with Object "InputParameters". diff --git a/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/python/designLog.txt b/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/python/designLog.txt new file mode 100644 index 0000000000..01170220d8 --- /dev/null +++ b/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/python/designLog.txt @@ -0,0 +1,20 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Unmodular. +Input Structure selected as Unbundled. +Constant Structure selected as WithInputs. +Constant Representation selected as Var. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched String with String. +Successfully matched Actor "Constants" with Object "Constants". +Successfully matched Real with Double. +Successfully matched Rational with Double. +Successfully matched Actor "InputParameters" with Object "InputParameters". diff --git a/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/swift/designLog.txt b/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/swift/designLog.txt new file mode 100644 index 0000000000..01170220d8 --- /dev/null +++ b/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/swift/designLog.txt @@ -0,0 +1,20 @@ +Languages selected as Python Cpp CSharp Java Swift.. +Modularity selected as Unmodular. +Input Structure selected as Unbundled. +Constant Structure selected as WithInputs. +Constant Representation selected as Var. +Implementation Type selected as Program. +Software Constraint Behaviour selected as Warning. +Physical Constraint Behaviour selected as Warning. +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. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Code Concept pi selected as Pi. +Successfully matched String with String. +Successfully matched Actor "Constants" with Object "Constants". +Successfully matched Real with Double. +Successfully matched Rational with Double. +Successfully matched Actor "InputParameters" with Object "InputParameters". From 297ad968a53c56052ed520d4aaabdf36d507c666 Mon Sep 17 00:00:00 2001 From: muhammad ali Date: Mon, 20 Jul 2020 11:28:18 -0400 Subject: [PATCH 7/9] Making the branch match stable --- code/drasil-code/Language/Drasil/Choices.hs | 9 ++------- 1 file changed, 2 insertions(+), 7 deletions(-) diff --git a/code/drasil-code/Language/Drasil/Choices.hs b/code/drasil-code/Language/Drasil/Choices.hs index 7609e98f85..739420a859 100644 --- a/code/drasil-code/Language/Drasil/Choices.hs +++ b/code/drasil-code/Language/Drasil/Choices.hs @@ -4,13 +4,8 @@ module Language.Drasil.Choices ( ConstantStructure(..), ConstantRepr(..), ConceptMatchMap, MatchedConceptMap, CodeConcept(..), matchConcepts, SpaceMatch, matchSpaces, ImplementationType(..), ConstraintBehaviour(..), Comments(..), Verbosity(..), Visibility(..), -<<<<<<< HEAD - Logging(..), AuxFile(..), getSampleData, hasSampleInput, hasReadMe, defaultChoices, - choicesSent, showChs -======= - Logging(..), AuxFile(..), getSampleData, hasSampleInput, defaultChoices ->>>>>>> 8bdb5e8b60d01625d4bcc4fc8a1e904c7fad8177 -) where + Logging(..), AuxFile(..), getSampleData, hasSampleInput, defaultChoices, + choicesSent, showChs) where import Language.Drasil import Utils.Drasil (foldlSent) From d85883b405750fdba6eecb44aed8b8a71db154ea Mon Sep 17 00:00:00 2001 From: muhammad ali Date: Mon, 20 Jul 2020 13:48:59 -0400 Subject: [PATCH 8/9] removing the periods in the design logs --- code/drasil-code/Language/Drasil/Choices.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/code/drasil-code/Language/Drasil/Choices.hs b/code/drasil-code/Language/Drasil/Choices.hs index 739420a859..8229aaa26b 100644 --- a/code/drasil-code/Language/Drasil/Choices.hs +++ b/code/drasil-code/Language/Drasil/Choices.hs @@ -8,7 +8,7 @@ module Language.Drasil.Choices ( choicesSent, showChs) where import Language.Drasil -import Utils.Drasil (foldlSent) +import Utils.Drasil (foldlSent_) import Language.Drasil.Code.Code (spaceToCodeType) import Language.Drasil.Code.Lang (Lang(..)) @@ -71,7 +71,7 @@ data Choices = Choices { class RenderChoices a where showChs :: a -> Sentence showChsList :: [a] -> Sentence - showChsList lst = foldlSent (map showChs lst) + showChsList lst = foldlSent_ (map showChs lst) data Modularity = Modular InputModule -- Different modules for: controller, -- input, calculations, output. @@ -251,7 +251,7 @@ defaultChoices = Choices { choicesSent :: Choices -> [Sentence] choicesSent chs = map chsFieldSent [ - (S "Languages", foldlSent $ map (S . show) $ lang chs) + (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) From d0bf3759bd90c9a191e753561b7c5b83ac9a87bb Mon Sep 17 00:00:00 2001 From: muhammad ali Date: Fri, 24 Jul 2020 09:03:50 -0400 Subject: [PATCH 9/9] updating stable periods --- code/stable/glassbr/src/cpp/designLog.txt | 11 +++++------ code/stable/glassbr/src/csharp/designLog.txt | 11 +++++------ code/stable/glassbr/src/java/designLog.txt | 11 +++++------ code/stable/glassbr/src/python/designLog.txt | 11 +++++------ code/stable/glassbr/src/swift/designLog.txt | 11 +++++------ code/stable/nopcm/src/cpp/designLog.txt | 6 +++--- code/stable/nopcm/src/csharp/designLog.txt | 6 +++--- code/stable/nopcm/src/java/designLog.txt | 6 +++--- code/stable/nopcm/src/python/designLog.txt | 6 +++--- .../Projectile_C_P_NoL_B_U_V_D/src/cpp/designLog.txt | 6 +++--- .../src/csharp/designLog.txt | 6 +++--- .../Projectile_C_P_NoL_B_U_V_D/src/java/designLog.txt | 6 +++--- .../src/python/designLog.txt | 6 +++--- .../src/swift/designLog.txt | 6 +++--- .../Projectile_S_L_NoL_U_U_V_F/src/cpp/designLog.txt | 6 +++--- .../src/csharp/designLog.txt | 6 +++--- .../Projectile_S_L_NoL_U_U_V_F/src/java/designLog.txt | 6 +++--- .../src/python/designLog.txt | 6 +++--- .../src/swift/designLog.txt | 6 +++--- .../Projectile_U_P_L_B_B_C_D/src/cpp/designLog.txt | 8 ++++---- .../Projectile_U_P_L_B_B_C_D/src/csharp/designLog.txt | 8 ++++---- .../Projectile_U_P_L_B_B_C_D/src/java/designLog.txt | 8 ++++---- .../Projectile_U_P_L_B_B_C_D/src/python/designLog.txt | 8 ++++---- .../Projectile_U_P_L_B_B_C_D/src/swift/designLog.txt | 8 ++++---- .../Projectile_U_P_L_B_WI_V_F/src/cpp/designLog.txt | 8 ++++---- .../src/csharp/designLog.txt | 8 ++++---- .../Projectile_U_P_L_B_WI_V_F/src/java/designLog.txt | 8 ++++---- .../src/python/designLog.txt | 8 ++++---- .../Projectile_U_P_L_B_WI_V_F/src/swift/designLog.txt | 8 ++++---- .../Projectile_U_P_NoL_U_WI_V_D/src/cpp/designLog.txt | 6 +++--- .../src/csharp/designLog.txt | 6 +++--- .../src/java/designLog.txt | 6 +++--- .../src/python/designLog.txt | 6 +++--- .../src/swift/designLog.txt | 6 +++--- 34 files changed, 122 insertions(+), 127 deletions(-) diff --git a/code/stable/glassbr/src/cpp/designLog.txt b/code/stable/glassbr/src/cpp/designLog.txt index 8d5330da2c..201279b5a6 100644 --- a/code/stable/glassbr/src/cpp/designLog.txt +++ b/code/stable/glassbr/src/cpp/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Modular Separated. Input Structure selected as Bundled. Constant Structure selected as Inline. @@ -6,19 +6,18 @@ 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.. +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.. +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 Integer with Integer. -Successfully matched Natural with Integer. Successfully matched Vect Real with List Double. Successfully matched Vect (Vect Real) with List (List Double). +Successfully matched Natural with Integer. diff --git a/code/stable/glassbr/src/csharp/designLog.txt b/code/stable/glassbr/src/csharp/designLog.txt index 8d5330da2c..201279b5a6 100644 --- a/code/stable/glassbr/src/csharp/designLog.txt +++ b/code/stable/glassbr/src/csharp/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Modular Separated. Input Structure selected as Bundled. Constant Structure selected as Inline. @@ -6,19 +6,18 @@ 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.. +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.. +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 Integer with Integer. -Successfully matched Natural with Integer. Successfully matched Vect Real with List Double. Successfully matched Vect (Vect Real) with List (List Double). +Successfully matched Natural with Integer. diff --git a/code/stable/glassbr/src/java/designLog.txt b/code/stable/glassbr/src/java/designLog.txt index 8d5330da2c..201279b5a6 100644 --- a/code/stable/glassbr/src/java/designLog.txt +++ b/code/stable/glassbr/src/java/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Modular Separated. Input Structure selected as Bundled. Constant Structure selected as Inline. @@ -6,19 +6,18 @@ 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.. +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.. +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 Integer with Integer. -Successfully matched Natural with Integer. Successfully matched Vect Real with List Double. Successfully matched Vect (Vect Real) with List (List Double). +Successfully matched Natural with Integer. diff --git a/code/stable/glassbr/src/python/designLog.txt b/code/stable/glassbr/src/python/designLog.txt index 8d5330da2c..201279b5a6 100644 --- a/code/stable/glassbr/src/python/designLog.txt +++ b/code/stable/glassbr/src/python/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Modular Separated. Input Structure selected as Bundled. Constant Structure selected as Inline. @@ -6,19 +6,18 @@ 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.. +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.. +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 Integer with Integer. -Successfully matched Natural with Integer. Successfully matched Vect Real with List Double. Successfully matched Vect (Vect Real) with List (List Double). +Successfully matched Natural with Integer. diff --git a/code/stable/glassbr/src/swift/designLog.txt b/code/stable/glassbr/src/swift/designLog.txt index 8d5330da2c..201279b5a6 100644 --- a/code/stable/glassbr/src/swift/designLog.txt +++ b/code/stable/glassbr/src/swift/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Modular Separated. Input Structure selected as Bundled. Constant Structure selected as Inline. @@ -6,19 +6,18 @@ 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.. +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.. +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 Integer with Integer. -Successfully matched Natural with Integer. Successfully matched Vect Real with List Double. Successfully matched Vect (Vect Real) with List (List Double). +Successfully matched Natural with Integer. diff --git a/code/stable/nopcm/src/cpp/designLog.txt b/code/stable/nopcm/src/cpp/designLog.txt index 885f72ec61..5e058133f9 100644 --- a/code/stable/nopcm/src/cpp/designLog.txt +++ b/code/stable/nopcm/src/cpp/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java.. +Languages selected as Python Cpp CSharp Java. Modularity selected as Modular Combined. Input Structure selected as Unbundled. Constant Structure selected as Store Bundled. @@ -6,12 +6,12 @@ Constant Representation selected as Const. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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. -Auxiliary Files selected as SampleInput ../../datafiles/NoPCM/sampleInput.txt ReadME.. +Auxiliary Files selected as SampleInput ../../datafiles/NoPCM/sampleInput.txt ReadME. Language Cpp is not compatible with chosen library SciPy, trying next choice. Language Cpp is not compatible with chosen library OSLO, trying next choice. Language Cpp is not compatible with chosen library Apache, trying next choice. diff --git a/code/stable/nopcm/src/csharp/designLog.txt b/code/stable/nopcm/src/csharp/designLog.txt index e7cd5050a6..092f153c1e 100644 --- a/code/stable/nopcm/src/csharp/designLog.txt +++ b/code/stable/nopcm/src/csharp/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java.. +Languages selected as Python Cpp CSharp Java. Modularity selected as Modular Combined. Input Structure selected as Unbundled. Constant Structure selected as Store Bundled. @@ -6,12 +6,12 @@ Constant Representation selected as Const. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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. -Auxiliary Files selected as SampleInput ../../datafiles/NoPCM/sampleInput.txt ReadME.. +Auxiliary Files selected as SampleInput ../../datafiles/NoPCM/sampleInput.txt ReadME. Language CSharp is not compatible with chosen library SciPy, trying next choice. ODE Library package selected as OSLO. Successfully matched String with String. diff --git a/code/stable/nopcm/src/java/designLog.txt b/code/stable/nopcm/src/java/designLog.txt index 819944a55f..7af8447d3a 100644 --- a/code/stable/nopcm/src/java/designLog.txt +++ b/code/stable/nopcm/src/java/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java.. +Languages selected as Python Cpp CSharp Java. Modularity selected as Modular Combined. Input Structure selected as Unbundled. Constant Structure selected as Store Bundled. @@ -6,12 +6,12 @@ Constant Representation selected as Const. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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. -Auxiliary Files selected as SampleInput ../../datafiles/NoPCM/sampleInput.txt ReadME.. +Auxiliary Files selected as SampleInput ../../datafiles/NoPCM/sampleInput.txt ReadME. Language Java is not compatible with chosen library SciPy, trying next choice. Language Java is not compatible with chosen library OSLO, trying next choice. ODE Library package selected as Apache. diff --git a/code/stable/nopcm/src/python/designLog.txt b/code/stable/nopcm/src/python/designLog.txt index 58323a2b87..07ab161884 100644 --- a/code/stable/nopcm/src/python/designLog.txt +++ b/code/stable/nopcm/src/python/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java.. +Languages selected as Python Cpp CSharp Java. Modularity selected as Modular Combined. Input Structure selected as Unbundled. Constant Structure selected as Store Bundled. @@ -6,12 +6,12 @@ Constant Representation selected as Const. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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. -Auxiliary Files selected as SampleInput ../../datafiles/NoPCM/sampleInput.txt ReadME.. +Auxiliary Files selected as SampleInput ../../datafiles/NoPCM/sampleInput.txt ReadME. Successfully selected first choice ODE Library package SciPy. Successfully matched String with String. Successfully matched Actor "Constants" with Object "Constants". diff --git a/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/cpp/designLog.txt b/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/cpp/designLog.txt index 7c065d42b7..68d9030ee1 100644 --- a/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/cpp/designLog.txt +++ b/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/cpp/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Modular Combined. Input Structure selected as Bundled. Constant Structure selected as Store Unbundled. @@ -6,12 +6,12 @@ Constant Representation selected as Var. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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. -Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched String with String. Successfully matched Actor "Constants" with Object "Constants". diff --git a/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/csharp/designLog.txt b/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/csharp/designLog.txt index 7c065d42b7..68d9030ee1 100644 --- a/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/csharp/designLog.txt +++ b/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/csharp/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Modular Combined. Input Structure selected as Bundled. Constant Structure selected as Store Unbundled. @@ -6,12 +6,12 @@ Constant Representation selected as Var. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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. -Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched String with String. Successfully matched Actor "Constants" with Object "Constants". diff --git a/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/java/designLog.txt b/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/java/designLog.txt index 7c065d42b7..68d9030ee1 100644 --- a/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/java/designLog.txt +++ b/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/java/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Modular Combined. Input Structure selected as Bundled. Constant Structure selected as Store Unbundled. @@ -6,12 +6,12 @@ Constant Representation selected as Var. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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. -Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched String with String. Successfully matched Actor "Constants" with Object "Constants". diff --git a/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/python/designLog.txt b/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/python/designLog.txt index 7c065d42b7..68d9030ee1 100644 --- a/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/python/designLog.txt +++ b/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/python/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Modular Combined. Input Structure selected as Bundled. Constant Structure selected as Store Unbundled. @@ -6,12 +6,12 @@ Constant Representation selected as Var. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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. -Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched String with String. Successfully matched Actor "Constants" with Object "Constants". diff --git a/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/swift/designLog.txt b/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/swift/designLog.txt index 7c065d42b7..68d9030ee1 100644 --- a/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/swift/designLog.txt +++ b/code/stable/projectile/Projectile_C_P_NoL_B_U_V_D/src/swift/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Modular Combined. Input Structure selected as Bundled. Constant Structure selected as Store Unbundled. @@ -6,12 +6,12 @@ Constant Representation selected as Var. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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. -Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched String with String. Successfully matched Actor "Constants" with Object "Constants". diff --git a/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/cpp/designLog.txt b/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/cpp/designLog.txt index 73bc9d351e..a166a71c11 100644 --- a/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/cpp/designLog.txt +++ b/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/cpp/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Modular Separated. Input Structure selected as Unbundled. Constant Structure selected as Store Unbundled. @@ -6,12 +6,12 @@ Constant Representation selected as Var. Implementation Type selected as Library. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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. -Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched Real with Float. Successfully matched String with String. diff --git a/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/csharp/designLog.txt b/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/csharp/designLog.txt index 73bc9d351e..a166a71c11 100644 --- a/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/csharp/designLog.txt +++ b/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/csharp/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Modular Separated. Input Structure selected as Unbundled. Constant Structure selected as Store Unbundled. @@ -6,12 +6,12 @@ Constant Representation selected as Var. Implementation Type selected as Library. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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. -Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched Real with Float. Successfully matched String with String. diff --git a/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/java/designLog.txt b/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/java/designLog.txt index 73bc9d351e..a166a71c11 100644 --- a/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/java/designLog.txt +++ b/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/java/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Modular Separated. Input Structure selected as Unbundled. Constant Structure selected as Store Unbundled. @@ -6,12 +6,12 @@ Constant Representation selected as Var. Implementation Type selected as Library. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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. -Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched Real with Float. Successfully matched String with String. diff --git a/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/python/designLog.txt b/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/python/designLog.txt index c5469b2d38..84c61a47a7 100644 --- a/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/python/designLog.txt +++ b/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/python/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Modular Separated. Input Structure selected as Unbundled. Constant Structure selected as Store Unbundled. @@ -6,12 +6,12 @@ Constant Representation selected as Var. Implementation Type selected as Library. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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. -Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Language Python does not support code type Float, chosen as the match for the Real space. Trying next choice. Successfully matched Real with Double. diff --git a/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/swift/designLog.txt b/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/swift/designLog.txt index 73bc9d351e..a166a71c11 100644 --- a/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/swift/designLog.txt +++ b/code/stable/projectile/Projectile_S_L_NoL_U_U_V_F/src/swift/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Modular Separated. Input Structure selected as Unbundled. Constant Structure selected as Store Unbundled. @@ -6,12 +6,12 @@ Constant Representation selected as Var. Implementation Type selected as Library. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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. -Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched Real with Float. Successfully matched String with String. diff --git a/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/cpp/designLog.txt b/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/cpp/designLog.txt index 4cb5136969..6ea69173ad 100644 --- a/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/cpp/designLog.txt +++ b/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/cpp/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Unmodular. Input Structure selected as Bundled. Constant Structure selected as Store Bundled. @@ -6,12 +6,12 @@ Constant Representation selected as Const. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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/Projectile/sampleInput.txt ReadME.. +Logging selected as LogVar LogFunc. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched Real with Double. Successfully matched String with String. diff --git a/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/csharp/designLog.txt b/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/csharp/designLog.txt index 4cb5136969..6ea69173ad 100644 --- a/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/csharp/designLog.txt +++ b/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/csharp/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Unmodular. Input Structure selected as Bundled. Constant Structure selected as Store Bundled. @@ -6,12 +6,12 @@ Constant Representation selected as Const. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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/Projectile/sampleInput.txt ReadME.. +Logging selected as LogVar LogFunc. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched Real with Double. Successfully matched String with String. diff --git a/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/java/designLog.txt b/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/java/designLog.txt index 4cb5136969..6ea69173ad 100644 --- a/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/java/designLog.txt +++ b/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/java/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Unmodular. Input Structure selected as Bundled. Constant Structure selected as Store Bundled. @@ -6,12 +6,12 @@ Constant Representation selected as Const. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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/Projectile/sampleInput.txt ReadME.. +Logging selected as LogVar LogFunc. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched Real with Double. Successfully matched String with String. diff --git a/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/python/designLog.txt b/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/python/designLog.txt index 4cb5136969..6ea69173ad 100644 --- a/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/python/designLog.txt +++ b/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/python/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Unmodular. Input Structure selected as Bundled. Constant Structure selected as Store Bundled. @@ -6,12 +6,12 @@ Constant Representation selected as Const. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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/Projectile/sampleInput.txt ReadME.. +Logging selected as LogVar LogFunc. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched Real with Double. Successfully matched String with String. diff --git a/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/swift/designLog.txt b/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/swift/designLog.txt index 4cb5136969..6ea69173ad 100644 --- a/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/swift/designLog.txt +++ b/code/stable/projectile/Projectile_U_P_L_B_B_C_D/src/swift/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Unmodular. Input Structure selected as Bundled. Constant Structure selected as Store Bundled. @@ -6,12 +6,12 @@ Constant Representation selected as Const. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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/Projectile/sampleInput.txt ReadME.. +Logging selected as LogVar LogFunc. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched Real with Double. Successfully matched String with String. diff --git a/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/cpp/designLog.txt b/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/cpp/designLog.txt index 0d72e800c9..a55c0ddafc 100644 --- a/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/cpp/designLog.txt +++ b/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/cpp/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Unmodular. Input Structure selected as Bundled. Constant Structure selected as WithInputs. @@ -6,12 +6,12 @@ Constant Representation selected as Var. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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/Projectile/sampleInput.txt ReadME.. +Logging selected as LogVar LogFunc. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched Real with Float. Successfully matched Rational with Float. diff --git a/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/csharp/designLog.txt b/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/csharp/designLog.txt index 0d72e800c9..a55c0ddafc 100644 --- a/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/csharp/designLog.txt +++ b/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/csharp/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Unmodular. Input Structure selected as Bundled. Constant Structure selected as WithInputs. @@ -6,12 +6,12 @@ Constant Representation selected as Var. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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/Projectile/sampleInput.txt ReadME.. +Logging selected as LogVar LogFunc. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched Real with Float. Successfully matched Rational with Float. diff --git a/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/java/designLog.txt b/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/java/designLog.txt index 0d72e800c9..a55c0ddafc 100644 --- a/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/java/designLog.txt +++ b/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/java/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Unmodular. Input Structure selected as Bundled. Constant Structure selected as WithInputs. @@ -6,12 +6,12 @@ Constant Representation selected as Var. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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/Projectile/sampleInput.txt ReadME.. +Logging selected as LogVar LogFunc. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched Real with Float. Successfully matched Rational with Float. diff --git a/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/python/designLog.txt b/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/python/designLog.txt index 94919cf79e..37661ffd9c 100644 --- a/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/python/designLog.txt +++ b/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/python/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Unmodular. Input Structure selected as Bundled. Constant Structure selected as WithInputs. @@ -6,12 +6,12 @@ Constant Representation selected as Var. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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/Projectile/sampleInput.txt ReadME.. +Logging selected as LogVar LogFunc. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Language Python does not support code type Float, chosen as the match for the Real space. Trying next choice. Successfully matched Real with Double. diff --git a/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/swift/designLog.txt b/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/swift/designLog.txt index 0d72e800c9..a55c0ddafc 100644 --- a/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/swift/designLog.txt +++ b/code/stable/projectile/Projectile_U_P_L_B_WI_V_F/src/swift/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Unmodular. Input Structure selected as Bundled. Constant Structure selected as WithInputs. @@ -6,12 +6,12 @@ Constant Representation selected as Var. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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/Projectile/sampleInput.txt ReadME.. +Logging selected as LogVar LogFunc. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched Real with Float. Successfully matched Rational with Float. diff --git a/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/cpp/designLog.txt b/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/cpp/designLog.txt index 01170220d8..e86086c995 100644 --- a/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/cpp/designLog.txt +++ b/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/cpp/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Unmodular. Input Structure selected as Unbundled. Constant Structure selected as WithInputs. @@ -6,12 +6,12 @@ Constant Representation selected as Var. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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. -Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched String with String. Successfully matched Actor "Constants" with Object "Constants". diff --git a/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/csharp/designLog.txt b/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/csharp/designLog.txt index 01170220d8..e86086c995 100644 --- a/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/csharp/designLog.txt +++ b/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/csharp/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Unmodular. Input Structure selected as Unbundled. Constant Structure selected as WithInputs. @@ -6,12 +6,12 @@ Constant Representation selected as Var. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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. -Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched String with String. Successfully matched Actor "Constants" with Object "Constants". diff --git a/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/java/designLog.txt b/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/java/designLog.txt index 01170220d8..e86086c995 100644 --- a/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/java/designLog.txt +++ b/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/java/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Unmodular. Input Structure selected as Unbundled. Constant Structure selected as WithInputs. @@ -6,12 +6,12 @@ Constant Representation selected as Var. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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. -Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched String with String. Successfully matched Actor "Constants" with Object "Constants". diff --git a/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/python/designLog.txt b/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/python/designLog.txt index 01170220d8..e86086c995 100644 --- a/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/python/designLog.txt +++ b/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/python/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Unmodular. Input Structure selected as Unbundled. Constant Structure selected as WithInputs. @@ -6,12 +6,12 @@ Constant Representation selected as Var. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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. -Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched String with String. Successfully matched Actor "Constants" with Object "Constants". diff --git a/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/swift/designLog.txt b/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/swift/designLog.txt index 01170220d8..e86086c995 100644 --- a/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/swift/designLog.txt +++ b/code/stable/projectile/Projectile_U_P_NoL_U_WI_V_D/src/swift/designLog.txt @@ -1,4 +1,4 @@ -Languages selected as Python Cpp CSharp Java Swift.. +Languages selected as Python Cpp CSharp Java Swift. Modularity selected as Unmodular. Input Structure selected as Unbundled. Constant Structure selected as WithInputs. @@ -6,12 +6,12 @@ Constant Representation selected as Var. Implementation Type selected as Program. Software Constraint Behaviour selected as Warning. Physical Constraint Behaviour selected as Warning. -Comments selected as CommentFunc CommentClass CommentMod.. +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. -Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME.. +Auxiliary Files selected as SampleInput ../../../datafiles/Projectile/sampleInput.txt ReadME. Code Concept pi selected as Pi. Successfully matched String with String. Successfully matched Actor "Constants" with Object "Constants".