Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- data BasisFactorizationControlParameters = BasisFactorizationControlParameters {
- bfcpMessageLevel :: Unused GlpkMessageLevel
- bfcpType :: GlpkFactorizationType
- bfcpLUSize :: Unused CInt
- bfcpPivotTolerance :: CDouble
- bfcpPivotLimit :: CInt
- bfcpSuhl :: GlpkControl
- bfcpEpsilonTolerance :: CDouble
- bfcpMaxGro :: Unused CDouble
- bfcpNfsMax :: CInt
- bfcpUpdateTolerance :: Unused CDouble
- bfcpNrsMax :: CInt
- bfcpRsSize :: Unused CInt
- bfcpFooBar :: Unused (FixedLengthArray BfcpFooBar CDouble)
- data SimplexMethodControlParameters = SimplexMethodControlParameters {
- smcpMessageLevel :: GlpkMessageLevel
- smcpMethod :: GlpkSimplexMethod
- smcpPricing :: GlpkPricing
- smcpRatioTest :: GlpkRatioTest
- smcpPrimalFeasibilityTolerance :: Double
- smcpDualFeasibilityTolerance :: Double
- smcpPivotTolerance :: Double
- smcpLowerObjectiveLimit :: Double
- smcpUpperObjectiveLimit :: Double
- smcpIterationLimit :: CInt
- smcpTimeLimitMillis :: CInt
- smcpOutputFrequencyMillis :: CInt
- smcpOutputDelayMillis :: CInt
- smcpPresolve :: GlpkPresolve
- smcpExcl :: Unused CInt
- smcpShift :: Unused CInt
- smcpAOrN :: Unused CInt
- smcpFooBar :: Unused (FixedLengthArray SmcpFooBar CDouble)
- data InteriorPointControlParameters = InteriorPointControlParameters {}
- data MIPControlParameters a = MIPControlParameters {
- iocpMessageLevel :: GlpkMessageLevel
- iocpBranchingTechnique :: GlpkBranchingTechnique
- iocpBacktrackingTechnique :: GlpkBacktrackingTechnique
- iocpAbsoluteFeasibilityTolerance :: CDouble
- iocpRelativeObjectiveTolerance :: CDouble
- iocpTimeLimitMillis :: CInt
- iocpOutputFrequencyMillis :: CInt
- iocpOutputDelayMillis :: CInt
- iocpCallback :: FunPtr (Ptr (GlpkTree a) -> Ptr a -> IO ())
- iocpNodeData :: Ptr a
- iocpNodeDataSize :: CInt
- iocpPreprocessingTechnique :: GlpkPreProcessingTechnique
- iocpRelativeMIPGap :: CDouble
- iocpMIRCuts :: GlpkMIRCuts
- iocpGormoryCuts :: GlpkGomoryCuts
- iocpCoverCuts :: GlpkCoverCuts
- iocpCliqueCuts :: GlpkCliqueCuts
- iocpPresolve :: GlpkPresolve
- iocpBinarization :: GlpkBinarization
- iocpFeasibilityPump :: GlpkFeasibilityPump
- iocpProximitySearch :: GlpkProximitySearch
- iocpProximityTimeLimitMillis :: CInt
- iocpSimpleRounding :: GlpkSimpleRounding
- iocpUseExistingSolution :: Unused CInt
- iocpNewSolutionFileName :: Unused (Ptr CChar)
- iocpUseAlienSolver :: Unused CInt
- iocpUseLongStepDual :: Unused CInt
- iocpFooBar :: Unused (FixedLengthArray IocpFooBar CDouble)
- data MPSControlParameters = MPSControlParameters {}
- data CplexLPFormatControlParameters = CplexLPFormatControlParameters {}
- data GlpkCutAttribute = GlpkCutAttribute {}
- newtype GlpkUserCutType = GlpkUserCutType {}
- newtype GlpkArray a = GlpkArray {
- fromGlpkArray :: Ptr a
- mallocGlpkArray :: Storable a => [a] -> IO (GlpkArray a)
- allocaGlpkArray :: Storable a => [a] -> (GlpkArray a -> IO b) -> IO b
- initGlpkArray :: Storable a => [a] -> Ptr a -> IO (GlpkArray a)
- class FixedLength a where
- fixedLength :: a -> Int
- newtype FixedLengthArray a b = FixedLengthArray {
- fromFixedLengthArray :: [b]
- newtype GlpkInt a = GlpkInt {
- fromGlpkInt :: CInt
- data Problem
- data GlpkColumn
- data GlpkRow
- data GlpkNodeIndex
- data GlpkTree a
- data MathProgWorkspace
- type Row = GlpkInt GlpkRow
- type Column = GlpkInt GlpkColumn
- newtype MathProgResult = MathProgResult {}
- newtype Unused a = Unused {
- fromUnused :: a
- data BfcpFooBar
- data SmcpFooBar
- data IptcpFooBar
- data IocpFooBar
- data AttrFooBar
- data MpscpFooBar
- data CpxcpFooBar
- data GlpkMajorVersion
- glpkMajorVersion :: GlpkMajorVersion
- data GlpkMinorVersion
- glpkMinorVersion :: GlpkMinorVersion
- data GlpkDirection
- glpkMin :: GlpkDirection
- glpkMax :: GlpkDirection
- newtype GlpkVariableType = GlpkVariableType {}
- glpkContinuous :: GlpkVariableType
- glpkInteger :: GlpkVariableType
- glpkBinary :: GlpkVariableType
- data GlpkConstraintType
- glpkFree :: GlpkConstraintType
- glpkGT :: GlpkConstraintType
- glpkLT :: GlpkConstraintType
- glpkBounded :: GlpkConstraintType
- glpkFixed :: GlpkConstraintType
- data GlpkVariableStatus
- glpkBasic :: GlpkVariableStatus
- glpkNonBasicLower :: GlpkVariableStatus
- glpkNonBasicUpper :: GlpkVariableStatus
- glpkNonBasicFree :: GlpkVariableStatus
- glpkNonBasicFixed :: GlpkVariableStatus
- data GlpkScaling
- glpkGeometricMeanScaling :: GlpkScaling
- glpkEquilibrationScaling :: GlpkScaling
- glpkPowerOfTwoScaling :: GlpkScaling
- glpkSkipScaling :: GlpkScaling
- glpkAutoScaling :: GlpkScaling
- data GlpkSolutionType
- glpkBasicSolution :: GlpkSolutionType
- glpkInteriorPointSolution :: GlpkSolutionType
- glpkMIPSolution :: GlpkSolutionType
- data GlpkSolutionStatus
- glpkOptimal :: GlpkSolutionStatus
- glpkFeasible :: GlpkSolutionStatus
- glpkInfeasible :: GlpkSolutionStatus
- glpkNoFeasible :: GlpkSolutionStatus
- glpkUnbounded :: GlpkSolutionStatus
- glpkUndefined :: GlpkSolutionStatus
- data GlpkMessageLevel
- glpkMessageOff :: GlpkMessageLevel
- glpkMessageError :: GlpkMessageLevel
- glpkMessageOn :: GlpkMessageLevel
- glpkMessageAll :: GlpkMessageLevel
- glpkMessageDebug :: GlpkMessageLevel
- data GlpkSimplexMethod
- glpkPrimalSimplex :: GlpkSimplexMethod
- glpkDualSimplex :: GlpkSimplexMethod
- glpkDualPSimplex :: GlpkSimplexMethod
- data GlpkPricing
- glpkTextbookPricing :: GlpkPricing
- glpkStandardPricing :: GlpkPricing
- glpkProjectedSteepestEdge :: GlpkPricing
- data GlpkRatioTest
- glpkStandardRatioTest :: GlpkRatioTest
- glpkHarrisTwoPassRatioTest :: GlpkRatioTest
- data GlpkPreCholeskyOrdering
- glpkNatural :: GlpkPreCholeskyOrdering
- glpkQuotientMinimumDegree :: GlpkPreCholeskyOrdering
- glpkApproximateMinimumDegree :: GlpkPreCholeskyOrdering
- glpkSymmetricApproximateMinimumDegree :: GlpkPreCholeskyOrdering
- data GlpkBranchingTechnique
- glpkFirstFractional :: GlpkBranchingTechnique
- glpkLastFractional :: GlpkBranchingTechnique
- glpkMostFractional :: GlpkBranchingTechnique
- glpkDriebeckTomlin :: GlpkBranchingTechnique
- glpkHybridPseudoCost :: GlpkBranchingTechnique
- data GlpkBacktrackingTechnique
- glpkDepthFirstSearch :: GlpkBacktrackingTechnique
- glpkBreadthFirstSearch :: GlpkBacktrackingTechnique
- glpkBestLocalBound :: GlpkBacktrackingTechnique
- glpkBestProjectionHeuristic :: GlpkBacktrackingTechnique
- data GlpkPreProcessingTechnique
- glpkPreProcessNone :: GlpkPreProcessingTechnique
- glpkPreProcessRoot :: GlpkPreProcessingTechnique
- glpkPreProcessAll :: GlpkPreProcessingTechnique
- data GlpkFeasibilityPump
- glpkFeasibilityPumpOn :: GlpkFeasibilityPump
- glpkFeasibilityPumpOff :: GlpkFeasibilityPump
- data GlpkProximitySearch
- glpkProximitySearchOn :: GlpkProximitySearch
- glpkProximitySearchOff :: GlpkProximitySearch
- data GlpkGomoryCuts
- glpkGomoryCutsOn :: GlpkGomoryCuts
- glpkGomoryCutsOff :: GlpkGomoryCuts
- data GlpkMIRCuts
- glpkMIRCutsOn :: GlpkMIRCuts
- glpkMIRCutsOff :: GlpkMIRCuts
- data GlpkCoverCuts
- glpkCoverCutsOn :: GlpkCoverCuts
- glpkCoverCutsOff :: GlpkCoverCuts
- data GlpkCliqueCuts
- glpkCliqueCutsOn :: GlpkCliqueCuts
- glpkCliqueCutsOff :: GlpkCliqueCuts
- data GlpkPresolve
- glpkPresolveOn :: GlpkPresolve
- glpkPresolveOff :: GlpkPresolve
- data GlpkBinarization
- glpkBinarizationOn :: GlpkBinarization
- glpkBinarizationOff :: GlpkBinarization
- data GlpkSimpleRounding
- glpkSimpleRoundingOn :: GlpkSimpleRounding
- glpkSimpleRoundingOff :: GlpkSimpleRounding
- data GlpkConstraintOrigin
- glpkRegularConstraint :: GlpkConstraintOrigin
- glpkLazyConstraint :: GlpkConstraintOrigin
- glpkCuttingPlaneConstraint :: GlpkConstraintOrigin
- data GlpkCutType
- glpkGomoryCut :: GlpkCutType
- glpkMIRCut :: GlpkCutType
- glpkCoverCut :: GlpkCutType
- glpkCliqueCut :: GlpkCutType
- data GlpkControl
- glpkOn :: GlpkControl
- glpkOff :: GlpkControl
- data GlpkCallbackReason
- glpkSubproblemSelection :: GlpkCallbackReason
- glpkPreprocessing :: GlpkCallbackReason
- glpkRowGeneration :: GlpkCallbackReason
- glpkHeuristicSolution :: GlpkCallbackReason
- glpkCutGeneration :: GlpkCallbackReason
- glpkBranching :: GlpkCallbackReason
- glpkNewIncumbent :: GlpkCallbackReason
- data GlpkBranchOption
- glpkBranchUp :: GlpkBranchOption
- glpkBranchDown :: GlpkBranchOption
- glpkBranchAuto :: GlpkBranchOption
- data GlpkFactorizationResult
- glpkFactorizationSuccess :: GlpkFactorizationResult
- glpkFactorizationBadBasis :: GlpkFactorizationResult
- glpkFactorizationSingular :: GlpkFactorizationResult
- glpkFactorizationIllConditioned :: GlpkFactorizationResult
- data GlpkSimplexStatus
- glpkSimplexSuccess :: GlpkSimplexStatus
- glpkSimplexBadBasis :: GlpkSimplexStatus
- glpkSimplexSingular :: GlpkSimplexStatus
- glpkSimplexIllConditioned :: GlpkSimplexStatus
- glpkSimplexBadBound :: GlpkSimplexStatus
- glpkSimplexFailure :: GlpkSimplexStatus
- glpkSimplexDualLowerLimitFailure :: GlpkSimplexStatus
- glpkSimplexDualUpperLimitFailure :: GlpkSimplexStatus
- glpkSimplexIterationLimit :: GlpkSimplexStatus
- glpkSimplexTimeLimit :: GlpkSimplexStatus
- glpkSimplexPrimalInfeasible :: GlpkSimplexStatus
- glpkSimplexDualInfeasible :: GlpkSimplexStatus
- data GlpkMIPStatus
- glpkMIPSuccess :: GlpkMIPStatus
- glpkMIPBadBound :: GlpkMIPStatus
- glpkMIPNoBasis :: GlpkMIPStatus
- glpkMIPPrimalInfeasible :: GlpkMIPStatus
- glpkMIPDualInfeasible :: GlpkMIPStatus
- glpkMIPFailure :: GlpkMIPStatus
- glpkMIPRelativeGap :: GlpkMIPStatus
- glpkMIPTimeLimit :: GlpkMIPStatus
- glpkMIPStopped :: GlpkMIPStatus
- data GlpkInteriorPointStatus
- glpkInteriorPointSuccess :: GlpkInteriorPointStatus
- glpkInteriorPointFailure :: GlpkInteriorPointStatus
- glpkInteriorPointNoConvergence :: GlpkInteriorPointStatus
- glpkInteriorPointIterationLimit :: GlpkInteriorPointStatus
- glpkInteriorPointNumericalInstability :: GlpkInteriorPointStatus
- data GlpkKKTCheck
- glpkKKTPrimalEquality :: GlpkKKTCheck
- glpkKKTPrimalBound :: GlpkKKTCheck
- glpkKKTDualEquality :: GlpkKKTCheck
- glpkKKTDualBound :: GlpkKKTCheck
- data GlpkMPSFormat
- glpkMPSAncient :: GlpkMPSFormat
- glpkMPSDeck :: GlpkMPSFormat
- glpkMPSModern :: GlpkMPSFormat
- data GlpkFactorizationType
- glpkLUForrestTomlin :: GlpkFactorizationType
- glpkLUSchurCompBartelsGolub :: GlpkFactorizationType
- glpkLUSchurGivensRotation :: GlpkFactorizationType
- glpkBTSchurBartelsGolub :: GlpkFactorizationType
- glpkBTSchurGivensRotation :: GlpkFactorizationType
- glp_create_prob :: IO (Ptr Problem)
- glp_delete_prob :: Ptr Problem -> IO ()
- glp_set_prob_name :: Ptr Problem -> CString -> IO ()
- glp_set_obj_name :: Ptr Problem -> CString -> IO ()
- glp_set_obj_dir :: Ptr Problem -> GlpkDirection -> IO ()
- glp_add_rows :: Ptr Problem -> CInt -> IO Row
- glp_add_cols :: Ptr Problem -> CInt -> IO Column
- glp_set_row_name :: Ptr Problem -> Row -> CString -> IO ()
- glp_set_col_name :: Ptr Problem -> Column -> CString -> IO ()
- glp_set_row_bnds :: Ptr Problem -> Row -> GlpkConstraintType -> CDouble -> CDouble -> IO ()
- glp_set_col_bnds :: Ptr Problem -> Column -> GlpkConstraintType -> CDouble -> CDouble -> IO ()
- glp_set_obj_coef :: Ptr Problem -> Column -> CDouble -> IO ()
- glp_set_mat_row :: Ptr Problem -> Row -> CInt -> GlpkArray Column -> GlpkArray CDouble -> IO ()
- glp_set_mat_col :: Ptr Problem -> Column -> CInt -> Ptr Row -> GlpkArray CDouble -> IO ()
- glp_load_matrix :: Ptr Problem -> CInt -> GlpkArray Row -> GlpkArray Column -> GlpkArray CDouble -> IO ()
- glp_check_dup :: CInt -> CInt -> CInt -> GlpkArray CInt -> GlpkArray CInt -> CInt
- glp_sort_matrix :: Ptr Problem -> IO ()
- glp_del_rows :: Ptr Problem -> CInt -> GlpkArray Row -> IO ()
- glp_del_cols :: Ptr Problem -> CInt -> GlpkArray Column -> IO ()
- glp_copy_prob :: Ptr Problem -> Ptr Problem -> GlpkControl -> IO ()
- glp_erase_prob :: Ptr Problem -> IO ()
- glp_get_prob_name :: Ptr Problem -> IO CString
- glp_get_obj_name :: Ptr Problem -> IO CString
- glp_get_obj_dir :: Ptr Problem -> IO GlpkDirection
- glp_get_num_rows :: Ptr Problem -> IO CInt
- glp_get_num_cols :: Ptr Problem -> IO CInt
- glp_get_row_name :: Ptr Problem -> Row -> IO CString
- glp_get_col_name :: Ptr Problem -> Column -> IO CString
- glp_get_row_type :: Ptr Problem -> Row -> IO GlpkConstraintType
- glp_get_row_lb :: Ptr Problem -> Row -> IO CDouble
- glp_get_row_ub :: Ptr Problem -> Row -> IO CDouble
- glp_get_col_type :: Ptr Problem -> Column -> IO GlpkVariableType
- glp_get_col_lb :: Ptr Problem -> Column -> IO CDouble
- glp_get_col_ub :: Ptr Problem -> Column -> IO CDouble
- glp_get_obj_coef :: Ptr Problem -> Column -> IO CDouble
- glp_get_num_nz :: Ptr Problem -> IO CInt
- glp_get_mat_row :: Ptr Problem -> Row -> GlpkArray Column -> GlpkArray CDouble -> IO CInt
- glp_get_mat_col :: Ptr Problem -> Column -> GlpkArray Row -> GlpkArray CDouble -> IO CInt
- glp_create_index :: Ptr Problem -> IO ()
- glp_delete_index :: Ptr Problem -> IO ()
- glp_find_row :: Ptr Problem -> CString -> IO Row
- glp_find_col :: Ptr Problem -> CString -> IO Column
- glp_set_rii :: Ptr Problem -> Row -> CDouble -> IO ()
- glp_get_rii :: Ptr Problem -> Row -> IO CDouble
- glp_set_sjj :: Ptr Problem -> Column -> CDouble -> IO ()
- glp_get_sjj :: Ptr Problem -> Column -> IO CDouble
- glp_scale_prob :: Ptr Problem -> GlpkScaling -> IO ()
- glp_unscale_prob :: Ptr Problem -> IO ()
- glp_set_row_stat :: Ptr Problem -> Row -> GlpkVariableStatus -> IO ()
- glp_set_col_stat :: Ptr Problem -> Column -> GlpkVariableStatus -> IO ()
- glp_std_basis :: Ptr Problem -> IO ()
- glp_adv_basis :: Ptr Problem -> Unused CInt -> IO ()
- glp_cpx_basis :: Ptr Problem -> IO ()
- glp_simplex :: Ptr Problem -> Ptr SimplexMethodControlParameters -> IO GlpkSimplexStatus
- glp_exact :: Ptr Problem -> Ptr SimplexMethodControlParameters -> IO GlpkSimplexStatus
- glp_init_smcp :: Ptr SimplexMethodControlParameters -> IO ()
- glp_get_status :: Ptr Problem -> IO GlpkSolutionStatus
- glp_get_prim_stat :: Ptr Problem -> IO GlpkSolutionStatus
- glp_get_dual_stat :: Ptr Problem -> IO GlpkSolutionStatus
- glp_get_obj_val :: Ptr Problem -> IO CDouble
- glp_get_row_stat :: Ptr Problem -> Row -> IO GlpkVariableStatus
- glp_get_col_stat :: Ptr Problem -> Column -> IO GlpkVariableStatus
- glp_get_row_prim :: Ptr Problem -> Row -> IO CDouble
- glp_get_row_dual :: Ptr Problem -> Row -> IO CDouble
- glp_get_col_prim :: Ptr Problem -> Column -> IO CDouble
- glp_get_col_dual :: Ptr Problem -> Column -> IO CDouble
- glp_get_unbnd_ray :: Ptr Problem -> IO CInt
- glp_get_bfcp :: Ptr Problem -> Ptr BasisFactorizationControlParameters -> IO ()
- glp_set_bfcp :: Ptr Problem -> Ptr BasisFactorizationControlParameters -> IO ()
- glp_interior :: Ptr Problem -> Ptr InteriorPointControlParameters -> IO GlpkInteriorPointStatus
- glp_init_iptcp :: Ptr InteriorPointControlParameters -> IO ()
- glp_ipt_status :: Ptr Problem -> IO GlpkSolutionStatus
- glp_intopt :: Ptr Problem -> Ptr (MIPControlParameters a) -> IO GlpkMIPStatus
- glp_mip_status :: Ptr Problem -> IO GlpkSolutionStatus
- glp_mip_obj_val :: Ptr Problem -> IO CDouble
- glp_mip_row_val :: Ptr Problem -> Row -> IO CDouble
- glp_mip_col_val :: Ptr Problem -> Column -> IO CDouble
- glp_check_kkt :: Ptr Problem -> GlpkSolutionType -> GlpkKKTCheck -> Ptr CDouble -> Ptr CInt -> Ptr CDouble -> Ptr CInt -> IO ()
- glp_print_sol :: Ptr Problem -> CString -> IO CInt
- glp_read_sol :: Ptr Problem -> CString -> IO CInt
- glp_write_sol :: Ptr Problem -> CString -> IO CInt
- glp_print_ranges :: Ptr Problem -> CInt -> Ptr CInt -> Unused CInt -> CString -> IO CInt
- glp_print_ipt :: Ptr Problem -> CString -> IO CInt
- glp_read_ipt :: Ptr Problem -> CString -> IO CInt
- glp_write_ipt :: Ptr Problem -> CString -> IO CInt
- glp_print_mip :: Ptr Problem -> CString -> IO CInt
- glp_read_mip :: Ptr Problem -> CString -> IO CInt
- glp_write_mip :: Ptr Problem -> CString -> IO CInt
- glp_bf_exists :: Ptr Problem -> IO CInt
- glp_factorize :: Ptr Problem -> IO ()
- glp_bf_updated :: Ptr Problem -> IO CInt
- glp_get_bhead :: Ptr Problem -> CInt -> IO CInt
- glp_get_row_bind :: Ptr Problem -> CInt -> IO CInt
- glp_get_col_bind :: Ptr Problem -> CInt -> IO CInt
- glp_ftran :: Ptr Problem -> Ptr CDouble -> IO ()
- glp_btran :: Ptr Problem -> Ptr CDouble -> IO ()
- glp_warm_up :: Ptr Problem -> IO GlpkFactorizationResult
- glp_eval_tab_row :: Ptr Problem -> CInt -> Ptr CInt -> Ptr CDouble -> IO CInt
- glp_eval_tab_col :: Ptr Problem -> CInt -> Ptr CInt -> Ptr CDouble -> IO CInt
- glp_transform_row :: Ptr Problem -> CInt -> Ptr CInt -> Ptr CDouble -> IO CInt
- glp_transform_col :: Ptr Problem -> CInt -> Ptr CInt -> Ptr CDouble -> IO CInt
- glp_prim_rtest :: Ptr Problem -> CInt -> Ptr CInt -> Ptr CDouble -> CInt -> CDouble -> IO CInt
- glp_dual_rtest :: Ptr Problem -> CInt -> Ptr CInt -> Ptr CDouble -> CInt -> CDouble -> IO CInt
- glp_analyze_bound :: Ptr Problem -> CInt -> Ptr CDouble -> Ptr Column -> Ptr CDouble -> Ptr Column -> IO ()
- glp_analyze_coef :: Ptr Problem -> CInt -> Ptr CDouble -> Ptr Column -> Ptr CDouble -> Ptr CDouble -> Ptr Column -> Ptr CDouble -> IO ()
- glp_init_iocp :: Ptr (MIPControlParameters a) -> IO ()
- glp_ipt_obj_val :: Ptr Problem -> IO CDouble
- glp_ipt_row_prim :: Ptr Problem -> Row -> IO Double
- glp_ipt_row_dual :: Ptr Problem -> Row -> IO Double
- glp_ipt_col_prim :: Ptr Problem -> Column -> IO CDouble
- glp_ipt_col_dual :: Ptr Problem -> Column -> IO Double
- glp_ios_reason :: Ptr (GlpkTree a) -> IO GlpkCallbackReason
- glp_ios_get_prob :: Ptr (GlpkTree a) -> IO (Ptr Problem)
- glp_ios_tree_size :: Ptr (GlpkTree a) -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO ()
- glp_ios_curr_node :: Ptr (GlpkTree a) -> IO (GlpkInt GlpkNodeIndex)
- glp_ios_next_node :: Ptr (GlpkTree a) -> GlpkInt GlpkNodeIndex -> IO (GlpkInt GlpkNodeIndex)
- glp_ios_prev_node :: Ptr (GlpkTree a) -> GlpkInt GlpkNodeIndex -> IO (GlpkInt GlpkNodeIndex)
- glp_ios_up_node :: Ptr (GlpkTree a) -> GlpkInt GlpkNodeIndex -> IO (GlpkInt GlpkNodeIndex)
- glp_ios_node_level :: Ptr (GlpkTree a) -> GlpkInt GlpkNodeIndex -> IO CInt
- glp_ios_node_bound :: Ptr (GlpkTree a) -> GlpkInt GlpkNodeIndex -> IO CDouble
- glp_ios_best_node :: Ptr (GlpkTree a) -> IO (GlpkInt GlpkNodeIndex)
- glp_ios_mip_gap :: Ptr (GlpkTree a) -> IO CDouble
- glp_ios_node_data :: Ptr (GlpkTree a) -> GlpkInt GlpkNodeIndex -> IO (Ptr a)
- glp_ios_row_attr :: Ptr (GlpkTree a) -> CInt -> Ptr GlpkCutAttribute -> IO ()
- glp_ios_pool_size :: Ptr (GlpkTree a) -> IO CInt
- glp_ios_add_row :: Ptr (GlpkTree a) -> CString -> GlpkUserCutType -> Unused CInt -> CInt -> GlpkArray CInt -> GlpkArray CDouble -> GlpkConstraintType -> CDouble -> IO ()
- glp_ios_del_row :: Ptr (GlpkTree a) -> CInt -> IO ()
- glp_ios_clear_pool :: Ptr (GlpkTree a) -> IO ()
- glp_ios_can_branch :: Ptr (GlpkTree a) -> Column
- glp_ios_branch_upon :: Ptr (GlpkTree a) -> Column -> GlpkBranchOption -> IO ()
- glp_ios_select_node :: Ptr (GlpkTree a) -> GlpkInt GlpkNodeIndex -> IO ()
- glp_ios_heur_sol :: Ptr (GlpkTree a) -> GlpkArray CDouble -> IO ()
- glp_ios_terminate :: Ptr (GlpkTree a) -> IO ()
- glp_set_col_kind :: Ptr Problem -> Column -> GlpkVariableType -> IO ()
- glp_get_col_kind :: Ptr Problem -> Column -> IO GlpkVariableType
- glp_get_num_int :: Ptr Problem -> IO CInt
- glp_get_num_bin :: Ptr Problem -> IO CInt
- glp_init_mpscp :: Ptr MPSControlParameters -> IO ()
- glp_read_mps :: Ptr Problem -> GlpkMPSFormat -> Ptr MPSControlParameters -> CString -> IO ()
- glp_write_mps :: Ptr Problem -> GlpkMPSFormat -> Ptr MPSControlParameters -> CString -> IO ()
- glp_init_cpxcp :: Ptr CplexLPFormatControlParameters -> IO ()
- glp_read_lp :: Ptr Problem -> Ptr CplexLPFormatControlParameters -> CString -> IO CInt
- glp_write_lp :: Ptr Problem -> Ptr CplexLPFormatControlParameters -> CString -> IO CInt
- glp_read_prob :: Ptr Problem -> Unused CInt -> CString -> IO CInt
- glp_write_prob :: Ptr Problem -> Unused CInt -> CString -> IO CInt
- glp_mpl_alloc_wksp :: IO (Ptr MathProgWorkspace)
- glp_mpl_free_wksp :: Ptr MathProgWorkspace -> IO ()
- glp_mpl_init_rand :: Ptr MathProgWorkspace -> CInt -> IO MathProgResult
- glp_mpl_read_model :: Ptr MathProgWorkspace -> CString -> CInt -> IO MathProgResult
- glp_mpl_read_data :: Ptr MathProgWorkspace -> CString -> IO MathProgResult
- glp_mpl_generate :: Ptr MathProgWorkspace -> CString -> IO MathProgResult
- glp_mpl_build_prob :: Ptr MathProgWorkspace -> Ptr Problem -> IO MathProgResult
- glp_mpl_postsolve :: Ptr MathProgWorkspace -> Ptr Problem -> GlpkSolutionType -> IO MathProgResult
- glp_read_cnfstat :: Ptr Problem -> CString -> CInt
- glp_write_cnfstat :: Ptr Problem -> CString -> CInt
- glp_minisat1 :: Ptr Problem -> IO CInt
- glp_intfeas1 :: Ptr Problem -> CInt -> CInt -> IO CInt
- glp_init_env :: IO CInt
- glp_free_env :: IO CInt
- glp_version :: IO CString
- glp_config :: CString -> IO CString
- glp_term_out :: GlpkControl -> IO GlpkControl
- glp_term_hook :: FunPtr (Ptr a -> CString -> IO CInt) -> Ptr a -> IO ()
- glp_error_hook :: FunPtr (Ptr a -> IO CInt) -> Ptr a -> IO ()
- mkHaskellErrorHook :: (Ptr a -> IO CInt) -> IO (FunPtr (Ptr a -> IO CInt))
- mkHaskellTermHook :: (Ptr a -> IO CInt) -> IO (FunPtr (Ptr a -> IO CInt))
- mkHaskellMIPCallback :: (Ptr (GlpkTree a) -> Ptr a -> IO ()) -> IO (FunPtr (Ptr (GlpkTree a) -> Ptr a -> IO ()))
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
data SimplexMethodControlParameters Source #
Instances
data InteriorPointControlParameters Source #
Instances
data MIPControlParameters a Source #
Instances
data MPSControlParameters Source #
Instances
data CplexLPFormatControlParameters Source #
Instances
data GlpkCutAttribute Source #
Instances
newtype GlpkUserCutType Source #
Instances
GLPK arrays
GLPK uses a 1-based indexing for arrays. This is accomplished by ignoring the 0th entry.
An array whose data begins at index 1
GlpkArray | |
|
Instances
Storable (GlpkArray a) Source # | |
Defined in Math.Programming.Glpk.Header 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 () # | |
Show (GlpkArray a) Source # | |
Eq (GlpkArray a) Source # | |
Ord (GlpkArray a) Source # | |
Defined in Math.Programming.Glpk.Header |
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.
fixedLength :: a -> Int Source #
Instances
FixedLength AttrFooBar Source # | |
Defined in Math.Programming.Glpk.Header fixedLength :: AttrFooBar -> Int Source # | |
FixedLength BfcpFooBar Source # | |
Defined in Math.Programming.Glpk.Header fixedLength :: BfcpFooBar -> Int Source # | |
FixedLength CpxcpFooBar Source # | |
Defined in Math.Programming.Glpk.Header fixedLength :: CpxcpFooBar -> Int Source # | |
FixedLength IocpFooBar Source # | |
Defined in Math.Programming.Glpk.Header fixedLength :: IocpFooBar -> Int Source # | |
FixedLength IptcpFooBar Source # | |
Defined in Math.Programming.Glpk.Header fixedLength :: IptcpFooBar -> Int Source # | |
FixedLength MpscpFooBar Source # | |
Defined in Math.Programming.Glpk.Header fixedLength :: MpscpFooBar -> Int Source # | |
FixedLength SmcpFooBar Source # | |
Defined in Math.Programming.Glpk.Header fixedLength :: SmcpFooBar -> Int Source # |
newtype FixedLengthArray a b Source #
A type representing fixed-length array members of structs.
Instances
Low-level and phantom types
Wrapper around CInt
values, tagged with a phantom type to help
track what it refers to.
Instances
Storable (GlpkInt a) Source # | |
Defined in Math.Programming.Glpk.Header | |
Enum (GlpkInt a) Source # | |
Defined in Math.Programming.Glpk.Header succ :: GlpkInt a -> GlpkInt a # pred :: GlpkInt a -> 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] # | |
Num (GlpkInt a) Source # | |
Defined in Math.Programming.Glpk.Header | |
Read (GlpkInt a) Source # | |
Integral (GlpkInt a) Source # | |
Defined in Math.Programming.Glpk.Header | |
Real (GlpkInt a) Source # | |
Defined in Math.Programming.Glpk.Header toRational :: GlpkInt a -> Rational # | |
Show (GlpkInt a) Source # | |
Eq (GlpkInt a) Source # | |
Ord (GlpkInt a) Source # | |
Defined in Math.Programming.Glpk.Header |
data GlpkColumn Source #
Phantom type used to denote data as being a column.
data GlpkNodeIndex Source #
Phantom type used to denote data as being a node index.
data MathProgWorkspace Source #
Phantom type used to denote pointers to workspaces.
type Column = GlpkInt GlpkColumn Source #
Convenient alias for columns.
newtype MathProgResult Source #
Instances
Undocumented and unused structures
A type used to represent an unused or undocumented struct member.
Unused | |
|
Instances
Storable a => Storable (Unused a) Source # | |
Defined in Math.Programming.Glpk.Header | |
Enum a => Enum (Unused a) Source # | |
Defined in Math.Programming.Glpk.Header | |
Read a => Read (Unused a) Source # | |
Show a => Show (Unused a) Source # | |
GStorable a => GStorable (Unused a) Source # | |
Eq a => Eq (Unused a) Source # | |
Ord a => Ord (Unused a) Source # | |
Defined in Math.Programming.Glpk.Header |
data BfcpFooBar Source #
Instances
FixedLength BfcpFooBar Source # | |
Defined in Math.Programming.Glpk.Header fixedLength :: BfcpFooBar -> Int Source # |
data SmcpFooBar Source #
Instances
FixedLength SmcpFooBar Source # | |
Defined in Math.Programming.Glpk.Header fixedLength :: SmcpFooBar -> Int Source # |
data IptcpFooBar Source #
Instances
FixedLength IptcpFooBar Source # | |
Defined in Math.Programming.Glpk.Header fixedLength :: IptcpFooBar -> Int Source # |
data IocpFooBar Source #
Instances
FixedLength IocpFooBar Source # | |
Defined in Math.Programming.Glpk.Header fixedLength :: IocpFooBar -> Int Source # |
data AttrFooBar Source #
Instances
FixedLength AttrFooBar Source # | |
Defined in Math.Programming.Glpk.Header fixedLength :: AttrFooBar -> Int Source # |
data MpscpFooBar Source #
Instances
FixedLength MpscpFooBar Source # | |
Defined in Math.Programming.Glpk.Header fixedLength :: MpscpFooBar -> Int Source # |
data CpxcpFooBar Source #
Instances
FixedLength CpxcpFooBar Source # | |
Defined in Math.Programming.Glpk.Header fixedLength :: CpxcpFooBar -> Int Source # |
GLPK API
Enums
data GlpkMajorVersion Source #
Instances
data GlpkMinorVersion Source #
Instances
data GlpkDirection Source #
Instances
newtype GlpkVariableType Source #
Instances
data GlpkConstraintType Source #
Instances
data GlpkVariableStatus Source #
Instances
data GlpkScaling Source #
Instances
data GlpkSolutionType Source #
Instances
data GlpkSolutionStatus Source #
Instances
data GlpkMessageLevel Source #
Instances
data GlpkSimplexMethod Source #
Instances
data GlpkPricing Source #
Instances
data GlpkRatioTest Source #
Instances
data GlpkPreCholeskyOrdering Source #
Instances
data GlpkBranchingTechnique Source #
Instances
data GlpkBacktrackingTechnique Source #
Instances
data GlpkPreProcessingTechnique Source #
Instances
data GlpkFeasibilityPump Source #
Instances
data GlpkProximitySearch Source #
Instances
data GlpkGomoryCuts Source #
Instances
data GlpkMIRCuts Source #
Instances
data GlpkCoverCuts Source #
Instances
data GlpkCliqueCuts Source #
Instances
data GlpkPresolve Source #
Instances
data GlpkBinarization Source #
Instances
data GlpkSimpleRounding Source #
Instances
data GlpkConstraintOrigin Source #
Instances
data GlpkCutType Source #
Instances
data GlpkControl Source #
Instances
glpkOn :: GlpkControl Source #
data GlpkCallbackReason Source #
Instances
data GlpkBranchOption Source #
Instances
data GlpkFactorizationResult Source #
Instances
data GlpkSimplexStatus Source #
Instances
data GlpkMIPStatus Source #
Instances
data GlpkInteriorPointStatus Source #
Instances
data GlpkKKTCheck Source #
Instances
data GlpkMPSFormat Source #
Instances
data GlpkFactorizationType Source #
Instances
Functions
:: Ptr Problem | The problem instance |
-> GlpkDirection | Whether the problem is a minimization or maximization problem |
-> IO () |
:: Ptr Problem | The problem instance |
-> IO GlpkDirection | The direction of the objective |
:: Ptr Problem | The problem instance |
-> Row | The index of the constraint |
-> IO GlpkConstraintType | The constraint type |
:: Ptr Problem | The problem instance |
-> Column | The index of the variable |
-> IO GlpkVariableType | The constraint type |
:: Ptr Problem | The problem instance |
-> GlpkScaling | The type of scaling to apply |
-> IO () |
:: Ptr Problem | The problem instance |
-> Row | The constraint to modify |
-> GlpkVariableStatus | The status to apply |
-> IO () |
:: Ptr Problem | The problem instance |
-> Column | The variable to modify |
-> GlpkVariableStatus | The status to apply |
-> IO () |
:: Ptr Problem | The problem instance |
-> Ptr SimplexMethodControlParameters | Simplex control parameters |
-> IO GlpkSimplexStatus | The exit status |
:: Ptr Problem | The problem instance |
-> Ptr SimplexMethodControlParameters | Simplex control parameters |
-> IO GlpkSimplexStatus | The exit status |
:: Ptr SimplexMethodControlParameters | The Simplex control parameters to initialize |
-> IO () |
:: Ptr Problem | The problem instance |
-> IO GlpkSolutionStatus |
:: Ptr Problem | The problem instance |
-> IO GlpkSolutionStatus |
:: Ptr Problem | The problem instance |
-> IO GlpkSolutionStatus |
:: Ptr Problem | The problem instance |
-> Row | The constraint to query |
-> IO GlpkVariableStatus | The status of the associated with the auxiliary variable |
:: Ptr Problem | The problem instance |
-> Column | The variable to query |
-> IO GlpkVariableStatus | The status of the variable |
:: Ptr Problem | The problem instance |
-> Ptr BasisFactorizationControlParameters | A pointer that will hold the basis factorization control parameters |
-> IO () |
:: Ptr Problem | The problem instance |
-> Ptr BasisFactorizationControlParameters | The basis factorization control parameters |
-> IO () |
:: Ptr Problem | The problem instance |
-> Ptr InteriorPointControlParameters | The interior point control parameters |
-> IO GlpkInteriorPointStatus | The status of the solve |
:: Ptr InteriorPointControlParameters | The control parameters to initialize |
-> IO () |
:: Ptr Problem | The problem instance |
-> IO GlpkSolutionStatus | The status of the interior point solve |
:: Ptr Problem | The problem instance |
-> Ptr (MIPControlParameters a) | The MIP control parameters |
-> IO GlpkMIPStatus | The status of the solve |
:: Ptr Problem | The problem instance |
-> IO GlpkSolutionStatus |
:: 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 () |
:: Ptr Problem | The problem instance |
-> IO GlpkFactorizationResult |
:: Ptr (MIPControlParameters a) | The MIP control parameters to initialize |
-> IO () |
:: Ptr (GlpkTree a) | The search tree |
-> IO GlpkCallbackReason | The reason the callback is being called |
:: Ptr (GlpkTree a) | The search tree |
-> IO (GlpkInt GlpkNodeIndex) | The current node in the search tree |
:: 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 |
:: 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 |
:: Ptr (GlpkTree a) | The search tree |
-> GlpkInt GlpkNodeIndex | The target node in the search tree |
-> IO (GlpkInt GlpkNodeIndex) | The parent of the target node |
:: Ptr (GlpkTree a) | The search tree |
-> IO (GlpkInt GlpkNodeIndex) | The node in the search tree with the best objective bound |
:: 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 () |
:: Ptr (GlpkTree a) | The search tree |
-> Column | The index of the variable to branch on |
-> GlpkBranchOption | The branching decision |
-> IO () |
:: Ptr (GlpkTree a) | The search tree |
-> GlpkInt GlpkNodeIndex | The subproblem to explore |
-> IO () |
:: Ptr Problem | The problem instance |
-> Column | The variable index |
-> GlpkVariableType | The type of the variable |
-> IO () |
:: Ptr Problem | The problem instance |
-> Column | The variable index |
-> IO GlpkVariableType | The type of the variable |
:: Ptr MPSControlParameters | The MPS control parameters to initialize |
-> IO () |
:: 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 () |
:: 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 () |
:: Ptr CplexLPFormatControlParameters | The CPLEX LP control parameters to initialize |
-> IO () |
:: IO (Ptr MathProgWorkspace) | The allocated MathProg workspace |
:: Ptr MathProgWorkspace | The MathProg workspace to deallocate |
-> IO () |
:: Ptr MathProgWorkspace | The MathProg workspace |
-> CInt | The random number generator seed |
-> IO MathProgResult |
:: Ptr MathProgWorkspace | The MathProg workspace |
-> CString | The name of the file to read |
-> CInt | If nonzero, skip the data section |
-> IO MathProgResult |
:: Ptr MathProgWorkspace | The MathProg workspace |
-> CString | The name of the file to read |
-> IO MathProgResult |
:: Ptr MathProgWorkspace | The MathProg workspace |
-> CString | The output file. If NULL, output is written to standard output |
-> IO MathProgResult |
:: Ptr MathProgWorkspace | The MathProg workspace |
-> Ptr Problem | The problem instance to write to |
-> IO MathProgResult |
:: Ptr MathProgWorkspace | The MathProg workspace |
-> Ptr Problem | The solved problem instance |
-> GlpkSolutionType | The type of solution to be copied |
-> IO MathProgResult |
glp_init_env :: IO CInt Source #
glp_free_env :: IO CInt Source #
glp_version :: IO CString Source #
glp_term_out :: GlpkControl -> IO GlpkControl Source #