Rewrote Fill2.pm to C++, deleted Perl infills for good.

Removed dependency on Perl Math::PlanePath module.
Fixed compilation with Visual Studio and SLIC3R_DEBUG: Visual Studio older than 2015 does not support the prinf type specifier %zu. Use %Iu instead.
C++11 move semantics enabled.
This commit is contained in:
bubnikv 2016-11-02 10:47:00 +01:00
parent 3a31d37d35
commit 95ede7c4b8
49 changed files with 628 additions and 1803 deletions

View File

@ -15,7 +15,6 @@ my %prereqs = qw(
File::Basename 0 File::Basename 0
File::Spec 0 File::Spec 0
Getopt::Long 0 Getopt::Long 0
Math::PlanePath 53
Module::Build::WithXSpp 0.14 Module::Build::WithXSpp 0.14
Moo 1.003001 Moo 1.003001
POSIX 0 POSIX 0

View File

@ -56,8 +56,6 @@ use Slic3r::Config;
use Slic3r::ExPolygon; use Slic3r::ExPolygon;
use Slic3r::ExtrusionLoop; use Slic3r::ExtrusionLoop;
use Slic3r::ExtrusionPath; use Slic3r::ExtrusionPath;
use Slic3r::Fill;
use Slic3r::Fill2;
use Slic3r::Flow; use Slic3r::Flow;
use Slic3r::Format::AMF; use Slic3r::Format::AMF;
use Slic3r::Format::OBJ; use Slic3r::Format::OBJ;
@ -139,7 +137,7 @@ sub spawn_thread {
# Otherwise run the task on the current thread. # Otherwise run the task on the current thread.
# Used for # Used for
# Slic3r::Print::Object->layers->make_perimeters : This is a pure C++ function. # Slic3r::Print::Object->layers->make_perimeters : This is a pure C++ function.
# Slic3r::Print::Object->layers->make_fill : This requires a rewrite of Fill.pm to C++. # Slic3r::Print::Object->layers->make_fill : This is a pure C++ function.
# Slic3r::Print::SupportMaterial::generate_toolpaths # Slic3r::Print::SupportMaterial::generate_toolpaths
sub parallelize { sub parallelize {
my %params = @_; my %params = @_;

View File

@ -1,308 +0,0 @@
package Slic3r::Fill;
use Moo;
use List::Util qw(max);
use Slic3r::ExtrusionPath ':roles';
use Slic3r::Fill::3DHoneycomb;
use Slic3r::Fill::Base;
use Slic3r::Fill::Concentric;
use Slic3r::Fill::Honeycomb;
use Slic3r::Fill::PlanePath;
use Slic3r::Fill::Rectilinear;
use Slic3r::Flow ':roles';
use Slic3r::Geometry qw(X Y PI scale chained_path deg2rad);
use Slic3r::Geometry::Clipper qw(union union_ex diff diff_ex intersection_ex offset offset2);
use Slic3r::Surface ':types';
has 'bounding_box' => (is => 'ro', required => 0);
has 'fillers' => (is => 'rw', default => sub { {} });
our %FillTypes = (
archimedeanchords => 'Slic3r::Fill::ArchimedeanChords',
rectilinear => 'Slic3r::Fill::Rectilinear',
grid => 'Slic3r::Fill::Grid',
flowsnake => 'Slic3r::Fill::Flowsnake',
octagramspiral => 'Slic3r::Fill::OctagramSpiral',
hilbertcurve => 'Slic3r::Fill::HilbertCurve',
line => 'Slic3r::Fill::Line',
concentric => 'Slic3r::Fill::Concentric',
honeycomb => 'Slic3r::Fill::Honeycomb',
'3dhoneycomb' => 'Slic3r::Fill::3DHoneycomb',
);
sub filler {
my $self = shift;
my ($filler) = @_;
if (!ref $self) {
return $FillTypes{$filler}->new;
}
$self->fillers->{$filler} ||= $FillTypes{$filler}->new(
bounding_box => $self->bounding_box,
);
return $self->fillers->{$filler};
}
sub make_fill {
my $self = shift;
my ($layerm) = @_;
Slic3r::debugf "Filling layer %d:\n", $layerm->layer->id;
my $fill_density = $layerm->region->config->fill_density;
my $infill_flow = $layerm->flow(FLOW_ROLE_INFILL);
my $solid_infill_flow = $layerm->flow(FLOW_ROLE_SOLID_INFILL);
my $top_solid_infill_flow = $layerm->flow(FLOW_ROLE_TOP_SOLID_INFILL);
my @surfaces = ();
# merge adjacent surfaces
# in case of bridge surfaces, the ones with defined angle will be attached to the ones
# without any angle (shouldn't this logic be moved to process_external_surfaces()?)
{
my @surfaces_with_bridge_angle = grep { $_->bridge_angle >= 0 } @{$layerm->fill_surfaces};
# group surfaces by distinct properties
my @groups = @{$layerm->fill_surfaces->group};
# merge compatible groups (we can generate continuous infill for them)
{
# cache flow widths and patterns used for all solid groups
# (we'll use them for comparing compatible groups)
my @is_solid = my @fw = my @pattern = ();
for (my $i = 0; $i <= $#groups; $i++) {
# we can only merge solid non-bridge surfaces, so discard
# non-solid surfaces
if ($groups[$i][0]->is_solid && (!$groups[$i][0]->is_bridge || $layerm->layer->id == 0)) {
$is_solid[$i] = 1;
$fw[$i] = ($groups[$i][0]->surface_type == S_TYPE_TOP)
? $top_solid_infill_flow->width
: $solid_infill_flow->width;
$pattern[$i] = $groups[$i][0]->is_external
? $layerm->region->config->external_fill_pattern
: 'rectilinear';
} else {
$is_solid[$i] = 0;
$fw[$i] = 0;
$pattern[$i] = 'none';
}
}
# loop through solid groups
for (my $i = 0; $i <= $#groups; $i++) {
next if !$is_solid[$i];
# find compatible groups and append them to this one
for (my $j = $i+1; $j <= $#groups; $j++) {
next if !$is_solid[$j];
if ($fw[$i] == $fw[$j] && $pattern[$i] eq $pattern[$j]) {
# groups are compatible, merge them
push @{$groups[$i]}, @{$groups[$j]};
splice @groups, $j, 1;
splice @is_solid, $j, 1;
splice @fw, $j, 1;
splice @pattern, $j, 1;
}
}
}
}
# give priority to bridges
@groups = sort { ($a->[0]->bridge_angle >= 0) ? -1 : 0 } @groups;
foreach my $group (@groups) {
my $union_p = union([ map $_->p, @$group ], 1);
# subtract surfaces having a defined bridge_angle from any other
if (@surfaces_with_bridge_angle && $group->[0]->bridge_angle < 0) {
$union_p = diff(
$union_p,
[ map $_->p, @surfaces_with_bridge_angle ],
1,
);
}
# subtract any other surface already processed
my $union = diff_ex(
$union_p,
[ map $_->p, @surfaces ],
1,
);
push @surfaces, map $group->[0]->clone(expolygon => $_), @$union;
}
}
# we need to detect any narrow surfaces that might collapse
# when adding spacing below
# such narrow surfaces are often generated in sloping walls
# by bridge_over_infill() and combine_infill() as a result of the
# subtraction of the combinable area from the layer infill area,
# which leaves small areas near the perimeters
# we are going to grow such regions by overlapping them with the void (if any)
# TODO: detect and investigate whether there could be narrow regions without
# any void neighbors
{
my $distance_between_surfaces = max(
$infill_flow->scaled_spacing,
$solid_infill_flow->scaled_spacing,
$top_solid_infill_flow->scaled_spacing,
);
my $collapsed = diff(
[ map @{$_->expolygon}, @surfaces ],
offset2([ map @{$_->expolygon}, @surfaces ], -$distance_between_surfaces/2, +$distance_between_surfaces/2),
1,
);
push @surfaces, map Slic3r::Surface->new(
expolygon => $_,
surface_type => S_TYPE_INTERNALSOLID,
), @{intersection_ex(
offset($collapsed, $distance_between_surfaces),
[
(map @{$_->expolygon}, grep $_->surface_type == S_TYPE_INTERNALVOID, @surfaces),
(@$collapsed),
],
1,
)};
}
if (0) {
require "Slic3r/SVG.pm";
Slic3r::SVG::output("fill_" . $layerm->print_z . ".svg",
expolygons => [ map $_->expolygon, grep !$_->is_solid, @surfaces ],
red_expolygons => [ map $_->expolygon, grep $_->is_solid, @surfaces ],
);
}
my @fills = ();
SURFACE: foreach my $surface (@surfaces) {
next if $surface->surface_type == S_TYPE_INTERNALVOID;
my $filler = $layerm->region->config->fill_pattern;
my $density = $fill_density;
my $role = ($surface->surface_type == S_TYPE_TOP) ? FLOW_ROLE_TOP_SOLID_INFILL
: $surface->is_solid ? FLOW_ROLE_SOLID_INFILL
: FLOW_ROLE_INFILL;
my $is_bridge = $layerm->layer->id > 0 && $surface->is_bridge;
my $is_solid = $surface->is_solid;
if ($surface->is_solid) {
$density = 100;
$filler = 'rectilinear';
if ($surface->is_external && !$is_bridge) {
$filler = $layerm->region->config->external_fill_pattern;
}
} else {
next SURFACE unless $density > 0;
}
# get filler object
my $f = $self->filler($filler);
# calculate the actual flow we'll be using for this infill
my $h = $surface->thickness == -1 ? $layerm->layer->height : $surface->thickness;
my $flow = $layerm->region->flow(
$role,
$h,
$is_bridge || $f->use_bridge_flow,
$layerm->layer->id == 0,
-1,
$layerm->layer->object,
);
# calculate flow spacing for infill pattern generation
my $using_internal_flow = 0;
if (!$is_solid && !$is_bridge) {
# it's internal infill, so we can calculate a generic flow spacing
# for all layers, for avoiding the ugly effect of
# misaligned infill on first layer because of different extrusion width and
# layer height
my $internal_flow = $layerm->region->flow(
FLOW_ROLE_INFILL,
$layerm->layer->object->config->layer_height, # TODO: handle infill_every_layers?
0, # no bridge
0, # no first layer
-1, # auto width
$layerm->layer->object,
);
$f->spacing($internal_flow->spacing);
$using_internal_flow = 1;
# } elsif ($surface->surface_type == S_TYPE_INTERNALBRIDGE) {
# # The internal bridging layer will be sparse.
# $f->spacing($flow->spacing * 2.);
} else {
$f->spacing($flow->spacing);
}
my $old_spacing = $f->spacing;
$f->layer_id($layerm->layer->id);
$f->z($layerm->layer->print_z);
$f->angle(deg2rad($layerm->region->config->fill_angle));
$f->loop_clipping(scale($flow->nozzle_diameter) * &Slic3r::LOOP_CLIPPING_LENGTH_OVER_NOZZLE_DIAMETER);
# apply half spacing using this flow's own spacing and generate infill
my @polylines = map $f->fill_surface(
$_,
density => $density/100,
layer_height => $h,
#FIXME Vojtech disabled the automatic extrusion width adjustment as this feature quite often
# generated extrusions with excessive widths.
# The goal of the automatic line width adjustment was to fill in a region without a gap, but because
# the filled regions are mostly not aligned with the fill direction, very likely
# the extrusion width adjustment causes more harm than good.
dont_adjust => 1,
), @{ $surface->offset(-scale($f->spacing)/2) };
next unless @polylines;
# calculate actual flow from spacing (which might have been adjusted by the infill
# pattern generator)
if ($using_internal_flow) {
# if we used the internal flow we're not doing a solid infill
# so we can safely ignore the slight variation that might have
# been applied to $f->flow_spacing
} else {
if (abs($old_spacing - $f->spacing) > 0.3 * $old_spacing) {
print "Infill: Extreme spacing adjustment, from: ", $old_spacing, " to: ", $f->spacing, "\n";
}
$flow = Slic3r::Flow->new_from_spacing(
spacing => $f->spacing,
nozzle_diameter => $flow->nozzle_diameter,
layer_height => $h,
bridge => $is_bridge || $f->use_bridge_flow,
);
}
my $mm3_per_mm = $flow->mm3_per_mm;
# save into layer
{
my $role = $is_bridge ? EXTR_ROLE_BRIDGE
: $is_solid ? (($surface->surface_type == S_TYPE_TOP) ? EXTR_ROLE_TOPSOLIDFILL : EXTR_ROLE_SOLIDFILL)
: EXTR_ROLE_FILL;
push @fills, my $collection = Slic3r::ExtrusionPath::Collection->new;
$collection->no_sort($f->no_sort);
$collection->append(
map Slic3r::ExtrusionPath->new(
polyline => $_,
role => $role,
mm3_per_mm => $mm3_per_mm,
width => $flow->width,
height => $flow->height,
), @polylines,
);
}
}
# add thin fill regions
foreach my $thin_fill (@{$layerm->thin_fills}) {
push @fills, Slic3r::ExtrusionPath::Collection->new($thin_fill);
}
return @fills;
}
1;

View File

@ -1,230 +0,0 @@
package Slic3r::Fill::3DHoneycomb;
use Moo;
extends 'Slic3r::Fill::Base';
use POSIX qw(ceil fmod);
use Slic3r::Geometry qw(scale scaled_epsilon);
use Slic3r::Geometry::Clipper qw(intersection_pl);
# require bridge flow since most of this pattern hangs in air
sub use_bridge_flow { 1 }
sub fill_surface {
my ($self, $surface, %params) = @_;
my $expolygon = $surface->expolygon;
my $bb = $expolygon->bounding_box;
my $size = $bb->size;
my $distance = scale($self->spacing) / $params{density};
# align bounding box to a multiple of our honeycomb grid module
# (a module is 2*$distance since one $distance half-module is
# growing while the other $distance half-module is shrinking)
{
my $min = $bb->min_point;
$min->translate(
-($bb->x_min % (2*$distance)),
-($bb->y_min % (2*$distance)),
);
$bb->merge_point($min);
}
# generate pattern
my @polylines = map Slic3r::Polyline->new(@$_),
makeGrid(
scale($self->z),
$distance,
ceil($size->x / $distance) + 1,
ceil($size->y / $distance) + 1, #//
(($self->layer_id / $surface->thickness_layers) % 2) + 1,
);
# move pattern in place
$_->translate($bb->x_min, $bb->y_min) for @polylines;
# clip pattern to boundaries
@polylines = @{intersection_pl(\@polylines, \@$expolygon)};
# connect lines
unless ($params{dont_connect} || !@polylines) { # prevent calling leftmost_point() on empty collections
my ($expolygon_off) = @{$expolygon->offset_ex(scaled_epsilon)};
my $collection = Slic3r::Polyline::Collection->new(@polylines);
@polylines = ();
foreach my $polyline (@{$collection->chained_path_from($collection->leftmost_point, 0)}) {
# try to append this polyline to previous one if any
if (@polylines) {
my $line = Slic3r::Line->new($polylines[-1]->last_point, $polyline->first_point);
if ($line->length <= 1.5*$distance && $expolygon_off->contains_line($line)) {
$polylines[-1]->append_polyline($polyline);
next;
}
}
# make a clone before $collection goes out of scope
push @polylines, $polyline->clone;
}
}
# TODO: return ExtrusionLoop objects to get better chained paths
return @polylines;
}
=head1 DESCRIPTION
Creates a contiguous sequence of points at a specified height that make
up a horizontal slice of the edges of a space filling truncated
octahedron tesselation. The octahedrons are oriented so that the
square faces are in the horizontal plane with edges parallel to the X
and Y axes.
Credits: David Eccles (gringer).
=head2 makeGrid(z, gridSize, gridWidth, gridHeight, curveType)
Generate a set of curves (array of array of 2d points) that describe a
horizontal slice of a truncated regular octahedron with a specified
grid square size.
=cut
sub makeGrid {
my ($z, $gridSize, $gridWidth, $gridHeight, $curveType) = @_;
my $scaleFactor = $gridSize;
my $normalisedZ = $z / $scaleFactor;
my @points = makeNormalisedGrid($normalisedZ, $gridWidth, $gridHeight, $curveType);
foreach my $lineRef (@points) {
foreach my $pointRef (@$lineRef) {
$pointRef->[0] *= $scaleFactor;
$pointRef->[1] *= $scaleFactor;
}
}
return @points;
}
=head1 FUNCTIONS
=cut
=head2 colinearPoints(offset, gridLength)
Generate an array of points that are in the same direction as the
basic printing line (i.e. Y points for columns, X points for rows)
Note: a negative offset only causes a change in the perpendicular
direction
=cut
sub colinearPoints {
my ($offset, $baseLocation, $gridLength) = @_;
my @points = ();
push @points, $baseLocation - abs($offset/2);
for (my $i = 0; $i < $gridLength; $i++) {
push @points, $baseLocation + $i + abs($offset/2);
push @points, $baseLocation + ($i+1) - abs($offset/2);
}
push @points, $baseLocation + $gridLength + abs($offset/2);
return @points;
}
=head2 colinearPoints(offset, baseLocation, gridLength)
Generate an array of points for the dimension that is perpendicular to
the basic printing line (i.e. X points for columns, Y points for rows)
=cut
sub perpendPoints {
my ($offset, $baseLocation, $gridLength) = @_;
my @points = ();
my $side = 2*(($baseLocation) % 2) - 1;
push @points, $baseLocation - $offset/2 * $side;
for (my $i = 0; $i < $gridLength; $i++) {
$side = 2*(($i+$baseLocation) % 2) - 1;
push @points, $baseLocation + $offset/2 * $side;
push @points, $baseLocation + $offset/2 * $side;
}
push @points, $baseLocation - $offset/2 * $side;
return @points;
}
=head2 trim(pointArrayRef, minX, minY, maxX, maxY)
Trims an array of points to specified rectangular limits. Point
components that are outside these limits are set to the limits.
=cut
sub trim {
my ($pointArrayRef, $minX, $minY, $maxX, $maxY) = @_;
foreach (@$pointArrayRef) {
$_->[0] = ($_->[0] < $minX) ? $minX : (($_->[0] > $maxX) ? $maxX : $_->[0]);
$_->[1] = ($_->[1] < $minY) ? $minY : (($_->[1] > $maxY) ? $maxY : $_->[1]);
}
}
=head2 makeNormalisedGrid(z, gridWidth, gridHeight, curveType)
Generate a set of curves (array of array of 2d points) that describe a
horizontal slice of a truncated regular octahedron with edge length 1.
curveType specifies which lines to print, 1 for vertical lines
(columns), 2 for horizontal lines (rows), and 3 for both.
=cut
sub makeNormalisedGrid {
my ($z, $gridWidth, $gridHeight, $curveType) = @_;
## offset required to create a regular octagram
my $octagramGap = 0.5;
# sawtooth wave function for range f($z) = [-$octagramGap .. $octagramGap]
my $a = sqrt(2); # period
my $wave = abs(fmod($z, $a) - $a/2)/$a*4 - 1;
my $offset = $wave * $octagramGap;
my @points = ();
if (($curveType & 1) != 0) {
for (my $x = 0; $x <= $gridWidth; $x++) {
my @xPoints = perpendPoints($offset, $x, $gridHeight);
my @yPoints = colinearPoints($offset, 0, $gridHeight);
# This is essentially @newPoints = zip(@xPoints, @yPoints)
my @newPoints = map [ $xPoints[$_], $yPoints[$_] ], 0..$#xPoints;
# trim points to grid edges
#trim(\@newPoints, 0, 0, $gridWidth, $gridHeight);
if ($x % 2 == 0){
push @points, [ @newPoints ];
} else {
push @points, [ reverse @newPoints ];
}
}
}
if (($curveType & 2) != 0) {
for (my $y = 0; $y <= $gridHeight; $y++) {
my @xPoints = colinearPoints($offset, 0, $gridWidth);
my @yPoints = perpendPoints($offset, $y, $gridWidth);
my @newPoints = map [ $xPoints[$_], $yPoints[$_] ], 0..$#xPoints;
# trim points to grid edges
#trim(\@newPoints, 0, 0, $gridWidth, $gridHeight);
if ($y % 2 == 0) {
push @points, [ @newPoints ];
} else {
push @points, [ reverse @newPoints ];
}
}
}
return @points;
}
1;

View File

@ -1,101 +0,0 @@
package Slic3r::Fill::Base;
use Moo;
has 'layer_id' => (is => 'rw');
has 'z' => (is => 'rw'); # in unscaled coordinates
has 'angle' => (is => 'rw'); # in radians, ccw, 0 = East
has 'spacing' => (is => 'rw'); # in unscaled coordinates
has 'loop_clipping' => (is => 'rw', default => sub { 0 }); # in scaled coordinates
has 'bounding_box' => (is => 'ro', required => 0); # Slic3r::Geometry::BoundingBox object
sub set_spacing {
my ($self, $spacing) = @_;
$self->spacing($spacing);
}
sub set_angle {
my ($self, $angle) = @_;
$self->angle($angle);
}
sub adjust_solid_spacing {
my $self = shift;
my %params = @_;
my $number_of_lines = int($params{width} / $params{distance}) + 1;
return $params{distance} if $number_of_lines <= 1;
my $extra_space = $params{width} % $params{distance};
return $params{distance} + $extra_space / ($number_of_lines - 1);
}
sub no_sort { 0 }
sub use_bridge_flow { 0 }
package Slic3r::Fill::WithDirection;
use Moo::Role;
use Slic3r::Geometry qw(PI rad2deg);
sub angles () { [0, PI/2] }
sub infill_direction {
my $self = shift;
my ($surface) = @_;
if (!defined $self->angle) {
warn "Using undefined infill angle";
$self->angle(0);
}
# set infill angle
my (@rotate);
$rotate[0] = $self->angle;
$rotate[1] = $self->bounding_box
? $self->bounding_box->center
: $surface->expolygon->bounding_box->center;
my $shift = $rotate[1]->clone;
if (defined $self->layer_id) {
# alternate fill direction
my $layer_num = $self->layer_id / $surface->thickness_layers;
my $angle = $self->angles->[$layer_num % @{$self->angles}];
$rotate[0] = $self->angle + $angle if $angle;
}
# use bridge angle
if ($surface->bridge_angle >= 0) {
Slic3r::debugf "Filling bridge with angle %d\n", rad2deg($surface->bridge_angle);
$rotate[0] = $surface->bridge_angle;
}
$rotate[0] += PI/2;
$shift->rotate(@rotate);
return [\@rotate, $shift];
}
# this method accepts any object that implements rotate() and translate()
sub rotate_points {
my $self = shift;
my ($expolygon, $rotate_vector) = @_;
# rotate points
my ($rotate, $shift) = @$rotate_vector;
$rotate = [ -$rotate->[0], $rotate->[1] ];
$expolygon->rotate(@$rotate);
$expolygon->translate(@$shift);
}
sub rotate_points_back {
my $self = shift;
my ($paths, $rotate_vector) = @_;
my ($rotate, $shift) = @$rotate_vector;
$shift = [ map -$_, @$shift ];
$_->translate(@$shift) for @$paths;
$_->rotate(@$rotate) for @$paths;
}
1;

View File

@ -1,57 +0,0 @@
package Slic3r::Fill::Concentric;
use Moo;
extends 'Slic3r::Fill::Base';
use Slic3r::Geometry qw(scale unscale X);
use Slic3r::Geometry::Clipper qw(offset offset2 union_pt_chained);
sub no_sort { 1 }
sub fill_surface {
my $self = shift;
my ($surface, %params) = @_;
# no rotation is supported for this infill pattern
my $expolygon = $surface->expolygon;
my $bounding_box = $expolygon->bounding_box;
my $min_spacing = scale($self->spacing);
my $distance = $min_spacing / $params{density};
if ($params{density} == 1 && !$params{dont_adjust}) {
$distance = $self->adjust_solid_spacing(
width => $bounding_box->size->[X],
distance => $distance,
);
$self->spacing(unscale $distance);
}
my @loops = my @last = map $_->clone, @$expolygon;
while (@last) {
push @loops, @last = @{offset2(\@last, -($distance + 0.5*$min_spacing), +0.5*$min_spacing)};
}
# generate paths from the outermost to the innermost, to avoid
# adhesion problems of the first central tiny loops
@loops = map Slic3r::Polygon->new(@$_),
reverse @{union_pt_chained(\@loops)};
# split paths using a nearest neighbor search
my @paths = ();
my $last_pos = Slic3r::Point->new(0,0);
foreach my $loop (@loops) {
push @paths, $loop->split_at_index($last_pos->nearest_point_index(\@$loop));
$last_pos = $paths[-1]->last_point;
}
# clip the paths to prevent the extruder from getting exactly on the first point of the loop
$_->clip_end($self->loop_clipping) for @paths;
@paths = grep $_->is_valid, @paths; # remove empty paths (too short, thus eaten by clipping)
# TODO: return ExtrusionLoop objects to get better chained paths
return @paths;
}
1;

View File

@ -1,129 +0,0 @@
package Slic3r::Fill::Honeycomb;
use Moo;
extends 'Slic3r::Fill::Base';
with qw(Slic3r::Fill::WithDirection);
has 'cache' => (is => 'rw', default => sub {{}});
use Slic3r::Geometry qw(PI X Y MIN MAX scale scaled_epsilon);
use Slic3r::Geometry::Clipper qw(intersection intersection_pl);
sub angles () { [0, PI/3, PI/3*2] }
sub fill_surface {
my $self = shift;
my ($surface, %params) = @_;
my $rotate_vector = $self->infill_direction($surface);
# cache hexagons math
my $cache_id = sprintf "d%s_s%s", $params{density}, $self->spacing;
my $m;
if (!($m = $self->cache->{$cache_id})) {
$m = $self->cache->{$cache_id} = {};
my $min_spacing = scale($self->spacing);
$m->{distance} = $min_spacing / $params{density};
$m->{hex_side} = $m->{distance} / (sqrt(3)/2);
$m->{hex_width} = $m->{distance} * 2; # $m->{hex_width} == $m->{hex_side} * sqrt(3);
my $hex_height = $m->{hex_side} * 2;
$m->{pattern_height} = $hex_height + $m->{hex_side};
$m->{y_short} = $m->{distance} * sqrt(3)/3;
$m->{x_offset} = $min_spacing / 2;
$m->{y_offset} = $m->{x_offset} * sqrt(3)/3;
$m->{hex_center} = Slic3r::Point->new($m->{hex_width}/2, $m->{hex_side});
}
my @polygons = ();
{
# adjust actual bounding box to the nearest multiple of our hex pattern
# and align it so that it matches across layers
my $bounding_box = $surface->expolygon->bounding_box;
{
# rotate bounding box according to infill direction
my $bb_polygon = $bounding_box->polygon;
$bb_polygon->rotate($rotate_vector->[0][0], $m->{hex_center});
$bounding_box = $bb_polygon->bounding_box;
# extend bounding box so that our pattern will be aligned with other layers
# $bounding_box->[X1] and [Y1] represent the displacement between new bounding box offset and old one
$bounding_box->merge_point(Slic3r::Point->new(
$bounding_box->x_min - ($bounding_box->x_min % $m->{hex_width}),
$bounding_box->y_min - ($bounding_box->y_min % $m->{pattern_height}),
));
}
my $x = $bounding_box->x_min;
while ($x <= $bounding_box->x_max) {
my $p = [];
my @x = ($x + $m->{x_offset}, $x + $m->{distance} - $m->{x_offset});
for (1..2) {
@$p = reverse @$p; # turn first half upside down
my @p = ();
for (my $y = $bounding_box->y_min; $y <= $bounding_box->y_max; $y += $m->{y_short} + $m->{hex_side} + $m->{y_short} + $m->{hex_side}) {
push @$p,
[ $x[1], $y + $m->{y_offset} ],
[ $x[0], $y + $m->{y_short} - $m->{y_offset} ],
[ $x[0], $y + $m->{y_short} + $m->{hex_side} + $m->{y_offset} ],
[ $x[1], $y + $m->{y_short} + $m->{hex_side} + $m->{y_short} - $m->{y_offset} ],
[ $x[1], $y + $m->{y_short} + $m->{hex_side} + $m->{y_short} + $m->{hex_side} + $m->{y_offset} ];
}
@x = map $_ + $m->{distance}, reverse @x; # draw symmetrical pattern
$x += $m->{distance};
}
push @polygons, Slic3r::Polygon->new(@$p);
}
$_->rotate(-$rotate_vector->[0][0], $m->{hex_center}) for @polygons;
}
my @paths;
if ($params{complete} || 1) {
# we were requested to complete each loop;
# in this case we don't try to make more continuous paths
@paths = map $_->split_at_first_point,
@{intersection([ $surface->p ], \@polygons)};
} else {
# consider polygons as polylines without re-appending the initial point:
# this cuts the last segment on purpose, so that the jump to the next
# path is more straight
@paths = @{intersection_pl(
[ map Slic3r::Polyline->new(@$_), @polygons ],
[ @{$surface->expolygon} ],
)};
# connect paths
if (@paths) { # prevent calling leftmost_point() on empty collections
my $collection = Slic3r::Polyline::Collection->new(@paths);
@paths = ();
foreach my $path (@{$collection->chained_path_from($collection->leftmost_point, 0)}) {
if (@paths) {
# distance between first point of this path and last point of last path
my $distance = $paths[-1]->last_point->distance_to($path->first_point);
if ($distance <= $m->{hex_width}) {
$paths[-1]->append_polyline($path);
next;
}
}
# make a clone before $collection goes out of scope
push @paths, $path->clone;
}
}
# clip paths again to prevent connection segments from crossing the expolygon boundaries
@paths = @{intersection_pl(
\@paths,
[ map @$_, @{$surface->expolygon->offset_ex(scaled_epsilon)} ],
)};
}
return @paths;
}
1;

View File

@ -1,118 +0,0 @@
package Slic3r::Fill::PlanePath;
use Moo;
extends 'Slic3r::Fill::Base';
with qw(Slic3r::Fill::WithDirection);
use Slic3r::Geometry qw(scale X1 Y1 X2 Y2);
use Slic3r::Geometry::Clipper qw(intersection_pl);
sub angles () { [0] }
sub multiplier () { 1 }
sub process_polyline {}
sub fill_surface {
my $self = shift;
my ($surface, %params) = @_;
# rotate polygons
my $expolygon = $surface->expolygon->clone;
my $rotate_vector = $self->infill_direction($surface);
$self->rotate_points($expolygon, $rotate_vector);
my $distance_between_lines = scale($self->spacing) / $params{density} * $self->multiplier;
# align infill across layers using the object's bounding box
my $bb_polygon = $self->bounding_box->polygon;
$self->rotate_points($bb_polygon, $rotate_vector);
my $bounding_box = $bb_polygon->bounding_box;
(ref $self) =~ /::([^:]+)$/;
my $path = "Math::PlanePath::$1"->new;
my $translate = Slic3r::Point->new(0,0); # vector
if ($path->x_negative || $path->y_negative) {
# if the curve extends on both positive and negative coordinate space,
# center our expolygon around origin
$translate = $bounding_box->center->negative;
} else {
# if the curve does not extend in negative coordinate space,
# move expolygon entirely in positive coordinate space
$translate = $bounding_box->min_point->negative;
}
$expolygon->translate(@$translate);
$bounding_box->translate(@$translate);
my ($n_lo, $n_hi) = $path->rect_to_n_range(
map { $_ / $distance_between_lines }
@{$bounding_box->min_point},
@{$bounding_box->max_point},
);
my $polyline = Slic3r::Polyline->new(
map [ map { $_ * $distance_between_lines } $path->n_to_xy($_) ], ($n_lo..$n_hi)
);
return {} if @$polyline <= 1;
$self->process_polyline($polyline, $bounding_box);
my @paths = @{intersection_pl([$polyline], \@$expolygon)};
if (0) {
require "Slic3r/SVG.pm";
Slic3r::SVG::output("fill.svg",
no_arrows => 1,
polygons => \@$expolygon,
green_polygons => [ $bounding_box->polygon ],
polylines => [ $polyline ],
red_polylines => \@paths,
);
}
# paths must be repositioned and rotated back
$_->translate(@{$translate->negative}) for @paths;
$self->rotate_points_back(\@paths, $rotate_vector);
return @paths;
}
package Slic3r::Fill::ArchimedeanChords;
use Moo;
extends 'Slic3r::Fill::PlanePath';
use Math::PlanePath::ArchimedeanChords;
package Slic3r::Fill::Flowsnake;
use Moo;
extends 'Slic3r::Fill::PlanePath';
use Math::PlanePath::Flowsnake;
use Slic3r::Geometry qw(X);
# Sorry, this fill is currently broken.
sub process_polyline {
my $self = shift;
my ($polyline, $bounding_box) = @_;
$_->[X] += $bounding_box->center->[X] for @$polyline;
}
package Slic3r::Fill::HilbertCurve;
use Moo;
extends 'Slic3r::Fill::PlanePath';
use Math::PlanePath::HilbertCurve;
package Slic3r::Fill::OctagramSpiral;
use Moo;
extends 'Slic3r::Fill::PlanePath';
use Math::PlanePath::OctagramSpiral;
sub multiplier () { sqrt(2) }
1;

View File

@ -1,172 +0,0 @@
package Slic3r::Fill::Rectilinear;
use Moo;
extends 'Slic3r::Fill::Base';
with qw(Slic3r::Fill::WithDirection);
has '_min_spacing' => (is => 'rw');
has '_line_spacing' => (is => 'rw');
has '_diagonal_distance' => (is => 'rw');
has '_line_oscillation' => (is => 'rw');
use Slic3r::Geometry qw(scale unscale scaled_epsilon);
use Slic3r::Geometry::Clipper qw(intersection_pl);
sub horizontal_lines { 0 }
sub fill_surface {
my $self = shift;
my ($surface, %params) = @_;
# rotate polygons so that we can work with vertical lines here
my $expolygon = $surface->expolygon->clone;
my $rotate_vector = $self->infill_direction($surface);
$self->rotate_points($expolygon, $rotate_vector);
$self->_min_spacing(scale $self->spacing);
$self->_line_spacing($self->_min_spacing / $params{density});
$self->_diagonal_distance($self->_line_spacing * 2);
$self->_line_oscillation($self->_line_spacing - $self->_min_spacing); # only for Line infill
my $bounding_box = $expolygon->bounding_box;
# define flow spacing according to requested density
if ($params{density} == 1 && !$params{dont_adjust}) {
my $old_spacing = $self->spacing;
$self->_line_spacing($self->adjust_solid_spacing(
width => $bounding_box->size->x,
distance => $self->_line_spacing,
));
$self->spacing(unscale $self->_line_spacing);
if (abs($old_spacing - $self->spacing) > 0.3 * $old_spacing) {
print "Infill2: Extreme spacing adjustment, from: ", $old_spacing, " to: ", $self->spacing, "\n";
}
} else {
# extend bounding box so that our pattern will be aligned with other layers
$bounding_box->merge_point(Slic3r::Point->new(
$bounding_box->x_min - ($bounding_box->x_min % $self->_line_spacing),
$bounding_box->y_min - ($bounding_box->y_min % $self->_line_spacing),
));
}
# generate the basic pattern
my $x_max = $bounding_box->x_max + scaled_epsilon;
my @lines = ();
for (my $x = $bounding_box->x_min; $x <= $x_max; $x += $self->_line_spacing) {
push @lines, $self->_line($#lines, $x, $bounding_box->y_min, $bounding_box->y_max);
}
if ($self->horizontal_lines) {
my $y_max = $bounding_box->y_max + scaled_epsilon;
for (my $y = $bounding_box->y_min; $y <= $y_max; $y += $self->_line_spacing) {
push @lines, Slic3r::Polyline->new(
[$bounding_box->x_min, $y],
[$bounding_box->x_max, $y],
);
}
}
# clip paths against a slightly larger expolygon, so that the first and last paths
# are kept even if the expolygon has vertical sides
# the minimum offset for preventing edge lines from being clipped is scaled_epsilon;
# however we use a larger offset to support expolygons with slightly skewed sides and
# not perfectly straight
my @polylines = @{intersection_pl(\@lines, $expolygon->offset(+scale 0.02))};
my $extra = $self->_min_spacing * &Slic3r::INFILL_OVERLAP_OVER_SPACING;
foreach my $polyline (@polylines) {
my ($first_point, $last_point) = @$polyline[0,-1];
if ($first_point->y > $last_point->y) { #>
($first_point, $last_point) = ($last_point, $first_point);
}
$first_point->set_y($first_point->y - $extra); #--
$last_point->set_y($last_point->y + $extra); #++
}
# connect lines
unless ($params{dont_connect} || !@polylines) { # prevent calling leftmost_point() on empty collections
# offset the expolygon by max(min_spacing/2, extra)
my ($expolygon_off) = @{$expolygon->offset_ex($self->_min_spacing/2)};
my $collection = Slic3r::Polyline::Collection->new(@polylines);
@polylines = ();
foreach my $polyline (@{$collection->chained_path_from($collection->leftmost_point, 0)}) {
if (@polylines) {
my $first_point = $polyline->first_point;
my $last_point = $polylines[-1]->last_point;
my @distance = map abs($first_point->$_ - $last_point->$_), qw(x y);
# TODO: we should also check that both points are on a fill_boundary to avoid
# connecting paths on the boundaries of internal regions
if ($self->_can_connect(@distance) && $expolygon_off->contains_line(Slic3r::Line->new($last_point, $first_point))) {
$polylines[-1]->append_polyline($polyline);
next;
}
}
# make a clone before $collection goes out of scope
push @polylines, $polyline->clone;
}
}
# paths must be rotated back
$self->rotate_points_back(\@polylines, $rotate_vector);
return @polylines;
}
sub _line {
my ($self, $i, $x, $y_min, $y_max) = @_;
return Slic3r::Polyline->new(
[$x, $y_min],
[$x, $y_max],
);
}
sub _can_connect {
my ($self, $dist_X, $dist_Y) = @_;
return $dist_X <= $self->_diagonal_distance
&& $dist_Y <= $self->_diagonal_distance;
}
package Slic3r::Fill::Line;
use Moo;
extends 'Slic3r::Fill::Rectilinear';
use Slic3r::Geometry qw(scaled_epsilon);
sub _line {
my ($self, $i, $x, $y_min, $y_max) = @_;
if ($i % 2) {
return Slic3r::Polyline->new(
[$x - $self->_line_oscillation, $y_min],
[$x + $self->_line_oscillation, $y_max],
);
} else {
return Slic3r::Polyline->new(
[$x, $y_min],
[$x, $y_max],
);
}
}
sub _can_connect {
my ($self, $dist_X, $dist_Y) = @_;
my $TOLERANCE = 10 * scaled_epsilon;
return ($dist_X >= ($self->_line_spacing - $self->_line_oscillation) - $TOLERANCE)
&& ($dist_X <= ($self->_line_spacing + $self->_line_oscillation) + $TOLERANCE)
&& $dist_Y <= $self->_diagonal_distance;
}
package Slic3r::Fill::Grid;
use Moo;
extends 'Slic3r::Fill::Rectilinear';
sub angles () { [0] }
sub horizontal_lines { 1 }
1;

View File

@ -1,294 +0,0 @@
# This is derived from Fill.pm
# and it uses the C++ fillers.
package Slic3r::Fill2;
use Moo;
use List::Util qw(max);
use Slic3r::ExtrusionPath ':roles';
use Slic3r::Flow ':roles';
use Slic3r::Geometry qw(X Y PI scale chained_path deg2rad);
use Slic3r::Geometry::Clipper qw(union union_ex diff diff_ex intersection_ex offset offset2);
use Slic3r::Surface ':types';
has 'bounding_box' => (is => 'ro', required => 0);
has 'fillers' => (is => 'rw', default => sub { {} });
sub filler {
my $self = shift;
my ($filler) = @_;
if (!ref $self) {
return Slic3r::Filler->new_from_type($filler);
}
#print "Filler: ", $filler, "\n";
$self->fillers->{$filler} ||= Slic3r::Filler->new_from_type($filler);
$self->fillers->{$filler}->set_bounding_box($self->bounding_box);
return $self->fillers->{$filler};
}
# Generate infills for Slic3r::Layer::Region.
# The Slic3r::Layer::Region at this point of time may contain
# surfaces of various types (internal/bridge/top/bottom/solid).
# The infills are generated on the groups of surfaces with a compatible type.
# Returns an array of Slic3r::ExtrusionPath::Collection objects containing the infills generaed now
# and the thin fills generated by generate_perimeters().
sub make_fill {
my $self = shift;
# of type - C++: LayerRegion, Perl: Slic3r::Layer::Region
my ($layerm) = @_;
Slic3r::debugf "Filling layer %d:\n", $layerm->layer->id;
my $fill_density = $layerm->region->config->fill_density;
my $infill_flow = $layerm->flow(FLOW_ROLE_INFILL);
my $solid_infill_flow = $layerm->flow(FLOW_ROLE_SOLID_INFILL);
my $top_solid_infill_flow = $layerm->flow(FLOW_ROLE_TOP_SOLID_INFILL);
# Surfaces are of the type Slic3r::Surface
my @surfaces = ();
# merge adjacent surfaces
# in case of bridge surfaces, the ones with defined angle will be attached to the ones
# without any angle (shouldn't this logic be moved to process_external_surfaces()?)
{
my @surfaces_with_bridge_angle = grep { $_->bridge_angle >= 0 } @{$layerm->fill_surfaces};
# group surfaces by distinct properties
# group is of type Slic3r::SurfaceCollection
my @groups = @{$layerm->fill_surfaces->group};
# merge compatible groups (we can generate continuous infill for them)
{
# cache flow widths and patterns used for all solid groups
# (we'll use them for comparing compatible groups)
my @is_solid = my @fw = my @pattern = ();
for (my $i = 0; $i <= $#groups; $i++) {
# we can only merge solid non-bridge surfaces, so discard
# non-solid surfaces
if ($groups[$i][0]->is_solid && (!$groups[$i][0]->is_bridge || $layerm->layer->id == 0)) {
$is_solid[$i] = 1;
$fw[$i] = ($groups[$i][0]->surface_type == S_TYPE_TOP)
? $top_solid_infill_flow->width
: $solid_infill_flow->width;
$pattern[$i] = $groups[$i][0]->is_external
? $layerm->region->config->external_fill_pattern
: 'rectilinear';
} else {
$is_solid[$i] = 0;
$fw[$i] = 0;
$pattern[$i] = 'none';
}
}
# loop through solid groups
for (my $i = 0; $i <= $#groups; $i++) {
next if !$is_solid[$i];
# find compatible groups and append them to this one
for (my $j = $i+1; $j <= $#groups; $j++) {
next if !$is_solid[$j];
if ($fw[$i] == $fw[$j] && $pattern[$i] eq $pattern[$j]) {
# groups are compatible, merge them
push @{$groups[$i]}, @{$groups[$j]};
splice @groups, $j, 1;
splice @is_solid, $j, 1;
splice @fw, $j, 1;
splice @pattern, $j, 1;
}
}
}
}
# give priority to bridges
@groups = sort { ($a->[0]->bridge_angle >= 0) ? -1 : 0 } @groups;
foreach my $group (@groups) {
# Make a union of polygons defining the infiill regions of a group, use a safety offset.
my $union_p = union([ map $_->p, @$group ], 1);
# Subtract surfaces having a defined bridge_angle from any other, use a safety offset.
if (@surfaces_with_bridge_angle && $group->[0]->bridge_angle < 0) {
$union_p = diff(
$union_p,
[ map $_->p, @surfaces_with_bridge_angle ],
1,
);
}
# subtract any other surface already processed
#FIXME Vojtech: Because the bridge surfaces came first, they are subtracted twice!
my $union = diff_ex(
$union_p,
[ map $_->p, @surfaces ],
1,
);
push @surfaces, map $group->[0]->clone(expolygon => $_), @$union;
}
}
# we need to detect any narrow surfaces that might collapse
# when adding spacing below
# such narrow surfaces are often generated in sloping walls
# by bridge_over_infill() and combine_infill() as a result of the
# subtraction of the combinable area from the layer infill area,
# which leaves small areas near the perimeters
# we are going to grow such regions by overlapping them with the void (if any)
# TODO: detect and investigate whether there could be narrow regions without
# any void neighbors
{
my $distance_between_surfaces = max(
$infill_flow->scaled_spacing,
$solid_infill_flow->scaled_spacing,
$top_solid_infill_flow->scaled_spacing,
);
my $collapsed = diff(
[ map @{$_->expolygon}, @surfaces ],
offset2([ map @{$_->expolygon}, @surfaces ], -$distance_between_surfaces/2, +$distance_between_surfaces/2),
1,
);
push @surfaces, map Slic3r::Surface->new(
expolygon => $_,
surface_type => S_TYPE_INTERNALSOLID,
), @{intersection_ex(
offset($collapsed, $distance_between_surfaces),
[
(map @{$_->expolygon}, grep $_->surface_type == S_TYPE_INTERNALVOID, @surfaces),
(@$collapsed),
],
1,
)};
}
if (0) {
require "Slic3r/SVG.pm";
Slic3r::SVG::output("fill_" . $layerm->print_z . ".svg",
expolygons => [ map $_->expolygon, grep !$_->is_solid, @surfaces ],
red_expolygons => [ map $_->expolygon, grep $_->is_solid, @surfaces ],
);
}
# Fills are of perl type Slic3r::ExtrusionPath::Collection, c++ type ExtrusionEntityCollection
my @fills = ();
SURFACE: foreach my $surface (@surfaces) {
next if $surface->surface_type == S_TYPE_INTERNALVOID;
my $filler = $layerm->region->config->fill_pattern;
my $density = $fill_density;
my $role = ($surface->surface_type == S_TYPE_TOP) ? FLOW_ROLE_TOP_SOLID_INFILL
: $surface->is_solid ? FLOW_ROLE_SOLID_INFILL
: FLOW_ROLE_INFILL;
my $is_bridge = $layerm->layer->id > 0 && $surface->is_bridge;
my $is_solid = $surface->is_solid;
if ($surface->is_solid) {
$density = 100;
$filler = 'rectilinear';
if ($surface->is_external && !$is_bridge) {
$filler = $layerm->region->config->external_fill_pattern;
}
} else {
next SURFACE unless $density > 0;
}
# get filler object
my $f = $self->filler($filler);
# calculate the actual flow we'll be using for this infill
my $h = $surface->thickness == -1 ? $layerm->layer->height : $surface->thickness;
my $flow = $layerm->region->flow(
$role,
$h,
$is_bridge || $f->use_bridge_flow,
$layerm->layer->id == 0,
-1,
$layerm->layer->object,
);
# calculate flow spacing for infill pattern generation
my $using_internal_flow = 0;
if (!$is_solid && !$is_bridge) {
# it's internal infill, so we can calculate a generic flow spacing
# for all layers, for avoiding the ugly effect of
# misaligned infill on first layer because of different extrusion width and
# layer height
my $internal_flow = $layerm->region->flow(
FLOW_ROLE_INFILL,
$layerm->layer->object->config->layer_height, # TODO: handle infill_every_layers?
0, # no bridge
0, # no first layer
-1, # auto width
$layerm->layer->object,
);
$f->set_spacing($internal_flow->spacing);
$using_internal_flow = 1;
} else {
$f->set_spacing($flow->spacing);
}
$f->set_layer_id($layerm->layer->id);
$f->set_z($layerm->layer->print_z);
$f->set_angle(deg2rad($layerm->region->config->fill_angle));
$f->set_loop_clipping(scale($flow->nozzle_diameter) * &Slic3r::LOOP_CLIPPING_LENGTH_OVER_NOZZLE_DIAMETER);
# apply half spacing using this flow's own spacing and generate infill
my @polylines = $f->fill_surface(
$surface,
density => $density/100,
layer_height => $h,
);
next unless @polylines;
# calculate actual flow from spacing (which might have been adjusted by the infill
# pattern generator)
if ($using_internal_flow) {
# if we used the internal flow we're not doing a solid infill
# so we can safely ignore the slight variation that might have
# been applied to $f->flow_spacing
} else {
$flow = Slic3r::Flow->new_from_spacing(
spacing => $f->spacing,
nozzle_diameter => $flow->nozzle_diameter,
layer_height => $h,
bridge => $is_bridge || $f->use_bridge_flow,
);
}
# save into layer
{
my $role = $is_bridge ? EXTR_ROLE_BRIDGE
: $is_solid ? (($surface->surface_type == S_TYPE_TOP) ? EXTR_ROLE_TOPSOLIDFILL : EXTR_ROLE_SOLIDFILL)
: EXTR_ROLE_FILL;
push @fills, my $collection = Slic3r::ExtrusionPath::Collection->new;
# Only concentric fills are not sorted.
$collection->no_sort($f->no_sort);
$collection->append(
map Slic3r::ExtrusionPath->new(
polyline => $_,
role => $role,
mm3_per_mm => $flow->mm3_per_mm,
width => $flow->width,
height => $flow->height,
), map @$_, @polylines,
);
}
}
# add thin fill regions
# thin_fills are of C++ Slic3r::ExtrusionEntityCollection, perl type Slic3r::ExtrusionPath::Collection
# Unpacks the collection, creates multiple collections per path.
# The path type could be ExtrusionPath, ExtrusionLoop or ExtrusionEntityCollection.
# Why the paths are unpacked?
foreach my $thin_fill (@{$layerm->thin_fills}) {
push @fills, Slic3r::ExtrusionPath::Collection->new($thin_fill);
}
return @fills;
}
1;

View File

@ -31,17 +31,6 @@ sub regions {
return [ map $self->get_region($_), 0..($self->region_count-1) ]; return [ map $self->get_region($_), 0..($self->region_count-1) ];
} }
sub make_fill {
my ($self) = @_;
foreach my $layerm (@{$self->regions}) {
$layerm->fills->clear;
# Fearlessly enable the C++ fillers.
$layerm->fills->append($_) for $self->object->fill_maker2->make_fill($layerm);
# $layerm->fills->append($_) for $self->object->fill_maker->make_fill($layerm);
}
}
package Slic3r::Layer::Support; package Slic3r::Layer::Support;
our @ISA = qw(Slic3r::Layer); our @ISA = qw(Slic3r::Layer);

View File

@ -544,8 +544,8 @@ sub process_layer {
} }
# process infill # process infill
# $layerm->fills is a collection of ExtrusionPath::Collection objects, each one containing # $layerm->fills is a collection of Slic3r::ExtrusionPath::Collection objects (C++ class ExtrusionEntityCollection),
# the ExtrusionPath objects of a certain infill "group" (also called "surface" # each one containing the ExtrusionPath objects of a certain infill "group" (also called "surface"
# throughout the code). We can redefine the order of such Collections but we have to # throughout the code). We can redefine the order of such Collections but we have to
# do each one completely at once. # do each one completely at once.
foreach my $fill (@{$layerm->fills}) { foreach my $fill (@{$layerm->fills}) {

View File

@ -14,19 +14,6 @@ use Slic3r::Surface ':types';
# If enabled, phases of prepare_infill will be written into SVG files to an "out" directory. # If enabled, phases of prepare_infill will be written into SVG files to an "out" directory.
our $SLIC3R_DEBUG_SLICE_PROCESSING = 0; our $SLIC3R_DEBUG_SLICE_PROCESSING = 0;
# TODO: lazy
sub fill_maker {
my $self = shift;
return Slic3r::Fill->new(bounding_box => $self->bounding_box);
}
# Vojtech's implementation: Create the C++ filler.
# TODO: lazy
sub fill_maker2 {
my $self = shift;
return Slic3r::Fill2->new(bounding_box => $self->bounding_box);
}
sub region_volumes { sub region_volumes {
my $self = shift; my $self = shift;
return [ map $self->get_region_volumes($_), 0..($self->region_count - 1) ]; return [ map $self->get_region_volumes($_), 0..($self->region_count - 1) ];
@ -617,12 +604,12 @@ sub infill {
thread_cb => sub { thread_cb => sub {
my $q = shift; my $q = shift;
while (defined (my $i = $q->dequeue)) { while (defined (my $i = $q->dequeue)) {
$self->get_layer($i)->make_fill; $self->get_layer($i)->make_fills;
} }
}, },
no_threads_cb => sub { no_threads_cb => sub {
foreach my $layer (@{$self->layers}) { foreach my $layer (@{$self->layers}) {
$layer->make_fill; $layer->make_fills;
} }
}, },
); );
@ -678,14 +665,7 @@ sub _support_material {
); );
} else { } else {
# New supports, C++ implementation. # New supports, C++ implementation.
return Slic3r::Print::SupportMaterial2->new( return Slic3r::Print::SupportMaterial2->new($self);
print_config => $self->print->config,
object_config => $self->config,
first_layer_flow => $first_layer_flow,
flow => $self->support_material_flow,
interface_flow => $self->support_material_flow(FLOW_ROLE_SUPPORT_MATERIAL_INTERFACE),
soluble_interface => ($self->config->support_material_contact_distance == 0),
);
} }
} }

View File

@ -761,10 +761,13 @@ sub generate_toolpaths {
# Allocate the fillers exclusively in the worker threads! Don't allocate them at the main thread, # Allocate the fillers exclusively in the worker threads! Don't allocate them at the main thread,
# as Perl copies the C++ pointers by default, so then the C++ objects are shared between threads! # as Perl copies the C++ pointers by default, so then the C++ objects are shared between threads!
my %fillers = ( my %fillers = (
interface => $object->fill_maker2->filler('rectilinear'), interface => Slic3r::Filler->new_from_type('rectilinear'),
support => $object->fill_maker2->filler($pattern), support => Slic3r::Filler->new_from_type($pattern),
); );
my $bounding_box = $object->bounding_box;
$fillers{interface}->set_bounding_box($object->bounding_box);
$fillers{support}->set_bounding_box($object->bounding_box);
# interface and contact infill # interface and contact infill
if (@$interface || @$contact_infill) { if (@$interface || @$contact_infill) {
$fillers{interface}->set_angle($interface_angle); $fillers{interface}->set_angle($interface_angle);

View File

@ -18,27 +18,11 @@ use Slic3r::Test;
sub scale_points (@) { map [scale $_->[X], scale $_->[Y]], @_ } sub scale_points (@) { map [scale $_->[X], scale $_->[Y]], @_ }
{
my $print = Slic3r::Print->new;
my $filler = Slic3r::Fill::Rectilinear->new(
print => $print,
bounding_box => Slic3r::Geometry::BoundingBox->new_from_points([ Slic3r::Point->new(0, 0), Slic3r::Point->new(10, 10) ]),
);
my $surface_width = 250;
my $distance = $filler->adjust_solid_spacing(
width => $surface_width,
distance => 100,
);
is $distance, 125, 'adjusted solid distance';
is $surface_width % $distance, 0, 'adjusted solid distance';
}
{ {
my $expolygon = Slic3r::ExPolygon->new([ scale_points [0,0], [50,0], [50,50], [0,50] ]); my $expolygon = Slic3r::ExPolygon->new([ scale_points [0,0], [50,0], [50,50], [0,50] ]);
my $filler = Slic3r::Fill::Rectilinear->new( my $filler = Slic3r::Filler->new_from_type('rectilinear');
bounding_box => $expolygon->bounding_box, $filler->set_bounding_box($expolygon->bounding_box);
angle => 0, $filler->set_angle(0);
);
my $surface = Slic3r::Surface->new( my $surface = Slic3r::Surface->new(
surface_type => S_TYPE_TOP, surface_type => S_TYPE_TOP,
expolygon => $expolygon, expolygon => $expolygon,
@ -48,11 +32,11 @@ sub scale_points (@) { map [scale $_->[X], scale $_->[Y]], @_ }
height => 0.4, height => 0.4,
nozzle_diameter => 0.50, nozzle_diameter => 0.50,
); );
$filler->spacing($flow->spacing); $filler->set_spacing($flow->spacing);
foreach my $angle (0, 45) { foreach my $angle (0, 45) {
$surface->expolygon->rotate(Slic3r::Geometry::deg2rad($angle), [0,0]); $surface->expolygon->rotate(Slic3r::Geometry::deg2rad($angle), [0,0]);
my @paths = $filler->fill_surface($surface, layer_height => 0.4, density => 0.4); my $paths = $filler->fill_surface($surface, layer_height => 0.4, density => 0.4);
is scalar @paths, 1, 'one continuous path'; is scalar @$paths, 1, 'one continuous path';
} }
} }
@ -60,10 +44,12 @@ sub scale_points (@) { map [scale $_->[X], scale $_->[Y]], @_ }
my $test = sub { my $test = sub {
my ($expolygon, $flow_spacing, $angle, $density) = @_; my ($expolygon, $flow_spacing, $angle, $density) = @_;
my $filler = Slic3r::Fill::Rectilinear->new( my $filler = Slic3r::Filler->new_from_type('rectilinear');
bounding_box => $expolygon->bounding_box, $filler->set_bounding_box($expolygon->bounding_box);
angle => $angle // 0, $filler->set_angle($angle // 0);
); # Adjust line spacing to fill the region.
$filler->set_dont_adjust(0);
$filler->set_link_max_length(scale(1.2*$flow_spacing));
my $surface = Slic3r::Surface->new( my $surface = Slic3r::Surface->new(
surface_type => S_TYPE_BOTTOM, surface_type => S_TYPE_BOTTOM,
expolygon => $expolygon, expolygon => $expolygon,
@ -73,28 +59,30 @@ sub scale_points (@) { map [scale $_->[X], scale $_->[Y]], @_ }
height => 0.4, height => 0.4,
nozzle_diameter => $flow_spacing, nozzle_diameter => $flow_spacing,
); );
$filler->spacing($flow->spacing); $filler->set_spacing($flow->spacing);
my @paths = $filler->fill_surface( my $paths = $filler->fill_surface(
$surface, $surface,
layer_height => $flow->height, layer_height => $flow->height,
density => $density // 1, density => $density // 1,
); );
# check whether any part was left uncovered # check whether any part was left uncovered
my @grown_paths = map @{Slic3r::Polyline->new(@$_)->grow(scale $filler->spacing/2)}, @paths; my @grown_paths = map @{Slic3r::Polyline->new(@$_)->grow(scale $filler->spacing/2)}, @$paths;
my $uncovered = diff_ex([ @$expolygon ], [ @grown_paths ], 1); my $uncovered = diff_ex([ @$expolygon ], [ @grown_paths ], 1);
# ignore very small dots # ignore very small dots
@$uncovered = grep $_->area > (scale $flow_spacing)**2, @$uncovered; my $uncovered_filtered = [ grep $_->area > (scale $flow_spacing)**2, @$uncovered ];
is scalar(@$uncovered_filtered), 0, 'solid surface is fully filled';
is scalar(@$uncovered), 0, 'solid surface is fully filled'; if (0 && @$uncovered_filtered) {
if (0 && @$uncovered) {
require "Slic3r/SVG.pm"; require "Slic3r/SVG.pm";
Slic3r::SVG::output( Slic3r::SVG::output("uncovered.svg",
"uncovered.svg", no_arrows => 1,
expolygons => [$expolygon], expolygons => [ $expolygon ],
red_expolygons => $uncovered, blue_expolygons => [ @$uncovered ],
red_expolygons => [ @$uncovered_filtered ],
polylines => [ @$paths ],
); );
exit; exit;
} }

View File

@ -187,7 +187,7 @@ if ($ENV{SLIC3R_DEBUG}) {
if ($cpp_guess->is_gcc) { if ($cpp_guess->is_gcc) {
# check whether we're dealing with a buggy GCC version # check whether we're dealing with a buggy GCC version
# see https://github.com/alexrj/Slic3r/issues/1965 # see https://github.com/alexrj/Slic3r/issues/1965
if (`cc --version` =~ / 4\.7\.[012]/) { if (`cc --version` =~ m/ 4\.7\.[012]/) {
# Workaround suggested by Boost devs: # Workaround suggested by Boost devs:
# https://svn.boost.org/trac/boost/ticket/8695 # https://svn.boost.org/trac/boost/ticket/8695
push @cflags, qw(-fno-inline-small-functions); push @cflags, qw(-fno-inline-small-functions);

View File

@ -38,7 +38,7 @@ BridgeDetector::BridgeDetector(const ExPolygon &_expolygon, const ExPolygonColle
intersection(grown, this->lower_slices.contours(), &this->_edges); intersection(grown, this->lower_slices.contours(), &this->_edges);
#ifdef SLIC3R_DEBUG #ifdef SLIC3R_DEBUG
printf(" bridge has %zu support(s)\n", this->_edges.size()); printf(" bridge has " PRINTF_ZU " support(s)\n", this->_edges.size());
#endif #endif
// detect anchors as intersection between our bridge expolygon and the lower slices // detect anchors as intersection between our bridge expolygon and the lower slices

View File

@ -456,7 +456,7 @@ ExPolygon::triangulate_pp(Polygons* polygons) const
{ {
TPPLPoly p; TPPLPoly p;
p.Init(ex->contour.points.size()); p.Init(ex->contour.points.size());
//printf("%zu\n0\n", ex->contour.points.size()); //printf(PRINTF_ZU "\n0\n", ex->contour.points.size());
for (Points::const_iterator point = ex->contour.points.begin(); point != ex->contour.points.end(); ++point) { for (Points::const_iterator point = ex->contour.points.begin(); point != ex->contour.points.end(); ++point) {
p[ point-ex->contour.points.begin() ].x = point->x; p[ point-ex->contour.points.begin() ].x = point->x;
p[ point-ex->contour.points.begin() ].y = point->y; p[ point-ex->contour.points.begin() ].y = point->y;
@ -470,7 +470,7 @@ ExPolygon::triangulate_pp(Polygons* polygons) const
for (Polygons::const_iterator hole = ex->holes.begin(); hole != ex->holes.end(); ++hole) { for (Polygons::const_iterator hole = ex->holes.begin(); hole != ex->holes.end(); ++hole) {
TPPLPoly p; TPPLPoly p;
p.Init(hole->points.size()); p.Init(hole->points.size());
//printf("%zu\n1\n", hole->points.size()); //printf(PRINTF_ZU "\n1\n", hole->points.size());
for (Points::const_iterator point = hole->points.begin(); point != hole->points.end(); ++point) { for (Points::const_iterator point = hole->points.begin(); point != hole->points.end(); ++point) {
p[ point-hole->points.begin() ].x = point->x; p[ point-hole->points.begin() ].x = point->x;
p[ point-hole->points.begin() ].y = point->y; p[ point-hole->points.begin() ].y = point->y;

View File

@ -69,7 +69,7 @@ inline Polygons to_polygons(const ExPolygons &src)
return polygons; return polygons;
} }
#if SLIC3R_CPPVER > 11 #if SLIC3R_CPPVER >= 11
inline Polygons to_polygons(ExPolygons &&src) inline Polygons to_polygons(ExPolygons &&src)
{ {
Polygons polygons; Polygons polygons;
@ -83,6 +83,37 @@ inline Polygons to_polygons(ExPolygons &&src)
} }
#endif #endif
// Count a nuber of polygons stored inside the vector of expolygons.
// Useful for allocating space for polygons when converting expolygons to polygons.
inline size_t number_polygons(const ExPolygons &expolys)
{
size_t n_polygons = 0;
for (ExPolygons::const_iterator it = expolys.begin(); it != expolys.end(); ++ it)
n_polygons += it->holes.size() + 1;
return n_polygons;
}
// Append a vector of ExPolygons at the end of another vector of polygons.
inline void polygons_append(Polygons &dst, const ExPolygons &src)
{
dst.reserve(dst.size() + number_polygons(src));
for (ExPolygons::const_iterator it = src.begin(); it != src.end(); ++ it) {
dst.push_back(it->contour);
dst.insert(dst.end(), it->holes.begin(), it->holes.end());
}
}
#if SLIC3R_CPPVER >= 11
inline void polygons_append(Polygons &dst, ExPolygons &&src)
{
dst.reserve(dst.size() + number_polygons(src));
for (ExPolygons::const_iterator it = expolys.begin(); it != expolys.end(); ++ it) {
dst.push_back(std::move(it->contour));
std::move(std::begin(it->contour), std::end(it->contour), std::back_inserter(dst));
}
}
#endif
extern BoundingBox get_extents(const ExPolygon &expolygon); extern BoundingBox get_extents(const ExPolygon &expolygon);
extern BoundingBox get_extents(const ExPolygons &expolygons); extern BoundingBox get_extents(const ExPolygons &expolygons);

View File

@ -19,8 +19,11 @@ ExtrusionEntityCollection::ExtrusionEntityCollection(const ExtrusionPaths &paths
ExtrusionEntityCollection& ExtrusionEntityCollection::operator= (const ExtrusionEntityCollection &other) ExtrusionEntityCollection& ExtrusionEntityCollection::operator= (const ExtrusionEntityCollection &other)
{ {
ExtrusionEntityCollection tmp(other); this->entities = other.entities;
this->swap(tmp); for (size_t i = 0; i < this->entities.size(); ++i)
this->entities[i] = this->entities[i]->clone();
this->orig_indices = other.orig_indices;
this->no_sort = other.no_sort;
return *this; return *this;
} }
@ -32,10 +35,11 @@ ExtrusionEntityCollection::swap (ExtrusionEntityCollection &c)
std::swap(this->no_sort, c.no_sort); std::swap(this->no_sort, c.no_sort);
} }
ExtrusionEntityCollection::~ExtrusionEntityCollection() void ExtrusionEntityCollection::clear()
{ {
for (ExtrusionEntitiesPtr::iterator it = this->entities.begin(); it != this->entities.end(); ++it) for (size_t i = 0; i < this->entities.size(); ++i)
delete *it; delete this->entities[i];
this->entities.clear();
} }
ExtrusionEntityCollection::operator ExtrusionPaths() const ExtrusionEntityCollection::operator ExtrusionPaths() const
@ -52,9 +56,8 @@ ExtrusionEntityCollection*
ExtrusionEntityCollection::clone() const ExtrusionEntityCollection::clone() const
{ {
ExtrusionEntityCollection* coll = new ExtrusionEntityCollection(*this); ExtrusionEntityCollection* coll = new ExtrusionEntityCollection(*this);
for (size_t i = 0; i < coll->entities.size(); ++i) { for (size_t i = 0; i < coll->entities.size(); ++i)
coll->entities[i] = this->entities[i]->clone(); coll->entities[i] = this->entities[i]->clone();
}
return coll; return coll;
} }

View File

@ -17,7 +17,7 @@ class ExtrusionEntityCollection : public ExtrusionEntity
ExtrusionEntityCollection(const ExtrusionEntityCollection &collection); ExtrusionEntityCollection(const ExtrusionEntityCollection &collection);
ExtrusionEntityCollection(const ExtrusionPaths &paths); ExtrusionEntityCollection(const ExtrusionPaths &paths);
ExtrusionEntityCollection& operator= (const ExtrusionEntityCollection &other); ExtrusionEntityCollection& operator= (const ExtrusionEntityCollection &other);
~ExtrusionEntityCollection(); ~ExtrusionEntityCollection() { clear(); }
operator ExtrusionPaths() const; operator ExtrusionPaths() const;
bool is_collection() const { bool is_collection() const {
@ -29,9 +29,7 @@ class ExtrusionEntityCollection : public ExtrusionEntity
bool empty() const { bool empty() const {
return this->entities.empty(); return this->entities.empty();
}; };
void clear() { void clear();
this->entities.clear();
};
void swap (ExtrusionEntityCollection &c); void swap (ExtrusionEntityCollection &c);
void append(const ExtrusionEntity &entity); void append(const ExtrusionEntity &entity);
void append(const ExtrusionEntitiesPtr &entities); void append(const ExtrusionEntitiesPtr &entities);

View File

@ -1,14 +1,17 @@
#include <assert.h>
#include <stdio.h> #include <stdio.h>
#include "../ClipperUtils.hpp" #include "../ClipperUtils.hpp"
#include "../Surface.hpp" #include "../Geometry.hpp"
#include "../Layer.hpp"
#include "../Print.hpp"
#include "../PrintConfig.hpp" #include "../PrintConfig.hpp"
#include "../Surface.hpp"
#include "FillBase.hpp" #include "FillBase.hpp"
namespace Slic3r { namespace Slic3r {
#if 0
// Generate infills for Slic3r::Layer::Region. // Generate infills for Slic3r::Layer::Region.
// The Slic3r::Layer::Region at this point of time may contain // The Slic3r::Layer::Region at this point of time may contain
// surfaces of various types (internal/bridge/top/bottom/solid). // surfaces of various types (internal/bridge/top/bottom/solid).
@ -31,8 +34,8 @@ void make_fill(LayerRegion &layerm, ExtrusionEntityCollection &out)
// without any angle (shouldn't this logic be moved to process_external_surfaces()?) // without any angle (shouldn't this logic be moved to process_external_surfaces()?)
{ {
SurfacesPtr surfaces_with_bridge_angle; SurfacesPtr surfaces_with_bridge_angle;
surfaces_with_bridge_angle.reserve(layerm->fill_surfaces.surfaces.size()); surfaces_with_bridge_angle.reserve(layerm.fill_surfaces.surfaces.size());
for (Surfaces::iterator it = layerm->fill_surfaces.surfaces.begin(); it != layerm->fill_surfaces.surfaces.end(); ++ it) for (Surfaces::iterator it = layerm.fill_surfaces.surfaces.begin(); it != layerm.fill_surfaces.surfaces.end(); ++ it)
if (it->bridge_angle >= 0) if (it->bridge_angle >= 0)
surfaces_with_bridge_angle.push_back(&(*it)); surfaces_with_bridge_angle.push_back(&(*it));
@ -40,76 +43,61 @@ void make_fill(LayerRegion &layerm, ExtrusionEntityCollection &out)
// group is of type Slic3r::SurfaceCollection // group is of type Slic3r::SurfaceCollection
//FIXME: Use some smart heuristics to merge similar surfaces to eliminate tiny regions. //FIXME: Use some smart heuristics to merge similar surfaces to eliminate tiny regions.
std::vector<SurfacesPtr> groups; std::vector<SurfacesPtr> groups;
layerm->fill_surfaces.group(&groups); layerm.fill_surfaces.group(&groups);
// merge compatible groups (we can generate continuous infill for them) // merge compatible groups (we can generate continuous infill for them)
{ {
// cache flow widths and patterns used for all solid groups // cache flow widths and patterns used for all solid groups
// (we'll use them for comparing compatible groups) // (we'll use them for comparing compatible groups)
my @is_solid = my @fw = my @pattern = (); std::vector<char> is_solid(groups.size(), false);
for (my $i = 0; $i <= $num_ groups; $i++) { std::vector<float> fw(groups.size(), 0.f);
std::vector<int> pattern(groups.size(), -1);
for (size_t i = 0; i < groups.size(); ++ i) {
// we can only merge solid non-bridge surfaces, so discard // we can only merge solid non-bridge surfaces, so discard
// non-solid surfaces // non-solid surfaces
if ($groups[$i][0]->is_solid && (!$groups[$i][0]->is_bridge || $layerm->layer->id == 0)) { const Surface &surface = *groups[i].front();
$is_solid[$i] = 1; if (surface.is_solid() && (!surface.is_bridge() || layerm.layer()->id() == 0)) {
$fw[$i] = ($groups[$i][0]->surface_type == S_TYPE_TOP) is_solid[i] = true;
? $top_solid_infill_flow->width fw[i] = (surface.surface_type == stTop) ? top_solid_infill_flow.width : solid_infill_flow.width;
: $solid_infill_flow->width; pattern[i] = surface.is_external() ? layerm.region()->config.external_fill_pattern.value : ipRectilinear;
$pattern[$i] = $groups[$i][0]->is_external
? $layerm->region->config->external_fill_pattern
: 'rectilinear';
} else {
$is_solid[$i] = 0;
$fw[$i] = 0;
$pattern[$i] = 'none';
} }
} }
// loop through solid groups // loop through solid groups
for (my $i = 0; $i <= $num_groups; $i++) { for (size_t i = 0; i < groups.size(); ++ i) {
next if !$is_solid[$i]; if (is_solid[i]) {
// find compatible groups and append them to this one
// find compatible groups and append them to this one for (size_t j = i + 1; j < groups.size(); ++ j) {
for (my $j = $i+1; $j <= $num_groups; $j++) { if (is_solid[j] && fw[i] == fw[j] && pattern[i] == pattern[j]) {
next if !$is_solid[$j]; // groups are compatible, merge them
groups[i].insert(groups[i].end(), groups[j].begin(), groups[j].end());
if ($fw[$i] == $fw[$j] && $pattern[$i] eq $pattern[$j]) { groups.erase(groups.begin() + j);
// groups are compatible, merge them is_solid.erase(is_solid.begin() + j);
push @{$groups[$i]}, @{$groups[$j]}; fw.erase(fw.begin() + j);
splice @groups, $j, 1; pattern.erase(pattern.begin() + j);
splice @is_solid, $j, 1; }
splice @fw, $j, 1;
splice @pattern, $j, 1;
} }
} }
} }
} }
// give priority to bridges // Give priority to bridges. Process the bridges in the first round, the rest of the surfaces in the 2nd round.
@groups = sort { ($a->[0]->bridge_angle >= 0) ? -1 : 0 } @groups; for (size_t round = 0; round < 2; ++ round) {
for (std::vector<SurfacesPtr>::iterator it_group = groups.begin(); it_group != groups.end(); ++ it_group) {
foreach my $group (@groups) { const SurfacesPtr &group = *it_group;
// Make a union of polygons defining the infiill regions of a group, use a safety offset. bool is_bridge = group.front()->bridge_angle >= 0;
my $union_p = union([ map $_->p, @$group ], 1); if (is_bridge != (round == 0))
continue;
// Subtract surfaces having a defined bridge_angle from any other, use a safety offset. // Make a union of polygons defining the infiill regions of a group, use a safety offset.
if (@surfaces_with_bridge_angle && $group->[0]->bridge_angle < 0) { Polygons union_p = union_(to_polygons(*it_group), true);
$union_p = diff( // Subtract surfaces having a defined bridge_angle from any other, use a safety offset.
$union_p, if (! surfaces_with_bridge_angle.empty() && it_group->front()->bridge_angle < 0)
[ map $_->p, @surfaces_with_bridge_angle ], union_p = diff(union_p, to_polygons(surfaces_with_bridge_angle), true);
1, // subtract any other surface already processed
); //FIXME Vojtech: Because the bridge surfaces came first, they are subtracted twice!
ExPolygons union_expolys = diff_ex(union_p, to_polygons(surfaces), true);
for (ExPolygons::const_iterator it_expoly = union_expolys.begin(); it_expoly != union_expolys.end(); ++ it_expoly)
surfaces.push_back(Surface(*it_group->front(), *it_expoly));
} }
// subtract any other surface already processed
//FIXME Vojtech: Because the bridge surfaces came first, they are subtracted twice!
my $union = diff_ex(
$union_p,
[ map $_->p, @surfaces ],
1,
);
push @surfaces, map $group->[0]->clone(expolygon => $_), @$union;
} }
} }
@ -123,149 +111,140 @@ void make_fill(LayerRegion &layerm, ExtrusionEntityCollection &out)
// TODO: detect and investigate whether there could be narrow regions without // TODO: detect and investigate whether there could be narrow regions without
// any void neighbors // any void neighbors
{ {
my $distance_between_surfaces = max( coord_t distance_between_surfaces = std::max(
$infill_flow->scaled_spacing, std::max(infill_flow.scaled_spacing(), solid_infill_flow.scaled_spacing()),
$solid_infill_flow->scaled_spacing, top_solid_infill_flow.scaled_spacing());
$top_solid_infill_flow->scaled_spacing, Polygons surfaces_polygons = to_polygons(surfaces);
); Polygons collapsed = diff(
my $collapsed = diff( surfaces_polygons,
[ map @{$_->expolygon}, @surfaces ], offset2(surfaces_polygons, -distance_between_surfaces/2, +distance_between_surfaces/2),
offset2([ map @{$_->expolygon}, @surfaces ], -$distance_between_surfaces/2, +$distance_between_surfaces/2), true);
1, Polygons to_subtract;
); to_subtract.reserve(collapsed.size() + number_polygons(surfaces));
push @surfaces, map Slic3r::Surface->new( for (Surfaces::const_iterator it_surface = surfaces.begin(); it_surface != surfaces.end(); ++ it_surface)
expolygon => $_, if (it_surface->surface_type == stInternalVoid)
surface_type => S_TYPE_INTERNALSOLID, polygons_append(to_subtract, *it_surface);
), @{intersection_ex( polygons_append(to_subtract, collapsed);
offset($collapsed, $distance_between_surfaces), surfaces_append(
[ surfaces,
(map @{$_->expolygon}, grep $_->surface_type == S_TYPE_INTERNALVOID, @surfaces), intersection_ex(
(@$collapsed), offset(collapsed, distance_between_surfaces),
], to_subtract,
1, true),
)}; stInternalSolid);
} }
if (0) { if (0) {
require "Slic3r/SVG.pm"; // require "Slic3r/SVG.pm";
Slic3r::SVG::output("fill_" . $layerm->print_z . ".svg", // Slic3r::SVG::output("fill_" . $layerm->print_z . ".svg",
expolygons => [ map $_->expolygon, grep !$_->is_solid, @surfaces ], // expolygons => [ map $_->expolygon, grep !$_->is_solid, @surfaces ],
red_expolygons => [ map $_->expolygon, grep $_->is_solid, @surfaces ], // red_expolygons => [ map $_->expolygon, grep $_->is_solid, @surfaces ],
); // );
} }
SURFACE: foreach my $surface (@surfaces) { for (Surfaces::const_iterator surface_it = surfaces.begin(); surface_it != surfaces.end(); ++ surface_it) {
next if $surface->surface_type == S_TYPE_INTERNALVOID; const Surface &surface = *surface_it;
my $filler = $layerm->region->config->fill_pattern; if (surface.surface_type == stInternalVoid)
my $density = $fill_density; continue;
my $role = ($surface->surface_type == S_TYPE_TOP) ? FLOW_ROLE_TOP_SOLID_INFILL InfillPattern fill_pattern = layerm.region()->config.fill_pattern.value;
: $surface->is_solid ? FLOW_ROLE_SOLID_INFILL double density = fill_density;
: FLOW_ROLE_INFILL; FlowRole role = (surface.surface_type == stTop) ? frTopSolidInfill :
my $is_bridge = $layerm->layer->id > 0 && $surface->is_bridge; (surface.is_solid() ? frSolidInfill : frInfill);
my $is_solid = $surface->is_solid; bool is_bridge = layerm.layer()->id() > 0 && surface.is_bridge();
if ($surface->is_solid) { if (surface.is_solid()) {
$density = 100; density = 100;
$filler = 'rectilinear'; fill_pattern = (surface.is_external() && ! is_bridge) ?
if ($surface->is_external && !$is_bridge) { layerm.region()->config.external_fill_pattern.value :
$filler = $layerm->region->config->external_fill_pattern; ipRectilinear;
} } else if (density <= 0)
} else { continue;
next SURFACE unless $density > 0;
}
// get filler object // get filler object
my $f = $self->filler($filler); std::auto_ptr<Fill> f = std::auto_ptr<Fill>(Fill::new_from_type(fill_pattern));
f->set_bounding_box(layerm.layer()->object()->bounding_box());
// calculate the actual flow we'll be using for this infill // calculate the actual flow we'll be using for this infill
my $h = $surface->thickness == -1 ? $layerm->layer->height : $surface->thickness; coordf_t h = (surface.thickness == -1) ? layerm.layer()->height : surface.thickness;
my $flow = $layerm->region->flow( Flow flow = layerm.region()->flow(
$role, role,
$h, h,
$is_bridge || $f->use_bridge_flow, is_bridge || f->use_bridge_flow(), // bridge flow?
$layerm->layer->id == 0, layerm.layer()->id() == 0, // first layer?
-1, -1, // auto width
$layerm->layer->object, *layerm.layer()->object()
); );
// calculate flow spacing for infill pattern generation // calculate flow spacing for infill pattern generation
my $using_internal_flow = 0; bool using_internal_flow = false;
if (!$is_solid && !$is_bridge) { if (! surface.is_solid() && ! is_bridge) {
// it's internal infill, so we can calculate a generic flow spacing // it's internal infill, so we can calculate a generic flow spacing
// for all layers, for avoiding the ugly effect of // for all layers, for avoiding the ugly effect of
// misaligned infill on first layer because of different extrusion width and // misaligned infill on first layer because of different extrusion width and
// layer height // layer height
my $internal_flow = $layerm->region->flow( Flow internal_flow = layerm.region()->flow(
FLOW_ROLE_INFILL, frInfill,
$layerm->layer->object->config->layer_height, // TODO: handle infill_every_layers? layerm.layer()->object()->config.layer_height.value, // TODO: handle infill_every_layers?
0, // no bridge false, // no bridge
0, // no first layer false, // no first layer
-1, // auto width -1, // auto width
$layerm->layer->object, *layerm.layer()->object()
); );
$f->set_spacing($internal_flow->spacing); f->spacing = internal_flow.spacing();
$using_internal_flow = 1; using_internal_flow = 1;
} else { } else {
$f->set_spacing($flow->spacing); f->spacing = flow.spacing();
} }
my $link_max_length = 0; double link_max_length = 0.;
if (! $is_bridge) { if (! is_bridge) {
$link_max_length = $layerm->region->config->get_abs_value_over($surface->is_external ? 'external_fill_link_max_length' : 'fill_link_max_length', $flow->spacing); link_max_length = layerm.region()->config.get_abs_value(surface.is_external() ? "external_fill_link_max_length" : "fill_link_max_length", flow.spacing());
print "flow spacing: ", $flow->spacing, " is_external: ", $surface->is_external, ", link_max_length: $link_max_length\n"; // printf("flow spacing: %f, is_external: %d, link_max_length: %lf\n", flow.spacing(), int(surface.is_external()), link_max_length);
} }
$f->set_layer_id($layerm->layer->id); f->layer_id = layerm.layer()->id();
$f->set_z($layerm->layer->print_z); f->z = layerm.layer()->print_z;
$f->set_angle(deg2rad($layerm->region->config->fill_angle)); f->angle = Geometry::deg2rad(layerm.region()->config.fill_angle.value);
// Maximum length of the perimeter segment linking two infill lines. // Maximum length of the perimeter segment linking two infill lines.
$f->set_link_max_length(scale($link_max_length)); f->link_max_length = scale_(link_max_length);
// Used by the concentric infill pattern to clip the loops to create extrusion paths. // Used by the concentric infill pattern to clip the loops to create extrusion paths.
$f->set_loop_clipping(scale($flow->nozzle_diameter) * &Slic3r::LOOP_CLIPPING_LENGTH_OVER_NOZZLE_DIAMETER); f->loop_clipping = scale_(flow.nozzle_diameter) * LOOP_CLIPPING_LENGTH_OVER_NOZZLE_DIAMETER;
// f->layer_height = h;
// apply half spacing using this flow's own spacing and generate infill
my @polylines = $f->fill_surface( // apply half spacing using this flow's own spacing and generate infill
$surface, FillParams params;
density => $density/100, params.density = 0.01 * density;
layer_height => $h, params.dont_adjust = true;
); Polylines polylines = f->fill_surface(&surface, params);
next unless @polylines; if (polylines.empty())
continue;
// calculate actual flow from spacing (which might have been adjusted by the infill // calculate actual flow from spacing (which might have been adjusted by the infill
// pattern generator) // pattern generator)
if ($using_internal_flow) { if (using_internal_flow) {
// if we used the internal flow we're not doing a solid infill // if we used the internal flow we're not doing a solid infill
// so we can safely ignore the slight variation that might have // so we can safely ignore the slight variation that might have
// been applied to $f->flow_spacing // been applied to $f->flow_spacing
} else { } else {
$flow = Slic3r::Flow->new_from_spacing( flow = Flow::new_from_spacing(f->spacing, flow.nozzle_diameter, h, is_bridge || f->use_bridge_flow());
spacing => $f->spacing,
nozzle_diameter => $flow->nozzle_diameter,
layer_height => $h,
bridge => $is_bridge || $f->use_bridge_flow,
);
} }
// save into layer // save into layer
{ {
my $role = $is_bridge ? EXTR_ROLE_BRIDGE ExtrusionRole role = is_bridge ? erBridgeInfill :
: $is_solid ? (($surface->surface_type == S_TYPE_TOP) ? EXTR_ROLE_TOPSOLIDFILL : EXTR_ROLE_SOLIDFILL) (surface.is_solid() ? ((surface.surface_type == stTop) ? erTopSolidInfill : erSolidInfill) : erInternalInfill);
: EXTR_ROLE_FILL; ExtrusionEntityCollection &collection = *(new ExtrusionEntityCollection());
out.entities.push_back(&collection);
out.
push @fills, my $collection = Slic3r::ExtrusionPath::Collection->new;
// Only concentric fills are not sorted. // Only concentric fills are not sorted.
$collection->no_sort($f->no_sort); collection.no_sort = f->no_sort();
$collection->append( for (Polylines::iterator it = polylines.begin(); it != polylines.end(); ++ it) {
map Slic3r::ExtrusionPath->new( ExtrusionPath *path = new ExtrusionPath(role);
polyline => $_, collection.entities.push_back(path);
role => $role, path->polyline.points.swap(it->points);
mm3_per_mm => $flow->mm3_per_mm, path->mm3_per_mm = flow.mm3_per_mm();
width => $flow->width, path->width = flow.width,
height => $flow->height, path->height = flow.height;
), map @$_, @polylines, }
);
} }
} }
@ -275,12 +254,15 @@ void make_fill(LayerRegion &layerm, ExtrusionEntityCollection &out)
// The path type could be ExtrusionPath, ExtrusionLoop or ExtrusionEntityCollection. // The path type could be ExtrusionPath, ExtrusionLoop or ExtrusionEntityCollection.
// Why the paths are unpacked? // Why the paths are unpacked?
for (ExtrusionEntitiesPtr::iterator thin_fill = layerm.thin_fills.entities.begin(); thin_fill != layerm.thin_fills.entities.end(); ++ thin_fill) { for (ExtrusionEntitiesPtr::iterator thin_fill = layerm.thin_fills.entities.begin(); thin_fill != layerm.thin_fills.entities.end(); ++ thin_fill) {
// ExtrusionEntityCollection #if 0
out.append(new ExtrusionEntityCollection->new($thin_fill); out.entities.push_back((*thin_fill)->clone());
assert(dynamic_cast<ExtrusionEntityCollection*>(out.entities.back()) != NULL);
#else
ExtrusionEntityCollection &collection = *(new ExtrusionEntityCollection());
out.entities.push_back(&collection);
collection.entities.push_back((*thin_fill)->clone());
#endif
} }
return @fills;
} }
#endif
} // namespace Slic3r } // namespace Slic3r

View File

@ -13,7 +13,8 @@
namespace Slic3r { namespace Slic3r {
class Surface; class ExtrusionEntityCollection;
class LayerRegion;
// An interface class to Perl, aggregating an instance of a Fill and a FillData. // An interface class to Perl, aggregating an instance of a Fill and a FillData.
class Filler class Filler
@ -28,6 +29,8 @@ public:
FillParams params; FillParams params;
}; };
void make_fill(LayerRegion &layerm, ExtrusionEntityCollection &out);
} // namespace Slic3r } // namespace Slic3r
#endif // slic3r_Fill_hpp_ #endif // slic3r_Fill_hpp_

View File

@ -60,15 +60,25 @@ Polylines Fill::fill_surface(const Surface *surface, const FillParams &params)
// Calculate a new spacing to fill width with possibly integer number of lines, // Calculate a new spacing to fill width with possibly integer number of lines,
// the first and last line being centered at the interval ends. // the first and last line being centered at the interval ends.
//FIXME Vojtech: This
// This function possibly increases the spacing, never decreases, // This function possibly increases the spacing, never decreases,
// and for a narrow width the increase in spacing may become severe! // and for a narrow width the increase in spacing may become severe,
// therefore the adjustment is limited to 20% increase.
coord_t Fill::_adjust_solid_spacing(const coord_t width, const coord_t distance) coord_t Fill::_adjust_solid_spacing(const coord_t width, const coord_t distance)
{ {
coord_t number_of_intervals = coord_t(coordf_t(width) / coordf_t(distance)); assert(width >= 0);
return (number_of_intervals == 0) ? assert(distance > 0);
// floor(width / distance)
coord_t number_of_intervals = width / distance;
coord_t distance_new = (number_of_intervals == 0) ?
distance : distance :
(width / number_of_intervals); (width / number_of_intervals);
const coordf_t factor = coordf_t(distance_new) / coordf_t(distance);
assert(factor > 1. - 1e-5);
// How much could the extrusion width be increased? By 20%.
const coordf_t factor_max = 1.2;
if (factor > factor_max)
distance_new = coord_t(floor((coordf_t(distance) * factor_max + 0.5)));
return distance_new;
} }
// Returns orientation of the infill and the reference point of the infill pattern. // Returns orientation of the infill and the reference point of the infill pattern.

View File

@ -17,7 +17,8 @@ void FillHoneycomb::_fill_surface_single(
CacheID cache_id(params.density, this->spacing); CacheID cache_id(params.density, this->spacing);
Cache::iterator it_m = this->cache.find(cache_id); Cache::iterator it_m = this->cache.find(cache_id);
if (it_m == this->cache.end()) { if (it_m == this->cache.end()) {
#if SLIC3R_CPPVER > 11 #if 0
// #if SLIC3R_CPPVER > 11
it_m = this->cache.emplace_hint(it_m); it_m = this->cache.emplace_hint(it_m);
#else #else
it_m = this->cache.insert(it_m, std::pair<CacheID, CacheData>(cache_id, CacheData())); it_m = this->cache.insert(it_m, std::pair<CacheID, CacheData>(cache_id, CacheData()));

View File

@ -67,7 +67,7 @@ public:
virtual ~FillGrid() {} virtual ~FillGrid() {}
protected: protected:
// The grid fill will keep the angle constant between the layers, see the implementation of Slic3r::Fill::Base. // The grid fill will keep the angle constant between the layers, see the implementation of Slic3r::Fill.
virtual float _layer_angle(size_t idx) const { return 0.f; } virtual float _layer_angle(size_t idx) const { return 0.f; }
// Flag for Slic3r::Fill::Rectilinear to fill both directions. // Flag for Slic3r::Fill::Rectilinear to fill both directions.
virtual bool _horizontal_lines() const { return true; } virtual bool _horizontal_lines() const { return true; }

View File

@ -790,10 +790,8 @@ bool FillRectilinear2::fill_surface_by_lines(const Surface *surface, const FillP
std::pair<float, Point> rotate_vector = this->_infill_direction(surface); std::pair<float, Point> rotate_vector = this->_infill_direction(surface);
rotate_vector.first += angleBase; rotate_vector.first += angleBase;
this->_min_spacing = scale_(this->spacing);
myassert(params.density > 0.0001f && params.density <= 1.f); myassert(params.density > 0.0001f && params.density <= 1.f);
this->_line_spacing = coord_t(coordf_t(this->_min_spacing) / params.density); coord_t line_spacing = coord_t(scale_(this->spacing) / params.density);
this->_diagonal_distance = this->_line_spacing * 2;
// On the polygons of poly_with_offset, the infill lines will be connected. // On the polygons of poly_with_offset, the infill lines will be connected.
ExPolygonWithOffset poly_with_offset( ExPolygonWithOffset poly_with_offset(
@ -811,24 +809,24 @@ bool FillRectilinear2::fill_surface_by_lines(const Surface *surface, const FillP
// define flow spacing according to requested density // define flow spacing according to requested density
bool full_infill = params.density > 0.9999f; bool full_infill = params.density > 0.9999f;
if (full_infill && !params.dont_adjust) { if (full_infill && !params.dont_adjust) {
// this->_min_spacing = this->_line_spacing = this->_adjust_solid_spacing(bounding_box.size().x, this->_line_spacing); line_spacing = this->_adjust_solid_spacing(bounding_box.size().x, line_spacing);
// this->spacing = unscale(this->_line_spacing); this->spacing = unscale(line_spacing);
} else { } else {
// extend bounding box so that our pattern will be aligned with other layers // extend bounding box so that our pattern will be aligned with other layers
// Transform the reference point to the rotated coordinate system. // Transform the reference point to the rotated coordinate system.
Point refpt = rotate_vector.second.rotated(- rotate_vector.first); Point refpt = rotate_vector.second.rotated(- rotate_vector.first);
// _align_to_grid will not work correctly with positive pattern_shift. // _align_to_grid will not work correctly with positive pattern_shift.
coord_t pattern_shift_scaled = coord_t(scale_(pattern_shift)) % this->_line_spacing; coord_t pattern_shift_scaled = coord_t(scale_(pattern_shift)) % line_spacing;
refpt.x -= (pattern_shift_scaled > 0) ? pattern_shift_scaled : (this->_line_spacing + pattern_shift_scaled); refpt.x -= (pattern_shift_scaled > 0) ? pattern_shift_scaled : (line_spacing + pattern_shift_scaled);
bounding_box.merge(_align_to_grid( bounding_box.merge(_align_to_grid(
bounding_box.min, bounding_box.min,
Point(this->_line_spacing, this->_line_spacing), Point(line_spacing, line_spacing),
refpt)); refpt));
} }
// Intersect a set of euqally spaced vertical lines wiht expolygon. // Intersect a set of euqally spaced vertical lines wiht expolygon.
size_t n_vlines = (bounding_box.max.x - bounding_box.min.x + SCALED_EPSILON) / this->_line_spacing; size_t n_vlines = (bounding_box.max.x - bounding_box.min.x + SCALED_EPSILON) / line_spacing;
coord_t x0 = bounding_box.min.x + this->_line_spacing; coord_t x0 = bounding_box.min.x + line_spacing / 2;
#ifdef SLIC3R_DEBUG #ifdef SLIC3R_DEBUG
static int iRun = 0; static int iRun = 0;
@ -847,7 +845,7 @@ bool FillRectilinear2::fill_surface_by_lines(const Surface *surface, const FillP
std::vector<SegmentedIntersectionLine> segs(n_vlines, SegmentedIntersectionLine()); std::vector<SegmentedIntersectionLine> segs(n_vlines, SegmentedIntersectionLine());
for (size_t i = 0; i < n_vlines; ++ i) { for (size_t i = 0; i < n_vlines; ++ i) {
segs[i].idx = i; segs[i].idx = i;
segs[i].pos = x0 + i * this->_line_spacing; segs[i].pos = x0 + i * line_spacing;
} }
for (size_t iContour = 0; iContour < poly_with_offset.n_contours; ++ iContour) { for (size_t iContour = 0; iContour < poly_with_offset.n_contours; ++ iContour) {
const Points &contour = poly_with_offset.contour(iContour).points; const Points &contour = poly_with_offset.contour(iContour).points;
@ -864,12 +862,12 @@ bool FillRectilinear2::fill_surface_by_lines(const Surface *surface, const FillP
if (l > r) if (l > r)
std::swap(l, r); std::swap(l, r);
// il, ir are the left / right indices of vertical lines intersecting a segment // il, ir are the left / right indices of vertical lines intersecting a segment
int il = (l - x0) / this->_line_spacing; int il = (l - x0) / line_spacing;
while (il * this->_line_spacing + x0 < l) while (il * line_spacing + x0 < l)
++ il; ++ il;
il = std::max(int(0), il); il = std::max(int(0), il);
int ir = (r - x0 + this->_line_spacing) / this->_line_spacing; int ir = (r - x0 + line_spacing) / line_spacing;
while (ir * this->_line_spacing + x0 > r) while (ir * line_spacing + x0 > r)
-- ir; -- ir;
ir = std::min(int(segs.size()) - 1, ir); ir = std::min(int(segs.size()) - 1, ir);
if (il > ir) if (il > ir)
@ -879,7 +877,7 @@ bool FillRectilinear2::fill_surface_by_lines(const Surface *surface, const FillP
myassert(ir >= 0 && ir < segs.size()); myassert(ir >= 0 && ir < segs.size());
for (int i = il; i <= ir; ++ i) { for (int i = il; i <= ir; ++ i) {
coord_t this_x = segs[i].pos; coord_t this_x = segs[i].pos;
assert(this_x == i * this->_line_spacing + x0); assert(this_x == i * line_spacing + x0);
SegmentIntersection is; SegmentIntersection is;
is.iContour = iContour; is.iContour = iContour;
is.iSegment = iSegment; is.iSegment = iSegment;

View File

@ -17,11 +17,6 @@ public:
protected: protected:
bool fill_surface_by_lines(const Surface *surface, const FillParams &params, float angleBase, float pattern_shift, Polylines &polylines_out); bool fill_surface_by_lines(const Surface *surface, const FillParams &params, float angleBase, float pattern_shift, Polylines &polylines_out);
coord_t _min_spacing;
coord_t _line_spacing;
// distance threshold for allowing the horizontal infill lines to be connected into a continuous path
coord_t _diagonal_distance;
}; };
class FillGrid2 : public FillRectilinear2 class FillGrid2 : public FillRectilinear2
@ -31,7 +26,7 @@ public:
virtual Polylines fill_surface(const Surface *surface, const FillParams &params); virtual Polylines fill_surface(const Surface *surface, const FillParams &params);
protected: protected:
// The grid fill will keep the angle constant between the layers, see the implementation of Slic3r::Fill::Base. // The grid fill will keep the angle constant between the layers, see the implementation of Slic3r::Fill.
virtual float _layer_angle(size_t idx) const { return 0.f; } virtual float _layer_angle(size_t idx) const { return 0.f; }
}; };
@ -42,7 +37,7 @@ public:
virtual Polylines fill_surface(const Surface *surface, const FillParams &params); virtual Polylines fill_surface(const Surface *surface, const FillParams &params);
protected: protected:
// The grid fill will keep the angle constant between the layers, see the implementation of Slic3r::Fill::Base. // The grid fill will keep the angle constant between the layers, see the implementation of Slic3r::Fill.
virtual float _layer_angle(size_t idx) const { return 0.f; } virtual float _layer_angle(size_t idx) const { return 0.f; }
}; };
@ -53,7 +48,7 @@ public:
virtual Polylines fill_surface(const Surface *surface, const FillParams &params); virtual Polylines fill_surface(const Surface *surface, const FillParams &params);
protected: protected:
// The grid fill will keep the angle constant between the layers, see the implementation of Slic3r::Fill::Base. // The grid fill will keep the angle constant between the layers, see the implementation of Slic3r::Fill.
virtual float _layer_angle(size_t idx) const { return 0.f; } virtual float _layer_angle(size_t idx) const { return 0.f; }
}; };

View File

@ -362,7 +362,7 @@ GCodeSender::on_read(const boost::system::error_code& error,
} }
this->send(); this->send();
} else { } else {
printf("Cannot resend %zu (oldest we have is %zu)\n", toresend, this->sent - this->last_sent.size()); printf("Cannot resend " PRINTF_ZU " (oldest we have is " PRINTF_ZU ")\n", toresend, this->sent - this->last_sent.size());
} }
} else if (boost::starts_with(line, "wait")) { } else if (boost::starts_with(line, "wait")) {
// ignore // ignore

View File

@ -372,7 +372,7 @@ Pointfs arrange(size_t num_parts, const Pointf &part_size, coordf_t gap, const B
size_t cellw = size_t(floor((bed_bbox.size().x + gap) / cell_size.x)); size_t cellw = size_t(floor((bed_bbox.size().x + gap) / cell_size.x));
size_t cellh = size_t(floor((bed_bbox.size().y + gap) / cell_size.y)); size_t cellh = size_t(floor((bed_bbox.size().y + gap) / cell_size.y));
if (num_parts > cellw * cellh) if (num_parts > cellw * cellh)
CONFESS("%zu parts won't fit in your print area!\n", num_parts); CONFESS(PRINTF_ZU " parts won't fit in your print area!\n", num_parts);
// Get a bounding box of cellw x cellh cells, centered at the center of the bed. // Get a bounding box of cellw x cellh cells, centered at the center of the bed.
Pointf cells_size(cellw * cell_size.x - gap, cellh * cell_size.y - gap); Pointf cells_size(cellw * cell_size.x - gap, cellh * cell_size.y - gap);
@ -446,7 +446,7 @@ arrange(size_t total_parts, const Pointf &part_size, coordf_t dist, const Boundi
size_t cellw = floor((area.x + dist) / part.x); size_t cellw = floor((area.x + dist) / part.x);
size_t cellh = floor((area.y + dist) / part.y); size_t cellh = floor((area.y + dist) / part.y);
if (total_parts > (cellw * cellh)) if (total_parts > (cellw * cellh))
CONFESS("%zu parts won't fit in your print area!\n", total_parts); CONFESS(PRINTF_ZU " parts won't fit in your print area!\n", total_parts);
// total space used by cells // total space used by cells
Pointf cells(cellw * part.x, cellh * part.y); Pointf cells(cellw * part.x, cellh * part.y);

View File

@ -2,6 +2,7 @@
#include "ClipperUtils.hpp" #include "ClipperUtils.hpp"
#include "Geometry.hpp" #include "Geometry.hpp"
#include "Print.hpp" #include "Print.hpp"
#include "Fill/Fill.hpp"
#include "SVG.hpp" #include "SVG.hpp"
namespace Slic3r { namespace Slic3r {
@ -69,8 +70,9 @@ Layer::region_count() const
void void
Layer::clear_regions() Layer::clear_regions()
{ {
for (int i = this->regions.size()-1; i >= 0; --i) for (size_t i = 0; i < this->regions.size(); ++ i)
this->delete_region(i); delete this->regions[i];
this->regions.clear();
} }
LayerRegion* LayerRegion*
@ -170,7 +172,7 @@ void
Layer::make_perimeters() Layer::make_perimeters()
{ {
#ifdef SLIC3R_DEBUG #ifdef SLIC3R_DEBUG
printf("Making perimeters for layer %zu\n", this->id()); printf("Making perimeters for layer " PRINTF_ZU "\n", this->id());
#endif #endif
// keep track of regions whose perimeters we have already generated // keep track of regions whose perimeters we have already generated
@ -272,6 +274,22 @@ Layer::make_perimeters()
} }
} }
void Layer::make_fills()
{
#ifdef SLIC3R_DEBUG
printf("Making fills for layer " PRINTF_ZU "\n", this->id());
#endif
for (LayerRegionPtrs::iterator it_layerm = regions.begin(); it_layerm != regions.end(); ++ it_layerm) {
LayerRegion &layerm = *(*it_layerm);
layerm.fills.clear();
make_fill(layerm, layerm.fills);
#ifndef NDEBUG
for (size_t i = 0; i < layerm.fills.entities.size(); ++ i)
assert(dynamic_cast<ExtrusionEntityCollection*>(layerm.fills.entities[i]) != NULL);
#endif
}
}
void Layer::export_region_slices_to_svg(const char *path) void Layer::export_region_slices_to_svg(const char *path)
{ {
BoundingBox bbox; BoundingBox bbox;

View File

@ -116,6 +116,7 @@ public:
template <class T> bool any_internal_region_slice_contains(const T &item) const; template <class T> bool any_internal_region_slice_contains(const T &item) const;
template <class T> bool any_bottom_region_slice_contains(const T &item) const; template <class T> bool any_bottom_region_slice_contains(const T &item) const;
void make_perimeters(); void make_perimeters();
void make_fills();
void export_region_slices_to_svg(const char *path); void export_region_slices_to_svg(const char *path);
void export_region_fill_surfaces_to_svg(const char *path); void export_region_fill_surfaces_to_svg(const char *path);

View File

@ -119,7 +119,7 @@ LayerRegion::process_external_surfaces(const Layer* lower_layer)
); );
#ifdef SLIC3R_DEBUG #ifdef SLIC3R_DEBUG
printf("Processing bridge at layer %zu:\n", this->layer()->id(); printf("Processing bridge at layer " PRINTF_ZU ":\n", this->layer()->id();
#endif #endif
if (bd.detect_angle()) { if (bd.detect_angle()) {
@ -257,7 +257,7 @@ LayerRegion::process_external_surfaces(const Layer* lower_layer)
this->flow(frInfill, this->layer()->height, true).scaled_width() this->flow(frInfill, this->layer()->height, true).scaled_width()
); );
#ifdef SLIC3R_DEBUG #ifdef SLIC3R_DEBUG
printf("Processing bridge at layer %zu:\n", this->layer()->id(); printf("Processing bridge at layer " PRINTF_ZU ":\n", this->layer()->id());
#endif #endif
if (bd.detect_angle()) { if (bd.detect_angle()) {
surface.bridge_angle = bd.angle; surface.bridge_angle = bd.angle;

View File

@ -100,7 +100,7 @@ PerimeterGenerator::process()
ex->medial_axis(ext_pwidth + ext_pspacing2, min_width, &thin_walls); ex->medial_axis(ext_pwidth + ext_pspacing2, min_width, &thin_walls);
#ifdef DEBUG #ifdef DEBUG
printf(" %zu thin walls detected\n", thin_walls.size()); printf(" " PRINTF_ZU " thin walls detected\n", thin_walls.size());
#endif #endif
/* /*

View File

@ -58,6 +58,18 @@ extern bool remove_sticks(Polygons &polys);
// Remove polygons with less than 3 edges. // Remove polygons with less than 3 edges.
extern bool remove_degenerate(Polygons &polys); extern bool remove_degenerate(Polygons &polys);
extern bool remove_small(Polygons &polys, double min_area); extern bool remove_small(Polygons &polys, double min_area);
// Append a vector of polygons at the end of another vector of polygons.
inline void polygons_append(Polygons &dst, const Polygons &src) { dst.insert(dst.end(), src.begin(), src.end()); }
#if SLIC3R_CPPVER >= 11
inline void polygons_append(Polygons &dst, Polygons &&src)
{
if (dst.empty())
dst = std::move(src);
else
std::move(std::begin(src), std::end(src), std::back_inserter(dst));
}
#endif
} }
// start Boost // start Boost

View File

@ -47,7 +47,7 @@ inline int nearest_point_index(const std::vector<Chaining> &pairs, const Point &
} }
Polylines PolylineCollection::chained_path_from( Polylines PolylineCollection::chained_path_from(
#if SLIC3R_CPPVER > 11 #if SLIC3R_CPPVER >= 11
Polylines &&src, Polylines &&src,
#else #else
const Polylines &src, const Polylines &src,
@ -70,7 +70,7 @@ Polylines PolylineCollection::chained_path_from(
// find nearest point // find nearest point
int endpoint_index = nearest_point_index<double>(endpoints, start_near, no_reverse); int endpoint_index = nearest_point_index<double>(endpoints, start_near, no_reverse);
assert(endpoint_index >= 0 && endpoint_index < endpoints.size() * 2); assert(endpoint_index >= 0 && endpoint_index < endpoints.size() * 2);
#if SLIC3R_CPPVER > 11 #if SLIC3R_CPPVER >= 11
retval.push_back(std::move(src[endpoints[endpoint_index/2].idx])); retval.push_back(std::move(src[endpoints[endpoint_index/2].idx]));
#else #else
retval.push_back(src[endpoints[endpoint_index/2].idx]); retval.push_back(src[endpoints[endpoint_index/2].idx]);
@ -83,7 +83,7 @@ Polylines PolylineCollection::chained_path_from(
return retval; return retval;
} }
#if SLIC3R_CPPVER > 11 #if SLIC3R_CPPVER >= 11
Polylines PolylineCollection::chained_path(Polylines &&src, bool no_reverse) Polylines PolylineCollection::chained_path(Polylines &&src, bool no_reverse)
{ {
return (src.empty() || src.front().empty()) ? return (src.empty() || src.front().empty()) ?

View File

@ -19,7 +19,7 @@ public:
void append(const Polylines &polylines); void append(const Polylines &polylines);
static Point leftmost_point(const Polylines &polylines); static Point leftmost_point(const Polylines &polylines);
#if SLIC3R_CPPVER > 11 #if SLIC3R_CPPVER >= 11
static Polylines chained_path(Polylines &&src, bool no_reverse = false); static Polylines chained_path(Polylines &&src, bool no_reverse = false);
static Polylines chained_path_from(Polylines &&src, Point start_near, bool no_reverse = false); static Polylines chained_path_from(Polylines &&src, Point start_near, bool no_reverse = false);
static Polylines chained_path(Polylines src, bool no_reverse = false); static Polylines chained_path(Polylines src, bool no_reverse = false);

View File

@ -100,7 +100,6 @@ public:
LayerPtrs layers; LayerPtrs layers;
SupportLayerPtrs support_layers; SupportLayerPtrs support_layers;
// TODO: Fill* fill_maker => (is => 'lazy');
PrintState<PrintObjectStep> state; PrintState<PrintObjectStep> state;
Print* print() { return this->_print; } Print* print() { return this->_print; }
@ -114,7 +113,10 @@ public:
bool delete_all_copies(); bool delete_all_copies();
bool set_copies(const Points &points); bool set_copies(const Points &points);
bool reload_model_instances(); bool reload_model_instances();
BoundingBox bounding_box() const; BoundingBox bounding_box() const {
// since the object is aligned to origin, bounding box coincides with size
return BoundingBox(Point(0,0), this->size);
}
// adds region_id, too, if necessary // adds region_id, too, if necessary
void add_region_volume(int region_id, int volume_id); void add_region_volume(int region_id, int volume_id);

View File

@ -89,16 +89,6 @@ PrintObject::reload_model_instances()
return this->set_copies(copies); return this->set_copies(copies);
} }
BoundingBox
PrintObject::bounding_box() const
{
// since the object is aligned to origin, bounding box coincides with size
Points pp;
pp.push_back(Point(0,0));
pp.push_back(this->size);
return BoundingBox(pp);
}
void void
PrintObject::add_region_volume(int region_id, int volume_id) PrintObject::add_region_volume(int region_id, int volume_id)
{ {
@ -229,8 +219,10 @@ PrintObject::invalidate_state_by_config_options(const std::vector<t_config_optio
|| *opt_key == "ensure_vertical_shell_thickness") { || *opt_key == "ensure_vertical_shell_thickness") {
steps.insert(posPrepareInfill); steps.insert(posPrepareInfill);
} else if (*opt_key == "external_fill_pattern" } else if (*opt_key == "external_fill_pattern"
|| *opt_key == "external_fill_link_max_length"
|| *opt_key == "fill_angle" || *opt_key == "fill_angle"
|| *opt_key == "fill_pattern" || *opt_key == "fill_pattern"
|| *opt_key == "fill_link_max_length"
|| *opt_key == "top_infill_extrusion_width" || *opt_key == "top_infill_extrusion_width"
|| *opt_key == "first_layer_extrusion_width") { || *opt_key == "first_layer_extrusion_width") {
steps.insert(posInfill); steps.insert(posInfill);
@ -375,15 +367,9 @@ PrintObject::discover_vertical_shells()
++ idx; ++ idx;
} }
#endif /* SLIC3R_DEBUG_SLICE_PROCESSING */ #endif /* SLIC3R_DEBUG_SLICE_PROCESSING */
for (int n = (int)idx_layer - layerm->region()->config.bottom_solid_layers + 1; n < (int)idx_layer + layerm->region()->config.top_solid_layers; ++ n) { for (int n = (int)idx_layer - layerm->region()->config.bottom_solid_layers + 1; n < (int)idx_layer + layerm->region()->config.top_solid_layers; ++ n)
if (n < 0 || n >= (int)this->layers.size()) if (n >= 0 && n < (int)this->layers.size())
continue; polygons_append(shell, this->layers[n]->perimeter_expolygons.expolygons);
ExPolygons &expolys = this->layers[n]->perimeter_expolygons;
for (size_t i = 0; i < expolys.size(); ++ i) {
shell.push_back(expolys[i].contour);
shell.insert(shell.end(), expolys[i].holes.begin(), expolys[i].holes.end());
}
}
#ifdef SLIC3R_DEBUG_SLICE_PROCESSING #ifdef SLIC3R_DEBUG_SLICE_PROCESSING
{ {
static size_t idx = 0; static size_t idx = 0;
@ -565,7 +551,7 @@ PrintObject::bridge_over_infill()
} }
#ifdef SLIC3R_DEBUG #ifdef SLIC3R_DEBUG
printf("Bridging %zu internal areas at layer %zu\n", to_bridge.size(), layer->id()); printf("Bridging " PRINTF_ZU " internal areas at layer " PRINTF_ZU "\n", to_bridge.size(), layer->id());
#endif #endif
// compute the remaning internal solid surfaces as difference // compute the remaning internal solid surfaces as difference

View File

@ -5,11 +5,14 @@
#include "Layer.hpp" #include "Layer.hpp"
#include "SupportMaterial.hpp" #include "SupportMaterial.hpp"
#include "Fill/FillBase.hpp" #include "Fill/FillBase.hpp"
#include "SVG.hpp"
#include <cmath> #include <cmath>
#include <cassert> #include <cassert>
#include <memory> #include <memory>
#define SLIC3R_DEBUG
namespace Slic3r { namespace Slic3r {
// Increment used to reach MARGIN in steps to avoid trespassing thin objects // Increment used to reach MARGIN in steps to avoid trespassing thin objects
@ -24,21 +27,27 @@ PrintObjectSupportMaterial::PrintObjectSupportMaterial(const PrintObject *object
m_print_config (&object->print()->config), m_print_config (&object->print()->config),
m_object_config (&object->config), m_object_config (&object->config),
m_first_layer_flow (0, 0, 0, false), // First layer flow will be set in the constructor code. m_first_layer_flow (Flow::new_from_config_width(
frSupportMaterial,
(object->print()->config.first_layer_extrusion_width.value > 0) ? object->print()->config.first_layer_extrusion_width : object->config.support_material_extrusion_width,
object->print()->config.nozzle_diameter.get_at(object->config.support_material_extruder-1),
object->config.get_abs_value("first_layer_height"),
false
)),
m_support_material_flow (Flow::new_from_config_width( m_support_material_flow (Flow::new_from_config_width(
frSupportMaterial, frSupportMaterial,
object->config.support_material_extrusion_width, // object->config.extrusion_width.value (object->config.support_material_extrusion_width.value > 0) ? object->config.support_material_extrusion_width : object->config.extrusion_width,
object->print()->config.nozzle_diameter.get_at(object->config.support_material_extruder-1), object->print()->config.nozzle_diameter.get_at(object->config.support_material_extruder-1),
object->config.layer_height.value, object->config.layer_height.value,
false)), false)),
m_support_material_interface_flow(Flow::new_from_config_width( m_support_material_interface_flow(Flow::new_from_config_width(
frSupportMaterialInterface, frSupportMaterialInterface,
object->config.support_material_extrusion_width, // object->config.extrusion_width.value (object->config.support_material_extrusion_width.value > 0) ? object->config.support_material_extrusion_width : object->config.extrusion_width,
object->print()->config.nozzle_diameter.get_at(object->config.support_material_interface_extruder-1), object->print()->config.nozzle_diameter.get_at(object->config.support_material_interface_extruder-1),
object->config.layer_height.value, object->config.layer_height.value,
false)), false)),
m_soluble_interface (object->config.support_material_contact_distance.value == 0), m_soluble_interface (object->config.support_material_contact_distance.value == 0),
m_support_material_raft_base_flow(0, 0, 0, false), m_support_material_raft_base_flow(0, 0, 0, false),
m_support_material_raft_interface_flow(0, 0, 0, false), m_support_material_raft_interface_flow(0, 0, 0, false),
m_support_material_raft_contact_flow(0, 0, 0, false), m_support_material_raft_contact_flow(0, 0, 0, false),
@ -173,10 +182,13 @@ inline void layers_append(PrintObjectSupportMaterial::MyLayersPtr &dst, const Pr
dst.insert(dst.end(), src.begin(), src.end()); dst.insert(dst.end(), src.begin(), src.end());
} }
inline void polygons_append(Polygons &dst, const Polygons &src) // Compare layers lexicographically.
struct MyLayersPtrCompare
{ {
dst.insert(dst.end(), src.begin(), src.end()); bool operator()(const PrintObjectSupportMaterial::MyLayer* layer1, const PrintObjectSupportMaterial::MyLayer* layer2) const {
} return *layer1 < *layer2;
}
};
void PrintObjectSupportMaterial::generate(PrintObject &object) void PrintObjectSupportMaterial::generate(PrintObject &object)
{ {
@ -204,10 +216,30 @@ void PrintObjectSupportMaterial::generate(PrintObject &object)
// Nothing is supported, no supports are generated. // Nothing is supported, no supports are generated.
return; return;
#ifdef SLIC3R_DEBUG
static int iRun = 0;
iRun ++;
for (MyLayersPtr::const_iterator it = top_contacts.begin(); it != top_contacts.end(); ++ it) {
const MyLayer &layer = *(*it);
::Slic3r::SVG svg(debug_out_path("support-top-contacts-%d-%lf.svg", iRun, layer.print_z), get_extents(layer.polygons));
Slic3r::ExPolygons expolys = union_ex(layer.polygons, false);
svg.draw(expolys);
}
#endif /* SLIC3R_DEBUG */
// Determine the bottom contact surfaces of the supports over the top surfaces of the object. // Determine the bottom contact surfaces of the supports over the top surfaces of the object.
// Depending on whether the support is soluble or not, the contact layer thickness is decided. // Depending on whether the support is soluble or not, the contact layer thickness is decided.
MyLayersPtr bottom_contacts = this->bottom_contact_layers(object, top_contacts, layer_storage); MyLayersPtr bottom_contacts = this->bottom_contact_layers(object, top_contacts, layer_storage);
#ifdef SLIC3R_DEBUG
for (MyLayersPtr::const_iterator it = bottom_contacts.begin(); it != bottom_contacts.end(); ++ it) {
const MyLayer &layer = *(*it);
::Slic3r::SVG svg(debug_out_path("support-bottom-contacts-%d-%lf.svg", iRun, layer.print_z), get_extents(layer.polygons));
Slic3r::ExPolygons expolys = union_ex(layer.polygons, false);
svg.draw(expolys);
}
#endif /* SLIC3R_DEBUG */
// Because the top and bottom contacts are thick slabs, they may overlap causing over extrusion // Because the top and bottom contacts are thick slabs, they may overlap causing over extrusion
// and unwanted strong bonds to the object. // and unwanted strong bonds to the object.
// Rather trim the top contacts by their overlapping bottom contacts to leave a gap instead of over extruding. // Rather trim the top contacts by their overlapping bottom contacts to leave a gap instead of over extruding.
@ -223,6 +255,15 @@ void PrintObjectSupportMaterial::generate(PrintObject &object)
// Fill in intermediate layers between the top / bottom support contact layers, trimmed by the object. // Fill in intermediate layers between the top / bottom support contact layers, trimmed by the object.
this->generate_base_layers(object, bottom_contacts, top_contacts, intermediate_layers); this->generate_base_layers(object, bottom_contacts, top_contacts, intermediate_layers);
#ifdef SLIC3R_DEBUG
for (MyLayersPtr::const_iterator it = intermediate_layers.begin(); it != intermediate_layers.end(); ++ it) {
const MyLayer &layer = *(*it);
::Slic3r::SVG svg(debug_out_path("support-base-layers-%d-%lf.svg", iRun, layer.print_z), get_extents(layer.polygons));
Slic3r::ExPolygons expolys = union_ex(layer.polygons, false);
svg.draw(expolys);
}
#endif /* SLIC3R_DEBUG */
// If raft is to be generated, the 1st top_contact layer will contain the 1st object layer silhouette without holes. // If raft is to be generated, the 1st top_contact layer will contain the 1st object layer silhouette without holes.
// Add the bottom contacts to the raft, inflate the support bases. // Add the bottom contacts to the raft, inflate the support bases.
// There is a contact layer below the 1st object layer in the bottom contacts. // There is a contact layer below the 1st object layer in the bottom contacts.
@ -242,6 +283,15 @@ void PrintObjectSupportMaterial::generate(PrintObject &object)
MyLayersPtr interface_layers = this->generate_interface_layers( MyLayersPtr interface_layers = this->generate_interface_layers(
object, bottom_contacts, top_contacts, intermediate_layers, layer_storage); object, bottom_contacts, top_contacts, intermediate_layers, layer_storage);
#ifdef SLIC3R_DEBUG
for (MyLayersPtr::const_iterator it = interface_layers.begin(); it != interface_layers.end(); ++ it) {
const MyLayer &layer = *(*it);
::Slic3r::SVG svg(debug_out_path("support-interface-layers-%d-%lf.svg", iRun, layer.print_z), get_extents(layer.polygons));
Slic3r::ExPolygons expolys = union_ex(layer.polygons, false);
svg.draw(expolys);
}
#endif /* SLIC3R_DEBUG */
/* /*
// Clip with the pillars. // Clip with the pillars.
if (! shape.empty()) { if (! shape.empty()) {
@ -257,7 +307,7 @@ void PrintObjectSupportMaterial::generate(PrintObject &object)
layers_append(layers_sorted, top_contacts); layers_append(layers_sorted, top_contacts);
layers_append(layers_sorted, intermediate_layers); layers_append(layers_sorted, intermediate_layers);
layers_append(layers_sorted, interface_layers); layers_append(layers_sorted, interface_layers);
std::sort(layers_sorted.begin(), layers_sorted.end()); std::sort(layers_sorted.begin(), layers_sorted.end(), MyLayersPtrCompare());
int layer_id = 0; int layer_id = 0;
for (int i = 0; i < int(layers_sorted.size());) { for (int i = 0; i < int(layers_sorted.size());) {
@ -302,10 +352,8 @@ void collect_region_slices_by_type(const Layer &layer, SurfaceType surface_type,
const SurfaceCollection &slices = region.slices; const SurfaceCollection &slices = region.slices;
for (Surfaces::const_iterator it = slices.surfaces.begin(); it != slices.surfaces.end(); ++ it) { for (Surfaces::const_iterator it = slices.surfaces.begin(); it != slices.surfaces.end(); ++ it) {
const Surface &surface = *it; const Surface &surface = *it;
if (surface.surface_type == surface_type) { if (surface.surface_type == surface_type)
out.push_back(surface.expolygon.contour); polygons_append(out, surface.expolygon);
out.insert(out.end(), surface.expolygon.holes.begin(), surface.expolygon.holes.end());
}
} }
} }
} }
@ -344,23 +392,44 @@ Polygons collect_region_slices_outer(const Layer &layer)
return out; return out;
} }
// Collect outer contours of all expolygons in all layer region slices.
void collect_slices_outer(const Layer &layer, Polygons &out)
{
out.reserve(out.size() + layer.slices.expolygons.size());
for (ExPolygons::const_iterator it = layer.slices.expolygons.begin(); it != layer.slices.expolygons.end(); ++ it)
out.push_back(it->contour);
}
// Collect outer contours of all expolygons in all layer region slices.
Polygons collect_slices_outer(const Layer &layer)
{
Polygons out;
collect_slices_outer(layer, out);
return out;
}
// Find the top contact surfaces of the support or the raft. // Find the top contact surfaces of the support or the raft.
PrintObjectSupportMaterial::MyLayersPtr PrintObjectSupportMaterial::top_contact_layers(const PrintObject &object, MyLayerStorage &layer_storage) const PrintObjectSupportMaterial::MyLayersPtr PrintObjectSupportMaterial::top_contact_layers(const PrintObject &object, MyLayerStorage &layer_storage) const
{ {
#ifdef SLIC3R_DEBUG
static int iRun = 0;
++ iRun;
#endif /* SLIC3R_DEBUG */
// Output layers, sorte by top Z. // Output layers, sorte by top Z.
MyLayersPtr contact_out; MyLayersPtr contact_out;
// If user specified a custom angle threshold, convert it to radians. // If user specified a custom angle threshold, convert it to radians.
double threshold_rad = 0.; double threshold_rad = 0.;
if (m_object_config->support_material_threshold > 0) { if (m_object_config->support_material_threshold.value > 0) {
threshold_rad = M_PI * double(m_object_config->support_material_threshold + 1) / 180.; // +1 makes the threshold inclusive threshold_rad = M_PI * double(m_object_config->support_material_threshold.value + 1) / 180.; // +1 makes the threshold inclusive
// Slic3r::debugf "Threshold angle = %d°\n", rad2deg($threshold_rad); // Slic3r::debugf "Threshold angle = %d°\n", rad2deg($threshold_rad);
} }
// Build support on a build plate only? If so, then collect top surfaces into $buildplate_only_top_surfaces // Build support on a build plate only? If so, then collect top surfaces into $buildplate_only_top_surfaces
// and subtract $buildplate_only_top_surfaces from the contact surfaces, so // and subtract $buildplate_only_top_surfaces from the contact surfaces, so
// there is no contact surface supported by a top surface. // there is no contact surface supported by a top surface.
bool buildplate_only = m_object_config->support_material && m_object_config->support_material_buildplate_only; bool buildplate_only = m_object_config->support_material.value && m_object_config->support_material_buildplate_only.value;
Polygons buildplate_only_top_surfaces; Polygons buildplate_only_top_surfaces;
// Determine top contact areas. // Determine top contact areas.
@ -401,7 +470,7 @@ PrintObjectSupportMaterial::MyLayersPtr PrintObjectSupportMaterial::top_contact_
// This is the first object layer, so the object is being printed on a raft and // This is the first object layer, so the object is being printed on a raft and
// we're here just to get the object footprint for the raft. // we're here just to get the object footprint for the raft.
// We only consider contours and discard holes to get a more continuous raft. // We only consider contours and discard holes to get a more continuous raft.
overhang_polygons = collect_region_slices_outer(layer); overhang_polygons = collect_slices_outer(layer);
// Extend by SUPPORT_MATERIAL_MARGIN, which is 1.5mm // Extend by SUPPORT_MATERIAL_MARGIN, which is 1.5mm
contact_polygons = offset(overhang_polygons, scale_(SUPPORT_MATERIAL_MARGIN)); contact_polygons = offset(overhang_polygons, scale_(SUPPORT_MATERIAL_MARGIN));
} else { } else {
@ -413,7 +482,7 @@ PrintObjectSupportMaterial::MyLayersPtr PrintObjectSupportMaterial::top_contact_
// It is the maximum widh of the extrudate. // It is the maximum widh of the extrudate.
coord_t fw = layerm.flow(frExternalPerimeter).scaled_width(); coord_t fw = layerm.flow(frExternalPerimeter).scaled_width();
coordf_t lower_layer_offset = coordf_t lower_layer_offset =
(layer_id < m_object_config->support_material_enforce_layers) ? (layer_id < m_object_config->support_material_enforce_layers.value) ?
// Enforce a full possible support, ignore the overhang angle. // Enforce a full possible support, ignore the overhang angle.
0 : 0 :
(threshold_rad > 0. ? (threshold_rad > 0. ?
@ -424,9 +493,10 @@ PrintObjectSupportMaterial::MyLayersPtr PrintObjectSupportMaterial::top_contact_
// Overhang polygons for this layer and region. // Overhang polygons for this layer and region.
Polygons diff_polygons; Polygons diff_polygons;
if (lower_layer_offset == 0.) { if (lower_layer_offset == 0.) {
// Support everything.
diff_polygons = diff( diff_polygons = diff(
(Polygons)layerm.slices, (Polygons)layerm.slices,
(Polygons)lower_layer.slices); (Polygons)lower_layer.slices);
} else { } else {
// Get the regions needing a suport. // Get the regions needing a suport.
diff_polygons = diff( diff_polygons = diff(
@ -437,11 +507,19 @@ PrintObjectSupportMaterial::MyLayersPtr PrintObjectSupportMaterial::top_contact_
if (diff_polygons.empty()) if (diff_polygons.empty())
continue; continue;
// Offset the support regions back to a full overhang, restrict them to the full overhang. // Offset the support regions back to a full overhang, restrict them to the full overhang.
diff_polygons = intersection(offset(diff_polygons, lower_layer_offset), (Polygons)layerm.slices); diff_polygons = diff(intersection(offset(diff_polygons, lower_layer_offset), (Polygons)layerm.slices), (Polygons)lower_layer.slices);
} }
if (diff_polygons.empty()) if (diff_polygons.empty())
continue; continue;
#ifdef SLIC3R_DEBUG
{
::Slic3r::SVG svg(debug_out_path("support-top-contacts-raw-run%d-layer%d-region%d.svg", iRun, layer_id, it_layerm - layer.regions.begin()), get_extents(diff_polygons));
Slic3r::ExPolygons expolys = union_ex(diff_polygons, false);
svg.draw(expolys);
}
#endif /* SLIC3R_DEBUG */
if (m_object_config->dont_support_bridges) { if (m_object_config->dont_support_bridges) {
// compute the area of bridging perimeters // compute the area of bridging perimeters
// Note: this is duplicate code from GCode.pm, we need to refactor // Note: this is duplicate code from GCode.pm, we need to refactor
@ -452,16 +530,20 @@ PrintObjectSupportMaterial::MyLayersPtr PrintObjectSupportMaterial::top_contact_
coordf_t nozzle_diameter = m_print_config->nozzle_diameter.get_at( coordf_t nozzle_diameter = m_print_config->nozzle_diameter.get_at(
layerm.region()->config.perimeter_extruder-1); layerm.region()->config.perimeter_extruder-1);
Polygons lower_grown_slices = offset((Polygons)lower_layer.slices, +scale_(0.5*nozzle_diameter)); Polygons lower_grown_slices = offset((Polygons)lower_layer.slices, 0.5f*scale_(nozzle_diameter));
// TODO: split_at_first_point() could split a bridge mid-way // TODO: split_at_first_point() could split a bridge mid-way
Polylines overhang_perimeters; Polylines overhang_perimeters;
for (size_t i = 0; i < layerm.perimeters.entities.size(); ++ i) { for (ExtrusionEntitiesPtr::const_iterator it_island = layerm.perimeters.entities.begin(); it_island != layerm.perimeters.entities.end(); ++ it_island) {
ExtrusionEntity *entity = layerm.perimeters.entities[i]; const ExtrusionEntityCollection *island = dynamic_cast<ExtrusionEntityCollection*>(*it_island);
ExtrusionLoop *loop = dynamic_cast<Slic3r::ExtrusionLoop*>(entity); assert(island != NULL);
overhang_perimeters.push_back(loop ? for (size_t i = 0; i < island->entities.size(); ++ i) {
loop->as_polyline() : ExtrusionEntity *entity = island->entities[i];
dynamic_cast<const Slic3r::ExtrusionPath*>(entity)->polyline); ExtrusionLoop *loop = dynamic_cast<Slic3r::ExtrusionLoop*>(entity);
overhang_perimeters.push_back(loop ?
loop->as_polyline() :
dynamic_cast<const Slic3r::ExtrusionPath*>(entity)->polyline);
}
} }
// workaround for Clipper bug, see Slic3r::Polygon::clip_as_polyline() // workaround for Clipper bug, see Slic3r::Polygon::clip_as_polyline()
@ -484,7 +566,7 @@ PrintObjectSupportMaterial::MyLayersPtr PrintObjectSupportMaterial::top_contact_
// Offset a polyline into a polygon. // Offset a polyline into a polygon.
Polylines tmp; tmp.push_back(*it); Polylines tmp; tmp.push_back(*it);
Polygons out; Polygons out;
offset(tmp, &out, 0.5 * w + 10.); offset(tmp, &out, 0.5f * w + 10.f);
polygons_append(bridged_perimeters, out); polygons_append(bridged_perimeters, out);
} }
} }
@ -495,14 +577,10 @@ PrintObjectSupportMaterial::MyLayersPtr PrintObjectSupportMaterial::top_contact_
if (1) { if (1) {
// remove the entire bridges and only support the unsupported edges // remove the entire bridges and only support the unsupported edges
Polygons bridges; Polygons bridges;
for (Surfaces::const_iterator it = layerm.fill_surfaces.surfaces.begin(); it != layerm.fill_surfaces.surfaces.end(); ++ it) { for (Surfaces::const_iterator it = layerm.fill_surfaces.surfaces.begin(); it != layerm.fill_surfaces.surfaces.end(); ++ it)
if (it->surface_type == stBottomBridge && it->bridge_angle != -1) { if (it->surface_type == stBottomBridge && it->bridge_angle != -1)
bridges.push_back(it->expolygon.contour); polygons_append(bridges, it->expolygon);
bridges.insert(bridges.end(), it->expolygon.holes.begin(), it->expolygon.holes.end()); polygons_append(bridged_perimeters, bridges);
}
}
bridged_perimeters.insert(bridged_perimeters.end(), bridges.begin(), bridges.end());
diff_polygons = diff(diff_polygons, bridged_perimeters, true); diff_polygons = diff(diff_polygons, bridged_perimeters, true);
Polygons unsupported_bridge_polygons; Polygons unsupported_bridge_polygons;
@ -514,8 +592,7 @@ PrintObjectSupportMaterial::MyLayersPtr PrintObjectSupportMaterial::top_contact_
offset(tmp, &out, scale_(SUPPORT_MATERIAL_MARGIN)); offset(tmp, &out, scale_(SUPPORT_MATERIAL_MARGIN));
polygons_append(unsupported_bridge_polygons, out); polygons_append(unsupported_bridge_polygons, out);
} }
Polygons bridge_anchors = intersection(unsupported_bridge_polygons, bridges); polygons_append(diff_polygons, intersection(unsupported_bridge_polygons, bridges));
polygons_append(diff_polygons, bridge_anchors);
} else { } else {
// just remove bridged areas // just remove bridged areas
diff_polygons = diff(diff_polygons, layerm.bridged, true); diff_polygons = diff(diff_polygons, layerm.bridged, true);
@ -531,6 +608,14 @@ PrintObjectSupportMaterial::MyLayersPtr PrintObjectSupportMaterial::top_contact_
if (diff_polygons.empty()) if (diff_polygons.empty())
continue; continue;
#ifdef SLIC3R_DEBUG
{
::Slic3r::SVG svg(debug_out_path("support-top-contacts-filtered-run%d-layer%d-region%d.svg", iRun, layer_id, it_layerm - layer.regions.begin()), get_extents(diff_polygons));
Slic3r::ExPolygons expolys = union_ex(diff_polygons, false);
svg.draw(expolys);
}
#endif /* SLIC3R_DEBUG */
polygons_append(overhang_polygons, diff_polygons); polygons_append(overhang_polygons, diff_polygons);
// Let's define the required contact area by using a max gap of half the upper // Let's define the required contact area by using a max gap of half the upper
@ -586,12 +671,12 @@ PrintObjectSupportMaterial::MyLayersPtr PrintObjectSupportMaterial::top_contact_
size_t n_nozzle_dmrs = 0; size_t n_nozzle_dmrs = 0;
for (LayerRegionPtrs::const_iterator it_region_ptr = layer.regions.begin(); it_region_ptr != layer.regions.end(); ++ it_region_ptr) { for (LayerRegionPtrs::const_iterator it_region_ptr = layer.regions.begin(); it_region_ptr != layer.regions.end(); ++ it_region_ptr) {
const PrintRegion &region = *(*it_region_ptr)->region(); const PrintRegion &region = *(*it_region_ptr)->region();
nozzle_dmr += m_print_config->nozzle_diameter.get_at(region.config.perimeter_extruder-1); nozzle_dmr += m_print_config->nozzle_diameter.get_at(region.config.perimeter_extruder.value - 1);
nozzle_dmr += m_print_config->nozzle_diameter.get_at(region.config.infill_extruder-1); nozzle_dmr += m_print_config->nozzle_diameter.get_at(region.config.infill_extruder.value - 1);
nozzle_dmr += m_print_config->nozzle_diameter.get_at(region.config.solid_infill_extruder-1); nozzle_dmr += m_print_config->nozzle_diameter.get_at(region.config.solid_infill_extruder.value - 1);
n_nozzle_dmrs += 3; n_nozzle_dmrs += 3;
} }
nozzle_dmr /= n_nozzle_dmrs; nozzle_dmr /= coordf_t(n_nozzle_dmrs);
new_layer.print_z = layer.print_z - nozzle_dmr - m_object_config->support_material_contact_distance; new_layer.print_z = layer.print_z - nozzle_dmr - m_object_config->support_material_contact_distance;
// Don't know the height of the top contact layer yet. The top contact layer is printed with a normal flow and // Don't know the height of the top contact layer yet. The top contact layer is printed with a normal flow and
// its height will be set adaptively later on. // its height will be set adaptively later on.
@ -632,7 +717,7 @@ PrintObjectSupportMaterial::MyLayersPtr PrintObjectSupportMaterial::bottom_conta
// find object top surfaces // find object top surfaces
// we'll use them to clip our support and detect where does it stick // we'll use them to clip our support and detect where does it stick
MyLayersPtr bottom_contacts; MyLayersPtr bottom_contacts;
if (! m_object_config->support_material_buildplate_only && ! top_contacts.empty()) if (! m_object_config->support_material_buildplate_only.value && ! top_contacts.empty())
{ {
// Sum of unsupported contact areas above the current layer.print_z. // Sum of unsupported contact areas above the current layer.print_z.
Polygons projection; Polygons projection;
@ -840,7 +925,7 @@ void PrintObjectSupportMaterial::generate_base_layers(
-- idx_top_contact_overlapping; -- idx_top_contact_overlapping;
// Collect all the top_contact layer intersecting with this layer. // Collect all the top_contact layer intersecting with this layer.
for (int i = idx_top_contact_overlapping; i >= 0; -- i) { for (int i = idx_top_contact_overlapping; i >= 0; -- i) {
MyLayer &layer_top_overlapping = *top_contacts[idx_top_contact_overlapping]; MyLayer &layer_top_overlapping = *top_contacts[i];
if (layer_top_overlapping.print_z < layer_intermediate.bottom_z - overlap_extra_below) if (layer_top_overlapping.print_z < layer_intermediate.bottom_z - overlap_extra_below)
break; break;
polygons_append(polygons_trimming, layer_top_overlapping.polygons); polygons_append(polygons_trimming, layer_top_overlapping.polygons);
@ -885,6 +970,17 @@ void PrintObjectSupportMaterial::generate_base_layers(
*/ */
} }
#ifdef SLIC3R_DEBUG
static int iRun = 0;
iRun ++;
for (MyLayersPtr::const_iterator it = top_contacts.begin(); it != top_contacts.end(); ++ it) {
const MyLayer &layer = *(*it);
::Slic3r::SVG svg(debug_out_path("support-intermediate-layers-untrimmed-%d-%lf.svg", iRun, layer.print_z), get_extents(layer.polygons));
Slic3r::ExPolygons expolys = union_ex(layer.polygons, false);
svg.draw(expolys);
}
#endif /* SLIC3R_DEBUG */
//FIXME This could be parallelized. //FIXME This could be parallelized.
const coordf_t gap_extra_above = 0.1f; const coordf_t gap_extra_above = 0.1f;
const coordf_t gap_extra_below = 0.1f; const coordf_t gap_extra_below = 0.1f;
@ -924,13 +1020,13 @@ Polygons PrintObjectSupportMaterial::generate_raft_base(
MyLayersPtr &intermediate_layers) const MyLayersPtr &intermediate_layers) const
{ {
assert(! bottom_contacts.empty()); assert(! bottom_contacts.empty());
MyLayer &contacts = *bottom_contacts.front();
MyLayer &columns_base = *intermediate_layers.front();
Polygons raft_polygons; Polygons raft_polygons;
#if 0 #if 0
const float inflate_factor = scale_(3.); const float inflate_factor = scale_(3.);
if (this->has_raft()) { if (this->has_raft()) {
MyLayer &contacts = *bottom_contacts.front();
MyLayer &columns_base = *intermediate_layers.front();
if (m_num_base_raft_layers == 0 && m_num_interface_raft_layers == 0 && m_num_contact_raft_layers == 1) { if (m_num_base_raft_layers == 0 && m_num_interface_raft_layers == 0 && m_num_contact_raft_layers == 1) {
// Having only the contact layer, which has the height of the 1st layer. // Having only the contact layer, which has the height of the 1st layer.
// We are free to merge the contacts with the columns_base, they will be printed the same way. // We are free to merge the contacts with the columns_base, they will be printed the same way.
@ -948,6 +1044,7 @@ Polygons PrintObjectSupportMaterial::generate_raft_base(
} else { } else {
// No raft. The 1st intermediate layer contains the bases of the support columns. // No raft. The 1st intermediate layer contains the bases of the support columns.
// Expand the polygons, but trim with the object. // Expand the polygons, but trim with the object.
MyLayer &columns_base = *intermediate_layers.front();
columns_base.polygons = diff( columns_base.polygons = diff(
offset(columns_base.polygons, inflate_factor), offset(columns_base.polygons, inflate_factor),
offset(m_object->get_layer(0), safety_factor); offset(m_object->get_layer(0), safety_factor);

View File

@ -43,7 +43,8 @@ public:
height(0.), height(0.),
idx_object_layer_above(size_t(-1)), idx_object_layer_above(size_t(-1)),
idx_object_layer_below(size_t(-1)), idx_object_layer_below(size_t(-1)),
bridging(false) bridging(false),
aux_polygons(NULL)
{} {}
~MyLayer() ~MyLayer()

View File

@ -40,6 +40,20 @@ public:
: surface_type(_surface_type), expolygon(_expolygon), : surface_type(_surface_type), expolygon(_expolygon),
thickness(-1), thickness_layers(1), bridge_angle(-1), extra_perimeters(0) thickness(-1), thickness_layers(1), bridge_angle(-1), extra_perimeters(0)
{}; {};
Surface(const Surface &other, const ExPolygon &_expolygon)
: surface_type(other.surface_type), expolygon(_expolygon),
thickness(other.thickness), thickness_layers(other.thickness_layers), bridge_angle(other.bridge_angle), extra_perimeters(other.extra_perimeters)
{};
#if SLIC3R_CPPVER >= 11
Surface(SurfaceType _surface_type, const ExPolygon &&_expolygon)
: surface_type(_surface_type), expolygon(std::move(_expolygon)),
thickness(-1), thickness_layers(1), bridge_angle(-1), extra_perimeters(0)
{};
Surface(const Surface &other, const ExPolygon &&_expolygon)
: surface_type(other.surface_type), expolygon(std::move(_expolygon)),
thickness(other.thickness), thickness_layers(other.thickness_layers), bridge_angle(other.bridge_angle), extra_perimeters(other.extra_perimeters)
{};
#endif
operator Polygons() const; operator Polygons() const;
double area() const; double area() const;
bool is_solid() const; bool is_solid() const;
@ -52,22 +66,43 @@ public:
typedef std::vector<Surface> Surfaces; typedef std::vector<Surface> Surfaces;
typedef std::vector<Surface*> SurfacesPtr; typedef std::vector<Surface*> SurfacesPtr;
inline Polygons to_polygons(const SurfacesPtr &src) inline Polygons to_polygons(const Surfaces &src)
{ {
size_t num = 0;
for (Surfaces::const_iterator it = src.begin(); it != src.end(); ++it)
num += it->expolygon.holes.size() + 1;
Polygons polygons; Polygons polygons;
for (SurfacesPtr::const_iterator it = src.begin(); it != src.end(); ++it) { polygons.reserve(num);
polygons.push_back((*it)->expolygon.contour); for (Surfaces::const_iterator it = src.begin(); it != src.end(); ++it) {
for (Polygons::const_iterator ith = (*it)->expolygon.holes.begin(); ith != (*it)->expolygon.holes.end(); ++ith) { polygons.push_back(it->expolygon.contour);
for (Polygons::const_iterator ith = it->expolygon.holes.begin(); ith != it->expolygon.holes.end(); ++ith)
polygons.push_back(*ith); polygons.push_back(*ith);
}
} }
return polygons; return polygons;
} }
#if SLIC3R_CPPVER > 11 inline Polygons to_polygons(const SurfacesPtr &src)
{
size_t num = 0;
for (SurfacesPtr::const_iterator it = src.begin(); it != src.end(); ++it)
num += (*it)->expolygon.holes.size() + 1;
Polygons polygons;
polygons.reserve(num);
for (SurfacesPtr::const_iterator it = src.begin(); it != src.end(); ++it) {
polygons.push_back((*it)->expolygon.contour);
for (Polygons::const_iterator ith = (*it)->expolygon.holes.begin(); ith != (*it)->expolygon.holes.end(); ++ith)
polygons.push_back(*ith);
}
return polygons;
}
#if SLIC3R_CPPVER >= 11
inline Polygons to_polygons(SurfacesPtr &&src) inline Polygons to_polygons(SurfacesPtr &&src)
{ {
for (SurfacesPtr::const_iterator it = src.begin(); it != src.end(); ++it)
num += (*it)->expolygon.holes.size() + 1;
Polygons polygons; Polygons polygons;
polygons.reserve(num);
for (ExPolygons::const_iterator it = src.begin(); it != src.end(); ++it) { for (ExPolygons::const_iterator it = src.begin(); it != src.end(); ++it) {
polygons.push_back(std::move((*it)->expolygon.contour)); polygons.push_back(std::move((*it)->expolygon.contour));
for (Polygons::const_iterator ith = (*it)->expolygon.holes.begin(); ith != (*it)->expolygon.holes.end(); ++ith) { for (Polygons::const_iterator ith = (*it)->expolygon.holes.begin(); ith != (*it)->expolygon.holes.end(); ++ith) {
@ -78,6 +113,94 @@ inline Polygons to_polygons(SurfacesPtr &&src)
} }
#endif #endif
// Count a nuber of polygons stored inside the vector of expolygons.
// Useful for allocating space for polygons when converting expolygons to polygons.
inline size_t number_polygons(const Surfaces &surfaces)
{
size_t n_polygons = 0;
for (Surfaces::const_iterator it = surfaces.begin(); it != surfaces.end(); ++ it)
n_polygons += it->expolygon.holes.size() + 1;
return n_polygons;
}
inline size_t number_polygons(const SurfacesPtr &surfaces)
{
size_t n_polygons = 0;
for (SurfacesPtr::const_iterator it = surfaces.begin(); it != surfaces.end(); ++ it)
n_polygons += (*it)->expolygon.holes.size() + 1;
return n_polygons;
}
// Append a vector of Surfaces at the end of another vector of polygons.
inline void polygons_append(Polygons &dst, const Surfaces &src)
{
dst.reserve(dst.size() + number_polygons(src));
for (Surfaces::const_iterator it = src.begin(); it != src.end(); ++ it) {
dst.push_back(it->expolygon.contour);
dst.insert(dst.end(), it->expolygon.holes.begin(), it->expolygon.holes.end());
}
}
#if SLIC3R_CPPVER >= 11
inline void polygons_append(Polygons &dst, Surfaces &&src)
{
dst.reserve(dst.size() + number_polygons(src));
for (Surfaces::const_iterator it = src.begin(); it != src.end(); ++ it) {
dst.push_back(std::move(it->expolygon.contour));
std::move(std::begin(it->expolygon.contour), std::end(it->expolygon.contour), std::back_inserter(dst));
}
}
#endif
// Append a vector of Surfaces at the end of another vector of polygons.
inline void polygons_append(Polygons &dst, const SurfacesPtr &src)
{
dst.reserve(dst.size() + number_polygons(src));
for (SurfacesPtr::const_iterator it = src.begin(); it != src.end(); ++ it) {
dst.push_back((*it)->expolygon.contour);
dst.insert(dst.end(), (*it)->expolygon.holes.begin(), (*it)->expolygon.holes.end());
}
}
#if SLIC3R_CPPVER >= 11
inline void polygons_append(Polygons &dst, SurfacesPtr &&src)
{
dst.reserve(dst.size() + number_polygons(src));
for (SurfacesPtr::const_iterator it = src.begin(); it != src.end(); ++ it) {
dst.push_back(std::move((*it)->expolygon.contour));
std::move(std::begin((*it)->expolygon.contour), std::end((*it)->expolygon.contour), std::back_inserter(dst));
}
}
#endif
// Append a vector of Surfaces at the end of another vector of polygons.
inline void surfaces_append(Surfaces &dst, const ExPolygons &src, SurfaceType surfaceType)
{
dst.reserve(dst.size() + src.size());
for (ExPolygons::const_iterator it = src.begin(); it != src.end(); ++ it)
dst.push_back(Surface(surfaceType, *it));
}
inline void surfaces_append(Surfaces &dst, const ExPolygons &src, const Surface &surfaceTempl)
{
dst.reserve(dst.size() + number_polygons(src));
for (ExPolygons::const_iterator it = src.begin(); it != src.end(); ++ it)
dst.push_back(Surface(surfaceTempl, *it));
}
#if SLIC3R_CPPVER >= 11
inline void surfaces_append(Surfaces &dst, ExPolygons &&src, SurfaceType surfaceType)
{
dst.reserve(dst.size() + src.size());
for (ExPolygons::const_iterator it = src.begin(); it != src.end(); ++ it)
dst.push_back(Surface(surfaceType, std::move(*it)));
}
inline void surfaces_append(Surfaces &dst, ExPolygons &&src, const Surface &surfaceTempl)
{
dst.reserve(dst.size() + number_polygons(src));
for (ExPolygons::const_iterator it = src.begin(); it != src.end(); ++ it)
dst.push_back(Surface(surfaceTempl, std::move(*it)));
}
#endif
extern BoundingBox get_extents(const Surface &surface); extern BoundingBox get_extents(const Surface &surface);
extern BoundingBox get_extents(const Surfaces &surfaces); extern BoundingBox get_extents(const Surfaces &surfaces);
extern BoundingBox get_extents(const SurfacesPtr &surfaces); extern BoundingBox get_extents(const SurfacesPtr &surfaces);

View File

@ -29,7 +29,7 @@ class SurfaceCollection
void remove_types(const SurfaceType *types, int ntypes); void remove_types(const SurfaceType *types, int ntypes);
void filter_by_type(SurfaceType type, Polygons* polygons); void filter_by_type(SurfaceType type, Polygons* polygons);
void append(const SurfaceCollection &coll); void append(const SurfaceCollection &coll);
void append(const SurfaceType surfaceType, const Slic3r::ExPolygons &expoly); void append(const SurfaceType surfaceType, const ExPolygons &expoly);
// For debugging purposes: // For debugging purposes:
void export_to_svg(const char *path, bool show_labels); void export_to_svg(const char *path, bool show_labels);

View File

@ -475,7 +475,7 @@ TriangleMeshSlicer::slice(const std::vector<float> &z, std::vector<Polygons>* la
for (std::vector<IntersectionLines>::iterator it = lines.begin(); it != lines.end(); ++it) { for (std::vector<IntersectionLines>::iterator it = lines.begin(); it != lines.end(); ++it) {
size_t layer_idx = it - lines.begin(); size_t layer_idx = it - lines.begin();
#ifdef SLIC3R_TRIANGLEMESH_DEBUG #ifdef SLIC3R_TRIANGLEMESH_DEBUG
printf("Layer %zu:\n", layer_idx); printf("Layer " PRINTF_ZU ":\n", layer_idx);
#endif #endif
this->make_loops(*it, &(*layers)[layer_idx]); this->make_loops(*it, &(*layers)[layer_idx]);
} }
@ -491,7 +491,7 @@ TriangleMeshSlicer::slice(const std::vector<float> &z, std::vector<ExPolygons>*
for (std::vector<Polygons>::const_iterator loops = layers_p.begin(); loops != layers_p.end(); ++loops) { for (std::vector<Polygons>::const_iterator loops = layers_p.begin(); loops != layers_p.end(); ++loops) {
#ifdef SLIC3R_TRIANGLEMESH_DEBUG #ifdef SLIC3R_TRIANGLEMESH_DEBUG
size_t layer_id = loops - layers_p.begin(); size_t layer_id = loops - layers_p.begin();
printf("Layer %zu (slice_z = %.2f):\n", layer_id, z[layer_id]); printf("Layer " PRINTF_ZU " (slice_z = %.2f):\n", layer_id, z[layer_id]);
#endif #endif
this->make_expolygons(*loops, &(*layers)[ loops - layers_p.begin() ]); this->make_expolygons(*loops, &(*layers)[ loops - layers_p.begin() ]);
@ -839,7 +839,7 @@ TriangleMeshSlicer::make_expolygons(const Polygons &loops, ExPolygons* slices)
for (ExPolygons::const_iterator e = ex_slices.begin(); e != ex_slices.end(); ++e) { for (ExPolygons::const_iterator e = ex_slices.begin(); e != ex_slices.end(); ++e) {
holes_count += e->holes.size(); holes_count += e->holes.size();
} }
printf("%zu surface(s) having %zu holes detected from %zu polylines\n", printf(PRINTF_ZU " surface(s) having " PRINTF_ZU " holes detected from " PRINTF_ZU " polylines\n",
ex_slices.size(), holes_count, loops.size()); ex_slices.size(), holes_count, loops.size());
#endif #endif

View File

@ -78,6 +78,13 @@ inline std::string debug_out_path(const char *name, ...)
return std::string(SLIC3R_DEBUG_OUT_PATH_PREFIX) + std::string(buffer); return std::string(SLIC3R_DEBUG_OUT_PATH_PREFIX) + std::string(buffer);
} }
#ifdef _MSC_VER
// Visual Studio older than 2015 does not support the prinf type specifier %zu. Use %Iu instead.
#define PRINTF_ZU "%Iu"
#else
#define PRINTF_ZU "%zu"
#endif
// Write slices as SVG images into out directory during the 2D processing of the slices. // Write slices as SVG images into out directory during the 2D processing of the slices.
// #define SLIC3R_DEBUG_SLICE_PROCESSING // #define SLIC3R_DEBUG_SLICE_PROCESSING

View File

@ -5,7 +5,6 @@ use warnings;
use Slic3r::XS; use Slic3r::XS;
use Test::More tests => 146; use Test::More tests => 146;
use Data::Dumper;
foreach my $config (Slic3r::Config->new, Slic3r::Config::Static::new_FullPrintConfig) { foreach my $config (Slic3r::Config->new, Slic3r::Config::Static::new_FullPrintConfig) {
$config->set('layer_height', 0.3); $config->set('layer_height', 0.3);

View File

@ -11,8 +11,7 @@
Clone<ExtrusionEntityCollection> clone() Clone<ExtrusionEntityCollection> clone()
%code{% RETVAL = THIS->clone(); %}; %code{% RETVAL = THIS->clone(); %};
void reverse(); void reverse();
void clear() void clear();
%code{% THIS->entities.clear(); %};
ExtrusionEntityCollection* chained_path(bool no_reverse) ExtrusionEntityCollection* chained_path(bool no_reverse)
%code{% %code{%
RETVAL = new ExtrusionEntityCollection(); RETVAL = new ExtrusionEntityCollection();

View File

@ -4,6 +4,8 @@
#include <xsinit.h> #include <xsinit.h>
#include "libslic3r/Fill/Fill.hpp" #include "libslic3r/Fill/Fill.hpp"
#include "libslic3r/PolylineCollection.hpp" #include "libslic3r/PolylineCollection.hpp"
#include "libslic3r/ExtrusionEntity.hpp"
#include "libslic3r/ExtrusionEntityCollection.hpp"
%} %}
%name{Slic3r::Filler} class Filler { %name{Slic3r::Filler} class Filler {
@ -63,5 +65,13 @@ new_from_type(CLASS, type)
OUTPUT: OUTPUT:
RETVAL RETVAL
void
make_fill(CLASS, layer_region, out_append)
char* CLASS;
LayerRegion* layer_region;
ExtrusionEntityCollection* out_append;
CODE:
make_fill(*layer_region, *out_append);
%} %}
}; };

View File

@ -96,6 +96,7 @@
bool any_bottom_region_slice_contains_polyline(Polyline* polyline) bool any_bottom_region_slice_contains_polyline(Polyline* polyline)
%code%{ RETVAL = THIS->any_bottom_region_slice_contains(*polyline); %}; %code%{ RETVAL = THIS->any_bottom_region_slice_contains(*polyline); %};
void make_perimeters(); void make_perimeters();
void make_fills();
void export_region_slices_to_svg(const char *path); void export_region_slices_to_svg(const char *path);
void export_region_fill_surfaces_to_svg(const char *path); void export_region_fill_surfaces_to_svg(const char *path);