{-# language CPP #-}
{-# language BangPatterns #-}
{-# language DataKinds #-}
{-# language MagicHash #-}
{-# language UnboxedTuples #-}

#include <MachDeps.h>

module Basics.Word256
  ( -- Types
    T
  , T#
  , R
    -- Lifting
  , lift
  , unlift
    -- Array
  , read#
  , write#
  , index#
  , uninitialized#
  , initialized#
  , copy#
  , copyMutable#
  , set#
  , shrink#
  , eq#
  , neq#
    -- Encode
  , shows
  ) where

import Prelude hiding (shows,minBound,maxBound)

import Data.WideWord.Word256 (Word256(Word256))
import GHC.Exts hiding (setByteArray#)
import GHC.Word (Word64(W64#))

import qualified Data.WideWord.Word256 as Word256
import qualified GHC.Exts as Exts

type T = Word256
type T# = (# Word#, Word#, Word#, Word# #)
type R = 'TupleRep '[ 'WordRep, 'WordRep, 'WordRep, 'WordRep ]

lift :: T# -> T
{-# inline lift #-}
lift :: T# -> T
lift (# Word#
a, Word#
b, Word#
c, Word#
d #) = Word64 -> Word64 -> Word64 -> Word64 -> T
Word256 (Word# -> Word64
W64# Word#
a) (Word# -> Word64
W64# Word#
b) (Word# -> Word64
W64# Word#
c) (Word# -> Word64
W64# Word#
d)

unlift :: T -> T#
{-# inline unlift #-}
unlift :: T -> T#
unlift (Word256 (W64# Word#
a) (W64# Word#
b) (W64# Word#
c) (W64# Word#
d)) = (# Word#
a, Word#
b, Word#
c, Word#
d #)

eq# :: T# -> T# -> Int#
{-# inline eq# #-}
eq# :: T# -> T# -> Int#
eq# (# Word#
x1, Word#
y1, Word#
z1, Word#
w1 #) (# Word#
x2, Word#
y2, Word#
z2, Word#
w2 #) =
  (Word# -> Word# -> Int#
eqWord# Word#
x1 Word#
x2) Int# -> Int# -> Int#
`andI#`
  (Word# -> Word# -> Int#
eqWord# Word#
y1 Word#
y2) Int# -> Int# -> Int#
`andI#`
  (Word# -> Word# -> Int#
eqWord# Word#
z1 Word#
z2) Int# -> Int# -> Int#
`andI#`
  (Word# -> Word# -> Int#
eqWord# Word#
w1 Word#
w2)

neq# :: T# -> T# -> Int#
{-# inline neq# #-}
neq# :: T# -> T# -> Int#
neq# (# Word#
x1, Word#
y1, Word#
z1, Word#
w1 #) (# Word#
x2, Word#
y2, Word#
z2, Word#
w2 #) =
  (Word# -> Word# -> Int#
neWord# Word#
x1 Word#
x2) Int# -> Int# -> Int#
`orI#`
  (Word# -> Word# -> Int#
neWord# Word#
y1 Word#
y2) Int# -> Int# -> Int#
`orI#`
  (Word# -> Word# -> Int#
neWord# Word#
z1 Word#
z2) Int# -> Int# -> Int#
`orI#`
  (Word# -> Word# -> Int#
neWord# Word#
w1 Word#
w2)

set# :: MutableByteArray# s -> Int# -> Int# -> T# -> State# s -> State# s
{-# inline set# #-}
set# :: forall s.
MutableByteArray# s -> Int# -> Int# -> T# -> State# s -> State# s
set# MutableByteArray# s
marr Int#
off Int#
len T#
x State# s
s = case Int#
len of
  Int#
0# -> State# s
s
  Int#
_ -> forall s.
MutableByteArray# s -> Int# -> Int# -> T# -> State# s -> State# s
set# MutableByteArray# s
marr (Int#
off Int# -> Int# -> Int#
+# Int#
1# ) (Int#
len Int# -> Int# -> Int#
-# Int#
1# ) T#
x (forall s. MutableByteArray# s -> Int# -> T# -> State# s -> State# s
write# MutableByteArray# s
marr Int#
off T#
x State# s
s)

uninitialized# :: Int# -> State# s -> (# State# s, MutableByteArray# s #)
{-# inline uninitialized# #-}
uninitialized# :: forall s. Int# -> State# s -> (# State# s, MutableByteArray# s #)
uninitialized# Int#
sz = forall s. Int# -> State# s -> (# State# s, MutableByteArray# s #)
Exts.newByteArray# (Int#
sz Int# -> Int# -> Int#
*# Int#
32# )

initialized# ::
     Int# -> T# -> State# s
  -> (# State# s, MutableByteArray# s #)
{-# inline initialized# #-}
initialized# :: forall s.
Int# -> T# -> State# s -> (# State# s, MutableByteArray# s #)
initialized# Int#
n T#
e State# s
s0 = case forall s. Int# -> State# s -> (# State# s, MutableByteArray# s #)
uninitialized# Int#
n State# s
s0 of
  (# State# s
s1, MutableByteArray# s
a #) -> case forall s.
MutableByteArray# s -> Int# -> Int# -> T# -> State# s -> State# s
set# MutableByteArray# s
a Int#
0# Int#
n T#
e State# s
s1 of
    State# s
s2 -> (# State# s
s2, MutableByteArray# s
a #)

copy# :: MutableByteArray# s -> Int# -> ByteArray# -> Int# -> Int# -> State# s -> State# s
{-# inline copy# #-}
copy# :: forall s.
MutableByteArray# s
-> Int# -> ByteArray# -> Int# -> Int# -> State# s -> State# s
copy# MutableByteArray# s
dst Int#
doff ByteArray#
src Int#
soff Int#
len =
  forall d.
ByteArray#
-> Int#
-> MutableByteArray# d
-> Int#
-> Int#
-> State# d
-> State# d
Exts.copyByteArray# ByteArray#
src (Int#
soff Int# -> Int# -> Int#
*# Int#
32#) MutableByteArray# s
dst (Int#
doff Int# -> Int# -> Int#
*# Int#
32#) (Int#
len Int# -> Int# -> Int#
*# Int#
32#)

copyMutable# :: MutableByteArray# s -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
{-# inline copyMutable# #-}
copyMutable# :: forall s.
MutableByteArray# s
-> Int#
-> MutableByteArray# s
-> Int#
-> Int#
-> State# s
-> State# s
copyMutable# MutableByteArray# s
dst Int#
doff MutableByteArray# s
src Int#
soff Int#
len =
  forall s.
MutableByteArray# s
-> Int#
-> MutableByteArray# s
-> Int#
-> Int#
-> State# s
-> State# s
Exts.copyMutableByteArray# MutableByteArray# s
src (Int#
soff Int# -> Int# -> Int#
*# Int#
32#) MutableByteArray# s
dst (Int#
doff Int# -> Int# -> Int#
*# Int#
32#) (Int#
len Int# -> Int# -> Int#
*# Int#
32#)

shrink# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, MutableByteArray# s #)
{-# inline shrink# #-}
shrink# :: forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, MutableByteArray# s #)
shrink# MutableByteArray# s
m Int#
i State# s
s0 = (# forall d. MutableByteArray# d -> Int# -> State# d -> State# d
Exts.shrinkMutableByteArray# MutableByteArray# s
m (Int#
i Int# -> Int# -> Int#
*# Int#
32#) State# s
s0, MutableByteArray# s
m #)

shows :: T -> String -> String
shows :: T -> String -> String
shows T
x = (T -> String
Word256.showHexWord256 T
x forall a. [a] -> [a] -> [a]
++)

#if WORDS_BIGENDIAN
index# :: ByteArray# -> Int# -> T#
{-# inline index# #-}
index# arr# i# =
  (# Exts.indexWordArray# arr# (4# *# i#)
  ,  Exts.indexWordArray# arr# ((4# *# i#) +# 1#)
  ,  Exts.indexWordArray# arr# ((4# *# i#) +# 2#)
  ,  Exts.indexWordArray# arr# ((4# *# i#) +# 3#)
  #)

read# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, T# #)
{-# inline read# #-}
read# arr# i# s0 = case Exts.readWordArray# arr# (4# *# i#) s0 of
  (# s1, i0 #) -> case Exts.readWordArray# arr# ((4# *# i#) +# 1#) s1 of
    (# s2, i1 #) -> case Exts.readWordArray# arr# ((4# *# i#) +# 2#) s2 of
      (# s3, i2 #) -> case Exts.readWordArray# arr# ((4# *# i#) +# 3#) s3 of
        (# s4, i3 #) -> (# s4, (# i0, i1, i2, i3 #) #)

write# :: MutableByteArray# s -> Int# -> T# -> State# s -> State# s
{-# inline write# #-}
write# arr# i# (# a, b, c, d #) s0 =
  case Exts.writeWordArray# arr# (4# *# i#) a s0 of
    s1 -> case Exts.writeWordArray# arr# ((4# *# i#) +# 1#) b s1 of
      s2 -> case Exts.writeWordArray# arr# ((4# *# i#) +# 2#) c s2 of
        s3 -> case Exts.writeWordArray# arr# ((4# *# i#) +# 3#) d s3 of
          s4 -> s4
#else
index# :: ByteArray# -> Int# -> T#
{-# inline index# #-}
index# :: ByteArray# -> Int# -> T#
index# ByteArray#
arr# Int#
i# =
  (# ByteArray# -> Int# -> Word#
Exts.indexWordArray# ByteArray#
arr# ((Int#
4# Int# -> Int# -> Int#
*# Int#
i#) Int# -> Int# -> Int#
+# Int#
3#)
  ,  ByteArray# -> Int# -> Word#
Exts.indexWordArray# ByteArray#
arr# ((Int#
4# Int# -> Int# -> Int#
*# Int#
i#) Int# -> Int# -> Int#
+# Int#
2#)
  ,  ByteArray# -> Int# -> Word#
Exts.indexWordArray# ByteArray#
arr# ((Int#
4# Int# -> Int# -> Int#
*# Int#
i#) Int# -> Int# -> Int#
+# Int#
1#)
  ,  ByteArray# -> Int# -> Word#
Exts.indexWordArray# ByteArray#
arr# (Int#
4# Int# -> Int# -> Int#
*# Int#
i#)
  #)

read# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, T# #)
{-# inline read# #-}
read# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, T# #)
read# MutableByteArray# s
arr# Int#
i# State# s
s0 = case forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #)
Exts.readWordArray# MutableByteArray# s
arr# ((Int#
4# Int# -> Int# -> Int#
*# Int#
i#) Int# -> Int# -> Int#
+# Int#
3#) State# s
s0 of
  (# State# s
s1, Word#
i0 #) -> case forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #)
Exts.readWordArray# MutableByteArray# s
arr# ((Int#
4# Int# -> Int# -> Int#
*# Int#
i#) Int# -> Int# -> Int#
+# Int#
2#) State# s
s1 of
    (# State# s
s2, Word#
i1 #) -> case forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #)
Exts.readWordArray# MutableByteArray# s
arr# ((Int#
4# Int# -> Int# -> Int#
*# Int#
i#) Int# -> Int# -> Int#
+# Int#
1#) State# s
s2 of
      (# State# s
s3, Word#
i2 #) -> case forall d.
MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #)
Exts.readWordArray# MutableByteArray# s
arr# (Int#
4# Int# -> Int# -> Int#
*# Int#
i#) State# s
s3 of
        (# State# s
s4, Word#
i3 #) -> (# State# s
s4, (# Word#
i0, Word#
i1, Word#
i2, Word#
i3 #) #)

write# :: MutableByteArray# s -> Int# -> T# -> State# s -> State# s
{-# inline write# #-}
write# :: forall s. MutableByteArray# s -> Int# -> T# -> State# s -> State# s
write# MutableByteArray# s
arr# Int#
i# (# Word#
a, Word#
b, Word#
c, Word#
d #) State# s
s0 =
  case forall d.
MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
Exts.writeWordArray# MutableByteArray# s
arr# ((Int#
4# Int# -> Int# -> Int#
*# Int#
i#) Int# -> Int# -> Int#
+# Int#
3#) Word#
a State# s
s0 of
    State# s
s1 -> case forall d.
MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
Exts.writeWordArray# MutableByteArray# s
arr# ((Int#
4# Int# -> Int# -> Int#
*# Int#
i#) Int# -> Int# -> Int#
+# Int#
2#) Word#
b State# s
s1 of
      State# s
s2 -> case forall d.
MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
Exts.writeWordArray# MutableByteArray# s
arr# ((Int#
4# Int# -> Int# -> Int#
*# Int#
i#) Int# -> Int# -> Int#
+# Int#
1#) Word#
c State# s
s2 of
        State# s
s3 -> case forall d.
MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
Exts.writeWordArray# MutableByteArray# s
arr# (Int#
4# Int# -> Int# -> Int#
*# Int#
i#) Word#
d State# s
s3 of
          State# s
s4 -> State# s
s4
#endif