Skip to content

Commit

Permalink
Add set3 method to create Rational Bezier objects.
Browse files Browse the repository at this point in the history
  • Loading branch information
gha3mi committed Apr 7, 2024
1 parent da1ff60 commit 93dd393
Show file tree
Hide file tree
Showing 3 changed files with 186 additions and 75 deletions.
83 changes: 58 additions & 25 deletions src/NURBS/forcad_nurbs_curve.f90
Original file line number Diff line number Diff line change
Expand Up @@ -21,31 +21,32 @@ module forcad_nurbs_curve
integer, private :: nc !! number of control points
integer, private :: ng !! number of geometry points
contains
procedure :: set1 !!> Set knot vector, control points and weights for the NURBS curve object
procedure :: set2 !!> Set NURBS curve using nodes of parameter space, order, continuity, control points and weights
generic :: set => set1, set2 !!> Set NURBS curve
procedure :: create !!> Generate geometry points
procedure :: get_Xc !!> Get control points
procedure :: get_Xg !!> Get geometry points
procedure :: get_Wc !!> Get weights
procedure :: get_Xt !!> Get parameter values
procedure :: get_knot !!> Get knot vector
procedure :: get_ng !!> Get number of geometry points
procedure :: get_order !!> Get order of the NURBS curve
procedure :: finalize !!> Finalize the NURBS curve object
procedure :: get_elem_Xc !!> Generate connectivity for control points
procedure :: get_elem_Xg !!> Generate connectivity for geometry points
procedure :: export_Xc !!> Export control points to VTK file
procedure :: export_Xg !!> Export geometry points to VTK file
procedure :: modify_Xc !!> Modify control points
procedure :: modify_Wc !!> Modify weights
procedure :: get_multiplicity !!> Get multiplicity of the knot vector
procedure :: get_continuity !!> Get continuity of the curve
procedure :: get_nc !!> Get number of required control points
procedure :: insert_knots !!> Insert knots into the knot vector
procedure :: elevate_degree !!> Elevate the degree of the curve
procedure :: derivative !!> Compute the derivative of the NURBS curve
procedure :: basis !!> Compute the basis functions of the NURBS curve
procedure :: set1 !!> Set knot vector, control points and weights for the NURBS curve object
procedure :: set2 !!> Set NURBS curve using nodes of parameter space, order, continuity, control points and weights
procedure :: set3 !!> Set Bezier or Rational Bezier curve using control points and weights
generic :: set => set1, set2, set3 !!> Set NURBS curve
procedure :: create !!> Generate geometry points
procedure :: get_Xc !!> Get control points
procedure :: get_Xg !!> Get geometry points
procedure :: get_Wc !!> Get weights
procedure :: get_Xt !!> Get parameter values
procedure :: get_knot !!> Get knot vector
procedure :: get_ng !!> Get number of geometry points
procedure :: get_order !!> Get order of the NURBS curve
procedure :: finalize !!> Finalize the NURBS curve object
procedure :: get_elem_Xc !!> Generate connectivity for control points
procedure :: get_elem_Xg !!> Generate connectivity for geometry points
procedure :: export_Xc !!> Export control points to VTK file
procedure :: export_Xg !!> Export geometry points to VTK file
procedure :: modify_Xc !!> Modify control points
procedure :: modify_Wc !!> Modify weights
procedure :: get_multiplicity !!> Get multiplicity of the knot vector
procedure :: get_continuity !!> Get continuity of the curve
procedure :: get_nc !!> Get number of required control points
procedure :: insert_knots !!> Insert knots into the knot vector
procedure :: elevate_degree !!> Elevate the degree of the curve
procedure :: derivative !!> Compute the derivative of the NURBS curve
procedure :: basis !!> Compute the basis functions of the NURBS curve
end type
!===============================================================================

Expand Down Expand Up @@ -107,6 +108,38 @@ pure subroutine set2(this, Xth_dir, order, continuity, Xc, Wc)
!===============================================================================


!===============================================================================
!> author: Seyed Ali Ghasemi
!> license: BSD 3-Clause
!> Set Bezier or Rational Bezier curve using control points and weights.
pure subroutine set3(this, Xc, Wc)
class(nurbs_curve), intent(inout) :: this
real(rk), intent(in) :: Xc(:,:)
real(rk), intent(in), optional :: Wc(:)

if (allocated(this%knot)) deallocate(this%knot)
if (allocated(this%Xc)) deallocate(this%Xc)

this%Xc = Xc
this%nc = size(this%Xc, 1)

allocate(this%knot(2*this%nc))
this%knot(1:this%nc) = 0.0_rk
this%knot(this%nc+1:2*this%nc) = 1.0_rk

this%order = this%get_order()
if (present(Wc)) then
if (size(Wc) /= this%nc) then
error stop 'Number of weights does not match the number of control points.'
else
if (allocated(this%Wc)) deallocate(this%Wc)
this%Wc = Wc
end if
end if
end subroutine
!===============================================================================


!===============================================================================
!> author: Seyed Ali Ghasemi
!> license: BSD 3-Clause
Expand Down
87 changes: 62 additions & 25 deletions src/NURBS/forcad_nurbs_surface.f90
Original file line number Diff line number Diff line change
Expand Up @@ -23,31 +23,32 @@ module forcad_nurbs_surface
integer, private :: nc(2) !! number of control points in each direction
integer, private :: ng(2) !! number of geometry points in each direction
contains
procedure :: set1 !!> Set knot vectors, control points and weights for the NURBS surface object
procedure :: set2 !!> Set NURBS surface using nodes of parameter space, order, continuity, control points and weights
generic :: set => set1, set2 !!> Set NURBS surface
procedure :: create !!> Generate geometry points
procedure :: get_Xc !!> Get control points
procedure :: get_Xg !!> Get geometry points
procedure :: get_Wc !!> Get weights
procedure :: get_Xt !!> Get parameter values
procedure :: get_knot !!> Get knot vector
procedure :: get_ng !!> Get number of geometry points
procedure :: get_order !!> Get order of the NURBS surface
procedure :: finalize !!> Finalize the NURBS surface object
procedure :: get_elem_Xc !!> Generate connectivity for control points
procedure :: get_elem_Xg !!> Generate connectivity for geometry points
procedure :: export_Xc !!> Export control points to VTK file
procedure :: export_Xg !!> Export geometry points to VTK file
procedure :: modify_Xc !!> Modify control points
procedure :: modify_Wc !!> Modify weights
procedure :: get_multiplicity !!> Get multiplicity of the knot vector
procedure :: get_continuity !!> Get continuity of the surface
procedure :: get_nc !!> Get number of required control points
procedure :: derivative !!> Compute the derivative of the NURBS surface
procedure :: basis !!> Compute the basis functions of the NURBS surface
procedure :: insert_knots !!> Insert knots into the knot vector
procedure :: elevate_degree !!> Elevate degree
procedure :: set1 !!> Set knot vectors, control points and weights for the NURBS surface object
procedure :: set2 !!> Set NURBS surface using nodes of parameter space, order, continuity, control points and weights
procedure :: set3 !!> Set Bezier or Rational Bezier surface using control points and weights
generic :: set => set1, set2, set3 !!> Set NURBS surface
procedure :: create !!> Generate geometry points
procedure :: get_Xc !!> Get control points
procedure :: get_Xg !!> Get geometry points
procedure :: get_Wc !!> Get weights
procedure :: get_Xt !!> Get parameter values
procedure :: get_knot !!> Get knot vector
procedure :: get_ng !!> Get number of geometry points
procedure :: get_order !!> Get order of the NURBS surface
procedure :: finalize !!> Finalize the NURBS surface object
procedure :: get_elem_Xc !!> Generate connectivity for control points
procedure :: get_elem_Xg !!> Generate connectivity for geometry points
procedure :: export_Xc !!> Export control points to VTK file
procedure :: export_Xg !!> Export geometry points to VTK file
procedure :: modify_Xc !!> Modify control points
procedure :: modify_Wc !!> Modify weights
procedure :: get_multiplicity !!> Get multiplicity of the knot vector
procedure :: get_continuity !!> Get continuity of the surface
procedure :: get_nc !!> Get number of required control points
procedure :: derivative !!> Compute the derivative of the NURBS surface
procedure :: basis !!> Compute the basis functions of the NURBS surface
procedure :: insert_knots !!> Insert knots into the knot vector
procedure :: elevate_degree !!> Elevate degree
end type
!===============================================================================

Expand Down Expand Up @@ -99,6 +100,42 @@ pure subroutine set2(this, Xth_dir1, Xth_dir2, order, continuity1, continuity2,
!===============================================================================


!===============================================================================
!> author: Seyed Ali Ghasemi
!> license: BSD 3-Clause
!> Set Bezier or Rational Bezier surface using control points and weights.
pure subroutine set3(this, nc, Xc, Wc)
class(nurbs_surface), intent(inout) :: this
integer, intent(in) :: nc(:)
real(rk), intent(in) :: Xc(:,:)
real(rk), intent(in), optional :: Wc(:)

if (allocated(this%Xc)) deallocate(this%Xc)

this%Xc = Xc
this%nc = nc

allocate(this%knot1(2*this%nc(1)))
this%knot1(1:this%nc(1)) = 0.0_rk
this%knot1(this%nc(1)+1:2*this%nc(1)) = 1.0_rk

allocate(this%knot2(2*this%nc(2)))
this%knot2(1:this%nc(2)) = 0.0_rk
this%knot2(this%nc(2)+1:2*this%nc(2)) = 1.0_rk

this%order = this%get_order()
if (present(Wc)) then
if (size(Wc) /= this%nc(1)*this%nc(2)) then
error stop 'Number of weights does not match the number of control points.'
else
if (allocated(this%Wc)) deallocate(this%Wc)
this%Wc = Wc
end if
end if
end subroutine
!===============================================================================


!===============================================================================
!> author: Seyed Ali Ghasemi
!> license: BSD 3-Clause
Expand Down
91 changes: 66 additions & 25 deletions src/NURBS/forcad_nurbs_volume.f90
Original file line number Diff line number Diff line change
Expand Up @@ -25,31 +25,32 @@ module forcad_nurbs_volume
integer, private :: nc(3) !! number of control points in each direction
integer, private :: ng(3) !! number of geometry points in each direction
contains
procedure :: set1 !!> Set knot vectors, control points and weights for the NURBS volume object
procedure :: set2 !!> Set NURBS volume using nodes of parameter space, order, continuity, control points and weights
generic :: set => set1, set2 !!> Set NURBS volume
procedure :: create !!> Generate geometry points
procedure :: get_Xc !!> Get control points
procedure :: get_Xg !!> Get geometry points
procedure :: get_Wc !!> Get weights
procedure :: get_Xt !!> Get parameter values
procedure :: get_knot !!> Get knot vector
procedure :: get_ng !!> Get number of geometry points
procedure :: get_order !!> Get order of the NURBS volume
procedure :: finalize !!> Finalize the NURBS volume object
procedure :: get_elem_Xc !!> Generate connectivity for control points
procedure :: get_elem_Xg !!> Generate connectivity for geometry points
procedure :: export_Xc !!> Export control points to VTK file
procedure :: export_Xg !!> Export geometry points to VTK file
procedure :: modify_Xc !!> Modify control points
procedure :: modify_Wc !!> Modify weights
procedure :: get_multiplicity !!> Get multiplicity of the knot vector
procedure :: get_continuity !!> Get continuity of the volume
procedure :: get_nc !!> Get number of required control points
procedure :: derivative !!> Compute the derivative of the NURBS volume
procedure :: basis !!> Compute the basis functions of the NURBS volume
procedure :: insert_knots !!> Insert knots into the knot vector
procedure :: elevate_degree !!> Elevate the degree of the NURBS volume
procedure :: set1 !!> Set knot vectors, control points and weights for the NURBS volume object
procedure :: set2 !!> Set NURBS volume using nodes of parameter space, order, continuity, control points and weights
procedure :: set3 !!> Set Bezier or Rational Bezier volume using control points and weights
generic :: set => set1, set2, set3 !!> Set NURBS volume
procedure :: create !!> Generate geometry points
procedure :: get_Xc !!> Get control points
procedure :: get_Xg !!> Get geometry points
procedure :: get_Wc !!> Get weights
procedure :: get_Xt !!> Get parameter values
procedure :: get_knot !!> Get knot vector
procedure :: get_ng !!> Get number of geometry points
procedure :: get_order !!> Get order of the NURBS volume
procedure :: finalize !!> Finalize the NURBS volume object
procedure :: get_elem_Xc !!> Generate connectivity for control points
procedure :: get_elem_Xg !!> Generate connectivity for geometry points
procedure :: export_Xc !!> Export control points to VTK file
procedure :: export_Xg !!> Export geometry points to VTK file
procedure :: modify_Xc !!> Modify control points
procedure :: modify_Wc !!> Modify weights
procedure :: get_multiplicity !!> Get multiplicity of the knot vector
procedure :: get_continuity !!> Get continuity of the volume
procedure :: get_nc !!> Get number of required control points
procedure :: derivative !!> Compute the derivative of the NURBS volume
procedure :: basis !!> Compute the basis functions of the NURBS volume
procedure :: insert_knots !!> Insert knots into the knot vector
procedure :: elevate_degree !!> Elevate the degree of the NURBS volume
end type
!===============================================================================

Expand Down Expand Up @@ -105,6 +106,46 @@ pure subroutine set2(this, Xth_dir1, Xth_dir2, Xth_dir3, order, continuity1, con
!===============================================================================


!===============================================================================
!> author: Seyed Ali Ghasemi
!> license: BSD 3-Clause
!> Set Bezier or Rational Bezier volume using control points and weights.
pure subroutine set3(this, nc, Xc, Wc)
class(nurbs_volume), intent(inout) :: this
integer, intent(in) :: nc(:)
real(rk), intent(in) :: Xc(:,:)
real(rk), intent(in), optional :: Wc(:)

if (allocated(this%Xc)) deallocate(this%Xc)

this%Xc = Xc
this%nc = nc

allocate(this%knot1(2*this%nc(1)))
this%knot1(1:this%nc(1)) = 0.0_rk
this%knot1(this%nc(1)+1:2*this%nc(1)) = 1.0_rk

allocate(this%knot2(2*this%nc(2)))
this%knot2(1:this%nc(2)) = 0.0_rk
this%knot2(this%nc(2)+1:2*this%nc(2)) = 1.0_rk

allocate(this%knot3(2*this%nc(3)))
this%knot3(1:this%nc(3)) = 0.0_rk
this%knot3(this%nc(3)+1:2*this%nc(3)) = 1.0_rk

this%order = this%get_order()
if (present(Wc)) then
if (size(Wc) /= this%nc(1)*this%nc(2)*this%nc(3)) then
error stop 'Number of weights does not match the number of control points.'
else
if (allocated(this%Wc)) deallocate(this%Wc)
this%Wc = Wc
end if
end if
end subroutine
!===============================================================================


!===============================================================================
!> author: Seyed Ali Ghasemi
!> license: BSD 3-Clause
Expand Down

0 comments on commit 93dd393

Please sign in to comment.