Repository : ssh://darcs.haskell.org//srv/darcs/packages/template-haskell

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/742f0578f42470eaded5131d2c7489d2f062feca

>---------------------------------------------------------------

commit 742f0578f42470eaded5131d2c7489d2f062feca
Author: Simon Peyton Jones <[email protected]>
Date:   Mon Jul 16 17:46:02 2012 +0100

    Reorganise the Language.Haskell.TH export list, so that it Haddocks better
    
    Thanks to Reiner Pope

>---------------------------------------------------------------

 Language/Haskell/TH.hs |   46 ++++++++++++++++++++++++++++++++++++----------
 1 files changed, 36 insertions(+), 10 deletions(-)

diff --git a/Language/Haskell/TH.hs b/Language/Haskell/TH.hs
index 8e36af7..bd04357 100644
--- a/Language/Haskell/TH.hs
+++ b/Language/Haskell/TH.hs
@@ -6,33 +6,59 @@ For other documentation, refer to:
 -}
 module Language.Haskell.TH(
        -- * The monad and its operations
-       Q, runQ,
-       report,           -- :: Bool -> String -> Q ()
+       Q,
+       runQ,
+        -- ** Administration: errors, locations and IO
+       reportError,              -- :: String -> Q ()
+       reportWarning,            -- :: String -> Q ()
+       report,                   -- :: Bool -> String -> Q ()
        recover,          -- :: Q a -> Q a -> Q a
-       reify,            -- :: Name -> Q Info
-       location,         -- :: Q Location
+       location,         -- :: Q Loc
+       Loc(..),
        runIO,            -- :: IO a -> Q a
-       lookupTypeName, lookupValueName,
-        isInstance, reifyInstances,
+       -- ** Querying the compiler
+       -- *** Reify
+       reify,            -- :: Name -> Q Info
+       Info(..),
+       InstanceDec,
+       ParentName,
+       Arity,
+       Unlifted,
+       -- *** Name lookup
+       lookupTypeName,  -- :: String -> Q (Maybe Name)
+       lookupValueName, -- :: String -> Q (Maybe Name)
+       -- *** Instance lookup
+       reifyInstances,
+       isInstance,
 
        -- * Names
        Name, NameSpace,        -- Abstract
+       -- ** Constructing names
        mkName,         -- :: String -> Name
        newName,        -- :: String -> Q Name
+       -- ** Deconstructing names
        nameBase,       -- :: Name -> String
        nameModule,     -- :: Name -> Maybe String
+       -- ** Built-in names
        tupleTypeName, tupleDataName,   -- Int -> Name
+       unboxedTupleTypeName, unboxedTupleDataName, -- :: Int -> Name
 
     -- * The algebraic data types
     -- | The lowercase versions (/syntax operators/) of these constructors are
     -- preferred to these constructors, since they compose better with
     -- quotations (@[| |]@) and splices (@$( ... )@)
-       Dec(..), Exp(..), Con(..), Type(..), TyVarBndr(..), TyLit(..), Kind, 
Cxt,
-       Pred(..), Match(..), Clause(..), Body(..), Guard(..), Stmt(..),
-       Range(..), Lit(..), Pat(..), FieldExp, FieldPat,
+
+    -- ** Declarations
+       Dec(..), Con(..), Clause(..), 
        Strict(..), Foreign(..), Callconv(..), Safety(..), Pragma(..),
-       Inline(..), InlineSpec(..), FunDep(..), FamFlavour(..), Info(..), 
Loc(..),
+       Inline(..), InlineSpec(..), FunDep(..), FamFlavour(..),
        Fixity(..), FixityDirection(..), defaultFixity, maxPrecedence,
+    -- ** Expressions
+        Exp(..), Match(..), Body(..), Guard(..), Stmt(..), Range(..), Lit(..),
+    -- ** Patterns
+        Pat(..), FieldExp, FieldPat,
+    -- ** Types
+        Type(..), TyVarBndr(..), TyLit(..), Kind, Cxt, Pred(..),
 
     -- * Library functions
     -- ** Abbreviations



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to