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 7646 for trunk/NEMOGCM/NEMO/LIM_SRC_3/limwri.F90 – NEMO

Ignore:
Timestamp:
2017-02-06T10:25:03+01:00 (7 years ago)
Author:
timgraham
Message:

Merge of dev_merge_2016 into trunk. UPDATE TO ARCHFILES NEEDED for XIOS2.
LIM_SRC_s/limrhg.F90 to follow in next commit due to change of kind (I'm unable to do it in this commit).
Merged using the following steps:

1) svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk .
2) Resolve minor conflicts in sette.sh and namelist_cfg for ORCA2LIM3 (due to a change in trunk after branch was created)
3) svn commit
4) svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
5) svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2016/dev_merge_2016 .
6) At this stage I checked out a clean copy of the branch to compare against what is about to be committed to the trunk.
6) svn commit #Commit code to the trunk

In this commit I have also reverted a change to Fcheck_archfile.sh which was causing problems on the Paris machine.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/LIM_SRC_3/limwri.F90

    r6418 r7646  
    1717   USE sbc_oce         ! Surface boundary condition: ocean fields 
    1818   USE sbc_ice         ! Surface boundary condition: ice fields 
    19    USE dom_ice 
    2019   USE ice 
    2120   USE limvar 
     
    5655      INTEGER  ::  ji, jj, jk, jl  ! dummy loop indices 
    5756      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 
     57      REAL(wp) ::  z2da, z2db, ztmp 
     58      REAL(wp), POINTER, DIMENSION(:,:,:) ::  zswi2 
     59      REAL(wp), POINTER, DIMENSION(:,:)   ::  z2d, zswi    ! 2D workspace 
    6160      !!------------------------------------------------------------------- 
    6261 
    6362      IF( nn_timing == 1 )  CALL timing_start('limwri') 
    6463 
    65       CALL wrk_alloc( jpi, jpj, jpl, zoi, zei, zt_i, zt_s ) 
    66       CALL wrk_alloc( jpi, jpj     , z2d, z2da, z2db, zswi ) 
     64      CALL wrk_alloc( jpi,jpj,jpl, zswi2 ) 
     65      CALL wrk_alloc( jpi,jpj    , z2d, zswi ) 
    6766 
    6867      !----------------------------- 
     
    7170      z1_365 = 1._wp / 365._wp 
    7271 
    73       CALL lim_var_icetm      ! mean sea ice temperature 
    74  
    75       CALL lim_var_bv         ! brine volume 
    76  
    77       DO jj = 1, jpj          ! presence indicator of ice 
     72      ! brine volume 
     73      CALL lim_var_bv  
     74 
     75      ! tresholds for outputs 
     76      DO jj = 1, jpj 
    7877         DO ji = 1, jpi 
    7978            zswi(ji,jj)  = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - epsi06 ) ) 
    8079         END DO 
    8180      END DO 
    82       ! 
    83       ! 
    84       !                                              
    85       IF ( iom_use( "icethic_cea" ) ) THEN                       ! mean ice thickness 
    86          DO jj = 1, jpj  
     81      DO jl = 1, jpl 
     82         DO jj = 1, jpj 
    8783            DO ji = 1, jpi 
    88                z2d(ji,jj)  = vt_i(ji,jj) / MAX( at_i(ji,jj), epsi06 ) * zswi(ji,jj) 
     84               zswi2(ji,jj,jl)  = MAX( 0._wp , SIGN( 1._wp , a_i(ji,jj,jl) - epsi06 ) ) 
    8985            END DO 
    9086         END DO 
    91          CALL iom_put( "icethic_cea"  , z2d              ) 
    92       ENDIF 
    93  
    94       IF ( iom_use( "snowthic_cea" ) ) THEN                      ! snow thickness = mean snow thickness over the cell  
    95          DO jj = 1, jpj                                             
    96             DO ji = 1, jpi 
    97                z2d(ji,jj)  = vt_s(ji,jj) / MAX( at_i(ji,jj), epsi06 ) * zswi(ji,jj) 
    98             END DO 
    99          END DO 
    100          CALL iom_put( "snowthic_cea" , z2d              )        
    101       ENDIF 
     87      END DO 
    10288      ! 
     89      ! fluxes 
     90      ! pfrld is the lead fraction at the previous time step (actually between TRP and THD) 
     91      IF( iom_use('qsr_oce') )   CALL iom_put( "qsr_oce" , qsr_oce(:,:) * pfrld(:,:) )                                   !     solar flux at ocean surface 
     92      IF( iom_use('qns_oce') )   CALL iom_put( "qns_oce" , qns_oce(:,:) * pfrld(:,:) + qemp_oce(:,:) )                   ! non-solar flux at ocean surface 
     93      IF( iom_use('qsr_ice') )   CALL iom_put( "qsr_ice" , SUM( qsr_ice(:,:,:) * a_i_b(:,:,:), dim=3 ) )                 !     solar flux at ice surface 
     94      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 
     95      IF( iom_use('qtr_ice') )   CALL iom_put( "qtr_ice" , SUM( ftr_ice(:,:,:) * a_i_b(:,:,:), dim=3 ) )                 !     solar flux transmitted thru ice 
     96      IF( iom_use('qt_oce' ) )   CALL iom_put( "qt_oce"  , ( qsr_oce(:,:) + qns_oce(:,:) ) * pfrld(:,:) + qemp_oce(:,:) )   
     97      IF( iom_use('qt_ice' ) )   CALL iom_put( "qt_ice"  , SUM( ( qns_ice(:,:,:) + qsr_ice(:,:,:) )   & 
     98         &                                                      * a_i_b(:,:,:), dim=3 ) + qemp_ice(:,:) ) 
     99      IF( iom_use('qemp_oce') )  CALL iom_put( "qemp_oce" , qemp_oce(:,:) )   
     100      IF( iom_use('qemp_ice') )  CALL iom_put( "qemp_ice" , qemp_ice(:,:) )   
     101      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) 
     102      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) 
     103 
     104      ! velocity 
    103105      IF ( iom_use( "uice_ipa" ) .OR. iom_use( "vice_ipa" ) .OR. iom_use( "icevel" ) ) THEN  
    104106         DO jj = 2 , jpjm1 
    105107            DO ji = 2 , jpim1 
    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 
     108               z2da  = ( u_ice(ji,jj) * umask(ji,jj,1) + u_ice(ji-1,jj) * umask(ji-1,jj,1) ) * 0.5_wp 
     109               z2db  = ( v_ice(ji,jj) * vmask(ji,jj,1) + v_ice(ji,jj-1) * vmask(ji,jj-1,1) ) * 0.5_wp 
     110               z2d(ji,jj) = SQRT( z2da * z2da + z2db * z2db ) 
    108111           END DO 
    109112         END DO 
    110          CALL lbc_lnk( z2da, 'T', -1. ) 
    111          CALL lbc_lnk( z2db, 'T', -1. ) 
    112          CALL iom_put( "uice_ipa"     , z2da             )       ! ice velocity u component 
    113          CALL iom_put( "vice_ipa"     , z2db             )       ! ice velocity v component 
    114          DO jj = 1, jpj                                  
    115             DO ji = 1, jpi 
    116                z2d(ji,jj)  = SQRT( z2da(ji,jj) * z2da(ji,jj) + z2db(ji,jj) * z2db(ji,jj) )  
    117             END DO 
    118          END DO 
    119          CALL iom_put( "icevel"       , z2d              )       ! ice velocity module 
     113         CALL lbc_lnk( z2d, 'T', 1. ) 
     114         CALL iom_put( "uice_ipa"     , u_ice      )       ! ice velocity u component 
     115         CALL iom_put( "vice_ipa"     , v_ice      )       ! ice velocity v component 
     116         CALL iom_put( "icevel"       , z2d        )       ! ice velocity module 
    120117      ENDIF 
     118 
     119      IF ( iom_use( "tau_icebfr" ) )    CALL iom_put( "tau_icebfr"  , tau_icebfr             )  ! ice friction with ocean bottom (landfast ice)   
    121120      ! 
    122       IF ( iom_use( "miceage" ) ) THEN  
    123          z2d(:,:) = 0.e0 
    124          DO jl = 1, jpl 
    125             DO jj = 1, jpj 
    126                DO ji = 1, jpi 
    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 ) 
    129                END DO 
    130             END DO 
    131          END DO 
    132          CALL iom_put( "miceage"     , z2d * z1_365      )        ! mean ice age 
    133       ENDIF 
    134  
    135       IF ( iom_use( "micet" ) ) THEN  
    136          DO jj = 1, jpj 
    137             DO ji = 1, jpi 
    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 
    142       ENDIF 
     121      IF ( iom_use( "miceage" ) )       CALL iom_put( "miceage"     , om_i * zswi * z1_365   )  ! mean ice age 
     122      IF ( iom_use( "icethic_cea" ) )   CALL iom_put( "icethic_cea" , htm_i * zswi           )  ! ice thickness mean 
     123      IF ( iom_use( "snowthic_cea" ) )  CALL iom_put( "snowthic_cea", htm_s * zswi           )  ! snow thickness mean 
     124      IF ( iom_use( "micet" ) )         CALL iom_put( "micet"       , ( tm_i  - rt0 ) * zswi )  ! ice mean    temperature 
     125      IF ( iom_use( "icest" ) )         CALL iom_put( "icest"       , ( tm_su - rt0 ) * zswi )  ! ice surface temperature 
     126      IF ( iom_use( "icecolf" ) )       CALL iom_put( "icecolf"     , hicol                  )  ! frazil ice collection thickness 
    143127      ! 
    144       IF ( iom_use( "icest" ) ) THEN  
    145          z2d(:,:) = 0.e0 
    146          DO jl = 1, jpl 
    147             DO jj = 1, jpj 
    148                DO ji = 1, jpi 
    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 ) 
    150                END DO 
    151             END DO 
    152          END DO 
    153          CALL iom_put( "icest"       , z2d              )        ! ice surface temperature 
    154       ENDIF 
    155  
    156       IF ( iom_use( "icecolf" ) )   CALL iom_put( "icecolf", hicol )  ! frazil ice collection thickness 
    157   
    158128      CALL iom_put( "isst"        , sst_m               )        ! sea surface temperature 
    159129      CALL iom_put( "isss"        , sss_m               )        ! sea surface salinity 
    160       CALL iom_put( "iceconc"     , at_i                )        ! ice concentration 
    161       CALL iom_put( "icevolu"     , vt_i                )        ! ice volume = mean ice thickness over the cell 
    162       CALL iom_put( "icehc"       , et_i                )        ! ice total heat content 
    163       CALL iom_put( "isnowhc"     , et_s                )        ! snow total heat content 
    164       CALL iom_put( "ibrinv"      , bv_i * 100._wp      )        ! brine volume 
     130      CALL iom_put( "iceconc"     , at_i  * zswi        )        ! ice concentration 
     131      CALL iom_put( "icevolu"     , vt_i  * zswi        )        ! ice volume = mean ice thickness over the cell 
     132      CALL iom_put( "icehc"       , et_i  * zswi        )        ! ice total heat content 
     133      CALL iom_put( "isnowhc"     , et_s  * zswi        )        ! snow total heat content 
     134      CALL iom_put( "ibrinv"      , bvm_i * zswi * 100. )        ! brine volume 
    165135      CALL iom_put( "utau_ice"    , utau_ice            )        ! wind stress over ice along i-axis at I-point 
    166136      CALL iom_put( "vtau_ice"    , vtau_ice            )        ! wind stress over ice along j-axis at I-point 
    167137      CALL iom_put( "snowpre"     , sprecip * 86400.    )        ! snow precipitation  
    168       CALL iom_put( "micesalt"    , smt_i               )        ! mean ice salinity 
    169  
    170       CALL iom_put( "icestr"      , strength * 0.001    )        ! ice strength 
    171       CALL iom_put( "idive"       , divu_i * 1.0e8      )        ! divergence 
    172       CALL iom_put( "ishear"      , shear_i * 1.0e8     )        ! shear 
    173       CALL iom_put( "snowvol"     , vt_s                )        ! snow volume 
     138      CALL iom_put( "micesalt"    , smt_i   * zswi      )        ! mean ice salinity 
     139 
     140      CALL iom_put( "icestr"      , strength * zswi )    ! ice strength 
     141      CALL iom_put( "idive"       , divu_i * 1.0e8      )    ! divergence 
     142      CALL iom_put( "ishear"      , shear_i * 1.0e8     )    ! shear 
     143      CALL iom_put( "snowvol"     , vt_s   * zswi       )        ! snow volume 
    174144       
    175145      CALL iom_put( "icetrp"      , diag_trp_vi * rday  )        ! ice volume transport 
     
    180150 
    181151      CALL iom_put( "sfxbog"      , sfx_bog * rday      )        ! salt flux from bottom growth 
    182       CALL iom_put( "sfxbom"      , sfx_bom * rday      )        ! salt flux from bottom melt 
    183       CALL iom_put( "sfxsum"      , sfx_sum * rday      )        ! salt flux from surface melt 
     152      CALL iom_put( "sfxbom"      , sfx_bom * rday      )        ! salt flux from bottom melting 
     153      CALL iom_put( "sfxsum"      , sfx_sum * rday      )        ! salt flux from surface melting 
     154      CALL iom_put( "sfxlam"      , sfx_lam * rday      )        ! salt flux from lateral melting 
    184155      CALL iom_put( "sfxsni"      , sfx_sni * rday      )        ! salt flux from snow ice formation 
    185156      CALL iom_put( "sfxopw"      , sfx_opw * rday      )        ! salt flux from open water formation 
    186157      CALL iom_put( "sfxdyn"      , sfx_dyn * rday      )        ! salt flux from ridging rafting 
    187       CALL iom_put( "sfxres"      , sfx_res * rday      )        ! salt flux from residual 
     158      CALL iom_put( "sfxres"      , sfx_res * rday      )        ! salt flux from limupdate (resultant) 
    188159      CALL iom_put( "sfxbri"      , sfx_bri * rday      )        ! salt flux from brines 
    189160      CALL iom_put( "sfxsub"      , sfx_sub * rday      )        ! salt flux from sublimation 
     
    198169      CALL iom_put( "vfxsum"     , wfx_sum * ztmp       )        ! surface melt  
    199170      CALL iom_put( "vfxbom"     , wfx_bom * ztmp       )        ! bottom melt  
     171      CALL iom_put( "vfxlam"     , wfx_lam * ztmp       )        ! lateral melt  
    200172      CALL iom_put( "vfxice"     , wfx_ice * ztmp       )        ! total ice growth/melt  
     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 / rhosn 
     182      CALL iom_put( "vfxspr"     , wfx_spr * ztmp       )        ! precip (snow) 
    201183      CALL iom_put( "vfxsnw"     , wfx_snw * ztmp       )        ! total snw growth/melt  
    202       CALL iom_put( "vfxsub"     , wfx_sub * ztmp       )        ! sublimation (snow)  
    203       CALL iom_put( "vfxspr"     , wfx_spr * ztmp       )        ! precip (snow) 
     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  
    204186       
    205187      CALL iom_put( "afxtot"     , afx_tot * rday       )        ! concentration tendency (total) 
     
    222204      CALL iom_put ('hfxdif'     , hfx_dif(:,:)         )   !   
    223205      CALL iom_put ('hfxopw'     , hfx_opw(:,:)         )   !   
    224       CALL iom_put ('hfxtur'     , fhtur(:,:) * SUM(a_i_b(:,:,:), dim=3) ) ! turbulent heat flux at ice base  
     206      CALL iom_put ('hfxtur'     , fhtur(:,:) * at_i_b(:,:) ) ! turbulent heat flux at ice base  
    225207      CALL iom_put ('hfxdhc'     , diag_heat(:,:)       )   ! Heat content variation in snow and ice  
    226208      CALL iom_put ('hfxspr'     , hfx_spr(:,:)         )   ! Heat content of snow precip  
    227        
    228       IF ( iom_use( "vfxthin" ) ) THEN   ! ice production for open water + thin ice (<20cm) => comparable to observations   
    229          DO jj = 1, jpj  
    230             DO ji = 1, jpi 
    231                z2d(ji,jj)  = vt_i(ji,jj) / MAX( at_i(ji,jj), epsi06 ) * zswi(ji,jj) ! mean ice thickness 
    232             END DO 
    233          END DO 
    234          WHERE( z2d(:,:) < 0.2 .AND. z2d(:,:) > 0. ) ; z2da = wfx_bog 
    235          ELSEWHERE                                   ; z2da = 0._wp 
    236          END WHERE 
    237          CALL iom_put( "vfxthin", ( wfx_opw + z2da ) * ztmp ) 
    238       ENDIF 
    239  
     209 
     210       
    240211      !-------------------------------- 
    241212      ! Output values for each category 
    242213      !-------------------------------- 
    243       CALL iom_put( "iceconc_cat"      , a_i         )        ! area for categories 
    244       CALL iom_put( "icethic_cat"      , ht_i        )        ! thickness for categories 
    245       CALL iom_put( "snowthic_cat"     , ht_s        )        ! snow depth for categories 
    246       CALL iom_put( "salinity_cat"     , sm_i        )        ! salinity for categories 
    247  
     214      IF ( iom_use( "iceconc_cat"  ) )  CALL iom_put( "iceconc_cat"      , a_i   * zswi2   )        ! area for categories 
     215      IF ( iom_use( "icethic_cat"  ) )  CALL iom_put( "icethic_cat"      , ht_i  * zswi2   )        ! thickness for categories 
     216      IF ( iom_use( "snowthic_cat" ) )  CALL iom_put( "snowthic_cat"     , ht_s  * zswi2   )        ! snow depth for categories 
     217      IF ( iom_use( "salinity_cat" ) )  CALL iom_put( "salinity_cat"     , sm_i  * zswi2   )        ! salinity for categories 
    248218      ! ice temperature 
    249       IF ( iom_use( "icetemp_cat" ) ) THEN  
    250          zt_i(:,:,:) = SUM( t_i(:,:,:,:), dim=3 ) * r1_nlay_i 
    251          CALL iom_put( "icetemp_cat"   , zt_i - rt0  ) 
    252       ENDIF 
    253        
     219      IF ( iom_use( "icetemp_cat"  ) )  CALL iom_put( "icetemp_cat", ( SUM( t_i(:,:,:,:), dim=3 ) * r1_nlay_i - rt0 ) * zswi2 ) 
    254220      ! snow temperature 
    255       IF ( iom_use( "snwtemp_cat" ) ) THEN  
    256          zt_s(:,:,:) = SUM( t_s(:,:,:,:), dim=3 ) * r1_nlay_s 
    257          CALL iom_put( "snwtemp_cat"   , zt_s - rt0  ) 
    258       ENDIF 
    259  
    260       ! Compute ice age 
    261       IF ( iom_use( "iceage_cat" ) ) THEN  
    262          DO jl = 1, jpl  
    263             DO jj = 1, jpj 
    264                DO ji = 1, jpi 
    265                   rswitch = MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - 0.1 ) ) 
    266                   rswitch = rswitch * MAX( 0._wp , SIGN( 1._wp , a_i(ji,jj,jl) - 0.1 ) ) 
    267                   zoi(ji,jj,jl) = oa_i(ji,jj,jl)  / MAX( a_i(ji,jj,jl) , 0.1 ) * rswitch 
    268                END DO 
    269             END DO 
    270          END DO 
    271          CALL iom_put( "iceage_cat"   , zoi * z1_365 )        ! ice age for categories 
    272       ENDIF 
    273  
    274       ! Compute brine volume 
    275       IF ( iom_use( "brinevol_cat" ) ) THEN  
    276          zei(:,:,:) = 0._wp 
    277          DO jl = 1, jpl  
    278             DO jk = 1, nlay_i 
    279                DO jj = 1, jpj 
    280                   DO ji = 1, jpi 
    281                      rswitch = MAX( 0._wp , SIGN( 1._wp , a_i(ji,jj,jl) - epsi06 ) ) 
    282                      zei(ji,jj,jl) = zei(ji,jj,jl) + 100.0 *  & 
    283                         ( - tmut * s_i(ji,jj,jk,jl) / MIN( ( t_i(ji,jj,jk,jl) - rt0 ), - epsi06 ) ) * & 
    284                         rswitch * r1_nlay_i 
    285                   END DO 
    286                END DO 
    287             END DO 
    288          END DO 
    289          CALL iom_put( "brinevol_cat"     , zei      )        ! brine volume for categories 
    290       ENDIF 
     221      IF ( iom_use( "snwtemp_cat"  ) )  CALL iom_put( "snwtemp_cat", ( SUM( t_s(:,:,:,:), dim=3 ) * r1_nlay_s - rt0 ) * zswi2 ) 
     222      ! ice age 
     223      IF ( iom_use( "iceage_cat"   ) )  CALL iom_put( "iceage_cat" , o_i * zswi2 * z1_365 ) 
     224      ! brine volume 
     225      IF ( iom_use( "brinevol_cat" ) )  CALL iom_put( "brinevol_cat", bv_i * 100. * zswi2 ) 
    291226 
    292227      !     !  Create an output files (output.lim.abort.nc) if S < 0 or u > 20 m/s 
     
    294229      !     not yet implemented 
    295230       
    296       CALL wrk_dealloc( jpi, jpj, jpl, zoi, zei, zt_i, zt_s ) 
    297       CALL wrk_dealloc( jpi, jpj     , z2d, zswi, z2da, z2db ) 
     231      CALL wrk_dealloc( jpi, jpj, jpl, zswi2 ) 
     232      CALL wrk_dealloc( jpi, jpj     , z2d, zswi ) 
    298233 
    299234      IF( nn_timing == 1 )  CALL timing_stop('limwri') 
     
    312247      !! 
    313248      !! History : 
    314       !!   4.1  !  2013-06  (C. Rousset) 
     249      !!   4.0  !  2013-06  (C. Rousset) 
    315250      !!---------------------------------------------------------------------- 
    316       INTEGER, INTENT( in ) ::   kt               ! ocean time-step index) 
    317       INTEGER, INTENT( in ) ::   kid , kh_i        
     251      INTEGER, INTENT( in )   ::   kt               ! ocean time-step index) 
     252      INTEGER, INTENT( in )   ::   kid , kh_i 
     253      INTEGER                 ::   nz_i, jl 
     254      REAL(wp), DIMENSION(jpl) :: jcat 
    318255      !!---------------------------------------------------------------------- 
    319  
    320       CALL histdef( kid, "iicethic", "Ice thickness"           , "m"      ,   & 
    321       &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    322       CALL histdef( kid, "iiceconc", "Ice concentration"       , "%"      ,   & 
    323       &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    324       CALL histdef( kid, "iicetemp", "Ice temperature"         , "C"      ,   & 
    325       &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    326       CALL histdef( kid, "iicevelu", "i-Ice speed (I-point)"   , "m/s"    ,   & 
    327       &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    328       CALL histdef( kid, "iicevelv", "j-Ice speed (I-point)"   , "m/s"    ,   & 
    329       &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
    330       CALL histdef( kid, "iicestru", "i-Wind stress over ice (I-pt)", "Pa",   & 
    331       &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    332       CALL histdef( kid, "iicestrv", "j-Wind stress over ice (I-pt)", "Pa",   & 
    333       &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
    334       CALL histdef( kid, "iicesflx", "Solar flux over ocean"     , "w/m2" ,   & 
    335       &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
    336       CALL histdef( kid, "iicenflx", "Non-solar flux over ocean" , "w/m2" ,   & 
     256      DO jl = 1, jpl 
     257         jcat(jl) = REAL(jl) 
     258      ENDDO 
     259       
     260      CALL histvert( kid, "ncatice", "Ice Categories","", jpl, jcat, nz_i, "up") 
     261 
     262      CALL histdef( kid, "sithic", "Ice thickness"           , "m"      ,   & 
     263      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     264      CALL histdef( kid, "siconc", "Ice concentration"       , "%"      ,   & 
     265      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     266      CALL histdef( kid, "sitemp", "Ice temperature"         , "C"      ,   & 
     267      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     268      CALL histdef( kid, "sivelu", "i-Ice speed "            , "m/s"    ,   & 
     269      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     270      CALL histdef( kid, "sivelv", "j-Ice speed "            , "m/s"    ,   & 
     271      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     272      CALL histdef( kid, "sistru", "i-Wind stress over ice " , "Pa"     ,   & 
     273      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     274      CALL histdef( kid, "sistrv", "j-Wind stress over ice " , "Pa"     ,   & 
     275      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     276      CALL histdef( kid, "sisflx", "Solar flux over ocean"     , "w/m2" ,   & 
     277      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     278      CALL histdef( kid, "sinflx", "Non-solar flux over ocean" , "w/m2" ,   & 
    337279      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    338280      CALL histdef( kid, "isnowpre", "Snow precipitation"      , "kg/m2/s",   & 
    339281      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
    340       CALL histdef( kid, "iicesali", "Ice salinity"            , "PSU"    ,   & 
    341       &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
    342       CALL histdef( kid, "iicevolu", "Ice volume"              , "m"      ,   & 
    343       &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
    344       CALL histdef( kid, "iicedive", "Ice divergence"          , "10-8s-1",   & 
    345       &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
    346       CALL histdef( kid, "iicebopr", "Ice bottom production"   , "m/s"    ,   & 
    347       &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    348       CALL histdef( kid, "iicedypr", "Ice dynamic production"  , "m/s"    ,   & 
    349       &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    350       CALL histdef( kid, "iicelapr", "Ice open water prod"     , "m/s"    ,   & 
     282      CALL histdef( kid, "sisali", "Ice salinity"            , "PSU"    ,   & 
     283      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     284      CALL histdef( kid, "sivolu", "Ice volume"              , "m"      ,   & 
     285      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     286      CALL histdef( kid, "sidive", "Ice divergence"          , "10-8s-1",   & 
     287      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     288 
     289      CALL histdef( kid, "vfxbog", "Ice bottom production"   , "m/s"    ,   & 
     290      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     291      CALL histdef( kid, "vfxdyn", "Ice dynamic production"  , "m/s"    ,   & 
     292      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     293      CALL histdef( kid, "vfxopw", "Ice open water prod"     , "m/s"    ,   & 
    351294      &       jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    352       CALL histdef( kid, "iicesipr", "Snow ice production "    , "m/s"    ,   & 
    353       &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    354       CALL histdef( kid, "iicerepr", "Ice prod from limupdate" , "m/s"    ,   & 
    355       &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    356       CALL histdef( kid, "iicebome", "Ice bottom melt"         , "m/s"    ,   & 
    357       &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    358       CALL histdef( kid, "iicesume", "Ice surface melt"        , "m/s"    ,   & 
    359       &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    360       CALL histdef( kid, "iisfxdyn", "Salt flux from dynmics"  , ""       ,   & 
    361       &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
    362       CALL histdef( kid, "iisfxres", "Salt flux from limupdate", ""       ,   & 
    363       &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     295      CALL histdef( kid, "vfxsni", "Snow ice production "    , "m/s"    ,   & 
     296      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     297      CALL histdef( kid, "vfxres", "Ice prod from limupdate" , "m/s"    ,   & 
     298      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     299      CALL histdef( kid, "vfxbom", "Ice bottom melt"         , "m/s"    ,   & 
     300      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     301      CALL histdef( kid, "vfxsum", "Ice surface melt"        , "m/s"    ,   & 
     302      &      jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     303 
     304      CALL histdef( kid, "sithicat", "Ice thickness"         , "m"      ,   & 
     305      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt ) 
     306      CALL histdef( kid, "siconcat", "Ice concentration"     , "%"      ,   & 
     307      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt ) 
     308      CALL histdef( kid, "sisalcat", "Ice salinity"           , ""      ,   & 
     309      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt ) 
     310      CALL histdef( kid, "sitemcat", "Ice temperature"       , "C"      ,   & 
     311      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt ) 
     312      CALL histdef( kid, "snthicat", "Snw thickness"         , "m"      ,   & 
     313      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt ) 
     314      CALL histdef( kid, "sntemcat", "Snw temperature"       , "C"      ,   & 
     315      &      jpi, jpj, kh_i, jpl, 1, jpl, nz_i, 32, "inst(x)", rdt, rdt ) 
    364316 
    365317      CALL histend( kid, snc4set )   ! end of the file definition 
    366318 
    367       CALL histwrite( kid, "iicethic", kt, icethi        , jpi*jpj, (/1/) )     
    368       CALL histwrite( kid, "iiceconc", kt, at_i          , jpi*jpj, (/1/) ) 
    369       CALL histwrite( kid, "iicetemp", kt, tm_i - rt0    , jpi*jpj, (/1/) ) 
    370       CALL histwrite( kid, "iicevelu", kt, u_ice          , jpi*jpj, (/1/) ) 
    371       CALL histwrite( kid, "iicevelv", kt, v_ice          , jpi*jpj, (/1/) ) 
    372       CALL histwrite( kid, "iicestru", kt, utau_ice       , jpi*jpj, (/1/) ) 
    373       CALL histwrite( kid, "iicestrv", kt, vtau_ice       , jpi*jpj, (/1/) ) 
    374       CALL histwrite( kid, "iicesflx", kt, qsr , jpi*jpj, (/1/) ) 
    375       CALL histwrite( kid, "iicenflx", kt, qns , jpi*jpj, (/1/) ) 
     319      CALL histwrite( kid, "sithic", kt, htm_i         , jpi*jpj, (/1/) )     
     320      CALL histwrite( kid, "siconc", kt, at_i          , jpi*jpj, (/1/) ) 
     321      CALL histwrite( kid, "sitemp", kt, tm_i - rt0    , jpi*jpj, (/1/) ) 
     322      CALL histwrite( kid, "sivelu", kt, u_ice          , jpi*jpj, (/1/) ) 
     323      CALL histwrite( kid, "sivelv", kt, v_ice          , jpi*jpj, (/1/) ) 
     324      CALL histwrite( kid, "sistru", kt, utau_ice       , jpi*jpj, (/1/) ) 
     325      CALL histwrite( kid, "sistrv", kt, vtau_ice       , jpi*jpj, (/1/) ) 
     326      CALL histwrite( kid, "sisflx", kt, qsr , jpi*jpj, (/1/) ) 
     327      CALL histwrite( kid, "sinflx", kt, qns , jpi*jpj, (/1/) ) 
    376328      CALL histwrite( kid, "isnowpre", kt, sprecip        , jpi*jpj, (/1/) ) 
    377       CALL histwrite( kid, "iicesali", kt, smt_i          , jpi*jpj, (/1/) ) 
    378       CALL histwrite( kid, "iicevolu", kt, vt_i           , jpi*jpj, (/1/) ) 
    379       CALL histwrite( kid, "iicedive", kt, divu_i*1.0e8   , jpi*jpj, (/1/) ) 
    380  
    381       CALL histwrite( kid, "iicebopr", kt, wfx_bog        , jpi*jpj, (/1/) ) 
    382       CALL histwrite( kid, "iicedypr", kt, wfx_dyn        , jpi*jpj, (/1/) ) 
    383       CALL histwrite( kid, "iicelapr", kt, wfx_opw        , jpi*jpj, (/1/) ) 
    384       CALL histwrite( kid, "iicesipr", kt, wfx_sni        , jpi*jpj, (/1/) ) 
    385       CALL histwrite( kid, "iicerepr", kt, wfx_res        , jpi*jpj, (/1/) ) 
    386       CALL histwrite( kid, "iicebome", kt, wfx_bom        , jpi*jpj, (/1/) ) 
    387       CALL histwrite( kid, "iicesume", kt, wfx_sum        , jpi*jpj, (/1/) ) 
    388       CALL histwrite( kid, "iisfxdyn", kt, sfx_dyn        , jpi*jpj, (/1/) ) 
    389       CALL histwrite( kid, "iisfxres", kt, sfx_res        , jpi*jpj, (/1/) ) 
     329      CALL histwrite( kid, "sisali", kt, smt_i          , jpi*jpj, (/1/) ) 
     330      CALL histwrite( kid, "sivolu", kt, vt_i           , jpi*jpj, (/1/) ) 
     331      CALL histwrite( kid, "sidive", kt, divu_i*1.0e8   , jpi*jpj, (/1/) ) 
     332 
     333      CALL histwrite( kid, "vfxbog", kt, wfx_bog        , jpi*jpj, (/1/) ) 
     334      CALL histwrite( kid, "vfxdyn", kt, wfx_dyn        , jpi*jpj, (/1/) ) 
     335      CALL histwrite( kid, "vfxopw", kt, wfx_opw        , jpi*jpj, (/1/) ) 
     336      CALL histwrite( kid, "vfxsni", kt, wfx_sni        , jpi*jpj, (/1/) ) 
     337      CALL histwrite( kid, "vfxres", kt, wfx_res        , jpi*jpj, (/1/) ) 
     338      CALL histwrite( kid, "vfxbom", kt, wfx_bom        , jpi*jpj, (/1/) ) 
     339      CALL histwrite( kid, "vfxsum", kt, wfx_sum        , jpi*jpj, (/1/) ) 
     340 
     341      CALL histwrite( kid, "sithicat", kt, ht_i        , jpi*jpj*jpl, (/1/) )     
     342      CALL histwrite( kid, "siconcat", kt, a_i         , jpi*jpj*jpl, (/1/) )     
     343      CALL histwrite( kid, "sisalcat", kt, sm_i        , jpi*jpj*jpl, (/1/) )     
     344      CALL histwrite( kid, "sitemcat", kt, tm_i - rt0  , jpi*jpj*jpl, (/1/) )     
     345      CALL histwrite( kid, "snthicat", kt, ht_s        , jpi*jpj*jpl, (/1/) )     
     346      CALL histwrite( kid, "sntemcat", kt, tm_su - rt0 , jpi*jpj*jpl, (/1/) )     
    390347 
    391348      ! Close the file 
Note: See TracChangeset for help on using the changeset viewer.