dyn_exchange_constituent_states Subroutine

public subroutine dyn_exchange_constituent_states(direction, exchange, conversion)

Uses

    • cam_logfile
    • ccpp_kinds
    • cam_abortutils
    • cam_ccpp_cap
    • cam_constituents
    • physics_types
    • shr_kind_mod
    • vert_coord
  • proc~~dyn_exchange_constituent_states~~UsesGraph proc~dyn_exchange_constituent_states dyn_exchange_constituent_states cam_abortutils cam_abortutils proc~dyn_exchange_constituent_states->cam_abortutils cam_ccpp_cap cam_ccpp_cap proc~dyn_exchange_constituent_states->cam_ccpp_cap cam_constituents cam_constituents proc~dyn_exchange_constituent_states->cam_constituents cam_logfile cam_logfile proc~dyn_exchange_constituent_states->cam_logfile ccpp_kinds ccpp_kinds proc~dyn_exchange_constituent_states->ccpp_kinds physics_types physics_types proc~dyn_exchange_constituent_states->physics_types shr_kind_mod shr_kind_mod proc~dyn_exchange_constituent_states->shr_kind_mod vert_coord vert_coord proc~dyn_exchange_constituent_states->vert_coord

Exchange and/or convert constituent states between CAM-SIMA and MPAS. If exchange is .true. and direction is "e" or "export", set MPAS state scalars from physics state constituents. If exchange is .true. and direction is "i" or "import", set physics state constituents from MPAS state scalars. Think of it as "exporting/importing constituent states in CAM-SIMA to/from MPAS". Otherwise, if exchange is .false., no exchange is performed at all. If conversion is .true., appropriate conversion is performed for constituent mixing ratios that have different definitions between CAM-SIMA and MPAS (i.e., dry/moist). Otherwise, if conversion is .false., no conversion is performed at all. This subroutine is intentionally designed to have these elaborate controls due to complications in CAM-SIMA. Some procedures in CAM-SIMA expect constituent states to be dry, while the others expect them to be moist. (KCW, 2024-09-26)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: direction
logical, intent(in) :: exchange
logical, intent(in) :: conversion

Calls

proc~~dyn_exchange_constituent_states~~CallsGraph proc~dyn_exchange_constituent_states dyn_exchange_constituent_states cam_constituents_array cam_constituents_array proc~dyn_exchange_constituent_states->cam_constituents_array check_allocate check_allocate proc~dyn_exchange_constituent_states->check_allocate const_is_dry const_is_dry proc~dyn_exchange_constituent_states->const_is_dry const_is_water_species const_is_water_species proc~dyn_exchange_constituent_states->const_is_water_species endrun endrun proc~dyn_exchange_constituent_states->endrun none~get_variable_pointer mpas_dynamical_core_type%get_variable_pointer proc~dyn_exchange_constituent_states->none~get_variable_pointer pdel pdel proc~dyn_exchange_constituent_states->pdel pdeldry pdeldry proc~dyn_exchange_constituent_states->pdeldry proc~dyn_debug_print dyn_debug_print proc~dyn_exchange_constituent_states->proc~dyn_debug_print proc~dyn_mpas_exchange_halo mpas_dynamical_core_type%dyn_mpas_exchange_halo proc~dyn_exchange_constituent_states->proc~dyn_mpas_exchange_halo proc~dyn_mpas_map_constituent_index mpas_dynamical_core_type%dyn_mpas_map_constituent_index proc~dyn_exchange_constituent_states->proc~dyn_mpas_map_constituent_index proc~dyn_mpas_map_mpas_scalar_index mpas_dynamical_core_type%dyn_mpas_map_mpas_scalar_index proc~dyn_exchange_constituent_states->proc~dyn_mpas_map_mpas_scalar_index proc~reverse reverse proc~dyn_exchange_constituent_states->proc~reverse proc~dyn_mpas_get_variable_pointer_c0 mpas_dynamical_core_type%dyn_mpas_get_variable_pointer_c0 none~get_variable_pointer->proc~dyn_mpas_get_variable_pointer_c0 proc~dyn_mpas_get_variable_pointer_c1 mpas_dynamical_core_type%dyn_mpas_get_variable_pointer_c1 none~get_variable_pointer->proc~dyn_mpas_get_variable_pointer_c1 proc~dyn_mpas_get_variable_pointer_i0 mpas_dynamical_core_type%dyn_mpas_get_variable_pointer_i0 none~get_variable_pointer->proc~dyn_mpas_get_variable_pointer_i0 proc~dyn_mpas_get_variable_pointer_i1 mpas_dynamical_core_type%dyn_mpas_get_variable_pointer_i1 none~get_variable_pointer->proc~dyn_mpas_get_variable_pointer_i1 proc~dyn_mpas_get_variable_pointer_i2 mpas_dynamical_core_type%dyn_mpas_get_variable_pointer_i2 none~get_variable_pointer->proc~dyn_mpas_get_variable_pointer_i2 proc~dyn_mpas_get_variable_pointer_i3 mpas_dynamical_core_type%dyn_mpas_get_variable_pointer_i3 none~get_variable_pointer->proc~dyn_mpas_get_variable_pointer_i3 proc~dyn_mpas_get_variable_pointer_l0 mpas_dynamical_core_type%dyn_mpas_get_variable_pointer_l0 none~get_variable_pointer->proc~dyn_mpas_get_variable_pointer_l0 proc~dyn_mpas_get_variable_pointer_r0 mpas_dynamical_core_type%dyn_mpas_get_variable_pointer_r0 none~get_variable_pointer->proc~dyn_mpas_get_variable_pointer_r0 proc~dyn_mpas_get_variable_pointer_r1 mpas_dynamical_core_type%dyn_mpas_get_variable_pointer_r1 none~get_variable_pointer->proc~dyn_mpas_get_variable_pointer_r1 proc~dyn_mpas_get_variable_pointer_r2 mpas_dynamical_core_type%dyn_mpas_get_variable_pointer_r2 none~get_variable_pointer->proc~dyn_mpas_get_variable_pointer_r2 proc~dyn_mpas_get_variable_pointer_r3 mpas_dynamical_core_type%dyn_mpas_get_variable_pointer_r3 none~get_variable_pointer->proc~dyn_mpas_get_variable_pointer_r3 proc~dyn_mpas_get_variable_pointer_r4 mpas_dynamical_core_type%dyn_mpas_get_variable_pointer_r4 none~get_variable_pointer->proc~dyn_mpas_get_variable_pointer_r4 proc~dyn_mpas_get_variable_pointer_r5 mpas_dynamical_core_type%dyn_mpas_get_variable_pointer_r5 none~get_variable_pointer->proc~dyn_mpas_get_variable_pointer_r5 stringify stringify proc~dyn_debug_print->stringify mpas_dmpar_exch_halo_field mpas_dmpar_exch_halo_field proc~dyn_mpas_exchange_halo->mpas_dmpar_exch_halo_field mpas_pool_get_field mpas_pool_get_field proc~dyn_mpas_exchange_halo->mpas_pool_get_field mpas_pool_get_field_info mpas_pool_get_field_info proc~dyn_mpas_exchange_halo->mpas_pool_get_field_info proc~dyn_mpas_debug_print mpas_dynamical_core_type%dyn_mpas_debug_print proc~dyn_mpas_exchange_halo->proc~dyn_mpas_debug_print proc~stringify stringify proc~dyn_mpas_exchange_halo->proc~stringify proc~dyn_mpas_debug_print->proc~stringify mpas_pool_get_array mpas_pool_get_array proc~dyn_mpas_get_variable_pointer_c0->mpas_pool_get_array mpas_pool_get_config mpas_pool_get_config proc~dyn_mpas_get_variable_pointer_c0->mpas_pool_get_config proc~dyn_mpas_get_pool_pointer mpas_dynamical_core_type%dyn_mpas_get_pool_pointer proc~dyn_mpas_get_variable_pointer_c0->proc~dyn_mpas_get_pool_pointer proc~dyn_mpas_get_variable_pointer_c1->mpas_pool_get_array proc~dyn_mpas_get_variable_pointer_c1->proc~dyn_mpas_get_pool_pointer proc~dyn_mpas_get_variable_pointer_i0->mpas_pool_get_array proc~dyn_mpas_get_variable_pointer_i0->mpas_pool_get_config mpas_pool_get_dimension mpas_pool_get_dimension proc~dyn_mpas_get_variable_pointer_i0->mpas_pool_get_dimension proc~dyn_mpas_get_variable_pointer_i0->proc~dyn_mpas_get_pool_pointer proc~dyn_mpas_get_variable_pointer_i1->mpas_pool_get_array proc~dyn_mpas_get_variable_pointer_i1->mpas_pool_get_dimension proc~dyn_mpas_get_variable_pointer_i1->proc~dyn_mpas_get_pool_pointer proc~dyn_mpas_get_variable_pointer_i2->mpas_pool_get_array proc~dyn_mpas_get_variable_pointer_i2->proc~dyn_mpas_get_pool_pointer proc~dyn_mpas_get_variable_pointer_i3->mpas_pool_get_array proc~dyn_mpas_get_variable_pointer_i3->proc~dyn_mpas_get_pool_pointer proc~dyn_mpas_get_variable_pointer_l0->mpas_pool_get_config proc~dyn_mpas_get_variable_pointer_l0->proc~dyn_mpas_get_pool_pointer proc~dyn_mpas_get_variable_pointer_r0->mpas_pool_get_array proc~dyn_mpas_get_variable_pointer_r0->mpas_pool_get_config proc~dyn_mpas_get_variable_pointer_r0->proc~dyn_mpas_get_pool_pointer proc~dyn_mpas_get_variable_pointer_r1->mpas_pool_get_array proc~dyn_mpas_get_variable_pointer_r1->proc~dyn_mpas_get_pool_pointer proc~dyn_mpas_get_variable_pointer_r2->mpas_pool_get_array proc~dyn_mpas_get_variable_pointer_r2->proc~dyn_mpas_get_pool_pointer proc~dyn_mpas_get_variable_pointer_r3->mpas_pool_get_array proc~dyn_mpas_get_variable_pointer_r3->proc~dyn_mpas_get_pool_pointer proc~dyn_mpas_get_variable_pointer_r4->mpas_pool_get_array proc~dyn_mpas_get_variable_pointer_r4->proc~dyn_mpas_get_pool_pointer proc~dyn_mpas_get_variable_pointer_r5->mpas_pool_get_array proc~dyn_mpas_get_variable_pointer_r5->proc~dyn_mpas_get_pool_pointer mpas_pool_get_subpool mpas_pool_get_subpool proc~dyn_mpas_get_pool_pointer->mpas_pool_get_subpool

Called by

proc~~dyn_exchange_constituent_states~~CalledByGraph proc~dyn_exchange_constituent_states dyn_exchange_constituent_states none~set_physics_state_external set_physics_state_external none~set_physics_state_external->proc~dyn_exchange_constituent_states proc~dyn_init dyn_init proc~dyn_init->proc~dyn_exchange_constituent_states proc~dynamics_to_physics_coupling dynamics_to_physics_coupling proc~dynamics_to_physics_coupling->proc~dyn_exchange_constituent_states proc~dynamics_to_physics_coupling->none~set_physics_state_external proc~physics_to_dynamics_coupling physics_to_dynamics_coupling proc~physics_to_dynamics_coupling->proc~dyn_exchange_constituent_states proc~stepon_run2 stepon_run2 proc~stepon_run2->proc~physics_to_dynamics_coupling proc~stepon_timestep_init stepon_timestep_init proc~stepon_timestep_init->proc~dynamics_to_physics_coupling

Variables

Type Visibility Attributes Name Initial
real(kind=kind_phys), private, pointer :: constituents(:,:,:)
integer, private :: i
integer, private :: ierr
logical, private, allocatable :: is_conversion_needed(:)
logical, private, allocatable :: is_water_species(:)
integer, private, allocatable :: is_water_species_index(:)
integer, private :: j
real(kind=kind_dyn_mpas), private, pointer :: scalars(:,:,:)
real(kind=kind_r8), private, allocatable :: sigma_all_q(:)
character(len=*), private, parameter :: subname = 'dyn_comp::dyn_exchange_constituent_states'

Source Code

    subroutine dyn_exchange_constituent_states(direction, exchange, conversion)
        ! Module(s) from CAM-SIMA.
        use cam_abortutils, only: check_allocate, endrun
        use cam_constituents, only: const_is_dry, const_is_water_species, num_advected
        use cam_logfile, only: debugout_debug, debugout_info
        use physics_types, only: phys_state
        use vert_coord, only: pver
        ! Module(s) from CCPP.
        use cam_ccpp_cap, only: cam_constituents_array
        use ccpp_kinds, only: kind_phys
        ! Module(s) from CESM Share.
        use shr_kind_mod, only: kind_r8 => shr_kind_r8

        character(*), intent(in) :: direction
        logical, intent(in) :: exchange
        logical, intent(in) :: conversion

        character(*), parameter :: subname = 'dyn_comp::dyn_exchange_constituent_states'
        integer :: i, j
        integer :: ierr
        integer, allocatable :: is_water_species_index(:)
        logical, allocatable :: is_conversion_needed(:)
        logical, allocatable :: is_water_species(:)
        real(kind_phys), pointer :: constituents(:, :, :) ! This points to CCPP memory.
        real(kind_r8), allocatable :: sigma_all_q(:)      ! Summation of all water species mixing ratios.
        real(kind_dyn_mpas), pointer :: scalars(:, :, :)  ! This points to MPAS memory.

        call dyn_debug_print(debugout_debug, subname // ' entered')

        select case (trim(adjustl(direction)))
            case ('e', 'export')
                if (exchange) then
                    call dyn_debug_print(debugout_info, 'Setting MPAS state "scalars" from physics state "constituents"')
                end if

                if (conversion) then
                    call dyn_debug_print(debugout_info, 'Converting MPAS state "scalars"')
                end if
            case ('i', 'import')
                if (exchange) then
                    call dyn_debug_print(debugout_info, 'Setting physics state "constituents" from MPAS state "scalars"')
                end if

                if (conversion) then
                    call dyn_debug_print(debugout_info, 'Converting physics state "constituents"')
                end if
            case default
                call endrun('Unsupported exchange direction "' // trim(adjustl(direction)) // '"', subname, __LINE__)
        end select

        nullify(constituents)
        nullify(scalars)

        allocate(is_conversion_needed(num_advected), stat=ierr)
        call check_allocate(ierr, subname, &
            'is_conversion_needed(num_advected)', &
            'dyn_comp', __LINE__)

        allocate(is_water_species(num_advected), stat=ierr)
        call check_allocate(ierr, subname, &
            'is_water_species(num_advected)', &
            'dyn_comp', __LINE__)

        do j = 1, num_advected
            ! All constituent mixing ratios in MPAS are dry.
            ! Therefore, conversion in between is needed for any constituent mixing ratios that are not dry in CAM-SIMA.
            is_conversion_needed(j) = .not. const_is_dry(j)
            is_water_species(j) = const_is_water_species(j)
        end do

        allocate(is_water_species_index(count(is_water_species)), stat=ierr)
        call check_allocate(ierr, subname, &
            'is_water_species_index(count(is_water_species))', &
            'dyn_comp', __LINE__)

        allocate(sigma_all_q(pver), stat=ierr)
        call check_allocate(ierr, subname, &
            'sigma_all_q(pver)', &
            'dyn_comp', __LINE__)

        constituents => cam_constituents_array()

        if (.not. associated(constituents)) then
            call endrun('Failed to find variable "constituents"', subname, __LINE__)
        end if

        call mpas_dynamical_core % get_variable_pointer(scalars, 'state', 'scalars', time_level=1)

        if (trim(adjustl(direction)) == 'e' .or. trim(adjustl(direction)) == 'export') then
            do i = 1, ncells_solve
                if (conversion .and. any(is_conversion_needed)) then
                    ! The summation term of equation 8 in doi:10.1029/2017MS001257.
                    ! Using equation 7 here is not possible because it requires all constituent mixing ratio to be moist
                    ! on the RHS of it. There is no such guarantee in CAM-SIMA.
                    sigma_all_q(:) = reverse(phys_state % pdel(i, :) / phys_state % pdeldry(i, :))
                end if

                ! `j` is indexing into `scalars`, so it is regarded as MPAS scalar index.
                do j = 1, num_advected
                    if (exchange) then
                        ! Vertical index order is reversed between CAM-SIMA and MPAS.
                        scalars(j, :, i) = &
                            real(reverse(constituents(i, :, mpas_dynamical_core % map_constituent_index(j))), kind_dyn_mpas)
                    end if

                    if (conversion .and. is_conversion_needed(mpas_dynamical_core % map_constituent_index(j))) then
                        ! Equation 8 in doi:10.1029/2017MS001257.
                        scalars(j, :, i) = &
                            real(real(scalars(j, :, i), kind_r8) * sigma_all_q(:), kind_dyn_mpas)
                    end if
                end do
            end do
        else
            is_water_species_index(:) = &
                pack([(mpas_dynamical_core % map_mpas_scalar_index(i), i = 1, num_advected)], is_water_species)

            do i = 1, ncells_solve
                if (conversion .and. any(is_conversion_needed)) then
                    ! The summation term of equation 8 in doi:10.1029/2017MS001257.
                    sigma_all_q(:) = reverse(1.0_kind_r8 + sum(real(scalars(is_water_species_index, :, i), kind_r8), 1))
                end if

                ! `j` is indexing into `constituents`, so it is regarded as constituent index.
                do j = 1, num_advected
                    if (exchange) then
                        ! Vertical index order is reversed between CAM-SIMA and MPAS.
                        constituents(i, :, j) = &
                            reverse(real(scalars(mpas_dynamical_core % map_mpas_scalar_index(j), :, i), kind_r8))
                    end if

                    if (conversion .and. is_conversion_needed(j)) then
                        ! Equation 8 in doi:10.1029/2017MS001257.
                        constituents(i, :, j) = &
                            constituents(i, :, j) / sigma_all_q(:)
                    end if
                end do
            end do
        end if

        deallocate(is_conversion_needed)
        deallocate(is_water_species)
        deallocate(is_water_species_index)
        deallocate(sigma_all_q)

        nullify(constituents)
        nullify(scalars)

        if (trim(adjustl(direction)) == 'e' .or. trim(adjustl(direction)) == 'export') then
            ! Because we are injecting data directly into MPAS memory, halo layers need to be updated manually.
            call mpas_dynamical_core % exchange_halo('scalars')
        end if

        call dyn_debug_print(debugout_debug, subname // ' completed')
    end subroutine dyn_exchange_constituent_states