@@ -21,10 +21,12 @@ module fpm
21
21
use fpm_manifest, only : get_package_data, package_config_t
22
22
use fpm_meta, only : resolve_metapackages
23
23
use fpm_error, only : error_t, fatal_error, fpm_stop
24
- use ,intrinsic :: iso_fortran_env, only : stdin= > input_unit, &
25
- & stdout= > output_unit, &
26
- & stderr= > error_unit
24
+ use , intrinsic :: iso_fortran_env, only : stdin = > input_unit, &
25
+ & stdout = > output_unit, &
26
+ & stderr = > error_unit
27
27
use iso_c_binding, only: c_char, c_ptr, c_int, c_null_char, c_associated, c_f_pointer
28
+ use fpm_environment, only: os_is_unix
29
+
28
30
implicit none
29
31
private
30
32
public :: cmd_build, cmd_run, cmd_clean
@@ -42,7 +44,6 @@ subroutine build_model(model, settings, package, error)
42
44
integer :: i, j
43
45
type (package_config_t) :: dependency
44
46
character (len= :), allocatable :: manifest, lib_dir
45
- character (len= :), allocatable :: version
46
47
logical :: has_cpp
47
48
logical :: duplicates_found
48
49
type (string_t) :: include_dir
@@ -324,7 +325,7 @@ end subroutine check_modules_for_duplicates
324
325
subroutine check_module_names (model , error )
325
326
type (fpm_model_t), intent (in ) :: model
326
327
type (error_t), allocatable , intent (out ) :: error
327
- integer :: i,j, k,l,m
328
+ integer :: k,l,m
328
329
logical :: valid,errors_found,enforce_this_file
329
330
type (string_t) :: package_name,module_name,package_prefix
330
331
@@ -619,29 +620,29 @@ subroutine cmd_run(settings,test)
619
620
call fpm_stop(stat(firsterror),' *cmd_run*:stopping due to failed executions' )
620
621
end if
621
622
622
- endif
623
+ end if
624
+
623
625
contains
626
+
624
627
subroutine compact_list_all ()
625
628
integer , parameter :: LINE_WIDTH = 80
626
- integer :: i, j , nCol
627
- j = 1
629
+ integer :: ii, jj , nCol
630
+ jj = 1
628
631
nCol = LINE_WIDTH/ col_width
629
632
write (stderr,* ) ' Available names:'
630
- do i = 1 ,size (targets)
633
+ do ii = 1 ,size (targets)
631
634
632
- exe_target = > targets(i )% ptr
635
+ exe_target = > targets(ii )% ptr
633
636
634
637
if (exe_target% target_type == FPM_TARGET_EXECUTABLE .and. &
635
638
allocated (exe_target% dependencies)) then
636
639
637
640
exe_source = > exe_target% dependencies(1 )% ptr% source
638
641
639
642
if (exe_source% unit_scope == run_scope) then
640
-
641
- write (stderr,' (A)' ,advance= (merge (" yes" ," no " ,modulo (j,nCol)==0 ))) &
643
+ write (stderr,' (A)' ,advance= (merge (" yes" ," no " ,modulo (jj,nCol)==0 ))) &
642
644
& [character (len= col_width) :: basename(exe_target% output_file, suffix= .false. )]
643
- j = j + 1
644
-
645
+ jj = jj + 1
645
646
end if
646
647
end if
647
648
end do
@@ -650,15 +651,15 @@ end subroutine compact_list_all
650
651
651
652
subroutine compact_list ()
652
653
integer , parameter :: LINE_WIDTH = 80
653
- integer :: i, j , nCol
654
- j = 1
654
+ integer :: ii, jj , nCol
655
+ jj = 1
655
656
nCol = LINE_WIDTH/ col_width
656
657
write (stderr,* ) ' Matched names:'
657
- do i = 1 ,size (executables)
658
- write (stderr,' (A)' ,advance= (merge (" yes" ," no " ,modulo (j ,nCol)==0 ))) &
659
- & [character (len= col_width) :: basename(executables(i )% s, suffix= .false. )]
660
- j = j + 1
661
- enddo
658
+ do ii = 1 ,size (executables)
659
+ write (stderr,' (A)' ,advance= (merge (" yes" ," no " ,modulo (jj ,nCol)==0 ))) &
660
+ & [character (len= col_width) :: basename(executables(ii )% s, suffix= .false. )]
661
+ jj = jj + 1
662
+ end do
662
663
write (stderr,* )
663
664
end subroutine compact_list
664
665
@@ -679,27 +680,28 @@ subroutine delete_skip(is_unix)
679
680
end do
680
681
end subroutine delete_skip
681
682
683
+ ! > Delete the build directory including or excluding dependencies.
682
684
subroutine cmd_clean (settings )
683
- ! > fpm clean called
685
+ ! > Settings for the clean command.
684
686
class(fpm_clean_settings), intent (in ) :: settings
685
- ! character(len=:), allocatable :: dir
686
- ! type(string_t), allocatable :: files(:)
687
- character (len = 1 ) :: response
687
+
688
+ character :: user_response
689
+
688
690
if (is_dir(' build' )) then
689
- ! remove the entire build directory
691
+ ! Remove the entire build directory
690
692
if (settings% clean_call) then
691
- call os_delete_dir(settings% is_unix, ' build' )
692
- return
693
+ call os_delete_dir(os_is_unix(), ' build' ); return
693
694
end if
694
- ! remove the build directory but skip dependencies
695
+
696
+ ! Remove the build directory but skip dependencies
695
697
if (settings% clean_skip) then
696
- call delete_skip(settings% is_unix)
697
- return
698
+ call delete_skip(os_is_unix()); return
698
699
end if
699
- ! prompt to remove the build directory but skip dependencies
700
+
701
+ ! Prompt to remove the build directory but skip dependencies
700
702
write (stdout, ' (A)' , advance= ' no' ) " Delete build, excluding dependencies (y/n)? "
701
- read (stdin, ' (A1)' ) response
702
- if (lower(response ) == ' y' ) call delete_skip(settings % is_unix )
703
+ read (stdin, ' (A1)' ) user_response
704
+ if (lower(user_response ) == ' y' ) call delete_skip(os_is_unix() )
703
705
else
704
706
write (stdout, ' (A)' ) " fpm: No build directory found."
705
707
end if
0 commit comments