61 CHARACTER(LEN=100),
DIMENSION(max_files),
SAVE ::
filelist
66 CHARACTER(LEN=100),
SAVE,
ALLOCATABLE,
DIMENSION(:) ::
fichier
67 CHARACTER(LEN=l_n),
SAVE,
ALLOCATABLE,
DIMENSION(:) ::
targetlist
71 CHARACTER(LEN=6),
SAVE ::
c_i_fmt =
'(I5.5)'
102 CHARACTER(LEN=l_n) :: keystr
103 INTEGER :: keystatus, keytype, keycompress, &
104 & keyfromfile, keymemstart, keymemlen
109 INTEGER,
SAVE,
ALLOCATABLE,
DIMENSION(:) ::
i_mem
111 REAL,
SAVE,
ALLOCATABLE,
DIMENSION(:) ::
r_mem
113 CHARACTER(LEN=100),
SAVE,
ALLOCATABLE,
DIMENSION(:) ::
c_mem
115 LOGICAL,
SAVE,
ALLOCATABLE,
DIMENSION(:) ::
l_mem
122 SUBROUTINE getinis (target,ret_val)
126 CHARACTER(LEN=*) :: target
129 INTEGER,
DIMENSION(1) :: tmp_ret_val
130 INTEGER :: pos,status=0,fileorig
137 tmp_ret_val(1) = ret_val
141 CALL get_fil (
target,status,fileorig,i_val=tmp_ret_val)
144 & (
target,status,fileorig,1,i_val=tmp_ret_val)
147 CALL get_rdb (pos,1,
target,i_val=tmp_ret_val)
149 ret_val = tmp_ret_val(1)
153 SUBROUTINE getini1d (target,ret_val)
157 CHARACTER(LEN=*) :: target
158 INTEGER,
DIMENSION(:) :: ret_val
160 INTEGER,
DIMENSION(:),
ALLOCATABLE,
SAVE :: tmp_ret_val
161 INTEGER,
SAVE :: tmp_ret_size = 0
162 INTEGER :: pos,size_of_in,status=0,fileorig
169 size_of_in =
SIZE(ret_val)
170 IF (.NOT.
ALLOCATED(tmp_ret_val))
THEN
171 ALLOCATE (tmp_ret_val(size_of_in))
172 ELSE IF (size_of_in > tmp_ret_size)
THEN
173 DEALLOCATE (tmp_ret_val)
174 ALLOCATE (tmp_ret_val(size_of_in))
175 tmp_ret_size = size_of_in
177 tmp_ret_val(1:size_of_in) = ret_val(1:size_of_in)
181 CALL get_fil (
target,status,fileorig,i_val=tmp_ret_val)
184 & (
target,status,fileorig,size_of_in,i_val=tmp_ret_val)
187 CALL get_rdb (pos,size_of_in,
target,i_val=tmp_ret_val)
189 ret_val(1:size_of_in) = tmp_ret_val(1:size_of_in)
193 SUBROUTINE getini2d (target,ret_val)
197 CHARACTER(LEN=*) :: target
198 INTEGER,
DIMENSION(:,:) :: ret_val
200 INTEGER,
DIMENSION(:),
ALLOCATABLE,
SAVE :: tmp_ret_val
201 INTEGER,
SAVE :: tmp_ret_size = 0
202 INTEGER :: pos,size_of_in,size_1,size_2,status=0,fileorig
210 size_of_in =
SIZE(ret_val)
211 size_1 =
SIZE(ret_val,1)
212 size_2 =
SIZE(ret_val,2)
213 IF (.NOT.
ALLOCATED(tmp_ret_val))
THEN
214 ALLOCATE (tmp_ret_val(size_of_in))
215 ELSE IF (size_of_in > tmp_ret_size)
THEN
216 DEALLOCATE (tmp_ret_val)
217 ALLOCATE (tmp_ret_val(size_of_in))
218 tmp_ret_size = size_of_in
225 tmp_ret_val(jl) = ret_val(ji,jj)
231 CALL get_fil (
target,status,fileorig,i_val=tmp_ret_val)
234 & (
target,status,fileorig,size_of_in,i_val=tmp_ret_val)
237 CALL get_rdb (pos,size_of_in,
target,i_val=tmp_ret_val)
244 ret_val(ji,jj) = tmp_ret_val(jl)
252 SUBROUTINE getinrs (target,ret_val)
256 CHARACTER(LEN=*) :: target
259 REAL,
DIMENSION(1) :: tmp_ret_val
260 INTEGER :: pos,status=0,fileorig
267 tmp_ret_val(1) = ret_val
271 CALL get_fil (
target,status,fileorig,r_val=tmp_ret_val)
274 & (
target,status,fileorig,1,r_val=tmp_ret_val)
277 CALL get_rdb (pos,1,
target,r_val=tmp_ret_val)
279 ret_val = tmp_ret_val(1)
283 SUBROUTINE getinr1d (target,ret_val)
287 CHARACTER(LEN=*) :: target
288 REAL,
DIMENSION(:) :: ret_val
290 REAL,
DIMENSION(:),
ALLOCATABLE,
SAVE :: tmp_ret_val
291 INTEGER,
SAVE :: tmp_ret_size = 0
292 INTEGER :: pos,size_of_in,status=0,fileorig
299 size_of_in =
SIZE(ret_val)
300 IF (.NOT.
ALLOCATED(tmp_ret_val))
THEN
301 ALLOCATE (tmp_ret_val(size_of_in))
302 ELSE IF (size_of_in > tmp_ret_size)
THEN
303 DEALLOCATE (tmp_ret_val)
304 ALLOCATE (tmp_ret_val(size_of_in))
305 tmp_ret_size = size_of_in
307 tmp_ret_val(1:size_of_in) = ret_val(1:size_of_in)
311 CALL get_fil (
target,status,fileorig,r_val=tmp_ret_val)
314 & (
target,status,fileorig,size_of_in,r_val=tmp_ret_val)
317 CALL get_rdb (pos,size_of_in,
target,r_val=tmp_ret_val)
319 ret_val(1:size_of_in) = tmp_ret_val(1:size_of_in)
323 SUBROUTINE getinr2d (target,ret_val)
327 CHARACTER(LEN=*) :: target
328 REAL,
DIMENSION(:,:) :: ret_val
330 REAL,
DIMENSION(:),
ALLOCATABLE,
SAVE :: tmp_ret_val
331 INTEGER,
SAVE :: tmp_ret_size = 0
332 INTEGER :: pos,size_of_in,size_1,size_2,status=0,fileorig
340 size_of_in =
SIZE(ret_val)
341 size_1 =
SIZE(ret_val,1)
342 size_2 =
SIZE(ret_val,2)
343 IF (.NOT.
ALLOCATED(tmp_ret_val))
THEN
344 ALLOCATE (tmp_ret_val(size_of_in))
345 ELSE IF (size_of_in > tmp_ret_size)
THEN
346 DEALLOCATE (tmp_ret_val)
347 ALLOCATE (tmp_ret_val(size_of_in))
348 tmp_ret_size = size_of_in
355 tmp_ret_val(jl) = ret_val(ji,jj)
361 CALL get_fil (
target,status,fileorig,r_val=tmp_ret_val)
364 & (
target,status,fileorig,size_of_in,r_val=tmp_ret_val)
367 CALL get_rdb (pos,size_of_in,
target,r_val=tmp_ret_val)
374 ret_val(ji,jj) = tmp_ret_val(jl)
382 SUBROUTINE getincs (target,ret_val)
386 CHARACTER(LEN=*) :: target
387 CHARACTER(LEN=*) :: ret_val
389 CHARACTER(LEN=100),
DIMENSION(1) :: tmp_ret_val
390 INTEGER :: pos,status=0,fileorig
397 tmp_ret_val(1) = ret_val
401 CALL get_fil (
target,status,fileorig,c_val=tmp_ret_val)
404 & (
target,status,fileorig,1,c_val=tmp_ret_val)
407 CALL get_rdb (pos,1,
target,c_val=tmp_ret_val)
409 ret_val = tmp_ret_val(1)
413 SUBROUTINE getinc1d (target,ret_val)
417 CHARACTER(LEN=*) :: target
418 CHARACTER(LEN=*),
DIMENSION(:) :: ret_val
420 CHARACTER(LEN=100),
DIMENSION(:),
ALLOCATABLE,
SAVE :: tmp_ret_val
421 INTEGER,
SAVE :: tmp_ret_size = 0
422 INTEGER :: pos,size_of_in,status=0,fileorig
429 size_of_in =
SIZE(ret_val)
430 IF (.NOT.
ALLOCATED(tmp_ret_val))
THEN
431 ALLOCATE (tmp_ret_val(size_of_in))
432 ELSE IF (size_of_in > tmp_ret_size)
THEN
433 DEALLOCATE (tmp_ret_val)
434 ALLOCATE (tmp_ret_val(size_of_in))
435 tmp_ret_size = size_of_in
437 tmp_ret_val(1:size_of_in) = ret_val(1:size_of_in)
441 CALL get_fil (
target,status,fileorig,c_val=tmp_ret_val)
444 & (
target,status,fileorig,size_of_in,c_val=tmp_ret_val)
447 CALL get_rdb (pos,size_of_in,
target,c_val=tmp_ret_val)
449 ret_val(1:size_of_in) = tmp_ret_val(1:size_of_in)
453 SUBROUTINE getinc2d (target,ret_val)
457 CHARACTER(LEN=*) :: target
458 CHARACTER(LEN=*),
DIMENSION(:,:) :: ret_val
460 CHARACTER(LEN=100),
DIMENSION(:),
ALLOCATABLE,
SAVE :: tmp_ret_val
461 INTEGER,
SAVE :: tmp_ret_size = 0
462 INTEGER :: pos,size_of_in,size_1,size_2,status=0,fileorig
470 size_of_in =
SIZE(ret_val)
471 size_1 =
SIZE(ret_val,1)
472 size_2 =
SIZE(ret_val,2)
473 IF (.NOT.
ALLOCATED(tmp_ret_val))
THEN
474 ALLOCATE (tmp_ret_val(size_of_in))
475 ELSE IF (size_of_in > tmp_ret_size)
THEN
476 DEALLOCATE (tmp_ret_val)
477 ALLOCATE (tmp_ret_val(size_of_in))
478 tmp_ret_size = size_of_in
485 tmp_ret_val(jl) = ret_val(ji,jj)
491 CALL get_fil (
target,status,fileorig,c_val=tmp_ret_val)
494 & (
target,status,fileorig,size_of_in,c_val=tmp_ret_val)
497 CALL get_rdb (pos,size_of_in,
target,c_val=tmp_ret_val)
504 ret_val(ji,jj) = tmp_ret_val(jl)
512 SUBROUTINE getinls (target,ret_val)
516 CHARACTER(LEN=*) :: target
519 LOGICAL,
DIMENSION(1) :: tmp_ret_val
520 INTEGER :: pos,status=0,fileorig
527 tmp_ret_val(1) = ret_val
531 CALL get_fil (
target,status,fileorig,l_val=tmp_ret_val)
534 & (
target,status,fileorig,1,l_val=tmp_ret_val)
537 CALL get_rdb (pos,1,
target,l_val=tmp_ret_val)
539 ret_val = tmp_ret_val(1)
543 SUBROUTINE getinl1d (target,ret_val)
547 CHARACTER(LEN=*) :: target
548 LOGICAL,
DIMENSION(:) :: ret_val
550 LOGICAL,
DIMENSION(:),
ALLOCATABLE,
SAVE :: tmp_ret_val
551 INTEGER,
SAVE :: tmp_ret_size = 0
552 INTEGER :: pos,size_of_in,status=0,fileorig
559 size_of_in =
SIZE(ret_val)
560 IF (.NOT.
ALLOCATED(tmp_ret_val))
THEN
561 ALLOCATE (tmp_ret_val(size_of_in))
562 ELSE IF (size_of_in > tmp_ret_size)
THEN
563 DEALLOCATE (tmp_ret_val)
564 ALLOCATE (tmp_ret_val(size_of_in))
565 tmp_ret_size = size_of_in
567 tmp_ret_val(1:size_of_in) = ret_val(1:size_of_in)
571 CALL get_fil (
target,status,fileorig,l_val=tmp_ret_val)
574 & (
target,status,fileorig,size_of_in,l_val=tmp_ret_val)
577 CALL get_rdb (pos,size_of_in,
target,l_val=tmp_ret_val)
579 ret_val(1:size_of_in) = tmp_ret_val(1:size_of_in)
583 SUBROUTINE getinl2d (target,ret_val)
587 CHARACTER(LEN=*) :: target
588 LOGICAL,
DIMENSION(:,:) :: ret_val
590 LOGICAL,
DIMENSION(:),
ALLOCATABLE,
SAVE :: tmp_ret_val
591 INTEGER,
SAVE :: tmp_ret_size = 0
592 INTEGER :: pos,size_of_in,size_1,size_2,status=0,fileorig
600 size_of_in =
SIZE(ret_val)
601 size_1 =
SIZE(ret_val,1)
602 size_2 =
SIZE(ret_val,2)
603 IF (.NOT.
ALLOCATED(tmp_ret_val))
THEN
604 ALLOCATE (tmp_ret_val(size_of_in))
605 ELSE IF (size_of_in > tmp_ret_size)
THEN
606 DEALLOCATE (tmp_ret_val)
607 ALLOCATE (tmp_ret_val(size_of_in))
608 tmp_ret_size = size_of_in
615 tmp_ret_val(jl) = ret_val(ji,jj)
621 CALL get_fil (
target,status,fileorig,l_val=tmp_ret_val)
624 & (
target,status,fileorig,size_of_in,l_val=tmp_ret_val)
627 CALL get_rdb (pos,size_of_in,
target,l_val=tmp_ret_val)
634 ret_val(ji,jj) = tmp_ret_val(jl)
642 SUBROUTINE get_fil (target,status,fileorig,i_val,r_val,c_val,l_val)
657 CHARACTER(LEN=*) :: target
658 INTEGER,
INTENT(OUT) :: status,fileorig
659 INTEGER,
DIMENSION(:),
OPTIONAL :: i_val
660 REAL,
DIMENSION(:),
OPTIONAL :: r_val
661 LOGICAL,
DIMENSION(:),
OPTIONAL :: l_val
662 CHARACTER(LEN=*),
DIMENSION(:),
OPTIONAL :: c_val
664 INTEGER :: k_typ,nb_to_ret,it,pos,len_str,status_cnt,io_err
665 CHARACTER(LEN=n_d_fmt) :: cnt
666 CHARACTER(LEN=80) :: str_READ,str_READ_lower
667 CHARACTER(LEN=9) :: c_vtyp
668 LOGICAL,
DIMENSION(:),
ALLOCATABLE :: found
669 LOGICAL :: def_beha,compressed
670 CHARACTER(LEN=10) :: c_fmt
673 INTEGER :: ipos_tr,ipos_fl
677 CALL get_qtyp (k_typ,c_vtyp,i_val,r_val,c_val,l_val)
680 nb_to_ret =
SIZE(i_val)
682 nb_to_ret =
SIZE(r_val)
684 nb_to_ret =
SIZE(c_val)
686 nb_to_ret =
SIZE(l_val)
689 &
'Internal error',
'Unknown type of data',
' ')
696 ALLOCATE(found(nb_to_ret))
723 str_read = adjustl(
fichier(pos))
724 str_read_lower = str_read
727 IF ( (trim(str_read_lower) ==
'def') &
728 & .OR.(trim(str_read_lower) ==
'default') )
THEN
732 len_str = len_trim(str_read)
736 WRITE (
unit=c_fmt,fmt=
'("(I",I3.3,")")') len_str
737 READ (
unit=str_read(1:len_str), &
738 & fmt=c_fmt,iostat=io_err) i_val(it)
740 READ (
unit=str_read(1:len_str), &
741 & fmt=*,iostat=io_err) r_val(it)
743 c_val(it) = str_read(1:len_str)
747 ipos_tr = max(index(str_read_lower,
'tru'), &
748 & index(str_read_lower,
'y'))
749 ipos_fl = max(index(str_read_lower,
'fal'), &
750 & index(str_read_lower,
'n'))
751 IF (ipos_tr > 0)
THEN
753 ELSE IF (ipos_fl > 0)
THEN
759 IF (io_err /= 0)
THEN
761 &
'Target '//trim(
target), &
762 &
'is not of '//trim(c_vtyp)//
' type',
' ')
766 IF ( (k_typ ==
k_i).OR.(k_typ ==
k_r) )
THEN
771 IF (
compline(pos) /= nb_to_ret)
THEN
773 &
'For key '//trim(
target)//
' we have a compressed field', &
774 &
'which does not have the right size.', &
775 &
'We will try to fix that.')
777 IF (k_typ ==
k_i)
THEN
779 ELSE IF (k_typ ==
k_r)
THEN
791 IF ( (k_typ ==
k_i).OR.(k_typ ==
k_r) )
THEN
796 IF (.NOT.found(it))
THEN
797 IF (k_typ ==
k_i)
THEN
799 ELSE IF (k_typ ==
k_r)
THEN
810 WRITE(*,*)
'USING DEFAULT BEHAVIOUR FOR ',trim(
target)
814 IF (.NOT.found(it))
THEN
815 status_cnt = status_cnt+1
817 WRITE (
unit=*,fmt=
'(" USING DEFAULTS : ",A)', &
818 & advance=
'NO') trim(
target)
819 IF (nb_to_ret > 1)
THEN
820 WRITE (
unit=*,fmt=
'("__")',advance=
'NO')
825 WRITE (
unit=*,fmt=*)
"=",i_val(it)
827 WRITE (
unit=*,fmt=*)
"=",r_val(it)
829 WRITE (
unit=*,fmt=*)
"=",c_val(it)
831 WRITE (
unit=*,fmt=*)
"=",l_val(it)
833 ELSE IF (status_cnt ==
max_msgs+1)
THEN
834 WRITE (
unit=*,fmt=
'(" USING DEFAULTS ... ",A)')
839 IF (status_cnt == 0)
THEN
841 ELSE IF (status_cnt == nb_to_ret)
THEN
852 SUBROUTINE get_rdb (pos,size_of_in,target,i_val,r_val,c_val,l_val)
858 INTEGER :: pos,size_of_in
859 CHARACTER(LEN=*) :: target
860 INTEGER,
DIMENSION(:),
OPTIONAL :: i_val
861 REAL,
DIMENSION(:),
OPTIONAL :: r_val
862 LOGICAL,
DIMENSION(:),
OPTIONAL :: l_val
863 CHARACTER(LEN=*),
DIMENSION(:),
OPTIONAL :: c_val
865 INTEGER :: k_typ,k_beg,k_end
866 CHARACTER(LEN=9) :: c_vtyp
870 CALL get_qtyp (k_typ,c_vtyp,i_val,r_val,c_val,l_val)
871 IF ( (k_typ /=
k_i).AND.(k_typ /=
k_r) &
872 & .AND.(k_typ /=
k_c).AND.(k_typ /=
k_l) )
THEN
874 &
'Internal error',
'Unknown type of data',
' ')
877 IF (
key_tab(pos)%keytype /= k_typ)
THEN
879 &
'Wrong data type for keyword '//trim(
target), &
880 &
'(NOT '//trim(c_vtyp)//
')',
' ')
883 IF (
key_tab(pos)%keycompress > 0)
THEN
884 IF ( (
key_tab(pos)%keycompress /= size_of_in) &
885 & .OR.(
key_tab(pos)%keymemlen /= 1) )
THEN
887 &
'Wrong compression length',
'for keyword '//trim(
target),
' ')
897 IF (
key_tab(pos)%keymemlen /= size_of_in)
THEN
899 &
'Wrong array length',
'for keyword '//trim(
target),
' ')
901 k_beg =
key_tab(pos)%keymemstart
902 k_end = k_beg+
key_tab(pos)%keymemlen-1
905 i_val(1:size_of_in) =
i_mem(k_beg:k_end)
907 r_val(1:size_of_in) =
r_mem(k_beg:k_end)
909 c_val(1:size_of_in) =
c_mem(k_beg:k_end)
911 l_val(1:size_of_in) =
l_mem(k_beg:k_end)
919 & (
target,status,fileorig,size_of_in, &
920 & i_val,r_val,c_val,l_val)
926 CHARACTER(LEN=*) :: target
927 INTEGER :: status,fileorig,size_of_in
928 INTEGER,
DIMENSION(:),
OPTIONAL :: i_val
929 REAL,
DIMENSION(:),
OPTIONAL :: r_val
930 LOGICAL,
DIMENSION(:),
OPTIONAL :: l_val
931 CHARACTER(LEN=*),
DIMENSION(:),
OPTIONAL :: c_val
934 CHARACTER(LEN=9) :: c_vtyp
935 INTEGER :: k_mempos,k_memsize,k_beg,k_end
940 CALL get_qtyp (k_typ,c_vtyp,i_val,r_val,c_val,l_val)
941 IF ( (k_typ /=
k_i).AND.(k_typ /=
k_r) &
942 & .AND.(k_typ /=
k_c).AND.(k_typ /=
k_l) )
THEN
944 &
'Internal error',
'Unknown type of data',
' ')
955 l_cmp = (minval(i_val) == maxval(i_val)) &
959 l_cmp = (minval(r_val) == maxval(r_val)) &
1015 INTEGER,
SAVE :: allread=0
1016 INTEGER,
SAVE :: current
1018 IF (allread == 0)
THEN
1053 CHARACTER(LEN=100) :: READ_str,NEW_str,last_key,key_str
1054 CHARACTER(LEN=n_d_fmt) :: cnt
1055 CHARACTER(LEN=10) :: c_fmt
1056 INTEGER :: nb_lastkey
1058 INTEGER :: eof,ptn,len_str,i,it,iund,io_err
1059 LOGICAL :: check = .
false.
1066 WRITE(*,*)
'getin_readdef : Open file ',trim(
filelist(current))
1069 OPEN (
unit=22,file=
filelist(current),status=
"OLD",iostat=io_err)
1070 IF (io_err /= 0)
THEN
1071 CALL ipslerr (2,
'getin_readdef', &
1072 &
'Could not open file '//trim(
filelist(current)),
' ',
' ')
1079 len_str = len_trim(read_str)
1080 ptn = index(read_str,
'=')
1084 key_str = trim(adjustl(read_str(1:ptn-1)))
1086 iund = index(key_str,
'__')
1088 WRITE (
unit=c_fmt,fmt=
'("(I",I3.3,")")') &
1089 & len_trim(key_str)-iund-1
1090 READ(
unit=key_str(iund+2:len_trim(key_str)), &
1091 & fmt=c_fmt,iostat=io_err) it
1092 IF ( (io_err == 0).AND.(it > 0) )
THEN
1094 key_str = key_str(1:iund+1)//cnt
1096 CALL ipslerr (3,
'getin_readdef', &
1097 &
'A very strange key has just been found :', &
1098 & trim(key_str),
' ')
1102 new_str = trim(adjustl(read_str(ptn+1:len_str)))
1105 new_str = trim(adjustl(new_str))
1108 &
'--> getin_readdef : ',trim(key_str),
' :: ',trim(new_str)
1115 CALL getin_decrypt (current,key_str,new_str,last_key,nb_lastkey)
1117 ELSE IF (len_str > 0)
THEN
1120 IF (nb_lastkey > 0)
THEN
1121 iund = index(last_key,
'__')
1124 key_str = last_key(1:iund-1)
1126 IF (nb_lastkey /= 1)
THEN
1127 CALL ipslerr (3,
'getin_readdef', &
1128 &
'We can not have a scalar keyword', &
1129 &
'and a vector content',
' ')
1134 & last_key(1:min(len_trim(last_key),
l_n-
n_d_fmt-2))//
'__'//cnt
1135 key_str = last_key(1:len_trim(last_key))
1139 new_str = trim(adjustl(read_str(1:len_str)))
1140 CALL getin_decrypt (current,key_str,new_str,last_key,nb_lastkey)
1145 WRITE(*,*)
'getin_readdef : Have found an emtpy line '
1153 OPEN (
unit=22,file=
'run.def.test')
1164 SUBROUTINE getin_decrypt(current,key_str,NEW_str,last_key,nb_lastkey)
1174 INTEGER :: current,nb_lastkey
1175 CHARACTER(LEN=*) :: key_str,NEW_str,last_key
1179 INTEGER :: len_str,blk,nbve,starpos
1180 CHARACTER(LEN=100) :: tmp_str,new_key,mult
1181 CHARACTER(LEN=n_d_fmt) :: cnt
1182 CHARACTER(LEN=10) :: c_fmt
1184 len_str = len_trim(new_str)
1185 blk = index(new_str(1:len_str),
' ')
1186 tmp_str = new_str(1:len_str)
1191 IF (index(key_str,
'INCLUDEDEF') > 0)
THEN
1194 CALL ipslerr (3,
'getin_decrypt', &
1195 &
'Too many files to include',
' ',
' ')
1201 tmp_str = trim(adjustl(tmp_str(blk+1:len_trim(tmp_str))))
1202 blk = index(tmp_str(1:len_trim(tmp_str)),
' ')
1206 CALL ipslerr (3,
'getin_decrypt', &
1207 &
'Too many files to include',
' ',
' ')
1213 last_key =
'INCLUDEDEF'
1227 starpos = index(new_str(1:len_str),
'*')
1228 IF ( (starpos > 0).AND.(tmp_str(1:1) /=
'"') &
1229 & .AND.(tmp_str(1:1) /=
"'") )
THEN
1231 IF (index(key_str(1:len_trim(key_str)),
'__') > 0)
THEN
1232 CALL ipslerr (3,
'getin_decrypt', &
1233 &
'We can not have a compressed field of values', &
1234 &
'in a vector notation (TARGET__n).', &
1235 &
'The key at fault : '//trim(key_str))
1240 mult = trim(adjustl(new_str(1:starpos-1)))
1242 new_str = trim(adjustl(new_str(starpos+1:len_str)))
1243 len_str = len_trim(new_str)
1244 blk = index(new_str(1:len_str),
' ')
1246 CALL ipslerr (2,
'getin_decrypt', &
1247 &
'This is a strange behavior',
'you could report',
' ')
1249 WRITE (
unit=c_fmt,fmt=
'("(I",I5.5,")")') len_trim(mult)
1261 & .OR.(tmp_str(1:1) ==
'"') &
1262 & .OR.(tmp_str(1:1) ==
"'") )
THEN
1264 IF (nb_lastkey == 0)
THEN
1268 last_key = key_str(1:min(len_trim(key_str),
l_n))
1275 & key_str(1:min(len_trim(key_str),
l_n-
n_d_fmt-2))//
'__'//cnt
1277 & key_str(1:min(len_trim(key_str),
l_n-
n_d_fmt-2))//
'__'//cnt
1278 nb_lastkey = nb_lastkey+1
1291 IF (index(trim(key_str),
'__') > 0)
THEN
1292 CALL ipslerr (3,
'getin_decrypt', &
1293 &
'We have found a mixed vector notation (TARGET__n).', &
1294 &
'The key at fault : '//trim(key_str),
' ')
1307 & key_str(1:min(len_trim(key_str),
l_n-
n_d_fmt-2))//
'__'//cnt
1311 tmp_str = trim(adjustl(tmp_str(blk+1:len_trim(tmp_str))))
1312 blk = index(trim(tmp_str),
' ')
1327 & key_str(1:min(len_trim(key_str),
l_n-
n_d_fmt-2))//
'__'//cnt
1332 & key_str(1:min(len_trim(key_str),
l_n-
n_d_fmt-2))//
'__'//cnt
1349 INTEGER :: line,n_k,k
1364 WRITE(*,*)
'COUNT : ',n_k
1366 &
'getin_checkcohe : Found a problem on key ',trim(
targetlist(line))
1368 &
'getin_checkcohe : The following values were encoutered :'
1374 &
'getin_checkcohe : We will keep only the last value'
1387 INTEGER :: unit,eof,nb_lastkey
1388 CHARACTER(LEN=100) :: dummy
1389 CHARACTER(LEN=100) :: out_string
1390 CHARACTER(LEN=1) :: first
1396 DO WHILE (first ==
"#")
1397 READ (unit=unit,fmt=
'(A)',
err=9998,end=7778) dummy
1398 dummy = trim(adjustl(dummy))
1400 IF (first ==
"#")
THEN
1409 CALL ipslerr (3,
'getin_skipafew',
'Error while reading file',
' ',
' ')
1422 TYPE(
t_key),
ALLOCATABLE,
DIMENSION(:) :: tmp_key_tab
1423 CHARACTER(LEN=100),
ALLOCATABLE :: tmp_str(:)
1426 CHARACTER(LEN=20) :: c_tmp
1435 CALL ipslerr (3,
'getin_allockeys', &
1436 &
'Can not allocate key_tab', &
1437 &
'to size '//trim(adjustl(c_tmp)),
' ')
1451 CALL ipslerr (3,
'getin_allockeys', &
1452 &
'Can not allocate tmp_key_tab', &
1453 &
'to size '//trim(adjustl(c_tmp)),
' ')
1460 CALL ipslerr (3,
'getin_allockeys', &
1461 &
'Can not allocate key_tab', &
1462 &
'to size '//trim(adjustl(c_tmp)),
' ')
1466 DEALLOCATE(tmp_key_tab)
1481 INTEGER ::
type,len_wanted
1483 INTEGER,
ALLOCATABLE :: tmp_int(:)
1484 REAL,
ALLOCATABLE :: tmp_real(:)
1485 CHARACTER(LEN=100),
ALLOCATABLE :: tmp_char(:)
1486 LOGICAL,
ALLOCATABLE :: tmp_logic(:)
1488 CHARACTER(LEN=20) :: c_tmp
1496 CALL ipslerr (3,
'getin_allocmem', &
1497 &
'Unable to allocate db-memory', &
1498 &
'i_mem to size '//trim(adjustl(c_tmp)),
' ')
1505 CALL ipslerr (3,
'getin_allocmem', &
1506 &
'Unable to allocate tmp_int', &
1507 &
'to size '//trim(adjustl(c_tmp)),
' ')
1514 CALL ipslerr (3,
'getin_allocmem', &
1515 &
'Unable to re-allocate db-memory', &
1516 &
'i_mem to size '//trim(adjustl(c_tmp)),
' ')
1527 CALL ipslerr (3,
'getin_allocmem', &
1528 &
'Unable to allocate db-memory', &
1529 &
'r_mem to size '//trim(adjustl(c_tmp)),
' ')
1536 CALL ipslerr (3,
'getin_allocmem', &
1537 &
'Unable to allocate tmp_real', &
1538 &
'to size '//trim(adjustl(c_tmp)),
' ')
1545 CALL ipslerr (3,
'getin_allocmem', &
1546 &
'Unable to re-allocate db-memory', &
1547 &
'r_mem to size '//trim(adjustl(c_tmp)),
' ')
1551 DEALLOCATE(tmp_real)
1558 CALL ipslerr (3,
'getin_allocmem', &
1559 &
'Unable to allocate db-memory', &
1560 &
'c_mem to size '//trim(adjustl(c_tmp)),
' ')
1567 CALL ipslerr (3,
'getin_allocmem', &
1568 &
'Unable to allocate tmp_char', &
1569 &
'to size '//trim(adjustl(c_tmp)),
' ')
1576 CALL ipslerr (3,
'getin_allocmem', &
1577 &
'Unable to re-allocate db-memory', &
1578 &
'c_mem to size '//trim(adjustl(c_tmp)),
' ')
1582 DEALLOCATE(tmp_char)
1589 CALL ipslerr (3,
'getin_allocmem', &
1590 &
'Unable to allocate db-memory', &
1591 &
'l_mem to size '//trim(adjustl(c_tmp)),
' ')
1598 CALL ipslerr (3,
'getin_allocmem', &
1599 &
'Unable to allocate tmp_logic', &
1600 &
'to size '//trim(adjustl(c_tmp)),
' ')
1607 CALL ipslerr (3,
'getin_allocmem', &
1608 &
'Unable to re-allocate db-memory', &
1609 &
'l_mem to size '//trim(adjustl(c_tmp)),
' ')
1613 DEALLOCATE(tmp_logic)
1616 CALL ipslerr (3,
'getin_allocmem',
'Unknown type of data',
' ',
' ')
1627 CHARACTER(LEN=100),
ALLOCATABLE :: tmp_fic(:)
1628 CHARACTER(LEN=l_n),
ALLOCATABLE :: tmp_tgl(:)
1629 INTEGER,
ALLOCATABLE :: tmp_int(:)
1632 CHARACTER(LEN=20) :: c_tmp1,c_tmp2
1641 CALL ipslerr (3,
'getin_alloctxt', &
1642 &
'Can not allocate fichier', &
1643 &
'to size '//trim(adjustl(c_tmp1)),
' ')
1648 CALL ipslerr (3,
'getin_alloctxt', &
1649 &
'Can not allocate targetlist', &
1650 &
'to size '//trim(adjustl(c_tmp1)),
' ')
1655 CALL ipslerr (3,
'getin_alloctxt', &
1656 &
'Can not allocate fromfile', &
1657 &
'to size '//trim(adjustl(c_tmp1)),
' ')
1662 CALL ipslerr (3,
'getin_alloctxt', &
1663 &
'Can not allocate compline', &
1664 &
'to size '//trim(adjustl(c_tmp1)),
' ')
1678 CALL ipslerr (3,
'getin_alloctxt', &
1679 &
'Can not allocate tmp_fic', &
1680 &
'to size '//trim(adjustl(c_tmp1)),
' ')
1686 CALL ipslerr (3,
'getin_alloctxt', &
1687 &
'Can not allocate fichier', &
1688 &
'to size '//trim(adjustl(c_tmp2)),
' ')
1695 CALL ipslerr (3,
'getin_alloctxt', &
1696 &
'Can not allocate tmp_tgl', &
1697 &
'to size '//trim(adjustl(c_tmp1)),
' ')
1703 CALL ipslerr (3,
'getin_alloctxt', &
1704 &
'Can not allocate targetlist', &
1705 &
'to size '//trim(adjustl(c_tmp2)),
' ')
1712 CALL ipslerr (3,
'getin_alloctxt', &
1713 &
'Can not allocate tmp_int', &
1714 &
'to size '//trim(adjustl(c_tmp1)),
' ')
1720 CALL ipslerr (3,
'getin_alloctxt', &
1721 &
'Can not allocate fromfile', &
1722 &
'to size '//trim(adjustl(c_tmp2)),
' ')
1730 CALL ipslerr (3,
'getin_alloctxt', &
1731 &
'Can not allocate compline', &
1732 &
'to size '//trim(adjustl(c_tmp2)),
' ')
1748 CHARACTER(*),
OPTIONAL :: fileprefix
1750 CHARACTER(LEN=80) :: usedfileprefix
1751 INTEGER :: ikey,if,iff,iv
1752 CHARACTER(LEN=20) :: c_tmp
1753 CHARACTER(LEN=100) :: tmp_str,used_filename
1754 LOGICAL :: check = .
false.
1756 IF (
PRESENT(fileprefix))
THEN
1757 usedfileprefix = fileprefix(1:min(len_trim(fileprefix),80))
1759 usedfileprefix =
"used"
1764 used_filename = trim(usedfileprefix)//
'_'//trim(
filelist(if))
1767 &
'GETIN_DUMP : opens file : ',trim(used_filename),
' if = ',
if
1768 WRITE(*,*)
'GETIN_DUMP : NUMBER OF KEYS : ',
nb_keys
1770 OPEN (
unit=22,file=used_filename)
1774 IF ( (
if == 1).AND.(
nbfiles > 1) )
THEN
1776 WRITE(22,*)
'# This file is linked to the following files :'
1779 WRITE(22,*)
'INCLUDEDEF = ',trim(
filelist(iff))
1787 IF (
key_tab(ikey)%keyfromfile == if)
THEN
1791 SELECT CASE (
key_tab(ikey)%keystatus)
1793 WRITE(22,*)
'# Values of ', &
1794 & trim(
key_tab(ikey)%keystr),
' comes from the run.def.'
1796 WRITE(22,*)
'# Values of ', &
1797 & trim(
key_tab(ikey)%keystr),
' are all defaults.'
1799 WRITE(22,*)
'# Values of ', &
1800 & trim(
key_tab(ikey)%keystr), &
1801 &
' are a mix of run.def and defaults.'
1803 WRITE(22,*)
'# Dont know from where the value of ', &
1804 & trim(
key_tab(ikey)%keystr),
' comes.'
1809 SELECT CASE (
key_tab(ikey)%keytype)
1811 IF (
key_tab(ikey)%keymemlen == 1)
THEN
1812 IF (
key_tab(ikey)%keycompress < 0)
THEN
1814 & trim(
key_tab(ikey)%keystr), &
1818 & trim(
key_tab(ikey)%keystr), &
1819 &
' = ',
key_tab(ikey)%keycompress, &
1823 DO iv=0,
key_tab(ikey)%keymemlen-1
1826 & trim(
key_tab(ikey)%keystr), &
1827 &
'__',trim(adjustl(c_tmp)), &
1832 IF (
key_tab(ikey)%keymemlen == 1)
THEN
1833 IF (
key_tab(ikey)%keycompress < 0)
THEN
1835 & trim(
key_tab(ikey)%keystr), &
1839 & trim(
key_tab(ikey)%keystr), &
1840 &
' = ',
key_tab(ikey)%keycompress, &
1844 DO iv=0,
key_tab(ikey)%keymemlen-1
1847 & trim(
key_tab(ikey)%keystr),
'__',trim(adjustl(c_tmp)), &
1852 IF (
key_tab(ikey)%keymemlen == 1)
THEN
1854 WRITE(22,*) trim(
key_tab(ikey)%keystr), &
1855 &
' = ',trim(tmp_str)
1857 DO iv=0,
key_tab(ikey)%keymemlen-1
1861 & trim(
key_tab(ikey)%keystr), &
1862 &
'__',trim(adjustl(c_tmp)), &
1863 &
' = ',trim(tmp_str)
1867 IF (
key_tab(ikey)%keymemlen == 1)
THEN
1869 WRITE(22,*) trim(
key_tab(ikey)%keystr),
' = TRUE '
1871 WRITE(22,*) trim(
key_tab(ikey)%keystr),
' = FALSE '
1874 DO iv=0,
key_tab(ikey)%keymemlen-1
1877 WRITE(22,*) trim(
key_tab(ikey)%keystr),
'__', &
1878 & trim(adjustl(c_tmp)),
' = TRUE '
1880 WRITE(22,*) trim(
key_tab(ikey)%keystr),
'__', &
1881 & trim(adjustl(c_tmp)),
' = FALSE '
1886 CALL ipslerr (3,
'getin_dump', &
1887 &
'Unknown type for variable '//trim(
key_tab(ikey)%keystr), &
1899 SUBROUTINE get_qtyp (k_typ,c_vtyp,i_v,r_v,c_v,l_v)
1905 INTEGER,
INTENT(OUT) :: k_typ
1906 CHARACTER(LEN=*),
INTENT(OUT) :: c_vtyp
1907 INTEGER,
DIMENSION(:),
OPTIONAL :: i_v
1908 REAL,
DIMENSION(:),
OPTIONAL :: r_v
1909 LOGICAL,
DIMENSION(:),
OPTIONAL :: l_v
1910 CHARACTER(LEN=*),
DIMENSION(:),
OPTIONAL :: c_v
1913 IF (count((/
PRESENT(i_v),
PRESENT(r_v),
PRESENT(c_v),
PRESENT(l_v)/)) &
1916 &
'Invalid number of optional arguments',
'(/= 1)',
' ')
1919 IF (
PRESENT(i_v))
THEN
1922 ELSEIF (
PRESENT(r_v))
THEN
1925 ELSEIF (
PRESENT(c_v))
THEN
1927 c_vtyp =
'CHARACTER'
1928 ELSEIF (
PRESENT(l_v))
THEN
1948 INTEGER,
INTENT(in) :: i_tab
1949 CHARACTER(LEN=*),
INTENT(in) :: c_key
1950 INTEGER,
INTENT(out) :: pos
1952 INTEGER :: ikey_max,ikey
1953 CHARACTER(LEN=l_n) :: c_q_key
1956 IF (i_tab == 1)
THEN
1958 ELSEIF (i_tab == 2)
THEN
1963 IF ( ikey_max > 0 )
THEN
1965 IF (i_tab == 1)
THEN
1966 c_q_key =
key_tab(ikey)%keystr
1970 IF (trim(c_q_key) == trim(c_key))
THEN
subroutine getin_alloctxt()
integer, parameter i_txtslab
subroutine getinr1d(target, ret_val)
subroutine getinis(target, ret_val)
subroutine getin_checkcohe()
character(len=100), dimension(max_files), save filelist
integer, parameter memslabs
integer, dimension(:), allocatable, save compline
character(len=l_n), dimension(:), allocatable, save targetlist
subroutine getinls(target, ret_val)
character(len=100), dimension(:), allocatable, save c_mem
subroutine getin_skipafew(unit, out_string, eof, nb_lastkey)
subroutine getinl1d(target, ret_val)
subroutine getinrs(target, ret_val)
!$Header!integer nvarmx s s s fichier
subroutine get_qtyp(k_typ, c_vtyp, i_v, r_v, c_v, l_v)
integer, parameter max_files
subroutine getini1d(target, ret_val)
integer, dimension(:), allocatable, save fromfile
subroutine get_rdb(pos, size_of_in, target, i_val, r_val, c_val, l_val)
subroutine err(ierr, typ, nam)
type(t_key), dimension(:), allocatable, save key_tab
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
integer, parameter compress_lim
subroutine getinc2d(target, ret_val)
character(len=6), save c_i_fmt
logical, dimension(:), allocatable, save l_mem
integer, parameter n_d_fmt
subroutine getin_decrypt(current, key_str, NEW_str, last_key, nb_lastkey)
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
subroutine get_fil(target, status, fileorig, i_val, r_val, c_val, l_val)
subroutine getincs(target, ret_val)
subroutine getin_readdef(current)
subroutine, public getin_dump(fileprefix)
real, dimension(:), allocatable, save r_mem
integer, dimension(:), allocatable, save i_mem
subroutine getini2d(target, ret_val)
subroutine strlowercase(str)
subroutine get_findkey(i_tab, c_key, pos)
subroutine, public ipslerr(plev, pcname, pstr1, pstr2, pstr3)
subroutine getinr2d(target, ret_val)
subroutine getinl2d(target, ret_val)
subroutine get_wdb(target, status, fileorig, size_of_in, i_val, r_val, c_val, l_val)
subroutine getinc1d(target, ret_val)
!$Header!integer nvarmx s s unit
subroutine getin_allockeys()
subroutine getin_allocmem(type, len_wanted)
INTERFACE subroutine only
integer, parameter max_msgs