pic_types.F90 Source File

pic_types.F90 controls the standarized sizes for the datatypes across pic, this is key for interfacing with other codes specially those that use default sizes


Files dependent on this one

sourcefile~~pic_types.f90~~AfferentGraph sourcefile~pic_types.f90 pic_types.F90 sourcefile~pic_array.f90 pic_array.f90 sourcefile~pic_array.f90->sourcefile~pic_types.f90 sourcefile~pic_blas_interfaces.f90 pic_blas_interfaces.F90 sourcefile~pic_blas_interfaces.f90->sourcefile~pic_types.f90 sourcefile~pic_command_line.f90 pic_command_line.f90 sourcefile~pic_command_line.f90->sourcefile~pic_types.f90 sourcefile~pic_constants.f90 pic_constants.f90 sourcefile~pic_constants.f90->sourcefile~pic_types.f90 sourcefile~pic_flop_rate.f90 pic_flop_rate.f90 sourcefile~pic_flop_rate.f90->sourcefile~pic_types.f90 sourcefile~pic_flop_recorder.f90 pic_flop_recorder.f90 sourcefile~pic_flop_rate.f90->sourcefile~pic_flop_recorder.f90 sourcefile~pic_string_utils.f90 pic_string_utils.f90 sourcefile~pic_flop_rate.f90->sourcefile~pic_string_utils.f90 sourcefile~pic_timer.f90 pic_timer.F90 sourcefile~pic_flop_rate.f90->sourcefile~pic_timer.f90 sourcefile~pic_flop_recorder.f90->sourcefile~pic_types.f90 sourcefile~pic_global_definitions.f90 pic_global_definitions.f90 sourcefile~pic_global_definitions.f90->sourcefile~pic_types.f90 sourcefile~pic_helpers.f90 pic_helpers.f90 sourcefile~pic_helpers.f90->sourcefile~pic_types.f90 sourcefile~pic_helpers.f90->sourcefile~pic_global_definitions.f90 sourcefile~pic_logger.f90 pic_logger.f90 sourcefile~pic_logger.f90->sourcefile~pic_types.f90 sourcefile~pic_logger.f90->sourcefile~pic_global_definitions.f90 sourcefile~pic_matrix_printer.f90 pic_matrix_printer.f90 sourcefile~pic_matrix_printer.f90->sourcefile~pic_types.f90 sourcefile~pic_matrix_printer.f90->sourcefile~pic_string_utils.f90 sourcefile~pic_matrix_printer_v2.f90 pic_matrix_printer_v2.f90 sourcefile~pic_matrix_printer_v2.f90->sourcefile~pic_types.f90 sourcefile~pic_matrix_printer_v2.f90->sourcefile~pic_string_utils.f90 sourcefile~pic_mpi.f90 pic_mpi.F90 sourcefile~pic_mpi.f90->sourcefile~pic_types.f90 sourcefile~pic_output_helpers.f90 pic_output_helpers.f90 sourcefile~pic_output_helpers.f90->sourcefile~pic_types.f90 sourcefile~pic_string_utils.f90->sourcefile~pic_types.f90 sourcefile~pic_timer.f90->sourcefile~pic_types.f90 sourcefile~pic_timer.f90->sourcefile~pic_string_utils.f90 sourcefile~pic_debugging_tools.f90 pic_debugging_tools.f90 sourcefile~pic_debugging_tools.f90->sourcefile~pic_matrix_printer.f90 sourcefile~pic_debugging_tools.f90->sourcefile~pic_string_utils.f90

Source Code

!! pic_types.F90 controls the standarized sizes for the datatypes across
!! pic, this is key for interfacing with other codes specially those that
!! use default sizes

module pic_types
   !! main module for defining types for integer and double precision
   use, intrinsic :: iso_fortran_env, only: int32, int64
   implicit none

   private

   public :: int32, int64
   ! Define kinds for different data types
   ! int32 and int64 are defined in the iso_fortran_env, if you need to change things please do so here
   integer, parameter, public :: sp = SELECTED_REAL_KIND(6, 37)
      !! single precision size
   integer, parameter, public :: dp = SELECTED_REAL_KIND(15, 307)
      !! double precision size
   integer, parameter, public :: qp = SELECTED_REAL_KIND(33, 4931)
      !! quadruple precision size, varies by compiler

   ! Define default types
#ifdef USE_INT8
   integer, parameter, public :: default_int = int64
    !! if you compile PIC requesting USE_INT8 the default_int will be set to int64 this is kinda equivalent
    !! to compiling with -i8. If linking to a legacy codebase that relies on this, compile PIC with USE_INT8
#else
   integer, parameter, public :: default_int = int32
    !! the default integer kind in PIC is int32 which faciliates the interfaces to MPI
    !! pay special attention if linking PIC to a code that use default int size of 8
#endif
   integer, parameter, public :: default_real = dp
    !! naturally, our default real is double precision
   integer, parameter, public :: default_complex = dp
    !! default complex is double precision

end module pic_types