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 6225 for branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/NEMO/LIM_SRC_3/limwri.F90 – NEMO

Ignore:
Timestamp:
2016-01-08T10:35:19+01:00 (8 years ago)
Author:
jamesharle
Message:

Update MPP_BDY_UPDATE branch to be consistent with head of trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/NEMO/LIM_SRC_3/limwri.F90

    r4688 r6225  
    2424   USE lib_mpp         ! MPP library 
    2525   USE wrk_nemo        ! work arrays 
    26    USE par_ice 
    2726   USE iom 
    2827   USE timing          ! Timing 
     
    3534   PUBLIC lim_wri_state  ! called by dia_wri_state  
    3635 
    37    REAL(wp)  ::   epsi06 = 1.e-6_wp 
    3836   !!---------------------------------------------------------------------- 
    3937   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011) 
     
    4341CONTAINS 
    4442 
    45 #if defined key_dimgout 
    46 # include "limwri_dimg.h90" 
    47 #else 
    4843 
    4944   SUBROUTINE lim_wri( kindic ) 
     
    5954      INTEGER, INTENT(in) ::   kindic   ! if kindic < 0 there has been an error somewhere 
    6055      ! 
    61       INTEGER ::  ji, jj, jk, jl  ! dummy loop indices 
    62       REAL(wp) ::  zinda, zindb, z1_365 
    63       REAL(wp), POINTER, DIMENSION(:,:,:) ::   zoi, zei 
    64       REAL(wp), POINTER, DIMENSION(:,:)   :: z2d, z2da, z2db, zind    ! 2D workspace 
     56      INTEGER  ::  ji, jj, jk, jl  ! dummy loop indices 
     57      REAL(wp) ::  z1_365 
     58      REAL(wp) ::  ztmp 
     59      REAL(wp), POINTER, DIMENSION(:,:,:) ::  zoi, zei, zt_i, zt_s 
     60      REAL(wp), POINTER, DIMENSION(:,:)   ::  z2d, z2da, z2db, zswi    ! 2D workspace 
    6561      !!------------------------------------------------------------------- 
    6662 
    6763      IF( nn_timing == 1 )  CALL timing_start('limwri') 
    6864 
    69       CALL wrk_alloc( jpi, jpj, jpl, zoi, zei ) 
    70       CALL wrk_alloc( jpi, jpj     , z2d, z2da, z2db, zind ) 
     65      CALL wrk_alloc( jpi, jpj, jpl, zoi, zei, zt_i, zt_s ) 
     66      CALL wrk_alloc( jpi, jpj     , z2d, z2da, z2db, zswi ) 
    7167 
    7268      !----------------------------- 
    7369      ! Mean category values 
    7470      !----------------------------- 
     71      z1_365 = 1._wp / 365._wp 
    7572 
    7673      CALL lim_var_icetm      ! mean sea ice temperature 
     
    8077      DO jj = 1, jpj          ! presence indicator of ice 
    8178         DO ji = 1, jpi 
    82             zind(ji,jj)  = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - epsi06 ) ) 
     79            zswi(ji,jj)  = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - epsi06 ) ) 
    8380         END DO 
    8481      END DO 
     
    8986         DO jj = 1, jpj  
    9087            DO ji = 1, jpi 
    91                z2d(ji,jj)  = vt_i(ji,jj) / MAX( at_i(ji,jj), epsi06 ) * zind(ji,jj) 
     88               z2d(ji,jj)  = vt_i(ji,jj) / MAX( at_i(ji,jj), epsi06 ) * zswi(ji,jj) 
    9289            END DO 
    9390         END DO 
     
    9895         DO jj = 1, jpj                                             
    9996            DO ji = 1, jpi 
    100                z2d(ji,jj)  = vt_s(ji,jj) / MAX( at_i(ji,jj), epsi06 ) * zind(ji,jj) 
     97               z2d(ji,jj)  = vt_s(ji,jj) / MAX( at_i(ji,jj), epsi06 ) * zswi(ji,jj) 
    10198            END DO 
    10299         END DO 
     
    107104         DO jj = 2 , jpjm1 
    108105            DO ji = 2 , jpim1 
    109                z2da(ji,jj)  = (  u_ice(ji,jj) * tmu(ji,jj) + u_ice(ji-1,jj) * tmu(ji-1,jj) ) * 0.5_wp 
    110                z2db(ji,jj)  = (  v_ice(ji,jj) * tmv(ji,jj) + v_ice(ji,jj-1) * tmv(ji,jj-1) ) * 0.5_wp 
     106               z2da(ji,jj)  = (  u_ice(ji,jj) * umask(ji,jj,1) + u_ice(ji-1,jj) * umask(ji-1,jj,1) ) * 0.5_wp 
     107               z2db(ji,jj)  = (  v_ice(ji,jj) * vmask(ji,jj,1) + v_ice(ji,jj-1) * vmask(ji,jj-1,1) ) * 0.5_wp 
    111108           END DO 
    112109         END DO 
    113110         CALL lbc_lnk( z2da, 'T', -1. ) 
    114111         CALL lbc_lnk( z2db, 'T', -1. ) 
    115          CALL iom_put( "uice_ipa"     , z2da                )       ! ice velocity u component 
    116          CALL iom_put( "vice_ipa"     , z2db                )       ! ice velocity v component 
     112         CALL iom_put( "uice_ipa"     , z2da             )       ! ice velocity u component 
     113         CALL iom_put( "vice_ipa"     , z2db             )       ! ice velocity v component 
    117114         DO jj = 1, jpj                                  
    118115            DO ji = 1, jpi 
     
    120117            END DO 
    121118         END DO 
    122          CALL iom_put( "icevel"       , z2d                 )       ! ice velocity module 
     119         CALL iom_put( "icevel"       , z2d              )       ! ice velocity module 
    123120      ENDIF 
    124121      ! 
     
    128125            DO jj = 1, jpj 
    129126               DO ji = 1, jpi 
    130                   z2d(ji,jj) = z2d(ji,jj) + zind(ji,jj) * oa_i(ji,jj,jl) 
     127                  rswitch    = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - 0.1 ) ) 
     128                  z2d(ji,jj) = z2d(ji,jj) + rswitch * oa_i(ji,jj,jl) / MAX( at_i(ji,jj), 0.1 ) 
    131129               END DO 
    132130            END DO 
    133131         END DO 
    134          z1_365 = 1._wp / 365._wp 
    135          CALL iom_put( "miceage"     , z2d * z1_365         )        ! mean ice age 
     132         CALL iom_put( "miceage"     , z2d * z1_365      )        ! mean ice age 
    136133      ENDIF 
    137134 
     
    139136         DO jj = 1, jpj 
    140137            DO ji = 1, jpi 
    141                z2d(ji,jj) = ( tm_i(ji,jj) - rtt ) * zind(ji,jj) 
    142             END DO 
    143          END DO 
    144          CALL iom_put( "micet"       , z2d                  )        ! mean ice temperature 
     138               z2d(ji,jj) = ( tm_i(ji,jj) - rt0 ) * zswi(ji,jj) 
     139            END DO 
     140         END DO 
     141         CALL iom_put( "micet"       , z2d               )        ! mean ice temperature 
    145142      ENDIF 
    146143      ! 
     
    150147            DO jj = 1, jpj 
    151148               DO ji = 1, jpi 
    152                   z2d(ji,jj) = z2d(ji,jj) + zind(ji,jj) * ( t_su(ji,jj,jl) - rtt ) * a_i(ji,jj,jl) / MAX( at_i(ji,jj) , epsi06 ) 
     149                  z2d(ji,jj) = z2d(ji,jj) + zswi(ji,jj) * ( t_su(ji,jj,jl) - rt0 ) * a_i(ji,jj,jl) / MAX( at_i(ji,jj) , epsi06 ) 
    153150               END DO 
    154151            END DO 
    155152         END DO 
    156          CALL iom_put( "icest"       , z2d                 )        ! ice surface temperature 
     153         CALL iom_put( "icest"       , z2d              )        ! ice surface temperature 
    157154      ENDIF 
    158155 
     
    160157         DO jj = 1, jpj 
    161158            DO ji = 1, jpi 
    162                zindb  = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) ) ) 
    163                z2d(ji,jj) = hicol(ji,jj) * zindb 
    164             END DO 
    165          END DO 
    166          CALL iom_put( "icecolf"     , z2d                 )        ! frazil ice collection thickness 
     159               rswitch  = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) ) ) 
     160               z2d(ji,jj) = hicol(ji,jj) * rswitch 
     161            END DO 
     162         END DO 
     163         CALL iom_put( "icecolf"     , z2d              )        ! frazil ice collection thickness 
    167164      ENDIF 
    168165 
     
    176173      CALL iom_put( "utau_ice"    , utau_ice            )        ! wind stress over ice along i-axis at I-point 
    177174      CALL iom_put( "vtau_ice"    , vtau_ice            )        ! wind stress over ice along j-axis at I-point 
    178       CALL iom_put( "snowpre"     , sprecip             )        ! snow precipitation  
     175      CALL iom_put( "snowpre"     , sprecip * 86400.    )        ! snow precipitation  
    179176      CALL iom_put( "micesalt"    , smt_i               )        ! mean ice salinity 
    180177 
     
    186183      CALL iom_put( "icetrp"      , diag_trp_vi * rday  )        ! ice volume transport 
    187184      CALL iom_put( "snwtrp"      , diag_trp_vs * rday  )        ! snw volume transport 
     185      CALL iom_put( "saltrp"      , diag_trp_smv * rday * rhoic ) ! salt content transport 
    188186      CALL iom_put( "deitrp"      , diag_trp_ei         )        ! advected ice enthalpy (W/m2) 
    189187      CALL iom_put( "destrp"      , diag_trp_es         )        ! advected snw enthalpy (W/m2) 
     
    199197      CALL iom_put( "sfx"         , sfx     * rday      )        ! total salt flux 
    200198 
    201       CALL iom_put( "vfxres"     , wfx_res * rday / rhoic  )        ! daily prod./melting due to limupdate  
    202       CALL iom_put( "vfxopw"     , wfx_opw * rday / rhoic  )        ! daily lateral thermodynamic ice production 
    203       CALL iom_put( "vfxsni"     , wfx_sni * rday / rhoic  )        ! daily snowice ice production 
    204       CALL iom_put( "vfxbog"     , wfx_bog * rday / rhoic  )       ! daily bottom thermodynamic ice production 
    205       CALL iom_put( "vfxdyn"     , wfx_dyn * rday / rhoic  )       ! daily dynamic ice production (rid/raft) 
    206       CALL iom_put( "vfxsum"     , wfx_sum * rday / rhoic  )        ! surface melt  
    207       CALL iom_put( "vfxbom"     , wfx_bom * rday / rhoic  )        ! bottom melt  
    208       CALL iom_put( "vfxice"     , wfx_ice * rday / rhoic  )        ! total ice growth/melt  
    209       CALL iom_put( "vfxsnw"     , wfx_snw * rday / rhoic  )        ! total snw growth/melt  
    210       CALL iom_put( "vfxsub"     , wfx_sub * rday / rhoic  )        ! sublimation (snow)  
    211       CALL iom_put( "vfxspr"     , wfx_spr * rday / rhoic  )        ! precip (snow)  
    212  
    213       CALL iom_put ('hfxthd', hfx_thd(:,:) )   !   
    214       CALL iom_put ('hfxdyn', hfx_dyn(:,:) )   !   
    215       CALL iom_put ('hfxres', hfx_res(:,:) )   !   
    216       CALL iom_put ('hfxout', hfx_out(:,:) )   !   
    217       CALL iom_put ('hfxin' , hfx_in(:,:) )   !   
    218       CALL iom_put ('hfxsnw', hfx_snw(:,:) )   !   
    219       CALL iom_put ('hfxsub', hfx_sub(:,:) )   !   
    220       CALL iom_put ('hfxerr', hfx_err(:,:) )   !   
    221       CALL iom_put ('hfxerr_rem', hfx_err_rem(:,:) )   !   
    222        
    223       CALL iom_put ('hfxsum', hfx_sum(:,:) )   !   
    224       CALL iom_put ('hfxbom', hfx_bom(:,:) )   !   
    225       CALL iom_put ('hfxbog', hfx_bog(:,:) )   !   
    226       CALL iom_put ('hfxdif', hfx_dif(:,:) )   !   
    227       CALL iom_put ('hfxopw', hfx_opw(:,:) )   !   
    228       CALL iom_put ('hfxtur', fhtur(:,:) * at_i(:,:) )   ! turbulent heat flux at ice base  
    229       CALL iom_put ('hfxdhc', diag_heat_dhc(:,:) )          ! Heat content variation in snow and ice  
    230       CALL iom_put ('hfxspr', hfx_spr(:,:) )          ! Heat content of snow precip  
     199      ztmp = rday / rhoic 
     200      CALL iom_put( "vfxres"     , wfx_res * ztmp       )        ! daily prod./melting due to limupdate  
     201      CALL iom_put( "vfxopw"     , wfx_opw * ztmp       )        ! daily lateral thermodynamic ice production 
     202      CALL iom_put( "vfxsni"     , wfx_sni * ztmp       )        ! daily snowice ice production 
     203      CALL iom_put( "vfxbog"     , wfx_bog * ztmp       )        ! daily bottom thermodynamic ice production 
     204      CALL iom_put( "vfxdyn"     , wfx_dyn * ztmp       )        ! daily dynamic ice production (rid/raft) 
     205      CALL iom_put( "vfxsum"     , wfx_sum * ztmp       )        ! surface melt  
     206      CALL iom_put( "vfxbom"     , wfx_bom * ztmp       )        ! bottom melt  
     207      CALL iom_put( "vfxice"     , wfx_ice * ztmp       )        ! total ice growth/melt  
     208      CALL iom_put( "vfxsnw"     , wfx_snw * ztmp       )        ! total snw growth/melt  
     209      CALL iom_put( "vfxsub"     , wfx_sub * ztmp       )        ! sublimation (snow)  
     210      CALL iom_put( "vfxspr"     , wfx_spr * ztmp       )        ! precip (snow) 
     211       
     212      CALL iom_put( "afxtot"     , afx_tot * rday       )        ! concentration tendency (total) 
     213      CALL iom_put( "afxdyn"     , afx_dyn * rday       )        ! concentration tendency (dynamics) 
     214      CALL iom_put( "afxthd"     , afx_thd * rday       )        ! concentration tendency (thermo) 
     215 
     216      CALL iom_put ('hfxthd'     , hfx_thd(:,:)         )   !   
     217      CALL iom_put ('hfxdyn'     , hfx_dyn(:,:)         )   !   
     218      CALL iom_put ('hfxres'     , hfx_res(:,:)         )   !   
     219      CALL iom_put ('hfxout'     , hfx_out(:,:)         )   !   
     220      CALL iom_put ('hfxin'      , hfx_in(:,:)          )   !   
     221      CALL iom_put ('hfxsnw'     , hfx_snw(:,:)         )   !   
     222      CALL iom_put ('hfxsub'     , hfx_sub(:,:)         )   !   
     223      CALL iom_put ('hfxerr'     , hfx_err(:,:)         )   !   
     224      CALL iom_put ('hfxerr_rem' , hfx_err_rem(:,:)     )   !   
     225       
     226      CALL iom_put ('hfxsum'     , hfx_sum(:,:)         )   !   
     227      CALL iom_put ('hfxbom'     , hfx_bom(:,:)         )   !   
     228      CALL iom_put ('hfxbog'     , hfx_bog(:,:)         )   !   
     229      CALL iom_put ('hfxdif'     , hfx_dif(:,:)         )   !   
     230      CALL iom_put ('hfxopw'     , hfx_opw(:,:)         )   !   
     231      CALL iom_put ('hfxtur'     , fhtur(:,:) * SUM(a_i_b(:,:,:), dim=3) ) ! turbulent heat flux at ice base  
     232      CALL iom_put ('hfxdhc'     , diag_heat(:,:)       )   ! Heat content variation in snow and ice  
     233      CALL iom_put ('hfxspr'     , hfx_spr(:,:)         )   ! Heat content of snow precip  
    231234       
    232235      !-------------------------------- 
     
    238241      CALL iom_put( "salinity_cat"     , sm_i        )        ! salinity for categories 
    239242 
     243      ! ice temperature 
     244      IF ( iom_use( "icetemp_cat" ) ) THEN  
     245         zt_i(:,:,:) = SUM( t_i(:,:,:,:), dim=3 ) * r1_nlay_i 
     246         CALL iom_put( "icetemp_cat"   , zt_i - rt0  ) 
     247      ENDIF 
     248       
     249      ! snow temperature 
     250      IF ( iom_use( "snwtemp_cat" ) ) THEN  
     251         zt_s(:,:,:) = SUM( t_s(:,:,:,:), dim=3 ) * r1_nlay_s 
     252         CALL iom_put( "snwtemp_cat"   , zt_s - rt0  ) 
     253      ENDIF 
     254 
    240255      ! Compute ice age 
    241256      IF ( iom_use( "iceage_cat" ) ) THEN  
     
    243258            DO jj = 1, jpj 
    244259               DO ji = 1, jpi 
    245                   zinda = MAX( 0._wp , SIGN( 1._wp , a_i(ji,jj,jl) - epsi06 ) ) 
    246                   zoi(ji,jj,jl) = oa_i(ji,jj,jl)  / MAX( a_i(ji,jj,jl) , epsi06 ) * zinda 
     260                  rswitch = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - 0.1 ) ) 
     261                  rswitch = rswitch * MAX( 0._wp , SIGN( 1._wp , a_i(ji,jj,jl) - 0.1 ) ) 
     262                  zoi(ji,jj,jl) = oa_i(ji,jj,jl)  / MAX( a_i(ji,jj,jl) , 0.1 ) * rswitch 
    247263               END DO 
    248264            END DO 
    249265         END DO 
    250          CALL iom_put( "iceage_cat"     , zoi        )        ! ice age for categories 
     266         CALL iom_put( "iceage_cat"   , zoi * z1_365 )        ! ice age for categories 
    251267      ENDIF 
    252268 
     
    258274               DO jj = 1, jpj 
    259275                  DO ji = 1, jpi 
    260                      zinda = MAX( 0._wp , SIGN( 1._wp , a_i(ji,jj,jl) - epsi06 ) ) 
    261                      zei(ji,jj,jl) = zei(ji,jj,jl) + 100.0* & 
    262                         ( - tmut * s_i(ji,jj,jk,jl) / MIN( ( t_i(ji,jj,jk,jl) - rtt ), - epsi06 ) ) * & 
    263                         zinda / nlay_i 
     276                     rswitch = MAX( 0._wp , SIGN( 1._wp , a_i(ji,jj,jl) - epsi06 ) ) 
     277                     zei(ji,jj,jl) = zei(ji,jj,jl) + 100.0 * & 
     278                        ( - tmut * s_i(ji,jj,jk,jl) / MIN( ( t_i(ji,jj,jk,jl) - rt0 ), - epsi06 ) ) * & 
     279                        rswitch * r1_nlay_i 
    264280                  END DO 
    265281               END DO 
    266282            END DO 
    267283         END DO 
    268          CALL iom_put( "brinevol_cat"     , zei         )        ! brine volume for categories 
     284         CALL iom_put( "brinevol_cat"     , zei      )        ! brine volume for categories 
    269285      ENDIF 
    270286 
     
    273289      !     not yet implemented 
    274290       
    275       CALL wrk_dealloc( jpi, jpj, jpl, zoi, zei ) 
    276       CALL wrk_dealloc( jpi, jpj     , z2d, zind, z2da, z2db ) 
     291      CALL wrk_dealloc( jpi, jpj, jpl, zoi, zei, zt_i, zt_s ) 
     292      CALL wrk_dealloc( jpi, jpj     , z2d, zswi, z2da, z2db ) 
    277293 
    278294      IF( nn_timing == 1 )  CALL timing_stop('limwri') 
    279295       
    280296   END SUBROUTINE lim_wri 
    281 #endif 
    282297 
    283298  
     
    298313      !!---------------------------------------------------------------------- 
    299314 
    300       CALL histdef( kid, "iicethic", "Ice thickness"           , "m"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    301       CALL histdef( kid, "iiceconc", "Ice concentration"       , "%"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    302       CALL histdef( kid, "iicetemp", "Ice temperature"         , "C"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    303       CALL histdef( kid, "iicevelu", "i-Ice speed (I-point)"   , "m/s"    , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    304       CALL histdef( kid, "iicevelv", "j-Ice speed (I-point)"   , "m/s"    , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
    305       CALL histdef( kid, "iicestru", "i-Wind stress over ice (I-pt)", "Pa", jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    306       CALL histdef( kid, "iicestrv", "j-Wind stress over ice (I-pt)", "Pa", jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
    307       CALL histdef( kid, "iicesflx", "Solar flux over ocean"     , "w/m2"   , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
    308       CALL histdef( kid, "iicenflx", "Non-solar flux over ocean" , "w/m2"   , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    309       CALL histdef( kid, "isnowpre", "Snow precipitation"      , "kg/m2/s", jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
    310       CALL histdef( kid, "iicesali", "Ice salinity"            , "PSU"    , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
    311       CALL histdef( kid, "iicevolu", "Ice volume"              , "m"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
    312       CALL histdef( kid, "iicedive", "Ice divergence"          , "10-8s-1", jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
    313       CALL histdef( kid, "iicebopr", "Ice bottom production"   , "m/s"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    314       CALL histdef( kid, "iicedypr", "Ice dynamic production"  , "m/s"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    315       CALL histdef( kid, "iicelapr", "Ice open water prod"     , "m/s"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    316       CALL histdef( kid, "iicesipr", "Snow ice production "    , "m/s"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    317       CALL histdef( kid, "iicerepr", "Ice prod from limupdate" , "m/s"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    318       CALL histdef( kid, "iicebome", "Ice bottom melt"         , "m/s"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    319       CALL histdef( kid, "iicesume", "Ice surface melt"        , "m/s"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    320       CALL histdef( kid, "iisfxdyn", "Salt flux from dynmics"  , ""      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    321       CALL histdef( kid, "iisfxres", "Salt flux from limupdate", ""      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     315      CALL histdef( kid, "iicethic", "Ice thickness"           , "m"      ,   & 
     316      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     317      CALL histdef( kid, "iiceconc", "Ice concentration"       , "%"      ,   & 
     318      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     319      CALL histdef( kid, "iicetemp", "Ice temperature"         , "C"      ,   & 
     320      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     321      CALL histdef( kid, "iicevelu", "i-Ice speed (I-point)"   , "m/s"    ,   & 
     322      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     323      CALL histdef( kid, "iicevelv", "j-Ice speed (I-point)"   , "m/s"    ,   & 
     324      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     325      CALL histdef( kid, "iicestru", "i-Wind stress over ice (I-pt)", "Pa",   & 
     326      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     327      CALL histdef( kid, "iicestrv", "j-Wind stress over ice (I-pt)", "Pa",   & 
     328      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     329      CALL histdef( kid, "iicesflx", "Solar flux over ocean"     , "w/m2" ,   & 
     330      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     331      CALL histdef( kid, "iicenflx", "Non-solar flux over ocean" , "w/m2" ,   & 
     332      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     333      CALL histdef( kid, "isnowpre", "Snow precipitation"      , "kg/m2/s",   & 
     334      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     335      CALL histdef( kid, "iicesali", "Ice salinity"            , "PSU"    ,   & 
     336      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     337      CALL histdef( kid, "iicevolu", "Ice volume"              , "m"      ,   & 
     338      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     339      CALL histdef( kid, "iicedive", "Ice divergence"          , "10-8s-1",   & 
     340      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     341      CALL histdef( kid, "iicebopr", "Ice bottom production"   , "m/s"    ,   & 
     342      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     343      CALL histdef( kid, "iicedypr", "Ice dynamic production"  , "m/s"    ,   & 
     344      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     345      CALL histdef( kid, "iicelapr", "Ice open water prod"     , "m/s"    ,   & 
     346      &       jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     347      CALL histdef( kid, "iicesipr", "Snow ice production "    , "m/s"    ,   & 
     348      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     349      CALL histdef( kid, "iicerepr", "Ice prod from limupdate" , "m/s"    ,   & 
     350      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     351      CALL histdef( kid, "iicebome", "Ice bottom melt"         , "m/s"    ,   & 
     352      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     353      CALL histdef( kid, "iicesume", "Ice surface melt"        , "m/s"    ,   & 
     354      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     355      CALL histdef( kid, "iisfxdyn", "Salt flux from dynmics"  , ""       ,   & 
     356      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     357      CALL histdef( kid, "iisfxres", "Salt flux from limupdate", ""       ,   & 
     358      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    322359 
    323360      CALL histend( kid, snc4set )   ! end of the file definition 
     
    325362      CALL histwrite( kid, "iicethic", kt, icethi        , jpi*jpj, (/1/) )     
    326363      CALL histwrite( kid, "iiceconc", kt, at_i          , jpi*jpj, (/1/) ) 
    327       CALL histwrite( kid, "iicetemp", kt, tm_i - rtt    , jpi*jpj, (/1/) ) 
     364      CALL histwrite( kid, "iicetemp", kt, tm_i - rt0    , jpi*jpj, (/1/) ) 
    328365      CALL histwrite( kid, "iicevelu", kt, u_ice          , jpi*jpj, (/1/) ) 
    329366      CALL histwrite( kid, "iicevelv", kt, v_ice          , jpi*jpj, (/1/) ) 
Note: See TracChangeset for help on using the changeset viewer.