V3FIT
coordinate_utilities.f
Go to the documentation of this file.
1 !*******************************************************************************
4 !
5 ! Note separating the Doxygen comment block here so detailed decription is
6 ! found in the Module not the file.
7 !
10 !*******************************************************************************
11 
13  USE stel_kinds
14  USE stel_constants
15 
16 !*******************************************************************************
17 ! INTERFACE BLOCKS
18 !*******************************************************************************
21  PRIVATE :: check
22 
23  CONTAINS
24 
25 !*******************************************************************************
26 ! UTILITY SUBROUTINES
27 !*******************************************************************************
28 !-------------------------------------------------------------------------------
38 !-------------------------------------------------------------------------------
39  PURE FUNCTION cart_to_cyl(cart)
40 
41  IMPLICIT NONE
42 
43 ! Declare Arguments
44  REAL (rprec), DIMENSION(3) :: cart_to_cyl
45  REAL (rprec), DIMENSION(3), INTENT(in) :: cart
46 
47 ! Start of executable code
48  cart_to_cyl(1) = sqrt(dot_product(cart(1:2), cart(1:2)))
49  cart_to_cyl(2) = atan2(cart(2), cart(1))
50  cart_to_cyl(3) = cart(3)
51 
52  END FUNCTION
53 
54 !-------------------------------------------------------------------------------
65 !-------------------------------------------------------------------------------
66  PURE FUNCTION cyl_to_cart(cyl)
67 
68  IMPLICIT NONE
69 
70 ! Declare Arguments
71  REAL (rprec), DIMENSION(3) :: cyl_to_cart
72  REAL (rprec), DIMENSION(3), INTENT(in) :: cyl
73 
74 ! Start of executable code
75  cyl_to_cart(1) = cyl(1)*cos(cyl(2))
76  cyl_to_cart(2) = cyl(1)*sin(cyl(2))
77  cyl_to_cart(3) = cyl(3)
78 
79  END FUNCTION
80 
81 !-------------------------------------------------------------------------------
93 !-------------------------------------------------------------------------------
94  PURE FUNCTION cyl_to_cart_vec(cyl, vec)
95 
96  IMPLICIT NONE
97 
98 ! Declare Arguments
99  REAL (rprec), DIMENSION(3) :: cyl_to_cart_vec
100  REAL (rprec), DIMENSION(3), INTENT(in) :: cyl
101  REAL (rprec), DIMENSION(3), INTENT(in) :: vec
102 
103 ! Start of executable code
104  cyl_to_cart_vec(1) = cos(cyl(2))*vec(1) - sin(cyl(2))*vec(2)
105  cyl_to_cart_vec(2) = sin(cyl(2))*vec(1) + cos(cyl(2))*vec(2)
106  cyl_to_cart_vec(3) = vec(3)
107 
108  END FUNCTION
109 
110 !-------------------------------------------------------------------------------
124 !-------------------------------------------------------------------------------
125  PURE FUNCTION cart_to_cyl_vec(cart, vec)
126 
127  IMPLICIT NONE
128 
129 ! Declare Arguments
130  REAL (rprec), DIMENSION(3) :: cart_to_cyl_vec
131  REAL (rprec), DIMENSION(3), INTENT(in) :: cart
132  REAL (rprec), DIMENSION(3), INTENT(in) :: vec
133 
134 ! local variables
135  REAL (rprec) :: r
136 
137 ! Start of executable code
138  r = sqrt(dot_product(cart(1:2), cart(1:2)))
139 
140  cart_to_cyl_vec(1) = ( cart(1)*vec(1) + cart(2)*vec(2))/r
141  cart_to_cyl_vec(2) = (-cart(2)*vec(1) + cart(1)*vec(2))/r
142  cart_to_cyl_vec(3) = vec(3)
143 
144  END FUNCTION
145 
146 !*******************************************************************************
147 ! UNIT TESTS
148 !*******************************************************************************
149 !-------------------------------------------------------------------------------
155 !-------------------------------------------------------------------------------
156  FUNCTION cood_utils_test()
157 
158  IMPLICIT NONE
159 
160 ! Declare Arguments
161  LOGICAL :: cood_utils_test
162 
163 ! local variables
164  REAL (rprec), DIMENSION(3) :: result
165 
166 ! Start of executable code
167 ! Test cart_to_cyl function. cart(0,0,1) = cyl(0,0,1)
168  result = cart_to_cyl((/ 0.0d+0, 0.0d+0, 1.0d+0 /))
169  cood_utils_test = check(0.0d+0, result(1), 1, "cart_to_cyl")
170  IF (.not.cood_utils_test) RETURN
171  cood_utils_test = check(0.0d+0, result(2), 2, "cart_to_cyl")
172  IF (.not.cood_utils_test) RETURN
173  cood_utils_test = check(1.0d+0, result(3), 3, "cart_to_cyl")
174  IF (.not.cood_utils_test) RETURN
175 
176 ! Test cart_to_cyl function. cart(-1,0,0) = cyl(1,Pi,0)
177  result = cart_to_cyl((/ -1.0d+0, 0.0d+0, 0.0d+0 /))
178  cood_utils_test = check(1.0d+0, result(1), 4, "cart_to_cyl")
179  IF (.not.cood_utils_test) RETURN
180  cood_utils_test = check(pi, result(2), 5, "cart_to_cyl")
181  IF (.not.cood_utils_test) RETURN
182  cood_utils_test = check(0.0d+0, result(3), 6, "cart_to_cyl")
183  IF (.not.cood_utils_test) RETURN
184 
185 ! Test cart_to_cyl function. cart(-1,0,-1) = cyl(1,Pi/2,-1)
186  result = cart_to_cyl((/ 0.0d+0, 1.0d+0, -1.0d+0 /))
187  IF (.not.cood_utils_test) RETURN
188  cood_utils_test = check(1.0d+0, result(1), 7, "cart_to_cyl")
189  IF (.not.cood_utils_test) RETURN
190  cood_utils_test = check(pi/2.0d+0, result(2), 8, "cart_to_cyl")
191  IF (.not.cood_utils_test) RETURN
192  cood_utils_test = check(-1.0d+0, result(3), 9, "cart_to_cyl")
193  IF (.not.cood_utils_test) RETURN
194 
195 ! Test cyl_to_cart function. cart(0,0,1) = cyl(0,0,1)
196  result = cyl_to_cart((/ 0.0d+0, 0.0d+0, 1.0d+0 /))
197  cood_utils_test = check(0.0d+0, result(1), 1, "cyl_to_cart")
198  IF (.not.cood_utils_test) RETURN
199  cood_utils_test = check(0.0d+0, result(2), 2, "cyl_to_cart")
200  IF (.not.cood_utils_test) RETURN
201  cood_utils_test = check(1.0d+0, result(3), 3, "cyl_to_cart")
202  IF (.not.cood_utils_test) RETURN
203 
204 ! Test cyl_to_cart function. cart(-1,0,0) = cyl(1,Pi,0)
205  result = cyl_to_cart((/ 1.0d+0, pi, 0.0d+0 /))
206  cood_utils_test = check(-1.0d+0, result(1), 4, "cyl_to_cart")
207  IF (.not.cood_utils_test) RETURN
208  cood_utils_test = check(1.0*sin(pi), result(2), 5, "cyl_to_cart")
209  IF (.not.cood_utils_test) RETURN
210  cood_utils_test = check(0.0d+0, result(3), 6, "cyl_to_cart")
211  IF (.not.cood_utils_test) RETURN
212 
213 ! Test cyl_to_cart function. cart(0,1,-1) = cyl(1,Pi/2,-1)
214  result = cyl_to_cart((/ 1.0d+0, pi/2.0d+0, -1.0d+0 /))
215  cood_utils_test = &
216  & check(cos(pi/2.0d+0), result(1), 7, "cyl_to_cart")
217  IF (.not.cood_utils_test) RETURN
218  cood_utils_test = check(1.0d+0, result(2), 8, "cyl_to_cart")
219  IF (.not.cood_utils_test) RETURN
220  cood_utils_test = check(-1.0d+0, result(3), 9, "cyl_to_cart")
221  IF (.not.cood_utils_test) RETURN
222 
223 ! Test cyl_to_cart_vec function. cart(1,0,0) = cyl(1,0,0) @ phi=0
224  result = cyl_to_cart_vec((/ 1.0d+0, 0.0d+0, 0.0d+0 /), &
225  & (/ 1.0d+0, 0.0d+0, 0.0d+0 /))
226  cood_utils_test = check(1.0d+0, result(1), 1, "cyl_to_cart_vec")
227  IF (.not.cood_utils_test) RETURN
228  cood_utils_test = check(0.0d+0, result(2), 2, "cyl_to_cart_vec")
229  IF (.not.cood_utils_test) RETURN
230  cood_utils_test = check(0.0d+0, result(3), 3, "cyl_to_cart_vec")
231  IF (.not.cood_utils_test) RETURN
232 
233 ! Test cyl_to_cart_vec function. cart(-1,0,0) = cyl(0,1,0) @ phi=0
234  result = cyl_to_cart_vec((/ 1.0d+0, 0.0d+0, 0.0d+0 /), &
235  & (/ 0.0d+0, 1.0d+0, 0.0d+0 /))
236  cood_utils_test = check(0.0d+0, result(1), 4, "cyl_to_cart_vec")
237  IF (.not.cood_utils_test) RETURN
238  cood_utils_test = check(1.0d+0, result(2), 5, "cyl_to_cart_vec")
239  IF (.not.cood_utils_test) RETURN
240  cood_utils_test = check(0.0d+0, result(3), 6, "cyl_to_cart_vec")
241  IF (.not.cood_utils_test) RETURN
242 
243 ! Test cyl_to_cart_vec function. cart(0,0,1) = cyl(0,0,1) @ phi=Pi/2
244  result = cyl_to_cart_vec((/ 1.0d+0, pi/2.0d+0, 0.0d+0 /), &
245  & (/ 0.0d+0, 0.0d+0, 1.0d+0 /))
246  cood_utils_test = check(0.0d+0, result(1), 7, "cyl_to_cart_vec")
247  IF (.not.cood_utils_test) RETURN
248  cood_utils_test = check(0.0d+0, result(2), 8, "cyl_to_cart_vec")
249  IF (.not.cood_utils_test) RETURN
250  cood_utils_test = check(1.0d+0, result(3), 9, "cyl_to_cart_vec")
251  IF (.not.cood_utils_test) RETURN
252 
253  END FUNCTION
254 
255 !*******************************************************************************
256 ! PRIVATE
257 !*******************************************************************************
258 !-------------------------------------------------------------------------------
269 !-------------------------------------------------------------------------------
270  FUNCTION check(expected, received, testNum, name)
271 
272  IMPLICIT NONE
273 
274 ! Declare Arguments
275  LOGICAL :: check
276  REAL (rprec), INTENT(in) :: expected
277  REAL (rprec), INTENT(in) :: received
278  INTEGER, INTENT(in) :: testnum
279  CHARACTER (LEN=*), INTENT(in) :: name
280 
281 ! local parameters
282  REAL(rprec), PARAMETER :: range = 1.0e-15_dp
283 
284 ! Start of executable code
285  check = (expected .eq. received) .or. &
286  & ((expected .lt. received + range) .and. &
287  & (expected .gt. received - range))
288  IF (.not.check) THEN
289  write(*,*) "coordinate_utilities.f: ", name, " test", testnum, &
290  & "failed."
291  write(*,*) "Expected", expected, "Received", received
292  END IF
293 
294  END FUNCTION
295 
296  END MODULE
coordinate_utilities
Module is part of the LIBSTELL. This modules containes code to convert from different coordinate syst...
Definition: coordinate_utilities.f:12
coordinate_utilities::cart_to_cyl_vec
pure real(rprec) function, dimension(3) cart_to_cyl_vec(cart, vec)
Convert vector from cartesian coordinates to cylindical coordinates.
Definition: coordinate_utilities.f:126
coordinate_utilities::cyl_to_cart_vec
pure real(rprec) function, dimension(3), public cyl_to_cart_vec(cyl, vec)
Convert vector from cylindical coordinates to cartesian coordinates.
Definition: coordinate_utilities.f:95
coordinate_utilities::cood_utils_test
logical function, public cood_utils_test()
Coordinate utilities unit test function.
Definition: coordinate_utilities.f:157
coordinate_utilities::cyl_to_cart
pure real(rprec) function, dimension(3), public cyl_to_cart(cyl)
Convert a point from cylindical coordinates to cartesian coordinates.
Definition: coordinate_utilities.f:67
coordinate_utilities::check
logical function, private check(expected, received, testNum, name)
Check a value.
Definition: coordinate_utilities.f:271
coordinate_utilities::cart_to_cyl
pure real(rprec) function, dimension(3), public cart_to_cyl(cart)
Convert a point from cartes cartesian coordinates to cylindical coordinates.
Definition: coordinate_utilities.f:40