File Coverage

blib/lib/List/Objects/WithUtils/Role/Hash.pm
Criterion Covered Total %
statement 145 145 100.0
branch 24 24 100.0
condition 6 8 75.0
subroutine 49 49 100.0
pod 31 33 93.9
total 255 259 98.4


line stmt bran cond sub pod time code
1             package List::Objects::WithUtils::Role::Hash;
2             $List::Objects::WithUtils::Role::Hash::VERSION = '2.027002';
3 133     133   97033 use strictures 2;
  133         3179  
  133         6874  
4              
5 133     133   59325 use Module::Runtime ();
  133         67989  
  133         2351  
6 133     133   682 use Scalar::Util ();
  133         221  
  133         1958  
7 133     133   656 use List::Util ();
  133         203  
  133         12233  
8              
9             =for Pod::Coverage HASH_TYPE blessed_or_pkg
10              
11             =cut
12              
13             sub HASH_TYPE () { 'List::Objects::WithUtils::Hash' }
14             sub blessed_or_pkg {
15 55 100   55 0 544 Scalar::Util::blessed($_[0]) ?
16             $_[0] : Module::Runtime::use_module(HASH_TYPE)
17             }
18              
19 133     133   708 use Role::Tiny;
  133         242  
  133         804  
20              
21 115     115 1 777 sub array_type { 'List::Objects::WithUtils::Array' }
22 4     4 1 35 sub inflated_type { 'List::Objects::WithUtils::Hash::Inflated' }
23 2     2 1 20 sub inflated_rw_type { 'List::Objects::WithUtils::Hash::Inflated::RW' }
24              
25             =for Pod::Coverage TO_JSON TO_ZPL damn type
26              
27             =cut
28              
29 2     2 1 10 sub is_mutable { 1 }
30 2     2 1 29 sub is_immutable { ! $_[0]->is_mutable }
31              
32       2 0   sub type { }
33              
34             our %Required;
35             sub new {
36 68     68 1 392 my $arraytype = $_[0]->array_type;
37             $Required{$arraytype} = Module::Runtime::require_module($arraytype)
38 68 100       458 unless exists $Required{$arraytype};
39 68   66     1656 bless +{ @_[1 .. $#_] }, Scalar::Util::blessed($_[0]) || $_[0]
40             }
41              
42 13     13 1 1090 sub export { %{ $_[0] } }
  13         160  
43 16     16 1 2632 sub unbless { +{ %{ $_[0] } } }
  16         111  
44              
45 133     133   51120 { no warnings 'once';
  133         252  
  133         18364  
46             *TO_JSON = *unbless;
47             *TO_ZPL = *unbless;
48             *damn = *unbless;
49             }
50              
51 1     1 1 6 sub clear { %{ $_[0] } = (); $_[0] }
  1         7  
  1         6  
52              
53             =for Pod::Coverage untyped
54              
55             =cut
56              
57 4     4 1 40 sub copy { blessed_or_pkg($_[0])->new(%{ $_[0] }) }
  4         74  
58 133     133   735 { no warnings 'once'; *untyped = *copy; }
  133         275  
  133         62111  
59              
60             sub inflate {
61 3     3 1 25 my ($self, %params) = @_;
62 3 100       15 my $type = $params{rw} ? 'inflated_rw_type' : 'inflated_type';
63 3         13 my $cls = blessed_or_pkg($self);
64 3         51 Module::Runtime::require_module( $cls->$type );
65 3         20 $cls->$type->new( %$self )
66             }
67              
68 6     6 1 64 sub defined { CORE::defined $_[0]->{ $_[1] } }
69 7     7 1 68 sub exists { CORE::exists $_[0]->{ $_[1] } }
70              
71 4     4 1 26 sub is_empty { ! keys %{ $_[0] } }
  4         34  
72              
73             sub get {
74 47 100   47 1 14419 if (@_ > 2) {
75             return blessed_or_pkg($_[0])->array_type->new(
76 2         10 @{ $_[0] }{ @_[1 .. $#_] }
  2         18  
77             )
78             }
79 45         283 $_[0]->{ $_[1] }
80             }
81              
82             sub get_or_else {
83 10 100 100 10 1 144 exists $_[0]->{ $_[1] } ? $_[0]->{ $_[1] }
    100          
84             : (Scalar::Util::reftype $_[2] || '') eq 'CODE' ? $_[2]->(@_[0,1])
85             : $_[2]
86             }
87              
88             sub get_path {
89 11     11 1 568 my $ref = $_[0];
90 11         31 for my $part (@_[1 .. $#_]) {
91 25 100       80 $ref = ref $part eq 'ARRAY' ? $ref->[ $part->[0] ] : $ref->{$part};
92 23 100       64 return undef unless defined $ref;
93             }
94             $ref
95 6         28 }
96              
97             =for Pod::Coverage slice
98              
99             =cut
100              
101 133     133   737 { no warnings 'once'; *slice = *sliced; }
  133         275  
  133         104921  
102             { local $@;
103             if ($] >= 5.020) {
104 4     4 1 177 eval q[
  4         28  
  11         110  
105             sub sliced {
106             blessed_or_pkg($_[0])->new(
107             %{ $_[0] }{ grep {; exists $_[0]->{$_} } @_[1 .. $#_] }
108             )
109             }
110             ];
111             } else {
112             eval q[
113             sub sliced {
114             blessed_or_pkg($_[0])->new(
115             map {; exists $_[0]->{$_} ? ($_ => $_[0]->{$_}) : () }
116             @_[1 .. $#_]
117             )
118             }
119             ];
120             }
121             die "installing sub 'sliced' died: $@" if $@;
122             }
123              
124             sub set {
125 8     8 1 1047 my $self = shift;
126 8         13 my (@keysidx, @valsidx);
127 8         27 for (0 .. $#_) {
128 24 100       70 $_ % 2 ? push @valsidx, $_ : push @keysidx, $_
129             }
130 8         22 @{$self}{ @_[@keysidx] } = @_[@valsidx];
  8         37  
131 7         54 $self
132             }
133              
134             sub maybe_set {
135 2     2 1 57 my $self = shift;
136 2         9 for (grep {; not $_ % 2 } 0 .. $#_) {
  12         28  
137 6 100       33 $self->{ $_[$_] } = $_[$_ + 1] unless exists $self->{ $_[$_] }
138             }
139             $self
140 2         16 }
141              
142             sub delete {
143             blessed_or_pkg($_[0])->array_type->new(
144 4     4 1 43 CORE::delete @{ $_[0] }{ @_[1 .. $#_] }
  4         36  
145             )
146             }
147              
148             sub keys {
149             blessed_or_pkg($_[0])->array_type->new(
150 10     10 1 1368 CORE::keys %{ $_[0] }
  10         98  
151             )
152             }
153              
154             sub values {
155             blessed_or_pkg($_[0])->array_type->new(
156 2     2 1 34 CORE::values %{ $_[0] }
  2         22  
157             )
158             }
159              
160             sub intersection {
161 3     3 1 41 my %seen; my %inner;
162             blessed_or_pkg($_[0])->array_type->new(
163 8         36 grep {; not $seen{$_}++ }
164 3         12 grep {; ++$inner{$_} > $#_ } map {; CORE::keys %$_ } @_
  49         101  
  8         33  
165             )
166             }
167              
168             sub diff {
169 3     3 1 40 my %seen; my %inner;
170 3         6 my @vals = map {; CORE::keys %$_ } @_;
  7         31  
171 3         25 $seen{$_}++ for @vals;
172             blessed_or_pkg($_[0])->array_type->new(
173 19         51 grep {; $seen{$_} != @_ }
174 3         12 grep {; not $inner{$_}++ } @vals
  28         57  
175             )
176             }
177              
178             sub iter {
179 3     3 1 30 my @list = %{ $_[0] };
  3         18  
180 9     9   53 sub { splice @list, 0, 2 }
181 3         15 }
182              
183             sub kv {
184             blessed_or_pkg($_[0])->array_type->new(
185 2     2 1 31 map {; [ $_, $_[0]->{ $_ } ] } CORE::keys %{ $_[0] }
  4         21  
  2         12  
186             )
187             }
188              
189             sub kv_sort {
190 10 100 66 10 1 1158 if (defined $_[1] && (my $cb = $_[1])) {
191 6         14 my $pkg = caller;
192 133     133   794 no strict 'refs';
  133         258  
  133         32292  
193             return blessed_or_pkg($_[0])->array_type->new(
194 15         89 map {; [ $_, $_[0]->{ $_ } ] } sort {;
195 16         110 local (*{"${pkg}::a"}, *{"${pkg}::b"}) = (\$a, \$b);
  16         42  
  16         43  
196 16         46 $a->$cb($b)
197 6         27 } CORE::keys %{ $_[0] }
  6         42  
198             )
199             }
200             blessed_or_pkg($_[0])->array_type->new(
201 4         15 map {; [ $_, $_[0]->{ $_ } ] } sort( CORE::keys %{ $_[0] } )
  16         55  
  4         24  
202             )
203             }
204              
205             sub kv_map {
206 3     3 1 38 my ($self, $cb) = @_;
207 3         8 my $pkg = caller;
208 133     133   701 no strict 'refs';
  133         262  
  133         20924  
209             blessed_or_pkg($self)->array_type->new(
210             List::Util::pairmap {;
211 9     9   41 local (*{"${pkg}::a"}, *{"${pkg}::b"}) = (\$a, \$b);
  9         22  
  9         24  
212 9         23 $a->$cb($b)
213 3         11 } %$self
214             )
215             }
216              
217             sub kv_grep {
218 3     3 1 33 my ($self, $cb) = @_;
219 3         8 my $pkg = caller;
220 133     133   738 no strict 'refs';
  133         256  
  133         31545  
221             blessed_or_pkg($self)->new(
222             List::Util::pairgrep {;
223 9     9   84 local (*{"${pkg}::a"}, *{"${pkg}::b"}) = (\$a, \$b);
  9         23  
  9         23  
224 9         23 $a->$cb($b)
225 3         11 } %$self
226             )
227             }
228              
229             =for Pod::Coverage invert
230              
231             =cut
232              
233             sub inverted {
234 2     2 1 29 my ($self) = @_;
235 2         9 my $cls = blessed_or_pkg($self);
236 2         39 my %new;
237             List::Util::pairmap {;
238             exists $new{$b} ?
239 8 100   8   76 $new{$b}->push($a) : ( $new{$b} = $cls->array_type->new($a) )
240 2         40 } %$self;
241 2         16 $cls->new(%new)
242             }
243 133     133   722 { no warnings 'once'; *invert = *inverted; }
  133         1381  
  133         22169  
244              
245              
246             print
247             qq[ huf: I learned that from toyota via agile blahblah,],
248             qq[ it's asking the five "why" questions.\n],
249             qq[ WHY WHY WHY WHY GOD WHY\n]
250             unless caller;
251             1;
252              
253              
254             =pod
255              
256             =head1 NAME
257              
258             List::Objects::WithUtils::Role::Hash - Hash manipulation methods
259              
260             =head1 SYNOPSIS
261              
262             ## Via List::Objects::WithUtils::Hash ->
263             use List::Objects::WithUtils 'hash';
264              
265             my $hash = hash(foo => 'bar');
266              
267             $hash->set(
268             foo => 'baz',
269             pie => 'tasty',
270             );
271              
272             my @matches = $hash->keys->grep(sub { $_[0] =~ /foo/ })->all;
273              
274             my $pie = $hash->get('pie')
275             if $hash->exists('pie');
276              
277             for my $pair ( $hash->kv->all ) {
278             my ($key, $val) = @$pair;
279             ...
280             }
281              
282             my $obj = $hash->inflate;
283             my $foo = $obj->foo;
284              
285             ## As a Role ->
286             use Role::Tiny::With;
287             with 'List::Objects::WithUtils::Role::Hash';
288              
289             =head1 DESCRIPTION
290              
291             A L role defining methods for creating and manipulating HASH-type
292             objects.
293              
294             In addition to the methods documented below, these objects provide a
295             C method exporting a plain HASH-type reference for convenience when
296             feeding L or similar, as well as a C method for
297             compatibility with L.
298              
299             =head2 Basic hash methods
300              
301             =head3 new
302              
303             Constructs a new HASH-type object.
304              
305             =head3 copy
306              
307             Creates a shallow clone of the current object.
308              
309             =head3 defined
310              
311             if ( $hash->defined($key) ) { ... }
312              
313             Returns boolean true if the key has a defined value.
314              
315             =head3 exists
316              
317             if ( $hash->exists($key) ) { ... }
318              
319             Returns boolean true if the key exists.
320              
321             =head3 export
322              
323             my %hash = $hash->export;
324              
325             Returns a raw key => value list.
326              
327             For a plain HASH-type reference, see: L
328              
329             =head3 array_type
330              
331             The class name of array-type objects that will be used to contain the results
332             of methods returning a list.
333              
334             Defaults to L.
335              
336             Subclasses can override C to produce different types of array
337             objects.
338              
339             =head3 inflate
340              
341             my $obj = hash(foo => 'bar', baz => 'quux')->inflate;
342             my $baz = $obj->baz;
343              
344             Inflates a simple object providing accessors for a hash.
345              
346             By default, accessors are read-only; specifying C 1> allows setting new
347             values:
348              
349             my $obj = hash(foo => 'bar', baz => 'quux')->inflate(rw => 1);
350             $obj->foo('frobulate');
351              
352             Returns an L (or L) object.
353              
354             The default objects provide a C method returning a
355             plain hash; this makes it easy to turn inflated objects back into a C
356             for modification:
357              
358             my $first = hash( foo => 'bar', baz => 'quux' )->inflate;
359             my $second = hash( $first->DEFLATE, frobulate => 1 )->inflate;
360              
361             =head3 inflated_type
362              
363             The class name that objects are blessed into when calling L.
364              
365             Defaults to L.
366              
367             =head3 inflated_rw_type
368              
369             The class name that objects are blessed into when calling L with
370             C 1>.
371              
372             Defaults to L, a subclass of
373             L.
374              
375             =head3 is_empty
376              
377             Returns boolean true if the hash has no keys.
378              
379             =head3 is_mutable
380              
381             Returns boolean true if the hash is mutable; immutable subclasses can override
382             to provide a negative value.
383              
384             =head3 is_immutable
385              
386             The opposite of L.
387              
388             =head3 unbless
389              
390             Returns a plain C reference (shallow clone).
391              
392             =head2 Methods that manipulate the hash
393              
394             =head3 clear
395              
396             Clears the current hash entirely.
397              
398             Returns the (same, but now empty) hash object.
399              
400             =head3 delete
401              
402             $hash->delete(@keys);
403              
404             Deletes the given key(s) from the hash.
405              
406             Returns an L object containing the deleted values.
407              
408             =head3 set
409              
410             $hash->set(
411             key1 => $val,
412             key2 => $other,
413             )
414              
415             Sets keys in the hash.
416              
417             Returns the current hash object.
418              
419             =head3 maybe_set
420              
421             my $hash = hash(foo => 1, bar => 2, baz => 3);
422             $hash->maybe_set(foo => 2, bar => 3, quux => 4);
423             # $hash = +{ foo => 1, bar => 2, baz => 3, quux => 4 }
424              
425             Like L, but only sets values that do not already exist in the hash.
426              
427             Returns the current hash object.
428              
429             =head2 Methods that retrieve items
430              
431             =head3 get
432              
433             my $val = $hash->get($key);
434             my @vals = $hash->get(@keys)->all;
435              
436             Retrieves a key or list of keys from the hash.
437              
438             If we're taking a slice (multiple keys were specified), values are returned
439             as an L object. (See L if you'd rather generate a new
440             hash.)
441              
442             =head3 get_path
443              
444             my $hash = hash(
445             foo => +{ bar => +{ baz => 'bork' } },
446             quux => [ +{ weeble => 'snork' } ],
447             );
448             my $item = $hash->get_path(qw/foo bar baz/); # 'bork'
449              
450             Attempt to retrieve a value from a 'deep' hash (without risking
451             autovivification).
452              
453             If an element of the given path is a (plain) array reference, as in this
454             example:
455              
456             my $item = $hash->get_path('quux', [1], 'weeble'); # "snork"
457              
458             ... then it is taken as the index of an array or array-type object in the
459             path.
460              
461             Returns undef if any of the path elements are nonexistant.
462            
463             An exception is thrown if an invalid access is attempted, such as trying to
464             use a hash-type object as if it were an array.
465              
466             (Available from v2.15.1)
467              
468             =head3 get_or_else
469              
470             # Expect to find an array() obj at $key in $hash,
471             # or create an empty one if $key doesn't exist:
472             my @all = $hash->get_or_else($key => array)->all;
473              
474             # Or pass a coderef
475             # First arg is the object being operated on
476             # Second arg is the requested key
477             my $item = $hash->get_or_else($key => sub { shift->get($defaultkey) });
478              
479             Retrieves a key from the hash; optionally takes a second argument that is used
480             as a default value if the given key does not exist in the hash.
481              
482             If the second argument is a coderef, it is invoked on the object (with the
483             requested key as an argument) and its return value is taken as the default
484             value.
485              
486             =head3 keys
487              
488             my @keys = $hash->keys->all;
489              
490             Returns the list of keys in the hash as an L object.
491              
492             =head3 values
493              
494             my @vals = $hash->values->all;
495              
496             Returns the list of values in the hash as an L object.
497              
498             =head3 inverted
499              
500             my $hash = hash(
501             a => 1,
502             b => 2,
503             c => 2,
504             d => 3
505             );
506             my $newhash = $hash->inverted;
507             # $newhash = +{
508             # 1 => array('a'),
509             # 2 => array('b', 'c'),
510             # 3 => array('d'),
511             # }
512              
513             Inverts the hash, creating L objects containing one or more keys
514             for each unique value.
515              
516             This is a bit like reversing the hash, but lossless.
517              
518             (Available from v2.14.1)
519              
520             =head3 iter
521              
522             my $iter = $hash->iter;
523             while (my ($key, $val) = $iter->()) {
524             # ...
525             }
526              
527             Returns an iterator that, when called, returns ($key, $value) pairs.
528              
529             The iterator operates on a shallow clone of the current hash, making it
530             (relatively) safe to operate on the original hash while using the iterator.
531              
532             (Available from v2.9.1)
533              
534             =head3 kv
535              
536             for my $pair ($hash->kv->all) {
537             my ($key, $val) = @$pair;
538             }
539              
540             Returns an L object containing the key/value pairs in the hash,
541             each of which is a two-element (unblessed) ARRAY.
542              
543             =head3 kv_grep
544              
545             my $positive_vals = $hash->kv_grep(sub { $b > 0 });
546              
547             Like C, but operates on pairs. See L.
548              
549             Returns a hash-type object consisting of the key/value pairs for which the
550             given block returned true.
551              
552             (Available from v2.21.1)
553              
554             =head3 kv_map
555              
556             # Add 1 to each value, get back an array-type object:
557             my $kvs = hash(a => 2, b => 2, c => 3)
558             ->kv_map(sub { ($a, $b + 1) });
559              
560             Like C, but operates on pairs. See L.
561              
562             Returns an L object containing the results of the map.
563              
564             In versions prior to v2.20.1, C<$_[0]> and C<$_[1]> must be used in place of
565             C<$a> and C<$b>, respectively.
566              
567             (Available from v2.8.1)
568              
569             =head3 kv_sort
570              
571             my $kvs = hash(a => 1, b => 2, c => 3)->kv_sort;
572             # $kvs = array(
573             # [ a => 1 ],
574             # [ b => 2 ],
575             # [ c => 3 ]
576             # )
577              
578             my $reversed = hash(a => 1, b => 2, c => 3)
579             ->kv_sort(sub { $b cmp $a });
580             # Reverse result as above
581              
582             Like L, but sorted by key. A sort routine can be provided.
583              
584             In versions prior to v2.19.1, C<$_[0]> and C<$_[1]> must be used in place of
585             C<$a> and C<$b>, respectively.
586              
587             =head3 sliced
588              
589             my $newhash = $hash->sliced(@keys);
590              
591             Returns a new hash object built from the specified set of keys and their
592             respective values.
593              
594             If a given key is not found in the hash, it is omitted from the result (this
595             is different than C hash slice syntax, which sets unknown keys to
596             C in the slice).
597              
598             If you only need the values, see L.
599              
600             =head2 Methods that compare hashes
601              
602             =head3 intersection
603              
604             my $first = hash(a => 1, b => 2, c => 3);
605             my $second = hash(b => 2, c => 3, d => 4);
606             my $intersection = $first->intersection($second);
607             my @common = $intersection->sort->all;
608              
609             Returns the list of keys common between all given hash-type objects (including
610             the invocant) as an L object.
611              
612             =head3 diff
613              
614             The opposite of L; returns the list of keys that are not common
615             to all given hash-type objects (including the invocant) as an L
616             object.
617              
618             =head1 NOTES FOR CONSUMERS
619              
620             If creating your own consumer of this role, some extra effort is required to
621             make C<$a> and C<$b> work in sort statements without warnings; an example with
622             a custom exported constructor might look something like:
623              
624             package My::Custom::Hash;
625             use strictures 2;
626             require Role::Tiny;
627             Role::Tiny->apply_roles_to_package( __PACKAGE__,
628             qw/
629             List::Objects::WithUtils::Role::Hash
630             My::Custom::Hash::Role
631             /
632             );
633              
634             use Exporter ();
635             our @EXPORT = 'myhash';
636             sub import {
637             my $pkg = caller;
638             { no strict 'refs';
639             ${"${pkg}::a"} = ${"${pkg}::a"};
640             ${"${pkg}::b"} = ${"${pkg}::b"};
641             }
642             goto &Exporter::import
643             }
644              
645             sub myhash { __PACKAGE__->new(@_) }
646              
647             =head1 SEE ALSO
648              
649             L
650              
651             L
652              
653             L
654              
655             L
656              
657             L
658              
659             =head1 AUTHOR
660              
661             Jon Portnoy
662              
663             Portions of this code are derived from L by Matthew Phillips
664             (CPAN: MATTP), haarg et al
665              
666             Licensed under the same terms as Perl.
667              
668             =cut