befor64_pack_data_m.F90 Source File

KISS library for packing heterogeneous data into single (homogeneous) packed one.

This File Depends On

sourcefile~~befor64_pack_data_m.f90~2~~EfferentGraph sourcefile~befor64_pack_data_m.f90~2 befor64_pack_data_m.F90 sourcefile~penf.f90 penf.F90 sourcefile~penf.f90->sourcefile~befor64_pack_data_m.f90~2 sourcefile~penf_b_size.f90 penf_b_size.F90 sourcefile~penf_b_size.f90->sourcefile~penf.f90 sourcefile~penf_stringify.f90 penf_stringify.F90 sourcefile~penf_b_size.f90->sourcefile~penf_stringify.f90 sourcefile~penf_global_parameters_variables.f90 penf_global_parameters_variables.F90 sourcefile~penf_global_parameters_variables.f90->sourcefile~penf.f90 sourcefile~penf_global_parameters_variables.f90->sourcefile~penf_b_size.f90 sourcefile~penf_global_parameters_variables.f90->sourcefile~penf_stringify.f90 sourcefile~penf_stringify.f90->sourcefile~penf.f90
Help


Source Code

!< KISS library for packing heterogeneous data into single (homogeneous) packed one.
module befor64_pack_data_m
!-----------------------------------------------------------------------------------------------------------------------------------
!< KISS library for packing heterogeneous data into single (homogeneous) packed one.
!-----------------------------------------------------------------------------------------------------------------------------------
use penf ! Portability environment.
!-----------------------------------------------------------------------------------------------------------------------------------

!-----------------------------------------------------------------------------------------------------------------------------------
implicit none
private
public :: pack_data
!-----------------------------------------------------------------------------------------------------------------------------------

!-----------------------------------------------------------------------------------------------------------------------------------
interface pack_data
  !< Pack different kinds of data into single I1P array.
  !<
  !< This is useful for encoding different (heterogeneous) kinds variables into a single (homogeneous) stream of bits.
  !< @note This procedure exploits the `transfer` builtin function, that from the standard (2003+) is defined as
  !< `TRANSFER(SOURCE, MOLD [, SIZE])`. Data object having a physical representation identical to that of `SOURCE` but with the type
  !< and type parameters of `MOLD`. The result is of the same type and type parameters as `MOLD`.
  !< If `MOLD` is an array and `SIZE` is absent, the result is an array and of rank one. Its size is as small as possible such
  !< that its physical representation is not shorter than that of `SOURCE`.
  !<
  !< Presently, the following combinations are available:
  !<
  !<* [ ] Arrays-Arrays:
  !<    * [X] real(any)-real(any);
  !<    * [X] real(any)-integer(any);
  !<    * [X] integer(any)-integer(any);
  !<    * [X] integer(any)-real(any);
  !<    * [ ] real(any)-character;
  !<    * [ ] character-real(any);
  !<    * [ ] integer(any)-character;
  !<    * [ ] character-integer(any);
  !<* [ ] Scalars-Scalars:
  !<    * [ ] real(any)-real(any);
  !<    * [ ] real(any)-integer(any);
  !<    * [ ] integer(any)-integer(any);
  !<    * [ ] integer(any)-real(any);
  !<    * [ ] real(any)-character;
  !<    * [ ] character-real(any);
  !<    * [ ] integer(any)-character;
  !<    * [ ] character-integer(any);
  !<
  !<### Examples of usage
  !<
  !<#### Packing two real arrays, one with kind R8P and one with R4P
  !<```fortran
  !<real(R8P)::                 array_r8(1:12)
  !<real(R4P)::                 array_r4(-1:5)
  !<integer(I1P), allocatable:: rpack
  !<...
  !<call pack_data(a1=array_r8,a2=array_r4,packed=rpack)
  !<```
  !<#### Packing two arrays, one real with kind R4P and one integer with I4P
  !<```fortran
  !<real(R4P)::                 array_r4(2)
  !<integer(I4P)::              array_i4(0:2)
  !<integer(I1P), allocatable:: rpack
  !<...
  !<call pack_data(a1=array_r4,a2=array_i4,packed=rpack)
  !<```
  module procedure pack_data_R8_R4,pack_data_R8_I8,pack_data_R8_I4,pack_data_R8_I2,pack_data_R8_I1, &
                   pack_data_R4_R8,pack_data_R4_I8,pack_data_R4_I4,pack_data_R4_I2,pack_data_R4_I1, &
                   pack_data_I8_R8,pack_data_I8_R4,pack_data_I8_I4,pack_data_I8_I2,pack_data_I8_I1, &
                   pack_data_I4_R8,pack_data_I4_R4,pack_data_I4_I8,pack_data_I4_I2,pack_data_I4_I1, &
                   pack_data_I2_R8,pack_data_I2_R4,pack_data_I2_I8,pack_data_I2_I4,pack_data_I2_I1, &
                   pack_data_I1_R8,pack_data_I1_R4,pack_data_I1_I8,pack_data_I1_I4,pack_data_I1_I2
endinterface
!-----------------------------------------------------------------------------------------------------------------------------------
contains
  pure subroutine pack_data_R8_R4(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  real(R8P),                 intent(in)    :: a1(1:)    !< Firs data stream.
  real(R4P),                 intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_R8_R4

  pure subroutine pack_data_R8_I8(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  real(R8P),                 intent(in)    :: a1(1:)    !< First data stream.
  integer(I8P),              intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_R8_I8

  pure subroutine pack_data_R8_I4(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  real(R8P),                 intent(in)    :: a1(1:)    !< First data stream.
  integer(I4P),              intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_R8_I4

  pure subroutine pack_data_R8_I2(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  real(R8P),                 intent(in)    :: a1(1:)    !< First data stream.
  integer(I2P),              intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_R8_I2

  pure subroutine pack_data_R8_I1(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  real(R8P),                 intent(in)    :: a1(1:)    !< First data stream.
  integer(I1P),              intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_R8_I1

  pure subroutine pack_data_R4_R8(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  real(R4P),                 intent(in)    :: a1(1:)    !< Firs data stream.
  real(R8P),                 intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_R4_R8

  pure subroutine pack_data_R4_I8(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  real(R4P),                 intent(in)    :: a1(1:)    !< First data stream.
  integer(I8P),              intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_R4_I8

  pure subroutine pack_data_R4_I4(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  real(R4P),                 intent(in)    :: a1(1:)    !< First data stream.
  integer(I4P),              intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_R4_I4

  pure subroutine pack_data_R4_I2(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  real(R4P),                 intent(in)    :: a1(1:)    !< First data stream.
  integer(I2P),              intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_R4_I2

  pure subroutine pack_data_R4_I1(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  real(R4P),                 intent(in)    :: a1(1:)    !< First data stream.
  integer(I1P),              intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_R4_I1

  pure subroutine pack_data_I8_R8(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I8P),              intent(in)    :: a1(1:)    !< First data stream.
  real(R8P),                 intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_I8_R8

  pure subroutine pack_data_I8_R4(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I8P),              intent(in)    :: a1(1:)    !< First data stream.
  real(R4P),                 intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_I8_R4

  pure subroutine pack_data_I8_I4(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I8P),              intent(in)    :: a1(1:)    !< First data stream.
  integer(I4P),              intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_I8_I4

  pure subroutine pack_data_I8_I2(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I8P),              intent(in)    :: a1(1:)    !< First data stream.
  integer(I2P),              intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_I8_I2

  pure subroutine pack_data_I8_I1(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I8P),              intent(in)    :: a1(1:)    !< First data stream.
  integer(I1P),              intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_I8_I1

  pure subroutine pack_data_I4_R8(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I4P),              intent(in)    :: a1(1:)    !< First data stream.
  real(R8P),                 intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_I4_R8

  pure subroutine pack_data_I4_R4(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I4P),              intent(in)    :: a1(1:)    !< First data stream.
  real(R4P),                 intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_I4_R4

  pure subroutine pack_data_I4_I8(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I4P),              intent(in)    :: a1(1:)    !< First data stream.
  integer(I8P),              intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_I4_I8

  pure subroutine pack_data_I4_I2(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I4P),              intent(in)    :: a1(1:)    !< First data stream.
  integer(I2P),              intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_I4_I2

  pure subroutine pack_data_I4_I1(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I4P),              intent(in)    :: a1(1:)    !< First data stream.
  integer(I1P),              intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_I4_I1

  pure subroutine pack_data_I2_R8(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I2P),              intent(in)    :: a1(1:)    !< First data stream.
  real(R8P),                 intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_I2_R8

  pure subroutine pack_data_I2_R4(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I2P),              intent(in)    :: a1(1:)    !< First data stream.
  real(R4P),                 intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_I2_R4

  pure subroutine pack_data_I2_I8(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I2P),              intent(in)    :: a1(1:)    !< First data stream.
  integer(I8P),              intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_I2_I8

  pure subroutine pack_data_I2_I4(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I2P),              intent(in)    :: a1(1:)    !< First data stream.
  integer(I4P),              intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_I2_I4

  pure subroutine pack_data_I2_I1(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I2P),              intent(in)    :: a1(1:)    !< First data stream.
  integer(I1P),              intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_I2_I1

  pure subroutine pack_data_I1_R8(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I1P),              intent(in)    :: a1(1:)    !< First data stream.
  real(R8P),                 intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_I1_R8

  pure subroutine pack_data_I1_R4(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I1P),              intent(in)    :: a1(1:)    !< First data stream.
  real(R4P),                 intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_I1_R4

  pure subroutine pack_data_I1_I8(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I1P),              intent(in)    :: a1(1:)    !< First data stream.
  integer(I8P),              intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_I1_I8

  pure subroutine pack_data_I1_I4(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I1P),              intent(in)    :: a1(1:)    !< First data stream.
  integer(I4P),              intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_I1_I4

  pure subroutine pack_data_I1_I2(a1, a2, packed)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Pack different kinds of data into single I1P array.
  !---------------------------------------------------------------------------------------------------------------------------------
  integer(I1P),              intent(in)    :: a1(1:)    !< First data stream.
  integer(I2P),              intent(in)    :: a2(1:)    !< Second data stream.
  integer(I1P), allocatable, intent(inout) :: packed(:) !< Packed data into I1P array.
  integer(I1P), allocatable                :: p1(:)     !< Temporary packed data of first stream.
  integer(I1P), allocatable                :: p2(:)     !< Temporary packed data of second stream.
  integer(I4P)                             :: np        !< Size of temporary packed data.
  !---------------------------------------------------------------------------------------------------------------------------------

  !---------------------------------------------------------------------------------------------------------------------------------
  np = size(transfer(a1,p1)) ; allocate(p1(1:np)) ; p1 = transfer(a1,p1)
  np = size(transfer(a2,p2)) ; allocate(p2(1:np)) ; p2 = transfer(a2,p2)
  if (allocated(packed)) deallocate(packed) ; allocate(packed(1:size(p1,dim=1)+size(p2,dim=1))) ; packed = [p1,p2]
  deallocate(p1,p2)
  return
  !---------------------------------------------------------------------------------------------------------------------------------
  endsubroutine pack_data_I1_I2
endmodule befor64_pack_data_m

assignments.f90 basename_dir.f90 befor64.F90 befor64.F90 befor64_pack_data_m.F90 befor64_pack_data_m.F90 camelcase.f90 capitalize.f90 compact_real.f90 compact_real.f90 compact_real.f90 concatenation.f90 csv_naive_parser.f90 decode.f90 encode.f90 equal.f90 escape.f90 extension.f90 fill.f90 free.f90 fury.f90 fury_mixed_kinds.F90 fury_qreal128.F90 fury_qreal32.F90 fury_qreal64.F90 fury_system_abstract128.F90 fury_system_abstract32.F90 fury_system_abstract64.F90 fury_system_si128.F90 fury_system_si32.F90 fury_system_si64.F90 fury_test_bolt32.f90 fury_test_bolt64.f90 fury_test_qreal_add.f90 fury_test_qreal_add_aliases_failure.f90 fury_test_qreal_add_failure.f90 fury_test_qreal_add_mixed.f90 fury_test_qreal_add_mixed_failure.f90 fury_test_qreal_aliases.f90 fury_test_qreal_assign.f90 fury_test_qreal_conversions_complex.f90 fury_test_qreal_conversions_si.f90 fury_test_qreal_conversions_simple.f90 fury_test_qreal_div.f90 fury_test_qreal_div_mixed.f90 fury_test_qreal_eq.f90 fury_test_qreal_eq_mixed.f90 fury_test_qreal_mul.f90 fury_test_qreal_mul_mixed.f90 fury_test_qreal_not_eq.f90 fury_test_qreal_not_eq_mixed.f90 fury_test_qreal_pow.f90 fury_test_qreal_sub.f90 fury_test_qreal_sub_failure.f90 fury_test_qreal_sub_mixed.f90 fury_test_qreal_sub_mixed_failure.f90 fury_test_system_si.f90 fury_test_uom_add.f90 fury_test_uom_add_failure.f90 fury_test_uom_aliases.f90 fury_test_uom_assign.f90 fury_test_uom_assign_failure.f90 fury_test_uom_div.f90 fury_test_uom_mul.f90 fury_test_uom_parse_failure.f90 fury_test_uom_pow.f90 fury_test_uom_sub.f90 fury_test_uom_sub_failure.f90 fury_uom128.F90 fury_uom32.F90 fury_uom64.F90 fury_uom_converter.F90 fury_uom_reference128.F90 fury_uom_reference32.F90 fury_uom_reference64.F90 fury_uom_symbol128.F90 fury_uom_symbol32.F90 fury_uom_symbol64.F90 greater_equal_than.f90 greater_than.f90 insert.f90 io_basic.F90 io_listdirected.F90 is_digit.f90 is_integer.f90 is_number.f90 is_real.f90 join.f90 lower_equal_than.f90 lower_than.f90 not_equal.f90 partition.f90 penf.F90 penf.F90 penf.F90 penf.F90 penf.F90 penf_b_size.F90 penf_global_parameters_variables.F90 penf_stringify.F90 read_file.f90 read_line.f90 read_lines.f90 replace.f90 reverse.f90 sadjustlr.f90 scount.f90 search.f90 sindex.f90 slen.f90 slice.f90 snakecase.f90 split.f90 srepeat.f90 sscan.f90 start_end.f90 startcase.f90 strim.f90 stringifor.F90 stringifor_string_t.F90 strip.f90 sverify.f90 swapcase.f90 test_all.F90 test_all.f90 test_all.f90 Test_Driver.f90 to_number.f90 unescape.f90 unique.f90 upper_lower.f90 write_file.f90 write_lines.f90