cake3-0.6.5: 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

Instances

Monad m => MonadState MakeState (Make' m) Source # 

Methods

get :: Make' m MakeState #

put :: MakeState -> Make' m () #

state :: (MakeState -> (a, MakeState)) -> Make' m a #

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

Add prebuild command

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

Add postbuild 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.

Minimal complete definition

liftMake

Methods

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

Instances

MonadMake m => MonadMake (A' m) Source # 

Methods

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

MonadMake (Make' IO) Source # 

Methods

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

MonadMake m => MonadMake (UrpGen m) Source # 

Methods

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

MonadMake m => MonadMake (StateT s m) Source # 

Methods

liftMake :: Make' IO a -> StateT s m a Source #

newtype Make' m a Source #

Constructors

Make 

Fields

Instances

Monad m => MonadState MakeState (Make' m) Source # 

Methods

get :: Make' m MakeState #

put :: MakeState -> Make' m () #

state :: (MakeState -> (a, MakeState)) -> Make' m a #

(RefInput a x, MonadMake a) => RefInput a (Make x) Source # 

Methods

refInput :: Make x -> a Command Source #

Monad m => Monad (Make' m) Source # 

Methods

(>>=) :: Make' m a -> (a -> Make' m b) -> Make' m b #

(>>) :: Make' m a -> Make' m b -> Make' m b #

return :: a -> Make' m a #

fail :: String -> Make' m a #

Functor m => Functor (Make' m) Source # 

Methods

fmap :: (a -> b) -> Make' m a -> Make' m b #

(<$) :: a -> Make' m b -> Make' m a #

MonadFix m => MonadFix (Make' m) Source # 

Methods

mfix :: (a -> Make' m a) -> Make' m a #

Monad m => Applicative (Make' m) Source # 

Methods

pure :: a -> Make' m a #

(<*>) :: Make' m (a -> b) -> Make' m a -> Make' m b #

(*>) :: Make' m a -> Make' m b -> Make' m b #

(<*) :: Make' m a -> Make' m b -> Make' m a #

MonadIO m => MonadIO (Make' m) Source # 

Methods

liftIO :: IO a -> Make' m a #

Monad m => MonadLoc (Make' m) Source # 

Methods

withLoc :: String -> Make' m a -> Make' m a #

MonadMake (Make' IO) Source # 

Methods

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

EmbedDecl x => EmbedDecl (Make x) Source # 

Methods

embed :: MonadMake m => Make x -> UrpGen m () Source #

SrcDecl x => SrcDecl (Make x) Source # 

Methods

src :: MonadMake m => Make x -> UrpGen m () Source #

LinkDecl x => LinkDecl (Make' IO x) Source # 

Methods

link :: MonadMake m => Make' IO x -> UrpGen m () Source #

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

Instances

Monad m => MonadState Recipe (A' m) Source # 

Methods

get :: A' m Recipe #

put :: Recipe -> A' m () #

state :: (Recipe -> (a, Recipe)) -> A' m a #

Monad m => Monad (A' m) Source # 

Methods

(>>=) :: A' m a -> (a -> A' m b) -> A' m b #

(>>) :: A' m a -> A' m b -> A' m b #

return :: a -> A' m a #

fail :: String -> A' m a #

Functor m => Functor (A' m) Source # 

Methods

fmap :: (a -> b) -> A' m a -> A' m b #

(<$) :: a -> A' m b -> A' m a #

MonadFix m => MonadFix (A' m) Source # 

Methods

mfix :: (a -> A' m a) -> A' m a #

Monad m => Applicative (A' m) Source # 

Methods

pure :: a -> A' m a #

(<*>) :: A' m (a -> b) -> A' m a -> A' m b #

(*>) :: A' m a -> A' m b -> A' m b #

(<*) :: A' m a -> A' m b -> A' m a #

MonadIO m => MonadIO (A' m) Source # 

Methods

liftIO :: IO a -> A' m a #

MonadMake m => MonadMake (A' m) Source # 

Methods

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

Monad m => RefInput (A' m) CakeString Source # 
Monad m => RefInput (A' m) Tool Source # 

Methods

refInput :: Tool -> A' m Command Source #

Monad m => RefInput (A' m) Variable Source # 
Monad m => RefInput (A' m) Recipe Source # 

Methods

refInput :: Recipe -> A' m Command Source #

Monad m => RefInput (A' m) File Source # 

Methods

refInput :: File -> A' m Command Source #

Monad m => RefInput (A' m) UWExe Source # 

Methods

refInput :: UWExe -> A' m Command Source #

Monad m => RefInput (A' m) UWLib Source # 

Methods

refInput :: UWLib -> A' m Command Source #

Monad m => RefInput (A' m) (CommandGen' m) Source # 

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

Verison of Action monad with fixed parents

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

A class of monads providing access to the underlying A monad. It tells Haskell how to do a convertion: given a . (A' m) -> a class (Monad m, Monad a) => MonadAction a m | a -> m where liftAction :: A' m x -> a x

Fill recipe r using the action act by running the action monad

runA Source #

Arguments

:: Monad m 
=> String

Location string (in the Cakefile.hs)

-> A' m a

Recipe builder

-> m (Recipe, a) 

Create an empty recipe, fill it using action @act

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

Version of runA discarding the result of 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 expansion of it's commands

Constructors

CommandGen' 

Fields

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

shell1 :: Monad m => CommandGen' m -> A' m File Source #

Version of @shell returning a single file

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

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

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.

Minimal complete definition

refOutput

Methods

refOutput :: x -> A' m Command Source #

Instances

inbetween :: (Foldable t, Monad m) => a -> m (t [a]) -> m [a] Source #

spacify :: (Monad m, Foldable t) => m (t [CommandPiece]) -> m [CommandPiece] Source #

class Monad a => RefInput a x where Source #

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

Minimal complete definition

refInput

Methods

refInput :: x -> a Command Source #

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

Instances

RefInput a x => RefInput a (Maybe x) Source # 

Methods

refInput :: Maybe x -> a Command Source #

(MonadIO a, RefInput a x) => RefInput a (IO x) Source # 

Methods

refInput :: IO x -> a Command Source #

RefInput a x => RefInput a (Set x) Source # 

Methods

refInput :: Set x -> a Command Source #

RefInput a x => RefInput a [x] Source # 

Methods

refInput :: [x] -> a Command Source #

(RefInput a x, MonadMake a) => RefInput a (Make x) Source # 

Methods

refInput :: Make x -> a Command Source #

Monad m => RefInput (A' m) CakeString Source # 
Monad m => RefInput (A' m) Tool Source # 

Methods

refInput :: Tool -> A' m Command Source #

Monad m => RefInput (A' m) Variable Source # 
Monad m => RefInput (A' m) Recipe Source # 

Methods

refInput :: Recipe -> A' m Command Source #

Monad m => RefInput (A' m) File Source # 

Methods

refInput :: File -> A' m Command Source #

Monad m => RefInput (A' m) UWExe Source # 

Methods

refInput :: UWExe -> A' m Command Source #

Monad m => RefInput (A' m) UWLib Source # 

Methods

refInput :: UWLib -> A' m Command Source #

Monad m => RefInput (UrpGen m) File Source # 
Monad m => RefInput (A' m) (CommandGen' m) Source # 

depend Source #

Arguments

:: RefInput a 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 item x.

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