/[lmdze]/trunk/dyn3d/test_disvert.f90
ViewVC logotype

Annotation of /trunk/dyn3d/test_disvert.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 328 - (hide annotations)
Thu Jun 13 14:40:06 2019 UTC (5 years ago) by guez
File size: 3753 byte(s)
Change all `.f` suffixes to `.f90`. (The opposite was done in revision
82.)  Because of change of philosopy in GNUmakefile: we already had a
rewritten rule for `.f`, so it does not make the makefile longer to
replace it by a rule for `.f90`. And it spares us options of
makedepf90 and of the compiler. Also we prepare the way for a simpler
`CMakeLists.txt`.

1 guez 99 module test_disvert_m
2    
3     implicit none
4    
5     contains
6    
7     subroutine test_disvert
8    
9     ! Author: Lionel GUEZ
10    
11     ! This procedure tests the order of pressure values at half-levels
12     ! and full levels, and writes the vertical coordinates to files
13     ! "half_level.csv" and "full_level.csv" for a reference surface
14     ! pressure. We arbitrarily choose to test ngrid values of the
15     ! surface pressure, which sample possible values on Earth.
16    
17     use abort_gcm_m, only: abort_gcm
18     use comconst, only: kappa, cpp
19 guez 107 use disvert_m, only: ap, bp, preff, presnivs, s
20 guez 265 use dimensions, only: llm
21 guez 99 use exner_hyb_m, only: exner_hyb
22     use jumble, only: new_unit
23    
24     integer i, unit, l
25     integer, parameter:: ngrid = 8
26     real p(ngrid, 1, llm + 1) ! pressure at half-level, in Pa
27     real z(llm) ! pressure-altitude at half-level (km)
28     real pks(ngrid, 1) ! exner function at the surface, in J K-1 kg-1
29     real pk(ngrid, 1, llm) ! exner function at full level, in J K-1 kg-1
30     real ps(ngrid, 1) ! surface pressure, in Pa
31     real p_lay(ngrid, llm) ! pressure at full level, in Pa
32     real, parameter:: delta_ps = 6e4 / (ngrid - 2) ! in Pa
33    
34     !---------------------
35    
36     print *, "Call sequence information: test_disvert"
37    
38 guez 266 ps(:, 1) = [(5e4 + delta_ps * i, i = 0, ngrid - 2), preff]
39 guez 99 forall (l = 1: llm + 1) p(:, 1, l) = ap(l) + bp(l) * ps(:, 1)
40     call exner_hyb(ps, p, pks, pk)
41     p_lay = preff * (pk(:, 1, :) / cpp)**(1. / kappa)
42    
43 guez 266 ! Write distribution for the reference surface pressure (which is
44     ! surface pressure at index ngrid):
45 guez 99
46     z = 7. * log(preff / p(ngrid, 1, :llm))
47     call new_unit(unit)
48    
49     open(unit, file="half_level.csv", status="replace", action="write")
50 guez 266 ! Title lines:
51     write(unit, fmt=*) 'hPa "" "" hPa km'
52     write(unit, fmt=*) 'ap bp s pressure z'
53 guez 99 do l = 1, llm
54     write(unit, fmt=*) ap(l) / 100., bp(l), s(l), p(ngrid, 1, l) / 100., z(l)
55     end do
56     close(unit)
57     print *, 'The file "half_level.csv" has been created.'
58    
59     open(unit, file="full_level.csv", status="replace", action="write")
60 guez 266 ! Title lines:
61     write(unit, fmt=*) '"pressure at full level from Exner function for a ', &
62     'reference surface pressure" altitude "approximate pressure at ', &
63     'full level for a reference surface pressure" "layer thickness"'
64     write(unit, fmt=*) 'hPa km hPa km'
65     write(unit, fmt=*) 'p_lay z presnivs delta_z'
66 guez 99 do l = 1, llm - 1
67     write(unit, fmt=*) p_lay(ngrid, l) / 100., &
68     7. * log(preff / p_lay(ngrid, l)), presnivs(l) / 100., z(l+1) - z(l)
69     end do
70     write(unit, fmt=*) p_lay(ngrid, llm) / 100., &
71 guez 266 7. * log(preff / p_lay(ngrid, llm)), presnivs(llm) / 100., "NaN"
72 guez 99 close(unit)
73     print *, 'The file "full_level.csv" has been created.'
74    
75 guez 116 ! Are pressure values in the right order?
76     if (any(p(:, 1, :llm) <= p_lay .or. p_lay <= p(:, 1, 2:))) then
77     ! List details and stop:
78     do l = 1, llm
79     do i = 1, ngrid
80     if (p(i, 1, l) <= p_lay(i, l)) then
81     print 1000, "ps = ", ps(i, 1) / 100., "hPa, p(level ", l, &
82     ") = ", p(i, 1, l) / 100., " hPa <= p(layer ", l, ") = ", &
83     p_lay(i, l) / 100., " hPa"
84     end if
85     if (p_lay(i, l) <= p(i, 1, l+1)) then
86     print 1000, "ps = ", ps(i, 1) / 100., &
87     "hPa, p(layer ", l, ") = ", p_lay(i, l) / 100., &
88     " hPa <= p(level ", l + 1, ") = ", &
89     p(i, 1, l + 1) / 100., " hPa"
90     end if
91     end do
92     end do
93 guez 171 call abort_gcm("test_disvert", "bad order of pressure values")
94 guez 116 end if
95    
96 guez 175 1000 format (3(a, g11.4, a, i0))
97 guez 99
98     end subroutine test_disvert
99    
100     end module test_disvert_m

  ViewVC Help
Powered by ViewVC 1.1.21