Skip to content
This repository was archived by the owner on Aug 28, 2024. It is now read-only.

Commit

Permalink
Browse files Browse the repository at this point in the history
Fixed small bugs
  • Loading branch information
daminton committed May 25, 2021
1 parent c3120d5 commit 2e7df1d
Show file tree
Hide file tree
Showing 2 changed files with 9 additions and 16 deletions.
21 changes: 7 additions & 14 deletions src/modules/module_interfaces.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1103,20 +1103,13 @@ end subroutine symba_rearray


INTERFACE
SUBROUTINE symba_reorder_pl(npl, symba_plA)
USE swiftest_globals
USE swiftest_data_structures
USE module_helio
USE module_symba
IMPLICIT NONE
INTEGER(I4B), INTENT(IN) :: npl
TYPE(symba_pl), INTENT(INOUT) :: symba_plA
INTEGER(I4B) :: i
INTEGER(I4B), DIMENSION(:), ALLOCATABLE :: index
REAL(DP), DIMENSION(:), ALLOCATABLE :: mass
REAL(DP), DIMENSION(:,:), allocatable :: symba_plwkspA
INTEGER(I4B), DIMENSION(:,:), allocatable :: symba_plwkspA_id_status
END SUBROUTINE symba_reorder_pl
subroutine symba_reorder_pl(npl, symba_plA)
use swiftest_globals
use module_symba
implicit NONE
integer(I4B), intent(in) :: npl
type(symba_pl), intent(inout) :: symba_plA
end subroutine symba_reorder_pl
END INTERFACE

INTERFACE
Expand Down
4 changes: 2 additions & 2 deletions src/symba/symba_frag_pos.f90
Original file line number Diff line number Diff line change
Expand Up @@ -417,7 +417,7 @@ subroutine calculate_system_energy(linclude_fragments)
logical, intent(in) :: linclude_fragments
! Internals
real(DP) :: ke_orbit, ke_spin, pe, te
real(DP), dimension(NDIM) :: Ltot, Lorbit, Lspin
real(DP), dimension(NDIM) :: Lorbit, Lspin
integer(I4B) :: i, npl_new, nplm
logical, dimension(:), allocatable :: ltmp
logical :: lk_plpl
Expand Down Expand Up @@ -499,7 +499,7 @@ subroutine calculate_system_energy(linclude_fragments)
end do
ke_target = ke_family + (ke_spin_before - ke_spin) + (pe_before - pe) - Qloss
ke_offset = ke_frag - ke_target
L_offset(:) = Ltot_before(:) - Ltot(:)
L_offset(:) = Ltot_before(:) - Ltot_after(:)
else
Ltot_before(:) = Lorbit(:) + Lspin(:)
Lmag_before = norm2(Ltot_before(:))
Expand Down

0 comments on commit 2e7df1d

Please sign in to comment.