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_2.F90 in trunk/NEMO/LIM_SRC_2 – NEMO

source: trunk/NEMO/LIM_SRC_2/limwri_2.F90 @ 1339

Last change on this file since 1339 was 1339, checked in by smasson, 15 years ago

bugfix in lim outputs calendar see ticket:368 (and orginally ticket:335)

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