~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/hipe/cerl/erl_bif_types.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
32
32
-define(BITS, 128). %This is only in bsl to convert answer to pos_inf/neg_inf.
33
33
-define(TAG_IMMED1_SIZE, 4).
34
34
 
35
 
-export([type/3, type/4, arg_types/1, arg_types/3, 
 
35
-export([type/3, type/4, arg_types/3, 
36
36
         is_known/3, infinity_add/2]).
37
37
 
38
 
-include("../icode/hipe_icode_primops.hrl").
39
 
 
40
38
-import(erl_types, [
41
39
                    number_max/1,
42
40
                    number_min/1,
44
42
                    t_arity/0,
45
43
                    t_atom/0,
46
44
                    t_atom/1,
 
45
                    t_atoms/1,
47
46
                    t_atom_vals/1,
48
47
                    t_binary/0,
49
48
                    t_bitstr/0,
69
68
                    t_inf/2,
70
69
                    t_integer/0,
71
70
                    t_integer/1,
72
 
                    t_iolist/0,
73
71
                    t_non_neg_integer/0,
74
72
                    t_pos_integer/0,
75
73
                    t_integers/1,
 
74
                    t_iolist/0,
76
75
                    t_is_any/1,
77
76
                    t_is_atom/1,
78
77
                    t_is_binary/1,
102
101
                    t_list_termination/1,
103
102
                    t_mfa/0,
104
103
                    t_nil/0,
 
104
                    t_node/0,
105
105
                    t_none/0,
106
106
                    t_nonempty_list/0,
107
107
                    t_nonempty_list/1,
115
115
                    t_subtract/2,
116
116
                    t_sup/1,
117
117
                    t_sup/2,
 
118
                    t_timeout/0,
118
119
                    t_tuple/0,
119
120
                    t_tuple/1,
120
121
                    t_tuple_args/1,
247
248
         end);
248
249
type(code, soft_purge, 1, Xs) ->
249
250
  type(code, delete, 1, Xs);
250
 
type(code, stick_dir, 1, Xs) ->
251
 
  strict(arg_types(code, stick_dir, 1), Xs,
252
 
         fun (_) -> t_sup(t_atom('ok'), t_atom('error')) end);
253
251
type(code, stick_mod, 1, Xs) ->
254
252
  strict(arg_types(code, stick_mod, 1), Xs, fun (_) -> t_atom('true') end);
255
 
type(code, stop, 0, _) -> t_none();
256
 
type(code, unstick_dir, 1, Xs) ->
257
 
  type(code, stick_dir, 1, Xs);
258
253
type(code, unstick_mod, 1, Xs) ->
259
254
  type(code, stick_mod, 1, Xs);
260
255
type(code, which, 1, Xs) ->
691
686
type(erlang, bitsize, 1, Xs) -> % XXX: TAKE OUT
692
687
  type(erlang, bit_size, 1, Xs);
693
688
type(erlang, bit_size, 1, Xs) ->
694
 
  strict(arg_types(erlang, bit_size, 1), Xs, fun (_) -> t_non_neg_integer() end);
 
689
  strict(arg_types(erlang, bit_size, 1), Xs,
 
690
         fun (_) -> t_non_neg_integer() end);
695
691
type(erlang, bitstr_to_list, 1, Xs) ->  % XXX: TAKE OUT
696
692
  type(erlang, bitstring_to_list, 1, Xs);
697
693
type(erlang, bitstring_to_list, 1, Xs) ->
701
697
  strict(arg_types(erlang, bump_reductions, 1), Xs,
702
698
         fun (_) -> t_atom('true') end);
703
699
type(erlang, byte_size, 1, Xs) ->
704
 
  strict(arg_types(erlang, byte_size, 1), Xs, fun (_) -> t_non_neg_integer() end);
 
700
  strict(arg_types(erlang, byte_size, 1), Xs,
 
701
         fun (_) -> t_non_neg_integer() end);
705
702
type(erlang, cancel_timer, 1, Xs) ->
706
703
  strict(arg_types(erlang, cancel_timer, 1), Xs,
707
704
         fun (_) -> t_sup(t_integer(), t_atom('false')) end);
 
705
type(erlang, characters_to_list, 2, Xs) ->
 
706
  strict(arg_types(erlang, characters_to_list, 2), Xs,
 
707
         fun (_) -> t_string() end);
 
708
type(erlang, characters_to_utf8, 2, Xs) ->
 
709
  strict(arg_types(erlang, characters_to_list, 2), Xs,
 
710
         fun (_) -> t_binary() end);
708
711
type(erlang, check_process_code, 2, Xs) ->
709
712
  strict(arg_types(erlang, check_process_code, 2), Xs,
710
713
         fun (_) -> t_bool() end);
712
715
  strict(arg_types(erlang, concat_binary, 1), Xs, fun (_) -> t_binary() end);
713
716
type(erlang, date, 0, _) ->
714
717
  t_date();
 
718
type(erlang, decode_packet, 3, Xs) ->
 
719
  strict(arg_types(erlang, decode_packet, 3), Xs,
 
720
         fun (_) ->
 
721
             t_sup([t_tuple([t_atom('ok'), t_packet(), t_binary()]),
 
722
                    t_tuple([t_atom('more'), t_sup([t_non_neg_integer(),
 
723
                                                    t_atom('undefined')])]),
 
724
                    t_tuple([t_atom('error'), t_any()])])
 
725
         end);
715
726
type(erlang, delete_module, 1, Xs) ->
716
727
  strict(arg_types(erlang, delete_module, 1), Xs,
717
728
         fun (_) -> t_sup(t_atom('true'), t_atom('undefined')) end);
1080
1091
type(erlang, monitor_node, 3, Xs) ->
1081
1092
  strict(arg_types(erlang, monitor_node, 3), Xs,
1082
1093
         fun (_) -> t_atom('true') end);
1083
 
type(erlang, node, 0, _) -> t_atom();
 
1094
type(erlang, node, 0, _) -> t_node();
1084
1095
type(erlang, node, 1, Xs) ->
1085
 
  strict(arg_types(erlang, node, 1), Xs, fun (_) -> t_atom() end);
1086
 
type(erlang, nodes, 0, _) -> t_list(t_atom());
 
1096
  strict(arg_types(erlang, node, 1), Xs, fun (_) -> t_node() end);
 
1097
type(erlang, nodes, 0, _) -> t_list(t_node());
1087
1098
type(erlang, nodes, 1, Xs) ->
1088
 
  strict(arg_types(erlang, nodes, 1), Xs, fun (_) -> t_list(t_atom()) end);
 
1099
  strict(arg_types(erlang, nodes, 1), Xs, fun (_) -> t_list(t_node()) end);
1089
1100
type(erlang, now, 0, _) ->
1090
1101
  t_time();
1091
1102
type(erlang, open_port, 2, Xs) ->
1306
1317
type(erlang, seq_trace_print, 2, Xs) ->
1307
1318
  strict(arg_types(erlang, seq_trace_print, 2), Xs, fun (_) -> t_bool() end);
1308
1319
type(erlang, set_cookie, 2, Xs) ->
1309
 
  strict(arg_types(erlang, set_cookie, 2), Xs,
1310
 
         fun (_) -> t_atom('true') end);
 
1320
  strict(arg_types(erlang, set_cookie, 2), Xs, fun (_) -> t_atom('true') end);
1311
1321
type(erlang, setelement, 3, Xs) ->
1312
1322
  strict(arg_types(erlang, setelement, 3), Xs,
1313
1323
         fun ([X1, X2, X3]) ->
2555
2565
type(os, getpid, 0, _) -> t_string();
2556
2566
type(os, putenv, 2, Xs) ->
2557
2567
  strict(arg_types(os, putenv, 2), Xs, fun (_) -> t_atom('true') end);
 
2568
%%-- re -----------------------------------------------------------------------
 
2569
type(re, run, 2, Xs) ->
 
2570
  strict(arg_types(re, run, 2), Xs,
 
2571
         fun (_) ->
 
2572
             t_sup([t_tuple([t_atom('match'), t_re_Captured()]),
 
2573
                    t_atom('nomatch'),
 
2574
                    t_tuple([t_atom('error'),
 
2575
                             t_tuple([t_string(), t_non_neg_integer()])])])
 
2576
         end);
 
2577
type(re, run, 3, Xs) ->
 
2578
  strict(arg_types(re, run, 3), Xs,
 
2579
         fun (_) ->
 
2580
             t_sup([t_tuple([t_atom('match'), t_re_Captured()]),
 
2581
                    t_atom('match'),
 
2582
                    t_atom('nomatch'),
 
2583
                    t_tuple([t_atom('error'),
 
2584
                             t_tuple([t_string(), t_non_neg_integer()])])])
 
2585
         end);
2558
2586
%%-- string -------------------------------------------------------------------
2559
2587
type(string, chars, 2, Xs) ->  % NOTE: added to avoid loss of information
2560
2588
  strict(arg_types(string, chars, 2), Xs, fun (_) -> t_string() end);
2602
2630
%%-----------------------------------------------------------------------------
2603
2631
 
2604
2632
strict(Xs, Ts, F) ->
2605
 
%%  io:format("inf lists arg~n1:~p~n2:~p ~n", [Xs, Ts]),
 
2633
  %% io:format("inf lists arg~n1:~p~n2:~p ~n", [Xs, Ts]),
2606
2634
  Xs1 = inf_lists(Xs, Ts),
2607
 
%%  io:format("inf lists return ~p ~n", [Xs1]),
 
2635
  %% io:format("inf lists return ~p ~n", [Xs1]),
2608
2636
  case any_is_none_or_unit(Xs1) of
2609
2637
    true -> t_none();
2610
2638
    false -> F(Xs1)
2704
2732
                  T)
2705
2733
  end.
2706
2734
 
2707
 
-spec(infinity_abs/1 :: ('pos_inf' | 'neg_inf') -> 'pos_inf'
2708
 
                      ; (integer()) -> non_neg_integer()).
 
2735
-spec infinity_abs('pos_inf' | 'neg_inf') -> 'pos_inf'
 
2736
                ; (integer()) -> non_neg_integer().
2709
2737
 
2710
2738
infinity_abs(pos_inf) -> pos_inf;
2711
2739
infinity_abs(neg_inf) -> pos_inf;
2991
3019
      end
2992
3020
  end.
2993
3021
 
2994
 
 
2995
 
%% =====================================================================
2996
 
%% @doc
2997
 
%% function arg_types returns a list of the demanded argument types for
2998
 
%% a bif to succeed.
2999
 
 
3000
 
arg_types({M, F, A}) ->
3001
 
  arg_types(M, F, A);
3002
 
arg_types('+') ->
3003
 
  [t_number(), t_number()];
3004
 
arg_types('-') ->
3005
 
  [t_number(), t_number()];
3006
 
arg_types('*') ->
3007
 
  [t_number(), t_number()];
3008
 
arg_types('/') ->
3009
 
  [t_number(), t_number()];
3010
 
arg_types('div') ->
3011
 
  [t_integer(), t_integer()];
3012
 
arg_types('rem') ->
3013
 
  [t_integer(), t_integer()];
3014
 
arg_types('band') ->
3015
 
  [t_integer(), t_integer()];
3016
 
arg_types('bor') ->
3017
 
  [t_integer(), t_integer()];
3018
 
arg_types('bxor') ->
3019
 
  [t_integer(), t_integer()];
3020
 
arg_types('bsr') ->
3021
 
  [t_integer(), t_integer()];
3022
 
arg_types('bsl') ->
3023
 
  [t_integer(), t_integer()];
3024
 
arg_types('bnot') ->
3025
 
  [t_integer()];
3026
 
%% arg_types(redtest) ->
3027
 
%%   [];
3028
 
arg_types(#element{}) ->
3029
 
  [t_pos_fixnum(), t_tuple()];
3030
 
%% arg_types({unsafe_element, N}) ->
3031
 
%%   [t_tuple()];
3032
 
arg_types(_BIF) ->
3033
 
  %% io:format("~w\n", [_BIF]),
3034
 
  any.                     % safe approximation for all bifs.
3035
 
 
3036
 
 
3037
3022
%%------- code ----------------------------------------------------------------
3038
3023
arg_types(code, add_path, 1) ->
3039
 
  [t_any()];
 
3024
  [t_string()];
3040
3025
arg_types(code, add_patha, 1) ->
3041
3026
  arg_types(code, add_path, 1);
3042
3027
arg_types(code, add_paths, 1) ->
3043
 
  [t_list()];
 
3028
  [t_list(t_string())];
3044
3029
arg_types(code, add_pathsa, 1) ->
3045
3030
  arg_types(code, add_paths, 1);
3046
3031
arg_types(code, add_pathsz, 1) ->
3052
3037
arg_types(code, compiler_dir, 0) ->
3053
3038
  [];
3054
3039
arg_types(code, del_path, 1) ->
3055
 
  [t_any()];  % OBS: currently code:del_path(42) returns {'error','bad_name'}
 
3040
  [t_sup(t_string(), t_atom())];  % OBS: doc differs from add_path/1 - why?
3056
3041
arg_types(code, delete, 1) ->
3057
3042
  arg_types(code, load_file, 1);
3058
3043
arg_types(code, ensure_loaded, 1) ->
3060
3045
arg_types(code, get_chunk, 2) ->
3061
3046
  [t_binary(), t_string()];
3062
3047
arg_types(code, get_object_code, 1) ->
3063
 
  [t_any()];  % OBS: currently code:get_object_code(42) returns 'error'
 
3048
  [t_atom()];
3064
3049
arg_types(code, get_path, 0) ->
3065
3050
  [];
3066
3051
arg_types(code, is_loaded, 1) ->
3067
 
  [t_any()];  % OBS: not t_atom(); currently code:is_loaded(42) returns 'false'
 
3052
  [t_atom()];
3068
3053
arg_types(code, is_sticky, 1) ->
3069
3054
  [t_atom()];
3070
3055
arg_types(code, is_module_native, 1) ->
3072
3057
arg_types(code, lib_dir, 0) ->
3073
3058
  [];
3074
3059
arg_types(code, lib_dir, 1) ->
3075
 
  [t_any()];  % OBS: currently code:lib_dir(42) returns {'error','bad_name'}
 
3060
  [t_atom()];
3076
3061
arg_types(code, load_abs, 1) ->
3077
3062
  [t_string()];
3078
3063
arg_types(code, load_abs, 2) ->
3090
3075
arg_types(code, make_stub_module, 3) ->
3091
3076
  [t_atom(), t_binary(), t_tuple([t_list(), t_list()])];
3092
3077
arg_types(code, priv_dir, 1) ->
3093
 
  [t_any()];  % OBS: currently code:lib_dir(42) returns {'error','bad_name'}
 
3078
  [t_atom()];
3094
3079
arg_types(code, purge, 1) ->
3095
3080
  arg_types(code, delete, 1);
3096
3081
arg_types(code, rehash, 0) ->
3100
3085
arg_types(code, root_dir, 0) ->
3101
3086
  [];
3102
3087
arg_types(code, set_path, 1) ->
3103
 
  [t_any()];  % OBS: currently code:set_path(42) returns {'error','bad_path'}
 
3088
  [t_string()];
3104
3089
arg_types(code, soft_purge, 1) ->
3105
3090
  arg_types(code, delete, 1);
3106
 
arg_types(code, stick_dir, 1) ->
3107
 
  [t_any()];  % OBS: currently code:stick_dir(42) returns 'error'
3108
3091
arg_types(code, stick_mod, 1) ->
3109
 
  [t_any()];
3110
 
arg_types(code, stop, 0) ->
3111
 
  [];
3112
 
arg_types(code, unstick_dir, 1) ->
3113
 
  arg_types(code, stick_dir, 1);
 
3092
  [t_atom()];
3114
3093
arg_types(code, unstick_mod, 1) ->
3115
3094
  arg_types(code, stick_mod, 1);
3116
3095
arg_types(code, which, 1) ->
3161
3140
%%------- erlang --------------------------------------------------------------
3162
3141
arg_types(erlang, '!', 2) ->
3163
3142
  Pid = t_sup([t_pid(), t_port(), t_atom(),
3164
 
               t_tuple([t_atom(), t_atom()])]),
 
3143
               t_tuple([t_atom(), t_node()])]),
3165
3144
  [Pid, t_any()];
3166
3145
arg_types(erlang, '==', 2) ->
3167
3146
  [t_any(), t_any()];
3182
3161
arg_types(erlang, '+', 1) ->
3183
3162
  [t_number()];
3184
3163
arg_types(erlang, '+', 2) ->
3185
 
  arg_types('+');
 
3164
  [t_number(), t_number()];
3186
3165
arg_types(erlang, '++', 2) ->
3187
3166
  [t_list(), t_any()];
3188
3167
arg_types(erlang, '-', 1) ->
3189
3168
  [t_number()];
3190
3169
arg_types(erlang, '-', 2) ->
3191
 
  arg_types('-');
 
3170
  [t_number(), t_number()];
3192
3171
arg_types(erlang, '--', 2) ->
3193
3172
  [t_list(), t_list()];
3194
3173
arg_types(erlang, '*', 2) ->
3195
 
  arg_types('*');
 
3174
  [t_number(), t_number()];
3196
3175
arg_types(erlang, '/', 2) ->
3197
 
  arg_types('/');
 
3176
  [t_number(), t_number()];
3198
3177
arg_types(erlang, 'div', 2) ->
3199
 
  arg_types('div');
 
3178
  [t_integer(), t_integer()];
3200
3179
arg_types(erlang, 'rem', 2) ->
3201
3180
  [t_integer(), t_integer()];
3202
3181
arg_types(erlang, 'and', 2) ->
3253
3232
  [t_binary()];
3254
3233
arg_types(erlang, cancel_timer, 1) ->
3255
3234
  [t_ref()];
 
3235
arg_types(erlang, characters_to_list, 2) ->
 
3236
  [t_ML(), t_encoding()];
 
3237
arg_types(erlang, characters_to_utf8, 2) ->
 
3238
  [t_ML(), t_encoding()];
3256
3239
arg_types(erlang, check_process_code, 2) ->
3257
3240
  [t_pid(), t_atom()];
3258
3241
arg_types(erlang, concat_binary, 1) ->
3259
3242
  [t_list(t_binary())];
3260
3243
arg_types(erlang, date, 0) ->
3261
3244
  [];
 
3245
arg_types(erlang, decode_packet, 3) ->
 
3246
  [t_decode_packet_type(), t_binary(), t_list(t_decode_packet_option())];
3262
3247
arg_types(erlang, delete_module, 1) ->
3263
3248
  [t_atom()];
3264
3249
arg_types(erlang, demonitor, 1) ->
3265
3250
  [t_ref()];
3266
3251
arg_types(erlang, disconnect_node, 1) ->
3267
 
  [t_atom()];
 
3252
  [t_node()];
3268
3253
arg_types(erlang, display, 1) ->
3269
3254
  [t_any()];
3270
3255
arg_types(erlang, dist_exit, 3) ->
3437
3422
arg_types(erlang, module_loaded, 1) ->
3438
3423
  [t_atom()];
3439
3424
arg_types(erlang, monitor, 2) ->
3440
 
  [t_atom(), t_sup([t_pid(), t_atom(), t_tuple([t_atom(), t_atom()])])];
 
3425
  [t_atom(), t_sup([t_pid(), t_atom(), t_tuple([t_atom(), t_node()])])];
3441
3426
arg_types(erlang, monitor_node, 2) ->
3442
 
  [t_atom(), t_bool()];
 
3427
  [t_node(), t_bool()];
3443
3428
arg_types(erlang, monitor_node, 3) ->
3444
 
  [t_atom(), t_bool(), t_list(t_atom('allow_passive_connect'))];
 
3429
  [t_node(), t_bool(), t_list(t_atom('allow_passive_connect'))];
3445
3430
arg_types(erlang, node, 0) ->
3446
3431
  [];
3447
3432
arg_types(erlang, node, 1) ->
3449
3434
arg_types(erlang, nodes, 0) ->
3450
3435
  [];
3451
3436
arg_types(erlang, nodes, 1) ->
3452
 
  [t_sup(t_atom(), t_list(t_atom()))];
 
3437
  NodesArg = t_atoms(['visible', 'hidden', 'connected', 'this', 'known']),
 
3438
  [t_sup(NodesArg, t_list(NodesArg))];
3453
3439
arg_types(erlang, now, 0) ->
3454
3440
  [];
3455
3441
arg_types(erlang, open_port, 2) ->
3553
3539
arg_types(erlang, seq_trace_print, 2) ->
3554
3540
  [t_sup(t_atom(), t_fixnum()), t_any()];
3555
3541
arg_types(erlang, set_cookie, 2) ->
3556
 
  [t_atom(), t_atom()];
 
3542
  [t_node(), t_atom()];
3557
3543
arg_types(erlang, setelement, 3) ->
3558
3544
  [t_pos_integer(), t_tuple(), t_any()];
3559
3545
arg_types(erlang, setnode, 2) ->
3565
3551
arg_types(erlang, spawn, 1) -> %% TODO: Tuple?
3566
3552
  [t_fun()];
3567
3553
arg_types(erlang, spawn, 2) -> %% TODO: Tuple?
3568
 
  [t_atom(), t_fun()];
 
3554
  [t_node(), t_fun()];
3569
3555
arg_types(erlang, spawn, 3) -> %% TODO: Tuple?
3570
3556
  [t_atom(), t_atom(), t_list()];
3571
3557
arg_types(erlang, spawn, 4) -> %% TODO: Tuple?
3572
 
  [t_atom(), t_atom(), t_atom(), t_list()];
 
3558
  [t_node(), t_atom(), t_atom(), t_list()];
3573
3559
arg_types(erlang, spawn_link, 1) ->
3574
3560
  arg_types(erlang, spawn, 1);  % same
3575
3561
arg_types(erlang, spawn_link, 2) ->
3585
3571
arg_types(erlang, spawn_opt, 3) ->
3586
3572
  [t_atom(), t_fun(), t_list(t_spawn_options())];
3587
3573
arg_types(erlang, spawn_opt, 4) ->
3588
 
  [t_atom(), t_atom(), t_list(), t_list(t_spawn_options())];
 
3574
  [t_node(), t_atom(), t_list(), t_list(t_spawn_options())];
3589
3575
arg_types(erlang, split_binary, 2) ->
3590
3576
  [t_binary(), t_non_neg_integer()];
3591
3577
arg_types(erlang, start_timer, 3) ->
3831
3817
arg_types(gen_tcp, recv, 3) ->
3832
3818
  arg_types(gen_tcp, recv, 2) ++ [t_timeout()];
3833
3819
arg_types(gen_tcp, send, 2) ->
3834
 
  [t_socket(), t_gen_tcp_packet()];
 
3820
  [t_socket(), t_packet()];
3835
3821
arg_types(gen_tcp, shutdown, 2) ->
3836
3822
  [t_socket(), t_sup([t_atom('read'), t_atom('write'), t_atom('read_write')])];
3837
3823
%%------- gen_udp -------------------------------------------------------------
3844
3830
arg_types(gen_udp, recv, 3) ->
3845
3831
  arg_types(gen_tcp, recv, 3);
3846
3832
arg_types(gen_udp, send, 4) ->
3847
 
  [t_socket(), t_gen_tcp_address(), t_gen_tcp_port(), t_gen_tcp_packet()];
 
3833
  [t_socket(), t_gen_tcp_address(), t_gen_tcp_port(), t_packet()];
3848
3834
%%------- hipe_bifs -----------------------------------------------------------
3849
3835
arg_types(hipe_bifs, add_ref, 2) ->
3850
3836
  [t_mfa(), t_tuple([t_mfa(),
4122
4108
  [];
4123
4109
arg_types(os, putenv, 2) ->
4124
4110
  [t_string(), t_string()];
 
4111
%%-- re -----------------------------------------------------------------------
 
4112
arg_types(re, run, 2) ->
 
4113
  [t_file_io_data(), t_re_RE()];
 
4114
arg_types(re, run, 3) ->
 
4115
  [t_file_io_data(), t_re_RE(), t_list(t_re_run_option())];
4125
4116
%%------- string --------------------------------------------------------------
4126
4117
arg_types(string, chars, 2) ->
4127
4118
  [t_char(), t_non_neg_integer()];
4176
4167
 
4177
4168
t_socket() -> t_port(). % alias
4178
4169
 
4179
 
t_timeout() ->
4180
 
  t_sup(t_non_neg_integer(), t_atom('infinity')).
4181
 
 
4182
4170
t_ip_address() ->
4183
4171
  T_int16 = t_from_range(0,  16#FFFF),
4184
4172
  t_sup(t_tuple([t_byte(), t_byte(), t_byte(), t_byte()]),
4186
4174
                 T_int16, T_int16, T_int16, T_int16])).
4187
4175
 
4188
4176
%% =====================================================================
 
4177
%% Some basic types used in various parts of the system
 
4178
%% =====================================================================
 
4179
 
 
4180
t_date() ->
 
4181
  t_tuple([t_pos_fixnum(), t_pos_fixnum(), t_pos_fixnum()]).
 
4182
 
 
4183
t_time() ->
 
4184
  t_tuple([t_non_neg_fixnum(), t_non_neg_fixnum(), t_non_neg_fixnum()]).
 
4185
 
 
4186
t_packet() ->
 
4187
  t_sup([t_binary(), t_iolist(), t_httppacket()]).
 
4188
 
 
4189
t_httppacket() ->
 
4190
  t_sup([t_HttpRequest(), t_HttpResponse(),
 
4191
         t_HttpHeader(), t_atom('http_eoh'), t_HttpError()]).
 
4192
 
 
4193
%% =====================================================================
 
4194
%% HTTP types documented in R12B-4
 
4195
%% =====================================================================
 
4196
 
 
4197
t_HttpRequest() ->
 
4198
  t_tuple([t_atom('http_request'), t_HttpMethod(), t_HttpUri(), t_HttpVersion()]).
 
4199
 
 
4200
t_HttpResponse() ->
 
4201
   t_tuple([t_atom('http_response'), t_HttpVersion(), t_integer(), t_string()]).
 
4202
 
 
4203
t_HttpHeader() ->
 
4204
  t_tuple([t_atom('http_header'), t_integer(), t_HttpField(), t_any(), t_string()]).
 
4205
 
 
4206
t_HttpError() ->
 
4207
  t_tuple([t_atom('http_error'), t_string()]).
 
4208
 
 
4209
t_HttpMethod() ->
 
4210
  t_sup(t_HttpMethodAtom(), t_string()).
 
4211
 
 
4212
t_HttpMethodAtom() ->
 
4213
  t_atoms(['OPTIONS', 'GET', 'HEAD', 'POST', 'PUT', 'DELETE', 'TRACE']).
 
4214
 
 
4215
t_HttpUri() ->
 
4216
  t_sup([t_atom('*'),
 
4217
         t_tuple([t_atom('absoluteURI'),
 
4218
                  t_sup(t_atom('http'), t_atom('https')),
 
4219
                  t_string(),
 
4220
                  t_sup(t_non_neg_integer(), t_atom('undefined')),
 
4221
                  t_string()]),
 
4222
         t_tuple([t_atom('scheme'), t_string(), t_string()]),
 
4223
         t_tuple([t_atom('abs_path'), t_string()]),
 
4224
         t_string()]).
 
4225
 
 
4226
t_HttpVersion() ->
 
4227
  t_tuple([t_non_neg_integer(), t_non_neg_integer()]).
 
4228
 
 
4229
t_HttpField() ->
 
4230
  t_sup(t_HttpFieldAtom(), t_string()).
 
4231
 
 
4232
t_HttpFieldAtom() ->
 
4233
  t_atoms(['Cache-Control', 'Connection', 'Date', 'Pragma', 'Transfer-Encoding',
 
4234
           'Upgrade', 'Via', 'Accept', 'Accept-Charset', 'Accept-Encoding',
 
4235
           'Accept-Language', 'Authorization', 'From', 'Host',
 
4236
           'If-Modified-Since', 'If-Match', 'If-None-Match', 'If-Range',
 
4237
           'If-Unmodified-Since', 'Max-Forwards', 'Proxy-Authorization',
 
4238
           'Range', 'Referer', 'User-Agent', 'Age', 'Location',
 
4239
           'Proxy-Authenticate', 'Public', 'Retry-After', 'Server', 'Vary',
 
4240
           'Warning', 'Www-Authenticate', 'Allow', 'Content-Base',
 
4241
           'Content-Encoding', 'Content-Language', 'Content-Length',
 
4242
           'Content-Location', 'Content-Md5', 'Content-Range', 'Content-Type',
 
4243
           'Etag', 'Expires', 'Last-Modified', 'Accept-Ranges',
 
4244
           'Set-Cookie', 'Set-Cookie2', 'X-Forwarded-For', 'Cookie',
 
4245
           'Keep-Alive', 'Proxy-Connection']).
 
4246
 
 
4247
%% =====================================================================
4189
4248
%% These are used for the built-in functions of 'code'
4190
4249
%% =====================================================================
4191
4250
 
4207
4266
%% These are used for the built-in functions of 'erlang'
4208
4267
%% =====================================================================
4209
4268
 
 
4269
t_ML() ->     %% a possibly deep list of integers or binaries
 
4270
  t_list([t_integer(), t_binary(), t_list()]).
 
4271
 
 
4272
t_decode_packet_option() ->
 
4273
  t_sup([t_tuple([t_atom('packet_size'), t_non_neg_integer()]),
 
4274
         t_tuple([t_atom('line_length'), t_non_neg_integer()])]).
 
4275
 
 
4276
t_decode_packet_type() ->
 
4277
  t_sup(t_inet_setoption_packettype(), t_atom('httph')).
 
4278
 
 
4279
t_dist_exit() ->
 
4280
  t_sup([t_atom('kill'), t_atom('noconnection'), t_atom('normal')]).
 
4281
 
 
4282
t_encoding() ->
 
4283
  t_sup([t_atom('latin1'), t_atom('unicode')]).
 
4284
 
 
4285
t_match_spec_test_errors() ->
 
4286
  t_list(t_sup(t_tuple([t_atom('error'), t_string()]),
 
4287
               t_tuple([t_atom('warning'), t_string()]))).
 
4288
 
 
4289
t_module_info_2() ->
 
4290
 t_sup([t_atom('module'),
 
4291
        t_atom('imports'),
 
4292
        t_atom('exports'),
 
4293
        t_atom('functions'),
 
4294
        t_atom('attributes'),
 
4295
        t_atom('compile'),
 
4296
        t_atom('native_addresses')]).
 
4297
 
4210
4298
t_pinfo() ->
4211
4299
  t_sup([t_pinfo_item(), t_list(t_pinfo_item())]).
4212
4300
 
4237
4325
         t_atom('total_heap_size'),
4238
4326
         t_atom('trap_exit')]).
4239
4327
 
4240
 
t_dist_exit() ->
4241
 
  t_sup([t_atom('kill'), t_atom('noconnection'), t_atom('normal')]).
4242
 
 
4243
 
t_match_spec_test_errors() ->
4244
 
  t_list(t_sup(t_tuple([t_atom('error'), t_string()]),
4245
 
               t_tuple([t_atom('warning'), t_string()]))).
4246
 
 
4247
 
t_module_info_2() ->
4248
 
 t_sup([t_atom('module'),
4249
 
        t_atom('imports'),
4250
 
        t_atom('exports'),
4251
 
        t_atom('functions'),
4252
 
        t_atom('attributes'),
4253
 
        t_atom('compile'),
4254
 
        t_atom('native_addresses')]).
4255
 
 
4256
4328
t_process_priority_level() ->
4257
4329
  t_sup([t_atom('max'), t_atom('high'), t_atom('normal'), t_atom('low')]).
4258
4330
 
4354
4426
         t_atom('type')]).
4355
4427
 
4356
4428
%% =====================================================================
4357
 
%% These are used for the built-in functions of 'inet'
4358
 
%% =====================================================================
4359
 
 
4360
 
t_inet_setoption() ->
4361
 
  t_sup([%% first the 2-tuple options
4362
 
         t_tuple([t_atom('active'), t_sup(t_bool(), t_atom('once'))]),
4363
 
         t_tuple([t_atom('broadcast'), t_bool()]),
4364
 
         t_tuple([t_atom('delay_send'), t_bool()]),
4365
 
         t_tuple([t_atom('dontroute'), t_bool()]),
4366
 
         t_tuple([t_atom('exit_on_close'), t_bool()]),
4367
 
         t_tuple([t_atom('header'), t_non_neg_integer()]),
4368
 
         t_tuple([t_atom('keepalive'), t_bool()]),
4369
 
         t_tuple([t_atom('nodelay'), t_bool()]),
4370
 
         t_tuple([t_atom('packet'), t_inet_setoption_packettype()]),
4371
 
         t_tuple([t_atom('packet_size'), t_non_neg_integer()]),
4372
 
         t_tuple([t_atom('read_packets'), t_non_neg_integer()]),
4373
 
         t_tuple([t_atom('recbuf'), t_non_neg_integer()]),
4374
 
         t_tuple([t_atom('reuseaddr'), t_bool()]),
4375
 
         t_tuple([t_atom('send_timeout'), t_non_neg_integer()]),
4376
 
         t_tuple([t_atom('sndbuf'), t_non_neg_integer()]),
4377
 
         t_tuple([t_atom('priority'), t_non_neg_integer()]),
4378
 
         t_tuple([t_atom('tos'), t_non_neg_integer()]),
4379
 
         %% and a 4-tuple option
4380
 
         t_tuple([t_atom('raw'),
4381
 
                  t_non_neg_integer(),  % protocol level
4382
 
                  t_non_neg_integer(),  % option number
4383
 
                  t_binary()])]).       % actual option value
4384
 
 
4385
 
t_inet_setoption_packettype() ->
4386
 
  t_sup([t_atom('raw'),
4387
 
         t_integers([0,1,2,4]),
4388
 
         t_atom('asn1'), t_atom('cdr'), t_atom('sunrm'),
4389
 
         t_atom('fcgi'), t_atom('tpkt'), t_atom('line')]).
4390
 
 
4391
 
t_inet_posix_error() ->
4392
 
  t_atom().  %% XXX: Very underspecified
4393
 
 
4394
 
%% =====================================================================
4395
4429
%% These are used for the built-in functions of 'file'
4396
4430
%% =====================================================================
4397
4431
 
4398
4432
t_file_io_data() ->
4399
 
  t_sup([t_binary(),
4400
 
         %% IoList() = [char() | binary() | IoList()] -- approximation below
4401
 
         t_string(),
4402
 
         t_maybe_improper_list()]).
 
4433
  t_sup([t_binary(), t_iolist()]).
4403
4434
 
4404
4435
t_file_io_device() ->
4405
 
  t_sup(t_pid(), t_tuple([t_atom('file_descriptor'), t_any(), t_any()])).
 
4436
  t_sup(t_pid(), t_tuple([t_atom('file_descriptor'), t_atom(), t_any()])).
4406
4437
 
4407
4438
t_file_name() ->
4408
4439
  t_sup([t_atom(),
4497
4528
         t_atom('inet'),
4498
4529
         t_inet_setoption()]).
4499
4530
 
4500
 
t_gen_tcp_packet() ->
4501
 
  %% Documentation reads: string() | binary() but it is actually an IOList
4502
 
  t_file_io_data().
4503
 
 
4504
4531
t_gen_tcp_recv() ->
4505
 
  t_sup(t_tuple([t_atom('ok'), t_gen_tcp_packet()]),
 
4532
  t_sup(t_tuple([t_atom('ok'), t_packet()]),
4506
4533
        t_tuple([t_atom('error'), t_sup([t_atom('closed'),
4507
4534
                                         t_inet_posix_error()])])).
4508
4535
 
4523
4550
  t_sup(t_tuple([t_atom('ok'),
4524
4551
                 t_tuple([t_ip_address(),
4525
4552
                          t_gen_tcp_port(),
4526
 
                          t_gen_tcp_packet()])]),
 
4553
                          t_packet()])]),
4527
4554
        t_tuple([t_atom('error'),
4528
4555
                 t_sup(t_atom('not_owner'), t_inet_posix_error())])).
4529
4556
 
4537
4564
t_immediate() ->
4538
4565
  t_sup([t_nil(), t_atom(), t_fixnum()]).
4539
4566
 
4540
 
t_date() ->
4541
 
  t_tuple([t_pos_fixnum(), t_pos_fixnum(), t_pos_fixnum()]).
4542
 
 
4543
 
t_time() ->
4544
 
  t_tuple([t_non_neg_fixnum(), t_non_neg_fixnum(), t_non_neg_fixnum()]).
4545
 
 
4546
4567
t_immarray() ->
4547
 
  t_sup(t_nil(), t_integer()).  %% abstract data type
 
4568
  t_integer().  %% abstract data type
4548
4569
 
4549
4570
t_hiperef() ->
4550
4571
  t_immarray().
4565
4586
         t_atom('closure')]).
4566
4587
 
4567
4588
%% =====================================================================
 
4589
%% These are used for the built-in functions of 'inet'
 
4590
%% =====================================================================
 
4591
 
 
4592
t_inet_setoption() ->
 
4593
  t_sup([%% first the 2-tuple options
 
4594
         t_tuple([t_atom('active'), t_sup(t_bool(), t_atom('once'))]),
 
4595
         t_tuple([t_atom('broadcast'), t_bool()]),
 
4596
         t_tuple([t_atom('delay_send'), t_bool()]),
 
4597
         t_tuple([t_atom('dontroute'), t_bool()]),
 
4598
         t_tuple([t_atom('exit_on_close'), t_bool()]),
 
4599
         t_tuple([t_atom('header'), t_non_neg_integer()]),
 
4600
         t_tuple([t_atom('keepalive'), t_bool()]),
 
4601
         t_tuple([t_atom('nodelay'), t_bool()]),
 
4602
         t_tuple([t_atom('packet'), t_inet_setoption_packettype()]),
 
4603
         t_tuple([t_atom('packet_size'), t_non_neg_integer()]),
 
4604
         t_tuple([t_atom('read_packets'), t_non_neg_integer()]),
 
4605
         t_tuple([t_atom('recbuf'), t_non_neg_integer()]),
 
4606
         t_tuple([t_atom('reuseaddr'), t_bool()]),
 
4607
         t_tuple([t_atom('send_timeout'), t_non_neg_integer()]),
 
4608
         t_tuple([t_atom('sndbuf'), t_non_neg_integer()]),
 
4609
         t_tuple([t_atom('priority'), t_non_neg_integer()]),
 
4610
         t_tuple([t_atom('tos'), t_non_neg_integer()]),
 
4611
         %% and a 4-tuple option
 
4612
         t_tuple([t_atom('raw'),
 
4613
                  t_non_neg_integer(),  % protocol level
 
4614
                  t_non_neg_integer(),  % option number
 
4615
                  t_binary()])]).       % actual option value
 
4616
 
 
4617
t_inet_setoption_packettype() ->
 
4618
  t_sup([t_atom('raw'),
 
4619
         t_integers([0,1,2,4]),
 
4620
         t_atom('asn1'), t_atom('cdr'), t_atom('sunrm'),
 
4621
         t_atom('fcgi'), t_atom('tpkt'), t_atom('line'),
 
4622
         t_atom('http')]).      %% but t_atom('httph') is not needed
 
4623
 
 
4624
t_inet_posix_error() ->
 
4625
  t_atom().  %% XXX: Very underspecified
 
4626
 
 
4627
%% =====================================================================
4568
4628
%% These are used for the built-in functions of 'io'
4569
4629
%% =====================================================================
4570
4630
 
4578
4638
  t_sup([t_atom(), t_list(), t_binary()]).
4579
4639
 
4580
4640
%% =====================================================================
 
4641
%% These are used for the built-in functions of 're'; the functions
 
4642
%% whose last name component starts with a capital letter are types
 
4643
%% =====================================================================
 
4644
 
 
4645
t_re_MP() ->  %% it's supposed to be an opaque data type
 
4646
  t_tuple([t_atom('re_pattern'), t_integer(), t_integer(), t_binary()]).
 
4647
 
 
4648
t_re_RE() ->
 
4649
  t_sup(t_re_MP(), t_file_io_data()).
 
4650
 
 
4651
t_re_compile_option() ->
 
4652
  t_sup([t_atoms(['anchored', 'caseless', 'dollar_endonly', 'dotall',
 
4653
                  'extended', 'firstline', 'multiline', 'no_auto_capture',
 
4654
                  'dupnames', 'ungreedy']),
 
4655
         t_tuple([t_atom('newline'), t_re_NLSpec()])]).
 
4656
 
 
4657
t_re_run_option() ->
 
4658
  t_sup([t_atoms(['anchored', 'global', 'notbol', 'noteol', 'notempty']),
 
4659
         t_tuple([t_atom('offset'), t_integer()]),
 
4660
         t_tuple([t_atom('newline'), t_re_NLSpec()]),
 
4661
         t_tuple([t_atom('capture'), t_re_ValueSpec()]),
 
4662
         t_tuple([t_atom('capture'), t_re_ValueSpec(), t_re_Type()]),
 
4663
         t_re_compile_option()]).
 
4664
 
 
4665
t_re_Type() ->
 
4666
  t_atoms(['index', 'list', 'binary']).
 
4667
 
 
4668
t_re_NLSpec() ->
 
4669
  t_atoms(['cr', 'crlf', 'lf', 'anycrlf']).
 
4670
 
 
4671
t_re_ValueSpec() ->
 
4672
  t_sup(t_atoms(['all', 'all_but_first', 'first']), t_re_ValueList()).
 
4673
 
 
4674
t_re_ValueList() ->
 
4675
  t_list(t_sup([t_integer(), t_string(), t_atom()])).
 
4676
 
 
4677
t_re_Captured() ->
 
4678
  t_list(t_sup(t_re_CapturedData(), t_list(t_re_CapturedData()))).
 
4679
 
 
4680
t_re_CapturedData() ->
 
4681
  t_sup([t_tuple([t_integer(), t_integer()]), t_string(), t_binary()]).
 
4682
 
 
4683
 
 
4684
%% =====================================================================
4581
4685
%% Some testing code for ranges below
4582
4686
%% =====================================================================
4583
4687