ghc-7.6.1: The GHC API

Safe HaskellNone

Vectorise.Monad.Base

Contents

Description

The Vectorisation monad.

Synopsis

The Vectorisation Monad

data VResult a Source

Vectorisation can either succeed with new envionment and a value, or return with failure (including a description of the reason for failure).

Constructors

Yes GlobalEnv LocalEnv a 
No SDoc 

newtype VM a Source

Constructors

VM 

Fields

runVM :: Builtins -> GlobalEnv -> LocalEnv -> DsM (VResult a)
 

Lifting

liftDs :: DsM a -> VM aSource

Lift a desugaring computation into the vectorisation monad.

Error Handling

cantVectorise :: DynFlags -> String -> SDoc -> aSource

Throw a pgmError saying we can't vectorise something.

maybeCantVectorise :: DynFlags -> String -> SDoc -> Maybe a -> aSource

Like fromJust, but pgmError on Nothing.

maybeCantVectoriseM :: (Monad m, HasDynFlags m) => String -> SDoc -> m (Maybe a) -> m aSource

Like maybeCantVectorise but in a Monad.

Debugging

emitVt :: String -> SDoc -> VM ()Source

Output a trace message if -ddump-vt-trace is active.

traceVt :: String -> SDoc -> VM ()Source

Output a trace message if -ddump-vt-trace is active.

dumpOptVt :: DynFlag -> String -> SDoc -> VM ()Source

Dump the given program conditionally.

dumpVt :: String -> SDoc -> VM ()Source

Dump the given program unconditionally.

Control

noV :: SDoc -> VM aSource

Return some result saying we've failed.

traceNoV :: String -> SDoc -> VM aSource

Like traceNoV but also emit some trace message to stderr.

ensureV :: SDoc -> Bool -> VM ()Source

If True then carry on, otherwise fail.

traceEnsureV :: String -> SDoc -> Bool -> VM ()Source

Like ensureV but if we fail then emit some trace message to stderr.

onlyIfV :: SDoc -> Bool -> VM a -> VM aSource

If True then return the first argument, otherwise fail.

tryV :: VM a -> VM (Maybe a)Source

Try some vectorisation computaton.

If it succeeds then return Just the result; otherwise, return Nothing without emitting a failure message.

tryErrV :: VM a -> VM (Maybe a)Source

Try some vectorisation computaton.

If it succeeds then return Just the result; otherwise, return Nothing after emitting a failure message.

maybeV :: SDoc -> VM (Maybe a) -> VM aSource

If Just then return the value, otherwise fail.

traceMaybeV :: String -> SDoc -> VM (Maybe a) -> VM aSource

Like maybeV but emit a message to stderr if we fail.

orElseV :: VM a -> VM a -> VM aSource

Try the first computation,

  • if it succeeds then take the returned value, * if it fails then run the second computation instead without emitting a failure message.

orElseErrV :: VM a -> VM a -> VM aSource

Try the first computation,

  • if it succeeds then take the returned value, * if it fails then run the second computation instead while emitting a failure message.

fixV :: (a -> VM a) -> VM aSource

Fixpoint in the vectorisation monad.