| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Language.PureScript.Make
- data RebuildPolicy
- data ProgressMessage = CompilingModule ModuleName
- renderProgressMessage :: ProgressMessage -> String
- data MakeActions m = MakeActions {- getInputTimestamp :: ModuleName -> m (Either RebuildPolicy (Maybe UTCTime))
- getOutputTimestamp :: ModuleName -> m (Maybe UTCTime)
- readExterns :: ModuleName -> m (FilePath, Externs)
- codegen :: Module Ann -> Environment -> Externs -> SupplyT m ()
- progress :: ProgressMessage -> m ()
 
- type Externs = ByteString
- rebuildModule :: forall m. (Monad m, MonadBaseControl IO m, MonadError MultipleErrors m, MonadWriter MultipleErrors m) => MakeActions m -> [ExternsFile] -> Module -> m ExternsFile
- make :: forall m. (Monad m, MonadBaseControl IO m, MonadError MultipleErrors m, MonadWriter MultipleErrors m) => MakeActions m -> [Module] -> m [ExternsFile]
- newtype Make a = Make {}
- runMake :: Options -> Make a -> IO (Either MultipleErrors a, MultipleErrors)
- makeIO :: (IOError -> ErrorMessage) -> IO a -> Make a
- readTextFile :: FilePath -> Make ByteString
- buildMakeActions :: FilePath -> Map ModuleName (Either RebuildPolicy FilePath) -> Map ModuleName FilePath -> Bool -> MakeActions Make
- inferForeignModules :: forall m. MonadIO m => Map ModuleName (Either RebuildPolicy FilePath) -> m (Map ModuleName FilePath)
Make API
data RebuildPolicy Source #
Determines when to rebuild a module
Constructors
| RebuildNever | Never rebuild this module | 
| RebuildAlways | Always rebuild this module | 
Instances
data ProgressMessage Source #
Progress messages from the make process
Constructors
| CompilingModule ModuleName | Compilation started for the specified module | 
Instances
renderProgressMessage :: ProgressMessage -> String Source #
Render a progress message
data MakeActions m Source #
Actions that require implementations when running in "make" mode.
This type exists to make two things abstract:
- The particular backend being used (JavaScript, C++11, etc.)
- The details of how files are read/written etc.
Constructors
| MakeActions | |
| Fields 
 | |
type Externs = ByteString Source #
Generated code for an externs file.
rebuildModule :: forall m. (Monad m, MonadBaseControl IO m, MonadError MultipleErrors m, MonadWriter MultipleErrors m) => MakeActions m -> [ExternsFile] -> Module -> m ExternsFile Source #
Rebuild a single module.
This function is used for fast-rebuild workflows (PSCi and psc-ide are examples).
make :: forall m. (Monad m, MonadBaseControl IO m, MonadError MultipleErrors m, MonadWriter MultipleErrors m) => MakeActions m -> [Module] -> m [ExternsFile] Source #
Compiles in "make" mode, compiling each module separately to a .js file and an externs.json file.
If timestamps have not changed, the externs file can be used to provide the module's types without having to typecheck the module again.
Implementation of Make API using files on disk
runMake :: Options -> Make a -> IO (Either MultipleErrors a, MultipleErrors) Source #
Execute a Make monad, returning either errors, or the result of the compile plus any warnings.
makeIO :: (IOError -> ErrorMessage) -> IO a -> Make a Source #
Run an IO action in the Make monad, by specifying how IO errors should
 be rendered as ErrorMessage values.
readTextFile :: FilePath -> Make ByteString Source #
Read a text file in the Make monad, capturing any errors using the
 MonadError instance.
Arguments
| :: FilePath | the output directory | 
| -> Map ModuleName (Either RebuildPolicy FilePath) | a map between module names and paths to the file containing the PureScript module | 
| -> Map ModuleName FilePath | a map between module name and the file containing the foreign javascript for the module | 
| -> Bool | Generate a prefix comment? | 
| -> MakeActions Make | 
A set of make actions that read and write modules from the given directory.
inferForeignModules :: forall m. MonadIO m => Map ModuleName (Either RebuildPolicy FilePath) -> m (Map ModuleName FilePath) Source #
Infer the module name for a module by looking for the same filename with a .js extension.