-- File: NetworkBindingClient.mesa - last edit:
-- AOF                  2-Sep-87  9:32:00
-- kam                 23-Jun-86 15:24:38

-- Copyright (C) 1986, 1987 by Xerox Corporation. All rights reserved.

DIRECTORY
  ByteBlt USING [ByteBlt],
  Courier USING [
    Description, DeserializeParameters, NoteSize, NotesObject,
    SerializeParameters],
  CourierProtocol USING [ExchWords, Protocol3Body],
  Driver USING [Glitch],
  Environment USING [Block, bytesPerWord],
  Heap USING [systemZone],
  Inline USING [LongCOPY],
  MemoryStream USING [Create, IndexOutOfRange],
  NetworkBinding USING [
    defaultHops, NoBinding, nullPredicate, Predicate, PredicateRecord,
    RemoteProgram, Responses, ResponseSequence, DataTooLarge],
  NetworkBindingInternal USING [
    CallMessage, ClientInfo, fixedBytesInLocateCall, Hosts, HostsSubList,
    InitialHostsList, initialLocateStartIndex, initialLocateStopIndex,
    ReturnMessage, SetSequenceLength, ThreeCardinals],
  NetworkBindingProtocol USING [
    ClientInfo, clientType, clientVersionHigh, clientVersionLow, HostsRecord,
    maxHostsPerLocate, Procedure, program, socket, Cookie, baseWaitTime,
    timePerHop],
  NSBuffer USING [Body, Buffer],
  NSTypes USING [
    ExchangeClientType, ExchangeID, maxDataBytesPerExchange],
  Process USING [
    Detach, DisableTimeout, EnableAborts, InitializeCondition,
    SecondsToTicks, SetTimeout, Ticks],
  QuickSort USING [CompareProc, Sort, SwapProc],
  Router USING [
    endEnumeration, EnumerateRoutingTable, FillRoutingTable,
    FindMyHostID, GetDelayToNet, NoTableEntryForNet, startEnumeration],
  Socket USING [
    ChannelHandle, Create, Delete, GetPacket, GetSendBuffer, PutPacket,
    ReturnBuffer, SetPacketBytes, SetWaitTime, SocketNumber, TimeOut],
  Stream USING [Handle],
  System USING [
    broadcastHostNumber, GetClockPulses, HostNumber, NetworkAddress,
    NetworkNumber, nullHostNumber, nullNetworkNumber, nullSocketNumber,
    SocketNumber];

NetworkBindingClient: MONITOR
  IMPORTS
    ByteBlt, Courier, CourierProtocol, Driver, Heap, Inline, MemoryStream,
    NetworkBinding, NetworkBindingInternal, Process, QuickSort, Router,
    Socket, System
  EXPORTS NetworkBinding, NetworkBindingInternal =
  BEGIN

  Bug: ERROR = CODE;  --for glithes
  allocateAdjustment: NATURAL = 30;
  versionAdjustmentAllowed: BOOLEAN ← TRUE;
  bpw: NATURAL = Environment.bytesPerWord;
  myZone: UNCOUNTED ZONE = Heap.systemZone;

  RecursionData: TYPE = RECORD[
    sH: Socket.ChannelHandle, reqB: NSBuffer.Buffer,
    userData: Environment.Block, zone: UNCOUNTED ZONE,
    responseDescription: Courier.Description,
    size, length, maxHostList: NATURAL,
    isback: BOOLEAN, requeued: CONDITION];

  Request: TYPE = LONG POINTER TO RequestObject;
  RequestObject: TYPE = RECORD[
    sH: Socket.ChannelHandle,
    objective: {takeFirst, takeAll, exit, dally} ← takeFirst,
    b: NSBuffer.Buffer ← NIL, condition: CONDITION];

  broadcastingCount: NATURAL = 3;
  me: System.HostNumber = Router.FindMyHostID[];
  null: System.HostNumber = System.nullHostNumber;
  all: System.HostNumber = System.broadcastHostNumber;

  Sizer: PROC[h: LONG POINTER TO RecursionData] =
    BEGIN
    BailOut: PRIVATE ERROR = CODE;  --in a local frame yet
    SizeTrapper: Courier.NoteSize = {h.size ← h.size + size; ERROR BailOut};
    notes: Courier.NotesObject ← [
      zone: h.zone, operation: free, noteSize: SizeTrapper,
      noteLongCardinal: NIL, noteLongInteger: NIL, noteParameters: NIL,
      noteChoice: NIL, noteDeadSpace: NIL, noteString: NIL, noteSpace: NIL,
      noteArrayDescriptor: NIL, noteDisjointData: NIL, noteBlock: NIL];
    IF h.responseDescription # NIL THEN
      h.responseDescription[@notes ! BailOut => CONTINUE];  --sleeeeeze
    END;  --Sizer

  AppendResponse: PROC[
    data: LONG POINTER TO RecursionData, b: NSBuffer.Buffer,
    responses: LONG POINTER TO NetworkBinding.Responses] =
    BEGIN
    reply: LONG POINTER;
    element: LONG POINTER TO ElementObject;
    ElementObject: TYPE = RECORD[
      responder: System.NetworkAddress, response: ARRAY[0..0) OF WORD];
    length: NATURAL = IF responses↑ = NIL THEN 0 ELSE responses↑.elementCount;

    IF data.length < length THEN Driver.Glitch[Bug];

    IF data.length = length THEN
      BEGIN
      a3: NetworkBinding.Responses;
      data.length ← data.length + allocateAdjustment;
      a3 ← data.zone.NEW[
        NetworkBinding.ResponseSequence[data.size * data.length] ← [
	  elementSize: data.size, elementCount: length, element: ]];
      IF responses↑ # NIL THEN
        Inline.LongCOPY[
	  to: @a3[0], from: @responses↑[0],
	  nwords: data.size * length];
      data.zone.FREE[responses]; responses↑ ← a3;
      END;
    responses↑.elementCount ← SUCC[length];  --we're adding one
    element ← LOOPHOLE[@responses[0] + data.size * length];
    [element.responder, reply] ← ExtractResponse[
      b, data.responseDescription, myZone];

    IF reply # NIL THEN
      BEGIN
      Inline.LongCOPY[to: @element.response, from: reply, nwords: data.size];
      myZone.FREE[@reply];  --then get rid of that
      END;

    END;  --AppendResponse


  BindToAllNearby: PUBLIC <<NetworkBindingInternal>> PROC[
    predicate: NetworkBinding.PredicateRecord ← NetworkBinding.nullPredicate,
    responseDescription: Courier.Description ← NIL,
    maxHops: CARDINAL ← NetworkBinding.defaultHops,
    zone: UNCOUNTED ZONE ← NIL]
    RETURNS [responses: NetworkBinding.Responses ← NIL] =
    BEGIN
    <<
    Use this with descretion.  Don't (and I mean DON'T) ask for every workstation
    within a radius of 16 hops.  Probably you not should use this procedure with
    'maxHops' greater than 3 or 4.
    The result will be returned as a concatenation of answers that would have
    been returned with successive calls to BindToAllOnNet using a expanding
    ring broadcast (i.e., sorted by hop-count--processorid).
    >>
    Concat: PROC[append: NetworkBinding.Responses] =
      BEGIN
      l1, l2, s1, s2: NATURAL;
      a3: NetworkBinding.Responses;
      SELECT TRUE FROM
	(responses = NIL) AND (append = NIL) => RETURN;  --real simple
	(responses = NIL) AND (append # NIL) => a3 ← append;  --some simpler
	(responses # NIL) AND (append = NIL) => a3 ← responses;  --almost as easy
	ENDCASE =>  --but this is hard and mostly UGLY!
	  BEGIN
	  l1 ← responses.elementCount; l2 ← append.elementCount;
	  s1 ← l1 * responses.elementSize; s2 ← l2 * append.elementSize;
	  a3 ← zone.NEW[NetworkBinding.ResponseSequence[l1 + l2] ← [
	    elementSize: append.elementSize, elementCount: l1 + l2, element:]];
	  IF l1 # 0 THEN
	    Inline.LongCOPY[to: @a3[0], from: @responses[0], nwords: s1];
	  IF l2 # 0 THEN
	    Inline.LongCOPY[to: @a3[0] + s1, from: @append[0], nwords: s2];
	  zone.FREE[@responses]; zone.FREE[@append];  --gun the old versions
	  END; 
      responses ← a3; append ← NIL;  --and the result of our efforts
      END;  --Concat

    processCount: NATURAL;  --number of parallel processes we are using
    filled: BOOLEAN ← FALSE;  --keep track of whether we loaded router
    net: System.NetworkNumber;  --and this is a network of current interest
    ProcessLimit: TYPE = NATURAL[0..10);  --number of parallel processes to use
    process: ARRAY ProcessLimit OF Binders ← ALL[NIL];  --working data base
    Binders: TYPE = PROCESS RETURNS[NetworkBinding.Responses];

    IF zone = NIL THEN zone ← myZone;

    FOR delay: NATURAL IN[0..maxHops) DO
      IF delay = 1 THEN {Router.FillRoutingTable[maxHops]; filled ← TRUE};
      net ← Router.startEnumeration;  --set initial value
      processCount ← 0;  --initialize number of processes we have
      --FOR each net with hops = delay-- DO
	net ← Router.EnumerateRoutingTable[net, delay];
	SELECT TRUE FROM
	  (net = Router.endEnumeration) =>  --this is end of this ring
	    BEGIN
	    FOR i: NATURAL IN[0..processCount) DO
	      Concat[JOIN process[i]];  --append answer to list
	      processCount ← PRED[processCount];  --and manage the count
	      ENDLOOP;
	    GOTO exitRing;  --finished with this ring, go to next delay value
	    END;
	  ((processCount ← SUCC[processCount]) = LAST[ProcessLimit]) =>
	    BEGIN
	    temp: NetworkBinding.Responses ← BindToAllOnNet[
	      predicate, responseDescription, net, zone];
	    processCount ← PRED[processCount];  --last one isn't in the list
	    FOR i: NATURAL IN[0..processCount) DO
	      Concat[JOIN process[i]]; process[i] ← NIL; ENDLOOP;
	    Concat[temp];  --it really is logically last
	    processCount ← 0;  --reset counter
	    END;
	  ENDCASE =>
	    process[processCount - 1] ← FORK BindToAllOnNet[
	      predicate, responseDescription, net, zone];
	REPEAT exitRing => NULL;  --just going to next layer of expanding ring
        ENDLOOP;
      ENDLOOP;
    IF filled THEN Router.FillRoutingTable[0];  --close down routing table
    END;  --BindToAllNearby
     
  BindToFirstOnNet: PUBLIC <<NetworkBinding>> PROC[
    predicate: NetworkBinding.PredicateRecord ← NetworkBinding.nullPredicate,
    responseDescription: Courier.Description ← NIL,
    net: System.NetworkNumber ← System.nullNetworkNumber,
    zone: UNCOUNTED ZONE ← NIL]
    RETURNS [responder: System.NetworkAddress, response: LONG POINTER] =
  --REPORTS ERROR NoBinding;
    BEGIN

    RequeueProc: ENTRY PROC[b: NSBuffer.Buffer] = {reqB ← b; NOTIFY requeued};
    DequeueProc: ENTRY PROC[] = {UNTIL reqB # NIL DO WAIT requeued; ENDLOOP};
    WaitAnswer: ENTRY PROC[] = {ENABLE UNWIND => NULL; WAIT request.condition};

    requeued: CONDITION;
    reqBody: NSBuffer.Body;
    reqB: NSBuffer.Buffer ← NIL;
    broadcastTimout: LONG CARDINAL;
    broadcastingInterval: Process.Ticks;

    request: Request ← myZone.NEW[RequestObject ← [
      sH: Socket.Create[socket: System.nullSocketNumber, receive: 1]]];

    [broadcastTimout, broadcastingInterval] ← ComputeIntervals[net];
    Socket.SetWaitTime[request.sH, broadcastTimout];  --how long socket'll wait
    Process.SetTimeout[@request.condition, broadcastingInterval];
    Process.EnableAborts[@request.condition];  --so we can be gunned

    reqBody ← (reqB ← BuildLocateRequest[
      request.sH, predicate, responseDescription].b).ns;
    reqBody.destination ← [
      net, System.broadcastHostNumber, NetworkBindingProtocol.socket];
    reqB.requeueProcedure ← RequeueProc;

    Process.Detach[FORK ReportFirstResponse[request, reqBody.exchangeID]];

    THROUGH[0..broadcastingCount) UNTIL request.b # NIL DO
      ENABLE UNWIND => request.objective ← dally;
      b: NSBuffer.Buffer ← reqB;  --get copy of the buffer
      reqB ← NIL;  --make less local copy NIL
      Socket.PutPacket[request.sH, b];  --transmit
      DequeueProc[];  --wait for buffer to get back 
      WaitAnswer[];  --wait some appropriate time | notification
      IF reqB = NIL THEN Driver.Glitch[Bug];  --this just can't happen!
      ENDLOOP;

    Socket.ReturnBuffer[reqB];  --get rid of our buffer
    request.objective ← dally;  --tell process to self-destruct later

    IF request.b = NIL THEN RETURN WITH ERROR NetworkBinding.NoBinding;
    RETURN ExtractResponse[request.b, responseDescription, zone];
    END;  --BindToFirstOnNet
  
  BindToFirstNearby: PUBLIC <<NetworkBinding>> PROC[
    predicate: NetworkBinding.PredicateRecord ← NetworkBinding.nullPredicate,
    responseDescription: Courier.Description ← NIL,
    maxHops: CARDINAL ← NetworkBinding.defaultHops,
    zone: UNCOUNTED ZONE ← NIL]
    RETURNS [responder: System.NetworkAddress, response: LONG POINTER] =
  --REPORTS ERROR NoBinding;
    BEGIN

    RequeueProc: ENTRY PROC[b: NSBuffer.Buffer] = {reqB ← b; NOTIFY requeued};
    DequeueProc: ENTRY PROC[] = {UNTIL reqB # NIL DO WAIT requeued; ENDLOOP};
    WaitAnswer: ENTRY PROC[] = {ENABLE UNWIND => NULL; WAIT request.condition};

    requeued: CONDITION;
    reqBody: NSBuffer.Body;
    filled: BOOLEAN ← FALSE;
    net: System.NetworkNumber;
    reqB: NSBuffer.Buffer ← NIL;
    broadcastTimout: LONG CARDINAL;
    broadcastingInterval: Process.Ticks;

    request: Request ← myZone.NEW[RequestObject ← [
      sH: Socket.Create[socket: System.nullSocketNumber, receive: 1]]];

    Process.EnableAborts[@request.condition];  --so we can be gunned

    reqBody ← (reqB ← BuildLocateRequest[
      request.sH, predicate, responseDescription].b).ns;
    reqB.requeueProcedure ← RequeueProc;

    Process.Detach[FORK ReportFirstResponse[request, reqBody.exchangeID]];

    FOR delay: NATURAL IN[0..maxHops) WHILE request.b = NIL DO
      IF delay = 1 THEN {Router.FillRoutingTable[maxHops]; filled ← TRUE};
      net ← Router.startEnumeration;  --set initial value
      --FOR each net with hops = delay-- DO
	net ← Router.EnumerateRoutingTable[net, delay];
	IF net = Router.endEnumeration THEN EXIT;  --go to next delay
	reqBody.destination ← [
	  net, System.broadcastHostNumber, NetworkBindingProtocol.socket];
	[broadcastTimout, broadcastingInterval] ← ComputeIntervals[net];
	Socket.SetWaitTime[request.sH, broadcastTimout];
	Process.SetTimeout[@request.condition, broadcastingInterval];
	THROUGH[0..broadcastingCount) DO
	  ENABLE UNWIND => request.objective ← dally;
	  b: NSBuffer.Buffer ← reqB;  --get copy of the buffer
	  reqB ← NIL;  --make less local copy NIL
	  Socket.PutPacket[request.sH, b];  --transmit
	  DequeueProc[];  --wait for buffer to get back 
	  ENDLOOP;
	ENDLOOP;  --enumerate routing table
      WaitAnswer[];  --wait some appropriate time | notification
      ENDLOOP;  --for each hop

    Socket.ReturnBuffer[reqB];  --get rid of our buffer
    request.objective ← dally;  --tell process to self-destruct later
    IF filled THEN Router.FillRoutingTable[0];  --close down routing table

    IF request.b = NIL THEN RETURN WITH ERROR NetworkBinding.NoBinding;
    RETURN ExtractResponse[request.b, responseDescription, zone];
    
    END;  --BindToFirstNearby
  
  BindToAllOnNet: PUBLIC <<NetworkBinding>> PROC[
    predicate: NetworkBinding.PredicateRecord ← NetworkBinding.nullPredicate,
    responseDescription: Courier.Description ← NIL,
    net: System.NetworkNumber ← System.nullNetworkNumber,
    zone: UNCOUNTED ZONE ← NIL]
    RETURNS [responses: NetworkBinding.Responses ← NIL] =
  --REPORTS ERROR NoBinding;
    BEGIN
    <<
    Try to locate all the hosts that meet the predicate specified.  Since there
    would be too many responses to the question posed in the large, then we're
    going to break the field into smaller, more managable groups.
    >>
    b: NSBuffer.Buffer;
    userData: Environment.Block;
    broadcastTimout: LONG CARDINAL;
    data: LONG POINTER TO RecursionData;
    list: NetworkBindingInternal.HostsSubList;
    initialList: NetworkBindingInternal.InitialHostsList ← [];

    IF zone = NIL THEN zone ← myZone;  --default the value
    data ← zone.NEW[RecursionData];  --allocate the recursion record
    data.length ← 0;  --there's no data yet
    data.size ← SIZE[System.NetworkAddress];  --this plus client's length
    data.sH ← Socket.Create[socket: System.nullSocketNumber, receive: 20];
    [b, userData] ← BuildLocateRequest[data.sH, predicate, responseDescription];
    data.reqB ← b; data.userData ← userData; data.zone ← zone;
    data.maxHostList ← MaxListSize[userData];  --max list we can handle
    data.responseDescription ← responseDescription;  --he needs that
    Process.InitializeCondition[@data.requeued, 0];
    Process.DisableTimeout[@data.requeued];
    
    [broadcastTimout, ] ← ComputeIntervals[net];  --only need one of the two
    Socket.SetWaitTime[data.sH, broadcastTimout];  --how long socket'll wait
    b.ns.destination ← [
      net, System.broadcastHostNumber, NetworkBindingProtocol.socket];
    list ← [LOOPHOLE[LONG[@initialList]], 0, 2];
    Sizer[data];  --find out the client's size

    BEGIN
    Freeup: PROC =
      BEGIN
      Socket.ReturnBuffer[b];  --don't dripple those buffers around
      Socket.Delete[data.sH];  --don't have to wait 'cause it already timed out
      zone.FREE[@data];  --get rid of primary data structure
      END;  --Freeup

    Recurse[data, list, @responses !  --go do it
      UNWIND => Freeup[]];  --uncase we get blown away
    SortAndPrune[@responses, data];  --then clean them up
    Freeup[];  --and delete if we don't
    END;
    END;  --BindToAllOnNet

  ExtractResponse: PROC[
    b: NSBuffer.Buffer, how: Courier.Description, zone: UNCOUNTED ZONE]
    RETURNS[responder: System.NetworkAddress, response: LONG POINTER ← NIL] =
    BEGIN

    Describe: Courier.Description =
      {notes.noteDisjointData[notes.noteSize[SIZE[LONG POINTER]], how]};

    body: NSBuffer.Body ← b.ns;  --shorten route to interesting data

    return: NetworkBindingInternal.ReturnMessage = LOOPHOLE[@body.exchangeBody];
    IF zone = NIL THEN zone ← myZone;
    IF (how # NIL) AND (return.body.response.length # 0) THEN
      BEGIN
      sH: Stream.Handle = MemoryStream.Create[[
	LOOPHOLE[@return.body.response],
	SIZE[NetworkBindingProtocol.Cookie[0]] * bpw,
	SIZE[NetworkBindingProtocol.Cookie[return.body.response.length]] * bpw]];
      Courier.DeserializeParameters[[@response, Describe], sH, zone !
	UNWIND => {sH.delete[sH]; Socket.ReturnBuffer[b]}];
      sH.delete[sH];  --get rid of memory stream
      END;
    responder ← [  --make complete network address out of response and packet
      body.source.net, return.body.responder, System.nullSocketNumber];
    Socket.ReturnBuffer[b];  --give buffer back
    END;  --ExtractResponse

  VerifyBinding:  PUBLIC <<NetworkBinding>> PROC[
    predicate: NetworkBinding.PredicateRecord ← NetworkBinding.nullPredicate,
    responseDescription: Courier.Description ← NIL, host: System.NetworkAddress,
    zone: UNCOUNTED ZONE ← NIL] RETURNS[response: LONG POINTER ← NIL] =
    BEGIN

    RequeueProc: ENTRY PROC[b: NSBuffer.Buffer] = {reqB ← b; NOTIFY requeued};
    DequeueProc: ENTRY PROC = INLINE {UNTIL reqB # NIL DO WAIT requeued; ENDLOOP};
    EnqueueProc: PROC RETURNS[b: NSBuffer.Buffer] = INLINE {b ← reqB; reqB ← NIL};

    requeued: CONDITION;
    nobinding: BOOLEAN ← TRUE;
    requestTimout: LONG CARDINAL;
    reqBody, repBody: NSBuffer.Body;
    reqB, replyB: NSBuffer.Buffer ← NIL;
    return: NetworkBindingInternal.ReturnMessage;
    sH: Socket.ChannelHandle = Socket.Create[System.nullSocketNumber];

    [requestTimout, ] ← ComputeIntervals[host.net];
    Socket.SetWaitTime[sH, requestTimout];  --how long socket'll wait

    reqBody ← (reqB ← BuildLocateRequest[
      sH, predicate, responseDescription].b).ns;
    reqB.requeueProcedure ← RequeueProc;  --set up requeue
    host.socket ← NetworkBindingProtocol.socket;  --assign our wellknown socket
    reqBody.destination ← host;  --only talking to single machine

    THROUGH[0..broadcastingCount) DO
      ENABLE
        BEGIN
	Socket.TimeOut => CONTINUE;  --stays in loop but resends packet
	UNWIND => Socket.ReturnBuffer[reqB];  --client aborted GetPacket?
	END;
      Socket.PutPacket[sH, EnqueueProc[]];  --send out the request packet
      DequeueProc[];  --this procedure is not abortable, but it's fast
      repBody ← (replyB ← Socket.GetPacket[sH]).ns;  --try for an answer
      return ← LOOPHOLE[@repBody.exchangeBody];
      nobinding ← SELECT TRUE FROM
        (repBody.packetType # packetExchange) => TRUE,  --error packet?
        (repBody.exchangeID # reqBody.exchangeID) => TRUE,  --not us
	(return.courierVers # [3, 3]) => TRUE,  --can't talk his language
	(return.return.type # return) => TRUE,  --don't understand
	ENDCASE => FALSE;  --success comes to those that wait
      IF nobinding THEN Socket.ReturnBuffer[replyB] --ExtractResponse frees 'b'
      ELSE response ← ExtractResponse[replyB, responseDescription, zone].response;
      EXIT;  --and we exit the loop in any case
      ENDLOOP;

    Socket.ReturnBuffer[reqB];  --give back the request buffer
    Socket.Delete[sH];  --get rid of the socket
    IF nobinding THEN RETURN WITH ERROR NetworkBinding.NoBinding; 
    END;  --VerifyBinding

  VersionAdjustmentAllowed: PUBLIC <<NetworkBindingInternal>> PROC[
    allowed: BOOLEAN ← TRUE] = {versionAdjustmentAllowed ← allowed};
  
  BuildLocateRequest: PROC[
    cH: Socket.ChannelHandle,
    predicate: NetworkBinding.PredicateRecord,
    responseDescription: Courier.Description]
    RETURNS[b: NSBuffer.Buffer, userData: Environment.Block] =
    BEGIN
    <<
    Compute the maximum space needed to hold the predicate.  What's left over
    is available to store the HOSTS list.  When we put in the that list, BLT
    the predicate to butt up against its tail.  If the HOSTS list is too large,
    break it up.  The predicate has to go in this packet.
    >>

    sH: Stream.Handle;
    body: NSBuffer.Body;
    clientInfo: NetworkBindingInternal.ClientInfo;
    locate: NetworkBindingInternal.CallMessage;
    callMessage: call CourierProtocol.Protocol3Body = [call[
      transaction: 0,
      program: CourierProtocol.ExchWords[NetworkBindingProtocol.program],
      version: GetProtocolVersion[responseDescription = NIL],
      procedure: NetworkBindingProtocol.Procedure[locate].ORD]];
    body ← (b ← Socket.GetSendBuffer[cH]).ns;  --everybody wants one of these
    body.packetType ← packetExchange;  --anyhow we look like one
    body.exchangeID ← LOOPHOLE[System.GetClockPulses[]];
    body.exchangeType ← NetworkBindingProtocol.clientType;

    locate ← LOOPHOLE[@body.exchangeBody];
    locate.courierVers ← [3, 3];
    locate.call ← callMessage;
    locate.body.hosts[0] ← null;
    locate.body.hosts[1] ← all;
    NetworkBindingInternal.SetSequenceLength[@locate.body.hosts, 2];

    clientInfo ← @locate.body.clientInfo +  --using two sequences in one record
      SIZE[NetworkBindingProtocol.HostsRecord[2]] -  --that Mesa doesn't like
      SIZE[NetworkBindingProtocol.HostsRecord[0]];  -- us to do
    clientInfo.remoteProgram ← [
      CourierProtocol.ExchWords[
        predicate.pred.program.programNumber], predicate.pred.program.version];
    clientInfo.conjunct ← [CourierProtocol.ExchWords[predicate.pred.conjunct]];

    userData ← [blockPointer: LOOPHOLE[clientInfo],
      startIndex: NetworkBindingInternal.initialLocateStartIndex,
      stopIndexPlusOne: NetworkBindingInternal.initialLocateStopIndex];

    IF predicate.param.description # NIL THEN
      BEGIN
      DescribeParam: Courier.Description = {notes.noteDisjointData[
	notes.noteSize[SIZE[LONG POINTER]], predicate.param.description]};
      sH ← MemoryStream.Create[userData];  --set up stream for serialize
      Courier.SerializeParameters[  --move param directly into packet
	[@predicate.param.location, DescribeParam], sH !
	MemoryStream.IndexOutOfRange => GOTO badParam];  --too many bytes
      userData.stopIndexPlusOne ← CARDINAL[sH.getPosition[sH]];
      sH.delete[sH];  --the delete the stream
      END
    ELSE userData.stopIndexPlusOne ← userData.startIndex;  --just the length

    NetworkBindingInternal.SetSequenceLength[
      @clientInfo.param, (userData.stopIndexPlusOne - userData.startIndex) / bpw];
  
    Socket.SetPacketBytes[b,
      NetworkBindingInternal.fixedBytesInLocateCall +
      (SIZE[NetworkBindingProtocol.HostsRecord[2]] * bpw) +
      (SIZE[NetworkBindingProtocol.Cookie[clientInfo.param.length]] * bpw)];

    userData.startIndex ← 0;  --data between start and stop has to be moved

    EXITS badParam => RETURN WITH ERROR NetworkBinding.DataTooLarge;

    END;  --BuildLocateRequest

  ComputeIntervals: PROC[net: System.NetworkNumber] RETURNS[
      broadcastTimout: LONG CARDINAL, broadcastingInterval: Process.Ticks] =
    BEGIN
    --broadcastTimout is in milliseconds
    --broadcastingInterval is in Ticks
    hops: NATURAL ← 6;  --just a guess
    hops ← Router.GetDelayToNet[net ! Router.NoTableEntryForNet => CONTINUE];
    broadcastTimout ← (NetworkBindingProtocol.baseWaitTime +
      (NetworkBindingProtocol.timePerHop * hops));
    broadcastingInterval ← Process.SecondsToTicks[CARDINAL[broadcastTimout/250]];
    broadcastTimout ← broadcastTimout;
    END;

  GetProtocolVersion: PROC[nilResponse: BOOLEAN] RETURNS[NATURAL] = INLINE
    {RETURN[
      IF nilResponse AND versionAdjustmentAllowed THEN
        NetworkBindingProtocol.clientVersionLow
      ELSE NetworkBindingProtocol.clientVersionHigh]};

  ReportFirstResponse: <<DETACHED>> PROC[
    request: Request, exchangeID: NSTypes.ExchangeID] =
    BEGIN
    RecordAnswerAndNotify: ENTRY PROC[] = INLINE
      BEGIN
      request.b ← repB;  --record packet containing answer
      NOTIFY request.condition;  --notify process waiting
      END;  --RecordAnswerAndNotify
    return: NetworkBindingInternal.ReturnMessage;
    body: NSBuffer.Body;
    repB: NSBuffer.Buffer;
    UNTIL request.objective = exit DO
      ENABLE Socket.TimeOut =>
        IF request.objective = dally THEN EXIT ELSE CONTINUE;
      body ← (repB ← Socket.GetPacket[request.sH]).ns;
      return ← LOOPHOLE[@body.exchangeBody];
      SELECT TRUE FROM
        (request.objective = dally) => NULL;  --just marking time
        (body.exchangeID # exchangeID) => NULL;  --not for us
	(return.courierVers # [3, 3]) => NULL;  --busted
	(return.return.type # return) => NULL;  --only interested in success
        (request.b = NIL) => {RecordAnswerAndNotify[]; LOOP};
	ENDCASE;
      Socket.ReturnBuffer[repB];  --give buffer back
      ENDLOOP;
    Socket.Delete[request.sH];  --he created, we delete
    myZone.FREE[@request];  --he created, we delete
    END;  --ReportFirstResponse

  RippleExpand: PROC[
    b: NSBuffer.Buffer, answer: NetworkBindingInternal.Hosts,
    userData: Environment.Block, current: NATURAL]
    RETURNS[to: Environment.Block] =
    BEGIN
    body: NSBuffer.Body = b.ns;
    ripple: INTEGER = bpw *
      (SIZE[NetworkBindingProtocol.HostsRecord[current]] -
      SIZE[NetworkBindingProtocol.HostsRecord[2]]) -
      userData.startIndex;  --more relative where it is now
    locate: NetworkBindingInternal.CallMessage = LOOPHOLE[@body.exchangeBody];
    clientInfo: NetworkBindingInternal.ClientInfo = @locate.body.clientInfo +
      SIZE[NetworkBindingProtocol.HostsRecord[current]] -
      SIZE[NetworkBindingProtocol.HostsRecord[0]];
    <<
    Possibly expand the packet.  Move the 'userData' out just beyond
    the space that the current 'answer' will occupy.  There should be
    no danger in doing that as long as the current length of 'answer'
    is less than the maximum number we computed.  And always copy the
    current answer into to packet.
    >>
    to ← [
      blockPointer: userData.blockPointer,
      startIndex: CARDINAL[userData.startIndex + ripple],
      stopIndexPlusOne: CARDINAL[userData.stopIndexPlusOne + ripple]];
    [] ← ByteBlt.ByteBlt[to, userData, move];
    Socket.SetPacketBytes[b,
      NetworkBindingInternal.fixedBytesInLocateCall +
      (SIZE[NetworkBindingProtocol.HostsRecord[current]] * bpw) +
      (SIZE[NetworkBindingProtocol.Cookie[clientInfo.param.length]] * bpw)];
    Inline.LongCOPY[  --copy in the current sequence including length
      to: @locate.body.hosts, from: answer,
      nwords: SIZE[NetworkBindingProtocol.HostsRecord[current]]];
    END;  --RippleExpand

  Recurse: <<RECURSIVE>> PROC[
    data: LONG POINTER TO RecursionData,
    sublist: NetworkBindingInternal.HostsSubList,
    responses: LONG POINTER TO NetworkBinding.Responses] =
    BEGIN

    RequeueProc: ENTRY PROC[b: NSBuffer.Buffer] =
      {data.isback ← TRUE; NOTIFY data.requeued};
    DequeueProc: ENTRY PROC = INLINE
      {UNTIL data.isback DO WAIT data.requeued; ENDLOOP};

    SubdivisionNeeded: PROC RETURNS[BOOLEAN] =
      BEGIN
      <<
      'hosts' is the entire "matches" record. Its initial value is [nul;,all].
      'sublist' is the first version of 'hosts'.  We're trying to build up
      'hosts' by broadcasting a message that includes the current 'hosts'.
      If the length of 'hosts' gets larger than permitted (MaxListSize[]),
      then bail out of the procedure with a FALSE value.
      >>
      timeouts: NATURAL ← 0;  --number of times we timed out
      current: NATURAL ← sublist.stopIndexPlusOne - sublist.startIndex;
      hosts ← data.zone.NEW[
        NetworkBindingProtocol.HostsRecord[data.maxHostList]];
      Inline.LongCOPY[  --blt the current sublist into the hosts
        from: @sublist.pointer[sublist.startIndex], to: @hosts[0],
	nwords: SIZE[NetworkBindingProtocol.HostsRecord[current]] -
	  SIZE[NetworkBindingProtocol.HostsRecord[0]]];
      NetworkBindingInternal.SetSequenceLength[hosts, current];
      --Now we no longer should reference 'sublist'

      WHILE timeouts < broadcastingCount DO
      <<
      Broadcast 'broadcastingCount' times with each packet.  Collect all the
      responses and merge them into 'hosts'.  If we get no responses in
      'broadcastingCount' tries, we're done.  If we continue to get responses,
      then sort them, expand the packet and try again.
      >>
	replies: NATURAL ← 0;  --to count the replies to the broadcast

	data.userData ← RippleExpand[
	  data.reqB, hosts, data.userData, current];

	data.isback ← FALSE;  --set flag for detecting requeue
	Socket.PutPacket[data.sH, data.reqB];  --one little packet out
	DequeueProc[];  --wait for the buffer to come back

	WHILE current < data.maxHostList --UNTIL Socket.TimeOut-- DO
	  ENABLE Socket.TimeOut => {timeouts ← SUCC[timeouts]; EXIT};
	  return: NetworkBindingInternal.ReturnMessage;
	  repBody: NSBuffer.Body;
	  replyB: NSBuffer.Buffer;
	  repBody ← (replyB ← Socket.GetPacket[data.sH]).ns;  --collect hosts
	  return ← LOOPHOLE[@repBody.exchangeBody];
	  SELECT TRUE FROM
	    (repBody.exchangeID # data.reqB.ns.exchangeID) => NULL;
	    (return.courierVers # [3, 3]) => NULL;  --not speaking to us
	    (return.return.type = return) =>  --only interested in success
	      BEGIN
	      timeouts ← 0;  --reset this so we stay in loop
	      hosts[current] ← return.body.responder;  --responder (unsorted)
	      AppendResponse[data, replyB, responses];  --record the hosts
	      replies ← SUCC[replies];  --count the number of replies
	      current ← SUCC[current];  --and lengthen the table
	      LOOP;  --buffer was returned by AppendResponse
	      END;
	    ENDCASE;
	  Socket.ReturnBuffer[replyB];  --return the buffer received
	  ENDLOOP;
  
	IF replies = 0 THEN LOOP;  --no replies - maybe rebroadcast
	SortHosts[hosts, current];  --now sort it and make it right
	NetworkBindingInternal.SetSequenceLength[hosts, current];
	IF current = data.maxHostList THEN RETURN[TRUE];  --subdivide
	ENDLOOP;
      RETURN[FALSE];  --if we exited, we're satisfied with the answer 
      END;  --SubdivisionNeeded

    hosts: NetworkBindingInternal.Hosts ← NIL;  --working data area
    data.reqB.requeueProcedure ← RequeueProc;  --so we can reclaim the buffer

    IF SubdivisionNeeded[ ! UNWIND => data.zone.FREE[@hosts]] THEN
      BEGIN
      length: NATURAL = (hosts.count + 1) / 2;
      l1: NetworkBindingInternal.HostsSubList = [hosts, 0, length];
      l2: NetworkBindingInternal.HostsSubList = [hosts, length, hosts.count];
      Recurse[data, l1, responses]; Recurse[data, l2, responses];
      END;
    data.zone.FREE[@hosts];
    END;  --Recurse

  SortHosts: PROC[list: NetworkBindingInternal.Hosts, length: NATURAL] =
    BEGIN
    Compare: QuickSort.CompareProc =
      BEGIN
      OPEN list: NARROW[data, NetworkBindingInternal.Hosts];
      a: NetworkBindingInternal.ThreeCardinals = LOOPHOLE[list[one]];
      b: NetworkBindingInternal.ThreeCardinals = LOOPHOLE[list[two]];
      RETURN[SELECT TRUE FROM
        (a.one > b.one) => bigger,
	(a.one < b.one) => smaller,
	(a.two > b.two) => bigger,
	(a.two < b.two) => smaller,
	(a.three > b.three) => bigger,
	(a.three < b.three) => smaller,
	ENDCASE => same];
      END;  --Compare
    Swap: QuickSort.SwapProc =
      BEGIN
      OPEN list: NARROW[data, NetworkBindingInternal.Hosts];
      c: System.HostNumber = list[one];
      list[one] ← list[two]; list[two] ← c;
      END;  --Swap
    QuickSort.Sort[0, INTEGER[PRED[length]], Compare, Swap, list];
    NetworkBindingInternal.SetSequenceLength[list, length];
    END;  --SortHosts

  SortResponses: PROC[
    responses: NetworkBinding.Responses, zone: UNCOUNTED ZONE] =
    BEGIN
    Compare: QuickSort.CompareProc =
      BEGIN
      OPEN c: NARROW[data, NetworkBinding.Responses];
      uno, dou: NetworkBindingInternal.ThreeCardinals;
      p: LONG POINTER TO NetworkBindingInternal.ThreeCardinals ← LOOPHOLE[data +
        SIZE[NetworkBinding.ResponseSequence] + SIZE[System.NetworkNumber]];
      uno ← (p + (c.elementSize * one))↑;
      dou ← (p + (c.elementSize * two))↑;
      RETURN[SELECT TRUE FROM
        (uno.one > dou.one) => bigger,
	(uno.one < dou.one) => smaller,
	(uno.two > dou.two) => bigger,
	(uno.two < dou.two) => smaller,
	(uno.three > dou.three) => bigger,
	(uno.three < dou.three) => smaller,
	ENDCASE => same];
      END;  --Compare
    Swap: QuickSort.SwapProc =
      BEGIN
      a, b: LONG POINTER;
      size: NATURAL = NARROW[data, NetworkBinding.Responses].elementSize;
      a ← data + (one * size) + SIZE[NetworkBinding.ResponseSequence];
      b ← data + (two * size) + SIZE[NetworkBinding.ResponseSequence];
      Inline.LongCOPY[to: temp, from: a, nwords: size];
      Inline.LongCOPY[to: a, from: b, nwords: size];
      Inline.LongCOPY[to: b, from: temp, nwords: size];
      END;  --Swap
    DataBlock: TYPE = RECORD[SEQUENCE COMPUTED NATURAL OF WORD];
    temp: LONG POINTER ← zone.NEW[DataBlock[responses.elementSize]];
    QuickSort.Sort[
      0, INTEGER[PRED[responses.elementCount]], Compare, Swap, responses];
    zone.FREE[@temp];
    END;  --SortResponses

  SortAndPrune: PROC[
    responses: LONG POINTER TO NetworkBinding.Responses,
    data: LONG POINTER TO RecursionData] =
    BEGIN
    <<
    Sort the list, pruning out the entries with the host field equal to either
    'all' or 'null' or duplicate. The list  will be shorter than that since it
    started with a 'null' at the head and an 'all' at the end.
    >>
    PNA: TYPE = LONG POINTER TO System.NetworkAddress;
    size, length: NATURAL ← 0;
    in, out: PNA;  --pointers for pruning
    IF (responses↑ = NIL) THEN RETURN;  --real simple
    SortResponses[responses↑, data.zone];  --gag!@
    size ← responses↑.elementSize;  --get a local copy
    in ← out ← LOOPHOLE[@responses↑[0], PNA];  --beginning addresses
    THROUGH[0..responses↑.elementCount) DO
      SELECT in.host FROM
        null, all, NARROW[(in + size), PNA].host => NULL;  --ignore
	ENDCASE =>
	  BEGIN
	  length ← SUCC[length];  --keep track of how many survive
	  Inline.LongCOPY[to: out, from: in, nwords: size];
	  out ← out + size;  --to next slot in output
	  END;
      in ← in + size;  --go to next input slot
      ENDLOOP;
    responses↑.elementCount ← length;  --assign final pruned length
    END;  --SortAndPrune

  MaxListSize: PROC[userData: Environment.Block] RETURNS[max: NATURAL] =
    BEGIN
    <<
    This doesn't quite give the right answer, but its close
    >>
    maxBytesAvailable: NATURAL =
      NSTypes.maxDataBytesPerExchange -
      userData.stopIndexPlusOne + userData.startIndex -
      NetworkBindingInternal.fixedBytesInLocateCall;
    max ← ((maxBytesAvailable / bpw) -
      SIZE[NetworkBindingProtocol.HostsRecord[0]]) / SIZE[System.HostNumber];
    RETURN[MIN[max, NetworkBindingProtocol.maxHostsPerLocate]];
    END;  --MaxListSize

  END...

 1-Sep-87 18:13:05  AOF  Fix glitch in VerifyBinding