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 global_oct_m
28 use math_oct_m
32 use unit_oct_m
33
34 implicit none
35
36 public :: box_image_t
37
39 type, extends(box_shape_t) :: box_image_t
40 private
41 integer :: image_size(2)
42 real(real64), public :: pixel_size(2)
43 type(c_ptr) :: image
44 character(len=:), allocatable :: filename
45 contains
46 procedure :: shape_contains_points => box_image_shape_contains_points
47 procedure :: write_info => box_image_write_info
48 procedure :: short_info => box_image_short_info
49 final :: box_image_finalize
50 end type box_image_t
51
52 interface box_image_t
53 procedure box_image_constructor
54 end interface box_image_t
55
56contains
57
58 !--------------------------------------------------------------
59 function box_image_constructor(center, axes, lsize, filename, periodic_dim, namespace) result(box)
60 real(real64), intent(in) :: center(2)
61 real(real64), intent(in) :: axes(2, 2)
62 real(real64), intent(in) :: lsize(2)
66 character(len=*), intent(in) :: filename
67 integer, intent(in) :: periodic_dim
68 type(namespace_t), intent(in) :: namespace
69 class(box_image_t), pointer :: box
70
71 logical :: found
72 integer :: idir, box_npts
73 real(real64) :: lsize_adjusted(2)
74
75 push_sub(box_image_constructor)
76
77 ! Allocate memory
78 safe_allocate(box)
79
80 ! Initialize box
81 box%filename = trim(filename)
82 inquire(file=trim(box%filename), exist=found)
83 if (.not. found) then
84 deallocate(box%filename)
85 box%filename = trim(conf%share) // '/' // trim(filename)
86 inquire(file=trim(box%filename), exist=found)
87
88 if (.not. found) then
89 message(1) = "Could not find file '" // trim(filename) // "' for BoxShape = box_image."
90 call messages_fatal(1, namespace=namespace)
91 end if
92 end if
93
94 if (.not. c_associated(box%image)) then
95 message(1) = "Could not open file '" // trim(box%filename) // "' for BoxShape = box_image."
96 call messages_fatal(1, namespace=namespace)
97 end if
98
99 ! If necessary, adjust the bounding box to ensure that we always have a
100 ! pixel at the origin and that the edges always fall between two pixels.
101 do idir = 1, 2
102 box_npts = box%image_size(idir)
103 if ((idir > periodic_dim .and. even(box%image_size(idir))) .or. &
104 (idir <= periodic_dim .and. odd(box%image_size(idir)))) then
105 box_npts = box_npts + 1
106 lsize_adjusted(idir) = lsize(idir) * box_npts / box%image_size(idir)
107 else
108 lsize_adjusted(idir) = lsize(idir)
109 end if
110 end do
111
112 ! Calculate the size of a pixel. To have one grid point = one pixel the
113 ! spacing must be the same as the pixel size.
114 box%pixel_size(1:2) = m_two*lsize_adjusted(1:2)/box%image_size(1:2)
116 call box_shape_init(box, namespace, 2, center, bounding_box_min=-lsize_adjusted, bounding_box_max=lsize_adjusted, axes=axes)
117
118 box%bounding_box_l = lsize_adjusted + abs(center)
119
120 pop_sub(box_image_constructor)
121 end function box_image_constructor
122
123 !--------------------------------------------------------------
124 subroutine box_image_finalize(this)
125 type(box_image_t), intent(inout) :: this
126
127 push_sub(box_image_finalize)
128
129 call box_shape_end(this)
130 if (allocated(this%filename)) then
131 deallocate(this%filename)
132 end if
133
135 end subroutine box_image_finalize
137 !--------------------------------------------------------------
138 function box_image_shape_contains_points(this, nn, xx, tol) result(contained)
139 class(box_image_t), intent(in) :: this
140 integer, intent(in) :: nn
141 real(real64), contiguous, intent(in) :: xx(:,:)
142 real(real64), optional, intent(in) :: tol
143 logical :: contained(1:nn)
144
145 integer :: ip
146 integer :: red, green, blue, ix, iy
147
148 do ip = 1, nn
149 ! Transform our cartesian coordinates into pixel coordinates.
150 ! Why the minus sign for y? Explanation: http://biolinx.bios.niu.edu/bios546/gd_mod.htm
151 ! For reasons that probably made sense to someone at some time, computer graphic coordinates are not the same
152 ! as in standard graphing. ... The top left corner of the screen is (0,0).
153 ix = nint((xx(ip, 1) - this%center(1))/this%pixel_size(1)) + (this%image_size(1) - 1)/2
154 iy = - nint((xx(ip, 2) - this%center(2))/this%pixel_size(2)) + (this%image_size(2) - 1)/2
155 contained(ip) = (red == 255 .and. green == 255 .and. blue == 255) .neqv. this%is_inside_out()
156 end do
157
159
160 !--------------------------------------------------------------
161 subroutine box_image_write_info(this, iunit, namespace)
162 class(box_image_t), intent(in) :: this
163 integer, optional, intent(in) :: iunit
164 type(namespace_t), optional, intent(in) :: namespace
165
166 push_sub(box_image_write_info)
167
168 write(message(1),'(2x,3a,i6,a,i6)') 'Type = defined by image "', trim(this%filename), '"', this%image_size(1), ' x ', &
169 this%image_size(2)
170 call messages_info(1, iunit=iunit, namespace=namespace)
171
172 pop_sub(box_image_write_info)
173 end subroutine box_image_write_info
174
175 !--------------------------------------------------------------
176 character(len=BOX_INFO_LEN) function box_image_short_info(this, unit_length) result(info)
177 class(box_image_t), intent(in) :: this
178 type(unit_t), intent(in) :: unit_length
179
180 push_sub(box_image_short_info)
181
182 write(info, '(2a)') 'BoxShape = box_image; BoxShapeImage = ', trim(this%filename)
183
184 pop_sub(box_image_short_info)
185 end function box_image_short_info
186
187end module box_image_oct_m
188
189!! Local Variables:
190!! mode: f90
191!! coding: utf-8
192!! 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:270
class(box_image_t) function, pointer box_image_constructor(center, axes, lsize, filename, periodic_dim, namespace)
Definition: box_image.F90:153
subroutine box_image_finalize(this)
Definition: box_image.F90:218
subroutine box_image_write_info(this, iunit, namespace)
Definition: box_image.F90:255
logical function, dimension(1:nn) box_image_shape_contains_points(this, nn, xx, tol)
Definition: box_image.F90:232
subroutine, public box_shape_init(this, namespace, dim, center, bounding_box_min, bounding_box_max, axes)
Definition: box_shape.F90:177
subroutine, public box_shape_end(this)
Definition: box_shape.F90:273
real(real64), parameter, public m_two
Definition: global.F90:190
type(conf_t), public conf
Global instance of Octopus configuration.
Definition: global.F90:178
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:694
logical pure function, public odd(n)
Returns if n is odd.
Definition: math.F90:704
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:414
subroutine, public messages_info(no_lines, iunit, debug_only, stress, all_nodes, namespace)
Definition: messages.F90:616
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:132
Base class for more specialized boxes that are defined by a shape and have a center and basis vectors...
Definition: box_shape.F90:134