mixed-types-num-0.2: Alternative Prelude with numeric and logic expressions typed bottom-up

Copyright(c) Michal Konecny Pieter Collins
LicenseBSD3
Maintainermikkonecny@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

MixedTypesNumPrelude

Contents

Description

Main purpose

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

  • Dividing an integer by an integer, giving a rational, wrapped in the CN (ie Collecting NumErrors) monad:
>>> :t let n = 1 :: Integer in n/(n+1)
CN Rational
>>> :t 1/2
CN Rational

(Integer literals are always of type Integer, not Num t => t.)

  • Adding an integer and a rational, giving a rational:
>>> :t (length [x])+1/3
CN Rational

The CN monad is required because integer division can, in general, fail as it is a partial operation:

>>> 1/0
{[(ERROR,division by 0)]}

Note that when evaluating 1/0, it evaluates to the error value printed above. This is not an exception, but a special value.

When one is certain the division is well defined, one can remove CN in several ways:

>>> :t (1%2)  -- using Data.Ratio.(%), works only for integers
Rational
>>> :t (1/!2)  -- this works for non-integer division too
Rational
>>> :t (~!) (1/2) -- ~! removes CN from any type
Rational

The operator (/!) stands for division which throws an exception is the denominator is 0. It "propagates" any potential errors from the sub-expressions:

>>> :t 1/!(1 - 1/n)
CN Rational

The last example will throw an error exception when evaluated with n=1 but it will not thrown any excetion when n=0

  • taking natural, integer and fractional power using the same operator:
>>> :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, giving a seqeunce of Maybe Bool:
     if x < 0 then -x else x
     

In the last example, 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.

Testable specification

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.
  • 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ý.

More details

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

Synopsis

Re-exporting Prelude, hiding the operators we are changing

Modules with Prelude alternatives

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

Forms the ratio of two integral numbers.