Skip to content

Commit 2bfad84

Browse files
Merge pull request #336 from easifem-fortran/vickysharma0812
Minor fixes in Kernels
2 parents 51c9ce5 + e262673 commit 2bfad84

File tree

3 files changed

+38
-18
lines changed

3 files changed

+38
-18
lines changed

src/modules/AbstractKernel/src/KernelAssembleSurfaceForce_Method.F90

Lines changed: 6 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -112,7 +112,7 @@ SUBROUTINE KernelAssembleSurfaceForce2(rhs, dom, nbcPtrs, funcPtrs, fe, &
112112
CLASS(FiniteElement_), POINTER :: spaceFE, linSpaceFE
113113
CLASS(NeumannBC_), POINTER :: nbc
114114
CLASS(UserFunction_), POINTER :: func
115-
LOGICAL(LGT) :: problem, isNormal, isTangent
115+
LOGICAL(LGT) :: problem, isNormal, isTangent, isSelectionByMeshID
116116
INTEGER(I4B) :: tmesh, nsd, id, nns, iel, tnbc, nbcNo, idof, jd, &
117117
& returnType, tfunc
118118
INTEGER(I4B), ALLOCATABLE :: nptrs(:), meshID(:)
@@ -156,9 +156,10 @@ SUBROUTINE KernelAssembleSurfaceForce2(rhs, dom, nbcPtrs, funcPtrs, fe, &
156156
problem = .NOT. ASSOCIATED(nbc)
157157
IF (problem) CYCLE
158158

159-
CALL nbc%GetParam(isSelectionByMeshID=problem, &
159+
CALL nbc%GetParam(isSelectionByMeshID=isSelectionByMeshID, &
160160
& isNormal=isNormal, isTangent=isTangent)
161161

162+
problem = .NOT. isSelectionByMeshID
162163
IF (problem) THEN
163164
CALL e%RaiseInformation(modName//'::'//myName//' - '// &
164165
& '[SKIPPING] :: Currently, found isSelectionByMeshID false.')
@@ -271,7 +272,7 @@ SUBROUTINE KernelAssembleSurfaceForce3(rhs, extField, dom, nbcPtrs, fe, &
271272
CLASS(ReferenceElement_), POINTER :: refelem
272273
CLASS(FiniteElement_), POINTER :: spaceFE, linSpaceFE
273274
CLASS(NeumannBC_), POINTER :: nbc
274-
LOGICAL(LGT) :: problem, isNormal, isTangent
275+
LOGICAL(LGT) :: problem, isNormal, isTangent, isSelectionByMeshID
275276
INTEGER(I4B) :: tmesh, nsd, id, nns, iel, tnbc, nbcNo, idof, jd
276277
INTEGER(I4B), ALLOCATABLE :: nptrs(:), meshID(:)
277278
REAL(DFP), ALLOCATABLE :: fevec(:, :), xij(:, :), forceVec(:, :)
@@ -304,9 +305,10 @@ SUBROUTINE KernelAssembleSurfaceForce3(rhs, extField, dom, nbcPtrs, fe, &
304305
problem = .NOT. ASSOCIATED(nbc)
305306
IF (problem) CYCLE
306307

307-
CALL nbc%GetParam(isSelectionByMeshID=problem, &
308+
CALL nbc%GetParam(isSelectionByMeshID=isSelectionByMeshID, &
308309
& isNormal=isNormal, isTangent=isTangent)
309310

311+
problem = .NOT. isSelectionByMeshID
310312
IF (problem) THEN
311313
CALL e%RaiseInformation(modName//'::'//myName//' - '// &
312314
& '[SKIPPING] :: Currently, found isSelectionByMeshID false.')

src/submodules/AbstractBC/src/AbstractBC_Class@GetMethods.F90

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -177,10 +177,10 @@
177177

178178
MODULE PROCEDURE bc_GetQuery
179179
CALL obj%boundary%GetQuery(&
180-
& isSelectionByBox=isSelectionByBox, &
181-
& isSelectionByMeshID=isSelectionByMeshID, &
182-
& isSelectionByElemNum=isSelectionByElemNum, &
183-
& isSelectionByNodeNum=isSelectionByNodeNum)
180+
& isSelectionByBox=isSelectionByBox, &
181+
& isSelectionByMeshID=isSelectionByMeshID, &
182+
& isSelectionByElemNum=isSelectionByElemNum, &
183+
& isSelectionByNodeNum=isSelectionByNodeNum)
184184

185185
IF (PRESENT(idof)) idof = obj%idof
186186
IF (PRESENT(isTangent)) isTangent = obj%isTangent

src/submodules/AbstractKernel/src/AbstractKernel_Class@SetMethods.F90

Lines changed: 28 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -258,15 +258,12 @@
258258
& '[END] Setting Cell Finite Element.')
259259
#endif DEBUG_VER
260260

261-
CALL obj%SetQuadPointsInSpace()
262-
CALL obj%SetLocalElemShapeDataInSpace()
263-
261+
IF (nsd .GE. 2) THEN
264262
#ifdef DEBUG_VER
265-
CALL e%RaiseInformation(modName//'::'//myName//' - '// &
266-
& '[START] Setting Facet Finite Element.')
263+
CALL e%RaiseInformation(modName//'::'//myName//' - '// &
264+
& '[START] Setting Facet Finite Element.')
267265
#endif DEBUG_VER
268266

269-
IF (nsd .GE. 2) THEN
270267
elemType = obj%dom%GetElemType(dim=nsd - 1)
271268
order = obj%dom%GetOrder(dim=nsd - 1)
272269
tsize = SIZE(elemType)
@@ -312,14 +309,18 @@
312309

313310
END DO
314311

312+
#ifdef DEBUG_VER
313+
CALL e%RaiseInformation(modName//'::'//myName//' - '// &
314+
& '[END] Setting Facet Finite Element.')
315+
#endif DEBUG_VER
315316
END IF
316317

318+
IF (nsd .GE. 3) THEN
317319
#ifdef DEBUG_VER
318-
CALL e%RaiseInformation(modName//'::'//myName//' - '// &
319-
& '[END] Setting Facet Finite Element.')
320+
CALL e%RaiseInformation(modName//'::'//myName//' - '// &
321+
& '[START] Setting edge Finite Element.')
320322
#endif DEBUG_VER
321323

322-
IF (nsd .GE. 3) THEN
323324
elemType = obj%dom%GetElemType(dim=nsd - 2)
324325
order = obj%dom%GetOrder(dim=nsd - 2)
325326
tsize = SIZE(elemType)
@@ -363,9 +364,18 @@
363364
& lambda=obj%lambdaForSpace)
364365
END DO
365366

367+
#ifdef DEBUG_VER
368+
CALL e%RaiseInformation(modName//'::'//myName//' - '// &
369+
& '[END] Setting edge Finite Element.')
370+
#endif DEBUG_VER
366371
END IF
367372

368373
IF (obj%nnt .GT. 1_I4B) THEN
374+
#ifdef DEBUG_VER
375+
CALL e%RaiseInformation(modName//'::'//myName//' - '// &
376+
& '[START] Setting time Finite Element.')
377+
#endif DEBUG_VER
378+
369379
CALL obj%timeFE%InitiateLagrangeFE( &
370380
& nsd=nsd, &
371381
& elemType=Line2, &
@@ -392,8 +402,16 @@
392402

393403
CALL obj%SetQuadPointsInTime()
394404
CALL obj%SetLocalElemShapeDataInTime()
405+
406+
#ifdef DEBUG_VER
407+
CALL e%RaiseInformation(modName//'::'//myName//' - '// &
408+
& '[END] Setting time Finite Element.')
409+
#endif DEBUG_VER
395410
END IF
396411

412+
CALL obj%SetQuadPointsInSpace()
413+
CALL obj%SetLocalElemShapeDataInSpace()
414+
397415
IF (ALLOCATED(elemType)) DEALLOCATE (elemType)
398416
IF (ALLOCATED(order)) DEALLOCATE (order)
399417

@@ -456,7 +474,7 @@
456474
isok = ALLOCATED(obj%facetFE)
457475
IF (.NOT. isok) THEN
458476
CALL e%RaiseError(modName//'::'//myName//' - '// &
459-
& '[INTERNAL ERROR] :: AbstractKernel_::obj%cellFE not allocated')
477+
& '[INTERNAL ERROR] :: AbstractKernel_::obj%facetFE not allocated')
460478
RETURN
461479
END IF
462480

0 commit comments

Comments
 (0)