123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707170817091710171117121713171417151716171717181719172017211722172317241725172617271728172917301731173217331734173517361737173817391740174117421743174417451746174717481749175017511752175317541755175617571758175917601761176217631764176517661767176817691770177117721773177417751776177717781779178017811782178317841785178617871788178917901791179217931794179517961797179817991800180118021803180418051806180718081809181018111812181318141815181618171818181918201821182218231824182518261827182818291830183118321833183418351836183718381839184018411842184318441845184618471848184918501851185218531854185518561857185818591860186118621863186418651866186718681869187018711872187318741875187618771878187918801881188218831884188518861887188818891890189118921893189418951896189718981899190019011902190319041905190619071908190919101911191219131914191519161917191819191920192119221923192419251926192719281929193019311932193319341935193619371938193919401941194219431944194519461947194819491950195119521953195419551956195719581959196019611962196319641965196619671968196919701971197219731974197519761977197819791980198119821983198419851986198719881989199019911992199319941995199619971998199920002001200220032004200520062007200820092010201120122013201420152016201720182019202020212022202320242025202620272028202920302031203220332034203520362037203820392040204120422043204420452046204720482049205020512052205320542055205620572058205920602061206220632064206520662067206820692070207120722073207420752076207720782079208020812082208320842085208620872088208920902091209220932094209520962097209820992100210121022103210421052106210721082109211021112112211321142115211621172118211921202121212221232124212521262127212821292130213121322133213421352136213721382139214021412142214321442145214621472148214921502151215221532154215521562157215821592160216121622163216421652166216721682169217021712172217321742175217621772178217921802181218221832184218521862187218821892190219121922193219421952196219721982199220022012202220322042205220622072208220922102211221222132214221522162217221822192220222122222223222422252226222722282229223022312232223322342235223622372238223922402241224222432244224522462247224822492250225122522253225422552256225722582259226022612262226322642265226622672268226922702271227222732274227522762277227822792280228122822283228422852286228722882289229022912292229322942295229622972298229923002301230223032304230523062307230823092310231123122313231423152316231723182319232023212322232323242325232623272328232923302331233223332334233523362337233823392340234123422343234423452346234723482349235023512352235323542355235623572358235923602361236223632364236523662367236823692370237123722373237423752376237723782379238023812382238323842385238623872388238923902391239223932394239523962397239823992400240124022403240424052406240724082409241024112412241324142415241624172418241924202421242224232424242524262427242824292430243124322433243424352436243724382439244024412442244324442445244624472448244924502451245224532454245524562457245824592460246124622463246424652466246724682469247024712472247324742475247624772478247924802481248224832484248524862487248824892490249124922493249424952496249724982499250025012502250325042505250625072508250925102511251225132514251525162517251825192520252125222523252425252526252725282529253025312532253325342535253625372538253925402541254225432544254525462547254825492550255125522553255425552556255725582559256025612562256325642565256625672568256925702571257225732574257525762577257825792580258125822583258425852586258725882589259025912592259325942595259625972598259926002601260226032604260526062607260826092610261126122613261426152616261726182619262026212622262326242625262626272628262926302631263226332634263526362637263826392640264126422643264426452646264726482649265026512652265326542655265626572658265926602661266226632664266526662667266826692670267126722673267426752676267726782679268026812682268326842685268626872688268926902691269226932694269526962697269826992700270127022703270427052706270727082709271027112712271327142715271627172718271927202721272227232724272527262727272827292730273127322733273427352736273727382739274027412742274327442745274627472748274927502751275227532754275527562757275827592760276127622763276427652766276727682769277027712772277327742775277627772778277927802781278227832784278527862787278827892790279127922793279427952796279727982799280028012802280328042805280628072808280928102811281228132814281528162817281828192820282128222823282428252826282728282829283028312832283328342835283628372838283928402841284228432844284528462847284828492850285128522853285428552856285728582859286028612862286328642865286628672868286928702871287228732874287528762877287828792880288128822883288428852886288728882889289028912892289328942895289628972898289929002901290229032904290529062907290829092910291129122913291429152916291729182919292029212922292329242925292629272928292929302931293229332934293529362937293829392940294129422943294429452946294729482949295029512952295329542955295629572958295929602961296229632964296529662967296829692970297129722973297429752976297729782979298029812982298329842985298629872988298929902991299229932994299529962997299829993000300130023003 |
- {%MainUnit sysutils.pp}
- {
- *********************************************************************
- Copyright (C) 1997, 1998 Gertjan Schouten
- 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.
- **********************************************************************
- System Utilities For Free Pascal
- }
- { NewStr creates a new PString and assigns S to it
- if length(s) = 0 NewStr returns Nil }
- function NewStr(const S: string): PString;
- begin
- if (S='') then
- Result:=nil
- else
- begin
- new(result);
- if (Result<>nil) then
- Result^:=s;
- end;
- end;
- {$ifdef dummy}
- { declaring this breaks delphi compatibility and e.g. tw3721.pp }
- FUNCTION NewStr (Const S: ShortString): PShortString;
- VAR P: PShortString;
- BEGIN
- If (S = '') Then
- P := Nil
- Else
- Begin { Return nil }
- GetMem(P, Length(S) + 1); { Allocate memory }
- If (P<>Nil) Then P^ := S; { Hold string }
- End;
- NewStr := P; { Return result }
- END;
- {$endif dummy}
- { DisposeStr frees the memory occupied by S }
- procedure DisposeStr(S: PString);
- begin
- if S <> Nil then
- begin
- dispose(s);
- S:=nil;
- end;
- end;
- PROCEDURE DisposeStr (S: PShortString);
- BEGIN
- If (S <> Nil) Then FreeMem(S, Length(S^) + 1); { Release memory }
- END;
- { AssignStr assigns S to P^ }
- procedure AssignStr(var P: PString; const S: string);
- begin
- P^ := s;
- end ;
- { AppendStr appends S to Dest }
- procedure AppendStr(var Dest: String; const S: string);
- begin
- Dest := Dest + S;
- end ;
- function IsLeadChar(C: AnsiChar): Boolean; inline;
- begin
- Result:=C in LeadBytes;
- end;
- function IsLeadChar(B: Byte): Boolean; inline;
- begin
- Result:=AnsiChar(B) in LeadBytes;
- end;
- Function InternalChangeCase(Const S : AnsiString; const Chars: TSysCharSet; const Adjustment: Longint): AnsiString;
- var
- i : Integer;
- P : PAnsiChar;
- Unique : Boolean;
- begin
- Result := S;
- if Result='' then
- exit;
- Unique:=false;
- P:=PAnsiChar(Result);
- for i:=1 to Length(Result) do
- begin
- if CharInSet(P^,Chars) then
- begin
- if not Unique then
- begin
- UniqueString(Result);
- p:=@Result[i];
- Unique:=true;
- end;
- P^:=AnsiChar(Ord(P^)+Adjustment);
- end;
- Inc(P);
- end;
- end;
- { UpperCase returns a copy of S where all lowercase characters ( from a to z )
- have been converted to uppercase }
- Function UpperCase(Const S : AnsiString) : AnsiString;
- begin
- Result:=InternalChangeCase(S,['a'..'z'],-32);
- end;
- function UpperCase(const s: ansistring; LocaleOptions: TLocaleOptions): ansistring; overload;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- case LocaleOptions of
- loInvariantLocale: Result:=UpperCase(s);
- loUserLocale: Result:=AnsiUpperCase(s);
- end;
- end;
- { LowerCase returns a copy of S where all uppercase characters ( from A to Z )
- have been converted to lowercase }
- Function Lowercase(Const S : AnsiString) : AnsiString;
- begin
- Result:=InternalChangeCase(S,['A'..'Z'],32);
- end;
- function LowerCase(const s: ansistring; LocaleOptions: TLocaleOptions): ansistring; overload;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- case LocaleOptions of
- loInvariantLocale: Result:=LowerCase(s);
- loUserLocale: Result:=AnsiLowerCase(s);
- end;
- end;
- function LowerCase(const V: variant): string; overload;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- {$IFDEF UNICODERTL}
- result:=LowerCase(widestring(V));
- {ELSE}
- result:=LowerCase(ansistring(V));
- {$ENDIF}
- end;
- { CompareStr compares S1 and S2, the result is the based on
- substraction of the ascii values of the characters in S1 and S2
- case result
- S1 < S2 < 0
- S1 > S2 > 0
- S1 = S2 = 0 }
- {$IF SIZEOF(SIZEINT)>SIZEOF(INTEGER)}
- Function DoCapSizeInt(SI : SizeInt) : Integer; inline;
- begin
- if (SI<0) then
- result:=-1
- else if (SI>0) then
- result:=1
- else
- result:=0;
- end;
- {$DEFINE CAPSIZEINT:=DoCapSizeInt}
- {$ELSE}
- {$DEFINE CAPSIZEINT:=}
- {$ENDIF}
- function CompareStr(const S1, S2: string): Integer;
- var count, count1, count2: SizeInt;
- begin
- Count1 := Length(S1);
- Count2 := Length(S2);
- if Count1>Count2 then
- Count:=Count2
- else
- Count:=Count1;
- result := CompareMemRange(Pointer(S1),Pointer(S2), Count);
- if result=0 then
- // CAPSIZEINT is no-op if Sizeof(Sizeint)<=SizeOF(Integer)
- result:=CAPSIZEINT(Count1-Count2);
- end;
- function CompareStr(const S1, S2: string; LocaleOptions: TLocaleOptions): Integer; overload;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- case LocaleOptions of
- loInvariantLocale: Result:=CompareStr(S1,S2);
- loUserLocale: Result:=AnsiCompareStr(S1,S2);
- end;
- end;
- { CompareMemRange returns the result of comparison of Length bytes at P1 and P2
- case result
- P1 < P2 < 0
- P1 > P2 > 0
- P1 = P2 = 0 }
- function CompareMemRange(P1, P2: Pointer; Length: PtrUInt): integer;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- If P1=P2 then
- Result:=0
- else
- Result:=CompareByte(P1^,P2^,Length);
- end;
- function CompareMem(P1, P2: Pointer; Length: PtrUInt): Boolean;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- if P1=P2 then
- Result:=True
- else
- Result:=CompareByte(P1^,P2^,Length)=0;
- end;
- { CompareText compares S1 and S2, the result is the based on
- substraction of the ascii values of characters in S1 and S2
- comparison is case-insensitive
- case result
- S1 < S2 < 0
- S1 > S2 > 0
- S1 = S2 = 0 }
- function CompareText(const S1, S2: string): Integer; overload;
- var
- i, count, count1, count2: sizeint;
- Chr1, Chr2: byte;
- P1, P2: PChar;
- begin
- Count1 := Length(S1);
- Count2 := Length(S2);
- if (Count1>Count2) then
- Count := Count2
- else
- Count := Count1;
- i := 0;
- if count>0 then
- begin
- P1 := @S1[1];
- P2 := @S2[1];
- while i < Count do
- begin
- Chr1 := byte(p1^);
- Chr2 := byte(p2^);
- if Chr1 <> Chr2 then
- begin
- if Chr1 in [97..122] then
- dec(Chr1,32);
- if Chr2 in [97..122] then
- dec(Chr2,32);
- if Chr1 <> Chr2 then
- Break;
- end;
- Inc(P1); Inc(P2); Inc(I);
- end;
- end;
- if i < Count then
- result := Chr1-Chr2
- else
- // CAPSIZEINT is no-op if Sizeof(Sizeint)<=SizeOF(Integer)
- result:=CAPSIZEINT(Count1-Count2);
- end;
- function CompareText(const S1, S2: string; LocaleOptions: TLocaleOptions): Integer; overload;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- case LocaleOptions of
- loInvariantLocale: Result:=CompareText(S1,S2);
- loUserLocale: Result:=AnsiCompareText(S1,S2);
- end;
- end;
- function SameText(const s1,s2:String):Boolean; overload;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- Result:=CompareText(S1,S2)=0;
- end;
- function SameText(const s1,s2:String; LocaleOptions: TLocaleOptions):Boolean; overload;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- case LocaleOptions of
- loInvariantLocale: Result:=SameText(S1,S2);
- loUserLocale: Result:=AnsiSameText(S1,S2);
- end;
- end;
- function SameStr(const s1,s2:String):Boolean; overload;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- Result:=CompareStr(S1,S2)=0;
- end;
- function SameStr(const s1,s2:String; LocaleOptions: TLocaleOptions):Boolean; overload;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- case LocaleOptions of
- loInvariantLocale: Result:=SameStr(S1,S2);
- loUserLocale: Result:=AnsiSameStr(S1,S2);
- end;
- end;
- {$ifndef FPC_NOGENERICANSIROUTINES}
- {==============================================================================}
- { Ansi string functions }
- { these functions rely on the character set loaded by the OS }
- {==============================================================================}
- type
- TCaseTranslationTable = array[0..255] of AnsiChar;
- var
- { Tables with upper and lowercase forms of character sets.
- MUST be initialized with the correct code-pages }
- UpperCaseTable: TCaseTranslationTable;
- LowerCaseTable: TCaseTranslationTable;
- function GenericAnsiUpperCase(const s: ansistring): ansistring;
- var
- len, i: integer;
- begin
- len := length(s);
- SetLength(result, len);
- for i := 1 to len do
- result[i] := UpperCaseTable[ord(s[i])];
- end;
- function GenericAnsiLowerCase(const s: ansistring): ansistring;
- var
- len, i: integer;
- begin
- len := length(s);
- SetLength(result, len);
- for i := 1 to len do
- result[i] := LowerCaseTable[ord(s[i])];
- end;
- function GenericAnsiCompareStr(const S1, S2: ansistring): PtrInt;
- Var
- I,L1,L2 : SizeInt;
- begin
- Result:=0;
- L1:=Length(S1);
- L2:=Length(S2);
- I:=1;
- While (Result=0) and ((I<=L1) and (I<=L2)) do
- begin
- Result:=Ord(S1[I])-Ord(S2[I]); //!! Must be replaced by ansi characters !!
- Inc(I);
- end;
- If Result=0 Then
- Result:=L1-L2;
- end;
- function GenericAnsiCompareText(const S1, S2: ansistring): PtrInt;
- Var
- I,L1,L2 : SizeInt;
- begin
- Result:=0;
- L1:=Length(S1);
- L2:=Length(S2);
- I:=1;
- While (Result=0) and ((I<=L1) and (I<=L2)) do
- begin
- Result:=Ord(LowerCaseTable[Ord(S1[I])])-Ord(LowerCaseTable[Ord(S2[I])]); //!! Must be replaced by ansi characters !!
- Inc(I);
- end;
- If Result=0 Then
- Result:=L1-L2;
- end;
- function GenericAnsiStrComp(S1, S2: PAnsiChar): PtrInt;
- begin
- Result:=0;
- If S1=Nil then
- begin
- If S2=Nil Then Exit;
- result:=-1;
- exit;
- end;
- If S2=Nil then
- begin
- Result:=1;
- exit;
- end;
- While (Result=0) and (S1^<>#0) and (S2^<>#0) do begin
- Result:=Ord(S1^)-Ord(S2^); //!! Must be replaced by ansi characters !!
- Inc(S1);
- Inc(S2);
- end;
- if (Result=0) and (S1^<>S2^) then // loop ended because exactly one has #0
- if S1^=#0 then // shorter string is smaller
- result:=-1
- else
- result:=1;
- end;
- function GenericAnsiStrIComp(S1, S2: PAnsiChar): PtrInt;
- begin
- Result:=0;
- If S1=Nil then
- begin
- If S2=Nil Then Exit;
- result:=-1;
- exit;
- end;
- If S2=Nil then
- begin
- Result:=1;
- exit;
- end;
- While (Result=0) and (S1^<>#0) and (S2^<>#0) do begin
- Result:=Ord(LowerCaseTable[Ord(S1[0])])-Ord(LowerCaseTable[Ord(S2[0])]); //!! Must be replaced by ansi characters !!
- Inc(S1);
- Inc(S2);
- end;
- if (Result=0) and (s1[0]<>s2[0]) then //length(s1)<>length(s2)
- if s1[0]=#0 then
- Result:=-1 //s1 shorter than s2
- else
- Result:=1; //s1 longer than s2
- end;
- function GenericAnsiStrLComp(S1, S2: PAnsiChar; MaxLen: PtrUInt): PtrInt;
- Var I : PtrUInt;
- begin
- Result:=0;
- If MaxLen=0 then exit;
- If S1=Nil then
- begin
- If S2=Nil Then Exit;
- result:=-1;
- exit;
- end;
- If S2=Nil then
- begin
- Result:=1;
- exit;
- end;
- I:=0;
- Repeat
- Result:=Ord(S1[0])-Ord(S2[0]); //!! Must be replaced by ansi characters !!
- Inc(S1);
- Inc(S2);
- Inc(I);
- Until (Result<>0) or (I=MaxLen)
- end;
- function GenericAnsiStrLIComp(S1, S2: PAnsiChar; MaxLen: PtrUInt): PtrInt;
- Var I : PtrUInt;
- begin
- Result:=0;
- If MaxLen=0 then exit;
- If S1=Nil then
- begin
- If S2=Nil Then Exit;
- result:=-1;
- exit;
- end;
- If S2=Nil then
- begin
- Result:=1;
- exit;
- end;
- I:=0;
- Repeat
- Result:=Ord(LowerCaseTable[Ord(S1[0])])-Ord(LowerCaseTable[Ord(S2[0])]); //!! Must be replaced by ansi characters !!
- Inc(S1);
- Inc(S2);
- Inc(I);
- Until (Result<>0) or (I=MaxLen)
- end;
- function GenericAnsiStrLower(Str: PAnsiChar): PAnsiChar;
- begin
- result := Str;
- if Str <> Nil then begin
- while Str^ <> #0 do begin
- Str^ := LowerCaseTable[byte(Str^)];
- Str := Str + 1;
- end;
- end;
- end;
- function GenericAnsiStrUpper(Str: PAnsiChar): PAnsiChar;
- begin
- result := Str;
- if Str <> Nil then begin
- while Str^ <> #0 do begin
- Str^ := UpperCaseTable[byte(Str^)];
- Str := Str + 1;
- end ;
- end ;
- end ;
- {$endif FPC_NOGENERICANSIROUTINES}
- function AnsiSameText(const s1,s2:String):Boolean;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- AnsiSameText:=AnsiCompareText(S1,S2)=0;
- end;
- function AnsiSameStr(const s1,s2:String):Boolean;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- AnsiSameStr:=AnsiCompareStr(S1,S2)=0;
- end;
- function AnsiLastChar(const S: AnsiString): PAnsiChar;
- begin
- //!! No multibyte yet, so we return the last one.
- result:=StrEnd(PAnsiChar(pointer(S))); // strend checks for nil
- Dec(Result);
- end ;
- function AnsiLastChar(const S: UnicodeString): PWideChar;
- begin
- //!! No multibyte yet, so we return the last one.
- result:=StrEnd(PWideChar(Pointer(S))); // strend checks for nil
- Dec(Result);
- end ;
- function AnsiStrLastChar(Str: PAnsiChar): PAnsiChar;
- begin
- //!! No multibyte yet, so we return the last one.
- result:=StrEnd(Str);
- Dec(Result);
- end ;
- function AnsiUpperCase(const s: string): string;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- result:=widestringmanager.UpperAnsiStringProc(s);
- end;
- function AnsiLowerCase(const s: string): string;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- result:=widestringmanager.LowerAnsiStringProc(s);
- end;
- function AnsiCompareStr(const S1, S2: string): integer;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- // CAPSIZEINT is no-op if Sizeof(Sizeint)<=SizeOF(Integer)
- result:=CAPSIZEINT(widestringmanager.CompareStrAnsiStringProc(s1,s2));
- end;
- function AnsiCompareText(const S1, S2: string): integer;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- // CAPSIZEINT is no-op if Sizeof(Sizeint)<=SizeOF(Integer)
- result:=CAPSIZEINT(widestringmanager.CompareTextAnsiStringProc(s1,s2));
- end;
- function AnsiStrComp(S1, S2: PAnsiChar): integer;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- // CAPSIZEINT is no-op if Sizeof(Sizeint)<=SizeOF(Integer)
- result:=CAPSIZEINT(widestringmanager.StrCompAnsiStringProc(s1,s2));
- end;
- function AnsiStrIComp(S1, S2: PAnsiChar): integer;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- // CAPSIZEINT is no-op if Sizeof(Sizeint)<=SizeOF(Integer)
- result:=CAPSIZEINT(widestringmanager.StrICompAnsiStringProc(s1,s2));
- end;
- function AnsiStrLComp(S1, S2: PAnsiChar; MaxLen: SizeUInt): Integer;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- // CAPSIZEINT is no-op if Sizeof(Sizeint)<=SizeOF(Integer)
- result:=CAPSIZEINT(widestringmanager.StrLCompAnsiStringProc(s1,s2,maxlen));
- end;
- function AnsiStrLIComp(S1, S2: PAnsiChar; MaxLen: SizeUint): Integer;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- // CAPSIZEINT is no-op if Sizeof(Sizeint)<=SizeOF(Integer)
- result:=CAPSIZEINT(widestringmanager.StrLICompAnsiStringProc(s1,s2,maxlen));
- end;
- function AnsiStrLower(Str: PAnsiChar): PAnsiChar;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- result:=widestringmanager.StrLowerAnsiStringProc(Str);
- end;
- function AnsiStrUpper(Str: PAnsiChar): PAnsiChar;{$ifdef SYSUTILSINLINE}inline;{$endif}
- begin
- result:=widestringmanager.StrUpperAnsiStringProc(Str);
- end;
- {==============================================================================}
- { End of Ansi functions }
- {==============================================================================}
- { Trim returns a copy of S with blanks characters on the left and right stripped off }
- Const WhiteSpace = [#0..' '];
- function Trim(const S: ansistring): ansistring;
- var Ofs, Len: integer;
- begin
- len := Length(S);
- while (Len>0) and (S[Len] in WhiteSpace) do
- dec(Len);
- Ofs := 1;
- while (Ofs<=Len) and (S[Ofs] in WhiteSpace) do
- Inc(Ofs);
- result := Copy(S, Ofs, 1 + Len - Ofs);
- end ;
- { TrimLeft returns a copy of S with all blank characters on the left stripped off }
- function TrimLeft(const S: ansistring): ansistring;
- var i,l:integer;
- begin
- l := length(s);
- i := 1;
- while (i<=l) and (s[i] in whitespace) do
- inc(i);
- Result := copy(s, i, l);
- end ;
- { TrimRight returns a copy of S with all blank characters on the right stripped off }
- function TrimRight(const S: ansistring): ansistring;
- var l:integer;
- begin
- l := length(s);
- while (l>0) and (s[l] in whitespace) do
- dec(l);
- result := copy(s,1,l);
- end ;
- { QuotedStr returns S quoted left and right and every single quote in S
- replaced by two quotes }
- function QuotedStr(const S: string): string;
- begin
- result := AnsiQuotedStr(s, '''');
- end ;
- { AnsiQuotedStr returns S quoted left and right by Quote,
- and every single occurance of Quote replaced by two }
- function AnsiQuotedStr(const S: string; Quote: Char): string;
- var i, j, count: integer;
- begin
- result := '' + Quote;
- count := length(s);
- i := 0;
- j := 0;
- while i < count do begin
- i := i + 1;
- if S[i] = Quote then begin
- result := result + copy(S, 1 + j, i - j) + Quote;
- j := i;
- end ;
- end ;
- if i <> j then
- result := result + copy(S, 1 + j, i - j);
- result := result + Quote;
- end ;
- { AnsiExtractQuotedStr returns a copy of Src with quote characters
- deleted to the left and right and double occurances
- of Quote replaced by a single Quote }
- function AnsiExtractQuotedStr(var Src: PWideChar; Quote: WideChar): Widestring;
- var
- P,Q,R: PWideChar;
- begin
- result:='';
- if Src=Nil then exit;
- P := Src;
- Q := StrEnd(P);
- if P=Q then
- exit;
- if P^<>quote then
- exit(strpas(P));
- inc(p);
- setlength(result,(Q-P)+1);
- R:=@Result[1];
- while P <> Q do
- begin
- R^:=P^;
- inc(R);
- if (P^ = Quote) then
- begin
- P := P + 1;
- if (p^ <> Quote) then
- begin
- dec(R);
- break;
- end;
- end;
- P := P + 1;
- end ;
- src:=p;
- SetLength(result, (R-PWideChar(@Result[1])));
- end ;
- function AnsiExtractQuotedStr(var Src: PAnsiChar; Quote: AnsiChar): Ansistring;
- var
- P,Q,R: PAnsiChar;
- begin
- result:='';
- if Src=Nil then exit;
- P := Src;
- Q := StrEnd(P);
- if P=Q then
- exit;
- if P^<>quote then
- exit(strpas(P));
- inc(p);
- setlength(result,(Q-P)+1);
- R:=@Result[1];
- while P <> Q do
- begin
- R^:=P^;
- inc(R);
- if (P^ = Quote) then
- begin
- P := P + 1;
- if (p^ <> Quote) then
- begin
- dec(R);
- break;
- end;
- end;
- P := P + 1;
- end ;
- src:=p;
- SetLength(result, (R-PAnsiChar(@Result[1])));
- end ;
- function AnsiExtractQuotedStr(var Src: PWideChar; Quote: AnsiChar): Widestring;
- begin
- Result:=AnsiExtractQuotedStr(Src,WideChar(Quote));
- end;
- { Change CRLF, CR or LF with the default for the current platform }
- function AdjustLineBreaks(const S: string): string;
- begin
- Result:=AdjustLineBreaks(S,DefaultTextLineBreakStyle);
- end;
- { Change CRLF, CR or LF with the indicated style }
- function AdjustLineBreaks(const S: string; Style: TTextLineBreakStyle): string;
- var
- Sp,Se,SLiteralStart,SLiteralEnd,Rp: PChar;
- begin
- Result:='';
- repeat { Does two iterations, first is prepass, second fills the result with data and is distinguished by Assigned(Pointer(Result)). }
- Rp:=Pointer(Result);
- Sp:=PChar(S); { Readable #0 for empty string. }
- Se:=Sp+Length(S);
- SLiteralStart:=Sp;
- repeat
- while (Sp<Se) and not (Sp^ in [#13,#10]) do
- Inc(Sp);
- SLiteralEnd:=Sp; { Save position before consuming line ending. }
- if Sp^=#10 then { These accesses rely on terminating #0. }
- begin
- Inc(Sp);
- if Style=tlbsLF then
- continue;
- end
- else if Sp^=#13 then
- if Sp[1]=#10 then
- begin
- Inc(Sp,2);
- if Style=tlbsCRLF then
- continue;
- end
- else
- begin
- Inc(Sp);
- if Style=tlbsCR then
- continue;
- end;
- if Assigned(Pointer(Result)) then
- Move(SLiteralStart^,Rp^,Pointer(SLiteralEnd)-Pointer(SLiteralStart)); { Byte difference to avoid signed div 2 on char = widechar. }
- Inc(Pointer(Rp),Pointer(SLiteralEnd)-Pointer(SLiteralStart)); { Again, byte difference. }
- if SLiteralEnd=Sp then
- break;
- SLiteralStart:=Sp;
- Inc(Rp,1+ord(Style=tlbsCRLF));
- if Assigned(Pointer(Result)) then
- begin
- if Style=tlbsCRLF then
- Rp[-2]:=#13;
- if Style=tlbsCR then
- Rp[-1]:=#13
- else
- Rp[-1]:=#10;
- end;
- until false;
- if Assigned(Pointer(Result)) then { Second pass finished. }
- break;
- if SLiteralStart=PChar(S) then { String is unchanged. }
- Exit(S);
- SetLength(Result,SizeUint(Pointer(Rp)-Pointer(Result)) div SizeOf(Char)); { Prepare second pass. }
- until false;
- end;
- { IsValidIdent returns true if the first character of Ident is in:
- 'A' to 'Z', 'a' to 'z' or '_' and the following characters are
- on of: 'A' to 'Z', 'a' to 'z', '0'..'9' or '_' }
- function IsValidIdent(const Ident: string; AllowDots: Boolean = False; StrictDots: Boolean = False): Boolean;
- const
- Alpha = ['A'..'Z', 'a'..'z', '_'];
- AlphaNum = Alpha + ['0'..'9'];
- Dot = '.';
- var
- First: Boolean;
- I, Len: Integer;
- begin
- Len := Length(Ident);
- if Len < 1 then
- Exit(False);
- First := True;
- for I := 1 to Len do
- begin
- if First then
- begin
- Result := Ident[I] in Alpha;
- First := False;
- end
- else if AllowDots and (Ident[I] = Dot) then
- begin
- if StrictDots then
- begin
- Result := I < Len;
- First := True;
- end;
- end
- else
- Result := Ident[I] in AlphaNum;
- if not Result then
- Break;
- end;
- end;
- { IntToStr returns a string representing the value of Value }
- function IntToStr(Value: Longint): string;
- begin
- System.Str(Value, result);
- end ;
- function IntToStr(Value: int64): string;
- begin
- System.Str(Value, result);
- end ;
- function IntToStr(Value: QWord): string;
- begin
- System.Str(Value, result);
- end ;
- function UIntToStr(Value: QWord): string;
- begin
- result:=IntTostr(Value);
- end;
- function UIntToStr(Value: Cardinal): string;
- begin
- System.Str(Value, result);
- end;
- { IntToHex returns a string representing the hexadecimal value of Value }
- function IntToHex(Value: Longint; Digits: integer): string;
- var i: integer;
- begin
- If Digits=0 then
- Digits:=1;
- SetLength(result, digits);
- for i := 0 to digits - 1 do
- begin
- result[digits - i] := HexDigits[value and 15];
- value := value shr 4;
- end ;
- while value <> 0 do begin
- result := HexDigits[value and 15] + result;
- value := value shr 4;
- end;
- end ;
- function IntToHex(Value: int64; Digits: integer): string;
- var i: integer;
- begin
- If Digits=0 then
- Digits:=1;
- SetLength(result, digits);
- for i := 0 to digits - 1 do
- begin
- result[digits - i] := HexDigits[value and 15];
- value := value shr 4;
- end ;
- while value <> 0 do begin
- result := HexDigits[value and 15] + result;
- value := value shr 4;
- end;
- end ;
- function IntToHex(Value: QWord; Digits: integer): string;
- begin
- result:=IntToHex(Int64(Value),Digits);
- end;
- function IntToHex(Value: Int8): string;
- begin
- Result:=IntToHex(LongInt(Value) and $ff, 2*SizeOf(Int8));
- end;
- function IntToHex(Value: UInt8): string;
- begin
- Result:=IntToHex(Value, 2*SizeOf(UInt8));
- end;
- function IntToHex(Value: Int16): string;
- begin
- Result:=IntToHex(LongInt(Value) and $ffff, 2*SizeOf(Int16));
- end;
- function IntToHex(Value: UInt16): string;
- begin
- Result:=IntToHex(Value, 2*SizeOf(UInt16));
- end;
- function IntToHex(Value: Int32): string;
- begin
- Result:=IntToHex(Value, 2*SizeOf(Int32));
- end;
- function IntToHex(Value: UInt32): string;
- begin
- Result:=IntToHex(LongInt(Value), 2*SizeOf(UInt32));
- end;
- function IntToHex(Value: Int64): string;
- begin
- Result:=IntToHex(Value, 2*SizeOf(Int64));
- end;
- function IntToHex(Value: UInt64): string;
- begin
- Result:=IntToHex(Value, 2*SizeOf(UInt64));
- end;
- function TryStrToInt(const s: string; out i : Longint) : boolean;
- var
- Error : word;
- begin
- Val(s, i, Error);
- TryStrToInt:=(Error=0)
- end;
- { StrToInt converts the string S to an integer value,
- if S does not represent a valid integer value EConvertError is raised }
- function StrToInt(const S: string): Longint;
- begin
- if not(TryStrToInt(s,Result)) then
- raise EConvertError.createfmt(SInvalidInteger,[S]);
- end;
- function StrToInt64(const S: string): int64;
- begin
- if not(TryStrToInt64(s,Result)) then
- raise EConvertError.createfmt(SInvalidInteger,[S]);
- end;
- function TryStrToInt64(const s: string; Out i : int64) : boolean;
- var Error : word;
- begin
- Val(s, i, Error);
- TryStrToInt64:=Error=0
- end;
- function StrToQWord(const s: string): QWord;
- begin
- if not(TryStrToQWord(s,Result)) then
- raise EConvertError.createfmt(SInvalidInteger,[S]);
- end;
- function StrToUInt64(const s: string): UInt64;
- begin
- result:=StrToQWord(s);
- end;
- function StrToDWord(const s: string): DWord;
- begin
- if not(TryStrToDWord(s,Result)) then
- raise EConvertError.createfmt(SInvalidInteger,[S]);
- end;
- function TryStrToDWord(const s: string; Out D: DWord): boolean;
- var
- Error : word;
- lq : QWord;
- begin
- Val(s, lq, Error);
- TryStrToDWord:=(Error=0) and (lq<=High(DWord));
- if TryStrToDWord then
- D:=lq;
- end;
- function StrToUInt(const s: string): Cardinal;
- begin
- StrToUInt:=StrToDWord(s);
- end;
- function TryStrToUInt(const s: string; out C: Cardinal): Boolean;
- begin
- TryStrToUInt:=TryStrToDWord(s, C);
- end;
- function TryStrToQWord(const s: string; Out Q: QWord): boolean;
- var Error : word;
- begin
- Val(s, Q, Error);
- TryStrToQWord:=Error=0
- end;
- function TryStrToUInt64(const s: string; Out u: UInt64): boolean;
- begin
- result:=TryStrToQWord(s,u);
- end;
- { StrToIntDef converts the string S to an integer value,
- Default is returned in case S does not represent a valid integer value }
- function StrToIntDef(const S: string; Default: Longint): Longint;
- begin
- if not(TryStrToInt(s,Result)) then
- result := Default;
- end;
- { StrToDWordDef converts the string S to an DWord value,
- Default is returned in case S does not represent a valid DWord value }
- function StrToDWordDef(const S: string; Default: DWord): DWord;
- begin
- if not(TryStrToDWord(s,Result)) then
- result := Default;
- end;
- function StrToUIntDef(const S: string; Default: Cardinal): Cardinal;
- begin
- Result:=StrToDWordDef(S, Default);
- end;
- { StrToInt64Def converts the string S to an int64 value,
- Default is returned in case S does not represent a valid int64 value }
- function StrToInt64Def(const S: string; Default: int64): int64;
- begin
- if not(TryStrToInt64(s,Result)) then
- result := Default;
- end;
- { StrToQWordDef converts the string S to an QWord value,
- Default is returned in case S does not represent a valid QWord value }
- function StrToQWordDef(const S: string; Default: QWord): QWord;
- begin
- if not(TryStrToQWord(s,Result)) then
- result := Default;
- end;
- function StrToUInt64Def(const S: string; Default: UInt64): UInt64;
- begin
- result:=StrToQWordDef(S,Default);
- end;
- { LoadStr returns the string resource Ident. }
- function LoadStr(Ident: integer): string;
- begin
- result:='';
- end;
- { FmtLoadStr returns the string resource Ident and formats it accordingly }
- function FmtLoadStr(Ident: integer; const Args: array of const): string;
- begin
- result:='';
- end;
- Const
- feInvalidFormat = 1;
- feMissingArgument = 2;
- feInvalidArgIndex = 3;
- {$ifdef fmtdebug}
- Procedure Log (Const S: String);
- begin
- Writeln (S);
- end;
- {$endif}
- Procedure DoFormatError (ErrCode : Longint;const fmt:ansistring);
- Var
- S : String;
- begin
- //!! must be changed to contain format string...
- S:=fmt;
- Case ErrCode of
- feInvalidFormat : raise EConvertError.Createfmt(SInvalidFormat,[s]);
- feMissingArgument : raise EConvertError.Createfmt(SArgumentMissing,[s]);
- feInvalidArgIndex : raise EConvertError.Createfmt(SInvalidArgIndex,[s]);
- end;
- end;
- { we've no templates, but with includes we can simulate this :) }
- {$macro on}
- {$define INFORMAT}
- {$define TFormatString:=ansistring}
- {$define TFormatChar:=AnsiChar}
- Function Format (Const Fmt : AnsiString; const Args : Array of const; const FormatSettings: TFormatSettings) : AnsiString;
- {$i sysformt.inc}
- {$undef TFormatString}
- {$undef TFormatChar}
- {$undef INFORMAT}
- {$macro off}
- Function Format (Const Fmt : AnsiString; const Args : Array of const) : AnsiString;
- begin
- Result:=Format(Fmt,Args,DefaultFormatSettings);
- end;
- function SafeFormat (const Fmt: AnsiString; Args: array of const): UTF8String;
- begin
- Result:=SafeFormat(Fmt,Args,DefaultFormatSettings);
- end;
- function SafeFormat (const Fmt: AnsiString; Args: array of const; const FormatSettings: TFormatSettings): UTF8String;
- begin
- try
- Result:=Format(Fmt,Args,FormatSettings);
- except
- On E : Exception do
- Result:='Error "'+E.ClassName+'" during format('''+Fmt+''',['+ArrayOfConstToStr(Args,',','{','}')+']) : '+E.Message;
- end;
- end;
- Function FormatBuf (Var Buffer; BufLen : Cardinal; Const Fmt; fmtLen : Cardinal; Const Args : Array of const; Const FormatSettings: TFormatSettings) : Cardinal;
- Var S,F : AnsiString;
- begin
- Setlength(F,fmtlen);
- if fmtlen > 0 then
- Move(fmt,F[1],fmtlen);
- S:=Format (F,Args,FormatSettings);
- If Cardinal(Length(S))<Buflen then
- Result:=Length(S)
- else
- Result:=Buflen;
- Move(S[1],Buffer,Result);
- end;
- Function FormatBuf (Var Buffer; BufLen : Cardinal;
- Const Fmt; fmtLen : Cardinal;
- Const Args : Array of const) : Cardinal;
- begin
- Result:=FormatBuf(Buffer,BufLen,Fmt,FmtLen,Args,DefaultFormatSettings);
- end;
- Procedure FmtStr(Var Res: string; const Fmt : string; Const args: Array of const; Const FormatSettings: TFormatSettings);
- begin
- Res:=Format(fmt,Args,FormatSettings);
- end;
- Procedure FmtStr(Var Res: String; Const Fmt : String; Const args: Array of const);
- begin
- FmtStr(Res,Fmt,Args,DefaultFormatSettings);
- end;
- Function StrFmt(Buffer,Fmt : PChar; Const args: Array of const) : PChar;
- begin
- Result:=StrFmt(Buffer,Fmt,Args,DefaultFormatSettings);
- end;
- Function StrFmt(Buffer,Fmt : PChar; Const Args: Array of const; Const FormatSettings: TFormatSettings): PChar;
- Var
- Len : Integer;
- begin
- {$if SIZEOF(Char)=2}
- Len:=UnicodeFormatBuf(Buffer^,Maxint,Fmt^,strlen(fmt),args,FormatSettings);
- {$ELSE}
- Len:=FormatBuf(Buffer^,Maxint,Fmt^,strlen(fmt),args,FormatSettings);
- {$ENDIF}
- Buffer[Len]:=#0;
- Result:=Buffer;
- end;
- Function StrLFmt(Buffer : PChar; Maxlen : Cardinal;Fmt : PChar; Const args: Array of const) : PChar;
- begin
- Result:=StrLFmt(Buffer,MaxLen,Fmt,Args,DefaultFormatSettings);
- end;
- Function StrLFmt(Buffer : PChar; Maxlen : Cardinal;Fmt : PChar; Const args: Array of const; Const FormatSettings: TFormatSettings) : PChar;
- var
- Len : integer;
- begin
- {$if SIZEOF(Char)=2}
- Len:=UnicodeFormatBuf(Buffer^,MaxLen,Fmt^,strlen(fmt),args,FormatSettings);
- {$ELSE}
- Len:=FormatBuf(Buffer^,MaxLen,Fmt^,strlen(fmt),args,FormatSettings);
- {$ENDIF}
- Buffer[Len]:=#0;
- Result:=Buffer;
- end;
- {$ifndef FPUNONE}
- Function InternalTextToFloat(S: String; Out Value; ValueType: TFloatValue;
- Const FormatSettings: TFormatSettings): Boolean;
- Var
- E,P : Integer;
- Begin
- if S = '' then
- exit(false);
- //ThousandSeparator not allowed as by Delphi specs
- if (FormatSettings.ThousandSeparator <> FormatSettings.DecimalSeparator) and
- (Pos(FormatSettings.ThousandSeparator, S) <> 0) then
- begin
- Result := False;
- Exit;
- end;
- if (FormatSettings.DecimalSeparator <> '.') then
- begin
- if (Pos('.', S) <>0) then
- begin
- Result := False;
- Exit;
- end;
- P:=Pos(FormatSettings.DecimalSeparator,S);
- If (P<>0) Then
- S[P] := '.';
- end;
- s:=Trim(s);
- try
- case ValueType of
- fvCurrency:
- Val(S,Currency(Value),E);
- fvExtended:
- Val(S,Extended(Value),E);
- fvDouble:
- Val(S,Double(Value),E);
- fvSingle:
- Val(S,Single(Value),E);
- fvComp:
- Val(S,Comp(Value),E);
- fvReal:
- Val(S,Real(Value),E);
- end;
- { on x87, a floating point exception may be pending in case of an invalid
- input value -> trigger it now }
- {$if defined(cpui386) or (defined(cpux86_64) and not(defined(win64))) or defined(cpui8086)}
- asm
- fwait
- end;
- {$endif}
- except
- E:=1;
- end;
- Result:=(E=0);
- End;
- Function InternalTextToFloat(S: String; Out Value: Extended;
- Const FormatSettings: TFormatSettings): Boolean;
- Var
- E,P : Integer;
- Begin
- if S = '' then
- exit(false);
- //ThousandSeparator not allowed as by Delphi specs
- if (FormatSettings.ThousandSeparator <> FormatSettings.DecimalSeparator) and
- (Pos(FormatSettings.ThousandSeparator, S) <> 0) then
- begin
- Result := False;
- Exit;
- end;
- if (FormatSettings.DecimalSeparator <> '.') then
- begin
- if (Pos('.', S) <>0) then
- begin
- Result := False;
- Exit;
- end;
- P:=Pos(FormatSettings.DecimalSeparator,S);
- If (P<>0) Then
- S[P] := '.';
- end;
- try
- Val(trim(S),Value,E);
- { on x87, a floating point exception may be pending in case of an invalid
- input value -> trigger it now }
- {$if defined(cpui386) or (defined(cpux86_64) and not(defined(win64))) or defined(cpui8086)}
- asm
- fwait
- end;
- {$endif}
- except
- E:=1;
- end;
- Result:=(E=0);
- End;
- {$IF SIZEOF(CHAR)=2}
- Function TextToFloat(Buffer: PAnsiChar; Out Value; ValueType: TFloatValue): Boolean;
- begin
- Result:=TextToFloat(Buffer,Value,ValueType,DefaultFormatSettings);
- end;
- Function TextToFloat(Buffer: PAnsiChar; Out Value; ValueType: TFloatValue; Const FormatSettings: TFormatSettings): Boolean;
- Var
- E,P : Integer;
- S : AnsiString;
- Begin
- S:=StrPas(Buffer);
- //ThousandSeparator not allowed as by Delphi specs
- if (FormatSettings.ThousandSeparator <> FormatSettings.DecimalSeparator) and
- (Pos(FormatSettings.ThousandSeparator, S) <> 0) then
- begin
- Result := False;
- Exit;
- end;
- if (FormatSettings.DecimalSeparator <> '.') and
- (Pos('.', S) <>0) then
- begin
- Result := False;
- Exit;
- end;
- P:=Pos(FormatSettings.DecimalSeparator,S);
- If (P<>0) Then
- S[P] := '.';
- s:=Trim(s);
- try
- case ValueType of
- fvCurrency:
- Val(S,Currency(Value),E);
- fvExtended:
- Val(S,Extended(Value),E);
- fvDouble:
- Val(S,Double(Value),E);
- fvSingle:
- Val(S,Single(Value),E);
- fvComp:
- Val(S,Comp(Value),E);
- fvReal:
- Val(S,Real(Value),E);
- end;
- { on x87, a floating point exception may be pending in case of an invalid
- input value -> trigger it now }
- {$if defined(cpui386) or (defined(cpux86_64) and not(defined(win64))) or defined(cpui8086)}
- asm
- fwait
- end;
- {$endif}
- except
- E:=1;
- end;
- Result:=(E=0);
- End;
- {$ENDIF}
- Function StrToFloat(Const S: String): Extended;
- begin
- Result:=StrToFloat(S,DefaultFormatSettings);
- end;
- Function StrToFloat(Const S : String; Const FormatSettings: TFormatSettings) : Extended;
- Begin
- If Not InternalTextToFloat(S,Result,FormatSettings) then
- Raise EConvertError.createfmt(SInValidFLoat,[S]);
- End;
- function StrToFloatDef(const S: string; const Default: Extended): Extended;
- begin
- Result:=StrToFloatDef(S,Default,DefaultFormatSettings);
- end;
- Function StrToFloatDef(Const S: String; Const Default: Extended; Const FormatSettings: TFormatSettings): Extended;
- begin
- if not InternalTextToFloat(S,Result,fvExtended,FormatSettings) then
- Result:=Default;
- end;
- Function TextToFloat(Buffer: PChar; Out Value: Extended; Const FormatSettings: TFormatSettings): Boolean;
- begin
- Result := InternalTextToFloat(StrPas(Buffer), Value, FormatSettings);
- End;
- Function TextToFloat(Buffer: PChar; Out Value: Extended): Boolean;
- begin
- Result:=InternalTextToFloat(StrPas(Buffer),Value,DefaultFormatSettings);
- end;
- Function TextToFloat(Buffer: PChar; Out Value; ValueType: TFloatValue): Boolean;
- begin
- Result:=TextToFloat(Buffer,Value,ValueType,DefaultFormatSettings);
- end;
- Function TextToFloat(Buffer: PChar; Out Value; ValueType: TFloatValue; Const FormatSettings: TFormatSettings): Boolean;
- Begin
- Result := InternalTextToFloat(StrPas(Buffer), Value, ValueType, FormatSettings);
- End;
- Function TryStrToFloat(Const S : String; Out Value: Single): Boolean;
- begin
- Result:=TryStrToFloat(S,Value,DefaultFormatSettings);
- end;
- Function TryStrToFloat(Const S : String; Out Value: Single; Const FormatSettings: TFormatSettings): Boolean;
- Begin
- Result := InternalTextToFloat(S, Value, fvSingle,FormatSettings);
- End;
- Function TryStrToFloat(Const S : String; Out Value: Double): Boolean;
- begin
- Result:=TryStrToFloat(S,Value,DefaultFormatSettings);
- end;
- Function TryStrToFloat(Const S : String; Out Value: Double; Const FormatSettings: TFormatSettings): Boolean;
- Begin
- Result := InternalTextToFloat(S, Value, fvDouble,FormatSettings);
- End;
- {$ifdef FPC_HAS_TYPE_EXTENDED}
- Function TryStrToFloat(Const S : String; Out Value: Extended): Boolean;
- begin
- Result:=TryStrToFloat(S,Value,DefaultFormatSettings);
- end;
- Function TryStrToFloat(Const S : String; Out Value: Extended; Const FormatSettings: TFormatSettings): Boolean;
- Begin
- Result := InternalTextToFloat(S, Value,FormatSettings);
- End;
- {$endif FPC_HAS_TYPE_EXTENDED}
- const
- {$ifdef FPC_HAS_TYPE_EXTENDED}
- maxdigits = 17;
- {$else}
- maxdigits = 15;
- {$endif}
- Function FloatToStrFIntl(const Value; format: TFloatFormat; Precision, Digits: Integer; ValueType: TFloatValue; Const FormatSettings: TFormatSettings): String;
- Var
- P, PE, Q, Exponent: Integer;
- Negative: Boolean;
- DS: Char;
- function RemoveLeadingNegativeSign(var AValue: String): Boolean;
- // removes negative sign in case when result is zero eg. -0.00
- var
- i: PtrInt;
- TS: Char;
- StartPos: PtrInt;
- begin
- Result := False;
- if Format = ffCurrency then
- StartPos := 1
- else
- StartPos := 2;
- TS := FormatSettings.ThousandSeparator;
- for i := StartPos to length(AValue) do
- begin
- Result := (AValue[i] in ['0', DS, 'E', '+', TS]);
- if not Result then
- break;
- end;
- if (Result) and (Format <> ffCurrency) then
- Delete(AValue, 1, 1);
- end;
- Begin
- DS:=FormatSettings.DecimalSeparator;
- Case format Of
- ffGeneral:
- Begin
- case ValueType of
- fvCurrency:
- If (Precision = -1) Or (Precision > 19) Then Precision := 19;
- else
- If (Precision = -1) Or (Precision > maxdigits) Then Precision := maxdigits;
- end;
- { First convert to scientific format, with correct precision }
- case ValueType of
- fvDouble:
- Str(Double(Extended(Aligned(Value))):precision+7, Result);
- fvSingle:
- Str(Single(Extended(Aligned(Value))):precision+6, Result);
- fvCurrency:
- Str(Currency(Aligned(Value)):precision+6, Result);
- else
- Str(Extended(Aligned(Value)):precision+8, Result);
- end;
- { Delete leading spaces }
- while Result[1] = ' ' do
- System.Delete(Result, 1, 1);
- P := Pos('.', Result);
- if P<>0 then
- Result[P] := DS
- else
- Exit; { NAN or other special case }
- { Consider removing exponent }
- PE:=Pos('E',Result);
- if PE > 0 then begin
- { Read exponent }
- Q := PE+2;
- Exponent := 0;
- while (Q <= Length(Result)) do begin
- Exponent := Exponent*10 + Ord(Result[Q])-Ord('0');
- Inc(Q);
- end;
- if Result[PE+1] = '-' then
- Exponent := -Exponent;
- if (P+Exponent < PE) and (Exponent > -6) then begin
- { OK to remove exponent }
- SetLength(Result,PE-1); { Trim exponent }
- if Exponent >= 0 then begin
- { Shift point to right }
- for Q := 0 to Exponent-1 do begin
- Result[P] := Result[P+1];
- Inc(P);
- end;
- Result[P] := DS;
- P := 1;
- if Result[P] = '-' then
- Inc(P);
- while (Result[P] = '0') and (P < Length(Result)) and (Result[P+1] <> DS) do
- { Trim leading zeros; conversion above should not give any, but occasionally does
- because of rounding }
- System.Delete(Result,P,1);
- end else begin
- { Add zeros at start }
- Insert(Copy('00000',1,-Exponent),Result,P-1);
- Result[P-Exponent] := Result[P-Exponent-1]; { Copy leading digit }
- Result[P] := DS;
- if Exponent <> -1 then
- Result[P-Exponent-1] := '0';
- end;
- { Remove trailing zeros }
- Q := Length(Result);
- while (Q > 0) and (Result[Q] = '0') do
- Dec(Q);
- if Result[Q] = DS then
- Dec(Q); { Remove trailing decimal point }
- if (Q = 0) or ((Q=1) and (Result[1] = '-')) then
- Result := '0'
- else
- SetLength(Result,Q);
- end else begin
- { Need exponent, but remove superfluous characters }
- { Delete trailing zeros }
- while Result[PE-1] = '0' do begin
- System.Delete(Result,PE-1,1);
- Dec(PE);
- end;
- { If number ends in decimal point, remove it }
- if Result[PE-1] = DS then begin
- System.Delete(Result,PE-1,1);
- Dec(PE);
- end;
- { delete superfluous + in exponent }
- if Result[PE+1]='+' then
- System.Delete(Result,PE+1,1)
- else
- Inc(PE);
- while Result[PE+1] = '0' do
- { Delete leading zeros in exponent }
- System.Delete(Result,PE+1,1)
- end;
- end;
- End;
- ffExponent:
- Begin
- If (Precision = -1) Or (Precision > maxdigits) Then Precision := maxdigits;
- case ValueType of
- fvDouble:
- Str(Double(Extended(Aligned(Value))):Precision+7, Result);
- fvSingle:
- Str(Single(Extended(Aligned(Value))):Precision+6, Result);
- fvCurrency:
- Str(Currency(Aligned(Value)):Precision+6, Result);
- else
- Str(Extended(Aligned(Value)):Precision+8, Result);
- end;
- { Delete leading spaces }
- while Result[1] = ' ' do
- System.Delete(Result, 1, 1);
- if (Result[1]='-') and
- { not Nan etc.? }
- (Result[3]='.') then
- Result[3] := DS
- else if Result[2]='.' then
- Result[2] := DS;
- P:=Pos('E',Result);
- if P <> 0 then
- begin
- Inc(P, 2);
- if Digits > 4 then
- Digits:=4;
- Digits:=Length(Result) - P - Digits + 1;
- if Digits < 0 then
- insert(copy('0000',1,-Digits),Result,P)
- else
- while (Digits > 0) and (Result[P] = '0') do
- begin
- System.Delete(Result, P, 1);
- if P > Length(Result) then
- begin
- System.Delete(Result, P - 2, 2);
- break;
- end;
- Dec(Digits);
- end;
- end;
- End;
- ffFixed:
- Begin
- If Digits = -1 Then Digits := 2
- Else If Digits > 18 Then Digits := 18;
- case ValueType of
- fvDouble:
- Str(Double(Extended(Aligned(Value))):0:Digits, Result);
- fvSingle:
- Str(Single(Extended(Aligned(Value))):0:Digits, Result);
- fvCurrency:
- Str(Currency(Aligned(Value)):0:Digits, Result);
- else
- Str(Extended(Aligned(Value)):0:Digits, Result);
- end;
- If Result[1] = ' ' Then
- System.Delete(Result, 1, 1);
- P := Pos('.', Result);
- If P <> 0 Then Result[P] := DS;
- End;
- ffNumber:
- Begin
- If Digits = -1 Then Digits := 2
- Else If Digits > maxdigits Then Digits := maxdigits;
- case ValueType of
- fvDouble:
- Str(Double(Extended(Aligned(Value))):0:Digits, Result);
- fvSingle:
- Str(Single(Extended(Aligned(Value))):0:Digits, Result);
- fvCurrency:
- Str(Currency(Aligned(Value)):0:Digits, Result);
- else
- Str(Extended(Aligned(Value)):0:Digits, Result);
- end;
- If Result[1] = ' ' Then System.Delete(Result, 1, 1);
- P := Pos('.', Result);
- If P <> 0 Then
- Result[P] := DS
- else
- P := Length(Result)+1;
- Dec(P, 3);
- While (P > 1) Do
- Begin
- If (Result[P - 1] <> '-') And (FormatSettings.ThousandSeparator <> #0) Then
- Insert(FormatSettings.ThousandSeparator, Result, P);
- Dec(P, 3);
- End;
- End;
- ffCurrency:
- Begin
- If Digits = -1 Then Digits := FormatSettings.CurrencyDecimals
- Else If Digits > 18 Then Digits := 18;
- case ValueType of
- fvDouble:
- Str(Double(Extended(Aligned(Value))):0:Digits, Result);
- fvSingle:
- Str(Single(Extended(Aligned(Value))):0:Digits, Result);
- fvCurrency:
- Str(Currency(Aligned(Value)):0:Digits, Result);
- else
- Str(Extended(Aligned(Value)):0:Digits, Result);
- end;
- Negative:=Result[1] = '-';
- if Negative then
- System.Delete(Result, 1, 1);
- P := Pos('.', Result);
- If P <> 0 Then Result[P] := DS else P := Length(Result)+1;
- Dec(P, 3);
- While (P > 1) Do
- Begin
- If FormatSettings.ThousandSeparator<>#0 Then
- Insert(FormatSettings.ThousandSeparator, Result, P);
- Dec(P, 3);
- End;
- if (length(Result) > 1) and Negative then
- Negative := not RemoveLeadingNegativeSign(Result);
- If Not Negative Then
- Begin
- Case FormatSettings.CurrencyFormat Of
- 0: Result := FormatSettings.CurrencyString + Result;
- 1: Result := Result + FormatSettings.CurrencyString;
- 2: Result := FormatSettings.CurrencyString + ' ' + Result;
- 3: Result := Result + ' ' + FormatSettings.CurrencyString;
- End
- End
- Else
- Begin
- Case FormatSettings.NegCurrFormat Of
- 0: Result := '(' + FormatSettings.CurrencyString + Result + ')';
- 1: Result := '-' + FormatSettings.CurrencyString + Result;
- 2: Result := FormatSettings.CurrencyString + '-' + Result;
- 3: Result := FormatSettings.CurrencyString + Result + '-';
- 4: Result := '(' + Result + FormatSettings.CurrencyString + ')';
- 5: Result := '-' + Result + FormatSettings.CurrencyString;
- 6: Result := Result + '-' + FormatSettings.CurrencyString;
- 7: Result := Result + FormatSettings.CurrencyString + '-';
- 8: Result := '-' + Result + ' ' + FormatSettings.CurrencyString;
- 9: Result := '-' + FormatSettings.CurrencyString + ' ' + Result;
- 10: Result := Result + ' ' + FormatSettings.CurrencyString + '-';
- 11: Result := FormatSettings.CurrencyString + ' ' + Result + '-';
- 12: Result := FormatSettings.CurrencyString + ' ' + '-' + Result;
- 13: Result := Result + '-' + ' ' + FormatSettings.CurrencyString;
- 14: Result := '(' + FormatSettings.CurrencyString + ' ' + Result + ')';
- 15: Result := '(' + Result + ' ' + FormatSettings.CurrencyString + ')';
- End;
- End;
- End;
- End;
- if not (format in [ffCurrency]) and (length(Result) > 1) and (Result[1] = '-') then
- RemoveLeadingNegativeSign(Result);
- End;
- {$macro off}
- {$ifdef FPC_HAS_TYPE_EXTENDED}
- Function FloatToStr(Value: Extended; Const FormatSettings: TFormatSettings): String;
- Begin
- Result := FloatToStrFIntl(Value, ffGeneral, 15, 0, fvExtended,FormatSettings);
- End;
- Function FloatToStr(Value: Extended): String;
- begin
- Result:=FloatToStr(Value,DefaultFormatSettings);
- end;
- {$endif FPC_HAS_TYPE_EXTENDED}
- Function FloatToStr(Value: Currency; Const FormatSettings: TFormatSettings): String;
- Begin
- Result := FloatToStrFIntl(Value, ffGeneral, 15, 0, fvCurrency,FormatSettings);
- End;
- Function FloatToStr(Value: Currency): String;
- begin
- Result:=FloatToStr(Value,DefaultFormatSettings);
- end;
- Function FloatToStr(Value: Double; Const FormatSettings: TFormatSettings): String;
- var
- e: Extended;
- Begin
- e := Value;
- Result := FloatToStrFIntl(e, ffGeneral, 15, 0, fvDouble,FormatSettings);
- End;
- Function FloatToStr(Value: Double): String;
- begin
- Result:=FloatToStr(Value,DefaultFormatSettings);
- end;
- Function FloatToStr(Value: Single; Const FormatSettings: TFormatSettings): String;
- var
- e: Extended;
- Begin
- e := Value;
- Result := FloatToStrFIntl(e, ffGeneral, 15, 0, fvSingle,FormatSettings);
- End;
- Function FloatToStr(Value: Single): String;
- begin
- Result:=FloatToStr(Value,DefaultFormatSettings);
- end;
- Function FloatToStr(Value: Comp; Const FormatSettings: TFormatSettings): String;
- var
- e: Extended;
- Begin
- e := Value;
- Result := FloatToStrFIntl(e, ffGeneral, 15, 0, fvComp,FormatSettings);
- End;
- Function FloatToStr(Value: Comp): String;
- begin
- Result:=FloatToStr(Value,DefaultFormatSettings);
- end;
- {$ifndef FPC_COMP_IS_INT64}
- Function FloatToStr(Value: Int64): String;
- begin
- Result:=FloatToStr(Value,DefaultFormatSettings);
- end;
- Function FloatToStr(Value: Int64; Const FormatSettings: TFormatSettings): String;
- var
- e: Extended;
- Begin
- e := Comp(Value);
- Result := FloatToStrFIntl(e, ffGeneral, 15, 0, fvComp,FormatSettings);
- End;
- {$endif FPC_COMP_IS_INT64}
- Function FloatToText(Buffer: PAnsiChar; Value: Extended; format: TFloatFormat; Precision, Digits: Integer; Const FormatSettings: TFormatSettings): Longint;
- Var
- Tmp: String[40];
- Begin
- Tmp := FloatToStrF(Value, format, Precision, Digits,FormatSettings);
- Result := Length(Tmp);
- Move(Tmp[1], Buffer[0], Result);
- End;
- Function FloatToText(Buffer: PWideChar; Value: Extended; format: TFloatFormat; Precision, Digits: Integer; Const FormatSettings: TFormatSettings): Longint;
- Var
- Tmp: UnicodeString;
- Begin
- Tmp := FloatToStrF(Value, format, Precision, Digits,FormatSettings);
- Result := Length(Tmp);
- Move(Tmp[1], Buffer[0], Result*SizeOf(WideChar));
- End;
- Function FloatToText(Buffer: PAnsiChar; Value: Extended; format: TFloatFormat; Precision, Digits: Integer): Longint;
- begin
- Result:=FloatToText(Buffer,Value,Format,Precision,Digits,DefaultFormatSettings);
- end;
- Function FloatToText(Buffer: PWideChar; Value: Extended; format: TFloatFormat; Precision, Digits: Integer): Longint;
- begin
- Result:=FloatToText(Buffer,Value,Format,Precision,Digits,DefaultFormatSettings);
- end;
- {$ifdef FPC_HAS_TYPE_EXTENDED}
- Function FloatToStrF(Value: Extended; format: TFloatFormat; Precision, Digits: Integer; Const FormatSettings: TFormatSettings): String;
- begin
- Result := FloatToStrFIntl(value,format,precision,digits,fvExtended,FormatSettings);
- end;
- Function FloatToStrF(Value: Extended; format: TFloatFormat; Precision, Digits: Integer): String;
- begin
- Result:=FloatToStrF(Value,Format,Precision,Digits,DefaultFormatSettings);
- end;
- {$endif}
- Function FloatToStrF(Value: Currency; format: TFloatFormat; Precision, Digits: Integer; Const FormatSettings: TFormatSettings): String;
- begin
- Result := FloatToStrFIntl(value,format,precision,digits,fvCurrency,FormatSettings);
- end;
- Function FloatToStrF(Value: Currency; format: TFloatFormat; Precision, Digits: Integer): String;
- begin
- Result:=FloatToStrF(Value,format,Precision,Digits,DefaultFormatSettings);
- end;
- Function FloatToStrF(Value: Double; format: TFloatFormat; Precision, Digits: Integer; Const FormatSettings: TFormatSettings): String;
- var
- e: Extended;
- begin
- e := Value;
- result := FloatToStrFIntl(e,format,precision,digits,fvDouble,FormatSettings);
- end;
- Function FloatToStrF(Value: Double; format: TFloatFormat; Precision, Digits: Integer): String;
- begin
- Result:= FloatToStrF(Value,Format,Precision,Digits,DefaultFormatSettings);
- end;
- Function FloatToStrF(Value: Single; format: TFloatFormat; Precision, Digits: Integer; Const FormatSettings: TFormatSettings): String;
- var
- e: Extended;
- begin
- e:=Value;
- result := FloatToStrFIntl(e,format,precision,digits,fvSingle,FormatSettings);
- end;
- Function FloatToStrF(Value: Single; format: TFloatFormat; Precision, Digits: Integer): String;
- begin
- Result:= FloatToStrF(Value,Format,Precision,Digits,DefaultFormatSettings);
- end;
- Function FloatToStrF(Value: Comp; format: TFloatFormat; Precision, Digits: Integer; Const FormatSettings: TFormatSettings): String;
- var
- e: Extended;
- begin
- e := Value;
- Result := FloatToStrFIntl(e,format,precision,digits,fvComp,FormatSettings);
- end;
- Function FloatToStrF(Value: Comp; format: TFloatFormat; Precision, Digits: Integer): String;
- begin
- Result:=FloatToStrF(Value,Format,Precision,Digits,DefaultFormatSettings);
- end;
- {$ifndef FPC_COMP_IS_INT64}
- Function FloatToStrF(Value: Int64; format: TFloatFormat; Precision, Digits: Integer; Const FormatSettings: TFormatSettings): String;
- var
- e: Extended;
- begin
- e := Comp(Value);
- result := FloatToStrFIntl(e,format,precision,digits,fvComp,FormatSettings);
- end;
- Function FloatToStrF(Value: Int64; format: TFloatFormat; Precision, Digits: Integer): String;
- begin
- Result:=FloatToStrF(Value,Format,Precision,Digits,DefaultFormatSettings);
- end;
- {$endif FPC_COMP_IS_INT64}
- Function CurrToStrF(Value: Currency; Format: TFloatFormat; Digits: Integer; Const FormatSettings: TFormatSettings): string;
- begin
- result:=FloatToStrF(Value,Format,19,Digits,FormatSettings);
- end;
- Function CurrToStrF(Value: Currency; Format: TFloatFormat; Digits: Integer): string;
- begin
- Result:=CurrToStrF(Value,Format,Digits,DefaultFormatSettings);
- end;
- Function FloatToDateTime (Const Value : Extended) : TDateTime;
- begin
- If (Value<MinDateTime) or (Value>MaxDateTime) then
- Raise EConvertError.CreateFmt (SInvalidDateTimeFloat,[Value]);
- Result:=Value;
- end;
- function TryFloatToCurr(const Value: Extended; var AResult: Currency): Boolean;
- begin
- Result:=(Value>=MinCurrency) and (Value<=MaxCurrency);
- if Result then
- AResult := Value;
- end;
- function FloatToCurr(const Value: Extended): Currency;
- begin
- if not TryFloatToCurr(Value, Result) then
- Raise EConvertError.CreateFmt(SInvalidCurrency, [FloatToStr(Value)]);
- end;
- Function CurrToStr(Value: Currency): string;
- begin
- Result:=FloatToStrF(Value,ffGeneral,-1,0);
- end;
- Function CurrToStr(Value: Currency; Const FormatSettings: TFormatSettings): string;
- begin
- Result:=FloatToStrF(Value,ffGeneral,-1,0,FormatSettings);
- end;
- function StrToCurr(const S: string): Currency;
- begin
- if not InternalTextToFloat(S, Result, fvCurrency, DefaultFormatSettings) then
- Raise EConvertError.createfmt(SInValidFLoat,[S]);
- end;
- function StrToCurr(const S: string; Const FormatSettings: TFormatSettings): Currency;
- begin
- if not InternalTextToFloat(S, Result, fvCurrency,FormatSettings) then
- Raise EConvertError.createfmt(SInValidFLoat,[S]);
- end;
- Function TryStrToCurr(Const S : String; Out Value: Currency): Boolean;
- Begin
- Result := InternalTextToFloat(S, Value, fvCurrency, DefaultFormatSettings);
- End;
- function TryStrToCurr(const S: string;Out Value : Currency; Const FormatSettings: TFormatSettings): Boolean;
- Begin
- Result := InternalTextToFloat(S, Value, fvCurrency,FormatSettings);
- End;
- function StrToCurrDef(const S: string; Default : Currency): Currency;
- begin
- if not InternalTextToFloat(S, Result, fvCurrency, DefaultFormatSettings) then
- Result:=Default;
- end;
- function StrToCurrDef(const S: string; Default : Currency; Const FormatSettings: TFormatSettings): Currency;
- begin
- if not InternalTextToFloat(S, Result, fvCurrency,FormatSettings) then
- Result:=Default;
- end;
- {$endif FPUNONE}
- function AnsiDequotedStr(const S: string; AQuote: Char): string;
- var p : PChar;
- begin
- p:=PChar(pointer(s)); // work around CONST. Ansiextract is safe for nil
- result:=AnsiExtractquotedStr(p,AQuote);
- end;
- function StrToBool(const S: string): Boolean;
- begin
- if not(TryStrToBool(S,Result,DefaultFormatSettings)) then
- Raise EConvertError.CreateFmt(SInvalidBoolean,[S]);
- end;
- function StrToBool(const S: string; const FormatSettings: TFormatSettings): Boolean;
- begin
- if not(TryStrToBool(S,Result,FormatSettings)) then
- Raise EConvertError.CreateFmt(SInvalidBoolean,[S]);
- end;
- procedure CheckBoolStrs;
- begin
- If Length(TrueBoolStrs)=0 then
- begin
- SetLength(TrueBoolStrs,1);
- TrueBoolStrs[0]:='True';
- end;
- If Length(FalseBoolStrs)=0 then
- begin
- SetLength(FalseBoolStrs,1);
- FalseBoolStrs[0]:='False';
- end;
- end;
- function BoolToStr(B: Boolean;UseBoolStrs:Boolean=False): string;
- begin
- if UseBoolStrs Then
- begin
- CheckBoolStrs;
- if B then
- Result:=TrueBoolStrs[0]
- else
- Result:=FalseBoolStrs[0];
- end
- else
- If B then
- Result:='-1'
- else
- Result:='0';
- end;
- // from textmode IDE util funcs.
- function BoolToStr(B: boolean; const TrueS, FalseS: string): string;
- begin
- if B then Result:=TrueS else BoolToStr:=FalseS;
- end;
- function StrToBoolDef(const S: string; Default: Boolean): Boolean;
- begin
- if not(TryStrToBool(S,Result)) then
- Result:=Default;
- end;
- function StrToBoolDef(const S: string; Default: Boolean; const FormatSettings: TFormatSettings): Boolean;
- begin
- if not(TryStrToBool(S,Result,FormatSettings)) then
- Result:=Default;
- end;
- function TryStrToBool(const S: string; out Value: Boolean): Boolean;
- begin
- Result:=TryStrToBool(S,Value,DefaultFormatSettings);
- end;
- function TryStrToBool(const S: string; out Value: Boolean; const FormatSettings: TFormatSettings): Boolean;
- Var
- Temp : String;
- I : Longint;
- {$ifdef FPUNONE}
- D : Longint;
- {$else}
- D : Double;
- {$endif}
- Code: word;
- begin
- Temp:=upcase(S);
- Val(temp,D,code);
- Result:=true;
- If (Code=0) or TryStrToFloat(S,D,FormatSettings) then
- {$ifdef FPUNONE}
- Value:=(D<>0)
- {$else}
- Value:=(D<>0.0)
- {$endif}
- else
- begin
- CheckBoolStrs;
- for I:=low(TrueBoolStrs) to High(TrueBoolStrs) do
- if Temp=upcase(TrueBoolStrs[I]) then
- begin
- Value:=true;
- exit;
- end;
- for I:=low(FalseBoolStrs) to High(FalseBoolStrs) do
- if Temp=upcase(FalseBoolStrs[I]) then
- begin
- Value:=false;
- exit;
- end;
- Result:=false;
- end;
- end;
- {$ifndef FPUNONE}
- Function FloatToTextFmt(Buffer: PChar; Value: Extended; format: PChar): Integer;
- begin
- Result:=FloatToTextFmt(Buffer,Value,Format,DefaultFormatSettings);
- end;
- {$MACRO ON}
- {$define FPChar:=PAnsiChar}
- {$define FChar:=AnsiChar}
- {$define FString:=AnsiString}
- {$I fmtflt.inc}
- {$undef FPChar}
- {$undef FChar}
- {$undef FString}
- {$MACRO ON}
- {$define FPChar:=PWideChar}
- {$define FChar:=WideChar}
- {$define FString:=UnicodeString}
- {$I fmtflt.inc}
- {$define FPChar:=PAnsiChar}
- {$define FChar:=AnsiChar}
- {$define FString:=AnsiString}
- Function FloatToTextFmt(Buffer: PChar; Value: Extended; format: PChar; FormatSettings : TFormatSettings): Integer;
- begin
- Result:=IntFloatToTextFmt(Buffer,Value,fvExtended,Format,FormatSettings);
- end;
- Procedure FloatToDecimal(Out Result: TFloatRec; const Value; ValueType: TFloatValue; Precision, Decimals : integer);
- var
- Buffer: String[254]; //Though str func returns only 25 chars, this might change in the future
- InfNan: string[3];
- Error, N, L, Start, C: Integer;
- GotNonZeroBeforeDot, BeforeDot : boolean;
- begin
- case ValueType of
- fvExtended:
- Str(Extended(Value):25, Buffer);
- fvDouble,
- fvReal:
- Str(Double(Value):23, Buffer);
- fvSingle:
- Str(Single(Value):16, Buffer);
- fvCurrency:
- Str(Currency(Value):25, Buffer);
- fvComp:
- Str(Currency(Value):23, Buffer);
- end;
- N := 1;
- L := Byte(Buffer[0]);
- while Buffer[N]=' ' do
- Inc(N);
- Result.Negative := (Buffer[N] = '-');
- if Result.Negative then
- Inc(N)
- else if (Buffer[N] = '+') then
- inc(N);
- { special cases for Inf and Nan }
- if (L>=N+2) then
- begin
- InfNan:=copy(Buffer,N,3);
- if (InfNan='Inf') then
- begin
- Result.Digits[0]:=#0;
- Result.Exponent:=32767;
- exit
- end;
- if (InfNan='Nan') then
- begin
- Result.Digits[0]:=#0;
- Result.Exponent:=-32768;
- exit
- end;
- end;
- Start := N; //Start of digits
- Result.Exponent := 0; BeforeDot := true;
- GotNonZeroBeforeDot := false;
- while (L>=N) and (Buffer[N]<>'E') do
- begin
- if Buffer[N]='.' then
- BeforeDot := false
- else
- begin
- if BeforeDot then
- begin // Currently this is always 1 AnsiChar
- Inc(Result.Exponent);
- Result.Digits[N-Start] := Buffer[N];
- if Buffer[N] <> '0' then
- GotNonZeroBeforeDot := true;
- end
- else
- Result.Digits[N-Start-1] := Buffer[N]
- end;
- Inc(N);
- end;
- Inc(N); // Pass through 'E'
- if N<=L then
- begin
- Val(Copy(Buffer, N, L-N+1), C, Error); // Get exponent after 'E'
- Inc(Result.Exponent, C);
- end;
- // Calculate number of digits we have from str
- if BeforeDot then
- N := N - Start - 1
- else
- N := N - Start - 2;
- L := SizeOf(Result.Digits);
- if N<L then
- FillChar(Result.Digits[N], L-N, '0'); //Zero remaining space
- if Decimals + Result.Exponent < Precision Then //After this it is the same as in FloatToDecimal
- N := Decimals + Result.Exponent
- Else
- N := Precision;
- if N >= L Then
- N := L-1;
- if N = 0 Then
- begin
- if Result.Digits[0] >= '5' Then
- begin
- Result.Digits[0] := '1';
- Result.Digits[1] := #0;
- Inc(Result.Exponent);
- end
- Else
- Result.Digits[0] := #0;
- end //N=0
- Else if N > 0 Then
- begin
- if Result.Digits[N] >= '5' Then
- begin
- Repeat
- Result.Digits[N] := #0;
- Dec(N);
- Inc(Result.Digits[N]);
- Until (N = 0) Or (Result.Digits[N] < ':');
- If Result.Digits[0] = ':' Then
- begin
- Result.Digits[0] := '1';
- Inc(Result.Exponent);
- end;
- end
- Else
- begin
- Result.Digits[N] := '0';
- While (N > -1) And (Result.Digits[N] = '0') Do
- begin
- Result.Digits[N] := #0;
- Dec(N);
- end;
- end;
- end //N>0
- Else
- Result.Digits[0] := #0;
- if (Result.Digits[0] = #0) and
- not GotNonZeroBeforeDot then
- begin
- Result.Exponent := 0;
- Result.Negative := False;
- end;
- end;
- Procedure FloatToDecimal(Out Result: TFloatRec; Value: Extended; Precision, Decimals : integer);
- begin
- FloatToDecimal(Result,Value,fvExtended,Precision,Decimals);
- end;
- Function FormatFloat(Const Format : String; Value : Extended; Const FormatSettings: TFormatSettings) : String;
- Var
- buf : Array[0..1024] of Char;
- Len: Integer;
- Begin
- Len:=FloatToTextFmt(PChar(@Buf[0]),Value,PChar(Format),FormatSettings);
- Buf[Len]:=#0;
- Result:=StrPas(Pchar(@Buf[0]));
- End;
- Function FormatFloat(Const format: String; Value: Extended): String;
- begin
- Result:=FormatFloat(Format,Value,DefaultFormatSettings);
- end;
- Function FormatCurr(const Format: string; Value: Currency; Const FormatSettings: TFormatSettings): string;
- begin
- Result := FormatFloat(Format, Value,FormatSettings);
- end;
- function FormatCurr(const Format: string; Value: Currency): string;
- begin
- Result:=FormatCurr(Format,Value,DefaultFormatSettings);
- end;
- {$endif}
- {==============================================================================}
- { extra functions }
- {==============================================================================}
- { LeftStr returns Count left-most characters from S }
- function LeftStr(const S: string; Count: integer): string;
- begin
- result := Copy(S, 1, Count);
- end ;
- { RightStr returns Count right-most characters from S }
- function RightStr(const S: string; Count: integer): string;
- begin
- If Count>Length(S) then
- Count:=Length(S);
- result := Copy(S, 1 + Length(S) - Count, Count);
- end;
- { BCDToInt converts the BCD value Value to an integer }
- function BCDToInt(Value: integer): integer;
- var i, j, digit: integer;
- begin
- result := 0;
- j := 1;
- for i := 0 to SizeOf(Value) shl 1 - 1 do begin
- digit := Value and 15;
- if digit > $9 then
- begin
- if i = 0 then
- begin
- if digit in [$B, $D] then j := -1
- end
- else raise EConvertError.createfmt(SInvalidBCD,[Value]);
- end
- else
- begin
- result := result + j * digit;
- j := j * 10;
- end ;
- Value := Value shr 4;
- end ;
- end ;
- Function LastDelimiter(const Delimiters, S: string): SizeInt;
- var
- chs: TSysCharSet;
- I: SizeInt;
- begin
- chs := [];
- for I := 1 to Length(Delimiters) do
- Include(chs, Delimiters[I]);
- Result:=Length(S);
- While (Result>0) and not (S[Result] in chs) do
- Dec(Result);
- end;
- {$macro on}
- {$define INSTRINGREPLACE}
- {$define SRString:=AnsiString}
- {$define SRUpperCase:=AnsiUppercase}
- {$define SRPCHAR:=PAnsiChar}
- {$define SRCHAR:=AnsiChar}
- Function StringReplace(const S, OldPattern, NewPattern: Ansistring; Flags: TReplaceFlags): Ansistring;
- Var
- C : Integer;
- begin
- Result:=StringReplace(S,OldPattern,NewPattern,Flags,C);
- end;
- function StringReplace(const S, OldPattern, NewPattern: Ansistring; Flags: TReplaceFlags; Out aCount : Integer): Ansistring;
- {$i syssr.inc}
- {$undef INSTRINGREPLACE}
- {$undef SRString}
- {$undef SRUpperCase}
- {$undef SRPCHAR}
- {$undef SRCHAR}
- Function IsDelimiter(const Delimiters, S: string; Index: SizeInt): Boolean;
- begin
- Result:=False;
- If (Index>0) and (Index<=Length(S)) then
- Result:=Pos(S[Index],Delimiters)<>0; // Note we don't do MBCS yet
- end;
- Function ByteToCharLen(const S: string; MaxLen: SizeInt): SizeInt;
- begin
- Result:=Length(S);
- If Result>MaxLen then
- Result:=MaxLen;
- end;
- Function ByteToCharIndex(const S: string; Index: SizeInt): SizeInt;
- begin
- Result:=Index;
- end;
- Function CharToByteLen(const S: string; MaxLen: SizeInt): SizeInt;
- begin
- Result:=Length(S);
- If Result>MaxLen then
- Result:=MaxLen;
- end;
- Function CharToByteIndex(const S: string; Index: SizeInt): SizeInt;
- begin
- Result:=Index;
- end;
- Function ByteType(const S: string; Index: SizeUInt): TMbcsByteType;
- begin
- Result:=mbSingleByte;
- end;
- Function StrByteType(Str: PAnsiChar; Index: SizeUInt): TMbcsByteType;
- begin
- Result:=mbSingleByte;
- end;
- Function StrCharLength(const Str: PAnsiChar): SizeInt;
- begin
- result:=widestringmanager.CharLengthPCharProc(Str);
- end;
- function StrNextChar(const Str: PAnsiChar): PAnsiChar;
- begin
- result:=Str+StrCharLength(Str);
- end;
- Function FindCmdLineSwitch(const Switch: string; const Chars: TSysCharSet;IgnoreCase: Boolean): Boolean;
- Var
- I,L : Integer;
- S,T : String;
- begin
- Result:=False;
- S:=Switch;
- If IgnoreCase then
- S:=UpperCase(S);
- I:=ParamCount;
- While (Not Result) and (I>0) do
- begin
- L:=Length(Paramstr(I));
- If (L>0) and (ParamStr(I)[1] in Chars) then
- begin
- T:=Copy(ParamStr(I),2,L-1);
- If IgnoreCase then
- T:=UpperCase(T);
- Result:=S=T;
- end;
- Dec(i);
- end;
- end;
- Function FindCmdLineSwitch(const Switch: string; IgnoreCase: Boolean): Boolean;
- begin
- Result:=FindCmdLineSwitch(Switch,SwitchChars,IgnoreCase);
- end;
- Function FindCmdLineSwitch(const Switch: string): Boolean;
- begin
- Result:=FindCmdLineSwitch(Switch,SwitchChars,False);
- end;
- function WrapText(const Line, BreakStr: string; const BreakChars: TSysCharSet; MaxCol: Integer): string;
- const
- Quotes = ['''', '"'];
- Var
- L : String;
- C,LQ,BC : AnsiChar;
- P,BLen,Len : Integer;
- HB,IBC : Boolean;
- begin
- Result:='';
- L:=Line;
- Blen:=Length(BreakStr);
- If (BLen>0) then
- BC:=BreakStr[1]
- else
- BC:=#0;
- Len:=Length(L);
- While (Len>0) do
- begin
- P:=1;
- LQ:=#0;
- HB:=False;
- IBC:=False;
- While ((P<=Len) and ((P<=MaxCol) or not IBC)) and ((LQ<>#0) or Not HB) do
- begin
- C:=L[P];
- If (C=LQ) then
- LQ:=#0
- else If (C in Quotes) then
- LQ:=C;
- If (LQ<>#0) then
- Inc(P)
- else
- begin
- HB:=((C=BC) and (BreakStr=Copy(L,P,BLen)));
- If HB then
- Inc(P,Blen)
- else
- begin
- If (P>=MaxCol) then
- IBC:=C in BreakChars;
- Inc(P);
- end;
- end;
- // Writeln('"',C,'" : IBC : ',IBC,' HB : ',HB,' LQ : ',LQ,' P>MaxCol : ',P>MaxCol);
- end;
- Result:=Result+Copy(L,1,P-1);
- Delete(L,1,P-1);
- Len:=Length(L);
- If (Len>0) and Not HB then
- Result:=Result+BreakStr;
- end;
- end;
- function WrapText(const Line: string; MaxCol: Integer): string;
- begin
- Result:=WrapText(Line,sLineBreak, [' ', '-', #9], MaxCol);
- end;
- {$ifndef FPC_NOGENERICANSIROUTINES}
- {
- Case Translation Tables
- Can be used in internationalization support.
- Although these tables can be obtained through system calls
- cd it is better to not use those, since most implementation are not 100%
- WARNING:
- before modifying a translation table make sure that the current codepage
- of the OS corresponds to the one you make changes to
- }
- const
- {$if defined(MSDOS) or defined(GO32V2) or defined(WATCOM) or defined(WIN16) }
- { upper case translation table for character set 850 }
- CP850UCT: array[128..255] of AnsiChar =
- (#128,#154,#144,#182,#142,#182,#143,#128,#210,#211,#212,#216,#215,#222,#142,#143,
- #144,#146,#146,#226,#153,#227,#234,#235,'Y',#153,#154,#157,#156,#157,#158,#159,
- #181,#214,#224,#233,#165,#165,#166,#167,#168,#169,#170,#171,#172,#173,#174,#175,
- #176,#177,#178,#179,#180,#181,#182,#183,#184,#185,#186,#187,#188,#189,#190,#191,
- #192,#193,#194,#195,#196,#197,#199,#199,#200,#201,#202,#203,#204,#205,#206,#207,
- #208,#209,#210,#211,#212,#213,#214,#215,#216,#217,#218,#219,#220,#221,#222,#223,
- #224,#225,#226,#227,#229,#229,#230,#237,#232,#233,#234,#235,#237,#237,#238,#239,
- #240,#241,#242,#243,#244,#245,#246,#247,#248,#249,#250,#251,#252,#253,#254,#255);
- { lower case translation table for character set 850 }
- CP850LCT: array[128..255] of AnsiChar =
- (#135,#129,#130,#131,#132,#133,#134,#135,#136,#137,#138,#139,#140,#141,#132,#134,
- #130,#145,#145,#147,#148,#149,#150,#151,#152,#148,#129,#155,#156,#155,#158,#159,
- #160,#161,#162,#163,#164,#164,#166,#167,#168,#169,#170,#171,#172,#173,#174,#175,
- #176,#177,#178,#179,#180,#160,#131,#133,#184,#185,#186,#187,#188,#189,#190,#191,
- #192,#193,#194,#195,#196,#197,#198,#198,#200,#201,#202,#203,#204,#205,#206,#207,
- #208,#209,#136,#137,#138,#213,#161,#140,#139,#217,#218,#219,#220,#221,#141,#223,
- #162,#225,#147,#149,#228,#228,#230,#237,#232,#163,#150,#151,#236,#236,#238,#239,
- #240,#241,#242,#243,#244,#245,#246,#247,#248,#249,#250,#251,#252,#253,#254,#255);
- {$endif}
- { upper case translation table for character set ISO 8859/1 Latin 1 }
- CPISO88591UCT: array[192..255] of AnsiChar =
- ( #192, #193, #194, #195, #196, #197, #198, #199,
- #200, #201, #202, #203, #204, #205, #206, #207,
- #208, #209, #210, #211, #212, #213, #214, #215,
- #216, #217, #218, #219, #220, #221, #222, #223,
- #192, #193, #194, #195, #196, #197, #198, #199,
- #200, #201, #202, #203, #204, #205, #206, #207,
- #208, #209, #210, #211, #212, #213, #214, #247,
- #216, #217, #218, #219, #220, #221, #222, #89 );
- { lower case translation table for character set ISO 8859/1 Latin 1 }
- CPISO88591LCT: array[192..255] of AnsiChar =
- ( #224, #225, #226, #227, #228, #229, #230, #231,
- #232, #233, #234, #235, #236, #237, #238, #239,
- #240, #241, #242, #243, #244, #245, #246, #215,
- #248, #249, #250, #251, #252, #253, #254, #223,
- #224, #225, #226, #227, #228, #229, #230, #231,
- #232, #233, #234, #235, #236, #237, #238, #239,
- #240, #241, #242, #243, #244, #245, #246, #247,
- #248, #249, #250, #251, #252, #253, #254, #255 );
- {$endif FPC_NOGENERICANSIROUTINES}
- function sscanf(const s: string; const fmt : string;const Pointers : array of Pointer) : Integer;
- var
- i,j,n,m : SizeInt;
- s1 : string;
- function GetInt(unsigned : boolean=false) : Integer;
- begin
- s1 := '';
- while (Length(s) > n) and (s[n] = ' ') do
- inc(n);
- { read sign }
- if (Length(s)>= n) and (s[n] in ['+', '-']) then
- begin
- { don't accept - when reading unsigned }
- if unsigned and (s[n]='-') then
- begin
- result:=length(s1);
- exit;
- end
- else
- begin
- s1:=s1+s[n];
- inc(n);
- end;
- end;
- { read numbers }
- while (Length(s) >= n) and
- (s[n] in ['0'..'9']) do
- begin
- s1 := s1+s[n];
- inc(n);
- end;
- Result := Length(s1);
- end;
- function GetFloat : Integer;
- begin
- s1 := '';
- while (Length(s) > n) and (s[n] = ' ') do
- inc(n);
- while (Length(s) >= n) and
- (s[n] in ['0'..'9', '+', '-', FormatSettings.DecimalSeparator, 'e', 'E']) do
- begin
- s1 := s1+s[n];
- inc(n);
- end;
- Result := Length(s1);
- end;
- function GetString : Integer;
- begin
- s1 := '';
- while (Length(s) > n) and (s[n] = ' ') do
- inc(n);
- while (Length(s) >= n) and (s[n] <> ' ')do
- begin
- s1 := s1+s[n];
- inc(n);
- end;
- Result := Length(s1);
- end;
- function ScanStr(c : AnsiChar) : Boolean;
- begin
- while (Length(s) > n) and (s[n] <> c) do
- inc(n);
- inc(n);
- If (n <= Length(s)) then
- Result := True
- else
- Result := False;
- end;
- function GetFmt : Integer;
- begin
- Result := -1;
- while true do
- begin
- while (Length(fmt) > m) and (fmt[m] = ' ') do
- inc(m);
- if (m >= Length(fmt)) then
- break;
- if (fmt[m] = '%') then
- begin
- inc(m);
- case fmt[m] of
- 'd':
- Result:=vtInteger;
- {$ifndef FPUNONE}
- 'f':
- Result:=vtExtended;
- {$endif}
- 's':
- Result:=vtString;
- 'c':
- Result:=vtChar;
- else
- raise EFormatError.CreateFmt(SInvalidFormat,[fmt]);
- end;
- inc(m);
- break;
- end;
- if not(ScanStr(fmt[m])) then
- break;
- inc(m);
- end;
- end;
- begin
- n := 1;
- m := 1;
- Result := 0;
- for i:=0 to High(Pointers) do
- begin
- j := GetFmt;
- case j of
- vtInteger :
- begin
- if GetInt>0 then
- begin
- pLongint(Pointers[i])^:=StrToInt(s1);
- inc(Result);
- end
- else
- break;
- end;
- vtchar :
- begin
- if Length(s)>n then
- begin
- PChar(Pointers[i])^:=s[n];
- inc(n);
- inc(Result);
- end
- else
- break;
- end;
- {$ifndef FPUNONE}
- vtExtended :
- begin
- if GetFloat>0 then
- begin
- pextended(Pointers[i])^:=StrToFloat(s1);
- inc(Result);
- end
- else
- break;
- end;
- {$endif}
- vtString :
- begin
- if GetString > 0 then
- begin
- pstring(Pointers[i])^:=s1;
- inc(Result);
- end
- else
- break;
- end;
- else
- break;
- end;
- end;
- end;
- {$macro on}
- // Ansi version declaration
- {$UNDEF SBUNICODE}
- {$define SBChar:=AnsiChar}
- {$define SBString:=AnsiString}
- {$define TSBCharArray:=Array of SBChar}
- {$define PSBChar:=PAnsiChar}
- {$define SBRAWString:=RawByteString}
- {$define TGenericStringBuilder:=TAnsiStringBuilder}
- {$i syssb.inc}
- {$undef SBChar}
- {$undef SBString}
- {$undef TSBCharArray}
- {$undef PSBChar}
- {$undef SBRAWString}
- {$undef TGenericStringBuilder}
- // Unicode version declaration
- {$define SBUNICODE}
- {$define SBChar:=WideChar}
- {$define SBString:=UnicodeString}
- {$define TSBCharArray:=Array of SBChar}
- {$define PSBChar:=PWideChar}
- {$define SBRAWString:=UnicodeString}
- {$define TGenericStringBuilder:=TUnicodeStringBuilder}
- {$i syssb.inc}
- {$undef SBChar}
- {$undef SBString}
- {$undef TSBCharArray}
- {$undef PSBChar}
- {$undef SBRAWString}
- {$undef TGenericStringBuilder}
- {$undef SBUNICODE}
|