source: LMDZ6/trunk/libf/phylmd/readchlorophyll.f90 @ 5308

Last change on this file since 5308 was 5285, checked in by abarral, 4 days ago

As discussed internally, remove generic ONLY: ... for new _mod_h modules

File size: 3.9 KB
Line 
1!
2! $Id$
3!
4!--This routine is to be tested with MPI / OMP parallelism
5!--OB 26/03/2018
6
7SUBROUTINE readchlorophyll(debut)
8
9    USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, nf95_inq_varid, nf95_open
10    USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
11    USE phys_cal_mod, ONLY: mth_cur
12    USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, klon_glo, grid2dto1d_glo
13    USE mod_phys_lmdz_mpi_data, ONLY: is_mpi_root
14    USE mod_phys_lmdz_omp_data, ONLY: is_omp_root
15    USE mod_phys_lmdz_para, ONLY: scatter
16    USE phys_state_var_mod, ONLY: chl_con
17    USE print_control_mod, ONLY: prt_level,lunout
18
19    USE yomcst_mod_h
20IMPLICIT NONE
21
22
23
24! Variable input
25    LOGICAL debut
26
27! Variables locales
28    INTEGER n_lat   ! number of latitudes in the input data
29    INTEGER n_lon   ! number of longitudes in the input data
30    INTEGER n_lev   ! number of levels in the input data
31    INTEGER n_month ! number of months in the input data
32    REAL, ALLOCATABLE :: latitude(:)
33    REAL, ALLOCATABLE :: longitude(:)
34    REAL, ALLOCATABLE :: time(:)
35    INTEGER i, k
36    INTEGER, SAVE :: mth_pre
37!$OMP THREADPRIVATE(mth_pre)
38
39! Champs reconstitues
40    REAL, ALLOCATABLE :: chlorocon(:, :, :)
41    REAL, ALLOCATABLE :: chlorocon_mois(:, :)
42    REAL, ALLOCATABLE :: chlorocon_mois_glo(:)
43
44! For NetCDF:
45    INTEGER ncid_in  ! IDs for input files
46    INTEGER varid, ncerr
47
48!--------------------------------------------------------
49    CHARACTER (len = 20)  :: modname = 'readchlorophyll'
50    CHARACTER (len = 80)  :: abort_message
51
52!--only read file if beginning of run or start of new month
53    IF (debut.OR.mth_cur.NE.mth_pre) THEN
54
55    IF (is_mpi_root.AND.is_omp_root) THEN
56
57    CALL nf95_open("chlorophyll.nc", nf90_nowrite, ncid_in)
58
59    CALL nf95_inq_varid(ncid_in, "lon", varid)
60    CALL nf95_gw_var(ncid_in, varid, longitude)
61    n_lon = size(longitude)
62    IF (n_lon.NE.nbp_lon) THEN
63       abort_message='Le nombre de lon n est pas egal a nbp_lon'
64       CALL abort_physic(modname,abort_message,1)
65    ENDIF
66
67    CALL nf95_inq_varid(ncid_in, "lat", varid)
68    CALL nf95_gw_var(ncid_in, varid, latitude)
69    n_lat = size(latitude)
70    IF (n_lat.NE.nbp_lat) THEN
71       abort_message='Le nombre de lat n est pas egal a jnbp_lat'
72       CALL abort_physic(modname,abort_message,1)
73    ENDIF
74
75    CALL nf95_inq_varid(ncid_in, "time", varid)
76    CALL nf95_gw_var(ncid_in, varid, time)
77    n_month = size(time)
78    IF (n_month.NE.12) THEN
79       abort_message='Le nombre de month n est pas egal a 12'
80       CALL abort_physic(modname,abort_message,1)
81    ENDIF
82
83    IF (.not.ALLOCATED(chlorocon))          ALLOCATE(chlorocon(n_lon, n_lat, n_month))
84    IF (.not.ALLOCATED(chlorocon_mois))     ALLOCATE(chlorocon_mois(n_lon, n_lat))
85    IF (.not.ALLOCATED(chlorocon_mois_glo)) ALLOCATE(chlorocon_mois_glo(klon_glo))
86
87!--reading stratospheric AOD at 550 nm
88    CALL nf95_inq_varid(ncid_in, "CHL", varid)
89    ncerr = nf90_get_var(ncid_in, varid, chlorocon)
90    WRITE(lunout,*)'code erreur readchlorophyll=', ncerr, varid
91
92    CALL nf95_close(ncid_in)
93
94!---select the correct month
95    IF (mth_cur.LT.1.OR.mth_cur.GT.12) THEN
96      WRITE(lunout,*)'probleme avec le mois dans readchlorophyll =', mth_cur
97    ENDIF
98    chlorocon_mois(:,:) = chlorocon(:,:,mth_cur)
99
100!---reduce to a klon_glo grid
101    CALL grid2dTo1d_glo(chlorocon_mois,chlorocon_mois_glo)
102
103    WRITE(lunout,*)"chrolophyll current month",mth_cur
104    DO i=1,klon_glo
105!      if(isnan(chlorocon_mois_glo(i)))then ! isnan() is not in the Fortran standard...
106!      Another way to check for NaN:
107       IF (chlorocon_mois_glo(i).NE.chlorocon_mois_glo(i)) chlorocon_mois_glo(i)=0.
108    ENDDO
109
110!    DEALLOCATE(chlorocon)
111!    DEALLOCATE(chlorocon_mois)
112!    DEALLOCATE(chlorocon_mois_glo)
113 
114    ENDIF !--is_mpi_root and is_omp_root
115
116!--scatter on all proc
117    CALL scatter(chlorocon_mois_glo,chl_con)
118
119!--keep memory of previous month
120    mth_pre=mth_cur
121
122    ENDIF !--debut ou nouveau mois
123
124END SUBROUTINE readchlorophyll
Note: See TracBrowser for help on using the repository browser.