/[lmdze]/trunk/phylmd/getso4fromfile.f
ViewVC logotype

Annotation of /trunk/phylmd/getso4fromfile.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 105 - (hide annotations)
Thu Sep 4 10:40:24 2014 UTC (9 years, 8 months ago) by guez
File size: 2183 byte(s)
Removed intermediate variables in calcul_fluxs.
1 guez 69 module getso4fromfile_m
2 guez 68
3 guez 69 implicit none
4 guez 68
5 guez 69 contains
6 guez 68
7 guez 69 SUBROUTINE getso4fromfile(cyr, so4)
8 guez 68
9 guez 69 ! Routine for reading SO4 data from files
10 guez 68
11 guez 69 USE dimens_m, ONLY: iim, jjm
12     USE dimphy, ONLY: klev
13     USE netcdf, ONLY: nf90_nowrite
14     USE netcdf95, ONLY: nf95_close, nf95_get_var, nf95_inq_varid, nf95_open
15 guez 68
16 guez 69 CHARACTER(len=*), intent(in):: cyr
17     double precision so4(iim, jjm + 1, klev, 12)
18 guez 68
19 guez 69 ! Local:
20 guez 68
21 guez 69 CHARACTER(len=15) fname
22 guez 68
23 guez 105 CHARACTER(len=6) cvar
24 guez 69 INTEGER START(3), COUNT(3)
25     INTEGER NCID, VARID
26     INTEGER imth, i, j, k
27 guez 68
28 guez 69 double precision so4mth(iim, jjm + 1, klev)
29 guez 68
30 guez 69 !---------------------------------------------------------------------
31    
32     fname = 'so4.run'//cyr//'.cdf'
33    
34     write(*,*) 'reading ', fname
35     call NF95_OPEN(fname, NF90_NOWRITE, NCID)
36    
37     DO imth=1, 12
38     IF (imth.eq.1) THEN
39     cvar='SO4JAN'
40     ELSEIF (imth.eq.2) THEN
41     cvar='SO4FEB'
42     ELSEIF (imth.eq.3) THEN
43     cvar='SO4MAR'
44     ELSEIF (imth.eq.4) THEN
45     cvar='SO4APR'
46     ELSEIF (imth.eq.5) THEN
47     cvar='SO4MAY'
48     ELSEIF (imth.eq.6) THEN
49     cvar='SO4JUN'
50     ELSEIF (imth.eq.7) THEN
51     cvar='SO4JUL'
52     ELSEIF (imth.eq.8) THEN
53     cvar='SO4AUG'
54     ELSEIF (imth.eq.9) THEN
55     cvar='SO4SEP'
56     ELSEIF (imth.eq.10) THEN
57     cvar='SO4OCT'
58     ELSEIF (imth.eq.11) THEN
59     cvar='SO4NOV'
60     ELSEIF (imth.eq.12) THEN
61     cvar='SO4DEC'
62     ENDIF
63     start(1)=1
64     start(2)=1
65     start(3)=1
66     count(1)=iim
67     count(2)=jjm + 1
68     count(3)=klev
69     call NF95_INQ_VARID(NCID, cvar, VARID)
70     write(*,*) ncid,imth,cvar, varid
71    
72     call NF95_GET_VAR(NCID, VARID, so4mth, START,COUNT)
73    
74     DO k=1,klev
75     DO j=1,jjm+1
76     DO i=1,iim
77     IF (so4mth(i,j,k).LT.0.) then
78     write(*,*) 'this is shit'
79     write(*,*) 'so4(',i,j,k,') =',so4mth(i,j,k)
80     endif
81     so4(i,j,k,imth)=so4mth(i,j,k)
82     ENDDO
83     ENDDO
84     ENDDO
85     ENDDO
86    
87     call NF95_CLOSE(NCID)
88    
89     END SUBROUTINE getso4fromfile
90    
91     end module getso4fromfile_m

  ViewVC Help
Powered by ViewVC 1.1.21