MONC
cfltest.F90
Go to the documentation of this file.
1 
5 module cfltest_mod
9  use collections_mod, only : map_type
14  use grids_mod, only : z_index, y_index, x_index
15  use mpi, only : mpi_max, mpi_min
16  implicit none
17 
18 #ifndef TEST_MODE
19  private
20 #endif
21 
22  !! Configuration options - all are optional and have default values
24  logical l_monitor_cfl
25 
27 contains
28 
32  cfltest_get_descriptor%name="cfltest"
33  cfltest_get_descriptor%version=0.1
36  end function cfltest_get_descriptor
37 
40  subroutine initialisation_callback(current_state)
41  type(model_state_type), intent(inout), target :: current_state
42 
43  current_state%cfl_frequency=options_get_integer(current_state%options_database, "cfl_frequency")
44  tollerance=options_get_real(current_state%options_database, "cfl_tollerance")
45  cvismax=options_get_real(current_state%options_database, "cfl_cvismax")
46  cvelmax=options_get_real(current_state%options_database, "cfl_cvelmax")
47  dtmmax=options_get_real(current_state%options_database, "cfl_dtmmax")
48  dtmmin=options_get_real(current_state%options_database, "cfl_dtmmin")
49  rincmax=options_get_real(current_state%options_database, "cfl_rincmax")
50 
51  l_monitor_cfl = options_get_logical(current_state%options_database,"cfl_monitor")
52 
53  allocate(current_state%abswmax(current_state%local_grid%local_domain_end_index(z_index)))
54  end subroutine initialisation_callback
55 
59  subroutine timestep_callback(current_state)
60  type(model_state_type), intent(inout), target :: current_state
61 
62  real(kind=default_precision) :: cfl_number
63 
64  if (mod(current_state%timestep, current_state%cfl_frequency) == 1 .or. &
65  current_state%timestep-current_state%start_timestep .le. current_state%cfl_frequency) then
66  current_state%cvel=0.0_default_precision
67  current_state%cvel_x=0.0_default_precision
68  current_state%cvel_y=0.0_default_precision
69  current_state%cvel_z=0.0_default_precision
70 
72 
73  current_state%cvel=(current_state%cvel_x*current_state%global_grid%configuration%horizontal%cx+current_state%cvel_y*&
74  current_state%global_grid%configuration%horizontal%cy+current_state%cvel_z)*current_state%dtm
75  current_state%cvis=current_state%cvis*(current_state%dtm * 4)
76 
77  cfl_number=current_state%cvis/cvismax+current_state%cvel/cvelmax
78 
79  current_state%absolute_new_dtm=current_state%dtm
80  current_state%update_dtm=.false.
81  if (cfl_number .gt. 0.0_default_precision) then
82  if (cfl_number .lt. (1.0_default_precision-tollerance) .or. cfl_number .gt. (1.0_default_precision+tollerance)) then
83  current_state%absolute_new_dtm=current_state%dtm/cfl_number
84  end if
85  end if
86  end if
87  call update_dtm_based_on_absolute(current_state, cfl_number)
88  current_state%cvis=0.0_default_precision
89  end subroutine timestep_callback
90 
95  subroutine update_dtm_based_on_absolute(current_state, cfl_number)
96  type(model_state_type), intent(inout), target :: current_state
97  real(kind=default_precision), intent(in) :: cfl_number
98 
99  if (current_state%dtm .ne. current_state%absolute_new_dtm .and. &
100  (current_state%dtm .ne. dtmmax .or. current_state%absolute_new_dtm .lt. dtmmax)) then
101 
102  current_state%update_dtm=.true.
103 
104  current_state%dtm_new=min(current_state%dtm*(1.0_default_precision+rincmax), current_state%absolute_new_dtm, dtmmax)
105 
106  !! --- Diagnostic Writing -----------------
107  if (current_state%parallel%my_rank==0) then
108  if (log_get_logging_level() .eq. log_debug) then
109  call log_log(log_debug, "dtm changed from "//trim(conv_to_string(current_state%dtm, 5))//" to "//&
110  trim(conv_to_string(current_state%dtm_new, 5)))
111  end if
112  if (current_state%dtm_new .lt. dtmmin) then
113  call log_log(log_error, "Timestep too small, dtmnew="//trim(conv_to_string(current_state%dtm_new, 5))//&
114  " dtmmin="//trim(conv_to_string(dtmmin, 5)))
115  end if
116  if (l_monitor_cfl) then
117  call log_log(log_info, " --- CFL Monitoring Information --- ")
118  call log_log(log_info, "dtm changed from "//trim(conv_to_string(current_state%dtm, 5))//" to "//&
119  trim(conv_to_string(current_state%dtm_new, 5)))
120  if (cfl_number .gt. 0.0) then
121  call log_log(log_info, "cfl_number : "//trim(conv_to_string(cfl_number))//" (change divisor)")
122  call log_log(log_info, "cvis : "//trim(conv_to_string(current_state%cvis)) )
123  call log_log(log_info, "cvel : "//trim(conv_to_string(current_state%cvel)) )
124  else
125  call log_log(log_info, "dtm change due to ratcheting only. Target dtm unchanged.")
126  end if
127  call log_log(log_info, "target dtm : "//trim(conv_to_string(current_state%absolute_new_dtm)) )
128  call log_newline()
129 
130  end if ! l_monitor_cfl
131  end if ! Diagnostic Writing
132  end if
133  end subroutine update_dtm_based_on_absolute
134 
139  type(model_state_type), intent(inout), target :: current_state
140 
141  integer :: k
142  real(kind=default_precision) :: global_zumin, global_zumax, global_zvmin, &
143  global_zvmax, global_cvel_z, global_cvis
144 
145 #ifdef U_ACTIVE
146  current_state%local_zumin=current_state%local_zumin+current_state%ugal ! _undo Gal-trfm
147  current_state%local_zumax=current_state%local_zumax+current_state%ugal
148 #else
149  current_state%local_zumin=0.0_default_precision
150  current_state%local_zumax=0.0_default_precision
151 #endif
152 #ifdef V_ACTIVE
153  current_state%local_zvmin=current_state%local_zvmin+current_state%vgal ! _undo Gal-trfm
154  current_state%local_zvmax=current_state%local_zvmax+current_state%vgal
155 #else
156  current_state%local_zvmin=0.0_default_precision
157  current_state%local_zvmax=0.0_default_precision
158 #endif
159 #ifdef W_ACTIVE
160  current_state%local_cvel_z=current_state%cvel_z
161  do k=2,current_state%local_grid%local_domain_end_index(z_index)-1
162  ! CVELZ will be multiplied by DTM in TESTCFL
163  current_state%local_cvel_z=max(current_state%local_cvel_z, &
164  current_state%abswmax(k)*current_state%global_grid%configuration%vertical%rdzn(k+1))
165  end do
166 #else
167  current_state%local_cvel_z=0.0_default_precision
168 #endif
169  call get_global_values(current_state%local_zumin, current_state%local_zumax, current_state%local_zvmin, &
170  current_state%local_zvmax, current_state%local_cvel_z, current_state%cvis, &
171  global_zumin, global_zumax, global_zvmin, global_zvmax, global_cvel_z, global_cvis, current_state%parallel)
172 
173  if (current_state%galilean_transformation) then
174  if (.not.current_state%fix_ugal)current_state%ugal=0.5_default_precision*(global_zumin+global_zumax)
175  if (.not.current_state%fix_vgal)current_state%vgal=0.5_default_precision*(global_zvmin+global_zvmax)
176  else
177  current_state%ugal=0.0_default_precision
178  current_state%vgal=0.0_default_precision
179  end if
180  current_state%cvel_z=global_cvel_z
181  current_state%cvel_x=max(abs(global_zumax-current_state%ugal), abs(global_zumin-current_state%ugal))
182  current_state%cvel_y=max(abs(global_zvmax-current_state%vgal), abs(global_zvmin-current_state%vgal))
183  current_state%cvis=global_cvis
185 
200  subroutine get_global_values(local_zumin, local_zumax, local_zvmin, local_zvmax, local_cvel_z, local_cvis, &
201  global_zumin, global_zumax, global_zvmin, global_zvmax, global_cvel_z, global_cvis, parallel_state)
202  type(parallel_state_type), intent(inout) :: parallel_state
203  real(kind=default_precision), intent(in) :: local_zumin, local_zumax, local_zvmin, local_zvmax, local_cvel_z, local_cvis
204  real(kind=default_precision), intent(out) :: global_zumin, global_zumax, global_zvmin, global_zvmax, global_cvel_z, global_cvis
205 
206  integer :: ierr
207 
208  call mpi_allreduce(local_zumax, global_zumax, 1, precision_type, mpi_max, parallel_state%monc_communicator, ierr)
209  call mpi_allreduce(local_zvmax, global_zvmax, 1, precision_type, mpi_max, parallel_state%monc_communicator, ierr)
210  call mpi_allreduce(local_cvel_z, global_cvel_z, 1, precision_type, mpi_max, parallel_state%monc_communicator, ierr)
211  call mpi_allreduce(local_cvis, global_cvis, 1, precision_type, mpi_max, parallel_state%monc_communicator, ierr)
212  call mpi_allreduce(local_zumin, global_zumin, 1, precision_type, mpi_min, parallel_state%monc_communicator, ierr)
213  call mpi_allreduce(local_zvmin, global_zvmin, 1, precision_type, mpi_min, parallel_state%monc_communicator, ierr)
214  end subroutine get_global_values
215 end module cfltest_mod
logging_mod::log_error
integer, parameter, public log_error
Only log ERROR messages.
Definition: logging.F90:11
conversions_mod
Conversion between common inbuilt FORTRAN data types.
Definition: conversions.F90:5
collections_mod::map_type
Map data structure that holds string (length 20 maximum) key value pairs.
Definition: collections.F90:86
cfltest_mod::rincmax
real(kind=default_precision) rincmax
Definition: cfltest.F90:23
cfltest_mod::cvismax
real(kind=default_precision) cvismax
Definition: cfltest.F90:23
logging_mod::log_warn
integer, parameter, public log_warn
Log WARNING and ERROR messages.
Definition: logging.F90:12
cfltest_mod::tollerance
real(kind=default_precision) tollerance
Definition: cfltest.F90:23
cfltest_mod::cfltest_get_descriptor
type(component_descriptor_type) function, public cfltest_get_descriptor()
Provides the descriptor back to the caller and is used in component registration.
Definition: cfltest.F90:32
logging_mod::log_newline
subroutine, public log_newline()
Will log a new line to the stdout.
Definition: logging.F90:91
cfltest_mod::get_global_values
subroutine get_global_values(local_zumin, local_zumax, local_zvmin, local_zvmax, local_cvel_z, local_cvis, global_zumin, global_zumax, global_zvmin, global_zvmax, global_cvel_z, global_cvis, parallel_state)
Gets the global reduction values based upon the local contributions of CFL and Galilean transformatio...
Definition: cfltest.F90:202
collections_mod
Collection data structures.
Definition: collections.F90:7
grids_mod::x_index
integer, parameter, public x_index
Definition: grids.F90:14
optionsdatabase_mod::options_get_integer
integer function, public options_get_integer(options_database, key, index)
Retrieves an integer value from the database that matches the provided key.
Definition: optionsdatabase.F90:217
grids_mod::y_index
integer, parameter, public y_index
Definition: grids.F90:14
state_mod::parallel_state_type
Information about the parallel aspects of the system.
Definition: state.F90:21
logging_mod::log_info
integer, parameter, public log_info
Log INFO, WARNING and ERROR messages.
Definition: logging.F90:13
datadefn_mod::precision_type
integer, public precision_type
Definition: datadefn.F90:19
logging_mod::log_log
subroutine, public log_log(level, message, str)
Logs a message at the specified level. If the level is above the current level then the message is ig...
Definition: logging.F90:75
logging_mod::log_get_logging_level
integer function, public log_get_logging_level()
Retrieves the current logging level.
Definition: logging.F90:122
logging_mod::log_debug
integer, parameter, public log_debug
Log DEBUG, INFO, WARNING and ERROR messages.
Definition: logging.F90:14
cfltest_mod::timestep_callback
subroutine timestep_callback(current_state)
Called at each timestep, this will only do the CFL computation every nncfl timesteps (or every timest...
Definition: cfltest.F90:60
monc_component_mod
Interfaces and types that MONC components must specify.
Definition: monc_component.F90:6
cfltest_mod::update_dtm_based_on_absolute
subroutine update_dtm_based_on_absolute(current_state, cfl_number)
Updates the (new) dtm value, which is actioned after time step completion, based upon the absolute va...
Definition: cfltest.F90:96
cfltest_mod::dtmmin
real(kind=default_precision) dtmmin
Definition: cfltest.F90:23
cfltest_mod::cvelmax
real(kind=default_precision) cvelmax
Definition: cfltest.F90:23
cfltest_mod::initialisation_callback
subroutine initialisation_callback(current_state)
Called at initialisation, will read in configuration and use either configured or default values.
Definition: cfltest.F90:41
cfltest_mod::perform_cfl_and_galilean_transformation_calculation
subroutine perform_cfl_and_galilean_transformation_calculation(current_state)
Performs the CFL and Galilean transformation calculations. First locally and then will determine the ...
Definition: cfltest.F90:139
grids_mod::z_index
integer, parameter, public z_index
Grid index parameters.
Definition: grids.F90:14
conversions_mod::conv_to_string
Converts data types to strings.
Definition: conversions.F90:38
state_mod::model_state_type
The ModelState which represents the current state of a run.
Definition: state.F90:39
cfltest_mod::l_monitor_cfl
logical l_monitor_cfl
Definition: cfltest.F90:24
optionsdatabase_mod::options_get_logical
logical function, public options_get_logical(options_database, key, index)
Retrieves a logical value from the database that matches the provided key.
Definition: optionsdatabase.F90:154
logging_mod
Logging utility.
Definition: logging.F90:2
datadefn_mod
Contains common definitions for the data and datatypes used by MONC.
Definition: datadefn.F90:2
cfltest_mod::dtmmax
real(kind=default_precision) dtmmax
Definition: cfltest.F90:23
grids_mod
Functionality to support the different types of grid and abstraction between global grids and local o...
Definition: grids.F90:5
optionsdatabase_mod
Manages the options database. Contains administration functions and deduce runtime options from the c...
Definition: optionsdatabase.F90:7
monc_component_mod::component_descriptor_type
Description of a component.
Definition: monc_component.F90:42
optionsdatabase_mod::options_get_real
real(kind=default_precision) function, public options_get_real(options_database, key, index)
Retrieves a real value from the database that matches the provided key.
Definition: optionsdatabase.F90:91
cfltest_mod
This contains the CFL test. It will perform the local advective CFL and Galilean transfromation calcu...
Definition: cfltest.F90:5
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
state_mod
The model state which represents the current state of a run.
Definition: state.F90:2