source: LMDZ6/branches/Amaury_dev/libf/phylmd/Dust/read_dust.f90 @ 5116

Last change on this file since 5116 was 5116, checked in by abarral, 2 months ago

rename modules properly lmdz_*
move ismin, ismax, minmax into new lmdz_libmath.f90
(lint) uppercase fortran keywords

File size: 1.9 KB
Line 
1SUBROUTINE read_dust(debutphy, step, nbjour, dust_ec)
2  USE dimphy
3  USE lmdz_grid_phy
4  USE lmdz_phys_para
5  USE netcdf, ONLY: nf90_get_var, nf90_nowrite, nf90_open, nf90_inq_varid
6  IMPLICIT NONE
7
8  INCLUDE "dimensions.h"
9  INCLUDE "paramet.h"
10
11  INTEGER :: step, nbjour
12  LOGICAL :: debutphy
13  REAL :: dust_ec(klon)
14  REAL :: dust_ec_glo(klon_glo)
15
16  ! as      real dust_nc(iip1,jjp1)
17  REAL :: dust_nc_glo(nbp_lon + 1, nbp_lat)
18  INTEGER :: rcode
19  INTEGER :: ncid1, varid1, ncid2, varid2
20
21  save ncid1, varid1, ncid2, varid2
22  !$OMP THREADPRIVATE(ncid1, varid1, ncid2, varid2)
23  INTEGER :: start(4), count(4), status
24  INTEGER :: i, j, ig
25
26  !$OMP MASTER
27  IF (is_mpi_root .AND. is_omp_root) THEN
28    if (debutphy) THEN
29      ncid1 = nf90_open('dust.nc', nf90_nowrite, rcode)
30      varid1 = nf90_inq_varid(ncid1, 'EMISSION', rcode)
31    endif
32
33    start(1) = 1
34    start(2) = 1
35    start(4) = 0
36
37    count(1) = nbp_lon + 1
38    count(2) = nbp_lat
39    count(3) = 1
40    count(4) = 0
41
42    start(3) = step
43
44    status = nf90_get_var(ncid1, varid1, dust_nc_glo, start, count)
45
46    ! CALL correctbid(iim,jjp1,dust_nc)
47    CALL correctbid(nbp_lon, nbp_lat, dust_nc_glo)
48
49    !--upside down + physical grid
50
51    !--OB=change jjp1 to 1 here ;
52    !----AS: OB's change is needed if lats N to S (90 to -90) in dust.nc
53    !  dust_ec(1)=MAX(dust_nc(1,jjp1),0.0)
54    dust_ec_glo(1) = MAX(dust_nc_glo(1, nbp_lat), 0.0)
55    ig = 2
56    ! DO j=2,jjm
57    DO j = 2, nbp_lat - 1
58      ! DO i = 1, iim
59      DO i = 1, nbp_lon
60        !--OB=change jjp1+1-j to j here
61        ! dust_ec(ig)=MAX(dust_nc(i,jjp1+1-j),0.0)
62        dust_ec_glo(ig) = MAX(dust_nc_glo(i, nbp_lat + 1 - j), 0.0)
63        ig = ig + 1
64      ENDDO
65    ENDDO
66    !--OB=change second 1 to jjp1 here
67    dust_ec_glo(ig) = MAX(dust_nc_glo(1, 1), 0.0)
68    ! end if master
69  ENDIF
70  !$OMP END MASTER
71  !$OMP BARRIER
72  CALL scatter(dust_ec_glo, dust_ec)
73
74
75END SUBROUTINE read_dust
Note: See TracBrowser for help on using the repository browser.