Ignore:
Timestamp:
Nov 30, 2016, 1:28:41 PM (8 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes r2664:2719 into testing branch

Location:
LMDZ5/branches/testing
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/dynphy_lonlat/phylmd/etat0phys_netcdf.F90

    r2669 r2720  
    5959  INTEGER,            SAVE      :: iml_phys, jml_phys, llm_phys, ttm_phys, fid_phys
    6060  REAL, ALLOCATABLE,  SAVE      :: lon_phys(:,:), lat_phys(:,:), levphys_ini(:)
     61  CHARACTER(LEN=256), PARAMETER :: oroparam="oro_params.nc"
    6162  CHARACTER(LEN=256), PARAMETER :: orofname="Relief.nc", orogvar="RELIEF"
    6263  CHARACTER(LEN=256), PARAMETER :: phyfname="ECPHY.nc",  psrfvar="SP"
     
    255256!   This routine launch grid_noro, which computes parameters for SSO scheme as
    256257!   described in LOTT & MILLER (1997) and LOTT(1999).
     258!   In case the file oroparam is present and the key read_orop is activated,
     259!   grid_noro is bypassed and sub-cell parameters are read from the file.
    257260!===============================================================================
    258   USE grid_noro_m, ONLY: grid_noro
     261  USE grid_noro_m, ONLY: grid_noro, read_noro
     262  USE logic_mod,   ONLY: read_orop
    259263  IMPLICIT NONE
    260264!-------------------------------------------------------------------------------
     
    266270  CHARACTER(LEN=256) :: modname
    267271  INTEGER            :: fid, llm_tmp,ttm_tmp, iml,jml, iml_rel,jml_rel, itau(1)
     272  INTEGER            :: ierr
    268273  REAL               :: lev(1), date, dt
    269274  REAL, ALLOCATABLE  :: lon_rad(:), lon_ini(:), lon_rel(:,:), relief_hi(:,:)
     
    306311  ALLOCATE(zpic0(iml,jml),zval0(iml,jml)) !--- Peaks and valley heights
    307312
     313!--- READ SUB-CELL SCALES PARAMETERS FROM A FILE (AT RIGHT RESOLUTION)
     314  OPEN(UNIT=66,FILE=oroparam,STATUS='OLD',IOSTAT=ierr)
     315  IF(ierr==0.AND.read_orop) THEN
     316    CLOSE(UNIT=66)
     317    CALL read_noro(lon_in,lat_in,oroparam,                                     &
     318                   phis,zmea0,zstd0,zsig0,zgam0,zthe0,zpic0,zval0,masque)
     319  ELSE
    308320!--- CALL OROGRAPHY MODULE TO COMPUTE FIELDS
    309   CALL grid_noro(lon_rad,lat_rad,relief_hi,lon_in,lat_in,phis,zmea0,zstd0,     &
    310                                       zsig0,zgam0,zthe0,zpic0,zval0,masque)
     321    CALL grid_noro(lon_rad,lat_rad,relief_hi,lon_in,lat_in,                    &
     322                   phis,zmea0,zstd0,zsig0,zgam0,zthe0,zpic0,zval0,masque)
     323  END IF
    311324  phis = phis * 9.81
    312325  phis(iml,:) = phis(1,:)
Note: See TracChangeset for help on using the changeset viewer.