1 !WRF:MEDIATION_LAYER:SOLVER
3 MODULE module_after_all_rk_steps
7 ! This subroutine is called once per domain per time step. It is outside
8 ! of and after the end of the Runge-Kutta time steps, after the calls to
9 ! the explicit moisture driver, and after the polar filtering calls. The
10 ! variables in here are all up-to-date with the end of this current time
14 SUBROUTINE after_all_rk_steps ( grid, config_flags, &
15 moist, chem, tracer, scalar, &
16 th_phy, pi_phy, p_phy, &
18 curr_secs, curr_secs2, &
20 ids, ide, jds, jde, kds, kde, &
21 ims, ime, jms, jme, kms, kme, &
22 ips, ipe, jps, jpe, kps, kpe, &
23 imsx, imex, jmsx, jmex, kmsx, kmex, &
24 ipsx, ipex, jpsx, jpex, kpsx, kpex, &
25 imsy, imey, jmsy, jmey, kmsy, kmey, &
26 ipsy, ipey, jpsy, jpey, kpsy, kpey )
29 !=============================================================
30 ! USE Association for Generic WRF Infrastructure
31 !=============================================================
33 ! Pick up the number of members for each of the 4d arrays - for declaration purposes.
35 USE module_state_description, ONLY: num_moist, num_chem, num_tracer, num_scalar
37 ! This gives us the type definition for grid (domain)
39 USE module_domain, ONLY : domain
41 ! All of the information from the namelist is in config_flags. The
42 ! type declaration for this puppy must be available.
44 USE module_configure, ONLY : grid_config_rec_type
47 ! Ensure some of the fancy diagnostics variables that need to
48 ! talk to other patches can do so.
50 USE module_dm, ONLY : &
51 local_communicator, mytask, ntasks, ntasks_x, ntasks_y &
52 ,local_communicator_periodic, wrf_dm_maxval
54 USE module_comm_dm, ONLY : &
55 halo_em_phys_w_sub, halo_em_phys_hcw_sub
58 !=============================================================
59 ! USE Association for the Diagnostic Packages
60 !=============================================================
62 USE module_diagnostics_driver, ONLY : diagnostics_driver
68 !=============================================================
69 ! Subroutine Arguments
70 !=============================================================
72 ! Arguments passed in. All of the diagnostics are part of the grid structure, so
73 ! even though we are not changing any of the fundamental variables, we are computing
74 ! the diagnostics. Therefore grid is INOUT.
76 TYPE ( domain ), INTENT(INOUT) :: grid
78 ! We are not changing any of the namelist settings.
80 TYPE ( grid_config_rec_type ), INTENT(IN) :: config_flags
82 ! The 4d arrays are input only, no mods to them.
84 REAL , DIMENSION(ims:ime,kms:kme,jms:jme,num_moist ) , INTENT(IN) :: moist
85 REAL , DIMENSION(ims:ime,kms:kme,jms:jme,num_chem ) , INTENT(IN) :: chem
86 REAL , DIMENSION(ims:ime,kms:kme,jms:jme,num_tracer) , INTENT(IN) :: tracer
87 REAL , DIMENSION(ims:ime,kms:kme,jms:jme,num_scalar) , INTENT(IN) :: scalar
89 ! A few handy 3d arrays computed for the physics scheme: pressure (Pa) and
90 ! temperature (K), on both half (_phy) and full levels.
92 REAL , DIMENSION(ims:ime,kms:kme,jms:jme) , INTENT(IN) :: th_phy , &
99 ! Time (s) since the beginning of the restart.
104 ! Is this to be a history output time? If so, compute the diagnostics.
108 ! The sundry dimensions required to keep a model running smoothly:
110 ! i: refers to the nominally west east direction, the inner-most (fastest)
112 ! j: refers to the nominally south north direction, the outer-most (slowest)
114 ! k: refers to the vertical direction form bottom to top, the second dimension
117 ! d: refers to the domain size, the geophysical extent of the entire domain,
118 ! not used in dimensions or looping, used to determine when we are close to
119 ! the edge of the boundary
120 ! m: refers to the memory size size, all 2d and 3d arrays from the Registry
121 ! (passed into here via the grid structure or the I1 variables [such as
122 ! p_phy, for example]) use these values for dimensioning
123 ! p: refers to the patch size, the extent over which computational loops run
125 INTEGER , INTENT(IN) :: ids, ide, jds, jde, kds, kde, &
126 ims, ime, jms, jme, kms, kme, &
127 ips, ipe, jps, jpe, kps, kpe
129 ! Hopefully unnecessary, these are the filtered dimensions.
131 INTEGER , INTENT(IN) :: imsx,imex,jmsx,jmex,kmsx,kmex, &
132 ipsx,ipex,jpsx,jpex,kpsx,kpex, &
133 imsy,imey,jmsy,jmey,kmsy,kmey, &
134 ipsy,ipey,jpsy,jpey,kpsy,kpey
137 !=============================================================
138 ! Include patch communications
139 !=============================================================
140 # include "HALO_EM_PHYS_W.inc"
141 # include "HALO_EM_PHYS_HCW.inc"
144 !=============================================================
145 ! Start of executable code
146 !=============================================================
148 CALL wrf_debug ( 100 , '--> TOP OF AFTER ALL RK STEPS' )
149 CALL wrf_debug ( 100 , '--> CALLING DIAGNOSTICS DRIVER' )
151 CALL diagnostics_driver ( grid, config_flags, &
152 moist, chem, tracer, scalar, &
153 th_phy, pi_phy, p_phy, &
155 curr_secs, curr_secs2, &
157 ids, ide, jds, jde, kds, kde, &
158 ims, ime, jms, jme, kms, kme, &
159 ips, ipe, jps, jpe, kps, kpe, &
160 imsx, imex, jmsx, jmex, kmsx, kmex, &
161 ipsx, ipex, jpsx, jpex, kpsx, kpex, &
162 imsy, imey, jmsy, jmey, kmsy, kmey, &
163 ipsy, ipey, jpsy, jpey, kpsy, kpey )
166 END SUBROUTINE after_all_rk_steps
168 END MODULE module_after_all_rk_steps