cake3-0.6.0: Third cake the Makefile EDSL

Safe HaskellNone
LanguageHaskell98

Development.Cake3.Monad

Synopsis

Documentation

data MakeState Source

MakeState describes the state of the EDSL synthesizers during the the program execution.

Constructors

MS 

Fields

prebuilds :: Recipe

Prebuild commands. targets/prerequsites of the recipe are ignored, commands are executed before any target

postbuilds :: Recipe

Postbuild commands.

recipes :: Set Recipe

The set of recipes, to be checked and renderd as a Makefile

sloc :: Location

Current location. FIXME: fix or remove

makeDeps :: Set File

Set of files which the Makefile depends on

placement :: [File]

Placement list is the order of targets to be placed in the output file

includes :: Set File

Set of files to include in the output file (Makefile specific thing)

errors :: String

Errors found so far

warnings :: String

Warnings found so far

outputFile :: File

Name of the Makefile being generated , tmpIndex :: Int ^ Index to build temp names

extraClean :: Set File

extra clean files

Instances

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

Add prebuild command

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

Add prebuild command

checkForEmptyTarget :: Foldable f => f Recipe -> String Source

Find recipes without targets. Empty result means 'No errors'

checkForTargetConflicts :: Foldable f => f Recipe -> String Source

Find recipes sharing a target. Empty result means 'No errors'

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

newtype Make' m a Source

Constructors

Make 

Fields

unMake :: StateT MakeState m a
 

Instances

(RefInput a m x, MonadMake a) => RefInput a m (Make x) 
(MonadAction a m, MonadMake a) => RefInput a m (Make Recipe) 
Monad m => MonadState MakeState (Make' m) 
Monad m => Monad (Make' m) 
Functor m => Functor (Make' m) 
MonadFix m => MonadFix (Make' m) 
(Monad m, Functor m) => Applicative (Make' m) 
Monad m => MonadLoc (Make' m) 
MonadIO m => MonadIO (Make' m) 
MonadMake (Make' IO) 

type Make a = Make' IO a Source

evalMake :: Monad m => File -> Make' m a -> m MakeState Source

Evaluate the Make monad mf, return MakeState containing the result. Name mf is used for self-referencing recipes.

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

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

newtype A' m a Source

A here stands for Action. It is a State monad carrying a Recipe as its state. Various monadic actions add targets, prerequisites and shell commands to this recipe. After that, rule function records it to the MakeState. After the recording, no modification is allowed for this recipe.

Constructors

A' 

Fields

unA' :: StateT Recipe m a
 

Instances

Monad m => MonadState Recipe (A' m) 
Monad m => Monad (A' m) 
Functor m => Functor (A' m) 
MonadFix m => MonadFix (A' m) 
(Monad m, Functor m) => Applicative (A' m) 
MonadIO m => MonadIO (A' m) 
MonadMake m => MonadMake (A' m) 
Monad m => MonadAction (A' m) m 

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

Verison of Action monad with fixed parents

class (Monad m, Monad t) => MonadAction t m | t -> m where Source

A class of monads providing access to the underlying A monad

Methods

liftAction :: A' m x -> t x Source

Instances

Monad m => MonadAction (A' m) m 

runA' :: Monad m => Recipe -> A' m a -> m (Recipe, a) Source

Run the Action monad, using already existing Recipe as input.

runA Source

Arguments

:: Monad m 
=> String

Location string (in the Cakefile.hs)

-> A' m a

Recipe builder

-> m (Recipe, a) 

Create new empty recipe and run action on it.

runA_ :: Monad m => String -> A' m a -> m Recipe Source

Version of runA discarding the result of A's computation

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

Get a list of targets added so far

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

Get a list of prerequisites added so far

markPhony :: Monad m => A' m () Source

Mark the recipe as PHONY i.e. claim that all it's targets are not real files. Makefile-specific.

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

markIntermediate :: Monad m => A' m () Source

Mark the recipe as INTERMEDIATE i.e. claim that all it's targets may be removed after the build process. Makefile-specific.

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.

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

commandGen :: A Command -> CommandGen Source

Pack the command builder into a CommandGen

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

Modifie the recipe builder: ignore all the dependencies

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

newtype CakeString Source

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

Constructors

CakeString String 

string :: String -> CakeString Source

An alias to CakeString constructor

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] 

inbetween :: Monad m => t -> m [[t]] -> m [t] Source

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

Class of things which may be referenced using '$(expr)' syntax of the 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 Tool 
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] 

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.

variables Source

Arguments

:: (Foldable t, Monad m) 
=> t Variable

A set of variables to depend the recipe on

-> A' m () 

Add variables vs to tracking list of the current recipe

tools Source

Arguments

:: (Foldable t, Monad m) 
=> t Tool

A set of tools used by this recipe

-> A' m () 

Add tools ts to the tracking list of the current recipe

commands :: Monad m => [Command] -> A' m () Source

Add commands to the list of commands of a current recipe under construction. Warning: this function behaves like unsafeShell i.e. it doesn't analyze the command text

location :: Monad m => String -> A' m () Source

Set the recipe's location in the Cakefile.hs

flags :: Monad m => Set Flag -> A' m () Source

Set additional flags

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