123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908 |
- {
- $Id$
- This file is part of the Free Pascal run time library.
- Copyright (c) 1999-2000 by the Free Pascal development team
- See the file COPYING.FPC, included in this distribution,
- for details about the copyright.
- This program is distributed in the hope that it will be useful,
- but WITHOUT ANY WARRANTY; without even the implied warranty of
- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
- **********************************************************************}
- {****************************************************************************
- subroutines for string handling
- ****************************************************************************}
- {$ifndef INTERNSETLENGTH}
- procedure SetLength(var s:shortstring;len:SizeInt);
- {$else INTERNSETLENGTH}
- procedure fpc_Shortstr_SetLength(var s:shortstring;len:SizeInt);[Public,Alias : 'FPC_SHORTSTR_SETLENGTH']; {$ifdef hascompilerproc} compilerproc; {$endif}
- {$endif INTERNSETLENGTH}
- begin
- if Len>255 then
- Len:=255;
- s[0]:=chr(len);
- end;
- {$ifdef interncopy}
- function fpc_shortstr_copy(const s : shortstring;index : SizeInt;count : SizeInt): shortstring;compilerproc;
- {$else}
- function copy(const s : shortstring;index : SizeInt;count : SizeInt): shortstring;
- {$endif}
- begin
- if count<0 then
- count:=0;
- if index>1 then
- dec(index)
- else
- index:=0;
- if index>length(s) then
- count:=0
- else
- if count>length(s)-index then
- count:=length(s)-index;
- {$ifdef interncopy}
- fpc_shortstr_Copy[0]:=chr(Count);
- Move(s[Index+1],fpc_shortstr_Copy[1],Count);
- {$else}
- Copy[0]:=chr(Count);
- Move(s[Index+1],Copy[1],Count);
- {$endif}
- end;
- procedure delete(var s : shortstring;index : SizeInt;count : SizeInt);
- begin
- if index<=0 then
- exit;
- if (Index<=Length(s)) and (Count>0) then
- begin
- if Count>length(s)-Index then
- Count:=length(s)-Index+1;
- s[0]:=Chr(length(s)-Count);
- if Index<=Length(s) then
- Move(s[Index+Count],s[Index],Length(s)-Index+1);
- end;
- end;
- procedure insert(const source : shortstring;var s : shortstring;index : SizeInt);
- var
- cut,srclen,indexlen : longint;
- begin
- if index<1 then
- index:=1;
- if index>length(s) then
- index:=length(s)+1;
- indexlen:=Length(s)-Index+1;
- srclen:=length(Source);
- if length(source)+length(s)>=sizeof(s) then
- begin
- cut:=length(source)+length(s)-sizeof(s)+1;
- if cut>indexlen then
- begin
- dec(srclen,cut-indexlen);
- indexlen:=0;
- end
- else
- dec(indexlen,cut);
- end;
- move(s[Index],s[Index+srclen],indexlen);
- move(Source[1],s[Index],srclen);
- s[0]:=chr(index+srclen+indexlen-1);
- end;
- procedure insert(source : Char;var s : shortstring;index : SizeInt);
- var
- indexlen : longint;
- begin
- if index<1 then
- index:=1;
- if index>length(s) then
- index:=length(s)+1;
- indexlen:=Length(s)-Index+1;
- if (length(s)+1=sizeof(s)) and (indexlen>0) then
- dec(indexlen);
- move(s[Index],s[Index+1],indexlen);
- s[Index]:=Source;
- s[0]:=chr(index+indexlen);
- end;
- function pos(const substr : shortstring;const s : shortstring):SizeInt;
- var
- i,MaxLen : SizeInt;
- pc : pchar;
- begin
- Pos:=0;
- if Length(SubStr)>0 then
- begin
- MaxLen:=Length(s)-Length(SubStr);
- i:=0;
- pc:=@s[1];
- while (i<=MaxLen) do
- begin
- inc(i);
- if (SubStr[1]=pc^) and
- (CompareChar(Substr[1],pc^,Length(SubStr))=0) then
- begin
- Pos:=i;
- exit;
- end;
- inc(pc);
- end;
- end;
- end;
- {Faster when looking for a single char...}
- function pos(c:char;const s:shortstring):SizeInt;
- var
- i : SizeInt;
- pc : pchar;
- begin
- pc:=@s[1];
- for i:=1 to length(s) do
- begin
- if pc^=c then
- begin
- pos:=i;
- exit;
- end;
- inc(pc);
- end;
- pos:=0;
- end;
- {$ifdef interncopy}
- function fpc_char_copy(c:char;index : SizeInt;count : SizeInt): shortstring;compilerproc;
- begin
- if (index=1) and (Count>0) then
- fpc_char_Copy:=c
- else
- fpc_char_Copy:='';
- end;
- {$else}
- function copy(c:char;index : SizeInt;count : SizeInt): shortstring;
- begin
- if (index=1) and (Count>0) then
- Copy:=c
- else
- Copy:='';
- end;
- {$endif}
- function pos(const substr : shortstring;c:char): SizeInt;
- begin
- if (length(substr)=1) and (substr[1]=c) then
- Pos:=1
- else
- Pos:=0;
- end;
- {$ifdef IBM_CHAR_SET}
- const
- UpCaseTbl : shortstring[7]=#154#142#153#144#128#143#165;
- LoCaseTbl : shortstring[7]=#129#132#148#130#135#134#164;
- {$endif}
- function upcase(c : char) : char;
- {$IFDEF IBM_CHAR_SET}
- var
- i : longint;
- {$ENDIF}
- begin
- if (c in ['a'..'z']) then
- upcase:=char(byte(c)-32)
- else
- {$IFDEF IBM_CHAR_SET}
- begin
- i:=Pos(c,LoCaseTbl);
- if i>0 then
- upcase:=UpCaseTbl[i]
- else
- upcase:=c;
- end;
- {$ELSE}
- upcase:=c;
- {$ENDIF}
- end;
- function upcase(const s : shortstring) : shortstring;
- var
- i : longint;
- begin
- upcase[0]:=s[0];
- for i := 1 to length (s) do
- upcase[i] := upcase (s[i]);
- end;
- function lowercase(c : char) : char;overload;
- {$IFDEF IBM_CHAR_SET}
- var
- i : longint;
- {$ENDIF}
- begin
- if (c in ['A'..'Z']) then
- lowercase:=char(byte(c)+32)
- else
- {$IFDEF IBM_CHAR_SET}
- begin
- i:=Pos(c,UpCaseTbl);
- if i>0 then
- lowercase:=LoCaseTbl[i]
- else
- lowercase:=c;
- end;
- {$ELSE}
- lowercase:=c;
- {$ENDIF}
- end;
- function lowercase(const s : shortstring) : shortstring; overload;
- var
- i : longint;
- begin
- lowercase [0]:=s[0];
- for i:=1 to length(s) do
- lowercase[i]:=lowercase (s[i]);
- end;
- const
- HexTbl : array[0..15] of char='0123456789ABCDEF';
- function hexstr(val : longint;cnt : byte) : shortstring;
- var
- i : longint;
- begin
- hexstr[0]:=char(cnt);
- for i:=cnt downto 1 do
- begin
- hexstr[i]:=hextbl[val and $f];
- val:=val shr 4;
- end;
- end;
- function octstr(val : longint;cnt : byte) : shortstring;
- var
- i : longint;
- begin
- octstr[0]:=char(cnt);
- for i:=cnt downto 1 do
- begin
- octstr[i]:=hextbl[val and 7];
- val:=val shr 3;
- end;
- end;
- function binstr(val : longint;cnt : byte) : shortstring;
- var
- i : longint;
- begin
- binstr[0]:=char(cnt);
- for i:=cnt downto 1 do
- begin
- binstr[i]:=char(48+val and 1);
- val:=val shr 1;
- end;
- end;
- function hexstr(val : int64;cnt : byte) : shortstring;
- var
- i : longint;
- begin
- hexstr[0]:=char(cnt);
- for i:=cnt downto 1 do
- begin
- hexstr[i]:=hextbl[val and $f];
- val:=val shr 4;
- end;
- end;
- function octstr(val : int64;cnt : byte) : shortstring;
- var
- i : longint;
- begin
- octstr[0]:=char(cnt);
- for i:=cnt downto 1 do
- begin
- octstr[i]:=hextbl[val and 7];
- val:=val shr 3;
- end;
- end;
- function binstr(val : int64;cnt : byte) : shortstring;
- var
- i : longint;
- begin
- binstr[0]:=char(cnt);
- for i:=cnt downto 1 do
- begin
- binstr[i]:=char(48+val and 1);
- val:=val shr 1;
- end;
- end;
- function space (b : byte): shortstring;
- begin
- space[0] := chr(b);
- FillChar (Space[1],b,' ');
- end;
- {*****************************************************************************
- Str() Helpers
- *****************************************************************************}
- {$ifdef STR_USES_VALINT}
- procedure fpc_shortstr_SInt(v : valSInt;len : SizeInt;var s : shortstring);[public,alias:'FPC_SHORTSTR_SINT']; {$ifdef hascompilerproc} compilerproc; {$endif}
- {$else}
- procedure fpc_shortstr_longint(v : longint;len : SizeInt;var s : shortstring);[public,alias:'FPC_SHORTSTR_LONGINT']; {$ifdef hascompilerproc} compilerproc; {$endif}
- {$endif}
- begin
- int_str(v,s);
- if length(s)<len then
- s:=space(len-length(s))+s;
- end;
- {$ifdef STR_USES_VALINT}
- procedure fpc_shortstr_UInt(v : valUInt;len : SizeInt;var s : shortstring);[public,alias:'FPC_SHORTSTR_UINT']; {$ifdef hascompilerproc} compilerproc; {$endif}
- {$else}
- {$ifdef ver1_0}
- procedure fpc_shortstr_cardinal(v : longword;len : SizeInt;var s : shortstring);[public,alias:'FPC_SHORTSTR_CARDINAL']; {$ifdef hascompilerproc} compilerproc; {$endif}
- {$else}
- procedure fpc_shortstr_longword(v : longword;len : SizeInt;var s : shortstring);[public,alias:'FPC_SHORTSTR_LONGWORD']; {$ifdef hascompilerproc} compilerproc; {$endif}
- {$endif}
- {$endif}
- begin
- int_str(v,s);
- if length(s)<len then
- s:=space(len-length(s))+s;
- end;
- {$ifndef CPU64}
- procedure fpc_shortstr_qword(v : qword;len : longint;var s : shortstring);[public,alias:'FPC_SHORTSTR_QWORD']; {$ifdef hascompilerproc} compilerproc; {$endif}
- begin
- int_str(v,s);
- if length(s)<len then
- s:=space(len-length(s))+s;
- end;
- procedure fpc_shortstr_int64(v : int64;len : longint;var s : shortstring);[public,alias:'FPC_SHORTSTR_INT64']; {$ifdef hascompilerproc} compilerproc; {$endif}
- begin
- int_str(v,s);
- if length(s)<len then
- s:=space(len-length(s))+s;
- end;
- {$endif CPU64}
- { fpc_shortstr_sInt must appear before this file is included, because }
- { it's used inside real2str.inc and otherwise the searching via the }
- { compilerproc name will fail (JM) }
- {$I real2str.inc}
- procedure fpc_ShortStr_Float(d : ValReal;len,fr,rt : SizeInt;var s : shortstring);[public,alias:'FPC_SHORTSTR_FLOAT']; {$ifdef hascompilerproc}compilerproc;{$endif hascompilerproc}
- begin
- str_real(len,fr,d,treal_type(rt),s);
- end;
- {
- Array Of Char Str() helpers
- }
- {$ifdef STR_USES_VALINT}
- procedure fpc_chararray_sint(v : valsint;len : SizeInt;var a:array of char);{$ifdef hascompilerproc} compilerproc; {$endif}
- {$else}
- procedure fpc_chararray_longint(v : longint;len : SizeInt;var a:array of char);{$ifdef hascompilerproc} compilerproc; {$endif}
- {$endif}
- var
- ss : shortstring;
- maxlen : SizeInt;
- begin
- int_str(v,ss);
- if length(ss)<len then
- ss:=space(len-length(ss))+ss;
- if length(ss)<high(a)+1 then
- maxlen:=length(ss)
- else
- maxlen:=high(a)+1;
- move(ss[1],pchar(@a)^,maxlen);
- end;
- {$ifdef STR_USES_VALINT}
- procedure fpc_chararray_uint(v : valuint;len : SizeInt;var a : array of char);{$ifdef hascompilerproc} compilerproc; {$endif}
- {$else}
- procedure fpc_chararray_longword(v : longword;len : SizeInt;var a : array of char);{$ifdef hascompilerproc} compilerproc; {$endif}
- {$endif}
- var
- ss : shortstring;
- maxlen : SizeInt;
- begin
- int_str(v,ss);
- if length(ss)<len then
- ss:=space(len-length(ss))+ss;
- if length(ss)<high(a)+1 then
- maxlen:=length(ss)
- else
- maxlen:=high(a)+1;
- move(ss[1],pchar(@a)^,maxlen);
- end;
- {$ifndef CPU64}
- procedure fpc_chararray_qword(v : qword;len : SizeInt;var a : array of char);{$ifdef hascompilerproc} compilerproc; {$endif}
- var
- ss : shortstring;
- maxlen : SizeInt;
- begin
- int_str(v,ss);
- if length(ss)<len then
- ss:=space(len-length(ss))+ss;
- if length(ss)<high(a)+1 then
- maxlen:=length(ss)
- else
- maxlen:=high(a)+1;
- move(ss[1],pchar(@a)^,maxlen);
- end;
- procedure fpc_chararray_int64(v : int64;len : SizeInt;var a : array of char);{$ifdef hascompilerproc} compilerproc; {$endif}
- var
- ss : shortstring;
- maxlen : SizeInt;
- begin
- int_str(v,ss);
- if length(ss)<len then
- ss:=space(len-length(ss))+ss;
- if length(ss)<high(a)+1 then
- maxlen:=length(ss)
- else
- maxlen:=high(a)+1;
- move(ss[1],pchar(@a)^,maxlen);
- end;
- {$endif CPU64}
- procedure fpc_chararray_Float(d : ValReal;len,fr,rt : SizeInt;var a : array of char);{$ifdef hascompilerproc}compilerproc;{$endif hascompilerproc}
- var
- ss : shortstring;
- maxlen : SizeInt;
- begin
- str_real(len,fr,d,treal_type(rt),ss);
- if length(ss)<high(a)+1 then
- maxlen:=length(ss)
- else
- maxlen:=high(a)+1;
- move(ss[1],pchar(@a)^,maxlen);
- end;
- {*****************************************************************************
- Val() Functions
- *****************************************************************************}
- Function InitVal(const s:shortstring;var negativ:boolean;var base:byte):ValSInt;
- var
- Code : SizeInt;
- begin
- {Skip Spaces and Tab}
- code:=1;
- while (code<=length(s)) and (s[code] in [' ',#9]) do
- inc(code);
- {Sign}
- negativ:=false;
- case s[code] of
- '-' : begin
- negativ:=true;
- inc(code);
- end;
- '+' : inc(code);
- end;
- {Base}
- base:=10;
- if code<=length(s) then
- begin
- case s[code] of
- '$' : begin
- base:=16;
- repeat
- inc(code);
- until (code>=length(s)) or (s[code]<>'0');
- end;
- '%' : begin
- base:=2;
- inc(code);
- end;
- '&' : begin
- Base:=8;
- repeat
- inc(code);
- until (code>=length(s)) or (s[code]<>'0');
- end;
- end;
- end;
- InitVal:=code;
- end;
- Function fpc_Val_SInt_ShortStr(DestSize: SizeInt; Const S: ShortString; var Code: ValSInt): ValSInt; [public, alias:'FPC_VAL_SINT_SHORTSTR']; {$ifdef hascompilerproc} compilerproc; {$endif}
- var
- u, temp, prev, maxPrevValue, maxNewValue: ValUInt;
- base : byte;
- negative : boolean;
- begin
- fpc_Val_SInt_ShortStr := 0;
- Temp:=0;
- Code:=InitVal(s,negative,base);
- if Code>length(s) then
- exit;
- maxPrevValue := ValUInt(MaxUIntValue) div ValUInt(Base);
- if (base = 10) then
- maxNewValue := MaxSIntValue + ord(negative)
- else
- maxNewValue := MaxUIntValue;
- while Code<=Length(s) do
- begin
- case s[Code] of
- '0'..'9' : u:=Ord(S[Code])-Ord('0');
- 'A'..'F' : u:=Ord(S[Code])-(Ord('A')-10);
- 'a'..'f' : u:=Ord(S[Code])-(Ord('a')-10);
- else
- u:=16;
- end;
- Prev := Temp;
- Temp := Temp*ValUInt(base);
- If (u >= base) or
- (ValUInt(maxNewValue-u) < Temp) or
- (prev > maxPrevValue) Then
- Begin
- fpc_Val_SInt_ShortStr := 0;
- Exit
- End;
- Temp:=Temp+u;
- inc(code);
- end;
- code := 0;
- fpc_Val_SInt_ShortStr := ValSInt(Temp);
- If Negative Then
- fpc_Val_SInt_ShortStr := -fpc_Val_SInt_ShortStr;
- If Not(Negative) and (base <> 10) Then
- {sign extend the result to allow proper range checking}
- Case DestSize of
- 1: fpc_Val_SInt_ShortStr := shortint(fpc_Val_SInt_ShortStr);
- 2: fpc_Val_SInt_ShortStr := smallint(fpc_Val_SInt_ShortStr);
- { Uncomment the folling once full 64bit support is in place
- 4: fpc_Val_SInt_ShortStr := SizeInt(fpc_Val_SInt_ShortStr);}
- End;
- end;
- {$ifdef hascompilerproc}
- { we need this for fpc_Val_SInt_Ansistr and fpc_Val_SInt_WideStr because }
- { we have to pass the DestSize parameter on (JM) }
- Function fpc_Val_SInt_ShortStr(DestSize: SizeInt; Const S: ShortString; var Code: ValSInt): ValSInt; [external name 'FPC_VAL_SINT_SHORTSTR'];
- {$endif hascompilerproc}
- Function fpc_Val_UInt_Shortstr(Const S: ShortString; var Code: ValSInt): ValUInt; [public, alias:'FPC_VAL_UINT_SHORTSTR']; {$ifdef hascompilerproc} compilerproc; {$endif}
- var
- u, prev : ValUInt;
- base : byte;
- negative : boolean;
- begin
- fpc_Val_UInt_Shortstr:=0;
- Code:=InitVal(s,negative,base);
- If Negative or (Code>length(s)) Then
- Exit;
- while Code<=Length(s) do
- begin
- case s[Code] of
- '0'..'9' : u:=Ord(S[Code])-Ord('0');
- 'A'..'F' : u:=Ord(S[Code])-(Ord('A')-10);
- 'a'..'f' : u:=Ord(S[Code])-(Ord('a')-10);
- else
- u:=16;
- end;
- prev := fpc_Val_UInt_Shortstr;
- If (u>=base) or
- (ValUInt(MaxUIntValue-u) div ValUInt(Base)<prev) then
- begin
- fpc_Val_UInt_Shortstr:=0;
- exit;
- end;
- fpc_Val_UInt_Shortstr:=fpc_Val_UInt_Shortstr*ValUInt(base) + u;
- inc(code);
- end;
- code := 0;
- end;
- {$ifndef CPU64}
- Function fpc_val_int64_shortstr(Const S: ShortString; var Code: ValSInt): Int64; [public, alias:'FPC_VAL_INT64_SHORTSTR']; {$ifdef hascompilerproc} compilerproc; {$endif}
- type
- QWordRec = packed record
- l1,l2: longint;
- end;
- var
- u, temp, prev, maxint64, maxqword : qword;
- base : byte;
- negative : boolean;
- begin
- fpc_val_int64_shortstr := 0;
- Temp:=0;
- Code:=InitVal(s,negative,base);
- if Code>length(s) then
- exit;
- { high(int64) produces 0 in version 1.0 (JM) }
- with qwordrec(maxint64) do
- begin
- l1 := longint($ffffffff);
- l2 := $7fffffff;
- end;
- with qwordrec(maxqword) do
- begin
- l1 := longint($ffffffff);
- l2 := longint($ffffffff);
- end;
- while Code<=Length(s) do
- begin
- case s[Code] of
- '0'..'9' : u:=Ord(S[Code])-Ord('0');
- 'A'..'F' : u:=Ord(S[Code])-(Ord('A')-10);
- 'a'..'f' : u:=Ord(S[Code])-(Ord('a')-10);
- else
- u:=16;
- end;
- Prev:=Temp;
- Temp:=Temp*Int64(base);
- If (u >= base) or
- ((base = 10) and
- (maxint64-temp+ord(negative) < u)) or
- ((base <> 10) and
- (qword(maxqword-temp) < u)) or
- (prev > maxqword div qword(base)) Then
- Begin
- fpc_val_int64_shortstr := 0;
- Exit
- End;
- Temp:=Temp+u;
- inc(code);
- end;
- code:=0;
- fpc_val_int64_shortstr:=int64(Temp);
- If Negative Then
- fpc_val_int64_shortstr:=-fpc_val_int64_shortstr;
- end;
- Function fpc_val_qword_shortstr(Const S: ShortString; var Code: ValSInt): QWord; [public, alias:'FPC_VAL_QWORD_SHORTSTR']; {$ifdef hascompilerproc} compilerproc; {$endif}
- type qwordrec = packed record
- l1,l2: longint;
- end;
- var
- u, prev, maxqword: QWord;
- base : byte;
- negative : boolean;
- begin
- fpc_val_qword_shortstr:=0;
- Code:=InitVal(s,negative,base);
- If Negative or (Code>length(s)) Then
- Exit;
- with qwordrec(maxqword) do
- begin
- l1 := longint($ffffffff);
- l2 := longint($ffffffff);
- end;
- while Code<=Length(s) do
- begin
- case s[Code] of
- '0'..'9' : u:=Ord(S[Code])-Ord('0');
- 'A'..'F' : u:=Ord(S[Code])-(Ord('A')-10);
- 'a'..'f' : u:=Ord(S[Code])-(Ord('a')-10);
- else
- u:=16;
- end;
- prev := fpc_val_qword_shortstr;
- If (u>=base) or
- ((QWord(maxqword-u) div QWord(base))<prev) then
- Begin
- fpc_val_qword_shortstr := 0;
- Exit
- End;
- fpc_val_qword_shortstr:=fpc_val_qword_shortstr*QWord(base) + u;
- inc(code);
- end;
- code := 0;
- end;
- {$endif CPU64}
- Function fpc_Val_Real_ShortStr(const s : shortstring; var code : ValSInt): ValReal; [public, alias:'FPC_VAL_REAL_SHORTSTR']; {$ifdef hascompilerproc} compilerproc; {$endif}
- var
- hd,
- esign,sign : valreal;
- exponent,i : SizeInt;
- flags : byte;
- begin
- fpc_Val_Real_ShortStr:=0.0;
- code:=1;
- exponent:=0;
- esign:=1;
- flags:=0;
- sign:=1;
- while (code<=length(s)) and (s[code] in [' ',#9]) do
- inc(code);
- case s[code] of
- '+' : inc(code);
- '-' : begin
- sign:=-1;
- inc(code);
- end;
- end;
- while (Code<=Length(s)) and (s[code] in ['0'..'9']) do
- begin
- { Read integer part }
- flags:=flags or 1;
- fpc_Val_Real_ShortStr:=fpc_Val_Real_ShortStr*10+(ord(s[code])-ord('0'));
- inc(code);
- end;
- { Decimal ? }
- if (s[code]='.') and (length(s)>=code) then
- begin
- hd:=1.0;
- inc(code);
- while (s[code] in ['0'..'9']) and (length(s)>=code) do
- begin
- { Read fractional part. }
- flags:=flags or 2;
- fpc_Val_Real_ShortStr:=fpc_Val_Real_ShortStr*10+(ord(s[code])-ord('0'));
- hd:=hd*10.0;
- inc(code);
- end;
- fpc_Val_Real_ShortStr:=fpc_Val_Real_ShortStr/hd;
- end;
- { Again, read integer and fractional part}
- if flags=0 then
- begin
- fpc_Val_Real_ShortStr:=0.0;
- exit;
- end;
- { Exponent ? }
- if (upcase(s[code])='E') and (length(s)>=code) then
- begin
- inc(code);
- if s[code]='+' then
- inc(code)
- else
- if s[code]='-' then
- begin
- esign:=-1;
- inc(code);
- end;
- if not(s[code] in ['0'..'9']) or (length(s)<code) then
- begin
- fpc_Val_Real_ShortStr:=0.0;
- exit;
- end;
- while (s[code] in ['0'..'9']) and (length(s)>=code) do
- begin
- exponent:=exponent*10;
- exponent:=exponent+ord(s[code])-ord('0');
- inc(code);
- end;
- end;
- { Calculate Exponent }
- {
- if esign>0 then
- for i:=1 to exponent do
- fpc_Val_Real_ShortStr:=Val_Real_ShortStr*10
- else
- for i:=1 to exponent do
- fpc_Val_Real_ShortStr:=Val_Real_ShortStr/10; }
- hd:=1.0;
- for i:=1 to exponent do
- hd:=hd*10.0;
- if esign>0 then
- fpc_Val_Real_ShortStr:=fpc_Val_Real_ShortStr*hd
- else
- fpc_Val_Real_ShortStr:=fpc_Val_Real_ShortStr/hd;
- { Not all characters are read ? }
- if length(s)>=code then
- begin
- fpc_Val_Real_ShortStr:=0.0;
- exit;
- end;
- { evaluate sign }
- fpc_Val_Real_ShortStr:=fpc_Val_Real_ShortStr*sign;
- { success ! }
- code:=0;
- end;
- Procedure SetString (Var S : Shortstring; Buf : PChar; Len : SizeInt);
- begin
- If Len > High(S) then
- Len := High(S);
- SetLength(S,Len);
- If Buf<>Nil then
- begin
- Move (Buf[0],S[1],Len);
- end;
- end;
- {
- $Log$
- Revision 1.30 2004-05-01 23:55:18 peter
- * replace strlenint with sizeint
- Revision 1.29 2004/05/01 20:52:50 peter
- * ValSInt fixed for 64 bit
- Revision 1.28 2004/04/29 18:59:43 peter
- * str() helpers now also use valint/valuint
- * int64/qword helpers disabled for cpu64
- Revision 1.27 2003/02/26 20:04:47 jonas
- * fixed shortstring version of setstring
- Revision 1.26 2002/10/21 19:52:47 jonas
- * fixed some buffer overflow errors in SetString (both short and
- ansistring versions) (merged)
- Revision 1.25 2002/10/19 17:06:50 michael
- + Added check for nil buffer to setstring
- Revision 1.24 2002/10/02 18:21:51 peter
- * Copy() changed to internal function calling compilerprocs
- * FPC_SHORTSTR_COPY renamed to FPC_SHORTSTR_ASSIGN because of the
- new copy functions
- Revision 1.23 2002/09/14 11:20:50 carl
- * Delphi compatibility fix (with string routines)
- Revision 1.22 2002/09/07 21:19:00 carl
- * cardinal -> longword
- Revision 1.21 2002/09/07 15:07:46 peter
- * old logs removed and tabs fixed
- Revision 1.20 2002/09/02 19:24:41 peter
- * array of char support for Str()
- Revision 1.19 2002/08/06 20:53:38 michael
- + Added support for octal strings (using &)
- Revision 1.18 2002/01/24 18:27:06 peter
- * lowercase() overloaded
- }
|