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