Changeset 2344


Ignore:
Timestamp:
Aug 21, 2015, 9:23:13 AM (9 years ago)
Author:
Ehouarn Millour
Message:

Physics/dynamics separation: get rid of all the 'include "temps.h"' in the physics; variables in module time_phylmdz_mod must be used instead. Also added JD_cur, JH_cur and JD_ref in module phys_cal_mod, in preparation for having physics handle its calendar internally.
EM

Location:
LMDZ5/trunk/libf/phylmd
Files:
21 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/condsurf.F90

    r2311 r2344  
    66  USE mod_phys_lmdz_para
    77  USE indice_sol_mod
     8  USE time_phylmdz_mod, ONLY: annee_ref
    89  IMPLICIT NONE
    910
     
    2425  INTEGER epais(2)
    2526
    26   ! ym#include "dimensions.h"
    27   ! ym#include "dimphy.h"
    28   include "temps.h"
    2927  include "clesphys.h"
    3028
  • LMDZ5/trunk/libf/phylmd/conf_phys_m.F90

    r2311 r2344  
    2727    USE phys_cal_mod
    2828    USE carbon_cycle_mod, ONLY : carbon_cycle_tr, carbon_cycle_cpl
    29     USE control_mod
    3029    USE mod_grid_phy_lmdz, only: klon_glo
    3130    USE print_control_mod, ONLY: lunout
  • LMDZ5/trunk/libf/phylmd/cpl_mod.F90

    r2311 r2344  
    2424  USE oasis
    2525  USE write_field_phy
    26   USE control_mod
    27 
     26!  USE control_mod
     27  USE time_phylmdz_mod, ONLY: day_step_phy
    2828 
    2929! Global attributes
     
    102102    USE surface_data
    103103    USE indice_sol_mod
     104    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
     105    USE time_phylmdz_mod, ONLY: annee_ref, day_ini, itau_phy, itaufin_phy
    104106    USE print_control_mod, ONLY: lunout
    105 
    106     INCLUDE "dimensions.h"
    107     INCLUDE "temps.h"
    108107
    109108! Input arguments
     
    121120    INTEGER                           :: npas ! only for OASIS2
    122121    REAL                              :: zjulian
    123     REAL, DIMENSION(iim,jjm+1)        :: zx_lon, zx_lat
     122    REAL, DIMENSION(nbp_lon,nbp_lat)  :: zx_lon, zx_lat
    124123    CHARACTER(len = 20)               :: modname = 'cpl_init'
    125124    CHARACTER(len = 80)               :: abort_message
     
    131130!*************************************************************************************
    132131     
    133     npas = itaufin/ iphysiq
     132    npas = itaufin_phy
    134133!    nexca = 86400 / dtime
    135134    nexca = t_coupl / dtime
     
    172171    ALLOCATE(cpl_taumod(klon,2), stat = error)
    173172    sum_error = sum_error + error
    174     ALLOCATE(cpl_rriv2D(iim,jj_nb), stat=error)
    175     sum_error = sum_error + error
    176     ALLOCATE(cpl_rcoa2D(iim,jj_nb), stat=error)
    177     sum_error = sum_error + error
    178     ALLOCATE(cpl_rlic2D(iim,jj_nb), stat=error)
    179     sum_error = sum_error + error
    180     ALLOCATE(read_sst(iim, jj_nb), stat = error)
    181     sum_error = sum_error + error
    182     ALLOCATE(read_sic(iim, jj_nb), stat = error)
    183     sum_error = sum_error + error
    184     ALLOCATE(read_sit(iim, jj_nb), stat = error)
    185     sum_error = sum_error + error
    186     ALLOCATE(read_alb_sic(iim, jj_nb), stat = error)
    187     sum_error = sum_error + error
    188     ALLOCATE(read_u0(iim, jj_nb), stat = error)
    189     sum_error = sum_error + error
    190     ALLOCATE(read_v0(iim, jj_nb), stat = error)
     173    ALLOCATE(cpl_rriv2D(nbp_lon,jj_nb), stat=error)
     174    sum_error = sum_error + error
     175    ALLOCATE(cpl_rcoa2D(nbp_lon,jj_nb), stat=error)
     176    sum_error = sum_error + error
     177    ALLOCATE(cpl_rlic2D(nbp_lon,jj_nb), stat=error)
     178    sum_error = sum_error + error
     179    ALLOCATE(read_sst(nbp_lon, jj_nb), stat = error)
     180    sum_error = sum_error + error
     181    ALLOCATE(read_sic(nbp_lon, jj_nb), stat = error)
     182    sum_error = sum_error + error
     183    ALLOCATE(read_sit(nbp_lon, jj_nb), stat = error)
     184    sum_error = sum_error + error
     185    ALLOCATE(read_alb_sic(nbp_lon, jj_nb), stat = error)
     186    sum_error = sum_error + error
     187    ALLOCATE(read_u0(nbp_lon, jj_nb), stat = error)
     188    sum_error = sum_error + error
     189    ALLOCATE(read_v0(nbp_lon, jj_nb), stat = error)
    191190    sum_error = sum_error + error
    192191
    193192    IF (carbon_cycle_cpl) THEN
    194        ALLOCATE(read_co2(iim, jj_nb), stat = error)
     193       ALLOCATE(read_co2(nbp_lon, jj_nb), stat = error)
    195194       sum_error = sum_error + error
    196195       ALLOCATE(cpl_atm_co2(klon,2), stat = error)
     
    230229       idayref = day_ini
    231230       CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
    232        CALL gr_fi_ecrit(1,klon,iim,jjm+1,rlon,zx_lon)
    233        DO i = 1, iim
     231       CALL gr_fi_ecrit(1,klon,nbp_lon,nbp_lat,rlon,zx_lon)
     232       DO i = 1, nbp_lon
    234233          zx_lon(i,1) = rlon(i+1)
    235           zx_lon(i,jjm+1) = rlon(i+1)
     234          zx_lon(i,nbp_lat) = rlon(i+1)
    236235       ENDDO
    237        CALL gr_fi_ecrit(1,klon,iim,jjm+1,rlat,zx_lat)
     236       CALL gr_fi_ecrit(1,klon,nbp_lon,nbp_lat,rlat,zx_lat)
    238237       clintocplnam="cpl_atm_tauflx"
    239        CALL histbeg(clintocplnam, iim,zx_lon(:,1),jjm+1,zx_lat(1,:),&
    240             1,iim,1,jjm+1, itau_phy,zjulian,dtime,nhoridct,nidct)
     238       CALL histbeg(clintocplnam,nbp_lon,zx_lon(:,1),nbp_lat,zx_lat(1,:),&
     239            1,nbp_lon,1,nbp_lat, itau_phy,zjulian,dtime,nhoridct,nidct)
    241240! no vertical axis
    242241       CALL histdef(nidct, 'tauxe','tauxe', &
    243             "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
     242            "-",nbp_lon,nbp_lat, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
    244243       CALL histdef(nidct, 'tauyn','tauyn', &
    245             "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
     244            "-",nbp_lon,nbp_lat, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
    246245       CALL histdef(nidct, 'tmp_lon','tmp_lon', &
    247             "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
     246            "-",nbp_lon,nbp_lat, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
    248247       CALL histdef(nidct, 'tmp_lat','tmp_lat', &
    249             "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
     248            "-",nbp_lon,nbp_lat, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
    250249       DO jf=1,maxsend
    251250         IF (infosend(i)%action) THEN
    252251             CALL histdef(nidct, infosend(i)%name ,infosend(i)%name , &
    253                 "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
     252                "-",nbp_lon,nbp_lat,nhoridct,1,1,1,-99,32,"inst",dtime,dtime)
    254253         ENDIF
    255254       END DO
     
    258257       
    259258       clfromcplnam="cpl_atm_sst"
    260        CALL histbeg(clfromcplnam, iim,zx_lon(:,1),jjm+1,zx_lat(1,:),1,iim,1,jjm+1, &
     259       CALL histbeg(clfromcplnam,nbp_lon,zx_lon(:,1),nbp_lat,zx_lat(1,:),1,nbp_lon,1,nbp_lat, &
    261260            0,zjulian,dtime,nhoridcs,nidcs)
    262261! no vertical axis
     
    264263         IF (inforecv(i)%action) THEN
    265264             CALL histdef(nidcs,inforecv(i)%name ,inforecv(i)%name , &
    266                 "-",iim, jjm+1, nhoridcs, 1, 1, 1, -99, 32, "inst", dtime,dtime)
     265                "-",nbp_lon,nbp_lat,nhoridcs,1,1,1,-99,32,"inst",dtime,dtime)
    267266         ENDIF
    268267       END DO
     
    297296    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl
    298297    USE indice_sol_mod
    299 
    300     INCLUDE "temps.h"
     298    USE time_phylmdz_mod, ONLY: start_time, itau_phy
     299    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
     300
    301301    INCLUDE "YOMCST.h"
    302     INCLUDE "dimensions.h"
    303302
    304303! Arguments
     
    313312    INTEGER                                 :: j, i, time_sec
    314313    INTEGER                                 :: itau_w
    315     INTEGER, DIMENSION(iim*(jjm+1))         :: ndexcs
     314    INTEGER, DIMENSION(nbp_lon*nbp_lat)     :: ndexcs
    316315    CHARACTER(len = 20)                     :: modname = 'cpl_receive_frac'
    317316    CHARACTER(len = 80)                     :: abort_message
    318317    REAL, DIMENSION(klon)                   :: read_sic1D
    319     REAL, DIMENSION(iim,jj_nb,maxrecv)      :: tab_read_flds
     318    REAL, DIMENSION(nbp_lon,jj_nb,maxrecv)      :: tab_read_flds
    320319    REAL, DIMENSION(klon,nbsrf)             :: pctsrf_old
    321320    REAL, DIMENSION(klon_mpi)               :: rlon_mpi, rlat_mpi
    322     REAL, DIMENSION(iim, jj_nb)             :: tmp_lon, tmp_lat
    323     REAL, DIMENSION(iim, jj_nb)             :: tmp_r0
     321    REAL, DIMENSION(nbp_lon,jj_nb)             :: tmp_lon, tmp_lat
     322    REAL, DIMENSION(nbp_lon,jj_nb)             :: tmp_r0
    324323
    325324!*************************************************************************************
     
    345344       IF (is_sequential) THEN
    346345          ndexcs(:) = 0
    347           itau_w = itau_phy + itime + start_time * day_step / iphysiq
     346          itau_w = itau_phy + itime + start_time * day_step_phy
    348347          DO i = 1, maxrecv
    349348            IF (inforecv(i)%action) THEN
    350                 CALL histwrite(nidcs,inforecv(i)%name,itau_w,tab_read_flds(:,:,i),iim*(jjm+1),ndexcs)
     349                CALL histwrite(nidcs,inforecv(i)%name,itau_w,tab_read_flds(:,:,i),nbp_lon*(nbp_lat),ndexcs)
    351350            ENDIF
    352351          END DO
     
    373372! Transform the currents from cartesian to spheric coordinates
    374373! tmp_r0 should be zero
    375           CALL geo2atm(iim, jj_nb, tab_read_flds(:,:,idr_curenx), &
     374          CALL geo2atm(nbp_lon, jj_nb, tab_read_flds(:,:,idr_curenx), &
    376375             tab_read_flds(:,:,idr_cureny), tab_read_flds(:,:,idr_curenz), &
    377376               tmp_lon, tmp_lat, &
     
    542541    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send
    543542    USE indice_sol_mod
    544     INCLUDE "dimensions.h"
     543    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    545544
    546545! Input arguments
     
    635634       IF (.NOT. ALLOCATED(cpl_sols2D)) THEN
    636635          sum_error = 0
    637           ALLOCATE(cpl_sols2D(iim,jj_nb,2), stat=error)
    638           sum_error = sum_error + error
    639           ALLOCATE(cpl_nsol2D(iim,jj_nb,2), stat=error)
    640           sum_error = sum_error + error
    641           ALLOCATE(cpl_rain2D(iim,jj_nb,2), stat=error)
    642           sum_error = sum_error + error
    643           ALLOCATE(cpl_snow2D(iim,jj_nb,2), stat=error)
    644           sum_error = sum_error + error
    645           ALLOCATE(cpl_evap2D(iim,jj_nb,2), stat=error)
    646           sum_error = sum_error + error
    647           ALLOCATE(cpl_tsol2D(iim,jj_nb,2), stat=error)
    648           sum_error = sum_error + error
    649           ALLOCATE(cpl_fder2D(iim,jj_nb,2), stat=error)
    650           sum_error = sum_error + error
    651           ALLOCATE(cpl_albe2D(iim,jj_nb,2), stat=error)
    652           sum_error = sum_error + error
    653           ALLOCATE(cpl_taux2D(iim,jj_nb,2), stat=error)
    654           sum_error = sum_error + error
    655           ALLOCATE(cpl_tauy2D(iim,jj_nb,2), stat=error)
    656           sum_error = sum_error + error
    657           ALLOCATE(cpl_windsp2D(iim,jj_nb), stat=error)
    658           sum_error = sum_error + error
    659           ALLOCATE(cpl_taumod2D(iim,jj_nb,2), stat=error)
     636          ALLOCATE(cpl_sols2D(nbp_lon,jj_nb,2), stat=error)
     637          sum_error = sum_error + error
     638          ALLOCATE(cpl_nsol2D(nbp_lon,jj_nb,2), stat=error)
     639          sum_error = sum_error + error
     640          ALLOCATE(cpl_rain2D(nbp_lon,jj_nb,2), stat=error)
     641          sum_error = sum_error + error
     642          ALLOCATE(cpl_snow2D(nbp_lon,jj_nb,2), stat=error)
     643          sum_error = sum_error + error
     644          ALLOCATE(cpl_evap2D(nbp_lon,jj_nb,2), stat=error)
     645          sum_error = sum_error + error
     646          ALLOCATE(cpl_tsol2D(nbp_lon,jj_nb,2), stat=error)
     647          sum_error = sum_error + error
     648          ALLOCATE(cpl_fder2D(nbp_lon,jj_nb,2), stat=error)
     649          sum_error = sum_error + error
     650          ALLOCATE(cpl_albe2D(nbp_lon,jj_nb,2), stat=error)
     651          sum_error = sum_error + error
     652          ALLOCATE(cpl_taux2D(nbp_lon,jj_nb,2), stat=error)
     653          sum_error = sum_error + error
     654          ALLOCATE(cpl_tauy2D(nbp_lon,jj_nb,2), stat=error)
     655          sum_error = sum_error + error
     656          ALLOCATE(cpl_windsp2D(nbp_lon,jj_nb), stat=error)
     657          sum_error = sum_error + error
     658          ALLOCATE(cpl_taumod2D(nbp_lon,jj_nb,2), stat=error)
    660659          sum_error = sum_error + error
    661660         
    662661          IF (carbon_cycle_cpl) THEN
    663              ALLOCATE(cpl_atm_co22D(iim,jj_nb), stat=error)
     662             ALLOCATE(cpl_atm_co22D(nbp_lon,jj_nb), stat=error)
    664663             sum_error = sum_error + error
    665664          END IF
     
    733732    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl
    734733    USE indice_sol_mod
    735     INCLUDE "dimensions.h"
     734    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    736735
    737736! Input arguments
     
    820819       IF (.NOT. ALLOCATED(cpl_sols2D)) THEN
    821820          sum_error = 0
    822           ALLOCATE(cpl_sols2D(iim,jj_nb,2), stat=error)
    823           sum_error = sum_error + error
    824           ALLOCATE(cpl_nsol2D(iim,jj_nb,2), stat=error)
    825           sum_error = sum_error + error
    826           ALLOCATE(cpl_rain2D(iim,jj_nb,2), stat=error)
    827           sum_error = sum_error + error
    828           ALLOCATE(cpl_snow2D(iim,jj_nb,2), stat=error)
    829           sum_error = sum_error + error
    830           ALLOCATE(cpl_evap2D(iim,jj_nb,2), stat=error)
    831           sum_error = sum_error + error
    832           ALLOCATE(cpl_tsol2D(iim,jj_nb,2), stat=error)
    833           sum_error = sum_error + error
    834           ALLOCATE(cpl_fder2D(iim,jj_nb,2), stat=error)
    835           sum_error = sum_error + error
    836           ALLOCATE(cpl_albe2D(iim,jj_nb,2), stat=error)
    837           sum_error = sum_error + error
    838           ALLOCATE(cpl_taux2D(iim,jj_nb,2), stat=error)
    839           sum_error = sum_error + error
    840           ALLOCATE(cpl_tauy2D(iim,jj_nb,2), stat=error)
    841           sum_error = sum_error + error
    842           ALLOCATE(cpl_windsp2D(iim,jj_nb), stat=error)
    843           sum_error = sum_error + error
    844           ALLOCATE(cpl_taumod2D(iim,jj_nb,2), stat=error)
     821          ALLOCATE(cpl_sols2D(nbp_lon,jj_nb,2), stat=error)
     822          sum_error = sum_error + error
     823          ALLOCATE(cpl_nsol2D(nbp_lon,jj_nb,2), stat=error)
     824          sum_error = sum_error + error
     825          ALLOCATE(cpl_rain2D(nbp_lon,jj_nb,2), stat=error)
     826          sum_error = sum_error + error
     827          ALLOCATE(cpl_snow2D(nbp_lon,jj_nb,2), stat=error)
     828          sum_error = sum_error + error
     829          ALLOCATE(cpl_evap2D(nbp_lon,jj_nb,2), stat=error)
     830          sum_error = sum_error + error
     831          ALLOCATE(cpl_tsol2D(nbp_lon,jj_nb,2), stat=error)
     832          sum_error = sum_error + error
     833          ALLOCATE(cpl_fder2D(nbp_lon,jj_nb,2), stat=error)
     834          sum_error = sum_error + error
     835          ALLOCATE(cpl_albe2D(nbp_lon,jj_nb,2), stat=error)
     836          sum_error = sum_error + error
     837          ALLOCATE(cpl_taux2D(nbp_lon,jj_nb,2), stat=error)
     838          sum_error = sum_error + error
     839          ALLOCATE(cpl_tauy2D(nbp_lon,jj_nb,2), stat=error)
     840          sum_error = sum_error + error
     841          ALLOCATE(cpl_windsp2D(nbp_lon,jj_nb), stat=error)
     842          sum_error = sum_error + error
     843          ALLOCATE(cpl_taumod2D(nbp_lon,jj_nb,2), stat=error)
    845844          sum_error = sum_error + error
    846845
    847846          IF (carbon_cycle_cpl) THEN
    848              ALLOCATE(cpl_atm_co22D(iim,jj_nb), stat=error)
     847             ALLOCATE(cpl_atm_co22D(nbp_lon,jj_nb), stat=error)
    849848             sum_error = sum_error + error
    850849          END IF
     
    913912! (it is done in cpl_send_seaice_fields).
    914913!
    915     INCLUDE "dimensions.h"
     914    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    916915
    917916! Input arguments
     
    925924! Local variables
    926925!*************************************************************************************
    927     REAL, DIMENSION(iim,jj_nb)             :: rriv2D
    928     REAL, DIMENSION(iim,jj_nb)             :: rcoa2D
     926    REAL, DIMENSION(nbp_lon,jj_nb)             :: rriv2D
     927    REAL, DIMENSION(nbp_lon,jj_nb)             :: rcoa2D
    929928
    930929!*************************************************************************************
     
    972971!
    973972
    974     INCLUDE "dimensions.h"
     973    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    975974
    976975! Input varibales
     
    983982! Local varibales
    984983!*************************************************************************************
    985     REAL, DIMENSION(iim,jj_nb)             :: rlic2D
     984    REAL, DIMENSION(nbp_lon,jj_nb)             :: rlic2D
    986985
    987986!*************************************************************************************
     
    10271026    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl
    10281027    USE indice_sol_mod
     1028    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
     1029    USE time_phylmdz_mod, ONLY: start_time, itau_phy
    10291030! Some includes
    1030 !*************************************************************************************
    1031     INCLUDE "temps.h"
    1032     INCLUDE "dimensions.h"
    1033    
     1031!   
    10341032! Input arguments
    10351033!*************************************************************************************
     
    10451043    INTEGER                                              :: itau_w
    10461044    INTEGER                                              :: time_sec
    1047     INTEGER, DIMENSION(iim*(jjm+1))                      :: ndexct
     1045    INTEGER, DIMENSION(nbp_lon*(nbp_lat))                      :: ndexct
    10481046    REAL                                                 :: Up, Down
    1049     REAL, DIMENSION(iim, jj_nb)                          :: tmp_lon, tmp_lat
    1050     REAL, DIMENSION(iim, jj_nb, 4)                       :: pctsrf2D
    1051     REAL, DIMENSION(iim, jj_nb)                          :: deno
     1047    REAL, DIMENSION(nbp_lon, jj_nb)                          :: tmp_lon, tmp_lat
     1048    REAL, DIMENSION(nbp_lon, jj_nb, 4)                       :: pctsrf2D
     1049    REAL, DIMENSION(nbp_lon, jj_nb)                          :: deno
    10521050    CHARACTER(len = 20)                                  :: modname = 'cpl_send_all'
    10531051    CHARACTER(len = 80)                                  :: abort_message
    10541052   
    10551053! Variables with fields to coupler
    1056     REAL, DIMENSION(iim, jj_nb)                          :: tmp_taux
    1057     REAL, DIMENSION(iim, jj_nb)                          :: tmp_tauy
    1058     REAL, DIMENSION(iim, jj_nb)                          :: tmp_calv
     1054    REAL, DIMENSION(nbp_lon, jj_nb)                          :: tmp_taux
     1055    REAL, DIMENSION(nbp_lon, jj_nb)                          :: tmp_tauy
     1056    REAL, DIMENSION(nbp_lon, jj_nb)                          :: tmp_calv
    10591057! Table with all fields to send to coupler
    1060     REAL, DIMENSION(iim, jj_nb, maxsend)                 :: tab_flds
     1058    REAL, DIMENSION(nbp_lon, jj_nb, maxsend)                 :: tab_flds
    10611059    REAL, DIMENSION(klon_mpi)                            :: rlon_mpi, rlat_mpi
    10621060
     
    11121110
    11131111      DO j = 1, jj_nb
    1114          tmp_calv(:,j) = DOT_PRODUCT (cpl_rlic2D(1:iim,j), &
    1115               pctsrf2D(1:iim,j,is_lic)) / REAL(iim)
     1112         tmp_calv(:,j) = DOT_PRODUCT (cpl_rlic2D(1:nbp_lon,j), &
     1113              pctsrf2D(1:nbp_lon,j,is_lic)) / REAL(nbp_lon)
    11161114      ENDDO
    11171115   
     
    11331131         
    11341132         IF (.NOT. is_north_pole .AND. ii_begin /=1) THEN
    1135             Up=Up+tmp_calv(iim,1)
     1133            Up=Up+tmp_calv(nbp_lon,1)
    11361134            tmp_calv(:,1)=Up
    11371135         ENDIF
    11381136         
    1139          IF (.NOT. is_south_pole .AND. ii_end /= iim) THEN
     1137         IF (.NOT. is_south_pole .AND. ii_end /= nbp_lon) THEN
    11401138            Down=Down+tmp_calv(1,jj_nb)
    11411139            tmp_calv(:,jj_nb)=Down       
     
    12261224    IF (is_sequential) THEN
    12271225       IF (is_north_pole) tmp_lon(:,1)     = tmp_lon(:,2)
    1228        IF (is_south_pole) tmp_lon(:,jjm+1) = tmp_lon(:,jjm)
     1226       IF (is_south_pole) tmp_lon(:,nbp_lat) = tmp_lon(:,nbp_lat-1)
    12291227    ENDIF
    12301228     
     
    12321230    IF (is_sequential) THEN
    12331231       ndexct(:) = 0
    1234        itau_w = itau_phy + itime + start_time * day_step / iphysiq
    1235        CALL histwrite(nidct,'tauxe',itau_w,tmp_taux,iim*(jjm+1),ndexct)
    1236        CALL histwrite(nidct,'tauyn',itau_w,tmp_tauy,iim*(jjm+1),ndexct)
    1237        CALL histwrite(nidct,'tmp_lon',itau_w,tmp_lon,iim*(jjm+1),ndexct)
    1238        CALL histwrite(nidct,'tmp_lat',itau_w,tmp_lat,iim*(jjm+1),ndexct)
     1232       itau_w = itau_phy + itime + start_time * day_step_phy
     1233       CALL histwrite(nidct,'tauxe',itau_w,tmp_taux,nbp_lon*(nbp_lat),ndexct)
     1234       CALL histwrite(nidct,'tauyn',itau_w,tmp_tauy,nbp_lon*(nbp_lat),ndexct)
     1235       CALL histwrite(nidct,'tmp_lon',itau_w,tmp_lon,nbp_lon*(nbp_lat),ndexct)
     1236       CALL histwrite(nidct,'tmp_lat',itau_w,tmp_lat,nbp_lon*(nbp_lat),ndexct)
    12391237    ENDIF
    12401238
     
    12421240! cartesian 3D coordinates
    12431241!$OMP MASTER
    1244     CALL atm2geo (iim, jj_nb, tmp_taux, tmp_tauy, tmp_lon, tmp_lat, &
     1242    CALL atm2geo (nbp_lon, jj_nb, tmp_taux, tmp_tauy, tmp_lon, tmp_lat, &
    12451243         tab_flds(:,:,ids_tauxxu), tab_flds(:,:,ids_tauyyu), tab_flds(:,:,ids_tauzzu) )
    12461244   
     
    12571255        DO j=1,maxsend
    12581256          IF (infosend(j)%action) CALL histwrite(nidct,infosend(j)%name, itau_w, &
    1259              tab_flds(:,:,j),iim*(jjm+1),ndexct)
     1257             tab_flds(:,:,j),nbp_lon*(nbp_lat),ndexct)
    12601258        ENDDO
    12611259    ENDIF
     
    13111309!   champ_out    champ sur la grille 'gatherd'
    13121310!
    1313     INCLUDE "dimensions.h"
     1311    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    13141312
    13151313! Input
    13161314    INTEGER, INTENT(IN)                       :: knon
    1317     REAL, DIMENSION(iim,jj_nb), INTENT(IN)    :: champ_in
     1315    REAL, DIMENSION(nbp_lon,jj_nb), INTENT(IN)    :: champ_in
    13181316    INTEGER, DIMENSION(klon), INTENT(IN)      :: knindex
    13191317
     
    13301328   
    13311329
    1332 ! Transform from 2 dimensions (iim,jj_nb) to 1 dimension (klon)
     1330! Transform from 2 dimensions (nbp_lon,jj_nb) to 1 dimension (klon)
    13331331!$OMP MASTER
    13341332    CALL Grid2Dto1D_mpi(champ_in,temp_mpi)
     
    13601358!   champ_out    champ sur la grille 2D
    13611359!
    1362     INCLUDE "dimensions.h"
     1360    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    13631361   
    13641362! Input arguments
     
    13701368! Output arguments
    13711369!*************************************************************************************
    1372     REAL, DIMENSION(iim,jj_nb), INTENT(OUT) :: champ_out
     1370    REAL, DIMENSION(nbp_lon,jj_nb), INTENT(OUT) :: champ_out
    13731371
    13741372! Local variables
     
    13861384    ENDDO
    13871385
    1388 ! Transform from 1 dimension (klon) to 2 dimensions (iim,jj_nb)
     1386! Transform from 1 dimension (klon) to 2 dimensions (nbp_lon,jj_nb)
    13891387    CALL gather_omp(temp_omp,temp_mpi)
    13901388
  • LMDZ5/trunk/libf/phylmd/ini_histday_seri.h

    r1907 r2344  
    77      IF (type_run.EQ."AMIP") THEN
    88!
    9        zstophy = dtime
     9       zstophy = pdtphys
    1010       zout = ecrit_day
    1111!
     
    1313         CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
    1414!
    15          CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlon,zx_lon)
    16          DO i = 1, iim
     15         CALL gr_fi_ecrit(1,klon,nbp_lon,nbp_lat,rlon,zx_lon)
     16         DO i = 1, nbp_lon
    1717            zx_lon(i,1) = rlon(i+1)
    18             zx_lon(i,jjmp1) = rlon(i+1)
     18            zx_lon(i,nbp_lat) = rlon(i+1)
    1919         ENDDO
    2020         DO ll=1,klev
    2121            znivsig(ll)=REAL(ll)
    2222         ENDDO
    23          CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlat,zx_lat)
     23         CALL gr_fi_ecrit(1,klon,nbp_lon,nbp_lat,rlat,zx_lat)
    2424!
    2525         imin_debut=1
     
    2929!
    3030         CALL histbeg("histday_seri.nc",  &
    31                        iim,zx_lon(:,1), jjmp1,zx_lat(1,:), &
     31                       nbp_lon,zx_lon(:,1),nbp_lat,zx_lat(1,:), &
    3232                       imin_debut,nbpti,jmin_debut,nbptj, &
    3333                       itau_phy, zjulian, dtime, &
     
    4040         CALL histdef(nid_day_seri, "bilTOA",  &
    4141                      "Net radiation at model top", "W/m2", &
    42                       iim,jjmp1,nhori, 1,1,1, -99, 32,  &
     42                      nbp_lon,nbp_lat,nhori, 1,1,1, -99, 32,  &
    4343                      "ave(X)", zstophy,zout)
    4444!
    4545         CALL histdef(nid_day_seri, "bils",  &
    4646                      "Net downward energy flux at surface","W/m2", &
    47                       iim,jjmp1,nhori, 1,1,1, -99, 32,  &
     47                      nbp_lon,nbp_lat,nhori, 1,1,1, -99, 32,  &
    4848                      "ave(X)", zstophy,zout)
    4949!
    5050         CALL histdef(nid_day_seri, "ecin",  &
    5151                      "Total kinetic energy (per unit area)","J/m2", &
    52                       iim,jjmp1,nhori, 1,1,1, -99, 32, &
     52                      nbp_lon,nbp_lat,nhori, 1,1,1, -99, 32, &
    5353                      "ave(X)", zstophy,zout)
    5454!
     
    5959                     "Total relative angular momentum (per unit area)", &
    6060                     "kg/s", &
    61                       iim,jjmp1,nhori, 1,1,1, -99, 32, &
     61                      nbp_lon,nbp_lat,nhori, 1,1,1, -99, 32, &
    6262                      "ave(X)", zstophy,zout)
    6363!
    6464         CALL histdef(nid_day_seri, "frictor",  &
    6565                     "Friction torque (per unit area)", "N/m", &
    66                       iim,jjmp1,nhori, 1,1,1, -99, 32, &
     66                      nbp_lon,nbp_lat,nhori, 1,1,1, -99, 32, &
    6767                      "ave(X)", zstophy,zout)
    6868!
    6969         CALL histdef(nid_day_seri, "mountor",  &
    7070                     "Mountain torque (per unit area)", "N/m", &
    71                       iim,jjmp1,nhori, 1,1,1, -99, 32, &
     71                      nbp_lon,nbp_lat,nhori, 1,1,1, -99, 32, &
    7272                      "ave(X)", zstophy,zout)
    7373!
     
    7777                     "Axial angular momentum (per unit area)", &
    7878                     "kg/s", &
    79                       iim,jjmp1,nhori, 1,1,1, -99, 32, &
     79                      nbp_lon,nbp_lat,nhori, 1,1,1, -99, 32, &
    8080                      "ave(X)", zstophy,zout)
    8181!
    8282         CALL histdef(nid_day_seri, "torsfc",  &
    8383              "Total surface torque (including mountain torque)", "N/m", &
    84                       iim,jjmp1,nhori, 1,1,1, -99, 32, &
     84                      nbp_lon,nbp_lat,nhori, 1,1,1, -99, 32, &
    8585                      "ave(X)", zstophy,zout)
    8686!
     
    8989         CALL histdef(nid_day_seri, "tamv",  &
    9090                      "Temperature (mass-weighted vert. ave)", "K", &
    91                       iim,jjmp1,nhori, 1,1,1, -99, 32, &
     91                      nbp_lon,nbp_lat,nhori, 1,1,1, -99, 32, &
    9292                      "ave(X)", zstophy,zout)
    9393!
    9494         CALL histdef(nid_day_seri, "psol",  &
    9595                      "Surface pressure", "Pa", &
    96                       iim,jjmp1,nhori, 1,1,1, -99, 32,  &
     96                      nbp_lon,nbp_lat,nhori, 1,1,1, -99, 32,  &
    9797                      "ave(X)", zstophy,zout)
    9898!
     
    100100                      "Evaporation and sublimation (per unit area)",  &
    101101                      "kg/(m2*s)", &
    102                       iim,jjmp1,nhori, 1,1,1, -99, 32,  &
     102                      nbp_lon,nbp_lat,nhori, 1,1,1, -99, 32,  &
    103103                      "ave(X)", zstophy,zout)
    104104!
     
    106106!    .         "SnowFrac",
    107107!    .         "Snow-covered area ", "%", 
    108 !    .         iim,jjmp1,nhori, 1,1,1, -99, 32,
     108!    .         nbp_lon,nbp_lat,nhori, 1,1,1, -99, 32,
    109109!    .         "ave(X)", zstophy,zout)
    110110!
     
    113113!IM 191104  .                "Snow Depth (water equivalent)", "kg/m2",
    114114!    .                "Snow Mass", "kg/m2",
    115 !    .                iim,jjmp1,nhori, 1,1,1, -99, 32,
     115!    .                nbp_lon,nbp_lat,nhori, 1,1,1, -99, 32,
    116116!    .               "ave(X)", zstophy,zout)
    117117!
     
    119119               "tsol_"//clnsurf(is_oce),  &
    120120               "SST over open (ice-free) ocean ", "K",   &
    121                iim,jjmp1,nhori, 1,1,1, -99, 32, &
     121               nbp_lon,nbp_lat,nhori, 1,1,1, -99, 32, &
    122122               "ave(X)", zstophy,zout)
    123123!
  • LMDZ5/trunk/libf/phylmd/ini_paramLMDZ_phy.h

    r1907 r2344  
    99      if (is_mpi_root) then
    1010!
    11        zstophy = dtime
     11       zstophy = pdtphys
    1212       zout = mth_len*un_jour
    1313!
     
    1515       CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
    1616!
    17        CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlon_glo,zx_lon)
    18        if (iim.gt.1) then
    19        DO i = 1, iim
     17       CALL gr_fi_ecrit(1,klon,nbp_lon,nbp_lat,rlon_glo,zx_lon)
     18       if (nbp_lon.gt.1) then
     19       DO i = 1, nbp_lon
    2020         zx_lon(i,1) = rlon_glo(i+1)
    21          zx_lon(i,jjmp1) = rlon_glo(i+1)
     21         zx_lon(i,nbp_lat) = rlon_glo(i+1)
    2222       ENDDO
    2323       endif
    24        CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlat_glo,zx_lat)
     24       CALL gr_fi_ecrit(1,klon,nbp_lon,nbp_lat,rlat_glo,zx_lat)
    2525!
    2626       CALL histbeg("paramLMDZ_phy.nc",  &
  • LMDZ5/trunk/libf/phylmd/iophy.F90

    r2319 r2344  
    5454#endif
    5555  IMPLICIT NONE
    56   INCLUDE 'dimensions.h'
     56!  INCLUDE 'dimensions.h'
    5757    REAL,DIMENSION(klon),INTENT(IN) :: rlon
    5858    REAL,DIMENSION(klon),INTENT(IN) :: rlat
     
    7777   
    7878!$OMP MASTER 
    79     ALLOCATE(io_lat(jjm+1-1/(iim*jjm)))
     79    ALLOCATE(io_lat(nbp_lat-1/(nbp_lon*(nbp_lat-1))))
    8080    io_lat(1)=rlat_glo(1)
    81     io_lat(jjm+1-1/(iim*jjm))=rlat_glo(klon_glo)
    82     IF ((iim*jjm) > 1) then
    83       DO i=2,jjm
    84         io_lat(i)=rlat_glo(2+(i-2)*iim)
     81    io_lat(nbp_lat-1/(nbp_lon*(nbp_lat-1)))=rlat_glo(klon_glo)
     82    IF ((nbp_lon*nbp_lat) > 1) then
     83      DO i=2,nbp_lat-1
     84        io_lat(i)=rlat_glo(2+(i-2)*nbp_lon)
    8585      ENDDO
    8686    ENDIF
    8787
    88     ALLOCATE(io_lon(iim))
    89     io_lon(:)=rlon_glo(2-1/(iim*jjm):iim+1-1/(iim*jjm))
     88    ALLOCATE(io_lon(nbp_lon))
     89    IF (klon_glo == 1) THEN
     90      io_lon(1)=rlon_glo(1)
     91    ELSE
     92      io_lon(1:nbp_lon)=rlon_glo(2:nbp_lon+1)
     93    ENDIF
     94
    9095!! (I) dtnb   : total number of domains
    9196!! (I) dnb    : domain number
     
    104109
    105110    ddid=(/ 1,2 /)
    106     dsg=(/ iim, jjm+1-1/(iim*jjm) /)
    107     dsl=(/ iim, jj_nb /)
     111    dsg=(/ nbp_lon, nbp_lat /)
     112    dsl=(/ nbp_lon, jj_nb /)
    108113    dpf=(/ 1,jj_begin /)
    109     dpl=(/ iim, jj_end /)
     114    dpl=(/ nbp_lon, jj_end /)
    110115    dhs=(/ ii_begin-1,0 /)
    111116    IF (mpi_rank==mpi_size-1) THEN
    112117      dhe=(/0,0/)
    113118    ELSE
    114       dhe=(/ iim-ii_end,0 /) 
     119      dhe=(/ nbp_lon-ii_end,0 /) 
    115120    ENDIF
    116121
     
    155160                                mpi_size, mpi_rank
    156161  USE ioipsl, only: flio_dom_set
     162  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    157163  IMPLICIT NONE
    158   INCLUDE 'dimensions.h'   
    159     REAL,DIMENSION(iim),INTENT(IN) :: lon
    160     REAL,DIMENSION(jjm+1-1/(iim*jjm)),INTENT(IN) :: lat
     164    REAL,DIMENSION(nbp_lon),INTENT(IN) :: lon
     165    REAL,DIMENSION(nbp_lat),INTENT(IN) :: lat
    161166
    162167    INTEGER,DIMENSION(2) :: ddid
     
    169174
    170175!$OMP MASTER 
    171     allocate(io_lat(jjm+1-1/(iim*jjm)))
     176    allocate(io_lat(nbp_lat))
    172177    io_lat(:)=lat(:)
    173     allocate(io_lon(iim))
     178    allocate(io_lon(nbp_lon))
    174179    io_lon(:)=lon(:)
    175180   
    176181    ddid=(/ 1,2 /)
    177     dsg=(/ iim, jjm+1-1/(iim*jjm) /)
    178     dsl=(/ iim, jj_nb /)
     182    dsg=(/ nbp_lon, nbp_lat /)
     183    dsl=(/ nbp_lon, jj_nb /)
    179184    dpf=(/ 1,jj_begin /)
    180     dpl=(/ iim, jj_end /)
     185    dpl=(/ nbp_lon, jj_end /)
    181186    dhs=(/ ii_begin-1,0 /)
    182187    if (mpi_rank==mpi_size-1) then
    183188      dhe=(/0,0/)
    184189    else
    185       dhe=(/ iim-ii_end,0 /) 
     190      dhe=(/ nbp_lon-ii_end,0 /) 
    186191    endif
    187192   
     
    198203  USE mod_phys_lmdz_para, only: is_sequential, is_using_mpi, is_mpi_root, &
    199204                                jj_begin, jj_end, jj_nb
     205  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    200206  use ioipsl, only: histbeg
    201207#ifdef CPP_XIOS
     
    203209#endif
    204210  IMPLICIT NONE
    205   include 'dimensions.h'
    206211  include 'clesphys.h'
    207212   
     
    217222!$OMP MASTER   
    218223    if (is_sequential) then
    219       call histbeg(name,iim,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
    220                    1,iim,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day)
     224      call histbeg(name,nbp_lon,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
     225                   1,nbp_lon,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day)
    221226    else
    222       call histbeg(name,iim,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
    223                    1,iim,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day,phys_domain_id)
     227      call histbeg(name,nbp_lon,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
     228                   1,nbp_lon,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day,phys_domain_id)
    224229    endif
    225230
     
    240245
    241246  USE mod_phys_lmdz_para, only: jj_begin, jj_end, jj_nb, is_sequential
     247  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    242248  use ioipsl, only: histbeg
    243249
    244250  IMPLICIT NONE
    245   include 'dimensions.h'
    246251   
    247252    character*(*), INTENT(IN) :: name
     
    255260#ifndef CPP_IOIPSL_NO_OUTPUT
    256261    if (is_sequential) then
    257       call histbeg(name,iim,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
    258                    1,iim,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day)
     262      call histbeg(name,nbp_lon,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
     263                   1,nbp_lon,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day)
    259264    else
    260       call histbeg(name,iim,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
    261                    1,iim,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day,phys_domain_id)
     265      call histbeg(name,nbp_lon,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
     266                   1,nbp_lon,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day,phys_domain_id)
    262267    endif
    263268#endif
     
    274279                                is_sequential, klon_mpi_begin, klon_mpi_end, &
    275280                                mpi_rank
    276   USE mod_grid_phy_lmdz, only: klon_glo
     281  USE mod_grid_phy_lmdz, only: klon_glo, nbp_lon, nbp_lat
    277282  use ioipsl, only: histbeg
    278283
    279284  IMPLICIT NONE
    280   include 'dimensions.h'
    281285
    282286    REAL,DIMENSION(klon),INTENT(IN) :: rlon
     
    304308    REAL, allocatable, DIMENSION(:) :: npplat, npplon
    305309    REAL, allocatable, DIMENSION(:,:) :: npplat_bounds, npplon_bounds
    306     INTEGER, PARAMETER :: jjmp1=jjm+1-1/jjm
    307     REAL, DIMENSION(iim,jjmp1) :: zx_lon, zx_lat
     310    REAL, DIMENSION(nbp_lon,nbp_lat) :: zx_lon, zx_lat
    308311
    309312    CALL gather(rlat,rlat_glo)
     
    330333     endif
    331334!
    332      IF ( tabij(i).LE.iim) THEN
     335     IF ( tabij(i).LE.nbp_lon) THEN
    333336      plat_bounds(i,1)=rlat_glo(tabij(i))
    334337     ELSE
    335       plat_bounds(i,1)=rlat_glo(tabij(i)-iim)
     338      plat_bounds(i,1)=rlat_glo(tabij(i)-nbp_lon)
    336339     ENDIF
    337      plat_bounds(i,2)=rlat_glo(tabij(i)+iim)
     340     plat_bounds(i,2)=rlat_glo(tabij(i)+nbp_lon)
    338341!
    339342!    print*,'CFMIP_iophy point i lon lon_bds',i,plon_bounds(i,1),rlon_glo(tabij(i)),plon_bounds(i,2)
     
    351354     ENDDO
    352355
    353        CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlon_glo,zx_lon)
    354        if ((iim*jjm).gt.1) then
    355        DO i = 1, iim
     356       CALL gr_fi_ecrit(1,klon,nbp_lon,nbp_lat,rlon_glo,zx_lon)
     357       if ((nbp_lon*nbp_lat).gt.1) then
     358       DO i = 1, nbp_lon
    356359         zx_lon(i,1) = rlon_glo(i+1)
    357          zx_lon(i,jjmp1) = rlon_glo(i+1)
     360         zx_lon(i,nbp_lat) = rlon_glo(i+1)
    358361       ENDDO
    359362       endif
    360        CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlat_glo,zx_lat)
     363       CALL gr_fi_ecrit(1,klon,nbp_lon,nbp_lat,rlat_glo,zx_lat)
    361364
    362365    DO i=1,pim
     
    367370
    368371     if (ipt(i).EQ.1) then
    369       plon_bounds(i,1)=zx_lon(iim,jpt(i))
     372      plon_bounds(i,1)=zx_lon(nbp_lon,jpt(i))
    370373      plon_bounds(i,2)=360.+zx_lon(ipt(i)+1,jpt(i))
    371374     endif
    372375 
    373      if (ipt(i).EQ.iim) then
     376     if (ipt(i).EQ.nbp_lon) then
    374377      plon_bounds(i,2)=360.+zx_lon(1,jpt(i))
    375378     endif
     
    383386     endif
    384387 
    385      if (jpt(i).EQ.jjmp1) then
    386       plat_bounds(i,1)=zx_lat(ipt(i),jjmp1)+0.001
    387       plat_bounds(i,2)=zx_lat(ipt(i),jjmp1)-0.001
     388     if (jpt(i).EQ.nbp_lat) then
     389      plat_bounds(i,1)=zx_lat(ipt(i),nbp_lat)+0.001
     390      plat_bounds(i,2)=zx_lat(ipt(i),nbp_lat)-0.001
    388391     endif
    389392!
     
    451454    use phys_output_var_mod, only: type_ecri, zoutm, zdtime_moy, lev_files, &
    452455                                   nid_files, nhorim, swaero_diag, nfiles
     456    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    453457    IMPLICIT NONE
    454458
    455     INCLUDE "dimensions.h"
    456     INCLUDE "temps.h"
    457459    INCLUDE "clesphys.h"
    458460
     
    478480       IF ( flag_var(iff)<=lev_files(iff) ) THEN
    479481          CALL histdef (nid_files(iff),nomvar,titrevar,unitvar, &
    480                iim,jj_nb,nhorim(iff), 1,1,1, -99, 32, &
     482               nbp_lon,jj_nb,nhorim(iff), 1,1,1, -99, 32, &
    481483               type_ecri(iff), zstophym,zoutm(iff))               
    482484       ENDIF
     
    507509                                   nhorim, zdtime_moy, levmin, levmax, &
    508510                                   nvertm, nfiles
     511    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    509512    IMPLICIT NONE
    510513
    511     INCLUDE "dimensions.h"
    512     INCLUDE "temps.h"
    513 !    INCLUDE "indicesol.h"
    514514    INCLUDE "clesphys.h"
    515515
     
    535535       IF ( flag_var(iff)<=lev_files(iff) ) THEN
    536536          CALL histdef (nid_files(iff), nomvar, titrevar, unitvar, &
    537                iim, jj_nb, nhorim(iff), klev, levmin(iff), &
     537               nbp_lon, jj_nb, nhorim(iff), klev, levmin(iff), &
    538538               levmax(iff)-levmin(iff)+1, nvertm(iff), 32, type_ecri(iff), &
    539539               zstophym, zoutm(iff))
     
    564564                                   nid_files, nhorim, swaero_diag
    565565    USE print_control_mod, ONLY: prt_level,lunout
     566    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    566567#ifdef CPP_XIOS
    567568    use wxios, only: wxios_add_field_to_file
     
    569570    IMPLICIT NONE
    570571
    571     INCLUDE "dimensions.h"
    572     INCLUDE "temps.h"
    573572    INCLUDE "clesphys.h"
    574573
     
    621620       IF ( var%flag(iff)<=lev_files(iff) ) THEN
    622621          CALL histdef (nid_files(iff), var%name, var%description, var%unit, &
    623                iim,jj_nb,nhorim(iff), 1,1,1, -99, 32, &
     622               nbp_lon,jj_nb,nhorim(iff), 1,1,1, -99, 32, &
    624623               typeecrit, zstophym,zoutm(iff))               
    625624       ENDIF
     
    651650                                   levmax, nvertm
    652651    USE print_control_mod, ONLY: prt_level,lunout
     652    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    653653#ifdef CPP_XIOS
    654654    use wxios, only: wxios_add_field_to_file
     
    656656    IMPLICIT NONE
    657657
    658     INCLUDE "dimensions.h"
    659     INCLUDE "temps.h"
    660658    INCLUDE "clesphys.h"
    661659
     
    708706       IF ( var%flag(iff)<=lev_files(iff) ) THEN
    709707          CALL histdef (nid_files(iff), var%name, var%description, var%unit, &
    710                iim, jj_nb, nhorim(iff), klev, levmin(iff), &
     708               nbp_lon, jj_nb, nhorim(iff), klev, levmin(iff), &
    711709               levmax(iff)-levmin(iff)+1, nvertm(iff), 32, typeecrit, &
    712710               zstophym, zoutm(iff))
     
    750748  USE ioipsl, only: histwrite
    751749  USE print_control_mod, ONLY: prt_level,lunout
     750  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    752751  IMPLICIT NONE
    753   include 'dimensions.h'
    754752   
    755753    integer,INTENT(IN) :: nid
     
    760758    REAL,DIMENSION(klon_mpi) :: buffer_omp
    761759    INTEGER, allocatable, DIMENSION(:) :: index2d
    762     REAL :: Field2d(iim,jj_nb)
     760    REAL :: Field2d(nbp_lon,jj_nb)
    763761
    764762    integer :: ip
     
    772770    CALL grid1Dto2D_mpi(buffer_omp,Field2d)
    773771    if(.NOT.lpoint) THEN
    774      ALLOCATE(index2d(iim*jj_nb))
    775      ALLOCATE(fieldok(iim*jj_nb))
     772     ALLOCATE(index2d(nbp_lon*jj_nb))
     773     ALLOCATE(fieldok(nbp_lon*jj_nb))
    776774     IF (prt_level >= 10) write(lunout,*)'Sending ',name,' to IOIPSL'
    777      CALL histwrite(nid,name,itau,Field2d,iim*jj_nb,index2d)
     775     CALL histwrite(nid,name,itau,Field2d,nbp_lon*jj_nb,index2d)
    778776     IF (prt_level >= 10) write(lunout,*)'Finished sending ',name,' to IOIPSL'
    779777    else
     
    813811                                is_sequential, klon_mpi_begin, klon_mpi_end, &
    814812                                jj_nb, klon_mpi
     813  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    815814  use ioipsl, only: histwrite
    816815  USE print_control_mod, ONLY: prt_level,lunout
    817816  IMPLICIT NONE
    818   include 'dimensions.h'
    819817   
    820818    integer,INTENT(IN) :: nid
     
    824822    REAL,DIMENSION(:,:),INTENT(IN) :: field  ! --> field(klon,:)
    825823    REAL,DIMENSION(klon_mpi,size(field,2)) :: buffer_omp
    826     REAL :: Field3d(iim,jj_nb,size(field,2))
     824    REAL :: Field3d(nbp_lon,jj_nb,size(field,2))
    827825    INTEGER :: ip, n, nlev
    828826    INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d
     
    837835    CALL grid1Dto2D_mpi(buffer_omp,field3d)
    838836    if(.NOT.lpoint) THEN
    839      ALLOCATE(index3d(iim*jj_nb*nlev))
    840      ALLOCATE(fieldok(iim*jj_nb,nlev))
     837     ALLOCATE(index3d(nbp_lon*jj_nb*nlev))
     838     ALLOCATE(fieldok(nbp_lon*jj_nb,nlev))
    841839     IF (prt_level >= 10) write(lunout,*)'Sending ',name,' to IOIPSL'
    842      CALL histwrite(nid,name,itau,Field3d,iim*jj_nb*nlev,index3d)
     840     CALL histwrite(nid,name,itau,Field3d,nbp_lon*jj_nb*nlev,index3d)
    843841     IF (prt_level >= 10) write(lunout,*)'Finished sending ',name,' to IOIPSL'
    844842   else
     
    889887                                 nid_files
    890888  USE print_control_mod, ONLY: prt_level,lunout
     889  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    891890#ifdef CPP_XIOS
    892891  USE xios, only: xios_send_field
     
    895894
    896895  IMPLICIT NONE
    897   INCLUDE 'dimensions.h'
    898896  include 'clesphys.h'
    899897
     
    908906    REAL,DIMENSION(klon_mpi) :: buffer_omp
    909907    INTEGER, allocatable, DIMENSION(:) :: index2d
    910     REAL :: Field2d(iim,jj_nb)
     908    REAL :: Field2d(nbp_lon,jj_nb)
    911909
    912910    INTEGER :: ip
     
    989987
    990988                  IF(.NOT.clef_stations(iff)) THEN
    991                         ALLOCATE(index2d(iim*jj_nb))
    992                         ALLOCATE(fieldok(iim*jj_nb))
     989                        ALLOCATE(index2d(nbp_lon*jj_nb))
     990                        ALLOCATE(fieldok(nbp_lon*jj_nb))
    993991#ifndef CPP_IOIPSL_NO_OUTPUT
    994                         CALL histwrite(nid_files(iff),var%name,itau_iophy,Field2d,iim*jj_nb,index2d)
     992                        CALL histwrite(nid_files(iff),var%name,itau_iophy,Field2d,nbp_lon*jj_nb,index2d)
    995993#endif
    996994!#ifdef CPP_XIOS
     
    10481046                                 nfiles, vars_defined, clef_stations, &
    10491047                                 nid_files
     1048  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    10501049#ifdef CPP_XIOS
    10511050  USE xios, only: xios_send_field
     
    10541053
    10551054  IMPLICIT NONE
    1056   INCLUDE 'dimensions.h'
    10571055  include 'clesphys.h'
    10581056
     
    10651063!$OMP THREADPRIVATE(firstx)
    10661064    REAL,DIMENSION(klon_mpi,SIZE(field,2)) :: buffer_omp
    1067     REAL :: Field3d(iim,jj_nb,SIZE(field,2))
     1065    REAL :: Field3d(nbp_lon,jj_nb,SIZE(field,2))
    10681066    INTEGER :: ip, n, nlev, nlevx
    10691067    INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d
     
    11311129                  write(lunout,*)'histwrite3d_phy: call xios_send_field for ', &
    11321130                                  trim(var%name), ' with iim jjm nlevx = ', &
    1133                                   iim,jj_nb,nlevx
     1131                                  nbp_lon,jj_nb,nlevx
    11341132                endif
    11351133                CALL xios_send_field(var%name, Field3d(:,:,1:nlevx))
     
    11381136#endif
    11391137                IF (.NOT.clef_stations(iff)) THEN
    1140                         ALLOCATE(index3d(iim*jj_nb*nlev))
    1141                         ALLOCATE(fieldok(iim*jj_nb,nlev))
     1138                        ALLOCATE(index3d(nbp_lon*jj_nb*nlev))
     1139                        ALLOCATE(fieldok(nbp_lon*jj_nb,nlev))
    11421140
    11431141#ifndef CPP_IOIPSL_NO_OUTPUT
    1144                         CALL histwrite(nid_files(iff),var%name,itau_iophy,Field3d,iim*jj_nb*nlev,index3d)
     1142                        CALL histwrite(nid_files(iff),var%name,itau_iophy,Field3d,nbp_lon*jj_nb*nlev,index3d)
    11451143#endif
    11461144
     
    11941192                                is_sequential, klon_mpi_begin, klon_mpi_end, &
    11951193                                jj_nb, klon_mpi
     1194  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    11961195  USE xios, only: xios_send_field
    11971196  USE print_control_mod, ONLY: prt_level,lunout
    11981197
    11991198  IMPLICIT NONE
    1200   INCLUDE 'dimensions.h'
    12011199
    12021200    CHARACTER(LEN=*), INTENT(IN) :: field_name
     
    12051203    REAL,DIMENSION(klon_mpi) :: buffer_omp
    12061204    INTEGER, allocatable, DIMENSION(:) :: index2d
    1207     REAL :: Field2d(iim,jj_nb)
     1205    REAL :: Field2d(nbp_lon,jj_nb)
    12081206
    12091207    INTEGER :: ip
     
    12241222    !IF(.NOT.clef_stations(iff)) THEN
    12251223    IF (.TRUE.) THEN
    1226         ALLOCATE(index2d(iim*jj_nb))
    1227         ALLOCATE(fieldok(iim*jj_nb))
     1224        ALLOCATE(index2d(nbp_lon*jj_nb))
     1225        ALLOCATE(fieldok(nbp_lon*jj_nb))
    12281226
    12291227
     
    12651263                                jj_nb, klon_mpi
    12661264  USE xios, only: xios_send_field
     1265  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    12671266  USE print_control_mod, ONLY: prt_level,lunout
    12681267
    12691268  IMPLICIT NONE
    1270   INCLUDE 'dimensions.h'
    12711269
    12721270    CHARACTER(LEN=*), INTENT(IN) :: field_name
     
    12741272
    12751273    REAL,DIMENSION(klon_mpi,SIZE(field,2)) :: buffer_omp
    1276     REAL :: Field3d(iim,jj_nb,SIZE(field,2))
     1274    REAL :: Field3d(nbp_lon,jj_nb,SIZE(field,2))
    12771275    INTEGER :: ip, n, nlev
    12781276    INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d
     
    12951293    !IF (.NOT.clef_stations(iff)) THEN
    12961294    IF(.TRUE.)THEN
    1297         ALLOCATE(index3d(iim*jj_nb*nlev))
    1298         ALLOCATE(fieldok(iim*jj_nb,nlev))
     1295        ALLOCATE(index3d(nbp_lon*jj_nb*nlev))
     1296        ALLOCATE(fieldok(nbp_lon*jj_nb,nlev))
    12991297        CALL xios_send_field(field_name, Field3d(:,:,1:nlev))
    13001298                       
  • LMDZ5/trunk/libf/phylmd/limit_slab.F90

    r2311 r2344  
    44
    55  USE dimphy
    6   USE mod_grid_phy_lmdz
     6  USE mod_grid_phy_lmdz, ONLY: klon_glo
    77  USE mod_phys_lmdz_para
    88  USE netcdf
     
    1111  IMPLICIT NONE
    1212
    13   INCLUDE "temps.h"
    1413  INCLUDE "clesphys.h"
    15   INCLUDE "dimensions.h"
    1614
    1715! In- and ouput arguments
  • LMDZ5/trunk/libf/phylmd/pbl_surface_mod.F90

    r2311 r2344  
    261261    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send
    262262    USE indice_sol_mod
     263    USE time_phylmdz_mod, ONLY: day_ini,annee_ref,itau_phy
     264    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    263265    USE print_control_mod, ONLY: prt_level,lunout
    264266
     
    271273    INCLUDE "clesphys.h"
    272274    INCLUDE "compbl.h"
    273     INCLUDE "dimensions.h"
    274     INCLUDE "temps.h"
    275275    INCLUDE "flux_arp.h"
    276276!****************************************************************************************
     
    733733
    734734! For debugging with IOIPSL
    735     INTEGER, DIMENSION(iim*(jjm+1))    :: ndexbg
     735    INTEGER, DIMENSION(nbp_lon*nbp_lat)    :: ndexbg
    736736    REAL                               :: zjulian
    737737    REAL, DIMENSION(klon)              :: tabindx
    738     REAL, DIMENSION(iim,jjm+1)         :: zx_lon, zx_lat
    739     REAL, DIMENSION(iim,jjm+1)         :: debugtab
     738    REAL, DIMENSION(nbp_lon,nbp_lat)         :: zx_lon, zx_lat
     739    REAL, DIMENSION(nbp_lon,nbp_lat)         :: debugtab
    740740
    741741
     
    794794          idayref = day_ini
    795795          CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
    796           CALL gr_fi_ecrit(1,klon,iim,jjm+1,rlon,zx_lon)
    797           DO i = 1, iim
     796          CALL gr_fi_ecrit(1,klon,nbp_lon,nbp_lat,rlon,zx_lon)
     797          DO i = 1, nbp_lon
    798798             zx_lon(i,1) = rlon(i+1)
    799              zx_lon(i,jjm+1) = rlon(i+1)
     799             zx_lon(i,nbp_lat) = rlon(i+1)
    800800          ENDDO
    801           CALL gr_fi_ecrit(1,klon,iim,jjm+1,rlat,zx_lat)
    802           CALL histbeg("sous_index", iim,zx_lon(:,1),jjm+1,zx_lat(1,:), &
    803                1,iim,1,jjm+1, &
     801          CALL gr_fi_ecrit(1,klon,nbp_lon,nbp_lat,rlat,zx_lat)
     802          CALL histbeg("sous_index",nbp_lon,zx_lon(:,1),nbp_lat,zx_lat(1,:), &
     803               1,nbp_lon,1,nbp_lat, &
    804804               itau_phy,zjulian,dtime,nhoridbg,nidbg)
    805805          ! no vertical axis
     
    809809          cl_surf(4)='sic'
    810810          DO nsrf=1,nbsrf
    811              CALL histdef(nidbg, cl_surf(nsrf),cl_surf(nsrf), "-",iim, &
    812                   jjm+1,nhoridbg, 1, 1, 1, -99, 32, "inst", dtime,dtime)
     811             CALL histdef(nidbg, cl_surf(nsrf),cl_surf(nsrf), "-",nbp_lon, &
     812                  nbp_lat,nhoridbg, 1, 1, 1, -99, 32, "inst", dtime,dtime)
    813813          END DO
    814814
     
    11441144          ndexbg(:) = 0
    11451145          CALL gath2cpl(tabindx,debugtab,knon,ni)
    1146           CALL histwrite(nidbg,cl_surf(nsrf),itap,debugtab,iim*(jjm+1), ndexbg)
     1146          CALL histwrite(nidbg,cl_surf(nsrf),itap,debugtab,nbp_lon*nbp_lat, ndexbg)
    11471147       ENDIF
    11481148       
  • LMDZ5/trunk/libf/phylmd/phyaqua_mod.F90

    r2243 r2344  
    2525    USE fonte_neige_mod, ONLY: fonte_neige_init
    2626    USE phys_state_var_mod
    27     USE control_mod, ONLY: dayref, nday, iphysiq
     27    USE time_phylmdz_mod, ONLY: day_ref, ndays, pdtphys, &
     28                                day_ini,day_end
    2829    USE indice_sol_mod
    29 
     30    USE nrtype, ONLY: pi
    3031    USE ioipsl
    3132    IMPLICIT NONE
    3233
    33     include "dimensions.h"
    34     ! #include "dimphy.h"
    35     ! #include "YOMCST.h"
    36     include "comconst.h"
     34    include "YOMCST.h"
    3735    include "clesphys.h"
    3836    include "dimsoil.h"
    39     include "temps.h"
    4037
    4138    INTEGER, INTENT (IN) :: nlon, iflag_phys
     
    161158    ! -----------------------------------------------------------------------
    162159
    163     day_ini = dayref
    164     day_end = day_ini + nday
     160    day_ini = day_ref
     161    day_end = day_ini + ndays
    165162    airefi = 1.
    166163    zcufi = 1.
     
    276273    ! Ecriture etat initial physique
    277274
    278     timestep = dtvr*float(iphysiq)
    279     radpas = nint(daysec/timestep/float(nbapp_rad))
     275    timestep = pdtphys
     276    radpas = nint(rday/timestep/float(nbapp_rad))
    280277
    281278    DO i = 1, longcles
  • LMDZ5/trunk/libf/phylmd/phyetat0.F90

    r2333 r2344  
    2626  USE indice_sol_mod, only: nbsrf, is_ter, epsfra, is_lic, is_oce, is_sic
    2727  USE ocean_slab_mod, ONLY: tslab, seaice, tice, ocean_slab_init
     28  USE time_phylmdz_mod, ONLY: init_iteration, pdtphys, itau_phy
    2829
    2930  IMPLICIT none
     
    3233  ! Objet: Lecture de l'etat initial pour la physique
    3334  !======================================================================
    34   include "dimensions.h"
    3535  include "netcdf.inc"
    3636  include "dimsoil.h"
    3737  include "clesphys.h"
    38   include "temps.h"
    3938  include "thermcell.h"
    4039  include "compbl.h"
     
    7574  ! FH1D
    7675  !     real iolat(jjm+1)
    77   real iolat(jjm+1-1/(iim*jjm))
     76  !real iolat(jjm+1-1/(iim*jjm))
    7877
    7978  ! Ouvrir le fichier contenant l'etat initial:
     
    10099  ENDDO
    101100
    102   tab_cntrl(1)=dtime
     101  tab_cntrl(1)=pdtphys
    103102  tab_cntrl(2)=radpas
    104103
     
    134133  clesphy0(7)=tab_cntrl( 11 )
    135134  clesphy0(8)=tab_cntrl( 12 )
     135
     136  ! set time iteration
     137   CALL init_iteration(itau_phy)
    136138
    137139  ! Lecture des latitudes (coordonnees):
  • LMDZ5/trunk/libf/phylmd/phyredem.F90

    r2333 r2344  
    2020  USE surface_data
    2121  USE ocean_slab_mod, ONLY : tslab, seaice, tice, fsic
     22  USE time_phylmdz_mod, ONLY: annee_ref, day_end, itau_phy, pdtphys
    2223
    2324  IMPLICIT none
     
    2526  include "dimsoil.h"
    2627  include "clesphys.h"
    27   include "temps.h"
    2828  include "thermcell.h"
    2929  include "compbl.h"
     
    6767     tab_cntrl(ierr) = 0.0
    6868  ENDDO
    69   tab_cntrl(1) = dtime
     69  tab_cntrl(1) = pdtphys
    7070  tab_cntrl(2) = radpas
    7171  ! co2_ppm : current value of atmospheric CO2
  • LMDZ5/trunk/libf/phylmd/phys_cal_mod.F90

    r2098 r2344  
    11! $Id:$
    22MODULE phys_cal_mod
    3 ! This module contains information on the calendar at the actual time step
     3! This module contains information on the calendar at the current time step
    44
    5   SAVE
    6 
    7   INTEGER :: year_cur      ! current year
    8   INTEGER :: mth_cur       ! current month
    9   INTEGER :: day_cur       ! current day
    10   INTEGER :: days_elapsed  ! number of whole days since start of the simulation
    11   INTEGER :: mth_len       ! number of days in the current month
    12   INTEGER year_len ! number of days in the current year
    13   REAL    :: hour
    14   REAL    :: jD_1jan
    15   REAL    :: jH_1jan
    16   REAL    :: xjour
     5  INTEGER,SAVE :: year_cur      ! current year
     6!$OMP THREADPRIVATE(year_cur)
     7  INTEGER,SAVE :: mth_cur       ! current month
     8!$OMP THREADPRIVATE(mth_cur)
     9  INTEGER,SAVE :: day_cur       ! current day
     10!$OMP THREADPRIVATE(day_cur)
     11  INTEGER,SAVE :: days_elapsed  ! number of whole days since start of the simulation
     12!$OMP THREADPRIVATE(days_elapsed)
     13  INTEGER,SAVE :: mth_len       ! number of days in the current month
     14!$OMP THREADPRIVATE(mth_len)
     15  INTEGER,SAVE :: year_len      ! number of days in the current year
     16!$OMP THREADPRIVATE(year_len)
     17  REAL,SAVE    :: hour
     18!$OMP THREADPRIVATE(hour)
     19  REAL,SAVE    :: jD_1jan
     20!$OMP THREADPRIVATE(jD_1jan)
     21  REAL,SAVE    :: jH_1jan
     22!$OMP THREADPRIVATE(jH_1jan)
     23  REAL,SAVE    :: xjour
     24!$OMP THREADPRIVATE(xjour)
     25  REAL,SAVE    :: jD_cur  ! jour courant a l'appel de la physique (jour julien)
     26!$OMP THREADPRIVATE(jD_cur)
     27  REAL,SAVE    :: jH_cur  ! heure courante a l'appel de la physique (jour julien)
     28!$OMP THREADPRIVATE(jH_cur)
     29  REAL,SAVE    :: jD_ref  ! jour du demarage de la simulation (jour julien)
     30!$OMP THREADPRIVATE(jD_ref)
    1731
    1832
    1933CONTAINS
    2034 
     35  SUBROUTINE phys_cal_init(annee_ref,day_ref)
     36  USE IOIPSL, ONLY:  ymds2ju
     37  IMPLICIT NONE
     38    INTEGER,INTENT(IN) :: annee_ref
     39    INTEGER,INTENT(IN) :: day_ref
     40
     41    CALL ymds2ju(annee_ref, 1, day_ref, 0., jD_ref)
     42    jD_ref=INT(jD_ref)
     43 
     44  END SUBROUTINE  phys_cal_init
     45
    2146  SUBROUTINE phys_cal_update(jD_cur, jH_cur)
    2247    ! This subroutine updates the module saved variables.
  • LMDZ5/trunk/libf/phylmd/phys_output_mod.F90

    r2327 r2344  
    4444    USE surface_data, ONLY : ok_snow
    4545    USE phys_output_ctrlout_mod
    46     USE mod_grid_phy_lmdz, only: klon_glo
     46    USE mod_grid_phy_lmdz, only: klon_glo,nbp_lon,nbp_lat
    4747    USE print_control_mod, ONLY: prt_level,lunout
    4848    USE vertical_layers_mod, ONLY: ap,bp,preff,presnivs
    49 
     49    USE time_phylmdz_mod, ONLY: day_ini, itau_phy, start_time, annee_ref, day_ref
    5050#ifdef CPP_XIOS
    5151    ! ug Pour les sorties XIOS
     
    5454
    5555    IMPLICIT NONE
    56     include "dimensions.h"
    57     include "temps.h"
    5856    include "clesphys.h"
    5957    include "thermcell.h"
     
    6967    REAL, DIMENSION(klon, klev+1), INTENT(IN)   :: paprs
    7068    REAL, DIMENSION(klon,klev,nqtot), INTENT(IN):: qx, d_qx
    71     REAL, DIMENSION(klon, llm), INTENT(IN)      :: zmasse
     69    REAL, DIMENSION(klon, klev), INTENT(IN)      :: zmasse
    7270
    7371
     
    106104    CHARACTER(LEN=2)                      :: bb3
    107105    CHARACTER(LEN=6)                      :: type_ocean
    108     INTEGER, DIMENSION(iim*jjmp1)         ::  ndex2d
    109     INTEGER, DIMENSION(iim*jjmp1*klev)    :: ndex3d
     106    INTEGER, DIMENSION(nbp_lon*jjmp1)         ::  ndex2d
     107    INTEGER, DIMENSION(nbp_lon*jjmp1*klev)    :: ndex3d
    110108    INTEGER                               :: imin_ins, imax_ins
    111109    INTEGER                               :: jmin_ins, jmax_ins
     
    343341          IF (phys_out_regfkey(iff)) then
    344342             imin_ins=1
    345              imax_ins=iim
     343             imax_ins=nbp_lon
    346344             jmin_ins=1
    347345             jmax_ins=jjmp1
    348346
    349347             ! correction abderr       
    350              do i=1,iim
     348             do i=1,nbp_lon
    351349                WRITE(lunout,*)'io_lon(i)=',io_lon(i)
    352350                IF (io_lon(i).le.phys_out_lonmin(iff)) imin_ins=i
     
    367365                  io_lat(jmax_ins),io_lat(jmin_ins)
    368366
    369              CALL histbeg(phys_out_filenames(iff),iim,io_lon,jjmp1,io_lat, &
     367             CALL histbeg(phys_out_filenames(iff),nbp_lon,io_lon,jjmp1,io_lat, &
    370368                  imin_ins,imax_ins-imin_ins+1, &
    371369                  jmin_ins,jmax_ins-jmin_ins+1, &
     
    523521    use ioipsl
    524522    USE phys_cal_mod
     523    USE time_phylmdz_mod, ONLY: day_ref, annee_ref
    525524    USE print_control_mod, ONLY: lunout
    526525
     
    532531    real                :: ttt,xxx,timestep,dayseconde,dtime
    533532    parameter (dayseconde=86400.)
    534     include "temps.h"
    535533    include "comconst.h"
    536534
  • LMDZ5/trunk/libf/phylmd/phys_output_write_mod.F90

    r2333 r2344  
    2525
    2626    USE dimphy, only: klon, klev, klevp1, nslay
    27     USE control_mod, only: day_step, iphysiq
     27    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
     28    USE time_phylmdz_mod, only: day_step_phy, start_time, itau_phy
    2829    USE phys_output_ctrlout_mod, only: o_phis, o_aire, is_ter, is_lic, is_oce, &
    2930         is_ave, is_sic, o_contfracATM, o_contfracOR, &
     
    268269
    269270
    270     INCLUDE "temps.h"
    271271    INCLUDE "clesphys.h"
    272272    INCLUDE "thermcell.h"
    273273    INCLUDE "compbl.h"
    274274    INCLUDE "YOMCST.h"
    275     INCLUDE "dimensions.h"
    276275
    277276    ! Input
     
    288287    REAL, DIMENSION(klon, klev+1) :: paprs
    289288    REAL, DIMENSION(klon,klev,nqtot) :: qx, d_qx
    290     REAL, DIMENSION(klon, llm) :: zmasse
     289    REAL, DIMENSION(klon, klev) :: zmasse
    291290    LOGICAL :: flag_aerosol_strat
    292291    INTEGER :: flag_aerosol
     
    295294
    296295    ! Local
    297     INTEGER, PARAMETER :: jjmp1=jjm+1-1/jjm
    298296    INTEGER :: itau_w
    299297    INTEGER :: i, iinit, iinitend=1, iff, iq, nsrf, k, ll, naero
     
    302300    REAL, DIMENSION (klon,klev+1) :: zx_tmp_fi3d1
    303301    CHARACTER (LEN=4)              :: bb2
    304     INTEGER, DIMENSION(iim*jjmp1)  :: ndex2d
    305     INTEGER, DIMENSION(iim*jjmp1*klev) :: ndex3d
     302    INTEGER, DIMENSION(nbp_lon*nbp_lat)  :: ndex2d
     303    INTEGER, DIMENSION(nbp_lon*nbp_lat*klev) :: ndex3d
    306304    REAL, PARAMETER :: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2
    307305!   REAL, PARAMETER :: missing_val=nf90_fill_real
     
    312310
    313311    ! On calcul le nouveau tau:
    314     itau_w = itau_phy + itap + start_time * day_step / iphysiq
     312    itau_w = itau_phy + itap + start_time * day_step_phy
    315313    ! On le donne à iophy pour que les histwrite y aient accès:
    316314    CALL set_itau_iophy(itau_w)
  • LMDZ5/trunk/libf/phylmd/physiq.F90

    r2343 r2344  
    33
    44SUBROUTINE physiq (nlon,nlev, &
    5      debut,lafin,jD_cur, jH_cur,pdtphys, &
     5     debut,lafin,jD_cur_,jH_cur_,pdtphys_, &
    66     paprs,pplay,pphi,pphis,presnivs, &
    77     u,v,rot,t,qx, &
     
    1414  USE comgeomphy
    1515  USE phys_cal_mod, only: year_len, mth_len, days_elapsed, jh_1jan, year_cur, &
    16        mth_cur, phys_cal_update
     16       mth_cur,jD_cur, jH_cur, jD_ref, phys_cal_update
    1717  USE write_field_phy
    1818  USE dimphy
    1919  USE infotrac_phy, ONLY: nqtot, nbtr, nqo, type_trac
    20   USE mod_grid_phy_lmdz
     20  USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, nbp_lev, klon_glo
    2121  USE mod_phys_lmdz_para
    2222  USE iophy
     
    4848  use radlwsw_m, only: radlwsw
    4949  use phyaqua_mod, only: zenang_an
     50  USE time_phylmdz_mod, only: day_step_phy, annee_ref, day_ref, itau_phy, &
     51                              start_time, pdtphys
    5052  USE control_mod, ONLY: config_inca
    5153#ifdef CPP_XIOS
     
    114116  !! d_ps----output-R-tendance physique de la pression au sol
    115117  !!======================================================================
    116   include "dimensions.h"
    117118  integer jjmp1
    118   parameter (jjmp1=jjm+1-1/jjm)
    119   integer iip1
    120   parameter (iip1=iim+1)
     119!  parameter (jjmp1=jjm+1-1/jjm) ! => (jjmp1=nbp_lat-1/(nbp_lat-1))
     120!  integer iip1
     121!  parameter (iip1=iim+1)
    121122
    122123  include "regdim.h"
    123124  include "dimsoil.h"
    124125  include "clesphys.h"
    125   include "temps.h"
    126126  include "thermcell.h"
    127127  !======================================================================
     
    219219  INTEGER nlon
    220220  INTEGER nlev
    221   REAL, intent(in):: jD_cur, jH_cur
    222 
    223   REAL pdtphys
     221  REAL, intent(in):: jD_cur_, jH_cur_
     222! JD_cur and JH_cur to be used in physics are in phys_cal_mod
     223  REAL,INTENT(IN) :: pdtphys_
     224! NB: pdtphys to be used in physics is in time_phylmdz_mod
    224225  LOGICAL debut, lafin
    225226  REAL paprs(klon,klev+1)
     
    509510  SAVE lmt_pas                ! frequence de mise a jour
    510511  !$OMP THREADPRIVATE(lmt_pas)
    511   real zmasse(klon, llm),exner(klon, llm)
     512  real zmasse(klon, nbp_lev),exner(klon, nbp_lev)
    512513  !     (column-density of mass of air in a cell, in kg m-2)
    513514  real, parameter:: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2
     
    694695  REAL tabcntr0( length       )
    695696  !
    696   INTEGER ndex2d(iim*jjmp1)
     697  INTEGER ndex2d(nbp_lon*nbp_lat)
    697698  !IM
    698699  !
     
    706707  !IM 141004 END
    707708  !IM 190504 BEG
    708   INTEGER ij, imp1jmp1
    709   PARAMETER(imp1jmp1=(iim+1)*jjmp1)
     709  INTEGER ij
     710!  INTEGER imp1jmp1
     711!  PARAMETER(imp1jmp1=(iim+1)*jjmp1)
    710712  !ym A voir plus tard
    711   REAL zx_tmp(imp1jmp1), airedyn(iim+1,jjmp1)
    712   REAL padyn(iim+1,jjmp1,klev+1)
    713   REAL dudyn(iim+1,jjmp1,klev)
    714   REAL rlatdyn(iim+1,jjmp1)
     713  REAL zx_tmp((nbp_lon+1)*nbp_lat)
     714  REAL airedyn(nbp_lon+1,nbp_lat)
     715  REAL padyn(nbp_lon+1,nbp_lat,klev+1)
     716  REAL dudyn(nbp_lon+1,nbp_lat,klev)
     717  REAL rlatdyn(nbp_lon+1,nbp_lat)
    715718  !IM 190504 END
    716719  LOGICAL ok_msk
     
    724727  REAL zx_tmp_fi2d(klon)      ! variable temporaire grille physique
    725728  REAL zx_tmp_fi3d(klon,klev) ! variable temporaire pour champs 3D
    726   REAL zx_tmp_2d(iim,jjmp1)
    727   REAL zx_lon(iim,jjmp1), zx_lat(iim,jjmp1)
     729  REAL zx_tmp_2d(nbp_lon,nbp_lat)
     730  REAL zx_lon(nbp_lon,nbp_lat)
     731  REAL zx_lat(nbp_lon,nbp_lat)
    728732  !
    729733  INTEGER nid_day_seri, nid_ctesGCM
     
    900904!albedo SB <<<
    901905
     906  ! Ehouarn: set value of jjmp1 since it is no longer a "fixed parameter"
     907  jjmp1=nbp_lat
     908
    902909  !======================================================================
    903910  ! Gestion calendrier : mise a jour du module phys_cal_mod
    904911  !
     912  JD_cur=JD_cur_
     913  JH_cur=JH_cur_
     914  pdtphys=pdtphys_
    905915  CALL phys_cal_update(jD_cur,jH_cur)
    906916
     
    9921002
    9931003  torsfc=0.
    994   forall (k=1: llm) zmasse(:, k) = (paprs(:, k)-paprs(:, k+1)) / rg
     1004  forall (k=1: nbp_lev) zmasse(:, k) = (paprs(:, k)-paprs(:, k+1)) / rg
    9951005
    9961006
     
    18321842
    18331843  if (mydebug) then
    1834      call writefield_phy('u_seri',u_seri,llm)
    1835      call writefield_phy('v_seri',v_seri,llm)
    1836      call writefield_phy('t_seri',t_seri,llm)
    1837      call writefield_phy('q_seri',q_seri,llm)
     1844     call writefield_phy('u_seri',u_seri,nbp_lev)
     1845     call writefield_phy('v_seri',v_seri,nbp_lev)
     1846     call writefield_phy('t_seri',t_seri,nbp_lev)
     1847     call writefield_phy('q_seri',q_seri,nbp_lev)
    18381848  endif
    18391849
     
    19781988
    19791989     if (mydebug) then
    1980         call writefield_phy('u_seri',u_seri,llm)
    1981         call writefield_phy('v_seri',v_seri,llm)
    1982         call writefield_phy('t_seri',t_seri,llm)
    1983         call writefield_phy('q_seri',q_seri,llm)
     1990        call writefield_phy('u_seri',u_seri,nbp_lev)
     1991        call writefield_phy('v_seri',v_seri,nbp_lev)
     1992        call writefield_phy('t_seri',t_seri,nbp_lev)
     1993        call writefield_phy('q_seri',q_seri,nbp_lev)
    19841994     endif
    19851995
     
    24692479
    24702480  if (mydebug) then
    2471      call writefield_phy('u_seri',u_seri,llm)
    2472      call writefield_phy('v_seri',v_seri,llm)
    2473      call writefield_phy('t_seri',t_seri,llm)
    2474      call writefield_phy('q_seri',q_seri,llm)
     2481     call writefield_phy('u_seri',u_seri,nbp_lev)
     2482     call writefield_phy('v_seri',v_seri,nbp_lev)
     2483     call writefield_phy('t_seri',t_seri,nbp_lev)
     2484     call writefield_phy('q_seri',q_seri,nbp_lev)
    24752485  endif
    24762486
     
    30393049
    30403050  if (mydebug) then
    3041      call writefield_phy('u_seri',u_seri,llm)
    3042      call writefield_phy('v_seri',v_seri,llm)
    3043      call writefield_phy('t_seri',t_seri,llm)
    3044      call writefield_phy('q_seri',q_seri,llm)
     3051     call writefield_phy('u_seri',u_seri,nbp_lev)
     3052     call writefield_phy('v_seri',v_seri,nbp_lev)
     3053     call writefield_phy('t_seri',t_seri,nbp_lev)
     3054     call writefield_phy('q_seri',q_seri,nbp_lev)
    30453055  endif
    30463056
     
    33973407          ibas_con, &
    33983408          cldfra, &
    3399           iim, &
    3400           jjm, &
     3409          nbp_lon, &
     3410          nbp_lat-1, &
    34013411          tr_seri, &
    34023412          ftsol, &
     
    35253535
    35263536     if (mydebug) then
    3527         call writefield_phy('u_seri',u_seri,llm)
    3528         call writefield_phy('v_seri',v_seri,llm)
    3529         call writefield_phy('t_seri',t_seri,llm)
    3530         call writefield_phy('q_seri',q_seri,llm)
     3537        call writefield_phy('u_seri',u_seri,nbp_lev)
     3538        call writefield_phy('v_seri',v_seri,nbp_lev)
     3539        call writefield_phy('t_seri',t_seri,nbp_lev)
     3540        call writefield_phy('q_seri',q_seri,nbp_lev)
    35313541     endif
    35323542
     
    37163726  !
    37173727  if (mydebug) then
    3718      call writefield_phy('u_seri',u_seri,llm)
    3719      call writefield_phy('v_seri',v_seri,llm)
    3720      call writefield_phy('t_seri',t_seri,llm)
    3721      call writefield_phy('q_seri',q_seri,llm)
     3728     call writefield_phy('u_seri',u_seri,nbp_lev)
     3729     call writefield_phy('v_seri',v_seri,nbp_lev)
     3730     call writefield_phy('t_seri',t_seri,nbp_lev)
     3731     call writefield_phy('q_seri',q_seri,nbp_lev)
    37223732  endif
    37233733
     
    38013811  !
    38023812  if (mydebug) then
    3803      call writefield_phy('u_seri',u_seri,llm)
    3804      call writefield_phy('v_seri',v_seri,llm)
    3805      call writefield_phy('t_seri',t_seri,llm)
    3806      call writefield_phy('q_seri',q_seri,llm)
     3813     call writefield_phy('u_seri',u_seri,nbp_lev)
     3814     call writefield_phy('v_seri',v_seri,nbp_lev)
     3815     call writefield_phy('t_seri',t_seri,nbp_lev)
     3816     call writefield_phy('q_seri',q_seri,nbp_lev)
    38073817  endif
    38083818
     
    39093919
    39103920  if (mydebug) then
    3911      call writefield_phy('u_seri',u_seri,llm)
    3912      call writefield_phy('v_seri',v_seri,llm)
    3913      call writefield_phy('t_seri',t_seri,llm)
    3914      call writefield_phy('q_seri',q_seri,llm)
     3921     call writefield_phy('u_seri',u_seri,nbp_lev)
     3922     call writefield_phy('v_seri',v_seri,nbp_lev)
     3923     call writefield_phy('t_seri',t_seri,nbp_lev)
     3924     call writefield_phy('q_seri',q_seri,nbp_lev)
    39153925  endif
    39163926
     
    40824092
    40834093  d_t_ec(:,:)=0.
    4084   forall (k=1: llm) exner(:, k) = (pplay(:, k)/paprs(:,1))**RKAPPA
     4094  forall (k=1: nbp_lev) exner(:, k) = (pplay(:, k)/paprs(:,1))**RKAPPA
    40854095  CALL ener_conserv(klon,klev,pdtphys,u,v,t,qx(:,:,ivap), &
    40864096       u_seri,v_seri,t_seri,q_seri,pbl_tke(:,:,is_ave)-tke0(:,:), &
     
    41784188  !
    41794189  if (mydebug) then
    4180      call writefield_phy('u_seri',u_seri,llm)
    4181      call writefield_phy('v_seri',v_seri,llm)
    4182      call writefield_phy('t_seri',t_seri,llm)
    4183      call writefield_phy('q_seri',q_seri,llm)
     4190     call writefield_phy('u_seri',u_seri,nbp_lev)
     4191     call writefield_phy('v_seri',v_seri,nbp_lev)
     4192     call writefield_phy('t_seri',t_seri,nbp_lev)
     4193     call writefield_phy('q_seri',q_seri,nbp_lev)
    41844194  endif
    41854195
  • LMDZ5/trunk/libf/phylmd/phytrac_mod.F90

    r2320 r2344  
    106106
    107107    INCLUDE "YOMCST.h"
    108     INCLUDE "dimensions.h"
    109108    INCLUDE "clesphys.h"
    110     INCLUDE "temps.h"
    111     INCLUDE "paramet.h"
    112109    INCLUDE "thermcell.h"
    113110    !==========================================================================
  • LMDZ5/trunk/libf/phylmd/readaerosol_interp.F90

    r2315 r2344  
    2727  INCLUDE "YOMCST.h"
    2828  INCLUDE "chem.h"     
    29   INCLUDE "temps.h"     
    3029  INCLUDE "clesphys.h"
    31   INCLUDE "dimensions.h"
     30
    3231!
    3332! Input:
  • LMDZ5/trunk/libf/phylmd/surf_land_orchidee_mod.F90

    r2311 r2344  
    4646    USE indice_sol_mod
    4747    USE print_control_mod, ONLY: lunout
     48    USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat
    4849!   
    4950! Cette routine sert d'interface entre le modele atmospherique et le
     
    9899!   qsurf        air moisture at surface
    99100!
    100     INCLUDE "temps.h"
    101101    INCLUDE "YOMCST.h"
    102     INCLUDE "dimensions.h"
    103102 
    104103!
     
    229228       DO igrid = 2, klon - 1
    230229          indi = indi + 1
    231           IF ( indi > iim) THEN
     230          IF ( indi > nbp_lon) THEN
    232231             indi = 1
    233232             indj = indj + 1
     
    237236       ENDDO
    238237       ig(klon) = 1
    239        jg(klon) = jjm + 1
     238       jg(klon) = nbp_lat
    240239
    241240       IF ((.NOT. ALLOCATED(lalo))) THEN
     
    247246       ENDIF
    248247       IF ((.NOT. ALLOCATED(lon_scat))) THEN
    249           ALLOCATE(lon_scat(iim,jjm+1), stat = error)
     248          ALLOCATE(lon_scat(nbp_lon,nbp_lat), stat = error)
    250249          IF (error /= 0) THEN
    251250             abort_message='Pb allocation lon_scat'
     
    254253       ENDIF
    255254       IF ((.NOT. ALLOCATED(lat_scat))) THEN
    256           ALLOCATE(lat_scat(iim,jjm+1), stat = error)
     255          ALLOCATE(lat_scat(nbp_lon,nbp_lat), stat = error)
    257256          IF (error /= 0) THEN
    258257             abort_message='Pb allocation lat_scat'
     
    275274       IF (is_mpi_root) THEN
    276275          index = 1
    277           DO jj = 2, jjm
    278              DO ij = 1, iim
     276          DO jj = 2, nbp_lat-1
     277             DO ij = 1, nbp_lon
    279278                index = index + 1
    280279                lon_scat(ij,jj) = rlon_g(index)
     
    284283          lon_scat(:,1) = lon_scat(:,2)
    285284          lat_scat(:,1) = rlat_g(1)
    286           lon_scat(:,jjm+1) = lon_scat(:,2)
    287           lat_scat(:,jjm+1) = rlat_g(klon_glo)
     285          lon_scat(:,nbp_lat) = lon_scat(:,2)
     286          lat_scat(:,nbp_lat) = rlat_g(klon_glo)
    288287       ENDIF
    289288   
     
    395394
    396395#ifdef CPP_VEGET
    397           CALL intersurf_main (itime+itau_phy-1, iim, jjm+1, knon, ktindex, dtime, &
     396          CALL intersurf_main (itime+itau_phy-1, nbp_lon, nbp_lat, knon, ktindex, dtime, &
    398397               lrestart_read, lrestart_write, lalo, &
    399398               contfrac, neighbours, resolution, date0, &
     
    419418    IF (knon > 0) THEN
    420419#ifdef CPP_VEGET   
    421        CALL intersurf_main (itime+itau_phy, iim, jjm+1, knon, ktindex, dtime,  &
     420       CALL intersurf_main (itime+itau_phy, nbp_lon, nbp_lat, knon, ktindex, dtime,  &
    422421            lrestart_read, lrestart_write, lalo, &
    423422            contfrac, neighbours, resolution, date0, &
  • LMDZ5/trunk/libf/phylmd/surf_land_orchidee_noopenmp_mod.F90

    r2311 r2344  
    9898    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, fco2_land_inst, fco2_lu_inst
    9999    USE indice_sol_mod
     100    USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat
    100101    IMPLICIT NONE
    101102
    102     INCLUDE "temps.h"
    103103    INCLUDE "YOMCST.h"
    104     INCLUDE "dimensions.h"
    105104 
    106105!
     
    231230       DO igrid = 2, klon - 1
    232231          indi = indi + 1
    233           IF ( indi > iim) THEN
     232          IF ( indi > nbp_lon) THEN
    234233             indi = 1
    235234             indj = indj + 1
     
    239238       ENDDO
    240239       ig(klon) = 1
    241        jg(klon) = jjm + 1
     240       jg(klon) = nbp_lat
    242241
    243242       IF ((.NOT. ALLOCATED(lalo))) THEN
     
    249248       ENDIF
    250249       IF ((.NOT. ALLOCATED(lon_scat))) THEN
    251           ALLOCATE(lon_scat(iim,jjm+1), stat = error)
     250          ALLOCATE(lon_scat(nbp_lon,nbp_lat), stat = error)
    252251          IF (error /= 0) THEN
    253252             abort_message='Pb allocation lon_scat'
     
    256255       ENDIF
    257256       IF ((.NOT. ALLOCATED(lat_scat))) THEN
    258           ALLOCATE(lat_scat(iim,jjm+1), stat = error)
     257          ALLOCATE(lat_scat(nbp_lon,nbp_lat), stat = error)
    259258          IF (error /= 0) THEN
    260259             abort_message='Pb allocation lat_scat'
     
    277276       IF (is_mpi_root) THEN
    278277          index = 1
    279           DO jj = 2, jjm
    280              DO ij = 1, iim
     278          DO jj = 2, nbp_lat-1
     279             DO ij = 1, nbp_lon
    281280                index = index + 1
    282281                lon_scat(ij,jj) = rlon_g(index)
     
    286285          lon_scat(:,1) = lon_scat(:,2)
    287286          lat_scat(:,1) = rlat_g(1)
    288           lon_scat(:,jjm+1) = lon_scat(:,2)
    289           lat_scat(:,jjm+1) = rlat_g(klon_glo)
     287          lon_scat(:,nbp_lat) = lon_scat(:,2)
     288          lat_scat(:,nbp_lat) = rlat_g(klon_glo)
    290289       ENDIF
    291290
     
    398397!  if (pole_nord) then
    399398!    offset=0
    400 !    ktindex(:)=ktindex(:)+iim-1
     399!    ktindex(:)=ktindex(:)+nbp_lon-1
    401400!  else
    402 !    offset = klon_mpi_begin-1+iim-1
    403 !    ktindex(:)=ktindex(:)+MOD(offset,iim)
    404 !    offset=offset-MOD(offset,iim)
     401!    offset = klon_mpi_begin-1+nbp_lon-1
     402!    ktindex(:)=ktindex(:)+MOD(offset,nbp_lon)
     403!    offset=offset-MOD(offset,nbp_lon)
    405404!  endif
    406405 
     
    412411#ifndef CPP_MPI
    413412          ! Interface for ORCHIDEE compiled in sequential mode(without preprocessing flag CPP_MPI)
    414           CALL intersurf_main (itime+itau_phy-1, iim, jjm+1, knon, ktindex, dtime, &
     413          CALL intersurf_main (itime+itau_phy-1, nbp_lon, nbp_lat, knon, ktindex, dtime, &
    415414               lrestart_read, lrestart_write, lalo, &
    416415               contfrac, neighbours, resolution, date0, &
     
    429428#else         
    430429          ! Interface for ORCHIDEE version 1.9 or later(1.9.2, 1.9.3, 1.9.4, 1.9.5) compiled in parallel mode(with preprocessing flag CPP_MPI)
    431           CALL intersurf_main (itime+itau_phy-1, iim, jjm+1, offset, knon, ktindex, &
     430          CALL intersurf_main (itime+itau_phy-1, nbp_lon, nbp_lat, offset, knon, ktindex, &
    432431               orch_comm, dtime, lrestart_read, lrestart_write, lalo, &
    433432               contfrac, neighbours, resolution, date0, &
     
    457456#ifndef CPP_MPI
    458457       ! Interface for ORCHIDEE compiled in sequential mode(without preprocessing flag CPP_MPI)
    459        CALL intersurf_main (itime+itau_phy, iim, jjm+1, knon, ktindex, dtime, &
     458       CALL intersurf_main (itime+itau_phy, nbp_lon, nbp_lat, knon, ktindex, dtime, &
    460459            lrestart_read, lrestart_write, lalo, &
    461460            contfrac, neighbours, resolution, date0, &
     
    473472#else
    474473       ! Interface for ORCHIDEE version 1.9 or later compiled in parallel mode(with preprocessing flag CPP_MPI)
    475        CALL intersurf_main (itime+itau_phy, iim, jjm+1,offset, knon, ktindex, &
     474       CALL intersurf_main (itime+itau_phy, nbp_lon, nbp_lat,offset, knon, ktindex, &
    476475            orch_comm,dtime, lrestart_read, lrestart_write, lalo, &
    477476            contfrac, neighbours, resolution, date0, &
     
    529528  SUBROUTINE Init_orchidee_index(knon,orch_comm,knindex,offset,ktindex)
    530529   
    531     INCLUDE "dimensions.h"
     530    USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat
    532531
    533532#ifdef CPP_MPI
     
    562561!****************************************************************************************
    563562
    564     MyLastPoint=klon_mpi_begin-1+knindex(knon)+iim-1
     563    MyLastPoint=klon_mpi_begin-1+knindex(knon)+nbp_lon-1
    565564   
    566565    IF (is_parallel) THEN
     
    591590       offset=0
    592591    ELSE
    593        offset=LastPoint-MOD(LastPoint,iim)
    594     ENDIF
    595    
    596     ktindex(1:knon)=knindex(1:knon)+(klon_mpi_begin+iim-1)-offset-1     
     592       offset=LastPoint-MOD(LastPoint,nbp_lon)
     593    ENDIF
     594   
     595    ktindex(1:knon)=knindex(1:knon)+(klon_mpi_begin+nbp_lon-1)-offset-1
    597596   
    598597
     
    634633   
    635634    USE indice_sol_mod
    636 
    637     INCLUDE "dimensions.h"
     635    USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat
     636
    638637#ifdef CPP_MPI
    639638    INCLUDE 'mpif.h'
     
    661660    INTEGER, DIMENSION(8)                :: offset 
    662661    INTEGER, DIMENSION(knon)             :: ktindex_p
    663     INTEGER, DIMENSION(iim,jjm+1)        :: correspond
     662    INTEGER, DIMENSION(nbp_lon,nbp_lat)        :: correspond
    664663    INTEGER, ALLOCATABLE, DIMENSION(:)   :: ktindex_g
    665664    INTEGER, ALLOCATABLE, DIMENSION(:,:) :: neighbours_g
     
    694693   ENDIF
    695694   
    696     ktindex_p(1:knon)=ktindex(1:knon)+klon_mpi_begin-1+iim-1
     695    ktindex_p(1:knon)=ktindex(1:knon)+klon_mpi_begin-1+nbp_lon-1
    697696   
    698697    IF (is_sequential) THEN
     
    713712!
    714713! offset bord ouest
    715        off_ini(1,1) = - iim  ; off_ini(2,1) = - iim + 1; off_ini(3,1) = 1
    716        off_ini(4,1) = iim + 1; off_ini(5,1) = iim      ; off_ini(6,1) = 2 * iim - 1
    717        off_ini(7,1) = iim -1 ; off_ini(8,1) = - 1
     714       off_ini(1,1) = - nbp_lon  ; off_ini(2,1) = - nbp_lon + 1; off_ini(3,1) = 1
     715       off_ini(4,1) = nbp_lon + 1; off_ini(5,1) = nbp_lon      ; off_ini(6,1) = 2 * nbp_lon - 1
     716       off_ini(7,1) = nbp_lon -1 ; off_ini(8,1) = - 1
    718717! offset point normal
    719        off_ini(1,2) = - iim  ; off_ini(2,2) = - iim + 1; off_ini(3,2) = 1
    720        off_ini(4,2) = iim + 1; off_ini(5,2) = iim      ; off_ini(6,2) = iim - 1
    721        off_ini(7,2) = -1     ; off_ini(8,2) = - iim - 1
     718       off_ini(1,2) = - nbp_lon  ; off_ini(2,2) = - nbp_lon + 1; off_ini(3,2) = 1
     719       off_ini(4,2) = nbp_lon + 1; off_ini(5,2) = nbp_lon      ; off_ini(6,2) = nbp_lon - 1
     720       off_ini(7,2) = -1     ; off_ini(8,2) = - nbp_lon - 1
    722721! offset bord   est
    723        off_ini(1,3) = - iim; off_ini(2,3) = - 2 * iim + 1; off_ini(3,3) = - iim + 1
    724        off_ini(4,3) =  1   ; off_ini(5,3) = iim          ; off_ini(6,3) = iim - 1
    725        off_ini(7,3) = -1   ; off_ini(8,3) = - iim - 1
     722       off_ini(1,3) = - nbp_lon; off_ini(2,3) = - 2 * nbp_lon + 1; off_ini(3,3) = - nbp_lon + 1
     723       off_ini(4,3) =  1   ; off_ini(5,3) = nbp_lon          ; off_ini(6,3) = nbp_lon - 1
     724       off_ini(7,3) = -1   ; off_ini(8,3) = - nbp_lon - 1
    726725!
    727726!
     
    730729       DO igrid = 1, knon_g
    731730          index = ktindex_g(igrid)
    732           jj = INT((index - 1)/iim) + 1
    733           ij = index - (jj - 1) * iim
     731          jj = INT((index - 1)/nbp_lon) + 1
     732          ij = index - (jj - 1) * nbp_lon
    734733          correspond(ij,jj) = igrid
    735734       ENDDO
     
    737736       DO igrid = 1, knon_g
    738737          iglob = ktindex_g(igrid)
    739           IF (MOD(iglob, iim) == 1) THEN
     738          IF (MOD(iglob, nbp_lon) == 1) THEN
    740739             offset = off_ini(:,1)
    741           ELSE IF(MOD(iglob, iim) == 0) THEN
     740          ELSE IF(MOD(iglob, nbp_lon) == 0) THEN
    742741             offset = off_ini(:,3)
    743742          ELSE
     
    746745          DO i = 1, 8
    747746             index = iglob + offset(i)
    748              ireal = (MIN(MAX(1, index - iim + 1), klon_glo))
     747             ireal = (MIN(MAX(1, index - nbp_lon + 1), klon_glo))
    749748             IF (pctsrf_g(ireal) > EPSFRA) THEN
    750                 jj = INT((index - 1)/iim) + 1
    751                 ij = index - (jj - 1) * iim
     749                jj = INT((index - 1)/nbp_lon) + 1
     750                ij = index - (jj - 1) * nbp_lon
    752751                neighbours_g(igrid, i) = correspond(ij, jj)
    753752             ENDIF
  • LMDZ5/trunk/libf/phylmd/time_phylmdz_mod.F90

    r2343 r2344  
    2626    INTEGER,SAVE :: itau_phy     ! number of physiq iteration from origin
    2727!$OMP THREADPRIVATE(itau_phy)
    28     INTEGER,SAVE :: itaufin      ! final iteration
    29 !$OMP THREADPRIVATE(itaufin)
     28    INTEGER,SAVE :: itaufin_phy      ! final iteration (in itau_phy steps)
     29!$OMP THREADPRIVATE(itaufin_phy)
    3030    REAL,SAVE    :: current_time ! current elapsed time (s) from the begining of the run
    3131!$OMP THREADPRIVATE(current_time)
     
    3737                       ndays_, pdtphys_)
    3838  USE ioipsl_getin_p_mod, ONLY : getin_p
     39  USE phys_cal_mod, ONLY: phys_cal_init
    3940  IMPLICIT NONE
    4041  INCLUDE 'YOMCST.h'
     
    6263    current_time=0
    6364   
    64 !    CALL phys_cal_init(annee_ref,day_ref)
     65    CALL phys_cal_init(annee_ref,day_ref)
    6566   
    6667  END SUBROUTINE init_time
    6768
     69  SUBROUTINE init_iteration(itau_phy_)
     70  IMPLICIT NONE
     71    INTEGER, INTENT(IN) :: itau_phy_
     72    itau_phy=itau_phy_
     73    IF (raz_date==1) itau_phy=0
     74   
     75    itaufin_phy=itau_phy+NINT(ndays/pdtphys)
     76   
     77  END SUBROUTINE init_iteration
     78
    6879END MODULE time_phylmdz_mod     
    6980
  • LMDZ5/trunk/libf/phylmd/write_histday_seri.h

    r2343 r2344  
    2424      zx_tmp_fi2d(1:klon)=moyglo
    2525!
    26       CALL gr_fi_ecrit(1, klon,iim,jjmp1, zx_tmp_fi2d,zx_tmp_2d)
     26      CALL gr_fi_ecrit(1, klon,nbp_lon,nbp_lat, zx_tmp_fi2d,zx_tmp_2d)
    2727      CALL histwrite(nid_day_seri,"bilTOA",itau_w, &
    28                      zx_tmp_2d,iim*jjmp1,ndex2d)
     28                     zx_tmp_2d,nbp_lon*nbp_lat,ndex2d)
    2929!
    3030      ok_msk=.FALSE.
     
    3333      zx_tmp_fi2d(1:klon)=moyglo
    3434!
    35       CALL gr_fi_ecrit(1, klon,iim,jjmp1, zx_tmp_fi2d,zx_tmp_2d)
     35      CALL gr_fi_ecrit(1, klon,nbp_lon,nbp_lat, zx_tmp_fi2d,zx_tmp_2d)
    3636      CALL histwrite(nid_day_seri,"bils",itau_w, &
    37                      zx_tmp_2d,iim*jjmp1,ndex2d)
     37                     zx_tmp_2d,nbp_lon*nbp_lat,ndex2d)
    3838!
    3939      DO k=1, klev
     
    4848      zx_tmp_fi2d(1:klon)=moyglo
    4949!
    50       CALL gr_fi_ecrit(1, klon,iim,jjmp1, zx_tmp_fi2d,zx_tmp_2d)
     50      CALL gr_fi_ecrit(1, klon,nbp_lon,nbp_lat, zx_tmp_fi2d,zx_tmp_2d)
    5151      CALL histwrite(nid_day_seri,"ecin",itau_w, &
    52                      zx_tmp_2d,iim*jjmp1,ndex2d)
     52                     zx_tmp_2d,nbp_lon*nbp_lat,ndex2d)
    5353!
    5454!IM 151004 BEG
     
    6565      zx_tmp_fi2d(1:klon)=moyglo
    6666!
    67       CALL gr_fi_ecrit(1, klon,iim,jjmp1, zx_tmp_fi2d,zx_tmp_2d)
     67      CALL gr_fi_ecrit(1, klon,nbp_lon,nbp_lat, zx_tmp_fi2d,zx_tmp_2d)
    6868      CALL histwrite(nid_day_seri,"momang",itau_w,zx_tmp_2d, &
    69                      iim*jjmp1,ndex2d)
     69                     nbp_lon*nbp_lat,ndex2d)
    7070!
    7171! friction torque
     
    8080      zx_tmp_fi2d(1:klon)=moyglo
    8181!
    82       CALL gr_fi_ecrit(1, klon,iim,jjmp1, zx_tmp_fi2d,zx_tmp_2d)
     82      CALL gr_fi_ecrit(1, klon,nbp_lon,nbp_lat, zx_tmp_fi2d,zx_tmp_2d)
    8383      CALL histwrite(nid_day_seri,"frictor",itau_w,zx_tmp_2d, &
    84                      iim*jjmp1,ndex2d)
     84                     nbp_lon*nbp_lat,ndex2d)
    8585!
    8686! mountain torque
    8787!
    8888!IM 190504 BEG
    89       CALL gr_fi_dyn(1,klon,iim+1,jjm+1,airephy,airedyn)
    90       CALL gr_fi_dyn(klev+1,klon,iim+1,jjm+1,paprs,padyn)
    91       CALL gr_fi_dyn(1,klon,iim+1,jjm+1,rlat,rlatdyn)
     89      CALL gr_fi_dyn(1,klon,nbp_lon+1,nbp_lat,airephy,airedyn)
     90      CALL gr_fi_dyn(klev+1,klon,nbp_lon+1,nbp_lat,paprs,padyn)
     91      CALL gr_fi_dyn(1,klon,nbp_lon+1,nbp_lat,rlat,rlatdyn)
    9292      mountor=0.
    9393      airetot=0.
    94       DO j = 1, jjmp1
    95        DO i = 1, iim+1
    96         ij=i+(iim+1)*(j-1)
     94      DO j = 1, nbp_lat
     95       DO i = 1, nbp_lon+1
     96        ij=i+(nbp_lon+1)*(j-1)
    9797        zx_tmp(ij)=0.
    9898        DO k = 1, klev
     
    113113!
    114114!IM 190504 END
    115       zx_tmp_2d(1:iim,1:jjmp1)=mountor
     115      zx_tmp_2d(1:nbp_lon,1:nbp_lat)=mountor
    116116      CALL histwrite(nid_day_seri,"mountor",itau_w,zx_tmp_2d, &
    117                      iim*jjmp1,ndex2d)
     117                     nbp_lon*nbp_lat,ndex2d)
    118118!
    119119      ENDIF !(1.EQ.0) THEN
    120120!
    121121!
    122       CALL gr_fi_dyn(1,klon,iim+1,jjm+1,airephy,airedyn)
    123       CALL gr_fi_ecrit(1,klon,iim,jjmp1,airephy,zx_tmp_2d)
     122      CALL gr_fi_dyn(1,klon,nbp_lon+1,nbp_lat,airephy,airedyn)
     123      CALL gr_fi_ecrit(1,klon,nbp_lon,nbp_lat,airephy,zx_tmp_2d)
    124124      airetot=0.
    125 !     DO j = 1, jjmp1
    126 !      DO i = 1, iim+1
    127 !       ij=i+(iim+1)*(j-1)
     125!     DO j = 1, nbp_lat
     126!      DO i = 1, nbp_lon+1
     127!       ij=i+(nbp_lon+1)*(j-1)
    128128!       DO k = 1, klev
    129129!        airetot=airetot+airedyn(i,j)
     
    139139!
    140140      airetot=0.
    141       DO j=1, jjmp1
    142        DO i=1, iim
     141      DO j=1, nbp_lat
     142       DO i=1, nbp_lon
    143143        airetot=airetot+zx_tmp_2d(i,j)
    144144       ENDDO
     
    149149!
    150150      zx_tmp_fi2d(1:klon)=aam/airetot
    151       CALL gr_fi_ecrit(1,klon,iim,jjmp1,zx_tmp_fi2d,zx_tmp_2d)
     151      CALL gr_fi_ecrit(1,klon,nbp_lon,nbp_lat,zx_tmp_fi2d,zx_tmp_2d)
    152152      CALL histwrite(nid_day_seri,"momang",itau_w,zx_tmp_2d, &
    153                      iim*jjmp1,ndex2d)
     153                     nbp_lon*nbp_lat,ndex2d)
    154154!
    155155      zx_tmp_fi2d(1:klon)=torsfc/airetot
    156       CALL gr_fi_ecrit(1,klon,iim,jjmp1,zx_tmp_fi2d,zx_tmp_2d)
     156      CALL gr_fi_ecrit(1,klon,nbp_lon,nbp_lat,zx_tmp_fi2d,zx_tmp_2d)
    157157      CALL histwrite(nid_day_seri,"torsfc",itau_w,zx_tmp_2d, &
    158                      iim*jjmp1,ndex2d)
     158                     nbp_lon*nbp_lat,ndex2d)
    159159!
    160160!IM 151004 END
     
    164164      zx_tmp_fi2d(1:klon)=moyglo
    165165!
    166       CALL gr_fi_ecrit(1,klon,iim,jjmp1,zx_tmp_fi2d,zx_tmp_2d)
     166      CALL gr_fi_ecrit(1,klon,nbp_lon,nbp_lat,zx_tmp_fi2d,zx_tmp_2d)
    167167      CALL histwrite(nid_day_seri,"tamv",itau_w, &
    168                      zx_tmp_2d,iim*jjmp1,ndex2d)
     168                     zx_tmp_2d,nbp_lon*nbp_lat,ndex2d)
    169169!
    170170      ok_msk=.FALSE.
     
    173173      zx_tmp_fi2d(1:klon)=moyglo
    174174!
    175       CALL gr_fi_ecrit(1, klon,iim,jjmp1, zx_tmp_fi2d,zx_tmp_2d)
     175      CALL gr_fi_ecrit(1, klon,nbp_lon,nbp_lat, zx_tmp_fi2d,zx_tmp_2d)
    176176      CALL histwrite(nid_day_seri,"psol",itau_w, &
    177                      zx_tmp_2d,iim*jjmp1,ndex2d)
     177                     zx_tmp_2d,nbp_lon*nbp_lat,ndex2d)
    178178!
    179179      ok_msk=.FALSE.
     
    182182      zx_tmp_fi2d(1:klon)=moyglo
    183183!
    184       CALL gr_fi_ecrit(1, klon,iim,jjmp1, zx_tmp_fi2d,zx_tmp_2d)
     184      CALL gr_fi_ecrit(1, klon,nbp_lon,nbp_lat, zx_tmp_fi2d,zx_tmp_2d)
    185185      CALL histwrite(nid_day_seri,"evap",itau_w, &
    186                      zx_tmp_2d,iim*jjmp1,ndex2d)
     186                     zx_tmp_2d,nbp_lon*nbp_lat,ndex2d)
    187187!
    188188!     DO i=1, klon
     
    196196!     zx_tmp_fi2d(1:klon)=moyglo
    197197!
    198 !     CALL gr_fi_ecrit(1, klon,iim,jjmp1,zx_tmp_fi2d,zx_tmp_2d)
     198!     CALL gr_fi_ecrit(1, klon,nbp_lon,nbp_lat,zx_tmp_fi2d,zx_tmp_2d)
    199199!     CALL histwrite(nid_day_seri,"SnowFrac",
    200 !    .               itau_w,zx_tmp_2d,iim*jjmp1,ndex2d)
     200!    .               itau_w,zx_tmp_2d,nbp_lon*nbp_lat,ndex2d)
    201201!
    202202!     DO i=1, klon
     
    212212!     zx_tmp_fi2d(1:klon)=moyglo
    213213!
    214 !     CALL gr_fi_ecrit(1, klon,iim,jjmp1,zx_tmp_fi2d,zx_tmp_2d)
     214!     CALL gr_fi_ecrit(1, klon,nbp_lon,nbp_lat,zx_tmp_fi2d,zx_tmp_2d)
    215215!     CALL histwrite(nid_day_seri,"snow_depth",itau_w,
    216 !    .               zx_tmp_2d,iim*jjmp1,ndex2d)
     216!    .               zx_tmp_2d,nbp_lon*nbp_lat,ndex2d)
    217217!
    218218      DO i=1, klon
     
    226226      zx_tmp_fi2d(1:klon)=moyglo
    227227!
    228       CALL gr_fi_ecrit(1, klon,iim,jjmp1, zx_tmp_fi2d, zx_tmp_2d)
     228      CALL gr_fi_ecrit(1, klon,nbp_lon,nbp_lat, zx_tmp_fi2d, zx_tmp_2d)
    229229      CALL histwrite(nid_day_seri,"tsol_"//clnsurf(is_oce), &
    230                      itau_w,zx_tmp_2d,iim*jjmp1,ndex2d)
     230                     itau_w,zx_tmp_2d,nbp_lon*nbp_lat,ndex2d)
    231231!
    232232!=================================================================
Note: See TracChangeset for help on using the changeset viewer.