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

Last change on this file since 5793 was 5616, checked in by acosce, 3 years ago

update size of array "fichier" for ORCHIDEE group (Nicolas Vuichard)

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