facet_object Derived Type

type, public :: facet_object

type~~facet_object~~InheritsGraph type~facet_object facet_object vector_R8P vector_R8P vector_R8P->type~facet_object normal, vertex_1, vertex_2, vertex_3, E12, E13, bb
Help


FOSSIL, facet class.

Inherited By

type~~facet_object~~InheritedByGraph type~facet_object facet_object type~aabb_object aabb_object type~facet_object->type~aabb_object facet type~file_stl_object file_stl_object type~facet_object->type~file_stl_object facet type~aabb_node_object aabb_node_object type~aabb_object->type~aabb_node_object aabb type~aabb_tree_object aabb_tree_object type~aabb_node_object->type~aabb_tree_object node type~aabb_tree_object->type~file_stl_object aabb
Help

Source Code


Components

TypeVisibility AttributesNameInitial
type(vector_R8P), public :: normal

Facet (outward) normal (versor), (v2-v1).cross.(v3-v1).

type(vector_R8P), public :: vertex_1

Facet vertex 1.

type(vector_R8P), public :: vertex_2

Facet vertex 2.

type(vector_R8P), public :: vertex_3

Facet vertex 3.

type(vector_R8P), public :: E12

Edge 1-2, V2-V1.

type(vector_R8P), public :: E13

Edge 1-3, V3-V1.

real(kind=R8P), public :: a =0._R8P

E12.dot.E12.

real(kind=R8P), public :: b =0._R8P

E12.dot.E13.

real(kind=R8P), public :: c =0._R8P

E13.dot.E13.

real(kind=R8P), public :: det =0._R8P

a*c - b*b.

real(kind=R8P), public :: d =0._R8P

normal.dot.vertex_1

type(vector_R8P), public :: bb(2)

Axis-aligned bounding box (AABB), bb(1)=min, bb(2)=max.

integer(kind=I4P), public :: id

Facet global ID.

integer(kind=I4P), public :: fcon_edge_12 =0_I4P

Connected face ID along edge 1-2.

integer(kind=I4P), public :: fcon_edge_23 =0_I4P

Connected face ID along edge 2-3.

integer(kind=I4P), public :: fcon_edge_31 =0_I4P

Connected face ID along edge 3-1.

integer(kind=I4P), public, allocatable:: vertex_1_occurrence(:)

List of vertex 1 "occurrencies", list of facets global ID containing it.

integer(kind=I4P), public, allocatable:: vertex_2_occurrence(:)

List of vertex 2 "occurrencies", list of facets global ID containing it.

integer(kind=I4P), public, allocatable:: vertex_3_occurrence(:)

List of vertex 3 "occurrencies", list of facets global ID containing it.


Type-Bound Procedures

procedure, public, pass(self) :: add_vertex_occurrence

Add vertex occurence.

  • private elemental subroutine add_vertex_occurrence(self, vertex_id, facet_id)

    Add vertex occurrence.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: self

    Facet.

    integer(kind=I4P), intent(in) :: vertex_id

    Vertex ID in local numeration, 1, 2 or 3.

    integer(kind=I4P), intent(in) :: facet_id

    Other facet ID containing vertex.

procedure, public, pass(self) :: check_normal

Check normal consistency.

  • private elemental function check_normal(self) result(is_consistent)

    Check normal consistency.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(in) :: self

    Facet.

    Return Value logical

    Consistency check result.

procedure, public, pass(self) :: check_vertices_occurrencies

Check if vertices of facet are identical to ones of other facet.

  • private pure subroutine check_vertices_occurrencies(self, other)

    Check if vertices of facet are identical (with tollerance) to the ones of other facet.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: self

    Facet.

    type(facet_object), intent(inout) :: other

    Other facet.

procedure, public, pass(self) :: compute_metrix

Compute local (plane) metrix.

  • private elemental subroutine compute_metrix(self)

    Compute local (plane) metrix.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: self

    Facet.

procedure, public, pass(self) :: compute_normal

Compute normal by means of vertices data.

  • private elemental subroutine compute_normal(self)

    Compute normal by means of vertices data.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: self

    Facet.

procedure, public, pass(self) :: destroy

Destroy facet.

  • private elemental subroutine destroy(self)

    Destroy AABB.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: self

    Facet.

procedure, public, pass(self) :: distance

Compute the (unsigned, squared) distance from a point to facet.

  • private pure function distance(self, point)

    Compute the (unsigned, squared) distance from a point to the facet surface.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(in) :: self

    Facet.

    type(vector_R8P), intent(in) :: point

    Point.

    Return Value real(kind=R8P)

    Closest distance from point to the facet.

procedure, public, pass(self) :: do_ray_intersect

Return true if facet is intersected by a ray.

  • private pure function do_ray_intersect(self, ray_origin, ray_direction) result(intersect)

    Return true if facet is intersected by ray from origin and oriented as ray direction vector.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(in) :: self

    Facet.

    type(vector_R8P), intent(in) :: ray_origin

    Ray origin.

    type(vector_R8P), intent(in) :: ray_direction

    Ray direction.

    Return Value logical

    Intersection test result.

procedure, public, pass(self) :: initialize

Initialize facet.

  • private elemental subroutine initialize(self)

    Initialize facet.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: self

    Facet.

procedure, public, pass(self) :: load_from_file_ascii

Load facet from ASCII file.

  • private subroutine load_from_file_ascii(self, file_unit)

    Load facet from ASCII file.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: self

    Facet.

    integer(kind=I4P), intent(in) :: file_unit

    File unit.

procedure, public, pass(self) :: load_from_file_binary

Load facet from binary file.

  • private subroutine load_from_file_binary(self, file_unit)

    Load facet from binary file.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: self

    Facet.

    integer(kind=I4P), intent(in) :: file_unit

    File unit.

procedure, public, pass(self) :: make_normal_consistent

Make normal of other facet consistent with self.

  • private pure subroutine make_normal_consistent(self, edge_dir, other)

    Make normal of other facet consistent with self.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(in) :: self

    Facet.

    character(len=*), intent(in) :: edge_dir

    Edge (in self numeration) along which other is connected.

    type(facet_object), intent(inout) :: other

    Other facet to make consistent with self.

generic, public :: mirror => mirror_by_normal, mirror_by_matrix

Mirror facet.

  • private pure subroutine mirror_by_normal(self, normal, recompute_metrix)

    Mirror facet given normal of mirroring plane.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: self

    Facet.

    type(vector_R8P), intent(in) :: normal

    Normal of mirroring plane.

    logical, intent(in), optional :: recompute_metrix

    Sentinel to activate metrix recomputation.

  • private pure subroutine mirror_by_matrix(self, matrix, recompute_metrix)

    Mirror facet given matrix (of mirroring).

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: self

    Facet.

    real(kind=R8P), intent(in) :: matrix(3,3)

    Mirroring matrix.

    logical, intent(in), optional :: recompute_metrix

    Sentinel to activate metrix recomputation.

procedure, public, pass(self) :: reverse_normal

Reverse facet normal.

  • private elemental subroutine reverse_normal(self)

    Reverse facet normal.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: self

    Facet.

procedure, public, pass(self) :: resize

Resize (scale) facet by x or y or z or vectorial factors.

  • private elemental subroutine resize(self, factor, recompute_metrix)

    Resize (scale) facet by x or y or z or vectorial factors.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: self

    Facet

    type(vector_R8P), intent(in) :: factor

    Vectorial factor.

    logical, intent(in), optional :: recompute_metrix

    Sentinel to activate metrix recomputation.

generic, public :: rotate => rotate_by_axis_angle, rotate_by_matrix

Rotate facet.

  • private pure subroutine rotate_by_axis_angle(self, axis, angle, recompute_metrix)

    Rotate facet given axis and angle.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: self

    Facet.

    type(vector_R8P), intent(in) :: axis

    Axis of rotation.

    real(kind=R8P), intent(in) :: angle

    Angle of rotation.

    logical, intent(in), optional :: recompute_metrix

    Sentinel to activate metrix recomputation.

  • private pure subroutine rotate_by_matrix(self, matrix, recompute_metrix)

    Rotate facet given matrix (of ratation).

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: self

    Facet.

    real(kind=R8P), intent(in) :: matrix(3,3)

    Rotation matrix.

    logical, intent(in), optional :: recompute_metrix

    Sentinel to activate metrix recomputation.

procedure, public, pass(self) :: save_into_file_ascii

Save facet into ASCII file.

  • private subroutine save_into_file_ascii(self, file_unit)

    Save facet into ASCII file.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(in) :: self

    Facet.

    integer(kind=I4P), intent(in) :: file_unit

    File unit.

procedure, public, pass(self) :: save_into_file_binary

Save facet into binary file.

  • private subroutine save_into_file_binary(self, file_unit)

    Save facet into binary file.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(in) :: self

    Facet.

    integer(kind=I4P), intent(in) :: file_unit

    File unit.

procedure, public, pass(self) :: solid_angle

Return the (projected) solid angle of the facet with respect point.

  • private pure function solid_angle(self, point)

    Return the (projected) solid angle of the facet with respect the point.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(in) :: self

    Facet.

    type(vector_R8P), intent(in) :: point

    Point.

    Return Value real(kind=R8P)

    Solid angle.

procedure, public, pass(self) :: tetrahedron_volume

Return the volume of tetrahedron built by facet and a given apex.

  • private pure function tetrahedron_volume(self, apex) result(volume)

    Return the volume of tetrahedron built by facet and a given apex.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(in) :: self

    Facet.

    type(vector_R8P), intent(in) :: apex

    Tetrahedron apex.

    Return Value real(kind=R8P)

    Tetrahedron volume.

procedure, public, pass(self) :: translate

Translate facet given vectorial delta.

  • private elemental subroutine translate(self, delta, recompute_metrix)

    Translate facet given vectorial delta.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: self

    Facet.

    type(vector_R8P), intent(in) :: delta

    Translation delta.

    logical, intent(in), optional :: recompute_metrix

    Sentinel to activate metrix recomputation.

procedure, public, pass(self) :: update_connectivity

Update facet connectivity.

  • private pure subroutine update_connectivity(self)

    Update facet connectivity.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: self

    Facet.

procedure, public, pass(self) :: vertex_global_id

Return the vertex global id given the local one.

  • private pure function vertex_global_id(self, vertex_id)

    Return the vertex global id given the local one.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(in) :: self

    Facet.

    integer(kind=I4P), intent(in) :: vertex_id

    Local vertex id.

    Return Value integer(kind=I4P)

    Gloval vertex id.

generic, public :: assignment(=) => facet_assign_facet

Overload =.

  • private pure subroutine facet_assign_facet(lhs, rhs)

    Operator =.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: lhs

    Left hand side.

    type(facet_object), intent(in) :: rhs

    Right hand side.

procedure, private, pass(self) :: edge_connection_in_other_ref

Return the edge of connection in the other reference.

  • private pure subroutine edge_connection_in_other_ref(self, other, edge_dir, edge)

    Return the edge of connection in the other reference.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(in) :: self

    Facet.

    type(facet_object), intent(in) :: other

    Other facet.

    character(len=*), intent(out) :: edge_dir

    Edge (in other numeration) along which self is connected.

    type(vector_R8P), intent(out) :: edge

    Edge (in other numeration) along which self is connected.

procedure, private, pass(lhs) :: facet_assign_facet

Operator =.

  • private pure subroutine facet_assign_facet(lhs, rhs)

    Operator =.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: lhs

    Left hand side.

    type(facet_object), intent(in) :: rhs

    Right hand side.

procedure, private, pass(self) :: flip_edge

Flip facet edge.

  • private pure subroutine flip_edge(self, edge_dir)

    Flip facet edge.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: self

    Facet.

    character(len=*), intent(in) :: edge_dir

    Edge to be flipped.

procedure, private, pass(self) :: mirror_by_normal

Mirror facet given normal of mirroring plane.

  • private pure subroutine mirror_by_normal(self, normal, recompute_metrix)

    Mirror facet given normal of mirroring plane.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: self

    Facet.

    type(vector_R8P), intent(in) :: normal

    Normal of mirroring plane.

    logical, intent(in), optional :: recompute_metrix

    Sentinel to activate metrix recomputation.

procedure, private, pass(self) :: mirror_by_matrix

Mirror facet given matrix.

  • private pure subroutine mirror_by_matrix(self, matrix, recompute_metrix)

    Mirror facet given matrix (of mirroring).

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: self

    Facet.

    real(kind=R8P), intent(in) :: matrix(3,3)

    Mirroring matrix.

    logical, intent(in), optional :: recompute_metrix

    Sentinel to activate metrix recomputation.

procedure, private, pass(self) :: rotate_by_axis_angle

Rotate facet given axis and angle.

  • private pure subroutine rotate_by_axis_angle(self, axis, angle, recompute_metrix)

    Rotate facet given axis and angle.

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: self

    Facet.

    type(vector_R8P), intent(in) :: axis

    Axis of rotation.

    real(kind=R8P), intent(in) :: angle

    Angle of rotation.

    logical, intent(in), optional :: recompute_metrix

    Sentinel to activate metrix recomputation.

procedure, private, pass(self) :: rotate_by_matrix

Rotate facet given matrix.

  • private pure subroutine rotate_by_matrix(self, matrix, recompute_metrix)

    Rotate facet given matrix (of ratation).

    Arguments

    Type IntentOptional AttributesName
    class(facet_object), intent(inout) :: self

    Facet.

    real(kind=R8P), intent(in) :: matrix(3,3)

    Rotation matrix.

    logical, intent(in), optional :: recompute_metrix

    Sentinel to activate metrix recomputation.

Source Code

type :: facet_object
   !< FOSSIL, facet class.
   type(vector_R8P) :: normal   !< Facet (outward) normal (versor), `(v2-v1).cross.(v3-v1)`.
   type(vector_R8P) :: vertex_1 !< Facet vertex 1.
   type(vector_R8P) :: vertex_2 !< Facet vertex 2.
   type(vector_R8P) :: vertex_3 !< Facet vertex 3.
   ! metrix
   ! triangle plane parametric equation: T(s,t) = B + s*E12 + t*E13
   type(vector_R8P) :: E12        !< Edge 1-2, `V2-V1`.
   type(vector_R8P) :: E13        !< Edge 1-3, `V3-V1`.
   real(R8P)        :: a=0._R8P   !< `E12.dot.E12`.
   real(R8P)        :: b=0._R8P   !< `E12.dot.E13`.
   real(R8P)        :: c=0._R8P   !< `E13.dot.E13`.
   real(R8P)        :: det=0._R8P !< `a*c - b*b`.
   ! triangle plane equation: nx*x + ny*y + nz*z - d = 0, normal == [nx, ny, nz]
   real(R8P) :: d=0._R8P !< `normal.dot.vertex_1`
   ! auxiliary
   type(vector_R8P) :: bb(2) !< Axis-aligned bounding box (AABB), bb(1)=min, bb(2)=max.
   ! connectivity
   integer(I4P)              :: id                     !< Facet global ID.
   integer(I4P)              :: fcon_edge_12=0_I4P     !< Connected face ID along edge 1-2.
   integer(I4P)              :: fcon_edge_23=0_I4P     !< Connected face ID along edge 2-3.
   integer(I4P)              :: fcon_edge_31=0_I4P     !< Connected face ID along edge 3-1.
   integer(I4P), allocatable :: vertex_1_occurrence(:) !< List of vertex 1 "occurrencies", list of facets global ID containing it.
   integer(I4P), allocatable :: vertex_2_occurrence(:) !< List of vertex 2 "occurrencies", list of facets global ID containing it.
   integer(I4P), allocatable :: vertex_3_occurrence(:) !< List of vertex 3 "occurrencies", list of facets global ID containing it.
   contains
      ! public methods
      procedure, pass(self) :: add_vertex_occurrence           !< Add vertex occurence.
      procedure, pass(self) :: check_normal                    !< Check normal consistency.
      procedure, pass(self) :: check_vertices_occurrencies     !< Check if vertices of facet are *identical* to ones of other facet.
      procedure, pass(self) :: compute_metrix                  !< Compute local (plane) metrix.
      procedure, pass(self) :: compute_normal                  !< Compute normal by means of vertices data.
      procedure, pass(self) :: destroy                         !< Destroy facet.
      procedure, pass(self) :: distance                        !< Compute the (unsigned, squared) distance from a point to facet.
      procedure, pass(self) :: do_ray_intersect                !< Return true if facet is intersected by a ray.
      procedure, pass(self) :: initialize                      !< Initialize facet.
      procedure, pass(self) :: load_from_file_ascii            !< Load facet from ASCII file.
      procedure, pass(self) :: load_from_file_binary           !< Load facet from binary file.
      procedure, pass(self) :: make_normal_consistent          !< Make normal of other facet consistent with self.
      generic               :: mirror => mirror_by_normal, &
                                         mirror_by_matrix      !< Mirror facet.
      procedure, pass(self) :: reverse_normal                  !< Reverse facet normal.
      procedure, pass(self) :: resize                          !< Resize (scale) facet by x or y or z or vectorial factors.
      generic               :: rotate => rotate_by_axis_angle, &
                                         rotate_by_matrix      !< Rotate facet.
      procedure, pass(self) :: save_into_file_ascii            !< Save facet into ASCII file.
      procedure, pass(self) :: save_into_file_binary           !< Save facet into binary file.
      procedure, pass(self) :: solid_angle                     !< Return the (projected) solid angle of the facet with respect point.
      procedure, pass(self) :: tetrahedron_volume              !< Return the volume of tetrahedron built by facet and a given apex.
      procedure, pass(self) :: translate                       !< Translate facet given vectorial delta.
      procedure, pass(self) :: update_connectivity             !< Update facet connectivity.
      procedure, pass(self) :: vertex_global_id                !< Return the vertex global id given the local one.
      ! operators
      generic :: assignment(=) => facet_assign_facet !< Overload `=`.
      ! private methods
      procedure, pass(self), private :: edge_connection_in_other_ref !< Return the edge of connection in the other reference.
      procedure, pass(lhs),  private :: facet_assign_facet           !< Operator `=`.
      procedure, pass(self), private :: flip_edge                    !< Flip facet edge.
      procedure, pass(self), private :: mirror_by_normal             !< Mirror facet given normal of mirroring plane.
      procedure, pass(self), private :: mirror_by_matrix             !< Mirror facet given matrix.
      procedure, pass(self), private :: rotate_by_axis_angle         !< Rotate facet given axis and angle.
      procedure, pass(self), private :: rotate_by_matrix             !< Rotate facet given matrix.
endtype facet_object