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 branches/dev_004_VVL/NEMO/LIM_SRC_2 – NEMO

source: branches/dev_004_VVL/NEMO/LIM_SRC_2/limwri_2.F90 @ 1434

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

first implementation of iom_put, see ticket:387

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