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 @ 2524

Last change on this file since 2524 was 2477, checked in by cetlod, 13 years ago

v3.2:remove hardcoded value of num_sal in limrst.F90, see ticket #633

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