mixed-types-num-0.5.0.0: Alternative Prelude with numeric and logic expressions typed bottom-up
Copyright(c) Michal Konecny Pieter Collins
LicenseBSD3
Maintainermikkonecny@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

MixedTypesNumPrelude

Description

MixedTypesNumPrelude provides a version of Prelude where unary and binary operations such as not, +, == have their result type derived from the parameter type(s).

This module facilitates a single-line import for the package mixed-types-num. See the re-exported modules for further details.

Synopsis

Feature highlights

Basics

To replicate the below in ghci using stack, start it as follows:

> stack ghci mixed-types-num:lib
...> :add MixedTypesNumPrelude

Literals have a fixed type

...> :t 1
... Integer
...> :t 1.0
... Rational
...> 1 :: Rational
... Couldn't match type ‘Integer’ with ‘GHC.Real.Ratio Integer’ ...

Mixed-type operations

...> :t 1.5 + 1
... :: Rational
...> :t 1.5 * (length [[]])
... :: Rational

Dividing integers, dealing with potential error

...> :t let n = 1 in n/(n+1)
... :: Rational

To avoid runtime exceptions, it is recommended to use the CN error-collecting wrapper from package collect-errors:

...> :t let n = cn 1 in n/(n+1)
... :: CN Rational

CN is a synonym for CollectErrors [(ErrorCertaintyLevel, NumError)] Rational as defined in module Numeric.CollectErrors. The CN wrapper indicates that integer division can fail for some values:

...> let n = cn 1 in n/(n-1)
{[(division by 0,ERROR)]}

Note that the error printed above is not an exception, but a special value.

All arithmetic operations have been extended to CN types so that it is possible to have expressions that operate exclusively on CN types:

...> f (n :: CN Integer) = 1/(1/(n-1) + 1/n) :: CN Rational
...> f (cn 0)
{[(division by 0,POTENTIAL ERROR),(division by 0,ERROR)]}
...> f (cn 1)
{[(division by 0,POTENTIAL ERROR),(division by 0,ERROR)]}
...> f (cn 2)
2 % 3

The function hasError can be used to check whether any error occurred:

...> hasError (cn 1/0)
True
...> hasError (cn 1/1)
False

To extract a value from the CN wrapper, one can use function withErrorOrValue:

...> withErrorOrValue (const 0.0) id (cn 1/2)
1 % 2

The following examples require also package aern2-real. To get access to this via stack, you can start ghci eg as follows:

 stack ghci aern2-real:lib
...> :add AERN2.Real

Also other harmless potential errors can be ignored using (~!):

...> (~!) $ sqrt (pi-pi) ? (bitsS 10)
 [0.000007629... ± 7.6294e-6 <2^(-17)]
...> sqrt (pi-pi) ? (bitsS 10)
 [0.000007629... ± 7.6294e-6 <2^(-17)]{[(POTENTIAL ERROR,out of range: sqrt: argument must be >= 0: [0 ± 2.3283e-10 <2^(-32)])]}

When an error is present (which can be checked using hasErrorCN), the function hasCertainErrorCN can be used to further distinguish cases where the error is certain or potential:

...> hasCertainErrorCN (sqrt (-1) ? (bitsS 10))
True
...> hasCertainErrorCN (sqrt (pi-pi) ? (bitsS 10))
False

Natural, integer and fractional powers

...> :t 2^2
...CN Integer
...> :t 2.0^(-2)
...CN Rational
...> :t (double 2)^(1/!2)
...Double

The following examples require package aern2-real:

...> :t 2^(1/2)
...CauchyRealCN
...> :t pi
...CauchyReal
...> :t sqrt 2
...CauchyRealCN

Comparing an integer with an (exact) real number

...> let abs2 x = if x < 0 then -x else x in (abs2 (pi - pi)) ? (bitsS 100)
[0 ± <2^(-103)]{[(POTENTIAL ERROR,numeric error: union of enclosures: not enclosing the same value)]}

The potential error means that both branches were executed in parallel because the condition could not be decided, and it was moreover impossible to guarantee (in general) that both branches will return the same number. If we make a mistake, this error may appear with certainty, eg:

...> let abs2 x = if x < 0 then 1-x else x in (abs2 (pi - pi)) ? (bitsS 100)
*** Exception: WithGlobalParam ensureNoCE: [(ERROR,numeric error: union of enclosures: not enclosing the same value)]

If we are certain such errors will never appear, we can silence the potential error warnings:

...> let abs2 x = (~!) (if x < 0 then -x else x) in (abs2 (pi - pi)) ? (bitsS 100)
[0 ± <2^(-103)]

In these examples, if is overloaded so that it works for conditions of other types than Bool. Here the condition has the type Sequence (Maybe Bool). The whole expression is the sequence of balls in which those balls for which the condition is inconclusive are the union of the balls computed by both branches.

Type classes

Arithmetic operations are provided via multi-parameter type classes and the result type is given by associated type families. For example:

(+) :: (CanAddAsymmetric t1 t2) => t1 -> t2 -> AddType t1 t2

The type constraint CanAdd t1 t2 implies both CanAddAsymmetric t1 t2 and CanAddAsymmetric t2 t1.

For convenience there are other aggregate type constraints such as CanAddThis t1 t2, which implies that the result is of type t1, and CanAddSameType t, which is a shortcut for CanAddThis t t.

Notably, there are convenience classes Ring and Field.

For types that instantiate Prelude classes such as Num, one can define instances of the new classes using the default implementation, eg:

newtype II = II Integer deriving (Eq, Ord, Num) -- assuming -XGeneralizedNewtypeDeriving
instance CanAddAsymmetric II II

Conversely, if one defines instances for classes such as CanAddAsymmetric, one can then trivially define also instances of Num etc:

instance Prelude.Num T where
  (+) = (+)
  ...

Testable specifications

The arithmetic type classes are accompanied by generic hspec test suites, which are specialised to concrete instance types for their testing. These test suites include the expected algebraic properties of operations, such as commutativity and associativity of addition.

Limitations

  • Not all numerical operations are supported yet. Eg tan, atan are missing at the moment.
  • Not all Prelude numerical types are supported yet. Eg Natural and Float are not supported at present, but Double is supported.
  • Many common operations such as fromEnum, threadDelay give or require an Int value, which means we sometimes need to convert:
threadDelay (int 1000000)
integer (fromEnum True)

Prelude functions such as take, !! and length that use Int in Prelude are shadowed in MixedTypesNumPrelude with more compatible/flexible versions. Beware that Data.List.length clashes with length in MixedTypesNumPrelude.

  • Inferred types can be very large. Eg for f a b c = sqrt (a + b * c + 1) the inferred type is:
 f: (CanMulAsymmetric t1 t2, CanAddAsymmetric t4 (MulType t1 t2),
     CanAddAsymmetric (AddType t4 (MulType t1 t2)) Integer,
     CanSqrt (AddType (AddType t4 (MulType t1 t2)) Integer)) =>
    t4
    -> t1
    -> t2
    -> SqrtType (AddType (AddType t4 (MulType t1 t2)) Integer)
  • Due to limitations of some versions of ghc, type inferrence sometimes fails. Eg add1 = (+ 1) fails (eg with ghc 8.0.2) unless we explicitly declare the type add1 :: (CanAdd Integer t) => t -> AddType t Integer or use an explicit parameter, eg add1 x = x + 1.

Origin

The idea of having numeric expressions in Haskell with types derived bottom-up was initially suggested and implemented by Pieter Collins. This version is a fresh rewrite by Michal Konečný.

Re-exporting Prelude, hiding the operators we are changing

A part of package `convertible'

Modules with Prelude alternatives

Re-export for convenient Rational literals

(%) :: Integral a => a -> a -> Ratio a infixl 7 #

Forms the ratio of two integral numbers.