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

Ignore:
Timestamp:
2017-09-25T21:11:19+02:00 (7 years ago)
Author:
clem
Message:

cosmetics only

File:
1 edited

Legend:

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

    r8534 r8562  
    4040CONTAINS 
    4141 
    42    SUBROUTINE ice_wri( kindic ) 
     42   SUBROUTINE ice_wri( kt ) 
    4343      !!------------------------------------------------------------------- 
    4444      !!  This routine computes the average of some variables and write it 
     
    5050      !!  modif : 03/06/98 
    5151      !!------------------------------------------------------------------- 
    52       INTEGER, INTENT(in) ::   kindic   ! if kindic < 0 there has been an error somewhere 
     52      INTEGER, INTENT(in) ::   kt   ! time-step 
    5353      ! 
    5454      INTEGER  ::  ji, jj, jk, jl  ! dummy loop indices 
    55       REAL(wp) ::  z2da, z2db, ztmp, zrho1, zrho2, zmiss_val 
     55      REAL(wp) ::  z2da, z2db, zrho1, zrho2, zmiss_val 
    5656      REAL(wp), DIMENSION(jpi,jpj)     ::  z2d, zswi, zmiss !  2D workspace 
    5757      REAL(wp), DIMENSION(jpi,jpj)     ::  zfb              ! ice freeboard 
     
    9595      ! Standard outputs 
    9696      !---------------------------------------- 
    97       ! fluxes  
    98       IF( iom_use('qsr_oce') )   CALL iom_put( "qsr_oce" , qsr_oce(:,:) * ( 1._wp - at_i_b(:,:) ) )                      !     solar flux at ocean surface 
    99       IF( iom_use('qns_oce') )   CALL iom_put( "qns_oce" , qns_oce(:,:) * ( 1._wp - at_i_b(:,:) ) + qemp_oce(:,:) )      ! non-solar flux at ocean surface 
    100       IF( iom_use('qsr_ice') )   CALL iom_put( "qsr_ice" , SUM( qsr_ice(:,:,:) * a_i_b(:,:,:), dim=3 ) )                 !     solar flux at ice surface 
    101       IF( iom_use('qns_ice') )   CALL iom_put( "qns_ice" , SUM( qns_ice(:,:,:) * a_i_b(:,:,:), dim=3 ) + qemp_ice(:,:) ) ! non-solar flux at ice surface 
    102       IF( iom_use('qtr_ice') )   CALL iom_put( "qtr_ice" , SUM( ftr_ice(:,:,:) * a_i_b(:,:,:), dim=3 ) )                 !     solar flux transmitted thru ice 
    103       IF( iom_use('qt_oce' ) )   CALL iom_put( "qt_oce"  , ( qsr_oce(:,:) + qns_oce(:,:) ) * ( 1._wp - at_i_b(:,:) ) + qemp_oce(:,:) ) 
    104       IF( iom_use('qt_ice' ) )   CALL iom_put( "qt_ice"  , SUM( ( qns_ice(:,:,:) + qsr_ice(:,:,:) )   & 
    105          &                                                      * a_i_b(:,:,:), dim=3 ) + qemp_ice(:,:) ) 
    106 !!gm I don't understand the variable below.... why not multiplied by a_i_b or (1-a_i_b) ???  
    107       IF( iom_use('qemp_oce') )  CALL iom_put( "qemp_oce" , qemp_oce(:,:) )   
    108       IF( iom_use('qemp_ice') )  CALL iom_put( "qemp_ice" , qemp_ice(:,:) )   
    109       IF( iom_use('emp_oce' ) )  CALL iom_put( "emp_oce"  , emp_oce (:,:) )   ! emp over ocean (taking into account the snow blown away from the ice) 
    110       IF( iom_use('emp_ice' ) )  CALL iom_put( "emp_ice"  , emp_ice (:,:) )   ! emp over ice   (taking into account the snow blown away from the ice) 
    111  
    11297      ! velocity 
    11398      IF( iom_use('uice_ipa') )  CALL iom_put( "uice_ipa" , u_ice         )   ! ice velocity u component 
     
    126111         IF( iom_use('icevel_mv') )   CALL iom_put( "icevel_mv"    , z2d(:,:) * zswi(:,:) + zmiss(:,:) )   ! ice velocity module (missing value) 
    127112      ENDIF 
    128  
    129       IF( iom_use('tau_icebfr') )     CALL iom_put( "tau_icebfr"  , tau_icebfr             )  ! ice friction with ocean bottom (landfast ice)   
    130113      ! 
    131114      IF( iom_use('miceage')  )       CALL iom_put( "miceage"     , om_i * zswi * zamask15 )  ! mean ice age 
    132115      IF( iom_use('micet')    )       CALL iom_put( "micet"       , ( tm_i  - rt0 ) * zswi )  ! ice mean    temperature 
    133116      IF( iom_use('icest')    )       CALL iom_put( "icest"       , ( tm_su - rt0 ) * zswi )  ! ice surface temperature 
    134       IF( iom_use('icecolf')  )       CALL iom_put( "icecolf"     , hicol                  )  ! frazil ice collection thickness 
     117      IF( iom_use('icecolf')  )       CALL iom_put( "icecolf"     , ht_i_new               )  ! new ice thickness formed in the leads 
    135118      ! 
    136119      CALL iom_put( "isst"        , sst_m               )        ! sea surface temperature 
     
    142125      CALL iom_put( "isnowhc"     , et_s  * zswi        )        ! snow total heat content 
    143126      CALL iom_put( "ibrinv"      , bvm_i * zswi * 100. )        ! brine volume 
    144       CALL iom_put( "snowpre"     , sprecip * 86400.    )        ! snow precipitation [m/day] 
    145127      CALL iom_put( "micesalt"    , smt_i   * zswi      )        ! mean ice salinity 
    146128      CALL iom_put( "snowvol"     , vt_s    * zswi      )        ! snow volume 
    147129       
    148       CALL iom_put( "sfxbog"      , sfx_bog * rday      )        ! salt flux from bottom growth 
    149       CALL iom_put( "sfxbom"      , sfx_bom * rday      )        ! salt flux from bottom melting 
    150       CALL iom_put( "sfxsum"      , sfx_sum * rday      )        ! salt flux from surface melting 
    151       CALL iom_put( "sfxlam"      , sfx_lam * rday      )        ! salt flux from lateral melting 
    152       CALL iom_put( "sfxsni"      , sfx_sni * rday      )        ! salt flux from snow ice formation 
    153       CALL iom_put( "sfxopw"      , sfx_opw * rday      )        ! salt flux from open water formation 
    154       CALL iom_put( "sfxdyn"      , sfx_dyn * rday      )        ! salt flux from ridging rafting 
    155       CALL iom_put( "sfxres"      , sfx_res * rday      )        ! salt flux from corrections (resultant) 
    156       CALL iom_put( "sfxbri"      , sfx_bri * rday      )        ! salt flux from brines 
    157       CALL iom_put( "sfxsub"      , sfx_sub * rday      )        ! salt flux from sublimation 
    158       CALL iom_put( "sfx"         , sfx     * rday      )        ! total salt flux 
    159  
    160       ztmp = rday / rhoic 
    161       CALL iom_put( "vfxres"     , wfx_res * ztmp       )        ! daily prod./melting due to corrections  
    162       CALL iom_put( "vfxopw"     , wfx_opw * ztmp       )        ! daily lateral thermodynamic ice production 
    163       CALL iom_put( "vfxsni"     , wfx_sni * ztmp       )        ! daily snowice ice production 
    164       CALL iom_put( "vfxbog"     , wfx_bog * ztmp       )        ! daily bottom thermodynamic ice production 
    165       CALL iom_put( "vfxdyn"     , wfx_dyn * ztmp       )        ! daily dynamic ice production (rid/raft) 
    166       CALL iom_put( "vfxsum"     , wfx_sum * ztmp       )        ! surface melt  
    167       CALL iom_put( "vfxbom"     , wfx_bom * ztmp       )        ! bottom melt  
    168       CALL iom_put( "vfxlam"     , wfx_lam * ztmp       )        ! lateral melt  
    169       CALL iom_put( "vfxice"     , wfx_ice * ztmp       )        ! total ice growth/melt  
    170  
    171       IF ( ln_pnd ) & 
    172          CALL iom_put( "vfxpnd"  , wfx_pnd * ztmp       )        ! melt pond water flux 
    173  
    174       IF ( iom_use( "vfxthin" ) ) THEN   ! ice production for open water + thin ice (<20cm) => comparable to observations   
    175          WHERE( htm_i(:,:) < 0.2 .AND. htm_i(:,:) > 0. ) ; z2d = wfx_bog 
    176          ELSEWHERE                                       ; z2d = 0._wp 
    177          END WHERE 
    178          CALL iom_put( "vfxthin", ( wfx_opw + z2d ) * ztmp ) 
    179       ENDIF 
    180  
    181       ztmp = rday * r1_rhosn 
    182       CALL iom_put( "vfxspr"     , wfx_spr * ztmp       )        ! precip (snow) 
    183       CALL iom_put( "vfxsnw"     , wfx_snw * ztmp       )        ! total snw growth/melt  
    184       CALL iom_put( "vfxsub"     , wfx_sub * ztmp       )        ! sublimation (snow/ice)  
    185       CALL iom_put( "vfxsub_err" , wfx_err_sub * ztmp   )        ! "excess" of sublimation sent to ocean       
    186   
    187       CALL iom_put ('hfxthd'     , hfx_thd(:,:)         )   !   
    188       CALL iom_put ('hfxdyn'     , hfx_dyn(:,:)         )   !   
    189       CALL iom_put ('hfxres'     , hfx_res(:,:)         )   !   
    190       CALL iom_put ('hfxout'     , hfx_out(:,:)         )   !   
    191       CALL iom_put ('hfxin'      , hfx_in(:,:)          )   !   
    192       CALL iom_put ('hfxsnw'     , hfx_snw(:,:)         )   !   
    193       CALL iom_put ('hfxsub'     , hfx_sub(:,:)         )   !   
    194       CALL iom_put ('hfxerr'     , hfx_err_dif(:,:)     )   !   
    195       CALL iom_put ('hfxerr_rem' , hfx_err_rem(:,:)     )   !   
    196        
    197       CALL iom_put ('hfxsum'     , hfx_sum(:,:)         )   !   
    198       CALL iom_put ('hfxbom'     , hfx_bom(:,:)         )   !   
    199       CALL iom_put ('hfxbog'     , hfx_bog(:,:)         )   !   
    200       CALL iom_put ('hfxdif'     , hfx_dif(:,:)         )   !   
    201       CALL iom_put ('hfxopw'     , hfx_opw(:,:)         )   !   
    202       CALL iom_put ('hfxtur'     , fhtur(:,:) * at_i_b(:,:) ) ! turbulent heat flux at ice base  
    203       CALL iom_put ('hfxdhc'     , diag_heat(:,:)       )   ! Heat content variation in snow and ice  
    204       CALL iom_put ('hfxspr'     , hfx_spr(:,:)         )   ! Heat content of snow precip  
    205  
    206 !!gm ====>>>>>  THIS should be moved where at_ip, vt_ip are computed fro the last time in the time-step  (limmpd) 
    207       ! MV MP 2016 
    208130      IF ( ln_pnd ) THEN 
    209131         CALL iom_put( "iceamp"  , at_ip  * zswi        )   ! melt pond total fraction 
    210132         CALL iom_put( "icevmp"  , vt_ip  * zswi        )   ! melt pond total volume per unit area 
    211133      ENDIF 
    212       ! END MV MP 2016 
    213 !!gm  <<<<<<======= end 
    214134 
    215135      !---------------------------------- 
     
    225145      IF ( iom_use('brinevol_cat') )  CALL iom_put( "brinevol_cat", bv_i * 100. * zswi2 )          ! brine volume 
    226146 
    227       ! MV MP 2016 
    228147      IF ( ln_pnd ) THEN 
    229148         IF ( iom_use('iceamp_cat') )  CALL iom_put( "iceamp_cat"     , a_ip       * zswi2   )       ! melt pond frac for categories 
     
    232151         IF ( iom_use('iceafp_cat') )  CALL iom_put( "iceafp_cat"     , a_ip_frac  * zswi2   )       ! melt pond frac for categories 
    233152      ENDIF 
    234       ! END MV MP 2016 
    235153 
    236154      !-------------------------------- 
     
    360278      !! History :   4.0  !  2013-06  (C. Rousset) 
    361279      !!---------------------------------------------------------------------- 
    362       INTEGER, INTENT( in )   ::   kt               ! ocean time-step index) 
     280      INTEGER, INTENT( in )   ::   kt               ! ocean time-step index 
    363281      INTEGER, INTENT( in )   ::   kid , kh_i 
    364282      INTEGER                 ::   nz_i, jl 
     
    476394      CALL histwrite( kid, "sntemcat", kt, tm_su - rt0 , jpi*jpj*jpl, (/1/) )     
    477395 
    478       ! Close the file 
    479       ! ----------------- 
    480 !!gm I don't understand why the file is not closed ! 
    481       !CALL histclo( kid ) 
     396      !! The file is closed in dia_wri_state (ocean routine) 
     397      !! CALL histclo( kid ) 
    482398      ! 
    483399    END SUBROUTINE ice_wri_state 
Note: See TracChangeset for help on using the changeset viewer.