~statik/ubuntu/maverick/erlang/erlang-merge-testing

« 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-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
/* ``The contents of this file are subject to the Erlang Public License,
 
1
/*
 
2
 * %CopyrightBegin%
 
3
 * 
 
4
 * Copyright Ericsson AB 2001-2009. All Rights Reserved.
 
5
 * 
 
6
 * The contents of this file are subject to the Erlang Public License,
2
7
 * Version 1.1, (the "License"); you may not use this file except in
3
8
 * compliance with the License. You should have received a copy of the
4
9
 * Erlang Public License along with this software. If not, it can be
5
 
 * retrieved via the world wide web at http://www.erlang.org/.
 
10
 * retrieved online at http://www.erlang.org/.
6
11
 * 
7
12
 * Software distributed under the License is distributed on an "AS IS"
8
13
 * basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
14
 * the License for the specific language governing rights and limitations
10
15
 * under the License.
11
16
 * 
12
 
 * The Initial Developer of the Original Code is Ericsson Utvecklings AB.
13
 
 * Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
14
 
 * AB. All Rights Reserved.''
15
 
 * 
16
 
 *     $Id$
 
17
 * %CopyrightEnd%
17
18
 */
18
19
 
19
20
#ifdef HAVE_CONFIG_H
213
214
    Eterm *hp;
214
215
    Eterm *hp_end;              /* To satisfy hybrid heap architecture */
215
216
    unsigned ret_flags = 0U;
 
217
    int fpe_was_unmasked;
216
218
 
217
219
    bytes = &port_input[0];
218
220
    port_resp = port_result;
293
295
    }
294
296
    erts_smp_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
295
297
    prc  = (char *) port_resp;
296
 
    erts_block_fpe();
 
298
    fpe_was_unmasked = erts_block_fpe();
297
299
    ret = drv->call((ErlDrvData)p->drv_data, 
298
300
                    (unsigned) op,
299
301
                    (char *) bytes, 
301
303
                    &prc, 
302
304
                    (int) sizeof(port_result),
303
305
                    &ret_flags);
304
 
    erts_unblock_fpe();
 
306
    erts_unblock_fpe(fpe_was_unmasked);
305
307
    if (IS_TRACED_FL(p, F_TRACE_SCHED_PORTS)) {
306
308
        trace_sched_ports_where(p, am_out, am_call);
307
309
    }
592
594
    if (is_not_nil(settings)) {
593
595
        nargs = list_val(settings);
594
596
        while (1) {
595
 
            if (is_tuple(*nargs)) {
 
597
            if (is_tuple_arity(*nargs, 2)) {
596
598
                tp = tuple_val(*nargs);
597
599
                arity = *tp++;
598
 
                if (arity != make_arityval(2)) {
599
 
                    goto badarg;
600
 
                }
601
600
                option = *tp++;
602
601
                if (option == am_packet) {
603
602
                    if (is_not_small(*tp)) {
850
849
        Eterm* tp;
851
850
 
852
851
        tmp = CAR(list_val(env));
853
 
        if (is_not_tuple(tmp)) {
 
852
        if (is_not_tuple_arity(tmp, 2)) {
854
853
            goto done;
855
854
        }
856
855
        tp = tuple_val(tmp);
857
 
        if (tp[0] != make_arityval(2)) {
858
 
            goto done;
859
 
        }
860
856
        tmp = CONS(hp, make_small(0), NIL);
861
857
        hp += 2;
862
858
        if (tp[2] != am_false) {
889
885
    return bytes;
890
886
}
891
887
 
 
888
/* ------------ decode_packet() and friends: */
892
889
 
893
890
struct packet_callback_args
894
891
{
895
892
    Process* p;  /* In */
896
893
    Eterm res;   /* Out */
 
894
    int string_as_bin; /* return strings as binaries (http_bin): */
 
895
    byte* aligned_ptr;
 
896
    Eterm orig;
 
897
    Uint bin_offs;
 
898
    byte bin_bitoffs;
897
899
};
898
900
 
 
901
static Eterm
 
902
http_bld_string(struct packet_callback_args* pca, Uint **hpp, Uint *szp,
 
903
                const char *str, Sint len)
 
904
{
 
905
    Eterm res = THE_NON_VALUE;
 
906
    Uint size;
 
907
 
 
908
    if (pca->string_as_bin) {
 
909
        size = heap_bin_size(len);
 
910
    
 
911
        if (szp) {
 
912
            *szp += (size > ERL_SUB_BIN_SIZE) ? ERL_SUB_BIN_SIZE : size;        
 
913
        }
 
914
        if (hpp) {
 
915
            res = make_binary(*hpp);
 
916
            if (size > ERL_SUB_BIN_SIZE) {
 
917
                ErlSubBin* bin = (ErlSubBin*) *hpp;
 
918
                bin->thing_word = HEADER_SUB_BIN;
 
919
                bin->size = len;
 
920
                bin->offs = pca->bin_offs + ((byte*)str - pca->aligned_ptr);
 
921
                bin->orig = pca->orig;
 
922
                bin->bitoffs = pca->bin_bitoffs;
 
923
                bin->bitsize = 0;
 
924
                bin->is_writable = 0;
 
925
                *hpp += ERL_SUB_BIN_SIZE;
 
926
            }
 
927
            else {
 
928
                ErlHeapBin* bin = (ErlHeapBin*) *hpp;
 
929
                bin->thing_word = header_heap_bin(len);
 
930
                bin->size = len;
 
931
                memcpy(bin->data, str, len);
 
932
                *hpp += size;
 
933
            }
 
934
        }
 
935
    }
 
936
    else {
 
937
        res = erts_bld_string_n(hpp, szp, str, len);
 
938
    }
 
939
    return res;
 
940
}
 
941
 
899
942
static int http_response_erl(void *arg, int major, int minor,
900
943
                             int status, const char* phrase, int phrase_len)
901
944
{
902
945
    /* {http_response,{Major,Minor},Status,"Phrase"} */
903
946
    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);
 
947
    Eterm phrase_term, ver;
 
948
    Uint hsize = 3 + 5;
 
949
    Eterm* hp;
907
950
#ifdef DEBUG
908
 
    Eterm* hend = hp + hsize;
 
951
    Eterm* hend;
909
952
#endif
910
953
 
911
 
    list = erts_bld_string_n(&hp, NULL, phrase, phrase_len);
 
954
    http_bld_string(pca, NULL, &hsize, phrase, phrase_len);
 
955
    hp = HAlloc(pca->p, hsize);
 
956
#ifdef DEBUG
 
957
    hend = hp + hsize;
 
958
#endif
 
959
    phrase_term = http_bld_string(pca, &hp, NULL, phrase, phrase_len);
912
960
    ver = TUPLE2(hp, make_small(major), make_small(minor));
913
961
    hp += 3;
914
 
    pca->res = TUPLE4(hp, am_http_response, ver, make_small(status), list);
 
962
    pca->res = TUPLE4(hp, am_http_response, ver, make_small(status), phrase_term);
915
963
    ASSERT(hp+5==hend);
916
964
    return 1;
917
965
}   
918
966
    
919
 
static Eterm http_bld_uri(Eterm** hpp, Uint* szp, const PacketHttpURI* uri)
 
967
static Eterm http_bld_uri(struct packet_callback_args* pca,
 
968
                          Eterm** hpp, Uint* szp, const PacketHttpURI* uri)
920
969
{
921
970
    Eterm s1, s2;
922
971
    if (uri->type == URI_STAR) {
923
972
        return am_Times; /* '*' */
924
973
    }
925
974
 
926
 
    s1 = erts_bld_string_n(hpp, szp, uri->s1_ptr, uri->s1_len);
 
975
    s1 = http_bld_string(pca, hpp, szp, uri->s1_ptr, uri->s1_len);
927
976
 
928
977
    switch (uri->type) {
929
978
    case URI_ABS_PATH:
930
979
        return erts_bld_tuple(hpp, szp, 2, am_abs_path, s1);
931
980
    case URI_HTTP:
932
981
    case URI_HTTPS:
933
 
        s2 = erts_bld_string_n(hpp, szp, uri->s2_ptr, uri->s2_len);
 
982
        s2 = http_bld_string(pca, hpp, szp, uri->s2_ptr, uri->s2_len);
934
983
        return erts_bld_tuple
935
984
            (hpp, szp, 5, am_absoluteURI, 
936
985
             ((uri->type==URI_HTTP) ? am_http : am_https),
941
990
    case URI_STRING:
942
991
        return s1;
943
992
    case URI_SCHEME:
944
 
        s2 = erts_bld_string_n(hpp, szp, uri->s2_ptr, uri->s2_len);
 
993
        s2 = http_bld_string(pca, hpp, szp, uri->s2_ptr, uri->s2_len);
945
994
        return erts_bld_tuple(hpp, szp, 3, am_scheme, s1, s2);
946
995
                              
947
996
    default:
964
1013
 
965
1014
    for (;;) {
966
1015
        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);
 
1016
            http_bld_string(pca, hpp, szp, meth_ptr, meth_len);
 
1017
        uri_term = http_bld_uri(pca, hpp, szp, uri);
969
1018
        ver_term = erts_bld_tuple(hpp, szp, 2,
970
1019
                                  make_small(major), make_small(minor));
971
1020
        pca->res = erts_bld_tuple(hpp, szp, 4, am_http_request, meth_term,
984
1033
{
985
1034
    struct packet_callback_args* pca = (struct packet_callback_args*) arg;    
986
1035
    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);
 
1036
    Uint sz = 6;
 
1037
    Eterm* hp;
989
1038
#ifdef DEBUG
990
 
    Eterm* hend = hp + sz;
 
1039
    Eterm* hend;
991
1040
#endif
992
 
 
 
1041
    
993
1042
    /* {http_header,Bit,Name,IValue,Value} */
 
1043
 
 
1044
    if (name == NULL) {
 
1045
        http_bld_string(pca, NULL, &sz, name_ptr, name_len);
 
1046
    }
 
1047
    http_bld_string(pca, NULL, &sz, value_ptr, value_len);
 
1048
 
 
1049
    hp = HAlloc(pca->p, sz);
 
1050
#ifdef DEBUG
 
1051
    hend = hp + sz;
 
1052
#endif  
 
1053
 
994
1054
    if (name != NULL) {
995
1055
        bit_term = make_small(name->index+1);
996
1056
        name_term = name->atom;
997
1057
    }
998
 
    else {
999
 
        bit_term = make_small(0);
1000
 
        name_term = erts_bld_string_n(&hp,NULL,name_ptr,name_len);
 
1058
    else {      
 
1059
        bit_term = make_small(0);       
 
1060
        name_term = http_bld_string(pca, &hp,NULL,name_ptr,name_len);
1001
1061
    }
1002
1062
 
1003
 
    val_term = erts_bld_string_n(&hp, NULL, value_ptr, value_len);
 
1063
    val_term = http_bld_string(pca, &hp, NULL, value_ptr, value_len);
1004
1064
    pca->res = TUPLE5(hp, am_http_header, bit_term, name_term, am_undefined, val_term);
1005
1065
    ASSERT(hp+6==hend);
1006
1066
    return 1;
1018
1078
{
1019
1079
    /* {http_error,Line} */
1020
1080
    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);
 
1081
    Uint sz = 3;
 
1082
    Eterm* hp;
 
1083
#ifdef DEBUG
 
1084
    Eterm* hend;
 
1085
#endif
 
1086
 
 
1087
    http_bld_string(pca, NULL, &sz, buf, len);
 
1088
 
 
1089
    hp = HAlloc(pca->p, sz);
 
1090
#ifdef DEBUG
 
1091
    hend = hp + sz;
 
1092
#endif
 
1093
    pca->res = erts_bld_tuple(&hp, NULL, 2, am_http_error,
 
1094
                              http_bld_string(pca, &hp, NULL, buf, len));
1030
1095
    ASSERT(hp==hend);
1031
1096
    return 1;
1032
1097
}
1077
1142
    unsigned trunc_len = 0;  /* Truncate lines if longer, 0=no limit */
1078
1143
    int http_state = 0;      /* 0=request/response 1=header */
1079
1144
    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 */
 
1145
    byte* bin_ptr;           /*| orig: original binary                     */
 
1146
    byte bin_bitsz;          /*| bin: BIF_ARG_2, may be sub-binary of orig */
 
1147
    Uint bin_sz;             /*| packet: prefix of bin                     */
 
1148
    char* body_ptr;          /*| body: part of packet to return            */
 
1149
    int body_sz;             /*| rest: bin without packet                  */
1089
1150
    struct packet_callback_args pca;
1090
1151
    enum PacketParseType type;
1091
1152
    Eterm* hp;
1099
1160
        (!is_list(BIF_ARG_3) && !is_nil(BIF_ARG_3))) {
1100
1161
        BIF_ERROR(BIF_P, BADARG);
1101
1162
    }
1102
 
 
1103
1163
    switch (BIF_ARG_1) {
1104
1164
    case make_small(0): case am_raw: type = TCP_PB_RAW; break;
1105
1165
    case make_small(1): type = TCP_PB_1; break;
1113
1173
    case am_tpkt: type = TCP_PB_TPKT; break;
1114
1174
    case am_http: type = TCP_PB_HTTP; break;
1115
1175
    case am_httph: type = TCP_PB_HTTPH; break;
 
1176
    case am_http_bin: type = TCP_PB_HTTP_BIN; break;
 
1177
    case am_httph_bin: type = TCP_PB_HTTPH_BIN; break;
1116
1178
    case am_ssl_tls: type = TCP_PB_SSL_TLS; break;
1117
1179
    default:
1118
1180
        BIF_ERROR(BIF_P, BADARG);
1144
1206
 
1145
1207
 
1146
1208
    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);
 
1209
    ERTS_GET_BINARY_BYTES(BIF_ARG_2, bin_ptr, pca.bin_bitoffs, bin_bitsz);  
 
1210
    if (pca.bin_bitoffs != 0) {
 
1211
        pca.aligned_ptr = erts_alloc(ERTS_ALC_T_TMP, bin_sz);
 
1212
        erts_copy_bits(bin_ptr, pca.bin_bitoffs, 1, pca.aligned_ptr, 0, 1, bin_sz*8);
1151
1213
    }
1152
1214
    else {
1153
 
        aligned_ptr = bin_ptr;
 
1215
        pca.aligned_ptr = bin_ptr;
1154
1216
    }
1155
 
    packet_sz = packet_get_length(type, (char*)aligned_ptr, bin_sz,
 
1217
    packet_sz = packet_get_length(type, (char*)pca.aligned_ptr, bin_sz,
1156
1218
                                  max_plen, trunc_len, &http_state);
1157
1219
    if (!(packet_sz > 0 && packet_sz <= bin_sz)) {
1158
1220
        if (packet_sz < 0) {
1168
1230
    }
1169
1231
    /* We got a whole packet */
1170
1232
 
1171
 
    body_ptr = (char*) aligned_ptr;
 
1233
    body_ptr = (char*) pca.aligned_ptr;
1172
1234
    body_sz = packet_sz;
1173
1235
    packet_get_body(type, (const char**) &body_ptr, &body_sz);
1174
1236
 
1175
 
    ERTS_GET_REAL_BIN(BIF_ARG_2, orig, bin_offs, bin_bitoffs, bin_bitsz);
 
1237
    ERTS_GET_REAL_BIN(BIF_ARG_2, pca.orig, pca.bin_offs, pca.bin_bitoffs, bin_bitsz);
1176
1238
    pca.p = BIF_P;
1177
1239
    pca.res = THE_NON_VALUE;
1178
 
    code = packet_parse(type, (char*)aligned_ptr, packet_sz, &http_state,
 
1240
    pca.string_as_bin = (type == TCP_PB_HTTP_BIN || type == TCP_PB_HTTPH_BIN);
 
1241
    code = packet_parse(type, (char*)pca.aligned_ptr, packet_sz, &http_state,
1179
1242
                        &packet_callbacks_erl, &pca);
1180
1243
    if (code == 0) { /* no special packet parsing, make plain binary */
1181
1244
        ErlSubBin* body;
1186
1249
        body = (ErlSubBin *) hp;
1187
1250
        body->thing_word = HEADER_SUB_BIN;
1188
1251
        body->size = body_sz;
1189
 
        body->offs = bin_offs + (body_ptr - (char*)aligned_ptr);
1190
 
        body->orig = orig;
1191
 
        body->bitoffs = bin_bitoffs;
 
1252
        body->offs = pca.bin_offs + (body_ptr - (char*)pca.aligned_ptr);
 
1253
        body->orig = pca.orig;
 
1254
        body->bitoffs = pca.bin_bitoffs;
1192
1255
        body->bitsize = 0;
1193
1256
        body->is_writable = 0;
1194
1257
        hp += ERL_SUB_BIN_SIZE;
1210
1273
    rest = (ErlSubBin *) hp;
1211
1274
    rest->thing_word = HEADER_SUB_BIN;
1212
1275
    rest->size = bin_sz - packet_sz;
1213
 
    rest->offs = bin_offs + packet_sz;
1214
 
    rest->orig = orig;
1215
 
    rest->bitoffs = bin_bitoffs;
 
1276
    rest->offs = pca.bin_offs + packet_sz;
 
1277
    rest->orig = pca.orig;
 
1278
    rest->bitoffs = pca.bin_bitoffs;
1216
1279
    rest->bitsize = bin_bitsz;   /* The extra bits go into the rest. */
1217
1280
    rest->is_writable = 0;
1218
1281
    hp += ERL_SUB_BIN_SIZE;
1221
1284
    ASSERT(hp==hend); (void)hend;
1222
1285
 
1223
1286
done:
1224
 
    if (aligned_ptr != bin_ptr) {
1225
 
        erts_free(ERTS_ALC_T_TMP, aligned_ptr);
 
1287
    if (pca.aligned_ptr != bin_ptr) {
 
1288
        erts_free(ERTS_ALC_T_TMP, pca.aligned_ptr);
1226
1289
    }
1227
1290
    BIF_RET(res);
1228
1291
}