Skip to content

Commit

Permalink
Separated and refactored code
Browse files Browse the repository at this point in the history
  • Loading branch information
TimeTravelPenguin committed Nov 10, 2023
1 parent c88309e commit a2fdd7a
Show file tree
Hide file tree
Showing 2 changed files with 261 additions and 135 deletions.
281 changes: 146 additions & 135 deletions src/Data/Configuration.hs
Original file line number Diff line number Diff line change
@@ -1,161 +1,172 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}

module Data.Configuration (
CopyTemplateItemName,
-- * Type Alias
ReplacementActionName,
ReplacementSearchString,
TemplateName,

-- * Data Types

-- ** Text Replacement Action
TextReplacementAction (..),
CopyTemplateItem (..),
CopyConfiguration (..),
replacementActionName,
replacementActionSearchString,
replacementText,

-- ** Template Configuration
AuthorInfo (..),
TemplateConfiguration (..),
authorInfo,
templateDirectoryPath,
relativeOutputPath,
fileContentReplacementMap,

-- ** Configuration
Configuration (..),
contentReplacementActions,
templateConfigurations,

-- ** Other datatypes
ConfigurationPath (NewConfiguration, ExistingConfiguration),
ifNewConfiguration,
-- Lenses
includeInDefaultCopyTemplate,
templateItemDirectory,
relativeOutputLocation,
fileContentReplacementMappings,
configAuthorName,
copyTemplateItems,
-- Actions
findOrCreateDefaultConfig,
parseApplicationConfig,
) where

import Control.Lens (makeLenses, (&), (.~))
import Control.Monad (unless)
import Data.Aeson (FromJSON, ToJSON, eitherDecodeFileStrict)
import Control.Lens (makeLenses)
import Data.Aeson (FromJSON, ToJSON)
import Data.List.NonEmpty (NonEmpty)
import Data.Map.Strict (Map)
import Data.Map.Strict qualified as Map
import Data.Semigroup (Arg (Arg))
import Data.Sequence (Seq)
import Data.Text (Text)
import GHC.Generics (Generic)
import IOHelpers (encodeFilePretty)
import Path (Abs, Dir, File, Path, Rel, fromAbsFile, parent, reldir, relfile)
import Path.IO (doesFileExist, ensureDir, resolveDir, resolveFile)

type CopyTemplateItemName = Text

data TextReplacementAction
= CourseCodeReplacement
| AssessmentNumberReplacement
| AuthorNameReplacement
deriving (Show, Eq, Generic)

data CopyTemplateItem = CopyTemplateItem
{ _includeInDefaultCopyTemplate :: Bool
, _templateItemDirectory :: Path Abs Dir
, _relativeOutputLocation :: Path Rel Dir
, _fileContentReplacementMappings :: Map (Path Rel File) (Map Text TextReplacementAction)
import Path (Abs, Dir, File, Path, Rel)

type ReplacementActionName = Text
type ReplacementSearchString = Text
type TemplateName = Text

-- | A text replacement action to perform on the contents of a file,
-- as read from a configuration file.
data TextReplacementAction = TextReplacementAction
{ _replacementActionName :: ReplacementActionName
-- ^ The unique name for the replacement action
, _replacementActionSearchString :: ReplacementSearchString
-- ^ The String to find and replace with a file
, _replacementText :: Text
-- ^ The value to substitute in place of the found search string.
-- There are some special values that can be used based on the current directory:
--
-- +------------------------+-----------------------------------------------------+
-- | _replacementText Value | Substituted Value |
-- +========================+=====================================================+
-- | %%THECOURSE%% | The course code found in the current directory. |
-- +------------------------+-----------------------------------------------------+
-- | %%THEASSESSNO%% | The numeric value of the current assessment folder. |
-- +------------------------+-----------------------------------------------------+
-- | %%THEAUTHOR%% | The author as specified in the used template. |
-- | | If no author is given, no replacement will be made. |
-- +------------------------+-----------------------------------------------------+
--
-- Any other values will be substituted as is.
}
deriving (Show, Eq, Generic)

data CopyConfiguration = CopyConfiguration
{ _configAuthorName :: Maybe Text -- TODO: Make this a datatype for multiple configs, settable via CLI commands
, _copyTemplateItems :: Map CopyTemplateItemName CopyTemplateItem
deriving (Show, Eq, Generic, FromJSON, ToJSON)

-- | Information about authors for `TemplateConfiguration`s.
data AuthorInfo
= -- | A single author
SingularAuthor Text
| -- | A non-empty collection of authors
MultipleAuthors (NonEmpty Text)
deriving (Show, Eq, Generic, FromJSON, ToJSON)

-- | A template to specify a directory of files to copy to a new location.
data TemplateConfiguration = TemplateConfiguration
{ _authorInfo :: Maybe AuthorInfo
-- ^ The author of the current template
, _templateDirectoryPath :: Path Abs Dir
-- ^ The absolute path to the directory of files consisting of the template
, _relativeOutputPath :: Path Rel Dir
-- ^ The path relative to the assessment root (or current directory when using --here)
-- where the contents of the template folder will be copied into.
-- An empty path will copy directly into the root directory, without a new folder.
, _fileContentReplacementMap :: Map (Path Rel File) (Seq Text)
-- ^ A mapping of files relative to the template directory with `TextReplacementAction`s to perform.
-- Keys are the relative file paths and values are `Seq Text` of names to `TextReplacementActions`.
}
deriving (Show, Eq, Generic, FromJSON, ToJSON)

-- | A template configuration used to copy a directory when creating a new assessment.
data Configuration = Configuration
{ _contentReplacementActions :: Seq TextReplacementAction
-- ^ A collection of replacement actions to perform on specified file contents
, -- TODO: Allow for copy templates to be compositions, which are lists of existing copy template names
_templateConfigurations :: Map TemplateName TemplateConfiguration
-- ^ A mapping of template configuration names to configurations
}
deriving (Show, Eq, Generic)
deriving (Show, Eq, Generic, FromJSON, ToJSON)

data ConfigurationPath
= NewConfiguration (Path Abs File)
| ExistingConfiguration (Path Abs File)
deriving (Show, Eq)
deriving (Show, Eq, Generic, FromJSON, ToJSON)

ifNewConfiguration :: ConfigurationPath -> (Path Abs File -> t) -> (Path Abs File -> t) -> t
ifNewConfiguration cfg p q =
case cfg of
NewConfiguration config -> p config
ExistingConfiguration config -> q config

makeLenses ''CopyTemplateItem
makeLenses ''CopyConfiguration
makeLenses ''TextReplacementAction
makeLenses ''TemplateConfiguration
makeLenses ''Configuration

{-
instance ToJSON TextReplacementAction
instance FromJSON TextReplacementAction

instance ToJSON CopyTemplateItem
instance FromJSON CopyTemplateItem

instance ToJSON CopyTemplate
instance FromJSON CopyTemplate
instance ToJSON CopyConfiguration
instance FromJSON CopyConfiguration

-- Creates demo file for the default config. It will make all parents in the filepath if they do not exist.
createDemoTemplateFile :: Path Abs File -> IO ()
createDemoTemplateFile filePath = do
ensureDir (parent filePath)
writeFile
(fromAbsFile filePath)
"\\documentclass[11pt]{article}\n\
\\n\\title{%%COURSE%% Assessment %%ASSESSNO%%}\n\
\\\date{\\today}\n\
\\\author{%%NAME%%}\n\
\\n\\begin{document}\n\
\ \\maketitle\n\
\ Hello, there! This is just a simple \\LaTeX template!\n\
\\\end{document}"

createDemoTemplateFileIfNotExist :: Path Abs File -> IO ()
createDemoTemplateFileIfNotExist filePath = do
fileExists <- doesFileExist filePath
unless fileExists $ createDemoTemplateFile filePath

createDefaultConfigFile :: Path Abs Dir -> IO (Path Abs File)
createDefaultConfigFile configPath = do
-- Make a new template directory in config dir
assessmentTemplatePath <- resolveDir configPath "AssessmentTemplates"

-- Create demo template sub-folders
mathTemplateDir <- resolveDir assessmentTemplatePath "MathTemplate"
compSciTemplateDir <- resolveDir assessmentTemplatePath "CompSciTemplate"

-- Create demo assessment template files in each sub-dir
mathTemplate <- resolveFile mathTemplateDir "main.tex"
compSciTemplate <- resolveFile compSciTemplateDir "main.tex"

-- Parent directories will be created along with files
createDemoTemplateFileIfNotExist mathTemplate
createDemoTemplateFileIfNotExist compSciTemplate

let fileContentMap =
Map.fromArgSet
[ Arg "%%COURSE%%" CourseCodeReplacement
, Arg "%%ASSESSNO%%" AssessmentNumberReplacement
, Arg "%%NAME%%" AuthorNameReplacement
]
template =
CopyTemplateItem
{ _includeInDefaultCopyTemplate = True
, _templateItemDirectory = mathTemplateDir
, _relativeOutputLocation = [reldir|tex/|]
, _fileContentReplacementMappings = Map.fromArgSet [Arg [relfile|tex/file.tex|] fileContentMap]
}
config =
CopyConfiguration
{ _configAuthorName = Just "Your Name"
, _copyTemplateItems =
Map.fromArgSet
[ Arg "MathTemplate" template
, Arg "CompSciTemplate" $
template
& (templateItemDirectory .~ compSciTemplateDir)
. (fileContentReplacementMappings .~ Map.fromArgSet [Arg [relfile|./tex/files/the_file.tex|] fileContentMap])
]
}

configFile <- resolveFile configPath "config.json"
encodeFilePretty (fromAbsFile configFile) config
return configFile

-- | Creates a default "config.json" in the provided directory, if one is not found.
findOrCreateDefaultConfig :: Path Abs Dir -> FilePath -> IO ConfigurationPath
findOrCreateDefaultConfig dir cfgName = do
configFile <- resolveFile dir cfgName
configExists <- doesFileExist configFile
if not configExists
then NewConfiguration <$> createDefaultConfigFile dir
else return $ ExistingConfiguration configFile

parseApplicationConfig :: Path Abs File -> IO (Either String CopyConfiguration)
parseApplicationConfig configFile = do
eitherDecodeFileStrict (fromAbsFile configFile)
-}

{-
instance ToJSON TextReplacementAction where
toJSON v =
object
[ "ActionName" .= (v ^. replacementActionName)
, "SearchString" .= (v ^. replacementActionSearchString)
]
instance FromJSON TextReplacementAction where
parseJSON = withObject "TextReplacementAction" $ \v ->
TextReplacementAction
<$> v .: "ActionName"
<*> v .: "SearchString"
instance ToJSON CopyTemplate where
toJSON v =
object
[ "TemplateFolderDirectory" .= (v ^. templateFolderDirectory)
, "RelativeOutputPath" .= (v ^. relativeOutputPath)
, "FileContentReplacementMap" .= (v ^. fileContentReplacementMap)
]
instance FromJSON CopyTemplate where
parseJSON = withObject "CopyTemplate" $ \v ->
CopyTemplate
<$> v .: "TemplateFolderDirectory"
<*> v .: "RelativeOutputPath"
<*> v .: "FileContentReplacementMap"
instance ToJSON CopyConfiguration where
toJSON v =
object
[ "CopyTemplates" .= (v ^. copyTemplates)
, "ContentReplacementActions" .= (v ^. contentReplacementActions)
]
instance FromJSON CopyConfiguration where
parseJSON = withObject "CopyConfiguration" $ \v ->
CopyConfiguration
<$> v .: "ContentReplacementActions"
<*> v .: "CopyTemplates"
-}
Loading

0 comments on commit a2fdd7a

Please sign in to comment.