@@ -112,7 +112,7 @@ module fpm_lock
112
112
113
113
use :: fpm_error, only : error_t, fatal_error
114
114
use :: fpm_os, only : get_current_directory
115
- use :: fpm_filesystem, only : join_path
115
+ use :: fpm_filesystem, only : join_path, delete_file
116
116
use , intrinsic :: iso_fortran_env, only : stderr = > error_unit
117
117
use iso_c_binding, only : c_int, c_char, c_null_char, c_ptr, c_funptr, &
118
118
c_funloc, c_f_pointer
@@ -133,14 +133,6 @@ subroutine c_create(path, iostat, iomsg, exists) bind(c, name='c_create')
133
133
integer (kind= c_int), intent (out ) :: exists
134
134
end subroutine c_create
135
135
136
- ! This function is defined in `fpm_lock.c`.
137
- subroutine c_remove (path , iostat , iomsg ) bind(c, name= ' c_remove' )
138
- import c_int, c_char, c_ptr
139
- character (kind= c_char), intent (in ) :: path(* )
140
- integer (kind= c_int), intent (out ) :: iostat
141
- type (c_ptr), intent (out ) :: iomsg
142
- end subroutine c_remove
143
-
144
136
! atexit is a standard C90 function.
145
137
subroutine atexit (fptr ) bind(c, name= ' atexit' )
146
138
import c_funptr
@@ -287,24 +279,29 @@ subroutine fpm_lock_release(error)
287
279
! > Error handling
288
280
type (error_t), allocatable , intent (out ) :: error
289
281
290
- integer :: lock_unit
291
-
282
+ integer :: unit
292
283
integer :: iostat
293
- character (:), allocatable :: iomsg
294
- character (len= 1 ), pointer :: c_iomsg(:)
295
- type (c_ptr) :: c_iomsg_ptr
284
+ character (len= 256 ) :: iomsg
296
285
297
- call c_remove(' .fpm-package-lock' // c_null_char, iostat, c_iomsg_ptr)
286
+ open (file= ' .fpm-package-lock' , &
287
+ action= ' read' , &
288
+ status= ' old' , &
289
+ newunit= unit, &
290
+ iostat= iostat, &
291
+ iomsg= iomsg)
298
292
299
293
if (iostat /= 0 ) then
300
- ! Convert C pointer to Fortran pointer.
301
- call c_f_pointer(c_iomsg_ptr, c_iomsg, [1024 ])
302
- ! Convert Fortran pointer to Fortran string.
303
- iomsg = f_string(c_iomsg)
304
- ! iomsg = f_string(c_iomsg_ptr)
305
- call fatal_error(error, " Error trying to delete lock-file: " // iomsg)
294
+ call fatal_error(error, " Error opening lock-file for deletion: " // iomsg)
295
+ return
296
+ end if
306
297
307
- call c_free(c_iomsg_ptr)
298
+ close (unit= unit, &
299
+ status= ' delete' , &
300
+ iostat= iostat)
301
+
302
+ if (iostat /= 0 ) then
303
+ call fatal_error(error, " Error closing lock-file" )
304
+ return
308
305
end if
309
306
end subroutine fpm_lock_release
310
307
0 commit comments