/[lmdze]/trunk/libf/phylmd/CV_routines/cv_uncompress.f90
ViewVC logotype

Contents of /trunk/libf/phylmd/CV_routines/cv_uncompress.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 52 - (show annotations)
Fri Sep 23 12:28:01 2011 UTC (12 years, 7 months ago) by guez
File size: 1364 byte(s)
Split "conflx.f" into single-procedure files in directory "Conflx".

Split "cv_routines.f" into single-procedure files in directory
"CV_routines". Made module "cvparam" from included file
"cvparam.h". No included file other than "netcdf.inc" left in LMDZE.

1
2 SUBROUTINE cv_uncompress(nloc,len,ncum,nd,idcum &
3 ,iflag &
4 ,precip,cbmf &
5 ,ft,fq,fu,fv &
6 ,Ma,qcondc &
7 ,iflag1 &
8 ,precip1,cbmf1 &
9 ,ft1,fq1,fu1,fv1 &
10 ,Ma1,qcondc1 &
11 )
12 use cvparam
13 implicit none
14
15
16 ! inputs:
17 integer len, ncum, nd, nloc
18 integer idcum(nloc)
19 integer iflag(nloc)
20 real precip(nloc), cbmf(nloc)
21 real ft(nloc,nd), fq(nloc,nd), fu(nloc,nd), fv(nloc,nd)
22 real Ma(nloc,nd)
23 real qcondc(nloc,nd) !cld
24
25 ! outputs:
26 integer iflag1(len)
27 real precip1(len), cbmf1(len)
28 real ft1(len,nd), fq1(len,nd), fu1(len,nd), fv1(len,nd)
29 real Ma1(len,nd)
30 real qcondc1(len,nd) !cld
31
32 ! local variables:
33 integer i,k
34
35 do 2000 i=1,ncum
36 precip1(idcum(i))=precip(i)
37 cbmf1(idcum(i))=cbmf(i)
38 iflag1(idcum(i))=iflag(i)
39 2000 continue
40
41 do 2020 k=1,nl
42 do 2010 i=1,ncum
43 ft1(idcum(i),k)=ft(i,k)
44 fq1(idcum(i),k)=fq(i,k)
45 fu1(idcum(i),k)=fu(i,k)
46 fv1(idcum(i),k)=fv(i,k)
47 Ma1(idcum(i),k)=Ma(i,k)
48 qcondc1(idcum(i),k)=qcondc(i,k)
49 2010 continue
50 2020 continue
51
52 return
53 end

  ViewVC Help
Powered by ViewVC 1.1.21