{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE Rank2Types #-}
module Data.Memory.Encoding.Base32
( toBase32
, unBase32Length
, fromBase32
) where
import Data.Memory.Internal.Compat
import Data.Word
import Basement.Bits
import Basement.IntegralConv
import GHC.Prim
import GHC.Word
import Control.Monad
import Foreign.Storable
import Foreign.Ptr (Ptr)
toBase32 :: Ptr Word8
-> Ptr Word8
-> Int
-> IO ()
toBase32 :: Ptr Word8 -> Ptr Word8 -> Int -> IO ()
toBase32 Ptr Word8
dst Ptr Word8
src Int
len = Int -> Int -> IO ()
loop Int
0 Int
0
where
eqChar :: Word8
eqChar :: Word8
eqChar = Word8
0x3d
peekOrZero :: Int -> IO Word8
peekOrZero :: Int -> IO Word8
peekOrZero Int
i
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
len = Word8 -> IO Word8
forall (m :: * -> *) a. Monad m => a -> m a
return Word8
0
| Bool
otherwise = Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src Int
i
pokeOrPadding :: Int
-> Int
-> Word8
-> IO ()
pokeOrPadding :: Int -> Int -> Word8 -> IO ()
pokeOrPadding Int
i Int
di Word8
v
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
len = Ptr Word8 -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Word8
dst Int
di Word8
v
| Bool
otherwise = Ptr Word8 -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Word8
dst Int
di Word8
eqChar
loop :: Int
-> Int
-> IO ()
loop :: Int -> Int -> IO ()
loop Int
i Int
di
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
len = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = do
Word8
i1 <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src Int
i
Word8
i2 <- Int -> IO Word8
peekOrZero (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
Word8
i3 <- Int -> IO Word8
peekOrZero (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)
Word8
i4 <- Int -> IO Word8
peekOrZero (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3)
Word8
i5 <- Int -> IO Word8
peekOrZero (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4)
let (Word8
o1,Word8
o2,Word8
o3,Word8
o4,Word8
o5,Word8
o6,Word8
o7,Word8
o8) = (Word8, Word8, Word8, Word8, Word8)
-> (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8)
toBase32Per5Bytes (Word8
i1, Word8
i2, Word8
i3, Word8
i4, Word8
i5)
Ptr Word8 -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Word8
dst Int
di Word8
o1
Ptr Word8 -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Word8
dst (Int
di Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Word8
o2
Int -> Int -> Word8 -> IO ()
pokeOrPadding (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Int
di Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) Word8
o3
Int -> Int -> Word8 -> IO ()
pokeOrPadding (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Int
di Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3) Word8
o4
Int -> Int -> Word8 -> IO ()
pokeOrPadding (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) (Int
di Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4) Word8
o5
Int -> Int -> Word8 -> IO ()
pokeOrPadding (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3) (Int
di Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
5) Word8
o6
Int -> Int -> Word8 -> IO ()
pokeOrPadding (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3) (Int
di Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
6) Word8
o7
Int -> Int -> Word8 -> IO ()
pokeOrPadding (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4) (Int
di Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
7) Word8
o8
Int -> Int -> IO ()
loop (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
5) (Int
diInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
8)
toBase32Per5Bytes :: (Word8, Word8, Word8, Word8, Word8)
-> (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8)
toBase32Per5Bytes :: (Word8, Word8, Word8, Word8, Word8)
-> (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8)
toBase32Per5Bytes (!Word8
i1, !Word8
i2, !Word8
i3, !Word8
i4, !Word8
i5) =
(Word8 -> Word8
index Word8
o1, Word8 -> Word8
index Word8
o2, Word8 -> Word8
index Word8
o3, Word8 -> Word8
index Word8
o4, Word8 -> Word8
index Word8
o5, Word8 -> Word8
index Word8
o6, Word8 -> Word8
index Word8
o7, Word8 -> Word8
index Word8
o8)
where
!o1 :: Word8
o1 = (Word8
i1 Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.&. Word8
0xF8) Word8 -> CountOf Bool -> Word8
forall bits. BitOps bits => bits -> CountOf Bool -> bits
.>>. CountOf Bool
3
!o2 :: Word8
o2 = ((Word8
i1 Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.&. Word8
0x07) Word8 -> CountOf Bool -> Word8
forall bits. BitOps bits => bits -> CountOf Bool -> bits
.<<. CountOf Bool
2) Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.|. ((Word8
i2 Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.&. Word8
0xC0) Word8 -> CountOf Bool -> Word8
forall bits. BitOps bits => bits -> CountOf Bool -> bits
.>>. CountOf Bool
6)
!o3 :: Word8
o3 = ((Word8
i2 Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.&. Word8
0x3E) Word8 -> CountOf Bool -> Word8
forall bits. BitOps bits => bits -> CountOf Bool -> bits
.>>. CountOf Bool
1)
!o4 :: Word8
o4 = ((Word8
i2 Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.&. Word8
0x01) Word8 -> CountOf Bool -> Word8
forall bits. BitOps bits => bits -> CountOf Bool -> bits
.<<. CountOf Bool
4) Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.|. ((Word8
i3 Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.&. Word8
0xF0) Word8 -> CountOf Bool -> Word8
forall bits. BitOps bits => bits -> CountOf Bool -> bits
.>>. CountOf Bool
4)
!o5 :: Word8
o5 = ( (Word8
i3 Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.&. Word8
0x0F) Word8 -> CountOf Bool -> Word8
forall bits. BitOps bits => bits -> CountOf Bool -> bits
.<<. CountOf Bool
1) Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.|. ((Word8
i4 Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.&. Word8
0x80) Word8 -> CountOf Bool -> Word8
forall bits. BitOps bits => bits -> CountOf Bool -> bits
.>>. CountOf Bool
7)
!o6 :: Word8
o6 = (Word8
i4 Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.&. Word8
0x7C) Word8 -> CountOf Bool -> Word8
forall bits. BitOps bits => bits -> CountOf Bool -> bits
.>>. CountOf Bool
2
!o7 :: Word8
o7 = ((Word8
i4 Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.&. Word8
0x03) Word8 -> CountOf Bool -> Word8
forall bits. BitOps bits => bits -> CountOf Bool -> bits
.<<. CountOf Bool
3) Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.|. ((Word8
i5 Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.&. Word8
0xE0) Word8 -> CountOf Bool -> Word8
forall bits. BitOps bits => bits -> CountOf Bool -> bits
.>>. CountOf Bool
5)
!o8 :: Word8
o8 = Word8
i5 Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.&. Word8
0x1F
!set :: Addr#
set = Addr#
"ABCDEFGHIJKLMNOPQRSTUVWXYZ234567"#
index :: Word8 -> Word8
index :: Word8 -> Word8
index Word8
idx = Word# -> Word8
W8# (Addr# -> Int# -> Word#
indexWord8OffAddr# Addr#
set (Word# -> Int#
word2Int# Word#
widx))
where !(W# Word#
widx) = Word8 -> Word
forall a b. IntegralUpsize a b => a -> b
integralUpsize Word8
idx
unBase32Length :: Ptr Word8 -> Int -> IO (Maybe Int)
unBase32Length :: Ptr Word8 -> Int -> IO (Maybe Int)
unBase32Length Ptr Word8
src Int
len
| Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1 = Maybe Int -> IO (Maybe Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Int -> IO (Maybe Int)) -> Maybe Int -> IO (Maybe Int)
forall a b. (a -> b) -> a -> b
$ Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0
| (Int
len Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
8) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0 = Maybe Int -> IO (Maybe Int)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Int
forall a. Maybe a
Nothing
| Bool
otherwise = do
Word8
last1Byte <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
Word8
last2Byte <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2)
Word8
last3Byte <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
3)
Word8
last4Byte <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
4)
Word8
last5Byte <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
5)
Word8
last6Byte <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
6)
let dstLen :: Int
dstLen = Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Int
caseByte Word8
last1Byte Word8
last2Byte Word8
last3Byte Word8
last4Byte Word8
last5Byte Word8
last6Byte
Maybe Int -> IO (Maybe Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Int -> IO (Maybe Int)) -> Maybe Int -> IO (Maybe Int)
forall a b. (a -> b) -> a -> b
$ Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> Int -> Maybe Int
forall a b. (a -> b) -> a -> b
$ (Int
len Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
8) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
5 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
dstLen
where
caseByte :: Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Int
caseByte :: Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Int
caseByte Word8
last1 Word8
last2 Word8
last3 Word8
last4 Word8
last5 Word8
last6
| Word8
last6 Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
eqAscii = Int
4
| Word8
last5 Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
eqAscii = Int
3
| Word8
last4 Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
eqAscii = Int
3
| Word8
last3 Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
eqAscii = Int
2
| Word8
last2 Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
eqAscii = Int
1
| Word8
last1 Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
eqAscii = Int
1
| Bool
otherwise = Int
0
eqAscii :: Word8
eqAscii :: Word8
eqAscii = Word8
0x3D
fromBase32 :: Ptr Word8 -> Ptr Word8 -> Int -> IO (Maybe Int)
fromBase32 :: Ptr Word8 -> Ptr Word8 -> Int -> IO (Maybe Int)
fromBase32 Ptr Word8
dst Ptr Word8
src Int
len
| Int
len Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = Maybe Int -> IO (Maybe Int)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Int
forall a. Maybe a
Nothing
| Bool
otherwise = Int -> Int -> IO (Maybe Int)
loop Int
0 Int
0
where
loop :: Int
-> Int
-> IO (Maybe Int)
loop :: Int -> Int -> IO (Maybe Int)
loop Int
di Int
i
| Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
8) = do
Word8
i1 <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src Int
i
Word8
i2 <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
Word8
i3 <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)
Word8
i4 <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3)
Word8
i5 <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4)
Word8
i6 <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
5)
Word8
i7 <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
6)
Word8
i8 <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
7)
let (Int
nbBytes, Word8
i3', Word8
i4', Word8
i5', Word8
i6', Word8
i7', Word8
i8') =
case (Word8
i3, Word8
i4, Word8
i5, Word8
i6, Word8
i7, Word8
i8) of
(Word8
0x3D, Word8
0x3D, Word8
0x3D, Word8
0x3D, Word8
0x3D, Word8
0x3D) -> (Int
6, Word8
0x41, Word8
0x41, Word8
0x41, Word8
0x41, Word8
0x41, Word8
0x41)
(Word8
0x3D, Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
_ ) -> (Int
0, Word8
i3, Word8
i4, Word8
i5, Word8
i6, Word8
i7, Word8
i8)
(Word8
_ , Word8
0x3D, Word8
0x3D, Word8
0x3D, Word8
0x3D, Word8
0x3D) -> (Int
5, Word8
i3 , Word8
0x41, Word8
0x41, Word8
0x41, Word8
0x41, Word8
0x41)
(Word8
_ , Word8
0x3D, Word8
_ , Word8
_ , Word8
_ , Word8
_ ) -> (Int
0, Word8
i3, Word8
i4, Word8
i5, Word8
i6, Word8
i7, Word8
i8)
(Word8
_ , Word8
_ , Word8
0x3D, Word8
0x3D, Word8
0x3D, Word8
0x3D) -> (Int
4, Word8
i3 , Word8
i4 , Word8
0x41, Word8
0x41, Word8
0x41, Word8
0x41)
(Word8
_ , Word8
_ , Word8
0x3D, Word8
_ , Word8
_ , Word8
_ ) -> (Int
0, Word8
i3, Word8
i4, Word8
i5, Word8
i6, Word8
i7, Word8
i8)
(Word8
_ , Word8
_ , Word8
_ , Word8
0x3D, Word8
0x3D, Word8
0x3D) -> (Int
3, Word8
i3 , Word8
i4 , Word8
i5 , Word8
0x41, Word8
0x41, Word8
0x41)
(Word8
_ , Word8
_ , Word8
_ , Word8
0x3D, Word8
_ , Word8
_ ) -> (Int
0, Word8
i3, Word8
i4, Word8
i5, Word8
i6, Word8
i7, Word8
i8)
(Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
0x3D, Word8
0x3D) -> (Int
2, Word8
i3 , Word8
i4 , Word8
i5 , Word8
i6 , Word8
0x41, Word8
0x41)
(Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
0x3D, Word8
_ ) -> (Int
0, Word8
i3, Word8
i4, Word8
i5, Word8
i6, Word8
i7, Word8
i8)
(Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
0x3D) -> (Int
1, Word8
i3 , Word8
i4 , Word8
i5 , Word8
i6 , Word8
i7 , Word8
0x41)
(Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
_ ) -> (Int
0 :: Int, Word8
i3, Word8
i4, Word8
i5, Word8
i6, Word8
i7, Word8
i8)
case (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8)
-> Either Int (Word8, Word8, Word8, Word8, Word8)
fromBase32Per8Bytes (Word8
i1, Word8
i2, Word8
i3', Word8
i4', Word8
i5', Word8
i6', Word8
i7', Word8
i8') of
Left Int
ofs -> Maybe Int -> IO (Maybe Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Int -> IO (Maybe Int)) -> Maybe Int -> IO (Maybe Int)
forall a b. (a -> b) -> a -> b
$ Int -> Maybe Int
forall a. a -> Maybe a
Just (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
ofs)
Right (Word8
o1, Word8
o2, Word8
o3, Word8
o4, Word8
o5) -> do
Ptr Word8 -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Word8
dst Int
di Word8
o1
Ptr Word8 -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Word8
dst (Int
diInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Word8
o2
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
nbBytes Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
5) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Word8
dst (Int
diInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
2) Word8
o3
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
nbBytes Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
4) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Word8
dst (Int
diInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
3) Word8
o4
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
nbBytes Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
2) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Word8
dst (Int
diInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
4) Word8
o5
Maybe Int -> IO (Maybe Int)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Int
forall a. Maybe a
Nothing
| Bool
otherwise = do
Word8
i1 <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src Int
i
Word8
i2 <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
Word8
i3 <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2)
Word8
i4 <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3)
Word8
i5 <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
4)
Word8
i6 <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
5)
Word8
i7 <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
6)
Word8
i8 <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
src (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
7)
case (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8)
-> Either Int (Word8, Word8, Word8, Word8, Word8)
fromBase32Per8Bytes (Word8
i1, Word8
i2, Word8
i3, Word8
i4, Word8
i5, Word8
i6, Word8
i7, Word8
i8) of
Left Int
ofs -> Maybe Int -> IO (Maybe Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Int -> IO (Maybe Int)) -> Maybe Int -> IO (Maybe Int)
forall a b. (a -> b) -> a -> b
$ Int -> Maybe Int
forall a. a -> Maybe a
Just (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
ofs)
Right (Word8
o1, Word8
o2, Word8
o3, Word8
o4, Word8
o5) -> do
Ptr Word8 -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Word8
dst Int
di Word8
o1
Ptr Word8 -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Word8
dst (Int
diInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Word8
o2
Ptr Word8 -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Word8
dst (Int
diInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
2) Word8
o3
Ptr Word8 -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Word8
dst (Int
diInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
3) Word8
o4
Ptr Word8 -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Word8
dst (Int
diInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
4) Word8
o5
Int -> Int -> IO (Maybe Int)
loop (Int
diInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
5) (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
8)
fromBase32Per8Bytes :: (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8)
-> Either Int (Word8, Word8, Word8, Word8, Word8)
fromBase32Per8Bytes :: (Word8, Word8, Word8, Word8, Word8, Word8, Word8, Word8)
-> Either Int (Word8, Word8, Word8, Word8, Word8)
fromBase32Per8Bytes (Word8
i1, Word8
i2, Word8
i3, Word8
i4, Word8
i5, Word8
i6, Word8
i7, Word8
i8) =
case (Word8 -> Word8
rset Word8
i1, Word8 -> Word8
rset Word8
i2, Word8 -> Word8
rset Word8
i3, Word8 -> Word8
rset Word8
i4, Word8 -> Word8
rset Word8
i5, Word8 -> Word8
rset Word8
i6, Word8 -> Word8
rset Word8
i7, Word8 -> Word8
rset Word8
i8) of
(Word8
0xFF, Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
_ ) -> Int -> Either Int (Word8, Word8, Word8, Word8, Word8)
forall a b. a -> Either a b
Left Int
0
(Word8
_ , Word8
0xFF, Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
_ ) -> Int -> Either Int (Word8, Word8, Word8, Word8, Word8)
forall a b. a -> Either a b
Left Int
1
(Word8
_ , Word8
_ , Word8
0xFF, Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
_ ) -> Int -> Either Int (Word8, Word8, Word8, Word8, Word8)
forall a b. a -> Either a b
Left Int
2
(Word8
_ , Word8
_ , Word8
_ , Word8
0xFF, Word8
_ , Word8
_ , Word8
_ , Word8
_ ) -> Int -> Either Int (Word8, Word8, Word8, Word8, Word8)
forall a b. a -> Either a b
Left Int
3
(Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
0xFF, Word8
_ , Word8
_ , Word8
_ ) -> Int -> Either Int (Word8, Word8, Word8, Word8, Word8)
forall a b. a -> Either a b
Left Int
4
(Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
0xFF, Word8
_ , Word8
_ ) -> Int -> Either Int (Word8, Word8, Word8, Word8, Word8)
forall a b. a -> Either a b
Left Int
5
(Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
0xFF, Word8
_ ) -> Int -> Either Int (Word8, Word8, Word8, Word8, Word8)
forall a b. a -> Either a b
Left Int
6
(Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
_ , Word8
0xFF) -> Int -> Either Int (Word8, Word8, Word8, Word8, Word8)
forall a b. a -> Either a b
Left Int
7
(Word8
ri1 , Word8
ri2 , Word8
ri3 , Word8
ri4 , Word8
ri5 , Word8
ri6 , Word8
ri7 , Word8
ri8 ) ->
let o1 :: Word8
o1 = (Word8
ri1 Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
3) Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.|. (Word8
ri2 Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
2)
o2 :: Word8
o2 = (Word8
ri2 Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
6) Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.|. (Word8
ri3 Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
1) Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.|. (Word8
ri4 Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
4)
o3 :: Word8
o3 = (Word8
ri4 Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
4) Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.|. (Word8
ri5 Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
1)
o4 :: Word8
o4 = (Word8
ri5 Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
7) Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.|. (Word8
ri6 Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
2) Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.|. (Word8
ri7 Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
3)
o5 :: Word8
o5 = (Word8
ri7 Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
5) Word8 -> Word8 -> Word8
forall bits. BitOps bits => bits -> bits -> bits
.|. Word8
ri8
in (Word8, Word8, Word8, Word8, Word8)
-> Either Int (Word8, Word8, Word8, Word8, Word8)
forall a b. b -> Either a b
Right (Word8
o1, Word8
o2, Word8
o3, Word8
o4, Word8
o5)
where
rset :: Word8 -> Word8
rset :: Word8 -> Word8
rset Word8
w = Word# -> Word8
W8# (Addr# -> Int# -> Word#
indexWord8OffAddr# Addr#
rsetTable (Word# -> Int#
word2Int# Word#
widx))
where !(W# Word#
widx) = Word8 -> Word
forall a b. IntegralUpsize a b => a -> b
integralUpsize Word8
w
!rsetTable :: Addr#
rsetTable = Addr#
"\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\
\\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\
\\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\
\\xFF\xFF\x1A\x1B\x1C\x1D\x1E\x1F\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\
\\xFF\x00\x01\x02\x03\x04\x05\x06\x07\x08\x09\x0A\x0B\x0C\x0D\x0E\
\\x0F\x10\x11\x12\x13\x14\x15\x16\x17\x18\x19\xFF\xFF\xFF\xFF\xFF\
\\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\
\\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\
\\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\
\\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\
\\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\
\\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\
\\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\
\\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\
\\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\
\\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF"#