Ignore:
Timestamp:
Nov 30, 2016, 1:28:41 PM (8 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes r2664:2719 into testing branch

Location:
LMDZ5/branches/testing
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/phylmd/rrtm/readaerosolstrato2_rrtm.F90

    r2594 r2720  
    22! $Id: readaerosolstrato2_rrtm.F90 2526 2016-05-26 22:13:40Z oboucher $
    33!
    4 subroutine readaerosolstrato2_rrtm(debut)
    5 
    6     use netcdf95, only: nf95_close, nf95_gw_var, nf95_inq_dimid, &
     4SUBROUTINE readaerosolstrato2_rrtm(debut)
     5
     6    USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, &
    77                        nf95_inq_varid, nf95_open
    8     use netcdf, only: nf90_get_var, nf90_noerr, nf90_nowrite
     8    USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
    99
    1010    USE phys_cal_mod, ONLY : mth_cur
     
    1717    USE aero_mod
    1818    USE dimphy
    19     USE YOERAD   , ONLY : NLW
    20 
    21     implicit none
    22 
    23     include "YOMCST.h"
     19    USE YOERAD, ONLY : NLW
     20    USE YOMCST
     21
     22    IMPLICIT NONE
     23
    2424    INCLUDE "clesphys.h"
    2525
     
    2828
    2929! Variable input
    30     logical, intent(in) ::  debut
     30    LOGICAL, INTENT(IN) ::  debut
    3131
    3232! Variables locales
    33     integer n_lat   ! number of latitudes in the input data
    34     integer n_lon   ! number of longitudes
    35     integer n_lev   ! number of levels in the input data
    36     integer n_month ! number of months in the input data
    37     integer n_wav   ! number of wavelengths in the input data
    38     real, pointer:: latitude(:)
    39     real, pointer:: longitude(:)
    40     real, pointer:: time(:)
    41     real, pointer:: lev(:)
    42     real, pointer:: wav(:)
    43     integer i,k,wave,band
    44     integer, save :: mth_pre
    45 
    46     real, allocatable, dimension(:,:,:), save :: tau_aer_strat
    47     real, allocatable, dimension(:,:,:), save :: piz_aer_strat
    48     real, allocatable, dimension(:,:,:), save :: cg_aer_strat
    49     real, allocatable, dimension(:,:,:), save :: taulw_aer_strat
     33    INTEGER n_lat   ! number of latitudes in the input data
     34    INTEGER n_lon   ! number of longitudes
     35    INTEGER n_lev   ! number of levels in the input data
     36    INTEGER n_month ! number of months in the input data
     37    INTEGER n_wav   ! number of wavelengths in the input data
     38    REAL, POINTER:: latitude(:)
     39    REAL, POINTER:: time(:)
     40    REAL, POINTER:: lev(:)
     41    REAL, POINTER:: wav(:)
     42    INTEGER i,k,wave,band
     43    INTEGER, SAVE :: mth_pre
     44
     45    REAL, ALLOCATABLE, DIMENSION(:,:,:), SAVE :: tau_aer_strat
     46    REAL, ALLOCATABLE, DIMENSION(:,:,:), SAVE :: piz_aer_strat
     47    REAL, ALLOCATABLE, DIMENSION(:,:,:), SAVE :: cg_aer_strat
     48    REAL, ALLOCATABLE, DIMENSION(:,:,:), SAVE :: taulw_aer_strat
    5049!$OMP THREADPRIVATE(tau_aer_strat,piz_aer_strat,cg_aer_strat,taulw_aer_strat)
    5150
    5251! Champs reconstitues
    53     real, allocatable:: tauaerstrat(:, :, :, :)
    54     real, allocatable:: pizaerstrat(:, :, :, :)
    55     real, allocatable:: cgaerstrat(:, :, :, :)
    56     real, allocatable:: taulwaerstrat(:, :, :, :)
    57 
    58     real, allocatable:: tauaerstrat_mois(:, :, :, :)
    59     real, allocatable:: pizaerstrat_mois(:, :, :, :)
    60     real, allocatable:: cgaerstrat_mois(:, :, :, :)
    61     real, allocatable:: taulwaerstrat_mois(:, :, :, :)
    62 
    63     real, allocatable:: tauaerstrat_mois_glo(:, :, :)
    64     real, allocatable:: pizaerstrat_mois_glo(:, :, :)
    65     real, allocatable:: cgaerstrat_mois_glo(:, :, :)
    66     real, allocatable:: taulwaerstrat_mois_glo(:, :, :)
     52    REAL, ALLOCATABLE:: tauaerstrat(:, :, :, :)
     53    REAL, ALLOCATABLE:: pizaerstrat(:, :, :, :)
     54    REAL, ALLOCATABLE:: cgaerstrat(:, :, :, :)
     55    REAL, ALLOCATABLE:: taulwaerstrat(:, :, :, :)
     56
     57    REAL, ALLOCATABLE:: tauaerstrat_mois(:, :, :, :)
     58    REAL, ALLOCATABLE:: pizaerstrat_mois(:, :, :, :)
     59    REAL, ALLOCATABLE:: cgaerstrat_mois(:, :, :, :)
     60    REAL, ALLOCATABLE:: taulwaerstrat_mois(:, :, :, :)
     61
     62    REAL, ALLOCATABLE:: tauaerstrat_mois_glo(:, :, :)
     63    REAL, ALLOCATABLE:: pizaerstrat_mois_glo(:, :, :)
     64    REAL, ALLOCATABLE:: cgaerstrat_mois_glo(:, :, :)
     65    REAL, ALLOCATABLE:: taulwaerstrat_mois_glo(:, :, :)
    6766
    6867! For NetCDF:
    69     integer ncid_in  ! IDs for input files
    70     integer varid, ncerr
     68    INTEGER ncid_in  ! IDs for input files
     69    INTEGER varid, ncerr
    7170
    7271!--------------------------------------------------------
     
    343342    tau_aero_lw_rrtm = MAX(tau_aero_lw_rrtm,1.e-15)
    344343
    345 end subroutine readaerosolstrato2_rrtm
     344END SUBROUTINE readaerosolstrato2_rrtm
Note: See TracChangeset for help on using the changeset viewer.