Jump to content
IGNORED

PL65 Problem - WRTSTR/WRTLN


MrFish

Recommended Posts

I'm doing some coding in PL65 using the 2nd cracked version (where compiling actually produces run-able code). I'm having a problem getting several related library procedures to execute properly when being called from a procedure that has a STRING passed as one of it's parameters.

 

The following code example produces an executable in which the PROC WRTSTR (from 'Terminal.lib') in the PROC PrintText does not print the string A$. At this point during execution the program continuously prints to the screen what looks like the contents of memory.

 

INCLUDE D:Terminal.lib

!--------------------------------------

PROC PrintText (STRING A$[20])

 INT I

BEGIN

 FOR I=1 TO 50000 DO
 NEXT

 WRTSTR (A$)

 REPEAT
 FOREVER

END

!--------------------------------------

MAIN ()

 STRING A$[20]

BEGIN

 A$ = "Main Proc "
 WRTSTR (A$)

 A$ = "PrintText Proc "
 PrintText (A$)

END

 

 

If I code the PROC PrintText without a STRING as a parameter I can then execute a WRTSTR without any problems. This example will work whether I have no parameters or if any parameters that are passed are not STRINGs.

 

 

INCLUDE D:Terminal.lib

!--------------------------------------

PROC PrintText ()

 INT I
 STRING A$[20] DATA "PrintText Proc ";

BEGIN

 FOR I=1 TO 50000 DO
 NEXT

 WRTSTR (A$)

 REPEAT
 FOREVER

END

!--------------------------------------

MAIN ()

 STRING A$[20]

BEGIN

 A$ = "Main Proc "
 WRTSTR (A$)

 PrintText ()

END

 

 

Also, WRTSTR will fail in PROC PrintText if I pass a STRING parameter even if I don't use the passed parameter in the WRTSTR statement. This problem persists with the WRTLN function as well, which is just a variant that sends an EOL at the end of the string being printed to the screen. Using PCHAR (and altering the code accordingly) instead of WRTSTR cures the problem, but I'm still wondering why WRTSTR and WRTLN will not function properly in this particular case?

 

I'm running the compiler off a DOS 2.5 disk rather than the uploaded SpartaDOS disk. I've tried compiling and running it under SpartaDOS X using the original disk and the DOS 2.5 disk as well and it doesn't change the outcome. I've run the executables under emulation and with real hardware and I've compiled it using real hardware. There are no examples of using WRTSTR or WRTLN in the sample game program that Noahsoft included on the PL65 disk. It uses PCHAR for it's title screen.

 

Normally I would post this in the programming forum, but since the cracked disk was posted on the main forum and since this may be a problem with the cracked compiler or an associated library file, I'm posting it here.

 

Here are the files for the above example, including a copy of PL65 on a DOS 2.5 disk:

 

PL65 Example.zip

 

Any help is appreciated.

 

Thanks,

MF

Link to comment
Share on other sites

Interesting. In either case, surely WRTSTR is passed a pointer value. Only difference I can see is in use the parameter stack between the two calls. I've had a play around with it but am not making any progress.

 

It's an interesting language, this. Pascal-like with assembler thrown in. I have to say it's given me an appetite for coding on the A8 again - which I have sorely missed since going cross-development. I wish we had the sources for PL65 since I think the compiler's I/O could probably be speeded up (assuming it uses single byte put / get).

 

Anyway - getting away from the point here. I'll keep playing with this. :)

Link to comment
Share on other sites

  • 2 years later...

Hi Mr Fish,

 

I just stumble over your text now and I don't know if my quote may be usefull for you by now in 2014 ...

 

I see you used the same A$ declaration for your procedure and for global variable.

perhaps if compiler is single pass, reservation for A$ as var either as global and local can make a problem. trying to change to B$ in proc declaration, just to see ?

 

perhaps also map A$ to see how strings are implemented (pascal as PL65 seems to get its inspiration use the first byte of data string to define the lenght of the string (quicker process)

while C (azt) check each char/byte to see if zero (slower). perhaps another method here, I don't know.

 

I stumble on your post because PL65 interest me as he can mix ASM & high level language (as we could do in turbo-pascal at his time) (and it remember me a bit the PLM I used 20 years ago on 8031/ 8051 microcontrollers).

 

best regards

 

Rudy

Edited by DearHorse
Link to comment
Share on other sites

Hello,Friends,

Resently I've tried to write simplest TSR in pl65.

! VBI Procedure for changing colors
! It Stays TSR after loading
BYTE HELPFG=$02DC,COLBAK=$02C8
CONST HELP=$11,BLUE=$80,RED=$32
BYTE OLDHLP
INT DOSINI=$0C,MEMLO=$2E7,FINISH

PROC VBI*()
  CONST SYSVBV=$E45F
BEGIN
    LDA HELPFG
    CMP OLDHLP BEQ Exit
    CMP #HELP BNE Exit
!
    LDA COLBAK
    CMP #RED BNE ToRED
!
    LDA #BLUE STA COLBAK
    GOTO Exit
:ToRED
    LDA #RED STA COLBAK
:Exit
    LDA HELPFG STA OLDHLP
    LDA #$07 STA HELPFG
    JMP SYSVBV
END

PROC SetVBI*()
  CONST SETVBV=$E45C
BEGIN
  STX XSAVE
  LDA #$06
  LDX #VBI/$100
  LDY #VBI AND $FF
  JSR SETVBV
  LDX XSAVE
END

PROC NoRESET*()
BEGIN
  GOTO INIT
! This part is Resident.
:TROJAN
  RTS
:BUMPUP
  LDA #FINISH AND $FF STA MEMLO
  LDA #FINISH/$100    STA MEMLO+1
  RTS
:TSR
  JSR TROJAN
  JSR BUMPUP
  JSR SetVBI
  LDA #BLUE STA COLBAK
  RTS

! This part is executed at power up only.
:INIT
  LDA DOSINI   STA TSR+1
  LDA DOSINI+1 STA TSR+2
!
  LDA #TSR AND $FF STA DOSINI
  LDA #TSR/$100    STA DOSINI+1
!
  JSR BUMPUP
END

CONST LoMem=@

MAIN()
BEGIN
  COLBAK=BLUE
  SetVBI*()
  FINISH=LoMem
  NoRESET*()
END

You can see that it's really assembler, but I know that it can be written in clear PL65, as it's no more then moving data between variables, or filling data with the help of pointers.

 

The only thing I can't solve lays in single-pass nature of pl65 and it's assembler.

All things must be declared before compilation.

 

I can't find a way to properly fill address field of JSR TROJAN statement.

 

I'm not a programmer at all, sorry.

 

Link to comment
Share on other sites

Dear Mr Fish,

 

This is CITE from PL65 manual:

 

Parameter variables are treated within the procedure exactly the same as local variables, ...

 

Thus this strange behavior may be caused by the absense of proper initialisation for

PROC PrintText (STRING A$[20])

 

I mean that as parameter is LOCAL, then A$ in PrintText is different then A$ in MAIN ANYWAY!

 

Parameter declaration in PrintTest only says compiler about the quantity of bytes needed on stack for transmitting to PROC and no more.

 

Really A$ in PrintText never was declared as no address and no length can't be accessed by compiler.

 

This may help IMHO:

INCLUDE TERMINAL.LIB

STRING A$[20] ! Declaration and memory allocation for string
...
PROC PrintText (STRING A$[20]) ! Here compiler knows A$
     INT I
BEGIN
     FOR I=1 TO 50000 DO
     NEXT
     WRTSTR (A$)
     REPEAT
     FOREVER
END
...
MAIN() ! Here compiler knows the same A$ as PrintText thus we can make
       ! proper initialization of string in MAIN()
BEGIN
...
END

In this case A$ is seeing for both PrintText and MAIN.

 

Another way may be using POINTERS to beginning of string.

 

Another note is that real dimension of any string MUST be LEN+4.

2 bytes is string address and two bytes is it's lenght.

 

That's all Folks. ;)

Edited by 130XE
Link to comment
Share on other sites

  • 1 year later...

I recently found that the meaning of real declaration of string in PL65 is like this:

Adr (2 bytes), Len (2 bytes), String (len-1 bytes), EOL(1 byte)

 

PL65 works with ASM values anyway, thus it can't exclude $9B FROM string, because another program may use $9B as terminator.

 

I recently replaced EOL with SPACE. It works!

 

It was NOT string-dedicated function! (It was some kind of byte oriented function.)

 

String-dedicated functions - all pays attention to EOL after string.

Some of them using it but some not.

Link to comment
Share on other sites

  • 7 months later...

Hi there, FRIENDS!

Recently I found very convenient russified font editing program...

It takes all my mind and I decided to write some PL65 code for autorun fontloader for programming in russified BASIC F.E...

The PL65 is really the product of ingenious master who placed all it's ideas in lang and never tried to exhaustively testing it.

The code:

INCLUDE TERMINAL.LIB

MAIN()
  STRING S$[2]
BEGIN
  PUT(0,125)
  WRTLN("ENTER STRING, PLEASE ...")
  S$=INPUT$()
  WRTSTR("LEN OF INPUT$ = ") WRITE(LEN(S$))
END

Being tested and working it gives this picture while entered "Return" only:

Thus you know the beast side of beauty!

This problem may be simply recognized.

Manual says that the string in PL65 is defined as addr/len
(it means that TERMINAL.LIB based on pointers)
but ATARI's SIO is defined in other way: addr/EOL

I mean that PL65 never recognizes EOL, because it's internal control symbol for PL65.

I want to say that when some of our procedures or functiones calls SIO,
SIO evidently returns EOL with it's output!

And PL65 adds 1 to LEN(string$)

post-20208-0-49514300-1481973154_thumb.png

Link to comment
Share on other sites

Here i'll add some workable code:

INCLUDE TERMINAL.LIB

STRING FName$[20]

! Procedures and Functions
!-------------------------
PROC Cls()
BEGIN PUT(0,125) END
!-------------------------
FUNC Prompt$()
  STRING Out$[20]
BEGIN
  Cls()
  WRTLN("INPUT:")
  WRTLN("ENTER FILENAME TO LOAD, PLEASE...")
  Out$=INPUT$()
END Out$
!-------------------------
PROC Adopt()
  STRING D$[20] DATA "D:";
BEGIN
  IF LEN(FName$)=1 THEN ERROR(7) ENDIF

  IF (FName$[1,1]=":" OR FName$[2,2]=":") THEN
! If FName$ contain ':' then we need not concatenation!
    RETURN
  ELSE
! In contrary we need it!
    D$[LEN(D$)]=FName$
    FName$=D$
  ENDIF
END
! Main program
!-------------------------
MAIN()
BEGIN
  TRAP retry
:again
  FName$=Prompt$()
  Adopt()
  WRTLN(FName$)
  GOTO exit
:retry
  TRAP retry
  GOTO again
:exit
END

It's filename normalization.

 

Here I must say that simple code:

(FName$[1]=":" OR FName$[2]=":")

is absolutely NOT Working!!!

Because of PL65 manner of string nature of compared values.

 

As them represents both addresses and lengthes they do NOT compares identical values at all!

Addr or Len will be different anyway!

 

WRTSTR("FILE") will never give us addr/len such as WRTSTR("F")

Link to comment
Share on other sites

I used PL65 almost exclusively for years and never realised there was a problem with WRTSTR. I'm wondering whether or not it's poor documentation that's the problem, although BITD I considered the documentation to be pretty good.

 

However, I suspect that WRTSTR was one function that I didn't use that often. I tended to roll my own code, especially for game and demo projects. However, there is one project that I might still have lying around that may have used extensive use of WRTSTR. But then again IIRC use of the library functions caused a noticeable slowdown in writing text to the screen, so I may even have written my own code for that.

  • Like 1
Link to comment
Share on other sites

Hello Tickled_Pink!

 

I must say that documentation of PL65 is very detailed and explicit.

Particularly it means that to find something we need to read all book. :)

 

My personal problem was that I could not realize for a long time that There Is NOT string PROCs in PL65 but only string FUNCs.

Any PROC works with strings by default.

 

Another thing is that we need not $-sign in FUNCs only in 2 cases - while writing compile-time expression and while using dot operator.

 

For fast screen-out I often used line based output with precalculated array of 24 POINTER addresses of screen lines.

Link to comment
Share on other sites

I was just thinking about it now. Doesn't WRTSTR use the SIO functions in another library file - is it TERMINAL.LIB? That would account for the slowness of the text draw. So thinking about it now I probably did write my own for the project I was working on. I did a writeup on this and a version of the game Loopz that I had been working on for MyAtari magazine years ago. Both being written in PL65.

 

I intend to finish them at some point if I still have the original disks. Life kind of got in the way. Loopz was around 75% complete. The other was a disk cataloguer which had a GUI-like interface insofar as the way that I displayed unavailable menu options greyed out using DLIs.

Link to comment
Share on other sites

  • 4 months later...

I really love PL65. It's the artifact of langs. Only thinking in it's way we can understand how the langs growth.

 

Even ACTION! is premAtive because of lack of typedef syntax in PL65.

 

YES! It's possible to wright something like Dynamic Memory Allocation in PL65 but ...

 

Its POINTERS are too ancient at all!!!

 

Anyway I love your interest in PL65. ;-)

Link to comment
Share on other sites

  • 5 years later...

Hello Friends!

Investigating PL65 I made too many mistakes!!! So sorry!

 

Here some string declarations:

First - Declared and initialized in compile time!

STRING s$[960] DATA "Some String Data";

 

And another:

This MUST be Declared in compile time but can be Initialized in Runtime while running MAIN()

STRING s$[960]

...

MAIN()

BEGIN

    s$="Some String Data"

END

 

The memory structure of PL65 strings is :

DIM,SIZ,STRING

where:

NAME=s$

ADDR of string - can be accessed as .s (without $-sign)

SIZ is Runtime Size (INT value) addressed as .s-2

DIM is Declared (INT value) like [960] can be accessed as .s-4

STRING is "Some String Data" and is equal to count between "..." (here 16)

 

Here is my trying to make TEXT.LIB for PL65 to normally work with strings.

!====================================!
! TEXT.LIB                           !
!     String Functions for PL65      !
!       Programming Language         !
!------------------------------------!
! Evgeny Zolotarev,(aka 576XE), 2022 !
!====================================!

!- Global Strings -------------------!
STRING p$[960],s$[960]

!= String Functions =================!
FUNC Find()
!- Returns COUNTED but INDEXED ------!
  POINTER pP,sP
    BYTE pV BASED pP,sV BASED sP
  BYTE sC,pC,f INT pL,sL,i,j,pos
BEGIN
  pL=LEN(p$) sL=LEN(s$)
  IF pL<=sL THEN
    sL=sL-pL+1
    i=0 j=0
! Repeating along the String
    REPEAT
      f=$FF
! Traversing along the Pattern
      FOR j=0 TO pL-1 DO
        sP=.s+i+j sC=sV
        pP=.p+j   pC=pV
        IF sC<>pC THEN f=0 ENDIF
      NEXT
      i=i+1
    UNTIL (i=sL-1 OR f<>0)
    IF f<>0 THEN pos=i ELSE pos=0 ENDIF
  ELSE pos=0 ENDIF
END pos
!====================================!
ENDFILE

 

And code for testing

!====================================!
! TEXT.PRG                           !
!  Using String Functions for PL65   !
!       Programming Language         !
!------------------------------------!
! Evgeny Zolotarev,(aka 576XE), 2022 !
!====================================!
INCLUDE TERMINAL.LIB
INCLUDE TEXT.LIB
!- Global Data ----------------------!

!====================================!
MAIN()
  INT posn
BEGIN
!- Strings Assignment ---------------!
  p$="Petersburg"
  s$="Moscow Petersburg Evpatoria Feodosia Simeiz Konakovo"
  posn=Find()
  CR() WRITE(posn) CR()
END
!====================================!

 

The purpose of placing STRING p$[960],s$[960] in such a strange place is to make it vizible for Find routine

while Initializing from MAIN() program !!!

I still have some problems with transfering string parameters in PL65, thus use GLOBALS instead.

Best wishes from Moscow!

zen

Edited by 576XE
  • Like 1
Link to comment
Share on other sites

  • 2 weeks later...
! T.PRG
INCLUDE TERMINAL.LIB
  STRING s$[255] ! String Declaration

PROC print(PROC WRTSTR)
BEGIN
  CR()
END

MAIN()
BEGIN
  s$="Moscow" ! String Assignment
  print(s$)
END

This code works. PROC is just indirect parameters passing. Too strange strings behavior. Seems like something crashes the stack.

zen

Link to comment
Share on other sites

image.thumb.jpeg.a82c6737264d12bc1587e6299d74c0a7.jpeg

 

I've recently just really enjoyed programming in this language PL65 - conceptually this is the language for me.  The reason for it, is no line numbers, the algol roots of the language, the fact that I can write in an 80 column editor (or any text editor) and then compile it later....are good.  But what makes it great is most atari tutorials are in assembler and you can mix and match assembly - that's the perfect combo.

 

I'll share the quirks I've noticed in a couple weekends of programming. I've found it is important the exact order of calling graphics and pmgraphics, otherwise pmgraphics memory areas become corrupted.  Further the PEEKPOKE.LIB I don't use at all, because POKE was just being silently ignored, whereas just doing an inline LDA STA and that works.    Also., routines like PCHAR are present in the demo program, but no reference for PCHAR in the manual (at least if I search for PCHAR, not found, but who knows if that is a pdf conversion issue), and if I start at other postiion X=0, PCHAR sometimes leaves a cursor character on the screen for no apparent reason.  It's unknown why I'm passing a 6 as the first parameter, other than I copied it from the demo.

 

With those limitations in mind, I have written portion of the game already (I'm porting 'world's hardest game')...and I see no reason not to finish.... this is a great platform for productivity, if one can avoid the bugs, anyway.

 

anyway, just sharing, not to take over the thread.  I only briefly used WRTLN. 

 

Again, just sharing for those interested in PL65 - I'm not really revealling anything of course.  I've had to get my mindset back into the limitations of 1980's.  One thing that set me back for a few minutes it that   INT A and STRING A$[255] is a violation, considered to be re-use of the same variable....probably made sense in 1980's, but odd to me now.

 

 

 

  • Like 2
Link to comment
Share on other sites

  • 2 weeks later...

Hello Friends!

As far as it is concerned passing string arguments to PROC...

Here is some kind of WORKAROUND!

INCLUDE TERMINAL.LIB

PROC print(INT a,l)
BEGIN
  WRTLN(a,l)
END

MAIN()
  STRING str$[10] ! Defined as Local
  INT adr,len
BEGIN
  str$="Moscow" ! Initialized
  adr=.str len=LEN(str$)
  CR() print(adr,len)
END

IMHO it can help. :)

Also I think that Pointers can be passed too for working with Literals.

zen

Edited by 576XE
Link to comment
Share on other sites

  • 2 weeks later...

Hello, Friends!

Today I decided the problem with string arguments passing to subroutine.
The reason of problem is in the fact that There are two different representation of strings in PL65.
Human oriented  (str$[40]) for declaring and Compiler oriented (addr,len) for calculations.

The fact is that Compiler simply not decipheres Human oriented representation into Compiler oriented thus PROC pos(STRING patn$[40],strg$[40]) is meaningless as subroutine arguments must be in Compiler representation for calculations.

 

And this code is working!

INCLUDE TERMINAL.LIB

FUNC Pos(INT pA,pL,sA,sL)
  POINTER pP,sP
  BYTE pV BASED pP,sV BASED sP
  INT sC,pC,i,j,psn BYTE f
BEGIN
  IF pL<=sL THEN
  sL=sL-pL+1
  i=0 j=0
! Repeating along the String
  REPEAT
    f=$FF
! Indexing along the Pattern
    FOR j=0 TO pL-1 DO
! Initialize and Atualize Data
      sP=sA+i+j sC=sV
      pP=pA+j   pC=pV
      IF sC<>pC THEN f=0 ENDIF
    NEXT
    i=i+1
  UNTIL (i=sL-1 OR f<>0)
  IF f<>0 THEN psn=i ELSE psn=0 ENDIF
ELSE psn=0 ENDIF
END psn

MAIN()
  STRING s$[256],p$[256]
  INT psn
BEGIN
  s$="Moscow Petersburg Evpatoria Feodosia Simeiz Konakovo"
  p$="Petersburg"
  CR() psn=Pos(p$,s$) WRITE(psn) CR()
END

zen

Link to comment
Share on other sites

  • 5 months later...

Hello Friends!

Recently I've wrote PL65 TEXT Librery with some useful functions.

You can use it at your service, of course.

 

!====================================!
! TEXT.LIB                           !
!  Text Functions Library for PL65   !
!       Programming Language         !
!------------------------------------!
! Evgeny Zolotarev,(aka 576XE), 2023 !
!====================================!
POINTER sP BYTE sV BASED sP
            BYTE wV BASED sP
!====================================!
FUNC Left$(INT sA,sL,n)
  STRING out$[256] INT i
BEGIN
  FOR i=0 TO n DO
    sP=sA+i out$[i,i]=CHR$(sV)
  NEXT
END out$
!------------------------------------!
FUNC Mid$(INT sA,sL,m,n)
  STRING out$[256] INT i
BEGIN
  sA=sA+m-1
  FOR i=0 TO n DO
    sP=sA+i out$[i,i]=CHR$(sV)
  NEXT
END out$
!------------------------------------!
FUNC Right$(INT sA,sL,n)
  STRING out$[256] INT i
BEGIN
  sA=sA+sL-n
  FOR i=0 TO n DO
    sP=sA+i out$[i,i]=CHR$(sV)
  NEXT
END out$
!------------------------------------!
FUNC Pos(INT pA,pL,sA,sL)
  POINTER pP BYTE pV BASED pP
  INT i,j,psn BYTE f
BEGIN
  IF pL<=sL THEN
    sL=sL-pL+1
    i=0 j=0
    ! While Fail ...
    ! Repeating along the String
    REPEAT
      f=$FF
      ! If Success...
      ! Indexing along the Pattern
      FOR j=0 TO pL-1 DO
        sP=sA+i+j pP=pA+j
        IF sV<>pV THEN f=0 ENDIF
      NEXT
      i=i+1
    UNTIL (i=sL OR f<>0)
    IF f<>0 THEN psn=i ELSE psn=0
    ENDIF
  ELSE psn=0 ENDIF
END psn
!------------------------------------!
FUNC Conc$(INT sA,sL,pA,pL)
  STRING out$[256] INT i,j
BEGIN
  FOR i=0 TO sL DO
    sP=sA+i out$[i,i]=CHR$(sV)
  NEXT
  FOR j=0 TO pL DO
    sP=pA+j out$[i+j,i+j]=CHR$(sV)
  NEXT
  i=sL out$[i,i]=" "
END out$
!------------------------------------!
FUNC Ins$(INT pA,pL,sA,sL,m)
  STRING out$[256],a$[256],b$[256]
  INT n
BEGIN
  a$=Left$(sA,sL,m) b$=Right$(sA,sL,sL-m-1)
  n=LEN(a$)+pL+1
  a$=Conc$(a$,pA,pL)
  out$=Conc$(a$,b$)
END out$
!------------------------------------!
FUNC Del$(INT sA,sL,m,n)
  STRING a$[256],b$[256],out$[256] INT i
BEGIN
  a$=Left$(sA,sL,m) b$=Right$(sA,sL,sL-m-n)
  out$=Conc$(a$,b$)
  i=LEN(a$) out$[i,i]=" "
  sP=.out-2 wV=sL-n+1
END out$
!------------------------------------!
FUNC Inv$(INT sA,sL,m,n)
  STRING out$[256] INT i
BEGIN
  out$=Mid$(sA,sL,1,sL)
  FOR i=0 TO n-1 DO
    sP=.out+m-1+i sV=sV+128
  NEXT
END out$
!------------------------------------!
FUNC Upper$(INT sA,sL,m,n)
  STRING out$[256] INT i
BEGIN
  out$=Mid$(sA,sL,1,sL)
  FOR i=0 TO n-1 DO
    sP=.out+m-1+i
    IF sV>$60 AND sV<$7B
    THEN sV=sV-$20 ENDIF
  NEXT
END out$
!------------------------------------!
FUNC Lower$(INT sA,sL,m,n)
  STRING out$[256] INT i
BEGIN
  out$=Mid$(sA,sL,1,sL)
  FOR i=0 TO n-1 DO
    sP=.out+m-1+i
    IF sV>$40 AND sV<$5B
    THEN sV=sV+$20 ENDIF
  NEXT
END out$
!====================================!
ENDFILE

 

Also here is Driver program to check functionality.

 

!====================================!
! TEXT.PRG                           !
!  Text Functions Program for PL65   !
!       Programming Language         !
!------------------------------------!
! Evgeny Zolotarev,(aka 576XE), 2023 !
!====================================!
INCLUDE TERMINAL.LIB
INCLUDE TEXT.LIB
!====================================!
MAIN()
  STRING s$[256],p$[256],a$[256],out$[256] INT psn,m,n
BEGIN
  s$="Moscow Alma-Ata Petersburg Evpatoria Feodosia Simeiz Konakovo"
  p$="Alma-Ata" a$="Syktyvkar"
  m=15 n=12
  CR()
  WRTSTR("Left$ - ") WRTLN(Left$(s$,6))
  WRTSTR("Mid$ - ") WRTLN(Mid$(s$,8,8))
  WRTSTR("Right$ - ") WRTLN(Right$(s$,8))
  CR()
  psn=Pos(p$,s$) WRTSTR("Pos - ") WRITE(psn) CR()
  CR()
  WRTSTR("Conc$ - ") WRTLN(Conc$(p$,a$))
  out$=Ins$(a$,s$,m) WRTSTR("Ins$ -") WRTLN(out$)
  out$=Del$(s$,m,n) WRTSTR("Del$ -") WRTLN(out$)
  m=17 n=10
  CR()
  WRTSTR("Inv$ - ") WRTLN(Inv$(s$,m,n))
  WRTSTR("Upper$ - ") WRTLN(Upper$(s$,m,n))
  WRTSTR("Lower$ - ") WRTLN(Lower$(s$,m,n))
END
!====================================!

 

And the result of course...

TEXT.thumb.png.29379da8170a50230f9435e2db76c933.png

Here is ATR Image of disk :)

 

PL65 TEXT SpDOSx33a 360.atr

 

Best Wishes from Moscow

zen

Edited by 576XE
  • Like 1
Link to comment
Share on other sites

Some explaination after all...

There are 2 forms of string arguments representation in PL65.

 

1. String Name calling: FE out$=Conc$(a$,b$)

- Useful ONLY if we initialize string in THE SAME function !!!

 

2. String INTs calling: FE out$=Conc$(aAdr,aLen,bAdr,bLen)

Here aAdr,aLen,bAdr,bLen obviously declared as INTs in Conc$

- Useful if we initialize string in Calling Procedure and want to send string parameters to Called Subroutine.

It's related to the fact that strings are stored on Stack Only in Adr,Len format and Called Function expected just such data but Name.

 

Best wishes from Moscow :)

zen

Edited by 576XE
Link to comment
Share on other sites

  • 5 weeks later...

Here I added 24 bit calculations (I just needed an access to Bank memory so Add24 and Sub24)

It needs TEXT.LIB because "num to text" and "text to num" transformations.

 

INCLUDE TERMINAL.LIB
INCLUDE TEXT.LIB
!= Globals ==========================!
BYTE op1[3]=$0600,op2[3]=$0603
STRING li1$[7],li2$[7]
!------------------------------------!

PROC inpHex(INT li1A,li1L,li2A,li2L)
  STRING l1$[2],m1$[2],b1$[2]
  STRING l2$[2],m2$[2],b2$[2]
BEGIN
  l1$=Mid$(li1$,6,2)
    m1$=Mid$(li1$,4,2)
      b1$=Mid$(li1$,2,2)
  l2$=Mid$(li2$,6,2)
    m2$=Mid$(li2$,4,2)
      b2$=Mid$(li2$,2,2)
  BASE=16
  op1[0]=VAL(l1$)
    op1[1]=VAL(m1$)
      op1[2]=VAL(b1$)
  op2[0]=VAL(l2$)
    op2[1]=VAL(m2$)
      op2[2]=VAL(b2$)
  BASE=10
END
!------------------------------------!

PROC outHex()
  STRING w$[2]
BEGIN
  IF op1[2]>=10 THEN WRITE(op1[2])
  ELSE w$[1]=STR$(0) w$[2]=STR$(op1[2])
    WRTSTR(w$)
  ENDIF
  IF op1[1]>=10 THEN WRITE(op1[1])
  ELSE w$[0]=STR$(0) w$[1]=STR$(op1[1])
    WRTSTR(w$)
  ENDIF
  IF op1[0]>=10 THEN WRITE(op1[0])
  ELSE w$[1]=STR$(0) w$[2]=STR$(op1[0])
    WRTSTR(w$)
  ENDIF
END
!------------------------------------!

PROC Add24()
  POINTER zp1,zp2
BEGIN
  zp1=.op1 zp2=.op2
  STX XSAVE
  LDX #$03 LDY #$00
  CLC
:loop
  LDA (zp1),Y
  ADC (zp2),Y
  STA (zp1),Y
  INY DEX
  BNE loop
  LDX XSAVE
END
!------------------------------------!

PROC Sub24()
  POINTER zp1,zp2
BEGIN
  zp1=.op1 zp2=.op2
  STX XSAVE
  LDX #$03 LDY #$00
  SEC
:loop
  LDA (zp1),Y
  SBC (zp2),Y
  STA (zp1),Y
  INY DEX
  BNE loop
  LDX XSAVE
END
!====================================!

MAIN()
  STRING w$[2]
BEGIN
  li1$="$ABCDEF" li2$="$123456"

  inpHex(li1$,li2$)
  BASE=16
  Add24() WRTSTR("$") outHex() CR()

  inpHex(li1$,li2$)
  BASE=16
  Sub24() WRTSTR("$") outHex() CR()
END
!====================================!

Here is the image of disk...

PL65 TEXT SpDOSx33a 360.atr

And the result of $ABCDEF and $123456 Addition and Subtruction :)24bit.thumb.png.b129ccddfd5532229be501fd2acaa068.png

 

 

 

Edited by 576XE
Link to comment
Share on other sites

It's great to see people getting interested in this overlooked language. The main issue I found with it was that it created compound files, which probably slowed down compilation somewhat. I really want to dig out my PL65 stuff and see if any of it still works.

 

Something that I did do with mine was swap out the DOS 2.5 to MyDOS. Slightly risky but it worked. Although the DOS 2.5 on the disk had been pre-modified to allow 7 open IOCB channels at once, the limitations of DOS 2.5 were such that I found it easier to install MyDOS on the disk for the Menu Print disk cataloguing project. I can't remember what the exact issue was, but I was spending a lot of time investigating the various Menu and DOS variants so I could get it to read virtually any disk format. I suspect MyDOS made that easier in some way.

 

While I did use inline assembler, I'd typically restrict them to interrupt routines. Something I loved about the language was the introduction of pointers. This was my first introduction to pointers and a high level language that didn't use line numbers. So, I guess that almost everything I've picked up since can be traced to what I learned from using PL65.

With the compound files issue, I was going to write a converter that would change it to a contiguous file because I wanted the Menu Print project to be cartridge based, although I'm not sure how practical that was. That could be a nice little challenge for someone to write one in PL65? I'm fairly sure that, despite the output being compound files, the blocks followed each other in memory. The only question mark might be the location of the runtime library as opposed to the start of the compiled code. There's likely a gap between the two.

Found a copy of the manual in the shed the other day. It's not my original. It was one I printed from a copy found on AA a while ago.

  • Like 1
Link to comment
Share on other sites

Join the conversation

You can post now and register later. If you have an account, sign in now to post with your account.
Note: Your post will require moderator approval before it will be visible.

Guest
Reply to this topic...

×   Pasted as rich text.   Paste as plain text instead

  Only 75 emoji are allowed.

×   Your link has been automatically embedded.   Display as a link instead

×   Your previous content has been restored.   Clear editor

×   You cannot paste images directly. Upload or insert images from URL.

Loading...
  • Recently Browsing   0 members

    • No registered users viewing this page.
×
×
  • Create New...