trdatbuf_lib

This is the help file for TRDATBUF_LIB - a fortran library for accessing TRANSP's
Physics Data

Home Top


Introduction

The trdatbuf_lib is a collection of modules and routines which allows a callable interface 
to experimental data which is input to TRANSP, without recourse to "trcom", TRANSP internal
data structures. It was developed to provide other codes access to the same data as seen 
by TRANSP.

The trdatbuf_lib imports data from the Physics Data File "<runid>PH.CDF" produced by 
the TRANSP preprocessing program TRDAT. Normally, TRDAT runs automatically in the course of
a TRANSP batch job, processing the experimental data (Ufiles and/or MDS+ files) and 
produces the Physics Data File as an intermediate file which is read by TRANSP itself 
and archived. The archived Physics Data File <runid>PH.CDF is now retrievable for
access by other codes.

The physics data is loaded into a "trdatbuf" object (data structure).  This is done by
making a call to a routine to load the object, which takes as an argument a file path to
the Physics Data File.  Once this is done, the data becomes accessible via the trdatbuf_lib
library applications programming interface.

The types of data which can be accessed using trdatbuf_lib fall into several general 
catagories, each with their own methods of access:

	1D Data types - f(t)
	2D Data types - f(x,t)
	Neutral Beam Data (powers, voltages, energy fractions vs. time)
	RF Antenna Data (e.g. powers, frequencies vs. time)
	MHD Equilibrium Moments Data (ie fourier harmonics of plasma boundary or
               entire equilibrium) vs. time.

All data types, including time series data types, are identified by three character
"trigraphs", consistant with the identification used for Ufiles. A more detailed description
can be found in the TRANSP Help page at

   https://w3.pppl.gov/~pshare/help/transp.htm 

Home Top


Limitations

Generally, the trdatbuf_lib facility only gives access to time dependent data used by 
TRANSP.  Time invariant information, such as beam geometry, vacuum vessel shape, RF 
antenna description, etc., are entered into TRANSP by means of a namelist.  Namelist
information is not accessible through trdatbuf_lib.  However, there is a separate 
library, "splitn", which does enable access to TRANSP namelist elements without 
requiring access to TRANSP internal data structures.  The splitn library is included
in the TRANSP client software module, tr_client.

The contents and time range of any given trdatbuf file "<runid>PH.CDF" or 
corresponding MDS+ tree are exactly as selected by the original TRANSP user.  Only that 
user can vouch for the accuracy or appropriateness of the file contents; there is nothing 
in the software itself that can independently verify these attributes.

Home Top


Usage Overview

 An overview of the routines required to access various data is provided here.
 Please see the detailed descriptions of the individual routines for details
 on calling arguments and return data.

Home Top


Initialization

Use of the trdatbuf_lib requires the following statements:

  USE trdatbuf_module      ! provides access to all modules and routines in trdatbuf_lib
  ...
  type(trdatbuf) :: d      ! declare (instantiate) a trdatbuf object
  ...
  call trdatbuf_init(d)    ! initialize trdatbuf object (allocate buffers)
  ...
  call trdatbuf_read(...)  ! read trdatbuf object from physics data file

The trdatbuf object can be re-initialized (deallocate buffers and call trdatbuf_init)
using the routine trdatbuf_reInit if desired.

Home Top


Making Inquiries

The presence of data in the trdatbuf object can made using the following routines:

  tdb_defined1 -- Tests if a 3 character name is recognizable as an f(t) item.

  tdb_defined2 -- Tests if a 3 character name is recognizable as an f(x,t) item.

  tdb_present1 -- Test for presence of 1D data, f(t), in trdatbuf object
                  Returns index to 1D data in trdatbuf object if found.

  tdb_present2 -- Test for presence of 2D data, f(x,t), in trdatbuf object
                  Returns index to 2D data in trdatbuf object if found.

  tdb_logchk_special  -- Query the presence of "special" data items in trdatbuf object

  tdb_logchk_nbi      -- Query the presence of NBI-related data items in trdatbuf object

  tdb_zeff_simple  --  return TRUE if Zeff data available by a simple interpolation.

  tdb_imp_single   --  return TRUE if TRANSP run only has a single impurity species.
  
Home Top


Data Access


Home Top


Time ranges

The time range of the trdatbuf data can be obtained using:

  tdb_tlims
  
The number of points used in the timebases for 1D and 2D data can be gotten from:

  tdb_ntimes

Home Top


Species

  tdb_nplas -- the number of non-impurity main plasma thermal species
  tdb_plas -- Z & A values returned for each main plasma thermal species.

  tdb_nfast -- the number of plasma fast ion species
  tdb_plas -- Z & A values returned for each fast ion species
  
Home Top


Max_beam_energy

  tdb_ebmax -- get the maximum energy (eV) detected for any neutral beam.

Home Top


Accessing 1D Data Types

 1D data types are typically scalar data as a function of time. 
 The following sequence of calls are needed:
 
  tdb_defined1 - test if trigraph is recognized as a 1d data item
                 (this doesn't mean it is present in a given dataset).

  tdb_present1 - get index to 1D data
  tdb_lookup1  - get time interpolation indices and factors
		 For efficiency, this lookup should only be done once
		 per trdatbuf object read, and, one time zone lookup should
		 be amortized over several 1d time interpolation calls.
  tdb_fintrp1  - interpolation call

Home Top


Trigraphs for 1D Data Types

 The follow lists the 1D data types recognized by trdatbuf. Note, however, that for
 a "typical" TRANSP run only a few of these input data channels are active.

  Trigraph    Description            Units
  SAW         sawtooth times         seconds
  CUR         plasma current         amps
  IIC         Total ICRF Current     amps
  PIC         Total ICRF power       watts
  PEB         Tot. IB pow. (Elec)    watts
  PIB         Tot. IB pow. (Ions)    watts
  ILH         Total LH Current       amps
  PLH         Total LH power         watts
  PEC         Total ECRH power       watts
  IEC         Total ECRH Current     amps
  IBM         Total Beam Current     amps
  PBI         Beam Power (Ions)      watts
  PBE         Beam Power (Elec)      watts
  TQT         anom. total torque     Nt-m
  VSF         surface voltage        volts
  RBZ         [ext. B field] * R     Tesla*cm
  POS         major radius           cm
  RMN         minor radius           cm
  LAD         line avg density       n/cm**3
  LID         line int density       n/cm**2
  ZIM         Zimp
  ZEF         Zeff
  ZFA         Zeff at edge
  VSB         Vis. Bremsstrahlung    VB units
  TET         Te renormalizer        eV
  FMX         ECE Freq. of Te peak   GHz
  TIT         Ti renormalizer        eV
  XKF         chi(i) multiplier
  GIE         Ti/Te factor
  FIE         Switch Ti->GIEFAC*Te
  PFL         PCX Ti lower fit lim   eV
  PFH         PCX Ti upper fit lim   eV
  TXI         PCX Ti intercept       cm**-5
  NTX         Neutron flux           n/sec
  L2B         li/2 + beta(pol)
  BDI         beta diamagnetic
  DFL         diamagnetic flux       Webers
  EDI         paramagnetic energy    Joules
  EHP         E(Bpol)/2+E(plasma)    Joules
  ELI         e(Li) non-circular     Joules
  RTP         magnetics Rt est.      cm
  ALP         magnetics alpha est.
  HAL         H/D alpha light        ph/sec
  TPI         particle confinement   seconds
  RCY         recycling source       #/sec
  GAS         gas flow source        #/sec
  SBT         particle source        #/sec
  VPH         axial rotation         cm/sec
  RM0         0th R moment           cm
  FMN         minority fraction
  ZPL         plasma elevation       cm
  RCH         recycling H source     #/sec
  GFH         H gas flow source      #/sec
  RCD         recycling D source     #/sec
  GFD         D gas flow source      #/sec
  RCT         recycling T source     #/sec
  GFT         T gas flow source      #/sec
  RC3         recycling He3 source   #/sec
  GF3         He3 gas flow source    #/sec
  RC4         recycling He4 source   #/sec
  GF4         He4 gas flow source    #/sec
  RC6         recycling Li source    #/sec
  GF6         Li gas flow source     #/sec
  SFA         fusion alpha source    #/sec
  SF3         fusion He3 source      #/sec
  SFL         fusion LI source       #/sec
  SFT         fusion triton source   #/sec
  SFp         fusion proton source   #/sec
  PLF         Poloidal flux          Webers
  TRF         Toroidal flux          Webers

Home Top


Accessing 2D Data Types

 2D Data Types are typically profile data as a function of time.
 The following sequence of statements and calls are needed:
 
  type(profget) :: t  !  object to aid profile interpolation
   ...
  tdb_symini 		-- Initialization call to allocate workspace for profile interpolation
  tdb_profget_init	-- Initialize a profget object 
  tdb_profin		-- Map specified trdatbuf profile data to user profile grid
  tdb_profget_free	-- de-initialize (deallocate) a profget object
 
 The profget objects are used to pass and retrieve data from the profile
 interpolation routines. 
 
Home Top


Trigraphs for 2D Data Types

 The follow lists the 2D data (aka Profile data) types recognized by trdatbuf

  Trigraph    Description            Units
  NER         electron density       n/cm**3
  TER         electron temperature   eV
  ECF         electron temperature   eV
  ZF2         Zeff profile
  VB2         VB emission profile    VB counts
  BOL         Power radiated         W/cm**3
  VP2         plasma rotation        rad/sec
  OMG         plasma rotation        rad/sec
  TI2         ion temperature        eV
  KI2         chi(i) data            cm**2/sec
  KF2         chi(i) multiplier
  KE2         chi(e) data            cm**2/sec
  KPH         chi(phi) data          cm**2/sec
  QPR         q profile
  BPB         Bp/Bz field ratio
  BPA         arctan(Bp/Bz) data     radians
  RES         Resistivity            ohm*cm
  NMR         minority density       n/cm**3
  NIM         impurity density       n/cm**3
  DE2         elec ptcl diffusivty   cm**2/sec
  D2F         fast ion diffusivty    cm**2/sec
  JIC         ICRF current profile   A/cm**2
  QIC         ICRF power profile     W/cm**3
  QEC         ECRH power profile     W/cm**3
  JEC         ECRH current profile   A/cm**2
  JBM         Beam current profile   A/cm**2
  QBI         Beam pwr prof (ions)   W/cm**3
  QBE         Beam pwr prof (Elec)   W/cm**3
  LHJ         LH driven current      A/cm**2
  LHE         LH electron heating    W/cm**3
  NIH         H+ ion density         n/cm**3
  NID         D+ ion density         n/cm**3
  NIT         T+ ion density         n/cm**3
  NI3         He3++ ion density      n/cm**3
  NI4         He4++ ion density      n/cm**3
  NI6         Li+++ ion density      n/cm**3
  VCH         H+ v(convective)       cm/sec
  VCD         D+ v(convective)       cm/sec
  VCT         T+ v(convective)       cm/sec
  VC3         He3++ v(convective)    cm/sec
  VC4         He4++ v(convective)    cm/sec
  VC6         Li+++ v(convective)    cm/sec
  LFH         H+ Ln(flow)            cm
  LFD         D+ Ln(flow)            cm
  LFT         T+ Ln(flow)            cm
  LF3         He3++ Ln(flow)         cm
  LF4         He4++ Ln(flow)         cm
  LF6         Li+++ Ln(flow)         cm
  DFH         H+ Diffusivity         cm**2/sec
  DFD         D+ Diffusivity         cm**2/sec
  DFT         T+ Diffusivity         cm**2/sec
  DF3         He3++ Diffusivity      cm**2/sec
  DF4         He4++ Diffusivity      cm**2/sec
  DF6         Li+++ Diffusivity      cm**2/sec
  IBI         IBW ion heating        watts/cm3
  IBE         IBW electron heating   watts/cm3
  PRS         MHD Pressure profile   Pascals
  GRB         MHD g (R*Bt) profile   Tesla*cm
  MSE         MSE data               Degrees
  VTR         specie tor.velocity    cm/sec
  VPR         specie pol.velocity    cm/sec
  VPO         Er potential           volts
 

Home Top


Accessing Neutral Beam Data

 Neutral Beam Power, Voltage, or Energy fraction vs time is available thru the following routines
 
 tdb_logchk_special	-- Query the presence of NBI-related data items in trdatbuf object
 
 tdb_logchk_nbi	-- Query the presence of NB Power, Voltage, Full Energy or Half Energy
 
 tdb_nchan_find --  Return the number of beam lines
 
 tdb_onoff_atime -- Return time range for beams - first (minimum) on time and last (maximum) off time 
                    Beams may turn on and off between these times as well.
		    
 tdb_onoff_times -- Return vectors of all on/off times for beams
 
 tdb_pwrget_init -- initialize a data structure of type pwrget for use in accessing NB data
 
 tdb_pwrdata_avg -- Return NB Power ('PWR'), Voltage ('VLT'), Full Energy ('FUL') or Half Energy ('HLF')
                    data averaged over requested time range
		    
  Typical usage involves first verifying the presence of NBI data with tdb_logchk_special,
  then determining the number of beam lines present with tdb_nchan_find.
  The on/off times of the beams is useful, but not required.
  The presence of NB data does not assure the presence of all components.
  Checks should be made with tdb_logchk_nbi.
  The initialization of a pwrget object is required before attempting to call
  tdb_pwrdata_avg.

Home Top


Accessing Antenna Data

 Antenna Data (ECH/ECCD, ICRF, Lower Hybrid)

 tdb_logchk_special	-- Query the presence of specific Antenna data items in trdatbuf object
 
 tdb_nchan_find --  Return the number of antennas
 
 tdb_onoff_atime -- Return time range for antennas - first (minimum) on time and last (maximum) off time
                    Antenna powers may turn on and off between these times as well.
		    
 tdb_onoff_times -- Return vectors of all on/off times for antennas
 
 tdb_pwrget_init -- initialize a data structure of type pwrget for use in accessing antenna data
 
 tdb_pwrdata_avg -- Return average power data
                    data averaged over requested time range
		    
  Typical usage involves first verifying the presence of antenna data with tdb_logchk_special,
  then determining the number of antennas present with tdb_nchan_find.
  The on/off times of the antennas is useful, but not required.
  The initialization of a pwrget object is required before attempting to call
  tdb_pwrdata_avg.

Home Top


Accessing Moments Data

 Moments Data can almost always be found for the plasma boundary:
 
 tdb_find_nmoms	-- Get number of fourier moments defining plasma boundary
 tdb_bdy_timefac	-- Get boundary time interpolation indices and factors
 tdb_bdy_getmoms	-- Get boundary moments
 
 In some cases equilibrium data will exist. Moments for all internal flux surfaces
 can obtained and mapped to user flux coordinates:
 
 tdb_getmmx	-- Get equilibrium geometry moments (ie internal flux surfaces)
 
 As with all profile data, tdb_present2 should be used to check for presence of data
 before calling tdb_getmmx.

Home Top


Miscellaneous

 tdb_rmp_bdy	-- Get inner and outer midplane boundary intercept radii at a 
                   selected time, based on experimental estimate of plasma
                   position and shape.
 

Home Top


Data Archival

A trdatbuf object can be archived and retrieved from MDS+ using the following routines:

  use trdatbuf_module
  use trdatbuf_intmod

  wr_trdatbuf  -- write trdatbuf object into MDS+
  rd_trdatbuf  -- read trdatbuf object from MDS+

MDS+ does not directly support the storage of derived data types. This is circumvented
by breaking the trdatbuf object in data chunks of similar intrinsic type arrays which
can be handled by MDS+. There are still few enough components to avoid the overhead of
numerous network calls.

The wr_trdatbuf routine creates new nodes in a MDS+ tree of a specified shot to hold the
trdatbuf object data. A top level node call TRBUFDATA is created to contain 5 child nodes.
The real*8 data of a trdatbuf object exists in a 1D array component and is stored as is
in a child node called DATBUF. The integer data of a trdatbuf object exists as a large
number of scalar and 1D vector components. These are first concatenated into a single
large 1D array and stored in a child node called INTBUF. To facilitate reconstruction
of a trdatbuf object, three additional nodes are required. The names of the integer
components of the trdatbuf module are stored in a character node called IVARNAME.
The sizes (dimensions) of the integer components of the trdatbuf module are stored
in an integer array node call IVARSIZE. Finally, the sizes of the nodes are stored
in a small integer array node called PARAMS.

The rd_trdatbuf routine actually reads in data from the 5 child nodes and reconstructs
the trdatbuf object. The reconstruction assumes that new components may be added over
time to a trdatbuf object, but at present does not allow for the deletion of components.



Home Top


Routines Summary

These routines are listed in a standard calling order:
------------------------------------------------------

trdatbuf_init	-- Initialize new trdatbuf object (allocate buffers)

trdatbuf_reInit	-- Re-initialize trdatbuf object (deallocate buffers and call trdatbuf_init)

trdatbuf_read	-- Read Physics Data File into trdatbuf object

tdb_defined1	-- Test if given name is a valid 1d data item name.

tdb_defined2	-- Test if given name is a valid 2d data item name.

tdb_present1	-- Test for presence of 1D data, f(t), in trdatbuf object

tdb_present2	-- Test for presence of 2D data, f(x,t), in trdatbuf object

tdb_tlims	-- Get time range (start, end) of trdatbuf data

tdb_tlim_ok	-- Get time beyond which data may be suspect

tdb_ntimes	-- Get number of points in f(t) and f(x,t) timebases

tdb_ebmax       -- Get the maximum energy (eV) detected for any neutral beam.
			
tdb_lookup1	-- Get time interpolation indices and factors

tdb_fintrpl1	-- Time interpolate 1D data

tdb_rmp_bdy	-- Get inner and outer midplane boundary intercept radii

tdb_symini	-- Initialization call to support profile interpolation

tdb_profget_init	-- Initialize a profget object 

tdb_profin	-- Map specified trdatbuf profile data to user profile grid

tdb_profget_free	-- de-initialize (deallocate) a profget object

tdb_logchk_special	-- Query the presence of "special" data items in trdatbuf object

tdb_logchk_nbi	-- Query the presence of NBI-related data items in trdatbuf object

tdb_nchan_find --  Return the number of beams or antennas.
 
tdb_onoff_atime -- Return time range for beams or RF antennae - first (minimum) on time
                   and last (maximum) off time.  Beams or RF antennae may turn on and off
                   between these times as well.
		    
tdb_onoff_times -- Return vectors of all on/off times for beams or RF antennae
 
tdb_pwrget_init -- initialize a data structure of type pwrget for use in accessing NB or
                   RF data
 
tdb_pwrdata_avg -- Return beam or antenna data as specified in pwrget object.
		    
tdb_find_nmoms	-- Get number of fourier moments defining plasma boundary

tdb_bdy_timefac	-- Get boundary time interpolation indices and factors

tdb_bdy_getmom	-- Get boundary moments one by one

tdb_bdy_getmoms  -- Get boundary all moments in single call

tdb_getmmx	-- Get equilibrium geometry moments (ie internal flux surfaces)

tdb_npel        -- Get number of pellets

tdb_pelda       -- Get details on a specific pellet

tdb_freebdy_dims -- Return the dimensions of the data associated with a free boundary solver

tdb_freebdy_pfccurs -- Return the poloidal fiel coil currents

tdb_freebdy_pre_pfc_pcur -- Return the poloidal fiel coil currents and plasma current before TINIT

wr_trdatbuf      -- Writes trdatbuf object into MDSplus

rd_trdatbuf      -- Reads  trdatbuf object from MDSplus

Home Top


Routine Interface details


Home Top


trdatbuf_init

    subroutine trdatbuf_init(s)
      type (trdatbuf) :: s ! trdatbuf object
      
   Initialize new trdatbuf object (allocate buffers). This must be called prior to calling trdatbuf_read to read
   a Physics Data File.

Home Top


trdatbuf_reInit

    subroutine trdatbuf_reInit(s)
      type (trdatbuf) :: s ! trdatbuf object
      
   Re-initialize a trdatbuf object (deallocate buffers and call trdatbuf_init). This should be called prior to 
   calling trdatbuf_read to read a new Physics Data File.

Home Top


trdatbuf_read

    subroutine trdatbuf_read(klun,z,kerr)
      integer, intent(in) :: klun    ! fortran lun (logical unit number)
      type (trdatbuf) :: z           ! trdatbuf object
      integer, intent(out) :: kerr   ! completion code, 0=ok

   Reads a Physics Data File into a trdatbuf object. 
   
Home Top


tdb_defined1

    logical function tdb_defined1(d,ztrigraph)
      type (trdatbuf) :: d                    ! trdatbuf object
      character*(*), intent(in) :: ztrigraph  ! trigraph (typically three character string) identifying times series data

    Function returns .TRUE. if name is recognized as a valid 1d f(t) item name.  This does NOT
    indicate the presence of the item in a given dataset; see tdb_present1(...).
   
Home Top


tdb_defined2

    logical function tdb_defined2(d,ztrigraph)
      type (trdatbuf) :: d                    ! trdatbuf object
      character*(*), intent(in) :: ztrigraph  ! trigraph (typically three character string) identifying profile data

    Function returns .TRUE. if name is recognized as a valid 2d f(x,t) item name.  This does NOT
    indicate the presence of the item in a given dataset; see tdb_present2(...).
     
Home Top


tdb_present1

    logical function tdb_present1(d,ztrigraph,iaddr)
      type (trdatbuf) :: d                    ! trdatbuf object
      character*(*), intent(in) :: ztrigraph  ! trigraph (typically three character string) identifying times series data
      integer, intent(out), optional :: iaddr           ! address of data

    Function tests for the presence of 1D data, f(t), in trdatbuf object. 
    It returns .TRUE. if time series data for trigraph is found, returns .FALSE. if not. 
    Also returns starting address of trigraph data which must be passed to 1D time interpolation
    function tdb_fintrpl1.
        
Home Top


tdb_present2

    logical function tdb_present2(d,ztrigraph,iaddr)
      type (trdatbuf) :: d                    ! trdatbuf object
      character*(*), intent(in) :: ztrigraph  ! trigraph (typically three character string) identifying profile data
      integer, intent(out), optional :: iaddr           ! address of data
 
    Function tests for the presence of 2D data, f(x,t), in trdatbuf object. 
    It returns .TRUE. if time series data for trigraph is found, returns .FALSE. if not.
    Also returns starting address of trigraph data. Unlike 1D data, this address is not 
    used for time interpolation and can be ignored.
 
Home Top


tdb_tlims

    subroutine tdb_tlims(d,zd_tinit,zd_ftime)
      type (trdatbuf) :: d             ! trdatbuf object
      real*8, intent(out) :: zd_tinit  ! start time
      real*8, intent(out) :: zd_ftime  ! stop time

    Subroutine returns time range (start, end) of trdatbuf data. 
    
Home Top


tdb_tlim_ok

    subroutine tdb_tlim_ok(d,zd_ftime_ok)
      !
      !  return time beyond which a code failure should be ignored
      !  (allows experimentalists to set off time after disruption,
      !  without leading to a crash requiring manual intervention 
      !  for run to completion -- FTIME_OK in the TRANSP namelist).
      !
      type (trdatbuf) :: d
      real*8, intent(out) :: zd_ftime_ok  ! stop time


Home Top


tdb_ntimes

    subroutine tdb_ntimes(d,intime1,intime2)
      type (trdatbuf) :: d            ! trdatbuf object
      integer, intent(out) :: intime1 ! number of time points for 1D data 
      integer, intent(out) :: intime2 ! number of time points for 2D data 
      
    Subroutine returns number of points in f(t) and f(x,t) timebases.
    			
Home Top


tdb_ebmax

    subroutine tdb_ebmax(d,zebmax)
      !
      ! return the max beam energy seen in the input data
      !
      type (trdatbuf) :: d            ! trdatbuf object
      real*8, intent(out) :: zebmax   ! max detected beam energy (eV)

Home Top


tdb_lookup1

    subroutine tdb_lookup1(d,ztime,it1,it2,zf1,zf2)
      type (trdatbuf) :: d             ! trdatbuf object
      real*8, intent(in) :: ztime      ! user time for interpolation
      integer, intent(out) :: it1,it2  ! time offsets btw which ZTIME lies
      real*8, intent(out) :: zf1,zf2   ! linear interpolation factors
      
    Subroutine returns time interpolation indices and factors for use in subsequent
    function evaluations by tdb_fintrp1. 

Home Top


tdb_fintrpl1

    real*8 function tdb_fintrp1(d,iloc,it1,it2,zf1,zf2)
      type (trdatbuf) :: d            ! trdatbuf object
      integer, intent(in) :: iloc     ! data location
      integer, intent(in) :: it1,it2  ! time offsets btw which ZTIME lies
      real*8, intent(in) :: zf1,zf2   ! linear interpolation factors
      
    Function performs time interpolation of 1D data. It requires a prior call
    to tdb_lookup1 to calculate the time interpolation indices (it1,it2) and factors (zf1,zf2)

Home Top


tdb_rmp_bdy

    subroutine tdb_rmp_bdy(d,ztime,zr1,zr2)
      type(trdatbuf) :: d          ! data buffer object
      real*8, intent(in) :: ztime  ! time (seconds)
      real*8, intent(out) :: zr1   ! inner intercept major radius (cm)
      real*8, intent(out) :: zr2   ! outer intercept major radius (cm)
      
    Subroutine returns the inner and outer midplane boundary intercept radii
    of the plasma boundary contained in the trdatbuf object at specified time.
    
    This information is needed by subroutine tdb_profin for proper mapping
    of profile data (aka 2D data) in trdatbuf to user grid.
    
Home Top


tdb_symini

    subroutine tdb_symini(d,nzones)
      type (trdatbuf) :: d            ! trdatbuf object
      integer, intent(in) :: nzones   ! no. of radial zones in caller's grid

    Subroutine sets up workspace for (internal) presymmetrization & mapping of profiles.
    The size of workspace depends on target application's number of zones
    and the number of zones in the input data.

Home Top


tdb_profget_init

    subroutine tdb_profget_init(t,izones,idebug)
      type(profget) :: t             ! profget object containing input/output data
      integer, intent(in) :: izones  ! number of zones in user grid
      logical, intent(in) :: idebug  ! set debug flag in t%idebug for additional output

    Subroutine initializes a profget object needed for accessing profile data (aka 2D data)
    Must be called prior to calling tdb_profin for profile interpolation.
    
Home Top


tdb_profin

    subroutine tdb_profin(d, t, ierr)
      type (trdatbuf) :: d          ! trdatbuf object
      type (profget) :: t           ! profget object containing input/output data
      integer, intent(out) :: ierr  ! completion code (0=OK)
      
      Subroutine maps specified trdatbuf profile data to user profile grid.
      
      It fetchs profile data from trdatbuf buffer (d) according to
      specifications in target structure (t):
      
      The following components of t must be set on input:
      
      t%item                   identifier for electron density...
      t%time                   time
      t%xibdys(1:nzones+1)     toroidal flux profile
      t%rmajmp                 major radius of profile 
      t%bmidp                  magnetic field on midplane
      t%plflxg(1:nzones+1)     poloidal flux profile 
      t%ibdy                   interpolation flag 
                               .FALSE. = to zone centers; bdy values set to 
                               half the sum of values of the adjacent centers
		               .TRUE. = to zone bdy; centers set to 
			       half the sum of values of the adjacent bdys
      
      The following components of t are set on output:
      
      t%data_zb(1:nzones+1) 	data at zone boundaries
      t%data_zc(1:nzones+1)     data at zone center
      
Home Top


tdb_profget_free

    subroutine tdb_profget_free(t)
      type(profget) :: t    ! profget object
    
    Subroutine de-initialize (deallocate) a profget object, freeing up dynamically allocated memory.
    
Home Top


tdb_logchk_special

  logical function tdb_logchk_special(d,zitem,iwarn)
    type (trdatbuf) :: d
    character*(*), intent(in) :: zitem   ! item queried
    integer, intent(out) :: iwarn        ! 0: OK; 1: item not recognized
  
  Function queries the presence of "special" data items in trdatbuf object
  
    ! dmc Apr 2005
    ! logical query -- presence (T) or absence (F) of "special" data items
    ! in trdat buffer.

    ! the items covered are those not handled by the general 1D and 2D routines:
    !   "RPL" -- TF ripple vs. (R,Z)
    !   "NB2" -- beam power/voltage/etc data vs. time
    !   "RFP" -- ICRF antenna power vs. time
    !   "RFF" -- ICRF frequencies vs. time
    !   "LHP" -- LH antenna powers vs. time
    !   "ECP" -- ECH antenna powers vs. time
    !   "MMX" -- complete MHD equilibrium (inside plasma bdy) vs. time
    !   "SAW" -- sawtooth event times
    !   "PEL" -- pellet event times
    !
    ! All the above "trigraphs" are
    ! associated with "special_handling" i.e. hand coded data channels.  Many,
    ! but not necessarily all, special handling channels are supported in this
    ! routine.

Home Top


tdb_logchk_nbi

  logical function tdb_logchk_nbi(d,zsubset,iwarn)
    type (trdatbuf) :: d                 ! trdatbuf object
    character*(*), intent(in) :: zsubset ! subset item queried
    integer, intent(out) :: iwarn        ! 0: OK; 1: item not recognized

  Function queries the presence of NBI-related data items in trdatbuf object.
  
    ! dmc Apr 2005
    ! logical query -- presence (T) or absence (F) of NBI-related data items
    ! in trdatbuf.
    !
    ! if NB2 data is not in trdatbuf at all, always return F = FALSE.
    !
    ! known subset names:
    !   "PWR" -- beam power
    !   "VLT" -- beam voltage (full energy injected ptcls)
    !   "FUL" -- full energy fraction (#/sec)/(total #/sec)
    !   "HLF" -- half energy fraction (#/sec)/(total #/sec)
    !
    ! this code is matched to code in trdatusub which acquires NBI-related
    ! time dependent data...
    
Home Top


tdb_nchan_find

  integer function tdb_nchan_find(d,z2char)
  type (trdatbuf) :: d                 ! data buffer object
  character*(*), intent(in) :: z2char  ! 2-character code...

   Function returns the number of beams or attennas.
   
   A copy of z2char is converted to uppercase before testing
   if z2char is uppercase, then,
 
   z2char.eq.'NB' means -- requested information is # of neutral beams

   z2char.eq.'EC' means -- requested information is # of ECH antennas
                           electron cyclotron heating / current drive

   z2char.eq.'LH' means -- requested information is # of LH antennas
                           lower hybrid heating / current drive

   z2char.eq.'RF' means -- requested information is # of ICRF antennas
                           ICRF heating / current drive

   if z2char is recognized, the number of beams or antennas is returned;
   it could be zero.

   if z2char is not recognized, the number -1 is returned 

 
Home Top


tdb_onoff_atime

  subroutine tdb_onoff_atime(d,z2char,zthresh,zdtfix,ton,toff,ierr)
    type (trdatbuf) :: d
    character*(*), intent(in) :: z2char  ! channel type NB/LH/EC/RF
    real*8, intent(in) :: zthresh        ! on/off threshhold (see comments)
    real*8, intent(in) :: zdtfix         ! time to search from threshhold
    real*8, intent(out) :: ton,toff      ! on/off times (seconds)
    integer, intent(out) :: ierr         ! completion code; 0=OK
    
    Return time range for beams - first (minimum) on time and last (maximum) off time 
    Beams may turn on and off between these times as well.
		    
    ! for power-channel data (NB,EC,LH,RF) define the on and off times:
    !   ton = min(on times for any channel) (*output*)
    !   toff = max(off times for any channel) (*output*)
    !
    !   z2char => chooses heating channel:
    !     "nb" or "NB" -- neutral beams
    !     "ec" -- ECH/ECCD
    !     "lh" -- Lower Hybrid
    !     "rf" -- ICRF   
    !   all tests of z2char value are case insensitive
    ! 
    !   zthresh = threshhold:
    !     if positive -- a power, in watts, must be < 20% of the maximum
    !                    power ever occurring on any channel
    !     if negative -- (-1) * a fraction (no units) -- btw -0.0001 and -0.20 --
    !                    power threshold becomes -zthresh * (maximum power
    !                    ever occurring on any channel).
    !
    !   zdtfix -- time to search from first/last powers satisfying thresh-
    !             hold, for an actual 0 or negative power...
    !
    !   ierr is set only if there is no data or if z2char is unrecognized;
    !   if the zthresh limit has to be adjusted to conform to rules, a 
    !   warning message is written but ierr is not set.
    !

  
Home Top


tdb_onoff_times

  subroutine tdb_onoff_times(d,z2char,zthresh,zdtfix,tonarr,toffarr,ierr)
    type (trdatbuf) :: d
    character*(*), intent(in) :: z2char  ! channel type NB/LH/EC/RF
    real*8, intent(in) :: zthresh        ! on/off threshhold (see comments)
    real*8, intent(in) :: zdtfix         ! time to search from threshhold
    real*8, intent(out), dimension(:) :: tonarr,toffarr  ! on/off times (seconds)
    integer, intent(out) :: ierr         ! completion code; 0=OK
  
  Subroutine returns vectors of all on/off times for beams or RF antenna sets
  
    ! for power-channel data (NB,EC,LH,RF) define the on and off times:
    !   tonarr(i) = on time for channel #i (i.e. beam or antenna) (*output*)
    !   toffarr(i) = off time for channel #i (*output*)
    !
    !   z2char => chooses heating channel:
    !     "nb" or "NB" -- neutral beams
    !     "ec" -- ECH/ECCD
    !     "lh" -- Lower Hybrid
    !     "rf" -- ICRF   
    !   all tests of z2char value are case insensitive
    ! 
    !   zthresh = threshhold:
    !     if positive -- a power, in watts, must be < 20% of the maximum
    !                    power ever occurring on any channel
    !     if negative -- (-1) * a fraction (no units) -- btw -0.0001 and -0.20 --
    !                    power threshold becomes -zthresh * (maximum power
    !                    ever occurring on any channel).
    !
    !   zdtfix -- time to search from first/last powers satisfying thresh-
    !             hold, for an actual 0 or negative power...
    !
    !   ierr is set only if there is no data or if z2char is unrecognized;
    !   if the zthresh limit has to be adjusted to conform to rules, a 
    !   warning message is written but ierr is not set.
    !


Home Top


tdb_pwrget_init

  subroutine tdb_pwrget_init(znbi)
    type(pwrget) :: znbi ! pwrget object
     
     Subroutine initializes a data structure of type pwrget for use in accessing NB and antenna data.
     Must be called prior to calling tdb_pwrdata_avg with pwrget object.
     
Home Top


tdb_pwrdata_avg

  subroutine tdb_pwrdata_avg(d,zpwr,ierr)
    type (trdatbuf) :: d           ! trdat data object
    type (pwrget) :: zpwr          ! specification of desired parameters
    integer, intent(out) :: ierr   ! completion code (0=OK)
  
    Return beam or antenna data as specified in pwrget object.
  

     ! The following should be set on input
     !
     zpwr%item    (character*4)        ! Data item to fetch/average
     zpwr%ztime1  (real*8)             ! start of time averaging window
     zpwr%ztime2  (real*8)             ! end of time averaging window
     zpwrpweight  (logical)            ! .TRUE. for power weighted average
     zpwr%nbeam   (integer)            ! no. of beams -- expected to match trdatbuf nbdata
     zpwr%tbon(1:nbeam)   (real*8)     ! on times for beams 
     zpwr%tboff(1:nbeam)  (real*8)     ! off times for beams 
     
     ! Outputs
     !
     zpwr%zparam(1:nbeam) (real*8)     ! return vector...
		    


Home Top


tdb_find_nmoms

  subroutine tdb_find_nmoms(d,imoms,icirc)
    type (trdatbuf) :: d                  ! trdatbuf object
    integer, intent(out) :: imoms,icirc   ! number of moments, flag for circular flux surfaces
    
   Subroutine returns the number of fourier moments defining plasma boundary.
   Also sets flag if circular flux surfaces found (not common) 
   
    ! return imoms = # of moments (0:imoms) in Fourier expansion
    ! return icirc = 1 if circular flux surfaces (minor & major radius only)
    !                are in use (this is very rare).


Home Top


tdb_bdy_timefac

  subroutine tdb_bdy_timefac(d,ztime,it,zf)
    type (trdatbuf) :: d           ! trdatbuf object
    real*8, intent(in) :: ztime    ! time (seconds)
    integer, intent(out) :: it     ! time bin
    real*8, intent(out) :: zf      ! interpolation factor w/in bin

    Subroutine returns time interpolation indices and factor at time specified.
    Used by boundary Fourier moments function tdb_bdy_getmom (for single moment) 
    and subroutine tdb_bdy_getmoms (for all moments) 

Home Top


tdb_bdy_getmom

  real*8 function tdb_bdy_getmom(d,it,zf,imom,itype)
    type (trdatbuf) :: d          ! trdatbuf object
    integer, intent(in) :: it     ! time bin index
    real*8, intent(in) :: zf      ! time interpolation factor
    integer, intent(in) :: imom   ! moment index
    integer, intent(in) :: itype  ! moment type
    
    Function returns boundary moments one by one. Subroutine tdb_bdy_timefac must be
    called first to evaluate time interpolation index it, and factor zf.
    Subroutine tdb_find_nmoms must also be called to determine number of moments
    present in trdatbuf object. 
    
    Moment index (imom) passed must be less than or equal to 
    the number of moments present.
    
    Moment type (itype) identifies the type of harmonic desired.
    
    for Rcos term, itype = 1 (or TDB_MOMS_RCOS)
    for Rsin term, itype = 2 (or TDB_MOMS_RSIN)
    for Zcos term, itype = 3 (or TDB_MOMS_ZCOS)
    for Zsin term, itype = 4 (or TDB_MOMS_ZSIN)
    
    where TDB_MOMS_RCOS, TDB_MOMS_RSIN, TDB_MOMS_ZCOS and TDB_MOMS_ZSIN are
    predefined integer parameters available when USEing the trdatbuf_module.
    
   
Home Top


tdb_bdy_getmoms

    subroutine tdb_bdy_getmoms(d,it,zf,rmcb,ymcb,nmom)
      type (trdatbuf) :: d                      ! trdatbuf object
      integer, intent(in) :: it                 ! time bin index
      real*8, intent(in) :: zf                  ! time interpolation factor 
      integer, intent(in) :: nmom               ! number of moments
      real*8, dimension(0:nmom,2) :: rmcb,ymcb  ! boundary harmonics 0:nmom, cos:sin
      
    Subroutine returns all boundary moments in single call (by making repeated calls
    to tdb_bdy_getmom). Subroutine tdb_bdy_timefac must be
    called first to evaluate time interpolation index it, and factor zf.
    Subroutine tdb_find_nmoms must also be called to determine number of moments, nmom,
    present in trdatbuf object. 
    
    Returned arrays rmcb and ymcb contain all radial and vertical fourier moments.
      xxx(0:nmom,1) => cosine moments
      xxx(0:nmom,2) => sine moments
      
    Note routine returns all moments whether boundary is symmetric or not. 
    
    
Home Top


tdb_getmmx

  subroutine tdb_getmmx(d,zt,xib,zrmc2,zymc2,mj,mimom,lcentr,nzp1,zdrshaf)
    type (trdatbuf) :: d         ! trdatbuf object
    REAL*8,intent(in) :: zt      ! time at which to fetch moments

    real*8,intent(in) :: xib(mj) ! flux surfaces (xib(j)=sqrt(Phi/Philim) at
                                 ! surface "j").

    REAL*8,intent(out) :: zrmc2(mj,0:mimom,2),zymc2(mj,0:mimom,2)
                                 ! asymmetric Fourier moments set at xi bdys


    integer, intent(in) :: mj    ! flux surface array dimension for zrmc2,zymc2
    integer, intent(in) :: mimom ! moments array dimension for zrmc2,zymc2

    integer :: lcentr            ! index to magnetic axis
    integer :: nzp1              ! no. of surfaces including mag. axis

    REAL*8,intent(out) :: zdrshaf(mj)
                                 ! "Shafranov" shift of interior surfaces
                                 ! relative to the boundary surface

    Subroutine returns all equilibrium geometry moments (ie internal flux surfaces).
    Logical function tdb_logchk_special(d,'MMX,iwarn) should be used to test
    for the presence of data before calling tdb_getmmx.
    
    ! using the MMX data, fetch the current equilibrium geometry.
    ! this routine MUST NOT be called unless the MMX data exists.

Home Top


tdb_num_sawtimes(d,insaw)

    subroutine tdb_num_sawtimes(d,insaw)
       implicit NONE
       !  return number of sawtooth events
       type (trdatbuf) :: d
       integer, intent(out) :: insaw ! number of sawteeth this run
    end subroutine tdb_num_sawtimes

Home Top


tdb_sawtimes

    subroutine tdb_sawtimes(d,zsaw_times,insaw)
       implicit NONE
       !  return the sawtooth event times
       type (trdatbuf) :: d
       integer, intent(in) :: insaw ! number of sawteeth this run (array size)
       real*8, intent(out) :: zsaw_times(insaw)
    end subroutine tdb_num_sawtimes

Home Top


tdb_npel

    subroutine tdb_npel(d,inpel)
       implicit NONE
       !  return number of pellet events
       type (trdatbuf) :: d
       integer, intent(out) :: inpel ! number of pellets this run
    end subroutine tdb_npel

Home Top


tdb_pelda

    subroutine tdb_pelda(d,ipel,p,ierr)
       implicit NONE
       !  return data associated with a particular pellet
       type (trdatbuf) :: d
       integer, intent(in) :: ipel   ! index of desired pellet data (ipel'th pellet)
       type (pelget) :: p            ! pellet data returned here
       integer, intent(out) :: ierr  ! return .ne.0 if ipel input out of range
    end subroutine tdb_pelda

Home Top


tdb_freebdy_dims

    subroutine tdb_freebdy_dims(d, npfc)
      implicit NONE

      type(trdatbuf)       :: d       ! trdatbuf
      integer, intent(out) :: npfc    ! number of poloidal field coils or 0 if none

    end subroutine tdb_freebdy_dims

Home Top


tdb_freebdy_pfccurs

    subroutine tdb_freebdy_pfccurs(d, ztime, n, cur, ier)
      implicit NONE

      type(trdatbuf)       :: d       ! trdatbuf
      real*8,  intent(in)  :: ztime   ! time (seconds)
      integer, intent(in)  :: n       ! number of currents expected
      real*8,  intent(out) :: cur(n)  ! poloidal field coil currents returned
      integer, intent(out) :: ier     ! nonzero on error

    end subroutine tdb_freebdy_pfccurs

Home Top


tdb_freebdy_pre_pfc_pcur

    subroutine tdb_freebdy_pre_pfc_pcur(d, ztime, n, cur, pcur, ier)
      implicit NONE

      type(trdatbuf)       :: d       ! trdatbuf
      real*8,  intent(in)  :: ztime   ! time (seconds)
      integer, intent(in)  :: n       ! number of currents expected
      real*8,  intent(out) :: cur(n)  ! poloidal field coil currents returned
      real*8,  intent(out) :: pcur    ! plasma current returned, if not defined in input this will be 0.
      integer, intent(out) :: ier     ! nonzero on error
    end subroutine tdb_freebdy_pre_pfc_pcur

Home Top


wr_trdatbuf

    subroutine wr_trdatbuf(nonlin, d, zserver, ztree, zshot, ztok, iyear, ishot,  ier)
      implicit none

      integer :: nonlin         ! lun for error messages

      Type (trdatbuf) :: d      ! trdatbuf object

      character*120 :: zserver  ! mds+ server
      character*80  :: ztree    ! mds+ tree
      character*80  :: zshot    ! runid
      character*20  :: ztok     ! tokamak

      integer :: iyear          ! two digit year
      integer :: ishot          ! mds+ shot
      integer :: ier            ! error flag

Home Top


rd_trdatbuf

    subroutine rd_trdatbuf(nonlin, d, zserver, ztree, zshot, ztok, iyear, ishot,  ier)
      implicit none

      integer :: nonlin         ! lun for error messages

      Type (trdatbuf) :: d      ! trdatbuf object

      character*120 :: zserver  ! mds+ server
      character*80  :: ztree    ! mds+ tree
      character*80  :: zshot    ! runid
      character*20  :: ztok     ! tokamak

      integer :: iyear          ! two digit year
      integer :: ishot          ! mds+ shot
      integer :: ier            ! error flag

Home Top


Data Objects


Home Top


profget

     
  type profget

     !  access to profile datasets

     !----------------------------------------
     !  input information...
 
     character*4 :: item      ! profile item desired...
     integer :: iselect       ! profile selection w/in item (3d sets only)

     integer :: nzones        ! number of zones in target grid

     !  to map data vs. normalized toroidal flux or norm. sqrt. tor. flux:

     real*8, dimension(:), pointer :: xibdys  ! (nzones+1) x @ zone bdys
     !      x is sqrt(Phi/Philim) ref enclosed toroidal flux at zone surfaces
     !      xibdys(1)=0; xibdys(nzones+1)=1 expected.

     !  to map data vs. normalized poloidal flux or norm. sqrt. pol. flux:

     real*8, dimension(:), pointer :: plflxg  ! (nzones+1) enclosed poloidal
     !      flux "psi" (Wb/2pi); Bpol = (1/R)*grad(psi)
     !      at zone bdys; plflxg(1)=0 expected.

     !  to map data vs. major or minor radius coordinate:

     real*8, dimension(:), pointer :: rmajmp  ! (2*nzones+1) major radii at
     !      flux zone boundary / midplane intercepts (cm).  RMAJMP(nzones+1)
     !      gives the magnetic axis; RMAJMP(1)= plasma boundary at midplane,
     !      small major radius side; RMAJMP(2*nzones+1) = plasma boundary at
     !      midplane, large major radius side.

     !  to map data vs. ECE frequency:

     real*8, dimension(:), pointer :: bmidp   ! (2*nzones+1) total B field (T)
     !      vs. major radius (rmajmp) along the midplane

     !  for all data items:

     real*8 :: time           ! time at which data is required (seconds)

     real*8 :: delta_t        ! average from time-delta_t to time+delta_t
                              ! default: delta_t = ZERO

     logical :: ibdy          ! T to interpolate to boundaries & fill in zones
                              ! F to interpolate to zone centers & fill in bdys

     !----------------------------------------
     !  internal:

     logical :: idebug        ! T to request extra output pertaining to
                              ! mapping or symmetrization of data
                              ! default: F

     logical :: iece          ! T for data vs. EC resonance frequency
     ! (trdatbuf object knows the harmonic frequency)

     integer :: nguard        ! used to verify object initialization
     integer :: nrmaj         ! 2*nzones + 1 -- rmajmp dimension
     integer :: nrsym         ! 4*nzones + 5 -- rmjsym dimension

     !  the following can be treated as output if desired by caller...
     !  these are only defined if idebug=T

     real*8, dimension(:), pointer :: xilmp
                              ! signed normalized sqrt tor flux on rmajmp grid

     real*8, dimension(:), pointer :: rmjsym
                              ! fine (nrsym) radial grid for symmetrization
                              ! comparison outputs
     real*8, dimension(:), pointer :: xirsym
                              ! signed normalized sqrt tor flux on rmjsym grid
                              ! range slightly greater than [-1,-1].

     !----------------------------------------
     !  output profiles: data & asymmetry profiles in data units...

     real*8, dimension(:), pointer :: data_zc ! (nzones+1) profile at zone
     !  centers, including a dummy zone, 1/2 zone width beyond plasma boundary

     real*8, dimension(:), pointer :: data_zb ! (nzones+1) profile at zone
     !  boundaries

     !----------------------------------------
     !  additional outputs created only if idebug=T...
     !
     !  for data that is input 2-sided vs. major radius and symmetrized
     !  by in/out averaging (nsyxxx=2 option):

     real*8, dimension(:), pointer :: asym_zc ! (nzones+1) profile asymmetry
     !  at zone centers (averaged value - measured value on large major radius
     !  side)

     real*8, dimension(:), pointer :: asym_zb ! (nzones+1) profile asymmetry
     !  at zone boundaries

     !  for data that is input 2-sided vs. major radius and symmetrized by
     !  the "slice and stack" method:

     real*8, dimension(:), pointer :: shift ! (nzones+1) inferred shift of
     !  flux surfaces relative to plasma boundary (cm)

     !  data mapped to fine major radius grid (in data units)

     real*8, dimension(:), pointer :: datrsym ! symmetrized data vs. rmjsym
     
     real*8, dimension(:), pointer :: datusym ! unsymmetrized data va. rmjsym

     real*8 :: ecegap   ! maximal B(R) monotonicity gap (cm)
     !  in high beta tokamak shots dB/dR can change sign due to diamagnetic
     !  effects, screening part of the plasma from view of an ECE temperature
     !  diagnostic; this number estimates the maximum such gap occurring
     !  it is calculated only if t%iece = .TRUE. and t%idebug = .TRUE.

  end type profget

    

Home Top


pwrget

  type pwrget

     !  access to power vs. time datasets (e.g. beam or RF powers)
     !
     ! Inputs
     !
     character*4 :: item            ! NBI data item to fetch/average
     real*8 :: ztime1               ! start of time averaging window
     real*8 :: ztime2               ! end of time averaging window
     logical :: pweight             ! .TRUE. for power weighted average
     integer :: nbeam               ! no. of beams -- expected to match trdatbuf nbdata
     real*8 :: tbon(tdbaux_maxnb)   ! on times for beams (1:nbeam)
     real*8 :: tboff(tdbaux_maxnb)  ! off times for beams (1:nbeam)
     
     ! internal
     !
     integer :: nguard              ! if not equal to 123456789 assume not initialized.
     
     ! Outputs
     !
     real*8 :: zparam(tdbaux_maxnb) ! return vector...

  end type pwrget
  
Home Top


trdatbuf

  type trdatbuf
 
  Contains entire contents pf Physics Data File. It's detailed structure is not intended for 
  direct access, but can be accessed thru all the routines described herein.

Home Top


Test Programs


Home Top


trdatbuf_test

  A test program call trdatbuf_test was written to demonstrate use of the routines
  where <run-id>PH.CDF is the name of a Physics Data File produced by the TRANSP
  preprocessing routine TRDAT

  At present, the trdatbuf_test program is available with the TRANSP release.

Home Top


trdatbuf_tomds

  A test program call trdatbuf_tomds was written to demonstrate the writing of
  a trdatbuf object to MDS+. It is a standalone program which reads in a
  <run-id>PH.CDF Physics Data File produced by the TRANS preprocessing routine
  TRDAT and stores is in a user specified MDS+ tree.

  Usage:

  trdatbuf_tomds  <ph.CDF> <server> <tree> <tok> <yr> <runid> <pulse>

  Example:

  trdatbuf_tomds 112989Z11PH.CDF TRANSPGRID.PPPL.GOV TRANSP_TFTR TFTR 88 37065Z11 370652611

Home Top


trdatbuf_frommds

  A test program call trdatbuf_frommds was written to demonstrate the reading of
  a trdatbuf object from MDS+. It is a standalone program which writes out a
  <run-id>PH.CDF Physics Data File after reading in a trdatbuf object from
  a user specified MDS+ tree.

  Usage:

  trdatbuf_frommds  <ph.CDF> <server> <tree> <tok> <yr> <runid> <pulse>

  Example:

  trdatbuf_frommds 112989Z11PH.CDF TRANSPGRID.PPPL.GOV TRANSP_TFTR TFTR 88 37065Z11 370652611

Home Top


Known Limitations

  Methods for accessing complete information on impurities remain to be worked out, in
  cases where the originating TRANSP run had profile data on multiple impurity species.

  Information on Zeff in TRANSP runs is often not provided in a simple way.  For example,
  sometimes only raw visible bremsstrahlung data is provided, requiring conversion in
  order to infer Zeff.  The routine "tdb_zeff_simple" is provided to test whether or not
  Zeff is available in a simple way, i.e. by direct interpolation of a scalar or profile
  function of time.
Home Top


About this document

This Document was created by hlptohtml

  • Written By:
  • Manish Vachharajani(mvachhar@pppl.gov)