42 integer :: image_size(2)
43 real(real64),
public :: pixel_size(2)
45 character(len=:),
allocatable :: filename
54 procedure box_image_constructor
61 real(real64),
intent(in) :: center(2)
62 real(real64),
intent(in) :: axes(2, 2)
63 real(real64),
intent(in) :: lsize(2)
67 character(len=*),
intent(in) :: filename
68 integer,
intent(in) :: periodic_dim
69 type(namespace_t),
intent(in) :: namespace
70 class(box_image_t),
pointer :: box
73 integer :: idir, box_npts
74 real(real64) :: lsize_adjusted(2)
82 box%filename = trim(filename)
83 inquire(file=trim(box%filename), exist=found)
85 deallocate(box%filename)
86 box%filename = trim(
conf%share) //
'/' // trim(filename)
87 inquire(file=trim(box%filename), exist=found)
90 message(1) =
"Could not find file '" // trim(filename) //
"' for BoxShape = box_image."
98 if (.not. c_associated(box%image))
then
99 message(1) =
"Could not open file '" // trim(box%filename) //
"' for BoxShape = box_image."
110 box_npts = box%image_size(idir)
111 if ((idir > periodic_dim .and.
even(box%image_size(idir))) .or. &
112 (idir <= periodic_dim .and.
odd(box%image_size(idir))))
then
113 box_npts = box_npts + 1
114 lsize_adjusted(idir) = lsize(idir) * box_npts / box%image_size(idir)
116 lsize_adjusted(idir) = lsize(idir)
122 box%pixel_size(1:2) =
m_two*lsize_adjusted(1:2)/box%image_size(1:2)
124 call box_shape_init(box, namespace, 2, center, bounding_box_min=-lsize_adjusted, bounding_box_max=lsize_adjusted, axes=axes)
126 box%bounding_box_l = lsize_adjusted + abs(center)
133 type(box_image_t),
intent(inout) :: this
138 if (
allocated(this%filename))
then
139 deallocate(this%filename)
151 integer,
intent(in) :: nn
152 real(real64),
contiguous,
intent(in) :: xx(:,:)
153 logical :: contained(1:nn)
156 integer :: red, green, blue, ix, iy
163 ix = nint((xx(ip, 1) - this%center(1))/this%pixel_size(1)) + (this%image_size(1) - 1)/2
164 iy = - nint((xx(ip, 2) - this%center(2))/this%pixel_size(2)) + (this%image_size(2) - 1)/2
166#if defined(HAVE_GDLIB)
169 contained(ip) = (red == 255 .and. green == 255 .and. blue == 255) .neqv. this%is_inside_out()
177 integer,
optional,
intent(in) :: iunit
178 type(
namespace_t),
optional,
intent(in) :: namespace
182 write(
message(1),
'(2x,3a,i6,a,i6)')
'Type = defined by image "', trim(this%filename),
'"', this%image_size(1),
' x ', &
192 type(
unit_t),
intent(in) :: unit_length
196 write(
info,
'(2a)')
'BoxShape = box_image; BoxShapeImage = ', trim(this%filename)
character(len=box_info_len) function box_image_short_info(this, unit_length)
class(box_image_t) function, pointer box_image_constructor(center, axes, lsize, filename, periodic_dim, namespace)
subroutine box_image_finalize(this)
subroutine box_image_write_info(this, iunit, namespace)
logical function, dimension(1:nn) box_image_shape_contains_points(this, nn, xx)
subroutine, public box_shape_init(this, namespace, dim, center, bounding_box_min, bounding_box_max, axes)
subroutine, public box_shape_end(this)
type(c_ptr) function, public gdlib_image_create_from(filename)
real(real64), parameter, public m_two
type(conf_t), public conf
Global instance of Octopus configuration.
This module is intended to contain "only mathematical" functions and procedures.
logical pure function, public even(n)
Returns if n is even.
logical pure function, public odd(n)
Returns if n is odd.
subroutine, public messages_info(no_lines, iunit, verbose_limit, stress, all_nodes, namespace)
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
subroutine, public messages_fatal(no_lines, only_root_writes, namespace)
brief This module defines the class unit_t which is used by the unit_systems_oct_m module.
Class implementing a box generated from a 2D image.
Base class for more specialized boxes that are defined by a shape and have a center and basis vectors...