瀏覽代碼

* PChar -> PAnsichar

Michaël Van Canneyt 2 年之前
父節點
當前提交
4cfd9fa16e

+ 1 - 0
packages/fv/examples/testapp.pas

@@ -36,6 +36,7 @@ PROGRAM testapp;
 { ****************************** END REMARK *** Leon de Boer, 06Nov99 * }
 
 {$I platform.inc}
+{$H-}
   USES
 {$IFDEF OS2PM}
      {$IFDEF OS_OS2} Os2Def, os2PmApi,  {$ENDIF}

+ 1 - 0
packages/fv/examples/testuapp.pas

@@ -1,6 +1,7 @@
 program testuapp;
 
 {$codepage UTF8}
+{$h-}
 
 uses
   Objects, UDrivers, UViews, UMenus, UDialogs, UApp, UMsgBox, UInpLong, UTabs, SysUtils;

+ 2 - 2
packages/fv/src/app.inc

@@ -1029,10 +1029,10 @@ END;
 {  HandleEvent -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 12Sep97 LdB       }
 {---------------------------------------------------------------------------}
 PROCEDURE TProgram.HandleEvent (Var Event: TEvent);
-VAR C: Char;
+VAR C: AnsiChar;
 BEGIN
    If (Event.What = evKeyDown) Then Begin             { Key press event }
-     C := GetAltChar(Event.KeyCode);                  { Get alt char code }
+     C := GetAltChar(Event.KeyCode);                  { Get alt AnsiChar code }
      If (C >= '1') AND (C <= '9') Then
        If (Message(Desktop, evBroadCast, cmSelectWindowNum,
          Pointer(Byte(C) - $30)) <> Nil)              { Select window }

+ 4 - 3
packages/fv/src/asciitab.pas

@@ -34,13 +34,14 @@ UNIT AsciiTab;
 {====================================================================}
 
 {==== Compiler directives ===========================================}
-
+{$H-}
 {$X+} { Extended syntax is ok }
 {$R-} { Disable range checking }
 {$S-} { Disable Stack Checking }
 {$I-} { Disable IO Checking }
 {$Q-} { Disable Overflow Checking }
 {$V-} { Turn off strict VAR strings }
+
 {====================================================================}
 
 USES FVConsts, Objects, Drivers, Views, App;      { Standard GFV units }
@@ -64,7 +65,7 @@ type
   end;
 
 {---------------------------------------------------------------------------}
-{                  TREPORT OBJECT - View with details of current char       }
+{                  TREPORT OBJECT - View with details of current AnsiChar       }
 {---------------------------------------------------------------------------}
   PReport = ^TReport;
   TReport = object(TView)
@@ -243,7 +244,7 @@ begin
   while length(stDec)<3 do
     stDec:=' '+stDec;
   stHex:=hexstr(AsciiChar,2);
-  s:='Char "'+chr(AsciiChar)+'" Decimal: '+
+  s:='AnsiChar "'+chr(AsciiChar)+'" Decimal: '+
      StDec+' Hex: $'+StHex+
      '  '; // //{!ss:fill gap. FormatStr function using be better}
   WriteStr(0,0,S,1);

+ 2 - 1
packages/fv/src/colorsel.pas

@@ -22,7 +22,8 @@
  ****************************************************************************}
 }
 unit ColorSel;
-
+{$mode fpc}
+{$h-}
 interface
 
 uses Objects, Dialogs, Views;

+ 16 - 16
packages/fv/src/dialogs.inc

@@ -273,7 +273,7 @@ TYPE
       PROCEDURE MovedTo (Item: Sw_Integer); Virtual;
       PROCEDURE SetState (AState: Word; Enable: Boolean); Virtual;
       PROCEDURE DrawMultiBox (Const Icon, Marker: Sw_String);
-      PROCEDURE DrawBox (Const Icon: String; Marker: Char);
+      PROCEDURE DrawBox (Const Icon: String; Marker: AnsiChar);
       PROCEDURE SetButtonState (AMask: Longint; Enable: Boolean);
       PROCEDURE GetData (Var Rec); Virtual;
       PROCEDURE SetData (Var Rec); Virtual;
@@ -1080,7 +1080,7 @@ CONST
 {---------------------------------------------------------------------------}
 {  IsBlank -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 08Jun98 LdB           }
 {---------------------------------------------------------------------------}
-FUNCTION IsBlank (Ch: Char): Boolean;
+FUNCTION IsBlank (Ch: AnsiChar): Boolean;
 BEGIN
    IsBlank := (Ch = ' ') OR (Ch = #13) OR (Ch = #10); { Check for characters }
 END;
@@ -1088,7 +1088,7 @@ END;
 {---------------------------------------------------------------------------}
 {  HotKey -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 08Jun98 LdB            }
 {---------------------------------------------------------------------------}
-FUNCTION HotKey (Const S: String): Char;
+FUNCTION HotKey (Const S: String): AnsiChar;
 VAR I: Sw_Word;
 BEGIN
    HotKey := #0;                                      { Preset fail }
@@ -1815,7 +1815,7 @@ BEGIN
          Event.KeyCode := CtrlToArrow(Event.KeyCode); { Convert keycode }
          If (Event.ScanCode IN PadKeys) AND
          (GetShiftState AND $03 <> 0) Then Begin      { Mark selection active }
-           Event.CharCode := #0;                      { Clear char code }
+           Event.CharCode := #0;                      { Clear AnsiChar code }
            If (CurPos = SelEnd) Then                  { Find if at end }
              Anchor := SelStart Else                  { Anchor from start }
              Anchor := SelEnd;                        { Anchor from end }
@@ -1836,7 +1836,7 @@ BEGIN
            End;
            kbBack: If (Data <> Sw_PString_Empty) AND (CurPos > 0)  { Not at line start }
            Then Begin
-             Delete(Data Sw_PString_DeRef, CurPos, 1);  { Backspace over char }
+             Delete(Data Sw_PString_DeRef, CurPos, 1);  { Backspace over AnsiChar }
              Dec(CurPos);                             { Move cursor back one }
              If (FirstPos > 0) Then Dec(FirstPos);    { Move first position }
              CheckValid(True);                        { Check if valid }
@@ -1913,7 +1913,7 @@ BEGIN
          If (Data <> Sw_PString_Empty) Then OldData := Copy(Data Sw_PString_DeRef,
            FirstPos+1, CurPos-FirstPos)               { Text area string }
            Else OldData := '';                        { Empty string }
-         Delta := 1;                          { Safety = 1 char }
+         Delta := 1;                          { Safety = 1 AnsiChar }
          While (TextWidth(OldData) > (Size.X-Delta)
          - TextWidth(LeftArr) - TextWidth(RightArr))  { Check text fits }
          Do Begin
@@ -2182,7 +2182,7 @@ END;
 {  HandleEvent -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 05Sep99 LdB       }
 {---------------------------------------------------------------------------}
 PROCEDURE TButton.HandleEvent (Var Event: TEvent);
-VAR Down: Boolean; C: Char; ButRect: TRect;
+VAR Down: Boolean; C: AnsiChar; ButRect: TRect;
     Mouse : TPoint;
 BEGIN
    ButRect.A.X := 0;                            { Get origin point }
@@ -2221,7 +2221,7 @@ BEGIN
      evKeyDown: Begin
        If Title <> Sw_PString_Empty Then C := HotKey(Title Sw_PString_DeRef)     { Key title hotkey }
          Else C := #0;                                { Invalid title }
-       If (Event.KeyCode = GetAltCode(C)) OR          { Alt char }
+       If (Event.KeyCode = GetAltCode(C)) OR          { Alt AnsiChar }
        (Owner^.Phase = phPostProcess) AND (C <> #0)
        AND (Upcase(Event.CharCode) = C) OR            { Matches hotkey }
        (State AND sfFocused <> 0) AND                 { View focused }
@@ -2469,7 +2469,7 @@ END;
 {--TCluster-----------------------------------------------------------------}
 {  DrawBox -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 03Jun98 LdB           }
 {---------------------------------------------------------------------------}
-PROCEDURE TCluster.DrawBox (Const Icon: String; Marker: Char);
+PROCEDURE TCluster.DrawBox (Const Icon: String; Marker: AnsiChar);
 BEGIN
    DrawMultiBox(Icon, ' '+Marker);                    { Call draw routine }
 END;
@@ -2537,7 +2537,7 @@ END;
 {  HandleEvent -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 04Jun98 LdB       }
 {---------------------------------------------------------------------------}
 PROCEDURE TCluster.HandleEvent (Var Event: TEvent);
-VAR C: Char; I, S, Vh: Sw_Integer; Key: Word; Mouse: TPoint; Ts: PString;
+VAR C: AnsiChar; I, S, Vh: Sw_Integer; Key: Word; Mouse: TPoint; Ts: PString;
 
    PROCEDURE MoveSel;
    BEGIN
@@ -3245,11 +3245,11 @@ BEGIN
     if P <= L then
     begin
       Just := 0;                                       { Default left justify }
-      If (S[P] = #2) Then Begin                        { Right justify char }
+      If (S[P] = #2) Then Begin                        { Right justify AnsiChar }
         Just := 2;                                     { Set right justify }
         Inc(P);                                        { Next character }
       End;
-      If (S[P] = #3) Then Begin                        { Centre justify char }
+      If (S[P] = #3) Then Begin                        { Centre justify AnsiChar }
         Just := 1;                                     { Set centre justify }
         Inc(P);                                        { Next character }
       End;
@@ -3445,7 +3445,7 @@ END;
 {  HandleEvent -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 26Oct99 LdB       }
 {---------------------------------------------------------------------------}
 PROCEDURE TLabel.HandleEvent (Var Event: TEvent);
-VAR C: Char;
+VAR C: AnsiChar;
 
    PROCEDURE FocusLink;
    BEGIN
@@ -3464,7 +3464,7 @@ BEGIN
          if text<>Sw_PString_Empty then
            begin
              C := HotKey(Text Sw_PString_DeRef);            { Check for hotkey }
-             If (GetAltCode(C) = Event.KeyCode) OR          { Alt plus char }
+             If (GetAltCode(C) = Event.KeyCode) OR          { Alt plus AnsiChar }
                ((C <> #0) AND (Owner^.Phase = phPostProcess)  { Post process phase }
                 AND (UpCase(Event.CharCode) = C)) Then         { Upper case match }
                FocusLink;                                   { Focus link view }
@@ -3688,8 +3688,8 @@ BEGIN
       End;
      RecordHistory(Link^.Data Sw_PString_DeRef);      { Record current data }
      Link^.GetBounds(R);                              { Get view bounds }
-     Dec(R.A.X);                                      { One char in from us }
-     Inc(R.B.X);                                      { One char short of us }
+     Dec(R.A.X);                                      { One AnsiChar in from us }
+     Inc(R.B.X);                                      { One AnsiChar short of us }
      Inc(R.B.Y, 7);                                   { Seven lines down }
      Dec(R.A.Y,1);                                    { One line below us }
      Owner^.GetExtent(P);                             { Get owner extents }

+ 34 - 34
packages/fv/src/drivers.inc

@@ -288,12 +288,12 @@ TYPE
             1: (
 {$ifdef ENDIAN_BIG}
                 ScanCode: Byte;
-                CharCode: Char;
+                CharCode: AnsiChar;
 {$else not ENDIAN_BIG}
-                CharCode: Char;                       { Char code }
+                CharCode: AnsiChar;                       { AnsiChar code }
                 ScanCode: Byte;                       { Scan code }
 {$endif not ENDIAN_BIG}
-                UnicodeChar: WideChar;                { Unicode char code.
+                UnicodeChar: WideChar;                { Unicode AnsiChar code.
                           Code points from the Supplementary Planes (U+010000 to
                           U+10FFFF) are encoded as 2 consecutive key events,
                           forming an UTF-16 surrogate pair. }
@@ -308,7 +308,7 @@ TYPE
             2: (InfoWord: Word);                      { Message Sw_Word }
             3: (InfoInt: SmallInt);                   { Message Sw_Integer }
             4: (InfoByte: Byte);                      { Message byte }
-            5: (InfoChar: Char));                     { Message character }
+            5: (InfoChar: AnsiChar));                     { Message character }
    END;
    PEvent = ^TEvent;
 
@@ -397,7 +397,7 @@ set to Attr, or remain unchanged if Attr is zero.
 {$ifdef FV_UNICODE}
 PROCEDURE MoveChar (Var Dest; C: UnicodeString; Attr: Byte; Count: Sw_Word);
 {$else FV_UNICODE}
-PROCEDURE MoveChar (Var Dest; C: Char; Attr: Byte; Count: Sw_Word);
+PROCEDURE MoveChar (Var Dest; C: AnsiChar; Attr: Byte; Count: Sw_Word);
 {$endif FV_UNICODE}
 
 {+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++}
@@ -408,25 +408,25 @@ PROCEDURE MoveChar (Var Dest; C: Char; Attr: Byte; Count: Sw_Word);
 Returns the scancode corresponding to Alt+Ch key that is given.
 25May96 LdB
 ---------------------------------------------------------------------}
-FUNCTION GetAltCode (Ch: Char): Word;
+FUNCTION GetAltCode (Ch: AnsiChar): Word;
 
 {-GetCtrlCode--------------------------------------------------------
 Returns the scancode corresponding to Alt+Ch key that is given.
 25May96 LdB
 ---------------------------------------------------------------------}
-FUNCTION GetCtrlCode (Ch: Char): Word;
+FUNCTION GetCtrlCode (Ch: AnsiChar): Word;
 
 {-GetAltChar---------------------------------------------------------
 Returns the ascii character for the Alt+Key scancode that was given.
 25May96 LdB
 ---------------------------------------------------------------------}
-FUNCTION GetAltChar (KeyCode: Word): Char;
+FUNCTION GetAltChar (KeyCode: Word): AnsiChar;
 
 {-GetCtrlChar--------------------------------------------------------
 Returns the ascii character for the Ctrl+Key scancode that was given.
 25May96 LdB
 ---------------------------------------------------------------------}
-FUNCTION GetCtrlChar (KeyCode: Word): Char;
+FUNCTION GetCtrlChar (KeyCode: Word): AnsiChar;
 
 {-CtrlToArrow--------------------------------------------------------
 Converts a WordStar-compatible control key code to the corresponding
@@ -1003,7 +1003,7 @@ BEGIN
    for EGC in TUnicodeStringExtendedGraphemeClustersEnumerator.Create(Str) do
      begin
        If (Attr <> 0) Then P^.Attribute := Attr;        { Copy attribute }
-       P^.ExtendedGraphemeCluster := EGC;               { Copy string char }
+       P^.ExtendedGraphemeCluster := EGC;               { Copy string AnsiChar }
        Inc(P, Video.ExtendedGraphemeClusterDisplayWidth(EGC));
      end;
 END;
@@ -1014,7 +1014,7 @@ BEGIN
    For I := 1 To Length(Str) Do Begin                 { For each character }
      P := @TWordArray(Dest)[I-1];                     { Pointer to Sw_Word }
      If (Attr <> 0) Then WordRec(P^).Hi := Attr;      { Copy attribute }
-     WordRec(P^).Lo := Byte(Str[I]);                  { Copy string char }
+     WordRec(P^).Lo := Byte(Str[I]);                  { Copy string AnsiChar }
    End;
 END;
 {$endif FV_UNICODE}
@@ -1034,7 +1034,7 @@ BEGIN
          begin
            If (Lo(Attrs) <> 0) Then
              P^.Attribute := Lo(Attrs);                   { Copy attribute }
-           P^.ExtendedGraphemeCluster:=EGC;               { Copy string char }
+           P^.ExtendedGraphemeCluster:=EGC;               { Copy string AnsiChar }
            Inc(P, Video.ExtendedGraphemeClusterDisplayWidth(EGC));  { Next position }
          end
        else
@@ -1055,7 +1055,7 @@ BEGIN
        P := @TWordArray(Dest)[J];                     { Pointer to Sw_Word }
        If (Lo(Attrs) <> 0) Then
          WordRec(P^).Hi := Lo(Attrs);                 { Copy attribute }
-       WordRec(P^).Lo := Byte(Str[I]);                { Copy string char }
+       WordRec(P^).Lo := Byte(Str[I]);                { Copy string AnsiChar }
        Inc(J);                                        { Next position }
      End Else Begin
        B := Hi(Attrs);                                { Hold attribute }
@@ -1101,7 +1101,7 @@ BEGIN
           exit;
         end;
       If (Attr <> 0) Then P^.Attribute := Attr;        { Copy attribute }
-      P^.ExtendedGraphemeCluster := EGC;               { Copy string char }
+      P^.ExtendedGraphemeCluster := EGC;               { Copy string AnsiChar }
       Inc(P, Video.ExtendedGraphemeClusterDisplayWidth(EGC));
     end;
 END;
@@ -1135,7 +1135,7 @@ BEGIN
    End;
 END;
 {$else FV_UNICODE}
-PROCEDURE MoveChar (Var Dest; C: Char; Attr: Byte; Count: Sw_Word);
+PROCEDURE MoveChar (Var Dest; C: AnsiChar; Attr: Byte; Count: Sw_Word);
 VAR I: Word; P: PWord;
 BEGIN
    For I := 1 To Count Do Begin
@@ -1153,7 +1153,7 @@ END;
 {---------------------------------------------------------------------------}
 {  GetAltCode -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 25May96 LdB        }
 {---------------------------------------------------------------------------}
-FUNCTION GetAltCode (Ch: Char): Word;
+FUNCTION GetAltCode (Ch: AnsiChar): Word;
 BEGIN
    GetAltCode := 0;                                   { Preset zero return }
    Ch := UpCase(Ch);                                  { Convert upper case }
@@ -1166,7 +1166,7 @@ END;
 {---------------------------------------------------------------------------}
 {  GetCtrlCode -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 25May96 LdB       }
 {---------------------------------------------------------------------------}
-FUNCTION GetCtrlCode (Ch: Char): Word;
+FUNCTION GetCtrlCode (Ch: AnsiChar): Word;
 BEGIN
    GetCtrlCode := GetAltCode(Ch) OR (Ord(Ch) - $40);  { Ctrl+key code }
 END;
@@ -1174,7 +1174,7 @@ END;
 {---------------------------------------------------------------------------}
 {  GetAltChar -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 25May96 LdB        }
 {---------------------------------------------------------------------------}
-FUNCTION GetAltChar (KeyCode: Word): Char;
+FUNCTION GetAltChar (KeyCode: Word): AnsiChar;
 VAR I: Sw_Integer;
 BEGIN
    GetAltChar := #0;                                  { Preset fail return }
@@ -1185,19 +1185,19 @@ BEGIN
          Do Inc(I);                                   { Search for match }
        If (I < 128) Then GetAltChar := Chr(I);        { Return character }
      End Else
-       If (Hi(KeyCode)=$02) Then GetAltChar := #240;  { Return char }
+       If (Hi(KeyCode)=$02) Then GetAltChar := #240;  { Return AnsiChar }
    End;
 END;
 
 {---------------------------------------------------------------------------}
 {  GetCtrlChar -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 25May96 LdB       }
 {---------------------------------------------------------------------------}
-FUNCTION GetCtrlChar (KeyCode: Word): Char;
-VAR C: Char;
+FUNCTION GetCtrlChar (KeyCode: Word): AnsiChar;
+VAR C: AnsiChar;
 BEGIN
   C := #0;                                            { Preset #0 return }
   If (Lo(KeyCode) > 0) AND (Lo(KeyCode) <= 26) Then   { Between 1-26 }
-    C := Chr(Lo(KeyCode) + $40);                      { Return char A-Z }
+    C := Chr(Lo(KeyCode) + $40);                      { Return AnsiChar A-Z }
   GetCtrlChar := C;                                   { Return result }
 END;
 
@@ -1206,7 +1206,7 @@ END;
 {---------------------------------------------------------------------------}
 FUNCTION CtrlToArrow (KeyCode: Word): Word;
 CONST NumCodes = 11;
-      CtrlCodes : Array [0..NumCodes-1] Of Char =
+      CtrlCodes : Array [0..NumCodes-1] Of AnsiChar =
         (#19, #4, #5, #24, #1, #6, #7, #22, #18, #3, #8);
       ArrowCodes: Array [0..NumCodes-1] Of Sw_Word =
        (kbLeft, kbRight, kbUp, kbDown, kbHome, kbEnd, kbDel, kbIns,
@@ -1620,10 +1620,10 @@ procedure FormatStr (Var Result: Sw_String; CONST Format: Sw_String; Var Params)
 TYPE TLongArray = Array[0..0] Of PtrInt;
 VAR W, ResultLength : SmallInt;
     FormatIndex, Justify, Wth: Byte;
-    Fill: Char; S: Sw_String;
+    Fill: AnsiChar; S: Sw_String;
 
    FUNCTION LongToStr (L: Longint; Radix: Byte): Sw_String;
-   CONST HexChars: Array[0..15] Of Char =
+   CONST HexChars: Array[0..15] Of AnsiChar =
     ('0', '1', '2', '3', '4', '5', '6', '7',
      '8', '9', 'A', 'B', 'C', 'D', 'E', 'F');
    VAR I: LongInt; S: Sw_String; Sign: String[1];
@@ -1636,7 +1636,7 @@ VAR W, ResultLength : SmallInt;
      S := '';                                         { Preset empty string }
      Repeat
        I := L MOD Radix;                              { Radix mod of value }
-       S := HexChars[I] + S;                          { Add char to string }
+       S := HexChars[I] + S;                          { Add AnsiChar to string }
        L := L DIV Radix;                              { Divid by radix }
      Until (L = 0);                                   { Until no remainder }
      LongToStr := Sign + S;                           { Return result }
@@ -1650,24 +1650,24 @@ VAR W, ResultLength : SmallInt;
          exit;
 {$endif FV_UNICODE}
        While (FormatIndex <= Length(Format)) and
-             (Format[FormatIndex] <> '%')          { Param char not found }
+             (Format[FormatIndex] <> '%')          { Param AnsiChar not found }
         Do begin
 {$ifdef FV_UNICODE}
          SetLength(Result,ResultLength+1);
 {$endif FV_UNICODE}
          Result[ResultLength+1] := Format[FormatIndex]; { Transfer character }
          Inc(ResultLength);                           { One character added }
-         Inc(FormatIndex);                            { Next param char }
+         Inc(FormatIndex);                            { Next param AnsiChar }
        end;
-       If (FormatIndex < Length(Format)) and          { Not last char and }
-       (Format[FormatIndex] = '%') Then begin         { '%' char found }
-         Fill := ' ';                                 { Default fill char }
+       If (FormatIndex < Length(Format)) and          { Not last AnsiChar and }
+       (Format[FormatIndex] = '%') Then begin         { '%' AnsiChar found }
+         Fill := ' ';                                 { Default fill AnsiChar }
          Justify := 0;                                { Default justify }
          Wth := 0;                                    { Default 0=no width }
          Inc(FormatIndex);                            { Next character }
          If (Format[FormatIndex] = '0') Then
-           Fill := '0';                               { Fill char to zero }
-         If (Format[FormatIndex] = '-') Then begin    { Optional just char }
+           Fill := '0';                               { Fill AnsiChar to zero }
+         If (Format[FormatIndex] = '-') Then begin    { Optional just AnsiChar }
            Justify := 1;                              { Right justify }
            Inc(FormatIndex);                          { Next character }
          end;
@@ -1697,7 +1697,7 @@ VAR W, ResultLength : SmallInt;
              Inc(ResultLength,Length(S));
              Continue;
            end;
-           'c': S := Char(TLongArray(Params)[I]);  { Character parameter }
+           'c': S := AnsiChar(TLongArray(Params)[I]);  { Character parameter }
              'd': S := LongToStr(TLongArray(Params)[I],
                10);                                   { Decimal parameter }
              's': S := PString(TLongArray(Params)[I])^;{ String parameter }

+ 34 - 34
packages/fv/src/editors.pas

@@ -137,7 +137,7 @@ type
 
 
   PEditBuffer = ^TEditBuffer;
-  TEditBuffer = array[0..MaxBufLength] of Char;
+  TEditBuffer = array[0..MaxBufLength] of AnsiChar;
 
   PEditor = ^TEditor;
   TEditor = object (TView)
@@ -178,7 +178,7 @@ type
                           AIndicator : PIndicator; ABufSize : Sw_Word);
     constructor Load (var S : Objects.TStream);
     destructor Done; virtual;
-    function   BufChar (P : Sw_Word) : Char;
+    function   BufChar (P : Sw_Word) : AnsiChar;
     function   BufPtr (P : Sw_Word) : Sw_Word;
     procedure  ChangeBounds (var Bounds : TRect); virtual;
     procedure  ConvertEvent (var Event : Drivers.TEvent); virtual;
@@ -322,7 +322,7 @@ function TabStopDialog : Dialogs.PDialog;
 function StdEditorDialog(Dialog: SmallInt; Info: Pointer): Word;
 
 const
-  WordChars    : set of Char = ['!'..#255];
+  WordChars    : set of AnsiChar = ['!'..#255];
 
   LineBreak    : string[2]=
 {$ifdef UNIXLF}
@@ -977,10 +977,10 @@ end;
 
 function CountLines(var Buf; Count: sw_Word): sw_Integer;
 var
-  p : pchar;
+  p : PAnsiChar;
   lines : sw_word;
 begin
-  p:=pchar(@buf);
+  p:=PAnsiChar(@buf);
   lines:=0;
   while (count>0) do
    begin
@@ -1006,13 +1006,13 @@ procedure GetLimits(var Buf; Count: sw_Word;var lim:objects.TPoint);
 { Get the limits needed for Buf, its an extended version of countlines (lim.y),
   which also gets the maximum line length in lim.x }
 var
-  p : pchar;
+  p : PAnsiChar;
   len : sw_word;
 begin
   lim.x:=0;
   lim.y:=0;
   len:=0;
-  p:=pchar(@buf);
+  p:=PAnsiChar(@buf);
   while (count>0) do
    begin
      if p^ in [#10,#13] then
@@ -1116,15 +1116,15 @@ end;
 
 function IScan(var Block; Size: Sw_Word;const Str: String): Sw_Word;
 Var
-  buffer : Array[0..MaxBufLength-1] of Char Absolute block;
+  buffer : Array[0..MaxBufLength-1] of AnsiChar Absolute block;
   s      : String;
   len,
   numb,
   x      : Sw_Word;
   found  : Boolean;
   bt     : Btable;
-  p      : pchar;
-  c      : char;
+  p      : PAnsiChar;
+  c      : AnsiChar;
 begin
   len:=length(str);
   if (len=0) or (len>size) then
@@ -1194,7 +1194,7 @@ end; { TIndicator.Init }
 procedure TIndicator.Draw;
 VAR
   Color : Byte;
-  Frame : Char;
+  Frame : AnsiChar;
   L     : array[0..1] of PtrInt;
   S     : String[15];
   B     : TDrawBuffer;
@@ -1414,7 +1414,7 @@ begin
 end; { TEditor.Done }
 
 
-function TEditor.BufChar(P: Sw_Word): Char;
+function TEditor.BufChar(P: Sw_Word): AnsiChar;
 begin
   if P>=CurPtr then
    inc(P,Gaplen);
@@ -1437,7 +1437,7 @@ procedure TEditor.Center_Text (Select_Mode : Byte);
 { If the Line_Length exceeds the Right_Margin, or the  }
 { line is just a blank line, we exit and do nothing.   }
 VAR
-  Spaces      : array [1..80] of Char;  { Array to hold spaces we'll insert. }
+  Spaces      : array [1..80] of AnsiChar;  { Array to hold spaces we'll insert. }
   Index       : Byte;                   { Index into Spaces array.           }
   Line_Length : Sw_Integer;             { Holds the length of the line.      }
   E,S : Sw_Word;                        { End of the current line.           }
@@ -1936,10 +1936,10 @@ var
 
   function FormatUntil(endpos:Sw_word):boolean;
   var
-    p : pchar;
+    p : PAnsiChar;
   begin
     FormatUntil:=false;
-    p:=pchar(Buffer)+idxpos;
+    p:=PAnsiChar(Buffer)+idxpos;
     while endpos>idxpos do
      begin
        if OutCnt>=Width then
@@ -2381,17 +2381,17 @@ function TEditor.LineEnd (P : Sw_Word) : Sw_Word;
 var
   start,
   i  : Sw_word;
-  pc : pchar;
+  pc : PAnsiChar;
 begin
   if P<CurPtr then
    begin
      i:=CurPtr-P;
-     pc:=pchar(Buffer)+P;
+     pc:=PAnsiChar(Buffer)+P;
      while (i>0) do
       begin
         if pc^ in [#10,#13] then
          begin
-           LineEnd:=pc-pchar(Buffer);
+           LineEnd:=pc-PAnsiChar(Buffer);
            exit;
          end;
         inc(pc);
@@ -2402,18 +2402,18 @@ begin
   else
    start:=P;
   i:=BufLen-Start;
-  pc:=pchar(Buffer)+GapLen+start;
+  pc:=PAnsiChar(Buffer)+GapLen+start;
   while (i>0) do
    begin
      if pc^ in [#10,#13] then
       begin
-        LineEnd:=pc-(pchar(Buffer)+Gaplen);
+        LineEnd:=pc-(PAnsiChar(Buffer)+Gaplen);
         exit;
       end;
      inc(pc);
      dec(i);
    end;
-  LineEnd:=pc-(pchar(Buffer)+Gaplen);
+  LineEnd:=pc-(PAnsiChar(Buffer)+Gaplen);
 end; { TEditor.LineEnd }
 
 
@@ -2448,12 +2448,12 @@ end; { TEditor.LineMove }
 function TEditor.LineStart (P : Sw_Word) : Sw_Word;
 var
   i  : Sw_word;
-  start,pc : pchar;
-  oc : char;
+  start,pc : PAnsiChar;
+  oc : AnsiChar;
 begin
   if P>CurPtr then
    begin
-     start:=pchar(Buffer)+GapLen;
+     start:=PAnsiChar(Buffer)+GapLen;
      pc:=start;
      i:=P-CurPtr;
      dec(pc);
@@ -2469,7 +2469,7 @@ begin
    i:=0;
   if i=0 then
    begin
-     start:=pchar(Buffer);
+     start:=PAnsiChar(Buffer);
      i:=P;
      pc:=start+p;
      dec(pc);
@@ -2493,11 +2493,11 @@ end; { TEditor.LineStart }
 
 function TEditor.LineNr (P : Sw_Word) : Sw_Word;
 var
-  pc,endp : pchar;
+  pc,endp : PAnsiChar;
   lines : sw_word;
 begin
-  endp:=pchar(Buffer)+BufPtr(P);
-  pc:=pchar(Buffer);
+  endp:=PAnsiChar(Buffer)+BufPtr(P);
+  pc:=PAnsiChar(Buffer);
   lines:=0;
   while (pc<endp) do
    begin
@@ -2561,14 +2561,14 @@ end; { TEditor.NewLine }
 
 function TEditor.NextChar (P : Sw_Word) : Sw_Word;
 var
-  pc : pchar;
+  pc : PAnsiChar;
 begin
   if P<>BufLen then
    begin
      inc(P);
      if P<>BufLen then
       begin
-        pc:=pchar(Buffer);
+        pc:=PAnsiChar(Buffer);
         if P>=CurPtr then
          inc(pc,GapLen);
         inc(pc,P-1);
@@ -2600,14 +2600,14 @@ end; { TEditor.NextWord }
 
 function TEditor.PrevChar (P : Sw_Word) : Sw_Word;
 var
-  pc : pchar;
+  pc : PAnsiChar;
 begin
   if p<>0 then
    begin
      dec(p);
      if p<>0 then
       begin
-        pc:=pchar(Buffer);
+        pc:=PAnsiChar(Buffer);
         if P>=CurPtr then
          inc(pc,GapLen);
         inc(pc,P-1);
@@ -2690,7 +2690,7 @@ function TEditor.Reformat_Paragraph (Select_Mode   : Byte;
 { the AutoIndent feature.  Reformat is not possible if the CurPos exceeds   }
 { the Right_Margin.  Right_Margin is where the EOL is considered to be.     }
 CONST
-  Space : array [1..2] of Char = #32#32;
+  Space : array [1..2] of AnsiChar = #32#32;
 VAR
   C : Sw_Word;  { Position of CurPtr when we come into procedure. }
   E : Sw_Word;  { End of a line.                                  }
@@ -3215,7 +3215,7 @@ VAR
   Index    : Sw_Integer;             { Loop counter.                       }
   Position : Sw_Integer;             { CurPos.X position.                  }
   S        : Sw_Word;                { Start of current line.              }
-  Spaces   : array [1..80] of Char;  { Array to hold spaces for insertion. }
+  Spaces   : array [1..80] of AnsiChar;  { Array to hold spaces for insertion. }
 begin
   E := LineEnd (CurPtr);
   S := LineStart (CurPtr);

+ 2 - 2
packages/fv/src/fvcommon.inc

@@ -156,9 +156,9 @@ CONST
 {$ELSE FV_UNICODE}
 TYPE
    Sw_String = ShortString;
-   Sw_Char = Char;
+   Sw_Char = AnsiChar;
    Sw_PString = PShortString;
-   Sw_ExtendedGraphemeCluster = Char;
+   Sw_ExtendedGraphemeCluster = AnsiChar;
 CONST
    Sw_PString_Empty = Nil;
 {$ENDIF FV_UNICODE}

+ 4 - 2
packages/fv/src/gadgets.pas

@@ -49,7 +49,7 @@
 {  would continually redraw. By moving the memavail call   }
 {  the update procedure this eliminates this problem.      }
 {                                                          }
-{   Finally the original object relied on the font char    }
+{   Finally the original object relied on the font AnsiChar    }
 {  blocks being square to erase it's entire view area as   }
 {  it used a simple writeline call in the Draw method.     }
 {  Under GFV font blocks are not necessarily square and    }
@@ -84,6 +84,8 @@ UNIT Gadgets;
   {$P-} { Normal string variables }
   {$N-} { No 80x87 code generation }
   {$E+} { Emulation is on }
+{$ELSE}
+  {$H-}
 {$ENDIF}
 
 {$X+} { Extended syntax is ok }
@@ -124,7 +126,7 @@ TYPE
 {---------------------------------------------------------------------------}
 TYPE
    TClockView = OBJECT (TView)
-         am : Char;
+         am : AnsiChar;
          Refresh : Byte;                              { Refresh rate }
          LastTime: Longint;                           { Last time displayed }
          TimeStr : String[10];                        { Time string }

+ 11 - 11
packages/fv/src/histlist.inc

@@ -302,10 +302,10 @@ BEGIN
 END;
 {$else FV_UNICODE}
 PROCEDURE DeleteString;
-VAR Len: Sw_Integer; P, P2: PChar;
+VAR Len: Sw_Integer; P, P2: PAnsiChar;
 BEGIN
-   P := PChar(CurString);                             { Current string }
-   P2 := PChar(CurString);                            { Current string }
+   P := PAnsiChar(CurString);                             { Current string }
+   P2 := PAnsiChar(CurString);                            { Current string }
    Len := PByte(P2)^+3;                               { Length of data }
    Dec(P, 2);                                         { Correct position }
    Inc(P2, PByte(P2)^+1);                             { Next hist record }
@@ -319,7 +319,7 @@ END;
 {  AdvanceStringPtr -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 30Sep99 LdB  }
 {---------------------------------------------------------------------------}
 PROCEDURE AdvanceStringPtr;
-VAR P: PChar;
+VAR P: PAnsiChar;
 {$ifdef FV_UNICODE}
     Len: SizeUInt;
 {$endif FV_UNICODE}
@@ -333,14 +333,14 @@ BEGIN
      Len := DecodeSizeUInt(CurString);
      Inc(CurString, Len);                             { Move to next string }
 {$else FV_UNICODE}
-     Inc(PChar(CurString), PByte(CurString)^+1);      { Move to next string }
+     Inc(PAnsiChar(CurString), PByte(CurString)^+1);      { Move to next string }
 {$endif FV_UNICODE}
      If (Pointer(CurString) >= Pointer(HistoryBlock) + HistoryUsed) Then Begin{ Last string check }
        CurString := Nil;                              { Clear current string }
        Exit;                                          { Now exit }
      End;
-     P := PChar(CurString);                        { Transfer record ptr }
-     Inc(PChar(CurString), 2);                        { Move to string }
+     P := PAnsiChar(CurString);                        { Transfer record ptr }
+     Inc(PAnsiChar(CurString), 2);                        { Move to string }
      if (P^<>#0) then
        RunError(215);
      Inc(P);
@@ -387,11 +387,11 @@ BEGIN
 END;
 {$else FV_UNICODE}
 PROCEDURE InsertString (Id: Byte; Const Str: String);
-VAR P, P1, P2: PChar;
+VAR P, P1, P2: PAnsiChar;
 BEGIN
   while (HistoryUsed+Length(Str)+3>HistorySize) do
    begin
-       P:=PChar(HistoryBlock);
+       P:=PAnsiChar(HistoryBlock);
        while Pointer(P)<Pointer(HistoryBlock)+HistorySize do
          begin
            if Pointer(P)+Length(PShortString(P+2)^)+6+Length(Str) >
@@ -404,7 +404,7 @@ BEGIN
            Inc(P,Length(PShortString(P+2)^)+3);
          end;
    end;
-   P1 := PChar(HistoryBlock)+1;                     { First history record }
+   P1 := PAnsiChar(HistoryBlock)+1;                     { First history record }
    P2 := P1+Length(Str)+3;                          { History record after }
    Move(P1^, P2^, HistoryUsed - 1);                 { Shuffle history data }
    P1^:=#0;                         { Set marker byte }
@@ -501,7 +501,7 @@ END;
 PROCEDURE ClearHistory;
 BEGIN
    If (HistoryBlock <> Nil) Then Begin                { History initiated }
-     PChar(HistoryBlock)^ := #0;                      { Clear first byte }
+     PAnsiChar(HistoryBlock)^ := #0;                      { Clear first byte }
      HistoryUsed := 1;        { Set position }
    End;
 END;

+ 1 - 1
packages/fv/src/inplong.inc

@@ -181,7 +181,7 @@ end;
 
 FUNCTION Hex2(B : Byte) : Sw_String;
 Const
-  HexArray : array[0..15] of char = '0123456789ABCDEF';
+  HexArray : array[0..15] of AnsiChar = '0123456789ABCDEF';
 begin
 SetLength(Hex2, 2);
 Hex2[1] := HexArray[B shr 4];

+ 10 - 10
packages/fv/src/menus.inc

@@ -191,7 +191,7 @@ TYPE
       FUNCTION Execute: Word; Virtual;
       FUNCTION GetHelpCtx: Word; Virtual;
       FUNCTION GetPalette: PPalette; Virtual;
-      FUNCTION FindItem (Ch: Char): PMenuItem;
+      FUNCTION FindItem (Ch: AnsiChar): PMenuItem;
       FUNCTION HotKey (KeyCode: Word): PMenuItem;
       FUNCTION NewSubView (Var Bounds: TRect; AMenu: PMenu;
         AParentMenu: PMenuView): PMenuView; Virtual;
@@ -426,7 +426,7 @@ CONST
 {$ifdef FV_UNICODE}
   SubMenuChar : array[boolean] of WideChar = ('>',#$25BA);
 {$else FV_UNICODE}
-  SubMenuChar : array[boolean] of char = ('>',#16);
+  SubMenuChar : array[boolean] of AnsiChar = ('>',#16);
 {$endif FV_UNICODE}
   { SubMenuChar is the character displayed at right of submenu }
 
@@ -505,7 +505,7 @@ END;
 {---------------------------------------------------------------------------}
 FUNCTION TMenuView.Execute: Word;
 TYPE MenuAction = (DoNothing, DoSelect, DoReturn);
-VAR AutoSelect: Boolean; Action: MenuAction; Ch: Char; Res: Word; R: TRect;
+VAR AutoSelect: Boolean; Action: MenuAction; Ch: AnsiChar; Res: Word; R: TRect;
   ItemShown, P: PMenuItem; Target: PMenuView; E: TEvent; MouseActive: Boolean;
 
    PROCEDURE TrackMouse;
@@ -738,16 +738,16 @@ END;
 {--TMenuView----------------------------------------------------------------}
 {  FindItem -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 11May98 LdB          }
 {---------------------------------------------------------------------------}
-FUNCTION TMenuView.FindItem (Ch: Char): PMenuItem;
+FUNCTION TMenuView.FindItem (Ch: AnsiChar): PMenuItem;
 VAR I: SmallInt; P: PMenuItem;
 BEGIN
-   Ch := UpCase(Ch);                                  { Upper case of char }
+   Ch := UpCase(Ch);                                  { Upper case of AnsiChar }
    P := Menu^.Items;                                  { First menu item }
    While (P <> Nil) Do Begin                          { While item valid }
      If (P^.Name <> Sw_PString_Empty) AND (NOT P^.Disabled)  { Valid enabled cmd }
      Then Begin
        I := Pos('~', P^.Name Sw_PString_Deref);  { Scan for highlight }
-       If (I <> 0) AND (Ch = UpCase(P^.Name Sw_PString_Deref[I+1]))   { Hotkey char found }
+       If (I <> 0) AND (Ch = UpCase(P^.Name Sw_PString_Deref[I+1]))   { Hotkey AnsiChar found }
        Then Begin
          FindItem := P;                               { Return item }
          Exit;                                        { Now exit }
@@ -1055,7 +1055,7 @@ Type
 {$ifdef FV_UNICODE}
    FrameLineChars = Array[0..2] of WideChar;
 {$else FV_UNICODE}
-   FrameLineChars = Array[0..2] of char;
+   FrameLineChars = Array[0..2] of AnsiChar;
 {$endif FV_UNICODE}
 Const
    FrameLines : Array[FrameLineType] of FrameLineChars =
@@ -1512,12 +1512,12 @@ BEGIN
    HintBuf := Hint(HelpCtx);                          { Get hint string }
    If (HintBuf <> '') Then Begin                      { Hint present }
 {$ifdef FV_UNICODE}
-     MoveChar(B[I], #$2502, Byte(CNormal), 1);        { '|' char to buffer }
+     MoveChar(B[I], #$2502, Byte(CNormal), 1);        { '|' AnsiChar to buffer }
 {$else FV_UNICODE}
      {$IFNDEF OS_WINDOWS}
-     MoveChar(B[I], #179, Byte(CNormal), 1);          { '|' char to buffer }
+     MoveChar(B[I], #179, Byte(CNormal), 1);          { '|' AnsiChar to buffer }
      {$ELSE}
-     MoveChar(B[I], #124, Byte(CNormal), 1);          { '|' char to buffer }
+     MoveChar(B[I], #124, Byte(CNormal), 1);          { '|' AnsiChar to buffer }
      {$ENDIF}
 {$endif FV_UNICODE}
      Inc(I, 2);                                       { Move along }

+ 1 - 1
packages/fv/src/outline.inc

@@ -13,7 +13,7 @@
     MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
 
  **********************************************************************}
-
+{$H-}
 {$ifdef FV_UNICODE}
 unit uoutline;
 {$else FV_UNICODE}

+ 2 - 2
packages/fv/src/resource.pas

@@ -445,7 +445,7 @@ end;
 function TMemStringList.LoadStrings: Sw_Integer;
   procedure MakeEditableString (var Str: string);
   const
-    SpecialChars: array[1..3] of Char = #3#10#13;
+    SpecialChars: array[1..3] of AnsiChar = #3#10#13;
   var
     i, j: Byte;
   begin
@@ -542,7 +542,7 @@ var
           Inc(j,Byte(S[Succ(j)] in Numbers));
         Val(Copy(S,i,j-i+1),N,ErrorCode);
         System.Delete(S,Pred(i),j-i+2);
-        System.Insert(Char(N),S,Pred(i));
+        System.Insert(AnsiChar(N),S,Pred(i));
       end;
       StrList^.Put(Value,Text)
     end;

+ 1 - 1
packages/fv/src/statuses.pas

@@ -732,7 +732,7 @@ end;
 { TArrowGauge.Draw                                                           }
 {****************************************************************************}
 procedure TArrowGauge.Draw;
-const Arrows : array[0..1] of Char = '<>';
+const Arrows : array[0..1] of AnsiChar = '<>';
 var
   B : TDrawBuffer;
   C : Word;

+ 17 - 17
packages/fv/src/stddlg.pas

@@ -73,7 +73,7 @@ const
   MaxDir   = 255;   { Maximum length of a DirStr. }
   MaxFName = 255; { Maximum length of a FNameStr. }
 
-  DirSeparator : Char = system.DirectorySeparator;
+  DirSeparator : AnsiChar = system.DirectorySeparator;
 
 {$ifdef Unix}
   AllFiles = '*';
@@ -351,7 +351,7 @@ const
 function Contains(S1, S2: String): Boolean;
   { Contains returns true if S1 contains any characters in S2. }
 
-function DriveValid(Drive: Char): Boolean;
+function DriveValid(Drive: AnsiChar): Boolean;
   { DriveValid returns True if Drive is a valid DOS drive.  Drive valid works
     by attempting to change the current directory to Drive, then restoring
     the original directory. }
@@ -385,7 +385,7 @@ function GetCurDir: DirStr;
   { GetCurDir returns the current directory.  The directory returned always
     ends with a trailing backslash '\'. }
 
-function GetCurDrive: Char;
+function GetCurDrive: AnsiChar;
   { GetCurDrive returns the letter of the current drive as reported by the
     operating system. }
 
@@ -393,7 +393,7 @@ function IsWild(const S: String): Boolean;
   { IsWild returns True if S contains a question mark (?) or asterix (*). }
 
 function IsList(const S: String): Boolean;
-  { IsList returns True if S contains list separator (;) char }
+  { IsList returns True if S contains list separator (;) AnsiChar }
 
 function IsDir(const S: String): Boolean;
   { IsDir returns True if S is a valid DOS directory. }
@@ -774,7 +774,7 @@ end;
      in_name:=true;
      for i:=length(s) downto 1 do
       if in_name and (s[i] in ['a'..'z']) then
-        uppername[i]:=char(byte(s[i])-32)
+        uppername[i]:=AnsiChar(byte(s[i])-32)
       else
        begin
           uppername[i]:=s[i];
@@ -849,7 +849,7 @@ function MatchesMask(What, Mask: string): boolean;
   begin
      for i:=1 to length(s) do
       if s[i] in ['a'..'z'] then
-       upper[i]:=char(byte(s[i])-32)
+       upper[i]:=AnsiChar(byte(s[i])-32)
       else
        upper[i]:=s[i];
      upper[0]:=s[0];
@@ -1365,7 +1365,7 @@ begin
       if C = cmOk then
       begin
         Rslt := HistoryWindow^.GetSelection;
-        if Length(Rslt) > Link^.MaxLen then Rslt[0] := Char(Link^.MaxLen);
+        if Length(Rslt) > Link^.MaxLen then Rslt[0] := AnsiChar(Link^.MaxLen);
         Link^.Data^ := Rslt;
         Link^.SelectAll(True);
         Link^.DrawView;
@@ -1850,7 +1850,7 @@ const
 var
   AList: PCollection;
   NewDir, Dirct: DirStr;
-  C, OldC: Char;
+  C, OldC: AnsiChar;
   S, Indent: String[80];
   P: PString;
   NewCur: Word;
@@ -2245,7 +2245,7 @@ end;
 {****************************************************************************}
 procedure TSortedListBox.HandleEvent(var Event: TEvent);
 const
-  SpecialChars: set of Char = [#0,#9,#27];
+  SpecialChars: set of AnsiChar = [#0,#9,#27];
 var
   CurString, NewString: String;
   K: Pointer;
@@ -2277,7 +2277,7 @@ begin
    Dec(SearchPos);
           if SearchPos = 0 then
             HandleDir:= ((GetShiftState and $3) <> 0) or (Event.CharCode in ['A'..'Z']);
-   CurString[0] := Char(SearchPos);
+   CurString[0] := AnsiChar(SearchPos);
       end
       else if (Event.CharCode = '.') then
         SearchPos := Pos('.',CurString)
@@ -2286,7 +2286,7 @@ begin
    Inc(SearchPos);
           if SearchPos = 1 then
             HandleDir := ((GetShiftState and 3) <> 0) or (Event.CharCode in ['A'..'Z']);
-   CurString[0] := Char(SearchPos);
+   CurString[0] := AnsiChar(SearchPos);
    CurString[SearchPos] := Event.CharCode;
       end;
       K := GetKey(CurString);
@@ -2371,10 +2371,10 @@ end;
 {****************************************************************************}
 { DriveValid                         }
 {****************************************************************************}
-function DriveValid(Drive: Char): Boolean;
+function DriveValid(Drive: AnsiChar): Boolean;
 {$ifdef HAS_DOS_DRIVES}
 var
-  D: Char;
+  D: AnsiChar;
 begin
   D := GetCurDrive;
   {$push}{$I-}
@@ -2475,14 +2475,14 @@ end;
 {****************************************************************************}
 { GetCurDrive                       }
 {****************************************************************************}
-function GetCurDrive: Char;
+function GetCurDrive: AnsiChar;
 {$ifdef go32v2}
 var
   Regs : Registers;
 begin
   Regs.AH := $19;
   Intr($21,Regs);
-  GetCurDrive := Char(Regs.AL + Byte('A'));
+  GetCurDrive := AnsiChar(Regs.AL + Byte('A'));
 end;
 {$else not go32v2}
 var
@@ -2492,7 +2492,7 @@ begin
   if (Length(D)>1) and (D[2]=':') then
     begin
       if (D[1]>='a') and (D[1]<='z') then
-        GetCurDrive:=Char(Byte(D[1])+Byte('A')-Byte('a'))
+        GetCurDrive:=AnsiChar(Byte(D[1])+Byte('A')-Byte('a'))
       else
         GetCurDrive:=D[1];
     end
@@ -2598,7 +2598,7 @@ end;
 {****************************************************************************}
 function NoWildChars(S: String): String;
 const
-  WildChars : array[0..1] of Char = ('?','*');
+  WildChars : array[0..1] of AnsiChar = ('?','*');
 var
   i : Sw_Word;
 begin

+ 1 - 1
packages/fv/src/strtxt.inc

@@ -16,7 +16,7 @@
 
 type standard_string=record
        nr:word;
-       text:Pchar;
+       text:PAnsiChar;
      end;
 
 const standard_string_count=107;

+ 2 - 2
packages/fv/src/tabs.inc

@@ -57,7 +57,7 @@ type
       Name     : Sw_PString;
       Items    : PTabItem;
       DefItem  : PView;
-      ShortCut : char;
+      ShortCut : AnsiChar;
     end;
 
     PTab = ^TTab;
@@ -496,7 +496,7 @@ var B     : TDrawBuffer;
     Name       : Sw_PString;
     ActiveKPos : SmallInt;
     ActiveVPos : SmallInt;
-    FC   : char;
+    FC   : AnsiChar;
 procedure SWriteBuf(X,Y,W,H: SmallInt; var Buf);
 var i: SmallInt;
 begin

+ 13 - 13
packages/fv/src/validate.inc

@@ -171,7 +171,7 @@ TYPE CharSet = TCharSet;
 {---------------------------------------------------------------------------}
 TYPE
    TFilterValidator = OBJECT (TValidator)
-         ValidChars: CharSet;                         { Valid char set }
+         ValidChars: CharSet;                         { Valid AnsiChar set }
       CONSTRUCTOR Init (AValidChars: CharSet);
       CONSTRUCTOR Load (Var S: TStream);
       FUNCTION IsValid (CONST S: Sw_String): Boolean; Virtual;
@@ -319,9 +319,9 @@ USES MsgBox;                                          { GFV standard unit }
 {---------------------------------------------------------------------------}
 {  IsLetter -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 18May98 LdB          }
 {---------------------------------------------------------------------------}
-FUNCTION IsLetter (Chr: Char): Boolean;
+FUNCTION IsLetter (Chr: AnsiChar): Boolean;
 BEGIN
-   Chr := Char(Ord(Chr) AND $DF);                     { Lower to upper case }
+   Chr := AnsiChar(Ord(Chr) AND $DF);                     { Lower to upper case }
    If (Chr >= 'A') AND (Chr <='Z') Then               { Check if A..Z }
      IsLetter := True Else IsLetter := False;         { Return result }
 END;
@@ -346,19 +346,19 @@ END;
 {---------------------------------------------------------------------------}
 {  NumChar -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 18May98 LdB           }
 {---------------------------------------------------------------------------}
-FUNCTION NumChar (Chr: Char; Const S: String): Byte;
+FUNCTION NumChar (Chr: AnsiChar; Const S: String): Byte;
 VAR I, Total: Byte;
 BEGIN
    Total := 0;                                        { Zero total }
    For I := 1 To Length(S) Do                         { For entire string }
      If (S[I] = Chr) Then Inc(Total);                 { Count matches of Chr }
-   NumChar := Total;                                  { Return char count }
+   NumChar := Total;                                  { Return AnsiChar count }
 END;
 
 {---------------------------------------------------------------------------}
 {  IsSpecial -> Platforms DOS/DPMI/WIN/NT/OS2 - Updated 18May98 LdB         }
 {---------------------------------------------------------------------------}
-FUNCTION IsSpecial (Chr: Char; Const Special: String): Boolean;
+FUNCTION IsSpecial (Chr: AnsiChar; Const Special: String): Boolean;
 VAR Rslt: Boolean; I: Byte;
 BEGIN
    Rslt := False;                                     { Preset false result }
@@ -509,7 +509,7 @@ VAR I, J: Byte; Rslt: TPicResult; Reprocess: Boolean;
    FUNCTION Process (TermCh: Byte): TPicResult;
    VAR Rslt: TPicResult; Incomp: Boolean; OldI, OldJ, IncompJ, IncompI: Byte;
 
-     PROCEDURE Consume (Ch: Char);
+     PROCEDURE Consume (Ch: AnsiChar);
      BEGIN
        Input[J] := Ch;                                { Return character }
        Inc(J);                                        { Inc count J }
@@ -630,7 +630,7 @@ VAR I, J: Byte; Rslt: TPicResult; Reprocess: Boolean;
      END;
 
      FUNCTION Scan: TPicResult;
-     VAR Ch: Char; Rslt: TPicResult;
+     VAR Ch: AnsiChar; Rslt: TPicResult;
      BEGIN
        Scan := prError;                               { Preset return error }
        Rslt := prEmpty;                               { Preset empty result }
@@ -826,7 +826,7 @@ END;
 CONSTRUCTOR TFilterValidator.Init (AValidChars: CharSet);
 BEGIN
    Inherited Init;                                    { Call ancestor }
-   ValidChars := AValidChars;                         { Hold valid char set }
+   ValidChars := AValidChars;                         { Hold valid AnsiChar set }
 END;
 
 {--TFilterValidator---------------------------------------------------------}
@@ -835,7 +835,7 @@ END;
 CONSTRUCTOR TFilterValidator.Load (Var S: TStream);
 BEGIN
    Inherited Load(S);                                 { Call ancestor }
-   S.Read(ValidChars, SizeOf(ValidChars));            { Read valid char set }
+   S.Read(ValidChars, SizeOf(ValidChars));            { Read valid AnsiChar set }
 END;
 
 {--TFilterValidator---------------------------------------------------------}
@@ -845,7 +845,7 @@ FUNCTION TFilterValidator.IsValid (Const S: Sw_String): Boolean;
 VAR I: SmallInt;
 BEGIN
    I := 1;                                            { Start at position 1 }
-   While S[I] In ValidChars Do Inc(I);                { Check each char }
+   While S[I] In ValidChars Do Inc(I);                { Check each AnsiChar }
    If (I > Length(S)) Then IsValid := True Else       { All characters valid }
      IsValid := False;                                { Invalid characters }
 END;
@@ -857,7 +857,7 @@ FUNCTION TFilterValidator.IsValidInput (Var S: Sw_String; SuppressFill: Boolean)
 VAR I: SmallInt;
 BEGIN
    I := 1;                                            { Start at position 1 }
-   While S[I] In ValidChars Do Inc(I);                { Check each char }
+   While S[I] In ValidChars Do Inc(I);                { Check each AnsiChar }
    If (I > Length(S)) Then IsValidInput := True       { All characters valid }
      Else IsValidInput := False;                      { Invalid characters }
 END;
@@ -877,7 +877,7 @@ END;
 PROCEDURE TFilterValidator.Store (Var S: TStream);
 BEGIN
    TValidator.Store(S);                               { TValidator.Store call }
-   S.Write(ValidChars, SizeOf(ValidChars));           { Write valid char set }
+   S.Write(ValidChars, SizeOf(ValidChars));           { Write valid AnsiChar set }
 END;
 
 {+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++}

+ 11 - 11
packages/fv/src/views.inc

@@ -352,7 +352,7 @@ TYPE
          HoldLimit: PComplexArea;                     { Hold limit values }
 
          RevCol    : Boolean;
-         BackgroundChar : Char;
+         BackgroundChar : AnsiChar;
 
       CONSTRUCTOR Init (Var Bounds: TRect);
       CONSTRUCTOR Load (Var S: TStream);
@@ -431,7 +431,7 @@ TYPE
       PROCEDURE WriteChar (X, Y: Sw_Integer; C: UnicodeString; Color: Byte;
         Count: Sw_Integer);
 {$else FV_UNICODE}
-      PROCEDURE WriteChar (X, Y: Sw_Integer; C: Char; Color: Byte;
+      PROCEDURE WriteChar (X, Y: Sw_Integer; C: AnsiChar; Color: Byte;
         Count: Sw_Integer);
 {$endif FV_UNICODE}
       PROCEDURE DragView (Event: TEvent; Mode: Byte; Var Limits: TRect;
@@ -542,7 +542,7 @@ TYPE
 {$ifdef FV_UNICODE}
    TScrollChars = Array [0..4] of WideChar;
 {$else FV_UNICODE}
-   TScrollChars = Array [0..4] of Char;
+   TScrollChars = Array [0..4] of AnsiChar;
 {$endif FV_UNICODE}
 
    TScrollBar = OBJECT (TView)
@@ -729,7 +729,7 @@ CONST
 {$ifdef FV_UNICODE}
    SpecialChars: Array [0..5] Of WideChar = (#$00BB, #$00AB, #$2192, #$2190, ' ', ' ');
 {$else FV_UNICODE}
-   SpecialChars: Array [0..5] Of Char = (#175, #174, #26, #27, ' ', ' ');
+   SpecialChars: Array [0..5] Of AnsiChar = (#175, #174, #26, #27, ' ', ' ');
 {$endif FV_UNICODE}
 
 {+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++}
@@ -2745,9 +2745,9 @@ const
     #$0020#$0020#$0020#$255A#$0020#$2551#$2554#$255F+
     #$0020#$255D#$2550#$2567#$2557#$2562#$2564#$256C;
 {$else FV_UNICODE}
-  FrameChars_437: array[0..31] of Char =
+  FrameChars_437: array[0..31] of AnsiChar =
     '   '#192' '#179#218#195' '#217#196#193#191#180#194#197'   '#200' '#186#201#199' '#188#205#207#187#182#209#206;
-  FrameChars_850: array[0..31] of Char =
+  FrameChars_850: array[0..31] of AnsiChar =
     '   '#192' '#179#218#195' '#217#196#193#191#180#194#197'   '#200' '#186#201#186' '#188#205#205#187#186#205#206;
 {$endif FV_UNICODE}
 var
@@ -2758,7 +2758,7 @@ var
   i,j,k     : {Sw_  lo and hi are used !! }SmallInt;
   CurrView  : PView;
 {$ifndef FV_UNICODE}
-  p         : Pchar;
+  p         : PAnsiChar;
 {$endif FV_UNICODE}
 begin
   FrameMask[0]:=InitFrame[n];
@@ -2841,9 +2841,9 @@ const
   RestoreC:array[boolean] of widechar=('|',#$2195);
   ClickC:array[boolean] of widechar=('*',#$263C);
 {$else FV_UNICODE}
-  LargeC:array[boolean] of char=('^',#24);
-  RestoreC:array[boolean] of char=('|',#18);
-  ClickC:array[boolean] of char=('*',#15);
+  LargeC:array[boolean] of AnsiChar=('^',#24);
+  RestoreC:array[boolean] of AnsiChar=('|',#18);
+  ClickC:array[boolean] of AnsiChar=('*',#15);
 {$endif FV_UNICODE}
 var
   CFrame, CTitle: Word;
@@ -4473,7 +4473,7 @@ end;
 {$ifdef FV_UNICODE}
 procedure TView.WriteChar(X,Y:Sw_Integer; C:UnicodeString; Color:Byte; Count:Sw_Integer);
 {$else FV_UNICODE}
-procedure TView.WriteChar(X,Y:Sw_Integer; C:Char; Color:Byte; Count:Sw_Integer);
+procedure TView.WriteChar(X,Y:Sw_Integer; C:AnsiChar; Color:Byte; Count:Sw_Integer);
 {$endif FV_UNICODE}
 var
   B : TDrawBuffer;