Contents Prev Manual

SUBROUTINE F2NEW(L)

Outputs a new LSQ family 2 (structure parameters) card (for A, T
or F cards ).

Arguments:

On entry L is the position in the alphabet of the first letter of the card:
L = 1, 6 OR 20 for A, F OR T.

Prerequisite calls:

The card should have been read to ICARD in /SCRACH/.

Output:

Outputs to unit NEWIN a new card, with altered parameters if necessary.

Calls:

CONATF ERRIN2 IATOM INPUTA INPUTF INPUTT ISCAT LENGT

Called by:

NWINSF

Common blocks used:

/ANISO/ to use ATF IAPT IATYP
/CARDRC/ to use SDREAD
/FORMDA/ to use CMULT
/NEWOLD/ to use NEWIN
/POSNS/ to use TF SITE SDX SDTF SDSITE

*** F2NEW updated by JCM 6 Feb 90 ***

Classification:

General Least Squares Refinement . . . . . . . Crystallographic

SUBROUTINE F2PARP

Dummy routine to force inclusion of BLOCK DATA F2PARS

Calls:

DUMMY

Called by:

LSETSF

Classification:

Specific Least Squares Refinement . . . . . . . Setting Up

SUBROUTINE F2RELA(IFAM,ISPVEC)

Collects all structure factor type constraints implied by the
symmetry.

Arguments:

IFAM gives family number; so far this is 2 for structure parameters,
but it may one day be more general

ISPVEC is a vector holding miscellaneous pointers saying which parameters
within family IFAM, genus IR(=which atom) the following are: (1) x position coord (2) B11 first atf coefficient (3) f, the scattering factor with room for others which may be required later

Prerequisite calls:

JPHASE, JSOURC hold phase and source

Description:

Space group symmetry generated constraints are each between 2 parameters only, and refer to x, y, z coordinates, or to anisotropic coefficients
Some of the relations found may lead to fixings rather than constraints (Later - if magnetic, do the constraints on the magnetic pars here also)
We also chain together here the scattering factors of like atoms and fix any non-existent atfs. In the process, we check that the given atfs have the correct symmetry to start with.

Calls:

FIXPAR FIXREL GMEQ GMREV GMUNI KPAK RELSM3 RELSM6 ADDFX5

Called by:

PARSSF

Common blocks used:

/ANISO/ to use IAPT
/FORMDA/ to use NFORMF NBAKF
/PHASE/ to use JPHASE
/POSNS/ to use NATOM ISGEN
/SYMDA/ to use SYM

*** F2RELA updated by JCM 8 Sep 88 ***

Classification:

General Least Squares Refinement . . . . . . . Crystallographic

SUBROUTINE F2SHFT

Applies a shift to a particular family 2 (structure) parameter.

Prerequisite calls:

On entry in/NEWOLD/ IGEN=which atom and ISPC=which parameter
SHIFT is the LSQ matrix inversion shift
ESD is the its esd.

Calls:

ADJUST CONATF

Called by:

APSHSF

Common blocks used:

/ANISO/ to use ATF IAPT
/FORMDA/ to use NFORMF CMULT
/NEWOLD/ to use SHIFT ESD IGEN ISPC
/POSNS/ to use TF SITE SDX SDTF SDSITE

*** F2SHFT updated by JCM 10 Feb 87 ***

Classification:

General Least Squares Refinement . . . . . . . Crystallographic

SUBROUTINE F2VAR8(NG,NS,NV)

Records varying information for a particular family 2 (structure)
parameter.

Arguments:

On entry NG is the genus (which atom)
NS is the species
NV is which variable it will be

Description:

Records the information for future consultation

Entries:

F2VAR9 called by: VARSMG VARSSF

Called by:

VARSMG VARSSF

Common blocks used:

/ANISO/ to use KATF IAPT
/FORMDA/ to use KCMULT
/POSNS/ to use NATOM KX KTF KSITE

*** F2VAR8 corrected by PJB 30-Jan-98 ***

Classification:

General Least Squares Refinement . . . . . . . Setting Up

SUBROUTINE FACGRP(ISTAB,ISFTAB,NFAC)

Finds the factor elements which generate a space group from one of
its sub-groups.

Arguments:

On entry:
ISTAB(I) is positive if element I is in S.
ISTAB(I) is negative if S is non-centric and only the centre
related partner is in S

ISTAB(NOPC+1) is zero if G is non-centrosymmetric
+1 if S is centric, -1 if it is non-centric

On exit:
IFTAB(I) defines the factorisation.
IFTAB(I) =1 if I is in S,
= I if I is a member of F for all other elements IFTAB(N)=I where MULTAB(I,J)=N and J is an element of S.
Negative values of the entries indicate that it is the centre related partner that is required.

IFTAB(NOPC+1) = ISTAB(NOPC+1) set as above
NFAC is the multiplicity of F

Description:

To extract the factor group F of space group G given a subgroup S such that FxS=G

Notes:

ISTAB and IFTAB may refer to the same vector in the calling routine

Calls:

ADDELM JGMEQ JGMZER

Called by:

MAGCON MAGSYM MUCALC

Common blocks used:

/NSYM/ to use NOPC
/SYMTAB/ to use MULTAB

*** FACGRP rewritten by PJB March 2006 ***

Classification:

Basic Crystallography . . . . . . . Setting Up

FUNCTION FACT(K)

Calculates factorial K.

Arguments:

On entry K holds an integer which is positive or zero.
On exit FACT holds factorial K

Calls:

ERRIN2

Called by:

DIJROT DOCHI1 EXPINT RADFUN VECOUP FORFAC OVERLA

*** FACT by PJB 19 Jan 85 ***

Classification:

Mathematical Functions . . . . . . . Utility

COMPLEX FUNCTION FCALC(H)

Calculates the COMPLEX nuclear structure factor for the reflection
H.

Arguments:

On entry H is a 1x3 read vector holding h,k,l.
On exit FCALC holds the COMPLEX nuclear structure factor

Prerequisite calls:

PREFIN, RECIP, SYMOP, SETFOR, ATOPOS and SETANI must be called before the first call to FCALC. (All these except PREFIN are all in SETFC)

Description:

Forms sin theta/lambda and leaves it in STHL in /BRAGG
Cycles over atomic positions, then over symmetry operators, forming
COMPLEX FCALC by the usual formula.
Applies scattering factor, site occupation factor, multiplicity of atom and individual isotropic or anisotropic temperature factors.

Calls:

ANITF FORMFA ROTSYM SCALPR VCTMOD

Called by:

ADDFC CALMSF CALQSF GENREF GETMSF GETSFZ MAGPOW POWDER

Common blocks used:

/BRAGG/ to use STHL
/CONSTA/ to use TWOPI
/FORMDA/ to use NFORMF
/NSYM/ to use NOPC CENTRC
/POSNS/ to use NATOM AMULT TF SITE
/SYMDA/ to use TRANS

*** FCALC by JCM 19 Jul 83 ***

Classification:

Structure Factor Calculations . . . . . . . Crystallographic

SUBROUTINE FCHALC(H,FMCMOD,FMCSQR)

Calculates induced magnetic interaction vectors and magnetic
structure factors. with anisotropic susceptibilities

Arguments:

On entry H is the 1x3 vector containing h,k,l
On exit FMCMOD = domain average of the lengths of the m.i. vector
FMCSQR = square of the above

Prerequisite calls:

STHL in /BRAGG should hold sin theta/lambda
NKSTAR in /SATELL should have been set up by routine PROPER
The setting up routines:
RECIP (for the cell parameters)
SYMOP (for the space group symmetry)
SETFOR (for the scattering factors, both nuclear and magnetic)
SETANI (for the anisotropic temperature factors)
DOCHI(1) and (2) (for the susceptibilities)
should all have been obeyed to set up the structure.

Description:

On exit Q(1:3,1:NDOM) in COMMON QCAL contains the magnetic interaction vectors for each of the NDOM domains.
Sets SSQRD in /BRAGG to be STHL squared
Gives zero as answers for magnetic absences

Notes:

There is also the routine LMCALC which does a similar calculation but also calculates derivatives, for use in LSQ.

Calls:

ANITF C1MSCA CGMADD CGMSCA CGMZER CMRSCA FORMFA GMPRD GMSUB MAGABS ORTHO RCMPRD ROTSYM RSCALP SCALPR UNIVEC

Common blocks used:

/BRAGG/ to use STHL SSQRD
/CONSTA/ to use TWOPI VALMUB
/MAGCHI/ to use all members
/MAGDAT/ to use NMAG JMAGAT NMFORM
/NSYM/ to use NOPC CENTRC
/POSNS/ to use AMULT TF SITE
/SYMDA/ to use TRANS

*** FCHALC new by PJB May 2001 ***

Classification:

Magnetic Structure Factors . . . . . . . Crystallographic

SUBROUTINE FCTOR(H,N)

Finds the highest common factor of a set of indices and reduces
them by that factor.

Arguments:

On entry H is a 1x3 array holding 3 reals, usually h,k,l
On exit N is the integer highest common factor of the elements of H, assumed integral, and H has been divided through by N

Calls:

JFIX

Called by:

AXIS FIXUNI INVENT LATVCS PRMTIV SETGEN TRYUNI UNITID

*** FCTOR by PJB/JCM 28 Jun 83 ***

Classification:

Basic Crystallography . . . . . . . Utility

SUBROUTINE FETSHF(N,SH,ES)

Fettles a shift and esd for printing and counts, in the
application of shifts in LSQ.

Arguments:

On entry N indicates which action is required:
N=1 initialise
N=2 add in to totals
N=3 print at cycle end
On entry 2 SH holds the shift
ES holds the esd

Prerequisite calls:

In /NEWOLD/ ISHFT = number of shifts dealt with so far in this cycle,
AVSHFT=the sum of their SHIFT/ESD so far,
AMAXSH=the maximum SHIFT/ESD so far.

Description:

Updates ISHFT, AVSHFT and AMAXSH

Calls:

TESTOV

Called by:

APSHDS APSHSF DOMPL2 PRMBLK

Common blocks used:

/IOUNIT/ to use LPT
/NEWOLD/ to use SHESD ISHFT AVSHFT AMAXSH
/REFINE/ to use ICYC

*** FETSHF updated by JCM 21 Mar 89 ***

Classification:

General Least Squares Refinement . . . . . . . Utility

SUBROUTINE FETTLE(X,IFIELD,IFDIG)

Decides field width and fractional part of real number in order to
print it.

Arguments:

On entry X holds the real number.
On exit IFDIG is the minimum number of digits in which the
fractional part of X may be printed (up to 4)

IFIELD is the corresponding necessary total field width.

Calls:

FRACT INTDIG JFIX

Called by:

MAPDRW PLOTO PLTTXT

*** FETTLE by JCM 8 Jun 82 ***

Classification:

CCSL Input/Output Routines . . . . . . . Utility

SUBROUTINE FF01A(VJS,VYS,XS,N)

Modified Harwell routine for zero order Bessel functions.

Called by:

BJ

*** FF01A from HARWELL LIBRARY modified by JCM 17 Jan 85 ***

Classification:

Mathematical Functions . . . . . . . Utility

SUBROUTINE FF02A(VJS,VYS,S,N)

Modified Harwell routine for first order Bessel functions.

Called by:

BJ

*** FF02A from HARWELL LIBRARY modified by JCM 17 Jan 85 ***

Classification:

Mathematical Functions . . . . . . . Utility

SUBROUTINE FGAMMA(R,M,QQ,QL,RMS)

Calculates gamma, the ratio of magnetic and nuclear scattering,
and its standard deviation.

Arguments:

On entry R(1) holds the flipping ratio
R(2) holds the standard deviation
M = 0 for abs(gamma) >1
1 for abs(gamma) <1

QQ is the sine of the angle between the magnetisation direction
and the scattering vector

QL is the cosine of the angle between the polarisation direction
and the scattering vector

RMS is the ratio of multiple (or lamba/2) to nuclear scattering.
and to FGAMMS, RMS is the ratio of nuclear to magnetic scattering.

On exit R(1) holds the appropriate gamma
R(2) holds its standard deviation.

Prerequisite calls:

SETPOL should have set the polarisation values in /POLDA/

Calls:

CGAMMA

Called by:

SORGAM

Common blocks used:

/POLDA/ to use POLUP DPOLUP POLDW DPOLDW

*** FGAMMA modified to match new CGAMMA by PJB 04-May-1999 ***

Classification:

Data Collection and Reduction . . . . . . . Crystallographic

CHARACTER*10 FUNCTION FILNOM(LUN)

Returns the name of the file on FORTRAN unit LUN.

Arguments:

LUN on entry holds an input/output unit number
FILNOM is an A10 character variable which on exit holds the file name

Prerequisite calls:

NOPFIL (or OPNFIL) must have attached the unit number to the name in LUNTAB

Output:

If unit LUN is not in the table LUNTAB, an error message is given

Calls:

ERRIN2 NFIND

Called by:

ARREAD BIGGAM CDFIN MAJUST CENPRC GENREF MAG3D POSOUT MG3DGL NVENTR SORGAM

Common blocks used:

/FINAME/ to use all members
/LOONEY/ to use LUNTAB

*** FILNOM by PJB Jan 86 **

Classification:

CCSL Input/Output Routines . . . . . . . Utility

SUBROUTINE FILPRO(DEFT,IU,LFIL)

Makes sense of general file names, under VMS AND UNIX.

Calls:

ERRCHK EXPAND JGMZER LENG LENGT MESS UPONE

Called by:

NOPFIL

Common blocks used:

/FINAME/ to use all members
/GLOBAL/ to use NSYSTM
/IOUNIT/ to use ITO
/SCRACH/ to use NAMFIL

*** FILPRO updated by PJB for UNIX 28-Mar-1994 ***

Classification:

CCSL Input/Output Routines . . . . . . . Utility

SUBROUTINE FINDCD(CH,WORD,LEN,K,LCD)

Searches for a card starting with letter CH and with WORD in
columns 3-6.

Arguments:

On entry CH is a single character with which the card is required to start
WORD is an A4 character variable required in columns 3-6
LEN is the number of characters of WORD required to match (=<4)
K points to the last read card:
K=0 means start at the beginning of the C H cards
K>0 implies that the Kth card was a C H card

On exit LCD indicates whether such a card has been found:
LCD=-1 if no cards are found starting CH
= 0 if some start CH, but no "WORD" >=1 if card found, and then LCD is its position in
the Crystal Data File.

Description:

The search starts at the K+1th card of the whole crystal data
If a card is found, a copy of the card in A80 FORMAT is in ICARD in /SCRACH

Calls:

CARDIN LETTER

Called by:

DOTWN1 FUDGIN GEOMIN ICDFMT PROPAG RDRELA SETFOU STLSFW ICDINC BONDS ICDINC MAG3D MAG3DX MVENTX

Common blocks used:

/CARDRC/ to use NTOTAL NYZ
/PHASE/ to use JPHASE

*** FINDCD updated by JCM 2 Feb 88 ***

Classification:

CCSL Input/Output Routines . . . . . . . Utility

SUBROUTINE FIXPAR(NP,NFIX)

Records an instruction to fix a LSQ parameter.

Arguments:

On entry NP= which parameter to fix, assuming that there is a new
numbering of parameters so that NP is an address in the array
NFIX. All parameters which may be involved with NP must also have addresses within NFIX.
NFIX is an integer array containing potential chaining information
for the relevant parameters.

Description:

Records the fixing of the given parameter, and any chained to it.

Called by:

F2RELA PROPAG RELPAR RELPOS RELSM3 RELSM6

*** FIXPAR by JCM 13 Jul 83 ***

Classification:

General Least Squares Refinement . . . . . . . Setting Up

SUBROUTINE FIXREL(N,NFIX,FIX,KKLIST,NSTAT)

Takes a temporary set of fix/relate information and adds it to the
permanent information.

Arguments:


NFIX, FIX contain their temporary fix/relate info out of
FIXPAR, RELPAR

KKLIST is a list of KK (parameter spec) values corresponding to
the entries in NFIX

NSTAT is the status to be given to any FIX or CON info

Calls:

ADDFIX

Called by:

CELREL F2RELA PROPAG

*** FIXREL by JCM 11 Jan 88 ***

Classification:

General Least Squares Refinement . . . . . . . Setting Up

SUBROUTINE FIXUNI(A,NDO)

Deals with one potential plane face of asymmetric unit, while the
unit is being formed.

Arguments:

On entry NDO indicates the required action:
If NDO is -ve, removes plane number -NDO.
If NDO is +ve, it is the status of plane A, which is to be added
if possible.

A contains the direction cosines of the normal to the offered plane.

Description:

Calls TRYUNI to test particular possible units. Tests "NICE" on return:
NICE=0 OK, we have a unit of right size with 1 typical refln in it
NICE=1 Unit too big - continue
NICE=-1 Unit not possible - either it is too small, or there is no
typical reflection there at all.

TRYUNI also sends back VOL=number of times too big/small unit is, or
VOL=0. if there are 3 planes but they form a hinge.
Called repeatedly from SYMUNI, which decides what to offer or remove.
FIXUNI deals with the "NICE=-1" and the hinge conditions before returning to SYMUNI.

Calls:

FCTOR GMEQ TRYUNI VCTMOD VECPRD

Called by:

PLN3AD SYMUNI

Common blocks used:

/IOUNIT/ to use LPT ITO
/SCRAT/ to use all members

*** FIXUNI updated by JCM 26 Sep 84 ***

Classification:

Basic Crystallography . . . . . . . Setting Up

SUBROUTINE FIXVAR(FX,IFAM,IGEN,ISPC,KP,KS,
NSTAT)

Adds a request to fix (or vary) a parameter to the lists held in
setting up LSQ environments.

Arguments:

On entry:
For entries FIXVAR, ADDFX5, ADDVR5:
IFAM, IGEN, ISPC are the family, genus &$1;species of the parameter
KP, KS are the phase &$1;source if relevant, or may be zero

For entry FVKPAK, ADDFIX, ADDVAR
KK is the packed parameter spec, possibly incomplete
NSTAT is the status of the request (5=not changeable)
(4=changeable)

Prerequisite calls:

LSETUP must have initialised the list

Description:

Ensures an entry in the fix/vary list for the given parameter.
If there already was one for exactly this parameter, alters it as requested, checking that the request is reasonable.
Records whether the request was fix or vary in KSTFV, as + or -
Records status of request also in KSTFV.
Records time of request in KTIME, so that conflict can be resolved.
Keeps count of total number of such requests in NUMFV
Sets KTYPFV to 0 if the packed KK was complete (ie specific), or an address in the table KUNPFV into which the incomplete KK has been unpacked for future reference.

Notes:

Also entries ADDFIX, ADDVAR, FVKPAK

Entries:

ADDFX5 called by: F2RELA LLTFAC MAGCNL PARSSF
ADDVR5
ADDFIX called by: FIXREL
ADDVAR
FVKPAK called by: RDFV

Calls:

ERRCHK JGMEQ KPAK KWHOLE MESS NFIND NTICK PARNAM

Called by:

DOMAG2 RDFV

Common blocks used:

/IOUNIT/ to use LPT
/LINKAG/ to use NUMFV NUMPAK KKFV KTYPFV KSTFV KTIME KUNPFV NTIME

*** FIXVAR by JCM 9 Nov 90 ***

Classification:

General Least Squares Refinement . . . . . . . Utility

SUBROUTINE FLIP(I,J)

Exchanges the integers I and J.

Arguments:

On entry I and J holds certain values
On exit their values have been exchanged.

Called by:

BONTRI

*** FLIP by JCM 4 Feb 88 ***

Classification:

Miscellaneous . . . . . . . Utility

SUBROUTINE FMCALC(H,FMCMOD,FMCSQR)

Calculates magnetic interaction vectors and magnetic structure
factors.

Arguments:

On entry H is the 1x3 vector containing h,k,l
On exit FMCMOD = domain average of the lengths of the m.i. vector
FMCSQR = square of the above

Prerequisite calls:

STHL in /BRAGG should hold sin theta/lambda
NKSTAR in /SATELL should have been set up by routine KSTAR
The setting up routines:
RECIP (for the cell parameters)
SYMOP (for the space group symmetry)
SETFOR (for the scattering factors, both nuclear and magnetic)
SETANI (for the anisotropic temperature factors)
DOMAG(1) and (2) (for the magnetic structure) and
SPHELI (to set up the spin directions on spherical polars)
should all have been obeyed to set up the structure.

Description:

On exit Q(1:3,1:NDOM) in COMMON QCAL contains the magnetic interaction vectors for each of the NDOM domains.
Sets SSQRD in /BRAGG to be STHL squared
Gives zero as answers for magnetic absences

Notes:

There is also the routine LMCALC which does a similar calculation but also calculates derivatives, for use in LSQ.

Calls:

ANITF C1MSCA CGMADD CGMEQ CGMSCA CGMZER CMRSCA FORMFA GMREV MAGABS MAGDOM RADIAN RCMPRD ROTOSM ROTSYM RSCALP SCALPR ROTMAG CROTO

Called by:

CALMSF CALQSF GETMSF MAGPOW

Common blocks used:

/BRAGG/ to use STHL SSQRD
/CONSTA/ to use TWOPI VALMUB
/MAGDAT/ to use NMAG JMAGAT NMFORM SMOD PHIH LPHI FCENT IPTAB SPIND
/NSYM/ to use NOPC CENTRC
/POSNS/ to use AMULT TF SITE
/SATELL/ to use KSTAB IPROP FKSTAR
/SYMDA/ to use TRANS
/SYMMAG/ to use MSTAB OTRSYM FERO HELI MODUL
/SYMTAB/ to use MULTAB

*** FMCALC Updated for PSI's C141 March 2006 ***

Classification:

Magnetic Structure Factors . . . . . . . Crystallographic

SUBROUTINE FMMPCA(H,FMCMOD,FMCSQR)

Calculates magnetic interaction vectors and magnetic structure
factors with multipole form factors.

Arguments:

On entry H is the 1x3 vector containing h,k,l
On exit FMCMOD = domain average of the lengths of the m.i. vector
FMCSQR = square of the above

Prerequisite calls:

STHL in /BRAGG should hold sin theta/lambda
NKSTAR in /SATELL should have been set up by routine KSTAR
The setting up routines:
RECIP (for the cell parameters)
SYMOP (for the space group symmetry)
SETFOR (for the scattering factors, both nuclear and magnetic)
PFSET (for the multipole form factors
SETANI (for the anisotropic temperature factors)
DOMAG(1) and (2) (for the magnetic structure) and
SPHELI (to set up the spin directions on spherical polars)
should all have been obeyed to set up the structure.

Description:

On exit Q(1:3,1:NDOM) in COMMON QCAL contains the magnetic interaction vectors for each of the NDOM domains.
Sets SSQRD in /BRAGG to be STHL squared
Gives zero as answers for magnetic absences

Notes:

There is also the routine LMMCA which does a similar calculation but also calculates derivatives, for use in LSQ.

Calls:

ANITF C1MSCA CGMADD CGMEQ CGMSCA CGMZER CMRSCA FORMFA FORMFC GMREV MAGABS MAGDOM PFORMF RADIAN RCMPRD ROTOSM ROTSYM RSCALP SCALPR ROTMAG CROTO

Common blocks used:

/BRAGG/ to use STHL SSQRD
/CONSTA/ to use TWOPI FOURPI VALMUB
/MAGDAT/ to use NMAG JMAGAT NMFORM SMOD PHIH LPHI FCENT IPTAB SPIND
/MPODA/ to use MPNMTB MPTAB MP
/NSYM/ to use NOPC CENTRC
/POLFOR/ to use MPFOR MPLFOR
/POSNS/ to use AMULT TF SITE
/SATELL/ to use KSTAB IPROP FKSTAR
/SYMDA/ to use TRANS
/SYMMAG/ to use MSTAB OTRSYM FERO HELI MODUL
/SYMTAB/ to use MULTAB

*** FMMPCA from FMCALC by PJB 16 Feb 2001 ***

Classification:

Multipole Form Factors . . . . . . . Crystallographic

COMPLEX FUNCTION FMPCAL(H)

Calculates the COMPLEX nuclear structure factor for the reflection
H, using a multipole expansion of the form factor.

Calls:

ANITF FORMFA FORMFC LATABS PFORMF ROTSYM SCALPR VCTMOD

Common blocks used:

/BRAGG/ to use STHL
/CONSTA/ to use TWOPI FOURPI
/FCAL/ to use FC FCMOD COSAL SINAL
/FORMDA/ to use NFORMF
/MPODA/ to use MPNMTB MP
/NSYM/ to use NOPC CENTRC
/POLFOR/ to use MPFOR MPLFOR
/POSNS/ to use NATOM AMULT TF SITE
/SYMDA/ to use TRANS

Classification:

Multipole Form Factors . . . . . . . Crystallographic

SUBROUTINE FORIER(IIN,IOP,START)

Controls Fourier calculations.

Arguments:

On entry START, a logical, indicates whether this is the first call of FORIER
On exit IIN indicates how the next map is to be obtained:
IIN = 1 means get back previously saved map
2 means read back pre-calculated map in binary form 3 means calculate map using FOUR1Z 4 means calculate map using FOURGP (general plane) 5 means calculate map using ERRMAP (error map)

IOP indicates how the next map is to be sent out:
IOP contains 1 bit = print
2 bit = plot 4 bit = save

Prerequisite calls:

Must be set up by a call of SETFOU, reading the relevant M cards

Description:

If 2D (NDIM=2), only one possible map, a projection, is involved. If 3D (NDIM=3), several layers may be involved. Their values of Z are stored in arrays:
ZRDVAL for reading down pre-calculated maps
ZGTVAL for getting back previously saved maps
ZSVVAL for saving maps just calculated
ZPRVAL for printing
ZPLVAL for plotting

NDIM=4 is a request for a bounded section

Calls:

OPNFIL

Called by:

FORFIG FOURPL

Common blocks used:

/CONTUR/ to use ZPLVAL ZCPL IPL IZPL
/MAPDA/ to use OUTLIM NDIM MODEF MODET SECEND
/MAPGT/ to use ZGTVAL ZCGT IGT IZGT
/MAPRD/ to use all members
/MAPSV/ to use all members
/SCRACH/ to use all members

*** FORIER updated by PJB 29 Apr 88 ***

Classification:

Fourier Calculations . . . . . . . Crystallographic

COMPLEX FUNCTION FORMFA(AK,II)

Calculates form or scattering factors.

Arguments:

On entry AK=sin theta/lambda if relevant
II=which factor is required

On exit FORMFA holds the factor.

Prerequisite calls:

SETFOR must have read and interpreted F cards .

Description:

Allows 5 types of scattering factor, depending on MODE(I):
MODE(I)=1 neutron nuclear factor, the COMPLEX value (CMULT(I),0.)
2 exponential series of NT(I) terms held in F(,I) 3 interpolation in table of NT(I) entries held in S(,I) and F(,I) 4 as 2, but also times sin theta/lambda squared. 5 Form factor to be calculated from radial wave-functions
given on W cards and read by RADFUN (allowed by SETFOR but not included in FORMFA; see FORFAC)

Types 2,3 and 4 may also be multiplied by a constant in CMULT(I)

If NAMODE(I)=1, an anomalous scattering factor is added from FDASH(,I)

Output:

For type 3, if AK is given outside the range in S(,I), an error message is given and the routine stops.

Calls:

TB02A

Called by:

FCALC FCHALC FMCALC FMMPCA FMPCAL LFCALC LMCALC LMMPCA LMPCAL LCHALC

Common blocks used:

/ANSCAT/ to use NAMODE FDASH
/FORMDA/ to use MODE NT CMULT
/IOUNIT/ to use LPT ITO

*** FORMFA updated by JCM 25 Jan 91 ***

Classification:

Structure Factor Calculations . . . . . . . Crystallographic

FUNCTION FORMFC(AK,L,MODE,JAT)

Calculates form factor integrals from radial wave functions.

Arguments:

On entry AK=4*pi* sin theta/lamda.
MODE=0 requests FORMFC to be <Jl>
MODE=1 requests <Gl>, the orbital integral
MODE=2 requests the wavefunction factor.

On exit FORMFC contains the form factor

Prerequisite calls:

RADFUN should have read the radial wave function

Calls:

EXPINT NFIND

Called by:

ASPHFF FMMPCA FMPCAL LMMPCA LMPCAL PFORMF FORFAC

Common blocks used:

/RADINT/ to use FF NTERMS IRADF NRADF

*** FORMFC updated by PJB/JBF 3 Sep 89 ***

Classification:

Structure Factor Calculations . . . . . . . Crystallographic

SUBROUTINE FOUINP(K,F,ALPHA,MODED,MODEF,
ENDIP)

Reads one data item for a given type of Fourier, in a given
format.

Arguments:

On entry MODED indicates the data format type, from M DTYP card
MODED=0: user-supplied routine QFOUIN should set K, F, ALPHA, ENDIP
MODED=1: read H,K,L FCAL,FOBS,(D)
MODED=2: read H,K,L, mod(FCAL), phase angle, FOBS
MODED=3: read H,K,L, A, B, FOBS
MODED=4: read H,K,L, FOBS (or FCAL)

On entry MODEF indicates the Fourier type required, from M FTYP card
MODEF=1: FCAL
MODEF=2: FOBS (Centrosymmetric)
MODEF=3: mod(FOBS)*phase(FCAL)
MODEF=4: FOBS-FCAL
MODEF=5: (mod(FOBS)-mod(FCAL))*phase(FCAL)
MODEF=6: FOBS*FOBS (Patterson)

On exit K is a 1x3 integer vector holding h,k,l
F is a 1x2 vector holding whichever of FOBS, etc were requested
ALPHA, if relevant, holds the phase
ENDIP is a logical set TRUE if the end of the input has occurred.

Output:

Checks that MODED and MODEF are compatible and complains and stops if not.

Calls:

ERRMES QFOUIN RDDATA

Called by:

FOUR1D FOUR1Z FOURGP

Common blocks used:

/CONSTA/ to use PIBY2
/IOUNIT/ to use LUNI

*** FOUINP updated by JCM 14 Apr 89 ***

Classification:

Fourier Calculations . . . . . . . Utility

SUBROUTINE FOUR1D

Calculates a Fourier along a general line.

Prerequisite calls:

SETFOU should have been obeyed to read M, N and I cards and set up the calculation.

Description:

Uses FOUINP to allow all different data input and Fourier types.
Puts calculated 1-D Fourier in array DENS in /MAPDA

Notes:

Expects that the h,k,l values cover a suitable asymmetric unit, from which it uses the given symmetry to generate an entire reciprocal space full. If the data stray outside one asymmetric unit, some h,k,l values will occur more than once.

Calls:

CHOOSF FOUINP INDFLO RESOL SYMEQU TRIG VCTMOD

Common blocks used:

/CONSTA/ to use TWOPI
/MAPDA/ to use OUTLIM NX NY DENS MODEF NOBSIN NUSED SCALF1 SCALF2 DELTA MODED SMAX
/NSYM/ to use NOPC

*** FOUR1D by PJB Dec 85 ***

Classification:

Fourier Calculations . . . . . . . Crystallographic

SUBROUTINE FOUR1Z

Calculates 1 layer of Fourier sum : a section if 3D, a projection
if 2D, or a bounded section if "4D".

Prerequisite calls:

Must be set up by call to SETFOU to read M, N, I cards

Description:

Uses FOUINP to allow all different data input and Fourier types.
Puts calculated Fourier map in array DENS in /MAPDA

Notes:

Expects that the h,k,l values cover a suitable asymmetric unit, from which it uses the given symmetry to generate an entire reciprocal space full. If the data stray outside one asymmetric unit, some h,k,l values will occur more than once.
Ignores FRIEDL - if non-centrosymmetric, and Friedel's law not to be assumed, the user must do something to combine F(H,K,L) and F(-H,-K,-L) outside
FOUR1Z.

Calls:

CHOOSF FOUINP GMEQ GMPRD INDFLO RESOL SYMEQU TRIG VCTMOD

Called by:

FORFIG FOURPL

Common blocks used:

/CONSTA/ to use TWOPI
/MAPDA/ to use OUTLIM NX NY NXY NH NK NHK NKX DENS MODEF NOBSIN NUSED SCALF1 SCALF2 DELTA MODED SMAX SECZER
/NSYM/ to use NOPC
/SCRAT/ to use all members

*** FOUR1Z corrected by PJB 17-Jun-1994 ***

Classification:

Fourier Calculations . . . . . . . Crystallographic

SUBROUTINE FOURGP

Calculates a Fourier on a general plane.

Prerequisite calls:

Must be set up by call to SETFOU to read M, N, I cards

Description:

Uses FOUINP to allow all different data input and Fourier types.
Puts calculated Fourier map in array DENS in /MAPDA

Notes:

Expects that the h,k,l values cover a suitable asymmetric unit, from which it uses the given symmetry to generate an entire reciprocal space full. If the data stray outside one asymmetric unit, some h,k,l values will occur more than once.
Ignores FRIEDL - if non-centrosymmetric, and Friedel's law not to be assumed, the user must do something to combine F(H,K,L) and F(-H,-K,-L) outside
FOURGP

Calls:

CHOOSF FOUINP INDFLO RESOL SYMEQU TRIG VCTMOD

Called by:

FORFIG FOURPL

Common blocks used:

/CONSTA/ to use TWOPI
/MAPDA/ to use OUTLIM NX NY NXY DENS MODEF NOBSIN NUSED SCALF1 SCALF2 DELTA MODED SMAX SECZER
/NSYM/ to use NOPC
/SCRAT/ to use all members

*** FOURGP by PJB Dec 85 ***

Classification:

Fourier Calculations . . . . . . . Crystallographic

SUBROUTINE FRAC3(VEC)

Makes all 3 elements of a vector fractional

Arguments:

On entry VEC is a 1x3 real vector.
On exit the elements of VEC have each been put into the range 0 =< X < 1

Calls:

FRACT

Called by:

ATOMS EQPOS EQPPOS INCELL SYMOP

*** FRAC3 by JCM 11 Nov 83 ***

Classification:

Basic Crystallography . . . . . . . Utility

SUBROUTINE FRACT(X,Y,N)

Forms the fractional part of a real number.

Arguments:

On entry X is a real number
On exit X is in the range 0=< X <1
Y is set so that X+Y=original X
N= 0 if X was unchanged = 1 if X was >= 1 =-1 if X was < 0

Called by:

FETTLE FRAC3 NUMA1 NUMDEN OPSYM

*** FRACT by JCM ***

Classification:

Mathematical Functions . . . . . . . Utility

SUBROUTINE FRAME(X1,Y1,X2,Y2)

Draws a rectangle in the plotting context.

Arguments:

On entry (X1,Y1) and (X2,Y2) are the coordinates of opposite corners of the required rectangle. These are in "current coordinates"

Prerequisite calls:

The plotting must have been set up by, e.g. STPLOT, and a suitable space selected by SPCSET.

Calls:

KANGA1

Called by:

MAPCON MAPFRA MAPKEY MAPTIT PLOTO PLTTXT FORFIG FOURPL MAG3D

*** FRAME by JCM 24 Nov 83 ***

Classification:

Graphical Output . . . . . . . Utility

SUBROUTINE FT01A(IT,INV,TR,TI)

Modification of Harwell Fast Fourier Transform.

Common blocks used:

/CONSTA/ to use TWOPI
/FFTDA/ to use all members

*** FT01A updated by JCM FROM HARWELL ROUTINE 9 Sep 91 ***

Classification:

Mathematical Functions . . . . . . . Utility

SUBROUTINE FUDGET(IPT,ITYP,F1,F2)

Reads a fudge factor from a card having already read a parameter
specification.

Arguments:

IPT on entry points at next char on card ICARD
IPT on exit has been advanced by the amount read
ITYP on exit = type of factor read
F1 on exit = first no. read if appropriate
F2 on exit = second no. read if appropriate

Prerequisite calls:

Card is held in /SCRACH/ in ICARD

Description:

Reads one of:
a number into F1 (setting ITYP=1) "GE" number into F1 (setting ITYP=2) "LE" number into F2 (setting ITYP=3) both the above, setting ITYP=4

Calls:

RDREAL RDWORD

Called by:

FUDGIN

*** FUDGET by JCM 10 Feb 87 ***

Classification:

General Least Squares Refinement . . . . . . . Utility

SUBROUTINE FUDGIN

Interprets all
L FUDG cards .

Description:

Sets NFUDGE in /FUDG to be the number of fudge factors read.
Reads from the cards sets of <parameter specification> <fudge factor>
The parameter specification may be any of those described under PARRD
The fudge factor may be one of:
1) A simple multiplicative factor 2) GE followed by a lower limit 3) LE followed by an upper limit 4) both 2) and 3) in either order

Calls:

ERRCHK ERRMES FINDCD FUDGET KPAK MESS PARRD

Called by:

PARSSF

Common blocks used:

/CARDRC/ to use IERR
/FUDG/ to use NFUDGE FUDGE1 FUDGE2
/IOUNIT/ to use LPT
/PHASE/ to use KPHASE
/SOURCE/ to use KSOURC

*** FUDGIN updated by JCM 27 Apr 92 ***

Classification:

General Least Squares Refinement . . . . . . . Setting Up


Contents Manual

P. Jane Brown e-mail: brown@ill.fr
Institut Laue Langevin,
Grenoble, FRANCE