Sample FORTRAN & C  Programs 

Sample FORTRAN Driver Programs

These are sample FORTRAN programs used in part (6) or in whole throughout this document. In addition to these programs, there may be additional sample FORTRAN programs distributed with the Optimization Library code. Note that these simple driver programs are only samples that show how an application program that uses Optimization Library modules should be organized. They should not be used for production work or for evaluating performance.

Sample FORTRAN Program EXSELNAM

C***********************************************************************
C
C                            EXSELNAM
C
C   This program solves the same maximization problem as in sample
C   program EXLMDL. A secondary objective of the program is to show that
C   EKKCSET can be used to set the problem name, the right hand side
C   name and the range name; EKKNAME can be used to add row and column
C   names; EKKSEL can be used to restrict the EKKPRTS and EKKBCDO
C   operations to rows and columns whose names match a specified
C   character string.
C
C***********************************************************************
C
      PROGRAM MAIN
C
C   Bring in include files with control variable definitions.
      IMPLICIT NONE
      INCLUDE (OSLI)
      INCLUDE (OSLR)
      INCLUDE (OSLC)
C
C   Space to Use
      INTEGER*4 MAXSPC,NCHARS
      PARAMETER (MAXSPC=20000,NCHARS=7)
      REAL*8    DSPACE(MAXSPC)
C
      CHARACTER*7  ROWNAMES(5),COLNAMES(8)
      DATA COLNAMES/'TCOL001','TCOL002','TCOL003','TCOL004',
     +              'TCOL005','TCOL006','TCOL007','TCOL008'/
      DATA ROWNAMES/'TROW01','TROW02','TROW03','TROW04',
     +              'TROW05'/
      INTEGER*4 NUMROW,NUMCOL,STARTROW,STARTCOL,RTCOD
      DATA      NUMROW,NUMCOL,STARTROW,STARTCOL,RTCOD/5,8,1,1,0/
C
      CHARACTER SELNAME1*3,WCARD1*1,ARBCHAR1*1
      DATA      SELNAME1,WCARD1,ARBCHAR1/'?C*','*','?'/
C
      INTEGER*4 IRL,ICL,ICL1,IEL
      PARAMETER (IRL=5,ICL=8,ICL1=9,IEL=14)
      REAL*8 DRLO(IRL),DCLO(ICL),DOBJ(ICL),DELS(IEL),DRUP(IRL),DCUP(ICL)
      INTEGER*4 NROW,NCOL,NEL,ITYPE,MCOL(ICL1),MROW(IEL)
      DATA NROW,NCOL,NEL,ITYPE /5,8,14,2/
C
C   Matrix elements.
      DATA DELS /3.0D0,5.6D0,1.0D0,2.0D0,1.1D0,1.0D0,-2.0D0,
     +           2.8D0,-1.0D0,1.0D0,1.0D0,-1.2D0,-1.0D0,1.9D0/
C
C   Row indices.
      DATA MROW/1,5,1,2,2,3,1,4,1,5,3,4,1,5/
C
C   Column starts.
      DATA MCOL/1,3,5,7,9,11,12,13,15/
C
C   Lower bounds on row activities.
      DATA DRLO/2.5D0,-1.0D31,4.0D0,1.8D0,3.0D0/
C
C   Upper bounds on row activities.
      DATA DRUP/1.0D31,2.1D0,4.0D0,5.0D0,1.5D01/
C
C   Lower bounds on columns.
      DATA DCLO/2.5D0,0.0D0,2*0.0D0,5.0D-1,3*0.0D0/
C
C   Upper bounds on columns.
      DATA DCUP/1.0D31,4.1D0,2*1.0D31,4.0D0,2*1.0D31,4.3D0/
C
C   Objective function coefficients.
      DATA DOBJ/1.0D0,3*0.0D0,2.0D0,2*0.0D0,-1.0D0/
C
C
C   Describe application and specify that there is 1 model.
      CALL EKKDSCA(RTCOD,DSPACE,MAXSPC,1)
        IF (RTCOD.GT.0) CALL CHKRT('EKKDSCA',RTCOD)
C
C   Set to maximization problem.
      CALL EKKRGET(RTCOD,DSPACE,OSLR,OSLRLN)
        IF (RTCOD.GT.0) CALL CHKRT('EKKRGET',RTCOD)
        RMAXMIN = -1.0D0
      CALL EKKRSET(RTCOD,DSPACE,OSLR,OSLRLN)
        IF (RTCOD.GT.0) CALL CHKRT('EKKRSET',RTCOD)
C
C   Set length of names to be 7 characters maximum
      CALL EKKIGET(RTCOD,DSPACE,OSLI,OSLILN)
        IF (RTCOD.GT.0) CALL CHKRT('EKKIGET',RTCOD)
        INUMCHAR = NCHARS
      CALL EKKISET(RTCOD,DSPACE,OSLI,OSLILN)
        IF (RTCOD.GT.0) CALL CHKRT('EKKISET',RTCOD)
C
C   Pass model with matrix stored by columns.
      CALL EKKLMDL(RTCOD,DSPACE,ITYPE,NROW,NCOL,NEL,DOBJ,DRLO,DRUP,
     +             DCLO,DCUP,MROW,MCOL,DELS)
        IF (RTCOD.GT.0) CALL CHKRT('EKKLMDL',RTCOD)
C
C   Set names of current model, RHS, and range.
      CALL EKKCGET(RTCOD,DSPACE,OSLC,OSLCLN)
        IF (RTCOD.GT.0) CALL CHKRT('EKKCGET',RTCOD)
        CNAME   = 'TPROB01'
        CRHS    = 'TRHS1'
        CRANGE  = 'TRANGE1'
      CALL EKKCSET(RTCOD,DSPACE,OSLC,OSLCLN)
        IF (RTCOD.GT.0) CALL CHKRT('EKKCSET',RTCOD)
C
C   Add rows and columns names.
      CALL EKKNAME(RTCOD,DSPACE,NUMROW,ROWNAMES,STARTROW,NUMCOL,
     +             COLNAMES,STARTCOL,1)
        IF (RTCOD.GT.0) CALL CHKRT('EKKNAME',RTCOD)
C
C   Write current model to a file on unit 32 - MPS format.
      CALL EKKBCDO(RTCOD,DSPACE,32,1,2)
        IF (RTCOD.GT.0) CALL CHKRT('EKKBCDO',RTCOD)
C
C   Solve problem using simplex method.
      CALL EKKSSLV(RTCOD,DSPACE,1,2)
        IF (RTCOD.GT.0) CALL CHKRT('EKKSSLV',RTCOD)
C
C   Print solution.
      CALL EKKPRTS(RTCOD,DSPACE)
        IF (RTCOD.GT.0) CALL CHKRT('EKKPRTS',RTCOD)
C
C   Select rows/columns with names matching the string SELNAME1.
      CALL EKKSEL(RTCOD,DSPACE,SELNAME1,3,WCARD1,ARBCHAR1,1,1)
        IF (RTCOD.GT.0) CALL CHKRT('EKKSEL ',RTCOD)
C
C   Print "matching" part of solution.
      CALL EKKPRTS(RTCOD,DSPACE)
        IF (RTCOD.GT.0) CALL CHKRT('EKKPRTS',RTCOD)
C
C   Write "matching" part of model to a file on unit 33 - MPS format.
      CALL EKKBCDO(RTCOD,DSPACE,33,1,2)
        IF (RTCOD.GT.0) CALL CHKRT('EKKBCDO',RTCOD)
C
      STOP
      END
C
C***********************************************************************
C   This subroutine prints the character string RTNAME and the return
C   code RTCOD and stops if RTCOD is large enough to indicate that an
C   error or severe error has occured.
C***********************************************************************
C
      SUBROUTINE CHKRT(RTNAME,RTCOD)
      CHARACTER*7 RTNAME
      INTEGER*4   RTCOD
C
      WRITE(6,9000) RTNAME,RTCOD
      IF (RTCOD.GE.200) STOP 16
      RETURN
9000  FORMAT (1X,'********** ',A7,' return code of ',I4,' **********')
      END

No input data is required to run this program.

Sample FORTRAN Program EXSELNM2

C***********************************************************************
C
C                            EXSELNM2
C
C   This program solves the same maximization problem as in sample
C   program EXLMDL.  However, EKKNAME and EKKSEL are used here to
C   select rows and columns for printing.
C
C***********************************************************************
C
      PROGRAM MAIN
C
C   Bring in include files with control variable definitions.
      INCLUDE (OSLR)
      INCLUDE (OSLN)
C
C   Space to use
      PARAMETER (MAXSPC=15000)
      REAL*8    DSPACE(MAXSPC)
      INTEGER*4 MSPACE(2*MAXSPC)
      EQUIVALENCE (DSPACE,MSPACE)
C
      PARAMETER (IRL=5,ICL=8,ICL1=9,IEL=14)
      REAL*8 DRLO(IRL),DCLO(ICL),DOBJ(ICL),DELS(IEL),DRUP(IRL),DCUP(ICL)
      INTEGER*4 NCOL,NROW,NEL,ITYPE,MCOL(ICL1),MROW(IEL),RTCOD
C
C   Define the model.
      DATA NROW,NCOL,NEL,ITYPE/5,8,14,2/
C
C   Matrix elements.
      DATA DELS /3.0D0,5.6D0,1.0D0,2.0D0,1.1D0,1.0D0,-2.0D0,
     +           2.8D0,-1.0D0,1.0D0,1.0D0,-1.2D0,-1.0D0,1.9D0/
C
C   Row indices.
      DATA MROW /1,5,1,2,2,3,1,4,1,5,3,4,1,5/
C
C   Column starts.
      DATA MCOL /1,3,5,7,9,11,12,13,15/
C
C   Lower bounds on row activities.
      DATA DRLO /2.5D0,-1.0D31,4.0D0,1.8D0,3.0D0/
C
C   Upper bounds on row activities.
      DATA DRUP /1.0D31,2.1D0,4.0D0,5.0D0,1.5D01/
C
C   Lower bounds on columns.
      DATA DCLO /2.5D0,0.0D0,2*0.0D0,5.0D-1,3*0.0D0/
C
C   Upper bounds on columns.
      DATA DCUP /1.0D31,4.1D0,2*1.0D31,4.0D0,2*1.0D31,4.3D0/
C
C   Objective function coefficients.
      DATA DOBJ /1.0D0,3*0.0D0,2.0D0,2*0.0D0,-1.0D0/
C
C   Names to be added to matrix.
      CHARACTER*8  ROWNAMES(5), COLNAMES(8)
      DATA COLNAMES /'TCOL0001','TCOL0002','TCOL0003','TCOL0004',
     +               'TCOL0005','TCOL0006','TCOL0007','TCOL0008'/
      DATA ROWNAMES /'ROW01   ','ROW02   ','ROW03   ','ROW04   ',
     +               'ROW05   '/
      INTEGER*4  NUMROW,NUMCOL,STARTROW,STARTCOL,OSLNAMES
      DATA       NUMROW,NUMCOL,STARTROW,STARTCOL,OSLNAMES/5,8,1,1,0/
C
C   String used in selecting rows and columns to be printed.
C   Rows or columns with at least one character, followed by 'O',
C   followed by at least four characters will be printed.
      CHARACTER*8  SELNAME
      CHARACTER*1  WILDCARD, ARBCHAR
      INTEGER*4    SELNAMELEN, OPER, ROWCOL
      DATA         SELNAME, WILDCARD, ARBCHAR /'?*O????*','*','?'/
      DATA         SELNAMELEN, OPER, ROWCOL /8, 1, 1/
C
C
C   Describe application and specify that there is 1 model.
      CALL EKKDSCA(RTCOD,DSPACE,MAXSPC,1)
        IF (RTCOD.GT.0) CALL CHKRT('EKKDSCA',RTCOD)
C
C   Set to maximization problem.
      CALL EKKRGET(RTCOD,DSPACE,OSLR,OSLRLN)
        IF (RTCOD.GT.0) CALL CHKRT('EKKRGET',RTCOD)
        RMAXMIN=-1.0D0
      CALL EKKRSET(RTCOD,DSPACE,OSLR,OSLRLN)
        IF (RTCOD.GT.0) CALL CHKRT('EKKRSET',RTCOD)
C
C   Pass the model with matrix stored by columns.
      CALL EKKLMDL(RTCOD,DSPACE,ITYPE,NROW,NCOL,NEL,DOBJ,DRLO,DRUP,
     +             DCLO,DCUP,MROW,MCOL,DELS)
        IF (RTCOD.GT.0) CALL CHKRT('EKKLMDL',RTCOD)
C
C   Since matrix names are not yet defined, this will only
C   initialize selection lists to all 1s.
      CALL EKKSEL(RTCOD,DSPACE,SELNAME,SELNAMELEN,WILDCARD,ARBCHAR,
     +            OPER,ROWCOL)
        IF (RTCOD.GT.0) CALL CHKRT('EKKSEL ',RTCOD)
C
C   Write model to a file on unit 18 in MPS format.
      CALL EKKBCDO(RTCOD,DSPACE,18,1,2)
        IF (RTCOD.GT.0) CALL CHKRT('EKKBCDO',RTCOD)
C
C   Add names to the matrix.
      CALL EKKNAME(RTCOD,DSPACE,NUMROW,ROWNAMES,STARTROW,NUMCOL,
     +             COLNAMES,STARTCOL,OSLNAMES)
        IF (RTCOD.GT.0) CALL CHKRT('EKKNAME',RTCOD)
C
C   Solve problem using the simplex method.
      CALL EKKSSLV(RTCOD,DSPACE,1,2)
        IF (RTCOD.GT.0) CALL CHKRT('EKKSSLV',RTCOD)
C
C   Now update the selection lists based on the above criteria.
      CALL EKKSEL(RTCOD,DSPACE,SELNAME,SELNAMELEN,WILDCARD,ARBCHAR,
     +            OPER,ROWCOL)
        IF (RTCOD.GT.0) CALL CHKRT('EKKSEL',RTCOD)
C
C   Write basis to a file on unit 28 in MPS format.
      CALL EKKBASO(RTCOD,DSPACE,28,1)
        IF (RTCOD.GT.0) CALL CHKRT('EKKBCDO',RTCOD)
C
C   Change the selection lists directly.  Every odd-numbered row
C   will be selected for printing.
      CALL EKKNGET(RTCOD,DSPACE,OSLN,OSLNLN)
        IF (RTCOD.GT.0) CALL CHKRT('EKKNGET',RTCOD)
      DO I = 1,NROW,2
        MSPACE(NSELLISTROW+I-1)=IBSET(MSPACE(NSELLISTROW+I-1),0)
      ENDDO
      DO I = 2,NROW,2
        MSPACE(NSELLISTROW+I-1)=IBCLR(MSPACE(NSELLISTROW+I-1),0)
      ENDDO
C
C   Print the solution.
      CALL EKKPRTS(RTCOD,DSPACE)
        IF (RTCOD.GT.0) CALL CHKRT('EKKPRTS',RTCOD)
C
      STOP
      END
C
C***********************************************************************
C   This subroutine prints the character string RTNAME and the return
C   code RTCOD and stops if RTCOD is large enough to indicate that an
C   error or severe error has occured.
C***********************************************************************
C
      SUBROUTINE CHKRT(RTNAME,RTCOD)
      CHARACTER*7 RTNAME
      INTEGER*4   RTCOD
C
      WRITE(6,9000) RTNAME,RTCOD
      IF (RTCOD.GE.200) STOP 16
      RETURN
9000  FORMAT (1X,'********** ',A7,' return code of ',I4,' **********')
      END

No input data is required to run this program.

Sample FORTRAN Program EXSENS1

C***********************************************************************
C
C                            EXSENS1
C
C   This program reads an MPS file containing an LP model, performs
C   presolve processing, solves it, and performs sensitivity analysis
C   on the objective function coefficients and row and column bounds.
C   EKKPRTS is used to print the results.
C
C***********************************************************************
C
      PROGRAM MAIN
C
C   Allocate dspace.
      PARAMETER (MAXSPC=50000)
      REAL*8    DSPACE(MAXSPC)
      COMMON/BIG/DSPACE
      INTEGER*4 RTCOD
C
C   Describe application and specify that there is 1 model.
      CALL EKKDSCA(RTCOD,DSPACE,MAXSPC,1)
        IF (RTCOD.GT.0) CALL CHKRT('EKKDSCA',RTCOD)
C
C   Read an LP model from MPS file on unit 98.
      CALL EKKMPS(RTCOD,DSPACE,98,2,0)
        IF (RTCOD.GT.0) CALL CHKRT('EKKMPS ',RTCOD)
C
C   Presolve the problem.
      CALL EKKPRSL(RTCOD,DSPACE,12,3)
        IF (RTCOD.GT.0) CALL CHKRT('EKKPRSL',RTCOD)
C
C   Solve the problem using primal simplex.
      CALL EKKSSLV(RTCOD,DSPACE,1,2)
        IF (RTCOD.GT.0) CALL CHKRT('EKKSSLV',RTCOD)
C
C   Postsolve to map back to original variables.
      CALL EKKPSSL(RTCOD,DSPACE,12)
        IF (RTCOD.GT.0) CALL CHKRT('EKKPSSL',RTCOD)
C
C   Solve again to ensure dual feasibility.
      CALL EKKSSLV(RTCOD,DSPACE,1,3)
        IF (RTCOD.GT.0) CALL CHKRT('EKKSSLV',RTCOD)
C
C   Perform sensitivity analysis on the objective function.
      CALL EKKSOBJ(RTCOD,DSPACE)
        IF (RTCOD.GT.0) CALL CHKRT('EKKSOBJ',RTCOD)
C   Perform sensitivity analysis on row and column bounds.
      CALL EKKSBND(RTCOD,DSPACE,3,1)
        IF (RTCOD.GT.0) CALL CHKRT('EKKSOBJ',RTCOD)
C
C   Print the solution and sensitivity analysis results.
      CALL EKKPRTS(RTCOD,DSPACE)
        IF (RTCOD.GT.0) CALL CHKRT('EKKPRTS',RTCOD)
C
      STOP
      END
C
C***********************************************************************
C   This subroutine prints the character string RTNAME and the return
C   code RTCOD and stops if RTCOD is large enough to indicate that an
C   error or severe error has occured.
C***********************************************************************
C
      SUBROUTINE CHKRT(RTNAME,RTCOD)
      CHARACTER*7 RTNAME
      INTEGER*4   RTCOD
C
      WRITE(6,9000) RTNAME,RTCOD
      IF (RTCOD.GE.200) STOP 16
      RETURN
9000  FORMAT (1X,'********** ',A7,' return code of ',I4,' **********')
      END

You can run this program using "Sample Linear Programming Model Data 1".

Sample FORTRAN Program EXSENS2

C***********************************************************************
C
C                            EXSENS2
C
C   This program reads an MPS file containing an LP model, solves it,
C   and performs sensitivity analysis on the row and column bounds and
C   on the objective function coefficients.  Results are printed by
C   directly accessing the appropriate control variables, rather than
C   calling EKKPRTS.
C
C***********************************************************************
C
      PROGRAM MAIN
C
C   Bring in include files with control variable definitions.
      INCLUDE (OSLI)
      INCLUDE (OSLN)
C
C   Allocate dspace.
      PARAMETER (MAXSPC=50000)
      REAL*8     DSPACE(MAXSPC)
      INTEGER*4  MSPACE(2*MAXSPC),RTCOD
      EQUIVALENCE (DSPACE,MSPACE)
      COMMON/BIG/DSPACE
C
C   Describe application and specify that there is 1 model.
      CALL EKKDSCA(RTCOD,DSPACE,MAXSPC,1)
        IF (RTCOD.GT.0) CALL CHKRT('EKKDSCA',RTCOD)
C
C   Read an LP model from MPS file on unit 98.
      CALL EKKMPS(RTCOD,DSPACE,98,2,0)
        IF (RTCOD.GT.0) CALL CHKRT('EKKMPS ',RTCOD)
C
C   Solve the problem using primal simplex.
      CALL EKKSSLV(RTCOD,DSPACE,1,2)
        IF (RTCOD.GT.0) CALL CHKRT('EKKSSLV',RTCOD)
C
C   Perform sensitivity analysis on row and column bounds.
      CALL EKKSBND(RTCOD,DSPACE,3,1)
        IF (RTCOD.GT.0) CALL CHKRT('EKKSOBJ',RTCOD)
C
C   Perform sensitivity analysis on the objective function.
      CALL EKKSOBJ(RTCOD,DSPACE)
      IF (RTCOD.GT.0) CALL CHKRT('EKKSOBJ',RTCOD)
C
C   Print results of sensitivity analysis using the control variables.
      CALL EKKNGET(RTCOD,DSPACE,OSLN,OSLNLN)
      CALL EKKIGET(RTCOD,DSPACE,OSLI,OSLILN)
      WRITE(6,8000) '------- Objective Function Sensitivity -------'
      DO I = 1,INUMCOLS
        WRITE(6,7000)'  Coefficient', I
        WRITE(6,8000)'     Cost range upward:   ',DSPACE(NSOBJUPC+I-1)
        WRITE(6,8000)'        Objective value:  ',DSPACE(NSOBJUPV+I-1)
        WRITE(6,7000)'        Leaving variable: ',MSPACE(NSOBJUPL+I-1)
        WRITE(6,7000)'        Entering variable:',MSPACE(NSOBJUPE+I-1)
        WRITE(6,8000)'     Cost range downward: ',DSPACE(NSOBJDNC+I-1)
        WRITE(6,8000)'        Objective value:  ',DSPACE(NSOBJDNV+I-1)
        WRITE(6,7000)'        Leaving variable: ',MSPACE(NSOBJDNL+I-1)
        WRITE(6,7000)'        Entering variable:',MSPACE(NSOBJDNE+I-1)
      ENDDO
      WRITE(6,8000) '------- Column Bounds Sensitivity -------'
      DO I = 1,INUMCOLS
        WRITE(6,7000)'  Column', I
        WRITE(6,8000)'    Bound range upward:   ',DSPACE(NSBNDCUPB+I-1)
        WRITE(6,8000)'        Objective value:  ',DSPACE(NSBNDCUPV+I-1)
        WRITE(6,7000)'        Leaving variable: ',MSPACE(NSBNDCUPL+I-1)
        WRITE(6,7000)'        Entering variable:',MSPACE(NSBNDCUPE+I-1)
        WRITE(6,8000)'    Bound range downward: ',DSPACE(NSBNDCDNB+I-1)
        WRITE(6,8000)'        Objective value:  ',DSPACE(NSBNDCDNV+I-1)
        WRITE(6,7000)'        Leaving variable: ',MSPACE(NSBNDCDNL+I-1)
        WRITE(6,7000)'        Entering variable:',MSPACE(NSBNDCDNE+I-1)
      ENDDO
      WRITE(6,8000) '------- Row Bounds Sensitivity -------'
      DO I = 1,INUMROWS
        WRITE(6,7000)'  Row', I
        WRITE(6,8000)'    Bound range upward:   ',DSPACE(NSBNDRUPB+I-1)
        WRITE(6,8000)'        Objective value:  ',DSPACE(NSBNDRUPV+I-1)
        WRITE(6,7000)'        Leaving variable: ',MSPACE(NSBNDRUPL+I-1)
        WRITE(6,7000)'        Entering variable:',MSPACE(NSBNDRUPE+I-1)
        WRITE(6,8000)'    Bound range downward: ',DSPACE(NSBNDRDNB+I-1)
        WRITE(6,8000)'        Objective value:  ',DSPACE(NSBNDRDNV+I-1)
        WRITE(6,7000)'        Leaving variable: ',MSPACE(NSBNDRDNL+I-1)
        WRITE(6,7000)'        Entering variable:',MSPACE(NSBNDRDNE+I-1)
      ENDDO
C
7000  FORMAT (A,2X,I5)
8000  FORMAT (A,2X,1PD12.5)
C
      STOP
      END
C
C***********************************************************************
C   This subroutine prints the character string RTNAME and the return
C   code RTCOD and stops if RTCOD is large enough to indicate that an
C   error or severe error has occured.
C***********************************************************************
C
      SUBROUTINE CHKRT(RTNAME,RTCOD)
      CHARACTER*7 RTNAME
      INTEGER*4   RTCOD
C
      WRITE(6,9000) RTNAME,RTCOD
      IF (RTCOD.GE.200) STOP 16
      RETURN
9000  FORMAT (1X,'********** ',A7,' return code of ',I4,' **********')
      END

You can run this program using "Sample Linear Programming Model Data 1".

Sample FORTRAN Program EXSMDL

C***********************************************************************
C
C                            EXSMDL
C
C   This program reads a linear program from a spreadsheet workfile,
C   solves the problem with the simplex method, prints the solution,
C   and updates the contents of the adjustable cells in the spreadsheet
C   worfile. The program may be run using the sample spreadsheet
C   workfile exss1.ssdata. The sample file contains the following model
C   in spreadsheet format:
C
C   (Adjustable cells)
C   A1: 0       B1: 0       C1: 0
C
C   (Constraint cells)
C   A2: 0<=+A1  B2: 0<=+B1  C2: 0<=+C1  D2: +A1+B1<=10  E2: +B1+C1<=10
C
C   (Objective cell)
C   A3: -C1
C
C   (Named ranges)
C   SOL:   A:A1..A:C1      CONST: A:A2..A:E2           OBJ:   A:A
C
C***********************************************************************
C
      PROGRAM MAIN
C
C   Bring in include file with real control variable definitions.
      IMPLICIT NONE
      INCLUDE (OSLC)
C
C   Allocate dspace.
      INTEGER*4 MAXSPC,RTCOD
      PARAMETER (MAXSPC=200000)
      REAL*8    DSPACE(MAXSPC)
      COMMON/BIG/DSPACE
C
C   Describe application and specify that there is 1 model.
      CALL EKKDSCA(RTCOD,DSPACE,MAXSPC,1)
        IF (RTCOD.GT.0) CALL CHKRT('EKKDSCA',RTCOD)
C
C   Set character control variables to show cell locations.
      CALL EKKCGET(RTCOD,DSPACE,OSLC,OSLCLN)
        IF (RTCOD.GT.0) CALL CHKRT('EKKCGET',RTCOD)
        CSSOLUTION  = 'SOL'
        CSCONSTRTS  = 'CONST'
        CSOBJECTIVE = 'OBJ'
      CALL EKKCSET(RTCOD,DSPACE,OSLC,OSLCLN)
        IF (RTCOD.GT.0) CALL CHKRT('EKKCSET',RTCOD)
C
C   Read model data from spreadsheet workfile on unit 98.
      CALL EKKSMDL(RTCOD,DSPACE,98,1,1,0)
        IF (RTCOD.GT.0) CALL CHKRT('EKKSMDL',RTCOD)
C
C   Solve problem using primal simplex method.
      CALL EKKSSLV(RTCOD,DSPACE,1,2)
        IF (RTCOD.GT.0) CALL CHKRT('EKKSSLV',RTCOD)
C
C   Print the solution.
      CALL EKKPRTS(RTCOD,DSPACE)
        IF (RTCOD.GT.0) CALL CHKRT('EKKPRTS',RTCOD)
C
C   Update the adjustable cell contents in the spreadsheet.
      CALL EKKSMDL(RTCOD,DSPACE,98,2,1,0)
        IF (RTCOD.GT.0) CALL CHKRT('EKKSMDL',RTCOD)
C
      STOP
      END
C
C***********************************************************************
C   This subroutine prints the character string RTNAME and the return
C   code RTCOD and stops if RTCOD is large enough to indicate that an
C   error or severe error has occured.
C***********************************************************************
C
      SUBROUTINE CHKRT(RTNAME,RTCOD)
      CHARACTER*7 RTNAME
      INTEGER*4   RTCOD
C
      WRITE(6,9000) RTNAME,RTCOD
      IF (RTCOD.GE.200) STOP 16
      RETURN
9000  FORMAT (1X,'********** ',A7,' return code of ',I4,' **********')
      END

You can run this program using "Sample Spreadsheet Worksheet File 1".

Sample FORTRAN Program EXSOS

C*********************************************************************
C
C                            EXSOS
C
C   This program reads a MIP problem from an MPS file, sets the
C   appropriate control variables to allow for additional sets and
C   integers to be added by the SOS finding routine EKKSOS. EKKSOS
C   is then called to identify any SOS of types 1 and 3 present
C   in the model. The problem is then solved by the simplex solver,
C   followed by calls to EKKMPRE and EKKMSLV. Solution and solution
C   times are printed.
C
C*********************************************************************
C
      PROGRAM MAIN
C
C   Bring in include files with control variable definitions.
      IMPLICIT NONE
      INCLUDE (OSLI)
      INCLUDE (OSLR)
C
C   Allocate dspace and other arrays.
      INTEGER*4 MAXSPC,RTCOD
      PARAMETER (MAXSPC=80000000)
      REAL*8    DSPACE(MAXSPC), TIME1,TIME2
      COMMON/BIG/DSPACE
C
C   Describe application and specify that there is 1 model.
      CALL EKKDSCA(RTCOD,DSPACE,MAXSPC,1)
        IF (RTCOD.GT.0) CALL CHKRT('EKKDSCA',RTCOD)
C
C   Describe the model.
      CALL EKKDSCM(RTCOD,DSPACE,1,1)
        IF (RTCOD.GT.0) CALL CHKRT('EKKDSCM',RTCOD)
C
C   Allow space for adding new sets and integers.
      CALL EKKIGET(RTCOD,DSPACE,OSLI,OSLILN)
        IF (RTCOD.GT.0) CALL CHKRT('EKKIGET',RTCOD)
        IMAXSETS = -100000
        IMAXROWS = -5000
        IMAXINTS = -300000
        ISOLMASK=6
      CALL EKKISET(RTCOD,DSPACE,OSLI,OSLILN)
        IF (RTCOD.GT.0) CALL CHKRT('EKKISET',RTCOD)
C
C   Read in the MPS file from fortran unit 55.
      CALL EKKMPS(RTCOD,DSPACE,55,2,9)
        IF (RTCOD.GT.0) CALL CHKRT('EKKMPS',RTCOD)
C
C   Solve the LP relaxation using the simplex solver.
      CALL EKKSSLV(RTCOD,DSPACE,1,1)
        IF (RTCOD.GT.0) CALL CHKRT('EKKSSLV',RTCOD)
C
      CALL EKKCPUT(TIME1,RTCOD)
C
C   Invoke the MIP preprocessor.
      CALL EKKMPRE(RTCOD,DSPACE,1)
        IF (RTCOD.GT.0) CALL CHKRT('EKKMPRE',RTCOD)
C
C   Identify SOS type 1 & 3 Sets..
      CALL EKKSOS(RTCOD,DSPACE)
        IF (RTCOD.GT.0) CALL CHKRT('EKKSOS',RTCOD)
C
C   Call the branch-and-bound solver.
      CALL EKKMSLV(RTCOD,DSPACE,1,0,0)
        IF (RTCOD.GT.0) CALL CHKRT('EKKMSLV',RTCOD)
C
      CALL EKKCPUT(TIME2,RTCOD)
C
C   Print the solution.
      CALL EKKPRTS(RTCOD,DSPACE)
        IF (RTCOD.GT.0) CALL CHKRT('EKKPRTS',RTCOD)
C
      PRINT *,' '
      PRINT *,' Time spent in Solve: ', TIME2-TIME1, ' seconds.'
      PRINT *,' '
C
      STOP
      END
C
C*********************************************************************
C   This subroutine prints the character string RTNAME and the return
C   code RTCOD and stops if RTCOD is large enough to indicate that an
C   error or severe error has occured.
C*********************************************************************
C
      SUBROUTINE CHKRT(RTNAME,RTCOD)
      CHARACTER*7 RTNAME
      INTEGER*4   RTCOD
C
      WRITE(6,9000) RTNAME,RTCOD
      IF (RTCOD.GE.200) STOP 16
      RETURN
9000  FORMAT (1X,'********** ',A7,' return code of ',I4,' **********')
      END

You can run this program using "Sample Mixed Integer Programming Model Data 2".

Sample FORTRAN Program EXTOMPSX

C***********************************************************************
C
C                            EXTOMPSX
C
C   This program solves an LP problem using the primal simplex
C   algorithm and writes out the basis in the form expected by MPSX.
C
C   In MPSX, the objective row is stored as a row in the constraint
C   matrix. The logical variable associated with the objective row
C   is always a basic variable.  The row activity is equal to the
C   value of the objective function.
C
C   The objective row is not stored as a row in the constraint
C   matrix.  Therefore, it does not appear as part of the basis.
C
C   In this example, the Imaxrows control variable is set before
C   the call to EKKMPS to allow room to add a row to the constraint
C   matrix.  After the problem is solved, the objective row is
C   added to the constraint matrix, the row name is set to the name
C   of the objective function, the row activity for this row
C   is set to the value of the objective function, the row
C   is marked as basic in the row status vector, and the basis
C   is written out in MPS format using EKKBASO.
C
C***********************************************************************
C
      PROGRAM MAIN
C
C   Bring in include files with control variable definitions.
      INCLUDE(OSLR)
      INCLUDE(OSLI)
      INCLUDE(OSLN)
      INCLUDE(OSLC)
C
C   Allocate dspace.
      PARAMETER (MAXSPC=100000,NUMELEMS=30)
      REAL*8 DSPACE(MAXSPC)
      INTEGER*4 MSPACE(2*MAXSPC),RTCOD
      CHARACTER*8 CSPACE(MAXSPC)
      EQUIVALENCE (CSPACE,DSPACE,MSPACE)
      COMMON/BIG/DSPACE
C
C   Data structures to add a row.
      REAL*8 ELEMS(NUMELEMS)
      INTEGER*4 ICOLNUMS(NUMELEMS)
C
C   Describe application and specify that there is 1 model.
      CALL EKKDSCA(RTCOD,DSPACE,MAXSPC,1)
        IF (RTCOD .NE. 0) CALL CHKRT('EKKDSCA',RTCOD)
C
C   Describe the model.
      CALL EKKDSCM(RTCOD,DSPACE,1,1)
        IF (RTCOD .NE. 0) CALL CHKRT('EKKDSCM',RTCOD)
C
C   Set Imaxrows to allow room for an extra row.
      CALL EKKIGET(RTCOD,DSPACE,OSLI,OSLILN)
        IF (RTCOD .NE. 0) CALL CHKRT('EKKIGET',RTCOD)
        IMAXROWS=-1
      CALL EKKISET(RTCOD,DSPACE,OSLI,OSLILN)
        IF (RTCOD .NE. 0) CALL CHKRT('EKKISET',RTCOD)
C
C   Read model data from MPS file on unit 98
      CALL EKKMPS(RTCOD,DSPACE,98,2,0)
        IF (RTCOD .NE. 0) CALL CHKRT('EKKMPS ',RTCOD)
C
C   Crash the problem.
      CALL EKKCRSH(RTCOD,DSPACE,1)
        IF (RTCOD .NE. 0) CALL CHKRT('EKKCRSH',RTCOD)
C
C   Presolve the problem.
      CALL EKKPRSL(RTCOD,DSPACE,15,3)
        IF (RTCOD .NE. 0) CALL CHKRT('EKKPRSL',RTCOD)
C
C   Solve using simplex: random pricing first, then Devex.
      CALL EKKSSLV(RTCOD,DSPACE,1,2)
        IF (RTCOD .NE. 0) CALL CHKRT('EKKSSLV',RTCOD)
C
C   Postsolve the problem.
      CALL EKKPSSL(RTCOD,DSPACE,15)
        IF (RTCOD .NE. 0) CALL CHKRT('EKKPSSL',RTCOD)
C
C   Solve with "values" to ensure dual feasibility.
      CALL EKKSSLV(RTCOD,DSPACE,1,3)
        IF (RTCOD .NE. 0) CALL CHKRT('EKKSSLV',RTCOD)
C
C   Print the solution.
      CALL EKKPRTS(RTCOD,DSPACE)
        IF (RTCOD .NE. 0) CALL CHKRT('EKKPRTS',RTCOD)
C
C   Get integer and index control variables.
      CALL EKKIGET(RTCOD,DSPACE,OSLI,OSLILN)
        IF (RTCOD .NE. 0) CALL CHKRT('EKKIGET',RTCOD)
      CALL EKKNGET(RTCOD,DSPACE,OSLN,OSLNLN)
        IF (RTCOD .NE. 0) CALL CHKRT('EKKNGET',RTCOD)
C
C   Put the objective function in proper form for EKKROW.
      NELEMS=0
      DO 150 I=0,INUMCOLS-1
        IF (DSPACE(NOBJECTIVE+I) .NE. 0.0D0) THEN
          NELEMS=NELEMS+1
          IF (NELEMS .LE. NUMELEMS) THEN
            ELEMS(NELEMS)=DSPACE(NOBJECTIVE+I)
            ICOLNUMS(NELEMS)=I+1
          ENDIF
        ENDIF
 150  CONTINUE
      IF (NELEMS .GT. NUMELEMS) THEN
        WRITE(IPRINTUNIT,*) 'NUMELEMS must be increased to ',NELEMS
        GO TO 4000
      ENDIF
C
C   Add a row to the matrix for the objective function.
      CALL EKKROW(RTCOD,DSPACE,1,INUMROWS+1,NELEMS,ELEMS,ICOLNUMS)
        IF (RTCOD .NE. 0) CALL CHKRT('EKKROW ',RTCOD)
C
C   Get current values of control variables.
      CALL EKKCGET(RTCOD,DSPACE,OSLC,OSLCLN)
        IF (RTCOD .NE. 0) CALL CHKRT('EKKCGET',RTCOD)
      CALL EKKNGET(RTCOD,DSPACE,OSLN,OSLNLN)
        IF (RTCOD .NE. 0) CALL CHKRT('EKKNGET',RTCOD)
      CALL EKKIGET(RTCOD,DSPACE,OSLI,OSLILN)
        IF (RTCOD .NE. 0) CALL CHKRT('EKKIGET',RTCOD)
      CALL EKKRGET(RTCOD,DSPACE,OSLR,OSLRLN)
        IF (RTCOD .NE. 0) CALL CHKRT('EKKRGET',RTCOD)
C
C   Set name of the added row to the name of the objective function.
      CSPACE(NROWNAMES+INUMROWS-1) = COBJECTIVE
C
C   Set the row activity of the added row to the value of the objective.
      DSPACE(NROWACTS+INUMROWS-1) = ROBJVAL
C
C   Mark the added row as basic in the status vector.
      MSPACE(NROWSTAT+INUMROWS-1) = ISHFT(1,31)
C
C   Write out the basis as a file on unit 17 in MPS format.
      CALL EKKBASO(RTCOD,DSPACE,17,1)
        IF (RTCOD .NE. 0) CALL CHKRT('EKKBASO',RTCOD)
4000  CONTINUE
      STOP
      END
C
C***********************************************************************
C   This subroutine prints the character string RTNAME and the return
C   code RTCOD and stops if RTCOD is large enough to indicate that an
C   error or severe error has occured.
C***********************************************************************
C
      SUBROUTINE CHKRT(RTNAME,RTCOD)
      CHARACTER*7 RTNAME
      INTEGER*4   RTCOD
C
      WRITE(6,9000) RTNAME,RTCOD
      IF (RTCOD.GE.200) STOP 16
      RETURN
9000  FORMAT (1X,'********** ',A7,' return code of ',I4,' **********')
      END

You can run this program using "Sample Linear Programming Model Data 1"


Sample C Programs

These are C versions of some of the sample FORTRAN programs. A particular sample C program is functionally equivalent to the similarly named sample FORTRAN program. For example, the sample C program EXMPS is functionally equivalent to the sample FORTRAN program EXMPS.

The Optimization Library-specific C header necessary to run these sample programs is on the web site. Consult the program directory or "Processing Your Program" for information on where the header may be found after installation.

Sample C Program EXBMPR

/* -------------------------------------------------------------------
                               EXBMPR

   This program reads a MIP problem from an MPS file, transforms
   it to a 0/1 MIP problem, solves the problem with the branch-and-
   bound method and transforms back the optimal solution to the
   original variables.  The solution to the original model is printed.
------------------------------------------------------------------- */
#include <stdio.h
#include <stdarg.h
#include "ekkc.h"

void     chkrt(const char *,long);
#define  MAXSPC   3000000
#define  OSLRLN   45
#define  OSLILN   61
double   oslr[OSLRLN];
long     osli[OSLILN];
#define  IMAXROWS  osli[8]
#define  ISOLMASK  osli[32]

main() {
   long    rtcod, io_status;
   double  *dspace;

              /* Allocate work area */
   dspace = (double *) malloc(MAXSPC*sizeof(double));
   mspace = (long *) dspace;
   if (dspace == NULL) {
      printf("Memory allocation for dspace failed\n");
      exit(999);
   }

              /* Describe work space and allow room for one model */
   ekkdsca(&rtcod,dspace,MAXSPC,2);
   if (rtcod0) chkrt("ekkdsca",rtcod);

   ekkdscm(&rtcod,dspace,1,1);
   ekkiget(&rtcod,dspace,osli,OSLILN);
   if (rtcod0) chkrt("ekkiget",rtcod);
    IMAXROWS =-5000;
    ISOLMASK = 6;
   ekkiset(&rtcod,dspace,osli,OSLILN);
   if (rtcod0) chkrt("ekkiset",rtcod);

              /* Read model data from MPS file on FORTRAN unit 57 */
   ekkmps(&rtcod,dspace,57,2,9);
   if (rtcod0) chkrt("ekkmps",rtcod);

              /* Open unit 8 for storing transformations */

   ekkfopn(8,"/tmp/fort.8","UNKNOWN","SEQUENTIAL","FORMATTED",
   "NULL",0,&io_status);

              /* Transform the general integer problem */

   ekkbmpr(&rtcod,dspace,8,1);
   if (rtcod0) chkrt("ekkbmpr",rtcod);

              /* Preprocess the problem */

   ekkmpre(&rtcod,dspace,1);
   if (rtcod0) chkrt("ekkmpre",rtcod);

              /* Solve using B&B method */
   ekkmslv(&rtcod,dspace,1,0,0);
   if (rtcod0) chkrt("ekkmslv",rtcod);

              /* Transform the solution back */

   ekkbmps(&rtcod,dspace,8);
   if (rtcod0) chkrt("ekkbmps",rtcod);

             /* Print the solution */
   ekkprts(&rtcod,dspace);
   if (rtcod0) chkrt("ekkprts",rtcod);
}


void  chkrt(rtname,rtcod)
const char  *rtname;
long  rtcod;
{
   printf("\n****** %s return code of %d ******\n",rtname,rtcod);
   if (rtcod = 200) exit(16);
}

You can run this program using "Sample Mixed Integer Programming Model Data 1".

Sample C Program EXMPS

/* -------------------------------------------------------------------
                               EXMPS

   This program reads a maximization problem from an MPS file, sets
   the appropriate control variable to indicate that it is a
   maximization problem, solves the problem with the simplex method
   and prints the solution.
------------------------------------------------------------------- */
#include <stdio.h
#include <stdarg.h
#include <ekkc.h

void     chkrt(const char *,long);
#define  MAXSPC   300000
#define  OSLRLN   45
double   oslr[OSLRLN];
#define  RMAXMIN  oslr[2]

main() {
   long    rtcod;
   double  *dspace;

              /* Allocate work area */
   dspace = (double *) malloc(MAXSPC*sizeof(double));
   if (dspace == NULL) {
      printf("Memory allocation for dspace failed\n");
      exit(999);
   }


              /* Describe work space and allow room for one model */
   ekkdsca(&rtcod,dspace,MAXSPC,1);
   if (rtcod0) chkrt("ekkdsca",rtcod);

              /* Set to maximization problem */
   ekkrget(&rtcod,dspace,oslr,OSLRLN);
   if (rtcod0) chkrt("ekkrget",rtcod);
   RMAXMIN = -1.0;
   ekkrset(&rtcod,dspace,oslr,OSLRLN);
   if (rtcod0) chkrt("ekkrset",rtcod);

              /* Read model data from MPS file on FORTRAN unit 98 */
   ekkmps(&rtcod,dspace,98,2,0);
   if (rtcod0) chkrt("ekkmps",rtcod);

              /* Solve using simplex method */
   ekksslv(&rtcod,dspace,1,2);
   if (rtcod0) chkrt("ekksslv",rtcod);

              /* Print the solution */
   ekkprts(&rtcod,dspace);
   if (rtcod0) chkrt("ekkprts",rtcod);

}


void  chkrt(rtname,rtcod)
const char  *rtname;
long  rtcod;
{
   printf("\n****** %s return code of %d ******\n",rtname,rtcod);
   if (rtcod = 200) exit(16);
}

You can run this program using "Sample Linear Programming Model Data 1".

Sample C Program EXMPSCB

/* -------------------------------------------------------------------
                               EXMPSCB

   This program reads a maximization problem from an MPS file, sets the
   appropriate control variable to indicate that it is a maximization
   problem, solves the problem with the simplex method and prints the
   solution. This program uses the callback registration function ekkrgcb
   to override the default EKKITRU user-exit and use new exit functions,
   MYITRU and MYITRU2, at different points in the code.
------------------------------------------------------------------- */
#include <stdio.h
#include <stdarg.h
#include "ekkc.h"
#include "oslr.h"

void     chkrt(char *,long);
#define  MAXSPC   300000

/* MYITRU replaces the default EKKITRU */
int MYITRU(double *dspace, int *mspace, int *imode,
        int *istat)
{
    /* Parameter adjustments */
    --mspace;
    --dspace;

    printf("\n **** MYITRU Call Back: (maximization run) ****\n");

    /* Function Body */
    return 0;
} /* MYITRU */

/* MYITRU2 replaces the default EKKITRU */
int MYITRU2(double *dspace, int *mspace, int *imode,
        int *istat)
{
    /* Parameter adjustments */
    --mspace;
    --dspace;

    printf("\n **** MYITRU2 Call Back: (minimization run) ****\n");

    /* Function Body */
    return 0;
} /* MYITRU2 */

main(int argc, char *argv[]) {
   long    rtcod;
   double  *dspace;

              /* Register the callback function MYITRU */
   ekkrgcb(CBITR, MYITRU);

              /* Allocate work area */
   dspace = (double *) malloc(MAXSPC*sizeof(double));
   if (dspace == NULL) {
      printf("Memory allocation for dspace failed\n");
      exit(254);
   }

              /* Describe work space and allow room for one model */
   ekkdsca(&rtcod,dspace,MAXSPC,1);
   if (rtcod0) chkrt("ekkdsca",rtcod);

              /* Set to maximization problem */
   ekkrget(&rtcod,dspace,oslr,OSLRLN);
   if (rtcod0) chkrt("ekkrget",rtcod);
   RMAXMIN = -1.0;
   ekkrset(&rtcod,dspace,oslr,OSLRLN);
   if (rtcod0) chkrt("ekkrset",rtcod);

              /* Read model data from MPS file on FORTRAN unit 98 */
   ekkmps(&rtcod,dspace,98,2,0);
   if (rtcod0) chkrt("ekkmps",rtcod);

              /* Solve using simplex method */
   ekksslv(&rtcod,dspace,1,2);
   if (rtcod0) chkrt("ekksslv",rtcod);

              /* Clear all callback functions */
   ekkclcb();

              /* Register the callback function MYITRU2 */
   ekkrgcb(CBITR, MYITRU2);

              /* Set to minimization problem */
   ekkrget(&rtcod,dspace,oslr,OSLRLN);
   if (rtcod0) chkrt("ekkrget",rtcod);
   RMAXMIN = 1.0;
   ekkrset(&rtcod,dspace,oslr,OSLRLN);
   if (rtcod0) chkrt("ekkrset",rtcod);

              /* Solve using simplex method */
   ekksslv(&rtcod,dspace,1,2);
   if (rtcod0) chkrt("ekksslv",rtcod);

}

void  chkrt(rtname,rtcod)
char  *rtname;
long  rtcod;
{
   printf("\n****** %s return code of %d ******\n",rtname,rtcod);
   if (rtcod = 200) exit(16);
}

You can run this program also using "Sample Linear Programming Model Data 1".

Sample C Program EXNAME

/* ---------------------------------------------------------------------
                              EXNAME

   This program illustrates how EKKBASO can be used to write
   basis information for a problem that is initialized by EKKDSCB.

   The program builds a model by reading a small MPS file to
   initialize the index control variables for row and column names.
   This file does not contain any model information.  It is used
   to force allocation of storage for row and column names.

   The problem data for the model is initialized by calling EKKDSCB.
   Row and column names are initialized in the work area by using the
   index control variables to indicate the location of the first row
   name, first column name, etc.

   Basis information from the resulting model can be written
   with EKKBASO and read with EKKBASI.  A model must have
   names assigned to its rows and columns before EKKBASO may
   be called.
--------------------------------------------------------------------- */
#include <stdio.h
#include <stdarg.h
#include <ekkc.h

void     chkrt(const char *,long);

#define  MAXSPC   15000
#define  MAXNC    2
#define  MAXNR    3
#define  MAXNEL   6
#define  OSLILN   64
#define  OSLNLN   66
long     osli[OSLILN];
long     osln[OSLNLN];
#define  IMAXROWS   osli[8]
#define  IMAXCOLS   osli[9]
#define  INUMROWS   osli[26]
#define  INUMCOLS   osli[27]
#define  NROWLOWER  osln[0]
#define  NROWUPPER  osln[2]
#define  NCOLLOWER  osln[5]
#define  NCOLUPPER  osln[7]
#define  NOBJECTIVE osln[10]
#define  NROWNAMES  osln[11]
#define  NCOLNAMES  osln[12]

long     mrow[MAXNEL]  = {1,1,2,2,3,3};
long     mcol[MAXNEL]  = {1,2,1,2,1,2};
double   dels[MAXNEL]  = {1.0,-1.0,-1.0,1.0,-1.0,-1.0};
double   cost[MAXNC]   = {-2.0,-6.0};
double   dlorow[MAXNR] = {-1.0,-1.0,-2.0};
double   duprow[MAXNR] = {1.0e+31,1.0e+31,1.0e+31};
double   dlocol[MAXNC] = {0.0,0.0};
double   dupcol[MAXNC] = {1.0e+31,1.0e+31};

main() {
   double *dspace, *dspace_1, d_qout[2];
   long   rtcod,io_status,i,j,nc,nr,nel;
   char   *qout, *p1;
   nr = MAXNR; nc = MAXNC; nel = MAXNEL;

              /* Allocate work area */
   dspace = (double *) malloc(MAXSPC*sizeof(double));
   if (dspace == NULL) {
      printf("Memory allocation for dspace failed\n");
      exit(999);
   }
   dspace_1 = dspace - 1;
   qout = (char *) d_qout;


              /* Describe work space and allow room for one model */
   ekkdsca(&rtcod,dspace,MAXSPC,1);
   if (rtcod0) chkrt("ekkdsca",rtcod);
   ekkdscm(&rtcod,dspace,1,2);
   if (rtcod0) chkrt("ekkdscm",rtcod);

              /* Allow room for 50 spare rows and columns */
   ekkiget(&rtcod,dspace,osli,OSLILN);
   if (rtcod0) chkrt("ekkiget",rtcod);
   IMAXCOLS=-50;
   IMAXROWS=-50;
   ekkiset(&rtcod,dspace,osli,OSLILN);
   if (rtcod0) chkrt("ekkiset",rtcod);

         /* Read an MPS file on unit 98 with 1 row, 1 column, and 1 */
         /* element to establish storage for row and column names   */
   ekkmps(&rtcod,dspace,98,1,0);
   if (rtcod0) chkrt("ekkmps",rtcod);
   ekkiget(&rtcod,dspace,osli,OSLILN);
   if (rtcod0) chkrt("ekkiget",rtcod);
   INUMCOLS=2;
   INUMROWS=3;
   ekkiset(&rtcod,dspace,osli,OSLILN);
   if (rtcod0) chkrt("ekkiset",rtcod);

              /* Set up row and column names, bounds, and costs */
   ekknget(&rtcod,dspace,osln,OSLNLN);
   if (rtcod0) chkrt("ekknget",rtcod);
   qout[0] = 'R';
   for (i=1;i<nr+1;i++) {
      sprintf(&qout[1],"%7u",i);
      p1 = qout;
      for (j=0;j<8;j++) { if (*p1 == ' ')  *p1 = '0'; p1++; }
      dspace_1[NROWNAMES+i-1] = d_qout[0];
      dspace_1[NROWUPPER+i-1] = duprow[i-1];
      dspace_1[NROWLOWER+i-1] = dlorow[i-1];
   }
   qout[0] = 'C';
   for (i=1;i<nc+1;i++) {
      sprintf(&qout[1],"%7u",i);
      p1 = qout;
      for (j=0;j<8;j++) { if (*p1 ==' ')  *p1 = '0'; p1++; }
      dspace_1[NCOLNAMES+i-1]  = d_qout[0];
      dspace_1[NCOLUPPER+i-1]  = dupcol[i-1];
      dspace_1[NCOLLOWER+i-1]  = dlocol[i-1];
      dspace_1[NOBJECTIVE+i-1] = cost[i-1];
   }

              /* Write problem matrix data into dspace using ekkdscb */
   ekkdscb(&rtcod,dspace,1,1,mrow,mcol,dels,0,0,nc,nel);
   if (rtcod0) chkrt("ekkdscb",rtcod);

              /* Crash - create a starting basis */
   ekkcrsh(&rtcod,dspace,2);
   if (rtcod0) chkrt("ekkcrsh",rtcod);

              /* Write current basis to a file on unit 10 */
   ekkbaso(&rtcod,dspace,10,1);
   if (rtcod0) chkrt("ekkbaso",rtcod);

              /* Solve problem using primal simplex */
   ekksslv(&rtcod,dspace,1,1);
   if (rtcod0) chkrt("ekksslv",rtcod);

              /* Print solution */
   ekkprts(&rtcod,dspace);
   if (rtcod0) chkrt("ekkprts",rtcod);

   /* Rewind fortran unit 10; "fort.10" - the default file name for */
   /* fortran unit 10 is platform dependent */
   ekkfcls(10,"KEEP",&io_status);
   if (io_status0) printf("ekkfcls - io_status: %u\n",io_status);
   ekkfopn(10,"fort.10","OLD","SEQUENTIAL","FORMATTED","NULL",0,
           &io_status);
   if (io_status0) printf("ekkfopn - io_status: %u\n",io_status);

   /* Read in basis with ekkbasi and solve again using dual algorithm */
   ekkbasi(&rtcod,dspace,10);
   if (rtcod0) chkrt("ekkbasi",rtcod);

              /* Solve problem using dual simplex */
   ekksslv(&rtcod,dspace,2,1);
   if (rtcod0) chkrt("ekksslv",rtcod);

              /* Print solution */
   ekkprts(&rtcod,dspace);
   if (rtcod0) chkrt("ekkprts",rtcod);

              /* Close fortran unit 10 */
   ekkfcls(10,"KEEP",&io_status);
   if (io_status0) printf("ekkfcls - io_status: %u\n",io_status);

}

void  chkrt(rtname,rtcod)
const char  *rtname;
long  rtcod;
{
   printf("\n****** %s return code of %d ******\n",rtname,rtcod);
   if (rtcod = 200) exit(16);
}

You can run this program using "Sample Linear Programming Model Data 2".

Sample C Program EXPRSL

/* ---------------------------------------------------------------------
                               EXPRSL

   This program solves the following problem:

   maximize   x1 + 2x5 - x8
   subject to:

   2.5 <=   3x1 +  x2          - 2x4 - x5              -    x8
                  2x2 + 1.1x3                                  <=  2.1
                           x3             + x6                  =  4.0
   1.8 <=                      2.8x4            -1.2x7         <=  5.0
   3.0 <= 5.6x1                      + x5              + 1.9x8 <= 15.0

   and subject to:

   2.5 <= x1
     0 <= x2 <= 4.1
     0 <= x3
     0 <= x4
   0.5 <= x5 <= 4.0
     0 <= x6
     0 <= x7
     0 <= x8 <= 4.3
--------------------------------------------------------------------- */
#include <stdio.h
#include <stdarg.h
#include <ekkc.h

void    chkrt(const char *,long);

#define MAXSPC   15000
#define NCOL     8      /* no. of columns in the constraint matrix */
#define NROW     5      /* no. of rows in the constraint matrix */
#define NEL      14     /* no. of elements in the constraint matrix */
#define ITYPE    2      /* storage format: by columns */
#define IEL      14     /* length of arrays containing element info. */
#define IRL      5      /* length of arrays containing row info. */
#define ICL      8      /* length of arrays containing column info. */
#define ICL1     9
#define OSLILN   64
#define OSLRLN   45
long    osli[OSLILN];
double  oslr[OSLRLN];
#define IPRINTUNIT   osli[1]
#define ISOLMASK     osli[32]
#define RMAXMIN      oslr[2]
#define RSUMPINF     oslr[18]

                               /* Row indices */
long    mrow[IEL] = {1,5,1,2,2,3,1,4,1,5,3,4,1,5};

                               /* Column starts */
long    mcol[ICL1]= {1,3,5,7,9,11,12,13,15};

                               /* Matrix elements */
double  dels[IEL] = {3.0,5.6,1.0,2.0,1.1,1.0,-2.0,2.8,-1.0,
                     1.0,1.0,-1.2,-1.0,1.9};

                               /* Lower bounds on row activities */
double  drlo[IRL] = {2.5,-1.0e+31,4.0,1.8,3.0};

                               /* Upper bounds on row activities */
double  drup[IRL] = {1.0e+31,2.1,4.0,5.0,1.5e+1};

                               /* Lower bounds on columns */
double  dclo[ICL] = {2.5,0.0,0.0,0.0,0.5,0.0,0.0,0.0};

                               /* Upper bounds on columns */
double  dcup[ICL] = {1.0e+31,4.1,1.0e+31,1.0e+31,4.0,1.0e+31,
                     1.0e+31,4.3};

                               /* Objective function coefficients */
double  dobj[ICL] = {1.0,0.0,0.0,0.0,2.0,0.0,0.0,-1.0};


main() {
   double sinf,sinf1,*dspace;
   long   save_unit,rtcod,io_status,i,j;

              /* Allocate work area */
   dspace = (double *) malloc(MAXSPC*sizeof(double));
   if (dspace == NULL) {
      printf("Memory allocation for dspace failed\n");
      exit(999);
   }


              /* Describe work space and allow room for one model */
   ekkdsca(&rtcod,dspace,MAXSPC,1);
   if (rtcod0) chkrt("ekkdsca",rtcod);

              /* Set to maximization problem */
   ekkrget(&rtcod,dspace,oslr,OSLRLN);
   if (rtcod0) chkrt("ekkrget",rtcod);
   RMAXMIN = -1.0;
   ekkrset(&rtcod,dspace,oslr,OSLRLN);
   if (rtcod0) chkrt("ekkrset",rtcod);

              /* Pass model with matrix stored by column */
   ekklmdl(&rtcod,dspace,ITYPE,NROW,NCOL,NEL,dobj,drlo,drup,
           dclo,dcup,mrow,mcol,dels);
   if (rtcod0) chkrt("ekklmdl",rtcod);

              /* Turn off printing of message numbers */
   ekkmset(&rtcod,dspace,1,0,0,0,0,9999,1);
   if (rtcod0) chkrt("ekkmset",rtcod);

              /* Print ekkstat output to different unit */
   ekkiget(&rtcod,dspace,osli,OSLILN);
   if (rtcod0) chkrt("ekkiget",rtcod);
   save_unit = IPRINTUNIT;
   IPRINTUNIT = 12;
   ekkiset(&rtcod,dspace,osli,OSLILN);
   if (rtcod0) chkrt("ekkiset",rtcod);
   ekkstat(&rtcod,dspace);
   if (rtcod0) chkrt("ekkstat",rtcod);

              /* Set print unit back to its previous value */
   ekkiget(&rtcod,dspace,osli,OSLILN);
   if (rtcod0) chkrt("ekkiget",rtcod);
   IPRINTUNIT = save_unit;
   ekkiset(&rtcod,dspace,osli,OSLILN);
   if (rtcod0) chkrt("ekkiset",rtcod);

              /* Turn on printing of message numbers */
   ekkmset(&rtcod,dspace,1,0,0,0,0,9999,2);
   if (rtcod0) chkrt("ekkmset",rtcod);

              /* Scale problem */
   ekkscal(&rtcod,dspace);
   if (rtcod0) chkrt("ekkscal",rtcod);

              /* Presolve problem */
   ekkprsl(&rtcod,dspace,15,3);
   if (rtcod0) chkrt("ekkprsl",rtcod);

              /* Decide if crash will help or not. (A simple */
              /* strategy based on sum of primal infeasibilites) */
              /* Note: This could also be done using type=3 in ekkcrsh*/

              /* Get solution and sum of infeasibilities before crash */
   ekkinvt(&rtcod,dspace,1,1);
   if (rtcod0) chkrt("ekkinvt",rtcod);
   ekkrget(&rtcod,dspace,oslr,OSLRLN);
   if (rtcod0) chkrt("ekkrget",rtcod);
   sinf=RSUMPINF;
   printf("\nSum of primal infeasibilities before ekkcrsh: %e \n",sinf);

              /* Crash */
   ekkcrsh(&rtcod,dspace,1);
   if (rtcod0) chkrt("ekkcrsh",rtcod);

              /* Get solution and sum of infeasibilities after crash */
   ekkinvt(&rtcod,dspace,1,1);
   if (rtcod0) chkrt("ekkinvt",rtcod);
   ekkrget(&rtcod,dspace,oslr,OSLRLN);
   if (rtcod0) chkrt("ekkrget",rtcod);
   sinf1=RSUMPINF;
   printf("\nSum of primal infeasibilities after ekkcrsh: %e \n",sinf1);

       /* If the sum of infeasibilities was better before crash, get */
       /* a null basis. Otherwise, use the basis resulting from crash */

   if (sinf<sinf1) {
      ekknlbs(&rtcod,dspace);
      if (rtcod0) chkrt("ekknlbs",rtcod);
   }

              /* Create a vector copy of the matrix */
   ekknwmt(&rtcod,dspace,3);
   if (rtcod0) chkrt("ekknwmt",rtcod);

              /* Solve problem using primal simplex */
   ekksslv(&rtcod,dspace,1,2);
   if (rtcod0) chkrt("ekksslv",rtcod);

              /* Post-solve problem */
   ekkpssl(&rtcod,dspace,15);
   if (rtcod0) chkrt("ekkpssl",rtcod);

              /* Solve again to ensure dual feasibility */
   ekksslv(&rtcod,dspace,1,3);
   if (rtcod0) chkrt("ekksslv",rtcod);

              /* Set to print only columns with nonzero activities */
   ekkiget(&rtcod,dspace,osli,OSLILN);
   if (rtcod0) chkrt("ekkiget",rtcod);
   ISOLMASK = 6;
   ekkiset(&rtcod,dspace,osli,OSLILN);
   if (rtcod0) chkrt("ekkiset",rtcod);

              /* Print the solution */
   ekkprts(&rtcod,dspace);
   if (rtcod0) chkrt("ekkprts",rtcod);

              /* Close fortran unit 12 */
   ekkfcls(12,"KEEP",&io_status);
   if (io_status0) printf("ekkfcls - io_status: %u\n",io_status);

}

void  chkrt(rtname,rtcod)
const char  *rtname;
long  rtcod;
{
   printf("\n****** %s return code of %d ******\n",rtname,rtcod);
   if (rtcod = 200) exit(16);
}

No input data is required to run this program.

Sample C Program EXROW

/* ---------------------------------------------------------------------
                              EXROW

   This program solves the following problem:

   Maximize  4*x4 + 0.1*x5 + 6*x10 + 0.15*x11 + 8*x16 + 0.15*x17
                  + 6*x22 + 0.15*x23 + 3*x26 + 0.1*x27
                  + 3*x29 + 0.1*x30

   Subject to Dx = b; x = 0
   where trans(b) = (0,0,0,0,0,0,0,0,0,0,100,50)
   and the matrix D has the form:

   ---------------
   |      |  A   |
   |  B   |      |
   |      |------+-------
   |      |      |  A   |
   -------|  B   |      |
          |      |------+-------
          |      |      |  A   |
          -------|  B   |      |
                 |      |------+---------
                 |      |      |        |
                 -------|  B   |    C   |
                        |      |        |
                        |      |        |
                        -----------------
   --------
   |  A   |
   |      |
   --------

   Here A is a 2 X 6 matrix:

            __                     __
            | 1   1   1   1   0   0 |
        A = |                       |
            | 3   0   0   0   1   1 |
            --                     --

   B is a 4 X 6 matrix:

            __                     __
            | 0   0  -1   0   0   0 |
            |                       |
            | 0   0   0   0   0  -1 |
        B = |                       |
            |-4  -1   0   0   0   0 |
            |                       |
            | 0 -10   0   0   0   0 |
            --                     --

   C is a 4 X 6 matrix:

            __                     __
            | 1   1   0   0   0   0 |
            |                       |
            | 0   0   1   1   0   0 |
        C = |                       |
            |-1   0   0   0   1   0 |
            |                       |
            | 0   0   0  -1   0   1 |
            --                     --

   To illustrate the use of EKKROW and EKKCOL, this program
   first builds a matrix (D') which is D, but missing the last
   occurrence of A and the occurrence of C.  The last A block is
   added using EKKROW twice (once for each row) and C is added
   using EKKCOL 6 times (once for each column).
--------------------------------------------------------------------- */
#include <stdio.h
#include <stdarg.h
#include <ekkc.h

void    chkrt(const char *,long);

#define MAXSPC   15000
#define NROW     12     /* total no. of rows in the composite matrix */
#define NCOL     30     /* total no. of cols in the composite matrix */
#define NA       7      /* number of elements in A */
#define NACOL    6      /* number of columns in A  */
#define NB       5      /* number of elements in B */
#define NBCOL    6      /* number of columns in B  */
#define IATYPE   1      /* storage format: by indices */
#define IBTYPE   2      /* storage format: by columns */
#define OSLILN   64
#define OSLNLN   66
#define OSLRLN   45
long    osli[OSLILN];
long    osln[OSLNLN];
double  oslr[OSLRLN];
#define NROWLOWER    osln[0]
#define NROWUPPER    osln[2]
#define NCOLLOWER    osln[5]
#define NCOLUPPER    osln[7]
#define NOBJECTIVE   osln[10]
#define ISOLMASK     osli[32]
#define RMAXMIN      oslr[2]

long    mrow[1] = {0}, mcol[1] = {0};
double  dels[1] = {0.0};
                               /* Matrix elements - block A */
double  a[10]  = {1.0,3.0,1.0,1.0,1.0,1.0,1.0,0.0,0.0,0.0};

                               /* Matrix elements - block B */
double  b[10]  = {-4.0,-1.0,-10.0,-1.0,-1.0,0.0,0.0,0.0,0.0,0.0};

                               /* Row indices - block A */
long    ia[10] = {1,2,1,1,1,2,2,0,0,0};

                               /* Row indices - block B */
long    ib[10] = {3,3,4,1,2,0,0,0,0,0};

                               /* Column indices - block A */
long    ja[10] = {1,1,2,3,4,5,6,0,0,0};

                               /* Column starts - block B */
long    jb[10] = {1,2,4,5,5,5,6,0,0,0};

                               /* Rows to add */
double  ar1[4] = {1.0,1.0,1.0,1.0}, ar2[3] = {3.0,1.0,1.0};

                               /* Indices of rows to add */
long    iar1[4] = {1,2,3,4}, iar2[3] = {1,5,6};

                               /* Columns to add */
double  cc1[2] = {1.0,-1.0}, cc2[1] = {1.0},
        cc3[1] = {1.0}, cc4[2] = {1.0,-1.0},
        cc5[1] = {1.0}, cc6[1] = {1.0};

                               /* Indices of columns to add */
long    icc1[2] = {7,9}, icc2[1] = {7},
        icc3[1] = {8}, icc4[2] = {8,10},
        icc5[1] = {9}, icc6[1] = {10};

                               /* Lower bounds on row activities */
double  drlo[12]= {0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0};

                               /* Upper bounds on row activities */
double  drup[12]= {0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0};

                               /* Lower bounds on columns */
double  dclo[30]= {0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,
                   0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,
                   0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0};

                               /* Upper bounds on columns */
double  dcup[30]= {1.0e+31,1.0e+31,1.0e+31,1.0e+31,1.0e+31,
                   1.0e+31,1.0e+31,1.0e+31,1.0e+31,1.0e+31,
                   1.0e+31,1.0e+31,1.0e+31,1.0e+31,1.0e+31,
                   1.0e+31,1.0e+31,1.0e+31,1.0e+31,1.0e+31,
                   1.0e+31,1.0e+31,1.0e+31,1.0e+31,
                   0.0,0.0,0.0,0.0,0.0,0.0};

                     /* Obj. func. coeff. . Leave off those belonging */
                     /* to block "C". They will be added later */

double  dobj[30]= {0.0,0.0,0.0,4.0,0.1,0.0,0.0,0.0,0.0,6.0,
                   0.15,0.0,0.0,0.0,0.0,8.0,0.15,0.0,0.0,0.0,
                   0.0,6.0,0.15,0.0,0.0,0.0,0.0,0.0,0.0,0.0};

main() {
   double *dspace, *dspace_1;
   long   rtcod, numelem, i;

              /* Allocate work area */
   dspace = (double *) malloc(MAXSPC*sizeof(double));
   if (dspace == NULL) {
      printf("Memory allocation for dspace failed\n");
      exit(999);
   }
   dspace_1 = dspace - 1;


              /* Describe work space and allow room for one matrix */
   ekkdsca(&rtcod,dspace,MAXSPC,1);
   if (rtcod0) chkrt("ekkdsca",rtcod);

              /* Describe model as having 7 blocks */
   ekkdscm(&rtcod,dspace,1,7);
   if (rtcod0) chkrt("ekkdscm",rtcod);

              /* Set to maximization problem */
   ekkrget(&rtcod,dspace,oslr,OSLRLN);
   if (rtcod0) chkrt("ekkrget",rtcod);
   RMAXMIN = -1.0;
   ekkrset(&rtcod,dspace,oslr,OSLRLN);
   if (rtcod0) chkrt("ekkrset",rtcod);

              /* Set up the model */
   ekklmdl(&rtcod,dspace,1,NROW,NCOL,0,dobj,drlo,drup,dclo,dcup,
           mrow,mcol,dels);
   if (rtcod0) chkrt("ekklmdl",rtcod);

              /* Describe "A" block */
   ekkdscb(&rtcod,dspace,IATYPE,1,ia,ja,a,0,6,NACOL,NA);
   if (rtcod0) chkrt("ekkdscb",rtcod);

              /* Describe "B" block */
   ekkdscb(&rtcod,dspace,IBTYPE,2,ib,jb,b,0,0,NBCOL,NB);
   if (rtcod0) chkrt("ekkdscb",rtcod);

              /* Repeat "A" block */
   ekkdscb(&rtcod,dspace,IATYPE,3,ia,ja,a,2,12,NACOL,NA);
   if (rtcod0) chkrt("ekkdscb",rtcod);
   ekkdscb(&rtcod,dspace,IATYPE,4,ia,ja,a,4,18,NACOL,NA);
   if (rtcod0) chkrt("ekkdscb",rtcod);

              /* Repeat "B" block */
   ekkdscb(&rtcod,dspace,IBTYPE,5,ib,jb,b,2,6,NBCOL,NB);
   if (rtcod0) chkrt("ekkdscb",rtcod);
   ekkdscb(&rtcod,dspace,IBTYPE,6,ib,jb,b,4,12,NBCOL,NB);
   if (rtcod0) chkrt("ekkdscb",rtcod);
   ekkdscb(&rtcod,dspace,IBTYPE,7,ib,jb,b,6,18,NBCOL,NB);
   if (rtcod0) chkrt("ekkdscb",rtcod);

              /* We have finished building D'; now add the */
              /* last A block and the C block */
   numelem = 4;
   ekkrow(&rtcod,dspace,1,11,&numelem,ar1,iar1);
   if (rtcod0) chkrt("ekkrow",rtcod);
   numelem = 3;
   ekkrow(&rtcod,dspace,1,12,&numelem,ar2,iar2);
   if (rtcod0) chkrt("ekkrow",rtcod);

              /* Add the bounds on newly added rows */
   ekknget(&rtcod,dspace,osln,OSLNLN);
   if (rtcod0) chkrt("ekknget",rtcod);
   dspace_1[NROWLOWER+10] = 1.0e+2;         /* lower bounds */
   dspace_1[NROWLOWER+11] = 0.5e+2;
   dspace_1[NROWUPPER+10] = 1.0e+2;         /* upper bounds */
   dspace_1[NROWUPPER+11] = 0.5e+2;

              /* Add the necessary columns to add the C block */
   numelem = 2;
   ekkcol(&rtcod,dspace,1,25,&numelem,cc1,icc1);
   if (rtcod0) chkrt("ekkcol1",rtcod);
   numelem = 1;
   ekkcol(&rtcod,dspace,1,26,&numelem,cc2,icc2);
   if (rtcod0) chkrt("ekkcol2",rtcod);
   ekkcol(&rtcod,dspace,1,27,&numelem,cc3,icc3);
   if (rtcod0) chkrt("ekkcol3",rtcod);
   numelem = 2;
   ekkcol(&rtcod,dspace,1,28,&numelem,cc4,icc4);
   if (rtcod0) chkrt("ekkcol4",rtcod);
   numelem = 1;
   ekkcol(&rtcod,dspace,1,29,&numelem,cc5,icc5);
   if (rtcod0) chkrt("ekkcol5",rtcod);
   ekkcol(&rtcod,dspace,1,30,&numelem,cc6,icc6);
   if (rtcod0) chkrt("ekkcol6",rtcod);

              /* Add the bounds on the newly created columns */
   ekknget(&rtcod,dspace,osln,OSLNLN);
   if (rtcod0) chkrt("ekknget",rtcod);

   for (i=24;i<30;i++) {
      dspace_1[NCOLLOWER+i] = 0.0;          /* lower bounds */
      dspace_1[NCOLUPPER+i] = 1.0e+31;      /* upper bounds */
   }
              /* Add the objective function for newly added columns */
   dspace_1[NOBJECTIVE+24] = 0.0;
   dspace_1[NOBJECTIVE+25] = 3.0;
   dspace_1[NOBJECTIVE+26] = 0.1;
   dspace_1[NOBJECTIVE+27] = 0.0;
   dspace_1[NOBJECTIVE+28] = 3.0;
   dspace_1[NOBJECTIVE+29] = 0.1;

              /* Create a new copy of the matrix */
   ekknwmt(&rtcod,dspace,3);
   if (rtcod0) chkrt("ekknwmt",rtcod);

              /* Solve LP using simplex */
   ekksslv(&rtcod,dspace,1,2);
   if (rtcod0) chkrt("ekksslv",rtcod);

              /* Set to print only columns with nonzero activities */
   ekkiget(&rtcod,dspace,osli,OSLILN);
   if (rtcod0) chkrt("ekkiget",rtcod);
   ISOLMASK = 6;
   ekkiset(&rtcod,dspace,osli,OSLILN);
   if (rtcod0) chkrt("ekkiset",rtcod);

              /* Print the solution */
   ekkprts(&rtcod,dspace);
   if (rtcod0) chkrt("ekkprts",rtcod);

}

void  chkrt(rtname,rtcod)
const char  *rtname;
long  rtcod;
{
   printf("\n****** %s return code of %d ******\n",rtname,rtcod);
   if (rtcod = 200) exit(16);
}

No input data is required to run this program.

Sample C Program EXSELNAM

/* ---------------------------------------------------------------------
                              EXSELNAM

   This program solves the following problem:

   maximize   x1 + 2x5 - x8
   subject to:

   2.5 <=   3x1 +  x2          - 2x4 - x5              -    x8
                  2x2 + 1.1x3                                  <=  2.1
                           x3             + x6                  =  4.0
   1.8 <=                      2.8x4            -1.2x7         <=  5.0
   3.0 <= 5.6x1                      + x5              + 1.9x8 <= 15.0

   and subject to:

   2.5 <= x1
     0 <= x2 <= 4.1
     0 <= x3
     0 <= x4
   0.5 <= x5 <= 4.0
     0 <= x6
     0 <= x7
     0 <= x8 <= 4.3

   The routine EKKCSET is used to set the problem name, the right hand
   side name and the range name. The routine EKKNAME is used to add
   row and column names. The routine EKKSEL is used restrict the ekkprts
   and ekkbcdo operations to rows and columns whose names match a
   specified character string.

   A secondary objective of this program is to illustrate how character
   string arguments can be passed between a C program and the routines
   EKKCSET, EKKCGET, EKKSEL and EKKNAME.
--------------------------------------------------------------------- */
#include <stdio.h
#include <stdarg.h
#include <string.h
#include <ekkc.h

void    chkrt(const char *,long);

#define MAXSPC   25000
#define NCOL     8      /* no. of columns in the constraint matrix */
#define NROW     5      /* no. of rows in the constraint matrix */
#define NEL      14     /* no. of elements in the constraint matrix */
#define ITYPE    2      /* storage format: by columns */
#define IEL      14     /* length of arrays containing element info. */
#define IRL      5      /* length of arrays containing row info. */
#define ICL      8      /* length of arrays containing column info. */
#define ICL1     9
#define NUMCHAR  7
#define COLNAMLN NUMCHAR
#define ROWNAMLN NUMCHAR
#define OSLILN   64
#define OSLRLN   45
#define OSLCLN   17
long    osli[OSLILN];
double  oslr[OSLRLN];
char    oslc[OSLCLN*80];
#define RMAXMIN  oslr[2]
#define INUMCHAR osli[10]
#define CNAME    oslc[0*80]
#define CRHS     oslc[2*80]
#define CRANGE   oslc[3*80]

char    probnam1[]="TPROB01";
char    rhs1[]="TRHS1";
char    range1[]="TRANGE1";
char    colnames[NCOL][COLNAMLN+1]=
                {"TCOL001","TCOL002","TCOL003",
                 "TCOL004","TCOL005","TCOL006","TCOL007","TCOL008"};
char    rownames[NROW][ROWNAMLN+1]=
                {"TROW01","TROW02","TROW03","TROW04","TROW05"};

                               /* Row indices */
long    mrow[IEL] = {1,5,1,2,2,3,1,4,1,5,3,4,1,5};

                               /* Column starts */
long    mcol[ICL1]= {1,3,5,7,9,11,12,13,15};

                               /* Matrix elements */
double  dels[IEL] = {3.0,5.6,1.0,2.0,1.1,1.0,-2.0,2.8,-1.0,
                     1.0,1.0,-1.2,-1.0,1.9};

                               /* Lower bounds on row activities */
double  drlo[IRL] = {2.5,-1.0e+31,4.0,1.8,3.0};

                               /* Upper bounds on row activities */
double  drup[IRL] = {1.0e+31,2.1,4.0,5.0,1.5e+1};

                               /* Lower bounds on columns */
double  dclo[ICL] = {2.5,0.0,0.0,0.0,0.5,0.0,0.0,0.0};

                               /* Upper bounds on columns */
double  dcup[ICL] = {1.0e+31,4.1,1.0e+31,1.0e+31,4.0,1.0e+31,
                     1.0e+31,4.3};

                               /* Objective function coefficients */
double  dobj[ICL] = {1.0,0.0,0.0,0.0,2.0,0.0,0.0,-1.0};


main() {
   double *dspace;
   long   rtcod,io_status,i,j,slen;
   static char  selname1[]="?C*";
   char   *p1,*p2,*col_names,*row_names;

              /* Allocate work area */
   dspace = (double *) malloc(MAXSPC*sizeof(double));
   if (dspace == NULL) {
      printf("Memory allocation for dspace failed\n");
      exit(999);
   }
   col_names = (char *) malloc(NCOL*COLNAMLN*sizeof(char));
   if (col_names == NULL) {
      printf("Memory allocation for col_names failed\n");
      exit(999);
   }
   row_names = (char *) malloc(NROW*ROWNAMLN*sizeof(char));
   if (row_names == NULL) {
      printf("Memory allocation for row_names failed\n");
      exit(999);
   }


              /* Describe work space and allow room for one model */
   ekkdsca(&rtcod,dspace,MAXSPC,1);
   if (rtcod0) chkrt("ekkdsca",rtcod);

              /* Set to maximization problem */
   ekkrget(&rtcod,dspace,oslr,OSLRLN);
   if (rtcod0) chkrt("ekkrget",rtcod);
   RMAXMIN = -1.0;
   ekkrset(&rtcod,dspace,oslr,OSLRLN);
   if (rtcod0) chkrt("ekkrset",rtcod);

              /* Set length of names to be 7 characters maximum */
   ekkiget(&rtcod,dspace,osli,OSLILN);
   if (rtcod0) chkrt("ekkiget",rtcod);
   INUMCHAR = NUMCHAR;
   ekkiset(&rtcod,dspace,osli,OSLILN);
   if (rtcod0) chkrt("ekkiset",rtcod);

              /* Pass model with matrix stored by column */
   ekklmdl(&rtcod,dspace,ITYPE,NROW,NCOL,NEL,dobj,drlo,drup,
           dclo,dcup,mrow,mcol,dels);
   if (rtcod0) chkrt("ekklmdl",rtcod);

              /* Set names of model, RHS, and range */
   ekkcget(&rtcod,dspace,oslc,OSLCLN);
   if (rtcod0) chkrt("ekkcget",rtcod);
   p1 = &CNAME; p2 = probnam1; slen = strlen(probnam1);
   for (i=0;i<80;i++) {
      if (i<slen) *p1++ = *p2++;
      else *p1++ = ' ';
   }
   p1 = &CRHS; p2 = rhs1; slen = strlen(rhs1);
   for (i=0;i<80;i++) {
      if (i<slen) *p1++ = *p2++;
      else *p1++ = ' ';
   }
   p1 = &CRANGE; p2 = range1; slen = strlen(range1);
   for (i=0;i<80;i++) {
      if (i<slen) *p1++ = *p2++;
      else *p1++ = ' ';
   }
   ekkcset(&rtcod,dspace,oslc,OSLCLN);
   if (rtcod0) chkrt("ekkcset",rtcod);

              /* Convert row and column names to required format */
   for (i=0;i< NCOL;i++) {
      p1 = &col_names[i*COLNAMLN];
      p2 = colnames[i];
      for (j=0;j<COLNAMLN;j++) {
         if (j < strlen(colnames[i])) *p1++ = *p2++;
         else *p1++ = ' ';
      }
   }
   for (i=0;i< NROW;i++) {
      p1 = &row_names[i*ROWNAMLN];
      p2 = rownames[i];
      for (j=0;j<ROWNAMLN;j++) {
         if (j < strlen(rownames[i])) *p1++ = *p2++;
         else *p1++ = ' ';
      }
   }
              /* Add row and column names */
   ekkname(&rtcod,dspace,NROW,row_names,1,NCOL,col_names,1,1);
   if (rtcod0) chkrt("ekkname",rtcod);

              /* Write current model to FORTRAN unit 32 - MPS format */
   ekkbcdo(&rtcod,dspace,32,1,2);
   if (rtcod0) chkrt("ekkbcdo",rtcod);

              /* Solve problem using primal simplex */
   ekksslv(&rtcod,dspace,1,2);
   if (rtcod0) chkrt("ekksslv",rtcod);

              /* Print solution */
   ekkprts(&rtcod,dspace);
   if (rtcod0) chkrt("ekkprts",rtcod);

              /* Select rows/columns with names matching "?C*" */
   ekksel(&rtcod,dspace,selname1,strlen(selname1),'*','?',1,1);
   if (rtcod0) chkrt("ekksel",rtcod);

              /* Print "matching" part of solution */
   ekkprts(&rtcod,dspace);
   if (rtcod0) chkrt("ekkprts",rtcod);

              /* Write "matching" part of model to FORTRAN unit 33 */
   ekkbcdo(&rtcod,dspace,33,1,2);
   if (rtcod0) chkrt("ekkbcdo",rtcod);

              /* Close fortran units 32 and 33 */
   ekkfcls(32,"KEEP",&io_status);
   if (io_status0) printf("ekkfcls - io_status: %u\n",io_status);
   ekkfcls(33,"KEEP",&io_status);
   if (io_status0) printf("ekkfcls - io_status: %u\n",io_status);

}

void  chkrt(rtname,rtcod)
const char  *rtname;
long  rtcod;
{
   printf("\n****** %s return code of %d ******\n",rtname,rtcod);
   if (rtcod = 200) exit(16);
}

No input data is required to run this program.

Sample C Program EXIMDL6

/* ---------------------------------------------------------------------------

                        EXIMDL6

     This driver solves a separable minimization problem in two
  variables x and y. The linear problem constraints are given by
  0<=x<=10, 0<=y<=10 and x+y<=4.5. The objective function,
  Fx(x)+Fy(y) is modelled by a piecewise linear function Px(x)+Py(y).
  A Special Ordered Set of type 2 is used to express points on the
  curve Px() as convex combinations of adjacent knots in the
  curve. The set is referred to below as SOSx. Similarly the type 2
  Special Ordered Set SOSy is used to model Py(). The knots (x,Px(x))
  are given by (0,2), (7/10,1), (1,5), (4,-1), (5,-3), (10,4), and
  the knots for Py() are given by (0,2), (1,4), (4,-1) and (10,-2).
  The value of x is given by the dot product SOSx()*xabs() where
  xabs() contains the abscissae of the knots of Px(). A convexity
  row for SOSx ensures that the sum of the non-zero components of
  SOSx sum to one. Similarly, y=SOSy()*yabs(), where the non-zero
  components of SOSy() sum to one. The linearized objective function
  Px(x)+Py(y) is created by loading the ordinates of the knots into
  cost vector.  Feasible values for SOSx() and SOSy()
  then yield objective values of SOSx()*xord()+SOSy()*yord().
  The variables x and y themselves have objective function
  coefficients of 0.

     To demonstrate the use of "overlapping" Special Ordered Sets
  (i.e. SOS's that share one or more variables), the non-convex
  constraint that x may not be strictly between 4 and 5 is added.
  This is done by creating SOSo, a Special Ordered Set of type 1.
  The two members of the set are members 4 and 5 (corresponding to
  knots 4 and 5) of SOSx.


  MIP formulation:
  min 2x1 +  x2 + 5x3 -  x4 - 3x5 + 4x6 +   2y1 + 4y2 -  y3 - 2y4
  s.t. x1 +  x2 +  x3 +  x4 +  x5 +  x6                                = 1
       (7/10)x2 +  x3 + 4x4 + 5x5 +10x6 - x                            = 0
                                             y1 +  y2 +  y3 +  y4      = 1
                                                   y2 + 4y3 +10y4 - y  = 0
                                                                x + y <= 4.5
  0<=x<=10, 0<=y<=10, xi = 0 for all i
  x1,x2,x3,x4,x5,x6 are members of an SOS of type 2 (SOSx)
  y1,y2,y3,y4       are members of an SOS of type 2 (SOSy)
  x4,x5             are members of an SOS of type 1 (SOSo)

  The variables x1 up to x6 contain the members of SOSx, and the
  variables y1 up to y4 contain the members of SOSy.
  Columns 1...6 contain x1...x6, col 7 contains x, cols 8...11
  contain y1...y4 and col 12 contains y.  During the solution process,
  no more than two members of a given SOS2 will be non-zero, and if
  two are nonzero, then they must be adjacent. The user must supply
  convexity rows that are required by the formulation. Rows 1 and 3
  are the convexity rows for this problem.
--------------------------------------------------------------------------- */
#include <stdio.h
#include <stdarg.h
#include <ekkc.h

void    chkrt(const char *,long);

#define MAXSPC   500000
#define OSLNLN   69
#define OSLILN   61
#define OSLRLN   45
long    osln[OSLNLN];
long    osli[OSLILN];
double  oslr[OSLRLN];
#define IPRINTUNIT   osli[1]
#define IMAXINTS     osli[49]
#define ISOLMASK     osli[32]
#define RMAXMIN      oslr[2]
#define RSUMPINF     oslr[18]
#define NCOLNAMES    osln[12]

/* Num. of rows, columns, elements and type of EKKLMDL input format. */
  long NROW=5; long NCOL=12; long NELS; long ITYPE=1;

/* Storage for Row and Column indices */
  long IA[50],JA[50];

/* Upper and lower bounds of rows and columns, and elems and cost */
  double DRLO[50],DRUP[50],DCLO[50],DCUP[50&r

/* Number of integer variables (and/or SOS members) and the cor- */
/* responding column numbers */
  long NINTS=10; long INTNUMS[10] = {1,2,3,4,5,6,8,9,10,11};

/* Number of sets of integer variables, types and priorities. */
  long     NSETS=3;
  long      TYPE[3] = {2,   2,   1};
  long  PRIORITY[3] = {1000,1000,1000};

/* Total size of sets and integer variables. */
  long NTOTINFO=12;

/*  Indices of sets and numbers of the variables in the sets.
C   SETINDEX(i) gives the beginning index for the segment of the SETS()
C   array that contains Special Ordered Set i. So the members of the
C   first SOS are listed in entries 1 through (7-1) of SETS(). Note that
C   columns 4 and 5 are listed twice in SETS(). This is because these
C   columns belong to the first and the third Special Ordered Set. The
C   last entry in SETINDEX() is NTOTINFO+1, the upper bound for the last
C   SOS in SETS(). */
  long SETINDEX[4] = {1,7,11,13};
  long SETS[12]    = {1,2,3,4,5,6,8,9,10,11,4,5};

/* Pseudo costs. (Up pseudocost used for ref row entries) */
  double DNPCOST[50],UPPCOST[50];

/* Load abscissae and ordinates for the piecewise linear objectives */
  double XABS[50] = { 0.0, 0.7, 1.0,  4.0,  5.0, 10.0 };
  double XORD[50] = { 2.0, 1.0, 5.0, -1.0, -3.0,  4.0 };
  double YABS[50] = { 0.0, 1.0, 4.0, 10.0 };
  double YORD[50] = { 2.0, 4.0,-1.0, -2.0 };

main() {
   double *dspace;
   long   rtcod,i,j,member;
   char   *p;

              /* Allocate work area */
   dspace = (double *) malloc(MAXSPC*sizeof(double));
   if (dspace == NULL) {
      printf("Memory allocation for dspace failed\n");
      exit(999);
   }

/* Load information for SOSx */
      NELS = -1;
      for (member=0; member<6; member++) {
/* Load convexity row for SOSx so that SOSx yields a convex
   combination of two adjacent grid points. */
                    NELS  = NELS + 1;
                 JA[NELS] = member + 1;
                 IA[NELS] = 1;
               DELS[NELS] = 1.0;
/* Load the "value row" for x to impose the constraint x=SOSx()*xabs()
   Also add reference row entries in up pseudocost array. */
                    NELS  = NELS + 1;
                 JA[NELS] = member + 1;
                 IA[NELS] = 2;
               DELS[NELS] = XABS[member];
          UPPCOST[member] = XABS[member];
             DOBJ[member] = XORD[member];
             DCLO[member] = 0.0;
             DCUP[member] = 1.0e+31;
      }
/* Set row bounds for convexity row so that 1 <= conv(SOSx) <= 1 */
      DRLO[0] = 1.0;
      DRUP[0] = 1.0;
/* Set row bounds for value row so that 0 <= SOSx()*xabs() - x <= 0 */
      DRLO[1] = 0.0;
      DRUP[1] = 0.0;

/* Add column for x */
      NELS = NELS + 1;
      IA[NELS]   =  2;
      JA[NELS]   =  7;
      DELS[NELS] = -1.0;
      DOBJ[6]    =  0.0;
      DCLO[6]    =  0.0;
      DCUP[6]    = 10.0;

      for (member=0; member<4; member++) {
/* Load convexity row for SOSy so that SOSy yields a convex
   combination of two adjacent grid points. */
                    NELS  = NELS + 1;
                 JA[NELS] = member + 8;
                 IA[NELS] = 3;
               DELS[NELS] = 1.0;
/* Load the "value row" for y to impose the constraint y=SOSy()*yabs()
   Also add reference row entries in up pseudocost array. */
                    NELS  = NELS + 1;
                 JA[NELS] = member + 8;
                 IA[NELS] = 4;
               DELS[NELS] = YABS[member];
        UPPCOST[member+6] = YABS[member];
           DOBJ[member+7] = YORD[member];
           DCLO[member+7] = 0.0;
           DCUP[member+7] = 1.0e+31;
      }
/* Set row bounds for convexity row so that 1 <= conv(SOSy) <= 1 */
      DRLO[2] = 1.0;
      DRUP[2] = 1.0;
/* Set row bounds for value row so that 0 <= SOSy()*yabs() - y <= 0 */
      DRLO[3] = 0.0;
      DRUP[3] = 0.0;

/* Add column for  y */
      NELS = NELS + 1;
      IA[NELS]   =  4;
      JA[NELS]   = 12;
      DELS[NELS] = -1.0;
      DOBJ[11]   =  0.0;
      DCLO[11]   =  0.0;
      DCUP[11]   = 10.0;

/* Add constraint x+y<=4.5 */
      NELS       = NELS + 1;
      IA[NELS]   = 5;
      JA[NELS]   = 7;
      DELS[NELS] = 1.0;
      NELS       = NELS + 1;
      IA[NELS]   = 5;
      JA[NELS]   = 12;
      DELS[NELS] = 1.0;
      DRLO[4]    = -1.0e+31;
      DRUP[4]    = 4.5;

/* Load reference row entries for the SOS1 set. Any non-decreasing
   or non-increasing sequence will suffice. */
      UPPCOST[10] = XORD[3];
      UPPCOST[11] = XORD[4];

/* Convert NELS from a C index into the correct number of matrix elements. */
      NELS = NELS + 1;

              /* Describe work space and allow room for one model */
  ekkdsca(&rtcod,dspace,MAXSPC,1);
    if (rtcod0) chkrt("ekkdsca",rtcod);

/* Describe the model. */
  ekkdscm(&rtcod,dspace,1,1);
    if (rtcod0) chkrt("ekkdscm",rtcod);

/* Pass the model with the matrix stored by indices. */
  ekklmdl(&rtcod,dspace,ITYPE,NROW,NCOL,NELS,DOBJ,
          DRLO,DRUP,DCLO,DCUP,IA,JA,DELS);
    if (rtcod0) chkrt("ekklmdl",rtcod);

/* Create names for the variables */
  ekkname(&rtcod,dspace,0,0,1,0,0,1,1);
    if (rtcod0) chkrt("ekkname",rtcod);

/* Load names for x and y into the names region. */
  ekknget(&rtcod,dspace,osln,OSLNLN);
    if (rtcod0) chkrt("ekknget",rtcod);
    p = &dspace[NCOLNAMES+ 7-2]; sprintf(p,"%s","X_value"); p=p+7; *p
    p = &dspace[NCOLNAMES+12-2]; sprintf(p,"%s","Y_value"); p=p+7; *p

/* Specify three integer variables. */
  ekkiget(&rtcod,dspace,osli,OSLILN);
    if (rtcod0) chkrt("ekkiget",rtcod);
        IMAXINTS = 15;
        ISOLMASK = 6;
  ekkiset(&rtcod,dspace,osli,OSLILN);
    if (rtcod0) chkrt("ekkiset",rtcod);

/* Specify the integer parts of a mixed integer programming problem. */
  ekkimdl(&rtcod,dspace,NINTS,INTNUMS,NSETS,TYPE,
          PRIORITY,NTOTINFO,SETINDEX,SETS,DNPCOST,UPPCOST);
    if (rtcod0) chkrt("ekkimdl",rtcod);

/* Solve the model using mixed-integer programming. */
  ekkmslv(&rtcod,dspace,1,0,0);
    if (rtcod0) chkrt("ekkmslv",rtcod);

/* Print the solution. */
  ekkprts(&rtcod,dspace);
    if (rtcod0) chkrt("ekkprts",rtcod);

}
/* ************************************************************************* */
void  chkrt(rtname,rtcod)
char  *rtname;
long  rtcod;
{
   printf("\n****** %s return code of %d ******\n",rtname,rtcod);
   if (rtcod = 200) exit(16);
}

Sample Data Files in MPS Format

Sample input files that may be used with the sample programs can be found in Sample MPS Input Files The files that may be used with a particular sample program are indicated after each program. In addition to these files, there may be additional sample input files distributed with the Optimization Library code.
 

(6) There is one major difference between these sample programs and the code fragments throughout this document. The sample programs all have return code checking after each Optimization Libarary subroutine call. While this is not necessary, it is highly recommended for actual application programs (as opposed to examples), because it can save significant time in debugging.



  [ Top of Page | Previous Page | Next Page | Table of Contents ]