Skip to content

Commit

Permalink
PORT: MSVC
Browse files Browse the repository at this point in the history
More portable types and avoid possible overflows by using size_t
  • Loading branch information
JanWielemaker committed Aug 29, 2023
1 parent 2692749 commit 6de472f
Show file tree
Hide file tree
Showing 8 changed files with 35 additions and 32 deletions.
18 changes: 9 additions & 9 deletions parser.c
Original file line number Diff line number Diff line change
Expand Up @@ -105,7 +105,7 @@ static int process_entity(dtd_parser *p, const ichar *name);
static int emit_cdata(dtd_parser *p, int last);
static dtd_space_mode istr_to_space_mode(const ichar *val);
static void update_space_mode(dtd_parser *p, dtd_element *e,
int natts, sgml_attribute *atts);
size_t natts, sgml_attribute *atts);
static dtd_model * make_model(dtd_parser *p, const ichar *decl,
const ichar **end);
static void for_elements_in_model(dtd_model *m,
Expand Down Expand Up @@ -3211,7 +3211,7 @@ get_attribute_value(dtd_parser *p, ichar const *decl, sgml_attribute *att)
{ (void) istrtol(buf, &att->value.number);
} else
{ att->value.textW = istrdup(buf);
att->value.number = (long)istrlen(buf);
att->value.number = istrlen(buf);
}
return end;
case AT_CDATA: /* CDATA attribute */
Expand Down Expand Up @@ -3446,7 +3446,7 @@ add_default_attributes(dtd_parser *p, dtd_element *e,


static void
free_attribute_values(int argc, sgml_attribute *argv)
free_attribute_values(size_t argc, sgml_attribute *argv)
{ int i;

for(i=0; i<argc; i++, argv++)
Expand Down Expand Up @@ -4216,7 +4216,7 @@ istr_to_space_mode(const ichar *val)

static void
update_space_mode(dtd_parser *p, dtd_element *e,
int natts, sgml_attribute *atts)
size_t natts, sgml_attribute *atts)
{ for( ; natts-- > 0; atts++ )
{ const ichar *name = atts->definition->name->name;

Expand Down Expand Up @@ -4250,7 +4250,7 @@ empty_cdata(dtd_parser *p)


static void
cb_cdata(dtd_parser *p, ocharbuf *buf, int offset, int size)
cb_cdata(dtd_parser *p, ocharbuf *buf, size_t offset, size_t size)
{ if ( p->on_data )
(*p->on_data)(p, EC_CDATA, size, buf->data.w+offset);
}
Expand All @@ -4261,8 +4261,8 @@ emit_cdata(dtd_parser *p, int last)
{ dtd *dtd = p->dtd;
locbuf locsafe;
ocharbuf *cdata = p->cdata;
int offset = 0;
int size = cdata->size;
size_t offset = 0;
size_t size = cdata->size;

if ( size == 0 )
return TRUE; /* empty or done */
Expand Down Expand Up @@ -4768,7 +4768,7 @@ add_cdata(dtd_parser *p, int chr)

if ( chr == '\n' &&
p->environments && p->environments->space_mode != SP_STRICT )
{ int sz; /* insert missing CR */
{ size_t sz; /* insert missing CR */

if ( (sz=buf->size) == 0 ||
fetch_ocharbuf(buf, sz-1) != CR )
Expand All @@ -4785,7 +4785,7 @@ add_cdata(dtd_parser *p, int chr)
/* dubious. Should we do that here or in space-handling? */
if ( chr == '\n' &&
p->environments && p->environments->space_mode != SP_STRICT )
{ int sz;
{ size_t sz;

if ( (sz=buf->size) > 1 &&
fetch_ocharbuf(buf, sz-1) == LF &&
Expand Down
8 changes: 4 additions & 4 deletions parser.h
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@
typedef struct _sgml_attribute
{ struct /* so we can free members */
{ wchar_t *textW; /* UCS textual value */
long number; /* numeric value/length */
intptr_t number; /* numeric value/length */
} value;
dtd_attr *definition; /* DTD definition */
unsigned flags; /* additional flags */
Expand All @@ -57,14 +57,14 @@ typedef struct _dtd_parser *dtd_parser_p;

typedef int (*sgml_begin_element_f)(dtd_parser_p parser,
dtd_element *e,
int argc,
size_t argc,
sgml_attribute *argv);
typedef int (*sgml_end_element_f)(dtd_parser_p parser,
dtd_element *e);
typedef int (*sgml_data_f)(dtd_parser_p parser,
data_type type, int len, const wchar_t *text);
data_type type, size_t len, const wchar_t *text);
typedef int (*sgml_wdata_f)(dtd_parser_p parser,
data_type type, int len, const wchar_t *text);
data_type type, size_t len, const wchar_t *text);
typedef int (*sgml_entity_f)(dtd_parser_p parser,
dtd_entity *entity,
int chr);
Expand Down
18 changes: 9 additions & 9 deletions sgml2pl.c
Original file line number Diff line number Diff line change
Expand Up @@ -282,7 +282,7 @@ initConstants()
ATOM_position = PL_new_atom("#position");
}

static int on_data(dtd_parser *p, data_type type, int len, const wchar_t *data);
static int on_data(dtd_parser *p, data_type type, size_t len, const wchar_t *data);


/*******************************
Expand Down Expand Up @@ -1091,7 +1091,7 @@ put_attribute_value(dtd_parser *p, term_t t, sgml_attribute *a)
return put_att_text(p, t, a);
case AT_NUMBER:
{ if ( !put_att_text(p, t, a) )
return PL_put_integer(t, a->value.number);
return PL_put_int64(t, a->value.number);
return TRUE;
}
default: /* multi-valued attribute */
Expand Down Expand Up @@ -1151,8 +1151,8 @@ put_tag_position(dtd_parser *p, term_t pos)

WUNUSED static int
unify_attribute_list(dtd_parser *p, term_t alist,
int argc, sgml_attribute *argv)
{ int i;
size_t argc, sgml_attribute *argv)
{ size_t i;
term_t tail = PL_copy_term_ref(alist);
term_t h = PL_new_term_ref();
term_t a = PL_new_term_refs(2);
Expand Down Expand Up @@ -1188,7 +1188,7 @@ unify_attribute_list(dtd_parser *p, term_t alist,


static int
on_begin_(dtd_parser *p, dtd_element *e, int argc, sgml_attribute *argv)
on_begin_(dtd_parser *p, dtd_element *e, size_t argc, sgml_attribute *argv)
{ parser_data *pd = p->closure;

if ( pd->stopped )
Expand Down Expand Up @@ -1375,7 +1375,7 @@ on_entity_(dtd_parser *p, dtd_entity *e, int chr)


static int
on_data_(dtd_parser *p, data_type type, int len, const wchar_t *data)
on_data_(dtd_parser *p, data_type type, size_t len, const wchar_t *data)
{ parser_data *pd = p->closure;

if ( pd->on_cdata )
Expand Down Expand Up @@ -1445,7 +1445,7 @@ on_data_(dtd_parser *p, data_type type, int len, const wchar_t *data)


static int
on_cdata(dtd_parser *p, data_type type, int len, const wchar_t *data)
on_cdata(dtd_parser *p, data_type type, size_t len, const wchar_t *data)
{ return on_data(p, type, len, data);
}

Expand Down Expand Up @@ -1722,7 +1722,7 @@ on_decl(dtd_parser *p, const ichar *decl)


static int
on_begin(dtd_parser *p, dtd_element *e, int argc, sgml_attribute *argv)
on_begin(dtd_parser *p, dtd_element *e, size_t argc, sgml_attribute *argv)
{ int rc;

PL_STRINGS_MARK();
Expand All @@ -1733,7 +1733,7 @@ on_begin(dtd_parser *p, dtd_element *e, int argc, sgml_attribute *argv)
}

static int
on_data(dtd_parser *p, data_type type, int len, const wchar_t *data)
on_data(dtd_parser *p, data_type type, size_t len, const wchar_t *data)
{ int rc;

PL_STRINGS_MARK();
Expand Down
8 changes: 4 additions & 4 deletions util.c
Original file line number Diff line number Diff line change
Expand Up @@ -260,14 +260,14 @@ istrcasehash(const ichar *t, int tsize)


int
istrtol(const ichar *s, long *val)
{ long v;
istrtol(const ichar *s, intptr_t *val)
{ long long v;
ichar *e;

if ( *s )
{ v = wcstol(s, &e, 10);
{ v = wcstoll(s, &e, 10);
if ( !e[0] && errno != ERANGE )
{ *val = v;
{ *val = (intptr_t)v;
return TRUE;
}
}
Expand Down
6 changes: 4 additions & 2 deletions util.h
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,8 @@
Author: Jan Wielemaker
E-mail: [email protected]
WWW: http://www.swi-prolog.org
Copyright (c) 2000-2014, University of Amsterdam
Copyright (c) 2000-2023, University of Amsterdam
SWI-Prolog Solutions b.v.
All rights reserved.
Redistribution and use in source and binary forms, with or without
Expand Down Expand Up @@ -38,6 +39,7 @@

#include <stdio.h>
#include <sys/types.h>
#include <stdint.h>
#include <wchar.h>

#ifdef _WINDOWS /* get size_t */
Expand Down Expand Up @@ -78,7 +80,7 @@ int istrncaseeq(const ichar *s1, const ichar *s2, int len);
int istrhash(const ichar *t, int tsize);
int istrcasehash(const ichar *t, int tsize);
ichar * istrchr(const ichar *s, int c);
int istrtol(const ichar *s, long *val);
int istrtol(const ichar *s, intptr_t *val);
void * sgml_malloc(size_t size);
void * sgml_calloc(size_t n, size_t size);
void sgml_free(void *mem);
Expand Down
5 changes: 3 additions & 2 deletions xmlns.c
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,8 @@
Author: Jan Wielemaker
E-mail: [email protected]
WWW: http://www.swi-prolog.org
Copyright (c) 2000-2011, University of Amsterdam
Copyright (c) 2000-2023, University of Amsterdam
SWI-Prolog Solutions b.v.
All rights reserved.
Redistribution and use in source and binary forms, with or without
Expand Down Expand Up @@ -111,7 +112,7 @@ isxmlns(const ichar *s, int nschr)


void
update_xmlns(dtd_parser *p, dtd_element *e, int natts, sgml_attribute *atts)
update_xmlns(dtd_parser *p, dtd_element *e, size_t natts, sgml_attribute *atts)
{ dtd_attr_list *al;
int nschr = p->dtd->charfunc->func[CF_NS]; /* : */

Expand Down
2 changes: 1 addition & 1 deletion xmlns.h
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,7 @@ void xmlns_free(xmlns *list);
xmlns* xmlns_find(dtd_parser *p, dtd_symbol *ns);
xmlns * xmlns_push(dtd_parser *p, const ichar *ns, const ichar *url);
void update_xmlns(dtd_parser *p, dtd_element *e,
int natts, sgml_attribute *atts);
size_t natts, sgml_attribute *atts);
int xmlns_resolve_attribute(dtd_parser *p, dtd_symbol *id,
const ichar **local, const ichar **url, const ichar **prefix);
int xmlns_resolve_element(dtd_parser *p,
Expand Down
2 changes: 1 addition & 1 deletion xsd.c
Original file line number Diff line number Diff line change
Expand Up @@ -178,7 +178,7 @@ xsd_number_string(term_t number, term_t string)
} else
{ char *dp = strchr(s, '.');
if ( dp-s > 1 )
{ exp_shift = dp-s-1;
{ exp_shift = (int)(dp-s-1);
memmove(&s[2], &s[1], exp_shift);
s[1] = '.';
}
Expand Down

0 comments on commit 6de472f

Please sign in to comment.