1 /*
2  * %CopyrightBegin%
3  *
4  * Copyright Ericsson AB 2000-2016. All Rights Reserved.
5  *
6  * Licensed under the Apache License, Version 2.0 (the "License");
7  * you may not use this file except in compliance with the License.
8  * You may obtain a copy of the License at
9  *
10  *     http://www.apache.org/licenses/LICENSE-2.0
11  *
12  * Unless required by applicable law or agreed to in writing, software
13  * distributed under the License is distributed on an "AS IS" BASIS,
14  * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15  * See the License for the specific language governing permissions and
16  * limitations under the License.
17  *
18  * %CopyrightEnd%
19  */
20 package com.ericsson.otp.erlang;
21 
22 import java.io.ByteArrayInputStream;
23 import java.io.IOException;
24 import java.math.BigDecimal;
25 import java.util.Arrays;
26 
27 /**
28  * Provides a stream for decoding Erlang terms from external format.
29  *
30  * <p>
31  * Note that this class is not synchronized, if you need synchronization you
32  * must provide it yourself.
33  */
34 public class OtpInputStream extends ByteArrayInputStream {
35 
36     public static int DECODE_INT_LISTS_AS_STRINGS = 1;
37 
38     private final int flags;
39 
40     /**
41      * @param buf
42      */
OtpInputStream(final byte[] buf)43     public OtpInputStream(final byte[] buf) {
44         this(buf, 0);
45     }
46 
47     /**
48      * Create a stream from a buffer containing encoded Erlang terms.
49      *
50      * @param flags
51      */
OtpInputStream(final byte[] buf, final int flags)52     public OtpInputStream(final byte[] buf, final int flags) {
53         super(buf);
54         this.flags = flags;
55     }
56 
57     /**
58      * Create a stream from a buffer containing encoded Erlang terms at the
59      * given offset and length.
60      *
61      * @param flags
62      */
OtpInputStream(final byte[] buf, final int offset, final int length, final int flags)63     public OtpInputStream(final byte[] buf, final int offset, final int length,
64             final int flags) {
65         super(buf, offset, length);
66         this.flags = flags;
67     }
68 
69     /**
70      * Get the current position in the stream.
71      *
72      * @return the current position in the stream.
73      */
getPos()74     public int getPos() {
75         return super.pos;
76     }
77 
78     /**
79      * Set the current position in the stream.
80      *
81      * @param pos
82      *            the position to move to in the stream. If pos indicates a
83      *            position beyond the end of the stream, the position is move to
84      *            the end of the stream instead. If pos is negative, the
85      *            position is moved to the beginning of the stream instead.
86      *
87      * @return the previous position in the stream.
88      */
setPos(final int pos)89     public int setPos(final int pos) {
90         final int oldpos = super.pos;
91 
92         int apos = pos;
93         if (pos > super.count) {
94             apos = super.count;
95         } else if (pos < 0) {
96             apos = 0;
97         }
98 
99         super.pos = apos;
100 
101         return oldpos;
102     }
103 
104     /**
105      * Read an array of bytes from the stream. The method reads at most
106      * buf.length bytes from the input stream.
107      *
108      * @return the number of bytes read.
109      *
110      * @exception OtpErlangDecodeException
111      *                if the next byte cannot be read.
112      */
readN(final byte[] abuf)113     public int readN(final byte[] abuf) throws OtpErlangDecodeException {
114         return this.readN(abuf, 0, abuf.length);
115     }
116 
117     /**
118      * Read an array of bytes from the stream. The method reads at most len
119      * bytes from the input stream into offset off of the buffer.
120      *
121      * @return the number of bytes read.
122      *
123      * @exception OtpErlangDecodeException
124      *                if the next byte cannot be read.
125      */
readN(final byte[] abuf, final int off, final int len)126     public int readN(final byte[] abuf, final int off, final int len)
127             throws OtpErlangDecodeException {
128         if (len == 0 && available() == 0) {
129             return 0;
130         }
131         final int i = super.read(abuf, off, len);
132         if (i < 0) {
133             throw new OtpErlangDecodeException("Cannot read from input stream");
134         }
135         return i;
136     }
137 
138     /**
139      * Alias for peek1()
140      */
peek()141     public int peek() throws OtpErlangDecodeException {
142         return peek1();
143     }
144 
145     /**
146      * Look ahead one position in the stream without consuming the byte found
147      * there.
148      *
149      * @return the next byte in the stream, as an integer.
150      *
151      * @exception OtpErlangDecodeException
152      *                if the next byte cannot be read.
153      */
peek1()154     public int peek1() throws OtpErlangDecodeException {
155         int i;
156         try {
157             i = super.buf[super.pos];
158             if (i < 0) {
159                 i += 256;
160             }
161 
162             return i;
163         } catch (final Exception e) {
164             throw new OtpErlangDecodeException("Cannot read from input stream");
165         }
166     }
167 
peek1skip_version()168     public int peek1skip_version() throws OtpErlangDecodeException {
169         int i = peek1();
170         if (i == OtpExternal.versionTag) {
171             read1();
172             i = peek1();
173         }
174         return i;
175     }
176 
177     /**
178      * Read a one byte integer from the stream.
179      *
180      * @return the byte read, as an integer.
181      *
182      * @exception OtpErlangDecodeException
183      *                if the next byte cannot be read.
184      */
read1()185     public int read1() throws OtpErlangDecodeException {
186         int i;
187         i = super.read();
188 
189         if (i < 0) {
190             throw new OtpErlangDecodeException("Cannot read from input stream");
191         }
192 
193         return i;
194     }
195 
read1skip_version()196     public int read1skip_version() throws OtpErlangDecodeException {
197         int tag = read1();
198         if (tag == OtpExternal.versionTag) {
199             tag = read1();
200         }
201         return tag;
202     }
203 
204     /**
205      * Read a two byte big endian integer from the stream.
206      *
207      * @return the bytes read, converted from big endian to an integer.
208      *
209      * @exception OtpErlangDecodeException
210      *                if the next byte cannot be read.
211      */
read2BE()212     public int read2BE() throws OtpErlangDecodeException {
213         final byte[] b = new byte[2];
214         try {
215             super.read(b);
216         } catch (final IOException e) {
217             throw new OtpErlangDecodeException("Cannot read from input stream");
218         }
219         return (b[0] << 8 & 0xff00) + (b[1] & 0xff);
220     }
221 
222     /**
223      * Read a four byte big endian integer from the stream.
224      *
225      * @return the bytes read, converted from big endian to an integer.
226      *
227      * @exception OtpErlangDecodeException
228      *                if the next byte cannot be read.
229      */
read4BE()230     public int read4BE() throws OtpErlangDecodeException {
231         final byte[] b = new byte[4];
232         try {
233             super.read(b);
234         } catch (final IOException e) {
235             throw new OtpErlangDecodeException("Cannot read from input stream");
236         }
237         return (b[0] << 24 & 0xff000000) + (b[1] << 16 & 0xff0000)
238                 + (b[2] << 8 & 0xff00) + (b[3] & 0xff);
239     }
240 
241     /**
242      * Read a two byte little endian integer from the stream.
243      *
244      * @return the bytes read, converted from little endian to an integer.
245      *
246      * @exception OtpErlangDecodeException
247      *                if the next byte cannot be read.
248      */
read2LE()249     public int read2LE() throws OtpErlangDecodeException {
250         final byte[] b = new byte[2];
251         try {
252             super.read(b);
253         } catch (final IOException e) {
254             throw new OtpErlangDecodeException("Cannot read from input stream");
255         }
256         return (b[1] << 8 & 0xff00) + (b[0] & 0xff);
257     }
258 
259     /**
260      * Read a four byte little endian integer from the stream.
261      *
262      * @return the bytes read, converted from little endian to an integer.
263      *
264      * @exception OtpErlangDecodeException
265      *                if the next byte cannot be read.
266      */
read4LE()267     public int read4LE() throws OtpErlangDecodeException {
268         final byte[] b = new byte[4];
269         try {
270             super.read(b);
271         } catch (final IOException e) {
272             throw new OtpErlangDecodeException("Cannot read from input stream");
273         }
274         return (b[3] << 24 & 0xff000000) + (b[2] << 16 & 0xff0000)
275                 + (b[1] << 8 & 0xff00) + (b[0] & 0xff);
276     }
277 
278     /**
279      * Read a little endian integer from the stream.
280      *
281      * @param n
282      *            the number of bytes to read
283      *
284      * @return the bytes read, converted from little endian to an integer.
285      *
286      * @exception OtpErlangDecodeException
287      *                if the next byte cannot be read.
288      */
readLE(final int n)289     public long readLE(final int n) throws OtpErlangDecodeException {
290         final byte[] b = new byte[n];
291         try {
292             super.read(b);
293         } catch (final IOException e) {
294             throw new OtpErlangDecodeException("Cannot read from input stream");
295         }
296         long v = 0;
297         int i = n;
298         while (i-- > 0) {
299             v = v << 8 | (long) b[i] & 0xff;
300         }
301         return v;
302     }
303 
304     /**
305      * Read a bigendian integer from the stream.
306      *
307      * @param n
308      *            the number of bytes to read
309      *
310      * @return the bytes read, converted from big endian to an integer.
311      *
312      * @exception OtpErlangDecodeException
313      *                if the next byte cannot be read.
314      */
readBE(final int n)315     public long readBE(final int n) throws OtpErlangDecodeException {
316         final byte[] b = new byte[n];
317         try {
318             super.read(b);
319         } catch (final IOException e) {
320             throw new OtpErlangDecodeException("Cannot read from input stream");
321         }
322         long v = 0;
323         for (int i = 0; i < n; i++) {
324             v = v << 8 | (long) b[i] & 0xff;
325         }
326         return v;
327     }
328 
329     /**
330      * Read an Erlang atom from the stream and interpret the value as a boolean.
331      *
332      * @return true if the atom at the current position in the stream contains
333      *         the value 'true' (ignoring case), false otherwise.
334      *
335      * @exception OtpErlangDecodeException
336      *                if the next term in the stream is not an atom.
337      */
read_boolean()338     public boolean read_boolean() throws OtpErlangDecodeException {
339         return Boolean.valueOf(read_atom()).booleanValue();
340     }
341 
342     /**
343      * Read an Erlang atom from the stream.
344      *
345      * @return a String containing the value of the atom.
346      *
347      * @exception OtpErlangDecodeException
348      *                if the next term in the stream is not an atom.
349      */
350     @SuppressWarnings("fallthrough")
read_atom()351     public String read_atom() throws OtpErlangDecodeException {
352         int tag;
353         int len = -1;
354         byte[] strbuf;
355         String atom;
356 
357         tag = read1skip_version();
358 
359         switch (tag) {
360 
361         case OtpExternal.atomTag:
362             len = read2BE();
363             strbuf = new byte[len];
364             this.readN(strbuf);
365             try {
366                 atom = new String(strbuf, "ISO-8859-1");
367             } catch (final java.io.UnsupportedEncodingException e) {
368                 throw new OtpErlangDecodeException(
369                         "Failed to decode ISO-8859-1 atom");
370             }
371             if (atom.length() > OtpExternal.maxAtomLength) {
372                 /*
373                  * Throwing an exception would be better I think, but truncation
374                  * seems to be the way it has been done in other parts of OTP...
375                  */
376                 atom = atom.substring(0, OtpExternal.maxAtomLength);
377             }
378             break;
379 
380         case OtpExternal.smallAtomUtf8Tag:
381             len = read1();
382             // fall-through
383         case OtpExternal.atomUtf8Tag:
384             if (len < 0) {
385                 len = read2BE();
386             }
387             strbuf = new byte[len];
388             this.readN(strbuf);
389             try {
390                 atom = new String(strbuf, "UTF-8");
391             } catch (final java.io.UnsupportedEncodingException e) {
392                 throw new OtpErlangDecodeException(
393                         "Failed to decode UTF-8 atom");
394             }
395             if (atom.codePointCount(0, atom.length()) > OtpExternal.maxAtomLength) {
396                 /*
397                  * Throwing an exception would be better I think, but truncation
398                  * seems to be the way it has been done in other parts of OTP...
399                  */
400                 final int[] cps = OtpErlangString.stringToCodePoints(atom);
401                 atom = new String(cps, 0, OtpExternal.maxAtomLength);
402             }
403             break;
404 
405         default:
406             throw new OtpErlangDecodeException(
407                     "wrong tag encountered, expected " + OtpExternal.atomTag
408                             + ", or " + OtpExternal.atomUtf8Tag + ", got "
409                             + tag);
410         }
411 
412         return atom;
413     }
414 
415     /**
416      * Read an Erlang binary from the stream.
417      *
418      * @return a byte array containing the value of the binary.
419      *
420      * @exception OtpErlangDecodeException
421      *                if the next term in the stream is not a binary.
422      */
read_binary()423     public byte[] read_binary() throws OtpErlangDecodeException {
424         int tag;
425         int len;
426         byte[] bin;
427 
428         tag = read1skip_version();
429 
430         if (tag != OtpExternal.binTag) {
431             throw new OtpErlangDecodeException(
432                     "Wrong tag encountered, expected " + OtpExternal.binTag
433                             + ", got " + tag);
434         }
435 
436         len = read4BE();
437 
438         bin = new byte[len];
439         this.readN(bin);
440 
441         return bin;
442     }
443 
444     /**
445      * Read an Erlang bitstr from the stream.
446      *
447      * @param pad_bits
448      *            an int array whose first element will be set to the number of
449      *            pad bits in the last byte.
450      *
451      * @return a byte array containing the value of the bitstr.
452      *
453      * @exception OtpErlangDecodeException
454      *                if the next term in the stream is not a bitstr.
455      */
read_bitstr(final int pad_bits[])456     public byte[] read_bitstr(final int pad_bits[])
457             throws OtpErlangDecodeException {
458         int tag;
459         int len;
460         byte[] bin;
461 
462         tag = read1skip_version();
463 
464         if (tag != OtpExternal.bitBinTag) {
465             throw new OtpErlangDecodeException(
466                     "Wrong tag encountered, expected " + OtpExternal.bitBinTag
467                             + ", got " + tag);
468         }
469 
470         len = read4BE();
471         bin = new byte[len];
472         final int tail_bits = read1();
473         if (tail_bits < 0 || 7 < tail_bits) {
474             throw new OtpErlangDecodeException(
475                     "Wrong tail bit count in bitstr: " + tail_bits);
476         }
477         if (len == 0 && tail_bits != 0) {
478             throw new OtpErlangDecodeException(
479                     "Length 0 on bitstr with tail bit count: " + tail_bits);
480         }
481         this.readN(bin);
482 
483         pad_bits[0] = 8 - tail_bits;
484         return bin;
485     }
486 
487     /**
488      * Read an Erlang float from the stream.
489      *
490      * @return the float value.
491      *
492      * @exception OtpErlangDecodeException
493      *                if the next term in the stream is not a float.
494      */
read_float()495     public float read_float() throws OtpErlangDecodeException {
496         final double d = read_double();
497         return (float) d;
498     }
499 
500     /**
501      * Read an Erlang float from the stream.
502      *
503      * @return the float value, as a double.
504      *
505      * @exception OtpErlangDecodeException
506      *                if the next term in the stream is not a float.
507      */
read_double()508     public double read_double() throws OtpErlangDecodeException {
509         int tag;
510 
511         // parse the stream
512         tag = read1skip_version();
513 
514         switch (tag) {
515         case OtpExternal.newFloatTag: {
516             return Double.longBitsToDouble(readBE(8));
517         }
518         case OtpExternal.floatTag: {
519             BigDecimal val;
520             int epos;
521             int exp;
522             final byte[] strbuf = new byte[31];
523             String str;
524 
525             // get the string
526             this.readN(strbuf);
527             str = OtpErlangString.newString(strbuf);
528 
529             // find the exponent prefix 'e' in the string
530             epos = str.indexOf('e', 0);
531 
532             if (epos < 0) {
533                 throw new OtpErlangDecodeException("Invalid float format: '"
534                         + str + "'");
535             }
536 
537             // remove the sign from the exponent, if positive
538             String estr = str.substring(epos + 1).trim();
539 
540             if (estr.substring(0, 1).equals("+")) {
541                 estr = estr.substring(1);
542             }
543 
544             // now put the mantissa and exponent together
545             exp = Integer.valueOf(estr).intValue();
546             val = new BigDecimal(str.substring(0, epos)).movePointRight(exp);
547 
548             return val.doubleValue();
549         }
550         default:
551             throw new OtpErlangDecodeException(
552                     "Wrong tag encountered, expected "
553                             + OtpExternal.newFloatTag + ", got " + tag);
554         }
555     }
556 
557     /**
558      * Read one byte from the stream.
559      *
560      * @return the byte read.
561      *
562      * @exception OtpErlangDecodeException
563      *                if the next byte cannot be read.
564      */
read_byte()565     public byte read_byte() throws OtpErlangDecodeException {
566         final long l = this.read_long(false);
567         final byte i = (byte) l;
568 
569         if (l != i) {
570             throw new OtpErlangDecodeException("Value does not fit in byte: "
571                     + l);
572         }
573 
574         return i;
575     }
576 
577     /**
578      * Read a character from the stream.
579      *
580      * @return the character value.
581      *
582      * @exception OtpErlangDecodeException
583      *                if the next term in the stream is not an integer that can
584      *                be represented as a char.
585      */
read_char()586     public char read_char() throws OtpErlangDecodeException {
587         final long l = this.read_long(true);
588         final char i = (char) l;
589 
590         if (l != (i & 0xffffL)) {
591             throw new OtpErlangDecodeException("Value does not fit in char: "
592                     + l);
593         }
594 
595         return i;
596     }
597 
598     /**
599      * Read an unsigned integer from the stream.
600      *
601      * @return the integer value.
602      *
603      * @exception OtpErlangDecodeException
604      *                if the next term in the stream can not be represented as a
605      *                positive integer.
606      */
read_uint()607     public int read_uint() throws OtpErlangDecodeException {
608         final long l = this.read_long(true);
609         final int i = (int) l;
610 
611         if (l != (i & 0xFFFFffffL)) {
612             throw new OtpErlangDecodeException("Value does not fit in uint: "
613                     + l);
614         }
615 
616         return i;
617     }
618 
619     /**
620      * Read an integer from the stream.
621      *
622      * @return the integer value.
623      *
624      * @exception OtpErlangDecodeException
625      *                if the next term in the stream can not be represented as
626      *                an integer.
627      */
read_int()628     public int read_int() throws OtpErlangDecodeException {
629         final long l = this.read_long(false);
630         final int i = (int) l;
631 
632         if (l != i) {
633             throw new OtpErlangDecodeException("Value does not fit in int: "
634                     + l);
635         }
636 
637         return i;
638     }
639 
640     /**
641      * Read an unsigned short from the stream.
642      *
643      * @return the short value.
644      *
645      * @exception OtpErlangDecodeException
646      *                if the next term in the stream can not be represented as a
647      *                positive short.
648      */
read_ushort()649     public short read_ushort() throws OtpErlangDecodeException {
650         final long l = this.read_long(true);
651         final short i = (short) l;
652 
653         if (l != (i & 0xffffL)) {
654             throw new OtpErlangDecodeException("Value does not fit in ushort: "
655                     + l);
656         }
657 
658         return i;
659     }
660 
661     /**
662      * Read a short from the stream.
663      *
664      * @return the short value.
665      *
666      * @exception OtpErlangDecodeException
667      *                if the next term in the stream can not be represented as a
668      *                short.
669      */
read_short()670     public short read_short() throws OtpErlangDecodeException {
671         final long l = this.read_long(false);
672         final short i = (short) l;
673 
674         if (l != i) {
675             throw new OtpErlangDecodeException("Value does not fit in short: "
676                     + l);
677         }
678 
679         return i;
680     }
681 
682     /**
683      * Read an unsigned long from the stream.
684      *
685      * @return the long value.
686      *
687      * @exception OtpErlangDecodeException
688      *                if the next term in the stream can not be represented as a
689      *                positive long.
690      */
read_ulong()691     public long read_ulong() throws OtpErlangDecodeException {
692         return this.read_long(true);
693     }
694 
695     /**
696      * Read a long from the stream.
697      *
698      * @return the long value.
699      *
700      * @exception OtpErlangDecodeException
701      *                if the next term in the stream can not be represented as a
702      *                long.
703      */
read_long()704     public long read_long() throws OtpErlangDecodeException {
705         return this.read_long(false);
706     }
707 
read_long(final boolean unsigned)708     public long read_long(final boolean unsigned)
709             throws OtpErlangDecodeException {
710         final byte[] b = read_integer_byte_array();
711         return OtpInputStream.byte_array_to_long(b, unsigned);
712     }
713 
714     /**
715      * Read an integer from the stream.
716      *
717      * @return the value as a big endian 2's complement byte array.
718      *
719      * @exception OtpErlangDecodeException
720      *                if the next term in the stream is not an integer.
721      */
read_integer_byte_array()722     public byte[] read_integer_byte_array() throws OtpErlangDecodeException {
723         int tag;
724         byte[] nb;
725 
726         tag = read1skip_version();
727 
728         switch (tag) {
729         case OtpExternal.smallIntTag:
730             nb = new byte[2];
731             nb[0] = 0;
732             nb[1] = (byte) read1();
733             break;
734 
735         case OtpExternal.intTag:
736             nb = new byte[4];
737             if (this.readN(nb) != 4) { // Big endian
738                 throw new OtpErlangDecodeException(
739                         "Cannot read from intput stream");
740             }
741             break;
742 
743         case OtpExternal.smallBigTag:
744         case OtpExternal.largeBigTag:
745             int arity;
746             int sign;
747             if (tag == OtpExternal.smallBigTag) {
748                 arity = read1();
749                 sign = read1();
750             } else {
751                 arity = read4BE();
752                 sign = read1();
753                 if (arity + 1 < 0) {
754                     throw new OtpErlangDecodeException(
755                             "Value of largeBig does not fit in BigInteger, arity "
756                                     + arity + " sign " + sign);
757                 }
758             }
759             nb = new byte[arity + 1];
760             // Value is read as little endian. The big end is augumented
761             // with one zero byte to make the value 2's complement positive.
762             if (this.readN(nb, 0, arity) != arity) {
763                 throw new OtpErlangDecodeException(
764                         "Cannot read from intput stream");
765             }
766             // Reverse the array to make it big endian.
767             for (int i = 0, j = nb.length; i < j--; i++) {
768                 // Swap [i] with [j]
769                 final byte b = nb[i];
770                 nb[i] = nb[j];
771                 nb[j] = b;
772             }
773             if (sign != 0) {
774                 // 2's complement negate the big endian value in the array
775                 int c = 1; // Carry
776                 for (int j = nb.length; j-- > 0;) {
777                     c = (~nb[j] & 0xFF) + c;
778                     nb[j] = (byte) c;
779                     c >>= 8;
780                 }
781             }
782             break;
783 
784         default:
785             throw new OtpErlangDecodeException("Not valid integer tag: " + tag);
786         }
787 
788         return nb;
789     }
790 
byte_array_to_long(final byte[] b, final boolean unsigned)791     public static long byte_array_to_long(final byte[] b, final boolean unsigned)
792             throws OtpErlangDecodeException {
793         long v;
794         switch (b.length) {
795         case 0:
796             v = 0;
797             break;
798         case 2:
799             v = ((b[0] & 0xFF) << 8) + (b[1] & 0xFF);
800             v = (short) v; // Sign extend
801             if (v < 0 && unsigned) {
802                 throw new OtpErlangDecodeException("Value not unsigned: " + v);
803             }
804             break;
805         case 4:
806             v = ((b[0] & 0xFF) << 24) + ((b[1] & 0xFF) << 16)
807                     + ((b[2] & 0xFF) << 8) + (b[3] & 0xFF);
808             v = (int) v; // Sign extend
809             if (v < 0 && unsigned) {
810                 throw new OtpErlangDecodeException("Value not unsigned: " + v);
811             }
812             break;
813         default:
814             int i = 0;
815             final byte c = b[i];
816             // Skip non-essential leading bytes
817             if (unsigned) {
818                 if (c < 0) {
819                     throw new OtpErlangDecodeException("Value not unsigned: "
820                             + Arrays.toString(b));
821                 }
822                 while (b[i] == 0) {
823                     i++; // Skip leading zero sign bytes
824                 }
825             } else {
826                 if (c == 0 || c == -1) { // Leading sign byte
827                     i = 1;
828                     // Skip all leading sign bytes
829                     while (i < b.length && b[i] == c) {
830                         i++;
831                     }
832                     if (i < b.length) {
833                         // Check first non-sign byte to see if its sign
834                         // matches the whole number's sign. If not one more
835                         // byte is needed to represent the value.
836                         if (((c ^ b[i]) & 0x80) != 0) {
837                             i--;
838                         }
839                     }
840                 }
841             }
842             if (b.length - i > 8) {
843                 // More than 64 bits of value
844                 throw new OtpErlangDecodeException(
845                         "Value does not fit in long: " + Arrays.toString(b));
846             }
847             // Convert the necessary bytes
848             for (v = c < 0 ? -1 : 0; i < b.length; i++) {
849                 v = v << 8 | b[i] & 0xFF;
850             }
851         }
852         return v;
853     }
854 
855     /**
856      * Read a list header from the stream.
857      *
858      * @return the arity of the list.
859      *
860      * @exception OtpErlangDecodeException
861      *                if the next term in the stream is not a list.
862      */
read_list_head()863     public int read_list_head() throws OtpErlangDecodeException {
864         int arity = 0;
865         final int tag = read1skip_version();
866 
867         switch (tag) {
868         case OtpExternal.nilTag:
869             arity = 0;
870             break;
871 
872         case OtpExternal.stringTag:
873             arity = read2BE();
874             break;
875 
876         case OtpExternal.listTag:
877             arity = read4BE();
878             break;
879 
880         default:
881             throw new OtpErlangDecodeException("Not valid list tag: " + tag);
882         }
883 
884         return arity;
885     }
886 
887     /**
888      * Read a tuple header from the stream.
889      *
890      * @return the arity of the tuple.
891      *
892      * @exception OtpErlangDecodeException
893      *                if the next term in the stream is not a tuple.
894      */
read_tuple_head()895     public int read_tuple_head() throws OtpErlangDecodeException {
896         int arity = 0;
897         final int tag = read1skip_version();
898 
899         // decode the tuple header and get arity
900         switch (tag) {
901         case OtpExternal.smallTupleTag:
902             arity = read1();
903             break;
904 
905         case OtpExternal.largeTupleTag:
906             arity = read4BE();
907             break;
908 
909         default:
910             throw new OtpErlangDecodeException("Not valid tuple tag: " + tag);
911         }
912 
913         return arity;
914     }
915 
916     /**
917      * Read an empty list from the stream.
918      *
919      * @return zero (the arity of the list).
920      *
921      * @exception OtpErlangDecodeException
922      *                if the next term in the stream is not an empty list.
923      */
read_nil()924     public int read_nil() throws OtpErlangDecodeException {
925         int arity = 0;
926         final int tag = read1skip_version();
927 
928         switch (tag) {
929         case OtpExternal.nilTag:
930             arity = 0;
931             break;
932 
933         default:
934             throw new OtpErlangDecodeException("Not valid nil tag: " + tag);
935         }
936 
937         return arity;
938     }
939 
940     /**
941      * Read an Erlang PID from the stream.
942      *
943      * @return the value of the PID.
944      *
945      * @exception OtpErlangDecodeException
946      *                if the next term in the stream is not an Erlang PID.
947      */
read_pid()948     public OtpErlangPid read_pid() throws OtpErlangDecodeException {
949         String node;
950         int id;
951         int serial;
952         int creation;
953         int tag;
954 
955         tag = read1skip_version();
956 
957         if (tag != OtpExternal.pidTag &&
958 	    tag != OtpExternal.newPidTag) {
959             throw new OtpErlangDecodeException(
960                     "Wrong tag encountered, expected " + OtpExternal.pidTag
961 		    + " or " + OtpExternal.newPidTag
962                             + ", got " + tag);
963         }
964 
965         node = read_atom();
966         id = read4BE();
967         serial = read4BE();
968 	if (tag == OtpExternal.pidTag)
969 	    creation = read1();
970 	else
971 	    creation = read4BE();
972 
973         return new OtpErlangPid(tag, node, id, serial, creation);
974     }
975 
976     /**
977      * Read an Erlang port from the stream.
978      *
979      * @return the value of the port.
980      *
981      * @exception OtpErlangDecodeException
982      *                if the next term in the stream is not an Erlang port.
983      */
read_port()984     public OtpErlangPort read_port() throws OtpErlangDecodeException {
985         String node;
986         int id;
987         int creation;
988         int tag;
989 
990         tag = read1skip_version();
991 
992         if (tag != OtpExternal.portTag &&
993 	    tag != OtpExternal.newPortTag) {
994             throw new OtpErlangDecodeException(
995                     "Wrong tag encountered, expected " + OtpExternal.portTag
996 		    + " or " + OtpExternal.newPortTag
997                             + ", got " + tag);
998         }
999 
1000         node = read_atom();
1001         id = read4BE();
1002 	if (tag == OtpExternal.portTag)
1003 	    creation = read1();
1004 	else
1005 	    creation = read4BE();
1006 
1007         return new OtpErlangPort(tag, node, id, creation);
1008     }
1009 
1010     /**
1011      * Read an Erlang reference from the stream.
1012      *
1013      * @return the value of the reference
1014      *
1015      * @exception OtpErlangDecodeException
1016      *                if the next term in the stream is not an Erlang reference.
1017      */
read_ref()1018     public OtpErlangRef read_ref() throws OtpErlangDecodeException {
1019         String node;
1020         int id;
1021         int creation;
1022         int tag;
1023 
1024         tag = read1skip_version();
1025 
1026         switch (tag) {
1027         case OtpExternal.refTag:
1028             node = read_atom();
1029             id = read4BE() & 0x3ffff; // 18 bits
1030             creation = read1() & 0x03; // 2 bits
1031             return new OtpErlangRef(node, id, creation);
1032 
1033         case OtpExternal.newRefTag:
1034         case OtpExternal.newerRefTag:
1035             final int arity = read2BE();
1036             if (arity > 3) {
1037 		throw new OtpErlangDecodeException(
1038 		    "Ref arity " + arity + " too large ");
1039 	    }
1040             node = read_atom();
1041 	    if (tag == OtpExternal.newRefTag)
1042 		creation = read1();
1043 	    else
1044 		creation = read4BE();
1045 
1046             final int[] ids = new int[arity];
1047             for (int i = 0; i < arity; i++) {
1048                 ids[i] = read4BE();
1049             }
1050             return new OtpErlangRef(tag, node, ids, creation);
1051 
1052         default:
1053             throw new OtpErlangDecodeException(
1054                     "Wrong tag encountered, expected ref, got " + tag);
1055         }
1056     }
1057 
read_fun()1058     public OtpErlangFun read_fun() throws OtpErlangDecodeException {
1059         final int tag = read1skip_version();
1060         if (tag == OtpExternal.funTag) {
1061             final int nFreeVars = read4BE();
1062             final OtpErlangPid pid = read_pid();
1063             final String module = read_atom();
1064             final long index = read_long();
1065             final long uniq = read_long();
1066             final OtpErlangObject[] freeVars = new OtpErlangObject[nFreeVars];
1067             for (int i = 0; i < nFreeVars; ++i) {
1068                 freeVars[i] = read_any();
1069             }
1070             return new OtpErlangFun(pid, module, index, uniq, freeVars);
1071         } else if (tag == OtpExternal.newFunTag) {
1072             read4BE();
1073             final int arity = read1();
1074             final byte[] md5 = new byte[16];
1075             readN(md5);
1076             final int index = read4BE();
1077             final int nFreeVars = read4BE();
1078             final String module = read_atom();
1079             final long oldIndex = read_long();
1080             final long uniq = read_long();
1081             final OtpErlangPid pid = read_pid();
1082             final OtpErlangObject[] freeVars = new OtpErlangObject[nFreeVars];
1083             for (int i = 0; i < nFreeVars; ++i) {
1084                 freeVars[i] = read_any();
1085             }
1086             return new OtpErlangFun(pid, module, arity, md5, index, oldIndex,
1087                     uniq, freeVars);
1088         } else {
1089             throw new OtpErlangDecodeException(
1090                     "Wrong tag encountered, expected fun, got " + tag);
1091         }
1092     }
1093 
read_external_fun()1094     public OtpErlangExternalFun read_external_fun()
1095             throws OtpErlangDecodeException {
1096         final int tag = read1skip_version();
1097         if (tag != OtpExternal.externalFunTag) {
1098             throw new OtpErlangDecodeException(
1099                     "Wrong tag encountered, expected external fun, got " + tag);
1100         }
1101         final String module = read_atom();
1102         final String function = read_atom();
1103         final int arity = (int) read_long();
1104         return new OtpErlangExternalFun(module, function, arity);
1105     }
1106 
1107     /**
1108      * Read a string from the stream.
1109      *
1110      * @return the value of the string.
1111      *
1112      * @exception OtpErlangDecodeException
1113      *                if the next term in the stream is not a string.
1114      */
read_string()1115     public String read_string() throws OtpErlangDecodeException {
1116         int tag;
1117         int len;
1118         byte[] strbuf;
1119         int[] intbuf;
1120         tag = read1skip_version();
1121         switch (tag) {
1122         case OtpExternal.stringTag:
1123             len = read2BE();
1124             strbuf = new byte[len];
1125             this.readN(strbuf);
1126             return OtpErlangString.newString(strbuf);
1127         case OtpExternal.nilTag:
1128             return "";
1129         case OtpExternal.listTag: // List when unicode +
1130             len = read4BE();
1131             intbuf = new int[len];
1132             for (int i = 0; i < len; i++) {
1133                 intbuf[i] = read_int();
1134                 if (!OtpErlangString.isValidCodePoint(intbuf[i])) {
1135                     throw new OtpErlangDecodeException("Invalid CodePoint: "
1136                             + intbuf[i]);
1137                 }
1138             }
1139             read_nil();
1140             return new String(intbuf, 0, intbuf.length);
1141         default:
1142             throw new OtpErlangDecodeException(
1143                     "Wrong tag encountered, expected " + OtpExternal.stringTag
1144                             + " or " + OtpExternal.listTag + ", got " + tag);
1145         }
1146     }
1147 
1148     /**
1149      * Read a compressed term from the stream
1150      *
1151      * @return the resulting uncompressed term.
1152      *
1153      * @exception OtpErlangDecodeException
1154      *                if the next term in the stream is not a compressed term.
1155      */
read_compressed()1156     public OtpErlangObject read_compressed() throws OtpErlangDecodeException {
1157         final int tag = read1skip_version();
1158 
1159         if (tag != OtpExternal.compressedTag) {
1160             throw new OtpErlangDecodeException(
1161                     "Wrong tag encountered, expected "
1162                             + OtpExternal.compressedTag + ", got " + tag);
1163         }
1164 
1165         final int size = read4BE();
1166         final byte[] abuf = new byte[size];
1167         final java.util.zip.InflaterInputStream is = new java.util.zip.InflaterInputStream(
1168                 this, new java.util.zip.Inflater(), size);
1169         int curPos = 0;
1170         try {
1171             int curRead;
1172             while (curPos < size
1173                     && (curRead = is.read(abuf, curPos, size - curPos)) != -1) {
1174                 curPos += curRead;
1175             }
1176             if (curPos != size) {
1177                 throw new OtpErlangDecodeException("Decompression gave "
1178                         + curPos + " bytes, not " + size);
1179             }
1180         } catch (final IOException e) {
1181             throw new OtpErlangDecodeException("Cannot read from input stream");
1182         }
1183 
1184         @SuppressWarnings("resource")
1185         final OtpInputStream ois = new OtpInputStream(abuf, flags);
1186         return ois.read_any();
1187     }
1188 
1189     /**
1190      * Read an arbitrary Erlang term from the stream.
1191      *
1192      * @return the Erlang term.
1193      *
1194      * @exception OtpErlangDecodeException
1195      *                if the stream does not contain a known Erlang type at the
1196      *                next position.
1197      */
read_any()1198     public OtpErlangObject read_any() throws OtpErlangDecodeException {
1199         // calls one of the above functions, depending on o
1200         final int tag = peek1skip_version();
1201 
1202         switch (tag) {
1203         case OtpExternal.smallIntTag:
1204         case OtpExternal.intTag:
1205         case OtpExternal.smallBigTag:
1206         case OtpExternal.largeBigTag:
1207             return new OtpErlangLong(this);
1208 
1209         case OtpExternal.atomTag:
1210         case OtpExternal.smallAtomUtf8Tag:
1211         case OtpExternal.atomUtf8Tag:
1212             return new OtpErlangAtom(this);
1213 
1214         case OtpExternal.floatTag:
1215         case OtpExternal.newFloatTag:
1216             return new OtpErlangDouble(this);
1217 
1218         case OtpExternal.refTag:
1219         case OtpExternal.newRefTag:
1220         case OtpExternal.newerRefTag:
1221             return new OtpErlangRef(this);
1222 
1223         case OtpExternal.mapTag:
1224             return new OtpErlangMap(this);
1225 
1226         case OtpExternal.portTag:
1227         case OtpExternal.newPortTag:
1228             return new OtpErlangPort(this);
1229 
1230         case OtpExternal.pidTag:
1231         case OtpExternal.newPidTag:
1232             return new OtpErlangPid(this);
1233 
1234         case OtpExternal.stringTag:
1235             return new OtpErlangString(this);
1236 
1237         case OtpExternal.listTag:
1238         case OtpExternal.nilTag:
1239             if ((flags & DECODE_INT_LISTS_AS_STRINGS) != 0) {
1240                 final int savePos = getPos();
1241                 try {
1242                     return new OtpErlangString(this);
1243                 } catch (final OtpErlangDecodeException e) {
1244                 }
1245                 setPos(savePos);
1246             }
1247             return new OtpErlangList(this);
1248 
1249         case OtpExternal.smallTupleTag:
1250         case OtpExternal.largeTupleTag:
1251             return new OtpErlangTuple(this);
1252 
1253         case OtpExternal.binTag:
1254             return new OtpErlangBinary(this);
1255 
1256         case OtpExternal.bitBinTag:
1257             return new OtpErlangBitstr(this);
1258 
1259         case OtpExternal.compressedTag:
1260             return read_compressed();
1261 
1262         case OtpExternal.newFunTag:
1263         case OtpExternal.funTag:
1264             return new OtpErlangFun(this);
1265 
1266 	case OtpExternal.externalFunTag:
1267 	    return new OtpErlangExternalFun(this);
1268 
1269         default:
1270             throw new OtpErlangDecodeException("Uknown data type: " + tag);
1271         }
1272     }
1273 
read_map_head()1274     public int read_map_head() throws OtpErlangDecodeException {
1275         int arity = 0;
1276         final int tag = read1skip_version();
1277 
1278         // decode the map header and get arity
1279         switch (tag) {
1280         case OtpExternal.mapTag:
1281             arity = read4BE();
1282             break;
1283 
1284         default:
1285             throw new OtpErlangDecodeException("Not valid map tag: " + tag);
1286         }
1287 
1288         return arity;
1289     }
1290 }
1291