@@ -17,7 +17,7 @@ module fpm_manifest_preprocess
17
17
implicit none
18
18
private
19
19
20
- public :: preprocess_config_t, new_preprocess_config, new_preprocessors
20
+ public :: preprocess_config_t, new_preprocess_config, new_preprocessors, operator (==)
21
21
22
22
! > Configuration meta data for a preprocessor
23
23
type :: preprocess_config_t
@@ -41,6 +41,10 @@ module fpm_manifest_preprocess
41
41
42
42
end type preprocess_config_t
43
43
44
+ interface operator (== )
45
+ module procedure preprocess_is_same
46
+ end interface
47
+
44
48
contains
45
49
46
50
! > Construct a new preprocess configuration from TOML data structure
@@ -154,7 +158,7 @@ subroutine info(self, unit, verbosity)
154
158
pr = 1
155
159
end if
156
160
157
- if (pr < 1 ) return
161
+ if (pr < 1 ) return
158
162
159
163
write (unit, fmt) " Preprocessor"
160
164
if (allocated (self% name)) then
@@ -181,4 +185,47 @@ subroutine info(self, unit, verbosity)
181
185
182
186
end subroutine info
183
187
188
+ logical function preprocess_is_same (this ,that )
189
+ class(preprocess_config_t), intent (in ) :: this
190
+ class(preprocess_config_t), intent (in ) :: that
191
+
192
+ integer :: istr
193
+
194
+ preprocess_is_same = .false.
195
+
196
+ select type (other= >that)
197
+ type is (preprocess_config_t)
198
+ if (allocated (this% name).neqv. allocated (other% name)) return
199
+ if (allocated (this% name)) then
200
+ if (.not. (this% name== other% name)) return
201
+ endif
202
+ if (.not. (allocated (this% suffixes).eqv. allocated (other% suffixes))) return
203
+ if (allocated (this% suffixes)) then
204
+ do istr= 1 ,size (this% suffixes)
205
+ if (.not. (this% suffixes(istr)% s== other% suffixes(istr)% s)) return
206
+ end do
207
+ end if
208
+ if (.not. (allocated (this% directories).eqv. allocated (other% directories))) return
209
+ if (allocated (this% directories)) then
210
+ do istr= 1 ,size (this% directories)
211
+ if (.not. (this% directories(istr)% s== other% directories(istr)% s)) return
212
+ end do
213
+ end if
214
+ if (.not. (allocated (this% macros).eqv. allocated (other% macros))) return
215
+ if (allocated (this% macros)) then
216
+ do istr= 1 ,size (this% macros)
217
+ if (.not. (this% macros(istr)% s== other% macros(istr)% s)) return
218
+ end do
219
+ end if
220
+
221
+ class default
222
+ ! Not the same type
223
+ return
224
+ end select
225
+
226
+ ! > All checks passed!
227
+ preprocess_is_same = .true.
228
+
229
+ end function preprocess_is_same
230
+
184
231
end module fpm_manifest_preprocess
0 commit comments