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

source: branches/dev_002_LIM/NEMO/LIM_SRC_2/limwri_2.F90 @ 868

Last change on this file since 868 was 823, checked in by rblod, 16 years ago

Final step to rename LIM_SRC in LIM_SRC_2

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 12.3 KB
RevLine 
[821]1MODULE limwri_2
[3]2   !!======================================================================
[821]3   !!                     ***  MODULE  limwri_2  ***
[3]4   !!         Ice diagnostics :  write ice output files
5   !!======================================================================
[508]6   !! history :  2.0  ! 03-08  (C. Ethe) original code
7   !!            2.0  ! 04-10  (C. Ethe )  1D configuration
8   !!-------------------------------------------------------------------
[821]9#if defined key_lim2
[3]10   !!----------------------------------------------------------------------
[821]11   !!   'key_lim2'  i                                 LIM 2.0 sea-ice model
[3]12   !!----------------------------------------------------------------------
[508]13   !!----------------------------------------------------------------------
[821]14   !!   lim_wri_2      : write of the diagnostics variables in ouput file
15   !!   lim_wri_init_2 : initialization and namelist read
[3]16   !!----------------------------------------------------------------------
[719]17   USE ioipsl
18   USE dianam    ! build name of file (routine)
[717]19   USE phycst
[3]20   USE dom_oce
[717]21   USE daymod
[719]22   USE in_out_manager
[3]23   USE ice_oce         ! ice variables
[719]24   USE flx_oce
[821]25   USE dom_ice_2
26   USE ice_2
[717]27   USE lbclnk
[3]28
29   IMPLICIT NONE
30   PRIVATE
31
[821]32   PUBLIC   lim_wri_2        ! routine called by lim_step_2.F90
[3]33
[508]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 )
[3]42
[508]43   INTEGER ::   nice, nhorid, ndim, niter, ndepid       ! ????
44   INTEGER , DIMENSION( jpij ) ::   ndex51              ! ????
45
[3]46   REAL(wp)  ::            &  ! constant values
[88]47      epsi16 = 1.e-16   ,  &
48      zzero  = 0.e0     ,  &
49      zone   = 1.e0
[3]50
[508]51   !!----------------------------------------------------------------------
[719]52   !!  LIM 2.0, UCL-LOCEAN-IPSL (2005)
53   !! $Header$
[508]54   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
55   !!----------------------------------------------------------------------
56
[3]57CONTAINS
[508]58
[107]59#if defined key_dimgout
[508]60   !!----------------------------------------------------------------------
61   !!   'key_dimgout'                                    Direct Access file
62   !!----------------------------------------------------------------------
[821]63# include "limwri_dimg_2.h90"
[107]64#else
[508]65   !!----------------------------------------------------------------------
66   !!   Default option                                          NetCDF file
67   !!----------------------------------------------------------------------
[107]68
[821]69   SUBROUTINE lim_wri_2( kt )
[3]70      !!-------------------------------------------------------------------
[821]71      !!                    ***   ROUTINE lim_wri_2  ***
[508]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
[3]79      !!-------------------------------------------------------------------
[508]80      INTEGER, INTENT(in) ::   kt     ! number of iteration
[719]81
[508]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
[3]89      !!-------------------------------------------------------------------
90
[508]91      !                                          !--------------------!
[719]92      IF ( kt == nit000 ) THEN                !   Initialisation   !
[508]93         !                                       !--------------------!
[821]94         CALL lim_wri_init_2 
[508]95                           
[3]96         zsto     = rdt_ice
97!!Chris         clop     = "ave(only(x))"      !ibug  namelist parameter a ajouter
98         clop     = "ave(x)"
[719]99         zout     = nwrite * rdt_ice / nfice
[3]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' )
[508]106         CALL histbeg ( clhstnam, jpi, glamt, jpj, gphit,    &
107            &           1, jpi, 1, jpj, 0, zjulian, rdt_ice, nhorid, nice , domain_id=nidom)
[3]108         CALL histvert( nice, "deptht", "Vertical T levels", "m", 1, zdept, ndepid)
109         CALL wheneq  ( jpij , tmask(:,:,1), 1, 1., ndex51, ndim)
110         
[88]111         DO jf = 1, noumef
[719]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 )
[3]114         END DO
[508]115         CALL histend( nice )
[719]116         
[3]117      ENDIF
[508]118      !                                          !--------------------!
119      !                                          !   Cumulate at kt   !
120      !                                          !--------------------!
[3]121
[719]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,*)
[821]125         WRITE(numout,*) 'lim_wri_2 : write ice outputs in NetCDF files at time : ', nyear, nmonth, nday, kt + nfice - 1
126         WRITE(numout,*) '~~~~~~~~~ '
[719]127      ENDIF
128
129      !-- calculs des valeurs instantanees
[3]130     
[88]131      zcmo(:,:, 1:jpnoumax ) = 0.e0 
[3]132      DO jj = 2 , jpjm1
[719]133         DO ji = 2 , jpim1
[3]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)
[719]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) ) &
[3]146                                  / ztmu 
147
[719]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) ) &
[3]150                                  / ztmu
[719]151            zcmo(ji,jj,9)  = sst_io(ji,jj)
152            zcmo(ji,jj,10) = sss_io(ji,jj)
[3]153
[719]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)
[3]157            ! See thersf for the coefficient
[719]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)
[3]163            zcmo(ji,jj,19) = sprecip(ji,jj)
164         END DO
165      END DO
166      !
[508]167      ! Write the netcdf file
[3]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         
[719]177         IF ( jf == 7  .OR. jf == 8  .OR. jf == 15 .OR. jf == 16 ) THEN
[3]178            CALL lbc_lnk( zfield, 'T', -1. )
179         ELSE
180            CALL lbc_lnk( zfield, 'T',  1. )
181         ENDIF
182         
[719]183         IF ( nc(jf) == 1 ) CALL histwrite( nice, nam(jf), niter, zfield, ndim, ndex51 )
[3]184         
185      END DO
186     
[719]187      IF ( ( nfice * niter + nit000 - 1 ) >= nitend ) THEN
188         CALL histclo( nice ) 
189      ENDIF
[508]190      !
[821]191   END SUBROUTINE lim_wri_2
[508]192   
[107]193#endif
194   
[821]195   SUBROUTINE lim_wri_init_2
[3]196      !!-------------------------------------------------------------------
[821]197      !!                    ***   ROUTINE lim_wri_init_2  ***
[3]198      !!               
[508]199      !! ** Purpose :   intialisation of LIM sea-ice output
[3]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
[88]220      TYPE(FIELD) , DIMENSION(jpnoumax) :: zfield
[3]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
[719]227!!gm      NAMELIST/namiceout/ noumef, &
228!!           zfield( 1), zfield( 2), zfield( 3), zfield( 4), zfield( 5),   &
229!!           zfield( 6), zfield( 7), zfield( 8), zfield( 9), zfield(10),   &
230!!           zfield(11), zfield(12), zfield(13), zfield(14), zfield(15),   &
231!!gm         zfield(16), zfield(17), zfield(18), zfield(19)
[3]232      !!-------------------------------------------------------------------
233
[719]234      ! Read Namelist namicewri
235      REWIND ( numnam_ice )
[3]236      READ   ( numnam_ice  , namiceout )
[508]237     
[719]238      zfield(1)  = field_1
239      zfield(2)  = field_2
240      zfield(3)  = field_3
241      zfield(4)  = field_4
242      zfield(5)  = field_5
243      zfield(6)  = field_6
244      zfield(7)  = field_7
245      zfield(8)  = field_8
246      zfield(9)  = field_9
[3]247      zfield(10) = field_10
248      zfield(11) = field_11
249      zfield(12) = field_12
250      zfield(13) = field_13
251      zfield(14) = field_14
252      zfield(15) = field_15
253      zfield(16) = field_16
254      zfield(17) = field_17
255      zfield(18) = field_18
256      zfield(19) = field_19
257     
258      DO nf = 1, noumef
259         titn  (nf) = zfield(nf)%ztitle
260         nam   (nf) = zfield(nf)%zname
261         uni   (nf) = zfield(nf)%zunit
262         nc    (nf) = zfield(nf)%znc
263         cmulti(nf) = zfield(nf)%zcmulti
264         cadd  (nf) = zfield(nf)%zcadd
265      END DO
266
267      IF(lwp) THEN
268         WRITE(numout,*)
[821]269         WRITE(numout,*) 'lim_wri_init_2 : Ice parameters for outputs'
270         WRITE(numout,*) '~~~~~~~~~~~~~~'
[3]271         WRITE(numout,*) '    number of fields to be stored         noumef = ', noumef
272         WRITE(numout,*) '           title                            name     unit      Saving (1/0) ',   &
273            &            '    multiplicative constant       additive constant '
274         DO nf = 1 , noumef         
275            WRITE(numout,*) '   ', titn(nf), '   ', nam(nf),'      ', uni(nf),'  ', nc(nf),'        ', cmulti(nf),   &
[719]276               '        ', cadd(nf)
[3]277         END DO
278      ENDIF
[508]279      !   
[821]280   END SUBROUTINE lim_wri_init_2
[3]281
282#else
283   !!----------------------------------------------------------------------
[821]284   !!   Default option :         Empty module      NO LIM 2.0 sea-ice model
[3]285   !!----------------------------------------------------------------------
286CONTAINS
[821]287   SUBROUTINE lim_wri_2          ! Empty routine
288   END SUBROUTINE lim_wri_2
[3]289#endif
290
291   !!======================================================================
[821]292END MODULE limwri_2
Note: See TracBrowser for help on using the repository browser.