57 character(len=:),
allocatable,
public :: rep_name
66 type(
property_t),
pointer,
public :: property_set => null()
71 real(kind=
dp),
allocatable,
public :: condensed_data_real(:)
76 integer(kind=i_kind),
allocatable,
public :: condensed_data_int(:)
80 logical,
allocatable,
public :: aero_phase_is_at_surface(:)
84 integer(kind=i_kind),
public :: num_env_params = 0
154 integer(kind=c_int) :: aero_rep_type
156 integer(kind=c_int) :: aero_rep_solver_id = 0
158 integer(kind=c_int) :: cell_id = 1
160 type(c_ptr) :: update_data
206 integer(kind=i_kind),
intent(in) :: spec_state_id
220 integer,
intent(in) :: comm
233 character,
intent(inout) :: buffer(:)
235 integer,
intent(inout) :: pos
237 integer,
intent(in) :: comm
250 character,
intent(inout) :: buffer(:)
252 integer,
intent(inout) :: pos
254 integer,
intent(in) :: comm
268 integer(kind=i_kind) :: state_size
289 character(len=*),
optional,
intent(in) :: phase_name
291 integer(kind=i_kind),
optional,
intent(in) :: tracer_type
293 character(len=*),
optional,
intent(in) ::
spec_name
295 logical,
optional,
intent(in) :: phase_is_at_surface
321 integer(kind=i_kind) :: spec_id
325 character(len=*),
intent(in) :: unique_name
337 character(len=:),
allocatable ::
spec_name
341 character(len=*),
intent(in) :: unique_name
357 character(len=*),
intent(in) :: phase_name
359 logical,
intent(in),
optional :: is_at_surface
376 integer(kind=i_kind),
intent(in) :: phase_id
426 subroutine load(this, json, j_obj)
431 type(json_core),
pointer,
intent(in) :: json
433 type(json_value),
pointer,
intent(in) :: j_obj
435 type(json_value),
pointer :: child, next
436 character(kind=json_ck, len=:),
allocatable :: key, unicode_str_val
437 integer(kind=json_ik) :: var_type
438 logical :: found_name
443 if (.not.
allocated(this%rep_name)) &
444 this%rep_name =
"unknown aerosol representation"
450 call json%get_child(j_obj, child)
451 do while (
associated(child))
452 call json%info(child, name=key, var_type=var_type)
455 if (key.eq.
"name")
then
456 call assert_msg(196193896, var_type.eq.json_string, &
457 "Received non-string value for aerosol rep name")
458 call json%get(child, unicode_str_val)
459 this%rep_name = unicode_str_val
463 else if (key.ne.
"type")
then
464 call this%property_set%load(json, child, .false., this%rep_name)
467 call json%get_next(child, next)
470 call assert_msg(420903951, found_name, &
471 "Received unnamed aerosol representation.")
473 subroutine load(this)
478 call warn_msg(433045149,
"No support for input files")
489 character(len=:),
allocatable ::
get_name
504 integer(kind=i_kind),
allocatable ::
phase_ids(:)
508 character(len=*),
intent(in) :: phase_name
510 logical,
intent(in),
optional :: is_at_surface
512 integer(kind=i_kind) :: num_instances, i_instance, i_phase
514 num_instances = this%num_phase_instances(phase_name, is_at_surface)
516 if (
present(is_at_surface))
then
517 if (is_at_surface)
then
519 do i_phase = 1,
size(this%aero_phase)
520 if (this%aero_phase(i_phase)%val%name().eq. phase_name .and. &
521 this%aero_phase_is_at_surface(i_phase))
then
523 i_instance = i_instance + 1
528 do i_phase = 1,
size(this%aero_phase)
529 if (this%aero_phase(i_phase)%val%name().eq. phase_name .and. &
530 .not. this%aero_phase_is_at_surface(i_phase))
then
532 i_instance = i_instance + 1
538 do i_phase = 1,
size(this%aero_phase)
539 if (this%aero_phase(i_phase)%val%name().eq.phase_name)
then
541 i_instance = i_instance + 1
545 call assert(642387392, num_instances == i_instance-1)
558 integer,
intent(in) :: comm
575 character,
intent(inout) :: buffer(:)
577 integer,
intent(inout) :: pos
579 integer,
intent(in) :: comm
582 integer :: prev_position
588 call assert(257024095, &
589 pos - prev_position <= this%pack_size(comm))
602 character,
intent(inout) :: buffer(:)
604 integer,
intent(inout) :: pos
606 integer,
intent(in) :: comm
609 integer :: prev_position
616 call assert(954732699, &
617 pos - prev_position <= this%pack_size(comm))
630 integer(kind=i_kind),
optional :: file_unit
632 integer(kind=i_kind) :: f_unit
636 if (
present(file_unit)) f_unit = file_unit
637 write(f_unit,*)
"*** Aerosol Representation: ",trim(this%rep_name),
" ***"
638 if (
associated(this%property_set))
call this%property_set%print(f_unit)
639 if (
allocated(this%condensed_data_int)) &
640 write(f_unit,*)
" *** condensed data int: ",this%condensed_data_int(:)
641 if (
allocated(this%condensed_data_real)) &
642 write(f_unit,*)
" *** condensed data real: ",this%condensed_data_real(:)
666 if (
associated(this%val))
deallocate(this%val)
678 integer(kind=i_kind) :: i
692 integer(kind=c_int) :: aero_rep_type
696 aero_rep_type = this%aero_rep_type
706 integer(kind=c_int) :: cell_id
710 cell_id = this%cell_id
720 type(c_ptr) :: update_data
724 update_data = this%update_data
737 integer,
intent(in),
optional :: comm
742 if (
present(comm))
then
745 l_comm = mpi_comm_world
753 this%internal_pack_size(l_comm)
768 character,
intent(inout) :: buffer(:)
770 integer,
intent(inout) :: pos
772 integer,
intent(in),
optional :: comm
775 integer :: prev_position, l_comm
777 if (
present(comm))
then
780 l_comm = mpi_comm_world
785 int(this%aero_rep_type, kind=
i_kind), l_comm)
787 int(this%aero_rep_solver_id, kind=
i_kind), &
789 call this%internal_bin_pack(buffer, pos, l_comm)
790 call assert(538137635, &
791 pos - prev_position <= this%pack_size(l_comm))
804 character,
intent(inout) :: buffer(:)
806 integer,
intent(inout) :: pos
808 integer,
intent(in),
optional :: comm
811 integer :: prev_position, l_comm
812 integer(kind=i_kind) :: temp_int
814 if (
present(comm))
then
817 l_comm = mpi_comm_world
822 this%aero_rep_type = int(temp_int, kind=c_int)
824 this%aero_rep_solver_id = int(temp_int, kind=c_int)
825 call this%internal_bin_unpack(buffer, pos, l_comm)
826 call assert(257567920, &
827 pos - prev_position <= this%pack_size(l_comm))
840 integer(kind=i_kind),
optional :: file_unit
842 integer(kind=i_kind) :: f_unit
846 if (
present(file_unit)) f_unit = file_unit
848 write(f_unit,*)
"*** Aerosol representation update data ***"
849 write(f_unit,*)
"Aerosol representation type", this%aero_rep_type
850 write(f_unit,*)
"Aerosol representation solver id", this%aero_rep_solver_id
Get the size of the section of the camp_camp_state::camp_state_t::state_var array required for this a...
Initialize the aerosol representation data, validating component data and loading any required inform...
Extending-type binary pack function (Internal use only)
Extending-type binary unpack function (Internal use only)
Extending-type binary pack size (internal use only)
Get the number of Jacobian elements used in calculations of aerosol mass, volume, number,...
Get the number of instances of a specified aerosol phase.
Get the non-unique name of a chemical species by its unique name.
Get a species id on the camp_camp_state::camp_state_t::state_var array by unique name....
Get a list of unique names for each element on the camp_camp_state::camp_state_t::state_var array for...
The abstract aero_phase_data_t structure and associated subroutines.
subroutine bin_unpack(this, buffer, pos, comm)
Unpack the given value from the buffer, advancing position.
character(len=:) function, allocatable get_name(this)
Get the aerosol phase name.
subroutine ptr_finalize_array(this)
Finalize an array of pointers to aerosol phase data.
subroutine bin_pack(this, buffer, pos, comm)
Pack the given value to the buffer, advancing position.
subroutine load(this, json, j_obj)
Load species from an input file.
integer(kind=i_kind) function pack_size(this, comm)
Determine the size of a binary required to pack the aerosol representation data.
subroutine ptr_finalize(this)
Finalize a pointer to aerosol phase data.
subroutine do_print(this, file_unit)
Print out the aerosol phase data.
elemental subroutine dereference(this)
Dereference a pointer to aerosol phase data.
The abstract aero_rep_data_t structure and associated subroutines.
subroutine do_aero_rep_update_data_print(this, file_unit)
Print the update data.
integer(kind=i_kind) function, dimension(:), allocatable phase_ids(this, phase_name, is_at_surface)
Get a set of ids for all instances of a phase in this aerosol representation for use during solving.
type(c_ptr) function aero_rep_update_data_get_data(this)
Get the update data.
integer(kind=i_kind) function aero_rep_update_data_pack_size(this, comm)
Determine the size of a binary required to pack the reaction data.
subroutine do_print(this, file_unit)
Print the aerosol representation data.
subroutine aero_rep_update_data_bin_pack(this, buffer, pos, comm)
Pack the given value to the buffer, advancing position.
subroutine ptr_finalize(this)
Finalize a pointer to an aerosol representation.
integer(kind=i_kind) function pack_size(this, comm)
Determine the size of a binary required to pack the aerosol representation data.
subroutine load(this, json, j_obj)
Load an aerosol representation from an input file.
subroutine aero_rep_update_data_bin_unpack(this, buffer, pos, comm)
Unpack the given value from the buffer, advancing position.
subroutine bin_unpack(this, buffer, pos, comm)
Unpack the given value from the buffer, advancing position.
elemental subroutine dereference(this)
Deference a pointer to an aerosol representation.
integer(kind=c_int) function aero_rep_update_data_get_type(this)
Get the update data aerosol representation type.
subroutine bin_pack(this, buffer, pos, comm)
Pack the given value to the buffer, advancing position.
character(len=:) function, allocatable get_name(this)
Get the name of the aerosol representation.
subroutine ptr_finalize_array(this)
Finalize an array of pointers to aerosol representations.
integer(kind=c_int) function aero_rep_update_data_get_cell_id(this)
Get the grid cell id to update.
The camp_state_t structure and associated subroutines.
The chem_spec_data_t structure and associated subroutines.
logical function get_type(this, spec_name, spec_type)
Get a species type by species name. Returns true if the species is found or false otherwise.
integer, parameter dp
Kind of a double precision real number.
integer, parameter i_kind
Kind of an integer.
Wrapper functions for MPI.
subroutine camp_mpi_pack_integer_array(buffer, position, val, comm)
Packs the given value into the buffer, advancing position.
subroutine camp_mpi_pack_real_array(buffer, position, val, comm)
Packs the given value into the buffer, advancing position.
subroutine camp_mpi_unpack_integer_array(buffer, position, val, comm)
Unpacks the given value from the buffer, advancing position.
subroutine camp_mpi_unpack_integer(buffer, position, val, comm)
Unpacks the given value from the buffer, advancing position.
integer function camp_mpi_pack_size_real_array(val, comm)
Determines the number of bytes required to pack the given value.
integer function camp_mpi_pack_size_integer_array(val, comm)
Determines the number of bytes required to pack the given value.
subroutine camp_mpi_pack_integer(buffer, position, val, comm)
Packs the given value into the buffer, advancing position.
integer function camp_mpi_pack_size_integer(val, comm)
Determines the number of bytes required to pack the given value.
subroutine camp_mpi_unpack_real_array(buffer, position, val, comm)
Unpacks the given value from the buffer, advancing position.
The property_t structure and associated subroutines.
Common utility subroutines.
subroutine die_msg(code, error_msg)
Error immediately.
Pointer type for building arrays.
Pointer to aero_rep_data_t extending types.
Abstract aerosol representation data type.
String type for building arrays of string of various size.