source: LMDZ5/trunk/libf/phylmd/cv3_crit.F @ 1907

Last change on this file since 1907 was 1907, checked in by lguez, 10 years ago

Added a copyright property to every file of the distribution, except
for the fcm files (which have their own copyright). Use svn propget on
a file to see the copyright. For instance:

$ svn propget copyright libf/phylmd/physiq.F90
Name of program: LMDZ
Creation date: 1984
Version: LMDZ5
License: CeCILL version 2
Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
See the license file in the root directory

Also added the files defining the CeCILL version 2 license, in French
and English, at the top of the LMDZ tree.

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 1.8 KB
Line 
1        SUBROUTINE CV3_CRIT (nloc,ncum,nd,icb,inb,p,ph,pzero
2     $             ,v,threshold,kcrit,pcrit)
3***************************************************************
4*                                                             *
5* CV3_CRIT   Find pressure level where vertical profile of    *
6*            variable 'v' intersects 'threshold'              *
7*                                                             *
8* written by   : FROHWIRTH Julie, 13/08/2003, 21.55.12        *
9* modified by :                                               *
10***************************************************************
11*
12
13#include "cv3param.h"
14
15c input:
16      integer ncum, nd, nloc
17      integer icb(nloc), inb(nloc)
18      real p(nloc,nd), ph(nloc,nd+1)
19      real pzero(nloc)
20      real v(nloc,nd),threshold
21
22c output:
23      integer kcrit(nloc)
24      real pcrit(nloc)
25
26c local variables
27      integer i,j,k,il
28      logical ok(nloc)
29
30      do il = 1,ncum
31        ok(il) = .true.
32        pcrit(il) = -1.
33        kcrit(il) = 0
34      enddo
35c
36      DO i = 1,nl
37        DO il = 1,ncum
38        IF (i .GT. icb(il) .AND. i .LE. inb(il)) THEN
39        IF (P(il,i) .LE. Pzero(il) .AND. ok(il)) THEN
40          IF ( (v(il,i)-threshold)*(v(il,i-1)-threshold) .LT. 0.) THEN
41            pcrit(il) =
42     $       ((threshold-v(il,i))*P(il,i-1)-
43     $        (threshold-v(il,i-1))*P(il,i))
44     $           /(v(il,i-1)-v(il,i))
45           IF (pcrit(il) .gt. Pzero(il)) THEN
46            pcrit(il) = -1.
47           ELSE
48            ok(il) = .false.
49            kcrit(il) = i
50            IF (pcrit(il) .LT. PH(il,i)) kcrit(il) = kcrit(il)+1
51           ENDIF
52          ENDIF  ! end IF (v(i) ...
53        ENDIF    ! end IF (P(i) ...
54        ENDIF    ! end IF (icb+1 le i le inb)
55        ENDDO
56      ENDDO
57125   CONTINUE
58
59
60      RETURN
61      END
Note: See TracBrowser for help on using the repository browser.