File Coverage

blib/lib/MooseX/MungeHas.pm
Criterion Covered Total %
statement 147 180 81.6
branch 37 72 51.3
condition 12 24 50.0
subroutine 17 19 89.4
pod n/a
total 213 295 72.2


line stmt bran cond sub pod time code
1             package MooseX::MungeHas;
2              
3 7     7   2527907 use 5.008;
  7         59  
4 7     7   41 use strict;
  7         13  
  7         151  
5 7     7   31 use warnings;
  7         13  
  7         301  
6              
7             BEGIN {
8 7     7   20 $MooseX::MungeHas::AUTHORITY = 'cpan:TOBYINK';
9 7         170 $MooseX::MungeHas::VERSION = '0.011';
10             };
11              
12 7     7   40 use Carp qw(croak);
  7         20  
  7         392  
13 7     7   56 use Scalar::Util qw(blessed);
  7         23  
  7         765  
14              
15             BEGIN {
16 7     7   65 for my $backend (qw/ Eval::TypeTiny Eval::Closure /)
17             {
18             last if eval(
19 7 50       576 "require $backend; *eval_closure = \\&$backend\::eval_closure;"
20             );
21             }
22 7 50       264 exists(&eval_closure)
23             or croak "Could not load Eval::TypeTiny";
24             };
25              
26             sub import
27             {
28 7     7   43 no strict qw(refs);
  7         13  
  7         842  
29            
30 9     9   13170 my $class = shift;
31 9         24 my $caller = caller;
32            
33 9 50       16 my $orig = \&{"$caller\::has"}
  9         56  
34             or croak "$caller does not have a 'has' function to munge";
35            
36             my %export = (@_ == 1 and ref($_[0]) eq "HASH")
37 9 100 100     67 ? %{ $_[0] }
  1         4  
38             : ( has => [@_] );
39            
40 9         38 for my $f (sort keys %export)
41             {
42 7     7   58 no warnings qw(redefine prototype);
  7         15  
  7         11253  
43            
44 10         7161 *{"$caller\::$f"} = $class->_make_has(
45             $caller,
46 10         24 $class->_make_munger($caller, @{$export{$f}}),
  10         31  
47             $orig,
48             );
49             }
50             }
51              
52             {
53             sub __detect_oo
54             {
55 9     9   13 my $package = $_[0];
56            
57 9 100       32 if ($INC{'Moo.pm'})
58             {
59 3 100       15 return "Moo" if $Moo::MAKERS{$package};
60 1 50       8 return "Moo" if $Moo::Role::INFO{$package};
61             }
62            
63 6 50       17 if ($INC{'Moose.pm'})
64             {
65 6         37 require Moose::Util;
66 6 50       23 return "Moose" if Moose::Util::find_meta($package);
67             }
68            
69 0 0       0 if ($INC{'Mouse.pm'})
70             {
71 0         0 require Mouse::Util;
72 0 0       0 return "Mouse" if Mouse::Util::find_meta($package);
73             }
74            
75 0         0 my $meta;
76 0 0       0 eval { $meta = $package->meta } or return "?";
  0         0  
77            
78 0 0       0 return "Moo" if ref($meta) eq "Moo::HandleMoose::FakeMetaClass";
79 0 0       0 return "Mouse" if $meta->isa("Mouse::Meta::Module");
80 0 0       0 return "Moose" if $meta->isa("Moose::Meta::Class");
81 0 0       0 return "Moose" if $meta->isa("Moose::Meta::Role");
82 0         0 return "?";
83             }
84            
85             my %_cache;
86 47   66 47   193 sub _detect_oo { $_cache{$_[0]} ||= __detect_oo(@_) };
87             }
88              
89             sub _make_munger
90             {
91 10     10   19 my $class = shift;
92 10         25 return $class->_compile_munger_code(@_);
93             }
94              
95             sub _compile_munger_code
96             {
97 10     10   17 my $class = shift;
98 10         25 my ($caller, @features) = @_;
99 10         45 my %features = map +($_ => 1), grep !ref, @features;
100 10         26 my @subs = grep ref, @features;
101            
102 10         20 my @code = "sub {";
103            
104 10 100       23 if (_detect_oo($caller) =~ /^Mo[ou]se$/)
105             {
106 7         125 push @code, ' if (exists($_{isa}) && !ref($_{isa})) {';
107 7         12 push @code, ' $_{isa} = '._detect_oo($caller).'::Util::TypeConstraints::find_or_create_isa_type_constraint($_{isa});';
108 7         13 push @code, ' }';
109             }
110            
111 10         25 for my $is (qw/ro rw rwp lazy bare/)
112             {
113 50 100       128 if (delete $features{"is_$is"})
114             {
115 7         21 push @code, ' $_{is} ||= "'.$is.'";';
116             }
117             }
118            
119 10         32 push @code, ' if (exists($_{_is})) {';
120 10         28 push @code, ' my $_is = delete($_{_is});';
121 10         23 push @code, ' $_{is} ||= $_is;';
122 10         19 push @code, ' }';
123              
124 10         16 push @code, 'if ( ref $_{lazy} eq q(CODE) ) {';
125 10         20 push @code, ' $_{builder} ||= $_{lazy};';
126 10         25 push @code, '}';
127            
128 10         18 push @code, ' if (ref($_{builder}) eq q(CODE)) {';
129 10         18 push @code, ' no strict qw(refs);';
130 10         20 push @code, ' require Sub::Util;';
131 10         24 push @code, ' my $short_name = "_build_$_";';
132 10         22 push @code, ' my $name = "$_{__CALLER__}::$short_name";';
133 10         14 push @code, ' *$name = Sub::Util::set_subname($name, $_{builder});';
134 10         20 push @code, ' $_{builder} = $short_name;';
135 10         17 push @code, ' }';
136            
137 10 100       20 unless (_detect_oo($caller) eq "Moo")
138             {
139 7         19 push @code, ' my $is = $_{is} || "";';
140              
141 7         23 push @code, ' if ($is eq q(lazy)) {';
142 7         12 push @code, ' $_{is} = "ro";';
143 7         12 push @code, ' $_{lazy} = 1 unless exists($_{lazy});';
144 7         12 push @code, ' $_{builder} = "_build_$_" if $_{lazy} && !exists($_{builder}) && !exists($_{default});';
145 7         11 push @code, ' }';
146            
147 7         9 push @code, ' if ($is eq q(rwp)) {';
148 7         13 push @code, ' $_{is} = "ro";';
149 7         13 push @code, ' $_{writer} = "_set_$_" unless exists($_{writer});';
150 7         10 push @code, ' }';
151            
152 7         12 push @code, ' if (ref($_{isa}) eq q(CODE)) {';
153 7         10 push @code, ' require Type::Tiny;';
154 7         22 push @code, ' my $code = $_{isa};';
155 7         12 push @code, ' my $safe = sub { !!eval { $code->($_); 1 } };';
156 7         13 push @code, ' $_{isa} = "Type::Tiny"->new(constraint => $safe);';
157 7         10 push @code, ' }';
158             }
159            
160 10         19 delete $features{"eq_1"};
161 10         19 push @code, ' my ($pfx, $name) = ($_ =~ /^(_*)(.+)$/);';
162 10         12 push @code, ' $_{builder} = "_build_$_" if exists($_{builder}) && $_{builder} eq q(1);';
163 10         18 push @code, ' $_{clearer} = "${pfx}clear_${name}" if exists($_{clearer}) && $_{clearer} eq q(1);';
164 10         16 push @code, ' $_{predicate} = "${pfx}has_${name}" if exists($_{predicate}) && $_{predicate} eq q(1);';
165 10         16 push @code, ' if (exists($_{trigger}) && $_{trigger} eq q(1)) {';
166 10         27 push @code, ' my $method = "_trigger_$_";';
167 10         16 push @code, ' $_{trigger} = sub { shift->$method(@_) };';
168 10         15 push @code, ' }';
169            
170 10 100       45 if (delete $features{"always_coerce"})
171             {
172 2         6 push @code, ' if (exists($_{isa}) and !exists($_{coerce}) and Scalar::Util::blessed($_{isa}) and $_{isa}->can("has_coercion") and $_{isa}->has_coercion) {';
173 2         4 push @code, ' $_{coerce} = 1;';
174 2         3 push @code, ' }';
175             }
176            
177 10 100       25 if (delete $features{"always_required"})
178             {
179 2         4 push @code, ' if (!exists($_{required}) and !exists($_{default}) and !exists($_{builder})) {';
180 2         4 push @code, ' $_{required} = 1;';
181 2         5 push @code, ' }';
182             }
183              
184 10 100       24 if (_detect_oo($caller) eq "Moo")
185             {
186 3         6 push @code, ' if (defined($_{coerce}) and !ref($_{coerce}) and $_{coerce} eq "1") {';
187 3         4 push @code, ' Scalar::Util::blessed($_{isa})';
188 3         5 push @code, ' and $_{isa}->isa("Type::Tiny")';
189 3         6 push @code, ' and ($_{coerce} = $_{isa}->coercion);';
190 3         4 push @code, ' }';
191 3         5 push @code, ' elsif (exists($_{coerce}) and not $_{coerce}) {';
192 3         5 push @code, ' delete($_{coerce});';
193 3         4 push @code, ' }';
194             }
195            
196 10 50       26 if (delete $features{"no_isa"})
197             {
198 0         0 push @code, ' delete($_{isa}) if !exists($_{coerce});';
199             }
200            
201 10 100       25 if (delete $features{"simple_isa"})
202             {
203 2         6 push @code, ' $_{isa} = "'.$class.'"->_simplify_isa($_{isa}) if Scalar::Util::blessed($_{isa}) && !$_{coerce};';
204             }
205            
206 10         34 push @code, sprintf(' $subs[%d]->(@_);', $_) for 0..$#subs;
207             #push @code, ' ::diag(::explain($_, \%_));';
208 10         17 push @code, ' delete($_{__CALLER__});';
209 10         17 push @code, "}";
210            
211 10 50       36 croak sprintf("Did not understand mungers: %s", join(q[, ], sort keys %features))
212             if keys %features;
213            
214 10         72 return eval_closure(
215             source => \@code,
216             environment => { '@subs' => \@subs },
217             );
218             }
219              
220             sub _simplify_isa
221             {
222 2     2   74 my $class = shift;
223 2         5 my ($t) = @_;
224            
225 2         9 until ($t->can_be_inlined)
226             {
227 4 50       96 if ($t->has_parent)
228             {
229 4         26 $t = $t->parent;
230 4         17 next;
231             }
232            
233 0 0       0 if ($t->isa("Type::Tiny::Intersection"))
234             {
235 0         0 require Type::Tiny::Intersection;
236 0         0 my (@can_be_inlined) = grep $_->can_be_inlined, @$t;
237 0         0 $t = "Type::Tiny::Intersection"->new(type_constraints => \@can_be_inlined);
238 0         0 next;
239             }
240            
241 0         0 require Type::Tiny;
242 0         0 return "Type::Tiny"->new;
243             }
244            
245 2         67 return $t;
246             }
247              
248             sub _make_has
249             {
250 10     10   8533 my $class = shift;
251 10         26 my ($caller, $coderef, $orig) = @_;
252            
253 10 50       25 return $class->_make_has_mouse(@_) if _detect_oo($caller) eq "Mouse";
254            
255             return sub
256             {
257             my ($attr, %spec) = (
258             (@_ == 2 and ref($_[1]) eq "CODE") ? ($_[0], _is => "ro", lazy => 1, builder => $_[1]) :
259 24 100 100 24   42012 (@_ == 2 and ref($_[1]) eq "HASH") ? ($_[0], %{$_[1]}) :
  0 50 66     0  
    100 66        
260             (@_ == 2 and blessed($_[1]) and $_[1]->can('check')) ? ($_[0], _is => "ro", isa => $_[1]) :
261             @_
262             );
263            
264 24         138 $spec{"__CALLER__"} = $caller;
265            
266 24 100       64 if (ref($attr) eq q(ARRAY))
267             {
268 1         3 my @attrs = @$attr;
269 1         4 for my $attr (@attrs)
270             {
271 2         341 local %_ = %spec;
272 2         6 local $_ = $attr;
273 2         48 $coderef->($attr, %_);
274 2         135 $orig->($attr, %_);
275             }
276             }
277             else
278             {
279 23         96 local %_ = %spec;
280 23         52 local $_ = $attr;
281 23         565 $coderef->($attr, %_);
282 23         1499 return $orig->($attr, %_);
283             }
284 10         47 };
285             }
286              
287             sub _make_has_mouse
288             {
289 0     0     my $class = shift;
290 0           my ($caller, $coderef, $orig) = @_;
291            
292             return sub
293             {
294             my ($attr, %spec) = (
295             (@_ == 2 and ref($_[1]) eq "CODE") ? ($_[0], _is => "ro", lazy => 1, builder => $_[1]) :
296 0 0 0 0     (@_ == 2 and ref($_[1]) eq "HASH") ? ($_[0], %{$_[1]}) :
  0 0 0        
    0 0        
297             (@_ == 2 and blessed($_[1]) and $_[1]->can('check')) ? ($_[0], _is => "ro", isa => $_[1]) :
298             @_
299             );
300            
301 0           $spec{"__CALLER__"} = $caller;
302            
303 0 0         if (ref($attr) eq q(ARRAY))
304             {
305 0           croak "MooseX::MungeHas does not support has \\\@array for Mouse";
306             }
307             else
308             {
309 0           local %_ = %spec;
310 0           local $_ = $attr;
311 0           $coderef->($attr, %_);
312 0           @_ = ($attr, %_);
313 0           goto $orig;
314             }
315 0           };
316             }
317              
318             1;
319              
320             __END__
321              
322             =pod
323              
324             =encoding utf-8
325              
326             =for stopwords metathingies munges mungers
327              
328             =begin private
329              
330             =item eval_closure
331              
332             =end private
333              
334             =head1 NAME
335              
336             MooseX::MungeHas - munge your "has" (works with Moo, Moose and Mouse)
337              
338             =head1 SYNOPSIS
339              
340             package Foo::Bar;
341            
342             use Moose;
343             use MooseX::MungeHas "is_ro";
344            
345             has foo => (); # read-only
346             has bar => (is => "rw"); # read-write
347              
348             =head1 DESCRIPTION
349              
350             MooseX::MungeHas alters the behaviour of the attributes of your L<Moo>,
351             L<Moose> or L<Mouse> based class. It manages to support all three because
352             it doesn't attempt to do anything smart with metathingies; it simply
353             installs a wrapper for C<< has >> that munges the attribute specification
354             hash before passing it on to the original C<< has >> function.
355              
356             The following munges are always applied (simply because I can see no
357             sensible reason why you would not want them to be).
358              
359             =over
360              
361             =item *
362              
363             Implement C<< is => "rwp" >> and C<< is => "lazy" >> in L<Moose> and
364             L<Mouse>.
365              
366             (These already work in L<Moo>.)
367              
368             =item *
369              
370             Implement C<< builder => 1 >>, C<< clearer => 1 >>, C<< predicate => 1 >>,
371             and C<< trigger => 1 >> in L<Moose> and L<Mouse>.
372              
373             (These already work in L<Moo>.)
374              
375             =item *
376              
377             Implement C<< builder => sub { ... } >> in L<Moose> and L<Mouse>.
378              
379             (This already works in L<Moo>.)
380              
381             =item *
382              
383             Allow L<Moo> to support C<< coerce => 0|1 >> for L<Type::Tiny> type
384             constraints. (Moo normally expects a coderef for the coercion.)
385              
386             (These already work in L<Moose> and L<Mouse>, and has actually been
387             added to L<Moo> as of version 1.006000.)
388              
389             =item *
390              
391             Makes C<< has $name => sub { ... } >> into a shortcut for:
392              
393             has $name => (is => "lazy", builder => sub { ... });
394              
395             =item *
396              
397             Makes C<< has $name => $type_constraint >> into a shortcut for:
398              
399             has $name => (isa => $type_constraint);
400              
401             (Assuming that C<< $type_constraint >> is a blessed type constraint
402             object a la L<Type::Tiny>, L<MooseX::Types>, etc.)
403              
404             =item *
405              
406             Makes C<< lazy => sub { ... } >> into a shortcut for:
407              
408             lazy => 1,
409             builder => sub { ... },
410              
411             =back
412              
413             When you import this module (i.e. C<< use MooseX::MungeHas >>) you can
414             provide a list of additional mungers you want it to apply. These may be
415             provided as coderefs, though for a few common, useful sets of behaviour,
416             there are pre-defined shortcut strings.
417              
418             # "no_isa" is a pre-defined shortcut;
419             # the other munger is a coderef.
420             #
421             use MooseX::MungeHas "no_isa", sub {
422             # Make constructor ignore private attributes
423             $_{init_arg} = undef if /^_/;
424             };
425              
426             Within coderefs, the name of the attribute being processed is available
427             in the C<< $_ >> variable, and the specification hash is available as
428             C<< %_ >>.
429              
430             You may provide multiple coderefs.
431              
432             The following are the pre-defined shortcuts:
433              
434             =over
435              
436             =item C<< is_ro >>, C<< is_rw >>, C<< is_rwp >>, C<< is_lazy >>
437              
438             These mungers supply defaults for the C<< is >> option.
439              
440             =item C<< always_coerce >>
441              
442             Automatically provides C<< coerce => 1 >> if the type constraint provides
443             coercions. (Unless you've explicitly specified C<< coerce => 0 >>.)
444              
445             =item C<< always_required >>
446              
447             Automatically provides C<< required => 1 >> unless there is a default or
448             builder. (Unless you've explicitly specified C<< required => 0 >>.)
449              
450             =item C<< no_isa >>
451              
452             Switches off C<< isa >> checks for attributes, unless they coerce.
453              
454             =item C<< simple_isa >>
455              
456             Loosens type constraints if they don't coerce, and if it's likely to make
457             them significantly faster. (Loosening C<Int> to C<Num> won't speed it
458             up.)
459              
460             Only works if you're using L<Type::Tiny> constraints.
461              
462             =back
463              
464             Mungers provided as coderefs are executed I<after> predefined ones, but
465             are otherwise executed in the order specified.
466              
467             =head2 Multiple Wrappers
468              
469             Since version 0.007, it has been possible to use MooseX::MungeHas to
470             export multiple wrappers with different names:
471              
472             package Foo;
473             use Moose;
474             use MooseX::MungeHas {
475             has_ro => [ "is_ro", "always_coerce" ],
476             has_rw => [ "is_rw", "always_coerce" ],
477             };
478            
479             has_ro "foo" => (required => 1);
480             has_rw "bar";
481              
482             Note in the example above, MooseX::MungeHas has installed two brand new
483             wrapped C<has> functions with different names, but it has left the
484             standard C<has> function unmolested.
485              
486             If you wanted to alter the standard function too, then you could use:
487              
488             package Foo;
489             use Moose;
490             use MooseX::MungeHas {
491             has => [ "always_coerce" ],
492             has_ro => [ "is_ro", "always_coerce" ],
493             has_rw => [ "is_rw", "always_coerce" ],
494             };
495            
496             has_ro "foo" => (required => 1);
497             has_rw "bar";
498              
499             =head1 BUGS
500              
501             Please report any bugs to
502             L<http://rt.cpan.org/Dist/Display.html?Queue=MooseX-MungeHas>.
503              
504             =head1 SEE ALSO
505              
506             L<Moo>, L<Mouse>, L<Moose>, L<MooseX::AttributeShortcuts>,
507             L<MooseX::InlineTypes>, L<Type::Tiny::Manual>.
508              
509             Similar: L<MooseX::HasDefaults>, L<MooseX::Attributes::Curried>,
510             L<MooseX::Attribute::Prototype> and L<MooseX::AttributeDefaults>.
511              
512             =head1 AUTHOR
513              
514             Toby Inkster E<lt>tobyink@cpan.orgE<gt>.
515              
516             =head1 COPYRIGHT AND LICENCE
517              
518             This software is copyright (c) 2013-2014, 2017 by Toby Inkster.
519              
520             This is free software; you can redistribute it and/or modify it under
521             the same terms as the Perl 5 programming language system itself.
522              
523             =head1 DISCLAIMER OF WARRANTIES
524              
525             THIS PACKAGE IS PROVIDED "AS IS" AND WITHOUT ANY EXPRESS OR IMPLIED
526             WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED WARRANTIES OF
527             MERCHANTIBILITY AND FITNESS FOR A PARTICULAR PURPOSE.
528