Changeset 2766


Ignore:
Timestamp:
Jan 19, 2017, 4:56:16 PM (7 years ago)
Author:
dcugnet
Message:
  • Fix limit_netcdf to handle correctly files with sea ice concentration in fractions and not percents. CMIP6 official files have "units" attribute equal to "1.0" with a null end character.
  • Extraction of few calendar-related functions in cal_tools_m.F90.
Location:
LMDZ5/trunk/libf
Files:
1 added
1 edited

Legend:

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

    r2665 r2766  
    1717!-------------------------------------------------------------------------------
    1818
    19   USE ioipsl,             ONLY: flininfo, flinopen, flinget, flinclo,          &
    20    ioconf_calendar, ioget_calendar, lock_calendar, ioget_mon_len, ioget_year_len
     19  USE ioipsl,             ONLY: flininfo, flinopen, flinget, flinclo
    2120  USE assert_eq_m,        ONLY: assert_eq
     21  USE cal_tools_m,        ONLY: year_len, mid_month
    2222  USE conf_dat_m,         ONLY: conf_dat2d, conf_dat3d
    2323  USE dimphy,             ONLY: klon, zmasq
    24   USE geometry_mod, ONLY: longitude_deg, latitude_deg
     24  USE geometry_mod,       ONLY: longitude_deg, latitude_deg
    2525  USE phys_state_var_mod, ONLY: pctsrf
    26   USE control_mod, ONLY: anneeref
     26  USE control_mod,        ONLY: anneeref
    2727  USE init_ssrf_m,        ONLY: start_init_subsurf
    2828
     
    123123
    124124!--- Beware: anneeref (from gcm.def) is used to determine output time sampling
    125   ndays=ioget_year_len(anneeref)
     125  ndays=year_len(anneeref)
    126126
    127127!--- RUGOSITY TREATMENT --------------------------------------------------------
     
    375375!--- Read unit for sea-ice variable only
    376376  IF (mode=='SIC') THEN
    377     IF(NF90_GET_ATT(ncid, varid, 'units', unit_sic)/=NF90_NOERR) THEN
     377    ierr=NF90_GET_ATT(ncid, varid, 'units', unit_sic); CALL strclean(unit_sic)
     378    IF(ierr/=NF90_NOERR) THEN
    378379      CALL msg(5,'No unit in sea-ice file. Take percentage as default value')
    379380      unit_sic='X'
     381    ELSE IF(ANY(["%  ","1.0","1  "]==unit_sic)) THEN
     382      CALL msg(5,'Sea-ice cover has unit='//TRIM(unit_sic))
    380383    ELSE
    381       CALL msg(5,'Sea-ice cover has unit='//TRIM(unit_sic))
     384      CALL abort_physic('SIC','Unrecognized unit for sea-ice file: '&
     385        //TRIM(unit_sic),1)
    382386    END IF
    383387  END IF
     
    418422!--- Rebuilding input time vector (field from input file might be unreliable)
    419423  IF(lmdep==12) THEN
    420     timeyear=mid_month(anneeref, cal_in, ndays_in)
     424    timeyear=mid_month(anneeref, cal_in)
    421425    CALL msg(0,'Monthly input file(s) for '//TRIM(title)//'.')
    422426  ELSE IF(lmdep==ndays_in) THEN
     
    426430    WRITE(mess,'(a,i3,a,i3,a)')'Mismatching input file: found',lmdep,        &
    427431      ' records, 12/',ndays_in,' (monthly/daily needed).'
    428     CALL abort_physic('mid_months',TRIM(mess),1)
     432    CALL abort_physic('mid_month',TRIM(mess),1)
    429433  END IF
    430434
     
    433437  IF(extrp) ALLOCATE(work(imdep, jmdep))
    434438  CALL msg(5,'')
    435   CALL msg(5,'LECTURE ET INTERPOLATION HORIZ. DE ', lmdep, ' CHAMPS.')
     439  CALL msg(5,'READ AND INTERPOLATE HORIZONTALLY ', lmdep, ' FIELDS.')
    436440  CALL ncerr(NF90_INQ_VARID(ncid, varname, varid), fnam)
    437441  DO l=1, lmdep
    438442    CALL ncerr(NF90_GET_VAR(ncid,varid,champ,[1,1,l],[imdep,jmdep,1]),fnam)
     443    !--- Check whether values are acceptable for SIC, depending on unit.
     444    IF(mode=='SIC') THEN
     445      IF(TRIM(unit_sic)=="1".OR.TRIM(unit_sic)=="1.0") THEN
     446        IF(ANY(champ>1.0+EPSFRA)) &
     447          CALL abort_physic('SIC','Found sea-ice fractions greater than 1.')
     448      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.')
     451      END IF
     452    END IF
    439453    CALL conf_dat2d(title, dlon_ini, dlat_ini, dlon, dlat, champ, .TRUE.)
    440454    IF(extrp) CALL extrapol(champ,imdep,jmdep,999999.,.TRUE.,.TRUE.,2,work)
    441455    IF(l==1) THEN
    442456      CALL msg(5,"----------------------------------------------------------")
    443       CALL msg(5,"$$$ Interpolation barycentrique pour "//TRIM(title)//" $$$")
     457      CALL msg(5,"$$$ Barycentrique interpolation for "//TRIM(title)//" $$$")
    444458      CALL msg(5,"----------------------------------------------------------")
    445459    END IF
     
    504518     IF(ndays/=ndays_in) THEN
    505519        WRITE(lunout, *)
    506         WRITE(lunout,*)'DIFFERENTES LONGEURS D ANNEES:'
    507         WRITE(lunout,*)' Dans le fichier d entree: ',ndays_in
    508         WRITE(lunout,*)' Dans le fichier de sortie: ',ndays
     520        WRITE(lunout,*)'DIFFERENT YEAR LENGTHS:'
     521        WRITE(lunout,*)' In the input file: ',ndays_in
     522        WRITE(lunout,*)' In the output file: ',ndays
    509523     END IF
    510524     IF(lmdep==ndays_in) THEN
    511525        WRITE(lunout, *)
    512         WRITE(lunout, *)'PAS D INTERPOLATION TEMPORELLE.'
    513         WRITE(lunout, *)' Fichier journalier en entree.'
     526        WRITE(lunout, *)'NO TIME INTERPOLATION.'
     527        WRITE(lunout, *)' Daily input file.'
    514528     ELSE
    515         WRITE(lunout, *)'INTERPOLATION TEMPORELLE.'
    516         WRITE(lunout, *)' Vecteur temps en entree: ', timeyear
    517         WRITE(lunout, *)' Vecteur temps en sortie de 0 a ', ndays-1
     529        WRITE(lunout, *)'TIME INTERPOLATION.'
     530        WRITE(lunout, *)' Input time vector: ', timeyear
     531        WRITE(lunout, *)' Output time vector from 0 to ', ndays-1
    518532     END IF
    519533  END IF
     
    542556  DO j=1, jjp1
    543557    CALL minmax(iip1, champan(1, j, 10), chmin, chmax)
    544     IF (prt_level>5) WRITE(lunout, *)' ',TRIM(title),' au temps 10 ', chmin, chmax, j
     558    IF (prt_level>5) WRITE(lunout, *)' ',TRIM(title),' at time 10 ', chmin, chmax, j
    545559  END DO
    546560
    547561!--- SPECIAL FILTER FOR SST: SST>271.38 --------------------------------------
    548562  IF(mode=='SST') THEN
    549     CALL msg(5,'Filtrage de la SST: SST >= 271.38')
     563    CALL msg(0,'Filtering SST: SST >= 271.38')
    550564    WHERE(champan<271.38) champan=271.38
    551565  END IF
     
    553567!--- SPECIAL FILTER FOR SIC: 0.0<SIC<1.0 -------------------------------------
    554568  IF(mode=='SIC') THEN
    555     CALL msg(5,'Filtrage de la SIC: 0.0 < Sea-ice < 1.0')
    556 
    557     IF (unit_sic=='1') THEN
     569    CALL msg(0,'Filtering SIC: 0.0 < Sea-ice < 1.0')
     570    IF(TRIM(unit_sic)=="1".OR.TRIM(unit_sic)=="1.0") THEN
    558571       ! Nothing to be done for sea-ice field is already in fraction of 1
    559572       ! This is the case for sea-ice in file cpl_atm_sic.nc
    560        CALL msg(5,'Sea-ice field already in fraction of 1')
     573       CALL msg(0,'Sea-ice field already in fraction of 1')
    561574    ELSE
    562575       ! Convert sea ice from percentage to fraction of 1
    563        CALL msg(5,'Transformt sea-ice field from percentage to fraction of 1.')
     576       CALL msg(0,'Sea-ice field converted from percentage to fraction of 1.')
    564577       champan(:, :, :)=champan(:, :, :)/100.
    565578    END IF
    566 
    567579    champan(iip1, :, :)=champan(1, :, :)
    568580    WHERE(champan>1.0) champan=1.0
     
    647659!-------------------------------------------------------------------------------
    648660!
    649 FUNCTION year_len(y,cal_in)
    650 !
    651 !-------------------------------------------------------------------------------
    652   IMPLICIT NONE
    653 !-------------------------------------------------------------------------------
    654 ! Arguments:
    655   INTEGER                       :: year_len
    656   INTEGER,           INTENT(IN) :: y
    657   CHARACTER(LEN=*),  INTENT(IN) :: cal_in
    658 !-------------------------------------------------------------------------------
    659 ! Local variables:
    660   CHARACTER(LEN=20)             :: cal_out              ! calendar (for outputs)
    661 !-------------------------------------------------------------------------------
    662 !--- Getting the input calendar to reset at the end of the function
    663   CALL ioget_calendar(cal_out)
    664 
    665 !--- Unlocking calendar and setting it to wanted one
    666   CALL lock_calendar(.FALSE.); CALL ioconf_calendar(TRIM(cal_in))
    667 
    668 !--- Getting the number of days in this year
    669   year_len=ioget_year_len(y)
    670 
    671 !--- Back to original calendar
    672   CALL lock_calendar(.FALSE.); CALL ioconf_calendar(TRIM(cal_out))
    673 
    674 END FUNCTION year_len
    675 !
    676 !-------------------------------------------------------------------------------
    677 
    678 
    679 !-------------------------------------------------------------------------------
    680 !
    681 FUNCTION mid_month(y,cal_in,ndays_out)
    682 !
    683 !-------------------------------------------------------------------------------
    684   IMPLICIT NONE
    685 !-------------------------------------------------------------------------------
    686 ! Arguments:
    687   INTEGER,          INTENT(IN) :: y           ! year
    688   CHARACTER(LEN=*), INTENT(IN) :: cal_in      ! calendar
    689   INTEGER,          INTENT(IN) :: ndays_out   ! days   number
    690   REAL,          DIMENSION(14) :: mid_month   ! mid-bins times
    691 !-------------------------------------------------------------------------------
    692 ! Local variables:
    693   CHARACTER(LEN=99)      :: mess              ! error message
    694   CHARACTER(LEN=20)      :: cal_out           ! output calendar
    695   INTEGER, DIMENSION(14) :: tlen              ! months lengths (days)
    696   INTEGER                :: m                 ! months counter
    697   INTEGER                :: nd                ! number of days
    698 !-------------------------------------------------------------------------------
    699   !--- Save the input calendar to reset it at the end of the function
    700   CALL ioget_calendar(cal_out)
    701 
    702   !--- Unlock calendar and set it to "cal_in"
    703   CALL lock_calendar(.FALSE.); CALL ioconf_calendar(TRIM(cal_in))
    704 
    705   !--- Get the length of each month
    706   tlen(1 )=ioget_mon_len(y-1,12)
    707   DO m=1,12; tlen(m+1)=ioget_mon_len(y,m); END DO
    708   tlen(14)=ioget_mon_len(y+1, 1)
    709 
    710   !--- Mid-bins times
    711   mid_month(1)=-0.5*REAL(tlen(1))
    712   DO m=2,14; mid_month(m)=mid_month(m-1)+0.5*REAL(tlen(m-1)+tlen(m)); END DO
    713 
    714   !--- Back to original calendar
    715   CALL lock_calendar(.FALSE.); CALL ioconf_calendar(TRIM(cal_out))
    716 
    717 END FUNCTION mid_month
    718 !
    719 !-------------------------------------------------------------------------------
    720 
    721 
    722 
    723 !-------------------------------------------------------------------------------
    724 !
    725661SUBROUTINE msg(lev,str1,i,str2)
    726662!
Note: See TracChangeset for help on using the changeset viewer.