xref: /freebsd/contrib/bearssl/src/x509/asn1.t0 (revision cc9e6590773dba57440750c124173ed531349a06)
10957b409SSimon J. Gerraty\ Copyright (c) 2016 Thomas Pornin <pornin@bolet.org>
20957b409SSimon J. Gerraty\
30957b409SSimon J. Gerraty\ Permission is hereby granted, free of charge, to any person obtaining
40957b409SSimon J. Gerraty\ a copy of this software and associated documentation files (the
50957b409SSimon J. Gerraty\ "Software"), to deal in the Software without restriction, including
60957b409SSimon J. Gerraty\ without limitation the rights to use, copy, modify, merge, publish,
70957b409SSimon J. Gerraty\ distribute, sublicense, and/or sell copies of the Software, and to
80957b409SSimon J. Gerraty\ permit persons to whom the Software is furnished to do so, subject to
90957b409SSimon J. Gerraty\ the following conditions:
100957b409SSimon J. Gerraty\
110957b409SSimon J. Gerraty\ The above copyright notice and this permission notice shall be
120957b409SSimon J. Gerraty\ included in all copies or substantial portions of the Software.
130957b409SSimon J. Gerraty\
140957b409SSimon J. Gerraty\ THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
150957b409SSimon J. Gerraty\ EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
160957b409SSimon J. Gerraty\ MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
170957b409SSimon J. Gerraty\ NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS
180957b409SSimon J. Gerraty\ BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN
190957b409SSimon J. Gerraty\ ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN
200957b409SSimon J. Gerraty\ CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
210957b409SSimon J. Gerraty\ SOFTWARE.
220957b409SSimon J. Gerraty
230957b409SSimon J. Gerraty\ =======================================================================
240957b409SSimon J. Gerraty
250957b409SSimon J. Gerraty\ This file contains code which is common to all engines that do some
260957b409SSimon J. Gerraty\ ASN.1 decoding. It should not be compiled on its own, but only along
270957b409SSimon J. Gerraty\ with another file (e.g. x509_minimal.t0) which uses it.
280957b409SSimon J. Gerraty\
290957b409SSimon J. Gerraty\ Users must define several things:
300957b409SSimon J. Gerraty\
310957b409SSimon J. Gerraty\ -- In the preamble, a macro called "CTX" that evaluates to the current
320957b409SSimon J. Gerraty\ context structure.
330957b409SSimon J. Gerraty\
340957b409SSimon J. Gerraty\ -- In the preamble, a macro called "CONTEXT_NAME" that evaluates to the
350957b409SSimon J. Gerraty\ context structure type. This will be invoked during compilation.
360957b409SSimon J. Gerraty\
370957b409SSimon J. Gerraty\ -- A word called "read8-low" ( -- x ) that reads the next byte, or -1
380957b409SSimon J. Gerraty\ if the input buffer is empty. That word is usually written in C.
390957b409SSimon J. Gerraty\
400957b409SSimon J. Gerraty\ -- A word called "read-blob-inner" ( addr len -- addr len ) that is
410957b409SSimon J. Gerraty\ the multi-byte version of read8-low.
420957b409SSimon J. Gerraty\
430957b409SSimon J. Gerraty\ -- A word called "skip-remaining-inner" ( lim -- lim ) which reads but
440957b409SSimon J. Gerraty\ drops some input bytes.
450957b409SSimon J. Gerraty
460957b409SSimon J. Gerratypreamble {
470957b409SSimon J. Gerraty
480957b409SSimon J. Gerraty#include "inner.h"
490957b409SSimon J. Gerraty
500957b409SSimon J. Gerraty}
510957b409SSimon J. Gerraty
520957b409SSimon J. Gerraty\ Read next source character, skipping blanks.
530957b409SSimon J. Gerraty: skip-blanks begin char dup 32 > if ret then drop again ;
540957b409SSimon J. Gerraty
550957b409SSimon J. Gerraty: fail-oid
560957b409SSimon J. Gerraty	"Invalid OID" puts cr exitvm ;
570957b409SSimon J. Gerraty
580957b409SSimon J. Gerraty\ Read a decimal integer, followed by either a dot or whitespace.
590957b409SSimon J. Gerraty\ Note: this does not check for overflows.
600957b409SSimon J. Gerraty: parse-number ( -- val nextchar )
610957b409SSimon J. Gerraty	char decval
620957b409SSimon J. Gerraty	begin
630957b409SSimon J. Gerraty		char
640957b409SSimon J. Gerraty		dup dup `. = swap 32 <= or if ret then
650957b409SSimon J. Gerraty		decval swap 10 * +
660957b409SSimon J. Gerraty	again ;
670957b409SSimon J. Gerraty
680957b409SSimon J. Gerraty\ Encode a number in unsigned 7E format.
690957b409SSimon J. Gerraty: encode7E ( val -- )
700957b409SSimon J. Gerraty	0 encode7E-inner ;
710957b409SSimon J. Gerraty
720957b409SSimon J. Gerraty: encode7E-inner ( val eb -- )
730957b409SSimon J. Gerraty	swap dup 0x7F > if
740957b409SSimon J. Gerraty		dup 7 u>> 0x80 encode7E-inner 0x7F and
750957b409SSimon J. Gerraty	then
760957b409SSimon J. Gerraty	or data-add8 ;
770957b409SSimon J. Gerraty
780957b409SSimon J. Gerraty\ Decode an OID from source, and encode it. First byte is length,
790957b409SSimon J. Gerraty\ followed by encoded ASN.1 DER value. The OID is encoded in the
800957b409SSimon J. Gerraty\ current data block.
810957b409SSimon J. Gerraty: OID
820957b409SSimon J. Gerraty	\ Get current data address, and push a 0 for length.
830957b409SSimon J. Gerraty	current-data 0 data-add8
840957b409SSimon J. Gerraty	\ Skip blanks and get first digit, which must be 0, 1 or 2.
850957b409SSimon J. Gerraty	skip-blanks decval dup 2 > if fail-oid then
860957b409SSimon J. Gerraty	40 *
870957b409SSimon J. Gerraty	\ Next character must be a dot.
880957b409SSimon J. Gerraty	char `. <> if fail-oid then
890957b409SSimon J. Gerraty	\ Second group must be one or two digits.
900957b409SSimon J. Gerraty	parse-number { nextchar }
910957b409SSimon J. Gerraty	dup 40 >= if fail-oid then
920957b409SSimon J. Gerraty	+ encode7E
930957b409SSimon J. Gerraty	\ While next character is a dot, keep encoding numbers.
940957b409SSimon J. Gerraty	begin nextchar `. = while
950957b409SSimon J. Gerraty		parse-number >nextchar
960957b409SSimon J. Gerraty		encode7E
970957b409SSimon J. Gerraty	repeat
980957b409SSimon J. Gerraty	\ Write back length in the first byte.
990957b409SSimon J. Gerraty	dup current-data swap - 1- swap data-set8
1000957b409SSimon J. Gerraty	; immediate
1010957b409SSimon J. Gerraty
1020957b409SSimon J. Gerraty\ Define a new data word for an encoded OID. The OID is read from the
1030957b409SSimon J. Gerraty\ source.
1040957b409SSimon J. Gerraty: OID:
1050957b409SSimon J. Gerraty	new-data-block next-word define-data-word postpone OID ;
1060957b409SSimon J. Gerraty
1070957b409SSimon J. Gerraty\ Define a word that evaluates to the address of a field within the
1080957b409SSimon J. Gerraty\ context.
1090957b409SSimon J. Gerraty: addr:
1100957b409SSimon J. Gerraty	next-word { field }
1110957b409SSimon J. Gerraty	"addr-" field + 0 1 define-word
1120957b409SSimon J. Gerraty	0 8191 "offsetof(CONTEXT_NAME, " field + ")" + make-CX
1130957b409SSimon J. Gerraty	postpone literal postpone ; ;
1140957b409SSimon J. Gerraty
1150957b409SSimon J. Gerratyaddr: pad
1160957b409SSimon J. Gerraty
1170957b409SSimon J. Gerraty\ Define a word that evaluates to an error code through a macro name.
1180957b409SSimon J. Gerraty: err:
1190957b409SSimon J. Gerraty	next-word { name }
1200957b409SSimon J. Gerraty	name 0 1 define-word
1210957b409SSimon J. Gerraty	0 63 "BR_" name + make-CX postpone literal postpone ; ;
1220957b409SSimon J. Gerraty
1230957b409SSimon J. Gerratyerr: ERR_X509_INVALID_VALUE
1240957b409SSimon J. Gerratyerr: ERR_X509_TRUNCATED
1250957b409SSimon J. Gerratyerr: ERR_X509_EMPTY_CHAIN
1260957b409SSimon J. Gerratyerr: ERR_X509_INNER_TRUNC
1270957b409SSimon J. Gerratyerr: ERR_X509_BAD_TAG_CLASS
1280957b409SSimon J. Gerratyerr: ERR_X509_BAD_TAG_VALUE
1290957b409SSimon J. Gerratyerr: ERR_X509_INDEFINITE_LENGTH
1300957b409SSimon J. Gerratyerr: ERR_X509_EXTRA_ELEMENT
1310957b409SSimon J. Gerratyerr: ERR_X509_UNEXPECTED
1320957b409SSimon J. Gerratyerr: ERR_X509_NOT_CONSTRUCTED
1330957b409SSimon J. Gerratyerr: ERR_X509_NOT_PRIMITIVE
1340957b409SSimon J. Gerratyerr: ERR_X509_PARTIAL_BYTE
1350957b409SSimon J. Gerratyerr: ERR_X509_BAD_BOOLEAN
1360957b409SSimon J. Gerratyerr: ERR_X509_OVERFLOW
1370957b409SSimon J. Gerratyerr: ERR_X509_BAD_DN
1380957b409SSimon J. Gerratyerr: ERR_X509_BAD_TIME
1390957b409SSimon J. Gerratyerr: ERR_X509_UNSUPPORTED
1400957b409SSimon J. Gerratyerr: ERR_X509_LIMIT_EXCEEDED
1410957b409SSimon J. Gerratyerr: ERR_X509_WRONG_KEY_TYPE
1420957b409SSimon J. Gerratyerr: ERR_X509_BAD_SIGNATURE
1430957b409SSimon J. Gerratyerr: ERR_X509_EXPIRED
1440957b409SSimon J. Gerratyerr: ERR_X509_DN_MISMATCH
1450957b409SSimon J. Gerratyerr: ERR_X509_BAD_SERVER_NAME
1460957b409SSimon J. Gerratyerr: ERR_X509_CRITICAL_EXTENSION
1470957b409SSimon J. Gerratyerr: ERR_X509_NOT_CA
1480957b409SSimon J. Gerratyerr: ERR_X509_FORBIDDEN_KEY_USAGE
1490957b409SSimon J. Gerratyerr: ERR_X509_WEAK_PUBLIC_KEY
1500957b409SSimon J. Gerraty
1510957b409SSimon J. Gerraty: KEYTYPE_RSA     CX 0 15 { BR_KEYTYPE_RSA } ;
1520957b409SSimon J. Gerraty: KEYTYPE_EC      CX 0 15 { BR_KEYTYPE_EC } ;
1530957b409SSimon J. Gerraty
1540957b409SSimon J. Gerratycc: fail ( err -- ! ) {
1550957b409SSimon J. Gerraty	CTX->err = T0_POPi();
1560957b409SSimon J. Gerraty	T0_CO();
1570957b409SSimon J. Gerraty}
1580957b409SSimon J. Gerraty
1590957b409SSimon J. Gerraty\ Read one byte from the stream.
1600957b409SSimon J. Gerraty: read8-nc ( -- x )
1610957b409SSimon J. Gerraty	begin
1620957b409SSimon J. Gerraty		read8-low dup 0 >= if ret then
1630957b409SSimon J. Gerraty		drop co
1640957b409SSimon J. Gerraty	again ;
1650957b409SSimon J. Gerraty
1660957b409SSimon J. Gerraty\ Read one byte, enforcing current read limit.
1670957b409SSimon J. Gerraty: read8 ( lim -- lim x )
1680957b409SSimon J. Gerraty	dup ifnot ERR_X509_INNER_TRUNC fail then
1690957b409SSimon J. Gerraty	1- read8-nc ;
1700957b409SSimon J. Gerraty
1710957b409SSimon J. Gerraty\ Read a 16-bit value, big-endian encoding.
1720957b409SSimon J. Gerraty: read16be ( lim -- lim x )
1730957b409SSimon J. Gerraty	read8 8 << swap read8 rot + ;
1740957b409SSimon J. Gerraty
1750957b409SSimon J. Gerraty\ Read a 16-bit value, little-endian encoding.
1760957b409SSimon J. Gerraty: read16le ( lim -- lim x )
1770957b409SSimon J. Gerraty	read8 swap read8 8 << rot + ;
1780957b409SSimon J. Gerraty
1790957b409SSimon J. Gerraty\ Read all bytes from the current element, then close it (i.e. drop the
1800957b409SSimon J. Gerraty\ limit). Destination address is an offset within the context.
1810957b409SSimon J. Gerraty: read-blob ( lim addr -- )
1820957b409SSimon J. Gerraty	swap
1830957b409SSimon J. Gerraty	begin dup while read-blob-inner dup if co then repeat
1840957b409SSimon J. Gerraty	2drop ;
1850957b409SSimon J. Gerraty
1860957b409SSimon J. Gerraty\ Skip remaining bytes in the current structure, but do not close it
1870957b409SSimon J. Gerraty\ (thus, this leaves the value 0 on the stack).
1880957b409SSimon J. Gerraty: skip-remaining ( lim -- lim )
1890957b409SSimon J. Gerraty	begin dup while skip-remaining-inner dup if co then repeat ;
1900957b409SSimon J. Gerraty
1910957b409SSimon J. Gerraty: skip-remaining-inner ( lim -- lim )
1920957b409SSimon J. Gerraty	0 over read-blob-inner -rot 2drop ;
1930957b409SSimon J. Gerraty
1940957b409SSimon J. Gerratycc: set8 ( val addr -- ) {
1950957b409SSimon J. Gerraty	uint32_t addr = T0_POP();
1960957b409SSimon J. Gerraty	*((unsigned char *)CTX + addr) = (unsigned char)T0_POP();
1970957b409SSimon J. Gerraty}
1980957b409SSimon J. Gerraty
1990957b409SSimon J. Gerratycc: set16 ( val addr -- ) {
2000957b409SSimon J. Gerraty	uint32_t addr = T0_POP();
2010957b409SSimon J. Gerraty	*(uint16_t *)(void *)((unsigned char *)CTX + addr) = T0_POP();
2020957b409SSimon J. Gerraty}
2030957b409SSimon J. Gerraty
2040957b409SSimon J. Gerratycc: set32 ( val addr -- ) {
2050957b409SSimon J. Gerraty	uint32_t addr = T0_POP();
2060957b409SSimon J. Gerraty	*(uint32_t *)(void *)((unsigned char *)CTX + addr) = T0_POP();
2070957b409SSimon J. Gerraty}
2080957b409SSimon J. Gerraty
2090957b409SSimon J. Gerratycc: get8 ( addr -- val ) {
2100957b409SSimon J. Gerraty	uint32_t addr = T0_POP();
2110957b409SSimon J. Gerraty	T0_PUSH(*((unsigned char *)CTX + addr));
2120957b409SSimon J. Gerraty}
2130957b409SSimon J. Gerraty
2140957b409SSimon J. Gerratycc: get16 ( addr -- val ) {
2150957b409SSimon J. Gerraty	uint32_t addr = T0_POP();
2160957b409SSimon J. Gerraty	T0_PUSH(*(uint16_t *)(void *)((unsigned char *)CTX + addr));
2170957b409SSimon J. Gerraty}
2180957b409SSimon J. Gerraty
2190957b409SSimon J. Gerratycc: get32 ( addr -- val ) {
2200957b409SSimon J. Gerraty	uint32_t addr = T0_POP();
2210957b409SSimon J. Gerraty	T0_PUSH(*(uint32_t *)(void *)((unsigned char *)CTX + addr));
2220957b409SSimon J. Gerraty}
2230957b409SSimon J. Gerraty
2240957b409SSimon J. Gerraty\ Read an ASN.1 tag. This function returns the "constructed" status
2250957b409SSimon J. Gerraty\ and the tag value. The constructed status is a boolean (-1 for
2260957b409SSimon J. Gerraty\ constructed, 0 for primitive). The tag value is either 0 to 31 for
2270957b409SSimon J. Gerraty\ a universal tag, or 32+x for a contextual tag of value x. Tag classes
2280957b409SSimon J. Gerraty\ "application" and "private" are rejected. Universal tags beyond 30
2290957b409SSimon J. Gerraty\ are rejected. Contextual tags beyond 30 are rejected. Thus, accepted
2300957b409SSimon J. Gerraty\ tags will necessarily fit on exactly one byte. This does not support
2310957b409SSimon J. Gerraty\ the whole of ASN.1/BER, but is sufficient for certificate parsing.
2320957b409SSimon J. Gerraty: read-tag ( lim -- lim constructed value )
2330957b409SSimon J. Gerraty	read8 { fb }
2340957b409SSimon J. Gerraty
2350957b409SSimon J. Gerraty	\ Constructed flag is bit 5.
2360957b409SSimon J. Gerraty	fb 5 >> 0x01 and neg
2370957b409SSimon J. Gerraty
2380957b409SSimon J. Gerraty	\ Class is in bits 6 and 7. Accepted classes are 00 (universal)
2390957b409SSimon J. Gerraty	\ and 10 (context). We check that bit 6 is 0, and shift back
2400957b409SSimon J. Gerraty	\ bit 7 so that we get 0 (universal) or 32 (context).
2410957b409SSimon J. Gerraty	fb 6 >> dup 0x01 and if ERR_X509_BAD_TAG_CLASS fail then
2420957b409SSimon J. Gerraty	4 <<
2430957b409SSimon J. Gerraty
2440957b409SSimon J. Gerraty	\ Tag value is in bits 0..4. If the value is 31, then this is
2450957b409SSimon J. Gerraty	\ an extended tag, encoded over subsequent bytes, and we do
2460957b409SSimon J. Gerraty	\ not support that.
2470957b409SSimon J. Gerraty	fb 0x1F and dup 0x1F = if ERR_X509_BAD_TAG_VALUE fail then
2480957b409SSimon J. Gerraty	+ ;
2490957b409SSimon J. Gerraty
2500957b409SSimon J. Gerraty\ Read a tag, but only if not at the end of the current object. If there
2510957b409SSimon J. Gerraty\ is no room for another element (limit is zero), then this will push a
2520957b409SSimon J. Gerraty\ synthetic "no tag" value (primitive, with value -1).
2530957b409SSimon J. Gerraty: read-tag-or-end ( lim -- lim constructed value )
2540957b409SSimon J. Gerraty	dup ifnot 0 -1 ret then
2550957b409SSimon J. Gerraty	read-tag ;
2560957b409SSimon J. Gerraty
2570957b409SSimon J. Gerraty\ Compare the read tag with the provided value. If equal, then the
2580957b409SSimon J. Gerraty\ element is skipped, and a new tag is read (or end of object).
2590957b409SSimon J. Gerraty: iftag-skip ( lim constructed value ref -- lim constructed value )
2600957b409SSimon J. Gerraty	over = if
2610957b409SSimon J. Gerraty		2drop
2620957b409SSimon J. Gerraty		read-length-open-elt skip-close-elt
2630957b409SSimon J. Gerraty		read-tag-or-end
2640957b409SSimon J. Gerraty	then ;
2650957b409SSimon J. Gerraty
2660957b409SSimon J. Gerraty\ Read an ASN.1 length. This supports only definite lengths (theoretically,
2670957b409SSimon J. Gerraty\ certificates may use an indefinite length for the outer structure, using
2680957b409SSimon J. Gerraty\ DER only in the TBS, but this never happens in practice, except in a
2690957b409SSimon J. Gerraty\ single example certificate from 15 years ago that also fails to decode
2700957b409SSimon J. Gerraty\ properly for other reasons).
2710957b409SSimon J. Gerraty: read-length ( lim -- lim length )
2720957b409SSimon J. Gerraty	read8
2730957b409SSimon J. Gerraty	\ Lengths in 0x00..0x7F get encoded as a single byte.
2740957b409SSimon J. Gerraty	dup 0x80 < if ret then
2750957b409SSimon J. Gerraty
2760957b409SSimon J. Gerraty	\ If the byte is 0x80 then this is an indefinite length, and we
2770957b409SSimon J. Gerraty	\ do not support that.
2780957b409SSimon J. Gerraty	0x80 - dup ifnot ERR_X509_INDEFINITE_LENGTH fail then
2790957b409SSimon J. Gerraty
2800957b409SSimon J. Gerraty	\ Masking out bit 7, this yields the number of bytes over which
2810957b409SSimon J. Gerraty	\ the value is encoded. Since the total certificate length must
2820957b409SSimon J. Gerraty	\ fit over 3 bytes (this is a consequence of SSL/TLS message
2830957b409SSimon J. Gerraty	\ format), we can reject big lengths and keep the length in a
2840957b409SSimon J. Gerraty	\ single integer.
2850957b409SSimon J. Gerraty	{ n } 0
2860957b409SSimon J. Gerraty	begin n 0 > while n 1- >n
2870957b409SSimon J. Gerraty		dup 0x7FFFFF > if ERR_X509_INNER_TRUNC fail then
2880957b409SSimon J. Gerraty		8 << swap read8 rot +
2890957b409SSimon J. Gerraty	repeat ;
2900957b409SSimon J. Gerraty
2910957b409SSimon J. Gerraty\ Open a sub-structure. This subtracts the length from the limit, and
2920957b409SSimon J. Gerraty\ pushes the length back as new limit.
2930957b409SSimon J. Gerraty: open-elt ( lim length -- lim_outer lim_inner )
2940957b409SSimon J. Gerraty	dup2 < if ERR_X509_INNER_TRUNC fail then
2950957b409SSimon J. Gerraty	dup { len } - len ;
2960957b409SSimon J. Gerraty
2970957b409SSimon J. Gerraty\ Read a length and open the value as a sub-structure.
2980957b409SSimon J. Gerraty: read-length-open-elt ( lim -- lim_outer lim_inner )
2990957b409SSimon J. Gerraty	read-length open-elt ;
3000957b409SSimon J. Gerraty
3010957b409SSimon J. Gerraty\ Close a sub-structure. This verifies that there is no remaining
3020957b409SSimon J. Gerraty\ element to read.
3030957b409SSimon J. Gerraty: close-elt ( lim -- )
3040957b409SSimon J. Gerraty	if ERR_X509_EXTRA_ELEMENT fail then ;
3050957b409SSimon J. Gerraty
3060957b409SSimon J. Gerraty\ Skip remaining bytes in the current structure, then close it.
3070957b409SSimon J. Gerraty: skip-close-elt ( lim -- )
3080957b409SSimon J. Gerraty	skip-remaining drop ;
3090957b409SSimon J. Gerraty
3100957b409SSimon J. Gerraty\ Read a length and then skip the value.
3110957b409SSimon J. Gerraty: read-length-skip ( lim -- lim )
3120957b409SSimon J. Gerraty	read-length-open-elt skip-close-elt ;
3130957b409SSimon J. Gerraty
3140957b409SSimon J. Gerraty\ Check that a given tag is constructed and has the expected value.
3150957b409SSimon J. Gerraty: check-tag-constructed ( constructed value refvalue -- )
3160957b409SSimon J. Gerraty	= ifnot ERR_X509_UNEXPECTED fail then
3170957b409SSimon J. Gerraty	check-constructed ;
3180957b409SSimon J. Gerraty
3190957b409SSimon J. Gerraty\ Check that the top value is true; report a "not constructed"
3200957b409SSimon J. Gerraty\ error otherwise.
3210957b409SSimon J. Gerraty: check-constructed ( constructed -- )
3220957b409SSimon J. Gerraty	ifnot ERR_X509_NOT_CONSTRUCTED fail then ;
3230957b409SSimon J. Gerraty
3240957b409SSimon J. Gerraty\ Check that a given tag is primitive and has the expected value.
3250957b409SSimon J. Gerraty: check-tag-primitive ( constructed value refvalue -- )
3260957b409SSimon J. Gerraty	= ifnot ERR_X509_UNEXPECTED fail then
3270957b409SSimon J. Gerraty	check-primitive ;
3280957b409SSimon J. Gerraty
3290957b409SSimon J. Gerraty\ Check that the top value is true; report a "not primitive"
3300957b409SSimon J. Gerraty\ error otherwise.
3310957b409SSimon J. Gerraty: check-primitive ( constructed -- )
3320957b409SSimon J. Gerraty	if ERR_X509_NOT_PRIMITIVE fail then ;
3330957b409SSimon J. Gerraty
3340957b409SSimon J. Gerraty\ Check that the tag is for a constructed SEQUENCE.
3350957b409SSimon J. Gerraty: check-sequence ( constructed value -- )
3360957b409SSimon J. Gerraty	0x10 check-tag-constructed ;
3370957b409SSimon J. Gerraty
3380957b409SSimon J. Gerraty\ Read a tag, check that it is for a constructed SEQUENCE, and open
3390957b409SSimon J. Gerraty\ it as a sub-element.
3400957b409SSimon J. Gerraty: read-sequence-open ( lim -- lim_outer lim_inner )
3410957b409SSimon J. Gerraty	read-tag check-sequence read-length-open-elt ;
3420957b409SSimon J. Gerraty
3430957b409SSimon J. Gerraty\ Read the next element as a BIT STRING with no ignore bits, and open
3440957b409SSimon J. Gerraty\ it as a sub-element.
3450957b409SSimon J. Gerraty: read-bits-open ( lim -- lim_outer lim_inner )
3460957b409SSimon J. Gerraty	read-tag 0x03 check-tag-primitive
3470957b409SSimon J. Gerraty	read-length-open-elt
3480957b409SSimon J. Gerraty	read8 if ERR_X509_PARTIAL_BYTE fail then ;
3490957b409SSimon J. Gerraty
3500957b409SSimon J. GerratyOID: rsaEncryption               1.2.840.113549.1.1.1
3510957b409SSimon J. Gerraty
3520957b409SSimon J. GerratyOID: sha1WithRSAEncryption       1.2.840.113549.1.1.5
3530957b409SSimon J. GerratyOID: sha224WithRSAEncryption     1.2.840.113549.1.1.14
3540957b409SSimon J. GerratyOID: sha256WithRSAEncryption     1.2.840.113549.1.1.11
3550957b409SSimon J. GerratyOID: sha384WithRSAEncryption     1.2.840.113549.1.1.12
3560957b409SSimon J. GerratyOID: sha512WithRSAEncryption     1.2.840.113549.1.1.13
3570957b409SSimon J. Gerraty
3580957b409SSimon J. GerratyOID: id-sha1                     1.3.14.3.2.26
3590957b409SSimon J. GerratyOID: id-sha224                   2.16.840.1.101.3.4.2.4
3600957b409SSimon J. GerratyOID: id-sha256                   2.16.840.1.101.3.4.2.1
3610957b409SSimon J. GerratyOID: id-sha384                   2.16.840.1.101.3.4.2.2
3620957b409SSimon J. GerratyOID: id-sha512                   2.16.840.1.101.3.4.2.3
3630957b409SSimon J. Gerraty
3640957b409SSimon J. GerratyOID: id-ecPublicKey              1.2.840.10045.2.1
3650957b409SSimon J. Gerraty
3660957b409SSimon J. GerratyOID: ansix9p256r1                1.2.840.10045.3.1.7
3670957b409SSimon J. GerratyOID: ansix9p384r1                1.3.132.0.34
3680957b409SSimon J. GerratyOID: ansix9p521r1                1.3.132.0.35
3690957b409SSimon J. Gerraty
3700957b409SSimon J. GerratyOID: ecdsa-with-SHA1             1.2.840.10045.4.1
3710957b409SSimon J. GerratyOID: ecdsa-with-SHA224           1.2.840.10045.4.3.1
3720957b409SSimon J. GerratyOID: ecdsa-with-SHA256           1.2.840.10045.4.3.2
3730957b409SSimon J. GerratyOID: ecdsa-with-SHA384           1.2.840.10045.4.3.3
3740957b409SSimon J. GerratyOID: ecdsa-with-SHA512           1.2.840.10045.4.3.4
3750957b409SSimon J. Gerraty
3760957b409SSimon J. GerratyOID: id-at-commonName            2.5.4.3
3770957b409SSimon J. Gerraty
3780957b409SSimon J. Gerraty\ Read a "small value". This assumes that the tag has just been read
3790957b409SSimon J. Gerraty\ and processed, but not the length. The first pad byte is set to the
3800957b409SSimon J. Gerraty\ value length; the encoded value itself follows. If the value length
3810957b409SSimon J. Gerraty\ exceeds 255 bytes, then a single 0 is written in the pad, and this
3820957b409SSimon J. Gerraty\ method returns false (0). Otherwise, it returns true (-1).
3830957b409SSimon J. Gerraty\ Either way, the element is fully read.
3840957b409SSimon J. Gerraty: read-small-value ( lim -- lim bool )
3850957b409SSimon J. Gerraty	read-length-open-elt
3860957b409SSimon J. Gerraty	dup 255 > if skip-close-elt 0 addr-pad set8 0 ret then
3870957b409SSimon J. Gerraty	dup addr-pad set8
3880957b409SSimon J. Gerraty	addr-pad 1+ read-blob
3890957b409SSimon J. Gerraty	-1 ;
3900957b409SSimon J. Gerraty
3910957b409SSimon J. Gerraty\ Read an OID as a "small value" (tag, length and value). A boolean
3920957b409SSimon J. Gerraty\ value is returned, which is true (-1) if the OID value fits on the pad,
3930957b409SSimon J. Gerraty\ false (0) otherwise.
3940957b409SSimon J. Gerraty: read-OID ( lim -- lim bool )
3950957b409SSimon J. Gerraty	read-tag 0x06 check-tag-primitive read-small-value ;
3960957b409SSimon J. Gerraty
3970957b409SSimon J. Gerraty\ Read a UTF-8 code point. On error, return 0. Reading a code point of
3980957b409SSimon J. Gerraty\ value 0 is considered to be an error.
3990957b409SSimon J. Gerraty: read-UTF8 ( lim -- lim val )
4000957b409SSimon J. Gerraty	read8
4010957b409SSimon J. Gerraty	choice
4020957b409SSimon J. Gerraty		dup 0x80 < uf ret enduf
4030957b409SSimon J. Gerraty		dup 0xC0 < uf drop 0 ret enduf
4040957b409SSimon J. Gerraty		dup 0xE0 < uf 0x1F and 1 read-UTF8-next 0x80 0x7FF enduf
4050957b409SSimon J. Gerraty		dup 0xF0 < uf 0x0F and 2 read-UTF8-next 0x800 0xFFFF enduf
4060957b409SSimon J. Gerraty		dup 0xF8 < uf 0x07 and 3 read-UTF8-next 0x10000 0x10FFFF enduf
4070957b409SSimon J. Gerraty		drop 0 ret
4080957b409SSimon J. Gerraty	endchoice
4090957b409SSimon J. Gerraty	between? ifnot drop 0 then
4100957b409SSimon J. Gerraty	;
4110957b409SSimon J. Gerraty
4120957b409SSimon J. Gerraty\ Read n subsequent bytes to complete the provided first byte. The final
4130957b409SSimon J. Gerraty\ value is -1 on error, or the code point numerical value. The final
4140957b409SSimon J. Gerraty\ value is duplicated.
4150957b409SSimon J. Gerraty: read-UTF8-next ( lim val n -- lim val val )
4160957b409SSimon J. Gerraty	begin dup while
4170957b409SSimon J. Gerraty		-rot
4180957b409SSimon J. Gerraty		read-UTF8-chunk
4190957b409SSimon J. Gerraty		rot 1-
4200957b409SSimon J. Gerraty	repeat
4210957b409SSimon J. Gerraty	drop dup ;
4220957b409SSimon J. Gerraty
4230957b409SSimon J. Gerraty\ Read one byte, that should be a trailing UTF-8 byte, and complement the
4240957b409SSimon J. Gerraty\ current value. On error, value is set to -1.
4250957b409SSimon J. Gerraty: read-UTF8-chunk ( lim val -- lim val )
4260957b409SSimon J. Gerraty	swap
4270957b409SSimon J. Gerraty	\ If we are at the end of the value, report an error but don't fail.
4280957b409SSimon J. Gerraty	dup ifnot 2drop 0 -1 ret then
4290957b409SSimon J. Gerraty	read8 rot
4300957b409SSimon J. Gerraty	dup 0< if swap drop ret then 6 <<
4310957b409SSimon J. Gerraty	swap dup 6 >> 2 <> if 2drop -1 ret then
4320957b409SSimon J. Gerraty	0x3F and + ;
4330957b409SSimon J. Gerraty
4340957b409SSimon J. Gerraty: high-surrogate? ( x -- x bool )
4350957b409SSimon J. Gerraty	dup 0xD800 0xDBFF between? ;
4360957b409SSimon J. Gerraty
4370957b409SSimon J. Gerraty: low-surrogate? ( x -- x bool )
4380957b409SSimon J. Gerraty	dup 0xDC00 0xDFFF between? ;
4390957b409SSimon J. Gerraty
4400957b409SSimon J. Gerraty: assemble-surrogate-pair ( hi lim lo -- lim val )
4410957b409SSimon J. Gerraty	low-surrogate? ifnot rot 2drop 0 ret then
4420957b409SSimon J. Gerraty	rot 10 << + 0x35FDC00 - ;
4430957b409SSimon J. Gerraty
4440957b409SSimon J. Gerraty\ Read a UTF-16 code point (big-endian). Returned value is 0 on error.
4450957b409SSimon J. Gerraty: read-UTF16BE ( lim -- lim val )
4460957b409SSimon J. Gerraty	read16be
4470957b409SSimon J. Gerraty	choice
4480957b409SSimon J. Gerraty		high-surrogate? uf
4490957b409SSimon J. Gerraty			swap dup ifnot 2drop 0 0 ret then
4500957b409SSimon J. Gerraty			read16be assemble-surrogate-pair
4510957b409SSimon J. Gerraty		enduf
4520957b409SSimon J. Gerraty		low-surrogate? uf
4530957b409SSimon J. Gerraty			drop 0
4540957b409SSimon J. Gerraty		enduf
4550957b409SSimon J. Gerraty	endchoice ;
4560957b409SSimon J. Gerraty
4570957b409SSimon J. Gerraty\ Read a UTF-16 code point (little-endian). Returned value is 0 on error.
4580957b409SSimon J. Gerraty: read-UTF16LE ( lim -- lim val )
4590957b409SSimon J. Gerraty	read16le
4600957b409SSimon J. Gerraty	choice
4610957b409SSimon J. Gerraty		high-surrogate? uf
4620957b409SSimon J. Gerraty			swap dup ifnot 2drop 0 0 ret then
4630957b409SSimon J. Gerraty			read16le assemble-surrogate-pair
4640957b409SSimon J. Gerraty		enduf
4650957b409SSimon J. Gerraty		low-surrogate? uf
4660957b409SSimon J. Gerraty			drop 0
4670957b409SSimon J. Gerraty		enduf
4680957b409SSimon J. Gerraty	endchoice ;
4690957b409SSimon J. Gerraty
4700957b409SSimon J. Gerraty\ Add byte to current pad value. Offset is updated, or set to 0 on error.
4710957b409SSimon J. Gerraty: pad-append ( off val -- off )
4720957b409SSimon J. Gerraty	over dup 0= swap 256 >= or if 2drop 0 ret then
4730957b409SSimon J. Gerraty	over addr-pad + set8 1+ ;
4740957b409SSimon J. Gerraty
4750957b409SSimon J. Gerraty\ Add UTF-8 chunk byte to the pad. The 'nn' parameter is the shift count.
4760957b409SSimon J. Gerraty: pad-append-UTF8-chunk ( off val nn -- off )
4770957b409SSimon J. Gerraty	>> 0x3F and 0x80 or pad-append ;
4780957b409SSimon J. Gerraty
4790957b409SSimon J. Gerraty\ Test whether a code point is invalid when encoding. This rejects the
4800957b409SSimon J. Gerraty\ 66 noncharacters, and also the surrogate range; this function does NOT
4810957b409SSimon J. Gerraty\ check that the value is in the 0..10FFFF range.
4820957b409SSimon J. Gerraty: valid-unicode? ( val -- bool )
483*cc9e6590SSimon J. Gerraty	dup 0xFDD0 0xFDEF between? if drop 0 ret then
4840957b409SSimon J. Gerraty	dup 0xD800 0xDFFF between? if drop 0 ret then
4850957b409SSimon J. Gerraty	0xFFFF and 0xFFFE < ;
4860957b409SSimon J. Gerraty
4870957b409SSimon J. Gerraty\ Encode a code point in UTF-8. Offset is in the pad; it is updated, or
4880957b409SSimon J. Gerraty\ set to 0 on error. Leading BOM are ignored.
4890957b409SSimon J. Gerraty: encode-UTF8 ( val off -- off )
4900957b409SSimon J. Gerraty	\ Skip leading BOM (U+FEFF when off is 1).
4910957b409SSimon J. Gerraty	dup2 1 = swap 0xFEFF = and if swap drop ret then
4920957b409SSimon J. Gerraty
4930957b409SSimon J. Gerraty	swap dup { val }
4940957b409SSimon J. Gerraty	dup valid-unicode? ifnot 2drop 0 ret then
4950957b409SSimon J. Gerraty	choice
4960957b409SSimon J. Gerraty		dup 0x80 < uf pad-append enduf
4970957b409SSimon J. Gerraty		dup 0x800 < uf
4980957b409SSimon J. Gerraty			6 >> 0xC0 or pad-append
4990957b409SSimon J. Gerraty			val 0 pad-append-UTF8-chunk
5000957b409SSimon J. Gerraty		enduf
5010957b409SSimon J. Gerraty		dup 0xFFFF < uf
5020957b409SSimon J. Gerraty			12 >> 0xE0 or pad-append
5030957b409SSimon J. Gerraty			val 6 pad-append-UTF8-chunk
5040957b409SSimon J. Gerraty			val 0 pad-append-UTF8-chunk
5050957b409SSimon J. Gerraty		enduf
5060957b409SSimon J. Gerraty		18 >> 0xF0 or pad-append
5070957b409SSimon J. Gerraty		val 12 pad-append-UTF8-chunk
5080957b409SSimon J. Gerraty		val 6 pad-append-UTF8-chunk
5090957b409SSimon J. Gerraty		val 0 pad-append-UTF8-chunk
5100957b409SSimon J. Gerraty	endchoice ;
5110957b409SSimon J. Gerraty
5120957b409SSimon J. Gerraty\ Read a string value into the pad; this function checks that the source
5130957b409SSimon J. Gerraty\ characters are UTF-8 and non-zero. The string length (in bytes) is
5140957b409SSimon J. Gerraty\ written in the first pad byte. Returned value is true (-1) on success,
5150957b409SSimon J. Gerraty\ false (0) on error.
5160957b409SSimon J. Gerraty: read-value-UTF8 ( lim -- lim bool )
5170957b409SSimon J. Gerraty	read-length-open-elt
5180957b409SSimon J. Gerraty	1 { off }
5190957b409SSimon J. Gerraty	begin dup while
5200957b409SSimon J. Gerraty		read-UTF8 dup ifnot drop skip-close-elt 0 ret then
5210957b409SSimon J. Gerraty		off encode-UTF8 >off
5220957b409SSimon J. Gerraty	repeat
5230957b409SSimon J. Gerraty	drop off dup ifnot ret then 1- addr-pad set8 -1 ;
5240957b409SSimon J. Gerraty
5250957b409SSimon J. Gerraty\ Decode a UTF-16 string into the pad. The string is converted to UTF-8,
5260957b409SSimon J. Gerraty\ and the length is written in the first pad byte. A leading BOM is
5270957b409SSimon J. Gerraty\ honoured (big-endian is assumed if there is no BOM). A code point of
5280957b409SSimon J. Gerraty\ value 0 is an error. Returned value is true (-1) on success, false (0)
5290957b409SSimon J. Gerraty\ on error.
5300957b409SSimon J. Gerraty: read-value-UTF16 ( lim -- lim bool )
5310957b409SSimon J. Gerraty	read-length-open-elt
5320957b409SSimon J. Gerraty	dup ifnot addr-pad set8 -1 ret then
5330957b409SSimon J. Gerraty	1 { off }
5340957b409SSimon J. Gerraty	read-UTF16BE dup 0xFFFE = if
5350957b409SSimon J. Gerraty		\ Leading BOM, and indicates little-endian.
5360957b409SSimon J. Gerraty		drop
5370957b409SSimon J. Gerraty		begin dup while
5380957b409SSimon J. Gerraty			read-UTF16LE dup ifnot drop skip-close-elt 0 ret then
5390957b409SSimon J. Gerraty			off encode-UTF8 >off
5400957b409SSimon J. Gerraty		repeat
5410957b409SSimon J. Gerraty	else
5420957b409SSimon J. Gerraty		dup ifnot drop skip-close-elt 0 ret then
5430957b409SSimon J. Gerraty		\ Big-endian BOM, or no BOM.
5440957b409SSimon J. Gerraty		begin
5450957b409SSimon J. Gerraty			off encode-UTF8 >off
5460957b409SSimon J. Gerraty			dup while
5470957b409SSimon J. Gerraty			read-UTF16BE dup ifnot drop skip-close-elt 0 ret then
5480957b409SSimon J. Gerraty		repeat
5490957b409SSimon J. Gerraty	then
5500957b409SSimon J. Gerraty	drop off dup ifnot ret then 1- addr-pad set8 -1 ;
5510957b409SSimon J. Gerraty
5520957b409SSimon J. Gerraty\ Decode a latin-1 string into the pad. The string is converted to UTF-8,
5530957b409SSimon J. Gerraty\ and the length is written in the first pad byte. A source byte of
5540957b409SSimon J. Gerraty\ value 0 is an error. Returned value is true (-1) on success, false (0)
5550957b409SSimon J. Gerraty\ on error.
5560957b409SSimon J. Gerraty: read-value-latin1 ( lim -- lim bool )
5570957b409SSimon J. Gerraty	read-length-open-elt
5580957b409SSimon J. Gerraty	1 { off }
5590957b409SSimon J. Gerraty	begin dup while
5600957b409SSimon J. Gerraty		read8 dup ifnot drop skip-close-elt 0 ret then
5610957b409SSimon J. Gerraty		off encode-UTF8 >off
5620957b409SSimon J. Gerraty	repeat
5630957b409SSimon J. Gerraty	drop off dup ifnot ret then 1- addr-pad set8 -1 ;
5640957b409SSimon J. Gerraty
5650957b409SSimon J. Gerraty\ Read a value and interpret it as an INTEGER or ENUMERATED value. If
5660957b409SSimon J. Gerraty\ the integer value does not fit on an unsigned 32-bit value, an error
5670957b409SSimon J. Gerraty\ is reported. This function assumes that the tag has just been read
5680957b409SSimon J. Gerraty\ and processed, but not the length.
5690957b409SSimon J. Gerraty: read-small-int-value ( lim -- lim x )
5700957b409SSimon J. Gerraty	read-length-open-elt
5710957b409SSimon J. Gerraty	dup ifnot ERR_X509_OVERFLOW fail then
5720957b409SSimon J. Gerraty	read8 dup 0x80 >= if ERR_X509_OVERFLOW fail then
5730957b409SSimon J. Gerraty	{ x }
5740957b409SSimon J. Gerraty	begin dup while
5750957b409SSimon J. Gerraty		read8 x dup 0xFFFFFF >= if ERR_X509_OVERFLOW fail then
5760957b409SSimon J. Gerraty		8 << + >x
5770957b409SSimon J. Gerraty	repeat
5780957b409SSimon J. Gerraty	drop x ;
5790957b409SSimon J. Gerraty
5800957b409SSimon J. Gerraty\ Compare the OID in the pad with an OID in the constant data block.
5810957b409SSimon J. Gerraty\ Returned value is -1 on equality, 0 otherwise.
5820957b409SSimon J. Gerratycc: eqOID ( addrConst -- bool ) {
5830957b409SSimon J. Gerraty	const unsigned char *a2 = &t0_datablock[T0_POP()];
5840957b409SSimon J. Gerraty	const unsigned char *a1 = &CTX->pad[0];
5850957b409SSimon J. Gerraty	size_t len = a1[0];
5860957b409SSimon J. Gerraty	int x;
5870957b409SSimon J. Gerraty	if (len == a2[0]) {
5880957b409SSimon J. Gerraty		x = -(memcmp(a1 + 1, a2 + 1, len) == 0);
5890957b409SSimon J. Gerraty	} else {
5900957b409SSimon J. Gerraty		x = 0;
5910957b409SSimon J. Gerraty	}
5920957b409SSimon J. Gerraty	T0_PUSH((uint32_t)x);
5930957b409SSimon J. Gerraty}
5940957b409SSimon J. Gerraty
5950957b409SSimon J. Gerraty\ Compare two blobs in the context. Returned value is -1 on equality, 0
5960957b409SSimon J. Gerraty\ otherwise.
5970957b409SSimon J. Gerratycc: eqblob ( addr1 addr2 len -- bool ) {
5980957b409SSimon J. Gerraty	size_t len = T0_POP();
5990957b409SSimon J. Gerraty	const unsigned char *a2 = (const unsigned char *)CTX + T0_POP();
6000957b409SSimon J. Gerraty	const unsigned char *a1 = (const unsigned char *)CTX + T0_POP();
6010957b409SSimon J. Gerraty	T0_PUSHi(-(memcmp(a1, a2, len) == 0));
6020957b409SSimon J. Gerraty}
6030957b409SSimon J. Gerraty
6040957b409SSimon J. Gerraty\ Check that a value is in a given range (inclusive).
6050957b409SSimon J. Gerraty: between? ( x min max -- bool )
6060957b409SSimon J. Gerraty	{ min max } dup min >= swap max <= and ;
6070957b409SSimon J. Gerraty
6080957b409SSimon J. Gerraty\ Convert the provided byte value into a number in the 0..9 range,
6090957b409SSimon J. Gerraty\ assuming that it is an ASCII digit. A non-digit triggers an error
6100957b409SSimon J. Gerraty\ (a "bad time" error since this is used in date/time decoding).
6110957b409SSimon J. Gerraty: digit-dec ( char -- value )
6120957b409SSimon J. Gerraty	`0 - dup 0 9 between? ifnot ERR_X509_BAD_TIME fail then ;
6130957b409SSimon J. Gerraty
6140957b409SSimon J. Gerraty\ Read two ASCII digits and return the value in the 0..99 range. An
6150957b409SSimon J. Gerraty\ error is reported if the characters are not ASCII digits.
6160957b409SSimon J. Gerraty: read-dec2 ( lim -- lim x )
6170957b409SSimon J. Gerraty	read8 digit-dec 10 * { x } read8 digit-dec x + ;
6180957b409SSimon J. Gerraty
6190957b409SSimon J. Gerraty\ Read two ASCII digits and check that the value is in the provided
6200957b409SSimon J. Gerraty\ range (inclusive).
6210957b409SSimon J. Gerraty: read-dec2-range ( lim min max -- lim x )
6220957b409SSimon J. Gerraty	{ min max }
6230957b409SSimon J. Gerraty	read-dec2 dup min max between? ifnot ERR_X509_BAD_TIME fail then ;
6240957b409SSimon J. Gerraty
6250957b409SSimon J. Gerraty\ Maximum days in a month and accumulated day count. Each
6260957b409SSimon J. Gerraty\ 16-bit value contains the month day count in its lower 5 bits. The first
6270957b409SSimon J. Gerraty\ 12 values are for a normal year, the other 12 for a leap year.
6280957b409SSimon J. Gerratydata: month-to-days
6290957b409SSimon J. Gerratyhexb| 001F 03FC 077F 0B5E 0F1F 12FE 16BF 1A9F 1E7E 223F 261E 29DF |
6300957b409SSimon J. Gerratyhexb| 001F 03FD 079F 0B7E 0F3F 131E 16DF 1ABF 1E9E 225F 263E 29FF |
6310957b409SSimon J. Gerraty
6320957b409SSimon J. Gerraty\ Read a date (UTCTime or GeneralizedTime). The date value is converted
6330957b409SSimon J. Gerraty\ to a day count and a second count. The day count starts at 0 for
6340957b409SSimon J. Gerraty\ January 1st, 0 AD (that's they year before 1 AD, also known as 1 BC)
6350957b409SSimon J. Gerraty\ in a proleptic Gregorian calendar (i.e. Gregorian rules are assumed to
6360957b409SSimon J. Gerraty\ extend indefinitely in the past). The second count is between 0 and
6370957b409SSimon J. Gerraty\ 86400 (inclusive, in case of a leap second).
6380957b409SSimon J. Gerraty: read-date ( lim -- lim days seconds )
6390957b409SSimon J. Gerraty	\ Read tag; must be UTCTime or GeneralizedTime. Year count is
6400957b409SSimon J. Gerraty	\ 4 digits with GeneralizedTime, 2 digits with UTCTime.
6410957b409SSimon J. Gerraty	read-tag
6420957b409SSimon J. Gerraty	dup 0x17 0x18 between? ifnot ERR_X509_BAD_TIME fail then
6430957b409SSimon J. Gerraty	0x18 = { y4d }
6440957b409SSimon J. Gerraty	check-primitive
6450957b409SSimon J. Gerraty	read-length-open-elt
6460957b409SSimon J. Gerraty
6470957b409SSimon J. Gerraty	\ We compute the days and seconds counts during decoding, in
6480957b409SSimon J. Gerraty	\ order to minimize the number of needed temporary variables.
6490957b409SSimon J. Gerraty	{ ; days seconds x }
6500957b409SSimon J. Gerraty
6510957b409SSimon J. Gerraty	\ Year is 4-digit with GeneralizedTime. With UTCTime, the year
6520957b409SSimon J. Gerraty	\ is in the 1950..2049 range, and only the last two digits are
6530957b409SSimon J. Gerraty	\ present in the encoding.
6540957b409SSimon J. Gerraty	read-dec2
6550957b409SSimon J. Gerraty	y4d if
6560957b409SSimon J. Gerraty		100 * >x read-dec2 x +
6570957b409SSimon J. Gerraty	else
6580957b409SSimon J. Gerraty		dup 50 < if 100 + then 1900 +
6590957b409SSimon J. Gerraty	then
6600957b409SSimon J. Gerraty	>x
6610957b409SSimon J. Gerraty	x 365 * x 3 + 4 / + x 99 + 100 / - x 399 + 400 / + >days
6620957b409SSimon J. Gerraty
6630957b409SSimon J. Gerraty	\ Month is 1..12. Number of days in a months depend on the
6640957b409SSimon J. Gerraty	\ month and on the year (year count is in x at that point).
6650957b409SSimon J. Gerraty	1 12 read-dec2-range
6660957b409SSimon J. Gerraty	1- 1 <<
6670957b409SSimon J. Gerraty	x 4 % 0= x 100 % 0<> x 400 % 0= or and if 24 + then
6680957b409SSimon J. Gerraty	month-to-days + data-get16
6690957b409SSimon J. Gerraty	dup 5 >> days + >days
6700957b409SSimon J. Gerraty	0x1F and
6710957b409SSimon J. Gerraty
6720957b409SSimon J. Gerraty	\ Day. At this point, the TOS contains the maximum day count for
6730957b409SSimon J. Gerraty	\ the current month.
6740957b409SSimon J. Gerraty	1 swap read-dec2-range
6750957b409SSimon J. Gerraty	days + 1- >days
6760957b409SSimon J. Gerraty
6770957b409SSimon J. Gerraty	\ Hour, minute and seconds. Count of seconds is allowed to go to
6780957b409SSimon J. Gerraty	\ 60 in case of leap seconds (in practice, leap seconds really
6790957b409SSimon J. Gerraty	\ occur only at the very end of the day, so this computation is
6800957b409SSimon J. Gerraty	\ exact for a real leap second, and a spurious leap second only
6810957b409SSimon J. Gerraty	\ implies a one-second shift that we can ignore).
6820957b409SSimon J. Gerraty	0 23 read-dec2-range 3600 * >seconds
6830957b409SSimon J. Gerraty	0 59 read-dec2-range 60 * seconds + >seconds
6840957b409SSimon J. Gerraty	0 60 read-dec2-range seconds + >seconds
6850957b409SSimon J. Gerraty
6860957b409SSimon J. Gerraty	\ At this point, we may have fractional seconds. This should
6870957b409SSimon J. Gerraty	\ happen only with GeneralizedTime, but we accept it for UTCTime
6880957b409SSimon J. Gerraty	\ too (and, anyway, we ignore these fractional seconds).
6890957b409SSimon J. Gerraty	read8 dup `. = if
6900957b409SSimon J. Gerraty		drop
6910957b409SSimon J. Gerraty		begin read8 dup `0 `9 between? while drop repeat
6920957b409SSimon J. Gerraty	then
6930957b409SSimon J. Gerraty
6940957b409SSimon J. Gerraty	\ The time zone should be 'Z', not followed by anything. Other
6950957b409SSimon J. Gerraty	\ time zone indications are not DER and thus not supposed to
6960957b409SSimon J. Gerraty	\ appear in certificates.
6970957b409SSimon J. Gerraty	`Z <> if ERR_X509_BAD_TIME fail then
6980957b409SSimon J. Gerraty	close-elt
6990957b409SSimon J. Gerraty	days seconds ;
7000957b409SSimon J. Gerraty
7010957b409SSimon J. Gerraty\ Read an INTEGER (tag, length and value). The INTEGER is supposed to be
7020957b409SSimon J. Gerraty\ positive; its unsigned big-endian encoding is stored in the provided
7030957b409SSimon J. Gerraty\ in-context buffer. Returned value is the decoded length. If the integer
7040957b409SSimon J. Gerraty\ did not fit, or the value is negative, then an error is reported.
7050957b409SSimon J. Gerraty: read-integer ( lim addr len -- lim dlen )
7060957b409SSimon J. Gerraty	rot read-tag 0x02 check-tag-primitive -rot
7070957b409SSimon J. Gerraty	read-integer-next ;
7080957b409SSimon J. Gerraty
7090957b409SSimon J. Gerraty\ Identical to read-integer, but the tag has already been read and checked.
7100957b409SSimon J. Gerraty: read-integer-next ( lim addr len -- lim dlen )
7110957b409SSimon J. Gerraty	dup { addr len origlen }
7120957b409SSimon J. Gerraty	read-length-open-elt
7130957b409SSimon J. Gerraty	\ Read first byte; sign bit must be 0.
7140957b409SSimon J. Gerraty	read8 dup 0x80 >= if ERR_X509_OVERFLOW fail then
7150957b409SSimon J. Gerraty	\ Skip leading bytes of value 0. If there are only bytes of
7160957b409SSimon J. Gerraty	\ value 0, then return.
7170957b409SSimon J. Gerraty	begin dup 0 = while
7180957b409SSimon J. Gerraty		drop dup ifnot drop 0 ret then
7190957b409SSimon J. Gerraty		read8
7200957b409SSimon J. Gerraty	repeat
7210957b409SSimon J. Gerraty	\ At that point, we have the first non-zero byte on the stack.
7220957b409SSimon J. Gerraty	begin
7230957b409SSimon J. Gerraty		len dup ifnot ERR_X509_LIMIT_EXCEEDED fail then 1- >len
7240957b409SSimon J. Gerraty		addr set8 addr 1+ >addr
7250957b409SSimon J. Gerraty		dup while read8
7260957b409SSimon J. Gerraty	repeat
7270957b409SSimon J. Gerraty	drop origlen len - ;
7280957b409SSimon J. Gerraty
7290957b409SSimon J. Gerraty\ Read a BOOLEAN value. This should be called immediately after reading
7300957b409SSimon J. Gerraty\ the tag.
7310957b409SSimon J. Gerraty: read-boolean ( lim constructed value -- lim bool )
7320957b409SSimon J. Gerraty	0x01 check-tag-primitive
7330957b409SSimon J. Gerraty	read-length 1 <> if ERR_X509_BAD_BOOLEAN fail then
7340957b409SSimon J. Gerraty	read8 0<> ;
7350957b409SSimon J. Gerraty
7360957b409SSimon J. Gerraty\ Identify an elliptic curve: read the OID, then check it against the
7370957b409SSimon J. Gerraty\ known curve OID.
7380957b409SSimon J. Gerraty: read-curve-ID ( lim -- lim curve )
7390957b409SSimon J. Gerraty	read-OID ifnot ERR_X509_UNSUPPORTED fail then
7400957b409SSimon J. Gerraty	choice
7410957b409SSimon J. Gerraty		ansix9p256r1 eqOID uf 23 enduf
7420957b409SSimon J. Gerraty		ansix9p384r1 eqOID uf 24 enduf
7430957b409SSimon J. Gerraty		ansix9p521r1 eqOID uf 25 enduf
7440957b409SSimon J. Gerraty		ERR_X509_UNSUPPORTED fail
7450957b409SSimon J. Gerraty	endchoice ;
7460957b409SSimon J. Gerraty
7470957b409SSimon J. Gerraty\ A convenient debug word: print the current data stack contents.
7480957b409SSimon J. Gerratycc: DEBUG ( -- ) {
7490957b409SSimon J. Gerraty	extern int printf(const char *fmt, ...);
7500957b409SSimon J. Gerraty	uint32_t *p;
7510957b409SSimon J. Gerraty
7520957b409SSimon J. Gerraty	printf("<stack:");
7530957b409SSimon J. Gerraty	for (p = &CTX->dp_stack[0]; p != dp; p ++) {
7540957b409SSimon J. Gerraty		printf(" %lu", (unsigned long)*p);
7550957b409SSimon J. Gerraty	}
7560957b409SSimon J. Gerraty	printf(" >\n");
7570957b409SSimon J. Gerraty}
758