cake3-0.5.2.0: Third cake the Makefile EDSL

Safe HaskellNone
LanguageHaskell98

Development.Cake3

Synopsis

Documentation

data Variable Source

The representation of Makefile variable

data Recipe Source

Recipe answers to the question 'How to build the targets'. Internally, it contains sets of targets and prerequisites, as well as shell commands required to build former from latter

class MonadAction a m => RefInput a m x where Source

Class of things which may be referenced using '$(expr)' from inside of quasy-quoted shell expressions

Methods

refInput :: x -> a Command Source

Register the input item, return it's shell-script representation

Instances

MonadAction a m => RefInput a m CakeString 
MonadAction a m => RefInput a m Variable 
MonadAction a m => RefInput a m Recipe 
MonadAction a m => RefInput a m File 
MonadAction a m => RefInput a m UWExe 
MonadAction a m => RefInput a m UWLib 
MonadAction a m => RefInput a m (CommandGen' m) 
RefInput a m x => RefInput a m (Maybe x) 
(RefInput a m x, MonadMake a) => RefInput a m (Make x) 
(MonadAction a m, MonadMake a) => RefInput a m (Make Recipe) 
(MonadIO a, RefInput a m x) => RefInput a m (IO x) 
MonadAction a m => RefInput a m (Set File) 
RefInput a m x => RefInput a m [x] 

class Monad m => RefOutput m x where Source

Class of things which may be referenced using '@(expr)' syntax of the quasi-quoted shell expressions.

Methods

refOutput :: x -> A' m Command Source

Register the output item, return it's shell-command representation. Files are rendered using space protection quotation, variables are wrapped into $(VAR) syntax, item lists are converted into space-separated lists.

Instances

Monad m => RefOutput m File 
RefOutput m x => RefOutput m (Maybe x) 
Monad m => RefOutput m (Set File) 
Monad m => RefOutput m [File] 

data CakeString Source

Simple wrapper for strings, a target for various typeclass instances.

string :: String -> CakeString Source

An alias to CakeString constructor

type A a = A' (Make' IO) a Source

Verison of Action monad with fixed parents

type Make a = Make' IO a Source

buildMake :: MakeState -> Either String String Source

Render the Makefile. Return either the content (Right), or error messages (Left).

runMake :: Make a -> IO String Source

A General Make runner. Executes the monad, returns the Makefile as a String. Errors go to stdout. fail is possible.

writeMake Source

Arguments

:: File

Output file

-> Make a

Makefile builder

-> IO () 

Execute the Make monad, build the Makefile, write it to the output file. Also note, that errors (if any) go to the stderr. fail will be executed in such cases

includeMakefile :: Foldable t => t File -> Make () Source

Add 'include ...' directive to the final Makefile for each input file.

class Monad m => MonadMake m where Source

A Monad providing access to MakeState. TODO: not mention IO here.

Methods

liftMake :: Make' IO a -> m a Source

Instances

rule Source

Arguments

:: A a

Recipe builder

-> Make a 

A version of rule2. Rule places it's recipe above all recipies defined so far.

rule2 Source

Arguments

:: MonadMake m 
=> A a

Recipe builder

-> m (Recipe, a)

The recipe itself and the recipe builder's result

Build a Recipe using the builder provided and record it to the MakeState. Return the copy of Recipe (which should not be changed in future) and the result of recipe builder. The typical recipe builder result is the list of it's targets.

Example Lets declare a rule which builds "main.o" out of "main.c" and CFLAGS variable

let c = file "main.c"
rule $ shell [cmd| gcc -c $(extvar "CFLAGS") -o @(c.="o") $c |]

rule' :: MonadMake m => A a -> m a Source

A version of rule, without monad set explicitly

phony Source

Arguments

:: Monad m 
=> String

A name of phony target

-> A' m () 

Adds the phony target for a rule. Typical usage:

rule $ do
 phony "clean"
 unsafeShell [cmd|rm $elf $os $d|]

depend Source

Arguments

:: RefInput a m x 
=> x

File or [File] or (Set File) or other form of dependency.

-> a () 

Add it's argument to the list of dependencies (prerequsites) of a current recipe under construction

produce Source

Arguments

:: RefOutput m x 
=> x

File or [File] or other form of target.

-> A' m () 

Declare that current recipe produces some producable item.

ignoreDepends :: Monad m => A' m a -> A' m a Source

Modifie the recipe builder: ignore all the dependencies

prebuild :: MonadMake m => CommandGen -> m () Source

Add prebuild command

postbuild :: MonadMake m => CommandGen -> m () Source

Add prebuild command

type File = FileT FilePath Source

Simple wrapper for FilePath.

(.=) :: FileLike a => a -> String -> a Source

Alias for replaceExtension

(</>) :: FileLike a => a -> String -> a Source

Redefine standard / operator to work with Files

toFilePath :: FileT FilePath -> FilePath Source

Convert File back to FilePath

readFileForMake Source

Arguments

:: MonadMake m 
=> File

File to read contents of

-> m ByteString 

Obtain the contents of a File. Note, that this generally means, that Makefile should be regenerated each time the File is changed.

prerequisites :: (Applicative m, Monad m) => A' m (Set File) Source

Get a list of prerequisites added so far

shell Source

Arguments

:: Monad m 
=> CommandGen' m

Command builder as returned by cmd quasi-quoter

-> A' m [File] 

Apply the recipe builder to the current recipe state. Return the list of targets of the current Recipe under construction

unsafeShell :: Monad m => CommandGen' m -> A' m [File] Source

Version of shell which doesn't track it's dependencies

cmd :: QuasiQuoter Source

Has effect of a function QQ -> CommandGen where QQ is a string supporting the following syntax:

  • $(expr) evaluates to expr and adds it to the list of dependencies (prerequsites)
  • @(expr) evaluates to expr and adds it to the list of targets
  • $$ and @@ evaluates to $ and @

Example

[cmd|gcc $flags -o @file|]

is equivalent to

  return $ CommandGen $ do
    s1 <- refInput "gcc "
    s2 <- refInput (flags :: Variable)
    s3 <- refInput " -o "
    s4 <- refOutput (file :: File)
    return (s1 ++ s2 ++ s3 ++ s4)

Later, this command may be examined or passed to the shell function to apply it to the recipe

makevar Source

Arguments

:: String

Variable name

-> String

Default value

-> Variable 

Declare the variable which is defined in the current Makefile and has it's default value

extvar :: String -> Variable Source

Declare the variable which is not defined in the target Makefile

newtype CommandGen' m Source

CommandGen is a recipe-builder packed in the newtype to prevent partial expantion of it's commands

Constructors

CommandGen' 

Fields

unCommand :: A' m Command
 

Instances

make :: Variable Source

Special variable $(MAKE)