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 4161 for branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/LIM_SRC_3/limwri.F90 – NEMO

Ignore:
Timestamp:
2013-11-07T11:01:27+01:00 (10 years ago)
Author:
cetlod
Message:

dev_LOCEAN_2013 : merge in the 3rd dev branch dev_r4028_CNRS_LIM3, see ticket #1169

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/LIM_SRC_3/limwri.F90

    r4147 r4161  
    1010   !!   lim_wri      : write of the diagnostics variables in ouput file  
    1111   !!   lim_wri_init : initialization and namelist read 
     12   !!   lim_wri_state : write for initial state or/and abandon 
    1213   !!---------------------------------------------------------------------- 
    1314   USE ioipsl 
     
    2526   USE wrk_nemo        ! work arrays 
    2627   USE par_ice 
    27    USE lib_fortran     ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
     28   USE iom 
     29   USE timing          ! Timing 
     30   USE lib_fortran     ! Fortran utilities 
    2831 
    2932   IMPLICIT NONE 
     
    3134 
    3235   PUBLIC lim_wri        ! routine called by lim_step.F90 
    33  
    34    INTEGER, PARAMETER ::   jpnoumax = 40   !: maximum number of variable for ice output 
     36   PUBLIC lim_wri_state  ! called by dia_wri_state  
     37 
     38   INTEGER, PARAMETER ::   jpnoumax = 43   !: maximum number of variable for ice output 
    3539    
    3640   INTEGER  ::   noumef             ! number of fields 
     
    4852   INTEGER            , DIMENSION(jpnoumax) ::   nc  , nca     ! switch for saving field ( = 1 ) or not ( = 0 ) 
    4953 
    50    REAL(wp)  ::   epsi16 = 1e-16_wp 
     54   REAL(wp)  ::   epsi06 = 1e-6_wp 
    5155   REAL(wp)  ::   zzero  = 0._wp 
    5256   REAL(wp)  ::   zone   = 1._wp       
    5357   !!---------------------------------------------------------------------- 
    54    !! NEMO/LIM3 3.4 , UCL - NEMO Consortium (2011) 
     58   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011) 
    5559   !! $Id$ 
    5660   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    7781      INTEGER ::  ierr 
    7882      REAL(wp),DIMENSION(1) ::   zdept 
    79       REAL(wp) ::  zsto, zjulian, zout, zindh, zinda, zindb 
     83      REAL(wp) ::  zsto, zjulian, zout, zindh, zinda, zindb, zindc 
    8084      REAL(wp), POINTER, DIMENSION(:,:,:) ::   zcmo, zcmoa 
    8185      REAL(wp), POINTER, DIMENSION(:,:  ) ::   zfield 
    8286      REAL(wp), POINTER, DIMENSION(:,:,:) ::   zmaskitd, zoi, zei 
    8387 
    84       CHARACTER(len = 40) ::   clhstnam, clop, clhstnama 
     88      CHARACTER(len = 60) ::   clhstnam, clop, clhstnama 
    8589 
    8690      INTEGER , SAVE ::   nice, nhorid, ndim, niter, ndepid 
     
    9094      !!------------------------------------------------------------------- 
    9195 
     96      IF( nn_timing == 1 )  CALL timing_start('limwri') 
     97 
    9298      CALL wrk_alloc( jpi, jpj, zfield ) 
    9399      CALL wrk_alloc( jpi, jpj, jpnoumax, zcmo, zcmoa ) 
     
    116122         ! Normal file 
    117123         !------------- 
    118  
    119          zsto     = rdt_ice 
    120          IF( ln_mskland )   THEN   ;   clop = "ave(only(x))"   ! put 1.e+20 on land (very expensive!!) 
    121          ELSE                      ;   clop = "ave(x)"         ! no use of the mask value (require less cpu time) 
    122          ENDIF 
    123          zout     = nwrite * rdt_ice / nn_fsbc 
    124124         niter    = ( nit000 - 1 ) / nn_fsbc 
    125          zdept(1) = 0. 
    126  
    127125         CALL ymds2ju ( nyear, nmonth, nday, rdt, zjulian ) 
    128126         zjulian = zjulian - adatrj   !   set calendar origin to the beginning of the experiment 
    129          CALL dia_nam ( clhstnam, nwrite, 'icemod' ) 
    130          CALL histbeg ( clhstnam, jpi, glamt, jpj, gphit, 1, jpi, 1, jpj, niter, zjulian, rdt_ice,   & 
    131             &           nhorid, nice, domain_id=nidom, snc4chunks=snc4set ) 
    132          CALL histvert( nice, "deptht", "Vertical T levels", "m", 1, zdept, ndepid, "down") 
    133          CALL wheneq  ( jpij , tmask(:,:,1), 1, 1., ndex51, ndim) 
    134  
    135          DO jf = 1 , noumef 
    136             IF(lwp) WRITE(numout,*) 'jf', jf 
    137             IF ( nc(jf) == 1 ) THEN 
    138                CALL histdef( nice, nam(jf), titn(jf), uni(jf), jpi, jpj & 
    139                   , nhorid, 1, 1, 1, -99, 32, clop, zsto, zout ) 
    140                IF(lwp) WRITE(numout,*) 'nice, nam(jf), titn(jf), uni(jf), nhorid, clop, zsto, zout' 
    141                IF(lwp) WRITE(numout,*)  nice, nam(jf), titn(jf), uni(jf), nhorid, clop, zsto, zout  
    142             ENDIF 
    143          END DO 
    144  
    145          CALL histend(nice, snc4set) 
    146  
     127!clem 
     128!         zsto     = rdt_ice 
     129!         IF( ln_mskland )   THEN   ;   clop = "ave(only(x))"   ! put 1.e+20 on land (very expensive!!) 
     130!         ELSE                      ;   clop = "ave(x)"         ! no use of the mask value (require less cpu time) 
     131!         ENDIF 
     132!         zout     = nwrite * rdt_ice / nn_fsbc 
     133!         zdept(1) = 0. 
     134! 
     135!         CALL dia_nam ( clhstnam, nwrite, 'icemod_old' ) 
     136!         CALL histbeg ( clhstnam, jpi, glamt, jpj, gphit, 1, jpi, 1, jpj, niter, zjulian, rdt_ice,   & 
     137!            &           nhorid, nice, domain_id=nidom, snc4chunks=snc4set ) 
     138!         CALL histvert( nice, "deptht", "Vertical T levels", "m", 1, zdept, ndepid, "down") 
     139!         CALL wheneq  ( jpij , tmask(:,:,1), 1, 1., ndex51, ndim) 
     140! 
     141!         DO jf = 1 , noumef 
     142!            IF(lwp) WRITE(numout,*) 'jf', jf 
     143!            IF ( nc(jf) == 1 ) THEN 
     144!               CALL histdef( nice, nam(jf), titn(jf), uni(jf), jpi, jpj & 
     145!                  , nhorid, 1, 1, 1, -99, 32, clop, zsto, zout ) 
     146!               IF(lwp) WRITE(numout,*) 'nice, nam(jf), titn(jf), uni(jf), nhorid, clop, zsto, zout' 
     147!               IF(lwp) WRITE(numout,*)  nice, nam(jf), titn(jf), uni(jf), nhorid, clop, zsto, zout  
     148!            ENDIF 
     149!         END DO 
     150! 
     151!         CALL histend(nice, snc4set) 
     152!clem 
     153         ! 
    147154         !----------------- 
    148155         ! ITD file output 
     
    159166            nhorida,                   & ! ? linked with horizontal ... 
    160167            nicea , domain_id=nidom, snc4chunks=snc4set)                  ! file  
    161          CALL histvert( nicea, "icethi", "L levels",               & 
    162             "m", ipl , hi_mean , nz ) 
     168         CALL histvert( nicea, "icethi", "L levels","m", ipl , hi_mean , nz ) 
    163169         DO jl = 1, jpl 
    164170            zmaskitd(:,:,jl) = tmask(:,:,1) 
     
    198204      zcmoa( 1:jpi, 1:jpj, 1:jpnoumax ) = 0._wp 
    199205 
     206      ! Ice surface temperature and some fluxes 
    200207      DO jl = 1, jpl 
    201208         DO jj = 1, jpj 
    202209            DO ji = 1, jpi 
    203                zindh  = MAX( zzero , SIGN( zone , vt_i(ji,jj) * at_i(ji,jj) - 0.10 ) ) 
    204                zinda  = MAX( zzero , SIGN( zone , at_i(ji,jj) - 0.10 ) ) 
     210               zinda  = MAX( zzero , SIGN( zone , at_i(ji,jj) - epsi06 ) ) 
    205211               zcmo(ji,jj,17) = zcmo(ji,jj,17) + a_i(ji,jj,jl)*qsr_ice (ji,jj,jl)  
    206212               zcmo(ji,jj,18) = zcmo(ji,jj,18) + a_i(ji,jj,jl)*qns_ice(ji,jj,jl)  
    207                zcmo(ji,jj,27) = zcmo(ji,jj,27) + t_su(ji,jj,jl)*a_i(ji,jj,jl)/MAX(at_i(ji,jj),epsi16)*zinda 
     213               zcmo(ji,jj,27) = zcmo(ji,jj,27) + zinda*(t_su(ji,jj,jl)-rtt)*a_i(ji,jj,jl)/MAX(at_i(ji,jj),epsi06) 
     214               zcmo(ji,jj,21) = zcmo(ji,jj,21) + zinda*oa_i(ji,jj,jl)/MAX(at_i(ji,jj),epsi06)  
    208215            END DO 
    209216         END DO 
    210217      END DO 
    211218 
     219      ! Mean sea ice temperature 
     220      CALL lim_var_icetm 
     221 
     222      ! Brine volume 
    212223      CALL lim_var_bv 
    213224 
    214225      DO jj = 2 , jpjm1 
    215226         DO ji = 2 , jpim1 
    216             zindh  = MAX( zzero , SIGN( zone , vt_i(ji,jj) * at_i(ji,jj) - 0.10 ) ) 
    217             zinda  = MAX( zzero , SIGN( zone , at_i(ji,jj) - 0.10 ) ) 
    218             zindb  = zindh * zinda 
     227            zinda  = MAX( zzero , SIGN( zone , at_i(ji,jj) - epsi06 ) ) 
     228            zindb  = MAX( zzero , SIGN( zone , at_i(ji,jj) ) ) 
    219229 
    220230            zcmo(ji,jj,1)  = at_i(ji,jj) 
    221             zcmo(ji,jj,2)  = vt_i(ji,jj) / MAX( at_i(ji,jj), epsi16 ) * zinda 
    222             zcmo(ji,jj,3)  = vt_s(ji,jj) / MAX( at_i(ji,jj), epsi16 ) * zinda 
    223             zcmo(ji,jj,4)  = diag_bot_gr(ji,jj) * 86400.0 * zinda    ! Bottom thermodynamic ice production 
    224             zcmo(ji,jj,5)  = diag_dyn_gr(ji,jj) * 86400.0 * zinda    ! Dynamic ice production (rid/raft) 
    225             zcmo(ji,jj,22) = diag_lat_gr(ji,jj) * 86400.0 * zinda    ! Lateral thermodynamic ice production 
    226             zcmo(ji,jj,23) = diag_sni_gr(ji,jj) * 86400.0 * zinda    ! Snow ice production ice production 
    227             zcmo(ji,jj,24) = tm_i(ji,jj) - rtt 
    228  
    229             zcmo(ji,jj,6)  = fbif  (ji,jj) 
    230             zcmo(ji,jj,7)  = zindb * (  u_ice(ji,jj) * tmu(ji,jj) + u_ice(ji-1,jj) * tmu(ji-1,jj) ) * 0.5_wp 
    231             zcmo(ji,jj,8)  = zindb * (  v_ice(ji,jj) * tmv(ji,jj) + v_ice(ji,jj-1) * tmv(ji,jj-1) ) * 0.5_wp 
     231            zcmo(ji,jj,2)  = vt_i(ji,jj) / MAX( at_i(ji,jj), epsi06 ) * zinda 
     232            zcmo(ji,jj,3)  = vt_s(ji,jj) / MAX( at_i(ji,jj), epsi06 ) * zinda 
     233            zcmo(ji,jj,4)  = diag_bot_gr(ji,jj) * rday     ! Bottom thermodynamic ice production 
     234            zcmo(ji,jj,5)  = diag_dyn_gr(ji,jj) * rday     ! Dynamic ice production (rid/raft) 
     235            zcmo(ji,jj,22) = diag_lat_gr(ji,jj) * rday     ! Lateral thermodynamic ice production 
     236            zcmo(ji,jj,23) = diag_sni_gr(ji,jj) * rday     ! Snow ice production ice production 
     237            zcmo(ji,jj,24) = (tm_i(ji,jj) - rtt) * zinda 
     238 
     239            zcmo(ji,jj,6)  = fbif(ji,jj)*at_i(ji,jj) 
     240            zcmo(ji,jj,7)  = (  u_ice(ji,jj) * tmu(ji,jj) + u_ice(ji-1,jj) * tmu(ji-1,jj) ) * 0.5_wp 
     241            zcmo(ji,jj,8)  = (  v_ice(ji,jj) * tmv(ji,jj) + v_ice(ji,jj-1) * tmv(ji,jj-1) ) * 0.5_wp 
    232242            zcmo(ji,jj,9)  = sst_m(ji,jj) 
    233243            zcmo(ji,jj,10) = sss_m(ji,jj) 
     
    243253            zcmo(ji,jj,19) = sprecip(ji,jj) 
    244254            zcmo(ji,jj,20) = smt_i(ji,jj) 
    245             zcmo(ji,jj,21) = ot_i(ji,jj) 
    246255            zcmo(ji,jj,25) = et_i(ji,jj) 
    247256            zcmo(ji,jj,26) = et_s(ji,jj) 
     
    250259 
    251260            zcmo(ji,jj,30) = bv_i(ji,jj) 
    252             zcmo(ji,jj,31) = hicol(ji,jj) 
     261            zcmo(ji,jj,31) = hicol(ji,jj) * zindb 
    253262            zcmo(ji,jj,32) = strength(ji,jj) 
    254263            zcmo(ji,jj,33) = SQRT(  zcmo(ji,jj,7)*zcmo(ji,jj,7) + zcmo(ji,jj,8)*zcmo(ji,jj,8)  ) 
    255             zcmo(ji,jj,34) = diag_sur_me(ji,jj) * 86400.0 * zinda    ! Surface melt 
    256             zcmo(ji,jj,35) = diag_bot_me(ji,jj) * 86400.0 * zinda    ! Bottom melt 
     264            zcmo(ji,jj,34) = diag_sur_me(ji,jj) * rday     ! Surface melt 
     265            zcmo(ji,jj,35) = diag_bot_me(ji,jj) * rday     ! Bottom melt 
    257266            zcmo(ji,jj,36) = divu_i(ji,jj) 
    258267            zcmo(ji,jj,37) = shear_i(ji,jj) 
    259          END DO 
     268            zcmo(ji,jj,38) = diag_res_pr(ji,jj) * rday     ! Bottom melt 
     269            zcmo(ji,jj,39) = vt_i(ji,jj)  ! ice volume 
     270            zcmo(ji,jj,40) = vt_s(ji,jj)  ! snow volume 
     271 
     272            zcmo(ji,jj,41) = sfx_mec(ji,jj) 
     273            zcmo(ji,jj,42) = sfx_res(ji,jj) 
     274 
     275            zcmo(ji,jj,43) = diag_trp_vi(ji,jj) * rday     ! transport of ice volume 
     276 
     277        END DO 
    260278      END DO 
    261279 
     
    264282      ! 
    265283      niter = niter + 1 
    266       DO jf = 1 , noumef 
    267          ! 
    268          zfield(:,:) = zcmo(:,:,jf) * cmulti(jf) + cadd(jf) 
    269          ! 
    270          IF( jf == 7  .OR. jf == 8  .OR. jf == 15 .OR. jf == 16 ) THEN   ;   CALL lbc_lnk( zfield, 'T', -1. ) 
    271          ELSE                                                            ;   CALL lbc_lnk( zfield, 'T',  1. ) 
    272          ENDIF 
    273          ! 
    274          IF( ln_nicep ) THEN  
    275             WRITE(numout,*) 
    276             WRITE(numout,*) 'nc(jf), nice, nam(jf), niter, ndim' 
    277             WRITE(numout,*) nc(jf), nice, nam(jf), niter, ndim 
    278          ENDIF 
    279          IF( nc(jf) == 1 ) CALL histwrite( nice, nam(jf), niter, zfield, ndim, ndex51 ) 
    280          ! 
    281       END DO 
    282  
    283       IF( ( nn_fsbc * niter ) >= nitend .OR. kindic < 0 ) THEN 
    284          IF( lwp) WRITE(numout,*) ' Closing the icemod file ' 
    285          CALL histclo( nice ) 
    286       ENDIF 
     284!clem 
     285!      DO jf = 1 , noumef 
     286!         ! 
     287!         zfield(:,:) = zcmo(:,:,jf) * cmulti(jf) + cadd(jf) 
     288!         ! 
     289!         IF( jf == 7  .OR. jf == 8  .OR. jf == 15 .OR. jf == 16 ) THEN   ;   CALL lbc_lnk( zfield, 'T', -1. ) 
     290!         ELSE                                                            ;   CALL lbc_lnk( zfield, 'T',  1. ) 
     291!         ENDIF 
     292!         ! 
     293!         IF( ln_nicep ) THEN  
     294!            WRITE(numout,*) 
     295!            WRITE(numout,*) 'nc(jf), nice, nam(jf), niter, ndim' 
     296!            WRITE(numout,*) nc(jf), nice, nam(jf), niter, ndim 
     297!         ENDIF 
     298!         IF( nc(jf) == 1 ) CALL histwrite( nice, nam(jf), niter, zfield, ndim, ndex51 ) 
     299!         ! 
     300!      END DO 
     301! 
     302!      IF( ( nn_fsbc * niter ) >= nitend .OR. kindic < 0 ) THEN 
     303!         IF( lwp) WRITE(numout,*) ' Closing the icemod file ' 
     304!         CALL histclo( nice ) 
     305!      ENDIF 
     306!clem 
     307      ! 
     308       CALL iom_put ('iceconc', zcmo(:,:,1) )          ! field1: ice concentration 
     309       CALL iom_put ('icethic_cea', zcmo(:,:,2) )      ! field2: ice thickness (i.e. icethi(:,:)) 
     310       CALL iom_put ('snowthic_cea', zcmo(:,:,3))      ! field3: snow thickness 
     311       CALL iom_put ('icebopr', zcmo(:,:,4) )   ! field4: daily bottom thermo ice production 
     312       CALL iom_put ('icedypr', zcmo(:,:,5) )   ! field5: daily dynamic ice production 
     313       CALL iom_put ('ioceflxb', zcmo(:,:,6) )         ! field6: Oceanic flux at the ice base 
     314       CALL iom_put ('uice_ipa', zcmo(:,:,7) )         ! field7: ice velocity u component 
     315       CALL iom_put ('vice_ipa', zcmo(:,:,8) )         ! field8: ice velocity v component 
     316       CALL iom_put ('isst', zcmo(:,:,9) )             ! field 9: sea surface temperature 
     317       CALL iom_put ('isss', zcmo(:,:,10) )            ! field 10: sea surface salinity 
     318       CALL iom_put ('qt_oce', zcmo(:,:,11) )           ! field 11: total flux at ocean surface 
     319       CALL iom_put ('qsr_oce', zcmo(:,:,12) )          ! field 12: solar flux at ocean surface 
     320       CALL iom_put ('qns_oce', zcmo(:,:,13) )          ! field 13: non-solar flux at ocean surface 
     321       !CALL iom_put ('hfbri', fhbri )                  ! field 14: heat flux due to brine release 
     322       CALL iom_put( 'utau_ice', zcmo(:,:,15)  )     ! Wind stress over ice along i-axis at I-point 
     323       CALL iom_put( 'vtau_ice', zcmo(:,:,16) )     ! Wind stress over ice along j-axis at I-point 
     324       CALL iom_put ('qsr_io', zcmo(:,:,17) )          ! field 17: solar flux at ice/ocean surface 
     325       CALL iom_put ('qns_io', zcmo(:,:,18) )          ! field 18: non-solar flux at ice/ocean surface 
     326       !CALL iom_put ('snowpre', zcmo(:,:,19) * rday ! field 19 :snow precip           
     327       CALL iom_put ('micesalt', zcmo(:,:,20) )        ! field 20 :mean ice salinity 
     328       CALL iom_put ('miceage', zcmo(:,:,21) / 365)    ! field 21: mean ice age 
     329       CALL iom_put ('icelapr',zcmo(:,:,22) )   ! field 22: daily lateral thermo ice prod. 
     330       CALL iom_put ('icesipr',zcmo(:,:,23) )   ! field 23: daily snowice ice prod. 
     331       CALL iom_put ('micet', zcmo(:,:,24) )           ! field 24: mean ice temperature 
     332       CALL iom_put ('icehc', zcmo(:,:,25) )           ! field 25: ice total heat content 
     333       CALL iom_put ('isnowhc', zcmo(:,:,26) )         ! field 26: snow total heat content 
     334       CALL iom_put ('icest', zcmo(:,:,27) )           ! field 27: ice surface temperature 
     335       CALL iom_put ('sfxbri', zcmo(:,:,28) * rday )           ! field 28: brine salt flux 
     336       CALL iom_put ('sfxthd', zcmo(:,:,29) * rday )           ! field 29: equivalent FW salt flux 
     337       CALL iom_put ('ibrinv', zcmo(:,:,30) *100 )     ! field 30: brine volume 
     338       CALL iom_put ('icecolf', zcmo(:,:,31) )         ! field 31: frazil ice collection thickness 
     339       CALL iom_put ('icestr', zcmo(:,:,32) * 0.001 )  ! field 32: ice strength 
     340       CALL iom_put ('icevel', zcmo(:,:,33) )          ! field 33: ice velocity 
     341       CALL iom_put ('isume', zcmo(:,:,34) )    ! field 34: surface melt 
     342       CALL iom_put ('ibome', zcmo(:,:,35) )     ! field 35: bottom melt 
     343       CALL iom_put ('idive', zcmo(:,:,36) * 1.0e8)    ! field 36: divergence 
     344       CALL iom_put ('ishear', zcmo(:,:,37) * 1.0e8 )  ! field 37: shear 
     345       CALL iom_put ('icerepr', zcmo(:,:,38) ) ! field 38: daily prod./melting due to limupdate 
     346       CALL iom_put ('icevolu', zcmo(:,:,39) ) ! field 39: ice volume 
     347       CALL iom_put ('snowvol', zcmo(:,:,40) ) ! field 40: snow volume 
     348       CALL iom_put ('sfxmec', zcmo(:,:,41) * rday )           ! field 41: salt flux from ridging rafting 
     349       CALL iom_put ('sfxres', zcmo(:,:,42) * rday )           ! field 42: salt flux from limupdate (resultant) 
     350       CALL iom_put ('icetrp', zcmo(:,:,43) )    ! field 43: ice volume transport 
    287351 
    288352      !----------------------------- 
     
    303367            DO jj = 1, jpj 
    304368               DO ji = 1, jpi 
    305                   zinda = MAX( zzero , SIGN( zone , a_i(ji,jj,jl) - 1.0e-6 ) ) 
    306                   zoi(ji,jj,jl) = oa_i(ji,jj,jl)  / MAX( a_i(ji,jj,jl) , 1.0e-6 ) * zinda 
     369                  zinda = MAX( zzero , SIGN( zone , a_i(ji,jj,jl) - epsi06 ) ) 
     370                  zoi(ji,jj,jl) = oa_i(ji,jj,jl)  / MAX( a_i(ji,jj,jl) , epsi06 ) * zinda 
    307371               END DO 
    308372            END DO 
     
    315379               DO jj = 1, jpj 
    316380                  DO ji = 1, jpi 
    317                      zinda = MAX( zzero , SIGN( zone , a_i(ji,jj,jl) - 1.0e-6 ) ) 
     381                     zinda = MAX( zzero , SIGN( zone , a_i(ji,jj,jl) - epsi06 ) ) 
    318382                     zei(ji,jj,jl) = zei(ji,jj,jl) + 100.0* & 
    319                         ( - tmut * s_i(ji,jj,jk,jl) / MIN( ( t_i(ji,jj,jk,jl) - rtt ), -1.0e-6 ) ) * & 
     383                        ( - tmut * s_i(ji,jj,jk,jl) / MIN( ( t_i(ji,jj,jk,jl) - rtt ), - epsi06 ) ) * & 
    320384                        zinda / nlay_i 
    321385                  END DO 
     
    349413      CALL wrk_dealloc( jpi, jpj, jpnoumax, zcmo, zcmoa ) 
    350414      CALL wrk_dealloc( jpi, jpj, jpl, zmaskitd, zoi, zei ) 
     415 
     416      IF( nn_timing == 1 )  CALL timing_stop('limwri') 
    351417       
    352418   END SUBROUTINE lim_wri 
     
    383449         field_25, field_26, field_27, field_28, field_29, field_30,   & 
    384450         field_31, field_32, field_33, field_34, field_35, field_36,   & 
    385          field_37 
     451         field_37, field_38, field_39, field_40, field_41, field_42, field_43 
    386452 
    387453      TYPE(FIELD) , DIMENSION(jpnoumax) :: zfield 
     
    394460         field_25, field_26, field_27, field_28, field_29, field_30,   & 
    395461         field_31, field_32, field_33, field_34, field_35, field_36,   & 
    396          field_37, add_diag_swi 
     462         field_37, field_38, field_39, field_40, field_41, field_42, field_43, add_diag_swi 
    397463      !!------------------------------------------------------------------- 
    398464      REWIND( numnam_ice_ref )              ! Namelist namiceout in reference namelist : Ice outputs 
     
    442508      zfield(36) = field_36 
    443509      zfield(37) = field_37 
     510      zfield(38) = field_38 
     511      zfield(39) = field_39 
     512      zfield(40) = field_40 
     513      zfield(41) = field_41 
     514      zfield(42) = field_42 
     515      zfield(43) = field_43 
    444516 
    445517      DO nf = 1, noumef 
     
    467539      ! 
    468540   END SUBROUTINE lim_wri_init 
     541  
     542   SUBROUTINE lim_wri_state( kt, kid, kh_i ) 
     543      !!--------------------------------------------------------------------- 
     544      !!                 ***  ROUTINE lim_wri_state  *** 
     545      !!         
     546      !! ** Purpose :   create a NetCDF file named cdfile_name which contains  
     547      !!      the instantaneous ice state and forcing fields for ice model 
     548      !!        Used to find errors in the initial state or save the last 
     549      !!      ocean state in case of abnormal end of a simulation 
     550      !! 
     551      !! History : 
     552      !!   4.1  !  2013-06  (C. Rousset) 
     553      !!---------------------------------------------------------------------- 
     554      INTEGER, INTENT( in ) ::   kt               ! ocean time-step index) 
     555      INTEGER, INTENT( in ) ::   kid , kh_i        
     556      !!---------------------------------------------------------------------- 
     557      !CALL histvert( kid, "icethi", "L levels","m", jpl , hi_mean , nz ) 
     558 
     559      CALL histdef( kid, "iicethic", "Ice thickness"           , "m"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     560      CALL histdef( kid, "iiceconc", "Ice concentration"       , "%"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     561      CALL histdef( kid, "iicetemp", "Ice temperature"         , "C"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     562      CALL histdef( kid, "iicevelu", "i-Ice speed (I-point)"   , "m/s"    , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     563      CALL histdef( kid, "iicevelv", "j-Ice speed (I-point)"   , "m/s"    , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     564      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 ) 
     565      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 )  
     566      CALL histdef( kid, "iicesflx", "Solar flux over ocean"     , "w/m2"   , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     567      CALL histdef( kid, "iicenflx", "Non-solar flux over ocean" , "w/m2"   , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt ) 
     568      CALL histdef( kid, "isnowpre", "Snow precipitation"      , "kg/m2/s", jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     569      CALL histdef( kid, "iicesali", "Ice salinity"            , "PSU"    , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     570      CALL histdef( kid, "iicevolu", "Ice volume"              , "m"      , jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     571      CALL histdef( kid, "iicedive", "Ice divergence"          , "10-8s-1", jpi, jpj, kh_i, 1, 1, 1, -99, 32, "inst(x)", rdt, rdt )  
     572 
     573      !CALL histdef( kid, "iice_itd", "Ice concentration by cat", "%"      , jpi, jpj, kh_i, jpl, 1, jpl, -99, 32, "inst(x)", rdt, rdt )  
     574      !CALL histdef( kid, "iice_hid", "Ice thickness by cat"    , "m"      , jpi, jpj, kh_i, jpl, 1, jpl, -99, 32, "inst(x)", rdt, rdt )  
     575      !CALL histdef( kid, "iice_hsd", "Snow thickness by cat"   , "m"      , jpi, jpj, kh_i, jpl, 1, jpl, -99, 32, "inst(x)", rdt, rdt )  
     576      !CALL histdef( kid, "iice_std", "Ice salinity by cat"     , "PSU"    , jpi, jpj, kh_i, jpl, 1, jpl, -99, 32, "inst(x)", rdt, rdt )  
     577 
     578      CALL histend( kid, snc4set )   ! end of the file definition 
     579 
     580      CALL histwrite( kid, "iicethic", kt, icethi        , jpi*jpj, (/1/) )     
     581      CALL histwrite( kid, "iiceconc", kt, at_i          , jpi*jpj, (/1/) ) 
     582      CALL histwrite( kid, "iicetemp", kt, tm_i - rtt    , jpi*jpj, (/1/) ) 
     583      CALL histwrite( kid, "iicevelu", kt, u_ice          , jpi*jpj, (/1/) ) 
     584      CALL histwrite( kid, "iicevelv", kt, v_ice          , jpi*jpj, (/1/) ) 
     585      CALL histwrite( kid, "iicestru", kt, utau_ice       , jpi*jpj, (/1/) ) 
     586      CALL histwrite( kid, "iicestrv", kt, vtau_ice       , jpi*jpj, (/1/) ) 
     587      CALL histwrite( kid, "iicesflx", kt, qsr , jpi*jpj, (/1/) ) 
     588      CALL histwrite( kid, "iicenflx", kt, qns , jpi*jpj, (/1/) ) 
     589      CALL histwrite( kid, "isnowpre", kt, sprecip        , jpi*jpj, (/1/) ) 
     590      CALL histwrite( kid, "iicesali", kt, smt_i          , jpi*jpj, (/1/) ) 
     591      CALL histwrite( kid, "iicevolu", kt, vt_i           , jpi*jpj, (/1/) ) 
     592      CALL histwrite( kid, "iicedive", kt, divu_i*1.0e8   , jpi*jpj, (/1/) ) 
     593 
     594      !CALL histwrite( kid, "iice_itd", kt, a_i  , jpi*jpj*jpl, (/1/)  )   ! area 
     595      !CALL histwrite( kid, "iice_hid", kt, ht_i , jpi*jpj*jpl, (/1/)  )   ! thickness 
     596      !CALL histwrite( kid, "iice_hsd", kt, ht_s , jpi*jpj*jpl, (/1/)  )   ! snow depth 
     597      !CALL histwrite( kid, "iice_std", kt, sm_i , jpi*jpj*jpl, (/1/)  )   ! salinity 
     598 
     599    END SUBROUTINE lim_wri_state 
    469600 
    470601#else 
Note: See TracChangeset for help on using the changeset viewer.