Rename unsafeCast as castUnsafe

This commit is contained in:
Adithya Kumar 2022-02-06 05:51:33 +05:30
parent b2e386a06c
commit 064b1d9db7
5 changed files with 9 additions and 9 deletions

View File

@ -91,7 +91,7 @@ module Streamly.Internal.Data.Array.Foreign
-- * Casting
, cast
, asBytes
, unsafeCast -- castUnsafe?
, castUnsafe
, asPtrUnsafe
, unsafeAsCString -- asCStringUnsafe?
, A.unsafeFreeze -- asImmutableUnsafe?
@ -525,12 +525,12 @@ streamTransform f arr =
--
-- /Pre-release/
--
unsafeCast ::
castUnsafe ::
#ifdef DEVBUILD
Storable b =>
#endif
Array a -> Array b
unsafeCast (Array contents start end) =
castUnsafe (Array contents start end) =
Array contents (castPtr start) (castPtr end)
-- | Cast an @Array a@ into an @Array Word8@.
@ -538,7 +538,7 @@ unsafeCast (Array contents start end) =
-- @since 0.8.0
--
asBytes :: Array a -> Array Word8
asBytes = unsafeCast
asBytes = castUnsafe
-- | Cast an array having elements of type @a@ into an array having elements of
-- type @b@. The length of the array should be a multiple of the size of the
@ -552,7 +552,7 @@ cast arr =
r = len `mod` SIZE_OF(b)
in if r /= 0
then Nothing
else Just $ unsafeCast arr
else Just $ castUnsafe arr
-- | Convert an array of any type into a null terminated CString Ptr.
--

View File

@ -275,4 +275,4 @@ word64le = PRK.toParserK word64leD
{-# INLINE word64host #-}
word64host :: (MonadIO m, MonadCatch m) => Parser m Word8 Word64
word64host =
fmap (A.unsafeIndex 0 . A.unsafeCast) $ PR.takeEQ 8 (A.writeN 8)
fmap (A.unsafeIndex 0 . A.castUnsafe) $ PR.takeEQ 8 (A.writeN 8)

View File

@ -499,7 +499,7 @@ data Event = Event
readOneEvent :: Parser IO Word8 Event
readOneEvent = do
arr <- PR.takeEQ 24 (A.writeN 24)
let arr1 = A.unsafeCast arr :: Array Word64
let arr1 = A.castUnsafe arr :: Array Word64
eid = A.unsafeIndex 0 arr1
eflags = A.unsafeIndex 1 arr1
pathLen = fromIntegral $ A.unsafeIndex 2 arr1

View File

@ -677,7 +677,7 @@ data Event = Event
readOneEvent :: P.Parser IO Word8 Event
readOneEvent = do
arr <- P.takeEQ 24 (A.writeN 24)
let arr1 = A.unsafeCast arr :: A.Array Word64
let arr1 = A.castUnsafe arr :: A.Array Word64
eid = A.unsafeIndex 0 arr1
eflags = A.unsafeIndex 1 arr1
pathLen = fromIntegral $ A.unsafeIndex 2 arr1

View File

@ -668,7 +668,7 @@ data Event = Event
readOneEvent :: P.Parser IO Word8 Event
readOneEvent = do
arr <- P.takeEQ 24 (A.writeN 24)
let arr1 = A.unsafeCast arr :: A.Array Word64
let arr1 = A.castUnsafe arr :: A.Array Word64
eid = A.unsafeIndex 0 arr1
eflags = A.unsafeIndex 1 arr1
pathLen = fromIntegral $ A.unsafeIndex 2 arr1