1C
2C  This file is part of MUMPS 5.1.2, released
3C  on Mon Oct  2 07:37:01 UTC 2017
4C
5C
6C  Copyright 1991-2017 CERFACS, CNRS, ENS Lyon, INP Toulouse, Inria,
7C  University of Bordeaux.
8C
9C  This version of MUMPS is provided to you free of charge. It is
10C  released under the CeCILL-C license:
11C  http://www.cecill.info/licences/Licence_CeCILL-C_V1-en.html
12C
13C
14C**********************************************************************
15C
16      SUBROUTINE DMUMPS_SET_TYPE_SIZES( K34, K35, K16, K10 )
17      IMPLICIT NONE
18C
19C     Purpose:
20C     =======
21C
22C     Set the size in bytes of an "INTEGER" in K34
23C     Set the size of the default arithmetic (DOUBLE PRECISION, DOUBLE PRECISION,
24C     DOUBLE PRECISION or DOUBLE DOUBLE PRECISION) in K35
25C     Set the size of floating-point types that are real or double
26C     precision even for complex versions of MUMPS (DOUBLE PRECISION for S and
27C     C versions, DOUBLE PRECISION for D and Z versions)
28C     Assuming that the size of an INTEGER(8) is 8, store the ratio
29C     nb_bytes(INTEGER(8)) / nb_bytes(INTEGER) = 8 / K34 into K10.
30C
31C     In practice, we have:
32C
33C     K35:  Arithmetic   Value    Value for T3E
34C              S           4           8
35C              D           8          16
36C              C           8          16
37C              Z          16          32
38C
39C     K16 = K35 for S and D arithmetics
40C     K16 = K35 / 2 for C and Z arithmetics
41C
42C     K34= 4 and K10 = 2, except on CRAY machines or when compilation
43C     flag -i8 is used, in which case, K34 = 8 and K10 = 1
44C
45C
46      INTEGER, INTENT(OUT) :: K34, K35, K10, K16
47      INTEGER SIZE_INT, SIZE_REAL_OR_DOUBLE ! Type must match MUMPS_INT
48      INTEGER I(2)
49      DOUBLE PRECISION R(2) ! Will be DOUBLE PRECISION if 1
50      CALL MUMPS_SIZE_C(I(1),I(2),SIZE_INT)
51      CALL MUMPS_SIZE_C(R(1),R(2),SIZE_REAL_OR_DOUBLE)
52      K34 = int(SIZE_INT)
53      K10 = 8 / K34
54      K16 = int(SIZE_REAL_OR_DOUBLE)
55      K35 = K16
56      RETURN
57      END SUBROUTINE DMUMPS_SET_TYPE_SIZES
58C
59C**********************************************************************
60C
61      SUBROUTINE DMUMPSID( NSLAVES, LWK_USER, CNTL, ICNTL,
62     &                    KEEP,KEEP8,
63     &                    INFO, INFOG, RINFO, RINFOG, SYM, PAR,
64     &                    DKEEP, MYID )
65!$    USE OMP_LIB
66      IMPLICIT NONE
67C
68C  Purpose
69C  =======
70C
71C  The elements of the arrays CNTL and ICNTL control the action of
72C  DMUMPS, DMUMPS_ANA_DRIVER, DMUMPS_FAC_DRIVER, DMUMPS_SOLVE_DRIVER
73C  Default values for the elements are set in this routine.
74C
75      DOUBLE PRECISION    DKEEP(230)
76      DOUBLE PRECISION    CNTL(15), RINFO(40), RINFOG(40)
77      INTEGER ICNTL(40), KEEP(500), SYM, PAR, NSLAVES, MYID
78      INTEGER INFO(40), INFOG(40)
79      INTEGER(8) KEEP8(150)
80      INTEGER LWK_USER
81C
82C  Parameters
83C  ==========
84C===========================================
85C       Arrays for control and information
86C===========================================
87C
88C  N  Matrix order
89C
90C  NELT Number of elements for matrix in ELt format
91C
92C
93C  SYM = 0 ... initializes the defaults for unsymmetric code
94C      = 1,2 ... initializes the defaults for symmetric code
95C
96C
97C
98C  PAR = 0 ... instance where host is not working
99C      = 1 ... instance where host is working as a normal node.
100C              (host uses more memory than other processors in
101C               the latter case)
102C
103C  CNTL and the elements of the array ICNTL control the action of
104C     DMUMPS Default values
105C     are set by DMUMPSID.  The elements of the arrays RINFO
106C     and INFO provide information on the action of DMUMPS.
107C
108C  CNTL(1) has default value 0.01 and is used for
109C     threshold pivoting. Values greater than 1.0
110C     are treated as 1.0, and less than zero as zero.
111C     In general, a larger value of CNTL(1) leads to
112C     greater fill-in but a more accurate factorization.
113C     If CNTL(1) is nonzero, numerical pivoting will be performed.
114C     If CNTL(1) is zero, no pivoting will be performed and
115C     the subroutine will fail if a zero pivot is encountered.
116C     If the matrix A is diagonally dominant, then
117C     setting CNTL(1) to zero will decrease the factorization
118C     time while still providing a stable decomposition.
119C
120C  CNTL(2) must be set to the tolerance for convergence of iterative
121C     refinement.
122C     Default value is sqrt(macheps).
123C     Values less than zero are treated as sqrt(macheps).
124C
125C  CNTL(3) is only used combined with null pivot row
126C     detection (ICNTL(24) .eq. 1) and to Rank-Revealing (RR) option.
127C     It must be set to the absolute threshold for numerical pivoting.
128C     Default value is 0.0.
129C     Let A_{preproc} be the preprocessed matrix to be factored (see
130C       equation in the user's guide).
131C     A pivot is considered to be null if the infinite norm of its row/column
132C     is smaller than a threshold. Let MACHEPS be the machine precision and
133C     ||.|| be the infinite norm.
134C    The computed threshold value for postponing pivots in case of RR on root
135C     is stored in "SEUIL" and then "SEUIL_LDLT_NIV2"
136C     which are identical in current version.
137C     This absolute threshold value is stored in DKEEP(9).
138C
139C     The absolute value to detect a null pivot (when ICNTL(24) .NE.0)
140C     is stored in DKEEP(1) and must be smaller than
141C     SEUIL when combined with RR on root.
142C
143C     IF (ICNTL(16).NE.0) THEN
144C      RR on root is active
145C      IF  (CNTL3 .LT. ZERO) THEN
146C          SEUIL = abs(CNTL(3))
147C      ELSE IF  (CNTL3 .GT. ZERO) THEN
148C          SEUIL = CNTL3*ANORMINF
149C      ELSE  !  (CNTL(3) .EQ. ZERO) THEN
150C          SEUIL = N*EPS*ANORMINF  ! standard articles
151C      ENDIF
152C      IF (ICNTL(24).NE.0) THEN
153C       null pivot detection
154C       IF (CNTL(6).GT.0.AND.CNTL(6).LT.1) THEN
155C         we want DKEEP(1) < SEUIL
156C         DKEEP(1) = SEUIL*CNTL(6) ! ideally it could be SEUIL*CNTL(6)
157C       ELSE
158C         DKEEP(1) = SEUIL* 0.01D0
159C       ENDIF
160C      ENDIF
161C
162C     ELSE (ONLY NULL PIVOT detection is active)
163C         we keep stratgy used in MUMPS_4.10
164C      IF CNTL(3)  > 0 THEN
165C          DKEEP(1) = CNTL(3)  ||A_{preproc}||
166C      ELSE IF CNTL(3)  = 0.0 THEN
167C          DKEEP(1) = MACHEPS 10^{-5} ||A_{preproc}||
168C      ELSE IF CNTL(3)  < 0 THEN
169C          DKEEP(1) = abs(CNTL(3))   ! this was added for EDF
170C                                    ! in the context of SOLSTICE project
171C      ENDIF
172C
173C  CNTL(4) must be set to value for static pivoting.
174C     Default value is -1.0
175C     Note that static pivoting is enabled only when
176C     Rank-Revealing and null pivot detection
177C     are off (KEEP(19).EQ.0).AND.(KEEP(110).EQ.0).
178C     If negative, static pivoting will be set OFF (KEEP(97)=0)
179C     If positive, static pivoting is ON (KEEP(97=1) with threshold CNTL(4)
180C     If = 0, static pivoting is ON with threshold MACHEPS^1/2 || A ||
181C
182C  CNTL(5) fixation for null pivots
183C     Default value is 0.0
184C     Only active if ICNTL(24) = 1
185C     If > 0 after finding a null pivot, it is set to CNTL(5) x ||A||
186C     (This value is stored in DKEEP(2))
187C     If <=  0 then the row/column (except the pivot) is set to zero
188C     and the pivot is set to 1
189C     Default is 0.
190C     Note that in the symmetric parallel case, some elements of the column
191C     are not available on the local processor and cannot be set to 0 easily.
192C     In such cases, in the current version,
193C            -the corresponding pivot is first set
194C                to a large value instead of 1, even when CNTL(5) < 0.
195C            -Updating of the off diag block is done with this large
196C                value
197C            -diagonal value is then reset to zero
198C
199C  CNTL(6) expresses the ratio between
200C        absolute criterion for null pivots and absolute criterion
201C        for posponing pivots before partial pivoting analysis of pivots.
202C        Typically
203C          let SEUIL = F(CNTL(3)), and  0 < CNTL(6) < 1
204C          SEUIL is stored in DKEEP(9)
205C          if ||Pivot row|| < SEUIL*CNTL(6) then
206C              null pivot row detected (correct only if LDLT
207C                                 for LU pivot_col must be checked too)
208C          else if || Pivot_Row || < SEUIL then
209C              pospone pivot
210C          else
211C              partial threshold pivoting
212C          endif
213C
214C CNTL(7) tolerance for Low Rank approximation of the Blocks (BLR).
215C         Dropping parameter expressed with a double precision,
216C         real value, controlling
217C         compression and used to truncate the RRQR algorithm
218C         default value is 0.0.  (i.e. no approximation).
219C         The truncated RRQR operation is implemented as
220C         as variant of the LAPACK GEQP3 and LAQPS routines.
221C           0.0 : full precision approximation.
222C         > 0.0 : the dropping parameter is DKEEP(8).
223C
224C        Warning: using negative values is an experimental and
225C        non recommended setting.
226C        < 0.0 : the dropping parameter is |DKEEP(8)|*|Apre|, Apre
227C                as defined in user's guide
228C
229C
230C  -----------------------------------------
231C
232C  ICNTL(1) has default value 6.
233C     It is the output stream for error messages.
234C     If it is set to zero, these
235C     messages will be suppressed.
236C
237C  ICNTL(2) has default value 0.
238C     It is the output stream for diagnostic printing and
239C     for warning messages that are local to each MPI process.
240C     If it is set to zero, these messages are suppressed.
241C
242C  ICNTL(3) -- Host only
243C            It is the output stream for diagnostic printing
244C            and  for warning messages. Default value is 6.
245C            If it is set to zero, these messages are suppressed.
246C
247C  ICNTL(4) is used by DMUMPS to control printing of error,
248C     warning, and diagnostic messages. It has default value 2.
249C     Possible values are:
250C
251C    <1       __No messages output.
252C     1       __Only error messages printed.
253C     2       __Errors and warnings printed.
254C     3       __Errors and warnings and terse diagnostics
255C                (only first ten entries
256C               of arrays printed).
257C     4       __Errors and warnings and all information
258C               on input and output parameters printed.
259C
260C
261C  ICNTL(5) is the format of the input matrix and rhs
262C     0: assembled matrix, assembled rhs
263C     1: elemental matrix, assembled rhs
264C     Default value is 0.
265C
266C  ICNTL(6) has default value 7 for unsymmetric and
267C      general symmetric matrices, and 0 for SPD matrices.
268C      It is only accessed and operational
269C      on a call that includes an analysis phase
270C      (JOB = 1, 4, or 6).
271C      In these cases, if ICNTL(6)=1, 2, 3, 4, 5, 6 or 7,
272C      a column permutation based on algorithms described in
273C      Duff and Koster, 1997, *SIMAX <20>, 4, 889-901,
274C      is applied to the original matrix. Column permutations are
275C      then applied to the original matrix to get a zero-free diagonal.
276C      Except for ICNTL(6)=1, the numerical values of the
277C      original matrix, id%A(NE), need be provided by the user
278C      during the analysis phase.
279C      If ICNTL(6)=7, based on the structural symmetry of the
280C      input matrix the value of ICNTL(6) is automatically chosen.
281C     If the ordering is provided by the user
282C     (ICNTL(7)=1) then the value of ICNTL(6) is ignored.
283C
284C  ICNTL(7) has default value 7 and must be set by the user to
285C     1 if the pivot order in IS is to be used.
286C     Effective value of ordering stored in KEEP(256).
287C     Possible values are (depending on the softwares installed)
288C       0 AMD: Approximate minimum degree (included in DMUMPS package)
289C       1 Ordering provided by the user
290C       2 Approximate minimum fill (included in DMUMPS package)
291C       3 SCOTCH (see http://gforge.inria.fr/projects/scotch/)
292C         should be downloaded/installed separately.
293C       4 PORD from Juergen Schulze (js@juergenschulze.de)
294C         PORD package is extracted from the SPACE-1.0 package developed at the
295C         University of Paderborn by Juergen Schulze
296C         and is provided as a separate package.
297C       5 Metis ordering should be downloaded/installed separately.
298C       6 Approximate minimum degree with automatic quasi
299C           dense row detection (included in DMUMPS package).
300C           (to be used when ordering time with AMD is abnormally large)
301C       7 Automatic choice done during analysis phase
302C     For any other
303C     value of ICNTL(7), a suitable pivot order will be
304C     chosen automatically.
305C
306C  ICNTL(8)  is used to describe the scaling strategy.
307C     Default value is 77.
308C     Note that scaling is performed only when the numerical
309C     factorization step is performed (JOB = 2, 4>, 5>, or 6>).
310C     If ICNTL(8) is not equal to
311C     any of the values listed below then ICNTL(8) is treated
312C     as if it had its default value of 0 (no scaling).
313C     If the matrix is known to be very badly scaled,
314C     our experience has been that option 6 is the most robust but
315C     the best scaling is very problem dependent.
316C     If ICNTL(8)=0, COLSCA and ROWSCA are dummy arguments
317C     of the subroutine that are not accessed.
318C     Possible values of ICNTL(8) are:
319C
320C     -2 scaling computed during analysis (and applied during the
321C       factorization)
322C
323C     -1 the user must provide the scaling in arrays
324C        COLSCA and ROWSCA
325C
326C     0 no scaling
327C
328C     1 Diagonal scaling
329C
330C     2 not defined
331C
332C     3 Column scaling
333C
334C     4 Row and column scaling
335C
336C     5,6 not defined
337C     7, 8 Scaling based on Daniel Ruiz and Bora Ucar's work done
338C     during the ANR-SOLSTICE project.
339C     Reference for this work are:
340C     The scaling algorithms are based on those discussed in
341C     [1] D. Ruiz, "A scaling algorithm to equilibrate both rows and
342C         columns norms in matrices", Tech. Rep. Rutherford
343C         Appleton Laboratory, Oxon, UK and ENSEEIHT-IRIT,
344C         Toulouse, France, RAL-TR-2001-034 and RT/APO/01/4, 2001.
345C     [2] D. Ruiz and B. Ucar, "A symmetry preserving algorithm for
346C         matrix scaling", in preparation as of Jan'08.
347C     This scaling can work on both centralized and distributed
348C     assembled input matrix format. (it works for both symmetric
349C     and unsymmetric matrices)
350C     Option 8 is similar to 7 but more rigourous and expensive to compute.
351C     77 Automatic choice of scaling value done. Proposed algo:
352C          if (sym=1) then
353C           default = 0
354C          else
355C           if distributed matrix entry then
356C              default = 7
357C           else
358C               if (mc64 called or mc77 based matching) then
359C                 default=-2 and ordering is computed during analysis
360C               else
361C                 default = 7
362C               endif
363C           endif
364C          endif
365C
366C  ICNTL(9) has default value 1. If ICNTL(9)=1
367C     the system of equations A * x = b  is solved. For other
368C     values the system A^T *  x = b  is solved.
369C     When ICNTL(30) (compute selected entries in A-1) is activated
370C     ICNTL(9) is ignored.
371C
372C  ICNTL(10) has default value 0.
373C     If ICNTL(10)=0 : iterative refinement is not performed.
374C     Values of  ICNTL(10) < 0 : a fix number of steps equal
375C     to ICNTL(10) of IR is done.
376C     Values of ICNTL(10) > 0 : mean a maximum of ICNTL(10) number
377C                           of steps of IR is done, and a test of
378C                           convergence is used
379C
380C  ICNTL(11) has default value 0.
381C     A value equal to 1 will return a backward error estimate in
382C     RINFO(4-11).
383C     A value equal to 2 will return a backward error estimate in
384C     RINFO(4-8). No LCOND 1, 2 and forward error are computed.
385C     If ICNTL(11) is negative, zero or greater than 2 no estimate
386C     is returned.
387C
388C
389C  ICNTL(12) has default value 0 and define the strategy for
390C     LDLT orderings
391C     0 : automatic choice
392C     1 : usual ordering (nothing done)
393C     2 : ordering on the compressed graph, available with all orderings
394C         except with AMD
395C     3 : constraint ordering, only available with AMF,
396C         -> reset to 2 with other orderings
397C     Other values are treated as 1 (nothing done).
398C     On output KEEP(95) holds the internal value used and INFOG(24) gives
399C     access to KEEP(95) to the user.
400C     in LU facto it is always reset to 1
401C
402C     - ICNTL(12) = 3 has a lower priority than ICNTL(7)
403C     thus if ICNTL(12) = 3 and the ordering required is not AMF
404C     then ICNTL(12) is set to 2
405C
406C     - ICNTL(12) = 2 has a higher priority than ICNTL(7)
407C     thus if ICNTL(12) = 2 and the ordering required is AMD
408C     then the ordering used is QAMD
409C
410C     - ICNTL(12) has a higher priority than ICNTL(6) and ICNTL(8)
411C     thus if ICNTL(12) = 2 then ICNTL(6) is automatically
412C     set to a value between 1-6
413C     if ICNTL(12) = 3 then ICNTL(6) is automatically
414C     set to 5 and ICNTL(6) is set to -2 (we need the scaling  factors
415C     to define free and constrained variables)
416C
417C  ICNTL(13) has default value 0 and allows for selecting Type 3 node.
418C            IF ICNTL(13).GT. 0 scalapack is forbidden. Otherwise,
419C            scalapack will be activated if the root is large enough.
420C            Furthermore
421C             IF ((ICNTL(13).GT.0) .AND. (NSLAVES.GT.ICNTL(13),
422C               or ICNTL(13)=-1 THEN
423C               extra splitting of the root will be activated
424C               and is controlled by abs(KEEP(82)).
425C               The order of the root node is divided by KEEP(82)
426C             ENDIF
427C            If ICNTL(13) .EQ. -1 then splitting of the root
428C            is done whatever the nb of procs is.
429C
430C            Authorizing extra root spliting
431C            during analysis might be interesting
432C            to further split the root node
433C            (combined for example with
434C             null pivot detection option ICNTL(24)=1 OR ICNTL(16))
435C
436C            To summarize:
437C               -1         : root splitting and scalapack on
438C               0  or < -1 : root splitting off and sclalapack on
439C               > 0        : scalapack off
440C
441C  ICNTL(14) has default value 20 (or 30, or 5 depending on NSLAVES,
442C            SYM,...) and is the value for memory relaxation
443C            so called "PERLU" in the following.
444C
445C  ICNTL(18) has default value 0 and is only accessed by the host during
446C      the analysis phase if the matrix is assembled (ICNTL(5))= 0).
447C      ICNTL(18) defines the strategy for the distributed input matrix.
448C      Possible values are:
449C      0: input matrix is centralized on the host. This is the default
450C      1: user provides the structure of the matrix on the host at analysis,
451C        DMUMPS returns
452C        a mapping and user should provide the matrix distributed according
453C        to the mapping
454C      2:  user provides the structure of the matrix on the host at analysis,
455C          and the
456C          distributed matrix on all slave processors at factorization.
457C          Any distribution is allowed
458C      3: user directly provides the distributed matrix input both
459C         for analysis and factorization
460C
461C      For flexibility and performance issues, option 3 is recommended.
462C
463C   ICNTL(19) has default value 0 and is only accessed by the host
464C    during the analysis phase. If ICNTL(19) \neq 0 then Schur matrix will
465C    be returned to the user.
466C    The user must set on entry on the host node (before analysis):
467C    the integer variable SIZE\_SCHUR to the size fo the Schur matrix,
468C    the integer array pointer LISTVAR\_SCHUR to the list of indices
469C    of the schur matrix.
470C     if = 0      : Schur is off and the root node gets factorized
471C     if = 1      : Schur is on and the Schur complement is returned entirely
472C                   on a memory area provided by the user ONLY on the host node
473C     if = 2 or 3 : Schur is on and the Schur complement is returned in a
474C                   distributed fashion according to a 2D block-cyclic
475C                   distribution. In the case where the matrix is symmetric
476C                   the lower part is returned if =2 or the complete
477C                   matrix if =3.
478C
479C   ICNTL(20) has default value 0 and is only accessed  by the host
480C    during the solve phase. If ICNTL(20)=0, the right-hand side must given
481C    in dense form in the structure component RHS.
482C    If ICNTL(20)=1,2,3, then the right-hand side must be given in sparse form
483C    using the structure components IRHS\_SPARSE, RHS\_SPARSE, IRHS\_PTR and
484C    NZ\_RHS.
485C    When the right-hand side is provided in sparse form then duplicate entries
486C    are summed.
487C
488C       0 : dense RHS
489C       1,2,3 : Sparse RHS
490C          1 The decision of exploiting sparsity of the right-hand side to
491C            accelerate the solution phase is done automatically.
492C          2 Sparsity of the right-hand sides is NOT exploited
493C            to improve solution phase.
494C          3 Sparsity of the right-hand sides is exploited
495C            to improve solution phase.
496C    Values different from 0,1, 2,3 are treated as 0.
497C    For sparse RHS recommended value is 1.
498C
499C   ICNTL(21) has default value 0 and is only accessed by the host
500C    during the solve phase. If ICNTL(21)=0, the solution vector will be assembled
501C    and stored in the structure component RHS, that must have been allocated by
502C    the user. If ICNTL(21)=1, the solution vector is kept distributed at the
503C    end of the solve phase, and will be available on each slave processor
504C    in the structure components ISOL_loc and SOL_loc. ISOL_loc and SOL_loc
505C    must then have been allocated by the user and must be of size at least
506C    INFO(23), where INFO(23) has been returned by DMUMPS at the end of the
507C    factorization phase.
508C    Values of ICNTL(21) different from 0 and 1 are currently treated as 0.
509C
510C   ICNTL(22) (saved in KEEP(201) controls the OOC setting (0=incore, 1 =OOC)
511C    It has default value 0 (incore).
512C    If set before analysis then special setting and massage of the tree
513C    might be done (so far only extra splitting  CUTNODES) is performed.
514C    It is then accessed by the host
515C    during the factorization phase. If ICNTL(22)=0, then no attempt
516C    to use the disks is made. If ICNTL(22)=1, then DMUMPS will store
517C    the computed factors on disk for later use during the solution
518C    phase.
519C
520C   ICNTL(23) has default value 0 and is accessed by ALL processors
521C    at the beginning of the factorization phase.  If positive
522C    it corresponds to the maximum size of the working memory
523C    in MegaBytes that MUMPS can allocate per working processor.
524C    If only the host
525C    value is non zero, then other processors also use the value on
526C    the host. Otherwise, each processor uses the local value
527C    provided.
528C
529C   ICNTL(24) default value is 0
530C     if = 0 no null pivot detection (CNTL(5) and CNTL(3) are inactive),
531C        = 1 null pivot row detection; CNTL(3) and CNTL(5) are
532C            then used to describe the action taken.
533C
534C
535C   ICNTL(25) has default value 0 and is only accessed by the
536C   host during the solution stage. It is only significant if
537C   a null space basis was requested during the factorization
538C   phase (INFOG(28) .GT. 0); otherwise a normal solution step
539C   is performed.
540C   If ICNTL(25)=0, then a normal solution step is performed,
541C   on the internal problem (excluding the null space).
542C   No special property on the solution (discussion with Serge)
543C   If ICNTL(25)=i, 1 <= i <= INFOG(28), then the i-th vector
544C   of the null space basis is computed. In that case, note
545C   that NRHS should be set to 1.
546C   If ICNTL(25)=-1, then all null space is computed. The
547C   user should set NRHS=INFOG(28) in that case.
548C   Note that centralized or distributed solutions are
549C   applicable in that case, but that iterative refinement,
550C   error analysis, etc... are excluded. Note also that the
551C   option to solve the transpose system (ICNTL(9)) is ignored.
552C
553C
554C   ICNTL(26) has default value 0 and is accessed on the host only
555C     at the beginning of the solution step.
556C     It is only effective if the Schur option is ON.
557C     (copy in KEEP(221))
558C
559C
560C     During the solution step, a value of 0 will perform a normal
561C     solution step on the reduced problem not involving the Schur
562C     variables.
563C     During the solution step, if ICNTL(26)=1 or 2, then REDRHS
564C     should be allocated of size at least LREDRHS*(NRHS-1)+
565C     SIZE_SCHUR, where LREDRHS is the leading dimension of
566C     LREDRHS (LREDRHS >= SIZE_SCHUR).
567C
568C     If ICNTL(26)=1, then only a forward substitution is performed,
569C     and a reduced RHS will be computed and made available in
570C     REDRHS(i+(k-1)*LREDRHS), i=1, ..., SIZE_SCHUR, k=1, ..., NRHS.
571C     If ICNTL(26)=2, then REDRHS(i+(k-1)*LREDRHS),i=1, SIZE_SCHUR, k=1,NRHS is
572C     considered to be the solution corresponding to the Schur
573C     variables. It is injected in DMUMPS, that computes the solution
574C     on the "internal" problem during the backward substitution.
575C
576C ICNTL(27)  controls the blocking factor for multiple right-hand-sides
577C during the solution phase.
578C It influences both the memory used (see INFOG(30-31)) and
579C the solution time
580C (Larger values of ICNTL(27) leads to larger memory requirements).
581C Its tuning can be critical when
582C the factors are written on disk (out-of core, ICNTL(22)=1).
583C A negative value indicates that  automatic setting is performed by the solver.
584C Default value is -24.
585C
586C
587C   ICNTL(28) decides whether parallel or sequential analysis should be used. Three
588C       values are possible at the moment:
589C       0: automatic. This defaults to sequential analysis
590C       1: sequential. In this case the ordering strategy is defined by ICNTL(7)
591C       2: parallel. In this case the ordering strategy is defined by ICNTL(29)
592C
593C   ICNTL(29) defines the ordering too to be used during the parallel analysis. Three
594C       values are possible at the moment:
595C       0: automatic. This defaults to PT-SCOTCH
596C       1: PT-SCOTCH.
597C       2: ParMetis.
598C
599C
600C   ICNTL(30) controls the activation of functionality A-1.
601C             It has default value 0 and is only accessed by the master
602C             during the solution phase. It enables the solver to
603C             compute entries in the inverse of the original matrix.
604C             Possible values are:
605C              0  normal solution
606C              other values:   compute entries in A-1
607C             When ICNTL(30).NE.0 then the user
608C             must describe on entry to the solution phase,
609C             in the sparse right-hand-side
610C             (NZ_RHS, NRHS, RHS_SPARSE, IRHS_SPARSE, IRHS_PTR)
611C             the target entries of A-1 that need be computed.
612C             Note that RHS_SPARSE must be allocated but need not be
613C             initialized.
614C             On output RHS_SPARSE then holds the requested
615C             computed values of A-1.
616C             Note that when ICNTL(30).NE.0 then
617C              - sparse right hand side interface is implicitly used
618C                functionality (ICNTL(20)= 1) but RHS need not be
619C                allocated since computed A-1 entries will be stored
620C                in place.
621C              - ICNTL(9) option (solve Ax=b or Atx=b) is ignored
622C             In case of duplicate entries in the sparse rhs then
623C             on output duplicate entries in the solution are provided
624C             in the same place.
625C             This need not be mentioned in the spec since it is a
626C             "natural" extension.
627C
628C   -----------
629C   Fwd in facto
630C   -----------
631C   ICNTL(31) Must be set before analysis to control storage
632C             of LU factors. Default value is 0. Out of range
633C             values considered as 0.
634C             (copied in KEEP(251) and broadcast,
635C              when setting of ICNTL(31)
636C              results in not factors to be stored then
637C              KEEP(201) = -1, OOC is "suppressed")
638C            0 Keep factors needed for solution phase
639C              (when option forward during facto is used then
640C               on unsymmetric matrices L factors are not stored)
641C            1 Solve not needed (solve phase will never be called).
642C              When the user is only interested in the inertia or the
643C              determinant then
644C              all factor matrices need not be stored.
645C              This can also be useful for testing :
646C              to experiment facto OOC without
647C              effective storage of factors on disk.
648C            2 L factors not stored: meaningful when both
649C              - matrix is unsymmetric and fwd performed during facto
650C              - the user is only interested in the null-space basis
651C              and thus only need the U factors to be stored.
652C              Currently, L factors are always stored in IC.
653C
654C   -----------
655C   Fwd in facto
656C   -----------
657C   ICNTL(32) Must be set before analysis to indicate whether
658C             forward is performed during factorization.
659C             Default value is 0 (normal factorization without fwd)
660C             (copied in KEEP(252) and broadcast)
661C            0 Normal factorization (default value)
662C            1 Forward performed during factorization
663C
664C
665C   ICNTL(33) Must be set before the factorization phase to compute
666C             the determinant. See also KEEP(258), KEEP(259),
667C             DKEEP(6), DKEEP(7), INFOG(34), RINFOG(12), INFOG(34)
668C
669C            If ICNTL(33)=0 the determinant is not computed
670C            For all other values, the determinant is computed. Note that
671C            null pivots and static pivots are excluded from the
672C            computation of the determinant.
673C
674C
675C    ICNTL(35) : Block low rank (BLR) factorization
676C             Default value is 0
677C             0 = BLR is not activated
678C             1 = BLR activated with grouping based
679C                  on inherited clustering done during analysis
680C             Other values are treated as zero
681C      Note that this functionality is currently incompatible with elemental matrices
682C      (ICNTL(5) = 1) and with forward elimination during factorization (ICNTL(32) = 1).
683C
684C   ICNTL(38) not used in this version
685C
686C=========================
687C  ARRAYS FOR INFORMATION
688C========================
689C
690C-----
691C INFO is an INTEGER array of length 40 that need not be
692C     set by the user.
693C-----
694C
695C  INFO(1) is zero if the routine is successful, is negative if an
696C     error occurred, and is positive for a warning (see DMUMPS for
697C     a partial documentation and the userguide for a full documentation
698C     of INFO(1)).
699C
700C  INFO(2)   holds additional information concerning the
701C     error (see DMUMPS).
702C
703C ------------------------------------------
704C Statistics produced after analysis phase
705C ------------------------------------------
706C
707C  INFO(3)   Estimated real space needed for factors.
708C
709C  INFO(4)   Estimated integer space needed for factors.
710C
711C  INFO(5)  Estimated maximum frontal size.
712C
713C  INFO(6)  Number of nodes in the tree.
714C
715C  INFO(7)  Minimum value of integer working array IS (old MAXIS)
716C     estimated by the analysis phase
717C     to run the numerical factorization.
718C
719C  INFO(8)  Minimum value of real/complex arry S (old MAXS)
720C     estimated by the analysis phase
721C     to run the numerical factorization.
722C
723C  INFO(15) Estimated size in MBytes of all DMUMPS internal data
724C      structures to run factorization
725C
726C  INFO(17) provides an estimation (minimum in Megabytes)
727C  of the total memory required to run
728C  the numerical phases  out-of-core.
729C  This memory estimation corresponds to
730C  the least memory consuming out-of-core strategy and it can be
731C  used as a lower bound if the user wishes to provide ICNTL(23).
732C ---------------------------------------
733C Statistics produced after factorization
734C ---------------------------------------
735C  INFO(9)  Size of the real space used to store the LU factors.
736C
737C  INFO(10)  Size of the integer space used to store the LU factors.
738C
739C  INFO(11)  Order of largest frontal matrix.
740C
741C  INFO(12)  Number of off-diagonal pivots.
742C
743C  INFO(13)  Number of uneliminated variables sent to the father.
744C
745C  INFO(14)  Number of memory compresses.
746C
747C  INFO(18)  On exit to factorization:
748C              Local number of null pivots (ICNTL(24)=1)
749C              on the local processor even on master.
750C              (local size of array PIVNUL_LIST).
751C              Note that it does not include null pivots
752C              that might have been
753C              further detected on the root (ICNTL(16).NE.0).
754C
755C  INFO(19) - after analysis:
756C           Estimated size of the main internal integer workarray IS
757C     (old MAXIS) to run the numerical factorization out-of-core.
758C
759C  INFO(21) - after factorization: Effective space used in the main
760C           real/complex workarray S -- or in the workarray WK_USER,
761C           in the case where WK_USER is provided.
762C
763C  INFO(22) - after factorization:
764C      Size in millions of bytes of memory effectively used during
765C      factorization.
766C      This includes the memory effectively used in the workarray
767C      WK_USER, in the case where WK_user is provided.
768C
769C  INFO(23) - after factorization: total number of pivots eliminated
770C      on the processor. In the case of a distributed solution (see
771C      ICNTL(21)), this should be used by the user to allocate solution
772C      vectors ISOL_loc and SOL_loc of appropriate dimensions
773C      (ISOL_LOC of size INFO(23), SOL_LOC of size LSOL_LOC * NRHS
774C      where LSOL_LOC >= INFO(23)) on that processor, between the
775C      factorization and solve steps.
776C
777C  INFO(24) - after analysis: estimated number of entries in factors on
778C      the processor. If negative, then
779C      the absolute value corresponds to {\it millions} of entries
780C      in the factors.
781C      Note that in the unsymmetric case, INFO(24)=INFO(3).
782C      In the symmetric case, however, INFO(24) < INFO(3).
783C  INFO(25) - after factorization: number of tiny pivots (number of
784C       pivots modified by static pivoting) detected on the processor.
785C  INFO(26) - after solution:
786C                 effective size in Megabytes of all working space
787C                 to run  the solution phase.
788C     (The maximum and sum over all processors are returned
789C    respectively in INFOG(30) and INFOG(31)).
790C  INFO(27) - after factorization: effective number of entries in factors
791C      on the processor. If negative, then
792C      the absolute value corresponds to {\it millions} of entries
793C      in the factors.
794C      Note that in the unsymmetric case, INFO(27)=INFO(9).
795C      In the symmetric case, however, INFO(27) < INFO(9).
796C      The total number of entries over all processors is
797C      available in INFOG(29).
798C
799C -------------------------------------------------------------
800C -------------------------------------------------------------
801C RINFO is a DOUBLE PRECISION/DOUBLE PRECISION array of length 40 that
802C       need not be set by the user. This array supplies
803C       local information on the execution of DMUMPS.
804C
805C
806C RINFOG is a DOUBLE PRECISION/DOUBLE PRECISION array of length 40 that
807C       need not be set by the user. This array supplies
808C       global information on the execution of DMUMPS.
809C       RINFOG is only significant on processor 0
810C
811C
812C  RINFO(1) hold the estimated number of floating-point operations
813C           for the elimination process on the local processor
814C
815C  RINFOG(1) hold the estimated number of floating-point operations
816C           for the elimination process on all processors
817C
818C  RINFO(2)  Number of floating-point operations
819C     for the assembly process on local processor.
820C
821C  RINFOG(2) Number of floating-point operations
822C     for the assembly process.
823C
824C  RINFO(3)  Number of floating-point operations
825C     for the elimination process on the local processor.
826C
827C  RINFOG(3)  Number of floating-point operations
828C     for the elimination process on all processors.
829C
830C----------------------------------------------------
831C Statistics produced after solve with error analysis
832C----------------------------------------------------
833C
834C  RINFOG(4) Infinite norm of the input matrix.
835C
836C  RINFOG(5) Infinite norm of the computed solution, where
837C
838C  RINFOG(6) Norm of scaled residuals
839C
840C  RINFOG(7), `RINFOG(8) and `RINFOG(9) are used to hold information
841C     on the backward error.
842C     We calculate an estimate of the sparse backward error using the
843C     theory and measure developed
844C     by Arioli, Demmel, and Duff (1989). The scaled residual w1
845C     is calculated for all equations except those
846C     for which numerator is nonzero and the denominator is small.
847C     For the exceptional equations, w2, is used instead.
848C     The largest scaled residual (w1) is returned in
849C     RINFOG(7) and the largest scaled
850C     residual (w2) is returned in `RINFOG(8)>. If all equations are
851C     non exceptional then zero is returned in `RINFOG(8).
852C     The upper bound error is returned in `RINFOG(9).
853C
854C  RINFOG(14) Number of floating-point operations
855C     for the elimination process (on all fronts, BLR or not)
856C     performed when BLR option is activated on all processors.
857C     (equal to zero if BLR option not used, ICNTL(35).EQ.1)
858C
859C===========================
860C DESCRIPTION OF KEEP8 ARRAY
861C===========================
862C
863C   KEEP8 is a 64-bit integer array of length 150 that need not
864C   be set by the user
865C
866C===========================
867C DESCRIPTION OF KEEP ARRAY
868C===========================
869C
870C  KEEP is an INTEGER array of length 500 that need not
871C     be set by the user.
872C
873C
874C=============================
875C Description of DKEEP array
876C=============================
877C
878C DKEEP internal control array for DOUBLE PRECISION parameters
879C     of size 30
880C===================================
881C Default values for control arrays
882C==================================
883C     uninitialized values should be 0
884      LWK_USER = 0
885      KEEP(1:500) = 0
886      KEEP8(1:150)= 0_8
887      INFO(1:40)  = 0
888      INFOG(1:40) = 0
889      ICNTL(1:40) = 0
890      RINFO(1:40) = 0.0D0
891      RINFOG(1:40)= 0.0D0
892      CNTL(1:15)  = 0.0D0
893      DKEEP(1:230) = 0.0D0
894C     ----------------
895C     Symmetric code ?
896C     ----------------
897      KEEP( 50 ) = SYM
898C     -------------------------------------
899C     Only options 0, 1, or 2 are available
900C     -------------------------------------
901      IF ( KEEP(50).NE.1 .and. KEEP(50).NE.2 ) KEEP( 50 ) = 0
902C     threshold value for pivoting
903      IF ( KEEP(50) .NE. 1 ) THEN
904        CNTL(1)   = 0.01D0
905      ELSE
906        CNTL(1)   = 0.0D0
907      END IF
908      CNTL(2) = sqrt(epsilon(0.0D0))
909      CNTL(3) = 0.0D0
910      CNTL(4) = -1.0D0
911      CNTL(5) = 0.0D0
912      CNTL(6) = -1.0D0
913C     Working host ?
914      KEEP(46) = PAR
915      IF ( KEEP(46) .NE. 0 .AND.
916     &     KEEP(46) .NE. 1 ) THEN
917C          ----------------------
918C          If out-of-range value,
919C          use a working host
920C          ----------------------
921           KEEP(46) = 1
922      END IF
923C     control printing
924      ICNTL(1)  = 6
925      ICNTL(2)  = 0
926      ICNTL(3)  = 6
927      ICNTL(4)  = 2
928C     format of input matrix
929      ICNTL(5)  = 0
930C     maximum transversal (0=NO, 7=automatic)
931      IF (SYM.NE.1) THEN
932       ICNTL(6)  = 7
933      ELSE
934       ICNTL(6)  = 0
935      ENDIF
936C     Ordering option (icntl(7))
937C     Default is automatic choice done during analysis
938      ICNTL(7) = 7
939C     ask for scaling (0=NO, 4=Row and Column)
940C     Default value is 77: automatic choice for analysis
941      ICNTL(8)  = 77
942C     solve Ax=b (1) or Atx=b (other values)
943      ICNTL(9)  = 1
944C     Naximum number of IR (0=NO)
945      ICNTL(10)  = 0
946C     Error analysis (0=NO)
947      ICNTL(11)  = 0
948C     Control ordering strategy
949C     automatic choice
950      IF(SYM .EQ. 2) THEN
951         ICNTL(12)  = 0
952      ELSE
953         ICNTL(12)  = 1
954      ENDIF
955C     Control of the use of ScaLAPACK for root node
956C     If null space options asked, ScaLAPACK is always ignored
957C        and ICNTL(13) is not significant
958C     ICNTL(13) = 0 : Root parallelism on (if size large enough)
959C     ICNTL(13) = 1 : Root parallelism off
960      ICNTL(13) = 0
961C     Default value for the memory relaxation
962      IF (SYM.eq.1.AND.NSLAVES.EQ.1) THEN
963        ICNTL(14) = 5  ! it should work with 0
964      ELSE IF (NSLAVES .GT. 4) THEN
965        ICNTL(14) = 30
966      ELSE
967        ICNTL(14) = 20
968      END IF
969C     Minimum size of the null space
970      ICNTL(15) = 0
971C     Do not look for rank/null space basis
972      ICNTL(16) = 0
973C     Max size of null space
974      ICNTL(17) = 0
975C     Distributed matrix entry
976      ICNTL(18) = 0
977C     Schur  (default is not active)
978      ICNTL(19) = 0
979C     dense RHS by default
980      ICNTL(20) = 0
981C     solution vector centralized on host
982      ICNTL(21) = 0
983C     out-of-core flag
984      ICNTL(22) = 0
985C     MEM_ALLOWED (0: not provided)
986      ICNTL(23) = 0
987C     null pivots
988      ICNTL(24) = 0
989C     blocking factor for multiple RHS during solution phase
990      ICNTL(27) = -32
991C     analysis strategy: 0=auto, 1=sequential, 2=parallel
992      ICNTL(28) = 1
993C     tool used for parallel ordering computation :
994C     0 = auto, 1 = PT-SCOTCH, 2 = ParMETIS
995      ICNTL(29) = 0
996C     --------- Non documented ICNTL options
997C     Old or new symbolic factorization
998      ICNTL(39) = 1
999      ICNTL(40)  = 0
1000C===================================
1001C Default values for some components
1002C of KEEP array
1003C===================================
1004      KEEP(12) = 0
1005C      KEEP(11) = 2147483646
1006      KEEP(11) = huge(KEEP(11))
1007      KEEP(24) = 18
1008      KEEP(68) = 0
1009      KEEP(36) = 1
1010      KEEP(1) = 5
1011      KEEP(7)  = 150
1012      KEEP(8)  = 120
1013      KEEP(57) = 500
1014      KEEP(58) = 250
1015      IF ( SYM .eq. 0 ) THEN
1016        KEEP(4)  = 32
1017        KEEP(3)  = 96
1018        KEEP(5)  = 16
1019        KEEP(6)  = 32
1020        KEEP(9)  = 700
1021        KEEP(85) =  300
1022        KEEP(62) =  50
1023      ELSE
1024        KEEP(4)  = 24
1025        KEEP(3)  = 96
1026        KEEP(5)  = 16
1027        KEEP(6)  = 32
1028        KEEP(9)  = 400
1029        KEEP(85) = 100
1030        KEEP(62) = 50
1031      END IF
1032      KEEP(63) = 60
1033      KEEP(48) = 5
1034      KEEP(17) = 0
1035      CALL DMUMPS_SET_TYPE_SIZES( KEEP(34), KEEP(35),
1036     &                            KEEP(16), KEEP(10) )
1037      KEEP(51) = 70
1038      KEEP(37) = max(800, int(sqrt(dble(NSLAVES+1))*dble(KEEP(51))))
1039      IF ( NSLAVES > 256 ) THEN
1040        KEEP(39) = 10000
1041      ELSEIF ( NSLAVES > 128 ) THEN
1042        KEEP(39) = 20000
1043      ELSEIF ( NSLAVES > 64 ) THEN
1044        KEEP(39) = 40000
1045      ELSEIF ( NSLAVES > 16 ) THEN
1046        KEEP(39) = 80000
1047      ELSE
1048        KEEP(39) = 160000
1049      END IF
1050      KEEP(40) = -1 - 456789
1051      KEEP(45) = 0
1052      KEEP(47) = 2
1053      KEEP(64) = 20
1054      KEEP(69) = 4
1055C     To disable SMP management when using new mapping strategy
1056C      KEEP(69) = 1
1057C     Forcing proportional is ok with strategy 5
1058      KEEP(75) = 1
1059      KEEP(76) = 2
1060      KEEP(77) = 30
1061      KEEP(79) = 0  ! old splitting
1062      !write(6,*) ' TEMPORARY new splitting active, K79=', KEEP(79)
1063      IF (NSLAVES.GT.4) THEN
1064          KEEP(78)=max(
1065     &       int(log(dble(NSLAVES))/log(dble(2))) - 2
1066     &       , 0         )
1067      ENDIF
1068      KEEP(210) = 2
1069      KEEP8(79) = -10_8
1070      KEEP(80) = 1
1071      KEEP(81) = 0
1072      KEEP(82) = 30
1073      KEEP(83) = min(8,NSLAVES/4)
1074      KEEP(83) = max(min(4,NSLAVES),max(KEEP(83),1))
1075      KEEP(86)=1
1076      KEEP(87)=0
1077      KEEP(88)=0
1078      KEEP(90)=1
1079      KEEP(91)=min(8, NSLAVES)
1080      KEEP(91) = max(min(4,NSLAVES),min(KEEP(83),KEEP(91)))
1081      IF(NSLAVES.LT.48)THEN
1082         KEEP(102)=150
1083      ELSEIF(NSLAVES.LT.128)THEN
1084         KEEP(102)=150
1085      ELSEIF(NSLAVES.LT.256)THEN
1086         KEEP(102)=200
1087      ELSEIF(NSLAVES.LT.512)THEN
1088         KEEP(102)=300
1089      ELSEIF(NSLAVES.GE.512)THEN
1090         KEEP(102)=400
1091      ENDIF
1092#if defined(OLD_OOC_NOPANEL)
1093      KEEP(99)=0  ! no panel -> synchronous / no buffer
1094#else
1095      KEEP(99)=4  ! new OOC -> asynchronous + buffer
1096#endif
1097      KEEP(100)=0
1098      KEEP(204)=0
1099      KEEP(205)=0
1100      KEEP(209)=-1
1101      KEEP(104) = 16
1102      KEEP(107)=0
1103#if ! defined(NO_XXNBPR)
1104      KEEP(121)=-999999
1105#endif
1106      KEEP(122)=150
1107      KEEP(206)=1
1108      KEEP(211)=2
1109      IF (NSLAVES .EQ. 2) THEN
1110        KEEP(213) = 101
1111      ELSE
1112        KEEP(213) = 201
1113      ENDIF
1114      KEEP(217)=0
1115      KEEP(215)=0
1116      KEEP(216)=1
1117      KEEP(218)=50
1118      KEEP(219)=1
1119      IF (KEEP(50).EQ.2) THEN
1120        KEEP(227)= max(2,32)
1121      ELSE
1122        KEEP(227)= max(1,32)
1123      ENDIF
1124      KEEP(231) = 1
1125      KEEP(232) = 3
1126      KEEP(233) = 0
1127      KEEP(239) = 1
1128      KEEP(240) = 10
1129      DKEEP(4) = -1.0D0
1130      DKEEP(5) = -1.0D0
1131      DKEEP(10) = 1000.0D0  ! > 0 : GAP
1132      IF(NSLAVES.LE.8)THEN
1133         KEEP(238)=12
1134      ELSE
1135         KEEP(238)=7
1136      ENDIF
1137      KEEP(234)= 1
1138      KEEP(235)=-1
1139      DKEEP(3)=-5.0D0
1140      KEEP(242) = -9
1141      KEEP(243) = -1
1142      KEEP(249)=1
1143!$    KEEP(249) = OMP_GET_MAX_THREADS()
1144      KEEP(250) = 1
1145      KEEP(261) = 1
1146      KEEP(262) = 0
1147      KEEP(263) = 0
1148      KEEP(266) = 0
1149      KEEP(267) = 0
1150      KEEP(350) = 1
1151      KEEP(351) = 0
1152      KEEP(360) = 256
1153      KEEP(361) = 2048
1154      KEEP(362) = 4
1155      KEEP(363) = 512
1156      KEEP(364) = 32768
1157      KEEP(420) =  4*KEEP(6)   ! if KEEP(6)=32 then 128
1158      KEEP(468) = 3
1159      KEEP(469) = 1
1160      KEEP(470) = 1
1161      KEEP(471) = -1
1162      KEEP(480) = 0
1163      KEEP(479) = 1
1164      KEEP(478) = 0
1165      KEEP(474) = 0
1166      KEEP(481) = 0
1167      KEEP(482) = 0
1168      KEEP(472) = 1
1169      KEEP(473) = 0
1170      KEEP(475) = 0
1171      KEEP(476) = 50
1172      KEEP(477) = 100
1173      KEEP(483) = 50
1174      KEEP(484) = 50
1175      KEEP(485) = 1 ! (1 promote factors)
1176      KEEP(487) = 1
1177      IF (KEEP(472).EQ.1) THEN
1178        KEEP(488) = 512
1179      ELSE
1180        KEEP(488) =  8*KEEP(6)   ! if KEEP(6)=32 then 256
1181      ENDIF
1182      KEEP(489) = 0
1183      KEEP(490) = 128
1184      KEEP(491) = 1000
1185      KEEP(492) = 1
1186      KEEP(82) = 30
1187      KEEP(493) = 0
1188      KEEP(496) = 1
1189      KEEP(495) = -1
1190      KEEP(497) = -1
1191      RETURN
1192      END SUBROUTINE DMUMPSID
1193      SUBROUTINE DMUMPS_SET_KEEP72(id, LP)
1194      USE DMUMPS_STRUC_DEF
1195      IMPLICIT NONE
1196      TYPE (DMUMPS_STRUC) :: id
1197      INTEGER LP
1198      IF (id%KEEP(72)==1) THEN
1199         id%KEEP(37) = 2*id%NSLAVES
1200         id%KEEP(3)=3
1201         id%KEEP(4)=2
1202         id%KEEP(5)=1
1203         id%KEEP(6)=2
1204         id%KEEP(9)=3
1205         id%KEEP(39)=300
1206         id%CNTL(1)=0.1D0
1207         id%KEEP(213) = 101
1208         id%KEEP(85)=2
1209         id%KEEP(85)=-4
1210         id%KEEP(62) = 2
1211         id%KEEP(1)  = 1
1212         id%KEEP(51) = 2
1213!$       id%KEEP(360) = 2
1214!$       id%KEEP(361) = 2
1215!$       id%KEEP(362) = 1
1216!$       id%KEEP(363) = 2
1217         id%KEEP(364) = 10
1218         id%KEEP(420) = 4
1219         id%KEEP(488) = 4
1220         id%KEEP(490) = 5
1221         id%KEEP(491) = 5
1222         id%ICNTL(27)=-3
1223         id%KEEP(227)=3
1224      ELSE IF (id%KEEP(72)==2) THEN
1225         id%KEEP(85)=2            ! default is
1226         id%KEEP(85)=-10000         ! default is 160
1227         id%KEEP(62) = 10       ! default is 50
1228         id%KEEP(210) = 1       ! defaults is 0 (automatic)
1229         id%KEEP8(79) = 160000_8
1230         id%KEEP(1) = 2  ! default is 8
1231         id%KEEP(102) = 110     ! defaults is 150 up to 48 procs
1232         id%KEEP(213) = 121   ! default is 201
1233      END IF
1234      RETURN
1235      END SUBROUTINE DMUMPS_SET_KEEP72
1236