Skip to content

Commit 2abe27d

Browse files
committed
Replace c_remove with Fortran instrinsics
1 parent f1f14e4 commit 2abe27d

File tree

2 files changed

+19
-37
lines changed

2 files changed

+19
-37
lines changed

src/fpm_lock.c

Lines changed: 0 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -71,18 +71,3 @@ void c_create(char *path, int *iostat, char **iomsg, int *exists) {
7171
*iostat = 0;
7272
*iomsg = NULL;
7373
}
74-
75-
// @brief Remove a file/directory in an atomic manner.
76-
// @param path
77-
// @param iostat
78-
// @param iomsg
79-
void c_remove(char *path, int *iostat, char **iomsg) {
80-
int stat = remove(path);
81-
if (stat == -1) {
82-
*iostat = 1;
83-
*iomsg = my_strerror(errno);
84-
return;
85-
}
86-
*iostat = 0;
87-
*iomsg = NULL;
88-
}

src/fpm_lock.f90

Lines changed: 19 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -112,7 +112,7 @@ module fpm_lock
112112

113113
use :: fpm_error, only : error_t, fatal_error
114114
use :: fpm_os, only : get_current_directory
115-
use :: fpm_filesystem, only : join_path
115+
use :: fpm_filesystem, only : join_path, delete_file
116116
use, intrinsic :: iso_fortran_env, only : stderr => error_unit
117117
use iso_c_binding, only : c_int, c_char, c_null_char, c_ptr, c_funptr, &
118118
c_funloc, c_f_pointer
@@ -133,14 +133,6 @@ subroutine c_create(path, iostat, iomsg, exists) bind(c, name='c_create')
133133
integer(kind=c_int), intent(out) :: exists
134134
end subroutine c_create
135135

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-
144136
! atexit is a standard C90 function.
145137
subroutine atexit(fptr) bind(c, name='atexit')
146138
import c_funptr
@@ -287,24 +279,29 @@ subroutine fpm_lock_release(error)
287279
!> Error handling
288280
type(error_t), allocatable, intent(out) :: error
289281

290-
integer :: lock_unit
291-
282+
integer :: unit
292283
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
296285

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)
298292

299293
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
306297

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
308305
end if
309306
end subroutine fpm_lock_release
310307

0 commit comments

Comments
 (0)