Fortran is a high-performance scientific computing language which dates from the 1950s and is still in use.


Bindings for GNU gfortran edit

Jeff Kelly has made the following GNU gfortran GLPK language bindings available. See the next section for further details and discussion.

        use ISO_C_BINDING

        implicit none

c GNU GLP integer and real control and problem attribute declarations.

        integer(c_int) :: GLP_MIN
        integer(c_int) :: GLP_MAX

        integer(c_int) :: GLP_FR
        integer(c_int) :: GLP_LO
        integer(c_int) :: GLP_UP
        integer(c_int) :: GLP_DB
        integer(c_int) :: GLP_FX

        integer(c_int) :: GLP_ON
        integer(c_int) :: GLP_OFF

        integer(c_int) :: GLP_PRIMAL
        integer(c_int) :: GLP_DUALP
        integer(c_int) :: GLP_DUAL

        integer(c_int) :: GLP_UNDEF
        integer(c_int) :: GLP_FEAS
        integer(c_int) :: GLP_INFEAS
        integer(c_int) :: GLP_NOFEAS
        integer(c_int) :: GLP_OPT
        integer(c_int) :: GLP_UNBND

        integer(c_int) :: GLP_CV
        integer(c_int) :: GLP_IV
        integer(c_int) :: GLP_BV

        integer(c_int) :: GLP_ORD_NONE
        integer(c_int) :: GLP_ORD_QMD
        integer(c_int) :: GLP_ORD_AMD
        integer(c_int) :: GLP_ORD_SYMAMD

          parameter (GLP_MIN = 1)
          parameter (GLP_MAX = 2)

          parameter (GLP_FR = 1)
          parameter (GLP_LO = 2)
          parameter (GLP_UP = 3)
          parameter (GLP_DB = 4)
          parameter (GLP_FX = 5)

          parameter (GLP_ON = 1)
          parameter (GLP_OFF = 0)

          parameter (GLP_PRIMAL = 1)
          parameter (GLP_DUALP = 2)
          parameter (GLP_DUAL = 3)

        parameter (GLP_UNDEF = 1)
        parameter (GLP_FEAS = 2)
        parameter (GLP_INFEAS = 3)
        parameter (GLP_NOFEAS = 4)
        parameter (GLP_OPT = 5)
        parameter (GLP_UNBND = 6)

        parameter (GLP_CV = 1)
        parameter (GLP_IV = 2)
        parameter (GLP_BV = 3)

        parameter (GLP_ORD_NONE = 0)
        parameter (GLP_ORD_QMD = 1)
        parameter (GLP_ORD_AMD = 2)
        parameter (GLP_ORD_SYMAMD = 3)

c GNU GLP derived-type or structure definitions for their C-Language API interface.
c
c * Note that the intrinsic module ISO_C_BINDING is required.
c
c * Note that to interface the structure or derived-type to the C-language we can do
c   the following without using a pointer i.e., return = glp_init_smcp(problem1_set%msg_lev).
c
c   The idea is that because a derived-type or structure is simply a "blind" consecutive or
c   contiguous block of data then specifying the first component or item of the derived-type
c   is identical to the Fortran IV and Fortran 77 notion of passing in the first element of
c   an assumed array i.e., X(1) will pass in by reference all of the X(:) data.

c Simplex settings/options.

        type, bind(c) :: glp_smcp
          integer(c_int) :: msg_lev
          integer(c_int) :: meth
          integer(c_int) :: pricing
          integer(c_int) :: r_test
          real(c_double) :: tol_bnd
          real(c_double) :: tol_dj
          real(c_double) :: tol_piv
          real(c_double) :: obj_ll
          real(c_double) :: obj_ul
          integer(c_int) :: it_lim
          integer(c_int) :: tm_lim
          integer(c_int) :: out_frq
          integer(c_int) :: out_dly
          integer(c_int) :: presolve
          real(c_double) :: foo_bar(0:35)
        end type glp_smcp

c Interior-point settings/options.

        type, bind(c) :: glp_iptcp
          integer(c_int) :: msg_lev
          integer(c_int) :: ord_alg
          real(c_double) :: foo_bar(0:47)
        end type glp_iptcp

c GNU GLP interface block definitions for their C-Language API interface.

        interface

          function glp_create_prob() bind(C,name="glp_create_prob")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT:: glp_create_prob
             integer(c_int) :: glp_create_prob
          end function

              subroutine glp_set_prob_name(prob,probname) bind(C,name="glp_set_prob_name")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_set_prob_name
              integer(c_int), value :: prob
              character(c_char) :: probname(*)
            end subroutine

          function glp_init_smcp(parm_struct) bind(C,name="glp_init_smcp")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_init_smcp
            integer(c_int) :: glp_init_smcp
            integer(c_int) :: parm_struct
          end function

          function glp_init_iptcp(parm_struct) bind(C,name="glp_init_iptcp")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_init_iptcp
            integer(c_int) :: glp_init_iptcp
            integer(c_int) :: parm_struct
          end function

            subroutine glp_set_obj_dir(prob,objdir) bind(C,name="glp_set_obj_dir")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_set_obj_dir
              integer(c_int), value :: prob
              integer(c_int), value :: objdir
            end subroutine

            function glp_add_rows(prob,nrs) bind(C,name="glp_add_rows")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_add_rows
            integer(c_int) :: glp_add_rows
                integer(c_int), value :: prob
                integer(c_int), value :: nrs
            end function

              function glp_add_cols(prob,ncs) bind(C,name="glp_add_cols")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_add_cols
            integer(c_int) :: glp_add_cols
              integer(c_int), value :: prob
              integer(c_int), value :: ncs
            end function

            subroutine glp_set_obj_coef(prob,j,coef) bind(C,name="glp_set_obj_coef")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_set_obj_coef
              integer(c_int), value :: prob
              integer(c_int), value :: j
              real(c_double), value :: coef
            end subroutine

            subroutine glp_set_row_bnds(prob,i,type,lb,ub) bind(C,name="glp_set_row_bnds")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_set_row_bnds
              integer(c_int), value :: prob
              integer(c_int), value :: i
              integer(c_int), value :: type
              real(c_double), value :: lb
              real(c_double), value :: ub
            end subroutine

            subroutine glp_set_row_name(prob,i,name) bind(C,name="glp_set_row_name")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_set_row_name
                integer(c_int), value :: prob
                integer(c_int), value :: i
                character(c_char) :: name(*)
            end subroutine

            subroutine glp_set_col_bnds(prob,j,type,lb,ub) bind(C,name="glp_set_col_bnds")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_set_col_bnds
                integer(c_int), value :: prob
                integer(c_int), value :: j
                integer(c_int), value :: type
                real(c_double), value :: lb
                real(c_double), value :: ub
            end subroutine

            subroutine glp_set_col_name(prob,j,name) bind(C,name="glp_set_col_name")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_set_col_name
            integer(c_int), value :: prob
                integer(c_int), value :: j
                character(c_char) :: name(*)
            end subroutine

            subroutine glp_set_col_kind(prob,j,kind) bind(C,name="glp_set_col_kind")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_set_col_kind
                integer(c_int), value :: prob
            integer(c_int), value :: j
            integer(c_int), value :: kind
            end subroutine

            subroutine glp_load_matrix(prob,ne,ia,ja,ar) bind(C,name="glp_load_matrix")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_load_matrix
                integer(c_int), value :: prob
                integer(c_int), value :: ne
                integer(c_int) :: ia(*)
                integer(c_int) :: ja(*)
                real(c_double) :: ar(*)
            end subroutine

            subroutine glp_adv_basis(prob,flag) bind(C,name="glp_adv_basis")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_adv_basis
                integer(c_int), value :: prob
                integer(c_int), value :: flag
            end subroutine

            subroutine glp_cpx_basis(prob) bind(C,name="glp_cpx_basis")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_cpx_basis
                integer(c_int), value :: prob
            end subroutine

            function glp_simplex(prob,parm) bind(C,name="glp_simplex")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_simplex
            integer(c_int) :: glp_simplex
                integer(c_int), value :: prob
                integer(c_int) :: parm
            end function

            function glp_interior(prob,parm) bind(C,name="glp_interior")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_interior
            integer(c_int) :: glp_interior
                integer(c_int), value :: prob
                integer(c_int) :: parm
            end function

            function glp_write_lp(prob,parm,fname) bind(C,name="glp_write_lp")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_write_lp
            integer(c_int) :: glp_write_lp
                integer(c_int), value :: prob
                integer(c_int) :: parm
                character(c_char) :: fname(*)
            end function

            function glp_get_status(prob) bind(C,name="glp_get_status")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_get_status
            integer(c_int) :: glp_get_status
                integer(c_int), value :: prob
            end function

            function glp_ipt_status(prob) bind(C,name="glp_ipt_status")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_ipt_status
            integer(c_int) :: glp_ipt_status
                integer(c_int), value :: prob
            end function

            function glp_get_obj_val(prob) bind(C,name="glp_get_obj_val")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_get_obj_val
            real(c_double) :: glp_get_obj_val
                 integer(c_int), value :: prob
            end function

            function glp_ipt_obj_val(prob) bind(C,name="glp_ipt_obj_val")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_ipt_obj_val
            real(c_double) :: glp_ipt_obj_val
                integer(c_int), value :: prob
            end function

            function glp_get_col_prim(prob,j) bind(C,name="glp_get_col_prim")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_get_col_prim
            real(c_double) :: glp_get_col_prim
                  integer(c_int), value :: prob
            integer(c_int), value :: j
            end function

            function glp_ipt_col_prim(prob,j) bind(C,name="glp_ipt_col_prim")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_ipt_col_prim
            real(c_double) :: glp_ipt_col_prim
                integer(c_int), value :: prob
            integer(c_int), value :: j
            end function

            subroutine glp_erase_prob(prob) bind(C,name="glp_erase_prob")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_erase_prob
                integer(c_int), value :: prob
            end subroutine

            subroutine glp_delete_prob(prob) bind(C,name="glp_delete_prob")
            use ISO_C_BINDING
cGCC$ ATTRIBUTES DLLIMPORT :: glp_delete_prob
                integer(c_int), value :: prob
            end subroutine

        end interface

Bindings for Fortran 2003 edit

Jeff Kelly has made the following main program example available, complete with language bindings. This code was developed using the Intel Fortran 2003 compiler.

The program itself calls GLPK to:

max c'*x such that A*x <= b and lower <= x <= upper

The example includes the necessary Fortran bindings and also shows how to setup the callback for integer optimization (if required) using GLPKintsolcb() and the Fortran LOC() intrinsic.

The most difficult part when interfacing GLPK to Fortran concerns the two derived types glp_smcp (simplex settings) and glp_iocp (integer optimization settings). These derived types are treated as "blind arrays" so that one simply needs to match the bit pattern of the blind array with the derived type and then pass this via glp_init_smcp() — for example (as shown below), the first integer value problem1_set1%msg_lev acts like an integer pointer to the blind array as usual.

Main program example edit

c Intel Fortran Calls to GLPK.

      integer(4) :: problem1_ptr
      character(80) :: problem1_name, problem_name

      type (glp_smcp) :: problem1_set1
      type (glp_iocp) :: problem1_set2

      integer(4) :: M, N, NZ
      integer(4) :: ROWS(NZ), COLS(NZ)
      real(8) :: L(N), U(N), LPOBJ, MIPOBJ, C(N), B(M), A(NZ)
      integer(4) :: status, i, j

      common /cbcommon/ N, problem1_ptr, problem1_name

      problem1_name = "GLPKproblem"

      problem1_ptr = glp_create_prob()
      problem_name = TRIM(problem1_name)//CHAR(0)
      call glp_set_prob_name(problem1_ptr,problem_name)

      status = glp_init_smcp(problem1_set1%msg_lev)
      problem1_set1%presolve = GLP_ON

      status = glp_init_iocp(problem1_set2%msg_lev)
      problem1_set2%fp_heur  = GLP_ON
      problem1_set2%cb_func = LOC(GLPKintsolcb)

      call glp_set_obj_dir(problem1_ptr,GLP_MAX)

      status = glp_add_rows(problem1_ptr,M)
      status = glp_add_cols(problem1_ptr,N)

      do i = 1,M
        if (constraint_type(i) == "E") then
          call glp_set_row_bnds(problem1_ptr,i,GLP_FX,B(i),0d+0)
        elseif (constraint_type(i) == "L") then
          call glp_set_row_bnds(problem1_ptr,i,GLP_UP,0d+0,B(i))
        elseif (constraint_type(i) == "G") then
          call glp_set_row_bnds(problem1_ptr,i,GLP_LO,B(i),0d+0)
        end if
      end do

      do j = 1,N
        call glp_set_col_bnds(problem1_ptr,j,GLP_DB,L(j),U(j))
        call glp_set_obj_coef(problem1_ptr,j,C(j))
        if ((L(j) == 0) .and. (U(j) == 1.0)) then
          call glp_set_col_kind(problem1_ptr,j,GLP_BV)
        else
          call glp_set_col_kind(problem1_ptr,j,GLP_CV)
        end if
      end do

      call glp_load_matrix(problem1_ptr,NZ,ROWS,COLS,A)

      status = glp_simplex(problem1_ptr,problem1_set1%msg_lev)
        LPOBJ = glp_get_obj_val(problem1_ptr)
        status = glp_get_status(problem1_ptr)

      status = glp_intopt(problem1_ptr,problem1_set2%msg_lev)
      MIPOBJ = glp_mip_obj_val(problem1_ptr)
        status = glp_mip_status(problem1_ptr)

c Intel Fortran Callback to GLPK (if required).

      subroutine GLPKintsolcb(tree,info)
cDEC$ ATTRIBUTES DLLEXPORT, REFERENCE, ALIAS : "GLPKINTSOLCB" :: GLPKINTSOLCB

        implicit none

        integer(4) :: N
        integer(4) :: problem1_ptr
        character(80) :: problem1_name
        common /cbcommon/ N, problem1_ptr, problem1_name

        character(80) :: problem_name

        integer(4), intent(in) :: tree
cDEC$ ATTRIBUTES REFERENCE :: tree
        integer(4), optional, intent(in) :: info
cDEC$ ATTRIBUTES REFERENCE :: info

        real(8) :: x(1:N)

        integer(4) :: status, i

        interface

            integer(4) function glp_ios_reason(tree)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_ios_reason" :: glp_ios_reason
                    integer(4) :: tree
cDEC$ ATTRIBUTES REFERENCE :: tree
          end function

          integer(4) function glp_mip_status(prob)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_mip_status" :: glp_mip_status
                    integer(4) :: prob
cDEC$ ATTRIBUTES VALUE :: prob
            end function

          real(8) function glp_mip_obj_val(prob)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_mip_obj_val" :: glp_mip_obj_val
              integer(4) :: prob
cDEC$ ATTRIBUTES VALUE :: prob
          end function

            real(8) function glp_mip_col_val(prob,j)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_mip_col_val" :: glp_mip_col_val
                    integer(4) :: prob
cDEC$ ATTRIBUTES VALUE :: prob
            integer(4) :: j
cDEC$ ATTRIBUTES VALUE :: j
            end function

        end interface

        integer(4) :: GLP_IROWGEN
        integer(4) :: GLP_IBINGO
        integer(4) :: GLP_IHEUR
        integer(4) :: GLP_ICUTGEN
        integer(4) :: GLP_IBRANCH
        integer(4) :: GLP_ISELECT
        integer(4) :: GLP_IPREPRO

        parameter (GLP_IROWGEN =  1)
        parameter (GLP_IBINGO  =  2)
        parameter (GLP_IHEUR   =  3)
        parameter (GLP_ICUTGEN =  4)
        parameter (GLP_IBRANCH =  5)
        parameter (GLP_ISELECT =  6)
        parameter (GLP_IPREPRO =  7)

        select case (glp_ios_reason(tree))

        case (GLP_IBINGO)

          do i = 1,N
            x(i) = glp_mip_col_val(problem1_ptr,i)
          end do

        end select

      end subroutine GLPKintsolcb

c Intel Fortran Bindings/Interface to GLPK.

      integer(4) :: GLP_MIN
      integer(4) :: GLP_MAX

      integer(4) :: GLP_FR
      integer(4) :: GLP_LO
      integer(4) :: GLP_UP
      integer(4) :: GLP_DB
      integer(4) :: GLP_FX

      integer(4) :: GLP_ON
      integer(4) :: GLP_OFF

      integer(4) :: GLP_PRIMAL
      integer(4) :: GLP_DUALP
      integer(4) :: GLP_DUAL

      integer(4) :: GLP_OPT
      integer(4) :: GLP_FEAS
      integer(4) :: GLP_INFEAS
      integer(4) :: GLP_NOFEAS
      integer(4) :: GLP_UNBND
      integer(4) :: GLP_UNDEF

      integer(4) :: GLP_CV
      integer(4) :: GLP_IV
      integer(4) :: GLP_BV

      integer(4) :: GLP_IROWGEN
      integer(4) :: GLP_IBINGO
      integer(4) :: GLP_IHEUR
      integer(4) :: GLP_ICUTGEN
      integer(4) :: GLP_IBRANCH
      integer(4) :: GLP_ISELECT
      integer(4) :: GLP_IPREPRO

        parameter (GLP_MIN = 1)
        parameter (GLP_MAX = 2)

        parameter (GLP_FR = 1)
        parameter (GLP_LO = 2)
        parameter (GLP_UP = 3)
        parameter (GLP_DB = 4)
        parameter (GLP_FX = 5)

        parameter (GLP_ON = 1)
        parameter (GLP_OFF = 0)

        parameter (GLP_PRIMAL = 1)
        parameter (GLP_DUALP  = 2)
        parameter (GLP_DUAL   = 3)

      parameter (GLP_UNDEF  = 1)
      parameter (GLP_FEAS   = 2)
      parameter (GLP_INFEAS = 3)
      parameter (GLP_NOFEAS = 4)
      parameter (GLP_OPT    = 5)
      parameter (GLP_UNBND  = 6)

      parameter (GLP_CV = 1)
      parameter (GLP_IV = 2)
      parameter (GLP_BV = 3)

      parameter (GLP_IROWGEN =  1)
      parameter (GLP_IBINGO  =  2)
      parameter (GLP_IHEUR   =  3)
      parameter (GLP_ICUTGEN =  4)
      parameter (GLP_IBRANCH =  5)
      parameter (GLP_ISELECT =  6)
      parameter (GLP_IPREPRO =  7)

      type, bind(c) :: glp_smcp
        integer (c_int) :: msg_lev
        integer (c_int) :: meth
        integer (c_int) :: pricing
        integer (c_int) :: r_test
        real (c_double) :: tol_bnd
        real (c_double) :: tol_dj
        real (c_double) :: tol_piv
        real (c_double) :: obj_ll
        real (c_double) :: obj_ul
        integer (c_int) :: it_lim
        integer (c_int) :: tm_lim
        integer (c_int) :: out_frq
        integer (c_int) :: out_dly
        integer (c_int) :: presolve
        real (c_double) :: foo_bar(0:35)
      end type glp_smcp

      type, bind(c) :: glp_iocp
        integer (c_int) :: msg_lev
        integer (c_int) :: br_tech
        integer (c_int) :: bt_tech
        real (c_double) :: tol_int
        real (c_double) :: tol_obj
        integer (c_int) :: tm_lim
        integer (c_int) :: out_frq
        integer (c_int) :: out_dly
        integer (c_int) :: cb_func
        integer (c_int) :: cb_info
        integer (c_int) :: cb_size
        integer (c_int) :: pp_tech
        real (c_double) :: mip_gap
        integer (c_int) :: mir_cuts
        integer (c_int) :: gmi_cuts
        integer (c_int) :: cov_cuts
        integer (c_int) :: clq_cuts
        integer (c_int) :: presolve
        integer (c_int) :: binarize
        integer (c_int) :: fp_heur
        real (c_double) :: foo_bar(0:29)
      end type glp_iocp

      interface

        integer(4) function glp_create_prob()
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_create_prob" :: glp_create_prob
        end function

        integer(4) function glp_init_smcp(parm_struct)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_init_smcp" :: glp_init_smcp
          integer(4) :: parm_struct
cDEC$ ATTRIBUTES REFERENCE :: parm_struct
        end function

          subroutine glp_set_prob_name(prob,probname)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_set_prob_name" :: glp_set_prob_name
            integer(4) :: prob
cDEC$ ATTRIBUTES VALUE :: prob
            character(*) :: probname
cDEC$ ATTRIBUTES REFERENCE :: probname
          end subroutine

          subroutine glp_set_obj_dir(prob,objdir)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_set_obj_dir" :: glp_set_obj_dir
            integer(4) :: prob
cDEC$ ATTRIBUTES VALUE :: prob
            integer(4) :: objdir
cDEC$ ATTRIBUTES VALUE :: objdir
          end subroutine

          integer(4) function glp_add_rows(prob,nrs)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_add_rows" :: glp_add_rows
            integer(4) :: prob
cDEC$ ATTRIBUTES VALUE :: prob
            integer(4) :: nrs
cDEC$ ATTRIBUTES VALUE :: nrs
          end function

          integer(4) function glp_add_cols(prob,ncs)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_add_cols" :: glp_add_cols
            integer(4) :: prob
cDEC$ ATTRIBUTES VALUE :: prob
            integer(4) :: ncs
cDEC$ ATTRIBUTES VALUE :: ncs
          end function

          subroutine glp_set_obj_coef(prob,j,coef)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_set_obj_coef" :: glp_set_obj_coef
            integer(4) :: prob
cDEC$ ATTRIBUTES VALUE :: prob
            integer(4) :: j
cDEC$ ATTRIBUTES VALUE :: j
            real(8) :: coef
cDEC$ ATTRIBUTES VALUE :: coef
          end subroutine

          subroutine glp_set_row_bnds(prob,i,type,lb,ub)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_set_row_bnds" :: glp_set_row_bnds
            integer(4) :: prob
cDEC$ ATTRIBUTES VALUE :: prob
            integer(4) :: i
cDEC$ ATTRIBUTES VALUE :: i
            integer(4) :: type
cDEC$ ATTRIBUTES VALUE :: type
            real(8) :: lb
cDEC$ ATTRIBUTES VALUE :: lb
            real(8) :: ub
cDEC$ ATTRIBUTES VALUE :: ub
          end subroutine

          subroutine glp_set_col_bnds(prob,j,type,lb,ub)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_set_col_bnds" :: glp_set_col_bnds
                  integer(4) :: prob
cDEC$ ATTRIBUTES VALUE :: prob
                  integer(4) :: j
cDEC$ ATTRIBUTES VALUE :: j
                  integer(4) :: type
cDEC$ ATTRIBUTES VALUE :: type
                  real(8) :: lb
cDEC$ ATTRIBUTES VALUE :: lb
                  real(8) :: ub
cDEC$ ATTRIBUTES VALUE :: ub
          end subroutine

          subroutine glp_load_matrix(prob,ne,ia,ja,ar)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_load_matrix" :: glp_load_matrix
                  integer(4) :: prob
cDEC$ ATTRIBUTES VALUE :: prob
                  integer(4) :: ne
cDEC$ ATTRIBUTES VALUE :: ne
                  integer(4) :: ia(*)
cDEC$ ATTRIBUTES REFERENCE :: ia
                  integer(4) :: ja(*)
cDEC$ ATTRIBUTES REFERENCE :: ja
                  real(8) :: ar(*)
cDEC$ ATTRIBUTES REFERENCE :: ar
          end subroutine

          integer(4) function glp_check_dup(m,n,ne,ia,ja)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_check_dup" :: glp_check_dup
                  integer(4) :: m
cDEC$ ATTRIBUTES VALUE :: m
                  integer(4) :: n
cDEC$ ATTRIBUTES VALUE :: n
                  integer(4) :: ne
cDEC$ ATTRIBUTES VALUE :: ne
                  integer(4) :: ia(*)
cDEC$ ATTRIBUTES REFERENCE :: ia
                  integer(4) :: ja(*)
cDEC$ ATTRIBUTES REFERENCE :: ja
          end function

          integer(4) function glp_simplex(prob,parm)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_simplex" :: glp_simplex
                  integer(4) :: prob
cDEC$ ATTRIBUTES VALUE :: prob
                  integer(4) :: parm
cDEC$ ATTRIBUTES REFERENCE :: parm
          end function

          integer(4) function glp_write_lp(prob,parm,fname)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_write_lp" :: glp_write_lp
                  integer(4) :: prob
cDEC$ ATTRIBUTES VALUE :: prob
                  integer(4) :: parm
cDEC$ ATTRIBUTES REFERENCE :: parm
                  character(*) :: fname
cDEC$ ATTRIBUTES REFERENCE :: fname
          end function

          integer(4) function glp_get_status(prob)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_get_status" :: glp_get_status
                  integer(4) :: prob
cDEC$ ATTRIBUTES VALUE :: prob
          end function

          real(8) function glp_get_obj_val(prob)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_get_obj_val" :: glp_get_obj_val
                  integer(4) :: prob
cDEC$ ATTRIBUTES VALUE :: prob
          end function

          real(8) function glp_get_col_prim(prob,j)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_get_col_prim" :: glp_get_col_prim
                  integer(4) :: prob
cDEC$ ATTRIBUTES VALUE :: prob
          integer(4) :: j
cDEC$ ATTRIBUTES VALUE :: j
          end function

        integer(4) function glp_init_iocp(parm_struct)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_init_iocp" :: glp_init_iocp

            integer(4) :: parm_struct
cDEC$ ATTRIBUTES REFERENCE :: parm_struct
        end function

          subroutine glp_set_col_kind(prob,j,kind)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_set_col_kind" :: glp_set_col_kind
                  integer(4) :: prob
cDEC$ ATTRIBUTES VALUE :: prob
          integer(4) :: j
cDEC$ ATTRIBUTES VALUE :: j
          integer(4) :: kind
cDEC$ ATTRIBUTES VALUE :: kind
          end subroutine

          integer(4) function glp_intopt(prob,parm)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_intopt" :: glp_intopt
                  integer(4) :: prob
cDEC$ ATTRIBUTES VALUE :: prob
                  integer(4) :: parm
cDEC$ ATTRIBUTES REFERENCE :: parm
          end function

          integer(4) function glp_mip_status(prob)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_mip_status" :: glp_mip_status
                  integer(4) :: prob
cDEC$ ATTRIBUTES VALUE :: prob
          end function

        real(8) function glp_mip_obj_val(prob)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_mip_obj_val" :: glp_mip_obj_val
            integer(4) :: prob
cDEC$ ATTRIBUTES VALUE :: prob
          end function

          real(8) function glp_mip_col_val(prob,j)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_mip_col_val" :: glp_mip_col_val
                  integer(4) :: prob
cDEC$ ATTRIBUTES VALUE :: prob
          integer(4) :: j
cDEC$ ATTRIBUTES VALUE :: j
          end function

        integer(4) function glp_ios_curr_node(tree)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_ios_curr_node" :: glp_ios_curr_node
          integer(4) :: tree
cDEC$ ATTRIBUTES REFERENCE :: tree
        end function

          subroutine glp_delete_prob(prob)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_delete_prob" :: glp_delete_prob
                  integer(4) :: prob
cDEC$ ATTRIBUTES VALUE :: prob
          end subroutine

          integer(4) function glp_ios_reason(tree)
cDEC$ ATTRIBUTES DLLIMPORT, ALIAS : "_glp_ios_reason" :: glp_ios_reason
                  integer(4) :: tree
cDEC$ ATTRIBUTES REFERENCE :: tree
          end function

        subroutine GLPKintsolcb(tree,info)
cDEC$ ATTRIBUTES DLLEXPORT, REFERENCE, ALIAS : "GLPKINTSOLCB" ::
GLPKINTSOLCB
          integer(4), intent(in) :: tree
cDEC$ ATTRIBUTES REFERENCE :: tree

c * Note that because "info" is always NULL in our case, we can completely remove it
c   from the argument list above.

          integer(4), optional, intent(in) :: info
cDEC$ ATTRIBUTES REFERENCE :: info
        end subroutine

      end interface

GLPK-Fortran edit

A FORTRAN 90 binding by Jeff Armstrong can be found at https://github.com/ArmstrongJ/GLPK-Fortran. Development stopped in 2014. The code in licensed under GPL 3.