Skip to content

Commit

Permalink
Extend honeyplots module to handle xy_lattice types
Browse files Browse the repository at this point in the history
Now there is a generic interface (plot) overloaded to both hex_plot and
the new xy_plot. The latter takes all the same optional backend-related
input variables, but a type(xy_lattice) instead of an array of type(hex)

Furthermore it takes optionally NN_mask and NNN_mask, as generated using
the xy_neighbors module. If the former is passed it draws the NN bonds,
if the latter is passed it draws dashed NNN links. If nothing is passed
it draws only the lattice points. PLEASE NOTE THAT THE BOND/LINK OPTION
IS NOT AVAILABLE WITH THE GNUPLOT BACKEND. I don't know how to get this
working with the gnuplot interface provided by OGPF, since it allows to
generate all plot-parts in the same call, which is not feasible if you
want to plot single segments, I think. Maybe we should just drop OGPF.

> This allowed to test both the NN and the NNN masks, for the very basic
  structure we currently generate in the test script. It works perfectly.

TODO: add finally a module to automatically generate the most commonly
      needed shapes: generic radius flakes, rectangular strips, common
      parallelogram-shaped supercells (what PythTB does...), triangles.
  • Loading branch information
beddalumia committed Sep 19, 2022
1 parent 4bd2daa commit 99061ce
Show file tree
Hide file tree
Showing 2 changed files with 199 additions and 28 deletions.
193 changes: 180 additions & 13 deletions src/honeyplots.f90
Original file line number Diff line number Diff line change
Expand Up @@ -7,34 +7,204 @@ module honeyplots
use hex_layout
use hex_neighbors
use xy_coordinates
use xy_neighbors

implicit none
private

public :: hex_plot
public :: xy_plot, hex_plot, plot

integer, parameter :: N = 6 ! Number of vertices in a hexagon

interface plot
procedure :: xy_plot
procedure :: hex_plot
end interface

contains

subroutine xy_plot(lattice,nn_mask,nnn_mask,backend,figure_name,script_name,set_terminal)
!! >>> CURRENTLY GNUPLOT DOES NOT SUPPORT NN AND NNN LINKS, HELP IS WELCOME!
!! Simple plotter for class(xy_lattice) objects. If optional argument nn_mask
!! is passed it draws the nearest-neighbor bonds too. Similarly, if optional
!! argument nnn_mask is passed a dashed link to next-nearest neighbors would
!! be drawed. Otherwise only lallice sites. It features two backends, giving
!! access to either matplotlib(pyplot) or gnuplot internal machinery. Either
!! library needs to be installed in your system for hex_plot to work.
!! You can specify a figure_name to save the plot to disk. If not specified
!! the plot would be just displayed in a popup window (or the terminal with
!! suitable configuration of the gnuplot backend) and a corresponding script
!! saved, aiming at fast reproduction (the script will all contain data).
!! The script has a default name (hex_plot.{py,gp}), but you can optionally
!! give your own custom string, do not forget the appropriate file extension.
!! Regarding output formats instead, the two backends have slightly different
!! behavior: pyplot would infer the format from the given file extension in
!! figure_name, whilst gnuplot does need a proper "output terminal" to be set.
!! You can do that by passing the optional set_parameter variable. Refer to
!! original gnuplot documentation for the list of available terminals and how
!! they should be chosen. For convenience we report that you can get the list
!! of (system dependent) available terminals in your console by executing the
!! gnuplot -e "set terminal" command in your shell. Furthermore all systems
!! should be compatible with the "dumb" terminal option, which would direct
!! the plot to the terminal itself, in the form of ASCII art. This can be
!! very useful for HPC workflows.
type(xy_lattice),intent(in) :: lattice
logical,allocatable,intent(in),optional :: nn_mask(:,:)
logical,allocatable,intent(in),optional :: nnn_mask(:,:)
character(*),intent(in),optional :: backend !! default: "pyplot" (or "gnuplot")
character(*),intent(in),optional :: figure_name
character(*),intent(in),optional :: script_name
character(*),intent(in),optional :: set_terminal !! relevant to gnuplot backend
character(8) :: engine
character(32) :: source_name
logical,allocatable :: MaskA(:),MaskB(:)
real(8),allocatable :: Ax(:),Ay(:)
real(8),allocatable :: Bx(:),By(:)
real(8),dimension(2) :: x,y,x1,y1,x2,y2
type(pyplot) :: plt
type(gpf) :: gnu
integer :: i,j,k,l

associate (all_sites => lattice%site)

! Sublattice "A"
MaskA = all_sites%label=="A"
Ax = pack(all_sites%x,MaskA)
Ay = pack(all_sites%y,MaskA)

! Sublattice "B"
MaskB = all_sites%label=="B"
Bx = pack(all_sites%x,MaskB)
By = pack(all_sites%y,MaskB)

end associate !all_sites

if(present(backend))then
engine = trim(backend)
else
engine = "pyplot"
end if

select case(trim(engine))

case default
print*, "unknown backend: no plot generated"

case ("pyplot")

call plt%initialize(xlabel='x',ylabel='y',axis_equal=.true.)
! Nearest Neighbor Links
if(present(nn_mask))then
do i = 1, size(nn_mask,1)
do j = 1, size(nn_mask,1)
if(nn_mask(i,j))then
x(1) = lattice%site(i)%x
x(2) = lattice%site(j)%x
y(1) = lattice%site(i)%y
y(2) = lattice%site(j)%y
call plt%add_plot(x,y,label='',linestyle='-k')
endif
enddo
enddo
endif
! Next Nearest Neighbors
if(present(nnn_mask))then
do i = 1, size(nnn_mask,1)
do j = 1, size(nnn_mask,1)
if(nnn_mask(i,j))then
x(1) = lattice%site(i)%x
x(2) = lattice%site(j)%x
y(1) = lattice%site(i)%y
y(2) = lattice%site(j)%y
call plt%add_plot(x,y,label='',linestyle=':k')
endif
enddo
enddo
endif
! Sublattice "A"
call plt%add_plot(Ax,Ay,label='',linestyle='o',markersize=15)
! Sublattice "B
call plt%add_plot(Bx,By,label='',linestyle='o',markersize=15)

if(present(script_name))then
source_name = script_name
else
source_name = "hex_plot.py"
endif

if(present(figure_name))then
call plt%savefig(trim(figure_name), pyfile=trim(source_name))
print*
print*, "> PyPlot figure saved to: "//trim(figure_name)
print*
else
print*
print*, "> PyPlot GUI popping up..."
print*
call plt%showfig(pyfile=trim(source_name))
endif

case ("gnuplot")

if(present(script_name))then
source_name = script_name
else
source_name = "hex_plot.gp"
endif

if(present(script_name))then
source_name = script_name
else
source_name = "hex_plot.gp"
endif

if(present(set_terminal))then
call gnu%options("set term "//set_terminal//";")
else
call gnu%options("set term qt;")
endif

if(present(figure_name))then
call gnu%options('set output "'//figure_name//'"')
endif

call gnu%options("set size ratio -1;") ! --> axis equal
call gnu%options("unset grid") ! --> grid off
call gnu%xlabel('x')
call gnu%ylabel('y')
call gnu%filename(source_name)
print*
print*, "> Gnuplot GUI popping up..."
print*
call gnu%plot( &
x1=Ax, y1=Ay, &
ls1='with points pt 7 ps 3 lc rgb "#1F77B4"', &
x2=Bx, y2=By, &
ls2='with points pt 7 ps 3 lc rgb "#FF7F0E"' &
)

end select

end subroutine xy_plot

subroutine hex_plot(layout,hexagons,backend,figure_name,script_name,set_terminal)
!! Simple plotter for honeycomb structures. It features two backends, giving
!! Simple plotter for arrays of type(hex). It features two backends, giving
!! access to either matplotlib(pyplot) or gnuplot internal machinery. Either
!! library needs to be installed in your system for hex_plot to work.
!! You can specify a figure_name to save the plot to disk. If not specified
!! the plot would be just displayed in a popup window (or the terminal with
!! suitable configuration of the gnuplot backend) and a corresponding script
!! saved, aiming at fast reproduction (the script will all contain data).
!! You can specify a figure_name to save the plot to disk. If not specified
!! the plot would be just displayed in a popup window (or the terminal with
!! suitable configuration of the gnuplot backend) and a corresponding script
!! saved, aiming at fast reproduction (the script will all contain data).
!! The script has a default name (hex_plot.{py,gp}), but you can optionally
!! give your own custom string, do not forget the appropriate file extension.
!! Regarding output formats instead, the two backends have slightly different
!! behavior: pyplot would infer the format from the given file extension in
!! figure_name, whilst gnuplot does need a proper "output terminal" to be set.
!! You can do that by passing the optional set_parameter variable. Refer to
!! You can do that by passing the optional set_parameter variable. Refer to
!! original gnuplot documentation for the list of available terminals and how
!! they should be chosen. For convenience we report that you can get the list
!! of (system dependent) available terminals in your console by executing the
!! gnuplot -e "set terminal" command in your shell. Furthermore all systems
!! gnuplot -e "set terminal" command in your shell. Furthermore all systems
!! should be compatible with the "dumb" terminal option, which would direct
!! the plot to the terminal itself, in the form of ASCII art. This can be
!! very useful for HPC workflows.
Expand Down Expand Up @@ -120,7 +290,7 @@ subroutine hex_plot(layout,hexagons,backend,figure_name,script_name,set_terminal
else
call gnu%options("set term qt;")
endif

if(present(figure_name))then
call gnu%options('set output "'//figure_name//'"')
endif
Expand All @@ -137,9 +307,6 @@ subroutine hex_plot(layout,hexagons,backend,figure_name,script_name,set_terminal

end select

deallocate(x,y)

end subroutine

end subroutine hex_plot

end module honeyplots
34 changes: 19 additions & 15 deletions test/unit.f90
Original file line number Diff line number Diff line change
Expand Up @@ -150,6 +150,21 @@ program unit_test
open(unit=21,action='write')
call xy_print(lattice,quiet=.true.,unit=21)

print*, ""
print*, "Plotting neighborhood of hex a..."
call plot(v,neighborhood,backend="pyplot",figure_name='pyflower.svg')
call plot(v,neighborhood,backend="gnuplot",set_terminal='svg',figure_name='gnuflower.svg')
call plot(v,neighborhood,backend="gnuplot",set_terminal='dumb')
!call plot(v,neighborhood,backend="gnuplot") ! this would be a problem in CI
!call plot(v,neighborhood,backend="pyplot") ! this would be a problem in CI
!call plot(u,neighborhood,backend="gnuplot") ! this would be a problem in CI
!call plot(u,neighborhood,backend="pyplot") ! this would be a problem in CI
! THIS HAS TO BE TESTED MUCH MORE CAREFULLY TO ASSURE GOOD COVERAGE
call plot(u,neighborhood,backend='matlab') ! would skip due to <UNKNOWN BACKEND>
call plot(u,neighborhood,figure_name='pyflower.svg',script_name='hex_test.py') ! auto pyplot!
call plot(u,neighborhood,backend="gnuplot",set_terminal='png',figure_name='gnuflower.png')
call plot(u,neighborhood,backend="gnuplot",set_terminal='dumb',script_name='hex_test.gp')

! Rusty test for xy_neighboors
call xy_shells(lattice,shell_table,distance_set)
call xy_nearest_neighbors(lattice,NN)
Expand All @@ -163,20 +178,9 @@ program unit_test
do i = 1, size(lattice%site)
write(*,*) (NNN(i,j), j = 1, size(lattice%site))
enddo

print*, ""
print*, "Plotting neighborhood of hex a..."
call hex_plot(v,neighborhood,backend="pyplot",figure_name='pyflower.svg')
call hex_plot(v,neighborhood,backend="gnuplot",set_terminal='svg',figure_name='gnuflower.svg')
call hex_plot(v,neighborhood,backend="gnuplot",set_terminal='dumb')
!call hex_plot(v,neighborhood,backend="gnuplot") ! this would be a problem in CI
!call hex_plot(v,neighborhood,backend="pyplot") ! this would be a problem in CI
!call hex_plot(u,neighborhood,backend="gnuplot") ! this would be a problem in CI
!call hex_plot(u,neighborhood,backend="pyplot") ! this would be a problem in CI
! THIS HAS TO BE TESTED MUCH MORE CAREFULLY TO ASSURE GOOD COVERAGE
call hex_plot(u,neighborhood,backend='matlab') ! would skip due to <UNKNOWN BACKEND>
call hex_plot(u,neighborhood,figure_name='pyflower.svg',script_name='test.py') ! auto pyplot!
call hex_plot(u,neighborhood,backend="gnuplot",set_terminal='png',figure_name='gnuflower.png')
call hex_plot(u,neighborhood,backend="gnuplot",set_terminal='dumb',script_name='test.gp')
call plot(lattice,backend='matlab') ! would skip due to <UNKNOWN BACKEND>
call plot(lattice,backend='gnuplot',figure_name='gnuflake.svg',set_terminal='svg')
call plot(lattice,NN,script_name='xy_test.py',figure_name='pyflake.svg')
call plot(lattice,NN,NNN,figure_name='pyball.svg')

end program unit_test

1 comment on commit 99061ce

@beddalumia
Copy link
Member Author

@beddalumia beddalumia commented on 99061ce Sep 19, 2022

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Sublattice Support Nearest Neighbors Next Nearest Neighbors
gnuflake pyflake pyball
backend="gnuplot" available backend="pyplot" is mandatory backend="pyplot" is mandatory

Please sign in to comment.