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 13640 for NEMO/releases – NEMO

Changeset 13640 for NEMO/releases


Ignore:
Timestamp:
2020-10-19T19:15:09+02:00 (3 years ago)
Author:
clem
Message:

4.0-HEAD: solve ticket #2554

Location:
NEMO/releases/r4.0/r4.0-HEAD/src/ICE
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • NEMO/releases/r4.0/r4.0-HEAD/src/ICE/ice.F90

    r13589 r13640  
    391391   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_vice         !: ice volume variation   [m/s]  
    392392   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_vsnw         !: snw volume variation   [m/s]  
     393   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_aice         !: ice conc.  variation   [s-1]  
    393394   ! 
    394395   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_adv_mass     !: advection of mass (kg/m2/s) 
     
    497498      ! * Ice diagnostics 
    498499      ii = ii + 1 
    499       ALLOCATE( diag_trp_vi(jpi,jpj) , diag_trp_vs (jpi,jpj) , diag_trp_ei(jpi,jpj),   &  
    500          &      diag_trp_es(jpi,jpj) , diag_trp_sv (jpi,jpj) , diag_heat  (jpi,jpj),   & 
    501          &      diag_sice  (jpi,jpj) , diag_vice   (jpi,jpj) , diag_vsnw  (jpi,jpj),   & 
     500      ALLOCATE( diag_trp_vi(jpi,jpj) , diag_trp_vs (jpi,jpj) , diag_trp_ei(jpi,jpj),                      &  
     501         &      diag_trp_es(jpi,jpj) , diag_trp_sv (jpi,jpj) , diag_heat  (jpi,jpj),                      & 
     502         &      diag_sice  (jpi,jpj) , diag_vice   (jpi,jpj) , diag_vsnw  (jpi,jpj), diag_aice(jpi,jpj),  & 
    502503         &      diag_adv_mass(jpi,jpj), diag_adv_salt(jpi,jpj), diag_adv_heat(jpi,jpj), STAT=ierr(ii) ) 
    503504 
  • NEMO/releases/r4.0/r4.0-HEAD/src/ICE/icecor.F90

    r13589 r13640  
    5555      INTEGER  ::   ji, jj, jk, jl   ! dummy loop indices 
    5656      REAL(wp) ::   zsal, zzc 
    57       REAL(wp), DIMENSION(jpi,jpj) ::   zafx   ! concentration trends diag 
    5857      !!---------------------------------------------------------------------- 
    5958      ! controls 
     
    123122         CALL lbc_lnk_multi( 'icecor', u_ice, 'U', -1._wp, v_ice, 'V', -1._wp ) 
    124123      ENDIF 
    125  
    126       !                             !----------------------------------------------------- 
    127       SELECT CASE( kn )             !  Diagnostics                                       ! 
    128       !                             !----------------------------------------------------- 
    129       CASE( 1 )                        !--- dyn trend diagnostics 
    130          ! 
    131          IF( ln_icediachk .OR. iom_use('hfxdhc') ) THEN 
    132             diag_heat(:,:) = - SUM(SUM( e_i (:,:,1:nlay_i,:) - e_i_b (:,:,1:nlay_i,:), dim=4 ), dim=3 ) * r1_rdtice &      ! W.m-2 
    133                &             - SUM(SUM( e_s (:,:,1:nlay_s,:) - e_s_b (:,:,1:nlay_s,:), dim=4 ), dim=3 ) * r1_rdtice 
    134             diag_sice(:,:) =   SUM(     sv_i(:,:,:)          - sv_i_b(:,:,:)                  , dim=3 ) * r1_rdtice * rhoi 
    135             diag_vice(:,:) =   SUM(     v_i (:,:,:)          - v_i_b (:,:,:)                  , dim=3 ) * r1_rdtice * rhoi 
    136             diag_vsnw(:,:) =   SUM(     v_s (:,:,:)          - v_s_b (:,:,:)                  , dim=3 ) * r1_rdtice * rhos 
    137          ENDIF 
    138          !                       ! concentration tendency (dynamics) 
    139          IF( iom_use('afxdyn') .OR. iom_use('afxthd') .OR. iom_use('afxtot') ) THEN  
    140             zafx(:,:) = SUM( a_i(:,:,:) - a_i_b(:,:,:), dim=3 ) * r1_rdtice  
    141             CALL iom_put( 'afxdyn' , zafx ) 
    142          ENDIF 
    143          ! 
    144       CASE( 2 )                        !--- thermo trend diagnostics & ice aging 
    145          ! 
    146          oa_i(:,:,:) = oa_i(:,:,:) + a_i(:,:,:) * rdt_ice   ! ice natural aging incrementation 
    147          ! 
    148          IF( ln_icediachk .OR. iom_use('hfxdhc') ) THEN 
    149             diag_heat(:,:) = diag_heat(:,:) & 
    150                &             - SUM(SUM( e_i (:,:,1:nlay_i,:) - e_i_b (:,:,1:nlay_i,:), dim=4 ), dim=3 ) * r1_rdtice & 
    151                &             - SUM(SUM( e_s (:,:,1:nlay_s,:) - e_s_b (:,:,1:nlay_s,:), dim=4 ), dim=3 ) * r1_rdtice 
    152             diag_sice(:,:) = diag_sice(:,:) & 
    153                &             + SUM(     sv_i(:,:,:)          - sv_i_b(:,:,:)                  , dim=3 ) * r1_rdtice * rhoi 
    154             diag_vice(:,:) = diag_vice(:,:) & 
    155                &             + SUM(     v_i (:,:,:)          - v_i_b (:,:,:)                  , dim=3 ) * r1_rdtice * rhoi 
    156             diag_vsnw(:,:) = diag_vsnw(:,:) & 
    157                &             + SUM(     v_s (:,:,:)          - v_s_b (:,:,:)                  , dim=3 ) * r1_rdtice * rhos 
    158             CALL iom_put ( 'hfxdhc' , diag_heat )  
    159          ENDIF 
    160          !                       ! concentration tendency (total + thermo) 
    161          IF( iom_use('afxdyn') .OR. iom_use('afxthd') .OR. iom_use('afxtot') ) THEN  
    162             zafx(:,:) = zafx(:,:) + SUM( a_i(:,:,:) - a_i_b(:,:,:), dim=3 ) * r1_rdtice 
    163             CALL iom_put( 'afxthd' , SUM( a_i(:,:,:) - a_i_b(:,:,:), dim=3 ) * r1_rdtice ) 
    164             CALL iom_put( 'afxtot' , zafx ) 
    165          ENDIF 
    166          ! 
    167       END SELECT 
    168124      ! 
    169125      ! controls 
  • NEMO/releases/r4.0/r4.0-HEAD/src/ICE/icestp.F90

    r13589 r13640  
    5555   USE icedyn         ! sea-ice: dynamics 
    5656   USE icethd         ! sea-ice: thermodynamics 
    57    USE icecor         ! sea-ice: corrections 
    5857   USE iceupdate      ! sea-ice: sea surface boundary condition update 
    5958   USE icedia         ! sea-ice: budget diagnostics 
     
    162161            &                           CALL ice_dyn( kt )            ! -- Ice dynamics 
    163162         ! 
     163                                        CALL diag_trends( 1 )         ! record dyn trends 
     164         ! 
    164165         !                          !==  lateral boundary conditions  ==! 
    165166         IF( ln_icethd .AND. ln_bdy )   CALL bdy_ice( kt )            ! -- bdy ice thermo 
     
    189190         IF( ln_icethd )                CALL ice_thd( kt )            ! -- Ice thermodynamics       
    190191         ! 
    191                                         CALL ice_cor( kt , 2 )        ! -- Corrections 
    192          ! 
     192                                        CALL diag_trends( 2 )         ! record thermo trends 
    193193                                        CALL ice_var_glo2eqv          ! necessary calls (at least for coupling) 
    194194                                        CALL ice_var_agg( 2 )         ! necessary calls (at least for coupling) 
     
    391391      !!               of the time step 
    392392      !!---------------------------------------------------------------------- 
    393       INTEGER  ::   ji, jj      ! dummy loop index 
    394       !!---------------------------------------------------------------------- 
    395       sfx    (:,:) = 0._wp   ; 
    396       sfx_bri(:,:) = 0._wp   ;   sfx_lam(:,:) = 0._wp 
    397       sfx_sni(:,:) = 0._wp   ;   sfx_opw(:,:) = 0._wp 
    398       sfx_bog(:,:) = 0._wp   ;   sfx_dyn(:,:) = 0._wp 
    399       sfx_bom(:,:) = 0._wp   ;   sfx_sum(:,:) = 0._wp 
    400       sfx_res(:,:) = 0._wp   ;   sfx_sub(:,:) = 0._wp 
    401       ! 
    402       wfx_snw(:,:) = 0._wp   ;   wfx_ice(:,:) = 0._wp 
    403       wfx_sni(:,:) = 0._wp   ;   wfx_opw(:,:) = 0._wp 
    404       wfx_bog(:,:) = 0._wp   ;   wfx_dyn(:,:) = 0._wp 
    405       wfx_bom(:,:) = 0._wp   ;   wfx_sum(:,:) = 0._wp 
    406       wfx_res(:,:) = 0._wp   ;   wfx_sub(:,:) = 0._wp 
    407       wfx_spr(:,:) = 0._wp   ;   wfx_lam(:,:) = 0._wp   
    408       wfx_snw_dyn(:,:) = 0._wp ; wfx_snw_sum(:,:) = 0._wp 
    409       wfx_snw_sub(:,:) = 0._wp ; wfx_ice_sub(:,:) = 0._wp 
    410       wfx_snw_sni(:,:) = 0._wp  
    411       wfx_pnd(:,:) = 0._wp 
    412  
    413       hfx_thd(:,:) = 0._wp   ; 
    414       hfx_snw(:,:) = 0._wp   ;   hfx_opw(:,:) = 0._wp 
    415       hfx_bog(:,:) = 0._wp   ;   hfx_dyn(:,:) = 0._wp 
    416       hfx_bom(:,:) = 0._wp   ;   hfx_sum(:,:) = 0._wp 
    417       hfx_res(:,:) = 0._wp   ;   hfx_sub(:,:) = 0._wp 
    418       hfx_spr(:,:) = 0._wp   ;   hfx_dif(:,:) = 0._wp 
    419       hfx_err_dif(:,:) = 0._wp 
    420       wfx_err_sub(:,:) = 0._wp 
    421       ! 
    422       diag_heat(:,:) = 0._wp ;   diag_sice(:,:) = 0._wp 
    423       diag_vice(:,:) = 0._wp ;   diag_vsnw(:,:) = 0._wp 
    424  
    425       ! SIMIP diagnostics 
    426       qcn_ice_bot(:,:,:) = 0._wp ; qcn_ice_top(:,:,:) = 0._wp ! conductive fluxes 
    427       t_si       (:,:,:) = rt0   ! temp at the ice-snow interface 
    428  
    429       tau_icebfr (:,:)   = 0._wp   ! landfast ice param only (clem: important to keep the init here) 
    430       cnd_ice    (:,:,:) = 0._wp   ! initialisation: effective conductivity at the top of ice/snow (ln_cndflx=T) 
    431       qcn_ice    (:,:,:) = 0._wp   ! initialisation: conductive flux (ln_cndflx=T & ln_cndemule=T) 
    432       qtr_ice_bot(:,:,:) = 0._wp   ! initialization: part of solar radiation transmitted through the ice needed at least for outputs 
    433       qsb_ice_bot(:,:)   = 0._wp   ! (needed if ln_icethd=F) 
    434       ! 
    435       ! for control checks (ln_icediachk) 
    436       diag_trp_vi(:,:) = 0._wp   ;   diag_trp_vs(:,:) = 0._wp 
    437       diag_trp_ei(:,:) = 0._wp   ;   diag_trp_es(:,:) = 0._wp 
    438       diag_trp_sv(:,:) = 0._wp 
    439       diag_adv_mass(:,:) = 0._wp 
    440       diag_adv_salt(:,:) = 0._wp 
    441       diag_adv_heat(:,:) = 0._wp 
     393      INTEGER  ::   ji, jj, jl      ! dummy loop index 
     394      !!---------------------------------------------------------------------- 
     395 
     396      DO jj = 1, jpj  
     397         DO ji = 1, jpi 
     398            sfx    (ji,jj) = 0._wp   ; 
     399            sfx_bri(ji,jj) = 0._wp   ;   sfx_lam(ji,jj) = 0._wp 
     400            sfx_sni(ji,jj) = 0._wp   ;   sfx_opw(ji,jj) = 0._wp 
     401            sfx_bog(ji,jj) = 0._wp   ;   sfx_dyn(ji,jj) = 0._wp 
     402            sfx_bom(ji,jj) = 0._wp   ;   sfx_sum(ji,jj) = 0._wp 
     403            sfx_res(ji,jj) = 0._wp   ;   sfx_sub(ji,jj) = 0._wp 
     404            ! 
     405            wfx_snw(ji,jj) = 0._wp   ;   wfx_ice(ji,jj) = 0._wp 
     406            wfx_sni(ji,jj) = 0._wp   ;   wfx_opw(ji,jj) = 0._wp 
     407            wfx_bog(ji,jj) = 0._wp   ;   wfx_dyn(ji,jj) = 0._wp 
     408            wfx_bom(ji,jj) = 0._wp   ;   wfx_sum(ji,jj) = 0._wp 
     409            wfx_res(ji,jj) = 0._wp   ;   wfx_sub(ji,jj) = 0._wp 
     410            wfx_spr(ji,jj) = 0._wp   ;   wfx_lam(ji,jj) = 0._wp   
     411            wfx_snw_dyn(ji,jj) = 0._wp ; wfx_snw_sum(ji,jj) = 0._wp 
     412            wfx_snw_sub(ji,jj) = 0._wp ; wfx_ice_sub(ji,jj) = 0._wp 
     413            wfx_snw_sni(ji,jj) = 0._wp  
     414            wfx_pnd(ji,jj) = 0._wp 
     415 
     416            hfx_thd(ji,jj) = 0._wp   ; 
     417            hfx_snw(ji,jj) = 0._wp   ;   hfx_opw(ji,jj) = 0._wp 
     418            hfx_bog(ji,jj) = 0._wp   ;   hfx_dyn(ji,jj) = 0._wp 
     419            hfx_bom(ji,jj) = 0._wp   ;   hfx_sum(ji,jj) = 0._wp 
     420            hfx_res(ji,jj) = 0._wp   ;   hfx_sub(ji,jj) = 0._wp 
     421            hfx_spr(ji,jj) = 0._wp   ;   hfx_dif(ji,jj) = 0._wp 
     422            hfx_err_dif(ji,jj) = 0._wp 
     423            wfx_err_sub(ji,jj) = 0._wp 
     424            ! 
     425            diag_heat(ji,jj) = 0._wp ;   diag_sice(ji,jj) = 0._wp 
     426            diag_vice(ji,jj) = 0._wp ;   diag_vsnw(ji,jj) = 0._wp 
     427            diag_aice(ji,jj) = 0._wp 
     428 
     429            tau_icebfr (ji,jj) = 0._wp   ! landfast ice param only (clem: important to keep the init here) 
     430            qsb_ice_bot(ji,jj) = 0._wp   ! (needed if ln_icethd=F) 
     431 
     432            fhld(ji,jj) = 0._wp   ! needed if ln_icethd=F 
     433 
     434            ! for control checks (ln_icediachk) 
     435            diag_trp_vi(ji,jj) = 0._wp   ;   diag_trp_vs(ji,jj) = 0._wp 
     436            diag_trp_ei(ji,jj) = 0._wp   ;   diag_trp_es(ji,jj) = 0._wp 
     437            diag_trp_sv(ji,jj) = 0._wp 
     438            ! 
     439            diag_adv_mass(ji,jj) = 0._wp 
     440            diag_adv_salt(ji,jj) = 0._wp 
     441            diag_adv_heat(ji,jj) = 0._wp 
     442         END DO 
     443      END DO 
     444 
     445      DO jl = 1, jpl 
     446         DO jj = 1, jpj  
     447            DO ji = 1, jpi 
     448               ! SIMIP diagnostics 
     449               t_si       (ji,jj,jl) = rt0     ! temp at the ice-snow interface 
     450               qcn_ice_bot(ji,jj,jl) = 0._wp 
     451               qcn_ice_top(ji,jj,jl) = 0._wp   ! conductive fluxes 
     452               cnd_ice    (ji,jj,jl) = 0._wp   ! effective conductivity at the top of ice/snow (ln_cndflx=T) 
     453               qcn_ice    (ji,jj,jl) = 0._wp   ! conductive flux (ln_cndflx=T & ln_cndemule=T) 
     454               qtr_ice_bot(ji,jj,jl) = 0._wp   ! part of solar radiation transmitted through the ice needed at least for outputs 
     455            END DO 
     456         END DO 
     457      END DO 
    442458       
    443459   END SUBROUTINE diag_set0 
     460 
     461 
     462   SUBROUTINE diag_trends( kn ) 
     463      !!---------------------------------------------------------------------- 
     464      !!                  ***  ROUTINE diag_trends  *** 
     465      !! 
     466      !! ** purpose : diagnostics of the trends. Used for conservation purposes 
     467      !!              and outputs 
     468      !!---------------------------------------------------------------------- 
     469      INTEGER, INTENT(in) ::   kn    ! 1 = after dyn ; 2 = after thermo 
     470      !!---------------------------------------------------------------------- 
     471      ! 
     472      ! --- trends of heat, salt, mass (used for conservation controls) 
     473      IF( ln_icediachk .OR. iom_use('hfxdhc') ) THEN 
     474         ! 
     475         diag_heat(:,:) = diag_heat(:,:) & 
     476            &             - SUM(SUM( e_i (:,:,1:nlay_i,:) - e_i_b (:,:,1:nlay_i,:), dim=4 ), dim=3 ) * r1_rdtice & 
     477            &             - SUM(SUM( e_s (:,:,1:nlay_s,:) - e_s_b (:,:,1:nlay_s,:), dim=4 ), dim=3 ) * r1_rdtice 
     478         diag_sice(:,:) = diag_sice(:,:) & 
     479            &             + SUM(     sv_i(:,:,:)          - sv_i_b(:,:,:)                  , dim=3 ) * r1_rdtice * rhoi 
     480         diag_vice(:,:) = diag_vice(:,:) & 
     481            &             + SUM(     v_i (:,:,:)          - v_i_b (:,:,:)                  , dim=3 ) * r1_rdtice * rhoi 
     482         diag_vsnw(:,:) = diag_vsnw(:,:) & 
     483            &             + SUM(     v_s (:,:,:)          - v_s_b (:,:,:)                  , dim=3 ) * r1_rdtice * rhos 
     484         ! 
     485         IF( kn == 2 )    CALL iom_put ( 'hfxdhc' , diag_heat )   ! output of heat trend 
     486         ! 
     487      ENDIF 
     488      ! 
     489      ! --- trends of concentration (used for simip outputs) 
     490      IF( iom_use('afxdyn') .OR. iom_use('afxthd') .OR. iom_use('afxtot') ) THEN 
     491         ! 
     492         diag_aice(:,:) = diag_aice(:,:) + SUM( a_i(:,:,:) - a_i_b(:,:,:), dim=3 ) * r1_rdtice 
     493         ! 
     494         IF( kn == 1 )   CALL iom_put( 'afxdyn' , diag_aice )                                           ! dyn trend 
     495         IF( kn == 2 )   CALL iom_put( 'afxthd' , SUM( a_i(:,:,:) - a_i_b(:,:,:), dim=3 ) * r1_rdtice ) ! thermo trend 
     496         IF( kn == 2 )   CALL iom_put( 'afxtot' , diag_aice )                                           ! total trend 
     497         ! 
     498      ENDIF 
     499      ! 
     500   END SUBROUTINE diag_trends 
    444501 
    445502#else 
  • NEMO/releases/r4.0/r4.0-HEAD/src/ICE/icethd.F90

    r13589 r13640  
    3030   USE icethd_pnd     ! sea-ice: melt ponds 
    3131   USE iceitd         ! sea-ice: remapping thickness distribution 
     32   USE icecor         ! sea-ice: corrections 
    3233   USE icetab         ! sea-ice: 1D <==> 2D transformation 
    3334   USE icevar         ! sea-ice: operations 
     
    271272      IF( ln_icedO )          CALL ice_thd_do                       ! --- Frazil ice growth in leads --- ! 
    272273      ! 
     274                              CALL ice_cor( kt , 2 )                ! --- Corrections --- ! 
     275      ! 
     276      oa_i(:,:,:) = oa_i(:,:,:) + a_i(:,:,:) * rdt_ice              ! ice natural aging incrementation      
     277      ! 
    273278      ! convergence tests 
    274279      IF( ln_zdf_chkcvg ) THEN 
Note: See TracChangeset for help on using the changeset viewer.