alloc_var_R16P_3D Subroutine

private subroutine alloc_var_R16P_3D(var, ulb, msg, verbose)

Allocate CPU variable with memory checking (kind R16P, rank 3).

 use penf
 real(R16P), allocatable :: a(:,:,:)
 integer(I4P)            :: ulb(2,3)=reshape([1,1, &
                                              1,2, &
                                              1,3],&
                                             [2,3])
 call allocate_variable(a, ulb)
 print*, allocated(a)

Arguments

Type IntentOptional Attributes Name
real(kind=R16P), intent(inout), allocatable :: var(:,:,:)

Varibale to be allocate on CPU.

integer(kind=I4P), intent(in) :: ulb(2,3)

Upper/lower bounds of variable.

character(len=*), intent(in), optional :: msg

Message to be printed in verbose mode.

logical, intent(in), optional :: verbose

Flag to activate verbose mode.


Calls

proc~~alloc_var_r16p_3d~~CallsGraph proc~alloc_var_r16p_3d alloc_var_R16P_3D interface~str str proc~alloc_var_r16p_3d->interface~str proc~get_memory_info get_memory_info proc~alloc_var_r16p_3d->proc~get_memory_info proc~str_a_i1p str_a_I1P interface~str->proc~str_a_i1p proc~str_a_i2p str_a_I2P interface~str->proc~str_a_i2p proc~str_a_i4p str_a_I4P interface~str->proc~str_a_i4p proc~str_a_i8p str_a_I8P interface~str->proc~str_a_i8p proc~str_a_r4p str_a_R4P interface~str->proc~str_a_r4p proc~str_a_r8p str_a_R8P interface~str->proc~str_a_r8p proc~str_bol str_bol interface~str->proc~str_bol proc~str_i1p str_I1P interface~str->proc~str_i1p proc~str_i2p str_I2P interface~str->proc~str_i2p proc~str_i4p str_I4P interface~str->proc~str_i4p proc~str_i8p str_I8P interface~str->proc~str_i8p proc~str_r4p str_R4P interface~str->proc~str_r4p proc~str_r8p str_R8P interface~str->proc~str_r8p proc~strf_i1p strf_I1P interface~str->proc~strf_i1p proc~strf_i2p strf_I2P interface~str->proc~strf_i2p proc~strf_i4p strf_I4P interface~str->proc~strf_i4p proc~strf_i8p strf_I8P interface~str->proc~strf_i8p proc~strf_r4p strf_R4P interface~str->proc~strf_r4p proc~strf_r8p strf_R8P interface~str->proc~strf_r8p interface~cton cton proc~get_memory_info->interface~cton proc~ctoi_i1p ctoi_I1P interface~cton->proc~ctoi_i1p proc~ctoi_i2p ctoi_I2P interface~cton->proc~ctoi_i2p proc~ctoi_i4p ctoi_I4P interface~cton->proc~ctoi_i4p proc~ctoi_i8p ctoi_I8P interface~cton->proc~ctoi_i8p proc~ctor_r4p ctor_R4P interface~cton->proc~ctor_r4p proc~ctor_r8p ctor_R8P interface~cton->proc~ctor_r8p proc~str_a_i1p->proc~str_i1p proc~str_a_i2p->proc~str_i2p proc~str_a_i4p->proc~str_i4p proc~str_a_i8p->proc~str_i8p proc~str_a_r4p->proc~str_r4p proc~str_a_r8p->proc~str_r8p proc~compact_real_string compact_real_string proc~str_r4p->proc~compact_real_string proc~str_r8p->proc~compact_real_string

Source Code

   subroutine alloc_var_R16P_3D(var, ulb, msg, verbose)
   !< Allocate CPU variable with memory checking (kind R16P, rank 3).
   !<
   !<```fortran
   !< use penf
   !< real(R16P), allocatable :: a(:,:,:)
   !< integer(I4P)            :: ulb(2,3)=reshape([1,1, &
   !<                                              1,2, &
   !<                                              1,3],&
   !<                                             [2,3])
   !< call allocate_variable(a, ulb)
   !< print*, allocated(a)
   !<```
   !=> T <<<
   real(R16P), allocatable, intent(inout)        :: var(:,:,:)          !< Varibale to be allocate on CPU.
   integer(I4P),           intent(in)            :: ulb(2,3)            !< Upper/lower bounds of variable.
   character(*),           intent(in), optional  :: msg                 !< Message to be printed in verbose mode.
   logical,                intent(in), optional  :: verbose             !< Flag to activate verbose mode.
   character(:), allocatable                     :: msg_                !< Message to be printed in verbose mode, local var.
   logical                                       :: verbose_            !< Flag to activate verbose mode, local var.
   integer(C_LONG)                               :: mem_free, mem_total !< CPU memory.

   msg_     = ''      ; if (present(msg    )) msg_     = msg
   verbose_ = .false. ; if (present(verbose)) verbose_ = verbose
   if (allocated(var)) deallocate(var)
   if (verbose_) then
      call get_memory_info(mem_total, mem_free)
      print '(A)', msg_//'free/total memory BEFORE allocate:'//trim(str([mem_free,mem_total]))//'[bytes]'
   endif
   allocate(var(ulb(1,1):ulb(2,1), ulb(1,2):ulb(2,2), ulb(1,3):ulb(2,3)))
   if (verbose_) then
      call get_memory_info(mem_total, mem_free)
      print '(A)', msg_//'free/total memory AFTER  allocate:'//trim(str([mem_free,mem_total]))//'[bytes]'
   endif
   endsubroutine alloc_var_R16P_3D