CONGEN  5.0
Configuration generation for SCATCI
congen_projection Module Reference

Projection on spin states. More...

Functions/Subroutines

subroutine, private cntrct (nelt, no, ndo, cdo, thres)
 Throw away determinants with negligible contribution. More...
 
subroutine, private dophz (nftw, nocsf, nelt, ndtrf, nconf, indo, ndo, lenndo, icdo, cdo, lencdo, iphz, leniphz, iphz0, leniphz0, nctarg, nctgt, notgt, mrkorb, mdegen, ntgsym, mcont, symtyp, npflg)
 Phase factor. More...
 
subroutine, private dophz0 (nftw, nocsf, nelt, ndtrf, nconf, indo, ndo, lenndo, icdo, cdo, lencdo, iphz, npflg)
 Phase factor. More...
 
integer function, private iphase (nconf, nelt)
 Sequence phase factor. More...
 
subroutine, private mkorbs (nob, nsym, mn, mg, mm, ms, norb, nsrb_in, map, mpos, iposit, nobl, nob0l, symtyp)
 Compute the orbital table. More...
 
subroutine, private pkwf (nod, ieltp, cdo, mdo, idopl, mdop, idcpl, mdcp, nftw, ndo, ndto, len_ndto, ithis_csf)
 Pack wave function. More...
 
subroutine, private pmkorbs (nob, nobe, nsym, mn, mg, mm, ms, nsrb, norb, nsrbd, map, mpos, iposit, symtyp)
 ? More...
 
subroutine, private popnwf (nsrb, nsrbs, nelt, ndtrf, mopmx, mdop, mdcp, mop, mdc, mdo, ndta, nod, nda, idop, idcp, ieltp, flip, nalm)
 Get open-shell part of determinants. More...
 
subroutine, private prjct (nelt, mxss, nodi, ndo, cdi, nodo, cdo, maxcdo, mgvn, iss, isd, thres, r, ndtr, mm, ms, maxndo, symtyp, nsrb)
 Apply Lowdin projection operator. More...
 
subroutine, public projec (sname, megul, symtyp, mgvn, s, sz, r, pin, nocsf, byproj, idiag, npflg, thres, nelt, nsym, nob, ndtrf, nftw, iposit, nob0, nob1, nob01, iscat, ntgsym, notgt, nctgt, mcont, gucont, mrkorb, mdegen, mflag, nobe, nobp, nobv, maxtgsym)
 Project the wave function. More...
 
subroutine, private ptpwf (nftw, nocsf, nelt, ndtrf, nodi, indi, icdi, ndi, cdi)
 Print the CSFs. More...
 
integer function, private qsort (n, a)
 Sort integer array. More...
 
subroutine, private rdwf (nft, k1, nodi, k2, cdi, k3, ndi)
 Read CSF. More...
 
subroutine, private rdwf_getsize (iunit, num_csfs, num_dets, len_dets)
 Reads the size of the wavefunction. More...
 
subroutine, private rfltn (nelt, nodi, ndi, cdi, r, mxnd, ndmxp, thres, nodo, cdo, ndtr, mm, bst)
 Add mirror-reflected spin-orbitals. More...
 
real(kind=wp) function, private snrm2 (n, array, istep)
 Real strided vector norm. More...
 
subroutine, private stmrg (nelt, maxcdo, maxndo, ndo, cdo, nodo, ndi, cdi, bst)
 Add determinant to a list of determinants. More...
 
subroutine, private wfgntr (mgvn, iss, isd, thres, r, symtyp, nelt, nsyml, nob, nobl, nob0l, nobe, norb, nsrb, mn, mg, mm, ms, iposit, map, mpos, nocsf, ndtrf, nodi, ndi, cdi, indil, icdil, maxndi, maxcdi, nodo, ndo, cdo, indo, icdo, maxndo, maxcdo, lenndo, lencdo, npflg, byproj, nftw, nalm)
 Form spin eigenstates. More...
 
subroutine, private wrnfto (sname, mgvn, s, sz, r, pin, norb, nsrb, nocsf, nelt, idiag, nsym, symtyp, nob, ndtrf, nodo, m, icdo, indo, ndo, lndi, cdo, lcdi, nfto, nobl, nx, npflg, thres, iposit, nob0, nob0l, nctarg, ntgsym, notgt, nctgt, mcont, gucont, iphz, nobe, nobp, nobv, maxtgsym)
 WRNFTO - WRite wavefunction data to unit NFTO. More...
 
subroutine, private wrwf (nft, n1, nodo, n2, cdo, n3, ndo)
 Write wave functions using SPEEDY format. More...
 

Detailed Description

Routines in this module, most prominently the central subroutine projec, read back all CSFs generated in the previous part of CONGEN execution and recombine the determinants to satisfy spin composition rules. While doing that, several new combinations of spin-orbitals (determinants) may be added if there are any open shells where the electrons spins can be freely permuted. Also, the routines apply a threshold for final selection of contributing determinants, so the output can be even smaller than the input (though this mostly signalizes some error in setup).

Function/Subroutine Documentation

◆ cntrct()

subroutine, private congen_projection::cntrct ( integer, intent(in)  nelt,
integer, intent(inout)  no,
integer, dimension(*), intent(inout)  ndo,
real(kind=wp), dimension(*), intent(inout)  cdo,
real(kind=wp), intent(in)  thres 
)
private

Scans the store of determinants, discard such whose contribution (multiplication factor) is below given tolerance, and bubbles out the vacated intervals from the storage arrays.

Definition at line 66 of file congen_projection.f90.

Referenced by prjct(), and rfltn().

Here is the caller graph for this function:

◆ dophz()

subroutine, private congen_projection::dophz ( integer  nftw,
integer  nocsf,
integer  nelt,
integer, dimension(nelt)  ndtrf,
integer, dimension(nelt)  nconf,
integer, dimension(nocsf)  indo,
integer, dimension(lenndo)  ndo,
integer  lenndo,
integer, dimension(nocsf)  icdo,
real(kind=wp), dimension(:), allocatable  cdo,
integer  lencdo,
integer, dimension(leniphz)  iphz,
integer  leniphz,
integer, dimension(leniphz0)  iphz0,
integer  leniphz0,
integer  nctarg,
integer, dimension(ntgsym)  nctgt,
integer, dimension(ntgsym)  notgt,
integer, dimension(ntgsym)  mrkorb,
integer, dimension(ntgsym)  mdegen,
integer  ntgsym,
integer, dimension(ntgsym)  mcont,
integer  symtyp,
integer  npflg 
)
private

Compute phase factor implied by placing continuum spin-orbital after all target spin-orbitals

Note
MAL 10/05/2011 Changes made are in order to bring dophz into line with the changes made in 'projec' in order to utilize dynamic memory

Definition at line 107 of file congen_projection.f90.

References iphase().

Referenced by projec().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ dophz0()

subroutine, private congen_projection::dophz0 ( integer  nftw,
integer  nocsf,
integer  nelt,
integer, dimension(nelt)  ndtrf,
integer, dimension(nelt)  nconf,
integer, dimension(nocsf)  indo,
integer, dimension(lenndo)  ndo,
integer  lenndo,
integer, dimension(nocsf)  icdo,
real(kind=wp), dimension(lencdo)  cdo,
integer  lencdo,
integer, dimension(nocsf)  iphz,
integer  npflg 
)
private

Compute phase factor for target CSFs - given by reordering spin-orbitals in ascending order.

Todo:
MAL 10/05/2011: Changes have been made to this subroutine to bring it into line with the changes made to 'projec' and ensure to compliance with F95 standards

Definition at line 232 of file congen_projection.f90.

References iphase().

Referenced by projec().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ iphase()

integer function, private congen_projection::iphase ( integer, dimension(nelt), intent(in)  nconf,
integer, intent(in)  nelt 
)
private

Compute phase factor (if any) due to out of sequence ordering of spin-orbitals in CSF stored in nconf.

Definition at line 283 of file congen_projection.f90.

Referenced by dophz(), dophz0(), and projec().

Here is the caller graph for this function:

◆ mkorbs()

subroutine, private congen_projection::mkorbs ( integer, dimension(nsym)  nob,
integer  nsym,
integer, dimension(nsrb_in)  mn,
integer, dimension(nsrb_in)  mg,
integer, dimension(nsrb_in)  mm,
integer, dimension(nsrb_in)  ms,
integer  norb,
integer  nsrb_in,
integer, dimension(norb)  map,
integer, dimension(nsrb_in)  mpos,
integer  iposit,
integer, dimension(*)  nobl,
integer, dimension(nsym)  nob0l,
integer  symtyp 
)
private

Computes the orbital table which is then used in the projection step. This is called from projec().

    Input data:
       ISYMTYP  Switch for C-inf-v (=0 or 1) / Abelian point group (=2
           NOB  Number of orbitals per symmetry
          NSYM  Number of symmetries in the orbital set
         NPFLG  Flag controlling printing of computed orbital table

    Output data:
             MN  Orbital number associated with each spin-orbital
             MG  G/U designation for each spin-orbital (C-inf-v only)
                 Actually this is always zero because C-inf-v does not
                 distinguish between g/u. It exists because original
                 version of Alchemy tried to use it for D-inf-h too;
                 all CI evauation is doen in C-inf-v now because CONGE
                 converts D-inf-h to C-inf-v data.
             MM  Symmetry quantum number associated with each spin-orb
             MS  Spin function ( alpha or beta ) associated with each
                 spin orbital

    Notes:

     The orbital table establishes orbital and quantum number data for
    each spin orbital in the set.

    e.g. C-inf-v symmetry with NSYM=2, NOB=3,1, yields ten spin
         orbitals which are designated as follows by this routine:

       Spin orb.     MN  MG  MM  MS     Comments
           1          1   0   0   0     1 sigma spin up
           2          1   0   0   1     1 sigma spin down
           3          2   0   0   0     2 sigma spin up
           4          2   0   0   1     2 sigma spin down
           5          3   0   0   0     3 sigma spin up
           6          3   0   0   1     3 sigma spin down
           7          4   0   1   0     1 pi(lambda=+1) spin up
           8          4   0   1   1     1 pi(lambda=+1) spin down
           9          4   0  -1   0     1 pi(lambda=-1) spin up
          10          4   0  -1   1     1 pi(lambda=-1) spin down
Note
MAL 11/05/2011 : Changes made here are to bring the subroutine into line with the changes that were made in 'projec' in order to utilize dynamic memory and also to comply with the F95 standard

Definition at line 372 of file congen_projection.f90.

References congen_data::nftw.

Referenced by projec().

Here is the caller graph for this function:

◆ pkwf()

subroutine, private congen_projection::pkwf ( integer  nod,
integer  ieltp,
real(kind=wp), dimension(nod)  cdo,
integer, dimension(nod*ieltp)  mdo,
integer  idopl,
integer, dimension(idopl)  mdop,
integer  idcpl,
integer, dimension(idcpl)  mdcp,
integer  nftw,
integer  ndo,
integer, dimension(len_ndto)  ndto,
integer  len_ndto,
integer  ithis_csf 
)
private

Reformats (packs) the CSF expression into the style used throughout the rest of Alchemy, that is as a set of replacements from the reference determinant. Adds this to the end of the array ntdo() from location "ndo".

On entry to this routine we have the CSF defined for us as follows (from the projection step):

  1. there are "nod" determinants
  2. each determinant is of length "ieltp".
  3. "cdo" contains the coefficient which multiplies each determinant. This is derived from the coupling process.
  4. the determinants are stored in "mdo", as a list of spin orbitals - so it is of lenth nod*ieltp

The above information is complemented by the analysis in the calling routine which classifies spin orbitals in this CSF wrt the reference determinant:

  1. "idopl" is the number of spin orbs in the reference det but not present in this CSF; "mdop()" is the list of those spin orbitals
  2. "idcpl" is the number of spin orbs in this CSF but not present in the reference determinant; "mdcp()" is the list of those spin orbitals.

So, given all of the above information, the determinants in "mdo" are processed and each expressed in the format

  • number of replacements from ref determinant
  • list of replaced spin orbitals
  • list of replacing spin orbitals

The output is placed into array "ndto". The length available in "ndto" is passed into the routing in "len_ndto" and this is monitored to be sure we do not overflow it.

During the process, it may be necessary to multiply "cdo" by -1 as we order spin orbitals. cdo() holds the coefficients associated with each determinant. These were constructed earlier in the spin projection - note we only receive the relevant "piece" of the cdo(0 array in the arglist, the bit for this CSF, not all of it for all CSFs, as is the case with "ndto()". "nftw" is the logical unit for the printer

Note
MAL 11/05/2011: Changes made here are to bring the subroutine into line with the changes that were made in 'projec' in order to utilize dynamic memory and to comply with the F95 standard.

Definition at line 655 of file congen_projection.f90.

Referenced by wfgntr().

Here is the caller graph for this function:

◆ pmkorbs()

subroutine, private congen_projection::pmkorbs ( integer, dimension(nsym)  nob,
integer, dimension(nsym)  nobe,
integer  nsym,
integer, dimension(nsrb)  mn,
integer, dimension(nsrb)  mg,
integer, dimension(nsrb)  mm,
integer, dimension(nsrb)  ms,
integer  nsrb,
integer  norb,
integer  nsrbd,
integer, dimension(norb)  map,
integer, dimension(nsrb)  mpos,
integer  iposit,
integer  symtyp 
)
private

Definition at line 809 of file congen_projection.f90.

References congen_data::nftw.

Referenced by projec().

Here is the caller graph for this function:

◆ popnwf()

subroutine, private congen_projection::popnwf ( integer  nsrb,
integer  nsrbs,
integer  nelt,
integer, dimension(nelt)  ndtrf,
integer  mopmx,
integer, dimension(nelt)  mdop,
integer, dimension(nelt)  mdcp,
integer, dimension(mopmx)  mop,
integer, dimension(nsrb)  mdc,
integer, dimension(nsrb)  mdo,
integer, dimension(nsrb)  ndta,
integer  nod,
integer, dimension(*)  nda,
integer  idop,
integer  idcp,
integer  ieltp,
logical, dimension(nod)  flip,
integer  nalm 
)
private

Fills the array mop with subset of specification of every determinant for the current CSF. Only spin-orbitals that are in open shells are used, as the rest does not participate in spin composition done later in prjct. The written spin-orbitals are also immediately sorted in non-descending order. The even or odd number of swaps needed for sorting is returned (as .false. and .true., respectively) via the logical array flip, so that the sign of determinant coefficients within this CSF can be adjusted to the used order.

     OUTPUT IDOP        NO OF SO IN DR BUT NOT IN DC
            MDOP(NELT)        SO IN DR BUT NOT IN DC
            IDCP        NO OF SO IN DC BUT NOT IN DR
            MDCP(NELT)        SO IN DC BUT NOT IN DR
            IELTP       NO OF SO IN OPEN SHELLS FOR A DTR
            MOP(MOPMX)  SO
Note
In the original code there was a common block
          /OWF/ IDOP,IDCP,IELTP
which was used to pass three integer values back to the caling routine. these have now been placed into the argument list; correspondingly the routine WFGNTR has been modified. It is the only routine whihc calls this one. the purpose of the variables is as follows:
            IDOP  holds the number of entries in MDOP 
            IDCP  holds the number of entries in MDCP
            IELTP is the number of electrons in open shell

Definition at line 949 of file congen_projection.f90.

References qsort().

Referenced by wfgntr().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ prjct()

subroutine, private congen_projection::prjct ( integer  nelt,
integer  mxss,
integer  nodi,
integer, dimension(maxndo), target  ndo,
real(kind=wp), dimension(*)  cdi,
integer  nodo,
real(kind=wp), dimension(maxcdo)  cdo,
integer  maxcdo,
integer  mgvn,
integer  iss,
integer  isd,
real(kind=wp)  thres,
real(kind=wp)  r,
integer, dimension(nsrb)  ndtr,
integer, dimension(nsrb)  mm,
integer, dimension(nsrb)  ms,
integer  maxndo,
integer  symtyp,
integer  nsrb 
)
private

This routine applies the Lowdin projection operator. More details can be found in the literature at for example:

       Nelson F Beebe and Sten Lucil, J Phys B: At Mol Phys, Vol. 8, Issue 14, 1975, p2320

This routine is called when a CSF is found to have two, or more electrons in open shells. Each pair of spin-orbitals in each determinant is examined and potentially used to create a new determinant. Thus the output expression for the CSF

       nodo, cdo(), ndo()

may be much larger than the input

       nodi, cdi(), ndo()                       

Note reuse of ndo() here. cdi() is used an an extendable buffer too and must have more than "nodi" elements.

The generated list of determinants is examined for any with very small coefficients (thres) and these are removed. Thus the the list may grow and shrink in this routine.

Of course the nature of the projection process is controlled by the quantum numbers input.

The routine terminates with an error message if any error conditions are found.

Definition at line 1310 of file congen_projection.f90.

References cntrct(), qsort(), rfltn(), snrm2(), and stmrg().

Referenced by wfgntr().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ projec()

subroutine, public congen_projection::projec ( character(len=80)  sname,
integer  megul,
integer  symtyp,
integer  mgvn,
real(kind=wp)  s,
real(kind=wp)  sz,
real(kind=wp)  r,
real(kind=wp)  pin,
integer  nocsf,
integer  byproj,
integer  idiag,
integer, dimension(6)  npflg,
real(kind=wp)  thres,
integer  nelt,
integer  nsym,
integer, dimension(nsym)  nob,
integer, dimension(nelt)  ndtrf,
integer  nftw,
integer  iposit,
integer, dimension(nsym)  nob0,
integer, dimension(*)  nob1,
integer, dimension(nsym)  nob01,
integer, intent(in)  iscat,
integer, intent(inout)  ntgsym,
integer, dimension(ntgsym)  notgt,
integer, dimension(ntgsym)  nctgt,
integer, dimension(ntgsym)  mcont,
integer, dimension(ntgsym)  gucont,
integer, dimension(ntgsym)  mrkorb,
integer, dimension(ntgsym)  mdegen,
integer, intent(in)  mflag,
integer, dimension(nsym)  nobe,
integer, dimension(nsym)  nobp,
integer, dimension(nsym)  nobv,
integer  maxtgsym 
)

The subroutine projec controls the projection of the wavefunctions and writes out the final wavefunctions plus header information for future use.

Note
MAL 06/05/11 PROJEC has been considerably modified to take advantage of dynamic memory allocation.

Definition at line 1646 of file congen_projection.f90.

References dophz(), dophz0(), iphase(), mkorbs(), pmkorbs(), ptpwf(), rdwf(), rdwf_getsize(), wfgntr(), wrnfto(), and wrwf().

Referenced by congen_driver::csfgen().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ ptpwf()

subroutine, private congen_projection::ptpwf ( integer, intent(in)  nftw,
integer, intent(in)  nocsf,
integer, intent(in)  nelt,
integer, dimension(*), intent(in)  ndtrf,
integer, dimension(*), intent(in)  nodi,
integer, dimension(*), intent(in)  indi,
integer, dimension(*), intent(in)  icdi,
integer, dimension(*), intent(in)  ndi,
real(kind=wp), dimension(*), intent(in)  cdi 
)
private

This provides a complete text dump of all CSFs in terms of their packed determinants.

Parameters
nftwFile unit for text output of the program.
nocsfNumber of wave functions (CSFs).
neltNumber of electrons (and size of ndtrf).
ndtrfReference determinant (spinorbitals per electron).
nodiArray with number of determinants per CSF.
indiArray with offsets in ndi per CSF.
icdiArray with offsets in cdi per CSF.
ndiPacked determinants.
cdiDeteminant coefficients.

Definition at line 2614 of file congen_projection.f90.

Referenced by projec().

Here is the caller graph for this function:

◆ qsort()

integer function, private congen_projection::qsort ( integer, intent(in)  n,
integer, dimension(n), intent(inout)  a 
)
private
Authors
J Benda
Date
2018

Sort array in-place in non-descending order. Currently implemented as a stable insertion sort. This algorithm is advantageous for short and almost sorted arrays, which is the case for augmented open-shell-only subsets of determinants in CONGEN, typically resulting in asymptotic complexity of O(n).

Parameters
nLength of the array to sort.
aInteger array to sort.
Returns
Number of swaps done. This is needed elsewhere to update determinant signs.

Definition at line 2657 of file congen_projection.f90.

Referenced by popnwf(), prjct(), and rfltn().

Here is the caller graph for this function:

◆ rdwf()

subroutine, private congen_projection::rdwf ( integer  nft,
integer  k1,
integer, dimension(*)  nodi,
integer  k2,
real(kind=wp), dimension(*)  cdi,
integer  k3,
integer, dimension(*)  ndi 
)
private

Routine congen_distribution::wfn stores the CSF data in buffers of fixed size.

When the buffers are full, they are emptied to disk and reused. This is why we can have several sets to read here.

Definition at line 2699 of file congen_projection.f90.

Referenced by projec().

Here is the caller graph for this function:

◆ rdwf_getsize()

subroutine, private congen_projection::rdwf_getsize ( integer  iunit,
integer  num_csfs,
integer  num_dets,
integer  len_dets 
)
private

Reads the information giving the size of the data used for the wavefunction, for example the number of determinants, but does not read the actual data, such as the determinants.

This is really just a stripped down version of the routine rdwf which reads the full data.

Parameters
iunitThe logical unit on which the wavefucntion data is located.
num_csfsOn return, number of CSFs stored in the file.
num_detsOn return, number of determinants summed over all CSFs in the file.
len_detsOn return, total summed length of all arrays of packed determinants in the file.
Note
MAL 10/05/2011: This subroutine is new to congen and is included to bring congen into line with the changes that were made in projec in order to utilize dynamic memory

Definition at line 2748 of file congen_projection.f90.

Referenced by projec().

Here is the caller graph for this function:

◆ rfltn()

subroutine, private congen_projection::rfltn ( integer  nelt,
integer, intent(in)  nodi,
integer, dimension(*)  ndi,
real(kind=wp), dimension(*), intent(in)  cdi,
real(kind=wp), intent(in)  r,
integer  mxnd,
integer  ndmxp,
real(kind=wp)  thres,
integer, intent(inout)  nodo,
real(kind=wp), dimension(*)  cdo,
integer, dimension(*)  ndtr,
integer, dimension(*), intent(in)  mm,
type(det_tree), intent(inout)  bst 
)
private

Used only for C_infv and D_infh.

Definition at line 2794 of file congen_projection.f90.

References cntrct(), qsort(), and stmrg().

Referenced by prjct().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ snrm2()

real(kind=wp) function, private congen_projection::snrm2 ( integer, intent(in)  n,
real(kind=wp), dimension(*), intent(in)  array,
integer, intent(in)  istep 
)
private

This is actually an in-house version of the BLAS level 1 routine of the same name, included here to avoid dependency on BLAS library.

Parameters
nLength of the vector
arrayVector of real numbers
istepStride
Returns
Square of L2 norm of the vector.

Definition at line 2844 of file congen_projection.f90.

Referenced by prjct(), and wfgntr().

Here is the caller graph for this function:

◆ stmrg()

subroutine, private congen_projection::stmrg ( integer  nelt,
integer  maxcdo,
integer  maxndo,
integer, dimension(maxndo)  ndo,
real(kind=wp), dimension(maxcdo)  cdo,
integer  nodo,
integer, dimension(nelt)  ndi,
real(kind=wp)  cdi,
type(det_tree bst 
)
private

Given an existing list of determinants in cdo()/ndo() and a new single determinant cdi/ndi(), the new determinant is merged into the list and the list extended if necessary.

This operation is used during spin-projection of a CSF.

Note
MAL 16/05/11 : Modified to bring the subroutine into line with the changes made to projec
Parameters
neltNumber of electrons in each det.
maxcdoDimension of cdo.
maxndoDimension of ndo.
ndoList of determinants each with "nelt" spin-orbitals.
cdoCoefficient for each det in ndo.
nodoOn input is the number of determinants in cdo/ndo. Will be updated for output if the data in cdi/ndi new entry.
ndiA single det of "nelt" spin orbs which has to be merged into ndo.
cdiSingle coefficient going with the single determinant defined in ndi.
bstBinary search tree used for fast localization of determinants.

Definition at line 2888 of file congen_projection.f90.

Referenced by prjct(), and rfltn().

Here is the caller graph for this function:

◆ wfgntr()

subroutine, private congen_projection::wfgntr ( integer  mgvn,
integer  iss,
integer  isd,
real(kind=wp)  thres,
real(kind=wp)  r,
integer  symtyp,
integer  nelt,
integer  nsyml,
integer, dimension(nsyml)  nob,
integer, dimension(nsyml)  nobl,
integer, dimension(nsyml)  nob0l,
integer, dimension(nsyml)  nobe,
integer  norb,
integer  nsrb,
integer, dimension(nsrb)  mn,
integer, dimension(nsrb)  mg,
integer, dimension(nsrb)  mm,
integer, dimension(nsrb)  ms,
integer  iposit,
integer, dimension(nsrb)  map,
integer, dimension(nsrb)  mpos,
integer  nocsf,
integer, dimension(nelt)  ndtrf,
integer, dimension(nocsf)  nodi,
integer, dimension(maxndi)  ndi,
real(kind=wp), dimension(maxcdi)  cdi,
integer, dimension(nocsf+1)  indil,
integer, dimension(nocsf+1)  icdil,
integer  maxndi,
integer  maxcdi,
integer, dimension(nocsf)  nodo,
integer, dimension(maxndi)  ndo,
real(kind=wp), dimension(maxcdi)  cdo,
integer, dimension(nocsf+1)  indo,
integer, dimension(nocsf+1)  icdo,
integer  maxndo,
integer  maxcdo,
integer  lenndo,
integer  lencdo,
integer, dimension(6)  npflg,
integer  byproj,
integer  nftw,
integer  nalm 
)
private

Takes the wavefunction generated by CSFGEN and transforms it to be fully in accord with the spin quantum numbers of the system.

Note
MAL 10/05/2011: The changes made to wfgntr have made so as to make the subroutine compatible with the changes made to its calling subroutine, projec.

Definition at line 3003 of file congen_projection.f90.

References pkwf(), popnwf(), prjct(), and snrm2().

Referenced by projec().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ wrnfto()

subroutine, private congen_projection::wrnfto ( character(80)  sname,
integer  mgvn,
real(kind=wp)  s,
real(kind=wp)  sz,
real(kind=wp)  r,
real(kind=wp)  pin,
integer  norb,
integer  nsrb,
integer  nocsf,
integer  nelt,
integer  idiag,
integer  nsym,
integer  symtyp,
integer, dimension(nsym)  nob,
integer, dimension(nelt)  ndtrf,
integer, dimension(nocsf)  nodo,
integer  m,
integer, dimension(m)  icdo,
integer, dimension(m)  indo,
integer, dimension(lndi)  ndo,
integer  lndi,
real(kind=wp), dimension(lcdi)  cdo,
integer  lcdi,
integer  nfto,
integer, dimension(nx)  nobl,
integer  nx,
integer, dimension(6)  npflg,
real(kind=wp)  thres,
integer  iposit,
integer, dimension(nsym)  nob0,
integer, dimension(nx)  nob0l,
integer  nctarg,
integer  ntgsym,
integer, dimension(ntgsym)  notgt,
integer, dimension(ntgsym)  nctgt,
integer, dimension(ntgsym)  mcont,
integer, dimension(ntgsym)  gucont,
integer, dimension(nctarg)  iphz,
integer, dimension(nsym)  nobe,
integer, dimension(nsym)  nobp,
integer, dimension(nsym)  nobv,
integer  maxtgsym 
)
private
Note
MAL 10/05/2011 : This subroutine has been changed to bring it into line with the changes that have been made to 'projec' in order to utilize dynamic memory. 'wrnfto' has also been modified in order to comply to the F95 standard

Definition at line 3615 of file congen_projection.f90.

Referenced by projec().

Here is the caller graph for this function:

◆ wrwf()

subroutine, private congen_projection::wrwf ( integer, intent(in)  nft,
integer, intent(in)  n1,
integer, dimension(n1), intent(in)  nodo,
integer, intent(in)  n2,
real(kind=wp), dimension(n2), intent(in)  cdo,
integer, intent(in)  n3,
integer, dimension(n3), intent(in)  ndo 
)
private

This subroutine writes all determinants in the current CSF to a binary file that has the following format:

    [WP] n1, [INTEGER] nodo(1:n1)
    [WP] n2, [WP]      cdo(1:n2)
    [WP] n3, [INTEGER] ndo(1:n3)

On entry, the file will be rewindws to its beginning. On return, the output file is rewinded to its beginning, again.

Parameters
nftAn open binary file for output.
n1Length of nodo (number of determinants).
nodoDeterminant sizes.
n2Length of cdo (number of determinants).
cdoDeterminant factors within the CSF.
n3Length of ndo (number of integers defining the determinants).
ndoPacked determinants.

Definition at line 3739 of file congen_projection.f90.

Referenced by projec().

Here is the caller graph for this function: