[commit: packages/template-haskell] master: Follow changes in comparison primops (see #6135) (8922e3e)
git at git.haskell.org
git at git.haskell.org
Wed Sep 18 17:12:33 CEST 2013
Repository : ssh://git@git.haskell.org/template-haskell
On branch : master
Link : http://git.haskell.org/packages/template-haskell.git/commitdiff/8922e3edf07946ce8a6a7e4d5bcb950217391e70
>---------------------------------------------------------------
commit 8922e3edf07946ce8a6a7e4d5bcb950217391e70
Author: Jan Stolarek <jan.stolarek at p.lodz.pl>
Date: Mon Sep 16 15:17:09 2013 +0100
Follow changes in comparison primops (see #6135)
>---------------------------------------------------------------
8922e3edf07946ce8a6a7e4d5bcb950217391e70
Language/Haskell/TH/Syntax.hs | 15 +++++++--------
1 file changed, 7 insertions(+), 8 deletions(-)
diff --git a/Language/Haskell/TH/Syntax.hs b/Language/Haskell/TH/Syntax.hs
index 545757f..d59ffff 100644
--- a/Language/Haskell/TH/Syntax.hs
+++ b/Language/Haskell/TH/Syntax.hs
@@ -16,8 +16,7 @@
module Language.Haskell.TH.Syntax where
-import GHC.Base ( Int(..), Int#, (<#), (==#) )
-
+import GHC.Exts
import Data.Data (Data(..), Typeable, mkConstr, mkDataType, constrIndex)
import qualified Data.Data as Data
import Control.Applicative( Applicative(..) )
@@ -722,17 +721,17 @@ instance Ord NameFlavour where
(NameU _) `compare` NameS = GT
(NameU _) `compare` (NameQ _) = GT
- (NameU u1) `compare` (NameU u2) | u1 <# u2 = LT
- | u1 ==# u2 = EQ
- | otherwise = GT
+ (NameU u1) `compare` (NameU u2) | isTrue# (u1 <# u2) = LT
+ | isTrue# (u1 ==# u2) = EQ
+ | otherwise = GT
(NameU _) `compare` _ = LT
(NameL _) `compare` NameS = GT
(NameL _) `compare` (NameQ _) = GT
(NameL _) `compare` (NameU _) = GT
- (NameL u1) `compare` (NameL u2) | u1 <# u2 = LT
- | u1 ==# u2 = EQ
- | otherwise = GT
+ (NameL u1) `compare` (NameL u2) | isTrue# (u1 <# u2) = LT
+ | isTrue# (u1 ==# u2) = EQ
+ | otherwise = GT
(NameL _) `compare` _ = LT
(NameG ns1 p1 m1) `compare` (NameG ns2 p2 m2) = (ns1 `compare` ns2) `thenCmp`
More information about the ghc-commits
mailing list