new_target Function

public function new_target(package, type, output_name, source, link_libraries, features, preprocess, version, output_dir)

Allocate a new target

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: package
integer, intent(in) :: type
character(len=*), intent(in) :: output_name
type(srcfile_t), intent(in), optional :: source
type(string_t), intent(in), optional :: link_libraries(:)
type(fortran_features_t), intent(in), optional :: features
type(preprocess_config_t), intent(in), optional :: preprocess
character(len=*), intent(in), optional :: version
character(len=*), intent(in), optional :: output_dir

Return Value type(build_target_ptr)


Source Code

type(build_target_ptr) function new_target(package, type, output_name, source, link_libraries, &
        & features, preprocess, version, output_dir)
    character(*), intent(in) :: package
    integer, intent(in) :: type
    character(*), intent(in) :: output_name
    type(srcfile_t), intent(in), optional :: source
    type(string_t), intent(in), optional :: link_libraries(:)
    type(fortran_features_t), intent(in), optional :: features
    type(preprocess_config_t), intent(in), optional :: preprocess
    character(*), intent(in), optional :: version
    character(*), intent(in), optional :: output_dir

    allocate(new_target%ptr)
    
    associate(target=>new_target%ptr)
    
        target%target_type = type
        target%output_name = output_name
        target%package_name = package
        if (present(source)) target%source = source
        if (present(link_libraries)) target%link_libraries = link_libraries
        if (present(features)) target%features = features
        if (present(preprocess)) then
            if (allocated(preprocess%macros)) target%macros = preprocess%macros
        endif
        if (present(version)) target%version = version
        allocate(target%dependencies(0))
        
        call target%set_output_dir(output_dir)
    
    endassociate
    
end function new_target