profile_same Function

public function profile_same(this, that)

All checks passed!

Type Bound

profile_config_t

Arguments

Type IntentOptional Attributes Name
class(profile_config_t), intent(in) :: this
class(serializable_t), intent(in) :: that

Return Value logical


Variables

Type Visibility Attributes Name Initial
integer, public :: ii

Source Code

      logical function profile_same(this,that)
          class(profile_config_t), intent(in) :: this
          class(serializable_t), intent(in) :: that

          integer :: ii

          profile_same = .false.

          select type (other=>that)
             type is (profile_config_t)
                if (allocated(this%profile_name).neqv.allocated(other%profile_name)) return
                if (allocated(this%profile_name)) then
                    if (.not.(this%profile_name==other%profile_name)) return
                endif
                if (allocated(this%compiler).neqv.allocated(other%compiler)) return
                if (allocated(this%compiler)) then
                    if (.not.(this%compiler==other%compiler)) return
                endif
                if (this%os_type/=other%os_type) return
                if (allocated(this%flags).neqv.allocated(other%flags)) return
                if (allocated(this%flags)) then
                    if (.not.(this%flags==other%flags)) return
                endif
                if (allocated(this%c_flags).neqv.allocated(other%c_flags)) return
                if (allocated(this%c_flags)) then
                    if (.not.(this%c_flags==other%c_flags)) return
                endif
                if (allocated(this%cxx_flags).neqv.allocated(other%cxx_flags)) return
                if (allocated(this%cxx_flags)) then
                    if (.not.(this%cxx_flags==other%cxx_flags)) return
                endif
                if (allocated(this%link_time_flags).neqv.allocated(other%link_time_flags)) return
                if (allocated(this%link_time_flags)) then
                    if (.not.(this%link_time_flags==other%link_time_flags)) return
                endif

                if (allocated(this%file_scope_flags).neqv.allocated(other%file_scope_flags)) return
                if (allocated(this%file_scope_flags)) then
                    if (.not.size(this%file_scope_flags)==size(other%file_scope_flags)) return
                    do ii=1,size(this%file_scope_flags)
                        print *, 'check ii-th file scope: ',ii
                       if (.not.this%file_scope_flags(ii)==other%file_scope_flags(ii)) return
                    end do
                endif

                if (this%is_built_in.neqv.other%is_built_in) return

             class default
                ! Not the same type
                return
          end select

          !> All checks passed!
          profile_same = .true.

    end function profile_same