Commit 4d6ebdd0 authored by Adam Vogt's avatar Adam Vogt

add `Description :` field for haddock

descriptions are copied from README mostly, but a couple
were missing from there
parent 4f162ffc
{-# LANGUAGE PatternGuards #-}
{- | very approximate completion. Seems to generate what is required by
{- | Description : generates tab-completion options
very approximate completion. Seems to generate what is required by
<http://ipython.org/ipython-doc/dev/development/messaging.html#complete>,
but for whatever reason nothing gets added when the liftIO below prints
stuff like:
......
{-# LANGUAGE QuasiQuotes #-}
-- | Description : IPython configuration files are compiled-into IHaskell
module IHaskell.Config (ipython, notebook, console, qtconsole, customjs) where
import Data.String.Here
......
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoImplicitPrelude #-}
-- | This module exports all functions used for evaluation of IHaskell input.
{- | Description : Wrapper around GHC API, exposing a single `evaluate` interface that runs
a statement, declaration, import, or directive.
This module exports all functions used for evaluation of IHaskell input.
-}
module IHaskell.Eval.Evaluate (
interpret, evaluate, Interpreter, liftIO
) where
......
-- | Description : Shell scripting wrapper using @Shelly@ for the @notebook@, @setup@, and
-- @console@ commands.
module IHaskell.IPython (
runIHaskell,
setupIPythonProfile,
......
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoImplicitPrelude #-}
-- | This module is responsible for converting from low-level ByteStrings
-- | obtained from the 0MQ sockets into Messages. The only exposed function is
-- | `parseMessage`, which should only be used in the low-level 0MQ interface.
-- | Description : Parsing messages received from IPython
--
-- This module is responsible for converting from low-level ByteStrings
-- obtained from the 0MQ sockets into Messages. The only exposed function is
-- `parseMessage`, which should only be used in the low-level 0MQ interface.
module IHaskell.Message.Parser (parseMessage) where
import ClassyPrelude
......
-- | Generate, parse, and pretty print UUIDs for use with IPython.
-- | Description : UUID generator and data structure
--
-- Generate, parse, and pretty print UUIDs for use with IPython.
module IHaskell.Message.UUID (
UUID,
random, randoms,
......
{-# LANGUAGE CPP #-}
-- | This module contains the @ToJSON@ instance for @Message@.
-- | Description : @ToJSON@ for Messages
--
-- This module contains the @ToJSON@ instance for @Message@.
module IHaskell.Message.Writer (
ToJSON(..)
) where
......
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
-- | Description : All message type definitions.
module IHaskell.Types (
Profile (..),
Message (..),
......
-- | The "ZeroMQ" module abstracts away the low-level 0MQ based interface with IPython,
-- | Description : Low-level ZeroMQ communication wrapper.
--
-- The "ZeroMQ" module abstracts away the low-level 0MQ based interface with IPython,
-- replacing it instead with a Haskell Channel based interface. The `serveProfile` function
-- takes a IPython profile specification and returns the channel interface to use.
module IHaskell.ZeroMQ (
......
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
-- | Description : Argument parsing and basic messaging loop, using Haskell
-- Chans to communicate with the ZeroMQ sockets.
module Main where
import ClassyPrelude hiding (liftIO)
import Control.Concurrent.Chan
import Data.Aeson
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment