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

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

Numeric.MixedTypes.Literals

Contents

Description

This module defines fixed-type integer and rational literals. This is useful when deriving the type of an expression bottom-up. Eg we would not be able to write 1 < x when the type of < does not force the two sides to be of the same type. We would need to write eg (1::Integer) < x with Prelude's generic literals.

Moreover, convenient conversion functions are provided for the most common numeric types. Thus one can say eg:

  • take (int 1)
  • integer (length list).
  • double 0.5

To avoid integer overflow, no aritmetic operations return Int. Nevertheless, one can usually mix Int with other types in expressions.

Any approximate arithmetic, ie arithmetic involving Doubles, returns values of type Double. Double values cannot be easily converted to exact types such as Rational or Integer so that all such conversions are clearly visible as labelled as inexact.

Synopsis

Fixed-type literals

fromInteger :: Integer -> Integer Source #

Replacement for fromInteger using the RebindableSyntax extension. This version of fromInteger arranges that integer literals are always of type Integer.

fromRational :: Rational -> Rational Source #

Replacement for fromRational using the RebindableSyntax extension. This version of fromRational arranges that rational literals are always of type Rational.

ifThenElse :: Bool -> t -> t -> t Source #

Restore if-then-else with RebindableSyntax

Convenient conversions

int :: CanBeInt t => t -> Int Source #

ints :: CanBeInt t => [t] -> [Int] Source #

doubles :: CanBeDouble t => [t] -> [Double] Source #

class ConvertibleExactly t1 t2 where Source #

Define our own ConvertibleExactly since convertible is too relaxed for us. For example, convertible allows conversion from Rational to Integer, rounding to nearest integer. We prefer to allow only exact conversions.

type ConvertResult a = Either ConvertError a #

The result of a safe conversion via safeConvert.

convError :: (Show a, Typeable * a, Typeable * b) => String -> a -> ConvertResult b #

Generic list index

(!!) :: CanBeInteger t => [a] -> t -> a Source #

specCanBeInteger :: (CanBeInteger t, Show t, Arbitrary t) => T t -> Spec Source #

HSpec properties that each implementation of CanBeInteger should satisfy.

printArgsIfFails2 :: (Testable prop, Show a, Show b) => String -> (a -> b -> prop) -> a -> b -> Property Source #

Testing support functions

data T t Source #

A runtime representative of type t. Used for specialising polymorphic tests to concrete types.

Constructors

T String 

Helper functions

convertFirst Source #

Arguments

:: ConvertibleExactly a b 
=> (b -> b -> c)

same-type operation

-> a -> b -> c

mixed-type operation

convertSecond Source #

Arguments

:: ConvertibleExactly b a 
=> (a -> a -> c)

same-type operation

-> a -> b -> c

mixed-type operation

convertFirstUsing Source #

Arguments

:: (a -> b -> b)

conversion function

-> (b -> b -> c)

same-type operation

-> a -> b -> c

mixed-type operation

convertSecondUsing Source #

Arguments

:: (a -> b -> a)

conversion function

-> (a -> a -> c)

same-type operation

-> a -> b -> c

mixed-type operation