1 | SUBROUTINE 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 paramet_mod_h |
---|
7 | IMPLICIT NONE |
---|
8 | ! |
---|
9 | |
---|
10 | |
---|
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) |
---|
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 | 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 |
---|
35 | ! |
---|
36 | endif |
---|
37 | ! |
---|
38 | start_(1)=1 |
---|
39 | start_(2)=1 |
---|
40 | start_(3)=step |
---|
41 | start_(4)=0 |
---|
42 | |
---|
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 |
---|
49 | ! |
---|
50 | ! |
---|
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 |
---|
53 | |
---|
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 |
---|
77 | !$OMP END MASTER |
---|
78 | !$OMP BARRIER |
---|
79 | CALL scatter(dust_ec_glo,dust_ec) |
---|
80 | ! |
---|
81 | RETURN |
---|
82 | END SUBROUTINE read_dust |
---|