| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Development.Cake3.Monad
- type Location = String
- data MakeState = MS {}
- initialMakeState :: File -> MakeState
- defr :: Recipe
- getPlacementPos :: Make Int
- addPlacement :: Int -> File -> Make ()
- addMakeDep :: File -> Make ()
- tmp_file :: String -> File
- prebuild :: MonadMake m => CommandGen -> m ()
- postbuild :: MonadMake m => CommandGen -> m ()
- prebuildS :: MonadMake m => CommandGen -> m ()
- postbuildS :: MonadMake m => CommandGen -> m ()
- checkForEmptyTarget :: Foldable f => f Recipe -> String
- checkForTargetConflicts :: Foldable f => f Recipe -> String
- class Monad m => MonadMake m where
- newtype Make' m a = Make {}
- type Make a = Make' IO a
- evalMake :: Monad m => File -> Make' m a -> m MakeState
- modifyLoc :: MonadState MakeState m => (Location -> Location) -> m ()
- addRecipe :: Recipe -> Make ()
- getLoc :: Make String
- includeMakefile :: Foldable t => t File -> Make ()
- newtype A' m a = A' {}
- type A a = A' (Make' IO) a
- runA' :: Monad m => Recipe -> A' m a -> m (Recipe, a)
- runA :: Monad m => String -> A' m a -> m (Recipe, a)
- runA_ :: Monad m => String -> A' m a -> m Recipe
- targets :: (Applicative m, Monad m) => A' m (Set File)
- prerequisites :: (Applicative m, Monad m) => A' m (Set File)
- markPhony :: Monad m => A' m ()
- phony :: Monad m => String -> A' m ()
- markIntermediate :: Monad m => A' m ()
- readFileForMake :: MonadMake m => File -> m ByteString
- newtype CommandGen' m = CommandGen' {}
- type CommandGen = CommandGen' (Make' IO)
- commandGen :: A Command -> CommandGen
- ignoreDepends :: Monad m => A' m a -> A' m a
- shell :: Monad m => CommandGen' m -> A' m [File]
- shell1 :: Monad m => CommandGen' m -> A' m File
- unsafeShell :: Monad m => CommandGen' m -> A' m [File]
- newtype CakeString = CakeString String
- string :: String -> CakeString
- class Monad m => RefOutput m x where
- inbetween :: (Foldable t, Monad m) => a -> m (t [a]) -> m [a]
- spacify :: (Monad m, Foldable t) => m (t [CommandPiece]) -> m [CommandPiece]
- class Monad a => RefInput a x where
- depend :: RefInput a x => x -> a ()
- produce :: RefOutput m x => x -> A' m ()
- variables :: (Foldable t, Monad m) => t Variable -> A' m ()
- tools :: (Foldable t, Monad m) => t Tool -> A' m ()
- commands :: Monad m => [Command] -> A' m ()
- location :: Monad m => String -> A' m ()
- flags :: Monad m => Set Flag -> A' m ()
- cmd :: QuasiQuoter
Documentation
MakeState describes the state of the EDSL synthesizers during the the program execution.
Constructors
| MS | |
Fields
| |
initialMakeState :: File -> MakeState Source #
addMakeDep :: File -> Make () Source #
prebuild :: MonadMake m => CommandGen -> m () Source #
Add prebuild command
postbuild :: MonadMake m => CommandGen -> m () Source #
Add postbuild command
prebuildS :: MonadMake m => CommandGen -> m () Source #
postbuildS :: MonadMake m => CommandGen -> m () Source #
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
Instances
| Monad m => MonadState MakeState (Make' m) Source # | |
| (RefInput a x, MonadMake a) => RefInput a (Make x) Source # | |
| Monad m => Monad (Make' m) Source # | |
| Functor m => Functor (Make' m) Source # | |
| MonadFix m => MonadFix (Make' m) Source # | |
| Monad m => Applicative (Make' m) Source # | |
| MonadIO m => MonadIO (Make' m) Source # | |
| Monad m => MonadLoc (Make' m) Source # | |
| MonadMake (Make' IO) Source # | |
| EmbedDecl x => EmbedDecl (Make x) Source # | |
| SrcDecl x => SrcDecl (Make x) Source # | |
| LinkDecl x => LinkDecl (Make' IO x) 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.
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.
Instances
| Monad m => MonadState Recipe (A' m) Source # | |
| Monad m => Monad (A' m) Source # | |
| Functor m => Functor (A' m) Source # | |
| MonadFix m => MonadFix (A' m) Source # | |
| Monad m => Applicative (A' m) Source # | |
| MonadIO m => MonadIO (A' m) Source # | |
| MonadMake m => MonadMake (A' m) Source # | |
| Monad m => RefInput (A' m) CakeString Source # | |
| Monad m => RefInput (A' m) Tool Source # | |
| Monad m => RefInput (A' m) Variable Source # | |
| Monad m => RefInput (A' m) Recipe Source # | |
| Monad m => RefInput (A' m) File Source # | |
| Monad m => RefInput (A' m) UWExe Source # | |
| Monad m => RefInput (A' m) UWLib Source # | |
| Monad m => RefInput (A' m) (CommandGen' m) Source # | |
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
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
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.
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.
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' | |
type CommandGen = CommandGen' (Make' IO) Source #
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
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 |
Instances
| Eq CakeString Source # | |
| Ord CakeString Source # | |
| Show CakeString Source # | |
| Monad m => RefInput (A' m) CakeString Source # | |
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
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
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 # | |
| (MonadIO a, RefInput a x) => RefInput a (IO x) Source # | |
| RefInput a x => RefInput a (Set x) Source # | |
| RefInput a x => RefInput a [x] Source # | |
| (RefInput a x, MonadMake a) => RefInput a (Make x) Source # | |
| Monad m => RefInput (A' m) CakeString Source # | |
| Monad m => RefInput (A' m) Tool Source # | |
| Monad m => RefInput (A' m) Variable Source # | |
| Monad m => RefInput (A' m) Recipe Source # | |
| Monad m => RefInput (A' m) File Source # | |
| Monad m => RefInput (A' m) UWExe Source # | |
| Monad m => RefInput (A' m) UWLib Source # | |
| Monad m => RefInput (UrpGen m) File Source # | |
| Monad m => RefInput (A' m) (CommandGen' m) 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
Declare that current recipe produces item x.
Add variables vs to tracking list of the current recipe
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
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