Mem Files

Mem Files

Postby Silvio.Falconi » Thu Oct 07, 2021 11:16 am

Someone has a utility to load,show,save the oldest Mem files ?
I found the source of MemFedit but I cannot converte it ( clipper)
Since from 1991/1992 ( fw for clipper Rel. 14.4 - Momos)
I use : FiveWin for Harbour November 2023 - January 2024 - Harbour 3.2.0dev (harbour_bcc770_32_20240309) - Bcc7.70 - xMate ver. 1.15.3 - PellesC - mail: silvio[dot]falconi[at]gmail[dot]com
User avatar
Silvio.Falconi
 
Posts: 6768
Joined: Thu Oct 18, 2012 7:17 pm

Re: Mem Files

Postby Antonio Linares » Thu Oct 07, 2021 11:25 am

Dear Silvio,

Have you tried with Harbour function __MRestore() ?
regards, saludos

Antonio Linares
www.fivetechsoft.com
User avatar
Antonio Linares
Site Admin
 
Posts: 41314
Joined: Thu Oct 06, 2005 5:47 pm
Location: Spain

Re: Mem Files

Postby Silvio.Falconi » Fri Oct 08, 2021 6:32 am

Antonio Linares wrote:Dear Silvio,

Have you tried with Harbour function __MRestore() ?


I'm converting an oldest prg from Dos Clipper I made ( I think is from clipper since 90 years)

I not Know this function wich are the paramters ?
Since from 1991/1992 ( fw for clipper Rel. 14.4 - Momos)
I use : FiveWin for Harbour November 2023 - January 2024 - Harbour 3.2.0dev (harbour_bcc770_32_20240309) - Bcc7.70 - xMate ver. 1.15.3 - PellesC - mail: silvio[dot]falconi[at]gmail[dot]com
User avatar
Silvio.Falconi
 
Posts: 6768
Joined: Thu Oct 18, 2012 7:17 pm

Re: Mem Files

Postby Antonio Linares » Fri Oct 08, 2021 6:49 am

It is used from https://github.com/harbour/core/blob/master/tests/memfile.prg this way:

? __MRestore( "memfile", .F., "m_nDouble*", .T. )

Correct name is function __MVRestore() and it is implemented here (so you can review each parameter):
https://github.com/harbour/core/blob/d407898675b14fbf9b10cd2e23723e9a522686e5/src/vm/memvars.c
regards, saludos

Antonio Linares
www.fivetechsoft.com
User avatar
Antonio Linares
Site Admin
 
Posts: 41314
Joined: Thu Oct 06, 2005 5:47 pm
Location: Spain

Re: Mem Files

Postby Silvio.Falconi » Fri Oct 08, 2021 7:34 am

Antonio Linares wrote:It is used from https://github.com/harbour/core/blob/master/tests/memfile.prg this way:

? __MRestore( "memfile", .F., "m_nDouble*", .T. )

Correct name is function __MVRestore() and it is implemented here (so you can review each parameter):
https://github.com/harbour/core/blob/d407898675b14fbf9b10cd2e23723e9a522686e5/src/vm/memvars.c


Antonio,
Perhaps I found a function It browse me all variables but I cannot show the values
I saw all the variables init form CFG_


Function test()
local aVar:= {}

nMemHandle := Fopen( 'config.mem', 2 )
nMemLength := Fseek( nMemHandle, 0, 2)
Fseek(nMemHandle,0)
nCount := 1

Do While Fseek(nMemHandle, 0, 1)+1 < nMemLength
nMemWidth:= space(18)
Fread( nMemHandle, @nMemWidth, 18 )
cVarName := Left( nMemWidth, At( Chr(0) , nMemWidth ) -1 )
cVartype := Substr( nMemWidth, 12, 1 )
cVarRec := Bin2w( Right( nMemWidth, 2 ) )


nMemCount:= If( cVarType $ Chr(195)+Chr(204), 14+cVarRec, 22 )
Fseek(nMemHandle, nMemCount, 1)




aadd(aVar,{cVarName,cVartype,cVarRec,nMemCount})

EndDo

xbrowser avar

Fclose( nMemHandle )

return nil
Since from 1991/1992 ( fw for clipper Rel. 14.4 - Momos)
I use : FiveWin for Harbour November 2023 - January 2024 - Harbour 3.2.0dev (harbour_bcc770_32_20240309) - Bcc7.70 - xMate ver. 1.15.3 - PellesC - mail: silvio[dot]falconi[at]gmail[dot]com
User avatar
Silvio.Falconi
 
Posts: 6768
Joined: Thu Oct 18, 2012 7:17 pm

Re: Mem Files

Postby Jack » Sat Oct 09, 2021 8:26 am

I use : restore from DATA.MEME ADDITIVE and it works fine .

I know the name of memvar store in the MEM files .

Have a good WD

Philippe
Jack
 
Posts: 280
Joined: Wed Jul 11, 2007 11:06 am

Re: Mem Files

Postby Jimmy » Sat Oct 09, 2021 8:35 am

hi,

i have some (old) Code which work under Cl*pper and Xbase++
i have try same Code under harbour and got 3 "missing"
FExists()
F2BIN()
BIN2F()

so i add
Code: Select all  Expand view
#IFDEF __XPP__
#ELSE
   REQUEST HB_GT_WIN_DEFAULT
   #xTranslate FExists => File
#ENDIF

and in harbour *.HBC
Code: Select all  Expand view
libs=hbxpp.hbc


but i got "empty" Result ... hm

i have "extract" HB_FUNC from hbxpp and add it to Demo Code
if someone can "fix-it" for harbour
Code: Select all  Expand view
/*****************************
* Source : memedit.prg
* System :
* Author : Phil Ide
* Created: 07-Dec-2004
*
* Purpose:
* ----------------------------
* History:
* ----------------------------
* 07-Dec-2004 14:39:39 idep - Created
*
* ----------------------------
* Last Revision:
*    $Rev$
*    $Date$
*    $Author$
*    $URL$
*
*****************************/


#include "common.ch"
#include "fileio.ch"

#define CRLF Chr(13)+Chr(10)
#define SIZEOF_MEM_RECORD       32

#define VAR_NAME  1
#define VAR_TYPE  2
#define VAR_LEN   3
#define VAR_DEC   4
#define VAR_VALUE 5

#define VAR_SIZE 5

#IFDEF __XPP__
#ELSE
   REQUEST HB_GT_WIN_DEFAULT
   #xTranslate FExists => File
#ENDIF

STATIC nIn
STATIC nOut

Procedure main( cMemFile )
   local fHandle

   CLS
   set century on
   set epoch to 1950

   if PCount() < 1
      Help()
   else
      if FExists(cMemFile)
         ManipulateMemFile(cMemFile)
      else
         Help()
      endif
   endif
   WAIT
   return

Procedure Help()
   ? 'Usage: MemEdit <memfile>'
   return

Procedure ManipulateMemFile(cMemFile)
   local aVars

   aVars := ReadMemFile(cMemFile)
   if Len(aVars) > 0
      EditVars(aVars)
*      WriteVars(aVars, cMemFile)
   else
   ? "no Vars"
   endif
   return

Function ReadMemFile(cMemFile)
   local aVars := {}
   local cMemRec := Space(SIZEOF_MEM_RECORD)
   local cName
   local cType
   local nLen
   local nDec
   local nSize
   local fHandle

   if (fHandle := FOPEN(cMemFile, FO_READ + FO_DENYWRITE)) > 0

      while FRead(fHandle, @cMemRec, SIZEOF_MEM_RECORD ) == SIZEOF_MEM_RECORD
         cName := Left( cMemRec, At(Chr(0),cMemRec) -1 )
         cType := Chr(Asc(SubStr(cMemrec,12,1))-128)
         nLen  := Asc(SubStr(cMemRec,17,1))
         nDec  := Asc(SubStr(cMemRec,18,1))

         Aadd( aVars, Cast2Var(fHandle,cName,cType,nLen,nDec) )
      enddo
      FClose(fHandle)
   endif
   return aVars

Function WriteVars(aVars, cMemFile)
   local i
   local cVar
   local cBuff := ''
   local cType
   local x
   local nH
   local lOk := FALSE

   if (nH := FCreate(cMemFile)) > 0
      for i := 1 to Len(aVars)
         cVar := Replicate(Chr(0),SIZEOF_MEM_RECORD)

         cVar := Stuff( cVar, 1, Len(aVars[i][VAR_NAME]), upper(aVars[i][VAR_NAME]) )

         cType := aVars[i][VAR_TYPE]

         cVar[12] := Chr(Asc(aVars[i][VAR_TYPE])+128)
         cVar[17] := Chr(aVars[i][VAR_LEN])
         cVar[18] := Chr(aVars[i][VAR_DEC])

         do case
            case cType == 'C'
               cVar[17] := Chr(aVars[i][VAR_LEN]%256)
               cVar[18] := Chr(Int(aVars[i][VAR_DEC]/256))
               cVar += aVars[i][VAR_VALUE]+Chr(0)

            case cType == 'D'

               //x := ctod('01/01/0100')//-1757585
               x := aVars[i][VAR_VALUE]
               x := Val(DtoS(x))-17587860

               nOut := F2Bin( x )
               x := F2Bin( x )
               cVar += x

            case cType == 'N'
               cVar += F2Bin(aVars[i][VAR_VALUE])

            case cType == 'L'
               cVar += Chr(iif(aVars[i][VAR_VALUE],1,0))

         endcase
         FWrite(nH,cVar)
      next
      FWrite(nH,Chr(0x1a))
      FClose(nH)
      lOk := (FError() == 0)
   endif
   return lOk

Function Cast2Var(fHandle,cName,cType,nLen,nDec)
   local aRet := Array(VAR_SIZE)
   local nSize
   local cStr

   aRet[VAR_NAME ] := cName
   aRet[VAR_TYPE ] := cType
   aRet[VAR_LEN  ] := nLen
   aRet[VAR_DEC  ] := nDec

   do case
      case cType == 'C'
         nSize := nLen + nDec * 256
         cStr := SPACE(nSize)
         FREAD(fHandle, @cStr, nSize)
         cStr := SUBSTR(cStr, 1, LEN(cStr)-1)
         aRet[VAR_VALUE] := cStr

      case cType == 'L'
         cStr := SPACE(1)
         FREAD(fHandle, @cStr, 1)
         aRet[VAR_VALUE] := IF(ASC(cStr) == 0, .F., .T.)

      case cType == 'N'
         cStr := Space(8)
         FRead(fHandle,@cStr,8)
         aRet[VAR_VALUE] := Bin2F(cStr)

      case cType == 'D'
         cStr := SPACE(8)
         FREAD(fHandle, @cStr, 8)
         aRet[VAR_VALUE] := CTOD(DTOC(CTOD('01/01/0100') +        ;
            Bin2F(cStr) - 1757585))
         nIn := Bin2F(cStr)

   endcase
   return aRet

Procedure EditVars(aVars)
   local i, x

   FOR i := 1 TO LEN(aVars)
       ? aVars[i]
   NEXT

/***************************************************************
   // do some editing here

   // add a couple of new records if these variabes are missing
   if (i := AScan( aVars, {|e| e[VAR_NAME] == "DVAR2" } )) == 0
      aadd( aVars, {"dVar2","D",8,0,Date()+2} )
      aadd( aVars, {"nVar2","N",8,0,Val(Dtos(Date()))} )
   endif

   // demonstrate changing a variable
   if (i := AScan( aVars, {|e| e[VAR_NAME] == "LVAR" } )) > 0
      aVars[i][VAR_VALUE] := !aVars[i][VAR_VALUE]
   endif
***************************************************************/


return

#IFDEF AAAA

#pragma BEGINDUMP

#include "hbapi.h"
#include "hbapiitm.h"

HB_FUNC( F2BIN )
{
   char buf[ sizeof( double ) ];
   double d = hb_parnd( 1 );

   HB_PUT_LE_DOUBLE( buf, d );
   hb_retclen( buf, sizeof( buf ) );
}

HB_FUNC( BIN2F )
{
   if( hb_parclen( 1 ) >= sizeof( double ) )
   {
      const char * buf = hb_parc( 1 );

      hb_retnd( HB_GET_LE_DOUBLE( buf ) );
   }
   else
      hb_retnd( 0.0 );
}

#pragma ENDDUMP

#ENDIF
greeting,
Jimmy
User avatar
Jimmy
 
Posts: 1585
Joined: Thu Sep 05, 2019 5:32 am
Location: Hamburg, Germany

Re: Mem Files

Postby Jimmy » Sat Oct 09, 2021 9:17 am

hi,

got it working :)

Result is Array but harbour can´t "?" it

after
Code: Select all  Expand view
? hb_valToExp( aVars[i] )
it work under harbour
greeting,
Jimmy
User avatar
Jimmy
 
Posts: 1585
Joined: Thu Sep 05, 2019 5:32 am
Location: Hamburg, Germany

Re: Mem Files

Postby Silvio.Falconi » Sat Oct 09, 2021 9:45 am

I correct and Add some source

You must Compile with hbxpp.lib
F2Bin,bin2f are of xpp

Open the vars into a Xbrowse

the Editvars function not run and risk to erase file mem

Code: Select all  Expand view


#include "fivewin.ch"
#include "common.ch"
#include "fileio.ch"

#define CRLF Chr(13)+Chr(10)
#define SIZEOF_MEM_RECORD       32

#define VAR_NAME  1
#define VAR_TYPE  2
#define VAR_LEN   3
#define VAR_DEC   4
#define VAR_VALUE 5

#define VAR_SIZE 5


Function Main()
local mm_fcnt := ADIR("*.mem") && Count mem files.
local  fil_name[mm_fcnt+1]
local  fil_size[mm_fcnt+1]
local aFiles := ADIR("*.mem",fil_name,fil_size) && Get mem files.
local  mm_flen

       /*
 FOR mm_i = 1 TO mm_fcnt
         mm_flen = LEN(TRIM(fil_name[mm_i]))
         fil_name[mm_i] = fil_name[mm_i] + SPACE(15-mm_flen) + ;
                           str(fil_size[mm_i])
      NEXT

      ASORT(fil_name)
      */








 mm_choice :=  MsgList(fil_name, "Memory Files")


 OpenFileMem(fil_name[mm_choice])

   return nil


//------------------------------------------------------//
Procedure OpenFileMem(cMemFile)
   local fHandle

   set century on
   set epoch to 1950
   set date ansi


*   if PCount() < 1
*      Help()
*   else

      if FILE(cMemFile)
         ManipulateMemFile(cMemFile)
      else
         Help()
      endif

      *  endif
   return
//---------------------------------------------------------------//
Procedure Help()
   ? 'Usage: MemEdit <memfile>'
   return
//---------------------------------------------------------------//
Procedure ManipulateMemFile(cMemFile)
   local aVars

   aVars := ReadMemFile(cMemFile)

   xbrowser aVars


 if Len(aVars) > 0
   //   EditVars_(aVars)
 //     WriteVars(aVars, cMemFile)  // not run ok erase  file mem
   endif

   return

//---------------------------------------------------------------//
Function ReadMemFile(cMemFile)
   local aVars := {}
   local cMemRec := Space(SIZEOF_MEM_RECORD)
   local cName
   local cType
   local nLen
   local nDec
   local nSize
   local fHandle

   if (fHandle := FOPEN(cMemFile, FO_READ + FO_DENYWRITE)) > 0

      while FRead(fHandle, @cMemRec, SIZEOF_MEM_RECORD ) == SIZEOF_MEM_RECORD
         cName := Left( cMemRec, At(Chr(0),cMemRec) -1 )
         cType := Chr(Asc(SubStr(cMemrec,12,1))-128)
         nLen  := Asc(SubStr(cMemRec,17,1))
         nDec  := Asc(SubStr(cMemRec,18,1))

         Aadd( aVars, Cast2Var(fHandle,cName,cType,nLen,nDec) )
      enddo
      FClose(fHandle)
   endif
   return aVars

Function WriteVars(aVars, cMemFile)
   local i
   local cVar
   local cBuff := ''
   local cType
   local x
   local nH
   local lOk := FALSE

   if (nH := FCreate(cMemFile)) > 0
      for i := 1 to Len(aVars)
         cVar := Replicate(Chr(0),SIZEOF_MEM_RECORD)

         cVar := Stuff( cVar, 1, Len(aVars[i][VAR_NAME]), upper(aVars[i][VAR_NAME]) )

         cType := aVars[i][VAR_TYPE]

         cVar[12] := Chr(Asc(aVars[i][VAR_TYPE])+128)
         cVar[17] := Chr(aVars[i][VAR_LEN])
         cVar[18] := Chr(aVars[i][VAR_DEC])

         do case
            case cType == 'C'
               cVar[17] := Chr(aVars[i][VAR_LEN]%256)
               cVar[18] := Chr(Int(aVars[i][VAR_DEC]/256))
               cVar += aVars[i][VAR_VALUE]+Chr(0)

            case cType == 'D'
               aVars[i][VAR_VALUE] += 1757585
               x := aVars[i][VAR_VALUE] - stod('01000101')
               cVar += f2bin(x)


            case cType == 'N'
               cVar += F2Bin(aVars[i][VAR_VALUE])

            case cType == 'L'
               cVar += Chr(iif(aVars[i][VAR_VALUE],1,0))

         endcase
         FWrite(nH,cVar)
      next
      FWrite(nH,Chr(0x1a))
      FClose(nH)
      lOk := (FError() == 0)
   endif
   return lOk

Function Cast2Var(fHandle,cName,cType,nLen,nDec)
   local aRet := Array(VAR_SIZE)
   local nSize
   local cStr

   aRet[VAR_NAME ] := cName
   aRet[VAR_TYPE ] := cType
   aRet[VAR_LEN  ] := nLen
   aRet[VAR_DEC  ] := nDec

   do case
      case cType == 'C'
         nSize := nLen + nDec * 256
         cStr := SPACE(nSize)
         FREAD(fHandle, @cStr, nSize)
         cStr := SUBSTR(cStr, 1, LEN(cStr)-1)
         aRet[VAR_VALUE] := cStr

      case cType == 'L'
         cStr := SPACE(1)
         FREAD(fHandle, @cStr, 1)
         aRet[VAR_VALUE] := IF(ASC(cStr) == 0, .F., .T.)

      case cType == 'N'
         cStr := Space(8)
         FRead(fHandle,@cStr,8)
         aRet[VAR_VALUE] := Bin2F(cStr)

      case cType == 'D'
         cStr := SPACE(8)
         FREAD(fHandle, @cStr, 8)
        aRet[VAR_VALUE] := CTOD(DTOC(CTOD('0100.01.01')+bin2f(cStr) - 1757585))

   endcase
   return aRet
//------------------------------------------------------------------//

  Function EditVars_(aVars)
   local i

   // do some editing here





   // add a couple of new records if these variables are missing
   if (i := AScan( aVars, {|e| e[VAR_NAME] == "DVAR2" } )) == 0
      aadd( aVars, {"dVar2","D",8,0,Date()+2} )
      aadd( aVars, {"nVar2","N",8,0,Val(Dtos(Date()))} )
   endif
   if (i := AScan( aVars, {|e| e[VAR_NAME] == "DVAR3" } )) == 0
      aadd( aVars, {"dVar3","D",8,0,stod('20040131')} )
   endif

   // demonstrate changing a variable
   if (i := AScan( aVars, {|e| e[VAR_NAME] == "LVAR" } )) > 0
      aVars[i][VAR_VALUE] := !aVars[i][VAR_VALUE]
   endif

   // display all available vars
   for i := 1 to Len(aVars)
      ? Padr(aVars[i][VAR_NAME],10)+':', aVars[i][VAR_VALUE]
   next

   return
//------------------------------------------------------------------//


 
Since from 1991/1992 ( fw for clipper Rel. 14.4 - Momos)
I use : FiveWin for Harbour November 2023 - January 2024 - Harbour 3.2.0dev (harbour_bcc770_32_20240309) - Bcc7.70 - xMate ver. 1.15.3 - PellesC - mail: silvio[dot]falconi[at]gmail[dot]com
User avatar
Silvio.Falconi
 
Posts: 6768
Joined: Thu Oct 18, 2012 7:17 pm

Re: Mem Files

Postby Silvio.Falconi » Sat Oct 09, 2021 11:52 am

This is a small conversion of MemFedit.prg of Clipper Summer87

Original

Code: Select all  Expand view
* Program: Memfedit.prg
* Author: Glenn Toney
* Version: Clipper Summer '87
* Note(s): This program creates a text file from a Clipper .mem
* file. You can edit the text file using MEMOEDIT()
* and then write the text file back to a .mem file.
*
CLEAR
SET SCOREBOARD OFF
mm_fcnt = ADIR("*.mem") && Count mem files.
DECLARE fil_name[mm_fcnt+1],fil_size[mm_fcnt+1]
ADIR("*.mem",fil_name,fil_size) && Get mem files.

* This is used to sort the name with the file size
FOR mm_i = 1 TO mm_fcnt
mm_flen = LEN(TRIM(fil_name[mm_i]))
fil_name[mm_i] = fil_name[mm_i] + SPACE(15-mm_flen) + ;
str(fil_size[mm_i])
NEXT
ASORT(fil_name)
fil_name[mm_fcnt+1] = "new file" && Add a new file to the array.
fil_size[mm_fcnt+1] = 0
mm_newmem = .F.

* Separate the size from the file name.
FOR mm_i = 1 TO mm_fcnt
fil_size[mm_i] = val(STUFF(fil_name[mm_i],1,15,""))
fil_name[mm_i] = STUFF(fil_name[mm_i],16,10,"")
NEXT

* Select the memory file.
@ 2,33 TO 21,46 DOUBLE
@ 4,34 TO 4,45 DOUBLE
@ 3,34 SAY "Memory Files"
mm_choice = ACHOICE(5,34,20,45,fil_name)
IF mm_choice = 0
CLEAR
RETURN
ENDIF
CLEAR
@ 10,23 SAY "CREATING TEXT FILE, PLEASE WAIT ..."
mm_memfile = fil_name[mm_choice]
IF mm_choice < mm_fcnt + 1 && If mm_choice = mm_fcnt you
mm_fsize = fil_size[mm_choice] && have a new file.
mm_handle = FOPEN(mm_memfile) && Low-level file handling.
mm_block = mm_fsize && I set up a buffer for the
mm_buffer = SPACE(mm_block) && size of the file.

* This reads the memory file into the buffer by using Clippers
* low-level file handling feature.
FREAD(mm_handle,@mm_buffer, mm_block)

* This restores the memory file to get the values of the numeric
* variables and the Date variables.
RESTORE FROM &mm_memfile. ADDITIVE
mm_offset = 0 && Offset of each new variable in the memory file.
mm_varno = 1 && Variable counter.

mm_maxvar = int(mm_fsize/32)+1 && Maximum variable in file.
DECLARE mm_mvar[mm_maxvar],mm_mtyp[mm_maxvar],mm_mval[mm_maxvar]

* Initialize arrays.
AFILL(mm_mtyp,"")
AFILL(mm_mvar,"")
AFILL(mm_mval,"")
mm_endvar = .N.

* This loop is used to increment the position in the buffer.
FOR mm_i = 1 TO mm_block

* The ASCII value is obtained from the byte being scanned.
mm_asc = VAL(TRANSFORM(ASC(SUBSTR(mm_buffer,mm_i,1)),"999"))
IF mm_offset < 11 && Variable Names are Bytes 0-10.
IF mm_asc <> 0 .AND. .NOT. mm_endvar
mm_mvar[mm_varno] = mm_mvar[mm_varno] + CHR(mm_asc)
ELSE
mm_endvar = .Y. && Variable Name is found.
ENDIF
ENDIF
IF mm_offset = 11 && Byte 11 is the varible type.
IF mm_asc = 195 && Variable is a character.
mm_mtyp[mm_varno] = '
C'
ENDIF
IF mm_asc = 206 && Variable is a numeric.
mm_mtyp[mm_varno] = '
N'
ENDIF
IF mm_asc = 204 && Variable is a logical.
mm_mtyp[mm_varno] = '
L'
ENDIF
IF mm_asc = 196 && Variable is a date.
mm_mtyp[mm_varno] = '
D'
ENDIF
ENDIF
IF mm_offset > 31 && Byte 32 is first byte of
IF mm_mtyp[mm_varno] = '
C' && the value.
IF mm_asc <> 0 .AND. mm_asc <> 13 .AND. mm_asc <> 26
mm_mval[mm_varno] = mm_mval[mm_varno] + CHR(mm_asc)
ELSE

* Begin a new variable.
mm_varno = mm_varno + 1
mm_offset = -1
mm_endvar = .N.
ENDIF
ENDIF
IF mm_mtyp[mm_varno] = '
N' .OR. mm_mtyp[mm_varno] = 'D'
IF (mm_asc <> 0 .AND. mm_asc <> 13 .AND. mm_asc <> 26 ;
.AND. mm_offset < 40)
mm_mval[mm_varno] = mm_mval[mm_varno] + CHR(mm_asc)
ELSE

* If the offset is greater than 39 and the current
* variable is type '
N' or 'D', move to the next
* variable to obtain the variable name.
IF mm_offset > 39
mm_varno = mm_varno + 1
IF mm_asc <> 0 .AND. mm_asc <> 13 .AND. ;
mm_asc <> 26
mm_mvar[mm_varno] = mm_mvar[mm_varno] + ;
CHR(mm_asc)
ENDIF
mm_offset = 0
mm_endvar = .N.
ENDIF
ENDIF
ENDIF
IF mm_mtyp[mm_varno] = "L" .AND. mm_offset = 32
IF mm_asc <> 0 .AND. mm_asc <> 13
mm_mval[mm_varno] = ".T."
ELSE
mm_mval[mm_varno] = ".F."
ENDIF

* Begin a new variable.
mm_varno = mm_varno + 1
mm_offset = -1
mm_endvar = .N.
ENDIF
ENDIF
mm_offset = mm_offset + 1
NEXT
FCLOSE(mm_handle)
CLEAR
mm_pos = AT(".MEM",mm_memfile)

mm_txtfile = STUFF(mm_memfile,mm_pos,4,".TXT")
SET DEVICE TO PRINT
SET PRINT TO &mm_txtfile.

* Output variables and their values to an ASCII text file.
FOR mm_i = 1 TO mm_varno - 1
IF mm_mtyp[mm_i] = '
C'
mm_mvar[mm_i] = mm_mvar[mm_i]+'
= '+'"'+mm_mval[mm_i]+'"'
@ mm_i-1,0 SAY mm_mvar[mm_i]
ENDIF
IF mm_mtyp[mm_i] = '
N'

* Instead of converting bytes to a numeric value, just
* restore the memory file and set the variable equal to
* its value.
mm_value = mm_mvar[mm_i]
mm_mval[mm_i] = &mm_value. && Macro used to get value.
mm_mvar[mm_i] = mm_mvar[mm_i]+'
= '+ ;
LTRIM(str(mm_mval[mm_i]))
@ mm_i-1,0 SAY mm_mvar[mm_i]
ENDIF
IF mm_mtyp[mm_i] = '
L'
mm_mvar[mm_i] = mm_mvar[mm_i]+'
= '+ mm_mval[mm_i]
@ mm_i-1,0 SAY mm_mvar[mm_i]
ENDIF
IF mm_mtyp[mm_i] = '
D'

* Instead of converting bytes to a Clipper date, just
* restore the memory file and set the variable equal to
* its value.
mm_value = mm_mvar[mm_i]
mm_mval[mm_i] = &mm_value. && Macro used to get value.
mm_mvar[mm_i] = ;
mm_mvar[mm_i]+'
= CTOD("'+ DTOC(mm_mval[mm_i])+'")'
@ mm_i-1,0 SAY mm_mvar[mm_i]
ENDIF
NEXT
SET DEVICE TO SCREEN
SET PRINTER TO
RELEASE ALL EXCEPT mm_*
ELSE && Get new file name.
mm_memfile = SPACE(8)
@ 22,10 SAY "New File Name:"
@ 22,25 GET mm_memfile PICTURE '
!!!!!!!!' VALID ;
Validf(mm_memfile)
@ 22,33 SAY ".MEM"
read
mm_memfile = TRIM(mm_memfile) + ".MEM"
IF mm_memfile = ".MEM"
CLEAR
RETURN
ENDIF
mm_pos = AT(".MEM",mm_memfile)
mm_txtfile = STUFF(mm_memfile,mm_pos,4,".TXT")
mm_fsize = 0
mm_newmem = .T.
ENDIF

* INITIAL VALUES FOR MEMOEDIT
mm_txtfile = TRIM(mm_txtfile)
mm_return = 0 && Return value for user function.
mm_altered = .F. && Flag to check for file being altered.
mm_top = 0 && Top Row.
mm_lft = 0 && Left Margin.
mm_bot = 23 && Bottom Row.
mm_rgt = 79 && Right Margin.
mm_upd = .T.
mm_browse = .T.
mm_linelen = 100
mm_ins_on = .F.
mm_msglen = 45
mm_tab = 4
IF FILE(mm_txtfile) && If text file size too large, you can not
IF mm_fsize > 22000 && use this editor. This value may vary.
mm_kyp = '
'
@ mm_bot + 1, mm_lft SAY ;
"File Too Large, Press any key TO exit" GET mm_kyp
READ
RETURN
ENDIF
ENDIF
IF FILE(mm_txtfile)
mm_memo = MEMOREAD(mm_txtfile)
mm_newtxt = .N.
ELSE
mm_memo = SPACE(100)
mm_newtxt = .Y.
ENDIF
mm_lineno = 1
mm_colno = 0
mm_altered = .F.
CLEAR
@ mm_top, mm_lft, mm_bot, mm_rgt BOX CHR(213)+CHR(205)+CHR(184)+;
CHR(179)+CHR(190)+CHR(205)+CHR(212)+CHR(179)
@ mm_bot + 1, mm_lft SAY LOWER(mm_txtfile)
@ mm_bot + 1, mm_lft+14 say " Save & Exit Exit"

* This is a clipper text file editer with a user-defined function,
* you may use any text editor.
mm_memo = MEMOEDIT(mm_memo, mm_top + 1, mm_lft + 1, mm_bot - 1, ;
mm_rgt - 1, mm_upd, "Mfunc",mm_linelen, mm_tab,mm_lineno, ;
mm_colno)
IF .NOT. EMPTY(mm_memo) .AND. mm_return = 23
IF .NOT. MEMOWRIT(mm_txtfile, mm_memo)
@ mm_bot + 1, mm_lft SAY Pad("Disk Write Error.", mm_msglen)
mm_i = INKEY(2)
RETURN
ENDIF
@ mm_bot + 1, mm_lft SAY Pad("Write successful.", mm_msglen)
mm_i = INKEY(2)
ENDIF
mm_endline = mlcount(mm_memo, 100)
DECLARE mm_newvar[mm_endline] && This array holds the variables
CLEAR && and their values.
FOR mm_line = 1 TO mm_endline
mm_newvar[mm_line] = MEMOLINE(mm_memo, 100, mm_line)
NEXT

* This loop will store the values to their respective variables.
FOR mm_line = 1 TO mm_endline
mm_exp = mm_newvar[mm_line]
mm_pos = AT("=",mm_exp) && Check for an equal sign.
IF mm_pos > 0
mm_left_arg = SUBSTR(mm_exp,1,mm_pos-1) && Variable.
mm_right_arg = ;
SUBSTR(mm_exp,mm_pos+1,LEN(mm_exp)-mm_pos) && Value.
STORE &mm_right_arg. TO &mm_left_arg.
ENDIF
NEXT
CLEAR
DECLARE mchoice[4]
mchoice[1] = "1. Create "+upper(TRIM(mm_memfile))+" From "+;
upper(TRIM(mm_txtfile))+" & SAVE "+ upper(TRIM(mm_txtfile)) + ;
SPACE(55)
mchoice[2] = "2. Create "+upper(TRIM(mm_memfile))+" From "+;
upper(TRIM(mm_txtfile))+" & DELETE "+ upper(TRIM(mm_txtfile)) + ;
SPACE(55)
mchoice[3] = "3. DELETE "+upper(TRIM(mm_txtfile))+" & Exit " + ;
SPACE(55)
mchoice[4] = "4. Exit " + SPACE(55)
@ 2,9 TO 9,71 DOUBLE
@ 4,10 TO 4,70 DOUBLE
@ 3,10 SAY SPACE(20)+"Selection Menu"+SPACE(21)
mm_choice = ACHOICE(5,10,8,70,mchoice)
DO CASE
CASE mm_choice = 1 .OR. mm_choice = 2
IF mm_choice = 2
DELETE FILE &mm_txtfile.
ENDIF
savefile = mm_memfile
* Release all the variables used in this program and save
* the variables that were assigned value in the editor.
RELEASE ALL LIKE mm_*
SAVE TO &savefile. ALL EXCEPT savefile
CASE mm_choice = 3
DELETE FILE &mm_txtfile.
ENDCASE
CLEAR

FUNCTION Mfunc && MEMOEDIT() user function
PARAMETERS mode, line, col
PRIVATE kp,yesno
mm_return = 0
DO CASE
CASE mode = 0 && Idle.
@ mm_bot + 1, mm_rgt - 20 SAY "Line: " + ;
Pad(LTRIM(STR(line)), 4)
@ mm_bot + 1, mm_rgt - 8 SAY "Col: " + ;
Pad(LTRIM(STR(col)), 3)
OTHERWISE
kp = LASTKEY() && Keystroke exception.

* Save values to possibly resume edit
IF mode = 2
mm_altered = .T.
ENDIF
DO CASE
CASE kp = 23 .OR. kp = -1

* ^W or F2 to save file.
@ mm_bot + 1, mm_lft SAY SPACE(mm_msglen)
IF .NOT. FILE(mm_txtfile)
@ mm_bot + 1, mm_lft SAY "Writing " + ;
LOWER(mm_txtfile) + "..."
mm_return = 23
ELSE
@ mm_bot + 1, mm_lft SAY "Exist...Replace (Y/N)? "
yesno = " "
DO WHILE .NOT. yesno $ "YN"
yesno = UPPER(CHR(INKEY(0)))
ENDDO
@ mm_bot + 1, mm_lft SAY SPACE(mm_msglen)
IF yesno = "Y"
mm_return = 23
ELSE
mm_return = 27
ENDIF
ENDIF
CASE kp = 301 .OR. kp = 27

* Esc or Alt-X to exit.
IF .NOT. mm_altered
mm_return = 27 && No change.
ELSE

* Changes have been made to memo.
@ mm_bot + 1, mm_lft SAY SPACE(mm_msglen)
@ mm_bot + 1, mm_lft SAY "SAVE [Y/N]? "
yesno = " "
DO WHILE .NOT. yesno $ "YN"
yesno = UPPER(CHR(INKEY(0)))
ENDDO
@ mm_bot + 1, mm_lft SAY SPACE(mm_msglen)
DO CASE
CASE yesno = "N" && Abort.
mm_return = 27
CASE yesno = "Y" && Save and exit.
@ mm_bot + 1, mm_lft SAY SPACE(mm_msglen)
IF .not. FILE(mm_txtfile)
@ mm_bot + 1, mm_lft SAY "Writing " + ;
LOWER(mm_txtfile) + "..."
mm_return = 23
ELSE
@ mm_bot + 1, mm_lft SAY ;
"Exist...Replace (Y/N)? "
yesno = " "
DO WHILE .NOT. yesno $ "YN"
yesno = UPPER(CHR(INKEY(0)))
ENDDO
@ mm_bot + 1, mm_lft SAY SPACE(mm_msglen)
IF yesno = "Y"
mm_return = 23
ELSE
mm_return = 27
ENDIF
ENDIF
ENDCASE
ENDIF
CASE (kp = 279 .OR. kp = 22) .AND. mm_upd

* ^V or Ins or Alt-I toggles insert mode.
mm_ins_on = .NOT. mm_ins_on
@ mm_bot + 1, mm_rgt - 25 SAY IF(mm_ins_on, "I", " ")
mm_return = 22
ENDCASE
ENDCASE
RETURN mm_return

FUNCTION Pad && Pad with spaces.
PARAMETERS string, length
RETURN SUBSTR(string + SPACE(length), 1, length)

FUNCTION Validf && Checks for filename validity.
parameter mfile
mfile = TRIM(mfile)
mlen = LEN(mfile)
mvalid = .Y.
FOR mm_i = 1 TO mlen
mchar = SUBSTR(mfile,mm_i,1)
IF mchar = '
'
mvalid = .N.
ENDIF
IF mchar < '
0' .OR. mchar > '_'
mvalid = .N.
ENDIF
IF mchar > '
9' .AND. mchar < 'A'
mvalid = .N.
ENDIF
* IF mchar > '
Z' .AND. ASC(mchar) < '_'
* mvalid = .N.
* ENDIF
NEXT
RETURN(mvalid)




Modify by me( for fwh )

Code: Select all  Expand view
* Program: Memfedit.prg
* Author: Glenn Toney
* Version: Clipper Summer '87
* Note(s): This program creates a text file from a Clipper .mem
* file. You can edit the text file using MEMOEDIT()
* and then write the text file back to a .mem file.
*

#include "fivewin.ch"

Function Main()
*CLEAR
*SET SCOREBOARD OFF

local mm_fcnt := ADIR("*.mem") && Count mem files.
local  fil_name := array(mm_fcnt+1)
local   fil_size:= array(mm_fcnt+1)

ADIR("*.mem",fil_name,fil_size) && Get mem files.

* This is used to sort the name with the file size
        FOR mm_i = 1 TO mm_fcnt
            mm_flen = LEN(TRIM(fil_name[mm_i]))
            fil_name[mm_i] = fil_name[mm_i] + SPACE(15-mm_flen) + ;
            str(fil_size[mm_i])
         NEXT

         ASORT(fil_name)

fil_name[mm_fcnt+1] = "new file" && Add a new file to the array.
fil_size[mm_fcnt+1] = 0
mm_newmem = .F.

* Separate the size from the file name.
        FOR mm_i = 1 TO mm_fcnt
           fil_size[mm_i] = val(STUFF(fil_name[mm_i],1,15,""))
           fil_name[mm_i] = STUFF(fil_name[mm_i],16,10,"")
        NEXT

* Select the memory file.
*@ 2,33 TO 21,46 DOUBLE
*@ 4,34 TO 4,45 DOUBLE
*@ 3,34 SAY "Memory Files"
//mm_choice = ACHOICE(5,34,20,45,fil_name)

mm_choice = MsgList(fil_name,"Memory Files")
IF mm_choice = 0
      CLEAR
    RETURN
 ENDIF


 OpenMemFile(mm_choice,fil_name,mm_fcnt,fil_size)

*CLEAR
Return nil
//----------------------------------------------------------//


Function OpenMemFile(mm_choice,fil_name,mm_fcnt,fil_size)

*@ 10,23 SAY "CREATING TEXT FILE, PLEASE WAIT ..."
local mm_memfile := fil_name[mm_choice]
local mm_fsize,mm_handle,mm_block,mm_buffer
local mm_maxvar,mm_mvar,mm_mtyp,mm_mval
local mm_offset,mm_varno,mm_endvar
local mm_i
local mm_asc

local mm_pos,mm_txtfile
local aVars := {}
local oText


IF mm_choice < mm_fcnt + 1 && If mm_choice = mm_fcnt you
     mm_fsize := fil_size[mm_choice] && have a new file.
     mm_handle := FOPEN(mm_memfile) && Low-level file handling.
     mm_block := mm_fsize && I set up a buffer for the
     mm_buffer := SPACE(mm_block) && size of the file.



* This reads the memory file into the buffer by using Clippers
* low-level file handling feature.
    FREAD(mm_handle,@mm_buffer, mm_block)


* This restores the memory file to get the values of the numeric
* variables and the Date variables.

RESTORE FROM &mm_memfile. ADDITIVE


mm_offset := 0 && Offset of each new variable in the memory file.
mm_varno := 1 && Variable counter.

mm_maxvar := int(mm_fsize/32)+1 && Maximum variable in file.

mm_mvar:=array(mm_maxvar)
mm_mtyp:=array(mm_maxvar)
mm_mval:=array(mm_maxvar)



* Initialize arrays.
AFILL(mm_mtyp,"")
AFILL(mm_mvar,"")
AFILL(mm_mval,"")

mm_endvar := .N.

* This loop is used to increment the position in the buffer.
FOR mm_i = 1 TO mm_block

* The ASCII value is obtained from the byte being scanned.
mm_asc := VAL(TRANSFORM(ASC(SUBSTR(mm_buffer,mm_i,1)),"999"))

   IF mm_offset < 11 && Variable Names are Bytes 0-10.
         IF mm_asc <> 0 .AND. .NOT. mm_endvar
            mm_mvar[mm_varno] = mm_mvar[mm_varno] + CHR(mm_asc)
          ELSE
            mm_endvar = .Y. && Variable Name is found.
         ENDIF
      ENDIF



     IF mm_offset = 11 && Byte 11 is the varible type.
        IF mm_asc = 195 && Variable is a character.
              mm_mtyp[mm_varno] = '
C'
        ENDIF
        IF mm_asc = 206 && Variable is a numeric.
             mm_mtyp[mm_varno] = '
N'
        ENDIF
        IF mm_asc = 204 && Variable is a logical.
            mm_mtyp[mm_varno] = '
L'
        ENDIF
        IF mm_asc = 196 && Variable is a date.
           mm_mtyp[mm_varno] = '
D'
        ENDIF
     ENDIF




           IF mm_offset > 31 && Byte 32 is first byte of
              IF mm_mtyp[mm_varno] = '
C' && the value.
                 IF mm_asc <> 0 .AND. mm_asc <> 13 .AND. mm_asc <> 26
                    mm_mval[mm_varno] = mm_mval[mm_varno] + CHR(mm_asc)
                  ELSE

                    * Begin a new variable.
                     mm_varno = mm_varno + 1
                     mm_offset = -1
                     mm_endvar = .N.
                   ENDIF
              ENDIF
              IF mm_mtyp[mm_varno] = '
N' .OR. mm_mtyp[mm_varno] = 'D'
                 IF (mm_asc <> 0 .AND. mm_asc <> 13 .AND. mm_asc <> 26 ;
                     .AND. mm_offset < 40)
                     mm_mval[mm_varno] = mm_mval[mm_varno] + CHR(mm_asc)
                  ELSE

                  * If the offset is greater than 39 and the current
                  * variable is type '
N' or 'D', move to the next
                  * variable to obtain the variable name.
                    IF mm_offset > 39
                        mm_varno = mm_varno + 1
                         IF mm_asc <> 0 .AND. mm_asc <> 13 .AND. ;
                           mm_asc <> 26
                           mm_mvar[mm_varno] = mm_mvar[mm_varno] + ;
                            CHR(mm_asc)
                         ENDIF
                        mm_offset = 0
                        mm_endvar = .N.
                    ENDIF
                ENDIF
             ENDIF





            IF mm_mtyp[mm_varno] = "L" .AND. mm_offset = 32
                IF mm_asc <> 0 .AND. mm_asc <> 13
                   mm_mval[mm_varno] = ".T."
                   ELSE
                     mm_mval[mm_varno] = ".F."
                 ENDIF

                   * Begin a new variable.
                      mm_varno = mm_varno + 1
                      mm_offset = -1
                      mm_endvar = .N.
                 ENDIF
              ENDIF


         mm_offset = mm_offset + 1
      NEXT

FCLOSE(mm_handle)
*CLEAR


mm_pos := AT(".MEM",mm_memfile)
mm_txtfile := STUFF(mm_memfile,mm_pos,4,".TXT")

//SET DEVICE TO PRINT
//SET PRINT TO &mm_txtfile.

oText:=TTxtFile():New( mm_txtfile )
if oText:Open()


* Output variables and their values to an ASCII text file.
          FOR mm_i = 1 TO mm_varno - 1
                IF mm_mtyp[mm_i] = '
C'
                 mm_mvar[mm_i] = mm_mvar[mm_i]+'
= '+'"'+mm_mval[mm_i]+'"'
                *@ mm_i-1,0 SAY mm_mvar[mm_i]
             ENDIF

IF mm_mtyp[mm_i] = '
N'

* Instead of converting bytes to a numeric value, just
* restore the memory file and set the variable equal to
* its value.
mm_value = mm_mvar[mm_i]
mm_mval[mm_i] = &mm_value. && Macro used to get value.
mm_mvar[mm_i] = mm_mvar[mm_i]+'
= '+ ;
LTRIM(str(mm_mval[mm_i]))
*@ mm_i-1,0 SAY mm_mvar[mm_i]
ENDIF

IF mm_mtyp[mm_i] = '
L'
mm_mvar[mm_i] = mm_mvar[mm_i]+'
= '+ mm_mval[mm_i]
*@ mm_i-1,0 SAY mm_mvar[mm_i]
ENDIF


IF mm_mtyp[mm_i] = '
D'

* Instead of converting bytes to a Clipper date, just
* restore the memory file and set the variable equal to
* its value.
mm_value = mm_mvar[mm_i]
mm_mval[mm_i] = &mm_value. && Macro used to get value.
mm_mvar[mm_i] = ;
mm_mvar[mm_i]+'
= CTOD("'+ DTOC(mm_mval[mm_i])+'")'
*@ mm_i-1,0 SAY mm_mvar[mm_i]
ENDIF
*aadd (avars, {mm_mvar[mm_i]})
     oText:Add( mm_mvar[mm_i] )
  NEXT

 oText:Close()
Endif


/*For n=1 to Len(aVars)
   if oText:Open()
     oText:Add( aVars[n][1] )
     oText:Close()
  endif
Next
  */
MsgInfo( MemoRead( mm_txtfile ) )
*xbrowser avars

//SET DEVICE TO SCREEN
//SET PRINTER TO

RELEASE ALL EXCEPT mm_*

            ELSE && Get new file name.
               mm_memfile = SPACE(8)


               /*
@ 22,10 SAY "New File Name:"
@ 22,25 GET mm_memfile PICTURE '
!!!!!!!!' VALID ;
Validf(mm_memfile)
@ 22,33 SAY ".MEM"
read

IF mm_memfile = ".MEM"
CLEAR
RETURN
ENDIF
*/


mm_memfile := TRIM(mm_memfile) + ".MEM"
mm_pos := AT(".MEM",mm_memfile)
mm_txtfile := STUFF(mm_memfile,mm_pos,4,".TXT")
mm_fsize := 0
mm_newmem = .T.

ENDIF




* INITIAL VALUES FOR MEMOEDIT
mm_txtfile := TRIM(mm_txtfile)
mm_return := 0 && Return value for user function.
mm_altered := .F. && Flag to check for file being altered.
mm_top := 0 && Top Row.
mm_lft := 0 && Left Margin.
mm_bot := 23 && Bottom Row.
mm_rgt := 79 && Right Margin.
mm_upd := .T.
mm_browse := .T.
mm_linelen := 100
mm_ins_on := .F.
mm_msglen := 45
mm_tab := 4


IF FILE(mm_txtfile) && If text file size too large, you can not
IF mm_fsize > 22000 && use this editor. This value may vary.
mm_kyp := '
'
@ mm_bot + 1, mm_lft SAY ;
"File Too Large, Press any key TO exit" GET mm_kyp
READ
RETURN
ENDIF
ENDIF



IF FILE(mm_txtfile)
mm_memo = MEMOREAD(mm_txtfile)
mm_newtxt = .N.
ELSE
mm_memo = SPACE(100)
mm_newtxt = .Y.
ENDIF



mm_lineno = 1
mm_colno = 0
mm_altered = .F.
CLEAR



@ mm_top, mm_lft, mm_bot, mm_rgt BOX CHR(213)+CHR(205)+CHR(184)+;
CHR(179)+CHR(190)+CHR(205)+CHR(212)+CHR(179)
@ mm_bot + 1, mm_lft SAY LOWER(mm_txtfile)
@ mm_bot + 1, mm_lft+14 say " Save & Exit Exit"





* This is a clipper text file editer with a user-defined function,
* you may use any text editor.
mm_memo = MEMOEDIT(mm_memo, mm_top + 1, mm_lft + 1, mm_bot - 1, ;
mm_rgt - 1, mm_upd, "Mfunc",mm_linelen, mm_tab,mm_lineno, ;
mm_colno)
IF .NOT. EMPTY(mm_memo) .AND. mm_return = 23
IF .NOT. MEMOWRIT(mm_txtfile, mm_memo)
@ mm_bot + 1, mm_lft SAY Pad("Disk Write Error.", mm_msglen)
mm_i = INKEY(2)
RETURN
ENDIF
@ mm_bot + 1, mm_lft SAY Pad("Write successful.", mm_msglen)
mm_i = INKEY(2)
ENDIF
mm_endline = mlcount(mm_memo, 100)
DECLARE mm_newvar[mm_endline] && This array holds the variables
CLEAR && and their values.
FOR mm_line = 1 TO mm_endline
mm_newvar[mm_line] = MEMOLINE(mm_memo, 100, mm_line)
NEXT

* This loop will store the values to their respective variables.
FOR mm_line = 1 TO mm_endline
mm_exp = mm_newvar[mm_line]
mm_pos = AT("=",mm_exp) && Check for an equal sign.
IF mm_pos > 0
mm_left_arg = SUBSTR(mm_exp,1,mm_pos-1) && Variable.
mm_right_arg = ;
SUBSTR(mm_exp,mm_pos+1,LEN(mm_exp)-mm_pos) && Value.
STORE &mm_right_arg. TO &mm_left_arg.
ENDIF
NEXT
CLEAR
DECLARE mchoice[4]
mchoice[1] = "1. Create "+upper(TRIM(mm_memfile))+" From "+;
upper(TRIM(mm_txtfile))+" & SAVE "+ upper(TRIM(mm_txtfile)) + ;
SPACE(55)
mchoice[2] = "2. Create "+upper(TRIM(mm_memfile))+" From "+;
upper(TRIM(mm_txtfile))+" & DELETE "+ upper(TRIM(mm_txtfile)) + ;
SPACE(55)
mchoice[3] = "3. DELETE "+upper(TRIM(mm_txtfile))+" & Exit " + ;
SPACE(55)
mchoice[4] = "4. Exit " + SPACE(55)
@ 2,9 TO 9,71 DOUBLE
@ 4,10 TO 4,70 DOUBLE
@ 3,10 SAY SPACE(20)+"Selection Menu"+SPACE(21)
mm_choice = ACHOICE(5,10,8,70,mchoice)
DO CASE
CASE mm_choice = 1 .OR. mm_choice = 2
IF mm_choice = 2
DELETE FILE &mm_txtfile.
ENDIF
savefile = mm_memfile
* Release all the variables used in this program and save
* the variables that were assigned value in the editor.
RELEASE ALL LIKE mm_*
SAVE TO &savefile. ALL EXCEPT savefile
CASE mm_choice = 3
DELETE FILE &mm_txtfile.
ENDCASE
CLEAR


//--------------------------------------------------------------------------//

FUNCTION Mfunc && MEMOEDIT() user function
PARAMETERS mode, line, col
PRIVATE kp,yesno
mm_return = 0
DO CASE
CASE mode = 0 && Idle.
@ mm_bot + 1, mm_rgt - 20 SAY "Line: " + ;
Pad(LTRIM(STR(line)), 4)
@ mm_bot + 1, mm_rgt - 8 SAY "Col: " + ;
Pad(LTRIM(STR(col)), 3)
OTHERWISE
kp = LASTKEY() && Keystroke exception.

* Save values to possibly resume edit
IF mode = 2
mm_altered = .T.
ENDIF
DO CASE
CASE kp = 23 .OR. kp = -1

* ^W or F2 to save file.
@ mm_bot + 1, mm_lft SAY SPACE(mm_msglen)
IF .NOT. FILE(mm_txtfile)
@ mm_bot + 1, mm_lft SAY "Writing " + ;
LOWER(mm_txtfile) + "..."
mm_return = 23
ELSE
@ mm_bot + 1, mm_lft SAY "Exist...Replace (Y/N)? "
yesno = " "
DO WHILE .NOT. yesno $ "YN"
yesno = UPPER(CHR(INKEY(0)))
ENDDO
@ mm_bot + 1, mm_lft SAY SPACE(mm_msglen)
IF yesno = "Y"
mm_return = 23
ELSE
mm_return = 27
ENDIF
ENDIF
CASE kp = 301 .OR. kp = 27

* Esc or Alt-X to exit.
IF .NOT. mm_altered
mm_return = 27 && No change.
ELSE

* Changes have been made to memo.
@ mm_bot + 1, mm_lft SAY SPACE(mm_msglen)
@ mm_bot + 1, mm_lft SAY "SAVE [Y/N]? "
yesno = " "
DO WHILE .NOT. yesno $ "YN"
yesno = UPPER(CHR(INKEY(0)))
ENDDO
@ mm_bot + 1, mm_lft SAY SPACE(mm_msglen)
DO CASE
CASE yesno = "N" && Abort.
mm_return = 27
CASE yesno = "Y" && Save and exit.
@ mm_bot + 1, mm_lft SAY SPACE(mm_msglen)
IF .not. FILE(mm_txtfile)
@ mm_bot + 1, mm_lft SAY "Writing " + ;
LOWER(mm_txtfile) + "..."
mm_return = 23
ELSE
@ mm_bot + 1, mm_lft SAY ;
"Exist...Replace (Y/N)? "
yesno = " "
DO WHILE .NOT. yesno $ "YN"
yesno = UPPER(CHR(INKEY(0)))
ENDDO
@ mm_bot + 1, mm_lft SAY SPACE(mm_msglen)
IF yesno = "Y"
mm_return = 23
ELSE
mm_return = 27
ENDIF
ENDIF
ENDCASE
ENDIF
CASE (kp = 279 .OR. kp = 22) .AND. mm_upd

* ^V or Ins or Alt-I toggles insert mode.
mm_ins_on = .NOT. mm_ins_on
@ mm_bot + 1, mm_rgt - 25 SAY IF(mm_ins_on, "I", " ")
mm_return = 22
ENDCASE
ENDCASE
RETURN mm_return




//-----------------------------------------------------------------------//
FUNCTION Pad && Pad with spaces.
PARAMETERS string, length
RETURN SUBSTR(string + SPACE(length), 1, length)



//-----------------------------------------------------------------------//
FUNCTION Validf && Checks for filename validity.
parameter mfile
mfile = TRIM(mfile)
mlen = LEN(mfile)
mvalid = .Y.
FOR mm_i = 1 TO mlen
mchar = SUBSTR(mfile,mm_i,1)
IF mchar = '
'
mvalid = .N.
ENDIF
IF mchar < '
0' .OR. mchar > '_'
mvalid = .N.
ENDIF
IF mchar > '
9' .AND. mchar < 'A'
mvalid = .N.
ENDIF
* IF mchar > '
Z' .AND. ASC(mchar) < '_'
* mvalid = .N.
* ENDIF
NEXT
RETURN(mvalid)




To simulate the command SET PRINT TO &mm_txtfile. I used TxtFile class to create a xxxx.Txt from xxxx.mem

then MemFedit use a memoedit to edit this txt but I not understood how converte it
then it save a new file with SAVE TO &savefile. ALL EXCEPT savefile


Perhaps to Edit all variables we can save all variables and values on array and then can use Xbrowse
then wecan save all or converte into inifile
Since from 1991/1992 ( fw for clipper Rel. 14.4 - Momos)
I use : FiveWin for Harbour November 2023 - January 2024 - Harbour 3.2.0dev (harbour_bcc770_32_20240309) - Bcc7.70 - xMate ver. 1.15.3 - PellesC - mail: silvio[dot]falconi[at]gmail[dot]com
User avatar
Silvio.Falconi
 
Posts: 6768
Joined: Thu Oct 18, 2012 7:17 pm

Re: Mem Files

Postby nageswaragunupudi » Sat Oct 16, 2021 8:34 am

Code: Select all  Expand view
function testmemvars()

   local aVars, aVar, aEdit

   // Step 1 : Read vars from "myvars.mem"
   RESTORE FROM myvars

   // Step 2: View vars and values
   XBROWSER ( aVars := __MVSYMBOLINFO() )

   // Step 3: Edit variables
   aEdit := {}
   for each aVar in aVars
      if !( aVar[ 1 ] == "GETLIST" )
         AAdd( aEdit, { aVar[ 1 ], bSETGET( &( aVar[ 1 ] ) ) } )
      endif
   next

   TDataRow():New( aEdit ):Edit()

   // Step 4: View vars and modified values
   XBROWSER ( aVars := __MVSYMBOLINFO() )

   // Step 5: Save changes to "myvars.mem"
   SAVE TO myvars

return nil
 


Image
Regards

G. N. Rao.
Hyderabad, India
User avatar
nageswaragunupudi
 
Posts: 10248
Joined: Sun Nov 19, 2006 5:22 am
Location: India

Re: Mem Files

Postby Silvio.Falconi » Sat Oct 16, 2021 10:48 am

nageswaragunupudi wrote:
Code: Select all  Expand view
function testmemvars()

   local aVars, aVar, aEdit

   // Step 1 : Read vars from "myvars.mem"
   RESTORE FROM myvars

   // Step 2: View vars and values
   XBROWSER ( aVars := __MVSYMBOLINFO() )

   // Step 3: Edit variables
   aEdit := {}
   for each aVar in aVars
      if !( aVar[ 1 ] == "GETLIST" )
         AAdd( aEdit, { aVar[ 1 ], bSETGET( &( aVar[ 1 ] ) ) } )
      endif
   next

   TDataRow():New( aEdit ):Edit()

   // Step 4: View vars and modified values
   XBROWSER ( aVars := __MVSYMBOLINFO() )

   // Step 5: Save changes to "myvars.mem"
   SAVE TO myvars

return nil
 


Image




FANTASTIC ....
THANKS RAO
too wonderful
Since from 1991/1992 ( fw for clipper Rel. 14.4 - Momos)
I use : FiveWin for Harbour November 2023 - January 2024 - Harbour 3.2.0dev (harbour_bcc770_32_20240309) - Bcc7.70 - xMate ver. 1.15.3 - PellesC - mail: silvio[dot]falconi[at]gmail[dot]com
User avatar
Silvio.Falconi
 
Posts: 6768
Joined: Thu Oct 18, 2012 7:17 pm


Return to FiveWin for Harbour/xHarbour

Who is online

Users browsing this forum: No registered users and 95 guests