Perl unit tests for perimeters and multi-material were rewritten to C++.

Perl binding was slimmed down, namely Clipper is no more linked by Perl.
This commit is contained in:
Vojtech Bubnik 2022-05-04 15:05:56 +02:00
parent 7380787b3a
commit a627614b58
48 changed files with 1194 additions and 2310 deletions

View File

@ -28,11 +28,6 @@ BEGIN {
use FindBin;
# Let the XS module know where the GUI resources reside.
set_resources_dir(decode_path($FindBin::Bin) . (($^O eq 'darwin') ? '/../Resources' : '/resources'));
set_var_dir(resources_dir() . "/icons");
set_local_dir(resources_dir() . "/localization/");
use Moo 1.003001;
use Slic3r::XS; # import all symbols (constants etc.) before they get parsed
@ -60,82 +55,4 @@ use constant SCALING_FACTOR => 0.000001;
$Slic3r::loglevel = (defined($ENV{'SLIC3R_LOGLEVEL'}) && $ENV{'SLIC3R_LOGLEVEL'} =~ /^[1-9]/) ? $ENV{'SLIC3R_LOGLEVEL'} : 0;
set_logging_level($Slic3r::loglevel);
# Let the palceholder parser evaluate one expression to initialize its local static macro_processor
# class instance in a thread safe manner.
Slic3r::GCode::PlaceholderParser->new->evaluate_boolean_expression('1==1');
# Open a file by converting $filename to local file system locales.
sub open {
my ($fh, $mode, $filename) = @_;
return CORE::open $$fh, $mode, encode_path($filename);
}
sub tags {
my ($format) = @_;
$format //= '';
my %tags;
# End of line
$tags{eol} = ($format eq 'html') ? '<br>' : "\n";
# Heading
$tags{h2start} = ($format eq 'html') ? '<b>' : '';
$tags{h2end} = ($format eq 'html') ? '</b>' : '';
# Bold font
$tags{bstart} = ($format eq 'html') ? '<b>' : '';
$tags{bend} = ($format eq 'html') ? '</b>' : '';
# Verbatim
$tags{vstart} = ($format eq 'html') ? '<pre>' : '';
$tags{vend} = ($format eq 'html') ? '</pre>' : '';
return %tags;
}
sub slic3r_info
{
my (%params) = @_;
my %tag = Slic3r::tags($params{format});
my $out = '';
$out .= "$tag{bstart}$Slic3r::FORK_NAME$tag{bend}$tag{eol}";
$out .= "$tag{bstart}Version: $tag{bend}$Slic3r::VERSION$tag{eol}";
$out .= "$tag{bstart}Build: $tag{bend}$Slic3r::BUILD$tag{eol}";
return $out;
}
sub copyright_info
{
my (%params) = @_;
my %tag = Slic3r::tags($params{format});
my $out =
'Copyright &copy; 2016 Vojtech Bubnik, Prusa Research. <br />' .
'Copyright &copy; 2011-2016 Alessandro Ranellucci. <br />' .
'<a href="http://slic3r.org/">Slic3r</a> is licensed under the ' .
'<a href="http://www.gnu.org/licenses/agpl-3.0.html">GNU Affero General Public License, version 3</a>.' .
'<br /><br /><br />' .
'Contributions by Henrik Brix Andersen, Nicolas Dandrimont, Mark Hindess, Petr Ledvina, Y. Sapir, Mike Sheldrake and numerous others. ' .
'Manual by Gary Hodgson. Inspired by the RepRap community. <br />' .
'Slic3r logo designed by Corey Daniels, <a href="http://www.famfamfam.com/lab/icons/silk/">Silk Icon Set</a> designed by Mark James. ';
return $out;
}
sub system_info
{
my (%params) = @_;
my %tag = Slic3r::tags($params{format});
my $out = '';
$out .= "$tag{bstart}Operating System: $tag{bend}$Config{osname}$tag{eol}";
$out .= "$tag{bstart}System Architecture: $tag{bend}$Config{archname}$tag{eol}";
if ($^O eq 'MSWin32') {
$out .= "$tag{bstart}Windows Version: $tag{bend}" . `ver` . $tag{eol};
} else {
# Hopefully some kind of unix / linux.
$out .= "$tag{bstart}System Version: $tag{bend}" . `uname -a` . $tag{eol};
}
$out .= $tag{vstart} . Config::myconfig . $tag{vend};
$out .= " $tag{bstart}\@INC:$tag{bend}$tag{eol}$tag{vstart}";
foreach my $i (@INC) {
$out .= " $i\n";
}
$out .= "$tag{vend}";
return $out;
}
1;

View File

@ -23,47 +23,6 @@ our $Options = print_config_def();
}
}
# From command line parameters, used by slic3r.pl
sub new_from_cli {
my $class = shift;
my %args = @_;
# Delete hash keys with undefined value.
delete $args{$_} for grep !defined $args{$_}, keys %args;
# Replace the start_gcode, end_gcode ... hash values
# with the content of the files they reference.
for (qw(start end layer toolchange)) {
my $opt_key = "${_}_gcode";
if ($args{$opt_key}) {
if (-e $args{$opt_key}) {
Slic3r::open(\my $fh, "<", $args{$opt_key})
or die "Failed to open $args{$opt_key}\n";
binmode $fh, ':utf8';
$args{$opt_key} = do { local $/; <$fh> };
close $fh;
}
}
}
my $self = $class->new;
foreach my $opt_key (keys %args) {
my $opt_def = $Options->{$opt_key};
# we use set_deserialize() for bool options since GetOpt::Long doesn't handle
# arrays of boolean values
if ($opt_key =~ /^(?:bed_shape|duplicate_grid|extruder_offset)$/ || $opt_def->{type} eq 'bool') {
$self->set_deserialize($opt_key, $args{$opt_key});
} elsif (my $shortcut = $opt_def->{shortcut}) {
$self->set($_, $args{$opt_key}) for @$shortcut;
} else {
$self->set($opt_key, $args{$opt_key});
}
}
return $self;
}
package Slic3r::Config::Static;
use parent 'Slic3r::Config';

View File

@ -4,13 +4,6 @@ use warnings;
# an ExPolygon is a polygon with holes
sub noncollapsing_offset_ex {
my $self = shift;
my ($distance, @params) = @_;
return $self->offset_ex($distance + 1, @params);
}
sub bounding_box {
my $self = shift;
return $self->contour->bounding_box;

View File

@ -1,13 +0,0 @@
package Slic3r::Geometry::Clipper;
use strict;
use warnings;
require Exporter;
our @ISA = qw(Exporter);
our @EXPORT_OK = qw(
offset
offset2_ex
diff_ex diff union_ex
union);
1;

View File

@ -31,7 +31,4 @@ sub regions {
return [ map $self->get_region($_), 0..($self->region_count-1) ];
}
package Slic3r::Layer::Support;
our @ISA = qw(Slic3r::Layer);
1;

View File

@ -5,9 +5,4 @@ use warnings;
# a line is a two-points line
use parent 'Slic3r::Polyline';
sub grow {
my $self = shift;
return Slic3r::Polyline->new(@$self)->grow(@_);
}
1;

View File

@ -133,11 +133,4 @@ sub add_instance {
}
}
sub mesh_stats {
my $self = shift;
# TODO: sum values from all volumes
return $self->volumes->[0]->mesh->stats;
}
1;

View File

@ -5,9 +5,4 @@ use warnings;
# a polygon is a closed polyline.
use parent 'Slic3r::Polyline';
sub grow {
my $self = shift;
return $self->split_at_first_point->grow(@_);
}
1;

View File

@ -5,7 +5,6 @@ use warnings;
use List::Util qw(min max sum first);
use Slic3r::Flow ':roles';
use Slic3r::Print::State ':steps';
use Slic3r::Surface ':types';
sub layers {
@ -13,9 +12,4 @@ sub layers {
return [ map $self->get_layer($_), 0..($self->layer_count - 1) ];
}
sub support_layers {
my $self = shift;
return [ map $self->get_support_layer($_), 0..($self->support_layer_count - 1) ];
}
1;

View File

@ -1,12 +0,0 @@
# Wraps C++ enums Slic3r::PrintStep and Slic3r::PrintObjectStep
package Slic3r::Print::State;
use strict;
use warnings;
require Exporter;
our @ISA = qw(Exporter);
our @EXPORT_OK = qw(STEP_SLICE STEP_PERIMETERS STEP_PREPARE_INFILL
STEP_INFILL STEP_SUPPORTMATERIAL STEP_SKIRT STEP_BRIM STEP_WIPE_TOWER);
our %EXPORT_TAGS = (steps => \@EXPORT_OK);
1;

View File

@ -215,9 +215,9 @@ bool GCodeReader::parse_file_raw(const std::string &filename, raw_line_callback_
[](size_t){});
}
bool GCodeReader::GCodeLine::has(char axis) const
const char* GCodeReader::axis_pos(const char *raw_str, char axis)
{
const char *c = m_raw.c_str();
const char *c = raw_str;
// Skip the whitespaces.
c = skip_whitespaces(c);
// Skip the command.
@ -230,29 +230,25 @@ bool GCodeReader::GCodeLine::has(char axis) const
break;
// Check the name of the axis.
if (*c == axis)
return true;
return c;
// Skip the rest of the word.
c = skip_word(c);
}
return false;
return nullptr;
}
bool GCodeReader::GCodeLine::has(char axis) const
{
const char *c = axis_pos(m_raw.c_str(), axis);
return c != nullptr;
}
bool GCodeReader::GCodeLine::has_value(char axis, float &value) const
{
assert(is_decimal_separator_point());
const char *c = m_raw.c_str();
// Skip the whitespaces.
c = skip_whitespaces(c);
// Skip the command.
c = skip_word(c);
// Up to the end of line or comment.
while (! is_end_of_gcode_line(*c)) {
// Skip whitespaces.
c = skip_whitespaces(c);
if (is_end_of_gcode_line(*c))
break;
// Check the name of the axis.
if (*c == axis) {
const char *c = axis_pos(m_raw.c_str(), axis);
if (c == nullptr)
return false;
// Try to parse the numeric value.
char *pend = nullptr;
double v = strtod(++ c, &pend);
@ -261,9 +257,21 @@ bool GCodeReader::GCodeLine::has_value(char axis, float &value) const
value = float(v);
return true;
}
return false;
}
// Skip the rest of the word.
c = skip_word(c);
bool GCodeReader::GCodeLine::has_value(char axis, int &value) const
{
const char *c = axis_pos(m_raw.c_str(), axis);
if (c == nullptr)
return false;
// Try to parse the numeric value.
char *pend = nullptr;
long v = strtol(++ c, &pend, 10);
if (pend != nullptr && is_end_of_word(*pend)) {
// The axis value has been parsed correctly.
value = int(v);
return true;
}
return false;
}

View File

@ -30,6 +30,7 @@ public:
float value(Axis axis) const { return m_axis[axis]; }
bool has(char axis) const;
bool has_value(char axis, float &value) const;
bool has_value(char axis, int &value) const;
float new_X(const GCodeReader &reader) const { return this->has(X) ? this->x() : reader.x(); }
float new_Y(const GCodeReader &reader) const { return this->has(Y) ? this->y() : reader.y(); }
float new_Z(const GCodeReader &reader) const { return this->has(Z) ? this->z() : reader.z(); }
@ -166,6 +167,7 @@ private:
; // silence -Wempty-body
return c;
}
static const char* axis_pos(const char *raw_str, char axis);
GCodeConfig m_config;
char m_extrusion_axis;

View File

@ -196,7 +196,7 @@ BoundingBox get_extents(const Polylines &polylines)
const Point& leftmost_point(const Polylines &polylines)
{
if (polylines.empty())
throw Slic3r::InvalidArgument("leftmost_point() called on empty PolylineCollection");
throw Slic3r::InvalidArgument("leftmost_point() called on empty Polylines");
Polylines::const_iterator it = polylines.begin();
const Point *p = &it->leftmost_point();
for (++ it; it != polylines.end(); ++it) {

View File

@ -80,15 +80,6 @@ public:
inline bool operator==(const Polyline &lhs, const Polyline &rhs) { return lhs.points == rhs.points; }
inline bool operator!=(const Polyline &lhs, const Polyline &rhs) { return lhs.points != rhs.points; }
// Don't use this class in production code, it is used exclusively by the Perl binding for unit tests!
#ifdef PERL_UCHAR_MIN
class PolylineCollection
{
public:
Polylines polylines;
};
#endif /* PERL_UCHAR_MIN */
extern BoundingBox get_extents(const Polyline &polyline);
extern BoundingBox get_extents(const Polylines &polylines);

View File

@ -211,6 +211,16 @@ public:
DynamicPrintConfig& operator=(DynamicPrintConfig &&rhs) noexcept { DynamicConfig::operator=(std::move(rhs)); return *this; }
static DynamicPrintConfig full_print_config();
static DynamicPrintConfig full_print_config_with(const t_config_option_key &opt_key, const std::string &str, bool append = false) {
auto config = DynamicPrintConfig::full_print_config();
config.set_deserialize_strict(opt_key, str, append);
return config;
}
static DynamicPrintConfig full_print_config_with(std::initializer_list<SetDeserializeItem> items) {
auto config = DynamicPrintConfig::full_print_config();
config.set_deserialize_strict(items);
return config;
}
static DynamicPrintConfig* new_from_defaults_keys(const std::vector<std::string> &keys);
// Overrides ConfigBase::def(). Static configuration definition. Any value stored into this ConfigBase shall have its definition here.

View File

@ -18,7 +18,6 @@ namespace Slic3r {
extern void set_logging_level(unsigned int level);
extern unsigned get_logging_level();
extern void trace(unsigned int level, const char *message);
// Format memory allocated, separate thousands by comma.
extern std::string format_memsize_MB(size_t n);
// Return string to be added to the boost::log output to inform about the current process memory allocation.
@ -68,13 +67,6 @@ std::string debug_out_path(const char *name, ...);
// This type is only needed for Perl bindings to relay to Perl that the string is raw, not UTF-8 encoded.
typedef std::string local_encoded_string;
// Convert an UTF-8 encoded string into local coding.
// On Windows, the UTF-8 string is converted to a local 8-bit code page.
// On OSX and Linux, this function does no conversion and returns a copy of the source string.
extern local_encoded_string encode_path(const char *src);
extern std::string decode_path(const char *src);
extern std::string normalize_utf8_nfc(const char *src);
// Returns next utf8 sequence length. =number of bytes in string, that creates together one utf-8 character.
// Starting at pos. ASCII characters returns 1. Works also if pos is in the middle of the sequence.
extern size_t get_utf8_sequence_length(const std::string& text, size_t pos = 0);
@ -115,19 +107,6 @@ extern bool is_gallery_file(const boost::filesystem::directory_entry& path, char
extern bool is_gallery_file(const std::string& path, char const* type);
extern bool is_shapes_dir(const std::string& dir);
// File path / name / extension splitting utilities, working with UTF-8,
// to be published to Perl.
namespace PerlUtils {
// Get a file name including the extension.
extern std::string path_to_filename(const char *src);
// Get a file name without the extension.
extern std::string path_to_stem(const char *src);
// Get just the extension.
extern std::string path_to_extension(const char *src);
// Get a directory without the trailing slash.
extern std::string path_to_parent_path(const char *src);
};
std::string string_printf(const char *format, ...);
// Standard "generated by Slic3r version xxx timestamp xxx" header string,

View File

@ -125,14 +125,6 @@ static struct RunOnInit {
}
} g_RunOnInit;
void trace(unsigned int level, const char *message)
{
boost::log::trivial::severity_level severity = level_to_boost(level);
BOOST_LOG_STREAM_WITH_PARAMS(::boost::log::trivial::logger::get(),\
(::boost::log::keywords::severity = severity)) << message;
}
void disable_multi_threading()
{
// Disable parallelization so the Shiny profiler works
@ -820,49 +812,6 @@ bool is_shapes_dir(const std::string& dir)
namespace Slic3r {
// Encode an UTF-8 string to the local code page.
std::string encode_path(const char *src)
{
#ifdef WIN32
// Convert the source utf8 encoded string to a wide string.
std::wstring wstr_src = boost::nowide::widen(src);
if (wstr_src.length() == 0)
return std::string();
// Convert a wide string to a local code page.
int size_needed = ::WideCharToMultiByte(0, 0, wstr_src.data(), (int)wstr_src.size(), nullptr, 0, nullptr, nullptr);
std::string str_dst(size_needed, 0);
::WideCharToMultiByte(0, 0, wstr_src.data(), (int)wstr_src.size(), str_dst.data(), size_needed, nullptr, nullptr);
return str_dst;
#else /* WIN32 */
return src;
#endif /* WIN32 */
}
// Encode an 8-bit string from a local code page to UTF-8.
// Multibyte to utf8
std::string decode_path(const char *src)
{
#ifdef WIN32
int len = int(strlen(src));
if (len == 0)
return std::string();
// Convert the string encoded using the local code page to a wide string.
int size_needed = ::MultiByteToWideChar(0, 0, src, len, nullptr, 0);
std::wstring wstr_dst(size_needed, 0);
::MultiByteToWideChar(0, 0, src, len, wstr_dst.data(), size_needed);
// Convert a wide string to utf8.
return boost::nowide::narrow(wstr_dst.c_str());
#else /* WIN32 */
return src;
#endif /* WIN32 */
}
std::string normalize_utf8_nfc(const char *src)
{
static std::locale locale_utf8(boost::locale::generator().generate(""));
return boost::locale::normalize(src, boost::locale::norm_nfc, locale_utf8);
}
size_t get_utf8_sequence_length(const std::string& text, size_t pos)
{
assert(pos < text.size());
@ -933,18 +882,6 @@ size_t get_utf8_sequence_length(const char *seq, size_t size)
return length;
}
namespace PerlUtils {
// Get a file name including the extension.
std::string path_to_filename(const char *src) { return boost::filesystem::path(src).filename().string(); }
// Get a file name without the extension.
std::string path_to_stem(const char *src) { return boost::filesystem::path(src).stem().string(); }
// Get just the extension.
std::string path_to_extension(const char *src) { return boost::filesystem::path(src).extension().string(); }
// Get a directory without the trailing slash.
std::string path_to_parent_path(const char *src) { return boost::filesystem::path(src).parent_path().string(); }
};
std::string string_printf(const char *format, ...)
{
va_list args1;

View File

@ -1,93 +0,0 @@
use Test::More;
use strict;
use warnings;
plan skip_all => 'variable-width paths are currently disabled';
plan tests => 20;
BEGIN {
use FindBin;
use lib "$FindBin::Bin/../lib";
use local::lib "$FindBin::Bin/../local-lib";
}
use List::Util qw(first);
use Slic3r;
use Slic3r::Geometry qw(X Y scale epsilon);
use Slic3r::Surface ':types';
sub scale_points (@) { map [scale $_->[X], scale $_->[Y]], @_ }
{
my $square = Slic3r::ExPolygon->new([
scale_points [0,0], [10,0], [10,10], [0,10],
]);
my @offsets = @{$square->noncollapsing_offset_ex(- scale 5)};
is scalar @offsets, 1, 'non-collapsing offset';
}
{
local $Slic3r::Config = Slic3r::Config->new(
perimeters => 3,
);
my $w = 0.7;
my $perimeter_flow = Slic3r::Flow->new(
nozzle_diameter => 0.5,
layer_height => 0.4,
width => $w,
);
my $print = Slic3r::Print->new;
my $region = Slic3r::Print::Region->new(
print => $print,
flows => { perimeter => $perimeter_flow },
);
push @{$print->regions}, $region;
my $object = Slic3r::Print::Object->new(
print => $print,
size => [1,1],
);
my $make_layer = sub {
my ($width) = @_;
my $layer = Slic3r::Layer->new(
object => $object,
id => 1,
slices => [
Slic3r::Surface->new(
surface_type => S_TYPE_INTERNAL,
expolygon => Slic3r::ExPolygon->new([ scale_points [0,0], [50,0], [50,$width], [0,$width] ]),
),
],
thin_walls => [],
);
my $layerm = $layer->region(0);
$layer->make_perimeters;
return $layerm;
};
my %widths = (
1 * $w => { perimeters => 1, gaps => 0 },
1.3 * $w => { perimeters => 1, gaps => 1, gap_flow_spacing => $perimeter_flow->clone(width => 0.2 * $w)->spacing },
1.5 * $w => { perimeters => 1, gaps => 1, gap_flow_spacing => $perimeter_flow->clone(width => 0.5 * $w)->spacing },
2 * $w => { perimeters => 1, gaps => 1, gap_flow_spacing => $perimeter_flow->spacing },
2.5 * $w => { perimeters => 1, gaps => 1, gap_flow_spacing => $perimeter_flow->clone(width => 1.5 * $w)->spacing },
3 * $w => { perimeters => 2, gaps => 0 },
4 * $w => { perimeters => 2, gaps => 1, gap_flow_spacing => $perimeter_flow->spacing },
);
foreach my $width (sort keys %widths) {
my $layerm = $make_layer->($width);
is scalar @{$layerm->perimeters}, $widths{$width}{perimeters}, 'right number of perimeters';
is scalar @{$layerm->thin_fills} ? 1 : 0, $widths{$width}{gaps},
($widths{$width}{gaps} ? 'gaps were filled' : 'no gaps detected'); # TODO: we should check the exact number of gaps, but we need a better medial axis algorithm
my @gaps = map $_, @{$layerm->thin_fills};
if (@gaps) {
ok +(!first { abs($_->flow_spacing - $widths{$width}{gap_flow_spacing}) > epsilon } @gaps),
'flow spacing was dynamically adjusted';
}
}
}
__END__

View File

@ -2,7 +2,7 @@ use Test::More;
use strict;
use warnings;
plan tests => 27;
plan tests => 26;
BEGIN {
use FindBin;
@ -125,13 +125,6 @@ my $polygons = [
#==========================================================
{
my $line = Slic3r::Line->new([10,10], [20,10]);
is $line->grow(5)->[0]->area, Slic3r::Polygon->new([10,5], [20,5], [20,15], [10,15])->area, 'grow line';
}
#==========================================================
{
# if chained_path() works correctly, these points should be joined with no diagonal paths
# (thus 26 units long)

221
t/multi.t
View File

@ -1,221 +0,0 @@
use Test::More tests => 13;
use strict;
use warnings;
BEGIN {
use FindBin;
use lib "$FindBin::Bin/../lib";
use local::lib "$FindBin::Bin/../local-lib";
}
use List::Util qw(first);
use Slic3r;
use Slic3r::Geometry qw(scale convex_hull);
use Slic3r::Geometry::Clipper qw(offset);
use Slic3r::Test;
{
my $config = Slic3r::Config::new_from_defaults;
$config->set('nozzle_diameter', [0.6,0.6,0.6,0.6]);
$config->set('raft_layers', 2);
$config->set('infill_extruder', 2);
$config->set('solid_infill_extruder', 3);
$config->set('support_material_extruder', 4);
$config->set('ooze_prevention', 1);
$config->set('extruder_offset', [ [0,0], [20,0], [0,20], [20,20] ]);
$config->set('temperature', [200, 180, 170, 160]);
$config->set('first_layer_temperature', [206, 186, 166, 156]);
$config->set('toolchange_gcode', 'T[next_extruder] ;toolchange'); # test that it doesn't crash when this is supplied
# Since July 2019, PrusaSlicer only emits automatic Tn command in case that the toolchange_gcode is empty
# The "T[next_extruder]" is therefore needed in this test.
my $print = Slic3r::Test::init_print('20mm_cube', config => $config);
my $tool = undef;
my @tool_temp = (0,0,0,0);
my @toolchange_points = ();
my @extrusion_points = ();
Slic3r::GCode::Reader->new->parse(Slic3r::Test::gcode($print), sub {
my ($self, $cmd, $args, $info) = @_;
if ($cmd =~ /^T(\d+)/) {
# ignore initial toolchange
if (defined $tool) {
my $expected_temp = $self->Z == ($config->get_value('first_layer_height') + $config->z_offset)
? $config->first_layer_temperature->[$tool]
: $config->temperature->[$tool];
die 'standby temperature was not set before toolchange'
if $tool_temp[$tool] != $expected_temp + $config->standby_temperature_delta;
push @toolchange_points, my $point = Slic3r::Point->new_scale($self->X, $self->Y);
}
$tool = $1;
} elsif ($cmd eq 'M104' || $cmd eq 'M109') {
my $t = $args->{T} // $tool;
if ($tool_temp[$t] == 0) {
fail 'initial temperature is not equal to first layer temperature + standby delta'
unless $args->{S} == $config->first_layer_temperature->[$t] + $config->standby_temperature_delta;
}
$tool_temp[$t] = $args->{S};
} elsif ($cmd eq 'G1' && $info->{extruding} && $info->{dist_XY} > 0) {
push @extrusion_points, my $point = Slic3r::Point->new_scale($args->{X}, $args->{Y});
$point->translate(map +scale($_), @{ $config->extruder_offset->[$tool] });
}
});
my $convex_hull = convex_hull(\@extrusion_points);
my @t = ();
foreach my $point (@toolchange_points) {
foreach my $offset (@{$config->extruder_offset}) {
push @t, my $p = $point->clone;
$p->translate(map +scale($_), @$offset);
}
}
ok !(defined first { $convex_hull->contains_point($_) } @t), 'all nozzles are outside skirt at toolchange';
if (0) {
require "Slic3r/SVG.pm";
Slic3r::SVG::output(
"ooze_prevention_test.svg",
no_arrows => 1,
polygons => [$convex_hull],
red_points => \@t,
points => \@toolchange_points,
);
}
# offset the skirt by the maximum displacement between extruders plus a safety extra margin
my $delta = scale(20 * sqrt(2) + 1);
my $outer_convex_hull = offset([$convex_hull], +$delta)->[0];
ok !(defined first { !$outer_convex_hull->contains_point($_) } @toolchange_points), 'all toolchanges happen within expected area';
}
{
my $config = Slic3r::Config::new_from_defaults;
$config->set('nozzle_diameter', [0.6,0.6,0.6,0.6]);
$config->set('support_material_extruder', 3);
my $print = Slic3r::Test::init_print('20mm_cube', config => $config);
ok Slic3r::Test::gcode($print), 'no errors when using non-consecutive extruders';
}
{
my $config = Slic3r::Config->new;
$config->set('nozzle_diameter', [0.6,0.6,0.6,0.6]);
$config->set('extruder', 2);
my $print = Slic3r::Test::init_print('20mm_cube', config => $config);
like Slic3r::Test::gcode($print), qr/ T1/, 'extruder shortcut';
}
{
my $config = Slic3r::Config->new;
$config->set('nozzle_diameter', [0.6,0.6,0.6,0.6]);
$config->set('perimeter_extruder', 2);
$config->set('infill_extruder', 2);
$config->set('support_material_extruder', 2);
$config->set('support_material_interface_extruder', 2);
my $print = Slic3r::Test::init_print('20mm_cube', config => $config);
ok Slic3r::Test::gcode($print), 'no errors when using multiple skirts with a single, non-zero, extruder';
}
{
my $model = stacked_cubes();
my $lower_config = $model->get_material('lower')->config;
my $upper_config = $model->get_material('upper')->config;
$lower_config->set('extruder', 1);
$lower_config->set('bottom_solid_layers', 0);
$lower_config->set('top_solid_layers', 1);
$upper_config->set('extruder', 2);
$upper_config->set('bottom_solid_layers', 1);
$upper_config->set('top_solid_layers', 0);
my $config = Slic3r::Config::new_from_defaults;
$config->set('nozzle_diameter', [0.6,0.6,0.6,0.6]);
$config->set('fill_density', 0);
$config->set('solid_infill_speed', 99);
$config->set('top_solid_infill_speed', 99);
$config->set('cooling', [ 0 ]); # for preventing speeds from being altered
$config->set('first_layer_speed', '100%'); # for preventing speeds from being altered
my $test = sub {
my $print = Slic3r::Test::init_print($model, config => $config);
my $tool = undef;
my %T0_shells = my %T1_shells = (); # Z => 1
Slic3r::GCode::Reader->new->parse(my $gcode = Slic3r::Test::gcode($print), sub {
my ($self, $cmd, $args, $info) = @_;
if ($cmd =~ /^T(\d+)/) {
$tool = $1;
} elsif ($cmd eq 'G1' && $info->{extruding} && $info->{dist_XY} > 0) {
if (($args->{F} // $self->F) == $config->solid_infill_speed*60) {
if ($tool == 0) {
$T0_shells{$self->Z} = 1;
} elsif ($tool == 1) {
$T1_shells{$self->Z} = 1;
}
}
}
});
return [ sort keys %T0_shells ], [ sort keys %T1_shells ];
};
{
my ($t0, $t1) = $test->();
is scalar(@$t0), 0, 'no interface shells';
is scalar(@$t1), 0, 'no interface shells';
}
{
$config->set('interface_shells', 1);
my ($t0, $t1) = $test->();
is scalar(@$t0), $lower_config->top_solid_layers, 'top interface shells';
is scalar(@$t1), $upper_config->bottom_solid_layers, 'bottom interface shells';
}
}
{
my $model = stacked_cubes();
my $object = $model->objects->[0];
my $config = Slic3r::Config::new_from_defaults;
$config->set('nozzle_diameter', [0.6,0.6,0.6,0.6]);
$config->set('layer_height', 0.4);
$config->set('first_layer_height', $config->layer_height);
$config->set('skirts', 0);
my $print = Slic3r::Test::init_print($model, config => $config);
is $object->volumes->[0]->config->extruder, 1, 'auto_assign_extruders() assigned correct extruder to first volume';
is $object->volumes->[1]->config->extruder, 2, 'auto_assign_extruders() assigned correct extruder to second volume';
my $tool = undef;
my %T0 = my %T1 = (); # Z => 1
Slic3r::GCode::Reader->new->parse(my $gcode = Slic3r::Test::gcode($print), sub {
my ($self, $cmd, $args, $info) = @_;
if ($cmd =~ /^T(\d+)/) {
$tool = $1;
} elsif ($cmd eq 'G1' && $info->{extruding} && $info->{dist_XY} > 0) {
if ($tool == 0) {
$T0{$self->Z} = 1;
} elsif ($tool == 1) {
$T1{$self->Z} = 1;
}
}
});
ok !(defined first { $_ > 20 } keys %T0), 'T0 is never used for upper object';
ok !(defined first { $_ < 20 } keys %T1), 'T1 is never used for lower object';
}
sub stacked_cubes {
my $model = Slic3r::Model->new;
my $object = $model->add_object;
$object->add_volume(mesh => Slic3r::Test::mesh('20mm_cube'), material_id => 'lower');
$object->add_volume(mesh => Slic3r::Test::mesh('20mm_cube', translate => [0,0,20]), material_id => 'upper');
$object->add_instance(offset => Slic3r::Pointf->new(0,0));
return $model;
}
__END__

File diff suppressed because one or more lines are too long

152
t/slice.t
View File

@ -1,152 +0,0 @@
use Test::More;
use strict;
use warnings;
plan skip_all => 'temporarily disabled';
plan tests => 16;
BEGIN {
use FindBin;
use lib "$FindBin::Bin/../lib";
use local::lib "$FindBin::Bin/../local-lib";
}
# temporarily disable compilation errors due to constant not being exported anymore
sub Slic3r::TriangleMesh::I_B {}
sub Slic3r::TriangleMesh::I_FACET_EDGE {}
sub Slic3r::TriangleMesh::FE_BOTTOM {
sub Slic3r::TriangleMesh::FE_TOP {}}
use Slic3r;
use Slic3r::Geometry qw(X Y Z);
my @lines;
my $z = 20;
my @points = ([3, 4], [8, 5], [1, 9]); # XY coordinates of the facet vertices
# NOTE:
# the first point of the intersection lines is replaced by -1 because TriangleMesh.pm
# is saving memory and doesn't store point A anymore since it's not actually needed.
# We disable this test because intersect_facet() now assumes we never feed a horizontal
# facet to it.
# is_deeply lines(20, 20, 20), [
# [ -1, $points[1] ], # $points[0]
# [ -1, $points[2] ], # $points[1]
# [ -1, $points[0] ], # $points[2]
# ], 'horizontal';
is_deeply lines(22, 20, 20), [ [ -1, $points[2] ] ], 'lower edge on layer'; # $points[1]
is_deeply lines(20, 20, 22), [ [ -1, $points[1] ] ], 'lower edge on layer'; # $points[0]
is_deeply lines(20, 22, 20), [ [ -1, $points[0] ] ], 'lower edge on layer'; # $points[2]
is_deeply lines(20, 20, 10), [ [ -1, $points[0] ] ], 'upper edge on layer'; # $points[1]
is_deeply lines(10, 20, 20), [ [ -1, $points[1] ] ], 'upper edge on layer'; # $points[2]
is_deeply lines(20, 10, 20), [ [ -1, $points[2] ] ], 'upper edge on layer'; # $points[0]
is_deeply lines(20, 15, 10), [ ], 'upper vertex on layer';
is_deeply lines(28, 20, 30), [ ], 'lower vertex on layer';
{
my @z = (24, 10, 16);
is_deeply lines(@z), [
[
-1, # line_plane_intersection([ vertices(@z)->[0], vertices(@z)->[1] ]),
line_plane_intersection([ vertices(@z)->[2], vertices(@z)->[0] ]),
]
], 'two edges intersect';
}
{
my @z = (16, 24, 10);
is_deeply lines(@z), [
[
-1, # line_plane_intersection([ vertices(@z)->[1], vertices(@z)->[2] ]),
line_plane_intersection([ vertices(@z)->[0], vertices(@z)->[1] ]),
]
], 'two edges intersect';
}
{
my @z = (10, 16, 24);
is_deeply lines(@z), [
[
-1, # line_plane_intersection([ vertices(@z)->[2], vertices(@z)->[0] ]),
line_plane_intersection([ vertices(@z)->[1], vertices(@z)->[2] ]),
]
], 'two edges intersect';
}
{
my @z = (24, 10, 20);
is_deeply lines(@z), [
[
-1, # line_plane_intersection([ vertices(@z)->[0], vertices(@z)->[1] ]),
$points[2],
]
], 'one vertex on plane and one edge intersects';
}
{
my @z = (10, 20, 24);
is_deeply lines(@z), [
[
-1, # line_plane_intersection([ vertices(@z)->[2], vertices(@z)->[0] ]),
$points[1],
]
], 'one vertex on plane and one edge intersects';
}
{
my @z = (20, 24, 10);
is_deeply lines(@z), [
[
-1, # line_plane_intersection([ vertices(@z)->[1], vertices(@z)->[2] ]),
$points[0],
]
], 'one vertex on plane and one edge intersects';
}
my @lower = intersect(22, 20, 20);
my @upper = intersect(20, 20, 10);
is $lower[0][Slic3r::TriangleMesh::I_FACET_EDGE], Slic3r::TriangleMesh::FE_BOTTOM, 'bottom edge on layer';
is $upper[0][Slic3r::TriangleMesh::I_FACET_EDGE], Slic3r::TriangleMesh::FE_TOP, 'upper edge on layer';
my $mesh;
sub intersect {
$mesh = Slic3r::TriangleMesh->new(
facets => [],
vertices => [],
);
push @{$mesh->facets}, [ [0,0,0], @{vertices(@_)} ];
$mesh->analyze;
return map Slic3r::TriangleMesh::unpack_line($_), $mesh->intersect_facet($#{$mesh->facets}, $z);
}
sub vertices {
push @{$mesh->vertices}, map [ @{$points[$_]}, $_[$_] ], 0..2;
[ ($#{$mesh->vertices}-2) .. $#{$mesh->vertices} ]
}
sub lines {
my @lines = intersect(@_);
#$_->a->[X] = sprintf('%.0f', $_->a->[X]) for @lines;
#$_->a->[Y] = sprintf('%.0f', $_->a->[Y]) for @lines;
$_->[Slic3r::TriangleMesh::I_B][X] = sprintf('%.0f', $_->[Slic3r::TriangleMesh::I_B][X]) for @lines;
$_->[Slic3r::TriangleMesh::I_B][Y] = sprintf('%.0f', $_->[Slic3r::TriangleMesh::I_B][Y]) for @lines;
return [ map [ -1, $_->[Slic3r::TriangleMesh::I_B] ], @lines ];
}
sub line_plane_intersection {
my ($line) = @_;
@$line = map $mesh->vertices->[$_], @$line;
return [
map sprintf('%.0f', $_),
map +($line->[1][$_] + ($line->[0][$_] - $line->[1][$_]) * ($z - $line->[1][Z]) / ($line->[0][Z] - $line->[1][Z])),
(X,Y)
];
}
__END__

View File

@ -1,272 +0,0 @@
use Test::More;
use strict;
use warnings;
plan skip_all => 'temporarily disabled';
plan tests => 27;
BEGIN {
use FindBin;
use lib "$FindBin::Bin/../lib";
use local::lib "$FindBin::Bin/../local-lib";
}
use List::Util qw(first);
use Slic3r;
use Slic3r::Flow ':roles';
use Slic3r::Geometry qw(epsilon scale);
use Slic3r::Geometry::Clipper qw(diff);
use Slic3r::Test;
{
my $config = Slic3r::Config::new_from_defaults;
$config->set('support_material', 1);
my @contact_z = my @top_z = ();
my $test = sub {
my $print = Slic3r::Test::init_print('20mm_cube', config => $config);
my $object_config = $print->print->objects->[0]->config;
my $flow = Slic3r::Flow->new_from_width(
width => $object_config->support_material_extrusion_width || $object_config->extrusion_width,
role => FLOW_ROLE_SUPPORT_MATERIAL,
nozzle_diameter => $print->config->nozzle_diameter->[$object_config->support_material_extruder-1] // $print->config->nozzle_diameter->[0],
layer_height => $object_config->layer_height,
);
my $support = Slic3r::Print::SupportMaterial->new(
object_config => $print->print->objects->[0]->config,
print_config => $print->print->config,
flow => $flow,
interface_flow => $flow,
first_layer_flow => $flow,
);
my $support_z = $support->support_layers_z($print->print->objects->[0], \@contact_z, \@top_z, $config->layer_height);
my $expected_top_spacing = $support->contact_distance($config->layer_height, $config->nozzle_diameter->[0]);
is $support_z->[0], $config->first_layer_height,
'first layer height is honored';
is scalar(grep { $support_z->[$_]-$support_z->[$_-1] <= 0 } 1..$#$support_z), 0,
'no null or negative support layers';
is scalar(grep { $support_z->[$_]-$support_z->[$_-1] > $config->nozzle_diameter->[0] + epsilon } 1..$#$support_z), 0,
'no layers thicker than nozzle diameter';
my $wrong_top_spacing = 0;
foreach my $top_z (@top_z) {
# find layer index of this top surface
my $layer_id = first { abs($support_z->[$_] - $top_z) < epsilon } 0..$#$support_z;
# check that first support layer above this top surface (or the next one) is spaced with nozzle diameter
$wrong_top_spacing = 1
if ($support_z->[$layer_id+1] - $support_z->[$layer_id]) != $expected_top_spacing
&& ($support_z->[$layer_id+2] - $support_z->[$layer_id]) != $expected_top_spacing;
}
ok !$wrong_top_spacing, 'layers above top surfaces are spaced correctly';
};
$config->set('layer_height', 0.2);
$config->set('first_layer_height', 0.3);
@contact_z = (1.9);
@top_z = (1.1);
$test->();
$config->set('first_layer_height', 0.4);
$test->();
$config->set('layer_height', $config->nozzle_diameter->[0]);
$test->();
}
{
my $config = Slic3r::Config::new_from_defaults;
$config->set('raft_layers', 3);
$config->set('brim_width', 0);
$config->set('skirts', 0);
$config->set('support_material_extruder', 2);
$config->set('support_material_interface_extruder', 2);
$config->set('layer_height', 0.4);
$config->set('first_layer_height', 0.4);
my $print = Slic3r::Test::init_print('overhang', config => $config);
ok my $gcode = Slic3r::Test::gcode($print), 'no conflict between raft/support and brim';
my $tool = 0;
Slic3r::GCode::Reader->new->parse($gcode, sub {
my ($self, $cmd, $args, $info) = @_;
if ($cmd =~ /^T(\d+)/) {
$tool = $1;
} elsif ($info->{extruding}) {
if ($self->Z <= ($config->raft_layers * $config->layer_height)) {
fail 'not extruding raft with support material extruder'
if $tool != ($config->support_material_extruder-1);
} else {
fail 'support material exceeds raft layers'
if $tool == $config->support_material_extruder-1;
# TODO: we should test that full support is generated when we use raft too
}
}
});
}
{
my $config = Slic3r::Config::new_from_defaults;
$config->set('skirts', 0);
$config->set('raft_layers', 3);
$config->set('support_material_pattern', 'honeycomb');
$config->set('support_material_extrusion_width', 0.6);
$config->set('first_layer_extrusion_width', '100%');
$config->set('bridge_speed', 99);
$config->set('cooling', [ 0 ]); # prevent speed alteration
$config->set('first_layer_speed', '100%'); # prevent speed alteration
$config->set('start_gcode', ''); # prevent any unexpected Z move
my $print = Slic3r::Test::init_print('20mm_cube', config => $config);
my $layer_id = -1; # so that first Z move sets this to 0
my @raft = my @first_object_layer = ();
my %first_object_layer_speeds = (); # F => 1
Slic3r::GCode::Reader->new->parse(Slic3r::Test::gcode($print), sub {
my ($self, $cmd, $args, $info) = @_;
if ($info->{extruding} && $info->{dist_XY} > 0) {
if ($layer_id <= $config->raft_layers) {
# this is a raft layer or the first object layer
my $line = Slic3r::Line->new_scale([ $self->X, $self->Y ], [ $info->{new_X}, $info->{new_Y} ]);
my @path = @{$line->grow(scale($config->support_material_extrusion_width/2))};
if ($layer_id < $config->raft_layers) {
# this is a raft layer
push @raft, @path;
} else {
push @first_object_layer, @path;
$first_object_layer_speeds{ $args->{F} // $self->F } = 1;
}
}
} elsif ($cmd eq 'G1' && $info->{dist_Z} > 0) {
$layer_id++;
}
});
ok !@{diff(\@first_object_layer, \@raft)},
'first object layer is completely supported by raft';
is scalar(keys %first_object_layer_speeds), 1,
'only one speed used in first object layer';
ok +(keys %first_object_layer_speeds)[0] == $config->bridge_speed*60,
'bridge speed used in first object layer';
}
{
my $config = Slic3r::Config::new_from_defaults;
$config->set('skirts', 0);
$config->set('layer_height', 0.35);
$config->set('first_layer_height', 0.3);
$config->set('nozzle_diameter', [0.5]);
$config->set('support_material_extruder', 2);
$config->set('support_material_interface_extruder', 2);
my $test = sub {
my ($raft_layers) = @_;
$config->set('raft_layers', $raft_layers);
my $print = Slic3r::Test::init_print('20mm_cube', config => $config);
my %raft_z = (); # z => 1
my $tool = undef;
Slic3r::GCode::Reader->new->parse(Slic3r::Test::gcode($print), sub {
my ($self, $cmd, $args, $info) = @_;
if ($cmd =~ /^T(\d+)/) {
$tool = $1;
} elsif ($info->{extruding} && $info->{dist_XY} > 0) {
if ($tool == $config->support_material_extruder-1) {
$raft_z{$self->Z} = 1;
}
}
});
is scalar(keys %raft_z), $config->raft_layers, 'correct number of raft layers is generated';
};
$test->(2);
$test->(70);
$config->set('layer_height', 0.4);
$config->set('first_layer_height', 0.35);
$test->(3);
$test->(70);
}
{
my $config = Slic3r::Config::new_from_defaults;
$config->set('brim_width', 0);
$config->set('skirts', 0);
$config->set('support_material', 1);
$config->set('top_solid_layers', 0); # so that we don't have the internal bridge over infill
$config->set('bridge_speed', 99);
$config->set('cooling', [ 0 ]);
$config->set('first_layer_speed', '100%');
my $test = sub {
my $print = Slic3r::Test::init_print('overhang', config => $config);
my $has_bridge_speed = 0;
Slic3r::GCode::Reader->new->parse(Slic3r::Test::gcode($print), sub {
my ($self, $cmd, $args, $info) = @_;
if ($info->{extruding}) {
if (($args->{F} // $self->F) == $config->bridge_speed*60) {
$has_bridge_speed = 1;
}
}
});
return $has_bridge_speed;
};
$config->set('support_material_contact_distance', 0.2);
ok $test->(), 'bridge speed is used when support_material_contact_distance > 0';
$config->set('support_material_contact_distance', 0);
ok !$test->(), 'bridge speed is not used when support_material_contact_distance == 0';
$config->set('raft_layers', 5);
$config->set('support_material_contact_distance', 0.2);
ok $test->(), 'bridge speed is used when raft_layers > 0 and support_material_contact_distance > 0';
$config->set('support_material_contact_distance', 0);
ok !$test->(), 'bridge speed is not used when raft_layers > 0 and support_material_contact_distance == 0';
}
{
my $config = Slic3r::Config::new_from_defaults;
$config->set('skirts', 0);
$config->set('start_gcode', '');
$config->set('raft_layers', 8);
$config->set('nozzle_diameter', [0.4, 1]);
$config->set('layer_height', 0.1);
$config->set('first_layer_height', 0.8);
$config->set('support_material_extruder', 2);
$config->set('support_material_interface_extruder', 2);
$config->set('support_material_contact_distance', 0);
my $print = Slic3r::Test::init_print('20mm_cube', config => $config);
ok my $gcode = Slic3r::Test::gcode($print), 'first_layer_height is validated with support material extruder nozzle diameter when using raft layers';
my $tool = undef;
my @z = (0);
my %layer_heights_by_tool = (); # tool => [ lh, lh... ]
Slic3r::GCode::Reader->new->parse($gcode, sub {
my ($self, $cmd, $args, $info) = @_;
if ($cmd =~ /^T(\d+)/) {
$tool = $1;
} elsif ($cmd eq 'G1' && exists $args->{Z} && $args->{Z} != $self->Z) {
push @z, $args->{Z};
} elsif ($info->{extruding} && $info->{dist_XY} > 0) {
$layer_heights_by_tool{$tool} ||= [];
push @{ $layer_heights_by_tool{$tool} }, $z[-1] - $z[-2];
}
});
ok !defined(first { $_ > $config->nozzle_diameter->[0] + epsilon }
@{ $layer_heights_by_tool{$config->perimeter_extruder-1} }),
'no object layer is thicker than nozzle diameter';
ok !defined(first { abs($_ - $config->layer_height) < epsilon }
@{ $layer_heights_by_tool{$config->support_material_extruder-1} }),
'no support material layer is as thin as object layers';
}
__END__

View File

@ -10,6 +10,8 @@ add_executable(${_TEST_NAME}_tests
test_gcodefindreplace.cpp
test_gcodewriter.cpp
test_model.cpp
test_multi.cpp
test_perimeters.cpp
test_print.cpp
test_printgcode.cpp
test_printobject.cpp

View File

@ -141,3 +141,10 @@ TEST_CASE("ExtrusionEntityCollection: Chained path", "[ExtrusionEntity]") {
}
}
}
TEST_CASE("ExtrusionEntityCollection: Chained path with no explicit starting point", "[ExtrusionEntity]") {
auto polylines = Polylines { { { 0, 15 }, {0, 18}, {0, 20} }, { { 0, 10 }, {0, 8}, {0, 5} } };
auto target = Polylines { { {0, 5}, {0, 8}, { 0, 10 } }, { { 0, 15 }, {0, 18}, {0, 20} } };
auto chained = chain_polylines(polylines);
REQUIRE(chained == target);
}

View File

@ -0,0 +1,268 @@
#include <catch2/catch.hpp>
#include <numeric>
#include <sstream>
#include "libslic3r/ClipperUtils.hpp"
#include "libslic3r/Geometry.hpp"
#include "libslic3r/Geometry/ConvexHull.hpp"
#include "libslic3r/Print.hpp"
#include "libslic3r/libslic3r.h"
#include "test_data.hpp"
using namespace Slic3r;
using namespace std::literals;
SCENARIO("Basic tests", "[Multi]")
{
WHEN("Slicing multi-material print with non-consecutive extruders") {
std::string gcode = Slic3r::Test::slice({ Slic3r::Test::TestMesh::cube_20x20x20 },
{
{ "nozzle_diameter", "0.6, 0.6, 0.6, 0.6" },
{ "extruder", 2 },
{ "infill_extruder", 4 },
{ "support_material_extruder", 0 }
});
THEN("Sliced successfully") {
REQUIRE(! gcode.empty());
}
THEN("T3 toolchange command found") {
bool T1_found = gcode.find("\nT3\n") != gcode.npos;
REQUIRE(T1_found);
}
}
WHEN("Slicing with multiple skirts with a single, non-zero extruder") {
std::string gcode = Slic3r::Test::slice({ Slic3r::Test::TestMesh::cube_20x20x20 },
{
{ "nozzle_diameter", "0.6, 0.6, 0.6, 0.6" },
{ "perimeter_extruder", 2 },
{ "infill_extruder", 2 },
{ "support_material_extruder", 2 },
{ "support_material_interface_extruder", 2 },
});
THEN("Sliced successfully") {
REQUIRE(! gcode.empty());
}
}
}
SCENARIO("Ooze prevention", "[Multi]")
{
DynamicPrintConfig config = Slic3r::DynamicPrintConfig::full_print_config_with({
{ "nozzle_diameter", "0.6, 0.6, 0.6, 0.6" },
{ "raft_layers", 2 },
{ "infill_extruder", 2 },
{ "solid_infill_extruder", 3 },
{ "support_material_extruder", 4 },
{ "ooze_prevention", 1 },
{ "extruder_offset", "0x0, 20x0, 0x20, 20x20" },
{ "temperature", "200, 180, 170, 160" },
{ "first_layer_temperature", "206, 186, 166, 156" },
// test that it doesn't crash when this is supplied
{ "toolchange_gcode", "T[next_extruder] ;toolchange" }
});
FullPrintConfig print_config;
print_config.apply(config);
// Since July 2019, PrusaSlicer only emits automatic Tn command in case that the toolchange_gcode is empty
// The "T[next_extruder]" is therefore needed in this test.
std::string gcode = Slic3r::Test::slice({ Slic3r::Test::TestMesh::cube_20x20x20 }, config);
GCodeReader parser;
int tool = -1;
int tool_temp[] = { 0, 0, 0, 0};
Points toolchange_points;
Points extrusion_points;
parser.parse_buffer(gcode, [&tool, &tool_temp, &toolchange_points, &extrusion_points, &print_config]
(Slic3r::GCodeReader &self, const Slic3r::GCodeReader::GCodeLine &line)
{
// if the command is a T command, set the the current tool
if (boost::starts_with(line.cmd(), "T")) {
// Ignore initial toolchange.
if (tool != -1) {
int expected_temp = is_approx<double>(self.z(), print_config.get_abs_value("first_layer_height") + print_config.z_offset) ?
print_config.first_layer_temperature.get_at(tool) :
print_config.temperature.get_at(tool);
if (tool_temp[tool] != expected_temp + print_config.standby_temperature_delta)
throw std::runtime_error("Standby temperature was not set before toolchange.");
toolchange_points.emplace_back(self.xy_scaled());
}
tool = atoi(line.cmd().data() + 1);
} else if (line.cmd_is("M104") || line.cmd_is("M109")) {
// May not be defined on this line.
int t = tool;
line.has_value('T', t);
// Should be available on this line.
int s;
if (! line.has_value('S', s))
throw std::runtime_error("M104 or M109 without S");
if (tool_temp[t] == 0 && s != print_config.first_layer_temperature.get_at(t) + print_config.standby_temperature_delta)
throw std::runtime_error("initial temperature is not equal to first layer temperature + standby delta");
tool_temp[t] = s;
} else if (line.cmd_is("G1") && line.extruding(self) && line.dist_XY(self) > 0) {
extrusion_points.emplace_back(line.new_XY_scaled(self) + scaled<coord_t>(print_config.extruder_offset.get_at(tool)));
}
});
Polygon convex_hull = Geometry::convex_hull(extrusion_points);
THEN("all nozzles are outside skirt at toolchange") {
Points t;
sort_remove_duplicates(toolchange_points);
size_t inside = 0;
for (const auto &point : toolchange_points)
for (const Vec2d &offset : print_config.extruder_offset.values) {
Point p = point + scaled<coord_t>(offset);
if (convex_hull.contains(p))
++ inside;
}
REQUIRE(inside == 0);
}
#if 0
require "Slic3r/SVG.pm";
Slic3r::SVG::output(
"ooze_prevention_test.svg",
no_arrows => 1,
polygons => [$convex_hull],
red_points => \@t,
points => \@toolchange_points,
);
#endif
THEN("all toolchanges happen within expected area") {
// offset the skirt by the maximum displacement between extruders plus a safety extra margin
const float delta = scaled<float>(20. * sqrt(2.) + 1.);
Polygon outer_convex_hull = expand(convex_hull, delta).front();
size_t inside = std::count_if(toolchange_points.begin(), toolchange_points.end(), [&outer_convex_hull](const Point &p){ return outer_convex_hull.contains(p); });
REQUIRE(inside == toolchange_points.size());
}
}
std::string slice_stacked_cubes(const DynamicPrintConfig &config, const DynamicPrintConfig &volume1config, const DynamicPrintConfig &volume2config)
{
Model model;
ModelObject *object = model.add_object();
object->name = "object.stl";
ModelVolume *v1 = object->add_volume(Test::mesh(Test::TestMesh::cube_20x20x20));
v1->set_material_id("lower_material");
v1->config.assign_config(volume1config);
ModelVolume *v2 = object->add_volume(Test::mesh(Test::TestMesh::cube_20x20x20));
v2->set_material_id("upper_material");
v2->translate(0., 0., 20.);
v2->config.assign_config(volume2config);
object->add_instance();
object->ensure_on_bed();
Print print;
print.auto_assign_extruders(object);
THEN("auto_assign_extruders() assigned correct extruder to first volume") {
REQUIRE(v1->config.extruder() == 1);
}
THEN("auto_assign_extruders() assigned correct extruder to second volume") {
REQUIRE(v2->config.extruder() == 2);
}
print.apply(model, config);
print.validate();
return Test::gcode(print);
}
SCENARIO("Stacked cubes", "[Multi]")
{
DynamicPrintConfig lower_config;
lower_config.set_deserialize_strict({
{ "extruder", 1 },
{ "bottom_solid_layers", 0 },
{ "top_solid_layers", 1 },
});
DynamicPrintConfig upper_config;
upper_config.set_deserialize_strict({
{ "extruder", 2 },
{ "bottom_solid_layers", 1 },
{ "top_solid_layers", 0 }
});
static constexpr const double solid_infill_speed = 99;
auto config = Slic3r::DynamicPrintConfig::full_print_config_with({
{ "nozzle_diameter", "0.6, 0.6, 0.6, 0.6" },
{ "fill_density", 0 },
{ "solid_infill_speed", solid_infill_speed },
{ "top_solid_infill_speed", solid_infill_speed },
// for preventing speeds from being altered
{ "cooling", "0, 0, 0, 0" },
// for preventing speeds from being altered
{ "first_layer_speed", "100%" }
});
auto test_shells = [](const std::string &gcode) {
GCodeReader parser;
int tool = -1;
// Scaled Z heights.
std::set<coord_t> T0_shells, T1_shells;
parser.parse_buffer(gcode, [&tool, &T0_shells, &T1_shells]
(Slic3r::GCodeReader &self, const Slic3r::GCodeReader::GCodeLine &line)
{
if (boost::starts_with(line.cmd(), "T")) {
tool = atoi(line.cmd().data() + 1);
} else if (line.cmd() == "G1" && line.extruding(self) && line.dist_XY(self) > 0) {
if (is_approx<double>(line.new_F(self), solid_infill_speed * 60.) && (tool == 0 || tool == 1))
(tool == 0 ? T0_shells : T1_shells).insert(scaled<coord_t>(self.z()));
}
});
return std::make_pair(T0_shells, T1_shells);
};
WHEN("Interface shells disabled") {
std::string gcode = slice_stacked_cubes(config, lower_config, upper_config);
auto [t0, t1] = test_shells(gcode);
THEN("no interface shells") {
REQUIRE(t0.empty());
REQUIRE(t1.empty());
}
}
WHEN("Interface shells enabled") {
config.set_deserialize_strict("interface_shells", "1");
std::string gcode = slice_stacked_cubes(config, lower_config, upper_config);
auto [t0, t1] = test_shells(gcode);
THEN("top interface shells") {
REQUIRE(t0.size() == lower_config.opt_int("top_solid_layers"));
}
THEN("bottom interface shells") {
REQUIRE(t1.size() == upper_config.opt_int("bottom_solid_layers"));
}
}
WHEN("Slicing with auto-assigned extruders") {
auto config = Slic3r::DynamicPrintConfig::full_print_config_with({
{ "nozzle_diameter", "0.6,0.6,0.6,0.6" },
{ "layer_height", 0.4 },
{ "first_layer_height", 0.4 },
{ "skirts", 0 }
});
std::string gcode = slice_stacked_cubes(config, DynamicPrintConfig{}, DynamicPrintConfig{});
GCodeReader parser;
int tool = -1;
// Scaled Z heights.
std::set<coord_t> T0_shells, T1_shells;
parser.parse_buffer(gcode, [&tool, &T0_shells, &T1_shells](Slic3r::GCodeReader &self, const Slic3r::GCodeReader::GCodeLine &line)
{
if (boost::starts_with(line.cmd(), "T")) {
tool = atoi(line.cmd().data() + 1);
} else if (line.cmd() == "G1" && line.extruding(self) && line.dist_XY(self) > 0) {
if (tool == 0 && self.z() > 20)
// Layers incorrectly extruded with T0 at the top object.
T0_shells.insert(scaled<coord_t>(self.z()));
else if (tool == 1 && self.z() < 20)
// Layers incorrectly extruded with T1 at the bottom object.
T1_shells.insert(scaled<coord_t>(self.z()));
}
});
THEN("T0 is never used for upper object") {
REQUIRE(T0_shells.empty());
}
THEN("T0 is never used for lower object") {
REQUIRE(T1_shells.empty());
}
}
}

View File

@ -0,0 +1,599 @@
#include <catch2/catch.hpp>
#include <numeric>
#include <sstream>
#include "libslic3r/Config.hpp"
#include "libslic3r/ClipperUtils.hpp"
#include "libslic3r/Layer.hpp"
#include "libslic3r/PerimeterGenerator.hpp"
#include "libslic3r/Print.hpp"
#include "libslic3r/PrintConfig.hpp"
#include "libslic3r/SurfaceCollection.hpp"
#include "libslic3r/libslic3r.h"
#include "test_data.hpp"
using namespace Slic3r;
SCENARIO("Perimeter nesting", "[Perimeters]")
{
struct TestData {
ExPolygons expolygons;
// expected number of loops
int total;
// expected number of external loops
int external;
// expected external perimeter
std::vector<bool> ext_order;
// expected number of internal contour loops
int cinternal;
// expected number of ccw loops
int ccw;
// expected ccw/cw order
std::vector<bool> ccw_order;
// expected nesting order
std::vector<std::vector<int>> nesting;
};
FullPrintConfig config;
auto test = [&config](const TestData &data) {
SurfaceCollection slices;
slices.append(data.expolygons, stInternal);
ExtrusionEntityCollection loops;
ExtrusionEntityCollection gap_fill;
SurfaceCollection fill_surfaces;
PerimeterGenerator perimeter_generator(
&slices,
1., // layer height
Flow(1., 1., 1.),
static_cast<const PrintRegionConfig*>(&config),
static_cast<const PrintObjectConfig*>(&config),
static_cast<const PrintConfig*>(&config),
false, // spiral_vase
// output:
&loops, &gap_fill, &fill_surfaces);
perimeter_generator.process();
THEN("expected number of collections") {
REQUIRE(loops.entities.size() == data.expolygons.size());
}
loops = loops.flatten();
THEN("expected number of loops") {
REQUIRE(loops.entities.size() == data.total);
}
THEN("expected number of external loops") {
size_t num_external = std::count_if(loops.entities.begin(), loops.entities.end(),
[](const ExtrusionEntity *ee){ return ee->role() == erExternalPerimeter; });
REQUIRE(num_external == data.external);
}
THEN("expected external order") {
std::vector<bool> ext_order;
for (auto *ee : loops.entities)
ext_order.emplace_back(ee->role() == erExternalPerimeter);
REQUIRE(ext_order == data.ext_order);
}
THEN("expected number of internal contour loops") {
size_t cinternal = std::count_if(loops.entities.begin(), loops.entities.end(),
[](const ExtrusionEntity *ee){ return dynamic_cast<const ExtrusionLoop*>(ee)->loop_role() == elrContourInternalPerimeter; });
REQUIRE(cinternal == data.cinternal);
}
THEN("expected number of ccw loops") {
size_t ccw = std::count_if(loops.entities.begin(), loops.entities.end(),
[](const ExtrusionEntity *ee){ return dynamic_cast<const ExtrusionLoop*>(ee)->polygon().is_counter_clockwise(); });
REQUIRE(ccw == data.ccw);
}
THEN("expected ccw/cw order") {
std::vector<bool> ccw_order;
for (auto *ee : loops.entities)
ccw_order.emplace_back(dynamic_cast<const ExtrusionLoop*>(ee)->polygon().is_counter_clockwise());
REQUIRE(ccw_order == data.ccw_order);
}
THEN("expected nesting order") {
for (const std::vector<int> &nesting : data.nesting) {
for (size_t i = 1; i < nesting.size(); ++ i)
REQUIRE(dynamic_cast<const ExtrusionLoop*>(loops.entities[nesting[i - 1]])->polygon().contains(loops.entities[nesting[i]]->first_point()));
}
}
};
WHEN("Rectangle") {
config.perimeters.value = 3;
TestData data;
data.expolygons = {
ExPolygon{ Polygon::new_scale({ {0,0}, {100,0}, {100,100}, {0,100} }) }
};
data.total = 3;
data.external = 1;
data.ext_order = { false, false, true };
data.cinternal = 1;
data.ccw = 3;
data.ccw_order = { true, true, true };
data.nesting = { { 2, 1, 0 } };
test(data);
}
WHEN("Rectangle with hole") {
config.perimeters.value = 3;
TestData data;
data.expolygons = {
ExPolygon{ Polygon::new_scale({ {0,0}, {100,0}, {100,100}, {0,100} }),
Polygon::new_scale({ {40,40}, {40,60}, {60,60}, {60,40} }) }
};
data.total = 6;
data.external = 2;
data.ext_order = { false, false, true, false, false, true };
data.cinternal = 1;
data.ccw = 3;
data.ccw_order = { false, false, false, true, true, true };
data.nesting = { { 5, 4, 3, 0, 1, 2 } };
test(data);
}
WHEN("Nested rectangles with holes") {
config.perimeters.value = 3;
TestData data;
data.expolygons = {
ExPolygon{ Polygon::new_scale({ {0,0}, {200,0}, {200,200}, {0,200} }),
Polygon::new_scale({ {20,20}, {20,180}, {180,180}, {180,20} }) },
ExPolygon{ Polygon::new_scale({ {50,50}, {150,50}, {150,150}, {50,150} }),
Polygon::new_scale({ {80,80}, {80,120}, {120,120}, {120,80} }) }
};
data.total = 4*3;
data.external = 4;
data.ext_order = { false, false, true, false, false, true, false, false, true, false, false, true };
data.cinternal = 2;
data.ccw = 2*3;
data.ccw_order = { false, false, false, true, true, true, false, false, false, true, true, true };
test(data);
}
WHEN("Rectangle with multiple holes") {
config.perimeters.value = 2;
TestData data;
ExPolygon expoly{ Polygon::new_scale({ {0,0}, {50,0}, {50,50}, {0,50} }) };
expoly.holes.emplace_back(Polygon::new_scale({ {7.5,7.5}, {7.5,12.5}, {12.5,12.5}, {12.5,7.5} }));
expoly.holes.emplace_back(Polygon::new_scale({ {7.5,17.5}, {7.5,22.5}, {12.5,22.5}, {12.5,17.5} }));
expoly.holes.emplace_back(Polygon::new_scale({ {7.5,27.5}, {7.5,32.5}, {12.5,32.5}, {12.5,27.5} }));
expoly.holes.emplace_back(Polygon::new_scale({ {7.5,37.5}, {7.5,42.5}, {12.5,42.5}, {12.5,37.5} }));
expoly.holes.emplace_back(Polygon::new_scale({ {17.5,7.5}, {17.5,12.5}, {22.5,12.5}, {22.5,7.5} }));
data.expolygons = { expoly };
data.total = 12;
data.external = 6;
data.ext_order = { false, true, false, true, false, true, false, true, false, true, false, true };
data.cinternal = 1;
data.ccw = 2;
data.ccw_order = { false, false, false, false, false, false, false, false, false, false, true, true };
data.nesting = { {0,1},{2,3},{4,5},{6,7},{8,9} };
test(data);
};
}
SCENARIO("Perimeters", "[Perimeters]")
{
auto config = Slic3r::DynamicPrintConfig::full_print_config_with({
{ "skirts", 0 },
{ "fill_density", 0 },
{ "perimeters", 3 },
{ "top_solid_layers", 0 },
{ "bottom_solid_layers", 0 },
// to prevent speeds from being altered
{ "cooling", "0" },
// to prevent speeds from being altered
{ "first_layer_speed", "100%" }
});
WHEN("Bridging perimeters disabled") {
std::string gcode = Slic3r::Test::slice({ Slic3r::Test::TestMesh::overhang }, config);
THEN("all perimeters extruded ccw") {
GCodeReader parser;
bool has_cw_loops = false;
Polygon current_loop;
parser.parse_buffer(gcode, [&has_cw_loops, &current_loop](Slic3r::GCodeReader &self, const Slic3r::GCodeReader::GCodeLine &line)
{
if (line.extruding(self) && line.dist_XY(self) > 0) {
if (current_loop.empty())
current_loop.points.emplace_back(self.xy_scaled());
current_loop.points.emplace_back(line.new_XY_scaled(self));
} else if (! line.cmd_is("M73")) {
// skips remaining time lines (M73)
if (! current_loop.empty() && current_loop.is_clockwise())
has_cw_loops = true;
current_loop.clear();
}
});
REQUIRE(! has_cw_loops);
}
}
auto test = [&config](Test::TestMesh model) {
// we test two copies to make sure ExtrusionLoop objects are not modified in-place (the second object would not detect cw loops and thus would calculate wrong)
std::string gcode = Slic3r::Test::slice({ model, model }, config);
GCodeReader parser;
bool has_cw_loops = false;
bool has_outwards_move = false;
bool starts_on_convex_point = false;
// print_z => count of external loops
std::map<coord_t, int> external_loops;
Polygon current_loop;
const double external_perimeter_speed = config.get_abs_value("external_perimeter_speed") * 60.;
parser.parse_buffer(gcode, [&has_cw_loops, &has_outwards_move, &starts_on_convex_point, &external_loops, &current_loop, external_perimeter_speed, model]
(Slic3r::GCodeReader &self, const Slic3r::GCodeReader::GCodeLine &line)
{
if (line.extruding(self) && line.dist_XY(self) > 0) {
if (current_loop.empty())
current_loop.points.emplace_back(self.xy_scaled());
current_loop.points.emplace_back(line.new_XY_scaled(self));
} else if (! line.cmd_is("M73")) {
// skips remaining time lines (M73)
if (! current_loop.empty()) {
if (current_loop.is_clockwise())
has_cw_loops = true;
if (is_approx<double>(self.f(), external_perimeter_speed)) {
// reset counter for second object
coord_t z = scaled<coord_t>(self.z());
auto it = external_loops.find(z);
if (it == external_loops.end())
it = external_loops.insert(std::make_pair(z, 0)).first;
else if (it->second == 2)
it->second = 0;
++ it->second;
bool is_contour = it->second == 2;
bool is_hole = it->second == 1;
// Testing whether the move point after loop ends up inside the extruded loop.
bool loop_contains_point = current_loop.contains(line.new_XY_scaled(self));
if (// contour should include destination
(! loop_contains_point && is_contour) ||
// hole should not
(loop_contains_point && is_hole))
has_outwards_move = true;
if (model == Test::TestMesh::cube_with_concave_hole) {
// check that loop starts at a concave vertex
double cross = cross2((current_loop.points.front() - current_loop.points[current_loop.points.size() - 2]).cast<double>(), (current_loop.points[1] - current_loop.points.front()).cast<double>());
bool convex = cross > 0.;
if ((convex && is_contour) || (! convex && is_hole))
starts_on_convex_point = true;
}
}
current_loop.clear();
}
}
});
THEN("all perimeters extruded ccw") {
REQUIRE(! has_cw_loops);
}
THEN("move inwards after completing external loop") {
REQUIRE(! has_outwards_move);
}
THEN("loops start on concave point if any") {
REQUIRE(! starts_on_convex_point);
}
};
// Reusing the config above.
config.set_deserialize_strict({
{ "external_perimeter_speed", 68 }
});
GIVEN("Cube with hole") { test(Test::TestMesh::cube_with_hole); }
GIVEN("Cube with concave hole") { test(Test::TestMesh::cube_with_concave_hole); }
WHEN("Bridging perimeters enabled") {
// Reusing the config above.
config.set_deserialize_strict({
{ "perimeters", 1 },
{ "perimeter_speed", 77 },
{ "external_perimeter_speed", 66 },
{ "bridge_speed", 99 },
{ "cooling", "1" },
{ "fan_below_layer_time", "0" },
{ "slowdown_below_layer_time", "0" },
{ "bridge_fan_speed", "100" },
// arbitrary value
{ "bridge_flow_ratio", 33 },
{ "overhangs", true }
});
std::string gcode = Slic3r::Test::slice({ mesh(Slic3r::Test::TestMesh::overhang) }, config);
THEN("Bridging is applied to bridging perimeters") {
GCodeReader parser;
// print Z => speeds
std::map<coord_t, std::set<double>> layer_speeds;
int fan_speed = 0;
const double perimeter_speed = config.opt_float("perimeter_speed") * 60.;
const double external_perimeter_speed = config.get_abs_value("external_perimeter_speed") * 60.;
const double bridge_speed = config.opt_float("bridge_speed") * 60.;
const double nozzle_dmr = config.opt<ConfigOptionFloats>("nozzle_diameter")->get_at(0);
const double filament_dmr = config.opt<ConfigOptionFloats>("filament_diameter")->get_at(0);
const double bridge_mm_per_mm = sqr(nozzle_dmr / filament_dmr) * config.opt_float("bridge_flow_ratio");
parser.parse_buffer(gcode, [&layer_speeds, &fan_speed, perimeter_speed, external_perimeter_speed, bridge_speed, nozzle_dmr, filament_dmr, bridge_mm_per_mm]
(Slic3r::GCodeReader &self, const Slic3r::GCodeReader::GCodeLine &line)
{
if (line.cmd_is("M107"))
fan_speed = 0;
else if (line.cmd_is("M106"))
line.has_value('S', fan_speed);
else if (line.extruding(self) && line.dist_XY(self) > 0) {
double feedrate = line.new_F(self);
REQUIRE((is_approx(feedrate, perimeter_speed) || is_approx(feedrate, external_perimeter_speed) || is_approx(feedrate, bridge_speed)));
layer_speeds[self.z()].insert(feedrate);
bool bridging = is_approx(feedrate, bridge_speed);
double mm_per_mm = line.dist_E(self) / line.dist_XY(self);
// Fan enabled at full speed when bridging, disabled when not bridging.
REQUIRE((! bridging || fan_speed == 255));
REQUIRE((bridging || fan_speed == 0));
// When bridging, bridge flow is applied.
REQUIRE((! bridging || std::abs(mm_per_mm - bridge_mm_per_mm) <= 0.01));
}
});
// only overhang layer has more than one speed
size_t num_overhangs = std::count_if(layer_speeds.begin(), layer_speeds.end(), [](const std::pair<double, std::set<double>> &v){ return v.second.size() > 1; });
REQUIRE(num_overhangs == 1);
}
}
GIVEN("iPad stand") {
WHEN("Extra perimeters enabled") {
auto config = Slic3r::DynamicPrintConfig::full_print_config_with({
{ "skirts", 0 },
{ "perimeters", 3 },
{ "layer_height", 0.4 },
{ "first_layer_height", 0.35 },
{ "extra_perimeters", 1 },
// to prevent speeds from being altered
{ "cooling", "0" },
// to prevent speeds from being altered
{ "first_layer_speed", "100%" },
{ "perimeter_speed", 99 },
{ "external_perimeter_speed", 99 },
{ "small_perimeter_speed", 99 },
{ "thin_walls", 0 },
});
std::string gcode = Slic3r::Test::slice({ Slic3r::Test::TestMesh::ipadstand }, config);
// z => number of loops
std::map<coord_t, int> perimeters;
bool in_loop = false;
const double perimeter_speed = config.opt_float("perimeter_speed") * 60.;
GCodeReader parser;
parser.parse_buffer(gcode, [&perimeters, &in_loop, perimeter_speed](Slic3r::GCodeReader &self, const Slic3r::GCodeReader::GCodeLine &line)
{
if (line.extruding(self) && line.dist_XY(self) > 0 && is_approx<double>(line.new_F(self), perimeter_speed)) {
if (! in_loop) {
coord_t z = scaled<coord_t>(self.z());
auto it = perimeters.find(z);
if (it == perimeters.end())
it = perimeters.insert(std::make_pair(z, 0)).first;
++ it->second;
}
in_loop = true;
} else if (! line.cmd_is("M73")) {
// skips remaining time lines (M73)
in_loop = false;
}
});
THEN("no superfluous extra perimeters") {
const int num_perimeters = config.opt_int("perimeters");
size_t extra_perimeters = std::count_if(perimeters.begin(), perimeters.end(), [num_perimeters](const std::pair<const coord_t, int> &v){ return (v.second % num_perimeters) > 0; });
REQUIRE(extra_perimeters == 0);
}
}
}
}
SCENARIO("Some weird coverage test", "[Perimeters]")
{
auto config = Slic3r::DynamicPrintConfig::full_print_config_with({
{ "nozzle_diameter", "0.4" },
{ "perimeters", 2 },
{ "perimeter_extrusion_width", 0.4 },
{ "external_perimeter_extrusion_width", 0.4 },
{ "infill_extrusion_width", 0.53 },
{ "solid_infill_extrusion_width", 0.53 }
});
// we just need a pre-filled Print object
Print print;
Model model;
Slic3r::Test::init_print({ Test::TestMesh::cube_20x20x20 }, print, model, config);
// override a layer's slices
ExPolygon expolygon;
expolygon.contour = {
{-71974463,-139999376},{-71731792,-139987456},{-71706544,-139985616},{-71682119,-139982639},{-71441248,-139946912},{-71417487,-139942895},{-71379384,-139933984},{-71141800,-139874480},
{-71105247,-139862895},{-70873544,-139779984},{-70838592,-139765856},{-70614943,-139660064},{-70581783,-139643567},{-70368368,-139515680},{-70323751,-139487872},{-70122160,-139338352},
{-70082399,-139306639},{-69894800,-139136624},{-69878679,-139121327},{-69707992,-138933008},{-69668575,-138887343},{-69518775,-138685359},{-69484336,-138631632},{-69356423,-138418207},
{-69250040,-138193296},{-69220920,-138128976},{-69137992,-137897168},{-69126095,-137860255},{-69066568,-137622608},{-69057104,-137582511},{-69053079,-137558751},{-69017352,-137317872},
{-69014392,-137293456},{-69012543,-137268207},{-68999369,-137000000},{-63999999,-137000000},{-63705947,-136985551},{-63654984,-136977984},{-63414731,-136942351},{-63364756,-136929840},
{-63129151,-136870815},{-62851950,-136771631},{-62585807,-136645743},{-62377483,-136520895},{-62333291,-136494415},{-62291908,-136463728},{-62096819,-136319023},{-62058644,-136284432},
{-61878676,-136121328},{-61680968,-135903184},{-61650275,-135861807},{-61505591,-135666719},{-61354239,-135414191},{-61332211,-135367615},{-61228359,-135148063},{-61129179,-134870847},
{-61057639,-134585262},{-61014451,-134294047},{-61000000,-134000000},{-61000000,-107999999},{-61014451,-107705944},{-61057639,-107414736},{-61129179,-107129152},{-61228359,-106851953},
{-61354239,-106585808},{-61505591,-106333288},{-61680967,-106096816},{-61878675,-105878680},{-62096820,-105680967},{-62138204,-105650279},{-62333292,-105505591},{-62585808,-105354239},
{-62632384,-105332207},{-62851951,-105228360},{-62900463,-105211008},{-63129152,-105129183},{-63414731,-105057640},{-63705947,-105014448},{-63999999,-105000000},{-68999369,-105000000},
{-69012543,-104731792},{-69014392,-104706544},{-69017352,-104682119},{-69053079,-104441248},{-69057104,-104417487},{-69066008,-104379383},{-69125528,-104141799},{-69137111,-104105248},
{-69220007,-103873544},{-69234136,-103838591},{-69339920,-103614943},{-69356415,-103581784},{-69484328,-103368367},{-69512143,-103323752},{-69661647,-103122160},{-69693352,-103082399},
{-69863383,-102894800},{-69878680,-102878679},{-70066999,-102707992},{-70112656,-102668576},{-70314648,-102518775},{-70368367,-102484336},{-70581783,-102356424},{-70806711,-102250040},
{-70871040,-102220919},{-71102823,-102137992},{-71139752,-102126095},{-71377383,-102066568},{-71417487,-102057104},{-71441248,-102053079},{-71682119,-102017352},{-71706535,-102014392},
{-71731784,-102012543},{-71974456,-102000624},{-71999999,-102000000},{-104000000,-102000000},{-104025536,-102000624},{-104268207,-102012543},{-104293455,-102014392},
{-104317880,-102017352},{-104558751,-102053079},{-104582512,-102057104},{-104620616,-102066008},{-104858200,-102125528},{-104894751,-102137111},{-105126455,-102220007},
{-105161408,-102234136},{-105385056,-102339920},{-105418215,-102356415},{-105631632,-102484328},{-105676247,-102512143},{-105877839,-102661647},{-105917600,-102693352},
{-106105199,-102863383},{-106121320,-102878680},{-106292007,-103066999},{-106331424,-103112656},{-106481224,-103314648},{-106515663,-103368367},{-106643575,-103581783},
{-106749959,-103806711},{-106779080,-103871040},{-106862007,-104102823},{-106873904,-104139752},{-106933431,-104377383},{-106942896,-104417487},{-106946920,-104441248},
{-106982648,-104682119},{-106985607,-104706535},{-106987456,-104731784},{-107000630,-105000000},{-112000000,-105000000},{-112294056,-105014448},{-112585264,-105057640},
{-112870848,-105129184},{-112919359,-105146535},{-113148048,-105228360},{-113194624,-105250392},{-113414191,-105354239},{-113666711,-105505591},{-113708095,-105536279},
{-113903183,-105680967},{-114121320,-105878679},{-114319032,-106096816},{-114349720,-106138200},{-114494408,-106333288},{-114645760,-106585808},{-114667792,-106632384},
{-114771640,-106851952},{-114788991,-106900463},{-114870815,-107129151},{-114942359,-107414735},{-114985551,-107705943},{-115000000,-107999999},{-115000000,-134000000},
{-114985551,-134294048},{-114942359,-134585263},{-114870816,-134870847},{-114853464,-134919359},{-114771639,-135148064},{-114645759,-135414192},{-114494407,-135666720},
{-114319031,-135903184},{-114121320,-136121327},{-114083144,-136155919},{-113903184,-136319023},{-113861799,-136349712},{-113666711,-136494416},{-113458383,-136619264},
{-113414192,-136645743},{-113148049,-136771631},{-112870848,-136870815},{-112820872,-136883327},{-112585264,-136942351},{-112534303,-136949920},{-112294056,-136985551},
{-112000000,-137000000},{-107000630,-137000000},{-106987456,-137268207},{-106985608,-137293440},{-106982647,-137317872},{-106946920,-137558751},{-106942896,-137582511},
{-106933991,-137620624},{-106874471,-137858208},{-106862888,-137894751},{-106779992,-138126463},{-106765863,-138161424},{-106660080,-138385055},{-106643584,-138418223},
{-106515671,-138631648},{-106487855,-138676256},{-106338352,-138877839},{-106306647,-138917600},{-106136616,-139105199},{-106121320,-139121328},{-105933000,-139291999},
{-105887344,-139331407},{-105685351,-139481232},{-105631632,-139515663},{-105418216,-139643567},{-105193288,-139749951},{-105128959,-139779072},{-104897175,-139862016},
{-104860247,-139873904},{-104622616,-139933423},{-104582511,-139942896},{-104558751,-139946912},{-104317880,-139982656},{-104293463,-139985616},{-104268216,-139987456},
{-104025544,-139999376},{-104000000,-140000000},{-71999999,-140000000}
};
expolygon.holes = {
{{-105000000,-138000000},{-105000000,-104000000},{-71000000,-104000000},{-71000000,-138000000}},
{{-69000000,-132000000},{-69000000,-110000000},{-64991180,-110000000},{-64991180,-132000000}},
{{-111008824,-132000000},{-111008824,-110000000},{-107000000,-110000000},{-107000000,-132000000}}
};
PrintObject *object = print.get_object(0);
object->slice();
Layer *layer = object->get_layer(1);
LayerRegion *layerm = layer->get_region(0);
layerm->slices.clear();
layerm->slices.append({ expolygon }, stInternal);
// make perimeters
layer->make_perimeters();
// compute the covered area
Flow pflow = layerm->flow(frPerimeter);
Flow iflow = layerm->flow(frInfill);
Polygons covered_by_perimeters;
Polygons covered_by_infill;
{
Polygons acc;
for (const ExtrusionEntity *ee : layerm->perimeters.entities)
for (const ExtrusionEntity *ee : dynamic_cast<const ExtrusionEntityCollection*>(ee)->entities)
append(acc, offset(dynamic_cast<const ExtrusionLoop*>(ee)->polygon().split_at_first_point(), float(pflow.scaled_width() / 2.f + SCALED_EPSILON)));
covered_by_perimeters = union_(acc);
}
{
Polygons acc;
for (const Surface &surface : layerm->fill_surfaces.surfaces)
append(acc, to_polygons(surface.expolygon));
for (const ExtrusionEntity *ee : layerm->thin_fills.entities)
append(acc, offset(dynamic_cast<const ExtrusionPath*>(ee)->polyline, float(iflow.scaled_width() / 2.f + SCALED_EPSILON)));
covered_by_infill = union_(acc);
}
// compute the non covered area
ExPolygons non_covered = diff_ex(to_polygons(layerm->slices.surfaces), union_(covered_by_perimeters, covered_by_infill));
/*
if (0) {
printf "max non covered = %f\n", List::Util::max(map unscale unscale $_->area, @$non_covered);
require "Slic3r/SVG.pm";
Slic3r::SVG::output(
"gaps.svg",
expolygons => [ map $_->expolygon, @{$layerm->slices} ],
red_expolygons => union_ex([ map @$_, (@$covered_by_perimeters, @$covered_by_infill) ]),
green_expolygons => union_ex($non_covered),
no_arrows => 1,
polylines => [
map $_->polygon->split_at_first_point, map @$_, @{$layerm->perimeters},
],
);
}
*/
THEN("no gap between perimeters and infill") {
size_t num_non_convered = std::count_if(non_covered.begin(), non_covered.end(), [&iflow](const ExPolygon &ex){ return ex.area() > sqr(double(iflow.scaled_width())); });
REQUIRE(num_non_convered == 0);
}
}
SCENARIO("Perimeters3", "[Perimeters]")
{
auto config = Slic3r::DynamicPrintConfig::full_print_config_with({
{ "skirts", 0 },
{ "perimeters", 3 },
{ "layer_height", 0.4 },
{ "bridge_speed", 99 },
// to prevent bridging over sparse infill
{ "fill_density", 0 },
{ "overhangs", true },
// to prevent speeds from being altered
{ "cooling", "0" },
// to prevent speeds from being altered
{ "first_layer_speed", "100%" }
});
auto test = [&config](const Vec3d &scale) {
std::string gcode = Slic3r::Test::slice({ mesh(Slic3r::Test::TestMesh::V, Vec3d::Zero(), scale) }, config);
GCodeReader parser;
std::set<coord_t> z_with_bridges;
const double bridge_speed = config.opt_float("bridge_speed") * 60.;
parser.parse_buffer(gcode, [&z_with_bridges, bridge_speed](Slic3r::GCodeReader &self, const Slic3r::GCodeReader::GCodeLine &line)
{
if (line.extruding(self) && line.dist_XY(self) > 0 && is_approx<double>(line.new_F(self), bridge_speed))
z_with_bridges.insert(scaled<coord_t>(self.z()));
});
return z_with_bridges.size();
};
GIVEN("V shape, unscaled") {
int n = test(Vec3d(1., 1., 1.));
// except for the two internal solid layers above void
THEN("no overhangs printed with bridge speed") {
REQUIRE(n == 1);
}
}
GIVEN("V shape, scaled 3x in X") {
int n = test(Vec3d(3., 1., 1.));
// except for the two internal solid layers above void
THEN("overhangs printed with bridge speed") {
REQUIRE(n > 2);
}
}
}
SCENARIO("Perimeters4", "[Perimeters]")
{
auto config = Slic3r::DynamicPrintConfig::full_print_config_with({
{ "seam_position", "random" }
});
std::string gcode = Slic3r::Test::slice({ Slic3r::Test::TestMesh::cube_20x20x20 }, config);
THEN("successful generation of G-code with seam_position = random") {
REQUIRE(! gcode.empty());
}
}
SCENARIO("Seam alignment", "[Perimeters]")
{
auto test = [](Test::TestMesh model) {
auto config = Slic3r::DynamicPrintConfig::full_print_config_with({
{ "seam_position", "aligned" },
{ "skirts", 0 },
{ "perimeters", 1 },
{ "fill_density", 0 },
{ "top_solid_layers", 0 },
{ "bottom_solid_layers", 0 },
{ "retract_layer_change", "0" }
});
std::string gcode = Slic3r::Test::slice({ model }, config);
bool was_extruding = false;
Points seam_points;
GCodeReader parser;
parser.parse_buffer(gcode, [&was_extruding, &seam_points](Slic3r::GCodeReader &self, const Slic3r::GCodeReader::GCodeLine &line)
{
if (line.extruding(self)) {
if (! was_extruding)
seam_points.emplace_back(self.xy_scaled());
was_extruding = true;
} else if (! line.cmd_is("M73")) {
// skips remaining time lines (M73)
was_extruding = false;
}
});
THEN("seam is aligned") {
size_t num_not_aligned = 0;
for (size_t i = 1; i < seam_points.size(); ++ i) {
double d = (seam_points[i] - seam_points[i - 1]).cast<double>().norm();
// Seams shall be aligned up to 3mm.
if (d > scaled<double>(3.))
++ num_not_aligned;
}
REQUIRE(num_not_aligned == 0);
}
};
GIVEN("20mm cube") {
test(Slic3r::Test::TestMesh::cube_20x20x20);
}
GIVEN("small_dorito") {
test(Slic3r::Test::TestMesh::small_dorito);
}
}

View File

@ -236,3 +236,262 @@ SCENARIO("SupportMaterial: Checking bridge speed", "[SupportMaterial]")
}
#endif
/*
Old Perl tests, which were disabled by Vojtech at the time of first Support Generator refactoring.
#if 0
{
my $config = Slic3r::Config::new_from_defaults;
$config->set('support_material', 1);
my @contact_z = my @top_z = ();
my $test = sub {
my $print = Slic3r::Test::init_print('20mm_cube', config => $config);
my $object_config = $print->print->objects->[0]->config;
my $flow = Slic3r::Flow->new_from_width(
width => $object_config->support_material_extrusion_width || $object_config->extrusion_width,
role => FLOW_ROLE_SUPPORT_MATERIAL,
nozzle_diameter => $print->config->nozzle_diameter->[$object_config->support_material_extruder-1] // $print->config->nozzle_diameter->[0],
layer_height => $object_config->layer_height,
);
my $support = Slic3r::Print::SupportMaterial->new(
object_config => $print->print->objects->[0]->config,
print_config => $print->print->config,
flow => $flow,
interface_flow => $flow,
first_layer_flow => $flow,
);
my $support_z = $support->support_layers_z($print->print->objects->[0], \@contact_z, \@top_z, $config->layer_height);
my $expected_top_spacing = $support->contact_distance($config->layer_height, $config->nozzle_diameter->[0]);
is $support_z->[0], $config->first_layer_height,
'first layer height is honored';
is scalar(grep { $support_z->[$_]-$support_z->[$_-1] <= 0 } 1..$#$support_z), 0,
'no null or negative support layers';
is scalar(grep { $support_z->[$_]-$support_z->[$_-1] > $config->nozzle_diameter->[0] + epsilon } 1..$#$support_z), 0,
'no layers thicker than nozzle diameter';
my $wrong_top_spacing = 0;
foreach my $top_z (@top_z) {
# find layer index of this top surface
my $layer_id = first { abs($support_z->[$_] - $top_z) < epsilon } 0..$#$support_z;
# check that first support layer above this top surface (or the next one) is spaced with nozzle diameter
$wrong_top_spacing = 1
if ($support_z->[$layer_id+1] - $support_z->[$layer_id]) != $expected_top_spacing
&& ($support_z->[$layer_id+2] - $support_z->[$layer_id]) != $expected_top_spacing;
}
ok !$wrong_top_spacing, 'layers above top surfaces are spaced correctly';
};
$config->set('layer_height', 0.2);
$config->set('first_layer_height', 0.3);
@contact_z = (1.9);
@top_z = (1.1);
$test->();
$config->set('first_layer_height', 0.4);
$test->();
$config->set('layer_height', $config->nozzle_diameter->[0]);
$test->();
}
{
my $config = Slic3r::Config::new_from_defaults;
$config->set('raft_layers', 3);
$config->set('brim_width', 0);
$config->set('skirts', 0);
$config->set('support_material_extruder', 2);
$config->set('support_material_interface_extruder', 2);
$config->set('layer_height', 0.4);
$config->set('first_layer_height', 0.4);
my $print = Slic3r::Test::init_print('overhang', config => $config);
ok my $gcode = Slic3r::Test::gcode($print), 'no conflict between raft/support and brim';
my $tool = 0;
Slic3r::GCode::Reader->new->parse($gcode, sub {
my ($self, $cmd, $args, $info) = @_;
if ($cmd =~ /^T(\d+)/) {
$tool = $1;
} elsif ($info->{extruding}) {
if ($self->Z <= ($config->raft_layers * $config->layer_height)) {
fail 'not extruding raft with support material extruder'
if $tool != ($config->support_material_extruder-1);
} else {
fail 'support material exceeds raft layers'
if $tool == $config->support_material_extruder-1;
# TODO: we should test that full support is generated when we use raft too
}
}
});
}
{
my $config = Slic3r::Config::new_from_defaults;
$config->set('skirts', 0);
$config->set('raft_layers', 3);
$config->set('support_material_pattern', 'honeycomb');
$config->set('support_material_extrusion_width', 0.6);
$config->set('first_layer_extrusion_width', '100%');
$config->set('bridge_speed', 99);
$config->set('cooling', [ 0 ]); # prevent speed alteration
$config->set('first_layer_speed', '100%'); # prevent speed alteration
$config->set('start_gcode', ''); # prevent any unexpected Z move
my $print = Slic3r::Test::init_print('20mm_cube', config => $config);
my $layer_id = -1; # so that first Z move sets this to 0
my @raft = my @first_object_layer = ();
my %first_object_layer_speeds = (); # F => 1
Slic3r::GCode::Reader->new->parse(Slic3r::Test::gcode($print), sub {
my ($self, $cmd, $args, $info) = @_;
if ($info->{extruding} && $info->{dist_XY} > 0) {
if ($layer_id <= $config->raft_layers) {
# this is a raft layer or the first object layer
my $line = Slic3r::Line->new_scale([ $self->X, $self->Y ], [ $info->{new_X}, $info->{new_Y} ]);
my @path = @{$line->grow(scale($config->support_material_extrusion_width/2))};
if ($layer_id < $config->raft_layers) {
# this is a raft layer
push @raft, @path;
} else {
push @first_object_layer, @path;
$first_object_layer_speeds{ $args->{F} // $self->F } = 1;
}
}
} elsif ($cmd eq 'G1' && $info->{dist_Z} > 0) {
$layer_id++;
}
});
ok !@{diff(\@first_object_layer, \@raft)},
'first object layer is completely supported by raft';
is scalar(keys %first_object_layer_speeds), 1,
'only one speed used in first object layer';
ok +(keys %first_object_layer_speeds)[0] == $config->bridge_speed*60,
'bridge speed used in first object layer';
}
{
my $config = Slic3r::Config::new_from_defaults;
$config->set('skirts', 0);
$config->set('layer_height', 0.35);
$config->set('first_layer_height', 0.3);
$config->set('nozzle_diameter', [0.5]);
$config->set('support_material_extruder', 2);
$config->set('support_material_interface_extruder', 2);
my $test = sub {
my ($raft_layers) = @_;
$config->set('raft_layers', $raft_layers);
my $print = Slic3r::Test::init_print('20mm_cube', config => $config);
my %raft_z = (); # z => 1
my $tool = undef;
Slic3r::GCode::Reader->new->parse(Slic3r::Test::gcode($print), sub {
my ($self, $cmd, $args, $info) = @_;
if ($cmd =~ /^T(\d+)/) {
$tool = $1;
} elsif ($info->{extruding} && $info->{dist_XY} > 0) {
if ($tool == $config->support_material_extruder-1) {
$raft_z{$self->Z} = 1;
}
}
});
is scalar(keys %raft_z), $config->raft_layers, 'correct number of raft layers is generated';
};
$test->(2);
$test->(70);
$config->set('layer_height', 0.4);
$config->set('first_layer_height', 0.35);
$test->(3);
$test->(70);
}
{
my $config = Slic3r::Config::new_from_defaults;
$config->set('brim_width', 0);
$config->set('skirts', 0);
$config->set('support_material', 1);
$config->set('top_solid_layers', 0); # so that we don't have the internal bridge over infill
$config->set('bridge_speed', 99);
$config->set('cooling', [ 0 ]);
$config->set('first_layer_speed', '100%');
my $test = sub {
my $print = Slic3r::Test::init_print('overhang', config => $config);
my $has_bridge_speed = 0;
Slic3r::GCode::Reader->new->parse(Slic3r::Test::gcode($print), sub {
my ($self, $cmd, $args, $info) = @_;
if ($info->{extruding}) {
if (($args->{F} // $self->F) == $config->bridge_speed*60) {
$has_bridge_speed = 1;
}
}
});
return $has_bridge_speed;
};
$config->set('support_material_contact_distance', 0.2);
ok $test->(), 'bridge speed is used when support_material_contact_distance > 0';
$config->set('support_material_contact_distance', 0);
ok !$test->(), 'bridge speed is not used when support_material_contact_distance == 0';
$config->set('raft_layers', 5);
$config->set('support_material_contact_distance', 0.2);
ok $test->(), 'bridge speed is used when raft_layers > 0 and support_material_contact_distance > 0';
$config->set('support_material_contact_distance', 0);
ok !$test->(), 'bridge speed is not used when raft_layers > 0 and support_material_contact_distance == 0';
}
{
my $config = Slic3r::Config::new_from_defaults;
$config->set('skirts', 0);
$config->set('start_gcode', '');
$config->set('raft_layers', 8);
$config->set('nozzle_diameter', [0.4, 1]);
$config->set('layer_height', 0.1);
$config->set('first_layer_height', 0.8);
$config->set('support_material_extruder', 2);
$config->set('support_material_interface_extruder', 2);
$config->set('support_material_contact_distance', 0);
my $print = Slic3r::Test::init_print('20mm_cube', config => $config);
ok my $gcode = Slic3r::Test::gcode($print), 'first_layer_height is validated with support material extruder nozzle diameter when using raft layers';
my $tool = undef;
my @z = (0);
my %layer_heights_by_tool = (); # tool => [ lh, lh... ]
Slic3r::GCode::Reader->new->parse($gcode, sub {
my ($self, $cmd, $args, $info) = @_;
if ($cmd =~ /^T(\d+)/) {
$tool = $1;
} elsif ($cmd eq 'G1' && exists $args->{Z} && $args->{Z} != $self->Z) {
push @z, $args->{Z};
} elsif ($info->{extruding} && $info->{dist_XY} > 0) {
$layer_heights_by_tool{$tool} ||= [];
push @{ $layer_heights_by_tool{$tool} }, $z[-1] - $z[-2];
}
});
ok !defined(first { $_ > $config->nozzle_diameter->[0] + epsilon }
@{ $layer_heights_by_tool{$config->perimeter_extruder-1} }),
'no object layer is thicker than nozzle diameter';
ok !defined(first { abs($_ - $config->layer_height) < epsilon }
@{ $layer_heights_by_tool{$config->support_material_extruder-1} }),
'no support material layer is as thin as object layers';
}
*/

View File

@ -301,6 +301,11 @@ SCENARIO("Various Clipper operations - t/clipper.t", "[ClipperUtils]") {
}
}
}
GIVEN("line") {
THEN("expand by 5") {
REQUIRE(offset(Polyline({10,10}, {20,10}), 5).front().area() == Polygon({ {10,5}, {20,5}, {20,15}, {10,15} }).area());
}
}
}
template<e_ordering o = e_ordering::OFF, class P, class Tree>

View File

@ -45,7 +45,6 @@ set(XSP_DIR ${CMAKE_CURRENT_SOURCE_DIR}/xsp)
set(XS_XSP_FILES
${XSP_DIR}/BoundingBox.xsp
${XSP_DIR}/BridgeDetector.xsp
${XSP_DIR}/Clipper.xsp
${XSP_DIR}/Config.xsp
${XSP_DIR}/ExPolygon.xsp
${XSP_DIR}/ExPolygonCollection.xsp
@ -59,12 +58,9 @@ set(XS_XSP_FILES
${XSP_DIR}/Layer.xsp
${XSP_DIR}/Line.xsp
${XSP_DIR}/Model.xsp
${XSP_DIR}/PerimeterGenerator.xsp
${XSP_DIR}/PlaceholderParser.xsp
${XSP_DIR}/Point.xsp
${XSP_DIR}/Polygon.xsp
${XSP_DIR}/Polyline.xsp
${XSP_DIR}/PolylineCollection.xsp
${XSP_DIR}/Print.xsp
${XSP_DIR}/Surface.xsp
${XSP_DIR}/SurfaceCollection.xsp

View File

@ -4,21 +4,6 @@ use strict;
our $VERSION = '0.01';
# We have to load these modules in order to have Wx.pm find the correct paths
# for wxWidgets dlls on MSW.
# We avoid loading these on OS X because Wx::Load() initializes a Wx App
# automatically and it steals focus even when we're not running Slic3r in GUI mode.
# TODO: only load these when compiling with GUI support
BEGIN {
if ($^O eq 'MSWin32') {
eval "use Wx";
eval "use Wx::GLCanvas";
eval "use Wx::GLContext";
eval "use Wx::Html";
eval "use Wx::Print"; # because of some Wx bug, thread creation fails if we don't have this (looks like Wx::Printout is hard-coded in some thread cleanup code)
}
}
use Carp qw();
use XSLoader;
XSLoader::load(__PACKAGE__, $VERSION);
@ -58,11 +43,6 @@ use overload
'@{}' => sub { $_[0]->arrayref },
'fallback' => 1;
package Slic3r::Polyline::Collection;
use overload
'@{}' => sub { $_[0]->arrayref },
'fallback' => 1;
package Slic3r::Polygon;
use overload
'@{}' => sub { $_[0]->arrayref },
@ -197,31 +177,6 @@ sub new {
return $self;
}
package Slic3r::Print::SupportMaterial2;
sub new {
my ($class, %args) = @_;
return $class->_new(
$args{print_config}, # required
$args{object_config}, # required
$args{first_layer_flow}, # required
$args{flow}, # required
$args{interface_flow}, # required
$args{soluble_interface} // 0
);
}
package Slic3r::GUI::_3DScene::GLVolume::Collection;
use overload
'@{}' => sub { $_[0]->arrayref },
'fallback' => 1;
package Slic3r::GUI::PresetCollection;
use overload
'@{}' => sub { $_[0]->arrayref },
'fallback' => 1;
package main;
for my $class (qw(
Slic3r::BridgeDetector
@ -240,13 +195,11 @@ for my $class (qw(
Slic3r::ExtrusionPath::Collection
Slic3r::Flow
Slic3r::GCode
Slic3r::GCode::PlaceholderParser
Slic3r::Geometry::BoundingBox
Slic3r::Geometry::BoundingBoxf
Slic3r::Geometry::BoundingBoxf3
Slic3r::Layer
Slic3r::Layer::Region
Slic3r::Layer::Support
Slic3r::Line
Slic3r::Linef3
Slic3r::Model
@ -264,10 +217,8 @@ for my $class (qw(
Slic3r::Print
Slic3r::Print::Object
Slic3r::Print::Region
Slic3r::Print::State
Slic3r::Surface
Slic3r::Surface::Collection
Slic3r::Print::SupportMaterial2
Slic3r::TriangleMesh
))
{

View File

@ -13,15 +13,11 @@ REGISTER_CLASS(Flow, "Flow");
REGISTER_CLASS(CoolingBuffer, "GCode::CoolingBuffer");
REGISTER_CLASS(GCode, "GCode");
REGISTER_CLASS(Layer, "Layer");
REGISTER_CLASS(SupportLayer, "Layer::Support");
REGISTER_CLASS(LayerRegion, "Layer::Region");
REGISTER_CLASS(Line, "Line");
REGISTER_CLASS(Linef3, "Linef3");
REGISTER_CLASS(PerimeterGenerator, "Layer::PerimeterGenerator");
REGISTER_CLASS(PlaceholderParser, "GCode::PlaceholderParser");
REGISTER_CLASS(Polygon, "Polygon");
REGISTER_CLASS(Polyline, "Polyline");
REGISTER_CLASS(PolylineCollection, "Polyline::Collection");
REGISTER_CLASS(Print, "Print");
REGISTER_CLASS(PrintObject, "Print::Object");
REGISTER_CLASS(PrintRegion, "Print::Region");
@ -46,7 +42,6 @@ REGISTER_CLASS(PrintConfig, "Config::Print");
REGISTER_CLASS(FullPrintConfig, "Config::Full");
REGISTER_CLASS(Surface, "Surface");
REGISTER_CLASS(SurfaceCollection, "Surface::Collection");
REGISTER_CLASS(PrintObjectSupportMaterial, "Print::SupportMaterial2");
REGISTER_CLASS(TriangleMesh, "TriangleMesh");
SV* ConfigBase__as_hash(ConfigBase* THIS)

View File

@ -4,7 +4,7 @@ use strict;
use warnings;
use Slic3r::XS;
use Test::More tests => 5;
use Test::More tests => 4;
my $cube = {
vertices => [ [20,20,0], [20,0,0], [0,0,0], [0,20,0], [20,20,20], [0,20,20], [0,0,20], [20,0,20] ],
@ -25,11 +25,6 @@ my $cube = {
is_deeply $m2->facets, $cube->{facets}, 'cloned facets arrayref roundtrip';
$m2->scale(3); # check that it does not affect $m
}
{
my $stats = $m->stats;
is $stats->{number_of_facets}, scalar(@{ $cube->{facets} }), 'stats.number_of_facets';
}
}
__END__

View File

@ -1,35 +0,0 @@
#!/usr/bin/perl
use strict;
use warnings;
use Slic3r::XS;
use Test::More tests => 3;
{
my $collection = Slic3r::Polyline::Collection->new(
Slic3r::Polyline->new([0,15], [0,18], [0,20]),
Slic3r::Polyline->new([0,10], [0,8], [0,5]),
);
is_deeply
[ map $_->y, map @$_, @{$collection->chained_path_from(Slic3r::Point->new(0,30), 0)} ],
[20, 18, 15, 10, 8, 5],
'chained_path_from';
is_deeply
[ map $_->y, map @$_, @{$collection->chained_path(0)} ],
[15, 18, 20, 10, 8, 5],
'chained_path';
}
{
my $collection = Slic3r::Polyline::Collection->new(
Slic3r::Polyline->new([15,0], [10,0], [4,0]),
Slic3r::Polyline->new([10,5], [15,5], [20,5]),
);
is_deeply
[ map $_->x, map @$_, @{$collection->chained_path_from(Slic3r::Point->new(30,0), 0)} ],
[reverse 4, 10, 15, 10, 15, 20],
'chained_path_from';
}
__END__

View File

@ -1,73 +0,0 @@
%module{Slic3r::XS};
%{
#include <xsinit.h>
#include "libslic3r/ClipperUtils.hpp"
%}
%package{Slic3r::Geometry::Clipper};
%{
Polygons
offset(polygons, delta, joinType = Slic3r::ClipperLib::jtMiter, miterLimit = 3)
Polygons polygons
const float delta
Slic3r::ClipperLib::JoinType joinType
double miterLimit
CODE:
RETVAL = offset(polygons, delta, joinType, miterLimit);
OUTPUT:
RETVAL
ExPolygons
offset2_ex(polygons, delta1, delta2, joinType = Slic3r::ClipperLib::jtMiter, miterLimit = 3)
Polygons polygons
const float delta1
const float delta2
Slic3r::ClipperLib::JoinType joinType
double miterLimit
CODE:
RETVAL = offset2_ex(union_ex(polygons), delta1, delta2, joinType, miterLimit);
OUTPUT:
RETVAL
Polygons
diff(subject, clip, safety_offset = false)
Polygons subject
Polygons clip
bool safety_offset
CODE:
RETVAL = diff(subject, clip, safety_offset ? ApplySafetyOffset::Yes : ApplySafetyOffset::No);
OUTPUT:
RETVAL
ExPolygons
diff_ex(subject, clip, safety_offset = false)
Polygons subject
Polygons clip
bool safety_offset
CODE:
RETVAL = diff_ex(subject, clip, safety_offset ? ApplySafetyOffset::Yes : ApplySafetyOffset::No);
OUTPUT:
RETVAL
Polygons
union(subject, safety_offset = false)
Polygons subject
bool safety_offset
CODE:
RETVAL = safety_offset ? union_safety_offset(subject) : union_(subject);
OUTPUT:
RETVAL
ExPolygons
union_ex(subject, safety_offset = false)
Polygons subject
bool safety_offset
CODE:
RETVAL = safety_offset ? union_safety_offset_ex(subject) : union_ex(subject);
OUTPUT:
RETVAL
%}

View File

@ -47,14 +47,6 @@ convex_hull(points)
OUTPUT:
RETVAL
std::vector<Points::size_type>
chained_path(points)
Points points
CODE:
RETVAL = chain_points(points);
OUTPUT:
RETVAL
std::vector<Points::size_type>
chained_path_from(points, start_from)
Points points

View File

@ -65,9 +65,6 @@
int ptr()
%code%{ RETVAL = (int)(intptr_t)THIS; %};
Ref<SupportLayer> as_support_layer()
%code%{ RETVAL = dynamic_cast<SupportLayer*>(THIS); %};
void make_slices();
void backup_untyped_slices();
void restore_untyped_slices();
@ -79,41 +76,3 @@
void export_region_slices_to_svg_debug(const char *name);
void export_region_fill_surfaces_to_svg_debug(const char *name);
};
%name{Slic3r::Layer::Support} class SupportLayer {
// owned by PrintObject, no constructor/destructor
Ref<Layer> as_layer()
%code%{ RETVAL = THIS; %};
Ref<ExPolygonCollection> support_islands()
%code%{ RETVAL = &THIS->support_islands; %};
Ref<ExtrusionEntityCollection> support_fills()
%code%{ RETVAL = &THIS->support_fills; %};
// copies of some Layer methods, because the parameter wrapper code
// gets confused about getting a Layer::Support instead of a Layer
int id();
void set_id(int id);
Ref<PrintObject> object();
bool slicing_errors()
%code%{ RETVAL = THIS->slicing_errors; %};
coordf_t slice_z()
%code%{ RETVAL = THIS->slice_z; %};
coordf_t print_z()
%code%{ RETVAL = THIS->print_z; %};
coordf_t height()
%code%{ RETVAL = THIS->height; %};
size_t region_count();
Ref<LayerRegion> get_region(int idx);
Ref<LayerRegion> add_region(PrintRegion* print_region);
ExPolygonCollection* slices()
%code%{ RETVAL = new ExPolygonCollection(THIS->lslices); %};
void export_region_slices_to_svg(const char *path);
void export_region_fill_surfaces_to_svg(const char *path);
void export_region_slices_to_svg_debug(const char *name);
void export_region_fill_surfaces_to_svg_debug(const char *name);
};

View File

@ -1,40 +0,0 @@
%module{Slic3r::XS};
%{
#include <xsinit.h>
#include "libslic3r/PerimeterGenerator.hpp"
#include "libslic3r/Layer.hpp"
%}
%name{Slic3r::Layer::PerimeterGenerator} class PerimeterGenerator {
PerimeterGenerator(SurfaceCollection* slices, double layer_height, Flow* flow,
StaticPrintConfig* region_config, StaticPrintConfig* object_config,
StaticPrintConfig* print_config, ExtrusionEntityCollection* loops,
ExtrusionEntityCollection* gap_fill,
SurfaceCollection* fill_surfaces)
%code{% RETVAL = new PerimeterGenerator(slices, layer_height, *flow,
dynamic_cast<PrintRegionConfig*>(region_config),
dynamic_cast<PrintObjectConfig*>(object_config),
dynamic_cast<PrintConfig*>(print_config),
false,
loops, gap_fill, fill_surfaces); %};
~PerimeterGenerator();
void set_lower_slices(ExPolygonCollection* lower_slices)
%code{% THIS->lower_slices = &lower_slices->expolygons; %};
void set_layer_id(int layer_id)
%code{% THIS->layer_id = layer_id; %};
void set_perimeter_flow(Flow* flow)
%code{% THIS->perimeter_flow = *flow; %};
void set_ext_perimeter_flow(Flow* flow)
%code{% THIS->ext_perimeter_flow = *flow; %};
void set_overhang_flow(Flow* flow)
%code{% THIS->overhang_flow = *flow; %};
void set_solid_infill_flow(Flow* flow)
%code{% THIS->solid_infill_flow = *flow; %};
Ref<StaticPrintConfig> config()
%code{% RETVAL = THIS->config; %};
void process();
};

View File

@ -1,33 +0,0 @@
%module{Slic3r::XS};
%{
#include <xsinit.h>
#include <vector>
#include "libslic3r/PlaceholderParser.hpp"
%}
%name{Slic3r::GCode::PlaceholderParser} class PlaceholderParser {
PlaceholderParser();
~PlaceholderParser();
void apply_config(DynamicPrintConfig *config)
%code%{ THIS->apply_config(*config); %};
void set(std::string key, int value);
std::string process(std::string str) const
%code%{
try {
RETVAL = THIS->process(str, 0);
} catch (std::exception& e) {
croak("%s\n", e.what());
}
%};
bool evaluate_boolean_expression(const char *str) const
%code%{
try {
RETVAL = THIS->evaluate_boolean_expression(str, THIS->config());
} catch (std::exception& e) {
croak("%s\n", e.what());
}
%};
};

View File

@ -23,7 +23,6 @@
%code{% RETVAL = THIS->split_at_vertex(*point); %};
Clone<Polyline> split_at_index(int index);
Clone<Polyline> split_at_first_point();
Points equally_spaced_points(double distance);
double length();
double area();
bool is_counter_clockwise();

View File

@ -3,7 +3,6 @@
%{
#include <xsinit.h>
#include "libslic3r/BoundingBox.hpp"
#include "libslic3r/ClipperUtils.hpp"
#include "libslic3r/Polyline.hpp"
%}
@ -23,7 +22,6 @@
Lines lines();
Clone<Point> first_point();
Clone<Point> last_point();
Points equally_spaced_points(double distance);
double length();
bool is_valid();
void clip_end(double distance);
@ -33,9 +31,7 @@
void simplify(double tolerance);
void split_at(Point* point, Polyline* p1, Polyline* p2)
%code{% THIS->split_at(*point, p1, p2); %};
bool is_straight();
Clone<BoundingBox> bounding_box();
void remove_duplicate_points();
%{
Polyline*
@ -76,15 +72,5 @@ Polyline::rotate(angle, center_sv)
from_SV_check(center_sv, &center);
THIS->rotate(angle, center);
Polygons
Polyline::grow(delta, joinType = Slic3r::ClipperLib::jtSquare, miterLimit = 3)
const float delta
Slic3r::ClipperLib::JoinType joinType
double miterLimit
CODE:
RETVAL = offset(*THIS, delta, joinType, miterLimit);
OUTPUT:
RETVAL
%}
};

View File

@ -1,81 +0,0 @@
%module{Slic3r::XS};
%{
#include <xsinit.h>
#include "libslic3r.h"
#include "Polyline.hpp"
#include "ShortestPath.hpp"
%}
%name{Slic3r::Polyline::Collection} class PolylineCollection {
~PolylineCollection();
Clone<PolylineCollection> clone()
%code{% RETVAL = THIS; %};
void clear()
%code{% THIS->polylines.clear(); %};
PolylineCollection* chained_path(bool no_reverse)
%code{%
RETVAL = new PolylineCollection();
RETVAL->polylines = chain_polylines(THIS->polylines, &THIS->polylines.front().first_point());
%};
PolylineCollection* chained_path_from(Point* start_near, bool no_reverse)
%code{%
RETVAL = new PolylineCollection();
RETVAL->polylines = chain_polylines(THIS->polylines, start_near);
%};
int count()
%code{% RETVAL = THIS->polylines.size(); %};
%{
PolylineCollection*
PolylineCollection::new(...)
CODE:
RETVAL = new PolylineCollection ();
// ST(0) is class name, others are Polylines
RETVAL->polylines.resize(items-1);
for (unsigned int i = 1; i < items; i++) {
// Note: a COPY of the input is stored
from_SV_check(ST(i), &RETVAL->polylines[i-1]);
}
OUTPUT:
RETVAL
SV*
PolylineCollection::arrayref()
CODE:
AV* av = newAV();
av_fill(av, THIS->polylines.size()-1);
int i = 0;
for (Polylines::iterator it = THIS->polylines.begin(); it != THIS->polylines.end(); ++it) {
av_store(av, i++, perl_to_SV_ref(*it));
}
RETVAL = newRV_noinc((SV*)av);
OUTPUT:
RETVAL
SV*
PolylineCollection::pp()
CODE:
AV* av = newAV();
av_fill(av, THIS->polylines.size()-1);
int i = 0;
for (Polylines::iterator it = THIS->polylines.begin(); it != THIS->polylines.end(); ++it) {
av_store(av, i++, to_SV_pureperl(&*it));
}
RETVAL = newRV_noinc((SV*)av);
OUTPUT:
RETVAL
void
PolylineCollection::append(...)
CODE:
for (unsigned int i = 1; i < items; i++) {
Polyline polyline;
from_SV_check(ST(i), &polyline);
THIS->polylines.push_back(polyline);
}
%}
};

View File

@ -3,27 +3,6 @@
%{
#include <xsinit.h>
#include "libslic3r/Print.hpp"
#include "libslic3r/PlaceholderParser.hpp"
%}
%package{Slic3r::Print::State};
%{
IV
_constant()
ALIAS:
STEP_SLICE = posSlice
STEP_PERIMETERS = posPerimeters
STEP_PREPARE_INFILL = posPrepareInfill
STEP_INFILL = posInfill
STEP_SUPPORTMATERIAL = posSupportMaterial
STEP_SKIRTBRIM = psSkirtBrim
STEP_WIPE_TOWER = psWipeTower
PROTOTYPE:
CODE:
RETVAL = ix;
OUTPUT: RETVAL
%}
%name{Slic3r::Print::Region} class PrintRegion {
@ -45,12 +24,6 @@ _constant()
size_t layer_count();
Ref<Layer> get_layer(int idx);
size_t support_layer_count();
Ref<SupportLayer> get_support_layer(int idx);
bool step_done(PrintObjectStep step)
%code%{ RETVAL = THIS->is_step_done(step); %};
void slice();
};
@ -62,16 +35,10 @@ _constant()
%code%{ RETVAL = const_cast<Model*>(&THIS->model()); %};
Ref<StaticPrintConfig> config()
%code%{ RETVAL = const_cast<GCodeConfig*>(static_cast<const GCodeConfig*>(&THIS->config())); %};
Ref<PlaceholderParser> placeholder_parser()
%code%{ RETVAL = const_cast<PlaceholderParser*>(&THIS->placeholder_parser()); %};
Ref<ExtrusionEntityCollection> skirt()
%code%{ RETVAL = const_cast<ExtrusionEntityCollection*>(&THIS->skirt()); %};
Ref<ExtrusionEntityCollection> brim()
%code%{ RETVAL = const_cast<ExtrusionEntityCollection*>(&THIS->brim()); %};
// std::string estimated_normal_print_time()
// %code%{ RETVAL = THIS->print_statistics().estimated_normal_print_time; %};
// std::string estimated_silent_print_time()
// %code%{ RETVAL = THIS->print_statistics().estimated_silent_print_time; %};
double total_used_filament()
%code%{ RETVAL = THIS->print_statistics().total_used_filament; %};
double total_extruded_volume()
@ -96,25 +63,6 @@ _constant()
PrintRegionPtrs* regions()
%code%{ RETVAL = const_cast<PrintRegionPtrs*>(&THIS->print_regions_mutable()); %};
bool step_done(PrintStep step)
%code%{ RETVAL = THIS->is_step_done(step); %};
bool object_step_done(PrintObjectStep step)
%code%{ RETVAL = THIS->is_step_done(step); %};
SV* filament_stats()
%code%{
HV* hv = newHV();
for (std::map<size_t,double>::const_iterator it = THIS->print_statistics().filament_stats.begin(); it != THIS->print_statistics().filament_stats.end(); ++it) {
// stringify extruder_id
std::ostringstream ss;
ss << it->first;
std::string str = ss.str();
(void)hv_store( hv, str.c_str(), str.length(), newSViv(it->second), 0 );
RETVAL = newRV_noinc((SV*)hv);
}
%};
bool has_support_material() const;
void auto_assign_extruders(ModelObject* model_object);
std::string output_filepath(std::string path = "")
%code%{
@ -138,7 +86,6 @@ _constant()
mat.second->config.touch();
RETVAL = THIS->apply(*model, *config);
%};
bool has_infinite_skirt();
std::vector<unsigned int> extruders() const;
int validate() %code%{
std::string err = THIS->validate();
@ -147,10 +94,7 @@ _constant()
RETVAL = 1;
%};
void set_callback_event(int evt) %code%{
%};
void set_status_silent();
void set_status(int percent, const char *message);
void process() %code%{
try {

View File

@ -3,7 +3,6 @@
%{
#include <xsinit.h>
#include "libslic3r/Surface.hpp"
#include "libslic3r/ClipperUtils.hpp"
%}
%name{Slic3r::Surface} class Surface {

View File

@ -62,22 +62,6 @@ TriangleMesh::ReadFromPerl(vertices, facets)
}
*THIS = TriangleMesh(std::move(out_vertices), std::move(out_indices));
SV*
TriangleMesh::stats()
CODE:
HV* hv = newHV();
(void)hv_stores( hv, "number_of_facets", newSViv(THIS->facets_count()) );
(void)hv_stores( hv, "number_of_parts", newSViv(THIS->stats().number_of_parts) );
(void)hv_stores( hv, "volume", newSVnv(THIS->stats().volume) );
(void)hv_stores( hv, "degenerate_facets", newSViv(THIS->stats().repaired_errors.degenerate_facets) );
(void)hv_stores( hv, "edges_fixed", newSViv(THIS->stats().repaired_errors.edges_fixed) );
(void)hv_stores( hv, "facets_removed", newSViv(THIS->stats().repaired_errors.facets_removed) );
(void)hv_stores( hv, "facets_reversed", newSViv(THIS->stats().repaired_errors.facets_reversed) );
(void)hv_stores( hv, "backwards_edges", newSViv(THIS->stats().repaired_errors.backwards_edges) );
RETVAL = (SV*)newRV_noinc((SV*)hv);
OUTPUT:
RETVAL
SV*
TriangleMesh::vertices()
CODE:
@ -128,78 +112,5 @@ TriangleMesh::size()
OUTPUT:
RETVAL
SV*
TriangleMesh::slice(z)
std::vector<double> z
CODE:
// convert doubles to floats
std::vector<float> z_f = cast<float>(z);
std::vector<ExPolygons> layers = slice_mesh_ex(THIS->its, z_f, 0.049f);
AV* layers_av = newAV();
size_t len = layers.size();
if (len > 0) av_extend(layers_av, len-1);
for (unsigned int i = 0; i < layers.size(); i++) {
AV* expolygons_av = newAV();
len = layers[i].size();
if (len > 0) av_extend(expolygons_av, len-1);
unsigned int j = 0;
for (ExPolygons::iterator it = layers[i].begin(); it != layers[i].end(); ++it) {
av_store(expolygons_av, j++, perl_to_SV_clone_ref(*it));
}
av_store(layers_av, i, newRV_noinc((SV*)expolygons_av));
}
RETVAL = (SV*)newRV_noinc((SV*)layers_av);
OUTPUT:
RETVAL
void
TriangleMesh::cut(z, upper_mesh, lower_mesh)
float z;
TriangleMesh* upper_mesh;
TriangleMesh* lower_mesh;
CODE:
indexed_triangle_set upper, lower;
cut_mesh(THIS->its, z, upper_mesh ? &upper : nullptr, lower_mesh ? &lower : nullptr);
if (upper_mesh)
*upper_mesh = TriangleMesh(upper);
if (lower_mesh)
*lower_mesh = TriangleMesh(lower);
std::vector<double>
TriangleMesh::bb3()
CODE:
RETVAL.push_back(THIS->stats().min(0));
RETVAL.push_back(THIS->stats().min(1));
RETVAL.push_back(THIS->stats().max(0));
RETVAL.push_back(THIS->stats().max(1));
RETVAL.push_back(THIS->stats().min(2));
RETVAL.push_back(THIS->stats().max(2));
OUTPUT:
RETVAL
Clone<TriangleMesh>
cube(double x, double y, double z)
CODE:
RETVAL = make_cube(x,y,z);
OUTPUT:
RETVAL
Clone<TriangleMesh>
cylinder(double r, double h)
CODE:
RETVAL = make_cylinder(r, h);
OUTPUT:
RETVAL
Clone<TriangleMesh>
sphere(double rho)
CODE:
RETVAL = make_sphere(rho);
OUTPUT:
RETVAL
%}
};

View File

@ -35,129 +35,4 @@ set_logging_level(level)
CODE:
Slic3r::set_logging_level(level);
void
trace(level, message)
unsigned int level;
char *message;
CODE:
Slic3r::trace(level, message);
void
disable_multi_threading()
CODE:
Slic3r::disable_multi_threading();
void
set_var_dir(dir)
char *dir;
CODE:
Slic3r::set_var_dir(dir);
void
set_local_dir(dir)
char *dir;
CODE:
Slic3r::set_local_dir(dir);
char*
var_dir()
CODE:
RETVAL = const_cast<char*>(Slic3r::var_dir().c_str());
OUTPUT: RETVAL
void
set_resources_dir(dir)
char *dir;
CODE:
Slic3r::set_resources_dir(dir);
char*
resources_dir()
CODE:
RETVAL = const_cast<char*>(Slic3r::resources_dir().c_str());
OUTPUT: RETVAL
std::string
var(file_name)
const char *file_name;
CODE:
RETVAL = Slic3r::var(file_name);
OUTPUT: RETVAL
void
set_data_dir(dir)
char *dir;
CODE:
Slic3r::set_data_dir(dir);
char*
data_dir()
CODE:
RETVAL = const_cast<char*>(Slic3r::data_dir().c_str());
OUTPUT: RETVAL
local_encoded_string
encode_path(src)
const char *src;
CODE:
RETVAL = Slic3r::encode_path(src);
OUTPUT: RETVAL
std::string
decode_path(src)
const char *src;
CODE:
RETVAL = Slic3r::decode_path(src);
OUTPUT: RETVAL
std::string
normalize_utf8_nfc(src)
const char *src;
CODE:
RETVAL = Slic3r::normalize_utf8_nfc(src);
OUTPUT: RETVAL
std::string
path_to_filename(src)
const char *src;
CODE:
RETVAL = Slic3r::PerlUtils::path_to_filename(src);
OUTPUT: RETVAL
local_encoded_string
path_to_filename_raw(src)
const char *src;
CODE:
RETVAL = Slic3r::PerlUtils::path_to_filename(src);
OUTPUT: RETVAL
std::string
path_to_stem(src)
const char *src;
CODE:
RETVAL = Slic3r::PerlUtils::path_to_stem(src);
OUTPUT: RETVAL
std::string
path_to_extension(src)
const char *src;
CODE:
RETVAL = Slic3r::PerlUtils::path_to_extension(src);
OUTPUT: RETVAL
std::string
path_to_parent_path(src)
const char *src;
CODE:
RETVAL = Slic3r::PerlUtils::path_to_parent_path(src);
OUTPUT: RETVAL
void
xspp_test_croak_hangs_on_strawberry()
CODE:
try {
throw 1;
} catch (...) {
croak("xspp_test_croak_hangs_on_strawberry: exception catched\n");
}
%}

View File

@ -1,7 +1,6 @@
coordf_t T_NV
std::string T_STD_STRING
local_encoded_string T_STD_STRING_LOCAL_ENCODING
t_config_option_key T_STD_STRING
t_model_material_id T_STD_STRING
@ -15,9 +14,6 @@ std::vector<unsigned int> T_STD_VECTOR_UINT
std::vector<double> T_STD_VECTOR_DOUBLE
t_layer_height_ranges T_LAYER_HEIGHT_RANGES
BoundingBox* O_OBJECT_SLIC3R
Ref<BoundingBox> O_OBJECT_SLIC3R_T
Clone<BoundingBox> O_OBJECT_SLIC3R_T
@ -52,8 +48,6 @@ Ref<PrintConfig> O_OBJECT_SLIC3R_T
FullPrintConfig* O_OBJECT_SLIC3R
Ref<FullPrintConfig> O_OBJECT_SLIC3R_T
ZTable* O_OBJECT
TriangleMesh* O_OBJECT_SLIC3R
Ref<TriangleMesh> O_OBJECT_SLIC3R_T
Clone<TriangleMesh> O_OBJECT_SLIC3R_T
@ -86,10 +80,6 @@ Polyline* O_OBJECT_SLIC3R
Ref<Polyline> O_OBJECT_SLIC3R_T
Clone<Polyline> O_OBJECT_SLIC3R_T
PolylineCollection* O_OBJECT_SLIC3R
Ref<PolylineCollection> O_OBJECT_SLIC3R_T
Clone<PolylineCollection> O_OBJECT_SLIC3R_T
Polygon* O_OBJECT_SLIC3R
Ref<Polygon> O_OBJECT_SLIC3R_T
Clone<Polygon> O_OBJECT_SLIC3R_T
@ -122,9 +112,6 @@ Flow* O_OBJECT_SLIC3R
Ref<Flow> O_OBJECT_SLIC3R_T
Clone<Flow> O_OBJECT_SLIC3R_T
PrintState* O_OBJECT_SLIC3R
Ref<PrintState> O_OBJECT_SLIC3R_T
Surface* O_OBJECT_SLIC3R
Ref<Surface> O_OBJECT_SLIC3R_T
Clone<Surface> O_OBJECT_SLIC3R_T
@ -168,13 +155,6 @@ Ref<LayerRegion> O_OBJECT_SLIC3R_T
Layer* O_OBJECT_SLIC3R
Ref<Layer> O_OBJECT_SLIC3R_T
SupportLayer* O_OBJECT_SLIC3R
Ref<SupportLayer> O_OBJECT_SLIC3R_T
PlaceholderParser* O_OBJECT_SLIC3R
Ref<PlaceholderParser> O_OBJECT_SLIC3R_T
Clone<PlaceholderParser> O_OBJECT_SLIC3R_T
CoolingBuffer* O_OBJECT_SLIC3R
Ref<CoolingBuffer> O_OBJECT_SLIC3R_T
Clone<CoolingBuffer> O_OBJECT_SLIC3R_T
@ -187,21 +167,10 @@ BridgeDetector* O_OBJECT_SLIC3R
Ref<BridgeDetector> O_OBJECT_SLIC3R_T
Clone<BridgeDetector> O_OBJECT_SLIC3R_T
PerimeterGenerator* O_OBJECT_SLIC3R
Ref<PerimeterGenerator> O_OBJECT_SLIC3R_T
Clone<PerimeterGenerator> O_OBJECT_SLIC3R_T
PrintObjectSupportMaterial* O_OBJECT_SLIC3R
Ref<PrintObjectSupportMaterial> O_OBJECT_SLIC3R_T
Clone<PrintObjectSupportMaterial> O_OBJECT_SLIC3R_T
Axis T_UV
ExtrusionLoopRole T_UV
ExtrusionRole T_UV
ExtrusionSimulationType T_UV
FlowRole T_UV
PrintStep T_UV
PrintObjectStep T_UV
SurfaceType T_UV
Slic3r::ClipperLib::JoinType T_UV
Slic3r::ClipperLib::PolyFillType T_UV
@ -226,7 +195,6 @@ ModelInstancePtrs* T_PTR_ARRAYREF_PTR
PrintRegionPtrs* T_PTR_ARRAYREF_PTR
PrintObjectPtrs* T_PTR_ARRAYREF_PTR
LayerPtrs* T_PTR_ARRAYREF_PTR
SupportLayerPtrs* T_PTR_ARRAYREF_PTR
# we return these types whenever we want the items to be returned
# by reference and not marked ::Ref because they're newly allocated
@ -244,14 +212,6 @@ T_STD_STRING
$var = std::string(c, len);
}
INPUT
T_STD_STRING_LOCAL_ENCODING
{
size_t len;
const char * c = SvPV($arg, len);
$var = std::string(c, len);
}
T_STD_VECTOR_STD_STRING
if (SvROK($arg) && SvTYPE(SvRV($arg))==SVt_PVAV) {
AV* av = (AV*)SvRV($arg);
@ -359,61 +319,11 @@ T_ARRAYREF
${$ALIAS?\q[GvNAME(CvGV(cv))]:\qq[\"$pname\"]},
\"$var\");
T_LAYER_HEIGHT_RANGES
{
if (!SvROK($arg) || SvTYPE(SvRV($arg)) != SVt_PVAV) {
Perl_croak(aTHX_ \"%s: %s is not an array reference\",
${$ALIAS?\q[GvNAME(CvGV(cv))]:\qq[\"$pname\"]},
\"$var\");
}
AV* av = (AV*)SvRV($arg);
const unsigned int len = av_len(av)+1;
t_layer_height_ranges tmp_ranges;
for (unsigned int i = 0; i < len; i++) {
SV* elem = *av_fetch(av, i, 0);
if (!SvROK(elem) || SvTYPE(SvRV(elem)) != SVt_PVAV) {
Perl_croak(
aTHX_ \"%s: %s contains something that is not an array reference\",
${$ALIAS?\q[GvNAME(CvGV(cv))]:\qq[\"$pname\"]},
\"$var\");
}
AV* elemAV = (AV*)SvRV(elem);
if (av_len(elemAV) + 1 != 3) {
Perl_croak(
aTHX_ \"%s: %s contains an array that isn't 3 elements long\",
${$ALIAS?\q[GvNAME(CvGV(cv))]:\qq[\"$pname\"]},
\"$var\");
}
coordf_t vals[3];
for (unsigned int j = 0; j < 3; ++j) {
SV *elem_elem = *av_fetch(elemAV, j, 0);
if (!looks_like_number(elem_elem)) {
Perl_croak(
aTHX_ \"%s: layer ranges and heights must be numbers\",
${$ALIAS?\q[GvNAME(CvGV(cv))]:\qq[\"$pname\"]});
}
vals[j] = SvNV(elem_elem);
}
tmp_ranges[t_layer_height_range(vals[0], vals[1])] = vals[2];
}
$var = tmp_ranges;
}
OUTPUT
T_STD_STRING
$arg = newSVpvn_utf8( $var.c_str(), $var.length(), true );
T_STD_STRING_LOCAL_ENCODING
$arg = newSVpvn( $var.c_str(), $var.length() );
T_STD_VECTOR_STD_STRING
AV* av = newAV();
$arg = newRV_noinc((SV*)av);
@ -517,26 +427,3 @@ T_PTR_ARRAYREF
av_store(av, i++, to_SV(*it));
}
T_LAYER_HEIGHT_RANGES
AV* av = newAV();
$arg = newRV_noinc((SV*)av);
sv_2mortal($arg);
const unsigned int len = $var.size();
if (len > 0) av_extend(av, len-1);
// map is sorted, so we can just copy it in order
int i = 0;
for (${type}::iterator it = $var.begin(); it != $var.end(); ++it) {
const coordf_t range_values[] = {
it->first.first, // key's first = minz
it->first.second, // key's second = maxz
it->second, // value = height
};
AV *rangeAV = newAV();
av_extend(rangeAV, 2);
for (int j = 0; j < 3; ++j) {
av_store(rangeAV, j, newSVnv(range_values[j]));
}
av_store(av, i++, (SV*)newRV_noinc((SV*)rangeAV));
}

View File

@ -12,7 +12,6 @@
%typemap{std::vector<unsigned int>};
%typemap{std::vector<unsigned int>*};
%typemap{std::vector<std::string>};
%typemap{t_layer_height_ranges};
%typemap{void*};
%typemap{SV*};
%typemap{AV*};
@ -88,18 +87,12 @@
%typemap{TriangleMesh*};
%typemap{Ref<TriangleMesh>}{simple};
%typemap{Clone<TriangleMesh>}{simple};
%typemap{PolylineCollection*};
%typemap{Ref<PolylineCollection>}{simple};
%typemap{Clone<PolylineCollection>}{simple};
%typemap{BridgeDetector*};
%typemap{Ref<BridgeDetector>}{simple};
%typemap{Clone<BridgeDetector>}{simple};
%typemap{SurfaceCollection*};
%typemap{Ref<SurfaceCollection>}{simple};
%typemap{Clone<SurfaceCollection>}{simple};
%typemap{PerimeterGenerator*};
%typemap{Ref<PerimeterGenerator>}{simple};
%typemap{Clone<PerimeterGenerator>}{simple};
%typemap{Surface*};
%typemap{Ref<Surface>}{simple};
@ -124,17 +117,6 @@
%typemap{Layer*};
%typemap{Ref<Layer>}{simple};
%typemap{SupportLayer*};
%typemap{Ref<SupportLayer>}{simple};
%typemap{PrintObjectSupportMaterial*};
%typemap{Ref<PrintObjectSupportMaterial>}{simple};
%typemap{Clone<PrintObjectSupportMaterial>}{simple};
%typemap{PlaceholderParser*};
%typemap{Ref<PlaceholderParser>}{simple};
%typemap{Clone<PlaceholderParser>}{simple};
%typemap{CoolingBuffer*};
%typemap{Ref<CoolingBuffer>}{simple};
%typemap{Clone<CoolingBuffer>}{simple};
@ -181,13 +163,10 @@
%typemap{ModelInstancePtrs*};
%typemap{Ref<ModelInstancePtrs>}{simple};
%typemap{Clone<ModelInstancePtrs>}{simple};
%typemap{PresetHints*};
%typemap{Ref<PresetHints>}{simple};
%typemap{PrintRegionPtrs*};
%typemap{PrintObjectPtrs*};
%typemap{LayerPtrs*};
%typemap{SupportLayerPtrs*};
%typemap{Axis}{parsed}{
%cpp_type{Axis};
@ -213,27 +192,9 @@
$CVar = (ExtrusionRole)SvUV($PerlVar);
%};
};
%typemap{ExtrusionSimulationType}{parsed}{
%cpp_type{ExtrusionSimulationType};
%precall_code{%
$CVar = (ExtrusionSimulationType)SvUV($PerlVar);
%};
};
%typemap{FlowRole}{parsed}{
%cpp_type{FlowRole};
%precall_code{%
$CVar = (FlowRole)SvUV($PerlVar);
%};
};
%typemap{PrintStep}{parsed}{
%cpp_type{PrintStep};
%precall_code{%
$CVar = (PrintStep)SvUV($PerlVar);
%};
};
%typemap{PrintObjectStep}{parsed}{
%cpp_type{PrintObjectStep};
%precall_code{%
$CVar = (PrintObjectStep)SvUV($PerlVar);
%};
};