cake3-0.6.5: Third cake the Makefile EDSL

Safe HaskellNone
LanguageHaskell98

Development.Cake3

Synopsis

Documentation

data Variable Source #

The representation of Makefile variable.

Instances

Eq Variable Source # 
Data Variable Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Variable -> c Variable #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Variable #

toConstr :: Variable -> Constr #

dataTypeOf :: Variable -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Variable) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Variable) #

gmapT :: (forall b. Data b => b -> b) -> Variable -> Variable #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Variable -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Variable -> r #

gmapQ :: (forall d. Data d => d -> u) -> Variable -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Variable -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Variable -> m Variable #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Variable -> m Variable #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Variable -> m Variable #

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

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

Instances

Eq Recipe Source # 

Methods

(==) :: Recipe -> Recipe -> Bool #

(/=) :: Recipe -> Recipe -> Bool #

Data Recipe Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Recipe -> c Recipe #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Recipe #

toConstr :: Recipe -> Constr #

dataTypeOf :: Recipe -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Recipe) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Recipe) #

gmapT :: (forall b. Data b => b -> b) -> Recipe -> Recipe #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Recipe -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Recipe -> r #

gmapQ :: (forall d. Data d => d -> u) -> Recipe -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Recipe -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Recipe -> m Recipe #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Recipe -> m Recipe #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Recipe -> m Recipe #

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

Methods

get :: A' m Recipe #

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

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

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

Methods

refInput :: Recipe -> A' m Command 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 # 

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

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 #

Execute the mk monad, return the Makefile as a String. In case of errors, print report to stderr and abort the execution with fail call

runMakeH Source #

Arguments

:: MakeState

Result of evalMake

-> (String -> IO b)

Handler to output the file

-> IO (MakeState, b) 

A Generic Make monad runner. Execute the monad mk, provide the output handler with Makefile encoded as a string. Note that Makefile may contain rules which references the file itself by the name makefile. In case of errors, print report to stderr and abort the execution with fail call

runMakeH_ Source #

Arguments

:: MakeState

Result of evalMake

-> (String -> IO b)

Handler to output the file

-> IO b 

A Version of runMakeH returning no state

writeMake Source #

Arguments

:: File

Output file

-> Make a

Makefile builder

-> IO () 

Execute the mk monad, build the Makefile, write it to the output file. In case of errors, print report to stderr and abort the execution with fail call

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.

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 #

rule' 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 Source #

Arguments

:: A a

Recipe builder

-> Make a 

Create the rule, place it's recipe above all recipies defined so far. See rule' for other details

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

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 postbuild command

class FileLike a where Source #

Instances

FileLike FilePath Source # 
(Monad m, FileLike (FileT h a)) => FileLike (m (FileT h a)) Source # 

Methods

combine :: m (FileT h a) -> String -> m (FileT h a) Source #

takeDirectory :: m (FileT h a) -> m (FileT h a) Source #

takeBaseName :: m (FileT h a) -> String Source #

takeFileName :: m (FileT h a) -> String Source #

makeRelative :: m (FileT h a) -> m (FileT h a) -> m (FileT h a) Source #

replaceExtension :: m (FileT h a) -> String -> m (FileT h a) Source #

takeExtension :: m (FileT h a) -> String Source #

takeExtensions :: m (FileT h a) -> String Source #

dropExtensions :: m (FileT h a) -> m (FileT h a) Source #

dropExtension :: m (FileT h a) -> m (FileT h a) Source #

splitDirectories :: m (FileT h a) -> [String] Source #

(Eq h, Show h, FileLike a) => FileLike (FileT h a) Source # 

data FileT h a Source #

Constructors

FileT h a 

Instances

EmbedDecl File Source # 

Methods

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

SrcDecl File Source # 

Methods

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

LinkDecl File Source # 

Methods

link :: MonadMake m => File -> UrpGen m () Source #

ModuleDecl File Source # 

Methods

ur :: Monad m => File -> UrpGen m () Source #

Monad m => RefOutput m File Source # 

Methods

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

Monad m => LibraryDecl m File Source # 

Methods

library :: File -> UrpGen m () Source #

RefOutput m File => RefOutput m (m File) Source # 

Methods

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

Monad m => RefOutput m (Set File) Source # 
Monad m => RefOutput m [File] Source # 

Methods

refOutput :: [File] -> A' m Command Source #

Monad m => LibraryDecl m (m File) Source # 

Methods

library :: m File -> UrpGen m () Source #

Monad m => LibraryDecl m [File] Source # 

Methods

library :: [File] -> UrpGen m () Source #

(Monad m, FileLike (FileT h a)) => FileLike (m (FileT h a)) Source # 

Methods

combine :: m (FileT h a) -> String -> m (FileT h a) Source #

takeDirectory :: m (FileT h a) -> m (FileT h a) Source #

takeBaseName :: m (FileT h a) -> String Source #

takeFileName :: m (FileT h a) -> String Source #

makeRelative :: m (FileT h a) -> m (FileT h a) -> m (FileT h a) Source #

replaceExtension :: m (FileT h a) -> String -> m (FileT h a) Source #

takeExtension :: m (FileT h a) -> String Source #

takeExtensions :: m (FileT h a) -> String Source #

dropExtensions :: m (FileT h a) -> m (FileT h a) Source #

dropExtension :: m (FileT h a) -> m (FileT h a) Source #

splitDirectories :: m (FileT h a) -> [String] Source #

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

Methods

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

Monad m => RefInput (UrpGen m) File Source # 
(Eq a, Eq h) => Eq (FileT h a) Source # 

Methods

(==) :: FileT h a -> FileT h a -> Bool #

(/=) :: FileT h a -> FileT h a -> Bool #

(Data a, Data h) => Data (FileT h a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FileT h a -> c (FileT h a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FileT h a) #

toConstr :: FileT h a -> Constr #

dataTypeOf :: FileT h a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (FileT h a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FileT h a)) #

gmapT :: (forall b. Data b => b -> b) -> FileT h a -> FileT h a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FileT h a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FileT h a -> r #

gmapQ :: (forall d. Data d => d -> u) -> FileT h a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FileT h a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FileT h a -> m (FileT h a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FileT h a -> m (FileT h a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FileT h a -> m (FileT h a) #

(Ord a, Ord h) => Ord (FileT h a) Source # 

Methods

compare :: FileT h a -> FileT h a -> Ordering #

(<) :: FileT h a -> FileT h a -> Bool #

(<=) :: FileT h a -> FileT h a -> Bool #

(>) :: FileT h a -> FileT h a -> Bool #

(>=) :: FileT h a -> FileT h a -> Bool #

max :: FileT h a -> FileT h a -> FileT h a #

min :: FileT h a -> FileT h a -> FileT h a #

(Show a, Show h) => Show (FileT h a) Source # 

Methods

showsPrec :: Int -> FileT h a -> ShowS #

show :: FileT h a -> String #

showList :: [FileT h a] -> ShowS #

(Eq h, Show h, FileLike a) => FileLike (FileT h a) Source # 
LinkDecl (File, String) Source # 

Methods

link :: MonadMake m => (File, String) -> UrpGen m () Source #

ModuleDecl (File, File) Source # 

Methods

ur :: Monad m => (File, File) -> UrpGen m () Source #

SrcDecl (File, String, String) Source # 

Methods

src :: MonadMake m => (File, String, String) -> UrpGen m () Source #

type File = FileT ModuleLocation FilePath Source #

Simple wrapper for FilePath. The first type argument is a Hint, containing the path to the current module

data ModuleLocation Source #

Constructors

ModuleLocation 

Fields

Instances

Eq ModuleLocation Source # 
Data ModuleLocation Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModuleLocation -> c ModuleLocation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModuleLocation #

toConstr :: ModuleLocation -> Constr #

dataTypeOf :: ModuleLocation -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ModuleLocation) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModuleLocation) #

gmapT :: (forall b. Data b => b -> b) -> ModuleLocation -> ModuleLocation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModuleLocation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModuleLocation -> r #

gmapQ :: (forall d. Data d => d -> u) -> ModuleLocation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModuleLocation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModuleLocation -> m ModuleLocation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleLocation -> m ModuleLocation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleLocation -> m ModuleLocation #

Ord ModuleLocation Source # 
Show ModuleLocation Source # 
EmbedDecl File Source # 

Methods

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

SrcDecl File Source # 

Methods

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

LinkDecl File Source # 

Methods

link :: MonadMake m => File -> UrpGen m () Source #

ModuleDecl File Source # 

Methods

ur :: Monad m => File -> UrpGen m () Source #

Monad m => RefOutput m File Source # 

Methods

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

Monad m => LibraryDecl m File Source # 

Methods

library :: File -> UrpGen m () Source #

RefOutput m File => RefOutput m (m File) Source # 

Methods

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

Monad m => RefOutput m (Set File) Source # 
Monad m => RefOutput m [File] Source # 

Methods

refOutput :: [File] -> A' m Command Source #

Monad m => LibraryDecl m (m File) Source # 

Methods

library :: m File -> UrpGen m () Source #

Monad m => LibraryDecl m [File] Source # 

Methods

library :: [File] -> UrpGen m () Source #

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

Methods

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

Monad m => RefInput (UrpGen m) File Source # 
LinkDecl (File, String) Source # 

Methods

link :: MonadMake m => (File, String) -> UrpGen m () Source #

ModuleDecl (File, File) Source # 

Methods

ur :: Monad m => (File, File) -> UrpGen m () Source #

SrcDecl (File, String, String) Source # 

Methods

src :: MonadMake m => (File, String, String) -> UrpGen m () Source #

file' :: ModuleLocation -> FilePath -> File Source #

Converts string representation of Path into type-safe File. Internally, files are stored in a form of offset from module root directory, plus the path from top-level dir to module root and back (see ModuleLocation)

TODO: rename to mkFile

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

Alias for replaceExtension

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

Redefine standard / operator to work with Files

topRel :: File -> FilePath Source #

Returns the path to the file, relative to the top-level directory (the place, where the target Makefile is located)

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.

genFile' :: File -> String -> A () -> Make File Source #

A version of rule, without monad set explicitly rule' :: (MonadMake m) => A a -> m a rule' act = liftMake $ snd $ withPlacement (rule2 act)

Build a rule for creating file tgt with a fixed content cnt, use additional actions act for the recipe

genFile :: File -> String -> Make File Source #

Similar to @genFile' with empty additional action

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 

Define the Makefile-level variable. Rules, referring to a variable, notice it's changes.

extvar :: String -> Variable Source #

Declare the variable defined elsewhere. Typycally, environment variables may be decalred with this functions. Variables are tracked by the cake3. Rules, referring to a variable, notice it's changes.

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

make :: Variable Source #

Reref to special variable $(MAKE)