{-# LINE 1 "Codec/Compression/QuickLZ.hsc" #-}
{-# LANGUAGE CPP, ForeignFunctionInterface #-}
{-# LINE 2 "Codec/Compression/QuickLZ.hsc" #-}

-- |
-- Module      : Codec.Compression.QuickLZ
-- Copyright   : (c) Austin Seipp 2011
-- License     : GPLv2
-- 
-- Maintainer  : as@hacks.yi.org
-- Stability   : experimental
-- Portability : portable
-- 
-- This module provides a high level 'ByteString' interface to
-- the QuickLZ library. More info about quicklz can be found here:
-- <http://quicklz.com>
-- 
-- QuickLZ is fast and compresses well.
-- The library that is bundled with this version is QuickLZ v1.5.0,
-- with the compression level set to 1.
-- 
-- Truthfully, the only laws that hold with this library are the following:
-- 
-- @(decompress . compress) == id@
-- 
-- @(decompress xs) == (decompress xs)@
-- 
-- Note that:
-- 
-- @(compress xs) == (compress xs)@
-- 
-- Does not hold.
-- QuickLZ uses random data to seed part of the compression, so the lengths
-- and compressed results can differ. But they will always decompress back
-- to the same string, e.g., @compress@ is not referentially transparent, but
-- @decompress@ is (so don't go and insert compressed data as keys into any `Data.Map`s.)
-- 
-- Arguably this is an abomination; nonetheless, this pure interface is a
-- nice abstraction.
-- 
module Codec.Compression.QuickLZ
( -- * Compressing and decompressing strict 'ByteString's
  compress      -- :: S.ByteString -> S.ByteString
, decompress    -- :: S.ByteString -> S.ByteString
) where

import Foreign
import Foreign.C

import qualified Data.ByteString.Char8 as S
import qualified Data.ByteString.Internal as SI
import qualified Data.ByteString.Unsafe as U


{-# LINE 53 "Codec/Compression/QuickLZ.hsc" #-}

-- 
-- High-level interface
-- 

-- | Compresses the input 'ByteString'.
compress :: S.ByteString -> S.ByteString
compress xs
  | S.null xs = S.empty
  | otherwise = 
      unsafePerformIO . allocaBytes qlz_state_compress_sz $ \compress_state ->
        SI.createAndTrim (S.length xs + 400) $ \output -> do
          U.unsafeUseAsCStringLen xs $ \(cstr,len) -> 
            c_qlz_compress cstr output len compress_state
{-# INLINEABLE compress #-}

-- | Decompress the input 'ByteString'.
decompress :: S.ByteString -> S.ByteString
decompress xs
  | S.null xs = S.empty
  | otherwise = 
      unsafePerformIO . allocaBytes qlz_state_decompress_sz $ \decompress_state -> do
        sz <- U.unsafeUseAsCString xs c_qlz_size_decompressed
        SI.createAndTrim sz $ \output -> do
          U.unsafeUseAsCString xs $ \cstr -> 
            c_qlz_decompress cstr output decompress_state
{-# INLINEABLE decompress #-}

-- 
-- Simple bindings to some constants
-- 
qlz_state_compress_sz :: Int
qlz_state_compress_sz = (36868)
{-# LINE 86 "Codec/Compression/QuickLZ.hsc" #-}
qlz_state_decompress_sz :: Int
qlz_state_decompress_sz = (20484)
{-# LINE 88 "Codec/Compression/QuickLZ.hsc" #-}

--
-- FFI Bindings
-- 
foreign import ccall unsafe "quicklz.h qlz_compress"
  c_qlz_compress :: Ptr a -> Ptr b -> Int -> Ptr c -> IO Int

foreign import ccall unsafe "quicklz.h qlz_decompress"
  c_qlz_decompress :: Ptr a -> Ptr b -> Ptr c -> IO Int

foreign import ccall unsafe "quicklz.h qlz_size_decompressed"
  c_qlz_size_decompressed :: CString -> IO Int