File Coverage

blib/lib/List/Objects/WithUtils/Role/Hash.pm
Criterion Covered Total %
statement 150 150 100.0
branch 26 26 100.0
condition 8 10 80.0
subroutine 52 52 100.0
pod 34 36 94.4
total 270 274 98.5


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