cake3-0.1.0.0: Third cake - Makefile DSL

Safe HaskellNone

Development.Cake3

Synopsis

Documentation

data Alias Source

The File Alias records the file which may be referenced from other rules, it's Brothers, and the recipes required to build this file.

data Variable Source

Item wich have it's position in the Makefile. Positioned adds the metric to the contained datatype. Note, that the metric is not the subject of Eq or Ord. mappend-ing two metrics results in taking the minimal one. data Pos a = Pos { ppos :: Int, pwhat :: a } deriving(Show, Eq)

Makefile variable

class Referal x whereSource

Data structure x may be referenced from within the command. Referal class specifies side effects of such referencing. For example, referencig the file leads to adding it to the prerequisites list.

Methods

ref :: x -> A CommandSource

data A a Source

Instances

Monad A 
Functor A 
MonadFix A 
Applicative A 
MonadIO A 
MonadState Recipe1 A 
Referal x => Referal (A x) 

runMake_ :: Make () -> IO ()Source

rule :: Rulable f a => f -> A () -> aSource

ruleM :: (Monad m, Rulable f a) => f -> A () -> m aSource

phonyM :: Monad m => String -> A () -> m AliasSource

depend :: Referal x => x -> A ()Source

unsafe :: A () -> A ()Source

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

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

cmd :: QuasiQuoterSource

Has effect of a function :: QQ -> CommandGen where QQ is a string supporting $VARs. Each $VAR will be dereferenced using Ref typeclass. Result will be equivalent to

return Command $ do s1 <- ref gcc s2 <- ref (flags :: Variable) s3 <- ref s4 <- ref (file :: File) return (s1 ++ s2 ++ s3)

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

newtype CommandGen Source

CommandGen is a recipe packed in the newtype to prevent partial expantion

Constructors

CommandGen (A Command) 

Instances