Skip to content

Commit

Permalink
Transitioned NFR implementation in SSP (#1273)
Browse files Browse the repository at this point in the history
* 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
  • Loading branch information
samm82 authored and JacquesCarette committed May 6, 2019
1 parent d5650a6 commit 5598d93
Show file tree
Hide file tree
Showing 17 changed files with 152 additions and 77 deletions.
8 changes: 5 additions & 3 deletions code/drasil-data/Data/Drasil/Concepts/Documentation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand All @@ -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]
Expand Down Expand Up @@ -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,
Expand All @@ -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
Expand Down
4 changes: 2 additions & 2 deletions code/drasil-docLang/Drasil/DocLang.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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),
Expand Down Expand Up @@ -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'',
Expand Down
6 changes: 4 additions & 2 deletions code/drasil-docLang/Drasil/DocLang/SRS.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -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"
Expand All @@ -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"
4 changes: 2 additions & 2 deletions code/drasil-docLang/Drasil/DocumentLanguage.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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,
Expand Down Expand Up @@ -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)

{--}

Expand Down
69 changes: 41 additions & 28 deletions code/drasil-docLang/Drasil/Sections/Requirements.hs
Original file line number Diff line number Diff line change
@@ -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

Expand All @@ -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
Expand All @@ -43,37 +60,33 @@ 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_
listO explanation_ [] priority_ = S "so" +:+ head priority_ +:+ S "is a high" +:+. (phrase priority) +:+ explanation_ +:+ S "The other" +:+. listT (tail 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] -> [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"
19 changes: 7 additions & 12 deletions code/drasil-example/Drasil/SSP/Body.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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,
Expand All @@ -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)
Expand Down Expand Up @@ -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,
Expand Down Expand Up @@ -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
Expand All @@ -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
Expand All @@ -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

Expand Down Expand Up @@ -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 --
Expand Down
43 changes: 37 additions & 6 deletions code/drasil-example/Drasil/SSP/Requirements.hs
Original file line number Diff line number Diff line change
@@ -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),
Expand All @@ -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]

Expand Down Expand Up @@ -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
Loading

0 comments on commit 5598d93

Please sign in to comment.