[Internal] move all primitives stuff in CompatPrim
This commit is contained in:
parent
6dcba8d8cd
commit
8655eb0468
@ -9,20 +9,15 @@
|
|||||||
-- or other needed packages, so that modules don't need to use CPP
|
-- or other needed packages, so that modules don't need to use CPP
|
||||||
--
|
--
|
||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
{-# LANGUAGE MagicHash #-}
|
|
||||||
module Crypto.Internal.Compat
|
module Crypto.Internal.Compat
|
||||||
( unsafeDoIO
|
( unsafeDoIO
|
||||||
, popCount
|
, popCount
|
||||||
, byteSwap64
|
, byteSwap64
|
||||||
, booleanPrim
|
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import System.IO.Unsafe
|
import System.IO.Unsafe
|
||||||
import Data.Word
|
import Data.Word
|
||||||
import Data.Bits
|
import Data.Bits
|
||||||
#if __GLASGOW_HASKELL__ >= 708
|
|
||||||
import GHC.Prim
|
|
||||||
#endif
|
|
||||||
|
|
||||||
-- | perform io for hashes that do allocation and ffi.
|
-- | perform io for hashes that do allocation and ffi.
|
||||||
-- unsafeDupablePerformIO is used when possible as the
|
-- unsafeDupablePerformIO is used when possible as the
|
||||||
@ -51,11 +46,3 @@ byteSwap64 w =
|
|||||||
.|. ((w `shiftR` 24) .&. 0xff0000) .|. ((w .&. 0xff0000) `shiftL` 24)
|
.|. ((w `shiftR` 24) .&. 0xff0000) .|. ((w .&. 0xff0000) `shiftL` 24)
|
||||||
.|. ((w `shiftR` 8) .&. 0xff000000) .|. ((w .&. 0xff000000) `shiftL` 8)
|
.|. ((w `shiftR` 8) .&. 0xff000000) .|. ((w .&. 0xff000000) `shiftL` 8)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
#if __GLASGOW_HASKELL__ >= 708
|
|
||||||
booleanPrim :: Int# -> Bool
|
|
||||||
booleanPrim v = tagToEnum# v
|
|
||||||
#else
|
|
||||||
booleanPrim :: Bool -> Bool
|
|
||||||
booleanPrim b = b
|
|
||||||
#endif
|
|
||||||
|
|||||||
@ -16,6 +16,7 @@
|
|||||||
module Crypto.Internal.CompatPrim
|
module Crypto.Internal.CompatPrim
|
||||||
( be32Prim
|
( be32Prim
|
||||||
, byteswap32Prim
|
, byteswap32Prim
|
||||||
|
, booleanPrim
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import GHC.Prim
|
import GHC.Prim
|
||||||
@ -38,3 +39,11 @@ byteswap32Prim w =
|
|||||||
d = and# (uncheckedShiftRL# w 24#) 0x000000ff##
|
d = and# (uncheckedShiftRL# w 24#) 0x000000ff##
|
||||||
in or# a (or# b (or# c d))
|
in or# a (or# b (or# c d))
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
|
#if __GLASGOW_HASKELL__ >= 708
|
||||||
|
booleanPrim :: Int# -> Bool
|
||||||
|
booleanPrim v = tagToEnum# v
|
||||||
|
#else
|
||||||
|
booleanPrim :: Bool -> Bool
|
||||||
|
booleanPrim b = b
|
||||||
|
#endif
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user