module Language.Drasil.Code.Imperative.Descriptions (
modDesc, unmodularDesc, inputParametersDesc, inputConstructorDesc,
inputFormatDesc, derivedValuesDesc, inputConstraintsDesc, constModDesc,
outputFormatDesc, inputClassDesc, constClassDesc, inFmtFuncDesc,
inConsFuncDesc, dvFuncDesc, calcModDesc, woFuncDesc
) where
import Utils.Drasil (stringList)
import Language.Drasil
import Language.Drasil.Chunk.CodeBase
import Language.Drasil.Code.Imperative.DrasilState (GenState, DrasilState(..),
genICName)
import Language.Drasil.Choices (ImplementationType(..), Structure(..),
InternalConcept(..))
import Language.Drasil.CodeSpec (HasOldCodeSpec(..))
import Language.Drasil.Mod (Description)
import Language.Drasil.Printers (SingleLine(OneLine), sentenceDoc)
import Data.Map (member)
import qualified Data.Map as Map (filter, lookup, null)
import Data.Maybe (mapMaybe)
import Control.Lens ((^.))
import Control.Monad.State (get)
import SysInfo.Drasil hiding (sysinfodb)
modDesc :: GenState [Description] -> GenState Description
modDesc :: GenState [Name] -> GenState Name
modDesc = ([Name] -> Name) -> GenState [Name] -> GenState Name
forall a b.
(a -> b)
-> StateT DrasilState Identity a -> StateT DrasilState Identity b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Name -> Name -> Name
forall a. [a] -> [a] -> [a]
(++) Name
"Provides " (Name -> Name) -> ([Name] -> Name) -> [Name] -> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Name] -> Name
stringList)
unmodularDesc :: GenState Description
unmodularDesc :: GenState Name
unmodularDesc = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let spec :: CodeSpec
spec = DrasilState -> CodeSpec
codeSpec DrasilState
g
implTypeStr :: ImplementationType -> Name
implTypeStr ImplementationType
Program = Name
"program"
implTypeStr ImplementationType
Library = Name
"library"
Name -> GenState Name
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> GenState Name) -> Name -> GenState Name
forall a b. (a -> b) -> a -> b
$ Doc -> Name
forall a. Show a => a -> Name
show (Doc -> Name) -> Doc -> Name
forall a b. (a -> b) -> a -> b
$ ChunkDB -> Stage -> SingleLine -> Sentence -> Doc
sentenceDoc (CodeSpec
spec CodeSpec -> Getting ChunkDB CodeSpec ChunkDB -> ChunkDB
forall s a. s -> Getting a s a -> a
^. Getting ChunkDB CodeSpec ChunkDB
forall c. HasOldCodeSpec c => Lens' c ChunkDB
Lens' CodeSpec ChunkDB
sysinfodbO) Stage
Implementation SingleLine
OneLine (Sentence -> Doc) -> Sentence -> Doc
forall a b. (a -> b) -> a -> b
$ Sentence -> Sentence
capSent (Sentence -> Sentence) -> Sentence -> Sentence
forall a b. (a -> b) -> a -> b
$
[Sentence] -> Sentence
foldlSent ([Name -> Sentence
S Name
"a", Name -> Sentence
S (ImplementationType -> Name
implTypeStr (DrasilState -> ImplementationType
implType DrasilState
g)), Name -> Sentence
S Name
"to"] [Sentence] -> [Sentence] -> [Sentence]
forall a. [a] -> [a] -> [a]
++ DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting [Sentence] CodeSpec [Sentence] -> [Sentence]
forall s a. s -> Getting a s a -> a
^. Getting [Sentence] CodeSpec [Sentence]
forall c. HasSystemInformation c => Lens' c [Sentence]
Lens' CodeSpec [Sentence]
purpose)
inputParametersDesc :: GenState [Description]
inputParametersDesc :: GenState [Name]
inputParametersDesc = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
Name
ifDesc <- GenState Name
inputFormatDesc
Name
dvDesc <- GenState Name
derivedValuesDesc
Name
icDesc <- GenState Name
inputConstraintsDesc
let st :: Structure
st = DrasilState -> Structure
inStruct DrasilState
g
ipDesc :: [Name]
ipDesc = Structure -> [Name]
inDesc Structure
st [Name] -> [Name] -> [Name]
forall a. [a] -> [a] -> [a]
++ [Name
ifDesc, Name
dvDesc, Name
icDesc]
inDesc :: Structure -> [Name]
inDesc Structure
Bundled = [Name
"the structure for holding input values"]
inDesc Structure
Unbundled = [Name
""]
[Name] -> GenState [Name]
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return [Name]
ipDesc
inputConstructorDesc :: GenState Description
inputConstructorDesc :: GenState Name
inputConstructorDesc = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
Name
pAndS <- GenState Name
physAndSfwrCons
Name
giName <- InternalConcept -> GenState Name
genICName InternalConcept
GetInput
Name
dvName <- InternalConcept -> GenState Name
genICName InternalConcept
DerivedValuesFn
Name
icName <- InternalConcept -> GenState Name
genICName InternalConcept
InputConstraintsFn
let ifDesc :: Bool -> Name
ifDesc Bool
False = Name
""
ifDesc Bool
True = Name
"reading inputs"
idDesc :: Bool -> Name
idDesc Bool
False = Name
""
idDesc Bool
True = Name
"calculating derived values"
icDesc :: Bool -> Name
icDesc Bool
False = Name
""
icDesc Bool
True = Name
"checking " Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ Name
pAndS Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ Name
" on the input"
ds :: Set Name
ds = DrasilState -> Set Name
defSet DrasilState
g
Name -> GenState Name
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> GenState Name) -> Name -> GenState Name
forall a b. (a -> b) -> a -> b
$ Name
"Initializes input object by " Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ [Name] -> Name
stringList [
Bool -> Name
ifDesc (Name
giName Name -> Set Name -> Bool
forall a. Eq a => a -> Set a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Set Name
ds),
Bool -> Name
idDesc (Name
dvName Name -> Set Name -> Bool
forall a. Eq a => a -> Set a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Set Name
ds),
Bool -> Name
icDesc (Name
icName Name -> Set Name -> Bool
forall a. Eq a => a -> Set a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Set Name
ds)]
inputFormatDesc :: GenState Description
inputFormatDesc :: GenState Name
inputFormatDesc = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
Name
giName <- InternalConcept -> GenState Name
genICName InternalConcept
GetInput
let ifDesc :: Bool -> Name
ifDesc Bool
False = Name
""
ifDesc Bool
_ = Name
"the function for reading inputs"
Name -> GenState Name
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> GenState Name) -> Name -> GenState Name
forall a b. (a -> b) -> a -> b
$ Bool -> Name
ifDesc (Bool -> Name) -> Bool -> Name
forall a b. (a -> b) -> a -> b
$ Name
giName Name -> Set Name -> Bool
forall a. Eq a => a -> Set a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` DrasilState -> Set Name
defSet DrasilState
g
derivedValuesDesc :: GenState Description
derivedValuesDesc :: GenState Name
derivedValuesDesc = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
Name
dvName <- InternalConcept -> GenState Name
genICName InternalConcept
DerivedValuesFn
let dvDesc :: Bool -> Name
dvDesc Bool
False = Name
""
dvDesc Bool
_ = Name
"the function for calculating derived values"
Name -> GenState Name
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> GenState Name) -> Name -> GenState Name
forall a b. (a -> b) -> a -> b
$ Bool -> Name
dvDesc (Bool -> Name) -> Bool -> Name
forall a b. (a -> b) -> a -> b
$ Name
dvName Name -> Set Name -> Bool
forall a. Eq a => a -> Set a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` DrasilState -> Set Name
defSet DrasilState
g
inputConstraintsDesc :: GenState Description
inputConstraintsDesc :: GenState Name
inputConstraintsDesc = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
Name
icName <- InternalConcept -> GenState Name
genICName InternalConcept
InputConstraintsFn
Name
pAndS <- GenState Name
physAndSfwrCons
let icDesc :: Bool -> Name
icDesc Bool
False = Name
""
icDesc Bool
_ = Name
"the function for checking the " Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ Name
pAndS Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++
Name
" on the input"
Name -> GenState Name
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> GenState Name) -> Name -> GenState Name
forall a b. (a -> b) -> a -> b
$ Bool -> Name
icDesc (Bool -> Name) -> Bool -> Name
forall a b. (a -> b) -> a -> b
$ Name
icName Name -> Set Name -> Bool
forall a. Eq a => a -> Set a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` DrasilState -> Set Name
defSet DrasilState
g
constModDesc :: GenState Description
constModDesc :: GenState Name
constModDesc = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
Name
cname <- InternalConcept -> GenState Name
genICName InternalConcept
Constants
let cDesc :: [a] -> Name
cDesc [] = Name
""
cDesc [a]
_ = Name
"the structure for holding constant values"
Name -> GenState Name
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> GenState Name) -> Name -> GenState Name
forall a b. (a -> b) -> a -> b
$ [Const] -> Name
forall {a}. [a] -> Name
cDesc ([Const] -> Name) -> [Const] -> Name
forall a b. (a -> b) -> a -> b
$ (Const -> Bool) -> [Const] -> [Const]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Name -> Map Name Name -> Bool) -> Map Name Name -> Name -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip Name -> Map Name Name -> Bool
forall k a. Ord k => k -> Map k a -> Bool
member ((Name -> Bool) -> Map Name Name -> Map Name Name
forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter (Name
cname Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
==)
(DrasilState -> Map Name Name
clsMap DrasilState
g)) (Name -> Bool) -> (Const -> Name) -> Const -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Const -> Name
forall c. CodeIdea c => c -> Name
codeName) (DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting [Const] CodeSpec [Const] -> [Const]
forall s a. s -> Getting a s a -> a
^. Getting [Const] CodeSpec [Const]
forall c. HasOldCodeSpec c => Lens' c [Const]
Lens' CodeSpec [Const]
constantsO)
outputFormatDesc :: GenState Description
outputFormatDesc :: GenState Name
outputFormatDesc = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
Name
woName <- InternalConcept -> GenState Name
genICName InternalConcept
WriteOutput
let ofDesc :: Bool -> Name
ofDesc Bool
False = Name
""
ofDesc Bool
_ = Name
"the function for writing outputs"
Name -> GenState Name
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> GenState Name) -> Name -> GenState Name
forall a b. (a -> b) -> a -> b
$ Bool -> Name
ofDesc (Bool -> Name) -> Bool -> Name
forall a b. (a -> b) -> a -> b
$ Name
woName Name -> Set Name -> Bool
forall a. Eq a => a -> Set a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` DrasilState -> Set Name
defSet DrasilState
g
inputClassDesc :: GenState Description
inputClassDesc :: GenState Name
inputClassDesc = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
Name
cname <- InternalConcept -> GenState Name
genICName InternalConcept
InputParameters
let ipMap :: Map Name Name
ipMap = (Name -> Bool) -> Map Name Name -> Map Name Name
forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter (Name
cname Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
==) (DrasilState -> Map Name Name
clsMap DrasilState
g)
inIPMap :: [Input] -> [Input]
inIPMap = (Input -> Bool) -> [Input] -> [Input]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Name -> Map Name Name -> Bool
forall k a. Ord k => k -> Map k a -> Bool
`member` Map Name Name
ipMap) (Name -> Bool) -> (Input -> Name) -> Input -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Input -> Name
forall c. CodeIdea c => c -> Name
codeName)
inClassD :: Bool -> Name
inClassD Bool
True = Name
""
inClassD Bool
_ = Name
"Structure for holding the " Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ [Name] -> Name
stringList [
[Input] -> Name
forall {a}. [a] -> Name
inPs ([Input] -> Name) -> [Input] -> Name
forall a b. (a -> b) -> a -> b
$ [Input] -> [Input]
inIPMap ([Input] -> [Input]) -> [Input] -> [Input]
forall a b. (a -> b) -> a -> b
$ DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting [Input] CodeSpec [Input] -> [Input]
forall s a. s -> Getting a s a -> a
^. Getting [Input] CodeSpec [Input]
forall c. HasOldCodeSpec c => Lens' c [Input]
Lens' CodeSpec [Input]
extInputsO,
[Input] -> Name
forall {a}. [a] -> Name
dVs ([Input] -> Name) -> [Input] -> Name
forall a b. (a -> b) -> a -> b
$ [Input] -> [Input]
inIPMap ([Input] -> [Input]) -> [Input] -> [Input]
forall a b. (a -> b) -> a -> b
$ (Const -> Input) -> [Const] -> [Input]
forall a b. (a -> b) -> [a] -> [b]
map Const -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar ([Const] -> [Input]) -> [Const] -> [Input]
forall a b. (a -> b) -> a -> b
$ DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting [Const] CodeSpec [Const] -> [Const]
forall s a. s -> Getting a s a -> a
^. Getting [Const] CodeSpec [Const]
forall c. HasOldCodeSpec c => Lens' c [Const]
Lens' CodeSpec [Const]
derivedInputsO,
[Input] -> Name
forall {a}. [a] -> Name
cVs ([Input] -> Name) -> [Input] -> Name
forall a b. (a -> b) -> a -> b
$ [Input] -> [Input]
inIPMap ([Input] -> [Input]) -> [Input] -> [Input]
forall a b. (a -> b) -> a -> b
$ (Const -> Input) -> [Const] -> [Input]
forall a b. (a -> b) -> [a] -> [b]
map Const -> Input
forall c. (Quantity c, MayHaveUnit c) => c -> Input
quantvar ([Const] -> [Input]) -> [Const] -> [Input]
forall a b. (a -> b) -> a -> b
$ DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting [Const] CodeSpec [Const] -> [Const]
forall s a. s -> Getting a s a -> a
^. Getting [Const] CodeSpec [Const]
forall c. HasOldCodeSpec c => Lens' c [Const]
Lens' CodeSpec [Const]
constantsO]
inPs :: [a] -> Name
inPs [] = Name
""
inPs [a]
_ = Name
"input values"
dVs :: [a] -> Name
dVs [] = Name
""
dVs [a]
_ = Name
"derived values"
cVs :: [a] -> Name
cVs [] = Name
""
cVs [a]
_ = Name
"constant values"
Name -> GenState Name
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> GenState Name) -> Name -> GenState Name
forall a b. (a -> b) -> a -> b
$ Bool -> Name
inClassD (Bool -> Name) -> Bool -> Name
forall a b. (a -> b) -> a -> b
$ Map Name Name -> Bool
forall k a. Map k a -> Bool
Map.null Map Name Name
ipMap
constClassDesc :: GenState Description
constClassDesc :: GenState Name
constClassDesc = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
Name
cname <- InternalConcept -> GenState Name
genICName InternalConcept
Constants
let ccDesc :: [a] -> Name
ccDesc [] = Name
""
ccDesc [a]
_ = Name
"Structure for holding the constant values"
Name -> GenState Name
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> GenState Name) -> Name -> GenState Name
forall a b. (a -> b) -> a -> b
$ [Const] -> Name
forall {a}. [a] -> Name
ccDesc ([Const] -> Name) -> [Const] -> Name
forall a b. (a -> b) -> a -> b
$ (Const -> Bool) -> [Const] -> [Const]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Name -> Map Name Name -> Bool) -> Map Name Name -> Name -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip Name -> Map Name Name -> Bool
forall k a. Ord k => k -> Map k a -> Bool
member ((Name -> Bool) -> Map Name Name -> Map Name Name
forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter (Name
cname Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
==)
(DrasilState -> Map Name Name
clsMap DrasilState
g)) (Name -> Bool) -> (Const -> Name) -> Const -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Const -> Name
forall c. CodeIdea c => c -> Name
codeName) (DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting [Const] CodeSpec [Const] -> [Const]
forall s a. s -> Getting a s a -> a
^. Getting [Const] CodeSpec [Const]
forall c. HasOldCodeSpec c => Lens' c [Const]
Lens' CodeSpec [Const]
constantsO)
inFmtFuncDesc :: GenState Description
inFmtFuncDesc :: GenState Name
inFmtFuncDesc = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
Name
giName <- InternalConcept -> GenState Name
genICName InternalConcept
GetInput
let ifDesc :: Bool -> Name
ifDesc Bool
False = Name
""
ifDesc Bool
_ = Name
"Reads input from a file with the given file name"
Name -> GenState Name
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> GenState Name) -> Name -> GenState Name
forall a b. (a -> b) -> a -> b
$ Bool -> Name
ifDesc (Bool -> Name) -> Bool -> Name
forall a b. (a -> b) -> a -> b
$ Name
giName Name -> Set Name -> Bool
forall a. Eq a => a -> Set a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` DrasilState -> Set Name
defSet DrasilState
g
inConsFuncDesc :: GenState Description
inConsFuncDesc :: GenState Name
inConsFuncDesc = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
Name
icName <- InternalConcept -> GenState Name
genICName InternalConcept
InputConstraintsFn
Name
pAndS <- GenState Name
physAndSfwrCons
let icDesc :: Bool -> Name
icDesc Bool
False = Name
""
icDesc Bool
_ = Name
"Verifies that input values satisfy the " Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ Name
pAndS
Name -> GenState Name
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> GenState Name) -> Name -> GenState Name
forall a b. (a -> b) -> a -> b
$ Bool -> Name
icDesc (Bool -> Name) -> Bool -> Name
forall a b. (a -> b) -> a -> b
$ Name
icName Name -> Set Name -> Bool
forall a. Eq a => a -> Set a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` DrasilState -> Set Name
defSet DrasilState
g
dvFuncDesc :: GenState Description
dvFuncDesc :: GenState Name
dvFuncDesc = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
Name
dvName <- InternalConcept -> GenState Name
genICName InternalConcept
DerivedValuesFn
let dvDesc :: Bool -> Name
dvDesc Bool
False = Name
""
dvDesc Bool
_ = Name
"Calculates values that can be immediately derived from the"
Name -> Name -> Name
forall a. [a] -> [a] -> [a]
++ Name
" inputs"
Name -> GenState Name
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> GenState Name) -> Name -> GenState Name
forall a b. (a -> b) -> a -> b
$ Bool -> Name
dvDesc (Bool -> Name) -> Bool -> Name
forall a b. (a -> b) -> a -> b
$ Name
dvName Name -> Set Name -> Bool
forall a. Eq a => a -> Set a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` DrasilState -> Set Name
defSet DrasilState
g
calcModDesc :: Description
calcModDesc :: Name
calcModDesc = Name
"Provides functions for calculating the outputs"
woFuncDesc :: GenState Description
woFuncDesc :: GenState Name
woFuncDesc = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
Name
woName <- InternalConcept -> GenState Name
genICName InternalConcept
WriteOutput
let woDesc :: Bool -> Name
woDesc Bool
False = Name
""
woDesc Bool
_ = Name
"Writes the output values to output.txt"
Name -> GenState Name
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> GenState Name) -> Name -> GenState Name
forall a b. (a -> b) -> a -> b
$ Bool -> Name
woDesc (Bool -> Name) -> Bool -> Name
forall a b. (a -> b) -> a -> b
$ Name
woName Name -> Set Name -> Bool
forall a. Eq a => a -> Set a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` DrasilState -> Set Name
defSet DrasilState
g
physAndSfwrCons :: GenState Description
physAndSfwrCons :: GenState Name
physAndSfwrCons = do
DrasilState
g <- StateT DrasilState Identity DrasilState
forall s (m :: * -> *). MonadState s m => m s
get
let cns :: [ConstraintCE]
cns = [[ConstraintCE]] -> [ConstraintCE]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[ConstraintCE]] -> [ConstraintCE])
-> [[ConstraintCE]] -> [ConstraintCE]
forall a b. (a -> b) -> a -> b
$ (Input -> Maybe [ConstraintCE]) -> [Input] -> [[ConstraintCE]]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe ((UID -> Map UID [ConstraintCE] -> Maybe [ConstraintCE]
forall k a. Ord k => k -> Map k a -> Maybe a
`Map.lookup` (DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec
-> Getting
(Map UID [ConstraintCE]) CodeSpec (Map UID [ConstraintCE])
-> Map UID [ConstraintCE]
forall s a. s -> Getting a s a -> a
^. Getting (Map UID [ConstraintCE]) CodeSpec (Map UID [ConstraintCE])
forall c. HasOldCodeSpec c => Lens' c (Map UID [ConstraintCE])
Lens' CodeSpec (Map UID [ConstraintCE])
cMapO)) (UID -> Maybe [ConstraintCE])
-> (Input -> UID) -> Input -> Maybe [ConstraintCE]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Input -> Getting UID Input UID -> UID
forall s a. s -> Getting a s a -> a
^. Getting UID Input UID
forall c. HasUID c => Getter c UID
Getter Input UID
uid))
(DrasilState -> CodeSpec
codeSpec DrasilState
g CodeSpec -> Getting [Input] CodeSpec [Input] -> [Input]
forall s a. s -> Getting a s a -> a
^. Getting [Input] CodeSpec [Input]
forall c. HasOldCodeSpec c => Lens' c [Input]
Lens' CodeSpec [Input]
inputsO)
Name -> GenState Name
forall a. a -> StateT DrasilState Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> GenState Name) -> Name -> GenState Name
forall a b. (a -> b) -> a -> b
$ [Name] -> Name
stringList [
if Bool -> Bool
not ((ConstraintCE -> Bool) -> [ConstraintCE] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ConstraintCE -> Bool
forall e. Constraint e -> Bool
isPhysC [ConstraintCE]
cns) then Name
"" else Name
"physical constraints",
if Bool -> Bool
not ((ConstraintCE -> Bool) -> [ConstraintCE] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ConstraintCE -> Bool
forall e. Constraint e -> Bool
isSfwrC [ConstraintCE]
cns) then Name
"" else Name
"software constraints"]