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

source: branches/DEV_r1837_mass_heat_salt_fluxes/NEMO/LIM_SRC_2/limdia_2.F90 @ 1855

Last change on this file since 1855 was 1855, checked in by gm, 14 years ago

ticket:#665 style change only, with the suppression of thd_ice_2 (merged in ice_2)

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