the polymorphic tracking code ptc etienne forest kek and frank schmidt cern basic “clickable”...

32
The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Upload: darlene-gardner

Post on 18-Dec-2015

240 views

Category:

Documents


3 download

TRANSCRIPT

Page 1: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

The Polymorphic Tracking CodePTC

Etienne Forest

KEK

and

Frank Schmidt

CERN

Basic “Clickable” Survey

Page 2: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

S ta rt

1

2

4

3

En d

S tart_G rou n d

L a s tLas tp o s = 3

L egen dS p ec ial no d es o f typ e fib re

A c tual no d es o f typ e fib re rep res enting "m agnet" num b er ii

P o inter to next no d eP o inter to p revio us no d e

N ull P o inter at the s tart and the end o f the lis t

L inked c ut in trac king a ring (S o r o ne-s p here to p o lo gy)1

Linked rep lac ing 1in the c as e o f S

Layout of Fibres

The layout is primarily a description of the “beam pipe” as a function of a discontinues index “i” ranging from 1 to N. In PTC it is a Fortran90 linked list. The above example has 4 fibres.Click on the figure for explanations.

Diagram of a fibre

Page 3: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Diagram of a Fibre

M A GN E T _ C H A R T

M A GN E T _ N

M A G N E T _ C H A R T

M A G N E T D E S C R IP T IO NA N D

T R A C K IN G A L G O R IT H M

M A G N ET _ I

M A GN E T _ 1

M A GN E T _ I

Element

Chart

Page 4: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Diagram of a Chart

A LP H A

EN T (1,3)

EN T (3,3)

L

EX I(3,3)

EX I(1,3)

A (3)

B (3)

M ID (3,3)

M ID (1,3)

M is a lign ed E lem en t

Page 5: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

MisalignmentsThe existence of the chart insures that the single particle propagators attached to an element will behave like true objects. It is very important for the tunnel and the actual magnet to exist separately in theory as they do in the real world. This is insure by the Chart inside the fibre.

The first application of the “object-oriented” propagator of the fibre resides in the implementation of misalignments. The misalignments are defined with respect to the frame “MID” of the Chart. It is represented by the fat orange line.

The syntax for misalignments is simpleFIBRE=MIS(6)

MIS(1:3)=translation and MIS(4:6)=rotation.

Page 6: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Object Tracked by PTC: Flow

1. Six Double Precision X(6)2. Six REAL_8 Y(6)3. Six ENV_8 YS(6)

These three different objects can be tracked. They are the fundamental objects on which the flow operates.

Page 7: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Tracking Calls in a Layout•TRACK(Layout,X(6) ,i, j,Present_State )

•TRACK(Layout,Y(6) ,i, j,+ Present_State )

•TRACK(Layout,YS(6) ,i,j,+ Present_State )The italic objects are optional. The object is tracked from position i to position j in the layout.

In the absence of j, if the layout is a ring, then the layout is tracked one turn around starting at i.

The flow is tracked in the state Present_State if present, otherwise in the Default state.

The optional + turns on parameter dependence.

Page 8: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Fixed Point Finder•FIND_ORBIT(Layout,X(6) ,i, Present_State ,EPS)

•FIND_ORBIT(Layout,Y(6) ,i, Present_State )

•FIND_ORBIT(Layout,YS(6) , X(6) ,i)These call can only be used on a closed ring topology. The variable EPS, a small real number, is used for the numerical computation of the linear matrix used in the Newton search.All the other calls used TPSA and therefore CANNOT be used inside a TPSA algorithm.

The second call, on the polymorph Y(6), returns the matrix in Y with No=1. Y must be allocated or killed before entry.

Similar situation with YS(6), it must be fresh on entry. The code returns a YS with No=1 and the equilibrium sizes in YS%SIGMA0. YS is ready to be tracked.

Page 9: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Tracking a Polymorph Y(6) In PTC if the Real_8 array Y(6) starts as “real” and if there are no system parameters, then tracking proceed as if Y were double precision albeit slower. Obviously a useless outcome. Thus the real goal here is to track a Taylor series map. We now outline the steps.

First CALL:•CALL INIT(STATE,NO,NP,PACKAGE,MAPINT,ND2,NPARA)•CALL INIT(STATE, NO,NP,PACKAGE,ND2,NPARA,Y) => this call is explained later.

•PACKAGE supports BERZ or ETIENNE! We recommend BERZ for the time being as ETIENNE is an experimental package.•MAPINT is an integer indicating, on the basis of the STATE, how many of the six variables of Y start as a Taylor series rather than as a real. In PTC, MAPINT is either 4,5, or 6.•ND2 is the phase space dimension: 4 or 6 in PTC. (2,4, or 6 in FPP)•NPARA is related to polymorphic parameter dependence. For example if one wants a quadrupole strength to be a Taylor variable. NPARA is always MAPINT+1. So it is a little redundant.

For the computation of a Taylor map, the set of calls may look like this:CALL FIND_ORBIT(STATE,FIX,LOCATION,1.D-7) ! Finds orbit at position LOCATIONCALL INIT(STATE,NO,NP,PACKAGE,MAPINT,ND2,NPARA)CALL ALLOC(Y) ! Allocation of Y(6) Y= MAPINT ! Tells FPP to get ready to create an identity map in first MAPINT variablesY=FIX ! Creates an identity map around the fixed point stored in FIXCALL TRACK(LAYOUT,Y, LOCATION, STATE)

Page 10: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

On-the-fly Parameter DependenceOne of the virtue of PTC is on-the-fly parameter dependence. This is activated with the unary + on a state:

CALL TRACK(PSR,Y,1,+Default)This will track the variable Y(6) (most likely a Taylor map) with system parameters on. This activation is always temporary. Thus in the calls

CALL TRACK(PSR,Y,1,+Default)CALL TRACK(PSR,Y,1, Default)

The second call does use the system parameters.

The system parameters are set with the type POL_BLOCK; system parameters can be permanently removed from a layout such as PSR with: CALL KILL_PARA(PSR) .

All TSPA calculations in FPP are done with the system parameters. Thus, as we said perhaps 100 times, all of standard perturbation is accessible to PTC will polymorphism turned on.

Page 11: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Tracking (cont)

The following assignment is permissible in PTC. For example: Y=MAPINT ! Makes the first MAPINT polymorph KIND=0 Y=NORMAL%A_T+X ! Adding a real array with a DAMAP; only allowed in PTC CALL TRACK(LAYOUT,Y, LOCATION,J, STATE)

In this case the array Y is set equal to the fixed point plus the canonical transformation A of a normal form. This is obviously a lattice function calculation from position LOCATION to position J. Notice that this is normally forbidden in FPP since a kind=0 polymorph expects an integer. However this precaution is superseded in PTC by setting insane_PTC = . true.!

The call INIT(STATE, NO,NP,PACKAGE,ND2,NPARA,Y) does internally the calls

CALL ALLOC(Y) Y=MAPINT

One must make sure that Y has been killed if used previously.

So far we did not discuss how to turn some variable into a TPSA parameter. Of course this involves the unary (+) on the state, but this is not sufficient. One must tell PTC what the parameters are. This can be done easily with the type POL_BLOCK.

Page 12: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Eternal States•Default0•Totalpath0•Radiation0•Nocavity0•Time0•Fringe0•Exactmis0•Only_4d0•Delta0

These states are the fundamental states on which PTC builds its tracking states. The last two states in red are related to TPSA calculations and thus affect mostly the flow of Y(6).

The eternal states are to provide a mean to restore PTC in its original pristine state if necessary. They are Fortran constants.

Page 13: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Ordinary States and Operations

•Default•Totalpath•Radiation•Nocavity•Time•Fringe•Exactmis•Only_4d•Delta

Same as the eternal state, but these can be changed by the user. In addition the

•Make_States•Addition : S1+S2•Subtraction : S1-S2•Unary + : +S1•Update_States•Print: call Print(state,file_unit)•Clear_States : returns all states to the eternal values

Page 14: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Fibre Definition TYPE FIBRE ! BELOW ARE THE DATA CARRIED BY THE NODE TYPE(CHART),POINTER ::LOCAL TYPE (ELEMENT), POINTER :: MAG TYPE (ELEMENTP),POINTER :: MAGP ! END OF DATA ! POINTER TO THE MAGNETS ON EACH SIDE OF THIS NODE TYPE (FIBRE),POINTER :: PREVIOUS TYPE (FIBRE),POINTER :: NEXT END TYPE FIBRE

The main type is LOCAL which describes the local geometry of the fibre. MAG(MAGP) describes the magnet, including single particle propagators.

The pointers PREVIOUS and NEXT point to the neighboring fibres.

Page 15: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Chart Definition TYPE CHART DOUBLE PRECISION, POINTER:: ENT(:,:) DOUBLE PRECISION, POINTER:: EXI(:,:) DOUBLE PRECISION, POINTER:: A(:),B(:) DOUBLE PRECISION, POINTER:: A_XY DOUBLE PRECISION, POINTER:: L DOUBLE PRECISION, POINTER:: ALPHA ! PATCHES LOGICAL, POINTER:: ENERGY LOGICAL, POINTER:: TIME DOUBLE PRECISION, POINTER:: A_T,B_T LOGICAL, POINTER:: PATCH DOUBLE PRECISION, POINTER:: A_D(:),B_D(:),A_ANG(:),B_ANG(:) ! EXTRA FRAME IN THE CENTER DOUBLE PRECISION, POINTER:: MID(:,:) DOUBLE PRECISION, POINTER:: O(:) ! FIBRE MISALIGNMENTS IF ISOMORPHISM_MIS IS TRUE DOUBLE PRECISION, POINTER:: D_IN(:),ANG_IN(:) DOUBLE PRECISION, POINTER:: D_OUT(:),ANG_OUT(:) END TYPE CHART

Notice that Chart does not support polymorphic REAL_8 variables. Therefore in PTC it is not possible to take derivatives with respect to “tunnel” variables.

Click for diagram

Page 16: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Element Definition TYPE ELEMENT INTEGER, POINTER :: KIND ! COMMON STUFF TO ALL ELEMENT TYPE(MAGNET_CHART), POINTER :: P CHARACTER(16), POINTER :: NAME,VORNAME ! IDENTIFICATION LOGICAL, POINTER :: PERMFRINGE LOGICAL, POINTER :: MAD_CARTESIAN ! SPECIAL FLAG CONNECTED WITH THE CODE MAD ! LENGTH IS COMMON ALTHOUGH CERTAIN THINGS LIKE MARKERS SHOULD NOT HAVE A LENGTH ! WELL LET US SAY IT IS ZERO DOUBLE PRECISION, POINTER :: L ! LENGTH OF INTEGRATION OFTEN SAME AS LD ! DOUBLE PRECISION, DIMENSION(:), POINTER:: AN,BN !MULTIPOLE COMPONENT ! DOUBLE PRECISION, POINTER :: VOLT, FREQ,PHAS,DELTA_E ! CAVITY INFORMATION DOUBLE PRECISION, POINTER :: B_SOL ! SOLENOIDAL FIELD LOGICAL, POINTER :: THIN_SOL ! MISALIGNEMENTS AND ROTATION LOGICAL, POINTER :: MIS,EXACTMIS DOUBLE PRECISION, DIMENSION(:), POINTER ::D,R ! MISALIGNEMENTS! TYPES OF MAGNETS TYPE(FITTED_MAGNET), POINTER :: BEND ! MACHIDA'S FITTED MAGNET TYPE(DRIFT1), POINTER :: D0 ! DRIFT TYPE(DKD2), POINTER :: K2 ! INTEGRATOR TYPE(KICKT3), POINTER :: K3 ! THIN KICK TYPE(CAV4), POINTER :: C4 ! CAVITY TYPE(SOL5), POINTER :: S5 ! SOLENOID TYPE(KTK), POINTER :: T6 ! INTEGRATOR THICK SLOW TYPE(TKTF), POINTER :: T7 ! INTEGRATOR THICK FAST TYPE(NSMI), POINTER :: S8 ! NORMAL SMI TYPE(SSMI), POINTER :: S9 ! SKEW SMI TYPE(TEAPOT), POINTER :: TP10 ! SECTOR TEAPOT TYPE(USER1), POINTER :: U1 ! USER DEFINED TYPE(USER2), POINTER :: U2 ! USER DEFINED END TYPE ELEMENT

Page 17: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Reference Energy in PTCIn PTC the beam line reference energy is used mainly in preparation routines of the MAD_LIKE input. It is used to set the all important reference energy of the element. Since all the PTC propagators have a reference energy associated to them, there is no real need for a “layout reference energy.” Of course by default, energy patches are not used and consequently the layout sits initially at a single reference energy.

The reference energy of a fibre or an Element(P) can be retrieve or set with the help of a variable of type work.

Page 18: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Type Work: Changing Energy TYPE WORK DOUBLE PRECISION BETA0,ENERGY,KINETIC,P0C,BRHO,GAMMA0I,GAMBET DOUBLE PRECISION MASS LOGICAL RESCALE END TYPE WORK

•Work = 0•Work = dE (double precision)•Fibre = Work•Fibre =+Work•Work=Fibre

Fibre assignments generalize the Fibre =(+)Work generalize the assignment Element(P) =(+)Work and sets the energy patch fibre%local%energy to true for this magnet.The assignment Work=Fibre actually reads the energy data from Fibre%mag and warns the user if the data differs substantially with that of Fibre%magp.

Work is initialized: rescale is set to true.

Energy is dE is added to Work%Energy; everything is recomputed.

The fibre’s energy reference is passed to the fibre. Certain magnet data is scaled.

The fibre’s energy reference is passed to the fibre. No scaling; rescale is false!

The fibre’s energy is passed to a work variable.

Page 19: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Type Mul_Block TYPE MUL_BLOCK ! STUFF FOR SETTING MULTIPOLE DOUBLE PRECISION AN(NMAX),BN(NMAX) INTEGER NMUL,NATURAL,ADD END TYPE MUL_BLOCK

Mul_Block is a convenient type to retrieve and put multipoles in a fibre. It is limited to NMAX=20. This is not a fundamental limitation.

•Mul_Block=Nmul

•Fibre= +Mul_Block

•Mul_Block = Fibre => Mul_Block = Fibre%Mag

Fibre%Mag = Mul_Block

Fibre%Magp = Mul_Block

The unary (+) permits to add the Mul_block to the existing multipoles.

These types can be used with any magnet using AN and BN.

Page 20: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Layout Definition TYPE LAYOUT LOGICAL,POINTER ::CLOSED INTEGER, POINTER :: N ! TOTAL ELEMENT IN THE CHAIN INTEGER,POINTER ::NTHIN ! NUMBER IF THIN LENSES IN COLLECTION (FOR SPEED ESTIMATES) DOUBLE PRECISION, POINTER :: THIN ! PARAMETER USED FOR AUTOMATIC CUTTING INTO THIN LENS DOUBLE PRECISION, POINTER :: CIRCUMFERENCE ! IDEAL LENGTH DOUBLE PRECISION, POINTER :: ENERGY,KINETIC,P0C,BRHO,BETA0 !ENERGY,KINETIC ENERGY, ETC... !POINTERS OF LINK LAYOUT INTEGER, POINTER :: LASTPOS ! POSITION OF LAST VISITED TYPE (FIBRE), POINTER :: LAST ! LAST VISITED ! TYPE (FIBRE), POINTER :: END TYPE (FIBRE), POINTER :: START TYPE (FIBRE), POINTER :: START_GROUND ! STORE THE GROUNDED VALUE OF START DURING CIRCULAR SCANNING

TYPE (FIBRE), POINTER :: END_GROUND ! STORE THE GROUNDED VALUE OF END DURING CIRCULAR SCANNING

END TYPE LAYOUT

The most important items of type Layout are in red. Layout is a two linked list. It is circular if the parameter CLOSED is true.

Page 21: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

TYPE(POL_BLOCK) QUAD_FAMILY1,QUAD_FAMILY2 • • •CALL INIT(DEFAULT+DELTA,3,2,BERZ,MAPINT,ND2,NPARA)CALL ALLOC(Y);CALL ALLOC(NORMAL); ! ALLOCATE VARIABLESY=MAPINTY=X

QUAD_FAMILY1=NPARA ; QUAD_FAMILY2=NPARA ;QUAD_FAMILY1%IBN(2)=1 ; QUAD_FAMILY2%IBN(2)=2;QUAD_FAMILY1%NAME=“QF” ; QUAD_FAMILY2%NAME=“QD”;PSR=QUAD_FAMILY1 ; PSR=QUAD_FAMILY2;

CALL TRACK(PSR,Y,1,+(DEFAULT+DELTA))

Parameters : Pol_Block

Number of parameters

The above code shows the usage of two Pol_Block. The family of QF will be represented by the first TPSA parameter and that of QD will use the second parameter. Notice the unary plus + in the TRACK call. The output looks like this for the tune:

0 0.2541028117559953 0 0 0 0 0 0 0 1 -0.9281703935548629 0 0 0 0 1 0 0 1 4.884893727296833 0 0 0 0 0 1 0 1 1.507923217196958 0 0 0 0 0 0 1

Pol_block definition here

x

KQD

x

KQF

Page 22: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Setting Parameters : Pol_Block

Often we may want to change the numerical value of a field described by a Pol_Block, for example during a fit using TPSA. Pol_Block provides tools for this.

Pol_block definition here

QUAD_FAMILY1=NPARA ; QUAD_FAMILY2=NPARA ;QUAD_FAMILY1%IBN(2)=1 ; QUAD_FAMILY2%IBN(2)=2;QUAD_FAMILY1%NAME='QF' ; QUAD_FAMILY2%NAME='QD';SET_TPSAFIT=.TRUE.TPSAFIT(1)=1. D-4;TPSAFIT(2)=1.D-4;PSR=QUAD_FAMILY1 ; PSR=QUAD_FAMILY2;

The only difference with the previous example are in red. The result for the tune is: 0 0.2547420327906353 0 0 0 0 0 0 0The reader can plug parameters in the tune formula of the previous slide and check numerically this result.

N.B. These changes only affect the polymorphic part of the layout. To upgrade the full layout one must use the command copy_elp_el(layout).

Page 23: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

The Topology of the Layout

A fibre is either circular (a ring) or a segment ( a beam line).

In a ring, the violet lines are cut and replaced by the blue lines.

The next pointer of the last fibre points to the first fibre.

The previous pointer of the first fibre points to the last fibre.

Page 24: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

REAL_8

TYPE REAL_8 TYPE (TAYLOR) T ! IF TAYLOR DOUBLE PRECISION R ! IF REAL INTEGER KIND ! 0,1,2,3 (1=REAL,2=TAYLOR,3=TAYLOR KNOB, 0=SPECIAL) INTEGER I ! USED FOR KNOBS AND KIND=0 DOUBLE PRECISION S ! SCALING FOR KNOBS AND KIND=0 LOGICAL :: ALLOC ! IF TAYLOR IS ALLOCATED IN DA-PACKAGE END TYPE REAL_8

This type is defined in FPP’s definition.f90

Page 25: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

ENV_8 !RADIATION TYPE ENV_8 TYPE (REAL_8) V TYPE (REAL_8) E(NDIM2) TYPE (REAL_8) SIGMA0(NDIM2) TYPE (REAL_8) SIGMAF(NDIM2) END TYPE ENV_8

Page 26: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

States Definition TYPE INTERNAL_STATE LOGICAL TOTALPATH,TIME,RADIATION,NOCAVITY,FRINGE,EXACTMIS LOGICAL PARA_IN,ONLY_4D,DELTA END TYPE INTERNAL_STATE

In the Default0 state all the above logicals are all false.Generally a variable named after a state is true for this state and all the other are false.

•Time: time rather than path length is computed•Totalpath: total path length or time is computed rather than just the differential T-Tdesign

•Radiation: Classical radiation is turned on•Nocavity: RF Cavities (kind4) are ignored.•Fringe: quadrupole fringe fields are on•Exactmis: Exact formulas for the misalignments•Para_in, only_4d and delta affect TPSA calculations.

Page 27: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Make_StatesEvery main program using PTC must start with a call to MAKE_STATES. There are two possible interfaces.

CALL MAKE_STATES(particle) ! Particle is a logical or asCALL MAKE_STATES(muonfactor) ! Muonfactor is a real*8

Particle is true for an electron and false for a proton. The other case is equivalent to an electron but with a scale factor of “muonfactor” for the mass.

This subroutine sets all the fundamental internal states equal to the eternal states. In addition, it solves Maxwell's equations in polar coordinates to order SECTOR_NMUL. Please set SECTOR_NMUL to the desired order prior to calling MAKE_STATES.

Now we show how the state DEFAULT can be modified.

Page 28: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Addition of StatesTwo states can be added. For example:

Default=Default+Fringe0In this case the new Default has quadrupole fringes always on.The logicals of each state are added as follows in the overloading function Add:

Add%field = Default% field .or. Fringe0% field Where field stands for any field of type Internal_state such as Fringe or Time.

This is followed by a checkIF(ADD%DELTA) THEN

ADD%ONLY_4D = T ! T stands for .TRUE. and F for .FALSE.ADD%NOCAVITY = T

ENDIFIF(ADD%ONLY_4D) THEN

ADD%TOTALPATH = FADD%RADIATION = FADD%NOCAVITY = T

ENDIF

Page 29: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Subtraction of States

One can temporarily remove a property from a state. For example, suppose that the state default has been changed to contain quadrupole fringes. (take a look here)

We can remove this particular property temporarily using subtraction of states. For example

CALL TRACK(PSR,Y,1,DEFAULT-FRINGE0)

In this case tracking ignores quadrupole fringe fields in magnets unless the fringe fields are permanently turned on with PERMFRINGE set to true.

Page 30: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Updating States

At the start of any PTC run the states are all in the Default state except for the property which is special to them. For example, the NOCAVITY state is the Default state with the field NOCAVITY set to true. Suppose we change Default to include quadrupole fringe fields, then only the Default state with have fringes on. Can we update all the states to have this property?

The simple statementCALL UPDATE_STATES

does the job.

Page 31: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Magnet_Chart

TYPE MAGNET_CHART TYPE(CHART), POINTER :: LOCAL DOUBLE PRECISION, POINTER :: LD,B0,LC ! DOUBLE PRECISION, POINTER :: TILTD ! INTERNAL FRAME DOUBLE PRECISION, DIMENSION(:), POINTER :: EDGE(:) ! INTERNAL FRAME DOUBLE PRECISION, POINTER :: BETA0,GAMMA0I,GAMBET,P0C ! INTEGER, POINTER :: TOTALPATH ! LOGICAL, POINTER :: EXACT,RADIATION,NOCAVITY ! STATE LOGICAL, POINTER :: FRINGE,TIME ! ! LOGICAL, POINTER :: IN,OUT ! HALF MAGNET FLAG (SPECIAL FLAG FOR EVIL 1/2 MAGNETS) ! ! INTEGER, POINTER :: METHOD,NST ! METHOD OF INTEGRATION 2,4,OR 6 YOSHIDA INTEGER, POINTER :: NMUL ! NUMBER OF MULTIPOLE END TYPE MAGNET_CHART

The chart local is of the same nature as the chart local of a fibre. Theoretically it can describe the position of a magnet propagator within the blue frame shown on chart diagram. A full implementation of this feature, could allow the integration variable ELEMENT%L to be really polymorphic.BETA0,GAMMA0I,GAMBET and P0C are redundant energy variables of the magnet. They can be changed using the type WORK.

METHOD and NST describe the integration method and the number of steps desired. NMUL is connected to the number of multipole components activated in various kinds.

Page 32: The Polymorphic Tracking Code PTC Etienne Forest KEK and Frank Schmidt CERN Basic “Clickable” Survey

Pol_Block Definition

TYPE POL_BLOCK CHARACTER*16 NAME,VORNAME ! STUFF FOR SETTING MAGNET USING GLOBAL ARRAY TPSAFIT DOUBLE PRECISION,DIMENSION(:), POINTER :: TPSAFIT LOGICAL, POINTER :: SET_TPSAFIT ! STUFF FOR PARAMETER DEPENDENCE INTEGER NPARA INTEGER IAN(NMAX),IBN(NMAX) DOUBLE PRECISION SAN(NMAX),SBN(NMAX) INTEGER IVOLT, IFREQ,IPHAS INTEGER IB_SOL DOUBLE PRECISION SVOLT, SFREQ,SPHAS DOUBLE PRECISION SB_SOL ! USER DEFINED FUNCTIONS TYPE(POL_BLOCK1) USER1 TYPE(POL_BLOCK2) USER2 END TYPE POL_BLOCK

•Family name and first name used to identify a magnet. •TPSA_FIT: array containing numerical values of parameters•Polymorphic information for FPP•Polymorphic information of user-defined elements