Look for flags, c-flags, link-time-flags key-val pairs and files table in a given table and create new profiles
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=:), | intent(in), | allocatable | :: | profile_name |
Name of profile |
|
character(len=:), | intent(in), | allocatable | :: | compiler_name |
Name of compiler |
|
integer, | intent(in) | :: | os_type |
OS type |
||
type(toml_key), | intent(in), | allocatable | :: | key_list(:) |
List of keys in the table |
|
type(toml_table), | intent(in), | pointer | :: | table |
Table containing OS tables |
|
type(profile_config_t), | intent(inout), | allocatable | :: | profiles(:) |
List of profiles |
|
integer, | intent(inout) | :: | profindex |
Index in the list of profiles |
||
logical, | intent(in) | :: | os_valid |
Was called with valid operating system |
Type | Visibility | Attributes | Name | Initial | |||
---|---|---|---|---|---|---|---|
character(len=:), | public, | allocatable | :: | c_flags | |||
character(len=:), | public, | allocatable | :: | cxx_flags | |||
character(len=:), | public, | allocatable | :: | err_message | |||
character(len=:), | public, | allocatable | :: | file_flags | |||
type(toml_key), | public, | allocatable | :: | file_list(:) | |||
character(len=:), | public, | allocatable | :: | file_name | |||
type(file_scope_flag), | public, | allocatable | :: | file_scope_flags(:) | |||
type(toml_table), | public, | pointer | :: | files | |||
character(len=:), | public, | allocatable | :: | flags | |||
integer, | public | :: | ifile | ||||
integer, | public | :: | ikey | ||||
logical, | public | :: | is_valid | ||||
character(len=:), | public, | allocatable | :: | key_name | |||
character(len=:), | public, | allocatable | :: | link_time_flags | |||
integer, | public | :: | stat |
subroutine get_flags(profile_name, compiler_name, os_type, key_list, table, profiles, profindex, os_valid) !> Name of profile character(len=:), allocatable, intent(in) :: profile_name !> Name of compiler character(len=:), allocatable, intent(in) :: compiler_name !> OS type integer, intent(in) :: os_type !> List of keys in the table type(toml_key), allocatable, intent(in) :: key_list(:) !> Table containing OS tables type(toml_table), pointer, intent(in) :: table !> List of profiles type(profile_config_t), allocatable, intent(inout) :: profiles(:) !> Index in the list of profiles integer, intent(inout) :: profindex !> Was called with valid operating system logical, intent(in) :: os_valid character(len=:), allocatable :: flags, c_flags, cxx_flags, link_time_flags, key_name, file_name, file_flags, err_message type(toml_table), pointer :: files type(toml_key), allocatable :: file_list(:) type(file_scope_flag), allocatable :: file_scope_flags(:) integer :: ikey, ifile, stat logical :: is_valid call get_value(table, 'flags', flags) call get_value(table, 'c-flags', c_flags) call get_value(table, 'cxx-flags', cxx_flags) call get_value(table, 'link-time-flags', link_time_flags) call get_value(table, 'files', files) if (associated(files)) then call files%get_keys(file_list) allocate(file_scope_flags(size(file_list))) do ifile=1,size(file_list) file_name = file_list(ifile)%key call get_value(files, file_name, file_flags) associate(cur_file=>file_scope_flags(ifile)) if (.not.(path.eq."")) file_name = join_path(path, file_name) cur_file%file_name = file_name cur_file%flags = file_flags end associate end do end if profiles(profindex) = new_profile(profile_name, compiler_name, os_type, & & flags, c_flags, cxx_flags, link_time_flags, file_scope_flags) profindex = profindex + 1 end subroutine get_flags