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 8486 for branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icedia.F90 – NEMO

Ignore:
Timestamp:
2017-09-01T15:49:35+02:00 (7 years ago)
Author:
clem
Message:

changes in style - part1 - (now the code looks better txs to Gurvan's comments)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icedia.F90

    r8426 r8486  
    11MODULE icedia 
    22   !!====================================================================== 
    3    !!                       ***  MODULE limdia_hsb   *** 
    4    !!  LIM-3 sea ice model :   diagnostics of ice model  
     3   !!                       ***  MODULE icedia  *** 
     4   !!  Sea-Ice model :   global budgets  
    55   !!====================================================================== 
    66   !! History :  3.4  ! 2012-10  (C. Rousset)  original code 
     7   !!            4.0  ! 2017-08  (C. Rousset)  fits nemo4.0 standards 
    78   !!---------------------------------------------------------------------- 
    89#if defined key_lim3 
     
    1011   !!   'key_lim3'                                       LIM3 sea-ice model 
    1112   !!---------------------------------------------------------------------- 
    12    !!   lim_dia_hsb        : computation and output of the time evolution of keys variables 
    13    !!   lim_dia_hsb_init   : initialization and namelist read 
    14    !!---------------------------------------------------------------------- 
    15    USE ice             ! LIM-3: sea-ice variable 
    16    USE dom_oce         ! ocean domain 
    17    USE sbc_oce, ONLY: sfx         ! surface boundary condition: ocean fields 
    18    USE daymod          ! model calendar 
    19    USE phycst          ! physical constant 
    20    USE in_out_manager  ! I/O manager 
    21    USE lib_mpp         ! MPP library 
    22    USE timing          ! preformance summary 
    23    USE iom             ! I/O manager 
    24    USE lib_fortran     ! glob_sum 
    25    USE icerst          ! ice restart 
     13   !!    ice_dia      : diagnostic of the sea-ice global heat content, salt content and volume conservation 
     14   !!    ice_dia_init : initialization of budget calculation 
     15   !!    ice_dia_rst  : read/write budgets restart 
     16   !!---------------------------------------------------------------------- 
     17   USE ice            ! LIM-3: sea-ice variable 
     18   USE dom_oce        ! ocean domain 
     19   USE phycst         ! physical constant 
     20   USE daymod         ! model calendar 
     21   USE sbc_oce , ONLY : sfx   ! surface boundary condition: ocean fields 
     22   USE icerst         ! ice restart 
     23   ! 
     24   USE in_out_manager ! I/O manager 
     25   USE lib_mpp        ! MPP library 
     26   USE timing         ! preformance summary 
     27   USE iom            ! I/O manager 
     28   USE lib_fortran    ! glob_sum 
    2629 
    2730   IMPLICIT NONE 
     
    3639   !! * Substitutions 
    3740#  include "vectopt_loop_substitute.h90" 
    38  
    39    !!---------------------------------------------------------------------- 
    40    !! NEMO/OPA 3.4 , NEMO Consortium (2012) 
     41   !!---------------------------------------------------------------------- 
     42   !! NEMO/ICE 4.0 , NEMO Consortium (2017) 
    4143   !! $Id: icedia.F90 8413 2017-08-07 17:05:39Z clem $ 
    4244   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    4345   !!---------------------------------------------------------------------- 
    44  
    4546CONTAINS 
    4647 
     
    4950      !!                  ***  ROUTINE ice_dia  *** 
    5051      !!      
    51       !! ** Purpose: Compute the ice global heat content, salt content and volume conservation 
    52       !!  
    53       !!--------------------------------------------------------------------------- 
    54       INTEGER, INTENT(in) :: kt    ! number of iteration 
    55       !! 
    56       real(wp)   ::   zbg_ivol, zbg_svol, zbg_area, zbg_isal, zbg_item ,zbg_stem 
    57       REAL(wp)   ::   z_frc_voltop, z_frc_volbot, z_frc_sal, z_frc_temtop, z_frc_tembot   
     52      !! ** Purpose:   Compute the sea-ice global heat content, salt content  
     53      !!             and volume conservation 
     54      !!--------------------------------------------------------------------------- 
     55      INTEGER, INTENT(in) ::   kt   ! ocean time step  
     56      !! 
     57      REAL(wp)   ::   zbg_ivol, zbg_item, zbg_area, zbg_isal 
     58      REAL(wp)   ::   zbg_svol, zbg_stem 
     59      REAL(wp)   ::   z_frc_voltop, z_frc_temtop, z_frc_sal 
     60      REAL(wp)   ::   z_frc_volbot, z_frc_tembot   
    5861      REAL(wp)   ::   zdiff_vol, zdiff_sal, zdiff_tem   
    5962      !!--------------------------------------------------------------------------- 
     
    6265      IF( kt == nit000 .AND. lwp ) THEN 
    6366         WRITE(numout,*) 
    64          WRITE(numout,*)'icedia' 
     67         WRITE(numout,*)'icedia : outpout ice diagnostics (integrated over the domain)' 
    6568         WRITE(numout,*)'~~~~~~' 
    6669      ENDIF 
    6770 
     71!!gm glob_sum includes a " * tmask_i ", so remove  " * tmask(:,:,1) " 
     72 
    6873      ! ----------------------- ! 
    6974      ! 1 -  Contents ! 
    7075      ! ----------------------- ! 
    71       zbg_ivol = glob_sum( vt_i(:,:) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 )                  ! ice volume (km3) 
    72       zbg_svol = glob_sum( vt_s(:,:) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 )                  ! snow volume (km3) 
    73       zbg_area = glob_sum( at_i(:,:) * e1e2t(:,:) * tmask(:,:,1) * 1.e-6 )                  ! area (km2) 
    74       zbg_isal = glob_sum( SUM( smv_i(:,:,:), dim=3 ) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 ) ! salt content (pss*km3) 
    75       zbg_item = glob_sum( et_i * e1e2t(:,:) * tmask(:,:,1) * 1.e-20 )                      ! heat content (1.e20 J) 
    76       zbg_stem = glob_sum( et_s * e1e2t(:,:) * tmask(:,:,1) * 1.e-20 )                      ! heat content (1.e20 J) 
     76      zbg_ivol = glob_sum( vt_i(:,:) * e1e2t(:,:) ) * 1.e-9                  ! ice volume (km3) 
     77      zbg_svol = glob_sum( vt_s(:,:) * e1e2t(:,:) ) * 1.e-9                  ! snow volume (km3) 
     78      zbg_area = glob_sum( at_i(:,:) * e1e2t(:,:) ) * 1.e-6                  ! area (km2) 
     79      zbg_isal = glob_sum( SUM( smv_i(:,:,:), dim=3 ) * e1e2t(:,:) ) * 1.e-9 ! salt content (pss*km3) 
     80      zbg_item = glob_sum( et_i * e1e2t(:,:) ) * 1.e-20                      ! heat content (1.e20 J) 
     81      zbg_stem = glob_sum( et_s * e1e2t(:,:) ) * 1.e-20                      ! heat content (1.e20 J) 
    7782       
    7883      ! ---------------------------! 
    7984      ! 2 - Trends due to forcing  ! 
    8085      ! ---------------------------! 
    81       z_frc_volbot = r1_rau0 * glob_sum( - ( wfx_ice(:,:) + wfx_snw(:,:) + wfx_err_sub(:,:) ) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 )  ! freshwater flux ice/snow-ocean  
    82       z_frc_voltop = r1_rau0 * glob_sum( - ( wfx_sub(:,:) + wfx_spr(:,:) ) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 )                     ! freshwater flux ice/snow-atm 
    83       z_frc_sal    = r1_rau0 * glob_sum( - sfx(:,:) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 )                                            ! salt fluxes ice/snow-ocean 
    84       z_frc_tembot =           glob_sum( hfx_out(:,:) * e1e2t(:,:) * tmask(:,:,1) * 1.e-20 )                                         ! heat on top of ocean (and below ice) 
    85       z_frc_temtop =           glob_sum( hfx_in (:,:) * e1e2t(:,:) * tmask(:,:,1) * 1.e-20 )                                         ! heat on top of ice-coean 
     86      z_frc_volbot = r1_rau0 * glob_sum( - ( wfx_ice(:,:) + wfx_snw(:,:) + wfx_err_sub(:,:) ) * e1e2t(:,:) ) * 1.e-9  ! freshwater flux ice/snow-ocean  
     87      z_frc_voltop = r1_rau0 * glob_sum( - ( wfx_sub(:,:) + wfx_spr(:,:) ) * e1e2t(:,:) ) * 1.e-9                     ! freshwater flux ice/snow-atm 
     88      z_frc_sal    = r1_rau0 * glob_sum(   - sfx(:,:) * e1e2t(:,:) ) * 1.e-9                                          ! salt fluxes ice/snow-ocean 
     89      z_frc_tembot =           glob_sum( hfx_out(:,:) * e1e2t(:,:) ) * 1.e-20                                         ! heat on top of ocean (and below ice) 
     90      z_frc_temtop =           glob_sum( hfx_in (:,:) * e1e2t(:,:) ) * 1.e-20                                         ! heat on top of ice-coean 
    8691      ! 
    8792      frc_voltop  = frc_voltop  + z_frc_voltop  * rdt_ice ! km3 
     
    9499      ! 3 -  Content variations ! 
    95100      ! ----------------------- ! 
    96       zdiff_vol = r1_rau0 * glob_sum( ( rhoic * vt_i(:,:) + rhosn * vt_s(:,:) - vol_loc_ini(:,:)  &  ! freshwater trend (km3)  
    97          &                            ) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 )  
    98       zdiff_sal = r1_rau0 * glob_sum( ( rhoic * SUM( smv_i(:,:,:), dim=3 ) - sal_loc_ini(:,:)     &  ! salt content trend (km3*pss) 
    99          &                            ) * e1e2t(:,:) * tmask(:,:,1) * 1.e-9 ) 
    100       zdiff_tem =           glob_sum( ( et_i(:,:) + et_s(:,:) - tem_loc_ini(:,:)                  &  ! heat content trend (1.e20 J) 
    101       !  &                            + SUM( qevap_ice * a_i_b, dim=3 ) &     !! clem: I think this line should be commented (but needs a check) 
    102          &                            ) * e1e2t(:,:) * tmask(:,:,1) * 1.e-20 ) 
     101      zdiff_vol = r1_rau0 * glob_sum( ( rhoic*vt_i(:,:) + rhosn*vt_s(:,:) - vol_loc_ini(:,:) ) * e1e2t(:,:) ) * 1.e-9 ! freshwater trend (km3)  
     102      zdiff_sal = r1_rau0 * glob_sum( ( rhoic* SUM( smv_i(:,:,:), dim=3 ) - sal_loc_ini(:,:) ) * e1e2t(:,:) ) * 1.e-9 ! salt content trend (km3*pss) 
     103      zdiff_tem =           glob_sum( ( et_i(:,:) + et_s(:,:)             - tem_loc_ini(:,:) ) * e1e2t(:,:) ) * 1.e-20 ! heat content trend (1.e20 J) 
     104      !                               + SUM( qevap_ice * a_i_b, dim=3 )       !! clem: I think this term should not be there (but needs a check) 
    103105 
    104106      ! ----------------------- ! 
     
    112114      ! 5 - Diagnostics writing ! 
    113115      ! ----------------------- ! 
    114       ! 
    115       IF( iom_use('ibgvolume') )  CALL iom_put( 'ibgvolume' , zdiff_vol        )   ! ice/snow volume  drift            (km3 equivalent ocean water)          
    116       IF( iom_use('ibgsaltco') )  CALL iom_put( 'ibgsaltco' , zdiff_sal        )   ! ice salt content drift            (psu*km3 equivalent ocean water) 
    117       IF( iom_use('ibgheatco') )  CALL iom_put( 'ibgheatco' , zdiff_tem        )   ! ice/snow heat content drift       (1.e20 J) 
    118       IF( iom_use('ibgheatfx') )  CALL iom_put( 'ibgheatfx' , zdiff_tem /      &   ! ice/snow heat flux drift          (W/m2) 
    119          &                                                    glob_sum( e1e2t(:,:) * tmask(:,:,1) * 1.e-20 * kt*rdt ) ) 
    120  
    121       IF( iom_use('ibgfrcvoltop') )  CALL iom_put( 'ibgfrcvoltop' , frc_voltop )   ! vol  forcing ice/snw-atm          (km3 equivalent ocean water)  
    122       IF( iom_use('ibgfrcvolbot') )  CALL iom_put( 'ibgfrcvolbot' , frc_volbot )   ! vol  forcing ice/snw-ocean        (km3 equivalent ocean water)  
    123       IF( iom_use('ibgfrcsal') )     CALL iom_put( 'ibgfrcsal'    , frc_sal    )   ! sal - forcing                     (psu*km3 equivalent ocean water)    
    124       IF( iom_use('ibgfrctemtop') )  CALL iom_put( 'ibgfrctemtop' , frc_temtop )   ! heat on top of ice/snw/ocean      (1.e20 J)    
    125       IF( iom_use('ibgfrctembot') )  CALL iom_put( 'ibgfrctembot' , frc_tembot )   ! heat on top of ocean(below ice)   (1.e20 J)    
    126       IF( iom_use('ibgfrchfxtop') )  CALL iom_put( 'ibgfrchfxtop' , frc_temtop / & ! heat on top of ice/snw/ocean      (W/m2)  
    127          &                                                    glob_sum( e1e2t(:,:) * tmask(:,:,1) * 1.e-20 * kt*rdt ) ) 
    128       IF( iom_use('ibgfrchfxbot') )  CALL iom_put( 'ibgfrchfxbot' , frc_tembot / & ! heat on top of ocean(below ice)   (W/m2)  
    129          &                                                    glob_sum( e1e2t(:,:) * tmask(:,:,1) * 1.e-20 * kt*rdt ) ) 
    130  
    131       IF( iom_use('ibgvol_tot' ) )  CALL iom_put( 'ibgvol_tot'  , zbg_ivol     )   ! ice volume                        (km3) 
    132       IF( iom_use('sbgvol_tot' ) )  CALL iom_put( 'sbgvol_tot'  , zbg_svol     )   ! snow volume                       (km3) 
    133       IF( iom_use('ibgarea_tot') )  CALL iom_put( 'ibgarea_tot' , zbg_area     )   ! ice area                          (km2) 
    134       IF( iom_use('ibgsalt_tot') )  CALL iom_put( 'ibgsalt_tot' , zbg_isal     )   ! ice salinity content              (pss*km3) 
    135       IF( iom_use('ibgheat_tot') )  CALL iom_put( 'ibgheat_tot' , zbg_item     )   ! ice heat content                  (1.e20 J) 
    136       IF( iom_use('sbgheat_tot') )  CALL iom_put( 'sbgheat_tot' , zbg_stem     )   ! snow heat content                 (1.e20 J) 
     116!!gm I don't understand the division by the ocean surface (i.e. glob_sum( e1e2t(:,:) ) * 1.e-20 * kt*rdt ) 
     117!!   and its multiplication bu kt ! is it really what we want ? what is this quantity ? 
     118!!   IF it is really what we want, compute it at kt=nit000, not 3 time by time-step ! 
     119!!   kt*rdt  : you mean rdtice ? 
     120!!gm 
     121      ! 
     122      IF( iom_use('ibgvolume')    )   CALL iom_put( 'ibgvolume' , zdiff_vol     )   ! ice/snow volume  drift            (km3 equivalent ocean water)          
     123      IF( iom_use('ibgsaltco')    )   CALL iom_put( 'ibgsaltco' , zdiff_sal     )   ! ice salt content drift            (psu*km3 equivalent ocean water) 
     124      IF( iom_use('ibgheatco')    )   CALL iom_put( 'ibgheatco' , zdiff_tem     )   ! ice/snow heat content drift       (1.e20 J) 
     125      IF( iom_use('ibgheatfx')    )   CALL iom_put( 'ibgheatfx' ,               &   ! ice/snow heat flux drift          (W/m2) 
     126         &                                                     zdiff_tem /glob_sum( e1e2t(:,:) * 1.e-20 * kt*rdt ) ) 
     127 
     128      IF( iom_use('ibgfrcvoltop') )   CALL iom_put( 'ibgfrcvoltop' , frc_voltop )   ! vol  forcing ice/snw-atm          (km3 equivalent ocean water)  
     129      IF( iom_use('ibgfrcvolbot') )   CALL iom_put( 'ibgfrcvolbot' , frc_volbot )   ! vol  forcing ice/snw-ocean        (km3 equivalent ocean water)  
     130      IF( iom_use('ibgfrcsal')    )   CALL iom_put( 'ibgfrcsal'    , frc_sal    )   ! sal - forcing                     (psu*km3 equivalent ocean water)    
     131      IF( iom_use('ibgfrctemtop') )   CALL iom_put( 'ibgfrctemtop' , frc_temtop )   ! heat on top of ice/snw/ocean      (1.e20 J)    
     132      IF( iom_use('ibgfrctembot') )   CALL iom_put( 'ibgfrctembot' , frc_tembot )   ! heat on top of ocean(below ice)   (1.e20 J)    
     133      IF( iom_use('ibgfrchfxtop') )   CALL iom_put( 'ibgfrchfxtop' ,            &   ! heat on top of ice/snw/ocean      (W/m2)  
     134         &                                                          frc_temtop / glob_sum( e1e2t(:,:) ) * 1.e-20 * kt*rdt  ) 
     135      IF( iom_use('ibgfrchfxbot') )   CALL iom_put( 'ibgfrchfxbot' ,            &   ! heat on top of ocean(below ice)   (W/m2)  
     136         &                                                          frc_tembot / glob_sum( e1e2t(:,:) ) * 1.e-20 * kt*rdt  ) 
     137 
     138      IF( iom_use('ibgvol_tot' )  )   CALL iom_put( 'ibgvol_tot'  , zbg_ivol     )   ! ice volume                       (km3) 
     139      IF( iom_use('sbgvol_tot' )  )   CALL iom_put( 'sbgvol_tot'  , zbg_svol     )   ! snow volume                      (km3) 
     140      IF( iom_use('ibgarea_tot')  )   CALL iom_put( 'ibgarea_tot' , zbg_area     )   ! ice area                         (km2) 
     141      IF( iom_use('ibgsalt_tot')  )   CALL iom_put( 'ibgsalt_tot' , zbg_isal     )   ! ice salinity content             (pss*km3) 
     142      IF( iom_use('ibgheat_tot')  )   CALL iom_put( 'ibgheat_tot' , zbg_item     )   ! ice heat content                 (1.e20 J) 
     143      IF( iom_use('sbgheat_tot')  )   CALL iom_put( 'sbgheat_tot' , zbg_stem     )   ! snow heat content                (1.e20 J) 
    137144      ! 
    138145      IF( lrst_ice )   CALL ice_dia_rst( 'WRITE', kt_ice ) 
     
    174181         RETURN 
    175182      ENDIF 
    176  
     183      ! 
    177184      CALL ice_dia_rst( 'READ' )  !* read or initialize all required files 
    178185      ! 
    179186   END SUBROUTINE ice_dia_init 
    180187 
     188 
    181189   SUBROUTINE ice_dia_rst( cdrw, kt ) 
    182      !!--------------------------------------------------------------------- 
    183      !!                   ***  ROUTINE limdia_rst  *** 
    184      !!                      
    185      !! ** Purpose :   Read or write DIA file in restart file 
    186      !! 
    187      !! ** Method  :   use of IOM library 
    188      !!---------------------------------------------------------------------- 
    189      CHARACTER(len=*), INTENT(in) ::   cdrw   ! "READ"/"WRITE" flag 
    190      INTEGER         , INTENT(in), OPTIONAL ::   kt     ! ice time-step 
    191      REAL(wp)                     ::   ziter 
    192      INTEGER                      ::   iter 
    193      ! 
    194      !!---------------------------------------------------------------------- 
    195      ! 
    196      IF( TRIM(cdrw) == 'READ' ) THEN        ! Read/initialise  
    197         IF( ln_rstart ) THEN                   !* Read the restart file 
    198            ! 
    199            CALL iom_get( numrir, 'kt_ice' , ziter ) 
    200            IF(lwp) WRITE(numout,*) 
    201            IF(lwp) WRITE(numout,*) ' ice_dia_rst read at time step = ', ziter 
    202            IF(lwp) WRITE(numout,*) '~~~~~~~' 
    203            CALL iom_get( numrir, 'frc_voltop' , frc_voltop  ) 
    204            CALL iom_get( numrir, 'frc_volbot' , frc_volbot  ) 
    205            CALL iom_get( numrir, 'frc_temtop' , frc_temtop  ) 
    206            CALL iom_get( numrir, 'frc_tembot' , frc_tembot  ) 
    207            CALL iom_get( numrir, 'frc_sal'    , frc_sal     ) 
    208            CALL iom_get( numrir, jpdom_autoglo, 'vol_loc_ini', vol_loc_ini ) 
    209            CALL iom_get( numrir, jpdom_autoglo, 'tem_loc_ini', tem_loc_ini ) 
    210            CALL iom_get( numrir, jpdom_autoglo, 'sal_loc_ini', sal_loc_ini ) 
    211         ELSE 
    212            IF(lwp) WRITE(numout,*) 
    213            IF(lwp) WRITE(numout,*) ' ice_dia at initial state ' 
    214            IF(lwp) WRITE(numout,*) '~~~~~~~' 
    215            ! set trends to 0 
    216            frc_voltop  = 0._wp                                           
    217            frc_volbot  = 0._wp                                           
    218            frc_temtop  = 0._wp                                                  
    219            frc_tembot  = 0._wp                                                  
    220            frc_sal     = 0._wp                                                  
    221            ! record initial ice volume, salt and temp 
    222            vol_loc_ini(:,:) = rhoic * vt_i(:,:) + rhosn * vt_s(:,:)  ! ice/snow volume (kg/m2) 
    223            tem_loc_ini(:,:) = et_i(:,:) + et_s(:,:)                  ! ice/snow heat content (J) 
    224            sal_loc_ini(:,:) = rhoic * SUM( smv_i(:,:,:), dim=3 )     ! ice salt content (pss*kg/m2) 
    225             
    226        ENDIF 
    227  
    228      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN   ! Create restart file 
    229         !                                   ! ------------------- 
    230         iter = kt + nn_fsbc - 1   ! ice restarts are written at kt == nitrst - nn_fsbc + 1 
    231  
    232         IF( iter == nitrst ) THEN 
    233            IF(lwp) WRITE(numout,*) 
    234            IF(lwp) WRITE(numout,*) ' ice_dia_rst write at time step = ', kt 
    235            IF(lwp) WRITE(numout,*) '~~~~~~~' 
    236         ENDIF 
    237  
    238         ! Write in numriw (if iter == nitrst) 
    239         ! ------------------  
    240         CALL iom_rstput( iter, nitrst, numriw, 'frc_voltop' , frc_voltop  ) 
    241         CALL iom_rstput( iter, nitrst, numriw, 'frc_volbot' , frc_volbot  ) 
    242         CALL iom_rstput( iter, nitrst, numriw, 'frc_temtop' , frc_temtop  ) 
    243         CALL iom_rstput( iter, nitrst, numriw, 'frc_tembot' , frc_tembot  ) 
    244         CALL iom_rstput( iter, nitrst, numriw, 'frc_sal'    , frc_sal     ) 
    245         CALL iom_rstput( iter, nitrst, numriw, 'vol_loc_ini', vol_loc_ini ) 
    246         CALL iom_rstput( iter, nitrst, numriw, 'tem_loc_ini', tem_loc_ini ) 
    247         CALL iom_rstput( iter, nitrst, numriw, 'sal_loc_ini', sal_loc_ini ) 
    248         ! 
    249      ENDIF 
    250      ! 
     190      !!--------------------------------------------------------------------- 
     191      !!                   ***  ROUTINE limdia_rst  *** 
     192      !!                      
     193      !! ** Purpose :   Read or write DIA file in restart file 
     194      !! 
     195      !! ** Method  :   use of IOM library 
     196      !!---------------------------------------------------------------------- 
     197      CHARACTER(len=*) , INTENT(in) ::   cdrw   ! "READ"/"WRITE" flag 
     198      INTEGER, OPTIONAL, INTENT(in) ::   kt     ! ice time-step 
     199      ! 
     200      INTEGER  ::   iter    ! local integer 
     201      REAL(wp) ::   ziter   ! local scalar 
     202      !!---------------------------------------------------------------------- 
     203      ! 
     204      IF( TRIM(cdrw) == 'READ' ) THEN        ! Read/initialise  
     205         IF( ln_rstart ) THEN                   !* Read the restart file 
     206            ! 
     207            CALL iom_get( numrir, 'kt_ice' , ziter ) 
     208            IF(lwp) WRITE(numout,*) 
     209            IF(lwp) WRITE(numout,*) ' ice_dia_rst read at time step = ', ziter 
     210            IF(lwp) WRITE(numout,*) '~~~~~~~' 
     211            CALL iom_get( numrir, 'frc_voltop' , frc_voltop  ) 
     212            CALL iom_get( numrir, 'frc_volbot' , frc_volbot  ) 
     213            CALL iom_get( numrir, 'frc_temtop' , frc_temtop  ) 
     214            CALL iom_get( numrir, 'frc_tembot' , frc_tembot  ) 
     215            CALL iom_get( numrir, 'frc_sal'    , frc_sal     ) 
     216            CALL iom_get( numrir, jpdom_autoglo, 'vol_loc_ini', vol_loc_ini ) 
     217            CALL iom_get( numrir, jpdom_autoglo, 'tem_loc_ini', tem_loc_ini ) 
     218            CALL iom_get( numrir, jpdom_autoglo, 'sal_loc_ini', sal_loc_ini ) 
     219         ELSE 
     220            IF(lwp) WRITE(numout,*) 
     221            IF(lwp) WRITE(numout,*) ' ice_dia at initial state ' 
     222            IF(lwp) WRITE(numout,*) '~~~~~~~' 
     223            ! set trends to 0 
     224            frc_voltop  = 0._wp                                           
     225            frc_volbot  = 0._wp                                           
     226            frc_temtop  = 0._wp                                                  
     227            frc_tembot  = 0._wp                                                  
     228            frc_sal     = 0._wp                                                  
     229            ! record initial ice volume, salt and temp 
     230            vol_loc_ini(:,:) = rhoic * vt_i(:,:) + rhosn * vt_s(:,:)  ! ice/snow volume (kg/m2) 
     231            tem_loc_ini(:,:) = et_i(:,:) + et_s(:,:)                  ! ice/snow heat content (J) 
     232            sal_loc_ini(:,:) = rhoic * SUM( smv_i(:,:,:), dim=3 )     ! ice salt content (pss*kg/m2) 
     233         ENDIF 
     234         ! 
     235      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN   ! Create restart file 
     236         !                                   ! ------------------- 
     237         iter = kt + nn_fsbc - 1   ! ice restarts are written at kt == nitrst - nn_fsbc + 1 
     238         ! 
     239         IF( iter == nitrst ) THEN 
     240            IF(lwp) WRITE(numout,*) 
     241            IF(lwp) WRITE(numout,*) ' ice_dia_rst write at time step = ', kt 
     242            IF(lwp) WRITE(numout,*) '~~~~~~~' 
     243         ENDIF 
     244         ! 
     245         ! Write in numriw (if iter == nitrst) 
     246         ! ------------------  
     247         CALL iom_rstput( iter, nitrst, numriw, 'frc_voltop' , frc_voltop  ) 
     248         CALL iom_rstput( iter, nitrst, numriw, 'frc_volbot' , frc_volbot  ) 
     249         CALL iom_rstput( iter, nitrst, numriw, 'frc_temtop' , frc_temtop  ) 
     250         CALL iom_rstput( iter, nitrst, numriw, 'frc_tembot' , frc_tembot  ) 
     251         CALL iom_rstput( iter, nitrst, numriw, 'frc_sal'    , frc_sal     ) 
     252         CALL iom_rstput( iter, nitrst, numriw, 'vol_loc_ini', vol_loc_ini ) 
     253         CALL iom_rstput( iter, nitrst, numriw, 'tem_loc_ini', tem_loc_ini ) 
     254         CALL iom_rstput( iter, nitrst, numriw, 'sal_loc_ini', sal_loc_ini ) 
     255         ! 
     256      ENDIF 
     257      ! 
    251258   END SUBROUTINE ice_dia_rst 
    252259  
     
    255262   !!   Default option :         Empty module          NO LIM sea-ice model 
    256263   !!---------------------------------------------------------------------- 
    257 CONTAINS 
    258    SUBROUTINE ice_dia          ! Empty routine 
    259    END SUBROUTINE ice_dia 
    260264#endif 
     265 
    261266   !!====================================================================== 
    262267END MODULE icedia 
Note: See TracChangeset for help on using the changeset viewer.