purescript-0.15.7: PureScript Programming Language Compiler
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.PureScript.Make.Actions

Synopsis

Documentation

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

  • getInputTimestampsAndHashes :: ModuleName -> m (Either RebuildPolicy (Map FilePath (UTCTime, m ContentHash)))

    Get the timestamps and content hashes for the input files for a module. The content hash is returned as a monadic action so that the file does not have to be read if it's not necessary.

  • getOutputTimestamp :: ModuleName -> m (Maybe UTCTime)

    Get the time this module was last compiled, provided that all of the requested codegen targets were also produced then. The defaultMakeActions implementation uses the modification time of the externs file, because the externs file is written first and we always write one. If there is no externs file, or if any of the requested codegen targets were not produced the last time this module was compiled, this function must return Nothing; this indicates that the module will have to be recompiled.

  • readExterns :: ModuleName -> m (FilePath, Maybe ExternsFile)

    Read the externs file for a module as a string and also return the actual path for the file.

  • codegen :: Module Ann -> Module -> ExternsFile -> SupplyT m ()

    Run the code generator for the module and write any required output files.

  • ffiCodegen :: Module Ann -> m ()

    Check ffi and print it in the output directory.

  • progress :: ProgressMessage -> m ()

    Respond to a progress update.

  • readCacheDb :: m CacheDb

    Read the cache database (which contains timestamps and hashes for input files) from some external source, e.g. a file on disk.

  • writeCacheDb :: CacheDb -> m ()

    Write the given cache database to some external source (e.g. a file on disk).

  • writePackageJson :: m ()

    Write to the output directory the package.json file allowing Node.js to load .js files as ES modules.

  • outputPrimDocs :: m ()

    If generating docs, output the documentation for the Prim modules

renderProgressMessage :: Text -> ProgressMessage -> Text Source #

Render a progress message

buildMakeActions Source #

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.

checkForeignDecls :: Module ann -> FilePath -> Make (Either MultipleErrors (ForeignModuleType, Set Ident)) Source #

Check that the declarations in a given PureScript module match with those in its corresponding foreign module.

cacheDbFile :: FilePath -> FilePath Source #

Given the output directory, determines the location for the CacheDb file

readCacheDb' Source #

Arguments

:: (MonadIO m, MonadError MultipleErrors m) 
=> FilePath

The path to the output directory

-> m CacheDb 

writeCacheDb' Source #

Arguments

:: (MonadIO m, MonadError MultipleErrors m) 
=> FilePath

The path to the output directory

-> CacheDb

The CacheDb to be written

-> m () 

ffiCodegen' :: Map ModuleName FilePath -> Set CodegenTarget -> Maybe (ModuleName -> String -> FilePath) -> Module Ann -> Make () Source #

FFI check and codegen action. If path maker is supplied copies foreign module to the output.