render_sub Subroutine

private subroutine render_sub(cnt, extent, samples, state)

Render the SDFs onto a voxel grid

Arguments

Type IntentOptional Attributes Name
type(sdf), intent(in) :: cnt(:)
type(vector), intent(in) :: extent
integer, intent(in) :: samples(3)
type(settings_t), intent(in) :: state

Source Code

    subroutine render_sub(cnt, extent, samples, state)
        !! Render the SDFs onto a voxel grid
        use sim_state_mod, only : settings_t
        use utils,         only : pbar
        use constants,     only : fileplace, sp
        use writer_mod
                  
        type(settings_t), intent(IN) :: state
        type(sdf),  intent(IN) :: cnt(:)
        integer,          intent(IN) :: samples(3)
        type(vector),     intent(IN) :: extent

        type(vector)               :: pos, wid
        integer                    :: i, j, k, u, id
        real(kind=wp)              :: x, y, z, ds(size(cnt)), ns(3), minvalue
        real(kind=sp), allocatable :: image(:, :, :)
        type(pbar)                 :: bar

        ns = nint(samples / 2._wp)
        allocate(image(samples(1), samples(2), samples(3)))
        wid = vector(extent%x/ns(1), extent%y/ns(2), extent%z/ns(3))
        bar = pbar(samples(1))
!$omp parallel default(none) shared(cnt, ns, wid, image, samples, bar)&
!$omp private(i, x, y, z, pos, j, k, u, ds, id, minvalue)
!$omp do
        do i = 1, samples(1)
            x = (i-ns(1)) *wid%x
            do j = 1, samples(2)
                y = (j-ns(2)) *wid%y
                do k = 1, samples(3)
                    z = (k-ns(3)) * wid%z
                    pos = vector(x, y, z)
                    ds = 0._wp
                    do u = 1, size(ds)
                        ds(u) = cnt(u)%evaluate(pos)
                    end do
                    image(i, j, k) = minval(ds)
                end do
            end do
            call bar%progress()
        end do
!$OMP end  do
!$OMP end parallel
        call write_data(image, trim(fileplace)//state%renderfile, state, overwrite=.true.)
    end subroutine render_sub