[commit: ghc] master: coreSyn: detabify/dewhitespace TrieMap (11f05c5)

git at git.haskell.org git at git.haskell.org
Wed Aug 20 08:47:49 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/11f05c538addda0e037c626d75de96a9eb477f94/ghc

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

commit 11f05c538addda0e037c626d75de96a9eb477f94
Author: Austin Seipp <austin at well-typed.com>
Date:   Wed Aug 20 03:29:49 2014 -0500

    coreSyn: detabify/dewhitespace TrieMap
    
    Signed-off-by: Austin Seipp <austin at well-typed.com>


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

11f05c538addda0e037c626d75de96a9eb477f94
 compiler/coreSyn/TrieMap.lhs | 67 ++++++++++++++++++++------------------------
 1 file changed, 30 insertions(+), 37 deletions(-)

diff --git a/compiler/coreSyn/TrieMap.lhs b/compiler/coreSyn/TrieMap.lhs
index 2744c5d..d552506 100644
--- a/compiler/coreSyn/TrieMap.lhs
+++ b/compiler/coreSyn/TrieMap.lhs
@@ -4,13 +4,6 @@
 %
 
 \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 RankNTypes, TypeFamilies #-}
 module TrieMap(
    CoreMap, emptyCoreMap, extendCoreMap, lookupCoreMap, foldCoreMap,
@@ -51,14 +44,14 @@ some neat handling of *binders*.  In effect they are deBruijn
 numbered on the fly.
 
 %************************************************************************
-%*									*
+%*                                                                      *
                    The TrieMap class
-%*									*
+%*                                                                      *
 %************************************************************************
 
 \begin{code}
-type XT a = Maybe a -> Maybe a	-- How to alter a non-existent elt (Nothing)
-     	    	       		--               or an existing elt (Just)
+type XT a = Maybe a -> Maybe a  -- How to alter a non-existent elt (Nothing)
+                                --               or an existing elt (Just)
 
 class TrieMap m where
    type Key m :: *
@@ -104,9 +97,9 @@ deMaybe (Just m) = m
 \end{code}
 
 %************************************************************************
-%*									*
+%*                                                                      *
                    IntMaps
-%*									*
+%*                                                                      *
 %************************************************************************
 
 \begin{code}
@@ -140,9 +133,9 @@ instance TrieMap UniqFM where
 
 
 %************************************************************************
-%*									*
+%*                                                                      *
                    Lists
-%*									*
+%*                                                                      *
 %************************************************************************
 
 If              m is a map from k -> val
@@ -216,9 +209,9 @@ foldMaybe k (Just a) b = k a b
 
 
 %************************************************************************
-%*									*
+%*                                                                      *
                    Basic maps
-%*									*
+%*                                                                      *
 %************************************************************************
 
 \begin{code}
@@ -242,9 +235,9 @@ xtLit = alterTM
 \end{code}
 
 %************************************************************************
-%*									*
+%*                                                                      *
                    CoreMap
-%*									*
+%*                                                                      *
 %************************************************************************
 
 Note [Binders]
@@ -296,10 +289,10 @@ data CoreMap a
 
 wrapEmptyCM :: CoreMap a
 wrapEmptyCM = CM { cm_var = emptyTM, cm_lit = emptyLiteralMap
- 		 , cm_co = emptyTM, cm_type = emptyTM
- 		 , cm_cast = emptyTM, cm_app = emptyTM 
- 		 , cm_lam = emptyTM, cm_letn = emptyTM 
- 		 , cm_letr = emptyTM, cm_case = emptyTM
+                 , cm_co = emptyTM, cm_type = emptyTM
+                 , cm_cast = emptyTM, cm_app = emptyTM
+                 , cm_lam = emptyTM, cm_letn = emptyTM
+                 , cm_letr = emptyTM, cm_case = emptyTM
                  , cm_ecase = emptyTM, cm_tick = emptyTM }
 
 instance TrieMap CoreMap where
@@ -315,9 +308,9 @@ mapE :: (a->b) -> CoreMap a -> CoreMap b
 mapE _ EmptyCM = EmptyCM
 mapE f (CM { cm_var = cvar, cm_lit = clit
            , cm_co = cco, cm_type = ctype
- 	   , cm_cast = ccast , cm_app = capp
- 	   , cm_lam = clam, cm_letn = cletn 
- 	   , cm_letr = cletr, cm_case = ccase
+           , cm_cast = ccast , cm_app = capp
+           , cm_lam = clam, cm_letn = cletn
+           , cm_letr = cletr, cm_case = ccase
            , cm_ecase = cecase, cm_tick = ctick })
   = CM { cm_var = mapTM f cvar, cm_lit = mapTM f clit
        , cm_co = mapTM f cco, cm_type = mapTM f ctype
@@ -365,9 +358,9 @@ lkE env expr cm
   | EmptyCM <- cm = Nothing
   | otherwise     = go expr cm
   where
-    go (Var v)  	    = cm_var  >.> lkVar env v
+    go (Var v)              = cm_var  >.> lkVar env v
     go (Lit l)              = cm_lit  >.> lkLit l
-    go (Type t) 	    = cm_type >.> lkT env t
+    go (Type t)             = cm_type >.> lkT env t
     go (Coercion c)         = cm_co   >.> lkC env c
     go (Cast e c)           = cm_cast >.> lkE env e >=> lkC env c
     go (Tick tickish e)     = cm_tick >.> lkE env e >=> lkTickish tickish
@@ -388,7 +381,7 @@ lkE env expr cm
 xtE :: CmEnv -> CoreExpr -> XT a -> CoreMap a -> CoreMap a
 xtE env e              f EmptyCM = xtE env e f wrapEmptyCM
 xtE env (Var v)              f m = m { cm_var  = cm_var m  |> xtVar env v f }
-xtE env (Type t) 	     f m = m { cm_type = cm_type m |> xtT env t f }
+xtE env (Type t)             f m = m { cm_type = cm_type m |> xtT env t f }
 xtE env (Coercion c)         f m = m { cm_co   = cm_co m   |> xtC env c f }
 xtE _   (Lit l)              f m = m { cm_lit  = cm_lit m  |> xtLit l f }
 xtE env (Cast e c)           f m = m { cm_cast = cm_cast m |> xtE env e |>>
@@ -420,7 +413,7 @@ xtTickish :: Tickish Id -> XT a -> TickishMap a -> TickishMap a
 xtTickish = alterTM
 
 ------------------------
-data AltMap a	-- A single alternative
+data AltMap a   -- A single alternative
   = AM { am_deflt :: CoreMap a
        , am_data  :: NameEnv (CoreMap a)
        , am_lit   :: LiteralMap (CoreMap a) }
@@ -459,9 +452,9 @@ fdA k m = foldTM k (am_deflt m)
 \end{code}
 
 %************************************************************************
-%*									*
+%*                                                                      *
                    Coercions
-%*									*
+%*                                                                      *
 %************************************************************************
 
 \begin{code}
@@ -627,9 +620,9 @@ mapR f = RM . mapTM f . unRM
 
 
 %************************************************************************
-%*									*
+%*                                                                      *
                    Types
-%*									*
+%*                                                                      *
 %************************************************************************
 
 \begin{code}
@@ -775,9 +768,9 @@ foldTyLit l m = flip (Map.fold l) (tlm_string m)
 
 
 %************************************************************************
-%*									*
+%*                                                                      *
                    Variables
-%*									*
+%*                                                                      *
 %************************************************************************
 
 \begin{code}
@@ -811,7 +804,7 @@ xtBndr env v f = xtT env (varType v) f
 
 --------- Variable occurrence -------------
 data VarMap a = VM { vm_bvar   :: BoundVarMap a  -- Bound variable
-                   , vm_fvar   :: VarEnv a }  	  -- Free variable
+                   , vm_fvar   :: VarEnv a }      -- Free variable
 
 instance TrieMap VarMap where
    type Key VarMap = Var



More information about the ghc-commits mailing list