ecpint.F90 Source File


Files dependent on this one

sourcefile~~ecpint.f90~~AfferentGraph sourcefile~ecpint.f90 ecpint.F90 sourcefile~ecp.f90 ecp.F90 sourcefile~ecp.f90->sourcefile~ecpint.f90 sourcefile~grd1.f90 grd1.F90 sourcefile~grd1.f90->sourcefile~ecp.f90 sourcefile~int1.f90 int1.F90 sourcefile~int1.f90->sourcefile~ecp.f90 sourcefile~electric_moments.f90 electric_moments.F90 sourcefile~electric_moments.f90->sourcefile~int1.f90 sourcefile~get_basis_overlap.f90 get_basis_overlap.F90 sourcefile~get_basis_overlap.f90->sourcefile~int1.f90 sourcefile~hf_gradient.f90 hf_gradient.F90 sourcefile~hf_gradient.f90->sourcefile~grd1.f90 sourcefile~huckel.f90 huckel.F90 sourcefile~huckel.f90->sourcefile~int1.f90 sourcefile~int1e.f90 int1e.F90 sourcefile~int1e.f90->sourcefile~int1.f90 sourcefile~resp.f90 resp.F90 sourcefile~resp.f90->sourcefile~int1.f90 sourcefile~tdhf_energy.f90 tdhf_energy.F90 sourcefile~tdhf_energy.f90->sourcefile~int1.f90 sourcefile~tdhf_gradient.f90 tdhf_gradient.F90 sourcefile~tdhf_gradient.f90->sourcefile~grd1.f90 sourcefile~tdhf_sf_lib.f90 tdhf_sf_lib.F90 sourcefile~tdhf_sf_lib.f90->sourcefile~int1.f90 sourcefile~guess_huckel.f90 guess_huckel.F90 sourcefile~guess_huckel.f90->sourcefile~huckel.f90 sourcefile~tdhf_mrsf_energy.f90 tdhf_mrsf_energy.F90 sourcefile~tdhf_mrsf_energy.f90->sourcefile~tdhf_sf_lib.f90 sourcefile~tdhf_sf_energy.f90 tdhf_sf_energy.F90 sourcefile~tdhf_sf_energy.f90->sourcefile~tdhf_sf_lib.f90 sourcefile~tdhf_z_vector.f90 tdhf_z_vector.F90 sourcefile~tdhf_z_vector.f90->sourcefile~tdhf_sf_lib.f90

Source Code

module libecp_result
    use iso_c_binding
    implicit none

    type, bind(c) :: ecp_result
        type(c_ptr) :: data
        integer(c_int) :: size
    end type ecp_result
end module libecp_result

module libecpint_wrapper
    use iso_c_binding, only : c_int, c_double, c_ptr
    implicit none

    interface
        function init_integrator(num_gaussians, g_coords, g_exps, g_coefs, &
                                 g_ams, g_lengths) bind(c, name="init_integrator")
            use iso_c_binding, only : c_int, c_double, c_ptr
            type(c_ptr) :: init_integrator
            integer(c_int), value :: num_gaussians
            real(c_double), dimension(*), intent(in) :: g_coords
            real(c_double), dimension(*), intent(in) :: g_exps
            real(c_double), dimension(*), intent(in) :: g_coefs
!            real(c_double), dimension(*) :: g_coords, g_exps, g_coefs
            integer(c_int), dimension(*) :: g_ams, g_lengths
        end function init_integrator

        subroutine set_ecp_basis(integrator, num_ecps, u_coords, u_exps, &
                                 u_coefs, u_ams, u_ns, u_lengths) &
                                 bind(c, name="set_ecp_basis")
            use iso_c_binding, only : c_int, c_double, c_ptr
            type(c_ptr), value :: integrator
            integer(c_int), value :: num_ecps
            real(c_double), dimension(*) :: u_coords, u_exps, u_coefs
            integer(c_int), dimension(*) :: u_ams, u_ns, u_lengths
        end subroutine set_ecp_basis

        subroutine init_integrator_instance(integrator, deriv_order) &
                   bind(c, name="init_integrator_instance")
            use iso_c_binding, only : c_int, c_ptr
            type(c_ptr), value :: integrator
            integer(c_int), value :: deriv_order
        end subroutine init_integrator_instance

        function compute_integrals(integrator) bind(c, name="compute_integrals")
            use iso_c_binding, only : c_ptr
            use libecp_result
            type(ecp_result) :: compute_integrals
            type(c_ptr), value :: integrator
        end function compute_integrals

        function compute_first_derivs(integrator) bind(c, name="compute_first_derivs")
            use iso_c_binding, only : c_ptr
            use libecp_result
            type(ecp_result) :: compute_first_derivs
            type(c_ptr), value :: integrator
        end function compute_first_derivs

        subroutine free_integrator(integrator) bind(c, name="free_integrator")
            use iso_c_binding, only : c_ptr
            type(c_ptr), value :: integrator
        end subroutine free_integrator

        subroutine free_result(result) bind(c, name="free_result")
            use libecp_result
            type(ecp_result), value :: result
        end subroutine free_result
    end interface
end module libecpint_wrapper