Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
8 changes: 6 additions & 2 deletions src/modules/BaseType/src/BaseType.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1471,11 +1471,15 @@ END SUBROUTINE highorder_refelem
!! number of shape functions
REAL(DFP), ALLOCATABLE :: N(:, :)
!! Shape function value `N(I, ips)`
!! nrow = nns
!! ncol = nips
!! shape: (nns, nips)
!! dim 1 = number of nodes in element
!! dim 2 = number of integration points
REAL(DFP), ALLOCATABLE :: dNdXi(:, :, :)
!! Local derivative of a shape function
!! shape = nns, xidim, nips
!! dim 1 = number of nodes in element
!! dim 2 = xi dimension (xi, eta, zeta)
!! dim 3 = number of integration points
REAL(DFP), ALLOCATABLE :: jacobian(:, :, :)
!! Jacobian of mapping `J(:,:,ips)` also $\mathbf{F}_{\Xi x}$
!! shape = nsd, xidim, nips
Expand Down
19 changes: 10 additions & 9 deletions src/modules/ElemshapeData/src/ElemshapeData_Method.F90
Original file line number Diff line number Diff line change
Expand Up @@ -20,15 +20,6 @@ MODULE ElemshapeData_Method
USE ElemshapeData_GetMethods
USE ElemshapeData_GradientMethods

! USE ElemshapeData_H1Methods
! USE ElemshapeData_HCurlMethods
! USE ElemshapeData_HDivMethods
! USE ElemshapeData_DGMethods

USE ElemshapeData_Lagrange
USE ElemshapeData_Hierarchical
USE ElemshapeData_Orthogonal

USE ElemshapeData_HRGNParamMethods
USE ElemshapeData_HRQIParamMethods
USE ElemshapeData_HminHmaxMethods
Expand All @@ -41,4 +32,14 @@ MODULE ElemshapeData_Method
USE ElemshapeData_StabilizationParamMethods
USE ElemshapeData_UnitNormalMethods

! USE ElemshapeData_H1Methods
! USE ElemshapeData_HCurlMethods
! USE ElemshapeData_HDivMethods
! USE ElemshapeData_DGMethods

USE ElemshapeData_Lagrange
USE ElemshapeData_Hierarchical
USE ElemshapeData_Orthogonal


END MODULE ElemshapeData_Method
3 changes: 3 additions & 0 deletions src/modules/ElemshapeData/src/ElemshapeData_SetMethods.F90
Original file line number Diff line number Diff line change
Expand Up @@ -242,6 +242,9 @@ MODULE PURE SUBROUTINE stsd_SetJacobian(obj, val, dNdXi, T)
CLASS(STElemshapeData_), INTENT(INOUT) :: obj
REAL(DFP), INTENT(IN) :: val(:, :, :)
!! Space time nodal values of coordinates
!! dim1 = spatial coordinates
!! dim2 = space nodes
!! dim3 = time nodes
REAL(DFP), INTENT(IN) :: dNdXi(:, :, :)
!! Local derivative of shape function for geometry
REAL(DFP), INTENT(IN) :: T(:)
Expand Down
15 changes: 15 additions & 0 deletions src/modules/IntVector/src/IntVector_GetMethod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -395,6 +395,21 @@ MODULE FUNCTION intVec_getPointer_2(obj, datatype) RESULT(val)
END FUNCTION intVec_getPointer_2
END INTERFACE GetPointer

!----------------------------------------------------------------------------
! GetPointers@getMethod
!----------------------------------------------------------------------------

!> author: Vikas Sharma, Ph. D.
! date: 2025-05-29
! summary: Get the pointer to the raw data of the IntVector instance.

INTERFACE GetPointer
MODULE FUNCTION intVec_getPointer_3(obj) RESULT(val)
CLASS(IntVector_), INTENT(IN), TARGET :: obj
INTEGER(I4B), POINTER :: val(:)
END FUNCTION intVec_getPointer_3
END INTERFACE GetPointer

!----------------------------------------------------------------------------
! getIndex@getMethod
!----------------------------------------------------------------------------
Expand Down
36 changes: 29 additions & 7 deletions src/modules/QuadraturePoint/src/QuadraturePoint_Method.F90
Original file line number Diff line number Diff line change
Expand Up @@ -193,10 +193,12 @@ END SUBROUTINE obj_Initiate3

!> author: Vikas Sharma, Ph. D.
! date: 23 July 2021
! summary: This routine Initiates the quadrature points
! summary: This routine Initiates the quadrature points from number of IP
!
!# Introduction
!
! This routine is used to initiate the quadrature points from number of
! integration points.
! We call obj_Initiate6 in this routine

INTERFACE Initiate
Expand All @@ -207,7 +209,7 @@ MODULE SUBROUTINE obj_Initiate4(obj, refElem, nips, quadratureType, &
CLASS(ReferenceElement_), INTENT(IN) :: refElem
!! Reference element
INTEGER(I4B), INTENT(IN) :: nips(1)
!! order of integrand
!! number of quadrature points
CHARACTER(*), INTENT(IN) :: quadratureType
!! Total number quadrature points
REAL(DFP), OPTIONAL, INTENT(IN) :: alpha
Expand Down Expand Up @@ -366,6 +368,17 @@ END SUBROUTINE obj_Initiate8
!
!----------------------------------------------------------------------------

!> author: Vikas Sharma, Ph. D.
! date: 2025-05-21
! summary: This routine Initiates the quadrature points
!
!# Introduction
!
! This routine is used to initiate the quadrature points from order of
! of integrand.
! This subroutine does not require formation of reference element.
! This routine calls obj_Initiate11 method.

INTERFACE Initiate
MODULE SUBROUTINE obj_Initiate9(obj, elemType, domainName, order, &
quadratureType, alpha, beta, lambda, xij)
Expand All @@ -374,9 +387,8 @@ MODULE SUBROUTINE obj_Initiate9(obj, elemType, domainName, order, &
INTEGER(I4B), INTENT(IN) :: elemType
!! element name
CHARACTER(*), INTENT(IN) :: domainName
!! domain name
!! domain name for reference element
!! unit or biunit
!! Reference-element
INTEGER(I4B), INTENT(IN) :: order
!! order of integrand
INTEGER(I4B), INTENT(IN) :: quadratureType
Expand All @@ -398,6 +410,17 @@ END SUBROUTINE obj_Initiate9
!
!----------------------------------------------------------------------------

!> author: Vikas Sharma, Ph. D.
! date: 2025-05-21
! summary: This routine Initiates the quadrature points
!
!# Introduction
!
! This routine is used to initiate the quadrature points from number of
! integration points.
! This subroutine does not require formation of reference element.
! This routine calls obj_Initiate12 method.

INTERFACE Initiate
MODULE SUBROUTINE obj_Initiate10(obj, elemType, domainName, nips, &
quadratureType, alpha, beta, lambda, xij)
Expand All @@ -406,11 +429,10 @@ MODULE SUBROUTINE obj_Initiate10(obj, elemType, domainName, nips, &
INTEGER(I4B), INTENT(IN) :: elemType
!! element name
CHARACTER(*), INTENT(IN) :: domainName
!! domain name
!! domain name, reference element
!! unit or biunit
!! Reference-element
INTEGER(I4B), INTENT(IN) :: nips(1)
!! order of integrand
!! Number of integration points
!! in the case of quadrangle element nips(1) denotes the
!! number of quadrature points in the x and y direction
!! so the total number of quadrature points are nips(1)*nips(1)
Expand Down
31 changes: 24 additions & 7 deletions src/modules/String/src/String_Class.F90
Original file line number Diff line number Diff line change
Expand Up @@ -312,18 +312,16 @@ MODULE String_Class
PROCEDURE, PASS(self) :: tempname
!! Return a safe temporary name suitable for temporary file
!! or directories.
GENERIC :: to_number => &
to_integer_I1P, &
GENERIC :: to_number => to_integer_I1P, to_integer_I4P, to_integer_I8P, &
to_real_R8P, to_real_R4P, &
#ifndef _NVF
to_integer_I2P, &
#endif
to_integer_I4P, &
to_integer_I8P, &
#ifdef _R16P
to_real_R16P, &
#endif
to_real_R8P, &
to_real_R4P
to_logical_1

!! Cast string to number.
PROCEDURE, PASS(self) :: unescape
!! Unescape double backslashes (or custom escaped character).
Expand Down Expand Up @@ -475,7 +473,7 @@ MODULE String_Class
!! Cast string to real.
PROCEDURE, PRIVATE, PASS(self) :: to_real_R16P
!! Cast string to real.
PROCEDURE, PUBLIC, PASS(self) :: to_logical
PROCEDURE, PUBLIC, PASS(self) :: to_logical, to_logical_1
!! Convert a string to logical
! assignments
PROCEDURE, PRIVATE, PASS(lhs) :: string_assign_string
Expand Down Expand Up @@ -3169,6 +3167,25 @@ END FUNCTION tempname
!
!----------------------------------------------------------------------------

!> author: Vikas Sharma, Ph. D.
! date: 2025-05-29
! summary: Cast string to logical

ELEMENTAL FUNCTION to_logical_1(self, kind) RESULT(ans)
CLASS(string), INTENT(IN) :: self
!! The string.
LOGICAL, INTENT(IN) :: kind
!! Mold parameter for kind detection.
LOGICAL :: ans
!! The number into the string.

ans = self%to_logical()
END FUNCTION to_logical_1

!----------------------------------------------------------------------------
!
!----------------------------------------------------------------------------

!> author: Vikas Sharma, Ph. D.
! date: 23 July 2022
! summary: Cast string to integer (I1P).
Expand Down
14 changes: 11 additions & 3 deletions src/submodules/ElemshapeData/src/[email protected]
Original file line number Diff line number Diff line change
Expand Up @@ -49,14 +49,19 @@
!----------------------------------------------------------------------------

MODULE PROCEDURE elemsd_SetBarycentricCoord
obj%coord(1:obj%nsd, 1:obj%nips) = MATMUL(val, N)
INTEGER(I4B) :: nns
nns = SIZE(N, 1)
obj%coord(1:obj%nsd, 1:obj%nips) = MATMUL(val(1:obj%nsd, 1:nns), &
N(1:nns, 1:obj%nips))
END PROCEDURE elemsd_SetBarycentricCoord

!----------------------------------------------------------------------------
! SetBarycentricCoord
!----------------------------------------------------------------------------

MODULE PROCEDURE stsd_SetBarycentricCoord
! TODO: Improve this function by removing the temporary variable
! It is better to store a temporary variable in obj itself
CALL SetBarycentricCoord(obj=obj, val=MATMUL(val, T), N=N)
END PROCEDURE stsd_SetBarycentricCoord

Expand Down Expand Up @@ -136,15 +141,18 @@
!----------------------------------------------------------------------------

MODULE PROCEDURE elemsd_SetJacobian
obj%jacobian(1:obj%nsd, 1:obj%xidim, 1:obj%nips) = MATMUL(val, dNdXi)
obj%jacobian(1:obj%nsd, 1:obj%xidim, 1:obj%nips) = &
MATMUL(val(1:obj%nsd, 1:obj%nns), dNdXi(1:obj%nns, 1:obj%xidim, 1:obj%nips))
END PROCEDURE elemsd_SetJacobian

!----------------------------------------------------------------------------
! SetJacobian
!----------------------------------------------------------------------------

MODULE PROCEDURE stsd_SetJacobian
obj%jacobian = MATMUL(MATMUL(val, T), dNdXi)
obj%jacobian(1:obj%nsd, 1:obj%xidim, 1:obj%nips) = &
MATMUL(MATMUL(val(1:obj%nsd, 1:obj%nns, :), T), &
dNdXi(1:obj%nns, 1:obj%xidim, 1:obj%nips))
END PROCEDURE stsd_SetJacobian

!----------------------------------------------------------------------------
Expand Down
Loading
Loading