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 14072 for NEMO/trunk/src/ICE/iceistate.F90 – NEMO

Ignore:
Timestamp:
2020-12-04T08:48:38+01:00 (3 years ago)
Author:
laurent
Message:

Merging branch "2020/dev_r13648_ASINTER-04_laurent_bulk_ice", ticket #2369

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/ICE/iceistate.F90

    r14053 r14072  
    1818   USE oce            ! dynamics and tracers variables 
    1919   USE dom_oce        ! ocean domain 
    20    USE sbc_oce , ONLY : sst_m, sss_m, ln_ice_embd  
     20   USE sbc_oce , ONLY : sst_m, sss_m, ln_ice_embd 
    2121   USE sbc_ice , ONLY : tn_ice, snwice_mass, snwice_mass_b 
    2222   USE eosbn2         ! equation of state 
     
    4040   USE agrif_oce 
    4141   USE agrif_ice 
    42    USE agrif_ice_interp  
    43 # endif    
     42   USE agrif_ice_interp 
     43# endif 
    4444 
    4545   IMPLICIT NONE 
     
    9191      !! 
    9292      !! ** Method  :   This routine will put some ice where ocean 
    93       !!                is at the freezing point, then fill in ice  
    94       !!                state variables using prescribed initial  
    95       !!                values in the namelist             
     93      !!                is at the freezing point, then fill in ice 
     94      !!                state variables using prescribed initial 
     95      !!                values in the namelist 
    9696      !! 
    9797      !! ** Steps   :   1) Set initial surface and basal temperatures 
     
    103103      !!              where there is no ice 
    104104      !!-------------------------------------------------------------------- 
    105       INTEGER, INTENT(in) :: kt            ! time step  
     105      INTEGER, INTENT(in) :: kt            ! time step 
    106106      INTEGER, INTENT(in) :: Kbb, Kmm, Kaa ! ocean time level indices 
    107107      ! 
     
    129129      ! basal temperature (considered at freezing point)   [Kelvin] 
    130130      CALL eos_fzp( sss_m(:,:), t_bo(:,:) ) 
    131       t_bo(:,:) = ( t_bo(:,:) + rt0 ) * tmask(:,:,1)  
     131      t_bo(:,:) = ( t_bo(:,:) + rt0 ) * tmask(:,:,1) 
    132132      ! 
    133133      ! surface temperature and conductivity 
     
    154154      e_i (:,:,:,:) = 0._wp 
    155155      e_s (:,:,:,:) = 0._wp 
    156        
     156 
    157157      ! general fields 
    158158      a_i (:,:,:) = 0._wp 
     
    229229               IF( TRIM(si(jp_apd)%clrootname) == 'NOT USED' ) & 
    230230                  &     si(jp_apd)%fnow(:,:,1) = ( rn_apd_ini_n * zswitch + rn_apd_ini_s * (1._wp - zswitch) ) * tmask(:,:,1) & ! rn_apd = pond fraction => rn_apnd * a_i = pond conc. 
    231                   &                              * si(jp_ati)%fnow(:,:,1)  
     231                  &                              * si(jp_ati)%fnow(:,:,1) 
    232232               ! 
    233233               ! pond depth 
     
    248248               ! 
    249249               ! change the switch for the following 
    250                WHERE( zat_i_ini(:,:) > 0._wp )   ;   zswitch(:,:) = tmask(:,:,1)  
     250               WHERE( zat_i_ini(:,:) > 0._wp )   ;   zswitch(:,:) = tmask(:,:,1) 
    251251               ELSEWHERE                         ;   zswitch(:,:) = 0._wp 
    252252               END WHERE 
     
    256256               !                          !---------------! 
    257257               ! no ice if (sst - Tfreez) >= thresold 
    258                WHERE( ( sst_m(:,:) - (t_bo(:,:) - rt0) ) * tmask(:,:,1) >= rn_thres_sst )   ;   zswitch(:,:) = 0._wp  
     258               WHERE( ( sst_m(:,:) - (t_bo(:,:) - rt0) ) * tmask(:,:,1) >= rn_thres_sst )   ;   zswitch(:,:) = 0._wp 
    259259               ELSEWHERE                                                                    ;   zswitch(:,:) = tmask(:,:,1) 
    260260               END WHERE 
     
    269269                  zt_su_ini(:,:) = rn_tsu_ini_n * zswitch(:,:) 
    270270                  ztm_s_ini(:,:) = rn_tms_ini_n * zswitch(:,:) 
    271                   zapnd_ini(:,:) = rn_apd_ini_n * zswitch(:,:) * zat_i_ini(:,:) ! rn_apd = pond fraction => rn_apd * a_i = pond conc.  
     271                  zapnd_ini(:,:) = rn_apd_ini_n * zswitch(:,:) * zat_i_ini(:,:) ! rn_apd = pond fraction => rn_apd * a_i = pond conc. 
    272272                  zhpnd_ini(:,:) = rn_hpd_ini_n * zswitch(:,:) 
    273273                  zhlid_ini(:,:) = rn_hld_ini_n * zswitch(:,:) 
     
    295295               zhlid_ini(:,:) = 0._wp 
    296296            ENDIF 
    297              
     297 
    298298            IF ( .NOT.ln_pnd_lids ) THEN 
    299299               zhlid_ini(:,:) = 0._wp 
    300300            ENDIF 
    301              
     301 
    302302            !----------------! 
    303303            ! 3) fill fields ! 
     
    323323            CALL tab_2d_1d( npti, nptidx(1:npti), h_ip_1d(1:npti)  , zhpnd_ini ) 
    324324            CALL tab_2d_1d( npti, nptidx(1:npti), h_il_1d(1:npti)  , zhlid_ini ) 
    325              
     325 
    326326            ! allocate temporary arrays 
    327327            ALLOCATE( zhi_2d (npti,jpl), zhs_2d (npti,jpl), zai_2d (npti,jpl), & 
     
    377377            DO jl = 1, jpl 
    378378               DO_3D( 1, 1, 1, 1, 1, nlay_i ) 
    379                   t_i (ji,jj,jk,jl) = zti_3d(ji,jj,jl)  
     379                  t_i (ji,jj,jk,jl) = zti_3d(ji,jj,jl) 
    380380                  ztmelts          = - rTmlt * sz_i(ji,jj,jk,jl) + rt0 ! melting temperature in K 
    381381                  e_i(ji,jj,jk,jl) = zswitch(ji,jj) * v_i(ji,jj,jl) * r1_nlay_i * & 
     
    385385               END_3D 
    386386            END DO 
    387              
     387 
    388388#if  defined key_agrif 
    389389         ELSE 
    390   
     390 
    391391            Agrif_SpecialValue    = -9999. 
    392392            Agrif_UseSpecialValue = .TRUE. 
     
    399399            use_sign_north = .FALSE. 
    400400            Agrif_UseSpecialValue = .FALSE. 
    401         ! lbc ????  
     401        ! lbc ???? 
    402402   ! Here we know : a_i, v_i, v_s, sv_i, oa_i, a_ip, v_ip, v_il, t_su, e_s, e_i 
    403403            CALL ice_var_glo2eqv 
     
    413413         v_ip(:,:,:) = h_ip(:,:,:) * a_ip(:,:,:) 
    414414         v_il(:,:,:) = h_il(:,:,:) * a_ip(:,:,:) 
    415           
     415 
    416416         ! specific temperatures for coupled runs 
    417417         tn_ice(:,:,:) = t_su(:,:,:) 
     
    456456      !!------------------------------------------------------------------- 
    457457      !!                   ***  ROUTINE ice_istate_init  *** 
    458       !!         
    459       !! ** Purpose :   Definition of initial state of the ice  
    460       !! 
    461       !! ** Method  :   Read the namini namelist and check the parameter  
     458      !! 
     459      !! ** Purpose :   Definition of initial state of the ice 
     460      !! 
     461      !! ** Method  :   Read the namini namelist and check the parameter 
    462462      !!              values called at the first timestep (nit000) 
    463463      !! 
     
    500500         WRITE(numout,*) '      max ocean temp. above Tfreeze with initial ice   rn_thres_sst   = ', rn_thres_sst 
    501501         IF( ln_iceini .AND. nn_iceini_file == 0 ) THEN 
    502             WRITE(numout,*) '      initial snw thickness in the north-south         rn_hts_ini     = ', rn_hts_ini_n,rn_hts_ini_s  
     502            WRITE(numout,*) '      initial snw thickness in the north-south         rn_hts_ini     = ', rn_hts_ini_n,rn_hts_ini_s 
    503503            WRITE(numout,*) '      initial ice thickness in the north-south         rn_hti_ini     = ', rn_hti_ini_n,rn_hti_ini_s 
    504504            WRITE(numout,*) '      initial ice concentr  in the north-south         rn_ati_ini     = ', rn_ati_ini_n,rn_ati_ini_s 
Note: See TracChangeset for help on using the changeset viewer.