module Language.Drasil.Choices (
Choices(..), Architecture (..), makeArchit, DataInfo(..), makeData, Maps(..),
makeMaps, spaceToCodeType, Constraints(..), makeConstraints, ODE(..), makeODE,
DocConfig(..), makeDocConfig, LogConfig(..), makeLogConfig, OptionalFeatures(..),
makeOptFeats, ExtLib(..), Modularity(..), InputModule(..), inputModule, Structure(..),
ConstantStructure(..), ConstantRepr(..), ConceptMatchMap, MatchedConceptMap,
CodeConcept(..), matchConcepts, SpaceMatch, matchSpaces, ImplementationType(..),
ConstraintBehaviour(..), Comments(..), Verbosity(..), Visibility(..),
Logging(..), AuxFile(..), getSampleData, hasSampleInput, defaultChoices,
choicesSent, showChs) where
import Language.Drasil hiding (None, Var)
import Language.Drasil.Code.Code (spaceToCodeType)
import Language.Drasil.Code.Lang (Lang(..))
import Language.Drasil.Data.ODEInfo (ODEInfo)
import Language.Drasil.Data.ODELibPckg (ODELibPckg)
import GOOL.Drasil (CodeType)
import Control.Lens ((^.))
import Data.Map (Map, fromList)
data Choices = Choices {
Choices -> [Lang]
lang :: [Lang],
Choices -> Architecture
architecture :: Architecture,
Choices -> DataInfo
dataInfo :: DataInfo,
Choices -> Maps
maps :: Maps,
Choices -> OptionalFeatures
optFeats :: OptionalFeatures,
Choices -> Constraints
srsConstraints :: Constraints,
Choices -> [ExtLib]
extLibs :: [ExtLib],
Choices -> Int
folderVal :: Int
}
class RenderChoices a where
showChs :: a -> Sentence
showChsList :: [a] -> Sentence
showChsList [] = String -> Sentence
S String
"None"
showChsList [a]
lst = [Sentence] -> Sentence
foldlSent_ (forall a b. (a -> b) -> [a] -> [b]
map forall a. RenderChoices a => a -> Sentence
showChs [a]
lst)
data Architecture = Archt {
Architecture -> Modularity
modularity :: Modularity,
Architecture -> ImplementationType
impType :: ImplementationType
}
makeArchit :: Modularity -> ImplementationType -> Architecture
makeArchit :: Modularity -> ImplementationType -> Architecture
makeArchit = Modularity -> ImplementationType -> Architecture
Archt
data Modularity = Modular InputModule
| Unmodular
instance RenderChoices Modularity where
showChs :: Modularity -> Sentence
showChs Modularity
Unmodular = String -> Sentence
S String
"Unmodular"
showChs (Modular InputModule
Combined) = String -> Sentence
S String
"Modular Combined"
showChs (Modular InputModule
Separated)= String -> Sentence
S String
"Modular Separated"
data InputModule = Combined
| Separated
inputModule :: Choices -> InputModule
inputModule :: Choices -> InputModule
inputModule Choices
c = Modularity -> InputModule
inputModule' forall a b. (a -> b) -> a -> b
$ Architecture -> Modularity
modularity forall a b. (a -> b) -> a -> b
$ Choices -> Architecture
architecture Choices
c
where inputModule' :: Modularity -> InputModule
inputModule' Modularity
Unmodular = InputModule
Combined
inputModule' (Modular InputModule
im) = InputModule
im
data ImplementationType = Library
| Program
instance RenderChoices ImplementationType where
showChs :: ImplementationType -> Sentence
showChs ImplementationType
Library = String -> Sentence
S String
"Library"
showChs ImplementationType
Program = String -> Sentence
S String
"Program"
data DataInfo = DataInfo {
DataInfo -> Structure
inputStructure :: Structure,
DataInfo -> ConstantStructure
constStructure :: ConstantStructure,
DataInfo -> ConstantRepr
constRepr :: ConstantRepr
}
makeData :: Structure -> ConstantStructure -> ConstantRepr -> DataInfo
makeData :: Structure -> ConstantStructure -> ConstantRepr -> DataInfo
makeData = Structure -> ConstantStructure -> ConstantRepr -> DataInfo
DataInfo
data Structure = Unbundled
| Bundled
instance RenderChoices Structure where
showChs :: Structure -> Sentence
showChs Structure
Unbundled = String -> Sentence
S String
"Unbundled"
showChs Structure
Bundled = String -> Sentence
S String
"Bundled"
data ConstantStructure = Inline
| WithInputs
| Store Structure
instance RenderChoices ConstantStructure where
showChs :: ConstantStructure -> Sentence
showChs ConstantStructure
Inline = String -> Sentence
S String
"Inline"
showChs ConstantStructure
WithInputs = String -> Sentence
S String
"WithInputs"
showChs (Store Structure
Unbundled) = String -> Sentence
S String
"Store Unbundled"
showChs (Store Structure
Bundled) = String -> Sentence
S String
"Store Bundled"
data ConstantRepr = Var
| Const
instance RenderChoices ConstantRepr where
showChs :: ConstantRepr -> Sentence
showChs ConstantRepr
Var = String -> Sentence
S String
"Var"
showChs ConstantRepr
Const = String -> Sentence
S String
"Const"
data Maps = Maps {
Maps -> ConceptMatchMap
conceptMatch :: ConceptMatchMap,
Maps -> SpaceMatch
spaceMatch :: SpaceMatch
}
makeMaps :: ConceptMatchMap -> SpaceMatch -> Maps
makeMaps :: ConceptMatchMap -> SpaceMatch -> Maps
makeMaps = ConceptMatchMap -> SpaceMatch -> Maps
Maps
type ConceptMatchMap = Map UID [CodeConcept]
type MatchedConceptMap = Map UID CodeConcept
data CodeConcept = Pi deriving CodeConcept -> CodeConcept -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CodeConcept -> CodeConcept -> Bool
$c/= :: CodeConcept -> CodeConcept -> Bool
== :: CodeConcept -> CodeConcept -> Bool
$c== :: CodeConcept -> CodeConcept -> Bool
Eq
instance RenderChoices CodeConcept where
showChs :: CodeConcept -> Sentence
showChs CodeConcept
Pi = String -> Sentence
S String
"Pi"
matchConcepts :: (HasUID c) => [(c, [CodeConcept])] -> ConceptMatchMap
matchConcepts :: forall c. HasUID c => [(c, [CodeConcept])] -> ConceptMatchMap
matchConcepts = forall k a. Ord k => [(k, a)] -> Map k a
fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (\(c
cnc,[CodeConcept]
cdc) -> (c
cnc forall s a. s -> Getting a s a -> a
^. forall c. HasUID c => Lens' c UID
uid, [CodeConcept]
cdc))
type SpaceMatch = Space -> [CodeType]
matchSpace :: Space -> [CodeType] -> SpaceMatch -> SpaceMatch
matchSpace :: Space -> [CodeType] -> SpaceMatch -> SpaceMatch
matchSpace Space
_ [] SpaceMatch
_ = forall a. HasCallStack => String -> a
error String
"Must match each Space to at least one CodeType"
matchSpace Space
s [CodeType]
ts SpaceMatch
sm = \Space
sp -> if Space
sp forall a. Eq a => a -> a -> Bool
== Space
s then [CodeType]
ts else SpaceMatch
sm Space
sp
matchSpaces :: [(Space, [CodeType])] -> SpaceMatch
matchSpaces :: [(Space, [CodeType])] -> SpaceMatch
matchSpaces [(Space, [CodeType])]
spMtchs = [(Space, [CodeType])] -> SpaceMatch -> SpaceMatch
matchSpaces' [(Space, [CodeType])]
spMtchs SpaceMatch
spaceToCodeType
where matchSpaces' :: [(Space, [CodeType])] -> SpaceMatch -> SpaceMatch
matchSpaces' ((Space
s,[CodeType]
ct):[(Space, [CodeType])]
sms) SpaceMatch
sm = [(Space, [CodeType])] -> SpaceMatch -> SpaceMatch
matchSpaces' [(Space, [CodeType])]
sms forall a b. (a -> b) -> a -> b
$ Space -> [CodeType] -> SpaceMatch -> SpaceMatch
matchSpace Space
s [CodeType]
ct SpaceMatch
sm
matchSpaces' [] SpaceMatch
sm = SpaceMatch
sm
data OptionalFeatures = OptFeats{
OptionalFeatures -> DocConfig
docConfig :: DocConfig,
OptionalFeatures -> LogConfig
logConfig :: LogConfig,
OptionalFeatures -> [AuxFile]
auxFiles :: [AuxFile]
}
makeOptFeats :: DocConfig -> LogConfig -> [AuxFile] -> OptionalFeatures
makeOptFeats :: DocConfig -> LogConfig -> [AuxFile] -> OptionalFeatures
makeOptFeats = DocConfig -> LogConfig -> [AuxFile] -> OptionalFeatures
OptFeats
data DocConfig = DocConfig {
:: [Comments],
DocConfig -> Verbosity
doxVerbosity :: Verbosity,
DocConfig -> Visibility
dates :: Visibility
}
makeDocConfig :: [Comments] -> Verbosity -> Visibility -> DocConfig
makeDocConfig :: [Comments] -> Verbosity -> Visibility -> DocConfig
makeDocConfig = [Comments] -> Verbosity -> Visibility -> DocConfig
DocConfig
data =
|
|
deriving Comments -> Comments -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Comments -> Comments -> Bool
$c/= :: Comments -> Comments -> Bool
== :: Comments -> Comments -> Bool
$c== :: Comments -> Comments -> Bool
Eq
instance RenderChoices Comments where
showChs :: Comments -> Sentence
showChs Comments
CommentFunc = String -> Sentence
S String
"CommentFunc"
showChs Comments
CommentClass = String -> Sentence
S String
"CommentClass"
showChs Comments
CommentMod = String -> Sentence
S String
"CommentMod"
data Verbosity = Verbose | Quiet
instance RenderChoices Verbosity where
showChs :: Verbosity -> Sentence
showChs Verbosity
Verbose = String -> Sentence
S String
"Verbose"
showChs Verbosity
Quiet = String -> Sentence
S String
"Quiet"
data Visibility = Show
| Hide
instance RenderChoices Visibility where
showChs :: Visibility -> Sentence
showChs Visibility
Show = String -> Sentence
S String
"Show"
showChs Visibility
Hide = String -> Sentence
S String
"Hide"
data LogConfig = LogConfig {
LogConfig -> [Logging]
logging :: [Logging],
LogConfig -> String
logFile :: FilePath
}
makeLogConfig :: [Logging] -> FilePath -> LogConfig
makeLogConfig :: [Logging] -> String -> LogConfig
makeLogConfig = [Logging] -> String -> LogConfig
LogConfig
data Logging = LogFunc
| LogVar
deriving Logging -> Logging -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Logging -> Logging -> Bool
$c/= :: Logging -> Logging -> Bool
== :: Logging -> Logging -> Bool
$c== :: Logging -> Logging -> Bool
Eq
instance RenderChoices Logging where
showChs :: Logging -> Sentence
showChs Logging
LogFunc = String -> Sentence
S String
"LogFunc"
showChs Logging
LogVar = String -> Sentence
S String
"LogVar"
data AuxFile = SampleInput FilePath
| ReadME
deriving AuxFile -> AuxFile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AuxFile -> AuxFile -> Bool
$c/= :: AuxFile -> AuxFile -> Bool
== :: AuxFile -> AuxFile -> Bool
$c== :: AuxFile -> AuxFile -> Bool
Eq
instance RenderChoices AuxFile where
showChs :: AuxFile -> Sentence
showChs (SampleInput String
fp) = String -> Sentence
S String
"SampleInput" Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
fp
showChs AuxFile
ReadME = String -> Sentence
S String
"ReadME"
getSampleData :: Choices -> Maybe FilePath
getSampleData :: Choices -> Maybe String
getSampleData Choices
chs = [AuxFile] -> Maybe String
getSampleData' (OptionalFeatures -> [AuxFile]
auxFiles forall a b. (a -> b) -> a -> b
$ Choices -> OptionalFeatures
optFeats Choices
chs)
where getSampleData' :: [AuxFile] -> Maybe String
getSampleData' [] = forall a. Maybe a
Nothing
getSampleData' (SampleInput String
fp:[AuxFile]
_) = forall a. a -> Maybe a
Just String
fp
getSampleData' (AuxFile
_:[AuxFile]
xs) = [AuxFile] -> Maybe String
getSampleData' [AuxFile]
xs
hasSampleInput :: [AuxFile] -> Bool
hasSampleInput :: [AuxFile] -> Bool
hasSampleInput [] = Bool
False
hasSampleInput (SampleInput String
_:[AuxFile]
_) = Bool
True
hasSampleInput (AuxFile
_:[AuxFile]
xs) = [AuxFile] -> Bool
hasSampleInput [AuxFile]
xs
data Constraints = Constraints{
Constraints -> ConstraintBehaviour
onSfwrConstraint :: ConstraintBehaviour,
Constraints -> ConstraintBehaviour
onPhysConstraint :: ConstraintBehaviour
}
makeConstraints :: ConstraintBehaviour -> ConstraintBehaviour -> Constraints
makeConstraints :: ConstraintBehaviour -> ConstraintBehaviour -> Constraints
makeConstraints = ConstraintBehaviour -> ConstraintBehaviour -> Constraints
Constraints
data ConstraintBehaviour = Warning
| Exception
instance RenderChoices ConstraintBehaviour where
showChs :: ConstraintBehaviour -> Sentence
showChs ConstraintBehaviour
Warning = String -> Sentence
S String
"Warning"
showChs ConstraintBehaviour
Exception = String -> Sentence
S String
"Exception"
newtype ExtLib = Math ODE
data ODE = ODE{
ODE -> [ODEInfo]
odeInfo :: [ODEInfo],
ODE -> [ODELibPckg]
odeLib :: [ODELibPckg]
}
makeODE :: [ODEInfo] -> [ODELibPckg] -> ODE
makeODE :: [ODEInfo] -> [ODELibPckg] -> ODE
makeODE = [ODEInfo] -> [ODELibPckg] -> ODE
ODE
defaultChoices :: Choices
defaultChoices :: Choices
defaultChoices = Choices {
lang :: [Lang]
lang = [Lang
Python],
architecture :: Architecture
architecture = Modularity -> ImplementationType -> Architecture
makeArchit (InputModule -> Modularity
Modular InputModule
Combined) ImplementationType
Program,
dataInfo :: DataInfo
dataInfo = Structure -> ConstantStructure -> ConstantRepr -> DataInfo
makeData Structure
Bundled ConstantStructure
Inline ConstantRepr
Const,
maps :: Maps
maps = ConceptMatchMap -> SpaceMatch -> Maps
makeMaps
(forall c. HasUID c => [(c, [CodeConcept])] -> ConceptMatchMap
matchConcepts ([] :: [(SimpleQDef, [CodeConcept])]))
SpaceMatch
spaceToCodeType,
optFeats :: OptionalFeatures
optFeats = DocConfig -> LogConfig -> [AuxFile] -> OptionalFeatures
makeOptFeats
([Comments] -> Verbosity -> Visibility -> DocConfig
makeDocConfig [] Verbosity
Verbose Visibility
Hide)
([Logging] -> String -> LogConfig
makeLogConfig [] String
"log.txt")
[AuxFile
ReadME],
srsConstraints :: Constraints
srsConstraints = ConstraintBehaviour -> ConstraintBehaviour -> Constraints
makeConstraints ConstraintBehaviour
Exception ConstraintBehaviour
Warning,
extLibs :: [ExtLib]
extLibs = [],
folderVal :: Int
folderVal = Int
4
}
choicesSent :: Choices -> [Sentence]
choicesSent :: Choices -> [Sentence]
choicesSent Choices
chs = forall a b. (a -> b) -> [a] -> [b]
map (Sentence, Sentence) -> Sentence
chsFieldSent [
(String -> Sentence
S String
"Languages", [Sentence] -> Sentence
foldlSent_ forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (String -> Sentence
S forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show) forall a b. (a -> b) -> a -> b
$ Choices -> [Lang]
lang Choices
chs),
(String -> Sentence
S String
"Modularity", forall a. RenderChoices a => a -> Sentence
showChs forall a b. (a -> b) -> a -> b
$ Architecture -> Modularity
modularity forall a b. (a -> b) -> a -> b
$ Choices -> Architecture
architecture Choices
chs),
(String -> Sentence
S String
"Input Structure", forall a. RenderChoices a => a -> Sentence
showChs forall a b. (a -> b) -> a -> b
$ DataInfo -> Structure
inputStructure forall a b. (a -> b) -> a -> b
$ Choices -> DataInfo
dataInfo Choices
chs),
(String -> Sentence
S String
"Constant Structure", forall a. RenderChoices a => a -> Sentence
showChs forall a b. (a -> b) -> a -> b
$ DataInfo -> ConstantStructure
constStructure forall a b. (a -> b) -> a -> b
$ Choices -> DataInfo
dataInfo Choices
chs),
(String -> Sentence
S String
"Constant Representation", forall a. RenderChoices a => a -> Sentence
showChs forall a b. (a -> b) -> a -> b
$ DataInfo -> ConstantRepr
constRepr forall a b. (a -> b) -> a -> b
$ Choices -> DataInfo
dataInfo Choices
chs),
(String -> Sentence
S String
"Implementation Type", forall a. RenderChoices a => a -> Sentence
showChs forall a b. (a -> b) -> a -> b
$ Architecture -> ImplementationType
impType forall a b. (a -> b) -> a -> b
$ Choices -> Architecture
architecture Choices
chs),
(String -> Sentence
S String
"Software Constraint Behaviour", forall a. RenderChoices a => a -> Sentence
showChs forall a b. (a -> b) -> a -> b
$ Constraints -> ConstraintBehaviour
onSfwrConstraint forall a b. (a -> b) -> a -> b
$ Choices -> Constraints
srsConstraints Choices
chs),
(String -> Sentence
S String
"Physical Constraint Behaviour", forall a. RenderChoices a => a -> Sentence
showChs forall a b. (a -> b) -> a -> b
$ Constraints -> ConstraintBehaviour
onPhysConstraint forall a b. (a -> b) -> a -> b
$ Choices -> Constraints
srsConstraints Choices
chs),
(String -> Sentence
S String
"Comments", forall a. RenderChoices a => [a] -> Sentence
showChsList forall a b. (a -> b) -> a -> b
$ DocConfig -> [Comments]
comments forall a b. (a -> b) -> a -> b
$ OptionalFeatures -> DocConfig
docConfig forall a b. (a -> b) -> a -> b
$ Choices -> OptionalFeatures
optFeats Choices
chs),
(String -> Sentence
S String
"Dox Verbosity", forall a. RenderChoices a => a -> Sentence
showChs forall a b. (a -> b) -> a -> b
$ DocConfig -> Verbosity
doxVerbosity forall a b. (a -> b) -> a -> b
$ OptionalFeatures -> DocConfig
docConfig forall a b. (a -> b) -> a -> b
$ Choices -> OptionalFeatures
optFeats Choices
chs),
(String -> Sentence
S String
"Dates", forall a. RenderChoices a => a -> Sentence
showChs forall a b. (a -> b) -> a -> b
$ DocConfig -> Visibility
dates forall a b. (a -> b) -> a -> b
$ OptionalFeatures -> DocConfig
docConfig forall a b. (a -> b) -> a -> b
$ Choices -> OptionalFeatures
optFeats Choices
chs),
(String -> Sentence
S String
"Log File Name", String -> Sentence
S forall a b. (a -> b) -> a -> b
$ LogConfig -> String
logFile forall a b. (a -> b) -> a -> b
$ OptionalFeatures -> LogConfig
logConfig forall a b. (a -> b) -> a -> b
$ Choices -> OptionalFeatures
optFeats Choices
chs),
(String -> Sentence
S String
"Logging", forall a. RenderChoices a => [a] -> Sentence
showChsList forall a b. (a -> b) -> a -> b
$ LogConfig -> [Logging]
logging forall a b. (a -> b) -> a -> b
$ OptionalFeatures -> LogConfig
logConfig forall a b. (a -> b) -> a -> b
$ Choices -> OptionalFeatures
optFeats Choices
chs),
(String -> Sentence
S String
"Auxiliary Files", forall a. RenderChoices a => [a] -> Sentence
showChsList forall a b. (a -> b) -> a -> b
$ OptionalFeatures -> [AuxFile]
auxFiles forall a b. (a -> b) -> a -> b
$ Choices -> OptionalFeatures
optFeats Choices
chs)
]
chsFieldSent :: (Sentence, Sentence) -> Sentence
chsFieldSent :: (Sentence, Sentence) -> Sentence
chsFieldSent (Sentence
rec, Sentence
chc) = Sentence
rec Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
"selected as" Sentence -> Sentence -> Sentence
+:+. Sentence
chc