TweetFollow Us on Twitter

HyperAppleTalk 2
Volume Number:5
Issue Number:2
Column Tag:HyperChat™

Related Info: AppleTalk Mgr

XCMD Corner: HyperAppleTalk, Part II

By Don Koscheka, Aurthur Young & Company, MacTutor Contributing Editor

Last month I introduced access to AppleTalk from HyperCard. Over the next few months I will continue this theme. Adding a multi-user dimension to your stacks should yield some very interesting and exciting results. This month I will introduce the Name Binding Protocol and leave you with a set of XCMDs that implement the more salient features of NBP.

The Basics

First, a quick review of the basics. Sending information across AppleTalk requires two mechanisms: (1) a way of identifying entities on the network so that any two devices can find each other and (2) a “transaction protocol”, some method of sending packets of information between any two entities. AppleTalk implements the first of these mechanism with the Name Binding Protocol (NBP) which serves as a sort of “directory assistance for the network. Several protocols exist for sending information between nodes. One of the earliest is the AppleTalk Transaction Protocol which manages quite well for fixed-size packages. A newer and more sophisticated transaction mechanism has recently been introduced by Apple and is called the AppleTalk Data Stream Protocol (ADSP). This protocol is straightforward and easy to understand, which is why I chose it for this project. If you must have access to the network now, I’ve implemented the ATP protocol which is available in the “HyperAppleTalk” toolkit from Apple. If you want to get a glimpse of the future of easy-to-program networks, I will be discussing ADSP in greater detail next month.

Naming entities on the network is really a courtesy to the user. AppleTalk does not use names to address entities. Each node on the network is assigned a unique address consisting of a network id, a node id and a socket id. These three elements comprise a “phone number” of sorts. AppleTalk identifies entities on the network by the network address. Like the phone system, when you wish to call someone, you pick up the phone and dial that party’s number. With no further intervention (until your party picks up the phone at the other end), the phone system establishes the connection and notifies your party with a ringing telephone.

Because AppleTalk does not care who is at the other end of a connection, identifying a party becomes impossible in all but the smallest of network configurations (n=2). Imagine that your local phone directory contained the phone numbers of everyone in your town, but not the names associated with those phone numbers. From the telephone system’s point of view, the phone book is complete, every phone number is listed in the phone book. From a human interface perspective, a phone book that listed the numbers but not the names would only be useful to if you didn’t care who was at the other end of the line.

The network becomes useful to the end user if some sort of mechanism associates entity names with network addresses. An entity name can be anything you choose. As an example, the chooser dialog allows you to enter a name for your node. Entering a name from the chooser, however, doesn’t mean that your name is automatically registered on the network. In fact, AppleTalk ignores this name; it is simply placed in a globally accessible “STR “ resource (-16906) and made available to any application that wants to know it. You cannot register the name until you receive an address from the network (Imagine that you are applying for a new phone number from Ma Bell. Once the phone number is assigned, the operator will ask you how you want to be registered in the phone book).

Last Month

Last month’s column provided a lot of nebulous code in the form of ADSPOpen and NBPOpen. Presenting this material resulted in a bit of a chicken and egg problem. I wanted to introduce NBP first because you already understand it in another form - directory assistance. In order to use NBP, you need a network address (if you were to look someone up in the phone book and not find a phone number next to their name, you might tend to believe that the phone book is not very useful except as a spelling checker). Thus, I needed to present just enough of the transaction side of the equation to cajole an address out of the network. If you compile last month’s code and run it on a system that has ADSP installed, about all you will get for your troubles is the address of a connection listener.

When we invoked adspOpen, we first initialized some records that will be used by our network code. Pointers are indicated because HyperCard is fussy about the state of its heap. Our network code executes asynchronously. This technique allows us to get some semblance of background networking out of the system. In effect, we issue a request to send some information on the network and then go away. When the network can, it will send our information and then notify us when the dialog completes, allowing us to move on without waiting for the communication to complete (which can take a long time on the network).

Memory can’t be moving around on us because we have no idea when our information will actually be looked at by the network. Normally, allocating our data in handles and then locking down those handles during a dialog would suffice. But, as the saying goes, “HyperCard abhors a locked handle” and will unceremonioulsy unlock it if it needs to fix up its heap (once you get the hang of this in XCMD programming you begin to appreciate the beauty of it). This poses no problem since we can force our data not to move by allocating non-relocatable memory in pointers. This is not inconsistent with Inside Macintosh, and it allows us to leave HyperCard’s heap in the state that it expects to find it (HyperCard is quite effective at handling pointers always pushing them to the bottom of the heap).

Registering

After allocating and initializing the data, we ask the network to consider us as a node by telling the network manager that we are capable of listening and responding to connection requests from another entity. This is just like hooking up a telephone in your house. Once the phone is installed and the phone company gives you a phone number, anytime the phone rings, you have a good idea that someone is trying to call you. A connection listener performs the same task, notifying us when another party calls. For the moment, let’s leave the phone ringing and get back to the matter of how we identify parties on the line.

If you’ve ever applied for a telephone number you know the phone company will give you a number and then ask how you want to be listed. NBP provides just this feature on the network. Once you get your network address, you want to tell the network what name you can be reached by. This is why we do the adspopen before the nbpopen. First we apply for a phone number; if we get it we list our name in the phone book using the NBPRegister call to AppleTalk.

The first element in the record tells us whether we are registered or not. If we are, then we probably don’t need to register again (would registering under several aliases serve any purpose?) NTEntry is of type NamesTableEntry, a special AppleTalk type that glues names to addresses (figure 1). To register an entity with the network, we must place both its internet address (in this case obtained from last month’s ADSPOpen XFCN) as well as the name into the names table entry.

A registered name consists of three parts: (1) zone, (2) name and (3) a type. For now, the zone name is always “*” (we’ll relax this constraint when we introduce the concept of inter network addressing in a future article). The name can be anything but most likely you will use the name already entered in the “User Name” edit box in the chooser.

This is a matter of personal choice and need. Your code might first check the chooser for a name and , if no name is found, then ask the user directly for a name. This HyperTalk script will register the entity using the name in the chooser and setting the type to “HyperPeople”:

--1

on MouseUp
 global myRegisteredType, myRegisteredName
 
 Put NBPRegisterName() into errorMessage

 if errorMessage is empty then
 -- myRegisteredName now contains the same name
 -- as is entered in the chooser
 else
 -- report error to user 
 end if
end MouseUp

The type is quite important. We don’t want to send HyperCard messages to entities that are not capable of understanding them so we apply a filter to names: communicate only with entities that are registered as a given type. This makes sense, if you have two entities on the network simultaneously playing chess and checkers you don’t want the messages to get crossed (kings, for example, have dramatically different powers in both games). I feel the type is important, so if the user (your stack) doesn’t choose one, I set the default to “HyperPeople”. This is a type that is capable of reading any HyperCard message whether it makes sense or not!

The rest is pretty easy to figure out. If you know the address of an entity then it should be an easy task to provide that address along with a name and a type to some xcmd that registers that name with the network. NBPRegisterName (Listing 1) does just that. The code is quite straightforward.

The flow of information from node to node in a computer network is governed by the underlying physics of the network. Appletalk’s physics may beset be described as a case of organized chaos. I like to think of it as a “mobocratic” system, run by mob rule. While any two entities are passing information between themselves, all other entities must wait for the transaction to complete. The moment the transaction completes, the next entity to get its request on the wire is the winner. It may take several tries to be the next entity on the wire. The network’s dynamics govern the number of retries and the time interval between retries; the busier the network, the more you’ll have to wait. When you attempt to register with the net, you want to make sure that every entity has an opportunity to update their local copy of the phone book at the time you register. To make sure as many nodes as possible see you register, you specify a retry count. This is just like repeating yourself to a large gathering in hopes that more of the crowd will hear you. Interval specifies the time to wait between retries. The unit time is the “decatick”. There are sixty ticks per second so an interval of 6 specifies a waiting period of one second.

The last parameter that we pass to NBPRegisterName is the verify flag. If set true we want the name verified at registration time. Verification is another convenience item. If any node is already registered with that name, you won’t be able to register. The error message is quite explicit so you may wish to ask the user for another name. It’s okay to have duplicate names registered, although this can lead to some confusion. Just as when you look up a Smith in the phone book, “Now which Smith is it that I want to call?”

NBPUnRegisterName (listing 2) removes the registered name from the network. This is useful if, for example, you want to register under a new name. The following Script will invoke NBPUnRegisterName:

--2

on mouseUp
  global myRegisteredname, myRegisteredType
  
  Put NbpUnRegisterName()into error
  if error is not empty then put error
end mouseUp

Once registered with the network, other entities can see us and send connection requests to us (next month). To be able to see other entities, we need some method of looking up other parties in some sort of directory.

NBPLookupnames (Listing 3) returns a list of the network entities currently visible to us. This is exactly like requesting a phone book from the phone company, except that you will always get the very latest copy. One word of note: the latest copy of the directory may not contain ALL entities on the network, just those that happened to be visible and responded to the update request at the time that the look up was issued.

NBPLookupNames issues a request to find all entities on the network. This function becomes more useful when we limit the process to only entities of a certain type. Since we are really only interested in finding entities that speak HyperTalk, we can filter our request to find only entities of type ‘Hyperpeople’ (or whatever type you register).

The lookup uses three of the fields in the NBPBlock structure that we introduced last month. EntCount is set to the number of entities that the function actually saw (initially set to zero indicating that no lookup has been performed). We place an upper limit of 100 (maxnodes) entities on the lookup. You can tune this constant to suit the individual needs of your network.

LookupBuffer is a handle to the list of visible entities. You’ll use NBPExtractName to pull entities out of the list. NBPLocal is used internally by NBP itself. You provide this buffer to NBP and leave it alone. NBP wants that space and doesn’t want us fussing with it. So we don’t.

Once the lookup completes, LookupBuffer contains a handle to the entities that were found on the network. The internal structure of the lookup table is somewhat complicated by the intermixing of names and their addresses. To help in extracting information from the table.

This is by no means an exhaustive list of all the capabilities of NBP; but since such a list would truly be exhausting, I’ve intentionally left some of the NBP routines out of the picture. For the sake of completeness, we will cover these routines as we go ahead with the project. Next month we will introduce the AppleTalk Data Stream Protocol and provide a stack example that uses these routines.

The data declarations used in these modules are defined in Listing 4. You should refer to last month’s article for information on opening a connection listener.

--------------------------------------------
(**************************************)
(* file:  NBPRegisterName.p *)
(* *)
(* Register a name with the *)
(* network...    *)
(* *)
(* Requires that GlobalNBPData be  *)
(* initialized and that the global *)
(* myRegisteredName be defined     *)
(* --------------------------------*)
(* © 1988, Donald Koscheka*)
(* 10-November, 1988 *)
(* All Rights Reserved    *)
(* *)
(**************************************)

(*******************************
 MPW Build Sequence
 
pascal NBPRegisterName.p -o NBPRegisterName.p.o
link -m ENTRYPOINT  -rt XFCN=2003 -sn Main=NBPRegisterName
 NBPRegisterName.p.o
 “{libraries}”Interface.o 
 -o YourStackNameHere

*******************************)

{$R-}
{$S NBPRegisterName}

UNIT Donald_Koscheka;

(*******************************)
 INTERFACE
(*******************************)

Uses  
 MemTypes, QuickDraw, OSIntf,
 ToolIntf, PackIntf, HyperXCmd, 
 AppleTalk, nbpxcmd;

Procedure EntryPoint( paramPtr : XCmdPtr );


(*******************************)
 IMPLEMENTATION
(*******************************)

 
PROCEDURE NBPRegisterName( paramPtr: XCmdPtr ); FORWARD;

Procedure EntryPoint( paramPtr : XCmdPtr );
Begin
 NBPRegisterName( paramPtr );
End;

PROCEDURE NBPRegisterName( paramPtr: XCmdPtr );
(**********************************
* Register this entity on the network
* using the name and type specified.
*
* Set the globalvariable, ‘myRegisteredName’
* to the name that was registered. Note
* that NBPOpen must be called before
* attempting to register.
*
* params[1] theName
* Params[2] theType
* params[3] count
* params[4] interval
* params[5] verifyFlag
*
* The type is in the global myRegisteredType
* ----------------------------------
*
* defaults are: 
*name = (from chooser)
*type = ‘HyperPeople’
*count  = 2
*interval= 8
*verify = false;
*
* NOTE: will not register if a socket
* is not open on this node!
**********************************)
VAR
nbp: NBPBlkPtr;  {*** our global nbp data    ***}
theName: Str255; {*** name to register ***}
theType: Str255; {*** type for this node     ***}
theZone: Str255; {*** always ‘*’(zone name)  ***}
str: Str255;{*** used in getting globs ***}
myName: Handle;  {*** used for chooser name  ***}
tempH: Handle; {*** used in getting globs    ***} 
count: Byte;{*** number of retries ***}
interval: Byte;  {*** wait between retires   ***}
verify: Byte;  {*** name must be unique***}
error: OSErr;  {*** result code    ***}
i,j: INTEGER;  {*** pascal string length     ***}
Mpb: MPPParamBlock;{*** param block  ***}

{$I XCMDGlue.Inc }

BEGIN
 error := noErr; 
 nbp  := NIL; 
 
 {*** Retrieve pointer to our NBPData***}
 tempH := GetGlobal( ‘GLOBALNBPDATA’ );
 
 {*** Convert the string to a handle ***}
 IF (tempH <> NIL) THEN
 BEGIN
 HLock( tempH );
 ZeroToPas( tempH^, Str );
 nbp := NBPBlkPtr( StrToLong( Str ));
 HUnlock( tempH );
 DisposHandle( tempH );
 END;

 IF ( nbp <> NIL ) AND ( NOT nbp^.Registered ) THEN
 BEGIN
 
 {*** Before registering, we need  ***}
 {*** the internet address stored in ***}
 {*** string form in a container   ***}
 tempH := GetGlobal( ‘mySocketListener’ );
 
 {*** Convert the string to a network***}
 {*** address (longinteger) ***}
 IF ( tempH <> NIL ) THEN
 BEGIN
 HLock( tempH );
 ZeroToPas( tempH^, Str );
 nbp^.NTEntry.nteAddress:= AddrBlock(StrToLong(Str));
 HUnlock( tempH );
 DisposHandle( tempH );
 END; 
 
 nbp^.NTEntry.qLink := NIL; 
 
 WITH ParamPtr^ DO
 BEGIN
 {*** If  user specifies a name  ***}
 {*** we’ll use it, otherwise use  ***}
 {*** the name in the Chooser ***}
 IF ( params[1] = nil ) OR (params[1]^^ = 0) THEN
 BEGIN  {*** Get name from chooser ***}
 myName := GetResource( ‘STR ‘, NODE_NAME );
 
 IF myName <> NIL THEN
 BlockMove( myName^, @theName[0],
 GetHandleSize( myName ) );
 END
 ELSE
 BEGIN  {*** Use name passed in  ***}
 HLock( params[1] );
 ZeroToPas( params[1]^, theName );
 HUnlock( params[1] );
 END;
 
 {*** IF the user provides a type  ***}
 {*** use it otherwise, use the  ***}
 {*** default type ***}
 IF (params[2] = nil) OR (params[2]^^ = 0) THEN
 theType := ‘HyperPeople’
 ELSE
 BEGIN
 HLock( params[2] );
 ZeroToPas( params[2]^, theType );
 HUnlock( params[2] );
 END;

 {*** AppleTalk, Zone Name must    ***}
 {*** be ‘*’ (this zone)  ***}
 theZone := ‘*’;
 
 {*** Put the name away in the***}
 {*** entity data part of the names***}
 {*** table entry.  Inside Macintosh ***}
 {*** vol II p.321 (figure 13) depicts ***}
 {*** the structure of a names table ***}
 {*** element.  Note that the first  ***}
 {*** byte in the nteData array is used***}
 {*** internally.  We put the chars***}
 {*** away starting at array offset 2***}
 
 i := 2;
 
 FOR j := 0 TO Length( theName ) DO  
 BEGIN
 nbp^.NTEntry.nteData[i] := theName[j];
 i := i + 1;
 END;
 
 {*** The type gets tacked to the  ***}
 {*** end of the names string. This***}
 {*** is not the same as the concat***}
 {*** function, each string keeps  ***}
 {*** its length byte.    ***}
 
 FOR j := 0 TO Length( theType ) DO  
 BEGIN
 nbp^.NTEntry.nteData[i] := TheType[j];
 i := i + 1;
 END;

 {*** Likewise, theZone gets tacked***}
 {*** to the end of the type string***}
 FOR j := 0 TO Length( theZone ) DO  
 BEGIN
 nbp^.NTEntry.nteData[i] := TheZone[j];
 i := i + 1;
 END;
 
 {*** Number of times to register  ***}
 IF params[3] <> NIL THEN
 BEGIN
 HLock( params[3] );
 ZeroToPas( params[3]^, str );
 count := INTEGER( StrToLong( Str ));
 HUnlock( Params[3] );
 END
 ELSE
 count := 2;
 
 {*** 10X ticks between requests ***}
 IF params[4] <> NIL THEN
 BEGIN
 HLock( params[4] );
 ZeroToPas( params[4]^, str );
 interval := INTEGER( StrToLong( Str ));
 HUnlock( Params[4] );
 END
 ELSE
 Interval := 8;  
 
 {*** If the last parameter is true***}
 {*** make sure that the  name is  ***}
 {*** not already in use  ***}
 IF params[5] <> NIL THEN
 BEGIN
 HLock( params[5] );
 ZeroToPas( params[5]^, str );
 verify  := BYTE(strToNum( str ));
 HUnlock( Params[5] );
 END
 ELSE
 verify := 0;
 END; 
 
 {*** Now set up an make the call  ***}
 {*** to register this enitity***}
 Mpb.ioCompletion:= NIL;  
 Mpb.interval    := interval;
 Mpb.count:= count;
 Mpb.entityPtr   := @nbp^.NTEntry;
 Mpb.verifyFlag  := verify;

 error := PRegisterName( @Mpb, SYNC);
 
 IF error = noErr THEN
 BEGIN
 paramPtr^.returnValue := PasToZero( ‘’ );
 {*** As a courtesy to the system, ***}
 {*** save name off in a global    ***}
 {*** this is an easy way to get   ***}
 {*** name from the chooser ***}
 nbp^.Registered := TRUE;
 SetGlobal( ‘MyRegisteredName’,PasToZero(theName));
 END
 ELSE
 paramPtr^.returnValue:=PasToZero(numToStr(longint(error)));
 
 END;
END;

END.

Listing 1. NBPRegisterName

--------------------------------------------
(********************************)
(*file: NBPUnRegisterName.p *)
(* *)
(* Remove name from the network  *)
(* if that name if currently  *)
(* registered.   *)
(* *)
(* Requires GlobalNBPData be*)
(* initialized and that global*)
(* myRegisteredName be defined   *)
(* ----------------------------  *)
(* © 1988, Donald Koscheka*)
(* 8-December, 1988*)
(* All Rights Reserved    *)
(* *)
(********************************)

(*******************************
 MPW Build Sequence
 
pascal NBPUnRegisterName.p -o NBPUnRegisterName.p.o
link -m ENTRYPOINT  -rt XFCN=2004 -sn Main=NBPUnRegisterName
 NBPUnRegisterName.p.o
 “{libraries}”Interface.o 
 -o yourStackNameHere

*******************************)

{$R-}
{$S NBPUnRegisterName}

UNIT Donald_Koscheka;

(*******************************)
 INTERFACE
(*******************************)

Uses  
 MemTypes, QuickDraw, OSIntf,
 ToolIntf, PackIntf, HyperXCmd, 
 AppleTalk, nbpxcmd;


Procedure EntryPoint( paramPtr : XCmdPtr );

(*******************************)
 IMPLEMENTATION
(*******************************)
 
PROCEDURE NBPUnRegisterName( paramPtr: XCmdPtr ); FORWARD;

Procedure EntryPoint( paramPtr : XCmdPtr );
Begin
 NBPUnRegisterName( paramPtr );
End;

PROCEDURE NBPUnRegisterName( paramPtr: XCmdPtr );
(**********************************
* UnRegister this entity on the network
* using the information already contained
* in the NBP data block.  
*
* Upon successful completion, clear the
* global variable, ‘myRegisteredName’ and
* set the state of the “Registered” flag
* for this connection to FALSE.
* ----------------------------------
**********************************)
VAR
nbp: NBPBlkPtr;  {*** our global nbp data    ***}
tempH: Handle; {*** used in getting globs    ***} 
error: OSErr;  {*** result code    ***}
Mpb: MPPParamBlock;{*** param block  ***}
Str: Str255;
 
{$I XCMDGlue.Inc }

BEGIN
 error := noErr; 
 nbp  := NIL; 
 
 {*** Retrieve pointer to our NBPData***}
 tempH := GetGlobal( ‘GLOBALNBPDATA’ );
 
 {*** Convert the string to a handle ***}
 IF (tempH <> NIL) THEN
 BEGIN
 HLock( tempH );
 ZeroToPas( tempH^, Str );
 nbp := NBPBlkPtr( StrToLong( Str ));
 HUnlock( tempH );
 DisposHandle( tempH );
 END;

 IF ( nbp <> NIL ) AND ( nbp^.Registered ) THEN
 BEGIN
 Mpb.ioCompletion:= NIL;  
 Mpb.entityPtr   := @nbp^.NTEntry.nteData[2];
 error := PRemoveName( @Mpb, SYNC);
 
 IF error = noErr THEN
 BEGIN
 paramPtr^.returnValue := PasToZero( ‘’ );
 {*** As a courtesy to the system, ***}
 {*** save name off in a global    ***}
 {*** this is an easy way to get   ***}
 {*** name from the chooser ***}
 nbp^.Registered := FALSE;
 SetGlobal( ‘MyRegisteredName’, PasToZero( ‘’ ) );
 END
 ELSE
 paramPtr^.returnValue := 
 PasToZero(numToStr(longint(error)));

 END;

END.

Listing 2. NBPUnRegisterName

--------------------------------------------
(********************************)
(* file:  NBPLookup.p*)
(* *)
(* params[1] = theType    *)
(* params[2] = theZone    *)
(* params[3] = number to look up*)
(* params[4] = count *)
(* params[5] = interval   *)
(* *)
(* Entity names are returned*)
(* in a list and sent to the  *)
(* HyperCard global: *)
(* ‘NBPLookUpTable’*)
(* *)
(* ReturnValue is set to the*) 
(* result of the lookup   *)
(* *)
(* ----------------------------  *)
(* Defaults:*)
(* *)
(* name = ‘=’ ( All names)*)
(* type = ‘=’ ( all types ) *)
(* zone = ‘*’ (current zone)*)
(* num  = 100 ( 100 names)  *)
(* count= 2   ( do 3 lookups) *)
(* interval= 4( decaticks)*)
(* *)
(* ----------------------------  *)
(* © 1988, Donald Koscheka*)
(* All Rights Reserved    *)
(* *)
(* 05-Nov-88*)
(* ----------------------------  *)
(********************************)

(*******************************
 MPW Build Sequence
 
pascal NBPLookupNames.p -o NBPLookupNames.p.o
link -m ENTRYPOINT  -rt XFCN=2005 -sn Main=NBPLookupNames
 NBPLookupNames.p.o
 “{libraries}”Interface.o 
 “{plibraries}”PasLib.o 
 -o yourStackNameHere

*******************************)

{$R-}
{$S NBPLookupNames}

UNIT Donald_Koscheka;

(*******************************)
 INTERFACE
(*******************************)

Uses  
 MemTypes, QuickDraw, OSIntf,
 ToolIntf, PackIntf, HyperXCmd, 
 AppleTalk, nbpxcmd;

Procedure EntryPoint( paramPtr : XCmdPtr );

(*******************************)
 IMPLEMENTATION
(*******************************)

CONST
 DEFAULT_ERR= 128; {*** some sort of mem error     ***}

TYPE
 Str255Ptr= ^Str255;
 
PROCEDURE NBPLookupNames( paramPtr: XCmdPtr ); FORWARD;

Procedure EntryPoint( paramPtr : XCmdPtr );
Begin
 NBPLookupNames( paramPtr );
End;

PROCEDURE NBPLookupNames( paramPtr: XCmdPtr );
(**********************
* Lookup  entities of the 
* requested type and zone
* (up to num elements):
*
**********************)
VAR
 tempH  : Handle;
 nbp    : NBPBlkPtr;
 EntSize  : LongInt;
 i,j,cnt, err,
 intr, total,
 num    : INTEGER;
 str    : Str255;
 ent    : NamesTableEntry;
 Mpb    : MPPParamBlock;
 theType,
 theZone: Str255;
 
{$I XCMDGlue.Inc }

 FUNCTION ReturnNames: Handle;
 (*****************************
 * Return a list of entities as
 * found in the lookup table
 *
 *****************************)
 VAR
 eAddr  : AddrBlock; {*** Needed by the extract    ***}
 newHand: Handle;{*** current entity name&typ      ***}
 theTable: Handle; {*** Lookup Data to return            ***}
 ret  : String[1]; {*** newline after each ent     ***}
 oldSize: LongInt; {*** Previous size of table     ***}
 newSize: LongInt; {*** size to add to table       ***}
 i : INTEGER;  {*** loop control variable          ***}
 theEnt : EntityName;{*** names from the names table     ***}
 
 BEGIN
 oldSize  := 1;
 theTable := NewHandle( oldSize );
 
 IF theTable <> NIL THEN
 BEGIN
 theTable^^ := 0;{*** set theTable to EMPTY***}
 ret[0] := CHR( 1 );
 ret[1] := CHR( 13);
 
 FOR i := 1 TO nbp^.EntCount DO
 BEGIN
 {*** extract name i from the list ***}
 WITH nbp^ DO
 BEGIN
 HLock( LookUpBuffer );
 err := NBPExtract( LookUpBuffer^, 
 total, i, theEnt, eAddr);
 HUnlock( LookUpBuffer );
 END;
 
 IF err = noErr THEN
 BEGIN
 {*** each line in the list gets   ***}
 {*** entities name and type***}
 Str := ‘’;

 Str := Concat( theEnt.objStr, 
 ‘,’,theEnt.typeStr,ret);
 newHand:= PasToZero( Str );
 newSize:=GetHandleSize(newHand);
 oldSize:=GetHandleSize(theTable);
 SetHandleSize(theTable,newSize+oldSize);
 BlockMove(newHand^,
    Ptr(ORD(theTable^)+oldSize-1),
    NewSize);
 DisposHandle( newHand );
 END; 
 END; {*** FOR i := 1 to Total ***}
 
 {*** make sure  return string is null ***}
 {*** terminated or hypercard will have***}
 {*** a fit ***}
 END; {*** IF theTable <> NIL ***}
 ReturnNames := theTable;
 END;
 
BEGIN
 err := noErr;
 
 {*** Retrieve pointer to our NBPData***}
 tempH := GetGlobal( ‘GLOBALNBPDATA’ );
 
 {*** Convert the string to a handle ***}
 IF (tempH <> NIL) THEN
 BEGIN
 HLock( tempH );
 ZeroToPas( tempH^, Str );
 nbp := NBPBlkPtr( StrToLong( Str ));
 HUnlock( tempH );
 DisposHandle( tempH );
 END;

 IF ( nbp <> NIL ) THEN {*** okay to lookup ***}
 BEGIN
 WITH paramPtr^ DO
 BEGIN
 IF params[1] = NIL THEN
 theType := ‘=’
 ELSE 
 BEGIN
 HLock( params[1] );
 ZeroToPas( params[1]^, theType );
 HUnlock( params[1] );
 END;
 
 IF params[2] = NIL THEN
 theZone := ‘*’
 ELSE
 BEGIN
 HLock( params[2] );
 ZeroToPas( params[2]^, theZone );
 HUnlock( params[2] );
 END;
 
 IF params[3] <> NIL THEN
 BEGIN
 HLock( params[3] );
 ZeroToPas( params[3]^, Str );
 num := INTEGER(StrToNum( Str ) );
 HUnlock( params[3] );
 END
 ELSE
 num := MAXNODES;
 
 IF params[4] <> NIL THEN
 BEGIN
 HLock( params[4] );
 ZeroToPas( params[4]^, Str );
 cnt := INTEGER(StrToNum( Str ) );
 HUnlock( params[4] );
 END
 ELSE
 cnt := 2;
 
 IF params[5] <> NIL THEN
 BEGIN
 HLock( params[5] );
 ZeroToPas( params[5]^, Str );
 intr := INTEGER( StrToNum( Str ) );
 HUnlock( params[5] );
 END
 ELSE
 intr := 4; 
 END; {*** with paramPtr^ ***}
 
 {*** Concatenate the name, type and zone string   ***}
 ent.nteData[2] := CHR(1);
 ent.nteData[3] := ‘=’;
 i := 4;
 
 FOR j := 0 TO Length( theType ) DO  
 BEGIN
 ent.nteData[i] := TheType[j];
 i := i + 1;
 END;

 {*** Likewise, theZone gets tacked***}
 {*** to the end of the type string***}
 FOR j := 0 TO Length( theZone ) DO  
 BEGIN
 ent.nteData[i] := TheZone[j];
 i := i + 1;
 END;

 {*** The lookup data is stored as a handle in     ***}
 {*** our NBPBlock. Since a new lookup supercedes***}
 {*** the previous data, delete previous (if any)***}
 IF nbp^.LookupBuffer <> NIL THEN
 BEGIN
 HUnlock( nbp^.LookUpBuffer );
 DisposHandle( nbp^.LookUpBuffer );
 END;
 
 nbp^.EntCount := 0;
 EntSize:= sizeof( NamesTableEntry );
 nbp^.LookUpBuffer:= NewHandle( num *  EntSize );

 IF nbp^.LookUpBuffer <> NIL THEN
 BEGIN
 MoveHHi( nbp^.LookUpBuffer );
 HLock( nbp^.LookUpBuffer );
 
 WITH mpb DO
 BEGIN
 EntityPtr:= @ent.nteData[2];
 retBuffPtr := nbp^.LookUpBuffer^;
 retBuffSize   := INTEGER( EntSize*num );
 maxToGet := num;
 interval := intr;
 count  := cnt;
 END; {*** with mpb ***}  
 err  := PLookUpName( @Mpb, SYNC );
 
 IF err = noErr THEN
 BEGIN
 nbp^.EntCount := Mpb.numGotten;
 SetGlobal(‘NBPLookupTable’,ReturnNames );
 paramPtr^.returnValue := PasToZero( ‘’ );
 END
 ELSE
 paramPtr^.returnValue := 
 PasToZero(numToStr(longint(err)));
 
 HUnlock( nbp^.LookUpBuffer );
 END
 ELSE
 err := DEFAULT_ERR; {*** no room in the heap? ***}
 END;
END;
END.

Listing 3. NBPLookUpNames

--------------------------------------------
(********************************)
(* file:  NBPXCMD.p*)
(* *)
(* Constant and type declaration*)
(* file for nbp xcmds*)
(* ----------------------------  *)
(* © Donald Koscheka *)
(* 6-October, 1988 *)
(* All Rights Reserved    *)
(* *)
(* -------------------------- *)
(********************************)

UNIT  NBPXCMD;

(*******************************)
 INTERFACE
(*******************************)

USES  Memtypes, QuickDraw, OSIntf, ToolIntf, AppleTalk;

CONST

ASYNC   = TRUE;
SYNC    = FALSE;
NODE_NAME = -16096;(* STR resource name from Chooser     *)
MAXNODES= 100;   (* maximum # of nodes for  zone   *)
NBPLSIZE= 120;   (* size of a local buffer for NBP *)
NN = 30;(* # of names in lookup table*)
ENTITYSIZE= 110; (* size of entity in lookupbuffer *)

TYPE

Str31 = String[31];

NBPBlkPtr = ^NBPBlock;
NBPBlock = RECORD
Registered: BOOLEAN; (* true = registered          *)
EntCount: INTEGER; (* # of entities visible        *)
LookUpBuffer: Handle;(* lookup buffer*)
NTEntry : NamesTableEntry;(* entry in names table  *)
NBPLocal: array[1..NBPLSIZE] of Char;(* used by NBP      *)
END;
END.

Listing 4. Definitions needed for the XFCNs

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

 

Community Search:
MacTech Search:

Software Updates via MacUpdate

coconutBattery 3.9.14 - Displays info ab...
With coconutBattery you're always aware of your current battery health. It shows you live information about your battery such as how often it was charged and how is the current maximum capacity in... Read more
Keynote 13.2 - Apple's presentation...
Easily create gorgeous presentations with the all-new Keynote, featuring powerful yet easy-to-use tools and dazzling effects that will make you a very hard act to follow. The Theme Chooser lets you... Read more
Apple Pages 13.2 - Apple's word pro...
Apple Pages is a powerful word processor that gives you everything you need to create documents that look beautiful. And read beautifully. It lets you work seamlessly between Mac and iOS devices, and... Read more
Numbers 13.2 - Apple's spreadsheet...
With Apple Numbers, sophisticated spreadsheets are just the start. The whole sheet is your canvas. Just add dramatic interactive charts, tables, and images that paint a revealing picture of your data... Read more
Ableton Live 11.3.11 - Record music usin...
Ableton Live lets you create and record music on your Mac. Use digital instruments, pre-recorded sounds, and sampled loops to arrange, produce, and perform your music like never before. Ableton Live... Read more
Affinity Photo 2.2.0 - Digital editing f...
Affinity Photo - redefines the boundaries for professional photo editing software for the Mac. With a meticulous focus on workflow it offers sophisticated tools for enhancing, editing and retouching... Read more
SpamSieve 3.0 - Robust spam filter for m...
SpamSieve is a robust spam filter for major email clients that uses powerful Bayesian spam filtering. SpamSieve understands what your spam looks like in order to block it all, but also learns what... Read more
WhatsApp 2.2338.12 - Desktop client for...
WhatsApp is the desktop client for WhatsApp Messenger, a cross-platform mobile messaging app which allows you to exchange messages without having to pay for SMS. WhatsApp Messenger is available for... Read more
Fantastical 3.8.2 - Create calendar even...
Fantastical is the Mac calendar you'll actually enjoy using. Creating an event with Fantastical is quick, easy, and fun: Open Fantastical with a single click or keystroke Type in your event details... Read more
iShowU Instant 1.4.14 - Full-featured sc...
iShowU Instant gives you real-time screen recording like you've never seen before! It is the fastest, most feature-filled real-time screen capture tool from shinywhitebox yet. All of the features you... Read more

Latest Forum Discussions

See All

The iPhone 15 Episode – The TouchArcade...
After a 3 week hiatus The TouchArcade Show returns with another action-packed episode! Well, maybe not so much “action-packed" as it is “packed with talk about the iPhone 15 Pro". Eli, being in a time zone 3 hours ahead of me, as well as being smart... | Read more »
TouchArcade Game of the Week: ‘DERE Veng...
Developer Appsir Games have been putting out genre-defying titles on mobile (and other platforms) for a number of years now, and this week marks the release of their magnum opus DERE Vengeance which has been many years in the making. In fact, if the... | Read more »
SwitchArcade Round-Up: Reviews Featuring...
Hello gentle readers, and welcome to the SwitchArcade Round-Up for September 22nd, 2023. I’ve had a good night’s sleep, and though my body aches down to the last bit of sinew and meat, I’m at least thinking straight again. We’ve got a lot to look at... | Read more »
TGS 2023: Level-5 Celebrates 25 Years Wi...
Back when I first started covering the Tokyo Game Show for TouchArcade, prolific RPG producer Level-5 could always be counted on for a fairly big booth with a blend of mobile and console games on offer. At recent shows, the company’s presence has... | Read more »
TGS 2023: ‘Final Fantasy’ & ‘Dragon...
Square Enix usually has one of the bigger, more attention-grabbing booths at the Tokyo Game Show, and this year was no different in that sense. The line-ups to play pretty much anything there were among the lengthiest of the show, and there were... | Read more »
Valve Says To Not Expect a Faster Steam...
With the big 20% off discount for the Steam Deck available to celebrate Steam’s 20th anniversary, Valve had a good presence at TGS 2023 with interviews and more. | Read more »
‘Honkai Impact 3rd Part 2’ Revealed at T...
At TGS 2023, HoYoverse had a big presence with new trailers for the usual suspects, but I didn’t expect a big announcement for Honkai Impact 3rd (Free). | Read more »
‘Junkworld’ Is Out Now As This Week’s Ne...
Epic post-apocalyptic tower-defense experience Junkworld () from Ironhide Games is out now on Apple Arcade worldwide. We’ve been covering it for a while now, and even through its soft launches before, but it has returned as an Apple Arcade... | Read more »
Motorsport legends NASCAR announce an up...
NASCAR often gets a bad reputation outside of America, but there is a certain charm to it with its close side-by-side action and its focus on pure speed, but it never managed to really massively break out internationally. Now, there's a chance... | Read more »
Skullgirls Mobile Version 6.0 Update Rel...
I’ve been covering Marie’s upcoming release from Hidden Variable in Skullgirls Mobile (Free) for a while now across the announcement, gameplay | Read more »

Price Scanner via MacPrices.net

New low price: 13″ M2 MacBook Pro for $1049,...
Amazon has the Space Gray 13″ MacBook Pro with an Apple M2 CPU and 256GB of storage in stock and on sale today for $250 off MSRP. Their price is the lowest we’ve seen for this configuration from any... Read more
Apple AirPods 2 with USB-C now in stock and o...
Amazon has Apple’s 2023 AirPods Pro with USB-C now in stock and on sale for $199.99 including free shipping. Their price is $50 off MSRP, and it’s currently the lowest price available for new AirPods... Read more
New low prices: Apple’s 15″ M2 MacBook Airs w...
Amazon has 15″ MacBook Airs with M2 CPUs and 512GB of storage in stock and on sale for $1249 shipped. That’s $250 off Apple’s MSRP, and it’s the lowest price available for these M2-powered MacBook... Read more
New low price: Clearance 16″ Apple MacBook Pr...
B&H Photo has clearance 16″ M1 Max MacBook Pros, 10-core CPU/32-core GPU/1TB SSD/Space Gray or Silver, in stock today for $2399 including free 1-2 day delivery to most US addresses. Their price... Read more
Switch to Red Pocket Mobile and get a new iPh...
Red Pocket Mobile has new Apple iPhone 15 and 15 Pro models on sale for $300 off MSRP when you switch and open up a new line of service. Red Pocket Mobile is a nationwide service using all the major... Read more
Apple continues to offer a $350 discount on 2...
Apple has Studio Display models available in their Certified Refurbished store for up to $350 off MSRP. Each display comes with Apple’s one-year warranty, with new glass and a case, and ships free.... Read more
Apple’s 16-inch MacBook Pros with M2 Pro CPUs...
Amazon is offering a $250 discount on new Apple 16-inch M2 Pro MacBook Pros for a limited time. Their prices are currently the lowest available for these models from any Apple retailer: – 16″ MacBook... Read more
Closeout Sale: Apple Watch Ultra with Green A...
Adorama haș the Apple Watch Ultra with a Green Alpine Loop on clearance sale for $699 including free shipping. Their price is $100 off original MSRP, and it’s the lowest price we’ve seen for an Apple... Read more
Use this promo code at Verizon to take $150 o...
Verizon is offering a $150 discount on cellular-capable Apple Watch Series 9 and Ultra 2 models for a limited time. Use code WATCH150 at checkout to take advantage of this offer. The fine print: “Up... Read more
New low price: Apple’s 10th generation iPads...
B&H Photo has the 10th generation 64GB WiFi iPad (Blue and Silver colors) in stock and on sale for $379 for a limited time. B&H’s price is $70 off Apple’s MSRP, and it’s the lowest price... Read more

Jobs Board

Optometrist- *Apple* Valley, CA- Target Opt...
Optometrist- Apple Valley, CA- Target Optical Date: Sep 23, 2023 Brand: Target Optical Location: Apple Valley, CA, US, 92308 **Requisition ID:** 796045 At Target Read more
Senior *Apple* iOS CNO Developer (Onsite) -...
…Offense and Defense Experts (CODEX) is in need of smart, motivated and self-driven Apple iOS CNO Developers to join our team to solve real-time cyber challenges. Read more
*Apple* Systems Administrator - JAMF - Activ...
…**Public Trust/Other Required:** None **Job Family:** Systems Administration **Skills:** Apple Platforms,Computer Servers,Jamf Pro **Experience:** 3 + years of Read more
Child Care Teacher - Glenda Drive/ *Apple* V...
Child Care Teacher - Glenda Drive/ Apple ValleyTeacher Share by Email Share on LinkedIn Share on Twitter Share on Facebook Apply Read more
Machine Operator 4 - *Apple* 2nd Shift - Bon...
Machine Operator 4 - Apple 2nd ShiftApply now " Apply now + Start apply with LinkedIn + Apply Now Start + Please wait Date:Sep 22, 2023 Location: Swedesboro, NJ, US, Read more
All contents are Copyright 1984-2011 by Xplain Corporation. All rights reserved. Theme designed by Icreon.