aboutsummaryrefslogtreecommitdiff
path: root/src/clp.f90
diff options
context:
space:
mode:
Diffstat (limited to 'src/clp.f90')
-rw-r--r--src/clp.f9041
1 files changed, 25 insertions, 16 deletions
diff --git a/src/clp.f90 b/src/clp.f90
index cd34b95..24fc769 100644
--- a/src/clp.f90
+++ b/src/clp.f90
@@ -1082,22 +1082,24 @@ contains
end function Clp_SetProblemName
- subroutine Clp_problemName(model,maxNumberCharacters,array)
+ subroutine Clp_problemName(model,array)
use clp_interface_utils
use iso_c_binding
implicit none
type(c_ptr) :: model
- integer(c_int), intent(in) :: maxNumberCharacters
- character(len=*) :: array
+ character(len=*), intent(out) :: array
type(c_ptr)::c_array
- c_array = allocate_and_populate_c_string(array)
-
- call Clp_problemName_C(model, maxNumberCharacters, c_array)
+ array = ' '
- call c_free(c_array)
+ c_array = c_allocate(int(len(array) + 1, kind=c_size_t))
+ if(c_associated(c_array)) then
+ call Clp_problemName_C(model, len(array), c_array)
+ call populate_fortran_string(c_array, array)
+ call c_free(c_array)
+ end if
end subroutine Clp_problemName
@@ -1154,16 +1156,20 @@ contains
type(c_ptr) :: model
integer, intent(in)::iRow
- character(*), intent(in) :: name
-
+ character(*), intent(out) :: name
+
type(c_ptr) :: np
-
- np = allocate_and_populate_c_string(name)
+
+ name = ' '
+
+ np = c_allocate(int(Clp_LengthNames(model)+1, kind=c_size_t))
if(c_associated(np)) then
call Clp_rowName_C(model, int(iRow, kind=c_int), np)
+ call populate_fortran_string(np, name)
call c_free(np)
end if
+
end subroutine Clp_rowName
subroutine Clp_columnName(model,iColumn,name)
@@ -1173,13 +1179,16 @@ contains
type(c_ptr) :: model
integer, intent(in)::iColumn
- character(*), intent(in) :: name
-
+ character(*), intent(out) :: name
+
type(c_ptr) :: np
-
- np = allocate_and_populate_c_string(name)
+
+ name = ' '
+
+ np = c_allocate(int(Clp_LengthNames(model)+1, kind=c_size_t))
if(c_associated(np)) then
- call Clp_rowName_C(model, int(iColumn, kind=c_int), np)
+ call Clp_columnName_C(model, int(iColumn, kind=c_int), np)
+ call populate_fortran_string(np, name)
call c_free(np)
end if