Renommage BIG_ENDIAN -> ARCH_BIG_ENDIAN, etc.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@913 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
6fda5ca60c
commit
7774748a20
|
@ -37,7 +37,7 @@ struct extern_obj {
|
||||||
static struct extern_obj * extern_table;
|
static struct extern_obj * extern_table;
|
||||||
static unsigned long extern_table_size;
|
static unsigned long extern_table_size;
|
||||||
|
|
||||||
#ifdef SIXTYFOUR
|
#ifdef ARCH_SIXTYFOUR
|
||||||
#define Hash(v) (((unsigned long) ((v) >> 3)) % extern_table_size)
|
#define Hash(v) (((unsigned long) ((v) >> 3)) % extern_table_size)
|
||||||
#else
|
#else
|
||||||
#define Hash(v) (((unsigned long) ((v) >> 2)) % extern_table_size)
|
#define Hash(v) (((unsigned long) ((v) >> 2)) % extern_table_size)
|
||||||
|
@ -163,7 +163,7 @@ static void writecode32(code, val)
|
||||||
extern_ptr += 5;
|
extern_ptr += 5;
|
||||||
}
|
}
|
||||||
|
|
||||||
#ifdef SIXTYFOUR
|
#ifdef ARCH_SIXTYFOUR
|
||||||
static void writecode64(code, val)
|
static void writecode64(code, val)
|
||||||
int code;
|
int code;
|
||||||
long val;
|
long val;
|
||||||
|
@ -199,7 +199,7 @@ static void extern_rec(v)
|
||||||
writecode8(CODE_INT8, n);
|
writecode8(CODE_INT8, n);
|
||||||
} else if (n >= -(1 << 15) && n < (1 << 15)) {
|
} else if (n >= -(1 << 15) && n < (1 << 15)) {
|
||||||
writecode16(CODE_INT16, n);
|
writecode16(CODE_INT16, n);
|
||||||
#ifdef SIXTYFOUR
|
#ifdef ARCH_SIXTYFOUR
|
||||||
} else if (n < -(1L << 31) || n >= (1L << 31)) {
|
} else if (n < -(1L << 31) || n >= (1L << 31)) {
|
||||||
writecode64(CODE_INT64, n);
|
writecode64(CODE_INT64, n);
|
||||||
#endif
|
#endif
|
||||||
|
@ -334,7 +334,7 @@ static long extern_value(v)
|
||||||
/* Free the table of shared objects */
|
/* Free the table of shared objects */
|
||||||
stat_free((char *) extern_table);
|
stat_free((char *) extern_table);
|
||||||
/* Write the sizes */
|
/* Write the sizes */
|
||||||
#ifdef SIXTYFOUR
|
#ifdef ARCH_SIXTYFOUR
|
||||||
if (size_32 >= (1L << 32) || size_64 >= (1L << 32)) {
|
if (size_32 >= (1L << 32) || size_64 >= (1L << 32)) {
|
||||||
/* The object is so big its size cannot be written in the header.
|
/* The object is so big its size cannot be written in the header.
|
||||||
Besides, some of the block sizes or string lengths or shared offsets
|
Besides, some of the block sizes or string lengths or shared offsets
|
||||||
|
|
|
@ -22,7 +22,7 @@
|
||||||
|
|
||||||
/* This code is needed only if the processor is big endian */
|
/* This code is needed only if the processor is big endian */
|
||||||
|
|
||||||
#ifdef BIG_ENDIAN
|
#ifdef ARCH_BIG_ENDIAN
|
||||||
|
|
||||||
void fixup_endianness(code, len)
|
void fixup_endianness(code, len)
|
||||||
code_t code;
|
code_t code;
|
||||||
|
|
|
@ -21,7 +21,7 @@
|
||||||
#include "misc.h"
|
#include "misc.h"
|
||||||
#include "stacks.h"
|
#include "stacks.h"
|
||||||
|
|
||||||
#ifdef ALIGN_DOUBLE
|
#ifdef ARCH_ALIGN_DOUBLE
|
||||||
|
|
||||||
double Double_val(val)
|
double Double_val(val)
|
||||||
value val;
|
value val;
|
||||||
|
|
|
@ -71,7 +71,7 @@ static void hash_aux(obj)
|
||||||
/* For doubles, we inspect their binary representation, LSB first.
|
/* For doubles, we inspect their binary representation, LSB first.
|
||||||
The results are consistent among all platforms with IEEE floats. */
|
The results are consistent among all platforms with IEEE floats. */
|
||||||
hash_univ_count--;
|
hash_univ_count--;
|
||||||
#ifdef BIG_ENDIAN
|
#ifdef ARCH_BIG_ENDIAN
|
||||||
for (p = &Byte_u(obj, sizeof(double) - 1), i = sizeof(double);
|
for (p = &Byte_u(obj, sizeof(double) - 1), i = sizeof(double);
|
||||||
i > 0;
|
i > 0;
|
||||||
p--, i--)
|
p--, i--)
|
||||||
|
@ -85,7 +85,7 @@ static void hash_aux(obj)
|
||||||
case Double_array_tag:
|
case Double_array_tag:
|
||||||
hash_univ_count--;
|
hash_univ_count--;
|
||||||
for (j = 0; j < Bosize_val(obj); j += sizeof(double)) {
|
for (j = 0; j < Bosize_val(obj); j += sizeof(double)) {
|
||||||
#ifdef BIG_ENDIAN
|
#ifdef ARCH_BIG_ENDIAN
|
||||||
for (p = &Byte_u(obj, j + sizeof(double) - 1), i = sizeof(double);
|
for (p = &Byte_u(obj, j + sizeof(double) - 1), i = sizeof(double);
|
||||||
i > 0;
|
i > 0;
|
||||||
p--, i--)
|
p--, i--)
|
||||||
|
|
|
@ -53,7 +53,7 @@ static value intern_block;
|
||||||
(Sign_extend(intern_src[-4]) << 24) + (intern_src[-3] << 16) + \
|
(Sign_extend(intern_src[-4]) << 24) + (intern_src[-3] << 16) + \
|
||||||
(intern_src[-2] << 8) + intern_src[-1])
|
(intern_src[-2] << 8) + intern_src[-1])
|
||||||
|
|
||||||
#ifdef SIXTYFOUR
|
#ifdef ARCH_SIXTYFOUR
|
||||||
static long read64s()
|
static long read64s()
|
||||||
{
|
{
|
||||||
long res;
|
long res;
|
||||||
|
@ -136,7 +136,7 @@ static void intern_rec(dest)
|
||||||
v = Val_long(read32s());
|
v = Val_long(read32s());
|
||||||
break;
|
break;
|
||||||
case CODE_INT64:
|
case CODE_INT64:
|
||||||
#ifdef SIXTYFOUR
|
#ifdef ARCH_SIXTYFOUR
|
||||||
v = Val_long(read64s());
|
v = Val_long(read64s());
|
||||||
break;
|
break;
|
||||||
#else
|
#else
|
||||||
|
@ -255,7 +255,7 @@ value input_value(chan) /* ML */
|
||||||
}
|
}
|
||||||
intern_src = intern_input;
|
intern_src = intern_input;
|
||||||
/* Allocate result */
|
/* Allocate result */
|
||||||
#ifdef SIXTYFOUR
|
#ifdef ARCH_SIXTYFOUR
|
||||||
whsize = size_64;
|
whsize = size_64;
|
||||||
#else
|
#else
|
||||||
whsize = size_32;
|
whsize = size_32;
|
||||||
|
@ -286,7 +286,7 @@ value input_value_from_string(str, ofs) /* ML */
|
||||||
size_32 = read32u();
|
size_32 = read32u();
|
||||||
size_64 = read32u();
|
size_64 = read32u();
|
||||||
/* Allocate result */
|
/* Allocate result */
|
||||||
#ifdef SIXTYFOUR
|
#ifdef ARCH_SIXTYFOUR
|
||||||
whsize = size_64;
|
whsize = size_64;
|
||||||
#else
|
#else
|
||||||
whsize = size_32;
|
whsize = size_32;
|
||||||
|
|
|
@ -46,7 +46,7 @@
|
||||||
#define CODE_DOUBLE_ARRAY32_BIG 0xF
|
#define CODE_DOUBLE_ARRAY32_BIG 0xF
|
||||||
#define CODE_DOUBLE_ARRAY32_LITTLE 0x7
|
#define CODE_DOUBLE_ARRAY32_LITTLE 0x7
|
||||||
|
|
||||||
#ifdef BIG_ENDIAN
|
#ifdef ARCH_BIG_ENDIAN
|
||||||
#define CODE_DOUBLE_NATIVE CODE_DOUBLE_BIG
|
#define CODE_DOUBLE_NATIVE CODE_DOUBLE_BIG
|
||||||
#define CODE_DOUBLE_ARRAY8_NATIVE CODE_DOUBLE_ARRAY8_BIG
|
#define CODE_DOUBLE_ARRAY8_NATIVE CODE_DOUBLE_ARRAY8_BIG
|
||||||
#define CODE_DOUBLE_ARRAY32_NATIVE CODE_DOUBLE_ARRAY32_BIG
|
#define CODE_DOUBLE_ARRAY32_NATIVE CODE_DOUBLE_ARRAY32_BIG
|
||||||
|
|
|
@ -117,7 +117,9 @@ static int do_write(fd, p, n)
|
||||||
retcode = ui_write(fd, p, n);
|
retcode = ui_write(fd, p, n);
|
||||||
#else
|
#else
|
||||||
again:
|
again:
|
||||||
|
enter_blocking_section();
|
||||||
retcode = write(fd, p, n);
|
retcode = write(fd, p, n);
|
||||||
|
leave_blocking_section();
|
||||||
if (retcode == -1) {
|
if (retcode == -1) {
|
||||||
if (errno == EINTR) goto again;
|
if (errno == EINTR) goto again;
|
||||||
if (errno == EAGAIN || errno == EWOULDBLOCK) {
|
if (errno == EAGAIN || errno == EWOULDBLOCK) {
|
||||||
|
@ -342,7 +344,7 @@ value input_int(channel) /* ML */
|
||||||
{
|
{
|
||||||
long i;
|
long i;
|
||||||
i = getword(channel);
|
i = getword(channel);
|
||||||
#ifdef SIXTYFOUR
|
#ifdef ARCH_SIXTYFOUR
|
||||||
i = (i << 32) >> 32; /* Force sign extension */
|
i = (i << 32) >> 32; /* Force sign extension */
|
||||||
#endif
|
#endif
|
||||||
return Val_long(i);
|
return Val_long(i);
|
||||||
|
|
|
@ -38,7 +38,7 @@ struct lexing_table {
|
||||||
value lex_check;
|
value lex_check;
|
||||||
};
|
};
|
||||||
|
|
||||||
#ifdef BIG_ENDIAN
|
#ifdef ARCH_BIG_ENDIAN
|
||||||
#define Short(tbl,n) \
|
#define Short(tbl,n) \
|
||||||
(*((unsigned char *)((tbl) + (n) * sizeof(short))) + \
|
(*((unsigned char *)((tbl) + (n) * sizeof(short))) + \
|
||||||
(*((schar *)((tbl) + (n) * sizeof(short) + 1)) << 8))
|
(*((schar *)((tbl) + (n) * sizeof(short) + 1)) << 8))
|
||||||
|
|
|
@ -227,7 +227,7 @@ int main(argc, argv)
|
||||||
if (read(fd, (char *) start_code, code_size) != code_size)
|
if (read(fd, (char *) start_code, code_size) != code_size)
|
||||||
fatal_error("Fatal error: truncated bytecode file.\n");
|
fatal_error("Fatal error: truncated bytecode file.\n");
|
||||||
|
|
||||||
#ifdef BIG_ENDIAN
|
#ifdef ARCH_BIG_ENDIAN
|
||||||
fixup_endianness(start_code, code_size);
|
fixup_endianness(start_code, code_size);
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
|
|
|
@ -24,7 +24,7 @@
|
||||||
#ifdef __STDC__
|
#ifdef __STDC__
|
||||||
#include <limits.h>
|
#include <limits.h>
|
||||||
#else
|
#else
|
||||||
#ifdef SIXTYFOUR
|
#ifdef ARCH_SIXTYFOUR
|
||||||
#define LONG_MAX 0x7FFFFFFFFFFFFFFF
|
#define LONG_MAX 0x7FFFFFFFFFFFFFFF
|
||||||
#else
|
#else
|
||||||
#define LONG_MAX 0x7FFFFFFF
|
#define LONG_MAX 0x7FFFFFFF
|
||||||
|
|
|
@ -83,7 +83,7 @@ value md5_chan(chan, len) /* ML */
|
||||||
* will fill a supplied 16-byte array with the digest.
|
* will fill a supplied 16-byte array with the digest.
|
||||||
*/
|
*/
|
||||||
|
|
||||||
#ifndef BIG_ENDIAN
|
#ifndef ARCH_BIG_ENDIAN
|
||||||
#define byteReverse(buf, len) /* Nothing */
|
#define byteReverse(buf, len) /* Nothing */
|
||||||
#else
|
#else
|
||||||
void byteReverse(buf, longs)
|
void byteReverse(buf, longs)
|
||||||
|
|
|
@ -35,7 +35,7 @@ value reify_bytecode(prog, len) /* ML */
|
||||||
value prog, len;
|
value prog, len;
|
||||||
{
|
{
|
||||||
value clos;
|
value clos;
|
||||||
#ifdef BIG_ENDIAN
|
#ifdef ARCH_BIG_ENDIAN
|
||||||
fixup_endianness((code_t) prog, (asize_t) Long_val(len));
|
fixup_endianness((code_t) prog, (asize_t) Long_val(len));
|
||||||
#endif
|
#endif
|
||||||
#ifdef THREADED_CODE
|
#ifdef THREADED_CODE
|
||||||
|
|
|
@ -104,7 +104,7 @@ bits 63 10 9 8 7 0
|
||||||
#define Bp_hp(hp) ((char *) Val_hp (hp))
|
#define Bp_hp(hp) ((char *) Val_hp (hp))
|
||||||
|
|
||||||
#define Num_tags (1 << 8)
|
#define Num_tags (1 << 8)
|
||||||
#ifdef SIXTYFOUR
|
#ifdef ARCH_SIXTYFOUR
|
||||||
#define Max_wosize ((1L << 54) - 1)
|
#define Max_wosize ((1L << 54) - 1)
|
||||||
#else
|
#else
|
||||||
#define Max_wosize ((1 << 22) - 1)
|
#define Max_wosize ((1 << 22) - 1)
|
||||||
|
@ -132,7 +132,7 @@ bits 63 10 9 8 7 0
|
||||||
#define Bhsize_hp(hp) (Bsize_wsize (Whsize_hp (hp)))
|
#define Bhsize_hp(hp) (Bsize_wsize (Whsize_hp (hp)))
|
||||||
#define Bhsize_hd(hd) (Bsize_wsize (Whsize_hd (hd)))
|
#define Bhsize_hd(hd) (Bsize_wsize (Whsize_hd (hd)))
|
||||||
|
|
||||||
#ifdef BIG_ENDIAN
|
#ifdef ARCH_BIG_ENDIAN
|
||||||
#define Tag_val(val) (((unsigned char *) (val)) [-1])
|
#define Tag_val(val) (((unsigned char *) (val)) [-1])
|
||||||
/* Also an l-value. */
|
/* Also an l-value. */
|
||||||
#define Tag_hp(hp) (((unsigned char *) (hp)) [sizeof(value)-1])
|
#define Tag_hp(hp) (((unsigned char *) (hp)) [sizeof(value)-1])
|
||||||
|
@ -195,7 +195,7 @@ value callback3 P((value closure, value arg1, value arg2, value arg3));
|
||||||
/* Floating-point numbers. */
|
/* Floating-point numbers. */
|
||||||
#define Double_tag 253
|
#define Double_tag 253
|
||||||
#define Double_wosize ((sizeof(double) / sizeof(value)))
|
#define Double_wosize ((sizeof(double) / sizeof(value)))
|
||||||
#ifndef ALIGN_DOUBLE
|
#ifndef ARCH_ALIGN_DOUBLE
|
||||||
#define Double_val(v) (* (double *)(v))
|
#define Double_val(v) (* (double *)(v))
|
||||||
#define Store_double_val(v,d) (* (double *)(v) = (d))
|
#define Store_double_val(v,d) (* (double *)(v) = (d))
|
||||||
#else
|
#else
|
||||||
|
|
|
@ -57,7 +57,7 @@ struct parser_env { /* Mirrors parser_env in ../stdlib/parsing.ml */
|
||||||
value errflag;
|
value errflag;
|
||||||
};
|
};
|
||||||
|
|
||||||
#ifdef BIG_ENDIAN
|
#ifdef ARCH_BIG_ENDIAN
|
||||||
#define Short(tbl,n) \
|
#define Short(tbl,n) \
|
||||||
(*((unsigned char *)((tbl) + (n) * sizeof(short))) + \
|
(*((unsigned char *)((tbl) + (n) * sizeof(short))) + \
|
||||||
(*((schar *)((tbl) + (n) * sizeof(short) + 1)) << 8))
|
(*((schar *)((tbl) + (n) * sizeof(short) + 1)) << 8))
|
||||||
|
|
|
@ -56,7 +56,7 @@
|
||||||
_p[4] = _a; \
|
_p[4] = _a; \
|
||||||
}
|
}
|
||||||
|
|
||||||
#ifdef SIXTYFOUR
|
#ifdef ARCH_SIXTYFOUR
|
||||||
#define Reverse_word Reverse_int64
|
#define Reverse_word Reverse_int64
|
||||||
#else
|
#else
|
||||||
#define Reverse_word Reverse_int32
|
#define Reverse_word Reverse_int32
|
||||||
|
|
|
@ -13,7 +13,7 @@
|
||||||
|
|
||||||
/* Machine configuration, Intel x86 processors, Windows NT */
|
/* Machine configuration, Intel x86 processors, Windows NT */
|
||||||
|
|
||||||
#undef SIXTYFOUR
|
#undef ARCH_SIXTYFOUR
|
||||||
#undef BIG_ENDIAN
|
#undef ARCH_BIG_ENDIAN
|
||||||
#undef ALIGN_DOUBLE
|
#undef ARCH_ALIGN_DOUBLE
|
||||||
|
|
||||||
|
|
|
@ -13,23 +13,24 @@
|
||||||
|
|
||||||
/* Processor dependencies */
|
/* Processor dependencies */
|
||||||
|
|
||||||
#define SIXTYFOUR
|
#define ARCH_SIXTYFOUR
|
||||||
|
|
||||||
/* Define SIXTYFOUR if the processor has a natural word size of 64 bits.
|
/* Define ARCH_SIXTYFOUR if the processor has a natural word size of 64 bits.
|
||||||
That is, both sizeof(long) = 8 and sizeof(char *) = 8.
|
That is, both sizeof(long) = 8 and sizeof(char *) = 8.
|
||||||
Otherwise, leave SIXTYFOUR undefined. This assumes
|
Otherwise, leave ARCH_SIXTYFOUR undefined. This assumes
|
||||||
sizeof(long) = sizeof(char *) = 4. */
|
sizeof(long) = sizeof(char *) = 4. */
|
||||||
|
|
||||||
#define BIG_ENDIAN
|
#define ARCH_BIG_ENDIAN
|
||||||
|
|
||||||
/* Define BIG_ENDIAN if the processor is big endian (the most significant
|
/* Define ARCH_BIG_ENDIAN if the processor is big endian (the most
|
||||||
byte of an integer stored in memory comes first). Leave BIG_ENDIAN undefined
|
significant byte of an integer stored in memory comes first).
|
||||||
if the processor is little-endian (the least significant byte comes first).
|
Leave ARCH_BIG_ENDIAN undefined if the processor is little-endian
|
||||||
|
(the least significant byte comes first).
|
||||||
*/
|
*/
|
||||||
|
|
||||||
#define ALIGN_DOUBLE
|
#define ARCH_ALIGN_DOUBLE
|
||||||
|
|
||||||
/* Define ALIGN_DOUBLE if the processor requires doubles to be
|
/* Define ARCH_ALIGN_DOUBLE if the processor requires doubles to be
|
||||||
doubleword-aligned. Leave ALIGN_DOUBLE undefined if the processor supports
|
doubleword-aligned. Leave ARCH_ALIGN_DOUBLE undefined if the processor
|
||||||
word-aligned doubles. */
|
supports word-aligned doubles. */
|
||||||
|
|
||||||
|
|
|
@ -99,9 +99,9 @@ echo "Checking the sizes of integers and pointers..."
|
||||||
set `sh runtest sizes.c`
|
set `sh runtest sizes.c`
|
||||||
case "$1,$2,$3" in
|
case "$1,$2,$3" in
|
||||||
4,4,4) echo "OK, this is a regular 32 bit architecture."
|
4,4,4) echo "OK, this is a regular 32 bit architecture."
|
||||||
echo "#undef SIXTYFOUR" >> m.h;;
|
echo "#undef ARCH_SIXTYFOUR" >> m.h;;
|
||||||
4,8,8) echo "Wow! A 64 bit architecture!"
|
4,8,8) echo "Wow! A 64 bit architecture!"
|
||||||
echo "#define SIXTYFOUR" >> m.h;;
|
echo "#define ARCH_SIXTYFOUR" >> m.h;;
|
||||||
8,*,*) echo "Wow! A 64 bit architecture!"
|
8,*,*) echo "Wow! A 64 bit architecture!"
|
||||||
echo "Unfortunately, Objective Caml does not handle the case"
|
echo "Unfortunately, Objective Caml does not handle the case"
|
||||||
echo "sizeof(int) = 8."
|
echo "sizeof(int) = 8."
|
||||||
|
@ -125,15 +125,15 @@ esac
|
||||||
sh runtest endian.c
|
sh runtest endian.c
|
||||||
case $? in
|
case $? in
|
||||||
0) echo "This is a big-endian architecture."
|
0) echo "This is a big-endian architecture."
|
||||||
echo "#define BIG_ENDIAN" >> m.h;;
|
echo "#define ARCH_BIG_ENDIAN" >> m.h;;
|
||||||
1) echo "This is a little-endian architecture."
|
1) echo "This is a little-endian architecture."
|
||||||
echo "#undef BIG_ENDIAN" >> m.h;;
|
echo "#undef ARCH_BIG_ENDIAN" >> m.h;;
|
||||||
2) echo "This architecture seems to be neither big endian nor little endian."
|
2) echo "This architecture seems to be neither big endian nor little endian."
|
||||||
echo "Objective Caml won't run on this architecture."
|
echo "Objective Caml won't run on this architecture."
|
||||||
exit 2;;
|
exit 2;;
|
||||||
*) echo "Something went wrong during endianness determination."
|
*) echo "Something went wrong during endianness determination."
|
||||||
echo "You'll have to figure out endianness yourself"
|
echo "You'll have to figure out endianness yourself"
|
||||||
echo "(option BIG_ENDIAN in m.h).";;
|
echo "(option ARCH_BIG_ENDIAN in m.h).";;
|
||||||
esac
|
esac
|
||||||
|
|
||||||
# Determine alignment constraints
|
# Determine alignment constraints
|
||||||
|
@ -141,14 +141,14 @@ esac
|
||||||
sh runtest dblalign.c
|
sh runtest dblalign.c
|
||||||
case $? in
|
case $? in
|
||||||
0) echo "Doubles can be word-aligned."
|
0) echo "Doubles can be word-aligned."
|
||||||
echo "#undef ALIGN_DOUBLE" >> m.h;;
|
echo "#undef ARCH_ALIGN_DOUBLE" >> m.h;;
|
||||||
1) echo "Doubles must be doubleword-aligned."
|
1) echo "Doubles must be doubleword-aligned."
|
||||||
echo "#define ALIGN_DOUBLE" >> m.h;;
|
echo "#define ARCH_ALIGN_DOUBLE" >> m.h;;
|
||||||
*) echo "Something went wrong during alignment determination for doubles."
|
*) echo "Something went wrong during alignment determination for doubles."
|
||||||
echo "I'm going to assume this architecture has alignment constraints over doubles."
|
echo "I'm going to assume this architecture has alignment constraints over doubles."
|
||||||
echo "That's a safe bet: Objective Caml will work even if"
|
echo "That's a safe bet: Objective Caml will work even if"
|
||||||
echo "this architecture has actually no alignment constraints."
|
echo "this architecture has actually no alignment constraints."
|
||||||
echo "#define ALIGN_DOUBLE" >> m.h;;
|
echo "#define ARCH_ALIGN_DOUBLE" >> m.h;;
|
||||||
esac
|
esac
|
||||||
|
|
||||||
# Configure the bytecode compiler
|
# Configure the bytecode compiler
|
||||||
|
|
Loading…
Reference in New Issue