Changeset 600


Ignore:
Timestamp:
Feb 25, 2005, 6:01:31 PM (19 years ago)
Author:
Laurent Fairhead
Message:

Pour etre synchro avec la version qui a tourne pour IPCC, SD
LF

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ.3.3/branches/rel-LF/libf/phylmd/readsulfate.F

    r523 r600  
     1c
     2c $Header$
     3c
    14      SUBROUTINE readsulfate (r_day, first, sulfate)
    25     
     
    4851c ----------------     
    4952      INTEGER i, ig, k, it
    50       INTEGER j, iday, ny, iyr
     53      INTEGER j, iday, ny, iyr, iyr1, iyr2
    5154      parameter (ny=jjm+1)
    5255     
    5356      INTEGER ismaller
    54       INTEGER idec1, idec2 ! The two decadal data read ini
     57CJLD      INTEGER idec1, idec2 ! The two decadal data read ini
    5558      CHARACTER*4 cyear
    5659     
     
    100103      ENDDO
    101104
    102       IF (iyr .lt. 1930) THEN
    103          WRITE(*,*) 'iyr=', iyr
     105
     106      IF (iyr .lt. 1850) THEN
    104107         cyear='.nat'
     108         WRITE(*,*) 'getso4  iyr=', iyr,'   ',cyear
     109         CALL getso4fromfile(cyear, so4_1)
     110      ELSE IF (iyr .ge. 2100) THEN
     111         cyear='2100'
     112         WRITE(*,*) 'getso4  iyr=', iyr,'   ',cyear
    105113         CALL getso4fromfile(cyear, so4_1)
    106114      ELSE
    107115
    108       ! Read in data:
     116        ! Read in data:
    109117      ! a) from actual 10-yr-period
    110118
    111       idec1 = (iyr-1900)/10
    112       IF (idec1.LT.10) THEN
    113          cyear='19'//char(idec1+48)//'0'
    114       ELSE         
    115          cyear='20'//char(idec1-10+48)//'0'
     119      IF (iyr.LT.1900) THEN
     120         iyr1 = 1850
     121         iyr2 = 1900
     122      ELSE IF (iyr.ge.1900.and.iyr.lt.1920) THEN
     123         iyr1 = 1900
     124         iyr2 = 1920
     125      ELSE
     126         iyr1 = INT(iyr/10)*10
     127         iyr2 = INT(1+iyr/10)*10
    116128      ENDIF
     129      WRITE(cyear,'(I4)') iyr1
     130      WRITE(*,*) 'getso4  iyr=', iyr,'   ',cyear
    117131      CALL getso4fromfile(cyear, so4_1)
    118132
     
    120134      ! If to read two decades:
    121135      IF (.NOT.lonlyone) THEN
    122       idec2=idec1+1
    123136         
    124137      ! b) from the next following one
    125       IF (idec2.LT.10) THEN
    126          cyear='19'//char(idec2+48)//'0'
    127       ELSE
    128          cyear='20'//char(idec2-10+48)//'0'
     138      WRITE(cyear,'(I4)') iyr2
     139      WRITE(*,*) 'getso4  iyr=', iyr,'   ',cyear
     140      CALL getso4fromfile(cyear, so4_2)
     141
    129142      ENDIF
    130       CALL getso4fromfile(cyear, so4_2)
    131          
    132       ENDIF
    133        
     143 
    134144      ! Interpolate linarily to the actual year:
    135145      DO it=1,12
     
    138148               DO i=1,iim
    139149                  so4_1(i,j,k,it)=so4_1(i,j,k,it)
    140      .                 - FLOAT(iyr-1900-10*idec1)/10.
     150     .                 - FLOAT(iyr-iyr1)/FLOAT(iyr2-iyr1)
    141151     .                 * (so4_1(i,j,k,it) - so4_2(i,j,k,it))
    142152               ENDDO
     
    231241
    232242     
    233       ! The sulfate concentration [molec cm-3] is read in.
    234       ! Convert it into mass [ug SO4/m3]
    235       ! masse_so4 in [g/mol], n_avogadro in [molec/mol]
     243CJLD      ! The sulfate concentration [molec cm-3] is read in.
     244CJLD      ! Convert it into mass [ug SO4/m3]
     245CJLD      ! masse_so4 in [g/mol], n_avogadro in [molec/mol]
     246      ! The sulfate mass [ug SO4/m3] is read in.
    236247      DO k=1,klev
    237248         DO i=1,klon
    238             sulfate(i,k) = sulfate(i,k)*masse_so4
    239      .           /n_avogadro*1.e+12
     249CJLD            sulfate(i,k) = sulfate(i,k)*masse_so4
     250CJLD     .           /n_avogadro*1.e+12
    240251            so4_out(i,k) = sulfate(i,k)
    241252            IF (so4_out(i,k).LT.0)
     
    448459
    449460     
    450       ! The sulfate concentration [molec cm-3] is read in.
    451       ! Convert it into mass [ug SO4/m3]
    452       ! masse_so4 in [g/mol], n_avogadro in [molec/mol]
     461CJLD      ! The sulfate concentration [molec cm-3] is read in.
     462CJLD      ! Convert it into mass [ug SO4/m3]
     463CJLD      ! masse_so4 in [g/mol], n_avogadro in [molec/mol]
    453464      DO k=1,klev
    454465         DO i=1,klon
    455             pi_sulfate(i,k) = pi_sulfate(i,k)*masse_so4
    456      .           /n_avogadro*1.e+12
     466CJLD            pi_sulfate(i,k) = pi_sulfate(i,k)*masse_so4
     467CJLD     .           /n_avogadro*1.e+12
    457468            pi_so4_out(i,k) = pi_sulfate(i,k)
    458469         ENDDO
Note: See TracChangeset for help on using the changeset viewer.