read_chease.f90 Source File


Contents

Source Code


Source Code

! DO NOT EDIT THIS FILE
! This file has been automatically generated using generate_read_chease.py

!> A module to read in datafiles from CHEASE.
!>
!> Based on code written by Edmund Highcock
!> edmundhighcock@sourceforge.net
!>
!> This is free software released under the MIT Licence
!>
!> This module is generated automatically
!> using
!>    $ python generate_read_chease.py read_chease.f90
module read_chease
  implicit none
  private
  public :: read_infile, finish
  integer, public :: npsi_chease, nchi_chease
  real, public :: r0exp_chease
  real, public :: b0exp_chease
  real, dimension(:), allocatable, public :: psi_chease
  real, dimension(:), allocatable, public :: chi_chease
  real, dimension(:), allocatable, public :: rgeom_chease
  real, dimension(:), allocatable, public :: ageom_chease
  real, dimension(:), allocatable, public :: q_chease
  real, dimension(:), allocatable, public :: dqdpsi_chease
  real, dimension(:), allocatable, public :: d2qdpsi2_chease
  real, dimension(:), allocatable, public :: p_chease
  real, dimension(:), allocatable, public :: dpdpsi_chease
  real, dimension(:), allocatable, public :: f_chease
  real, dimension(:), allocatable, public :: fdfdpsi_chease
  real, dimension(:), allocatable, public :: v_chease
  real, dimension(:), allocatable, public :: rho_t_chease
  real, dimension(:), allocatable, public :: shear_chease
  real, dimension(:), allocatable, public :: dsheardpsi_chease
  real, dimension(:), allocatable, public :: kappa_chease
  real, dimension(:), allocatable, public :: delta_lower_chease
  real, dimension(:), allocatable, public :: delta_upper_chease
  real, dimension(:), allocatable, public :: dvdpsi_chease
  real, dimension(:), allocatable, public :: dpsidrhotor_chease
  real, dimension(:), allocatable, public :: gdpsi_av_chease
  real, dimension(:), allocatable, public :: radius_av_chease
  real, dimension(:), allocatable, public :: r_av_chease
  real, dimension(:), allocatable, public :: te_chease
  real, dimension(:), allocatable, public :: dtedpsi_chease
  real, dimension(:), allocatable, public :: ne_chease
  real, dimension(:), allocatable, public :: dnedpsi_chease
  real, dimension(:), allocatable, public :: ti_chease
  real, dimension(:), allocatable, public :: dtidpsi_chease
  real, dimension(:), allocatable, public :: ni_chease
  real, dimension(:), allocatable, public :: dnidpsi_chease
  real, dimension(:), allocatable, public :: zeff_chease
  real, dimension(:), allocatable, public :: signeo_chease
  real, dimension(:), allocatable, public :: jbsbav_chease
  real, dimension(:, :), allocatable, public :: g11_chease
  real, dimension(:, :), allocatable, public :: g12_chease
  real, dimension(:, :), allocatable, public :: g22_chease
  real, dimension(:, :), allocatable, public :: g33_chease
  real, dimension(:, :), allocatable, public :: b_chease
  real, dimension(:, :), allocatable, public :: dbdpsi_chease
  real, dimension(:, :), allocatable, public :: dbdchi_chease
  real, dimension(:, :), allocatable, public :: dpsidr_chease
  real, dimension(:, :), allocatable, public :: dpsidz_chease
  real, dimension(:, :), allocatable, public :: dchidr_chease
  real, dimension(:, :), allocatable, public :: dchidz_chease
  real, dimension(:, :), allocatable, public :: jacobian_chease
  real, dimension(:, :), allocatable, public :: r_chease
  real, dimension(:, :), allocatable, public :: z_chease
  logical, parameter :: debug = .true.
contains
!> Open and read chease file named "filename". Populates module level variables with the output.
subroutine read_infile(filename)
  implicit none
  character(len=*), intent(in) :: filename
  integer :: infile
  open(newunit = infile, file = filename)
  read(infile, *) ; read(infile, *) npsi_chease ; read(infile, *) ; read(infile, *) nchi_chease
  if (debug) write(*, *) npsi_chease, "<---npsi_chease"
  if (debug) write(*, *) nchi_chease, "<---nchi_chease"

  read(infile, *) ; read(infile, *) r0exp_chease
  read(infile, *) ; read(infile, *) b0exp_chease

  allocate( psi_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) psi_chease
  allocate( chi_chease(nchi_chease)) ; read(infile, *) ; read(infile, *) chi_chease
  allocate( rgeom_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) rgeom_chease
  allocate( ageom_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) ageom_chease
  allocate( q_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) q_chease
  allocate( dqdpsi_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) dqdpsi_chease
  allocate( d2qdpsi2_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) d2qdpsi2_chease
  allocate( p_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) p_chease
  allocate( dpdpsi_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) dpdpsi_chease
  allocate( f_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) f_chease
  allocate( fdfdpsi_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) fdfdpsi_chease
  allocate( v_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) v_chease
  allocate( rho_t_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) rho_t_chease
  allocate( shear_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) shear_chease
  allocate( dsheardpsi_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) dsheardpsi_chease
  allocate( kappa_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) kappa_chease
  allocate( delta_lower_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) delta_lower_chease
  allocate( delta_upper_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) delta_upper_chease
  allocate( dvdpsi_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) dvdpsi_chease
  allocate( dpsidrhotor_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) dpsidrhotor_chease
  allocate( gdpsi_av_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) gdpsi_av_chease
  allocate( radius_av_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) radius_av_chease
  allocate( r_av_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) r_av_chease
  allocate( te_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) te_chease
  allocate( dtedpsi_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) dtedpsi_chease
  allocate( ne_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) ne_chease
  allocate( dnedpsi_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) dnedpsi_chease
  allocate( ti_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) ti_chease
  allocate( dtidpsi_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) dtidpsi_chease
  allocate( ni_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) ni_chease
  allocate( dnidpsi_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) dnidpsi_chease
  allocate( zeff_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) zeff_chease
  allocate( signeo_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) signeo_chease
  allocate( jbsbav_chease(npsi_chease)) ; read(infile, *) ; read(infile, *) jbsbav_chease

  allocate( g11_chease(npsi_chease, nchi_chease)) ; read(infile, *) ; read(infile, *) g11_chease
  allocate( g12_chease(npsi_chease, nchi_chease)) ; read(infile, *) ; read(infile, *) g12_chease
  allocate( g22_chease(npsi_chease, nchi_chease)) ; read(infile, *) ; read(infile, *) g22_chease
  allocate( g33_chease(npsi_chease, nchi_chease)) ; read(infile, *) ; read(infile, *) g33_chease
  allocate( b_chease(npsi_chease, nchi_chease)) ; read(infile, *) ; read(infile, *) b_chease
  allocate( dbdpsi_chease(npsi_chease, nchi_chease)) ; read(infile, *) ; read(infile, *) dbdpsi_chease
  allocate( dbdchi_chease(npsi_chease, nchi_chease)) ; read(infile, *) ; read(infile, *) dbdchi_chease
  allocate( dpsidr_chease(npsi_chease, nchi_chease)) ; read(infile, *) ; read(infile, *) dpsidr_chease
  allocate( dpsidz_chease(npsi_chease, nchi_chease)) ; read(infile, *) ; read(infile, *) dpsidz_chease
  allocate( dchidr_chease(npsi_chease, nchi_chease)) ; read(infile, *) ; read(infile, *) dchidr_chease
  allocate( dchidz_chease(npsi_chease, nchi_chease)) ; read(infile, *) ; read(infile, *) dchidz_chease
  allocate( jacobian_chease(npsi_chease, nchi_chease)) ; read(infile, *) ; read(infile, *) jacobian_chease
  allocate( r_chease(npsi_chease, nchi_chease)) ; read(infile, *) ; read(infile, *) r_chease
  allocate( z_chease(npsi_chease, nchi_chease)) ; read(infile, *) ; read(infile, *) z_chease

  close(unit = infile)
end subroutine read_infile
!> Deallocate any module level arrays which have been allocated
subroutine finish
  implicit none
  if ( allocated(psi_chease)) deallocate(psi_chease)
  if ( allocated(chi_chease)) deallocate(chi_chease)
  if ( allocated(rgeom_chease)) deallocate(rgeom_chease)
  if ( allocated(ageom_chease)) deallocate(ageom_chease)
  if ( allocated(q_chease)) deallocate(q_chease)
  if ( allocated(dqdpsi_chease)) deallocate(dqdpsi_chease)
  if ( allocated(d2qdpsi2_chease)) deallocate(d2qdpsi2_chease)
  if ( allocated(p_chease)) deallocate(p_chease)
  if ( allocated(dpdpsi_chease)) deallocate(dpdpsi_chease)
  if ( allocated(f_chease)) deallocate(f_chease)
  if ( allocated(fdfdpsi_chease)) deallocate(fdfdpsi_chease)
  if ( allocated(v_chease)) deallocate(v_chease)
  if ( allocated(rho_t_chease)) deallocate(rho_t_chease)
  if ( allocated(shear_chease)) deallocate(shear_chease)
  if ( allocated(dsheardpsi_chease)) deallocate(dsheardpsi_chease)
  if ( allocated(kappa_chease)) deallocate(kappa_chease)
  if ( allocated(delta_lower_chease)) deallocate(delta_lower_chease)
  if ( allocated(delta_upper_chease)) deallocate(delta_upper_chease)
  if ( allocated(dvdpsi_chease)) deallocate(dvdpsi_chease)
  if ( allocated(dpsidrhotor_chease)) deallocate(dpsidrhotor_chease)
  if ( allocated(gdpsi_av_chease)) deallocate(gdpsi_av_chease)
  if ( allocated(radius_av_chease)) deallocate(radius_av_chease)
  if ( allocated(r_av_chease)) deallocate(r_av_chease)
  if ( allocated(te_chease)) deallocate(te_chease)
  if ( allocated(dtedpsi_chease)) deallocate(dtedpsi_chease)
  if ( allocated(ne_chease)) deallocate(ne_chease)
  if ( allocated(dnedpsi_chease)) deallocate(dnedpsi_chease)
  if ( allocated(ti_chease)) deallocate(ti_chease)
  if ( allocated(dtidpsi_chease)) deallocate(dtidpsi_chease)
  if ( allocated(ni_chease)) deallocate(ni_chease)
  if ( allocated(dnidpsi_chease)) deallocate(dnidpsi_chease)
  if ( allocated(zeff_chease)) deallocate(zeff_chease)
  if ( allocated(signeo_chease)) deallocate(signeo_chease)
  if ( allocated(jbsbav_chease)) deallocate(jbsbav_chease)
  if ( allocated(g11_chease)) deallocate(g11_chease)
  if ( allocated(g12_chease)) deallocate(g12_chease)
  if ( allocated(g22_chease)) deallocate(g22_chease)
  if ( allocated(g33_chease)) deallocate(g33_chease)
  if ( allocated(b_chease)) deallocate(b_chease)
  if ( allocated(dbdpsi_chease)) deallocate(dbdpsi_chease)
  if ( allocated(dbdchi_chease)) deallocate(dbdchi_chease)
  if ( allocated(dpsidr_chease)) deallocate(dpsidr_chease)
  if ( allocated(dpsidz_chease)) deallocate(dpsidz_chease)
  if ( allocated(dchidr_chease)) deallocate(dchidr_chease)
  if ( allocated(dchidz_chease)) deallocate(dchidz_chease)
  if ( allocated(jacobian_chease)) deallocate(jacobian_chease)
  if ( allocated(r_chease)) deallocate(r_chease)
  if ( allocated(z_chease)) deallocate(z_chease)
end subroutine finish
end module read_chease