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/NEMO/LIM_SRC – NEMO

source: trunk/NEMO/LIM_SRC/limwri.F90 @ 508

Last change on this file since 508 was 508, checked in by opalod, 18 years ago

nemo_v1_update_071:RB: add iom for restart and reorganization of restart

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 12.3 KB
Line 
1MODULE limwri
2   !!======================================================================
3   !!                     ***  MODULE  limwri  ***
4   !!         Ice diagnostics :  write ice output files
5   !!======================================================================
6   !! history :  2.0  ! 03-08  (C. Ethe) original code
7   !!            2.0  ! 04-10  (C. Ethe )  1D configuration
8   !!-------------------------------------------------------------------
9#if defined key_ice_lim
10   !!----------------------------------------------------------------------
11   !!   'key_ice_lim'                                     LIM sea-ice model
12   !!----------------------------------------------------------------------
13   !!----------------------------------------------------------------------
14   !!   lim_wri      : write of the diagnostics variables in ouput file
15   !!   lim_wri_init : initialization and namelist read
16   !!----------------------------------------------------------------------
17   USE ioipsl
18   USE dianam    ! build name of file (routine)
19   USE phycst
20   USE dom_oce
21   USE daymod
22   USE in_out_manager
23   USE ice_oce         ! ice variables
24   USE flx_oce
25   USE dom_ice
26   USE ice
27   USE lbclnk
28
29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC   lim_wri        ! routine called by lim_step.F90
33
34   INTEGER, PARAMETER                       ::   jpnoumax = 40   ! maximum number of variable for ice output
35   INTEGER                                  ::   noumef          ! number of fields
36   REAL(wp)           , DIMENSION(jpnoumax) ::   cmulti ,     &  ! multiplicative constant
37      &                                          cadd            ! additive constant
38   CHARACTER(len = 35), DIMENSION(jpnoumax) ::   titn            ! title of the field
39   CHARACTER(len = 8 ), DIMENSION(jpnoumax) ::   nam             ! name of the field
40   CHARACTER(len = 8 ), DIMENSION(jpnoumax) ::   uni             ! unit of the field
41   INTEGER            , DIMENSION(jpnoumax) ::   nc              ! switch for saving field ( = 1 ) or not ( = 0 )
42
43   INTEGER ::   nice, nhorid, ndim, niter, ndepid       ! ????
44   INTEGER , DIMENSION( jpij ) ::   ndex51              ! ????
45
46   REAL(wp)  ::            &  ! constant values
47      epsi16 = 1.e-16   ,  &
48      zzero  = 0.e0     ,  &
49      zone   = 1.e0
50
51   !!----------------------------------------------------------------------
52   !!  LIM 2.0, UCL-LOCEAN-IPSL (2005)
53   !! $Header$
54   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
55   !!----------------------------------------------------------------------
56
57CONTAINS
58
59#if defined key_dimgout
60   !!----------------------------------------------------------------------
61   !!   'key_dimgout'                                    Direct Access file
62   !!----------------------------------------------------------------------
63# include "limwri_dimg.h90"
64#else
65   !!----------------------------------------------------------------------
66   !!   Default option                                          NetCDF file
67   !!----------------------------------------------------------------------
68
69   SUBROUTINE lim_wri( kt )
70      !!-------------------------------------------------------------------
71      !!                    ***   ROUTINE lim_wri  ***
72      !!               
73      !! ** Purpose :   write the sea-ice output file in NetCDF
74      !!
75      !! ** Method  :   computes the average of some variables and write
76      !!      it in the NetCDF ouput files
77      !!      CAUTION: the sea-ice time-step must be an integer fraction
78      !!      of a day
79      !!-------------------------------------------------------------------
80      INTEGER, INTENT(in) ::   kt     ! number of iteration
81
82      INTEGER  ::   ji, jj, jf                      ! dummy loop indices
83      CHARACTER(len = 40)  ::   clhstnam, clop
84      REAL(wp) ::   zsto, zsec, zjulian, zout,   &  ! temporary scalars
85         &          zindh, zinda, zindb, ztmu
86      REAL(wp), DIMENSION(1)                ::   zdept
87      REAL(wp), DIMENSION(jpi,jpj)          ::   zfield
88      REAL(wp), DIMENSION(jpi,jpj,jpnoumax) ::   zcmo
89      !!-------------------------------------------------------------------
90
91      !                                          !--------------------!
92      IF ( kt == nit000 ) THEN                !   Initialisation   !
93         !                                       !--------------------!
94         CALL lim_wri_init 
95                           
96         zsto     = rdt_ice
97!!Chris         clop     = "ave(only(x))"      !ibug  namelist parameter a ajouter
98         clop     = "ave(x)"
99         zout     = nwrite * rdt_ice / nfice
100         zsec     = 0.
101         niter    = 0
102         zdept(1) = 0.
103         
104         CALL ymds2ju ( nyear, nmonth, nday, zsec, zjulian )
105         CALL dia_nam ( clhstnam, nwrite, 'icemod' )
106         CALL histbeg ( clhstnam, jpi, glamt, jpj, gphit,    &
107            &           1, jpi, 1, jpj, 0, zjulian, rdt_ice, nhorid, nice , domain_id=nidom)
108         CALL histvert( nice, "deptht", "Vertical T levels", "m", 1, zdept, ndepid)
109         CALL wheneq  ( jpij , tmask(:,:,1), 1, 1., ndex51, ndim)
110         
111         DO jf = 1, noumef
112            IF ( nc(jf) == 1 )   CALL histdef( nice, nam(jf), titn(jf), uni(jf), jpi, jpj   &
113                  &                                , nhorid, 1, 1, 1, -99, 32, clop, zsto, zout )
114         END DO
115         CALL histend( nice )
116         
117      ENDIF
118      !                                          !--------------------!
119      !                                          !   Cumulate at kt   !
120      !                                          !--------------------!
121
122!!gm  change the print below to have it only at output time step or when nitend =< 100
123      IF(lwp) THEN
124         WRITE(numout,*)
125         WRITE(numout,*) 'lim_wri : write ice outputs in NetCDF files at time : ', nyear, nmonth, nday, kt + nfice - 1
126         WRITE(numout,*) '~~~~~~~ '
127      ENDIF
128
129      !-- calculs des valeurs instantanees
130     
131      zcmo(:,:, 1:jpnoumax ) = 0.e0 
132      DO jj = 2 , jpjm1
133         DO ji = 2 , jpim1
134            zindh  = MAX( zzero , SIGN( zone , hicif(ji,jj) * (1.0 - frld(ji,jj) ) - 0.10 ) )
135            zinda  = MAX( zzero , SIGN( zone , ( 1.0 - frld(ji,jj) ) - 0.10 ) )
136            zindb  = zindh * zinda
137            ztmu   = MAX( 0.5 * zone , ( tmu(ji,jj) + tmu(ji+1,jj) + tmu(ji,jj+1) + tmu(ji+1,jj+1) ) ) 
138            zcmo(ji,jj,1)  = hsnif (ji,jj)
139            zcmo(ji,jj,2)  = hicif (ji,jj)
140            zcmo(ji,jj,3)  = hicifp(ji,jj)
141            zcmo(ji,jj,4)  = frld  (ji,jj)
142            zcmo(ji,jj,5)  = sist  (ji,jj)
143            zcmo(ji,jj,6)  = fbif  (ji,jj)
144            zcmo(ji,jj,7)  = zindb * (  u_ice(ji,jj  ) * tmu(ji,jj  ) + u_ice(ji+1,jj  ) * tmu(ji+1,jj  )   &
145                                      + u_ice(ji,jj+1) * tmu(ji,jj+1) + u_ice(ji+1,jj+1) * tmu(ji+1,jj+1) ) &
146                                  / ztmu 
147
148            zcmo(ji,jj,8)  = zindb * (  v_ice(ji,jj  ) * tmu(ji,jj  ) + v_ice(ji+1,jj  ) * tmu(ji+1,jj  )   &
149                                      + v_ice(ji,jj+1) * tmu(ji,jj+1) + v_ice(ji+1,jj+1) * tmu(ji+1,jj+1) ) &
150                                  / ztmu
151            zcmo(ji,jj,9)  = sst_io(ji,jj)
152            zcmo(ji,jj,10) = sss_io(ji,jj)
153
154            zcmo(ji,jj,11) = fnsolar(ji,jj) + fsolar(ji,jj)
155            zcmo(ji,jj,12) = fsolar (ji,jj)
156            zcmo(ji,jj,13) = fnsolar(ji,jj)
157            ! See thersf for the coefficient
158            zcmo(ji,jj,14) = - fsalt(ji,jj) * rday * ( sss_io(ji,jj) + epsi16 ) / soce
159            zcmo(ji,jj,15) = gtaux(ji,jj)
160            zcmo(ji,jj,16) = gtauy(ji,jj)
161            zcmo(ji,jj,17) = ( 1.0 - frld(ji,jj) ) * qsr_ice (ji,jj) + frld(ji,jj) * qsr_oce (ji,jj)
162            zcmo(ji,jj,18) = ( 1.0 - frld(ji,jj) ) * qnsr_ice(ji,jj) + frld(ji,jj) * qnsr_oce(ji,jj)
163            zcmo(ji,jj,19) = sprecip(ji,jj)
164         END DO
165      END DO
166      !
167      ! Write the netcdf file
168      !
169      niter = niter + 1
170      DO jf = 1 , noumef
171         DO jj = 1 , jpj
172            DO ji = 1 , jpi
173               zfield(ji,jj) = zcmo(ji,jj,jf) * cmulti(jf) + cadd(jf)
174            END DO
175         END DO
176         
177         IF ( jf == 7  .OR. jf == 8  .OR. jf == 11 .OR. jf == 12 .OR. jf == 15 .OR.   &
178            jf == 23 .OR. jf == 24 .OR. jf == 16 ) THEN
179            CALL lbc_lnk( zfield, 'T', -1. )
180         ELSE
181            CALL lbc_lnk( zfield, 'T',  1. )
182         ENDIF
183         
184         IF ( nc(jf) == 1 ) CALL histwrite( nice, nam(jf), niter, zfield, ndim, ndex51 )
185         
186      END DO
187     
188      IF ( ( nfice * niter + nit000 - 1 ) >= nitend ) THEN
189         CALL histclo( nice ) 
190      ENDIF
191      !
192   END SUBROUTINE lim_wri
193   
194#endif
195   
196   SUBROUTINE lim_wri_init
197      !!-------------------------------------------------------------------
198      !!                    ***   ROUTINE lim_wri_init  ***
199      !!               
200      !! ** Purpose :   intialisation of LIM sea-ice output
201      !!
202      !! ** Method  : Read the namicewri namelist and check the parameter
203      !!       values called at the first timestep (nit000)
204      !!
205      !! ** input   :   Namelist namicewri
206      !!-------------------------------------------------------------------
207      INTEGER ::   nf      ! ???
208      TYPE FIELD 
209         CHARACTER(len = 35) :: ztitle 
210         CHARACTER(len = 8 ) :: zname         
211         CHARACTER(len = 8 ) :: zunit
212         INTEGER             :: znc   
213         REAL                :: zcmulti 
214         REAL                :: zcadd       
215      END TYPE FIELD
216      TYPE(FIELD) ::  &
217         field_1 , field_2 , field_3 , field_4 , field_5 , field_6 ,   &
218         field_7 , field_8 , field_9 , field_10, field_11, field_12,   &
219         field_13, field_14, field_15, field_16, field_17, field_18,   &
220         field_19
221      TYPE(FIELD) , DIMENSION(jpnoumax) :: zfield
222
223      NAMELIST/namiceout/ noumef, &
224         field_1 , field_2 , field_3 , field_4 , field_5 , field_6 ,   &
225         field_7 , field_8 , field_9 , field_10, field_11, field_12,   &
226         field_13, field_14, field_15, field_16, field_17, field_18,   &
227         field_19
228!!gm      NAMELIST/namiceout/ noumef, &
229!!           zfield( 1), zfield( 2), zfield( 3), zfield( 4), zfield( 5),   &
230!!           zfield( 6), zfield( 7), zfield( 8), zfield( 9), zfield(10),   &
231!!           zfield(11), zfield(12), zfield(13), zfield(14), zfield(15),   &
232!!gm         zfield(16), zfield(17), zfield(18), zfield(19)
233      !!-------------------------------------------------------------------
234
235      ! Read Namelist namicewri
236      REWIND ( numnam_ice )
237      READ   ( numnam_ice  , namiceout )
238     
239      zfield(1)  = field_1
240      zfield(2)  = field_2
241      zfield(3)  = field_3
242      zfield(4)  = field_4
243      zfield(5)  = field_5
244      zfield(6)  = field_6
245      zfield(7)  = field_7
246      zfield(8)  = field_8
247      zfield(9)  = field_9
248      zfield(10) = field_10
249      zfield(11) = field_11
250      zfield(12) = field_12
251      zfield(13) = field_13
252      zfield(14) = field_14
253      zfield(15) = field_15
254      zfield(16) = field_16
255      zfield(17) = field_17
256      zfield(18) = field_18
257      zfield(19) = field_19
258     
259      DO nf = 1, noumef
260         titn  (nf) = zfield(nf)%ztitle
261         nam   (nf) = zfield(nf)%zname
262         uni   (nf) = zfield(nf)%zunit
263         nc    (nf) = zfield(nf)%znc
264         cmulti(nf) = zfield(nf)%zcmulti
265         cadd  (nf) = zfield(nf)%zcadd
266      END DO
267
268      IF(lwp) THEN
269         WRITE(numout,*)
270         WRITE(numout,*) 'lim_wri_init : Ice parameters for outputs'
271         WRITE(numout,*) '~~~~~~~~~~~~'
272         WRITE(numout,*) '    number of fields to be stored         noumef = ', noumef
273         WRITE(numout,*) '           title                            name     unit      Saving (1/0) ',   &
274            &            '    multiplicative constant       additive constant '
275         DO nf = 1 , noumef         
276            WRITE(numout,*) '   ', titn(nf), '   ', nam(nf),'      ', uni(nf),'  ', nc(nf),'        ', cmulti(nf),   &
277               '        ', cadd(nf)
278         END DO
279      ENDIF
280      !   
281   END SUBROUTINE lim_wri_init
282
283#else
284   !!----------------------------------------------------------------------
285   !!   Default option :         Empty module          NO LIM sea-ice model
286   !!----------------------------------------------------------------------
287CONTAINS
288   SUBROUTINE lim_wri          ! Empty routine
289   END SUBROUTINE lim_wri
290#endif
291
292   !!======================================================================
293END MODULE limwri
Note: See TracBrowser for help on using the repository browser.