Ignore:
Timestamp:
Nov 25, 2009, 3:02:45 PM (15 years ago)
Author:
Laurent Fairhead
Message:

Les nouvelles routines de lecture des aerosols posent probleme en multiproc. On revient aux routines
precedentes en incluant le traitement du calendrier realiste.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/readaerosol_interp.F90

    r1269 r1270  
    7979
    8080  REAL, DIMENSION(:,:,:), POINTER   :: pt_tmp      ! Pointer allocated in readaerosol
    81   REAL, DIMENSION(:,:), POINTER     :: pt_tmp_surf ! Pointer allocated in readaerosol
    82   REAL, DIMENSION(:,:), POINTER     :: pt_tmp_load ! Pointer allocated in readaerosol
    83   REAL, DIMENSION(:,:), POINTER     :: pt_tmp_pi_surf ! Pointer allocated in readaerosol
    84   REAL, DIMENSION(:,:), POINTER     :: pt_tmp_pi_load ! Pointer allocated in readaerosol
    8581  REAL, POINTER, DIMENSION(:), SAVE :: pt_ap, pt_b ! Pointer for describing the vertical levels
    8682!$OMP THREADPRIVATE(pt_ap, pt_b)
    8783  INTEGER, SAVE                     :: nbr_tsteps ! number of time steps in file read
    8884  REAL, DIMENSION(14), SAVE         :: month_len, month_start, month_mid
    89 !$OMP THREADPRIVATE(month_len, month_start, month_mid)
     85!$OMP THREADPRIVATE(nbr_tsteps, month_len, month_start, month_mid)
    9086  REAL                              :: jDay
    9187
    92 !$OMP THREADPRIVATE(nbr_tsteps)
    9388  LOGICAL            :: lnewday      ! Indicates if first time step at a new day
    9489  LOGICAL            :: OLDNEWDAY
     
    110105
    111106  ! Use phys_cal_mod
    112 ! iday= day_cur
    113 ! iyr = year_cur
    114 ! im  = mth_cur
     107  !iday= day_cur
     108  !iyr = year_cur
     109  !im  = mth_cur
    115110
    116111  iday = INT(r_day)
     
    153148     IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 2',1)
    154149
    155 !     ALLOCATE( psurf_year(klon, 12, naero_spc), pi_psurf_year(klon, 12, naero_spc), stat=ierr)
    156 !     IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 3',1)
    157 !
    158 !     ALLOCATE( load_year(klon, 12, naero_spc), pi_load_year(klon, 12, naero_spc), stat=ierr)
    159 !     IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 4',1)
     150     ALLOCATE( psurf_year(klon, 12, naero_spc), pi_psurf_year(klon, 12, naero_spc), stat=ierr)
     151     IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 3',1)
     152
     153     ALLOCATE( load_year(klon, 12, naero_spc), pi_load_year(klon, 12, naero_spc), stat=ierr)
     154     IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 4',1)
    160155
    161156     lnewday=.TRUE.
     
    172167  IF ( (first .OR. iday==0) .AND. lnewday ) THEN
    173168     NULLIFY(pt_tmp)
    174      NULLIFY(pt_tmp_surf)
    175      NULLIFY(pt_tmp_pi_surf)
    176      NULLIFY(pt_tmp_load)
    177      NULLIFY(pt_tmp_pi_load)
    178169
    179170     ! Reading values corresponding to the closest year taking into count the choice of aer_type.
    180171     ! For aer_type=scenario interpolation between 2 data sets is done in readaerosol.
    181172     CALL readaerosol(name_aero(id_aero), aer_type, iyr, klev_src, pt_ap, pt_b, pt_tmp, &
    182           pt_tmp_surf,pt_tmp_load,nbr_tsteps)
     173          psurf_year(:,:,id_aero), load_year(:,:,id_aero))
    183174     IF (.NOT. ALLOCATED(var_year)) THEN
    184         ALLOCATE(var_year(klon, klev_src, nbr_tsteps, naero_spc), stat=ierr)
    185         IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 5.1',1)
    186         ALLOCATE( psurf_year(klon, nbr_tsteps, naero_spc), load_year(klon, nbr_tsteps, naero_spc), stat=ierr)
    187         IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 5.2',1)
     175        ALLOCATE(var_year(klon, klev_src, 12, naero_spc), stat=ierr)
     176        IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 5',1)
    188177     END IF
    189178     var_year(:,:,:,id_aero) = pt_tmp(:,:,:)
    190      psurf_year(:,:,id_aero) = pt_tmp_surf(:,:)
    191      load_year(:,:,id_aero) = pt_tmp_load(:,:)
    192179
    193180     ! Reading values corresponding to the preindustrial concentrations.
    194181     CALL readaerosol(name_aero(id_aero), 'preind', iyr, pi_klev_src, pt_ap, pt_b, pt_tmp, &
    195           pt_tmp_surf,pt_tmp_load,nbr_tsteps)
     182          pi_psurf_year(:,:,id_aero), pi_load_year(:,:,id_aero))
    196183
    197184     ! klev_src must be the same in both files.
     
    204191
    205192     IF (.NOT. ALLOCATED(pi_var_year)) THEN
    206         ALLOCATE(pi_var_year(klon, klev_src, nbr_tsteps, naero_spc), stat=ierr)
    207         IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 6.1',1)
    208         ALLOCATE( pi_psurf_year(klon, nbr_tsteps, naero_spc), pi_load_year(klon, nbr_tsteps, naero_spc), stat=ierr)
    209         IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 6.2',1)
     193        ALLOCATE(pi_var_year(klon, klev_src, 12, naero_spc), stat=ierr)
     194        IF (ierr /= 0) CALL abort_gcm('readaerosol_interp', 'pb in allocation 6',1)
    210195     END IF
    211196     pi_var_year(:,:,:,id_aero) = pt_tmp(:,:,:)
    212      pi_psurf_year(:,:,id_aero) = pt_tmp_surf(:,:)
    213      pi_load_year(:,:,id_aero) = pt_tmp_load(:,:)
    214197   
    215198     IF (debug) THEN
    216         CALL writefield_phy('var_year_first',var_year(:,:,1,id_aero),klev_src)
    217         CALL writefield_phy('var_year_last',var_year(:,:,nbr_tsteps,id_aero),klev_src)
     199        CALL writefield_phy('var_year_jan',var_year(:,:,1,id_aero),klev_src)
     200        CALL writefield_phy('var_year_dec',var_year(:,:,12,id_aero),klev_src)
    218201        CALL writefield_phy('psurf_src',psurf_year(:,:,id_aero),1)
    219202        CALL writefield_phy('pi_psurf_src',pi_psurf_year(:,:,id_aero),1)
     
    224207     ! Pointer no more useful, deallocate.
    225208     DEALLOCATE(pt_tmp)
    226      DEALLOCATE(pt_tmp_surf)
    227      DEALLOCATE(pt_tmp_load)
    228209
    229210     ! Test if vertical interpolation will be needed.
     
    259240     month_mid(:) = month_start (:) + month_len(:)/2.
    260241
    261      write(55,*)'month_len = ',month_len
    262      write(55,*)'month_start = ',month_start
    263      write(55,*)'month_mid = ',month_mid
    264        
    265242  END IF  ! IF ( (first .OR. iday==0) .AND. lnewday ) THEN
    266243 
     
    277254!****************************************************************************************
    278255    ! Find which months and days to use for time interpolation
     256     nbr_tsteps = 12
    279257     IF (nbr_tsteps == 12) then
    280258       IF (jDay < month_mid(im+1)) THEN
     
    313291     ENDIF
    314292
    315 !     ! Find which months and days to use for time interpolation
    316 !     IF (iday < im*30-15) THEN
    317 !        ! in the first half of the month use month before and actual month
    318 !        im2=im-1
    319 !        day2 = im2*30-15
    320 !        day1 = im2*30+15
    321 !        IF (im2 <= 0) THEN
    322 !           ! the month is january, thus the month before december
    323 !           im2=12
    324 !        END IF
    325 !     ELSE
    326 !        ! the second half of the month
    327 !        im2=im+1
    328 !        IF (im2 > 12) THEN
    329 !           ! the month is december, the following thus january
    330 !           im2=1
    331 !        ENDIF
    332 !        day2 = im*30-15
    333 !        day1 = im*30+15
    334 !     END IF
    335 !      jDay = jDay+1
    336 !      write(55,*)'iday, jDay, im, im2, day1, day2 = ',iday, jDay, im, im2, day1, day2, nbr_tsteps
    337293 
    338294     ! Time interpolation, still on vertical source grid
Note: See TracChangeset for help on using the changeset viewer.