cct_register Subroutine

public subroutine cct_register(self, command, target_os, error)

Register a new compile command

Type Bound

compile_command_table_t

Arguments

Type IntentOptional Attributes Name
class(compile_command_table_t), intent(inout) :: self

Instance of the serializable object

character(len=*), intent(in) :: command

Data structure

integer, intent(in) :: target_os

The target OS of the compile_commands.json (may be cross-compiling)

type(error_t), intent(out), allocatable :: error

Error handling


Variables

Type Visibility Attributes Name Initial
character(len=:), public, allocatable :: args(:)
type(compile_command_t), public :: cmd
character(len=:), public, allocatable :: cwd
integer, public :: i
integer, public :: n
logical, public :: sh_success
character(len=:), public, allocatable :: source_file

Source Code

    subroutine cct_register(self, command, target_os, error)

        !> Instance of the serializable object
        class(compile_command_table_t), intent(inout) :: self

        !> Data structure
        character(len=*), intent(in) :: command
        
        !> The target OS of the compile_commands.json (may be cross-compiling)
        integer, intent(in) :: target_os
        
        !> Error handling
        type(error_t), allocatable, intent(out) :: error    
        
        ! Local variables
        type(compile_command_t) :: cmd
        character(len=:), allocatable :: args(:), cwd, source_file
        logical :: sh_success
        integer :: i,n
        
        ! Early check
        if (len_trim(command) <= 0) then
            call syntax_error(error, "compile_command_table_t trying to register an empty command")
            return
        end if

        ! Tokenize the input command into args(:)
        if (target_os==OS_WINDOWS) then 
            args = ms_split(command, ucrt=.true., success=sh_success)
        else
            args = sh_split(command, join_spaced=.false., keep_quotes=.true., success=sh_success)
        end if
        n = size(args)
        
        if (n==0 .or. .not.sh_success) then 
            call syntax_error(error, "compile_command_table_t failed tokenizing: <"//command//">")
            return
        end if
        
        ! Get current working directory
        call get_current_directory(cwd, error)
        if (allocated(error)) return

        ! Try to find the source file
        allocate(character(len=0) :: source_file)
        find_source_file: do i = 1, n-1
            if (args(i) == "-c") then
                source_file = trim(args(i+1))
                exit find_source_file
            end if
        end do find_source_file

        ! Fallback: use last argument if not found
        if (len_trim(source_file)==0) source_file = trim(args(n))

        ! Fill in the compile_command_t. 
        ! Use non-default initializer due to gcc 15 bug
        cmd = compile_command_t(cwd, args, source_file)
        
        ! Add it to the structure
        !$omp critical (command_update)
        call cct_register_object(self, cmd, error)
        !$omp end critical (command_update)

    end subroutine cct_register