@@ -214,14 +214,14 @@ contains
214214 if(scale % re == 0.0_${k1}$) then
215215 ti = scale % im * r1
216216 tr = 0.0_${k1}$
217- elseif (scale % im == 0.0_${k1}$) then
217+ else if (scale % im == 0.0_${k1}$) then
218218 tr = scale % re * r1
219219 ti = 0.0_${k1}$
220220 else
221221 tr = scale % re * r1
222222 r1 = unif_dist_rvs_0_r${k1}$( )
223223 ti = scale % im * r1
224- endif
224+ end if
225225 res = cmplx(tr, ti, kind=${k1}$)
226226 end function unif_dist_rvs_1_${t1[0]}$${k1}$
227227
@@ -248,14 +248,14 @@ contains
248248 if(scale % re == 0.0_${k1}$) then
249249 tr = loc % re
250250 ti = loc % im + scale % im * r1
251- elseif (scale % im == 0.0_${k1}$) then
251+ else if (scale % im == 0.0_${k1}$) then
252252 tr = loc % re + scale % re * r1
253253 ti = loc % im
254254 else
255255 tr = loc % re + scale % re * r1
256256 r1 = unif_dist_rvs_0_r${k1}$( )
257257 ti = loc % im + scale % im * r1
258- endif
258+ end if
259259 res = cmplx(tr, ti, kind=${k1}$)
260260 end function unif_dist_rvs_${t1[0]}$${k1}$
261261
@@ -318,7 +318,7 @@ contains
318318 tmp = shiftr(dist_rand(INT_ONE), 11)
319319 t = real(tmp * MESENNE_NUMBER, kind = ${k1}$)
320320 res(i) = loc + scale * t
321- enddo
321+ end do
322322 end function unif_dist_rvs_array_${t1[0]}$${k1}$
323323
324324 #:endfor
@@ -345,15 +345,15 @@ contains
345345 if(scale % re == 0.0_${k1}$) then
346346 tr = loc % re
347347 ti = loc % im + scale % im * r1
348- elseif (scale % im == 0.0_${k1}$) then
348+ else if (scale % im == 0.0_${k1}$) then
349349 tr = loc % re + scale % re * r1
350350 ti = loc % im
351351 else
352352 tr = loc % re + scale % re * r1
353353 tmp = shiftr(dist_rand(INT_ONE), 11)
354354 r1 = real(tmp * MESENNE_NUMBER, kind = ${k1}$)
355355 ti = loc % im + scale % im * r1
356- endif
356+ end if
357357 res(i) = cmplx(tr, ti, kind=${k1}$)
358358 end do
359359 end function unif_dist_rvs_array_${t1[0]}$${k1}$
@@ -370,7 +370,7 @@ contains
370370
371371 if(scale == 0_${k1}$) then
372372 res = 0.0
373- elseif (x < loc .or. x > (loc + scale)) then
373+ else if (x < loc .or. x > (loc + scale)) then
374374 res = 0.0
375375 else
376376 res = 1. / (scale + 1_${k1}$)
@@ -389,7 +389,7 @@ contains
389389
390390 if(scale == 0.0_${k1}$) then
391391 res = 0.0
392- elseif (x <= loc .or. x >= (loc + scale)) then
392+ else if (x <= loc .or. x >= (loc + scale)) then
393393 res = 0.0
394394 else
395395 res = 1.0 / scale
@@ -410,7 +410,7 @@ contains
410410 tr = loc % re + scale % re; ti = loc % im + scale % im
411411 if(scale == (0.0_${k1}$,0.0_${k1}$)) then
412412 res = 0.0
413- elseif ((x % re >= loc % re .and. x % re <= tr) .and. &
413+ else if ((x % re >= loc % re .and. x % re <= tr) .and. &
414414 (x % im >= loc % im .and. x % im <= ti)) then
415415 res = 1.0 / (scale % re * scale % im)
416416 else
@@ -430,9 +430,9 @@ contains
430430
431431 if(scale == 0_${k1}$) then
432432 res = 0.0
433- elseif (x < loc) then
433+ else if (x < loc) then
434434 res = 0.0
435- elseif (x >= loc .and. x <= (loc + scale)) then
435+ else if (x >= loc .and. x <= (loc + scale)) then
436436 res = real((x - loc + 1_${k1}$)) / real((scale + 1_${k1}$))
437437 else
438438 res = 1.0
@@ -451,9 +451,9 @@ contains
451451
452452 if(scale == 0.0_${k1}$) then
453453 res = 0.0
454- elseif (x < loc) then
454+ else if (x < loc) then
455455 res = 0.0
456- elseif (x >= loc .and. x <= (loc + scale)) then
456+ else if (x >= loc .and. x <= (loc + scale)) then
457457 res = (x - loc) / scale
458458 else
459459 res = 1.0
@@ -474,22 +474,22 @@ contains
474474 if(scale == (0.0_${k1}$,0.0_${k1}$)) then
475475 res = 0.0
476476 return
477- endif
477+ end if
478478 r1 = x % re < loc % re
479479 r2 = x % re > (loc % re + scale % re)
480480 i1 = x % im < loc % im
481481 i2 = x % im > (loc % im + scale % im)
482482 if(r1 .or. i1) then
483483 res = 0.0
484- elseif ((.not. r1) .and. (.not. r2) .and. i2) then
484+ else if ((.not. r1) .and. (.not. r2) .and. i2) then
485485 res = (x % re - loc % re) / scale % re
486- elseif ((.not. i1) .and. (.not. i2) .and. r2) then
486+ else if ((.not. i1) .and. (.not. i2) .and. r2) then
487487 res = (x % im - loc % im) / scale % im
488- elseif ((.not. r1) .and. (.not. r2) .and. (.not. i1) .and. (.not. i2)) &
488+ else if ((.not. r1) .and. (.not. r2) .and. (.not. i1) .and. (.not. i2)) &
489489 then
490490 res = (x % re - loc % re) * (x % im - loc % im) / &
491491 (scale % re * scale % im)
492- elseif (r2 .and. i2)then
492+ else if (r2 .and. i2)then
493493 res = 1.0
494494 end if
495495 end function unif_dist_cdf_${t1[0]}$${k1}$
0 commit comments