Skip to content

Commit

Permalink
regenerate pointers when move_alloc is used
Browse files Browse the repository at this point in the history
  • Loading branch information
aoterodelaroza committed Feb 1, 2024
1 parent 80bdf65 commit 703300c
Show file tree
Hide file tree
Showing 6 changed files with 42 additions and 13 deletions.
5 changes: 4 additions & 1 deletion src/gui/[email protected]
Original file line number Diff line number Diff line change
Expand Up @@ -510,7 +510,7 @@ module subroutine add_systems_from_seeds(nseed,seed,collapse,iafield)
use interfaces_cimgui, only: getCurrentWorkDir
use grid1mod, only: grid1_register_ae
use gui_main, only: reuse_mid_empty_systems
use windows, only: nwin, win, iwin_tree
use windows, only: nwin, win, iwin_tree, regenerate_window_pointers
use interfaces_threads, only: allocate_mtx, mtx_init, mtx_plain
use crystalseedmod, only: read_seeds_from_file, crystalseed
use tools_io, only: uout
Expand Down Expand Up @@ -592,6 +592,9 @@ module subroutine add_systems_from_seeds(nseed,seed,collapse,iafield)
sys(i)%f(j)%sptr = c_loc(sys(i))
end do
end do

! refresh window pointers
call regenerate_window_pointers()
end if

do iseed = 1, nseed
Expand Down
1 change: 0 additions & 1 deletion src/gui/scenes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -74,7 +74,6 @@ module scenes
integer :: idwin = 0 ! edit representation window ID
integer :: iord = 0 ! representation order integer in menu
character(kind=c_char,len=:), allocatable :: name ! name of the representation
type(scene), pointer :: sc ! pointer to the parent scene
! global parameters
integer(c_int) :: pertype = 1 ! periodicity control: 0=none, 1=auto, 2=manual
integer(c_int) :: ncell(3) ! number of unit cells drawn
Expand Down
3 changes: 2 additions & 1 deletion src/gui/[email protected]
Original file line number Diff line number Diff line change
Expand Up @@ -789,6 +789,7 @@ end function representation_menu
!> representations array.
module function get_new_representation_id(s) result(id)
use types, only: realloc
use windows, only: regenerate_window_pointers
class(scene), intent(inout), target :: s
integer :: id

Expand All @@ -810,6 +811,7 @@ module function get_new_representation_id(s) result(id)
aux(1:size(s%rep,1)) = s%rep
call move_alloc(aux,s%rep)
call realloc(s%iord,2*s%nrep)
call regenerate_window_pointers()
end if
id = s%nrep

Expand Down Expand Up @@ -952,7 +954,6 @@ module subroutine representation_init(r,sc,isys,irep,itype,style)
r%isinit = .false.
r%shown = .false.
r%type = reptype_none
r%sc => sc
r%id = isys
r%idrep = irep
r%idwin = 0
Expand Down
4 changes: 4 additions & 0 deletions src/gui/windows.f90
Original file line number Diff line number Diff line change
Expand Up @@ -90,6 +90,7 @@ module windows
type(c_ptr) :: ptr ! ImGuiWindow* pointer (use only after Begin())
type(c_ptr) :: dptr ! ImGuiFileDialog* pointer for dialogs
integer :: isys = 1 ! the system on which the window operates
integer :: irep = 0 ! the representation on which the window operates
real(c_float) :: pos(2) = (/0._c_float,0._c_float/) ! the position of the window's top left corner
logical :: isdocked = .false. ! whether the window is docked
real*8 :: timelastupdate ! time the window data was last updated
Expand Down Expand Up @@ -251,6 +252,7 @@ module windows
public :: stack_realloc_maybe
public :: stack_create_window
public :: update_window_id
public :: regenerate_window_pointers

!xx! Interfaces
interface
Expand All @@ -273,6 +275,8 @@ module subroutine update_window_id(id,changed)
integer, intent(inout) :: id
integer, intent(out), optional :: changed
end subroutine update_window_id
module subroutine regenerate_window_pointers()
end subroutine regenerate_window_pointers
module subroutine window_init(w,type,isopen,id,purpose,isys,irep,idcaller)
class(window), intent(inout), target :: w
integer, intent(in) :: type
Expand Down
38 changes: 31 additions & 7 deletions src/gui/[email protected]
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,7 @@ module subroutine stack_realloc_maybe()
allocate(winaux(2*(nwin+iroom)))
winaux(1:size(win,1)) = win
call move_alloc(winaux,win)
call regenerate_window_pointers()
end if

end subroutine stack_realloc_maybe
Expand Down Expand Up @@ -127,6 +128,30 @@ module subroutine update_window_id(id,changed)

end subroutine update_window_id

!> This routine regenerates all pointers to the widows in the win(:)
!> structure and its components. It is used when an array size is
!> exceeded and move_alloc needs to be used to allocate more memory.
module subroutine regenerate_window_pointers()
use gui_main, only: sysc, nsys, sys_init

integer :: i, j, iv

do i = 1, nwin
if (win(i)%type == wintype_editrep .and. win(i)%irep > 0) then
win(i)%rep => win(win(i)%idparent)%sc%rep(win(i)%irep)
elseif (win(i)%type == wintype_view) then
win(i)%sc => null()
iv = win(i)%view_selected
if (iv >= 1 .and. iv <= nsys) then
if (sysc(iv)%status == sys_init.and.win(i)%ismain) then
win(i)%sc => sysc(iv)%sc
end if
end if
end if
end do

end subroutine regenerate_window_pointers

!> Initialize a window of the given type. If isiopen, initialize it
!> as open.
module subroutine window_init(w,type,isopen,id,purpose,isys,irep,idcaller)
Expand Down Expand Up @@ -182,6 +207,10 @@ module subroutine window_init(w,type,isopen,id,purpose,isys,irep,idcaller)
w%forcequitdialog = .false.
w%plotn = 0
w%idsave = 0
if (present(isys)) w%isys = isys
if (present(irep)) w%irep = irep
if (present(idcaller)) w%idparent = idcaller
if (present(purpose)) w%dialog_purpose = purpose

! type-specific initialization
if (type == wintype_dialog) then
Expand All @@ -193,17 +222,14 @@ module subroutine window_init(w,type,isopen,id,purpose,isys,irep,idcaller)
call IGFD_SetFileStyle(w%dptr,IGFD_FileStyleByTypeFile,c_null_ptr,ColorDialogFile,c_loc(str1),c_null_ptr)
if (.not.present(purpose)) &
call ferror('window_init','dialog requires a purpose',faterr)
w%dialog_purpose = purpose
elseif (type == wintype_load_field) then
! dialog: load field window
if (.not.present(isys)) &
call ferror('window_init','load_field requires isys',faterr)
w%isys = isys
elseif (type == wintype_scfplot) then
! SCF plot window
if (.not.present(isys)) &
call ferror('window_init','scfplot requires isys',faterr)
w%isys = isys
elseif (type == wintype_editrep) then
! edit representation window
if (.not.present(isys)) &
Expand All @@ -212,14 +238,11 @@ module subroutine window_init(w,type,isopen,id,purpose,isys,irep,idcaller)
call ferror('window_init','editrep requires irep',faterr)
if (.not.present(idcaller)) &
call ferror('window_init','editrep requires idcaller',faterr)
w%isys = isys
w%rep => win(idcaller)%sc%rep(irep)
w%idparent = idcaller
elseif (type == wintype_exportimage) then
! export image window
if (.not.present(idcaller)) &
call ferror('window_init','exportimage requires idcaller',faterr)
w%idparent = idcaller
elseif (type == wintype_view) then
! view window
if (.not.present(purpose)) &
Expand All @@ -237,7 +260,6 @@ module subroutine window_init(w,type,isopen,id,purpose,isys,irep,idcaller)
! recalculate bonds window
if (.not.present(isys)) &
call ferror('window_init','rebond requires isys',faterr)
w%isys = isys
end if

end subroutine window_init
Expand Down Expand Up @@ -270,6 +292,8 @@ module subroutine window_end(w)
if (allocated(w%plotx)) deallocate(w%plotx)
if (allocated(w%ploty)) deallocate(w%ploty)
nullify(w%rep)
w%isys = 1
w%irep = 0

end subroutine window_end

Expand Down
4 changes: 1 addition & 3 deletions src/gui/[email protected]
Original file line number Diff line number Diff line change
Expand Up @@ -1508,7 +1508,6 @@ module subroutine update_editrep(w)
if (.not.doquit) doquit = (sysc(isys)%status /= sys_init)
if (.not.doquit) doquit = .not.associated(w%rep)
if (.not.doquit) doquit = .not.w%rep%isinit
if (.not.doquit) doquit = .not.associated(w%rep%sc)
if (.not.doquit) doquit = (w%rep%type <= 0)
if (.not.doquit) doquit = .not.(w%idparent > 0 .and. w%idparent <= nwin)
if (.not.doquit) doquit = .not.(win(w%idparent)%isinit)
Expand Down Expand Up @@ -1546,7 +1545,6 @@ module subroutine draw_editrep(w)
if (.not.doquit) doquit = (sysc(isys)%status /= sys_init)
if (.not.doquit) doquit = .not.associated(w%rep)
if (.not.doquit) doquit = .not.w%rep%isinit
if (.not.doquit) doquit = .not.associated(w%rep%sc)
if (.not.doquit) doquit = (w%rep%type <= 0)
if (.not.doquit) doquit = .not.(w%idparent > 0 .and. w%idparent <= nwin)
if (.not.doquit) doquit = .not.(win(w%idparent)%isinit)
Expand Down Expand Up @@ -1606,7 +1604,7 @@ module subroutine draw_editrep(w)
str2 = w%rep%name
itype = w%rep%type
lshown = w%rep%shown
call w%rep%init(w%rep%sc,w%rep%id,w%rep%idrep,itype,win(w%idparent)%sc%style)
call w%rep%init(sysc(w%isys)%sc,w%rep%id,w%rep%idrep,itype,win(w%idparent)%sc%style)
w%rep%name = str2
w%rep%shown = lshown
win(w%idparent)%sc%forcebuildlists = .true.
Expand Down

0 comments on commit 703300c

Please sign in to comment.