Millepede-II  V04-00-00_preview
 All Classes Files Functions Variables Enumerator Pages
mpmod.f90
Go to the documentation of this file.
1 
3 
8 
9 MODULE mpmod
10  USE mpdef
11  IMPLICIT NONE
12  SAVE
13  ! steering parameters
14  INTEGER :: ictest=0 !< test mode '-t'
15  INTEGER :: metsol=0 !< solution method (1: inversion, 2: diagonalization, 3: \ref minres "MINRES")
16  INTEGER :: matsto=2 !< (global) matrix storage mode (1: full, 2: sparse)
17  INTEGER :: mprint=1 !< print flag (0: minimal, 1: normal, >1: more)
18  INTEGER :: mdebug=0 !< debug flag (number of records to print)
19  INTEGER :: mdebg2=10 !< number of measurements for record debug printout
20  INTEGER :: mreqen=10 !< required number of entries (for variable global parameter)
21  INTEGER :: mitera=1 !< number of iterations
22  INTEGER :: nloopn=0 !< number of data reading, fitting loops
23  INTEGER :: mbandw=0 !< band width of preconditioner matrix
24  INTEGER :: lunkno=0 !< flag for unkown keywords
25  INTEGER :: lhuber=0 !< Huber down-weighting flag
26  REAL :: chicut=0.0 !< cut in terms of 3-sigma cut, first iteration
27  REAL :: chirem=0.0 !< cut in terms of 3-sigma cut, other iterations, approaching 1.
28  REAL :: chhuge=50.0 !< cut in terms of 3-sigma for unreasonable data, all iterations
29  INTEGER :: nrecpr=0 !< record number with printout
30  INTEGER :: nrecp2=0 !< record number with printout
31  INTEGER :: nrec1 =0 !< record number with largest residual
32  INTEGER :: nrec2 =0 !< record number with largest chi^2/Ndf
33  REAL :: value1=0.0!< largest residual
34  REAL :: value2=0.0!< largest chi^2/Ndf
35  REAL :: dwcut=0.0 !< down-weight fraction cut
36  INTEGER :: isubit=0 !< subito flag '-s'
37  REAL :: wolfc1=0.0!< C_1 of strong Wolfe condition
38  REAL :: wolfc2=0.0!< C_2 of strong Wolfe condition
39  DOUBLE PRECISION :: mrestl=1.0D-06 !< tolerance criterion for MINRES
40  INTEGER :: nofeas=0 !< flag for skipping making parameters feasible
41  INTEGER :: nhistp=0 !< flag for histogram printout
42  REAL :: delfun=0.0!< expected function change
43  REAL :: actfun=0.0!< actual function change
44  REAL :: angras=0.0!< angle between gradient and search direction
45  INTEGER :: iterat=0 !< iterations in solution
46  INTEGER :: nregul=0 !< regularization flag
47  REAL :: regula=1.0!< regularization parameter, add regula * norm(global par.) to objective function
48  REAL :: regpre=0.0!< default presigma
49  INTEGER :: matrit=0 !< matrix calculation up to iteration MATRIT
50  INTEGER :: icalcm=0 !< calculation mode (for \ref xloopn "XLOOPN") , >0: calculate matrix
51  INTEGER :: numbit=1 !< number of bits for pair counters
52  INTEGER :: nbndr =0 !< number of records with bordered band matrix for local fit
53  INTEGER :: nbdrx =0 !< max border size for local fit
54  INTEGER :: nbndx =0 !< max band width for local fit
55  INTEGER :: nrecer=0 !< record with error (rank deficit or Not-a-Number) for printout
56  INTEGER :: nrec3 =maxi4 !< (1.) record number with error
57  INTEGER :: mreqpe=1 !< min number of pair entries
58  INTEGER :: mhispe=0 !< upper bound for pair entry histogrammimg
59  INTEGER :: msngpe=0 !< upper bound for pair entry single precision storage
60  INTEGER :: mcmprs=0 !< compression flag for sparsity (column indices)
61  INTEGER :: mthrd =1 !< number of (OpenMP) threads
62  INTEGER :: mxrec =0 !< max number of records
63  INTEGER :: matmon=0 !< record interval for monitoring of (sparse) matrix construction
64  INTEGER :: lfitnp=maxi4 !< local fit: number of iteration to calculate pulls
65  INTEGER :: lfitbb=1 !< local fit: check for bordered band matrix (if >0)
66  INTEGER :: mnrsel=0 !< number of MINRES error labels in LBMNRS (calc err, corr with SOLGLO)
67  INTEGER :: ncache=-1 !< buffer size for caching (default 100MB per thread)
68  REAL, DIMENSION(3) :: fcache = (/ 0.8, 0., 0. /) !< read cache, average fill level; write cache; dynamic size
69  INTEGER :: mthrdr=1 !< number of threads for reading binary files
70  INTEGER :: mnrsit=0 !< total number of MINRES internal iterations
71  INTEGER :: iforce=0 !< switch to SUBITO for (global) rank defects if zero
72  INTEGER :: igcorr=0 !< flag for output of global correlations for inversion, =0: none
73  INTEGER :: memdbg=0 !< debug flag for memory management
74  REAL :: prange=0.0!< range (-PRANGE..PRANGE) for histograms of pulls, norm. residuals
75  ! variables
76  INTEGER :: lunlog !< unit for logfile
77  INTEGER :: lvllog !< log level
78  INTEGER :: ntgb !< total number of global parameters
79  INTEGER :: nvgb !< number of variable global parameters
80  INTEGER :: nagb !< number of fit parameters (global par. + Lagrange mult.)
81  INTEGER :: ncgb !< number of constraints
82  INTEGER :: nagbn !< max number of global paramters per record
83  INTEGER :: nalcn !< max number of local paramters per record
84  INTEGER :: naeqn !< max number of equations (measurements) per record
85  INTEGER :: nrec !< (current) record number
86  REAL :: dflim !< convergence limit
87  INTEGER, DIMENSION(0:3) :: nrejec !< rejected events
88  REAL, DIMENSION(0:8) :: times !< cpu time counters
89  REAL :: stepl !< step length (line search)
90  CHARACTER (LEN=74) :: textl !< name of current MP 'module' (step)
91  LOGICAL :: newite !< flag for new iteration
92  INTEGER :: ndfsum !< sum(ndf)
93  INTEGER :: iitera !< MINRES iterations
94  INTEGER :: istopa !< MINRES istop (convergence)
95  INTEGER :: lsinfo !< linesearch: returned information
96  REAL :: rstart !< cpu start time for solution iterations
97  REAL :: deltim !< cpu time difference
98  INTEGER :: npresg !< number of pre-sigmas
99  INTEGER :: nrecal !< number of records
100  INTEGER :: nmiss1 !< rank deficit for constraints
101  INTEGER :: lcalcm !< last calclation mode
102  INTEGER :: nspc !< number of precision for sparse global matrix (1=D, 2=D+F)
103  INTEGER :: nencdb !< encoding info (number bits for column counter)
104  INTEGER, DIMENSION(100) :: lbmnrs !< MINRES error labels
105  DOUBLE PRECISION :: fvalue !< function value (chi2 sum) solution
106  DOUBLE PRECISION :: flines !< function value line search
107  DOUBLE PRECISION :: sumndf !< weighted sum(ndf)
108  ! each loop
109  INTEGER :: numReadbuffer !< number of buffers (records) in (read) block
110  INTEGER :: numBlocks !< number of (read) blocks
111  INTEGER :: sumRecords !< sum of records
112  INTEGER :: skippedRecords !< number of skipped records (buffer too small)
113  INTEGER :: minRecordsInBlock !< min. records in block
114  INTEGER :: maxRecordsInBlock !< max. records in block
115  ! accurate sumation
116  INTEGER, PARAMETER::nexp20=1048576 ! 2**20
117  DOUBLE PRECISION::accurateDsum=0.0D0 !< fractional part of sum
118  INTEGER::accurateNsum=0 !< sum mod 2**20
119  INTEGER::accurateNexp=0 !< sum / 2**20
120  INTEGER :: lenGlobalVec !< length of global vector 'b' (A*x=b)
121  ! dynamic arrays
122  !======================================================
123  ! global parameters
124  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: globalParameter !< global parameters (start values + sum(x_i))
125  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: globalParCopy !< copy of global parameters
126  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: globalCorrections !< correction x_i (from A*x_i=b_i in iteration i)
127  REAL, DIMENSION(:), ALLOCATABLE :: globalParStart !< start value for global parameters
128  REAL, DIMENSION(:), ALLOCATABLE :: globalParPreSigma !< pre-sigma for global parameters
129  REAL, DIMENSION(:), ALLOCATABLE :: globalParPreWeight !< weight from pre-sigma
130  ! global matrix, vector
131  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: globalMatD !< global matrix 'A' (double, full or sparse)
132  REAL, DIMENSION(:), ALLOCATABLE :: globalMatF !< global matrix 'A' (float part for compressed sparse)
133  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: globalVector !< global vector 'x' (in A*x=b)
134  ! preconditioning
135  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: matPreCond !< preconditioner (band) matrix
136  INTEGER, DIMENSION(:), ALLOCATABLE :: indPreCond !< preconditioner pointer array
137  ! auxiliary vectors
138  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: workspaceD !< (general) workspace (D)
139  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: workspaceLinesearch !< workspace line search
140  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: workspaceDiagonalization !< workspace diag.
141  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: workspaceEigenValues !< workspace eigen values
142  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: workspaceEigenVectors !< workspace eigen vectors
143  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: workspaceMinres !< workspace MINRES
144  INTEGER, DIMENSION(:), ALLOCATABLE :: workspaceI !< (general) workspace (I)
145  ! constraint matrix, residuals
146  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: matConsProduct !< product matrix of constraints
147  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: vecConsResiduals !< residuals of constraints
148  ! global parameter mapping
149  INTEGER, DIMENSION(:,:), ALLOCATABLE :: globalParLabelIndex !< global parameters label, total -> var. index
150  INTEGER, DIMENSION(:), ALLOCATABLE :: globalParHashTable !< global parameters hash table
151  INTEGER, DIMENSION(:), ALLOCATABLE :: globalParVarToTotal !< global parameters variable -> total index
152  INTEGER, DIMENSION(-7:0) :: globalParHeader = 0 !< global parameters (mapping) header
153  !!
154  !! 0: length of labels/indices; \n
155  !! -1: number of stored items; \n
156  !! -2: =0 during build-up; \n
157  !! -3: next number; \n
158  !! -4: (largest) prime number (< length); \n
159  !! -5: number of overflows; \n
160  !! -6: nr of variable parameters; \n
161  !! -7: call counter for build-up;
162 
163  ! row information for sparse matrix
164  INTEGER, DIMENSION(:), ALLOCATABLE :: sparseMatrixCompression !< compression info (per row)
165  INTEGER, DIMENSION(:), ALLOCATABLE :: sparseMatrixColumns !< (compressed) list of columns for sparse matrix
166  INTEGER(kind=large), DIMENSION(:,:), ALLOCATABLE :: sparseMatrixOffsets !< row offsets for column list, sparse matrix elements
167  ! read buffer
168  INTEGER, DIMENSION(:,:), ALLOCATABLE :: readBufferInfo !< buffer management (per thread)
169  INTEGER, DIMENSION(:), ALLOCATABLE :: readBufferPointer !< pointer to used buffers
170  INTEGER, DIMENSION(:), ALLOCATABLE :: readBufferDataI !< integer data
171  REAL, DIMENSION(:), ALLOCATABLE :: readBufferDataF !< float data
172  ! global parameter usage in record
173  INTEGER, DIMENSION(:), ALLOCATABLE :: globalIndexUsage !< indices of global par in record
174  INTEGER, DIMENSION(:), ALLOCATABLE :: backIndexUsage !< list of global par in record
175  ! local fit
176  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE::blvec !< local fit vector 'b' (in A*x=b), replaced by 'x'
177  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE::clmat !< local fit matrix 'A' (in A*x=b)
178  INTEGER, DIMENSION(:), ALLOCATABLE:: ibandh !< local fit 'band width histogram' (band size autodetection)
179  ! scratch arrays for local fit
180  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE::vbnd !< local fit band part of 'A'
181  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE::vbdr !< local fit border part of 'A'
182  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE::aux !< local fit 'solutions for border rows'
183  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE::vbk !< local fit 'matrix for border solution'
184  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE::vzru !< local fit 'border solution'
185  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE::scdiag !< local fit workspace (D)
186  INTEGER, DIMENSION(:), ALLOCATABLE:: scflag !< local fit workspace (I)
187  REAL, DIMENSION(:), ALLOCATABLE :: localCorrections !< local fit corrections (to residuals)
188  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: localGlobalMatrix !< matrix correlating local and global par
189  ! update of global matrix
190  INTEGER, DIMENSION(:,:), ALLOCATABLE :: writeBufferInfo !< write buffer management (per thread)
191  REAL, DIMENSION(:,:), ALLOCATABLE :: writeBufferData !< write buffer data (largest residual, Chi2/ndf, per thread)
192  INTEGER, DIMENSION(:), ALLOCATABLE :: writeBufferIndices !< write buffer for indices
193  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: writeBufferUpdates !< write buffer for update matrices
194  INTEGER, DIMENSION(-6:6) :: writeBufferHeader = 0 !< write buffer header (-6..-1: updates, 1..6: indices)
195  !!
196  !! +/-1: buffer size (words) per thread; \n
197  !! +/-2: min number of free words; \n
198  !! +/-3: number of buffer flushes; \n
199  !! +/-4: number of buffer overruns; \n
200  !! +/-5: average fill level; \n
201  !! +/-6: peak fill level;
203  INTEGER :: lenParameters=0 !< length of list of parameters from steering file
204  TYPE(listitem), DIMENSION(:), ALLOCATABLE :: listParameters !< list of parameters from steering file
205  INTEGER :: lenPresigmas=0 !< length of list of pre-sigmas from steering file
206  TYPE(listitem), DIMENSION(:), ALLOCATABLE :: listPreSigmas !< list of pre-sgmas from steering file
207  INTEGER :: lenConstraints=0 !< length of list of constraints from steering file
208  TYPE(listitem), DIMENSION(:), ALLOCATABLE :: listConstraints !< list of constraints from steering file
209  INTEGER :: lenMeasurements=0 !< length of list of measurements from steering file
210  TYPE(listitem), DIMENSION(:), ALLOCATABLE :: listMeasurements !< list of measurements from steering file
211  !======================================================
212  ! file information
213  INTEGER, DIMENSION(:), ALLOCATABLE :: mfd !< file mode: cbinary =1, text =2, fbinary=3
214  INTEGER, DIMENSION(:), ALLOCATABLE :: lfd !< length of file name
215  INTEGER, DIMENSION(:), ALLOCATABLE :: nfd !< index (line) in (steering) file
216  INTEGER, DIMENSION(:,:), ALLOCATABLE :: kfd !< (1,.)= number of records in file, (2,..)= file order
217  INTEGER, DIMENSION(:), ALLOCATABLE :: ifd !< file: integrated record numbers (=offset)
218  INTEGER, DIMENSION(:), ALLOCATABLE :: jfd !< file: number of accepted records
219  INTEGER, DIMENSION(:), ALLOCATABLE :: dfd !< file: ndf sum
220  INTEGER, DIMENSION(:), ALLOCATABLE :: xfd !< file: max. record size
221  REAL, DIMENSION(:), ALLOCATABLE :: cfd !< file: chi2 sum
222  REAL, DIMENSION(:), ALLOCATABLE :: ofd !< file: option
223  REAL, DIMENSION(:), ALLOCATABLE :: wfd !< file: weight
224  CHARACTER (LEN=1024) :: filnam !< name of steering file
225  INTEGER :: nfnam !< length of sterring file name
226  CHARACTER, DIMENSION(:), ALLOCATABLE :: tfd !< file names (concatenation)
227  INTEGER :: ifile !< current file (index)
228  INTEGER :: nfiles !< number of files
229  INTEGER :: nfilb !< number of binary files
230  INTEGER :: nfilf !< number of Fortran binary files
231  INTEGER :: nfilc !< number of C binary files
232  INTEGER :: nfilw !< number of weighted binary files
233  INTEGER :: ndimbuf=10000 !< default read buffer size (I/F words, half record length)
234 
235 END MODULE mpmod