Ignore:
Timestamp:
Jul 24, 2024, 12:17:33 PM (4 months ago)
Author:
abarral
Message:

Put abort_physic into a module
Remove -g option from makelmdz_fcm, since that option is linked to a header file that isn't included anywhere.
(lint) light lint on traversed files

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/phylmd/readchlorophyll.F90

    r5110 r5111  
    1 
    21! $Id$
    32
     
    76SUBROUTINE readchlorophyll(debut)
    87
    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 lmdz_grid_phy, ONLY: nbp_lon, nbp_lat, klon_glo, grid2dto1d_glo
    13     USE lmdz_phys_mpi_data, ONLY: is_mpi_root
    14     USE lmdz_phys_omp_data, ONLY: is_omp_root
    15     USE lmdz_phys_para, ONLY: scatter
    16     USE phys_state_var_mod, ONLY: chl_con
    17     USE print_control_mod, ONLY: prt_level,lunout
     8  USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, nf95_inq_varid, nf95_open
     9  USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
     10  USE phys_cal_mod, ONLY: mth_cur
     11  USE lmdz_grid_phy, ONLY: nbp_lon, nbp_lat, klon_glo, grid2dto1d_glo
     12  USE lmdz_phys_mpi_data, ONLY: is_mpi_root
     13  USE lmdz_phys_omp_data, ONLY: is_omp_root
     14  USE lmdz_phys_para, ONLY: scatter
     15  USE phys_state_var_mod, ONLY: chl_con
     16  USE print_control_mod, ONLY: prt_level, lunout
     17  USE lmdz_abort_physic, ONLY: abort_physic
    1818
    19     IMPLICIT NONE
     19  IMPLICIT NONE
    2020
    21     INCLUDE "YOMCST.h"
     21  INCLUDE "YOMCST.h"
    2222
    23 ! Variable input
    24     LOGICAL debut
     23  ! Variable input
     24  LOGICAL debut
    2525
    26 ! Variables locales
    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
    31     REAL, ALLOCATABLE :: latitude(:)
    32     REAL, ALLOCATABLE :: longitude(:)
    33     REAL, ALLOCATABLE :: time(:)
    34     INTEGER i, k
    35     INTEGER, SAVE :: mth_pre
    36 !$OMP THREADPRIVATE(mth_pre)
     26  ! Variables locales
     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
     31  REAL, ALLOCATABLE :: latitude(:)
     32  REAL, ALLOCATABLE :: longitude(:)
     33  REAL, ALLOCATABLE :: time(:)
     34  INTEGER i, k
     35  INTEGER, SAVE :: mth_pre
     36  !$OMP THREADPRIVATE(mth_pre)
    3737
    38 ! Champs reconstitues
    39     REAL, ALLOCATABLE :: chlorocon(:, :, :)
    40     REAL, ALLOCATABLE :: chlorocon_mois(:, :)
    41     REAL, ALLOCATABLE :: chlorocon_mois_glo(:)
     38  ! Champs reconstitues
     39  REAL, ALLOCATABLE :: chlorocon(:, :, :)
     40  REAL, ALLOCATABLE :: chlorocon_mois(:, :)
     41  REAL, ALLOCATABLE :: chlorocon_mois_glo(:)
    4242
    43 ! For NetCDF:
    44     INTEGER ncid_in  ! IDs for input files
    45     INTEGER varid, ncerr
     43  ! For NetCDF:
     44  INTEGER ncid_in  ! IDs for input files
     45  INTEGER varid, ncerr
    4646
    47 !--------------------------------------------------------
    48     CHARACTER (len = 20) :: modname = 'readchlorophyll'
    49     CHARACTER (len = 80) :: abort_message
     47  !--------------------------------------------------------
     48  CHARACTER (len = 20) :: modname = 'readchlorophyll'
     49  CHARACTER (len = 80) :: abort_message
    5050
    51 !--only read file if beginning of run or start of new month
    52     IF (debut.OR.mth_cur/=mth_pre) THEN
     51  !--only read file if beginning of run or start of new month
     52  IF (debut.OR.mth_cur/=mth_pre) THEN
    5353
    5454    IF (is_mpi_root.AND.is_omp_root) THEN
    5555
    56     CALL nf95_open("chlorophyll.nc", nf90_nowrite, ncid_in)
     56      CALL nf95_open("chlorophyll.nc", nf90_nowrite, ncid_in)
    5757
    58     CALL nf95_inq_varid(ncid_in, "lon", varid)
    59     CALL nf95_gw_var(ncid_in, varid, longitude)
    60     n_lon = size(longitude)
    61     IF (n_lon/=nbp_lon) THEN
    62        abort_message='Le nombre de lon n est pas egal a nbp_lon'
    63        CALL abort_physic(modname,abort_message,1)
    64     ENDIF
     58      CALL nf95_inq_varid(ncid_in, "lon", varid)
     59      CALL nf95_gw_var(ncid_in, varid, longitude)
     60      n_lon = size(longitude)
     61      IF (n_lon/=nbp_lon) THEN
     62        abort_message = 'Le nombre de lon n est pas egal a nbp_lon'
     63        CALL abort_physic(modname, abort_message, 1)
     64      ENDIF
    6565
    66     CALL nf95_inq_varid(ncid_in, "lat", varid)
    67     CALL nf95_gw_var(ncid_in, varid, latitude)
    68     n_lat = size(latitude)
    69     IF (n_lat/=nbp_lat) THEN
    70        abort_message='Le nombre de lat n est pas egal a jnbp_lat'
    71        CALL abort_physic(modname,abort_message,1)
    72     ENDIF
     66      CALL nf95_inq_varid(ncid_in, "lat", varid)
     67      CALL nf95_gw_var(ncid_in, varid, latitude)
     68      n_lat = size(latitude)
     69      IF (n_lat/=nbp_lat) THEN
     70        abort_message = 'Le nombre de lat n est pas egal a jnbp_lat'
     71        CALL abort_physic(modname, abort_message, 1)
     72      ENDIF
    7373
    74     CALL nf95_inq_varid(ncid_in, "time", varid)
    75     CALL nf95_gw_var(ncid_in, varid, time)
    76     n_month = size(time)
    77     IF (n_month/=12) THEN
    78        abort_message='Le nombre de month n est pas egal a 12'
    79        CALL abort_physic(modname,abort_message,1)
    80     ENDIF
     74      CALL nf95_inq_varid(ncid_in, "time", varid)
     75      CALL nf95_gw_var(ncid_in, varid, time)
     76      n_month = size(time)
     77      IF (n_month/=12) THEN
     78        abort_message = 'Le nombre de month n est pas egal a 12'
     79        CALL abort_physic(modname, abort_message, 1)
     80      ENDIF
    8181
    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))
     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))
    8585
    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)
    89     WRITE(lunout,*)'code erreur readchlorophyll=', ncerr, varid
     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)
     89      WRITE(lunout, *)'code erreur readchlorophyll=', ncerr, varid
    9090
    91     CALL nf95_close(ncid_in)
     91      CALL nf95_close(ncid_in)
    9292
    93 !---select the correct month
    94     IF (mth_cur<1.OR.mth_cur>12) THEN
    95       WRITE(lunout,*)'probleme avec le mois dans readchlorophyll =', mth_cur
    96     ENDIF
    97     chlorocon_mois(:,:) = chlorocon(:,:,mth_cur)
     93      !---select the correct month
     94      IF (mth_cur<1.OR.mth_cur>12) THEN
     95        WRITE(lunout, *)'probleme avec le mois dans readchlorophyll =', mth_cur
     96      ENDIF
     97      chlorocon_mois(:, :) = chlorocon(:, :, mth_cur)
    9898
    99 !---reduce to a klon_glo grid
    100     CALL grid2dTo1d_glo(chlorocon_mois,chlorocon_mois_glo)
     99      !---reduce to a klon_glo grid
     100      CALL grid2dTo1d_glo(chlorocon_mois, chlorocon_mois_glo)
    101101
    102     WRITE(lunout,*)"chrolophyll current month",mth_cur
    103     DO i=1,klon_glo
    104 !      if(isnan(chlorocon_mois_glo(i)))then ! isnan() is not in the Fortran standard...
    105 !      Another way to check for NaN:
    106        IF (chlorocon_mois_glo(i)/=chlorocon_mois_glo(i)) chlorocon_mois_glo(i)=0.
    107     ENDDO
     102      WRITE(lunout, *)"chrolophyll current month", mth_cur
     103      DO i = 1, klon_glo
     104        !      if(isnan(chlorocon_mois_glo(i)))then ! isnan() is not in the Fortran standard...
     105        !      Another way to check for NaN:
     106        IF (chlorocon_mois_glo(i)/=chlorocon_mois_glo(i)) chlorocon_mois_glo(i) = 0.
     107      ENDDO
    108108
    109 !    DEALLOCATE(chlorocon)
    110 !    DEALLOCATE(chlorocon_mois)
    111 !    DEALLOCATE(chlorocon_mois_glo)
    112  
     109      !    DEALLOCATE(chlorocon)
     110      !    DEALLOCATE(chlorocon_mois)
     111      !    DEALLOCATE(chlorocon_mois_glo)
     112
    113113    ENDIF !--is_mpi_root and is_omp_root
    114114
    115 !--scatter on all proc
    116     CALL scatter(chlorocon_mois_glo,chl_con)
     115    !--scatter on all proc
     116    CALL scatter(chlorocon_mois_glo, chl_con)
    117117
    118 !--keep memory of previous month
    119     mth_pre=mth_cur
     118    !--keep memory of previous month
     119    mth_pre = mth_cur
    120120
    121     ENDIF !--debut ou nouveau mois
     121  ENDIF !--debut ou nouveau mois
    122122
    123123END SUBROUTINE readchlorophyll
Note: See TracChangeset for help on using the changeset viewer.