aboutsummaryrefslogtreecommitdiff
path: root/src/clp.f90
diff options
context:
space:
mode:
Diffstat (limited to 'src/clp.f90')
-rw-r--r--src/clp.f9096
1 files changed, 90 insertions, 6 deletions
diff --git a/src/clp.f90 b/src/clp.f90
index 427ec55..2c8692a 100644
--- a/src/clp.f90
+++ b/src/clp.f90
@@ -401,21 +401,25 @@ module clp
type(c_ptr), value :: model
type(c_ptr) :: Clp_getVectorStarts_C
end function
- function Clp_getIndices(model) bind(C,name="Clp_getIndices")
+
+ function Clp_getIndices_C(model) bind(C,name="Clp_getIndices")
use iso_c_binding
type(c_ptr), value :: model
- type(c_ptr) :: Clp_getIndices
+ type(c_ptr) :: Clp_getIndices_C
end function
- function Clp_getVectorLengths(model) bind(C,name="Clp_getVectorLengths")
+
+ function Clp_getVectorLengths_C(model) bind(C,name="Clp_getVectorLengths")
use iso_c_binding
type(c_ptr), value :: model
- type(c_ptr) :: Clp_getVectorLengths
+ type(c_ptr) :: Clp_getVectorLengths_C
end function
- function Clp_getElements(model) bind(C,name="Clp_getElements")
+
+ function Clp_getElements_C(model) bind(C,name="Clp_getElements")
use iso_c_binding
type(c_ptr), value :: model
- type(c_ptr) :: Clp_getElements
+ type(c_ptr) :: Clp_getElements_C
end function
+
function Clp_objectiveValue(model) bind(C,name="Clp_objectiveValue")
use iso_c_binding
type(c_ptr), value :: model
@@ -1616,4 +1620,84 @@ contains
end subroutine Clp_freeRay
+ function Clp_getIndices(model) result(res)
+ use iso_c_binding
+ implicit none
+
+ type(c_ptr) :: model
+ integer(c_int), dimension(:), pointer :: res
+ integer::nrows
+
+ type(c_ptr) :: c_res
+
+ res => null()
+
+ c_res = Clp_getIndices_C(model)
+ if(c_associated(c_res)) then
+ nrows = Clp_Numberrows(model)
+ call c_f_pointer(c_res, res, (/ nrows /))
+ end if
+
+ end function Clp_getIndices
+
+ function Clp_getVectorLengths(model) result(res)
+ use iso_c_binding
+ implicit none
+
+ type(c_ptr) :: model
+ integer(c_int), dimension(:), pointer :: res
+ integer::ncols
+
+ type(c_ptr) :: c_res
+
+ res => null()
+
+ c_res = Clp_getVectorLengths_C(model)
+ if(c_associated(c_res)) then
+ ncols = Clp_Numbercolumns(model)
+ call c_f_pointer(c_res, res, (/ ncols /))
+ end if
+
+ end function Clp_getVectorLengths
+
+ function Clp_getElements(model) result(res)
+ use iso_c_binding
+ use clp_constants
+ implicit none
+
+ type(c_ptr) :: model
+ real(c_double), dimension(:), pointer :: res
+ integer :: n
+
+ type(c_ptr) :: c_res
+
+ res => null()
+
+ c_res = Clp_getElements_C(model)
+ if(c_associated(c_res)) then
+ n = Clp_getNumElements(model)
+ call c_f_pointer(c_res, res, (/ n /))
+ end if
+
+ end function Clp_getElements
+
+ subroutine Clp_integerInformation(model, str)
+ use iso_c_binding
+ use clp_interface_utils
+ implicit none
+
+ type(c_ptr) :: model
+ character(*), intent(out) :: str
+
+ type(c_ptr) :: cstr
+
+ str = ' '
+
+ cstr = Clp_integerInformation_C(model)
+ if(c_associated(cstr)) then
+ call populate_fortran_string(cstr, str)
+ end if
+
+ end subroutine Clp_integerInformation
+
end module clp