Safe Haskell | None |
---|---|
Language | Haskell98 |
The Vectorisation monad.
- data VResult a
- newtype VM a = VM {}
- liftDs :: DsM a -> VM a
- cantVectorise :: DynFlags -> String -> SDoc -> a
- maybeCantVectorise :: DynFlags -> String -> SDoc -> Maybe a -> a
- maybeCantVectoriseM :: (Monad m, HasDynFlags m) => String -> SDoc -> m (Maybe a) -> m a
- emitVt :: String -> SDoc -> VM ()
- traceVt :: String -> SDoc -> VM ()
- dumpOptVt :: DumpFlag -> String -> SDoc -> VM ()
- dumpVt :: String -> SDoc -> VM ()
- noV :: SDoc -> VM a
- traceNoV :: String -> SDoc -> VM a
- ensureV :: SDoc -> Bool -> VM ()
- traceEnsureV :: String -> SDoc -> Bool -> VM ()
- onlyIfV :: SDoc -> Bool -> VM a -> VM a
- tryV :: VM a -> VM (Maybe a)
- tryErrV :: VM a -> VM (Maybe a)
- maybeV :: SDoc -> VM (Maybe a) -> VM a
- traceMaybeV :: String -> SDoc -> VM (Maybe a) -> VM a
- orElseV :: VM a -> VM a -> VM a
- orElseErrV :: VM a -> VM a -> VM a
- fixV :: (a -> VM a) -> VM a
The Vectorisation Monad
Vectorisation can either succeed with new envionment and a value, or return with failure (including a description of the reason for failure).
Lifting
Error Handling
cantVectorise :: DynFlags -> String -> SDoc -> a Source
Throw a pgmError
saying we can't vectorise something.
maybeCantVectorise :: DynFlags -> String -> SDoc -> Maybe a -> a Source
Like fromJust
, but pgmError
on Nothing.
maybeCantVectoriseM :: (Monad m, HasDynFlags m) => String -> SDoc -> m (Maybe a) -> m a Source
Like maybeCantVectorise
but in a Monad
.
Debugging
Control
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 a Source
If True
then return the first argument, otherwise fail.
traceMaybeV :: String -> SDoc -> VM (Maybe a) -> VM a Source
Like maybeV
but emit a message to stderr if we fail.
orElseV :: VM a -> VM a -> VM a Source
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 a Source
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.