source: IOIPSL/trunk/src/getincom.f90 @ 4863

Last change on this file since 4863 was 4863, checked in by jgipsl, 4 years ago

Following changes have been done by A.Jornet/LSCE. No change is results and no change in usage have been seen. Some more error checking might stop the model for example if dimensions are not correct in call to histcom module.

Restcom:

  • Define a new var size length (20 to 100 )→ pbs found without no errors
  • Raise an error when var name is too long
  • Deallocate any buffer at the end of all restput/restcget calls → buffers only increase size. After loading/saving nothing is done with this memory

Histcom:

  • Raise an error if given history declared variables do not match with given dimensions from histwrite

getincom and stringop:

  • Enable any length character for the run.def → useful for long filepaths

flincom

  • Enable filenames longer than 80 chars to any
  • Deallocate buffers at the end of any flinget subroutine
  • Property svn:keywords set to Id
File size: 67.2 KB
Line 
1MODULE getincom
2!-
3!$Id$
4!-
5! This software is governed by the CeCILL license
6! See IOIPSL/IOIPSL_License_CeCILL.txt
7!---------------------------------------------------------------------
8USE errioipsl, ONLY : ipslerr,ipsldbg,ipslout
9USE stringop, &
10 &   ONLY : nocomma,cmpblank,strlowercase,nocomment, COMMENT_TAG
11!-
12IMPLICIT NONE
13!-
14PRIVATE
15PUBLIC :: getin_name, getin, getin_dump, getin_dump_para
16!-
17!!--------------------------------------------------------------------
18!! The "getin_name" routine allows the user to change the name
19!! of the definition file in which the data will be read.
20!! ("run.def" by default)
21!!
22!!  SUBROUTINE getin_name (file_name)
23!!
24!! OPTIONAL INPUT argument
25!!
26!! (C) file_name :  the name of the file
27!!                  in which the data will be read
28!!--------------------------------------------------------------------
29!-
30!-
31INTERFACE getin
32!!--------------------------------------------------------------------
33!! The "getin" routines get a variable.
34!! We first check if we find it in the database
35!! and if not we get it from the definition file.
36!!
37!! SUBROUTINE getin (targetname,ret_val)
38!!
39!! INPUT
40!!
41!! (C) targetname : Name of the variable
42!!
43!! OUTPUT
44!!
45!! (I/R/C/L) ret_val : scalar, vector or matrix that will contain
46!!                     that will contain the (standard)
47!!                     integer/real/character/logical values
48!!--------------------------------------------------------------------
49  MODULE PROCEDURE getinrs, getinr1d, getinr2d, &
50 &                 getinis, getini1d, getini2d, &
51 &                 getincs, getinc1d, getinc2d, &
52 &                 getinls, getinl1d, getinl2d
53END INTERFACE
54!-
55!!--------------------------------------------------------------------
56!! The "getin_dump" routine will dump the content of the database
57!! into a file which has the same format as the definition file.
58!! The idea is that the user can see which parameters were used
59!! and re-use the file for another run.
60!!
61!!  SUBROUTINE getin_dump (fileprefix)
62!!
63!! OPTIONAL INPUT argument
64!!
65!! (C) fileprefix : allows the user to change the name of the file
66!!                  in which the data will be archived
67!!--------------------------------------------------------------------
68!-
69!!------------------------------------------------------------------------
70!! Parallel version of getin_dump : user must give a fileprefix and a rank.
71!! It may be usefull to verify that only the root proc is reading the input
72!! def files.
73!!
74!!  SUBROUTINE getin_dump_para (fileprefix,rank)
75!!
76!! INPUT argument
77!!
78!! (C) fileprefix : allows the user to change the name of the file
79!!                  in which the data will be archived
80!! (I) rank : the rank of the parallel process (only 0-999 files will be created)
81!!--------------------------------------------------------------------
82!-
83  INTEGER,PARAMETER :: max_files=100
84  CHARACTER(LEN=100),DIMENSION(max_files),SAVE :: filelist
85  INTEGER,SAVE      :: nbfiles
86!-
87  INTEGER,SAVE :: allread=0
88  CHARACTER(LEN=100),SAVE :: def_file = 'run.def'
89!-
90  INTEGER,PARAMETER :: i_txtslab=1000,l_n=30
91  INTEGER,SAVE :: nb_lines,i_txtsize=0
92  CHARACTER(LEN=100),SAVE,ALLOCATABLE,DIMENSION(:) :: fichier
93  CHARACTER(LEN=l_n),SAVE,ALLOCATABLE,DIMENSION(:) :: targetlist
94  INTEGER,SAVE,ALLOCATABLE,DIMENSION(:) :: fromfile,compline
95!-
96  INTEGER,PARAMETER :: n_d_fmt=5,max_msgs=30
97  CHARACTER(LEN=6),SAVE :: c_i_fmt = '(I5.5)'
98!-
99! The data base of parameters
100!-
101  INTEGER,PARAMETER :: memslabs=300
102  INTEGER,PARAMETER :: compress_lim=20
103!-
104  INTEGER,SAVE :: nb_keys=0
105  INTEGER,SAVE :: keymemsize=0
106!-
107! keystr definition
108! name of a key
109!-
110! keystatus definition
111! keystatus = 1 : Value comes from the file defined by 'def_file'
112! keystatus = 2 : Default value is used
113! keystatus = 3 : Some vector elements were taken from default
114  INTEGER,PARAMETER :: nondefault=1, default=2, vectornondefault=3
115!-
116! keytype definition
117! keytype = 1 : Integer
118! keytype = 2 : Real
119! keytype = 3 : Character
120! keytype = 4 : Logical
121!-
122  INTEGER,PARAMETER :: k_i=1, k_r=2, k_c=3, k_l=4
123!-
124! Allow compression for keys (only for integer and real)
125! keycompress < 0 : not compressed
126! keycompress > 0 : number of repeat of the value
127!-
128TYPE :: t_key
129  CHARACTER(LEN=l_n) :: keystr
130  INTEGER :: keystatus, keytype, keycompress, &
131 &           keyfromfile, keymemstart, keymemlen
132END TYPE t_key
133!-
134  TYPE(t_key),SAVE,ALLOCATABLE,DIMENSION(:) :: key_tab
135!-
136  INTEGER,SAVE,ALLOCATABLE,DIMENSION(:) :: i_mem
137  INTEGER,SAVE :: i_memsize=0, i_mempos=0
138  REAL,SAVE,ALLOCATABLE,DIMENSION(:) :: r_mem
139  INTEGER,SAVE :: r_memsize=0, r_mempos=0
140  CHARACTER(LEN=300),SAVE,ALLOCATABLE,DIMENSION(:) :: c_mem
141  INTEGER,SAVE :: c_memsize=0, c_mempos=0
142  LOGICAL,SAVE,ALLOCATABLE,DIMENSION(:) :: l_mem
143  INTEGER,SAVE :: l_memsize=0, l_mempos=0
144!-
145CONTAINS
146!-
147!=== DEFINITION FILE NAME INTERFACE
148!-
149SUBROUTINE getin_name (cname)
150!---------------------------------------------------------------------
151  IMPLICIT NONE
152!-
153  CHARACTER(LEN=*) :: cname
154!---------------------------------------------------------------------
155  IF (allread == 0) THEN
156    def_file = ADJUSTL(cname)
157  ELSE
158    CALL ipslerr (3,'getin_name', &
159 &   'The name of the database file (any_name.def)', &
160 &   'must be changed *before* any attempt','to read the database.')
161  ENDIF
162!------------------------
163END SUBROUTINE getin_name
164!-
165!=== INTEGER INTERFACE
166!-
167SUBROUTINE getinis (targetname,ret_val)
168!---------------------------------------------------------------------
169  IMPLICIT NONE
170!-
171  CHARACTER(LEN=*) :: targetname
172  INTEGER :: ret_val
173!-
174  INTEGER,DIMENSION(1) :: tmp_ret_val
175  INTEGER :: pos,status=0,fileorig, size_of_in
176!---------------------------------------------------------------------
177!-
178! Do we have this targetname in our database ?
179!-
180  CALL get_findkey (1,targetname,pos)
181!-
182  tmp_ret_val(1) = ret_val
183  size_of_in = SIZE(tmp_ret_val)
184 
185!-
186  IF (pos < 0) THEN
187!-- Get the information out of the file
188    CALL get_fil (targetname,status,fileorig,size_of_in,i_val=tmp_ret_val)
189!-- Put the data into the database
190    CALL get_wdb &
191 &   (targetname,status,fileorig,1,i_val=tmp_ret_val)
192  ELSE
193!-- Get the value out of the database
194    CALL get_rdb (pos,1,targetname,i_val=tmp_ret_val)
195  ENDIF
196  ret_val = tmp_ret_val(1)
197!---------------------
198END SUBROUTINE getinis
199!===
200SUBROUTINE getini1d (targetname,ret_val)
201!---------------------------------------------------------------------
202  IMPLICIT NONE
203!-
204  CHARACTER(LEN=*) :: targetname
205  INTEGER,DIMENSION(:) :: ret_val
206!-
207  INTEGER,DIMENSION(:),ALLOCATABLE,SAVE :: tmp_ret_val
208  INTEGER,SAVE :: tmp_ret_size = 0
209  INTEGER :: pos,size_of_in,status=0,fileorig
210!---------------------------------------------------------------------
211!-
212! Do we have this targetname in our database ?
213!-
214  CALL get_findkey (1,targetname,pos)
215!-
216  size_of_in = SIZE(ret_val)
217  IF (.NOT.ALLOCATED(tmp_ret_val)) THEN
218    ALLOCATE (tmp_ret_val(size_of_in))
219  ELSE IF (size_of_in > tmp_ret_size) THEN
220    DEALLOCATE (tmp_ret_val)
221    ALLOCATE (tmp_ret_val(size_of_in))
222    tmp_ret_size = size_of_in
223  ENDIF
224  tmp_ret_val(1:size_of_in) = ret_val(1:size_of_in)
225!-
226  IF (pos < 0) THEN
227!-- Get the information out of the file
228    CALL get_fil (targetname,status,fileorig,size_of_in,i_val=tmp_ret_val)
229!-- Put the data into the database
230    CALL get_wdb &
231 &   (targetname,status,fileorig,size_of_in,i_val=tmp_ret_val)
232  ELSE
233!-- Get the value out of the database
234    CALL get_rdb (pos,size_of_in,targetname,i_val=tmp_ret_val)
235  ENDIF
236  ret_val(1:size_of_in) = tmp_ret_val(1:size_of_in)
237!----------------------
238END SUBROUTINE getini1d
239!===
240SUBROUTINE getini2d (targetname,ret_val)
241!---------------------------------------------------------------------
242  IMPLICIT NONE
243!-
244  CHARACTER(LEN=*) :: targetname
245  INTEGER,DIMENSION(:,:) :: ret_val
246!-
247  INTEGER,DIMENSION(:),ALLOCATABLE,SAVE :: tmp_ret_val
248  INTEGER,SAVE :: tmp_ret_size = 0
249  INTEGER :: pos,size_of_in,size_1,size_2,status=0,fileorig
250  INTEGER :: jl,jj,ji
251!---------------------------------------------------------------------
252!-
253! Do we have this targetname in our database ?
254!-
255  CALL get_findkey (1,targetname,pos)
256!-
257  size_of_in = SIZE(ret_val)
258  size_1 = SIZE(ret_val,1)
259  size_2 = SIZE(ret_val,2)
260  IF (.NOT.ALLOCATED(tmp_ret_val)) THEN
261    ALLOCATE (tmp_ret_val(size_of_in))
262  ELSE IF (size_of_in > tmp_ret_size) THEN
263    DEALLOCATE (tmp_ret_val)
264    ALLOCATE (tmp_ret_val(size_of_in))
265    tmp_ret_size = size_of_in
266  ENDIF
267!-
268  jl=0
269  DO jj=1,size_2
270    DO ji=1,size_1
271      jl=jl+1
272      tmp_ret_val(jl) = ret_val(ji,jj)
273    ENDDO
274  ENDDO
275!-
276  IF (pos < 0) THEN
277!-- Get the information out of the file
278    CALL get_fil (targetname,status,fileorig,size_of_in,i_val=tmp_ret_val)
279!-- Put the data into the database
280    CALL get_wdb &
281 &   (targetname,status,fileorig,size_of_in,i_val=tmp_ret_val)
282  ELSE
283!-- Get the value out of the database
284    CALL get_rdb (pos,size_of_in,targetname,i_val=tmp_ret_val)
285  ENDIF
286!-
287  jl=0
288  DO jj=1,size_2
289    DO ji=1,size_1
290      jl=jl+1
291      ret_val(ji,jj) = tmp_ret_val(jl)
292    ENDDO
293  ENDDO
294!----------------------
295END SUBROUTINE getini2d
296!-
297!=== REAL INTERFACE
298!-
299SUBROUTINE getinrs (targetname,ret_val)
300!---------------------------------------------------------------------
301  IMPLICIT NONE
302!-
303  CHARACTER(LEN=*) :: targetname
304  REAL :: ret_val
305!-
306  REAL,DIMENSION(1) :: tmp_ret_val
307  INTEGER :: pos,status=0,fileorig, size_of_in
308!---------------------------------------------------------------------
309!-
310! Do we have this targetname in our database ?
311!-
312  CALL get_findkey (1,targetname,pos)
313!-
314  tmp_ret_val(1) = ret_val
315  size_of_in = SIZE(tmp_ret_val)
316!-
317  IF (pos < 0) THEN
318!-- Get the information out of the file
319    CALL get_fil (targetname,status,fileorig,size_of_in,r_val=tmp_ret_val)
320!-- Put the data into the database
321    CALL get_wdb &
322 &   (targetname,status,fileorig,1,r_val=tmp_ret_val)
323  ELSE
324!-- Get the value out of the database
325    CALL get_rdb (pos,1,targetname,r_val=tmp_ret_val)
326  ENDIF
327  ret_val = tmp_ret_val(1)
328!---------------------
329END SUBROUTINE getinrs
330!===
331SUBROUTINE getinr1d (targetname,ret_val)
332!---------------------------------------------------------------------
333  IMPLICIT NONE
334!-
335  CHARACTER(LEN=*) :: targetname
336  REAL,DIMENSION(:) :: ret_val
337!-
338  REAL,DIMENSION(:),ALLOCATABLE,SAVE :: tmp_ret_val
339  INTEGER,SAVE :: tmp_ret_size = 0
340  INTEGER :: pos,size_of_in,status=0,fileorig
341!---------------------------------------------------------------------
342!-
343! Do we have this targetname in our database ?
344!-
345  CALL get_findkey (1,targetname,pos)
346!-
347  size_of_in = SIZE(ret_val)
348  IF (.NOT.ALLOCATED(tmp_ret_val)) THEN
349    ALLOCATE (tmp_ret_val(size_of_in))
350  ELSE IF (size_of_in > tmp_ret_size) THEN
351    DEALLOCATE (tmp_ret_val)
352    ALLOCATE (tmp_ret_val(size_of_in))
353    tmp_ret_size = size_of_in
354  ENDIF
355  tmp_ret_val(1:size_of_in) = ret_val(1:size_of_in)
356!-
357  IF (pos < 0) THEN
358!-- Get the information out of the file
359    CALL get_fil (targetname,status,fileorig,size_of_in,r_val=tmp_ret_val)
360!-- Put the data into the database
361    CALL get_wdb &
362 &   (targetname,status,fileorig,size_of_in,r_val=tmp_ret_val)
363  ELSE
364!-- Get the value out of the database
365    CALL get_rdb (pos,size_of_in,targetname,r_val=tmp_ret_val)
366  ENDIF
367  ret_val(1:size_of_in) = tmp_ret_val(1:size_of_in)
368!----------------------
369
370END SUBROUTINE getinr1d
371!===
372SUBROUTINE getinr2d (targetname,ret_val)
373!---------------------------------------------------------------------
374  IMPLICIT NONE
375!-
376  CHARACTER(LEN=*) :: targetname
377  REAL,DIMENSION(:,:) :: ret_val
378!-
379  REAL,DIMENSION(:),ALLOCATABLE,SAVE :: tmp_ret_val
380  INTEGER,SAVE :: tmp_ret_size = 0
381  INTEGER :: pos,size_of_in,size_1,size_2,status=0,fileorig
382  INTEGER :: jl,jj,ji
383!---------------------------------------------------------------------
384!-
385! Do we have this targetname in our database ?
386!-
387  CALL get_findkey (1,targetname,pos)
388!-
389  size_of_in = SIZE(ret_val)
390  size_1 = SIZE(ret_val,1)
391  size_2 = SIZE(ret_val,2)
392  IF (.NOT.ALLOCATED(tmp_ret_val)) THEN
393    ALLOCATE (tmp_ret_val(size_of_in))
394  ELSE IF (size_of_in > tmp_ret_size) THEN
395    DEALLOCATE (tmp_ret_val)
396    ALLOCATE (tmp_ret_val(size_of_in))
397    tmp_ret_size = size_of_in
398  ENDIF
399!-
400  jl=0
401  DO jj=1,size_2
402    DO ji=1,size_1
403      jl=jl+1
404      tmp_ret_val(jl) = ret_val(ji,jj)
405    ENDDO
406  ENDDO
407!-
408  IF (pos < 0) THEN
409!-- Get the information out of the file
410    CALL get_fil (targetname,status,fileorig,size_of_in,r_val=tmp_ret_val)
411!-- Put the data into the database
412    CALL get_wdb &
413 &   (targetname,status,fileorig,size_of_in,r_val=tmp_ret_val)
414  ELSE
415!-- Get the value out of the database
416    CALL get_rdb (pos,size_of_in,targetname,r_val=tmp_ret_val)
417  ENDIF
418!-
419  jl=0
420  DO jj=1,size_2
421    DO ji=1,size_1
422      jl=jl+1
423      ret_val(ji,jj) = tmp_ret_val(jl)
424    ENDDO
425  ENDDO
426!----------------------
427END SUBROUTINE getinr2d
428!-
429!=== CHARACTER INTERFACE
430!-
431SUBROUTINE getincs (targetname,ret_val)
432!---------------------------------------------------------------------
433  IMPLICIT NONE
434!-
435  CHARACTER(LEN=*) :: targetname
436  CHARACTER(LEN=*) :: ret_val
437!-
438  CHARACTER(LEN=:),ALLOCATABLE,DIMENSION(:) :: tmp_ret_val
439  INTEGER :: pos,status=0,fileorig,size_of_in,ier
440  INTEGER :: inlength
441!---------------------------------------------------------------------
442!-
443  inlength = LEN(ret_val)
444  ALLOCATE(CHARACTER(inlength) :: tmp_ret_val(1), stat=ier)
445  IF (ier /= 0) CALL ipslerr(3, 'getincs', 'Allocation memory problem for', &
446                             'tmp_ret_val' ,'')
447!-
448! Do we have this targetname in our database ?
449!-
450  CALL get_findkey (1,targetname,pos)
451!-
452  tmp_ret_val(1) = ret_val
453  size_of_in = SIZE(tmp_ret_val)
454!-
455  IF (pos < 0) THEN
456!-- Get the information out of the file
457    CALL get_fil (targetname,status,fileorig,size_of_in,c_val=tmp_ret_val)
458!-- Put the data into the database
459    CALL get_wdb &
460 &   (targetname,status,fileorig,1,c_val=tmp_ret_val)
461  ELSE
462!-- Get the value out of the database
463    CALL get_rdb (pos,1,targetname,c_val=tmp_ret_val)
464  ENDIF
465  ret_val = tmp_ret_val(1)
466!--
467  DEALLOCATE(tmp_ret_val)
468!---------------------
469END SUBROUTINE getincs
470!===
471SUBROUTINE getinc1d (targetname,ret_val)
472!---------------------------------------------------------------------
473  IMPLICIT NONE
474!-
475  CHARACTER(LEN=*) :: targetname
476  CHARACTER(LEN=*),DIMENSION(:) :: ret_val
477!-
478  CHARACTER(LEN=100),DIMENSION(:),ALLOCATABLE,SAVE :: tmp_ret_val
479  INTEGER,SAVE :: tmp_ret_size = 0
480  INTEGER :: pos,size_of_in,status=0,fileorig
481!---------------------------------------------------------------------
482!-
483! Do we have this targetname in our database ?
484!-
485  CALL get_findkey (1,targetname,pos)
486!-
487  size_of_in = SIZE(ret_val)
488  IF (.NOT.ALLOCATED(tmp_ret_val)) THEN
489    ALLOCATE (tmp_ret_val(size_of_in))
490  ELSE IF (size_of_in > tmp_ret_size) THEN
491    DEALLOCATE (tmp_ret_val)
492    ALLOCATE (tmp_ret_val(size_of_in))
493    tmp_ret_size = size_of_in
494  ENDIF
495  tmp_ret_val(1:size_of_in) = ret_val(1:size_of_in)
496!-
497  IF (pos < 0) THEN
498!-- Get the information out of the file
499    CALL get_fil (targetname,status,fileorig,size_of_in,c_val=tmp_ret_val)
500!-- Put the data into the database
501    CALL get_wdb &
502 &   (targetname,status,fileorig,size_of_in,c_val=tmp_ret_val)
503  ELSE
504!-- Get the value out of the database
505    CALL get_rdb (pos,size_of_in,targetname,c_val=tmp_ret_val)
506  ENDIF
507  ret_val(1:size_of_in) = tmp_ret_val(1:size_of_in)
508!----------------------
509END SUBROUTINE getinc1d
510!===
511SUBROUTINE getinc2d (targetname,ret_val)
512!---------------------------------------------------------------------
513  IMPLICIT NONE
514!-
515  CHARACTER(LEN=*) :: targetname
516  CHARACTER(LEN=*),DIMENSION(:,:) :: ret_val
517!-
518  CHARACTER(LEN=100),DIMENSION(:),ALLOCATABLE,SAVE :: tmp_ret_val
519  INTEGER,SAVE :: tmp_ret_size = 0
520  INTEGER :: pos,size_of_in,size_1,size_2,status=0,fileorig
521  INTEGER :: jl,jj,ji
522!---------------------------------------------------------------------
523!-
524! Do we have this targetname in our database ?
525!-
526  CALL get_findkey (1,targetname,pos)
527!-
528  size_of_in = SIZE(ret_val)
529  size_1 = SIZE(ret_val,1)
530  size_2 = SIZE(ret_val,2)
531  IF (.NOT.ALLOCATED(tmp_ret_val)) THEN
532    ALLOCATE (tmp_ret_val(size_of_in))
533  ELSE IF (size_of_in > tmp_ret_size) THEN
534    DEALLOCATE (tmp_ret_val)
535    ALLOCATE (tmp_ret_val(size_of_in))
536    tmp_ret_size = size_of_in
537  ENDIF
538!-
539  jl=0
540  DO jj=1,size_2
541    DO ji=1,size_1
542      jl=jl+1
543      tmp_ret_val(jl) = ret_val(ji,jj)
544    ENDDO
545  ENDDO
546!-
547  IF (pos < 0) THEN
548!-- Get the information out of the file
549    CALL get_fil (targetname,status,fileorig,size_of_in,c_val=tmp_ret_val)
550!-- Put the data into the database
551    CALL get_wdb &
552 &   (targetname,status,fileorig,size_of_in,c_val=tmp_ret_val)
553  ELSE
554!-- Get the value out of the database
555    CALL get_rdb (pos,size_of_in,targetname,c_val=tmp_ret_val)
556  ENDIF
557!-
558  jl=0
559  DO jj=1,size_2
560    DO ji=1,size_1
561      jl=jl+1
562      ret_val(ji,jj) = tmp_ret_val(jl)
563    ENDDO
564  ENDDO
565!----------------------
566END SUBROUTINE getinc2d
567!-
568!=== LOGICAL INTERFACE
569!-
570SUBROUTINE getinls (targetname,ret_val)
571!---------------------------------------------------------------------
572  IMPLICIT NONE
573!-
574  CHARACTER(LEN=*) :: targetname
575  LOGICAL :: ret_val
576!-
577  LOGICAL,DIMENSION(1) :: tmp_ret_val
578  INTEGER :: pos,status=0,fileorig,size_of_in
579!---------------------------------------------------------------------
580!-
581! Do we have this targetname in our database ?
582!-
583  CALL get_findkey (1,targetname,pos)
584!-
585  tmp_ret_val(1) = ret_val
586  size_of_in = SIZE(tmp_ret_val)
587!-
588  IF (pos < 0) THEN
589!-- Get the information out of the file
590    CALL get_fil (targetname,status,fileorig,size_of_in,l_val=tmp_ret_val)
591!-- Put the data into the database
592    CALL get_wdb &
593 &   (targetname,status,fileorig,1,l_val=tmp_ret_val)
594  ELSE
595!-- Get the value out of the database
596    CALL get_rdb (pos,1,targetname,l_val=tmp_ret_val)
597  ENDIF
598  ret_val = tmp_ret_val(1)
599!---------------------
600END SUBROUTINE getinls
601!===
602SUBROUTINE getinl1d (targetname,ret_val)
603!---------------------------------------------------------------------
604  IMPLICIT NONE
605!-
606  CHARACTER(LEN=*) :: targetname
607  LOGICAL,DIMENSION(:) :: ret_val
608!-
609  LOGICAL,DIMENSION(:),ALLOCATABLE,SAVE :: tmp_ret_val
610  INTEGER,SAVE :: tmp_ret_size = 0
611  INTEGER :: pos,size_of_in,status=0,fileorig
612!---------------------------------------------------------------------
613!-
614! Do we have this targetname in our database ?
615!-
616  CALL get_findkey (1,targetname,pos)
617!-
618  size_of_in = SIZE(ret_val)
619  IF (.NOT.ALLOCATED(tmp_ret_val)) THEN
620    ALLOCATE (tmp_ret_val(size_of_in))
621  ELSE IF (size_of_in > tmp_ret_size) THEN
622    DEALLOCATE (tmp_ret_val)
623    ALLOCATE (tmp_ret_val(size_of_in))
624    tmp_ret_size = size_of_in
625  ENDIF
626  tmp_ret_val(1:size_of_in) = ret_val(1:size_of_in)
627!-
628  IF (pos < 0) THEN
629!-- Get the information out of the file
630    CALL get_fil (targetname,status,fileorig,size_of_in,l_val=tmp_ret_val)
631!-- Put the data into the database
632    CALL get_wdb &
633 &   (targetname,status,fileorig,size_of_in,l_val=tmp_ret_val)
634  ELSE
635!-- Get the value out of the database
636    CALL get_rdb (pos,size_of_in,targetname,l_val=tmp_ret_val)
637  ENDIF
638  ret_val(1:size_of_in) = tmp_ret_val(1:size_of_in)
639!----------------------
640END SUBROUTINE getinl1d
641!===
642SUBROUTINE getinl2d (targetname,ret_val)
643!---------------------------------------------------------------------
644  IMPLICIT NONE
645!-
646  CHARACTER(LEN=*) :: targetname
647  LOGICAL,DIMENSION(:,:) :: ret_val
648!-
649  LOGICAL,DIMENSION(:),ALLOCATABLE,SAVE :: tmp_ret_val
650  INTEGER,SAVE :: tmp_ret_size = 0
651  INTEGER :: pos,size_of_in,size_1,size_2,status=0,fileorig
652  INTEGER :: jl,jj,ji
653!---------------------------------------------------------------------
654!-
655! Do we have this targetname in our database ?
656!-
657  CALL get_findkey (1,targetname,pos)
658!-
659  size_of_in = SIZE(ret_val)
660  size_1 = SIZE(ret_val,1)
661  size_2 = SIZE(ret_val,2)
662  IF (.NOT.ALLOCATED(tmp_ret_val)) THEN
663    ALLOCATE (tmp_ret_val(size_of_in))
664  ELSE IF (size_of_in > tmp_ret_size) THEN
665    DEALLOCATE (tmp_ret_val)
666    ALLOCATE (tmp_ret_val(size_of_in))
667    tmp_ret_size = size_of_in
668  ENDIF
669!-
670  jl=0
671  DO jj=1,size_2
672    DO ji=1,size_1
673      jl=jl+1
674      tmp_ret_val(jl) = ret_val(ji,jj)
675    ENDDO
676  ENDDO
677!-
678  IF (pos < 0) THEN
679!-- Get the information out of the file
680    CALL get_fil (targetname,status,fileorig,size_of_in,l_val=tmp_ret_val)
681!-- Put the data into the database
682    CALL get_wdb &
683 &   (targetname,status,fileorig,size_of_in,l_val=tmp_ret_val)
684  ELSE
685!-- Get the value out of the database
686    CALL get_rdb (pos,size_of_in,targetname,l_val=tmp_ret_val)
687  ENDIF
688!-
689  jl=0
690  DO jj=1,size_2
691    DO ji=1,size_1
692      jl=jl+1
693      ret_val(ji,jj) = tmp_ret_val(jl)
694    ENDDO
695  ENDDO
696!----------------------
697END SUBROUTINE getinl2d
698!-
699!=== Generic file/database INTERFACE
700!-
701SUBROUTINE get_fil (targetname,status,fileorig,nb_to_ret,i_val,r_val,c_val,l_val)
702!---------------------------------------------------------------------
703!- Subroutine that will extract from the file the values
704!- attributed to the keyword targetname
705!-
706!- (C) targetname    : target for which we will look in the file
707!- (I) status    : tells us from where we obtained the data
708!- (I) fileorig  : index of the file from which the key comes
709!- (I) nb_to_ret : size of output vector
710!- (I) i_val(:)  : INTEGER(nb_to_ret)   values
711!- (R) r_val(:)  : REAL(nb_to_ret)      values
712!- (L) l_val(:)  : LOGICAL(nb_to_ret)   values
713!- (C) c_val(:)  : CHARACTER(nb_to_ret) values
714!---------------------------------------------------------------------
715  IMPLICIT NONE
716!-
717  CHARACTER(LEN=*) :: targetname
718  INTEGER,INTENT(IN) :: nb_to_ret
719  INTEGER,INTENT(OUT) :: status,fileorig
720  INTEGER,DIMENSION(:),OPTIONAL          :: i_val
721  REAL,DIMENSION(:),OPTIONAL             :: r_val
722  LOGICAL,DIMENSION(:),OPTIONAL          :: l_val
723  CHARACTER(LEN=*),DIMENSION(:),OPTIONAL :: c_val
724!-
725  INTEGER :: k_typ,it,pos,len_str,status_cnt,io_err
726  CHARACTER(LEN=n_d_fmt)  :: cnt
727  CHARACTER(LEN=:), ALLOCATABLE :: str_READ,str_READ_lower
728  CHARACTER(LEN=9)  :: c_vtyp
729  LOGICAL,DIMENSION(:),ALLOCATABLE :: found
730  LOGICAL :: def_beha,compressed
731  CHARACTER(LEN=10) :: c_fmt
732  INTEGER :: i_cmpval
733  REAL    :: r_cmpval
734  INTEGER :: ipos_tr,ipos_fl
735  LOGICAL :: l_dbg
736!---------------------------------------------------------------------
737  CALL ipsldbg (old_status=l_dbg)
738!---------------------------------------------------------------------
739!-
740! Get the type of the argument
741  CALL get_qtyp (k_typ,c_vtyp,i_val,r_val,c_val,l_val)
742  IF ( (k_typ.NE.k_i) .AND. (k_typ.NE.k_r) .AND. (k_typ.NE.k_c) .AND. (k_typ.NE.k_l) ) THEN
743    CALL ipslerr (3,'get_fil', &
744 &   'Internal error','Unknown type of data',' ')
745  ENDIF
746!-
747! Read the file(s)
748  CALL getin_read
749!-
750! Allocate and initialize the memory we need
751  ALLOCATE(found(nb_to_ret))
752  found(:) = .FALSE.
753!-
754! See what we find in the files read
755!---
756!-- We dont know from which file the target could come.
757!-- Thus by default we attribute it to the first file :
758  fileorig = 1
759!-
760  DO it=1,nb_to_ret
761!---
762!-- First try the target as it is
763    CALL get_findkey (2,targetname,pos)
764!---
765!-- Another try
766!---
767    IF (pos < 0) THEN
768      WRITE(UNIT=cnt,FMT=c_i_fmt) it
769      CALL get_findkey (2,TRIM(targetname)//'__'//cnt,pos)
770    ENDIF
771!---
772    IF (pos > 0) THEN
773!-----
774      found(it) = .TRUE.
775      fileorig = fromfile(pos)
776      !
777      IF (l_dbg) THEN
778         WRITE(*,*) &
779              &      'getin_fil : read key ',targetname,' from file ',fileorig,' has type ',k_typ
780      ENDIF
781!-----
782!---- DECODE
783!-----
784      str_READ = ADJUSTL(fichier(pos))
785      str_READ_lower = str_READ
786      CALL strlowercase (str_READ_lower)
787      IF (l_dbg) THEN
788         WRITE(*,*) &
789              &      '            value    ',str_READ_lower
790      ENDIF
791!-----
792      IF (    (TRIM(str_READ_lower) == 'def')     &
793 &        .OR.(TRIM(str_READ_lower) == 'default') ) THEN
794        def_beha = .TRUE.
795      ELSE
796        def_beha = .FALSE.
797        len_str = LEN_TRIM(str_READ)
798        io_err = 0
799        SELECT CASE (k_typ)
800        CASE(k_i)
801          WRITE (UNIT=c_fmt,FMT='("(I",I3.3,")")') len_str
802          READ (UNIT=str_READ(1:len_str), &
803 &              FMT=c_fmt,IOSTAT=io_err) i_val(it)
804        CASE(k_r)
805          READ (UNIT=str_READ(1:len_str), &
806 &              FMT=*,IOSTAT=io_err) r_val(it)
807        CASE(k_c)
808          c_val(it) = str_READ(1:len_str)
809        CASE(k_l)
810          ipos_tr = -1
811          ipos_fl = -1
812          ipos_tr = MAX(INDEX(str_READ_lower,'tru'), &
813 &                      INDEX(str_READ_lower,'y'))
814          ipos_fl = MAX(INDEX(str_READ_lower,'fal'), &
815 &                      INDEX(str_READ_lower,'n'))
816          IF (ipos_tr > 0) THEN
817            l_val(it) = .TRUE.
818          ELSE IF (ipos_fl > 0) THEN
819            l_val(it) = .FALSE.
820          ELSE
821            io_err = 100
822          ENDIF
823        END SELECT
824        IF (io_err /= 0) THEN
825          CALL ipslerr (3,'get_fil', &
826 &         'Target '//TRIM(targetname), &
827 &         'is not of '//TRIM(c_vtyp)//' type',' ')
828        ENDIF
829      ENDIF
830!-----
831      IF ( (k_typ == k_i).OR.(k_typ == k_r) ) THEN
832!-------
833!------ Is this the value of a compressed field ?
834        compressed = (compline(pos) > 0)
835        IF (compressed) THEN
836          IF (compline(pos) /= nb_to_ret) THEN
837            CALL ipslerr (2,'get_fil', &
838 &           'For key '//TRIM(targetname)//' we have a compressed field', &
839 &           'which does not have the right size.', &
840 &           'We will try to fix that.')
841          ENDIF
842          IF      (k_typ == k_i) THEN
843            i_cmpval = i_val(it)
844          ELSE IF (k_typ == k_r) THEN
845            r_cmpval = r_val(it)
846          ENDIF
847        ENDIF
848      ENDIF
849    ELSE
850      found(it) = .FALSE.
851      def_beha = .FALSE.
852      compressed = .FALSE.
853    ENDIF
854  ENDDO
855!-
856  IF ( (k_typ == k_i).OR.(k_typ == k_r) ) THEN
857!---
858!-- If this is a compressed field then we will uncompress it
859    IF (compressed) THEN
860      DO it=1,nb_to_ret
861        IF (.NOT.found(it)) THEN
862          IF      (k_typ == k_i) THEN
863            i_val(it) = i_cmpval
864          ELSE IF (k_typ == k_r) THEN
865            r_val(it) = r_cmpval
866          ENDIF
867          found(it) = .TRUE.
868        ENDIF
869      ENDDO
870    ENDIF
871  ENDIF
872!-
873! Now we set the status for what we found
874  IF (def_beha) THEN
875    status = default
876    CALL ipslerr (1,'USING DEFAULT BEHAVIOUR FOR', &
877 &   TRIM(targetname),' ',' ')
878    WRITE(ipslout,*) 'USING DEFAULT BEHAVIOUR FOR ',TRIM(targetname)
879  ELSE
880    status_cnt = 0
881    DO it=1,nb_to_ret
882      IF (.NOT.found(it)) THEN
883        status_cnt = status_cnt+1
884        IF      (status_cnt <= max_msgs) THEN
885          WRITE (UNIT=ipslout,FMT='(" USING DEFAULTS : ",A)', &
886 &               ADVANCE='NO') TRIM(targetname)
887          IF (nb_to_ret > 1) THEN
888            WRITE (UNIT=ipslout,FMT='("__")',ADVANCE='NO')
889            WRITE (UNIT=ipslout,FMT=c_i_fmt,ADVANCE='NO') it
890          ENDIF
891          SELECT CASE (k_typ)
892          CASE(k_i)
893            WRITE (UNIT=ipslout,FMT=*) "=",i_val(it)
894          CASE(k_r)
895            WRITE (UNIT=ipslout,FMT=*) "=",r_val(it)
896          CASE(k_c)
897            WRITE (UNIT=ipslout,FMT=*) "=",c_val(it)
898          CASE(k_l)
899            WRITE (UNIT=ipslout,FMT=*) "=",l_val(it)
900          END SELECT
901        ELSE IF (status_cnt == max_msgs+1) THEN
902          WRITE (UNIT=ipslout,FMT='(" USING DEFAULTS ... ",A)')
903        ENDIF
904      ENDIF
905    ENDDO
906!---
907    IF (status_cnt == 0) THEN
908      status = nondefault
909    ELSE IF (status_cnt == nb_to_ret) THEN
910      status = default
911    ELSE
912      status = vectornondefault
913    ENDIF
914  ENDIF
915! Deallocate the memory
916  DEALLOCATE(found)
917!---------------------
918END SUBROUTINE get_fil
919!===
920SUBROUTINE get_rdb (pos,size_of_in,targetname,i_val,r_val,c_val,l_val)
921!---------------------------------------------------------------------
922!- Read the required variable in the database
923!---------------------------------------------------------------------
924  IMPLICIT NONE
925!-
926  INTEGER :: pos,size_of_in
927  CHARACTER(LEN=*) :: targetname
928  INTEGER,DIMENSION(:),OPTIONAL          :: i_val
929  REAL,DIMENSION(:),OPTIONAL             :: r_val
930  LOGICAL,DIMENSION(:),OPTIONAL          :: l_val
931  CHARACTER(LEN=*),DIMENSION(:),OPTIONAL :: c_val
932!-
933  INTEGER :: k_typ,k_beg,k_end
934  CHARACTER(LEN=9) :: c_vtyp
935!---------------------------------------------------------------------
936!-
937! Get the type of the argument
938  CALL get_qtyp (k_typ,c_vtyp,i_val,r_val,c_val,l_val)
939  IF (     (k_typ /= k_i).AND.(k_typ /= k_r) &
940 &    .AND.(k_typ /= k_c).AND.(k_typ /= k_l) )THEN
941    CALL ipslerr (3,'get_rdb', &
942 &   'Internal error','Unknown type of data',' ')
943  ENDIF
944!-
945  IF (key_tab(pos)%keytype /= k_typ) THEN
946    CALL ipslerr (3,'get_rdb', &
947 &   'Wrong data type for keyword '//TRIM(targetname), &
948 &   '(NOT '//TRIM(c_vtyp)//')',' ')
949  ENDIF
950!-
951  IF (key_tab(pos)%keycompress > 0) THEN
952    IF (    (key_tab(pos)%keycompress /= size_of_in) &
953 &      .OR.(key_tab(pos)%keymemlen /= 1) ) THEN
954      CALL ipslerr (3,'get_rdb', &
955 &     'Wrong compression length','for keyword '//TRIM(targetname),' ')
956    ELSE
957      SELECT CASE (k_typ)
958      CASE(k_i)
959        i_val(1:size_of_in) = i_mem(key_tab(pos)%keymemstart)
960      CASE(k_r)
961        r_val(1:size_of_in) = r_mem(key_tab(pos)%keymemstart)
962      END SELECT
963    ENDIF
964  ELSE
965    IF (key_tab(pos)%keymemlen /= size_of_in) THEN
966      CALL ipslerr (3,'get_rdb', &
967 &     'Wrong array length','for keyword '//TRIM(targetname),' ')
968    ELSE
969      k_beg = key_tab(pos)%keymemstart
970      k_end = k_beg+key_tab(pos)%keymemlen-1
971      SELECT CASE (k_typ)
972      CASE(k_i)
973        i_val(1:size_of_in) = i_mem(k_beg:k_end)
974      CASE(k_r)
975        r_val(1:size_of_in) = r_mem(k_beg:k_end)
976      CASE(k_c)
977        c_val(1:size_of_in) = c_mem(k_beg:k_end)
978      CASE(k_l)
979        l_val(1:size_of_in) = l_mem(k_beg:k_end)
980      END SELECT
981    ENDIF
982  ENDIF
983!---------------------
984END SUBROUTINE get_rdb
985!===
986SUBROUTINE get_wdb &
987 &  (targetname,status,fileorig,size_of_in, &
988 &   i_val,r_val,c_val,l_val)
989!---------------------------------------------------------------------
990!- Write data into the data base
991!---------------------------------------------------------------------
992  IMPLICIT NONE
993!-
994  CHARACTER(LEN=*) :: targetname
995  INTEGER :: status,fileorig,size_of_in
996  INTEGER,DIMENSION(:),OPTIONAL          :: i_val
997  REAL,DIMENSION(:),OPTIONAL             :: r_val
998  LOGICAL,DIMENSION(:),OPTIONAL          :: l_val
999  CHARACTER(LEN=*),DIMENSION(:),OPTIONAL :: c_val
1000!-
1001  INTEGER :: k_typ
1002  CHARACTER(LEN=9) :: c_vtyp
1003  INTEGER :: k_mempos,k_memsize,k_beg,k_end
1004  LOGICAL :: l_cmp
1005  LOGICAL :: l_dbg
1006!---------------------------------------------------------------------
1007  CALL ipsldbg (old_status=l_dbg)
1008!---------------------------------------------------------------------
1009!-
1010! Get the type of the argument
1011  CALL get_qtyp (k_typ,c_vtyp,i_val,r_val,c_val,l_val)
1012  IF (     (k_typ /= k_i).AND.(k_typ /= k_r) &
1013 &    .AND.(k_typ /= k_c).AND.(k_typ /= k_l) )THEN
1014    CALL ipslerr (3,'get_wdb', &
1015 &   'Internal error','Unknown type of data',' ')
1016  ENDIF
1017!-
1018! First check if we have sufficiant space for the new key
1019  IF (nb_keys+1 > keymemsize) THEN
1020    CALL getin_allockeys ()
1021  ENDIF
1022!-
1023  SELECT CASE (k_typ)
1024  CASE(k_i)
1025    k_mempos = i_mempos; k_memsize = i_memsize;
1026    l_cmp = (MINVAL(i_val) == MAXVAL(i_val)) &
1027 &         .AND.(size_of_in > compress_lim)
1028  CASE(k_r)
1029    k_mempos = r_mempos; k_memsize = r_memsize;
1030    l_cmp = (MINVAL(r_val) == MAXVAL(r_val)) &
1031 &         .AND.(size_of_in > compress_lim)
1032  CASE(k_c)
1033    k_mempos = c_mempos; k_memsize = c_memsize;
1034    l_cmp = .FALSE.
1035  CASE(k_l)
1036    k_mempos = l_mempos; k_memsize = l_memsize;
1037    l_cmp = .FALSE.
1038  END SELECT
1039!-
1040! Fill out the items of the data base
1041  nb_keys = nb_keys+1
1042  key_tab(nb_keys)%keystr = targetname(1:MIN(LEN_TRIM(targetname),l_n))
1043  key_tab(nb_keys)%keystatus = status
1044  key_tab(nb_keys)%keytype = k_typ
1045  key_tab(nb_keys)%keyfromfile = fileorig
1046  key_tab(nb_keys)%keymemstart = k_mempos+1
1047  IF (l_cmp) THEN
1048    key_tab(nb_keys)%keycompress = size_of_in
1049    key_tab(nb_keys)%keymemlen = 1
1050  ELSE
1051    key_tab(nb_keys)%keycompress = -1
1052    key_tab(nb_keys)%keymemlen = size_of_in
1053  ENDIF
1054  IF (l_dbg) THEN
1055     WRITE(*,*) &
1056 &     "get_wdb : nb_keys ",nb_keys," key_tab keystr   ",key_tab(nb_keys)%keystr,&
1057 &                                       ",keystatus   ",key_tab(nb_keys)%keystatus,&
1058 &                                       ",keytype     ",key_tab(nb_keys)%keytype,&
1059 &                                       ",keycompress ",key_tab(nb_keys)%keycompress,&
1060 &                                       ",keyfromfile ",key_tab(nb_keys)%keyfromfile,&
1061 &                                       ",keymemstart ",key_tab(nb_keys)%keymemstart
1062  ENDIF
1063
1064!-
1065! Before writing the actual size lets see if we have the space
1066  IF (key_tab(nb_keys)%keymemstart+key_tab(nb_keys)%keymemlen &
1067 &    > k_memsize) THEN
1068    CALL getin_allocmem (k_typ,key_tab(nb_keys)%keymemlen)
1069  ENDIF
1070!-
1071  k_beg = key_tab(nb_keys)%keymemstart
1072  k_end = k_beg+key_tab(nb_keys)%keymemlen-1
1073  SELECT CASE (k_typ)
1074  CASE(k_i)
1075    i_mem(k_beg:k_end) = i_val(1:key_tab(nb_keys)%keymemlen)
1076    i_mempos = k_end
1077  CASE(k_r)
1078    r_mem(k_beg:k_end) = r_val(1:key_tab(nb_keys)%keymemlen)
1079    r_mempos = k_end
1080  CASE(k_c)
1081    c_mem(k_beg:k_end) = c_val(1:key_tab(nb_keys)%keymemlen)
1082    c_mempos = k_end
1083  CASE(k_l)
1084    l_mem(k_beg:k_end) = l_val(1:key_tab(nb_keys)%keymemlen)
1085    l_mempos = k_end
1086  END SELECT
1087!---------------------
1088END SUBROUTINE get_wdb
1089!-
1090!===
1091!-
1092SUBROUTINE getin_read
1093!---------------------------------------------------------------------
1094  IMPLICIT NONE
1095!-
1096  INTEGER,SAVE :: current
1097!---------------------------------------------------------------------
1098  IF (allread == 0) THEN
1099!-- Allocate a first set of memory.
1100    CALL getin_alloctxt ()
1101    CALL getin_allockeys ()
1102    CALL getin_allocmem (k_i,0)
1103    CALL getin_allocmem (k_r,0)
1104    CALL getin_allocmem (k_c,0)
1105    CALL getin_allocmem (k_l,0)
1106!-- Start with reading the files
1107    nbfiles = 1
1108    filelist(1) = TRIM(def_file)
1109    current = 1
1110!--
1111    DO WHILE (current <= nbfiles)
1112      CALL getin_readdef (current)
1113      current = current+1
1114    ENDDO
1115    allread = 1
1116    CALL getin_checkcohe ()
1117  ENDIF
1118!------------------------
1119END SUBROUTINE getin_read
1120!-
1121!===
1122!-
1123  SUBROUTINE getin_readdef(current)
1124!---------------------------------------------------------------------
1125!- This subroutine will read the files and only keep the
1126!- the relevant information. The information is kept as it
1127!- found in the file. The data will be analysed later.
1128!---------------------------------------------------------------------
1129  IMPLICIT NONE
1130!-
1131  INTEGER :: current
1132!-
1133  CHARACTER(LEN=:), ALLOCATABLE :: READ_str, NEW_str
1134  CHARACTER(LEN=300) :: last_key,key_str
1135  CHARACTER(LEN=n_d_fmt) :: cnt
1136  CHARACTER(LEN=10) :: c_fmt
1137  INTEGER :: nb_lastkey
1138!-
1139  INTEGER :: eof,ptn,len_str,i,it,iund,io_err
1140  LOGICAL :: l_dbg
1141!---------------------------------------------------------------------
1142  CALL ipsldbg (old_status=l_dbg)
1143!---------------------------------------------------------------------
1144  eof = 0
1145  ptn = 1
1146  nb_lastkey = 0
1147!-
1148  IF (l_dbg) THEN
1149    WRITE(ipslout,*) 'getin_readdef : Open file ',TRIM(filelist(current))
1150  ENDIF
1151!-
1152  OPEN (UNIT=22,FILE=filelist(current),STATUS="OLD",IOSTAT=io_err)
1153  IF (io_err /= 0) THEN
1154    CALL ipslerr (2,'getin_readdef', &
1155 &  'Could not open file '//TRIM(filelist(current)),' ',' ')
1156    RETURN
1157  ENDIF
1158!-
1159  DO WHILE (eof /= 1)
1160!---
1161    CALL getin_skipafew (22,READ_str,eof,nb_lastkey)
1162    len_str = LEN_TRIM(READ_str)
1163    ptn = INDEX(READ_str,'=')
1164!---
1165    IF (ptn > 0) THEN
1166!---- Get the target
1167      key_str = TRIM(ADJUSTL(READ_str(1:ptn-1)))
1168!---- Make sure that a vector keyword has the right length
1169      iund = INDEX(key_str,'__')
1170      IF (iund > 0) THEN
1171        WRITE (UNIT=c_fmt,FMT='("(I",I3.3,")")') &
1172 &        LEN_TRIM(key_str)-iund-1
1173        READ(UNIT=key_str(iund+2:LEN_TRIM(key_str)), &
1174 &           FMT=c_fmt,IOSTAT=io_err) it
1175        IF ( (io_err == 0).AND.(it > 0) ) THEN
1176          WRITE(UNIT=cnt,FMT=c_i_fmt) it
1177          key_str = key_str(1:iund+1)//cnt
1178        ELSE
1179          CALL ipslerr (3,'getin_readdef', &
1180 &         'A very strange key has just been found :', &
1181 &         TRIM(key_str),' ')
1182        ENDIF
1183      ENDIF
1184!---- Prepare the content
1185      NEW_str = TRIM(ADJUSTL(READ_str(ptn+1:len_str)))
1186      CALL nocomma (NEW_str)
1187      CALL cmpblank (NEW_str)
1188      NEW_str  = TRIM(ADJUSTL(NEW_str))
1189      IF (l_dbg) THEN
1190        WRITE(ipslout,*) &
1191 &        '--> getin_readdef : ',TRIM(key_str),' :: ',TRIM(NEW_str)
1192      ENDIF
1193!---- Decypher the content of NEW_str
1194!-
1195!---- This has to be a new key word, thus :
1196      nb_lastkey = 0
1197!----
1198      CALL getin_decrypt (current,key_str,NEW_str,last_key,nb_lastkey)
1199!----
1200    ELSE IF (len_str > 0) THEN
1201!---- Prepare the key if we have an old one to which
1202!---- we will add the line just read
1203      IF (nb_lastkey > 0) THEN
1204        iund =  INDEX(last_key,'__')
1205        IF (iund > 0) THEN
1206!-------- We only continue a keyword, thus it is easy
1207          key_str = last_key(1:iund-1)
1208        ELSE
1209          IF (nb_lastkey /= 1) THEN
1210            CALL ipslerr (3,'getin_readdef', &
1211 &           'We can not have a scalar keyword', &
1212 &           'and a vector content',' ')
1213          ENDIF
1214!-------- The last keyword needs to be transformed into a vector.
1215          WRITE(UNIT=cnt,FMT=c_i_fmt) 1
1216          targetlist(nb_lines) = &
1217 &         last_key(1:MIN(LEN_TRIM(last_key),l_n-n_d_fmt-2))//'__'//cnt
1218          key_str = last_key(1:LEN_TRIM(last_key))
1219        ENDIF
1220      ENDIF
1221!---- Prepare the content
1222      NEW_str = TRIM(ADJUSTL(READ_str(1:len_str)))
1223      CALL getin_decrypt (current,key_str,NEW_str,last_key,nb_lastkey)
1224    ELSE
1225!---- If we have an empty line then the keyword finishes
1226      nb_lastkey = 0
1227      IF (l_dbg) THEN
1228        WRITE(ipslout,*) 'getin_readdef : Have found an emtpy line '
1229      ENDIF
1230    ENDIF
1231  ENDDO
1232!-
1233  CLOSE(UNIT=22)
1234!-
1235  IF (l_dbg) THEN
1236    OPEN (UNIT=22,file=TRIM(def_file)//'.test')
1237    DO i=1,nb_lines
1238      WRITE(UNIT=22,FMT=*) targetlist(i)," : ",fichier(i)
1239    ENDDO
1240    CLOSE(UNIT=22)
1241  ENDIF
1242!-
1243  IF (l_dbg) THEN
1244     WRITE(ipslout,*) "nb_lines ",nb_lines,"nb_keys ",nb_keys
1245     WRITE(ipslout,*) "fichier ",fichier(1:nb_lines)
1246     WRITE(ipslout,*) "targetlist ",targetlist(1:nb_lines)
1247     WRITE(ipslout,*) "fromfile ",fromfile(1:nb_lines)
1248     WRITE(ipslout,*) "compline ",compline(1:nb_lines)
1249     WRITE(ipslout,*) '<-getin_readdef'
1250  ENDIF
1251!---------------------------
1252END SUBROUTINE getin_readdef
1253!-
1254!===
1255!-
1256SUBROUTINE getin_decrypt(current,key_str,NEW_str,last_key,nb_lastkey)
1257!---------------------------------------------------------------------
1258!- This subroutine is going to decypher the line.
1259!- It essentialy checks how many items are included and
1260!- it they can be attached to a key.
1261!---------------------------------------------------------------------
1262  IMPLICIT NONE
1263!-
1264! ARGUMENTS
1265!-
1266  INTEGER :: current,nb_lastkey
1267  CHARACTER(LEN=*) :: key_str,NEW_str
1268  CHARACTER(LEN=*),INTENT(out) :: last_key
1269!-
1270! LOCAL
1271!-
1272  INTEGER :: len_str,blk,nbve,starpos
1273  CHARACTER(LEN=:), ALLOCATABLE :: tmp_str,new_key,mult
1274  CHARACTER(LEN=n_d_fmt) :: cnt
1275  CHARACTER(LEN=10) :: c_fmt
1276  LOGICAL :: l_dbg
1277!---------------------------------------------------------------------
1278  CALL ipsldbg (old_status=l_dbg)
1279!---------------------------------------------------------------------
1280  len_str = LEN_TRIM(NEW_str)
1281  blk = INDEX(NEW_str(1:len_str),' ')
1282  tmp_str = NEW_str(1:len_str)
1283!-
1284! If the key is a new file then we take it up. Else
1285! we save the line and go on.
1286!-
1287  IF (INDEX(key_str,'INCLUDEDEF') > 0) THEN
1288    DO WHILE (blk > 0)
1289      IF (nbfiles+1 > max_files) THEN
1290        CALL ipslerr (3,'getin_decrypt', &
1291 &       'Too many files to include',' ',' ')
1292      ENDIF
1293!-----
1294      nbfiles = nbfiles+1
1295      filelist(nbfiles) = tmp_str(1:blk)
1296!-----
1297      tmp_str = TRIM(ADJUSTL(tmp_str(blk+1:LEN_TRIM(tmp_str))))
1298      blk = INDEX(tmp_str(1:LEN_TRIM(tmp_str)),' ')
1299    ENDDO
1300!---
1301    IF (nbfiles+1 > max_files) THEN
1302      CALL ipslerr (3,'getin_decrypt', &
1303 &     'Too many files to include',' ',' ')
1304    ENDIF
1305!---
1306    nbfiles =  nbfiles+1
1307    filelist(nbfiles) = TRIM(ADJUSTL(tmp_str))
1308!---
1309    last_key = 'INCLUDEDEF'
1310    nb_lastkey = 1
1311  ELSE
1312!-
1313!-- We are working on a new line of input
1314!-
1315    IF (nb_lines+1 > i_txtsize) THEN
1316      CALL getin_alloctxt ()
1317    ENDIF
1318    nb_lines = nb_lines+1
1319!-
1320!-- First we solve the issue of conpressed information. Once
1321!-- this is done all line can be handled in the same way.
1322!-
1323    starpos = INDEX(NEW_str(1:len_str),'*')
1324    IF ( (starpos > 0).AND.(tmp_str(1:1) /= '"') &
1325 &                    .AND.(tmp_str(1:1) /= "'") ) THEN
1326!-----
1327      IF (INDEX(key_str(1:LEN_TRIM(key_str)),'__') > 0) THEN
1328        CALL ipslerr (3,'getin_decrypt', &
1329 &       'We can not have a compressed field of values', &
1330 &       'in a vector notation (TARGET__n).', &
1331 &       'The key at fault : '//TRIM(key_str))
1332      ENDIF
1333!-
1334!---- Read the multiplied
1335!-
1336      mult = TRIM(ADJUSTL(NEW_str(1:starpos-1)))
1337!---- Construct the new string and its parameters
1338      NEW_str = TRIM(ADJUSTL(NEW_str(starpos+1:len_str)))
1339      len_str = LEN_TRIM(NEW_str)
1340      blk = INDEX(NEW_str(1:len_str),' ')
1341      IF (blk > 1) THEN
1342        CALL ipslerr (2,'getin_decrypt', &
1343 &       'This is a strange behavior','you could report',' ')
1344      ENDIF
1345      WRITE (UNIT=c_fmt,FMT='("(I",I5.5,")")') LEN_TRIM(mult)
1346      READ(UNIT=mult,FMT=c_fmt) compline(nb_lines)
1347!---
1348    ELSE
1349      compline(nb_lines) = -1
1350    ENDIF
1351!-
1352!-- If there is no space wthin the line then the target is a scalar
1353!-- or the element of a properly written vector.
1354!-- (ie of the type TARGET__00001)
1355!-
1356    IF (    (blk <= 1) &
1357 &      .OR.(tmp_str(1:1) == '"') &
1358 &      .OR.(tmp_str(1:1) == "'") ) THEN
1359!-
1360      IF (nb_lastkey == 0) THEN
1361!------ Save info of current keyword as a scalar
1362!------ if it is not a continuation
1363        targetlist(nb_lines) = key_str(1:MIN(LEN_TRIM(key_str),l_n))
1364        last_key = key_str(1:MIN(LEN_TRIM(key_str),l_n))
1365        nb_lastkey = 1
1366      ELSE
1367!------ We are continuing a vector so the keyword needs
1368!------ to get the underscores
1369        WRITE(UNIT=cnt,FMT=c_i_fmt) nb_lastkey+1
1370        targetlist(nb_lines) = &
1371 &        key_str(1:MIN(LEN_TRIM(key_str),l_n-n_d_fmt-2))//'__'//cnt
1372        last_key = &
1373 &        key_str(1:MIN(LEN_TRIM(key_str),l_n-n_d_fmt-2))//'__'//cnt
1374        nb_lastkey = nb_lastkey+1
1375      ENDIF
1376!-----
1377      fichier(nb_lines) = NEW_str(1:len_str)
1378      fromfile(nb_lines) = current
1379    ELSE
1380!-
1381!---- If there are blanks whithin the line then we are dealing
1382!---- with a vector and we need to split it in many entries
1383!---- with the TARGET__n notation.
1384!----
1385!---- Test if the targer is not already a vector target !
1386!-
1387      IF (INDEX(TRIM(key_str),'__') > 0) THEN
1388        CALL ipslerr (3,'getin_decrypt', &
1389 &       'We have found a mixed vector notation (TARGET__n).', &
1390 &       'The key at fault : '//TRIM(key_str),' ')
1391      ENDIF
1392!-
1393      nbve = nb_lastkey
1394      nbve = nbve+1
1395      WRITE(UNIT=cnt,FMT=c_i_fmt) nbve
1396!-
1397      DO WHILE (blk > 0)
1398!-
1399!------ Save the content of target__nbve
1400!-
1401        fichier(nb_lines) = tmp_str(1:blk)
1402        new_key = &
1403 &       key_str(1:MIN(LEN_TRIM(key_str),l_n-n_d_fmt-2))//'__'//cnt
1404        targetlist(nb_lines) = new_key(1:MIN(LEN_TRIM(new_key),l_n))
1405        fromfile(nb_lines) = current
1406!-
1407        tmp_str = TRIM(ADJUSTL(tmp_str(blk+1:LEN_TRIM(tmp_str))))
1408        blk = INDEX(TRIM(tmp_str),' ')
1409!-
1410        IF (nb_lines+1 > i_txtsize) THEN
1411          CALL getin_alloctxt ()
1412        ENDIF
1413        nb_lines = nb_lines+1
1414        nbve = nbve+1
1415        WRITE(UNIT=cnt,FMT=c_i_fmt) nbve
1416        compline(nb_lines)=compline(nb_lines-1)
1417!-
1418      ENDDO
1419!-
1420!---- Save the content of the last target
1421!-
1422      fichier(nb_lines) = tmp_str(1:LEN_TRIM(tmp_str))
1423      new_key = &
1424 &      key_str(1:MIN(LEN_TRIM(key_str),l_n-n_d_fmt-2))//'__'//cnt
1425      targetlist(nb_lines) = new_key(1:MIN(LEN_TRIM(new_key),l_n))
1426      fromfile(nb_lines) = current
1427!-
1428      last_key = &
1429 &      key_str(1:MIN(LEN_TRIM(key_str),l_n-n_d_fmt-2))//'__'//cnt
1430      nb_lastkey = nbve
1431!-
1432    ENDIF
1433!-
1434  ENDIF
1435
1436  IF (l_dbg) THEN
1437     WRITE(ipslout,*) "getin_decrypt ->",TRIM(NEW_str), " : "
1438     WRITE(ipslout,*) "getin_decrypt ->", nb_lines,&
1439          & SIZE(fichier), &
1440          & SIZE(fromfile), &
1441          & SIZE(filelist)
1442     IF (nb_lines > 0) THEN
1443        WRITE(ipslout,*) "getin_decrypt ->", &
1444          & TRIM(fichier(nb_lines)), &
1445          & fromfile(nb_lines), &
1446          & TRIM(filelist(fromfile(nb_lines)))
1447        WRITE(ipslout,*) "                compline : ",compline(nb_lines)
1448        WRITE(ipslout,*) "                targetlist : ",TRIM(targetlist(nb_lines))
1449     ENDIF
1450     WRITE(ipslout,*) "                last_key : ",last_key
1451  ENDIF
1452!---------------------------
1453END SUBROUTINE getin_decrypt
1454!-
1455!===
1456!-
1457SUBROUTINE getin_checkcohe ()
1458!---------------------------------------------------------------------
1459!- This subroutine checks for redundancies.
1460!---------------------------------------------------------------------
1461  IMPLICIT NONE
1462!-
1463  INTEGER :: line,n_k,k
1464!---------------------------------------------------------------------
1465  DO line=1,nb_lines-1
1466!-
1467    n_k = 0
1468    DO k=line+1,nb_lines
1469      IF (TRIM(targetlist(line)) == TRIM(targetlist(k))) THEN
1470        n_k = k
1471        EXIT
1472      ENDIF
1473    ENDDO
1474!---
1475!-- IF we have found it we have a problem to solve.
1476!---
1477    IF (n_k > 0) THEN
1478      WRITE(ipslout,*) 'COUNT : ',n_k
1479      WRITE(ipslout,*) &
1480 &  'getin_checkcohe : Found a problem on key ',TRIM(targetlist(line))
1481      WRITE(ipslout,*) &
1482 &  'getin_checkcohe : The following values were encoutered :'
1483      WRITE(ipslout,*) &
1484 &  '                ',TRIM(targetlist(line)),' == ',fichier(line)
1485      WRITE(ipslout,*) &
1486 &  '                ',TRIM(targetlist(k)),' == ',fichier(k)
1487      WRITE(ipslout,*) &
1488 &  'getin_checkcohe : We will keep only the last value'
1489       CALL ipslerr (2,'getin_checkcohe','Found a problem on key ', &
1490 &                     TRIM(targetlist(line)), fichier(line)//" "//fichier(k))
1491      targetlist(line) = ' '
1492    ENDIF
1493  ENDDO
1494!-----------------------------
1495END SUBROUTINE getin_checkcohe
1496!-
1497!===
1498!-
1499SUBROUTINE getin_readline(unitf, out_string, is_eof)
1500!---------------------------------------------------------------------
1501  USE ISO_FORTRAN_ENV,ONLY : IOSTAT_EOR,IOSTAT_END
1502!-
1503  IMPLICIT NONE
1504!-
1505  INTEGER, PARAMETER :: CHARLEN = 100     ! buffer size
1506  INTEGER, INTENT(in) :: unitf
1507  INTEGER, INTENT(out) :: is_eof
1508  CHARACTER(LEN=:),INTENT(out),ALLOCATABLE :: out_string
1509!-
1510  CHARACTER(LEN=CHARLEN)  :: dummy
1511!-
1512  CHARACTER(LEN=:), ALLOCATABLE :: buff1  ! buffer
1513  INTEGER :: ioerr                  ! error code
1514  INTEGER :: readlength                   ! number of chars read from file
1515  LOGICAL :: is_eol, is_first_ite         ! end of line?
1516
1517  is_eof = 0
1518  is_eol = .FALSE.
1519  buff1 = ""
1520
1521  DO WHILE (.NOT. is_eol)
1522!-
1523      dummy = ""
1524      READ (UNIT=unitf,FMT='(A)', ADVANCE='NO', SIZE=readlength,ERR=9998,END=7778,IOSTAT=ioerr) dummy
1525      IF ((ioerr==IOSTAT_EOR).OR.(ioerr==IOSTAT_END)) ioerr = 0
1526!-
1527      ! keep looping if line is commented
1528      dummy = TRIM(ADJUSTL(dummy))
1529!-
1530      ! is end of line?
1531      is_eol = (readlength .LT. CHARLEN)
1532!-
1533      ! merge with previous buffer
1534      buff1 = TRIM(buff1)//TRIM(dummy)
1535  ENDDO
1536!-
1537  out_string=TRIM(buff1)
1538!-
1539  RETURN
1540!-
15419998 CONTINUE
1542  CALL ipslerr (3,'getin_readline','Error while reading file',' ',' ')
1543!-
15447778 CONTINUE
1545  out_string = TRIM(dummy)
1546  is_eof = 1
1547   
1548END SUBROUTINE getin_readline
1549!-
1550! getin_skipafew: reads 
1551!-
1552SUBROUTINE getin_skipafew (unit,out_string,is_eof,nb_lastkey)
1553!---------------------------------------------------------------------
1554  USE ISO_FORTRAN_ENV,ONLY : IOSTAT_EOR,IOSTAT_END
1555!-
1556  IMPLICIT NONE
1557!-
1558  INTEGER :: unit,is_eof,nb_lastkey
1559  CHARACTER(LEN=:),INTENT(out),ALLOCATABLE :: out_string
1560!-
1561  CHARACTER(LEN=1) :: first
1562  CHARACTER(LEN=:), ALLOCATABLE :: dummy
1563!---------------------------------------------------------------------
1564  first=COMMENT_TAG
1565  is_eof = 0
1566  dummy = ""
1567!-
1568! Loop until a non commented line is found
1569  DO WHILE (first == COMMENT_TAG .AND. is_eof == 0)
1570!-
1571     CALL getin_readline(unit, dummy, is_eof)
1572!-
1573!    Is first char a comment? #
1574     IF (LEN(dummy) > 0) THEN
1575         first=dummy(1:1)
1576         IF (first == COMMENT_TAG) THEN
1577           nb_lastkey = 0
1578         ENDIF
1579     ENDIF
1580!-
1581  ENDDO
1582!-
1583  CALL nocomment(dummy)
1584  out_string = TRIM(dummy)
1585!-
1586  RETURN
1587!-
15889998 CONTINUE
1589  CALL ipslerr (3,'getin_skipafew','Error while reading file',' ',' ')
1590!-
15917778 CONTINUE
1592  CALL nocomment(dummy)
1593  out_string = TRIM(dummy)
1594  is_eof = 1
1595!----------------------------
1596END SUBROUTINE getin_skipafew
1597!-
1598!===
1599!-
1600SUBROUTINE getin_allockeys ()
1601!---------------------------------------------------------------------
1602  IMPLICIT NONE
1603!-
1604  TYPE(t_key),ALLOCATABLE,DIMENSION(:) :: tmp_key_tab
1605!-
1606  INTEGER :: ier
1607  CHARACTER(LEN=20) :: c_tmp
1608!---------------------------------------------------------------------
1609  IF (keymemsize == 0) THEN
1610!---
1611!-- Nothing exists in memory arrays and it is easy to do.
1612!---
1613    WRITE (UNIT=c_tmp,FMT=*) memslabs
1614    ALLOCATE(key_tab(memslabs),stat=ier)
1615    IF (ier /= 0) THEN
1616      CALL ipslerr (3,'getin_allockeys', &
1617 &     'Can not allocate key_tab', &
1618 &     'to size '//TRIM(ADJUSTL(c_tmp)),' ')
1619    ENDIF
1620    nb_keys = 0
1621    keymemsize = memslabs
1622    key_tab(:)%keycompress = -1
1623!---
1624  ELSE
1625!---
1626!-- There is something already in the memory,
1627!-- we need to transfer and reallocate.
1628!---
1629    WRITE (UNIT=c_tmp,FMT=*) keymemsize
1630    ALLOCATE(tmp_key_tab(keymemsize),stat=ier)
1631    IF (ier /= 0) THEN
1632      CALL ipslerr (3,'getin_allockeys', &
1633 &     'Can not allocate tmp_key_tab', &
1634 &     'to size '//TRIM(ADJUSTL(c_tmp)),' ')
1635    ENDIF
1636    WRITE (UNIT=c_tmp,FMT=*) keymemsize+memslabs
1637    tmp_key_tab(1:keymemsize) = key_tab(1:keymemsize)
1638    DEALLOCATE(key_tab)
1639    ALLOCATE(key_tab(keymemsize+memslabs),stat=ier)
1640    IF (ier /= 0) THEN
1641      CALL ipslerr (3,'getin_allockeys', &
1642 &     'Can not allocate key_tab', &
1643 &     'to size '//TRIM(ADJUSTL(c_tmp)),' ')
1644    ENDIF
1645    key_tab(:)%keycompress = -1
1646    key_tab(1:keymemsize) = tmp_key_tab(1:keymemsize)
1647    DEALLOCATE(tmp_key_tab)
1648    keymemsize = keymemsize+memslabs
1649  ENDIF
1650!-----------------------------
1651END SUBROUTINE getin_allockeys
1652!-
1653!===
1654!-
1655SUBROUTINE getin_allocmem (type,len_wanted)
1656!---------------------------------------------------------------------
1657!- Allocate the memory of the data base for all 4 types of memory
1658!- INTEGER / REAL / CHARACTER / LOGICAL
1659!---------------------------------------------------------------------
1660  IMPLICIT NONE
1661!-
1662  INTEGER :: type,len_wanted
1663!-
1664  INTEGER,ALLOCATABLE :: tmp_int(:)
1665  REAL,ALLOCATABLE :: tmp_real(:)
1666  CHARACTER(LEN=300),ALLOCATABLE :: tmp_char(:)
1667  LOGICAL,ALLOCATABLE :: tmp_logic(:)
1668  INTEGER :: ier
1669  CHARACTER(LEN=20) :: c_tmp
1670!---------------------------------------------------------------------
1671  SELECT CASE (type)
1672  CASE(k_i)
1673    IF (i_memsize == 0) THEN
1674      ALLOCATE(i_mem(memslabs),stat=ier)
1675      IF (ier /= 0) THEN
1676        WRITE (UNIT=c_tmp,FMT=*) memslabs
1677        CALL ipslerr (3,'getin_allocmem', &
1678 &       'Unable to allocate db-memory', &
1679 &       'i_mem to size '//TRIM(ADJUSTL(c_tmp)),' ')
1680      ENDIF
1681      i_memsize=memslabs
1682    ELSE
1683      ALLOCATE(tmp_int(i_memsize),stat=ier)
1684      IF (ier /= 0) THEN
1685        WRITE (UNIT=c_tmp,FMT=*) i_memsize
1686        CALL ipslerr (3,'getin_allocmem', &
1687 &       'Unable to allocate tmp_int', &
1688 &       'to size '//TRIM(ADJUSTL(c_tmp)),' ')
1689      ENDIF
1690      tmp_int(1:i_memsize) = i_mem(1:i_memsize)
1691      DEALLOCATE(i_mem)
1692      ALLOCATE(i_mem(i_memsize+MAX(memslabs,len_wanted)),stat=ier)
1693      IF (ier /= 0) THEN
1694        WRITE (UNIT=c_tmp,FMT=*) i_memsize+MAX(memslabs,len_wanted)
1695        CALL ipslerr (3,'getin_allocmem', &
1696 &       'Unable to re-allocate db-memory', &
1697 &       'i_mem to size '//TRIM(ADJUSTL(c_tmp)),' ')
1698      ENDIF
1699      i_mem(1:i_memsize) = tmp_int(1:i_memsize)
1700      i_memsize = i_memsize+MAX(memslabs,len_wanted)
1701      DEALLOCATE(tmp_int)
1702    ENDIF
1703  CASE(k_r)
1704    IF (r_memsize == 0) THEN
1705      ALLOCATE(r_mem(memslabs),stat=ier)
1706      IF (ier /= 0) THEN
1707        WRITE (UNIT=c_tmp,FMT=*) memslabs
1708        CALL ipslerr (3,'getin_allocmem', &
1709 &       'Unable to allocate db-memory', &
1710 &       'r_mem to size '//TRIM(ADJUSTL(c_tmp)),' ')
1711      ENDIF
1712      r_memsize =  memslabs
1713    ELSE
1714      ALLOCATE(tmp_real(r_memsize),stat=ier)
1715      IF (ier /= 0) THEN
1716        WRITE (UNIT=c_tmp,FMT=*) r_memsize
1717        CALL ipslerr (3,'getin_allocmem', &
1718 &       'Unable to allocate tmp_real', &
1719 &       'to size '//TRIM(ADJUSTL(c_tmp)),' ')
1720      ENDIF
1721      tmp_real(1:r_memsize) = r_mem(1:r_memsize)
1722      DEALLOCATE(r_mem)
1723      ALLOCATE(r_mem(r_memsize+MAX(memslabs,len_wanted)),stat=ier)
1724      IF (ier /= 0) THEN
1725        WRITE (UNIT=c_tmp,FMT=*) r_memsize+MAX(memslabs,len_wanted)
1726        CALL ipslerr (3,'getin_allocmem', &
1727 &       'Unable to re-allocate db-memory', &
1728 &       'r_mem to size '//TRIM(ADJUSTL(c_tmp)),' ')
1729      ENDIF
1730      r_mem(1:r_memsize) = tmp_real(1:r_memsize)
1731      r_memsize = r_memsize+MAX(memslabs,len_wanted)
1732      DEALLOCATE(tmp_real)
1733    ENDIF
1734  CASE(k_c)
1735    IF (c_memsize == 0) THEN
1736      ALLOCATE(c_mem(memslabs),stat=ier)
1737      IF (ier /= 0) THEN
1738        WRITE (UNIT=c_tmp,FMT=*) memslabs
1739        CALL ipslerr (3,'getin_allocmem', &
1740 &       'Unable to allocate db-memory', &
1741 &       'c_mem to size '//TRIM(ADJUSTL(c_tmp)),' ')
1742      ENDIF
1743      c_memsize = memslabs
1744    ELSE
1745      ALLOCATE(tmp_char(c_memsize),stat=ier)
1746      IF (ier /= 0) THEN
1747        WRITE (UNIT=c_tmp,FMT=*) c_memsize
1748        CALL ipslerr (3,'getin_allocmem', &
1749 &       'Unable to allocate tmp_char', &
1750 &       'to size '//TRIM(ADJUSTL(c_tmp)),' ')
1751      ENDIF
1752      tmp_char(1:c_memsize) = c_mem(1:c_memsize)
1753      DEALLOCATE(c_mem)
1754      ALLOCATE(c_mem(c_memsize+MAX(memslabs,len_wanted)),stat=ier)
1755      IF (ier /= 0) THEN
1756        WRITE (UNIT=c_tmp,FMT=*) c_memsize+MAX(memslabs,len_wanted)
1757        CALL ipslerr (3,'getin_allocmem', &
1758 &       'Unable to re-allocate db-memory', &
1759 &       'c_mem to size '//TRIM(ADJUSTL(c_tmp)),' ')
1760      ENDIF
1761      c_mem(1:c_memsize) = tmp_char(1:c_memsize)
1762      c_memsize = c_memsize+MAX(memslabs,len_wanted)
1763      DEALLOCATE(tmp_char)
1764    ENDIF
1765  CASE(k_l)
1766    IF (l_memsize == 0) THEN
1767      ALLOCATE(l_mem(memslabs),stat=ier)
1768      IF (ier /= 0) THEN
1769        WRITE (UNIT=c_tmp,FMT=*) memslabs
1770        CALL ipslerr (3,'getin_allocmem', &
1771 &       'Unable to allocate db-memory', &
1772 &       'l_mem to size '//TRIM(ADJUSTL(c_tmp)),' ')
1773      ENDIF
1774      l_memsize = memslabs
1775    ELSE
1776      ALLOCATE(tmp_logic(l_memsize),stat=ier)
1777      IF (ier /= 0) THEN
1778        WRITE (UNIT=c_tmp,FMT=*) l_memsize
1779        CALL ipslerr (3,'getin_allocmem', &
1780 &       'Unable to allocate tmp_logic', &
1781 &       'to size '//TRIM(ADJUSTL(c_tmp)),' ')
1782      ENDIF
1783      tmp_logic(1:l_memsize) = l_mem(1:l_memsize)
1784      DEALLOCATE(l_mem)
1785      ALLOCATE(l_mem(l_memsize+MAX(memslabs,len_wanted)),stat=ier)
1786      IF (ier /= 0) THEN
1787        WRITE (UNIT=c_tmp,FMT=*) l_memsize+MAX(memslabs,len_wanted)
1788        CALL ipslerr (3,'getin_allocmem', &
1789 &       'Unable to re-allocate db-memory', &
1790 &       'l_mem to size '//TRIM(ADJUSTL(c_tmp)),' ')
1791      ENDIF
1792      l_mem(1:l_memsize) = tmp_logic(1:l_memsize)
1793      l_memsize = l_memsize+MAX(memslabs,len_wanted)
1794      DEALLOCATE(tmp_logic)
1795    ENDIF
1796  CASE DEFAULT
1797    CALL ipslerr (3,'getin_allocmem','Unknown type of data',' ',' ')
1798  END SELECT
1799!----------------------------
1800END SUBROUTINE getin_allocmem
1801!-
1802!===
1803!-
1804SUBROUTINE getin_alloctxt ()
1805!---------------------------------------------------------------------
1806  IMPLICIT NONE
1807!-
1808  CHARACTER(LEN=300),ALLOCATABLE :: tmp_fic(:)
1809  CHARACTER(LEN=l_n),ALLOCATABLE :: tmp_tgl(:)
1810  INTEGER,ALLOCATABLE :: tmp_int(:)
1811!-
1812  INTEGER :: ier
1813  CHARACTER(LEN=20) :: c_tmp1,c_tmp2
1814!---------------------------------------------------------------------
1815  IF (i_txtsize == 0) THEN
1816!---
1817!-- Nothing exists in memory arrays and it is easy to do.
1818!---
1819    WRITE (UNIT=c_tmp1,FMT=*) i_txtslab
1820    ALLOCATE(fichier(i_txtslab),stat=ier)
1821    IF (ier /= 0) THEN
1822      CALL ipslerr (3,'getin_alloctxt', &
1823 &     'Can not allocate fichier', &
1824 &     'to size '//TRIM(ADJUSTL(c_tmp1)),' ')
1825    ENDIF
1826!---
1827    ALLOCATE(targetlist(i_txtslab),stat=ier)
1828    IF (ier /= 0) THEN
1829      CALL ipslerr (3,'getin_alloctxt', &
1830 &     'Can not allocate targetlist', &
1831 &     'to size '//TRIM(ADJUSTL(c_tmp1)),' ')
1832    ENDIF
1833!---
1834    ALLOCATE(fromfile(i_txtslab),stat=ier)
1835    IF (ier /= 0) THEN
1836      CALL ipslerr (3,'getin_alloctxt', &
1837 &     'Can not allocate fromfile', &
1838 &     'to size '//TRIM(ADJUSTL(c_tmp1)),' ')
1839    ENDIF
1840!---
1841    ALLOCATE(compline(i_txtslab),stat=ier)
1842    IF (ier /= 0) THEN
1843      CALL ipslerr (3,'getin_alloctxt', &
1844 &     'Can not allocate compline', &
1845 &     'to size '//TRIM(ADJUSTL(c_tmp1)),' ')
1846    ENDIF
1847!---
1848    nb_lines = 0
1849    i_txtsize = i_txtslab
1850  ELSE
1851!---
1852!-- There is something already in the memory,
1853!-- we need to transfer and reallocate.
1854!---
1855    WRITE (UNIT=c_tmp1,FMT=*) i_txtsize
1856    WRITE (UNIT=c_tmp2,FMT=*) i_txtsize+i_txtslab
1857    ALLOCATE(tmp_fic(i_txtsize),stat=ier)
1858    IF (ier /= 0) THEN
1859      CALL ipslerr (3,'getin_alloctxt', &
1860 &     'Can not allocate tmp_fic', &
1861 &     'to size '//TRIM(ADJUSTL(c_tmp1)),' ')
1862    ENDIF
1863    tmp_fic(1:i_txtsize) = fichier(1:i_txtsize)
1864    DEALLOCATE(fichier)
1865    ALLOCATE(fichier(i_txtsize+i_txtslab),stat=ier)
1866    IF (ier /= 0) THEN
1867      CALL ipslerr (3,'getin_alloctxt', &
1868 &     'Can not allocate fichier', &
1869 &     'to size '//TRIM(ADJUSTL(c_tmp2)),' ')
1870    ENDIF
1871    fichier(1:i_txtsize) = tmp_fic(1:i_txtsize)
1872    DEALLOCATE(tmp_fic)
1873!---
1874    ALLOCATE(tmp_tgl(i_txtsize),stat=ier)
1875    IF (ier /= 0) THEN
1876      CALL ipslerr (3,'getin_alloctxt', &
1877 &     'Can not allocate tmp_tgl', &
1878 &     'to size '//TRIM(ADJUSTL(c_tmp1)),' ')
1879    ENDIF
1880    tmp_tgl(1:i_txtsize) = targetlist(1:i_txtsize)
1881    DEALLOCATE(targetlist)
1882    ALLOCATE(targetlist(i_txtsize+i_txtslab),stat=ier)
1883    IF (ier /= 0) THEN
1884      CALL ipslerr (3,'getin_alloctxt', &
1885 &     'Can not allocate targetlist', &
1886 &     'to size '//TRIM(ADJUSTL(c_tmp2)),' ')
1887    ENDIF
1888    targetlist(1:i_txtsize) = tmp_tgl(1:i_txtsize)
1889    DEALLOCATE(tmp_tgl)
1890!---
1891    ALLOCATE(tmp_int(i_txtsize),stat=ier)
1892    IF (ier /= 0) THEN
1893      CALL ipslerr (3,'getin_alloctxt', &
1894 &     'Can not allocate tmp_int', &
1895 &     'to size '//TRIM(ADJUSTL(c_tmp1)),' ')
1896    ENDIF
1897    tmp_int(1:i_txtsize) = fromfile(1:i_txtsize)
1898    DEALLOCATE(fromfile)
1899    ALLOCATE(fromfile(i_txtsize+i_txtslab),stat=ier)
1900    IF (ier /= 0) THEN
1901      CALL ipslerr (3,'getin_alloctxt', &
1902 &     'Can not allocate fromfile', &
1903 &     'to size '//TRIM(ADJUSTL(c_tmp2)),' ')
1904    ENDIF
1905    fromfile(1:i_txtsize) = tmp_int(1:i_txtsize)
1906!---
1907    tmp_int(1:i_txtsize) = compline(1:i_txtsize)
1908    DEALLOCATE(compline)
1909    ALLOCATE(compline(i_txtsize+i_txtslab),stat=ier)
1910    IF (ier /= 0) THEN
1911      CALL ipslerr (3,'getin_alloctxt', &
1912 &     'Can not allocate compline', &
1913 &     'to size '//TRIM(ADJUSTL(c_tmp2)),' ')
1914    ENDIF
1915    compline(1:i_txtsize) = tmp_int(1:i_txtsize)
1916    DEALLOCATE(tmp_int)
1917!---
1918    i_txtsize = i_txtsize+i_txtslab
1919  ENDIF
1920!----------------------------
1921END SUBROUTINE getin_alloctxt
1922!-
1923!===
1924!-
1925SUBROUTINE getin_dump (fileprefix)
1926!---------------------------------------------------------------------
1927  IMPLICIT NONE
1928!-
1929  CHARACTER(*),OPTIONAL :: fileprefix
1930!-
1931  CHARACTER(LEN=80) :: usedfileprefix
1932  INTEGER :: ikey,if,iff,iv
1933  CHARACTER(LEN=20) :: c_tmp
1934  CHARACTER(LEN=300) :: tmp_str,used_filename
1935  INTEGER :: io_err
1936  LOGICAL :: l_dbg
1937!---------------------------------------------------------------------
1938  CALL ipsldbg (old_status=l_dbg)
1939!---------------------------------------------------------------------
1940  IF (PRESENT(fileprefix)) THEN
1941    usedfileprefix = fileprefix(1:MIN(LEN_TRIM(fileprefix),80))
1942  ELSE
1943    usedfileprefix = "used"
1944  ENDIF
1945!-
1946  DO if=1,nbfiles
1947!---
1948    used_filename = TRIM(usedfileprefix)//'_'//TRIM(filelist(if))
1949    IF (l_dbg) THEN
1950      WRITE(ipslout,*) &
1951 &      'getin_dump : opens file : ',TRIM(used_filename),' if = ',if
1952      WRITE(ipslout,*) 'GETIN_DUMP : NUMBER OF KEYS : ',nb_keys
1953    ENDIF
1954    OPEN (UNIT=22,FILE=used_filename,iostat=io_err)
1955    IF (io_err /= 0) THEN
1956       CALL ipslerr (3,'getin_dump', &
1957            &   'Could not open file :',TRIM(used_filename), &
1958            &   '')
1959    ENDIF
1960!---
1961!-- If this is the first file we need to add the list
1962!-- of file which belong to it
1963    IF ( (if == 1).AND.(nbfiles > 1) ) THEN
1964      WRITE(22,*) '# '
1965      WRITE(22,*) '# This file is linked to the following files :'
1966      WRITE(22,*) '# '
1967      DO iff=2,nbfiles
1968        WRITE(22,*) 'INCLUDEDEF = ',TRIM(filelist(iff))
1969      ENDDO
1970      WRITE(22,*) '# '
1971      IF (l_dbg) THEN
1972         WRITE(ipslout,*) '# '
1973         WRITE(ipslout,*) '# This file is linked to the following files :'
1974         WRITE(ipslout,*) '# '
1975         DO iff=2,nbfiles
1976            WRITE(ipslout,*) 'INCLUDEDEF = ',TRIM(filelist(iff))
1977         ENDDO
1978         WRITE(ipslout,*) '# '
1979      ENDIF
1980    ENDIF
1981!---
1982    DO ikey=1,nb_keys
1983!-----
1984!---- Is this key from this file ?
1985      IF (key_tab(ikey)%keyfromfile == if) THEN
1986!-------
1987!------ Write some comments
1988        WRITE(22,*) '#'
1989        SELECT CASE (key_tab(ikey)%keystatus)
1990        CASE(nondefault)
1991          WRITE(22,*) '# Values of ', &
1992 &          TRIM(key_tab(ikey)%keystr),' comes from ',TRIM(def_file)
1993        CASE(default)
1994          WRITE(22,*) '# Values of ', &
1995 &          TRIM(key_tab(ikey)%keystr),' are all defaults.'
1996        CASE(vectornondefault)
1997          WRITE(22,*) '# Values of ', &
1998 &          TRIM(key_tab(ikey)%keystr), &
1999 &          ' are a mix of ',TRIM(def_file),' and defaults.'
2000        CASE DEFAULT
2001          WRITE(22,*) '# Dont know from where the value of ', &
2002 &          TRIM(key_tab(ikey)%keystr),' comes.'
2003        END SELECT
2004        WRITE(22,*) '#'
2005        !-
2006        IF (l_dbg) THEN
2007           WRITE(ipslout,*) '#'
2008           WRITE(ipslout,*) '# Status of key ', ikey, ' : ',&
2009 &          TRIM(key_tab(ikey)%keystr),key_tab(ikey)%keystatus
2010        ENDIF
2011!-------
2012!------ Write the values
2013        SELECT CASE (key_tab(ikey)%keytype)
2014        CASE(k_i)
2015          IF (key_tab(ikey)%keymemlen == 1) THEN
2016            IF (key_tab(ikey)%keycompress < 0) THEN
2017              WRITE(22,*) &
2018 &              TRIM(key_tab(ikey)%keystr), &
2019 &              ' = ',i_mem(key_tab(ikey)%keymemstart)
2020            ELSE
2021              WRITE(22,*) &
2022 &              TRIM(key_tab(ikey)%keystr), &
2023 &              ' = ',key_tab(ikey)%keycompress, &
2024 &              ' * ',i_mem(key_tab(ikey)%keymemstart)
2025            ENDIF
2026          ELSE
2027            DO iv=0,key_tab(ikey)%keymemlen-1
2028              WRITE(UNIT=c_tmp,FMT=c_i_fmt) iv+1
2029              WRITE(22,*) &
2030 &              TRIM(key_tab(ikey)%keystr), &
2031 &              '__',TRIM(ADJUSTL(c_tmp)), &
2032 &              ' = ',i_mem(key_tab(ikey)%keymemstart+iv)
2033            ENDDO
2034          ENDIF
2035        CASE(k_r)
2036          IF (key_tab(ikey)%keymemlen == 1) THEN
2037            IF (key_tab(ikey)%keycompress < 0) THEN
2038              WRITE(22,*) &
2039 &              TRIM(key_tab(ikey)%keystr), &
2040 &              ' = ',r_mem(key_tab(ikey)%keymemstart)
2041            ELSE
2042              WRITE(22,*) &
2043 &              TRIM(key_tab(ikey)%keystr), &
2044 &              ' = ',key_tab(ikey)%keycompress, &
2045                   & ' * ',r_mem(key_tab(ikey)%keymemstart)
2046            ENDIF
2047          ELSE
2048            DO iv=0,key_tab(ikey)%keymemlen-1
2049              WRITE(UNIT=c_tmp,FMT=c_i_fmt) iv+1
2050              WRITE(22,*) &
2051 &              TRIM(key_tab(ikey)%keystr),'__',TRIM(ADJUSTL(c_tmp)), &
2052 &              ' = ',r_mem(key_tab(ikey)%keymemstart+iv)
2053            ENDDO
2054          ENDIF
2055        CASE(k_c)
2056          IF (key_tab(ikey)%keymemlen == 1) THEN
2057            tmp_str = c_mem(key_tab(ikey)%keymemstart)
2058            WRITE(22,*) TRIM(key_tab(ikey)%keystr), &
2059 &              ' = ',TRIM(tmp_str)
2060          ELSE
2061            DO iv=0,key_tab(ikey)%keymemlen-1
2062              WRITE(UNIT=c_tmp,FMT=c_i_fmt) iv+1
2063              tmp_str = c_mem(key_tab(ikey)%keymemstart+iv)
2064              WRITE(22,*) &
2065 &              TRIM(key_tab(ikey)%keystr), &
2066 &              '__',TRIM(ADJUSTL(c_tmp)), &
2067 &              ' = ',TRIM(tmp_str)
2068            ENDDO
2069          ENDIF
2070        CASE(k_l)
2071          IF (key_tab(ikey)%keymemlen == 1) THEN
2072            IF (l_mem(key_tab(ikey)%keymemstart)) THEN
2073              WRITE(22,*) TRIM(key_tab(ikey)%keystr),' = TRUE '
2074            ELSE
2075              WRITE(22,*) TRIM(key_tab(ikey)%keystr),' = FALSE '
2076            ENDIF
2077          ELSE
2078            DO iv=0,key_tab(ikey)%keymemlen-1
2079              WRITE(UNIT=c_tmp,FMT=c_i_fmt) iv+1
2080              IF (l_mem(key_tab(ikey)%keymemstart+iv)) THEN
2081                WRITE(22,*) TRIM(key_tab(ikey)%keystr),'__', &
2082 &                          TRIM(ADJUSTL(c_tmp)),' = TRUE '
2083              ELSE
2084                WRITE(22,*) TRIM(key_tab(ikey)%keystr),'__', &
2085 &                          TRIM(ADJUSTL(c_tmp)),' = FALSE '
2086              ENDIF
2087            ENDDO
2088          ENDIF
2089        CASE DEFAULT
2090          CALL ipslerr (3,'getin_dump', &
2091 &         'Unknown type for variable '//TRIM(key_tab(ikey)%keystr), &
2092 &         ' ',' ')
2093        END SELECT
2094      ENDIF
2095    ENDDO
2096!-
2097    CLOSE(UNIT=22)
2098!-
2099  ENDDO
2100!------------------------
2101END SUBROUTINE getin_dump
2102!===
2103SUBROUTINE getin_dump_para (fileprefix,rank)
2104!---------------------------------------------------------------------
2105  IMPLICIT NONE
2106!-
2107  CHARACTER(*) :: fileprefix
2108  INTEGER,INTENT(IN) :: rank
2109!-
2110  CHARACTER(LEN=80) :: usedfileprefix
2111  LOGICAL :: l_dbg
2112  INTEGER :: isize
2113!---------------------------------------------------------------------
2114  CALL ipsldbg (old_status=l_dbg)
2115!---------------------------------------------------------------------
2116  IF ( rank < 1000 ) THEN
2117     isize=MIN(LEN_TRIM(fileprefix),75)
2118     usedfileprefix = fileprefix(1:isize)
2119     usedfileprefix((isize+1):(isize+1))='_'
2120     WRITE(usedfileprefix((isize+2):(isize+5)),'(I4.4)') rank
2121     IF (l_dbg) &
2122          WRITE(ipslout,*) 'Dump getin to file ',usedfileprefix
2123     CALL getin_dump(usedfileprefix)
2124  ENDIF
2125!------------------------
2126END SUBROUTINE getin_dump_para
2127
2128!===
2129SUBROUTINE get_qtyp (k_typ,c_vtyp,i_v,r_v,c_v,l_v)
2130!---------------------------------------------------------------------
2131!- Returns the type of the argument (mutually exclusive)
2132!---------------------------------------------------------------------
2133  IMPLICIT NONE
2134!-
2135  INTEGER,INTENT(OUT) :: k_typ
2136  CHARACTER(LEN=*),INTENT(OUT) :: c_vtyp
2137  INTEGER,DIMENSION(:),OPTIONAL          :: i_v
2138  REAL,DIMENSION(:),OPTIONAL             :: r_v
2139  LOGICAL,DIMENSION(:),OPTIONAL          :: l_v
2140  CHARACTER(LEN=*),DIMENSION(:),OPTIONAL :: c_v
2141!---------------------------------------------------------------------
2142  k_typ = 0
2143  IF (COUNT((/PRESENT(i_v),PRESENT(r_v),PRESENT(c_v),PRESENT(l_v)/)) &
2144 &    /= 1) THEN
2145    CALL ipslerr (3,'get_qtyp', &
2146 &   'Invalid number of optional arguments','(/= 1)',' ')
2147  ENDIF
2148!-
2149  IF     (PRESENT(i_v)) THEN
2150    k_typ = k_i
2151    c_vtyp = 'INTEGER'
2152  ELSEIF (PRESENT(r_v)) THEN
2153    k_typ = k_r
2154    c_vtyp = 'REAL'
2155  ELSEIF (PRESENT(c_v)) THEN
2156    k_typ = k_c
2157    c_vtyp = 'CHARACTER'
2158  ELSEIF (PRESENT(l_v)) THEN
2159    k_typ = k_l
2160    c_vtyp = 'LOGICAL'
2161  ENDIF
2162!----------------------
2163END SUBROUTINE get_qtyp
2164!===
2165SUBROUTINE get_findkey (i_tab,c_key,pos)
2166!---------------------------------------------------------------------
2167!- This subroutine looks for a key in a table
2168!---------------------------------------------------------------------
2169!- INPUT
2170!-   i_tab  : 1 -> search in key_tab(1:nb_keys)%keystr
2171!-            2 -> search in targetlist(1:nb_lines)
2172!-   c_key  : Name of the key we are looking for
2173!- OUTPUT
2174!-   pos    : -1 if key not found, else value in the table
2175!---------------------------------------------------------------------
2176  IMPLICIT NONE
2177!-
2178  INTEGER,INTENT(in) :: i_tab
2179  CHARACTER(LEN=*),INTENT(in) :: c_key
2180  INTEGER,INTENT(out) :: pos
2181!-
2182  INTEGER :: ikey_max,ikey
2183  CHARACTER(LEN=l_n) :: c_q_key
2184!---------------------------------------------------------------------
2185  pos = -1
2186  IF     (i_tab == 1) THEN
2187    ikey_max = nb_keys
2188  ELSEIF (i_tab == 2) THEN
2189    ikey_max = nb_lines
2190  ELSE
2191    ikey_max = 0
2192  ENDIF
2193  IF ( ikey_max > 0 ) THEN
2194    DO ikey=1,ikey_max
2195      IF (i_tab == 1) THEN
2196        c_q_key = key_tab(ikey)%keystr
2197      ELSE
2198        c_q_key = targetlist(ikey)
2199      ENDIF
2200      IF (TRIM(c_q_key) == TRIM(c_key)) THEN
2201        pos = ikey
2202        EXIT
2203      ENDIF
2204    ENDDO
2205  ENDIF
2206!-------------------------
2207END SUBROUTINE get_findkey
2208!===
2209!------------------
2210END MODULE getincom
Note: See TracBrowser for help on using the repository browser.