source: PSPA/parmelaPSPA/trunk/pardyn.f @ 465

Last change on this file since 465 was 12, checked in by lemeur, 12 years ago

parmela pspa initial

File size: 14.5 KB
Line 
1      subroutine pardyn
2c---calculate dynamics for nsteps in time (phase), each step of length dwt.
3c---calculate space-charge impulse at beginning of each nsc steps.  call
4c---output at end of every nout steps.
5c---insert common blocks here
6c----------------------------------------------------------------------
7      save
8      include 'param_sz.h'
9      include 'var_char.h'
10      include 'cfldscom.h'
11      include 'constcom.h'
12      include 'coordcom.h'
13      include 'debug.h'
14      include 'flagcom.h'
15      include 'misccom.h'
16      include 'ncordscom.h'
17      include 'outcom.h'
18      include 'pcordcom.h'
19      include 'sccom.h'
20      include 'syscom.h'
21      include 'tstepcom.h'
22      include 'ucom.h'
23c
24      common/aswap/acor(7,imaa)
25      common/back/bmax,byz0,byzs,pzowmin,pzowmax,iback
26      common/chars/title
27      common/ct/var,rp,dzmin,dzmax,wrm,dwbm,xrmsbg,yrmsbg,
28     1          xsmax,xpsmax,ysmax,ypsmax,istat,nebm
29      common/errors/eraln(5,0:lmx)
30      common/intype/intype ! mcd
31      common/jones/ajones,zjones,zcath(imaa) ! mcd
32      common/out6/nbphase,nbremesh
33      common/outbuf/outcor(8,imaa*imb)
34      common/part/nparticle(imaa)
35      common/pnum/ipnum(imaa)
36      common/save/zrsav
37      common/wtstep/wtestep,nstep ! mcd
38      real xyz(7)
39      logical outflag
40      equivalence (xyz(1),x)
41      data outflag/.true./
42c--------------------------------------------------------------------------
43c*
44      if(ngood.le.0)return
45      inb=imaa*imbf/npoints
46      if(inb.gt.maxbuf)inb=maxbuf
47      dcon=wavel/360.         ! conversion degrees to cm
48      dwtsc=nsc*dwt*dcon
49      mt=0
50c     For input type 10 and 11 nstep = no. of extra steps to be added
51c     at beginning of loop to allow for generation at the photocathode
52c     nstep is define in input 10 and 11
53      mt=mt-nstep ! mcd
54      msbl=0
55      mdpoutl=0
56c---start loop on time steps
57   10 continue
58      mt=mt+1
59      swt=sin(wt*radian)
60      cwt=cos(wt*radian)
61      wt1=wt+dwt
62c---set space-charge and output flags
63      if(nsc.le.0)msc=1
64c      if(nsc.gt.0)msc=mod(mt-1,nsc)
65      if(nsc.gt.0)msc=mod(mt,nsc)
66      if(beami.eq.0.)msc=1
67      if(nout.le.0)mout=1
68      if(nout.gt.0.and.mt.ne.0)mout=mod(mt,nout)
69c---calculate space-charge fields from present particle distribution.
70c---and apply space-charge impulse to particles.
71      if(msc.eq.0) then
72        if(iprog.eq.1) call scheff1(dwtsc,mt,wt1)
73        if(iprog.eq.2) call scheff2(dwtsc,mt,wt1)
74        if(iprog.eq.3) call scheff3(dwtsc,mt,wt1)
75      else          ! isc
76      endif         ! isc
77c---check single-bunch beam loadin flag
78      if(msbl.ne.0)call sbload(nesb)
79      if(mdpoutl.ne.0)call dpout(nedpout)
80      mdpoutl=0
81      msbl=0
82      np=0
83      nle=0
84c---start loop on particles
85   20 continue
86      np=np+1
87cbm      itoto=np
88      itoto=0
89      nupar=np
90c---get particle coordinates
91   25 do 26 i=1,7
92        xyz(i)=cord(i,np) !xyz(1,2,...,7) equiv to x,bgx,..,ne
93   26 continue
94      ne=rne
95      gamma=gam(np)
96      wtp=wt
97      dwtp=dwt
98      phinought=phizero(np)
99c Upstream of first element (ne.le.0)
100      if((intype.eq.10 .or. intype.eq.11 .or. intype.eq.15)
101     .  .and. ne.le.0) then
102c        5/10/87 Revised treatment of particles upstream of first element.
103        bz=bgz/gamma
104      if(bz.le.0.0) then   ! back-bombardment
105            if(iback.eq.0) go to 155
106            if(ne.gt.1 .or. (np.eq.1 .or. z.lt.z0)) go to 155
107      endif
108c---calculate remaining distance this particle would travel in this
109c---step at this velocity
110        dz=bz*dcon*dwtp
111        zn = z + dz
112c---set "end of element" flag to off
113        iend=0
114c        zcat = z coord of cathode for emission of this particle
115        zcat = zcath(np)
116        if(zn.lt.zcat) then
117c         particle remains upstream of first element
118c         advance the particle by dz
119          z = zn
120          x = x + dz*bgx/bgz
121          y = y + dz*bgy/bgz
122          go to 150
123        endif
124c         particle crosses into the first element
125c---calculate time spent before reaching the first element.
126        dz = zcat - z
127        dwtp = dz/(bz*dcon)
128c        move particle to beginning of first element
129        z = zcat
130        x = x + dz*bgx/bgz
131        y = y + dz*bgy/bgz
132        ne=1
133        rne=1.
134        nt=ntype(ne)
135c        go to 150 -> 180 -> 30 -> 35 -> 70 to apply cell impulse and drift
136        go to 150
137      endif
138c End upstream of first element
139cmcd
140      if(ne.gt.nel)go to 40
141   30 nt=ntype(ne)
142      if(nt.ne.27.and.nt.ne.29) go to 35
143c---sbload element. set flag,zlen and and cells if np=1
144c-- it is now in sbload
145      if(np.ne.1) go to 34
146      if(nt.eq.27)then
147         msbl=1
148         nesb=ne
149      else
150         mdpoutl=1
151         nedpout=ne
152      endif
153   34 if(ibeg.eq.0)then
154         ne=ne+1
155         rne=rne+1
156      else
157         ne=ne-1
158         rne=rne-1
159      endif
160      go to 30
161c---apply cell impulse
162   35 continue
163      if(nt.eq.7) call cellimp(wtp,dwtp)
164c---apply trwave impulse
165      if(nt.eq.9) call trwimp(wtp,dwtp)
166   40 continue
167      bz=bgz/gamma
168c------allow particles to go backward
169c      if(bz.le.0.)go to 155
170      if(bz.le.0.0) then   
171            if(iback.eq.0) go to 155
172            if(ne.gt.1 .or. (np.eq.1 .or. z.lt.z0)) go to 155
173      endif
174c---calculate remaining distance this particle would travel in this
175c---step at this velocity
176      dz=bz*dcon*dwtp
177      zn=z+dz
178c---set "end of element" flag to off
179      iend=0
180c-----allow particle to go backwards, set "begining of element" flag off
181      ibeg=0
182      if(ne.gt.0) go to 50
183c---particle is upstream of first element.  assume drift.
184      ne=0.
185      rne=0.
186      nt=ntype(1)
187      go to 70
188   50 continue
189      if(ne.gt.nel) go to 70
190      if(nt.eq.8)go to 130
191      if(nt.eq.2)go to 80
192      if(nt.eq.4)go to 100
193      if(nt.eq.35)go to 146 
194      if(nt.eq.36)go to 105
195c-----allow particle to go backwards
196c-----check if particle will cross into previous element during this step
197c-----ntype 1,2,5,7, and 9 perform this check so skip it.
198      if(nt.eq.1 .or. nt.eq.2 .or. nt.eq.7 .or. nt.eq.9
199     *  .or. nt.eq.5)go to 65
200      if(dz.lt.0 .and. ne.ge.1 .and. zn.lt.zloc(ne-1))then
201c---particle will cross into previous element during this step
202      zn=zloc(ne-1)
203      dwtp=(zn-z)/(bz*dcon)
204      ibeg=1
205      go to 64
206      endif
207      if(zn.lt.zloc(ne)) go to 65
208c---particle will cross into next element during this step
209      zn=zloc(ne)
210      dwtp=(zn-z)/(bz*dcon)
211      iend=1
212   64 continue
213      if(nt.eq.26)go to 140
214      if(nt.eq.30)go to 145
215      if(nt.eq.39)go to 147
216   65 continue
217      go to (70,80,90,100,110,120,75,130,70), nt
218c---after drift, linac cell impulse, or trwave impulse
219   70 continue
220      call drift(dwtp,iend,ibeg)
221      go to 150
222   75 continue
223      if(el(11,ne).eq.0)go to 70
224      call solnoid(dwtp,iend,ibeg,el(11,ne))
225      go to 150
226c---after solenoid
227   80 continue
228      call solnoid(dwtp,iend,ibeg,0.)
229      go to 150
230c---after quad
231   90 continue
232      call quad(zn)
233      go to 150
234c---after bend
235  100 continue
236      call bend(dwtp,iend)
237      go to 150
238c---after alpha magnet
239  105 continue
240      call alpham(dwtp,iend,np)
241      go to 150
242c---after buncher
243  110 continue
244      phase=(wtp*el(5,ne)/freq+el(6,ne))*radian
245      call buncher(phase,iend,ibeg)
246      dwtp=0.
247      go to 150
248c---after chopper
249  120 continue
250      phase= wtp*el(4,ne)/freq - el(5,ne)
251      if(phase.gt.0.)phase=amod(phase,360.)
252      if(phase.lt.0.)phase=360.-amod(-phase,360.)
253      if(phase.gt.180.)phase=phase-360.
254      if(abs(phase).gt.el(6,ne))go to 155
255      go to 150
256c---after tank
257  130 continue
258      call tank(wtp,dwtp,iend,ibeg)
259      bz=bgz/gamma
260      go to 150
261c---after rotate
262  140 continue
263      call rotate
264      go to 150
265c---after cathode
266  145 continue
267      call cathode(dwtp,iend,ibeg)
268      go to 150
269c---after wiggler
270  146 continue
271      call wiggler(dwtp,iend)
272      go to 150     
273c---after sextupole
274  147 continue
275      call sextupole(zn)
276      go to 150
277c---check for loss.
278  150 continue
279c-------allow particle to go backwards
280      if(bz.le.0.0) then   
281            if(iback.eq.0) go to 155
282            if(ne.gt.1 .or. (np.eq.1 .or. z.lt.0)) go to 155
283      endif
284      if(ne.le.0 .or. ne.gt.nel)go to 152
285      apsq=el(2,ne)**2    ! aperture
286      rsq=x**2+y**2
287      if(rsq.gt.apsq)go to 155
288  152 continue
289      wtp=wtp+dwtp
290      dwtp=wt1-wtp
291c---problem with number of significant digits so set dwtp=0 if very small.
292      if(abs(dwtp).lt.1.e-4)dwtp=0.
293c---check for end of element
294      if(iend.eq.0.and.ibeg.eq.0) go to 180
295c---particle is at end or begining of element.
296c---if particle is at begining forget it
297      if(ibeg.ne.0)go to 170
298c---this is special code for pepperpot.
299c      if(ne.eq.13.and.np.ne.1)then
300c--- at end of element 13 so apply pepper pot.
301c     x0=-1.1
302c     do 151 i=1,10
303c     x0=x0+.2
304c     y0=-1.1
305c     do 151 j=1,10
306c     y0=y0+.2
307c     if((x-x0)**2+(y-y0)**2.lt..00064516)go to 153
308c151  continue
309c--- particle stopped at pepperpot
310c     go to 155
311c     endif
312  153 continue
313      if(np.ne.1)go to 160
314c---this is the reference particle.  save phase and energy.
315      pr(ne)=wtp
316      wr(ne)=(gamma-1.)*erest
317      if(ne.eq.nel)then
318c--- this is end of last element so output the cordinates of all the
319c--- particles for FELEX  in the format: X,Bgx,Y,Bgy,Z,Bgz,Q(coul)
320      zrsav=cord(5,1)
321      ifelex=0
322      if(ifelex.eq.1) then
323       if(outflag)then
324       open(unit=ndpout,file='dpout',status='new',form='formatted')
325       outflag=.false.
326       endif
327      write(ndpout,'(6(1x,e15.9),1x,e15.9)')((cord(i,j),i=1,6),weight(j)
328     *   ,j=1,ngood)
329      endif
330      endif
331      go to 160
332c---particle has been lost
333  155 continue
334      if(np.eq.1)go to 220
335      call swap(np,wtp)
336      if(np.lt.ngood)np=np-1
337      ngood=ngood-1
338      go to 187
339c---check for output at end of element.
340  160 continue
341c      if(iel(3,ne).ne.0) then
342      nuel=el(3,ne)
343      if(nuel.ne.0) then
344      call sortie(np,ngood,wtp)
345      endif
346c      if(iel(3,ne).eq.0)go to 170
347      if(nuel.eq.0)go to 170
348c---check if referance particle particle is less than zlimit ahead of
349c---this particle if it is ignore it.
350      if(cord(5,1)-cord(5,np).gt.abs(zlimit)) go to 170   
351c---save coordinates in output buffer.
352c---does a buffer already exist for this element
353cliu      if(ne.eq.0) go to 170
354      do 162 i=1,inb
355      k=i
356      if (ne.eq.neb(i)) go to 168
357  162 continue
358c---no buffer. are there any unused buffers
359      do 164 i=1,inb
360      k=i
361      if (neb(i).eq.0) go to 166
362  164 continue
363c---no unused buffers. forget it.
364      write(ndiag,*)' no buffer avaliable for element',ne,' particle',np
365      go to 170
366c---new buffer.  set neb
367  166 continue
368      neb(k)=ne
369  168 continue
370      if(nbuf(k).eq.npoints)then
371c---buffer is full so output it. Then store particle in it.
372      call output(neb(k),nbuf(k),outcor(1,(k-1)*npoints+1),npoints,mt)
373      nbuf(k)=0
374      neb(k)=0
375      endif
376      nbuf(k)=nbuf(k)+1
377      nb=(k-1)*npoints+nbuf(k)
378      outcor(1,nb)=x
379      outcor(2,nb)=bgx/bgz
380      outcor(3,nb)=y
381      outcor(4,nb)=bgy/bgz
382      outcor(5,nb)=wtp
383      outcor(6,nb)=(gamma-1.)*erest
384      outcor(7,nb)=ipnum(np)
385      outcor(8,nb)=weight(np)
386c---if there is a background bfield the beam is rotating.
387c   therefor transform to the rotation frame of referance.
388      if(ifld.ne.0 .or. poiflag)then
389         if(ifoclal.eq.1) then
390           cay=bfldlal(z)/(brhof*sqrt(gamma**2-1.))
391         else
392           cay=bfld(z,sqrt(x**2+y**2),brfld)/(brhof*sqrt(gamma**2-1.))
393         endif
394         outcor(2,nb)=outcor(2,nb)-.5*cay*y
395         outcor(4,nb)=outcor(4,nb)+.5*cay*x
396      endif
397  170 continue
398      if(iback.eq.1) then   
399           if(iend.eq.1)ne=ne+1
400           if(ibeg.eq.1)ne=ne-1     
401      else
402           ne=ne+1
403      endif
404      rne=ne
405      if(ne.le.0.and.bgz.lt.0.)go to 155
406      nt=ntype(ne)
407c---check for misalignment errors
408      if(iend.ne.0) then
409          if(eraln(1,ne).eq.0.)go to 180
410c---adjust transverse coordinates to axis of element
411          con=bgx**2+bgy**2+bgz**2
412          x=x-eraln(2,ne)
413          bgx=bgx-bgz*eraln(3,ne)
414          y=y-eraln(4,ne)
415          bgy=bgy-bgz*eraln(5,ne)
416          bgz=sign(sqrt(con-bgx**2-bgy**2),bgz)
417      elseif(ibeg.ne.0)then
418          if(eraln(1,ne+1).eq.0.)go to 180
419          con=bgx**2+bgy**2+bgz**2
420          x=x+eraln(2,ne+1)
421          bgx=bgx+bgz*eraln(3,ne+1)
422          y=y+eraln(4,ne+1)
423          bgy=bgy+bgz*eraln(5,ne+1)
424          bgz=sign(sqrt(con-bgx**2-bgy**2),bgz)     
425      endif
426c---does this particle have farther to go ?
427  180 continue
428      if(dwtp.gt.0.)go to 30
429c---check distance limit if zlimit is negative particle is not discarded
430      if((cord(5,1)-z).gt.zlimit.and.zlimit.gt.0.)go to 155
431c---save particle back in cord array
432      do 185 i=1,7
433      cord(i,np)=xyz(i)
434 185  continue
435      gam(np)=gamma
436      if(ne.gt.nel)nle=nle+1
437      if(iback.eq.0) go to 187
438      if(ne.ne.1 .or. pzowmax.eq.0.0)go to 187 
439      if(phinought.gt.pzowmin.and.phinought.lt.pzowmax) then
440         if(amod(wt,5.).eq.0.0) write(nback) wtp,bz,x,y,z
441      endif
442c---get next particle, if any
443  187 continue
444      if(np.lt.ngood)go to 20
445c---end of one time step.  check for output
446  190 continue
447      if (ngood.le.0)go to 200
448      wt=wt1
449      if(mout.eq.0) then
450         call output(mout,mout,outcor,npoints,mt)
451      endif
452c---check output buffer.  have all good particles already passed
453c---element neo?
454      do 197 i=1,inb
455c---check output buffer. if full output it. if reference particle
456c---is greater then abs(zlimit) beyond it output it
457      if(nbuf(i).eq.npoints)then
458          neo=neb(i)
459          go to 196
460      endif
461      if(neb(i).ne.0.and.cord(5,1).gt.zloc(neb(i))+abs(zlimit)) then
462          neo=neb(i)
463          go to 196
464      endif
465      if(nbuf(i).eq.0)go to 197
466      neo=neb(i)
467      do 195 np=1,ngood
468      nne=cord(7,np)
469      if(nne.le.neo)go to 197
470  195 continue
471c---yes.  empty buffer.
472  196 continue
473      call output(neo,nbuf(i),outcor(1,(i-1)*npoints+1),npoints,mt)
474      nbuf(i)=0
475      neb(i)=0
476  197 continue
477  199 continue
478      if(mt.ge.nsteps)return
479      if(nle.ge.ngood)return
480      go to 10
481  200 continue
482      write(ndiag, 210)mt
483  210 format(' no more good particles after step',i5/)
484      go to 221
485  220 continue
486      write(nnout, 230)wtp,xyz
487      write(*,*) ' Reference particle lost '
488  221 continue
489      do 225 j=1,inb
490      if(neb(j).eq.0) go to 225
491      if(neb(j).lt.ne) then
492        call output
493     1      (neb(j),nbuf(j),outcor(1,(j-1)*npoints+1),npoints,mt)
494      endif
495      neb(j)=0.
496      nbuf(j)=0.
497  225 continue
498  230 format(' reference particle lost, wt=',f8.1,/
499     1'  x, bgx, y, bgy, z, bgz, rne',/   
500     2 4f8.4,2f8.2,f5.0,/)
501      return
502      end
503c++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++*
Note: See TracBrowser for help on using the repository browser.