Skip to content

Commit

Permalink
Adds inspection methods for the various buffers of a blob
Browse files Browse the repository at this point in the history
```hs
> let blob =  runPut $ put ((Left 64 :: Either Word8 Word8), (Right 65 :: Either Word8 Word8))

> inspectMeta blob
"SSSDSDSSSSSDSDSSSS"

> inspectShape blob
"(((()))((())))"

> inspectContent blob
-- Unimplemented

> inspectBlob blob
"((({0}({64})))(({1}({65}))))"
```
  • Loading branch information
Quantumplation committed Aug 13, 2018
1 parent 3e37148 commit bddeea2
Showing 1 changed file with 62 additions and 12 deletions.
74 changes: 62 additions & 12 deletions src/Data/Binary/Succinct/Blob.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,14 @@
module Data.Binary.Succinct.Blob
( Blob(..)
, runPut
, blob
-- guts
, metaBitCount
, shapeBitCount
, contentByteCount
, inspectMeta
, inspectShape
, inspectContent
, inspectBlob
) where

import Control.Monad (replicateM_)
Expand All @@ -15,7 +22,9 @@ import Data.ByteString.Lazy as Lazy
import qualified Data.Vector.Storable as Storable
import HaskellWorks.Data.BalancedParens.RangeMinMax as BP
import HaskellWorks.Data.RankSelect.CsPoppy as CsPoppy
import HaskellWorks.Data.RankSelect.Base.Rank0
import Data.Vector.Storable.ByteString
import HaskellWorks.Data.BalancedParens

import Data.Binary.Succinct.Put
import Data.Binary.Succinct.Orphans ()
Expand Down Expand Up @@ -49,20 +58,61 @@ runPutM ma = case unPutM ma' (S 0 0 0 0) of
runPut :: Put -> Blob
runPut = snd . runPutM

rank1_ :: Rank1 v => v -> Word64 -> Word64
rank1_ :: Rank1 v => v -> Int -> Word64
rank1_ s i
| i <= 0 = 0
| otherwise = rank1 s i
| otherwise = rank1 s (fromIntegral i)

access :: Rank1 v => v -> Word64 -> Bool
rank0_ :: Rank0 v => v -> Int -> Word64
rank0_ s i
| i <= 0 = 0
| otherwise = rank0 s (fromIntegral i)

access :: Rank1 v => v -> Int -> Bool
access s i = toEnum $ fromIntegral $ rank1_ s i - rank1_ s (i - 1)

-- currently segfaults
blob :: Blob -> String
blob (Blob m s _c) = do
i <- [0..fromIntegral $ Storable.length (csPoppyBits m)*64-1]
-- Compute how many bits the shape index takes up
-- We use findClose on the first paren to tell us where the last meaningful paren is
shapeBitCount :: Blob -> Int
shapeBitCount (Blob _ s _) = case findClose s 1 of
Just n -> fromIntegral n
Nothing -> 0

-- Compute how many bytes the content takes up
contentByteCount :: Blob -> Int
contentByteCount (Blob _ _ c) = Strict.length c

-- Compute how many bits are non-garbage in our meta index
metaBitCount :: Blob -> Int
metaBitCount b = contentByteCount b + shapeBitCount b

-- Print out a string of S's and D's, corresponding to Shape or Data, from the meta index
inspectMeta :: Blob -> String
inspectMeta b@(Blob m _ _) = do
i <- [1..(metaBitCount b)]
case access m i of
True -> "S"
False -> "D"

-- Print out the balanced parentheses representation of our shape index
inspectShape :: Blob -> String
inspectShape b@(Blob _ s _) = do
i <- [1..(shapeBitCount b)]
case access s i of
True -> "("
False -> ")"

-- Print out our raw content buffer
-- Can't figure out how to print strict bytestrings nicely...
inspectContent :: Blob -> String
inspectContent (Blob _ _ _) = undefined

-- Print out a representation of the entire blob, interleaving shape and content
inspectBlob :: Blob -> String
inspectBlob b@(Blob m s c) = do
i <- [1..(metaBitCount b)]
case access m i of
True -> case access s (rank1_ m i) of
False -> "("
True -> ")"
False -> "D" -- data
True -> case access s (fromIntegral $ rank1_ m i) of
True -> "("
False -> ")"
False -> "{" ++ show (Strict.index c $ (fromIntegral $ rank0_ m i) - 1) ++ "}"

0 comments on commit bddeea2

Please sign in to comment.