Skip to content

Commit

Permalink
Merge branch 'master' of darcs.haskell.org:/srv/darcs//ghc
Browse files Browse the repository at this point in the history
  • Loading branch information
Ian Lynagh committed Apr 6, 2013
2 parents 93494bd + 35a341d commit 8c2f280
Show file tree
Hide file tree
Showing 2 changed files with 8 additions and 19 deletions.
17 changes: 3 additions & 14 deletions compiler/cmm/CmmNode.hs
@@ -1,6 +1,7 @@
-- CmmNode type for representation using Hoopl graphs.
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-}

{-# OPTIONS -fno-warn-tabs #-}
Expand Down Expand Up @@ -199,20 +200,8 @@ way is done in cmm/CmmOpt.hs currently. We should fix this!

---------------------------------------------
-- Eq instance of CmmNode
-- It is a shame GHC cannot infer it by itself :(

instance Eq (CmmNode e x) where
(CmmEntry a) == (CmmEntry a') = a==a'
(CmmComment a) == (CmmComment a') = a==a'
(CmmAssign a b) == (CmmAssign a' b') = a==a' && b==b'
(CmmStore a b) == (CmmStore a' b') = a==a' && b==b'
(CmmUnsafeForeignCall a b c) == (CmmUnsafeForeignCall a' b' c') = a==a' && b==b' && c==c'
(CmmBranch a) == (CmmBranch a') = a==a'
(CmmCondBranch a b c) == (CmmCondBranch a' b' c') = a==a' && b==b' && c==c'
(CmmSwitch a b) == (CmmSwitch a' b') = a==a' && b==b'
(CmmCall a b c d e f) == (CmmCall a' b' c' d' e' f') = a==a' && b==b' && c==c' && d==d' && e==e' && f==f'
(CmmForeignCall a b c d e f) == (CmmForeignCall a' b' c' d' e' f') = a==a' && b==b' && c==c' && d==d' && e==e' && f==f'
_ == _ = False

deriving instance Eq (CmmNode e x)

----------------------------------------------
-- Hoopl instances of CmmNode
Expand Down
10 changes: 5 additions & 5 deletions compiler/cmm/CmmPipeline.hs
Expand Up @@ -184,11 +184,11 @@ cpsTop hsc_env proc =
|| not (tablesNextToCode dflags)
|| -- Note [inconsistent-pic-reg]
usingInconsistentPicReg
usingInconsistentPicReg = ( platformArch platform == ArchX86 ||
platformArch platform == ArchPPC
)
&& platformOS platform == OSDarwin
&& gopt Opt_PIC dflags
usingInconsistentPicReg
= case (platformArch platform, platformOS platform, gopt Opt_PIC dflags)
of (ArchX86, OSDarwin, pic) -> pic
(ArchPPC, OSDarwin, pic) -> pic
_ -> False

{- Note [inconsistent-pic-reg]
Expand Down

0 comments on commit 8c2f280

Please sign in to comment.