Changeset 963 for IOIPSL/trunk/src/getincom.f90
- Timestamp:
- 03/31/10 17:26:11 (15 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
IOIPSL/trunk/src/getincom.f90
r536 r963 13 13 !- 14 14 PRIVATE 15 PUBLIC :: getin, getin_dump 15 PUBLIC :: getin_name, getin, getin_dump 16 !- 17 !!-------------------------------------------------------------------- 18 !! The "getin_name" routine allows the user to change the name 19 !! of the definition file in which the data will be read. 20 !! ("run.def" by default) 21 !! 22 !! SUBROUTINE getin_name (file_name) 23 !! 24 !! OPTIONAL INPUT argument 25 !! 26 !! (C) file_name : the name of the file 27 !! in which the data will be read 28 !!-------------------------------------------------------------------- 29 !- 16 30 !- 17 31 INTERFACE getin … … 19 33 !! The "getin" routines get a variable. 20 34 !! We first check if we find it in the database 21 !! and if not we get it from the run.deffile.35 !! and if not we get it from the definition file. 22 36 !! 23 37 !! SUBROUTINE getin (target,ret_val) … … 41 55 !!-------------------------------------------------------------------- 42 56 !! The "getin_dump" routine will dump the content of the database 43 !! into a file which has the same format as the run.deffile.57 !! into a file which has the same format as the definition file. 44 58 !! The idea is that the user can see which parameters were used 45 59 !! and re-use the file for another run. … … 57 71 INTEGER,SAVE :: nbfiles 58 72 !- 73 INTEGER,SAVE :: allread=0 74 CHARACTER(LEN=100),SAVE :: def_file = 'run.def' 75 !- 59 76 INTEGER,PARAMETER :: i_txtslab=1000,l_n=30 60 77 INTEGER,SAVE :: nb_lines,i_txtsize=0 … … 78 95 !- 79 96 ! keystatus definition 80 ! keystatus = 1 : Value comes from run.def97 ! keystatus = 1 : Value comes from the file defined by 'def_file' 81 98 ! keystatus = 2 : Default value is used 82 99 ! keystatus = 3 : Some vector elements were taken from default … … 112 129 !- 113 130 CONTAINS 131 !- 132 !=== DEFINITION FILE NAME INTERFACE 133 !- 134 SUBROUTINE getin_name (cname) 135 !--------------------------------------------------------------------- 136 IMPLICIT NONE 137 !- 138 CHARACTER(LEN=*) :: cname 139 !--------------------------------------------------------------------- 140 IF (allread == 0) THEN 141 def_file = ADJUSTL(cname) 142 ELSE 143 CALL ipslerr (3,'getin_name', & 144 & 'The name of the database file (any_name.def)', & 145 & 'must be changed *before* any attempt','to read the database.') 146 ENDIF 147 !------------------------ 148 END SUBROUTINE getin_name 114 149 !- 115 150 !=== INTEGER INTERFACE … … 1008 1043 IMPLICIT NONE 1009 1044 !- 1010 INTEGER,SAVE :: allread=01011 1045 INTEGER,SAVE :: current 1012 1046 !--------------------------------------------------------------------- … … 1021 1055 !-- Start with reading the files 1022 1056 nbfiles = 1 1023 filelist(1) = 'run.def'1057 filelist(1) = TRIM(def_file) 1024 1058 current = 1 1025 1059 !-- … … 1146 1180 !- 1147 1181 IF (check) THEN 1148 OPEN (UNIT=22,file= 'run.def.test')1182 OPEN (UNIT=22,file=TRIM(def_file)//'.test') 1149 1183 DO i=1,nb_lines 1150 1184 WRITE(UNIT=22,FMT=*) targetlist(i)," : ",fichier(i) … … 1416 1450 !- 1417 1451 TYPE(t_key),ALLOCATABLE,DIMENSION(:) :: tmp_key_tab 1418 CHARACTER(LEN=100),ALLOCATABLE :: tmp_str(:)1419 1452 !- 1420 1453 INTEGER :: ier … … 1787 1820 CASE(1) 1788 1821 WRITE(22,*) '# Values of ', & 1789 & TRIM(key_tab(ikey)%keystr),' comes from the run.def.'1822 & TRIM(key_tab(ikey)%keystr),' comes from ',TRIM(def_file) 1790 1823 CASE(2) 1791 1824 WRITE(22,*) '# Values of ', & … … 1794 1827 WRITE(22,*) '# Values of ', & 1795 1828 & TRIM(key_tab(ikey)%keystr), & 1796 & ' are a mix of run.defand defaults.'1829 & ' are a mix of ',TRIM(def_file),' and defaults.' 1797 1830 CASE DEFAULT 1798 1831 WRITE(22,*) '# Dont know from where the value of ', &
Note: See TracChangeset
for help on using the changeset viewer.