cake3-0.2.1.0: Third cake the Makefile EDSL

Safe HaskellNone

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 whereSource

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

Methods

refInput :: x -> a CommandSource

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 
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 whereSource

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

Methods

refOutput :: x -> A' m CommandSource

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 -> CakeStringSource

An alias to CakeString constructor

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

Verison of Action monad with fixed parents

type Make a = Make' IO aSource

buildMake :: MakeState -> Either String StringSource

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

runMake :: Make a -> IO StringSource

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

writeMakeSource

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 whereSource

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

Methods

liftMake :: Make' IO a -> m aSource

Instances

ruleSource

Arguments

:: A a

Rule builder

-> Make a 

Version of rule2 which places it's recipe above all other recipies.

 let c = file "main.c"

Declare a rule to build main.o out of main.c and CFLAGS variable

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

rule2 :: MonadMake m => A a -> m (Recipe, a)Source

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

Version of rule2, without Make monad set explicitly

phony :: String -> A ()Source

Adds the phony target for a rule. Typical usage:

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

dependSource

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

produceSource

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 aSource

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 FilePathSource

Simple wrapper for FilePath.

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

Alias for replaceExtension

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

Redefine standard / operator to work with Files

toFilePath :: FileT FilePath -> FilePathSource

Convert File back to FilePath

readFileForMakeSource

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

shellSource

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 :: QuasiQuoterSource

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

makevarSource

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 -> VariableSource

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
 

make :: VariableSource

Special variable $(MAKE)