Contents Prev Manual

SUBROUTINE PARITY(N,M,EVEN)

Finds out whether N is odd or even.

Arguments:

On entry N is the integer to be tested
On exit EVEN is true if N is even, false if N is odd
If N is even M=N/2; if odd M=(N-1)/2

Called by:

BINDIG GAUSPT

*** PARITY by JCM 26 Sep 85

Classification:

Tests . . . . . . . Utility

SUBROUTINE PARNAM(IPNAM1,IPNAM2,N,M)

Obtains the printing name of a LSQ parameter.

Arguments:

On entry N specifies what the integer M is:
N=1 means M is the number of a basic variable
N=2 means M is the number of a variable
N=3 means M is a packed parameter specification

On exit IPNAM1 contains the A4 genus name,
IPNAM2 contains the A4 species name

Prerequisite calls:

LSETUP must have put the vocabulary into /WORDS/ etc
VARMAK must have set up varible structure and pointers

Description:

On exit KPHASE in /PHASE/ and KSOURC in /SOURCE/ have been given the current values of the phase and source.
From family, genus and species, decides source of genus and species names
A large, +ve value for the species type indicates only 1 name, not 2
Picks up names via PRIWRD

Calls:

ERRIN2 INTCHR INTDIG KUNPAK MF5ADD PRIWRD

Called by:

APSHDS APSHFW APSHSF APSHT2 DOMPL2 FIXVAR MATCOR MATINV MATSHF PARSFW PRIVAR PRMBLK

Common blocks used:

/ATNAM/ to use all members
/GLOBAL/ to use MULFAS
/IOUNIT/ to use LPT ITO
/MPODA/ to use MPATAB
/MPODAC/ to use all members
/PHASE/ to use KPHASE
/POINTS/ to use LVRPR LBSVR
/PRBLEM/ to use NSPCPS LF1SP LF3SP LF6SP
/SOURCE/ to use KSOURC

*** PARNAM updated by JCM 8 May 90 ***

Classification:

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

SUBROUTINE PARRD(IPT1,IPT2,K,IFAM,IGEN,ISPC)

Reads a LSQ parameter specification from a given card at given
point.

Arguments:

On entry IPT1 points to the starting character on the card in /SCRACH/
On exit IPT2 points to the next unread character on the card in /SCRACH/
K is the packed parameter unless K is -ve:

K=-99 'ONLY' read
K=-100 'ALL' read as first word, in which case IFAM is expected to
be set, and possibly one but not both of ISPC and IGEN

K=-100 and IFAM -ve means that the word after 'ALL' was composite
Composite words have come from MAIN program table with -ve small entries. For SFLSQ and the like,
IFAM=-1 'ALL XYZ'
IFAM=-2 'ALL BIJ'
IFAM=-3 'ALL XYZT'
IFAM=-4 'ALL CELL'
IFAM=-5 'ALL XYZB'
IFAM=-6 'ALL XYZS'

K=-101 'XYZ' as 2nd word; 1st word was genus in IGEN
K=-102 'BIJ' as 2nd word; 1st word was genus in IGEN
K=-103 'XYZT' as 2nd word; 1st word was genus in IGEN
K=-104 'CELL' as 2nd word; 1st word was genus in IGEN
K=-105 'XYZB' as 2nd word; 1st word was genus in IGEN
K=-106 'XYZS' as 2nd word; 1st word was genus in IGEN

Prerequisite calls:

The tables used must be set up by LSETUP

Description:

PARRD expects only a limited vocabulary, identified via TBLFND, being
a known genus followed by a species name 'ONLY' 'ALL' followed by anything making sense a genus name followed by a composite word like 'XYZ', 'BIJ', 'XYZT' 'XYZB' a species name alone, in the special case of family 1 or 6, genus 1 (and for PR, if SCAL is read, ignores a 1 if it follows) - wherever it makes sense.

Calls:

ERRIN2 KPAK NCFIND RDINTG RDWORD TBLFND

Called by:

FUDGIN RDFV RDRELA

Common blocks used:

/MPODA/ to use MPNMTB MPTAB
/MPODAC/ to use all members
/PHASE/ to use JPHASE KPHASE
/REFINE/ to use MPL
/SOURCE/ to use JSOURC KSOURC

*** PARRD updated by JCM 3 Aug 92 ***

Classification:

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

SUBROUTINE PARRUN(IFAM,IGEN,ISPC)

Controls the cycling over all parameters in LSQ (not for Profile
Refinement).

Arguments:

On entry, if IFAM=0 the cycle is to be initialised
and otherwise IFAM,IGEN,ISPC contain the "previous" values

On exit IFAM contains the family of the "next" parameter,
or -1 if the end has been reached.

IGEN contains the genus of the "next" parameter,
ISPC contains the species of the "next" parameter.

Prerequisite calls:

LSETUP must have set up the structure of the problem in the arrays:
NGENS(I)=number of genera in family I
NSPC(I) =number of species in each genus of family I
LF1SP(I)=number of species in family 1, genus I.

Notes:

There is a similar routine in the Profile Refinement section, RUNPAR, which deals also with the special family 4 parameters, and multi-phase and multi-source data.

Called by:

DOMAG DOMAG2 CHILSQ MAGLSQ MMPLSQ MPLSQ PALSQ SFLSQ SFTLSQ

Common blocks used:

/PRBLEM/ to use NFAM LF1SP

*** PARRUN updated by JCM 26 Oct 89 ***

Classification:

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

SUBROUTINE PARSDS

Collects together all parameter fixing and varying information for
LSQ refinement of cell parameters using d spacings.

Prerequisite calls:

The LSQ system must have been set up by LSETUP. A "C" card with cell parameters must have been read using RECIP.

Description:

Absorbs constraints due to symmetry for cell parameters, then reads and interprets L FIX, LVARY and L RELA cards .

Input:

L FIX, LVARY and L RELA cards .

Calls:

CELREL LDUMMY RDFV RDRELA

*** PARSDS updated by JCM 28 Jan 88 ***

Classification:

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

SUBROUTINE PARSFW

An older routine to set up variables from parameters for FWLSQ.

Description:

All parameters are in fact both variables and basic variables, as there
are no constraints on this problem

Calls:

KPAK MESS PARNAM

Common blocks used:

/CONSTR/ to use JCONST
/DERBAS/ to use LVARB
/DERVAR/ to use LVARV
/FWVALS/ to use NVALS
/IOUNIT/ to use LPT
/POINTS/ to use LVRBS LVRPR LBSVR

*** PARSFW updated by JCM 12 Jan 88 ***

Classification:

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

SUBROUTINE PARSSF(MAGPAR)

Collects all parameter fix and vary information for single crystal
LSQ.

Arguments:

MAGPAR is the name of a logical function which deals with parameters which are not in the basic structure factor set (F2PARS). It is
DOMAG2 for the standard magnetic parameters, and LDUMMY if there are no extra parameters.

Description:

Calls other routines to:
Collect all symmetry implied constraints
Read &$1;interpret all L FIX, L RELA and L VARY cards .

Input:

L FIX, L VARY and L RELA cards .

Calls:

CELREL F2RELA FUDGIN RDFV RDRELA

Called by:

CHILSQ MAGLSQ MMPLSQ MPLSQ PALSQ SFLSQ SFTLSQ

Common blocks used:

/EXTN/ to use IEXTYP
/NEWOLD/ to use IGEN ISPC
/OVER/ to use NTFAC
/SLAKDA/ to use NSLAK

*** PARSSF updated by PJB C105 Apr 2001 ***

Classification:

Specific Least Squares Refinement . . . . . . . Crystallographic

SUBROUTINE PFORMF(H,MAT,PSUM,PFACS,KODE)

Calculates radial form factors for multipole refinement.

Arguments:

H(3) contains the indices of the reflection
MAT is the number assigned to the multipole atom
On entry KODE gives the required action:
= 0. Calculate radial form factors for atom MAT and put in pformf = 1. Return sum over multipoles in PSUM

Notes:

The basis functions Ylm+ and Ylm- are defined by:
Ylm+ = sqrt(2)Real({Ylm})
Ylm- = sqrt(2)Imag({Ylm})

Thus Ylm+ = 1/sqrt(2)[Ylm + (-1)**m(Yl-m)]
Ylm- = -i/sqrt(2)[Ylm - (-1)**m(Yl-m)]

Calls:

ERRMES FORMFC GMEQ GMPRD GMZER SPHARM UNIVEC VCTMOD

Called by:

FMMPCA FMPCAL LMMPCA LMPCAL

Common blocks used:

/ATNAM/ to use ATNAME
/CONSTA/ to use FOURPI
/FORMDA/ to use NFORMF
/MAGDAT/ to use MAGAT NMFORM
/MPODAC/ to use all members
/MPODA/ to use MPATAB MPTAB POLAMP
/POLFOR/ to use MPFOR MPLFOR PFORFA LMAX
/QROT/ to use all members
/REFINE/ to use MAG

*** PFORMF updated by PJB C128 Feb 2004 ***

Classification:

Multipole Form Factors . . . . . . . Crystallographic

SUBROUTINE PFOUT

Reports the allocation of multipole form factors

Called by:

MMPLSQ MPLSQ

Common blocks used:

/ATNAM/ to use ATNAME
/FORMDA/ to use NFORMF
/FONAM/ to use FONAME
/IOUNIT/ to use LPT
/MAGDAT/ to use MAGAT NMFORM
/MPODA/ to use NMPAT MPATAB
/POLFOR/ to use MPFOR MPLFOR
/REFINE/ to use MAG

*** PFOUT updated by PJB C139 July-4-2005 ***

Classification:

Multipole Form Factors . . . . . . . Setting Up

SUBROUTINE PFSET

Directs the reading of J and
W cards for multipole calculations.

Calls:

CONVMP ERRCHK ERRMES INPUTJ INPUTW JGMZER MPCON MPFORM NCFIND NCHINT NFIND NPACK OPSYM ORTFUN RADFUN RDREAL RDWORD SORTN

Called by:

MMPLSQ MPLSQ

Common blocks used:

/ATNAM/ to use ATNAME
/CARDRC/ to use NYZ IERR
/DOMPL/ to use all members
/FORMDA/ to use NFORMF
/FONAM/ to use FONAME
/IOUNIT/ to use LPT ITO IOUT
/MAGDAT/ to use MAGAT NMFORM
/MPODA/ to use NMPAT NMPOL MPATAB MPNMTB NCLUMP MPTAB POLAMP
/MPODAC/ to use all members
/POLFOR/ to use MPFOR NMPFOR MPLFOR
/RADINT/ to use IRADF NRADF
/REFINE/ to use MAG
/SCRAT1/ to use all members

*** PFSET updated by PJB C139 July-4-2005 ***

Classification:

Multipole Form Factors . . . . . . . Setting Up

SUBROUTINE PICMOV

If plotting to Tektronix, do nothing; if to plotter, move to next
picture.

Prerequisite calls:

FROMCM in /PLODAT/ is 0 if plotting is actually to a VDU, for which the scale "from cm" is irrelevant.
NYPIC in /PLOMAP/ is the number of pictures expected, and IYPIC is the number already plotted.

Description:

If a large plotter is in use for several pictures plotted in sequence, the matrix PMTRIX(,,2) holds the part of the transformation which moves from one picture to another. This routine deals with the moving from one picture to another, advancing IYPIC and adjusting PMTRIX(,,2)

Called by:

FORFIG FOURPL

Common blocks used:

/PLODAT/ to use BORDER FROMCM
/PLOMAP/ to use WIDPIC HGTPIC NYPIC IYPIC
/PLTRAN/ to use PMTRIX

*** PICMOV by JCM 22 Aug 86 ***

Classification:

Graphical Output . . . . . . . Crystallographic

SUBROUTINE PIGLET(X,Y,N)

A complete set of device-specific plotting commands.

Arguments:

On entry X and Y are plotter coordinates
N indicates the function required:

N=0 Called at very start of a plotting job, to set up physical things like
plotter width in cms, plotter units (as FROMCM which converts from cms to plotter units). Also sets up some transformation matrices and initialises quantities for transformations.

N=2 Move the pen to the point X,Y (in the plotter's own coordinates) or N=2 moves with pen down (i.e. draws)
N=3 N=3 moves with pen up.
There was originally an N=1 meaning move with the pen in the state it was last time. Not every library implements this, so although CCSL uses it, it is now done by the routines which call PIGLET.

N=-1 - -15 Changes the colour of the ink in the pen
Cokours defined in /PGNUMS/ (These may be altered, or others added, as the user wishes)

The remaining values of N carry out whatever special actions the local plotter software needs to make when starting or finishing various stages.

Description:


The complete plotter output produced by the whole job is called here a "plot". The plot may be made up of various "pictures" such as layers of a Fourier map; or it may be just one graph. Within a "picture" there are various boxes of explanatory text and the main graphic object such as a "map" for fouriers or a "graph" from PLOTO
Most plotter software libraries require that a certain routine be called to start a plot, and some also require another routine to be called to finish a plot (say, to move the pen clear of the plot ready for the next job).
There is no obvious need for any special action on an actual plotter at the start and finish of one "picture", but if a Tektronix or other vdu is used, there will be only one "picture" on the screen at once (remember several "pictures"=1 "plot"), so special actions will be needed to start (say, clear screen) and finish (say, ask user if he wants a hard copy) a picture.
To accomplish these actions large values of n are assigned as follows:
N=999 Start "plot" (which will be X cms wide and Y cms high)
N=-999 Finish "plot" (which was X cms wide and Y cms high)
N=888 Start "picture" (which will be X cms wide and Y cms high)
N=-888 Finish "picture" (which was X cms wide and Y cms high)
Sets PMTRIX number 1: the CCSL to hardware transformation

Output:

When requested, sends output to graphical device.

Notes:

Contains all plotting commands which are specific to whatever machine (and which output device) is being used. These are believed to be a bare minimum. Whenever a new plotter (specifically a new plotter software library) is implemented on the system a specific version of this routine must be made.
There are other versions of PIGLET in CCSL for specific output devices.

Calls:

ERRMES GMSCA GMUNI GMZER PINITL PLCONV PLTRIN

Called by:

ATMPLT KANGA1 KANGA3 MAPCON MAPFRA MAPKEY PLOTCT PLOTO PLTTXT STPLOT FORFIG FOURPL MAG3D

Common blocks used:

/PLODAT/ to use FROMCM

*** PIGLET updated by JCM 27 Jun 86 ***

Classification:

Graphical Output . . . . . . . Utility

SUBROUTINE PINITL

Initialises the system in order to make graphical output.

Description:

Sets up various quantities, some of them probably machine specific, to enable SUBROUTINE PIGLET to be called. PIGLET may well alter some of them. Suitable for either the plotter version or the Tektronix
Sets PAPERW = width of paper in cms (or no. of pixels)
PAPERH = "height" of paper in cms - this is the maximum
amount allowed in direction perpendicular to the axis of the plotter (or no. of pixels)

FROMCM = the conversion factor from centimetres to hardware
units - set to 1 for now, and adjusted in PIGLET where necessary (<0 for VDU output)

CHUNIT = number of character units of a character grid which
make the height of a character (and also the maximum width of a character, which may not use it all)

ASPECT = ratio of the height of a plotted character to its width
BORDER = width of border between pictures, in cms
DASH = length of the dash of a dashed line, in cms

Initialises the general structure of transformations in /PLODAT; does not initialise the basic 'CCSL to hardware' transformation, which must be done in individual PIGLETs.

Calls:

GMUNI GMZER PLTRIN

Called by:

PIGLET

Common blocks used:

/ADASH/ to use DASH IDSH
/PLODAT/ to use all members

*** PINITL by JCM 27 Jun 86 ***

Classification:

Graphical Output . . . . . . . Setting Up

SUBROUTINE PLCONV(X1,Y1,NN1,X2,Y2,NN2)

Performs the transformation of coordinates between different
plotter spaces.

Arguments:

On entry X1, Y1 are coordinates in coordinate system number NN1
On exit X2, Y2 are the same coordinates transformed into the
coordinate system number NN2

Prerequisite calls:

PIGLET with N=0, PLTRIN to set up the required transformation matrices.

Description:

Coordinate systems: 0=Current - The current space is held in NSPCE in COMMON /PLTRAN/ 1=Plotter (actual coords on a particular plotter) 2=CCSL (the coords in which the programs are written)
Coordinate sytems 3 to 7 are for user applications, for example in plotting
Fourier maps they are used as follows: 3=Picture (one "picture" which contains one section of the map) 4=Map (The crystallographically related axes of the Fourier calculation) 5=Character type 1 (a mesh of 30 by 30 on which characters are defined) 6=Character type 2 (a mesh of 30 by 30 on which characters are defined) 7=Character type 3 (a mesh of 30 by 30 on which characters are defined)
Conversion involves both a translation (or origin shift) and a rotation.
These are combined by holding the conversion matrix as 3 by 2 with the translation vector as the 3rd column.

Calls:

GMEQ GMZER PMTINV PMTMUL

Called by:

ARROW ATMPLT CIRCLE DPLOT KANGA3 MAPFRA MAPKEY PIGLET PLOTO ELIPSE LABAXE

Common blocks used:

/IOUNIT/ to use LPT ITO
/PLTRAN/ to use PMTRIX PTRAN NSPCE NCON1 NCON2 NTRAN

*** PLCONV updated by PJB 4 Apr 85 ***

Classification:

Graphical Output . . . . . . . Crystallographic

SUBROUTINE PLN3AD(I,J,K)

A specialist routine used during the formation of the reciprocal
unit cell, to offer up 3 planes as boundaries, in cubic space groups.

Arguments:

On entry I,J,K specify 3 planes, by pointing to symmetry elements.
The array AXI(,I,,) holds the axes of these elements in reciprocal space, and these axes are normal to the planes in question

Description:

The 3 axes are first oriented so that the angles between the planes are acute.

Calls:

FIXUNI GMEQ GMREV SCALPR VECPRD

Called by:

SYMUNI

Common blocks used:

/SCRAT/ to use all members

*** PLN3AD by JCM 3 Oct 84 ***

Classification:

Basic Crystallography . . . . . . . Setting Up

SUBROUTINE PLOTCT(C,A,FOUND,M,N)

Plots a single contour throughout a given array.

Arguments:

On entry C is the contour value required
A is a M by N array of values in which the contour C is to be
interpolated

On exit FOUND is true if a contour was found and plotted, false otherwise.

Prerequisite calls:

PIGLET with N=0 and N=999, to set up the plotter.
The desired mesh on the plotter should be set up with PLTRIN and SPCSET

Output:

Output is to a plotter whose characteristics are defined in the version of
PIGLET linked.

Calls:

BITSET DPLOT ERRMES GETSQ LOCBIT MAKEBM PIGLET

Called by:

MAPDRW

Common blocks used:

/BITMAP/ to use IBIT

*** PLOTCT by JCM 24 Nov 83 ***

Classification:

Graphical Output . . . . . . . Crystallographic

SUBROUTINE PLOTIT(X,NP,SIZE)

Plots the graph of given vector y against x, with esds.

Arguments:

On entry X(3,NP) holds values to be plotted
X(1,1:NP)= x values
X(2,1:NP) = y values
X(3,1:NP) = standard deviations of y values

On entry NP = number of points in graph
SIZE a vector of dimension 2 holds the lengths of the x and
y axes in cms.

Description:

This subroutine sets up the plotter as well as drawing the graph.*

Output:

Output to a plotter whose characteristics are defined in the version of
PIGLET linked.

Calls:

GETSCL PLOTO

*** PLOTIT by PJB Sep 87 ***

Classification:

Graphical Output . . . . . . . Crystallographic

SUBROUTINE PLOTO(XX,YY,ER,MODE)

A multi-purpose graph-drawing routine.

Arguments:

On entry XX and YY are x and y coordinates whose meaning is defined by MODE:
MODE=0 Set up to draw a graph in which the lengths of the axes are x, y.
>0 Line drawing: move the "pen" from its current position to x, y.
If MODE = -1 the "pen" is down
= -2 a dashed line is drawn. The dash interval is ER. = -3 the "pen" is up

If -MODE > 10 and < 21 the symbol ABS(MODE+10) is drawn at
intervals of ER.

MODE>0 Plot the point x,y with an error bar of length ER. The value of
MODE defines the symbol to be plotted.
MODE = 1 square
MODE = 2 triangle, apex up
MODE = 3 triangle, apex down
MODE = 4 hexagon, which if small will look like a circle
MODE = 5 cross like x
MODE = 6 cross like +
MODE = 7 cross like x with top and bottom (egg-timer)
MODE = 8 cross like x with sides (butterfly)
MODE = 9 diamond

Prerequisite calls:

The vector X(I,J) held in COMMON /PLTS/ defines how the graph will be drawn
I=1 for x-axis, I=2 for y-axis.
J=1 length of axis in user units
J=2 length of axis in cms.
J=3 division of axis in user units
J=4 minimum value in user units
J=5 position of axis to be plotted

GETSCL should be called for both x and y axes, to define the ranges of values to plot.

Calls:

ASK DPLOT FETTLE FRAME KANGA1 KANGA2 KANGA3 LENG LENGT NUMA1 PIGLET PLCONV PLTRIN SPCSET

Called by:

PLOTIT

Common blocks used:

/ADASH/ to use DASH X1 Y1
/PLODAT/ to use ASPECT BORDER CHUNIT
/PLTS/ to use CH XS ISIG YS NDIVS
/PLOTCH/ to use all members

*** PLOTO updated by PJB/JCM 10 Jun 88 ***

Classification:

Graphical Output . . . . . . . Crystallographic

SUBROUTINE PLTRIN(PMAT,N,M)

Defines a new coordinate transformation for plotting.

Arguments:

On entry PMAT is a 2 X 3 real matrix which defines the coordinate system
N with respect to M.
PMAT(1:2,1:2) gives the scaling and rotation
PMAT(1:2,3) gives the origin of space N with respect to that of
space M, in M's cordinates.

M must be greater than N

Description:

PMAT and N will be written as items number N-1 in PMTRIX and NTRAN in
COMMON /PLTRAN/. MAXSP in /PLTRAN/ holds the largest N yet given.

Calls:

GMEQ

Called by:

MAPCON MAPKEY PIGLET PINITL PLOTO STPLOT MAG3D AROW3D

Common blocks used:

/IOUNIT/ to use LPT ITO
/PLTRAN/ to use PMTRIX NTRAN MAXSP

*** PLTRIN by JCM 4 Apr 85 ***

Classification:

Graphical Output . . . . . . . Crystallographic

SUBROUTINE PLTTXT

Plots a block of explanatory text under a plotted Fourier map.

Description:

Plots the block of text which lists all the necessary details for identification of the map. Does this in what is for the Fourier plotting "character 1 space", space number 5.

Output:

Outputs to graphical device as set up by PIGLET

Calls:

FETTLE FRAME KANGA1 KANGA2 NUMA1 PIGLET SPCSET

Called by:

FORFIG FOURPL

Common blocks used:

/MAPDA/ to use OUTLIM NDIM MODEF SCALF1 DELTA SECEND
/PLODAT/ to use CHUNIT

*** PLTTXT updated by JCM 29 Apr 92 ***

Classification:

Fourier Calculations . . . . . . . Crystallographic

SUBROUTINE PMTINV(A,B)

Specialist routine to invert a 2x3 matrix, such as those which
transform plotting coordinates from one space to another.

Arguments:

On entry A holds a 2x3 matrix as A(2,3)
On exit B(2,3) holds the matrix representing the inverse transformation.

Called by:

PLCONV

*** PMTINV by JCM 18 May 84 ***

Classification:

Graphical Output . . . . . . . Crystallographic

SUBROUTINE PMTMUL(A,B,C)

Specialist routine to multiply together two 2x3 matrices, such as
those which transform plotting coordinates from one space to another.

Arguments:

On entry A and B are 2x3 real arrays
On exit C represents the result of performing B then A.

Called by:

PLCONV SPCSET

*** PMTMUL by JCM 1 May 84 ***

Classification:

Graphical Output . . . . . . . Crystallographic

SUBROUTINE POLUNI

A specialist routine to "polish" the edges of a found asymmetric
unit by specifying exactly how its faces and edges should be treated.

Prerequisite calls:

POLUNI is called from the end of SYMUNI, and would not be useful outside this context.

Description:

Sets the array MARK in /GUNIT/ to indicate the exact treat ment of faces and edges of the reciprocal cell asymmetric unit in order to deduce the multiplicites of reflections occurring on them.

Calls:

BINDIG EQVEC GMREV INBOX INVENT SCALPR VECPRD

Called by:

SYMUNI

Common blocks used:

/CONSTA/ to use TWOPI
/FRIED/ to use FRIEDL
/FUNIT/ to use NASYM ASYM EDGE ANG
/GUNIT/ to use MARK BSYM
/IOUNIT/ to use LPT ITO IOUT
/NSYM/ to use NOP NOPC
/SCRAT/ to use all members
/SYMTAB/ to use NORD

*** POLUNI by PJB 8 Aug 83 ***

Classification:

Basic Crystallography . . . . . . . Setting Up

SUBROUTINE PRBLOK

Prints a block of shifts in parameters all relating to the same
atom in LSQ applications involving structure parameters.

Prerequisite calls:

IBUFF in /ATBLOK/ is the number of shifts to be printed. The calling routine APSHxx must control IBUFF and store shift information in the arrays in /ATBLOK and /ATBLOC.

Description:

If IBUFF=0 exits. Otherwise prints shifts across the page for one specific atom as stored. Sets IBUFF=0

Output:

Prints blocks of new parameter, esd, shift, old parameter, shift/esd labelled appropriately.

Calls:

ERRMES NSIGFG

Called by:

APSHSF DOMPL2

Common blocks used:

/ATBLOC/ to use all members
/ATBLOK/ to use all members
/IOUNIT/ to use LPT

*** PRBLOK updated (blocks of up to 12) 3rd-Apr-2001 ***

Classification:

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

SUBROUTINE PREFIN(PROGRM)

Makes the Crystal Data File readable in a random order by writing
it to a scratch file.

Arguments:

On entry PROGRM is the A6 name of the calling program, to head the output

Description:

Creates a direct access file number IO10, writes to it the given
Crystal Data File as A80 records, and keeps an index so that subsequently any "card" may be read or re-read as required.
Sets ICDNO(1-26) to be the number of "cards" read for each letter, except Y
and Z, which are passed through anywhere (printing out the Y).

Sets INREAD(1-26) to be the start record for each letter chunk.
Sets NTOTL to be the total number of records read.
Sets IERR=0 so that errors later may reset it.
Also initialises system by a call to INITIL. Jobs wishing to intervene to change parameters must say, e.g.:
CALL INITIL('NAME') change whatever wanted
CALL PREFIN('NAME')

PREFIN reads "cards" labelled with a letter from A-Z in column 1, from a dataset called the "crystal data". This is read from logical unit
ICRYDA, which may be assigned to a specific unit number in the main program, or left unassigned so that the call to OPNFIL will assign a unit number and ask interactively for a file name.
The "cards" give information about the current problem.
Letters used so far are:
A atomic positions (read by ATOPOS)
B bond length and angle instructions (read by main program BONDS)
C cell dimensions (read by RECIP)
D diffraction or diffractometer data (read by SETDC)
E extinction correction data (read by EXTINC)
F form factors (read by SETFOR)
G Gauss integration and other data for abs corr (read by SETGAU)
I instruction "cards" (read by main programs)
J multipole information (read by INPUTJ)
L least squares refinement data (read by, e.g., INPLSF)
M data for calculation of fourier maps (read by SETFOU)
N title (a single "card, read by INPUTN)
P polarisation data (read by SETPOL)
Q data for magnetic structures (read by DOMAG)
S symmetry "cards" (read by SYMOP)
T anisotropic temperature factors (read bY SETANI)
U indices supplied to force use of a particular unit asymmetric
unit (read by SYMUNI)

V choice of representation of the space group
W wave function data (read by INPUTW)
X entirely under user's control
Y comment repeated on ouput LPT
Z comment not repeated on output

All "cards" with the same initial letter must come together but the groups may be in any order.

Except in a few instances such as "F" "cards", where if a table of values is given, SETFOR expects "cards" to be in the correct sequence, the "cards" within a group may be in any order.

The restriction about having all "cards" of one letter together does not apply to "cards" starting Y or Z.

A completely blank line is ignored.

An end of file, or any "card" with a non letter symbol in column 1 terminates a set of crystal data. Any further data in the file may be read subsequently by the user's program.

If an "M GE T" card is given, the user wishes to take his basic data, and any saved Fourier maps, from a dataset supplied, not from this crystal data. The
SUBROUTINE MAJUST is called to adjust his file IO10 in this case.

Input:

Reads in the Crystal Data File

Output:

Lists on the lineprinter output a summary of what it found.

Calls:

CDFIN INITIL NOPFIL OPNFIL

Called by:

ABSMSF ADDFC ARRINC ARRNGE AVEXAR BONDS CALMSF CALQSF CHILSQ EXTCAL FORFAC FORFIG FOURPL GENREF GETMSF GETSFZ INCMSF MAG3D MAGLSQ MAGPOW MG3DGL MMPLSQ MPLSQ MVENTR PALSQ POWDER SFLSQ SFTLSQ SORGAM

Common blocks used:

/CARDRC/ to use ICRYDA NTOTAL NTOTL IERR IO10
/SCRACH/ to use all members

*** PREFIN updated by JCM 28 Apr 92 ***

Classification:

CCSL Input/Output Routines . . . . . . . Setting Up

SUBROUTINE PRILIS(AVAL,IPT1,IPT2)

Prints a list of real numbers held in an array, 5 per line.

Arguments:

On entry AVAL holds the required real numbers,
IPT1 points to the first to be printed,
IPT2 points to the last to be printed.

Output:

Writes out AVAL(IPT1 to IPT2), in format G12.5, 5 per line.

Called by:

INPUTM LLSCAL

Common blocks used:

/IOUNIT/ to use LPT

*** PRILIS updated by JCM 22 Aug 86 ***

Classification:

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

SUBROUTINE PRIPLN(A,IR)

Given the normal to a plane face in A, prints the equation of the
plane.

Arguments:

On entry A is a 1x3 array containing 3 elements of the normal.
IR=1 indicates that the normal is in terms of h,k,l, and
IR=2 in terms of x,y,z (for later use).

Output:

Writes on unit LPT the equation of the plane.

Notes:

At present every plane is assumed to go through the origin.

Calls:

JFIX

Called by:

UNITID

Common blocks used:

/CHARS/ to use LETLOW IDIGIT
/IOUNIT/ to use LPT

*** PRIPLN updated by JCM 12 Nov 89 ***

Classification:

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

SUBROUTINE PRIVAR

Prints a list of basic variables, and constraint relations, for
LSQ.

Prerequisite calls:

VARMAK must have been obeyed to create the lists

Output:

For most basic variables, lists their names. For family 4, ("very long
vectors") only prints ranges.

Then lists the strict constraints.
Any phases and sources are indicated by *P and *S

Calls:

KUNPAK MESS PARNAM

Called by:

VARMAK

Common blocks used:

/CONSTR/ to use JCONST JROWPT JCMAT AMOUNT
/DERBAS/ to use LVARB
/GLOBAL/ to use MULFAS
/IOUNIT/ to use LPT ITO
/PHASE/ to use KPHASE
/POINTS/ to use LVRPR LBSVR LRDVR
/SOURCE/ to use KSOURC

*** PRIVAR updated for MK4 by JCM Aug 89 ***

Classification:

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

SUBROUTINE PRIWRD(IFAM,IGEN,ISPC,NAME,MODE)

Finds the name of the packed (possibly part) LSQ parameter from
the built-in table of parameter names.

Arguments:

On entry IFAM, IGEN, ISPC are family, genus and species of the parameter.
MODE=0 requests left justify, =1 right justify.

On exit NAME is the A4 name from the table in /WORDS/, or 'XXXX'

Prerequisite calls:

The table must have been set up by LSETUP

Calls:

KPAK NFIND

Called by:

PARNAM

Common blocks used:

/GLOBAL/ to use MULONE
/SOURCE/ to use KSOURC
/WDSPC/ to use all members
/WORDS/ to use all members

*** PRIWRD updated for MK4 by JCM 8 May 90 ***

Classification:

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

SUBROUTINE PRMBLK

Applies shifts to multipole parameters, in both program and user
units.

Prerequisite calls:

APSHMP must have stored a vector of multipole shifts in POLAMP(,4)
and ESDs in POLAMP(,6)

CONMAT holds the conversion matrices

Description:

Applies matrix transformation to set of shifts to convert them into user's notation.

Output:

Prints the converted shifts in the usual format on unit LPT

Calls:

ADJUST CONVMP FETSHF KPAK NSIGFG PARNAM

Common blocks used:

/IOUNIT/ to use LPT
/MPODA/ to use NMPOL POLAMP KPOLMP
/NEWOLD/ to use SHIFT XOLD XNEW ESD IGEN ISPC SHESD

*** PRMBLK updated by PJB 4-Apr-2001 ***

Classification:

Multipole Form Factors . . . . . . . Crystallographic

SUBROUTINE PRMTIV

A specialist routine for use in generating h,k,l indices where the
natural stepping vectors do not define a primitive cell.

Prerequisite calls:

Called from SETGEN

Description:

Sets up coefficients NPRIM(2,2), MCOUNT(2), LFAC(2) in /HKLGEN/ to make primitive stepping vectors from the existing steps.

Calls:

BINDIG FCTOR GMADD GMEQ VECPRD

Called by:

SETGEN

Common blocks used:

/HKLGEN/ to use STEP NPRIM NP LFAC MCOUNT
/IOUNIT/ to use LPT ITO IOUT

*** PRMTIV by JCM 11 Oct 84 ***

Classification:

Manipulation of Reflection Indices . . . . . . . Setting Up

LOGICAL FUNCTION PRNCYC(N)

Decides whether printing (of various different quantities in LSQ)
is needed during the current LSQ cycle.

Arguments:

On entry N is an integer specifying which member of the array IPRNT
in /REFINE/ is to be consulted. Values of N already assigned in some standard LSQ applications are:

N=1: PRIN - routine IICD1 (called by most LSQ applications) scans any
I cards for a "PRIN" item; it it finds one, it reads the integer which follows to IPRNT(1), and uses it as an indicator of the frequency with which general "obs and calc" lists are printed during the refinement. These are:
0 = no printing 1 = print during first cycle 2 = print during last cycle 3 = print during first and last cycles 4 = print every cycle

N=2: PRFC - similar to N=1, but used in the Profile Refinement system
to control the printing of reflection information.

N=3: PRFO - as N=2, for a file to be reinput to the Fourier routines.
N=4: PRPR - as N=2, for a file containing the profile, to be reinput,
e.g., to GENIE.

N=5: PRCV - as N=2, but only obeyed on last cycle. The integer
following "PRCV" is an indication of how many covariances from the inverse LSQ matrix to print on the .HKL file.
So PRNCYC would be irrelevant here.

N=6: PREE - as N=2, for a file containing the eigenvalues and
eigenvectors of that part of the inverse LSQ matrix relevant to intensities. PRNCYC is again irrelevant, the integer here indicating how much material is sent to the line-printer file.

N=7: PRDM - read by IICD1, called by most LSQ applications. Requests
printing during the last cycle of h,k,l Fo Fc to a a .DEP file for "deposited Material". This file may be subsequently interpreted by the main program DEPOS.

N=8: PRSK - read by GEOMCO, called by structure LSQ applications.
Requests the printing of an "obs and calc" list for any slack constraints, including both geometrical constraints and those in Profile Refinement of Pawley-type.

The user would be free to use higher values of N, e.g. from 20 downwards, for his own print control. An example of such use occurs in the main program GRLSQ, in which N=2 is used in a different context from the above.

Prerequisite calls:

IPRNT(N) in /REFINE/ must contain an integer with a value in the range 0-4, as described above. ICYC in /REFINE/ must be the current cycle number.

Description:

The function PRNCYC is set TRUE if printing is required, taking of both IPRNT(N) and ICYC.

Called by:

GEOMLS CHILSQ MAGLSQ MMPLSQ MPLSQ PALSQ SFLSQ SFTLSQ

Common blocks used:

/REFINE/ to use NCYC1 LASTCY ICYC IPRNT

*** PRNCYC by JCM 17 Nov 84 ***

Classification:

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

SUBROUTINE PRNTMP(L21)

Prints out a Fourier projection or one layer of a 3D Fourier.

Arguments:

On entry L21 is the number of I5 integers required on a line.

Prerequisite calls:

The values of points on the map must be in array dens in COMMON /MAPDA/,
They are usually put there by one of FOUR1Z, FOURGP, ERRMAP, or GETMAP which of these is used is usually decided by FORIER in respons to requests on the M "cards"

Output:

The array of values is rounded to I5 integers and printed in rows of L21 columns on unit LPT

Calls:

INDFIX JFIX MESS

Called by:

FORFIG FOURPL

Common blocks used:

/IOUNIT/ to use LPT
/MAPDA/ to use OUTLIM NX NY NDIM DENS MODET SECEND

*** PRNTMP updated by PJB 29 Apr 88 ***

Classification:

Fourier Calculations . . . . . . . Crystallographic

SUBROUTINE PROPAG(MODE,INOUT)

Multiple entry subroutine for propagation vector refinement

Arguments:

MODE indicates what function is required
MODE = 1 Read a Q PROP card if present and if so call PROPER
on exit INOUT is 1 id found 0 if not
= 2 Set the symmetry constraints on the magnetic propagation vector
INOUT is set on input to the offset of the propagation vector in the family 1 genus 1 parameters
= 3 Apply a shift to the INOUTth component = 4 Write new Q PROP card on unit INOUT = 0 all components fixed = negative integer set the variable number of the -MODEth component to be INOUT

Calls:

ADJUST ERRMES FINDCD FIXPAR FIXREL GENELM GMEQ GMREV JGMZER KPAK LENGT PROPER RDNUMS RELSM3

Called by:

DOMAG DOMAG2 NWINDS VARSDS

Common blocks used:

/NSYM/ to use NOPC
/SATELL/ to use PROP KPROP KSTAB IPROP
/SYMDA/ to use SYM
/SYMTAB/ to use NORD

*** PROPAG new by PJB 28-Sept-93 ***

Classification:

Magnetic Structure Factors . . . . . . . Crystallographic

SUBROUTINE PROPDR(H,IS,DER)

Makes derivatives of d*sqrd with respect to the magnetic
propagation vector

Calls:

GMZER

Called by:

CALDSM

Common blocks used:

/CELPAR/ to use CPARS

*** PROPDR updated by PJB 1 Feb 1994 ***

Classification:

Magnetic Structure Factors . . . . . . . Crystallographic

SUBROUTINE PROPER(AKVEC)

Determines whether the satellites generated by the propagation
vector PROP have integer indices, and generates its "star".

Arguments:

On entry AKVEC is the 1X3 propagation vector copied to PROP
There is an ENTRY KSTAR(AKVEC,BKSTAR) to return the vectors AKSTAR of the star in BKSTAR as well as filling in the common /SATELL/

Prerequisite calls:

SYMOP should have been obeyed to read the space group symmetry

Description:

On exit IPROP in /SATELL/ is zero if PROP is 0 0 0
negative for other integer indices and positive for non-integer values.

IABS(IPROP) is set to 2 if twice PROP is a reciprocal
lattice vector.

On exit the symmetry table of the star is in KSTAB.
NKSTAR holds the number of vectors in the star,
INCOM is .TRUE. if the propagation vector is fixed on a symmetry point and FKSTAR is a scale for structure factors assuming a mono-k domain.
The ENTRY KSTAR not only writes the common /SATELL/ but also returns the vectors AKSTAR of the star.

Output:

Writes its findings on unit LPT

Entries:

KSTAR called by: ICDINC ICDINC MAG3D

Calls:

EQRLV GMEQ GMREV KSTARS ROTSYM

Called by:

DOMAG DOMAG1 ICDFMT PROPAG

Common blocks used:

/IOUNIT/ to use LPT
/NSYM/ to use NOPC
/SATELL/ to use PROP KSTAB NKSTAR IPROP FKSTAR NKC KCENT INCOM

*** PROPER updated by PJB FOR KSTAB(1) C141 MARCH 2006 ***

Classification:

Magnetic Structure Factors . . . . . . . Setting Up

SUBROUTINE PSFILE(NAME)

Generates a name for a postscript file

Arguments:

On exit NAME is the chosen name iwith extension ".ps" local file 'sequ.seq'. This number is incremented by 1 after each call, and set back to 1 when greater than 99.

Description:

The name chosen is the first 4(5) characters of the program name followed by the 2(1) digits in the sequence number read from the

Calls:

CLOFIL LENGT NOPFIL UPONE

Called by:

GRAFIC

Common blocks used:

/SCRACH/ to use MESSAG
/WHEN/ to use MAIN

*** PSFILE put in to library by PJB 20-Apr-2000 ***

Classification:

Graphical Output . . . . . . . Setting Up

SUBROUTINE PSICON(MGAT,IFTAB)

Determines which atoms need phase factors in modulated structures.

Arguments:

MGAT identifies the magnetic atom in question.
IFTAB contains the factor table for the atomic site symmetry group.

Prerequisite calls:

The factor table for the magnetic symmetry group must be already in MSTAB.

Description:

On entry LPHI in common MAGDAT holds the number of the operator
which generates a sub-lattice, and

PHIH the corresponding phase factor as read from the crystal data.

On exit IPTAB(I,MGAT) in MAGDAT has an entry for each symmetry operator I
giving the number labelling the sublattice which is generated by the operation of J on MGAT. The fundamental sublattice is labelled 1.

Logical FCENT(MGAT) is set TRUE when the centre of symmetry generates
magnetically independent sublattices which need phase factors: in which case the index I in
IPTAB runs from 1 to NOP, rathert han 1 to NOPC.

Notes:

The phase offsets refer to atoms in the actual positions generated by the symmetry elements, they need not necessarily be in the origin cell.

Calls:

COSET ERRIN2 GMEQ GMZER JGMEQ JGMZER LERCHK NFIND

Called by:

MAGCON

Common blocks used:

/ATNAM/ to use ATNAME
/IOUNIT/ to use LPT
/MAGDAT/ to use JMAGAT PHIH LPHI NPHI FCENT IPTAB
/NSYM/ to use NOP NOPC
/SYMMAG/ to use MSTAB

*** PSICON reorgsnised by PJB C141 March 2006 ***

Classification:

Magnetic Structure Factors . . . . . . . Setting Up

SUBROUTINE PUNPAK(KK,IFAM,IGEN,ISPC)

Unpacks a parameter specification from single integer.

Arguments:

On entry KK holds packed parameter specification
On exit IFAM holds family number
IGEN holds genus number
ISPC holds species number

Prerequisite calls:

KK must have been made via a call of KPAK set up by LSETUP

Description:

Unpacks KK according to bases previously set

Notes:

There is an inverse routine KPAK

Calls:

NPACK

Called by:

APSHDS APSHSF APSHT2 VARSDS VARSMG VARSSF VARST2

Common blocks used:

/LSQPAK/ to use all members

*** PUNPAK by JCM 8 Nov 90 ***

Classification:

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

SUBROUTINE PUTPAR(A,I,NUM,PAR,BAD)

Distributes parameters read by RDNUMS amongst individually named
variables.

Arguments:

On entry A is a vector of length at least NUM
NUM is the number of parameters read by RDNUMS
I is the position of the required parameter in A
BAD is the value to put into PAR if the parameter wasn't read
ie if I > NUM.

On exit the value has been set into PAR.

Called by:

DOMAG DOMAG1

*** PUTPAR by PJB Aug 91 ***

Classification:

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


Contents Manual

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