Changeset 2889 for LMDZ5


Ignore:
Timestamp:
May 23, 2017, 3:49:54 PM (7 years ago)
Author:
dcugnet
Message:

Change of behaviour for ce0l:

  • The time interpolation of AMIP mid-month boundary conditions datasets (corresponding ce0l standard files/variables names: "amipbc_sst_1x1.bnc/tosbcs", "amipbc_sic_1x1.nc/sicbcs") is no longer using splines, but is now linear. See https://pcmdi.llnl.gov/mips/amip/details
  • New ce0l standard files/variables names "amib_sst_1x1.nc/sst", "amip_sic_1x1.nc/sic" are introduced to allow splines time interpolation with monthly mean observations if needed (not adviced).

Note that splines time interpolation is still used for other fields "BILS", "ALB", "RUG"
and other cases ("amip_sst_1x1.nc" "cpl_atm_sst.nc" "histmth_sst.nc" "sstk.nc" for SST).

File:
1 edited

Legend:

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

    r2775 r2889  
    2828
    2929  CHARACTER(LEN=20), PARAMETER :: &
    30   fsst(4)=['amipbc_sst_1x1.nc   ','cpl_atm_sst.nc      ','histmth_sst.nc      '&
    31           ,'sstk.nc             ']
     30  fsst(5)=['amipbc_sst_1x1.nc   ','amip_sst_1x1.nc     ','cpl_atm_sst.nc      '&
     31          ,'histmth_sst.nc      ','sstk.nc             ']
    3232  CHARACTER(LEN=20), PARAMETER :: &
    33   fsic(4)=['amipbc_sic_1x1.nc   ','cpl_atm_sic.nc      ','histmth_sic.nc      '&
    34           ,'ci.nc               ']
     33  fsic(5)=['amipbc_sic_1x1.nc   ','amip_sic_1x1.nc     ','cpl_atm_sic.nc      '&
     34          ,'histmth_sic.nc      ','ci.nc               ']
    3535  CHARACTER(LEN=10), PARAMETER :: &
    36   vsst(4)=['tosbcs    ','SISUTESW  ','tsol_oce  ','sstk      '], &
    37   vsic(4)=['sicbcs    ','SIICECOV  ','pourc_sic ','ci        ']
     36  vsst(5)=['tosbcs    ','tos       ','SISUTESW  ','tsol_oce  ','sstk      '], &
     37  vsic(5)=['sicbcs    ','sic       ','SIICECOV  ','pourc_sic ','ci        ']
    3838  CHARACTER(LEN=10), PARAMETER :: &
    3939  frugo='Rugos.nc  ', falbe='Albedo.nc ', frelf='Relief.nc ',    &
     
    6161!  *    12/2009: D. Cugnet   (f77->f90, calendars, files from coupled runs)
    6262!  *    04/2016: D. Cugnet   (12/14 recs SST/SIC files: cyclic/interannual runs)
     63!  *    05/2017: D. Cugnet   (linear time interpolation for BCS files)
    6364!-------------------------------------------------------------------------------
    6465#ifndef CPP_1D
     
    102103  INTEGER :: NF90_FORMAT
    103104  INTEGER :: ndays                   !--- Depending on the output calendar
     105  CHARACTER(LEN=256) :: str
    104106
    105107!--- INITIALIZATIONS -----------------------------------------------------------
     
    158160     pctsrf_t(:,is_lic,k)=pctsrf(:,is_lic)       ! land ice
    159161     SELECT CASE(ix_sic)
    160         CASE(2)                                   ! SIC=pICE*(1-LIC-TER) (CPL)
     162        CASE(3)                                   ! SIC=pICE*(1-LIC-TER) (CPL)
    161163        pctsrf_t(:,is_sic,k)=fi_ice(:)*(1.-pctsrf(:,is_lic)-pctsrf(:,is_ter))
    162         CASE(3)                                   ! SIC=pICE            (HIST)
     164        CASE(4)                                   ! SIC=pICE            (HIST)
    163165        pctsrf_t(:,is_sic,k)=fi_ice(:)
    164166        CASE DEFAULT                              ! SIC=pICE-LIC   (AMIP,ERAI)
     
    223225  CALL ncerr(NF90_CREATE(fnam,NF90_CLOBBER,nid),fnam)
    224226  CALL ncerr(NF90_PUT_ATT(nid,NF90_GLOBAL,"title","Fichier conditions aux limites"),fnam)
     227  str='File produced using ce0l executable.'
     228  str=TRIM(str)//NEW_LINE(' ')//'Sea Ice Concentration built from'
     229  SELECT CASE(ix_sic)
     230    CASE(1); str=TRIM(str)//' Amip mid-month boundary condition (BCS).'
     231    CASE(2); str=TRIM(str)//' Amip monthly mean observations.'
     232    CASE(3); str=TRIM(str)//' IPSL coupled model outputs.'
     233    CASE(4); str=TRIM(str)//' LMDZ model outputs.'
     234    CASE(5); str=TRIM(str)//' ci.nc file.'
     235  END SELECT
     236  str=TRIM(str)//NEW_LINE(' ')//'Sea Surface Temperature built from'
     237  SELECT CASE(ix_sst)
     238    CASE(1); str=TRIM(str)//' Amip mid-month boundary condition (BCS).'
     239    CASE(2); str=TRIM(str)//' Amip monthly mean observations.'
     240    CASE(3); str=TRIM(str)//' IPSL coupled model outputs.'
     241    CASE(4); str=TRIM(str)//' LMDZ model outputs.'
     242    CASE(5); str=TRIM(str)//' sstk.nc file.'
     243  END SELECT
     244  CALL ncerr(NF90_PUT_ATT(nid,NF90_GLOBAL,"history",TRIM(str)),fnam)
    225245
    226246  !--- Dimensions creation
     
    348368  REAL, ALLOCATABLE :: work(:,:)          ! used for extrapolation
    349369  CHARACTER(LEN=128):: title, mess        ! for messages
     370  LOGICAL           :: is_bcs             ! flag for BCS data
    350371  LOGICAL           :: extrp              ! flag for extrapolation
    351   REAL              :: chmin, chmax
     372  REAL              :: chmin, chmax, timeday, al
    352373  INTEGER ierr, idx
    353374  integer n_extrap ! number of extrapolated points
     
    365386  END SELECT
    366387  extrp=.FALSE.; IF(PRESENT(flag).AND.mode=='SST') extrp=flag
     388  is_bcs=(mode=='SIC'.AND.ix_sic==1).OR.(mode=='SST'.AND.ix_sst==1)
    367389  idx=INDEX(fnam,'.nc')-1
    368390
     
    442464    CALL ncerr(NF90_GET_VAR(ncid,varid,champ,[1,1,l],[imdep,jmdep,1]),fnam)
    443465    !--- Check whether values are acceptable for SIC, depending on unit.
    444     IF(mode=='SIC') THEN
     466    !--- Dropped for mid-month boundary conditions datasets (BCS, ix_sic==1)
     467    IF(mode=='SIC'.AND.ix_sic/=1) THEN
    445468      IF(TRIM(unit_sic)=="1".OR.TRIM(unit_sic)=="1.0") THEN
    446469        IF(ANY(champ>1.0+EPSFRA)) &
    447470          CALL abort_physic('SIC','Found sea-ice fractions greater than 1.')
    448471      ELSE IF(TRIM(unit_sic)=="X".OR.TRIM(unit_sic)=="%") THEN
    449 !        IF(ANY(champ>100.0+EPSFRA)) &
    450 !          CALL abort_physic('SIC','Found sea-ice percentages greater than 100.')
     472        IF(ANY(champ>100.0+EPSFRA)) &
     473          CALL abort_physic('SIC','Found sea-ice percentages greater than 100.')
    451474        IF(MAXVAL(champ)< 1.01) &
    452475          CALL abort_physic('SIC','All sea-ice percentages lower than 1.')
     
    529552        WRITE(lunout, *)' Daily input file.'
    530553     ELSE
    531         WRITE(lunout, *)'TIME INTERPOLATION.'
     554        IF(     is_bcs) WRITE(lunout, *)'LINEAR TIME INTERPOLATION.'
     555        IF(.NOT.is_bcs) WRITE(lunout, *)'SPLINES TIME INTERPOLATION.'
    532556        WRITE(lunout, *)' Input time vector: ', timeyear
    533557        WRITE(lunout, *)' Output time vector from 0 to ', ndays-1
    534558     END IF
    535559  END IF
    536   ALLOCATE(yder(lmdep+2), champan(iip1, jjp1, ndays))
    537   IF(lmdep==ndays_in) THEN
     560  ALLOCATE(champan(iip1, jjp1, ndays))
     561
     562  IF(lmdep==ndays_in) THEN  !--- DAILY DATA: NO     TIME INTERPOLATION
    538563     champan(1:iim,:,:)=champtime
    539   ELSE
     564  ELSE IF(is_bcs) THEN      !--- BCS   DATA: LINEAR TIME INTERPOLATION
     565    l=1
     566    DO k=1, ndays
     567      timeday = REAL((k-1)*ndays_in)/ndays
     568      IF(timeyear(l+1)<timeday) l=l+1
     569      al=(timeday-timeyear(l))/(timeyear(l+1)-timeyear(l))
     570      DO j=1, jjp1
     571        DO i=1, iim
     572          champan(i,j,k) = champtime(i,j,l)+al*(champtime(i,j,l+1)-champtime(i,j,l))
     573        END DO
     574      END DO
     575    END DO
     576  ELSE                      !--- AVE   DATA: SPLINE TIME INTERPOLATION
    540577     skip = .false.
    541578     n_extrap = 0
     579     ALLOCATE(yder(lmdep+2))
    542580     DO j=1, jjp1
    543581       DO i=1, iim
     
    551589     END DO
    552590     IF(n_extrap /= 0) WRITE(lunout,*) "get_2Dfield pchfe_95: n_extrap = ", n_extrap
     591     DEALLOCATE(yder)
    553592  END IF
    554593  champan(iip1, :, :)=champan(1, :, :)
    555   DEALLOCATE(yder, champtime, timeyear)
     594  DEALLOCATE(champtime, timeyear)
    556595
    557596!--- Checking the result
Note: See TracChangeset for help on using the changeset viewer.