/[MITgcm]/MITgcm/pkg/diagnostics/diagstats_ascii_out.F
ViewVC logotype

Annotation of /MITgcm/pkg/diagnostics/diagstats_ascii_out.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.6 - (hide annotations) (download)
Mon Jul 14 23:26:03 2014 UTC (9 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65, checkpoint65p, checkpoint65q, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e
Changes since 1.5: +11 -5 lines
write stats-diags in ascii file with more digits (same as in monitor).

1 jmc 1.6 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagstats_ascii_out.F,v 1.5 2008/02/05 15:31:19 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "DIAG_OPTIONS.h"
5    
6     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7     CBOP 0
8     C !ROUTINE: DIAGSTATS_ASCII_OUT
9    
10     C !INTERFACE:
11     SUBROUTINE DIAGSTATS_ASCII_OUT(
12     I statGlob, nLev, ndId,
13     I mId, listId, myIter, myThid )
14    
15     C !DESCRIPTION:
16     C Write Global statistic to ASCII file
17    
18     C !USES:
19     IMPLICIT NONE
20     #include "SIZE.h"
21     #include "EEPARAMS.h"
22     #include "EESUPPORT.h"
23     #include "DIAGNOSTICS_SIZE.h"
24     #include "DIAGNOSTICS.h"
25    
26     C !INPUT PARAMETERS:
27     C statGlob ..... AVERAGED DIAGNOSTIC QUANTITY
28     C nLev .... 2nd Dimension (max Nb of levels) of statGlob array
29     C ndId ... diagnostic Id number (in diagnostics long list)
30     C mId ..... field rank in list "listId"
31     C listId ..... current output Stream list
32     C myIter ..... current Iteration Number
33     C myThid ..... my thread Id number
34     INTEGER nLev
35     _RL statGlob(0:nStats,0:nLev,0:nRegions)
36     INTEGER ndId, mId, listId
37     INTEGER myIter, myThid
38     CEOP
39    
40     C !LOCAL VARIABLES:
41     INTEGER im, ix, iv
42     PARAMETER ( iv = nStats - 2 , im = nStats - 1 , ix = nStats )
43 jmc 1.5 INTEGER i, j, k, klev, nUnit
44 jmc 1.1
45     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
46    
47     _BEGIN_MASTER( myThid)
48    
49     #ifdef ALLOW_USE_MPI
50     IF ( diagSt_Ascii .AND. mpiMyId.EQ.0 ) THEN
51     #else
52     IF ( diagSt_Ascii ) THEN
53     #endif
54    
55     nUnit = diagSt_ioUnit(listId)
56     klev = kdiag(ndId)
57     C- single level field: Vertical Integral (k=0) & 1rst level are identical
58     C => write only 1 of the 2:
59     IF ( klev.EQ.1 ) kLev = 0
60     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
61     DO j=0,nRegions
62     IF ( diagSt_region(j,listId).GE.1 ) THEN
63     WRITE(nUnit,'(3A,I10,2(A,I4))') ' field : ', cdiag(ndId),
64 jmc 1.2 & ' ; Iter =',myIter,' ; region #',j, ' ; nb.Lev =',kdiag(ndId)
65 jmc 1.1 c WRITE(nUnit,'(5A)') ' k |',
66     c & ' -- Average -- |', ' -- Std.Dev -- |',
67 jmc 1.5 c & ' -- min -- |', ' -- max -- |'
68 jmc 1.6 c WRITE(nUnit,'(6A)') ' k |',
69     c & ' -- Average -- |', ' -- Std.Dev -- |',
70     c & ' -- min -- |', ' -- max -- |',' -- Vol'
71     WRITE(nUnit,'(6A)') ' k |',
72     & ' -- Average -- |', ' -- Std.Dev -- |',
73     & ' -- min -- |', ' -- max -- |',' -- Vol'
74 jmc 1.1 DO k=0,klev
75     C full precision, do not write the volume:
76     c WRITE(nUnit,'(I3,1P4E20.12)') k,(statGlob(i,k,j),i=1,nStats)
77     C reduced precision + write the volume (usefull for testing):
78 jmc 1.6 c WRITE(nUnit,'(I3,1P5E18.10)')
79     c & k, (statGlob(i,k,j),i=1,nStats), statGlob(0,k,j)
80     C full precision + write the volume:
81     WRITE(nUnit,'(I3,1P5E21.13)')
82 jmc 1.1 & k, (statGlob(i,k,j),i=1,nStats), statGlob(0,k,j)
83     ENDDO
84     ENDIF
85     ENDDO
86     WRITE(nUnit,'(A)') ' '
87     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
88     ENDIF
89    
90     _END_MASTER( myThid )
91    
92     RETURN
93     END

  ViewVC Help
Powered by ViewVC 1.1.22