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.F90 in tags/start/NEMO/LIM_SRC – NEMO

source: tags/start/NEMO/LIM_SRC/limdia.F90 @ 3489

Last change on this file since 3489 was 3, checked in by opalod, 20 years ago

Initial revision

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 11.9 KB
Line 
1MODULE limdia
2   !!======================================================================
3   !!                       ***  MODULE limdia   ***
4   !!                      diagnostics of ice model
5   !!======================================================================
6#if defined key_ice_lim
7   !!----------------------------------------------------------------------
8   !!   'key_ice_lim' :                                   LIM sea-ice model
9   !!----------------------------------------------------------------------
10   !!   lim_dia      : computation of the time evolution of keys var.
11   !!   lim_dia_init : initialization and namelist read
12   !!----------------------------------------------------------------------
13   !! * Modules used
14   USE phycst
15   USE in_out_manager
16   USE ice_oce         ! ice variables
17   USE daymod
18   USE dom_ice
19   USE ice
20   USE iceini
21   USE limistate
22
23   IMPLICIT NONE
24   PRIVATE
25
26   !! * Routine accessibility
27   PUBLIC lim_dia       ! called by ice_step
28
29   !! * Module variables
30   INTEGER, PUBLIC  ::  &
31      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          ::  &
35      nfrinf  = 4          ! number of variables written in one line
36 
37   INTEGER          ::  &
38      nferme ,          &  ! last time step at which the var. are written on file
39      nvinfo ,          &  ! number of total variables
40      nbvt   ,          &  ! number of time variables
41      naveg                ! number of step for accumulation before averaging
42 
43   REAL(wp), DIMENSION(ninfmx) ::  &
44      vinfom               ! temporary working space
45
46   CHARACTER(len=8) ::  &
47      fmtinf  = '1PE13.5 ' ! format of the output values 
48
49   CHARACTER(len=30) :: &
50      fmtw  ,           &  !  formats
51      fmtr  ,           &  !
52      fmtitr               !
53
54   CHARACTER(len=nchsep), DIMENSION(ninfmx) ::   &
55      titvar               ! title of key variables
56
57   REAL(wp) :: &
58      epsi06 = 1.e-06
59
60   !! * Substitutions
61#  include "vectopt_loop_substitute.h90"
62   !!----------------------------------------------------------------------
63   !!   LIM 2.0 , UCL-LODYC-IPSL  (2003)
64   !!----------------------------------------------------------------------
65
66CONTAINS
67
68   SUBROUTINE lim_dia
69      !!--------------------------------------------------------------------
70      !!                  ***  ROUTINE lim_dia  ***
71      !!   
72      !! ** Purpose : Computation and outputs on file ice.evolu
73      !!      the temporal evolution of some key variables
74      !!
75      !! History :
76      !!   8.0  !  97-06  (Louvain-La-Neuve)  Original code
77      !!   8.5  !  02-09  (C. Ethe , G. Madec )  F90: Free form and module
78      !!-------------------------------------------------------------------
79      !! * Local variables
80       INTEGER ::   jv,ji, jj    ! dummy loop indices
81       INTEGER ::   nv           ! indice of variable
82       REAL(wp), DIMENSION(ninfmx) ::  & 
83          vinfor        ! temporary working space
84       REAL(wp)  ::    &
85          area    ,    &  ! sea ice area
86          ldarea  ,    &  ! leads area
87          extent15,    &  ! sea ice extent (15%)
88          extent85,    &  ! sea ice extent (85%)
89          icevol  ,    &  ! sea ice volume
90          snwvol  ,    &  ! snow volume over sea ice
91          icespd          ! sea ice velocity
92       !!-------------------------------------------------------------------
93
94       IF( numit == nstart )   CALL lim_dia_init   ! initialisation of ice_evolu file     
95
96       ! computation of key variables at each time step   
97
98       nv = 1 
99       vinfor(nv) = REAL(numit)
100       nv = nv + 1
101       vinfor(nv) = nyear
102 
103       DO  jv = nbvt + 1, nvinfo
104          vinfor(jv) = 0.0
105       END DO
106
107       extent15 = 0.e0
108       extent85 = 0.e0
109       ! variables in northern Hemis
110       DO  jj = jeq , jpjm1
111          DO  ji = fs_2 , fs_jpim1
112             IF( tms(ji,jj) == 1 ) THEN
113                area = ( 1.0 - frld(ji,jj) ) * aire(ji,jj)
114                IF (frld(ji,jj) <= 0.15 ) extent15 = aire(ji,jj)   
115                IF (frld(ji,jj) <= 0.85 ) extent85 = aire(ji,jj)   
116                ldarea = area   / MAX( ( 1 - frld(ji,jj) ) , epsi06 )
117                icevol = area   * hicif(ji,jj)
118                snwvol = area   * hsnif(ji,jj)
119                icespd = icevol * ( u_ice(ji,jj) * u_ice(ji,jj) + v_ice(ji,jj) * v_ice(ji,jj) )
120
121                vinfor(nv +  1) = vinfor(nv +  1) + area
122                vinfor(nv +  3) = vinfor(nv +  3) + extent15
123                vinfor(nv +  5) = vinfor(nv +  5) + extent85
124                vinfor(nv +  7) = vinfor(nv +  7) + ldarea
125                vinfor(nv +  9) = vinfor(nv +  9) + icevol
126                vinfor(nv + 11) = vinfor(nv + 11) + snwvol
127                vinfor(nv + 13) = vinfor(nv + 13) + icespd
128             ENDIF
129          END DO
130       END DO
131       vinfor(nv + 13) = SQRT( vinfor(nv + 13) / MAX( vinfor(nv + 9 ) , epsi06 ) )
132
133
134      ! variables in southern Hemis
135       nv = nv + 1
136       DO  jj = 2 , jeqm1
137          DO  ji = fs_2 , fs_jpim1
138             IF( tms(ji,jj) == 1 ) THEN
139                area = ( 1.0 - frld(ji,jj) ) * aire(ji,jj)
140                IF (frld(ji,jj) <= 0.15 ) extent15 = aire(ji,jj)   
141                IF (frld(ji,jj) <= 0.85 ) extent85 = aire(ji,jj)   
142                ldarea = area   / MAX( ( 1 - frld(ji,jj) ) , epsi06 )
143                icevol = area   * hicif(ji,jj)
144                snwvol = area   * hsnif(ji,jj)
145                icespd = icevol * ( u_ice(ji,jj) * u_ice(ji,jj) + v_ice(ji,jj) * v_ice(ji,jj) )
146
147                vinfor(nv + 1)  = vinfor(nv + 1)  + area
148                vinfor(nv + 3)  = vinfor(nv + 3)  + extent15
149                vinfor(nv + 5)  = vinfor(nv + 5)  + extent85
150                vinfor(nv + 7)  = vinfor(nv + 7)  + ldarea
151                vinfor(nv + 9)  = vinfor(nv + 9)  + icevol
152                vinfor(nv + 11) = vinfor(nv + 11) + snwvol
153                vinfor(nv + 13) = vinfor(nv + 13) + icespd
154             ENDIF
155          END DO
156       END DO
157       vinfor(nv + 13) = SQRT( vinfor(nv + 13) / MAX( vinfor(nv + 9 ) , epsi06 ) )   
158
159       !  Accumulation before averaging
160       DO jv = 1 , nvinfo
161          vinfom(jv) = vinfom(jv) + vinfor(jv)
162       END DO
163       naveg = naveg + 1 
164   
165       ! oututs on file ice_evolu   
166       IF( MOD( numit , ninfo ) == 0 ) THEN
167          WRITE(90,fmtw) ( titvar(jv), vinfom(jv)/naveg, jv = 1, nvinfo )
168          naveg = 0
169          DO  jv = 1, nvinfo
170             vinfom(jv)=0.0
171          END DO
172       ENDIF
173 
174    END SUBROUTINE lim_dia
175 
176
177    SUBROUTINE lim_dia_init
178       !!-------------------------------------------------------------------
179       !!                  ***  ROUTINE lim_dia_init  ***
180       !!             
181       !! ** Purpose : Preparation of the file ice_evolu for the output of
182       !!      the temporal evolution of key variables
183       !!
184       !! ** input   : Namelist namicedia
185       !!
186       !! history :
187       !!  8.5  ! 03-08 (C. Ethe) original code
188       !!-------------------------------------------------------------------
189       NAMELIST/namicedia/fmtinf, nfrinf, ninfo, ntmoy
190
191       INTEGER  ::   jv   ,     &  ! dummy loop indice
192          &          ntot ,     &
193          &          ndeb ,     &
194          &          irecl
195
196       INTEGER  ::   nv            ! indice of variable
197
198       REAL(wp) ::   zxx0, zxx1    ! temporary scalars
199
200       CHARACTER(len=nchinf) ::   titinf
201       !!-------------------------------------------------------------------
202
203
204       ! Read Namelist namicedia
205       REWIND ( numnam_ice )
206       READ   ( numnam_ice  , namicedia )
207       IF(lwp) THEN
208          WRITE(numout,*)
209          WRITE(numout,*) 'lim_dia_init : ice parameters for ice diagnostics '
210          WRITE(numout,*) '~~~~~~~~~~~~'
211          WRITE(numout,*) '   format of the output values                                 fmtinf = ', fmtinf
212          WRITE(numout,*) '   number of variables written in one line                     nfrinf = ', nfrinf 
213          WRITE(numout,*) '   Instantaneous values of ice evolution or averaging          ntmoy  = ', ntmoy
214          WRITE(numout,*) '   frequency of ouputs on file ice_evolu in case of averaging  ninfo  = ', ninfo
215       ENDIF
216
217       ! Titles of ice key variables :
218       nv = 1
219       titvar(nv) = 'NoIt'  ! iteration number
220       nv = nv + 1
221       titvar(nv) = 'T yr'  ! time step in years
222       nv = nv + 1
223
224       nbvt = nv - 1
225
226       titvar(nv) = 'AEFN' ! sea ice area in the northern Hemisp.(10^12 km2)
227       nv = nv + 1
228       titvar(nv) = 'AEFS' ! sea ice area in the southern Hemisp.(10^12 km2)
229       nv = nv + 1
230       titvar(nv) = 'A15N'  ! sea ice extent (15%) in the northern Hemisp.(10^12 km2)
231       nv = nv + 1
232       titvar(nv) = 'A15S'  ! sea ice extent (15%) in the southern Hemisp.(10^12 km2)
233       nv = nv + 1
234       titvar(nv) = 'A85N'  ! sea ice extent (85%) in the northern Hemisp.(10^12 km2)
235       nv = nv + 1
236       titvar(nv) = 'A85S'  ! sea ice extent (85%) in the southern Hemisp.(10^12 km2)
237       nv = nv + 1
238       titvar(nv) = 'ALEN'  ! leads area in the northern Hemisp.(10^12 km2)
239       nv = nv + 1
240       titvar(nv) = 'ALES'  ! leads area in the southern Hemisp.(10^12 km2)
241       nv = nv + 1
242       titvar(nv) = 'VOLN'  ! sea ice volume in the northern Hemisp.(10^3 km3)
243       nv = nv + 1
244       titvar(nv) = 'VOLS'  ! sea ice volume in the southern Hemisp.(10^3 km3)
245       nv = nv + 1
246       titvar(nv) = 'VONN'  ! snow volume over sea ice in the northern Hemisp.(10^3 km3)
247       nv = nv + 1
248       titvar(nv) = 'VONS'  ! snow volume over sea ice in the southern Hemisp.(10^3 km3)
249       nv = nv + 1
250       titvar(nv) = 'ECGN'  ! mean sea ice velocity in the northern Hemisp.(m/s)
251       nv = nv + 1
252       titvar(nv) = 'ECGS'  ! mean sea ice velocity in the southern Hemisp.(m/s)
253
254       nvinfo = nv
255
256       ! Definition et Ecriture de l'entete : nombre d'enregistrements
257       ndeb   = ( nstart - 1 ) / ninfo
258       IF( nstart == 1 ) ndeb = -1
259
260       nferme = ( nstart - 1 + nitrun) / ninfo
261       ntot   = nferme - ndeb
262       ndeb   = ninfo * ( 1 + ndeb )
263       nferme = ninfo * nferme
264
265       ! definition of formats
266       WRITE( fmtw  , '(A,I3,A2,I1,A)' )  '(', nfrinf, '(A', nchsep, ','//fmtinf//'))'
267       WRITE( fmtr  , '(A,I3,A,I1,A)'  )  '(', nfrinf, '(', nchsep, 'X,'//fmtinf//'))'
268       WRITE( fmtitr, '(A,I3,A,I1,A)'  )  '(', nvinfo, 'A', nchinf, ')'
269
270       ! opening  "ice_evolu" file
271       irecl = ( nchinf + 1 ) * nvinfo 
272       OPEN( numevo_ice, file='ice.evolu', status='unknown', RECL = irecl)
273       OPEN( numevo_ice, file='ice.evolu', status='unknown')
274
275       !- ecriture de 2 lignes d''entete :
276       WRITE(numevo_ice,1000) fmtr, fmtw, fmtitr, nvinfo, ntot, 0, nfrinf
277       zxx0 = 0.001 * REAL(ninfo)
278       zxx1 = 0.001 * REAL(ndeb)
279       WRITE(numevo_ice,1111) REAL(nchinf), 0., zxx1, zxx0, 0., 0., 0
280
281       !- ecriture de 2 lignes de titre :
282       WRITE(numevo_ice,'(A,I8,A,I8,A,I5)')                                      &
283          'Evolution chronologique - Experience '//cexper   &
284          //'   de', ndeb, ' a', nferme, ' pas', ninfo
285       WRITE(numevo_ice,fmtitr) ( titvar(jv), jv = 1, nvinfo )
286
287
288       !--preparation de "titvar" pour l''ecriture parmi les valeurs numeriques :
289       DO  jv = 2 , nvinfo
290          titinf     = titvar(jv)(:nchinf)
291          titvar(jv) = '  '//titinf
292       END DO
293
294       !--Initialisation of the arrays for the accumulation
295       DO  jv = 1, nvinfo
296          vinfom(jv) = 0.
297       END DO
298       naveg = 0
299
3001000   FORMAT( 3(A20),4(1x,I6) )
3011111   FORMAT( 3(F7.1,1X,F7.3,1X),I3,A ) 
302
303    END SUBROUTINE lim_dia_init
304
305#else
306   !!----------------------------------------------------------------------
307   !!   Default option :                               NO LIM sea-ice model
308   !!----------------------------------------------------------------------
309CONTAINS
310   SUBROUTINE lim_dia         ! Empty routine
311   END SUBROUTINE lim_dia
312#endif
313
314   !!======================================================================
315END MODULE limdia
Note: See TracBrowser for help on using the repository browser.