Skip to content

Commit

Permalink
commit r1970_prepare_vn1.0_part2 to trunk. There is still an issue wi…
Browse files Browse the repository at this point in the history
…th forcing and checkpointing but this commit adds a lot of new funtionality and corrects a lot of bugs.

Merged into /main/trunk: /main/branches/pkg/adrianhill/r1970_prepare_vn1.0_part2@2006 cf. /main/trunk@1970


git-svn-id: https://code.metoffice.gov.uk/svn/monc/main/trunk@2010 0f676ef4-b20c-4647-9485-21614760d15f
  • Loading branch information
adrianhill committed Nov 12, 2016
1 parent 7eb77e2 commit 8d45602
Show file tree
Hide file tree
Showing 40 changed files with 1,860 additions and 262 deletions.
57 changes: 56 additions & 1 deletion components/casim/src/casim.F90
Original file line number Diff line number Diff line change
@@ -1,7 +1,9 @@
!> Implimentation of CASIM microphysics
module casim_mod
use datadefn_mod, only : DEFAULT_PRECISION
use monc_component_mod, only : component_descriptor_type
use monc_component_mod, only : component_descriptor_type, &
COMPONENT_ARRAY_FIELD_TYPE, COMPONENT_DOUBLE_DATA_TYPE, &
component_field_value_type, component_field_information_type
use state_mod, only : FORWARD_STEPPING, model_state_type
use grids_mod, only : Z_INDEX, Y_INDEX, X_INDEX
use science_constants_mod
Expand Down Expand Up @@ -30,6 +32,8 @@ module casim_mod
private
#endif

real(kind=DEFAULT_PRECISION), dimension(:,:), allocatable :: surface_precip

REAL(wp), allocatable :: theta(:,:,:), pressure(:,:,:), &
z_half(:,:,:), z_centre(:,:,:), dz(:,:,:), qv(:,:,:),qc(:,:,:) &
, nc(:,:,:), qr(:,:,:), nr(:,:,:), m3r(:,:,:),rho(:,:,:) &
Expand Down Expand Up @@ -108,13 +112,59 @@ type(component_descriptor_type) function casim_get_descriptor()
casim_get_descriptor%version=0.1
casim_get_descriptor%initialisation=>initialisation_callback
casim_get_descriptor%timestep=>timestep_callback

casim_get_descriptor%field_value_retrieval=>field_value_retrieval_callback
casim_get_descriptor%field_information_retrieval=>field_information_retrieval_callback

allocate(casim_get_descriptor%published_fields(1))

casim_get_descriptor%published_fields(1)="surface_precip_local"

end function casim_get_descriptor

subroutine field_information_retrieval_callback(current_state, name, field_information)
type(model_state_type), target, intent(inout) :: current_state
character(len=*), intent(in) :: name
type(component_field_information_type), intent(out) :: field_information

field_information%field_type=COMPONENT_ARRAY_FIELD_TYPE
field_information%data_type=COMPONENT_DOUBLE_DATA_TYPE
field_information%number_dimensions=2
field_information%dimension_sizes(1)=current_state%local_grid%size(Y_INDEX)
field_information%dimension_sizes(2)=current_state%local_grid%size(X_INDEX)

field_information%enabled=.true.

end subroutine field_information_retrieval_callback

!> Field value retrieval callback, this returns the value of a specific published field
!! @param current_state Current model state
!! @param name The name of the field to retrieve the value for
!! @param field_value Populated with the value of the field
subroutine field_value_retrieval_callback(current_state, name, field_value)
type(model_state_type), target, intent(inout) :: current_state
character(len=*), intent(in) :: name
type(component_field_value_type), intent(out) :: field_value

integer :: i

if (name .eq. "surface_precip_local") then
allocate(field_value%real_2d_array(current_state%local_grid%size(Y_INDEX), &
current_state%local_grid%size(X_INDEX)))
field_value%real_2d_array(:,:)=surface_precip(:,:)
end if

end subroutine field_value_retrieval_callback

!> The initialisation callback sets up the microphysics
!! @param current_state The current model state
subroutine initialisation_callback(current_state)
type(model_state_type), target, intent(inout) :: current_state

integer :: y_size_local, x_size_local
y_size_local = current_state%local_grid%size(Y_INDEX)
x_size_local = current_state%local_grid%size(X_INDEX)

call read_configuration(current_state)

ils=1
Expand Down Expand Up @@ -209,6 +259,8 @@ subroutine initialisation_callback(current_state)
allocate(dActiveSolNumber(kte,1,1))
allocate(dActiveInsolNumber(kte,1,1))

allocate(surface_precip(y_size_local, x_size_local))

call set_mphys_switches(option,aerosol_option)
call mphys_init

Expand Down Expand Up @@ -365,6 +417,9 @@ subroutine timestep_callback(current_state)
ActiveInsolNumber = 0.0
dActiveInsolNumber = 0.0

! initialise surface precip to zero...
surface_precip = 0.0

i_here=icol
j_here=jcol
theta(:,1,1) = current_state%zth%data(:, jcol, icol) + current_state%global_grid%configuration%vertical%thref(:)
Expand Down
1 change: 1 addition & 0 deletions components/componentheaders.static
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@ use kidreader_mod, only : kidreader_get_descriptor
use lowerbc_mod, only : lowerbc_get_descriptor
use meanprofiles_mod, only : meanprofiles_get_descriptor
use modelsynopsis_mod, only : modelsynopsis_get_descriptor
use petsc_solver_mod, only : petsc_solver_get_descriptor
use pressuresource_mod, only : pressuresource_get_descriptor
use profile_diagnostics_mod, only : profile_diagnostics_get_descriptor
use pstep_mod, only : pstep_get_descriptor
Expand Down
1 change: 1 addition & 0 deletions components/componentregistrations.static
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@ call add_component(component_descriptions, kidreader_get_descriptor())
call add_component(component_descriptions, lowerbc_get_descriptor())
call add_component(component_descriptions, meanprofiles_get_descriptor())
call add_component(component_descriptions, modelsynopsis_get_descriptor())
call add_component(component_descriptions, petsc_solver_get_descriptor())
call add_component(component_descriptions, pressuresource_get_descriptor())
call add_component(component_descriptions, profile_diagnostics_get_descriptor())
call add_component(component_descriptions, pstep_get_descriptor())
Expand Down
Loading

0 comments on commit 8d45602

Please sign in to comment.