-- |
-- Module      : Data.ByteArray.MemView
-- License     : BSD-style
-- Maintainer  : Vincent Hanquez <vincent@snarc.org>
-- Stability   : stable
-- Portability : Good
--
module Data.ByteArray.MemView
    ( MemView(..)
    , memViewPlus
    ) where

import           Foreign.Ptr
import           Data.ByteArray.Types
import           Data.Memory.Internal.Imports

-- | A simple abstraction to a piece of memory.
--
-- Do beware that garbage collection related to
-- piece of memory could be triggered before this
-- is used.
--
-- Only use with the appropriate handler has been
-- used (e.g. withForeignPtr on ForeignPtr)
--
data MemView = MemView {-# UNPACK #-} !(Ptr Word8) {-# UNPACK #-} !Int
    deriving (Int -> MemView -> ShowS
[MemView] -> ShowS
MemView -> String
(Int -> MemView -> ShowS)
-> (MemView -> String) -> ([MemView] -> ShowS) -> Show MemView
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MemView] -> ShowS
$cshowList :: [MemView] -> ShowS
show :: MemView -> String
$cshow :: MemView -> String
showsPrec :: Int -> MemView -> ShowS
$cshowsPrec :: Int -> MemView -> ShowS
Show,MemView -> MemView -> Bool
(MemView -> MemView -> Bool)
-> (MemView -> MemView -> Bool) -> Eq MemView
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemView -> MemView -> Bool
$c/= :: MemView -> MemView -> Bool
== :: MemView -> MemView -> Bool
$c== :: MemView -> MemView -> Bool
Eq)

instance ByteArrayAccess MemView where
    length :: MemView -> Int
length (MemView Ptr Word8
_ Int
l) = Int
l
    withByteArray :: MemView -> (Ptr p -> IO a) -> IO a
withByteArray (MemView Ptr Word8
p Int
_) Ptr p -> IO a
f = Ptr p -> IO a
f (Ptr Word8 -> Ptr p
forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
p)

-- | Increase the memory view while reducing the size of the window
--
-- this is useful as an abtraction to represent the current offset
-- in a buffer, and the remaining bytes left.
memViewPlus :: MemView -> Int -> MemView
memViewPlus :: MemView -> Int -> MemView
memViewPlus (MemView Ptr Word8
p Int
len) Int
n = Ptr Word8 -> Int -> MemView
MemView (Ptr Word8
p Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
n) (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n)