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

« back to all changes in this revision

Viewing changes to erts/emulator/beam/erl_bif_port.c

  • 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:
24
24
#  include "ose.h"
25
25
#endif
26
26
 
 
27
#include <ctype.h>
 
28
 
27
29
#include "sys.h"
28
30
#include "erl_vm.h"
29
31
#include "erl_sys_driver.h"
38
40
#include "erl_db_util.h"
39
41
#include "register.h"
40
42
#include "external.h"
41
 
 
42
 
extern ErlDrvEntry fd_driver_entry;
43
 
extern ErlDrvEntry vanilla_driver_entry;
44
 
extern ErlDrvEntry spawn_driver_entry;
 
43
#include "packet_parser.h"
 
44
#include "erl_bits.h"
45
45
 
46
46
static int open_port(Process* p, Eterm name, Eterm settings, int *err_nump);
47
47
static byte* convert_environment(Process* p, Eterm env);
53
53
    char *str;
54
54
    int err_num;
55
55
 
56
 
    erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
57
 
 
58
56
    if ((port_num = open_port(BIF_P, BIF_ARG_1, BIF_ARG_2, &err_num)) < 0) {
59
 
        erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN);
60
57
        if (port_num == -3) {
61
58
            ASSERT(err_num == BADARG || err_num == SYSTEM_LIMIT);
62
59
            BIF_ERROR(BIF_P, err_num);
69
66
        BIF_ERROR(BIF_P, EXC_ERROR);
70
67
    }
71
68
 
72
 
    erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_MAIN|ERTS_PROC_LOCK_LINK);
 
69
    erts_smp_proc_lock(BIF_P, ERTS_PROC_LOCK_LINK);
73
70
 
74
71
    port_val = erts_port[port_num].id;
75
72
    erts_add_link(&(erts_port[port_num].nlinks), LINK_PID, BIF_P->id);
156
153
        if (erts_system_monitor_flags.busy_port) {
157
154
            monitor_generic(BIF_P, am_busy_port, p->id);
158
155
        }
159
 
        ERTS_BIF_PREP_ERROR(res, BIF_P, RESCHEDULE);
160
 
    
 
156
        ERTS_BIF_PREP_YIELD2(res, bif_export[BIF_port_command_2], BIF_P,
 
157
                             BIF_ARG_1, BIF_ARG_2);    
161
158
    } else {
162
159
        int wres;
163
160
        erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
205
202
    byte *bytes;
206
203
    byte *endp;
207
204
    size_t real_size;
208
 
    ErlDrvEntry *drv;
 
205
    erts_driver_t *drv;
209
206
    byte port_input[256];       /* Default input buffer to encode in */
210
207
    byte port_result[256];      /* Buffer for result from port. */
211
208
    byte* port_resp;            /* Pointer to result buffer. */
296
293
    }
297
294
    erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
298
295
    prc  = (char *) port_resp;
 
296
    erts_block_fpe();
299
297
    ret = drv->call((ErlDrvData)p->drv_data, 
300
298
                    (unsigned) op,
301
299
                    (char *) bytes, 
303
301
                    &prc, 
304
302
                    (int) sizeof(port_result),
305
303
                    &ret_flags);
306
 
    
 
304
    erts_unblock_fpe();
307
305
    if (IS_TRACED_FL(p, F_TRACE_SCHED_PORTS)) {
308
306
        trace_sched_ports_where(p, am_out, am_call);
309
307
    }
561
559
    Uint arity;
562
560
    Eterm* tp;
563
561
    Uint* nargs;
564
 
    ErlDrvEntry* driver;
 
562
    erts_driver_t* driver;
565
563
    char* name_buf = NULL;
566
564
    SysDriverOpts opts;
567
565
    int binary_io;
707
705
                erl_exit(1, "%s:%d: Internal error\n", __FILE__, __LINE__);
708
706
            name_buf[i] = '\0';
709
707
        }
710
 
        driver = &vanilla_driver_entry;
 
708
        driver = &vanilla_driver;
711
709
    } else {   
712
710
        if (is_not_tuple(name)) {
713
711
            goto badarg;                /* Not a process or fd port */
739
737
            } else {
740
738
                goto badarg;
741
739
            }
742
 
            driver = &spawn_driver_entry;
 
740
            driver = &spawn_driver;
743
741
        } else if (*tp == am_fd) { /* An fd port */
744
742
            int n;
745
743
            struct Sint_buf sbuf;
764
762
            p = Sint_to_buf(opts.ofd, &sbuf);
765
763
            sys_strcpy(name_buf+n+1, p);
766
764
 
767
 
            driver = &fd_driver_entry;
 
765
            driver = &fd_driver;
768
766
        } else {
769
767
            goto badarg;
770
768
        }
771
769
    }
772
770
 
773
 
    if (driver != &spawn_driver_entry && opts.exit_status) {
 
771
    if (driver != &spawn_driver && opts.exit_status) {
774
772
        goto badarg;
775
773
    }
776
774
 
778
776
        trace_virtual_sched(p, am_out);
779
777
    }
780
778
 
 
779
 
 
780
    erts_smp_proc_unlock(p, ERTS_PROC_LOCK_MAIN);
 
781
 
781
782
    port_num = erts_open_driver(driver, p->id, name_buf, &opts, err_nump);
 
783
 
 
784
    erts_smp_proc_lock(p, ERTS_PROC_LOCK_MAIN);
 
785
 
782
786
    if (port_num < 0) {
783
787
        DEBUGF(("open_driver returned %d(%d)\n", port_num, *err_nump));
784
788
        if (IS_TRACED_FL(p, F_TRACE_SCHED_PROCS)) {
884
888
    erts_free(ERTS_ALC_T_TMP, temp_heap);
885
889
    return bytes;
886
890
}
 
891
 
 
892
 
 
893
struct packet_callback_args
 
894
{
 
895
    Process* p;  /* In */
 
896
    Eterm res;   /* Out */
 
897
};
 
898
 
 
899
static int http_response_erl(void *arg, int major, int minor,
 
900
                             int status, const char* phrase, int phrase_len)
 
901
{
 
902
    /* {http_response,{Major,Minor},Status,"Phrase"} */
 
903
    struct packet_callback_args* pca = (struct packet_callback_args*) arg;    
 
904
    Eterm list, ver;
 
905
    unsigned hsize = phrase_len*2 + 3 + 5;
 
906
    Eterm* hp = HAlloc(pca->p, hsize);
 
907
#ifdef DEBUG
 
908
    Eterm* hend = hp + hsize;
 
909
#endif
 
910
 
 
911
    list = erts_bld_string_n(&hp, NULL, phrase, phrase_len);
 
912
    ver = TUPLE2(hp, make_small(major), make_small(minor));
 
913
    hp += 3;
 
914
    pca->res = TUPLE4(hp, am_http_response, ver, make_small(status), list);
 
915
    ASSERT(hp+5==hend);
 
916
    return 1;
 
917
}   
 
918
    
 
919
static Eterm http_bld_uri(Eterm** hpp, Uint* szp, const PacketHttpURI* uri)
 
920
{
 
921
    Eterm s1, s2;
 
922
    if (uri->type == URI_STAR) {
 
923
        return am_Times; /* '*' */
 
924
    }
 
925
 
 
926
    s1 = erts_bld_string_n(hpp, szp, uri->s1_ptr, uri->s1_len);
 
927
 
 
928
    switch (uri->type) {
 
929
    case URI_ABS_PATH:
 
930
        return erts_bld_tuple(hpp, szp, 2, am_abs_path, s1);
 
931
    case URI_HTTP:
 
932
    case URI_HTTPS:
 
933
        s2 = erts_bld_string_n(hpp, szp, uri->s2_ptr, uri->s2_len);
 
934
        return erts_bld_tuple
 
935
            (hpp, szp, 5, am_absoluteURI, 
 
936
             ((uri->type==URI_HTTP) ? am_http : am_https),
 
937
             s1, 
 
938
             ((uri->port==0) ? am_undefined : make_small(uri->port)),
 
939
             s2);
 
940
        
 
941
    case URI_STRING:
 
942
        return s1;
 
943
    case URI_SCHEME:
 
944
        s2 = erts_bld_string_n(hpp, szp, uri->s2_ptr, uri->s2_len);
 
945
        return erts_bld_tuple(hpp, szp, 3, am_scheme, s1, s2);
 
946
                              
 
947
    default:
 
948
        erl_exit(1, "%s, line %d: type=%u\n", __FILE__, __LINE__, uri->type);
 
949
    }
 
950
}
 
951
 
 
952
static int http_request_erl(void* arg, const http_atom_t* meth,
 
953
                            const char* meth_ptr, int meth_len,
 
954
                            const PacketHttpURI* uri, int major, int minor)
 
955
{
 
956
    struct packet_callback_args* pca = (struct packet_callback_args*) arg;    
 
957
    Eterm meth_term, uri_term, ver_term;
 
958
    Uint sz = 0;
 
959
    Uint* szp = &sz;
 
960
    Eterm* hp;
 
961
    Eterm** hpp = NULL;
 
962
 
 
963
    /* {http_request,Meth,Uri,Version} */
 
964
 
 
965
    for (;;) {
 
966
        meth_term = (meth!=NULL) ? meth->atom :
 
967
            erts_bld_string_n(hpp, szp, meth_ptr, meth_len);
 
968
        uri_term = http_bld_uri(hpp, szp, uri);
 
969
        ver_term = erts_bld_tuple(hpp, szp, 2,
 
970
                                  make_small(major), make_small(minor));
 
971
        pca->res = erts_bld_tuple(hpp, szp, 4, am_http_request, meth_term,
 
972
                                  uri_term, ver_term); 
 
973
        if (hpp != NULL) break;
 
974
        hpp = &hp;
 
975
        hp = HAlloc(pca->p, sz);
 
976
        szp = NULL;        
 
977
    }
 
978
    return 1;
 
979
}
 
980
 
 
981
static int
 
982
http_header_erl(void* arg, const http_atom_t* name, const char* name_ptr,
 
983
                int name_len, const char* value_ptr, int value_len)
 
984
{
 
985
    struct packet_callback_args* pca = (struct packet_callback_args*) arg;    
 
986
    Eterm bit_term, name_term, val_term;
 
987
    Uint sz = value_len*2 + 6 + (name ? 0 : name_len*2);
 
988
    Eterm* hp = HAlloc(pca->p,sz);
 
989
#ifdef DEBUG
 
990
    Eterm* hend = hp + sz;
 
991
#endif
 
992
 
 
993
    /* {http_header,Bit,Name,IValue,Value} */
 
994
    if (name != NULL) {
 
995
        bit_term = make_small(name->index+1);
 
996
        name_term = name->atom;
 
997
    }
 
998
    else {
 
999
        bit_term = make_small(0);
 
1000
        name_term = erts_bld_string_n(&hp,NULL,name_ptr,name_len);
 
1001
    }
 
1002
 
 
1003
    val_term = erts_bld_string_n(&hp, NULL, value_ptr, value_len);
 
1004
    pca->res = TUPLE5(hp, am_http_header, bit_term, name_term, am_undefined, val_term);
 
1005
    ASSERT(hp+6==hend);
 
1006
    return 1;
 
1007
}   
 
1008
 
 
1009
static int http_eoh_erl(void* arg)
 
1010
{
 
1011
    /* http_eoh */
 
1012
    struct packet_callback_args* pca = (struct packet_callback_args*) arg;    
 
1013
    pca->res = am_http_eoh;
 
1014
    return 1;
 
1015
}
 
1016
 
 
1017
static int http_error_erl(void* arg, const char* buf, int len)
 
1018
{
 
1019
    /* {http_error,Line} */
 
1020
    struct packet_callback_args* pca = (struct packet_callback_args*) arg;
 
1021
    unsigned hsize = len*2 + 3;
 
1022
    Eterm* hp = HAlloc(pca->p, hsize);
 
1023
#ifdef DEBUG
 
1024
    Eterm* hend = hp + hsize;
 
1025
#endif
 
1026
    Eterm line;
 
1027
 
 
1028
    line = erts_bld_string_n(&hp,NULL,buf,len);
 
1029
    pca->res = erts_bld_tuple(&hp,NULL,2,am_http_error,line);
 
1030
    ASSERT(hp==hend);
 
1031
    return 1;
 
1032
}
 
1033
 
 
1034
static
 
1035
int ssl_tls_erl(void* arg, unsigned type, unsigned major, unsigned minor,
 
1036
                const char* buf, int len, const char* prefix, int plen)
 
1037
{
 
1038
    struct packet_callback_args* pca = (struct packet_callback_args*) arg;
 
1039
    Eterm* hp;
 
1040
    Eterm ver;
 
1041
    Eterm bin = new_binary(pca->p, NULL, plen+len);
 
1042
    byte* bin_ptr = binary_bytes(bin);
 
1043
 
 
1044
    memcpy(bin_ptr+plen, buf, len);
 
1045
    if (plen) {
 
1046
        memcpy(bin_ptr, prefix, plen);
 
1047
    }
 
1048
 
 
1049
    /* {ssl_tls,NIL,ContentType,{Major,Minor},Bin} */
 
1050
    hp = HAlloc(pca->p, 3+6);
 
1051
    ver = TUPLE2(hp, make_small(major), make_small(minor));
 
1052
    hp += 3;
 
1053
    pca->res = TUPLE5(hp, am_ssl_tls, NIL, make_small(type), ver, bin);
 
1054
    return 1;
 
1055
}
 
1056
 
 
1057
 
 
1058
PacketCallbacks packet_callbacks_erl = {
 
1059
    http_response_erl,
 
1060
    http_request_erl,
 
1061
    http_eoh_erl,
 
1062
    http_header_erl,
 
1063
    http_error_erl,
 
1064
    ssl_tls_erl
 
1065
};
 
1066
 
 
1067
/*
 
1068
 decode_packet(Type,Bin,Options)
 
1069
 Returns:
 
1070
     {ok, PacketBodyBin, RestBin}
 
1071
     {more, PacketSz | undefined}
 
1072
     {error, invalid}
 
1073
*/
 
1074
BIF_RETTYPE decode_packet_3(BIF_ALIST_3)
 
1075
{
 
1076
    unsigned max_plen = 0;   /* Packet max length, 0=no limit */
 
1077
    unsigned trunc_len = 0;  /* Truncate lines if longer, 0=no limit */
 
1078
    int http_state = 0;      /* 0=request/response 1=header */
 
1079
    int packet_sz;           /*-------Binaries involved: ------------------*/
 
1080
    Eterm orig;              /*| orig: original binary                     */
 
1081
    Uint bin_offs;           /*| bin: BIF_ARG_2, may be sub-binary of orig */
 
1082
    byte* bin_ptr;           /*| packet: prefix of bin                     */
 
1083
    byte bin_bitoffs;        /*| body: part of packet to return            */
 
1084
    byte bin_bitsz;          /*| rest: bin without packet                  */
 
1085
    Uint bin_sz;
 
1086
    char* body_ptr;
 
1087
    int body_sz;
 
1088
    byte* aligned_ptr;        /* bin_ptr or byte aligned temp copy */
 
1089
    struct packet_callback_args pca;
 
1090
    enum PacketParseType type;
 
1091
    Eterm* hp;
 
1092
    Eterm* hend;
 
1093
    ErlSubBin* rest;
 
1094
    Eterm res;
 
1095
    Eterm options;
 
1096
    int code;
 
1097
 
 
1098
    if (!is_binary(BIF_ARG_2) || 
 
1099
        (!is_list(BIF_ARG_3) && !is_nil(BIF_ARG_3))) {
 
1100
        BIF_ERROR(BIF_P, BADARG);
 
1101
    }
 
1102
 
 
1103
    switch (BIF_ARG_1) {
 
1104
    case make_small(0): case am_raw: type = TCP_PB_RAW; break;
 
1105
    case make_small(1): type = TCP_PB_1; break;
 
1106
    case make_small(2): type = TCP_PB_2; break;
 
1107
    case make_small(4): type = TCP_PB_4; break;
 
1108
    case am_asn1: type = TCP_PB_ASN1; break;
 
1109
    case am_sunrm: type = TCP_PB_RM; break;
 
1110
    case am_cdr: type = TCP_PB_CDR; break;
 
1111
    case am_fcgi: type = TCP_PB_FCGI; break;
 
1112
    case am_line: type = TCP_PB_LINE_LF; break;
 
1113
    case am_tpkt: type = TCP_PB_TPKT; break;
 
1114
    case am_http: type = TCP_PB_HTTP; break;
 
1115
    case am_httph: type = TCP_PB_HTTPH; break;
 
1116
    case am_ssl_tls: type = TCP_PB_SSL_TLS; break;
 
1117
    default:
 
1118
        BIF_ERROR(BIF_P, BADARG);
 
1119
    }
 
1120
 
 
1121
    options = BIF_ARG_3;
 
1122
    while (!is_nil(options)) {
 
1123
        Eterm* cons = list_val(options);
 
1124
        if (is_tuple(CAR(cons))) {
 
1125
            Eterm* tpl = tuple_val(CAR(cons));
 
1126
            Uint val;
 
1127
            if (tpl[0] == make_arityval(2) &&
 
1128
                term_to_Uint(tpl[2],&val) && val <= UINT_MAX) {
 
1129
                switch (tpl[1]) {
 
1130
                case am_packet_size:
 
1131
                    max_plen = val;
 
1132
                    goto next_option;
 
1133
                case am_line_length:
 
1134
                    trunc_len = val;
 
1135
                    goto next_option;
 
1136
                }
 
1137
            }
 
1138
        }
 
1139
        BIF_ERROR(BIF_P, BADARG);
 
1140
 
 
1141
    next_option:       
 
1142
        options = CDR(cons);
 
1143
    }
 
1144
 
 
1145
 
 
1146
    bin_sz = binary_size(BIF_ARG_2);
 
1147
    ERTS_GET_BINARY_BYTES(BIF_ARG_2, bin_ptr, bin_bitoffs, bin_bitsz);  
 
1148
    if (bin_bitoffs != 0) {
 
1149
        aligned_ptr = erts_alloc(ERTS_ALC_T_TMP, bin_sz);
 
1150
        erts_copy_bits(bin_ptr, bin_bitoffs, 1, aligned_ptr, 0, 1, bin_sz*8);
 
1151
    }
 
1152
    else {
 
1153
        aligned_ptr = bin_ptr;
 
1154
    }
 
1155
    packet_sz = packet_get_length(type, (char*)aligned_ptr, bin_sz,
 
1156
                                  max_plen, trunc_len, &http_state);
 
1157
    if (!(packet_sz > 0 && packet_sz <= bin_sz)) {
 
1158
        if (packet_sz < 0) {
 
1159
            goto error;
 
1160
        }
 
1161
        else { /* not enough data */
 
1162
            Eterm plen = (packet_sz==0) ? am_undefined : 
 
1163
                erts_make_integer(packet_sz, BIF_P);
 
1164
            Eterm* hp = HAlloc(BIF_P,3);        
 
1165
            res = TUPLE2(hp, am_more, plen);
 
1166
            goto done;
 
1167
        }
 
1168
    }
 
1169
    /* We got a whole packet */
 
1170
 
 
1171
    body_ptr = (char*) aligned_ptr;
 
1172
    body_sz = packet_sz;
 
1173
    packet_get_body(type, (const char**) &body_ptr, &body_sz);
 
1174
 
 
1175
    ERTS_GET_REAL_BIN(BIF_ARG_2, orig, bin_offs, bin_bitoffs, bin_bitsz);
 
1176
    pca.p = BIF_P;
 
1177
    pca.res = THE_NON_VALUE;
 
1178
    code = packet_parse(type, (char*)aligned_ptr, packet_sz, &http_state,
 
1179
                        &packet_callbacks_erl, &pca);
 
1180
    if (code == 0) { /* no special packet parsing, make plain binary */
 
1181
        ErlSubBin* body;
 
1182
        Uint hsz = 2*ERL_SUB_BIN_SIZE + 4;
 
1183
        hp = HAlloc(BIF_P, hsz);
 
1184
        hend = hp + hsz;
 
1185
 
 
1186
        body = (ErlSubBin *) hp;
 
1187
        body->thing_word = HEADER_SUB_BIN;
 
1188
        body->size = body_sz;
 
1189
        body->offs = bin_offs + (body_ptr - (char*)aligned_ptr);
 
1190
        body->orig = orig;
 
1191
        body->bitoffs = bin_bitoffs;
 
1192
        body->bitsize = 0;
 
1193
        body->is_writable = 0;
 
1194
        hp += ERL_SUB_BIN_SIZE;
 
1195
        pca.res = make_binary(body);
 
1196
    }
 
1197
    else if (code > 0) {
 
1198
        Uint hsz = ERL_SUB_BIN_SIZE + 4;
 
1199
        ASSERT(pca.res != THE_NON_VALUE);
 
1200
        hp = HAlloc(BIF_P, hsz);
 
1201
        hend = hp + hsz;
 
1202
    }
 
1203
    else {
 
1204
error:
 
1205
        hp = HAlloc(BIF_P,3);        
 
1206
        res = TUPLE2(hp, am_error, am_invalid);
 
1207
        goto done;
 
1208
    }
 
1209
 
 
1210
    rest = (ErlSubBin *) hp;
 
1211
    rest->thing_word = HEADER_SUB_BIN;
 
1212
    rest->size = bin_sz - packet_sz;
 
1213
    rest->offs = bin_offs + packet_sz;
 
1214
    rest->orig = orig;
 
1215
    rest->bitoffs = bin_bitoffs;
 
1216
    rest->bitsize = bin_bitsz;   /* The extra bits go into the rest. */
 
1217
    rest->is_writable = 0;
 
1218
    hp += ERL_SUB_BIN_SIZE;
 
1219
    res = TUPLE3(hp, am_ok, pca.res, make_binary(rest));
 
1220
    hp += 4;
 
1221
    ASSERT(hp==hend); (void)hend;
 
1222
 
 
1223
done:
 
1224
    if (aligned_ptr != bin_ptr) {
 
1225
        erts_free(ERTS_ALC_T_TMP, aligned_ptr);
 
1226
    }
 
1227
    BIF_RET(res);
 
1228
}
 
1229