Changeset 1523 for trunk/LMDZ.GENERIC


Ignore:
Timestamp:
Mar 28, 2016, 5:27:51 PM (9 years ago)
Author:
emillour
Message:

All models: More updates to make planetary codes (+Earth) setups converge.

  • in dyn3d_common:
  • convmas.F => convmas.F90
  • enercin.F => enercin.F90
  • flumass.F => flumass.F90
  • massbar.F => massbar.F90
  • tourpot.F => tourpot.F90
  • vitvert.F => vitvert.F90
  • in misc:
  • move "q_sat" from "dyn3d_common" to "misc" (in Earth model, it is also called by the physics)
  • move "write_field" from "dyn3d_common" to "misc"(may be called from physics or dynamics and depends on neither).
  • in phy_common:
  • move "write_field_phy" here since it may be called from any physics package)
  • add module "regular_lonlat_mod" to store global information on lon-lat grid
  • in dynlonlat_phylonlat/phy*:
  • turn "iniphysiq.F90" into module "iniphysiq_mod.F90" (and of course adapt gcm.F[90] and 1D models accordingly)

EM

Location:
trunk/LMDZ.GENERIC
Files:
1 added
2 edited
1 moved

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/README

    r1521 r1523  
    11351135- Adapted "create_make_gcm" and "makegcm*" scripts accordingly
    11361136  (deleted obsolete makegcm_g95)
     1137
     1138== 28/03/2016 == EM
     1139- Added module "regular_lonlat_mod.F90" (to store information on global
     1140  lon-lat grid) in phy_common.
     1141- Turned iniphysiq (in dynlonlat_phylonlat/phymars)into module
     1142  "iniphysiq_mod.F90".
  • trunk/LMDZ.GENERIC/libf/dyn3d/gcm.F

    r1422 r1523  
    1212     .          apdiss,purmats,physic,apphys
    1313      USE temps_mod, ONLY: day_ini,day_end,itaufin,dt
     14      USE iniphysiq_mod, ONLY: iniphysiq
    1415      IMPLICIT NONE
    1516
     
    260261!         CALL iniphysiq(iim,jjm,llm,daysec,day_ini,dtphys/nsplit_phys,
    261262         CALL iniphysiq(iim,jjm,llm,daysec,day_ini,dtphys,
    262      &                rlatu,rlonv,aire,cu,cv,rad,g,r,cpp,
    263      &                1)
     263     &                  rlatu,rlatv,rlonu,rlonv,
     264     &                  aire,cu,cv,rad,g,r,cpp,
     265     &                  1)
    264266!     &                iflag_phys)
    265267!#endif
  • trunk/LMDZ.GENERIC/libf/dynlonlat_phylonlat/phystd/iniphysiq_mod.F90

    r1520 r1523  
     1MODULE iniphysiq_mod
     2
     3CONTAINS
     4
    15subroutine iniphysiq(ii,jj,nlayer,punjours, pdayref,ptimestep,           &
    2                      rlatu,rlonv,aire,cu,cv,                             &
     6                     rlatu,rlatv,rlonu,rlonv,aire,cu,cv,                 &
    37                     prad,pg,pr,pcpp,iflag_phys)
    48
     
    2024use planete_mod, only: ini_planete_mod
    2125USE comvert_mod, ONLY: ap,bp,preff
     26use regular_lonlat_mod, only: init_regular_lonlat, &
     27                              east, west, north, south, &
     28                              north_east, north_west, &
     29                              south_west, south_east
    2230
    2331implicit none
     
    3442integer,intent(in) :: ii ! number of atmospheric coulumns along longitudes
    3543integer,intent(in) :: jj  ! number of atompsheric columns along latitudes
    36 real,intent(in) :: rlatu(jj+1) ! latitudes of the dynamics U grid
    37 real,intent(in) :: rlonv(ii+1) ! longitudes of the dynamics V grid
     44real,intent(in) :: rlatu(jj+1) ! latitudes of the physics grid
     45real,intent(in) :: rlatv(jj) ! latitude boundaries of the physics grid
     46real,intent(in) :: rlonv(ii+1) ! longitudes of the physics grid
     47real,intent(in) :: rlonu(ii+1) ! longitude boundaries of the physics grid
    3848real,intent(in) :: aire(ii+1,jj+1) ! area of the dynamics grid (m2)
    3949real,intent(in) :: cu((ii+1)*(jj+1)) ! cu coeff. (u_covariant = cu * u)
     
    4858character(len=80) :: abort_message
    4959real :: total_area_phy, total_area_dyn
     60real :: pi
    5061
     62! boundaries, on global grid
     63real,allocatable :: boundslon_reg(:,:)
     64real,allocatable :: boundslat_reg(:,:)
    5165
    5266! global array, on full physics grid:
     
    5670real,allocatable :: cvfi(:)
    5771real,allocatable :: airefi(:)
     72
     73pi=2.*asin(1.0)
    5874
    5975IF (nlayer.NE.klev) THEN
     
    7692
    7793!call init_phys_lmdz(iim,jjm+1,llm,1,(/(jjm-1)*iim+2/))
     94
     95! init regular global longitude-latitude grid points and boundaries
     96ALLOCATE(boundslon_reg(ii,2))
     97ALLOCATE(boundslat_reg(jj+1,2))
     98 
     99DO i=1,ii
     100   boundslon_reg(i,east)=rlonu(i)
     101   boundslon_reg(i,west)=rlonu(i+1)
     102ENDDO
     103
     104boundslat_reg(1,north)= PI/2
     105boundslat_reg(1,south)= rlatv(1)
     106DO j=2,jj
     107   boundslat_reg(j,north)=rlatv(j-1)
     108   boundslat_reg(j,south)=rlatv(j)
     109ENDDO
     110boundslat_reg(jj+1,north)= rlatv(jj)
     111boundslat_reg(jj+1,south)= -PI/2
     112
     113! Write values in module regular_lonlat_mod
     114CALL init_regular_lonlat(ii,jj+1, rlonv(1:ii), rlatu, &
     115                         boundslon_reg, boundslat_reg)
    78116
    79117! Generate global arrays on full physics grid
     
    144182
    145183end subroutine iniphysiq
     184
     185
     186END MODULE iniphysiq_mod
Note: See TracChangeset for help on using the changeset viewer.