Skip to content

Commit e5c1cd6

Browse files
committed
move to separate module
1 parent fbc0bd5 commit e5c1cd6

File tree

2 files changed

+99
-87
lines changed

2 files changed

+99
-87
lines changed

src/fpm_compile_commands.F90

Lines changed: 96 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,96 @@
1+
!># Store compiler commands in a `compile_commands.json` table
2+
module fpm_compile_commands
3+
use fpm_toml, only: serializable_t, set_string, set_list, get_value, get_list, toml_table
4+
use fpm_strings, only: string_t, operator(==)
5+
use fpm_error, only: error_t
6+
implicit none
7+
8+
!> Definition of a build command
9+
type, extends(serializable_t) :: compile_command_t
10+
11+
type(string_t) :: directory
12+
13+
type(string_t), allocatable :: arguments(:)
14+
15+
type(string_t) :: file
16+
17+
contains
18+
19+
!> Serialization procedures
20+
procedure :: serializable_is_same => compile_command_is_same
21+
procedure :: dump_to_toml => compile_command_dump_toml
22+
procedure :: load_from_toml => compile_command_load_toml
23+
24+
end type compile_command_t
25+
26+
27+
contains
28+
29+
!> Dump compile_command_t to toml table
30+
subroutine compile_command_dump_toml(self, table, error)
31+
32+
!> Instance of the serializable object
33+
class(compile_command_t), intent(inout) :: self
34+
35+
!> Data structure
36+
type(toml_table), intent(inout) :: table
37+
38+
!> Error handling
39+
type(error_t), allocatable, intent(out) :: error
40+
41+
call set_string(table, "directory", self%directory, error, 'compile_command_t')
42+
if (allocated(error)) return
43+
call set_list(table, "arguments", self%arguments, error)
44+
if (allocated(error)) return
45+
call set_string(table, "file", self%file, error, 'compile_command_t')
46+
if (allocated(error)) return
47+
48+
end subroutine compile_command_dump_toml
49+
50+
!> Read compile_command_t from toml table (no checks made at this stage)
51+
subroutine compile_command_load_toml(self, table, error)
52+
53+
!> Instance of the serializable object
54+
class(compile_command_t), intent(inout) :: self
55+
56+
!> Data structure
57+
type(toml_table), intent(inout) :: table
58+
59+
!> Error handling
60+
type(error_t), allocatable, intent(out) :: error
61+
62+
call get_value(table, "directory", self%directory, error, 'compile_command_t')
63+
if (allocated(error)) return
64+
call get_list(table, "arguments", self%arguments, error)
65+
if (allocated(error)) return
66+
call get_value(table, "file", self%file, error, 'compile_command_t')
67+
if (allocated(error)) return
68+
69+
end subroutine compile_command_load_toml
70+
71+
!> Check that two compile_command_t objects are equal
72+
logical function compile_command_is_same(this,that)
73+
class(compile_command_t), intent(in) :: this
74+
class(serializable_t), intent(in) :: that
75+
76+
compile_command_is_same = .false.
77+
78+
select type (other=>that)
79+
type is (compile_command_t)
80+
81+
if (.not.this%directory==other%directory) return
82+
if (.not.this%arguments==other%arguments) return
83+
if (.not.this%file==other%file) return
84+
85+
class default
86+
! Not the same type
87+
return
88+
end select
89+
90+
!> All checks passed!
91+
compile_command_is_same = .true.
92+
93+
end function compile_command_is_same
94+
95+
96+
end module fpm_compile_commands

src/fpm_compiler.F90

Lines changed: 3 additions & 87 deletions
Original file line numberDiff line numberDiff line change
@@ -39,12 +39,11 @@ module fpm_compiler
3939
OS_UNKNOWN
4040
use fpm_filesystem, only: join_path, basename, get_temp_filename, delete_file, unix_path, &
4141
& getline, run
42-
use fpm_strings, only: split, string_cat, string_t, str_ends_with, str_begins_with_str, &
43-
& operator(==)
42+
use fpm_strings, only: split, string_cat, string_t, str_ends_with, str_begins_with_str
4443
use fpm_manifest, only : package_config_t
4544
use fpm_error, only: error_t, fatal_error
46-
use fpm_toml, only: serializable_t, toml_table, set_string, set_value, toml_stat, get_value, &
47-
& get_list, set_list
45+
use fpm_toml, only: serializable_t, toml_table, set_string, set_value, toml_stat, get_value
46+
use fpm_compile_commands, only: compile_command_t
4847
implicit none
4948
public :: compiler_t, new_compiler, archiver_t, new_archiver, get_macros
5049
public :: debug
@@ -74,24 +73,6 @@ module fpm_compiler
7473
end enum
7574
integer, parameter :: compiler_enum = kind(id_unknown)
7675

77-
!> Definition of a build command
78-
type, extends(serializable_t) :: compile_command_t
79-
80-
type(string_t) :: directory
81-
82-
type(string_t), allocatable :: arguments(:)
83-
84-
type(string_t) :: file
85-
86-
contains
87-
88-
!> Serialization procedures
89-
procedure :: serializable_is_same => compile_command_is_same
90-
procedure :: dump_to_toml => compile_command_dump_toml
91-
procedure :: load_from_toml => compile_command_load_toml
92-
93-
end type compile_command_t
94-
9576
!> Definition of compiler object
9677
type, extends(serializable_t) :: compiler_t
9778
!> Identifier of the compiler
@@ -1519,70 +1500,5 @@ logical function with_xdp(self)
15191500
('if (any(selected_real_kind(18) == [-1, selected_real_kind(33)])) stop 1; end')
15201501
end function with_xdp
15211502

1522-
!> Dump compile_command_t to toml table
1523-
subroutine compile_command_dump_toml(self, table, error)
1524-
1525-
!> Instance of the serializable object
1526-
class(compile_command_t), intent(inout) :: self
1527-
1528-
!> Data structure
1529-
type(toml_table), intent(inout) :: table
1530-
1531-
!> Error handling
1532-
type(error_t), allocatable, intent(out) :: error
1533-
1534-
call set_string(table, "directory", self%directory, error, 'compile_command_t')
1535-
if (allocated(error)) return
1536-
call set_list(table, "arguments", self%arguments, error)
1537-
if (allocated(error)) return
1538-
call set_string(table, "file", self%file, error, 'compile_command_t')
1539-
if (allocated(error)) return
1540-
1541-
end subroutine compile_command_dump_toml
1542-
1543-
!> Read compile_command_t from toml table (no checks made at this stage)
1544-
subroutine compile_command_load_toml(self, table, error)
1545-
1546-
!> Instance of the serializable object
1547-
class(compile_command_t), intent(inout) :: self
1548-
1549-
!> Data structure
1550-
type(toml_table), intent(inout) :: table
1551-
1552-
!> Error handling
1553-
type(error_t), allocatable, intent(out) :: error
1554-
1555-
call get_value(table, "directory", self%directory, error, 'compile_command_t')
1556-
if (allocated(error)) return
1557-
call get_list(table, "arguments", self%arguments, error)
1558-
if (allocated(error)) return
1559-
call get_value(table, "file", self%file, error, 'compile_command_t')
1560-
if (allocated(error)) return
1561-
1562-
end subroutine compile_command_load_toml
1563-
1564-
!> Check that two compile_command_t objects are equal
1565-
logical function compile_command_is_same(this,that)
1566-
class(compile_command_t), intent(in) :: this
1567-
class(serializable_t), intent(in) :: that
1568-
1569-
compile_command_is_same = .false.
1570-
1571-
select type (other=>that)
1572-
type is (compile_command_t)
1573-
1574-
if (.not.this%directory==other%directory) return
1575-
if (.not.this%arguments==other%arguments) return
1576-
if (.not.this%file==other%file) return
1577-
1578-
class default
1579-
! Not the same type
1580-
return
1581-
end select
1582-
1583-
!> All checks passed!
1584-
compile_command_is_same = .true.
1585-
1586-
end function compile_command_is_same
15871503

15881504
end module fpm_compiler

0 commit comments

Comments
 (0)