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/DOMAINcfg/src – NEMO

source: utils/tools/DOMAINcfg/src/getincom.f90 @ 14931

Last change on this file since 14931 was 14623, checked in by ldebreu, 3 years ago

AGFdomcfg: 1) Update DOMAINcfg to be compliant with the removal of halo cells 2) Update most of the LBC ... subroutines to a recent NEMO 4 version #2638

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