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

Last change on this file was 5274, checked in by abarral, 33 hours ago

Replace yomcst.h by existing module

File size: 4.7 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, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
20          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
21          , R_ecc, R_peri, R_incl                                      &
22          , RA, RG, R1SA                                         &
23          , RSIGMA                                                     &
24          , R, RMD, RMV, RD, RV, RCPD                    &
25          , RMO3, RMCO2, RMC, RMCH4, RMN2O, RMCFC11, RMCFC12        &
26          , RCPV, RCVD, RCVV, RKAPPA, RETV, eps_w                    &
27          , RCW, RCS                                                 &
28          , RLVTT, RLSTT, RLMLT, RTT, RATM                           &
29          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
30          , RALPD, RBETD, RGAMD
31IMPLICIT NONE
32
33
34
35! Variable input
36    LOGICAL debut
37
38! Variables locales
39    INTEGER n_lat   ! number of latitudes in the input data
40    INTEGER n_lon   ! number of longitudes in the input data
41    INTEGER n_lev   ! number of levels in the input data
42    INTEGER n_month ! number of months in the input data
43    REAL, ALLOCATABLE :: latitude(:)
44    REAL, ALLOCATABLE :: longitude(:)
45    REAL, ALLOCATABLE :: time(:)
46    INTEGER i, k
47    INTEGER, SAVE :: mth_pre
48!$OMP THREADPRIVATE(mth_pre)
49
50! Champs reconstitues
51    REAL, ALLOCATABLE :: chlorocon(:, :, :)
52    REAL, ALLOCATABLE :: chlorocon_mois(:, :)
53    REAL, ALLOCATABLE :: chlorocon_mois_glo(:)
54
55! For NetCDF:
56    INTEGER ncid_in  ! IDs for input files
57    INTEGER varid, ncerr
58
59!--------------------------------------------------------
60    CHARACTER (len = 20)  :: modname = 'readchlorophyll'
61    CHARACTER (len = 80)  :: abort_message
62
63!--only read file if beginning of run or start of new month
64    IF (debut.OR.mth_cur.NE.mth_pre) THEN
65
66    IF (is_mpi_root.AND.is_omp_root) THEN
67
68    CALL nf95_open("chlorophyll.nc", nf90_nowrite, ncid_in)
69
70    CALL nf95_inq_varid(ncid_in, "lon", varid)
71    CALL nf95_gw_var(ncid_in, varid, longitude)
72    n_lon = size(longitude)
73    IF (n_lon.NE.nbp_lon) THEN
74       abort_message='Le nombre de lon n est pas egal a nbp_lon'
75       CALL abort_physic(modname,abort_message,1)
76    ENDIF
77
78    CALL nf95_inq_varid(ncid_in, "lat", varid)
79    CALL nf95_gw_var(ncid_in, varid, latitude)
80    n_lat = size(latitude)
81    IF (n_lat.NE.nbp_lat) THEN
82       abort_message='Le nombre de lat n est pas egal a jnbp_lat'
83       CALL abort_physic(modname,abort_message,1)
84    ENDIF
85
86    CALL nf95_inq_varid(ncid_in, "time", varid)
87    CALL nf95_gw_var(ncid_in, varid, time)
88    n_month = size(time)
89    IF (n_month.NE.12) THEN
90       abort_message='Le nombre de month n est pas egal a 12'
91       CALL abort_physic(modname,abort_message,1)
92    ENDIF
93
94    IF (.not.ALLOCATED(chlorocon))          ALLOCATE(chlorocon(n_lon, n_lat, n_month))
95    IF (.not.ALLOCATED(chlorocon_mois))     ALLOCATE(chlorocon_mois(n_lon, n_lat))
96    IF (.not.ALLOCATED(chlorocon_mois_glo)) ALLOCATE(chlorocon_mois_glo(klon_glo))
97
98!--reading stratospheric AOD at 550 nm
99    CALL nf95_inq_varid(ncid_in, "CHL", varid)
100    ncerr = nf90_get_var(ncid_in, varid, chlorocon)
101    WRITE(lunout,*)'code erreur readchlorophyll=', ncerr, varid
102
103    CALL nf95_close(ncid_in)
104
105!---select the correct month
106    IF (mth_cur.LT.1.OR.mth_cur.GT.12) THEN
107      WRITE(lunout,*)'probleme avec le mois dans readchlorophyll =', mth_cur
108    ENDIF
109    chlorocon_mois(:,:) = chlorocon(:,:,mth_cur)
110
111!---reduce to a klon_glo grid
112    CALL grid2dTo1d_glo(chlorocon_mois,chlorocon_mois_glo)
113
114    WRITE(lunout,*)"chrolophyll current month",mth_cur
115    DO i=1,klon_glo
116!      if(isnan(chlorocon_mois_glo(i)))then ! isnan() is not in the Fortran standard...
117!      Another way to check for NaN:
118       IF (chlorocon_mois_glo(i).NE.chlorocon_mois_glo(i)) chlorocon_mois_glo(i)=0.
119    ENDDO
120
121!    DEALLOCATE(chlorocon)
122!    DEALLOCATE(chlorocon_mois)
123!    DEALLOCATE(chlorocon_mois_glo)
124 
125    ENDIF !--is_mpi_root and is_omp_root
126
127!--scatter on all proc
128    CALL scatter(chlorocon_mois_glo,chl_con)
129
130!--keep memory of previous month
131    mth_pre=mth_cur
132
133    ENDIF !--debut ou nouveau mois
134
135END SUBROUTINE readchlorophyll
Note: See TracBrowser for help on using the repository browser.