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

Last change on this file was 5159, checked in by abarral, 7 weeks ago

Put dimensions.h and paramet.h into modules

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