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.
File:
1 edited

Legend:

Unmodified
Added
Removed
  • 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.