/[lmdze]/trunk/Sources/phylmd/CV30_routines/cv3_uncompress.f
ViewVC logotype

Annotation of /trunk/Sources/phylmd/CV30_routines/cv3_uncompress.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 99 - (hide annotations)
Wed Jul 2 18:39:15 2014 UTC (9 years, 10 months ago) by guez
Original Path: trunk/phylmd/CV3_routines/cv3_uncompress.f
File size: 2658 byte(s)
Created procedure test_disvert (following LMDZ). Added procedures
hybrid and funcd in module disvert_m. Upgraded compute_ab from
internal procedure of disvert to module procedure. Added variables y,
ya in module disvert_m. Upgraded s from local variable of procedure
disvert to module variable.

Renamed allowed value of variable vert_sampling in procedure disvert
from "read" to "read_hybrid". Added possibility to read pressure
values, value "read_pressure". Replaced vertical distribution for
value "param" by the distribution "strato_correct" from LMDZ (but kept
the value "param"). In case "tropo", replaced 1 by dsigmin (following
LMDZ). In case "strato", replaced 0.3 by dsigmin (following LMDZ).

Changed computation of bp in procedure compute_ab.

Removed debugindex case in clmain. Removed useless argument rlon of
procedure clmain. Removed useless variables ytaux, ytauy of procedure
clmain.

Removed intermediary variables tsol, qsol, tsolsrf, tslab in procedure
etat0.

Removed variable ok_veget:. coupling with the model Orchid is not
possible. Removed variable ocean: modeling an ocean slab is not
possible.

Removed useless variables tmp_rriv and tmp_rcoa from module
interface_surf.

Moved initialization of variables da, mp, phi in procedure physiq to
to inside the test iflag_con >= 3.

1 guez 97 module cv3_uncompress_m
2 guez 47
3     implicit none
4    
5 guez 97 contains
6 guez 47
7 guez 97 SUBROUTINE cv3_uncompress(nloc, len, ncum, nd, idcum, iflag, precip, &
8     VPrecip, sig, w0, ft, fq, fu, fv, inb, Ma, upwd, dnwd, dnwd0, qcondc, &
9     wd, cape, da, phi, mp, iflag1, precip1, VPrecip1, sig1, w01, ft1, fq1, &
10     fu1, fv1, inb1, Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, cape1, da1, &
11     phi1, mp1)
12 guez 47
13 guez 97 USE cv3_param_m, ONLY: nl
14 guez 47
15 guez 97 ! inputs:
16     integer, intent(in):: nloc, len, ncum, nd
17     integer, intent(in):: idcum(nloc)
18     integer, intent(in):: iflag(nloc)
19     real, intent(in):: precip(nloc)
20     real, intent(in):: VPrecip(nloc, nd+1)
21     real, intent(in):: sig(nloc, nd), w0(nloc, nd)
22     real, intent(in):: ft(nloc, nd), fq(nloc, nd), fu(nloc, nd), fv(nloc, nd)
23     integer, intent(in):: inb(nloc)
24     real, intent(in):: Ma(nloc, nd)
25     real, intent(in):: upwd(nloc, nd), dnwd(nloc, nd), dnwd0(nloc, nd)
26     real, intent(in):: qcondc(nloc, nd)
27     real, intent(in):: wd(nloc), cape(nloc)
28     real, intent(in):: da(nloc, nd), phi(nloc, nd, nd), mp(nloc, nd)
29 guez 47
30 guez 97 ! outputs:
31     integer iflag1(len)
32     real precip1(len)
33     real VPrecip1(len, nd+1)
34     real sig1(len, nd), w01(len, nd)
35     real ft1(len, nd), fq1(len, nd), fu1(len, nd), fv1(len, nd)
36     integer inb1(len)
37     real Ma1(len, nd)
38     real upwd1(len, nd), dnwd1(len, nd), dnwd01(len, nd)
39     real qcondc1(nloc, nd)
40     real wd1(nloc), cape1(nloc)
41 guez 99 real, intent(inout):: da1(nloc, nd), phi1(nloc, nd, nd), mp1(nloc, nd)
42 guez 47
43 guez 97 ! local variables:
44     integer i, k, j
45 guez 47
46 guez 97 !-------------------------------------------------------------------
47 guez 47
48 guez 97 do i=1, ncum
49     precip1(idcum(i))=precip(i)
50     iflag1(idcum(i))=iflag(i)
51     wd1(idcum(i))=wd(i)
52     inb1(idcum(i))=inb(i)
53     cape1(idcum(i))=cape(i)
54     end do
55 guez 47
56 guez 97 do k=1, nl
57     do i=1, ncum
58     VPrecip1(idcum(i), k)=VPrecip(i, k)
59     sig1(idcum(i), k)=sig(i, k)
60     w01(idcum(i), k)=w0(i, k)
61     ft1(idcum(i), k)=ft(i, k)
62     fq1(idcum(i), k)=fq(i, k)
63     fu1(idcum(i), k)=fu(i, k)
64     fv1(idcum(i), k)=fv(i, k)
65     Ma1(idcum(i), k)=Ma(i, k)
66     upwd1(idcum(i), k)=upwd(i, k)
67     dnwd1(idcum(i), k)=dnwd(i, k)
68     dnwd01(idcum(i), k)=dnwd0(i, k)
69     qcondc1(idcum(i), k)=qcondc(i, k)
70     da1(idcum(i), k)=da(i, k)
71     mp1(idcum(i), k)=mp(i, k)
72     end do
73     end do
74    
75     do i=1, ncum
76     sig1(idcum(i), nd)=sig(i, nd)
77     end do
78    
79     do j=1, nd
80     do k=1, nd
81     do i=1, ncum
82     phi1(idcum(i), k, j)=phi(i, k, j)
83     end do
84     end do
85     end do
86    
87     end SUBROUTINE cv3_uncompress
88    
89     end module cv3_uncompress_m

  ViewVC Help
Powered by ViewVC 1.1.21