source: LMDZ6/trunk/libf/phylmd/Dust/read_dust.f90 @ 5271

Last change on this file since 5271 was 5271, checked in by abarral, 34 hours ago

Move dimensions.h into a module
Nb: doesn't compile yet

File size: 1.9 KB
Line 
1SUBROUTINE read_dust(debutphy, step, nbjour, dust_ec)
2  USE dimphy
3  USE mod_grid_phy_lmdz
4  USE mod_phys_lmdz_para
5  USE netcdf, ONLY: nf90_get_var, nf90_nowrite, nf90_open, nf90_inq_varid
6  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
7IMPLICIT NONE
8  !
9
10  INCLUDE "paramet.h"
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)
19  INTEGER :: ncid1, varid1, ncid2, varid2, rcode
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  !
30     ncid1=nf90_open('dust.nc',nf90_nowrite,rcode)
31     varid1=nf90_inq_varid(ncid1,'EMISSION',rcode)
32  !
33  endif
34  !
35  start(1)=1
36  start(2)=1
37  start(4)=0
38
39   ! count(1)=iip1
40  count(1)=nbp_lon+1
41   ! count(2)=jjp1
42  count(2)=nbp_lat
43  count(3)=1
44  count(4)=0
45  !
46  start(3)=step
47  !
48  status = nf90_get_var(ncid1, varid1, dust_nc_glo, start, count)
49
50  !
51  !  call correctbid(iim,jjp1,dust_nc)
52  call correctbid(nbp_lon,nbp_lat,dust_nc_glo)
53  !
54  !--upside down + physical grid
55  !
56  !--OB=change jjp1 to 1 here ;
57  !----AS: OB's change is needed if lats N to S (90 to -90) in dust.nc
58  !  dust_ec(1)=MAX(dust_nc(1,jjp1),0.0)
59  dust_ec_glo(1)=MAX(dust_nc_glo(1,nbp_lat),0.0)
60  ig=2
61   ! DO j=2,jjm
62  DO j=2,nbp_lat-1
63      ! DO i = 1, iim
64     DO i = 1, nbp_lon
65  !--OB=change jjp1+1-j to j here
66        ! dust_ec(ig)=MAX(dust_nc(i,jjp1+1-j),0.0)
67       dust_ec_glo(ig)=MAX(dust_nc_glo(i,nbp_lat+1-j),0.0)
68       ig=ig+1
69     ENDDO
70  ENDDO
71  !--OB=change second 1 to jjp1 here
72  dust_ec_glo(ig)=MAX(dust_nc_glo(1,1),0.0)
73   ! end if master
74  ENDIF
75!$OMP END MASTER
76!$OMP BARRIER
77  CALL scatter(dust_ec_glo,dust_ec)
78  !
79  RETURN
80END SUBROUTINE read_dust
Note: See TracBrowser for help on using the repository browser.