diff --git a/yesod-bin/HsFile.hs b/yesod-bin/HsFile.hs new file mode 100644 index 00000000..29095d85 --- /dev/null +++ b/yesod-bin/HsFile.hs @@ -0,0 +1,23 @@ +{-# LANGUAGE OverloadedStrings #-} +module HsFile (mkHsFile) where +import Text.ProjectTemplate (createTemplate) +import Data.Conduit + ( ($$), (=$), runResourceT, ResourceT, ConduitM, awaitForever, yield ) +import qualified Data.Conduit.List as CL +import Data.Conduit.Filesystem (traverse, sourceFile) +import Prelude hiding (FilePath) +import Filesystem.Path ( FilePath ) +import Filesystem.Path.CurrentOS ( encodeString ) +import qualified Data.ByteString as BS +import Control.Monad.IO.Class (liftIO) + +mkHsFile :: IO () +mkHsFile = runResourceT $ traverse False "." + $$ readIt + =$ createTemplate + =$ awaitForever (liftIO . BS.putStr) + +-- Reads a filepath from upstream and dumps a pair of (filepath, filecontents) +readIt :: ConduitM FilePath (FilePath, ResourceT IO BS.ByteString) (ResourceT IO) () +readIt = CL.map $ \i -> (i, liftIO $ BS.readFile $ encodeString i) + diff --git a/yesod-bin/main.hs b/yesod-bin/main.hs index b860a55a..387b2f83 100755 --- a/yesod-bin/main.hs +++ b/yesod-bin/main.hs @@ -23,6 +23,7 @@ import Options.Applicative.Builder.Internal (Mod, OptionFields) #ifndef WINDOWS import Build (touch) +import HsFile (mkHsFile) touch' :: IO () touch' = touch @@ -46,7 +47,7 @@ data Options = Options } deriving (Show, Eq) -data Command = Init { _initBare :: Bool } +data Command = Init { _initBare, _initHsFiles :: Bool } | Configure | Build { buildExtraArgs :: [String] } | Touch @@ -95,7 +96,7 @@ main = do ] optParser' let cabal = rawSystem' (cabalCommand o) case optCommand o of - Init bare -> scaffold bare + Init bare hsfiles -> if hsfiles then mkHsFile else scaffold bare Configure -> cabal ["configure"] Build es -> touch' >> cabal ("build":es) Touch -> touch' @@ -124,7 +125,8 @@ optParser = Options <$> flag Cabal CabalDev ( long "dev" <> short 'd' <> help "use cabal-dev" ) <*> switch ( long "verbose" <> short 'v' <> help "More verbose output" ) <*> subparser ( command "init" - (info (Init <$> switch (long "bare" <> help "Create files in current folder")) + (info (Init <$> (switch (long "bare" <> help "Create files in current folder")) + <*> (switch (long "hsfiles" <> help "Create a hsfiles file for the current folder"))) (progDesc "Scaffold a new site")) <> command "configure" (info (pure Configure) (progDesc "Configure a project for building")) diff --git a/yesod-bin/yesod-bin.cabal b/yesod-bin/yesod-bin.cabal index 71c1967a..a39669f9 100644 --- a/yesod-bin/yesod-bin.cabal +++ b/yesod-bin/yesod-bin.cabal @@ -90,6 +90,7 @@ executable yesod , warp >= 1.3.7.5 , wai >= 1.4 , data-default-class + , filesystem-conduit >= 1.0 && < 2.0 ghc-options: -Wall -threaded main-is: main.hs @@ -101,6 +102,7 @@ executable yesod AddHandler Paths_yesod_bin Options + HsFile source-repository head type: git