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)
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]
}
class RenderChoices a where
showChs :: a -> Sentence
showChsList :: [a] -> Sentence
showChsList lst :: [a]
lst = [Sentence] -> Sentence
foldlSent_ ((a -> Sentence) -> [a] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map a -> Sentence
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 Unmodular = String -> Sentence
S "Unmodular"
showChs (Modular Combined) = String -> Sentence
S "Modular Combined"
showChs (Modular Separated)= String -> Sentence
S "Modular Separated"
data InputModule = Combined
| Separated
inputModule :: Choices -> InputModule
inputModule :: Choices -> InputModule
inputModule c :: Choices
c = Modularity -> InputModule
inputModule' (Modularity -> InputModule) -> Modularity -> InputModule
forall a b. (a -> b) -> a -> b
$ Architecture -> Modularity
modularity (Architecture -> Modularity) -> Architecture -> Modularity
forall a b. (a -> b) -> a -> b
$ Choices -> Architecture
architecture Choices
c
where inputModule' :: Modularity -> InputModule
inputModule' Unmodular = InputModule
Combined
inputModule' (Modular im :: InputModule
im) = InputModule
im
data ImplementationType = Library
| Program
instance RenderChoices ImplementationType where
showChs :: ImplementationType -> Sentence
showChs Library = String -> Sentence
S "Library"
showChs Program = String -> Sentence
S "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 Unbundled = String -> Sentence
S "Unbundled"
showChs Bundled = String -> Sentence
S "Bundled"
data ConstantStructure = Inline
| WithInputs
| Store Structure
instance RenderChoices ConstantStructure where
showChs :: ConstantStructure -> Sentence
showChs Inline = String -> Sentence
S "Inline"
showChs WithInputs = String -> Sentence
S "WithInputs"
showChs (Store Unbundled) = String -> Sentence
S "Store Unbundled"
showChs (Store Bundled) = String -> Sentence
S "Store Bundled"
data ConstantRepr = Var
| Const
instance RenderChoices ConstantRepr where
showChs :: ConstantRepr -> Sentence
showChs Var = String -> Sentence
S "Var"
showChs Const = String -> Sentence
S "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
(CodeConcept -> CodeConcept -> Bool)
-> (CodeConcept -> CodeConcept -> Bool) -> Eq CodeConcept
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 Pi = String -> Sentence
S "Pi"
matchConcepts :: (HasUID c) => [(c, [CodeConcept])] -> ConceptMatchMap
matchConcepts :: [(c, [CodeConcept])] -> ConceptMatchMap
matchConcepts = [(UID, [CodeConcept])] -> ConceptMatchMap
forall k a. Ord k => [(k, a)] -> Map k a
fromList ([(UID, [CodeConcept])] -> ConceptMatchMap)
-> ([(c, [CodeConcept])] -> [(UID, [CodeConcept])])
-> [(c, [CodeConcept])]
-> ConceptMatchMap
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((c, [CodeConcept]) -> (UID, [CodeConcept]))
-> [(c, [CodeConcept])] -> [(UID, [CodeConcept])]
forall a b. (a -> b) -> [a] -> [b]
map (\(cnc :: c
cnc,cdc :: [CodeConcept]
cdc) -> (c
cnc c -> Getting UID c UID -> UID
forall s a. s -> Getting a s a -> a
^. Getting UID c UID
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 _ [] _ = String -> SpaceMatch
forall a. HasCallStack => String -> a
error "Must match each Space to at least one CodeType"
matchSpace s :: Space
s ts :: [CodeType]
ts sm :: SpaceMatch
sm = \sp :: Space
sp -> if Space
sp Space -> Space -> Bool
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 spMtchs :: [(Space, [CodeType])]
spMtchs = [(Space, [CodeType])] -> SpaceMatch -> SpaceMatch
matchSpaces' [(Space, [CodeType])]
spMtchs SpaceMatch
spaceToCodeType
where matchSpaces' :: [(Space, [CodeType])] -> SpaceMatch -> SpaceMatch
matchSpaces' ((s :: Space
s,ct :: [CodeType]
ct):sms :: [(Space, [CodeType])]
sms) sm :: SpaceMatch
sm = [(Space, [CodeType])] -> SpaceMatch -> SpaceMatch
matchSpaces' [(Space, [CodeType])]
sms (SpaceMatch -> SpaceMatch) -> SpaceMatch -> SpaceMatch
forall a b. (a -> b) -> a -> b
$ Space -> [CodeType] -> SpaceMatch -> SpaceMatch
matchSpace Space
s [CodeType]
ct SpaceMatch
sm
matchSpaces' [] sm :: 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
(Comments -> Comments -> Bool)
-> (Comments -> Comments -> Bool) -> Eq Comments
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 CommentFunc = String -> Sentence
S "CommentFunc"
showChs CommentClass = String -> Sentence
S "CommentClass"
showChs CommentMod = String -> Sentence
S "CommentMod"
data Verbosity = Verbose | Quiet
instance RenderChoices Verbosity where
showChs :: Verbosity -> Sentence
showChs Verbose = String -> Sentence
S "Verbose"
showChs Quiet = String -> Sentence
S "Quiet"
data Visibility = Show
| Hide
instance RenderChoices Visibility where
showChs :: Visibility -> Sentence
showChs Show = String -> Sentence
S "Show"
showChs Hide = String -> Sentence
S "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
(Logging -> Logging -> Bool)
-> (Logging -> Logging -> Bool) -> Eq Logging
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 LogFunc = String -> Sentence
S "LogFunc"
showChs LogVar = String -> Sentence
S "LogVar"
data AuxFile = SampleInput FilePath
| ReadME
deriving AuxFile -> AuxFile -> Bool
(AuxFile -> AuxFile -> Bool)
-> (AuxFile -> AuxFile -> Bool) -> Eq AuxFile
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 fp :: String
fp) = String -> Sentence
S "SampleInput" Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S String
fp
showChs ReadME = String -> Sentence
S "ReadME"
getSampleData :: Choices -> Maybe FilePath
getSampleData :: Choices -> Maybe String
getSampleData chs :: Choices
chs = [AuxFile] -> Maybe String
getSampleData' (OptionalFeatures -> [AuxFile]
auxFiles (OptionalFeatures -> [AuxFile]) -> OptionalFeatures -> [AuxFile]
forall a b. (a -> b) -> a -> b
$ Choices -> OptionalFeatures
optFeats Choices
chs)
where getSampleData' :: [AuxFile] -> Maybe String
getSampleData' [] = Maybe String
forall a. Maybe a
Nothing
getSampleData' (SampleInput fp :: String
fp:_) = String -> Maybe String
forall a. a -> Maybe a
Just String
fp
getSampleData' (_:xs :: [AuxFile]
xs) = [AuxFile] -> Maybe String
getSampleData' [AuxFile]
xs
hasSampleInput :: [AuxFile] -> Bool
hasSampleInput :: [AuxFile] -> Bool
hasSampleInput [] = Bool
False
hasSampleInput (SampleInput _:_) = Bool
True
hasSampleInput (_:xs :: [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 Warning = String -> Sentence
S "Warning"
showChs Exception = String -> Sentence
S "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]
-> Architecture
-> DataInfo
-> Maps
-> OptionalFeatures
-> Constraints
-> [ExtLib]
-> Choices
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
([(SimpleQDef, [CodeConcept])] -> ConceptMatchMap
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 [] "log.txt")
[AuxFile
ReadME],
srsConstraints :: Constraints
srsConstraints = ConstraintBehaviour -> ConstraintBehaviour -> Constraints
makeConstraints ConstraintBehaviour
Exception ConstraintBehaviour
Warning,
extLibs :: [ExtLib]
extLibs = []
}
choicesSent :: Choices -> [Sentence]
choicesSent :: Choices -> [Sentence]
choicesSent chs :: Choices
chs = ((Sentence, Sentence) -> Sentence)
-> [(Sentence, Sentence)] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map (Sentence, Sentence) -> Sentence
chsFieldSent [
(String -> Sentence
S "Languages", [Sentence] -> Sentence
foldlSent_ ([Sentence] -> Sentence) -> [Sentence] -> Sentence
forall a b. (a -> b) -> a -> b
$ (Lang -> Sentence) -> [Lang] -> [Sentence]
forall a b. (a -> b) -> [a] -> [b]
map (String -> Sentence
S (String -> Sentence) -> (Lang -> String) -> Lang -> Sentence
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lang -> String
forall a. Show a => a -> String
show) ([Lang] -> [Sentence]) -> [Lang] -> [Sentence]
forall a b. (a -> b) -> a -> b
$ Choices -> [Lang]
lang Choices
chs),
(String -> Sentence
S "Modularity", Modularity -> Sentence
forall a. RenderChoices a => a -> Sentence
showChs (Modularity -> Sentence) -> Modularity -> Sentence
forall a b. (a -> b) -> a -> b
$ Architecture -> Modularity
modularity (Architecture -> Modularity) -> Architecture -> Modularity
forall a b. (a -> b) -> a -> b
$ Choices -> Architecture
architecture Choices
chs),
(String -> Sentence
S "Input Structure", Structure -> Sentence
forall a. RenderChoices a => a -> Sentence
showChs (Structure -> Sentence) -> Structure -> Sentence
forall a b. (a -> b) -> a -> b
$ DataInfo -> Structure
inputStructure (DataInfo -> Structure) -> DataInfo -> Structure
forall a b. (a -> b) -> a -> b
$ Choices -> DataInfo
dataInfo Choices
chs),
(String -> Sentence
S "Constant Structure", ConstantStructure -> Sentence
forall a. RenderChoices a => a -> Sentence
showChs (ConstantStructure -> Sentence) -> ConstantStructure -> Sentence
forall a b. (a -> b) -> a -> b
$ DataInfo -> ConstantStructure
constStructure (DataInfo -> ConstantStructure) -> DataInfo -> ConstantStructure
forall a b. (a -> b) -> a -> b
$ Choices -> DataInfo
dataInfo Choices
chs),
(String -> Sentence
S "Constant Representation", ConstantRepr -> Sentence
forall a. RenderChoices a => a -> Sentence
showChs (ConstantRepr -> Sentence) -> ConstantRepr -> Sentence
forall a b. (a -> b) -> a -> b
$ DataInfo -> ConstantRepr
constRepr (DataInfo -> ConstantRepr) -> DataInfo -> ConstantRepr
forall a b. (a -> b) -> a -> b
$ Choices -> DataInfo
dataInfo Choices
chs),
(String -> Sentence
S "Implementation Type", ImplementationType -> Sentence
forall a. RenderChoices a => a -> Sentence
showChs (ImplementationType -> Sentence) -> ImplementationType -> Sentence
forall a b. (a -> b) -> a -> b
$ Architecture -> ImplementationType
impType (Architecture -> ImplementationType)
-> Architecture -> ImplementationType
forall a b. (a -> b) -> a -> b
$ Choices -> Architecture
architecture Choices
chs),
(String -> Sentence
S "Software Constraint Behaviour", ConstraintBehaviour -> Sentence
forall a. RenderChoices a => a -> Sentence
showChs (ConstraintBehaviour -> Sentence)
-> ConstraintBehaviour -> Sentence
forall a b. (a -> b) -> a -> b
$ Constraints -> ConstraintBehaviour
onSfwrConstraint (Constraints -> ConstraintBehaviour)
-> Constraints -> ConstraintBehaviour
forall a b. (a -> b) -> a -> b
$ Choices -> Constraints
srsConstraints Choices
chs),
(String -> Sentence
S "Physical Constraint Behaviour", ConstraintBehaviour -> Sentence
forall a. RenderChoices a => a -> Sentence
showChs (ConstraintBehaviour -> Sentence)
-> ConstraintBehaviour -> Sentence
forall a b. (a -> b) -> a -> b
$ Constraints -> ConstraintBehaviour
onPhysConstraint (Constraints -> ConstraintBehaviour)
-> Constraints -> ConstraintBehaviour
forall a b. (a -> b) -> a -> b
$ Choices -> Constraints
srsConstraints Choices
chs),
(String -> Sentence
S "Comments", [Comments] -> Sentence
forall a. RenderChoices a => [a] -> Sentence
showChsList ([Comments] -> Sentence) -> [Comments] -> Sentence
forall a b. (a -> b) -> a -> b
$ DocConfig -> [Comments]
comments (DocConfig -> [Comments]) -> DocConfig -> [Comments]
forall a b. (a -> b) -> a -> b
$ OptionalFeatures -> DocConfig
docConfig (OptionalFeatures -> DocConfig) -> OptionalFeatures -> DocConfig
forall a b. (a -> b) -> a -> b
$ Choices -> OptionalFeatures
optFeats Choices
chs),
(String -> Sentence
S "Dox Verbosity", Verbosity -> Sentence
forall a. RenderChoices a => a -> Sentence
showChs (Verbosity -> Sentence) -> Verbosity -> Sentence
forall a b. (a -> b) -> a -> b
$ DocConfig -> Verbosity
doxVerbosity (DocConfig -> Verbosity) -> DocConfig -> Verbosity
forall a b. (a -> b) -> a -> b
$ OptionalFeatures -> DocConfig
docConfig (OptionalFeatures -> DocConfig) -> OptionalFeatures -> DocConfig
forall a b. (a -> b) -> a -> b
$ Choices -> OptionalFeatures
optFeats Choices
chs),
(String -> Sentence
S "Dates", Visibility -> Sentence
forall a. RenderChoices a => a -> Sentence
showChs (Visibility -> Sentence) -> Visibility -> Sentence
forall a b. (a -> b) -> a -> b
$ DocConfig -> Visibility
dates (DocConfig -> Visibility) -> DocConfig -> Visibility
forall a b. (a -> b) -> a -> b
$ OptionalFeatures -> DocConfig
docConfig (OptionalFeatures -> DocConfig) -> OptionalFeatures -> DocConfig
forall a b. (a -> b) -> a -> b
$ Choices -> OptionalFeatures
optFeats Choices
chs),
(String -> Sentence
S "Log File Name", String -> Sentence
S (String -> Sentence) -> String -> Sentence
forall a b. (a -> b) -> a -> b
$ LogConfig -> String
logFile (LogConfig -> String) -> LogConfig -> String
forall a b. (a -> b) -> a -> b
$ OptionalFeatures -> LogConfig
logConfig (OptionalFeatures -> LogConfig) -> OptionalFeatures -> LogConfig
forall a b. (a -> b) -> a -> b
$ Choices -> OptionalFeatures
optFeats Choices
chs),
(String -> Sentence
S "Logging", [Logging] -> Sentence
forall a. RenderChoices a => [a] -> Sentence
showChsList ([Logging] -> Sentence) -> [Logging] -> Sentence
forall a b. (a -> b) -> a -> b
$ LogConfig -> [Logging]
logging (LogConfig -> [Logging]) -> LogConfig -> [Logging]
forall a b. (a -> b) -> a -> b
$ OptionalFeatures -> LogConfig
logConfig (OptionalFeatures -> LogConfig) -> OptionalFeatures -> LogConfig
forall a b. (a -> b) -> a -> b
$ Choices -> OptionalFeatures
optFeats Choices
chs),
(String -> Sentence
S "Auxiliary Files", [AuxFile] -> Sentence
forall a. RenderChoices a => [a] -> Sentence
showChsList ([AuxFile] -> Sentence) -> [AuxFile] -> Sentence
forall a b. (a -> b) -> a -> b
$ OptionalFeatures -> [AuxFile]
auxFiles (OptionalFeatures -> [AuxFile]) -> OptionalFeatures -> [AuxFile]
forall a b. (a -> b) -> a -> b
$ Choices -> OptionalFeatures
optFeats Choices
chs)
]
chsFieldSent :: (Sentence, Sentence) -> Sentence
chsFieldSent :: (Sentence, Sentence) -> Sentence
chsFieldSent (rec :: Sentence
rec, chc :: Sentence
chc) = Sentence
rec Sentence -> Sentence -> Sentence
+:+ String -> Sentence
S "selected as" Sentence -> Sentence -> Sentence
+:+. Sentence
chc