Skip to content

Commit

Permalink
Standardize Non-Functional Requirement Labels. (#3965)
Browse files Browse the repository at this point in the history
* Refactored common NFR descriptions into reusable functions to prevent inconsistencies across examples.

* Ensure NFR labels are consistent across all examples.

- Modified the following examples: dblpend, GlassBR, SWHSNoPCM, PDController, Projectile, SglPend, SSP, SWHS.

* Stabilize.

keep the code clean and avoid unnecessary dependencies.
  • Loading branch information
Xinlu-Y authored Sep 19, 2024
1 parent 90c92fd commit 6abd87c
Show file tree
Hide file tree
Showing 35 changed files with 330 additions and 332 deletions.
5 changes: 4 additions & 1 deletion code/drasil-docLang/lib/Drasil/DocLang.hs
Original file line number Diff line number Diff line change
Expand Up @@ -57,6 +57,8 @@ module Drasil.DocLang (
-- Drasil.Sections.Requirements
inReq, inTable, mkInputPropsTable, mkQRTuple, mkQRTupleRef,
mkValsSourceTable, reqInputsRef, mkMaintainableNFR, mkPortableNFR,
mkCorrectNFR, mkVerifiableNFR, mkUnderstandableNFR, mkReusableNFR,
mkSecurityNFR,
-- ** Specific System Description
-- Drasil.Sections.SpecificSystemDescription
auxSpecSent, termDefnF', inDataConstTbl, outDataConstTbl,
Expand Down Expand Up @@ -92,7 +94,8 @@ import Drasil.Sections.AuxiliaryConstants (tableOfConstants)
import Drasil.Sections.Introduction (purpDoc)
import Drasil.Sections.ReferenceMaterial (intro, emptySectSentPlu, emptySectSentSing)
import Drasil.Sections.Requirements (inReq, inTable, mkInputPropsTable,
mkQRTuple, mkQRTupleRef, mkValsSourceTable, reqInputsRef, mkMaintainableNFR, mkPortableNFR)
mkQRTuple, mkQRTupleRef, mkValsSourceTable, reqInputsRef, mkMaintainableNFR, mkPortableNFR, mkCorrectNFR,
mkVerifiableNFR, mkUnderstandableNFR, mkReusableNFR, mkSecurityNFR)
import Drasil.Sections.SpecificSystemDescription (auxSpecSent, termDefnF', inDataConstTbl, outDataConstTbl)
--import Drasil.Sections.Stakeholders
--import Drasil.Sections.TableOfAbbAndAcronyms
Expand Down
39 changes: 35 additions & 4 deletions code/drasil-docLang/lib/Drasil/Sections/Requirements.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,8 @@ module Drasil.Sections.Requirements (
fullReqs, fullTables, inReq, inTable,
mkInputPropsTable, mkQRTuple, mkQRTupleRef, mkValsSourceTable,
-- * Non-functional Requirements
nfReqF, mkMaintainableNFR, mkPortableNFR
nfReqF, mkMaintainableNFR, mkPortableNFR, mkCorrectNFR, mkVerifiableNFR,
mkUnderstandableNFR, mkReusableNFR, mkSecurityNFR
) where

import Utils.Drasil (stringList)
Expand All @@ -20,8 +21,8 @@ import Drasil.Sections.ReferenceMaterial(emptySectSentPlu)
import Theory.Drasil (HasOutput(output))

import Data.Drasil.Concepts.Documentation (description, funcReqDom, nonFuncReqDom,
functionalRequirement, input_, nonfunctionalRequirement, {-output_,-} section_,
software, symbol_, value, reqInput)
functionalRequirement, input_, nonfunctionalRequirement, output_, section_,
software, symbol_, value, reqInput, code, propOfCorSol, vavPlan, mg, mis)
import Data.Drasil.Concepts.Math (unit_)

import qualified Drasil.DocLang.SRS as SRS
Expand Down Expand Up @@ -122,7 +123,37 @@ mkPortableNFR refAddress osList lbl = cic refAddress (foldlSent [
S "The code shall be portable to multiple environments, particularly",
S $ stringList osList
]) lbl nonFuncReqDom


-- | Common Non-Functional Requirement for Correctness.
mkCorrectNFR :: String -> String -> ConceptInstance
mkCorrectNFR refAddress lbl = cic refAddress (foldlSent [
atStartNP' (output_ `the_ofThePS` code), S "have the",
namedRef (SRS.propCorSol [] []) (plural propOfCorSol)
]) lbl nonFuncReqDom

-- | Common Non-Functional Requirement for Verifiability.
mkVerifiableNFR :: String -> String -> ConceptInstance
mkVerifiableNFR refAddress lbl = cic refAddress (foldlSent [
atStartNP (the code), S "is tested with complete",
phrase vavPlan]) lbl nonFuncReqDom

-- | Common Non-Functional Requirement for Understandability.
mkUnderstandableNFR :: String -> String -> ConceptInstance
mkUnderstandableNFR refAddress lbl = cic refAddress (foldlSent [
atStartNP (the code), S "is modularized with complete",
phrase mg `S.and_` phrase mis]) lbl nonFuncReqDom

-- | Common Non-Functional Requirement for Reusability.
mkReusableNFR :: String -> String -> ConceptInstance
mkReusableNFR refAddress lbl = cic refAddress (foldlSent [
atStartNP (the code), S "is modularized"]) lbl nonFuncReqDom

-- | Common Non-Functional Requirement for Security.
mkSecurityNFR :: String -> String -> ConceptInstance
mkSecurityNFR refAddress lbl = cic refAddress (foldlSent [
S "The code shall be immune to common security problems such as memory",
S "leaks, divide by zero errors, and the square root of negative numbers"
]) lbl nonFuncReqDom

-- | Creates an Input Data Table for use in the Functional Requirments section. Takes a list of wrapped variables and something that is 'Referable'.
mkInputPropsTable :: (Quantity i, MayHaveUnit i, HasShortName r, Referable r) =>
Expand Down
12 changes: 4 additions & 8 deletions code/drasil-example/dblpend/lib/Drasil/DblPend/Requirements.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,13 @@
module Drasil.DblPend.Requirements where

import Language.Drasil
import Drasil.DocLang.SRS (datCon, propCorSol)
import Drasil.DocLang (mkPortableNFR)
import Language.Drasil.Chunk.Concept.NamedCombinators
import Drasil.DocLang.SRS (datCon)
import Drasil.DocLang (mkPortableNFR, mkCorrectNFR)
import qualified Language.Drasil.Sentence.Combinators as S

import Data.Drasil.Concepts.Computation (inValue)
import Data.Drasil.Concepts.Documentation (datumConstraint, funcReqDom,
output_, value, nonFuncReqDom, code, propOfCorSol)
output_, value)
-- likelyChg, mg, mis, module_, nonFuncReqDom,
-- requirement, srs, traceyMatrix, unlikelyChg, value, vavPlan)
import Data.Drasil.Concepts.Math (calculation)
Expand Down Expand Up @@ -47,10 +46,7 @@ nonFuncReqs :: [ConceptInstance]
nonFuncReqs = [correct, portable]

correct :: ConceptInstance
correct = cic "correct" (foldlSent [
atStartNP' (output_ `the_ofThePS` code), S "have the",
namedRef (propCorSol [] []) (plural propOfCorSol)]
) "Correctness" nonFuncReqDom
correct = mkCorrectNFR "correct" "Correctness"

portable :: ConceptInstance
portable = mkPortableNFR "portable" ["Windows", "Mac OSX", "Linux"] "Portability"
28 changes: 11 additions & 17 deletions code/drasil-example/glassbr/lib/Drasil/GlassBR/Requirements.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,17 +3,19 @@ module Drasil.GlassBR.Requirements (funcReqs, funcReqsTables, inReqDesc, nonfunc
import Control.Lens ((^.))

import Language.Drasil
import Drasil.DocLang (inReq, mkQRTuple, mkQRTupleRef, mkValsSourceTable, mkMaintainableNFR, mkPortableNFR)
import Drasil.DocLang.SRS (datCon, propCorSol)
import Drasil.DocLang (inReq, mkQRTuple, mkQRTupleRef, mkValsSourceTable,
mkMaintainableNFR, mkPortableNFR, mkCorrectNFR, mkVerifiableNFR,
mkUnderstandableNFR, mkReusableNFR)
import Drasil.DocLang.SRS (datCon)
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.NounPhrase.Combinators as NP
import qualified Language.Drasil.Sentence.Combinators as S
import Theory.Drasil (DataDefinition)

import Data.Drasil.Concepts.Computation (inValue)
import Data.Drasil.Concepts.Documentation (characteristic, code,
condition, datumConstraint, funcReqDom, message, mg,
mis, nonFuncReqDom, output_, property, system, type_, value, vavPlan)
import Data.Drasil.Concepts.Documentation (characteristic, condition,
datumConstraint, funcReqDom, message, output_, system,
type_, value)
import Data.Drasil.Concepts.Math (calculation)
import Data.Drasil.Concepts.PhysicalProperties (dimension)
import Data.Drasil.Concepts.Software (errMsg)
Expand Down Expand Up @@ -93,24 +95,16 @@ nonfuncReqs :: [ConceptInstance]
nonfuncReqs = [correct, verifiable, understandable, reusable, maintainable, portable]

correct :: ConceptInstance
correct = cic "correct" (foldlSent [
atStartNP' (output_ `the_ofThePS` code), S "have the",
plural property, S "described in", refS (propCorSol [] [])
]) "Correctness" nonFuncReqDom
correct = mkCorrectNFR "correct" "Correctness"

verifiable :: ConceptInstance
verifiable = cic "verifiable" (foldlSent [
atStartNP (the code), S "is tested with complete",
phrase vavPlan]) "Verifiability" nonFuncReqDom
verifiable = mkVerifiableNFR "verifiable" "Verifiability"

understandable :: ConceptInstance
understandable = cic "understandable" (foldlSent [
atStartNP (the code), S "is modularized with complete",
phrase mg `S.and_` phrase mis]) "Understandability" nonFuncReqDom
understandable = mkUnderstandableNFR "understandable" "Understandability"

reusable :: ConceptInstance
reusable = cic "reusable" (foldlSent [
atStartNP (the code), S "is modularized"]) "Reusability" nonFuncReqDom
reusable = mkReusableNFR "reusable" "Reusability"

maintainable :: ConceptInstance
maintainable = mkMaintainableNFR "maintainable" 10 "Maintainability"
Expand Down
Original file line number Diff line number Diff line change
@@ -1,9 +1,9 @@
{-#LANGUAGE PostfixOperators#-}
module Drasil.PDController.Requirements where

import Data.Drasil.Concepts.Documentation (funcReqDom, nonFuncReqDom, datumConstraint)
import Data.Drasil.Concepts.Documentation (funcReqDom, datumConstraint)
import Drasil.DocLang.SRS (datCon)
import Drasil.DocLang (mkMaintainableNFR, mkPortableNFR)
import Drasil.DocLang (mkMaintainableNFR, mkPortableNFR, mkVerifiableNFR, mkSecurityNFR)

import Drasil.PDController.Concepts
import Drasil.PDController.IModel
Expand Down Expand Up @@ -47,20 +47,10 @@ portability :: ConceptInstance
portability = mkPortableNFR "portable" ["Windows", "Mac OSX", "Linux"] "Portability"

security :: ConceptInstance
security
= cic "security"
(foldlSent
[S "The code shall be immune to common security problems such as memory",
S "leaks, divide by zero errors, and the square root of negative numbers"])
"Security"
nonFuncReqDom
security = mkSecurityNFR "security" "Security"

maintainability :: ConceptInstance
maintainability = mkMaintainableNFR "maintainability" 10 "Maintainability"

verifiability :: ConceptInstance
verifiability
= cic "verifiability"
(S "The code shall be verifiable against a Verification and Validation plan" !.)
"Verifiability"
nonFuncReqDom
verifiability = mkVerifiableNFR "verifiability" "Verifiability"
Original file line number Diff line number Diff line change
@@ -1,15 +1,14 @@
module Drasil.Projectile.Requirements (funcReqs, nonfuncReqs) where

import Language.Drasil
import Drasil.DocLang.SRS (datCon, propCorSol)
import Language.Drasil.Chunk.Concept.NamedCombinators
import Drasil.DocLang.SRS (datCon)
import qualified Language.Drasil.Sentence.Combinators as S
import Drasil.DocLang (mkMaintainableNFR, mkPortableNFR)
import Drasil.DocLang (mkMaintainableNFR, mkPortableNFR, mkCorrectNFR,
mkVerifiableNFR, mkUnderstandableNFR, mkReusableNFR)

import Data.Drasil.Concepts.Computation (inValue)
import Data.Drasil.Concepts.Documentation (code, datumConstraint,
funcReqDom, mg, mis, nonFuncReqDom, output_,
property, value, vavPlan, propOfCorSol)
import Data.Drasil.Concepts.Documentation (datumConstraint,
funcReqDom, output_, value)
import Data.Drasil.Concepts.Math (calculation)
import Data.Drasil.Concepts.Software (errMsg)

Expand Down Expand Up @@ -53,23 +52,16 @@ nonfuncReqs :: [ConceptInstance]
nonfuncReqs = [correct, verifiable, understandable, reusable, maintainable, portable]

correct :: ConceptInstance
correct = cic "correct" (foldlSent [
atStartNP' (output_ `the_ofThePS` code), S "have the",
plural property, S "described in", namedRef (propCorSol [] []) (titleize' propOfCorSol)
]) "Correctness" nonFuncReqDom
correct = mkCorrectNFR "correct" "Correctness"

verifiable :: ConceptInstance
verifiable = cic "verifiable" (foldlSent [
atStartNP (the code), S "is tested with complete",
phrase vavPlan]) "Verifiability" nonFuncReqDom
verifiable = mkVerifiableNFR "verifiable" "Verifiability"

understandable :: ConceptInstance
understandable = cic "understandable" (foldlSent [
atStartNP (the code), S "is modularized with complete",
phraseNP (mg `and_` mis)]) "Understandability" nonFuncReqDom
understandable = mkUnderstandableNFR "understandable" "Understandability"

reusable :: ConceptInstance
reusable = cic "reusable" (foldlSent [atStartNP (the code), S "is modularized"]) "Reusability" nonFuncReqDom
reusable = mkReusableNFR "reusable" "Reusability"

maintainable :: ConceptInstance
maintainable = mkMaintainableNFR "maintainable" 10 "Maintainability"
Expand Down
22 changes: 8 additions & 14 deletions code/drasil-example/ssp/lib/Drasil/SSP/Requirements.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,13 +4,13 @@ import Language.Drasil
import Language.Drasil.Chunk.Concept.NamedCombinators
import qualified Language.Drasil.Sentence.Combinators as S

import Drasil.DocLang (mkInputPropsTable, mkMaintainableNFR)
import Drasil.DocLang (mkInputPropsTable, mkMaintainableNFR, mkCorrectNFR,
mkUnderstandableNFR, mkReusableNFR)
import Drasil.DocLang.SRS (datCon, propCorSol)

import Data.Drasil.Concepts.Computation (inDatum)
import Data.Drasil.Concepts.Documentation (code,
datum, funcReqDom, input_, mg, mis, name_, nonFuncReqDom,
output_, physicalConstraint, property, symbol_, user, value, propOfCorSol)
import Data.Drasil.Concepts.Documentation (datum, funcReqDom, input_, name_,
output_, physicalConstraint, symbol_, user, value, propOfCorSol)
import Data.Drasil.Concepts.Physics (twoD)

import Drasil.SSP.Defs (crtSlpSrf, slope, slpSrf)
Expand Down Expand Up @@ -108,19 +108,13 @@ nonFuncReqs :: [ConceptInstance]
nonFuncReqs = [correct, understandable, reusable, maintainable]

correct :: ConceptInstance
correct = cic "correct" (foldlSent [
atStartNP' (output_ `the_ofThePS` code), S "have the",
plural property, S "described in", refS (propCorSol [] [])
]) "Correct" nonFuncReqDom
correct = mkCorrectNFR "correct" "Correctness"

understandable :: ConceptInstance
understandable = cic "understandable" (foldlSent [
atStartNP (the code), S "is modularized with complete",
phrase mg `S.and_` phrase mis]) "Understandable" nonFuncReqDom
understandable = mkUnderstandableNFR "understandable" "Understandability"

reusable :: ConceptInstance
reusable = cic "reusable" (foldlSent [
atStartNP (the code), S "is modularized"]) "Reusable" nonFuncReqDom
reusable = mkReusableNFR "reusable" "Reusability"

maintainable :: ConceptInstance
maintainable = mkMaintainableNFR "maintainable" 10 "Maintainable"
maintainable = mkMaintainableNFR "maintainable" 10 "Maintainability"
26 changes: 9 additions & 17 deletions code/drasil-example/swhs/lib/Drasil/SWHS/Requirements.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,13 +6,13 @@ import qualified Language.Drasil.NounPhrase.Combinators as NP
import qualified Language.Drasil.Sentence.Combinators as S
import Theory.Drasil (InstanceModel, HasOutput(output))

import Drasil.DocLang (inReq, mkMaintainableNFR)
import Drasil.DocLang (inReq, mkMaintainableNFR, mkCorrectNFR, mkVerifiableNFR,
mkUnderstandableNFR, mkReusableNFR)
import Drasil.DocLang.SRS (datCon, propCorSol)

import Data.Drasil.Concepts.Computation (inValue)
import Data.Drasil.Concepts.Documentation (code, condition,
funcReqDom, input_, mg, mis, nonFuncReqDom, output_,
physicalConstraint, property, propOfCorSol, value, vavPlan)
import Data.Drasil.Concepts.Documentation (condition, funcReqDom, input_, output_,
physicalConstraint, propOfCorSol, value)
import Data.Drasil.Concepts.Math (parameter)
import Data.Drasil.Concepts.PhysicalProperties (materialProprty)
import Data.Drasil.Concepts.Thermodynamics as CT (lawConsEnergy, melting)
Expand Down Expand Up @@ -136,24 +136,16 @@ nfRequirements :: [ConceptInstance]
nfRequirements = [correct, verifiable, understandable, reusable, maintainable]

correct :: ConceptInstance
correct = cic "correct" (foldlSent [atStartNP'
(output_ `the_ofThePS` code), S "have the",
plural property, S "described in", namedRef (propCorSol [] []) (titleize' propOfCorSol)
]) "Correct" nonFuncReqDom
correct = mkCorrectNFR "correct" "Correctness"

verifiable :: ConceptInstance
verifiable = cic "verifiable" (foldlSent [
atStartNP (the code), S "is tested with complete",
phrase vavPlan]) "Verifiable" nonFuncReqDom
verifiable = mkVerifiableNFR "verifiable" "Verifiability"

understandable :: ConceptInstance
understandable = cic "understandable" (foldlSent [
atStartNP (the code), S "is modularized with complete",
phrase mg `S.and_` phrase mis]) "Understandable" nonFuncReqDom
understandable = mkUnderstandableNFR "understandable" "Understandability"

reusable :: ConceptInstance
reusable = cic "reusable" (foldlSent [
atStartNP (the code), S "is modularized"]) "Reusable" nonFuncReqDom
reusable = mkReusableNFR "reusable" "Reusability"

maintainable :: ConceptInstance
maintainable = mkMaintainableNFR "maintainable" 10 "Maintainable"
maintainable = mkMaintainableNFR "maintainable" 10 "Maintainability"
2 changes: 1 addition & 1 deletion code/stable/glassbr/SRS/HTML/GlassBR_SRS.html

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion code/stable/glassbr/SRS/Jupyter/GlassBR_SRS.ipynb

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion code/stable/glassbr/SRS/PDF/GlassBR_SRS.tex

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion code/stable/glassbr/SRS/mdBook/src/SecNFRs.md

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion code/stable/pdcontroller/SRS/HTML/PDController_SRS.html

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion code/stable/pdcontroller/SRS/PDF/PDController_SRS.tex

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

Loading

0 comments on commit 6abd87c

Please sign in to comment.