ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-4/src/UseTheForce/DarkSide/switcheroo.F90
(Generate patch)

Comparing trunk/OOPSE-4/src/UseTheForce/DarkSide/switcheroo.F90 (file contents):
Revision 2715 by chrisfen, Sun Apr 16 02:51:16 2006 UTC vs.
Revision 2756 by gezelter, Wed May 17 15:37:15 2006 UTC

# Line 38 | Line 38
38   !! University of Notre Dame has been advised of the possibility of
39   !! such damages.
40   !!
41 <
41 > !!$
42   module switcheroo
43  
44    use definitions
45    use interpolation
46 +  use status
47  
48    implicit none
49    PRIVATE
50  
51   #define __FORTRAN90
51 #include "UseTheForce/fSwitchingFunction.h"
52   #include "UseTheForce/DarkSide/fSwitchingFunctionType.h"
53 +  
54 +  !! number of points for the spline approximations
55 +  INTEGER, PARAMETER :: np = 150
56  
57 <  real ( kind = dp ), dimension(NSWITCHTYPES) :: rin
58 <  real ( kind = dp ), dimension(NSWITCHTYPES) :: rout
59 <  real ( kind = dp ), dimension(NSWITCHTYPES) :: rin2
60 <  real ( kind = dp ), dimension(NSWITCHTYPES) :: rout2
58 <  real ( kind = dp ), save :: c0, c1, c2, c3, c4, c5
57 >  real ( kind = dp ), save :: rin
58 >  real ( kind = dp ), save :: rout
59 >  real ( kind = dp ), save :: rin2
60 >  real ( kind = dp ), save :: rout2
61  
62 <  logical, dimension(NSWITCHTYPES) :: isOK
63 <  logical, save :: haveFunctionType = .false.
62 <  logical, save :: haveSqrtSpline = .false.
63 <  logical, save :: useSpline = .true.
62 >  logical, save :: haveSplines = .false.
63 >  logical, save :: switchIsCubic = .true.
64    integer, save :: functionType = CUBIC
65  
66 +  ! spline structures
67 +  type(cubicSpline), save :: r2Spline
68 +  type(cubicSpline), save :: switchSpline
69  
70 <  ! spline variables
68 <  type(cubicSpline), save :: scoef
69 <  real ( kind = dp ), dimension(SPLINE_SEGMENTS) :: xValues
70 <  real ( kind = dp ), dimension(SPLINE_SEGMENTS) :: yValues
71 <  real ( kind = dp ), save :: dSqrt1, dSqrtN, range, dX
72 <  real ( kind = dp ), save :: lowerBound
73 <  logical, save :: uniformSpline = .true.
74 <
70 >  public::set_switch_type
71    public::set_switch
76  public::set_function_type
72    public::get_switch
73 +  public::delete_switch
74  
75   contains
76  
77 <  subroutine set_switch(SwitchType, rinner, router)
77 >  subroutine set_switch(rinner, router)
78  
79      real ( kind = dp ), intent(in):: rinner, router
80 <    integer, intent(in) :: SwitchType
80 >    real ( kind = dp ), dimension(np) :: xvals, yvals
81 >    real ( kind = dp ), dimension(2) :: rCubVals, sCubVals
82 >    real ( kind = dp ) :: rval, rval2, rval3, rval4, rval5
83 >    real ( kind = dp ) :: rvaldi, rvaldi2, rvaldi3, rvaldi4, rvaldi5
84 >    real ( kind = dp ) :: c0, c3, c4, c5, dx, r, r2
85      integer :: i
86  
87 <    if (SwitchType .gt. NSWITCHTYPES) then
88 <       write(default_error, *) &
89 <            'set_switch:  not that many switch types! '
87 >    if (router .lt. rinner) then
88 >       call handleError("set_switch", "router is less than rinner")
89         return
90      endif
91  
92 <    isOK(SwitchType) = .false.
93 <
95 <    if (router .lt. rinner) then
96 <       write(default_error, *) &
97 <            'set_switch:  router is less than rinner '
92 >    if ((router .lt. 0.0_dp) .or. (rinner .lt. 0.0_dp))  then
93 >       call handleError("set_switch", "one of the switches is negative!")
94         return
95      endif
96  
97 <    if ((router .lt. 0.0d0) .or. (rinner .lt. 0.0d0))  then
98 <       write(default_error, *) &
99 <            'set_switch:  one of the switches is negative!'
97 >    rin = rinner
98 >    rout = router
99 >    rin2 = rinner * rinner
100 >    rout2 = router * router
101 >
102 >    if ((router-rinner) .lt. 1e-8)  then
103 >       ! no reason to set up splines if the switching region is tiny
104         return
105      endif
106  
107 <    rin(SwitchType) = rinner
108 <    rout(SwitchType) = router
109 <    rin2(SwitchType) = rinner * rinner
110 <    rout2(SwitchType) = router * router
111 <    isOK(SwitchType) = .true.
107 >    dx = (rout2-rin2) / dble(np-1)
108 >    
109 >    do i = 1, np
110 >       r2 = rin2 + dble(i-1)*dx
111 >       xvals(i) = r2
112 >       yvals(i) = sqrt(r2)
113 >    enddo
114  
115 <    if (.not.haveSqrtSpline) then
116 <       ! fill arrays for building the spline
117 <       lowerBound = 1.0d0 ! the smallest value expected for r2
118 <       range = rout2(SwitchType) - lowerBound
119 <       dX = range / (SPLINE_SEGMENTS - 1)
120 <      
121 <       ! the spline is bracketed by lowerBound and rout2 endpoints
122 <       xValues(1) = lowerBound
123 <       yValues(1) = dsqrt(lowerBound)
124 <       do i = 1, SPLINE_SEGMENTS-1
125 <          xValues(i+1) = i * dX
126 <          yValues(i+1) = dsqrt( i * dX )
115 >    call newSpline(r2spline, xvals, yvals, .true.)
116 >
117 >    if (functionType .eq. FIFTH_ORDER_POLY) then
118 >       c0 = 1.0_dp
119 >       c3 = -10.0_dp
120 >       c4 = 15.0_dp
121 >       c5 = -6.0_dp
122 >
123 >       dx = (rout-rin) / dble(np-1)
124 >    
125 >       do i = 1, np
126 >          r = rin + dble(i-1)*dx
127 >          xvals(i) = r
128 >
129 >          rval = ( r - rin )
130 >          rval2 = rval*rval
131 >          rval3 = rval2*rval
132 >          rval4 = rval2*rval2
133 >          rval5 = rval3*rval2
134 >          rvaldi = 1.0_dp/( rout - rin )
135 >          rvaldi2 = rvaldi*rvaldi
136 >          rvaldi3 = rvaldi2*rvaldi
137 >          rvaldi4 = rvaldi2*rvaldi2
138 >          rvaldi5 = rvaldi3*rvaldi2
139 >          yvals(i)= c0 + c3*rval3*rvaldi3 + c4*rval4*rvaldi4 + c5*rval5*rvaldi5
140         enddo
141        
142 <       ! set the endpoint derivatives
128 <       dSqrt1 = 1 / ( 2.0d0 * dsqrt( xValues(1) ) )
129 <       dSqrtN = 1 / ( 2.0d0 * dsqrt( xValues(SPLINE_SEGMENTS) ) )
130 <
131 <       ! call newSpline to fill the coefficient array
132 <       call newSpline(scoef, xValues, yValues, dSqrt1, dSqrtN, uniformSpline)
142 >       call newSpline(switchSpline, xvals, yvals, .true.)
143        
144 +       switchIsCubic = .false.
145 +    else
146 +       rCubVals(1) = rin
147 +       rCubVals(2) = rout
148 +       sCubVals(1) = 1.0_dp
149 +       sCubVals(2) = 0.0_dp      
150 +       call newSpline(switchSpline, rCubVals, sCubVals, .true.)
151      endif
152      
153 +    haveSplines = .true.
154 +    return
155    end subroutine set_switch
156  
157 <  subroutine set_function_type(functionForm)
157 >  subroutine set_switch_type(functionForm)
158      integer, intent(in) :: functionForm    
159      functionType = functionForm
160  
161 <    if (functionType .eq. FIFTH_ORDER_POLY) then
162 <       c0 = 1.0d0
163 <       c1 = 0.0d0
164 <       c2 = 0.0d0
165 <       c3 = -10.0d0
166 <       c4 = 15.0d0
167 <       c5 = -6.0d0
161 >    if ((functionType.eq.FIFTH_ORDER_POLY).or.(functionType.eq.CUBIC)) then
162 >       if (haveSplines) then
163 >          call delete_switch()
164 >          call set_switch(rin, rout)
165 >       endif
166 >    else
167 >       call handleError("set_switch_type", &
168 >            "Unknown type of switching function!")
169 >       return      
170      endif
171 <  end subroutine set_function_type
171 >  end subroutine set_switch_type
172 >  
173 >  subroutine delete_switch()
174 >    call deleteSpline(switchSpline)
175 >    call deleteSpline(r2spline)
176 >    return
177 >  end subroutine delete_switch
178 >  
179 >  subroutine get_switch(r2, sw, dswdr, r, in_switching_region)
180  
152  subroutine get_switch(r2, sw, dswdr, r, SwitchType, in_switching_region)
153
181      real( kind = dp ), intent(in) :: r2
182      real( kind = dp ), intent(inout) :: sw, dswdr, r
156    real( kind = dp ) :: ron, roff
157    real( kind = dp ) :: rval, rval2, rval3, rval4, rval5
158    real( kind = dp ) :: rvaldi, rvaldi2, rvaldi3, rvaldi4, rvaldi5
159    integer, intent(in)    :: SwitchType
183      logical, intent(inout) :: in_switching_region
184 +    integer :: j
185 +    real ( kind = dp ) :: a, b, c, d, dx
186  
187 <    sw = 0.0d0
188 <    dswdr = 0.0d0
187 >    sw = 1.0_dp
188 >    dswdr = 0.0_dp
189      in_switching_region = .false.
190  
191 <    if (.not.isOK(SwitchType)) then
192 <       write(default_error, *) &
168 <            'get_switch:  this switching function has not been set up!'
169 <       return
170 <    endif
191 >    if (r2.gt.rin2) then
192 >       if (r2.gt.rout2) then
193  
194 <    if (r2.lt.rout2(SwitchType)) then
195 <       if (r2.lt.rin2(SwitchType)) then
174 <
175 <          sw = 1.0d0
176 <          dswdr = 0.0d0
194 >          sw = 0.0_dp
195 >          dswdr = 0.0_dp
196            return
197 <
198 <       else
199 <          if (useSpline) then
200 <             call lookup_uniform_spline(scoef, r2, r)
197 >          
198 >       else        
199 >          
200 >          call lookupUniformSpline(r2Spline, r2, r)
201 >          if (switchIsCubic) then
202 >             ! super zippy automated use of precomputed spline coefficients
203 >             dx = r - rin
204 >             sw = switchSpline%y(1) + dx*(dx*(switchSpline%c(1) + &
205 >                  dx*switchSpline%d(1)))
206 >             dswdr = dx*(2.0_dp * switchSpline%c(1) + &
207 >                  3.0_dp * dx * switchSpline%d(1))
208            else
209 <             r = dsqrt(r2)
209 >             call lookupUniformSpline1d(switchSpline, r, sw, dswdr)
210            endif
211 <
186 <          ron = rin(SwitchType)
187 <          roff = rout(SwitchType)
188 <
189 <          if (functionType .eq. FIFTH_ORDER_POLY) then
190 <             rval = ( r - ron )
191 <             rval2 = rval*rval
192 <             rval3 = rval2*rval
193 <             rval4 = rval2*rval2
194 <             rval5 = rval3*rval2
195 <             rvaldi = 1.0d0/( roff - ron )
196 <             rvaldi2 = rvaldi*rvaldi
197 <             rvaldi3 = rvaldi2*rvaldi
198 <             rvaldi4 = rvaldi2*rvaldi2
199 <             rvaldi5 = rvaldi3*rvaldi2
200 <             sw = c0 + c1*rval*rvaldi + c2*rval2*rvaldi2 + c3*rval3*rvaldi3 &
201 <                  + c4*rval4*rvaldi4 + c5*rval5*rvaldi5
202 <             dswdr = c1*rvaldi + 2.0d0*c2*rval*rvaldi2 &
203 <                  + 3.0d0*c3*rval2*rvaldi3 + 4.0d0*c4*rval3*rvaldi4 &
204 <                  + 5.0d0*c5*rval4*rvaldi5
205 <
206 <          else
207 <             sw = (roff + 2.0d0*r - 3.0d0*ron)*(roff-r)**2/ ((roff-ron)**3)
208 <             dswdr = 6.0d0*(r*r - r*ron - r*roff +roff*ron)/((roff-ron)**3)
209 <
210 <          endif
211 >          
212            in_switching_region = .true.
213 +          
214            return          
215         endif
216      else
217         return
218      endif
219 <
219 >    
220    end subroutine get_switch
221  
222   end module switcheroo

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines