-
Notifications
You must be signed in to change notification settings - Fork 20
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
- Loading branch information
1 parent
603de70
commit 0b12ec8
Showing
16 changed files
with
911 additions
and
10 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,82 @@ | ||
! Copyright (C) 2025 National Center for Atmospheric Research, | ||
! SPDX-License-Identifier: Apache-2.0 | ||
module musica_ccpp_aerosol_model | ||
|
||
implicit none | ||
private | ||
|
||
public :: aerosol_model_t | ||
|
||
!> Defines the configuration of any aerosol package (using | ||
!! any aerosol representation) based on user specification. These values are | ||
!! set during initialization and do not vary during the simulation. | ||
!! | ||
!! Each aerosol package (e.g., MAM, CARMA, etc) must extend the abstract | ||
!! aerosol_model_t class to define the details of their configuration. Any | ||
!! package must implement each of the deferred procedures of the abstract | ||
!! aerosol_model_t class, may include additional private data members and | ||
!! type-bound procedures, and may override functions of the abstract class. | ||
!! | ||
!! Please see the musica_ccpp_stub_aerosol_model module for an example of how the | ||
!! aerosol_model_t class can be extended for a specific aerosol package. | ||
type, abstract :: aerosol_model_t | ||
contains | ||
procedure(aerosol_model_create_state), deferred :: create_state | ||
procedure(aerosol_model_optical_properties), deferred :: optical_properties | ||
end type aerosol_model_t | ||
|
||
abstract interface | ||
|
||
!> Returns a new instance of the aerosol state for the aerosol model. | ||
!! The aerosol state is used to store the time-and-space varying aerosol | ||
!! properties for the aerosol model. | ||
!! @param this The aerosol model instance. | ||
!! @param number_of_columns The number of columns in the model grid. | ||
!! @param number_of_levels The number of levels in the model grid. | ||
!! @param error_message The error message if an error occurs. | ||
!! @param error_code The error code if an error occurs. | ||
!! @return The aerosol state instance. | ||
function aerosol_model_create_state(this, number_of_columns, number_of_levels, & | ||
error_message, error_code) result(aerosol_state) | ||
use musica_ccpp_aerosol_state, only: aerosol_state_t | ||
import :: aerosol_model_t | ||
class(aerosol_model_t), intent(in) :: this | ||
integer, intent(in) :: number_of_columns | ||
integer, intent(in) :: number_of_levels | ||
character(len=512), intent(out) :: error_message | ||
integer, intent(out) :: error_code | ||
class(aerosol_state_t), pointer :: aerosol_state | ||
end function aerosol_model_create_state | ||
|
||
!> Computes the optical properties of the aerosol for the given state and | ||
!! wavelengths. | ||
!! @param this The aerosol model instance. | ||
!! @param state The aerosol state instance. | ||
!! @param wavelengths The wavelengths at which to compute the optical properties. | ||
!! @param error_message The error message if an error occurs. | ||
!! @param error_code The error code if an error occurs. | ||
!! @param extinction Parameterized specific extinction (m^2/kg) [column, level, wavelength]. | ||
!! @param absorption Parameterized specific absorption (m^2/kg) [column, level, wavelength]. | ||
!! @param scattering Single scattering albedo (unitless) [column, level, wavelength]. | ||
!! @param asymmetry_factor Asymmetry factor (unitless) [column, level, wavelength]. | ||
subroutine aerosol_model_optical_properties(this, state, wavelengths, & | ||
error_message, error_code, extinction, absorption, scattering, & | ||
asymmetry_factor) | ||
use ccpp_kinds, only: rk => kind_phys | ||
use musica_ccpp_aerosol_state, only: aerosol_state_t | ||
use musica_ccpp_grid, only: grid_t | ||
import :: aerosol_model_t | ||
class(aerosol_model_t), intent(in) :: this | ||
class(aerosol_state_t), intent(in) :: state | ||
class(grid_t), intent(in) :: wavelengths | ||
character(len=512), intent(out) :: error_message | ||
integer, intent(out) :: error_code | ||
real(rk), optional, intent(out) :: extinction(:,:,:) | ||
real(rk), optional, intent(out) :: absorption(:,:,:) | ||
real(rk), optional, intent(out) :: scattering(:,:,:) | ||
real(rk), optional, intent(out) :: asymmetry_factor(:,:,:) | ||
end subroutine aerosol_model_optical_properties | ||
|
||
end interface | ||
|
||
end module musica_ccpp_aerosol_model |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,15 @@ | ||
! Copyright (C) 2025 National Center for Atmospheric Research, | ||
! SPDX-License-Identifier: Apache-2.0 | ||
module musica_ccpp_aerosol_state | ||
|
||
implicit none | ||
private | ||
|
||
public :: aerosol_state_t | ||
|
||
!> Defines the state of an aerosol system according to | ||
!! the aerosol representation of a specific aerosol package. | ||
type, abstract :: aerosol_state_t | ||
end type aerosol_state_t | ||
|
||
end module musica_ccpp_aerosol_state |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,6 @@ | ||
The stub aerosol model | ||
====================== | ||
|
||
The files in this folder define a stub aerosol model, primarily for use during | ||
development. Functions of the stub aerosol classes return values corresponding | ||
to the absence of aerosols. |
155 changes: 155 additions & 0 deletions
155
schemes/musica/aerosol_stub/musica_ccpp_stub_aerosol_model.F90
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,155 @@ | ||
! Copyright (C) 2025 National Center for Atmospheric Research, | ||
! SPDX-License-Identifier: Apache-2.0 | ||
module musica_ccpp_stub_aerosol_model | ||
|
||
use musica_ccpp_aerosol_model, only: aerosol_model_t | ||
|
||
implicit none | ||
private | ||
|
||
public :: stub_aerosol_model_t, stub_aerosol_model_parameters_t, & | ||
STUB_AEROSOL_INVALID_DIMENSION, STUB_AEROSOL_INVALID_STATE_TYPE | ||
|
||
!> @brief stub_aerosol_model_parameters_t defines the parameters for the | ||
!! stub aerosol model. (This model assumes no aerosols are present in | ||
!! the atmosphere, and therefore has no parameters.) | ||
type :: stub_aerosol_model_parameters_t | ||
end type stub_aerosol_model_parameters_t | ||
|
||
!> @brief stub_aerosol_model_t defines the configuration of a simplified | ||
!! aerosol package, which assumes no aerosols are present in the | ||
!! atmosphere. | ||
type, extends(aerosol_model_t) :: stub_aerosol_model_t | ||
contains | ||
procedure :: create_state => stub_aerosol_model_create_state | ||
procedure :: optical_properties => stub_aerosol_model_optical_properties | ||
end type stub_aerosol_model_t | ||
|
||
interface stub_aerosol_model_t | ||
module procedure stub_aerosol_model_constructor | ||
end interface stub_aerosol_model_t | ||
|
||
integer, parameter :: STUB_AEROSOL_INVALID_DIMENSION = 1 | ||
integer, parameter :: STUB_AEROSOL_INVALID_STATE_TYPE = 2 | ||
|
||
contains | ||
|
||
!> @brief Constructor for stub_aerosol_model_t | ||
!! @param parameters The parameters for the stub aerosol model. | ||
!! @param error_message The error message if an error occurs. | ||
!! @param error_code The error code if an error occurs. | ||
!! @return The stub aerosol model instance. | ||
function stub_aerosol_model_constructor(parameters, error_message, & | ||
error_code) result(model) | ||
type(stub_aerosol_model_t), pointer :: model | ||
class(stub_aerosol_model_parameters_t), intent(in) :: parameters | ||
character(len=512), intent(out) :: error_message | ||
integer, intent(out) :: error_code | ||
error_message = '' | ||
error_code = 0 | ||
allocate(model) | ||
end function stub_aerosol_model_constructor | ||
|
||
!> @brief Create a new aerosol state for the stub aerosol model. | ||
!! @param this The stub aerosol model instance. | ||
!! @param number_of_columns The number of columns in the model grid. | ||
!! @param number_of_levels The number of levels in the model grid. | ||
!! @param error_message The error message if an error occurs. | ||
!! @param error_code The error code if an error occurs. | ||
!! @return The aerosol state instance. | ||
function stub_aerosol_model_create_state(this, number_of_columns, & | ||
number_of_levels, error_message, error_code) result(aerosol_state) | ||
use musica_ccpp_aerosol_state, only: aerosol_state_t | ||
use musica_ccpp_stub_aerosol_state, only: stub_aerosol_state_t | ||
class(stub_aerosol_model_t), intent(in) :: this | ||
integer, intent(in) :: number_of_columns | ||
integer, intent(in) :: number_of_levels | ||
character(len=512), intent(out) :: error_message | ||
integer, intent(out) :: error_code | ||
class(aerosol_state_t), pointer :: aerosol_state | ||
error_message = '' | ||
error_code = 0 | ||
! Create a new aerosol state for the stub aerosol model | ||
aerosol_state => stub_aerosol_state_t(number_of_columns, number_of_levels) | ||
end function stub_aerosol_model_create_state | ||
|
||
!> @brief Compute the optical properties of the aerosol for the stub aerosol model. | ||
!! @param this The stub aerosol model instance. | ||
!! @param state The aerosol state instance. | ||
!! @param wavelengths The wavelengths at which to compute the optical properties. | ||
!! @param error_message The error message if an error occurs. | ||
!! @param error_code The error code if an error occurs. | ||
!! @param extinction Parameterized specific extinction (m^2/kg) [column, level, wavelength]. | ||
!! @param absorption Parameterized specific absorption (m^2/kg) [column, level, wavelength]. | ||
!! @param scattering Single scattering albedo (unitless) [column, level, wavelength]. | ||
!! @param asymmetry_factor Asymmetry factor (unitless) [column, level, wavelength]. | ||
subroutine stub_aerosol_model_optical_properties(this, state, wavelengths, & | ||
error_message, error_code, extinction, absorption, scattering, & | ||
asymmetry_factor) | ||
use ccpp_kinds, only: rk => kind_phys | ||
use musica_ccpp_aerosol_state, only: aerosol_state_t | ||
use musica_ccpp_grid, only: grid_t | ||
use musica_ccpp_stub_aerosol_state, only: stub_aerosol_state_t | ||
class(stub_aerosol_model_t), intent(in) :: this | ||
class(aerosol_state_t), intent(in) :: state | ||
class(grid_t), intent(in) :: wavelengths | ||
character(len=512), intent(out) :: error_message | ||
integer, intent(out) :: error_code | ||
real(rk), optional, intent(out) :: extinction(:,:,:) | ||
real(rk), optional, intent(out) :: absorption(:,:,:) | ||
real(rk), optional, intent(out) :: scattering(:,:,:) | ||
real(rk), optional, intent(out) :: asymmetry_factor(:,:,:) | ||
error_message = '' | ||
error_code = 0 | ||
select type(state) | ||
class is (stub_aerosol_state_t) | ||
! Compute the optical properties of the aerosol | ||
! (This model assumes no aerosols are present in the atmosphere, | ||
! so the optical properties are set to zero.) | ||
if (present(extinction)) then | ||
if (size(extinction, 1) /= state%number_of_columns() .or. & | ||
size(extinction, 2) /= state%number_of_levels() .or. & | ||
size(extinction, 3) /= wavelengths%number_of_sections()) then | ||
error_message = 'Invalid dimensions for extinction' | ||
error_code = STUB_AEROSOL_INVALID_DIMENSION | ||
return | ||
end if | ||
extinction = 0.0_rk | ||
end if | ||
if (present(absorption)) then | ||
if (size(absorption, 1) /= state%number_of_columns() .or. & | ||
size(absorption, 2) /= state%number_of_levels() .or. & | ||
size(absorption, 3) /= wavelengths%number_of_sections()) then | ||
error_message = 'Invalid dimensions for absorption' | ||
error_code = STUB_AEROSOL_INVALID_DIMENSION | ||
return | ||
end if | ||
absorption = 0.0_rk | ||
end if | ||
if (present(scattering)) then | ||
if (size(scattering, 1) /= state%number_of_columns() .or. & | ||
size(scattering, 2) /= state%number_of_levels() .or. & | ||
size(scattering, 3) /= wavelengths%number_of_sections()) then | ||
error_message = 'Invalid dimensions for scattering' | ||
error_code = STUB_AEROSOL_INVALID_DIMENSION | ||
return | ||
end if | ||
scattering = 0.0_rk | ||
end if | ||
if (present(asymmetry_factor)) then | ||
if (size(asymmetry_factor, 1) /= state%number_of_columns() .or. & | ||
size(asymmetry_factor, 2) /= state%number_of_levels() .or. & | ||
size(asymmetry_factor, 3) /= wavelengths%number_of_sections()) then | ||
error_message = 'Invalid dimensions for asymmetry factor' | ||
error_code = STUB_AEROSOL_INVALID_DIMENSION | ||
return | ||
end if | ||
asymmetry_factor = 0.0_rk | ||
end if | ||
class default | ||
error_message = 'Invalid aerosol state type' | ||
error_code = STUB_AEROSOL_INVALID_STATE_TYPE | ||
end select | ||
end subroutine stub_aerosol_model_optical_properties | ||
|
||
end module musica_ccpp_stub_aerosol_model |
59 changes: 59 additions & 0 deletions
59
schemes/musica/aerosol_stub/musica_ccpp_stub_aerosol_state.F90
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,59 @@ | ||
! Copyright (C) 2025 National Center for Atmospheric Research, | ||
! SPDX-License-Identifier: Apache-2.0 | ||
module musica_ccpp_stub_aerosol_state | ||
|
||
use musica_ccpp_aerosol_state, only: aerosol_state_t | ||
|
||
implicit none | ||
private | ||
|
||
public :: stub_aerosol_state_t | ||
|
||
!> stub_aerosol_state_t defines the state of an aerosol system according to | ||
!! the aerosol representation of the stub aerosol package. | ||
type, extends(aerosol_state_t) :: stub_aerosol_state_t | ||
integer :: number_of_columns_ = 0 !< The number of columns in the model grid | ||
integer :: number_of_levels_ = 0 !< The number of levels in the model grid | ||
contains | ||
procedure :: number_of_columns => stub_aerosol_state_number_of_columns | ||
procedure :: number_of_levels => stub_aerosol_state_number_of_levels | ||
end type stub_aerosol_state_t | ||
|
||
interface stub_aerosol_state_t | ||
module procedure stub_aerosol_state_constructor | ||
end interface stub_aerosol_state_t | ||
|
||
contains | ||
|
||
!> @brief Constructor for stub_aerosol_state_t | ||
!! @param number_of_columns The number of columns in the model grid. | ||
!! @param number_of_levels The number of levels in the model grid. | ||
!! @return The stub aerosol state instance. | ||
function stub_aerosol_state_constructor(number_of_columns, number_of_levels) result(state) | ||
type(stub_aerosol_state_t), pointer :: state | ||
integer, intent(in) :: number_of_columns | ||
integer, intent(in) :: number_of_levels | ||
allocate(state) | ||
state%number_of_columns_ = number_of_columns | ||
state%number_of_levels_ = number_of_levels | ||
end function stub_aerosol_state_constructor | ||
|
||
!> @brief Returns the number of columns in the model grid. | ||
!! @param this The stub aerosol state instance. | ||
!! @return The number of columns in the model grid. | ||
function stub_aerosol_state_number_of_columns(this) result(number_of_columns) | ||
class(stub_aerosol_state_t), intent(in) :: this | ||
integer :: number_of_columns | ||
number_of_columns = this%number_of_columns_ | ||
end function stub_aerosol_state_number_of_columns | ||
|
||
!> @brief Returns the number of levels in the model grid. | ||
!! @param this The stub aerosol state instance. | ||
!! @return The number of levels in the model grid. | ||
function stub_aerosol_state_number_of_levels(this) result(number_of_levels) | ||
class(stub_aerosol_state_t), intent(in) :: this | ||
integer :: number_of_levels | ||
number_of_levels = this%number_of_levels_ | ||
end function stub_aerosol_state_number_of_levels | ||
|
||
end module musica_ccpp_stub_aerosol_state |
Oops, something went wrong.