source: trunk/libs/newlib/src/newlib/libc/stdlib/wcstol.c @ 543

Last change on this file since 543 was 444, checked in by satin@…, 6 years ago

add newlib,libalmos-mkh, restructure shared_syscalls.h and mini-libc

File size: 8.0 KB
Line 
1/*
2FUNCTION
3   <<wcstol>>, <<wcstol_l>>---wide string to long
4
5INDEX
6        wcstol
7
8INDEX
9        wcstol_l
10
11INDEX
12        _wcstol_r
13
14SYNOPSIS
15        #include <wchar.h>
16        long wcstol(const wchar_t *__restrict <[s]>,
17                    wchar_t **__restrict <[ptr]>, int <[base]>);
18
19        #include <wchar.h>
20        long wcstol_l(const wchar_t *__restrict <[s]>,
21                      wchar_t **__restrict <[ptr]>, int <[base]>,
22                      locale_t <[locale]>);
23
24        long _wcstol_r(void *<[reent]>, const wchar_t *<[s]>,
25                       wchar_t **<[ptr]>, int <[base]>);
26
27DESCRIPTION
28The function <<wcstol>> converts the wide string <<*<[s]>>> to
29a <<long>>. First, it breaks down the string into three parts:
30leading whitespace, which is ignored; a subject string consisting
31of characters resembling an integer in the radix specified by <[base]>;
32and a trailing portion consisting of zero or more unparseable characters,
33and always including the terminating null character. Then, it attempts
34to convert the subject string into a <<long>> and returns the
35result.
36
37If the value of <[base]> is 0, the subject string is expected to look
38like a normal C integer constant: an optional sign, a possible `<<0x>>'
39indicating a hexadecimal base, and a number. If <[base]> is between
402 and 36, the expected form of the subject is a sequence of letters
41and digits representing an integer in the radix specified by <[base]>,
42with an optional plus or minus sign. The letters <<a>>--<<z>> (or,
43equivalently, <<A>>--<<Z>>) are used to signify values from 10 to 35;
44only letters whose ascribed values are less than <[base]> are
45permitted. If <[base]> is 16, a leading <<0x>> is permitted.
46
47The subject sequence is the longest initial sequence of the input
48string that has the expected form, starting with the first
49non-whitespace character.  If the string is empty or consists entirely
50of whitespace, or if the first non-whitespace character is not a
51permissible letter or digit, the subject string is empty.
52
53If the subject string is acceptable, and the value of <[base]> is zero,
54<<wcstol>> attempts to determine the radix from the input string. A
55string with a leading <<0x>> is treated as a hexadecimal value; a string with
56a leading 0 and no <<x>> is treated as octal; all other strings are
57treated as decimal. If <[base]> is between 2 and 36, it is used as the
58conversion radix, as described above. If the subject string begins with
59a minus sign, the value is negated. Finally, a pointer to the first
60character past the converted subject string is stored in <[ptr]>, if
61<[ptr]> is not <<NULL>>.
62
63If the subject string is empty (or not in acceptable form), no conversion
64is performed and the value of <[s]> is stored in <[ptr]> (if <[ptr]> is
65not <<NULL>>).
66
67The alternate function <<_wcstol_r>> is a reentrant version.  The
68extra argument <[reent]> is a pointer to a reentrancy structure.
69
70<<wcstol_l>> is like <<wcstol>> but performs the conversion based on the
71locale specified by the locale object locale.  If <[locale]> is
72LC_GLOBAL_LOCALE or not a valid locale object, the behaviour is undefined.
73
74RETURNS
75<<wcstol>>, <<wcstol_l>> return the converted value, if any. If no
76conversion was made, 0 is returned.
77
78<<wcstol>>, <<wcstol_l>> return <<LONG_MAX>> or <<LONG_MIN>> if the
79magnitude of the converted value is too large, and sets <<errno>>
80to <<ERANGE>>.
81
82PORTABILITY
83<<wcstol>> is ANSI.
84<<wcstol_l>> is a GNU extension.
85
86No supporting OS subroutines are required.
87*/
88
89/*-
90 * Copyright (c) 1990 The Regents of the University of California.
91 * All rights reserved.
92 *
93 * Redistribution and use in source and binary forms, with or without
94 * modification, are permitted provided that the following conditions
95 * are met:
96 * 1. Redistributions of source code must retain the above copyright
97 *    notice, this list of conditions and the following disclaimer.
98 * 2. Redistributions in binary form must reproduce the above copyright
99 *    notice, this list of conditions and the following disclaimer in the
100 *    documentation and/or other materials provided with the distribution.
101 * 3. All advertising materials mentioning features or use of this software
102 *    must display the following acknowledgement:
103 *      This product includes software developed by the University of
104 *      California, Berkeley and its contributors.
105 * 4. Neither the name of the University nor the names of its contributors
106 *    may be used to endorse or promote products derived from this software
107 *    without specific prior written permission.
108 *
109 * THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
110 * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
111 * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
112 * ARE DISCLAIMED.  IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
113 * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
114 * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
115 * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
116 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
117 * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
118 * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
119 * SUCH DAMAGE.
120 */
121
122
123#include <_ansi.h>
124#include <limits.h>
125#include <wctype.h>
126#include <errno.h>
127#include <wchar.h>
128#include <reent.h>
129#include "../locale/setlocale.h"
130
131/*
132 * Convert a wide string to a long integer.
133 */
134static long
135_wcstol_l (struct _reent *rptr, const wchar_t *nptr, wchar_t **endptr,
136           int base, locale_t loc)
137{
138        register const wchar_t *s = nptr;
139        register unsigned long acc;
140        register int c;
141        register unsigned long cutoff;
142        register int neg = 0, any, cutlim;
143
144        /*
145         * Skip white space and pick up leading +/- sign if any.
146         * If base is 0, allow 0x for hex and 0 for octal, else
147         * assume decimal; if base is already 16, allow 0x.
148         */
149        do {
150                c = *s++;
151        } while (iswspace_l(c, loc));
152        if (c == L'-') {
153                neg = 1;
154                c = *s++;
155        } else if (c == L'+')
156                c = *s++;
157        if ((base == 0 || base == 16) &&
158            c == L'0' && (*s == L'x' || *s == L'X')) {
159                c = s[1];
160                s += 2;
161                base = 16;
162        }
163        if (base == 0)
164                base = c == L'0' ? 8 : 10;
165
166        /*
167         * Compute the cutoff value between legal numbers and illegal
168         * numbers.  That is the largest legal value, divided by the
169         * base.  An input number that is greater than this value, if
170         * followed by a legal input character, is too big.  One that
171         * is equal to this value may be valid or not; the limit
172         * between valid and invalid numbers is then based on the last
173         * digit.  For instance, if the range for longs is
174         * [-2147483648..2147483647] and the input base is 10,
175         * cutoff will be set to 214748364 and cutlim to either
176         * 7 (neg==0) or 8 (neg==1), meaning that if we have accumulated
177         * a value > 214748364, or equal but the next digit is > 7 (or 8),
178         * the number is too big, and we will return a range error.
179         *
180         * Set any if any `digits' consumed; make it negative to indicate
181         * overflow.
182         */
183        cutoff = neg ? -(unsigned long)LONG_MIN : LONG_MAX;
184        cutlim = cutoff % (unsigned long)base;
185        cutoff /= (unsigned long)base;
186        for (acc = 0, any = 0;; c = *s++) {
187                if (c >= L'0' && c <= L'9')
188                        c -= L'0';
189                else if (c >= L'A' && c <= L'Z')
190                        c -= L'A' - 10;
191                else if (c >= L'a' && c <= L'z')
192                        c -= L'a' - 10;
193                else
194                        break;
195                if (c >= base)
196                        break;
197               if (any < 0 || acc > cutoff || (acc == cutoff && c > cutlim))
198                        any = -1;
199                else {
200                        any = 1;
201                        acc *= base;
202                        acc += c;
203                }
204        }
205        if (any < 0) {
206                acc = neg ? LONG_MIN : LONG_MAX;
207                rptr->_errno = ERANGE;
208        } else if (neg)
209                acc = -acc;
210        if (endptr != 0)
211                *endptr = (wchar_t *) (any ? s - 1 : nptr);
212        return (acc);
213}
214
215long
216_wcstol_r (struct _reent *rptr,
217        const wchar_t *nptr,
218        wchar_t **endptr,
219        int base)
220{
221        return _wcstol_l (rptr, nptr, endptr, base, __get_current_locale ());
222}
223
224#ifndef _REENT_ONLY
225
226long
227wcstol_l (const wchar_t *__restrict s, wchar_t **__restrict ptr, int base,
228          locale_t loc)
229{
230        return _wcstol_l (_REENT, s, ptr, base, loc);
231}
232
233long
234wcstol (const wchar_t *__restrict s,
235        wchar_t **__restrict ptr,
236        int base)
237{
238        return _wcstol_l (_REENT, s, ptr, base, __get_current_locale ());
239}
240
241#endif
Note: See TracBrowser for help on using the repository browser.