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