m_deallocate.f90 Source File

This File Depends On

sourcefile~~m_deallocate.f90~~EfferentGraph sourcefile~m_deallocate.f90 m_deallocate.f90 sourcefile~m_errors.f90 m_errors.f90 sourcefile~m_errors.f90->sourcefile~m_deallocate.f90 sourcefile~m_variablekind.f90 m_variableKind.f90 sourcefile~m_variablekind.f90->sourcefile~m_deallocate.f90 sourcefile~m_variablekind.f90->sourcefile~m_errors.f90
Help

Files Dependent On This One

sourcefile~~m_deallocate.f90~~AfferentGraph sourcefile~m_deallocate.f90 m_deallocate.f90 sourcefile~m_maths.f90 m_maths.f90 sourcefile~m_deallocate.f90->sourcefile~m_maths.f90 sourcefile~iddynamicarray_class.f90 idDynamicArray_Class.f90 sourcefile~m_deallocate.f90->sourcefile~iddynamicarray_class.f90 sourcefile~rdynamicarray_class.f90 rDynamicArray_Class.f90 sourcefile~m_deallocate.f90->sourcefile~rdynamicarray_class.f90 sourcefile~m_random.f90 m_random.f90 sourcefile~m_deallocate.f90->sourcefile~m_random.f90 sourcefile~idynamicarray_class.f90 iDynamicArray_Class.f90 sourcefile~m_deallocate.f90->sourcefile~idynamicarray_class.f90 sourcefile~ddynamicarray_class.f90 dDynamicArray_Class.f90 sourcefile~m_deallocate.f90->sourcefile~ddynamicarray_class.f90 sourcefile~m_kdtree.f90 m_KdTree.f90 sourcefile~m_deallocate.f90->sourcefile~m_kdtree.f90 sourcefile~m_tests.f90 m_tests.f90 sourcefile~m_deallocate.f90->sourcefile~m_tests.f90 sourcefile~m_maths.f90->sourcefile~m_kdtree.f90 sourcefile~m_maths.f90->sourcefile~m_tests.f90 sourcefile~scale_coretran.f90 scale_coretran.f90 sourcefile~m_maths.f90->sourcefile~scale_coretran.f90 sourcefile~iddynamicarray_class.f90->sourcefile~m_tests.f90 sourcefile~idargdynamicarray_class.f90 idArgDynamicArray_Class.f90 sourcefile~iddynamicarray_class.f90->sourcefile~idargdynamicarray_class.f90 sourcefile~rdynamicarray_class.f90->sourcefile~m_tests.f90 sourcefile~rargdynamicarray_class.f90 rArgDynamicArray_Class.f90 sourcefile~rdynamicarray_class.f90->sourcefile~rargdynamicarray_class.f90 sourcefile~m_random.f90->sourcefile~m_tests.f90 sourcefile~m_random.f90->sourcefile~scale_coretran.f90 sourcefile~test_coretran.f90 test_coretran.f90 sourcefile~m_random.f90->sourcefile~test_coretran.f90 sourcefile~m_array1d.f90 m_array1D.f90 sourcefile~m_random.f90->sourcefile~m_array1d.f90 sourcefile~idynamicarray_class.f90->sourcefile~m_kdtree.f90 sourcefile~idynamicarray_class.f90->sourcefile~m_tests.f90 sourcefile~idynamicarray_class.f90->sourcefile~idargdynamicarray_class.f90 sourcefile~idynamicarray_class.f90->sourcefile~rargdynamicarray_class.f90 sourcefile~dargdynamicarray_class.f90 dArgDynamicArray_Class.f90 sourcefile~idynamicarray_class.f90->sourcefile~dargdynamicarray_class.f90 sourcefile~iargdynamicarray_class.f90 iArgDynamicArray_Class.f90 sourcefile~idynamicarray_class.f90->sourcefile~iargdynamicarray_class.f90 sourcefile~ddynamicarray_class.f90->sourcefile~m_tests.f90 sourcefile~ddynamicarray_class.f90->sourcefile~dargdynamicarray_class.f90 sourcefile~m_kdtree.f90->sourcefile~m_tests.f90 sourcefile~m_kdtree.f90->sourcefile~scale_coretran.f90 sourcefile~m_tests.f90->sourcefile~test_coretran.f90 sourcefile~idargdynamicarray_class.f90->sourcefile~m_tests.f90 sourcefile~rargdynamicarray_class.f90->sourcefile~m_tests.f90 sourcefile~m_array1d.f90->sourcefile~m_maths.f90 sourcefile~m_array1d.f90->sourcefile~m_kdtree.f90 sourcefile~m_array1d.f90->sourcefile~m_tests.f90 sourcefile~m_array1d.f90->sourcefile~scale_coretran.f90 sourcefile~dargdynamicarray_class.f90->sourcefile~m_kdtree.f90 sourcefile~dargdynamicarray_class.f90->sourcefile~m_tests.f90 sourcefile~iargdynamicarray_class.f90->sourcefile~m_tests.f90
Help

Source Code


Source Code

module m_deallocate
  !! Contains fundamental interface to deallocate allocatable arrays of different types and shapes.
  !!
  !! See [[deallocate]] for more information.
  use variableKind, only: r32, r64, i32, i64
  use m_errors, only: eMsg,mErr

  implicit none

  private

  public deallocate

  interface deallocate
    !! Deallocate an allocatable array.
    !!
    !! Contains fundamental routines to deallocate allocatable arrays of different types and shapes.
    !! Does not overload the intrinsic deallocate function.
    !!
    !! This way, calling deallocate makes the user aware that checks are being made and errors are handled with a message.
    !!
    !! Checks for an error during allocation, and will stop the code if there is one.
    !!
    !! Example usage
    !!```fortran
    !!use variableKind
    !!use m_allocate, only: allocate
    !!use m_deallocate, only: deallocate
    !! ! Could be other intrinsic types too, integer(i32), complex(r32), etc.
    !!real(r64),allocatable :: a1D(:), a2D(:,:), a3D(:,:,:)
    !!call allocate(a1D, 20)
    !!call allocate(a2D, [20,20])
    !!call allocate(a3D, [20,20,20])
    !!write(*,'(a)') 'Shape of a3D is [20,20,20]? '//all(shape(a3D) == [20,20,20])
    !!call deallocate(a1D)
    !!call deallocate(a2D)
    !!call deallocate(a3D)
    !!```
    !====================================================================!
    module subroutine deallocate_r1D(this)
      !! Interfaced with [[deallocate]]
    !====================================================================!
      real(r32), allocatable, intent(inout) :: this(:) !! 1D array
    end subroutine
    !====================================================================!
    !====================================================================!
    module subroutine deallocate_r2D(this)
      !! Interfaced with [[deallocate]]
    !====================================================================!
      real(r32), allocatable, intent(inout) :: this(:,:) !! 2D array
    end subroutine
    !====================================================================!
    !====================================================================!
    module subroutine deallocate_r3D(this)
      !! Interfaced with [[deallocate]]
    !====================================================================!
      real(r32), allocatable, intent(inout) :: this(:,:,:) !! 3D array
    end subroutine
    !====================================================================!

    !====================================================================!
    module subroutine deallocate_d1D(this)
      !! Interfaced with [[deallocate]]
    !====================================================================!
      real(r64), allocatable, intent(inout) :: this(:) !! 1D array
    end subroutine
    !====================================================================!
    !====================================================================!
    module subroutine deallocate_d2D(this)
      !! Interfaced with [[deallocate]]
    !====================================================================!
      real(r64), allocatable, intent(inout) :: this(:,:) !! 2D array
    end subroutine
    !====================================================================!
    !====================================================================!
    module subroutine deallocate_d3D(this)
      !! Interfaced with [[deallocate]]
    !====================================================================!
      real(r64), allocatable, intent(inout) :: this(:,:,:) !! 3D array
    end subroutine
    !====================================================================!

    !====================================================================!
    module subroutine deallocate_i1D(this)
      !! Interfaced with [[deallocate]]
    !====================================================================!
      integer(i32), allocatable, intent(inout) :: this(:) !! 1D array
    end subroutine
    !====================================================================!
    !====================================================================!
    module subroutine deallocate_i2D(this)
      !! Interfaced with [[deallocate]]
    !====================================================================!
      integer(i32), allocatable, intent(inout) :: this(:,:) !! 2D array
    end subroutine
    !====================================================================!
    !====================================================================!
    module subroutine deallocate_i3D(this)
      !! Interfaced with [[deallocate]]
    !====================================================================!
      integer(i32), allocatable, intent(inout) :: this(:,:,:) !! 3D array
    end subroutine
    !====================================================================!

    !====================================================================!
    module subroutine deallocate_id1D(this)
      !! Interfaced with [[deallocate]]
    !====================================================================!
      integer(i64), allocatable, intent(inout) :: this(:) !! 1D array
    end subroutine
    !====================================================================!
    !====================================================================!
    module subroutine deallocate_id2D(this)
      !! Interfaced with [[deallocate]]
    !====================================================================!
      integer(i64), allocatable, intent(inout) :: this(:,:) !! 2D array
    end subroutine
    !====================================================================!
    !====================================================================!
    module subroutine deallocate_id3D(this)
      !! Interfaced with [[deallocate]]
    !====================================================================!
      integer(i64), allocatable, intent(inout) :: this(:,:,:) !! 3D array
    end subroutine
    !====================================================================!

    !====================================================================!
    module subroutine deallocate_c1D(this)
      !! Interfaced with [[deallocate]]
    !====================================================================!
      complex(r32), allocatable, intent(inout) :: this(:) !! 1D array
    end subroutine
    !====================================================================!
    !====================================================================!
    module subroutine deallocate_c2D(this)
      !! Interfaced with [[deallocate]]
    !====================================================================!
      complex(r32), allocatable, intent(inout) :: this(:,:) !! 2D array
    end subroutine
    !====================================================================!
    !====================================================================!
    module subroutine deallocate_c3D(this)
      !! Interfaced with [[deallocate]]
    !====================================================================!
      complex(r32), allocatable, intent(inout) :: this(:,:,:) !! 3D array
    end subroutine
    !====================================================================!

    !====================================================================!
    module subroutine deallocate_z1D(this)
      !! Interfaced with [[deallocate]]
    !====================================================================!
      complex(r64), allocatable, intent(inout) :: this(:) !! 1D array
    end subroutine
    !====================================================================!
    !====================================================================!
    module subroutine deallocate_z2D(this)
      !! Interfaced with [[deallocate]]
    !====================================================================!
      complex(r64), allocatable, intent(inout) :: this(:,:) !! 2D array
    end subroutine
    !====================================================================!
    !====================================================================!
    module subroutine deallocate_z3D(this)
      !! Interfaced with [[deallocate]]
    !====================================================================!
      complex(r64), allocatable, intent(inout) :: this(:,:,:) !! 3D array
    end subroutine
    !====================================================================!

    !====================================================================!
    module subroutine deallocate_l1D(this)
      !! Interfaced with [[deallocate]]
    !====================================================================!
      logical, allocatable, intent(inout) :: this(:) !! 1D array
    end subroutine
    !====================================================================!
    !====================================================================!
    module subroutine deallocate_l2D(this)
      !! Interfaced with [[deallocate]]
    !====================================================================!
      logical, allocatable, intent(inout) :: this(:,:) !! 2D array
    end subroutine
    !====================================================================!
    !====================================================================!
    module subroutine deallocate_l3D(this)
      !! Interfaced with [[deallocate]]
    !====================================================================!
      logical, allocatable, intent(inout) :: this(:,:,:) !! 3D array
    end subroutine
    !====================================================================!
  end interface

  contains

  !====================================================================!
  module subroutine deallocate_r1D(this)
    !! Interfaced with [[deallocate]]
  !====================================================================!
    real(r32), allocatable, intent(inout) :: this(:) !! 1D array
    integer(i32) :: istat
    if(allocated(this)) then
      deallocate(this, stat=istat)
      call mErr(istat,'deallocate_r1D:this',2)
    endif
  end subroutine
  !====================================================================!
  !====================================================================!
  module subroutine deallocate_r2D(this)
    !! Interfaced with [[deallocate]]
  !====================================================================!
    real(r32), allocatable, intent(inout) :: this(:,:) !! 2D array
    integer(i32) :: istat
    if(allocated(this)) then
      deallocate(this, stat=istat)
      call mErr(istat,'deallocate_r2D:this',2)
    endif
  end subroutine
  !====================================================================!
  !====================================================================!
  module subroutine deallocate_r3D(this)
    !! Interfaced with [[deallocate]]
  !====================================================================!
    real(r32), allocatable, intent(inout) :: this(:,:,:) !! 3D array
    integer(i32) :: istat
    if(allocated(this)) then
      deallocate(this, stat=istat)
      call mErr(istat,'deallocate_r3D:this',2)
    endif
  end subroutine
  !====================================================================!
  !====================================================================!
  module subroutine deallocate_d1D(this)
    !! Interfaced with [[deallocate]]
  !====================================================================!
    real(r64), allocatable, intent(inout) :: this(:) !! 1D array
    integer(i32) :: istat
    if(allocated(this)) then
      deallocate(this, stat=istat)
      call mErr(istat,'deallocate_d1D:this',2)
    endif
  end subroutine
  !====================================================================!
  !====================================================================!
  module subroutine deallocate_d2D(this)
    !! Interfaced with [[deallocate]]
  !====================================================================!
    real(r64), allocatable, intent(inout) :: this(:,:) !! 2D array
    integer(i32) :: istat
    if(allocated(this)) then
      deallocate(this, stat=istat)
      call mErr(istat,'deallocate_d2D:this',2)
    endif
  end subroutine
  !====================================================================!
  !====================================================================!
  module subroutine deallocate_d3D(this)
    !! Interfaced with [[deallocate]]
  !====================================================================!
    real(r64), allocatable, intent(inout) :: this(:,:,:) !! 3D array
    integer(i32) :: istat
    if(allocated(this)) then
      deallocate(this, stat=istat)
      call mErr(istat,'deallocate_d3D:this',2)
    endif
  end subroutine
  !====================================================================!
  !====================================================================!
  module subroutine deallocate_i1D(this)
    !! Interfaced with [[deallocate]]
  !====================================================================!
    integer(i32), allocatable, intent(inout) :: this(:) !! 1D array
    integer(i32) :: istat
    if(allocated(this)) then
      deallocate(this, stat=istat)
      call mErr(istat,'deallocate_i1D:this',2)
    endif
  end subroutine
  !====================================================================!
  !====================================================================!
  module subroutine deallocate_i2D(this)
    !! Interfaced with [[deallocate]]
  !====================================================================!
    integer(i32), allocatable, intent(inout) :: this(:,:) !! 2D array
    integer(i32) :: istat
    if(allocated(this)) then
      deallocate(this, stat=istat)
      call mErr(istat,'deallocate_i2D:this',2)
    endif
  end subroutine
  !====================================================================!
  !====================================================================!
  module subroutine deallocate_i3D(this)
    !! Interfaced with [[deallocate]]
  !====================================================================!
    integer(i32), allocatable, intent(inout) :: this(:,:,:) !! 3D array
    integer(i32) :: istat
    if(allocated(this)) then
      deallocate(this, stat=istat)
      call mErr(istat,'deallocate_i3D:this',2)
    endif
  end subroutine
  !====================================================================!
  !====================================================================!
  module subroutine deallocate_id1D(this)
    !! Interfaced with [[deallocate]]
  !====================================================================!
    integer(i64), allocatable, intent(inout) :: this(:) !! 1D array
    integer(i32) :: istat
    if(allocated(this)) then
      deallocate(this, stat=istat)
      call mErr(istat,'deallocate_id1D:this',2)
    endif
  end subroutine
  !====================================================================!
  !====================================================================!
  module subroutine deallocate_id2D(this)
    !! Interfaced with [[deallocate]]
  !====================================================================!
    integer(i64), allocatable, intent(inout) :: this(:,:) !! 2D array
    integer(i32) :: istat
    if(allocated(this)) then
      deallocate(this, stat=istat)
      call mErr(istat,'deallocate_id2D:this',2)
    endif
  end subroutine
  !====================================================================!
  !====================================================================!
  module subroutine deallocate_id3D(this)
    !! Interfaced with [[deallocate]]
  !====================================================================!
    integer(i64), allocatable, intent(inout) :: this(:,:,:) !! 3D array
    integer(i32) :: istat
    if(allocated(this)) then
      deallocate(this, stat=istat)
      call mErr(istat,'deallocate_id3D:this',2)
    endif
  end subroutine
  !====================================================================!
  !====================================================================!
  module subroutine deallocate_c1D(this)
    !! Interfaced with [[deallocate]]
  !====================================================================!
    complex(r32), allocatable, intent(inout) :: this(:) !! 1D array
    integer(i32) :: istat
    if(allocated(this)) then
      deallocate(this, stat=istat)
      call mErr(istat,'deallocate_c1D:this',2)
    endif
  end subroutine
  !====================================================================!
  !====================================================================!
  module subroutine deallocate_c2D(this)
    !! Interfaced with [[deallocate]]
  !====================================================================!
    complex(r32), allocatable, intent(inout) :: this(:,:) !! 2D array
    integer(i32) :: istat
    if(allocated(this)) then
      deallocate(this, stat=istat)
      call mErr(istat,'deallocate_c2D:this',2)
    endif
  end subroutine
  !====================================================================!
  !====================================================================!
  module subroutine deallocate_c3D(this)
    !! Interfaced with [[deallocate]]
  !====================================================================!
    complex(r32), allocatable, intent(inout) :: this(:,:,:) !! 3D array
    integer(i32) :: istat
    if(allocated(this)) then
      deallocate(this, stat=istat)
      call mErr(istat,'deallocate_c3D:this',2)
    endif
  end subroutine
  !====================================================================!
  !====================================================================!
  module subroutine deallocate_z1D(this)
    !! Interfaced with [[deallocate]]
  !====================================================================!
    complex(r64), allocatable, intent(inout) :: this(:) !! 1D array
    integer(i32) :: istat
    if(allocated(this)) then
      deallocate(this, stat=istat)
      call mErr(istat,'deallocate_z1D:this',2)
    endif
  end subroutine
  !====================================================================!
  !====================================================================!
  module subroutine deallocate_z2D(this)
    !! Interfaced with [[deallocate]]
  !====================================================================!
    complex(r64), allocatable, intent(inout) :: this(:,:) !! 2D array
    integer(i32) :: istat
    if(allocated(this)) then
      deallocate(this, stat=istat)
      call mErr(istat,'deallocate_z2D:this',2)
    endif
  end subroutine
  !====================================================================!
  !====================================================================!
  module subroutine deallocate_z3D(this)
    !! Interfaced with [[deallocate]]
  !====================================================================!
    complex(r64), allocatable, intent(inout) :: this(:,:,:) !! 3D array
    integer(i32) :: istat
    if(allocated(this)) then
      deallocate(this, stat=istat)
      call mErr(istat,'deallocate_z3D:this',2)
    endif
  end subroutine
  !====================================================================!
  !====================================================================!
  module subroutine deallocate_l1D(this)
    !! Interfaced with [[deallocate]]
  !====================================================================!
    logical, allocatable, intent(inout) :: this(:) !! 1D array
    integer(i32) :: istat
    if(allocated(this)) then
      deallocate(this, stat=istat)
      call mErr(istat,'deallocate_l1D:this',2)
    endif
  end subroutine
  !====================================================================!
  !====================================================================!
  module subroutine deallocate_l2D(this)
    !! Interfaced with [[deallocate]]
  !====================================================================!
    logical, allocatable, intent(inout) :: this(:,:) !! 2D array
    integer(i32) :: istat
    if(allocated(this)) then
      deallocate(this, stat=istat)
      call mErr(istat,'deallocate_l2D:this',2)
    endif
  end subroutine
  !====================================================================!
  !====================================================================!
  module subroutine deallocate_l3D(this)
    !! Interfaced with [[deallocate]]
  !====================================================================!
    logical, allocatable, intent(inout) :: this(:,:,:) !! 3D array
    integer(i32) :: istat
    if(allocated(this)) then
      deallocate(this, stat=istat)
      call mErr(istat,'deallocate_l3D:this',2)
    endif
  end subroutine
  !====================================================================!
end module