Changeset 3819


Ignore:
Timestamp:
Apr 22, 2015, 6:28:50 PM (10 years ago)
Author:
ymipsl
Message:

Removed all iim et jjm depedency. Replaced by nbp_lon and nbp_lat.
Supress gr_fi_ecrit, replaced by grid1dTo2d_glo

YM

Location:
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd
Files:
26 edited

Legend:

Unmodified
Added
Removed
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/cfmip_point_locations.F90

    r3809 r3819  
    3434  USE dimphy
    3535  USE iophy
    36   USE mod_grid_phy_lmdz
     36  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, klon_glo
    3737
    3838  IMPLICIT none
    39 #include "dimensions.h"
    4039  INTEGER :: npCFMIP
    4140  REAL, DIMENSION(npCFMIP) :: lonCFMIP, latCFMIP
     
    4443  REAL :: dlon1, dlon2
    4544  REAL :: dlat1, dlat2
    46   REAL, DIMENSION(iim+1) :: lon
     45  REAL, DIMENSION(nbp_lon+1) :: lon
    4746  INTEGER, DIMENSION(npCFMIP) :: tabijGCM
    4847  REAL, DIMENSION(npCFMIP) :: lonGCM, latGCM
    4948
    50   lon(1:iim)=io_lon(:)
    51   lon(iim+1)=-1*lon(1)
     49  lon(1:nbp_lon)=io_lon(:)
     50  lon(nbp_lon+1)=-1*lon(1)
    5251  OPEN(22, file="LMDZ_pointsCFMIP.txt")
    5352  DO np=1, npCFMIP
    54   DO i=1, iim
     53  DO i=1, nbp_lon
    5554!
    5655! PRINT*,'IM np i lonCF lonGCM lonGCM+1',np,i,lonCFMIP(np),lon(i), &
     
    8584   ELSE
    8685    j=j+1
    87     IF(j.LE.jjm) THEN
     86    IF(j.LE.nbp_lat-1) THEN
    8887     GOTO 40
    8988    ENDIF
     
    9998     lonGCM(ip)=lon(ipt(ip))
    10099     latGCM(ip)=io_lat(jpt(ip))
    101      if(jpt(ip).GE.2.AND.jpt(ip).LE.jjm) THEN     
    102       tabijGCM(ip)=1+(jpt(ip)-2)*iim+ipt(ip)
     100     if(jpt(ip).GE.2.AND.jpt(ip).LE. nbp_lat-1) THEN     
     101      tabijGCM(ip)=1+(jpt(ip)-2)*nbp_lon+ipt(ip)
    103102     else if(jpt(ip).EQ.1) THEN
    104103      tabijGCM(ip)=1
    105      else if(jpt(ip).EQ.jjm+1) THEN
     104     else if(jpt(ip).EQ.nbp_lat) THEN
    106105      tabijGCM(ip)=klon_glo
    107106     else
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/cpl_mod.F90

    r3817 r3819  
    103103    USE surface_data
    104104    USE indice_sol_mod
     105    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, grid1dTo2d_glo
    105106   ! USE temps_phy_mod
    106107    USE inifis_mod, ONLY: annee_ref, day_ini, itau_phy, itaufin, lunout
    107     INCLUDE "dimensions.h"
    108108
    109109! Input arguments
     
    121121    INTEGER                           :: npas ! only for OASIS2
    122122    REAL                              :: zjulian
    123     REAL, DIMENSION(iim,jjm+1)        :: zx_lon, zx_lat
     123    REAL, DIMENSION(nbp_lon,nbp_lat)        :: zx_lon, zx_lat
    124124    CHARACTER(len = 20)               :: modname = 'cpl_init'
    125125    CHARACTER(len = 80)               :: abort_message
     
    172172    ALLOCATE(cpl_taumod(klon,2), stat = error)
    173173    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)
     174    ALLOCATE(cpl_rriv2D(nbp_lon,jj_nb), stat=error)
     175    sum_error = sum_error + error
     176    ALLOCATE(cpl_rcoa2D(nbp_lon,jj_nb), stat=error)
     177    sum_error = sum_error + error
     178    ALLOCATE(cpl_rlic2D(nbp_lon,jj_nb), stat=error)
     179    sum_error = sum_error + error
     180    ALLOCATE(read_sst(nbp_lon, jj_nb), stat = error)
     181    sum_error = sum_error + error
     182    ALLOCATE(read_sic(nbp_lon, jj_nb), stat = error)
     183    sum_error = sum_error + error
     184    ALLOCATE(read_sit(nbp_lon, jj_nb), stat = error)
     185    sum_error = sum_error + error
     186    ALLOCATE(read_alb_sic(nbp_lon, jj_nb), stat = error)
     187    sum_error = sum_error + error
     188    ALLOCATE(read_u0(nbp_lon, jj_nb), stat = error)
     189    sum_error = sum_error + error
     190    ALLOCATE(read_v0(nbp_lon, jj_nb), stat = error)
    191191    sum_error = sum_error + error
    192192
    193193    IF (carbon_cycle_cpl) THEN
    194        ALLOCATE(read_co2(iim, jj_nb), stat = error)
     194       ALLOCATE(read_co2(nbp_lon, jj_nb), stat = error)
    195195       sum_error = sum_error + error
    196196       ALLOCATE(cpl_atm_co2(klon,2), stat = error)
     
    230230       idayref = day_ini
    231231       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
     232       CALL grid1dTo2d_glo(rlon,zx_lon)
     233       DO i = 1, nbp_lon
    234234          zx_lon(i,1) = rlon(i+1)
    235           zx_lon(i,jjm+1) = rlon(i+1)
     235          zx_lon(i,nbp_lat) = rlon(i+1)
    236236       ENDDO
    237        CALL gr_fi_ecrit(1,klon,iim,jjm+1,rlat,zx_lat)
     237       CALL grid1dTo2d_glo(rlat,zx_lat)
    238238       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)
     239       CALL histbeg(clintocplnam, nbp_lon,zx_lon(:,1),nbp_lat,zx_lat(1,:),&
     240            1,nbp_lon,1,nbp_lat, itau_phy,zjulian,dtime,nhoridct,nidct)
    241241! no vertical axis
    242242       CALL histdef(nidct, 'tauxe','tauxe', &
    243             "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
     243            "-",nbp_lon, nbp_lat, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
    244244       CALL histdef(nidct, 'tauyn','tauyn', &
    245             "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
     245            "-",nbp_lon, nbp_lat, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
    246246       CALL histdef(nidct, 'tmp_lon','tmp_lon', &
    247             "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
     247            "-",nbp_lon, nbp_lat, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
    248248       CALL histdef(nidct, 'tmp_lat','tmp_lat', &
    249             "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
     249            "-",nbp_lon, nbp_lat, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
    250250       DO jf=1,maxsend
    251251         IF (infosend(i)%action) THEN
    252252             CALL histdef(nidct, infosend(i)%name ,infosend(i)%name , &
    253                 "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
     253                "-",nbp_lon, nbp_lat, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
    254254         ENDIF
    255255       END DO
     
    258258       
    259259       clfromcplnam="cpl_atm_sst"
    260        CALL histbeg(clfromcplnam, iim,zx_lon(:,1),jjm+1,zx_lat(1,:),1,iim,1,jjm+1, &
     260       CALL histbeg(clfromcplnam, nbp_lon,zx_lon(:,1),nbp_lat,zx_lat(1,:),1,nbp_lon,1,nbp_lat, &
    261261            0,zjulian,dtime,nhoridcs,nidcs)
    262262! no vertical axis
     
    264264         IF (inforecv(i)%action) THEN
    265265             CALL histdef(nidcs,inforecv(i)%name ,inforecv(i)%name , &
    266                 "-",iim, jjm+1, nhoridcs, 1, 1, 1, -99, 32, "inst", dtime,dtime)
     266                "-",nbp_lon, nbp_lat, nhoridcs, 1, 1, 1, -99, 32, "inst", dtime,dtime)
    267267         ENDIF
    268268       END DO
     
    299299  !  USE temps_phy_mod
    300300    USE inifis_mod, ONLY: start_time, itau_phy
     301    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    301302   
    302303    INCLUDE "YOMCST.h"
    303     INCLUDE "dimensions.h"
    304 
    305304! Arguments
    306305!************************************************************************************
     
    314313    INTEGER                                 :: j, i, time_sec
    315314    INTEGER                                 :: itau_w
    316     INTEGER, DIMENSION(iim*(jjm+1))         :: ndexcs
     315    INTEGER, DIMENSION(nbp_lon*nbp_lat)    :: ndexcs
    317316    CHARACTER(len = 20)                     :: modname = 'cpl_receive_frac'
    318317    CHARACTER(len = 80)                     :: abort_message
    319318    REAL, DIMENSION(klon)                   :: read_sic1D
    320     REAL, DIMENSION(iim,jj_nb,maxrecv)      :: tab_read_flds
     319    REAL, DIMENSION(nbp_lon,jj_nb,maxrecv)  :: tab_read_flds
    321320    REAL, DIMENSION(klon,nbsrf)             :: pctsrf_old
    322321    REAL, DIMENSION(klon_mpi)               :: rlon_mpi, rlat_mpi
    323     REAL, DIMENSION(iim, jj_nb)             :: tmp_lon, tmp_lat
    324     REAL, DIMENSION(iim, jj_nb)             :: tmp_r0
     322    REAL, DIMENSION(nbp_lon, jj_nb)         :: tmp_lon, tmp_lat
     323    REAL, DIMENSION(nbp_lon, jj_nb)         :: tmp_r0
    325324
    326325!*************************************************************************************
     
    349348          DO i = 1, maxrecv
    350349            IF (inforecv(i)%action) THEN
    351                 CALL histwrite(nidcs,inforecv(i)%name,itau_w,tab_read_flds(:,:,i),iim*(jjm+1),ndexcs)
     350                CALL histwrite(nidcs,inforecv(i)%name,itau_w,tab_read_flds(:,:,i),nbp_lon*nbp_lat,ndexcs)
    352351            ENDIF
    353352          END DO
     
    374373! Transform the currents from cartesian to spheric coordinates
    375374! tmp_r0 should be zero
    376           CALL geo2atm(iim, jj_nb, tab_read_flds(:,:,idr_curenx), &
     375          CALL geo2atm(nbp_lon, jj_nb, tab_read_flds(:,:,idr_curenx), &
    377376             tab_read_flds(:,:,idr_cureny), tab_read_flds(:,:,idr_curenz), &
    378377               tmp_lon, tmp_lat, &
     
    543542    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send
    544543    USE indice_sol_mod
    545     INCLUDE "dimensions.h"
     544    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    546545
    547546! Input arguments
     
    636635       IF (.NOT. ALLOCATED(cpl_sols2D)) THEN
    637636          sum_error = 0
    638           ALLOCATE(cpl_sols2D(iim,jj_nb,2), stat=error)
    639           sum_error = sum_error + error
    640           ALLOCATE(cpl_nsol2D(iim,jj_nb,2), stat=error)
    641           sum_error = sum_error + error
    642           ALLOCATE(cpl_rain2D(iim,jj_nb,2), stat=error)
    643           sum_error = sum_error + error
    644           ALLOCATE(cpl_snow2D(iim,jj_nb,2), stat=error)
    645           sum_error = sum_error + error
    646           ALLOCATE(cpl_evap2D(iim,jj_nb,2), stat=error)
    647           sum_error = sum_error + error
    648           ALLOCATE(cpl_tsol2D(iim,jj_nb,2), stat=error)
    649           sum_error = sum_error + error
    650           ALLOCATE(cpl_fder2D(iim,jj_nb,2), stat=error)
    651           sum_error = sum_error + error
    652           ALLOCATE(cpl_albe2D(iim,jj_nb,2), stat=error)
    653           sum_error = sum_error + error
    654           ALLOCATE(cpl_taux2D(iim,jj_nb,2), stat=error)
    655           sum_error = sum_error + error
    656           ALLOCATE(cpl_tauy2D(iim,jj_nb,2), stat=error)
    657           sum_error = sum_error + error
    658           ALLOCATE(cpl_windsp2D(iim,jj_nb), stat=error)
    659           sum_error = sum_error + error
    660           ALLOCATE(cpl_taumod2D(iim,jj_nb,2), stat=error)
     637          ALLOCATE(cpl_sols2D(nbp_lon,jj_nb,2), stat=error)
     638          sum_error = sum_error + error
     639          ALLOCATE(cpl_nsol2D(nbp_lon,jj_nb,2), stat=error)
     640          sum_error = sum_error + error
     641          ALLOCATE(cpl_rain2D(nbp_lon,jj_nb,2), stat=error)
     642          sum_error = sum_error + error
     643          ALLOCATE(cpl_snow2D(nbp_lon,jj_nb,2), stat=error)
     644          sum_error = sum_error + error
     645          ALLOCATE(cpl_evap2D(nbp_lon,jj_nb,2), stat=error)
     646          sum_error = sum_error + error
     647          ALLOCATE(cpl_tsol2D(nbp_lon,jj_nb,2), stat=error)
     648          sum_error = sum_error + error
     649          ALLOCATE(cpl_fder2D(nbp_lon,jj_nb,2), stat=error)
     650          sum_error = sum_error + error
     651          ALLOCATE(cpl_albe2D(nbp_lon,jj_nb,2), stat=error)
     652          sum_error = sum_error + error
     653          ALLOCATE(cpl_taux2D(nbp_lon,jj_nb,2), stat=error)
     654          sum_error = sum_error + error
     655          ALLOCATE(cpl_tauy2D(nbp_lon,jj_nb,2), stat=error)
     656          sum_error = sum_error + error
     657          ALLOCATE(cpl_windsp2D(nbp_lon,jj_nb), stat=error)
     658          sum_error = sum_error + error
     659          ALLOCATE(cpl_taumod2D(nbp_lon,jj_nb,2), stat=error)
    661660          sum_error = sum_error + error
    662661         
    663662          IF (carbon_cycle_cpl) THEN
    664              ALLOCATE(cpl_atm_co22D(iim,jj_nb), stat=error)
     663             ALLOCATE(cpl_atm_co22D(nbp_lon,jj_nb), stat=error)
    665664             sum_error = sum_error + error
    666665          END IF
     
    734733    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl
    735734    USE indice_sol_mod
    736     INCLUDE "dimensions.h"
     735    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    737736
    738737! Input arguments
     
    821820       IF (.NOT. ALLOCATED(cpl_sols2D)) THEN
    822821          sum_error = 0
    823           ALLOCATE(cpl_sols2D(iim,jj_nb,2), stat=error)
    824           sum_error = sum_error + error
    825           ALLOCATE(cpl_nsol2D(iim,jj_nb,2), stat=error)
    826           sum_error = sum_error + error
    827           ALLOCATE(cpl_rain2D(iim,jj_nb,2), stat=error)
    828           sum_error = sum_error + error
    829           ALLOCATE(cpl_snow2D(iim,jj_nb,2), stat=error)
    830           sum_error = sum_error + error
    831           ALLOCATE(cpl_evap2D(iim,jj_nb,2), stat=error)
    832           sum_error = sum_error + error
    833           ALLOCATE(cpl_tsol2D(iim,jj_nb,2), stat=error)
    834           sum_error = sum_error + error
    835           ALLOCATE(cpl_fder2D(iim,jj_nb,2), stat=error)
    836           sum_error = sum_error + error
    837           ALLOCATE(cpl_albe2D(iim,jj_nb,2), stat=error)
    838           sum_error = sum_error + error
    839           ALLOCATE(cpl_taux2D(iim,jj_nb,2), stat=error)
    840           sum_error = sum_error + error
    841           ALLOCATE(cpl_tauy2D(iim,jj_nb,2), stat=error)
    842           sum_error = sum_error + error
    843           ALLOCATE(cpl_windsp2D(iim,jj_nb), stat=error)
    844           sum_error = sum_error + error
    845           ALLOCATE(cpl_taumod2D(iim,jj_nb,2), stat=error)
     822          ALLOCATE(cpl_sols2D(nbp_lon,jj_nb,2), stat=error)
     823          sum_error = sum_error + error
     824          ALLOCATE(cpl_nsol2D(nbp_lon,jj_nb,2), stat=error)
     825          sum_error = sum_error + error
     826          ALLOCATE(cpl_rain2D(nbp_lon,jj_nb,2), stat=error)
     827          sum_error = sum_error + error
     828          ALLOCATE(cpl_snow2D(nbp_lon,jj_nb,2), stat=error)
     829          sum_error = sum_error + error
     830          ALLOCATE(cpl_evap2D(nbp_lon,jj_nb,2), stat=error)
     831          sum_error = sum_error + error
     832          ALLOCATE(cpl_tsol2D(nbp_lon,jj_nb,2), stat=error)
     833          sum_error = sum_error + error
     834          ALLOCATE(cpl_fder2D(nbp_lon,jj_nb,2), stat=error)
     835          sum_error = sum_error + error
     836          ALLOCATE(cpl_albe2D(nbp_lon,jj_nb,2), stat=error)
     837          sum_error = sum_error + error
     838          ALLOCATE(cpl_taux2D(nbp_lon,jj_nb,2), stat=error)
     839          sum_error = sum_error + error
     840          ALLOCATE(cpl_tauy2D(nbp_lon,jj_nb,2), stat=error)
     841          sum_error = sum_error + error
     842          ALLOCATE(cpl_windsp2D(nbp_lon,jj_nb), stat=error)
     843          sum_error = sum_error + error
     844          ALLOCATE(cpl_taumod2D(nbp_lon,jj_nb,2), stat=error)
    846845          sum_error = sum_error + error
    847846
    848847          IF (carbon_cycle_cpl) THEN
    849              ALLOCATE(cpl_atm_co22D(iim,jj_nb), stat=error)
     848             ALLOCATE(cpl_atm_co22D(nbp_lon,jj_nb), stat=error)
    850849             sum_error = sum_error + error
    851850          END IF
     
    914913! (it is done in cpl_send_seaice_fields).
    915914!
    916     INCLUDE "dimensions.h"
     915    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    917916
    918917! Input arguments
     
    926925! Local variables
    927926!*************************************************************************************
    928     REAL, DIMENSION(iim,jj_nb)             :: rriv2D
    929     REAL, DIMENSION(iim,jj_nb)             :: rcoa2D
     927    REAL, DIMENSION(nbp_lon,jj_nb)             :: rriv2D
     928    REAL, DIMENSION(nbp_lon,jj_nb)             :: rcoa2D
    930929
    931930!*************************************************************************************
     
    968967
    969968  SUBROUTINE cpl_send_landice_fields(itime, knon, knindex, rlic_in)
     969  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    970970! This subroutine cumulates the field for melting ice for each time-step
    971971! during a coupling period. This routine will not send to coupler. Sending
    972972! will be done in cpl_send_seaice_fields.
    973973!
    974 
    975     INCLUDE "dimensions.h"
    976974
    977975! Input varibales
     
    984982! Local varibales
    985983!*************************************************************************************
    986     REAL, DIMENSION(iim,jj_nb)             :: rlic2D
     984    REAL, DIMENSION(nbp_lon,jj_nb)             :: rlic2D
    987985
    988986!*************************************************************************************
     
    10331031! Some includes
    10341032!*************************************************************************************
    1035     INCLUDE "dimensions.h"
     1033    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    10361034   
    10371035! Input arguments
     
    10481046    INTEGER                                              :: itau_w
    10491047    INTEGER                                              :: time_sec
    1050     INTEGER, DIMENSION(iim*(jjm+1))                      :: ndexct
     1048    INTEGER, DIMENSION(nbp_lon*nbp_lat)                  :: ndexct
    10511049    REAL                                                 :: Up, Down
    1052     REAL, DIMENSION(iim, jj_nb)                          :: tmp_lon, tmp_lat
    1053     REAL, DIMENSION(iim, jj_nb, 4)                       :: pctsrf2D
    1054     REAL, DIMENSION(iim, jj_nb)                          :: deno
     1050    REAL, DIMENSION(nbp_lon, jj_nb)                      :: tmp_lon, tmp_lat
     1051    REAL, DIMENSION(nbp_lon, jj_nb, 4)                   :: pctsrf2D
     1052    REAL, DIMENSION(nbp_lon, jj_nb)                      :: deno
    10551053    CHARACTER(len = 20)                                  :: modname = 'cpl_send_all'
    10561054    CHARACTER(len = 80)                                  :: abort_message
    10571055   
    10581056! Variables with fields to coupler
    1059     REAL, DIMENSION(iim, jj_nb)                          :: tmp_taux
    1060     REAL, DIMENSION(iim, jj_nb)                          :: tmp_tauy
    1061     REAL, DIMENSION(iim, jj_nb)                          :: tmp_calv
     1057    REAL, DIMENSION(nbp_lon, jj_nb)                      :: tmp_taux
     1058    REAL, DIMENSION(nbp_lon, jj_nb)                      :: tmp_tauy
     1059    REAL, DIMENSION(nbp_lon, jj_nb)                      :: tmp_calv
    10621060! Table with all fields to send to coupler
    1063     REAL, DIMENSION(iim, jj_nb, maxsend)                 :: tab_flds
     1061    REAL, DIMENSION(nbp_lon, jj_nb, maxsend)             :: tab_flds
    10641062    REAL, DIMENSION(klon_mpi)                            :: rlon_mpi, rlat_mpi
    10651063
     
    11151113
    11161114      DO j = 1, jj_nb
    1117          tmp_calv(:,j) = DOT_PRODUCT (cpl_rlic2D(1:iim,j), &
    1118               pctsrf2D(1:iim,j,is_lic)) / REAL(iim)
     1115         tmp_calv(:,j) = DOT_PRODUCT (cpl_rlic2D(1:nbp_lon,j), &
     1116              pctsrf2D(1:nbp_lon,j,is_lic)) / REAL(nbp_lon)
    11191117      ENDDO
    11201118   
     
    11361134         
    11371135         IF (.NOT. is_north_pole .AND. ii_begin /=1) THEN
    1138             Up=Up+tmp_calv(iim,1)
     1136            Up=Up+tmp_calv(nbp_lon,1)
    11391137            tmp_calv(:,1)=Up
    11401138         ENDIF
    11411139         
    1142          IF (.NOT. is_south_pole .AND. ii_end /= iim) THEN
     1140         IF (.NOT. is_south_pole .AND. ii_end /= nbp_lon) THEN
    11431141            Down=Down+tmp_calv(1,jj_nb)
    11441142            tmp_calv(:,jj_nb)=Down       
     
    12291227    IF (is_sequential) THEN
    12301228       IF (is_north_pole) tmp_lon(:,1)     = tmp_lon(:,2)
    1231        IF (is_south_pole) tmp_lon(:,jjm+1) = tmp_lon(:,jjm)
     1229       IF (is_south_pole) tmp_lon(:,nbp_lat) = tmp_lon(:,nbp_lat-1)
    12321230    ENDIF
    12331231     
     
    12361234       ndexct(:) = 0
    12371235       itau_w = itau_phy + itime + start_time * day_step / iphysiq
    1238        CALL histwrite(nidct,'tauxe',itau_w,tmp_taux,iim*(jjm+1),ndexct)
    1239        CALL histwrite(nidct,'tauyn',itau_w,tmp_tauy,iim*(jjm+1),ndexct)
    1240        CALL histwrite(nidct,'tmp_lon',itau_w,tmp_lon,iim*(jjm+1),ndexct)
    1241        CALL histwrite(nidct,'tmp_lat',itau_w,tmp_lat,iim*(jjm+1),ndexct)
     1236       CALL histwrite(nidct,'tauxe',itau_w,tmp_taux,nbp_lon*nbp_lat,ndexct)
     1237       CALL histwrite(nidct,'tauyn',itau_w,tmp_tauy,nbp_lon*nbp_lat,ndexct)
     1238       CALL histwrite(nidct,'tmp_lon',itau_w,tmp_lon,nbp_lon*nbp_lat,ndexct)
     1239       CALL histwrite(nidct,'tmp_lat',itau_w,tmp_lat,nbp_lon*nbp_lat,ndexct)
    12421240    ENDIF
    12431241
     
    12451243! cartesian 3D coordinates
    12461244!$OMP MASTER
    1247     CALL atm2geo (iim, jj_nb, tmp_taux, tmp_tauy, tmp_lon, tmp_lat, &
     1245    CALL atm2geo (nbp_lon, jj_nb, tmp_taux, tmp_tauy, tmp_lon, tmp_lat, &
    12481246         tab_flds(:,:,ids_tauxxu), tab_flds(:,:,ids_tauyyu), tab_flds(:,:,ids_tauzzu) )
    12491247   
     
    12601258        DO j=1,maxsend
    12611259          IF (infosend(j)%action) CALL histwrite(nidct,infosend(j)%name, itau_w, &
    1262              tab_flds(:,:,j),iim*(jjm+1),ndexct)
     1260             tab_flds(:,:,j),nbp_lon*nbp_lat,ndexct)
    12631261        ENDDO
    12641262    ENDIF
     
    13021300  SUBROUTINE cpl2gath(champ_in, champ_out, knon, knindex)
    13031301  USE mod_phys_lmdz_para
     1302  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    13041303! Cette routine transforme un champs de la grille 2D recu du coupleur sur la grille
    13051304! 'gathered' (la grille physiq comprime).
     
    13141313!   champ_out    champ sur la grille 'gatherd'
    13151314!
    1316     INCLUDE "dimensions.h"
    13171315
    13181316! Input
    1319     INTEGER, INTENT(IN)                       :: knon
    1320     REAL, DIMENSION(iim,jj_nb), INTENT(IN)    :: champ_in
    1321     INTEGER, DIMENSION(klon), INTENT(IN)      :: knindex
     1317    INTEGER, INTENT(IN)                        :: knon
     1318    REAL, DIMENSION(nbp_lon,jj_nb), INTENT(IN) :: champ_in
     1319    INTEGER, DIMENSION(klon), INTENT(IN)       :: knindex
    13221320
    13231321! Output
     
    13331331   
    13341332
    1335 ! Transform from 2 dimensions (iim,jj_nb) to 1 dimension (klon)
     1333! Transform from 2 dimensions (nbp_lon,jj_nb) to 1 dimension (klon)
    13361334!$OMP MASTER
    13371335    CALL Grid2Dto1D_mpi(champ_in,temp_mpi)
     
    13521350  SUBROUTINE gath2cpl(champ_in, champ_out, knon, knindex)
    13531351  USE mod_phys_lmdz_para
     1352  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    13541353! Cette routine ecrit un champ 'gathered' sur la grille 2D pour le passer
    13551354! au coupleur.
     
    13631362!   champ_out    champ sur la grille 2D
    13641363!
    1365     INCLUDE "dimensions.h"
    13661364   
    13671365! Input arguments
     
    13731371! Output arguments
    13741372!*************************************************************************************
    1375     REAL, DIMENSION(iim,jj_nb), INTENT(OUT) :: champ_out
     1373    REAL, DIMENSION(nbp_lon,jj_nb), INTENT(OUT) :: champ_out
    13761374
    13771375! Local variables
     
    13891387    ENDDO
    13901388
    1391 ! Transform from 1 dimension (klon) to 2 dimensions (iim,jj_nb)
     1389! Transform from 1 dimension (klon) to 2 dimensions (nbp_lon,jj_nb)
    13921390    CALL gather_omp(temp_omp,temp_mpi)
    13931391
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/ini_bilKP_ave.h

    r3809 r3819  
    1111         CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
    1212c
    13 cym         CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlon,zx_lon)
    14 cym         DO i = 1, iim
    15 cym            zx_lon(i,1) = rlon(i+1)
    16 cym            zx_lon(i,jjmp1) = rlon(i+1)
    17 cym         ENDDO
    1813         DO ll=1,klev
    1914            znivsig(ll)=REAL(ll)
    2015         ENDDO
    21 cym         CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlat,zx_lat)
    22 cym         write(*,*)'zx_lon = ',zx_lon(:,1)
    23 cym         write(*,*)'zx_lat = ',zx_lat(1,:)
    24 cym         CALL histbeg("histbilKP_ave", iim,zx_lon(:,1), jjmp1,
    25 cym     .                zx_lat(1,:),
    26 cym     .                1,iim,1,jjmp1, itau_phy, zjulian, dtime,
    27 cym     .                nhori, nid_bilKPave)
    2816         CALL histbeg_phy("histbilKP_ave", itau_phy, zjulian, dtime,
    2917     .                nhori, nid_bilKPave)
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/ini_bilKP_ins.h

    r3809 r3819  
    1111         CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
    1212c
    13 cym         CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlon,zx_lon)
    14 cym         DO i = 1, iim
    15 cym            zx_lon(i,1) = rlon(i+1)
    16 cym            zx_lon(i,jjmp1) = rlon(i+1)
    17 cym         ENDDO
    1813         DO ll=1,klev
    1914            znivsig(ll)=REAL(ll)
    2015         ENDDO
    21 cym         CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlat,zx_lat)
    22 cym         write(*,*)'zx_lon = ',zx_lon(:,1)
    23 cym         write(*,*)'zx_lat = ',zx_lat(1,:)
    2416c
    2517cIM 280405 BEG
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/ini_histday_seri.h

    r3818 r3819  
    1313         CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
    1414!
    15          CALL gr_fi_ecrit(1,klon,nbp_lon,jjmp1,rlon,zx_lon)
     15         CALL grid1dTo2d_glo(rlon,zx_lon)
    1616         DO i = 1, nbp_lon
    1717            zx_lon(i,1) = rlon(i+1)
     
    2121            znivsig(ll)=REAL(ll)
    2222         ENDDO
    23          CALL gr_fi_ecrit(1,klon,nbp_lon,jjmp1,rlat,zx_lat)
     23         CALL grid1dTo2d_glo(rlat,zx_lat)
    2424!
    2525         imin_debut=1
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/ini_paramLMDZ_phy.h

    r3818 r3819  
    1515       CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
    1616!
    17        CALL gr_fi_ecrit(1,klon,nbp_lon,nbp_lat,rlon_glo,zx_lon)
     17       CALL grid1dTo2d_glo(rlon_glo,zx_lon)
    1818       if (nbp_lon.gt.1) then
    1919       DO i = 1, nbp_lon
     
    2222       ENDDO
    2323       endif
    24        CALL gr_fi_ecrit(1,klon,nbp_lon,nbp_lat,rlat_glo,zx_lat)
     24       CALL grid1dTo2d_glo(rlat_glo,zx_lat)
    2525!
    2626       CALL histbeg("paramLMDZ_phy.nc",  &
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/iophy.F90

    r3817 r3819  
    5353#endif
    5454  IMPLICIT NONE
    55   INCLUDE 'dimensions.h'
    5655    REAL,DIMENSION(klon),INTENT(IN) :: rlon
    5756    REAL,DIMENSION(klon),INTENT(IN) :: rlat
     
    7675   
    7776!$OMP MASTER 
    78     ALLOCATE(io_lat(jjm+1-1/(iim*jjm)))
     77    ALLOCATE(io_lat(nbp_lat))
    7978    io_lat(1)=rlat_glo(1)
    80     io_lat(jjm+1-1/(iim*jjm))=rlat_glo(klon_glo)
    81     IF ((iim*jjm) > 1) then
    82       DO i=2,jjm
    83         io_lat(i)=rlat_glo(2+(i-2)*iim)
     79    io_lat(nbp_lat)=rlat_glo(klon_glo)
     80    IF ((nbp_lon*nbp_lat) > 1) then
     81      DO i=2,nbp_lat-1
     82        io_lat(i)=rlat_glo(2+(i-2)*nbp_lon)
    8483      ENDDO
    8584    ENDIF
    8685
    87     ALLOCATE(io_lon(iim))
    88     io_lon(:)=rlon_glo(2-1/(iim*jjm):iim+1-1/(iim*jjm))
     86    ALLOCATE(io_lon(nbp_lon))
     87    io_lon(1)=rlon_glo(1)
     88    IF (nbp_lon > 1) io_lon(2:nbp_lon)=rlon_glo(3:nbp_lon+1)
     89   
    8990!! (I) dtnb   : total number of domains
    9091!! (I) dnb    : domain number
     
    103104
    104105    ddid=(/ 1,2 /)
    105     dsg=(/ iim, jjm+1-1/(iim*jjm) /)
    106     dsl=(/ iim, jj_nb /)
     106    dsg=(/ nbp_lon, nbp_lat /)
     107    dsl=(/ nbp_lon, jj_nb /)
    107108    dpf=(/ 1,jj_begin /)
    108     dpl=(/ iim, jj_end /)
     109    dpl=(/ nbp_lon, jj_end /)
    109110    dhs=(/ ii_begin-1,0 /)
    110111    IF (mpi_rank==mpi_size-1) THEN
    111112      dhe=(/0,0/)
    112113    ELSE
    113       dhe=(/ iim-ii_end,0 /) 
     114      dhe=(/ nbp_lon-ii_end,0 /) 
    114115    ENDIF
    115116
     
    154155                                mpi_size, mpi_rank
    155156  USE ioipsl, only: flio_dom_set
     157  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    156158  IMPLICIT NONE
    157   INCLUDE 'dimensions.h'   
    158     REAL,DIMENSION(iim),INTENT(IN) :: lon
    159     REAL,DIMENSION(jjm+1-1/(iim*jjm)),INTENT(IN) :: lat
     159    REAL,DIMENSION(nbp_lon),INTENT(IN) :: lon
     160    REAL,DIMENSION(nbp_lat),INTENT(IN) :: lat
    160161
    161162    INTEGER,DIMENSION(2) :: ddid
     
    168169
    169170!$OMP MASTER 
    170     allocate(io_lat(jjm+1-1/(iim*jjm)))
     171    allocate(io_lat(nbp_lat))
    171172    io_lat(:)=lat(:)
    172     allocate(io_lon(iim))
     173    allocate(io_lon(nbp_lon))
    173174    io_lon(:)=lon(:)
    174175   
    175176    ddid=(/ 1,2 /)
    176     dsg=(/ iim, jjm+1-1/(iim*jjm) /)
    177     dsl=(/ iim, jj_nb /)
     177    dsg=(/ nbp_lon, nbp_lat /)
     178    dsl=(/ nbp_lon, jj_nb /)
    178179    dpf=(/ 1,jj_begin /)
    179     dpl=(/ iim, jj_end /)
     180    dpl=(/ nbp_lon, jj_end /)
    180181    dhs=(/ ii_begin-1,0 /)
    181182    if (mpi_rank==mpi_size-1) then
    182183      dhe=(/0,0/)
    183184    else
    184       dhe=(/ iim-ii_end,0 /) 
     185      dhe=(/ nbp_lon-ii_end,0 /) 
    185186    endif
    186187   
     
    197198  USE mod_phys_lmdz_para, only: is_sequential, is_using_mpi, is_mpi_root, &
    198199                                jj_begin, jj_end, jj_nb
     200  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    199201  use ioipsl, only: histbeg
    200202#ifdef CPP_XIOS
     
    202204#endif
    203205  IMPLICIT NONE
    204   include 'dimensions.h'
    205206  include 'clesphys.h'
    206207   
     
    216217!$OMP MASTER   
    217218    if (is_sequential) then
    218       call histbeg(name,iim,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
    219                    1,iim,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day)
     219      call histbeg(name,nbp_lon,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
     220                   1,nbp_lon,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day)
    220221    else
    221       call histbeg(name,iim,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
    222                    1,iim,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day,phys_domain_id)
     222      call histbeg(name,nbp_lon,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
     223                   1,nbp_lon,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day,phys_domain_id)
    223224    endif
    224225
     
    239240
    240241  USE mod_phys_lmdz_para, only: jj_begin, jj_end, jj_nb, is_sequential
     242  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    241243  use ioipsl, only: histbeg
    242244
    243245  IMPLICIT NONE
    244   include 'dimensions.h'
    245246   
    246247    character*(*), INTENT(IN) :: name
     
    254255#ifndef CPP_IOIPSL_NO_OUTPUT
    255256    if (is_sequential) then
    256       call histbeg(name,iim,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
    257                    1,iim,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day)
     257      call histbeg(name,nbp_lon,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
     258                   1,nbp_lon,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day)
    258259    else
    259       call histbeg(name,iim,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
    260                    1,iim,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day,phys_domain_id)
     260      call histbeg(name,nbp_lon,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
     261                   1,nbp_lon,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day,phys_domain_id)
    261262    endif
    262263#endif
     
    273274                                is_sequential, klon_mpi_begin, klon_mpi_end, &
    274275                                mpi_rank
    275   USE mod_grid_phy_lmdz, only: klon_glo
     276  USE mod_grid_phy_lmdz, only: klon_glo, nbp_lon, nbp_lat, grid1dTo2d_glo
    276277  use ioipsl, only: histbeg
    277278
    278279  IMPLICIT NONE
    279   include 'dimensions.h'
    280280
    281281    REAL,DIMENSION(klon),INTENT(IN) :: rlon
     
    303303    REAL, allocatable, DIMENSION(:) :: npplat, npplon
    304304    REAL, allocatable, DIMENSION(:,:) :: npplat_bounds, npplon_bounds
    305     INTEGER, PARAMETER :: jjmp1=jjm+1-1/jjm
    306     REAL, DIMENSION(iim,jjmp1) :: zx_lon, zx_lat
     305    REAL, DIMENSION(nbp_lon,nbp_lat) :: zx_lon, zx_lat
    307306
    308307    CALL gather(rlat,rlat_glo)
     
    329328     endif
    330329!
    331      IF ( tabij(i).LE.iim) THEN
     330     IF ( tabij(i).LE.nbp_lon) THEN
    332331      plat_bounds(i,1)=rlat_glo(tabij(i))
    333332     ELSE
    334       plat_bounds(i,1)=rlat_glo(tabij(i)-iim)
     333      plat_bounds(i,1)=rlat_glo(tabij(i)-nbp_lon)
    335334     ENDIF
    336      plat_bounds(i,2)=rlat_glo(tabij(i)+iim)
     335     plat_bounds(i,2)=rlat_glo(tabij(i)+nbp_lon)
    337336!
    338337!    print*,'CFMIP_iophy point i lon lon_bds',i,plon_bounds(i,1),rlon_glo(tabij(i)),plon_bounds(i,2)
     
    350349     ENDDO
    351350
    352        CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlon_glo,zx_lon)
    353        if ((iim*jjm).gt.1) then
    354        DO i = 1, iim
    355          zx_lon(i,1) = rlon_glo(i+1)
    356          zx_lon(i,jjmp1) = rlon_glo(i+1)
    357        ENDDO
    358        endif
    359        CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlat_glo,zx_lat)
     351       CALL grid1dTo2d_glo(rlon_glo,zx_lon)
     352       IF ( nbp_lon*nbp_lat > 1) then
     353         DO i = 1, nbp_lon
     354           zx_lon(i,1) = rlon_glo(i+1)
     355           zx_lon(i,nbp_lat) = rlon_glo(i+1)
     356         ENDDO
     357       ENDIF
     358       CALL grid1dTo2d_glo(rlat_glo,zx_lat)
    360359
    361360    DO i=1,pim
     
    366365
    367366     if (ipt(i).EQ.1) then
    368       plon_bounds(i,1)=zx_lon(iim,jpt(i))
     367      plon_bounds(i,1)=zx_lon(nbp_lon,jpt(i))
    369368      plon_bounds(i,2)=360.+zx_lon(ipt(i)+1,jpt(i))
    370369     endif
    371370 
    372      if (ipt(i).EQ.iim) then
     371     if (ipt(i).EQ.nbp_lon) then
    373372      plon_bounds(i,2)=360.+zx_lon(1,jpt(i))
    374373     endif
     
    382381     endif
    383382 
    384      if (jpt(i).EQ.jjmp1) then
    385       plat_bounds(i,1)=zx_lat(ipt(i),jjmp1)+0.001
    386       plat_bounds(i,2)=zx_lat(ipt(i),jjmp1)-0.001
     383     if (jpt(i).EQ.nbp_lat) then
     384      plat_bounds(i,1)=zx_lat(ipt(i),nbp_lat)+0.001
     385      plat_bounds(i,2)=zx_lat(ipt(i),nbp_lat)-0.001
    387386     endif
    388387!
     
    444443
    445444
    446   SUBROUTINE histdef2d_old (iff,lpoint,flag_var,nomvar,titrevar,unitvar)
    447 
    448     USE ioipsl, only: histdef
    449     USE mod_phys_lmdz_para, only: jj_nb
    450     use phys_output_var_mod, only: type_ecri, zoutm, zdtime_moy, lev_files, &
    451                                    nid_files, nhorim, swaero_diag, nfiles
    452     IMPLICIT NONE
    453     INCLUDE "dimensions.h"
    454     INCLUDE "clesphys.h"
    455 
    456     INTEGER                          :: iff
    457     LOGICAL                          :: lpoint
    458     INTEGER, DIMENSION(nfiles)       :: flag_var
    459     CHARACTER(LEN=20)                 :: nomvar
    460     CHARACTER(LEN=*)                 :: titrevar
    461     CHARACTER(LEN=*)                 :: unitvar
    462 
    463     REAL zstophym
    464 
    465     IF (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') THEN
    466        zstophym=zoutm(iff)
    467     ELSE
    468        zstophym=zdtime_moy
    469     ENDIF
    470 
    471     ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def
    472     CALL conf_physoutputs(nomvar,flag_var)
    473 
    474     IF(.NOT.lpoint) THEN 
    475        IF ( flag_var(iff)<=lev_files(iff) ) THEN
    476           CALL histdef (nid_files(iff),nomvar,titrevar,unitvar, &
    477                iim,jj_nb,nhorim(iff), 1,1,1, -99, 32, &
    478                type_ecri(iff), zstophym,zoutm(iff))               
    479        ENDIF
    480     ELSE
    481        IF ( flag_var(iff)<=lev_files(iff) ) THEN
    482           CALL histdef (nid_files(iff),nomvar,titrevar,unitvar, &
    483                npstn,1,nhorim(iff), 1,1,1, -99, 32, &
    484                type_ecri(iff), zstophym,zoutm(iff))               
    485        ENDIF
    486     ENDIF
    487 
    488     ! Set swaero_diag=true if at least one of the concerned variables are defined
    489     IF (nomvar=='topswad' .OR. nomvar=='topswai' .OR. nomvar=='solswad' .OR. nomvar=='solswai' ) THEN
    490        IF  ( flag_var(iff)<=lev_files(iff) ) THEN
    491           swaero_diag=.TRUE.
    492        END IF
    493     END IF
    494   END SUBROUTINE histdef2d_old
    495 
    496 
    497 
    498   SUBROUTINE histdef3d_old (iff,lpoint,flag_var,nomvar,titrevar,unitvar)
    499 
    500     USE ioipsl, only: histdef
    501     USE dimphy, only: klev
    502     USE mod_phys_lmdz_para, only: jj_nb
    503     use phys_output_var_mod, only: type_ecri, zoutm, lev_files, nid_files, &
    504                                    nhorim, zdtime_moy, levmin, levmax, &
    505                                    nvertm, nfiles
    506     IMPLICIT NONE
    507 
    508     INCLUDE "dimensions.h"
    509 !    INCLUDE "indicesol.h"
    510     INCLUDE "clesphys.h"
    511 
    512     INTEGER                          :: iff
    513     LOGICAL                          :: lpoint
    514     INTEGER, DIMENSION(nfiles)       :: flag_var
    515     CHARACTER(LEN=20)                 :: nomvar
    516     CHARACTER(LEN=*)                 :: titrevar
    517     CHARACTER(LEN=*)                 :: unitvar
    518 
    519     REAL zstophym
    520 
    521     ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def
    522     CALL conf_physoutputs(nomvar,flag_var)
    523 
    524     IF (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') THEN
    525        zstophym=zoutm(iff)
    526     ELSE
    527        zstophym=zdtime_moy
    528     ENDIF
    529 
    530     IF(.NOT.lpoint) THEN
    531        IF ( flag_var(iff)<=lev_files(iff) ) THEN
    532           CALL histdef (nid_files(iff), nomvar, titrevar, unitvar, &
    533                iim, jj_nb, nhorim(iff), klev, levmin(iff), &
    534                levmax(iff)-levmin(iff)+1, nvertm(iff), 32, type_ecri(iff), &
    535                zstophym, zoutm(iff))
    536        ENDIF
    537     ELSE
    538        IF ( flag_var(iff)<=lev_files(iff) ) THEN
    539           CALL histdef (nid_files(iff), nomvar, titrevar, unitvar, &
    540                npstn,1,nhorim(iff), klev, levmin(iff), &
    541                levmax(iff)-levmin(iff)+1, nvertm(iff), 32, &
    542                type_ecri(iff), zstophym,zoutm(iff))
    543        ENDIF
    544     ENDIF
    545   END SUBROUTINE histdef3d_old
    546 
    547 
    548 
    549 
    550 
    551 
    552 
    553445
    554446  SUBROUTINE histdef2d (iff,var)
     
    559451                                   clef_stations, phys_out_filenames, lev_files, &
    560452                                   nid_files, nhorim, swaero_diag
     453    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    561454#ifdef CPP_XIOS
    562455    use wxios, only: wxios_add_field_to_file
     
    564457    IMPLICIT NONE
    565458
    566     INCLUDE "dimensions.h"
    567459    INCLUDE "clesphys.h"
    568460
     
    615507       IF ( var%flag(iff)<=lev_files(iff) ) THEN
    616508          CALL histdef (nid_files(iff), var%name, var%description, var%unit, &
    617                iim,jj_nb,nhorim(iff), 1,1,1, -99, 32, &
     509               nbp_lon,jj_nb,nhorim(iff), 1,1,1, -99, 32, &
    618510               typeecrit, zstophym,zoutm(iff))               
    619511       ENDIF
     
    644536                                   nid_files, nhorim, swaero_diag, levmin, &
    645537                                   levmax, nvertm
     538  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    646539#ifdef CPP_XIOS
    647540    use wxios, only: wxios_add_field_to_file
    648541#endif
    649542    IMPLICIT NONE
    650 
    651     INCLUDE "dimensions.h"
    652543    INCLUDE "clesphys.h"
    653544
     
    700591       IF ( var%flag(iff)<=lev_files(iff) ) THEN
    701592          CALL histdef (nid_files(iff), var%name, var%description, var%unit, &
    702                iim, jj_nb, nhorim(iff), klev, levmin(iff), &
     593               nbp_lon, jj_nb, nhorim(iff), klev, levmin(iff), &
    703594               levmax(iff)-levmin(iff)+1, nvertm(iff), 32, typeecrit, &
    704595               zstophym, zoutm(iff))
     
    742633  USE ioipsl, only: histwrite
    743634  USE inifis_mod, ONLY: prt_level, lunout
     635  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    744636  IMPLICIT NONE
    745   include 'dimensions.h'
    746637   
    747638    integer,INTENT(IN) :: nid
     
    752643    REAL,DIMENSION(klon_mpi) :: buffer_omp
    753644    INTEGER, allocatable, DIMENSION(:) :: index2d
    754     REAL :: Field2d(iim,jj_nb)
     645    REAL :: Field2d(nbp_lon,jj_nb)
    755646
    756647    integer :: ip
     
    764655    CALL grid1Dto2D_mpi(buffer_omp,Field2d)
    765656    if(.NOT.lpoint) THEN
    766      ALLOCATE(index2d(iim*jj_nb))
    767      ALLOCATE(fieldok(iim*jj_nb))
     657     ALLOCATE(index2d(nbp_lon*jj_nb))
     658     ALLOCATE(fieldok(nbp_lon*jj_nb))
    768659     IF (prt_level >= 10) write(lunout,*)'Sending ',name,' to IOIPSL'
    769      CALL histwrite(nid,name,itau,Field2d,iim*jj_nb,index2d)
     660     CALL histwrite(nid,name,itau,Field2d,nbp_lon*jj_nb,index2d)
    770661     IF (prt_level >= 10) write(lunout,*)'Finished sending ',name,' to IOIPSL'
    771662    else
     
    805696                                is_sequential, klon_mpi_begin, klon_mpi_end, &
    806697                                jj_nb, klon_mpi
     698  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    807699  use ioipsl, only: histwrite
    808700  use inifis_mod, only: prt_level, lunout
    809701  IMPLICIT NONE
    810   include 'dimensions.h'
    811702   
    812703    integer,INTENT(IN) :: nid
     
    816707    REAL,DIMENSION(:,:),INTENT(IN) :: field  ! --> field(klon,:)
    817708    REAL,DIMENSION(klon_mpi,size(field,2)) :: buffer_omp
    818     REAL :: Field3d(iim,jj_nb,size(field,2))
     709    REAL :: Field3d(nbp_lon,jj_nb,size(field,2))
    819710    INTEGER :: ip, n, nlev
    820711    INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d
     
    829720    CALL grid1Dto2D_mpi(buffer_omp,field3d)
    830721    if(.NOT.lpoint) THEN
    831      ALLOCATE(index3d(iim*jj_nb*nlev))
    832      ALLOCATE(fieldok(iim*jj_nb,nlev))
     722     ALLOCATE(index3d(nbp_lon*jj_nb*nlev))
     723     ALLOCATE(fieldok(nbp_lon*jj_nb,nlev))
    833724     IF (prt_level >= 10) write(lunout,*)'Sending ',name,' to IOIPSL'
    834      CALL histwrite(nid,name,itau,Field3d,iim*jj_nb*nlev,index3d)
     725     CALL histwrite(nid,name,itau,Field3d,nbp_lon*jj_nb*nlev,index3d)
    835726     IF (prt_level >= 10) write(lunout,*)'Finished sending ',name,' to IOIPSL'
    836727   else
     
    880771                                 nfiles, vars_defined, clef_stations, &
    881772                                 nid_files
     773  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    882774#ifdef CPP_XIOS
    883775  USE xios, only: xios_send_field
     
    886778
    887779  IMPLICIT NONE
    888   INCLUDE 'dimensions.h'
    889780  include 'clesphys.h'
    890781
     
    899790    REAL,DIMENSION(klon_mpi) :: buffer_omp
    900791    INTEGER, allocatable, DIMENSION(:) :: index2d
    901     REAL :: Field2d(iim,jj_nb)
     792    REAL :: Field2d(nbp_lon,jj_nb)
    902793
    903794    INTEGER :: ip
     
    980871
    981872                  IF(.NOT.clef_stations(iff)) THEN
    982                         ALLOCATE(index2d(iim*jj_nb))
    983                         ALLOCATE(fieldok(iim*jj_nb))
     873                        ALLOCATE(index2d(nbp_lon*jj_nb))
     874                        ALLOCATE(fieldok(nbp_lon*jj_nb))
    984875#ifndef CPP_IOIPSL_NO_OUTPUT
    985                         CALL histwrite(nid_files(iff),var%name,itau_iophy,Field2d,iim*jj_nb,index2d)
     876                        CALL histwrite(nid_files(iff),var%name,itau_iophy,Field2d,nbp_lon*jj_nb,index2d)
    986877#endif
    987878!#ifdef CPP_XIOS
     
    1039930                                 nfiles, vars_defined, clef_stations, &
    1040931                                 nid_files
     932  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    1041933#ifdef CPP_XIOS
    1042934  USE xios, only: xios_send_field
     
    1045937
    1046938  IMPLICIT NONE
    1047   INCLUDE 'dimensions.h'
    1048939  include 'clesphys.h'
    1049940
     
    1056947!$OMP THREADPRIVATE(firstx)
    1057948    REAL,DIMENSION(klon_mpi,SIZE(field,2)) :: buffer_omp
    1058     REAL :: Field3d(iim,jj_nb,SIZE(field,2))
     949    REAL :: Field3d(nbp_lon,jj_nb,SIZE(field,2))
    1059950    INTEGER :: ip, n, nlev, nlevx
    1060951    INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d
     
    11211012                                  iff,nlev,klev, firstx                       
    11221013                  write(lunout,*)'histwrite3d_phy: call xios_send_field for ', &
    1123                                   trim(var%name), ' with iim jjm nlevx = ', &
    1124                                   iim,jj_nb,nlevx
     1014                                  trim(var%name), ' with nbp_lon nbp_lat nlevx = ', &
     1015                                  nbp_lon,jj_nb,nlevx
    11251016                endif
    11261017                CALL xios_send_field(var%name, Field3d(:,:,1:nlevx))
     
    11291020#endif
    11301021                IF (.NOT.clef_stations(iff)) THEN
    1131                         ALLOCATE(index3d(iim*jj_nb*nlev))
    1132                         ALLOCATE(fieldok(iim*jj_nb,nlev))
     1022                        ALLOCATE(index3d(nbp_lon*jj_nb*nlev))
     1023                        ALLOCATE(fieldok(nbp_lon*jj_nb,nlev))
    11331024
    11341025#ifndef CPP_IOIPSL_NO_OUTPUT
    1135                         CALL histwrite(nid_files(iff),var%name,itau_iophy,Field3d,iim*jj_nb*nlev,index3d)
     1026                        CALL histwrite(nid_files(iff),var%name,itau_iophy,Field3d,nbp_lon*jj_nb*nlev,index3d)
    11361027#endif
    11371028
     
    11851076                                is_sequential, klon_mpi_begin, klon_mpi_end, &
    11861077                                jj_nb, klon_mpi
     1078  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    11871079  USE xios, only: xios_send_field
    11881080
    11891081
    11901082  IMPLICIT NONE
    1191   INCLUDE 'dimensions.h'
    11921083
    11931084    CHARACTER(LEN=*), INTENT(IN) :: field_name
     
    11961087    REAL,DIMENSION(klon_mpi) :: buffer_omp
    11971088    INTEGER, allocatable, DIMENSION(:) :: index2d
    1198     REAL :: Field2d(iim,jj_nb)
     1089    REAL :: Field2d(nbp_lon,jj_nb)
    11991090
    12001091    INTEGER :: ip
     
    12151106    !IF(.NOT.clef_stations(iff)) THEN
    12161107    IF (.TRUE.) THEN
    1217         ALLOCATE(index2d(iim*jj_nb))
    1218         ALLOCATE(fieldok(iim*jj_nb))
     1108        ALLOCATE(index2d(nbp_lon*jj_nb))
     1109        ALLOCATE(fieldok(nbp_lon*jj_nb))
    12191110
    12201111
     
    12561147                                jj_nb, klon_mpi
    12571148  USE xios, only: xios_send_field
     1149  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    12581150
    12591151
    12601152  IMPLICIT NONE
    1261   INCLUDE 'dimensions.h'
    12621153
    12631154    CHARACTER(LEN=*), INTENT(IN) :: field_name
     
    12651156
    12661157    REAL,DIMENSION(klon_mpi,SIZE(field,2)) :: buffer_omp
    1267     REAL :: Field3d(iim,jj_nb,SIZE(field,2))
     1158    REAL :: Field3d(nbp_lon,jj_nb,SIZE(field,2))
    12681159    INTEGER :: ip, n, nlev
    12691160    INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d
     
    12861177    !IF (.NOT.clef_stations(iff)) THEN
    12871178    IF(.TRUE.)THEN
    1288         ALLOCATE(index3d(iim*jj_nb*nlev))
    1289         ALLOCATE(fieldok(iim*jj_nb,nlev))
     1179        ALLOCATE(index3d(nbp_lon*jj_nb*nlev))
     1180        ALLOCATE(fieldok(nbp_lon*jj_nb,nlev))
    12901181        CALL xios_send_field(field_name, Field3d(:,:,1:nlev))
    12911182                       
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/o3_chem_m.F90

    r3816 r3819  
    1414
    1515    ! All the 2-dimensional arrays are on the partial "physics" grid.
    16     ! Their shape is "(/klon, llm/)".
     16    ! Their shape is "(/klon, klev/)".
    1717    ! Index "(i, :)" is for longitude "rlon(i)", latitude "rlat(i)".
    18 
    1918    use assert_m, only: assert
    20     use dimphy, only: klon
     19    use dimphy, only: klon,klev
    2120    use regr_pr_comb_coefoz_m, only: c_Mob, a4_mass, a2, r_het_interm
    2221   ! use comconst_phy_mod
     
    2524    integer, intent(in):: julien ! jour julien, 1 <= julien <= 360
    2625    real, intent(in):: gmtime ! heure de la journée en fraction de jour
    27     real, intent(in):: t_seri(:, :) ! (klon, llm) temperature, in K
     26    real, intent(in):: t_seri(:, :) ! (klon, klev) temperature, in K
    2827
    29     real, intent(in):: zmasse(:, :) ! (klon, llm)
     28    real, intent(in):: zmasse(:, :) ! (klon, klev)
    3029    ! (column-density of mass of air in a cell, in kg m-2)
    3130    ! "zmasse(:, k)" is for layer "k".)
     
    3635    ! (longitude and latitude of each horizontal position, in degrees)
    3736
    38     real, intent(inout):: q(:, :) ! (klon, llm) mass fraction of ozone
     37    real, intent(inout):: q(:, :) ! (klon, klev) mass fraction of ozone
    3938    ! "q(:, k)" is at middle of layer "k".)
    4039
    4140    ! Variables local to the procedure:
    42     include "dimensions.h"
    4341    ! (for "pi")
    4442    integer k
    4543
    46     real c(klon, llm)
     44    real c(klon, klev)
    4745    ! (constant term during a time step in the net mass production
    4846    ! rate of ozone by chemistry, per unit mass of air, in s-1)
    4947    ! "c(:, k)" is at middle of layer "k".)
    5048
    51     real b(klon, llm)
     49    real b(klon, klev)
    5250    ! (coefficient of "q" in the net mass production
    5351    ! rate of ozone by chemistry, per unit mass of air, in s-1)
    5452    ! "b(:, k)" is at middle of layer "k".)
    5553
    56     real dq_o3_chem(klon, llm)
     54    real dq_o3_chem(klon, klev)
    5755    ! (variation of ozone mass fraction due to chemistry during a time step)
    5856    ! "dq_o3_chem(:, k)" is at middle of layer "k".)
     
    7068    call assert(klon == (/size(q, 1), size(t_seri, 1), size(zmasse, 1), &
    7169         size(rlat), size(rlon)/), "o3_chem klon")
    72     call assert(llm == (/size(q, 2), size(t_seri, 2), size(zmasse, 2)/), &
    73          "o3_chem llm")
     70    call assert(klev == (/size(q, 2), size(t_seri, 2), size(zmasse, 2)/), &
     71         "o3_chem klev")
    7472
    7573    c = c_Mob + a4_mass * t_seri
     
    8785    call orbite(real(julien), earth_long, trash1)
    8886    call zenang(earth_long, gmtime, pdtphys, rlat, rlon, pmu0, trash2)
    89     forall (k = 1: llm)
     87    forall (k = 1: klev)
    9088       where (pmu0 <= cos(87. / 180. * pi)) b(:, k) = 0.
    9189    end forall
     
    113111
    114112    ! All the 2-dimensional arrays are on the partial "physics" grid.
    115     ! Their shape is "(/klon, llm/)".
     113    ! Their shape is "(/klon, klev/)".
    116114    ! Index "(i, :)" is for longitude "rlon(i)", latitude "rlat(i)".
    117115
    118116    use regr_pr_comb_coefoz_m, only: a6_mass
    119117    use assert_m, only: assert
    120     use dimphy, only: klon
     118    use dimphy, only: klon, klev
    121119
    122120    real, intent(in):: q(:, :) ! mass fraction of ozone
     
    137135    ! ("b(:, k)" is at middle of layer "k".)
    138136
    139     include "dimensions.h"
    140137
    141     real o3_prod(klon, llm)
     138    real o3_prod(klon, klev)
    142139    ! (net mass production rate of ozone by chemistry, per unit mass
    143140    ! of air, in s-1)
     
    146143    ! Variables local to the procedure:
    147144
    148     real sigma_mass(klon, llm)
     145    real sigma_mass(klon, klev)
    149146    ! (mass column-density of ozone above point, in kg m-2)
    150147    ! ("sigma_mass(:, k)" is at middle of layer "k".)
     
    156153    call assert(klon == (/size(q, 1), size(zmasse, 1), size(c, 1), &
    157154         size(b, 1)/), "o3_prod 1")
    158     call assert(llm == (/size(q, 2), size(zmasse, 2), size(c, 2), &
     155    call assert(klev == (/size(q, 2), size(zmasse, 2), size(c, 2), &
    159156         size(b, 2)/), "o3_prod 2")
    160157
     
    162159    ! "k", and, as a first approximation, take it as column-density
    163160    ! above the middle of layer "k":
    164     sigma_mass(:, llm) = zmasse(:, llm) * q(:, llm) ! top layer
    165     do k =  llm - 1, 1, -1
     161    sigma_mass(:, klev) = zmasse(:, klev) * q(:, klev) ! top layer
     162    do k =  klev - 1, 1, -1
    166163       sigma_mass(:, k) = sigma_mass(:, k+1) + zmasse(:, k) * q(:, k)
    167164    end do
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/pbl_surface_mod.F90

    r3818 r3819  
    263263  !  USE temps_phy_mod
    264264    USE inifis_mod, ONLY: annee_ref, day_ini, itau_phy, lunout, prt_level
    265     USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat
     265    USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, grid1dto2d_glo
    266266    IMPLICIT NONE
    267267
     
    793793          idayref = day_ini
    794794          CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
    795           CALL gr_fi_ecrit(1,klon,nbp_lon,nbp_lat,rlon,zx_lon)
     795          CALL grid1dTo2d_glo(rlon,zx_lon)
    796796          DO i = 1, nbp_lon
    797797             zx_lon(i,1) = rlon(i+1)
    798798             zx_lon(i,nbp_lat) = rlon(i+1)
    799799          ENDDO
    800           CALL gr_fi_ecrit(1,klon,nbp_lon,nbp_lat,rlat,zx_lat)
     800          CALL grid1dTo2d_glo(rlat,zx_lat)
    801801          CALL histbeg("sous_index",nbp_lon,zx_lon(:,1),nbp_lat,zx_lat(1,:), &
    802802               1,nbp_lon,1,nbp_lat, &
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phys_output_mod.F90

    r3817 r3819  
    3636    USE iophy
    3737    USE dimphy
     38    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    3839    USE infotrac_phy
    3940    USE ioipsl
     
    5657   
    5758    IMPLICIT NONE
    58     include "dimensions.h"
    5959    include "clesphys.h"
    6060    include "thermcell.h"
     
    7070    REAL, DIMENSION(klon, klev+1), INTENT(IN)   :: paprs
    7171    REAL, DIMENSION(klon,klev,nqtot), INTENT(IN):: qx, d_qx
    72     REAL, DIMENSION(klon, llm), INTENT(IN)      :: zmasse
     72    REAL, DIMENSION(klon, klev), INTENT(IN)      :: zmasse
    7373
    7474
     
    107107    CHARACTER(LEN=2)                      :: bb3
    108108    CHARACTER(LEN=6)                      :: type_ocean
    109     INTEGER, DIMENSION(iim*jjmp1)         ::  ndex2d
    110     INTEGER, DIMENSION(iim*jjmp1*klev)    :: ndex3d
     109    INTEGER, DIMENSION(nbp_lon*jjmp1)     ::  ndex2d
     110    INTEGER, DIMENSION(nbp_lon*jjmp1*klev)    :: ndex3d
    111111    INTEGER                               :: imin_ins, imax_ins
    112112    INTEGER                               :: jmin_ins, jmax_ins
     
    344344          IF (phys_out_regfkey(iff)) then
    345345             imin_ins=1
    346              imax_ins=iim
     346             imax_ins=nbp_lon
    347347             jmin_ins=1
    348348             jmax_ins=jjmp1
    349349
    350350             ! correction abderr       
    351              do i=1,iim
     351             do i=1,nbp_lon
    352352                WRITE(lunout,*)'io_lon(i)=',io_lon(i)
    353353                IF (io_lon(i).le.phys_out_lonmin(iff)) imin_ins=i
     
    368368                  io_lat(jmax_ins),io_lat(jmin_ins)
    369369
    370              CALL histbeg(phys_out_filenames(iff),iim,io_lon,jjmp1,io_lat, &
     370             CALL histbeg(phys_out_filenames(iff),nbp_lon,io_lon,jjmp1,io_lat, &
    371371                  imin_ins,imax_ins-imin_ins+1, &
    372372                  jmin_ins,jmax_ins-jmin_ins+1, &
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phys_output_write_mod.F90

    r3817 r3819  
    2525
    2626    USE dimphy, only: klon, klev, klevp1, nslay
     27    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    2728    !USE control_phy_mod, only: day_step, iphysiq
    2829    USE inifis_mod, only: day_step, iphysiq
     
    258259    INCLUDE "compbl.h"
    259260    INCLUDE "YOMCST.h"
    260     INCLUDE "dimensions.h"
    261261
    262262    ! Input
     
    273273    REAL, DIMENSION(klon, klev+1) :: paprs
    274274    REAL, DIMENSION(klon,klev,nqtot) :: qx, d_qx
    275     REAL, DIMENSION(klon, llm) :: zmasse
     275    REAL, DIMENSION(klon, klev) :: zmasse
    276276    LOGICAL :: flag_aerosol_strat
    277277    INTEGER :: flag_aerosol
     
    280280
    281281    ! Local
    282     INTEGER, PARAMETER :: jjmp1=jjm+1-1/jjm
    283282    INTEGER :: itau_w
    284283    INTEGER :: i, iinit, iinitend=1, iff, iq, nsrf, k, ll, naero
     
    287286    REAL, DIMENSION (klon,klev+1) :: zx_tmp_fi3d1
    288287    CHARACTER (LEN=4)              :: bb2
    289     INTEGER, DIMENSION(iim*jjmp1)  :: ndex2d
    290     INTEGER, DIMENSION(iim*jjmp1*klev) :: ndex3d
     288    INTEGER, DIMENSION(nbp_lon*nbp_lat)  :: ndex2d
     289    INTEGER, DIMENSION(nbp_lon*nbp_lat*klev) :: ndex3d
    291290    REAL, PARAMETER :: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2
    292291    REAL, PARAMETER :: missing_val=nf90_fill_real
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/physiq.F90

    r3818 r3819  
    1818  USE dimphy
    1919  USE infotrac_phy
    20   USE mod_grid_phy_lmdz
    2120  USE mod_phys_lmdz_para
    2221  USE iophy
     
    5150                        annee_ref, day_ref, itau_phy, jD_ref, start_time, &
    5251                        prt_level, lunout
    53   USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, nbp_lev
     52  USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, nbp_lev, grid1dTo2d_glo, klon_glo
    5453#ifdef REPROBUS
    5554  USE CHEM_REP, ONLY : Init_chem_rep_xjour
     
    42944293  RETURN
    42954294END FUNCTION qcheck
    4296 SUBROUTINE gr_fi_ecrit(nfield,nlon,iim,jjmp1,fi,ecrit)
    4297   IMPLICIT none
    4298   !
    4299   ! Tranformer une variable de la grille physique a
    4300   ! la grille d'ecriture
    4301   !
    4302   INTEGER nfield,nlon,iim,jjmp1, jjm
    4303   REAL fi(nlon,nfield), ecrit(iim*jjmp1,nfield)
    4304   !
    4305   INTEGER i, n, ig
    4306   !
    4307   jjm = jjmp1 - 1
    4308   DO n = 1, nfield
    4309      DO i=1,iim
    4310         ecrit(i,n) = fi(1,n)
    4311         ecrit(i+jjm*iim,n) = fi(nlon,n)
    4312      ENDDO
    4313      DO ig = 1, nlon - 2
    4314         ecrit(iim+ig,n) = fi(1+ig,n)
    4315      ENDDO
    4316   ENDDO
    4317   RETURN
    4318   END SUBROUTINE gr_fi_ecrit
    4319 
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/readaerosol.F90

    r3817 r3819  
    178178! 3) Read field month by month
    179179! 4) Close file 
    180 ! 5) Transform the global field from 2D(iim, jjp+1) to 1D(klon_glo)
     180! 5) Transform the global field from 2D(nbp_lon, jjp+1) to 1D(klon_glo)
    181181!     - Also the levels and the latitudes have to be inversed
    182182!
     
    194194
    195195    IMPLICIT NONE
    196      
    197     INCLUDE "dimensions.h"     
    198196
    199197! Input argumets
     
    223221    REAL, ALLOCATABLE, DIMENSION(:)       :: varktmp
    224222
    225     REAL, DIMENSION(iim,jjm+1,12)         :: psurf_glo2D   ! Surface pression for 12 months on dynamics global grid
     223    REAL, DIMENSION(nbp_lon,nbp_lat,12)   :: psurf_glo2D   ! Surface pression for 12 months on dynamics global grid
    226224    REAL, DIMENSION(klon_glo,12)          :: psurf_glo1D   ! -"- on physical global grid
    227     REAL, DIMENSION(iim,jjm+1,12)         :: load_glo2D    ! Load for 12 months on dynamics global grid
     225    REAL, DIMENSION(nbp_lon,nbp_lat,12)   :: load_glo2D    ! Load for 12 months on dynamics global grid
    228226    REAL, DIMENSION(klon_glo,12)          :: load_glo1D    ! -"- on physical global grid
    229     REAL, DIMENSION(iim,jjm+1)            :: vartmp
    230     REAL, DIMENSION(iim)                  :: lon_src              ! longitudes in file
    231     REAL, DIMENSION(jjm+1)                :: lat_src, lat_src_inv ! latitudes in file
     227    REAL, DIMENSION(nbp_lon,nbp_lat)      :: vartmp
     228    REAL, DIMENSION(nbp_lon)              :: lon_src              ! longitudes in file
     229    REAL, DIMENSION(nbp_lat)              :: lat_src, lat_src_inv ! latitudes in file
    232230    LOGICAL                               :: new_file             ! true if new file format detected
    233231    LOGICAL                               :: invert_lat           ! true if the field has to be inverted for latitudes
     
    267265
    268266       ! Invert source latitudes
    269        DO j = 1, jjm+1
    270           lat_src_inv(j) = lat_src(jjm+1 +1 -j)
     267       DO j = 1, nbp_lat
     268          lat_src_inv(j) = lat_src(nbp_lat +1 -j)
    271269       END DO
    272270
     
    313311       
    314312     ! Allocate variables depending on the number of vertical levels
    315        ALLOCATE(varmth(iim, jjm+1, klev_src), varyear(iim, jjm+1, klev_src, 12), stat=ierr)
     313       ALLOCATE(varmth(nbp_lon, nbp_lat, klev_src), varyear(nbp_lon, nbp_lat, klev_src, 12), stat=ierr)
    316314       IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 1',1)
    317315
     
    435433     
    436434
    437 ! 5) Transform the global field from 2D(iim, jjp+1) to 1D(klon_glo)
     435! 5) Transform the global field from 2D(nbp_lon, jjp+1) to 1D(klon_glo)
    438436!****************************************************************************************
    439437! Test if vertical levels have to be inversed
     
    448446             varmth(:,:,:) = varyear(:,:,:,imth) ! use varmth temporarly
    449447             DO k=1, klev_src
    450                 DO j=1, jjm+1
    451                    DO i=1,iim
     448                DO j=1, nbp_lat
     449                   DO i=1,nbp_lon
    452450                      varyear(i,j,k,imth) = varmth(i,j,klev_src+1-k)
    453451                   END DO
     
    482480             varmth(:,:,:) = varyear(:,:,:,imth) ! use varmth temporarly
    483481             DO k=1,klev_src
    484                 DO j=1,jjm+1
    485                    DO i=1,iim
    486                       varyear(i,j,k,imth) = varmth(i,jjm+1+1-j,k)
     482                DO j=1,nbp_lat
     483                   DO i=1,nbp_lon
     484                      varyear(i,j,k,imth) = varmth(i,nbp_lat+1-j,k)
    487485                   END DO
    488486                END DO
     
    491489             ! Invert latitudes for surface pressure
    492490             vartmp(:,:) = psurf_glo2D(:,:,imth)
    493              DO j=1, jjm+1
    494                 DO i=1,iim
    495                    psurf_glo2D(i,j,imth)= vartmp(i,jjm+1+1-j)
     491             DO j=1, nbp_lat
     492                DO i=1,nbp_lon
     493                   psurf_glo2D(i,j,imth)= vartmp(i,nbp_lat+1-j)
    496494                END DO
    497495             END DO
     
    499497             ! Invert latitudes for the load
    500498             vartmp(:,:) = load_glo2D(:,:,imth)
    501              DO j=1, jjm+1
    502                 DO i=1,iim
    503                    load_glo2D(i,j,imth)= vartmp(i,jjm+1+1-j)
     499             DO j=1, nbp_lat
     500                DO i=1,nbp_lon
     501                   load_glo2D(i,j,imth)= vartmp(i,nbp_lat+1-j)
    504502                END DO
    505503             END DO
     
    509507          DO k=1, klev_src
    510508             npole=0.  ! North pole, j=1
    511              spole=0.  ! South pole, j=jjm+1         
    512              DO i=1,iim
     509             spole=0.  ! South pole, j=nbp_lat         
     510             DO i=1,nbp_lon
    513511                npole = npole + varyear(i,1,k,imth)
    514                 spole = spole + varyear(i,jjm+1,k,imth)
     512                spole = spole + varyear(i,nbp_lat,k,imth)
    515513             END DO
    516              npole = npole/REAL(iim)
    517              spole = spole/REAL(iim)
     514             npole = npole/REAL(nbp_lon)
     515             spole = spole/REAL(nbp_lon)
    518516             varyear(:,1,    k,imth) = npole
    519              varyear(:,jjm+1,k,imth) = spole
     517             varyear(:,nbp_lat,k,imth) = spole
    520518          END DO
    521519       END DO ! imth
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/readaerosol_interp.F90

    r3817 r3819  
    2828  INCLUDE "chem.h"     
    2929  INCLUDE "clesphys.h"
    30   INCLUDE "dimensions.h"
    3130!
    3231! Input:
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/readaerosolstrato.F90

    r3809 r3819  
    66
    77    USE phys_cal_mod, ONLY : mth_cur
    8     USE mod_grid_phy_lmdz
     8    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, klon_glo, grid2dTo1d_glo
    99    USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
    1010    USE mod_phys_lmdz_para
     
    1717
    1818    include "YOMCST.h"
    19     include "dimensions.h"
    2019
    2120! Variable input
     
    8584    n_lat = size(latitude)
    8685    print *, 'LAT aerosol strato=', n_lat, latitude
    87     IF (n_lat.NE.jjm+1) THEN
    88        print *,'Le nombre de lat n est pas egal a jjm+1'
     86    IF (n_lat.NE.nbp_lat) THEN
     87       print *,'Le nombre de lat n est pas egal a nbp_lat'
    8988       STOP
    9089    ENDIF
     
    9493    n_lon = size(longitude)
    9594    print *, 'LON aerosol strato=', n_lon, longitude
    96     IF (n_lon.NE.iim) THEN
    97        print *,'Le nombre de lon n est pas egal a iim'
     95    IF (n_lon.NE.nbp_lon) THEN
     96       print *,'Le nombre de lon n est pas egal a nbp_lon'
    9897       STOP
    9998    ENDIF
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/readchlorophyll.F90

    r3809 r3819  
    2020
    2121    include "YOMCST.h"
    22     include "dimensions.h"
    2322
    2423! Variable input
     
    6261    n_lon = size(longitude)
    6362!    print *, 'LON chlorophyll=', n_lon, longitude
    64     IF (n_lon.NE.iim) THEN
    65        print *,'Le nombre de lon n est pas egal a iim'
     63    IF (n_lon.NE.nbp_lon) THEN
     64       print *,'Le nombre de lon n est pas egal a nbp_lon'
    6665       STOP
    6766    ENDIF
     
    7271    n_lat = size(latitude)
    7372!    print *, 'LAT chlorophyll=', n_lat, latitude
    74     IF (n_lat.NE.jjm+1) THEN
    75        print *,'Le nombre de lat n est pas egal a jjm+1'
     73    IF (n_lat.NE.nbp_lat) THEN
     74       print *,'Le nombre de lat n est pas egal a nbp_lat'
    7675       STOP
    7776    ENDIF
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_lat_time_climoz_m.F90

    r3816 r3819  
    6565    ! periodicity for interpolation at the beginning and at the end of the
    6666    ! year.
    67 
     67    use mod_grid_phy_lmdz, ONLY : nbp_lat
    6868    use regr1_step_av_m, only: regr1_step_av
    6969    use regr3_lint_m, only: regr3_lint
     
    8585    ! Variables local to the procedure:
    8686
    87     include "dimensions.h"
    88     ! (for "jjm")
    89 
    9087    integer n_plev ! number of pressure levels in the input data
    9188    integer n_lat ! number of latitudes in the input data
     
    118115
    119116    real, allocatable:: o3_regr_lat(:, :, :, :)
    120     ! (jjm + 1, n_plev, 0:13, read_climoz)
     117    ! (nbp_lat, n_plev, 0:13, read_climoz)
    121118    ! mean of "o3_in" over a latitude interval of LMDZ
    122119    ! First dimension is latitude interval.
    123120    ! The latitude interval for "o3_regr_lat(j,:, :, :)" contains "rlatu(j)".
    124     ! If "j" is between 2 and "jjm" then the interval is:
     121    ! If "j" is between 2 and "nbp_lat-1" then the interval is:
    125122    ! [rlatv(j), rlatv(j-1)]
    126     ! If "j" is 1 or "jjm + 1" then the interval is:
     123    ! If "j" is 1 or "nbp_lat" then the interval is:
    127124    ! [rlatv(1), pi / 2]
    128125    ! or:
    129     ! [- pi / 2, rlatv(jjm)]
     126    ! [- pi / 2, rlatv(nbp_lat-1)]
    130127    ! respectively.
    131128    ! "o3_regr_lat(:, k, :, :)" is for pressure level "plev(k)".
     
    135132
    136133    real, allocatable:: o3_out(:, :, :, :)
    137     ! (jjm + 1, n_plev, 360, read_climoz)
     134    ! (nbp_lat, n_plev, 360, read_climoz)
    138135    ! regridded ozone climatology
    139136    ! "o3_out(j, k, l, :)" is at latitude "rlatu(j)", pressure
     
    286283    call nf95_close(ncid_in)
    287284
    288     allocate(o3_regr_lat(jjm + 1, n_plev, 0:13, read_climoz))
    289     allocate(o3_out(jjm + 1, n_plev, 360, read_climoz))
     285    allocate(o3_regr_lat(nbp_lat, n_plev, 0:13, read_climoz))
     286    allocate(o3_out(nbp_lat, n_plev, 360, read_climoz))
    290287
    291288    ! Regrid in latitude:
     
    295292       print *, &
    296293            "Found 12 months in ozone climatologies, assuming periodicity..."
    297        o3_regr_lat(jjm+1:1:-1, :, 1:12, :) = regr1_step_av(o3_in, &
    298             xs=sin(lat_in_edg), xt=sin((/- pi / 2, rlatv(jjm:1:-1), pi / 2/)))
     294       o3_regr_lat(nbp_lat:1:-1, :, 1:12, :) = regr1_step_av(o3_in, &
     295            xs=sin(lat_in_edg), xt=sin((/- pi / 2, rlatv(nbp_lat-1:1:-1), pi / 2/)))
    299296       ! (invert order of indices in "o3_regr_lat" because "rlatu" is
    300297       ! in descending order)
     
    306303    else
    307304       print *, "Using 14 months in ozone climatologies..."
    308        o3_regr_lat(jjm+1:1:-1, :, :, :) = regr1_step_av(o3_in, &
    309             xs=sin(lat_in_edg), xt=sin((/- pi / 2, rlatv(jjm:1:-1), pi / 2/)))
     305       o3_regr_lat(nbp_lat:1:-1, :, :, :) = regr1_step_av(o3_in, &
     306            xs=sin(lat_in_edg), xt=sin((/- pi / 2, rlatv(nbp_lat-1:1:-1), pi / 2/)))
    310307       ! (invert order of indices in "o3_regr_lat" because "rlatu" is
    311308       ! in descending order)
     
    317314    ! Write to file:
    318315    do m = 1, read_climoz
    319        call nf95_put_var(ncid_out, varid_out(m), o3_out(jjm+1:1:-1, :, :, m))
     316       call nf95_put_var(ncid_out, varid_out(m), o3_out(nbp_lat:1:-1, :, :, m))
    320317       ! (The order of "rlatu" is inverted in the output file)
    321318    end do
     
    333330    ! dimensions and variables, and writes one of the coordinate variables.
    334331
     332    use mod_grid_phy_lmdz, ONLY : nbp_lat
    335333    use netcdf95, only: nf95_create, nf95_def_dim, nf95_def_var, &
    336334         nf95_put_att, nf95_enddef, nf95_copy_att, nf95_put_var
     
    349347    ! Variables local to the procedure:
    350348
    351     include "dimensions.h"
    352 
    353349    integer ncerr
    354350    integer dimid_rlatu, dimid_plev, dimid_time
     
    364360    call nf95_def_dim(ncid_out, "time", 360, dimid_time)
    365361    call nf95_def_dim(ncid_out, "plev", n_plev, dimid_plev)
    366     call nf95_def_dim(ncid_out, "rlatu", jjm + 1, dimid_rlatu)
     362    call nf95_def_dim(ncid_out, "rlatu", nbp_lat, dimid_rlatu)
    367363
    368364    ! Define coordinate variables:
     
    425421
    426422    ! Write one of the coordinate variables:
    427     call nf95_put_var(ncid_out, varid_rlatu, rlatu(jjm+1:1:-1) / pi * 180.)
     423    call nf95_put_var(ncid_out, varid_rlatu, rlatu(nbp_lat:1:-1) / pi * 180.)
    428424    ! (convert from rad to degrees and sort in ascending order)
    429425
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_lat_time_coefoz_m.F90

    r3816 r3819  
    4040    ! when we regrid in pressure).
    4141
     42    use mod_grid_phy_lmdz, ONLY : nbp_lat
    4243    use regr1_step_av_m, only: regr1_step_av
    4344    use regr3_lint_m, only: regr3_lint
     
    5152    ! Variables local to the procedure:
    5253
    53     include "dimensions.h"
    54     ! (for "jjm")
    55 
    5654    integer ncid_in, ncid_out ! NetCDF IDs for input and output files
    5755    integer n_plev ! number of pressure levels in the input data
     
    7371    ! level "plev(l)". "month" is between 1 and 12.)
    7472
    75     real, allocatable:: v_regr_lat(:, :, :) ! (jjm + 1, n_plev, 0:13)
     73    real, allocatable:: v_regr_lat(:, :, :) ! (nbp_lat, n_plev, 0:13)
    7674    ! (mean of a variable "v" over a latitude interval)
    7775    ! (First dimension is latitude interval.
    7876    ! The latitude interval for "v_regr_lat(j,:, :)" contains "rlatu(j)".
    79     ! If "j" is between 2 and "jjm" then the interval is:
     77    ! If "j" is between 2 and "nbp_lat-1" then the interval is:
    8078    ! [rlatv(j), rlatv(j-1)]
    81     ! If "j" is 1 or "jjm + 1" then the interval is:
     79    ! If "j" is 1 or "nbp_lat" then the interval is:
    8280    ! [rlatv(1), pi / 2]
    8381    ! or:
    84     ! [- pi / 2, rlatv(jjm)]
     82    ! [- pi / 2, rlatv(nbp_lat-1)]
    8583    ! respectively.
    8684    ! "v_regr_lat(:, l, :)" is for pressure level "plev(l)".
    8785    ! Last dimension is month number.)
    8886
    89     real, allocatable:: o3_par_out(:, :, :) ! (jjm + 1, n_plev, 360)
     87    real, allocatable:: o3_par_out(:, :, :) ! (nbp_lat, n_plev, 360)
    9088    ! (regridded ozone parameter)
    9189    ! ("o3_par_out(j, l, day)" is at latitude "rlatu(j)", pressure
     
    198196
    199197    allocate(o3_par_in(n_lat, n_plev, 12))
    200     allocate(v_regr_lat(jjm + 1, n_plev, 0:13))
    201     allocate(o3_par_out(jjm + 1, n_plev, 360))
     198    allocate(v_regr_lat(nbp_lat, n_plev, 0:13))
     199    allocate(o3_par_out(nbp_lat, n_plev, 360))
    202200
    203201    do i_v = 1, n_o3_param
     
    212210       ! We average with respect to sine of latitude, which is
    213211       ! equivalent to weighting by cosine of latitude:
    214        v_regr_lat(jjm+1:1:-1, :, 1:12) = regr1_step_av(o3_par_in, &
    215             xs=sin(lat_in_edg), xt=sin((/- pi / 2, rlatv(jjm:1:-1), pi / 2/)))
     212       v_regr_lat(nbp_lat:1:-1, :, 1:12) = regr1_step_av(o3_par_in, &
     213            xs=sin(lat_in_edg), xt=sin((/- pi / 2, rlatv(nbp_lat-1:1:-1), pi / 2/)))
    216214       ! (invert order of indices in "v_regr_lat" because "rlatu" is
    217215       ! in descending order)
     
    227225       ! Write to file:
    228226       call nf95_put_var(ncid_out, varid_out(i_v), &
    229             o3_par_out(jjm+1:1:-1, :, :))
     227            o3_par_out(nbp_lat:1:-1, :, :))
    230228       ! (The order of "rlatu" is inverted in the output file)
    231229    end do
     
    244242    ! dimensions and variables, and writes one of the coordinate variables.
    245243
     244    use mod_grid_phy_lmdz, ONLY : nbp_lat
    246245    use assert_eq_m, only: assert_eq
    247246
     
    260259    ! Variables local to the procedure:
    261260
    262     include "dimensions.h"
    263     ! (for "jjm")
    264261
    265262    integer ncerr
     
    279276    call nf95_def_dim(ncid_out, "time", 360, dimid_time)
    280277    call nf95_def_dim(ncid_out, "plev", n_plev, dimid_plev)
    281     call nf95_def_dim(ncid_out, "rlatu", jjm + 1, dimid_rlatu)
     278    call nf95_def_dim(ncid_out, "rlatu", nbp_lat, dimid_rlatu)
    282279
    283280    ! Define coordinate variables:
     
    329326
    330327    ! Write one of the coordinate variables:
    331     call nf95_put_var(ncid_out, varid_rlatu, rlatu(jjm+1:1:-1) / pi * 180.)
     328    call nf95_put_var(ncid_out, varid_rlatu, rlatu(nbp_lat:1:-1) / pi * 180.)
    332329    ! (convert from rad to degrees and sort in ascending order)
    333330
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_pr_av_m.F90

    r3809 r3819  
    3333    ! NetCDF variable.
    3434
    35     use dimphy, only: klon
     35    use dimphy, only: klon, klev
     36    use mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    3637    use netcdf95, only: nf95_inq_varid, handle_err
    3738    use netcdf, only: nf90_get_var
     
    5253    ! ascending order
    5354
    54     real, intent(in):: paprs(:, :) ! (klon, llm + 1)
     55    real, intent(in):: paprs(:, :) ! (klon, klev + 1)
    5556    ! (pression pour chaque inter-couche, en Pa)
    5657
    57     real, intent(out):: v3(:, :, :) ! (klon, llm, size(name))
     58    real, intent(out):: v3(:, :, :) ! (klon, klev, size(name))
    5859    ! regridded fields on the partial "physics" grid
    5960    ! "v3(i, k, l)" is at longitude "xlon(i)", latitude
     
    6364    ! Variables local to the procedure:
    6465
    65     include "dimensions.h"
    6666    integer varid, ncerr ! for NetCDF
    6767
    68     real  v1(iim, jjm + 1, size(press_in_edg) - 1, size(name))
     68    real  v1(nbp_lon, nbp_lat, size(press_in_edg) - 1, size(name))
    6969    ! input fields at day "julien", on the global "dynamics" horizontal grid
    7070    ! First dimension is for longitude.
     
    8484    !--------------------------------------------
    8585
    86     call assert(size(v3, 1) == klon, size(v3, 2) == llm, "regr_pr_av v3 klon")
     86    call assert(size(v3, 1) == klon, size(v3, 2) == klev, "regr_pr_av v3 klon")
    8787    n_var = assert_eq(size(name), size(v3, 3), "regr_pr_av v3 n_var")
    88     call assert(shape(paprs) == (/klon, llm+1/), "regr_pr_av paprs")
     88    call assert(shape(paprs) == (/klon, klev+1/), "regr_pr_av paprs")
    8989
    9090    !$omp master
     
    102102       ! Latitudes are in ascending order in the input file while
    103103       ! "rlatu" is in descending order so we need to invert order:
    104        v1(1, :, :, :) = v1(1, jjm+1:1:-1, :, :)
     104       v1(1, :, :, :) = v1(1, nbp_lat:1:-1, :, :)
    105105
    106106       ! Duplicate on all longitudes:
    107        v1(2:, :, :, :) = spread(v1(1, :, :, :), dim=1, ncopies=iim-1)
     107       v1(2:, :, :, :) = spread(v1(1, :, :, :), dim=1, ncopies=nbp_lon-1)
    108108    end if
    109109    !$omp end master
     
    113113    ! Regrid in pressure at each horizontal position:
    114114    do i = 1, klon
    115        v3(i, llm:1:-1, :) = regr1_step_av(v2(i, :, :), press_in_edg, &
    116             paprs(i, llm+1:1:-1))
     115       v3(i, klev:1:-1, :) = regr1_step_av(v2(i, :, :), press_in_edg, &
     116            paprs(i, klev+1:1:-1))
    117117       ! (invert order of indices because "paprs" is in descending order)
    118118    end do
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_pr_comb_coefoz_m.F90

    r3809 r3819  
    3939    ! It allocates module variables.
    4040
    41     use dimphy, only: klon
     41    use dimphy, only: klon, klev
    4242
    4343    ! Variables local to the procedure:
    44     include "dimensions.h"
    4544
    4645    !---------------------------------------
     
    4948    print *, "Call sequence information: alloc_coefoz"
    5049    !$omp end master
    51     allocate(c_Mob(klon, llm), a2(klon, llm), a4_mass(klon, llm))
    52     allocate(a6_mass(klon, llm), r_het_interm(klon, llm))
     50    allocate(c_Mob(klon, klev), a2(klon, klev), a4_mass(klon, klev))
     51    allocate(a6_mass(klon, klev), r_het_interm(klon, klev))
    5352
    5453  end subroutine alloc_coefoz
     
    7473    use netcdf, only: nf90_nowrite
    7574    use assert_m, only: assert
    76     use dimphy, only: klon
     75    use dimphy, only: klon, klev
    7776    use mod_phys_lmdz_mpi_data, only: is_mpi_root
    7877    use regr_pr_av_m, only: regr_pr_av
     
    8584    ! (latitude on the partial "physics" grid, in degrees)
    8685
    87     real, intent(in):: paprs(:, :) ! (klon, llm + 1)
     86    real, intent(in):: paprs(:, :) ! (klon, klev + 1)
    8887    ! (pression pour chaque inter-couche, en Pa)
    8988
    90     real, intent(in):: pplay(:, :) ! (klon, llm)
     89    real, intent(in):: pplay(:, :) ! (klon, klev)
    9190    ! (pression pour le mileu de chaque couche, en Pa)
    9291
    9392    ! Variables local to the procedure:
    9493
    95     include "dimensions.h"
    9694    integer ncid ! for NetCDF
    9795
    98     real coefoz(klon, llm, 7)
     96    real coefoz(klon, klev, 7)
    9997    ! (temporary storage for 7 ozone coefficients)
    10098    ! (On the partial "physics" grid.
     
    102100    ! middle of layer "k".)
    103101
    104     real a6(klon, llm)
     102    real a6(klon, klev)
    105103    ! (derivative of "P_net_Mob" with respect to column-density of ozone
    106104    ! above, in cm2 s-1)
     
    121119    call assert((/size(rlat), size(paprs, 1), size(pplay, 1)/) == klon, &
    122120         "regr_pr_comb_coefoz klon")
    123     call assert((/size(paprs, 2) - 1, size(pplay, 2)/) == llm, &
    124          "regr_pr_comb_coefoz llm")
     121    call assert((/size(paprs, 2) - 1, size(pplay, 2)/) == klev, &
     122         "regr_pr_comb_coefoz klev")
    125123
    126124    !$omp master
     
    150148    r_het_interm = coefoz(:, :, 7)
    151149    ! Heterogeneous chemistry is only at high latitudes:
    152     forall (k = 1: llm)
     150    forall (k = 1: klev)
    153151       where (abs(rlat) <= 45.) r_het_interm(:, k) = 0.
    154152    end forall
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_pr_int_m.F90

    r3809 r3819  
    2424    ! Regridding is by linear interpolation.
    2525
    26     use dimphy, only: klon
     26    use dimphy, only: klon, klev
     27    use mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    2728    use netcdf95, only: nf95_inq_varid, handle_err
    2829    use netcdf, only: nf90_get_var
     
    4142    ! (pressure level of input data, in Pa, in strictly ascending order)
    4243
    43     real, intent(in):: pplay(:, :) ! (klon, llm)
     44    real, intent(in):: pplay(:, :) ! (klon, klev)
    4445    ! (pression pour le mileu de chaque couche, en Pa)
    4546
     
    4748    ! (extra value of field at 0 pressure)
    4849
    49     real, intent(out):: v3(:, :) ! (klon, llm)
     50    real, intent(out):: v3(:, :) ! (klon, klev)
    5051    ! (regridded field on the partial "physics" grid)
    5152    ! ("v3(i, k)" is at longitude "xlon(i)", latitude
     
    5455    ! Variables local to the procedure:
    5556
    56     include "dimensions.h"
    5757    integer varid, ncerr ! for NetCDF
    5858
    59     real  v1(iim, jjm + 1, 0:size(plev))
     59    real  v1(nbp_lon, nbp_lat, 0:size(plev))
    6060    ! (input field at day "julien", on the global "dynamics" horizontal grid)
    6161    ! (First dimension is for longitude.
     
    7272    !--------------------------------------------
    7373
    74     call assert(shape(v3) == (/klon, llm/), "regr_pr_int v3")
    75     call assert(shape(pplay) == (/klon, llm/), "regr_pr_int pplay")
     74    call assert(shape(v3) == (/klon, klev/), "regr_pr_int v3")
     75    call assert(shape(pplay) == (/klon, klev/), "regr_pr_int pplay")
    7676
    7777    !$omp master
     
    8484       ! Latitudes are in ascending order in the input file while
    8585       ! "rlatu" is in descending order so we need to invert order:
    86        v1(1, :, 1:) = v1(1, jjm+1:1:-1, 1:)
     86       v1(1, :, 1:) = v1(1, nbp_lat:1:-1, 1:)
    8787
    8888       ! Complete "v1" with the value at 0 pressure:
     
    9090
    9191       ! Duplicate on all longitudes:
    92        v1(2:, :, :) = spread(v1(1, :, :), dim=1, ncopies=iim-1)
     92       v1(2:, :, :) = spread(v1(1, :, :), dim=1, ncopies=nbp_lon-1)
    9393    end if
    9494    !$omp end master
     
    9898    ! Regrid in pressure at each horizontal position:
    9999    do i = 1, klon
    100        v3(i, llm:1:-1) = regr1_lint(v2(i, :), (/0., plev/), pplay(i, llm:1:-1))
     100       v3(i, klev:1:-1) = regr1_lint(v2(i, :), (/0., plev/), pplay(i, klev:1:-1))
    101101       ! (invert order of indices because "pplay" is in descending order)
    102102    end do
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_pr_o3_m.F90

    r3816 r3819  
    2525    ! hPa and strictly increasing.
    2626
     27    use dimphy, ONLY : klon, klev
     28    use mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    2729    use netcdf95, only: nf95_open, nf95_close, nf95_inq_varid, handle_err
    2830    use netcdf, only:  nf90_nowrite, nf90_get_var
     
    3739    ! for interface "l")
    3840
    39     real, intent(out):: o3_mob_regr(:, :, :) ! (iim + 1, jjm + 1, llm)
     41    real, intent(out):: o3_mob_regr(:, :, :) ! (nbp_lon + 1, nbp_lat + 1, klev)
    4042    ! (ozone mole fraction from Mobidic adapted to the LMDZ grid)
    4143    ! ("o3_mob_regr(i, j, l)" is at longitude "rlonv(i)", latitude
     
    4446    ! Variables local to the procedure:
    4547
    46     include "dimensions.h"
    4748
    4849    integer ncid, varid, ncerr ! for NetCDF
    4950    integer i, j
    5051
    51     real r_mob(jjm + 1, size(press_in_edg) - 1)
     52    real r_mob(nbp_lat, size(press_in_edg) - 1)
    5253    ! (ozone mole fraction from Mobidic at day "dayref")
    5354    ! (r_mob(j, k) is at latitude "rlatu(j)", in pressure interval
     
    5758
    5859    print *, "Call sequence information: regr_pr_o3"
    59     call assert(shape(o3_mob_regr) == (/iim + 1, jjm + 1, llm/), &
     60    call assert(shape(o3_mob_regr) == (/nbp_lon + 1, nbp_lat, klev/), &
    6061         "regr_pr_o3 o3_mob_regr")
    61     call assert(shape(p3d) == (/iim + 1, jjm + 1, llm + 1/), "regr_pr_o3 p3d")
     62    call assert(shape(p3d) == (/nbp_lon + 1, nbp_lat, klev + 1/), "regr_pr_o3 p3d")
    6263
    6364    call nf95_open("coefoz_LMDZ.nc", nf90_nowrite, ncid)
     
    6970    ! Latitudes are in ascending order in the input file while
    7071    ! "rlatu" is in descending order so we need to invert order:
    71     r_mob = r_mob(jjm+1:1:-1, :)
     72    r_mob = r_mob(nbp_lat:1:-1, :)
    7273
    7374    call nf95_close(ncid)
     
    7677
    7778    ! Poles:
    78     do j = 1, jjm + 1, jjm
    79        o3_mob_regr(1, j, llm:1:-1) &
    80             = regr1_step_av(r_mob(j, :), press_in_edg, p3d(1, j, llm+1:1:-1))
     79    do j = 1, nbp_lat, nbp_lat-1
     80       o3_mob_regr(1, j, klev:1:-1) &
     81            = regr1_step_av(r_mob(j, :), press_in_edg, p3d(1, j, klev+1:1:-1))
    8182       ! (invert order of indices because "p3d" is in descending order)
    8283    end do
    8384
    8485    ! Other latitudes:
    85     do j = 2, jjm
    86        do i = 1, iim
    87           o3_mob_regr(i, j, llm:1:-1) &
     86    do j = 2, nbp_lat-1
     87       do i = 1, nbp_lon
     88          o3_mob_regr(i, j, klev:1:-1) &
    8889               = regr1_step_av(r_mob(j, :), press_in_edg, &
    89                p3d(i, j, llm+1:1:-1))
     90               p3d(i, j, klev+1:1:-1))
    9091             ! (invert order of indices because "p3d" is in descending order)
    9192       end do
     
    9394
    9495    ! Duplicate pole values on all longitudes:
    95     o3_mob_regr(2:, 1, :) = spread(o3_mob_regr(1, 1, :), dim=1, ncopies=iim)
    96     o3_mob_regr(2:, jjm + 1, :) &
    97          = spread(o3_mob_regr(1, jjm + 1, :), dim=1, ncopies=iim)
     96    o3_mob_regr(2:, 1, :) = spread(o3_mob_regr(1, 1, :), dim=1, ncopies=nbp_lon)
     97    o3_mob_regr(2:, nbp_lat, :) &
     98         = spread(o3_mob_regr(1, nbp_lat, :), dim=1, ncopies=nbp_lon)
    9899
    99100    ! Duplicate first longitude to last longitude:
    100     o3_mob_regr(iim + 1, 2:jjm, :) = o3_mob_regr(1, 2:jjm, :)
     101    o3_mob_regr(nbp_lon + 1, 2:nbp_lat-1, :) = o3_mob_regr(1, 2:nbp_lat-1, :)
    101102
    102103  end subroutine regr_pr_o3
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/thermcell_old.F90

    r3818 r3819  
    327327    ! print*,k,lmax(1,k)
    328328  END DO
    329   ! print*,'ZMAX ZMAX ZMAX ',zmax
    330   ! call dump2d(iim,jjm-1,zmax(2:ngrid-1),'ZMAX      ')
    331329
    332330  ! print*,'OKl336'
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/write_bilKP_ave.h

    r3809 r3819  
    1111      itau_w = itau_phy + itap + start_time * day_step / iphysiq
    1212c
    13 cym      CALL gr_fi_ecrit(klev, klon,iim,jjmp1, ue_lay,zx_tmp_3d)
    1413      CALL histwrite_phy(nid_bilKPave,"ue",itau_w,ue_lay)
    1514c
    16 cym      CALL gr_fi_ecrit(klev, klon,iim,jjmp1, ve_lay,zx_tmp_3d)
    1715      CALL histwrite_phy(nid_bilKPave,"ve",itau_w,ve_lay)
    1816c
    19 cym      CALL gr_fi_ecrit(klev, klon,iim,jjmp1, uq_lay,zx_tmp_3d)
    2017      CALL histwrite_phy(nid_bilKPave,"uq",itau_w,uq_lay)
    2118c
    22 cym      CALL gr_fi_ecrit(klev, klon,iim,jjmp1, vq_lay,zx_tmp_3d)
    2319      CALL histwrite_phy(nid_bilKPave,"vq",itau_w,vq_lay)
    2420c
    2521c Champs 3D:
    2622C
    27 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, t_seri, zx_tmp_3d)
    2823      CALL histwrite_phy(nid_bilKPave,"temp",itau_w,t_seri)
    2924c
    30 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, qx(1,1,ivap), zx_tmp_3d)
    3125      CALL histwrite_phy(nid_bilKPave,"ovap",itau_w,qx(:,:,ivap))
    3226c
    33 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, zphi, zx_tmp_3d)
    3427      CALL histwrite_phy(nid_bilKPave,"geop",itau_w,zphi)
    3528c
    36 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, u_seri, zx_tmp_3d)
    3729      CALL histwrite_phy(nid_bilKPave,"vitu",itau_w,u_seri)
    3830c
    39 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, v_seri, zx_tmp_3d)
    4031      CALL histwrite_phy(nid_bilKPave,"vitv",itau_w,v_seri)
    4132c
    42 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, omega, zx_tmp_3d)
    4333      CALL histwrite_phy(nid_bilKPave,"vitw",itau_w,omega)
    4434c
    45 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, pplay, zx_tmp_3d)
    4635      CALL histwrite_phy(nid_bilKPave,"pres",itau_w,pplay)
    4736c
    48 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, paprs, zx_tmp_3d)
    4937      CALL histwrite_phy(nid_bilKPave,"play",itau_w,paprs)
    5038c
    51 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, cldliq, zx_tmp_3d)
    5239      CALL histwrite_phy(nid_bilKPave,"oliq",itau_w,cldliq)
    5340c
    54 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_dyn, zx_tmp_3d)
    5541      CALL histwrite_phy(nid_bilKPave,"dtdyn",itau_w,d_t_dyn)
    5642c
    57 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_dyn, zx_tmp_3d)
    5843      CALL histwrite_phy(nid_bilKPave,"dqdyn",itau_w,d_q_dyn)
    5944c
    60 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_con, zx_tmp_3d)
    6145      CALL histwrite_phy(nid_bilKPave,"dtcon",itau_w,d_t_con)
    6246c
    63 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_u_con, zx_tmp_3d)
    6447      CALL histwrite_phy(nid_bilKPave,"ducon",itau_w,d_u_con)
    6548c
    66 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_v_con, zx_tmp_3d)
    6749      CALL histwrite_phy(nid_bilKPave,"dvcon",itau_w,d_v_con)
    6850c
    69 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_con, zx_tmp_3d)
    7051      CALL histwrite_phy(nid_bilKPave,"dqcon",itau_w,d_q_con)
    7152c
    72 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_lsc, zx_tmp_3d)
    7353      CALL histwrite_phy(nid_bilKPave,"dtlsc",itau_w,d_t_lsc)
    7454c
    75 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_lsc, zx_tmp_3d)
    7655      CALL histwrite_phy(nid_bilKPave,"dqlsc",itau_w,d_q_lsc)
    7756c
    78 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_vdf, zx_tmp_3d)
    7957      CALL histwrite_phy(nid_bilKPave,"dtvdf",itau_w,d_t_vdf)
    8058c
    81 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_vdf, zx_tmp_3d)
    8259      CALL histwrite_phy(nid_bilKPave,"dqvdf",itau_w,d_q_vdf)
    8360c
    84 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_ajs, zx_tmp_3d)
    8561      CALL histwrite_phy(nid_bilKPave,"dtajs",itau_w,d_t_ajs)
    8662c
    87 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_ajs, zx_tmp_3d)
    8863      CALL histwrite_phy(nid_bilKPave,"dqajs",itau_w,d_q_ajs)
    8964c
    90 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_eva, zx_tmp_3d)
    9165      CALL histwrite_phy(nid_bilKPave,"dteva",itau_w,d_t_eva)
    9266c
    93 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_eva, zx_tmp_3d)
    9467      CALL histwrite_phy(nid_bilKPave,"dqeva",itau_w,d_q_eva)
    9568c
    96 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, heat, zx_tmp_3d)
    9769      CALL histwrite_phy(nid_bilKPave,"dtswr",itau_w,heat)
    9870c
    99 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, heat0, zx_tmp_3d)
    10071      CALL histwrite_phy(nid_bilKPave,"dtsw0",itau_w,heat0)
    10172c
    102 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, cool, zx_tmp_3d)
    10373      CALL histwrite_phy(nid_bilKPave,"dtlwr",itau_w,cool)
    10474c
    105 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, cool0, zx_tmp_3d)
    10675      CALL histwrite_phy(nid_bilKPave,"dtlw0",itau_w,cool0)
    10776c
    108 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_u_vdf, zx_tmp_3d)
    10977      CALL histwrite_phy(nid_bilKPave,"duvdf",itau_w,d_u_vdf)
    11078c
    111 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_v_vdf, zx_tmp_3d)
    11279      CALL histwrite_phy(nid_bilKPave,"dvvdf",itau_w,d_v_vdf)
    11380c
     
    12289      ENDDO
    12390c
    124 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_u_oli, zx_tmp_3d)
    12591      CALL histwrite_phy(nid_bilKPave,"duoli",d_u_oli)
    12692c
    127 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_v_oli, zx_tmp_3d)
    12893      CALL histwrite_phy(nid_bilKPave,"dvoli",itau_w,d_v_oli)
    12994c
     
    13196      ENDIF
    13297C
    133 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_u, zx_tmp_3d)
    13498      CALL histwrite_phy(nid_bilKPave,"duphy",itau_w,d_u)
    13599c
    136 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_v, zx_tmp_3d)
    137100      CALL histwrite_phy(nid_bilKPave,"dvphy",itau_w,d_v)
    138101c
    139 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t, zx_tmp_3d)
    140102      CALL histwrite_phy(nid_bilKPave,"dtphy",itau_w,d_t)
    141103c
    142 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_qx(:,:,1),
    143 cymf     .zx_tmp_3d)
    144104      CALL histwrite_phy(nid_bilKPave,"dqphy",itau_w,d_qx(:,:,1))
    145105c
    146 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_qx(:,:,2),
    147 cym     .zx_tmp_3d)
    148106      CALL histwrite_phy(nid_bilKPave,"dqlphy",itau_w,d_qx(:,:,2))
    149107c
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/write_bilKP_ins.h

    r3809 r3819  
    1111c Champs 3D:
    1212c
    13 cym      CALL gr_fi_ecrit(klev, klon,iim,jjmp1, ue_lay,zx_tmp_3d)
    1413      CALL histwrite_phy(nid_bilKPins,"ue",itau_w,ue_lay)
    1514c
    16 cym      CALL gr_fi_ecrit(klev, klon,iim,jjmp1, ve_lay,zx_tmp_3d)
    1715      CALL histwrite_phy(nid_bilKPins,"ve",itau_w,ve_lay)
    1816c
    19 cym      CALL gr_fi_ecrit(klev, klon,iim,jjmp1, uq_lay,zx_tmp_3d)
    2017      CALL histwrite_phy(nid_bilKPins,"uq",itau_w,uq_lay)
    2118c
    22 cym      CALL gr_fi_ecrit(klev, klon,iim,jjmp1, vq_lay,zx_tmp_3d)
    2319      CALL histwrite_phy(nid_bilKPins,"vq",itau_w,vq_lay)
    2420c
    2521c Champs 3D:
    2622C
    27 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, t_seri, zx_tmp_3d)
    2823      CALL histwrite_phy(nid_bilKPins,"temp",itau_w,t_seri)
    2924c
    30 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, qx(1,1,ivap), zx_tmp_3d)
    3125      CALL histwrite_phy(nid_bilKPins,"ovap",itau_w,qx(:,:,ivap))
    3226c
    33 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, zphi, zx_tmp_3d)
    3427      CALL histwrite_phy(nid_bilKPins,"geop",itau_w,zphi)
    3528c
    36 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, u_seri, zx_tmp_3d)
    3729      CALL histwrite_phy(nid_bilKPins,"vitu",itau_w,u_seri)
    3830c
    39 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, v_seri, zx_tmp_3d)
    4031      CALL histwrite_phy(nid_bilKPins,"vitv",itau_w,v_seri)
    4132c
    42 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, omega, zx_tmp_3d)
    4333      CALL histwrite_phy(nid_bilKPins,"vitw",itau_w,omega)
    4434c
    45 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, pplay, zx_tmp_3d)
    4635      CALL histwrite_phy(nid_bilKPins,"pres",itau_w,pplay)
    4736c
    48 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, paprs, zx_tmp_3d)
    4937      CALL histwrite_phy(nid_bilKPins,"play",itau_w,paprs)
    5038c
    51 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, cldliq, zx_tmp_3d)
    5239      CALL histwrite_phy(nid_bilKPins,"oliq",itau_w,cldliq)
    5340c
    54 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_dyn, zx_tmp_3d)
    5541      CALL histwrite_phy(nid_bilKPins,"dtdyn",itau_w,d_t_dyn)
    5642c
    57 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_dyn, zx_tmp_3d)
    5843      CALL histwrite_phy(nid_bilKPins,"dqdyn",itau_w,d_q_dyn)
    5944c
    60 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_con, zx_tmp_3d)
    6145      CALL histwrite_phy(nid_bilKPins,"dtcon",itau_w,d_t_con)
    6246c
    63 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_u_con, zx_tmp_3d)
    6447      CALL histwrite_phy(nid_bilKPins,"ducon",itau_w,d_u_con)
    65 c
    66 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_v_con, zx_tmp_3d)
     48c => toi-même !
     49
    6750      CALL histwrite_phy(nid_bilKPins,"dvcon",itau_w,d_v_con)
    6851c
    69 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_con, zx_tmp_3d)
    7052      CALL histwrite_phy(nid_bilKPins,"dqcon",itau_w,d_q_con)
    7153c
    72 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_lsc, zx_tmp_3d)
    7354      CALL histwrite_phy(nid_bilKPins,"dtlsc",itau_w,d_t_lsc)
    7455c
    75 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_lsc, zx_tmp_3d)
    7656      CALL histwrite_phy(nid_bilKPins,"dqlsc",itau_w,d_q_lsc)
    7757c
    78 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_vdf, zx_tmp_3d)
    7958      CALL histwrite_phy(nid_bilKPins,"dtvdf",itau_w,d_t_vdf)
    8059c
    81 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_vdf, zx_tmp_3d)
    8260      CALL histwrite_phy(nid_bilKPins,"dqvdf",itau_w,d_q_vdf)
    8361c
    84 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_ajs, zx_tmp_3d)
    8562      CALL histwrite_phy(nid_bilKPins,"dtajs",itau_w,d_t_ajs)
    8663c
    87 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_ajs, zx_tmp_3d)
    8864      CALL histwrite_phy(nid_bilKPins,"dqajs",itau_w,d_q_ajs)
    8965c
    90 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_eva, zx_tmp_3d)
    9166      CALL histwrite_phy(nid_bilKPins,"dteva",itau_w,d_t_eva)
    9267c
    93 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_eva, zx_tmp_3d)
    9468      CALL histwrite_phy(nid_bilKPins,"dqeva",itau_w,d_q_eva)
    9569c
    96 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, heat, zx_tmp_3d)
    9770      CALL histwrite_phy(nid_bilKPins,"dtswr",itau_w,heat)
    9871c
    99 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, heat0, zx_tmp_3d)
    10072      CALL histwrite_phy(nid_bilKPins,"dtsw0",itau_w,heat0)
    10173c
    102 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, cool, zx_tmp_3d)
    10374      CALL histwrite_phy(nid_bilKPins,"dtlwr",itau_w,cool)
    10475c
    105 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, cool0, zx_tmp_3d)
    10676      CALL histwrite_phy(nid_bilKPins,"dtlw0",itau_w,cool0)
    10777c
    108 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_u_vdf, zx_tmp_3d)
    10978      CALL histwrite_phy(nid_bilKPins,"duvdf",itau_w,d_u_vdf)
    11079c
    111 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_v_vdf, zx_tmp_3d)
    11280      CALL histwrite_phy(nid_bilKPins,"dvvdf",itau_w,d_v_vdf)
    11381c
     
    12290      ENDDO
    12391c
    124 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_u_oli, zx_tmp_3d)
    12592      CALL histwrite_phy(nid_bilKPins,"duoli",itau_w,d_u_oli)
    12693c
    127 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_v_oli, zx_tmp_3d)
    12894      CALL histwrite_phy(nid_bilKPins,"dvoli",itau_w,d_v_oli)
    12995c
     
    13197      ENDIF
    13298C
    133 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_u, zx_tmp_3d)
    13499      CALL histwrite_phy(nid_bilKPins,"duphy",itau_w,d_u)
    135100c
    136 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_v, zx_tmp_3d)
    137101      CALL histwrite_phy(nid_bilKPins,"dvphy",itau_w,d_v)
    138102c
    139 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t, zx_tmp_3d)
    140103      CALL histwrite_phy(nid_bilKPins,"dtphy",itau_w,d_t)
    141104c
    142 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_qx(:,:,1),
    143 cym     .zx_tmp_3d)
    144105      CALL histwrite_phy(nid_bilKPins,"dqphy",itau_w,d_qx(:,:,1))
    145106c
    146 cym      CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_qx(:,:,2),
    147 cym     .zx_tmp_3d)
    148107      CALL histwrite_phy(nid_bilKPins,"dqlphy",itau_w,d_qx(:,:,2))
    149108c
     
    161120       IF(bb2.EQ."850") THEN
    162121c
    163 cym        CALL gr_fi_ecrit(1, klon,iim,jjmp1,usumSTD(:,k,1),zx_tmp_2d)
    164122        CALL histwrite_phy(nid_bilKPins,"u"//bb2,itau_w,usumSTD(:,k,1))
    165123c
    166 cym        CALL gr_fi_ecrit(1, klon,iim,jjmp1,vsumSTD(:,k,1),zx_tmp_2d)
    167124        CALL histwrite_phy(nid_bilKPins,"v"//bb2,itau_w,vsumSTD(:,k,1))
    168125c
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/write_histday_seri.h

    r3818 r3819  
    2424      zx_tmp_fi2d(1:klon)=moyglo
    2525!
    26       CALL gr_fi_ecrit(1, klon,nbp_lon,jjmp1, zx_tmp_fi2d,zx_tmp_2d)
     26      CALL grid1dTo2d_glo(zx_tmp_fi2d,zx_tmp_2d)
    2727      CALL histwrite(nid_day_seri,"bilTOA",itau_w, &
    2828                     zx_tmp_2d,nbp_lon*jjmp1,ndex2d)
     
    3333      zx_tmp_fi2d(1:klon)=moyglo
    3434!
    35       CALL gr_fi_ecrit(1, klon,nbp_lon,jjmp1, zx_tmp_fi2d,zx_tmp_2d)
     35      CALL grid1dTo2d_glo(zx_tmp_fi2d,zx_tmp_2d)
    3636      CALL histwrite(nid_day_seri,"bils",itau_w, &
    3737                     zx_tmp_2d,nbp_lon*jjmp1,ndex2d)
     
    4848      zx_tmp_fi2d(1:klon)=moyglo
    4949!
    50       CALL gr_fi_ecrit(1, klon,nbp_lon,jjmp1, zx_tmp_fi2d,zx_tmp_2d)
     50      CALL grid1dTo2d_glo(zx_tmp_fi2d,zx_tmp_2d)
    5151      CALL histwrite(nid_day_seri,"ecin",itau_w, &
    5252                     zx_tmp_2d,nbp_lon*jjmp1,ndex2d)
     
    129129!#endif     
    130130     
    131       CALL gr_fi_ecrit(1,klon,nbp_lon,jjmp1,airephy,zx_tmp_2d)
     131      CALL grid1dTo2d_glo(airephy,zx_tmp_2d)
    132132      airetot=0.
    133133!     DO j = 1, jjmp1
     
    160160!
    161161      zx_tmp_fi2d(1:klon)=aam/airetot
    162       CALL gr_fi_ecrit(1,klon,nbp_lon,jjmp1,zx_tmp_fi2d,zx_tmp_2d)
     162      CALL grid1dTo2d_glo(zx_tmp_fi2d,zx_tmp_2d)
    163163      CALL histwrite(nid_day_seri,"momang",itau_w,zx_tmp_2d, &
    164164                     nbp_lon*jjmp1,ndex2d)
    165165!
    166166      zx_tmp_fi2d(1:klon)=torsfc/airetot
    167       CALL gr_fi_ecrit(1,klon,nbp_lon,jjmp1,zx_tmp_fi2d,zx_tmp_2d)
     167      CALL grid1dTo2d_glo(zx_tmp_fi2d,zx_tmp_2d)
    168168      CALL histwrite(nid_day_seri,"torsfc",itau_w,zx_tmp_2d, &
    169169                     nbp_lon*jjmp1,ndex2d)
     
    175175      zx_tmp_fi2d(1:klon)=moyglo
    176176!
    177       CALL gr_fi_ecrit(1,klon,nbp_lon,jjmp1,zx_tmp_fi2d,zx_tmp_2d)
     177      CALL grid1dTo2d_glo(zx_tmp_fi2d,zx_tmp_2d)
    178178      CALL histwrite(nid_day_seri,"tamv",itau_w, &
    179179                     zx_tmp_2d,nbp_lon*jjmp1,ndex2d)
     
    184184      zx_tmp_fi2d(1:klon)=moyglo
    185185!
    186       CALL gr_fi_ecrit(1, klon,nbp_lon,jjmp1, zx_tmp_fi2d,zx_tmp_2d)
     186      CALL grid1dTo2d_glo(zx_tmp_fi2d,zx_tmp_2d)
    187187      CALL histwrite(nid_day_seri,"psol",itau_w, &
    188188                     zx_tmp_2d,nbp_lon*jjmp1,ndex2d)
     
    193193      zx_tmp_fi2d(1:klon)=moyglo
    194194!
    195       CALL gr_fi_ecrit(1, klon,nbp_lon,jjmp1, zx_tmp_fi2d,zx_tmp_2d)
     195      CALL grid1dTo2d_glo(zx_tmp_fi2d,zx_tmp_2d)
    196196      CALL histwrite(nid_day_seri,"evap",itau_w, &
    197197                     zx_tmp_2d,nbp_lon*jjmp1,ndex2d)
     
    237237      zx_tmp_fi2d(1:klon)=moyglo
    238238!
    239       CALL gr_fi_ecrit(1, klon,nbp_lon,jjmp1, zx_tmp_fi2d, zx_tmp_2d)
     239      CALL grid1dTo2d_glo(zx_tmp_fi2d,zx_tmp_2d)
    240240      CALL histwrite(nid_day_seri,"tsol_"//clnsurf(is_oce), &
    241241                     itau_w,zx_tmp_2d,nbp_lon*jjmp1,ndex2d)
Note: See TracChangeset for help on using the changeset viewer.