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

Last change on this file since 3294 was 3294, checked in by rblod, 12 years ago

Merge of 3.4beta into the trunk

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