----------------------------------------------------------------------------- -- -- Module : Data.Function.Tabulated -- Copyright : (c) 2014-16 Brian W Bush -- License : MIT -- -- Maintainer : Brian W Bush -- Stability : Experimental -- Portability : Portable -- -- | Data tables that behave as functions. -- ----------------------------------------------------------------------------- {-# LANGUAGE Safe #-} module Data.Function.Tabulated {-# DEPRECATED "This module will be replaced in a future release." #-} ( -- * One dimension DomainFunction1(..) , TabulatedFunction1(..) , TabulatedFunctionImpl1 -- * Two dimensions , DomainFunction2(..) , TabulatedFunction2(..) , TabulatedFunctionImpl2 -- * Three dimensions , DomainFunction3(..) , TabulatedFunction3(..) , TabulatedFunctionImpl3 ) where import Data.List (nub, sort) import Data.Tuple.Util (curry3, fst3, snd3, trd3) import qualified Data.Map as M -- | Class for functions of one variable, supported on a particular domain. class DomainFunction1 t where -- | The domain of the function. domain1 :: Ord a => t a -- ^ The function. -> [a] -- ^ The domain. -- | Evaluate the function. evaluate1 :: Ord a => t a -- ^ The function. -> a -- ^ The argument. -> Maybe Double -- ^ The result, if the function is defined for the argument. -- | Class for tabulated functions of one variable. class DomainFunction1 t => TabulatedFunction1 t where -- | Make a tabulated function from a table. fromTable1 :: Ord a => [(a, Double)] -- The table. -> t a -- The tabulated function. -- | Make a tabulated function for a generating function and a list of values. fromUnTable1 :: Ord a => (b -> (a, Double)) -- ^ The generating function. -> [b] -- ^ The domain for tabulation. -> t a -- ^ The tabulated function. fromUnTable1 = (fromTable1 .) . map -- | Implementation of a tabulated function of one variable. data TabulatedFunctionImpl1 a = TabulatedFunctionImpl1 [a] (M.Map a Double) deriving Show instance DomainFunction1 TabulatedFunctionImpl1 where domain1 (TabulatedFunctionImpl1 d _) = d evaluate1 (TabulatedFunctionImpl1 _ m) = flip M.lookup m instance TabulatedFunction1 TabulatedFunctionImpl1 where fromTable1 x = TabulatedFunctionImpl1 (sort $ nub $ map fst x) (M.fromList x) -- | Class for functions of two variables, supported on a particular domain. class DomainFunction2 t where -- | The domain of the function. domain2 :: (Ord a, Ord b) => t a b -- ^ The function. -> ([a], [b]) -- ^ The domain. -- | Evaluate the function. evaluate2 :: (Ord a, Ord b) => t a b -- ^ The function. -> a -- ^ The first argument. -> b -- ^ The second argument. -> Maybe Double -- ^ The result, if the function is defined for the arguments. -- | Class for tabulated functions of two variables. class DomainFunction2 t => TabulatedFunction2 t where -- | Make a tabulated function from a table. fromTable2 :: (Ord a, Ord b) => [((a, b), Double)] -- ^ The table. -> t a b -- ^ The tabulated function. -- | Make a tabulated function for a generating function and a list of values. fromUnTable2 :: (Ord a, Ord b) => (c -> ((a, b), Double)) -- ^ The generating function. -> [c] -- ^ The domain for tabulation. -> t a b -- ^ The tabulated function. fromUnTable2 = (fromTable2 .) . map -- | Implementation of a tabulated function of two variables. data TabulatedFunctionImpl2 a b = TabulatedFunctionImpl2 ([a], [b]) (M.Map (a, b) Double) deriving Show instance DomainFunction2 TabulatedFunctionImpl2 where domain2 (TabulatedFunctionImpl2 d _) = d evaluate2 (TabulatedFunctionImpl2 _ m) = curry (`M.lookup` m) instance TabulatedFunction2 TabulatedFunctionImpl2 where fromTable2 x = TabulatedFunctionImpl2 (sort $ nub $ map (fst . fst) x, sort $ nub $ map (snd . fst) x) (M.fromList x) -- | Class for functions of three variables, class DomainFunction3 t where -- | The domain of the function. domain3 :: (Ord a, Ord b, Ord c) => t a b c -- ^ The function. -> ([a], [b], [c]) -- ^ The domain. -- | Evaluate the function. evaluate3 :: (Ord a, Ord b, Ord c) => t a b c -- ^ The function. -> a -- ^ The first argument. -> b -- ^ The second argument. -> c -- ^ The third argument. -> Maybe Double -- ^ The result, if the function is defined for the arguments. -- | Class for tabulated functions of two variables. class DomainFunction3 t => TabulatedFunction3 t where -- | Make a tabulated function from a table. fromTable3 :: (Ord a, Ord b, Ord c) => [((a, b, c), Double)] -- ^ The table. -> t a b c -- ^ The tabulated function. -- | Make a tabulated function for a generating function and a list of values. fromUnTable3 :: (Ord a, Ord b, Ord c) => (d -> ((a, b, c), Double)) -- ^ The generating function. -> [d] -- ^ The domain for the tabulation. -> t a b c -- ^ THe tabulated function. fromUnTable3 = (fromTable3 .) . map -- | Implementation of a tabulated function of three variables. data TabulatedFunctionImpl3 a b c = TabulatedFunctionImpl3 ([a], [b], [c]) (M.Map (a, b, c) Double) deriving Show instance DomainFunction3 TabulatedFunctionImpl3 where domain3 (TabulatedFunctionImpl3 d _) = d evaluate3 (TabulatedFunctionImpl3 _ m) = curry3 (`M.lookup` m) instance TabulatedFunction3 TabulatedFunctionImpl3 where fromTable3 x = TabulatedFunctionImpl3 (sort $ nub $ map (fst3 . fst) x, sort $ nub $ map (snd3 . fst) x, sort $ nub $ map (trd3 . fst) x) (M.fromList x)