pic_optional.f90 Source File

Optional value handling module


This file depends on

sourcefile~~pic_optional.f90~~EfferentGraph sourcefile~pic_optional.f90 pic_optional.f90 sourcefile~pic_types.f90 pic_types.F90 sourcefile~pic_optional.f90->sourcefile~pic_types.f90

Files dependent on this one

sourcefile~~pic_optional.f90~~AfferentGraph sourcefile~pic_optional.f90 pic_optional.f90 sourcefile~pic_array.f90 pic_array.f90 sourcefile~pic_array.f90->sourcefile~pic_optional.f90 sourcefile~pic_sorting.f90 pic_sorting.f90 sourcefile~pic_sorting.f90->sourcefile~pic_optional.f90 sourcefile~pic_string_type.f90 pic_string_type.F90 sourcefile~pic_string_type.f90->sourcefile~pic_optional.f90 sourcefile~pic_strings.f90 pic_strings.f90 sourcefile~pic_strings.f90->sourcefile~pic_optional.f90 sourcefile~pic_strings.f90->sourcefile~pic_string_type.f90 sourcefile~pic_knowledge.f90 pic_knowledge.f90 sourcefile~pic_knowledge.f90->sourcefile~pic_string_type.f90 sourcefile~pic_sorting_ord_sort.f90 pic_sorting_ord_sort.f90 sourcefile~pic_sorting_ord_sort.f90->sourcefile~pic_sorting.f90 sourcefile~pic_sorting_radix_sort.f90 pic_sorting_radix_sort.f90 sourcefile~pic_sorting_radix_sort.f90->sourcefile~pic_sorting.f90 sourcefile~pic_sorting_sort.f90 pic_sorting_sort.f90 sourcefile~pic_sorting_sort.f90->sourcefile~pic_sorting.f90 sourcefile~pic_sorting_sort_index.f90 pic_sorting_sort_index.F90 sourcefile~pic_sorting_sort_index.f90->sourcefile~pic_sorting.f90 sourcefile~pic_string_type_constructor.f90 pic_string_type_constructor.f90 sourcefile~pic_string_type_constructor.f90->sourcefile~pic_string_type.f90 sourcefile~pic_string_type_constructor.f90->sourcefile~pic_strings.f90 sourcefile~pic_strings_to_strings.f90 pic_strings_to_strings.F90 sourcefile~pic_strings_to_strings.f90->sourcefile~pic_string_type.f90 sourcefile~pic_strings_to_strings.f90->sourcefile~pic_strings.f90

Source Code

! SPDX-License-Identifier: MIT
! Copyright (c) 2025 Jorge Luis Galvez Vallejo
!! Optional value handling module
module pic_optional_value
   !! This module provides functions to handle optional arguments
   use pic_types, only: sp, dp, int32, int64
   implicit none

   private

   public :: pic_optional

   interface pic_optional
   !! Overloaded interface for optional value retrieval, supported types are:
   !! - integer(int32), integer(int64), real(sp), real(dp), character(len=*), logical
      module procedure :: optional_int32
      module procedure :: optional_int64
      module procedure :: optional_sp
      module procedure :: optional_dp
      module procedure :: optional_char
      module procedure :: optional_logical
   end interface

contains

   pure function optional_int32(input_value, default_value) result(output)
      !! Handle optional integer(int32) value
      integer(int32), intent(in), optional :: input_value
      integer(int32), intent(in) :: default_value
      integer(int32) :: output

      if (present(input_value)) then
         output = input_value
      else
         output = default_value
      end if
   end function optional_int32

   pure function optional_int64(input_value, default_value) result(output)
      !! Handle optional integer(int64) value
      integer(int64), intent(in), optional :: input_value
      integer(int64), intent(in) :: default_value
      integer(int64) :: output

      if (present(input_value)) then
         output = input_value
      else
         output = default_value
      end if
   end function optional_int64

   pure function optional_sp(input_value, default_value) result(output)
      !! Handle optional real(sp) value
      real(sp), intent(in), optional :: input_value
      real(sp), intent(in) :: default_value
      real(sp) :: output

      if (present(input_value)) then
         output = input_value
      else
         output = default_value
      end if
   end function optional_sp

   pure function optional_dp(input_value, default_value) result(output)
      !! Handle optional real(dp) value
      real(dp), intent(in), optional :: input_value
      real(dp), intent(in) :: default_value
      real(dp) :: output

      if (present(input_value)) then
         output = input_value
      else
         output = default_value
      end if
   end function optional_dp

   pure function optional_char(input_value, default_value) result(output)
      !! Handle optional character(len=*) value
      character(len=*), intent(in), optional :: input_value
      character(len=*), intent(in) :: default_value
      character(len=:), allocatable :: output
      if (present(input_value)) then
         output = input_value
      else
         output = default_value
      end if

   end function optional_char

   pure function optional_logical(input_value, default_value) result(output)
      !! Handle optional logical value
      logical, intent(in), optional :: input_value
      logical, intent(in) :: default_value
      logical :: output

      if (present(input_value)) then
         output = input_value
      else
         output = default_value
      end if
   end function optional_logical

end module pic_optional_value