{- | Module : Numeric.VariablePrecision.Precision Copyright : (c) Claude Heiland-Allen 2012 License : BSD3 Maintainer : claudiusmaximus@goto10.org Stability : unstable Portability : portable Classes for types with precision represented by a type-level natural number, and variable precision types. Note that performance may be (even) slow(er) with some versions of the type-level-natural-number package. -} module Numeric.VariablePrecision.Precision ( HasPrecision(precisionOf) , precision , atPrecision , atPrecisionOf , (.@) , VariablePrecision(adjustPrecision) , auto , withPrecision , withPrecisionOf , (.@~) , module TypeLevel.NaturalNumber , module Data.Word ) where import TypeLevel.NaturalNumber ( NaturalNumber(..), Zero, SuccessorTo, n0, successorTo ) import Data.Word (Word) -- | A class for types with precision. -- The methods must not evaluate their arguments, and their results -- must not be evaluated. -- Minimal complete definition: (none). class HasPrecision t where precisionOf :: NaturalNumber p => t p -> p precisionOf _ = undefined -- | Much like 'naturalNumberAsInt' combined with 'precisionOf'. precision :: (NaturalNumber p, HasPrecision t) => t p -> Word precision = fromIntegral . naturalNumberAsInt . precisionOf -- | Much like 'const' with a restricted type. atPrecision :: (NaturalNumber p, HasPrecision t) => t p -> p -> t p atPrecision = const -- | Much like 'const' with a restricted type. -- Precedence between '<' and '+'. atPrecisionOf :: (HasPrecision t, HasPrecision s) => t p -> s p -> t p atPrecisionOf = const -- where _ = precisionOf t `asTypeOf` precisionOf s infixl 5 `atPrecisionOf` -- | An alias for 'atPrecisionOf'. -- Precedence between '<' and '+'. (.@) :: (HasPrecision t , HasPrecision s) => t p -> s p -> t p (.@) = atPrecisionOf infixl 5 .@ -- | A class for types with adjustable precision. -- Minimal complete definition: 'adjustPrecision'. class HasPrecision t => VariablePrecision t where -- | Adjust the precision of a value preserving as much accuracy as -- possible. adjustPrecision :: (NaturalNumber p, NaturalNumber q) => t p -> t q -- | Synonym for 'adjustPrecision'. auto :: (VariablePrecision t, NaturalNumber p, NaturalNumber q) => t p -> t q auto = adjustPrecision -- | Much like 'adjustPrecision' combined with 'atPrecision'. withPrecision :: (NaturalNumber p, NaturalNumber q, VariablePrecision t) => t p -> q -> t q withPrecision s q = adjustPrecision s `atPrecision` q -- | Much like 'withPrecision' combined with 'precisionOf'. -- Precedence between '<' and '+'. withPrecisionOf :: (NaturalNumber p, NaturalNumber q, VariablePrecision t, HasPrecision s) => t p -> s q -> t q withPrecisionOf s w = s `withPrecision` precisionOf w infixl 5 `withPrecisionOf` -- | An alias for 'withPrecisionOf'. -- Precedence between '<' and '+'. (.@~) :: (NaturalNumber p, NaturalNumber q, VariablePrecision t, HasPrecision s) => t p -> s q -> t q (.@~) = withPrecisionOf infixl 5 .@~