/[lmdze]/trunk/phylmd/hgardfou.f90
ViewVC logotype

Contents of /trunk/phylmd/hgardfou.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 328 - (show annotations)
Thu Jun 13 14:40:06 2019 UTC (4 years, 11 months ago) by guez
File size: 1594 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 module hgardfou_m
2
3 IMPLICIT none
4
5 contains
6
7 SUBROUTINE hgardfou(t_seri, ftsol)
8
9 ! From phylmd/hgardfou.F, v 1.1.1.1, 2004/05/19 12:53:07
10
11 ! This procedure aborts the program if the temperature gets out of range.
12
13 use abort_gcm_m, only: abort_gcm
14 USE indicesol, ONLY: nbsrf, clnsurf
15 USE dimphy, ONLY: klev, klon
16 use nr_util, only: ifirstloc
17 use phyetat0_m, only: rlon, rlat
18
19 REAL, intent(in):: t_seri(:, :) ! (klon, klev)
20 REAL, intent(in):: ftsol(:, :) ! (klon, nbsrf)
21
22 ! Variables local to the procedure:
23
24 real, parameter:: temp_min = 50., temp_max = 370. ! temperature range, in K
25 INTEGER k, nsrf, jbad
26
27 !----------------------------------------------------------
28
29 DO k = 1, klev
30 jbad = ifirstloc(t_seri(:, k) > temp_max .or. t_seri(:, k) < temp_min)
31 if (jbad <= klon) then
32 print *, "t_seri(", jbad, ", ", k, ") = ", t_seri(jbad, k)
33 call abort_gcm('hgardfou', 'temperature out of range')
34 end if
35 ENDDO
36
37 DO nsrf = 1, nbsrf
38 jbad = ifirstloc(ftsol(:, nsrf) > temp_max &
39 .or. ftsol(:, nsrf) < temp_min)
40 if (jbad <= klon) then
41 print *, "ftsol(position index =", jbad, ", sub-surface index =", &
42 nsrf, ") =", ftsol(jbad, nsrf)
43 print *, "sub-surface name: ", clnsurf(nsrf)
44 print *, "longitude:", rlon(jbad), "degrees east"
45 print *, "latitude:", rlat(jbad), "degrees north"
46 call abort_gcm('hgardfou', 'temperature out of range')
47 ENDIF
48 ENDDO
49
50 END SUBROUTINE hgardfou
51
52 end module hgardfou_m

  ViewVC Help
Powered by ViewVC 1.1.21