Ignore:
Timestamp:
Oct 12, 2016, 2:53:20 PM (8 years ago)
Author:
dcugnet
Message:
  • A (re)startphy.nc file (standard name: "startphy0.nc") can be read by ce0l to get land mask, so mask can be defined (in decreasing priority order) from: 1) "o2a.nc file" if this file is found 2) "startphy0.nc" if this file is found 3) "Relief.nc" otherwise
  • Sub-cell scales parameters for orographic gravity waves can be read from file "oro_params.nc" if the configuration key "read_orop" is TRUE. The effect is to bypass the "grid_noro" routine in ce0l, so that any pre-defined mask (from o2a.nc or startphy0.nc) is then overwritten.
  • The gcm stops if the "limit.nc" records number differs from the current year number of days. A warning is issued in case the gcm calendar does not match the time axis attribute "calendar" (if available) from the "limit.nc" file. This attribute is now added to the "limit.nc" time axis.
  • Few simplifications in grid_noro
  • Few parameters changes in acama_gwd and flott_gwd.
  • Variable d_u can be saved in the outputs.
Location:
LMDZ5/trunk/libf/dynphy_lonlat/phylmd
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dynphy_lonlat/phylmd/ce0l.F90

    r2603 r2665  
    1212!     * "masque" can be:
    1313!       - read from file "o2a.nc"          (for coupled runs).
     14!       - read from file "startphy0.nc"    (from a previous run).
    1415!       - created in etat0phys or etat0dyn (for forced  runs).
    1516!     It is then passed to limit_netcdf to ensure consistancy.
     
    2021  USE etat0phys,      ONLY: etat0phys_netcdf
    2122  USE limit,          ONLY: limit_netcdf
    22   USE netcdf,         ONLY: NF90_OPEN, NF90_NOWRITE, NF90_CLOSE, NF90_NOERR
     23  USE netcdf,         ONLY: NF90_OPEN, NF90_NOWRITE, NF90_CLOSE, NF90_NOERR,    &
     24         NF90_INQUIRE_DIMENSION, NF90_INQ_DIMID, NF90_INQ_VARID, NF90_GET_VAR
    2325  USE infotrac,       ONLY: type_trac, infotrac_init
    2426  USE dimphy,         ONLY: klon
     
    6062  REAL, ALLOCATABLE  :: lat_omask(:,:), dlat_omask(:), ocetmp (:,:)
    6163  REAL               :: date, lev(1)
     64
     65!--- Local variables for land mask from startphy0 file reading
     66  INTEGER            :: nid_sta, nid_nph, nid_msk, nphys
     67  REAL, ALLOCATABLE  :: masktmp(:)
     68
    6269#ifndef CPP_PARA
    6370! for iniphysiq in serial mode
     
    133140  ENDIF
    134141
    135 !--- LAND MASK. TWO CASES:
     142!--- LAND MASK. THREE CASES:
    136143!   1) read from ocean model    file "o2a.nc"    (coupled runs)
    137 !   2) computed from topography file "Relief.nc" (masque(:,:)=-99999.)
    138 ! Coupled simulations (case 1) use the ocean model mask to compute the
     144!   2) read from previous run   file="startphy0.nc"
     145!   3) computed from topography file "Relief.nc" (masque(:,:)=-99999.)
     146! In the first case, the mask from the ocean model is used compute the
    139147! weights to ensure ocean fractions are the same for atmosphere and ocean.
    140148!*******************************************************************************
    141   IF(NF90_OPEN("o2a.nc", NF90_NOWRITE, nid_o2a)/=NF90_NOERR) THEN
    142     WRITE(lunout,*)'BEWARE !! No ocean mask "o2a.nc" file found'
    143     WRITE(lunout,*)'Forced run.'
    144     masque(:,:)=-99999.
    145   ELSE
     149  IF(NF90_OPEN("o2a.nc", NF90_NOWRITE, nid_o2a)==NF90_NOERR) THEN
    146150    iret=NF90_CLOSE(nid_o2a)
    147151    WRITE(lunout,*)'BEWARE !! Ocean mask "o2a.nc" file found'
     
    175179    masque(iip1 ,:)=masque(1,:)
    176180    DEALLOCATE(ocemask)
     181  ELSE IF(NF90_OPEN("startphy0.nc", NF90_NOWRITE, nid_sta)==NF90_NOERR) THEN
     182    WRITE(lunout,*)'BEWARE !! File "startphy0.nc" found.'
     183    WRITE(lunout,*)'Getting the land mask from a previous run.'
     184    iret=NF90_INQ_DIMID(nid_sta,'points_physiques',nid_nph)
     185    iret=NF90_INQUIRE_DIMENSION(nid_sta,nid_nph,len=nphys)
     186    IF(nphys/=klon) THEN
     187      WRITE(lunout,*)'Mismatching dimensions for land mask'
     188      WRITE(lunout,*)'nphys  = ',nphys ,' klon = ',klon
     189      iret=NF90_CLOSE(nid_sta)
     190      CALL abort_gcm(modname,'',1)
     191    END IF
     192    ALLOCATE(masktmp(klon))
     193    iret=NF90_INQ_VARID(nid_sta,'masque',nid_msk)
     194    iret=NF90_GET_VAR(nid_sta,nid_msk,masktmp)
     195    iret=NF90_CLOSE(nid_sta)
     196    CALL gr_fi_dyn(1,klon,iip1,jjp1,masktmp,masque)
     197    IF(prt_level>=1) THEN
     198      WRITE(fmt,"(i4,'i1)')")iip1 ; fmt='('//ADJUSTL(fmt)
     199      WRITE(lunout,*)'LAND MASK :'
     200      WRITE(lunout,fmt) NINT(masque)
     201    END IF
     202    DEALLOCATE(masktmp)
     203  ELSE
     204    WRITE(lunout,*)'BEWARE !! No ocean mask "o2a.nc" file or "startphy0.nc" file found'
     205    WRITE(lunout,*)'Land mask will be built from the topography file.'
     206    masque(:,:)=-99999.
    177207  END IF
    178208  phis(:,:)=-99999.
  • LMDZ5/trunk/libf/dynphy_lonlat/phylmd/etat0phys_netcdf.F90

    r2644 r2665  
    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,:)
  • LMDZ5/trunk/libf/dynphy_lonlat/phylmd/limit_netcdf.F90

    r2603 r2665  
    7171  USE netcdf95,           ONLY: nf95_def_var, nf95_put_att, nf95_put_var
    7272  USE comconst_mod, ONLY: pi
     73  USE phys_cal_mod, ONLY: calend
    7374  IMPLICIT NONE
    7475!-------------------------------------------------------------------------------
     
    244245  !--- Attributes creation
    245246  CALL ncerr(NF90_PUT_ATT(nid,id_tim, "title","Jour dans l annee"),fnam)
     247  CALL ncerr(NF90_PUT_ATT(nid,id_tim, "calendar",calend),fnam)
    246248  CALL ncerr(NF90_PUT_ATT(nid,id_FOCE,"title","Fraction ocean"),fnam)
    247249  CALL ncerr(NF90_PUT_ATT(nid,id_FSIC,"title","Fraction glace de mer"),fnam)
     
    405407      CASE('SIC', 'SST'); cal_in='gregorian'
    406408    END SELECT
    407   CALL msg(5,'WARNING: missing "calendar" attribute for "time" in '&
     409    CALL msg(5,'WARNING: missing "calendar" attribute for "time" in '&
    408410     &//TRIM(fnam)//'. Choosing default value.')
    409411  END IF
     412  CALL strclean(cal_in)                     !--- REMOVE (WEIRD) NULL CHARACTERS
    410413  CALL msg(5,'var, calendar, dim: '//TRIM(dnam)//' '//TRIM(cal_in), lmdep)
    411414 
     
    477480  fnam_p=fnam(1:idx)//'_p.nc'
    478481  IF(NF90_OPEN(fnam_p,NF90_NOWRITE,ncid)==NF90_NOERR) THEN
    479     CALL msg(0,'Reading previous year file ("'//TRIM(fnam_p)//'") first record for '//TRIM(title))
     482    CALL msg(0,'Reading next year file ("'//TRIM(fnam_p)//'") first record for '//TRIM(title))
    480483    CALL ncerr(NF90_INQ_VARID(ncid, varname, varid),fnam_p)
    481484    CALL ncerr(NF90_GET_VAR(ncid,varid,champ,[1,1,1],[imdep,jmdep,1]),fnam_p)
     
    767770!-------------------------------------------------------------------------------
    768771
     772
     773!-------------------------------------------------------------------------------
     774!
     775SUBROUTINE strclean(s)
     776!
     777!-------------------------------------------------------------------------------
     778  IMPLICIT NONE
     779!-------------------------------------------------------------------------------
     780! Purpose: Remove tail null characters from the input string.
     781!-------------------------------------------------------------------------------
     782! Parameters:
     783  CHARACTER(LEN=*), INTENT(INOUT) :: s
     784!-------------------------------------------------------------------------------
     785! Local variable:
     786  INTEGER :: k
     787!-------------------------------------------------------------------------------
     788  k=LEN_TRIM(s); DO WHILE(ICHAR(s(k:k))==0); s(k:k)=' '; k=LEN_TRIM(s); END DO
     789
     790END SUBROUTINE strclean
     791!
     792!-------------------------------------------------------------------------------
     793
    769794#endif
    770795! of #ifndef CPP_1D
Note: See TracChangeset for help on using the changeset viewer.