Safe Haskell | Safe |
---|---|
Language | Haskell98 |
Development.Cake3.Types
- data Variable = Variable {}
- data Tool = Tool {}
- type Command = [CommandPiece]
- data CommandPiece
- return_text :: Monad m => String -> m [CommandPiece]
- return_file :: Monad m => File -> m [CommandPiece]
- data Flag
- data Recipe = Recipe {}
- emptyRecipe :: String -> Recipe
- addPrerequisites :: Set File -> Recipe -> Recipe
- addPrerequisite :: File -> Recipe -> Recipe
- type Target = Set File
- groupSet :: (Ord k, Ord x, Foldable t) => (x -> Set k) -> t x -> Map k (Set x)
- groupRecipes :: Foldable t => t Recipe -> Map File (Set Recipe)
- flattern :: [Set x] -> [x]
- applyPlacement' :: Eq x => [File] -> Map File x -> [x]
- filterRecipesByTools :: Foldable t => [Tool] -> t Recipe -> Set Recipe
- filterRecipesByTargets :: (Foldable t, Foldable t2) => t2 File -> t Recipe -> Set Recipe
- filterRecipesByToolsDeep :: [Tool] -> Set Recipe -> Set Recipe
- applyPlacement :: Foldable t => [File] -> t Recipe -> [Recipe]
- transformRecipes :: Applicative m => (Recipe -> m (Set Recipe)) -> Set Recipe -> m (Set Recipe)
- transformRecipesM_ :: (Monad m, Foldable t) => (Recipe -> m ()) -> t Recipe -> m ()
- queryVariables :: Foldable t => t Recipe -> Set Variable
- queryVariablesE :: Foldable t => t Recipe -> Either String (Set Variable)
- queryTargets :: Foldable t => t Recipe -> Set File
- queryPrereq :: Foldable t => t Recipe -> Set File
- var :: String -> Maybe String -> Variable
- intermediateFiles :: Foldable t => t Recipe -> Set File
- tool :: String -> Tool
- makevar :: String -> String -> Variable
- extvar :: String -> Variable
- make :: Variable
- data ModuleLocation = ModuleLocation {}
- toplevelModule :: ModuleLocation
- type File = FileT ModuleLocation FilePath
- file' :: ModuleLocation -> FilePath -> File
- fileModule :: File -> File
- dottify :: FilePath -> FilePath
- topRel :: File -> FilePath
- wayback :: FilePath -> FilePath
- route :: File -> File -> FilePath
- escapeFile :: File -> FilePath
Documentation
The representation of Makefile variable.
Constructors
Variable | |
The representation a tool used by the Makefile's recipe. Typical example
are gcc
or bison
type Command = [CommandPiece] Source #
Command represents OS command line and consists of a list of fragments. Each fragment is either text (may contain spaces) or FilePath (spaces should be escaped)
data CommandPiece Source #
Instances
return_text :: Monad m => String -> m [CommandPiece] Source #
return_file :: Monad m => File -> m [CommandPiece] Source #
Constructors
Phony | |
Intermediate |
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
Constructors
Recipe | |
Fields
|
emptyRecipe :: String -> Recipe Source #
transformRecipes :: Applicative m => (Recipe -> m (Set Recipe)) -> Set Recipe -> m (Set Recipe) Source #
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.
data ModuleLocation Source #
Constructors
ModuleLocation | |
Instances
Eq ModuleLocation Source # | |
Data ModuleLocation Source # | |
Ord ModuleLocation Source # | |
Show ModuleLocation Source # | |
EmbedDecl File Source # | |
SrcDecl File Source # | |
LinkDecl File Source # | |
ModuleDecl File Source # | |
Monad m => RefOutput m File Source # | |
Monad m => LibraryDecl m File Source # | |
RefOutput m File => RefOutput m (m File) Source # | |
Monad m => RefOutput m (Set File) Source # | |
Monad m => RefOutput m [File] Source # | |
Monad m => LibraryDecl m (m File) Source # | |
Monad m => LibraryDecl m [File] Source # | |
Monad m => RefInput (A' m) File Source # | |
Monad m => RefInput (UrpGen m) File Source # | |
LinkDecl (File, String) Source # | |
ModuleDecl (File, File) Source # | |
SrcDecl (File, String, String) 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
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
fileModule :: File -> File Source #
Path to the module (a directory), which have originally declared the file
topRel :: File -> FilePath Source #
Returns the path to the file, relative to the top-level directory (the place, where the target Makefile is located)
wayback :: FilePath -> FilePath Source #
Converts path x
to the back-path, consisting of '..' directories
route :: File -> File -> FilePath Source #
Returns path from file s
to t
, via the top-level directory
escapeFile :: File -> FilePath Source #
Convert File back to FilePath with escaped spaces