/[MITgcm]/MITgcm/pkg/ptracers/ptracers_set_iolabel.F
ViewVC logotype

Annotation of /MITgcm/pkg/ptracers/ptracers_set_iolabel.F

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


Revision 1.1 - (hide annotations) (download)
Sat Nov 10 22:09:32 2007 UTC (16 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint62, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59k, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
use a 2 characters string ioLabel to identify tracers (if more than 99 tracers)

1 jmc 1.1 C $Header: $
2     C $Name: $
3    
4     #undef STAND_ALONE_IOLABEL_TESTING
5     C to test the S/R above, #define the above C-PreProcessor flag
6     C and compile this fortran source code alone.
7    
8     #ifdef STAND_ALONE_IOLABEL_TESTING
9     PROGRAM MAIN
10     INTEGER NLL, I
11     PARAMETER (NLL=62*62)
12     CHARACTER*2 LL(NLL)
13    
14     CALL PTRACERS_SET_IOLABEL( LL, NLL, 1 )
15     DO I=1, NLL
16     PRINT *, LL(I)
17     ENDDO
18     END
19     #endif /* STAND_ALONE_IOLABEL_TESTING */
20    
21     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
22    
23     CBOP
24     C !ROUTINE: PTRACERS_SET_IOLABEL
25    
26     C !INTERFACE: ==========================================================
27     SUBROUTINE PTRACERS_SET_IOLABEL(
28     O ioLbl,
29     I nbLbl, myThid )
30    
31     C !DESCRIPTION:
32     C S/R PTRACERS_SET_IOLABEL
33     C Set pTracers IO & diagnostics label (2 characters long)
34     C
35     C Set sequenced label list 00, 02, 03, ... 99, 0a...0Z...9a...9Z,a0...ZZ
36     C to more than 99 TRACERS but without requiring more than two digit labels.
37     C Sequence below allows 3843 (=62**2 -1) tracers.
38     C First 99 are numbered in decimal ;
39     C Then, from 100 to 619, analog to base 52 counting:
40     C 0-9 1rst digit , a-z,A-Z (=52 id) 2nd digit ;
41     C And from 620 to 3843, analog to base 62 counting:
42     C a-z,A-Z 1rst digit ; 0-9,a-z,A-Z (=62 id) 2nd digit ;
43     C ======================================================================
44    
45     C !USES:
46     IMPLICIT NONE
47    
48     C !INPUT PARAMETERS: ===================================================
49     C nbLbl :: number of labels to define
50     C myThid :: my Thread Id number
51     INTEGER nbLbl
52     INTEGER myThid
53    
54     C !OUTPUT PARAMETERS: ==================================================
55     C ioLbl :: io-label
56     CHARACTER*2 ioLbl(nbLbl)
57    
58     C !LOCAL VARIABLES: ====================================================
59     C c1Set1 :: 1rst digit (from left) of 1rst set of labels
60     C c2Set1 :: 2nd digit (from left) of 1rst set of labels
61     C c1Set2 :: 1rst digit (from left) of 2nd set of labels
62     C c2Set2 :: 2nd digit (from left) of 2nd set of labels
63     C c1Set3 :: 1rst digit (from left) of 3rd set of labels
64     C c2Set3 :: 2nd digit (from left) of 3rd set of labels
65     C l1Set :: length of 1rst digit list
66     C l2Set :: length of 2nd digit list
67     C i,j,n :: loop indices
68     CHARACTER*10 c1Set1
69     CHARACTER*10 c2Set1
70     CHARACTER*10 c1Set2
71     CHARACTER*52 c2Set2
72     CHARACTER*52 c1Set3
73     CHARACTER*62 c2Set3
74     INTEGER l1Set, l2Set
75     INTEGER i,j,n
76     CEOP
77    
78     c1Set1 = '0123456789'
79     c2Set1 = c1Set1
80    
81     c1Set2 = c1Set1
82     c2Set2 = 'abcdefghijklmnopqrstuvwxyz'
83     & //'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
84    
85     c1Set3 = c2Set2
86     c2Set3 = c1Set1//c2Set2
87    
88     C-- Set a default.
89     C This shouldn't show up unless there is a problem
90     C where nbLbl is equal or greater than 10*10 + 10*52 + 52*62 = 62**2
91     DO n=1,nbLbl
92     ioLbl(n) = '--'
93     ENDDO
94    
95     n = 0
96     C-- First set of labels:
97     l1Set = LEN(c1Set1)
98     l2Set = LEN(c2Set1)
99     DO j=1,l1Set
100     DO i=1,l2Set
101     C- skip label "00" (since we start tracer numberi from 1)
102     IF ( i.NE.1 .OR. j.NE.1 ) THEN
103     n=n+1
104     IF ( n.LE.nbLbl ) THEN
105     ioLbl(n)(1:1) = c1Set1(j:j)
106     ioLbl(n)(2:2) = c2Set1(i:i)
107     ENDIF
108     ENDIF
109     ENDDO
110     ENDDO
111    
112     C-- 2nd set of labels:
113     l1Set = LEN(c1Set2)
114     l2Set = LEN(c2Set2)
115     DO j=1,l1Set
116     DO i=1,l2Set
117     n=n+1
118     IF ( n.LE.nbLbl ) THEN
119     ioLbl(n)(1:1) = c1Set2(j:j)
120     ioLbl(n)(2:2) = c2Set2(i:i)
121     ENDIF
122     ENDDO
123     ENDDO
124    
125     C-- 3rd set of labels:
126     l1Set = LEN(c1Set3)
127     l2Set = LEN(c2Set3)
128     DO j=1,l1Set
129     DO i=1,l2Set
130     n=n+1
131     IF ( n.LE.nbLbl ) THEN
132     ioLbl(n)(1:1) = c1Set3(j:j)
133     ioLbl(n)(2:2) = c2Set3(i:i)
134     ENDIF
135     ENDDO
136     ENDDO
137    
138     RETURN
139     END

  ViewVC Help
Powered by ViewVC 1.1.22