source: LMDZ6/trunk/libf/phylmd/StratAer/minmaxsimple.f90 @ 5279

Last change on this file since 5279 was 5268, checked in by abarral, 3 days ago

.f90 <-> .F90 depending on cpp key use

  • Property svn:keywords set to Id
File size: 500 bytes
Line 
1!
2! $Id: minmaxsimple.f90 5268 2024-10-23 17:02:39Z abarral $
3!
4SUBROUTINE minmaxsimple(zq,qmin,qmax,comment)
5  USE dimphy
6  IMPLICIT NONE
7
8! Entrees
9  REAL,DIMENSION(klon,klev), INTENT(IN)   :: zq
10  REAL,INTENT(IN)                         :: qmin,qmax
11  CHARACTER(LEN=*),INTENT(IN)             :: comment
12
13! Local 
14  REAL zmin, zmax
15 
16  zmin=MINVAL(zq)
17  zmax=MAXVAL(zq)
18  PRINT *, "qmin qmax=", zmin, zmax, comment
19!  IF (zmin.LT.qmin.OR.zmax.GT.qmax) THEN
20!      WRITE(*,*) "qmin qmax=", zmin, zmax, comment
21!  ENDIF
22 
23END SUBROUTINE minmaxsimple
Note: See TracBrowser for help on using the repository browser.