diff options
5 files changed, 51 insertions, 51 deletions
| diff --git a/libraries/template-haskell/Language/Haskell/TH.hs b/libraries/template-haskell/Language/Haskell/TH.hs index 76aae272bd..934384d423 100644 --- a/libraries/template-haskell/Language/Haskell/TH.hs +++ b/libraries/template-haskell/Language/Haskell/TH.hs @@ -41,15 +41,15 @@ module Language.Haskell.TH(          TExp, unType,          -- * Names -        Name, NameSpace,	-- Abstract +        Name, NameSpace,        -- Abstract          -- ** Constructing names          mkName,         -- :: String -> Name          newName,        -- :: String -> Q Name          -- ** Deconstructing names -        nameBase,	-- :: Name -> String -        nameModule,	-- :: Name -> Maybe String +        nameBase,       -- :: Name -> String +        nameModule,     -- :: Name -> Maybe String          -- ** Built-in names -        tupleTypeName, tupleDataName,	-- Int -> Name +        tupleTypeName, tupleDataName,   -- Int -> Name          unboxedTupleTypeName, unboxedTupleDataName, -- :: Int -> Name      -- * The algebraic data types diff --git a/libraries/template-haskell/Language/Haskell/TH/Lib.hs b/libraries/template-haskell/Language/Haskell/TH/Lib.hs index 4d4f079719..2cfa4b3853 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Lib.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Lib.hs @@ -171,7 +171,7 @@ patG ss = do { ss' <- sequence ss; return (PatG ss') }  patGE :: [StmtQ] -> ExpQ -> Q (Guard, Exp)  patGE ss e = do { ss' <- sequence ss; -		  e'  <- e; +                  e'  <- e;                    return (PatG ss', e') }  ------------------------------------------------------------------------------- diff --git a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs index 81bf3c1d66..ce0992c487 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs @@ -52,9 +52,9 @@ instance Ppr Info where      ppr (FamilyI d is) = ppr d $$ vcat (map ppr is)      ppr (PrimTyConI name arity is_unlifted)        = text "Primitive" -	<+> (if is_unlifted then text "unlifted" else empty) -	<+> text "type constructor" <+> quotes (ppr name) -	<+> parens (text "arity" <+> int arity) +        <+> (if is_unlifted then text "unlifted" else empty) +        <+> text "type constructor" <+> quotes (ppr name) +        <+> parens (text "arity" <+> int arity)      ppr (ClassOpI v ty cls fix)        = text "Class op from" <+> ppr cls <> colon <+>          vcat [ppr_sig v ty, pprFixity v fix] @@ -330,8 +330,8 @@ ppr_dec _ (RoleAnnotD name roles)  ppr_data :: Doc -> Cxt -> Name -> Doc -> [Con] -> [Name] -> Doc  ppr_data maybeInst ctxt t argsDoc cs decs    = sep [text "data" <+> maybeInst -    	    <+> pprCxt ctxt -    	    <+> ppr t <+> argsDoc, +            <+> pprCxt ctxt +            <+> ppr t <+> argsDoc,           nest nestDepth (sep (pref $ map ppr cs)),           if null decs             then empty @@ -346,14 +346,14 @@ ppr_data maybeInst ctxt t argsDoc cs decs  ppr_newtype :: Doc -> Cxt -> Name -> Doc -> Con -> [Name] -> Doc  ppr_newtype maybeInst ctxt t argsDoc c decs    = sep [text "newtype" <+> maybeInst -    	    <+> pprCxt ctxt -    	    <+> ppr t <+> argsDoc, +            <+> pprCxt ctxt +            <+> ppr t <+> argsDoc,           nest 2 (char '=' <+> ppr c),           if null decs -       	   then empty -       	   else nest nestDepth -       	        $ text "deriving" -       	          <+> parens (hsep $ punctuate comma $ map ppr decs)] +           then empty +           else nest nestDepth +                $ text "deriving" +                  <+> parens (hsep $ punctuate comma $ map ppr decs)]  ppr_tySyn :: Doc -> Name -> Doc -> Type -> Doc  ppr_tySyn maybeInst t argsDoc rhs @@ -507,7 +507,7 @@ pprTyApp (PromotedTupleT n, args)   | length args == n = quoteParens (sep (punctuate comma (map ppr args)))  pprTyApp (fun, args) = pprParendType fun <+> sep (map pprParendType args) -pprFunArgType :: Type -> Doc	-- Should really use a precedence argument +pprFunArgType :: Type -> Doc    -- Should really use a precedence argument  -- Everything except forall and (->) binds more tightly than (->)  pprFunArgType ty@(ForallT {})                 = parens (ppr ty)  pprFunArgType ty@((ArrowT `AppT` _) `AppT` _) = parens (ppr ty) diff --git a/libraries/template-haskell/Language/Haskell/TH/PprLib.hs b/libraries/template-haskell/Language/Haskell/TH/PprLib.hs index 22b336ae81..ce456d7cdf 100644 --- a/libraries/template-haskell/Language/Haskell/TH/PprLib.hs +++ b/libraries/template-haskell/Language/Haskell/TH/PprLib.hs @@ -4,32 +4,32 @@  module Language.Haskell.TH.PprLib ( -	-- * The document type +        -- * The document type          Doc,            -- Abstract, instance of Show          PprM, -	-- * Primitive Documents +        -- * Primitive Documents          empty,          semi, comma, colon, space, equals, arrow,          lparen, rparen, lbrack, rbrack, lbrace, rbrace, -	-- * Converting values into documents +        -- * Converting values into documents          text, char, ptext,          int, integer, float, double, rational, -	-- * Wrapping documents in delimiters +        -- * Wrapping documents in delimiters          parens, brackets, braces, quotes, doubleQuotes, -	-- * Combining documents +        -- * Combining documents          (<>), (<+>), hcat, hsep,           ($$), ($+$), vcat,           sep, cat,           fsep, fcat,  -	nest, +        nest,          hang, punctuate, -	-- * Predicates on documents -	isEmpty, +        -- * Predicates on documents +        isEmpty,      to_HPJ_Doc, pprName, pprName'    ) where @@ -57,23 +57,23 @@ instance Show Doc where  isEmpty :: Doc    -> PprM Bool;  -- ^ Returns 'True' if the document is empty -empty   :: Doc;			-- ^ An empty document -semi	:: Doc;			-- ^ A ';' character -comma	:: Doc;			-- ^ A ',' character -colon	:: Doc;			-- ^ A ':' character -space	:: Doc;			-- ^ A space character -equals	:: Doc;			-- ^ A '=' character -arrow	:: Doc;			-- ^ A "->" string -lparen	:: Doc;			-- ^ A '(' character -rparen	:: Doc;			-- ^ A ')' character -lbrack	:: Doc;			-- ^ A '[' character -rbrack	:: Doc;			-- ^ A ']' character -lbrace	:: Doc;			-- ^ A '{' character -rbrace	:: Doc;			-- ^ A '}' character - -text	 :: String   -> Doc -ptext	 :: String   -> Doc -char 	 :: Char     -> Doc +empty   :: Doc;                 -- ^ An empty document +semi    :: Doc;                 -- ^ A ';' character +comma   :: Doc;                 -- ^ A ',' character +colon   :: Doc;                 -- ^ A ':' character +space   :: Doc;                 -- ^ A space character +equals  :: Doc;                 -- ^ A '=' character +arrow   :: Doc;                 -- ^ A "->" string +lparen  :: Doc;                 -- ^ A '(' character +rparen  :: Doc;                 -- ^ A ')' character +lbrack  :: Doc;                 -- ^ A '[' character +rbrack  :: Doc;                 -- ^ A ']' character +lbrace  :: Doc;                 -- ^ A '{' character +rbrace  :: Doc;                 -- ^ A '}' character + +text     :: String   -> Doc +ptext    :: String   -> Doc +char     :: Char     -> Doc  int      :: Int      -> Doc  integer  :: Integer  -> Doc  float    :: Float    -> Doc @@ -81,11 +81,11 @@ double   :: Double   -> Doc  rational :: Rational -> Doc -parens       :: Doc -> Doc; 	-- ^ Wrap document in @(...)@ -brackets     :: Doc -> Doc;  	-- ^ Wrap document in @[...]@ -braces	     :: Doc -> Doc;   	-- ^ Wrap document in @{...}@ -quotes	     :: Doc -> Doc;	-- ^ Wrap document in @\'...\'@ -doubleQuotes :: Doc -> Doc;	-- ^ Wrap document in @\"...\"@ +parens       :: Doc -> Doc;     -- ^ Wrap document in @(...)@ +brackets     :: Doc -> Doc;     -- ^ Wrap document in @[...]@ +braces       :: Doc -> Doc;     -- ^ Wrap document in @{...}@ +quotes       :: Doc -> Doc;     -- ^ Wrap document in @\'...\'@ +doubleQuotes :: Doc -> Doc;     -- ^ Wrap document in @\"...\"@  -- Combining @Doc@ values @@ -96,7 +96,7 @@ hsep   :: [Doc] -> Doc;          -- ^List version of '<+>'  ($$)   :: Doc -> Doc -> Doc;     -- ^Above; if there is no                                  -- overlap it \"dovetails\" the two -($+$)   :: Doc -> Doc -> Doc;	 -- ^Above, without dovetailing. +($+$)   :: Doc -> Doc -> Doc;    -- ^Above, without dovetailing.  vcat   :: [Doc] -> Doc;          -- ^List version of '$$'  cat    :: [Doc] -> Doc;          -- ^ Either hcat or vcat @@ -109,7 +109,7 @@ nest   :: Int -> Doc -> Doc;     -- ^ Nested  -- GHC-specific ones. -hang :: Doc -> Int -> Doc -> Doc;	-- ^ @hang d1 n d2 = sep [d1, nest n d2]@ +hang :: Doc -> Int -> Doc -> Doc;       -- ^ @hang d1 n d2 = sep [d1, nest n d2]@  punctuate :: Doc -> [Doc] -> [Doc];      -- ^ @punctuate p [d1, ... dn] = [d1 \<> p, d2 \<> p, ... dn-1 \<> p, dn]@ @@ -141,7 +141,7 @@ instance Show Name where  data Name = Name OccName NameFlavour  data NameFlavour -  | NameU Int#			-- A unique local name +  | NameU Int#                  -- A unique local name  -}  to_HPJ_Doc :: Doc -> HPJ.Doc diff --git a/libraries/template-haskell/Language/Haskell/TH/Quote.hs b/libraries/template-haskell/Language/Haskell/TH/Quote.hs index b9c0d25d2b..618906d901 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Quote.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Quote.hs @@ -1,6 +1,6 @@  {-# LANGUAGE RankNTypes, ScopedTypeVariables #-}  module Language.Haskell.TH.Quote( -	QuasiQuoter(..), +        QuasiQuoter(..),          dataToQa, dataToExpQ, dataToPatQ,          quoteFile      ) where | 
