DevWare DevDisk 077 Programming

C-Fortran 77, EZAsm

 

EZAsm    
Version 1.31, December '90   
by Joe Siebenmann

 

EZAsm was designed to simplify programming in 68000 assembly language, catering to both:

  • Experienced assembly language programmers.
  • Those interested in leveraging the speed and compact code of assembly language for their projects.

Key Features:

  • Hybrid Approach: Combines elements of the "C" language with 68000 assembly, creating a development experience that feels similar to higher-level languages.
  • Optimized Output: The resulting code is streamlined for maximum performance and efficiency.

Purpose:
To make assembly language programming more accessible and practical, while maintaining the performance benefits it offers.

 

C-Fortran77 ver.C 

 

 

Disk Preview

C
MuchMore
04/04/1991 23:00
17216
EZAsm
.info
08/18/1991 04:00
26
EZAsm
04/05/1991 02:00
24028
EZAsm.doc
04/05/1991 02:00
20244


    EZAsm	Version 1.31		December '90   by Joe Siebenmann


	DISCLAIMER:

	You have the right to freely use, copy and distribute this program
	as long as the following conditions are met:

	1.  The program and documentation are not modified in any way.
	2.  The program is not used or included in any package for profit
		unless written consent from the author is obtained.

	NOTE: The author does not accept any responsibility for any damage
		that might result from the use of this program.



	EZAsm was written to make programming in 68000 assembly language
		much easier, for both assembly language programmers, and
		those who may be interested in using the speed and compact
		code that assembly language provides for a project.
		EZAsm  combines parts of the "C" language with 68000
		assembly, giving it the "feel" of a higher level language. 
		The resulting code is optimized as much as possible.



Here are some of its advantages:


-	It always converts your statement into the fastest possible
		assembly statement(s), so you automatically write
		"good" code.

-	More structured.  Compare, and bit test statements can have
		braces and "else" like "C".  Being able to use braces lets
		you use assembly in a whole new way!

-	"C" like Amiga function calls!  Every 1.3 function in every
		library is supported.  An XREF table is automatically
		built and inserted.

-	Makes code MUCH more readable, for debugging etc.	

-	Enables you to code nearly TWICE as fast, with fewer syntax errors.

-	No more having to constantly look up which condition code to	
		use for compares, bit tests, or maximum numbers for
		"moveq" or "addq" etc.

-	You can insert normal assembly statements anywhere, for your
		special needs.



	You need to know a little about assembly language, and "C"
		operators, before you dive right in.  If you're new to
		68000 assembly language, I suggest looking at one of the
		many available books on the subject.  The included example
		source programs can give you a good idea about:


-	General statement syntax.

-	Use of the additional arguments, to "force" size etc.

-	Using assembly statements in your code.


****************************************	

Using EZAsm:



EZAsm filename.s


Where filename is the name of your source file including any path.
	Give your source file an extension ( .s etc. ) or your
	linker will overwrite it.

It produces an output file called filename.asm .

Be sure the files "funcnm" & "funcdat" are in the same directory
	as EZAsm.  Cd into this directory and you're ready to go.

Depending on which assembler you use on the final output file,
	you may need to change the extension from .asm to .a or make minor
	changes or additions to your source.  The code section has been made
	as compatible as possible.  If your assembler complains, it's
	typically something in the data section.

    Manx:   as scroll.asm
            ln scroll.o -lc



*********************************
*        Operand  Table         *
*********************************

              Operand Type

Mode     [A] [B] [C] [D] [E] [F]

Dn        *   *   *   -   *   -
An        *   -   *   -   -   -
(An)      *   *   *   *   *   *
(An)+     *   *   *   *   *   *
-(An)     *   *   *   *   *   *
d(An)     *   *   *   *   *   *
d(An,Xn)  *   *   *   *   *   *
abs.w     *   *   *   *   *   *
abs.l     *   *   *   *   *   *
d(PC)     *   -   -   -   *   *
d(PC,Xn)  *   -   -   -   *   *
d (immed) *   -   -   -   -   -


declared variables:

"foo"  becomes  "foo(a5)"  ( d(An) )


examples:

abs.w:  ($1f40)
        (1024)
        CLR_PUB     *1


abs.l:  ($bfe001)
        (12574721)
        Max         *1


d (immd):  $dff000
           -1
           512


*1  Where these have been previously defined as "CLR_PUB  equ  $10001" etc.

**************************************

      ( decimal or hex )

#<1>   1 - 8
#<2>   0 - 7
#<3>   0 - 31
#<4>   -128 - 127
#   any byte, word, or long size number


Dn     d0 - d7
An     a0 - a7


{B}    B (byte) data size not allowed for An operands


*****************************************
*    legal     *  converted   *  legal  *
*   operands   *     to       *  sizes  *
*****************************************

Addition  Subtraction

++
--

    [C]         addq/subq       L,W,{B}

+=
-=
	
    Dn   [A]    add/sub         L,W,B		

    [D]  Dn     add/sub         L,W,B

    An   [A]    adda/suba       L,W
	
    [B]  # addi/subi       L,W,B		
	
    [C]  #<1>   addq/subq       L,W,{B}	


Examples:

	Total ++	
	d1 += 10

Optional Args:

	l, w, b 

**********************************

Multiplication   Division


*=
/=

    Dn  [E]     divu/mulu (default)   W
	
    Dn  [E]  s  divs/muls             W


    ( SPECIAL:  Where # is a byte or word length number. ( higher could  
        overshift the result )  The resulting code is larger then "mulu"
        or "muls" but will execute much faster.
        ( it will default to a normal "mulu" or "muls"
        if the number isn't "right" ) )


    Dn *= #                           L


Examples:

	d0 *= d1
	d2 /= 2

Optional Args:

	w (default), s		

**********************************

And   Or   Exclusive Or


&=
|=

    [B]  #     andi/ori        L,W,B	
	
    Dn   [E]        and/or          L,W,B
	
    [D]  Dn         and/or          L,W,B


x=

    [B]  Dn         eor             L,W,B	
	
    [B]  #     eori            L,W,B


Examples:

	Mask &= %11010000
	Flags |= $f0

Optional Args:

	l, w, b 

***********************************

Shift  Left/Right


<<
>>

    Dn   Dn     lsl/lsr         L,W,B
	
    Dn   1-8    lsl/lsr         L,W,B
	
    [D]  1      lsl/lsr         L,W,B

             a  asl/asr


    ( SPECIAL:  Normally you're limited to 1-8 and must use a
        data register to hold higher.  In this statement  
        the output is optimized, so it's faster, and saves
        using a data register!  ( logical only ) )


    Dn   1-31                   L



Examples:

	d2 << d0
	d1 >> 4

Optional Args:

	l, w, b, a
	( logical is default )
	
***********************************

Assign


=	

    [B]  [A]    move            L,W,{B}
	
    An   [A]    movea           L,W
	
    Dn   #<4>   moveq           L


Examples:

	temp = Total
	(a1)+ = 0 w

Optional Args:

	l, w, b 

***********************************

Compare


>=
<=
!=
>
<
=

    Dn    [A]      cmp          L,W,{B}
	
    An    [A]      cmpa         L,W
	
    [B]   #   cmpi         L,W,B
	
    (An)+ (An)+    cmpm         L,W,B



Syntax types:


    [opr] [op] [opr]   label



    [opr] [op] [opr]   {
        .
        .
    }



    [opr] [op] [opr]   {
        .
        .
	
    } else {
        .
        .
    }


Example:

	Total >= 100 Over


Optional Args: ( placed AFTER label or brace )

	l, w, b, s

********************************************

Bit test



    Dn:0-31  =  0-1 label    btst.l     L
	
    Dn:Dn    =  0-1 label               L
	
	
    [F]:0-7  =  0-1 label    btst.b     B	
	
    [F]:Dn   =  0-1 label               B

	
( You can also use braces "{" instead of a label, see
	compare for use of braces )


Examples:

	d1:0 = 1 CalcRtn

	($bfe001):6 = 0 LMBDown

	d2:d0 = 1 ItsSet 


Optional Args:

	( ignored )
	
Rules:

-	No spaces inside first operand.

-	Only "=" is allowed.

-	Right operand can only be 0 or 1.


****************************************

Additional Arguments:


b   forces operation to be byte

w     "       "        "   word

l     "       "        "   long

a	arithmetic shift       ( <<, >> )       ( logical is default )

s	signed                 ( *=, /= , compares )


( these are RESERVED and can't be used as variables, or labels
	( unless you use upper case ) ) 

******************************************************

Functions:


Syntax types:

	CloseWindow( Window )

	Buf = AllocMem( 512 $10001 )

	Permit( )



Example:

--------------------------------

dosname		dc.b	"dos.library",0
fname		dc.b	"df0:myfile",0

CLEAR_PUBLIC equ	$10001
OLD          equ	1005


LONG	_DosBase FHandle num Rbuf 


		_DosBase = OpenLibrary( #dosname 0 ) 
		beq	 Exit

		Rbuf = AllocMem( 100 #CLEAR_PUBLIC )
		beq  Exit

		FHandle = Open( #fname #OLD ) 				
		beq  Exit

		d3 = 100	; preload D3   *1
		num = Read( d0 Rbuf * )

			.
			.
			.



*1   normally you wouldn't need to do this, it's only an example..

---------------------------------


-	You must first do an OpenLibrary( ) to access functions in
		a library.  Functions in ConsoleDevice are accessed 
		differently.  See the ConsoleDevice section in the RKM p 662.
		( load the io_Device field into "_ConBase" )
		Functions in ExecBase are always accessible and don't
		need to be opened.
		The library bases MUST be named:

	_ConBase
	_DiskfontBase
	_DosBase
	_ExpansionBase
	_GfxBase
	_IconBase
	_IntuitionBase
	_LayersBase
	_MathBase
	_MathIeeeDoubBasBase
	_MathIeeeDoubTransBase
	_MathTransBase
	_PotgoBase
	_RomBootBase
	_TimerBase
	_TranslatorBase



-	Unfortunately the leading underscores are necessary so you can use
		includes without your assembler complaining.  Some library
		bases ( IntuitionBase, ExecBase, GfxBase, ExpansionBase,
		RomBootBase ) are already defined in some .i's resulting in
		"multiply defined symbol" errors.

-	You might notice that ExecBase is missing.  It isn't needed.
		( it's loaded with "movea.l $4,a6" )


                   Permit( )
              OpenLibrary( #dosname 0 )
                        ^ ^          ^
               no space | | space    | space

-	The function name must be followed immediately with "(" ( no
		spaces between ) and then followed by a space or tab.
		If the function has no arguments, it still needs a space in
		the middle.  Arguments must be separated with a space or tab.


Arguments:

-	If your argument is already in a DIFFERENT data or address register,
		you can pass it as an argument.  Often a previous function
		will put results in D0, so just pass d0.  If the proper
		register is already loaded just pass "*".
		The above example shows both of these.

		( if you pass it the same register it uses, it'll be skipped.
		func defined as:  Lock( D1 D2 )  "Flock = Lock( d1 -2 )"
		arg "d1" will be skipped )


-	If you need a pointer to a newwindow, filename, library name, etc.
		use "#dosname" etc. like the example above. It'll load its
		address ( pointer ) into a data or address register.


	All functions within these ( 1.3 ) libraries are supported:

		ConsoleDevice
		DiskfontBase		
		DOSBase
		ExecBase  ( SysBase )
		ExpansionBase
		GfxBase
		IconBase
		IntuitionBase
		LayersBase
		MathBase
		MathIeeeDouBasBase
		MathIeeeDoubTransBase
		MathTransBase
		PotgoBase
		RomBootBase
		TimerBase
		TranslatorBase


-	It keeps track of the current library base.  As long as no user
		labels, or close braces ("}") are hit, it will not re-load
		the base register for functions which have the same
		library base.

-	The file "funcnm" contains a list of every function that is
		supported.

**************************************************

Optimizations:


  STATEMENT          BECOMES        NOTE


   An = 0          sub.l An,An

   [B] = 0         clr [B]          1


 ( compares )

   [B] = 0
   [B] != 0        tst [B]
                   bcc label

   ----------------------------------

   [B] += #
   [B] -= #

   [B] &= #   
   [B] |= #
   [B] x= #

   [B] = #         moveq   #,d7     2
                   [opr].l d7,[B]


   ( compares )

   dn .. # label   moveq   #,d7     2
                   cmp.l   d7,dn
                   bcc     label

   an .. # label   moveq   #,d7     2
                   cmpa.l  d7,an
                   bcc     label

   ----------------------------------

   Dn << 1-31
   Dn >> 1-31                       3, 2

   An += #1        lea  n(An),An
   An -= #1        lea  -n(An),An   4, 2

   An = #2         lea  n,An        5, 2

   Dn *= #1                         6

   

# = 1-127    ( #<4> if appropriate )

#1 = any byte or word length number

#2 = any byte, word, or long length number



Notes:

1	For byte and word sizes the code size is smaller, for long,
		its smaller and faster. ( then "move #0,[B]" )			

2	Only apply to long sized operations.

3	The resulting instructions are combinations of "swap", "clr.w",
		"add.l", "lsr" or "lsl".

4	( 1-8 handled by "addq", "subq" )

5	( 0 handled by "sub.l An,An" )

6	The resulting instructions are combinations of "move.l", "asl.l", 
		"asr.l", "add.l".		


********************************************

General Info:


-	Statements can be indented as you like.  Operands, operator,
		and arguments must be separated by at least one space or tab. 

-	Braces can be nested up to 30 deep.
	
-	Only one statement per line.

-	If you declare variables or use function call's, the first statement
		in your code must be an "EZAsm statement" so it knows when
		to insert the XREF's and/or get stack frame for the
		variables.  ( comments or assembly directives placed between
		your variables and the start of your code will be
		out of place in the output file )

-	Comments at 1st column must begin with "*" or ";".  Comments after
		statements must be begin with ";" and be separated from last
		argument, or operand.
		( both types are transferred to output file ( some may not ))

-	Operands supported: octal: @141  hex: $61  binary: %1100001
		ASCII: 'a' and decimal: 97   ASCII strings in operands
		can contain a maximum of 4 characters.
		( no quotes within quotes permitted )    

-	To make labels and symbols as compatible as possible, they arn't
		checked for illegal characters.  Typically the 1st character
		must be a letter, underscore "_", or a period "." .
		The rest of the characters can be any of these plus 0-9.

-	Labels and symbols can have an unlimited length.  ( check your
		assembler to find what length they are significant to
		( usually around 30 ) )

-	Labels that don't begin at column 1 should be followed immediately
		with ":".

-	Local labels ( "2$   d1 = 0" ) are supported.

-	No need to put in the usual "moveq #0,d0", "rts" at the end of your
		code, its part of the closing block of code it inserts to
		free the variables.

-	D7 is used as a scratch register for some optimizations, so be
		careful if you use it.

-	Labels that it generates for braces are in the range
		".laaa" to ".lzzz" so try to avoid using them.
		( upper case is OK )

-	"SP", "PC", "CCR", "SR" & "USP" are supported, but you must ensure
		the size is legal as no checks are made.
		( must be upper case )

-	For best viewing of output file set your tabs to 8 spaces.
		( printing should be fine )


IMPORTANT! :

Use of register A5 is RESERVED!

( it contains the base address for variable storage )


********************************

Variable Declaration:


LONG	foo Save[10] bar ...
WORD    DMASave ...
BYTE	Sw ...


-	"xxx[n]" reserves n consecutive blocks of given size, with
		"xxx" pointing to 1st byte.

-	You're limited to 14 variables per line.

-	No other statement types may occur between these lines.

-	Variables must be separated by at least one space, or tab.

-	To keep things word aligned, if an odd number of bytes are	
		declared in BYTE, an extra byte will be added.  This
		will offset the next "equ" by one.
		( in the case of "BYTE    Count foo buf[3]" ( 5 bytes )
		an extra would be added )

-	Variables are stored on the stack, and are not cleared.
		Be sure to properly initialize them.  

-	Any number of these can be used, in any order.	

-	Must occur JUST BEFORE your program code.

-	Must begin at 1st column, with LONG, WORD, or BYTE in upper case.


************************************************

How to get what you need, hints, etc.:


-	Using "ENDS":	Its safer to put all your data AFTER your code
		so it can't accidentally be executed when it runs.
		To do this, put "ENDS" ( END Source ) after your code,
		( signals the closing block of code to free the variables
		to be output ) and "END" at the very bottom.  "END" must
		allways be at the bottom.
		( see the example source "window.s" which uses this )

-	Instruction size:	In most cases you won't need
		a size argument.  It knows the size of the variables,
		address and data registers, and is smart enough to know
		what size to use.  It determines the size of data by it's
		actual value not its physical size.
		( $0020  %11010000  $12  125  are all BYTE size )
		If the data is smaller than the instruction size you want,
		( d1 = $20 w ) or it can't know an operands size
		( (a2)+ = 3(a0) l ) you'll need to give it a size argument.

		Caution:

			Be aware that if you load small variables into larger
			ones, the upper bytes will not be cleared and may
			garbage your result.


-	Since "(a1)" refers to the CONTENTS of the byte, word, or long
		that a1 points to, "($dff180)" is used in a similar way.
		"move.w  $dff01e,d0" would become, "d0 = ($dff01e) w".
		( decimal addr's are also valid: "(4)", "(256)" )

-	When numbers are used as operands "$fe02" or "37", they are
		converted to "#$fe02", "#37".  ( when "$2f(a2)" or "15(a0)"
		are used, they are left AS IS ( see below ))

-	Operands that it DOESN'T RECOGNIZE, doesn't match with any
		declared LONG, WORD, BYTE, or standard "(a1)+" etc., get
		output AS IS.  This is VERY USEFUL when you need operands
		like: "#intuiname", "wd_UserPort(a1)", "$20(a1)", "DMACON(a6)"

-	Most statements set condition code flags on the result of the
		operation.  Often, instead of using a compare to check the
		result, you can use an assembly instruction, branching on
		the state of a condition code flag! ( you need to check
		what flags are set ( if any ) for an instruction )

-	If at any time you're unsure of what a statement is being
		output as, or want to check something out, just look
		at the output file.

-	I think it's a good idea to get away from using include files.
		It speeds up the assembler tremendously.  Most assembly
		source files I see do this.


****************************************

Errors:


"Illegal argument"

	The argument found was not valid for the operator.  See
	the list of "Optional Args" for the operator.  It must
	be lower case, and be separated from the operands
	by at least a space or a tab.
	
"Illegal operand"

	One, or both, of the operands are:  not valid for the operator,
	have an invalid number, or byte size was specified for an
	"An" operand {B}.  In most cases it's looking for "Dn" or "An"
	as one of the operands.  ( look under the "legal operands"
	of the operator for a valid combination )

"Illegal size"

	The argument size you specified is not valid for the operator.	
	Check the "legal sizes" for the operator.
	
"Needs size argument"	

	It doesn't have enough size information about the operands to
	calculate an instruction size.
	You need to add an l, w, or b argument.

"Label not found"

	No label matching your label argument was found.	

"Brace mismatch"

	Checks are made when a closing brace ( "}" ) is hit, and when "END"
	is hit.  If the brace stack is "messed up" at that time, an error 
	is given.  If "}" is shown, look from there up.  Both "}" and "END"
	may appear.  If just "END", look for a "{" or "} else {" without a
	matching "}".

"Function not found"

	No function matching your function name was found.  Check case and	
	spelling of function name, and be sure there isn't a space before
	the "(".  Check the list of supported function names in the
	file "funcnm".

"Function argument count incorrect"

	Check the number of arguments you used for the function.  Too many
	or not enough were used.


*******************************************************************
*******************************************************************

Changes for 1.31 :

o	New "funcdat". ( same size )

o	Instruction size logic has been improved, now with no
	warnings.  Variable's "equ"'s have been changed.

o	Use of "$fffffffe" etc. now optimized for "moveq".


 

	I hope you find this program useful.  If you have any ideas for
		improvements, bugs, or something you'd like to see in a
		future version, I would appreciate hearing from you!


I can be contacted at:


( till around spring of '91 )

Joe Siebenmann
8303 Old Tree Ct.
Springfield, VA  22153
(703) 455-4982


( anytime )

PLINK:	IGZ798



Happy Programming!






EZAsm.doc.info
08/18/1991 04:00
734
colorchg
04/05/1991 02:00
228
colorchg.s
04/05/1991 02:00
1155


*	change color0 every 7th VBlank
*	( takes about 2 mins. to see all the colors )
*	hit left mouse button to quit
*	no display planes needed!


INTREQR		equ	$01e
INTREQ		equ	$09c
INTENAR		equ	$01c
INTENA		equ	$09a

DMACONR		equ	$002
DMACON		equ	$096

BPLCON0		equ	$100
BPLCON1		equ	$102
BPLCON2		equ	$104
BPL1MOD		equ	$108
BPL2MOD		equ	$10a

DDFSTRT		equ	$092
DDFSTOP		equ	$094
DIWSTRT		equ	$08e
DIWSTOP		equ	$090

BPL1PTH		equ	$0e0
BPL2PTH		equ	$0e4



*		CSEG (Manx)
		SECTION	CODE


LONG	DispMem Count
WORD	IntSave DmaSave Color



		a6 = $dff000
		IntSave = INTENAR(a6)
		DmaSave = DMACONR(a6)


		INTENA(a6) = $7fff
		DMACON(a6) = $7fff
		INTENA(a6) = $8020	;SET VERTB

		Count = 0
		Color = $777	;start half way thru

VBloop		d1 = INTREQR(a6) w
		d1:5 = 1 {

			INTREQ(a6) = $0020 w	;CLEAR VERTB
			
			Count ++
			Count >= 6 {
				Color += 2
				Color &= $0fff
				Count = 0
			}
			
			($dff180) = Color
		}

		($bfe001):6 = 1 VBloop


*	restore DMACON & INTENA
			
Quit		a6 = $dff000
		INTENA(a6) = $7fff
		DMACON(a6) = $7fff
			
		d0 = IntSave
		bset.l	#15,d0
		INTENA(a6) = d0 w
			
		d0 = DmaSave
		bset.l	#15,d0
		DMACON(a6) = d0 w


		END

funcdat
04/05/1991 02:00
2920
		
	
				
									
		
	
								
			
								
					
															
													
		
	











		
			
			
				
	
										
		
															
	
			
	
			
																																						
										
			
			
			
	
		
			
		
	
		
	
	
			
funcnm
04/05/1991 02:00
4855
AbortIO
ActivateGadget
ActivateWindow
AddAnimOb
AddBob
AddConfigDev
AddDevice
AddDosNode
AddFont
AddFreeList
AddGList
AddGadget
AddHead
AddIntServer
AddLibrary
AddMemList
AddPort
AddResource
AddSemaphore
AddTail
AddTask
AddTime
AddVSprite
Alert
AllocAbs
AllocBoardMem
AllocConfigDev
AllocEntry
AllocExpansionMem
AllocMem
AllocPotBits
AllocRemember
AllocSignal
AllocTrap
AllocWBObject
Allocate
AlocRaster
AlohaWorkBench
AndRectRegion
AndRegionRegion
Animate
AreaDraw
AreaEllipse
AreaEnd
AreaMove
AskDefaultKeyMap
AskFont
AskSoftStyle
AttemptLockLayerRom
AttemptSemaphore
AutoRequest
AvailFonts
AvailMem
BeginRefresh
BeginUpdate
BehindLayer
BltBitMap
BltBitMapRastPort
BltClear
BltMaskBitMapRastPort
BltPattern
BltTemplate
BuildSysRequest
BumpRevision
CBump
CDInputHandler
CMove
CWait
Cause
ChangeSprite
CheckIO
ClearDMRequest
ClearEOL
ClearMenuStrip
ClearPointer
ClearRectRegion
ClearRegion
ClearScreen
ClipBlit
Close
CloseDevice
CloseFont
CloseLibrary
CloseScreen
CloseWindow
CloseWorkBench
CmpTime
ConfigBoard
ConfigChain
CopyMem
CopyMemQuick
CopySBitMap
CreateBehindLayer
CreateDir
CreateProc
CreateUpfrontLayer
CurrentDir
CurrentTime
DateStamp
Deallocate
Debug
Delay
DeleteFile
DeleteLayer
DeviceProc
Disable
DisownBlitter
Dispatch
DisplayAlert
DisplayBeep
DisposeFontContents
DisposeLayerInfo
DisposeRegion
DoCollision
DoIO
DoubleClick
Draw
DrawBorder
DrawEllipse
DrawGList
DrawImage
DupLock
Enable
EndRefresh
EndRequest
EndUpdate
Enqueue
ExNext
Examine
Exception
Execute
Exit
ExitIntr
FattenLayerInfo
FindConfigDev
FindName
FindPort
FindResident
FindSemaphore
FindTask
FindToolType
Flood
Forbid
FreeBoardMem
FreeColorMap
FreeConfigDev
FreeCopList
FreeCprList
FreeDiskObject
FreeEntry
FreeExpansionMem
FreeFreeList
FreeGBuffers
FreeMem
FreePotBits
FreeRaster
FreeRemember
FreeSignal
FreeSprite
FreeSysRequest
FreeTrap
FreeVPortCopLists
FreeWBObject
GetCC
GetColorMap
GetCurrentBinding
GetDefPrefs
GetDiskObject
GetGBuffers
GetIcon
GetMsg
GetPacket
GetPrefs
GetRGB4
GetScreenData
GetSprite
GetWBObject
IEEEDPAbs
IEEEDPAcos
IEEEDPAdd
IEEEDPAsin
IEEEDPAtan
IEEEDPCeil
IEEEDPCmp
IEEEDPCos
IEEEDPCosh
IEEEDPDiv
IEEEDPExp
IEEEDPFieee
IEEEDPFix
IEEEDPFloor
IEEEDPFlt
IEEEDPLog
IEEEDPLog10
IEEEDPMul
IEEEDPNeg
IEEEDPPow
IEEEDPSin
IEEEDPSincos
IEEEDPSinh
IEEEDPSqrt
IEEEDPSub
IEEEDPTan
IEEEDPTanh
IEEEDPTieee
IEEEDPTst
Info
InitArea
InitBitMap
InitCode
InitGMasks
InitGels
InitLayers
InitMasks
InitRastPort
InitRequester
InitResident
InitSemaphore
InitStruct
InitTmpRas
InitVPort
InitView
Input
Insert
InstallClipRegion
IntuiTextLength
Intuition
IoErr
IsInteractive
ItemAddress
LoadRGB4
LoadSeg
LoadView
Lock
LockIBase
LockLayer
LockLayerInfo
LockLayerRom
LockLayers
MakeDosNode
MakeFunctions
MakeLibrary
MakeScreen
MakeVPort
MatchToolValue
ModifyIDCMP
ModifyProp
Move
MoveLayer
MoveLayerInFrontOf
MoveScreen
MoveSprite
MoveWindow
MrgCop
NewFontContents
NewLayerInfo
NewModifyProp
NewRegion
ObtainConfigBinding
ObtainSemaphore
ObtainSemaphoreList
OffGadget
OffMenu
OldOpenLibrary
OnGadget
OnMenu
Open
OpenDevice
OpenDiskFont
OpenFont
OpenIntuition
OpenLibrary
OpenResource
OpenScreen
OpenWindow
OpenWorkBench
OrRectRegion
OrRegionRegion
Output
OwnBlitter
ParentDir
Permit
PolyDraw
PrintIText
Procure
PutDiskObject
PutIcon
PutMsg
PutWBObject
QBSBlit
QBlit
QueuePacket
RawDoFmt
RawIOInit
RawKeyConvert
RawMayGetChar
RawPutChar
Read
ReadExpansionByte
ReadExpansionRom
ReadPixel
RectFill
RefreshGList
RefreshGadgets
RefreshWindowFrame
ReleaseConfigBinding
ReleaseSemaphore
ReleaseSemaphoreList
RemConfigDev
RemDevice
RemFont
RemHead
RemIBob
RemIntServer
RemLibrary
RemPort
RemResource
RemSemaphore
RemTail
RemTask
RemVSprite
RemakeDisplay
Remove
RemoveGList
RemoveGadget
Rename
ReplyMsg
ReportMouse
Request
Reschedule
RethinkDisplay
RomBoot
SPAbs
SPAcos
SPAdd
SPAsin
SPAtan
SPCeil
SPCmp
SPCos
SPCosh
SPDiv
SPExp
SPFieee
SPFix
SPFloor
SPFlt
SPLog
SPLog10
SPMul
SPNeg
SPPow
SPSin
SPSincos
SPSinh
SPSqrt
SPSub
SPTan
SPTanh
SPTieee
SPTst
Schedule
ScreenToBack
ScreenToFront
ScrollLayer
ScrollRaster
ScrollVPort
Seek
SendIO
SetAPen
SetBPen
SetCollision
SetComment
SetCurrentBinding
SetDMRequest
SetDefaultKeyMap
SetDrMd
SetExcept
SetFont
SetFunction
SetIntVector
SetMenuStrip
SetPointer
SetPrefs
SetProtection
SetRGB4
SetRGB4CM
SetRast
SetSR
SetSignal
SetSoftStyle
SetTaskPri
SetWindowTitles
ShowTitle
Signal
SizeLayer
SizeWindow
SortGList
SubTime
SumKickData
SumLibrary
SuperState
Supervisor
SwapBitsRastPortClipRect
Switch
SyncSBitMap
Text
TextLength
ThinLayerInfo
Translate
TypeOfMem
UCopperListInit
UnLoadSeg
UnLock
UnlockIBase
UnlockLayer
UnlockLayerInfo
UnlockLayerRom
UnlockLayers
UpfrontLayer
UserState
VBeamPos
Vacate
ViewAddress
ViewPortAddress
WBenchToBack
WBenchToFront
Wait
WaitBOVP
WaitBlit
WaitForChar
WaitIO
WaitPort
WaitTOF
WhichLayer
WindowLimits
WindowToBack
WindowToFront
Write
WriteExpansionByte
WritePixel
WritePotgo
XorRectRegion
XorRegionRegion
scroll
04/05/1991 02:00
344
scroll.s
04/05/1991 02:00
1611

*	scroll example
*	hit left mouse button to quit


INTREQR		equ	$01e
INTREQ		equ	$09c
INTENAR		equ	$01c
INTENA		equ	$09a

DMACONR		equ	$002
DMACON		equ	$096

BPLCON0		equ	$100
BPLCON1		equ	$102
BPLCON2		equ	$104
BPL1MOD		equ	$108
BPL2MOD		equ	$10a

DDFSTRT		equ	$092
DDFSTOP		equ	$094
DIWSTRT		equ	$08e
DIWSTOP		equ	$090

BPL1PTH		equ	$0e0
BPL2PTH		equ	$0e4



CLEAR_CHIP	equ	$10002


*		CSEG (Manx)
		SECTION	CODE


LONG	DispMem Count
WORD	IntSave DmaSave Color


		DispMem = AllocMem( 16000 #CLEAR_CHIP )
		beq	Quit
			
		a3 = $dff000
		IntSave = INTENAR(a3)	;save DMA and interrupt states
		DmaSave = DMACONR(a3)


*	set up display regs

		BPLCON0(a3) = $1200	; (LORES) 1BPL COLOR			
			
		BPLCON1(a3) = 0 w
		BPLCON2(a3) = 0 w
		BPL1MOD(a3) = 0 w
		BPL2MOD(a3) = 0 w

		DIWSTRT(a3) = $2c81
		DIWSTOP(a3) = $f4c1
		DDFSTRT(a3) = $0038 w
		DDFSTOP(a3) = $00d0 w

		INTENA(a3) = $7fff
		DMACON(a3) = $7fff
		INTENA(a3) = $8020	;SET VERTB
		DMACON(a3) = $8300	;SET DMAEN BPLEN

*	Make bands for effect

		d1 = 7
		d2 = $ffffffff
		a1 = DispMem
1$		d0 = 249
2$		(a1)+ = d2
		dbf	d0,2$
		a1 += 1000	;start of next band
		dbf	d1,1$

		d2 = DispMem
		d3 = d2
		d3 += 7960

VBloop		d1 = INTREQR(a3) w
		d1:5 = 1 {

			INTREQ(a3) = $0020 w

			d2 > d3 {
				d2 = DispMem
			} else {
				d2 += 50
			}

			BPL1PTH(a3) = d2
		}

		($bfe001):6 = 1 VBloop


Quit
		DispMem != 0 {		
			FreeMem( DispMem 16000 )
		}

*	restore DMACON & INTENA
			
		a3 = $dff000
		INTENA(a3) = $7fff
		DMACON(a3) = $7fff
		
		d0 = IntSave
		bset.l	#15,d0
		INTENA(a3) = d0 w
			
		d0 = DmaSave
		bset.l	#15,d0
		DMACON(a3) = d0 w


		END

window
04/05/1991 02:00
484
window.s
04/05/1991 02:00
2145



*	Opens a window, gets the window's fontdata into our CHIP area
*		and blits part of it into the window.

*	( uses "ENDS" for data at bottom )
*	( text might be trashed under 2.0 )

*	click left mouse button to exit

			
		include     "intuition/intuition.i"
		include     "exec/types.i"
		include     "graphics/gfx.i"
		include     "graphics/rastport.i"



CLEAR_CHIP	equ	$10002


		CSEG



LONG	Wind _IntuitionBase FontData Planes _GfxBase


		FontData = AllocMem( 2048 #CLEAR_CHIP )
		beq	Quit

		_IntuitionBase = OpenLibrary( #intuiname 0 )
		beq	Quit

		_GfxBase = OpenLibrary( #graphname 0 )
		beq	Quit

		Wind = OpenWindow( #newwin )
		beq	Quit



*	a handy debugging aid!

*	( just remove the '*', change the color, and be sure a label's
*	before the next one )

*		d6 = 1000
*1$		d7 = 10000
*2$		($dff180) = $0f0 w	;GREEN
*		dbf	d7,2$
*		dbf	d6,1$





*   load fontdata into our chip area

		a0 = Wind
		a1 = wd_RPort(a0)
		a2 = rp_Font(a1)
		a3 = tf_CharData(a2)
			
		d1 = 383
		a4 = FontData
FontLoop	(a4)+ = (a3)+ l
		dbf	d1,FontLoop


*   get addr of windows 1st bitplane

		a2 = rp_BitMap(a1)
		Planes = bm_Planes(a2)


*   blit out first portion of fontdata


		a6 = $dff000
			
		$40(a6) = $03aa		;BLTCON0  USE: C D  D=C
		$60(a6) = $007a w	;BLTCMOD
		$66(a6) = $000a w	;BLTDMOD
			
		d1 = Planes			
		d1 += 1605
		$54(a6) = d1
			
		$48(a6) = FontData
			
		$74(a6) = 0 w		;BLTADAT
		$72(a6) = 0 w		;BLTBDAT
			
		$96(a6) = $8240		;DMACON   SET DMAEN BLTEN
			
		$58(a6) = 547		;BLTSIZE


BlitWait	($dff002):6 = 1 BlitWait	;DMACONR  BBUSY?

QuitLoop	($bfe001):6 = 1 QuitLoop	;wait for LMB down


Quit
		Wind != 0 {
			CloseWindow( Wind )
		}

		_IntuitionBase != 0 {
			CloseLibrary( _IntuitionBase )
		}

		_GfxBase != 0 {
			CloseLibrary( _GfxBase )
		}

		FontData != 0 {			
			FreeMem( FontData 2048 )
		}


		ENDS


		DSEG



newwin		ds.w	0

		dc.w    0,0,640,200
		dc.b    -1,-1
		dc.l    0
		dc.l    WINDOWDRAG|WINDOWSIZING|SIZEBRIGHT|ACTIVATE|SMART_REFRESH
		dc.l    0,0,0,0,0
		dc.w    100,100,640,400
		dc.w    WBENCHSCREEN


intuiname	dc.b    "intuition.library",0
graphname	dc.b    "graphics.library",0


		END
Other_Disks
.info
08/18/1991 04:00
70
DD0055
04/04/1991 23:00
2147
DD0055
The Complete Amiga Replacement Project

ArpRel3.0
    This is the official AmigaDOS Resource Project (ARP) release 1.3.  This
    release is 99.99% compatible with AmigaDOS release 1.3.  The major
    differences from previous releases of ARP are the NEW Arp Shell (ASH)
    and the installation process.  ASH is usage compatible with the 1.3
    Shell it is not totally compatible with the 1.3 Shell because it uses
    its own command ARES to make commands resident; However, this is not a
    problem.  The new ARP installation program will in stall arp on any
    disk in under five minutes.  Note to new Amigans: ARP makes many    
    improvements to AmigaDOS and makes your system easier to use from the  
    CLI.  If you have AmigaDOS 1.2 or 1.3 you should get ARP.
    
ArpUserDocs3.1
   The documentation for the 3.1 release of Arp which replaces most
   1.3 AmigaDOS commands.  This is the full and complete Users manual.

ArpPro 1.3
   These files contain the programmer documentation and support libraries 
   for use of V1.3 of"arp.library" (library version 39.1).  ARP, the 
   AmigaDOS ResourceProject, is a group effort to provide enhancements to 
   AmigaDOS for users, as well providing a resource for Amiga developers and 
   Commodore to help improve the Amiga's OS software.

ConMan (v1.3.2)
By William S. Hawes
   
   ConMan is a replacement console handler that provides line editing and
   command history for any software that uses CON: windows.  It runs under
   AmigaDOS V1.2 and later, and is completely transparent to other software.
   After ConMan has been activated, all CON: windows opened by AmigaDOS will 
   automatically use the ConMan handler.  This includes the console windows
   opened by NEWCLI as well as any data input/output windows that your other
   software may use.
   
   Features new to ConMan V1.3 include the CND: handler for invisible,
   non-blocking type-ahead, the CNX: (extensible) handler for use of the
   serial device as a console, improved editing of long lines, and support
   for superbitmap windows.  The program also supports many of the 
   features of the ARP.library

DD0055.info
08/18/1991 04:00
2570
FunDisk0006
04/04/1991 23:00
1559
Amiga Developers' Library                                         FunDisk0000

Checkers
    This is a very good version of computer checkers with nice graphics and 
    good sound effects.  It has four difficulty levels, and you can also 
    play against another person.
    
Clue
    This is a one player version of the board game Clue, the computer plays
    the other two to five player.  The amount of intelligence of the 
    computer players is adjustable.
    
DumbBell
    A new Slide the pieces puzzle, this one is fairly simple.
    
Gold
    Another new Slide the pieces puzzle, this one is very challenging
   
Jeopard
    Jeopard is a an enhanced version of Risk for the Amiga, it allows two to 
    eight players.  It has may features the increase the speed of game play,
    and several new twists.  Note: Jeopard requires 1 meg and likes to run 
    in very clean ram, so for your convince this disk will boot and load 
    jeopard.
    
RushHour
    This game is simple in concept, but is surprisingly addicting.  The 
    object of the game is to cover the entire square track, with out 
    running to other car which is trying to hit you.  Note: JoyStick req.
    
SpaceWar
    SpaecWar is best described as a cross between Combat-Tanks and 
    asteroids.  In SpaceWar there are two ships one for each player and
    a planet.  The gravity of the planet is adjustable at the start of 
    the game.  Players score points by blowing the heck out of the other
    guys ship.  Note: Two Joysticks Req.
    
Copyright (C) 1989  DevWare Inc.
FunDisk0006.info
08/18/1991 04:00
854
WB0004
04/04/1991 23:00
2238
                            WBDisk0004

Access v1.42
   A very nice ANSI term program based on Comm v1.34, but with the
   addition of transfer protocols, friendly graphics interface which
   makes it easy to use.  A full script language to control things when
   you are not around.  Supports many screen sizes as well as overscan. 
   Definable Key macros.  Written by Keith Young.

Comm v1.34
   Last version of one of the best public domain communications programs
   ever made on the Amiga.  This version contains a phone directory and
   programmable function keys, as well as the Windowed X-Modem protocol
   for efficient downloading from PeopleLink. 
   Written by Dan James. 

Handshake v2.12a
   Handshake is a Full featured VT52/100/102/220 terminal emulator for 
   those people who really need it. It supports the full VT102 spec (VT102
   is a superset of VT100) and most of the VT220 spec. 
   Written by Eric Haberfellner.

JRComm  v0.93
   XMODEM, XMODEM-1k, WXMODEM, YMODEM, YMODEM-g, ZMODEM, CIS B+ and
   ASCII file transfer protocols are included.  All file transfers
   adhere strictly to the appropriate specifications and provide
   throughput figures exceeding most other communications programs
   available for the Amiga.  A phonebook that can store an almost limitless
   number of directory entries (dependant on available memory).  Each entry
   contains all the options available to completely re-configure JR-Comm, 
   not just name, number and serial port parameters.  Optionaly generate 
   a unique password for each directory entry.  An intelligent dialer that
   monitors the results of each attempt and is capable of multiple entry 
   dialing.  A very powerful file requester that maintains several lists 
   of files, devices and directories.  During a batch protocol selection 
   it enables you to select files from any number of directories in a simple
   manner.  An almost 100% complete IBM ANSI terminal emulation.  Chat mode
   with line editing and history.  Review buffer, function key macros.
   Session capture with filters.  Full Overscan and PAL support added.
   Session log.  Written by John P. Radigan.

Copyright (C) 1989  DevWare Inc.           * -- Includes program source code
WB0004.info
08/18/1991 04:00
1758
WB0012
04/04/1991 23:00
1871
                        WB0012
                     Disk Utilities

DirMaster
The fastest, most comprehensive, most versatile disk cataloguer currently 
available for the Amiga.  Its major features include: SPEED, MEMORY 
EFFICIENCY, EASY TO USE, UNIQUE COMPARE UTILITY, POWERFUL SORT FEATURE, 
AMIGADOS UTILITIES, SIX MAIN DISPLAY, EASY SCROLLING and much much more.

DiskOpti
The purpose of this program is to copy an entire disk in a way which will 
allow the files to be read faster by rearranging the data blocks.

DiskSpeed (v2.0)
This is yet another disk speed testing program, but with a few differences.  
It was designed to give the most accurate results of the true disk 
performance in the system.  For this reason many of DiskSpeed's results may 
look either lower or higher than other current disk performance tests.

Disk Sticker (v1.0)
A program designed to print labels for your Amiga  disks on standard printers 
and tracker feed labels.

FileMap
This little toy is designed to allow you to examine the sector allocation on 
your disks.  Instead of using the DOS to find files, it uses the trackdisk.
device and examines the sectors directly, traversing the filesystem "by hand."

NewZAP (v3.25)
A multi-purpose file sector editing utility. If you've ever had the need to 
alter just a few bytes within a file, examine its binary and ASCII 
representations, or search for key sequences of digits or characters, NewZAP 
will make your hacking life a little bit easier. It does what text editors 
were not meant to do; precise position-oriented object modifications.

Sid (v1.6)
From your workbench move, copy, delete, read, show, edit, arc, run, any 
command, and much much more to any file on your computer.  A great program 
for those of you who don't like using the CLI or for any body who needs a 
general purpose do all file manipulation program.
 
WB0012.info
08/18/1991 04:00
1758
WB0029
04/04/1991 23:00
3947
WB0029
Graphics and Sound


FRACTAL GENERATOR (v1.1)
By Doug Houck
This program grows fractal pictures from seeds you create.  It is 
meant to be a tool for exploring the world of fractals.  It can be
enjoyed on three levels: (1) loading and displaying fractals stored
on disk, (2) modifying existing fractals, and (3) creating your own 
fractals.

  The main idea of this program is very simple.  Take a shape composed
of several line segments, and replace each line segment with a small
copy of the entire shape.  Continue doing this until you reach the
resolution limit of your screen.  For example: (Koch Snowflake)

        /\
Seed   /  \
  ____/    \____

                   __/\__
1st Generation     \    /
               _/\_/    \_/\_


What you have is a self-similar fractal generated in beautiful living color.

MANDELS
This generates the classic mandelbrot set. What is the mandelbrot set?  
The mandelbrot set is a mathematical representation of fraction space. Ok 
Ok you say, fraction space but what is that?  Well what ever that is, it 
does generate some spectacular visual imagery.  This one comes in three 
varieties, a ieee, a fast floating point, and an 881 support.

MandelMountains (v1.1)
By Mathias Ortmann
Discover the Mandelbrot Set From a Completely New Point of View! 
MandelMountains gives you the ability to render wonderful three-dimensional
images  of  blow-ups of the Mandelbrot Set.  The well-known color strips of
the  usual  Mandelbrot  images  become  at once mountain sides that smoothly
climb to high plateaus, leaving deep valleys between them.

You  may  have already seen images of this type (e.g.  on the covers of the
books  "The  Beauty  of  Fractals - Images of Complex Dynamical Systems" by
H.-O.  Peitgen and P.H.  Richter or "The Science of Fractal Images", edited
by H.-O.  Peitgen and D.  Saupe) - here and now you have the tool to create
them  on  your  own!   MandelMountains  allows  you to produce high-quality
non-interlaced  or interlaced (and even overscan) images of arbitrary areas
of the Mandelbrot Set.  You can easily define magnification windows to zoom
deeper and deeper into this fascinating world.

TURBOMANDEL (v 1.0) 
By  Marivoet Philip
Another Mandelbrot set generator. This one is incredibly fast on a 
standard Amiga.  Contains some very nice features.  Source code provided.

Mostra -  A Universal IFF Viewer
By Sebastiano Vigna
In the words of the author "There are many utilities for viewing IFF ILBM 
files, but none I'd seen until now met the goal of displaying every IFF 
picture; each had its idiosyncrasies.  If one viewer could display 
overscan pictures, then every picture with more than 640 pixels on a line 
would be shifted like there were 700 pixels; some programs could only show 
a directory of pictures by forcing the user to enter all the filenames; 
some programs would crash with PAL pictures; others would do the same with
pictures larger than any screen; it was rare to have an option to
force a screen mode (for the tech-folks out there:  old IFF ILBM files
don't have the CAMG chunk!); there were no comfortable file requesters
for use when you didn't know the exact name of the file (who can
remember GRABBiT file names?); pressing the right mouse button could
cause a useless drag bar to corrupt the picture...   If a program had one 
feature, it lacked another, so I decided to write a show utility".

Sound
By Richard Lee Stockton
Sound will attempt to feed 's data to the audio device.
It will 'sound' files containing ANY kind of data, (try 'Sound Sound' :-)
and of ANY length. If you have expansion memory, 'Sound' will store data
in FAST ram, and use only 4-5 k. of CHIP ram to actually sound the data.
This is the magic of 'double-buffering'. Nice job.

Vdraw 
By Stephen Vermeulen
A very well implemented ShareWare Drawing/paint program.  Lots of well 
thought out features.

DynaShow

A dynamic high-res display program.

fd0020
04/04/1991 23:00
2808
                       FD0020
                    Tactical Games

MechForce - Heavy Metal Combat
What is MechForce?  It is a game that simulates combat between two or 
more giant, robot-like machines.  Simple words can't begin to give you 
the feel of piloting a 30 - 40 foot tall, fire breathing, earth 
shaking colossus that obeys your every whim.  To enjoy the game you 
must put yourself in the cockpit of a Combat Mech.  Live the 
experience! 
     You are the elite of the elite - a Mech Warrior.  Your Combat 
Mech thunders under you as you pace across the land, searching for a 
reported enemy mech.  You view the land around you, searching for the 
enemy.  To your left the plain climbs gradually from low hills up to 
high mountains.  To your right is a lake, the calm waters shading from 
light to cobalt blue as the water deepens in the center, with patches 
of treacherous swamp at the edges. Ahead of you the hills meet a 
mixture of light and heavy woods.  You are debating whether to climb 
the hills or fight your way through the trees when the enemy mech 
steps over the crest of the hill.
     Your heart leaps as you recognize a heavy Archer, just as he 
fires one of his massive 20 racks of Long Range Missiles.  Your 
Marauder is staggered by the multiple impacts as you frantically pit 
your piloting skill against 75 tons of overbalanced mech.  You swivel 
your torso and call up your weapons display.  The reassuring green 
lights indicate that all weapons are ready to fire.  You select your 
Auto Cannon 5 and one of your Particle Projection Cannons.  A moment 
later your combat display shows you your field of fire and weapon 
range.  The targeting pipper is blinking on the Archer as you fire 
your weapons up the mountain.
     The crash of your cannon tears chunks of armor from the Archer, 
but the scintillating beam of the Plasma Cannon slashes to the left of 
the Archer. "Too quick" you curse under your breath.  The temperature 
in your cockpit jumps as the heat from firing the Plasma Cannon soaks 
into your mech.  No problem so far, the heat sinks can handle it.  You 
drive your mech into a pounding run.  You've got to get close, his 
LRMs have a minimum effective range, if you can just get inside 
it...
     The Archer is shrouded in smoke as another salvo of missiles 
blast their way toward you.  Missiles clang off your armor, tearing 
chunks away.  Your cockpit rings as one hits the head of your mech.  
You arre empty now, he has to reload. 
     Motion, behind you.  Another Combat Mech breaks from the forest 
and races across the plains toward you.  You quickly identify it as a 
light weight Stinger, ordinarily no threat to a Marauder, but it AND 
an Archer? What to do?  Run?  Fight?  Fight which one?  Time to Rock 
an' Roll.  

This is MechForce! 
fd0020.info
08/18/1991 04:00
2570
wb0029.info
08/18/1991 04:00
2570
wb0038
04/04/1991 23:00
2046
WB38
Plotting and Graphics

Plans
By Gary Hale.
Plans is a high speed, versatile drafting program.  Plans uses a
heirarchical (DOS like) data structure allowing the user to manipulate
low level primitives or higher level objects (including the entire
drawing).  The operations permitted on the directory (object) level
include:  Copy, Move, Delete, Array Angle, Array Grid, Translate, Rotate,
Color, Size (distort), Group and Rename.  In addition the user may set 
the view to include the entire drawing or part.  Very professionally done.

Plasma
By W. Roger Uzun
A graphic hack.  This program produces graphic images that have the 
characteristics of a swirling pool with the colors of a kaleidoscope.  
Very pretty.

PlotXY (v 1.1)
By Robert Mack
PlotXY is a 2-D plotting package that plots X and Y data points 
from a file on several types of graphs.    The user can determine the 
type of graph (i.e. linear, linear-log, log-linear, log-log, and 
histogram), the size of the graph (by input  or interactively), the 
color of the graph and data, the marker type, the line type (although 
there are only 6 pre-defined types), annotation and title, and the 
graph characteristics (i.e. X /Y bounds, major/minor tick marks, grid, 
and overlay option).  Also included are linear  regression analysis 
and polynomial fit analysis.

Tessalator  (v1.0)
By Matt Fruin and Michael McCarty
M.C. Escher is probably best known for his "impossible" pictures, the
ones showing paradoxical buildings and other structures.  But another type
of his pictures fascinates us as well as his impossibilities.  These are his
"continuing series" pictures which regularly divide a plane into the same
picture stamped over and over, sometimes rotated.  The result is a sort of 
mosaic or tesselation, very intricate and intriguing to study.  We've tried
designing a tesselation like his on our own with paper and a pencil and got 
dismal results.  Then we decided to use the Amiga to help us.  The result of
this is Tessalator. Very interesting program, well done.
  
wb0038.info
08/18/1991 04:00
2570
arplibinstal
.info
08/18/1991 04:00
45
ARPLIB3_README
04/04/1991 23:00
4083
*** ARPLIB3.ZOO ******************************************************
Copyright (c) 1989 by ARP Authors.
All Rights Reserved.

This file contains the installation program for V1.3 of "arp.library".
This installation program lets you install "arp.library" for use by
programs which need the ARP library in order to run.

ARP, the AmigaDOS Resource Project, is a group effort to provide
enhancements to AmigaDOS for users, as well providing a resource for
Amiga developers and Commodore to help improve the Amiga's OS software.

This file, ARPLIB3.ZOO is freely redistributable *PROVIDED IT IS
DISTRIBUTED IN IT's ORIGINAL UNMODIFIED FORM*.  Please do not make any
changes to any files which you pass on to others; the user's only
insurance that they have the officially supported version of the ARP
release is in getting the files exactly as released.  For further
information about distribution and support of ARP,  please read the
file "DISCLAIMER", which is included with this distribution.

***********	WHY DO YOU NEED TO INSTALL A "LIBRARY"?	**************

The Amiga has resources called "libraries" which provide services for
software developers to use, making it easier for the developers to
create new software while also providing consistency for the user.

All Amiga software makes use of some libraries, however for the most
part users don't need to know anything about the libraries since they
are built into the system when you turn on your Amiga.

Some libraries are kept on diskette rather than being built into the
machine.  These libraries are kept on your WorkBench diskette (or a
hard disk), in a place called "Libs:".  Commodore provides some
libraries with the standard Amiga WorkBench diskette, such as
"diskfont.library" which lets you use fonts, and "translator.library"
which lets your Amiga talk.

Another disk-based library is "arp.library", which provides many basic
services for programmers.  However, unlike the libraries which are
provided on your WorkBench diskette, "arp.library" is provided
independently and thus in order to use it, you (the user) need to
explicitly put it onto your diskette.

If "arp.library" isn't installed on your diskette, any program which
needs the services provided will not be able to run, usually resulting
in an error message such as "you need arp.library V39+".

***********	HOW TO USE ARPLIBINSTALL FOR "arp.library"     *******

The program "ArpLibInstall" included here will let you do the
installation on your WorkBench diskette, so that applications which
need "arp.library" will be able to run.

In order to use "ArpLibInstall", you can either click on the provided
icon, or run ArpLibInstall from you CLI.  The installation program will
lead you through the steps you need to take to complete installation on
your system.

For users familiar with "ARP", this version of ArpLibInstall will
install the same version of "arp.library" as is installed by V1.3 of
"ArpInstall" provided in the ZOO file "ARPREL3.ZOO".  The ArpLibInstall
program, and the related ZOO file "ARPLIB3.ZOO", have been provided to
simplify use by both developers who want to use "arp.library", and
users who need to get "arp.library", but who do not want the complete
ARP installation.  The smaller ZOO file makes it easier for vendors who
supply files on tele- communications networks such as BIX, Compuserve,
and People Link, to use "arp.library" in their software development.


***********	FOR SOFTWARE DEVELOPERS USING "arp.library"	******

For developers who would like to include "arp.library" with their
software, please see the file "ARPLICENSE" in the programmers support
release "ARPPRO3.ZOO".  The programmers support release "ARPPRO3"
provides all the information developers need to be able to use
"arp.library" in their software, and the file "ARPLICENSE" describes
how developers can include the ARP files for their users while also
helping to insure that Arp Support can provide the best support for
"arp.library", and that users are assured that they have the correct
and most up to date versions of the release software.

ArpLib3_README.info
08/18/1991 04:00
250
ArpLibInstall
04/04/1991 23:00
30448
ArpLibInstall.info
08/18/1991 04:00
1022
Disclaimer
04/04/1991 23:00
956
Disclaimer for ARP

We have put every effort into making the ARP programs work as documented
and perform at least as well as their BCPL counterparts.  However, we are
sure there will be some bugs which may cause some ARP users problems due
to incompatabilities or simply due to program and documentation errors.
We will make every effort to solve such problems in future releases, but
make no warranty as to the fitness for use of any of the programs or
documentation included in the ARP release.

If you would like to print copies of the ARP documentation, you may
print up to 50 copies without explicit permission; please contact
ARP Support if you want to print more than 50 copies.

If you find any problems with ARP programs, we will appreciate if you will
report them to the address below.  Please do not phone Microsmiths for
ARP bug reports.

	ARP Support
	c/o Microsmiths, Inc
	PO Box 561
	Cambridge, MA 02140
	BIX, PLink: cheath  CIS: 76004,1766
bcf77
.info
08/18/1991 04:00
37
bcf
04/05/1991 01:00
272136
bcf77.english.readme
04/30/1991 02:00
15090
bcf77.english.readme.info
08/18/1991 05:00
2570
bcl
04/05/1991 01:00
43604
bcrtsy
04/05/1991 01:00
16464
lies.txt
04/05/1991 01:00
13917
mathlib.b
04/05/1991 01:00
14456
test.f
04/05/1991 01:00
980
      program matmul
c siehe RUS BI 3/88 (Rechenzentrum Uni Stuttgart)
c dort sind Rechenzeiten fr ber 20 Rechner aufgelistet
c z.B. PC/AT02+80287 fr n=100: 133 Sec. REAL, 454 Sec.(!) DOUBLE PRECISION
c mit Option deBugcode=aus ergibt sich REAL 123, DOUBLE PRECISION 199 Sec.
      parameter(n=8)
      dimension f1(n,n),  f2(n,n),  f3(n,n)
c      REAL f1,f2,f3,a,s,p23,p19,p12,p0
      DOUBLE PRECISION f1,f2,f3,a,s,p23,p19,p12,p0
      parameter(p23=2.3,p19=1.9,p12=1.2,p0=0)
c      CALL BCFOSD
       print *,'Matrixmultiplikation, n=',n
        a=p12
        do 1 i=1,n
         do 2 j=1,n
          f1(j,i)=a
          a=a+p23
 2       continue
 1      continue
        do 11 i=1,n
         do 12 j=1,n
          f2(j,i)=a
          a=a+p19
 12      continue
 11     continue
        do 3 i=1,n
        do 3 j=1,n
         s=p0
         do 4 k=1,n
 4        s=s+f1(i,k)*f2(k,j)
        f3(i,j)=s
 3      continue
        write(*,'(f30.14)')f3(n,n)
        stop
        end


.info
08/11/1990 09:00
94
DD0077.info
08/18/1991 03:00
2570
Disk.info
08/18/1991 03:00
3722
Other_Disks.info
08/18/1991 04:00
900
arplibinstal.info
08/18/1991 04:00
900
bcf77.info
08/18/1991 05:00
900
dd0077
04/30/1991 15:00
998
ezasm.info
08/18/1991 04:00
900
iconx
04/04/1991 23:00
3884
readme
04/04/1991 23:00
4062
                    DevWare, Inc.
                            
    DevWare Public Domain Library(c), 1986, 1987, 1988, 1989
                         

This disk contains public domain software collected and
cataloged by DevWare Inc.  Our library is composed of three
different series, Our "DevDisk" series contains tools and
information for the Amiga software developer and
power user (often source code is provided), our "WorkBench"
series is  designed to be of generally interest to all
people, these programs can generally be used from the
WorkBench, our "FunDisk" series is made up of fun and games
programs.  

In many cases individual disk in a series are cataloged 
by theme (fonts, utilities, pacman look alike games...).  
We try till fill each disk to capacity with as many high 
quality programs as are available.  As a company we at 
DevWare are dedicated to providing you, the consumer, with 
quality programs and examples, not quantity; therefore 
our library doesn't have 100's of disks but only a few 
disks packed with high quality programs.

We would like to offer you a caution, as a consumer of public
domain programs several firms exist out there that 
provide only one or two programs per disk and charge full 
price.  There are several firms that produce good high 
quality public domain libraries and also fill their disks full with 
programs.  We suggest that you support these firms.


We have made it easy to tell which series is which; the first 
two letter of disk represent the series, DD# is the 
"DevDisk" series, WB# is the "WorkBench" series, and FD# is 
the "FunDisk" series.

Note:    Most of the files on our "DevDisk" series do not have
icons.  If you are not familiar with the CLI, you will have
difficulty getting at the files from this series.  If you
have not learned CLI yet there is much published information
available to help you learn (it's really not that hard). In
addition to the books published on AmigaDOS and the CLI,
there are numerous articles in magazines like Info,
Antic Amiga Plus or Compute! Amiga Resource.

    Please be aware that our library is generally not on a
bootable Workbench disk--you will need to boot off of your
own Workbench to use the programs on this disk.  We have
done this so that we can pack as much useful stuff on each
disk as possible.

    In addition to maintaining the DevDisk public domain
library, DevWare Inc. also produces the DevWare line of
software products.  To get on our mailing list send a letter
to:

        DevWare Inc.
        PO Box 215
        La Jolla, CA  92038-0215

Also available from DevWare is a disk based catalog, to
order send $2.50 to the above address.  Order our catalog
and receive a coupon for a free disk on your next order.
         
    We are always looking for new software--if you are
interested, please contact us.  We also make pre-duplicated
copies of the Devware library available for sale at users
groups and in computer stores.  We welcome your comments and
criticisms. 

Legal Notice:

    DevWare Inc. makes no representations or warranties
with respect to the contents of this disk and 
specifically disclaims any implied warranties of 
merchantability or fitness for any particular purpose.
To the best of our knowledge, all of the software on this
disk is freely distributable.  Some of the items on this
disk may be "shareware", were the author requests a small
donation from users of the software.  We encourage the
shareware idea and urge you to support these developers in 
their efforts.  


Amiga          is a trademark of Commodore-Amiga, Inc.

This "ReadMe" file, the associated DevWare catalog files,
and the label and format of this disk are Copyrighted (C)
1986, 1987, 1988, 1989 by DevWare Inc. All rights to the
reproduction of these files and this disk in its entirety
are reserved by DevWare Inc.  The individual items of
software on this disk may or may not be copyrighted by 
the authors and have been released into the public domain.  
Some items may contain restrictions regarding their 
distribution.

 
readme.info
08/18/1991 03:00
1794
readthis
04/29/1991 10:00
157
To access the files on this disk you must use a CLI or shell.  
Be sure to check out all of the directories with a CLI, shell or your
favorite disk utility.
readthis.info
08/18/1991 03:00
1794
to_order_software
04/04/1991 23:00
1556
Print this file to order other disks for DevWare,

Current Prices

1-9 disks = 5.95 each
10-24 disks = 4.95 each
25+ disks = 3.95 each
Canadians add $ .15 per blank disk  Non-USA add $ .45 per blank disk
Anti-Virus is free on all orders with over 15 disks


Name ___________________________________________
Address _______________________________________
City ________________________________ ST ______ ZIP__________
Phone #________________________________________


Yes, I would like to order the following DevDisk's:

_______________           _____________        _____________
_______________           _____________        _____________
_______________           _____________        _____________
_______________           _____________        _____________

            Number of Disk ___  X $_____ ea.  = $__________
     California residents add 7.0% sales tax  = $__________
          Foreign orders (add $.50 per disk)  = $__________
  
                                       Total  = $__________
                         

Credit Card users fill out the following:
(Credit card orders require a minimum of $20.00 per order)

Master Card, Visa # _____________________________________
Expiration Date    _____________________________________
Signature          _____________________________________

Send payment to:

                        DevWare, Inc.
                        11258 Kirkham Court
                        Suite 11
                        Poway, CA 92064

Or call:

Orders 800 879-0759   Support 619 679-2825  Fax 619 679-2887

to_order_software.info
08/18/1991 03:00
1758