-- Copyright (c) 2014 Eric McCorkle. All rights reserved. -- -- Redistribution and use in source and binary forms, with or without -- modification, are permitted provided that the following conditions -- are met: -- -- 1. Redistributions of source code must retain the above copyright -- notice, this list of conditions and the following disclaimer. -- -- 2. Redistributions in binary form must reproduce the above copyright -- notice, this list of conditions and the following disclaimer in the -- documentation and/or other materials provided with the distribution. -- -- 3. Neither the name of the author nor the names of any contributors -- may be used to endorse or promote products derived from this software -- without specific prior written permission. -- -- THIS SOFTWARE IS PROVIDED BY THE AUTHORS AND CONTRIBUTORS ``AS IS'' -- AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED -- TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A -- PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHORS -- OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -- SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -- LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF -- USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND -- ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, -- OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT -- OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF -- SUCH DAMAGE. {-# OPTIONS_GHC -Wall -Werror #-} {-# LANGUAGE DeriveDataTypeable, ScopedTypeVariables #-} -- | ArithEncode is a library that provides tools for defining -- arithmetic encodings for arbitrary datatypes. The library is -- designed so that multiple encoding schemes can be defined for a -- given datatype, and a given encoding need not encode all possible -- instances of the datatype. -- -- An 'Encoding' is an object which is passed as the first argument -- to seven different functions. The primary function of an -- 'Encoding' is manifest in the 'encode' and 'decode' functions, -- which define an isomorphism between the datatype and the natural -- numbers (or a bounded set thereof), represented using @Integer@s. -- The 'encode' and 'decode' functions have the following properties: -- -- * @decode enc (encode enc v) == v@ for all values @v@ in the domain -- -- * @encode enc v == encode enc w@ only if @w == v@ -- -- * @decode enc n == decode enc m@ only if @n == m@ -- -- The 'inDomain' function indicates whether or not a given value is -- in the domain of the encoding. Passing a value @v@ where @inDomain -- enc v == False@ into any other function /may/ result in an -- @IllegalArgument@ exception. (For performance reasons, encodings -- are not /strictly/ required to throw @IllegalArgument@, but the -- result should not be considered valid if they do not throw the -- exception). -- -- This library provides a large collection of combinators for -- constructing more complex 'Encoding's out of simpler ones. The -- provided combinators should be appropriate for constructing -- 'Encoding's for most datatypes. -- -- As an example, the following definition creates an 'Encoding' for -- the @Tree Integer@ type: -- -- > tree :: Encoding (Tree Integer) -- > tree = -- > let -- > ... -- > nodeEncoding nodeenc = -- > wrap unmakeNode makeNode (pair interval (seq nodeenc)) -- > in -- > recursive nodeEncoding -- -- In this example, the @makeNode@ and @unmakeNode@ functios are -- simply \"glue\"; their definitions are -- -- > makeNode (label, children) = -- > Node { rootLabel = label, subForest = children } -- > -- > unmakeNode Node { rootLabel = label, subForest = children } = -- > Just (label, children) -- -- The resulting 'Encoding' maps any @Tree Integer@ to a unique -- @Integer@ value. -- -- 'Encoding's have a number of practical uses. First, all -- 'Encoding's in this library satisfy a /completeness/ property, -- which guarantees that they map each value to a finite natural -- number (or in the case of constructions on 'Encoding's, they -- preserve completeness). Hence, they can be used as an enumeration -- procedure for their underlying datatype. -- -- Second, as 'Encoding's define an isomorphism to the natural -- numbers, they provide an efficient binary encode/decode procedure -- in theory. In practice, the techniques used to guarantee the -- completeness property may result in long encodings of some types -- (particularly sequences). Also, knowledge of the distribution of -- the domain is necessary in order to achieve the most succinct -- possible encoding. module Data.ArithEncode( module Data.ArithEncode.Basic, module Data.ArithEncode.Util ) where import Data.ArithEncode.Basic import Data.ArithEncode.Util