Ignore:
Timestamp:
Nov 5, 2018, 3:24:59 PM (6 years ago)
Author:
Laurent Fairhead
Message:

Undoing merge with trunk (r3356) to properly register Yann's latest modifications

Location:
LMDZ6/branches/DYNAMICO-conv
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/DYNAMICO-conv

  • LMDZ6/branches/DYNAMICO-conv/libf/phylmd/readchlorophyll.F90

    r3356 r3411  
    22! $Id$
    33!
    4 !--This routine is to be tested with MPI / OMP parallelism
    5 !--OB 26/03/2018
    64
    7 SUBROUTINE readchlorophyll(debut)
     5subroutine readchlorophyll(debut)
    86
    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
     7    use netcdf95, only: nf95_close, nf95_gw_var, nf95_inq_dimid, &
     8                        nf95_inq_varid, nf95_open
     9    use netcdf, only: nf90_get_var, nf90_noerr, nf90_nowrite
     10
     11    USE phys_cal_mod, ONLY : mth_cur
     12    USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, klon_glo, &
     13                                 grid2dto1d_glo
     14    USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
    1515    USE mod_phys_lmdz_para, ONLY: scatter
    1616    USE phys_state_var_mod, ONLY: chl_con
    1717
    18     IMPLICIT NONE
     18    implicit none
    1919
    20     INCLUDE "YOMCST.h"
     20    include "YOMCST.h"
    2121
    2222! Variable input
    23     LOGICAL debut
     23    logical debut
    2424
    2525! Variables locales
    26     INTEGER n_lat   ! number of latitudes in the input data
    27     INTEGER n_lon   ! number of longitudes in the input data
    28     INTEGER n_lev   ! number of levels in the input data
    29     INTEGER n_month ! number of months in the input data
    30     REAL, POINTER :: latitude(:)
    31     REAL, POINTER :: longitude(:)
    32     REAL, POINTER :: time(:)
    33     INTEGER i, k
    34     INTEGER, SAVE :: mth_pre
     26    integer n_lat   ! number of latitudes in the input data
     27    integer n_lon   ! number of longitudes in the input data
     28    integer n_lev   ! number of levels in the input data
     29    integer n_month ! number of months in the input data
     30    real, pointer:: latitude(:)
     31    real, pointer:: longitude(:)
     32    real, pointer:: time(:)
     33    integer i, k
     34    integer, save :: mth_pre
    3535!$OMP THREADPRIVATE(mth_pre)
    3636
    3737! Champs reconstitues
    38     REAL, ALLOCATABLE :: chlorocon(:, :, :)
    39     REAL, ALLOCATABLE :: chlorocon_mois(:, :)
    40     REAL, ALLOCATABLE :: chlorocon_mois_glo(:)
     38    real, allocatable:: chlorocon(:, :, :)
     39    real, allocatable:: chlorocon_mois(:, :)
     40    real, allocatable:: chlorocon_mois_glo(:)
    4141
    4242! For NetCDF:
    43     INTEGER ncid_in  ! IDs for input files
    44     INTEGER varid, ncerr
     43    integer ncid_in  ! IDs for input files
     44    integer varid, ncerr
     45
    4546
    4647!--------------------------------------------------------
     48
    4749
    4850!--only read file if beginning of run or start of new month
    4951    IF (debut.OR.mth_cur.NE.mth_pre) THEN
    5052
    51     IF (is_mpi_root.AND.is_omp_root) THEN
     53    IF (is_mpi_root) THEN
     54
    5255
    5356    CALL nf95_open("chlorophyll.nc", nf90_nowrite, ncid_in)
     
    6164       STOP
    6265    ENDIF
     66
    6367
    6468    CALL nf95_inq_varid(ncid_in, "lat", varid)
     
    100104    CALL grid2dTo1d_glo(chlorocon_mois,chlorocon_mois_glo)
    101105
    102     print *,"chrolophyll current month",mth_cur
    103     DO i=1,klon_glo
     106
     107    print*,"chrolophyll current month",mth_cur
     108    do i=1,klon_glo
    104109!      if(isnan(chlorocon_mois_glo(i)))then ! isnan() is not in the Fortran standard...
    105110!      Another way to check for NaN:
    106        IF (chlorocon_mois_glo(i).NE.chlorocon_mois_glo(i)) chlorocon_mois_glo(i)=0.
    107     ENDDO
     111       if(chlorocon_mois_glo(i).ne.chlorocon_mois_glo(i)) then
     112         chlorocon_mois_glo(i)=0.
     113      endif
     114      !print*,"high chl con",i,chlorocon_mois_glo(i)
     115    enddo
    108116
    109117!    DEALLOCATE(chlorocon)
     
    111119!    DEALLOCATE(chlorocon_mois_glo)
    112120 
    113     ENDIF !--is_mpi_root and is_omp_root
     121    ENDIF !--is_mpi_root
    114122
    115123!--scatter on all proc
     
    121129    ENDIF !--debut ou nouveau mois
    122130
    123 END SUBROUTINE readchlorophyll
     131end subroutine readchlorophyll
Note: See TracChangeset for help on using the changeset viewer.