/[lmdze]/trunk/Sources/phylmd/readsulfate_preind.f
ViewVC logotype

Diff of /trunk/Sources/phylmd/readsulfate_preind.f

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

revision 190 by guez, Tue Mar 22 16:31:39 2016 UTC revision 191 by guez, Mon May 9 19:56:28 2016 UTC
# Line 4  module readsulfate_preind_m Line 4  module readsulfate_preind_m
4    
5  contains  contains
6    
7    SUBROUTINE readsulfate_preind(dayvrai, time, first, pi_sulfate)    SUBROUTINE readsulfate_preind(dayvrai, time, first, sulfate)
8    
9      ! Read in /calculate pre-industrial values of sulfate      ! Read and calculate pre-industrial values of sulfate. This
10        ! routine reads monthly mean values of sulfate aerosols and
11        ! returns a linearly interpolated daily-mean field. It does so for
12        ! the preindustriel values of the sulfate, to a large part
13        ! analogous to the routine readsulfate.
14    
15        ! Author:
16        ! Johannes Quaas (quaas@lmd.jussieu.fr)
17        ! June 26th, 2001
18    
19      use dimens_m      use dimens_m, only: iim, jjm
20      use dimphy      use dimphy, only: klon, klev
21      use dynetat0_m, only: annee_ref      use dynetat0_m, only: annee_ref
     use SUPHEC_M  
     use chem  
22      use getso4fromfile_m, only: getso4fromfile      use getso4fromfile_m, only: getso4fromfile
23    
     ! Content:  
     ! --------  
     ! This routine reads in monthly mean values of sulfate aerosols and  
     ! returns a linearly interpolated daily-mean field.  
     !  
     ! It does so for the preindustriel values of the sulfate, to a large part  
     ! analogous to the routine readsulfate.  
     !  
     ! Only Pb: Variables must be saved and don t have to be overwritten!  
     !  
     ! Author:  
     ! -------  
     ! Johannes Quaas (quaas@lmd.jussieu.fr)  
     ! 26/06/01  
     !  
     ! Input:  
     ! ------  
24      integer, intent(in):: dayvrai      integer, intent(in):: dayvrai
25      ! current day number, based at value 1 on January 1st of annee_ref      ! current day number, based at value 1 on January 1st of annee_ref
26    
27      REAL, intent(in):: time ! heure de la journ\'ee en fraction de jour      REAL, intent(in):: time ! heure de la journ\'ee en fraction de jour
28    
29      LOGICAL, intent(in):: first                 ! First timestep      LOGICAL, intent(in):: first ! First timestep
30      ! (and therefore initialization necessary)      ! (and therefore initialization necessary)
31      !  
32      ! Output:      real, intent(out):: sulfate (klon, klev)
33      ! -------      ! number concentration sulfate (monthly mean data, from file)
34      real pi_sulfate (klon, klev)  ! Number conc. sulfate (monthly mean data,  
35      !  from file)      ! Local:
     !  
     ! Local Variables:  
     ! ----------------  
36      INTEGER i, ig, k, it      INTEGER i, ig, k, it
37      INTEGER j, iday, iyr      INTEGER j, iday, iyr
   
38      INTEGER im, day1, day2, im2      INTEGER im, day1, day2, im2
39      double precision pi_so4_1(iim, jjm+1, klev, 12)      real so4_1(iim, jjm + 1, klev, 12)
40        double precision, save:: so4(klon, klev, 12) ! SO4 in right dimension
41      double precision pi_so4(klon, klev, 12)  ! SO4 in right dimension      double precision, save:: so4_out(klon, klev)
     SAVE pi_so4  
     double precision pi_so4_out(klon, klev)  
     SAVE pi_so4_out  
   
     CHARACTER(len=4) cyear  
42      LOGICAL lnewday      LOGICAL lnewday
43    
44        !----------------------------------------------------------------
45    
46      iday = dayvrai      iday = dayvrai
47    
48      ! Get the year of the run      ! Get the year of the run
49      iyr  = iday/360      iyr = iday/360
50    
51      ! Get the day of the actual year:      ! Get the day of the actual year:
52      iday = iday-iyr*360      iday = iday - iyr*360
53    
54      ! 0.02 is about 0.5/24, namly less than half an hour      ! 0.02 is about 0.5/24, namly less than half an hour
55      lnewday = time < 0.02      lnewday = time < 0.02
56    
57      ! ---------------------------------------------      ! All has to be done only, if a new day begins
     ! All has to be done only, if a new day begins!  
     ! ---------------------------------------------  
58    
59      IF (lnewday.OR.first) THEN      test_newday: IF (lnewday .OR. first) THEN
60         im = iday/30 +1 ! the actual month         im = iday/30 + 1 ! the actual month
61    
62         ! annee_ref is the initial year (defined in temps.h)         ! annee_ref is the initial year (defined in temps.h)
63         iyr = iyr + annee_ref         iyr = iyr + annee_ref
64    
   
65         IF (first) THEN         IF (first) THEN
           cyear='.nat'  
           CALL getso4fromfile(cyear,pi_so4_1)  
   
           ! Transform the horizontal 2D-field into the physics-field  
           ! (Also the levels and the latitudes have to be inversed)  
   
66            ! Initialize field            ! Initialize field
67            DO it=1,12            DO it = 1, 12
68               DO k=1,klev               DO k = 1, klev
69                  DO i=1,klon                  DO i = 1, klon
70                     pi_so4(i,k,it)=0.                     so4(i, k, it) = 0.
71                  ENDDO                  ENDDO
72               ENDDO               ENDDO
73            ENDDO            ENDDO
74    
75            write (*,*) 'preind: finished reading', FLOAT(iim)            CALL getso4fromfile('.nat', so4_1)
76            DO it=1,12  
77               DO k=1, klev            ! Transform the horizontal 2D-field into the physics-field
78              ! (Also the levels and the latitudes have to be inversed)
79    
80              DO it = 1, 12
81                 DO k = 1, klev
82                  ! a) at the poles, use the zonal mean:                  ! a) at the poles, use the zonal mean:
83                  DO i=1,iim                  DO i = 1, iim
84                     ! North pole                     ! North pole
85                     pi_so4(1,k,it)=pi_so4(1,k,it)+pi_so4_1(i,jjm+1,klev+1-k,it)                     so4(1, k, it) = so4(1, k, it) &
86                            + so4_1(i, jjm + 1, klev + 1 - k, it)
87                     ! South pole                     ! South pole
88                     pi_so4(klon,k,it)=pi_so4(klon,k,it)+pi_so4_1(i,1,klev+1-k,it)                     so4(klon, k, it) = so4(klon, k, it) &
89                            + so4_1(i, 1, klev + 1 - k, it)
90                  ENDDO                  ENDDO
91                  pi_so4(1,k,it)=pi_so4(1,k,it)/FLOAT(iim)                  so4(1, k, it) = so4(1, k, it)/REAL(iim)
92                  pi_so4(klon,k,it)=pi_so4(klon,k,it)/FLOAT(iim)                  so4(klon, k, it) = so4(klon, k, it)/REAL(iim)
93    
94                  ! b) the values between the poles:                  ! b) the values between the poles:
95                  ig=1                  ig = 1
96                  DO j=2,jjm                  DO j = 2, jjm
97                     DO i=1,iim                     DO i = 1, iim
98                        ig=ig+1                        ig = ig + 1
99                        if (ig.gt.klon) write (*,*) 'shit'                        if (ig > klon) stop 1
100                        pi_so4(ig,k,it) = pi_so4_1(i,jjm+1-j,klev+1-k,it)                        so4(ig, k, it) = so4_1(i, jjm + 1 - j, klev + 1 - k, it)
101                     ENDDO                     ENDDO
102                  ENDDO                  ENDDO
103                  IF (ig.NE.klon-1) STOP 'Error in readsulfate (var conversion)'                  IF (ig /= klon - 1) then
104                       print *, 'Error in readsulfate (var conversion)'
105                       STOP 1
106                    end IF
107               ENDDO ! Loop over k (vertical)               ENDDO ! Loop over k (vertical)
108            ENDDO ! Loop over it (months)            ENDDO ! Loop over it (months)
109           ENDIF ! Had to read new data?
        ENDIF                     ! Had to read new data?  
   
110    
111         ! Interpolate to actual day:         ! Interpolate to actual day:
112         IF (iday.LT.im*30-15) THEN         IF (iday < im*30 - 15) THEN
113            ! in the first half of the month use month before and actual month            ! in the first half of the month use month before and actual month
114            im2=im-1            im2 = im - 1
115            day1 = im2*30+15            day1 = im2*30 + 15
116            day2 = im2*30-15            day2 = im2*30 - 15
117            IF (im2.LE.0) THEN            IF (im2 <= 0) THEN
118               ! the month is january, thus the month before december               ! the month is january, thus the month before december
119               im2=12               im2 = 12
120            ENDIF            ENDIF
121            DO k=1,klev            DO k = 1, klev
122               DO i=1,klon               DO i = 1, klon
123                  pi_sulfate(i,k) = pi_so4(i,k,im2)   &                  sulfate(i, k) = so4(i, k, im2) &
124                       - FLOAT(iday-day2)/FLOAT(day1-day2) &                       - REAL(iday - day2)/REAL(day1 - day2) &
125                       * (pi_so4(i,k,im2) - pi_so4(i,k,im))                       * (so4(i, k, im2) - so4(i, k, im))
126                  IF (pi_sulfate(i,k).LT.0.) THEN                  IF (sulfate(i, k) < 0.) THEN
127                     IF (iday-day2.LT.0.) write(*,*) 'iday-day2',iday-day2                     IF (iday - day2 < 0.) write(*, *) 'iday - day2', iday - day2
128                     IF (pi_so4(i,k,im2) - pi_so4(i,k,im).LT.0.) &                     IF (so4(i, k, im2) - so4(i, k, im) < 0.) &
129                          write(*,*) 'pi_so4(i,k,im2) - pi_so4(i,k,im)', &                          write(*, *) 'so4(i, k, im2) - so4(i, k, im)', &
130                          pi_so4(i,k,im2) - pi_so4(i,k,im)                          so4(i, k, im2) - so4(i, k, im)
131                     IF (day1-day2.LT.0.) write(*,*) 'day1-day2',day1-day2                     IF (day1 - day2 < 0.) write(*, *) 'day1 - day2', day1 - day2
132                     stop 'pi_sulfate'                     stop 1
133                  endif                  endif
134               ENDDO               ENDDO
135            ENDDO            ENDDO
136         ELSE         ELSE
137            ! the second half of the month            ! the second half of the month
138            im2=im+1            im2 = im + 1
139            day1 = im*30+15            IF (im2 > 12) THEN
           IF (im2.GT.12) THEN  
140               ! the month is december, the following thus january               ! the month is december, the following thus january
141               im2=1               im2 = 1
142            ENDIF            ENDIF
143            day2 = im*30-15            day2 = im*30 - 15
144              day1 = im*30 + 15
145            DO k=1,klev            DO k = 1, klev
146               DO i=1,klon               DO i = 1, klon
147                  pi_sulfate(i,k) = pi_so4(i,k,im2)   &                  sulfate(i, k) = so4(i, k, im2) &
148                       - FLOAT(iday-day2)/FLOAT(day1-day2) &                       - REAL(iday - day2)/REAL(day1 - day2) &
149                       * (pi_so4(i,k,im2) - pi_so4(i,k,im))                       * (so4(i, k, im2) - so4(i, k, im))
150                  IF (pi_sulfate(i,k).LT.0.) THEN                  IF (sulfate(i, k) < 0.) THEN
151                     IF (iday-day2.LT.0.) write(*,*) 'iday-day2',iday-day2                     IF (iday - day2 < 0.) write(*, *) 'iday - day2', iday - day2
152                     IF (pi_so4(i,k,im2) - pi_so4(i,k,im).LT.0.) &                     IF (so4(i, k, im2) - so4(i, k, im) < 0.) &
153                          write(*,*) 'pi_so4(i,k,im2) - pi_so4(i,k,im)', &                          write(*, *) 'so4(i, k, im2) - so4(i, k, im)', &
154                          pi_so4(i,k,im2) - pi_so4(i,k,im)                          so4(i, k, im2) - so4(i, k, im)
155                     IF (day1-day2.LT.0.) write(*,*) 'day1-day2',day1-day2                     IF (day1 - day2 < 0.) write(*, *) 'day1 - day2', day1 - day2
156                     stop 'pi_sulfate'                     stop 1
157                  endif                  endif
158               ENDDO               ENDDO
159            ENDDO            ENDDO
160         ENDIF         ENDIF
161    
162           DO k = 1, klev
163         !JLD      ! The sulfate concentration [molec cm-3] is read in.            DO i = 1, klon
164         !JLD      ! Convert it into mass [ug SO4/m3]               so4_out(i, k) = sulfate(i, k)
        !JLD      ! masse_so4 in [g/mol], n_avogadro in [molec/mol]  
        DO k=1,klev  
           DO i=1,klon  
              !JLD            pi_sulfate(i,k) = pi_sulfate(i,k)*masse_so4  
              !JLD     .           /n_avogadro*1.e+12  
              pi_so4_out(i,k) = pi_sulfate(i,k)  
165            ENDDO            ENDDO
166         ENDDO         ENDDO
167        ELSE
168      ELSE ! If no new day, use old data:         ! If no new day, use old data:
169         DO k=1,klev         DO k = 1, klev
170            DO i=1,klon            DO i = 1, klon
171               pi_sulfate(i,k) = pi_so4_out(i,k)               sulfate(i, k) = so4_out(i, k)
172            ENDDO            ENDDO
173         ENDDO         ENDDO
174      ENDIF ! Was this the beginning of a new day?      ENDIF test_newday
175    
176    END SUBROUTINE readsulfate_preind    END SUBROUTINE readsulfate_preind
177    

Legend:
Removed from v.190  
changed lines
  Added in v.191

  ViewVC Help
Powered by ViewVC 1.1.21