spect3d_class.f03 Source File


This file depends on

sourcefile~~spect3d_class.f03~~EfferentGraph sourcefile~spect3d_class.f03 spect3d_class.f03 sourcefile~parallel_pipe_class.f03 parallel_pipe_class.f03 sourcefile~spect3d_class.f03->sourcefile~parallel_pipe_class.f03 sourcefile~perrors_class.f03 perrors_class.f03 sourcefile~spect3d_class.f03->sourcefile~perrors_class.f03 sourcefile~spect2d_class.f03 spect2d_class.f03 sourcefile~spect3d_class.f03->sourcefile~spect2d_class.f03 sourcefile~parallel_class.f03 parallel_class.f03 sourcefile~parallel_pipe_class.f03->sourcefile~parallel_class.f03 sourcefile~perrors_class.f03->sourcefile~parallel_class.f03 sourcefile~spect2d_class.f03->sourcefile~parallel_pipe_class.f03 sourcefile~spect2d_class.f03->sourcefile~perrors_class.f03

Files dependent on this one

sourcefile~~spect3d_class.f03~~AfferentGraph sourcefile~spect3d_class.f03 spect3d_class.f03 sourcefile~fdist3d_class.f03 fdist3d_class.f03 sourcefile~fdist3d_class.f03->sourcefile~spect3d_class.f03 sourcefile~ufield3d_class.f03 ufield3d_class.f03 sourcefile~fdist3d_class.f03->sourcefile~ufield3d_class.f03 sourcefile~input_class.f03 input_class.f03 sourcefile~fdist3d_class.f03->sourcefile~input_class.f03 sourcefile~field3d_class.f03 field3d_class.f03 sourcefile~field3d_class.f03->sourcefile~spect3d_class.f03 sourcefile~field3d_class.f03->sourcefile~ufield3d_class.f03 sourcefile~ufield3d_class.f03->sourcefile~spect3d_class.f03 sourcefile~part3d_class.f03 part3d_class.f03 sourcefile~part3d_class.f03->sourcefile~spect3d_class.f03 sourcefile~part3d_class.f03->sourcefile~fdist3d_class.f03 sourcefile~part3d_class.f03->sourcefile~ufield3d_class.f03 sourcefile~simulation_class.f03 simulation_class.f03 sourcefile~simulation_class.f03->sourcefile~spect3d_class.f03 sourcefile~simulation_class.f03->sourcefile~fdist3d_class.f03 sourcefile~simulation_class.f03->sourcefile~field3d_class.f03 sourcefile~simulation_class.f03->sourcefile~input_class.f03 sourcefile~species2d_class.f03 species2d_class.f03 sourcefile~simulation_class.f03->sourcefile~species2d_class.f03 sourcefile~beam3d_class.f03 beam3d_class.f03 sourcefile~simulation_class.f03->sourcefile~beam3d_class.f03 sourcefile~fdist2d_class.f03 fdist2d_class.f03 sourcefile~simulation_class.f03->sourcefile~fdist2d_class.f03 sourcefile~field2d_class.f03 field2d_class.f03 sourcefile~simulation_class.f03->sourcefile~field2d_class.f03 sourcefile~input_class.f03->sourcefile~spect3d_class.f03 sourcefile~species2d_class.f03->sourcefile~spect3d_class.f03 sourcefile~species2d_class.f03->sourcefile~field3d_class.f03 sourcefile~species2d_class.f03->sourcefile~fdist2d_class.f03 sourcefile~species2d_class.f03->sourcefile~field2d_class.f03 sourcefile~part2d_class.f03 part2d_class.f03 sourcefile~species2d_class.f03->sourcefile~part2d_class.f03 sourcefile~beam3d_class.f03->sourcefile~spect3d_class.f03 sourcefile~beam3d_class.f03->sourcefile~fdist3d_class.f03 sourcefile~beam3d_class.f03->sourcefile~field3d_class.f03 sourcefile~beam3d_class.f03->sourcefile~part3d_class.f03 sourcefile~beam3d_class.f03->sourcefile~field2d_class.f03 sourcefile~fdist2d_class.f03->sourcefile~input_class.f03 sourcefile~field2d_class.f03->sourcefile~field3d_class.f03 sourcefile~field2d_class.f03->sourcefile~ufield3d_class.f03 sourcefile~main.f03 main.f03 sourcefile~main.f03->sourcefile~simulation_class.f03 sourcefile~part2d_class.f03->sourcefile~fdist2d_class.f03

Contents

Source Code


Source Code

! Spect3d class for QuickPIC Open Source 1.0
! update: 04/18/2016

      module spect3d_class

      use perrors_class
      use parallel_pipe_class
      use spect2d_class
         
      implicit none

      private

      public :: spect3d

      type, extends(spect2d) :: spect3d

         private
         
         integer :: indz
         
         contains
         
         procedure, private :: init_spect3d
         procedure, private :: end_spect2d => end_spect3d
         generic :: new => init_spect3d
!         generic :: del => end_spect3d
         procedure :: getindz
                  
      end type spect3d
      
      contains
!
      subroutine init_spect3d(this,pp,perr,indx,indy,indz,psolver,inorder)
      
         implicit none
         
         class(spect3d), intent(inout) :: this
         class(perrors), intent(in), pointer :: perr
         class(parallel_pipe), intent(in), pointer :: pp
         integer, intent(in) :: indx, indy, indz,psolver, inorder
         
         call this%spect2d%new(pp,perr,indx,indy,psolver,inorder)
         this%indz = indz

      end subroutine init_spect3d
!
      subroutine end_spect3d(this)
          
         implicit none
         
         class(spect3d), intent(inout) :: this
         
         return
         
      end subroutine end_spect3d
!      
      function getindz(this)

         implicit none

         class(spect3d), intent(in) :: this
         integer :: getindz
         
         getindz = this%indz

      end function getindz        
!      
      end module spect3d_class