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 trunk/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: trunk/NEMOGCM/NEMO/LIM_SRC_3/limwri.F90 @ 2528

Last change on this file since 2528 was 2528, checked in by rblod, 13 years ago

Update NEMOGCM from branch nemo_v3_3_beta

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