New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 11932 for branches – NEMO

Changeset 11932 for branches


Ignore:
Timestamp:
2019-11-19T18:45:16+01:00 (4 years ago)
Author:
dcarneir
Message:

Changes in OBS and SBC routines for sea ice thickness data assimilation

Location:
branches/UKMO/dev_r5518_obs_oper_update_sit/NEMOGCM/NEMO/OPA_SRC
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_obs_oper_update_sit/NEMOGCM/NEMO/OPA_SRC/OBS/obs_oper.F90

    r11468 r11932  
    3737   USE obs_grid,      ONLY : &  
    3838      & obs_level_search      
     39#if defined key_cice 
     40   USE ice_constants, ONLY : &    ! For conversion from sea ice freeboard to thickness 
     41      & rhos, rhoi, rhow 
     42#endif 
    3943 
    4044   IMPLICIT NONE 
     
    874878          
    875879         IF ( surfdataqc%lclim ) surfdataqc%rclm(jobs,1) = zclm(1) 
     880 
     881         IF ( TRIM(surfdataqc%cvars(1)) == 'FBD' ) THEN 
     882            ! Convert radar freeboard to true freeboard (add 1/4 snow depth; 1/4 based on ratio of speed of light in vacuum compared to snow (3.0e8 vs 2.4e8 m/s)) 
     883            surfdataqc%rext(jobs,1) = surfdataqc%robs(jobs,1)  
     884            surfdataqc%robs(jobs,1) = surfdataqc%rext(jobs,1) + 0.25*surfdataqc%rext(jobs,2) 
     885            ! If the corrected freeboard observation is outside -0.3 to 3.0 m (CPOM) then set the QC flag to bad 
     886            IF ((surfdataqc%robs(jobs,1) < -0.3) .OR. (surfdataqc%robs(jobs,1) > 3.0)) THEN 
     887               surfdataqc%nqc(jobs) = 4 
     888            ENDIF            
     889            ! Convert corrected freeboard to ice thickness following Tilling et al. (2016) 
     890            surfdataqc%robs(jobs,1) = (surfdataqc%robs(jobs,1)*rhow + surfdataqc%rext(jobs,2)*rhos)/ & 
     891                                      (rhow - rhoi) 
     892            ! Flag any negative ice thickness values as bad 
     893            IF (surfdataqc%robs(jobs,1) < 0.0) THEN 
     894               surfdataqc%nqc(jobs) = 4 
     895            ENDIF                                      
     896         ENDIF 
    876897          
    877898         IF ( zext(1) == obfillflt ) THEN 
  • branches/UKMO/dev_r5518_obs_oper_update_sit/NEMOGCM/NEMO/OPA_SRC/OBS/obs_prep.F90

    r11461 r11932  
    5353 
    5454   SUBROUTINE obs_pre_surf( surfdata, surfdataqc, ld_nea, ld_bound_reject, & 
    55                             kqc_cutoff ) 
     55                            ld_seaicetypes, kqc_cutoff ) 
    5656      !!---------------------------------------------------------------------- 
    5757      !!                    ***  ROUTINE obs_pre_sla  *** 
     
    8383      LOGICAL, INTENT(IN) :: ld_nea                ! Switch for rejecting observation near land 
    8484      LOGICAL, INTENT(IN) :: ld_bound_reject       ! Switch for rejecting obs near the boundary 
    85       INTEGER, INTENT(IN), OPTIONAL :: kqc_cutoff   ! cut off for QC value 
     85      LOGICAL, INTENT(IN) :: ld_seaicetypes        ! Switch to indicate sea ice data 
     86      INTEGER, INTENT(IN), OPTIONAL :: kqc_cutoff  ! cut off for QC value 
    8687      !! * Local declarations 
    8788      INTEGER :: iqc_cutoff = 255   ! cut off for QC value 
     
    140141      ! ----------------------------------------------------------------------- 
    141142 
    142       CALL obs_coo_tim( icycle, & 
    143          &              iyea0,   imon0,   iday0,   ihou0,   imin0,      & 
    144          &              surfdata%nsurf,   surfdata%nyea, surfdata%nmon, & 
    145          &              surfdata%nday,    surfdata%nhou, surfdata%nmin, & 
    146          &              surfdata%nqc,     surfdata%mstp, iotdobs        ) 
     143      IF ( ld_seaicetypes ) THEN 
     144         CALL obs_coo_tim( icycle, & 
     145            &              iyea0,   imon0,   iday0,   ihou0,   imin0,      & 
     146            &              surfdata%nsurf,   surfdata%nyea, surfdata%nmon, & 
     147            &              surfdata%nday,    surfdata%nhou, surfdata%nmin, & 
     148            &              surfdata%nqc,     surfdata%mstp, iotdobs,       & 
     149            &              ld_seaicetypes = ld_seaicetypes ) 
     150      ELSE 
     151         CALL obs_coo_tim( icycle, & 
     152            &              iyea0,   imon0,   iday0,   ihou0,   imin0,      & 
     153            &              surfdata%nsurf,   surfdata%nyea, surfdata%nmon, & 
     154            &              surfdata%nday,    surfdata%nhou, surfdata%nmin, & 
     155            &              surfdata%nqc,     surfdata%mstp, iotdobs        ) 
     156      ENDIF 
    147157 
    148158      CALL obs_mpp_sum_integer( iotdobs, iotdobsmpp ) 
     
    558568      &                    kobsno,                                        & 
    559569      &                    kobsyea, kobsmon, kobsday, kobshou, kobsmin,   & 
    560       &                    kobsqc,  kobsstp, kotdobs                      ) 
     570      &                    kobsqc,  kobsstp, kotdobs, ld_seaicetypes      ) 
    561571      !!---------------------------------------------------------------------- 
    562572      !!                    ***  ROUTINE obs_coo_tim *** 
     
    606616         & kobsstp          ! Number of time steps up to the  
    607617                            ! observation time 
     618      LOGICAL, OPTIONAL, INTENT(IN) :: ld_seaicetypes 
    608619 
    609620      !! * Local declarations 
     
    620631      INTEGER :: iskip 
    621632      INTEGER :: idaystp 
     633      INTEGER :: icecount 
    622634      REAL(KIND=wp) :: zminstp 
    623635      REAL(KIND=wp) :: zhoustp 
     
    714726            CYCLE 
    715727         ENDIF 
     728 
     729         ! Flag sea ice observations falling on initial timestep 
     730           IF ( PRESENT(ld_seaicetypes) ) THEN 
     731 
     732                IF ( ( kobsstp(jobs) == (nit000 - 1) ) ) THEN 
     733                   IF (lwp) WRITE(numout,*)( 'Sea-ice not initialised on zeroth '// & 
     734                             &    'time-step but SIT observation valid then, flagging '// & 
     735                                  'in time check subroutine obs_coo_tim.' ) 
     736                   kobsqc(jobs) = IBSET(kobsqc(jobs),13) 
     737                   kotdobs      = kotdobs + 1 
     738                   CYCLE 
     739                ENDIF 
     740           ENDIF                      
    716741 
    717742      END DO 
  • branches/UKMO/dev_r5518_obs_oper_update_sit/NEMOGCM/NEMO/OPA_SRC/OBS/obs_read_surf.F90

    r11546 r11932  
    380380         surfdata%cext(2) = 'MDT' 
    381381      ENDIF 
     382      IF ( ldmod .AND. ( TRIM( surfdata%cvars(1) ) == 'FBD' ) ) THEN 
     383           surfdata%cext(1) = 'freeboard' 
     384           surfdata%cext(2) = 'thick_s' 
     385      ENDIF 
    382386      IF ( iextr > kextr ) surfdata%cext(iextr) = 'STD' 
    383387 
     
    461465               ! Observed value 
    462466               surfdata%robs(iobs,1) = inpfiles(jj)%pob(1,ji,1) 
     467               IF ( TRIM(surfdata%cvars(1)) == 'FBD' ) THEN 
     468                   surfdata%rext(iobs,1) = inpfiles(jj)%pob(1,ji,1) 
     469                   surfdata%rext(iobs,2) = fbrmdi 
     470               ENDIF 
    463471 
    464472               ! Model and MDT is set to fbrmdi unless read from file 
  • branches/UKMO/dev_r5518_obs_oper_update_sit/NEMOGCM/NEMO/OPA_SRC/OBS/obs_write.F90

    r11546 r11932  
    530530 
    531531         clfiletype = 'sicfb' 
    532          cllongname = 'Sea ice' 
     532         cllongname = 'Sea ice concentration' 
    533533         clunits    = 'Fraction' 
     534         clgrid     = 'T' 
     535 
     536      CASE('SIT') 
     537 
     538         clfiletype = 'sitfb' 
     539         cllongname = 'Sea ice thickness' 
     540         clunits    = 'm' 
    534541         clgrid     = 'T' 
    535542 
  • branches/UKMO/dev_r5518_obs_oper_update_sit/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_ice.F90

    r7960 r11932  
    101101   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fr_iu              !: ice fraction at NEMO U point 
    102102   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fr_iv              !: ice fraction at NEMO V point 
     103   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   thick_iu              !: ice thickness at NEMO U point 
     104   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   thick_iv              !: ice thickness at NEMO V point 
     105   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   thick_su              !: snow depth at NEMO U point 
     106   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   thick_sv              !: snow depth at NEMO V point 
    103107    
    104108   ! variables used in the coupled interface 
     
    156160                wndj_ice(jpi,jpj)     , nfrzmlt(jpi,jpj)      , ss_iou(jpi,jpj)       , & 
    157161                ss_iov(jpi,jpj)       , fr_iu(jpi,jpj)        , fr_iv(jpi,jpj)        , & 
     162                thick_iu(jpi,jpj)     , thick_iv(jpi,jpj)     ,                         & 
     163                thick_su(jpi,jpj)     , thick_sv(jpi,jpj)     ,                         & 
     164                ht_i(jpi,jpj,ncat)    , ht_s(jpi,jpj,ncat)    ,                         & 
    158165                a_i(jpi,jpj,ncat)     , topmelt(jpi,jpj,ncat) , botmelt(jpi,jpj,ncat) , & 
    159166                STAT= ierr(1) ) 
Note: See TracChangeset for help on using the changeset viewer.