1
1
module fpm_targets
2
2
use fpm_error, only: error_t, fatal_error
3
- use fpm_model! , only: srcfile_t, build_target_t, FPM_UNIT_PROGRAM, &
4
- ! FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE, FPM_TARGET_OBJECT
3
+ use fpm_model
5
4
use fpm_environment, only: get_os_type, OS_WINDOWS
6
- use fpm_filesystem, only: dirname, join_path
5
+ use fpm_filesystem, only: dirname, join_path, canon_path
7
6
use fpm_strings, only: operator (.in .)
8
7
implicit none
9
8
10
9
contains
11
10
12
- subroutine targets_from_sources (targets ,sources , package_name )
13
- type (build_target_ptr ), allocatable , intent (out ), target :: targets(:)
11
+ subroutine targets_from_sources (model ,sources )
12
+ type (fpm_model_t ), intent (inout ), target :: model
14
13
type (srcfile_t), intent (in ) :: sources(:)
15
- character (* ), intent (in ) :: package_name
16
14
17
15
integer :: i
18
16
type (build_target_t), pointer :: dep
19
17
logical :: with_lib
20
18
21
19
with_lib = any ([(sources(i)% unit_scope == FPM_SCOPE_LIB,i= 1 ,size (sources))])
22
20
23
- if (with_lib) call add_target(targets,type = FPM_TARGET_ARCHIVE,&
24
- output_file = package_name// ' .a' )
21
+ if (with_lib) call add_target(model% targets,type = FPM_TARGET_ARCHIVE,&
22
+ output_file = join_path(model% output_directory,&
23
+ ' lib' ,' lib' // model% package_name// ' .a' ))
25
24
26
25
do i= 1 ,size (sources)
27
26
28
27
select case (sources(i)% unit_type)
29
28
case (FPM_UNIT_MODULE,FPM_UNIT_SUBMODULE,FPM_UNIT_SUBPROGRAM,FPM_UNIT_CSOURCE)
30
29
31
- call add_target(targets,source = sources(i), &
30
+ call add_target(model % targets,source = sources(i), &
32
31
type = FPM_TARGET_OBJECT,&
33
- output_file = get_object_name(sources(i)% file_name ))
32
+ output_file = get_object_name(sources(i)))
34
33
35
34
if (with_lib .and. sources(i)% unit_scope == FPM_SCOPE_LIB) then
36
35
! Archive depends on object
37
- call add_dependency(targets(1 )% ptr, targets(size (targets))% ptr)
36
+ call add_dependency(model % targets(1 )% ptr, model % targets(size (model % targets))% ptr)
38
37
end if
39
38
40
39
case (FPM_UNIT_PROGRAM)
41
40
42
- call add_target(targets,type = FPM_TARGET_OBJECT,&
43
- output_file = get_object_name(sources(i)% file_name ), &
41
+ call add_target(model % targets,type = FPM_TARGET_OBJECT,&
42
+ output_file = get_object_name(sources(i)), &
44
43
source = sources(i) &
45
44
)
46
-
47
- call add_target(targets,type = FPM_TARGET_EXECUTABLE,&
48
- output_file = join_path(' app' ,sources(i)% exe_name))
49
-
45
+
46
+ if (sources(i)% unit_scope == FPM_SCOPE_APP) then
47
+ call add_target(model% targets,type = FPM_TARGET_EXECUTABLE,&
48
+ output_file = join_path(model% output_directory,' app' ,sources(i)% exe_name))
49
+ else
50
+ call add_target(model% targets,type = FPM_TARGET_EXECUTABLE,&
51
+ output_file = join_path(model% output_directory,' test' ,sources(i)% exe_name))
52
+
53
+ end if
50
54
51
55
! Executable depends on object
52
- call add_dependency(targets(size (targets))% ptr, targets(size (targets)- 1 )% ptr)
56
+ call add_dependency(model % targets(size (model % targets))% ptr, model % targets(size (model % targets)- 1 )% ptr)
53
57
54
58
if (with_lib) then
55
59
! Executable depends on library
56
- call add_dependency(targets(size (targets))% ptr, targets(1 )% ptr)
60
+ call add_dependency(model % targets(size (model % targets))% ptr, model % targets(1 )% ptr)
57
61
end if
58
62
59
63
end select
60
64
61
65
end do
62
66
67
+ contains
68
+
69
+ function get_object_name (source ) result(object_file)
70
+ ! Generate object target path from source name and model params
71
+ !
72
+ !
73
+ type (srcfile_t), intent (in ) :: source
74
+ character (:), allocatable :: object_file
75
+
76
+ integer :: i
77
+ character (1 ), parameter :: filesep = ' /'
78
+ character (:), allocatable :: dir
79
+
80
+ object_file = canon_path(source% file_name)
81
+
82
+ ! Ignore first directory level
83
+ object_file = object_file(index (object_file,filesep)+ 1 :)
84
+
85
+ ! Convert any remaining directory separators to underscores
86
+ i = index (object_file,filesep)
87
+ do while (i > 0 )
88
+ object_file(i:i) = ' _'
89
+ i = index (object_file,filesep)
90
+ end do
91
+
92
+ select case (source% unit_scope)
93
+
94
+ case (FPM_SCOPE_APP)
95
+ object_file = join_path(model% output_directory,' app' ,object_file)// ' .o'
96
+
97
+ case (FPM_SCOPE_TEST)
98
+ object_file = join_path(model% output_directory,' test' ,object_file)// ' .o'
99
+
100
+ case default
101
+ object_file = join_path(model% output_directory,' lib' ,object_file)// ' .o'
102
+
103
+ end select
104
+
105
+ end function get_object_name
106
+
63
107
end subroutine targets_from_sources
64
108
65
109
110
+ ! > Add new target to target list
66
111
subroutine add_target (targets ,type ,output_file ,source )
67
112
type (build_target_ptr), allocatable , intent (inout ) :: targets(:)
68
113
integer , intent (in ) :: type
@@ -84,49 +129,16 @@ subroutine add_target(targets,type,output_file,source)
84
129
end subroutine add_target
85
130
86
131
132
+ ! > Add pointer to dependeny in target%dependencies
87
133
subroutine add_dependency (target , dependency )
88
134
type (build_target_t), intent (inout ) :: target
89
135
type (build_target_t) , intent (in ), target :: dependency
90
136
91
- type (build_target_ptr) :: depend
92
-
93
- depend% ptr = > dependency
94
-
95
- ! if (.not.allocated(target%dependencies)) then
96
- ! allocate(target%dependencies(0))
97
- ! end if
98
-
99
- target % dependencies = [target % dependencies, depend]
100
- ! target%dependencies(size(target%dependencies))%ptr => dependency
137
+ target % dependencies = [target % dependencies, build_target_ptr(dependency)]
101
138
102
139
end subroutine add_dependency
103
140
104
141
105
- function get_object_name (source_file_name ) result(object_file)
106
- ! Generate object target path from source name and model params
107
- !
108
- ! src/test.f90 -> <output-dir>/<package-name>/test.o
109
- ! src/subdir/test.f90 -> <output-dir>/<package-name>/subdir_test.o
110
- !
111
- character (* ), intent (in ) :: source_file_name
112
- character (:), allocatable :: object_file
113
-
114
- integer :: i
115
- character (1 ) :: filesep
116
-
117
- select case (get_os_type())
118
- case (OS_WINDOWS)
119
- filesep = ' \'
120
- case default
121
- filesep = ' /'
122
- end select
123
-
124
- ! Exclude first directory level from path
125
- object_file = source_file_name(index (source_file_name,filesep)+ 1 :)// ' .o'
126
-
127
- end function get_object_name
128
-
129
-
130
142
subroutine resolve_module_dependencies (targets ,error )
131
143
! After enumerating all source files: resolve file dependencies
132
144
! by searching on module names
0 commit comments