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 7784 for branches – NEMO

Changeset 7784 for branches


Ignore:
Timestamp:
2017-03-10T17:12:32+01:00 (7 years ago)
Author:
cetlod
Message:

Bugfix on NEMO restartability in coupled mode when using ISF, see ticket #1863

Location:
branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/OPA_SRC
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/OPA_SRC/SBC/sbcisf.F90

    r7607 r7784  
    3232   PRIVATE 
    3333 
    34    PUBLIC   sbc_isf, sbc_isf_div, sbc_isf_alloc  ! routine called in sbcmod and divcur 
     34   PUBLIC   sbc_isf, sbc_isf_init, sbc_isf_div, sbc_isf_alloc  ! routine called in sbcmod and divcur 
    3535 
    3636   ! public in order to be able to output then  
     
    8383  
    8484  SUBROUTINE sbc_isf(kt) 
     85 
    8586    INTEGER, INTENT(in)          ::   kt         ! ocean time step 
    86     INTEGER                      ::   ji, jj, jk, ijkmin, inum, ierror 
     87    INTEGER                      ::   ji, jj, jk 
    8788    INTEGER                      ::   ikt, ikb   ! top and bottom level of the isf boundary layer 
    88     REAL(wp)                     ::   rmin 
    8989    REAL(wp)                     ::   zhk 
    9090    REAL(wp)                     ::   zt_frz, zpress 
    91     CHARACTER(len=256)           ::   cfisf , cvarzisf, cvarhisf   ! name for isf file 
    92     CHARACTER(LEN=256)           :: cnameis                     ! name of iceshelf file 
    93     CHARACTER (LEN=32)           :: cvarLeff                    ! variable name for efficient Length scale 
    94     INTEGER           ::   ios           ! Local integer output status for namelist read 
    95  
    9691    REAL(wp), DIMENSION(:,:,:), POINTER :: zfwfisf3d, zqhcisf3d, zqlatisf3d 
    9792    REAL(wp), DIMENSION(:,:  ), POINTER :: zqhcisf2d 
    9893    REAL(wp)                            :: zhisf 
    9994 
    100       ! 
    101       !!--------------------------------------------------------------------- 
    102       NAMELIST/namsbc_isf/ nn_isfblk, rn_hisf_tbl, ln_divisf, ln_conserve, rn_gammat0, rn_gammas0, nn_gammablk, & 
    103                          & sn_fwfisf, sn_qisf, sn_rnfisf, sn_depmax_isf, sn_depmin_isf, sn_Leff_isf 
    104       ! 
    105       ! 
    106       !                                         ! ====================== ! 
    107       IF( kt == nit000 ) THEN                   !  First call kt=nit000  ! 
    108          !                                      ! ====================== ! 
    109          REWIND( numnam_ref )              ! Namelist namsbc_rnf in reference namelist : Runoffs  
    110          READ  ( numnam_ref, namsbc_isf, IOSTAT = ios, ERR = 901) 
    111 901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_isf in reference namelist', lwp ) 
    112  
    113          REWIND( numnam_cfg )              ! Namelist namsbc_rnf in configuration namelist : Runoffs 
    114          READ  ( numnam_cfg, namsbc_isf, IOSTAT = ios, ERR = 902 ) 
    115 902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_isf in configuration namelist', lwp ) 
    116          IF(lwm) WRITE ( numond, namsbc_isf ) 
    117  
    118  
    119          IF ( lwp ) WRITE(numout,*) 
    120          IF ( lwp ) WRITE(numout,*) 'sbc_isf: heat flux of the ice shelf' 
    121          IF ( lwp ) WRITE(numout,*) '~~~~~~~~~' 
    122          IF ( lwp ) WRITE(numout,*) 'sbcisf :'  
    123          IF ( lwp ) WRITE(numout,*) '~~~~~~~~' 
    124          IF ( lwp ) WRITE(numout,*) '        nn_isf      = ', nn_isf 
    125          IF ( lwp ) WRITE(numout,*) '        nn_isfblk   = ', nn_isfblk 
    126          IF ( lwp ) WRITE(numout,*) '        rn_hisf_tbl = ', rn_hisf_tbl 
    127          IF ( lwp ) WRITE(numout,*) '        ln_divisf   = ', ln_divisf  
    128          IF ( lwp ) WRITE(numout,*) '        nn_gammablk = ', nn_gammablk  
    129          IF ( lwp ) WRITE(numout,*) '        rn_tfri2    = ', rn_tfri2  
    130          IF (ln_divisf) THEN       ! keep it in the namelist ??? used true anyway as for runoff ? (PM) 
    131             rdivisf = 1._wp 
    132          ELSE 
    133             rdivisf = 0._wp 
    134          END IF 
    135          ! 
    136          ! Allocate public variable 
    137          IF ( sbc_isf_alloc()  /= 0 )         CALL ctl_stop( 'STOP', 'sbc_isf : unable to allocate arrays' ) 
    138          ! 
    139          ! initialisation 
    140          qisf(:,:)        = 0._wp  ; fwfisf(:,:) = 0._wp 
    141          risf_tsc(:,:,:)  = 0._wp 
    142          ! 
    143          ! define isf tbl tickness, top and bottom indice 
    144          IF      (nn_isf == 1) THEN 
    145             rhisf_tbl(:,:) = rn_hisf_tbl 
    146             misfkt(:,:)    = mikt(:,:)         ! same indice for bg03 et cav => used in isfdiv 
    147          ELSE IF ((nn_isf == 3) .OR. (nn_isf == 2)) THEN 
    148             IF( .NOT.l_isfcpl ) THEN 
    149                ALLOCATE( sf_rnfisf(1), STAT=ierror ) 
    150                ALLOCATE( sf_rnfisf(1)%fnow(jpi,jpj,1), sf_rnfisf(1)%fdta(jpi,jpj,1,2) ) 
    151                CALL fld_fill( sf_rnfisf, (/ sn_rnfisf /), cn_dirisf, 'sbc_isf_init', 'read fresh water flux isf data', 'namsbc_isf' ) 
    152              ENDIF 
    153  
    154             !: read effective lenght (BG03) 
    155             IF (nn_isf == 2) THEN 
    156                ! Read Data and save some integral values 
    157                CALL iom_open( sn_Leff_isf%clname, inum ) 
    158                cvarLeff  = 'soLeff'               !: variable name for Efficient Length scale 
    159                CALL iom_get( inum, jpdom_data, cvarLeff, risfLeff , 1) 
    160                CALL iom_close(inum) 
    161                ! 
    162                risfLeff = risfLeff*1000           !: convertion in m 
    163             END IF 
    164  
    165            ! read depth of the top and bottom of the isf top boundary layer (in this case, isf front depth and grounding line depth) 
    166             CALL iom_open( sn_depmax_isf%clname, inum ) 
    167             cvarhisf = TRIM(sn_depmax_isf%clvar) 
    168             CALL iom_get( inum, jpdom_data, cvarhisf, rhisf_tbl, 1) !: depth of deepest point of the ice shelf base 
    169             CALL iom_close(inum) 
    170             ! 
    171             CALL iom_open( sn_depmin_isf%clname, inum ) 
    172             cvarzisf = TRIM(sn_depmin_isf%clvar) 
    173             CALL iom_get( inum, jpdom_data, cvarzisf, rzisf_tbl, 1) !: depth of shallowest point of the ice shelves base 
    174             CALL iom_close(inum) 
    175             ! 
    176             rhisf_tbl(:,:) = rhisf_tbl(:,:) - rzisf_tbl(:,:)        !: tickness isf boundary layer 
    177  
    178            !! compute first level of the top boundary layer 
    179            DO ji = 1, jpi 
    180               DO jj = 1, jpj 
    181                   jk = 2 
    182                   DO WHILE ( jk .LE. mbkt(ji,jj) .AND. gdepw_0(ji,jj,jk) < rzisf_tbl(ji,jj) ) ;  jk = jk + 1 ;  END DO 
    183                   misfkt(ji,jj) = jk-1 
    184                END DO 
    185             END DO 
    186  
    187          ELSE IF ( nn_isf == 4 ) THEN 
    188             ! as in nn_isf == 1 
    189             rhisf_tbl(:,:) = rn_hisf_tbl 
    190             misfkt(:,:)    = mikt(:,:)         ! same indice for bg03 et cav => used in isfdiv 
    191              
    192             ! load variable used in fldread (use for temporal interpolation of isf fwf forcing) 
    193             IF( .NOT.l_isfcpl ) THEN 
    194                ALLOCATE( sf_fwfisf(1), sf_qisf(1), STAT=ierror ) 
    195                ALLOCATE( sf_fwfisf(1)%fnow(jpi,jpj,1), sf_fwfisf(1)%fdta(jpi,jpj,1,2) ) 
    196                ALLOCATE( sf_qisf(1)%fnow(jpi,jpj,1), sf_qisf(1)%fdta(jpi,jpj,1,2) ) 
    197                CALL fld_fill( sf_fwfisf, (/ sn_fwfisf /), cn_dirisf, 'sbc_isf_init', 'read fresh water flux isf data', 'namsbc_isf' ) 
    198                !CALL fld_fill( sf_qisf  , (/ sn_qisf   /), cn_dirisf, 'sbc_isf_init', 'read heat flux isf data'       , 'namsbc_isf' ) 
    199             ENDIF 
    200          END IF 
    201           
    202          ! save initial top boundary layer thickness          
    203          rhisf_tbl_0(:,:) = rhisf_tbl(:,:) 
    204  
    205       END IF 
    206  
    207       !                                            ! ---------------------------------------- ! 
    208       IF( kt /= nit000 ) THEN                      !          Swap of forcing fields          ! 
    209          !                                         ! ---------------------------------------- ! 
    210          fwfisf_b  (:,:  ) = fwfisf  (:,:  )               ! Swap the ocean forcing fields except at nit000 
    211          risf_tsc_b(:,:,:) = risf_tsc(:,:,:)               ! where before fields are set at the end of the routine 
    212          ! 
    213       ENDIF 
    21495 
    21596      IF( MOD( kt-1, nn_fsbc) == 0 ) THEN 
     
    340221            ! 
    341222         END IF 
    342          ! 
    343          IF( kt == nit000 ) THEN                          !   set the forcing field at nit000 - 1    ! 
    344             IF( ln_rstart .AND.    &                     ! Restart: read in restart file 
    345                  & iom_varid( numror, 'fwf_isf_b', ldstop = .FALSE. ) > 0 ) THEN 
    346                IF(lwp) WRITE(numout,*) '          nit000-1 isf tracer content forcing fields read in the restart file' 
    347                CALL iom_get( numror, jpdom_autoglo, 'fwf_isf_b', fwfisf_b(:,:) )   ! before salt content isf_tsc trend 
    348                CALL iom_get( numror, jpdom_autoglo, 'isf_sc_b', risf_tsc_b(:,:,jp_sal) )   ! before salt content isf_tsc trend 
    349                CALL iom_get( numror, jpdom_autoglo, 'isf_hc_b', risf_tsc_b(:,:,jp_tem) )   ! before salt content isf_tsc trend 
    350             ELSE 
    351                fwfisf_b(:,:)    = fwfisf(:,:) 
    352                risf_tsc_b(:,:,:)= risf_tsc(:,:,:) 
    353             END IF 
    354          ENDIF 
    355223         !  
    356224      END IF 
    357    
     225      ! 
     226      ! 
     227      IF( kt == nit000 ) THEN                          !   set the forcing field at nit000 - 1    ! 
     228         IF( ln_rstart .AND.    &                     ! Restart: read in restart file 
     229              & iom_varid( numror, 'fwf_isf_b', ldstop = .FALSE. ) > 0 ) THEN 
     230            IF(lwp) WRITE(numout,*) '          nit000-1 isf tracer content forcing fields read in the restart file' 
     231            CALL iom_get( numror, jpdom_autoglo, 'fwf_isf_b', fwfisf_b(:,:) ) ! before salt content isf_tsc trend 
     232            CALL iom_get( numror, jpdom_autoglo, 'isf_sc_b', risf_tsc_b(:,:,jp_sal) )   ! before salt content isf_tsc trend 
     233            CALL iom_get( numror, jpdom_autoglo, 'isf_hc_b', risf_tsc_b(:,:,jp_tem) )   ! before salt content isf_tsc trend 
     234         ELSE 
     235            fwfisf_b(:,:)    = fwfisf(:,:) 
     236            risf_tsc_b(:,:,:)= risf_tsc(:,:,:) 
     237         END IF 
     238      ENDIF 
     239      ! 
     240      IF( lrst_oce ) THEN 
     241         IF(lwp) WRITE(numout,*) 
     242         IF(lwp) WRITE(numout,*) 'sbc : isf surface tracer content forcing fields written in ocean restart file ',   & 
     243            &                    'at it= ', kt,' date= ', ndastp 
     244         IF(lwp) WRITE(numout,*) '~~~~' 
     245         CALL iom_rstput( kt, nitrst, numrow, 'fwf_isf_b', fwfisf(:,:) ) 
     246         CALL iom_rstput( kt, nitrst, numrow, 'isf_hc_b' , risf_tsc(:,:,jp_tem) ) 
     247         CALL iom_rstput( kt, nitrst, numrow, 'isf_sc_b' , risf_tsc(:,:,jp_sal) ) 
     248      ENDIF 
     249       ! 
    358250  END SUBROUTINE sbc_isf 
     251 
     252  SUBROUTINE sbc_isf_init 
     253 
     254    INTEGER                      ::   ji, jj, jk, ijkmin, inum, ierror 
     255    INTEGER                      ::   ikt, ikb   ! top and bottom level of the isf boundary layer 
     256    REAL(wp)                     ::   zhk 
     257    CHARACTER(len=256)           ::   cfisf , cvarzisf, cvarhisf   ! name for isf file 
     258    CHARACTER(LEN=256)           :: cnameis                     ! name of iceshelf file 
     259    CHARACTER (LEN=32)           :: cvarLeff                    ! variable name for efficient Length scale 
     260    INTEGER           ::   ios           ! Local integer output status for namelist read 
     261 
     262      ! 
     263      !!--------------------------------------------------------------------- 
     264      NAMELIST/namsbc_isf/ nn_isfblk, rn_hisf_tbl, ln_divisf, ln_conserve, rn_gammat0, rn_gammas0, nn_gammablk, & 
     265                         & sn_fwfisf, sn_qisf, sn_rnfisf, sn_depmax_isf, sn_depmin_isf, sn_Leff_isf 
     266      ! 
     267      ! 
     268         REWIND( numnam_ref )              ! Namelist namsbc_rnf in reference namelist : Runoffs  
     269         READ  ( numnam_ref, namsbc_isf, IOSTAT = ios, ERR = 901) 
     270901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_isf in reference namelist', lwp ) 
     271 
     272         REWIND( numnam_cfg )              ! Namelist namsbc_rnf in configuration namelist : Runoffs 
     273         READ  ( numnam_cfg, namsbc_isf, IOSTAT = ios, ERR = 902 ) 
     274902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_isf in configuration namelist', lwp ) 
     275         IF(lwm) WRITE ( numond, namsbc_isf ) 
     276 
     277 
     278         IF ( lwp ) WRITE(numout,*) 
     279         IF ( lwp ) WRITE(numout,*) 'sbc_isf: heat flux of the ice shelf' 
     280         IF ( lwp ) WRITE(numout,*) '~~~~~~~~~' 
     281         IF ( lwp ) WRITE(numout,*) 'sbcisf :'  
     282         IF ( lwp ) WRITE(numout,*) '~~~~~~~~' 
     283         IF ( lwp ) WRITE(numout,*) '        nn_isf      = ', nn_isf 
     284         IF ( lwp ) WRITE(numout,*) '        nn_isfblk   = ', nn_isfblk 
     285         IF ( lwp ) WRITE(numout,*) '        rn_hisf_tbl = ', rn_hisf_tbl 
     286         IF ( lwp ) WRITE(numout,*) '        ln_divisf   = ', ln_divisf  
     287         IF ( lwp ) WRITE(numout,*) '        nn_gammablk = ', nn_gammablk  
     288         IF ( lwp ) WRITE(numout,*) '        rn_tfri2    = ', rn_tfri2  
     289         IF (ln_divisf) THEN       ! keep it in the namelist ??? used true anyway as for runoff ? (PM) 
     290            rdivisf = 1._wp 
     291         ELSE 
     292            rdivisf = 0._wp 
     293         END IF 
     294         ! 
     295         ! Allocate public variable 
     296         IF ( sbc_isf_alloc()  /= 0 )         CALL ctl_stop( 'STOP', 'sbc_isf : unable to allocate arrays' ) 
     297         ! 
     298         ! initialisation 
     299         qisf(:,:)        = 0._wp  ; fwfisf(:,:) = 0._wp 
     300         risf_tsc(:,:,:)  = 0._wp 
     301         ! 
     302         ! define isf tbl tickness, top and bottom indice 
     303         IF      (nn_isf == 1) THEN 
     304            rhisf_tbl(:,:) = rn_hisf_tbl 
     305            misfkt(:,:)    = mikt(:,:)         ! same indice for bg03 et cav => used in isfdiv 
     306         ELSE IF ((nn_isf == 3) .OR. (nn_isf == 2)) THEN 
     307            IF( .NOT.l_isfcpl ) THEN 
     308               ALLOCATE( sf_rnfisf(1), STAT=ierror ) 
     309               ALLOCATE( sf_rnfisf(1)%fnow(jpi,jpj,1), sf_rnfisf(1)%fdta(jpi,jpj,1,2) ) 
     310               CALL fld_fill( sf_rnfisf, (/ sn_rnfisf /), cn_dirisf, 'sbc_isf_init', 'read fresh water flux isf data', 'namsbc_isf' ) 
     311             ENDIF 
     312 
     313            !: read effective lenght (BG03) 
     314            IF (nn_isf == 2) THEN 
     315               ! Read Data and save some integral values 
     316               CALL iom_open( sn_Leff_isf%clname, inum ) 
     317               cvarLeff  = 'soLeff'               !: variable name for Efficient Length scale 
     318               CALL iom_get( inum, jpdom_data, cvarLeff, risfLeff , 1) 
     319               CALL iom_close(inum) 
     320               ! 
     321               risfLeff = risfLeff*1000           !: convertion in m 
     322            END IF 
     323 
     324           ! read depth of the top and bottom of the isf top boundary layer (in this case, isf front depth and grounding line depth) 
     325            CALL iom_open( sn_depmax_isf%clname, inum ) 
     326            cvarhisf = TRIM(sn_depmax_isf%clvar) 
     327            CALL iom_get( inum, jpdom_data, cvarhisf, rhisf_tbl, 1) !: depth of deepest point of the ice shelf base 
     328            CALL iom_close(inum) 
     329            ! 
     330            CALL iom_open( sn_depmin_isf%clname, inum ) 
     331            cvarzisf = TRIM(sn_depmin_isf%clvar) 
     332            CALL iom_get( inum, jpdom_data, cvarzisf, rzisf_tbl, 1) !: depth of shallowest point of the ice shelves base 
     333            CALL iom_close(inum) 
     334            ! 
     335            rhisf_tbl(:,:) = rhisf_tbl(:,:) - rzisf_tbl(:,:)        !: tickness isf boundary layer 
     336 
     337           !! compute first level of the top boundary layer 
     338           DO ji = 1, jpi 
     339              DO jj = 1, jpj 
     340                  jk = 2 
     341                  DO WHILE ( jk .LE. mbkt(ji,jj) .AND. gdepw_0(ji,jj,jk) < rzisf_tbl(ji,jj) ) ;  jk = jk + 1 ;  END DO 
     342                  misfkt(ji,jj) = jk-1 
     343               END DO 
     344            END DO 
     345 
     346         ELSE IF ( nn_isf == 4 ) THEN 
     347            ! as in nn_isf == 1 
     348            rhisf_tbl(:,:) = rn_hisf_tbl 
     349            misfkt(:,:)    = mikt(:,:)         ! same indice for bg03 et cav => used in isfdiv 
     350             
     351            ! load variable used in fldread (use for temporal interpolation of isf fwf forcing) 
     352            IF( .NOT.l_isfcpl ) THEN 
     353               ALLOCATE( sf_fwfisf(1), sf_qisf(1), STAT=ierror ) 
     354               ALLOCATE( sf_fwfisf(1)%fnow(jpi,jpj,1), sf_fwfisf(1)%fdta(jpi,jpj,1,2) ) 
     355               ALLOCATE( sf_qisf(1)%fnow(jpi,jpj,1), sf_qisf(1)%fdta(jpi,jpj,1,2) ) 
     356               CALL fld_fill( sf_fwfisf, (/ sn_fwfisf /), cn_dirisf, 'sbc_isf_init', 'read fresh water flux isf data', 'namsbc_isf' ) 
     357               !CALL fld_fill( sf_qisf  , (/ sn_qisf   /), cn_dirisf, 'sbc_isf_init', 'read heat flux isf data'       , 'namsbc_isf' ) 
     358            ENDIF 
     359         END IF 
     360         ! save initial top boundary layer thickness          
     361         rhisf_tbl_0(:,:) = rhisf_tbl(:,:) 
     362         !  
     363   END SUBROUTINE sbc_isf_init 
     364       
     365 
    359366 
    360367  INTEGER FUNCTION sbc_isf_alloc() 
  • branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r6459 r7784  
    300300      IF( ln_ssr           )   CALL sbc_ssr_init               ! Sea-Surface Restoring initialisation 
    301301      ! 
     302      IF( nn_isf   /= 0    )   CALL sbc_isf_init               ! Compute iceshelves 
     303 
    302304                               CALL sbc_rnf_init               ! Runof initialisation 
    303305      ! 
     
    343345            rnf_b    (:,:  ) = rnf    (:,:  ) 
    344346            rnf_tsc_b(:,:,:) = rnf_tsc(:,:,:) 
     347         ENDIF 
     348         IF( nn_isf /= 0  )  THEN 
     349            fwfisf_b  (:,:  ) = fwfisf  (:,:  )                
     350            risf_tsc_b(:,:,:) = risf_tsc(:,:,:)               
    345351         ENDIF 
    346352      ENDIF 
  • branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/OPA_SRC/TRA/trasbc.F90

    r6688 r7784  
    248248            END DO 
    249249         END DO 
    250          IF( lrst_oce ) THEN 
    251             IF(lwp) WRITE(numout,*) 
    252             IF(lwp) WRITE(numout,*) 'sbc : isf surface tracer content forcing fields written in ocean restart file ',   & 
    253                &                    'at it= ', kt,' date= ', ndastp 
    254             IF(lwp) WRITE(numout,*) '~~~~' 
    255             CALL iom_rstput( kt, nitrst, numrow, 'fwf_isf_b', fwfisf(:,:)          ) 
    256             CALL iom_rstput( kt, nitrst, numrow, 'isf_hc_b' , risf_tsc(:,:,jp_tem) ) 
    257             CALL iom_rstput( kt, nitrst, numrow, 'isf_sc_b' , risf_tsc(:,:,jp_sal) ) 
    258          ENDIF 
    259250      END IF 
    260251      ! 
Note: See TracChangeset for help on using the changeset viewer.