Converting from VFP to Harbour and HMG

1,262 views
Skip to first unread message

Jeff Stone

unread,
Jan 6, 2016, 4:17:09 PM1/6/16
to Harbour Users

As a VFP user with several large applications, I have been faced with the dilemma of having to prepare for the day
when VFP will no longer function in Windows.  Additionally, we have clients that occasionally ask us to develop
applications for them.  Since these clients are typically large international financial organizations, applications
developed in VFP are no longer an option as the clients' internal system requirements will no longer accept
applications written in languages that are no longer actively supported. Finally, we are cautious about converting our
programs and want to be able to run in parallel for at least 6 months.  As our applications may get enhanced monthly,
the ability to have a single set of .PRGs that could run on VFP and the new compiler would be preferable.

I translated some of our applications into VB and C#, but performance was noticeably slower when signicant
database operations were being performed.  I also investigated Lianja, Alaska Xbase++ and others.  Finally, I
came to Harbour and HMG.  I have found the combination of these two open source programs have met our needs
best in terms of minimizing the effort required to adapt our VFP .PRGs, getting a similar look and feel, and
overall program performance.  (Let me state here that our VFP applications are not heavily GUI dependent. Also,
our applications made minimal use of .DBC files which Harbour does not support.)

Below are notes that I put together converting our .PRGs to enable them to run in Harbour/HMG and VFP.  They are not
comprehensive in terms of addressing all the issues that a VFP user might encounter, but I hope are helpful to others.
I have also tried to be as accurate in my statements as possible, but please accept that I may have misunderstood
certain aspects of Harbour and HMG; so, there may be errors.  I hope that others on the board will correct these
errors, add additional notes, and improve any code I've provided below.

Below I sometimes show procedures/functions missing in Harbour to provide VFP equivalent functionality.
I did not write all of these procedures. Some were posted by Harbour User Group members, and I was able to use
them successfully in my testing.  Unfortunately, I didn't note who created the original code, so please forgive me for
not giving those of you who wrote the procedures/functions explicit credit.

People can feel free to pull information from this post and put it elsewhere (VivaClipper, etc.), if deemed worthy.

Finally, thanks to everyone on this forum who has helped me get up to speed with HMG and Harbour.

--Jeff


Harbour and HMG Differences Worth Noting
========================================
Harbour is designed to operated on multiple platforms in addition to Windows.  HMG is only for Windows.

Harbour and HMG are both Open Source development systems but they are independent. HMG incorporates Harbour into its
builds but as both Harbour and HMG are supported by helpful, busy individuals, there is a lag in HMG being updated
with the most recent Harbour nightly build.  So, if you notice some issues with Harbour that are newly addressed,
there may be a lag in those issues being incorporated into HMG. It also seems that HMG does not have all of the
latest Harbour \contrib code.  This may be because of certain compatibility issues, but I'm not sure.

While Harbour can be compiled with MinGW, MS Visual Studio, and others, HMG can only be compiled with MinGW. (?)


Harbour and VFP Differences/Observations
========================================
Below are differences noted between Harbour and VFP.  Some of these differences can be addressed by
compiling with hbfoxpro.ch which is in the contrib\ portion of Harbour. This file uses the #translate/
#command preprocessor directives to substitute VFP syntax with Harbour equivalents. For simplicity,
I have pasted hbfoxpro.ch below after that are some of my #translate/#command additions:

From hbfoxpro.ch
----------------
/* messages in FP */
#xtranslate .<!msg!> => :<msg>


/* array declarations */
#xtranslate __FP_DIM( <exp> ) => <exp>
#xtranslate __FP_DIM( <!name!>( <dim,...> ) ) => <name>\[ <dim> \]

#command PUBLIC <var1> [, <varN> ] => ;
         <@> PUBLIC __FP_DIM( <var1> ) [, __FP_DIM( <varN> ) ]
#command PRIVATE <var1> [, <varN> ] => ;
         <@> PRIVATE __FP_DIM( <var1> ) [, __FP_DIM( <varN> ) ]
#command DIMENSIONS <!name1!>( <dim1,...> ) [, <!nameN!>( <dimN,...> ) ] => ;
         PRIVATE <name1>\[ <dim1> \] [, <nameN>\[ <dimN> \] ]


/* workaround for problem with command using FIELDS keyword which can
   wrongly translate FIELD->fieldname.
 */
#translate FIELD-><!name!> => _FIELD-><name>


/* commands using FIELDS clause which is not accepted by Clipper */
#command DISPLAY [FIELDS <v,...>] [<off:OFF>] ;
                 [<prn:TO PRINTER>] [TO FILE <(f)>] ;
                 [FOR <for>] [WHILE <while>] [NEXT <next>] ;
                 [RECORD <rec>] [<rest:REST>] [<all:ALL>] => ;
         __dbList( <.off.>, { <{v}> }, <.all.>, ;
                   <{for}>, <{while}>, <next>, ;
                   <rec>, <.rest.>, <.prn.>, <(f)> )


/* commands and standard functions with alias */
#command SEEK <exp> [<soft: SOFTSEEK>] [<last: LAST>] ;
              [TAG <tag>] [IN <wa>] => ;
         __fox_Seek( <exp>, iif( <.soft.>, .T., NIL ), ;
                            iif( <.last.>, .T., NIL ), ;
                     <(wa)>, <(tag)> )
#command SET FILTER TO <exp> IN <wa> [NOOPTIMIZE] => ;
                                 <wa>->( DbSetFilter( <{exp}>, <"exp"> ) )
#command SKIP [<n>] IN <wa>   => <wa>->( DbSkip( <n> ) )
#command UNLOCK IN <wa>       => <wa>->( DbUnlock() )
#command GO TOP IN <wa>       => <wa>->( DbGoTop() )
#command GO BOTTOM IN <wa>    => <wa>->( DbGoBottom() )
#command GOTO <nRec> IN <wa>  => <wa>->( DbGoTo( <nRec> ) )

#xtranslate SEEK( <x>, <wa> ) => (<wa>)->( DbSeek( <x> ) )
#xtranslate RECCOUNT( <wa> )  => (<wa>)->( RecCount() )
#xtranslate RECSIZE( <wa> )   => (<wa>)->( RecSize() )
#xtranslate FCOUNT( <wa> )    => (<wa>)->( FCount() )
#xtranslate RECNO( <wa> )     => (<wa>)->( RecNo() )
#xtranslate RLOCK( <wa> )     => (<wa>)->( Rlock() )

#xtranslate USED( <wa> )    => __fox_Used( <wa> )


/* other commands */
#command SCAN [FOR <for>] [WHILE <while>] [NEXT <next>] ;
              [RECORD <rec>] [<rest:REST>] [ALL] [NOOPTIMIZE] => ;
         __dbLocate( <{for}>, <{while}>, <next>, <rec>, <.rest.> ) ;;
         WHILE Found()
#command ENDSCAN => __dbContinue(); ENDDO

#command EJECT PAGE => __Eject()
#command FLUSH      => DbCommitAll()
#command REGIONAL [<defs,...>] => LOCAL <defs>


Some of my #translate/#command additions
-----------------------------------------
 #translate .NULL. => NIL
 #translate WshShell.Run => WshShell:Run
 #translate CreateObject("WScript.Shell") => win_OleCreateObject("WScript.Shell")
 #translate GETE(<cString>) => GETENV(<cString>)
 #translate SET CPDIALOG OFF =>
 #translate SHOW WINDOW <cstring> =>
 #translate RELEASE WINDOW <cstring> =>
 #translate SET COMPATIBLE ON =>
 #translate THIS. => ::
 #translate SYS(5) => diskname()+":\"
 #translate RTRIM(SYS(5)+SYS(2003)) => ALLTRIM(DISKNAME()+":\"+CURDIR())
 #translate cd (<cstring>) => hbr_chgdir(<cstring>)
 #translate parameters() => pcount()
 #translate PROGRAM() => PROCNAME()
 #translate PROGRAM( <x> ) => PROCNAME( <x> )
 #translate LINENO() => PROCLINE()
*#translate FCLOSE(<x>) => =FCLOSE(<x>)
 #translate RECCOUNT() => LASTREC()
**NOTE: Harbour displays one less space than VFP when the transform() function is called with
**      a picture display such as "@( 99,999,999,999.99" or "@( 9,999,999,999.99"
**      which in Harbour need to be  "@( 999,999,999,999.99" and "@( 99,999,999,999.99" respectively to display the same
**      #translate directives cannot be used to correct this issue as the directives will
**      either effect themselves or the results. So, we had to declares these separately using #IFNDEF
**
**      Sometimes Harbour will report that a function or procedure .PRG cannot be opened and is assumed to be external
**      when the function or procedure is contained in a different .PRG file. This occurs when the function/procedure
**      in question is called with "do function with..." syntax.  The error disappears if the function/procedure is called
**      in the function format "function()"

//NOTE: Preprocessor translates strings delimited with aprostrophies to strings delimited with quotes!
 #translate getfile("CSV:csv", <cstring,...>) => getfile({{"CSV","*.csv"}}, <cstring>)
 #translate getfile(<cstring1>, <cstring2>,  <cstring3>, 0, <cstring4>) => getfile(<cstring1>, <cstring4>, '', .f., .t.)
 #command append from (<cstring>) type csv => append_from_csv(<cstring>)
 #command append from (<cstring>) csv => append_from_csv(<cstring>)
 #command dimension <arraynme>(<arrsize>) => <arraynme> = array(<arrsize>)
 #command wait window [<msg>] timeout <xtime> => eti_timeout(<xtime>)
 #command wait timeout <xtime> => eti_timeout(<xtime>)
 #command Wait Window [<cmsg>] at <coords> Nowait => Wait Window <cmsg> NoWait
 #xtranslate WaitWindow (<xlist, ...>) timeout <millisecs> => eti_timeout(<millisecs>)
 #xtranslate WaitWindow ( <cmsg>, .F.) at <top>, <left> Nowait => WaitWindow(<cmsg>, .T.)
//NOTE: Preprocessor can translates messagebox to messageboxw
 #xcommand messagebox(<cmsg>) => eti_msgbox(<cmsg>)
 #xcommand messageboxw(<cmsg>) => eti_msgbox(<cmsg>)
 #xcommand messageboxw(<cmsg>, <ctitle>) => eti_msgbox(<cmsg>, <ctitle>)
 #command open database (<cmsg>) =>
 #command close databases =>
 #xcommand if used(<filename>) => if select(<filename>) > 0
 #xcommand if .not. used(<filename>) => if select(<filename>) <= 0
 #translate &xcmd  => (xcmd)  &&VFP cannot execute (xcmd) and Harbour cannot execute &xcmd

Harbour requires the use of brackets with arrays whereas VFP also allows parentheses.

Harbour seems to have an issue with .PRG files that contain multiple Procedures/Functions but are named
for the top Procedure/Function in the file which is naturally missing the Procedure/Function declaration
statement.  This will result in a link error that says there are multiple definitions of that top
Procedure/Function.  Rename the PRG and give the top Procedure/Function a proper declaration statement to
resolve the issue.

A related Harbour issue is you may get a build error that states Harbour:
  Cannot open XXXXXXX.prg, assumed external
where xxxxxxx is the top Procedure/Function of one of the renamed .PRGs.  This seems to occur if the
Procedure/Function is called with the DO With command. Changing the procedure call from "DO" style to
function style seems tocorrect this problem; e.g.,
  DO Load_Data with "loans.csv"
  to
  Load_Data("loans.csv")

Harbour does not have the EXECSCRIPT() function.  Below is an equivalent created procedure; however, the use of
this function uses the Harbour compiler which is GPL.  This means if you use the below EXECSCRIPT(), you
have to make your code open source.

#IFDEF HBR
Procedure Execscript
parameter xCode
 local CONTENT, HANDLE_HRB, PRG, HRBCODE, EOL
 PRG := "proc P()" + crlf+;
        xCode + crlf+;
       "return"
 HRBCODE := hb_compileFromBuf( PRG, "harbour", "\n")
 hb_hrbRun(HRBCODE)
return
#ENDIF

Harbour does not seem to have an equivalent to VFP ALINES(). For Harbour users who are interested, Alines()
parses a char field or memo field to an array. I have not had the time to create a Harbour equivalent
function yet, nor have I found coding for one.

I don't think Harbour allows SQL queries against DBF files.  However, you can create
functions to accomplish many of the same tasks that you would want to accomplish with SQL.
Below is code to enable you to add a field to a .DBF:
Function Add_Field(laliasname, newfield, fldtype, fldlen, flddec)
 local a, x
 x = Ascan(::aFaliases, upper(laliasname))
 if x = 0
  ***report error that laliasname wasn't found
 endif
 select (laliasname)
 a := dbStruct()
 close (laliasname)
 aadd( a, {newfield, fldtype, fldlen, flddec} )
 dbCreate( "newDbf", a, , .T. )
 APPEND FROM (::aFnames[x])
 close newdbf
 Ferase( ::aFnames[x] )
 Frename( "newDbf.dbf", (::aFnames[x]) )
 select 0
 use (::aFnames[x]) alias (::aFaliases[x])
return

Harbour has no COPY TO ARRAY command, so below is a routine you can use to populate an array
with DBF field data:

  **routine assumes field to list is in current work area dbf
  PROCEDURE Copy_To_Array(FieldName, aField)
  Local x
    Asize(aField, Reccount())
    For x = 1 to Reccount()
      aField[x] = (FieldName)
    Next
  Return

  **Sample call
  Local aField[1]
  Copy_To_Array("ID_Code", @aField)

While Harbour's COPY TO command can create a delimited file, it can not create a .CSV file which
is a delimited file with a header record listing the fields. Below is a routine to create a
.CSV file in Harbour
**routine to create a csv file for HBR
procedure make_csv()
parameter csvfilename
local x, xhdr, xtemp, WshShell
   xtemp = "temp1.dat"
   xhdr = ""
   FOR x := 1 to FCOUNT()
     xhdr = xhdr + '"'+rtrim(FieldName(x))+'",'
   NEXT
   fhandle = fcreate(xtemp, 0)
   if fhandle < 0
     eti_msgbox("Error creating error file: "+ xtemp)
     wait
     quit
   endif
   writelen = fwrite(fhandle, xhdr)
   if writelen <> len(xhdr)
      eti_msgbox("Error writing to "+ xtemp)
      quit
   endif
  fclose(fhandle)
  copy to temp2.dat delimited
  WshShell = win_OleCreateObject("WScript.Shell")
  run_command = 'copy temp1.dat + temp2.dat '+csvfilename+' & del temp1.dat & del temp2.dat & exit'
  WshShell:Run("cmd /K "+run_command, 0, 1)
return


Similarly, Harbour does not enable appending from a .CSV file.  Below is a procedure to enable
appending from a .CSV file:
***routine to append from a CSV file for HBR
procedure append_from_csv()
parameter csvfile
local curr_rec
curr_rec = reccount()
append from &csvfile delimited
go curr_rec + 1
delete next 1
return


When appending one DBF to another, VFP will automatically convert fields with the same name
that have different field types. HBR does not. Below is code and an example created by Zoran Sibinovic
to handle this issue:
#command APPCONV [FROM <(f)>] [FIELDS <fields,...>] [FOR <for>] [VIA <rdd>] [EMPTYDEST <empty>] => ;
            __dbmyapp( <(f)>, { <(fields)> }, <{for}>, <rdd>,  <.empty.> )

#include "common.ch"

****************
PROCEDURE MAIN()

SET EXACT ON
SET DATE GERM
SET CENT ON

?time()

USE arhiva1 NEW

APPCONV FROM arhiva FIELDS objasn,ime,jedinica,za_mesec EMPTYDEST .T.

?time()
wait

*********************************************
PROCEDURE __dbmyapp(cBaseOld, aFields, bFor, rdd, empty )
Local aBaseOld, aBaseNew, aFieldsDiff:={}, mSelectOld, mSelectNew, i, aFieldsOk:={}, aTemp
Local aTempNew:={}, aTempOld:={}, SelNew, SelOld, nOrder:=INDEXORD(), nCountOld:=0, nCountNew

DEFAULT empty TO .f.

AEVAL(aFields,{|aVal,nIndex| aFields[nIndex] := UPPER(aFields[nIndex]) })
aFields:=IF(EMPTY(aFields),nil,aFields)

mSelectNew:=SELECT()
aBaseNew:=DBSTRUCT()
IF empty = .t. ; ZAP ; ENDIF
nCountNew=LASTREC()

DBUSEAREA( .t.,rdd, (cBaseOld),,.t.,.t.)
IF !HB_ISNIL(bFor)
   DBEVAL({|| nCountOld++ },bfor )
ELSE
   nCountOld:=LASTREC()
ENDIF

mSelectOld:=SELECT()
aBaseOld:=DBSTRUCT()

** shrink the arrays if aFields<>nil
IF !HB_ISNIL(aFields)
   aTemp:={}
   AEVAL(aBaseNew,{|aVal,nIndex| IF(ASCAN(aFields,aBaseNew[nIndex,1])<>0,AADD(aTemp,aBaseNew[nIndex]),"") })
   aBaseNew:=aTemp

   aTemp:={}
   AEVAL(aBaseOld,{|aVal,nIndex| IF(ASCAN(aFields,aBaseOld[nIndex,1])<>0,AADD(aTemp,aBaseOld[nIndex]),"") })
   aBaseOld:=aTemp
ENDIF

** find where the fields exist and of what type they are
FOR i = 1 TO LEN(aBaseOld)
    IF (nPos:=ASCAN(aBaseNew,{ |x| x[1] == aBaseOld[i,1] }))<>0
       AADD(aTempNew,aBaseNew[nPos]) // exist in both
       AADD(aTempOld,aBaseOld[i]) // exist in both
    ENDIF
NEXT

aBaseNew:=atempNew
aBaseOld:=atempOld

FOR i = 1 TO LEN(aBaseOld)
    IF ( nPos:=ASCAN( aBaseNew,{ |x| x[1] == aBaseOld[i,1] } ) ) <> 0 .AND. aBaseOld[i,2] <> aBaseNew[nPos,2]
      AADD(aFieldsDiff,{ aBaseOld[i,1],aBaseOld[i,2]+aBaseNew[nPos,2],aBaseOld[i,3],aBaseOld[i,4] } ) // fields of different type
    ELSE
      AADD(aFieldsOk,{ aBaseOld[i,1] } ) // fields of same type
    ENDIF
NEXT
aFieldsOk:=IF(EMPTY(aFieldsOk),nil,aFieldsOk)

*******************
CLOSE (mSelectOld)
SELECT (mSelectNew)
DBSETORDER(0)

IF EMPTY(aFieldsDiff)
   __dbApp( cBaseOld, aFieldsOk, bFor,,,,,rdd )
   DBSETORDER(nOrder)
   RETURN
ENDIF

IF !HB_ISNIL(aFieldsOk)
   __dbapp( cBaseOld, aFieldsOk, bFor,,,,,rdd )
ELSE
   DO WHILE nCountOld--<>0 ; DBAPPEND() ; ENDDO
ENDIF

IF LASTREC()=nCountNew ; DBSETORDER(nOrder) ; RETURN ; ENDIF
DBGOTO(nCountNew+1)

DBUSEAREA( .t.,rdd, (cBaseOld),,.t.,.t.)
mSelectOld:=SELECT()
DBSETORDER(0)
IF !HB_ISNIL(bFor) ; DBSETFILTER(bFor) ; ENDIF
DBGOTOP()

DO WHILE !EOF()
   FOR i = 1 TO LEN(aFieldsDiff)
       xField=aFieldsDiff[i,1]
      (mSelectNew)->&xField:=DOCONVERT(aFieldsDiff[i,1],aFieldsDiff[i,2],aFieldsDiff[i,3],aFieldsDiff[i,4])
   NEXT
   DBSKIP()
   (mSelectNew)->(DBSKIP())
ENDDO

DBCLOSEAREA()

SELECT (mSelectNew)
DBSETORDER(nOrder)

*******************
FUNCTION DOCONVERT( cName, cTypeTo, nLength, nDecimals )

Local xValue := &cName

DO CASE

   CASE cTypeTo = "CN"                       ; xValue = VAL( xValue )
   CASE cTypeTo = "CD"                       ; xValue = CTOD( ALLTRIM( xValue ) )
   CASE cTypeTo = "CL"                       ; xValue = IF( LEFT( xValue,1 ) $ "1Tt",.t.,.f. )
   CASE cTypeTo = "CM"                       ; xValue = ALLTRIM( xValue )

   CASE cTypeTo = "NC"                       ; xValue = STR( xValue, nLength, nDecimals )
   CASE cTypeTo = "ND"                       ; xValue = DTOC("")
   CASE cTypeTo = "NL" .AND. LEN(xValue)=1   ; xValue = IF( xValue = 1,.t.,.f. )
   CASE cTypeTo = "NL"                       ; xValue = .f.
   CASE cTypeTo = "NM"                       ; xValue = ALLTRIM( STR( xValue, nLength, nDecimals ) )

   CASE cTypeTo $ "DC DM"                    ; xValue = DTOC( xValue )
   CASE cTypeTo $ "DN DL"                    ; xValue = 0

   CASE cTypeTo $ "LC LM"                    ; xValue = IF( xValue, "T", "F" )
   CASE cTypeTo = "LN"                       ; xValue = IF( xValue, 1, 0 )
   CASE cTypeTo = "LD"                       ; xValue = DTOC( "" )

   CASE cTypeTo = "MC"                       ; xValue = ALLTRIM( xValue )
   CASE cTypeTo = "MN"                       ; xValue = VAL( ALLTRIM( xValue ) )
   CASE cTypeTo = "MD"                       ; xValue = CTOD( ALLTRIM( xValue ) )
   CASE cTypeTo = "ML"                       ; xValue = IF( LEFT( xValue,1 ) $ "1Tt",.t.,.f. )

ENDCASE

RETURN  xValue
****end APPCONV relate code from Zoran Sibinovic
************************************************************************************************************
************************************************************************************************************

Harbour did not seem to process the change directory "CD" command in the same manner as VFP.
Here is a routine to change directory equivalent to VFP CD command. Used in conjunction with the
"#translate cd (<cstring>) => hbr_chgdir(<cstring>)" preprocessor command, you don't have to change
your code:

procedure hbr_chgdir
parameter newdir
 result := dirchange(rtrim(right(padr(newdir,50),48)))
 if result != 0
  ? "Failed to change directory to", newdir
  quit
 endif
 diskchange(left(newdir,2))
return


HMG and VFP Differences/Observations
====================================
It would be unrealistic to expect HMG to be able to read/convert VFP .SCX files.  However, I believe that
it is possible to create a set of functions/procedures to do some of the conversion where VFP and HMG have
the same type of screen objects.  While I have not created those functions/procedures, there are some steps
that I have figured out to simplify the conversion.  The first step is to convert the .SCX file into a
.PRG file:
 From the main VFP IDE menu:
  -Tools --> Class Browser  --if nothing comes up then do:
           Tools --> Component Gallery
           -Click on the Class Browser Icon on the Component Gallery form
  -Click Open (the yellow folder icon).
  -From the Files of type drop-down, choose Form.
  -Select the form you wish to open.
  -In the class browser, click View Class Code (fourth icon from the left).
  -You can copy and paste this into a .PRG or other text file which can then be converted for HMG

Like VFP, the HMG IDE allows you to design a window form with objects.  The HMG IDE will put the results of your design
into a .FMG file which is functionally like a .PRG file.  You could add comments, procedures and functions to the
.FMG file; however, it is not recommended as modifying form with HMG IDE deletes comments, procedures and functions; so,
put procedures and functions into their own .PRG file.

Check boxes seem to align and size best with height and width are both 13.

I think VFP has the default Form Font and Font Size listed under Options/Debug/Environment:Foxpro Frame:Font.
I am not sure where the default HMG font and size are set.

Currently, in HMG, when you "DO FORM", HMG apparently #includes the form into the calling .PRG.  So, if you have an
error in your form construction that causes a runtime error, the stack display of the runtime error does
not list the form.  Instead, the stack display lists the procedure that called the form but rather than showing the
line number where that procedure calls the problematic form, it shows the last line number of the form object that
is causing the problem.

HMG does not have an UNLOAD event. Use the RELEASE method instead.

HMG GRIDs do not naturally display logical fields as CHECKBOXs. However, there is a way to make grids
work the same way at:
http://www.hmgforum.com/viewtopic.php?f=24&t=3583&p=32962&hilit=Lista+de+asistencia#p32962

While a Listbox in VFP can list the contents of a DBF field, HMG's Listbox only lists the contents of
an array.  Since HMG/Harbour has no COPY TO ARRAY command, use the Copy_To_Array Procedure listed above
to populate an array with DBF field data

When you look at HMG TEXTBOX and other object Events, you may notice that CLICK, DBLCLICK Events, etc.
are missing. Don't worry.  A neat feature has been added to HMG that allows you to create/define such
Events using code similar to:
   CREATE EVENT PROCNAME Textbox_Name_DBLCLICK() HWND Window_Name.Textbox_Name.HANDLE STOREINDEX nIndex
   EventProcessAllHookMessage ( nIndex, .T. )

Mario H. Sabado

unread,
Jan 6, 2016, 10:01:29 PM1/6/16
to harbou...@googlegroups.com
Hi Jeff,

Many thanks for this VFP to Harbour/HMG conversion guide.  Very helpful.

For the Make_CSV sample routine, I have the following code which I think is simpler for my use and does not rely on external scripting shell and physical temporary files creation.  It also utilize Przemek's (big thanks Przemek!) new GZIP IO which can save memory space for large files.
***********************************************************************************
REQUEST HB_MEMIO,HB_GZIO
function Dbf2Csv(cAlias)
  local nFCount:=(cAlias)->(FCount()),cHeaderLine:=""
  //gather fields as header
  AEVal( (cAlias)->(DbStruct()),{|x|cHeaderLine+=x[1] + ;
                                    IIF( x[1]!=(cAlias)->(FieldName(nFCount)),",","") } )
  COPY TO "gz:mem:csv_"+(cAlias)+".csv" DELIMITED //copy to memory file
  Hb_MemoWrit( cAlias+".csv",cHeaderLine+Hb_Eol()+Hb_MemoRead("gz:mem:csv_"+(cAlias)+".csv") )
  Hb_vfErase("mem:csv_"+(cAlias)+".csv")
return nil
***********************************************************************************

Regards,
Mario
--
--
You received this message because you are subscribed to the Google
Groups "Harbour Users" group.
Unsubscribe: harbour-user...@googlegroups.com
Web: http://groups.google.com/group/harbour-users

---
You received this message because you are subscribed to the Google Groups "Harbour Users" group.
To unsubscribe from this group and stop receiving emails from it, send an email to harbour-user...@googlegroups.com.
For more options, visit https://groups.google.com/d/optout.

Przemyslaw Czerpak

unread,
Jan 7, 2016, 5:12:23 AM1/7/16
to harbou...@googlegroups.com
On Wed, 06 Jan 2016, Jeff Stone wrote:

Hi Jeff,

Below are few notes about your PP rules.

> From hbfoxpro.ch
> Some of my #translate/#command additions
> -----------------------------------------
> #translate .NULL. => NIL

I'll add it to hbfoxpro.ch

> #translate WshShell.Run => WshShell:Run

This is covered by more general rule:
#xtranslate .<!msg!> => :<msg>
so you do not need it.

> #translate CreateObject("WScript.Shell") => ;
> win_OleCreateObject("WScript.Shell")

It's special case.
#xtranslate CreateObject( => win_OleCreateObject(
is more general. Anyhow it can be resolved by simple
function wrapper and such version works also with
macro compiler:
FUNCTION CreateObject( ... )
RETURN win_oleCreateObject( ... )
I can add it but xHarbour has function with the same
name what creates conflicts so meanwhile I'm leaving
it to user.

> #translate GETE(<cString>) => GETENV(<cString>)

Harbour allready has GETE() so above it's not necessary.

> #translate THIS. => ::

I'll add it.

> #translate SYS(5) => diskname()+":\"

As far as I know SYS( 5 ) should return Set( _SET_DEFAULT )
and it's implemented in such way. You made sth different,
what is the exact meaning of this SET in VFP?

> #translate RTRIM(SYS(5)+SYS(2003)) => ALLTRIM(DISKNAME()+":\"+CURDIR())

I'll add support for 2003 to contrib/hbfoxpro/misc.prg SYS()
function.

> #translate cd (<cstring>) => hbr_chgdir(<cstring>)

it should be:
#xcommand CD <(path)> => hb_cwd( <(path)> )

> #translate parameters() => pcount()

it already exists in hbfoxpro library.

> #translate PROGRAM() => PROCNAME()
> #translate PROGRAM( <x> ) => PROCNAME( <x> )
> #translate LINENO() => PROCLINE()

I'll add above as simple function wrappers.

> #translate RECCOUNT() => LASTREC()

this is unnecessary, RECCOUNT() is part of Harbour
core code.

> **NOTE: Harbour displays one less space than VFP when the transform()
> function is called with
> ** a picture display such as "@( 99,999,999,999.99" or "@(
> 9,999,999,999.99"
> ** which in Harbour need to be "@( 999,999,999,999.99" and "@(
> 99,999,999,999.99" respectively to display the same
> ** #translate directives cannot be used to correct this issue as the
> directives will
> ** either effect themselves or the results. So, we had to declares
> these separately using #IFNDEF

The differences in Transform() command should be covered by
new fox_Transform() function. Anyhow to implement it it's
necessary to create regression tests which can be executed
by VFP so we can compare results for different formats.
I do not have VFP so I cannot make it.

> ** Sometimes Harbour will report that a function or procedure .PRG
> cannot be opened and is assumed to be external
> ** when the function or procedure is contained in a different .PRG
> file. This occurs when the function/procedure
> ** in question is called with "do function with..." syntax. The error
> disappears if the function/procedure is called
> ** in the function format "function()"

It's standard Clipper behavior.
DO <funcname> [WITH <params,...>]
has special meaning. Compiler checks if <funcname>.prg exists and
add it to compiled files. If you want to disable this functionality
use -m Harbour compiler switch.

> //NOTE: Preprocessor translates strings delimited with aprostrophies to
> strings delimited with quotes!
> #translate getfile("CSV:csv", <cstring,...>) => getfile({{"CSV","*.csv"}},
> <cstring>)
> #translate getfile(<cstring1>, <cstring2>, <cstring3>, 0, <cstring4>) =>
> getfile(<cstring1>, <cstring4>, '', .f., .t.)

GETFILE() is not Harbour function so I do not know why you need it.
It should be part of GETFILE() function.

> #command dimension <arraynme>(<arrsize>) => <arraynme> = array(<arrsize>)

hbfoxpro.ch already contains:
#command DIMENSIONS <!name1!>( <dim1,...> ) [, <!nameN!>( <dimN,...> ) ] => ;
PRIVATE <name1>\[ <dim1> \] [, <nameN>\[ <dimN> \] ]
is it wrong?

> #xcommand if used(<filename>) => if select(<filename>) > 0
> #xcommand if .not. used(<filename>) => if select(<filename>) <= 0

hbfoxpro.ch already contains:
#xtranslate USED( <wa> ) => __fox_Used( <wa> )
is it wrong?

> #translate &xcmd => (xcmd) && VFP cannot execute (xcmd) and Harbour
> cannot execute &xcmd

??? I do not understand it. This code:

request QOUT
proc main()
local xcmd := "QOUT( 'THIS is test!!!' )"
&xcmd
return

so probably you need some other functionality.
Can you create as small as possible self contain code example
which illustrates the problem?

> Harbour requires the use of brackets with arrays whereas VFP
> also allows parentheses.

For PUBLIC, PRIVATE and DIMENSIONS declarations it should be
resolved by rules in hbfoxpro.ch
If VFP accepts parentheses also to access array items then it
cannot be easy implemented because it create conflict with
function call, i.e.:
a := { "A", "B", "C" }
? a[ 2 ] // array item
? a( 2 ) // call function A with 2 as first parameter
I do not know what VFP makes in such case.

> Harbour seems to have an issue with .PRG files that contain multiple
> Procedures/Functions but are named
> for the top Procedure/Function in the file which is naturally missing the
> Procedure/Function declaration
> statement. This will result in a link error that says there are multiple
> definitions of that top
> Procedure/Function. Rename the PRG and give the top Procedure/Function a
> proper declaration statement to
> resolve the issue.

The proper solution is -n harbour compiler switch.
Without -n Harbour and Clipper creates hidden function
with the same name as .prg filename.
So all what you need is adding -n to your .hbp file.

> A related Harbour issue is you may get a build error that states Harbour:
> Cannot open XXXXXXX.prg, assumed external
> where xxxxxxx is the top Procedure/Function of one of the renamed .PRGs.
> This seems to occur if the
> Procedure/Function is called with the DO With command. Changing the
> procedure call from "DO" style to
> function style seems tocorrect this problem; e.g.,
> DO Load_Data with "loans.csv"
> to
> Load_Data("loans.csv")

See above, the proper solution is -m compiler switch.

> Harbour does not seem to have an equivalent to VFP ALINES(). For Harbour
> users who are interested, Alines()
> parses a char field or memo field to an array. I have not had the time to
> create a Harbour equivalent
> function yet, nor have I found coding for one.

What is line delimiter in this function?
Is it correct substitute?
#xtranslate ALines( <text> ) => hb_ATokens( <text>, .T.)

> I don't think Harbour allows SQL queries against DBF files.

Yes and adding such functionality needs a lot of work
and I do not have time for it so it will have to wait
for some other developer.

> Harbour has no COPY TO ARRAY command, so below is a routine
> you can use to populate an array with DBF field data:
>
> **routine assumes field to list is in current work area dbf
> PROCEDURE Copy_To_Array(FieldName, aField)
> Local x
> Asize(aField, Reccount())
> For x = 1 to Reccount()
> aField[x] = (FieldName)

I think you rather wanted to make sth like:
aField[x] := &FieldName

> Next
> Return
>
> **Sample call
> Local aField[1]
> Copy_To_Array("ID_Code", @aField)

I can add general command:

#command COPY [TO ARRAY <v>] [FIELDS <fields,...>] ;
[FOR <for>] [WHILE <while>] [NEXT <next>] ;
[RECORD <rec>] [<rest:REST>] [ALL] => ...

anyhow it will not follow the exact VFP rules but rather
Cl*pper ones.

> While Harbour's COPY TO command can create a delimited file, it can not
> create a .CSV file which
> is a delimited file with a header record listing the fields.
> Similarly, Harbour does not enable appending from a .CSV file.

That's interesting functionality. I'll add for support
optional exporting filed names in first row to DELIM RDD.

> Similarly, Harbour does not enable appending from a .CSV file.

In import operation it is more complicated sue to Cl*pper
comptible protocol used in TRANSFER RDDs. I'll check what
I can do inside DELIM RDD code anyhow probably it will be
necessary to add external routine which open the CSV file
just to read field list and then close it before the real
import by DELIM RDD.

> When appending one DBF to another, VFP will automatically convert fields
> with the same name
> that have different field types. HBR does not. Below is code and an example
> created by Zoran Sibinovic
> to handle this issue:
> #command APPCONV [FROM <(f)>] [FIELDS <fields,...>] [FOR <for>] [VIA <rdd>]
> [EMPTYDEST <empty>] => ;
> __dbmyapp( <(f)>, { <(fields)> }, <{for}>, <rdd>, <.empty.> )
[...]

I think that adding error handler for type conversion.
If attached code makes VFP compatible conversions then
I can use this information to create such error handler.
BTW What VFP does when numeric field in destination table
is not large enough to hold the source number? Does it
generate data width error?

> Harbour did not seem to process the change directory "CD" command in the
> same manner as VFP.

Harbour does not have CD command but the functionality
you are asking for is realized by hb_cwd() function.
See PP rule above.

best regards,
Przemek

Jeff Stone

unread,
Jan 7, 2016, 6:06:20 PM1/7/16
to Harbour Users
Hi Przemek,
 
Thanks for the feedback. 
 
I think there may be some overlap/duplication in my PP rules as I was using hbfoxpro.ch that is included with the latest HMG build.  I think several of the \contrib libraries that are included with HMG are not up to date with the latest Harbour builds. So, my PP rules for Dimension(), USED() and others were needed by HMG but not Harbour.
 
In answer to some of your questions:
 
-SYS(5) in VFP is Default drive or volume.  So, perhaps I coded it incorrectly.
 
 In case anyone is interested, I am attaching a file that shows all of the VFP SYS codes.
 
-Regarding a fox_Transform() function, I would be happy to run whatever test you need in VFP, if you want to create the function.
 
-I think GETFILE() is an HMG function
 
-Below is VFP code where &xcmd had to be converted to (xcmd) in Harbour:
 if deals597->client = "PMC"
   tmp_loan_id = "loan_id2"
 else 
   tmp_loan_id = "loan_id" 
 endif
 select oldcol
 xcmd = "seek temp->"+tmp_loan_id
 &xcmd
If I understand Harbour/Clipper, & will substitute the contents of xcmd for a variable reference.  However, because I want the contents of xcmd to  be evaluated as a command, Harbour needs to have the last line as (xcmd)

-Alines() by default uses CHR(10), CHR(13), CHR(10)+CHR(13) or CHR(13)+CHR(10) as the line delimiter, so I think:
    #define CRLF HB_OsNewLine()
    aLines := HB_ATOKENS( MEMOREAD( cTextFName ), CRLF )
will accomplish the default behavior of Alines().  Thanks for that info.  If you care, here is the VFP description for Alines():
ALINES(ArrayName, cExpression [, lTrim] [cParseChar, ,… ,cParseChar])

Parameters

ArrayName
Specifies the name of the array to which the lines in the character expression or memo field are copied.

If the array you specify does not exist, Visual FoxPro automatically creates the array. If the array exists but is not large enough to contain all the lines in the memo field, Visual FoxPro automatically increases the size of the array. If the array is larger than necessary, Visual FoxPro truncates the array.

cExpression
Specifies the character expression or memo field containing the lines copied to the array. All character expressions are case-sensitive.

If cExpression is the empty string or the null value, an array with a single row is created and the row contains the empty string. You can use double-byte expressions.

lTrim
Specifies that leading and trailing blanks are removed from the lines copied to the array. If lTrim is true (.T.), leading and trailing blanks are removed from the lines. If lTrim is false (.F.) or is omitted, leading and trailing blanks are not removed.
cParseChar
Specifies one or more character strings that terminate the elements in cExpression. The maximum number of strings permitted in cParseChar is 23. The maximum length for each string is 11 characters.

A line feed (CHR(10)) or carriage return (CHR(13)) character denotes the end of a line. The end of the line can also be denoted with either combination of these two characters (CHR(10) + CHR(13) or CHR(13) + CHR(10)). The default behavior for ALINES( ) is to ignore CHR(13) and CHR(10) when you specify one or more values for cParseChar, unless you also specify the end of line characters.

Return Values

Numeric. ALINES( ) returns the number of rows in the array, or, identically, the number of lines in the character expression or memo field.

 
VFP_SYS_Codes.jpg

Francesco Perillo

unread,
Jan 7, 2016, 6:30:48 PM1/7/16
to harbou...@googlegroups.com
Sorry Jeff, are you sure that the following code snippet is real code ???

I ask since this code will never work in Harbour and changing &xcmd to (xcmd) means that it is not executed but that the content of xcmd variable is put on the stack and then discarded..!!!

If you want, you can change the code in:
xcmd = "dbseek(temp->"+tmp_loan_id + ")"
and then use &xcmd and the seek is performed. I don't know if dbSeek exists in VFP...

Harbour macro compiler can't compile commands but can compile functions.

I'd probably refactor the code a bit, but it depends a lot on the code before and after this...

See below for a test code.

 
-Below is VFP code where &xcmd had to be converted to (xcmd) in Harbour:
 if deals597->client = "PMC"
   tmp_loan_id = "loan_id2"
 else 
   tmp_loan_id = "loan_id" 
 endif
 select oldcol
 xcmd = "seek temp->"+tmp_loan_id
 &xcmd


Copy this snippet on a test.prg and update it to point to a dbf and index file, then add a value to be searched.

#pragma -w0

procedure main

use file index index

? recno()
xcmd = "seek 'value'"
(xcmd)
? recno()

// &xcmd   commented as it will generate an error

xcmd = "dbseek('value')"
&xcmd
? recno()

You will see that (xcmd) doesn't move the record pointer in Harbour...

 

Jeff Stone

unread,
Jan 8, 2016, 11:36:07 AM1/8/16
to Harbour Users
Hi Francesco,
 
Thanks very much for your post.  Indeed, my code would not work.  While VFP has _DBSEEK() as an API Library Routine, I think a PP command to convert the VFP seek to DB seek would be fine.  There were one thing I noticed in testing which may be helpful for others...
 
I created a test a Test.prg as you suggested:
 
procedure main
  use test
  index on fldx to test
  Go Top
  ? recno()
  seekstr = "x2"
  xcmd = "seek "+seekstr
  (xcmd)
  ? recno()
  xcmd = "dbseek(seekstr)"
  &xcmd
  ? recno()
return     
 
Running the .PRG, I got a runtime error message: Error BASE/1001  Undefined function: DBSEEK
So, then I replaced
          GO TOP
with
           DBSEEK("X1")    &&go to top record
and the runtime error message went away and the .PRG ran to completion and as desired.

This suggests that DBSEEK related code was not linked into the executable the first time because the compiler did not see an explicit DBSEEK call. 

Anyway, I changed our VFP code:
   xcmd = "seek temp->"+tmp_loan_id
to
   xcmd = "seek "+"temp->"+tmp_loan_id

and then used the following PP code to enable the .PRG to work for Harbour:
     #translate "seek "<seekstr> => "dbseek(<seekstr>)"   

Again, thanks for the feeback.

Jeff
 
 

Francesco Perillo

unread,
Jan 8, 2016, 12:49:08 PM1/8/16
to harbou...@googlegroups.com
Yes, sorry, I used hbrun to run the program. It is a sort of interpreter of .prg files and has a lot of functions already linked.

If you compile you need to link dbseek and can, for example, add the line
REQUEST dbseek

If you want to modify the code, I'd like to suggest something different. You should adapt it to your code, before and after that...

instead of storing the field name and use a costly macro compile/run, since *it seems* that *almost in this case* the options are just two, you can simplify the code in:


     if deals597->client = "PMC"
       cTmp = TEMP->loan_id2
     else
       cTmp = TEMP->loan_id
     endif
     select oldcol
     seek (cTmp)


If you need the tmp_loan_id variable in other places, you can still use it, but not in the seek-macro. The above code should be still compatible with VFP since it is standard db3 code.




--

jast...@gmail.com

unread,
May 21, 2021, 9:56:02 AM5/21/21
to Harbour Users
I recently discovered that VFP is very forgiving when appending .txt files in terms of End of Line markers.  VFP is okay with a line ending with Chr(13)+Chr(10), just Chr(13) or just Chr(10).  Harbour is not okay with lines ending in just Chr(10) by default.  If you know that you have to import a .txt file whose lines end with just Chr(10), you can add the following lines:
    cDefEol := SET( _SET_EOL, chr( 10 ) )
prior to your APPEND call and APPEND will now execute correctly.  If you then want APPEND to revert back to normal behavior, I think you may need to add:
   SET( _SET_EOL, cDefEol )
afterwards.


Reply all
Reply to author
Forward
0 new messages