limp-0.3.2.0: representation of Integer Linear Programs

Safe HaskellNone
LanguageHaskell2010

Numeric.Limp.Rep

Description

Representation of integers (Z) and reals (R) of similar precision. Programs are abstracted over this, so that ideally in the future we could have a solver that produces Integers and Rationals, instead of just Ints and Doubles.

We bundle Z and R up into a single representation instead of abstracting over both, because we must be able to convert from Z to R without loss.

Synopsis

Documentation

class (Num (Z c), Ord (Z c), Eq (Z c), Integral (Z c), Num (R c), Ord (R c), Eq (R c), RealFrac (R c)) => Rep c where Source

The Representation class. Requires its members Z c and R c to be Num, Ord and Eq.

For some reason, for type inference to work, the members must be data instead of type. This gives some minor annoyances when unpacking them. See unwrapR below.

Minimal complete definition

Nothing

Associated Types

data Z c Source

Integers

data R c Source

Real numbers

Methods

fromZ :: Z c -> R c Source

Convert an integer to a real. This should not lose any precision. (whereas fromIntegral 1000 :: Word8 would lose precision)

Instances

data Assignment z r c Source

An assignment from variables to values. Maps integer variables to integers, and real variables to reals.

Constructors

Assignment (Map z (Z c)) (Map r (R c)) 

Instances

(Show (Z c), Show (R c), Show z, Show r) => Show (Assignment z r c) 
(Ord z, Ord r) => Monoid (Assignment z r c) 

zOf :: (Rep c, Ord z) => Assignment z r c -> z -> Z c Source

Retrieve value of integer variable - or 0, if there is no value.

rOf :: (Rep c, Ord r) => Assignment z r c -> r -> R c Source

Retrieve value of real variable - or 0, if there is no value.

zrOf :: (Rep c, Ord z, Ord r) => Assignment z r c -> Either z r -> R c Source

Retrieve value of an integer or real variable, with result cast to a real regardless.

data IntDouble Source

A representation that uses native 64-bit ints and 64-bit doubles. Really, this should be 32-bit ints.

Instances

Rep IntDouble 
Enum (Z IntDouble) 
Enum (R IntDouble) 
Eq (Z IntDouble) 
Eq (R IntDouble) 
Fractional (R IntDouble) 
Integral (Z IntDouble) 
Num (Z IntDouble) 
Num (R IntDouble) 
Ord (Z IntDouble) 
Ord (R IntDouble) 
Real (Z IntDouble) 
Real (R IntDouble) 
RealFrac (R IntDouble) 
Show (Z IntDouble)

Define show manually, so we can strip out the Z and R prefixes.

Show (R IntDouble) 
data Z IntDouble = Z Int 
data R IntDouble = R Double 

unwrapR :: R IntDouble -> Double Source

Convert a wrapped (R IntDouble) to an actual Double.