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

source: trunk/NEMO/LIM_SRC_2/limdia_2.F90 @ 1470

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

[uv]i_ice and [uv]i_oce renamed [uv]_ice and [uv]_oce, see ticket:453

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 12.6 KB
Line 
1MODULE limdia_2
2   !!======================================================================
3   !!                       ***  MODULE limdia_2   ***
4   !!                      diagnostics of ice model
5   !!======================================================================
6   !! History :   8.0  !  97-06  (Louvain-La-Neuve)  Original code
7   !!             8.5  !  02-09  (C. Ethe , G. Madec )  F90: Free form and module
8   !!             9.0  !  06-08  (S. Masson)  change frequency output control
9   !!-------------------------------------------------------------------
10#if defined key_lim2
11   !!----------------------------------------------------------------------
12   !!   'key_lim2' :                                  LIM 2.0 sea-ice model
13   !!----------------------------------------------------------------------
14   !!----------------------------------------------------------------------
15   !!   lim_dia_2      : computation of the time evolution of keys var.
16   !!   lim_dia_init_2 : initialization and namelist read
17   !!----------------------------------------------------------------------
18   USE phycst          !
19   USE par_ice_2       ! ice parameters
20   USE sbc_oce         ! surface boundary condition variables
21   USE daymod          !
22   USE dom_ice_2       !
23   USE ice_2           !
24   USE limistate_2     !
25   USE in_out_manager  ! I/O manager
26
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC               lim_dia_2          ! called by sbc_ice_lim_2
31   INTEGER, PUBLIC ::   ntmoy   = 1 ,   &  !: instantaneous values of ice evolution or averaging ntmoy
32      &                 ninfo   = 1        !: frequency of ouputs on file ice_evolu in case of averaging
33
34   INTEGER, PARAMETER ::   &  ! Parameters for outputs to files "evolu"
35      jpinfmx = 100         ,    &  ! maximum number of key variables
36      jpchinf = 5           ,    &  ! ???
37      jpchsep = jpchinf + 2         ! ???
38
39   INTEGER ::   &
40      nfrinf  = 4 ,     &  ! number of variables written in one line
41      nferme ,          &  ! last time step at which the var. are written on file
42      nvinfo ,          &  ! number of total variables
43      nbvt   ,          &  ! number of time variables
44      naveg                ! number of step for accumulation before averaging
45
46   CHARACTER(len= 8) ::   fmtinf  = '1PE13.5 ' ! format of the output values 
47   CHARACTER(len=30) ::   fmtw  ,           &  ! formats
48      &                   fmtr  ,           &  ! ???
49      &                   fmtitr               ! ???
50   CHARACTER(len=jpchsep), DIMENSION(jpinfmx) ::   titvar               ! title of key variables
51 
52   REAL(wp)                     ::   epsi06 = 1.e-06      ! ???
53   REAL(wp), DIMENSION(jpinfmx) ::   vinfom               ! temporary working space
54   REAL(wp), DIMENSION(jpi,jpj) ::   aire                 ! masked grid cell area
55
56   !! * Substitutions
57#  include "vectopt_loop_substitute.h90"
58   !!----------------------------------------------------------------------
59   !!   LIM 2.0,  UCL-LOCEAN-IPSL (2005)
60   !! $Id$
61   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
62   !!----------------------------------------------------------------------
63
64CONTAINS
65
66   SUBROUTINE lim_dia_2( kt )
67      !!--------------------------------------------------------------------
68      !!                  ***  ROUTINE lim_dia_2  ***
69      !!   
70      !! ** Purpose : Computation and outputs on file ice.evolu
71      !!      the temporal evolution of some key variables
72      !!-------------------------------------------------------------------
73      INTEGER, INTENT(in) ::   kt     ! number of iteration
74      !!
75      INTEGER  ::   jv,ji, jj   ! dummy loop indices
76      INTEGER  ::   nv          ! indice of variable
77      REAL(wp) ::   zarea    , zldarea  ,    &  ! sea-ice and leads area
78         &          zextent15, zextent85,    &  ! sea-ice extent (15% and 85%)
79         &          zicevol  , zsnwvol  ,    &  ! sea-ice and snow volume volume
80         &          zicespd                     ! sea-ice velocity
81      REAL(wp), DIMENSION(jpinfmx) ::   vinfor  ! temporary working space
82      !!-------------------------------------------------------------------
83
84      IF( kt == nit000 )   CALL lim_dia_init_2  ! initialisation of ice_evolu file     
85
86      ! computation of key variables at each time step   
87
88      nv = 1 
89      vinfor(nv) = REAL( kt + nn_fsbc - 1 )
90      nv = nv + 1
91      vinfor(nv) = nyear
92 
93      DO jv = nbvt + 1, nvinfo
94         vinfor(jv) = 0.e0
95      END DO
96
97      zextent15 = 0.e0
98      zextent85 = 0.e0
99      ! variables in northern Hemis
100      DO jj = njeq, jpjm1
101         DO ji = fs_2, fs_jpim1   ! vector opt.
102            IF( tms(ji,jj) == 1 ) THEN
103               zarea = ( 1.0 - frld(ji,jj) ) * aire(ji,jj)
104               IF (frld(ji,jj) <= 0.15 ) zextent15 = aire(ji,jj)   
105               IF (frld(ji,jj) <= 0.85 ) zextent85 = aire(ji,jj)   
106               zldarea = zarea   / MAX( ( 1 - frld(ji,jj) ) , epsi06 )
107               zicevol = zarea   * hicif(ji,jj)
108               zsnwvol = zarea   * hsnif(ji,jj)
109               zicespd = zicevol * ( u_ice(ji,jj) * u_ice(ji,jj) + v_ice(ji,jj) * v_ice(ji,jj) )
110               vinfor(nv+ 1) = vinfor(nv+ 1) + zarea
111               vinfor(nv+ 3) = vinfor(nv+ 3) + zextent15
112               vinfor(nv+ 5) = vinfor(nv+ 5) + zextent85
113               vinfor(nv+ 7) = vinfor(nv+ 7) + zldarea
114               vinfor(nv+ 9) = vinfor(nv+ 9) + zicevol
115               vinfor(nv+11) = vinfor(nv+11) + zsnwvol
116               vinfor(nv+13) = vinfor(nv+13) + zicespd
117            ENDIF
118         END DO
119      END DO
120      vinfor(nv+13) = SQRT( vinfor(nv+13) / MAX( vinfor(nv+9) , epsi06 ) )
121
122
123      ! variables in southern Hemis
124       nv = nv + 1
125       DO jj = 2, njeqm1
126          DO ji = fs_2, fs_jpim1   ! vector opt.
127             IF( tms(ji,jj) == 1 ) THEN
128                zarea = ( 1.0 - frld(ji,jj) ) * aire(ji,jj)
129                IF (frld(ji,jj) <= 0.15 ) zextent15 = aire(ji,jj)   
130                IF (frld(ji,jj) <= 0.85 ) zextent85 = aire(ji,jj)   
131                zldarea = zarea   / MAX( ( 1 - frld(ji,jj) ) , epsi06 )
132                zicevol = zarea   * hicif(ji,jj)
133                zsnwvol = zarea   * hsnif(ji,jj)
134                zicespd = zicevol * ( u_ice(ji,jj) * u_ice(ji,jj) + v_ice(ji,jj) * v_ice(ji,jj) )
135                vinfor(nv+ 1) = vinfor(nv+ 1) + zarea
136                vinfor(nv+ 3) = vinfor(nv+ 3) + zextent15
137                vinfor(nv+ 5) = vinfor(nv+ 5) + zextent85
138                vinfor(nv+ 7) = vinfor(nv+ 7) + zldarea
139                vinfor(nv+ 9) = vinfor(nv+ 9) + zicevol
140                vinfor(nv+11) = vinfor(nv+11) + zsnwvol
141                vinfor(nv+13) = vinfor(nv+13) + zicespd
142             ENDIF
143          END DO
144       END DO
145       vinfor(nv+13) = SQRT( vinfor(nv+13) / MAX( vinfor(nv+9) , epsi06 ) )   
146
147       !  Accumulation before averaging
148       DO jv = 1, nvinfo
149          vinfom(jv) = vinfom(jv) + vinfor(jv)
150       END DO
151       naveg = naveg + 1 
152   
153       ! oututs on file ice_evolu   
154       IF( MOD( kt + nn_fsbc - 1, ninfo ) == 0 ) THEN
155          WRITE(numevo_ice,fmtw) ( titvar(jv), vinfom(jv)/naveg, jv = 1, nvinfo )
156          naveg = 0
157          DO jv = 1, nvinfo
158             vinfom(jv) = 0.e0
159          END DO
160       ENDIF
161       !
162    END SUBROUTINE lim_dia_2
163 
164
165    SUBROUTINE lim_dia_init_2
166       !!-------------------------------------------------------------------
167       !!                  ***  ROUTINE lim_dia_init_2  ***
168       !!             
169       !! ** Purpose : Preparation of the file ice_evolu for the output of
170       !!      the temporal evolution of key variables
171       !!
172       !! ** input   : Namelist namicedia
173       !!-------------------------------------------------------------------
174       CHARACTER(len=jpchinf) ::   titinf
175       CHARACTER(len=50)      ::   clname 
176       INTEGER  ::   jv            ! dummy loop indice
177       INTEGER  ::   ntot , ndeb , irecl
178       INTEGER  ::   nv            ! indice of variable
179       REAL(wp) ::   zxx0, zxx1    ! temporary scalars
180
181       NAMELIST/namicedia/fmtinf, nfrinf, ninfo, ntmoy
182       !!-------------------------------------------------------------------
183
184       ! Read Namelist namicedia
185       REWIND ( numnam_ice )
186       READ   ( numnam_ice  , namicedia )
187       
188       IF(lwp) THEN
189          WRITE(numout,*)
190          WRITE(numout,*) 'lim_dia_init_2 : ice parameters for ice diagnostics '
191          WRITE(numout,*) '~~~~~~~~~~~~~~'
192          WRITE(numout,*) '   format of the output values                                 fmtinf = ', fmtinf
193          WRITE(numout,*) '   number of variables written in one line                     nfrinf = ', nfrinf 
194          WRITE(numout,*) '   Instantaneous values of ice evolution or averaging          ntmoy  = ', ntmoy
195          WRITE(numout,*) '   frequency of ouputs on file ice_evolu in case of averaging  ninfo  = ', ninfo
196       ENDIF
197
198       ! masked grid cell area
199       aire(:,:) = area(:,:) * tms(:,:)
200
201       ! Titles of ice key variables :
202       nv = 1
203       titvar(nv) = 'NoIt'  ! iteration number
204       nv = nv + 1
205       titvar(nv) = 'T yr'  ! time step in years
206       
207       nbvt = nv - 1
208
209       nv = nv + 1   ;   titvar(nv) = 'AEFN' ! sea ice area in the northern Hemisp.(10^12 km2)
210       nv = nv + 1   ;   titvar(nv) = 'AEFS' ! sea ice area in the southern Hemisp.(10^12 km2)
211       nv = nv + 1   ;   titvar(nv) = 'A15N'  ! sea ice extent (15%) in the northern Hemisp.(10^12 km2)
212       nv = nv + 1   ;   titvar(nv) = 'A15S'  ! sea ice extent (15%) in the southern Hemisp.(10^12 km2)
213       nv = nv + 1   ;   titvar(nv) = 'A85N'  ! sea ice extent (85%) in the northern Hemisp.(10^12 km2)
214       nv = nv + 1   ;   titvar(nv) = 'A85S'  ! sea ice extent (85%) in the southern Hemisp.(10^12 km2)
215       nv = nv + 1   ;   titvar(nv) = 'ALEN'  ! leads area in the northern Hemisp.(10^12 km2)
216       nv = nv + 1   ;   titvar(nv) = 'ALES'  ! leads area in the southern Hemisp.(10^12 km2)
217       nv = nv + 1   ;   titvar(nv) = 'VOLN'  ! sea ice volume in the northern Hemisp.(10^3 km3)
218       nv = nv + 1   ;   titvar(nv) = 'VOLS'  ! sea ice volume in the southern Hemisp.(10^3 km3)
219       nv = nv + 1   ;   titvar(nv) = 'VONN'  ! snow volume over sea ice in the northern Hemisp.(10^3 km3)
220       nv = nv + 1   ;   titvar(nv) = 'VONS'  ! snow volume over sea ice in the southern Hemisp.(10^3 km3)
221       nv = nv + 1   ;   titvar(nv) = 'ECGN'  ! mean sea ice velocity in the northern Hemisp.(m/s)
222       nv = nv + 1   ;   titvar(nv) = 'ECGS'  ! mean sea ice velocity in the southern Hemisp.(m/s)
223
224       nvinfo = nv
225
226       ! Definition et Ecriture de l'entete : nombre d'enregistrements
227       ndeb   = ( nit000 - 1 + nn_fsbc - 1 ) / ninfo
228       IF( nit000 - 1 + nn_fsbc == 1 ) ndeb = -1
229
230       nferme = ( nitend + nn_fsbc - 1 ) / ninfo ! nit000 - 1 + nn_fsbc - 1 + nitend - nit000 + 1
231       ntot   = nferme - ndeb
232       ndeb   = ninfo * ( 1 + ndeb )
233       nferme = ninfo * nferme
234
235       ! definition of formats
236       WRITE( fmtw  , '(A,I3,A2,I1,A)' )  '(', nfrinf, '(A', jpchsep, ','//fmtinf//'))'
237       WRITE( fmtr  , '(A,I3,A,I1,A)'  )  '(', nfrinf, '(', jpchsep, 'X,'//fmtinf//'))'
238       WRITE( fmtitr, '(A,I3,A,I1,A)'  )  '(', nvinfo, 'A', jpchinf, ')'
239
240       ! opening  "ice_evolu" file
241       clname = 'ice_evolu' 
242       irecl = ( jpchinf + 1 ) * nvinfo 
243       CALL ctlopn( numevo_ice, clname, 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL',   &
244          &           irecl, numout, lwp, 1 )
245
246       !- ecriture de 2 lignes d''entete :
247       WRITE(numevo_ice,1000) fmtr, fmtw, fmtitr, nvinfo, ntot, 0, nfrinf
248       zxx0 = 0.001 * REAL( ninfo )
249       zxx1 = 0.001 * REAL( ndeb  )
250       WRITE(numevo_ice,1111) REAL(jpchinf), 0., zxx1, zxx0, 0., 0., 0
251
252       !- ecriture de 2 lignes de titre :
253       WRITE(numevo_ice,'(A,I8,A,I8,A,I5)')                 &
254          'Evolution chronologique - Experience '//cexper   &
255          //'   de', ndeb, ' a', nferme, ' pas', ninfo
256       WRITE(numevo_ice,fmtitr) ( titvar(jv), jv = 1, nvinfo )
257
258
259       !--preparation de "titvar" pour l''ecriture parmi les valeurs numeriques :
260       DO  jv = 2 , nvinfo
261          titinf     = titvar(jv)(:jpchinf)
262          titvar(jv) = '  '//titinf
263       END DO
264
265       !--Initialisation of the arrays for the accumulation
266       DO  jv = 1, nvinfo
267          vinfom(jv) = 0.
268       END DO
269       naveg = 0
270
2711000   FORMAT( 3(A20),4(1x,I6) )
2721111   FORMAT( 3(F7.1,1X,F7.3,1X),I3,A ) 
273      !
274    END SUBROUTINE lim_dia_init_2
275
276#else
277   !!----------------------------------------------------------------------
278   !!   Default option :                           NO LIM 2.0 sea-ice model
279   !!----------------------------------------------------------------------
280CONTAINS
281   SUBROUTINE lim_dia_2         ! Empty routine
282   END SUBROUTINE lim_dia_2
283#endif
284
285   !!======================================================================
286END MODULE limdia_2
Note: See TracBrowser for help on using the repository browser.