Skip to content

Commit

Permalink
Merge pull request loganoz#91 from luzpaz/typos
Browse files Browse the repository at this point in the history
Fix typos
  • Loading branch information
loganoz authored Sep 27, 2022
2 parents 8013f1e + b94a98e commit d95e02c
Show file tree
Hide file tree
Showing 14 changed files with 66 additions and 66 deletions.
14 changes: 7 additions & 7 deletions Solver/src/addons/tools/FWHPreSurface.f90
Original file line number Diff line number Diff line change
Expand Up @@ -182,7 +182,7 @@ Subroutine extractSurface(mesh, controlVariables)
globaleIDs, useFilter)
numberOfElements = size(eIDs)

! get the firs faces ids and construct the faces
! get the first faces ids and construct the faces
! ----------------------------------------------
allocate(firstFIDs(numberOfElements))
allocate(firstFaces(numberOfElements))
Expand Down Expand Up @@ -707,7 +707,7 @@ End Subroutine getFirstFace
!
!////////////////////////////////////////////////////////////////////////
!
Subroutine getAdditionalElements(mesh, BCeID, numberOfElements, zoneMarkers, zN, newEIDs, realNumberOfElemts)
Subroutine getAdditionalElements(mesh, BCeID, numberOfElements, zoneMarkers, zN, newEIDs, realNumberOfElements)

use ElementConnectivityDefinitions, only: normalAxis, FACES_PER_ELEMENT
use ElementClass
Expand All @@ -717,15 +717,15 @@ Subroutine getAdditionalElements(mesh, BCeID, numberOfElements, zoneMarkers, zN,
integer, intent(in) :: BCeID, numberOfElements, zN
integer, dimension(zN), intent(in) :: zoneMarkers
integer, dimension(:), allocatable, intent(out) :: newEIDs
integer, intent(out) :: realNumberOfElemts
integer, intent(out) :: realNumberOfElements

! local variables
integer :: i, j, neID, zoneID
class(Element), pointer :: e, BCe
integer :: thisMarker, fBCindex, conIndex, conNormal
integer, dimension(:), allocatable :: nEs

realNumberOfElemts = 0
realNumberOfElements = 0
BCe => mesh%elements(BCeID)

zone_loop: do i = 1, zN
Expand All @@ -745,7 +745,7 @@ Subroutine getAdditionalElements(mesh, BCeID, numberOfElements, zoneMarkers, zN,
i=1
do i = 1, numberOfElements
nEs(i) = e%eID
realNumberOfElemts = realNumberOfElemts + 1
realNumberOfElements = realNumberOfElements + 1
conNormal = normalAxis(fBCindex) * (-1)
! conIndex = findloc(normalAxis, conNormal, dim=1)
conIndex = maxloc(merge(1.0, 0.0, normalAxis == conNormal), dim=1)
Expand All @@ -756,8 +756,8 @@ Subroutine getAdditionalElements(mesh, BCeID, numberOfElements, zoneMarkers, zN,

!todo check that new bc have been reached

allocate(newEIDs(realNumberOfElemts))
newEIDs = nEs(1:realNumberOfElemts)
allocate(newEIDs(realNumberOfElements))
newEIDs = nEs(1:realNumberOfElements)
deallocate(nEs)


Expand Down
6 changes: 3 additions & 3 deletions Solver/src/addons/tools/LocalRefinementClass.f90
Original file line number Diff line number Diff line change
Expand Up @@ -23,11 +23,11 @@ Module LocalRefinement !
real(kind=RP), dimension(:,:), allocatable :: xlim ! limits for refinement in x direction
real(kind=RP), dimension(:,:), allocatable :: ylim
real(kind=RP), dimension(:,:), allocatable :: zlim
integer, dimension(:), allocatable :: Nx ! polynomial order for each selection whithin the limits in x diredirection
integer, dimension(:), allocatable :: Nx ! polynomial order for each selection within the limits in x redirection
integer, dimension(:), allocatable :: Ny
integer, dimension(:), allocatable :: Nz
integer, dimension(3) :: globalNxyz ! default polynomial order, outside the limits
integer :: lenRegions ! number of regions, it has to be the same for each diredirection
integer :: lenRegions ! number of regions, it has to be the same for each redirection

contains
procedure :: Construct => LocalRef_Construct
Expand Down Expand Up @@ -55,7 +55,7 @@ Subroutine LocalRef_Construct(self, controlVariables)
integer :: Nmax
logical :: hasZ

!get polynomial orders for all regions in all diredirections
!get polynomial orders for all regions in all redirections
NxName = trim(controlVariables%stringValueForKey("x regions orders",LINE_LENGTH))
NyName = trim(controlVariables%stringValueForKey("y regions orders",LINE_LENGTH))
NzName = trim(controlVariables%stringValueForKey("z regions orders",LINE_LENGTH))
Expand Down
26 changes: 13 additions & 13 deletions Solver/src/addons/tools/SurfaceClass.f90
Original file line number Diff line number Diff line change
Expand Up @@ -118,7 +118,7 @@ Subroutine SurfaceConstruct(self, mesh, fileName, eIDs, gIDs, fIDs, N)
self % name = RemovePath(getFileName(fileName))

allocate(self % surfaceZone)
call self % surfaceZone % CreateFicticious(-1, self % name, totalN, fIDs)
call self % surfaceZone % CreateFictitious(-1, self % name, totalN, fIDs)

allocate( self % globaleIDs(totalN), self % fIDs(totalN) )
self % globaleIDs = gIDs
Expand Down Expand Up @@ -781,7 +781,7 @@ Subroutine ElementGetNotConnectedN(self, mesh, surfaceElements, N, newFaceID)
integer :: i, j, k, numE, eID, targetEID, edgeIndex, targertEfID, faceIndex, normalFace
integer, dimension(2) :: thisFaceIndexes
class(SurfaceFace_t), pointer :: surfaceFace
integer, dimension(:), allocatable :: allElements, connectedElements, posibleElements
integer, dimension(:), allocatable :: allElements, connectedElements, possibleElements

if ( .not. self % needSecondFace ) return
newFaceID = 0
Expand Down Expand Up @@ -854,7 +854,7 @@ Subroutine ElementGetNotConnectedN(self, mesh, surfaceElements, N, newFaceID)
deallocate(allElements)

! get the element that is not connected to the already found surface
! first get the elements whith non shared edges
! first get the elements with non shared edges
allocate(allElements(numE))
targetEID = 0
i = 0
Expand All @@ -873,12 +873,12 @@ Subroutine ElementGetNotConnectedN(self, mesh, surfaceElements, N, newFaceID)
targetEID = allElements(1)
deallocate(allElements)
else
allocate(posibleElements(numE))
posibleElements = allElements(1:numE)
allocate(possibleElements(numE))
possibleElements = allElements(1:numE)
deallocate(allElements)
i = 0
pos_elems_loop: do k = 1, numE
eID = posibleElements(k)
eID = possibleElements(k)
do j = 1, NUM_OF_NEIGHBORS
if (surfaceFace % shareCorner(surfaceElements(eID) % faces(j))) cycle pos_elems_loop
end do
Expand Down Expand Up @@ -936,7 +936,7 @@ Subroutine ElementReconstructPeriodic(self)
class(SurfaceElement_t), target :: self

!local variables
class(SurfaceFace_t), pointer :: faceNew=>null(), faceOposite=>null()
class(SurfaceFace_t), pointer :: faceNew=>null(), faceOpposite=>null()
integer :: faceConnections
real(kind=RP), dimension(:,:), allocatable :: allCorners
real(kind=RP), dimension(NDIM,FACES_PER_ELEMENT) :: newCorners, notChangeCorners, oldCorners
Expand All @@ -956,7 +956,7 @@ Subroutine ElementReconstructPeriodic(self)
faceNew => self % faces(i)
cycle faces_loop
elseif (faceConnections .eq. FACES_PER_ELEMENT-2) then
faceOposite => self % faces(i)
faceOpposite => self % faces(i)
cycle faces_loop
end if
end do faces_loop
Expand All @@ -975,12 +975,12 @@ Subroutine ElementReconstructPeriodic(self)
allCorners(:,(i-1)*NODES_PER_FACE+j) = self % faces(i) % edges(j) % corners(:,1)
end do
end do
! get new and oposite corners
! get new and opposite corners
do j = 1, NODES_PER_FACE
newCorners(:,j) = faceNew % edges(j) % corners(:,1)
notChangeCorners(:,j) = faceOposite % edges(j) % corners(:,1)
notChangeCorners(:,j) = faceOpposite % edges(j) % corners(:,1)
end do
! get old corners, the ones that are not new nor oposite corners, remove duplicated
! get old corners, the ones that are not new nor opposite corners, remove duplicated
k = 0
outer: do i = 1, size(allCorners(1,:))
if (k .ge. NODES_PER_FACE) exit outer
Expand All @@ -1007,11 +1007,11 @@ Subroutine ElementReconstructPeriodic(self)

do i = 1, FACES_PER_ELEMENT
if (associated(faceNew, target=self % faces(i))) cycle
if (associated(faceOposite, target=self % faces(i))) cycle
if (associated(faceOpposite, target=self % faces(i))) cycle
call self % faces(i) % reconstructPeriod(oldCorners, newCorners, oldNewCornersMap)
end do

nullify(faceNew, faceOposite)
nullify(faceNew, faceOpposite)

End Subroutine ElementReconstructPeriodic
!
Expand Down
4 changes: 2 additions & 2 deletions Solver/src/libs/discretization/WallFunctionConnectivity.f90
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,7 @@ Subroutine Initialize_WallConnection(controlVariables, mesh)
use FileReadingUtilities, only: getCharArrayFromString
use ElementConnectivityDefinitions, only: normalAxis, FACES_PER_ELEMENT
use MPI_Process_Info
use WallFunctionDefinitions, only: Initialize_Wall_Fuction, wallFuncIndex, STD_WALL, ABL_WALL, u_tau0, useAverageV
use WallFunctionDefinitions, only: Initialize_Wall_Function, wallFuncIndex, STD_WALL, ABL_WALL, u_tau0, useAverageV
use Headers
#ifdef _HAS_MPI_
use mpi
Expand All @@ -77,7 +77,7 @@ Subroutine Initialize_WallConnection(controlVariables, mesh)
integer :: actualElementID, linkedElementID, normalIndex, oppositeIndex, oppositeNormalIndex
integer :: allFaces, ierr

call Initialize_Wall_Fuction(controlVariables, useWallFunc)
call Initialize_Wall_Function(controlVariables, useWallFunc)
if (.not. useWallFunc) then
return
end if
Expand Down
10 changes: 5 additions & 5 deletions Solver/src/libs/mesh/IBMClass.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1986,7 +1986,7 @@ end function isPointInsideTri
! This function computes the minimum distance from a point to a triangle in 3D.
! for more ditails see https://www.geometrictools.com/Documentation/DistancePoint3Triangle3.pdf
! ------------------------------------------------
subroutine MinumumPointTriDistance( Point, TriangleVertex1, TriangleVertex2, &
subroutine MinimumPointTriDistance( Point, TriangleVertex1, TriangleVertex2, &
TriangleVertex3, dist, IntersectionPoint )
use MappedGeometryClass
implicit none
Expand Down Expand Up @@ -2031,7 +2031,7 @@ subroutine MinumumPointTriDistance( Point, TriangleVertex1, TriangleVertex2, &

IntersectionPoint = bb + s*E0 + t*E1

end subroutine MinumumPointTriDistance
end subroutine MinimumPointTriDistance
!
!/////////////////////////////////////////////////////////////////////////////////////////////
!
Expand Down Expand Up @@ -2275,7 +2275,7 @@ subroutine MinimumDistance( Point, root, minDist, normal )

do i = 1, tree% NumOfObjs
index = tree% ObjsIndeces(i)
call MinumumPointTriDistance( Point, root% ObjectsList(index)% vertices(1)% coords, &
call MinimumPointTriDistance( Point, root% ObjectsList(index)% vertices(1)% coords, &
root% ObjectsList(index)% vertices(2)% coords, &
root% ObjectsList(index)% vertices(3)% coords, Dist, &
IntersPoint )
Expand Down Expand Up @@ -2348,7 +2348,7 @@ recursive subroutine MinimumDistOtherBoxes( Point, root, tree, Radius, New_minDi
if( tree% isLast ) then
do i = 1, tree% NumOfObjs
index = tree% ObjsIndeces(i)
call MinumumPointTriDistance( Point, root% ObjectsList(index)% vertices(1)% coords, &
call MinimumPointTriDistance( Point, root% ObjectsList(index)% vertices(1)% coords, &
root% ObjectsList(index)% vertices(2)% coords, &
root% ObjectsList(index)% vertices(3)% coords, Dist, &
IntersPoint )
Expand All @@ -2372,7 +2372,7 @@ end subroutine MinimumDistOtherBoxes
!/////////////////////////////////////////////////////////////////////////////////////////////
!
! ---------------------------------------------------------------------------------------------------
! This subroutine checks if a the sphere whit radius minDist is inside the box or not. If it's not
! This subroutine checks if a sphere with radius minDist is inside the box or not. If it's not
! a/ circle/s is/are computed. Each circle is the base of a cylinder used to find possible boxes that
! can intersect the sphere.
! ---------------------------------------------------------------------------------------------------
Expand Down
2 changes: 1 addition & 1 deletion Solver/src/libs/mesh/KDClass.f90
Original file line number Diff line number Diff line change
Expand Up @@ -327,7 +327,7 @@ end subroutine KDtree_plotBlock
!
! -------------------------------------------------
! This subroutine sets up the starting box of the tree which is called root.
! It coincides whit the OBB if PointList not present.
! It coincides with the OBB if PointList not present.
! ------------------------------------------------
subroutine KDtree_SetUpRoot( this, stl, Vertices, PointList )

Expand Down
8 changes: 4 additions & 4 deletions Solver/src/libs/mesh/SurfaceMesh.f90
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
!//////////////////////////////////////////////////////
!
!This module handle the ficticious surfaces that will be export to save solution of a set of faces, such as slices and FWH acoustic analogy
!This module handle the fictitious surfaces that will be export to save solution of a set of faces, such as slices and FWH acoustic analogy
! The solution is saved before the first time step and at a fixed dt

#include "Includes.h"
Expand Down Expand Up @@ -31,7 +31,7 @@ Module SurfaceMesh
integer :: numberOfSurfaces
integer, dimension(:), allocatable :: totalFaces ! number of faces in all partitions for each surface
integer, dimension(:), allocatable :: surfaceTypes ! type of each surface
type(Zone_t), dimension(:), allocatable :: zones ! ficticious zones that contains the faces of each surface
type(Zone_t), dimension(:), allocatable :: zones ! fictitious zones that contains the faces of each surface
logical, dimension(:), allocatable :: surfaceActive ! flag for each surface
logical, dimension(:), allocatable :: isNoSlip ! flag use for calculate and save variables of noslip bc
character(len=LINE_LENGTH), dimension(:), allocatable :: file_names
Expand Down Expand Up @@ -314,7 +314,7 @@ Subroutine SurfConstruct(self, controlVariables, mesh)
! ------------------
if ( .not. MPI_Process % isRoot ) return
if (hasFWH .and. .not. (hasBC .or. hasSliceX .or. hasSliceY .or. hasSliceZ)) return
call Subsection_Header("Ficticious surfaces zone")
call Subsection_Header("Fictitious surfaces zone")
write(STD_OUT,'(30X,A,A28,I0)') "->", "Number of surfaces: ", self % numberOfSurfaces
if (.not. all(self % surfaceActive)) write(STD_OUT,'(30X,A,A28,I0)') "->", "Inactive surfaces: ", count(.not. self % surfaceActive, dim=1)
write(STD_OUT,'(30X,A,A28,I0)') "->", "Number of slices: ", idSliceX + idSliceY + idSliceZ
Expand Down Expand Up @@ -598,7 +598,7 @@ Subroutine createSingleSurface(self, surface_index, surface_type, file_name, zon
self % file_names(surface_index) = trim(file_name)
! not set active nor create zone if there are no faces
if (no_of_faces .le. 0) return
call self % zones(surface_index) % CreateFicticious(-1, trim(zone_name), no_of_faces, facesIDs)
call self % zones(surface_index) % CreateFictitious(-1, trim(zone_name), no_of_faces, facesIDs)
self % surfaceActive(surface_index) = .true.
self % isNoSlip(surface_index) = isNoSlip

Expand Down
8 changes: 4 additions & 4 deletions Solver/src/libs/mesh/ZoneClass.f90
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ module ZoneClass
procedure :: Initialize => Zone_Initialize
procedure :: copy => Zone_Assign
generic :: assignment(=) => copy
procedure :: CreateFicticious => Zone_CreateFicticious
procedure :: CreateFictitious => Zone_CreateFictitious
end type Zone_t

contains
Expand Down Expand Up @@ -226,8 +226,8 @@ elemental subroutine Zone_Assign (to, from)
to % faces = from % faces
end subroutine Zone_Assign

! create a ficticious zone, useful to represent ficticious surfaces such as slices or FWH analogy
Subroutine Zone_CreateFicticious(self, marker, zoneName, no_of_faces, facesID)
! create a fictitious zone, useful to represent fictitious surfaces such as slices or FWH analogy
Subroutine Zone_CreateFictitious(self, marker, zoneName, no_of_faces, facesID)

implicit none
class(Zone_t) :: self
Expand All @@ -241,6 +241,6 @@ Subroutine Zone_CreateFicticious(self, marker, zoneName, no_of_faces, facesID)
allocate(self % faces(no_of_faces))
self % faces = facesID

End Subroutine Zone_CreateFicticious
End Subroutine Zone_CreateFictitious

end module ZoneClass
2 changes: 1 addition & 1 deletion Solver/src/libs/monitors/FWHGeneralClass.f90
Original file line number Diff line number Diff line change
Expand Up @@ -144,7 +144,7 @@ Subroutine FWHConstruct(self, mesh, controlVariables)
! Describe the zones
! ------------------
if ( .not. MPI_Process % isRoot ) return
call Subsection_Header("Ficticious FWH zone")
call Subsection_Header("Fictitious FWH zone")
write(STD_OUT,'(30X,A,A28,I0)') "->", "Number of faces: ", no_of_faces
write(STD_OUT,'(30X,A,A28,I0)') "->", "Number of observers: ", self % numberOfObservers
write(STD_OUT,'(30X,A,A28,I0)') "->", "Number of integrals: ", self % numberOfObservers * no_of_faces
Expand Down
2 changes: 1 addition & 1 deletion Solver/src/libs/monitors/FWHObseverClass.f90
Original file line number Diff line number Diff line change
Expand Up @@ -64,7 +64,7 @@ Module FWHObseverClass !
real(kind=RP), dimension(NDIM) :: x ! position of the observer at global coordinates
integer :: numberOfFaces
class(ObserverSourcePairClass), dimension(:), allocatable :: sourcePair
real(kind=RP), dimension(:,:), allocatable :: Pac ! acoustic pressure, two componenets and the total (sum)
real(kind=RP), dimension(:,:), allocatable :: Pac ! acoustic pressure, two components and the total (sum)
real(kind=RP) :: tDelay
real(kind=RP) :: tDelayMax
logical :: active
Expand Down
Loading

0 comments on commit d95e02c

Please sign in to comment.