glpk-headers-0.4.0: Low-level Haskell bindings to GLPK.
Safe HaskellNone
LanguageHaskell2010

Math.Programming.Glpk.Header

Description

Low-level bindings to the GLPK library.

Functions and enums wrapped directly from glpk.h are undocumented; refer to the official documentation distributed with GLPK for details.

Synopsis

Helper types

Control parameters

These structures wrap the low-level control structures used to change the behavior of various solver functions. You will likely want to utilize these.

data BasisFactorizationControlParameters Source #

Instances

Instances details
Eq BasisFactorizationControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show BasisFactorizationControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Generic BasisFactorizationControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable BasisFactorizationControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

type Rep BasisFactorizationControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

type Rep BasisFactorizationControlParameters = D1 ('MetaData "BasisFactorizationControlParameters" "Math.Programming.Glpk.Header" "glpk-headers-0.4.0-inplace" 'False) (C1 ('MetaCons "BasisFactorizationControlParameters" 'PrefixI 'True) (((S1 ('MetaSel ('Just "bfcpMessageLevel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Unused GlpkMessageLevel)) :*: (S1 ('MetaSel ('Just "bfcpType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkFactorizationType) :*: S1 ('MetaSel ('Just "bfcpLUSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Unused CInt)))) :*: (S1 ('MetaSel ('Just "bfcpPivotTolerance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CDouble) :*: (S1 ('MetaSel ('Just "bfcpPivotLimit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt) :*: S1 ('MetaSel ('Just "bfcpSuhl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkControl)))) :*: ((S1 ('MetaSel ('Just "bfcpEpsilonTolerance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CDouble) :*: (S1 ('MetaSel ('Just "bfcpMaxGro") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Unused CDouble)) :*: S1 ('MetaSel ('Just "bfcpNfsMax") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt))) :*: ((S1 ('MetaSel ('Just "bfcpUpdateTolerance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Unused CDouble)) :*: S1 ('MetaSel ('Just "bfcpNrsMax") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt)) :*: (S1 ('MetaSel ('Just "bfcpRsSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Unused CInt)) :*: S1 ('MetaSel ('Just "bfcpFooBar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Unused (FixedLengthArray BfcpFooBar CDouble))))))))

data SimplexMethodControlParameters Source #

Instances

Instances details
Eq SimplexMethodControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show SimplexMethodControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Generic SimplexMethodControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Associated Types

type Rep SimplexMethodControlParameters :: Type -> Type #

GStorable SimplexMethodControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

type Rep SimplexMethodControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

type Rep SimplexMethodControlParameters = D1 ('MetaData "SimplexMethodControlParameters" "Math.Programming.Glpk.Header" "glpk-headers-0.4.0-inplace" 'False) (C1 ('MetaCons "SimplexMethodControlParameters" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "smcpMessageLevel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkMessageLevel) :*: S1 ('MetaSel ('Just "smcpMethod") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkSimplexMethod)) :*: (S1 ('MetaSel ('Just "smcpPricing") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkPricing) :*: S1 ('MetaSel ('Just "smcpRatioTest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkRatioTest))) :*: ((S1 ('MetaSel ('Just "smcpPrimalFeasibilityTolerance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Just "smcpDualFeasibilityTolerance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :*: (S1 ('MetaSel ('Just "smcpPivotTolerance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: (S1 ('MetaSel ('Just "smcpLowerObjectiveLimit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Just "smcpUpperObjectiveLimit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double))))) :*: (((S1 ('MetaSel ('Just "smcpIterationLimit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt) :*: S1 ('MetaSel ('Just "smcpTimeLimitMillis") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt)) :*: (S1 ('MetaSel ('Just "smcpOutputFrequencyMillis") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt) :*: S1 ('MetaSel ('Just "smcpOutputDelayMillis") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt))) :*: ((S1 ('MetaSel ('Just "smcpPresolve") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkPresolve) :*: S1 ('MetaSel ('Just "smcpExcl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Unused CInt))) :*: (S1 ('MetaSel ('Just "smcpShift") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Unused CInt)) :*: (S1 ('MetaSel ('Just "smcpAOrN") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Unused CInt)) :*: S1 ('MetaSel ('Just "smcpFooBar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Unused (FixedLengthArray SmcpFooBar CDouble)))))))))

data InteriorPointControlParameters Source #

Instances

Instances details
Eq InteriorPointControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show InteriorPointControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Generic InteriorPointControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Associated Types

type Rep InteriorPointControlParameters :: Type -> Type #

GStorable InteriorPointControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

type Rep InteriorPointControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

type Rep InteriorPointControlParameters = D1 ('MetaData "InteriorPointControlParameters" "Math.Programming.Glpk.Header" "glpk-headers-0.4.0-inplace" 'False) (C1 ('MetaCons "InteriorPointControlParameters" 'PrefixI 'True) (S1 ('MetaSel ('Just "iptcpMessageLevel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkMessageLevel) :*: (S1 ('MetaSel ('Just "iptcpOrderingAlgorithm") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkPreCholeskyOrdering) :*: S1 ('MetaSel ('Just "iptcpFooBar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Unused (FixedLengthArray IptcpFooBar CDouble))))))

data MIPControlParameters a Source #

Instances

Instances details
Eq (MIPControlParameters a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show (MIPControlParameters a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Generic (MIPControlParameters a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Associated Types

type Rep (MIPControlParameters a) :: Type -> Type #

GStorable (MIPControlParameters a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

type Rep (MIPControlParameters a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

type Rep (MIPControlParameters a) = D1 ('MetaData "MIPControlParameters" "Math.Programming.Glpk.Header" "glpk-headers-0.4.0-inplace" 'False) (C1 ('MetaCons "MIPControlParameters" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "iocpMessageLevel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkMessageLevel) :*: (S1 ('MetaSel ('Just "iocpBranchingTechnique") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkBranchingTechnique) :*: S1 ('MetaSel ('Just "iocpBacktrackingTechnique") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkBacktrackingTechnique))) :*: ((S1 ('MetaSel ('Just "iocpAbsoluteFeasibilityTolerance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CDouble) :*: S1 ('MetaSel ('Just "iocpRelativeObjectiveTolerance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CDouble)) :*: (S1 ('MetaSel ('Just "iocpTimeLimitMillis") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt) :*: S1 ('MetaSel ('Just "iocpOutputFrequencyMillis") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt)))) :*: ((S1 ('MetaSel ('Just "iocpOutputDelayMillis") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt) :*: (S1 ('MetaSel ('Just "iocpCallback") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (FunPtr (Ptr (GlpkTree a) -> Ptr a -> IO ()))) :*: S1 ('MetaSel ('Just "iocpNodeData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ptr a)))) :*: ((S1 ('MetaSel ('Just "iocpNodeDataSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt) :*: S1 ('MetaSel ('Just "iocpPreprocessingTechnique") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkPreProcessingTechnique)) :*: (S1 ('MetaSel ('Just "iocpRelativeMIPGap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CDouble) :*: S1 ('MetaSel ('Just "iocpMIRCuts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkMIRCuts))))) :*: (((S1 ('MetaSel ('Just "iocpGormoryCuts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkGomoryCuts) :*: (S1 ('MetaSel ('Just "iocpCoverCuts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkCoverCuts) :*: S1 ('MetaSel ('Just "iocpCliqueCuts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkCliqueCuts))) :*: ((S1 ('MetaSel ('Just "iocpPresolve") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkPresolve) :*: S1 ('MetaSel ('Just "iocpBinarization") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkBinarization)) :*: (S1 ('MetaSel ('Just "iocpFeasibilityPump") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkFeasibilityPump) :*: S1 ('MetaSel ('Just "iocpProximitySearch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkProximitySearch)))) :*: ((S1 ('MetaSel ('Just "iocpProximityTimeLimitMillis") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt) :*: (S1 ('MetaSel ('Just "iocpSimpleRounding") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkSimpleRounding) :*: S1 ('MetaSel ('Just "iocpUseExistingSolution") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Unused CInt)))) :*: ((S1 ('MetaSel ('Just "iocpNewSolutionFileName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Unused (Ptr CChar))) :*: S1 ('MetaSel ('Just "iocpUseAlienSolver") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Unused CInt))) :*: (S1 ('MetaSel ('Just "iocpUseLongStepDual") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Unused CInt)) :*: S1 ('MetaSel ('Just "iocpFooBar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Unused (FixedLengthArray IocpFooBar CDouble)))))))))

data MPSControlParameters Source #

Instances

Instances details
Eq MPSControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show MPSControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Generic MPSControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Associated Types

type Rep MPSControlParameters :: Type -> Type #

GStorable MPSControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

type Rep MPSControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

type Rep MPSControlParameters = D1 ('MetaData "MPSControlParameters" "Math.Programming.Glpk.Header" "glpk-headers-0.4.0-inplace" 'False) (C1 ('MetaCons "MPSControlParameters" 'PrefixI 'True) ((S1 ('MetaSel ('Just "mpscpBlank") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt) :*: S1 ('MetaSel ('Just "mpscpObjectiveName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CString)) :*: (S1 ('MetaSel ('Just "mpscpZeroTolerance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CDouble) :*: S1 ('MetaSel ('Just "mpscpFooBar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Unused (FixedLengthArray MpscpFooBar CDouble))))))

data CplexLPFormatControlParameters Source #

Instances

Instances details
Eq CplexLPFormatControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show CplexLPFormatControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Generic CplexLPFormatControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Associated Types

type Rep CplexLPFormatControlParameters :: Type -> Type #

GStorable CplexLPFormatControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

type Rep CplexLPFormatControlParameters Source # 
Instance details

Defined in Math.Programming.Glpk.Header

type Rep CplexLPFormatControlParameters = D1 ('MetaData "CplexLPFormatControlParameters" "Math.Programming.Glpk.Header" "glpk-headers-0.4.0-inplace" 'False) (C1 ('MetaCons "CplexLPFormatControlParameters" 'PrefixI 'True) (S1 ('MetaSel ('Just "cpxcpFooBar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Unused (FixedLengthArray CpxcpFooBar CDouble)))))

data GlpkCutAttribute Source #

Instances

Instances details
Eq GlpkCutAttribute Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkCutAttribute Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Generic GlpkCutAttribute Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Associated Types

type Rep GlpkCutAttribute :: Type -> Type #

GStorable GlpkCutAttribute Source # 
Instance details

Defined in Math.Programming.Glpk.Header

type Rep GlpkCutAttribute Source # 
Instance details

Defined in Math.Programming.Glpk.Header

type Rep GlpkCutAttribute = D1 ('MetaData "GlpkCutAttribute" "Math.Programming.Glpk.Header" "glpk-headers-0.4.0-inplace" 'False) (C1 ('MetaCons "GlpkCutAttribute" 'PrefixI 'True) ((S1 ('MetaSel ('Just "attrLevel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt) :*: S1 ('MetaSel ('Just "attrContraintOrigin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkConstraintOrigin)) :*: (S1 ('MetaSel ('Just "attrCutType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlpkCutType) :*: S1 ('MetaSel ('Just "attrFooBar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Unused (FixedLengthArray AttrFooBar CDouble))))))

newtype GlpkUserCutType Source #

Constructors

GlpkUserCutType 

Instances

Instances details
Enum GlpkUserCutType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Eq GlpkUserCutType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkUserCutType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkUserCutType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkUserCutType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkUserCutType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GLPK arrays

GLPK uses a 1-based indexing for arrays. This is accomplished by ignoring the 0th entry.

newtype GlpkArray a Source #

An array whose data begins at index 1

Constructors

GlpkArray 

Fields

Instances

Instances details
Eq (GlpkArray a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Methods

(==) :: GlpkArray a -> GlpkArray a -> Bool #

(/=) :: GlpkArray a -> GlpkArray a -> Bool #

Ord (GlpkArray a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show (GlpkArray a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable (GlpkArray a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Methods

sizeOf :: GlpkArray a -> Int #

alignment :: GlpkArray a -> Int #

peekElemOff :: Ptr (GlpkArray a) -> Int -> IO (GlpkArray a) #

pokeElemOff :: Ptr (GlpkArray a) -> Int -> GlpkArray a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (GlpkArray a) #

pokeByteOff :: Ptr b -> Int -> GlpkArray a -> IO () #

peek :: Ptr (GlpkArray a) -> IO (GlpkArray a) #

poke :: Ptr (GlpkArray a) -> GlpkArray a -> IO () #

mallocGlpkArray :: Storable a => [a] -> IO (GlpkArray a) Source #

Create a new GlpkArray.

allocaGlpkArray :: Storable a => [a] -> (GlpkArray a -> IO b) -> IO b Source #

Run a computation with a temporary GlpkArray.

initGlpkArray :: Storable a => [a] -> Ptr a -> IO (GlpkArray a) Source #

Set the contents of a GlpkArray from a list.

class FixedLength a where Source #

The class of arrays of fixed length.

Methods

fixedLength :: a -> Int Source #

newtype FixedLengthArray a b Source #

A type representing fixed-length array members of structs.

Constructors

FixedLengthArray 

Fields

Instances

Instances details
Eq b => Eq (FixedLengthArray a b) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord b => Ord (FixedLengthArray a b) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read b => Read (FixedLengthArray a b) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show b => Show (FixedLengthArray a b) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

(FixedLength a, Storable b) => GStorable (FixedLengthArray a b) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Low-level and phantom types

newtype GlpkInt a Source #

Wrapper around CInt values, tagged with a phantom type to help track what it refers to.

Constructors

GlpkInt 

Fields

Instances

Instances details
Enum (GlpkInt a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Methods

succ :: GlpkInt a -> GlpkInt a #

pred :: GlpkInt a -> GlpkInt a #

toEnum :: Int -> GlpkInt a #

fromEnum :: GlpkInt a -> Int #

enumFrom :: GlpkInt a -> [GlpkInt a] #

enumFromThen :: GlpkInt a -> GlpkInt a -> [GlpkInt a] #

enumFromTo :: GlpkInt a -> GlpkInt a -> [GlpkInt a] #

enumFromThenTo :: GlpkInt a -> GlpkInt a -> GlpkInt a -> [GlpkInt a] #

Eq (GlpkInt a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Methods

(==) :: GlpkInt a -> GlpkInt a -> Bool #

(/=) :: GlpkInt a -> GlpkInt a -> Bool #

Integral (GlpkInt a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Methods

quot :: GlpkInt a -> GlpkInt a -> GlpkInt a #

rem :: GlpkInt a -> GlpkInt a -> GlpkInt a #

div :: GlpkInt a -> GlpkInt a -> GlpkInt a #

mod :: GlpkInt a -> GlpkInt a -> GlpkInt a #

quotRem :: GlpkInt a -> GlpkInt a -> (GlpkInt a, GlpkInt a) #

divMod :: GlpkInt a -> GlpkInt a -> (GlpkInt a, GlpkInt a) #

toInteger :: GlpkInt a -> Integer #

Num (GlpkInt a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Methods

(+) :: GlpkInt a -> GlpkInt a -> GlpkInt a #

(-) :: GlpkInt a -> GlpkInt a -> GlpkInt a #

(*) :: GlpkInt a -> GlpkInt a -> GlpkInt a #

negate :: GlpkInt a -> GlpkInt a #

abs :: GlpkInt a -> GlpkInt a #

signum :: GlpkInt a -> GlpkInt a #

fromInteger :: Integer -> GlpkInt a #

Ord (GlpkInt a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Methods

compare :: GlpkInt a -> GlpkInt a -> Ordering #

(<) :: GlpkInt a -> GlpkInt a -> Bool #

(<=) :: GlpkInt a -> GlpkInt a -> Bool #

(>) :: GlpkInt a -> GlpkInt a -> Bool #

(>=) :: GlpkInt a -> GlpkInt a -> Bool #

max :: GlpkInt a -> GlpkInt a -> GlpkInt a #

min :: GlpkInt a -> GlpkInt a -> GlpkInt a #

Read (GlpkInt a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Real (GlpkInt a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Methods

toRational :: GlpkInt a -> Rational #

Show (GlpkInt a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Methods

showsPrec :: Int -> GlpkInt a -> ShowS #

show :: GlpkInt a -> String #

showList :: [GlpkInt a] -> ShowS #

Storable (GlpkInt a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Methods

sizeOf :: GlpkInt a -> Int #

alignment :: GlpkInt a -> Int #

peekElemOff :: Ptr (GlpkInt a) -> Int -> IO (GlpkInt a) #

pokeElemOff :: Ptr (GlpkInt a) -> Int -> GlpkInt a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (GlpkInt a) #

pokeByteOff :: Ptr b -> Int -> GlpkInt a -> IO () #

peek :: Ptr (GlpkInt a) -> IO (GlpkInt a) #

poke :: Ptr (GlpkInt a) -> GlpkInt a -> IO () #

data Problem Source #

A phantom type representing a problem in GLPK.

data GlpkColumn Source #

Phantom type used to denote data as being a column.

data GlpkRow Source #

Phantom type used to denote data as being a row.

data GlpkNodeIndex Source #

Phantom type used to denote data as being a node index.

data GlpkTree a Source #

Phantom type indicating the data stored in MIP callbacks.

data MathProgWorkspace Source #

Phantom type used to denote pointers to workspaces.

type Row = GlpkInt GlpkRow Source #

Convenient alias for rows.

type Column = GlpkInt GlpkColumn Source #

Convenient alias for columns.

newtype MathProgResult Source #

Constructors

MathProgResult 

Instances

Instances details
Enum MathProgResult Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Eq MathProgResult Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord MathProgResult Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read MathProgResult Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show MathProgResult Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable MathProgResult Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Undocumented and unused structures

newtype Unused a Source #

A type used to represent an unused or undocumented struct member.

Constructors

Unused 

Fields

Instances

Instances details
Enum a => Enum (Unused a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Methods

succ :: Unused a -> Unused a #

pred :: Unused a -> Unused a #

toEnum :: Int -> Unused a #

fromEnum :: Unused a -> Int #

enumFrom :: Unused a -> [Unused a] #

enumFromThen :: Unused a -> Unused a -> [Unused a] #

enumFromTo :: Unused a -> Unused a -> [Unused a] #

enumFromThenTo :: Unused a -> Unused a -> Unused a -> [Unused a] #

Eq a => Eq (Unused a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Methods

(==) :: Unused a -> Unused a -> Bool #

(/=) :: Unused a -> Unused a -> Bool #

Ord a => Ord (Unused a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Methods

compare :: Unused a -> Unused a -> Ordering #

(<) :: Unused a -> Unused a -> Bool #

(<=) :: Unused a -> Unused a -> Bool #

(>) :: Unused a -> Unused a -> Bool #

(>=) :: Unused a -> Unused a -> Bool #

max :: Unused a -> Unused a -> Unused a #

min :: Unused a -> Unused a -> Unused a #

Read a => Read (Unused a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show a => Show (Unused a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Methods

showsPrec :: Int -> Unused a -> ShowS #

show :: Unused a -> String #

showList :: [Unused a] -> ShowS #

Storable a => Storable (Unused a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Methods

sizeOf :: Unused a -> Int #

alignment :: Unused a -> Int #

peekElemOff :: Ptr (Unused a) -> Int -> IO (Unused a) #

pokeElemOff :: Ptr (Unused a) -> Int -> Unused a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Unused a) #

pokeByteOff :: Ptr b -> Int -> Unused a -> IO () #

peek :: Ptr (Unused a) -> IO (Unused a) #

poke :: Ptr (Unused a) -> Unused a -> IO () #

GStorable a => GStorable (Unused a) Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Methods

gsizeOf :: Unused a -> Int #

galignment :: Unused a -> Int #

gpeekByteOff :: Ptr b -> Int -> IO (Unused a) #

gpokeByteOff :: Ptr b -> Int -> Unused a -> IO () #

data BfcpFooBar Source #

Instances

Instances details
FixedLength BfcpFooBar Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data SmcpFooBar Source #

Instances

Instances details
FixedLength SmcpFooBar Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data IptcpFooBar Source #

Instances

Instances details
FixedLength IptcpFooBar Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data IocpFooBar Source #

Instances

Instances details
FixedLength IocpFooBar Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data AttrFooBar Source #

Instances

Instances details
FixedLength AttrFooBar Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data MpscpFooBar Source #

Instances

Instances details
FixedLength MpscpFooBar Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data CpxcpFooBar Source #

Instances

Instances details
FixedLength CpxcpFooBar Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GLPK API

Enums

data GlpkMajorVersion Source #

Instances

Instances details
Eq GlpkMajorVersion Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkMajorVersion Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkMajorVersion Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkMajorVersion Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkMajorVersion Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkMinorVersion Source #

Instances

Instances details
Eq GlpkMinorVersion Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkMinorVersion Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkMinorVersion Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkMinorVersion Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkMinorVersion Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkDirection Source #

Instances

Instances details
Eq GlpkDirection Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkDirection Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkDirection Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkDirection Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkDirection Source # 
Instance details

Defined in Math.Programming.Glpk.Header

newtype GlpkVariableType Source #

Instances

Instances details
Eq GlpkVariableType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkVariableType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkVariableType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkVariableType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkVariableType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable GlpkVariableType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkConstraintType Source #

Instances

Instances details
Eq GlpkConstraintType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkConstraintType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkConstraintType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkConstraintType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkConstraintType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkVariableStatus Source #

Instances

Instances details
Eq GlpkVariableStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkVariableStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkVariableStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkVariableStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkVariableStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkScaling Source #

Instances

Instances details
Eq GlpkScaling Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkScaling Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkScaling Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkScaling Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkScaling Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkSolutionType Source #

Instances

Instances details
Eq GlpkSolutionType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkSolutionType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkSolutionType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkSolutionType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkSolutionType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkSolutionStatus Source #

Instances

Instances details
Eq GlpkSolutionStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkSolutionStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkSolutionStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkSolutionStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkSolutionStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkMessageLevel Source #

Instances

Instances details
Eq GlpkMessageLevel Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkMessageLevel Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkMessageLevel Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkMessageLevel Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkMessageLevel Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable GlpkMessageLevel Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkSimplexMethod Source #

Instances

Instances details
Eq GlpkSimplexMethod Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkSimplexMethod Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkSimplexMethod Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkSimplexMethod Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkSimplexMethod Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable GlpkSimplexMethod Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkPricing Source #

Instances

Instances details
Eq GlpkPricing Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkPricing Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkPricing Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkPricing Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkPricing Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable GlpkPricing Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkRatioTest Source #

Instances

Instances details
Eq GlpkRatioTest Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkRatioTest Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkRatioTest Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkRatioTest Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkRatioTest Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable GlpkRatioTest Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkPreCholeskyOrdering Source #

Instances

Instances details
Eq GlpkPreCholeskyOrdering Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkPreCholeskyOrdering Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkPreCholeskyOrdering Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkPreCholeskyOrdering Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkPreCholeskyOrdering Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable GlpkPreCholeskyOrdering Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkBranchingTechnique Source #

Instances

Instances details
Eq GlpkBranchingTechnique Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkBranchingTechnique Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkBranchingTechnique Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkBranchingTechnique Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkBranchingTechnique Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable GlpkBranchingTechnique Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkBacktrackingTechnique Source #

Instances

Instances details
Eq GlpkBacktrackingTechnique Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkBacktrackingTechnique Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkBacktrackingTechnique Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkBacktrackingTechnique Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkBacktrackingTechnique Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable GlpkBacktrackingTechnique Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkPreProcessingTechnique Source #

Instances

Instances details
Eq GlpkPreProcessingTechnique Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkPreProcessingTechnique Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkPreProcessingTechnique Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkPreProcessingTechnique Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkPreProcessingTechnique Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable GlpkPreProcessingTechnique Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkFeasibilityPump Source #

Instances

Instances details
Eq GlpkFeasibilityPump Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkFeasibilityPump Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkFeasibilityPump Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkFeasibilityPump Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkFeasibilityPump Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable GlpkFeasibilityPump Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkProximitySearch Source #

Instances

Instances details
Eq GlpkProximitySearch Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkProximitySearch Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkProximitySearch Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkProximitySearch Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkProximitySearch Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable GlpkProximitySearch Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkGomoryCuts Source #

Instances

Instances details
Eq GlpkGomoryCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkGomoryCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkGomoryCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkGomoryCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkGomoryCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable GlpkGomoryCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkMIRCuts Source #

Instances

Instances details
Eq GlpkMIRCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkMIRCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkMIRCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkMIRCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkMIRCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable GlpkMIRCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkCoverCuts Source #

Instances

Instances details
Eq GlpkCoverCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkCoverCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkCoverCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkCoverCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkCoverCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable GlpkCoverCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkCliqueCuts Source #

Instances

Instances details
Eq GlpkCliqueCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkCliqueCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkCliqueCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkCliqueCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkCliqueCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable GlpkCliqueCuts Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkPresolve Source #

Instances

Instances details
Eq GlpkPresolve Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkPresolve Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkPresolve Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkPresolve Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkPresolve Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable GlpkPresolve Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkBinarization Source #

Instances

Instances details
Eq GlpkBinarization Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkBinarization Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkBinarization Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkBinarization Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkBinarization Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable GlpkBinarization Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkSimpleRounding Source #

Instances

Instances details
Eq GlpkSimpleRounding Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkSimpleRounding Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkSimpleRounding Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkSimpleRounding Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkSimpleRounding Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable GlpkSimpleRounding Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkConstraintOrigin Source #

Instances

Instances details
Eq GlpkConstraintOrigin Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkConstraintOrigin Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkConstraintOrigin Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkConstraintOrigin Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkConstraintOrigin Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable GlpkConstraintOrigin Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkCutType Source #

Instances

Instances details
Eq GlpkCutType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkCutType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkCutType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkCutType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkCutType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable GlpkCutType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkControl Source #

Instances

Instances details
Eq GlpkControl Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkControl Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkControl Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkControl Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkControl Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable GlpkControl Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkCallbackReason Source #

Instances

Instances details
Eq GlpkCallbackReason Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkCallbackReason Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkCallbackReason Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkCallbackReason Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkCallbackReason Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkBranchOption Source #

Instances

Instances details
Eq GlpkBranchOption Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkBranchOption Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkBranchOption Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkBranchOption Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkBranchOption Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkFactorizationResult Source #

Instances

Instances details
Eq GlpkFactorizationResult Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkFactorizationResult Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkFactorizationResult Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkFactorizationResult Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkFactorizationResult Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkSimplexStatus Source #

Instances

Instances details
Eq GlpkSimplexStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkSimplexStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkSimplexStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkSimplexStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkSimplexStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkMIPStatus Source #

Instances

Instances details
Eq GlpkMIPStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkMIPStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkMIPStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkMIPStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkMIPStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkInteriorPointStatus Source #

Instances

Instances details
Eq GlpkInteriorPointStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkInteriorPointStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkInteriorPointStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkInteriorPointStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkInteriorPointStatus Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkKKTCheck Source #

Instances

Instances details
Eq GlpkKKTCheck Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkKKTCheck Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkKKTCheck Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkKKTCheck Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkKKTCheck Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkMPSFormat Source #

Instances

Instances details
Eq GlpkMPSFormat Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkMPSFormat Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkMPSFormat Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkMPSFormat Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkMPSFormat Source # 
Instance details

Defined in Math.Programming.Glpk.Header

data GlpkFactorizationType Source #

Instances

Instances details
Eq GlpkFactorizationType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Ord GlpkFactorizationType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Read GlpkFactorizationType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Show GlpkFactorizationType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Storable GlpkFactorizationType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

GStorable GlpkFactorizationType Source # 
Instance details

Defined in Math.Programming.Glpk.Header

Functions

glp_create_prob Source #

Arguments

:: IO (Ptr Problem)

The allocated problem instance

glp_delete_prob Source #

Arguments

:: Ptr Problem

The problem instance

-> IO () 

glp_set_prob_name Source #

Arguments

:: Ptr Problem

The problem instance

-> CString

The problem name

-> IO () 

glp_set_obj_name Source #

Arguments

:: Ptr Problem

The problem instance

-> CString

The objective name

-> IO () 

glp_set_obj_dir Source #

Arguments

:: Ptr Problem

The problem instance

-> GlpkDirection

Whether the problem is a minimization or maximization problem

-> IO () 

glp_add_rows Source #

Arguments

:: Ptr Problem

The problem instance

-> CInt

The number of constraints to add

-> IO Row

The index of the first new constraint added

glp_add_cols Source #

Arguments

:: Ptr Problem

The problem instance

-> CInt

The number of variables to add

-> IO Column

The index of the first new variable added

glp_set_row_name Source #

Arguments

:: Ptr Problem

The problem instance

-> Row

The constraint being named

-> CString

The name of the constraint

-> IO () 

glp_set_col_name Source #

Arguments

:: Ptr Problem

The problem instance

-> Column

The variable being named

-> CString

The name of the variable

-> IO () 

glp_set_row_bnds Source #

Arguments

:: Ptr Problem

The problem instance

-> Row

The constraint being bounded

-> GlpkConstraintType

The type of constraint

-> CDouble

The lower bound

-> CDouble

The upper bound

-> IO () 

glp_set_col_bnds Source #

Arguments

:: Ptr Problem

The problem instance

-> Column

The variable being bounded

-> GlpkConstraintType

The type of constraint

-> CDouble

The lower bound

-> CDouble

The upper bound

-> IO () 

glp_set_obj_coef Source #

Arguments

:: Ptr Problem

The problem instance

-> Column

The variable

-> CDouble

The objective coefficient

-> IO () 

glp_set_mat_row Source #

Arguments

:: Ptr Problem

The problem instance

-> Row

The constraint being modified

-> CInt

The number of variables being set

-> GlpkArray Column

The variables being set

-> GlpkArray CDouble

The variable coefficients

-> IO () 

glp_set_mat_col Source #

Arguments

:: Ptr Problem

The problem instance

-> Column

The variable being modified

-> CInt

The number of coefficients being set

-> Ptr Row

The constraints being modified

-> GlpkArray CDouble

The variable coefficients

-> IO () 

glp_load_matrix Source #

Arguments

:: Ptr Problem

The problem instance

-> CInt

The number of nonzero elements to be loaded

-> GlpkArray Row

The constraint indices

-> GlpkArray Column

The variable indices

-> GlpkArray CDouble

The coefficients

-> IO () 

glp_check_dup Source #

Arguments

:: CInt

The number of rows in the matrix

-> CInt

The number of columns in the matrix

-> CInt

The number of nonzeros in the matrix

-> GlpkArray CInt

The rows being checked

-> GlpkArray CInt

The columns being checked

-> CInt 

glp_sort_matrix Source #

Arguments

:: Ptr Problem

The problem instance

-> IO () 

glp_del_rows Source #

Arguments

:: Ptr Problem

The problem instance

-> CInt

The number of constraints to delete

-> GlpkArray Row

The indices of the constraints to delete

-> IO () 

glp_del_cols Source #

Arguments

:: Ptr Problem

The problem instance

-> CInt

The number of variables to delete

-> GlpkArray Column

The indices of the variables to delete

-> IO () 

glp_copy_prob Source #

Arguments

:: Ptr Problem

The destination problem instance

-> Ptr Problem

The problem instance to be copied

-> GlpkControl

Whether to copy symbolic names

-> IO () 

glp_erase_prob Source #

Arguments

:: Ptr Problem

The problem instance

-> IO () 

glp_get_prob_name Source #

Arguments

:: Ptr Problem

The problem instance

-> IO CString

The name of the problem

glp_get_obj_name Source #

Arguments

:: Ptr Problem

The problem instance

-> IO CString

The name of the objective

glp_get_obj_dir Source #

Arguments

:: Ptr Problem

The problem instance

-> IO GlpkDirection

The direction of the objective

glp_get_num_rows Source #

Arguments

:: Ptr Problem

The problem instance

-> IO CInt

The number of constraints

glp_get_num_cols Source #

Arguments

:: Ptr Problem

The problem instance

-> IO CInt

The number of variables

glp_get_row_name Source #

Arguments

:: Ptr Problem

The problem instance

-> Row

The index of the constraint

-> IO CString

The constraint name

glp_get_col_name Source #

Arguments

:: Ptr Problem

The problem instance

-> Column

The index of the variable

-> IO CString

The variable name

glp_get_row_type Source #

Arguments

:: Ptr Problem

The problem instance

-> Row

The index of the constraint

-> IO GlpkConstraintType

The constraint type

glp_get_row_lb Source #

Arguments

:: Ptr Problem

The problem instance

-> Row

The index of the constraint

-> IO CDouble

The constraint lower bound

glp_get_row_ub Source #

Arguments

:: Ptr Problem

The problem instance

-> Row

The index of the constraint

-> IO CDouble

The constraint upper bound

glp_get_col_type Source #

Arguments

:: Ptr Problem

The problem instance

-> Column

The index of the variable

-> IO GlpkVariableType

The constraint type

glp_get_col_lb Source #

Arguments

:: Ptr Problem

The problem instance

-> Column

The index of the variable

-> IO CDouble

The variable lower bound

glp_get_col_ub Source #

Arguments

:: Ptr Problem

The problem instance

-> Column

The index of the variable

-> IO CDouble

The variable upper bound

glp_get_obj_coef Source #

Arguments

:: Ptr Problem

The problem instance

-> Column

The index of the variable

-> IO CDouble

The objective coefficient

glp_get_num_nz Source #

Arguments

:: Ptr Problem

The problem instance

-> IO CInt

The number of nonzero constraint coefficients

glp_get_mat_row Source #

Arguments

:: Ptr Problem

The problem instance

-> Row

The constraint to retrieve

-> GlpkArray Column

The variable indices in the constraint

-> GlpkArray CDouble

The variable coefficients in the constraint

-> IO CInt

The length of the arrays

glp_get_mat_col Source #

Arguments

:: Ptr Problem

The problem instance

-> Column

The constraint to retrieve

-> GlpkArray Row

The constraint indices the variable is in

-> GlpkArray CDouble

The constraint coefficients for the variable

-> IO CInt

The length of the arrays

glp_create_index Source #

Arguments

:: Ptr Problem

The problem instance

-> IO () 

glp_delete_index Source #

Arguments

:: Ptr Problem

The problem instance

-> IO () 

glp_find_row Source #

Arguments

:: Ptr Problem

The problem instance

-> CString

The name of the constraint

-> IO Row

The index of the constraint

glp_find_col Source #

Arguments

:: Ptr Problem

The problem instance

-> CString

The name of the variable

-> IO Column

The index of the variable

glp_set_rii Source #

Arguments

:: Ptr Problem

The problem instance

-> Row

The constraint to scale

-> CDouble

The scaling factor

-> IO () 

glp_get_rii Source #

Arguments

:: Ptr Problem

The problem instance

-> Row

The constraint index

-> IO CDouble 

glp_set_sjj Source #

Arguments

:: Ptr Problem

The problem instance

-> Column

The variable to scale

-> CDouble

The scaling factor

-> IO () 

glp_get_sjj Source #

Arguments

:: Ptr Problem

The problem instance

-> Column

The variable index

-> IO CDouble 

glp_scale_prob Source #

Arguments

:: Ptr Problem

The problem instance

-> GlpkScaling

The type of scaling to apply

-> IO () 

glp_unscale_prob Source #

Arguments

:: Ptr Problem

The problem instance

-> IO () 

glp_set_row_stat Source #

Arguments

:: Ptr Problem

The problem instance

-> Row

The constraint to modify

-> GlpkVariableStatus

The status to apply

-> IO () 

glp_set_col_stat Source #

Arguments

:: Ptr Problem

The problem instance

-> Column

The variable to modify

-> GlpkVariableStatus

The status to apply

-> IO () 

glp_std_basis Source #

Arguments

:: Ptr Problem

The problem instance

-> IO () 

glp_adv_basis Source #

Arguments

:: Ptr Problem

The problem instance

-> Unused CInt

Reserved for future use, must be zero

-> IO () 

glp_cpx_basis Source #

Arguments

:: Ptr Problem

The problem instance

-> IO () 

glp_simplex Source #

Arguments

:: Ptr Problem

The problem instance

-> Ptr SimplexMethodControlParameters

Simplex control parameters

-> IO GlpkSimplexStatus

The exit status

glp_exact Source #

Arguments

:: Ptr Problem

The problem instance

-> Ptr SimplexMethodControlParameters

Simplex control parameters

-> IO GlpkSimplexStatus

The exit status

glp_init_smcp Source #

Arguments

:: Ptr SimplexMethodControlParameters

The Simplex control parameters to initialize

-> IO () 

glp_get_status Source #

Arguments

:: Ptr Problem

The problem instance

-> IO GlpkSolutionStatus 

glp_get_prim_stat Source #

Arguments

:: Ptr Problem

The problem instance

-> IO GlpkSolutionStatus 

glp_get_dual_stat Source #

Arguments

:: Ptr Problem

The problem instance

-> IO GlpkSolutionStatus 

glp_get_obj_val Source #

Arguments

:: Ptr Problem

The problem instance

-> IO CDouble 

glp_get_row_stat Source #

Arguments

:: Ptr Problem

The problem instance

-> Row

The constraint to query

-> IO GlpkVariableStatus

The status of the associated with the auxiliary variable

glp_get_col_stat Source #

Arguments

:: Ptr Problem

The problem instance

-> Column

The variable to query

-> IO GlpkVariableStatus

The status of the variable

glp_get_row_prim Source #

Arguments

:: Ptr Problem

The problem instance

-> Row

The constraint to query

-> IO CDouble

The primal auxiliary variable value

glp_get_row_dual Source #

Arguments

:: Ptr Problem

The problem instance

-> Row

The constraint to query

-> IO CDouble

The dual auxiliary variable value

glp_get_col_prim Source #

Arguments

:: Ptr Problem

The problem instance

-> Column

The variable to query

-> IO CDouble

The primal variable value

glp_get_col_dual Source #

Arguments

:: Ptr Problem

The problem instance

-> Column

The variable to query

-> IO CDouble

The dual variable value

glp_get_unbnd_ray Source #

Arguments

:: Ptr Problem

The problem instance

-> IO CInt

The index, k, of the variable producing unboundedness. If 1 <= k <= m, then k is the kth auxiliary variable. If m + 1 <= k <= m + n, it is the (k - m)th structural variable.

glp_get_bfcp Source #

Arguments

:: Ptr Problem

The problem instance

-> Ptr BasisFactorizationControlParameters

A pointer that will hold the basis factorization control parameters

-> IO () 

glp_set_bfcp Source #

Arguments

:: Ptr Problem

The problem instance

-> Ptr BasisFactorizationControlParameters

The basis factorization control parameters

-> IO () 

glp_interior Source #

Arguments

:: Ptr Problem

The problem instance

-> Ptr InteriorPointControlParameters

The interior point control parameters

-> IO GlpkInteriorPointStatus

The status of the solve

glp_init_iptcp Source #

Arguments

:: Ptr InteriorPointControlParameters

The control parameters to initialize

-> IO () 

glp_ipt_status Source #

Arguments

:: Ptr Problem

The problem instance

-> IO GlpkSolutionStatus

The status of the interior point solve

glp_intopt Source #

Arguments

:: Ptr Problem

The problem instance

-> Ptr (MIPControlParameters a)

The MIP control parameters

-> IO GlpkMIPStatus

The status of the solve

glp_mip_status Source #

Arguments

:: Ptr Problem

The problem instance

-> IO GlpkSolutionStatus 

glp_mip_obj_val Source #

Arguments

:: Ptr Problem

The problem instance

-> IO CDouble

The MIP object

glp_mip_row_val Source #

Arguments

:: Ptr Problem

The problem instance

-> Row

The constraint to query

-> IO CDouble

The value of the auxiliary variable

glp_mip_col_val Source #

Arguments

:: Ptr Problem

The problem instance

-> Column

The variable to query

-> IO CDouble

The value of the variable

glp_check_kkt Source #

Arguments

:: Ptr Problem

The problem instance

-> GlpkSolutionType

The solution type to check

-> GlpkKKTCheck

The condition to be checked

-> Ptr CDouble

The largest absolute error

-> Ptr CInt

The row, column, or variable with the largest absolute error

-> Ptr CDouble

The largest relative error

-> Ptr CInt

The row, column, or variable with the largest relative error

-> IO () 

glp_print_sol Source #

Arguments

:: Ptr Problem

The problem instance

-> CString

The file name to write to

-> IO CInt

Zero on success

glp_read_sol Source #

Arguments

:: Ptr Problem

The problem instance

-> CString

The file name to read from

-> IO CInt

Zero on success

glp_write_sol Source #

Arguments

:: Ptr Problem

The problem instance

-> CString

The file name to write to

-> IO CInt

Zero on success

glp_print_ranges Source #

Arguments

:: Ptr Problem

The problem instance

-> CInt

The number of rows and columns

-> Ptr CInt

The rows and clumns to analyze

-> Unused CInt

Reserved for future use, must be zero

-> CString

The file name to write to

-> IO CInt

Zero on success

glp_print_ipt Source #

Arguments

:: Ptr Problem

The problem instance

-> CString

The file to write to

-> IO CInt 

glp_read_ipt Source #

Arguments

:: Ptr Problem

The problem instance

-> CString

The file to read from

-> IO CInt 

glp_write_ipt Source #

Arguments

:: Ptr Problem

The problem instance

-> CString

The file to write to

-> IO CInt 

glp_print_mip Source #

Arguments

:: Ptr Problem

The problem instance

-> CString

The file to write to

-> IO CInt 

glp_read_mip Source #

Arguments

:: Ptr Problem

The problem instance

-> CString

The file to read from

-> IO CInt 

glp_write_mip Source #

Arguments

:: Ptr Problem

The problem instance

-> CString

The file to write to

-> IO CInt 

glp_bf_exists Source #

Arguments

:: Ptr Problem

The problem instance

-> IO CInt

Whether an LP basis factorization exists

glp_factorize Source #

Arguments

:: Ptr Problem

Compute an LP basis factorization

-> IO () 

glp_bf_updated Source #

Arguments

:: Ptr Problem

The problem instance

-> IO CInt

Whether the LP basis factorization is updated

glp_get_bhead Source #

Arguments

:: Ptr Problem

The problem instance

-> CInt 
-> IO CInt 

glp_get_row_bind Source #

Arguments

:: Ptr Problem

The problem instance

-> CInt 
-> IO CInt 

glp_get_col_bind Source #

Arguments

:: Ptr Problem

The problem instance

-> CInt 
-> IO CInt 

glp_ftran Source #

Arguments

:: Ptr Problem

The problem instance

-> Ptr CDouble 
-> IO () 

glp_btran Source #

Arguments

:: Ptr Problem

The problem instance

-> Ptr CDouble 
-> IO () 

glp_warm_up Source #

Arguments

:: Ptr Problem

The problem instance

-> IO GlpkFactorizationResult 

glp_eval_tab_row Source #

Arguments

:: Ptr Problem

The problem instance

-> CInt 
-> Ptr CInt 
-> Ptr CDouble 
-> IO CInt 

glp_eval_tab_col Source #

Arguments

:: Ptr Problem

The problem instance

-> CInt 
-> Ptr CInt 
-> Ptr CDouble 
-> IO CInt 

glp_transform_row Source #

Arguments

:: Ptr Problem

The problem instance

-> CInt 
-> Ptr CInt 
-> Ptr CDouble 
-> IO CInt 

glp_transform_col Source #

Arguments

:: Ptr Problem

The problem instance

-> CInt 
-> Ptr CInt 
-> Ptr CDouble 
-> IO CInt 

glp_prim_rtest Source #

Arguments

:: Ptr Problem

The problem instance

-> CInt 
-> Ptr CInt 
-> Ptr CDouble 
-> CInt 
-> CDouble 
-> IO CInt 

glp_dual_rtest Source #

Arguments

:: Ptr Problem

The problem instance

-> CInt 
-> Ptr CInt 
-> Ptr CDouble 
-> CInt 
-> CDouble 
-> IO CInt 

glp_analyze_bound Source #

Arguments

:: Ptr Problem

The problem instance

-> CInt 
-> Ptr CDouble 
-> Ptr Column 
-> Ptr CDouble 
-> Ptr Column 
-> IO () 

glp_analyze_coef Source #

Arguments

:: Ptr Problem

The problem instance

-> CInt 
-> Ptr CDouble 
-> Ptr Column 
-> Ptr CDouble 
-> Ptr CDouble 
-> Ptr Column 
-> Ptr CDouble 
-> IO () 

glp_init_iocp Source #

Arguments

:: Ptr (MIPControlParameters a)

The MIP control parameters to initialize

-> IO () 

glp_ipt_obj_val Source #

Arguments

:: Ptr Problem

The problem instance

-> IO CDouble

The objective value

glp_ipt_row_prim Source #

Arguments

:: Ptr Problem

The problem instance

-> Row

The constraint to query

-> IO Double

The primal auxiliary variable value

glp_ipt_row_dual Source #

Arguments

:: Ptr Problem

The problem instance

-> Row

The constraint to query

-> IO Double

The dual auxiliary variable value

glp_ipt_col_prim Source #

Arguments

:: Ptr Problem

The problem instance

-> Column

The variable to query

-> IO CDouble

The primal variable value

glp_ipt_col_dual Source #

Arguments

:: Ptr Problem

The problem instance

-> Column

The variable to query

-> IO Double

The dual variable value

glp_ios_reason Source #

Arguments

:: Ptr (GlpkTree a)

The search tree

-> IO GlpkCallbackReason

The reason the callback is being called

glp_ios_get_prob Source #

Arguments

:: Ptr (GlpkTree a)

The search tree

-> IO (Ptr Problem)

The active problem

glp_ios_tree_size Source #

Arguments

:: Ptr (GlpkTree a)

The search tree

-> Ptr CInt

The number of active nodes

-> Ptr CInt

The total number of active and inactive nodes

-> Ptr CInt

The total number of nodes that have been added to the tree

-> IO () 

glp_ios_curr_node Source #

Arguments

:: Ptr (GlpkTree a)

The search tree

-> IO (GlpkInt GlpkNodeIndex)

The current node in the search tree

glp_ios_next_node Source #

Arguments

:: Ptr (GlpkTree a)

The search tree

-> GlpkInt GlpkNodeIndex

The target node in the search tree

-> IO (GlpkInt GlpkNodeIndex)

The next node in the search tree after the target node

glp_ios_prev_node Source #

Arguments

:: Ptr (GlpkTree a)

The search tree

-> GlpkInt GlpkNodeIndex

The target node in the search tree

-> IO (GlpkInt GlpkNodeIndex)

The parent node in the search tree after the target node

glp_ios_up_node Source #

Arguments

:: Ptr (GlpkTree a)

The search tree

-> GlpkInt GlpkNodeIndex

The target node in the search tree

-> IO (GlpkInt GlpkNodeIndex)

The parent of the target node

glp_ios_node_level Source #

Arguments

:: Ptr (GlpkTree a)

The search tree

-> GlpkInt GlpkNodeIndex

The target node in the search tree

-> IO CInt

The level of the target in the search tree; the root problem has level 0.

glp_ios_node_bound Source #

Arguments

:: Ptr (GlpkTree a)

The search tree

-> GlpkInt GlpkNodeIndex

The target node in the search tree

-> IO CDouble

The objective bound on the target

glp_ios_best_node Source #

Arguments

:: Ptr (GlpkTree a)

The search tree

-> IO (GlpkInt GlpkNodeIndex)

The node in the search tree with the best objective bound

glp_ios_mip_gap Source #

Arguments

:: Ptr (GlpkTree a)

The search tree

-> IO CDouble

The current MIP gap

glp_ios_node_data Source #

Arguments

:: Ptr (GlpkTree a)

The search tree

-> GlpkInt GlpkNodeIndex

The target node in the search tree

-> IO (Ptr a)

The data associated with the target

glp_ios_row_attr Source #

Arguments

:: Ptr (GlpkTree a)

The search tree

-> CInt

The index of the target cut

-> Ptr GlpkCutAttribute

The information about the target cut

-> IO () 

glp_ios_pool_size Source #

Arguments

:: Ptr (GlpkTree a)

The search tree

-> IO CInt

The number of cutting planes added to the problem

glp_ios_add_row Source #

Arguments

:: Ptr (GlpkTree a)

The search tree

-> CString

The name of the cutting plane to add

-> GlpkUserCutType

The type of cut being added

-> Unused CInt

Unused; must be zero

-> CInt

The number of variable indices specified

-> GlpkArray CInt

The variable indices

-> GlpkArray CDouble

The variable coefficients

-> GlpkConstraintType

The type of the constraint

-> CDouble

The right-hand side of the constraint

-> IO () 

glp_ios_del_row Source #

Arguments

:: Ptr (GlpkTree a)

The search tree

-> CInt

The index of the cut to delete

-> IO () 

glp_ios_clear_pool Source #

Arguments

:: Ptr (GlpkTree a)

The search tree

-> IO () 

glp_ios_can_branch Source #

Arguments

:: Ptr (GlpkTree a)

The search tree

-> Column 

glp_ios_branch_upon Source #

Arguments

:: Ptr (GlpkTree a)

The search tree

-> Column

The index of the variable to branch on

-> GlpkBranchOption

The branching decision

-> IO () 

glp_ios_select_node Source #

Arguments

:: Ptr (GlpkTree a)

The search tree

-> GlpkInt GlpkNodeIndex

The subproblem to explore

-> IO () 

glp_ios_heur_sol Source #

Arguments

:: Ptr (GlpkTree a)

The search tree

-> GlpkArray CDouble

The variable values of an integer heuristic

-> IO () 

glp_ios_terminate Source #

Arguments

:: Ptr (GlpkTree a)

The search tree

-> IO () 

glp_set_col_kind Source #

Arguments

:: Ptr Problem

The problem instance

-> Column

The variable index

-> GlpkVariableType

The type of the variable

-> IO () 

glp_get_col_kind Source #

Arguments

:: Ptr Problem

The problem instance

-> Column

The variable index

-> IO GlpkVariableType

The type of the variable

glp_get_num_int Source #

Arguments

:: Ptr Problem

The problem instance

-> IO CInt

The number of integer variables

glp_get_num_bin Source #

Arguments

:: Ptr Problem

The problem instance

-> IO CInt

The number of binary variables

glp_init_mpscp Source #

Arguments

:: Ptr MPSControlParameters

The MPS control parameters to initialize

-> IO () 

glp_read_mps Source #

Arguments

:: Ptr Problem

The problem instance

-> GlpkMPSFormat

The MPS format to read

-> Ptr MPSControlParameters

The MPS control parameters

-> CString

The name of the file to read

-> IO () 

glp_write_mps Source #

Arguments

:: Ptr Problem

The problem instance

-> GlpkMPSFormat

The MPS format to read

-> Ptr MPSControlParameters

The MPS control parameters

-> CString

The name of the file to write to

-> IO () 

glp_init_cpxcp Source #

Arguments

:: Ptr CplexLPFormatControlParameters

The CPLEX LP control parameters to initialize

-> IO () 

glp_read_lp Source #

Arguments

:: Ptr Problem

The problem instance

-> Ptr CplexLPFormatControlParameters

The CPLEX LP control parameters

-> CString

The name of the file to read

-> IO CInt

Zero on success

glp_write_lp Source #

Arguments

:: Ptr Problem

The problem instance

-> Ptr CplexLPFormatControlParameters

The CPLEX LP control parameters

-> CString

The name of the file to write to

-> IO CInt

Zero on success

glp_read_prob Source #

Arguments

:: Ptr Problem

The problem instance

-> Unused CInt

Reserved for future use, must be zero

-> CString

The file to read from

-> IO CInt

Zero on success

glp_write_prob Source #

Arguments

:: Ptr Problem

The problem instance

-> Unused CInt

Reserved for future use, must be zero

-> CString

The file to write to

-> IO CInt

Zero on success

glp_mpl_alloc_wksp Source #

Arguments

:: IO (Ptr MathProgWorkspace)

The allocated MathProg workspace

glp_mpl_free_wksp Source #

Arguments

:: Ptr MathProgWorkspace

The MathProg workspace to deallocate

-> IO () 

glp_mpl_init_rand Source #

Arguments

:: Ptr MathProgWorkspace

The MathProg workspace

-> CInt

The random number generator seed

-> IO MathProgResult 

glp_mpl_read_model Source #

Arguments

:: Ptr MathProgWorkspace

The MathProg workspace

-> CString

The name of the file to read

-> CInt

If nonzero, skip the data section

-> IO MathProgResult 

glp_mpl_read_data Source #

Arguments

:: Ptr MathProgWorkspace

The MathProg workspace

-> CString

The name of the file to read

-> IO MathProgResult 

glp_mpl_generate Source #

Arguments

:: Ptr MathProgWorkspace

The MathProg workspace

-> CString

The output file. If NULL, output is written to standard output

-> IO MathProgResult 

glp_mpl_build_prob Source #

Arguments

:: Ptr MathProgWorkspace

The MathProg workspace

-> Ptr Problem

The problem instance to write to

-> IO MathProgResult 

glp_mpl_postsolve Source #

Arguments

:: Ptr MathProgWorkspace

The MathProg workspace

-> Ptr Problem

The solved problem instance

-> GlpkSolutionType

The type of solution to be copied

-> IO MathProgResult 

glp_read_cnfstat Source #

Arguments

:: Ptr Problem

The problem instance

-> CString

The file to read from

-> CInt

Zero on success

glp_write_cnfstat Source #

Arguments

:: Ptr Problem

The problem instance

-> CString

The file to write to

-> CInt

Zero on success

glp_minisat1 Source #

Arguments

:: Ptr Problem

The problem instance

-> IO CInt 

glp_intfeas1 Source #

Arguments

:: Ptr Problem

The problem instance

-> CInt 
-> CInt 
-> IO CInt 

glp_term_hook :: FunPtr (Ptr a -> CString -> IO CInt) -> Ptr a -> IO () Source #