source: LMDZ6/trunk/libf/phylmd/readchlorophyll.F90 @ 5133

Last change on this file since 5133 was 5084, checked in by Laurent Fairhead, 17 months ago

Reverting to r4065. Updating fortran standard broke too much stuff. Will do it by smaller chunks
AB, LF

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