Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module exports all functions used for evaluation of IHaskell input.
Synopsis
- interpret :: String -> Bool -> Bool -> (Bool -> Interpreter a) -> IO a
- testInterpret :: Interpreter a -> IO a
- testEvaluate :: String -> IO ()
- evaluate :: KernelState -> String -> Publisher -> (KernelState -> [WidgetMsg] -> IO KernelState) -> Interpreter (KernelState, ErrorOccurred)
- flushWidgetMessages :: KernelState -> [WidgetMsg] -> (KernelState -> [WidgetMsg] -> IO KernelState) -> Interpreter KernelState
- type Interpreter = Ghc
- liftIO :: MonadIO m => IO a -> m a
- typeCleaner :: String -> String
- formatType :: String -> Display
- capturedIO :: Publisher -> KernelState -> IO a -> Interpreter Display
Documentation
interpret :: String -> Bool -> Bool -> (Bool -> Interpreter a) -> IO a Source #
Run an interpreting action. This is effectively runGhc with initialization
and importing. The allowedStdin
argument indicates whether stdin
is
handled specially, which cannot be done in a testing environment. The
needsSupportLibraries
argument indicates whether we want support libraries
to be imported, which is not the case during testing. The argument passed to
the action indicates whether the IHaskell library is available.
testInterpret :: Interpreter a -> IO a Source #
Interpreting function for testing.
testEvaluate :: String -> IO () Source #
Evaluation function for testing.
:: KernelState | The kernel state. |
-> String | Haskell code or other interpreter commands. |
-> Publisher | Function used to publish data outputs. |
-> (KernelState -> [WidgetMsg] -> IO KernelState) | Function to handle widget messages |
-> Interpreter (KernelState, ErrorOccurred) |
Evaluate some IPython input code.
flushWidgetMessages :: KernelState -> [WidgetMsg] -> (KernelState -> [WidgetMsg] -> IO KernelState) -> Interpreter KernelState Source #
type Interpreter = Ghc Source #
liftIO :: MonadIO m => IO a -> m a #
Lift a computation from the IO
monad.
This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations
(i.e. IO
is the base monad for the stack).
Example
import Control.Monad.Trans.State -- from the "transformers" library printState :: Show s => StateT s IO () printState = do state <- get liftIO $ print state
Had we omitted
, we would have ended up with this error:liftIO
• Couldn't match type ‘IO’ with ‘StateT s IO’ Expected type: StateT s IO () Actual type: IO ()
The important part here is the mismatch between StateT s IO ()
and
.IO
()
Luckily, we know of a function that takes an
and returns an IO
a(m a)
:
,
enabling us to run the program and see the expected results:liftIO
> evalStateT printState "hello" "hello" > evalStateT printState 3 3
typeCleaner :: String -> String Source #
formatType :: String -> Display Source #
capturedIO :: Publisher -> KernelState -> IO a -> Interpreter Display Source #