purescript-0.9.1: PureScript Programming Language Compiler

Safe HaskellNone
LanguageHaskell98

Language.PureScript.Make

Contents

Synopsis

Make API

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 = String Source #

Generated code for an externs file.

make :: forall m. (Monad m, MonadBaseControl IO m, MonadReader Options m, MonadError MultipleErrors m, MonadWriter MultipleErrors m) => MakeActions m -> [Module] -> m [ExternsFile] Source #

Compiles in "make" mode, compiling each module separately to a js files and an externs 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

newtype Make a Source #

A monad for running make actions

Instances

Monad Make Source # 

Methods

(>>=) :: Make a -> (a -> Make b) -> Make b #

(>>) :: Make a -> Make b -> Make b #

return :: a -> Make a #

fail :: String -> Make a #

Functor Make Source # 

Methods

fmap :: (a -> b) -> Make a -> Make b #

(<$) :: a -> Make b -> Make a #

Applicative Make Source # 

Methods

pure :: a -> Make a #

(<*>) :: Make (a -> b) -> Make a -> Make b #

(*>) :: Make a -> Make b -> Make b #

(<*) :: Make a -> Make b -> Make a #

MonadIO Make Source # 

Methods

liftIO :: IO a -> Make a #

MonadError MultipleErrors Make Source # 
MonadBaseControl IO Make Source # 

Associated Types

type StM (Make :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase Make IO -> IO a) -> Make a #

restoreM :: StM Make a -> Make a #

MonadBase IO Make Source # 

Methods

liftBase :: IO α -> Make α #

MonadReader Options Make Source # 

Methods

ask :: Make Options #

local :: (Options -> Options) -> Make a -> Make a #

reader :: (Options -> a) -> Make a #

MonadWriter MultipleErrors Make Source # 
type StM Make a Source # 

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.

readTextFile :: FilePath -> Make String Source #

Read a text file in the Make monad, capturing any errors using the MonadError instance.

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.

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.