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

Diff of /trunk/phylmd/getso4fromfile.f

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 68 by guez, Wed Nov 14 16:59:30 2012 UTC revision 69 by guez, Mon Feb 18 16:33:12 2013 UTC
# Line 1  Line 1 
1  SUBROUTINE getso4fromfile (cyr, so4)  module getso4fromfile_m
2    
3    ! Routine for reading SO4 data from files    implicit none
4    
5    use dimens_m  contains
   use dimphy  
   use netcdf  
   CHARACTER*15 fname  
   CHARACTER*4 cyr  
   
   CHARACTER*6 cvar  
   INTEGER START(3), COUNT(3)  
   INTEGER  STATUS, NCID, VARID  
   INTEGER imth, i, j, k, ny  
   PARAMETER (ny=jjm+1)  
   
   
   double precision so4mth(iim, ny, klev)  
   double precision so4(iim, ny, klev, 12)  
   
   
   fname = 'so4.run'//cyr//'.cdf'  
   
   write (*,*) 'reading ', fname  
   STATUS = NF_OPEN (fname, NF_NOWRITE, NCID)  
   IF (STATUS .NE. NF_NOERR) write (*,*) 'err in open ',status  
   
   DO imth=1, 12  
      IF (imth.eq.1) THEN  
         cvar='SO4JAN'  
      ELSEIF (imth.eq.2) THEN  
         cvar='SO4FEB'  
      ELSEIF (imth.eq.3) THEN  
         cvar='SO4MAR'  
      ELSEIF (imth.eq.4) THEN  
         cvar='SO4APR'  
      ELSEIF (imth.eq.5) THEN  
         cvar='SO4MAY'  
      ELSEIF (imth.eq.6) THEN  
         cvar='SO4JUN'  
      ELSEIF (imth.eq.7) THEN  
         cvar='SO4JUL'  
      ELSEIF (imth.eq.8) THEN  
         cvar='SO4AUG'  
      ELSEIF (imth.eq.9) THEN  
         cvar='SO4SEP'  
      ELSEIF (imth.eq.10) THEN  
         cvar='SO4OCT'  
      ELSEIF (imth.eq.11) THEN  
         cvar='SO4NOV'  
      ELSEIF (imth.eq.12) THEN  
         cvar='SO4DEC'  
      ENDIF  
      start(1)=1  
      start(2)=1  
      start(3)=1  
      count(1)=iim  
      count(2)=ny  
      count(3)=klev  
      !         write(*,*) 'here i am'  
      STATUS = NF_INQ_VARID (NCID, cvar, VARID)  
      write (*,*) ncid,imth,cvar, varid  
      !         STATUS = NF_INQ_VARID (NCID, VARMONTHS(i), VARID(i))  
      IF (STATUS .NE. NF_NOERR) write (*,*) 'err in read ',status  
      STATUS = NF_GET_VARA_DOUBLE &  
           (NCID, VARID, START,COUNT, so4mth)  
      IF (STATUS .NE. NF_NOERR) write (*,*) 'err in read data',status  
   
      DO k=1,klev  
         DO j=1,jjm+1  
            DO i=1,iim  
               IF (so4mth(i,j,k).LT.0.) then  
                  write(*,*) 'this is shit'  
                  write(*,*) 'so4(',i,j,k,') =',so4mth(i,j,k)  
               endif  
               so4(i,j,k,imth)=so4mth(i,j,k)  
               !                  so4(i,j,k,imth)=so4mth(k,j,i)  
            ENDDO  
         ENDDO  
      ENDDO  
   ENDDO  
6    
7    STATUS = NF_CLOSE(NCID)    SUBROUTINE getso4fromfile(cyr, so4)
8  END SUBROUTINE getso4fromfile  
9        ! Routine for reading SO4 data from files
10    
11        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    
16        CHARACTER(len=*), intent(in):: cyr
17        double precision so4(iim, jjm + 1, klev, 12)
18    
19        ! Local:
20    
21        CHARACTER(len=15) fname
22    
23        CHARACTER*6 cvar
24        INTEGER START(3), COUNT(3)
25        INTEGER  NCID, VARID
26        INTEGER imth, i, j, k
27    
28        double precision so4mth(iim, jjm + 1, klev)
29    
30        !---------------------------------------------------------------------
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

Legend:
Removed from v.68  
changed lines
  Added in v.69

  ViewVC Help
Powered by ViewVC 1.1.21