{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
{-# HLINT ignore "Use fewer imports" #-}
module Unicode.Internal.Bits.Names
(
lookupInt32#
, unpackNBytes#
) where
#include "MachDeps.h"
import GHC.Exts (Addr#, Int#)
#ifdef WORDS_BIGENDIAN
import GHC.Exts (narrow32Word#, word2Int#, byteSwap32#, indexWord32OffAddr#)
#if MIN_VERSION_base(4,16,0)
import GHC.Exts (word32ToWord#)
#endif
#else
import GHC.Exts (indexInt32OffAddr#)
#if MIN_VERSION_base(4,16,0)
import GHC.Exts (int32ToInt#)
#endif
#endif
#if MIN_VERSION_base(4,15,0)
import GHC.Exts (unpackNBytes#)
#else
import GHC.CString (unpackNBytes#)
#endif
lookupInt32#
:: Addr#
-> Int#
-> Int#
lookupInt32# :: Addr# -> Int# -> Int#
lookupInt32#
#ifdef WORDS_BIGENDIAN
#if MIN_VERSION_base(4,16,0)
addr# k# = word2Int# (narrow32Word# (byteSwap32# (word32ToWord# (indexWord32OffAddr# addr# k#))))
#else
addr# k# = word2Int# (narrow32Word# (byteSwap32# (indexWord32OffAddr# addr# k#)))
#endif
#elif MIN_VERSION_base(4,16,0)
Addr#
addr# Int#
k# = Int32# -> Int#
int32ToInt# (Addr# -> Int# -> Int32#
indexInt32OffAddr# Addr#
addr# Int#
k#)
#else
= indexInt32OffAddr#
#endif