Skip to content
Snippets Groups Projects
Commit c3d8dadc authored by Stefan Schulze Frielinghaus's avatar Stefan Schulze Frielinghaus Committed by Ben Gamari
Browse files

Fix endian handling w.r.t. CPP macro WORDS_BIGENDIAN

Include header file `ghcautoconf.h` where the CPP macro
`WORDS_BIGENDIAN` is defined. This finally fixes #17337 (in conjunction
with commit 6c59cc71).

(cherry picked from commit 3c12355e)
(cherry picked from commit 11f8eef5)
parent a9bd5420
No related merge requests found
...@@ -17,6 +17,9 @@ ...@@ -17,6 +17,9 @@
module GHC.ByteOrder where module GHC.ByteOrder where
-- Required for WORDS_BIGENDIAN
#include <ghcautoconf.h>
-- | Byte ordering. -- | Byte ordering.
data ByteOrder data ByteOrder
= BigEndian -- ^ most-significant-byte occurs in lowest address. = BigEndian -- ^ most-significant-byte occurs in lowest address.
......
...@@ -7,6 +7,9 @@ module GHC.IO.Encoding.CodePage.API ( ...@@ -7,6 +7,9 @@ module GHC.IO.Encoding.CodePage.API (
mkCodePageEncoding mkCodePageEncoding
) where ) where
-- Required for WORDS_BIGENDIAN
#include <ghcautoconf.h>
import Foreign.C import Foreign.C
import Foreign.Ptr import Foreign.Ptr
import Foreign.Marshal import Foreign.Marshal
......
{-# LANGUAGE CPP #-}
-- !!! Bug # 7600. -- !!! Bug # 7600.
-- The LLVM backend can be tricky to get right with floating point constants -- The LLVM backend can be tricky to get right with floating point constants
-- and GHC. See Note [LLVM Float Types] in compiler/llvmGen/Llvm/Types.hs for -- and GHC. See Note [LLVM Float Types] in compiler/llvmGen/Llvm/Types.hs for
...@@ -16,6 +17,9 @@ ...@@ -16,6 +17,9 @@
-- Also worth looking at ticket # 3676 about issues with 'realToFrac'. -- Also worth looking at ticket # 3676 about issues with 'realToFrac'.
module Main (main) where module Main (main) where
-- Required for WORDS_BIGENDIAN
#include <ghcautoconf.h>
import T7600_A import T7600_A
-- a fp constant that requires double precision, but we only use a single -- a fp constant that requires double precision, but we only use a single
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment