Skip to content

Commit 06b5c3e

Browse files
committed
Merge branch 'wip_swapmesh_changenodetype' into 'master'
change NodeType in Swapmesh Tool See merge request flexi/flexi!709
2 parents 757443a + 8ddef2b commit 06b5c3e

File tree

4 files changed

+30
-8
lines changed

4 files changed

+30
-8
lines changed

posti/swapmesh/interpolatesolution.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,7 @@ SUBROUTINE InterpolateSolution()
4444
USE MOD_Basis, ONLY: LagrangeInterpolationPolys,BarycentricWeights
4545
USE MOD_Interpolation, ONLY: GetNodesAndWeights
4646
USE MOD_SwapMesh_Vars, ONLY: equalElem,Vdm_GPNState_GPNNew
47-
USE MOD_SwapMesh_Vars, ONLY: NState,NInter,NNew,NodeTypeState,RefState,nVar_State
47+
USE MOD_SwapMesh_Vars, ONLY: NState,NInter,NNew,NodeTypeState,RefState,nVar_State,NodeTypeOut
4848
USE MOD_SwapMesh_Vars, ONLY: Vdm_CLNInter_GPNNew
4949
USE MOD_SwapMesh_Vars, ONLY: UOld,xiInter,InterToElem,nElemsNew,IPDone
5050
USE MOD_SwapMesh_Vars, ONLY: Elem_IJK,ExtrudeTo3D,ExtrudeK
@@ -99,7 +99,7 @@ SUBROUTINE InterpolateSolution()
9999
! Equal elements
100100
IF(equalElem(iElemNew).GT.0) THEN
101101
iElemOld=equalElem(iElemNew)
102-
IF(NState.EQ.NNew)THEN
102+
IF((NState.EQ.Nnew).AND.(NodeTypeOut.EQ.NodetypeState))THEN
103103
U(:,:,:,:,iElemNew)=UOld(:,:,:,:,iElemOld)
104104
ELSE
105105
CALL ChangeBasisVolume(nVar_State,NState,NNew,Vdm_GPNState_GPNNew,UOld(:,:,:,:,iElemOld),U(:,:,:,:,iElemNew))

posti/swapmesh/posti_swapmesh.f90

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -70,6 +70,8 @@ PROGRAM swapMesh
7070
"high-order data and treat curved meshes as linear meshes.", '.TRUE.')
7171
CALL prms%CreateLogicalOption( "useCurvedsNew" , "Controls usage of high-order information in new mesh. Turn off to discard "//&
7272
"high-order data and treat curved meshes as linear meshes.", '.TRUE.')
73+
CALL prms%CreateStringOption( "NodeTypeNew " , "Change nodetype, tested for switching betwee GAUSS and GAUSS-LOBATTO "//&
74+
"on the same mesh.")
7375
CALL prms%CreateIntOption( "NInter" , "Polynomial degree used for interpolation on new mesh (should be equal or "//&
7476
"higher than NNew) - the state will be interpolated to this degree and then "//&
7577
"projected down to NNew")

posti/swapmesh/swapmesh.f90

Lines changed: 25 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -98,6 +98,8 @@ SUBROUTINE InitSwapmesh()
9898
! New mesh file, the state will be interpolated to this one
9999
MeshFileNew = GETSTR('MeshFileNew')
100100

101+
NodeTypeOut = GETSTR('NodeTypeNew',NodeTypeState)
102+
101103
! Curved meshes or not
102104
useCurvedsOld = GETLOGICAL("useCurvedsOld")
103105
useCurvedsNew = GETLOGICAL("useCurvedsNew")
@@ -307,7 +309,7 @@ END SUBROUTINE ReadMeshCoords
307309
SUBROUTINE prepareVandermonde()
308310
! MODULES
309311
USE MOD_Swapmesh_Vars, ONLY: NInter,NNew,NState,NState,NGeoOld,NGeoNew,NSuper
310-
USE MOD_Swapmesh_Vars, ONLY: NodeTypeState,nElemsNew,xCLInter
312+
USE MOD_Swapmesh_Vars, ONLY: NodeTypeState,nElemsNew,xCLInter,NodeTypeOut
311313
USE MOD_Swapmesh_Vars, ONLY: Vdm_CLNGeo_EquiNSuper,Vdm_CLNInter_GPNNew,Vdm_GPNState_GPNNew
312314
USE MOD_Swapmesh_Vars, ONLY: xCLNew
313315
USE MOD_Interpolation, ONLY: GetVandermonde
@@ -330,12 +332,12 @@ SUBROUTINE prepareVandermonde()
330332

331333
! Vandermonde from interpolation CL to new solution G/GL
332334
ALLOCATE(Vdm_CLNInter_GPNNew(0:NNew,0:NInter))
333-
CALL GetVandermonde(NInter,NodeTypeCL,NNew,NodeType,Vdm_CLNInter_GPNNew)
335+
CALL GetVandermonde(NInter,NodeTypeCL,NNew,NodeTypeOut,Vdm_CLNInter_GPNNew)
334336

335337
! Vandermonde for direct interpolation in equal elements
336-
IF(NNew.NE.NState)THEN
338+
IF((NNew.NE.NState).OR.(NodeTypeState.NE.NodeTypeOut))THEN
337339
ALLOCATE(Vdm_GPNState_GPNNew(0:NNew,0:NState))
338-
CALL GetVandermonde(NState,NodeTypeState,NNew,NodeType,Vdm_GPNState_GPNNew)
340+
CALL GetVandermonde(NState,NodeTypeState,NNew,NodeTypeOut,Vdm_GPNState_GPNNew)
339341
END IF
340342

341343
IF(NGeoNew.NE.NInter)THEN
@@ -471,15 +473,32 @@ END SUBROUTINE ReadOldStateFile
471473
!===================================================================================================================================
472474
SUBROUTINE WriteNewStateFile()
473475
! MODULES !
474-
USE MOD_HDF5_Output, ONLY: WriteState
475-
USE MOD_Swapmesh_Vars, ONLY: Time_State,MeshFileNew
476+
USE MOD_PreProc
477+
USE MOD_Globals
478+
USE MOD_IO_HDF5
479+
USE MOD_HDF5_Output
480+
USE MOD_Output_Vars, ONLY: ProjectName
481+
USE MOD_Swapmesh_Vars, ONLY: Time_State,MeshFileNew,NodeTypeOut,NodeTypeState
476482
!----------------------------------------------------------------------------------------------------------------------------------!
477483
IMPLICIT NONE
478484
! INPUT / OUTPUT VARIABLES
479485
!-----------------------------------------------------------------------------------------------------------------------------------
480486
! LOCAL VARIABLES
487+
CHARACTER(LEN=255) :: FileName,FileType
488+
481489
!===================================================================================================================================
482490
CALL WriteState(TRIM(MeshFileNew),Time_State,Time_State,isErrorFile=.FALSE.)
491+
492+
! Update the nodetype attribute in the State file, delete old attri and rewrite
493+
IF (NodeTypeOut.NE.NodeTypeState) THEN
494+
SWRITE(UNIT_stdOut,'(A)') "Updating NodeType in Statefile to new NodeType."
495+
FileType=MERGE('ERROR_State','State ',.FALSE.)
496+
FileName=TRIM(TIMESTAMP(TRIM(ProjectName)//'_'//TRIM(FileType),Time_State))//'.h5'
497+
CALL OpenDataFile(FileName,create=.FALSE.,single=.TRUE.,readOnly=.FALSE.)
498+
CALL H5ADELETE_F( File_ID,'NodeType',iError)
499+
CALL WriteAttribute(File_ID,'NodeType',1,StrScalar=(/NodeTypeOut/))
500+
CALL CloseDataFile()
501+
END IF
483502
END SUBROUTINE WriteNewStateFile
484503

485504
!===================================================================================================================================

posti/swapmesh/swapmesh_vars.f90

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -48,6 +48,7 @@ MODULE MOD_SwapMesh_Vars
4848
INTEGER :: NNew !< Polynomial degree of new state (=NState, if not specified otherwise)
4949
INTEGER :: NInter !< Polynomial degree for interpolation on new mesh (=NState, if not specified otherwise)
5050
CHARACTER(LEN=255) :: NodeTypeState !< NodeType of the old state (Gauss/Gauss-Lobatto)
51+
CHARACTER(LEN=255) :: NodeTypeOut !< NodeType of the output state (Gauss/Gauss-Lobatto)
5152
LOGICAL :: useCurvedsOld !< Should the old mesh use a curved mesh representation?
5253
LOGICAL :: useCurvedsNew !< Should the new mesh use a curved mesh representation?
5354
REAL,ALLOCATABLE :: RefState(:) !< Optional reference state used for points that can not be fond

0 commit comments

Comments
 (0)