Skip to content

Commit

Permalink
Merge pull request #1 from bjonkman/f/del-quki
Browse files Browse the repository at this point in the history
More updates for new `DbKi=R8Ki` behavior
  • Loading branch information
deslaughter authored Feb 17, 2023
2 parents 410d922 + e0471b0 commit ca3e998
Show file tree
Hide file tree
Showing 27 changed files with 127 additions and 309 deletions.
2 changes: 1 addition & 1 deletion modules/moordyn/src/MoorDyn.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1806,7 +1806,7 @@ SUBROUTINE MD_Init(InitInp, u, p, x, xd, z, other, y, m, DTcoupling, InitOut, Er
CALL MeshConstructElement(u%CoupledKinematics(iTurb), ELEMENT_POINT, ErrStat2, ErrMsg2, J)

! lastly, do this to set the attached line endpoint positions:
CALL Rod_SetKinematics(m%RodList(m%CpldRodIs(l,iTurb)), DBLE(rRef), m%zeros6, m%zeros6, 0.0_DbKi, m)
CALL Rod_SetKinematics(m%RodList(m%CpldRodIs(l,iTurb)), REAL(rRef,R8Ki), m%zeros6, m%zeros6, 0.0_DbKi, m)
END DO

DO l = 1,p%nCpldCons(iTurb) ! keeping this one simple for now, positioning at whatever is specified by glue code <<<
Expand Down
2 changes: 1 addition & 1 deletion modules/moordyn/src/MoorDyn_IO.f90
Original file line number Diff line number Diff line change
Expand Up @@ -139,7 +139,7 @@ SUBROUTINE setupBathymetry(inputString, defaultDepth, BathGrid, BathGrid_Xs, Bat
IF (LEN_TRIM(inputString) == 0) THEN
! If the input is empty (not provided), make the 1x1 bathymetry grid using the default depth
ALLOCATE(BathGrid(1,1), STAT=ErrStat4)
BathGrid(1,1) = DBLE(defaultDepth)
BathGrid(1,1) = REAL(defaultDepth,R8Ki)

ALLOCATE(BathGrid_Xs(1), STAT=ErrStat4)
BathGrid_Xs(1) = 0.0_DbKi
Expand Down
10 changes: 5 additions & 5 deletions modules/moordyn/src/MoorDyn_Misc.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1613,7 +1613,7 @@ SUBROUTINE setupWaterKin(WaterKinString, p, Tmax, ErrStat, ErrMsg)

! get wave number array once
DO I = 0, NStepWave2
WaveNmbr(i) = WaveNumber ( dble(I*WaveDOmega), p%g, p%WtrDpth )
WaveNmbr(i) = WaveNumber ( REAL(I*WaveDOmega, R8Ki), p%g, p%WtrDpth )
tmpComplex(I) = CMPLX(WaveElevC0(1,I), WaveElevC0(2,I))
END DO

Expand All @@ -1633,10 +1633,10 @@ SUBROUTINE setupWaterKin(WaterKinString, p, Tmax, ErrStat, ErrMsg)
ImagOmega = ImagNmbr*Omega

WaveElevC (i) = tmpComplex(i) * EXP( -ImagNmbr*WaveNmbr(i)*( p%pxWave(ix)*CosWaveDir + p%pyWave(iy)*SinWaveDir ))
WaveDynPC (i) = p%rhoW*p%g* WaveElevC(i) * COSHNumOvrCOSHDen( WaveNmbr(i), p%WtrDpth, DBLE(p%pzWave(iz)) )
WaveVelCHx(i) = Omega*WaveElevC(i) * COSHNumOvrSINHDen( WaveNmbr(i), p%WtrDpth, DBLE(p%pzWave(iz)) ) *CosWaveDir
WaveVelCHy(i) = Omega*WaveElevC(i) * COSHNumOvrSINHDen( WaveNmbr(i), p%WtrDpth, DBLE(p%pzWave(iz)) ) *SinWaveDir
WaveVelCV (i) = ImagOmega*WaveElevC(i) * SINHNumOvrSINHDen( WaveNmbr(i), p%WtrDpth, DBLE(p%pzWave(iz)) )
WaveDynPC (i) = p%rhoW*p%g* WaveElevC(i) * COSHNumOvrCOSHDen( WaveNmbr(i), p%WtrDpth, REAL(p%pzWave(iz), R8Ki) )
WaveVelCHx(i) = Omega*WaveElevC(i) * COSHNumOvrSINHDen( WaveNmbr(i), p%WtrDpth, REAL(p%pzWave(iz), R8Ki) ) *CosWaveDir
WaveVelCHy(i) = Omega*WaveElevC(i) * COSHNumOvrSINHDen( WaveNmbr(i), p%WtrDpth, REAL(p%pzWave(iz), R8Ki) ) *SinWaveDir
WaveVelCV (i) = ImagOmega*WaveElevC(i) * SINHNumOvrSINHDen( WaveNmbr(i), p%WtrDpth, REAL(p%pzWave(iz), R8Ki) )
WaveAccCHx(i) = ImagOmega*WaveVelCHx(i)
WaveAccCHy(i) = ImagOmega*WaveVelCHy(i)
WaveAccCV (i) = ImagOmega*WaveVelCV (i)
Expand Down
120 changes: 60 additions & 60 deletions modules/nwtc-library/src/NWTC_Num.f90

Large diffs are not rendered by default.

Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ SUBROUTINE ScaLAPACK_DLASRT2( ID, N, D, KEY, ErrStat, ErrMsg )

! .. Array Arguments ..
INTEGER, intent(inout) :: KEY( : )
REAL(R8Ki),intent(inout) :: D( : ) ! On entry, the array to be sorted. On exit, D has been sorted into increasing/decreasing order, depending on ID
REAL(R8Ki) ,intent(inout) :: D( : ) ! On entry, the array to be sorted. On exit, D has been sorted into increasing/decreasing order, depending on ID

! Local variable
INTEGER :: INFO ! = 0: successful exit; < 0: if INFO = -i, the i-th argument had an illegal value
Expand Down
12 changes: 6 additions & 6 deletions modules/nwtc-library/src/Polynomial/quartic.f90
Original file line number Diff line number Diff line change
Expand Up @@ -410,9 +410,9 @@ SUBROUTINE QuarticRoots(a,z)
! THE RESOLVENT CUBIC HAS ONLY REAL ROOTS
! REORDER THE ROOTS IN INCREASING ORDER

x1 = DBLE(z(1))
x2 = DBLE(z(2))
x3 = DBLE(z(3))
x1 = REAL(z(1),8)
x2 = REAL(z(2),8)
x3 = REAL(z(3),8)
IF (x1 > x2) CALL Swap(x1,x2)
IF (x2 > x3) CALL Swap(x2,x3)
IF (x1 > x2) CALL Swap(x1,x2)
Expand Down Expand Up @@ -460,7 +460,7 @@ SUBROUTINE QuarticRoots(a,z)

! THE RESOLVENT CUBIC HAS COMPLEX ROOTS

60 t = DBLE(z(1))
60 t = REAL(z(1),8)
x = ZERO
IF (t < ZERO) THEN
GO TO 61
Expand All @@ -469,14 +469,14 @@ SUBROUTINE QuarticRoots(a,z)
ELSE
GO TO 62
END IF
61 h = ABS(DBLE(z(2))) + ABS(AIMAG(z(2)))
61 h = ABS(REAL(z(2),8)) + ABS(AIMAG(z(2)))
IF (ABS(t) <= h) GO TO 70
GO TO 80
62 x = SQRT(t)
IF (q > ZERO) x = -x

70 w = SQRT(z(2))
u = TWO*DBLE(w)
u = TWO*REAL(w,8)
v = TWO*ABS(AIMAG(w))
t = x - b
x1 = t + u
Expand Down
6 changes: 3 additions & 3 deletions modules/nwtc-library/src/SingPrec.f90
Original file line number Diff line number Diff line change
Expand Up @@ -21,10 +21,10 @@
!..................................................................................................................................
!> This module stores constants to specify the KIND of variables.
!!
!! NOTE: When using preprocessor definition DOUBLE_PRECISION (which sets ReKi=R8Ki and DbKi=QuKi), you
!! NOTE: When using preprocessor definition DOUBLE_PRECISION (which sets ReKi=R8Ki), you
!! may need to use a compile option to convert default reals to 8 bytes: \n
!! - Intel: /real_size:64 /double_size:128
!! - Gnu: -fdefault-real-8
!! - Intel: /real_size:64
!! - Gnu: -fdefault-real-8
MODULE Precision
!..................................................................................................................................

Expand Down
26 changes: 0 additions & 26 deletions modules/nwtc-library/src/SysGnuWin.f90
Original file line number Diff line number Diff line change
Expand Up @@ -47,14 +47,12 @@ MODULE SysSubs
INTERFACE NWTC_ERF ! Returns the ERF value of its argument
MODULE PROCEDURE NWTC_ERFR4
MODULE PROCEDURE NWTC_ERFR8
MODULE PROCEDURE NWTC_ERFR16
END INTERFACE

INTERFACE NWTC_gamma ! Returns the gamma value of its argument
! note: gamma is part of the F08 standard, but may not be implemented everywhere...
MODULE PROCEDURE NWTC_gammaR4
MODULE PROCEDURE NWTC_gammaR8
MODULE PROCEDURE NWTC_gammaR16
END INTERFACE

INTEGER, PARAMETER :: ConRecL = 120 ! The record length for console output.
Expand Down Expand Up @@ -131,18 +129,6 @@ FUNCTION NWTC_ERFR8( x )

END FUNCTION NWTC_ERFR8
!=======================================================================
FUNCTION NWTC_ERFR16( x )

! Returns the ERF value of its argument. The result has a value equal
! to the error function: 2/pi * integral_from_0_to_x of e^(-t^2) dt.

REAL(QuKi), INTENT(IN) :: x ! input
REAL(QuKi) :: NWTC_ERFR16 ! result

NWTC_ERFR16 = ERF( x )

END FUNCTION NWTC_ERFR16
!=======================================================================
FUNCTION NWTC_GammaR4( x )

! Returns the gamma value of its argument. The result has a value equal
Expand All @@ -167,18 +153,6 @@ FUNCTION NWTC_GammaR8( x )

END FUNCTION NWTC_GammaR8
!=======================================================================
FUNCTION NWTC_GammaR16( x )

! Returns the gamma value of its argument. The result has a value equal
! to a processor-dependent approximation to the gamma function of x.

REAL(QuKi), INTENT(IN) :: x ! input
REAL(QuKi) :: NWTC_GammaR16 ! result

NWTC_GammaR16 = gamma( x )

END FUNCTION NWTC_GammaR16
!=======================================================================
SUBROUTINE FlushOut ( Unit )

! This subroutine flushes the buffer on the specified Unit.
Expand Down
26 changes: 0 additions & 26 deletions modules/nwtc-library/src/SysIFL.f90
Original file line number Diff line number Diff line change
Expand Up @@ -47,14 +47,12 @@ MODULE SysSubs
INTERFACE NWTC_ERF ! Returns the ERF value of its argument
MODULE PROCEDURE NWTC_ERFR4
MODULE PROCEDURE NWTC_ERFR8
MODULE PROCEDURE NWTC_ERFR16
END INTERFACE

INTERFACE NWTC_gamma ! Returns the gamma value of its argument
! note: gamma is part of the F08 standard, but may not be implemented everywhere...
MODULE PROCEDURE NWTC_gammaR4
MODULE PROCEDURE NWTC_gammaR8
MODULE PROCEDURE NWTC_gammaR16
END INTERFACE

INTEGER, PARAMETER :: ConRecL = 120 ! The record length for console output.
Expand Down Expand Up @@ -134,18 +132,6 @@ FUNCTION NWTC_ERFR8( x )

END FUNCTION NWTC_ERFR8
!=======================================================================
FUNCTION NWTC_ERFR16( x )

! Returns the ERF value of its argument. The result has a value equal
! to the error function: 2/pi * integral_from_0_to_x of e^(-t^2) dt.

REAL(QuKi), INTENT(IN) :: x ! input
REAL(QuKi) :: NWTC_ERFR16 ! result

NWTC_ERFR16 = ERF( x )

END FUNCTION NWTC_ERFR16
!=======================================================================
FUNCTION NWTC_GammaR4( x )

! Returns the gamma value of its argument. The result has a value equal
Expand All @@ -170,18 +156,6 @@ FUNCTION NWTC_GammaR8( x )

END FUNCTION NWTC_GammaR8
!=======================================================================
FUNCTION NWTC_GammaR16( x )

! Returns the gamma value of its argument. The result has a value equal
! to a processor-dependent approximation to the gamma function of x.

REAL(QuKi), INTENT(IN) :: x ! input
REAL(QuKi) :: NWTC_GammaR16 ! result

NWTC_GammaR16 = gamma( x )

END FUNCTION NWTC_GammaR16
!=======================================================================
SUBROUTINE FlushOut ( Unit )

! This subroutine flushes the buffer on the specified Unit.
Expand Down
25 changes: 0 additions & 25 deletions modules/nwtc-library/src/SysIVF.f90
Original file line number Diff line number Diff line change
Expand Up @@ -47,14 +47,12 @@ MODULE SysSubs
INTERFACE NWTC_ERF ! Returns the ERF value of its argument
MODULE PROCEDURE NWTC_ERFR4
MODULE PROCEDURE NWTC_ERFR8
MODULE PROCEDURE NWTC_ERFR16
END INTERFACE

INTERFACE NWTC_gamma ! Returns the gamma value of its argument
! note: gamma is part of the F08 standard, but may not be implemented everywhere...
MODULE PROCEDURE NWTC_gammaR4
MODULE PROCEDURE NWTC_gammaR8
MODULE PROCEDURE NWTC_gammaR16
END INTERFACE

INTEGER, PARAMETER :: ConRecL = 120 ! The record length for console output.
Expand Down Expand Up @@ -137,19 +135,6 @@ FUNCTION NWTC_ERFR8( x )

END FUNCTION NWTC_ERFR8
!=======================================================================
!> \copydoc syssubs::nwtc_erfr4
FUNCTION NWTC_ERFR16( x )

! Returns the ERF value of its argument. The result has a value equal
! to the error function: 2/pi * integral_from_0_to_x of e^(-t^2) dt.

REAL(QuKi), INTENT(IN) :: x ! input
REAL(QuKi) :: NWTC_ERFR16 ! result

NWTC_ERFR16 = ERF( x )

END FUNCTION NWTC_ERFR16
!=======================================================================
!> Returns the gamma value of its argument. The result has a value equal
!! to a processor-dependent approximation to the gamma function of x:
!! \f{equation}{
Expand Down Expand Up @@ -177,16 +162,6 @@ FUNCTION NWTC_GammaR8( x )

END FUNCTION NWTC_GammaR8
!=======================================================================
!> \copydoc syssubs::nwtc_gammar4
FUNCTION NWTC_GammaR16( x )

REAL(QuKi), INTENT(IN) :: x ! input
REAL(QuKi) :: NWTC_GammaR16 ! result

NWTC_GammaR16 = gamma( x )

END FUNCTION NWTC_GammaR16
!=======================================================================
!> This subroutine flushes the buffer on the specified Unit.
!! It is especially useful when printing "running..." type messages.
SUBROUTINE FlushOut ( Unit )
Expand Down
28 changes: 0 additions & 28 deletions modules/nwtc-library/src/SysIVF_Labview.f90
Original file line number Diff line number Diff line change
Expand Up @@ -60,13 +60,11 @@ MODULE SysSubs
INTERFACE NWTC_gamma ! Returns the gamma value of its argument
MODULE PROCEDURE NWTC_gammaR4
MODULE PROCEDURE NWTC_gammaR8
MODULE PROCEDURE NWTC_gammaR16
END INTERFACE

INTERFACE NWTC_ERF ! Returns the ERF value of its argument
MODULE PROCEDURE NWTC_ERFR4
MODULE PROCEDURE NWTC_ERFR8
MODULE PROCEDURE NWTC_ERFR16
END INTERFACE


Expand Down Expand Up @@ -217,19 +215,6 @@ FUNCTION NWTC_ERFR8( x )
NWTC_ERFR8 = ERF( x )

END FUNCTION NWTC_ERFR8
!=======================================================================
FUNCTION NWTC_ERFR16( x )

! Returns the ERF value of its argument. The result has a value equal
! to the error function: 2/pi * integral_from_0_to_x of e^(-t^2) dt.

REAL(QuKi), INTENT(IN) :: x ! input
REAL(QuKi) :: NWTC_ERFR16 ! result


NWTC_ERFR16 = ERF( x )

END FUNCTION NWTC_ERFR16
!=======================================================================
FUNCTION NWTC_GammaR4( x )

Expand All @@ -256,19 +241,6 @@ FUNCTION NWTC_GammaR8( x )
NWTC_GammaR8 = gamma( x )

END FUNCTION NWTC_GammaR8
!=======================================================================
FUNCTION NWTC_GammaR16( x )

! Returns the gamma value of its argument. The result has a value equal
! to a processor-dependent approximation to the gamma function of x.

REAL(QuKi), INTENT(IN) :: x ! input
REAL(QuKi) :: NWTC_GammaR16 ! result


NWTC_GammaR16 = gamma( x )

END FUNCTION NWTC_GammaR16
!=======================================================================
SUBROUTINE OpenCon

Expand Down
26 changes: 0 additions & 26 deletions modules/nwtc-library/src/SysMatlabLinuxGnu.f90
Original file line number Diff line number Diff line change
Expand Up @@ -50,14 +50,12 @@ MODULE SysSubs
INTERFACE NWTC_ERF ! Returns the ERF value of its argument
MODULE PROCEDURE NWTC_ERFR4
MODULE PROCEDURE NWTC_ERFR8
MODULE PROCEDURE NWTC_ERFR16
END INTERFACE

INTERFACE NWTC_gamma ! Returns the gamma value of its argument
! note: gamma is part of the F08 standard, but may not be implemented everywhere...
MODULE PROCEDURE NWTC_gammaR4
MODULE PROCEDURE NWTC_gammaR8
MODULE PROCEDURE NWTC_gammaR16
END INTERFACE

INTEGER, PARAMETER :: ConRecL = 120 ! The record length for console output.
Expand Down Expand Up @@ -134,18 +132,6 @@ FUNCTION NWTC_ERFR8( x )

END FUNCTION NWTC_ERFR8
!=======================================================================
FUNCTION NWTC_ERFR16( x )

! Returns the ERF value of its argument. The result has a value equal
! to the error function: 2/pi * integral_from_0_to_x of e^(-t^2) dt.

REAL(QuKi), INTENT(IN) :: x ! input
REAL(QuKi) :: NWTC_ERFR16 ! result

NWTC_ERFR16 = ERF( x )

END FUNCTION NWTC_ERFR16
!=======================================================================
FUNCTION NWTC_GammaR4( x )

! Returns the gamma value of its argument. The result has a value equal
Expand All @@ -170,18 +156,6 @@ FUNCTION NWTC_GammaR8( x )

END FUNCTION NWTC_GammaR8
!=======================================================================
FUNCTION NWTC_GammaR16( x )

! Returns the gamma value of its argument. The result has a value equal
! to a processor-dependent approximation to the gamma function of x.

REAL(QuKi), INTENT(IN) :: x ! input
REAL(QuKi) :: NWTC_GammaR16 ! result

NWTC_GammaR16 = gamma( x )

END FUNCTION NWTC_GammaR16
!=======================================================================
SUBROUTINE FlushOut ( Unit )

! This subroutine flushes the buffer on the specified Unit.
Expand Down
Loading

0 comments on commit ca3e998

Please sign in to comment.