Working on basic interpolation

This commit is contained in:
Chris Penner 2017-04-22 12:27:06 -06:00
parent 6caf392550
commit 11f3691722
7 changed files with 81 additions and 43 deletions

5
examples/env.yaml Normal file
View File

@ -0,0 +1,5 @@
env:
date: $ date
title: Testing Templating
output: ./dist

View File

@ -1,12 +1,12 @@
#!/Users/chris/.local/bin/plated-exe
This is normal Text
{{[[ tr 'a-z' 'A-Z' ]]
Testing and stuff
}}
more text
{{[[ cat ./lorem.md - ]]
the inner text
{{cat | tr 'a-z' 'A-Z' <<EOF
testing
}}
My env var: {{[[echo $test]]}}
blah
{{ cat ./lorem.md }}
Other text
{{ echo $env }}
go!

View File

@ -18,10 +18,17 @@ library
exposed-modules: Plated.Template
, Plated.Parser
, Plated.Command
, Plated.Yaml
build-depends: base >= 4.7 && < 5
, text
, parsec
, process
, yaml
, containers
, aeson
, data-default
, filepath
, directory
default-language: Haskell2010
executable plated-exe

View File

@ -10,9 +10,9 @@ data Command =
Command T.Text
deriving Show
interpCommand :: T.Text -> Command -> IO T.Text
interpCommand inp (Command cmd) = do
(_, out, _) <- readCreateProcessWithExitCode (shell $ T.unpack cmd) (T.unpack inp)
interpCommand :: Command -> IO T.Text
interpCommand (Command cmd) = do
(_, out, _) <- readCreateProcessWithExitCode (shell $ T.unpack cmd) ""
return . T.pack $ out

View File

@ -1,7 +1,6 @@
{-# language OverloadedStrings #-}
module Plated.Parser
( templateFromFile
, interpolate
, shebang
) where
@ -21,43 +20,29 @@ infix 0 ?>
(?>) :: String -> ParsecT s u m a -> ParsecT s u m a
(?>) = flip (<?>)
templateFromFile :: FilePath -> IO (Either ParseError (Template Directive))
templateFromFile :: FilePath -> IO (Either ParseError (Template Command))
templateFromFile fname = do
file <- TIO.readFile fname
return $ runP templateParser () fname file
templateParser :: Parser (Template Directive)
templateParser :: Parser (Template Command)
templateParser = do
optional shebang
tmp <- template
eof
return tmp
template :: Parser (Template Directive)
template = Template <$> many (dir <|> txt)
template :: Parser (Template Command)
template = Template <$> many (cmd <|> txt)
where
dir = Right <$> directive
cmd = Right <$> command
txt = Left . T.pack <$> many1 (notFollowedBy (string "{{") *> anyChar)
shebang :: Parser String
shebang = "she-bang" ?> liftA2 (++) (string "#!") (manyTill anyChar (char '\n'))
directive :: Parser Directive
directive = "Directive" ?> do
spaces
_ <- string "{{"
spaces
mCommand <- optionMaybe command
txt <- manyTill anyChar (string "}}")
optional newline
return $ Directive mCommand (T.pack txt)
command :: Parser Command
command = do
_ <- string "[["
cmdString <- manyTill anyChar (string "]]")
spaces
_ <- string "{{"
cmdString <- manyTill anyChar (string "}}")
return $ Command (T.pack cmdString)
interpolate :: Template Directive -> T.Text
interpolate = const "hi"

View File

@ -1,7 +1,6 @@
{-# language OverloadedStrings #-}
module Plated.Template
( Template(..)
, Directive(..)
, processTemplate
) where
@ -14,11 +13,5 @@ data Template a =
Template [Either T.Text a]
deriving Show
data Directive =
Directive (Maybe Command) T.Text
deriving Show
processTemplate :: Template Directive -> IO T.Text
processTemplate (Template elems) = fold <$> mapM (either return fromDirective) elems
where
fromDirective (Directive mCmd txt) = maybe (return "") (interpCommand txt) mCmd
processTemplate :: Template Command -> IO T.Text
processTemplate (Template elems) = fold <$> mapM (either return interpCommand) elems

48
src/Plated/Yaml.hs Normal file
View File

@ -0,0 +1,48 @@
{-# language LambdaCase #-}
{-# language TemplateHaskell #-}
{-# language ViewPatterns #-}
module Plated.Yaml
( PlatedOptions(..)
, optionsFromFilename
, recurseUp
) where
import Control.Monad
import Data.Yaml as Y
import Data.Aeson.TH
import Data.Map as M
import Data.Default
import Data.List
import System.FilePath
-- import System.Directory
import System.Exit
data PlatedOptions = PlatedOptions
{ _env :: Map String String
, _output :: String
} deriving Show
instance Default PlatedOptions where
def = PlatedOptions M.empty "./"
-- Derive toJSON, fromJSON
$(deriveJSON defaultOptions{fieldLabelModifier=drop 1} ''PlatedOptions)
-- Retrieve an options object from a yaml file
optionsFromFilename :: FilePath -> IO PlatedOptions
optionsFromFilename = Y.decodeFileEither >=>
\case
Left err -> die . prettyPrintParseException $ err
Right options -> return options
-- findProjRootFrom :: FilePath -> IO (Maybe FilePath)
-- findProjRootFrom (makeAbsolute -> fpath) = return . pure $ fpath
recurseUp :: FilePath -> [FilePath]
recurseUp = unfoldr go
where
go "/" = Nothing
go path = Just (takeDirectory path, takeDirectory path)