[commit: ghc] master: Derive Eq and Ord instance for SrcLoc and RealSrcLoc (67d2226)

git at git.haskell.org git at git.haskell.org
Wed Feb 17 20:02:49 UTC 2016


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/67d22261da840c5ba90414496457b583df0a3911/ghc

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

commit 67d22261da840c5ba90414496457b583df0a3911
Author: Gabriel Gonzalez <Gabriel439 at gmail.com>
Date:   Wed Feb 17 10:59:09 2016 +0100

    Derive Eq and Ord instance for SrcLoc and RealSrcLoc
    
    The Eq and Ord instance were previously hand-written and this change
    updates them to be automatically derived by the compiler.  The derived
    behavior should be equivalent to the original.
    
    Reviewers: hvr, austin, bgamari
    
    Reviewed By: bgamari
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D1913


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

67d22261da840c5ba90414496457b583df0a3911
 compiler/basicTypes/SrcLoc.hs | 30 ++----------------------------
 1 file changed, 2 insertions(+), 28 deletions(-)

diff --git a/compiler/basicTypes/SrcLoc.hs b/compiler/basicTypes/SrcLoc.hs
index 04f7ec9..2726f41 100644
--- a/compiler/basicTypes/SrcLoc.hs
+++ b/compiler/basicTypes/SrcLoc.hs
@@ -105,11 +105,12 @@ data RealSrcLoc
   = SrcLoc      FastString              -- A precise location (file name)
                 {-# UNPACK #-} !Int     -- line number, begins at 1
                 {-# UNPACK #-} !Int     -- column number, begins at 1
+  deriving (Eq, Ord)
 
 data SrcLoc
   = RealSrcLoc {-# UNPACK #-}!RealSrcLoc
   | UnhelpfulLoc FastString     -- Just a general indication
-  deriving Show
+  deriving (Eq, Ord, Show)
 
 {-
 ************************************************************************
@@ -164,36 +165,9 @@ advanceSrcLoc (SrcLoc f l c) _    = SrcLoc f  l (c + 1)
 ************************************************************************
 -}
 
--- SrcLoc is an instance of Ord so that we can sort error messages easily
-instance Eq SrcLoc where
-  loc1 == loc2 = case loc1 `cmpSrcLoc` loc2 of
-                 EQ     -> True
-                 _other -> False
-
-instance Eq RealSrcLoc where
-  loc1 == loc2 = case loc1 `cmpRealSrcLoc` loc2 of
-                 EQ     -> True
-                 _other -> False
-
-instance Ord SrcLoc where
-  compare = cmpSrcLoc
-
-instance Ord RealSrcLoc where
-  compare = cmpRealSrcLoc
-
 sortLocated :: [Located a] -> [Located a]
 sortLocated things = sortBy (comparing getLoc) things
 
-cmpSrcLoc :: SrcLoc -> SrcLoc -> Ordering
-cmpSrcLoc (UnhelpfulLoc s1) (UnhelpfulLoc s2) = s1 `compare` s2
-cmpSrcLoc (UnhelpfulLoc _)  (RealSrcLoc _)    = GT
-cmpSrcLoc (RealSrcLoc _)    (UnhelpfulLoc _)  = LT
-cmpSrcLoc (RealSrcLoc l1)   (RealSrcLoc l2)   = (l1 `compare` l2)
-
-cmpRealSrcLoc :: RealSrcLoc -> RealSrcLoc -> Ordering
-cmpRealSrcLoc (SrcLoc s1 l1 c1) (SrcLoc s2 l2 c2)
-  = (s1 `compare` s2) `thenCmp` (l1 `compare` l2) `thenCmp` (c1 `compare` c2)
-
 instance Outputable RealSrcLoc where
     ppr (SrcLoc src_path src_line src_col)
       = hcat [ pprFastFilePath src_path <> colon



More information about the ghc-commits mailing list