/[lmdze]/trunk/IOIPSL/histvar_seq.f
ViewVC logotype

Annotation of /trunk/IOIPSL/histvar_seq.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 82 - (hide annotations)
Wed Mar 5 14:57:53 2014 UTC (10 years, 3 months ago) by guez
File size: 5580 byte(s)
Changed all ".f90" suffixes to ".f".
1 guez 45 module histvar_seq_m
2    
3     implicit none
4    
5     contains
6    
7     SUBROUTINE histvar_seq (pfid, pvarname, pvid)
8    
9     ! This subroutine optimized the search for the variable in the table.
10     ! In a first phase it will learn the succession of the variables
11     ! called and then it will use the table to guess what comes next.
12     ! It is the best solution to avoid lengthy searches through array
13     ! vectors.
14    
15     ! ARGUMENTS :
16    
17     ! pfid : id of the file on which we work
18     ! pvarname : The name of the variable we are looking for
19     ! pvid : The var id we found
20    
21     USE find_str_m, ONLY: find_str
22     USE errioipsl, ONLY : histerr
23     use histcom_var
24    
25     INTEGER, INTENT(in) :: pfid
26     CHARACTER(LEN=*), INTENT(IN) :: pvarname
27     INTEGER, INTENT(out) :: pvid
28    
29     LOGICAL, SAVE :: learning(nb_files_max)=.TRUE.
30     INTEGER, SAVE :: overlap(nb_files_max) = -1
31     INTEGER, SAVE :: varseq(nb_files_max, nb_var_max*3)
32     INTEGER, SAVE :: varseq_len(nb_files_max) = 0
33     INTEGER, SAVE :: varseq_pos(nb_files_max)
34     INTEGER, SAVE :: varseq_err(nb_files_max) = 0
35     INTEGER :: nb, sp, nx, pos, ib
36     CHARACTER(LEN=20), DIMENSION(nb_var_max) :: tab_str20
37     CHARACTER(LEN=20) :: str20
38     CHARACTER(LEN=70) :: str70
39     INTEGER :: tab_str20_length(nb_var_max)
40    
41     !--------------------------------------------------------------------
42     nb = nb_var(pfid)
43    
44     IF (learning(pfid)) THEN
45    
46     !- 1.0 We compute the length over which we are going
47     !- to check the overlap
48    
49     IF (overlap(pfid) <= 0) THEN
50     IF (nb_var(pfid) > 6) THEN
51     overlap(pfid) = nb_var(pfid)/3*2
52     ELSE
53     overlap(pfid) = nb_var(pfid)
54     ENDIF
55     ENDIF
56    
57     !- 1.1 Find the position of this string
58    
59     str20 = pvarname
60     tab_str20(1:nb) = name(pfid, 1:nb)
61     tab_str20_length(1:nb) = name_length(pfid, 1:nb)
62    
63     CALL find_str (nb, tab_str20, tab_str20_length, str20, pos)
64    
65     IF (pos > 0) THEN
66     pvid = pos
67     ELSE
68     CALL histerr (3, "histvar_seq", &
69     & 'The name of the variable you gave has not been declared', &
70     & 'You should use subroutine histdef for declaring variable', &
71     & TRIM(str20))
72     ENDIF
73    
74     !- 1.2 If we have not given up we store the position
75     !- in the sequence of calls
76    
77     IF ( varseq_err(pfid) .GE. 0 ) THEN
78     sp = varseq_len(pfid)+1
79     IF (sp <= nb_var_max*3) THEN
80     varseq(pfid, sp) = pvid
81     varseq_len(pfid) = sp
82     ELSE
83     CALL histerr (2, "histvar_seq", &
84     & 'The learning process has failed and we give up. '// &
85     & 'Either you sequence is', &
86     & 'too complex or I am too dumb. '// &
87     & 'This will only affect the efficiency', &
88     & 'of your code. Thus if you wish to save time'// &
89     & ' contact the IOIPSL team. ')
90     WRITE(*, *) 'The sequence we have found up to now :'
91     WRITE(*, *) varseq(pfid, 1:sp-1)
92     varseq_err(pfid) = -1
93     ENDIF
94    
95     !--- 1.3 Check if we have found the right overlap
96    
97     IF (varseq_len(pfid) .GE. overlap(pfid)*2) THEN
98    
99     !----- We skip a few variables if needed as they could come
100     !----- from the initialisation of the model.
101    
102     DO ib = 0, sp-overlap(pfid)*2
103     IF ( learning(pfid) .AND.&
104     & SUM(ABS(varseq(pfid, ib+1:ib+overlap(pfid)) -&
105     & varseq(pfid, sp-overlap(pfid)+1:sp))) == 0 ) THEN
106     learning(pfid) = .FALSE.
107     varseq_len(pfid) = sp-overlap(pfid)-ib
108     varseq_pos(pfid) = overlap(pfid)+ib
109     varseq(pfid, 1:varseq_len(pfid)) = &
110     & varseq(pfid, ib+1:ib+varseq_len(pfid))
111     ENDIF
112     ENDDO
113     ENDIF
114     ENDIF
115     ELSE
116    
117     !- 2.0 Now we know how the calls to histwrite are sequenced
118     !- and we can get a guess at the var ID
119    
120     nx = varseq_pos(pfid)+1
121     IF (nx > varseq_len(pfid)) nx = 1
122    
123     pvid = varseq(pfid, nx)
124    
125     IF ( (INDEX(name(pfid, pvid), pvarname) <= 0) &
126     & .OR.(name_length(pfid, pvid) /= len_trim(pvarname)) ) THEN
127     str20 = pvarname
128     tab_str20(1:nb) = name(pfid, 1:nb)
129     tab_str20_length(1:nb) = name_length(pfid, 1:nb)
130     CALL find_str (nb, tab_str20, tab_str20_length, str20, pos)
131     IF (pos > 0) THEN
132     pvid = pos
133     ELSE
134     CALL histerr(3, "histvar_seq", &
135     & 'The name of the variable you gave has not been declared', &
136     & 'You should use subroutine histdef for declaring variable', str20)
137     ENDIF
138     varseq_err(pfid) = varseq_err(pfid)+1
139     ELSE
140    
141     !--- We only keep the new position if we have found the variable
142     !--- this way. This way an out of sequence call to histwrite does
143     !--- not defeat the process.
144    
145     varseq_pos(pfid) = nx
146     ENDIF
147    
148     IF (varseq_err(pfid) .GE. 10) THEN
149     WRITE(str70, '("for file ", I3)') pfid
150     CALL histerr(2, "histvar_seq", &
151     & 'There were 10 errors in the learned sequence of variables', &
152     & str70, 'This looks like a bug, please report it.')
153     varseq_err(pfid) = 0
154     ENDIF
155     ENDIF
156    
157     END SUBROUTINE histvar_seq
158    
159     end module histvar_seq_m

  ViewVC Help
Powered by ViewVC 1.1.21