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/2012/dev_NOC_2012_rev3555/NEMOGCM/NEMO/LIM_SRC_2 – NEMO

source: branches/2012/dev_NOC_2012_rev3555/NEMOGCM/NEMO/LIM_SRC_2/limdia_2.F90 @ 3750

Last change on this file since 3750 was 3625, checked in by acc, 11 years ago

Branch dev_NOC_2012_r3555. #1006. Step 7. Check in code now merged with dev_r3385_NOCS04_HAMF

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