source: LMDZ5/trunk/libf/phylmd/cv3_buoy.F90 @ 2057

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

Converted to free source form files in libf/phylmd which were still in
fixed source form. The conversion was done using the polish mode of
the NAG Fortran Compiler.

In addition to converting to free source form, the processing of the
files also:

-- indented the code (including comments);

-- set Fortran keywords to uppercase, and set all other identifiers
to lower case;

-- added qualifiers to end statements (for example "end subroutine
conflx", instead of "end");

-- changed the terminating statements of all DO loops so that each
loop ends with an ENDDO statement (instead of a labeled continue).

-- replaced #include by include.

  • 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: 3.6 KB
Line 
1SUBROUTINE cv3_buoy(nloc, ncum, nd, icb, inb, pbase, plcl, p, ph, ale, cin, &
2    tv, tvp, buoy)
3  ! **************************************************************
4  ! *
5  ! CV3_BUOY                                                    *
6  ! Buoyancy corrections to account for ALE             *
7  ! *
8  ! written by   : MOREAU Cecile, 07/08/2003, 15.55.48          *
9  ! modified by :                                               *
10  ! **************************************************************
11
12  IMPLICIT NONE
13
14  include "cvthermo.h"
15  include "cv3param.h"
16
17  ! input:
18  INTEGER ncum, nd, nloc
19  INTEGER icb(nloc), inb(nloc)
20  REAL pbase(nloc), plcl(nloc)
21  REAL p(nloc, nd), ph(nloc, nd+1)
22  REAL ale(nloc), cin(nloc)
23  REAL tv(nloc, nd), tvp(nloc, nd)
24
25  ! output:
26  REAL buoy(nloc, nd)
27
28  ! local variables:
29  INTEGER il, k
30  INTEGER kmx(nloc)
31  REAL bll(nloc), bmx(nloc)
32  REAL gamma(nloc)
33  LOGICAL ok(nloc)
34
35  REAL dgamma
36  REAL buoymin
37  PARAMETER (dgamma=2.E-03) !dgamma gamma
38  PARAMETER (buoymin=2.)
39
40  LOGICAL fixed_bll
41  SAVE fixed_bll
42  DATA fixed_bll/.TRUE./
43  !$OMP THREADPRIVATE(fixed_bll)
44
45
46  ! print *,' Ale+cin ',ale(1)+cin(1)
47  ! --------------------------------------------------------------
48  ! Recompute buoyancies
49  ! --------------------------------------------------------------
50  DO k = 1, nl
51    DO il = 1, ncum
52      buoy(il, k) = tvp(il, k) - tv(il, k)
53    END DO
54  END DO
55
56  ! -------------------------------------------------------------
57  ! -- Compute low level buoyancy ( function of Ale+Cin )
58  ! -------------------------------------------------------------
59  IF (fixed_bll) THEN
60
61    DO il = 1, ncum
62      bll(il) = 0.5
63    END DO
64  ELSE
65
66    DO il = 1, ncum
67      IF (ale(il)+cin(il)>0.) THEN
68        gamma(il) = 4.*buoy(il, icb(il))**2 + 8.*dgamma*(ale(il)+cin(il))*tv( &
69          il, icb(il))/grav
70        gamma(il) = max(gamma(il), 1.E-10)
71      END IF
72    END DO
73
74    DO il = 1, ncum
75      IF (ale(il)+cin(il)>0.) THEN
76        bll(il) = 4.*dgamma*(ale(il)+cin(il))*tv(il, icb(il))/ &
77          (grav*(abs(buoy(il,icb(il))+0.5*sqrt(gamma(il)))))
78      END IF
79    END DO
80
81    DO il = 1, ncum
82      IF (ale(il)+cin(il)>0.) THEN
83        bll(il) = min(bll(il), buoymin)
84      END IF
85    END DO
86
87  END IF !(fixed_bll)
88
89
90  ! -------------------------------------------------------------
91  ! --Get highest buoyancy among levels below LCL-200hPa
92  ! -------------------------------------------------------------
93
94  DO il = 1, ncum
95    bmx(il) = -1000.
96    kmx(il) = icb(il)
97    ok(il) = .TRUE.
98  END DO
99
100  DO k = 1, nl
101    DO il = 1, ncum
102      IF (ale(il)+cin(il)>0. .AND. ok(il)) THEN
103        IF (k>icb(il) .AND. k<=inb(il)) THEN
104          ! c         print *,'k,p(il,k),plcl(il)-200. ',
105          ! k,p(il,k),plcl(il)-200.
106          IF (p(il,k)>plcl(il)-200.) THEN
107            IF (buoy(il,k)>bmx(il)) THEN
108              bmx(il) = buoy(il, k)
109              kmx(il) = k
110              IF (bmx(il)>=bll(il)) ok(il) = .FALSE.
111            END IF
112          END IF
113        END IF
114      END IF
115    END DO
116  END DO
117
118  ! print *,' ==cv3_buoy== bll(1),bmx(1),icb(1),kmx(1) '
119  ! $       ,bll(1),bmx(1),icb(1),kmx(1)
120
121  ! -------------------------------------------------------------
122  ! --Calculate modified buoyancies
123  ! -------------------------------------------------------------
124
125  DO il = 1, ncum
126    IF (ale(il)+cin(il)>0.) THEN
127      bll(il) = min(bll(il), bmx(il))
128    END IF
129  END DO
130
131  DO k = 1, nl
132    DO il = 1, ncum
133      IF (ale(il)+cin(il)>0.) THEN
134        IF (k>=icb(il) .AND. k<=kmx(il)-1) THEN
135          buoy(il, k) = bll(il)
136        END IF
137      END IF
138    END DO
139  END DO
140
141
142
143  RETURN
144END SUBROUTINE cv3_buoy
Note: See TracBrowser for help on using the repository browser.