-- Copyright (c) 2016-present, Facebook, Inc.
-- All rights reserved.
--
-- This source code is licensed under the BSD-style license found in
-- the LICENSE file in the root directory of this source tree. An
-- additional grant of patent rights can be found in the PATENTS file
-- in the same directory.

-- |
-- Module      : Codec.Compression.Zstd.Efficient
-- Copyright   : (c) 2016-present, Facebook, Inc. All rights reserved.
--
-- License     : BSD3
-- Maintainer  : bryano@fb.com
-- Stability   : experimental
-- Portability : GHC
--
-- These functions allow for pre-allocation and reuse of relatively
-- expensive data structures, such as compression and decompression
-- contexts and dictionaries.
--
-- If your application mostly deals with small payloads and is
-- particularly sensitive to latency or throughput, using these
-- pre-allocated structures may make a noticeable difference to
-- performance.

module Codec.Compression.Zstd.Efficient
    (
    -- * Basic entry points
      Decompress(..)
    , decompressedSize
    , C.maxCLevel

    -- ** Cheaper operations using contexts
    -- *** Compression
    , CCtx
    , withCCtx
    , compressCCtx

    -- *** Decompression
    , DCtx
    , withDCtx
    , decompressDCtx

    -- * Dictionary-based compression
    , Dict
    , mkDict
    , fromDict
    , trainFromSamples
    , getDictID

    -- ** Basic pure API
    , compressUsingDict
    , decompressUsingDict

    -- ** Pre-digested dictionaries
    , Base.CDict
    , createCDict
    , compressUsingCDict

    , Base.DDict
    , createDDict
    , decompressUsingDDict
    ) where

import Codec.Compression.Zstd.Internal
import Codec.Compression.Zstd.Types (Decompress(..), Dict(..), mkDict)
import Codec.Compression.Zstd.Base.Types (CDict(..), DDict(..))
import Data.ByteString.Internal (ByteString(..))
import Foreign.ForeignPtr (withForeignPtr)
import System.IO.Unsafe (unsafePerformIO)
import qualified Codec.Compression.Zstd.FFI as C
import qualified Codec.Compression.Zstd.Base as Base

-- | Compress the given data as a single zstd compressed frame.
compressCCtx :: CCtx
             -- ^ Compression context.
             -> Int
             -- ^ Compression level. Must be >= 1 and <= 'C.maxCLevel'.
             -> ByteString
             -- ^ Payload to compress.
             -> IO ByteString
compressCCtx :: CCtx -> Int -> ByteString -> IO ByteString
compressCCtx (CCtx Ptr CCtx
cc) Int
level ByteString
bs =
  String
-> (Ptr Word8 -> CSize -> Ptr Word8 -> CSize -> CInt -> IO CSize)
-> Int
-> ByteString
-> IO ByteString
compressWith String
"compressCCtx" (Ptr CCtx
-> Ptr Word8 -> CSize -> Ptr Word8 -> CSize -> CInt -> IO CSize
forall dst src.
Ptr CCtx
-> Ptr dst -> CSize -> Ptr src -> CSize -> CInt -> IO CSize
C.compressCCtx Ptr CCtx
cc) Int
level ByteString
bs

-- | Decompress a single-frame payload of known size.  Typically this
-- will be a payload that was compressed with 'compress'.
--
-- /Note:/ This function is not capable of decompressing a payload
-- generated by the streaming or lazy compression APIs.
decompressDCtx :: DCtx
               -- ^ Decompression context.
               -> ByteString
               -- ^ Compressed payload.
               -> IO Decompress
decompressDCtx :: DCtx -> ByteString -> IO Decompress
decompressDCtx (DCtx Ptr DCtx
cc) ByteString
bs = (Ptr Word8 -> CSize -> Ptr Word8 -> CSize -> IO CSize)
-> ByteString -> IO Decompress
decompressWith (Ptr DCtx -> Ptr Word8 -> CSize -> Ptr Word8 -> CSize -> IO CSize
forall dst src.
Ptr DCtx -> Ptr dst -> CSize -> Ptr src -> CSize -> IO CSize
C.decompressDCtx Ptr DCtx
cc) ByteString
bs

-- | Compress the given data as a single zstd compressed frame, using
-- a prebuilt dictionary.
compressUsingDict :: Dict
                  -- ^ Compression dictionary.
                  -> Int
                  -- ^ Compression level. Must be >= 1 and <= 'C.maxCLevel'.
                  -> ByteString
                  -- ^ Payload to compress.
                  -> ByteString
compressUsingDict :: Dict -> Int -> ByteString -> ByteString
compressUsingDict Dict
dict Int
level ByteString
bs =
  IO ByteString -> ByteString
forall a. IO a -> a
unsafePerformIO (IO ByteString -> ByteString)
-> ((CCtx -> IO ByteString) -> IO ByteString)
-> (CCtx -> IO ByteString)
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CCtx -> IO ByteString) -> IO ByteString
forall a. (CCtx -> IO a) -> IO a
withCCtx ((CCtx -> IO ByteString) -> ByteString)
-> (CCtx -> IO ByteString) -> ByteString
forall a b. (a -> b) -> a -> b
$ \(CCtx Ptr CCtx
ctx) ->
    Dict -> (Ptr Any -> CSize -> IO ByteString) -> IO ByteString
forall dict a. Dict -> (Ptr dict -> CSize -> IO a) -> IO a
withDict Dict
dict ((Ptr Any -> CSize -> IO ByteString) -> IO ByteString)
-> (Ptr Any -> CSize -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Any
dictPtr CSize
dictLen ->
      let compressor :: Ptr dst -> CSize -> Ptr src -> CSize -> CInt -> IO CSize
compressor Ptr dst
dp CSize
dl Ptr src
sp CSize
sl CInt
l =
            Ptr CCtx
-> Ptr dst
-> CSize
-> Ptr src
-> CSize
-> Ptr Any
-> CSize
-> CInt
-> IO CSize
forall dst src dict.
Ptr CCtx
-> Ptr dst
-> CSize
-> Ptr src
-> CSize
-> Ptr dict
-> CSize
-> CInt
-> IO CSize
C.compressUsingDict Ptr CCtx
ctx Ptr dst
dp CSize
dl Ptr src
sp CSize
sl Ptr Any
dictPtr CSize
dictLen CInt
l
      in String
-> (Ptr Word8 -> CSize -> Ptr Word8 -> CSize -> CInt -> IO CSize)
-> Int
-> ByteString
-> IO ByteString
compressWith String
"compressUsingDict" Ptr Word8 -> CSize -> Ptr Word8 -> CSize -> CInt -> IO CSize
forall dst src.
Ptr dst -> CSize -> Ptr src -> CSize -> CInt -> IO CSize
compressor Int
level ByteString
bs

-- | Decompress a single-frame payload of known size, using a prebuilt
-- dictionary.  Typically this will be a payload that was compressed
-- with 'compressUsingDict'.
--
-- /Note:/ This function is not capable of decompressing a payload
-- generated by the streaming or lazy compression APIs.
decompressUsingDict :: Dict
                    -- ^ Dictionary.
                    -> ByteString
                    -- ^ Payload to decompress.
                    -> Decompress
decompressUsingDict :: Dict -> ByteString -> Decompress
decompressUsingDict Dict
dict ByteString
bs =
  IO Decompress -> Decompress
forall a. IO a -> a
unsafePerformIO (IO Decompress -> Decompress)
-> ((DCtx -> IO Decompress) -> IO Decompress)
-> (DCtx -> IO Decompress)
-> Decompress
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DCtx -> IO Decompress) -> IO Decompress
forall a. (DCtx -> IO a) -> IO a
withDCtx ((DCtx -> IO Decompress) -> Decompress)
-> (DCtx -> IO Decompress) -> Decompress
forall a b. (a -> b) -> a -> b
$ \(DCtx Ptr DCtx
ctx) ->
    Dict -> (Ptr Any -> CSize -> IO Decompress) -> IO Decompress
forall dict a. Dict -> (Ptr dict -> CSize -> IO a) -> IO a
withDict Dict
dict ((Ptr Any -> CSize -> IO Decompress) -> IO Decompress)
-> (Ptr Any -> CSize -> IO Decompress) -> IO Decompress
forall a b. (a -> b) -> a -> b
$ \Ptr Any
dictPtr CSize
dictLen ->
      let decompressor :: Ptr dst -> CSize -> Ptr src -> CSize -> IO CSize
decompressor Ptr dst
dp CSize
dl Ptr src
sp CSize
sl =
            Ptr DCtx
-> Ptr dst
-> CSize
-> Ptr src
-> CSize
-> Ptr Any
-> CSize
-> IO CSize
forall dst src dict.
Ptr DCtx
-> Ptr dst
-> CSize
-> Ptr src
-> CSize
-> Ptr dict
-> CSize
-> IO CSize
C.decompressUsingDict Ptr DCtx
ctx Ptr dst
dp CSize
dl Ptr src
sp CSize
sl Ptr Any
dictPtr CSize
dictLen
      in (Ptr Word8 -> CSize -> Ptr Word8 -> CSize -> IO CSize)
-> ByteString -> IO Decompress
decompressWith Ptr Word8 -> CSize -> Ptr Word8 -> CSize -> IO CSize
forall dst src. Ptr dst -> CSize -> Ptr src -> CSize -> IO CSize
decompressor ByteString
bs

-- | Create a pre-digested compression dictionary.
createCDict :: Int              -- ^ Compression level.
            -> Dict             -- ^ Dictionary.
            -> CDict
createCDict :: Int -> Dict -> CDict
createCDict Int
level Dict
d = IO CDict -> CDict
forall a. IO a -> a
unsafePerformIO (IO CDict -> CDict) -> IO CDict -> CDict
forall a b. (a -> b) -> a -> b
$
  Dict -> (Ptr Any -> CSize -> IO CDict) -> IO CDict
forall dict a. Dict -> (Ptr dict -> CSize -> IO a) -> IO a
withDict Dict
d ((Ptr Any -> CSize -> IO CDict) -> IO CDict)
-> (Ptr Any -> CSize -> IO CDict) -> IO CDict
forall a b. (a -> b) -> a -> b
$ \Ptr Any
dict CSize
size -> Ptr Any -> Int -> Int -> IO CDict
forall dict. Ptr dict -> Int -> Int -> IO CDict
Base.createCDict Ptr Any
dict (CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
size) Int
level

-- | Compress the given data as a single zstd compressed frame, using
-- a pre-built, pre-digested dictionary.
compressUsingCDict :: CCtx
                   -- ^ Compression context.
                   -> CDict
                   -- ^ Compression dictionary.
                   -> ByteString
                   -- ^ Payload to compress.
                   -> IO ByteString
compressUsingCDict :: CCtx -> CDict -> ByteString -> IO ByteString
compressUsingCDict (CCtx Ptr CCtx
ctx) (CD ForeignPtr CDict
fp) ByteString
bs =
  ForeignPtr CDict -> (Ptr CDict -> IO ByteString) -> IO ByteString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr CDict
fp ((Ptr CDict -> IO ByteString) -> IO ByteString)
-> (Ptr CDict -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr CDict
dict -> do
    let compressor :: Ptr dst -> CSize -> Ptr src -> CSize -> p -> IO CSize
compressor Ptr dst
dp CSize
dl Ptr src
sp CSize
sl p
_ = Ptr CCtx
-> Ptr dst -> CSize -> Ptr src -> CSize -> Ptr CDict -> IO CSize
forall dst src.
Ptr CCtx
-> Ptr dst -> CSize -> Ptr src -> CSize -> Ptr CDict -> IO CSize
C.compressUsingCDict Ptr CCtx
ctx Ptr dst
dp CSize
dl Ptr src
sp CSize
sl Ptr CDict
dict
    String
-> (Ptr Word8 -> CSize -> Ptr Word8 -> CSize -> CInt -> IO CSize)
-> Int
-> ByteString
-> IO ByteString
compressWith String
"compressUsingCDict" Ptr Word8 -> CSize -> Ptr Word8 -> CSize -> CInt -> IO CSize
forall dst src p.
Ptr dst -> CSize -> Ptr src -> CSize -> p -> IO CSize
compressor Int
0 ByteString
bs

-- | Create a pre-digested compression dictionary.
createDDict :: Dict             -- ^ Dictionary.
            -> DDict
createDDict :: Dict -> DDict
createDDict Dict
d = IO DDict -> DDict
forall a. IO a -> a
unsafePerformIO (IO DDict -> DDict) -> IO DDict -> DDict
forall a b. (a -> b) -> a -> b
$
  Dict -> (Ptr Any -> CSize -> IO DDict) -> IO DDict
forall dict a. Dict -> (Ptr dict -> CSize -> IO a) -> IO a
withDict Dict
d ((Ptr Any -> CSize -> IO DDict) -> IO DDict)
-> (Ptr Any -> CSize -> IO DDict) -> IO DDict
forall a b. (a -> b) -> a -> b
$ \Ptr Any
dict CSize
size -> Ptr Any -> Int -> IO DDict
forall dict. Ptr dict -> Int -> IO DDict
Base.createDDict Ptr Any
dict (CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
size)

-- | Decompress a single-frame payload of known size, using a
-- pre-built, pre-digested dictionary.  Typically this will be a
-- payload that was compressed with 'compressUsingCDict'.
--
-- /Note:/ This function is not capable of decompressing a payload
-- generated by the streaming or lazy compression APIs.
decompressUsingDDict :: DCtx
                     -- ^ Decompression context.
                     -> DDict
                     -- ^ Decompression dictionary.
                     -> ByteString
                     -- ^ Payload to compress.
                     -> IO Decompress
decompressUsingDDict :: DCtx -> DDict -> ByteString -> IO Decompress
decompressUsingDDict (DCtx Ptr DCtx
ctx) (DD ForeignPtr DDict
fp) ByteString
bs =
  ForeignPtr DDict -> (Ptr DDict -> IO Decompress) -> IO Decompress
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr DDict
fp ((Ptr DDict -> IO Decompress) -> IO Decompress)
-> (Ptr DDict -> IO Decompress) -> IO Decompress
forall a b. (a -> b) -> a -> b
$ \Ptr DDict
dict -> do
    let decompressor :: Ptr dst -> CSize -> Ptr src -> CSize -> IO CSize
decompressor Ptr dst
dp CSize
dl Ptr src
sp CSize
sl = Ptr DCtx
-> Ptr dst -> CSize -> Ptr src -> CSize -> Ptr DDict -> IO CSize
forall dst src.
Ptr DCtx
-> Ptr dst -> CSize -> Ptr src -> CSize -> Ptr DDict -> IO CSize
C.decompressUsingDDict Ptr DCtx
ctx Ptr dst
dp CSize
dl Ptr src
sp CSize
sl Ptr DDict
dict
    (Ptr Word8 -> CSize -> Ptr Word8 -> CSize -> IO CSize)
-> ByteString -> IO Decompress
decompressWith Ptr Word8 -> CSize -> Ptr Word8 -> CSize -> IO CSize
forall dst src. Ptr dst -> CSize -> Ptr src -> CSize -> IO CSize
decompressor ByteString
bs