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/icedia.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/icedia.F90

    r13970 r14072  
    22   !!====================================================================== 
    33   !!                       ***  MODULE icedia  *** 
    4    !!  Sea-Ice:   global budgets  
     4   !!  Sea-Ice:   global budgets 
    55   !!====================================================================== 
    66   !! History :  3.4  !  2012-10  (C. Rousset)       original code 
     
    3737   REAL(wp), DIMENSION(:,:), ALLOCATABLE ::   vol_loc_ini, sal_loc_ini, tem_loc_ini                    ! initial volume, salt and heat contents 
    3838   REAL(wp)                              ::   frc_sal, frc_voltop, frc_volbot, frc_temtop, frc_tembot  ! global forcing trends 
    39     
     39 
    4040   !!---------------------------------------------------------------------- 
    4141   !! NEMO/ICE 4.0 , NEMO Consortium (2018) 
     
    5959      !!--------------------------------------------------------------------------- 
    6060      !!                  ***  ROUTINE ice_dia  *** 
    61       !!      
    62       !! ** Purpose:   Compute the sea-ice global heat content, salt content  
     61      !! 
     62      !! ** Purpose:   Compute the sea-ice global heat content, salt content 
    6363      !!             and volume conservation 
    6464      !!--------------------------------------------------------------------------- 
    65       INTEGER, INTENT(in) ::   kt   ! ocean time step  
     65      INTEGER, INTENT(in) ::   kt   ! ocean time step 
    6666      !! 
    6767      REAL(wp)   ::   zbg_ivol, zbg_item, zbg_area, zbg_isal 
    6868      REAL(wp)   ::   zbg_svol, zbg_stem 
    6969      REAL(wp)   ::   z_frc_voltop, z_frc_temtop, z_frc_sal 
    70       REAL(wp)   ::   z_frc_volbot, z_frc_tembot   
    71       REAL(wp)   ::   zdiff_vol, zdiff_sal, zdiff_tem   
     70      REAL(wp)   ::   z_frc_volbot, z_frc_tembot 
     71      REAL(wp)   ::   zdiff_vol, zdiff_sal, zdiff_tem 
    7272      !!--------------------------------------------------------------------------- 
    7373      IF( ln_timing )   CALL timing_start('ice_dia') 
     
    8282         z1_e1e2 = 1._wp / glob_sum( 'icedia', e1e2t(:,:) ) 
    8383      ENDIF 
    84        
     84 
    8585      ! ----------------------- ! 
    8686      ! 1 -  Contents           ! 
     
    9696         zbg_stem = glob_sum( 'icedia', et_s(:,:) * e1e2t(:,:) ) * 1.e-20 ! heat content (1.e20 J) 
    9797 
    98          CALL iom_put( 'ibgvol_tot'  , zbg_ivol )  
    99          CALL iom_put( 'sbgvol_tot'  , zbg_svol )  
    100          CALL iom_put( 'ibgarea_tot' , zbg_area )  
    101          CALL iom_put( 'ibgsalt_tot' , zbg_isal )  
    102          CALL iom_put( 'ibgheat_tot' , zbg_item )  
    103          CALL iom_put( 'sbgheat_tot' , zbg_stem )  
    104   
     98         CALL iom_put( 'ibgvol_tot'  , zbg_ivol ) 
     99         CALL iom_put( 'sbgvol_tot'  , zbg_svol ) 
     100         CALL iom_put( 'ibgarea_tot' , zbg_area ) 
     101         CALL iom_put( 'ibgsalt_tot' , zbg_isal ) 
     102         CALL iom_put( 'ibgheat_tot' , zbg_item ) 
     103         CALL iom_put( 'sbgheat_tot' , zbg_stem ) 
     104 
    105105      ENDIF 
    106106 
     
    109109      ! ---------------------------! 
    110110      ! they must be kept outside an IF(iom_use) because of the call to dia_rst below 
    111       z_frc_volbot = r1_rho0 * glob_sum( 'icedia', -( wfx_ice(:,:) + wfx_snw(:,:) + wfx_err_sub(:,:) ) * e1e2t(:,:) ) * 1.e-9   ! freshwater flux ice/snow-ocean  
     111      z_frc_volbot = r1_rho0 * glob_sum( 'icedia', -( wfx_ice(:,:) + wfx_snw(:,:) + wfx_err_sub(:,:) ) * e1e2t(:,:) ) * 1.e-9   ! freshwater flux ice/snow-ocean 
    112112      z_frc_voltop = r1_rho0 * glob_sum( 'icedia', -( wfx_sub(:,:) + wfx_spr(:,:) )                    * e1e2t(:,:) ) * 1.e-9   ! freshwater flux ice/snow-atm 
    113113      z_frc_sal    = r1_rho0 * glob_sum( 'icedia', -      sfx(:,:)                                     * e1e2t(:,:) ) * 1.e-9   ! salt fluxes ice/snow-ocean 
     
    121121      frc_tembot  = frc_tembot  + z_frc_tembot  * rDt_ice ! 1.e20 J 
    122122 
    123       CALL iom_put( 'ibgfrcvoltop' , frc_voltop )   ! vol  forcing ice/snw-atm          (km3 equivalent ocean water)  
    124       CALL iom_put( 'ibgfrcvolbot' , frc_volbot )   ! vol  forcing ice/snw-ocean        (km3 equivalent ocean water)  
    125       CALL iom_put( 'ibgfrcsal'    , frc_sal    )   ! sal - forcing                     (psu*km3 equivalent ocean water)    
    126       CALL iom_put( 'ibgfrctemtop' , frc_temtop )   ! heat on top of ice/snw/ocean      (1.e20 J)    
    127       CALL iom_put( 'ibgfrctembot' , frc_tembot )   ! heat on top of ocean(below ice)   (1.e20 J)    
     123      CALL iom_put( 'ibgfrcvoltop' , frc_voltop )   ! vol  forcing ice/snw-atm          (km3 equivalent ocean water) 
     124      CALL iom_put( 'ibgfrcvolbot' , frc_volbot )   ! vol  forcing ice/snw-ocean        (km3 equivalent ocean water) 
     125      CALL iom_put( 'ibgfrcsal'    , frc_sal    )   ! sal - forcing                     (psu*km3 equivalent ocean water) 
     126      CALL iom_put( 'ibgfrctemtop' , frc_temtop )   ! heat on top of ice/snw/ocean      (1.e20 J) 
     127      CALL iom_put( 'ibgfrctembot' , frc_tembot )   ! heat on top of ocean(below ice)   (1.e20 J) 
    128128 
    129129      IF(  iom_use('ibgfrchfxtop') .OR. iom_use('ibgfrchfxbot') ) THEN 
    130130         CALL iom_put( 'ibgfrchfxtop' , frc_temtop * z1_e1e2 * 1.e-20 * kt*rn_Dt ) ! heat on top of ice/snw/ocean      (W/m2) 
    131          CALL iom_put( 'ibgfrchfxbot' , frc_tembot * z1_e1e2 * 1.e-20 * kt*rn_Dt ) ! heat on top of ocean(below ice)   (W/m2)  
    132       ENDIF 
    133        
     131         CALL iom_put( 'ibgfrchfxbot' , frc_tembot * z1_e1e2 * 1.e-20 * kt*rn_Dt ) ! heat on top of ocean(below ice)   (W/m2) 
     132      ENDIF 
     133 
    134134      ! ---------------------------------- ! 
    135135      ! 3 -  Content variations and drifts ! 
    136136      ! ---------------------------------- ! 
    137137      IF(  iom_use('ibgvolume') .OR. iom_use('ibgsaltco') .OR. iom_use('ibgheatco') .OR. iom_use('ibgheatfx') ) THEN 
    138              
    139          zdiff_vol = r1_rho0 * glob_sum( 'icedia', ( rhoi*vt_i(:,:) + rhos*vt_s(:,:) - vol_loc_ini(:,:) ) * e1e2t(:,:) ) * 1.e-9   ! freshwater trend (km3)  
     138 
     139         zdiff_vol = r1_rho0 * glob_sum( 'icedia', ( rhoi*vt_i(:,:) + rhos*vt_s(:,:) - vol_loc_ini(:,:) ) * e1e2t(:,:) ) * 1.e-9   ! freshwater trend (km3) 
    140140         zdiff_sal = r1_rho0 * glob_sum( 'icedia', ( rhoi*st_i(:,:)                  - sal_loc_ini(:,:) ) * e1e2t(:,:) ) * 1.e-9   ! salt content trend (km3*pss) 
    141141         zdiff_tem =           glob_sum( 'icedia', ( et_i(:,:) + et_s(:,:)           - tem_loc_ini(:,:) ) * e1e2t(:,:) ) * 1.e-20  ! heat content trend (1.e20 J) 
    142142         !                               + SUM( qevap_ice * a_i_b, dim=3 )       !! clem: I think this term should not be there (but needs a check) 
    143           
     143 
    144144         zdiff_vol = zdiff_vol - ( frc_voltop + frc_volbot ) 
    145145         zdiff_sal = zdiff_sal - frc_sal 
    146146         zdiff_tem = zdiff_tem - ( frc_tembot - frc_temtop ) 
    147           
    148          CALL iom_put( 'ibgvolume' , zdiff_vol )   ! ice/snow volume  drift            (km3 equivalent ocean water)          
     147 
     148         CALL iom_put( 'ibgvolume' , zdiff_vol )   ! ice/snow volume  drift            (km3 equivalent ocean water) 
    149149         CALL iom_put( 'ibgsaltco' , zdiff_sal )   ! ice salt content drift            (psu*km3 equivalent ocean water) 
    150150         CALL iom_put( 'ibgheatco' , zdiff_tem )   ! ice/snow heat content drift       (1.e20 J) 
    151151         ! 
    152152      ENDIF 
    153        
     153 
    154154      IF( lrst_ice )   CALL ice_dia_rst( 'WRITE', kt_ice ) 
    155155      ! 
     
    162162      !!--------------------------------------------------------------------------- 
    163163      !!                  ***  ROUTINE ice_dia_init  *** 
    164       !!      
     164      !! 
    165165      !! ** Purpose: Initialization for the heat salt volume budgets 
    166       !!  
     166      !! 
    167167      !! ** Method : Compute initial heat content, salt content and volume 
    168168      !! 
     
    173173      INTEGER            ::   ios, ierror   ! local integer 
    174174      !! 
    175       NAMELIST/namdia/ ln_icediachk, rn_icechk_cel, rn_icechk_glo, ln_icediahsb, ln_icectl, iiceprt, jiceprt   
     175      NAMELIST/namdia/ ln_icediachk, rn_icechk_cel, rn_icechk_glo, ln_icediahsb, ln_icectl, iiceprt, jiceprt 
    176176      !!---------------------------------------------------------------------- 
    177177      ! 
     
    194194         WRITE(numout,*) '         chosen grid point position          (iiceprt,jiceprt)  = (', iiceprt,',', jiceprt,')' 
    195195      ENDIF 
    196       !       
     196      ! 
    197197      IF( ln_icediahsb ) THEN 
    198198         IF( ice_dia_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'ice_dia_init : unable to allocate arrays' )   ! allocate tke arrays 
     
    206206      !!--------------------------------------------------------------------- 
    207207      !!                   ***  ROUTINE icedia_rst  *** 
    208       !!                      
     208      !! 
    209209      !! ** Purpose :   Read or write DIA file in restart file 
    210210      !! 
     
    218218      !!---------------------------------------------------------------------- 
    219219      ! 
    220       IF( TRIM(cdrw) == 'READ' ) THEN        ! Read/initialise  
     220      IF( TRIM(cdrw) == 'READ' ) THEN        ! Read/initialise 
    221221         IF( ln_rstart ) THEN                   !* Read the restart file 
    222222            ! 
     
    238238            IF(lwp) WRITE(numout,*) '~~~~~~~' 
    239239            ! set trends to 0 
    240             frc_voltop  = 0._wp                                           
    241             frc_volbot  = 0._wp                                           
    242             frc_temtop  = 0._wp                                                  
    243             frc_tembot  = 0._wp                                                  
    244             frc_sal     = 0._wp                                                  
     240            frc_voltop  = 0._wp 
     241            frc_volbot  = 0._wp 
     242            frc_temtop  = 0._wp 
     243            frc_tembot  = 0._wp 
     244            frc_sal     = 0._wp 
    245245            ! record initial ice volume, salt and temp 
    246246            vol_loc_ini(:,:) = rhoi * vt_i(:,:) + rhos * vt_s(:,:)  ! ice/snow volume (kg/m2) 
     
    260260         ! 
    261261         ! Write in numriw (if iter == nitrst) 
    262          ! ------------------  
     262         ! ------------------ 
    263263         CALL iom_rstput( iter, nitrst, numriw, 'frc_voltop' , frc_voltop ) 
    264264         CALL iom_rstput( iter, nitrst, numriw, 'frc_volbot' , frc_volbot ) 
     
    273273      ! 
    274274   END SUBROUTINE ice_dia_rst 
    275   
     275 
    276276#else 
    277277   !!---------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.