summaryrefslogtreecommitdiff
path: root/haskell/Data/VCDIFF/Types.hsc
blob: 54237b8155e99aa658e7e25db9639942b855167d (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
{-# LANGUAGE BangPatterns               #-}
{-# LANGUAGE GADTs                      #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase                 #-}
{-# LANGUAGE PatternSynonyms            #-}
module Data.VCDIFF.Types where

import Control.Exception
import Control.Monad
import Data.Bits
import qualified Data.ByteString          as B
import qualified Data.ByteString.Internal as B
import Data.Function
import Data.Int
import Data.Monoid
import Data.Primitive.ByteArray
import qualified Data.Text                as T
import Data.Text.Encoding
import Data.Word
import Foreign.C.String
import Foreign.C.Types
import Foreign.ForeignPtr
import Foreign.Marshal.Alloc
import Foreign.Marshal.Utils
import Foreign.Ptr
import Foreign.Storable
import System.IO
import System.IO.Error
import System.IO.Unsafe



#ifndef SIZEOF_SIZE_T
#define SIZEOF_SIZE_T __SIZEOF_SIZE_T__
#define SIZEOF_UNSIGNED_INT __SIZEOF_INT__
#define SIZEOF_UNSIGNED_LONG __SIZEOF_LONG__
#define SIZEOF_UNSIGNED_LONG_LONG __SIZEOF_LONG_LONG__
#define static_assert(...)
#endif
#include <xdelta3.h>

type Usize_t = #type usize_t
-- | Printf code for type Usize_t
pattern W :: String
pattern W = #const_str W ""

type Xoff_t = #type xoff_t
-- | Printf code for type Xoff_t
pattern Q :: String
pattern Q = #const_str Q ""


-- | These are the five ordinary status codes returned by the
-- xd3_encode_input() and xd3_decode_input() state machines.
--
-- An application must be prepared to handle these five return
-- values from either xd3_encode_input or xd3_decode_input except
-- in the case of no-source compression in which case XD3_GETSRCBLK
-- is never returned.  More detailed comments for these are given in
-- xd3_encode_input and xd3_decode_input comments below.
newtype ErrorCode = ErrorCode CInt
  deriving Show

pattern XD3_SUCCESS = ErrorCode 0

-- | need input
pattern XD3_INPUT         = ErrorCode (#const XD3_INPUT)

-- | have output
pattern XD3_OUTPUT        = ErrorCode (#const XD3_OUTPUT)

-- | need a block of source input (with no xd3_getblk function) a chance to do non-blocking read.
pattern XD3_GETSRCBLK     = ErrorCode (#const XD3_GETSRCBLK)

-- | (decode-only) after the initial VCDIFF & first window header
pattern XD3_GOTHEADER     = ErrorCode (#const XD3_GOTHEADER)

-- | notification: returned before a window is processed giving a chance to XD3_SKIP_WINDOW or not XD3_SKIP_EMIT that window.
pattern XD3_WINSTART      = ErrorCode (#const XD3_WINSTART)

-- | notification: returned after encode/decode & output for a window
pattern XD3_WINFINISH     = ErrorCode (#const XD3_WINFINISH)

-- | (encoder only) may be returned by getblk() if the block is too old
pattern XD3_TOOFARBACK    = ErrorCode (#const XD3_TOOFARBACK)

-- | internal error
pattern XD3_INTERNAL      = ErrorCode (#const XD3_INTERNAL)

-- | invalid config
pattern XD3_INVALID       = ErrorCode (#const XD3_INVALID)

-- | invalid input/decoder error
pattern XD3_INVALID_INPUT = ErrorCode (#const XD3_INVALID_INPUT)

-- | when secondary compression finds no improvement.
pattern XD3_NOSECOND      = ErrorCode (#const XD3_NOSECOND)

-- | currently VCD_TARGET VCD_CODETABLE
pattern XD3_UNIMPLEMENTED = ErrorCode (#const XD3_UNIMPLEMENTED)

instance Exception ErrorCode

data Config = Config
  { winsize :: Usize_t -- ^ The encoder window size.
                       -- The encoder allocates a buffer of this size if the
                       -- program supplies input in smaller units (unless the
                       -- XD3_FLUSH flag is set).
  , sprevsz   :: Usize_t -- ^  How far back small string matching goes
  , iopt_size :: Usize_t -- ^  entries in the instruction-optimizing buffer
  , flags     :: Flags   -- ^ stream->flags are initialized from xd3_config & never modified by the library.  Use xd3_set_flags to modify flags settings mid-stream.
  , sec_data  :: CompressorConfig -- ^  Secondary compressor config: data
  , sec_inst  :: CompressorConfig -- ^  Secondary compressor config: inst
  , sec_addr  :: CompressorConfig -- ^  Secondary compressor config: addr
  , smatch_cfg :: Either StringMatcher SMatchSelect -- ^  See enum: use fields below  for soft config
  , chunk_size :: Usize_t -- ^ Suggested chunking size for streaming.
  }

pattern XD3_DEFAULT_WINSIZE = #const XD3_DEFAULT_WINSIZE
pattern XD3_DEFAULT_SPREVSZ = #const XD3_DEFAULT_SPREVSZ
pattern XD3_DEFAULT_IOPT_SIZE = #const XD3_DEFAULT_IOPT_SIZE

newtype Flags = Flags Word32
    deriving (Storable,Eq,Bits,FiniteBits)

-- used by VCDIFF tools, see xdelta3-main.h.--/
pattern XD3_JUST_HDR       = Flags (#const XD3_JUST_HDR)
-- used by VCDIFF tools see xdelta3-main.h.--/
pattern XD3_SKIP_WINDOW    = Flags (#const XD3_SKIP_WINDOW)
-- | used by VCDIFF tools, see xdelta3-main.h. */
pattern XD3_SKIP_EMIT      = Flags (#const XD3_SKIP_EMIT)
-- | flush the stream buffer to prepare for xd3_stream_close(). */
pattern XD3_FLUSH          = Flags (#const XD3_FLUSH)
-- | use DJW static huffman */
pattern XD3_SEC_DJW        = Flags (#const XD3_SEC_DJW)
-- | use FGK adaptive huffman */
pattern XD3_SEC_FGK        = Flags (#const XD3_SEC_FGK)
-- | use LZMA secondary */
pattern XD3_SEC_LZMA       = Flags (#const XD3_SEC_LZMA)
pattern XD3_SEC_TYPE       = Flags (#const XD3_SEC_TYPE)
-- | disable secondary compression of the data section. */
pattern XD3_SEC_NODATA     = Flags (#const XD3_SEC_NODATA)
-- | disable secondary compression of the inst section. */
pattern XD3_SEC_NOINST     = Flags (#const XD3_SEC_NOINST)
-- | disable secondary compression of the addr section. */
pattern XD3_SEC_NOADDR     = Flags (#const XD3_SEC_NOADDR)
pattern XD3_SEC_NOALL      = Flags (#const XD3_SEC_NOALL)
-- | enable checksum computation in the encoder. */
pattern XD3_ADLER32        = Flags (#const XD3_ADLER32)
-- | disable checksum verification in the decoder. */
pattern XD3_ADLER32_NOVER  = Flags (#const XD3_ADLER32_NOVER)
-- | disable ordinary data * compression feature, only search * the source, not the target. */
pattern XD3_NOCOMPRESS     = Flags (#const XD3_NOCOMPRESS)
-- | disable the "1.5-pass * algorithm", instead use greedy * matching.  Greedy is off by * default. */
pattern XD3_BEGREEDY       = Flags (#const XD3_BEGREEDY)
-- | used by "recode". */
pattern XD3_ADLER32_RECODE = Flags (#const XD3_ADLER32_RECODE)
-- 4 bits to set the compression level the same as the command-line
-- setting -1 through -9 Flags (-0 corresponds to the XD3_NOCOMPRESS flag
-- and is independent of compression level).  This is for
-- convenience especially with xd3_encode_memoryFlags (). */
pattern XD3_COMPLEVEL_SHIFT = #const XD3_COMPLEVEL_SHIFT
pattern XD3_COMPLEVEL_MASK  = Flags (#const XD3_COMPLEVEL_MASK)
pattern XD3_COMPLEVEL_1     = Flags (#const XD3_COMPLEVEL_1)
pattern XD3_COMPLEVEL_2     = Flags (#const XD3_COMPLEVEL_2)
pattern XD3_COMPLEVEL_3     = Flags (#const XD3_COMPLEVEL_3)
pattern XD3_COMPLEVEL_6     = Flags (#const XD3_COMPLEVEL_6)
pattern XD3_COMPLEVEL_9     = Flags (#const XD3_COMPLEVEL_9)

instance Semigroup Flags where
    Flags a <> Flags b = Flags (a .|. b)

instance Monoid Flags where
    mempty = Flags 0
    Flags a `mappend` Flags b = Flags (a .|. b)

-- | Settings for the secondary compressor.
data CompressorConfig = CompressorConfig
  { ngroups     :: Usize_t     -- ^ Number of DJW Huffman groups.
  , sector_size :: Usize_t     -- ^ Sector size.
  , inefficient :: #{type int} -- ^ If true, ignore efficiency check [avoid XD3_NOSECOND].
  }

-- | The values of this enumeration are set in xd3_config using the
-- 'smatch_cfg' variable.  It can be set to default, slow, fast, etc.,
-- and soft.
data SMatchSelect
    = SMATCH_DEFAULT -- ^ Flags may contain XD3_COMPLEVEL bits, else default.
    | SMATCH_SLOW
    | SMATCH_FAST
    | SMATCH_FASTER
    | SMATCH_FASTEST
 deriving Enum

-- | This type exists only to be a tag for Ptr to an underlying C-struct called
-- xd3_stream.
data Xd3Stream

-- | This is the record of a pre-compiled configuration, a subset of
-- xd3_config. (struct _xd3_smatcher)
data StringMatcher = StringMatcher
    { smName        :: String
    , smStringMatch :: FunPtr (Ptr Xd3Stream -> ErrorCode)
    , smLargeLook   :: Usize_t
    , smLargeStep   :: Usize_t
    , smSmallLook   :: Usize_t
    , smSmallChain  :: Usize_t
    , smSmallLchain :: Usize_t
    , smMaxLazy     :: Usize_t
    , smLongEnough  :: Usize_t
    }