{-# LANGUAGE BangPatterns #-}
module Crypto.Number.Serialize.LE
( i2osp
, os2ip
, i2ospOf
, i2ospOf_
) where
import Crypto.Number.Basic
import Crypto.Internal.Compat (unsafeDoIO)
import qualified Crypto.Internal.ByteArray as B
import qualified Crypto.Number.Serialize.Internal.LE as Internal
os2ip :: B.ByteArrayAccess ba => ba -> Integer
os2ip bs = unsafeDoIO $ B.withByteArray bs (\p -> Internal.os2ip p (B.length bs))
i2osp :: B.ByteArray ba => Integer -> ba
i2osp 0 = B.allocAndFreeze 1 (\p -> Internal.i2osp 0 p 1 >> return ())
i2osp m = B.allocAndFreeze sz (\p -> Internal.i2osp m p sz >> return ())
where
!sz = numBytes m
{-# INLINABLE i2ospOf #-}
i2ospOf :: B.ByteArray ba => Int -> Integer -> Maybe ba
i2ospOf len m
| len <= 0 = Nothing
| m < 0 = Nothing
| sz > len = Nothing
| otherwise = Just $ B.unsafeCreate len (\p -> Internal.i2ospOf m p len >> return ())
where
!sz = numBytes m
i2ospOf_ :: B.ByteArray ba => Int -> Integer -> ba
i2ospOf_ len = maybe (error "i2ospOf_: integer is larger than expected") id . i2ospOf len