~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
/*
2
2
 * %CopyrightBegin%
3
 
 * 
4
 
 * Copyright Ericsson AB 2008-2009. All Rights Reserved.
5
 
 * 
 
3
 *
 
4
 * Copyright Ericsson AB 2008-2010. All Rights Reserved.
 
5
 *
6
6
 * The contents of this file are subject to the Erlang Public License,
7
7
 * Version 1.1, (the "License"); you may not use this file except in
8
8
 * compliance with the License. You should have received a copy of the
9
9
 * Erlang Public License along with this software. If not, it can be
10
10
 * retrieved online at http://www.erlang.org/.
11
 
 * 
 
11
 *
12
12
 * Software distributed under the License is distributed on an "AS IS"
13
13
 * basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
 * the License for the specific language governing rights and limitations
15
15
 * under the License.
16
 
 * 
 
16
 *
17
17
 * %CopyrightEnd%
18
18
 */
19
19
 
30
30
#include "big.h"
31
31
 
32
32
#include "erl_unicode.h"
 
33
#include "erl_unicode_normalize.h"
 
34
 
33
35
 
34
36
typedef struct _restart_context {
35
37
    byte *bytes;
54
56
                                         Uint num_resulting_chars, 
55
57
                                         int state, int left,
56
58
                                         Eterm tail);
57
 
static int analyze_utf8(byte *source, Uint size, 
58
 
                        byte **err_pos, Uint *num_chars, int *left);
59
 
#define UTF8_OK 0
60
 
#define UTF8_INCOMPLETE 1
61
 
#define UTF8_ERROR 2
62
 
#define UTF8_ANALYZE_MORE 3
63
 
 
64
59
static BIF_RETTYPE characters_to_utf8_trap(BIF_ALIST_3);
65
60
static BIF_RETTYPE characters_to_list_trap_1(BIF_ALIST_3);
66
61
static BIF_RETTYPE characters_to_list_trap_2(BIF_ALIST_3);
90
85
        am_atom_put("characters_to_utf8_trap",23);
91
86
    characters_to_utf8_trap_exp.code[2] = 3;
92
87
    characters_to_utf8_trap_exp.code[3] =
93
 
        (Eterm) em_apply_bif;
 
88
        (BeamInstr) em_apply_bif;
94
89
    characters_to_utf8_trap_exp.code[4] = 
95
 
        (Eterm) &characters_to_utf8_trap;
 
90
        (BeamInstr) &characters_to_utf8_trap;
96
91
 
97
92
    memset(&characters_to_list_trap_1_exp, 0, sizeof(Export));
98
93
    characters_to_list_trap_1_exp.address = 
102
97
        am_atom_put("characters_to_list_trap_1",25);
103
98
    characters_to_list_trap_1_exp.code[2] = 3;
104
99
    characters_to_list_trap_1_exp.code[3] =
105
 
        (Eterm) em_apply_bif;
 
100
        (BeamInstr) em_apply_bif;
106
101
    characters_to_list_trap_1_exp.code[4] = 
107
 
        (Eterm) &characters_to_list_trap_1;
 
102
        (BeamInstr) &characters_to_list_trap_1;
108
103
 
109
104
    memset(&characters_to_list_trap_2_exp, 0, sizeof(Export));
110
105
    characters_to_list_trap_2_exp.address = 
114
109
        am_atom_put("characters_to_list_trap_2",25);
115
110
    characters_to_list_trap_2_exp.code[2] = 3;
116
111
    characters_to_list_trap_2_exp.code[3] =
117
 
        (Eterm) em_apply_bif;
 
112
        (BeamInstr) em_apply_bif;
118
113
    characters_to_list_trap_2_exp.code[4] = 
119
 
        (Eterm) &characters_to_list_trap_2;
 
114
        (BeamInstr) &characters_to_list_trap_2;
120
115
 
121
116
 
122
117
    memset(&characters_to_list_trap_3_exp, 0, sizeof(Export));
127
122
        am_atom_put("characters_to_list_trap_3",25);
128
123
    characters_to_list_trap_3_exp.code[2] = 3;
129
124
    characters_to_list_trap_3_exp.code[3] =
130
 
        (Eterm) em_apply_bif;
 
125
        (BeamInstr) em_apply_bif;
131
126
    characters_to_list_trap_3_exp.code[4] = 
132
 
        (Eterm) &characters_to_list_trap_3;
 
127
        (BeamInstr) &characters_to_list_trap_3;
133
128
 
134
129
    memset(&characters_to_list_trap_4_exp, 0, sizeof(Export));
135
130
    characters_to_list_trap_4_exp.address = 
139
134
        am_atom_put("characters_to_list_trap_4",25);
140
135
    characters_to_list_trap_4_exp.code[2] = 1;
141
136
    characters_to_list_trap_4_exp.code[3] =
142
 
        (Eterm) em_apply_bif;
 
137
        (BeamInstr) em_apply_bif;
143
138
    characters_to_list_trap_4_exp.code[4] = 
144
 
        (Eterm) &characters_to_list_trap_4;
 
139
        (BeamInstr) &characters_to_list_trap_4;
145
140
 
146
141
    c_to_b_int_trap_exportp =  erts_export_put(am_unicode,am_characters_to_binary_int,2);
147
142
    c_to_l_int_trap_exportp =  erts_export_put(am_unicode,am_characters_to_list_int,2);
463
458
                        }
464
459
                        objp = list_val(ioterm);
465
460
                        obj = CAR(objp);
466
 
                        if (!is_byte(obj))
 
461
                        if (!is_small(obj))
467
462
                            break;
468
463
                    }
469
464
                } else if (is_nil(obj)) {
970
965
        bytes = erts_get_aligned_binary_bytes(orig_bin, &temp_alloc);
971
966
    }
972
967
    size = binary_size(orig_bin);
973
 
    ret = analyze_utf8(bytes,
 
968
    ret = erts_analyze_utf8(bytes,
974
969
                       size,
975
970
                       &endpos,&numchar,NULL);
976
971
    erts_free_aligned_binary_bytes(temp_alloc);
977
 
    return (ret == UTF8_OK);
 
972
    return (ret == ERTS_UTF8_OK);
978
973
}
979
974
 
980
975
BIF_RETTYPE unicode_characters_to_binary_2(BIF_ALIST_2)
1084
1079
            hp += 2;
1085
1080
            rest_term = CONS(hp,leftover_bin,rest_term);
1086
1081
        }
1087
 
        BIF_RET(finalize_list_to_list(p, bytes, rest_term, 0U, pos, characters, UTF8_ERROR, left, NIL));
 
1082
        BIF_RET(finalize_list_to_list(p, bytes, rest_term, 0U, pos, characters, ERTS_UTF8_ERROR, left, NIL));
1088
1083
    } else if (rest_term == NIL && num_leftovers != 0) {
1089
1084
        Eterm leftover_bin = new_binary(p, leftover, num_leftovers);
1090
1085
        if (check_leftovers(leftover,num_leftovers) != 0) {
1091
 
            BIF_RET(finalize_list_to_list(p, bytes, leftover_bin, 0U, pos, characters, UTF8_ERROR, 
 
1086
            BIF_RET(finalize_list_to_list(p, bytes, leftover_bin, 0U, pos, characters, ERTS_UTF8_ERROR, 
1092
1087
                                          left, NIL));
1093
1088
        } else {
1094
 
            BIF_RET(finalize_list_to_list(p, bytes, leftover_bin, 0U, pos, characters, UTF8_INCOMPLETE, 
 
1089
            BIF_RET(finalize_list_to_list(p, bytes, leftover_bin, 0U, pos, characters, ERTS_UTF8_INCOMPLETE, 
1095
1090
                                          left, NIL));
1096
1091
        }
1097
1092
    } else { /* All OK */           
1107
1102
            rc.num_processed_bytes = 0; /* not used */
1108
1103
            rc.num_bytes_to_process = pos;
1109
1104
            rc.num_resulting_chars = characters;
1110
 
            rc.state = UTF8_OK; /* not used */
 
1105
            rc.state = ERTS_UTF8_OK; /* not used */
1111
1106
            BIF_TRAP3(&characters_to_list_trap_1_exp, p, make_magic_bin_for_restart(p,&rc), 
1112
1107
                      rest_term, latin1);
1113
1108
        } else { /* Success */
1114
 
            BIF_RET(finalize_list_to_list(p, bytes, NIL, 0U, pos, characters, UTF8_OK, left, NIL));
 
1109
            BIF_RET(finalize_list_to_list(p, bytes, NIL, 0U, pos, characters, ERTS_UTF8_OK, left, NIL));
1115
1110
        }
1116
1111
    }
1117
1112
}
1205
1200
 * When input to characters_to_list is a plain binary and the format is 'unicode', we do
1206
1201
 * a faster analyze and size count with this function.
1207
1202
 */
1208
 
static int analyze_utf8(byte *source, Uint size, 
 
1203
int erts_analyze_utf8(byte *source, Uint size, 
1209
1204
                        byte **err_pos, Uint *num_chars, int *left)
1210
1205
{
1211
1206
    *err_pos = source;
1216
1211
            --size; 
1217
1212
        } else if (((*source) & ((byte) 0xE0)) == 0xC0) {
1218
1213
            if (size < 2) {
1219
 
                return UTF8_INCOMPLETE;
 
1214
                return ERTS_UTF8_INCOMPLETE;
1220
1215
            }
1221
1216
            if (((source[1] & ((byte) 0xC0)) != 0x80) ||
1222
1217
                ((*source) < 0xC2) /* overlong */) {
1223
 
                return UTF8_ERROR;
 
1218
                return ERTS_UTF8_ERROR;
1224
1219
            }
1225
1220
            source += 2;
1226
1221
            size -= 2;
1227
1222
        } else if (((*source) & ((byte) 0xF0)) == 0xE0) {
1228
1223
            if (size < 3) {
1229
 
                return UTF8_INCOMPLETE;
 
1224
                return ERTS_UTF8_INCOMPLETE;
1230
1225
            }
1231
1226
            if (((source[1] & ((byte) 0xC0)) != 0x80) ||
1232
1227
                ((source[2] & ((byte) 0xC0)) != 0x80) ||
1233
1228
                (((*source) == 0xE0) && (source[1] < 0xA0)) /* overlong */ ) {
1234
 
                return UTF8_ERROR;
 
1229
                return ERTS_UTF8_ERROR;
1235
1230
            }
1236
1231
            if ((((*source) & ((byte) 0xF)) == 0xD) && 
1237
1232
                ((source[1] & 0x20) != 0)) {
1238
 
                return UTF8_ERROR;
 
1233
                return ERTS_UTF8_ERROR;
1239
1234
            }
1240
1235
            if (((*source) == 0xEF) && (source[1] == 0xBF) &&
1241
1236
                ((source[2] == 0xBE) || (source[2] == 0xBF))) {
1242
 
                return UTF8_ERROR;
 
1237
                return ERTS_UTF8_ERROR;
1243
1238
            }
1244
1239
            source += 3;
1245
1240
            size -= 3;
1246
1241
        } else if (((*source) & ((byte) 0xF8)) == 0xF0) {
1247
1242
            if (size < 4) {
1248
 
                return UTF8_INCOMPLETE;
 
1243
                return ERTS_UTF8_INCOMPLETE;
1249
1244
            }
1250
1245
            if (((source[1] & ((byte) 0xC0)) != 0x80) ||
1251
1246
                ((source[2] & ((byte) 0xC0)) != 0x80) ||
1252
1247
                ((source[3] & ((byte) 0xC0)) != 0x80) ||
1253
1248
                (((*source) == 0xF0) && (source[1] < 0x90)) /* overlong */) {
1254
 
                return UTF8_ERROR;
 
1249
                return ERTS_UTF8_ERROR;
1255
1250
            }
1256
1251
            if ((((*source) & ((byte)0x7)) > 0x4U) ||
1257
1252
                ((((*source) & ((byte)0x7)) == 0x4U) && 
1258
1253
                 ((source[1] & ((byte)0x3F)) > 0xFU))) {
1259
 
                return UTF8_ERROR;
 
1254
                return ERTS_UTF8_ERROR;
1260
1255
            }
1261
1256
            source += 4;
1262
1257
            size -= 4; 
1263
1258
        } else {
1264
 
            return UTF8_ERROR;
 
1259
            return ERTS_UTF8_ERROR;
1265
1260
        }
1266
1261
        ++(*num_chars);
1267
1262
        *err_pos = source;
1268
1263
        if (left && --(*left) <= 0) {
1269
 
            return UTF8_ANALYZE_MORE;
 
1264
            return ERTS_UTF8_ANALYZE_MORE;
1270
1265
        }
1271
1266
    }
1272
 
    return UTF8_OK;
 
1267
    return ERTS_UTF8_OK;
1273
1268
}
1274
1269
 
1275
1270
/*
1304
1299
        } else if (((*source) & ((byte) 0xE0)) == 0xC0) {
1305
1300
            unipoint = 
1306
1301
                (((Uint) ((*source) & ((byte) 0x1F))) << 6) |
1307
 
                ((Uint) (source[1] & ((byte) 0x3F)));   
 
1302
                ((Uint) (source[1] & ((byte) 0x3F)));
1308
1303
        } else if (((*source) & ((byte) 0xF0)) == 0xE0) {
1309
1304
            unipoint = 
1310
1305
                (((Uint) ((*source) & ((byte) 0xF))) << 12) |
1330
1325
    return ret;
1331
1326
}
1332
1327
 
 
1328
static int is_candidate(Uint cp)
 
1329
{
 
1330
    int index,pos;
 
1331
    if (cp < 768) return 0;
 
1332
    if (cp > 4023) {
 
1333
        if (cp == 12441 || cp == 12442) return 1;
 
1334
        return 0;
 
1335
    }
 
1336
    index = cp / 32 - COMP_CANDIDATE_MAP_OFFSET;
 
1337
    pos = cp % 32;
 
1338
    return !!(comp_candidate_map[index] & (1UL << pos));
 
1339
}
 
1340
 
 
1341
static int hashsearch(int *htab, int htab_size, CompEntry *cv, Uint16 c)
 
1342
{
 
1343
        int bucket = c % htab_size;
 
1344
        while (htab[bucket] != -1 && cv[htab[bucket]].c != c)
 
1345
            bucket = (bucket + 1) % htab_size;
 
1346
        return htab[bucket];
 
1347
}
 
1348
 
 
1349
#define TRANSLATE_NO 0
 
1350
#define TRANSLATE_MAYBE -1
 
1351
 
 
1352
/* The s array is reversed */
 
1353
static int translate(Uint16 *s, int slen, Uint16 *res)
 
1354
{
 
1355
    /* Go backwards through buffer and match against tree */
 
1356
    int pos = 0;
 
1357
    CompEntry *cv = compose_tab;
 
1358
    int *hc = hash_compose_tab;
 
1359
    int cvs = compose_tab_size;
 
1360
    int x;
 
1361
    while (pos < slen) {
 
1362
        x = hashsearch(hc,cvs*HASH_SIZE_FACTOR,cv,s[pos]);
 
1363
        if (x < 0) {
 
1364
            return TRANSLATE_NO;
 
1365
        } 
 
1366
        if (cv[x].res) {
 
1367
            *res = cv[x].res;
 
1368
            return pos;
 
1369
        }
 
1370
        cvs = cv[x].num_subs;
 
1371
        hc = cv[x].hash;
 
1372
        cv = cv[x].subs;
 
1373
        ++pos;
 
1374
    }
 
1375
    return TRANSLATE_MAYBE;
 
1376
}
 
1377
 
 
1378
static void handle_first_norm(Uint16 *savepoints, int *numpointsp, Uint unipoint)
 
1379
{
 
1380
    /*erts_fprintf(stderr,"CP = %d, numpoints = %d\n",(int) unipoint,(int) *numpointsp);*/
 
1381
    *numpointsp = 1;
 
1382
    savepoints[0] = (Uint16) unipoint;
 
1383
}
 
1384
 
 
1385
static void cleanup_norm(Eterm **hpp, Uint16 *savepoints, int numpoints, Eterm *retp)
 
1386
{
 
1387
    Eterm *hp = *hpp;
 
1388
    int res,i;
 
1389
    Uint16 newpoint;
 
1390
    Eterm ret = *retp;
 
1391
    
 
1392
    ret = CONS(hp,make_small((Uint) savepoints[0]),ret);
 
1393
    hp += 2;
 
1394
    
 
1395
    for (i = 1;i < numpoints;) {
 
1396
        if(!is_candidate(savepoints[i]) || 
 
1397
           ((res = translate(savepoints+i,numpoints - i, &newpoint)) <= 0)) {
 
1398
            ret = CONS(hp,make_small((Uint) savepoints[i]),ret);
 
1399
            hp += 2;
 
1400
            ++i;
 
1401
        } else {
 
1402
            ret = CONS(hp,make_small((Uint) newpoint),ret);
 
1403
            hp += 2;
 
1404
            i += res;
 
1405
        }
 
1406
    }
 
1407
    *retp = ret;
 
1408
}
 
1409
    
 
1410
static void handle_potential_norm(Eterm **hpp, Uint16 *savepoints, int *numpointsp, Uint unipoint, Eterm *retp)
 
1411
{
 
1412
    Eterm *hp = *hpp;
 
1413
    int numpoints = *numpointsp;
 
1414
    int res,i;
 
1415
    Uint16 newpoint;
 
1416
    Eterm ret = *retp;
 
1417
 
 
1418
    /* erts_fprintf(stderr,"CP = %d, numpoints = %d\n",(int) unipoint,(int) numpoints);*/
 
1419
    if ((unipoint >> 16) == 0) { /* otherwise we're done here */ 
 
1420
        savepoints[numpoints++] = (Uint16) unipoint;
 
1421
        res = translate(savepoints,numpoints,&newpoint);
 
1422
        if (res == TRANSLATE_NO) {
 
1423
            ret = CONS(hp,make_small((Uint) savepoints[0]),ret);
 
1424
            hp += 2;
 
1425
            for (i = 1;i < numpoints;) {
 
1426
                if(!is_candidate(savepoints[i]) ||
 
1427
                   ((res = translate(savepoints+i,numpoints - i, &newpoint)) == 0)) {
 
1428
                    ret = CONS(hp,make_small((Uint) savepoints[i]),ret);
 
1429
                    hp += 2;
 
1430
                    ++i;
 
1431
                } else if (res > 0) {
 
1432
                    ret = CONS(hp,make_small((Uint) newpoint),ret);
 
1433
                    hp += 2;
 
1434
                    i += res;
 
1435
                } else { /* res < 0 */
 
1436
                    /* A "maybe", means we are not done yet */
 
1437
                    int j = 0;
 
1438
                    while (i < numpoints) {
 
1439
                        savepoints[j++] = savepoints[i++];
 
1440
                    }
 
1441
                    numpoints = j;
 
1442
                    goto breakaway;
 
1443
                }
 
1444
            }
 
1445
            numpoints = 0;
 
1446
        breakaway:
 
1447
            ;
 
1448
        } else if (res > 0) {
 
1449
            numpoints = 0;
 
1450
            ret = CONS(hp,make_small((Uint) newpoint),ret);
 
1451
            hp += 2;
 
1452
        } /* < 0 means go on */
 
1453
    } else {
 
1454
        /* Unconditional rollup, this character is larger than 16 bit */
 
1455
        ret = CONS(hp,make_small((Uint) savepoints[0]),ret);
 
1456
        hp += 2;
 
1457
        
 
1458
        for (i = 1;i < numpoints;) {
 
1459
            if(!is_candidate(savepoints[i]) || 
 
1460
               ((res = translate(savepoints+i,numpoints - i, &newpoint)) <= 0)) {
 
1461
                ret = CONS(hp,make_small((Uint) savepoints[i]),ret);
 
1462
                hp += 2;
 
1463
                ++i;
 
1464
            } else {
 
1465
                ret = CONS(hp,make_small((Uint) newpoint),ret);
 
1466
                hp += 2;
 
1467
                i += res;
 
1468
            }
 
1469
        }
 
1470
        ret = CONS(hp,make_small(unipoint),ret);
 
1471
        hp += 2;
 
1472
        numpoints = 0;
 
1473
    }   
 
1474
    *hpp = hp;
 
1475
    *numpointsp = numpoints;
 
1476
    *retp = ret;
 
1477
 
1478
 
 
1479
static Eterm do_utf8_to_list_normalize(Process *p, Uint num, byte *bytes, Uint sz)
 
1480
{
 
1481
    Eterm *hp,*hp_end;
 
1482
    Eterm ret;
 
1483
    byte *source;
 
1484
    Uint unipoint;
 
1485
    Uint16 savepoints[4];
 
1486
    int numpoints = 0;
 
1487
 
 
1488
    ASSERT(num > 0);
 
1489
 
 
1490
    hp = HAlloc(p,num * 2); /* May be to much */
 
1491
    hp_end = hp + num * 2;
 
1492
    ret = NIL;
 
1493
    source = bytes + sz;
 
1494
    while(--source >= bytes) {
 
1495
        if (((*source) & ((byte) 0x80)) == 0) {
 
1496
            unipoint = (Uint) *source;
 
1497
        } else if (((*source) & ((byte) 0xE0)) == 0xC0) {
 
1498
            unipoint = 
 
1499
                (((Uint) ((*source) & ((byte) 0x1F))) << 6) |
 
1500
                ((Uint) (source[1] & ((byte) 0x3F)));   
 
1501
        } else if (((*source) & ((byte) 0xF0)) == 0xE0) {
 
1502
            unipoint = 
 
1503
                (((Uint) ((*source) & ((byte) 0xF))) << 12) |
 
1504
                (((Uint) (source[1] & ((byte) 0x3F))) << 6) |
 
1505
                ((Uint) (source[2] & ((byte) 0x3F)));           
 
1506
        } else if (((*source) & ((byte) 0xF8)) == 0xF0) {
 
1507
            unipoint = 
 
1508
                (((Uint) ((*source) & ((byte) 0x7))) << 18) |
 
1509
                (((Uint) (source[1] & ((byte) 0x3F))) << 12) |
 
1510
                (((Uint) (source[2] & ((byte) 0x3F))) << 6) |
 
1511
                ((Uint) (source[3] & ((byte) 0x3F)));           
 
1512
        } else {
 
1513
            /* ignore 2#10XXXXXX */
 
1514
            continue;
 
1515
        }
 
1516
        if (numpoints) {
 
1517
            handle_potential_norm(&hp,savepoints,&numpoints,unipoint,&ret);
 
1518
            continue;
 
1519
        }
 
1520
        /* We are not building up any normalizations yet, look that we shouldn't start... */
 
1521
        if (is_candidate(unipoint)) {
 
1522
            handle_first_norm(savepoints,&numpoints,unipoint);
 
1523
            continue;
 
1524
        } 
 
1525
        ret = CONS(hp,make_small(unipoint),ret);
 
1526
        hp += 2;
 
1527
    }
 
1528
    /* so, we'we looped to the beginning, do we have anything saved? */
 
1529
    if (numpoints) {
 
1530
        cleanup_norm(&hp,savepoints,numpoints,&ret);
 
1531
    }
 
1532
    if (hp_end != hp) {
 
1533
        HRelease(p,hp_end,hp);
 
1534
    }
 
1535
    return ret;
 
1536
}
 
1537
 
1333
1538
/*
1334
1539
 * The last step of characters_to_list, build a list from the buffer 'bytes' (created in the same way
1335
1540
 * as for characters_to_utf8). All sizes are known in advance and most data will be held in a 
1378
1583
     */
1379
1584
 
1380
1585
    free_restart(bytes);
1381
 
    if (state == UTF8_INCOMPLETE) {
 
1586
    if (state == ERTS_UTF8_INCOMPLETE) {
1382
1587
        hp = HAlloc(p,4);
1383
1588
        ret = TUPLE3(hp,am_incomplete,converted,rest);
1384
 
    } else if (state == UTF8_ERROR) {
 
1589
    } else if (state == ERTS_UTF8_ERROR) {
1385
1590
        hp = HAlloc(p,4);
1386
1591
        ret = TUPLE3(hp,am_error,converted,rest);
1387
1592
    } else {
1408
1613
 
1409
1614
/*
1410
1615
 * Hooks into the process of decoding a binary depending on state.
1411
 
 * If last_state is UTF8_ANALYZE_MORE, num_bytes_to_process 
 
1616
 * If last_state is ERTS_UTF8_ANALYZE_MORE, num_bytes_to_process 
1412
1617
 * and num_resulting_chars will grow
1413
1618
 * until we're done analyzing the binary. Then we'll eat 
1414
1619
 * the bytes to process, lowering num_bytes_to_process and num_resulting_chars,
1465
1670
 
1466
1671
    left = allowed_iterations(p);
1467
1672
    
1468
 
    if (state == UTF8_ANALYZE_MORE) {
1469
 
        state = analyze_utf8(bytes + num_bytes_to_process,
 
1673
    if (state == ERTS_UTF8_ANALYZE_MORE) {
 
1674
        state = erts_analyze_utf8(bytes + num_bytes_to_process,
1470
1675
                             size - num_bytes_to_process,
1471
1676
                             &endpos,&numchar,&left);
1472
1677
        cost_to_proc(p,numchar);
1473
1678
        num_resulting_chars += numchar;
1474
1679
        num_bytes_to_process = endpos - bytes;
1475
 
        if (state == UTF8_ANALYZE_MORE) {
 
1680
        if (state == ERTS_UTF8_ANALYZE_MORE) {
1476
1681
            Eterm epos = erts_make_integer(num_bytes_to_process,p);
1477
1682
            Eterm enumchar = erts_make_integer(num_resulting_chars,p);
1478
1683
            erts_free_aligned_binary_bytes(temp_alloc);
1528
1733
        ErlSubBin *sb;
1529
1734
        Eterm orig;
1530
1735
        Uint offset;
1531
 
        ASSERT(state != UTF8_OK);
 
1736
        ASSERT(state != ERTS_UTF8_OK);
1532
1737
        hp = HAlloc(p, ERL_SUB_BIN_SIZE);
1533
1738
        sb = (ErlSubBin *) hp;
1534
1739
        ERTS_GET_REAL_BIN(orig_bin, orig, offset, bitoffs, bitsize);
1544
1749
 
1545
1750
    /* Done */
1546
1751
 
1547
 
    if (state == UTF8_INCOMPLETE) {
 
1752
    if (state == ERTS_UTF8_INCOMPLETE) {
1548
1753
        if (check_leftovers(bytes + num_bytes_to_process + num_processed_bytes,
1549
1754
                            b_sz) != 0) {
1550
1755
            goto error_return;
1551
1756
        }
1552
1757
        hp = HAlloc(p,4);
1553
1758
        ret = TUPLE3(hp,am_incomplete,converted,rest);
1554
 
    } else if (state == UTF8_ERROR) {
 
1759
    } else if (state == ERTS_UTF8_ERROR) {
1555
1760
 error_return:
1556
1761
        hp = HAlloc(p,4);
1557
1762
        ret = TUPLE3(hp,am_error,converted,rest);
1589
1794
                               0U, /* nothing processed yet */
1590
1795
                               num_bytes_to_process, 
1591
1796
                               num_resulting_chars,
1592
 
                               UTF8_ANALYZE_MORE, /* always this state here */
 
1797
                               ERTS_UTF8_ANALYZE_MORE, /* always this state here */
1593
1798
                               NIL); /* Nothing built -> no tail yet */
1594
1799
        
1595
1800
}
1642
1847
        BIF_ERROR(BIF_P,BADARG);
1643
1848
    }
1644
1849
    return do_bif_utf8_to_list(BIF_P, BIF_ARG_1, 0U, 0U, 0U, 
1645
 
                               UTF8_ANALYZE_MORE,NIL);
 
1850
                               ERTS_UTF8_ANALYZE_MORE,NIL);
1646
1851
}
1647
1852
 
1648
1853
 
1728
1933
            Uint n;
1729
1934
            int reds_left = bin_size+1; /* Number of reductions left. */
1730
1935
 
1731
 
            if (analyze_utf8(bytes, bin_size, &err_pos,
1732
 
                             &n, &reds_left) == UTF8_OK) {
 
1936
            if (erts_analyze_utf8(bytes, bin_size, &err_pos,
 
1937
                             &n, &reds_left) == ERTS_UTF8_OK) {
1733
1938
                /* 
1734
1939
                 * Correct UTF-8 encoding, but too many characters to
1735
1940
                 * fit in an atom.
1813
2018
{
1814
2019
    return binary_to_atom(BIF_P, BIF_ARG_1, BIF_ARG_2, 1);
1815
2020
}
 
2021
 
 
2022
/**********************************************************
 
2023
 * Simpler non-interruptable routines for UTF-8 and 
 
2024
 * Windowish UTF-16 (restricted)
 
2025
 **********************************************************/
 
2026
/*
 
2027
 * This function is the heart of the Unicode support for 
 
2028
 * open_port - spawn_executable. It converts both the name
 
2029
 * of the executable and the arguments according to the same rules
 
2030
 * as for filename conversion. That means as if your arguments are
 
2031
 * to be raw, you supply binaries, else unicode characters are allowed up to
 
2032
 * the encoding maximum (256 of the unicode max).
 
2033
 * Depending on the filename encoding standard, the vector is then
 
2034
 * converted to whatever is used, which might mean win_utf16 if on windows.
 
2035
 * Do not peek into the argument vector or filenam with ordinary
 
2036
 * string routines, that will certainly fail on some OS.
 
2037
 */
 
2038
 
 
2039
char *erts_convert_filename_to_native(Eterm name, ErtsAlcType_t alloc_type, int allow_empty)
 
2040
{
 
2041
    int encoding = erts_get_native_filename_encoding();
 
2042
    char* name_buf = NULL;
 
2043
 
 
2044
    if (is_atom(name) || is_list(name) || (allow_empty && is_nil(name))) {
 
2045
        Sint need;
 
2046
        if ((need = erts_native_filename_need(name,encoding)) < 0) {
 
2047
            return NULL;
 
2048
        }
 
2049
        if (encoding == ERL_FILENAME_WIN_WCHAR) {
 
2050
            need += 2;
 
2051
        } else {
 
2052
            ++need;
 
2053
        }
 
2054
        name_buf = (char *) erts_alloc(alloc_type, need);
 
2055
        erts_native_filename_put(name,encoding,(byte *)name_buf); 
 
2056
        name_buf[need-1] = 0;
 
2057
        if (encoding == ERL_FILENAME_WIN_WCHAR) {
 
2058
            name_buf[need-2] = 0;
 
2059
        }
 
2060
    } else if (is_binary(name)) {
 
2061
        byte *temp_alloc = NULL;
 
2062
        byte *bytes;
 
2063
        byte *err_pos;
 
2064
        Uint size,num_chars;
 
2065
        
 
2066
        size = binary_size(name);
 
2067
        bytes = erts_get_aligned_binary_bytes(name, &temp_alloc);
 
2068
        if (encoding != ERL_FILENAME_WIN_WCHAR) {
 
2069
            /*Add 0 termination only*/
 
2070
            name_buf = (char *) erts_alloc(alloc_type, size+1);
 
2071
            memcpy(name_buf,bytes,size);
 
2072
            name_buf[size]=0;
 
2073
        } else if (erts_analyze_utf8(bytes,size,&err_pos,&num_chars,NULL) != ERTS_UTF8_OK || 
 
2074
                   erts_get_user_requested_filename_encoding() ==  ERL_FILENAME_LATIN1) {
 
2075
            byte *p;
 
2076
            /* What to do now? Maybe latin1, so just take byte for byte instead */
 
2077
            name_buf = (char *) erts_alloc(alloc_type, (size+1)*2);
 
2078
            p = (byte *) name_buf;
 
2079
            while (size--) {
 
2080
                *p++ = *bytes++;
 
2081
                *p++ = 0;
 
2082
            }
 
2083
            *p++ = 0;
 
2084
            *p++ = 0;
 
2085
        } else { /* WIN_WCHAR and valid UTF8 */
 
2086
            name_buf = (char *) erts_alloc(alloc_type, (num_chars+1)*2);
 
2087
            erts_copy_utf8_to_utf16_little((byte *) name_buf, bytes, num_chars);
 
2088
            name_buf[num_chars*2] = 0;
 
2089
            name_buf[num_chars*2+1] = 0;
 
2090
        }
 
2091
        erts_free_aligned_binary_bytes(temp_alloc);
 
2092
    } else {
 
2093
        return NULL;
 
2094
    }
 
2095
    return name_buf;
 
2096
}
 
2097
 
 
2098
 
 
2099
Sint erts_native_filename_need(Eterm ioterm, int encoding) 
 
2100
{
 
2101
    Eterm *objp;
 
2102
    Eterm obj;
 
2103
    DECLARE_ESTACK(stack);
 
2104
    Sint need = 0;
 
2105
 
 
2106
    if (is_atom(ioterm)) {
 
2107
        Atom* ap;
 
2108
        int i;
 
2109
        ap = atom_tab(atom_val(ioterm));
 
2110
        switch (encoding) {
 
2111
        case ERL_FILENAME_LATIN1:
 
2112
            need = ap->len;
 
2113
            break;
 
2114
        case ERL_FILENAME_UTF8_MAC:
 
2115
        case ERL_FILENAME_UTF8:
 
2116
            for (i = 0; i < ap->len; i++) {
 
2117
                need += (ap->name[i] >= 0x80) ? 2 : 1;
 
2118
            }
 
2119
            break;
 
2120
        case ERL_FILENAME_WIN_WCHAR:
 
2121
            need = 2*(ap->len);
 
2122
            break;
 
2123
        default:
 
2124
            need = -1;
 
2125
        }
 
2126
        DESTROY_ESTACK(stack);
 
2127
        return need;
 
2128
    }
 
2129
 
 
2130
    if (is_nil(ioterm)) {
 
2131
        DESTROY_ESTACK(stack);
 
2132
        return need;
 
2133
    }
 
2134
    if (!is_list(ioterm)) {
 
2135
        DESTROY_ESTACK(stack);
 
2136
        return (Sint) -1;
 
2137
    }
 
2138
    /* OK a list, needs to be processed in order, handling each flat list-level
 
2139
       as they occur, just like io_list_to_binary would */
 
2140
    ESTACK_PUSH(stack,ioterm);
 
2141
    while (!ESTACK_ISEMPTY(stack)) {
 
2142
        ioterm = ESTACK_POP(stack);     
 
2143
        if (is_nil(ioterm)) {
 
2144
            /* ignore empty lists */
 
2145
            continue;
 
2146
        }
 
2147
        if(is_list(ioterm)) {
 
2148
L_Again:   /* Restart with sublist, old listend was pushed on stack */
 
2149
            objp = list_val(ioterm);
 
2150
            obj = CAR(objp);
 
2151
            for(;;) { /* loop over one flat list of bytes and binaries
 
2152
                         until sublist or list end is encountered */
 
2153
                if (is_small(obj)) { /* Always small */
 
2154
                    for(;;) {
 
2155
                        Uint x = unsigned_val(obj);
 
2156
                        switch (encoding) {
 
2157
                        case ERL_FILENAME_LATIN1:
 
2158
                            if (x > 255) {
 
2159
                                DESTROY_ESTACK(stack);
 
2160
                                return ((Sint) -1);
 
2161
                            }
 
2162
                            need += 1;
 
2163
                            break;
 
2164
                        case ERL_FILENAME_UTF8_MAC:
 
2165
                        case ERL_FILENAME_UTF8:
 
2166
                            if (x < 0x80) {
 
2167
                                need +=1;
 
2168
                            } else if (x < 0x800) {
 
2169
                                need += 2;
 
2170
                            } else if (x < 0x10000) {
 
2171
                                if ((x >= 0xD800 && x <= 0xDFFF) ||
 
2172
                                    (x == 0xFFFE) ||
 
2173
                                    (x == 0xFFFF)) { /* Invalid unicode range */
 
2174
                                    DESTROY_ESTACK(stack);
 
2175
                                    return ((Sint) -1);
 
2176
                                }
 
2177
                                need += 3;
 
2178
                            } else  if (x < 0x110000) {
 
2179
                                need += 4; 
 
2180
                            } else {
 
2181
                                DESTROY_ESTACK(stack);
 
2182
                                return ((Sint) -1);
 
2183
                            }
 
2184
                            break;
 
2185
                        case ERL_FILENAME_WIN_WCHAR:
 
2186
                            if (x <= 0xffff) { 
 
2187
                                need += 2;
 
2188
                                break;
 
2189
                            } /* else fall throug to error */
 
2190
                        default:
 
2191
                            DESTROY_ESTACK(stack);
 
2192
                            return ((Sint) -1);
 
2193
                        }
 
2194
                            
 
2195
                        /* everything else will give badarg later 
 
2196
                           in the process, so we dont check */
 
2197
                        ioterm = CDR(objp);
 
2198
                        if (!is_list(ioterm)) {
 
2199
                            break;
 
2200
                        }
 
2201
                        objp = list_val(ioterm);
 
2202
                        obj = CAR(objp);
 
2203
                        if (!is_small(obj))
 
2204
                            break;
 
2205
                    }
 
2206
                } else if (is_nil(obj)) {
 
2207
                    ioterm = CDR(objp);
 
2208
                    if (!is_list(ioterm)) {
 
2209
                        break;
 
2210
                    }
 
2211
                    objp = list_val(ioterm);
 
2212
                    obj = CAR(objp);
 
2213
                } else if (is_list(obj)) {
 
2214
                    /* push rest of list for later processing, start 
 
2215
                       again with sublist */
 
2216
                    ESTACK_PUSH(stack,CDR(objp));
 
2217
                    ioterm = obj;
 
2218
                    goto L_Again;
 
2219
                } else {
 
2220
                    DESTROY_ESTACK(stack);
 
2221
                    return ((Sint) -1);
 
2222
                } 
 
2223
                if (is_nil(ioterm) || !is_list(ioterm)) {
 
2224
                    break;
 
2225
                }
 
2226
            } /* for(;;) */
 
2227
        } /* is_list(ioterm) */
 
2228
        
 
2229
        if (!is_list(ioterm) && !is_nil(ioterm)) {
 
2230
            /* inproper list end */
 
2231
            DESTROY_ESTACK(stack);
 
2232
            return ((Sint) -1);
 
2233
        }
 
2234
    } /* while  not estack empty */
 
2235
    DESTROY_ESTACK(stack);
 
2236
    return need;
 
2237
}
 
2238
 
 
2239
void erts_native_filename_put(Eterm ioterm, int encoding, byte *p) 
 
2240
{
 
2241
    Eterm *objp;
 
2242
    Eterm obj;
 
2243
    DECLARE_ESTACK(stack);
 
2244
 
 
2245
    if (is_atom(ioterm)) {
 
2246
        Atom* ap;
 
2247
        int i;
 
2248
        ap = atom_tab(atom_val(ioterm));
 
2249
        switch (encoding) {
 
2250
        case ERL_FILENAME_LATIN1:
 
2251
            for (i = 0; i < ap->len; i++) {
 
2252
                *p++ = ap->name[i];
 
2253
            }
 
2254
            break;
 
2255
        case ERL_FILENAME_UTF8_MAC:
 
2256
        case ERL_FILENAME_UTF8:
 
2257
            for (i = 0; i < ap->len; i++) {
 
2258
                if(ap->name[i] < 0x80) {
 
2259
                    *p++ = ap->name[i];
 
2260
                } else {
 
2261
                    *p++ = (((ap->name[i]) >> 6) | ((byte) 0xC0));
 
2262
                    *p++ = (((ap->name[i]) & 0x3F) | ((byte) 0x80));
 
2263
                }
 
2264
            }
 
2265
            break;
 
2266
        case ERL_FILENAME_WIN_WCHAR:
 
2267
            for (i = 0; i < ap->len; i++) {
 
2268
                /* Little endian */
 
2269
                *p++ = ap->name[i];
 
2270
                *p++ = 0;
 
2271
            }
 
2272
            break;
 
2273
        default:
 
2274
            ASSERT(0);
 
2275
        }
 
2276
        DESTROY_ESTACK(stack);
 
2277
        return;
 
2278
    }
 
2279
 
 
2280
    if (is_nil(ioterm)) {
 
2281
        DESTROY_ESTACK(stack);
 
2282
        return;
 
2283
    }
 
2284
    ASSERT(is_list(ioterm));
 
2285
    /* OK a list, needs to be processed in order, handling each flat list-level
 
2286
       as they occur, just like io_list_to_binary would */
 
2287
    ESTACK_PUSH(stack,ioterm);
 
2288
    while (!ESTACK_ISEMPTY(stack)) {
 
2289
        ioterm = ESTACK_POP(stack);     
 
2290
        if (is_nil(ioterm)) {
 
2291
            /* ignore empty lists */
 
2292
            continue;
 
2293
        }
 
2294
        if(is_list(ioterm)) {
 
2295
L_Again:   /* Restart with sublist, old listend was pushed on stack */
 
2296
            objp = list_val(ioterm);
 
2297
            obj = CAR(objp);
 
2298
            for(;;) { /* loop over one flat list of bytes and binaries
 
2299
                         until sublist or list end is encountered */
 
2300
                if (is_small(obj)) { /* Always small */
 
2301
                    for(;;) {
 
2302
                        Uint x = unsigned_val(obj);
 
2303
                        switch (encoding) {
 
2304
                        case ERL_FILENAME_LATIN1:
 
2305
                            ASSERT( x < 256);
 
2306
                            *p++ = (byte) x;
 
2307
                            break;
 
2308
                        case ERL_FILENAME_UTF8_MAC:
 
2309
                        case ERL_FILENAME_UTF8:
 
2310
                            if (x < 0x80) {
 
2311
                                *p++ = (byte) x;
 
2312
                            }
 
2313
                            else if (x < 0x800) {
 
2314
                                *p++ = (((byte) (x >> 6)) | 
 
2315
                                        ((byte) 0xC0));
 
2316
                                *p++ = (((byte) (x & 0x3F)) | 
 
2317
                                        ((byte) 0x80));
 
2318
                            } else if (x < 0x10000) {
 
2319
                                ASSERT(!((x >= 0xD800 && x <= 0xDFFF) ||
 
2320
                                         (x == 0xFFFE) ||
 
2321
                                         (x == 0xFFFF)));
 
2322
                                *p++ = (((byte) (x >> 12)) | 
 
2323
                                        ((byte) 0xE0));
 
2324
                                *p++ = ((((byte) (x >> 6)) & 0x3F)  | 
 
2325
                                        ((byte) 0x80));
 
2326
                                *p++ = (((byte) (x & 0x3F)) | 
 
2327
                                        ((byte) 0x80));
 
2328
                            } else {
 
2329
                                ASSERT(x < 0x110000);
 
2330
                                *p++ = (((byte) (x >> 18)) | 
 
2331
                                        ((byte) 0xF0));
 
2332
                                *p++ = ((((byte) (x >> 12)) & 0x3F)  | 
 
2333
                                        ((byte) 0x80));
 
2334
                                *p++ = ((((byte) (x >> 6)) & 0x3F)  | 
 
2335
                                        ((byte) 0x80));
 
2336
                                *p++ = (((byte) (x & 0x3F)) | 
 
2337
                                        ((byte) 0x80));
 
2338
                            }
 
2339
                            break;
 
2340
                        case ERL_FILENAME_WIN_WCHAR:
 
2341
                            ASSERT(x <= 0xFFFF); 
 
2342
                            *p++ = (byte) (x & 0xFFU);
 
2343
                            *p++ = (byte) ((x >> 8) & 0xFFU);
 
2344
                            break;
 
2345
                        default:
 
2346
                            ASSERT(0);
 
2347
                        }
 
2348
                            
 
2349
                        /* everything else will give badarg later 
 
2350
                           in the process, so we dont check */
 
2351
                        ioterm = CDR(objp);
 
2352
                        if (!is_list(ioterm)) {
 
2353
                            break;
 
2354
                        }
 
2355
                        objp = list_val(ioterm);
 
2356
                        obj = CAR(objp);
 
2357
                        if (!is_small(obj))
 
2358
                            break;
 
2359
                    }
 
2360
                } else if (is_nil(obj)) {
 
2361
                    ioterm = CDR(objp);
 
2362
                    if (!is_list(ioterm)) {
 
2363
                        break;
 
2364
                    }
 
2365
                    objp = list_val(ioterm);
 
2366
                    obj = CAR(objp);
 
2367
                } else if (is_list(obj)) {
 
2368
                    /* push rest of list for later processing, start 
 
2369
                       again with sublist */
 
2370
                    ESTACK_PUSH(stack,CDR(objp));
 
2371
                    ioterm = obj;
 
2372
                    goto L_Again;
 
2373
                } else {
 
2374
                    ASSERT(0);
 
2375
                } 
 
2376
                if (is_nil(ioterm) || !is_list(ioterm)) {
 
2377
                    break;
 
2378
                }
 
2379
            } /* for(;;) */
 
2380
        } /* is_list(ioterm) */
 
2381
        
 
2382
        ASSERT(is_list(ioterm) || is_nil(ioterm));
 
2383
    } /* while  not estack empty */
 
2384
    DESTROY_ESTACK(stack);
 
2385
    return;
 
2386
}
 
2387
void erts_copy_utf8_to_utf16_little(byte *target, byte *bytes, int num_chars)
 
2388
{
 
2389
    Uint unipoint;
 
2390
    
 
2391
    while (num_chars--) {
 
2392
        if (((*bytes) & ((byte) 0x80)) == 0) {
 
2393
            unipoint = (Uint) *bytes;
 
2394
            ++bytes;
 
2395
        } else if (((*bytes) & ((byte) 0xE0)) == 0xC0) {
 
2396
            unipoint = 
 
2397
                (((Uint) ((*bytes) & ((byte) 0x1F))) << 6) |
 
2398
                ((Uint) (bytes[1] & ((byte) 0x3F)));    
 
2399
            bytes += 2;
 
2400
        } else if (((*bytes) & ((byte) 0xF0)) == 0xE0) {
 
2401
            unipoint = 
 
2402
                (((Uint) ((*bytes) & ((byte) 0xF))) << 12) |
 
2403
                (((Uint) (bytes[1] & ((byte) 0x3F))) << 6) |
 
2404
                ((Uint) (bytes[2] & ((byte) 0x3F)));
 
2405
            bytes +=3;
 
2406
        } else if (((*bytes) & ((byte) 0xF8)) == 0xF0) {
 
2407
            unipoint = 
 
2408
                (((Uint) ((*bytes) & ((byte) 0x7))) << 18) |
 
2409
                (((Uint) (bytes[1] & ((byte) 0x3F))) << 12) |
 
2410
                (((Uint) (bytes[2] & ((byte) 0x3F))) << 6) |
 
2411
                ((Uint) (bytes[3] & ((byte) 0x3F)));
 
2412
            bytes += 4;
 
2413
        } else {
 
2414
            erl_exit(1,"Internal unicode error in prim_file:internal_name2native/1");
 
2415
        }
 
2416
        *target++ = (byte) (unipoint & 0xFF);
 
2417
        *target++ = (byte) ((unipoint >> 8) & 0xFF);
 
2418
    }
 
2419
}
 
2420
 
 
2421
/*
 
2422
 * This internal bif converts a filename to whatever format is suitable for the file driver
 
2423
 * It also adds zero termination so that prim_file needn't bother with the character encoding
 
2424
 * of the file driver 
 
2425
 */
 
2426
BIF_RETTYPE prim_file_internal_name2native_1(BIF_ALIST_1)
 
2427
{
 
2428
    int encoding = erts_get_native_filename_encoding();
 
2429
    Sint need;
 
2430
    Eterm bin_term;
 
2431
    byte* bin_p;
 
2432
    /* Prim file explicitly does not allow atoms, although we could 
 
2433
       very well cope with it. Instead of letting 'file' handle them,
 
2434
       it would probably be more efficient to handle them here. Subject to 
 
2435
       change in R15. */ 
 
2436
    if (is_atom(BIF_ARG_1)) {
 
2437
        BIF_ERROR(BIF_P,BADARG);
 
2438
    }
 
2439
    if (is_binary(BIF_ARG_1)) {
 
2440
        byte *temp_alloc = NULL;
 
2441
        byte *bytes;
 
2442
        byte *err_pos;
 
2443
        Uint size,num_chars;
 
2444
        /* Uninterpreted encoding except if windows widechar, in case we convert from 
 
2445
           utf8 to win_wchar */
 
2446
        size = binary_size(BIF_ARG_1);
 
2447
        bytes = erts_get_aligned_binary_bytes(BIF_ARG_1, &temp_alloc);
 
2448
        if (encoding != ERL_FILENAME_WIN_WCHAR) {
 
2449
            /*Add 0 termination only*/
 
2450
            bin_term = new_binary(BIF_P, NULL, size+1);
 
2451
            bin_p = binary_bytes(bin_term);
 
2452
            memcpy(bin_p,bytes,size);
 
2453
            bin_p[size]=0;
 
2454
            erts_free_aligned_binary_bytes(temp_alloc);
 
2455
            BIF_RET(bin_term);
 
2456
        } 
 
2457
        /* In a wchar world, the emulator flags only affect how
 
2458
           binaries are interpreted when sent from the user. */
 
2459
        /* Determine real length and create a new binary */
 
2460
        if (erts_analyze_utf8(bytes,size,&err_pos,&num_chars,NULL) != ERTS_UTF8_OK || 
 
2461
            erts_get_user_requested_filename_encoding() ==  ERL_FILENAME_LATIN1) {
 
2462
            /* What to do now? Maybe latin1, so just take byte for byte instead */
 
2463
            bin_term = new_binary(BIF_P, 0, (size+1)*2);
 
2464
            bin_p = binary_bytes(bin_term);
 
2465
            while (size--) {
 
2466
                *bin_p++ = *bytes++;
 
2467
                *bin_p++ = 0;
 
2468
            }
 
2469
            *bin_p++ = 0;
 
2470
            *bin_p++ = 0;
 
2471
            erts_free_aligned_binary_bytes(temp_alloc);
 
2472
            BIF_RET(bin_term);
 
2473
        }
 
2474
        /* OK, UTF8 ok, number of characters is in num_chars */
 
2475
        bin_term = new_binary(BIF_P, 0, (num_chars+1)*2);
 
2476
        bin_p = binary_bytes(bin_term);
 
2477
        erts_copy_utf8_to_utf16_little(bin_p, bytes, num_chars);
 
2478
        /* zero termination */
 
2479
        bin_p[num_chars*2] = 0;
 
2480
        bin_p[num_chars*2+1] = 0;
 
2481
        erts_free_aligned_binary_bytes(temp_alloc);
 
2482
        BIF_RET(bin_term);
 
2483
    } /* binary */   
 
2484
            
 
2485
 
 
2486
    if ((need = erts_native_filename_need(BIF_ARG_1,encoding)) < 0) {
 
2487
        BIF_ERROR(BIF_P,BADARG);
 
2488
    }
 
2489
    if (encoding == ERL_FILENAME_WIN_WCHAR) {
 
2490
        need += 2;
 
2491
    } else {
 
2492
        ++need;
 
2493
    }
 
2494
    
 
2495
    bin_term = new_binary(BIF_P, 0, need);
 
2496
    bin_p = binary_bytes(bin_term);
 
2497
    erts_native_filename_put(BIF_ARG_1,encoding,bin_p); 
 
2498
    bin_p[need-1] = 0;
 
2499
    if (encoding == ERL_FILENAME_WIN_WCHAR) {
 
2500
        bin_p[need-2] = 0;
 
2501
    }
 
2502
    BIF_RET(bin_term);
 
2503
}
 
2504
 
 
2505
BIF_RETTYPE prim_file_internal_native2name_1(BIF_ALIST_1)
 
2506
{
 
2507
    Eterm real_bin;
 
2508
    Uint offset;
 
2509
    Uint size,num_chars;
 
2510
    Uint bitsize;
 
2511
    Uint bitoffs;
 
2512
    Eterm *hp;
 
2513
    byte *temp_alloc = NULL;
 
2514
    byte *bytes;
 
2515
    byte *err_pos;
 
2516
    Uint num_built; /* characters */
 
2517
    Uint num_eaten; /* bytes */
 
2518
    Eterm ret;
 
2519
    int mac = 0;
 
2520
 
 
2521
    if (is_not_binary(BIF_ARG_1)) {
 
2522
        BIF_ERROR(BIF_P,BADARG);
 
2523
    }
 
2524
    size = binary_size(BIF_ARG_1);
 
2525
    ERTS_GET_REAL_BIN(BIF_ARG_1, real_bin, offset, bitoffs, bitsize);
 
2526
    if (bitsize != 0) {
 
2527
        BIF_ERROR(BIF_P,BADARG);
 
2528
    }
 
2529
    if (size == 0) {
 
2530
        BIF_RET(NIL);
 
2531
    }
 
2532
    switch (erts_get_native_filename_encoding()) {
 
2533
    case ERL_FILENAME_LATIN1:
 
2534
        hp = HAlloc(BIF_P, 2 * size);
 
2535
        bytes = binary_bytes(real_bin)+offset;
 
2536
    
 
2537
        BIF_RET(erts_bin_bytes_to_list(NIL, hp, bytes, size, bitoffs));
 
2538
    case ERL_FILENAME_UTF8_MAC:
 
2539
        mac = 1;
 
2540
    case ERL_FILENAME_UTF8:
 
2541
        bytes = erts_get_aligned_binary_bytes(BIF_ARG_1, &temp_alloc);
 
2542
        if (erts_analyze_utf8(bytes,size,&err_pos,&num_chars,NULL) != ERTS_UTF8_OK) {
 
2543
            erts_free_aligned_binary_bytes(temp_alloc);
 
2544
            goto noconvert;
 
2545
        }
 
2546
        num_built = 0;
 
2547
        num_eaten = 0;
 
2548
        if (mac) {
 
2549
            ret = do_utf8_to_list_normalize(BIF_P, num_chars, bytes, size);
 
2550
        } else {
 
2551
            ret = do_utf8_to_list(BIF_P, num_chars, bytes, size, num_chars, &num_built, &num_eaten, NIL);
 
2552
        } 
 
2553
        erts_free_aligned_binary_bytes(temp_alloc);
 
2554
        BIF_RET(ret);
 
2555
    case ERL_FILENAME_WIN_WCHAR:
 
2556
        bytes = erts_get_aligned_binary_bytes(BIF_ARG_1, &temp_alloc);
 
2557
        if ((size % 2) != 0) { /* Panic fixup to avoid crashing the emulator */
 
2558
            size--;
 
2559
            hp = HAlloc(BIF_P, size+2);
 
2560
            ret = CONS(hp,make_small((Uint) bytes[size]),NIL);
 
2561
            hp += 2;
 
2562
        } else {
 
2563
            hp = HAlloc(BIF_P, size);
 
2564
            ret = NIL;
 
2565
        }
 
2566
        bytes += size-1;
 
2567
        while (size > 0) {
 
2568
            Uint x = ((Uint) *bytes--) << 8;
 
2569
            x |= ((Uint) *bytes--);
 
2570
            size -= 2;
 
2571
            ret = CONS(hp,make_small(x),ret);
 
2572
            hp += 2;
 
2573
        }           
 
2574
        erts_free_aligned_binary_bytes(temp_alloc);
 
2575
        BIF_RET(ret);
 
2576
    default:
 
2577
        goto noconvert;
 
2578
    }
 
2579
 noconvert:
 
2580
    BIF_RET(BIF_ARG_1);
 
2581
}
 
2582
 
 
2583
BIF_RETTYPE prim_file_internal_normalize_utf8_1(BIF_ALIST_1)
 
2584
{
 
2585
    Eterm real_bin;
 
2586
    Uint offset;
 
2587
    Uint size,num_chars;
 
2588
    Uint bitsize;
 
2589
    Uint bitoffs;
 
2590
    Eterm ret;
 
2591
    byte *temp_alloc = NULL;
 
2592
    byte *bytes;
 
2593
    byte *err_pos;
 
2594
 
 
2595
    if (is_not_binary(BIF_ARG_1)) {
 
2596
        BIF_ERROR(BIF_P,BADARG);
 
2597
    }
 
2598
    size = binary_size(BIF_ARG_1);
 
2599
    ERTS_GET_REAL_BIN(BIF_ARG_1, real_bin, offset, bitoffs, bitsize);
 
2600
    if (bitsize != 0) {
 
2601
        BIF_ERROR(BIF_P,BADARG);
 
2602
    }
 
2603
    if (size == 0) {
 
2604
        BIF_RET(NIL);
 
2605
    }
 
2606
    bytes = erts_get_aligned_binary_bytes(BIF_ARG_1, &temp_alloc);
 
2607
    if (erts_analyze_utf8(bytes,size,&err_pos,&num_chars,NULL) != ERTS_UTF8_OK) {
 
2608
        erts_free_aligned_binary_bytes(temp_alloc);
 
2609
        BIF_ERROR(BIF_P,BADARG);
 
2610
    }
 
2611
    ret = do_utf8_to_list_normalize(BIF_P, num_chars, bytes, size);
 
2612
    erts_free_aligned_binary_bytes(temp_alloc);
 
2613
    BIF_RET(ret);
 
2614
}  
 
2615
 
 
2616
BIF_RETTYPE file_native_name_encoding_0(BIF_ALIST_0)
 
2617
{
 
2618
    switch (erts_get_native_filename_encoding()) {
 
2619
    case ERL_FILENAME_LATIN1:
 
2620
        BIF_RET(am_latin1);
 
2621
    case ERL_FILENAME_UTF8_MAC:
 
2622
    case ERL_FILENAME_UTF8:
 
2623
        BIF_RET(am_utf8);
 
2624
    case ERL_FILENAME_WIN_WCHAR:
 
2625
        if (erts_get_user_requested_filename_encoding() ==  ERL_FILENAME_LATIN1) {
 
2626
            BIF_RET(am_latin1);
 
2627
        } else {
 
2628
            BIF_RET(am_utf8);
 
2629
        }
 
2630
    default:
 
2631
        BIF_RET(am_undefined);
 
2632
    }
 
2633
}