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.
limwri.F90 in branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/limwri.F90 @ 2364

Last change on this file since 2364 was 2364, checked in by acc, 13 years ago

Added basic NetCDF4 chunking and compression support (key_netcdf4). See ticket #754

  • Property svn:keywords set to Id
File size: 20.0 KB
Line 
1MODULE limwri
2   !!----------------------------------------------------------------------
3   !!   'key_lim3'                                      LIM3 sea-ice model
4   !!----------------------------------------------------------------------
5   !!======================================================================
6   !!                     ***  MODULE  limwri  ***
7   !!         Ice diagnostics :  write ice output files
8   !!======================================================================
9#if defined key_lim3
10   !!----------------------------------------------------------------------
11   !! NEMO/LIM3 3.3 , UCL - NEMO Consortium (2010)
12   !! $Id$
13   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
14   !!----------------------------------------------------------------------
15   !!   lim_wri      : write of the diagnostics variables in ouput file
16   !!   lim_wri_init : initialization and namelist read
17   !!----------------------------------------------------------------------
18   !! * Modules used
19   USE ioipsl
20   USE dianam          ! build name of file (routine)
21   USE phycst
22   USE dom_oce
23   USE in_out_manager
24   USE sbc_oce         ! Surface boundary condition: ocean fields
25   USE sbc_ice         ! Surface boundary condition: ice fields
26   USE dom_ice
27   USE ice
28   USE iceini
29   USE lbclnk
30   USE par_ice
31   USE limvar
32
33   IMPLICIT NONE
34   PRIVATE
35
36   !! * Accessibility
37   PUBLIC lim_wri        ! routine called by lim_step.F90
38
39   !! * Module variables
40   INTEGER, PARAMETER ::   &  !:
41      jpnoumax = 40             !: maximum number of variable for ice output
42   INTEGER  ::                                &
43      noumef          ,                       &  ! number of fields
44      noumefa         ,                       &  ! number of additional fields
45      add_diag_swi    ,                       &  ! additional diagnostics
46      nz                                         ! dimension for the itd field
47
48   REAL(wp)           , DIMENSION(jpnoumax) ::  &
49      cmulti          ,                       &  ! multiplicative constant
50      cadd            ,                       &  ! additive constant
51      cmultia         ,                       &  ! multiplicative constant
52      cadda                                      ! additive constant
53   CHARACTER(len = 35), DIMENSION(jpnoumax) ::  &
54      titn, titna                                ! title of the field
55   CHARACTER(len = 8 ), DIMENSION(jpnoumax) ::  &
56      nam, nama                                  ! name of the field
57   CHARACTER(len = 8 ), DIMENSION(jpnoumax) ::  &
58      uni, unia                                  ! unit of the field
59   INTEGER            , DIMENSION(jpnoumax) ::  &
60      nc, nca                                    ! switch for saving field ( = 1 ) or not ( = 0 )
61
62   REAL(wp)  ::            &  ! constant values
63      epsi16 = 1e-16   ,  &
64      zzero  = 0.e0     ,  &
65      zone   = 1.e0
66
67CONTAINS
68#if defined key_dimgout
69
70# include "limwri_dimg.h90"
71
72#else
73
74   SUBROUTINE lim_wri( kindic )
75      !!-------------------------------------------------------------------
76      !!  This routine computes the average of some variables and write it
77      !!  on the ouput files.
78      !!  ATTENTION cette routine n'est valable que si le pas de temps est
79      !!  egale a une fraction entiere de 1 jours.
80      !!  Diff 1-D 3-D : suppress common also included in etat
81      !!                 suppress cmoymo 11-18
82      !!  modif : 03/06/98
83      !!-------------------------------------------------------------------
84      INTEGER, INTENT(in) :: &
85         kindic                 ! if kindic < 0 there has been an error somewhere
86
87      !! * Local variables
88      REAL(wp),DIMENSION(1) ::   zdept
89
90      REAL(wp) :: &
91         zsto, zjulian,zout, &
92         zindh,zinda,zindb
93      REAL(wp), DIMENSION(jpi,jpj,jpnoumax) :: &
94         zcmo,               &
95         zcmoa                   ! additional fields
96
97      REAL(wp), DIMENSION(jpi,jpj) ::  &
98         zfield
99
100      REAL(wp), DIMENSION(jpi,jpj,jpl) ::  &
101         zmaskitd, zoi, zei
102
103      INTEGER ::  ji, jj, jk, jl, jf, ipl ! dummy loop indices
104
105      CHARACTER(len = 40)  :: &
106         clhstnam, clop, &
107         clhstnama
108
109      INTEGER , SAVE ::      &
110         nice, nhorid, ndim, niter, ndepid
111      INTEGER , SAVE ::      &
112         nicea, nhorida, ndimitd
113      INTEGER , DIMENSION( jpij ) , SAVE ::  &
114         ndex51
115      INTEGER , DIMENSION( jpij*jpl ) , SAVE ::  &
116         ndexitd
117      !!-------------------------------------------------------------------
118
119      ipl = jpl
120
121      IF ( numit == nstart ) THEN
122
123         CALL lim_wri_init 
124
125         IF(lwp) WRITE(numout,*) ' lim_wri, first time step '
126         IF(lwp) WRITE(numout,*) ' add_diag_swi ', add_diag_swi
127
128         !--------------------
129         !  1) Initialization
130         !--------------------
131
132         !-------------
133         ! Normal file
134         !-------------
135
136         zsto     = rdt_ice
137         IF( ln_mskland )   THEN   ;   clop = "ave(only(x))"   ! put 1.e+20 on land (very expensive!!)
138         ELSE                      ;   clop = "ave(x)"         ! no use of the mask value (require less cpu time)
139         ENDIF
140         zout     = nwrite * rdt_ice / nn_fsbc
141         niter    = ( nit000 - 1 ) / nn_fsbc
142         zdept(1) = 0.
143
144         CALL ymds2ju ( nyear, nmonth, nday, rdt, zjulian )
145         zjulian = zjulian - adatrj   !   set calendar origin to the beginning of the experiment
146         CALL dia_nam ( clhstnam, nwrite, 'icemod' )
147         CALL histbeg ( clhstnam, jpi, glamt, jpj, gphit, 1, jpi, 1, jpj, niter, zjulian, rdt_ice,   &
148            &           nhorid, nice, domain_id=nidom, snc4chunks=snc4set )
149         CALL histvert( nice, "deptht", "Vertical T levels", "m", 1, zdept, ndepid, "down")
150         CALL wheneq  ( jpij , tmask(:,:,1), 1, 1., ndex51, ndim)
151
152         DO jf = 1 , noumef
153            IF(lwp) WRITE(numout,*) 'jf', jf
154            IF ( nc(jf) == 1 ) THEN
155               CALL histdef( nice, nam(jf), titn(jf), uni(jf), jpi, jpj &
156                  , nhorid, 1, 1, 1, -99, 32, clop, zsto, zout )
157               IF(lwp) WRITE(numout,*) 'nice, nam(jf), titn(jf), uni(jf), nhorid, clop, zsto, zout'
158               IF(lwp) WRITE(numout,*)  nice, nam(jf), titn(jf), uni(jf), nhorid, clop, zsto, zout 
159            ENDIF
160         END DO
161
162         CALL histend(nice, snc4set)
163
164         !-----------------
165         ! ITD file output
166         !-----------------
167         zsto     = rdt_ice
168         clop     = "ave(x)"
169         zout     = nwrite * rdt_ice / nn_fsbc
170         zdept(1) = 0.
171
172         CALL dia_nam ( clhstnama, nwrite, 'icemoa' )
173         CALL histbeg ( clhstnama, jpi, glamt, jpj, gphit,         &
174            1, jpi, 1, jpj,            & ! zoom
175            niter, zjulian, rdt_ice,   & ! time
176            nhorida,                   & ! ? linked with horizontal ...
177            nicea , domain_id=nidom, snc4chunks=snc4set)                  ! file
178         CALL histvert( nicea, "icethi", "L levels",               &
179            "m", ipl , hi_mean , nz )
180         DO jl = 1, jpl
181            zmaskitd(:,:,jl) = tmask(:,:,1)
182         END DO
183         CALL wheneq  ( jpij , tmask(:,:,1), 1, 1., ndex51, ndim)
184         CALL wheneq( jpi*jpj*jpl, zmaskitd, 1, 1., ndexitd, ndimitd  ) 
185         CALL histdef( nicea, "iice_itd", "Ice area in categories"         , "-"    ,   & 
186            jpi, jpj, nhorida, jpl, 1, jpl, nz, 15, clop, zsto, zout )
187         CALL histdef( nicea, "iice_hid", "Ice thickness in categories"    , "m"    ,   & 
188            jpi, jpj, nhorida, jpl, 1, jpl, nz, 15, clop, zsto, zout )
189         CALL histdef( nicea, "iice_hsd", "Snow depth in in categories"    , "m"    ,   & 
190            jpi, jpj, nhorida, jpl, 1, jpl, nz, 15, clop, zsto, zout )
191         CALL histdef( nicea, "iice_std", "Ice salinity distribution"      , "ppt"  ,   & 
192            jpi, jpj, nhorida, jpl, 1, jpl, nz, 15, clop, zsto, zout )
193         CALL histdef( nicea, "iice_otd", "Ice age distribution"               , "days",   & 
194            jpi, jpj, nhorida, jpl, 1, jpl, nz, 15, clop, zsto, zout )
195         CALL histdef( nicea, "iice_etd", "Brine volume distr. "               , "%"    ,   & 
196            jpi, jpj, nhorida, jpl, 1, jpl, nz, 15, clop, zsto, zout )
197         CALL histend(nicea, snc4set)
198      ENDIF
199
200      !     !-----------------------------------------------------------------------!
201      !     !--2. Computation of instantaneous values                               !
202      !     !-----------------------------------------------------------------------!
203
204      !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
205      IF( ln_nicep ) THEN
206         WRITE(numout,*)
207         WRITE(numout,*) 'lim_wri : write ice outputs in NetCDF files at time : ', nyear, nmonth, nday, numit
208         WRITE(numout,*) '~~~~~~~ '
209         WRITE(numout,*) ' kindic = ', kindic
210      ENDIF
211      !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
212
213      !-- calculs des valeurs instantanees
214      zcmo( 1:jpi, 1:jpj, 1:jpnoumax ) = 0.0 
215      zcmoa( 1:jpi, 1:jpj, 1:jpnoumax ) = 0.0 
216
217      DO jl = 1, jpl
218         DO jj = 1, jpj
219            DO ji = 1, jpi
220               zindh  = MAX( zzero , SIGN( zone , vt_i(ji,jj) * at_i(ji,jj) - 0.10 ) )
221               zinda  = MAX( zzero , SIGN( zone , at_i(ji,jj) - 0.10 ) )
222               zcmo(ji,jj,17) = zcmo(ji,jj,17) + a_i(ji,jj,jl)*qsr_ice (ji,jj,jl) 
223               zcmo(ji,jj,18) = zcmo(ji,jj,18) + a_i(ji,jj,jl)*qns_ice(ji,jj,jl) 
224               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
225            END DO
226         END DO
227      END DO
228
229      CALL lim_var_bv
230
231      DO jj = 2 , jpjm1
232         DO ji = 2 , jpim1
233            zindh  = MAX( zzero , SIGN( zone , vt_i(ji,jj) * at_i(ji,jj) - 0.10 ) )
234            zinda  = MAX( zzero , SIGN( zone , at_i(ji,jj) - 0.10 ) )
235            zindb  = zindh * zinda
236
237            zcmo(ji,jj,1)  = at_i(ji,jj)
238            zcmo(ji,jj,2)  = vt_i(ji,jj)/MAX(at_i(ji,jj),epsi16)*zinda
239            zcmo(ji,jj,3)  = vt_s(ji,jj)/MAX(at_i(ji,jj),epsi16)*zinda
240            zcmo(ji,jj,4)  = diag_bot_gr(ji,jj) * &
241               86400.0 * zinda !Bottom thermodynamic ice production
242            zcmo(ji,jj,5)  = diag_dyn_gr(ji,jj) * &
243               86400.0 * zinda !Dynamic ice production (rid/raft)
244            zcmo(ji,jj,22) = diag_lat_gr(ji,jj) * &
245               86400.0 * zinda !Lateral thermodynamic ice production
246            zcmo(ji,jj,23) = diag_sni_gr(ji,jj) * &
247               86400.0 * zinda !Snow ice production ice production
248            zcmo(ji,jj,24) = tm_i(ji,jj) - rtt
249
250            zcmo(ji,jj,6)  = fbif  (ji,jj)
251            zcmo(ji,jj,7)  = zindb * (  u_ice(ji,jj  ) * tmu(ji,jj)        &
252               &                                + u_ice(ji-1,jj) * tmu(ji-1,jj) )    &
253               &                     / 2.0 
254            zcmo(ji,jj,8)  = zindb * (  v_ice(ji,jj  ) * tmv(ji,jj)        &
255               &                                + v_ice(ji,jj-1) * tmv(ji,jj-1) )    &
256               &                     / 2.0
257            zcmo(ji,jj,9)  = sst_m(ji,jj)
258            zcmo(ji,jj,10) = sss_m(ji,jj)
259
260            zcmo(ji,jj,11) = qns(ji,jj) + qsr(ji,jj)
261            zcmo(ji,jj,12) = qsr(ji,jj)
262            zcmo(ji,jj,13) = qns(ji,jj)
263            zcmo(ji,jj,14) = fhbri(ji,jj)
264            zcmo(ji,jj,15) = utau_ice(ji,jj)
265            zcmo(ji,jj,16) = vtau_ice(ji,jj)
266            zcmo(ji,jj,17) = zcmo(ji,jj,17) + (1.0-at_i(ji,jj))*qsr(ji,jj)
267            zcmo(ji,jj,18) = zcmo(ji,jj,18) + (1.0-at_i(ji,jj))*qns(ji,jj)
268            zcmo(ji,jj,19) = sprecip(ji,jj)
269            zcmo(ji,jj,20) = smt_i(ji,jj)
270            zcmo(ji,jj,21) = ot_i(ji,jj)
271            zcmo(ji,jj,25) = et_i(ji,jj)
272            zcmo(ji,jj,26) = et_s(ji,jj)
273            zcmo(ji,jj,28) = fsbri(ji,jj)
274            zcmo(ji,jj,29) = fseqv(ji,jj)
275
276            zcmo(ji,jj,30) = bv_i(ji,jj)
277            zcmo(ji,jj,31) = hicol(ji,jj)
278            zcmo(ji,jj,32) = strength(ji,jj)
279            zcmo(ji,jj,33) = SQRT( zcmo(ji,jj,7)*zcmo(ji,jj,7) + &
280               zcmo(ji,jj,8)*zcmo(ji,jj,8) )
281            zcmo(ji,jj,34) = diag_sur_me(ji,jj) * &
282               86400.0 * zinda ! Surface melt
283            zcmo(ji,jj,35) = diag_bot_me(ji,jj) * &
284               86400.0 * zinda ! Bottom melt
285            zcmo(ji,jj,36) = divu_i(ji,jj)
286            zcmo(ji,jj,37) = shear_i(ji,jj)
287         END DO
288      END DO
289
290      !
291      ! ecriture d'un fichier netcdf
292      !
293      niter = niter + 1
294      DO jf = 1 , noumef
295         DO jj = 1 , jpj
296            DO ji = 1 , jpi
297               zfield(ji,jj) = zcmo(ji,jj,jf) * cmulti(jf) + cadd(jf)
298            END DO
299         END DO
300
301         IF ( jf == 7  .OR. jf == 8  .OR. jf == 15 .OR. jf == 16 ) THEN
302            CALL lbc_lnk( zfield, 'T', -1. )
303         ELSE
304            CALL lbc_lnk( zfield, 'T',  1. )
305         ENDIF
306
307         IF( ln_nicep ) THEN
308            WRITE(numout,*)
309            WRITE(numout,*) 'nc(jf), nice, nam(jf), niter, ndim'
310            WRITE(numout,*) nc(jf), nice, nam(jf), niter, ndim
311         ENDIF
312         IF ( nc(jf) == 1 ) CALL histwrite( nice, nam(jf), niter, zfield, ndim, ndex51 )
313
314      END DO
315
316      IF ( ( nn_fsbc * niter ) >= nitend .OR. kindic < 0 ) THEN
317         IF( lwp) WRITE(numout,*) ' Closing the icemod file '
318         CALL histclo( nice )
319      ENDIF
320
321      !-----------------------------
322      ! Thickness distribution file
323      !-----------------------------
324      IF ( add_diag_swi .EQ. 1 ) THEN
325
326         DO jl = 1, jpl 
327            CALL lbc_lnk( a_i(:,:,jl)  , 'T' ,  1. )
328            CALL lbc_lnk( sm_i(:,:,jl) , 'T' ,  1. )
329            CALL lbc_lnk( oa_i(:,:,jl) , 'T' ,  1. )
330            CALL lbc_lnk( ht_i(:,:,jl) , 'T' ,  1. )
331            CALL lbc_lnk( ht_s(:,:,jl) , 'T' ,  1. )
332         END DO
333
334         ! Compute ice age
335         DO jl = 1, jpl 
336            DO jj = 1, jpj
337               DO ji = 1, jpi
338                  zinda = MAX( zzero , SIGN( zone , a_i(ji,jj,jl) - 1.0e-6 ) )
339                  zoi(ji,jj,jl) = oa_i(ji,jj,jl)  / MAX( a_i(ji,jj,jl) , 1.0e-6 ) * &
340                     zinda
341               END DO
342            END DO
343         END DO
344
345         ! Compute brine volume
346         zei(:,:,:) = 0.0
347         DO jl = 1, jpl 
348            DO jk = 1, nlay_i
349               DO jj = 1, jpj
350                  DO ji = 1, jpi
351                     zinda = MAX( zzero , SIGN( zone , a_i(ji,jj,jl) - 1.0e-6 ) )
352                     zei(ji,jj,jl) = zei(ji,jj,jl) + 100.0* &
353                        ( - tmut * s_i(ji,jj,jk,jl) / MIN( ( t_i(ji,jj,jk,jl) - rtt ), -1.0e-6 ) ) * &
354                        zinda / nlay_i
355                  END DO
356               END DO
357            END DO
358         END DO
359
360         DO jl = 1, jpl 
361            CALL lbc_lnk( zei(:,:,jl) , 'T' ,  1. )
362         END DO
363
364         CALL histwrite( nicea, "iice_itd", niter, a_i  , ndimitd , ndexitd  )   ! area
365         CALL histwrite( nicea, "iice_hid", niter, ht_i , ndimitd , ndexitd  )   ! thickness
366         CALL histwrite( nicea, "iice_hsd", niter, ht_s , ndimitd , ndexitd  )   ! snow depth
367         CALL histwrite( nicea, "iice_std", niter, sm_i , ndimitd , ndexitd  )   ! salinity
368         CALL histwrite( nicea, "iice_otd", niter, zoi  , ndimitd , ndexitd  )   ! age
369         CALL histwrite( nicea, "iice_etd", niter, zei  , ndimitd , ndexitd  )   ! brine volume
370
371         !     !  Create an output files (output.lim.abort.nc) if S < 0 or u > 20 m/s
372         !     IF( kindic < 0 )   CALL lim_wri_state( 'output.abort' )
373         !     not yet implemented
374
375         IF ( ( nn_fsbc * niter ) >= nitend .OR. kindic < 0 ) THEN
376            IF(lwp) WRITE(numout,*) ' Closing the icemod file '
377            CALL histclo( nicea ) 
378         ENDIF
379
380      ENDIF
381
382   END SUBROUTINE lim_wri
383#endif
384
385   SUBROUTINE lim_wri_init
386      !!-------------------------------------------------------------------
387      !!                    ***   ROUTINE lim_wri_init  ***
388      !!               
389      !! ** Purpose :   ???
390      !!
391      !! ** Method  : Read the namicewri namelist and check the parameter
392      !!       values called at the first timestep (nit000)
393      !!
394      !! ** input   :   Namelist namicewri
395      !!
396      !! history :
397      !!  8.5  ! 03-08 (C. Ethe) original code
398      !!-------------------------------------------------------------------
399      !! * Local declarations
400      INTEGER ::   nf      ! ???
401
402      TYPE FIELD 
403         CHARACTER(len = 35) :: ztitle 
404         CHARACTER(len = 8 ) :: zname         
405         CHARACTER(len = 8 ) :: zunit
406         INTEGER             :: znc   
407         REAL                :: zcmulti 
408         REAL                :: zcadd       
409      END TYPE FIELD
410
411      TYPE(FIELD) ::  &
412         field_1 , field_2 , field_3 , field_4 , field_5 , field_6 ,   &
413         field_7 , field_8 , field_9 , field_10, field_11, field_12,   &
414         field_13, field_14, field_15, field_16, field_17, field_18,   &
415         field_19, field_20, field_21, field_22, field_23, field_24,   &
416         field_25, field_26, field_27, field_28, field_29, field_30,   &
417         field_31, field_32, field_33, field_34, field_35, field_36,   &
418         field_37
419
420      TYPE(FIELD) , DIMENSION(jpnoumax) :: zfield
421
422      NAMELIST/namiceout/ noumef, &
423         field_1 , field_2 , field_3 , field_4 , field_5 , field_6 ,   &
424         field_7 , field_8 , field_9 , field_10, field_11, field_12,   &
425         field_13, field_14, field_15, field_16, field_17, field_18,   &
426         field_19, field_20, field_21, field_22, field_23, field_24,   &
427         field_25, field_26, field_27, field_28, field_29, field_30,   &
428         field_31, field_32, field_33, field_34, field_35, field_36,   &
429         field_37, add_diag_swi
430      !!-------------------------------------------------------------------
431
432      ! Read Namelist namicewri
433      REWIND ( numnam_ice )
434      READ   ( numnam_ice  , namiceout )
435
436      zfield(1)  = field_1
437      zfield(2)  = field_2
438      zfield(3)  = field_3
439      zfield(4)  = field_4
440      zfield(5)  = field_5
441      zfield(6)  = field_6
442      zfield(7)  = field_7
443      zfield(8)  = field_8
444      zfield(9)  = field_9
445      zfield(10) = field_10
446      zfield(11) = field_11
447      zfield(12) = field_12
448      zfield(13) = field_13
449      zfield(14) = field_14
450      zfield(15) = field_15
451      zfield(16) = field_16
452      zfield(17) = field_17
453      zfield(18) = field_18
454      zfield(19) = field_19
455      zfield(20) = field_20
456      zfield(21) = field_21
457      zfield(22) = field_22
458      zfield(23) = field_23
459      zfield(24) = field_24
460      zfield(25) = field_25
461      zfield(26) = field_26
462      zfield(27) = field_27
463      zfield(28) = field_28
464      zfield(29) = field_29
465      zfield(30) = field_30
466      zfield(31) = field_31
467      zfield(32) = field_32
468      zfield(33) = field_33
469      zfield(34) = field_34
470      zfield(35) = field_35
471      zfield(36) = field_36
472      zfield(37) = field_37
473
474      DO nf = 1, noumef
475         titn  (nf) = zfield(nf)%ztitle
476         nam   (nf) = zfield(nf)%zname
477         uni   (nf) = zfield(nf)%zunit
478         nc    (nf) = zfield(nf)%znc
479         cmulti(nf) = zfield(nf)%zcmulti
480         cadd  (nf) = zfield(nf)%zcadd
481      END DO
482
483      IF(lwp) THEN
484         WRITE(numout,*)
485         WRITE(numout,*) 'lim_wri_init : Ice parameters for outputs'
486         WRITE(numout,*) '~~~~~~~~~~~~'
487         WRITE(numout,*) '    number of fields to be stored         noumef = ', noumef
488         WRITE(numout,*) '           title                            name     unit      Saving (1/0) ',   &
489            &            '    multiplicative constant       additive constant '
490         DO nf = 1 , noumef         
491            WRITE(numout,*) '   ', titn(nf), '   ', nam(nf),'      ', uni(nf),'  ', nc(nf),'        ', cmulti(nf),   &
492               '        ', cadd(nf)
493         END DO
494         WRITE(numout,*) ' add_diag_swi ', add_diag_swi
495      ENDIF
496
497   END SUBROUTINE lim_wri_init
498
499#else
500   !!----------------------------------------------------------------------
501   !!   Default option :         Empty module          NO LIM sea-ice model
502   !!----------------------------------------------------------------------
503CONTAINS
504   SUBROUTINE lim_wri          ! Empty routine
505   END SUBROUTINE lim_wri
506#endif
507
508   !!======================================================================
509END MODULE limwri
Note: See TracBrowser for help on using the repository browser.