Octopus
box_image.F90
Go to the documentation of this file.
1!! Copyright (C) 2002-2006 M. Marques, A. Castro, A. Rubio, G. Bertsch
2!! Copyright (C) 2021 M. Oliveira, K. Lively, A. Obzhirov, I. Albar
3!!
4!! This program is free software; you can redistribute it and/or modify
5!! it under the terms of the GNU General Public License as published by
6!! the Free Software Foundation; either version 2, or (at your option)
7!! any later version.
8!!
9!! This program is distributed in the hope that it will be useful,
10!! but WITHOUT ANY WARRANTY; without even the implied warranty of
11!! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12!! GNU General Public License for more details.
13!!
14!! You should have received a copy of the GNU General Public License
15!! along with this program; if not, write to the Free Software
16!! Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
17!! 02110-1301, USA.
18!!
19
20#include "global.h"
21
22module box_image_oct_m
23 use box_oct_m
25 use debug_oct_m
26 use iso_c_binding
27 use gdlib_oct_m
28 use global_oct_m
29 use math_oct_m
33 use unit_oct_m
34
35 implicit none
36
37 public :: box_image_t
38
40 type, extends(box_shape_t) :: box_image_t
41 private
42 integer :: image_size(2)
43 real(real64), public :: pixel_size(2)
44 type(c_ptr) :: image
45 character(len=:), allocatable :: filename
46 contains
47 procedure :: shape_contains_points => box_image_shape_contains_points
48 procedure :: write_info => box_image_write_info
49 procedure :: short_info => box_image_short_info
50 final :: box_image_finalize
51 end type box_image_t
52
53 interface box_image_t
54 procedure box_image_constructor
55 end interface box_image_t
56
57contains
58
59 !--------------------------------------------------------------
60 function box_image_constructor(center, axes, lsize, filename, periodic_dim, namespace) result(box)
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
71
72 logical :: found
73 integer :: idir, box_npts
74 real(real64) :: lsize_adjusted(2)
75
76 push_sub(box_image_constructor)
77
78 ! Allocate memory
79 safe_allocate(box)
80
81 ! Initialize box
82 box%filename = trim(filename)
83 inquire(file=trim(box%filename), exist=found)
84 if (.not. found) then
85 deallocate(box%filename)
86 box%filename = trim(conf%share) // '/' // trim(filename)
87 inquire(file=trim(box%filename), exist=found)
88
89 if (.not. found) then
90 message(1) = "Could not find file '" // trim(filename) // "' for BoxShape = box_image."
91 call messages_fatal(1, namespace=namespace)
92 end if
93 end if
94
95#ifdef HAVE_GDLIB
96 box%image = gdlib_image_create_from(box%filename)
97#endif
98 if (.not. c_associated(box%image)) then
99 message(1) = "Could not open file '" // trim(box%filename) // "' for BoxShape = box_image."
100 call messages_fatal(1, namespace=namespace)
101 end if
102#ifdef HAVE_GDLIB
103 box%image_size(1) = gdlib_image_sx(box%image)
104 box%image_size(2) = gdlib_image_sy(box%image)
105#endif
106
107 ! If necessary, adjust the bounding box to ensure that we always have a
108 ! pixel at the origin and that the edges always fall between two pixels.
109 do idir = 1, 2
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)
115 else
116 lsize_adjusted(idir) = lsize(idir)
117 end if
118 end do
119
120 ! Calculate the size of a pixel. To have one grid point = one pixel the
121 ! spacing must be the same as the pixel size.
122 box%pixel_size(1:2) = m_two*lsize_adjusted(1:2)/box%image_size(1:2)
123
124 call box_shape_init(box, namespace, 2, center, bounding_box_min=-lsize_adjusted, bounding_box_max=lsize_adjusted, axes=axes)
125
126 box%bounding_box_l = lsize_adjusted + abs(center)
127
128 pop_sub(box_image_constructor)
129 end function box_image_constructor
130
131 !--------------------------------------------------------------
132 subroutine box_image_finalize(this)
133 type(box_image_t), intent(inout) :: this
134
137 call box_shape_end(this)
138 if (allocated(this%filename)) then
139 deallocate(this%filename)
140 end if
141#ifdef HAVE_GDLIB
142 call gdlib_imagedestroy(this%image)
143#endif
144
145 pop_sub(box_image_finalize)
146 end subroutine box_image_finalize
147
148 !--------------------------------------------------------------
149 function box_image_shape_contains_points(this, nn, xx) result(contained)
150 class(box_image_t), intent(in) :: this
151 integer, intent(in) :: nn
152 real(real64), contiguous, intent(in) :: xx(:,:)
153 logical :: contained(1:nn)
154
155 integer :: ip
156 integer :: red, green, blue, ix, iy
157
158 do ip = 1, nn
159 ! Transform our cartesian coordinates into pixel coordinates.
160 ! Why the minus sign for y? Explanation: http://biolinx.bios.niu.edu/bios546/gd_mod.htm
161 ! For reasons that probably made sense to someone at some time, computer graphic coordinates are not the same
162 ! as in standard graphing. ... The top left corner of the screen is (0,0).
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
165
166#if defined(HAVE_GDLIB)
167 call gdlib_image_get_pixel_rgb(this%image, ix, iy, red, green, blue)
168#endif
169 contained(ip) = (red == 255 .and. green == 255 .and. blue == 255) .neqv. this%is_inside_out()
170 end do
171
173
174 !--------------------------------------------------------------
175 subroutine box_image_write_info(this, iunit, namespace)
176 class(box_image_t), intent(in) :: this
177 integer, optional, intent(in) :: iunit
178 type(namespace_t), optional, intent(in) :: namespace
179
180 push_sub(box_image_write_info)
181
182 write(message(1),'(2x,3a,i6,a,i6)') 'Type = defined by image "', trim(this%filename), '"', this%image_size(1), ' x ', &
183 this%image_size(2)
184 call messages_info(1, iunit=iunit, namespace=namespace)
185
186 pop_sub(box_image_write_info)
187 end subroutine box_image_write_info
188
189 !--------------------------------------------------------------
190 character(len=BOX_INFO_LEN) function box_image_short_info(this, unit_length) result(info)
191 class(box_image_t), intent(in) :: this
192 type(unit_t), intent(in) :: unit_length
193
194 push_sub(box_image_short_info)
195
196 write(info, '(2a)') 'BoxShape = box_image; BoxShapeImage = ', trim(this%filename)
197
198 pop_sub(box_image_short_info)
199 end function box_image_short_info
200
201end module box_image_oct_m
202
203!! Local Variables:
204!! mode: f90
205!! coding: utf-8
206!! End:
subroutine info()
Definition: em_resp.F90:1096
character(len=box_info_len) function box_image_short_info(this, unit_length)
Definition: box_image.F90:284
class(box_image_t) function, pointer box_image_constructor(center, axes, lsize, filename, periodic_dim, namespace)
Definition: box_image.F90:154
subroutine box_image_finalize(this)
Definition: box_image.F90:226
subroutine box_image_write_info(this, iunit, namespace)
Definition: box_image.F90:269
logical function, dimension(1:nn) box_image_shape_contains_points(this, nn, xx)
Definition: box_image.F90:243
subroutine, public box_shape_init(this, namespace, dim, center, bounding_box_min, bounding_box_max, axes)
Definition: box_shape.F90:175
subroutine, public box_shape_end(this)
Definition: box_shape.F90:271
type(c_ptr) function, public gdlib_image_create_from(filename)
Definition: gdlib.F90:161
real(real64), parameter, public m_two
Definition: global.F90:189
type(conf_t), public conf
Global instance of Octopus configuration.
Definition: global.F90:177
This module is intended to contain "only mathematical" functions and procedures.
Definition: math.F90:115
logical pure function, public even(n)
Returns if n is even.
Definition: math.F90:689
logical pure function, public odd(n)
Returns if n is odd.
Definition: math.F90:699
subroutine, public messages_info(no_lines, iunit, verbose_limit, stress, all_nodes, namespace)
Definition: messages.F90:624
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
Definition: messages.F90:160
subroutine, public messages_fatal(no_lines, only_root_writes, namespace)
Definition: messages.F90:420
brief This module defines the class unit_t which is used by the unit_systems_oct_m module.
Definition: unit.F90:132
Class implementing a box generated from a 2D image.
Definition: box_image.F90:133
Base class for more specialized boxes that are defined by a shape and have a center and basis vectors...
Definition: box_shape.F90:134