stats_type_utilities.F90 coverage: 0.00 %func 0.00 %block
1) !-----------------------------------------------------------------------
2) ! $Id$
3) !===============================================================================
4) module stats_type_utilities
5)
6) ! Description:
7) ! Contains subroutines for interfacing with type, stats
8) !-----------------------------------------------------------------------
9)
10) use stats_type, only: &
11) stats ! type
12)
13) use clubb_precision, only: &
14) core_rknd
15)
16) implicit none
17)
18) private ! Set Default Scope
19)
20) public :: stat_assign, &
21) stat_update_var, &
22) stat_update_var_pt, &
23) stat_begin_update, &
24) stat_begin_update_pt, &
25) stat_end_update, &
26) stat_end_update_pt, &
27) stat_modify, &
28) stat_modify_pt
29) contains
30)
31) !=============================================================================
32) subroutine stat_assign( var_index, var_name, &
33) var_description, var_units, &
34) l_silhs, grid_kind )
35)
36) ! Description:
37) ! Assigns pointers for statistics variables in grid. There is an
38) ! option to make the variable a SILHS variable (updated n_microphys_calls
39) ! times per timestep rather than just once).
40)
41) !
42) ! References:
43) ! None
44) !-----------------------------------------------------------------------
45)
46) implicit none
47)
48) ! Input Variables
49)
50) integer,intent(in) :: var_index ! Variable index [#]
51) character(len = *), intent(in) :: var_name ! Variable name []
52) character(len = *), intent(in) :: var_description ! Variable description []
53) character(len = *), intent(in) :: var_units ! Variable units []
54)
55) logical, intent(in) :: l_silhs ! SILHS variable [boolean]
56)
57) ! Input/Output Variable
58)
59) ! Which grid the variable is located on (e.g., zt, zm, sfc)
60) type(stats), target, intent(inout) :: grid_kind
61)
62) grid_kind%file%var(var_index)%ptr => grid_kind%accum_field_values(:,:,:,var_index)
63) grid_kind%file%var(var_index)%name = var_name
64) grid_kind%file%var(var_index)%description = var_description
65) grid_kind%file%var(var_index)%units = var_units
66)
67) grid_kind%file%var(var_index)%l_silhs = l_silhs
68)
69) !Example of the old format
70) !changed by Joshua Fasching 23 August 2007
71)
72) !stats_zt%file%var(ithlm)%ptr => stats_zt%accum_field_values(:,k)
73) !stats_zt%file%var(ithlm)%name = "thlm"
74) !stats_zt%file%var(ithlm)%description = "thetal (K)"
75) !stats_zt%file%var(ithlm)%units = "K"
76)
77) return
78)
79) end subroutine stat_assign
80)
81) !=============================================================================
82) subroutine stat_update_var( var_index, value, grid_kind )
83)
84) ! Description:
85) ! This updates the value of a statistics variable located at var_index
86) ! associated with grid type 'grid_kind' (zt, zm, or sfc).
87) !
88) ! This subroutine is used when a statistical variable needs to be updated
89) ! only once during a model timestep.
90) !
91) ! In regards to budget terms, this subroutine is used for variables that
92) ! are either completely implicit (e.g. wprtp_ma) or completely explicit
93) ! (e.g. wp2_pr3). For completely implicit terms, once the variable has been
94) ! solved for, the implicit contribution can be finalized. The finalized
95) ! implicit contribution is sent into stat_update_var_pt. For completely
96) ! explicit terms, the explicit contribution is sent into stat_update_var_pt
97) ! once it has been calculated.
98) !---------------------------------------------------------------------
99)
100) use clubb_precision, only: &
101) stat_rknd ! Constant
102)
103) use stat_file_module, only: &
104) clubb_i, clubb_j ! Variable(s)
105)
106) implicit none
107)
108) ! Input Variables(s)
109)
110) integer, intent(in) :: &
111) var_index ! The index at which the variable is stored []
112)
113) ! Input/Output Variable(s)
114) type(stats), intent(inout) :: &
115) grid_kind ! Which grid the variable is located on (zt, zm, rad, or sfc )
116)
117) ! Input Variable(s) NOTE: Due to the implicit none above, these must
118) ! be declared below to allow the use of grid_kind
119)
120) real( kind = core_rknd ), dimension(grid_kind%kk), intent(in) :: &
121) value ! Value of field being added to the statistic [Units Vary]
122)
123) integer :: k
124)
125) if ( var_index > 0 ) then
126) do k = 1, grid_kind%kk
127) grid_kind%accum_field_values(clubb_i,clubb_j,k,var_index) = &
128) grid_kind%accum_field_values(clubb_i,clubb_j,k,var_index) + real( value(k), &
129) kind=stat_rknd )
130) grid_kind%accum_num_samples(clubb_i,clubb_j,k,var_index) = &
131) grid_kind%accum_num_samples(clubb_i,clubb_j,k,var_index) + 1
132) end do
133) endif
134)
135) return
136) end subroutine stat_update_var
137)
138) !=============================================================================
139) subroutine stat_update_var_pt( var_index, grid_level, value, grid_kind )
140)
141) ! Description:
142) ! This updates the value of a statistics variable located at var_index
143) ! associated with grid type 'grid_kind' at a specific grid_level.
144) !
145) ! See the description of stat_update_var for more details.
146) !---------------------------------------------------------------------
147)
148) use clubb_precision, only: &
149) stat_rknd ! Constant
150)
151) use stat_file_module, only: &
152) clubb_i, clubb_j ! Variable(s)
153)
154) implicit none
155)
156) ! Input Variables(s)
157)
158) integer, intent(in) :: &
159) var_index, & ! The index at which the variable is stored []
160) grid_level ! The level at which the variable is to be modified []
161)
162) real( kind = core_rknd ), intent(in) :: &
163) value ! Value of field being added to the statistic [Units Vary]
164)
165) ! Input/Output Variable(s)
166) type(stats), intent(inout) :: &
167) grid_kind ! Which grid the variable is located on (zt, zm, rad, or sfc).
168)
169) if ( var_index > 0 ) then
170)
171) grid_kind%accum_field_values(clubb_i,clubb_j,grid_level,var_index) = &
172) grid_kind%accum_field_values(clubb_i,clubb_j,grid_level,var_index) + &
173) real( value, kind=stat_rknd )
174)
175) grid_kind%accum_num_samples(clubb_i,clubb_j,grid_level,var_index) = &
176) grid_kind%accum_num_samples(clubb_i,clubb_j,grid_level,var_index) + 1
177)
178) endif
179)
180) return
181) end subroutine stat_update_var_pt
182)
183) !=============================================================================
184) subroutine stat_begin_update( var_index, value, &
185) grid_kind )
186)
187) ! Description:
188) ! This begins an update of the value of a statistics variable located at
189) ! var_index on the (zt, zm, or sfc) grid. It is used in conjunction with
190) ! subroutine stat_end_update.
191) !
192) ! This subroutine is used when a statistical variable needs to be updated
193) ! more than one time during a model timestep. Commonly, this is used for
194) ! beginning a budget term calculation.
195) !
196) ! In this type of stats calculation, we first subtract the field
197) ! (e.g. rtm / dt ) from the statistic, then update rtm by a term
198) ! (e.g. clip rtm), and then re-add the field (e.g. rtm / dt) to the
199) ! statistic.
200) !
201) ! Example:
202) !
203) ! call stat_begin_update( irtm_bt, real(rtm / dt), stats_zt )
204) !
205) ! !!! Perform clipping of rtm !!!
206) !
207) ! call stat_end_update( irtm_bt, real(rtm / dt), stats_zt )
208) !
209) ! This subroutine is often used with stats budget terms for variables that
210) ! have both implicit and explicit components (e.g. wp3_ta). The explicit
211) ! component is sent into stat_begin_update_pt (with the sign reversed
212) ! because stat_begin_update_pt automatically subtracts the value sent into
213) ! it). Then, once the variable has been solved for, the implicit
214) ! statistical contribution can be finalized. The finalized implicit
215) ! component is sent into stat_end_update_pt.
216) !---------------------------------------------------------------------
217)
218) use grid_class, only: gr ! Variable(s)
219)
220) implicit none
221)
222) ! Input Variables(s)
223)
224) integer, intent(in) :: &
225) var_index ! The index at which the variable is stored []
226)
227) real( kind = core_rknd ), dimension(gr%nz), intent(in) :: &
228) value ! Value of field being added to the statistic [Units Vary]
229)
230) ! Input/Output Variable(s)
231) type(stats), intent(inout) :: &
232) grid_kind ! Which grid the variable is located on (zt, zm, rad, or sfc).
233)
234) integer :: i
235)
236) do i = 1, gr%nz
237)
238) call stat_begin_update_pt &
239) ( var_index, i, value(i), grid_kind )
240)
241) enddo
242)
243) return
244) end subroutine stat_begin_update
245)
246) !=============================================================================
247) subroutine stat_begin_update_pt &
248) ( var_index, grid_level, value, grid_kind )
249)
250) ! Description:
251) ! This begins an update of the value of a statistics variable located at
252) ! var_index associated with the grid type (grid_kind) at a specific
253) ! grid_level. It is used in conjunction with subroutine stat_end_update_pt.
254) !
255) ! Notes:
256) ! Commonly this is used for beginning a budget. See the description of
257) ! stat_begin_update for more details.
258) !
259) ! References:
260) ! None
261) !---------------------------------------------------------------------
262)
263) use clubb_precision, only: &
264) stat_rknd ! Constant
265)
266) use stat_file_module, only: &
267) clubb_i, clubb_j ! Variable(s)
268)
269) use constants_clubb, only: &
270) fstderr ! Constant(s)
271)
272) use error_code, only: &
273) clubb_at_least_debug_level ! Procedure
274)
275) implicit none
276)
277) ! Input Variables(s)
278)
279) integer, intent(in) :: &
280) var_index, & ! The index at which the variable is stored []
281) grid_level ! The level at which the variable is to be modified []
282)
283) real( kind = core_rknd ), intent(in) :: &
284) value ! Value of field being added to the statistic [Units Vary]
285)
286) ! Input/Output Variable(s)
287) type(stats), intent(inout) :: &
288) grid_kind ! Which grid the variable is located on (zt, zm, rad, or sfc).
289)
290) ! ---- Begin Code ----
291)
292) if ( var_index > 0 ) then ! Are we storing this variable?
293)
294) ! Can we begin an update?
295) if ( .not. grid_kind%l_in_update(clubb_i,clubb_j,grid_level,var_index) ) then
296)
297) grid_kind%accum_field_values(clubb_i,clubb_j,grid_level, var_index) = &
298) grid_kind%accum_field_values(clubb_i,clubb_j,grid_level, var_index) - &
299) real( value, kind=stat_rknd )
300)
301) grid_kind%l_in_update(clubb_i,clubb_j,grid_level, var_index) = .true. ! Start Record
302)
303) else if ( clubb_at_least_debug_level( 1 ) ) then
304)
305) write(fstderr,*) "Beginning an update before finishing previous for variable: "// &
306) trim( grid_kind%file%var(var_index)%name )
307) endif
308)
309) endif
310)
311) return
312) end subroutine stat_begin_update_pt
313)
314) !=============================================================================
315) subroutine stat_end_update( var_index, value, grid_kind )
316)
317) ! Description:
318) ! This ends an update of the value of a statistics variable located at
319) ! var_index on the (zt, zm, or sfc) grid. It is used in conjunction with
320) ! subroutine stat_begin_update.
321) !
322) ! This subroutine is used when a statistical variable needs to be updated
323) ! more than one time during a model timestep. Commonly, this is used for
324) ! finishing a budget term calculation.
325) !
326) ! In this type of stats calculation, we first subtract the field
327) ! (e.g. rtm / dt ) from the statistic, then update rtm by a term
328) ! (e.g. clip rtm), and then re-add the field (e.g. rtm / dt) to the
329) ! statistic.
330) !
331) ! Example:
332) !
333) ! call stat_begin_update( irtm_bt, real(rtm / dt), stats_zt )
334) !
335) ! !!! Perform clipping of rtm !!!
336) !
337) ! call stat_end_update( irtm_bt, real(rtm / dt), stats_zt )
338) !
339) ! This subroutine is often used with stats budget terms for variables that
340) ! have both implicit and explicit components (e.g. wp3_ta). The explicit
341) ! component is sent into stat_begin_update_pt (with the sign reversed
342) ! because stat_begin_update_pt automatically subtracts the value sent into
343) ! it). Then, once the variable has been solved for, the implicit
344) ! statistical contribution can be finalized. The finalized implicit
345) ! component is sent into stat_end_update_pt.
346) !---------------------------------------------------------------------
347)
348) use grid_class, only: gr ! Variable(s)
349)
350) implicit none
351)
352) ! Input Variables(s)
353)
354) integer, intent(in) :: &
355) var_index ! The index at which the variable is stored []
356)
357) real( kind = core_rknd ), dimension(gr%nz), intent(in) :: &
358) value ! Value of field being added to the statistic [Units Vary]
359)
360) ! Input/Output Variable(s)
361) type(stats), intent(inout) :: &
362) grid_kind ! Which grid the variable is located on (zt, zm, rad, or sfc).
363)
364) integer :: k
365)
366) ! ---- Begin Code ----
367)
368) do k = 1,gr%nz
369) call stat_end_update_pt &
370) ( var_index, k, value(k), grid_kind )
371) enddo
372)
373) return
374) end subroutine stat_end_update
375)
376) !=============================================================================
377) subroutine stat_end_update_pt &
378) ( var_index, grid_level, value, grid_kind )
379)
380) ! Description:
381) ! This ends an update of the value of a statistics variable located at
382) ! var_index associated with the grid type (grid_kind) at a specific
383) ! grid_level. It is used in conjunction with subroutine
384) ! stat_begin_update_pt.
385) !
386) ! Commonly this is used for finishing a budget. See the description of
387) ! stat_end_update for more details.
388) !---------------------------------------------------------------------
389)
390) use stat_file_module, only: &
391) clubb_i, clubb_j ! Variable(s)
392)
393) use constants_clubb, only: &
394) fstderr ! Constant(s)
395)
396) use error_code, only: &
397) clubb_at_least_debug_level ! Procedure
398)
399) implicit none
400)
401) ! Input Variables(s)
402)
403) integer, intent(in) :: &
404) var_index, & ! The index at which the variable is stored []
405) grid_level ! The level at which the variable is to be modified []
406)
407) real( kind = core_rknd ), intent(in) :: &
408) value ! Value of field being added to the statistic [Units Vary]
409)
410) ! Input/Output Variable(s)
411) type(stats), intent(inout) :: &
412) grid_kind ! Which grid the variable is located on (zt, zm, rad, or sfc).
413)
414) ! ---- Begin Code ----
415)
416) if ( var_index > 0 ) then ! Are we storing this variable?
417)
418) ! Can we end an update?
419) if ( grid_kind%l_in_update(clubb_i,clubb_j,grid_level,var_index) ) then
420)
421) call stat_update_var_pt &
422) ( var_index, grid_level, value, grid_kind )
423)
424) grid_kind%l_in_update(clubb_i,clubb_j,grid_level,var_index) = .false. ! End Record
425)
426) else if ( clubb_at_least_debug_level( 1 ) ) then
427)
428) write(fstderr,*) "Ending before beginning update. For variable "// &
429) grid_kind%file%var(var_index)%name
430) endif
431)
432) endif
433)
434) return
435) end subroutine stat_end_update_pt
436)
437) !=============================================================================
438) subroutine stat_modify( var_index, value, &
439) grid_kind )
440)
441) ! Description:
442) ! This modifies the value of a statistics variable located at var_index on
443) ! the (zt, zm, or sfc) grid. It does not increment the sampling count.
444) !
445) ! This subroutine is normally used when a statistical variable needs to be
446) ! updated more than twice during a model timestep. Commonly, this is used
447) ! if a budget term calculation needs an intermediate modification between
448) ! stat_begin_update and stat_end_update.
449) !---------------------------------------------------------------------
450)
451) use grid_class, only: gr ! Variable(s)
452)
453) implicit none
454)
455) ! Input Variables(s)
456)
457) integer, intent(in) :: &
458) var_index ! The index at which the variable is stored []
459)
460) real( kind = core_rknd ), dimension(gr%nz), intent(in) :: &
461) value ! Value of field being added to the statistic [Units Vary]
462)
463) ! Input/Output Variable(s)
464) type(stats), intent(inout) :: &
465) grid_kind ! Which grid the variable is located on (zt, zm, rad, or sfc).
466)
467) integer :: k
468)
469) ! ---- Begin Code ----
470)
471) do k = 1, gr%nz
472)
473) call stat_modify_pt( var_index, k, value(k), grid_kind )
474)
475) enddo
476)
477) return
478) end subroutine stat_modify
479)
480) !=============================================================================
481) subroutine stat_modify_pt( var_index, grid_level, value, &
482) grid_kind )
483)
484) ! Description:
485) ! This modifies the value of a statistics variable located at var_index on
486) ! the grid at a specific point. It does not increment the sampling count.
487) !
488) ! Commonly this is used for intermediate updates to a budget. See the
489) ! description of stat_modify for more details.
490) !---------------------------------------------------------------------
491)
492) use clubb_precision, only: &
493) stat_rknd ! Constant
494)
495) use stat_file_module, only: &
496) clubb_i, clubb_j ! Variable(s)
497)
498) implicit none
499)
500) ! Input Variables(s)
501)
502) integer, intent(in) :: &
503) var_index ! The index at which the variable is stored []
504)
505)
506) real( kind = core_rknd ), intent(in) :: &
507) value ! Value of field being added to the statistic [Units Vary]
508)
509) integer, intent(in) :: &
510) grid_level ! The level at which the variable is to be modified []
511)
512) ! Input/Output Variable(s)
513) type(stats), intent(inout) :: &
514) grid_kind ! Which grid the variable is located on (zt, zm, rad, or sfc).
515)
516) ! ---- Begin Code ----
517)
518) if ( var_index > 0 ) then
519)
520) grid_kind%accum_field_values(clubb_i,clubb_j,grid_level,var_index ) &
521) = grid_kind%accum_field_values(clubb_i,clubb_j,grid_level,var_index ) + &
522) real( value, kind=stat_rknd )
523)
524) end if
525)
526) return
527) end subroutine stat_modify_pt
528)
529) !===============================================================================
530)
531) end module stats_type_utilities