Skip to content

Commit d95334f

Browse files
authored
Merge pull request #3071 from luwang00/f/Wake_merge_deslaughter
Various changes to the handling of wake planes
2 parents b37b534 + 9f6e419 commit d95334f

File tree

11 files changed

+335
-152
lines changed

11 files changed

+335
-152
lines changed

glue-codes/fast-farm/src/FAST_Farm_IO.f90

Lines changed: 17 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -106,7 +106,7 @@ SUBROUTINE Farm_PrintSum( farm, WD_InputFileData, ErrStat, ErrMsg )
106106

107107
end do
108108

109-
WRITE (UnSum,'(/,A)' ) 'Wake Dynamics Finite-Difference Grid: '//trim(Num2LStr(farm%WD(1)%p%NumRadii))//' Radii, '//trim(Num2LStr(farm%WD(1)%p%NumPlanes))//' Planes'
109+
WRITE (UnSum,'(/,A)' ) 'Wake Dynamics Finite-Difference Grid: '//trim(Num2LStr(farm%WD(1)%p%NumRadii))//' Radii'
110110
WRITE (UnSum,'(2X,A)') 'Radial Node Number Output Node Number Radius'
111111
WRITE (UnSum,'(2X,A)') ' (-) (-) (m) '
112112
do I = 0, farm%WD(1)%p%NumRadii-1
@@ -268,7 +268,7 @@ SUBROUTINE Farm_InitOutput( farm, ErrStat, ErrMsg )
268268
!============================================================
269269
! DEBUG OUTPUTS HERE
270270
!
271-
! DO I = 0,farm%WD(1)%p%NumPlanes-1 ! Loop through all selected output channels
271+
! DO I = 0,NINT(farm%WD(1)%y%NumPlanes)-1 ! Loop through all selected output channels
272272
!
273273
! WRITE( farm%p%UnOu,'(A14)',ADVANCE='NO') 'PPLANEX'//trim(num2lstr(I))
274274
! WRITE( farm%p%UnOu,'(A14)',ADVANCE='NO') 'PPLANEY'//trim(num2lstr(I))
@@ -301,7 +301,7 @@ SUBROUTINE Farm_InitOutput( farm, ErrStat, ErrMsg )
301301
!============================================================
302302
! DEBUG OUTPUTS HERE
303303
!
304-
! DO I = 0,farm%WD(1)%p%NumPlanes-1 ! Loop through all selected output channels
304+
! DO I = 0,NINT(farm%WD(1)%y%NumPlanes)-1 ! Loop through all selected output channels
305305
!
306306
! WRITE( farm%p%UnOu,'(A14)',ADVANCE='NO') ' (m) '
307307
! WRITE( farm%p%UnOu,'(A14)',ADVANCE='NO') ' (m) '
@@ -313,7 +313,7 @@ SUBROUTINE Farm_InitOutput( farm, ErrStat, ErrMsg )
313313
! WRITE( farm%p%UnOu,'(A14)',ADVANCE='NO' ) ' (m/s) '
314314
! WRITE( farm%p%UnOu,'(A14)',ADVANCE='NO' ) ' (m/s) '
315315
!
316-
! IF ( I < farm%WD(1)%p%NumPlanes-1 ) THEN
316+
! IF ( I < NINT(farm%WD(1)%y%NumPlanes)-1 ) THEN
317317
! WRITE( farm%p%UnOu,'(A14)',ADVANCE='NO' ) ' (-) '
318318
! END IF
319319
!
@@ -481,7 +481,7 @@ SUBROUTINE WriteFarmOutputToFile( t_global, farm, ErrStat, ErrMsg )
481481
!============================================================
482482
! DEBUG OUTPUTS HERE
483483
!
484-
! DO I = 0,farm%WD(1)%p%NumPlanes-1 ! Loop through all selected output channels
484+
! DO I = 0,NINT(farm%WD(1)%y%NumPlanes)-1 ! Loop through all selected output channels
485485
!
486486
! DO J = 1,3
487487
! WRITE( TmpStr2, '('//trim(farm%p%OutFmt)//')' ) farm%WD(1)%y%p_plane(J,I)
@@ -722,7 +722,16 @@ SUBROUTINE Farm_ReadPrimaryFile( InputFile, p, WD_InitInp, AWAE_InitInp, OutList
722722
CALL ReadVar( UnIn, InputFile, p%RotorDiamRef , "RotorDiamRef", "Reference turbine rotor diameter for wake calculations (m) [>0.0]", ErrStat2, ErrMsg2, UnEc); if(failed()) return
723723
CALL ReadVar( UnIn, InputFile, WD_InitInp%dr , "dr" , "Radial increment of radial finite-difference grid (m) [>0.0]", ErrStat2, ErrMsg2, UnEc); if(failed()) return
724724
CALL ReadVar( UnIn, InputFile, WD_InitInp%NumRadii, "NumRadii", "Number of radii in the radial finite-difference grid (-) [>=2]", ErrStat2, ErrMsg2, UnEc); if(failed()) return
725-
CALL ReadVar( UnIn, InputFile, WD_InitInp%NumPlanes,"NumPlanes", "Number of wake planes (-) [>=2]", ErrStat2, ErrMsg2, UnEc); if(failed()) return
725+
726+
CALL ReadVarWDefault( UnIn, InputFile, WD_InitInp%NumDFull, "NumDFull", &
727+
"Distance of full wake propagation, expressed as a multiple of RotorDiamRef [>0.0] or DEFAULT [DEFAULT=15]", &
728+
15_IntKi, ErrStat2, ErrMsg2, UnEc); if (Failed()) return
729+
730+
CALL ReadVarWDefault( UnIn, InputFile, WD_InitInp%NumDBuff, "NumDBuff", &
731+
"Length of wake propagation buffer region, expressed as a multiple of RotorDiamRef [>=0.0] or DEFAULT [DEFAULT=5]", &
732+
5_IntKi, ErrStat2, ErrMsg2, UnEc); if (Failed()) return
733+
734+
WD_InitInp%RotorDiamRef = p%RotorDiamRef
726735

727736
! f_c - Cut-off (corner) frequency of the low-pass time-filter for the wake advection, deflection, and meandering model (Hz) [>0.0] or DEFAULT [DEFAULT=0.0007]:
728737
DefaultReVal = 12.5_ReKi/(p%RotorDiamRef/2._ReKi) ! Eq. (32) of https://doi.org/10.1002/we.2785, with U=10, a=1/3
@@ -1024,7 +1033,8 @@ SUBROUTINE Farm_ValidateInput( p, WD_InitInp, AWAE_InitInp, ErrStat, ErrMsg )
10241033
IF (WD_InitInp%Mod_Wake < 1 .or. WD_InitInp%Mod_Wake >3 ) CALL SetErrStat(ErrID_Fatal,'Mod_Wake needs to be 1,2 or 3',ErrStat,ErrMsg,RoutineName)
10251034
IF (WD_InitInp%dr <= 0.0_ReKi) CALL SetErrStat(ErrID_Fatal,'dr (radial increment) must be larger than 0.',ErrStat,ErrMsg,RoutineName)
10261035
IF (WD_InitInp%NumRadii < 2) CALL SetErrStat(ErrID_Fatal,'NumRadii (number of radii) must be at least 2.',ErrStat,ErrMsg,RoutineName)
1027-
IF (WD_InitInp%NumPlanes < 2) CALL SetErrStat(ErrID_Fatal,'NumPlanes (number of wake planes) must be at least 2.',ErrStat,ErrMsg,RoutineName)
1036+
IF (WD_InitInp%NumDFull <= 0.0_ReKi) CALL SetErrStat(ErrID_Fatal,'NumDFull (distance of full wake propagation as a multiple of RotorDiamRef) must be positive.',ErrStat,ErrMsg,RoutineName)
1037+
IF (WD_InitInp%NumDBuff < 0.0_ReKi) CALL SetErrStat(ErrID_Fatal,'NumDBuff (length of wake propagation buffer region as a multiple of RotorDiamRef) must be nonnegative.',ErrStat,ErrMsg,RoutineName)
10281038

10291039
IF (WD_InitInp%k_VortexDecay < 0.0_ReKi) CALL SetErrStat(ErrID_Fatal,'k_VortexDecay must be >= 0',ErrStat,ErrMsg,RoutineName)
10301040
IF (WD_InitInp%NumVortices < 2) CALL SetErrStat(ErrID_Fatal,'NumVorticies must be greater than 1',ErrStat,ErrMsg,RoutineName)

glue-codes/fast-farm/src/FAST_Farm_Registry.txt

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -33,6 +33,7 @@ typedef ^ ParameterType DbKi DT_high -
3333
typedef ^ ParameterType DbKi TMax - - - "Total run time" seconds
3434
typedef ^ ParameterType IntKi n_high_low - - - "Number of high-resolution time steps per low-resolution time step" -
3535
typedef ^ ParameterType IntKi NumTurbines - - - "Number of turbines in the simulation" -
36+
typedef ^ ParameterType IntKi MaxNumPlanes {:} - - "Maximum number of wake planes for each rotor" -
3637
typedef ^ ParameterType CHARACTER(1024) WindFilePath - - - "Path name of wind data files from ABLSolver precursor" -
3738
typedef ^ ParameterType ReKi WT_Position {:}{:} - - "X-Y-Z position of each wind turbine; index 1 = XYZ; index 2 = turbine number" meters
3839
typedef ^ ParameterType IntKi WaveFieldMod - - - "Wave field handling (-) (switch) {0: use individual HydroDyn inputs without adjustment, 1: adjust wave phases based on turbine offsets from farm origin}" -

glue-codes/fast-farm/src/FAST_Farm_Subs.f90

Lines changed: 31 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -207,11 +207,14 @@ SUBROUTINE Farm_Initialize( farm, InputFile, ErrStat, ErrMsg )
207207
! [note that FAST uses the ceiling function, so it might think we're doing one more step than FAST.Farm;
208208
! This difference will be a problem only if FAST thinks it's doing FEWER timesteps than FAST.Farm does.]
209209

210-
IF ( WD_InitInput%InputFileData%NumPlanes > farm%p%n_TMax ) THEN
211-
WD_InitInput%InputFileData%NumPlanes = max( 2, min( WD_InitInput%InputFileData%NumPlanes, farm%p%n_TMax ) )
212-
call SetErrStat(ErrID_Warn, "For efficiency, NumPlanes has been reduced to the number of time steps ("//TRIM(Num2LStr(WD_InitInput%InputFileData%NumPlanes))//").", ErrStat, ErrMsg, RoutineName )
213-
ENDIF
214-
210+
211+
call AllocAry( farm%p%MaxNumPlanes, farm%p%NumTurbines, 'farm%p%MaxNumPlanes', ErrStat2, ErrMsg2); CALL SetErrStat( ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName); if (Failed()) return
212+
do i=1,farm%p%NumTurbines
213+
! Eventually, we will have different settings for different rotors
214+
farm%p%MaxNumPlanes(i) = ceiling( 15.0 * Real( WD_InitInput%InputFileData%NumDFull + WD_InitInput%InputFileData%NumDBuff , ReKi ) / AWAE_InitInput%InputFileData%C_Meander )
215+
farm%p%MaxNumPlanes(i) = max( 2, min( farm%p%MaxNumPlanes(i) , farm%p%n_TMax + 2 ) )
216+
end do
217+
215218
!...............................................................................................................................
216219
! step 3: initialize WAT, AWAE, and WD (b, c, and d can be done in parallel)
217220
!...............................................................................................................................
@@ -231,7 +234,7 @@ SUBROUTINE Farm_Initialize( farm, InputFile, ErrStat, ErrMsg )
231234
AWAE_InitInput%InputFileData%dt_low = farm%p%dt_low
232235
AWAE_InitInput%InputFileData%NumTurbines = farm%p%NumTurbines
233236
AWAE_InitInput%InputFileData%NumRadii = WD_InitInput%InputFileData%NumRadii
234-
AWAE_InitInput%InputFileData%NumPlanes = WD_InitInput%InputFileData%NumPlanes
237+
AWAE_InitInput%MaxPlanes = MAXVAL(farm%p%MaxNumPlanes)
235238
AWAE_InitInput%InputFileData%WindFilePath = farm%p%WindFilePath
236239
AWAE_InitInput%n_high_low = farm%p%n_high_low
237240
AWAE_InitInput%NumDT = farm%p%n_TMax
@@ -580,8 +583,9 @@ SUBROUTINE Farm_InitWD( farm, WD_InitInp, ErrStat, ErrMsg )
580583
! initialization can be done in parallel (careful for FWrap_InitInp, though)
581584
!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
582585

583-
WD_InitInp%TurbNum = nt
584-
WD_InitInp%OutFileRoot = farm%p%OutFileRoot
586+
WD_InitInp%TurbNum = nt
587+
WD_InitInp%MaxNumPlanes = farm%p%MaxNumPlanes(nt)
588+
WD_InitInp%OutFileRoot = farm%p%OutFileRoot
585589

586590
! note that WD_Init has Interval as INTENT(IN) so, we don't need to worry about overwriting farm%p%dt_low here:
587591
call WD_Init( WD_InitInp, farm%WD(nt)%u, farm%WD(nt)%p, farm%WD(nt)%x, farm%WD(nt)%xd, farm%WD(nt)%z, &
@@ -1367,7 +1371,7 @@ subroutine Farm_WriteOutput(n, t, farm, ErrStat, ErrMsg)
13671371
! Loop over user-requested, downstream distances (OutDist), m
13681372
do iOutDist = 1, farm%p%NOutDist
13691373

1370-
if ( farm%p%OutDist(iOutDist) >= maxval( farm%WD(nt)%y%x_plane(0:min(farm%WD(nt)%p%NumPlanes-1,n+1)) ) ) then
1374+
if ( farm%p%OutDist(iOutDist) >= maxval( farm%WD(nt)%y%x_plane( 0:NINT(farm%WD(nt)%y%NumPlanes)-1 ) ) ) then
13711375

13721376
farm%m%AllOuts(WkAxsXTD(iOutDist,nt)) = 0.0_ReKi
13731377
farm%m%AllOuts(WkAxsYTD(iOutDist,nt)) = 0.0_ReKi
@@ -1404,7 +1408,7 @@ subroutine Farm_WriteOutput(n, t, farm, ErrStat, ErrMsg)
14041408
else
14051409

14061410
! Find wake volume which contains the user-requested downstream location.
1407-
do np = 0, min(farm%WD(nt)%p%NumPlanes-2 , n)
1411+
do np = 0, NINT(farm%WD(nt)%y%NumPlanes)-2
14081412

14091413
if ( ( farm%p%OutDist(iOutDist) >= farm%WD(nt)%y%x_plane(np) ) .and. ( farm%p%OutDist(iOutDist) < farm%WD(nt)%y%x_plane(np+1) ) ) then ! A wake volume has been found
14101414

@@ -1774,12 +1778,14 @@ END SUBROUTINE Transfer_FAST_to_WD
17741778
SUBROUTINE Transfer_AWAE_to_WD(farm)
17751779
type(All_FastFarm_Data), INTENT(INOUT) :: farm !< FAST.Farm data
17761780

1777-
integer(intKi) :: nt
1781+
integer(IntKi) :: nt
1782+
integer(IntKi) :: MaxPln
17781783

17791784
DO nt = 1,farm%p%NumTurbines
1780-
farm%WD(nt)%u%V_plane = farm%AWAE%y%V_plane(:,:,nt) ! Advection, deflection, and meandering velocity of wake planes, m/s
1781-
farm%WD(nt)%u%Vx_wind_disk = farm%AWAE%y%Vx_wind_disk(nt) ! Rotor-disk-averaged ambient wind speed, normal to planes, m/s
1782-
farm%WD(nt)%u%TI_amb = farm%AWAE%y%TI_amb(nt) ! Ambient turbulence intensity of wind at rotor disk
1785+
MaxPln = NINT(farm%WD(nt)%y%NumPlanes)-1
1786+
farm%WD(nt)%u%V_plane(:,0:MaxPln) = farm%AWAE%y%V_plane(:,0:MaxPln,nt) ! Advection, deflection, and meandering velocity of wake planes, m/s
1787+
farm%WD(nt)%u%Vx_wind_disk = farm%AWAE%y%Vx_wind_disk(nt) ! Rotor-disk-averaged ambient wind speed, normal to planes, m/s
1788+
farm%WD(nt)%u%TI_amb = farm%AWAE%y%TI_amb(nt) ! Ambient turbulence intensity of wind at rotor disk
17831789
END DO
17841790

17851791
END SUBROUTINE Transfer_AWAE_to_WD
@@ -1788,16 +1794,19 @@ SUBROUTINE Transfer_WD_to_AWAE(farm)
17881794
type(All_FastFarm_Data), INTENT(INOUT) :: farm !< FAST.Farm data
17891795

17901796
integer(intKi) :: nt
1797+
integer(IntKi) :: MaxPln
17911798

1792-
DO nt = 1,farm%p%NumTurbines
1793-
farm%AWAE%u%xhat_plane(:,:,nt) = farm%WD(nt)%y%xhat_plane ! Orientations of wake planes, normal to wake planes, for each turbine
1794-
farm%AWAE%u%p_plane(:,:,nt) = farm%WD(nt)%y%p_plane ! Center positions of wake planes for each turbine
1795-
farm%AWAE%u%Vx_wake(:,:,:,nt) = farm%WD(nt)%y%Vx_wake2 ! Axial wake velocity deficit at wake planes, distributed radially, for each turbine
1796-
farm%AWAE%u%Vy_wake(:,:,:,nt) = farm%WD(nt)%y%Vy_wake2 ! Horizontal wake velocity deficit at wake planes, distributed radially, for each turbine
1797-
farm%AWAE%u%Vz_wake(:,:,:,nt) = farm%WD(nt)%y%Vz_wake2 ! "Vertical" wake velocity deficit at wake planes, distributed radially, for each turbine
1798-
farm%AWAE%u%D_wake(:,nt) = farm%WD(nt)%y%D_wake ! Wake diameters at wake planes for each turbine
1799+
DO nt = 1,farm%p%NumTurbines
1800+
MaxPln = NINT(farm%WD(nt)%y%NumPlanes)-1
1801+
farm%AWAE%u%NumPlanes ( nt) = farm%WD(nt)%y%NumPlanes ! Number of active wake planes for each turbine
1802+
farm%AWAE%u%xhat_plane( :,0:MaxPln,nt) = farm%WD(nt)%y%xhat_plane( :,0:MaxPln) ! Orientations of wake planes, normal to wake planes, for each turbine
1803+
farm%AWAE%u%p_plane ( :,0:MaxPln,nt) = farm%WD(nt)%y%p_plane ( :,0:MaxPln) ! Center positions of wake planes for each turbine
1804+
farm%AWAE%u%Vx_wake (:,:,0:MaxPln,nt) = farm%WD(nt)%y%Vx_wake2 (:,:,0:MaxPln) ! Axial wake velocity deficit at wake planes, distributed radially, for each turbine
1805+
farm%AWAE%u%Vy_wake (:,:,0:MaxPln,nt) = farm%WD(nt)%y%Vy_wake2 (:,:,0:MaxPln) ! Horizontal wake velocity deficit at wake planes, distributed radially, for each turbine
1806+
farm%AWAE%u%Vz_wake (:,:,0:MaxPln,nt) = farm%WD(nt)%y%Vz_wake2 (:,:,0:MaxPln) ! "Vertical" wake velocity deficit at wake planes, distributed radially, for each turbine
1807+
farm%AWAE%u%D_wake ( 0:MaxPln,nt) = farm%WD(nt)%y%D_wake ( 0:MaxPln) ! Wake diameters at wake planes for each turbine
17991808
if (farm%p%WAT /= Mod_WAT_None) then
1800-
farm%AWAE%u%WAT_k(:,:,:,nt) = farm%WD(nt)%y%WAT_k ! scaling factor for each wake plane for WAT
1809+
farm%AWAE%u%WAT_k (:,:,0:MaxPln,nt) = farm%WD(nt)%y%WAT_k (:,:,0:MaxPln) ! scaling factor for each wake plane for WAT
18011810
endif
18021811
END DO
18031812

glue-codes/fast-farm/src/FAST_Farm_Types.f90

Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -52,6 +52,7 @@ MODULE FAST_Farm_Types
5252
REAL(DbKi) :: TMax = 0.0_R8Ki !< Total run time [seconds]
5353
INTEGER(IntKi) :: n_high_low = 0_IntKi !< Number of high-resolution time steps per low-resolution time step [-]
5454
INTEGER(IntKi) :: NumTurbines = 0_IntKi !< Number of turbines in the simulation [-]
55+
INTEGER(IntKi) , DIMENSION(:), ALLOCATABLE :: MaxNumPlanes !< Maximum number of wake planes for each rotor [-]
5556
CHARACTER(1024) :: WindFilePath !< Path name of wind data files from ABLSolver precursor [-]
5657
REAL(ReKi) , DIMENSION(:,:), ALLOCATABLE :: WT_Position !< X-Y-Z position of each wind turbine; index 1 = XYZ; index 2 = turbine number [meters]
5758
INTEGER(IntKi) :: WaveFieldMod = 0_IntKi !< Wave field handling (-) (switch) {0: use individual HydroDyn inputs without adjustment, 1: adjust wave phases based on turbine offsets from farm origin} [-]
@@ -218,6 +219,18 @@ subroutine Farm_CopyParam(SrcParamData, DstParamData, CtrlCode, ErrStat, ErrMsg)
218219
DstParamData%TMax = SrcParamData%TMax
219220
DstParamData%n_high_low = SrcParamData%n_high_low
220221
DstParamData%NumTurbines = SrcParamData%NumTurbines
222+
if (allocated(SrcParamData%MaxNumPlanes)) then
223+
LB(1:1) = lbound(SrcParamData%MaxNumPlanes)
224+
UB(1:1) = ubound(SrcParamData%MaxNumPlanes)
225+
if (.not. allocated(DstParamData%MaxNumPlanes)) then
226+
allocate(DstParamData%MaxNumPlanes(LB(1):UB(1)), stat=ErrStat2)
227+
if (ErrStat2 /= 0) then
228+
call SetErrStat(ErrID_Fatal, 'Error allocating DstParamData%MaxNumPlanes.', ErrStat, ErrMsg, RoutineName)
229+
return
230+
end if
231+
end if
232+
DstParamData%MaxNumPlanes = SrcParamData%MaxNumPlanes
233+
end if
221234
DstParamData%WindFilePath = SrcParamData%WindFilePath
222235
if (allocated(SrcParamData%WT_Position)) then
223236
LB(1:2) = lbound(SrcParamData%WT_Position)
@@ -381,6 +394,9 @@ subroutine Farm_DestroyParam(ParamData, ErrStat, ErrMsg)
381394
character(*), parameter :: RoutineName = 'Farm_DestroyParam'
382395
ErrStat = ErrID_None
383396
ErrMsg = ''
397+
if (allocated(ParamData%MaxNumPlanes)) then
398+
deallocate(ParamData%MaxNumPlanes)
399+
end if
384400
if (allocated(ParamData%WT_Position)) then
385401
deallocate(ParamData%WT_Position)
386402
end if
@@ -431,6 +447,7 @@ subroutine Farm_PackParam(RF, Indata)
431447
call RegPack(RF, InData%TMax)
432448
call RegPack(RF, InData%n_high_low)
433449
call RegPack(RF, InData%NumTurbines)
450+
call RegPackAlloc(RF, InData%MaxNumPlanes)
434451
call RegPack(RF, InData%WindFilePath)
435452
call RegPackAlloc(RF, InData%WT_Position)
436453
call RegPack(RF, InData%WaveFieldMod)
@@ -512,6 +529,7 @@ subroutine Farm_UnPackParam(RF, OutData)
512529
call RegUnpack(RF, OutData%TMax); if (RegCheckErr(RF, RoutineName)) return
513530
call RegUnpack(RF, OutData%n_high_low); if (RegCheckErr(RF, RoutineName)) return
514531
call RegUnpack(RF, OutData%NumTurbines); if (RegCheckErr(RF, RoutineName)) return
532+
call RegUnpackAlloc(RF, OutData%MaxNumPlanes); if (RegCheckErr(RF, RoutineName)) return
515533
call RegUnpack(RF, OutData%WindFilePath); if (RegCheckErr(RF, RoutineName)) return
516534
call RegUnpackAlloc(RF, OutData%WT_Position); if (RegCheckErr(RF, RoutineName)) return
517535
call RegUnpack(RF, OutData%WaveFieldMod); if (RegCheckErr(RF, RoutineName)) return

0 commit comments

Comments
 (0)