New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
getincom.f90 in utils/tools_dev_r12970_AGRIF_CMEMS/DOMAINcfg/src – NEMO

source: utils/tools_dev_r12970_AGRIF_CMEMS/DOMAINcfg/src/getincom.f90 @ 13024

Last change on this file since 13024 was 13024, checked in by rblod, 4 years ago

First version of new nesting tools merged with domaincfg, see ticket #2129

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