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 12928 for NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser/src/OCE/SBC/sbcice_if.F90 – NEMO

Ignore:
Timestamp:
2020-05-14T21:46:00+02:00 (4 years ago)
Author:
smueller
Message:

Synchronizing with /NEMO/trunk@12925 (ticket #2170)

Location:
NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser

    • Property svn:externals
      •  

        old new  
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
         8 
         9# SETTE 
         10^/utils/CI/sette@HEAD         sette 
  • NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser/src/OCE/SBC/sbcice_if.F90

    r12178 r12928  
    3535   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_ice   ! structure of input ice-cover (file informations, fields read) 
    3636    
     37   !! * Substitutions 
     38#  include "do_loop_substitute.h90" 
    3739   !!---------------------------------------------------------------------- 
    3840   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    4244CONTAINS 
    4345 
    44    SUBROUTINE sbc_ice_if( kt ) 
     46   SUBROUTINE sbc_ice_if( kt, Kbb, Kmm ) 
    4547      !!--------------------------------------------------------------------- 
    4648      !!                     ***  ROUTINE sbc_ice_if  *** 
     
    5961      !!--------------------------------------------------------------------- 
    6062      INTEGER, INTENT(in) ::   kt   ! ocean time step 
     63      INTEGER, INTENT(in) ::   Kbb, Kmm   ! ocean time level indices 
    6164      ! 
    6265      INTEGER  ::   ji, jj     ! dummy loop indices 
     
    7477         !                                      ! ====================== ! 
    7578         ! set file information 
    76          REWIND( numnam_ref )              ! Namelist namsbc_iif in reference namelist : Ice if file 
    7779         READ  ( numnam_ref, namsbc_iif, IOSTAT = ios, ERR = 901) 
    7880901      IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc_iif in reference namelist' ) 
    7981 
    80          REWIND( numnam_cfg )              ! Namelist Namelist namsbc_iif in configuration namelist : Ice if file 
    8182         READ  ( numnam_cfg, namsbc_iif, IOSTAT = ios, ERR = 902 ) 
    8283902      IF( ios >  0 )   CALL ctl_nam ( ios , 'namsbc_iif in configuration namelist' ) 
     
    108109 
    109110         ! Flux and ice fraction computation 
    110          DO jj = 1, jpj 
    111             DO ji = 1, jpi 
    112                ! 
    113                zt_fzp  = fr_i(ji,jj)                        ! freezing point temperature 
    114                zfr_obs = sf_ice(1)%fnow(ji,jj,1)            ! observed ice cover 
    115                !                                            ! ocean ice fraction (0/1) from the freezing point temperature 
    116                IF( sst_m(ji,jj) <= zt_fzp ) THEN   ;   fr_i(ji,jj) = 1.e0 
    117                ELSE                                ;   fr_i(ji,jj) = 0.e0 
    118                ENDIF 
     111         DO_2D_11_11 
     112            ! 
     113            zt_fzp  = fr_i(ji,jj)                        ! freezing point temperature 
     114            zfr_obs = sf_ice(1)%fnow(ji,jj,1)            ! observed ice cover 
     115            !                                            ! ocean ice fraction (0/1) from the freezing point temperature 
     116            IF( sst_m(ji,jj) <= zt_fzp ) THEN   ;   fr_i(ji,jj) = 1.e0 
     117            ELSE                                ;   fr_i(ji,jj) = 0.e0 
     118            ENDIF 
    119119 
    120                tsn(ji,jj,1,jp_tem) = MAX( tsn(ji,jj,1,jp_tem), zt_fzp )     ! avoid over-freezing point temperature 
     120            ts(ji,jj,1,jp_tem,Kmm) = MAX( ts(ji,jj,1,jp_tem,Kmm), zt_fzp )     ! avoid over-freezing point temperature 
    121121 
    122                qsr(ji,jj) = ( 1. - zfr_obs ) * qsr(ji,jj)   ! solar heat flux : zero below observed ice cover 
     122            qsr(ji,jj) = ( 1. - zfr_obs ) * qsr(ji,jj)   ! solar heat flux : zero below observed ice cover 
    123123 
    124                !                                            ! non solar heat flux : add a damping term  
    125                !      # ztrp*(t-(tgel-1.))  if observed ice and no opa ice   (zfr_obs=1 fr_i=0) 
    126                !      # ztrp*min(0,t-tgel)  if observed ice and opa ice      (zfr_obs=1 fr_i=1) 
    127                zqri = ztrp * ( tsb(ji,jj,1,jp_tem) - ( zt_fzp - 1.) ) 
    128                zqrj = ztrp * MIN( 0., tsb(ji,jj,1,jp_tem) - zt_fzp ) 
    129                zqrp = ( zfr_obs * ( (1. - fr_i(ji,jj) ) * zqri    & 
    130                  &                 +      fr_i(ji,jj)   * zqrj ) ) * tmask(ji,jj,1) 
     124            !                                            ! non solar heat flux : add a damping term  
     125            !      # ztrp*(t-(tgel-1.))  if observed ice and no opa ice   (zfr_obs=1 fr_i=0) 
     126            !      # ztrp*min(0,t-tgel)  if observed ice and opa ice      (zfr_obs=1 fr_i=1) 
     127            zqri = ztrp * ( ts(ji,jj,1,jp_tem,Kbb) - ( zt_fzp - 1.) ) 
     128            zqrj = ztrp * MIN( 0., ts(ji,jj,1,jp_tem,Kbb) - zt_fzp ) 
     129            zqrp = ( zfr_obs * ( (1. - fr_i(ji,jj) ) * zqri    & 
     130              &                 +      fr_i(ji,jj)   * zqrj ) ) * tmask(ji,jj,1) 
    131131 
    132                !                                            ! non-solar heat flux  
    133                !      # qns unchanged              if no climatological ice              (zfr_obs=0) 
    134                !      # qns = zqrp                 if climatological ice and no opa ice  (zfr_obs=1, fr_i=0) 
    135                !      # qns = zqrp -2(-4) watt/m2  if climatological ice and opa ice     (zfr_obs=1, fr_i=1) 
    136                !                                   (-2=arctic, -4=antarctic)    
    137                zqi = -3. + SIGN( 1._wp, ff_f(ji,jj) ) 
    138                qns(ji,jj) = ( ( 1.- zfr_obs ) * qns(ji,jj)                             & 
    139                   &          +      zfr_obs   * fr_i(ji,jj) * zqi ) * tmask(ji,jj,1)   & 
    140                   &       + zqrp 
    141             END DO 
    142          END DO 
     132            !                                            ! non-solar heat flux  
     133            !      # qns unchanged              if no climatological ice              (zfr_obs=0) 
     134            !      # qns = zqrp                 if climatological ice and no opa ice  (zfr_obs=1, fr_i=0) 
     135            !      # qns = zqrp -2(-4) watt/m2  if climatological ice and opa ice     (zfr_obs=1, fr_i=1) 
     136            !                                   (-2=arctic, -4=antarctic)    
     137            zqi = -3. + SIGN( 1._wp, ff_f(ji,jj) ) 
     138            qns(ji,jj) = ( ( 1.- zfr_obs ) * qns(ji,jj)                             & 
     139               &          +      zfr_obs   * fr_i(ji,jj) * zqi ) * tmask(ji,jj,1)   & 
     140               &       + zqrp 
     141         END_2D 
    143142         ! 
    144143      ENDIF 
Note: See TracChangeset for help on using the changeset viewer.