sym_mod Module



Contents


Functions

public elemental function SYMPROD(ISYM1, ISYM2)

Arguments

Type IntentOptional Attributes Name
type(Symmetry), intent(in) :: ISYM1
type(Symmetry), intent(in) :: ISYM2

Return Value type(Symmetry)

public elemental function SymConj(s2)

Arguments

Type IntentOptional Attributes Name
type(Symmetry), intent(in) :: s2

Return Value type(Symmetry)

public elemental function LSYMSYM(SYM)

Arguments

Type IntentOptional Attributes Name
type(Symmetry), intent(in) :: SYM

Return Value logical

public function GETIRREPDECOMP(CHARS, IRREPCHARS, NIRREPS, NROT, IDECOMP, CNORM, TAbelian)

Arguments

Type IntentOptional Attributes Name
complex(kind=dp) :: CHARS(NROT)
complex(kind=dp) :: IRREPCHARS(NROT,NIRREPS)
integer :: NIRREPS
integer :: NROT
type(Symmetry) :: IDECOMP
real(kind=dp) :: CNORM
logical :: TAbelian

Return Value logical

public elemental function LCHKSYM(isym, jsym)

Arguments

Type IntentOptional Attributes Name
type(BasisFN), intent(in) :: isym
type(BasisFN), intent(in) :: jsym

Return Value logical

public function LCHKSYMD(NI, NJ, NEL, G1, nBasisMax)

Arguments

Type IntentOptional Attributes Name
integer :: NI(NEL)
integer :: NJ(NEL)
integer :: NEL
type(BasisFN) :: G1(*)
integer :: nBasisMax(5,*)

Return Value logical

public function SYMLT(A, B)

Arguments

Type IntentOptional Attributes Name
type(Symmetry) :: A
type(Symmetry) :: B

Return Value logical

public function SYMNE(A, B)

Arguments

Type IntentOptional Attributes Name
type(Symmetry) :: A
type(Symmetry) :: B

Return Value logical

public function SYMEQ(A, B)

Arguments

Type IntentOptional Attributes Name
type(Symmetry) :: A
type(Symmetry) :: B

Return Value logical

public function SYMGT(A, B)

Arguments

Type IntentOptional Attributes Name
type(Symmetry) :: A
type(Symmetry) :: B

Return Value logical

public function FindSymLabel(s)

Arguments

Type IntentOptional Attributes Name
type(Symmetry) :: s

Return Value integer

public pure function ComposeAbelianSym(AbelSym)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: AbelSym(3)

Return Value integer(kind=int64)

public pure function TotSymRep()

Arguments

None

Return Value type(Symmetry)

public function MinSymRep()

Arguments

None

Return Value integer(kind=int64)

public function MaxSymRep()

Arguments

None

Return Value integer(kind=int64)

public pure function RandExcitSymLabelProd(SymLabel1, SymLabel2)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: SymLabel1
integer, intent(in) :: SymLabel2

Return Value integer

public recursive function checkMomentumInvalidity(nI, cK, targetK, rElsUp, rElsDown) result(momcheck)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: nI
integer, intent(in), dimension(3) :: cK
integer, intent(in), dimension(3) :: targetK
integer, intent(in) :: rElsUp
integer, intent(in) :: rElsDown

Return Value logical

public function KALLOWED(G, nBasisMax)

Arguments

Type IntentOptional Attributes Name
type(BasisFN), intent(in) :: G
integer :: nBasisMax(5,*)

Return Value logical


Subroutines

public subroutine WRITESYMTABLE(IUNIT)

Arguments

Type IntentOptional Attributes Name
integer :: IUNIT

public subroutine GENMOLPSYMTABLE(NSYMMAX, G1, NBASIS)

Arguments

Type IntentOptional Attributes Name
integer :: NSYMMAX
type(BasisFN) :: G1(*)
integer :: NBASIS

public subroutine FREEZESYMLABELS(NHG, NBASIS, GG, FRZ)

Arguments

Type IntentOptional Attributes Name
integer :: NHG
integer :: NBASIS
integer :: GG(NHG)
logical :: FRZ

public subroutine GENMOLPSYMREPS()

Arguments

None

public subroutine ENDSYM()

Arguments

None

public subroutine GENSymStatePairs(NSTATES, FRZ)

Arguments

Type IntentOptional Attributes Name
integer :: NSTATES
logical :: FRZ

public subroutine GenSymPairs(nSymLabels, iPass)

Arguments

Type IntentOptional Attributes Name
integer :: nSymLabels
integer :: iPass

public subroutine GENALLSymStatePairs(NSTATES, TSTORE, FRZ)

Arguments

Type IntentOptional Attributes Name
integer :: NSTATES
logical :: TSTORE
logical :: FRZ

public subroutine FindSymProd(Prod, SymPairProds, nSymPairProds, iProd)

Arguments

Type IntentOptional Attributes Name
type(Symmetry) :: Prod
type(SymPairProd) :: SymPairProds(nSymPairProds)
integer :: nSymPairProds
integer :: iProd

public subroutine getsym_wrapper(det, sym)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: det(nel)
type(BasisFN), intent(out) :: sym

public subroutine GETSYM(NI2, NEL, G1, nBasisMax, ISym)

Arguments

Type IntentOptional Attributes Name
integer :: NI2(NEL)
integer :: NEL
type(BasisFN) :: G1(*)
integer :: nBasisMax(5,*)
type(BasisFN) :: ISym

public subroutine GetLz(nI, NElec, Lz)

Arguments

Type IntentOptional Attributes Name
integer :: nI(NElec)
integer :: NElec
integer :: Lz

public subroutine GENIRREPS(TKP, IMPROPER_OP, NROTOP)

Arguments

Type IntentOptional Attributes Name
logical :: TKP
logical :: IMPROPER_OP(NROTOP)
integer :: NROTOP

public subroutine WRITEIRREPTAB(IUNIT, CHARS, NROT, NSYM)

Arguments

Type IntentOptional Attributes Name
integer :: IUNIT
complex(kind=dp) :: CHARS(NROT,NSYM)
integer :: NROT
integer :: NSYM

public subroutine WRITECHARS(IUNIT, CHARS, NROT, STR)

Arguments

Type IntentOptional Attributes Name
integer :: IUNIT
complex(kind=dp) :: CHARS(NROT)
integer :: NROT
character(len=6) :: STR

public subroutine WRITECHARSF(IUNIT, CHARS, NROT, STR, LCOMP, LREAL)

Arguments

Type IntentOptional Attributes Name
integer :: IUNIT
complex(kind=dp) :: CHARS(NROT)
integer :: NROT
character(len=6) :: STR
logical :: LCOMP
logical :: LREAL

public subroutine DECOMPOSEREP(CHARSIN, IDECOMP)

Arguments

Type IntentOptional Attributes Name
complex(kind=dp) :: CHARSIN(NROT)
type(Symmetry) :: IDECOMP

public subroutine GENSYMTABLE()

Arguments

None

public subroutine GENSYMREPS(G1, NBASIS, ARR, DEGENTOL)

Arguments

Type IntentOptional Attributes Name
type(BasisFN) :: G1(nBasis)
integer :: NBASIS
real(kind=dp) :: ARR(NBASIS,2)
real(kind=dp) :: DEGENTOL

public pure subroutine ADDELECSYM(iEl, G1, nBasisMax, ISYM)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: iEl
type(BasisFN), intent(in) :: G1(*)
integer, intent(in) :: nBasisMax(5,*)
type(BasisFN), intent(inout) :: ISYM

public pure subroutine roundsym(isym, nbasismax)

Arguments

Type IntentOptional Attributes Name
type(BasisFN), intent(inout) :: isym
integer, intent(in) :: nbasismax(5,*)

public pure subroutine MOMPBCSYM(K1, nBasisMax)

Arguments

Type IntentOptional Attributes Name
integer, intent(inout) :: K1(3)
integer, intent(in) :: nBasisMax(5,*)

public subroutine BINARYSEARCHSYM(VAL, TAB, LEN, LOC)

Arguments

Type IntentOptional Attributes Name
type(Symmetry) :: VAL
type(Symmetry) :: TAB(LEN)
integer :: LEN
integer :: LOC

public subroutine GENNEXTSYM(NEL, nBasisMax, TSPN, LMS, TPARITY, IPARITY, TSETUP, TDONE, IMax, ISYM)

Arguments

Type IntentOptional Attributes Name
integer :: NEL
integer :: nBasisMax(5,*)
logical :: TSPN
integer :: LMS
logical :: TPARITY
type(BasisFN) :: IPARITY
logical :: TSETUP
logical :: TDONE
type(BasisFN) :: IMax(2)
type(BasisFN) :: ISYM

public subroutine DOSYMLIMDEGEN(IMax, nBasisMax)

Arguments

Type IntentOptional Attributes Name
type(BasisFN) :: IMax(2)
integer :: nBasisMax(5,*)

public subroutine GETSYMDEGEN(ISym, nBasisMax, IDEGEN)

Arguments

Type IntentOptional Attributes Name
type(BasisFN) :: ISym
integer :: nBasisMax(5,*)
integer :: IDEGEN

public elemental subroutine setupsym(isym)

Arguments

Type IntentOptional Attributes Name
type(BasisFN), intent(inout) :: isym

public subroutine WRITEALLSYM(IUNIT, SYM, LTERM)

Arguments

Type IntentOptional Attributes Name
integer :: IUNIT
type(BasisFN) :: SYM
logical :: LTERM

public subroutine WRITESYM(IUNIT, SYM, LTERM)

Arguments

Type IntentOptional Attributes Name
integer :: IUNIT
type(Symmetry) :: SYM
logical :: LTERM

public subroutine SetupFreezeAllSym(Sym)

Arguments

Type IntentOptional Attributes Name
type(BasisFN) :: Sym

public subroutine SetupFreezeSym(Sym)

Arguments

Type IntentOptional Attributes Name
type(BasisFN) :: Sym

public subroutine GenKPtIrreps(nTranslat, nKps, KpntInd, nStates)

Arguments

Type IntentOptional Attributes Name
integer :: nTranslat
integer :: nKps
integer :: KpntInd(nStates)
integer :: nStates

public pure subroutine DecomposeAbelianSym(Isym, AbelSym)

Arguments

Type IntentOptional Attributes Name
integer(kind=int64), intent(in) :: Isym
integer, intent(out) :: AbelSym(3)

public subroutine IncrSym(Sym)

Arguments

Type IntentOptional Attributes Name
type(Symmetry) :: Sym

public subroutine GETSYMTMATSIZE(Nirrep, nBasis, iSS, iSize)

Arguments

Type IntentOptional Attributes Name
integer :: Nirrep
integer :: nBasis
integer :: iSS
integer(kind=int64) :: iSize