source: LMDZ6/branches/contrails/libf/phylmd/Dust/read_dust.f90 @ 5489

Last change on this file since 5489 was 5489, checked in by aborella, 13 days ago

Merge with trunk

File size: 2.0 KB
RevLine 
[5246]1SUBROUTINE read_dust(debutphy, step, nbjour, dust_ec)
2  USE dimphy
3  USE mod_grid_phy_lmdz
4  USE mod_phys_lmdz_para
[5270]5  USE netcdf, ONLY: nf90_get_var, nf90_nowrite, nf90_open, nf90_inq_varid
[5337]6!!USE paramet_mod_h
[5271]7IMPLICIT NONE
[5246]8  !
[5271]9
[5272]10
[5246]11  !
12  INTEGER :: step, nbjour
13  LOGICAL :: debutphy
14  real :: dust_ec(klon)
15  real :: dust_ec_glo(klon_glo)
16  !
17  ! as      real dust_nc(iip1,jjp1)
18  real :: dust_nc_glo(nbp_lon+1,nbp_lat)
[5270]19  INTEGER :: ncid1, varid1, ncid2, varid2, rcode
[2630]20
[5246]21  save ncid1, varid1, ncid2, varid2
[2630]22!$OMP THREADPRIVATE(ncid1, varid1, ncid2, varid2)
[5489]23  integer :: start_(4),count_(4)
[5246]24  integer :: i, j, ig
25  !
[2630]26!$OMP MASTER
[5246]27  IF (is_mpi_root .AND. is_omp_root) THEN
28  if (debutphy) then
29  !
[5489]30     rcode=nf90_open('dust.nc',nf90_nowrite,ncid1)
31     if ( rcode /= 0 ) then ; call abort_physic('LMDZ','open dust.nc dans read_vent',1) ; endif
32
33     rcode=nf90_inq_varid(ncid1,'EMISSION',varid1)
34     if ( rcode /= 0 ) then ; call abort_physic('LMDZ','inq varid EMISSION dans read_vent',1) ; endif
[5246]35  !
36  endif
37  !
[5489]38  start_(1)=1
39  start_(2)=1
40  start_(3)=step
41  start_(4)=0
[2630]42
[5489]43   ! count_(1)=iip1
44  count_(1)=nbp_lon+1
45   ! count_(2)=jjp1
46  count_(2)=nbp_lat
47  count_(3)=1
48  count_(4)=0
[5246]49  !
50  !
[5489]51  rcode = nf90_get_var(ncid1, varid1, dust_nc_glo, start_, count_)
52  if ( rcode /= 0 ) then ; call abort_physic('LMDZ','get EMISSION dans read_vent',1) ; endif
[5249]53
[5246]54  !
55  call correctbid(nbp_lon,nbp_lat,dust_nc_glo)
56  !
57  !--upside down + physical grid
58  !
59  !--OB=change jjp1 to 1 here ;
60  !----AS: OB's change is needed if lats N to S (90 to -90) in dust.nc
61  !  dust_ec(1)=MAX(dust_nc(1,jjp1),0.0)
62  dust_ec_glo(1)=MAX(dust_nc_glo(1,nbp_lat),0.0)
63  ig=2
64   ! DO j=2,jjm
65  DO j=2,nbp_lat-1
66     DO i = 1, nbp_lon
67  !--OB=change jjp1+1-j to j here
68        ! dust_ec(ig)=MAX(dust_nc(i,jjp1+1-j),0.0)
69       dust_ec_glo(ig)=MAX(dust_nc_glo(i,nbp_lat+1-j),0.0)
70       ig=ig+1
71     ENDDO
72  ENDDO
73  !--OB=change second 1 to jjp1 here
74  dust_ec_glo(ig)=MAX(dust_nc_glo(1,1),0.0)
75   ! end if master
76  ENDIF
[2630]77!$OMP END MASTER
78!$OMP BARRIER
[5246]79  CALL scatter(dust_ec_glo,dust_ec)
80  !
81  RETURN
82END SUBROUTINE read_dust
Note: See TracBrowser for help on using the repository browser.