interfaces.F90 Source File


This file depends on

sourcefile~~interfaces.f90~~EfferentGraph sourcefile~interfaces.f90 interfaces.F90 sourcefile~status_codes.f90 status_codes.F90 sourcefile~interfaces.f90->sourcefile~status_codes.f90

Files dependent on this one

sourcefile~~interfaces.f90~~AfferentGraph sourcefile~interfaces.f90 interfaces.F90 sourcefile~udsystem.f90 UDSystem.F90 sourcefile~udsystem.f90->sourcefile~interfaces.f90 sourcefile~udunits2f.f90 udunits2f.F90 sourcefile~udunits2f.f90->sourcefile~interfaces.f90 sourcefile~udunits2f.f90->sourcefile~udsystem.f90 sourcefile~convertunitsaction.f90 ConvertUnitsAction.F90 sourcefile~convertunitsaction.f90->sourcefile~udunits2f.f90 sourcefile~fieldspec.f90~2 FieldSpec.F90 sourcefile~fieldspec.f90~2->sourcefile~udunits2f.f90 sourcefile~fieldspec.f90~2->sourcefile~convertunitsaction.f90 sourcefile~fieldunits.f90 FieldUnits.F90 sourcefile~fieldunits.f90->sourcefile~udunits2f.f90 sourcefile~mapl_initialize.f90 MAPL_Initialize.F90 sourcefile~mapl_initialize.f90->sourcefile~udunits2f.f90 sourcefile~test_udsystem.pf Test_UDSystem.pf sourcefile~test_udsystem.pf->sourcefile~udsystem.f90 sourcefile~test_udsystem.pf->sourcefile~udunits2f.f90 sourcefile~test_udunits2f.pf Test_udunits2f.pf sourcefile~test_udunits2f.pf->sourcefile~udsystem.f90 sourcefile~test_udunits2f.pf->sourcefile~udunits2f.f90 sourcefile~bracketspec.f90 BracketSpec.F90 sourcefile~bracketspec.f90->sourcefile~fieldspec.f90~2 sourcefile~make_itemspec.f90 make_itemSpec.F90 sourcefile~make_itemspec.f90->sourcefile~fieldspec.f90~2 sourcefile~make_itemspec.f90->sourcefile~bracketspec.f90 sourcefile~modelverticalgrid.f90 ModelVerticalGrid.F90 sourcefile~modelverticalgrid.f90->sourcefile~fieldspec.f90~2 sourcefile~test_addfieldspec.pf Test_AddFieldSpec.pf sourcefile~test_addfieldspec.pf->sourcefile~fieldspec.f90~2 sourcefile~test_bracketspec.pf Test_BracketSpec.pf sourcefile~test_bracketspec.pf->sourcefile~fieldspec.f90~2 sourcefile~test_bracketspec.pf->sourcefile~bracketspec.f90 sourcefile~test_fieldinfo.pf Test_FieldInfo.pf sourcefile~test_fieldinfo.pf->sourcefile~fieldspec.f90~2 sourcefile~test_fieldspec.pf Test_FieldSpec.pf sourcefile~test_fieldspec.pf->sourcefile~fieldspec.f90~2 sourcefile~can_connect_to.f90 can_connect_to.F90 sourcefile~can_connect_to.f90->sourcefile~modelverticalgrid.f90 sourcefile~can_connect_to.f90~2 can_connect_to.F90 sourcefile~can_connect_to.f90~2->sourcefile~modelverticalgrid.f90 sourcefile~can_connect_to.f90~3 can_connect_to.F90 sourcefile~can_connect_to.f90~3->sourcefile~modelverticalgrid.f90 sourcefile~initialize_advertise.f90 initialize_advertise.F90 sourcefile~initialize_advertise.f90->sourcefile~make_itemspec.f90 sourcefile~test_modelverticalgrid.pf Test_ModelVerticalGrid.pf sourcefile~test_modelverticalgrid.pf->sourcefile~make_itemspec.f90 sourcefile~test_modelverticalgrid.pf->sourcefile~modelverticalgrid.f90

Source Code

module ud2f_interfaces
   use ud2f_encoding, only: ut_encoding
   use ud2f_status_codes, only: ut_status
   use, intrinsic :: iso_c_binding, only: c_ptr, c_char, c_int, c_float, c_double
   implicit none
   private

   public :: ut_get_status, ut_parse
   public :: ut_read_xml_cptr
   public :: ut_get_converter, ut_are_convertible
   public :: cv_convert_double, cv_convert_float
   public :: cv_convert_doubles, cv_convert_floats
   public :: ut_free, ut_free_system, cv_free
   public :: ut_set_ignore_error_message_handler
   interface

      ! Procedures that return type(c_ptr) return a C null pointer on failure.
      ! However, checking for the C null pointer IS NOT a good check for status.
      ! ut_get_status is a better check, where UT_SUCCESS indicates success.

      ! Return type(c_ptr) to ut_system units database specified by path
      ! Use ut_get_status to check error condition. 
      ! UT_SUCCESS indicates that the function ran successfully.
      ! Other ut_status codes indicate cause of failure.
      type(c_ptr) function ut_read_xml_cptr(path) bind(c, name='ut_read_xml')
         import :: c_ptr
         type(c_ptr), value :: path
      end function ut_read_xml_cptr

      ! Get status code
      integer(ut_status) function ut_get_status() bind(c, name='ut_get_status')
         import :: ut_status
      end function ut_get_status

      ! Return non-zero value if unit1 can be converted to unit2, otherwise 0
      ! Use ut_get_status to check error condition. 
      ! UT_SUCCESS indicates that the function ran successfully.
      ! Other ut_status codes indicate cause of failure.
      integer(c_int) function ut_are_convertible(unit1, unit2) &
         bind(c, name='ut_are_convertible')
         import :: c_int, c_ptr
         type(c_ptr), value, intent(in) :: unit1, unit2
      end function ut_are_convertible

      ! Return type(c_ptr) to cv_converter
      ! Use ut_get_status to check error condition. 
      ! UT_SUCCESS indicates that the function ran successfully.
      ! Other ut_status codes indicate cause of failure.
      type(c_ptr) function ut_get_converter(from, to) &
         bind(c, name='ut_get_converter')
         import :: c_ptr
         type(c_ptr), value, intent(in) :: from, to
      end function ut_get_converter

      ! Use converter to convert value_
      ! Use ut_get_status to check error condition. 
      ! UT_SUCCESS indicates that the function ran successfully.
      ! Other ut_status codes indicate cause of failure.
      real(c_float) function cv_convert_float(converter, value_) bind(c)
         import :: c_ptr, c_float
         type(c_ptr), value, intent(in) :: converter
         real(c_float), value, intent(in) :: value_
      end function cv_convert_float

      ! Use converter to convert value_
      ! Use ut_get_status to check error condition. 
      ! UT_SUCCESS indicates that the function ran successfully.
      ! Other ut_status codes indicate cause of failure.
      real(c_double) function cv_convert_double(converter, value_) bind(c)
         import :: c_ptr, c_double
         type(c_ptr), value, intent(in) :: converter
         real(c_double), value, intent(in) :: value_
      end function cv_convert_double

      ! Use converter to convert in_ and put it in out_.
      ! Use ut_get_status to check error condition. 
      ! UT_SUCCESS indicates that the function ran successfully.
      ! Other ut_status codes indicate cause of failure.
      subroutine cv_convert_doubles(converter, in_, count_, out_) &
         bind(c, name='cv_convert_doubles')
         import :: c_double, c_int, c_ptr
         type(c_ptr), value, intent(in) :: converter
         real(c_double), intent(in) :: in_(*)
         integer(c_int), value, intent(in) :: count_
         real(c_double), intent(out) :: out_(count_)
      end subroutine cv_convert_doubles

      ! Use converter to convert in_ and put it in out_.
      ! Use ut_get_status to check error condition. 
      ! UT_SUCCESS indicates that the function ran successfully.
      ! Other ut_status codes indicate cause of failure.
      subroutine cv_convert_floats(converter, in_, count_, out_) &
         bind(c, name='cv_convert_floats')
         import :: c_ptr, c_float, c_int
         type(c_ptr), value, intent(in) :: converter
         real(c_float), intent(in) :: in_(*)
         integer(c_int), value, intent(in) :: count_
         real(c_float), intent(out) :: out_(count_)
      end subroutine cv_convert_floats

      ! Return type(c_ptr) to ut_unit
      ! UT_SUCCESS indicates that the function ran successfully.
      ! Other ut_status codes indicate cause of failure.
      ! Use ut_get_status to check error condition. 
      type(c_ptr) function ut_parse(system, string, encoding) &
         bind(c, name='ut_parse')
         import :: c_ptr, c_char, ut_encoding
         type(c_ptr), value, intent(in) :: system
         character(c_char), intent(in) :: string(*)
         integer(ut_encoding), value, intent(in) :: encoding
      end function ut_parse

      ! Free memory for ut_system
      subroutine ut_free_system(system) bind(c, name='ut_free_system')
         import :: c_ptr
         type(c_ptr), value :: system
      end subroutine ut_free_system

      ! Free memory for ut_unit
      subroutine ut_free(unit) bind(c, name='ut_free')
         import :: c_ptr
         type(c_ptr), value :: unit
      end subroutine ut_free

      ! Free memory for cv_converter
      subroutine cv_free(conv) bind(c, name='cv_free')
         import :: c_ptr
         type(c_ptr), value :: conv
      end subroutine cv_free

      ! Set udunits error handler to ut_ignore (do nothing)
      subroutine ut_set_ignore_error_message_handler() &
            bind(c, name='ut_set_ignore_error_message_handler')
      end subroutine ut_set_ignore_error_message_handler

   end interface

end module ud2f_interfaces