Changeset 2346


Ignore:
Timestamp:
Aug 21, 2015, 5:13:46 PM (9 years ago)
Author:
Ehouarn Millour
Message:

Physics/dynamics separation:

  • remove all references to dimensions.h from physics. nbp_lon (==iim) , nbp_lat (==jjm+1) and nbp_lev (==llm) from mod_grid_phy_lmdz should be used instead.
  • added module regular_lonlat_mod in phy_common to store information about the global (lon-lat) grid cell boundaries and centers.

EM

Location:
LMDZ5/trunk/libf
Files:
1 added
77 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3d/gcm.F90

    r2247 r2346  
    417417#ifdef CPP_PHYS
    418418     CALL iniphysiq(iim,jjm,llm,daysec,day_ini,dtphys/nsplit_phys, &
    419           rlatu,rlonv,aire,cu,cv,rad,g,r,cpp, &
     419          rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp, &
    420420          iflag_phys)
    421421#endif
  • LMDZ5/trunk/libf/dyn3dmem/gcm.F90

    r2263 r2346  
    401401#ifdef CPP_PHYS
    402402     CALL iniphysiq(iim,jjm,llm,daysec,day_ini,dtphys/nsplit_phys, &
    403           rlatu,rlonv,aire,cu,cv,rad,g,r,cpp, &
     403          rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp, &
    404404          iflag_phys)
    405405#endif
  • LMDZ5/trunk/libf/dyn3dpar/gcm.F

    r2239 r2346  
    407407#ifdef CPP_PHYS
    408408         CALL iniphysiq(iim,jjm,llm,daysec,day_ini,dtphys/nsplit_phys,
    409      &                rlatu,rlonv,aire,cu,cv,rad,g,r,cpp,
     409     &                rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp,
    410410     &                iflag_phys)
    411411#endif
  • LMDZ5/trunk/libf/dynlonlat_phylonlat/phydev/iniphysiq.F90

    r2320 r2346  
    22! $Id: iniphysiq.F 1403 2010-07-01 09:02:53Z fairhead $
    33!
    4 SUBROUTINE iniphysiq(iim,jjm,nlayer,punjours, pdayref,ptimestep,         &
    5                      rlatu,rlonv,aire,cu,cv,                            &
     4SUBROUTINE iniphysiq(iim,jjm,nlayer,punjours, pdayref,ptimestep, &
     5                     rlatu,rlatv,rlonu,rlonv,aire,cu,cv, &
    66                     prad,pg,pr,pcpp,iflag_phys)
    77  USE dimphy, ONLY: klev ! number of atmospheric levels
     
    2626  USE inifis_mod, ONLY: inifis
    2727  USE phyaqua_mod, ONLY: iniaqua
     28  USE regular_lonlat_mod, ONLY : init_regular_lonlat, &
     29                                 east, west, north, south, &
     30                                 north_east, north_west, &
     31                                 south_west, south_east
     32  USE nrtype, ONLY: pi
    2833  IMPLICIT NONE
    2934  !
     
    4550  INTEGER, INTENT (IN) :: jjm  ! number of atompsheric columns along latitudes
    4651  REAL, INTENT (IN) :: rlatu(jjm+1) ! latitudes of the physics grid
     52  REAL, INTENT (IN) :: rlatv(jjm) ! latitude boundaries of the physics grid
    4753  REAL, INTENT (IN) :: rlonv(iim+1) ! longitudes of the physics grid
     54  REAL, INTENT (IN) :: rlonu(iim+1) ! longitude boundaries of the physics grid
    4855  REAL, INTENT (IN) :: aire(iim+1,jjm+1) ! area of the dynamics grid (m2)
    4956  REAL, INTENT (IN) :: cu((iim+1)*(jjm+1)) ! cu coeff. (u_covariant = cu * u)
     
    5966  REAL :: total_area_phy, total_area_dyn
    6067
     68  ! boundaries, on global grid
     69  REAL,ALLOCATABLE :: boundslon_reg(:,:)
     70  REAL,ALLOCATABLE :: boundslat_reg(:,:)
    6171
    6272  ! global array, on full physics grid:
     
    7888  !call init_phys_lmdz(iim,jjm+1,llm,1,(/(jjm-1)*iim+2/))
    7989 
     90  ! init regular global longitude-latitude grid points and boundaries
     91  ALLOCATE(boundslon_reg(iim,2))
     92  ALLOCATE(boundslat_reg(jjm+1,2))
     93 
     94  DO i=1,iim
     95   boundslon_reg(i,east)=rlonu(i)
     96   boundslon_reg(i,west)=rlonu(i+1)
     97  ENDDO
     98
     99  boundslat_reg(1,north)= PI/2
     100  boundslat_reg(1,south)= rlatv(1)
     101  DO j=2,jjm
     102   boundslat_reg(j,north)=rlatv(j-1)
     103   boundslat_reg(j,south)=rlatv(j)
     104  ENDDO
     105  boundslat_reg(jjm+1,north)= rlatv(jjm)
     106  boundslat_reg(jjm+1,south)= -PI/2
     107
     108  ! Write values in module regular_lonlat_mod
     109  CALL init_regular_lonlat(iim,jjm+1, rlonv(1:iim), rlatu, &
     110                           boundslon_reg, boundslat_reg)
     111
    80112  ! Generate global arrays on full physics grid
    81113  ALLOCATE(latfi(klon_glo),lonfi(klon_glo),cufi(klon_glo),cvfi(klon_glo))
  • LMDZ5/trunk/libf/dynlonlat_phylonlat/phylmd/iniphysiq.F90

    r2343 r2346  
    33
    44
    5 SUBROUTINE iniphysiq(ii,jj,nlayer,punjours, pdayref,ptimestep,           &
    6                      rlatu,rlonv,aire,cu,cv,                             &
     5SUBROUTINE iniphysiq(ii,jj,nlayer,punjours, pdayref,ptimestep, &
     6                     rlatu,rlatv,rlonu,rlonv,aire,cu,cv,       &
    77                     prad,pg,pr,pcpp,iflag_phys)
    88  USE dimphy, ONLY: klev ! number of atmospheric levels
     
    3535  USE phystokenc_mod, ONLY: init_phystokenc
    3636  USE phyaqua_mod, ONLY: iniaqua
     37  USE regular_lonlat_mod, ONLY : init_regular_lonlat, &
     38                                 east, west, north, south, &
     39                                 north_east, north_west, &
     40                                 south_west, south_east
    3741  IMPLICIT NONE
    3842
     
    4448  include "dimensions.h"
    4549  include "comvert.h"
     50  include "comconst.h"
    4651  include "iniprint.h"
    4752  include "temps.h"
     
    5762  INTEGER, INTENT (IN) :: jj ! number of atompsheric columns along latitudes
    5863  REAL, INTENT (IN) :: rlatu(jj+1) ! latitudes of the physics grid
     64  REAL, INTENT (IN) :: rlatv(jj) ! latitude boundaries of the physics grid
    5965  REAL, INTENT (IN) :: rlonv(ii+1) ! longitudes of the physics grid
     66  REAL, INTENT (IN) :: rlonu(ii+1) ! longitude boundaries of the physics grid
    6067  REAL, INTENT (IN) :: aire(ii+1,jj+1) ! area of the dynamics grid (m2)
    6168  REAL, INTENT (IN) :: cu((ii+1)*(jj+1)) ! cu coeff. (u_covariant = cu * u)
     
    7178  REAL :: total_area_phy, total_area_dyn
    7279
     80  ! boundaries, on global grid
     81  REAL,ALLOCATABLE :: boundslon_reg(:,:)
     82  REAL,ALLOCATABLE :: boundslat_reg(:,:)
    7383
    7484  ! global array, on full physics grid:
     
    8797  !call init_phys_lmdz(ii,jj+1,llm,1,(/(jj-1)*ii+2/))
    8898 
     99  ! init regular global longitude-latitude grid points and boundaries
     100  ALLOCATE(boundslon_reg(ii,2))
     101  ALLOCATE(boundslat_reg(jj+1,2))
     102 
     103  DO i=1,ii
     104   boundslon_reg(i,east)=rlonu(i)
     105   boundslon_reg(i,west)=rlonu(i+1)
     106  ENDDO
     107
     108  boundslat_reg(1,north)= PI/2
     109  boundslat_reg(1,south)= rlatv(1)
     110  DO j=2,jj
     111   boundslat_reg(j,north)=rlatv(j-1)
     112   boundslat_reg(j,south)=rlatv(j)
     113  ENDDO
     114  boundslat_reg(jj+1,north)= rlatv(jj)
     115  boundslat_reg(jj+1,south)= -PI/2
     116
     117  ! Write values in module regular_lonlat_mod
     118  CALL init_regular_lonlat(ii,jj+1, rlonv(1:ii), rlatu, &
     119                           boundslon_reg, boundslat_reg)
     120
    89121  ! Generate global arrays on full physics grid
    90122  ALLOCATE(latfi(klon_glo),lonfi(klon_glo),cufi(klon_glo),cvfi(klon_glo))
  • LMDZ5/trunk/libf/dynlonlat_phylonlat/phymar/iniphysiq.F90

    r2242 r2346  
    22! $Id: iniphysiq.F 1403 2010-07-01 09:02:53Z fairhead $
    33!
    4 SUBROUTINE iniphysiq(iim,jjm,nlayer,punjours, pdayref,ptimestep,         &
    5                      rlatu,rlonv,aire,cu,cv,                             &
     4SUBROUTINE iniphysiq(iim,jjm,nlayer,punjours, pdayref,ptimestep, &
     5                     rlatu,rlatv,rlonu,rlonv,aire,cu,cv,         &
    66                     prad,pg,pr,pcpp,iflag_phys)
    77  USE dimphy, ONLY: klev ! number of atmospheric levels
     
    2323                       rcpp  ! specific heat of the atmosphere
    2424!  USE phyaqua_mod, ONLY: iniaqua
     25  USE regular_lonlat_mod, ONLY : init_regular_lonlat, &
     26                                 east, west, north, south, &
     27                                 north_east, north_west, &
     28                                 south_west, south_east
     29  USE nrtype, ONLY: pi
    2530  IMPLICIT NONE
    2631  !
     
    4247  INTEGER, INTENT (IN) :: jjm  ! number of atompsheric columns along latitudes
    4348  REAL, INTENT (IN) :: rlatu(jjm+1) ! latitudes of the physics grid
     49  REAL, INTENT (IN) :: rlatv(jjm) ! latitude boundaries of the physics grid
    4450  REAL, INTENT (IN) :: rlonv(iim+1) ! longitudes of the physics grid
     51  REAL, INTENT (IN) :: rlonu(iim+1) ! longitude boundaries of the physics grid
    4552  REAL, INTENT (IN) :: aire(iim+1,jjm+1) ! area of the dynamics grid (m2)
    4653  REAL, INTENT (IN) :: cu((iim+1)*(jjm+1)) ! cu coeff. (u_covariant = cu * u)
     
    5663  REAL :: total_area_phy, total_area_dyn
    5764
     65  ! boundaries, on global grid
     66  REAL,ALLOCATABLE :: boundslon_reg(:,:)
     67  REAL,ALLOCATABLE :: boundslat_reg(:,:)
    5868
    5969  ! global array, on full physics grid:
     
    7383  ENDIF
    7484
     85  ! init regular global longitude-latitude grid points and boundaries
     86  ALLOCATE(boundslon_reg(iim,2))
     87  ALLOCATE(boundslat_reg(jjm+1,2))
     88 
     89  DO i=1,iim
     90   boundslon_reg(i,east)=rlonu(i)
     91   boundslon_reg(i,west)=rlonu(i+1)
     92  ENDDO
     93
     94  boundslat_reg(1,north)= PI/2
     95  boundslat_reg(1,south)= rlatv(1)
     96  DO j=2,jjm
     97   boundslat_reg(j,north)=rlatv(j-1)
     98   boundslat_reg(j,south)=rlatv(j)
     99  ENDDO
     100  boundslat_reg(jjm+1,north)= rlatv(jjm)
     101  boundslat_reg(jjm+1,south)= -PI/2
     102
     103  ! Write values in module regular_lonlat_mod
     104  CALL init_regular_lonlat(iim,jjm+1, rlonv(1:iim), rlatu, &
     105                           boundslon_reg, boundslat_reg)
    75106
    76107  ! Generate global arrays on full physics grid
  • LMDZ5/trunk/libf/phylmd/aaam_bud.F90

    r2311 r2346  
    66
    77  USE dimphy
     8  USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat
    89  IMPLICIT NONE
    910  ! ======================================================================
     
    5859  ! ===================
    5960
    60   ! iim--common-I: Number of longitude intervals
    61   ! jjm--common-I: Number of latitude intervals
     61  ! nbp_lon--common-I: Number of longitude intervals
     62  ! (nbp_lat-1)--common-I: Number of latitude intervals
    6263  ! klon-common-I: Number of points seen by the physics
    63   ! iim*(jjm-1)+2 for instance
     64  ! nbp_lon*(nbp_lat-2)+2 for instance
    6465  ! klev-common-I: Number of vertical layers
    6566  ! ======================================================================
     
    8485  ! ======================================================================
    8586
    86   include "dimensions.h"
    87   ! cc#include "dimphy.h"
    88 
    8987  ! ARGUMENTS
    9088
     
    121119  ! PUT AAM QUANTITIES AT ZERO:
    122120
    123   IF (iim+1>801 .OR. jjm+1>401) THEN
     121  IF (nbp_lon+1>801 .OR. nbp_lat>401) THEN
    124122    abort_message = 'Pb de dimension dans aaam_bud'
    125123    CALL abort_physic(modname, abort_message, 1)
     
    129127  hadley = 1.E18
    130128  hadday = 1.E18*24.*3600.
    131   dlat = xpi/real(jjm)
    132   dlon = 2.*xpi/real(iim)
     129  dlat = xpi/real(nbp_lat-1)
     130  dlon = 2.*xpi/real(nbp_lon)
    133131
    134132  DO iax = 1, 3
     
    155153  zlat(1) = plat(l)*xpi/180.
    156154
    157   DO i = 1, iim + 1
     155  DO i = 1, nbp_lon + 1
    158156
    159157    zs(i, 1) = phis(l)/rg
     
    169167
    170168
    171   DO j = 2, jjm
     169  DO j = 2, nbp_lat-1
    172170
    173171    ! Values at Greenwich (Periodicity)
    174172
    175     zs(iim+1, j) = phis(l+1)/rg
    176     ps(iim+1, j) = p(l+1, 1)
    177     ssou(iim+1, j) = dragu(l+1) + liftu(l+1)
    178     ssov(iim+1, j) = dragv(l+1) + liftv(l+1)
    179     blsu(iim+1, j) = phyu(l+1) - dragu(l+1) - liftu(l+1)
    180     blsv(iim+1, j) = phyv(l+1) - dragv(l+1) - liftv(l+1)
    181     zlon(iim+1) = -plon(l+1)*xpi/180.
     173    zs(nbp_lon+1, j) = phis(l+1)/rg
     174    ps(nbp_lon+1, j) = p(l+1, 1)
     175    ssou(nbp_lon+1, j) = dragu(l+1) + liftu(l+1)
     176    ssov(nbp_lon+1, j) = dragv(l+1) + liftv(l+1)
     177    blsu(nbp_lon+1, j) = phyu(l+1) - dragu(l+1) - liftu(l+1)
     178    blsv(nbp_lon+1, j) = phyv(l+1) - dragv(l+1) - liftv(l+1)
     179    zlon(nbp_lon+1) = -plon(l+1)*xpi/180.
    182180    zlat(j) = plat(l+1)*xpi/180.
    183181
    184     ub(iim+1, j) = 0.
    185     vb(iim+1, j) = 0.
     182    ub(nbp_lon+1, j) = 0.
     183    vb(nbp_lon+1, j) = 0.
    186184    DO k = 1, nlev
    187       ub(iim+1, j) = ub(iim+1, j) + u(l+1, k)*(p(l+1,k)-p(l+1,k+1))/rg
    188       vb(iim+1, j) = vb(iim+1, j) + v(l+1, k)*(p(l+1,k)-p(l+1,k+1))/rg
    189     END DO
    190 
    191 
    192     DO i = 1, iim
     185      ub(nbp_lon+1, j) = ub(nbp_lon+1, j) + u(l+1, k)*(p(l+1,k)-p(l+1,k+1))/rg
     186      vb(nbp_lon+1, j) = vb(nbp_lon+1, j) + v(l+1, k)*(p(l+1,k)-p(l+1,k+1))/rg
     187    END DO
     188
     189
     190    DO i = 1, nbp_lon
    193191
    194192      l = l + 1
     
    215213  ! South Pole
    216214
    217   IF (jjm>1) THEN
     215  IF (nbp_lat-1>1) THEN
    218216    l = l + 1
    219     ub(1, jjm+1) = 0.
    220     vb(1, jjm+1) = 0.
     217    ub(1, nbp_lat) = 0.
     218    vb(1, nbp_lat) = 0.
    221219    DO k = 1, nlev
    222       ub(1, jjm+1) = ub(1, jjm+1) + u(l, k)*(p(l,k)-p(l,k+1))/rg
    223       vb(1, jjm+1) = vb(1, jjm+1) + v(l, k)*(p(l,k)-p(l,k+1))/rg
    224     END DO
    225     zlat(jjm+1) = plat(l)*xpi/180.
    226 
    227     DO i = 1, iim + 1
    228       zs(i, jjm+1) = phis(l)/rg
    229       ps(i, jjm+1) = p(l, 1)
    230       ssou(i, jjm+1) = dragu(l) + liftu(l)
    231       ssov(i, jjm+1) = dragv(l) + liftv(l)
    232       blsu(i, jjm+1) = phyu(l) - dragu(l) - liftu(l)
    233       blsv(i, jjm+1) = phyv(l) - dragv(l) - liftv(l)
    234       ub(i, jjm+1) = ub(1, jjm+1)
    235       vb(i, jjm+1) = vb(1, jjm+1)
     220      ub(1, nbp_lat) = ub(1, nbp_lat) + u(l, k)*(p(l,k)-p(l,k+1))/rg
     221      vb(1, nbp_lat) = vb(1, nbp_lat) + v(l, k)*(p(l,k)-p(l,k+1))/rg
     222    END DO
     223    zlat(nbp_lat) = plat(l)*xpi/180.
     224
     225    DO i = 1, nbp_lon + 1
     226      zs(i, nbp_lat) = phis(l)/rg
     227      ps(i, nbp_lat) = p(l, 1)
     228      ssou(i, nbp_lat) = dragu(l) + liftu(l)
     229      ssov(i, nbp_lat) = dragv(l) + liftv(l)
     230      blsu(i, nbp_lat) = phyu(l) - dragu(l) - liftu(l)
     231      blsv(i, nbp_lat) = phyv(l) - dragv(l) - liftv(l)
     232      ub(i, nbp_lat) = ub(1, nbp_lat)
     233      vb(i, nbp_lat) = vb(1, nbp_lat)
    236234    END DO
    237235  END IF
     
    240238  ! MOMENT ANGULAIRE
    241239
    242   DO j = 1, jjm
    243     DO i = 1, iim
     240  DO j = 1, nbp_lat-1
     241    DO i = 1, nbp_lon
    244242
    245243      raam(1) = raam(1) - rea**3*dlon*dlat*0.5*(cos(zlon(i))*sin(zlat(j))*cos &
     
    274272
    275273
    276   DO j = 1, jjm
    277     DO i = 1, iim
     274  DO j = 1, nbp_lat-1
     275    DO i = 1, nbp_lon
    278276      tmou(1) = tmou(1) - rea**2*dlon*0.5*sin(zlon(i))*(zs(i,j)-zs(i,j+1))*( &
    279277        cos(zlat(j+1))*ps(i,j+1)+cos(zlat(j))*ps(i,j))
     
    283281  END DO
    284282
    285   DO j = 2, jjm
    286     DO i = 1, iim
     283  DO j = 2, nbp_lat-1
     284    DO i = 1, nbp_lon
    287285      tmou(1) = tmou(1) + rea**2*dlat*0.5*sin(zlat(j))*(zs(i+1,j)-zs(i,j))*( &
    288286        cos(zlon(i+1))*ps(i+1,j)+cos(zlon(i))*ps(i,j))
     
    298296
    299297  l = 1
    300   DO j = 2, jjm
    301     DO i = 1, iim
     298  DO j = 2, nbp_lat-1
     299    DO i = 1, nbp_lon
    302300      l = l + 1
    303301      tsso(1) = tsso(1) - rea**3*cos(zlat(j))*dlon*dlat*ssou(i, j)*sin(zlat(j &
     
    341339100 FORMAT (F12.5, 15(1X,F12.5))
    342340
    343   ! write(iam+1,*)((zs(i,j),i=1,iim),j=1,jjm+1)
    344   ! write(iam+1,*)((ps(i,j),i=1,iim),j=1,jjm+1)
    345   ! write(iam+1,*)((ub(i,j),i=1,iim),j=1,jjm+1)
    346   ! write(iam+1,*)((vb(i,j),i=1,iim),j=1,jjm+1)
    347   ! write(iam+1,*)((ssou(i,j),i=1,iim),j=1,jjm+1)
    348   ! write(iam+1,*)((ssov(i,j),i=1,iim),j=1,jjm+1)
    349   ! write(iam+1,*)((blsu(i,j),i=1,iim),j=1,jjm+1)
    350   ! write(iam+1,*)((blsv(i,j),i=1,iim),j=1,jjm+1)
     341  ! write(iam+1,*)((zs(i,j),i=1,nbp_lon),j=1,nbp_lat)
     342  ! write(iam+1,*)((ps(i,j),i=1,nbp_lon),j=1,nbp_lat)
     343  ! write(iam+1,*)((ub(i,j),i=1,nbp_lon),j=1,nbp_lat)
     344  ! write(iam+1,*)((vb(i,j),i=1,nbp_lon),j=1,nbp_lat)
     345  ! write(iam+1,*)((ssou(i,j),i=1,nbp_lon),j=1,nbp_lat)
     346  ! write(iam+1,*)((ssov(i,j),i=1,nbp_lon),j=1,nbp_lat)
     347  ! write(iam+1,*)((blsu(i,j),i=1,nbp_lon),j=1,nbp_lat)
     348  ! write(iam+1,*)((blsv(i,j),i=1,nbp_lon),j=1,nbp_lat)
    351349
    352350  aam = raam(3)
  • LMDZ5/trunk/libf/phylmd/add_pbl_tend.F90

    r2235 r2346  
    1515  USE phys_local_var_mod
    1616  USE phys_state_var_mod
     17  USE mod_grid_phy_lmdz, ONLY: nbp_lev
    1718  IMPLICIT NONE
    18   include "dimensions.h"
    19   REAL hthturb_gcssold(llm)
    20   REAL hqturb_gcssold(llm)
    21   REAL dtime_frcg
     19  REAL,SAVE,ALLOCATABLE :: hthturb_gcssold(:)
     20  REAL,SAVE,ALLOCATABLE :: hqturb_gcssold(:)
     21!$OMP THREADPRIVATE(hthturb_gcssold,hqturb_gcssold)
     22  REAL,SAVE :: dtime_frcg
     23  LOGICAL,SAVE :: turb_fcg_gcssold
     24  LOGICAL,SAVE :: firstcall=.true.
     25!$OMP THREADPRIVATE(firstcall,turb_fcg_gcssold,dtime_frcg)
    2226  INTEGER abortphy
    23   LOGICAL turb_fcg_gcssold
    24   COMMON /turb_forcing/dtime_frcg, hthturb_gcssold, hqturb_gcssold, &
    25     turb_fcg_gcssold
     27!  COMMON /turb_forcing/dtime_frcg, hthturb_gcssold, hqturb_gcssold, &
     28!    turb_fcg_gcssold
    2629
    2730  ! Arguments :
     
    3639  REAL zzdt(klon, klev), zzdq(klon, klev)
    3740  INTEGER i, k
     41
     42  IF (firstcall) THEN
     43    ALLOCATE(hthturb_gcssold(nbp_lev))
     44    ALLOCATE(hqturb_gcssold(nbp_lev))
     45    firstcall=.false.
     46  ENDIF
    3847
    3948  IF (turb_fcg_gcssold) THEN
  • LMDZ5/trunk/libf/phylmd/aeropt.F90

    r2311 r2346  
    1010
    1111
    12   ! ym#include "dimensions.h"
    13   ! ym#include "dimphy.h"
    1412  include "YOMCST.h"
    1513
  • LMDZ5/trunk/libf/phylmd/ajsec.F90

    r1992 r2346  
    1414  ! d_t-----output-R-Incrementation de la temperature
    1515  ! ======================================================================
    16   ! ym#include "dimensions.h"
    17   ! ym#include "dimphy.h"
    1816  include "YOMCST.h"
    1917  REAL paprs(klon, klev+1), pplay(klon, klev)
     
    168166  ! d_t-----output-R-Incrementation de la temperature
    169167  ! ======================================================================
    170   ! ym#include "dimensions.h"
    171   ! ym#include "dimphy.h"
    172168  include "YOMCST.h"
    173169  REAL paprs(klon, klev+1), pplay(klon, klev)
     
    319315  ! d_t-----output-R-Incrementation de la temperature
    320316  ! ======================================================================
    321   ! ym#include "dimensions.h"
    322   ! ym#include "dimphy.h"
    323317  include "YOMCST.h"
    324318  REAL paprs(klon, klev+1), pplay(klon, klev)
  • LMDZ5/trunk/libf/phylmd/albedo.F90

    r2322 r2346  
    1919    ! albedo (out,R): albedo obtenu (de 0 a 1)
    2020    ! ======================================================================
    21     ! ym#include "dimensions.h"
    22     ! ym#include "dimphy.h"
    2321    include "YOMCST.h"
    2422    include "clesphys.h"
  • LMDZ5/trunk/libf/phylmd/atm2geo.F90

    r1907 r2346  
    66  USE mod_phys_lmdz_para
    77  IMPLICIT NONE
    8   INCLUDE 'dimensions.h'
    98  INCLUDE 'YOMCST.h'
    109!
  • LMDZ5/trunk/libf/phylmd/calltherm.F90

    r2311 r2346  
    2424
    2525      implicit none
    26 #include "dimensions.h"
    27 !#include "dimphy.h"
    28 #include "thermcell.h"
     26      include "thermcell.h"
    2927
    3028
  • LMDZ5/trunk/libf/phylmd/calwake.F90

    r2159 r2346  
    2222  IMPLICIT NONE
    2323  ! ======================================================================
    24   include "dimensions.h"
    25   ! #include "dimphy.h"
    2624  include "YOMCST.h"
    2725
  • LMDZ5/trunk/libf/phylmd/cfmip_point_locations.F90

    r1907 r2346  
    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
  • LMDZ5/trunk/libf/phylmd/conccm.F90

    r1992 r2346  
    1212  ! (schema standard du modele NCAR CCM2)
    1313  ! ======================================================================
    14   ! ym#include "dimensions.h"
    15   ! ym#include "dimphy.h"
    1614  include "YOMCST.h"
    1715  include "YOETHF.h"
     
    160158  ! simplifier la lecture et la comprehension.
    161159  ! -----------------------------------------------------------------------
    162   ! ym#include "dimensions.h"
    163   ! ym#include "dimphy.h"
    164160  INTEGER pcnst ! nombre de traceurs passifs
    165161  PARAMETER (pcnst=1)
  • LMDZ5/trunk/libf/phylmd/concvl.F90

    r2320 r2346  
    8484
    8585  include "clesphys.h"
    86   include "dimensions.h"
    8786
    8887  INTEGER iflag_clos
  • LMDZ5/trunk/libf/phylmd/conema3.F90

    r2320 r2346  
    5353  ! ======================================================================
    5454
    55   include "dimensions.h"
    5655  include "conema3.h"
    5756  INTEGER i, l, m, itra
  • LMDZ5/trunk/libf/phylmd/conemav.F90

    r2320 r2346  
    4141  ! Ice_flag-input-L-TRUE->prise en compte de la thermodynamique de la glace
    4242  ! ======================================================================
    43 
    44   include "dimensions.h"
    4543
    4644
  • LMDZ5/trunk/libf/phylmd/conflx.F90

    r2311 r2346  
    1616  ! et lessivage des traceurs passifs.
    1717  ! ======================================================================
    18   ! yminclude "dimensions.h"
    19   ! yminclude "dimphy.h"
    2018  include "YOMCST.h"
    2119  include "YOETHF.h"
     
    210208  IMPLICIT NONE
    211209  ! ------------------------------------------------------------------
    212   ! yminclude "dimensions.h"
    213   ! yminclude "dimphy.h"
    214210  include "YOMCST.h"
    215211  include "YOETHF.h"
     
    489485  ! AND INITIALIZES VALUES FOR UPDRAFTS
    490486  ! ----------------------------------------------------------------------
    491   ! yminclude "dimensions.h"
    492   ! yminclude "dimphy.h"
    493487  include "YOMCST.h"
    494488  include "YOETHF.h"
     
    619613  ! (NON ENTRAINING PLUME,I.E.CONSTANT MASSFLUX)
    620614  ! ----------------------------------------------------------------------
    621   ! yminclude "dimensions.h"
    622   ! yminclude "dimphy.h"
    623615  include "YOMCST.h"
    624616  include "YOETHF.h"
     
    696688  ! FOR CUMULUS PARAMETERIZATION
    697689  ! ----------------------------------------------------------------------
    698   ! yminclude "dimensions.h"
    699   ! yminclude "dimphy.h"
    700690  include "YOMCST.h"
    701691  include "YOETHF.h"
     
    998988  ! FLUXES IN THE CLOUD LAYER AND IN THE SUBCLOUD LAYER
    999989  ! ----------------------------------------------------------------------
    1000   ! yminclude "dimensions.h"
    1001   ! yminclude "dimphy.h"
    1002990  include "YOMCST.h"
    1003991  include "YOETHF.h"
     
    12421230  ! calculer les tendances T et Q
    12431231  ! ----------------------------------------------------------------------
    1244   ! yminclude "dimensions.h"
    1245   ! yminclude "dimphy.h"
    12461232  include "YOMCST.h"
    12471233  include "YOETHF.h"
     
    13191305  ! MOIST ENVIRONMENTAL AIR AND CLOUD AIR.
    13201306  ! ----------------------------------------------------------------------
    1321   ! yminclude "dimensions.h"
    1322   ! yminclude "dimphy.h"
    13231307  include "YOMCST.h"
    13241308  include "YOETHF.h"
     
    14281412
    14291413  ! ----------------------------------------------------------------------
    1430   ! yminclude "dimensions.h"
    1431   ! yminclude "dimphy.h"
    14321414  include "YOMCST.h"
    14331415  include "YOETHF.h"
     
    15351517  ! kcall=2  EVAPORATION IN DOWNDRAFTS (E.G. CUDLFS,CUDDRAF)
    15361518
    1537   ! yminclude "dimensions.h"
    1538   ! yminclude "dimphy.h"
    15391519  include "YOMCST.h"
    15401520
  • LMDZ5/trunk/libf/phylmd/conlmd.F90

    r1992 r2346  
    1111  ! Ajustement humide (Manabe) + Ajustement convectif (Kuo)
    1212  ! ======================================================================
    13   ! ym#include "dimensions.h"
    14   ! ym#include "dimphy.h"
    1513  include "YOMCST.h"
    1614  include "YOETHF.h"
     
    105103  ! du modele.
    106104  ! ======================================================================
    107   ! ym#include "dimensions.h"
    108   ! ym#include "dimphy.h"
    109105  include "YOMCST.h"
    110106
     
    310306  ! et itop est le haut du plus haut bloc
    311307  ! ======================================================================
    312   ! ym#include "dimensions.h"
    313   ! ym#include "dimphy.h"
    314308  include "YOMCST.h"
    315309
     
    10591053  ! N.B. version vectorielle (le 6 oct. 1997)
    10601054  ! ======================================================================
    1061   ! ym#include "dimensions.h"
    1062   ! ym#include "dimphy.h"
    10631055  include "YOMCST.h"
    10641056
     
    15781570  ! kcbot---output-I- Niveau du bas de la convection
    15791571  ! ======================================================================
    1580   ! ym#include "dimensions.h"
    1581   ! ym#include "dimphy.h"
    15821572  include "YOMCST.h"
    15831573  include "YOETHF.h"
     
    16821672  ! KCALL=2  EVAPORATION IN DOWNDRAFTS (E.G. CUDLFS,CUDDRAF)
    16831673
    1684   ! ym#include "dimensions.h"
    1685   ! ym#include "dimphy.h"
    16861674  include "YOMCST.h"
    16871675
     
    17771765  ! Ajustement humide (Schema de convection de Manabe)
    17781766  ! .
    1779   ! ym#include "dimensions.h"
    1780   ! ym#include "dimphy.h"
    17811767  include "YOMCST.h"
    17821768
     
    20622048  IMPLICIT NONE
    20632049
    2064   ! ym#include "dimensions.h"
    2065   ! ym#include "dimphy.h"
    20662050  include "YOMCST.h"
    20672051
  • LMDZ5/trunk/libf/phylmd/convect1.F90

    r1992 r2346  
    111111  USE dimphy
    112112  IMPLICIT NONE
    113 
    114   ! ym#include "dimensions.h"
    115   ! ym#include "dimphy.h"
    116113
    117114  INTEGER len
  • LMDZ5/trunk/libf/phylmd/convect2.F90

    r2110 r2346  
    150150  USE dimphy
    151151  IMPLICIT NONE
    152 
    153   ! ym#include "dimensions.h"
    154   ! ym#include "dimphy.h"
    155152
    156153  INTEGER kmax2, imax2, kmin2, imin2
  • LMDZ5/trunk/libf/phylmd/convect3.F90

    r2320 r2346  
    1818  USE infotrac_phy, ONLY: nbtr
    1919  IMPLICIT NONE
    20   include "dimensions.h"
    2120  INTEGER na
    2221  PARAMETER (na=60)
  • LMDZ5/trunk/libf/phylmd/cv_driver.F90

    r1992 r2346  
    9595
    9696
    97   ! ym#include "dimensions.h"
    98   ! ym#include "dimphy.h"
    99 
    10097  ! Input
    10198  INTEGER len
  • LMDZ5/trunk/libf/phylmd/cva_driver.F90

    r2311 r2346  
    160160
    161161
    162   include "dimensions.h"
    163 !!!!!#include "dimphy.h"
    164162
    165163! Input
  • LMDZ5/trunk/libf/phylmd/diagphy.F90

    r1992 r2346  
    5050  IMPLICIT NONE
    5151
    52   include "dimensions.h"
    53   ! cccc#include "dimphy.h"
    5452  include "YOMCST.h"
    5553  include "YOETHF.h"
     
    209207  IMPLICIT NONE
    210208
    211   include "dimensions.h"
    212   ! ccccc#include "dimphy.h"
    213209  include "YOMCST.h"
    214210  include "YOETHF.h"
  • LMDZ5/trunk/libf/phylmd/fisrtilp.F90

    r2343 r2346  
    2323  !======================================================================
    2424  !======================================================================
    25   !ym include "dimensions.h"
    26   !ym include "dimphy.h"
    2725  include "YOMCST.h"
    2826  include "fisrtilp.h"
  • LMDZ5/trunk/libf/phylmd/fisrtilp_tr.F90

    r2343 r2346  
    1919  ! ======================================================================
    2020  ! ======================================================================
    21   ! ym#include "dimensions.h"
    22   ! ym#include "dimphy.h"
    2321  include "YOMCST.h"
    2422
  • LMDZ5/trunk/libf/phylmd/flxtr.F90

    r1992 r2346  
    2525  ! =====================================================================
    2626
    27   ! ym#include "dimensions.h"
    28   ! ym#include "dimphy.h"
    2927  include "YOMCST.h"
    3028  include "YOECUMF.h"
  • LMDZ5/trunk/libf/phylmd/fonte_neige_mod.F90

    r2311 r2346  
    141141!   evap
    142142!
    143   INCLUDE "dimensions.h"
    144143  INCLUDE "YOETHF.h"
    145144  INCLUDE "YOMCST.h"
  • LMDZ5/trunk/libf/phylmd/geo2atm.F90

    r1907 r2346  
    77
    88  IMPLICIT NONE
    9   INCLUDE 'dimensions.h'
    109  INCLUDE 'YOMCST.h'
    1110
  • LMDZ5/trunk/libf/phylmd/grid_noro_m.F90

    r2311 r2346  
    4848  USE print_control_mod, ONLY: lunout
    4949  IMPLICIT NONE
    50 !  include "dimensions.h"
    5150  REAL, PARAMETER :: epsfra = 1.e-5
    5251!-------------------------------------------------------------------------------
  • LMDZ5/trunk/libf/phylmd/hbtm.F90

    r1992 r2346  
    4141
    4242
    43   ! ym#include "dimensions.h"
    44   ! ym#include "dimphy.h"
    4543  include "YOMCST.h"
    4644  REAL rlvcp, reps
  • LMDZ5/trunk/libf/phylmd/hbtm2l.F90

    r2159 r2346  
    2929  ! * re-ecriture complete Alain Mars 2012 dans LMDZ5V5           *
    3030  ! ***************************************************************
    31   ! ym#include "dimensions.h"
    32   ! ym#include "dimphy.h"
    3331  include "YOMCST.h"
    3432  REAL rlvcp, reps
  • LMDZ5/trunk/libf/phylmd/hgardfou.F90

    r2311 r2346  
    1010  ! Verifier la temperature
    1111  ! ======================================================================
    12   include "dimensions.h"
    1312  include "YOMCST.h"
    1413  REAL t(klon, klev), tsol(klon, nbsrf)
  • LMDZ5/trunk/libf/phylmd/hines_gwd.F90

    r2197 r2346  
    1616  IMPLICIT NONE
    1717
    18   ! ym#include "dimensions.h"
    19   ! ym#include "dimphy.h"
    2018  include "YOEGWD.h"
    2119  include "YOMCST.h"
  • LMDZ5/trunk/libf/phylmd/histo_o500_pctau.F90

    r1992 r2346  
    88  INTEGER :: ij, k, l, nw
    99  INTEGER :: nreg, nbreg
    10   ! ym#include "dimensions.h"
    11   ! ym#include "dimphy.h"
    1210  INTEGER, PARAMETER :: kmax = 8, lmax = 8
    1311  INTEGER, PARAMETER :: kmaxm1 = kmax - 1, lmaxm1 = lmax - 1
  • LMDZ5/trunk/libf/phylmd/homogene.F90

    r1992 r2346  
    1818  ! dv:   output, incrementation pour v
    1919  ! ==============================================================
    20   ! ym#include "dimensions.h"
    21   ! ym#include "dimphy.h"
    2220
    2321  REAL paprs(klon, klev+1)
  • LMDZ5/trunk/libf/phylmd/hydrol.F90

    r1992 r2346  
    2525  ! snow: couverture neigeuse
    2626
    27   ! ym#include "dimensions.h"
    28   ! ym#include "dimphy.h"
    2927  include "YOMCST.h"
    3028
  • LMDZ5/trunk/libf/phylmd/ini_undefSTD.F90

    r1992 r2346  
    3131  ! ====================================================================
    3232
    33   ! ym #include "dimensions.h"
    34   ! ym      integer jjmp1
    35   ! ym      parameter (jjmp1=jjm+1-1/jjm)
    3633  ! ym #include "dimphy.h"
    3734  ! variables Input/Output
  • LMDZ5/trunk/libf/phylmd/iophy.F90

    r2344 r2346  
    5454#endif
    5555  IMPLICIT NONE
    56 !  INCLUDE 'dimensions.h'
    5756    REAL,DIMENSION(klon),INTENT(IN) :: rlon
    5857    REAL,DIMENSION(klon),INTENT(IN) :: rlat
  • LMDZ5/trunk/libf/phylmd/lsc_scav.F90

    r2320 r2346  
    2424!=====================================================================
    2525
    26   include "dimensions.h"
    2726  include "chem.h"
    2827  include "YOMCST.h"
  • LMDZ5/trunk/libf/phylmd/moy_undefSTD.F90

    r2313 r2346  
    3535  ! NB: mettre "inst(X)" dans le write_hist*NMC.h !
    3636  ! ====================================================================
    37   ! ym#include "dimensions.h"
    38   ! ym      integer jjmp1
    39   ! ym      parameter (jjmp1=jjm+1-1/jjm)
    40   ! ym#include "dimphy.h"
    4137
    4238
  • LMDZ5/trunk/libf/phylmd/moyglo_aire.F90

    r1992 r2346  
    1616  ! ==================================================================
    1717
    18   include "dimensions.h"
    19   ! ym#include "dimphy.h"
    2018  INTEGER i, nhori
    2119  REAL champ(klon), aire(klon), msk(klon)
     
    7472
    7573  ! ==================================================================
    76   include "dimensions.h"
    77   ! ym#include "dimphy.h"
    7874  include "YOMCST.h"
    7975  INTEGER i, k, nhori, nvert
     
    119115
    120116  ! ==================================================================
    121   include "dimensions.h"
    122   ! ym#include "dimphy.h"
    123117  include "YOMCST.h"
    124118  INTEGER i, k, nhori, nvert
  • LMDZ5/trunk/libf/phylmd/nuage.F90

    r2109 r2346  
    3737  include "nuage.h" ! JBM 3/14
    3838
    39   ! ym#include "dimensions.h"
    40   ! ym#include "dimphy.h"
    4139  REAL paprs(klon, klev+1), pplay(klon, klev)
    4240  REAL t(klon, klev)
     
    246244  ! ces nuages. Je dois avouer que c'est une frustration.
    247245
    248   ! ym#include "dimensions.h"
    249   ! ym#include "dimphy.h"
    250246  include "YOMCST.h"
    251247
     
    323319  IMPLICIT NONE
    324320
    325   ! ym#include "dimensions.h"
    326   ! ym#include "dimphy.h"
    327321  include "YOMCST.h"
    328322
  • LMDZ5/trunk/libf/phylmd/o3_chem_m.F90

    r1907 r2346  
    1414
    1515    ! All the 2-dimensional arrays are on the partial "physics" grid.
    16     ! Their shape is "(/klon, llm/)".
     16    ! Their shape is "(/klon, nbp_lev/)".
    1717    ! Index "(i, :)" is for longitude "rlon(i)", latitude "rlat(i)".
    1818
     
    2020    use dimphy, only: klon
    2121    use regr_pr_comb_coefoz_m, only: c_Mob, a4_mass, a2, r_het_interm
     22    use mod_grid_phy_lmdz, only: nbp_lev
     23    use nrtype, only: pi
    2224
    2325    integer, intent(in):: julien ! jour julien, 1 <= julien <= 360
    2426    real, intent(in):: gmtime ! heure de la journée en fraction de jour
    25     real, intent(in):: t_seri(:, :) ! (klon, llm) temperature, in K
     27    real, intent(in):: t_seri(:, :) ! (klon, nbp_lev) temperature, in K
    2628
    27     real, intent(in):: zmasse(:, :) ! (klon, llm)
     29    real, intent(in):: zmasse(:, :) ! (klon, nbp_lev)
    2830    ! (column-density of mass of air in a cell, in kg m-2)
    2931    ! "zmasse(:, k)" is for layer "k".)
     
    3436    ! (longitude and latitude of each horizontal position, in degrees)
    3537
    36     real, intent(inout):: q(:, :) ! (klon, llm) mass fraction of ozone
     38    real, intent(inout):: q(:, :) ! (klon, nbp_lev) mass fraction of ozone
    3739    ! "q(:, k)" is at middle of layer "k".)
    3840
    3941    ! Variables local to the procedure:
    40     include "dimensions.h"
    41     include "comconst.h"
    4242    ! (for "pi")
    4343    integer k
    4444
    45     real c(klon, llm)
     45    real c(klon, nbp_lev)
    4646    ! (constant term during a time step in the net mass production
    4747    ! rate of ozone by chemistry, per unit mass of air, in s-1)
    4848    ! "c(:, k)" is at middle of layer "k".)
    4949
    50     real b(klon, llm)
     50    real b(klon, nbp_lev)
    5151    ! (coefficient of "q" in the net mass production
    5252    ! rate of ozone by chemistry, per unit mass of air, in s-1)
    5353    ! "b(:, k)" is at middle of layer "k".)
    5454
    55     real dq_o3_chem(klon, llm)
     55    real dq_o3_chem(klon, nbp_lev)
    5656    ! (variation of ozone mass fraction due to chemistry during a time step)
    5757    ! "dq_o3_chem(:, k)" is at middle of layer "k".)
     
    6969    call assert(klon == (/size(q, 1), size(t_seri, 1), size(zmasse, 1), &
    7070         size(rlat), size(rlon)/), "o3_chem klon")
    71     call assert(llm == (/size(q, 2), size(t_seri, 2), size(zmasse, 2)/), &
    72          "o3_chem llm")
     71    call assert(nbp_lev == (/size(q, 2), size(t_seri, 2), size(zmasse, 2)/), &
     72         "o3_chem nbp_lev")
    7373
    7474    c = c_Mob + a4_mass * t_seri
     
    8686    call orbite(real(julien), earth_long, trash1)
    8787    call zenang(earth_long, gmtime, pdtphys, rlat, rlon, pmu0, trash2)
    88     forall (k = 1: llm)
     88    forall (k = 1: nbp_lev)
    8989       where (pmu0 <= cos(87. / 180. * pi)) b(:, k) = 0.
    9090    end forall
     
    112112
    113113    ! All the 2-dimensional arrays are on the partial "physics" grid.
    114     ! Their shape is "(/klon, llm/)".
     114    ! Their shape is "(/klon, nbp_lev/)".
    115115    ! Index "(i, :)" is for longitude "rlon(i)", latitude "rlat(i)".
    116116
     
    118118    use assert_m, only: assert
    119119    use dimphy, only: klon
     120    use mod_grid_phy_lmdz, only: nbp_lev
    120121
    121122    real, intent(in):: q(:, :) ! mass fraction of ozone
     
    136137    ! ("b(:, k)" is at middle of layer "k".)
    137138
    138     include "dimensions.h"
    139 
    140     real o3_prod(klon, llm)
     139    real o3_prod(klon, nbp_lev)
    141140    ! (net mass production rate of ozone by chemistry, per unit mass
    142141    ! of air, in s-1)
     
    145144    ! Variables local to the procedure:
    146145
    147     real sigma_mass(klon, llm)
     146    real sigma_mass(klon, nbp_lev)
    148147    ! (mass column-density of ozone above point, in kg m-2)
    149148    ! ("sigma_mass(:, k)" is at middle of layer "k".)
     
    155154    call assert(klon == (/size(q, 1), size(zmasse, 1), size(c, 1), &
    156155         size(b, 1)/), "o3_prod 1")
    157     call assert(llm == (/size(q, 2), size(zmasse, 2), size(c, 2), &
     156    call assert(nbp_lev == (/size(q, 2), size(zmasse, 2), size(c, 2), &
    158157         size(b, 2)/), "o3_prod 2")
    159158
     
    161160    ! "k", and, as a first approximation, take it as column-density
    162161    ! above the middle of layer "k":
    163     sigma_mass(:, llm) = zmasse(:, llm) * q(:, llm) ! top layer
    164     do k =  llm - 1, 1, -1
     162    sigma_mass(:, nbp_lev) = zmasse(:, nbp_lev) * q(:, nbp_lev) ! top layer
     163    do k =  nbp_lev - 1, 1, -1
    165164       sigma_mass(:, k) = sigma_mass(:, k+1) + zmasse(:, k) * q(:, k)
    166165    end do
  • LMDZ5/trunk/libf/phylmd/oasis.F90

    r2311 r2346  
    100100#endif
    101101    USE print_control_mod, ONLY: lunout
    102 
    103     INCLUDE "dimensions.h"
     102    USE mod_grid_phy_lmdz, ONLY nbp_lon, nbp_lat
    104103
    105104! Local variables
     
    228227!************************************************************************************
    229228    ig_paral(1) = 1                            ! apple partition for //
    230     ig_paral(2) = (jj_begin-1)*iim+ii_begin-1  ! offset
    231     ig_paral(3) = (jj_end*iim+ii_end) - (jj_begin*iim+ii_begin) + 1
    232 
    233     IF (mpi_rank==mpi_size-1) ig_paral(3)=ig_paral(3)+iim-1
     229    ig_paral(2) = (jj_begin-1)*nbp_lon+ii_begin-1  ! offset
     230    ig_paral(3) = (jj_end*nbp_lon+ii_end) - (jj_begin*nbp_lon+ii_begin) + 1
     231
     232    IF (mpi_rank==mpi_size-1) ig_paral(3)=ig_paral(3)+nbp_lon-1
    234233    WRITE(lunout,*) mpi_rank,'ig_paral--->',ig_paral(2),ig_paral(3)
    235234   
     
    248247
    249248    il_var_actual_shape(1) = 1
    250     il_var_actual_shape(2) = iim
     249    il_var_actual_shape(2) = nbp_lon
    251250    il_var_actual_shape(3) = 1
    252     il_var_actual_shape(4) = jjm+1
     251    il_var_actual_shape(4) = nbp_lat
    253252   
    254253    il_var_type = PRISM_Real
     
    320319!
    321320    USE print_control_mod, ONLY: lunout
    322     INCLUDE "dimensions.h"
     321    USE mod_grid_phy_lmdz, ONLY nbp_lon, nbp_lat
    323322! Input arguments
    324323!************************************************************************************
     
    327326! Output arguments
    328327!************************************************************************************
    329     REAL, DIMENSION(iim, jj_nb,maxrecv), INTENT(OUT) :: tab_get
     328    REAL, DIMENSION(nbp_lon, jj_nb,maxrecv), INTENT(OUT) :: tab_get
    330329
    331330! Local variables
     
    335334    CHARACTER (len = 20)          :: modname = 'fromcpl'
    336335    CHARACTER (len = 80)          :: abort_message
    337     REAL, DIMENSION(iim*jj_nb)    :: field
     336    REAL, DIMENSION(nbp_lon*jj_nb)    :: field
    338337
    339338!************************************************************************************
     
    344343    istart=ii_begin
    345344    IF (is_south_pole) THEN
    346        iend=(jj_end-jj_begin)*iim+iim
     345       iend=(jj_end-jj_begin)*nbp_lon+nbp_lon
    347346    ELSE
    348        iend=(jj_end-jj_begin)*iim+ii_end
     347       iend=(jj_end-jj_begin)*nbp_lon+ii_end
    349348    ENDIF
    350349   
     
    353352          field(:) = -99999.
    354353          CALL prism_get_proto(inforecv(i)%nid, ktime, field(istart:iend), ierror)
    355           tab_get(:,:,i) = RESHAPE(field(:),(/iim,jj_nb/))
     354          tab_get(:,:,i) = RESHAPE(field(:),(/nbp_lon,jj_nb/))
    356355       
    357356          IF (ierror .NE. PRISM_Ok .AND. ierror.NE.PRISM_Recvd .AND. &
     
    382381!
    383382    USE print_control_mod, ONLY: lunout
    384     INCLUDE "dimensions.h"
     383    USE mod_grid_phy_lmdz, ONLY nbp_lon, nbp_lat
    385384! Input arguments
    386385!************************************************************************************
    387386    INTEGER, INTENT(IN)                              :: ktime
    388387    LOGICAL, INTENT(IN)                              :: last
    389     REAL, DIMENSION(iim, jj_nb, maxsend), INTENT(IN) :: tab_put
     388    REAL, DIMENSION(nbp_lon, jj_nb, maxsend), INTENT(IN) :: tab_put
    390389
    391390! Local variables
     
    395394    INTEGER                          :: wstart,wend
    396395    INTEGER                          :: ierror, i
    397     REAL, DIMENSION(iim*jj_nb)       :: field
     396    REAL, DIMENSION(nbp_lon*jj_nb)       :: field
    398397    CHARACTER (len = 20),PARAMETER   :: modname = 'intocpl'
    399398    CHARACTER (len = 80)             :: abort_message
     
    410409    istart=ii_begin
    411410    IF (is_south_pole) THEN
    412        iend=(jj_end-jj_begin)*iim+iim
     411       iend=(jj_end-jj_begin)*nbp_lon+nbp_lon
    413412    ELSE
    414        iend=(jj_end-jj_begin)*iim+ii_end
     413       iend=(jj_end-jj_begin)*nbp_lon+ii_end
    415414    ENDIF
    416415   
     
    418417       wstart=istart
    419418       wend=iend
    420        IF (is_north_pole) wstart=istart+iim-1
    421        IF (is_south_pole) wend=iend-iim+1
     419       IF (is_north_pole) wstart=istart+nbp_lon-1
     420       IF (is_south_pole) wend=iend-nbp_lon+1
    422421       
    423422       DO i = 1, maxsend
    424423          IF (infosend(i)%action) THEN
    425              field = RESHAPE(tab_put(:,:,i),(/iim*jj_nb/))
     424             field = RESHAPE(tab_put(:,:,i),(/nbp_lon*jj_nb/))
    426425             CALL writefield_phy(infosend(i)%name,field(wstart:wend),1)
    427426          END IF
     
    435434    DO i = 1, maxsend
    436435      IF (infosend(i)%action .AND. infosend(i)%nid .NE. -1 ) THEN
    437           field = RESHAPE(tab_put(:,:,i),(/iim*jj_nb/))
     436          field = RESHAPE(tab_put(:,:,i),(/nbp_lon*jj_nb/))
    438437          CALL prism_put_proto(infosend(i)%nid, ktime, field(istart:iend), ierror)
    439438         
  • LMDZ5/trunk/libf/phylmd/orbite.F90

    r1992 r2346  
    6363  ! la journee (0 a 1)
    6464  ! ======================================================================
    65   ! ym#include "dimensions.h"
    66   ! ym#include "dimphy.h"
    6765  REAL longi
    6866  REAL lati(klon), frac(klon), muzero(klon)
     
    129127  ! frac-----OUTPUT: ensoleillement moyen entre gmtime et gmtime+pdtrad
    130128  ! ================================================================
    131   ! ym#include "dimensions.h"
    132   ! ym#include "dimphy.h"
    133129  include "YOMCST.h"
    134130  ! ================================================================
     
    266262
    267263  ! ====================================================================
    268   ! ym#include "dimensions.h"
    269   ! ym#include "dimphy.h"
    270264  include "YOMCST.h"
    271265  ! ====================================================================
  • LMDZ5/trunk/libf/phylmd/orografi.F90

    r2311 r2346  
    2424  ! d_v-----output-R-increment de la vitesse v
    2525  ! ======================================================================
    26   ! ym#include "dimensions.h"
    27   ! ym#include "dimphy.h"
    2826  include "YOMCST.h"
    2927
     
    171169
    172170
    173   ! ym#include "dimensions.h"
    174   ! ym#include "dimphy.h"
    175171  include "YOMCST.h"
    176172  include "YOEGWD.h"
     
    404400
    405401
    406   ! ym#include "dimensions.h"
    407   ! ym#include "dimphy.h"
    408402  include "YOMCST.h"
    409403  include "YOEGWD.h"
     
    849843  USE dimphy
    850844  IMPLICIT NONE
    851   ! ym#include "dimensions.h"
    852   ! ym#include "dimphy.h"
    853845  include "YOMCST.h"
    854846  include "YOEGWD.h"
     
    980972
    981973
    982   ! ym#include "dimensions.h"
    983   ! ym#include "dimphy.h"
    984974  include "YOMCST.h"
    985975  include "YOEGWD.h"
     
    12091199  ! d_v-----output-R-increment de la vitesse v
    12101200  ! ======================================================================
    1211   ! ym#include "dimensions.h"
    1212   ! ym#include "dimphy.h"
    12131201  include "YOMCST.h"
    12141202
     
    13241312
    13251313
    1326   ! ym#include "dimensions.h"
    1327   ! ym#include "dimphy.h"
    13281314  include "YOMCST.h"
    13291315  include "YOEGWD.h"
  • LMDZ5/trunk/libf/phylmd/orografi_strato.F90

    r2333 r2346  
    6161
    6262  ! ======================================================================
    63   ! ym#include "dimensions.h"
    64   ! ym#include "dimphy.h"
    6563  include "YOMCST.h"
    6664  include "YOEGWD.h"
     
    239237
    240238
    241   ! ym#include "dimensions.h"
    242   ! ym#include "dimphy.h"
    243239  include "YOMCST.h"
    244240  include "YOEGWD.h"
     
    541537
    542538
    543   ! ym#include "dimensions.h"
    544   ! ym#include "dimphy.h"
    545539  include "YOMCST.h"
    546540  include "YOEGWD.h"
     
    995989  IMPLICIT NONE
    996990
    997   ! ym#include "dimensions.h"
    998   ! ym#include "dimphy.h"
    999991  include "YOMCST.h"
    1000992  include "YOEGWD.h"
     
    11141106  IMPLICIT NONE
    11151107
    1116   ! ym#include "dimensions.h"
    1117   ! ym#include "dimphy.h"
    11181108  include "YOMCST.h"
    11191109  include "YOEGWD.h"
     
    13501340  ! ======================================================================
    13511341
    1352   ! ym#include "dimensions.h"
    1353   ! ym#include "dimphy.h"
    13541342  include "YOMCST.h"
    13551343  include "YOEGWD.h"
     
    15101498
    15111499
    1512   ! ym#include "dimensions.h"
    1513   ! ym#include "dimphy.h"
    15141500  include "YOMCST.h"
    15151501  include "YOEGWD.h"
  • LMDZ5/trunk/libf/phylmd/phyaqua_mod.F90

    r2344 r2346  
    489489    USE mod_phys_lmdz_transfert_para, ONLY: gather
    490490    IMPLICIT NONE
    491     ! #include "dimensions.h"
    492     ! #include "dimphy.h"
    493491    include "netcdf.inc"
    494492
  • LMDZ5/trunk/libf/phylmd/plevel.F90

    r2271 r2346  
    1616#endif
    1717  IMPLICIT NONE
    18 
    19   ! ym#include "dimensions.h"
    20   ! y#include "dimphy.h"
    2118
    2219  ! ================================================================
  • LMDZ5/trunk/libf/phylmd/plevel_new.F90

    r2271 r2346  
    1818
    1919  IMPLICIT NONE
    20 
    21   ! ym#include "dimensions.h"
    22   ! y#include "dimphy.h"
    2320
    2421  ! ================================================================
  • LMDZ5/trunk/libf/phylmd/radiation_AR4.F90

    r2320 r2346  
    99  IMPLICIT NONE
    1010
    11   ! ym#include "dimensions.h"
    12   ! ym#include "dimphy.h"
    13   ! ym#include "raddim.h"
    1411  include "YOMCST.h"
    1512
     
    317314    rtdumg, rth2o, rtumg
    318315  IMPLICIT NONE
    319   ! ym#include "dimensions.h"
    320   ! ym#include "dimphy.h"
    321   ! ym#include "raddim.h"
    322316  include "radepsi.h"
    323317  include "radopt.h"
     
    491485
    492486  IMPLICIT NONE
    493   ! ym#include "dimensions.h"
    494   ! ym#include "dimphy.h"
    495   ! ym#include "raddim.h"i
    496487
    497488  ! ------------------------------------------------------------------
     
    715706
    716707  IMPLICIT NONE
    717   ! ym#include "dimensions.h"
    718   ! ym#include "dimphy.h"
    719   ! ym#include "raddim.h"
    720708  include "radepsi.h"
    721709
     
    12101198  USE radiation_ar4_param, ONLY: taua, rpiza, rcga
    12111199  IMPLICIT NONE
    1212   ! ym#include "dimensions.h"
    1213   ! ym#include "dimphy.h"
    1214   ! ym#include "raddim.h"
    12151200  include "radepsi.h"
    12161201  include "radopt.h"
     
    15411526  USE dimphy
    15421527  IMPLICIT NONE
    1543   ! ym#include "dimensions.h"
    1544   ! ym#include "dimphy.h"
    1545   ! ym#include "raddim.h"
    15461528  include "radepsi.h"
    15471529  include "radopt.h"
     
    18711853  USE dimphy
    18721854  IMPLICIT NONE
    1873   ! ym#include "dimensions.h"
    1874   ! ym#include "dimphy.h"
    1875   ! ym#include "raddim.h"
    18761855
    18771856  ! ------------------------------------------------------------------
     
    19981977  USE radiation_ar4_param, ONLY: apad, bpad, d
    19991978  IMPLICIT NONE
    2000   ! ym#include "dimensions.h"
    2001   ! ym#include "dimphy.h"
    2002   ! ym#include "raddim.h"
    20031979
    20041980  ! -----------------------------------------------------------------------
     
    20702046  USE radiation_ar4_param, ONLY: apad, bpad, d
    20712047  IMPLICIT NONE
    2072   ! ym#include "dimensions.h"
    2073   ! ym#include "dimphy.h"
    2074   ! ym#include "raddim.h"
    20752048
    20762049  ! -----------------------------------------------------------------------
     
    21532126  USE print_control_mod, ONLY: lunout
    21542127  IMPLICIT NONE
    2155   ! ym#include "dimensions.h"
    2156   ! ym#include "dimphy.h"
    2157   ! ym#include "raddim.h"
    21582128  include "raddimlw.h"
    21592129  include "YOMCST.h"
     
    23482318
    23492319  IMPLICIT NONE
    2350   ! ym#include "dimensions.h"
    2351   ! ym#include "dimphy.h"
    2352   ! ym#include "raddim.h"
    23532320  include "raddimlw.h"
    23542321  include "YOMCST.h"
     
    27142681  USE dimphy
    27152682  IMPLICIT NONE
    2716   ! ym#include "dimensions.h"
    2717   ! ym#include "dimphy.h"
    2718   ! ym#include "raddim.h"
    27192683  include "raddimlw.h"
    27202684  include "YOMCST.h"
     
    28032767  USE dimphy
    28042768  IMPLICIT NONE
    2805   ! ym#include "dimensions.h"
    2806   ! ym#include "dimphy.h"
    2807   ! ym#include "raddim.h"
    28082769  include "radepsi.h"
    28092770  include "radopt.h"
     
    31833144  USE radiation_ar4_param, ONLY: tintp, xp, ga, gb
    31843145  IMPLICIT NONE
    3185   ! ym#include "dimensions.h"
    3186   ! ym#include "dimphy.h"
    3187   ! ym#include "raddim.h"
    31883146  include "raddimlw.h"
    31893147
     
    45854543  USE dimphy
    45864544  IMPLICIT NONE
    4587   ! ym#include "dimensions.h"
    4588   ! ym#include "dimphy.h"
    4589   ! ym#include "raddim.h"
    45904545  include "raddimlw.h"
    45914546  include "YOMCST.h"
     
    46934648  USE dimphy
    46944649  IMPLICIT NONE
    4695   ! ym#include "dimensions.h"
    4696   ! ym#include "dimphy.h"
    4697   ! ym#include "raddim.h"
    46984650  include "raddimlw.h"
    46994651  include "radopt.h"
     
    49954947  USE dimphy
    49964948  IMPLICIT NONE
    4997   ! ym#include "dimensions.h"
    4998   ! ym#include "dimphy.h"
    4999   ! ym#include "raddim.h"
    50004949  include "raddimlw.h"
    50014950
     
    52315180  USE radiation_ar4_param, ONLY: wg1
    52325181  IMPLICIT NONE
    5233   ! ym#include "dimensions.h"
    5234   ! ym#include "dimphy.h"
    5235   ! ym#include "raddim.h"
    52365182  include "raddimlw.h"
    52375183
     
    54265372  USE dimphy
    54275373  IMPLICIT NONE
    5428   ! ym#include "dimensions.h"
    5429   ! ym#include "dimphy.h"
    5430   ! ym#include "raddim.h"
    54315374  include "raddimlw.h"
    54325375
     
    56025545  USE dimphy
    56035546  IMPLICIT NONE
    5604   ! ym#include "dimensions.h"
    5605   ! ym#include "dimphy.h"
    5606   ! ym#include "raddim.h"
    56075547  include "raddimlw.h"
    56085548
  • LMDZ5/trunk/libf/phylmd/readaerosol.F90

    r2317 r2346  
    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,nbp_lat) to 1D(klon_glo)
    181181!     - Also the levels and the latitudes have to be inversed
    182182!
     
    188188    USE netcdf
    189189    USE dimphy
    190     USE mod_grid_phy_lmdz
     190    USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, klon_glo, &
     191                                 grid2Dto1D_glo
    191192    USE mod_phys_lmdz_para
    192193    USE iophy, ONLY : io_lon, io_lat
     
    195196    IMPLICIT NONE
    196197     
    197     INCLUDE "dimensions.h"     
    198 
    199198! Input argumets
    200199    CHARACTER(len=7), INTENT(IN)          :: varname
     
    223222    REAL, ALLOCATABLE, DIMENSION(:)       :: varktmp
    224223
    225     REAL, DIMENSION(iim,jjm+1,12)         :: psurf_glo2D   ! Surface pression for 12 months on dynamics global grid
     224    REAL, DIMENSION(nbp_lon,nbp_lat,12)         :: psurf_glo2D   ! Surface pression for 12 months on dynamics global grid
    226225    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
     226    REAL, DIMENSION(nbp_lon,nbp_lat,12)         :: load_glo2D    ! Load for 12 months on dynamics global grid
    228227    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
     228    REAL, DIMENSION(nbp_lon,nbp_lat)            :: vartmp
     229    REAL, DIMENSION(nbp_lon)                  :: lon_src              ! longitudes in file
     230    REAL, DIMENSION(nbp_lat)                :: lat_src, lat_src_inv ! latitudes in file
    232231    LOGICAL                               :: new_file             ! true if new file format detected
    233232    LOGICAL                               :: invert_lat           ! true if the field has to be inverted for latitudes
     
    267266
    268267       ! Invert source latitudes
    269        DO j = 1, jjm+1
    270           lat_src_inv(j) = lat_src(jjm+1 +1 -j)
     268       DO j = 1, nbp_lat
     269          lat_src_inv(j) = lat_src(nbp_lat +1 -j)
    271270       END DO
    272271
     
    313312       
    314313     ! 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)
     314       ALLOCATE(varmth(nbp_lon,nbp_lat, klev_src), varyear(nbp_lon,nbp_lat, klev_src, 12), stat=ierr)
    316315       IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 1',1)
    317316
     
    435434     
    436435
    437 ! 5) Transform the global field from 2D(iim, jjp+1) to 1D(klon_glo)
     436! 5) Transform the global field from 2D(nbp_lon,nbp_lat) to 1D(klon_glo)
    438437!****************************************************************************************
    439438! Test if vertical levels have to be inversed
     
    448447             varmth(:,:,:) = varyear(:,:,:,imth) ! use varmth temporarly
    449448             DO k=1, klev_src
    450                 DO j=1, jjm+1
    451                    DO i=1,iim
     449                DO j=1, nbp_lat
     450                   DO i=1, nbp_lon
    452451                      varyear(i,j,k,imth) = varmth(i,j,klev_src+1-k)
    453452                   END DO
     
    482481             varmth(:,:,:) = varyear(:,:,:,imth) ! use varmth temporarly
    483482             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)
     483                DO j=1,nbp_lat
     484                   DO i=1,nbp_lon
     485                      varyear(i,j,k,imth) = varmth(i,nbp_lat+1-j,k)
    487486                   END DO
    488487                END DO
     
    491490             ! Invert latitudes for surface pressure
    492491             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)
     492             DO j=1,nbp_lat
     493                DO i=1,nbp_lon
     494                   psurf_glo2D(i,j,imth)= vartmp(i,nbp_lat+1-j)
    496495                END DO
    497496             END DO
     
    499498             ! Invert latitudes for the load
    500499             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)
     500             DO j=1,nbp_lat
     501                DO i=1,nbp_lon
     502                   load_glo2D(i,j,imth)= vartmp(i,nbp_lat+1-j)
    504503                END DO
    505504             END DO
     
    509508          DO k=1, klev_src
    510509             npole=0.  ! North pole, j=1
    511              spole=0.  ! South pole, j=jjm+1        
    512              DO i=1,iim
     510             spole=0.  ! South pole, j=nbp_lat       
     511             DO i=1,nbp_lon
    513512                npole = npole + varyear(i,1,k,imth)
    514                 spole = spole + varyear(i,jjm+1,k,imth)
     513                spole = spole + varyear(i,nbp_lat,k,imth)
    515514             END DO
    516              npole = npole/REAL(iim)
    517              spole = spole/REAL(iim)
     515             npole = npole/REAL(nbp_lon)
     516             spole = spole/REAL(nbp_lon)
    518517             varyear(:,1,    k,imth) = npole
    519              varyear(:,jjm+1,k,imth) = spole
     518             varyear(:,nbp_lat,k,imth) = spole
    520519          END DO
    521520       END DO ! imth
  • LMDZ5/trunk/libf/phylmd/readaerosolstrato.F90

    r2152 r2346  
    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, &
     9                                 grid2dto1d_glo
    910    USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
    1011    USE mod_phys_lmdz_para
     
    1718
    1819    include "YOMCST.h"
    19     include "dimensions.h"
    2020
    2121! Variable input
     
    8585    n_lat = size(latitude)
    8686    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'
     87    IF (n_lat.NE.nbp_lat) THEN
     88       print *,'Le nombre de lat n est pas egal a nbp_lat'
    8989       STOP
    9090    ENDIF
     
    9494    n_lon = size(longitude)
    9595    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'
     96    IF (n_lon.NE.nbp_lon) THEN
     97       print *,'Le nombre de lon n est pas egal a nbp_lon'
    9898       STOP
    9999    ENDIF
  • LMDZ5/trunk/libf/phylmd/readchlorophyll.F90

    r2227 r2346  
    1010
    1111    USE phys_cal_mod, ONLY : mth_cur
    12     USE mod_grid_phy_lmdz
     12    USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, klon_glo, &
     13                                 grid2dto1d_glo
    1314    USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
    1415    USE mod_phys_lmdz_para
     
    2021
    2122    include "YOMCST.h"
    22     include "dimensions.h"
    2323
    2424! Variable input
     
    6262    n_lon = size(longitude)
    6363!    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'
     64    IF (n_lon.NE.nbp_lon) THEN
     65       print *,'Le nombre de lon n est pas egal a nbp_lon'
    6666       STOP
    6767    ENDIF
     
    7272    n_lat = size(latitude)
    7373!    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'
     74    IF (n_lat.NE.nbp_lat) THEN
     75       print *,'Le nombre de lat n est pas egal a jnbp_lat'
    7676       STOP
    7777    ENDIF
  • LMDZ5/trunk/libf/phylmd/regr_lat_time_climoz_m.F90

    r1907 r2346  
    6666    ! year.
    6767
     68    use mod_grid_phy_lmdz, ONLY : nbp_lat
    6869    use regr1_step_av_m, only: regr1_step_av
    6970    use regr3_lint_m, only: regr3_lint
     
    7374    use netcdf, only: nf90_get_att, nf90_get_var, nf90_noerr, nf90_nowrite
    7475    use assert_m, only: assert
     76    use regular_lonlat_mod, only : boundslat_reg, south
     77    use nrtype, only: pi
    7578
    7679    integer, intent(in):: read_climoz ! read ozone climatology
     
    8184
    8285    ! Variables local to the procedure:
    83 
    84     include "dimensions.h"
    85     ! (for "jjm")
    86     include "paramet.h"
    87     ! (for the other included files)
    88     include "comgeom2.h"
    89     ! (for "rlatv")
    90     include "comconst.h"
    91     ! (for "pi")
    9286
    9387    integer n_plev ! number of pressure levels in the input data
     
    289283    call nf95_close(ncid_in)
    290284
    291     allocate(o3_regr_lat(jjm + 1, n_plev, 0:13, read_climoz))
    292     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))
    293287
    294288    ! Regrid in latitude:
     
    298292       print *, &
    299293            "Found 12 months in ozone climatologies, assuming periodicity..."
    300        o3_regr_lat(jjm+1:1:-1, :, 1:12, :) = regr1_step_av(o3_in, &
    301             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, boundslat_reg(nbp_lat-1:1:-1,south), pi / 2/)))
    302296       ! (invert order of indices in "o3_regr_lat" because "rlatu" is
    303297       ! in descending order)
     
    309303    else
    310304       print *, "Using 14 months in ozone climatologies..."
    311        o3_regr_lat(jjm+1:1:-1, :, :, :) = regr1_step_av(o3_in, &
    312             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, boundslat_reg(nbp_lat-1:1:-1,south), pi / 2/)))
    313307       ! (invert order of indices in "o3_regr_lat" because "rlatu" is
    314308       ! in descending order)
     
    320314    ! Write to file:
    321315    do m = 1, read_climoz
    322        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))
    323317       ! (The order of "rlatu" is inverted in the output file)
    324318    end do
     
    336330    ! dimensions and variables, and writes one of the coordinate variables.
    337331
     332    use mod_grid_phy_lmdz, ONLY : nbp_lat
    338333    use netcdf95, only: nf95_create, nf95_def_dim, nf95_def_var, &
    339334         nf95_put_att, nf95_enddef, nf95_copy_att, nf95_put_var
    340335    use netcdf, only: nf90_clobber, nf90_float, nf90_global
     336    use nrtype, only: pi
     337    use regular_lonlat_mod, only : lat_reg
    341338
    342339    integer, intent(in):: ncid_in, n_plev
     
    349346    ! Variables local to the procedure:
    350347
    351     include "dimensions.h"
    352     ! (for "jjm")
    353     include "paramet.h"
    354     ! (for the other included files)
    355     include "comgeom2.h"
    356     ! (for "rlatu")
    357     include "comconst.h"
    358     ! (for "pi")
    359 
    360348    integer ncerr
    361349    integer dimid_rlatu, dimid_plev, dimid_time
     
    371359    call nf95_def_dim(ncid_out, "time", 360, dimid_time)
    372360    call nf95_def_dim(ncid_out, "plev", n_plev, dimid_plev)
    373     call nf95_def_dim(ncid_out, "rlatu", jjm + 1, dimid_rlatu)
     361    call nf95_def_dim(ncid_out, "rlatu", nbp_lat, dimid_rlatu)
    374362
    375363    ! Define coordinate variables:
     
    432420
    433421    ! Write one of the coordinate variables:
    434     call nf95_put_var(ncid_out, varid_rlatu, rlatu(jjm+1:1:-1) / pi * 180.)
     422    call nf95_put_var(ncid_out, varid_rlatu, lat_reg(nbp_lat:1:-1) / pi * 180.)
    435423    ! (convert from rad to degrees and sort in ascending order)
    436424
  • LMDZ5/trunk/libf/phylmd/regr_lat_time_coefoz_m.F90

    r1907 r2346  
    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
     
    4546         nf95_put_var, nf95_gw_var
    4647    use netcdf, only: nf90_nowrite, nf90_get_var
     48    use nrtype, only: pi
     49    use regular_lonlat_mod, only: boundslat_reg, south
    4750
    4851    ! Variables local to the procedure:
    49 
    50     include "dimensions.h"
    51     ! (for "jjm")
    52     include "paramet.h"
    53     include "comgeom2.h"
    54     ! (for "rlatv")
    55     include "comconst.h"
    56     ! (for "pi")
    5752
    5853    integer ncid_in, ncid_out ! NetCDF IDs for input and output files
     
    164159    call nf95_inq_varid(ncid_in, "latitude", varid)
    165160    call nf95_gw_var(ncid_in, varid, latitude)
    166     ! Convert from degrees to rad, because "rlatv" is in rad:
     161    ! Convert from degrees to rad, because "boundslat_reg" is in rad:
    167162    latitude = latitude / 180. * pi
    168163    n_lat = size(latitude)
     
    200195
    201196    allocate(o3_par_in(n_lat, n_plev, 12))
    202     allocate(v_regr_lat(jjm + 1, n_plev, 0:13))
    203     allocate(o3_par_out(jjm + 1, n_plev, 360))
     197    allocate(v_regr_lat(nbp_lat, n_plev, 0:13))
     198    allocate(o3_par_out(nbp_lat, n_plev, 360))
    204199
    205200    do i_v = 1, n_o3_param
     
    214209       ! We average with respect to sine of latitude, which is
    215210       ! equivalent to weighting by cosine of latitude:
    216        v_regr_lat(jjm+1:1:-1, :, 1:12) = regr1_step_av(o3_par_in, &
    217             xs=sin(lat_in_edg), xt=sin((/- pi / 2, rlatv(jjm:1:-1), pi / 2/)))
     211       v_regr_lat(nbp_lat:1:-1, :, 1:12) = regr1_step_av(o3_par_in, &
     212            xs=sin(lat_in_edg), xt=sin((/- pi / 2, boundslat_reg(nbp_lat-1:1:-1,south), pi / 2/)))
    218213       ! (invert order of indices in "v_regr_lat" because "rlatu" is
    219214       ! in descending order)
     
    229224       ! Write to file:
    230225       call nf95_put_var(ncid_out, varid_out(i_v), &
    231             o3_par_out(jjm+1:1:-1, :, :))
     226            o3_par_out(nbp_lat:1:-1, :, :))
    232227       ! (The order of "rlatu" is inverted in the output file)
    233228    end do
     
    246241    ! dimensions and variables, and writes one of the coordinate variables.
    247242
     243    use mod_grid_phy_lmdz, ONLY : nbp_lat
    248244    use assert_eq_m, only: assert_eq
    249245
     
    251247         nf95_put_att, nf95_enddef, nf95_copy_att, nf95_put_var
    252248    use netcdf, only: nf90_clobber, nf90_float, nf90_copy_att, nf90_global
     249    use nrtype, only: pi
     250    use regular_lonlat_mod, only : lat_reg
    253251
    254252    integer, intent(in):: ncid_in, varid_in(:), n_plev
     
    257255
    258256    ! Variables local to the procedure:
    259 
    260     include "dimensions.h"
    261     ! (for "jjm")
    262     include "paramet.h"
    263     include "comgeom2.h"
    264     ! (for "rlatu")
    265     include "comconst.h"
    266     ! (for "pi")
    267257
    268258    integer ncerr
     
    282272    call nf95_def_dim(ncid_out, "time", 360, dimid_time)
    283273    call nf95_def_dim(ncid_out, "plev", n_plev, dimid_plev)
    284     call nf95_def_dim(ncid_out, "rlatu", jjm + 1, dimid_rlatu)
     274    call nf95_def_dim(ncid_out, "rlatu", nbp_lat, dimid_rlatu)
    285275
    286276    ! Define coordinate variables:
     
    332322
    333323    ! Write one of the coordinate variables:
    334     call nf95_put_var(ncid_out, varid_rlatu, rlatu(jjm+1:1:-1) / pi * 180.)
     324    call nf95_put_var(ncid_out, varid_rlatu, lat_reg(nbp_lat:1:-1) / pi * 180.)
    335325    ! (convert from rad to degrees and sort in ascending order)
    336326
  • LMDZ5/trunk/libf/phylmd/regr_pr_av_m.F90

    r1907 r2346  
    4040    use regr1_step_av_m, only: regr1_step_av
    4141    use mod_phys_lmdz_mpi_data, only: is_mpi_root
    42 
     42    use mod_grid_phy_lmdz, only: nbp_lon, nbp_lat, nbp_lev
    4343    use mod_phys_lmdz_transfert_para, only: scatter2d
    4444    ! (pack to the LMDZ horizontal "physics" grid and scatter)
     
    6363    ! Variables local to the procedure:
    6464
    65     include "dimensions.h"
    6665    integer varid, ncerr ! for NetCDF
    6766
    68     real  v1(iim, jjm + 1, size(press_in_edg) - 1, size(name))
     67    real  v1(nbp_lon, nbp_lat, size(press_in_edg) - 1, size(name))
    6968    ! input fields at day "julien", on the global "dynamics" horizontal grid
    7069    ! First dimension is for longitude.
     
    8483    !--------------------------------------------
    8584
    86     call assert(size(v3, 1) == klon, size(v3, 2) == llm, "regr_pr_av v3 klon")
     85    call assert(size(v3, 1) == klon, size(v3, 2) == nbp_lev, "regr_pr_av v3 klon")
    8786    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")
     87    call assert(shape(paprs) == (/klon, nbp_lev+1/), "regr_pr_av paprs")
    8988
    9089    !$omp master
     
    102101       ! Latitudes are in ascending order in the input file while
    103102       ! "rlatu" is in descending order so we need to invert order:
    104        v1(1, :, :, :) = v1(1, jjm+1:1:-1, :, :)
     103       v1(1, :, :, :) = v1(1, nbp_lat:1:-1, :, :)
    105104
    106105       ! Duplicate on all longitudes:
    107        v1(2:, :, :, :) = spread(v1(1, :, :, :), dim=1, ncopies=iim-1)
     106       v1(2:, :, :, :) = spread(v1(1, :, :, :), dim=1, ncopies=nbp_lon-1)
    108107    end if
    109108    !$omp end master
     
    113112    ! Regrid in pressure at each horizontal position:
    114113    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))
     114       v3(i, nbp_lev:1:-1, :) = regr1_step_av(v2(i, :, :), press_in_edg, &
     115            paprs(i, nbp_lev+1:1:-1))
    117116       ! (invert order of indices because "paprs" is in descending order)
    118117    end do
  • LMDZ5/trunk/libf/phylmd/regr_pr_comb_coefoz_m.F90

    r1907 r2346  
    4040
    4141    use dimphy, only: klon
     42    use mod_grid_phy_lmdz, only: nbp_lev
    4243
    4344    ! Variables local to the procedure:
    44     include "dimensions.h"
    4545
    4646    !---------------------------------------
     
    4949    print *, "Call sequence information: alloc_coefoz"
    5050    !$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))
     51    allocate(c_Mob(klon, nbp_lev), a2(klon, nbp_lev), a4_mass(klon, nbp_lev))
     52    allocate(a6_mass(klon, nbp_lev), r_het_interm(klon, nbp_lev))
    5353
    5454  end subroutine alloc_coefoz
     
    7979    use regr_pr_int_m, only: regr_pr_int
    8080    use press_coefoz_m, only: press_in_edg, plev
     81    use mod_grid_phy_lmdz, only: nbp_lev
    8182
    8283    integer, intent(in):: julien ! jour julien, 1 <= julien <= 360
     
    8586    ! (latitude on the partial "physics" grid, in degrees)
    8687
    87     real, intent(in):: paprs(:, :) ! (klon, llm + 1)
     88    real, intent(in):: paprs(:, :) ! (klon, nbp_lev + 1)
    8889    ! (pression pour chaque inter-couche, en Pa)
    8990
    90     real, intent(in):: pplay(:, :) ! (klon, llm)
     91    real, intent(in):: pplay(:, :) ! (klon, nbp_lev)
    9192    ! (pression pour le mileu de chaque couche, en Pa)
    9293
    9394    ! Variables local to the procedure:
    9495
    95     include "dimensions.h"
    9696    integer ncid ! for NetCDF
    9797
    98     real coefoz(klon, llm, 7)
     98    real coefoz(klon, nbp_lev, 7)
    9999    ! (temporary storage for 7 ozone coefficients)
    100100    ! (On the partial "physics" grid.
     
    102102    ! middle of layer "k".)
    103103
    104     real a6(klon, llm)
     104    real a6(klon, nbp_lev)
    105105    ! (derivative of "P_net_Mob" with respect to column-density of ozone
    106106    ! above, in cm2 s-1)
     
    121121    call assert((/size(rlat), size(paprs, 1), size(pplay, 1)/) == klon, &
    122122         "regr_pr_comb_coefoz klon")
    123     call assert((/size(paprs, 2) - 1, size(pplay, 2)/) == llm, &
    124          "regr_pr_comb_coefoz llm")
     123    call assert((/size(paprs, 2) - 1, size(pplay, 2)/) == nbp_lev, &
     124         "regr_pr_comb_coefoz nbp_lev")
    125125
    126126    !$omp master
     
    150150    r_het_interm = coefoz(:, :, 7)
    151151    ! Heterogeneous chemistry is only at high latitudes:
    152     forall (k = 1: llm)
     152    forall (k = 1: nbp_lev)
    153153       where (abs(rlat) <= 45.) r_het_interm(:, k) = 0.
    154154    end forall
  • LMDZ5/trunk/libf/phylmd/regr_pr_int_m.F90

    r1907 r2346  
    3030    use regr1_lint_m, only: regr1_lint
    3131    use mod_phys_lmdz_mpi_data, only: is_mpi_root
    32 
     32    use mod_grid_phy_lmdz, only: nbp_lon, nbp_lat, nbp_lev
    3333    use mod_phys_lmdz_transfert_para, only: scatter2d
    3434    ! (pack to the LMDZ horizontal "physics" grid and scatter)
     
    4141    ! (pressure level of input data, in Pa, in strictly ascending order)
    4242
    43     real, intent(in):: pplay(:, :) ! (klon, llm)
     43    real, intent(in):: pplay(:, :) ! (klon, nbp_lev)
    4444    ! (pression pour le mileu de chaque couche, en Pa)
    4545
     
    4747    ! (extra value of field at 0 pressure)
    4848
    49     real, intent(out):: v3(:, :) ! (klon, llm)
     49    real, intent(out):: v3(:, :) ! (klon, nbp_lev)
    5050    ! (regridded field on the partial "physics" grid)
    5151    ! ("v3(i, k)" is at longitude "xlon(i)", latitude
     
    5454    ! Variables local to the procedure:
    5555
    56     include "dimensions.h"
    5756    integer varid, ncerr ! for NetCDF
    5857
    59     real  v1(iim, jjm + 1, 0:size(plev))
     58    real  v1(nbp_lon, nbp_lat, 0:size(plev))
    6059    ! (input field at day "julien", on the global "dynamics" horizontal grid)
    6160    ! (First dimension is for longitude.
     
    7271    !--------------------------------------------
    7372
    74     call assert(shape(v3) == (/klon, llm/), "regr_pr_int v3")
    75     call assert(shape(pplay) == (/klon, llm/), "regr_pr_int pplay")
     73    call assert(shape(v3) == (/klon, nbp_lev/), "regr_pr_int v3")
     74    call assert(shape(pplay) == (/klon, nbp_lev/), "regr_pr_int pplay")
    7675
    7776    !$omp master
     
    8483       ! Latitudes are in ascending order in the input file while
    8584       ! "rlatu" is in descending order so we need to invert order:
    86        v1(1, :, 1:) = v1(1, jjm+1:1:-1, 1:)
     85       v1(1, :, 1:) = v1(1, nbp_lat:1:-1, 1:)
    8786
    8887       ! Complete "v1" with the value at 0 pressure:
     
    9089
    9190       ! Duplicate on all longitudes:
    92        v1(2:, :, :) = spread(v1(1, :, :), dim=1, ncopies=iim-1)
     91       v1(2:, :, :) = spread(v1(1, :, :), dim=1, ncopies=nbp_lon-1)
    9392    end if
    9493    !$omp end master
     
    9897    ! Regrid in pressure at each horizontal position:
    9998    do i = 1, klon
    100        v3(i, llm:1:-1) = regr1_lint(v2(i, :), (/0., plev/), pplay(i, llm:1:-1))
     99       v3(i, nbp_lev:1:-1) = regr1_lint(v2(i, :), (/0., plev/), pplay(i, nbp_lev:1:-1))
    101100       ! (invert order of indices because "pplay" is in descending order)
    102101    end do
  • LMDZ5/trunk/libf/phylmd/regr_pr_o3_m.F90

    r2345 r2346  
    3131    use press_coefoz_m, only: press_in_edg
    3232    use time_phylmdz_mod, only: day_ref
     33    use mod_grid_phy_lmdz, only: nbp_lon, nbp_lat, nbp_lev
    3334
    3435    REAL, intent(in):: p3d(:, :, :) ! pressure at layer interfaces, in Pa
     
    4344    ! Variables local to the procedure:
    4445
    45     include "dimensions.h"
    46 
    4746    integer ncid, varid, ncerr ! for NetCDF
    4847    integer i, j
    4948
    50     real r_mob(jjm + 1, size(press_in_edg) - 1)
     49    real r_mob(nbp_lat, size(press_in_edg) - 1)
    5150    ! (ozone mole fraction from Mobidic at day "day_ref")
    5251    ! (r_mob(j, k) is at latitude "rlatu(j)", in pressure interval
     
    5655
    5756    print *, "Call sequence information: regr_pr_o3"
    58     call assert(shape(o3_mob_regr) == (/iim + 1, jjm + 1, llm/), &
     57    call assert(shape(o3_mob_regr) == (/nbp_lon + 1, nbp_lat, nbp_lev/), &
    5958         "regr_pr_o3 o3_mob_regr")
    60     call assert(shape(p3d) == (/iim + 1, jjm + 1, llm + 1/), "regr_pr_o3 p3d")
     59    call assert(shape(p3d) == (/nbp_lon + 1, nbp_lat, nbp_lev + 1/), "regr_pr_o3 p3d")
    6160
    6261    call nf95_open("coefoz_LMDZ.nc", nf90_nowrite, ncid)
     
    6867    ! Latitudes are in ascending order in the input file while
    6968    ! "rlatu" is in descending order so we need to invert order:
    70     r_mob = r_mob(jjm+1:1:-1, :)
     69    r_mob = r_mob(nbp_lat:1:-1, :)
    7170
    7271    call nf95_close(ncid)
     
    7574
    7675    ! Poles:
    77     do j = 1, jjm + 1, jjm
    78        o3_mob_regr(1, j, llm:1:-1) &
    79             = regr1_step_av(r_mob(j, :), press_in_edg, p3d(1, j, llm+1:1:-1))
     76    do j = 1, nbp_lat, nbp_lat-1
     77       o3_mob_regr(1, j, nbp_lev:1:-1) &
     78            = regr1_step_av(r_mob(j, :), press_in_edg, p3d(1, j, nbp_lev+1:1:-1))
    8079       ! (invert order of indices because "p3d" is in descending order)
    8180    end do
    8281
    8382    ! Other latitudes:
    84     do j = 2, jjm
    85        do i = 1, iim
    86           o3_mob_regr(i, j, llm:1:-1) &
     83    do j = 2, nbp_lat-1
     84       do i = 1, nbp_lon
     85          o3_mob_regr(i, j, nbp_lev:1:-1) &
    8786               = regr1_step_av(r_mob(j, :), press_in_edg, &
    88                p3d(i, j, llm+1:1:-1))
     87               p3d(i, j, nbp_lev+1:1:-1))
    8988             ! (invert order of indices because "p3d" is in descending order)
    9089       end do
     
    9291
    9392    ! Duplicate pole values on all longitudes:
    94     o3_mob_regr(2:, 1, :) = spread(o3_mob_regr(1, 1, :), dim=1, ncopies=iim)
    95     o3_mob_regr(2:, jjm + 1, :) &
    96          = spread(o3_mob_regr(1, jjm + 1, :), dim=1, ncopies=iim)
     93    o3_mob_regr(2:, 1, :) = spread(o3_mob_regr(1, 1, :), dim=1, ncopies=nbp_lon)
     94    o3_mob_regr(2:, nbp_lat, :) &
     95         = spread(o3_mob_regr(1, nbp_lat, :), dim=1, ncopies=nbp_lon)
    9796
    9897    ! Duplicate first longitude to last longitude:
    99     o3_mob_regr(iim + 1, 2:jjm, :) = o3_mob_regr(1, 2:jjm, :)
     98    o3_mob_regr(nbp_lon + 1, 2:nbp_lat-1, :) = o3_mob_regr(1, 2:nbp_lat-1, :)
    10099
    101100  end subroutine regr_pr_o3
  • LMDZ5/trunk/libf/phylmd/thermcell.F90

    r2311 r2346  
    3434  ! -------------
    3535
    36   include "dimensions.h"
    37   ! ccc#include "dimphy.h"
    3836  include "YOMCST.h"
    3937
     
    998996  IMPLICIT NONE
    999997
    1000   include "dimensions.h"
    1001   ! ccc#include "dimphy.h"
    1002998  include "YOMCST.h"
    1003999
  • LMDZ5/trunk/libf/phylmd/thermcellV0_main.F90

    r2311 r2346  
    4242!   -------------
    4343
    44       include "dimensions.h"
    4544      include "YOMCST.h"
    4645      include "YOETHF.h"
  • LMDZ5/trunk/libf/phylmd/thermcell_main.F90

    r2311 r2346  
    6363!   -------------
    6464
    65 #include "dimensions.h"
    6665#include "YOMCST.h"
    6766#include "YOETHF.h"
  • LMDZ5/trunk/libf/phylmd/thermcell_old.F90

    r2311 r2346  
    3131  ! -------------
    3232
    33   include "dimensions.h"
    3433  include "YOMCST.h"
    3534
     
    742741  ! -------------
    743742
    744   include "dimensions.h"
    745   ! ccc#include "dimphy.h"
    746743  include "YOMCST.h"
    747744  include "YOETHF.h"
     
    23452342  ! -------------
    23462343
    2347   include "dimensions.h"
    2348   ! ccc#include "dimphy.h"
    23492344  include "YOMCST.h"
    23502345  include "YOETHF.h"
     
    32783273  ! -------------
    32793274
    3280   include "dimensions.h"
    3281   ! ccc#include "dimphy.h"
    32823275  include "YOMCST.h"
    32833276
     
    41394132  ! =======================================================================
    41404133
    4141   include "dimensions.h"
    4142   ! ccc#include "dimphy.h"
    4143 
    41444134  INTEGER ngrid, nlay
    41454135
     
    42354225
    42364226  ! =======================================================================
    4237 
    4238   include "dimensions.h"
    4239   ! ccc#include "dimphy.h"
    42404227
    42414228  INTEGER ngrid, nlay
     
    43424329  ! =======================================================================
    43434330
    4344   include "dimensions.h"
    4345   ! ccc#include "dimphy.h"
    4346 
    43474331  INTEGER ngrid, nlay
    43484332
     
    44194403
    44204404  ! =======================================================================
    4421 
    4422   include "dimensions.h"
    4423   ! ccc#include "dimphy.h"
    44244405
    44254406  INTEGER ngrid, nlay
     
    45614542  ! -------------
    45624543
    4563   include "dimensions.h"
    4564   ! ccc#include "dimphy.h"
    45654544  include "YOMCST.h"
    45664545
  • LMDZ5/trunk/libf/phylmd/transp.F90

    r1992 r2346  
    1313  ! ======================================================================
    1414
    15   ! ym#include "dimensions.h"
    16   ! ym#include "dimphy.h"
    1715  include "YOMCST.h"
    1816
  • LMDZ5/trunk/libf/phylmd/transp_lay.F90

    r1992 r2346  
    1313  ! ======================================================================
    1414
    15   ! ym#include "dimensions.h"
    16   ! ym#include "dimphy.h"
    1715  include "YOMCST.h"
    1816
  • LMDZ5/trunk/libf/phylmd/undefSTD.F90

    r2312 r2346  
    3737  ! ====================================================================
    3838
    39   ! ym#include "dimensions.h"
    40   ! ym      integer jjmp1
    41   ! ym      parameter (jjmp1=jjm+1-1/jjm)
    4239  ! ym#include "dimphy.h"
    4340  ! variables Input
  • LMDZ5/trunk/libf/phylmd/ustarhb.F90

    r1992 r2346  
    1818  ! model. J. of Climate, vol. 6, 1825-1842.
    1919  ! ======================================================================
    20   ! ym#include "dimensions.h"
    21   ! ym#include "dimphy.h"
    2220  include "YOMCST.h"
    2321
  • LMDZ5/trunk/libf/phylmd/vdif_kcay.F90

    r1992 r2346  
    66  USE dimphy
    77  IMPLICIT NONE
    8   ! .......................................................................
    9   ! ym#include "dimensions.h"
    10   ! ym#include "dimphy.h"
    11   ! .......................................................................
    128
    139  ! dt : pas de temps
  • LMDZ5/trunk/libf/phylmd/wake.F90

    r2311 r2346  
    114114  ! -------------------------------------------------------------------------
    115115
    116   include "dimensions.h"
    117116  include "YOMCST.h"
    118117  include "cvthermo.h"
  • LMDZ5/trunk/libf/phylmd/yamada.F90

    r1992 r2346  
    66  USE dimphy
    77  IMPLICIT NONE
    8   ! .......................................................................
    9   ! ym#include "dimensions.h"
    10   ! ym#include "dimphy.h"
    11   ! .......................................................................
    128
    139  ! dt : pas de temps
  • LMDZ5/trunk/libf/phylmd/yamada4.F90

    r2339 r2346  
    77  USE print_control_mod, ONLY: prt_level
    88  IMPLICIT NONE
    9   ! .......................................................................
    10   ! ym#include "dimensions.h"
    11   ! ym#include "dimphy.h"
    12   ! .......................................................................
    139
    1410  ! dt : pas de temps
     
    498494  USE dimphy
    499495  IMPLICIT NONE
    500   ! .......................................................................
    501   include "dimensions.h"
    502   ! ccc#include "dimphy.h"
    503   ! .......................................................................
    504496
    505497  ! dt : pas de temps
     
    574566  USE dimphy
    575567  IMPLICIT NONE
    576   ! .......................................................................
    577   include "dimensions.h"
    578   ! ccc#include "dimphy.h"
    579   ! .......................................................................
    580568
    581569  ! dt : pas de temps
  • LMDZ5/trunk/libf/phylmd/yamada_c.F90

    r2311 r2346  
    99      IMPLICIT NONE
    1010#include "YOMCST.h"
    11 !.......................................................................
    12 !ym#include "dimensions.h"
    13 !ym#include "dimphy.h"
    14 !.......................................................................
    1511!
    1612! timestep : pas de temps
Note: See TracChangeset for help on using the changeset viewer.