| 7 |
|
INTEGER, PARAMETER:: LAGUERRE = 3 |
| 8 |
|
INTEGER, PARAMETER:: HERMITE = 4 |
| 9 |
|
|
| 10 |
< |
public :: do_shape_pair |
| 11 |
< |
|
| 10 |
> |
contains |
| 11 |
|
|
| 12 |
|
SUBROUTINE Get_Associated_Legendre(x, l, m, lmax, plm, dlm) |
| 13 |
|
|
| 109 |
|
real(kind=8), intent(in) :: x |
| 110 |
|
integer, intent(in):: m |
| 111 |
|
integer, intent(in):: function_type |
| 112 |
< |
real(kind=8), dimension(0:n), intent(inout) :: pl, dpl |
| 112 |
> |
real(kind=8), dimension(0:m), intent(inout) :: pl, dpl |
| 113 |
|
|
| 114 |
< |
real(kind=8) :: a, b, c, y0, y1, dy0, dy1 |
| 114 |
> |
real(kind=8) :: a, b, c, y0, y1, dy0, dy1, yn, dyn |
| 115 |
> |
integer :: k |
| 116 |
|
|
| 117 |
|
A = 2.0D0 |
| 118 |
|
B = 0.0D0 |
| 136 |
|
PL(1) = 1.0D0-X |
| 137 |
|
DPL(1) = -1.0D0 |
| 138 |
|
ENDIF |
| 139 |
< |
DO K = 2, N |
| 139 |
> |
DO K = 2, m |
| 140 |
|
IF (function_type.EQ.LAGUERRE) THEN |
| 141 |
|
A = -1.0D0/K |
| 142 |
|
B = 2.0D0+A |
| 156 |
|
RETURN |
| 157 |
|
|
| 158 |
|
end subroutine Get_Orthogonal_Polynomial |
| 159 |
+ |
|
| 160 |
+ |
end module shapes |