1Type::Tiny(3)         User Contributed Perl Documentation        Type::Tiny(3)
2
3
4

NAME

6       Type::Tiny - tiny, yet Moo(se)-compatible type constraint
7

SYNOPSIS

9        use v5.12;
10        use strict;
11        use warnings;
12
13        package Horse {
14          use Moo;
15          use Types::Standard qw( Str Int Enum ArrayRef Object );
16          use Type::Params qw( signature );
17          use namespace::autoclean;
18
19          has name => (
20            is       => 'ro',
21            isa      => Str,
22            required => 1,
23          );
24          has gender => (
25            is       => 'ro',
26            isa      => Enum[qw( f m )],
27          );
28          has age => (
29            is       => 'rw',
30            isa      => Int->where( '$_ >= 0' ),
31          );
32          has children => (
33            is       => 'ro',
34            isa      => ArrayRef[Object],
35            default  => sub { return [] },
36          );
37
38          sub add_child {
39            state $check = signature(
40              method     => Object,
41              positional => [ Object ],
42            );                                         # method signature
43            my ( $self, $child ) = $check->( @_ );     # unpack @_
44
45            push @{ $self->children }, $child;
46            return $self;
47          }
48        }
49
50        package main;
51
52        my $boldruler = Horse->new(
53          name    => "Bold Ruler",
54          gender  => 'm',
55          age     => 16,
56        );
57
58        my $secretariat = Horse->new(
59          name    => "Secretariat",
60          gender  => 'm',
61          age     => 0,
62        );
63
64        $boldruler->add_child( $secretariat );
65

STATUS

67       This module is covered by the Type-Tiny stability policy.
68

DESCRIPTION

70       This documents the internals of the Type::Tiny class.
71       Type::Tiny::Manual is a better starting place if you're new.
72
73       Type::Tiny is a small class for creating Moose-like type constraint
74       objects which are compatible with Moo, Moose and Mouse.
75
76          use Scalar::Util qw(looks_like_number);
77          use Type::Tiny;
78
79          my $NUM = "Type::Tiny"->new(
80             name       => "Number",
81             constraint => sub { looks_like_number($_) },
82             message    => sub { "$_ ain't a number" },
83          );
84
85          package Ermintrude {
86             use Moo;
87             has favourite_number => (is => "ro", isa => $NUM);
88          }
89
90          package Bullwinkle {
91             use Moose;
92             has favourite_number => (is => "ro", isa => $NUM);
93          }
94
95          package Maisy {
96             use Mouse;
97             has favourite_number => (is => "ro", isa => $NUM);
98          }
99
100       Type::Tiny conforms to Type::API::Constraint,
101       Type::API::Constraint::Coercible, Type::API::Constraint::Constructor,
102       and Type::API::Constraint::Inlinable.
103
104       Maybe now we won't need to have separate MooseX, MouseX and MooX
105       versions of everything? We can but hope...
106
107   Constructor
108       "new(%attributes)"
109           Moose-style constructor function.
110
111   Attributes
112       Attributes are named values that may be passed to the constructor. For
113       each attribute, there is a corresponding reader method. For example:
114
115          my $type = Type::Tiny->new( name => "Foo" );
116          print $type->name, "\n";   # says "Foo"
117
118       Important attributes
119
120       These are the attributes you are likely to be most interested in
121       providing when creating your own type constraints, and most interested
122       in reading when dealing with type constraint objects.
123
124       "constraint"
125           Coderef to validate a value ($_) against the type constraint.  The
126           coderef will not be called unless the value is known to pass any
127           parent type constraint (see "parent" below).
128
129           Alternatively, a string of Perl code checking $_ can be passed as a
130           parameter to the constructor, and will be converted to a coderef.
131
132           Defaults to "sub { 1 }" - i.e. a coderef that passes all values.
133
134       "parent"
135           Optional attribute; parent type constraint. For example, an
136           "Integer" type constraint might have a parent "Number".
137
138           If provided, must be a Type::Tiny object.
139
140       "inlined"
141           A coderef which returns a string of Perl code suitable for inlining
142           this type. Optional.
143
144           (The coderef will be called in list context and can actually return
145           a list of strings which will be joined with "&&". If the first item
146           on the list is undef, it will be substituted with the type's
147           parent's inline check.)
148
149           If "constraint" (above) is a coderef generated via Sub::Quote, then
150           Type::Tiny may be able to automatically generate "inlined" for you.
151           If "constraint" (above) is a string, it will be able to.
152
153       "name"
154           The name of the type constraint. These need to conform to certain
155           naming rules (they must begin with an uppercase letter and continue
156           using only letters, digits 0-9 and underscores).
157
158           Optional; if not supplied will be an anonymous type constraint.
159
160       "display_name"
161           A name to display for the type constraint when stringified. These
162           don't have to conform to any naming rules. Optional; a default name
163           will be calculated from the "name".
164
165       "library"
166           The package name of the type library this type is associated with.
167           Optional. Informational only: setting this attribute does not
168           install the type into the package.
169
170       "deprecated"
171           Optional boolean indicating whether a type constraint is
172           deprecated.  Type::Library will issue a warning if you attempt to
173           import a deprecated type constraint, but otherwise the type will
174           continue to function as normal.  There will not be deprecation
175           warnings every time you validate a value, for instance. If omitted,
176           defaults to the parent's deprecation status (or false if there's no
177           parent).
178
179       "message"
180           Coderef that returns an error message when $_ does not validate
181           against the type constraint. Optional (there's a vaguely sensible
182           default.)
183
184       "coercion"
185           A Type::Coercion object associated with this type.
186
187           Generally speaking this attribute should not be passed to the
188           constructor; you should rely on the default lazily-built coercion
189           object.
190
191           You may pass "coercion => 1" to the constructor to inherit
192           coercions from the constraint's parent. (This requires the parent
193           constraint to have a coercion.)
194
195       "sorter"
196           A coderef which can be passed two values conforming to this type
197           constraint and returns -1, 0, or 1 to put them in order.
198           Alternatively an arrayref containing a pair of coderefs — a sorter
199           and a pre-processor for the Schwarzian transform. Optional.
200
201           The idea is to allow for:
202
203             @sorted = Int->sort( 2, 1, 11 );    # => 1, 2, 11
204             @sorted = Str->sort( 2, 1, 11 );    # => 1, 11, 2
205
206       "type_default"
207           A coderef which returns a sensible default value for this type. For
208           example, for a Counter type, a sensible default might be "0":
209
210             my $Size = Type::Tiny->new(
211               name          => 'Size',
212               parent        => Types::Standard::Enum[ qw( XS S M L XL ) ],
213               type_default  => sub { return 'M'; },
214             );
215
216             package Tshirt {
217               use Moo;
218               has size => (
219                 is       => 'ro',
220                 isa      => $Size,
221                 default  => $Size->type_default,
222               );
223             }
224
225           Child types will inherit a type default from their parent unless
226           the child has a "constraint". If a type neither has nor inherits a
227           type default, then calling "type_default" will return undef.
228
229           As a special case, this:
230
231             $type->type_default( @args )
232
233           Will return:
234
235             sub {
236               local $_ = \@args;
237               $type->type_default->( @_ );
238             }
239
240           Many of the types defined in Types::Standard and other bundled type
241           libraries have type defaults, but discovering them is left as an
242           exercise for the reader.
243
244       "my_methods"
245           Experimental hashref of additional methods that can be called on
246           the type constraint object.
247
248       Attributes related to parameterizable and parameterized types
249
250       The following additional attributes are used for parameterizable (e.g.
251       "ArrayRef") and parameterized (e.g. "ArrayRef[Int]") type constraints.
252       Unlike Moose, these aren't handled by separate subclasses.
253
254       "constraint_generator"
255           Coderef that is called when a type constraint is parameterized.
256           When called, it is passed the list of parameters, though any
257           parameter which looks like a foreign type constraint (Moose type
258           constraints, Mouse type constraints, etc, and coderefs(!!!)) is
259           first coerced to a native Type::Tiny object.
260
261           Note that for compatibility with the Moose API, the base type is
262           not passed to the constraint generator, but can be found in the
263           package variable $Type::Tiny::parameterize_type. The first
264           parameter is also available as $_.
265
266           Types can be parameterized with an empty parameter list. For
267           example, in Types::Standard, "Tuple" is just an alias for
268           "ArrayRef" but "Tuple[]" will only allow zero-length arrayrefs to
269           pass the constraint.  If you wish "YourType" and "YourType[]" to
270           mean the same thing, then do:
271
272            return $Type::Tiny::parameterize_type unless @_;
273
274           The constraint generator should generate and return a new
275           constraint coderef based on the parameters. Alternatively, the
276           constraint generator can return a fully-formed Type::Tiny object,
277           in which case the "name_generator", "inline_generator", and
278           "coercion_generator" attributes documented below are ignored.
279
280           Optional; providing a generator makes this type into a
281           parameterizable type constraint. If there is no generator,
282           attempting to parameterize the type constraint will throw an
283           exception.
284
285       "name_generator"
286           A coderef which generates a new display_name based on parameters.
287           Called with the same parameters and package variables as the
288           "constraint_generator".  Expected to return a string.
289
290           Optional; the default is reasonable.
291
292       "inline_generator"
293           A coderef which generates a new inlining coderef based on
294           parameters. Called with the same parameters and package variables
295           as the "constraint_generator".  Expected to return a coderef.
296
297           Optional.
298
299       "coercion_generator"
300           A coderef which generates a new Type::Coercion object based on
301           parameters.  Called with the same parameters and package variables
302           as the "constraint_generator". Expected to return a blessed object.
303
304           Optional.
305
306       "deep_explanation"
307           This API is not finalized. Coderef used by
308           Error::TypeTiny::Assertion to peek inside parameterized types and
309           figure out why a value doesn't pass the constraint.
310
311       "parameters"
312           In parameterized types, returns an arrayref of the parameters.
313
314       Lazy generated attributes
315
316       The following attributes should not be usually passed to the
317       constructor; unless you're doing something especially unusual, you
318       should rely on the default lazily-built return values.
319
320       "compiled_check"
321           Coderef to validate a value ($_[0]) against the type constraint.
322           This coderef is expected to also handle all validation for the
323           parent type constraints.
324
325       "definition_context"
326           Hashref of information indicating where the type constraint was
327           originally defined. Type::Tiny will generate this based on "caller"
328           if you do not supply it. The hashref will ordinarily contain keys
329           "package", "file", and "line".
330
331           For parameterized types and compound types (e.g. unions and
332           intersections), this may not be especially meaningful information.
333
334       "complementary_type"
335           A complementary type for this type. For example, the complementary
336           type for an integer type would be all things that are not integers,
337           including floating point numbers, but also alphabetic strings,
338           arrayrefs, filehandles, etc.
339
340       "moose_type", "mouse_type"
341           Objects equivalent to this type constraint, but as a
342           Moose::Meta::TypeConstraint or Mouse::Meta::TypeConstraint.
343
344           It should rarely be necessary to obtain a
345           Moose::Meta::TypeConstraint object from Type::Tiny because the
346           Type::Tiny object itself should be usable pretty much anywhere a
347           Moose::Meta::TypeConstraint is expected.
348
349   Methods
350       Predicate methods
351
352       These methods return booleans indicating information about the type
353       constraint. They are each tightly associated with a particular
354       attribute.  (See "Attributes".)
355
356       "has_parent", "has_library", "has_inlined", "has_constraint_generator",
357       "has_inline_generator", "has_coercion_generator", "has_parameters",
358       "has_message", "has_deep_explanation", "has_sorter"
359           Simple Moose-style predicate methods indicating the presence or
360           absence of an attribute.
361
362       "has_coercion"
363           Predicate method with a little extra DWIM. Returns false if the
364           coercion is a no-op.
365
366       "is_anon"
367           Returns true iff the type constraint does not have a "name".
368
369       "is_parameterized", "is_parameterizable"
370           Indicates whether a type has been parameterized (e.g.
371           "ArrayRef[Int]") or could potentially be (e.g. "ArrayRef").
372
373       "has_parameterized_from"
374           Useless alias for "is_parameterized".
375
376       Validation and coercion
377
378       The following methods are used for coercing and validating values
379       against a type constraint:
380
381       "check($value)"
382           Returns true iff the value passes the type constraint.
383
384       "validate($value)"
385           Returns the error message for the value; returns an explicit undef
386           if the value passes the type constraint.
387
388       "assert_valid($value)"
389           Like "check($value)" but dies if the value does not pass the type
390           constraint.
391
392           Yes, that's three very similar methods. Blame
393           Moose::Meta::TypeConstraint whose API I'm attempting to emulate.
394           :-)
395
396       "assert_return($value)"
397           Like "assert_valid($value)" but returns the value if it passes the
398           type constraint.
399
400           This seems a more useful behaviour than "assert_valid($value)". I
401           would have just changed "assert_valid($value)" to do this, except
402           that there are edge cases where it could break Moose compatibility.
403
404       "get_message($value)"
405           Returns the error message for the value; even if the value passes
406           the type constraint.
407
408       "validate_explain($value, $varname)"
409           Like "validate" but instead of a string error message, returns an
410           arrayref of strings explaining the reasoning why the value does not
411           meet the type constraint, examining parent types, etc.
412
413           The $varname is an optional string like '$foo' indicating the name
414           of the variable being checked.
415
416       "coerce($value)"
417           Attempt to coerce $value to this type.
418
419       "assert_coerce($value)"
420           Attempt to coerce $value to this type. Throws an exception if this
421           is not possible.
422
423       Child type constraint creation and parameterization
424
425       These methods generate new type constraint objects that inherit from
426       the constraint they are called upon:
427
428       "create_child_type(%attributes)"
429           Construct a new Type::Tiny object with this object as its parent.
430
431       "where($coderef)"
432           Shortcut for creating an anonymous child type constraint. Use it
433           like "HashRef->where(sub { exists($_->{name}) })". That said, you
434           can get a similar result using overloaded "&":
435
436              HashRef & sub { exists($_->{name}) }
437
438           Like the "constraint" attribute, this will accept a string of Perl
439           code:
440
441              HashRef->where('exists($_->{name})')
442
443       "child_type_class"
444           The class that create_child_type will construct by default.
445
446       "parameterize(@parameters)"
447           Creates a new parameterized type; throws an exception if called on
448           a non-parameterizable type.
449
450       "of(@parameters)"
451           A cute alias for "parameterize". Use it like "ArrayRef->of(Int)".
452
453       "plus_coercions($type1, $code1, ...)"
454           Shorthand for creating a new child type constraint with the same
455           coercions as this one, but then adding some extra coercions (at a
456           higher priority than the existing ones).
457
458       "plus_fallback_coercions($type1, $code1, ...)"
459           Like "plus_coercions", but added at a lower priority.
460
461       "minus_coercions($type1, ...)"
462           Shorthand for creating a new child type constraint with fewer type
463           coercions.
464
465       "no_coercions"
466           Shorthand for creating a new child type constraint with no
467           coercions at all.
468
469       Type relationship introspection methods
470
471       These methods allow you to determine a type constraint's relationship
472       to other type constraints in an organised hierarchy:
473
474       "equals($other)", "is_subtype_of($other)", "is_supertype_of($other)",
475       "is_a_type_of($other)"
476           Compare two types. See Moose::Meta::TypeConstraint for what these
477           all mean.  (OK, Moose doesn't define "is_supertype_of", but you get
478           the idea, right?)
479
480           Note that these have a slightly DWIM side to them. If you create
481           two Type::Tiny::Class objects which test the same class, they're
482           considered equal. And:
483
484              my $subtype_of_Num = Types::Standard::Num->create_child_type;
485              my $subtype_of_Int = Types::Standard::Int->create_child_type;
486              $subtype_of_Int->is_subtype_of( $subtype_of_Num );  # true
487
488       "strictly_equals($other)", "is_strictly_subtype_of($other)",
489       "is_strictly_supertype_of($other)", "is_strictly_a_type_of($other)"
490           Stricter versions of the type comparison functions. These only care
491           about explicit inheritance via "parent".
492
493              my $subtype_of_Num = Types::Standard::Num->create_child_type;
494              my $subtype_of_Int = Types::Standard::Int->create_child_type;
495              $subtype_of_Int->is_strictly_subtype_of( $subtype_of_Num );  # false
496
497       "parents"
498           Returns a list of all this type constraint's ancestor constraints.
499           For example, if called on the "Str" type constraint would return
500           the list "(Value, Defined, Item, Any)".
501
502           Due to a historical misunderstanding, this differs from the Moose
503           implementation of the "parents" method. In Moose, "parents" only
504           returns the immediate parent type constraints, and because type
505           constraints only have one immediate parent, this is effectively an
506           alias for "parent". The extension module
507           MooseX::Meta::TypeConstraint::Intersection is the only place where
508           multiple type constraints are returned; and they are returned as an
509           arrayref in violation of the base class' documentation. I'm keeping
510           my behaviour as it seems more useful.
511
512       "find_parent($coderef)"
513           Loops through the parent type constraints including the invocant
514           itself and returns the nearest ancestor type constraint where the
515           coderef evaluates to true. Within the coderef the ancestor
516           currently being checked is $_. Returns undef if there is no match.
517
518           In list context also returns the number of type constraints which
519           had been looped through before the matching constraint was found.
520
521       "find_constraining_type"
522           Finds the nearest ancestor type constraint (including the type
523           itself) which has a "constraint" coderef.
524
525           Equivalent to:
526
527              $type->find_parent(sub { not $_->_is_null_constraint })
528
529       "coercibles"
530           Return a type constraint which is the union of type constraints
531           that can be coerced to this one (including this one). If this type
532           constraint has no coercions, returns itself.
533
534       "type_parameter"
535           In parameterized type constraints, returns the first item on the
536           list of parameters; otherwise returns undef. For example:
537
538              ( ArrayRef[Int] )->type_parameter;    # returns Int
539              ( ArrayRef[Int] )->parent;            # returns ArrayRef
540
541           Note that parameterizable type constraints can perfectly
542           legitimately take multiple parameters (several of the
543           parameterizable type constraints in Types::Standard do). This
544           method only returns the first such parameter.  "Attributes related
545           to parameterizable and parameterized types" documents the
546           "parameters" attribute, which returns an arrayref of all the
547           parameters.
548
549       "parameterized_from"
550           Harder to spell alias for "parent" that only works for
551           parameterized types.
552
553       Hint for people subclassing Type::Tiny: Since version 1.006000, the
554       methods for determining subtype, supertype, and type equality should
555       not be overridden in subclasses of Type::Tiny. This is because of the
556       problem of diamond inheritance. If X and Y are both subclasses of
557       Type::Tiny, they both need to be consulted to figure out how type
558       constraints are related; not just one of them should be overriding
559       these methods. See the source code for Type::Tiny::Enum for an example
560       of how subclasses can give hints about type relationships to
561       Type::Tiny.  Summary: push a coderef onto @Type::Tiny::CMP. This
562       coderef will be passed two type constraints. It should then return one
563       of the constants Type::Tiny::CMP_SUBTYPE (first type is a subtype of
564       second type), Type::Tiny::CMP_SUPERTYPE (second type is a subtype of
565       first type), Type::Tiny::CMP_EQUAL (the two types are exactly the
566       same), Type::Tiny::CMP_EQUIVALENT (the two types are effectively the
567       same), or Type::Tiny::CMP_UNKNOWN (your coderef couldn't establish any
568       relationship).
569
570       Type relationship introspection function
571
572       "Type::Tiny::cmp($type1, $type2)"
573           The subtype/supertype relationship between types results in a
574           partial ordering of type constraints.
575
576           This function will return one of the constants:
577           Type::Tiny::CMP_SUBTYPE (first type is a subtype of second type),
578           Type::Tiny::CMP_SUPERTYPE (second type is a subtype of first type),
579           Type::Tiny::CMP_EQUAL (the two types are exactly the same),
580           Type::Tiny::CMP_EQUIVALENT (the two types are effectively the
581           same), or Type::Tiny::CMP_UNKNOWN (couldn't establish any
582           relationship).  In numeric contexts, these evaluate to -1, 1, 0, 0,
583           and 0, making it potentially usable with "sort" (though you may
584           need to silence warnings about treating the empty string as a
585           numeric value).
586
587       List processing methods
588
589       "grep(@list)"
590           Filters a list to return just the items that pass the type check.
591
592             @integers = Int->grep(@list);
593
594       "first(@list)"
595           Filters the list to return the first item on the list that passes
596           the type check, or undef if none do.
597
598             $first_lady = Woman->first(@people);
599
600       "map(@list)"
601           Coerces a list of items. Only works on types which have a coercion.
602
603             @truths = Bool->map(@list);
604
605       "sort(@list)"
606           Sorts a list of items according to the type's preferred sorting
607           mechanism, or if the type doesn't have a sorter coderef, uses the
608           parent type. If no ancestor type constraint has a sorter, throws an
609           exception. The "Str", "StrictNum", "LaxNum", and "Enum" type
610           constraints include sorters.
611
612             @sorted_numbers = Num->sort( Num->grep(@list) );
613
614       "rsort(@list)"
615           Like "sort" but backwards.
616
617       "any(@list)"
618           Returns true if any of the list match the type.
619
620             if ( Int->any(@numbers) ) {
621               say "there was at least one integer";
622             }
623
624       "all(@list)"
625           Returns true if all of the list match the type.
626
627             if ( Int->all(@numbers) ) {
628               say "they were all integers";
629             }
630
631       "assert_any(@list)"
632           Like "any" but instead of returning a boolean, returns the entire
633           original list if any item on it matches the type, and dies if none
634           does.
635
636       "assert_all(@list)"
637           Like "all" but instead of returning a boolean, returns the original
638           list if all items on it match the type, but dies as soon as it
639           finds one that does not.
640
641       Inlining methods
642
643       The following methods are used to generate strings of Perl code which
644       may be pasted into stringy "eval"uated subs to perform type checks:
645
646       "can_be_inlined"
647           Returns boolean indicating if this type can be inlined.
648
649       "inline_check($varname)"
650           Creates a type constraint check for a particular variable as a
651           string of Perl code. For example:
652
653              print( Types::Standard::Num->inline_check('$foo') );
654
655           prints the following output:
656
657              (!ref($foo) && Scalar::Util::looks_like_number($foo))
658
659           For Moose-compat, there is an alias "_inline_check" for this
660           method.
661
662       "inline_assert($varname)"
663           Much like "inline_check" but outputs a statement of the form:
664
665              ... or die ...;
666
667           Can also be called line "inline_assert($varname, $typevarname,
668           %extras)".  In this case, it will generate a string of code that
669           may include $typevarname which is supposed to be the name of a
670           variable holding the type itself. (This is kinda complicated, but
671           it allows a useful string to still be produced if the type is not
672           inlineable.) The %extras are additional options to be passed to
673           Error::TypeTiny::Assertion's constructor and must be key-value
674           pairs of strings only, no references or undefs.
675
676       Other methods
677
678       "qualified_name"
679           For non-anonymous type constraints that have a library, returns a
680           qualified "MyLib::MyType" sort of name. Otherwise, returns the same
681           as "name".
682
683       "isa($class)", "can($method)", "AUTOLOAD(@args)"
684           If Moose is loaded, then the combination of these methods is used
685           to mock a Moose::Meta::TypeConstraint.
686
687           If Mouse is loaded, then "isa" mocks Mouse::Meta::TypeConstraint.
688
689       "DOES($role)"
690           Overridden to advertise support for various roles.
691
692           See also Type::API::Constraint, etc.
693
694       "TIESCALAR", "TIEARRAY", "TIEHASH"
695           These are provided as hooks that wrap Type::Tie. They allow the
696           following to work:
697
698              use Types::Standard qw(Int);
699              tie my @list, Int;
700              push @list, 123, 456;   # ok
701              push @list, "Hello";    # dies
702
703       "exportables( $base_name )"
704           Returns a list of the functions a type library should export if it
705           contains this type constraint.
706
707           Example:
708
709             [
710               { name => 'Int',        tags => [ 'types' ],  code => sub { ... } },
711               { name => 'is_Int',     tags => [ 'is' ],     code => sub { ... } },
712               { name => 'assert_Int', tags => [ 'assert' ], code => sub { ... } },
713               { name => 'to_Int',     tags => [ 'to' ],     code => sub { ... } },
714             ]
715
716           $base_name is optional, but allows you to get a list of exportables
717           using a specific name. This is useful if the type constraint has a
718           name which wouldn't be a legal Perl function name.
719
720       "exportables_by_tag( $tag, $base_name )"
721           Filters "exportables" by a specific tag name. In list context,
722           returns all matching exportables. In scalar context returns a
723           single matching exportable and dies if multiple exportables match,
724           or none do!
725
726       The following methods exist for Moose/Mouse compatibility, but do not
727       do anything useful.
728
729       "compile_type_constraint"
730       "hand_optimized_type_constraint"
731       "has_hand_optimized_type_constraint"
732       "inline_environment"
733       "meta"
734
735   Overloading
736       •   Stringification is overloaded to return the qualified name.
737
738       •   Boolification is overloaded to always return true.
739
740       •   Coderefification is overloaded to call "assert_return".
741
742       •   On Perl 5.10.1 and above, smart match is overloaded to call
743           "check".
744
745       •   The "==" operator is overloaded to call "equals".
746
747       •   The "<" and ">" operators are overloaded to call "is_subtype_of"
748           and "is_supertype_of".
749
750       •   The "~" operator is overloaded to call "complementary_type".
751
752       •   The "|" operator is overloaded to build a union of two type
753           constraints.  See Type::Tiny::Union.
754
755       •   The "&" operator is overloaded to build the intersection of two
756           type constraints. See Type::Tiny::Intersection.
757
758       •   The "/" operator provides magical Devel::StrictMode support.  If
759           $ENV{PERL_STRICT} (or a few other environment variables) is true,
760           then it returns the left operand. Normally it returns the right
761           operand.
762
763       Previous versions of Type::Tiny would overload the "+" operator to call
764       "plus_coercions" or "plus_fallback_coercions" as appropriate.  Support
765       for this was dropped after 0.040.
766
767   Constants
768       "Type::Tiny::SUPPORT_SMARTMATCH"
769           Indicates whether the smart match overload is supported on your
770           version of Perl.
771
772   Package Variables
773       $Type::Tiny::DD
774           This undef by default but may be set to a coderef that Type::Tiny
775           and related modules will use to dump data structures in things like
776           error messages.
777
778           Otherwise Type::Tiny uses it's own routine to dump data structures.
779           $DD may then be set to a number to limit the lengths of the dumps.
780           (Default limit is 72.)
781
782           This is a package variable (rather than get/set class methods) to
783           allow for easy localization.
784
785       $Type::Tiny::AvoidCallbacks
786           If this variable is set to true (you should usually do it in a
787           "local" scope), it acts as a hint for type constraints, when
788           generating inlined code, to avoid making any callbacks to variables
789           and functions defined outside the inlined code itself.
790
791           This should have the effect that "$type->inline_check('$foo')" will
792           return a string of code capable of checking the type on Perl
793           installations that don't have Type::Tiny installed. This is
794           intended to allow Type::Tiny to be used with things like Mite.
795
796           The variable works on the honour system. Types need to explicitly
797           check it and decide to generate different code based on its truth
798           value. The bundled types in Types::Standard,
799           Types::Common::Numeric, and Types::Common::String all do.
800           (StrMatch is sometimes unable to, and will issue a warning if it
801           needs to rely on callbacks when asked not to.)
802
803           Most normal users can ignore this.
804
805       $Type::Tiny::SafePackage
806           This is the string "package Type::Tiny;" which is sometimes
807           inserted into strings of inlined code to avoid namespace clashes.
808           In most cases, you do not need to change this. However, if you are
809           inlining type constraint code, saving that code into Perl modules,
810           and uploading them to CPAN, you may wish to change it to avoid
811           problems with the CPAN indexer. Most normal users of Type::Tiny do
812           not need to be aware of this.
813
814   Environment
815       "PERL_TYPE_TINY_XS"
816           Currently this has more effect on Types::Standard than Type::Tiny.
817           In future it may be used to trigger or suppress the loading XS
818           implementations of parts of Type::Tiny.
819

BUGS

821       Please report any bugs to
822       <https://github.com/tobyink/p5-type-tiny/issues>.
823

SEE ALSO

825       The Type::Tiny homepage <https://typetiny.toby.ink/>.
826
827       Type::Tiny::Manual, Type::API.
828
829       Type::Library, Type::Utils, Types::Standard, Type::Coercion.
830
831       Type::Tiny::Class, Type::Tiny::Role, Type::Tiny::Duck,
832       Type::Tiny::Enum, Type::Tiny::Union, Type::Tiny::Intersection.
833
834       Moose::Meta::TypeConstraint, Mouse::Meta::TypeConstraint.
835
836       Type::Params.
837
838       Type::Tiny on GitHub <https://github.com/tobyink/p5-type-tiny>,
839       Type::Tiny on Travis-CI <https://travis-ci.com/tobyink/p5-type-tiny>,
840       Type::Tiny on AppVeyor
841       <https://ci.appveyor.com/project/tobyink/p5-type-tiny>, Type::Tiny on
842       Codecov <https://codecov.io/gh/tobyink/p5-type-tiny>, Type::Tiny on
843       Coveralls <https://coveralls.io/github/tobyink/p5-type-tiny>.
844

AUTHOR

846       Toby Inkster <tobyink@cpan.org>.
847

THANKS

849       Thanks to Matt S Trout for advice on Moo integration.
850
852       This software is copyright (c) 2013-2014, 2017-2023 by Toby Inkster.
853
854       This is free software; you can redistribute it and/or modify it under
855       the same terms as the Perl 5 programming language system itself.
856

DISCLAIMER OF WARRANTIES

858       THIS PACKAGE IS PROVIDED "AS IS" AND WITHOUT ANY EXPRESS OR IMPLIED
859       WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED WARRANTIES OF
860       MERCHANTIBILITY AND FITNESS FOR A PARTICULAR PURPOSE.
861
862
863
864perl v5.36.0                      2023-01-04                     Type::Tiny(3)
Impressum