{-#LANGUAGE PostfixOperators#-}
module Drasil.PDController.Requirements where
import Data.Drasil.Concepts.Documentation (funcReqDom, datumConstraint)
import Drasil.DocLang.SRS (datCon)
import Drasil.DocLang (mkMaintainableNFR, mkPortableNFR, mkVerifiableNFR, mkSecurityNFR)
import Drasil.PDController.Concepts
import Drasil.PDController.IModel
import Language.Drasil
funcReqs :: [ConceptInstance]
funcReqs :: [ConceptInstance]
funcReqs = [ConceptInstance
verifyInputs, ConceptInstance
calculateValues, ConceptInstance
outputValues]
verifyInputs, calculateValues, outputValues :: ConceptInstance
verifyInputs :: ConceptInstance
verifyInputs
= String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"verifyInputs" Sentence
verifyInputsDesc String
"Verify-Input-Values" ConceptChunk
funcReqDom
calculateValues :: ConceptInstance
calculateValues
= String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"calculateValues" Sentence
calculateValuesDesc String
"Calculate-Values" ConceptChunk
funcReqDom
outputValues :: ConceptInstance
outputValues = String -> Sentence -> String -> ConceptChunk -> ConceptInstance
forall c.
Concept c =>
String -> Sentence -> String -> c -> ConceptInstance
cic String
"outputValues" Sentence
outputValuesDesc String
"Output-Values" ConceptChunk
funcReqDom
verifyInputsDesc, calculateValuesDesc, outputValuesDesc :: Sentence
verifyInputsDesc :: Sentence
verifyInputsDesc
= [Sentence] -> Sentence
foldlSent_
[String -> Sentence
S String
"Ensure that the input values are within the",
String -> Sentence
S String
"limits specified in the"
Sentence -> Sentence -> Sentence
+:+. Section -> Sentence -> Sentence
forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef ([Contents] -> [Section] -> Section
datCon [] []) (IdeaDict -> Sentence
forall n. NamedIdea n => n -> Sentence
plural IdeaDict
datumConstraint)]
calculateValuesDesc :: Sentence
calculateValuesDesc
= [Sentence] -> Sentence
foldlSent
[String -> Sentence
S String
"Calculate the", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
processVariable, InstanceModel -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource InstanceModel
imPD,
String -> Sentence
S String
"over the simulation time"]
outputValuesDesc :: Sentence
outputValuesDesc
= [Sentence] -> Sentence
foldlSent
[String -> Sentence
S String
"Output the", ConceptChunk -> Sentence
forall n. NamedIdea n => n -> Sentence
phrase ConceptChunk
processVariable, InstanceModel -> Sentence
forall r. (Referable r, HasShortName r) => r -> Sentence
fromSource InstanceModel
imPD,
String -> Sentence
S String
"over the simulation time"]
nonfuncReqs :: [ConceptInstance]
nonfuncReqs :: [ConceptInstance]
nonfuncReqs = [ConceptInstance
portability, ConceptInstance
security, ConceptInstance
maintainability, ConceptInstance
verifiability]
portability :: ConceptInstance
portability :: ConceptInstance
portability = String -> [String] -> String -> ConceptInstance
mkPortableNFR String
"portable" [String
"Windows", String
"Mac OSX", String
"Linux"] String
"Portability"
security :: ConceptInstance
security :: ConceptInstance
security = String -> String -> ConceptInstance
mkSecurityNFR String
"security" String
"Security"
maintainability :: ConceptInstance
maintainability :: ConceptInstance
maintainability = String -> Integer -> String -> ConceptInstance
mkMaintainableNFR String
"maintainability" Integer
10 String
"Maintainability"
verifiability :: ConceptInstance
verifiability :: ConceptInstance
verifiability = String -> String -> ConceptInstance
mkVerifiableNFR String
"verifiability" String
"Verifiability"