MONC
Functions/Subroutines
merge_atm_data Module Reference

Functions/Subroutines

subroutine merge_data (current_state, socrates_opt, socrates_derived_fields, merge_fields, mcc)
 

Function/Subroutine Documentation

◆ merge_data()

subroutine merge_atm_data::merge_data ( type(model_state_type), intent(inout), target  current_state,
type (str_socrates_options), intent(in)  socrates_opt,
type (str_socrates_derived_fields), intent(in)  socrates_derived_fields,
type (str_merge_atm), intent(inout)  merge_fields,
type (str_mcc_profiles), intent(in)  mcc 
)

Definition at line 15 of file merge_atm_data.F90.

16  !
17  !------------------------------------------------------------------------
18  ! Routine to add ozone, qv and temperature information to the radiation
19  ! profiles (including MONC levels). This is called in the timestep
20  ! callback and uses irad_levs from calculate_radiation_levels.
21  ! Values of t and q above the MONC levels and ozone from all levels are
22  ! taken from a McClattchey profiles, which are defined in the
23  ! configuration file.
24  !------------------------------------------------------------------------
25  !
26  type(model_state_type), target, intent(inout) :: current_state
27  type (str_socrates_options), intent(in) :: socrates_opt
28  type (str_socrates_derived_fields), intent(in) :: socrates_derived_fields
29  type (str_mcc_profiles), intent(in) :: mcc
30  type (str_merge_atm), intent(inout) :: merge_fields
31 
32  type(vertical_grid_configuration_type) :: vertical_grid
33 
34  real(kind=default_precision), parameter :: gravity = 9.80665
35  ! weights for working out the temperature on grid boundaries
36  ! (weights are based on height)
37  real(kind=default_precision) :: weight_upper, weight_lower
38 
39  real(kind=default_precision) :: cloud_total
40 
41  integer :: k_top, icol, jcol ! Shorthand column indices
42 
43  integer :: k ! loop counter for z
44  integer :: j ! loop counter for mcc_levs
45 
46  k_top = current_state%local_grid%size(z_index)
47  icol=current_state%column_local_x
48  jcol=current_state%column_local_y
49 
50  vertical_grid=current_state%global_grid%configuration%vertical
51 
52  ! set the column vapour and temperature for clear sky
53  ! and cloudy calculation by combining the monc profiles and the McClatchey profiles
54  ! Remember the McClatchey profiles go from top of atmosphere as does the
55  ! radiation calc.
56  ! Also, it is important to note that I have assumed the McClatchey values
57  ! exist on the z levels (where w is) not zn.
58 
59  merge_fields%pres_level(1:mcc%cut) = mcc%p_level(1:mcc%cut)
60  merge_fields%pres_n(1:mcc%cut) = mcc%p_n(1:mcc%cut)
61  merge_fields%o3_n(1:mcc%cut) = mcc%o3_n(1:mcc%cut)
62  merge_fields%t_level(1:mcc%cut) = mcc%t_level(1:mcc%cut)
63  merge_fields%t_n(1:mcc%cut) = mcc%t_n(1:mcc%cut)
64  merge_fields%qv_n(1:mcc%cut) = mcc%q_n(1:mcc%cut)
65  merge_fields%ql_n(:) = 0.0
66  merge_fields%qi_n(:) = 0.0
67  merge_fields%total_cloud_fraction(:) = 0.0
68  merge_fields%liquid_cloud_fraction(:) = 0.0
69  merge_fields%ice_cloud_fraction(:) = 0.0
70 
71  cloud_total = 0.0
72 !
73 ! derive absolute temperature
74  do k=1, k_top
75  merge_fields%t_n_loc(k) = (current_state%th%data(k, jcol, icol) &
76  + current_state%global_grid%configuration%vertical%thref(k)) &
77  * current_state%global_grid%configuration%vertical%rprefrcp(k)
78  enddo
79 ! merge the fields centre grid fields that come from MONC first
80 ! cloud_number at 1+mcc%cut is not yet set.
81  do k = 2, k_top
82  ! centre pressure
83  merge_fields%pres_n(k+mcc%cut)= &
84  current_state%global_grid%configuration%vertical%prefn(k_top+2-k)
85  ! Absolute temperature at centre of the grid
86  merge_fields%t_n(k+mcc%cut) = merge_fields%t_n_loc(k_top+2-k)
87  ! vapour mixing ratio
88  merge_fields%qv_n(k+mcc%cut) = current_state%q(socrates_opt%iqv)%data(k_top+2-k, jcol, icol)
89  if ( socrates_opt%cloud_representation == 2) then
90  if (socrates_opt%mphys_nq_l > 0) then
91  merge_fields%ql_n(k+mcc%cut) = &
92  current_state%q(socrates_opt%iql)%data(k_top+2-k, jcol, icol)
93  if (.not. socrates_opt%l_fix_re) then
94  if (socrates_opt%mphys_nd_l > 0) then
95  ! Cloud is defined as double moment so set the cloud number for the
96  ! calculation of effective radius
97  if (socrates_opt%inl > 0) then
98  merge_fields%cloudnumber_n(k+mcc%cut) = &
99  current_state%q(socrates_opt%inl)%data(k_top+2-k, jcol, icol)
100  else
101  merge_fields%cloudnumber_n(k+mcc%cut) = &
102  socrates_opt%fixed_cloud_number*1.e6 ! convert to number per m3
103  endif
104  endif
105  endif
106  endif
107  ! NOTE: if rain is on then the mass is added to ql after
108  ! multiplication with rainfac. If available, there should
109  ! be a seperate optical property for rain.
110  if (socrates_opt%mphys_nq_r > 0) then
111  merge_fields%ql_n(k+mcc%cut) = merge_fields%ql_n(k+mcc%cut) + &
112  merge_fields%rainfac* &
113  (current_state%q(socrates_opt%iqr)%data(k_top+2-k, jcol, icol))
114  endif
115  if (socrates_opt%mphys_nq_i > 0) then
116  merge_fields%qi_n(k+mcc%cut) = &
117  current_state%q(socrates_opt%iqi)%data(k_top+2-k, jcol, icol)
118  endif
119  ! NOTE: if snow and graupel are on then the mass is added to qi after
120  ! multiplication with snowfac and graupfac. If available,
121  ! there should be a seperate optical property for snow and
122  ! graupel.
123  if (socrates_opt%mphys_nq_s > 0) then
124  merge_fields%qi_n(k+mcc%cut) = merge_fields%qi_n(k+mcc%cut) + &
125  merge_fields%snowfac* &
126  (current_state%q(socrates_opt%iqs)%data(k_top+2-k, jcol, icol))
127  endif
128  if (socrates_opt%mphys_nq_g > 0) then
129  merge_fields%qi_n(k+mcc%cut) = merge_fields%qi_n(k+mcc%cut) + &
130  merge_fields%graupfac* &
131  (current_state%q(socrates_opt%iqg)%data(k_top+2-k, jcol, icol))
132  endif
133  ! work out cloud fractions
134  cloud_total = merge_fields%ql_n(k+mcc%cut) + merge_fields%qi_n(k+mcc%cut)
135  if (cloud_total > epsilon(cloud_total) ) then
136  merge_fields%total_cloud_fraction(k+mcc%cut) = 1.0_default_precision
137  merge_fields%liquid_cloud_fraction(k+mcc%cut) = &
138  merge_fields%ql_n(k+mcc%cut)/(cloud_total)
139  merge_fields%ice_cloud_fraction(k+mcc%cut) = &
140  (1.0_default_precision - merge_fields%liquid_cloud_fraction(k+mcc%cut))
141  else
142  merge_fields%total_cloud_fraction(k+mcc%cut) = 0.0_default_precision
143  merge_fields%liquid_cloud_fraction(k+mcc%cut) = 0.0_default_precision
144  merge_fields%ice_cloud_fraction(k+mcc%cut) = 0.0_default_precision
145  endif
146  endif
147  enddo
148 
149  ! Work out k_top value for the centre fields. This is the mean of the monc centre value and
150  ! McClatchey centre fields
151  ! Pressure at the merge cut-off
152  merge_fields%pres_n(mcc%cut+1)= &
153  (current_state%global_grid%configuration%vertical%prefn(k_top) + &
154  mcc%p_n(mcc%cut))/2.0
155  ! Temperature at the merge cut-off
156  merge_fields%t_n(mcc%cut+1)= &
157  (merge_fields%t_n_loc(k_top) + mcc%t_n(mcc%cut))/2.0
158  ! Temperature at the merge cut-off
159  merge_fields%qv_n(mcc%cut+1)= &
160  (current_state%q(socrates_opt%iqv)%data(k_top, jcol, icol) + mcc%q_n(mcc%cut))/2.0
161 
162  ! Now work out the temperature and pressure on levels
163  ! Set the surface
164  merge_fields%pres_level(mcc%irad_levs) = current_state%surface_pressure
165  merge_fields%t_level(mcc%irad_levs) = socrates_derived_fields%srf_temperature
166  ! set the zero level (which is TOA) of t_level and pres_level (based on assumptions from LEM)
167  merge_fields%pres_level(0) = 0.0
168  merge_fields%t_level(0) = merge_fields%t_level(1)
169 
170  ! Assume the level is mid-way between n levels. While this is the same as
171  ! the LEM assumption, this is not correct. There should be a weighting factor
172  ! that accounts for a stretched MONC grid
173  do k = 1, mcc%irad_levs-1
174  merge_fields%pres_level(k) = 0.5_default_precision * &
175  (merge_fields%pres_n(k) + merge_fields%pres_n(k+1))
176 
177  merge_fields%t_level(k) = 0.5_default_precision * &
178  (merge_fields%t_n(k) + merge_fields%t_n(k+1))
179  enddo
180 
181  ! Now sort the Ozone profile which only exists on
182  ! McClatchey levels, so needs to be merged on to MONC
183  ! levels. Check this code!!
184 
185  do k=k_top+mcc%cut,mcc%cut,-1
186  if (merge_fields%pres_level(k).gt.mcc%p_level(mcc%levs)) then
187  merge_fields%o3_n(k) = mcc%o3_n(mcc%levs)
188  else
189  do j=mcc%levs,1,-1
190  if (merge_fields%pres_level(k).gt.mcc%p_level(j)) then
191  merge_fields%o3_n(k) = mcc%o3_n(j)
192  exit
193  endif
194  enddo
195  endif
196  enddo
197 
198  ! mass of the atmosphere on irad_levs for set_atm
199  do k=1, mcc%irad_levs
200  merge_fields%mass(k) = &
201  (merge_fields%pres_level(k)-merge_fields%pres_level(k-1))/gravity
202  enddo
203 
datadefn_mod::default_precision
integer, parameter, public default_precision
MPI communication type which we use for the prognostic and calculation data.
Definition: datadefn.F90:17