summaryrefslogtreecommitdiff
path: root/compiler
diff options
context:
space:
mode:
authorAustin Seipp <austin@well-typed.com>2014-08-20 03:43:14 -0500
committerAustin Seipp <austin@well-typed.com>2014-08-20 03:47:36 -0500
commit8a8ead0e467bb6d1ec40d5db3efd76fbf18c913c (patch)
treed0a5d60dc46a23939cfd2301229cfa645ca0b50c /compiler
parent07d01c9f77b510c6e1d64e090f6ff008d9fb5d56 (diff)
downloadhaskell-8a8ead0e467bb6d1ec40d5db3efd76fbf18c913c.tar.gz
hsSyn: detabify/dewhitespace HsLit
Signed-off-by: Austin Seipp <austin@well-typed.com>
Diffstat (limited to 'compiler')
-rw-r--r--compiler/hsSyn/HsLit.lhs112
1 files changed, 52 insertions, 60 deletions
diff --git a/compiler/hsSyn/HsLit.lhs b/compiler/hsSyn/HsLit.lhs
index a4749dd730..a766e40a9d 100644
--- a/compiler/hsSyn/HsLit.lhs
+++ b/compiler/hsSyn/HsLit.lhs
@@ -5,22 +5,14 @@
\section[HsLit]{Abstract syntax: source-language literals}
\begin{code}
-{-# OPTIONS_GHC -fno-warn-tabs #-}
--- The above warning supression flag is a temporary kludge.
--- While working on this module you are encouraged to remove it and
--- detab the module (please do the detabbing in a separate patch). See
--- http://ghc.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#TabsvsSpaces
--- for details
-
{-# LANGUAGE CPP, DeriveDataTypeable #-}
-
module HsLit where
#include "HsVersions.h"
import {-# SOURCE #-} HsExpr( SyntaxExpr, pprExpr )
import BasicTypes ( FractionalLit(..) )
-import Type ( Type, Kind )
+import Type ( Type, Kind )
import Outputable
import FastString
@@ -30,80 +22,80 @@ import Data.Data
%************************************************************************
-%* *
+%* *
\subsection{Annotating the syntax}
-%* *
+%* *
%************************************************************************
\begin{code}
type PostTcKind = Kind
-type PostTcType = Type -- Used for slots in the abstract syntax
- -- where we want to keep slot for a type
- -- to be added by the type checker...but
- -- before typechecking it's just bogus
+type PostTcType = Type -- Used for slots in the abstract syntax
+ -- where we want to keep slot for a type
+ -- to be added by the type checker...but
+ -- before typechecking it's just bogus
-placeHolderType :: PostTcType -- Used before typechecking
+placeHolderType :: PostTcType -- Used before typechecking
placeHolderType = panic "Evaluated the place holder for a PostTcType"
-placeHolderKind :: PostTcKind -- Used before typechecking
+placeHolderKind :: PostTcKind -- Used before typechecking
placeHolderKind = panic "Evaluated the place holder for a PostTcKind"
\end{code}
%************************************************************************
-%* *
+%* *
\subsection[HsLit]{Literals}
-%* *
+%* *
%************************************************************************
\begin{code}
data HsLit
- = HsChar Char -- Character
- | HsCharPrim Char -- Unboxed character
- | HsString FastString -- String
- | HsStringPrim ByteString -- Packed bytes
- | HsInt Integer -- Genuinely an Int; arises from TcGenDeriv,
- -- and from TRANSLATION
+ = HsChar Char -- Character
+ | HsCharPrim Char -- Unboxed character
+ | HsString FastString -- String
+ | HsStringPrim ByteString -- Packed bytes
+ | HsInt Integer -- Genuinely an Int; arises from TcGenDeriv,
+ -- and from TRANSLATION
| HsIntPrim Integer -- literal Int#
| HsWordPrim Integer -- literal Word#
| HsInt64Prim Integer -- literal Int64#
| HsWord64Prim Integer -- literal Word64#
- | HsInteger Integer Type -- Genuinely an integer; arises only from TRANSLATION
- -- (overloaded literals are done with HsOverLit)
- | HsRat FractionalLit Type -- Genuinely a rational; arises only from TRANSLATION
- -- (overloaded literals are done with HsOverLit)
- | HsFloatPrim FractionalLit -- Unboxed Float
- | HsDoublePrim FractionalLit -- Unboxed Double
+ | HsInteger Integer Type -- Genuinely an integer; arises only from TRANSLATION
+ -- (overloaded literals are done with HsOverLit)
+ | HsRat FractionalLit Type -- Genuinely a rational; arises only from TRANSLATION
+ -- (overloaded literals are done with HsOverLit)
+ | HsFloatPrim FractionalLit -- Unboxed Float
+ | HsDoublePrim FractionalLit -- Unboxed Double
deriving (Data, Typeable)
instance Eq HsLit where
- (HsChar x1) == (HsChar x2) = x1==x2
- (HsCharPrim x1) == (HsCharPrim x2) = x1==x2
- (HsString x1) == (HsString x2) = x1==x2
+ (HsChar x1) == (HsChar x2) = x1==x2
+ (HsCharPrim x1) == (HsCharPrim x2) = x1==x2
+ (HsString x1) == (HsString x2) = x1==x2
(HsStringPrim x1) == (HsStringPrim x2) = x1==x2
- (HsInt x1) == (HsInt x2) = x1==x2
+ (HsInt x1) == (HsInt x2) = x1==x2
(HsIntPrim x1) == (HsIntPrim x2) = x1==x2
(HsWordPrim x1) == (HsWordPrim x2) = x1==x2
(HsInt64Prim x1) == (HsInt64Prim x2) = x1==x2
(HsWord64Prim x1) == (HsWord64Prim x2) = x1==x2
(HsInteger x1 _) == (HsInteger x2 _) = x1==x2
- (HsRat x1 _) == (HsRat x2 _) = x1==x2
+ (HsRat x1 _) == (HsRat x2 _) = x1==x2
(HsFloatPrim x1) == (HsFloatPrim x2) = x1==x2
(HsDoublePrim x1) == (HsDoublePrim x2) = x1==x2
_ == _ = False
-data HsOverLit id -- An overloaded literal
+data HsOverLit id -- An overloaded literal
= OverLit {
- ol_val :: OverLitVal,
- ol_rebindable :: Bool, -- Note [ol_rebindable]
- ol_witness :: SyntaxExpr id, -- Note [Overloaded literal witnesses]
- ol_type :: PostTcType }
+ ol_val :: OverLitVal,
+ ol_rebindable :: Bool, -- Note [ol_rebindable]
+ ol_witness :: SyntaxExpr id, -- Note [Overloaded literal witnesses]
+ ol_type :: PostTcType }
deriving (Data, Typeable)
data OverLitVal
- = HsIntegral !Integer -- Integer-looking literals;
- | HsFractional !FractionalLit -- Frac-looking literals
- | HsIsString !FastString -- String-looking literals
+ = HsIntegral !Integer -- Integer-looking literals;
+ | HsFractional !FractionalLit -- Frac-looking literals
+ | HsIsString !FastString -- String-looking literals
deriving (Data, Typeable)
overLitType :: HsOverLit a -> Type
@@ -112,7 +104,7 @@ overLitType = ol_type
Note [ol_rebindable]
~~~~~~~~~~~~~~~~~~~~
-The ol_rebindable field is True if this literal is actually
+The ol_rebindable field is True if this literal is actually
using rebindable syntax. Specifically:
False iff ol_witness is the standard one
@@ -128,10 +120,10 @@ Note [Overloaded literal witnesses]
*Before* type checking, the SyntaxExpr in an HsOverLit is the
name of the coercion function, 'fromInteger' or 'fromRational'.
*After* type checking, it is a witness for the literal, such as
- (fromInteger 3) or lit_78
+ (fromInteger 3) or lit_78
This witness should replace the literal.
-This dual role is unusual, because we're replacing 'fromInteger' with
+This dual role is unusual, because we're replacing 'fromInteger' with
a call to fromInteger. Reason: it allows commoning up of the fromInteger
calls, which wouldn't be possible if the desguarar made the application.
@@ -167,28 +159,28 @@ instance Ord OverLitVal where
\begin{code}
instance Outputable HsLit where
- -- Use "show" because it puts in appropriate escapes
- ppr (HsChar c) = pprHsChar c
- ppr (HsCharPrim c) = pprHsChar c <> char '#'
- ppr (HsString s) = pprHsString s
+ -- Use "show" because it puts in appropriate escapes
+ ppr (HsChar c) = pprHsChar c
+ ppr (HsCharPrim c) = pprHsChar c <> char '#'
+ ppr (HsString s) = pprHsString s
ppr (HsStringPrim s) = pprHsBytes s <> char '#'
- ppr (HsInt i) = integer i
- ppr (HsInteger i _) = integer i
- ppr (HsRat f _) = ppr f
- ppr (HsFloatPrim f) = ppr f <> char '#'
+ ppr (HsInt i) = integer i
+ ppr (HsInteger i _) = integer i
+ ppr (HsRat f _) = ppr f
+ ppr (HsFloatPrim f) = ppr f <> char '#'
ppr (HsDoublePrim d) = ppr d <> text "##"
- ppr (HsIntPrim i) = integer i <> char '#'
- ppr (HsWordPrim w) = integer w <> text "##"
+ ppr (HsIntPrim i) = integer i <> char '#'
+ ppr (HsWordPrim w) = integer w <> text "##"
ppr (HsInt64Prim i) = integer i <> text "L#"
ppr (HsWord64Prim w) = integer w <> text "L##"
-- in debug mode, print the expression that it's resolved to, too
instance OutputableBndr id => Outputable (HsOverLit id) where
- ppr (OverLit {ol_val=val, ol_witness=witness})
- = ppr val <+> (ifPprDebug (parens (pprExpr witness)))
+ ppr (OverLit {ol_val=val, ol_witness=witness})
+ = ppr val <+> (ifPprDebug (parens (pprExpr witness)))
instance Outputable OverLitVal where
- ppr (HsIntegral i) = integer i
+ ppr (HsIntegral i) = integer i
ppr (HsFractional f) = ppr f
ppr (HsIsString s) = pprHsString s
\end{code}