Search Site | Contact Details | FAQ

ADAS Subroutine stark

      SUBROUTINE STARK( AMDEUT , AMSS   ,
     &                  BENER  , DV1    , DV2    , DV3   , DENSB ,
     &                  BMAG   , DB1    , DB2    , DB3   ,
     &                  EMAG   , DE1    , DE2    , DE3   ,
     &                  DO1    , DO2    , DO3    ,
     &                  POLO   , POLP   ,
     &                  DENS   , TE     , ZEFF   ,
     &                  NU     , NL     , POPU   ,
     &                  NDCOMP , NCOMP  , WVCOMP , EMCOMP
     &                )


C----------------------------------------------------------------------
C
C  ******************** FORTRAN77 SUBROUTINE: STARK *******************
C
C  PURPOSE: Code for modelling of emission from neutral hydrogen
C           in beams.
C
C  CALLING PROGRAM: ADAS305
C
C  NOTES: Developed from JETSHP.STARK.FORT(EMIS7)
C
C  STEPS: Evaluate Stark/Zeeman shifted hydrogenic energy levels and
C         evaluate dipole matrix elements.
C
C         Calculate directional positive ion impact born cross-sections
C         for Stark/Zeeman states.
C
C         Calculate populations of excited states.
C
C         Calculate polar distribution of emitted radiation for selected
C         lines and its polarisation for the charge exchange spectroscopy
C         multichord viewing lines.
C
C         Initial basis wave functions  -  n l s ml ms
C
C         Stark field is from particle motion across the magnetic induction
C         and a separate pure electric field.
C
C         General geometry specification is by direction cosines
C         dv1,dv2,dv3          : direction cosines of beam particle velocity
C         db1,db2,db3          : direction cosines of magnetic induction.
C         delec1,delec2,delec3 : direction cosines of pure electric filed
C         do1,do2,do3          : direction cosines of observation viewing line
C
C         Specific geometry
C         viewing direction defines the   -i direction
C         i-k plane is that of viewing line and beam direction
C         normal to i-k plane defines the  j direction
C         thetv= angle of beam to i direction (deg)
C         ebeam=beam speed  (kev/amu)
C         b=magnetic induction  (tesla)
C
C  SUBROUTINE:
C
C  INPUT : (I*4)  NU      = UPPER PRINCIPAL QUANTUM NUMBER LINE
C          (I*4)  NL      = LOWER PRINCIPAL QUANTUM NUMBER LINE
C          (I*4)  POPU    = RELATIVE POPULATION OF UPPER (NU) LEVEL
C
C          (R*8)  AMDEUT  = ATOMIC MASS OF HYDROGEN IN BEAM
C          (R*8)  AMSS    = ATOMIC MASS OF HYDROGEN IN PLASMA
C          (R*8)  BENERA  = ENERGY OF ITH BEAM COMPONENT (EV/AMU)
C          (R*8)  DV1     = D.C. FOR X-CPT OF BEAM VELOCITY
C          (R*8)  DV2     = D.C. FOR Y-CPT OF BEAM VELOCITY
C          (R*8)  DV3     = D.C. FOR Z-CPT OF BEAM VELOCITY
C          (R*8)  DENSB   = SPECIFIC NEUTRAL BEAM DENSITY (CM-3)
C          (R*8)  BMAG    = SPECIFIC MAGNETIC FIELD INDUCTION (TESLA)
C          (R*8)  DB1     = D.C. FOR X-CPT OF BMAG
C          (R*8)  DB2     = D.C. FOR Y-CPT OF BMAG
C          (R*8)  DB3     = D.C. FOR Z-CPT OF BMAG
C          (R*8)  EMAG    = SPECIFIC ELECTRIC FIELD STRENGTH (VOLTS)
C          (R*8)  DE1     = D.C. FOR X-CPT OF EMAG
C          (R*8)  DE2     = D.C. FOR Y-CPT OF EMAG
C          (R*8)  DE3     = D.C. FOR Z-CPT OF EMAG
C          (R*8)  DO1     = D.C. FOR X-CPT OF SPECIFIC VIEWING LINE
C          (R*8)  DO2     = D.C. FOR Y-CPT OF SPECIFIC VIEWING LINE
C          (R*8)  DO3     = D.C. FOR Z-CPT OF SPECIFIC VIEWING LINE
C          (R*8)  POLO    = SPECIFIC SIGMA POLARISATION INTENSITY MULTIPLIER
C          (R*8)  POLP    = SPECIFIC  PI   POLARISATION INTENSITY MULTIPLIER
C          (R*8)  DENS    = SPECIFIC PLASMA ELECTRON DENSITY (CM-3)
C          (R*8)  TE      = SPECIFIC PLASMA ELECTRON TEMPERATURE (EV)
C          (R*8)  ZEFF    = SPECIFIC PLASMA EFFECTIVE Z
C
C          (L)    LPASS   = IF TRUE OUTPUT A LOG FILE
C
C
C
C ROUTINES:
C          ROUTINE    SOURCE    BRIEF DESCRIPTION
C          ------------------------------------------------------------
C          BORNP1     ADAS      Stage 1 Born cross-section calculation
C          BORNP2     ADAS      Stage 2
C          DIPOL      ADAS      H Dipole length radial matrix elements
C          GAMAF      ADAS      Stack vector of factorial function
C          STARK2     ADAS      Calc. Stark perturb. matrix elements
C          UNBUN2     ADAS      Extract indiv. set qu. nos. from integer
C          ZEEMN2     ADAS      Calc. Zeeman perturb. matrix elements
C          C5RLSP     ADAS      Calc. rel.+s.o. energy matrix elements 
C          HYDEMI     ADAS      Collisional mixing of H excited levels
C          ZHPEV      LAPACK    Compute eigenvectors of complex 
C                               Hermitian matrix
C
C
C AUTHOR:  H.P.SUMMERS, JET
C          14 SEPT 1989
C
C----------------------------------------------------------------------
C
C
C ADAS305 version - originally SPSTRK.
C
C VERSION  : 1.1
C DATE     : 24-02-2005
C MODIFIED : Martin O'Mullane
C             - First version. Restrict to a single track.
C
C VERSION  : 1.2
C DATE     : 24-01-2006
C MODIFIED : Hugh Summers
C             - introduced relativistic +spin-orbit fine structure
C             - placed beam velocity vector direction cosines in call
C               parameters and made general
C             - corrected AMSS to AMDEUT for beam atom energy levels
C
C VERSION  : 1.3
C DATE     : 28-09-2006
C MODIFIED : Martin O'Mullane
C             - Add missing blockdata for WF, XF, ABETA and F
C               (prefixed variable with bd_ to avoid name clashes).
C             - INDW3A initialised to zero for all 726 values.
C             - Some more details sent to pass file.
C
C VERSION  : 1.4
C DATE     : 28-09-2006
C MODIFIED : Martin O'Mullane
C             - Setup infrastructure for matching upper level to adf22
C               data but don't make correction yet.
C
C----------------------------------------------------------------------
      INTEGER             NCOMP,       NDCOMP,      NL,          NU
      REAL*8              AMDEUT,      AMSS,        BENER,       BMAG
      REAL*8              DB1,         DB2,         DB3,         DE1
      REAL*8              DE2,         DE3,         DENS,        DENSB
      REAL*8              DO1,         DO2,         DO3,         DV1
      REAL*8              DV2,         DV3,         EMAG
      REAL*8              EMCOMP(NDCOMP),           POLO,        POLP
      REAL*8              POPU,        TE,          WVCOMP(NDCOMP)
      REAL*8              ZEFF
© Copyright 1995-2024 The ADAS Project
Comments and questions to: adas-at-adas.ac.uk