Skip to content

Commit

Permalink
Debug
Browse files Browse the repository at this point in the history
  • Loading branch information
ettaka committed Sep 4, 2023
1 parent e401ba5 commit 4c822dc
Show file tree
Hide file tree
Showing 2 changed files with 32 additions and 19 deletions.
40 changes: 26 additions & 14 deletions fem/src/modules/MagnetoDynamics/WhitneyAVSolver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -176,7 +176,7 @@ SUBROUTINE WhitneyAVSolver_Init0(Model,Solver,dt,Transient)
SRDecomposition = GetLogical( SolverParams, 'Source-Reaction Decomposition', Found )
IF (Found .AND. SRDecomposition) THEN
CALL ListAddNewString( SolverParams,'Exported Variable 1','Source Potential')
CALL ListAddNewString( SolverParams,'Exported Variable 2','Source Vector Potential [Source Vector Potential:3]')
CALL ListAddNewString( SolverParams,'Exported Variable 2','-dg Source Vector Potential E [Source Vector Potential E:3]')
CALL ListAddNewString( SolverParams,'Exported Variable 3', &
'-dg Source Magnetic Flux Density E [Source Magnetic Flux Density E:3]')
END IF
Expand Down Expand Up @@ -372,7 +372,7 @@ SUBROUTINE WhitneyAVSolver( Model,Solver,dt,Transient )
REAL(KIND=dp), POINTER :: Avals(:), Vvals(:)

CHARACTER(LEN=MAX_NAME_LEN):: CoilCurrentName
TYPE(Variable_t), POINTER :: CoilCurrentVar, BVar
TYPE(Variable_t), POINTER :: CoilCurrentVar, BsVar, AsVar
REAL(KIND=dp) :: CurrAmp
LOGICAL :: UseCoilCurrent, ElemCurrent, ElectroDynamics, EigenSystem
LOGICAL :: SRDecomposition=.FALSE.
Expand Down Expand Up @@ -536,8 +536,10 @@ SUBROUTINE WhitneyAVSolver( Model,Solver,dt,Transient )
CALL Fatal( 'WhitneyAVSolver', 'Memory allocation error.' )
END IF

BVar => VariableGet(Solver % Mesh % Variables, &
BsVar => VariableGet(Solver % Mesh % Variables, &
'source magnetic flux density e [source magnetic flux density e:3]', ThisOnly=.TRUE., UnFoundFatal=.TRUE.)
AsVar => VariableGet(Solver % Mesh % Variables, &
'source vector potential e [source vector potential e:3]', ThisOnly=.TRUE., UnFoundFatal=.TRUE.)
END IF

IF(ALLOCATED(FORCE)) THEN
Expand Down Expand Up @@ -1933,6 +1935,12 @@ SUBROUTINE LocalMatrix( MASS, DAMP, STIFF, FORCE, JFixFORCE, JFixVec, LOAD, &
BLOCK
REAL(KIND=dp) :: SRDAatIp(3)
REAL(KIND=dp) :: Weight
INTEGER :: ind(n)

ind(1:np) = AsVar % Perm(Element % DGIndexes(1:np))

FORCE = 0.0_dp
MASS = 0.0_dp

DO t=1,IP % n
stat = ElementInfo( Element, Nodes, IP % U(t), IP % V(t), &
Expand All @@ -1941,6 +1949,10 @@ SUBROUTINE LocalMatrix( MASS, DAMP, STIFF, FORCE, JFixFORCE, JFixVec, LOAD, &

SRDAatIp(1:3) = MATMUL( SRDA(1:3,1:n), Basis(1:n) )

DO k = 1,AsVar % DOFs
AsVar % Values( AsVar % DOFs*(ind(t)-1)+k) = SRDAatIp(k)
END DO

Weight = detJ*IP % s(t)

DO p=1,nd-np
Expand All @@ -1954,33 +1966,33 @@ SUBROUTINE LocalMatrix( MASS, DAMP, STIFF, FORCE, JFixFORCE, JFixVec, LOAD, &
CALL LuSolve(nd-np,MASS(1:6,1:6),FORCE(1:6))
Asloc(1:nd-np)=FORCE(1:nd-np)

FORCE = 0.0_dp
MASS = 0.0_dp
END BLOCK
FORCE = 0.0_dp
MASS = 0.0_dp


BLOCK
REAL(KIND=dp) :: Bs_dofs(n,3)
INTEGER :: ind(n)

ind(1:np) = BVar % Perm(Element % DGIndexes(1:np))
ind(1:np) = BsVar % Perm(Element % DGIndexes(1:np))

DO t=1,IP % n
stat = ElementInfo( Element, Nodes, IP % U(t), IP % V(t), &
IP % W(t), detJ, Basis, dBasisdx, EdgeBasis = WBasis, &
RotBasis = RotWBasis, USolver = pSolver )

Bs_dofs(t, 1:3) = MATMUL( Asloc(1:nd-np), RotWBasis(1:nd-np,:) )
! DO k = 1,BVar % DOFs
! BVar % Values( BVar % DOFs*(ind(t)-1)+k) = Bs_dofs(t, k)
! END DO
END DO

DO j = 1,n
DO k = 1,BVar % DOFs
BVar % Values( BVar % DOFs*(ind(j)-1)+k) = k
DO k = 1,BsVar % DOFs
BsVar % Values( BsVar % DOFs*(ind(t)-1)+k) = Bs_dofs(t, k)
END DO
END DO

! DO j = 1,n
! DO k = 1,BsVar % DOFs
! BsVar % Values( BsVar % DOFs*(ind(j)-1)+k) = Bs_dofs(j, k)
! END DO
! END DO
END BLOCK

END IF
Expand Down
11 changes: 6 additions & 5 deletions fem/tests/mgdyn_sr_decomp/sif/box.sif
Original file line number Diff line number Diff line change
Expand Up @@ -101,13 +101,14 @@ End
Body Force 1
!Source Vector Potential 1 = Variable Coordinate 1
! Real Procedure "source" "SourceFunX"
Source Vector Potential 1 = Variable Coordinate 2
Real MATC "tx"
! Source Vector Potential 1 = Variable Coordinate 2
! Real MATC "tx"
!Source Vector Potential 2 = Variable Coordinate 1
! Real Procedure "source" "SourceFunY"
Source Vector Potential 2 = Variable Coordinate 1
Real MATC "0"
Source Vector Potential 3 = Real 0
! Source Vector Potential 2 = Variable Coordinate 1
! Real MATC "0"
Source Vector Potential 3 = Variable Coordinate 1
Real MATC "tx"
Source Potential = Real 0
End Body Force
Boundary Condition 1 !---- BCn Flux Parallel
Expand Down

0 comments on commit 4c822dc

Please sign in to comment.