aboutsummaryrefslogtreecommitdiff
path: root/src/clp_callback.f90
diff options
context:
space:
mode:
Diffstat (limited to 'src/clp_callback.f90')
-rw-r--r--src/clp_callback.f9011
1 files changed, 7 insertions, 4 deletions
diff --git a/src/clp_callback.f90 b/src/clp_callback.f90
index d403be7..905d575 100644
--- a/src/clp_callback.f90
+++ b/src/clp_callback.f90
@@ -25,6 +25,7 @@ contains
nString, vString) bind(C)
use iso_c_binding
use clp_constants
+ use clp_interface_utils
implicit none
type(c_ptr), value :: model
@@ -34,8 +35,8 @@ contains
real(kind=c_double), dimension(:), pointer :: fdouble
integer(kind=c_int), dimension(:), pointer :: fint
- character(len=clp_default_message_len), dimension(:), pointer :: fstrs
-
+ character(len=clp_default_message_len), dimension(:), allocatable, target :: fstrs
+ character(len=clp_default_message_len), dimension(:), pointer :: fstr_pointer
! For converting C strings
type(c_ptr), dimension(:), pointer :: c_strings
integer::i
@@ -55,14 +56,16 @@ contains
do i = 1, nString
call populate_fortran_string(c_strings(i), fstrs(i))
end do
+
+ fstr_pointer => fstrs
end if
! Now that Fortran arrays are built, call the Fortran callback
if(associated(current_callback)) then
- call current_callback(model, messageNumber, fdouble, fint, fstrs)
+ call current_callback(model, messageNumber, fdouble, fint, fstr_pointer)
end if
- if(associated(fstrs)) then
+ if(allocated(fstrs)) then
deallocate(fstrs)
end if