Skip to content

Commit

Permalink
Removes CompileWithNodalSource flag
Browse files Browse the repository at this point in the history
  • Loading branch information
lmdiazangulo committed Nov 6, 2024
1 parent 1271e11 commit d44c2c3
Show file tree
Hide file tree
Showing 6 changed files with 12 additions and 63 deletions.
1 change: 0 additions & 1 deletion CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -143,7 +143,6 @@ add_definitions(
-DCompileWithAnisotropic
-DCompileWithEDispersives
-DCompileWithNF2FF
-DCompileWithNodalSources
-DCompileWithDMMA
-DCompileWithSGBC
-DCompileWithWires
Expand Down
8 changes: 0 additions & 8 deletions src_main_pub/errorreport.F90
Original file line number Diff line number Diff line change
Expand Up @@ -299,14 +299,6 @@ subroutine ReportExistence(sgg,layoutnumber,size,thereare,mur_second,MurAfterPML

call print11(layoutnumber,SEPARADOR//sEPARADOR//SEPARADOR)
!!!
if ((thereare%NodalE).or.(thereare%NodalH)) then
#ifdef CompileWithNodalSources
continue
#else
buff=trim(adjustl(whoami))//' Nodal sources unsupported. Recompile'
call stoponerror(layoutnumber,size,buff)
#endif
endif
!
IF (thereare%FarFields) then
#ifdef CompileWithNF2FF
Expand Down
9 changes: 2 additions & 7 deletions src_main_pub/interpreta_switches.F90
Original file line number Diff line number Diff line change
Expand Up @@ -5,9 +5,7 @@ module interpreta_switches_m
use EpsMuTimeScale_m
use Report
use version
! #ifdef CompilePrivateVersion
! use ParseadorClass
! #endif

IMPLICIT NONE
PRIVATE
!
Expand Down Expand Up @@ -1733,11 +1731,8 @@ subroutine print_help(l)
#else
!CALL print11 (l%layoutnumber, 'UNSUPPORTED: Loaded and grounded thin-wires with juntions')
#endif
#ifdef CompileWithNodalSources
CALL print11 (l%layoutnumber, 'SUPPORTED: Nodal hard/soft electric and magnetic sources')
#else
!CALL print11 (l%layoutnumber, 'UNSUPPORTED: Nodal hard/soft electric and magnetic sources')
#endif

#ifdef CompileWithHDF
CALL print11 (l%layoutnumber, 'SUPPORTED: .xdmf+.h5 probes ')
#else
Expand Down
4 changes: 0 additions & 4 deletions src_main_pub/nodalsources.F90
Original file line number Diff line number Diff line change
Expand Up @@ -29,8 +29,6 @@

module nodalsources

#ifdef CompileWithNodalSources

use fdetypes
USE REPORT

Expand Down Expand Up @@ -772,7 +770,5 @@ subroutine InitHopf(sgg,NumNodalSources,sggNodalSource,sggSweep,ficherohopf)
return
end subroutine InitHopf

#endif

END MODULE nodalsources

27 changes: 5 additions & 22 deletions src_main_pub/observation.F90
Original file line number Diff line number Diff line change
Expand Up @@ -54,9 +54,7 @@ module Observa
#ifdef CompileWithNF2FF
use farfield_m
#endif
#ifdef CompileWithNodalSources
use nodalsources
#endif
!
IMPLICIT NONE
private
Expand Down Expand Up @@ -1310,10 +1308,8 @@ subroutine InitObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,s
if (field==mapvtk) then
INIT=.TRUE.; geom=.false. ; asigna=.false.; magnetic=.false. ; electric=.true.

#ifdef CompileWithNodalSources
call nodalvtk(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,sggMtag, &
init,geom,asigna,electric,magnetic,conta,i,ii,output,Ntimeforvolumic)
#endif

#ifdef CompileWithWires
call wirebundlesvtk(sgg,init,geom,asigna,conta,i,ii,output,Ntimeforvolumic,wiresflavor,sggMtag)
Expand Down Expand Up @@ -1375,10 +1371,9 @@ subroutine InitObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,s
!!!
if (field==mapvtk) then
INIT=.false.; geom=.false. ; asigna=.false.; magnetic=.true. ; electric=.false.
#ifdef CompileWithNodalSources
call nodalvtk(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,sggMtag, &
init,geom,asigna,electric,magnetic,conta,i,ii,output,Ntimeforvolumic)
#endif

endif
!!!
output(ii)%item(i)%columnas=conta
Expand Down Expand Up @@ -1623,10 +1618,8 @@ subroutine InitObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,s
!!!
if (field==mapvtk) then
INIT=.false.; geom=.true. ; asigna=.false.; magnetic=.false. ; electric=.true.
#ifdef CompileWithNodalSources
call nodalvtk(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,sggMtag,&
init,geom,asigna,electric,magnetic,conta,i,ii,output,Ntimeforvolumic)
#endif
#ifdef CompileWithWires
call wirebundlesvtk(sgg,init,geom,asigna,conta,i,ii,output,Ntimeforvolumic,wiresflavor,sggMtag)
#endif
Expand Down Expand Up @@ -1733,10 +1726,9 @@ subroutine InitObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,s
!!!
if (field==mapvtk) then
INIT=.false.; geom=.true. ; asigna=.false.; magnetic=.true. ; electric=.false.
#ifdef CompileWithNodalSources
call nodalvtk(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,sggMtag,&
init,geom,asigna,electric,magnetic,conta,i,ii,output,Ntimeforvolumic)
#endif

endif
!!!
my_iostat=0
Expand Down Expand Up @@ -3466,10 +3458,9 @@ subroutine UpdateObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz
!!!
if (field==mapvtk) then
INIT=.false.; geom=.false. ; asigna=.true.; magnetic=.false. ; electric=.true.
#ifdef CompileWithNodalSources
call nodalvtk(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,sggMtag,&
init,geom,asigna,electric,magnetic,conta,i,ii,output,Ntimeforvolumic)
#endif

#ifdef CompileWithWires
call wirebundlesvtk(sgg,init,geom,asigna,conta,i,ii,output,Ntimeforvolumic,wiresflavor,sggMtag)
#endif
Expand All @@ -3488,9 +3479,9 @@ subroutine UpdateObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz
(dzh(KKK ) * Hz( III , JJJ , KKK ) + dzh(KKK +1) *Hz( III , JJJ , KKK +1) )/1.0_RKIND + &
dxh(III )*( Hx( III , JJJ , KKK +1) - Hx( III , JJJ , KKK -1) )/1.0_RKIND
!el Hx al promediarlo con el suyo (i,j,k) a ambos lados pierde su componente y solo quedan las adyacentes
!a pesar de ser lógico tengo dudas de esa division por 2 caso tiras guada 0824 !?!?
!a pesar de ser l�gico tengo dudas de esa division por 2 caso tiras guada 0824 !?!?
!he quitado la division por 2 porque el lazo debe tragarse los lados de la celda
!otro tema sería la resta de la corriente de desplazamiento ahora que tambien calculamos campo electrico es posible 020824
!otro tema ser�a la resta de la corriente de desplazamiento ahora que tambien calculamos campo electrico es posible 020824
Jz=(dyh(JJJ ) * Hy( III , JJJ , KKK ) + dyh(JJJ +1) *Hy( III , JJJ +1, KKK ) )/1.0_RKIND - &
(dyh(JJJ ) * Hy( III -1, JJJ , KKK ) + dyh(JJJ +1) *Hy( III -1, JJJ +1, KKK ) )/1.0_RKIND + &
dxh(III )*( Hx( III , JJJ -1, KKK ) - Hx( III , JJJ +1, KKK ) )/1.0_RKIND
Expand Down Expand Up @@ -3669,10 +3660,8 @@ subroutine UpdateObservation(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz
!!!
if (field==mapvtk) then
INIT=.false.; geom=.false. ; asigna=.true.; magnetic=.true. ; electric=.false.
#ifdef CompileWithNodalSources
call nodalvtk(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,sggMtag, &
init,geom,asigna,electric,magnetic,conta,i,ii,output,Ntimeforvolumic)
#endif
endif
!!!
!!!!!!!!!!!!esto dara problemas en los angulos y aristas donde porque ahi sacara la Bloque current en Hx!!!! 19/2/14
Expand Down Expand Up @@ -4815,10 +4804,6 @@ subroutine contabordes(sgg,imed,imed1,imed2,imed3,imed4,EsBorde,SINPML_fullsize,
return
end subroutine contabordes




#ifdef CompileWithNodalSources
subroutine nodalvtk(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,sggMtag, &
init,geom,asigna,electric,magnetic,conta,i,ii,output,Ntimeforvolumic)
type (SGGFDTDINFO), intent(IN) :: sgg
Expand Down Expand Up @@ -5184,8 +5169,6 @@ subroutine nodalvtk(sgg,sggMiEx,sggMiEy,sggMiEz,sggMiHx,sggMiHy,sggMiHz,sggMtag,
return
end subroutine

#endif
!del CompileWithNodalSources


#ifdef CompileWithWires
Expand Down
26 changes: 5 additions & 21 deletions src_main_pub/timestepping.F90
Original file line number Diff line number Diff line change
Expand Up @@ -50,10 +50,7 @@ module Solver
use Borders_CPML
use Borders_MUR
use Resuming

#ifdef CompileWithNodalSources
use nodalsources
#endif
use Lumped
use PMLbodies
#ifdef CompileWithXDMF
Expand Down Expand Up @@ -1024,8 +1021,6 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx
write(dubuf,*) '----> no Plane waves are found'; call print11(layoutnumber,dubuf)
endif

#ifdef CompileWithNodalSources
!debe venir antes para que observation las use en mapvtk
#ifdef CompileWithMPI
call MPI_Barrier(SUBCOMM_MPI,ierr)
#endif
Expand All @@ -1050,8 +1045,6 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx
write(dubuf,*) '----> no Structured Nodal sources are found'; call print11(layoutnumber,dubuf)
endif

#endif

!!!!!!!sgg 121020 !rellena la matriz Mtag con los slots de una celda
call fillMtag(sgg, sggMiEx, sggMiEy, sggMiEz, sggMiHx, sggMiHy, sggMiHz,sggMtag, b)
!!!!!!!fin
Expand Down Expand Up @@ -1518,16 +1511,13 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx
endif
endif


#ifdef CompileWithNodalSources
!NOdal sources E-field advancing
!Nodal sources E-field advancing
If (Thereare%NodalE) then
! if (.not.simu_devia) then !bug! debe entrar en nodal y si son hard simplemente ponerlas a cero !mdrc 290323
call AdvanceNodalE(sgg,sggMiEx,sggMiEy,sggMiEz,sgg%NumMedia,n, b,G2,Idxh,Idyh,Idzh,Ex,Ey,Ez,simu_devia)
! endif
! if (.not.simu_devia) then !bug! debe entrar en nodal y si son hard simplemente ponerlas a cero !mdrc 290323
call AdvanceNodalE(sgg,sggMiEx,sggMiEy,sggMiEz,sgg%NumMedia,n, b,G2,Idxh,Idyh,Idzh,Ex,Ey,Ez,simu_devia)
! endif
endif

#endif


!!!!!!!!!!!!!!!!!!
Expand Down Expand Up @@ -1693,17 +1683,13 @@ subroutine launch_simulation(sgg,sggMtag,sggMiNo,sggMiEx,sggMiEy,sggMiEz,sggMiHx

endif


#ifdef CompileWithNodalSources
!NOdal sources E-field advancing
!Nodal sources E-field advancing
If (Thereare%NodalH) then
!! if (.not.simu_devia) then !bug! debe entrar en nodal y si son hard simplemente ponerlas a cero !mdrc 290323
call AdvanceNodalH(sgg,sggMiHx,sggMiHy,sggMiHz,sgg%NumMedia,n, b ,GM2,Idxe,Idye,Idze,Hx,Hy,Hz,simu_devia)
!! endif
endif

#endif

!Must be called here again at the end to enforce any of the previous changes
!Posible Wire for thickwires advancing in the H-field part
#ifdef CompileWithWires
Expand Down Expand Up @@ -3272,9 +3258,7 @@ subroutine Destroy_All_exceptSGGMxx(sgg,Ex, Ey, Ez, Hx, Hy, Hz,G1,G2,GM1,GM2,dxe
REAL (KIND=RKIND), intent(INOUT) , pointer, dimension ( : ) :: G1,G2,GM1,GM2,dxe ,dye ,dze ,Idxe ,Idye ,Idze ,dxh ,dyh ,dzh ,Idxh ,Idyh ,Idzh

call DestroyObservation(sgg)
#ifdef CompileWithNodalSources
Call DestroyNodal(sgg)
#endif
call DestroyIlumina(sgg)
#ifdef CompileWithNIBC
call DestroyMultiports(sgg)
Expand Down

0 comments on commit d44c2c3

Please sign in to comment.