never executed always true always false
1 {-# LANGUAGE CPP #-}
2 {-# OPTIONS_HADDOCK not-home #-}
3
4 -- | Custom GHC "Prelude"
5 --
6 -- This module serves as a replacement for the "Prelude" module
7 -- and abstracts over differences between the bootstrapping
8 -- GHC version, and may also provide a common default vocabulary.
9
10 -- Every module in GHC
11 -- * Is compiled with -XNoImplicitPrelude
12 -- * Explicitly imports GHC.Prelude
13
14 module GHC.Prelude
15 (module X
16 ,module Bits
17 ,shiftL, shiftR
18 ) where
19
20
21 -- We export the 'Semigroup' class but w/o the (<>) operator to avoid
22 -- clashing with the (Outputable.<>) operator which is heavily used
23 -- through GHC's code-base.
24
25 {-
26 Note [Why do we import Prelude here?]
27 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
28 The files ghc-boot-th.cabal, ghc-boot.cabal, ghci.cabal and
29 ghc-heap.cabal contain the directive default-extensions:
30 NoImplicitPrelude. There are two motivations for this:
31 - Consistency with the compiler directory, which enables
32 NoImplicitPrelude;
33 - Allows loading the above dependent packages with ghc-in-ghci,
34 giving a smoother development experience when adding new
35 extensions.
36 -}
37
38 import Prelude as X hiding ((<>))
39 import Data.Foldable as X (foldl')
40
41 #if MIN_VERSION_base(4,16,0)
42 import GHC.Bits as Bits hiding (shiftL, shiftR)
43 # if defined(DEBUG)
44 import qualified GHC.Bits as Bits (shiftL, shiftR)
45 # endif
46
47 #else
48 --base <4.15
49 import Data.Bits as Bits hiding (shiftL, shiftR)
50 # if defined(DEBUG)
51 import qualified Data.Bits as Bits (shiftL, shiftR)
52 # endif
53 #endif
54
55 {- Note [Default to unsafe shifts inside GHC]
56 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
57 The safe shifts can introduce branches which come
58 at the cost of performance. We still want the additional
59 debugability for debug builds. So we define it as one or the
60 other depending on the DEBUG setting.
61
62 Why do we then continue on to re-export the rest of Data.Bits?
63 If we would not what is likely to happen is:
64 * Someone imports Data.Bits, uses xor. Things are fine.
65 * They add a shift and get an ambigious definition error.
66 * The are puzzled for a bit.
67 * They either:
68 + Remove the import of Data.Bits and get an error because xor is not in scope.
69 + Add the hiding clause to the Data.Bits import for the shifts.
70
71 Either is quite annoying. Simply re-exporting all of Data.Bits avoids this
72 making for a smoother developer experience. At the cost of having a few more
73 names in scope at all time. But that seems like a fair tradeoff.
74
75 See also #19618
76 -}
77
78 -- We always want the Data.Bits method to show up for rules etc.
79 {-# INLINE shiftL #-}
80 {-# INLINE shiftR #-}
81 shiftL, shiftR :: Bits.Bits a => a -> Int -> a
82 #if defined(DEBUG)
83 shiftL = Bits.shiftL
84 shiftR = Bits.shiftR
85 #else
86 shiftL = Bits.unsafeShiftL
87 shiftR = Bits.unsafeShiftR
88 #endif