-- 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
-- Copyright   : (c) 2016-present, Facebook, Inc. All rights reserved.
--
-- License     : BSD3
-- Maintainer  : bryano@fb.com
-- Stability   : experimental
-- Portability : GHC
--
-- A fast lossless compression algorithm, targeting real-time
-- compression scenarios at zlib-level and better compression ratios.

module Codec.Compression.Zstd
    (
    -- * Basic pure API
      compress
    , Decompress(..)
    , decompressedSize
    , decompress
    , C.maxCLevel

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

    -- ** Basic pure API
    , compressUsingDict
    , decompressUsingDict
    ) where

import Codec.Compression.Zstd.Internal
import Codec.Compression.Zstd.Types (Decompress(..), Dict(..), mkDict)
import Data.ByteString.Internal (ByteString(..))
import System.IO.Unsafe (unsafePerformIO)
import qualified Codec.Compression.Zstd.FFI as C

-- | Compress the given data as a single zstd compressed frame.
compress :: Int
         -- ^ Compression level. Must be >= 1 and <= 'C.maxCLevel'.
         -> ByteString
         -- ^ Payload to compress.
         -> ByteString
compress level bs = unsafePerformIO $
  compressWith "compress" C.compress level 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.
decompress :: ByteString -> Decompress
decompress bs = unsafePerformIO $ decompressWith C.decompress 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 level bs =
  unsafePerformIO . withCCtx $ \(CCtx ctx) ->
    withDict dict $ \dictPtr dictLen ->
      let compressor dp dl sp sl l =
            C.compressUsingDict ctx dp dl sp sl dictPtr dictLen l
      in compressWith "compressUsingDict" compressor level 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 bs =
  unsafePerformIO . withDCtx $ \(DCtx ctx) ->
    withDict dict $ \dictPtr dictLen ->
      let decompressor dp dl sp sl =
            C.decompressUsingDict ctx dp dl sp sl dictPtr dictLen
      in decompressWith decompressor bs