/[lmdze]/trunk/libf/phylmd/minmaxqfi.f90
ViewVC logotype

Annotation of /trunk/libf/phylmd/minmaxqfi.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 17 - (hide annotations)
Tue Aug 5 13:31:32 2008 UTC (15 years, 9 months ago) by guez
File size: 959 byte(s)
Created rule for "compare_sampl_*" files in
"Documentation/Manuel_LMDZE.texfol/Graphiques/GNUmakefile".

Extracted "qcheck", "radiornpb", "minmaxqfi" into separate files.

Read pressure coordinate of ozone coefficients once per run instead of
every day.

Added some "intent" attributes.

Added argument "nq" to "ini_histday". Replaced calls to "gr_fi_ecrit"
by calls to "gr_phy_write_2d". "Sigma_O3_Royer" is written to
"histday.nc" only if "nq >= 4". Moved "ini_histrac" to module
"ini_hist".

Compute "zmasse" in "physiq", pass it to "phytrac".

Removed computations of "pftsol*" and "ppsrf*" in "phytrac".

Do not use variable "rg" from module "YOMCST" in "TLIFT".

1 guez 17 module minmaxqfi_m
2    
3     IMPLICIT none
4    
5     contains
6    
7     SUBROUTINE minmaxqfi(zq, qmin, qmax, comment)
8    
9     ! From phylmd/minmaxqfi.F, version 1.1.1.1 2004/05/19 12:53:09
10    
11     use dimens_m, only: llm
12     use dimphy, only: klon
13     use numer_rec, only: assert
14    
15     real, intent(in):: zq(:, :), qmin, qmax
16     CHARACTER(len=*), intent(in):: comment
17    
18     ! Variables local to the procedure:
19    
20     INTEGER jadrs(klon), jbad, k, i
21    
22     !---------------------------------
23    
24     call assert(shape(zq) == (/klon, llm/), "minmaxqfi")
25    
26     DO k = 1, llm
27     jbad = 0
28     DO i = 1, klon
29     IF (zq(i, k) > qmax .OR. zq(i, k) < qmin) THEN
30     jbad = jbad + 1
31     jadrs(jbad) = i
32     ENDIF
33     ENDDO
34     IF (jbad > 0) THEN
35     PRINT *, comment
36     DO i = 1, jbad
37     PRINT *, "zq(", jadrs(i), ", ", k, ") = ", zq(jadrs(i), k)
38     ENDDO
39     ENDIF
40     ENDDO
41    
42     end SUBROUTINE minmaxqfi
43    
44     end module minmaxqfi_m

  ViewVC Help
Powered by ViewVC 1.1.21