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

File:
1 moved

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dynlonlat_phylonlat/phyvenus/iniphysiq_mod.F90

    r1520 r1523  
    1 
     1!
    22! $Id: iniphysiq.F90 2225 2015-03-11 14:55:23Z emillour $
    3 
     3!
     4MODULE iniphysiq_mod
     5
     6CONTAINS
    47
    58SUBROUTINE iniphysiq(iim,jjm,nlayer,punjours, pdayref,ptimestep,         &
    6                      rlatu,rlonv,aire,cu,cv,                             &
     9                     rlatu,rlatv,rlonu,rlonv,aire,cu,cv,                 &
    710                     prad,pg,pr,pcpp,iflag_phys)
    811  USE dimphy, ONLY: klev ! number of atmospheric levels
     
    1922                        rlond, & ! longitudes
    2023                        rlatd ! latitudes
     24  USE regular_lonlat_mod, ONLY : init_regular_lonlat, &
     25                                 east, west, north, south, &
     26                                 north_east, north_west, &
     27                                 south_west, south_east
     28  USE nrtype, ONLY: pi
    2129  IMPLICIT NONE
    2230
     
    3846  INTEGER, INTENT (IN) :: jjm ! number of atompsheric columns along latitudes
    3947  REAL, INTENT (IN) :: rlatu(jjm+1) ! latitudes of the physics grid
     48  REAL, INTENT (IN) :: rlatv(jjm) ! latitude boundaries of the physics grid
    4049  REAL, INTENT (IN) :: rlonv(iim+1) ! longitudes of the physics grid
     50  REAL, INTENT (IN) :: rlonu(iim+1) ! longitude boundaries of the physics grid
    4151  REAL, INTENT (IN) :: aire(iim+1,jjm+1) ! area of the dynamics grid (m2)
    4252  REAL, INTENT (IN) :: cu((iim+1)*(jjm+1)) ! cu coeff. (u_covariant = cu * u)
     
    5262  REAL :: total_area_phy, total_area_dyn
    5363
     64  ! boundaries, on global grid
     65  REAL,ALLOCATABLE :: boundslon_reg(:,:)
     66  REAL,ALLOCATABLE :: boundslat_reg(:,:)
    5467
    5568  ! global array, on full physics grid:
     
    6679    WRITE (lunout, *) 'klev   = ', klev
    6780    abort_message = ''
    68     CALL abort_gcm(modname, abort_message, 1)
     81    CALL abort_gcm(modname, 'Problem with dimensions', 1)
    6982  END IF
    7083
    7184  !call init_phys_lmdz(iim,jjm+1,llm,1,(/(jjm-1)*iim+2/))
    7285 
     86  ! init regular global longitude-latitude grid points and boundaries
     87  ALLOCATE(boundslon_reg(iim,2))
     88  ALLOCATE(boundslat_reg(jjm+1,2))
     89 
     90  DO i=1,iim
     91   boundslon_reg(i,east)=rlonu(i)
     92   boundslon_reg(i,west)=rlonu(i+1)
     93  ENDDO
     94
     95  boundslat_reg(1,north)= PI/2
     96  boundslat_reg(1,south)= rlatv(1)
     97  DO j=2,jjm
     98   boundslat_reg(j,north)=rlatv(j-1)
     99   boundslat_reg(j,south)=rlatv(j)
     100  ENDDO
     101  boundslat_reg(jjm+1,north)= rlatv(jjm)
     102  boundslat_reg(jjm+1,south)= -PI/2
     103
     104  ! Write values in module regular_lonlat_mod
     105  CALL init_regular_lonlat(iim,jjm+1, rlonv(1:iim), rlatu, &
     106                           boundslon_reg, boundslat_reg)
     107
    73108  ! Generate global arrays on full physics grid
    74109  ALLOCATE(latfi(klon_glo),lonfi(klon_glo),cufi(klon_glo),cvfi(klon_glo))
     
    194229
    195230END SUBROUTINE iniphysiq
     231
     232END MODULE iniphysiq_mod
Note: See TracChangeset for help on using the changeset viewer.