Skip to content

Commit

Permalink
Merge pull request #7 from ptrbortolotti/noise
Browse files Browse the repository at this point in the history
It looks good, thanks!
  • Loading branch information
ebranlard authored Sep 9, 2019
2 parents 8faf1cd + f633ee5 commit 6f09bfd
Show file tree
Hide file tree
Showing 5 changed files with 30 additions and 163 deletions.
149 changes: 6 additions & 143 deletions modules/aerodyn/src/AeroAcoustics/AeroAcoustics.f90
Original file line number Diff line number Diff line change
Expand Up @@ -84,7 +84,7 @@ subroutine AA_Init( InitInp, u, p, x, xd, z, OtherState, y, m, Interval, InitOut
p%RootName = TRIM(InitInp%RootName)//'.NN'

! Read the primary AeroAcoustics input file in AeroAcoustics_IO
call ReadInputFiles( InitInp%InputFile, InputFileData, interval, p%RootName, p%NumBlades, UnEcho, ErrStat2, ErrMsg2 )
call ReadInputFiles( InitInp%InputFile, InitInp%AFInfo%BL_file, InputFileData, interval, p%RootName, p%NumBlades, UnEcho, ErrStat2, ErrMsg2 )
if (Failed()) return

! Validate the inputs
Expand Down Expand Up @@ -166,8 +166,6 @@ subroutine SetParameters( InitInp, InputFileData, p, ErrStat, ErrMsg )
p%NrOutFile = InputFileData%NrOutFile
p%delim = " "
p%outFmt = "ES15.6E3"
p%LargeBinOutput = InputFileData%LargeBinOutput
p%TxtFileOutput = InputFileData%TxtFileOutput
p%NumBlNds = InitInp%NumBlNds
p%AirDens = InitInp%AirDens
p%KinVisc = InitInp%KinVisc
Expand Down Expand Up @@ -197,7 +195,7 @@ subroutine SetParameters( InitInp, InputFileData, p, ErrStat, ErrMsg )
tri=.true.
IF( (p%ITURB.eq.2) .or. (p%IInflow.gt.1) )then
! if tno is on or one of the guidati models is on, check if we have airfoil coordinates
DO k=1,size(p%AFInfo) ! if any of the airfoil coordinates are missing change calucaltion method
DO k=1,size(p%AFInfo) ! if any of the airfoil coordinates are missing change calculation method
IF( (size(p%AFInfo(k)%X_Coord) .lt. 5) .or. (size(p%AFInfo(k)%Y_Coord).lt.5) )then
IF (tri) then ! Print the message for once only
print*, 'Airfoil coordinates are missing: If Full or Simplified Guidati or Bl Calculation is on coordinates are needed '
Expand All @@ -209,7 +207,7 @@ subroutine SetParameters( InitInp, InputFileData, p, ErrStat, ErrMsg )
ENDIF
ENDDO
ENDIF

! Check 2
! if passed the first check and if tno or full guidati model is still on, turn on boundary layer calculation
IF( (p%ITURB.eq.2) .or. (p%IInflow.eq.2) )then
Expand Down Expand Up @@ -710,18 +708,7 @@ subroutine AA_UpdateStates( t, n, m, u, p, xd, errStat, errMsg )
ENDIF
enddo
enddo
IF (p%TxtFileOutput .eqv. .TRUE.) THEN
IF (n .eq. 0) THEN
open (123401,file='RegionTIDelete.bin',access='stream',form='unformatted',status='REPLACE') !open a binary file
write(123401) Size(xd%RegionTIDelete,1)
write(123401) Size(xd%RegionTIDelete,2)
write(123401) xd%RegionTIDelete
ELSE
open (123401, file="RegionTIDelete.bin", access='stream',status="old", form='unformatted',position="append")
write(123401) xd%RegionTIDelete
ENDIF
close(123401)
ENDIF

ELSE! interpolate from the user given ti values
do i=1,p%NumBlades
do j=1,p%NumBlNds
Expand Down Expand Up @@ -870,25 +857,6 @@ SUBROUTINE CalcObserve(p,m,u,xd,nt,errStat,errMsg)
m%LE_Location(3,J,I) = RLEObservereal(3) ! the height of leading edge
IF (nt.gt.p%Comp_AA_after) THEN
IF ( (mod(nt,p%saveeach).eq.0) ) THEN
IF (p%TxtFileOutput .eqv. .TRUE.) THEN
inquire(file="RTEObserve.txt", exist=exist)
if (exist) then
open(1254, file="RTEObserve.txt", status="old", position="append", action="write")
else
open(1254, file="RTEObserve.txt", status="new", action="write")
end if
write(1254, *) RTEObservereal
close(1254)

inquire(file="RLEObserve.txt", exist=exist)
if (exist) then
open(1254, file="RLEObserve.txt", status="old", position="append", action="write")
else
open(1254, file="RLEObserve.txt", status="new", action="write")
end if
write(1254, *) RLEObservereal
close(1254)
ENDIF

DO K = 1,p%NrObsLoc
! Calculate position vector from leading and trailing edge to observer in retarded trailing edge coordinate system
Expand Down Expand Up @@ -1030,53 +998,6 @@ SUBROUTINE CalcAeroAcousticsOutput(u,p,m,xd,y,errStat,errMsg)
!!!ENDIF


IF (p%TxtFileOutput .eqv. .TRUE.) THEN
inquire(file="alpha.txt", exist=exist)
if (exist) then
open(1254, file="alpha.txt", status="old", position="append", action="write")
else
open(1254, file="alpha.txt", status="new", action="write")
end if
write(1254, *) u%AoANoise* R2D_D
close(1254)

inquire(file="TIVrel.txt", exist=exist)
if (exist) then
open(1254, file="TIVrel.txt", status="old", position="append", action="write")
else
open(1254, file="TIVrel.txt", status="new", action="write")
end if
write(1254, *) xd%TIVrel
close(1254)

inquire(file="TIVx.txt", exist=exist)
if (exist) then
open(1254, file="TIVx.txt", status="old", position="append", action="write")
else
open(1254, file="TIVx.txt", status="new", action="write")
end if
write(1254, *) xd%TIVx
close(1254)

inquire(file="Inflow1.txt", exist=exist)
if (exist) then
open(1254, file="Inflow1.txt", status="old", position="append", action="write")
else
open(1254, file="Inflow1.txt", status="new", action="write")
end if
write(1254, *) u%Inflow(1,:,:)
close(1254)

inquire(file="Vrel.txt", exist=exist)
if (exist) then
open(1254, file="Vrel.txt", status="old", position="append", action="write")
else
open(1254, file="Vrel.txt", status="new", action="write")
end if
write(1254, *) u%Vrel
close(1254)
ENDIF


DO I = 1,p%numBlades
DO J = p%startnode,p%NumBlNds ! starts loop from startnode.
Expand Down Expand Up @@ -1311,66 +1232,6 @@ SUBROUTINE CalcAeroAcousticsOutput(u,p,m,xd,y,errStat,errMsg)
y%SumSpecNoiseSep = 10.*LOG10(y%SumSpecNoiseSep) ! P to SPL Conversion
ENDIF

!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
IF (p%LargeBinOutput .eqv. .TRUE.) THEN
IF (m%filesopen.eq.0) THEN
open (12340,file='ForMaxLoc3.bin',access='stream',form='unformatted',status='REPLACE') !open a binary file
write(12340) Size(ForMaxLoc3,1)
write(12340) Size(ForMaxLoc3,2)
write(12340) Size(ForMaxLoc3,3)
write(12340) Size(ForMaxLoc3,4)
write(12340) Size(ForMaxLoc3,5)
write(12340) ForMaxLoc3
ELSE
open (12340, file="ForMaxLoc3.bin", access='stream',status="old", form='unformatted',position="append")
write(12340) ForMaxLoc3
ENDIF
close(12340)
ENDIF
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
IF (p%TxtFileOutput .eqv. .TRUE.) THEN
IF (m%filesopen.eq.0) THEN
open (54218,file='SourceLoc.bin',access='stream',form='unformatted',status='REPLACE') !open a binary file
write(54218) Size(y%OutLECoords,1)
write(54218) Size(y%OutLECoords,2)
write(54218) Size(y%OutLECoords,3)
write(54218) Size(y%OutLECoords,4)
write(54218) y%OutLECoords

open (25684,file='SPL_Out.bin',access='stream',form='unformatted',status='REPLACE') !open a binary file
write(25684) Size(SPL_Out,1)
write(25684) Size(SPL_Out,2)
write(25684) Size(SPL_Out,3)
write(25684) SPL_Out
m%filesopen=1
ELSE
open (54218, file="SourceLoc.bin", access='stream',status="old", form='unformatted',position="append")
write(54218) y%OutLECoords

open (25684, file="SPL_Out.bin", access='stream',status="old", form='unformatted',position="append")
write(25684) SPL_Out
ENDIF
close(54218)
close(25684)

inquire(file="tempdispthick.txt", exist=exist)
if (exist) then
open(1254, file="tempdispthick.txt", status="old", position="append", action="write")
else
open(1254, file="tempdispthick.txt", status="new", action="write")
end if
write(1254, *) temp_dispthick
close(1254)

inquire(file="tempdispthickchord.txt", exist=exist)
if (exist) then
open(1254, file="tempdispthickchord.txt", status="old", position="append", action="write")
else
open(1254, file="tempdispthickchord.txt", status="new", action="write")
end if
write(1254, *) temp_dispthickchord
close(1254)
ENDIF
END SUBROUTINE CalcAeroAcousticsOutput
!==================================================================================================================================!
SUBROUTINE LBLVS(ALPSTAR,C,U,THETA,PHI,L,R,p,d99Var2,dstarVar1,dstarVar2,SPLLAM,errStat,errMsg)
Expand Down Expand Up @@ -2526,6 +2387,7 @@ SUBROUTINE BL_Param_Interp(p,m,U,AlphaNoise,C,whichairfoil, errStat, errMsg)

if (AlphaNoise .gt. p%AOAListBL(size(p%AOAListBL))) then
print*, 'Warning AeroAcoustics Module - Angle of attack (AoA) range is not in the range provided by the user'
print*, 'Station ',whichairfoil
print*, 'Airfoil AoA ',AlphaNoise,' Using the closest AoA ',p%AOAListBL(loop2+1)
m%dStarVar (1) = ( p%dstarall1 (loop2+1,loop1+1,whichairfoil)*redif2 + p%dstarall1 (loop2+1,loop1,whichairfoil)*redif1 )/(redif1+redif2)
m%dStarVar (2) = ( p%dstarall2 (loop2+1,loop1+1,whichairfoil)*redif2 + p%dstarall2 (loop2+1,loop1,whichairfoil)*redif1 )/(redif1+redif2)
Expand All @@ -2537,6 +2399,7 @@ SUBROUTINE BL_Param_Interp(p,m,U,AlphaNoise,C,whichairfoil, errStat, errMsg)
m%EdgeVelVar(2) = ( p%EdgeVelRat2(loop2+1,loop1+1,whichairfoil)*redif2 + p%EdgeVelRat2(loop2+1,loop1,whichairfoil)*redif1 )/(redif1+redif2)
elseif (AlphaNoise .lt. p%AOAListBL(1)) then
print*, 'Warning AeroAcoustics Module - Angle of attack (AoA) range is not in the range provided by the user'
print*, 'Station ',whichairfoil
print*, 'Airfoil AoA ',AlphaNoise,' Using the closest AoA ',p%AOAListBL(1)
m%dStarVar(1) = ( p%dstarall1 (1,loop1+1,whichairfoil)*redif2 + p%dstarall1 (1,loop1,whichairfoil)*redif1 ) / (redif1+redif2)
m%dStarVar(2) = ( p%dstarall2 (1,loop1+1,whichairfoil)*redif2 + p%dstarall2 (1,loop1,whichairfoil)*redif1 ) / (redif1+redif2)
Expand Down
23 changes: 11 additions & 12 deletions modules/aerodyn/src/AeroAcoustics/AeroAcoustics_IO.f90
Original file line number Diff line number Diff line change
Expand Up @@ -91,13 +91,14 @@ MODULE AeroAcoustics_IO
INTEGER(IntKi), PARAMETER :: MaxOutPts = 1103
contains
!----------------------------------------------------------------------------------------------------------------------------------
SUBROUTINE ReadInputFiles( InputFileName, InputFileData, Default_DT, OutFileRoot, NumBlades, UnEcho, ErrStat, ErrMsg )
SUBROUTINE ReadInputFiles( InputFileName, BL_Files, InputFileData, Default_DT, OutFileRoot, NumBlades, UnEcho, ErrStat, ErrMsg )
! This subroutine reads the input file and stores all the data in the AA_InputFile structure.
! It does not perform data validation.
!..................................................................................................................................
! Passed variables
REAL(DbKi), INTENT(IN) :: Default_DT ! The default DT (from glue code)
CHARACTER(*), INTENT(IN) :: InputFileName ! Name of the input file
CHARACTER(*), INTENT(IN) :: InputFileName ! Name of the aeroacoustics input file
CHARACTER(*), dimension(:), INTENT(IN) :: BL_Files ! Name of the BL input file
CHARACTER(*), INTENT(IN) :: OutFileRoot ! The rootname of all the output files written by this routine.
TYPE(AA_InputFile), INTENT(OUT) :: InputFileData ! Data stored in the module's input file
INTEGER(IntKi), INTENT(OUT) :: UnEcho ! Unit number for the echo file
Expand All @@ -115,6 +116,7 @@ SUBROUTINE ReadInputFiles( InputFileName, InputFileData, Default_DT, OutFileRoot
ErrMsg = ''
UnEcho = -1
InputFileData%DTAero = Default_DT ! the glue code's suggested DT for the module (may be overwritten in ReadPrimaryFile())


! Reads the module input-file data
CALL ReadPrimaryFile( InputFileName, InputFileData, AABlFile, OutFileRoot, UnEcho, ErrStat2, ErrMsg2 )
Expand All @@ -135,7 +137,7 @@ SUBROUTINE ReadInputFiles( InputFileName, InputFileData, Default_DT, OutFileRoot

if ((InputFileData%ITURB.eq.2) .or. (InputFileData%X_BLMethod.eq.2)) then
! We need to read the BL tables
CALL ReadBLTables( InputFileName,InputFileData, InputFileData%BladeProps(1)%NumBlNds, ErrStat2, ErrMsg2 )
CALL ReadBLTables( InputFileName, BL_Files, InputFileData, InputFileData%BladeProps(1)%NumBlNds, ErrStat2, ErrMsg2 )
if (Failed())return
endif

Expand Down Expand Up @@ -317,8 +319,6 @@ SUBROUTINE ReadPrimaryFile( InputFile, InputFileData, AABlFile, OutFileRoot, Un
! one file name is given by the user and the XXFile1.out XXFile2.out XXFile3.out is generated
IF ( PathIsRelative( InputFileData%AAOutFile(I) ) ) InputFileData%AAOutFile(I) = TRIM(PriPath)//TRIM(InputFileData%AAOutFile(1))//TRIM(Num2Lstr(I))//".out"
ENDDO
CALL ReadVar(UnIn,InputFile,InputFileData%LargeBinOutput,'LargeBinOutput','LargeBinOutput',ErrStat2,ErrMsg2,UnEc); call check
CALL ReadVar(UnIn,InputFile,InputFileData%TxtFileOutput, 'TxtFileOutput', 'TxtFileOutput', ErrStat2,ErrMsg2,UnEc); call check

! Return on error at end of section
IF ( ErrStat >= AbortErrLev ) THEN
Expand Down Expand Up @@ -421,10 +421,11 @@ subroutine ReadRealMatrix(fid, FileName, Mat, VarName, nLines,nRows, iStat, Msg,



SUBROUTINE ReadBLTables( InputFile,InputFileData, nAirfoils, ErrStat, ErrMsg )
SUBROUTINE ReadBLTables( InputFile,BL_Files,InputFileData, nAirfoils, ErrStat, ErrMsg )
! Passed variables
character(*), intent(in) :: InputFile ! Name of the file containing the primary input data
type(AA_InputFile), intent(inout) :: InputFileData ! All the data in the Noise input file
character(*), dimension(:), intent(in) :: BL_Files ! Name of the file containing the primary input data
type(AA_InputFile), intent(inout) :: InputFileData ! All the data in the Noise input file
integer(IntKi), intent(in) :: nAirfoils ! Number of Airfoil tables
integer(IntKi), intent(out) :: ErrStat ! Error status
character(*), intent(out) :: ErrMsg ! Error message
Expand All @@ -449,11 +450,9 @@ SUBROUTINE ReadBLTables( InputFile,InputFileData, nAirfoils, ErrStat, ErrMsg )
CALL GetPath( InputFile, PriPath ) ! Input files will be relative to the path where the primary input file is located.

do iAF=1,nAirfoils
if (InputFileData%ITRIP.eq.0) then
FileName = TRIM(PriPath)//'AirfoilsModified/AF'//TRIM(Num2LStr(iAF))//'BL_TripMod0.txt'
ELSE
FileName = TRIM(PriPath)//'AirfoilsModified/AF'//TRIM(Num2LStr(iAF))//'BL_TripMod1.txt'
ENDIF

FileName = trim(BL_Files(iAF))

print*,'AeroAcoustics_IO: reading BL table:'//trim(Filename)

CALL GetNewUnit(UnIn, ErrStat2, ErrMsg2); if(Failed()) return
Expand Down
3 changes: 0 additions & 3 deletions modules/aerodyn/src/AeroAcoustics_Registry.txt
Original file line number Diff line number Diff line change
Expand Up @@ -78,8 +78,6 @@ typedef ^ AA_InputFile ReKi ObsZ
typedef ^ AA_InputFile AA_BladePropsType BladeProps {:} - - "blade property information from blade input files" -
typedef ^ AA_InputFile IntKi NrOutFile - - - "Nr of output files" -
typedef ^ AA_InputFile CHARACTER(1024) AAoutfile {:} - - "AAoutfile for writing output files" -
typedef ^ AA_InputFile Logical LargeBinOutput - - - "Flag for output bin file " -
typedef ^ AA_InputFile Logical TxtFileOutput - - - "Flag for output txt files"
typedef ^ AA_InputFile IntKi Comp_AA_After - - - " " -
typedef ^ AA_InputFile ReKi SaveEach - - - " " -
typedef ^ AA_InputFile ReKi z0_AA - - - "Surface roughness" -
Expand Down Expand Up @@ -176,7 +174,6 @@ typedef ^ ParameterType ReKi rotorre
typedef ^ ParameterType ReKi rotorregionlimitsrad {:} - - ""
typedef ^ ParameterType IntKi NrObsLoc - - - "Number of observer locations " -
typedef ^ ParameterType Logical aweightflag - - - " " -
typedef ^ ParameterType Logical LargeBinOutput - - - " " -
typedef ^ ParameterType Logical TxtFileOutput - - - " " -
typedef ^ ParameterType IntKi Comp_AA_After - - - " " -
typedef ^ ParameterType ReKi ObsX {:} - - "Observer location in tower-base coordinate X horizontal" m
Expand Down
17 changes: 12 additions & 5 deletions modules/aerodyn/src/AirfoilInfo.f90
Original file line number Diff line number Diff line change
Expand Up @@ -517,11 +517,13 @@ SUBROUTINE ReadAFfile ( AFfile, NumCoefs, InCol_Alfa, InCol_Cl, InCol_Cd, InCol_
CHARACTER(ErrMsgLen) :: ErrMsg2
CHARACTER(*), PARAMETER :: RoutineName = 'ReadAFfile'
CHARACTER(10) :: defaultStr

CHARACTER(1024) :: PriPath

ErrStat = ErrID_None
ErrMsg = ""
defaultStr = ""

! Getting parent folder of airfoils data (e.g. "Arifoils/")
CALL GetPath( AFFile, PriPath )
! Process the (possibly) nested set of files. This copies the decommented contents of
! AFI_FileInfo%FileName and the files it includes (both directly and indirectly) into
! the FileInfo structure that we can then parse.
Expand Down Expand Up @@ -585,9 +587,14 @@ SUBROUTINE ReadAFfile ( AFfile, NumCoefs, InCol_Alfa, InCol_Cl, InCol_Cd, InCol_
ENDDO ! Row

ENDIF


! How many columns do we need to read in the input and how many total coefficients will be used?


CALL ParseVar ( FileInfo, CurLine, 'BL_file' , AFInfo%BL_file , ErrStat2, ErrMsg2, UnEc )
CALL SetErrStat( ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName )

AFInfo%BL_file=trim(PriPath)//trim(AFInfo%BL_file)

! How many columns do we need to read in the input and how many total coefficients will be used?

Cols2Parse = MAX( InCol_Alfa, InCol_Cl, InCol_Cd, InCol_Cm, InCol_Cpmin )
ALLOCATE ( SiAry( Cols2Parse ) , STAT=ErrStat2 )
Expand Down
1 change: 1 addition & 0 deletions modules/aerodyn/src/AirfoilInfo_Registry.txt
Original file line number Diff line number Diff line change
Expand Up @@ -90,6 +90,7 @@ typedef ^ ^ INTEGER NumClReKts - - - "The number of log(Re) knots for 2D splines
typedef ^ ^ INTEGER NumCmAoAkts - - - "The number of angle-of-attack knots for 2D splines of Cm" -
typedef ^ ^ INTEGER NumCmReKts - - - "The number of log(Re) knots for 2D splines of Cm" -
typedef ^ ^ INTEGER NumCoords - - - "The number of coordinates in the airfoil-shape table" -
typedef ^ ^ CHARACTER(1024) BL_file - - - "The name of the file with the boundary layer data" -
typedef ^ ^ INTEGER NumCpminAoAkts - - - "The number of angle-of-attack knots for 2D splines of Cpmin" -
typedef ^ ^ INTEGER NumCpminReKts - - - "The number of log(Re) knots for 2D splines of Cpmin" -
typedef ^ ^ INTEGER NumTabs - - - "The number of airfoil tables in the airfoil file" -
Expand Down

0 comments on commit 6f09bfd

Please sign in to comment.