hscaffold-0.4.5.0: Very simple file/directory structure scaffolding writer monad EDSL

Safe HaskellNone
LanguageHaskell2010

Hscaffold

Contents

Synopsis

Running Hscaffold

runHscaffold :: MonadIO m => FilePath -> WriterT ScaffoldActionV m a -> m a Source #

Run the scaffolding writer on the IO monad with no extensions

runHscaffold "." $ do
    file "./.gitignore" (Text.unlines [ ".stack-work"
                                      , "stuff"
                                      , "here"
                                      ])
    directory "./src" $ do
        file "./Main.hs" "main = putStrLn \"Hello World\""
        file "./Other.hs" "other = putStrLn \"Hello You\""

Convert Hscaffold to HSFILES (stack templates)

toHsfiles :: Writer ScaffoldActionV a -> Text Source #

Run the scaffolding writer and return an .hsfiles Text to use with stack-templates

writeToHsfiles :: MonadIO m => FilePath -> Writer ScaffoldActionV a -> m () Source #

Shortcut for

writeToHsfiles = do h <- toHsfiles w; liftIO $ Text.writeFile fp h

Convert HSFILES to Hscaffold

fromHsfiles :: String -> ScaffoldAction e Source #

Converts hsfiles to hscaffold actions

fromHsfilesW :: MonadWriter (ScaffoldAction e) m => String -> m () Source #

Converts hsfiles to a hscaffold monad

Convert a directory to Hscaffold

hscaffoldFromDirectory :: FilePath -> IO (ScaffoldAction e) Source #

Converts a directory to scaffold actions

hscaffoldFromDirectoryWith :: ([FilePath] -> [FilePath]) -> FilePath -> IO (ScaffoldAction e) Source #

Converts a directory to scaffold actions with a custom filter function. By default we ignore directories starting with .

Compile Hscaffold to Haskell code

hscaffoldToHaskell :: Foldable t => t (ScaffoldActionType e) -> Text Source #

Generates Haskell code from scaffold actions

Finer grained runners

runAction :: FilePath -> ScaffoldActionType e -> IO () Source #

Run a single scaffolding action on the IO monad with no extensions

runWriter :: Writer w a -> (a, w) #

Unwrap a writer computation as a (result, output) pair. (The inverse of writer.)

runWriterT :: WriterT w m a -> m (a, w) #

EDSL Combinators

directory :: MonadWriter (ScaffoldAction e) m => FilePath -> WriterT (ScaffoldAction e) m b -> m b Source #

Create a directory with the nested contents

file :: MonadWriter (ScaffoldAction e) m => FilePath -> Text -> m () Source #

Create a file with the given contents

link :: MonadWriter (ScaffoldAction e) m => FilePath -> FilePath -> m () Source #

Create a symbolic link between two filepaths

copy :: MonadWriter (ScaffoldAction e) m => FilePath -> FilePath -> m () Source #

Copy a file from A to B

Non-absolute paths are treated relative to the *current* root, nested blocks change the root

touch :: MonadWriter (ScaffoldAction e) m => FilePath -> m () Source #

Write the empty string to a file

Setting permissions

permissions :: MonadWriter (ScaffoldAction e) m => FilePath -> Permissions -> m () Source #

Set permissions on a filepath

fileWith :: MonadWriter (ScaffoldAction e) m => Permissions -> FilePath -> Text -> m () Source #

Create a file with the given contents and permissions

directoryWith :: MonadWriter (ScaffoldAction e) m => Permissions -> FilePath -> WriterT (ScaffoldAction e) m b -> m b Source #

Create a directory with the nested contents and permissions

copyWith :: MonadWriter (ScaffoldAction e) m => Permissions -> FilePath -> FilePath -> m () Source #

Copy a file from A to B and set permissions on B, see copy

touchWith :: MonadWriter (ScaffoldAction e) m => Permissions -> FilePath -> m () Source #

Write the empty string to a file with given permissions

Types

type ScaffoldMonadT m a = WriterT ScaffoldActionV m a Source #

The writer monad transformer for scaffold actions

type ScaffoldMonadIO a = WriterT ScaffoldActionV IO a Source #

The writer monad for scaffold actions, running in IO

type ScaffoldAction e = [ScaffoldActionType e] Source #

Accumulator for actions

type ScaffoldActionV = ScaffoldAction () Source #

Accumulator for actions set with void extension

type ScaffoldMonadET e m a = WriterT (ScaffoldAction e) m a Source #

The writer monad transformer for scaffold actions with an extension

Utilities

withTemporaryHscaffold :: (MonadMask m, MonadIO m) => ScaffoldMonadT m a -> (FilePath -> m b) -> m b Source #

Creates a temporary directory with the scaffold and runs an action that takes it as its argument.

Uses withSystemTempDirectory under the hood.

withTemporaryHscaffold
    (do
        file "something" "something"
        directory "something" $ file "something-else" "something"
    )
    (tmp -> do
        undefined
    )

Helpers

mkActionPath Source #

Arguments

:: FilePath

The root

-> FilePath

A filepath

-> FilePath 

Very simple helper, if the second argument is absolute, returns it, otherwise, return it relative to the first argument

Re-exports

data Text :: * #

A space efficient, packed, unboxed Unicode text type.

Instances

type Item Text 
type Item Text = Char