{-# LANGUAGE TupleSections #-} module Drasil.Projectile.Choices where import Language.Drasil (Space(..), programName) import Language.Drasil.Code (Choices(..), Comments(..), Verbosity(..), ConstraintBehaviour(..), ImplementationType(..), Lang(..), Logging(..), Modularity(..), Structure(..), ConstantStructure(..), ConstantRepr(..), CodeConcept(..), matchConcepts, SpaceMatch, matchSpaces, AuxFile(..), Visibility(..), defaultChoices, codeSpec, makeArchit, Architecture(..), makeData, DataInfo(..), Maps(..), makeMaps, spaceToCodeType, makeConstraints, makeDocConfig, makeLogConfig, LogConfig(..), OptionalFeatures(..), makeOptFeats) import Language.Drasil.Generate (genCode) import Drasil.GOOL (CodeType(..)) import Data.Drasil.Quantities.Math (piConst) import Drasil.Projectile.Body (fullSI) import SysInfo.Drasil (SystemInformation(SI, _sys)) import Data.List (intercalate) import System.Directory (createDirectoryIfMissing, getCurrentDirectory, setCurrentDirectory) import Data.Char (toLower) genCodeWithChoices :: [Choices] -> IO () genCodeWithChoices :: [Choices] -> IO () genCodeWithChoices [] = () -> IO () forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return () genCodeWithChoices (Choices c:[Choices] cs) = let dir :: [Char] dir = (Char -> Char) -> [Char] -> [Char] forall a b. (a -> b) -> [a] -> [b] map Char -> Char toLower ([Char] -> [Char]) -> [Char] -> [Char] forall a b. (a -> b) -> a -> b $ [Char] -> Choices -> [Char] codedDirName (SystemInformation -> [Char] getSysName SystemInformation fullSI) Choices c getSysName :: SystemInformation -> [Char] getSysName SI{_sys :: () _sys = a sysName} = a -> [Char] forall c. CommonIdea c => c -> [Char] programName a sysName in do [Char] workingDir <- IO [Char] getCurrentDirectory Bool -> [Char] -> IO () createDirectoryIfMissing Bool False [Char] dir [Char] -> IO () setCurrentDirectory [Char] dir Choices -> CodeSpec -> IO () genCode Choices c (SystemInformation -> Choices -> [Mod] -> CodeSpec codeSpec SystemInformation fullSI Choices c []) [Char] -> IO () setCurrentDirectory [Char] workingDir [Choices] -> IO () genCodeWithChoices [Choices] cs codedDirName :: String -> Choices -> String codedDirName :: [Char] -> Choices -> [Char] codedDirName [Char] n Choices { architecture :: Choices -> Architecture architecture = Architecture a, optFeats :: Choices -> OptionalFeatures optFeats = OptionalFeatures o, dataInfo :: Choices -> DataInfo dataInfo = DataInfo d, maps :: Choices -> Maps maps = Maps m} = [Char] -> [[Char]] -> [Char] forall a. [a] -> [[a]] -> [a] intercalate [Char] "_" [[Char] n, Modularity -> [Char] codedMod (Modularity -> [Char]) -> Modularity -> [Char] forall a b. (a -> b) -> a -> b $ Architecture -> Modularity modularity Architecture a, ImplementationType -> [Char] codedImpTp (ImplementationType -> [Char]) -> ImplementationType -> [Char] forall a b. (a -> b) -> a -> b $ Architecture -> ImplementationType impType Architecture a, [Logging] -> [Char] codedLog ([Logging] -> [Char]) -> [Logging] -> [Char] 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 o, Structure -> [Char] codedStruct (Structure -> [Char]) -> Structure -> [Char] forall a b. (a -> b) -> a -> b $ DataInfo -> Structure inputStructure DataInfo d, ConstantStructure -> [Char] codedConStruct (ConstantStructure -> [Char]) -> ConstantStructure -> [Char] forall a b. (a -> b) -> a -> b $ DataInfo -> ConstantStructure constStructure DataInfo d, ConstantRepr -> [Char] codedConRepr (ConstantRepr -> [Char]) -> ConstantRepr -> [Char] forall a b. (a -> b) -> a -> b $ DataInfo -> ConstantRepr constRepr DataInfo d, SpaceMatch -> [Char] codedSpaceMatch (SpaceMatch -> [Char]) -> SpaceMatch -> [Char] forall a b. (a -> b) -> a -> b $ Maps -> SpaceMatch spaceMatch Maps m] codedMod :: Modularity -> String codedMod :: Modularity -> [Char] codedMod Modularity Unmodular = [Char] "U" codedMod Modularity Modular = [Char] "M" codedImpTp :: ImplementationType -> String codedImpTp :: ImplementationType -> [Char] codedImpTp ImplementationType Program = [Char] "P" codedImpTp ImplementationType Library = [Char] "L" codedLog :: [Logging] -> String codedLog :: [Logging] -> [Char] codedLog [] = [Char] "NoL" codedLog [Logging] _ = [Char] "L" codedStruct :: Structure -> String codedStruct :: Structure -> [Char] codedStruct Structure Bundled = [Char] "B" codedStruct Structure Unbundled = [Char] "U" codedConStruct :: ConstantStructure -> String codedConStruct :: ConstantStructure -> [Char] codedConStruct ConstantStructure Inline = [Char] "I" codedConStruct ConstantStructure WithInputs = [Char] "WI" codedConStruct (Store Structure s) = Structure -> [Char] codedStruct Structure s codedConRepr :: ConstantRepr -> String codedConRepr :: ConstantRepr -> [Char] codedConRepr ConstantRepr Var = [Char] "V" codedConRepr ConstantRepr Const = [Char] "C" codedSpaceMatch :: SpaceMatch -> String codedSpaceMatch :: SpaceMatch -> [Char] codedSpaceMatch SpaceMatch sm = case SpaceMatch sm Space Real of [CodeType Double, CodeType Float] -> [Char] "D" [CodeType Float, CodeType Double] -> [Char] "F" [CodeType] _ -> [Char] -> [Char] forall a. HasCallStack => [Char] -> a error [Char] "Unexpected SpaceMatch for Projectile" choiceCombos :: [Choices] choiceCombos :: [Choices] choiceCombos = [ Choices baseChoices { lang = [Python, Cpp, CSharp, Java, Swift, Julia] }, Choices baseChoices { architecture = makeArchit Modular Program, dataInfo = makeData Bundled (Store Unbundled) Var }, Choices baseChoices { lang = [Python, Cpp, CSharp, Java, Swift, Julia], architecture = makeArchit Modular Library, dataInfo = makeData Unbundled (Store Unbundled) Var, maps = makeMaps (matchConcepts [(piConst, [Pi])]) matchToFloats }, Choices baseChoices { dataInfo = makeData Bundled (Store Bundled) Const, optFeats = makeOptFeats (makeDocConfig [CommentFunc, CommentClass, CommentMod] Quiet Hide) (makeLogConfig [LogVar, LogFunc] "log.txt") [SampleInput "../../../datafiles/projectile/sampleInput.txt", ReadME], folderVal = 5 }, Choices baseChoices { dataInfo = makeData Bundled WithInputs Var, maps = makeMaps (matchConcepts [(piConst, [Pi])]) matchToFloats, optFeats = makeOptFeats (makeDocConfig [CommentFunc, CommentClass, CommentMod] Quiet Hide) (makeLogConfig [LogVar, LogFunc] "log.txt") [SampleInput "../../../datafiles/projectile/sampleInput.txt", ReadME], folderVal = 5 }] matchToFloats :: SpaceMatch matchToFloats :: SpaceMatch matchToFloats = [(Space, [CodeType])] -> SpaceMatch matchSpaces ((Space -> (Space, [CodeType])) -> [Space] -> [(Space, [CodeType])] forall a b. (a -> b) -> [a] -> [b] map (,[CodeType Float, CodeType Double]) [Space Real, Space Rational]) baseChoices :: Choices baseChoices :: Choices baseChoices = Choices defaultChoices { lang = [Python, Cpp, CSharp, Java, Swift], architecture = makeArchit Unmodular Program, dataInfo = makeData Unbundled WithInputs Var, maps = makeMaps (matchConcepts [(piConst, [Pi])]) spaceToCodeType, optFeats = makeOptFeats (makeDocConfig [CommentFunc, CommentClass, CommentMod] Quiet Hide) (makeLogConfig [] "log.txt") [SampleInput "../../../datafiles/projectile/sampleInput.txt", ReadME], srsConstraints = makeConstraints Warning Warning, folderVal = 5 }