source: LMDZ5/trunk/libf/phylmd/readaerosol.F90 @ 2823

Last change on this file since 2823 was 2823, checked in by oboucher, 7 years ago

Climatological ASNO3M, CSNO3M, CINO3M aerosol fields can be read and fed
through the aerosol routines for optical properties. The get_aero_fromfile
routine needed some change so that it doesn't stop if a particular field
is not there.

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 25.2 KB
Line 
1! $Id: readaerosol.F90 2823 2017-03-14 22:10:55Z oboucher $
2!
3MODULE readaerosol_mod
4
5  REAL, SAVE :: not_valid=-333.
6
7CONTAINS
8
9SUBROUTINE readaerosol(name_aero, type, filename, iyr_in, klev_src, pt_ap, pt_b, pt_out, psurf, load)
10
11!****************************************************************************************
12! This routine will read the aersosol from file.
13!
14! Read a year data with get_aero_fromfile depending on aer_type :
15! - actuel   : read year 1980
16! - preind   : read natural data
17! - scenario : read one or two years and do eventually linare time interpolation
18!
19! Return pointer, pt_out, to the year read or result from interpolation
20!****************************************************************************************
21  USE dimphy
22  USE print_control_mod, ONLY: lunout
23
24  IMPLICIT NONE
25
26  ! Input arguments
27  CHARACTER(len=7), INTENT(IN) :: name_aero
28  CHARACTER(len=*), INTENT(IN) :: type  ! actuel, annuel, scenario or preind
29  CHARACTER(len=8), INTENT(IN) :: filename
30  INTEGER, INTENT(IN)          :: iyr_in
31
32  ! Output
33  INTEGER, INTENT(OUT)            :: klev_src
34  REAL, POINTER, DIMENSION(:)     :: pt_ap        ! Pointer for describing the vertical levels     
35  REAL, POINTER, DIMENSION(:)     :: pt_b         ! Pointer for describing the vertical levels     
36  REAL, POINTER, DIMENSION(:,:,:) :: pt_out       ! The massvar distributions, DIMENSION(klon, klev_src, 12)
37  REAL, DIMENSION(klon,12), INTENT(OUT) :: psurf  ! Surface pression for 12 months
38  REAL, DIMENSION(klon,12), INTENT(OUT) :: load   ! Aerosol mass load in each column for 12 months
39
40  ! Local variables
41  CHARACTER(len=4)                :: cyear
42  REAL, POINTER, DIMENSION(:,:,:) :: pt_2
43  REAL, DIMENSION(klon,12)        :: psurf2, load2
44  REAL                            :: p0           ! Reference pressure
45  INTEGER                         :: iyr1, iyr2, klev_src2
46  INTEGER                         :: it, k, i
47  LOGICAL, PARAMETER              :: lonlyone=.FALSE.
48
49!****************************************************************************************
50! Read data depending on aer_type
51!
52!****************************************************************************************
53
54  IF (type == 'actuel') THEN
55! Read and return data for year 1980
56!****************************************************************************************
57     cyear='1980'
58     ! get_aero_fromfile returns pt_out allocated and initialized with data for 12 month
59     ! pt_out has dimensions (klon, klev_src, 12)
60     CALL get_aero_fromfile(name_aero, cyear, filename, klev_src, pt_ap, pt_b, p0, pt_out, psurf, load)
61     
62
63  ELSE IF (type == 'preind') THEN
64! Read and return data from file with suffix .nat
65!****************************************************************************************     
66     cyear='.nat'
67     ! get_aero_fromfile returns pt_out allocated and initialized with data for 12 month
68     ! pt_out has dimensions (klon, klev_src, 12)
69     CALL get_aero_fromfile(name_aero, cyear, filename, klev_src, pt_ap, pt_b, p0, pt_out, psurf, load)
70     
71  ELSE IF (type == 'annuel') THEN
72! Read and return data from scenario annual files
73!****************************************************************************************     
74     WRITE(cyear,'(I4)') iyr_in
75     WRITE(lunout,*) 'get_aero 3 iyr_in=', iyr_in,'   ',cyear
76     ! get_aero_fromfile returns pt_out allocated and initialized with data for nbr_tsteps month
77     ! pt_out has dimensions (klon, klev_src, 12)
78     CALL get_aero_fromfile(name_aero, cyear, filename, klev_src, pt_ap, pt_b, p0, pt_out, psurf, load)
79     
80  ELSE IF (type == 'scenario') THEN
81! Read data depending on actual year and interpolate if necessary
82!****************************************************************************************
83     IF (iyr_in .LT. 1850) THEN
84        cyear='.nat'
85        WRITE(lunout,*) 'get_aero 1 iyr_in=', iyr_in,'   ',cyear
86        ! get_aero_fromfile returns pt_out allocated and initialized with data for 12 month
87        ! pt_out has dimensions (klon, klev_src, 12)
88        CALL get_aero_fromfile(name_aero, cyear, filename, klev_src, pt_ap, pt_b, p0, pt_out, psurf, load)
89       
90     ELSE IF (iyr_in .GE. 2100) THEN
91        cyear='2100'
92        WRITE(lunout,*) 'get_aero 2 iyr_in=', iyr_in,'   ',cyear
93        ! get_aero_fromfile returns pt_out allocated and initialized with data for 12 month
94        ! pt_out has dimensions (klon, klev_src, 12)
95        CALL get_aero_fromfile(name_aero, cyear, filename, klev_src, pt_ap, pt_b, p0, pt_out, psurf, load)
96       
97     ELSE
98        ! Read data from 2 decades and interpolate to actual year
99        ! a) from actual 10-yr-period
100        IF (iyr_in.LT.1900) THEN
101           iyr1 = 1850
102           iyr2 = 1900
103        ELSE IF (iyr_in.GE.1900.AND.iyr_in.LT.1920) THEN
104           iyr1 = 1900
105           iyr2 = 1920
106        ELSE
107           iyr1 = INT(iyr_in/10)*10
108           iyr2 = INT(1+iyr_in/10)*10
109        ENDIF
110       
111        WRITE(cyear,'(I4)') iyr1
112        WRITE(lunout,*) 'get_aero 3 iyr_in=', iyr_in,'   ',cyear
113        ! get_aero_fromfile returns pt_out allocated and initialized with data for 12 month
114        ! pt_out has dimensions (klon, klev_src, 12)
115        CALL get_aero_fromfile(name_aero, cyear, filename, klev_src, pt_ap, pt_b, p0, pt_out, psurf, load)
116       
117        ! If to read two decades:
118        IF (.NOT.lonlyone) THEN
119           
120           ! b) from the next following one
121           WRITE(cyear,'(I4)') iyr2
122           WRITE(lunout,*) 'get_aero 4 iyr_in=', iyr_in,'   ',cyear
123           
124           NULLIFY(pt_2)
125           ! get_aero_fromfile returns pt_2 allocated and initialized with data for 12 month
126           ! pt_2 has dimensions (klon, klev_src, 12)
127           CALL get_aero_fromfile(name_aero, cyear, filename, klev_src2, pt_ap, pt_b, p0, pt_2, psurf2, load2)
128           ! Test for same number of vertical levels
129           IF (klev_src /= klev_src2) THEN
130              WRITE(lunout,*) 'Two aerosols files with different number of vertical levels is not allowded'
131              CALL abort_physic('readaersosol','Error in number of vertical levels',1)
132           END IF
133           
134           ! Linare interpolate to the actual year:
135           DO it=1,12
136              DO k=1,klev_src
137                 DO i = 1, klon
138                    pt_out(i,k,it) = &
139                         pt_out(i,k,it) - REAL(iyr_in-iyr1)/REAL(iyr2-iyr1) * &
140                         (pt_out(i,k,it) - pt_2(i,k,it))
141                 END DO
142              END DO
143
144              DO i = 1, klon
145                 psurf(i,it) = &
146                      psurf(i,it) - REAL(iyr_in-iyr1)/REAL(iyr2-iyr1) * &
147                      (psurf(i,it) - psurf2(i,it))
148
149                 load(i,it) = &
150                      load(i,it) - REAL(iyr_in-iyr1)/REAL(iyr2-iyr1) * &
151                      (load(i,it) - load2(i,it))
152              END DO
153           END DO
154
155           ! Deallocate pt_2 no more needed
156           DEALLOCATE(pt_2)
157           
158        END IF ! lonlyone
159     END IF ! iyr_in .LT. 1850
160
161  ELSE
162     WRITE(lunout,*)'This option is not implemented : aer_type = ', type,' name_aero=',name_aero
163     CALL abort_physic('readaerosol','Error : aer_type parameter not accepted',1)
164  END IF ! type
165
166
167END SUBROUTINE readaerosol
168
169
170  SUBROUTINE get_aero_fromfile(varname, cyr, filename, klev_src, pt_ap, pt_b, p0, pt_year, psurf_out, load_out)
171!****************************************************************************************
172! Read 12 month aerosol from file and distribute to local process on physical grid.
173! Vertical levels, klev_src, may differ from model levels if new file format.
174!
175! For mpi_root and master thread :
176! 1) Open file
177! 2) Find vertical dimension klev_src
178! 3) Read field month by month
179! 4) Close file 
180! 5) Transform the global field from 2D(nbp_lon,nbp_lat) to 1D(klon_glo)
181!     - Also the levels and the latitudes have to be inversed
182!
183! For all processes and threads :
184! 6) Scatter global field(klon_glo) to local process domain(klon)
185! 7) Test for negative values
186!****************************************************************************************
187
188    USE netcdf
189    USE dimphy
190    USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, klon_glo, &
191                                 grid2Dto1D_glo
192    USE mod_phys_lmdz_para
193    USE iophy, ONLY : io_lon, io_lat
194    USE print_control_mod, ONLY: lunout
195
196    IMPLICIT NONE
197     
198! Input argumets
199    CHARACTER(len=7), INTENT(IN)          :: varname
200    CHARACTER(len=4), INTENT(IN)          :: cyr
201    CHARACTER(len=8), INTENT(IN)          :: filename
202
203! Output arguments
204    INTEGER, INTENT(OUT)                  :: klev_src     ! Number of vertical levels in file
205    REAL, POINTER, DIMENSION(:)           :: pt_ap        ! Pointer for describing the vertical levels     
206    REAL, POINTER, DIMENSION(:)           :: pt_b         ! Pointer for describing the vertical levels     
207    REAL                                  :: p0           ! Reference pressure value
208    REAL, POINTER, DIMENSION(:,:,:)       :: pt_year      ! Pointer-variabale from file, 12 month, grid : klon,klev_src
209    REAL, DIMENSION(klon,12), INTENT(OUT) :: psurf_out    ! Surface pression for 12 months
210    REAL, DIMENSION(klon,12), INTENT(OUT) :: load_out     ! Aerosol mass load in each column
211    INTEGER                               :: nbr_tsteps   ! number of month in file read
212
213! Local variables
214    CHARACTER(len=30)     :: fname
215    CHARACTER(len=30)     :: cvar
216    INTEGER               :: ncid, dimid, varid
217    INTEGER               :: imth, i, j, k, ierr
218    REAL                  :: npole, spole
219    REAL, ALLOCATABLE, DIMENSION(:,:,:)   :: varmth
220    REAL, ALLOCATABLE, DIMENSION(:,:,:,:) :: varyear       ! Global variable read from file, 12 month
221    REAL, ALLOCATABLE, DIMENSION(:,:,:)   :: varyear_glo1D !(klon_glo, klev_src, 12)
222    REAL, ALLOCATABLE, DIMENSION(:)       :: varktmp
223
224    REAL, DIMENSION(nbp_lon,nbp_lat,12)   :: psurf_glo2D   ! Surface pression for 12 months on dynamics global grid
225    REAL, DIMENSION(klon_glo,12)          :: psurf_glo1D   ! -"- on physical global grid
226    REAL, DIMENSION(nbp_lon,nbp_lat,12)   :: load_glo2D    ! Load for 12 months on dynamics global grid
227    REAL, DIMENSION(klon_glo,12)          :: load_glo1D    ! -"- on physical global grid
228    REAL, DIMENSION(nbp_lon,nbp_lat)      :: vartmp
229    REAL, DIMENSION(nbp_lon)              :: lon_src              ! longitudes in file
230    REAL, DIMENSION(nbp_lat)              :: lat_src, lat_src_inv ! latitudes in file
231    LOGICAL                               :: new_file             ! true if new file format detected
232    LOGICAL                               :: invert_lat           ! true if the field has to be inverted for latitudes
233
234
235    ! Deallocate pointers
236    IF (ASSOCIATED(pt_ap)) DEALLOCATE(pt_ap)
237    IF (ASSOCIATED(pt_b))  DEALLOCATE(pt_b)
238
239    IF (is_mpi_root .AND. is_omp_root) THEN
240
241! 1) Open file
242!****************************************************************************************
243! Add suffix to filename
244       fname = trim(filename)//cyr//'.nc'
245 
246       WRITE(lunout,*) 'reading variable ',TRIM(varname),' in file ', TRIM(fname)
247       CALL check_err( nf90_open(TRIM(fname), NF90_NOWRITE, ncid), "pb open "//trim(fname) )
248
249! Test for equal longitudes and latitudes in file and model
250!****************************************************************************************
251       ! Read and test longitudes
252       CALL check_err( nf90_inq_varid(ncid, 'lon', varid),"pb inq lon" )
253       CALL check_err( nf90_get_var(ncid, varid, lon_src(:)),"pb get lon" )
254       
255       IF (maxval(ABS(lon_src - io_lon)) > 0.001) THEN
256          WRITE(lunout,*) 'Problem in longitudes read from file : ',TRIM(fname)
257          WRITE(lunout,*) 'longitudes in file ', TRIM(fname),' : ', lon_src
258          WRITE(lunout,*) 'longitudes in model :', io_lon
259         
260          CALL abort_physic('get_aero_fromfile', 'longitudes are not the same in file and model',1)
261       END IF
262
263       ! Read and test latitudes
264       CALL check_err( nf90_inq_varid(ncid, 'lat', varid),"pb inq lat" )
265       CALL check_err( nf90_get_var(ncid, varid, lat_src(:)),"pb get lat" )
266
267       ! Invert source latitudes
268       DO j = 1, nbp_lat
269          lat_src_inv(j) = lat_src(nbp_lat +1 -j)
270       END DO
271
272       IF (maxval(ABS(lat_src - io_lat)) < 0.001) THEN
273          ! Latitudes are the same
274          invert_lat=.FALSE.
275       ELSE IF (maxval(ABS(lat_src_inv - io_lat)) < 0.001) THEN
276          ! Inverted source latitudes correspond to model latitudes
277          WRITE(lunout,*) 'latitudes will be inverted for file : ',TRIM(fname)
278          invert_lat=.TRUE.
279       ELSE
280          WRITE(lunout,*) 'Problem in latitudes read from file : ',TRIM(fname)
281          WRITE(lunout,*) 'latitudes in file ', TRIM(fname),' : ', lat_src     
282          WRITE(lunout,*) 'latitudes in model :', io_lat
283          CALL abort_physic('get_aero_fromfile', 'latitudes do not correspond between file and model',1)
284       END IF
285
286
287! 2) Check if old or new file is avalabale.
288!    New type of file should contain the dimension 'lev'
289!    Old type of file should contain the dimension 'PRESNIVS'
290!****************************************************************************************
291       ierr = nf90_inq_dimid(ncid, 'lev', dimid)
292       IF (ierr /= NF90_NOERR) THEN
293          ! Coordinate axe lev not found. Check for presnivs.
294          ierr = nf90_inq_dimid(ncid, 'PRESNIVS', dimid)
295          IF (ierr /= NF90_NOERR) THEN
296             ! Dimension PRESNIVS not found either
297             CALL abort_physic('get_aero_fromfile', 'dimension lev or presnivs not in file',1)
298          ELSE
299             ! Old file found
300             new_file=.FALSE.
301             WRITE(lunout,*) 'Vertical interpolation for ',TRIM(varname),' will not be done'
302          END IF
303       ELSE
304          ! New file found
305          new_file=.TRUE.
306          WRITE(lunout,*) 'Vertical interpolation for ',TRIM(varname),' will be done'
307       END IF
308       
309! 2) Find vertical dimension klev_src
310!****************************************************************************************
311       CALL check_err( nf90_inquire_dimension(ncid, dimid, len = klev_src),"pb inq dim for PRESNIVS or lev" )
312       
313     ! Allocate variables depending on the number of vertical levels
314       ALLOCATE(varmth(nbp_lon,nbp_lat, klev_src), varyear(nbp_lon,nbp_lat, klev_src, 12), stat=ierr)
315       IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 1',1)
316
317       ALLOCATE(pt_ap(klev_src), pt_b(klev_src), varktmp(klev_src), stat=ierr)
318       IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 2',1)
319
320! 3) Read all variables from file
321!    There is 2 options for the file structure :
322!    new_file=TRUE  : read varyear, ps, pt_ap and pt_b
323!    new_file=FALSE : read varyear month by month
324!****************************************************************************************
325
326       IF (new_file) THEN
327! ++) Check number of month in file opened
328!**************************************************************************************************
329       ierr = nf90_inq_dimid(ncid, 'TIME',dimid)
330       CALL check_err( nf90_inquire_dimension(ncid, dimid, len = nbr_tsteps),"pb inq dim TIME" )
331!       IF (nbr_tsteps /= 12 .AND. nbr_tsteps /= 14) THEN
332       IF (nbr_tsteps /= 12 ) THEN
333    CALL abort_physic('get_aero_fromfile', 'not the right number of months in aerosol file read (should be 12 for the moment)' &
334                     ,1)
335       ENDIF
336
337! ++) Read the aerosol concentration month by month and concatenate to total variable varyear
338!****************************************************************************************
339          ! Get variable id
340          !CALL check_err( nf90_inq_varid(ncid, TRIM(varname), varid),"pb inq var "//TRIM(varname) )
341          print *,'readaerosol ', TRIM(varname)
342          IF ( nf90_inq_varid(ncid, TRIM(varname), varid) /= NF90_NOERR ) THEN
343            ! Variable is not there
344            WRITE(lunout,*) 'Attention '//TRIM(varname)//' is not in aerosol input file'
345            varyear(:,:,:,:)=0.0
346          ELSE
347            ! Get the variable
348            CALL check_err( nf90_get_var(ncid, varid, varyear(:,:,:,:)),"pb get var "//TRIM(varname) )
349          ENDIF
350         
351! ++) Read surface pression, 12 month in one variable
352!****************************************************************************************
353          ! Get variable id
354          CALL check_err( nf90_inq_varid(ncid, "ps", varid),"pb inq var ps" )
355          ! Get the variable
356          CALL check_err( nf90_get_var(ncid, varid, psurf_glo2D),"pb get var ps" )
357         
358! ++) Read mass load, 12 month in one variable
359!****************************************************************************************
360          ! Get variable id
361          !CALL check_err( nf90_inq_varid(ncid, "load_"//TRIM(varname), varid) ,"pb inq var load_"//TRIM(varname))
362          IF ( nf90_inq_varid(ncid, "load_"//TRIM(varname), varid) /= NF90_NOERR ) THEN
363            WRITE(lunout,*) 'Attention load_'//TRIM(varname)//' is not in aerosol input file'
364            load_glo2D(:,:,:)=0.0
365          ELSE
366            ! Get the variable
367            CALL check_err( nf90_get_var(ncid, varid, load_glo2D),"pb get var load_"//TRIM(varname) )
368          ENDIF
369         
370! ++) Read ap
371!****************************************************************************************
372          ! Get variable id
373          CALL check_err( nf90_inq_varid(ncid, "ap", varid),"pb inq var ap" )
374          ! Get the variable
375          CALL check_err( nf90_get_var(ncid, varid, pt_ap),"pb get var ap" )
376
377! ++) Read b
378!****************************************************************************************
379          ! Get variable id
380          CALL check_err( nf90_inq_varid(ncid, "b", varid),"pb inq var b" )
381          ! Get the variable
382          CALL check_err( nf90_get_var(ncid, varid, pt_b),"pb get var b" )
383
384! ++) Read p0 : reference pressure
385!****************************************************************************************
386          ! Get variable id
387          CALL check_err( nf90_inq_varid(ncid, "p0", varid),"pb inq var p0" )
388          ! Get the variable
389          CALL check_err( nf90_get_var(ncid, varid, p0),"pb get var p0" )
390         
391
392       ELSE  ! old file
393
394! ++) Read the aerosol concentration month by month and concatenate to total variable varyear
395!****************************************************************************************
396          DO imth=1, 12
397             IF (imth.EQ.1) THEN
398                cvar=TRIM(varname)//'JAN'
399             ELSE IF (imth.EQ.2) THEN
400                cvar=TRIM(varname)//'FEB'
401             ELSE IF (imth.EQ.3) THEN
402                cvar=TRIM(varname)//'MAR'
403             ELSE IF (imth.EQ.4) THEN
404                cvar=TRIM(varname)//'APR'
405             ELSE IF (imth.EQ.5) THEN
406                cvar=TRIM(varname)//'MAY'
407             ELSE IF (imth.EQ.6) THEN
408                cvar=TRIM(varname)//'JUN'
409             ELSE IF (imth.EQ.7) THEN
410                cvar=TRIM(varname)//'JUL'
411             ELSE IF (imth.EQ.8) THEN
412                cvar=TRIM(varname)//'AUG'
413             ELSE IF (imth.EQ.9) THEN
414                cvar=TRIM(varname)//'SEP'
415             ELSE IF (imth.EQ.10) THEN
416                cvar=TRIM(varname)//'OCT'
417             ELSE IF (imth.EQ.11) THEN
418                cvar=TRIM(varname)//'NOV'
419             ELSE IF (imth.EQ.12) THEN
420                cvar=TRIM(varname)//'DEC'
421             END IF
422             
423             ! Get variable id
424             CALL check_err( nf90_inq_varid(ncid, TRIM(cvar), varid),"pb inq var "//TRIM(cvar) )
425             
426             ! Get the variable
427             CALL check_err( nf90_get_var(ncid, varid, varmth),"pb get var "//TRIM(cvar) )
428             
429             ! Store in variable for the whole year
430             varyear(:,:,:,imth)=varmth(:,:,:)
431             
432          END DO
433         
434          ! Putting dummy
435          psurf_glo2D(:,:,:) = not_valid
436          load_glo2D(:,:,:)  = not_valid
437          pt_ap(:) = not_valid
438          pt_b(:)  = not_valid
439
440       END IF
441
442! 4) Close file 
443!****************************************************************************************
444       CALL check_err( nf90_close(ncid),"pb in close" )
445     
446
447! 5) Transform the global field from 2D(nbp_lon,nbp_lat) to 1D(klon_glo)
448!****************************************************************************************
449! Test if vertical levels have to be inversed
450
451       IF ((pt_b(1) < pt_b(klev_src)) .OR. .NOT. new_file) THEN
452!          WRITE(lunout,*) 'Vertical axis in file ',TRIM(fname), ' needs to be inverted'
453!          WRITE(lunout,*) 'before pt_ap = ', pt_ap
454!          WRITE(lunout,*) 'before pt_b = ', pt_b
455         
456          ! Inverse vertical levels for varyear
457          DO imth=1, 12
458             varmth(:,:,:) = varyear(:,:,:,imth) ! use varmth temporarly
459             DO k=1, klev_src
460                DO j=1, nbp_lat
461                   DO i=1, nbp_lon
462                      varyear(i,j,k,imth) = varmth(i,j,klev_src+1-k)
463                   END DO
464                END DO
465             END DO
466          END DO
467           
468          ! Inverte vertical axes for pt_ap and pt_b
469          varktmp(:) = pt_ap(:)
470          DO k=1, klev_src
471             pt_ap(k) = varktmp(klev_src+1-k)
472          END DO
473
474          varktmp(:) = pt_b(:)
475          DO k=1, klev_src
476             pt_b(k) = varktmp(klev_src+1-k)
477          END DO
478          WRITE(lunout,*) 'after pt_ap = ', pt_ap
479          WRITE(lunout,*) 'after pt_b = ', pt_b
480
481       ELSE
482          WRITE(lunout,*) 'Vertical axis in file ',TRIM(fname), ' is ok, no vertical inversion is done'
483          WRITE(lunout,*) 'pt_ap = ', pt_ap
484          WRITE(lunout,*) 'pt_b = ', pt_b
485       END IF
486
487!     - Invert latitudes if necessary
488       DO imth=1, 12
489          IF (invert_lat) THEN
490
491             ! Invert latitudes for the variable
492             varmth(:,:,:) = varyear(:,:,:,imth) ! use varmth temporarly
493             DO k=1,klev_src
494                DO j=1,nbp_lat
495                   DO i=1,nbp_lon
496                      varyear(i,j,k,imth) = varmth(i,nbp_lat+1-j,k)
497                   END DO
498                END DO
499             END DO
500             
501             ! Invert latitudes for surface pressure
502             vartmp(:,:) = psurf_glo2D(:,:,imth)
503             DO j=1,nbp_lat
504                DO i=1,nbp_lon
505                   psurf_glo2D(i,j,imth)= vartmp(i,nbp_lat+1-j)
506                END DO
507             END DO
508             
509             ! Invert latitudes for the load
510             vartmp(:,:) = load_glo2D(:,:,imth)
511             DO j=1,nbp_lat
512                DO i=1,nbp_lon
513                   load_glo2D(i,j,imth)= vartmp(i,nbp_lat+1-j)
514                END DO
515             END DO
516          END IF ! invert_lat
517             
518          ! Do zonal mead at poles and distribut at whole first and last latitude
519          DO k=1, klev_src
520             npole=0.  ! North pole, j=1
521             spole=0.  ! South pole, j=nbp_lat       
522             DO i=1,nbp_lon
523                npole = npole + varyear(i,1,k,imth)
524                spole = spole + varyear(i,nbp_lat,k,imth)
525             END DO
526             npole = npole/REAL(nbp_lon)
527             spole = spole/REAL(nbp_lon)
528             varyear(:,1,    k,imth) = npole
529             varyear(:,nbp_lat,k,imth) = spole
530          END DO
531       END DO ! imth
532       
533       ALLOCATE(varyear_glo1D(klon_glo, klev_src, 12), stat=ierr)
534       IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 3',1)
535       
536       ! Transform from 2D to 1D field
537       CALL grid2Dto1D_glo(varyear,varyear_glo1D)
538       CALL grid2Dto1D_glo(psurf_glo2D,psurf_glo1D)
539       CALL grid2Dto1D_glo(load_glo2D,load_glo1D)
540
541    ELSE
542      ALLOCATE(varyear_glo1D(0,0,0))       
543    END IF ! is_mpi_root .AND. is_omp_root
544
545!$OMP BARRIER
546 
547! 6) Distribute to all processes
548!    Scatter global field(klon_glo) to local process domain(klon)
549!    and distribute klev_src to all processes
550!****************************************************************************************
551
552    ! Distribute klev_src
553    CALL bcast(klev_src)
554
555    ! Allocate and distribute pt_ap and pt_b
556    IF (.NOT. ASSOCIATED(pt_ap)) THEN  ! if pt_ap is allocated also pt_b is allocated
557       ALLOCATE(pt_ap(klev_src), pt_b(klev_src), stat=ierr)
558       IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 4',1)
559    END IF
560    CALL bcast(pt_ap)
561    CALL bcast(pt_b)
562
563    ! Allocate space for output pointer variable at local process
564    IF (ASSOCIATED(pt_year)) DEALLOCATE(pt_year)
565    ALLOCATE(pt_year(klon, klev_src, 12), stat=ierr)
566    IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 5',1)
567
568    ! Scatter global field to local domain at local process
569    CALL scatter(varyear_glo1D, pt_year)
570    CALL scatter(psurf_glo1D, psurf_out)
571    CALL scatter(load_glo1D,  load_out)
572
573! 7) Test for negative values
574!****************************************************************************************
575    IF (MINVAL(pt_year) < 0.) THEN
576       WRITE(lunout,*) 'Warning! Negative values read from file :', fname
577    END IF
578
579  END SUBROUTINE get_aero_fromfile
580
581
582  SUBROUTINE check_err(status,text)
583    USE netcdf
584    USE print_control_mod, ONLY: lunout
585    IMPLICIT NONE
586
587    INTEGER, INTENT (IN) :: status
588    CHARACTER(len=*), INTENT (IN), OPTIONAL :: text
589
590    IF (status /= NF90_NOERR) THEN
591       WRITE(lunout,*) 'Error in get_aero_fromfile, netcdf error code = ',status
592       IF (PRESENT(text)) THEN
593          WRITE(lunout,*) 'Error in get_aero_fromfile : ',text
594       END IF
595       CALL abort_physic('get_aero_fromfile',trim(nf90_strerror(status)),1)
596    END IF
597
598  END SUBROUTINE check_err
599
600
601END MODULE readaerosol_mod
Note: See TracBrowser for help on using the repository browser.