source: palm/trunk/UTIL/inifor/src/inifor_util.f90 @ 4568

Last change on this file since 4568 was 4568, checked in by eckhard, 4 years ago

Handle COSMO soil data with and without additional surface temperature

  • Property svn:keywords set to Id
File size: 16.5 KB
Line 
1!> @file src/inifor_util.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 2017-2020 Leibniz Universitaet Hannover
18! Copyright 2017-2020 Deutscher Wetterdienst Offenbach
19!------------------------------------------------------------------------------!
20!
21! Current revisions:
22! -----------------
23!
24!
25! Former revisions:
26! -----------------
27! $Id: inifor_util.f90 4568 2020-06-19 11:56:30Z eckhard $
28! Added function for checking floating point equality
29!
30!
31! 4523 2020-05-07 15:58:16Z eckhard
32! respect integer working precision (iwp) specified in inifor_defs.f90
33!
34!
35! 4499 2020-04-16 15:51:56Z eckhard
36! Bugfix: avoid using already overwritten elements in 'reverse' subroutine
37!
38!
39! 4481 2020-03-31 18:55:54Z maronga
40! Bugfix: use explicit loop in 'reverse' subroutine instead of implicit loop
41!
42! 3866 2019-04-05 14:25:01Z eckhard
43! Use PALM's working precision
44! Improved coding style
45!
46!
47! 3785 2019-03-06 10:41:14Z eckhard
48! Prefixed all INIFOR modules with inifor_
49!
50!
51! 3557 2018-11-22 16:01:22Z eckhard
52! Updated documentation
53!
54!
55! 3447 2018-10-29 15:52:54Z eckhard
56! Renamed source files for compatibilty with PALM build system
57!
58!
59! 3395 2018-10-22 17:32:49Z eckhard
60! New routines for computing potential temperature and moist air density
61! Increased number of digits in real-to-str conversion
62!
63! 3183 2018-07-27 14:25:55Z suehring
64! Improved real-to-string conversion
65!
66!
67! 3182 2018-07-27 13:36:03Z suehring
68! Initial revision
69!
70!
71!
72! Authors:
73! --------
74!> @author Eckhard Kadasch (Deutscher Wetterdienst, Offenbach)
75!
76! Description:
77! ------------
78!> The util module provides miscellaneous utility routines for INIFOR.
79!------------------------------------------------------------------------------!
80 MODULE inifor_util
81
82    USE inifor_defs,                                                           &
83        ONLY :  PI, DATE, SNAME, iwp, wp
84    USE inifor_types,                                                          &
85        ONLY :  grid_definition
86    USE, INTRINSIC :: ISO_C_BINDING,                                           &
87        ONLY :  C_CHAR, C_INT, C_PTR, C_SIZE_T
88
89    IMPLICIT NONE
90
91!------------------------------------------------------------------------------!
92! Description:
93! ------------
94!> Fortran implementation of C's struct tm for representing points in time
95!------------------------------------------------------------------------------!
96    TYPE, BIND(c) :: tm_struct
97       INTEGER(C_INT) :: tm_sec     !< seconds after the minute [0, 61]
98       INTEGER(C_INT) :: tm_min     !< minutes after the hour [0, 59]
99       INTEGER(C_INT) :: tm_hour    !< hours since midnight [0, 23]
100       INTEGER(C_INT) :: tm_mday    !< day of the month [1, 31]
101       INTEGER(C_INT) :: tm_mon     !< month since January [0, 11]
102       INTEGER(C_INT) :: tm_year    !< years since 1900
103       INTEGER(C_INT) :: tm_wday    !< days since Sunday [0, 6]
104       INTEGER(C_INT) :: tm_yday    !< days since January 1st [0, 356]
105       INTEGER(C_INT) :: tm_isdst   !< Daylight Saving Time flag
106    END TYPE
107
108 INTERFACE
109
110!------------------------------------------------------------------------------!
111! Description:
112! ------------
113!> Interface to C's strptime function, which converts a string to a tm
114!> structure.
115!------------------------------------------------------------------------------!
116    FUNCTION strptime(string, format, timeinfo) BIND(c, NAME='strptime')
117       IMPORT :: C_CHAR, C_SIZE_T, tm_struct
118
119       IMPLICIT NONE
120
121       CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) ::  string, format
122       TYPE(tm_struct), INTENT(OUT)                     ::  timeinfo
123
124       INTEGER(C_SIZE_T)                                ::  strptime
125    END FUNCTION
126
127
128!------------------------------------------------------------------------------!
129! Description:
130! ------------
131!> Interface to C's strftime function, which converts the given 'timeinfo'
132!> structure to a string in the given 'format'.
133!------------------------------------------------------------------------------!
134    FUNCTION strftime(string, string_len, format, timeinfo) BIND(c, NAME='strftime')
135       IMPORT :: C_CHAR, C_SIZE_T, tm_struct
136
137       IMPLICIT NONE
138
139       CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(OUT) ::  string
140       CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN)  ::  format
141       INTEGER(C_SIZE_T), INTENT(IN)                     ::  string_len
142       TYPE(tm_struct), INTENT(IN)                       ::  timeinfo
143
144       INTEGER(C_SIZE_T)                                 ::  strftime
145    END FUNCTION
146
147
148!------------------------------------------------------------------------------!
149! Description:
150! ------------
151!> Interface to C's mktime function, which converts the given tm structure to
152!> Unix time (number of seconds since 0 UTC, 1st January 1970). INIFOR uses the
153!> side effect that a call to mktime noramlizes the given 'timeinfo' structure,
154!> e.g. increments the date if hours overfow 24.
155!------------------------------------------------------------------------------!
156    FUNCTION mktime(timeinfo) BIND(c, NAME='mktime')
157       IMPORT :: C_PTR, tm_struct
158
159       IMPLICIT NONE
160
161       TYPE(tm_struct), INTENT(IN) ::  timeinfo
162
163       TYPE(C_PTR)                 ::  mktime
164    END FUNCTION
165
166 END INTERFACE
167
168 CONTAINS
169
170!------------------------------------------------------------------------------!
171! Description:
172! ------------
173!> Takes a string of the form YYYYMMDDHH, adds the given number of hours to its
174!> tm structure representation, and returns the corresponding string in the same
175!> format
176!------------------------------------------------------------------------------!
177 CHARACTER(LEN=DATE) FUNCTION add_hours_to(date_string, hours)
178    CHARACTER(LEN=DATE), INTENT(IN)          ::  date_string
179    INTEGER(iwp), INTENT(IN)                 ::  hours
180
181    CHARACTER(KIND=C_CHAR, LEN=*), PARAMETER ::  format_string = "%Y%m%d%H"
182    CHARACTER(KIND=C_CHAR, LEN=DATE)         ::  c_date_string
183    TYPE(C_PTR)                              ::  c_pointer
184    TYPE(tm_struct)                          ::  time_info
185    INTEGER(iwp)                             ::  err
186
187    c_date_string = date_string
188
189    ! Convert C string to C tm struct
190    CALL init_tm(time_info)
191    err = strptime(c_date_string, format_string, time_info)
192 
193    ! Manipulate and normalize C tm struct
194    time_info%tm_hour = time_info%tm_hour + hours
195    c_pointer = mktime(time_info)
196
197    ! Convert back to C string
198    err = strftime(c_date_string, INT(DATE, KIND=C_SIZE_T),                 &
199                   format_string, time_info)
200
201    add_hours_to = c_date_string
202 END FUNCTION
203
204
205!------------------------------------------------------------------------------!
206! Description:
207! ------------
208!> Print all members of the given tm structure
209!------------------------------------------------------------------------------!
210 SUBROUTINE print_tm(timeinfo)
211    TYPE(tm_struct), INTENT(IN) :: timeinfo
212
213    PRINT *, "sec: ", timeinfo%tm_sec,  &  !< seconds after the minute [0, 61]
214             "min: ", timeinfo%tm_min,  &  !< minutes after the hour [0, 59]
215             "hr:  ", timeinfo%tm_hour, &  !< hours since midnight [0, 23]
216             "day: ", timeinfo%tm_mday, &  !< day of the month [1, 31]
217             "mon: ", timeinfo%tm_mon,  &  !< month since January [0, 11]
218             "yr:  ", timeinfo%tm_year, &  !< years since 1900
219             "wday:", timeinfo%tm_wday, &  !< days since Sunday [0, 6]
220             "yday:", timeinfo%tm_yday, &  !< days since January 1st [0, 356]
221             "dst: ", timeinfo%tm_isdst    !< Daylight Saving time flag
222 END SUBROUTINE print_tm
223
224   
225!------------------------------------------------------------------------------!
226! Description:
227! ------------
228!> Initialize the given tm structure with zero values
229!------------------------------------------------------------------------------!
230 SUBROUTINE init_tm(timeinfo)
231    TYPE(tm_struct), INTENT(INOUT) :: timeinfo
232
233    timeinfo%tm_sec   = 0
234    timeinfo%tm_min   = 0
235    timeinfo%tm_hour  = 0
236    timeinfo%tm_mday  = 0
237    timeinfo%tm_mon   = 0
238    timeinfo%tm_year  = 0
239    timeinfo%tm_wday  = 0
240    timeinfo%tm_yday  = 0
241
242    ! We use UTC times, so marking Daylight Saving Time (DST) 'not available'
243    ! (< 0). If this is set to 0, mktime will convert the timeinfo to DST and
244    ! add one hour.
245    timeinfo%tm_isdst = -1
246 END SUBROUTINE init_tm
247
248
249!------------------------------------------------------------------------------!
250! Description:
251! ------------
252!> Fill the given array with values equally spaced between and including start
253!> and stop
254!------------------------------------------------------------------------------!
255 SUBROUTINE linspace(start, stop, array)
256
257    REAL(wp), INTENT(IN)    ::  start, stop
258    REAL(wp), INTENT(INOUT) ::  array(0:)
259    INTEGER(iwp)            ::  i, n
260
261    n = UBOUND(array, 1)
262
263    IF (n .EQ. 0)  THEN
264
265       array(0) = start
266
267    ELSE
268
269       DO i = 0, n
270          array(i) = start + REAL(i, wp) / n * (stop - start)
271       ENDDO
272
273    ENDIF
274   
275 END SUBROUTINE linspace
276
277
278!------------------------------------------------------------------------------!
279! Description:
280! ------------
281!> Reverse the order of the third (vertical) array dimension from top-down
282!> (COSMO) to bottom-up (PALM)
283!------------------------------------------------------------------------------!
284 SUBROUTINE reverse(input_arr)
285
286    INTEGER(iwp) ::  idx, opposite_idx, half_idx
287    INTEGER(iwp) ::  size_1st_dimension
288    INTEGER(iwp) ::  size_2nd_dimension
289    INTEGER(iwp) ::  size_3rd_dimension
290    INTEGER(iwp) ::  lbound_3rd_dimension
291    INTEGER(iwp) ::  ubound_3rd_dimension
292
293    REAL(wp), INTENT(INOUT) ::  input_arr(:,:,:)
294    REAL(wp), ALLOCATABLE  :: buffer_arr(:,:)
295
296    lbound_3rd_dimension = LBOUND(input_arr, 3)
297    ubound_3rd_dimension = UBOUND(input_arr, 3)
298    size_1st_dimension = SIZE(input_arr, 1)
299    size_2nd_dimension = SIZE(input_arr, 2)
300    size_3rd_dimension = SIZE(input_arr, 3)
301    half_idx = lbound_3rd_dimension + size_3rd_dimension / 2 - 1
302
303    ALLOCATE( buffer_arr(size_1st_dimension, size_2nd_dimension) )
304
305    DO  idx = lbound_3rd_dimension, half_idx
306       opposite_idx = ubound_3rd_dimension - ( idx - lbound_3rd_dimension )
307       buffer_arr(:,:) = input_arr(:,:,idx)
308       input_arr(:,:,idx) = input_arr(:,:,opposite_idx)
309       input_arr(:,:,opposite_idx) = buffer_arr(:,:)
310    ENDDO
311   
312    DEALLOCATE( buffer_arr )
313
314 END SUBROUTINE reverse
315
316
317!------------------------------------------------------------------------------!
318! Description:
319! ------------
320!>
321!------------------------------------------------------------------------------!
322 SUBROUTINE deaverage(avg_1, t1, avg_2, t2, avg_3, t3)
323
324    REAL(wp), DIMENSION(:,:,:), INTENT(IN)  ::  avg_1, avg_2
325    REAL(wp), INTENT(IN)                    ::  t1, t2, t3
326    REAL(wp), DIMENSION(:,:,:), INTENT(OUT) ::  avg_3
327
328    REAL(wp)                                ::  ti
329 
330    ti = 1.0_wp / t3
331
332    avg_3(:,:,:) = ti * ( t2 * avg_2(:,:,:) - t1 * avg_1(:,:,:) )
333
334 END SUBROUTINE deaverage
335
336
337!------------------------------------------------------------------------------!
338! Description:
339! ------------
340!> Compute the COSMO-DE/-D2 basic state pressure profile
341!------------------------------------------------------------------------------!
342 SUBROUTINE get_basic_state(z, beta, p_sl, t_sl, rd, g, p0)
343
344    REAL(wp), INTENT(IN)  ::  z(1:)  !< height [m]
345    REAL(wp), INTENT(IN)  ::  beta   !< logarithmic lapse rate, dT / d ln(p) [K]
346    REAL(wp), INTENT(IN)  ::  p_sl   !< reference pressure [Pa]
347    REAL(wp), INTENT(IN)  ::  t_sl   !< reference tempereature [K]
348    REAL(wp), INTENT(IN)  ::  rd     !< ideal gas constant of dry air [J/kg/K]
349    REAL(wp), INTENT(IN)  ::  g      !< acceleration of Earth's gravity [m/s^2]
350    REAL(wp), INTENT(OUT) ::  p0(1:) !< COSMO basic state pressure [Pa]
351    REAL(wp) ::  root_frac, factor   !< precomputed factors
352
353    factor = - t_sl / beta
354    root_frac = (2.0_wp * beta * g) / (rd * t_sl*t_sl)
355
356    p0(:) = p_sl * EXP(                                                     &
357               factor * ( 1.0_wp - SQRT( 1.0_wp - root_frac * z(:) ) )      &
358    )
359
360 END SUBROUTINE get_basic_state
361
362
363!------------------------------------------------------------------------------!
364! Description:
365! ------------
366!> Converts the absolute temperature to the potential temperature in place using
367!> the identity a^b = e^(b ln(a)).
368!>
369!>     theta = T * (p_ref/p)^(R/c_p) = T * e^( R/c_p * ln(p_ref/p) )
370!------------------------------------------------------------------------------!
371 SUBROUTINE potential_temperature(t, p, p_ref, r, cp)
372    REAL(wp), DIMENSION(:,:,:), INTENT(INOUT) ::  t
373    REAL(wp), DIMENSION(:,:,:), INTENT(IN)    ::  p
374    REAL(wp), INTENT(IN)                      ::  p_ref, r, cp
375    REAL(wp)                                  ::  rcp
376
377    rcp = r/cp
378    t(:,:,:) =  t(:,:,:) * EXP( rcp * LOG(p_ref / p(:,:,:)) )
379
380 END SUBROUTINE potential_temperature
381
382
383!------------------------------------------------------------------------------!
384! Description:
385! ------------
386!> Compute the density in place of the given temperature (t_rho).
387!------------------------------------------------------------------------------!
388 SUBROUTINE moist_density(t_rho, p, qv, rd, rv)
389    REAL(wp), DIMENSION(:,:,:), INTENT(INOUT) ::  t_rho
390    REAL(wp), DIMENSION(:,:,:), INTENT(IN)    ::  p, qv
391    REAL(wp), INTENT(IN)                      ::  rd, rv
392
393    t_rho(:,:,:) = p(:,:,:) / (                                             &
394       (rv * qv(:,:,:) + rd * (1.0_wp - qv(:,:,:))) * t_rho(:,:,:)          &
395    )
396
397 END SUBROUTINE moist_density
398
399!------------------------------------------------------------------------------!
400! Description:
401! ------------
402! Convert a real number to a string in scientific notation showing four
403! significant digits.
404!------------------------------------------------------------------------------!
405 CHARACTER(LEN=SNAME) FUNCTION real_to_str(val, format)
406
407    REAL(wp), INTENT(IN)                   ::  val
408    CHARACTER(LEN=*), OPTIONAL, INTENT(IN) ::  format
409
410    IF (PRESENT( format ) )  THEN
411       WRITE( real_to_str, format ) val
412    ELSE
413       WRITE( real_to_str, '(E11.4)' ) val
414    ENDIF
415    real_to_str = ADJUSTL( real_to_str )
416
417 END FUNCTION real_to_str
418
419
420!------------------------------------------------------------------------------!
421! Description:
422! ------------
423!> Converts the given real value to a string
424!------------------------------------------------------------------------------!
425 CHARACTER(LEN=16) FUNCTION real_to_str_f(val)
426
427     REAL(wp), INTENT(IN) ::  val
428
429     WRITE(real_to_str_f, '(F16.8)') val
430     real_to_str_f = ADJUSTL(real_to_str_f)
431
432 END FUNCTION real_to_str_f
433
434
435!------------------------------------------------------------------------------!
436! Description:
437! ------------
438!> Converts the given integer value to a string
439!------------------------------------------------------------------------------!
440 CHARACTER(LEN=10) FUNCTION str(val)
441
442     INTEGER(iwp), INTENT(IN) ::  val
443
444     WRITE(str, '(i10)') val
445     str = ADJUSTL(str)
446
447 END FUNCTION str
448
449
450!------------------------------------------------------------------------------!
451! Description:
452! ------------
453!> If the given path is not conlcuded by a slash, add one.
454!------------------------------------------------------------------------------!
455 SUBROUTINE normalize_path(path)
456     
457     CHARACTER(LEN=*), INTENT(INOUT) ::  path
458     INTEGER(iwp) ::  n
459
460     n = LEN_TRIM(path)
461
462     IF (path(n:n) .NE. '/')  THEN
463        path = TRIM(path) // '/'
464     ENDIF
465
466 END SUBROUTINE
467
468
469!------------------------------------------------------------------------------!
470! Description:
471! ------------
472!> Check for exact or near equality of two floating point numbers. Inspired by
473!> https://randomascii.wordpress.com/2012/02/25/comparing-floating-point-numbers-2012-edition/
474!------------------------------------------------------------------------------!
475 LOGICAL FUNCTION nearly_equal(a, b, max_rel_diff)
476
477    REAL(wp), INTENT(IN) ::  a, b, max_rel_diff
478    REAL(wp)             ::  diff, mag
479 
480    diff = ABS( a - b ) 
481    mag = MAX( ABS(a), ABS(b) )
482    nearly_equal = ( diff .LE. mag * max_rel_diff )
483
484 END FUNCTION nearly_equal
485
486 END MODULE inifor_util
Note: See TracBrowser for help on using the repository browser.