From 5598d935027c96acebbd9c1622246fbb75ed56db Mon Sep 17 00:00:00 2001 From: Sam Crawford <35857611+samm82@users.noreply.github.com> Date: Mon, 6 May 2019 17:04:38 -0400 Subject: [PATCH] Transitioned NFR implementation in SSP (#1273) * Changed 'business tasks' to 'tasks and behaviours' as per #1256 * Added infrastructure for NFR intro * Added more infrastructure for converting NFR style to FR style * Added first testing NFR a la previous FR structure for SSP * Removed accidental table duplication * Merged test NFR with Brooks's change - will re-add introduction * Req Intro now displaying and transistioned to nfReqF * Added Reusability and Maintainability requirements to SSP * Added Correct NFR to SSP * Changed implementation of nonFunqReq' to take an int and fix processing --- .../Data/Drasil/Concepts/Documentation.hs | 8 ++- code/drasil-docLang/Drasil/DocLang.hs | 4 +- code/drasil-docLang/Drasil/DocLang/SRS.hs | 6 +- .../drasil-docLang/Drasil/DocumentLanguage.hs | 4 +- .../Drasil/Sections/Requirements.hs | 69 +++++++++++-------- code/drasil-example/Drasil/SSP/Body.hs | 19 ++--- .../drasil-example/Drasil/SSP/Requirements.hs | 43 ++++++++++-- code/stable/gamephys/SRS/Chipmunk_SRS.tex | 4 +- .../stable/gamephys/Website/Chipmunk_SRS.html | 4 +- code/stable/glassbr/SRS/GlassBR_SRS.tex | 4 +- code/stable/glassbr/Website/GlassBR_SRS.html | 4 +- code/stable/nopcm/SRS/NoPCM_SRS.tex | 4 +- code/stable/nopcm/Website/NoPCM_SRS.html | 4 +- code/stable/ssp/SRS/SSP_SRS.tex | 13 +++- code/stable/ssp/Website/SSP_SRS.html | 31 ++++++++- code/stable/swhs/SRS/SWHS_SRS.tex | 4 +- code/stable/swhs/Website/SWHS_SRS.html | 4 +- 17 files changed, 152 insertions(+), 77 deletions(-) diff --git a/code/drasil-data/Data/Drasil/Concepts/Documentation.hs b/code/drasil-data/Data/Drasil/Concepts/Documentation.hs index a9b9843322..e993c486e7 100644 --- a/code/drasil-data/Data/Drasil/Concepts/Documentation.hs +++ b/code/drasil-data/Data/Drasil/Concepts/Documentation.hs @@ -40,10 +40,10 @@ doccon = [abbreviation, analysis, appendix, aspect, body, characteristic, class_ doccon' :: [CI] doccon' = [assumption, dataDefn, desSpec, genDefn, goalStmt, dataConst, inModel, likelyChg, - unlikelyChg, physSyst, requirement, thModel, mg, notApp, srs, typUnc] + unlikelyChg, physSyst, requirement, thModel, mg, mis, notApp, srs, typUnc] assumption, dataDefn, desSpec, genDefn, goalStmt, dataConst, inModel, likelyChg, - unlikelyChg, physSyst, requirement, thModel, mg, notApp, srs, typUnc, sec :: CI + unlikelyChg, physSyst, requirement, thModel, mg, mis, notApp, srs, typUnc, sec :: CI ----------------------------------------------------------------------------------------------------------------- -- | CI | | uid | term | abbreviation | ConceptDomain @@ -60,6 +60,7 @@ unlikelyChg = commonIdeaWithDict "unlikelyChg" (cn' "unlikely change") physSyst = commonIdeaWithDict "physSyst" (fterms compoundPhrase physicalSystem description) "PS" [softEng] requirement = commonIdeaWithDict "requirement" (cn' "requirement") "R" [softEng] thModel = commonIdeaWithDict "thModel" (cn' "theoretical model") "T" [softEng] +mis = commonIdeaWithDict "mis" (fterms compoundPhrase moduleInterface specification) "MIS" [softEng] mg = commonIdeaWithDict "mg" (fterms compoundPhrase module_ guide) "MG" [softEng] notApp = commonIdea "notApp" (nounPhraseSP "not applicable") "N/A" [] typUnc = commonIdeaWithDict "typUnc" (cn' "typical uncertainty") "Uncert." [softEng] @@ -239,7 +240,7 @@ scpOfTheProj oper = nc "scpOfTheProj" (scope `ofN_` theCustom oper project) -- r -- compounds -designDoc, fullForm, generalSystemDescription, indPRCase, +designDoc, fullForm, generalSystemDescription, moduleInterface, indPRCase, physicalConstraint, physicalSystem, problemDescription, prodUCTable, specificsystemdescription, systemdescription, systemConstraint, sysCont, userCharacteristic, datumConstraint, functionalRequirement, @@ -253,6 +254,7 @@ designDoc = compoundNC design document fullForm = compoundNC full form functionalRequirement = compoundNC functional requirement_ generalSystemDescription = compoundNC general systemdescription +moduleInterface = compoundNC module_ interface indPRCase = compoundNC individual productUC nonfunctionalRequirement = compoundNC nonfunctional requirement_ offShelfSolution = compoundNC offShelf solution diff --git a/code/drasil-docLang/Drasil/DocLang.hs b/code/drasil-docLang/Drasil/DocLang.hs index 6fd386abf0..7acc93db79 100644 --- a/code/drasil-docLang/Drasil/DocLang.hs +++ b/code/drasil-docLang/Drasil/DocLang.hs @@ -4,7 +4,7 @@ module Drasil.DocLang ( DocSection(..), Emphasis(..), GSDSec(GSDProg2), GSDSub(UsrChars, SystCons, SysCntxt), IntroSec(..), IntroSub(..), LCsSec(..), LFunc(..), Literature(Doc', Lit, Manual), ProblemDescription(..), RefSec(..), RefTab(..), - ReqrmntSec(..), ReqsSub(FReqsSub, NonFReqsSub), ScpOfProjSec(ScpOfProjProg), + ReqrmntSec(..), ReqsSub(FReqsSub, NonFReqsSub, NonFReqsSub'), ScpOfProjSec(ScpOfProjProg), SCSSub(..), SSDSec(..), SSDSub(..), SolChSpec(..), ExistingSolnSec(..), StkhldrSec(StkhldrProg2), LCsSec'(..), StkhldrSub(Client, Cstmr), TConvention(..), TraceabilitySec(TraceabilityProg), @@ -51,7 +51,7 @@ import Drasil.DocumentLanguage (AppndxSec(..), AuxConstntSec(..), DerivationDisplay(..), DocDesc, DocSection(..), Emphasis(..), ExistingSolnSec(..), GSDSec(GSDProg2), GSDSub(UsrChars, SystCons, SysCntxt), IntroSec(..), IntroSub(..), LCsSec(..), LFunc(..), Literature(Doc', Lit, Manual), ProblemDescription(..), - RefSec(..), RefTab(..), ReqrmntSec(..), ReqsSub(FReqsSub, NonFReqsSub), + RefSec(..), RefTab(..), ReqrmntSec(..), ReqsSub(FReqsSub, NonFReqsSub, NonFReqsSub'), ScpOfProjSec(ScpOfProjProg), SCSSub(..), SSDSec(..), SSDSub(..), SolChSpec(..), StkhldrSec(StkhldrProg2), StkhldrSub(Client, Cstmr), TConvention(..), LCsSec'(..), TraceabilitySec(TraceabilityProg), TSIntro(..), UCsSec(..), mkDoc, tsymb, tsymb'', diff --git a/code/drasil-docLang/Drasil/DocLang/SRS.hs b/code/drasil-docLang/Drasil/DocLang/SRS.hs index 39c3d2b8a8..0edabf6e4e 100644 --- a/code/drasil-docLang/Drasil/DocLang/SRS.hs +++ b/code/drasil-docLang/Drasil/DocLang/SRS.hs @@ -82,7 +82,7 @@ datCon cs ss = section (titleize' Doc.datumConstraint) cs ss datConLabel propCorSol cs ss = section' (titleize' Doc.propOfCorSol) cs ss "CorSolProps" require cs ss = section' (titleize' Doc.requirement) cs ss "Requirements" -nonfuncReq cs ss = section' (titleize' Doc.nonfunctionalRequirement) cs ss "NFRs" +nonfuncReq cs ss = section (titleize' Doc.nonfunctionalRequirement) cs ss nonfuncReqLabel funcReq cs ss = section (titleize' Doc.functionalRequirement) cs ss funcReqLabel likeChg cs ss = section (titleize' Doc.likelyChg) cs ss likeChgLabel @@ -110,7 +110,8 @@ section' a b c d = section a b c (makeSecRef d (toString a)) --FIXME: create using section information somehow? physSystLabel, datConLabel, genDefnLabel, thModelLabel, dataDefnLabel, inModelLabel, likeChgLabel, tOfSymbLabel, valsOfAuxConsLabel, referenceLabel, - indPRCaseLabel, unlikeChgLabel, assumptLabel, funcReqLabel, solCharSpecLabel :: Reference + indPRCaseLabel, unlikeChgLabel, assumptLabel, funcReqLabel, nonfuncReqLabel, + solCharSpecLabel :: Reference physSystLabel = makeSecRef "PhysSyst" "Physical System Description" datConLabel = makeSecRef "DataConstraints" "Data Constraints" genDefnLabel = makeSecRef "GDs" "General Definitions" @@ -125,4 +126,5 @@ referenceLabel = makeSecRef "References" "References" indPRCaseLabel = makeSecRef "IndividualProdUC" "Individual Product Use Cases" assumptLabel = makeSecRef "Assumps" "Assumptions" funcReqLabel = makeSecRef "FRs" "Functional Requirements" +nonfuncReqLabel = makeSecRef "NFRs" "Nonfunctional Requirements" solCharSpecLabel = makeSecRef "SolCharSpec" "Solution Characteristics Specification" diff --git a/code/drasil-docLang/Drasil/DocumentLanguage.hs b/code/drasil-docLang/Drasil/DocumentLanguage.hs index 747e85da08..7969531216 100644 --- a/code/drasil-docLang/Drasil/DocumentLanguage.hs +++ b/code/drasil-docLang/Drasil/DocumentLanguage.hs @@ -28,7 +28,7 @@ import qualified Drasil.Sections.GeneralSystDesc as GSD (genSysF, genSysIntro, systCon, usrCharsF, sysContxt) import qualified Drasil.Sections.Introduction as Intro (charIntRdrF, introductionSection, orgSec, purposeOfDoc, scopeOfRequirements) -import qualified Drasil.Sections.Requirements as R (fReqF, nonFuncReqF, nonFuncReqF', reqF) +import qualified Drasil.Sections.Requirements as R (reqF, fReqF, nfReqF, nonFuncReqF) import qualified Drasil.Sections.ScopeOfTheProject as SotP (scopeOfTheProjF) import qualified Drasil.Sections.SpecificSystemDescription as SSD (assumpF, datConF, dataDefnF, genDefnF, inModelF, probDescF, solutionCharSpecIntro, @@ -500,7 +500,7 @@ mkReqrmntSec (ReqsProg l) = R.reqF $ map mkSubs l mkSubs :: ReqsSub -> Section mkSubs (FReqsSub reqs) = R.fReqF reqs mkSubs (NonFReqsSub noPrrty prrty rsn explain) = R.nonFuncReqF noPrrty prrty rsn explain - mkSubs (NonFReqsSub' noPrrty nfrs rsn explain) = R.nonFuncReqF' noPrrty (mkEnumSimpleD nfrs) rsn explain + mkSubs (NonFReqsSub' noPrrty nfrs rsn explain) = R.nfReqF noPrrty (length nfrs) rsn explain (mkEnumSimpleD nfrs) {--} diff --git a/code/drasil-docLang/Drasil/Sections/Requirements.hs b/code/drasil-docLang/Drasil/Sections/Requirements.hs index 2a83e4e1f7..15863505ef 100644 --- a/code/drasil-docLang/Drasil/Sections/Requirements.hs +++ b/code/drasil-docLang/Drasil/Sections/Requirements.hs @@ -1,12 +1,12 @@ module Drasil.Sections.Requirements - (fReqF, reqF, nonFuncReqF, nonFuncReqF') where + (fReqF, reqF, nfReqF, nonFuncReqF) where import Language.Drasil import Data.Drasil.Concepts.Documentation (priority, software, nonfunctionalRequirement, functionalRequirement, section_) import Data.Drasil.Concepts.Software (program) -import Data.Drasil.SentenceStructures (foldlList, foldlSent, SepType(Comma), FoldType(List)) +import Data.Drasil.SentenceStructures (foldlList, foldlSent_, sAnd, SepType(Comma), FoldType(List)) import qualified Drasil.DocLang.SRS as SRS @@ -15,26 +15,43 @@ reqF :: [Section] -> Section reqF = SRS.require [reqIntro] fReqF :: [Contents] -> Section -fReqF listOfReqs = SRS.funcReq (fReqIntro : listOfReqs) [] +fReqF listOfFReqs = SRS.funcReq (fReqIntro : listOfFReqs) [] + +nfReqF :: (Concept c) => [c] -> Int -> Sentence -> Sentence -> [Contents] -> Section +nfReqF no num r e nfrs = SRS.nonfuncReq + (nfReqIntro : ((nonFuncReq' (map phrase no) num r e) : nfrs)) [] + +--helpers for requirements intros +reqIntroStart :: Sentence +reqIntroStart = foldlSent_ [S "This", (phrase section_), S "provides"] + +frReqIntroBody :: Sentence +frReqIntroBody = foldlSent_ + [S "the", (plural functionalRequirement) `sC` S "the tasks and behaviours that the", + (phrase software), S "is expected to complete"] + +nfrReqIntroBody :: Sentence +nfrReqIntroBody = foldlSent_ + [S "the", (plural nonfunctionalRequirement) `sC` S "the qualities that the", + (phrase software), S "is expected to exhibit"] --generalized requirements introduction reqIntroS :: Sentence -reqIntroS = foldlSent - [S "This", (phrase section_), S "provides the", - (plural functionalRequirement) `sC` S "the business tasks that the", - (phrase software), S "is expected to complete" `sC` S "and the", - (plural nonfunctionalRequirement) `sC` S "the qualities that the", - (phrase software), S "is expected to exhibit"] +reqIntroS = reqIntroStart +:+. ((frReqIntroBody :+: S ",") `sAnd` nfrReqIntroBody) -- FIXME: comma hack? reqIntro :: Contents reqIntro = mkParagraph reqIntroS --generalized functional requirements introduction fReqIntroS :: Sentence -fReqIntroS = foldlSent - [S "The following", (phrase section_), S "provides the", - (plural functionalRequirement) `sC` S "the business tasks that the", - (phrase software), S "is expected to complete"] +fReqIntroS = reqIntroStart +:+. frReqIntroBody + +nfReqIntro :: Contents +nfReqIntro = mkParagraph nfReqIntroS + +--generalized nonfunctional requirements introduction +nfReqIntroS :: Sentence +nfReqIntroS = reqIntroStart +:+. nfrReqIntroBody fReqIntro :: Contents fReqIntro = mkParagraph fReqIntroS @@ -43,18 +60,14 @@ fReqIntro = mkParagraph fReqIntroS nonFuncReqF :: (Concept c) => [c] -> [c] -> Sentence -> Sentence -> Section nonFuncReqF noPriority priority_ reason_ explanation_ = SRS.nonfuncReq [nonFuncReq (map phrase noPriority) (map phrase priority_) reason_ explanation_] [] - -nonFuncReqF' :: (Concept c) => [c] -> [Contents] -> Sentence -> Sentence -> Section -nonFuncReqF' noPriority nfrs reason_ explanation_ = SRS.nonfuncReq - ((nonFuncReq' (map phrase noPriority) nfrs reason_ explanation_) : nfrs) [] -- generalized non-functional requirements paragraph: list of non-priority requirements, list of priority requirements, -- reason for initial priority choice, explanation for how priority choice can be achieved. nonFuncReq :: [Sentence] -> [Sentence] -> Sentence -> Sentence -> Contents nonFuncReq noPriority priority_ reason_ explanation_ = mkParagraph $ reason_ `sC` (listO explanation_ noPriority priority_) -nonFuncReq' :: [Sentence] -> [Contents] -> Sentence -> Sentence -> Contents -nonFuncReq' noPriority priority_ reason_ explanation_ = mkParagraph $ reason_ `sC` (listO' explanation_ noPriority priority_) +nonFuncReq' :: [Sentence] -> Int -> Sentence -> Sentence -> Contents +nonFuncReq' noPriority num reason_ explanation_ = mkParagraph $ reason_ `sC` (listO' explanation_ noPriority num) listO :: Sentence -> [Sentence] -> [Sentence] -> Sentence listO explanation_ [] [] = S "so there are no" +:+ (plural priority) +:+ explanation_ @@ -62,18 +75,18 @@ listO explanation_ [] priority_ = S "so" +:+ head priority_ +:+ S "is a high" +: listO explanation_ [s] priority_ = S "so" +:+ s +:+ S "is not a" +:+. phrase priority +:+ explanation_ +:+ S "Rather than" +:+ s `sC` S "the" +:+. listT priority_ listO explanation_ s priority_ = S "so" +:+ foldlList Comma List s +:+ S "are not" +:+. (plural priority) +:+ explanation_ +:+ S "Rather, the" +:+. listT priority_ -listO' :: Sentence -> [Sentence] -> [Contents] -> Sentence -listO' explanation_ [] [] = S "so there are no" +:+ (plural priority) +:+ explanation_ -listO' explanation_ [] priority_ = S "so all" +:+ (plural nonfunctionalRequirement) +:+ S "are given equal" +:+ phrase priority +:+ explanation_ +:+ S "The" +:+. listT' priority_ -listO' explanation_ [s] priority_ = S "so" +:+ s +:+ S "is not a" +:+. phrase priority +:+ explanation_ +:+ S "Rather than" +:+ s `sC` S "the" +:+. listT' priority_ -listO' explanation_ s priority_ = S "so" +:+ foldlList Comma List s +:+ S "are not" +:+. (plural priority) +:+ explanation_ +:+ S "Rather, the" +:+. listT' priority_ +listO' :: Sentence -> [Sentence] -> Int -> Sentence +listO' explanation_ [] 0 = S "so there are no" +:+ (plural priority) +:+ explanation_ +listO' explanation_ [] num = S "so all" +:+ (plural nonfunctionalRequirement) +:+ S "are given equal" +:+ phrase priority +:+ explanation_ +:+ S "The" +:+ listT' num +listO' explanation_ [s] num = S "so" +:+ s +:+ S "is not a" +:+. phrase priority +:+ explanation_ +:+ S "Rather than" +:+ s `sC` S "the" +:+ listT' num +listO' explanation_ s num = S "so" +:+ foldlList Comma List s +:+ S "are not" +:+. (plural priority) +:+ explanation_ +:+ S "Rather, the" +:+ listT' num listT :: [Sentence] -> Sentence listT [] = (phrase program) +:+ S "does not possess a" +:+ (phrase priority) +:+ (phrase nonfunctionalRequirement) listT [s] = (phrase nonfunctionalRequirement) +:+ (phrase priority) +:+ S "is" +:+ s listT s = (phrase nonfunctionalRequirement) +:+ (plural priority) +:+ S "are" +:+ foldlList Comma List s -listT' :: [Contents] -> Sentence -listT' [] = (phrase program) +:+ S "does not possess a" +:+ (phrase priority) +:+ (phrase nonfunctionalRequirement) -listT' [_] = (phrase nonfunctionalRequirement) +:+ (phrase priority) +:+ S "is:" -listT' _ = (phrase nonfunctionalRequirement) +:+ (plural priority) +:+ S "are:" +listT' :: Int -> Sentence +listT' 0 = (phrase program) +:+ S "does not possess a" +:+ (phrase priority) +:+. (phrase nonfunctionalRequirement) +listT' 1 = (phrase nonfunctionalRequirement) +:+ (phrase priority) +: S "is" +listT' _ = (phrase nonfunctionalRequirement) +:+ (plural priority) +: S "are" diff --git a/code/drasil-example/Drasil/SSP/Body.hs b/code/drasil-example/Drasil/SSP/Body.hs index f3f2e30189..24ad89024f 100644 --- a/code/drasil-example/Drasil/SSP/Body.hs +++ b/code/drasil-example/Drasil/SSP/Body.hs @@ -13,7 +13,7 @@ import Drasil.DocLang (DocDesc, DocSection(..), IntroSec(..), IntroSub(..), TSIntro(..), UCsSec(..), Fields, Field(..), SSDSec(..), SSDSub(..), Verbosity(..), InclUnits(..), DerivationDisplay(..), SolChSpec(..), SCSSub(..), GSDSec(..), GSDSub(..), TraceabilitySec(TraceabilityProg), - ReqrmntSec(..), ReqsSub(FReqsSub, NonFReqsSub), + ReqrmntSec(..), ReqsSub(FReqsSub, NonFReqsSub'), dataConstraintUncertainty, goalStmtF, intro, mkDoc, mkEnumSimpleD, probDescF, termDefnF, tsymb'', valsOfAuxConstantsF,getDocDesc, egetDocDesc, generateTraceMap, @@ -35,8 +35,7 @@ import Data.Drasil.Concepts.Math (equation, shape, surface, mathcon, mathcon', import Data.Drasil.Concepts.PhysicalProperties (dimension, mass, physicalcon) import Data.Drasil.Concepts.Physics (cohesion, fbd, force, isotropy, strain, stress, time, twoD, physicCon) -import Data.Drasil.Concepts.Software (accuracy, correctness, maintainability, - program, reusability, understandability, softwarecon, performance) +import Data.Drasil.Concepts.Software (accuracy, program, softwarecon, performance) import Data.Drasil.Concepts.SolidMechanics (mobShear, normForce, shearForce, shearRes, solidcon) import Data.Drasil.Concepts.Computation (compcon, algorithm) @@ -65,7 +64,7 @@ import Drasil.SSP.GenDefs (generalDefinitions) import Drasil.SSP.Goals (sspGoals) import Drasil.SSP.IMods (sspIMods, instModIntro) import Drasil.SSP.References (sspCitations, morgenstern1965) -import Drasil.SSP.Requirements (sspRequirements, sspInputDataTable, +import Drasil.SSP.Requirements (sspFRequirements, sspNFRequirements, sspInputDataTable, sspInputsToOutputTable) import Drasil.SSP.TMods (factOfSafety, equilibrium, mcShrStrgth, effStress) import Drasil.SSP.Unitals (effCohesion, fricAngle, fs, index, @@ -144,9 +143,9 @@ mkSRS = [RefSec $ RefProg intro ], ReqrmntSec $ ReqsProg [ FReqsSub funcReqList, - NonFReqsSub [accuracy,performance] ssppriorityNFReqs -- The way to render the NonFReqsSub is right for here, fixme. + NonFReqsSub' [accuracy, performance] sspNFRequirements (short ssp +:+ S "is intended to be an educational tool") - (S "")] + EmptyS] , LCsSec $ LCsProg likelyChanges_SRS , UCsSec $ UCsProg unlikelyChanges_SRS , TraceabilitySec $ TraceabilityProg [traceyMatrix] traceTrailing @@ -172,7 +171,7 @@ ssp_theory :: [TheoryModel] ssp_theory = getTraceMapFromTM $ getSCSSub mkSRS ssp_concins :: [ConceptInstance] -ssp_concins = sspGoals ++ assumptions ++ sspRequirements ++ likelyChgs ++ unlikelyChgs +ssp_concins = sspGoals ++ assumptions ++ sspFRequirements ++ sspNFRequirements ++ likelyChgs ++ unlikelyChgs ssp_section :: [Section] ssp_section = ssp_sec @@ -191,10 +190,6 @@ stdFields = [DefiningEquation, Description Verbose IncludeUnits, Notes, Source, ssp_code :: CodeSpec ssp_code = codeSpec ssp_si [sspInputMod] -ssppriorityNFReqs :: [ConceptChunk] -ssppriorityNFReqs = [correctness, understandability, reusability, - maintainability] - traceyMatrix :: LabelledContent traceyMatrix = generateTraceTable ssp_si @@ -529,7 +524,7 @@ slopeVert = verticesConst $ phrase slope -- SECTION 5.1 -- funcReqList :: [Contents] -funcReqList = (mkEnumSimpleD sspRequirements) ++ +funcReqList = (mkEnumSimpleD sspFRequirements) ++ [LlC sspInputDataTable, LlC sspInputsToOutputTable] -- SECTION 5.2 -- diff --git a/code/drasil-example/Drasil/SSP/Requirements.hs b/code/drasil-example/Drasil/SSP/Requirements.hs index 70e2d6a8ee..f2dff71c35 100644 --- a/code/drasil-example/Drasil/SSP/Requirements.hs +++ b/code/drasil-example/Drasil/SSP/Requirements.hs @@ -1,11 +1,13 @@ -module Drasil.SSP.Requirements (sspRequirements, sspInputDataTable, - sspInputsToOutputTable) where +module Drasil.SSP.Requirements (sspFRequirements, sspNFRequirements, + sspInputDataTable, sspInputsToOutputTable) where import Language.Drasil import Data.Drasil.Concepts.Computation (inDatum) -import Data.Drasil.Concepts.Documentation (datum, funcReqDom, - input_, name_, output_, physicalConstraint, symbol_, user, value) +import Data.Drasil.Concepts.Documentation (assumption, code, dataDefn, + datum, funcReqDom, genDefn, inModel, input_, likelyChg, mg, mis, module_, + name_, nonFuncReqDom, output_, physicalConstraint, property, requirement, + srs, symbol_, thModel, traceyMatrix, unlikelyChg, user, value) import Data.Drasil.Concepts.Physics (twoD) import Data.Drasil.SentenceStructures (SepType(Comma), FoldType(List), @@ -19,8 +21,10 @@ import Drasil.SSP.Unitals (constF, coords, fs, fs_min, intNormForce, intShrForce, sspInputs, xMaxExtSlip, xMaxEtrSlip, xMinExtSlip, xMinEtrSlip, yMaxSlip, yMinSlip) -sspRequirements :: [ConceptInstance] -sspRequirements = [readAndStore, verifyInput, generateCSS, calculateFS, +{-Functional Requirements-} + +sspFRequirements :: [ConceptInstance] +sspFRequirements = [readAndStore, verifyInput, generateCSS, calculateFS, determineCritSlip, verifyOutput, displayInput, displayGraph, displayFS, displayNormal, displayShear, writeToFile] @@ -104,3 +108,30 @@ sspInputsToOutputTable :: LabelledContent sspInputsToOutputTable = llcc (makeTabRef "inputsToOutputTable") $ Table [titleize symbol_, titleize name_] (mkTable [ch, phrase] inputsToOutput) (at_start' input_ +:+ S "to be returned as" +:+ phrase output_) True + +{-Nonfunctional Requirements-} +sspNFRequirements :: [ConceptInstance] +sspNFRequirements = [correct, understandable, reusable, maintainable] + +correct :: ConceptInstance +correct = cic "correct" (foldlSent [ + S "The", plural output_ `ofThe` phrase code, S "have the", + plural property, S "described in (Properties of a Correct Solution)" + -- FIXME: (Properties of a Correct Solution) Section doesn't exist + ]) "Correct" nonFuncReqDom + +understandable :: ConceptInstance +understandable = cic "understandable" (foldlSent [ + S "The", phrase code, S "is modularized with complete", + phrase mg `sAnd` phrase mis]) "Understandable" nonFuncReqDom + +reusable :: ConceptInstance +reusable = cic "reusable" (foldlSent [ + S "The", phrase code, S "is modularized"]) "Reusable" nonFuncReqDom + +maintainable :: ConceptInstance +maintainable = cic "maintainable" (foldlSent [ + S "The traceability between", foldlList Comma List [plural requirement, + plural assumption, plural thModel, plural genDefn, plural dataDefn, plural inModel, + plural likelyChg, plural unlikelyChg, plural module_], S "is completely recorded in", + plural traceyMatrix, S "in the", getAcc srs `sAnd` phrase mg]) "Maintainable" nonFuncReqDom diff --git a/code/stable/gamephys/SRS/Chipmunk_SRS.tex b/code/stable/gamephys/SRS/Chipmunk_SRS.tex index a0f7cd0f9e..e5971ac9ee 100644 --- a/code/stable/gamephys/SRS/Chipmunk_SRS.tex +++ b/code/stable/gamephys/SRS/Chipmunk_SRS.tex @@ -1106,10 +1106,10 @@ \subsubsection{Data Constraints} \end{longtable} \section{Requirements} \label{Sec:Requirements} -This section provides the functional requirements, the business tasks that the software is expected to complete, and the non-functional requirements, the qualities that the software is expected to exhibit. +This section provides the functional requirements, the tasks and behaviours that the software is expected to complete, and the non-functional requirements, the qualities that the software is expected to exhibit. \subsection{Functional Requirements} \label{Sec:FRs} -The following section provides the functional requirements, the business tasks that the software is expected to complete. +This section provides the functional requirements, the tasks and behaviours that the software is expected to complete. \begin{itemize} \item[Simulation-Space:\phantomsection\label{reqSS}]Create a space for all of the rigid bodies in the physical simulation to interact in. \item[Input-Initial-Conditions:\phantomsection\label{reqIIC}]Input the initial masses, velocities, orientations, angular velocities of, and forces applied on rigid bodies. diff --git a/code/stable/gamephys/Website/Chipmunk_SRS.html b/code/stable/gamephys/Website/Chipmunk_SRS.html index 2200865822..5e9f91e808 100644 --- a/code/stable/gamephys/Website/Chipmunk_SRS.html +++ b/code/stable/gamephys/Website/Chipmunk_SRS.html @@ -3585,7 +3585,7 @@

Requirements

-This section provides the functional requirements, the business tasks that the software is expected to complete, and the non-functional requirements, the qualities that the software is expected to exhibit. +This section provides the functional requirements, the tasks and behaviours that the software is expected to complete, and the non-functional requirements, the qualities that the software is expected to exhibit.

@@ -3593,7 +3593,7 @@

Functional Requirements

-The following section provides the functional requirements, the business tasks that the software is expected to complete. +This section provides the functional requirements, the tasks and behaviours that the software is expected to complete.

diff --git a/code/stable/glassbr/SRS/GlassBR_SRS.tex b/code/stable/glassbr/SRS/GlassBR_SRS.tex index ae84937c11..d534419e95 100644 --- a/code/stable/glassbr/SRS/GlassBR_SRS.tex +++ b/code/stable/glassbr/SRS/GlassBR_SRS.tex @@ -1022,10 +1022,10 @@ \subsubsection{Data Constraints} \end{longtable} \section{Requirements} \label{Sec:Requirements} -This section provides the functional requirements, the business tasks that the software is expected to complete, and the non-functional requirements, the qualities that the software is expected to exhibit. +This section provides the functional requirements, the tasks and behaviours that the software is expected to complete, and the non-functional requirements, the qualities that the software is expected to exhibit. \subsection{Functional Requirements} \label{Sec:FRs} -The following section provides the functional requirements, the business tasks that the software is expected to complete. +This section provides the functional requirements, the tasks and behaviours that the software is expected to complete. \begin{itemize} \item[Input-Glass-Props:\phantomsection\label{inputGlassProps}]Input the quantities from \hyperref[Table:InputGlassPropsReqInputs]{Table:InputGlassPropsReqInputs}, which define the glass dimensions, type of glass, tolerable probability of failure, and the characteristics of the blast. \item[System-Set-Values-Following-Assumptions:\phantomsection\label{sysSetValsFollowingAssumps}]The system shall set the known values as follows: diff --git a/code/stable/glassbr/Website/GlassBR_SRS.html b/code/stable/glassbr/Website/GlassBR_SRS.html index cc907eb155..da96511385 100644 --- a/code/stable/glassbr/Website/GlassBR_SRS.html +++ b/code/stable/glassbr/Website/GlassBR_SRS.html @@ -3298,7 +3298,7 @@

Requirements

-This section provides the functional requirements, the business tasks that the software is expected to complete, and the non-functional requirements, the qualities that the software is expected to exhibit. +This section provides the functional requirements, the tasks and behaviours that the software is expected to complete, and the non-functional requirements, the qualities that the software is expected to exhibit.

@@ -3306,7 +3306,7 @@

Functional Requirements

-The following section provides the functional requirements, the business tasks that the software is expected to complete. +This section provides the functional requirements, the tasks and behaviours that the software is expected to complete.

diff --git a/code/stable/nopcm/SRS/NoPCM_SRS.tex b/code/stable/nopcm/SRS/NoPCM_SRS.tex index 6b5ff29448..130bddcffe 100644 --- a/code/stable/nopcm/SRS/NoPCM_SRS.tex +++ b/code/stable/nopcm/SRS/NoPCM_SRS.tex @@ -625,10 +625,10 @@ \subsubsection{Data Constraints} \end{longtable} \section{Requirements} \label{Sec:Requirements} -This section provides the functional requirements, the business tasks that the software is expected to complete, and the non-functional requirements, the qualities that the software is expected to exhibit. +This section provides the functional requirements, the tasks and behaviours that the software is expected to complete, and the non-functional requirements, the qualities that the software is expected to exhibit. \subsection{Functional Requirements} \label{Sec:FRs} -The following section provides the functional requirements, the business tasks that the software is expected to complete. +This section provides the functional requirements, the tasks and behaviours that the software is expected to complete. \begin{itemize} \item[Input-Inital-Values:\phantomsection\label{reqIIV}]Input the quantities described in \hyperref[Table:Input-Variable-Requirements]{Table:Input-Variable-Requirements}, which define the tank parameters, material properties and initial conditions. \item[Find-Mass:\phantomsection\label{reqFM}]Use the inputs in \hyperref[reqIIV]{FR: Input-Inital-Values} to find the mass needed for \hyperref[IM:eBalanceOnWtr]{IM: eBalanceOnWtr}, as follows, where ${V_{W}}$ is the volume of water and ${V_{tank}}$ is the volume of the cylindrical tank: ${m_{W}}={V_{W}} {ρ_{W}}=\frac{D}{2} L {ρ_{W}}$ diff --git a/code/stable/nopcm/Website/NoPCM_SRS.html b/code/stable/nopcm/Website/NoPCM_SRS.html index efaba39b39..c98c2a86ec 100644 --- a/code/stable/nopcm/Website/NoPCM_SRS.html +++ b/code/stable/nopcm/Website/NoPCM_SRS.html @@ -2084,7 +2084,7 @@

Requirements

-This section provides the functional requirements, the business tasks that the software is expected to complete, and the non-functional requirements, the qualities that the software is expected to exhibit. +This section provides the functional requirements, the tasks and behaviours that the software is expected to complete, and the non-functional requirements, the qualities that the software is expected to exhibit.

@@ -2092,7 +2092,7 @@

Functional Requirements

-The following section provides the functional requirements, the business tasks that the software is expected to complete. +This section provides the functional requirements, the tasks and behaviours that the software is expected to complete.

diff --git a/code/stable/ssp/SRS/SSP_SRS.tex b/code/stable/ssp/SRS/SSP_SRS.tex index cb6d44c679..301c36c227 100644 --- a/code/stable/ssp/SRS/SSP_SRS.tex +++ b/code/stable/ssp/SRS/SSP_SRS.tex @@ -2080,10 +2080,10 @@ \subsubsection{Data Constraints} \end{longtable} \section{Requirements} \label{Sec:Requirements} -This section provides the functional requirements, the business tasks that the software is expected to complete, and the non-functional requirements, the qualities that the software is expected to exhibit. +This section provides the functional requirements, the tasks and behaviours that the software is expected to complete, and the non-functional requirements, the qualities that the software is expected to exhibit. \subsection{Functional Requirements} \label{Sec:FRs} -The following section provides the functional requirements, the business tasks that the software is expected to complete. +This section provides the functional requirements, the tasks and behaviours that the software is expected to complete. \begin{itemize} \item[Read-and-Store:\phantomsection\label{readAndStore}]Read the inputs, shown in \hyperref[Table:inDataTable]{Table:inDataTable}, and store the data. \item[Verify-Input:\phantomsection\label{verifyInput}]Verify that the input data lie within the physical constraints shown in \hyperref[Table:InDataConstraints]{Table:InDataConstraints}. @@ -2168,7 +2168,14 @@ \subsection{Functional Requirements} \end{longtable} \subsection{Non-Functional Requirements} \label{Sec:NFRs} -SSP is intended to be an educational tool, so accuracy and performance are not priorities. Rather, the non-functional requirement priorities are correctness, understandability, reusability, and maintainability. +This section provides the non-functional requirements, the qualities that the software is expected to exhibit. +SSP is intended to be an educational tool, so accuracy and performance are not priorities. Rather, the non-functional requirement priorities are: +\begin{itemize} +\item[Correct:\phantomsection\label{correct}]The the outputs of the code have the properties described in (Properties of a Correct Solution). +\item[Understandable:\phantomsection\label{understandable}]The code is modularized with complete module guide and module interface specification. +\item[Reusable:\phantomsection\label{reusable}]The code is modularized. +\item[Maintainable:\phantomsection\label{maintainable}]The traceability between requirements, assumptions, theoretical models, general definitions, data definitions, instance models, likely changes, unlikely changes, and modules is completely recorded in traceability matrices in the SRS and module guide. +\end{itemize} \section{Likely Changes} \label{Sec:LCs} \begin{itemize} diff --git a/code/stable/ssp/Website/SSP_SRS.html b/code/stable/ssp/Website/SSP_SRS.html index 17e39f639d..5c68fde2be 100644 --- a/code/stable/ssp/Website/SSP_SRS.html +++ b/code/stable/ssp/Website/SSP_SRS.html @@ -6775,7 +6775,7 @@

Requirements

-This section provides the functional requirements, the business tasks that the software is expected to complete, and the non-functional requirements, the qualities that the software is expected to exhibit. +This section provides the functional requirements, the tasks and behaviours that the software is expected to complete, and the non-functional requirements, the qualities that the software is expected to exhibit.

@@ -6783,7 +6783,7 @@

Functional Requirements

-The following section provides the functional requirements, the business tasks that the software is expected to complete. +This section provides the functional requirements, the tasks and behaviours that the software is expected to complete.

@@ -7131,8 +7131,33 @@

Non-Functional Requirements

-SSP is intended to be an educational tool, so accuracy and performance are not priorities. Rather, the non-functional requirement priorities are correctness, understandability, reusability, and maintainability. +This section provides the non-functional requirements, the qualities that the software is expected to exhibit.

+

+SSP is intended to be an educational tool, so accuracy and performance are not priorities. Rather, the non-functional requirement priorities are: +

+
+

+

+Correct: The the outputs of the code have the properties described in (Properties of a Correct Solution). +
+

+

+

+Understandable: The code is modularized with complete module guide and module interface specification. +
+

+

+

+Reusable: The code is modularized. +
+

+

+

+Maintainable: The traceability between requirements, assumptions, theoretical models, general definitions, data definitions, instance models, likely changes, unlikely changes, and modules is completely recorded in traceability matrices in the SRS and module guide. +
+

+
diff --git a/code/stable/swhs/SRS/SWHS_SRS.tex b/code/stable/swhs/SRS/SWHS_SRS.tex index e9df56ce12..07688499b8 100644 --- a/code/stable/swhs/SRS/SWHS_SRS.tex +++ b/code/stable/swhs/SRS/SWHS_SRS.tex @@ -1055,10 +1055,10 @@ \subsubsection{Properties of a Correct Solution} Equations (FIXME: Equation 7) and (FIXME: Equation 8) can be used as ``sanity'' checks to gain confidence in any solution computed by SWHS. The relative error between the results computed by SWHS and the results calculated from the RHS of these equations should be less than 0.001% \hyperref[verifyEnergyOutput]{FR: Verify-Energy-Output-Follow-Conservation-of-Energy}. \section{Requirements} \label{Sec:Requirements} -This section provides the functional requirements, the business tasks that the software is expected to complete, and the non-functional requirements, the qualities that the software is expected to exhibit. +This section provides the functional requirements, the tasks and behaviours that the software is expected to complete, and the non-functional requirements, the qualities that the software is expected to exhibit. \subsection{Functional Requirements} \label{Sec:FRs} -The following section provides the functional requirements, the business tasks that the software is expected to complete. +This section provides the functional requirements, the tasks and behaviours that the software is expected to complete. \begin{itemize} \item[Input-Initial-Quantities:\phantomsection\label{inputInitQuants}]Input the following quantities described in \hyperref[Table:Input-Variable-Requirements]{Table:Input-Variable-Requirements}, which define the tank parameters, material properties and initial conditions. \hyperref[assumpVCN]{A: Volume-Coil-Negligible}. \item[Find-Mass:\phantomsection\label{findMass}]Use the inputs in \hyperref[inputInitQuants]{FR: Input-Initial-Quantities} to find the mass needed for \hyperref[IM:eBalanceOnWtr]{IM: eBalanceOnWtr}, \hyperref[IM:eBalanceOnPCM]{IM: eBalanceOnPCM}, \hyperref[IM:heatEInWtr]{IM: heatEInWtr}, and \hyperref[IM:heatEInPCM]{IM: heatEInPCM}, using ${m_{W}}={V_{W}} {ρ_{W}}=\left({V_{tank}}-{V_{P}}\right) {ρ_{W}}=\left(\frac{D}{2} L-{V_{P}}\right) {ρ_{W}}$ and ${m_{P}}={V_{P}} {ρ_{P}}$, where ${V_{W}}$ is the volume of water and ${V_{tank}}$ is the volume of the cylindrical tank. diff --git a/code/stable/swhs/Website/SWHS_SRS.html b/code/stable/swhs/Website/SWHS_SRS.html index 606c902f86..138ac573b2 100644 --- a/code/stable/swhs/Website/SWHS_SRS.html +++ b/code/stable/swhs/Website/SWHS_SRS.html @@ -3808,7 +3808,7 @@

Requirements

-This section provides the functional requirements, the business tasks that the software is expected to complete, and the non-functional requirements, the qualities that the software is expected to exhibit. +This section provides the functional requirements, the tasks and behaviours that the software is expected to complete, and the non-functional requirements, the qualities that the software is expected to exhibit.

@@ -3816,7 +3816,7 @@

Functional Requirements

-The following section provides the functional requirements, the business tasks that the software is expected to complete. +This section provides the functional requirements, the tasks and behaviours that the software is expected to complete.