Page MenuHomeHEPForge

No OneTemporary

Index: trunk/src/lhapdf/lhapdf.f90
===================================================================
--- trunk/src/lhapdf/lhapdf.f90 (revision 5913)
+++ trunk/src/lhapdf/lhapdf.f90 (revision 5914)
@@ -1,273 +1,273 @@
module lhapdf
use, intrinsic :: iso_c_binding
use kinds
implicit none
private
! Public types
public :: lhapdf_pdf_t
type :: lhapdf_pdf_t
private
type(c_ptr) :: cptr
contains
procedure :: init => lhapdf_pdf_init
procedure :: getxmin => lhapdf_getxmin
procedure :: getxmax => lhapdf_getxmax
procedure :: getq2min => lhapdf_getq2min
procedure :: getq2max => lhapdf_getq2max
procedure :: has_photon => lhapdf_hasphoton
procedure :: evolve_pdfm => lhapdf_evolve_pdfm
procedure :: evolve_pdfphotonm => lhapdf_evolve_pdfphotonm
procedure :: evolve_pdfpm => lhapdf_evolve_pdfpm
procedure :: get_qmass => lhapdf_get_qmass
procedure :: num_pdfm => lhapdf_num_pdfm
procedure :: alphas_pdf => lhapdf_alphas_pdf
end type lhapdf_pdf_t
! Interface for generic operators
interface
function lhapdf_init_pdf (setname, imem) bind (C) result (pdf)
import
integer(c_int), intent(in), value :: imem
character(len=1, kind=c_char), dimension(*), intent(in) :: setname
type(c_ptr) :: pdf
end function lhapdf_init_pdf
end interface
interface
subroutine lhapdf_pdf_delete (pdf) bind (C)
import
type(c_ptr), value :: pdf
end subroutine lhapdf_pdf_delete
end interface
interface
subroutine lhapdf_pdf_getxmin (pdf, xmin) bind (C)
import
type(c_ptr), intent(in), value :: pdf
real(c_double), intent(out) :: xmin
end subroutine lhapdf_pdf_getxmin
end interface
interface
subroutine lhapdf_pdf_getxmax (pdf, xmax) bind (C)
import
type(c_ptr), intent(in), value :: pdf
real(c_double), intent(out) :: xmax
end subroutine lhapdf_pdf_getxmax
end interface
interface
subroutine lhapdf_pdf_getq2min (pdf, q2min) bind (C)
import
type(c_ptr), intent(in), value :: pdf
real(c_double), intent(out) :: q2min
end subroutine lhapdf_pdf_getq2min
end interface
interface
subroutine lhapdf_pdf_getq2max (pdf, q2max) bind (C)
import
type(c_ptr), intent(in), value :: pdf
real(c_double), intent(out) :: q2max
end subroutine lhapdf_pdf_getq2max
end interface
interface
function lhapdf_has_photon (pdf) bind (C) result (flag)
import
type(c_ptr), intent(in), value :: pdf
logical(c_bool) :: flag
end function lhapdf_has_photon
end interface
interface
subroutine lhapdf_evolvepdfm (pdf, x, q, ff) bind (C)
import
type(c_ptr), intent(in), value :: pdf
real(c_double), intent(in), value :: x, q
real(c_double), dimension(-6:6), intent(out) :: ff
end subroutine lhapdf_evolvepdfm
end interface
interface
subroutine lhapdf_evolvepdfphotonm (pdf, x, q, ff, fphot) bind (C)
import
type(c_ptr), intent(in), value :: pdf
real(c_double), intent(in), value :: x, q
real(c_double), dimension(-6:6), intent(out) :: ff
real(c_double), intent(out) :: fphot
end subroutine lhapdf_evolvepdfphotonm
end interface
interface
subroutine lhapdf_evolvepdfpm (pdf, x, q, s, scheme, ff) bind (C)
import
type(c_ptr), intent(in), value :: pdf
integer(c_int), intent(in), value :: scheme
real(c_double), intent(in), value :: x, q, s
real(c_double), dimension(-6:6), intent(out) :: ff
end subroutine lhapdf_evolvepdfpm
end interface
interface
subroutine lhapdf_getqmass (pdf, nf, mass) bind (C)
import
type(c_ptr), intent(in), value :: pdf
integer(c_int), intent(in), value :: nf
real(c_double), intent(out) :: mass
end subroutine lhapdf_getqmass
end interface
interface
subroutine lhapdf_numpdfm (pdf, numpdf) bind (C)
import
type(c_ptr), intent(in), value :: pdf
integer(c_int), intent(out) :: numpdf
end subroutine lhapdf_numpdfm
end interface
interface
- subroutine lhapdf_alphaspdf (pdf, q, as) bind (C)
+ function lhapdf_alphaspdf (pdf, q) bind (C) result (as)
import
type(c_ptr), intent(in), value :: pdf
real(c_double), intent(in) :: q
- real(c_double), intent(out) :: as
- end subroutine lhapdf_alphaspdf
+ real(c_double) :: as
+ end function lhapdf_alphaspdf
end interface
contains
subroutine lhapdf_pdf_init (pdf, setname, imem)
class(lhapdf_pdf_t), intent(out) :: pdf
character(*), intent(in) :: setname
integer, intent(in) :: imem
character(len=1, kind=c_char), dimension(len(setname)) :: pdf_setname
integer(c_int) :: pdf_imem
integer :: i, strlen
strlen = len(setname)
forall (i=1:strlen)
pdf_setname(i) = setname(i:i)
end forall
pdf_setname(strlen+1) = c_null_char
pdf_imem = imem
pdf%cptr = lhapdf_init_pdf (pdf_setname, pdf_imem)
end subroutine lhapdf_pdf_init
function lhapdf_getxmin (pdf) result (xmin)
class(lhapdf_pdf_t), intent(inout) :: pdf
real(c_double) :: c_xmin
real(double) :: xmin
call lhapdf_pdf_getxmin (pdf%cptr, c_xmin)
xmin = c_xmin
end function lhapdf_getxmin
function lhapdf_getxmax (pdf) result (xmax)
class(lhapdf_pdf_t), intent(inout) :: pdf
real(c_double) :: c_xmax
real(double) :: xmax
call lhapdf_pdf_getxmax (pdf%cptr, c_xmax)
xmax = c_xmax
end function lhapdf_getxmax
function lhapdf_getq2min (pdf) result (q2min)
class(lhapdf_pdf_t), intent(inout) :: pdf
real(c_double) :: c_q2min
real(double) :: q2min
call lhapdf_pdf_getq2min (pdf%cptr, c_q2min)
q2min = c_q2min
end function lhapdf_getq2min
function lhapdf_getq2max (pdf) result (q2max)
class(lhapdf_pdf_t), intent(inout) :: pdf
real(c_double) :: c_q2max
real(double) :: q2max
call lhapdf_pdf_getq2max (pdf%cptr, c_q2max)
q2max = c_q2max
end function lhapdf_getq2max
function lhapdf_hasphoton (pdf) result (flag)
class(lhapdf_pdf_t), intent(inout) :: pdf
logical(c_bool) :: c_flag
logical :: flag
c_flag = lhapdf_has_photon (pdf%cptr)
flag = c_flag
end function lhapdf_hasphoton
subroutine lhapdf_evolve_pdfm (pdf, x, q, ff)
class(lhapdf_pdf_t), intent(inout) :: pdf
real(double), intent(in) :: x, q
real(double), dimension(-6:6), intent(out) :: ff
real(c_double) :: c_x, c_q
real(c_double), dimension(-6:6) :: c_ff
c_x = x
c_q = q
call lhapdf_evolvepdfm (pdf%cptr, c_x, c_q, c_ff)
ff = c_ff
end subroutine lhapdf_evolve_pdfm
subroutine lhapdf_evolve_pdfphotonm (pdf, x, q, ff, fphot)
class(lhapdf_pdf_t), intent(inout) :: pdf
real(double), intent(in) :: x, q
real(double), dimension(-6:6), intent(out) :: ff
real(double), intent(out) :: fphot
real(c_double) :: c_x, c_q, c_fphot
real(c_double), dimension(-6:6) :: c_ff
c_x = x
c_q = q
call lhapdf_evolvepdfphotonm &
(pdf%cptr, c_x, c_q, c_ff, c_fphot)
ff = c_ff
fphot = c_fphot
end subroutine lhapdf_evolve_pdfphotonm
subroutine lhapdf_evolve_pdfpm (pdf, x, q, s, scheme, ff)
class(lhapdf_pdf_t), intent(inout) :: pdf
real(double), intent(in) :: x, q, s
integer, intent(in) :: scheme
real(double), dimension(-6:6), intent(out) :: ff
real(c_double) :: c_x, c_q, c_s
integer(c_int) :: c_scheme
real(c_double), dimension(-6:6) :: c_ff
c_x = x
c_q = q
c_s = s
c_scheme = scheme
call lhapdf_evolvepdfpm (pdf%cptr, &
c_x, c_q, c_s, c_scheme, c_ff)
ff = c_ff
end subroutine lhapdf_evolve_pdfpm
function lhapdf_get_qmass (pdf, nf) result (mass)
class(lhapdf_pdf_t), intent(inout) :: pdf
integer, intent(in) :: nf
real(double) :: mass
real(c_double) :: c_mass
integer(c_int) :: c_nf
c_nf = nf
call lhapdf_getqmass (pdf%cptr, c_nf, c_mass)
mass = c_mass
end function lhapdf_get_qmass
function lhapdf_num_pdfm (pdf) result (numpdf)
class(lhapdf_pdf_t), intent(inout) :: pdf
integer :: numpdf
integer(c_int) :: c_numpdf
call lhapdf_numpdfm (pdf%cptr, c_numpdf)
numpdf = c_numpdf
end function lhapdf_num_pdfm
function lhapdf_alphas_pdf (pdf, q) result (as)
- class(lhapdf_pdf_t), intent(in) :: pdf
+ class(lhapdf_pdf_t), intent(in), target :: pdf
real(double), intent(in) :: q
real(double) :: as
- real(c_double) :: c_q, c_as
- call lhapdf_alphaspdf (pdf%cptr, c_q, c_as)
- as = c_as
+ real(c_double) :: c_q = 0
+ c_q = q
+ as = lhapdf_alphaspdf (pdf%cptr, c_q)
end function lhapdf_alphas_pdf
end module lhapdf

File Metadata

Mime Type
text/x-diff
Expires
Tue, Nov 19, 9:22 PM (1 d, 48 m)
Storage Engine
blob
Storage Format
Raw Data
Storage Handle
3806257
Default Alt Text
(8 KB)

Event Timeline