{- |
Module      :  Numeric.VariablePrecision.Precision
Copyright   :  (c) Claude Heiland-Allen 2012
License     :  BSD3

Maintainer  :  claudiusmaximus@goto10.org
Stability   :  provisional
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)
  , withPrecision
  , withPrecisionOf
  , (.@~)
  , module TypeLevel.NaturalNumber
  ) where

import TypeLevel.NaturalNumber

-- | A class for types with precision.
--   Minimal complete definition: (none).
class HasPrecision t where
  -- | Get the precision of a value. 'precisionOf' must not evaluate
  --   its argument, and its result must not be evaluated.
  precisionOf :: NaturalNumber p => t p -> p
  precisionOf _ = error "Numeric.VariablePrecision.Precision.HasPrecision.precisionOf: result evaluated"

-- | Much like 'naturalNumberAsInt' combined with 'precisionOf'.
precision :: (HasPrecision t, NaturalNumber p) => t p -> Int
precision = naturalNumberAsInt . precisionOf

-- | Much like 'const' with a restricted type.
atPrecision :: (HasPrecision t, NaturalNumber p) => t p -> p -> t p
atPrecision = const

-- | Much like 'const' with a restricted type.
atPrecisionOf
  :: (HasPrecision t, HasPrecision s, NaturalNumber p)
  => t p -> s p -> t p
atPrecisionOf = const
infixl 5 `atPrecisionOf` -- precedence between Prelude.< and Prelude.+

-- | An alias for 'atPrecisionOf'.
(.@)
  :: (HasPrecision t, HasPrecision s, NaturalNumber p)
  => t p -> s p -> t p
(.@) = atPrecisionOf
infixl 5 .@ -- precedence between Prelude.< and Prelude.+

-- | A class for types with variable precision.
--   Minimal complete definition: (all).
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

-- | Much like 'adjustPrecision' combined with 'atPrecision'.
withPrecision
  :: (VariablePrecision t, NaturalNumber p, NaturalNumber q)
  => t p -> q -> t q
withPrecision x q = adjustPrecision x `atPrecision` q

-- | Much like 'withPrecision' combined with 'precisionOf'.
withPrecisionOf
  :: (VariablePrecision t, HasPrecision s, NaturalNumber p, NaturalNumber q)
  => t p -> s q -> t q
withPrecisionOf x w = x `withPrecision` precisionOf w
infixl 5 `withPrecisionOf` -- precedence between Prelude.< and Prelude.+

-- | An alias for 'withPrecisionOf'.
(.@~)
  :: (VariablePrecision t, HasPrecision s, NaturalNumber p, NaturalNumber q)
  => t p -> s q -> t q
(.@~) = withPrecisionOf
infixl 5 .@~ -- precedence between Prelude.< and Prelude.+