remote.c revision 1.3
1/* Remote target communications for serial-line targets in custom GDB protocol
2
3   Copyright (C) 1988-2015 Free Software Foundation, Inc.
4
5   This file is part of GDB.
6
7   This program is free software; you can redistribute it and/or modify
8   it under the terms of the GNU General Public License as published by
9   the Free Software Foundation; either version 3 of the License, or
10   (at your option) any later version.
11
12   This program is distributed in the hope that it will be useful,
13   but WITHOUT ANY WARRANTY; without even the implied warranty of
14   MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15   GNU General Public License for more details.
16
17   You should have received a copy of the GNU General Public License
18   along with this program.  If not, see <http://www.gnu.org/licenses/>.  */
19
20/* See the GDB User Guide for details of the GDB remote protocol.  */
21
22#include "defs.h"
23#include <ctype.h>
24#include <fcntl.h>
25#include "inferior.h"
26#include "infrun.h"
27#include "bfd.h"
28#include "symfile.h"
29#include "target.h"
30/*#include "terminal.h" */
31#include "gdbcmd.h"
32#include "objfiles.h"
33#include "gdb-stabs.h"
34#include "gdbthread.h"
35#include "remote.h"
36#include "remote-notif.h"
37#include "regcache.h"
38#include "value.h"
39#include "observer.h"
40#include "solib.h"
41#include "cli/cli-decode.h"
42#include "cli/cli-setshow.h"
43#include "target-descriptions.h"
44#include "gdb_bfd.h"
45#include "filestuff.h"
46#include "rsp-low.h"
47
48#include <sys/time.h>
49
50#include "event-loop.h"
51#include "event-top.h"
52#include "inf-loop.h"
53
54#include <signal.h>
55#include "serial.h"
56
57#include "gdbcore.h" /* for exec_bfd */
58
59#include "remote-fileio.h"
60#include "gdb/fileio.h"
61#include <sys/stat.h>
62#include "xml-support.h"
63
64#include "memory-map.h"
65
66#include "tracepoint.h"
67#include "ax.h"
68#include "ax-gdb.h"
69#include "agent.h"
70#include "btrace.h"
71
72/* Temp hacks for tracepoint encoding migration.  */
73static char *target_buf;
74static long target_buf_size;
75
76/* The size to align memory write packets, when practical.  The protocol
77   does not guarantee any alignment, and gdb will generate short
78   writes and unaligned writes, but even as a best-effort attempt this
79   can improve bulk transfers.  For instance, if a write is misaligned
80   relative to the target's data bus, the stub may need to make an extra
81   round trip fetching data from the target.  This doesn't make a
82   huge difference, but it's easy to do, so we try to be helpful.
83
84   The alignment chosen is arbitrary; usually data bus width is
85   important here, not the possibly larger cache line size.  */
86enum { REMOTE_ALIGN_WRITES = 16 };
87
88/* Prototypes for local functions.  */
89static void async_cleanup_sigint_signal_handler (void *dummy);
90static int getpkt_sane (char **buf, long *sizeof_buf, int forever);
91static int getpkt_or_notif_sane (char **buf, long *sizeof_buf,
92				 int forever, int *is_notif);
93
94static void async_handle_remote_sigint (int);
95static void async_handle_remote_sigint_twice (int);
96
97static void remote_files_info (struct target_ops *ignore);
98
99static void remote_prepare_to_store (struct target_ops *self,
100				     struct regcache *regcache);
101
102static void remote_open_1 (const char *, int, struct target_ops *,
103			   int extended_p);
104
105static void remote_close (struct target_ops *self);
106
107static void remote_mourn (struct target_ops *ops);
108
109static void extended_remote_restart (void);
110
111static void extended_remote_mourn (struct target_ops *);
112
113static void remote_mourn_1 (struct target_ops *);
114
115static void remote_send (char **buf, long *sizeof_buf_p);
116
117static int readchar (int timeout);
118
119static void remote_serial_write (const char *str, int len);
120
121static void remote_kill (struct target_ops *ops);
122
123static int remote_can_async_p (struct target_ops *);
124
125static int remote_is_async_p (struct target_ops *);
126
127static void remote_async (struct target_ops *ops,
128			  void (*callback) (enum inferior_event_type event_type,
129					    void *context),
130			  void *context);
131
132static void sync_remote_interrupt_twice (int signo);
133
134static void interrupt_query (void);
135
136static void set_general_thread (struct ptid ptid);
137static void set_continue_thread (struct ptid ptid);
138
139static void get_offsets (void);
140
141static void skip_frame (void);
142
143static long read_frame (char **buf_p, long *sizeof_buf);
144
145static int hexnumlen (ULONGEST num);
146
147static void init_remote_ops (void);
148
149static void init_extended_remote_ops (void);
150
151static void remote_stop (struct target_ops *self, ptid_t);
152
153static int stubhex (int ch);
154
155static int hexnumstr (char *, ULONGEST);
156
157static int hexnumnstr (char *, ULONGEST, int);
158
159static CORE_ADDR remote_address_masked (CORE_ADDR);
160
161static void print_packet (const char *);
162
163static void compare_sections_command (char *, int);
164
165static void packet_command (char *, int);
166
167static int stub_unpack_int (char *buff, int fieldlength);
168
169static ptid_t remote_current_thread (ptid_t oldptid);
170
171static int putpkt_binary (const char *buf, int cnt);
172
173static void check_binary_download (CORE_ADDR addr);
174
175struct packet_config;
176
177static void show_packet_config_cmd (struct packet_config *config);
178
179static void show_remote_protocol_packet_cmd (struct ui_file *file,
180					     int from_tty,
181					     struct cmd_list_element *c,
182					     const char *value);
183
184static char *write_ptid (char *buf, const char *endbuf, ptid_t ptid);
185static ptid_t read_ptid (char *buf, char **obuf);
186
187static void remote_set_permissions (struct target_ops *self);
188
189struct remote_state;
190static int remote_get_trace_status (struct target_ops *self,
191				    struct trace_status *ts);
192
193static int remote_upload_tracepoints (struct target_ops *self,
194				      struct uploaded_tp **utpp);
195
196static int remote_upload_trace_state_variables (struct target_ops *self,
197						struct uploaded_tsv **utsvp);
198
199static void remote_query_supported (void);
200
201static void remote_check_symbols (void);
202
203void _initialize_remote (void);
204
205struct stop_reply;
206static void stop_reply_xfree (struct stop_reply *);
207static void remote_parse_stop_reply (char *, struct stop_reply *);
208static void push_stop_reply (struct stop_reply *);
209static void discard_pending_stop_replies_in_queue (struct remote_state *);
210static int peek_stop_reply (ptid_t ptid);
211
212static void remote_async_inferior_event_handler (gdb_client_data);
213
214static void remote_terminal_ours (struct target_ops *self);
215
216static int remote_read_description_p (struct target_ops *target);
217
218static void remote_console_output (char *msg);
219
220static int remote_supports_cond_breakpoints (struct target_ops *self);
221
222static int remote_can_run_breakpoint_commands (struct target_ops *self);
223
224/* For "remote".  */
225
226static struct cmd_list_element *remote_cmdlist;
227
228/* For "set remote" and "show remote".  */
229
230static struct cmd_list_element *remote_set_cmdlist;
231static struct cmd_list_element *remote_show_cmdlist;
232
233/* Stub vCont actions support.
234
235   Each field is a boolean flag indicating whether the stub reports
236   support for the corresponding action.  */
237
238struct vCont_action_support
239{
240  /* vCont;t */
241  int t;
242
243  /* vCont;r */
244  int r;
245};
246
247/* Controls whether GDB is willing to use range stepping.  */
248
249static int use_range_stepping = 1;
250
251#define OPAQUETHREADBYTES 8
252
253/* a 64 bit opaque identifier */
254typedef unsigned char threadref[OPAQUETHREADBYTES];
255
256/* About this many threadisds fit in a packet.  */
257
258#define MAXTHREADLISTRESULTS 32
259
260/* Description of the remote protocol state for the currently
261   connected target.  This is per-target state, and independent of the
262   selected architecture.  */
263
264struct remote_state
265{
266  /* A buffer to use for incoming packets, and its current size.  The
267     buffer is grown dynamically for larger incoming packets.
268     Outgoing packets may also be constructed in this buffer.
269     BUF_SIZE is always at least REMOTE_PACKET_SIZE;
270     REMOTE_PACKET_SIZE should be used to limit the length of outgoing
271     packets.  */
272  char *buf;
273  long buf_size;
274
275  /* True if we're going through initial connection setup (finding out
276     about the remote side's threads, relocating symbols, etc.).  */
277  int starting_up;
278
279  /* If we negotiated packet size explicitly (and thus can bypass
280     heuristics for the largest packet size that will not overflow
281     a buffer in the stub), this will be set to that packet size.
282     Otherwise zero, meaning to use the guessed size.  */
283  long explicit_packet_size;
284
285  /* remote_wait is normally called when the target is running and
286     waits for a stop reply packet.  But sometimes we need to call it
287     when the target is already stopped.  We can send a "?" packet
288     and have remote_wait read the response.  Or, if we already have
289     the response, we can stash it in BUF and tell remote_wait to
290     skip calling getpkt.  This flag is set when BUF contains a
291     stop reply packet and the target is not waiting.  */
292  int cached_wait_status;
293
294  /* True, if in no ack mode.  That is, neither GDB nor the stub will
295     expect acks from each other.  The connection is assumed to be
296     reliable.  */
297  int noack_mode;
298
299  /* True if we're connected in extended remote mode.  */
300  int extended;
301
302  /* True if we resumed the target and we're waiting for the target to
303     stop.  In the mean time, we can't start another command/query.
304     The remote server wouldn't be ready to process it, so we'd
305     timeout waiting for a reply that would never come and eventually
306     we'd close the connection.  This can happen in asynchronous mode
307     because we allow GDB commands while the target is running.  */
308  int waiting_for_stop_reply;
309
310  /* The status of the stub support for the various vCont actions.  */
311  struct vCont_action_support supports_vCont;
312
313  /* Nonzero if the user has pressed Ctrl-C, but the target hasn't
314     responded to that.  */
315  int ctrlc_pending_p;
316
317  /* Descriptor for I/O to remote machine.  Initialize it to NULL so that
318     remote_open knows that we don't have a file open when the program
319     starts.  */
320  struct serial *remote_desc;
321
322  /* These are the threads which we last sent to the remote system.  The
323     TID member will be -1 for all or -2 for not sent yet.  */
324  ptid_t general_thread;
325  ptid_t continue_thread;
326
327  /* This is the traceframe which we last selected on the remote system.
328     It will be -1 if no traceframe is selected.  */
329  int remote_traceframe_number;
330
331  char *last_pass_packet;
332
333  /* The last QProgramSignals packet sent to the target.  We bypass
334     sending a new program signals list down to the target if the new
335     packet is exactly the same as the last we sent.  IOW, we only let
336     the target know about program signals list changes.  */
337  char *last_program_signals_packet;
338
339  enum gdb_signal last_sent_signal;
340
341  int last_sent_step;
342
343  char *finished_object;
344  char *finished_annex;
345  ULONGEST finished_offset;
346
347  /* Should we try the 'ThreadInfo' query packet?
348
349     This variable (NOT available to the user: auto-detect only!)
350     determines whether GDB will use the new, simpler "ThreadInfo"
351     query or the older, more complex syntax for thread queries.
352     This is an auto-detect variable (set to true at each connect,
353     and set to false when the target fails to recognize it).  */
354  int use_threadinfo_query;
355  int use_threadextra_query;
356
357  void (*async_client_callback) (enum inferior_event_type event_type,
358				 void *context);
359  void *async_client_context;
360
361  /* This is set to the data address of the access causing the target
362     to stop for a watchpoint.  */
363  CORE_ADDR remote_watch_data_address;
364
365  /* This is non-zero if target stopped for a watchpoint.  */
366  int remote_stopped_by_watchpoint_p;
367
368  threadref echo_nextthread;
369  threadref nextthread;
370  threadref resultthreadlist[MAXTHREADLISTRESULTS];
371
372  /* The state of remote notification.  */
373  struct remote_notif_state *notif_state;
374};
375
376/* Private data that we'll store in (struct thread_info)->private.  */
377struct private_thread_info
378{
379  char *extra;
380  int core;
381};
382
383static void
384free_private_thread_info (struct private_thread_info *info)
385{
386  xfree (info->extra);
387  xfree (info);
388}
389
390/* This data could be associated with a target, but we do not always
391   have access to the current target when we need it, so for now it is
392   static.  This will be fine for as long as only one target is in use
393   at a time.  */
394static struct remote_state *remote_state;
395
396static struct remote_state *
397get_remote_state_raw (void)
398{
399  return remote_state;
400}
401
402/* Allocate a new struct remote_state with xmalloc, initialize it, and
403   return it.  */
404
405static struct remote_state *
406new_remote_state (void)
407{
408  struct remote_state *result = XCNEW (struct remote_state);
409
410  /* The default buffer size is unimportant; it will be expanded
411     whenever a larger buffer is needed. */
412  result->buf_size = 400;
413  result->buf = xmalloc (result->buf_size);
414  result->remote_traceframe_number = -1;
415  result->last_sent_signal = GDB_SIGNAL_0;
416
417  return result;
418}
419
420/* Description of the remote protocol for a given architecture.  */
421
422struct packet_reg
423{
424  long offset; /* Offset into G packet.  */
425  long regnum; /* GDB's internal register number.  */
426  LONGEST pnum; /* Remote protocol register number.  */
427  int in_g_packet; /* Always part of G packet.  */
428  /* long size in bytes;  == register_size (target_gdbarch (), regnum);
429     at present.  */
430  /* char *name; == gdbarch_register_name (target_gdbarch (), regnum);
431     at present.  */
432};
433
434struct remote_arch_state
435{
436  /* Description of the remote protocol registers.  */
437  long sizeof_g_packet;
438
439  /* Description of the remote protocol registers indexed by REGNUM
440     (making an array gdbarch_num_regs in size).  */
441  struct packet_reg *regs;
442
443  /* This is the size (in chars) of the first response to the ``g''
444     packet.  It is used as a heuristic when determining the maximum
445     size of memory-read and memory-write packets.  A target will
446     typically only reserve a buffer large enough to hold the ``g''
447     packet.  The size does not include packet overhead (headers and
448     trailers).  */
449  long actual_register_packet_size;
450
451  /* This is the maximum size (in chars) of a non read/write packet.
452     It is also used as a cap on the size of read/write packets.  */
453  long remote_packet_size;
454};
455
456/* Utility: generate error from an incoming stub packet.  */
457static void
458trace_error (char *buf)
459{
460  if (*buf++ != 'E')
461    return;			/* not an error msg */
462  switch (*buf)
463    {
464    case '1':			/* malformed packet error */
465      if (*++buf == '0')	/*   general case: */
466	error (_("remote.c: error in outgoing packet."));
467      else
468	error (_("remote.c: error in outgoing packet at field #%ld."),
469	       strtol (buf, NULL, 16));
470    default:
471      error (_("Target returns error code '%s'."), buf);
472    }
473}
474
475/* Utility: wait for reply from stub, while accepting "O" packets.  */
476static char *
477remote_get_noisy_reply (char **buf_p,
478			long *sizeof_buf)
479{
480  do				/* Loop on reply from remote stub.  */
481    {
482      char *buf;
483
484      QUIT;			/* Allow user to bail out with ^C.  */
485      getpkt (buf_p, sizeof_buf, 0);
486      buf = *buf_p;
487      if (buf[0] == 'E')
488	trace_error (buf);
489      else if (strncmp (buf, "qRelocInsn:", strlen ("qRelocInsn:")) == 0)
490	{
491	  ULONGEST ul;
492	  CORE_ADDR from, to, org_to;
493	  char *p, *pp;
494	  int adjusted_size = 0;
495	  volatile struct gdb_exception ex;
496
497	  p = buf + strlen ("qRelocInsn:");
498	  pp = unpack_varlen_hex (p, &ul);
499	  if (*pp != ';')
500	    error (_("invalid qRelocInsn packet: %s"), buf);
501	  from = ul;
502
503	  p = pp + 1;
504	  unpack_varlen_hex (p, &ul);
505	  to = ul;
506
507	  org_to = to;
508
509	  TRY_CATCH (ex, RETURN_MASK_ALL)
510	    {
511	      gdbarch_relocate_instruction (target_gdbarch (), &to, from);
512	    }
513	  if (ex.reason >= 0)
514	    {
515	      adjusted_size = to - org_to;
516
517	      xsnprintf (buf, *sizeof_buf, "qRelocInsn:%x", adjusted_size);
518	      putpkt (buf);
519	    }
520	  else if (ex.reason < 0 && ex.error == MEMORY_ERROR)
521	    {
522	      /* Propagate memory errors silently back to the target.
523		 The stub may have limited the range of addresses we
524		 can write to, for example.  */
525	      putpkt ("E01");
526	    }
527	  else
528	    {
529	      /* Something unexpectedly bad happened.  Be verbose so
530		 we can tell what, and propagate the error back to the
531		 stub, so it doesn't get stuck waiting for a
532		 response.  */
533	      exception_fprintf (gdb_stderr, ex,
534				 _("warning: relocating instruction: "));
535	      putpkt ("E01");
536	    }
537	}
538      else if (buf[0] == 'O' && buf[1] != 'K')
539	remote_console_output (buf + 1);	/* 'O' message from stub */
540      else
541	return buf;		/* Here's the actual reply.  */
542    }
543  while (1);
544}
545
546/* Handle for retreving the remote protocol data from gdbarch.  */
547static struct gdbarch_data *remote_gdbarch_data_handle;
548
549static struct remote_arch_state *
550get_remote_arch_state (void)
551{
552  return gdbarch_data (target_gdbarch (), remote_gdbarch_data_handle);
553}
554
555/* Fetch the global remote target state.  */
556
557static struct remote_state *
558get_remote_state (void)
559{
560  /* Make sure that the remote architecture state has been
561     initialized, because doing so might reallocate rs->buf.  Any
562     function which calls getpkt also needs to be mindful of changes
563     to rs->buf, but this call limits the number of places which run
564     into trouble.  */
565  get_remote_arch_state ();
566
567  return get_remote_state_raw ();
568}
569
570static int
571compare_pnums (const void *lhs_, const void *rhs_)
572{
573  const struct packet_reg * const *lhs = lhs_;
574  const struct packet_reg * const *rhs = rhs_;
575
576  if ((*lhs)->pnum < (*rhs)->pnum)
577    return -1;
578  else if ((*lhs)->pnum == (*rhs)->pnum)
579    return 0;
580  else
581    return 1;
582}
583
584static int
585map_regcache_remote_table (struct gdbarch *gdbarch, struct packet_reg *regs)
586{
587  int regnum, num_remote_regs, offset;
588  struct packet_reg **remote_regs;
589
590  for (regnum = 0; regnum < gdbarch_num_regs (gdbarch); regnum++)
591    {
592      struct packet_reg *r = &regs[regnum];
593
594      if (register_size (gdbarch, regnum) == 0)
595	/* Do not try to fetch zero-sized (placeholder) registers.  */
596	r->pnum = -1;
597      else
598	r->pnum = gdbarch_remote_register_number (gdbarch, regnum);
599
600      r->regnum = regnum;
601    }
602
603  /* Define the g/G packet format as the contents of each register
604     with a remote protocol number, in order of ascending protocol
605     number.  */
606
607  remote_regs = alloca (gdbarch_num_regs (gdbarch)
608			* sizeof (struct packet_reg *));
609  for (num_remote_regs = 0, regnum = 0;
610       regnum < gdbarch_num_regs (gdbarch);
611       regnum++)
612    if (regs[regnum].pnum != -1)
613      remote_regs[num_remote_regs++] = &regs[regnum];
614
615  qsort (remote_regs, num_remote_regs, sizeof (struct packet_reg *),
616	 compare_pnums);
617
618  for (regnum = 0, offset = 0; regnum < num_remote_regs; regnum++)
619    {
620      remote_regs[regnum]->in_g_packet = 1;
621      remote_regs[regnum]->offset = offset;
622      offset += register_size (gdbarch, remote_regs[regnum]->regnum);
623    }
624
625  return offset;
626}
627
628/* Given the architecture described by GDBARCH, return the remote
629   protocol register's number and the register's offset in the g/G
630   packets of GDB register REGNUM, in PNUM and POFFSET respectively.
631   If the target does not have a mapping for REGNUM, return false,
632   otherwise, return true.  */
633
634int
635remote_register_number_and_offset (struct gdbarch *gdbarch, int regnum,
636				   int *pnum, int *poffset)
637{
638  int sizeof_g_packet;
639  struct packet_reg *regs;
640  struct cleanup *old_chain;
641
642  gdb_assert (regnum < gdbarch_num_regs (gdbarch));
643
644  regs = xcalloc (gdbarch_num_regs (gdbarch), sizeof (struct packet_reg));
645  old_chain = make_cleanup (xfree, regs);
646
647  sizeof_g_packet = map_regcache_remote_table (gdbarch, regs);
648
649  *pnum = regs[regnum].pnum;
650  *poffset = regs[regnum].offset;
651
652  do_cleanups (old_chain);
653
654  return *pnum != -1;
655}
656
657static void *
658init_remote_state (struct gdbarch *gdbarch)
659{
660  struct remote_state *rs = get_remote_state_raw ();
661  struct remote_arch_state *rsa;
662
663  rsa = GDBARCH_OBSTACK_ZALLOC (gdbarch, struct remote_arch_state);
664
665  /* Use the architecture to build a regnum<->pnum table, which will be
666     1:1 unless a feature set specifies otherwise.  */
667  rsa->regs = GDBARCH_OBSTACK_CALLOC (gdbarch,
668				      gdbarch_num_regs (gdbarch),
669				      struct packet_reg);
670
671  /* Record the maximum possible size of the g packet - it may turn out
672     to be smaller.  */
673  rsa->sizeof_g_packet = map_regcache_remote_table (gdbarch, rsa->regs);
674
675  /* Default maximum number of characters in a packet body.  Many
676     remote stubs have a hardwired buffer size of 400 bytes
677     (c.f. BUFMAX in m68k-stub.c and i386-stub.c).  BUFMAX-1 is used
678     as the maximum packet-size to ensure that the packet and an extra
679     NUL character can always fit in the buffer.  This stops GDB
680     trashing stubs that try to squeeze an extra NUL into what is
681     already a full buffer (As of 1999-12-04 that was most stubs).  */
682  rsa->remote_packet_size = 400 - 1;
683
684  /* This one is filled in when a ``g'' packet is received.  */
685  rsa->actual_register_packet_size = 0;
686
687  /* Should rsa->sizeof_g_packet needs more space than the
688     default, adjust the size accordingly.  Remember that each byte is
689     encoded as two characters.  32 is the overhead for the packet
690     header / footer.  NOTE: cagney/1999-10-26: I suspect that 8
691     (``$NN:G...#NN'') is a better guess, the below has been padded a
692     little.  */
693  if (rsa->sizeof_g_packet > ((rsa->remote_packet_size - 32) / 2))
694    rsa->remote_packet_size = (rsa->sizeof_g_packet * 2 + 32);
695
696  /* Make sure that the packet buffer is plenty big enough for
697     this architecture.  */
698  if (rs->buf_size < rsa->remote_packet_size)
699    {
700      rs->buf_size = 2 * rsa->remote_packet_size;
701      rs->buf = xrealloc (rs->buf, rs->buf_size);
702    }
703
704  return rsa;
705}
706
707/* Return the current allowed size of a remote packet.  This is
708   inferred from the current architecture, and should be used to
709   limit the length of outgoing packets.  */
710static long
711get_remote_packet_size (void)
712{
713  struct remote_state *rs = get_remote_state ();
714  struct remote_arch_state *rsa = get_remote_arch_state ();
715
716  if (rs->explicit_packet_size)
717    return rs->explicit_packet_size;
718
719  return rsa->remote_packet_size;
720}
721
722static struct packet_reg *
723packet_reg_from_regnum (struct remote_arch_state *rsa, long regnum)
724{
725  if (regnum < 0 && regnum >= gdbarch_num_regs (target_gdbarch ()))
726    return NULL;
727  else
728    {
729      struct packet_reg *r = &rsa->regs[regnum];
730
731      gdb_assert (r->regnum == regnum);
732      return r;
733    }
734}
735
736static struct packet_reg *
737packet_reg_from_pnum (struct remote_arch_state *rsa, LONGEST pnum)
738{
739  int i;
740
741  for (i = 0; i < gdbarch_num_regs (target_gdbarch ()); i++)
742    {
743      struct packet_reg *r = &rsa->regs[i];
744
745      if (r->pnum == pnum)
746	return r;
747    }
748  return NULL;
749}
750
751static struct target_ops remote_ops;
752
753static struct target_ops extended_remote_ops;
754
755/* FIXME: cagney/1999-09-23: Even though getpkt was called with
756   ``forever'' still use the normal timeout mechanism.  This is
757   currently used by the ASYNC code to guarentee that target reads
758   during the initial connect always time-out.  Once getpkt has been
759   modified to return a timeout indication and, in turn
760   remote_wait()/wait_for_inferior() have gained a timeout parameter
761   this can go away.  */
762static int wait_forever_enabled_p = 1;
763
764/* Allow the user to specify what sequence to send to the remote
765   when he requests a program interruption: Although ^C is usually
766   what remote systems expect (this is the default, here), it is
767   sometimes preferable to send a break.  On other systems such
768   as the Linux kernel, a break followed by g, which is Magic SysRq g
769   is required in order to interrupt the execution.  */
770const char interrupt_sequence_control_c[] = "Ctrl-C";
771const char interrupt_sequence_break[] = "BREAK";
772const char interrupt_sequence_break_g[] = "BREAK-g";
773static const char *const interrupt_sequence_modes[] =
774  {
775    interrupt_sequence_control_c,
776    interrupt_sequence_break,
777    interrupt_sequence_break_g,
778    NULL
779  };
780static const char *interrupt_sequence_mode = interrupt_sequence_control_c;
781
782static void
783show_interrupt_sequence (struct ui_file *file, int from_tty,
784			 struct cmd_list_element *c,
785			 const char *value)
786{
787  if (interrupt_sequence_mode == interrupt_sequence_control_c)
788    fprintf_filtered (file,
789		      _("Send the ASCII ETX character (Ctrl-c) "
790			"to the remote target to interrupt the "
791			"execution of the program.\n"));
792  else if (interrupt_sequence_mode == interrupt_sequence_break)
793    fprintf_filtered (file,
794		      _("send a break signal to the remote target "
795			"to interrupt the execution of the program.\n"));
796  else if (interrupt_sequence_mode == interrupt_sequence_break_g)
797    fprintf_filtered (file,
798		      _("Send a break signal and 'g' a.k.a. Magic SysRq g to "
799			"the remote target to interrupt the execution "
800			"of Linux kernel.\n"));
801  else
802    internal_error (__FILE__, __LINE__,
803		    _("Invalid value for interrupt_sequence_mode: %s."),
804		    interrupt_sequence_mode);
805}
806
807/* This boolean variable specifies whether interrupt_sequence is sent
808   to the remote target when gdb connects to it.
809   This is mostly needed when you debug the Linux kernel: The Linux kernel
810   expects BREAK g which is Magic SysRq g for connecting gdb.  */
811static int interrupt_on_connect = 0;
812
813/* This variable is used to implement the "set/show remotebreak" commands.
814   Since these commands are now deprecated in favor of "set/show remote
815   interrupt-sequence", it no longer has any effect on the code.  */
816static int remote_break;
817
818static void
819set_remotebreak (char *args, int from_tty, struct cmd_list_element *c)
820{
821  if (remote_break)
822    interrupt_sequence_mode = interrupt_sequence_break;
823  else
824    interrupt_sequence_mode = interrupt_sequence_control_c;
825}
826
827static void
828show_remotebreak (struct ui_file *file, int from_tty,
829		  struct cmd_list_element *c,
830		  const char *value)
831{
832}
833
834/* This variable sets the number of bits in an address that are to be
835   sent in a memory ("M" or "m") packet.  Normally, after stripping
836   leading zeros, the entire address would be sent.  This variable
837   restricts the address to REMOTE_ADDRESS_SIZE bits.  HISTORY: The
838   initial implementation of remote.c restricted the address sent in
839   memory packets to ``host::sizeof long'' bytes - (typically 32
840   bits).  Consequently, for 64 bit targets, the upper 32 bits of an
841   address was never sent.  Since fixing this bug may cause a break in
842   some remote targets this variable is principly provided to
843   facilitate backward compatibility.  */
844
845static unsigned int remote_address_size;
846
847/* Temporary to track who currently owns the terminal.  See
848   remote_terminal_* for more details.  */
849
850static int remote_async_terminal_ours_p;
851
852/* The executable file to use for "run" on the remote side.  */
853
854static char *remote_exec_file = "";
855
856
857/* User configurable variables for the number of characters in a
858   memory read/write packet.  MIN (rsa->remote_packet_size,
859   rsa->sizeof_g_packet) is the default.  Some targets need smaller
860   values (fifo overruns, et.al.) and some users need larger values
861   (speed up transfers).  The variables ``preferred_*'' (the user
862   request), ``current_*'' (what was actually set) and ``forced_*''
863   (Positive - a soft limit, negative - a hard limit).  */
864
865struct memory_packet_config
866{
867  char *name;
868  long size;
869  int fixed_p;
870};
871
872/* Compute the current size of a read/write packet.  Since this makes
873   use of ``actual_register_packet_size'' the computation is dynamic.  */
874
875static long
876get_memory_packet_size (struct memory_packet_config *config)
877{
878  struct remote_state *rs = get_remote_state ();
879  struct remote_arch_state *rsa = get_remote_arch_state ();
880
881  /* NOTE: The somewhat arbitrary 16k comes from the knowledge (folk
882     law?) that some hosts don't cope very well with large alloca()
883     calls.  Eventually the alloca() code will be replaced by calls to
884     xmalloc() and make_cleanups() allowing this restriction to either
885     be lifted or removed.  */
886#ifndef MAX_REMOTE_PACKET_SIZE
887#define MAX_REMOTE_PACKET_SIZE 16384
888#endif
889  /* NOTE: 20 ensures we can write at least one byte.  */
890#ifndef MIN_REMOTE_PACKET_SIZE
891#define MIN_REMOTE_PACKET_SIZE 20
892#endif
893  long what_they_get;
894  if (config->fixed_p)
895    {
896      if (config->size <= 0)
897	what_they_get = MAX_REMOTE_PACKET_SIZE;
898      else
899	what_they_get = config->size;
900    }
901  else
902    {
903      what_they_get = get_remote_packet_size ();
904      /* Limit the packet to the size specified by the user.  */
905      if (config->size > 0
906	  && what_they_get > config->size)
907	what_they_get = config->size;
908
909      /* Limit it to the size of the targets ``g'' response unless we have
910	 permission from the stub to use a larger packet size.  */
911      if (rs->explicit_packet_size == 0
912	  && rsa->actual_register_packet_size > 0
913	  && what_they_get > rsa->actual_register_packet_size)
914	what_they_get = rsa->actual_register_packet_size;
915    }
916  if (what_they_get > MAX_REMOTE_PACKET_SIZE)
917    what_they_get = MAX_REMOTE_PACKET_SIZE;
918  if (what_they_get < MIN_REMOTE_PACKET_SIZE)
919    what_they_get = MIN_REMOTE_PACKET_SIZE;
920
921  /* Make sure there is room in the global buffer for this packet
922     (including its trailing NUL byte).  */
923  if (rs->buf_size < what_they_get + 1)
924    {
925      rs->buf_size = 2 * what_they_get;
926      rs->buf = xrealloc (rs->buf, 2 * what_they_get);
927    }
928
929  return what_they_get;
930}
931
932/* Update the size of a read/write packet.  If they user wants
933   something really big then do a sanity check.  */
934
935static void
936set_memory_packet_size (char *args, struct memory_packet_config *config)
937{
938  int fixed_p = config->fixed_p;
939  long size = config->size;
940
941  if (args == NULL)
942    error (_("Argument required (integer, `fixed' or `limited')."));
943  else if (strcmp (args, "hard") == 0
944      || strcmp (args, "fixed") == 0)
945    fixed_p = 1;
946  else if (strcmp (args, "soft") == 0
947	   || strcmp (args, "limit") == 0)
948    fixed_p = 0;
949  else
950    {
951      char *end;
952
953      size = strtoul (args, &end, 0);
954      if (args == end)
955	error (_("Invalid %s (bad syntax)."), config->name);
956#if 0
957      /* Instead of explicitly capping the size of a packet to
958         MAX_REMOTE_PACKET_SIZE or dissallowing it, the user is
959         instead allowed to set the size to something arbitrarily
960         large.  */
961      if (size > MAX_REMOTE_PACKET_SIZE)
962	error (_("Invalid %s (too large)."), config->name);
963#endif
964    }
965  /* Extra checks?  */
966  if (fixed_p && !config->fixed_p)
967    {
968      if (! query (_("The target may not be able to correctly handle a %s\n"
969		   "of %ld bytes. Change the packet size? "),
970		   config->name, size))
971	error (_("Packet size not changed."));
972    }
973  /* Update the config.  */
974  config->fixed_p = fixed_p;
975  config->size = size;
976}
977
978static void
979show_memory_packet_size (struct memory_packet_config *config)
980{
981  printf_filtered (_("The %s is %ld. "), config->name, config->size);
982  if (config->fixed_p)
983    printf_filtered (_("Packets are fixed at %ld bytes.\n"),
984		     get_memory_packet_size (config));
985  else
986    printf_filtered (_("Packets are limited to %ld bytes.\n"),
987		     get_memory_packet_size (config));
988}
989
990static struct memory_packet_config memory_write_packet_config =
991{
992  "memory-write-packet-size",
993};
994
995static void
996set_memory_write_packet_size (char *args, int from_tty)
997{
998  set_memory_packet_size (args, &memory_write_packet_config);
999}
1000
1001static void
1002show_memory_write_packet_size (char *args, int from_tty)
1003{
1004  show_memory_packet_size (&memory_write_packet_config);
1005}
1006
1007static long
1008get_memory_write_packet_size (void)
1009{
1010  return get_memory_packet_size (&memory_write_packet_config);
1011}
1012
1013static struct memory_packet_config memory_read_packet_config =
1014{
1015  "memory-read-packet-size",
1016};
1017
1018static void
1019set_memory_read_packet_size (char *args, int from_tty)
1020{
1021  set_memory_packet_size (args, &memory_read_packet_config);
1022}
1023
1024static void
1025show_memory_read_packet_size (char *args, int from_tty)
1026{
1027  show_memory_packet_size (&memory_read_packet_config);
1028}
1029
1030static long
1031get_memory_read_packet_size (void)
1032{
1033  long size = get_memory_packet_size (&memory_read_packet_config);
1034
1035  /* FIXME: cagney/1999-11-07: Functions like getpkt() need to get an
1036     extra buffer size argument before the memory read size can be
1037     increased beyond this.  */
1038  if (size > get_remote_packet_size ())
1039    size = get_remote_packet_size ();
1040  return size;
1041}
1042
1043
1044/* Generic configuration support for packets the stub optionally
1045   supports.  Allows the user to specify the use of the packet as well
1046   as allowing GDB to auto-detect support in the remote stub.  */
1047
1048enum packet_support
1049  {
1050    PACKET_SUPPORT_UNKNOWN = 0,
1051    PACKET_ENABLE,
1052    PACKET_DISABLE
1053  };
1054
1055struct packet_config
1056  {
1057    const char *name;
1058    const char *title;
1059
1060    /* If auto, GDB auto-detects support for this packet or feature,
1061       either through qSupported, or by trying the packet and looking
1062       at the response.  If true, GDB assumes the target supports this
1063       packet.  If false, the packet is disabled.  Configs that don't
1064       have an associated command always have this set to auto.  */
1065    enum auto_boolean detect;
1066
1067    /* Does the target support this packet?  */
1068    enum packet_support support;
1069  };
1070
1071/* Analyze a packet's return value and update the packet config
1072   accordingly.  */
1073
1074enum packet_result
1075{
1076  PACKET_ERROR,
1077  PACKET_OK,
1078  PACKET_UNKNOWN
1079};
1080
1081static enum packet_support packet_config_support (struct packet_config *config);
1082static enum packet_support packet_support (int packet);
1083
1084static void
1085show_packet_config_cmd (struct packet_config *config)
1086{
1087  char *support = "internal-error";
1088
1089  switch (packet_config_support (config))
1090    {
1091    case PACKET_ENABLE:
1092      support = "enabled";
1093      break;
1094    case PACKET_DISABLE:
1095      support = "disabled";
1096      break;
1097    case PACKET_SUPPORT_UNKNOWN:
1098      support = "unknown";
1099      break;
1100    }
1101  switch (config->detect)
1102    {
1103    case AUTO_BOOLEAN_AUTO:
1104      printf_filtered (_("Support for the `%s' packet "
1105			 "is auto-detected, currently %s.\n"),
1106		       config->name, support);
1107      break;
1108    case AUTO_BOOLEAN_TRUE:
1109    case AUTO_BOOLEAN_FALSE:
1110      printf_filtered (_("Support for the `%s' packet is currently %s.\n"),
1111		       config->name, support);
1112      break;
1113    }
1114}
1115
1116static void
1117add_packet_config_cmd (struct packet_config *config, const char *name,
1118		       const char *title, int legacy)
1119{
1120  char *set_doc;
1121  char *show_doc;
1122  char *cmd_name;
1123
1124  config->name = name;
1125  config->title = title;
1126  set_doc = xstrprintf ("Set use of remote protocol `%s' (%s) packet",
1127			name, title);
1128  show_doc = xstrprintf ("Show current use of remote "
1129			 "protocol `%s' (%s) packet",
1130			 name, title);
1131  /* set/show TITLE-packet {auto,on,off} */
1132  cmd_name = xstrprintf ("%s-packet", title);
1133  add_setshow_auto_boolean_cmd (cmd_name, class_obscure,
1134				&config->detect, set_doc,
1135				show_doc, NULL, /* help_doc */
1136				NULL,
1137				show_remote_protocol_packet_cmd,
1138				&remote_set_cmdlist, &remote_show_cmdlist);
1139  /* The command code copies the documentation strings.  */
1140  xfree (set_doc);
1141  xfree (show_doc);
1142  /* set/show remote NAME-packet {auto,on,off} -- legacy.  */
1143  if (legacy)
1144    {
1145      char *legacy_name;
1146
1147      legacy_name = xstrprintf ("%s-packet", name);
1148      add_alias_cmd (legacy_name, cmd_name, class_obscure, 0,
1149		     &remote_set_cmdlist);
1150      add_alias_cmd (legacy_name, cmd_name, class_obscure, 0,
1151		     &remote_show_cmdlist);
1152    }
1153}
1154
1155static enum packet_result
1156packet_check_result (const char *buf)
1157{
1158  if (buf[0] != '\0')
1159    {
1160      /* The stub recognized the packet request.  Check that the
1161	 operation succeeded.  */
1162      if (buf[0] == 'E'
1163	  && isxdigit (buf[1]) && isxdigit (buf[2])
1164	  && buf[3] == '\0')
1165	/* "Enn"  - definitly an error.  */
1166	return PACKET_ERROR;
1167
1168      /* Always treat "E." as an error.  This will be used for
1169	 more verbose error messages, such as E.memtypes.  */
1170      if (buf[0] == 'E' && buf[1] == '.')
1171	return PACKET_ERROR;
1172
1173      /* The packet may or may not be OK.  Just assume it is.  */
1174      return PACKET_OK;
1175    }
1176  else
1177    /* The stub does not support the packet.  */
1178    return PACKET_UNKNOWN;
1179}
1180
1181static enum packet_result
1182packet_ok (const char *buf, struct packet_config *config)
1183{
1184  enum packet_result result;
1185
1186  if (config->detect != AUTO_BOOLEAN_TRUE
1187      && config->support == PACKET_DISABLE)
1188    internal_error (__FILE__, __LINE__,
1189		    _("packet_ok: attempt to use a disabled packet"));
1190
1191  result = packet_check_result (buf);
1192  switch (result)
1193    {
1194    case PACKET_OK:
1195    case PACKET_ERROR:
1196      /* The stub recognized the packet request.  */
1197      if (config->support == PACKET_SUPPORT_UNKNOWN)
1198	{
1199	  if (remote_debug)
1200	    fprintf_unfiltered (gdb_stdlog,
1201				"Packet %s (%s) is supported\n",
1202				config->name, config->title);
1203	  config->support = PACKET_ENABLE;
1204	}
1205      break;
1206    case PACKET_UNKNOWN:
1207      /* The stub does not support the packet.  */
1208      if (config->detect == AUTO_BOOLEAN_AUTO
1209	  && config->support == PACKET_ENABLE)
1210	{
1211	  /* If the stub previously indicated that the packet was
1212	     supported then there is a protocol error.  */
1213	  error (_("Protocol error: %s (%s) conflicting enabled responses."),
1214		 config->name, config->title);
1215	}
1216      else if (config->detect == AUTO_BOOLEAN_TRUE)
1217	{
1218	  /* The user set it wrong.  */
1219	  error (_("Enabled packet %s (%s) not recognized by stub"),
1220		 config->name, config->title);
1221	}
1222
1223      if (remote_debug)
1224	fprintf_unfiltered (gdb_stdlog,
1225			    "Packet %s (%s) is NOT supported\n",
1226			    config->name, config->title);
1227      config->support = PACKET_DISABLE;
1228      break;
1229    }
1230
1231  return result;
1232}
1233
1234enum {
1235  PACKET_vCont = 0,
1236  PACKET_X,
1237  PACKET_qSymbol,
1238  PACKET_P,
1239  PACKET_p,
1240  PACKET_Z0,
1241  PACKET_Z1,
1242  PACKET_Z2,
1243  PACKET_Z3,
1244  PACKET_Z4,
1245  PACKET_vFile_open,
1246  PACKET_vFile_pread,
1247  PACKET_vFile_pwrite,
1248  PACKET_vFile_close,
1249  PACKET_vFile_unlink,
1250  PACKET_vFile_readlink,
1251  PACKET_qXfer_auxv,
1252  PACKET_qXfer_features,
1253  PACKET_qXfer_libraries,
1254  PACKET_qXfer_libraries_svr4,
1255  PACKET_qXfer_memory_map,
1256  PACKET_qXfer_spu_read,
1257  PACKET_qXfer_spu_write,
1258  PACKET_qXfer_osdata,
1259  PACKET_qXfer_threads,
1260  PACKET_qXfer_statictrace_read,
1261  PACKET_qXfer_traceframe_info,
1262  PACKET_qXfer_uib,
1263  PACKET_qGetTIBAddr,
1264  PACKET_qGetTLSAddr,
1265  PACKET_qSupported,
1266  PACKET_qTStatus,
1267  PACKET_QPassSignals,
1268  PACKET_QProgramSignals,
1269  PACKET_qCRC,
1270  PACKET_qSearch_memory,
1271  PACKET_vAttach,
1272  PACKET_vRun,
1273  PACKET_QStartNoAckMode,
1274  PACKET_vKill,
1275  PACKET_qXfer_siginfo_read,
1276  PACKET_qXfer_siginfo_write,
1277  PACKET_qAttached,
1278
1279  /* Support for conditional tracepoints.  */
1280  PACKET_ConditionalTracepoints,
1281
1282  /* Support for target-side breakpoint conditions.  */
1283  PACKET_ConditionalBreakpoints,
1284
1285  /* Support for target-side breakpoint commands.  */
1286  PACKET_BreakpointCommands,
1287
1288  /* Support for fast tracepoints.  */
1289  PACKET_FastTracepoints,
1290
1291  /* Support for static tracepoints.  */
1292  PACKET_StaticTracepoints,
1293
1294  /* Support for installing tracepoints while a trace experiment is
1295     running.  */
1296  PACKET_InstallInTrace,
1297
1298  PACKET_bc,
1299  PACKET_bs,
1300  PACKET_TracepointSource,
1301  PACKET_QAllow,
1302  PACKET_qXfer_fdpic,
1303  PACKET_QDisableRandomization,
1304  PACKET_QAgent,
1305  PACKET_QTBuffer_size,
1306  PACKET_Qbtrace_off,
1307  PACKET_Qbtrace_bts,
1308  PACKET_qXfer_btrace,
1309
1310  /* Support for the QNonStop packet.  */
1311  PACKET_QNonStop,
1312
1313  /* Support for multi-process extensions.  */
1314  PACKET_multiprocess_feature,
1315
1316  /* Support for enabling and disabling tracepoints while a trace
1317     experiment is running.  */
1318  PACKET_EnableDisableTracepoints_feature,
1319
1320  /* Support for collecting strings using the tracenz bytecode.  */
1321  PACKET_tracenz_feature,
1322
1323  /* Support for continuing to run a trace experiment while GDB is
1324     disconnected.  */
1325  PACKET_DisconnectedTracing_feature,
1326
1327  /* Support for qXfer:libraries-svr4:read with a non-empty annex.  */
1328  PACKET_augmented_libraries_svr4_read_feature,
1329
1330  PACKET_MAX
1331};
1332
1333static struct packet_config remote_protocol_packets[PACKET_MAX];
1334
1335/* Returns whether a given packet or feature is supported.  This takes
1336   into account the state of the corresponding "set remote foo-packet"
1337   command, which may be used to bypass auto-detection.  */
1338
1339static enum packet_support
1340packet_config_support (struct packet_config *config)
1341{
1342  switch (config->detect)
1343    {
1344    case AUTO_BOOLEAN_TRUE:
1345      return PACKET_ENABLE;
1346    case AUTO_BOOLEAN_FALSE:
1347      return PACKET_DISABLE;
1348    case AUTO_BOOLEAN_AUTO:
1349      return config->support;
1350    default:
1351      gdb_assert_not_reached (_("bad switch"));
1352    }
1353}
1354
1355/* Same as packet_config_support, but takes the packet's enum value as
1356   argument.  */
1357
1358static enum packet_support
1359packet_support (int packet)
1360{
1361  struct packet_config *config = &remote_protocol_packets[packet];
1362
1363  return packet_config_support (config);
1364}
1365
1366static void
1367show_remote_protocol_packet_cmd (struct ui_file *file, int from_tty,
1368				 struct cmd_list_element *c,
1369				 const char *value)
1370{
1371  struct packet_config *packet;
1372
1373  for (packet = remote_protocol_packets;
1374       packet < &remote_protocol_packets[PACKET_MAX];
1375       packet++)
1376    {
1377      if (&packet->detect == c->var)
1378	{
1379	  show_packet_config_cmd (packet);
1380	  return;
1381	}
1382    }
1383  internal_error (__FILE__, __LINE__, _("Could not find config for %s"),
1384		  c->name);
1385}
1386
1387/* Should we try one of the 'Z' requests?  */
1388
1389enum Z_packet_type
1390{
1391  Z_PACKET_SOFTWARE_BP,
1392  Z_PACKET_HARDWARE_BP,
1393  Z_PACKET_WRITE_WP,
1394  Z_PACKET_READ_WP,
1395  Z_PACKET_ACCESS_WP,
1396  NR_Z_PACKET_TYPES
1397};
1398
1399/* For compatibility with older distributions.  Provide a ``set remote
1400   Z-packet ...'' command that updates all the Z packet types.  */
1401
1402static enum auto_boolean remote_Z_packet_detect;
1403
1404static void
1405set_remote_protocol_Z_packet_cmd (char *args, int from_tty,
1406				  struct cmd_list_element *c)
1407{
1408  int i;
1409
1410  for (i = 0; i < NR_Z_PACKET_TYPES; i++)
1411    remote_protocol_packets[PACKET_Z0 + i].detect = remote_Z_packet_detect;
1412}
1413
1414static void
1415show_remote_protocol_Z_packet_cmd (struct ui_file *file, int from_tty,
1416				   struct cmd_list_element *c,
1417				   const char *value)
1418{
1419  int i;
1420
1421  for (i = 0; i < NR_Z_PACKET_TYPES; i++)
1422    {
1423      show_packet_config_cmd (&remote_protocol_packets[PACKET_Z0 + i]);
1424    }
1425}
1426
1427/* Returns true if the multi-process extensions are in effect.  */
1428
1429static int
1430remote_multi_process_p (struct remote_state *rs)
1431{
1432  return packet_support (PACKET_multiprocess_feature) == PACKET_ENABLE;
1433}
1434
1435/* Tokens for use by the asynchronous signal handlers for SIGINT.  */
1436static struct async_signal_handler *async_sigint_remote_twice_token;
1437static struct async_signal_handler *async_sigint_remote_token;
1438
1439
1440/* Asynchronous signal handle registered as event loop source for
1441   when we have pending events ready to be passed to the core.  */
1442
1443static struct async_event_handler *remote_async_inferior_event_token;
1444
1445
1446
1447static ptid_t magic_null_ptid;
1448static ptid_t not_sent_ptid;
1449static ptid_t any_thread_ptid;
1450
1451/* Find out if the stub attached to PID (and hence GDB should offer to
1452   detach instead of killing it when bailing out).  */
1453
1454static int
1455remote_query_attached (int pid)
1456{
1457  struct remote_state *rs = get_remote_state ();
1458  size_t size = get_remote_packet_size ();
1459
1460  if (packet_support (PACKET_qAttached) == PACKET_DISABLE)
1461    return 0;
1462
1463  if (remote_multi_process_p (rs))
1464    xsnprintf (rs->buf, size, "qAttached:%x", pid);
1465  else
1466    xsnprintf (rs->buf, size, "qAttached");
1467
1468  putpkt (rs->buf);
1469  getpkt (&rs->buf, &rs->buf_size, 0);
1470
1471  switch (packet_ok (rs->buf,
1472		     &remote_protocol_packets[PACKET_qAttached]))
1473    {
1474    case PACKET_OK:
1475      if (strcmp (rs->buf, "1") == 0)
1476	return 1;
1477      break;
1478    case PACKET_ERROR:
1479      warning (_("Remote failure reply: %s"), rs->buf);
1480      break;
1481    case PACKET_UNKNOWN:
1482      break;
1483    }
1484
1485  return 0;
1486}
1487
1488/* Add PID to GDB's inferior table.  If FAKE_PID_P is true, then PID
1489   has been invented by GDB, instead of reported by the target.  Since
1490   we can be connected to a remote system before before knowing about
1491   any inferior, mark the target with execution when we find the first
1492   inferior.  If ATTACHED is 1, then we had just attached to this
1493   inferior.  If it is 0, then we just created this inferior.  If it
1494   is -1, then try querying the remote stub to find out if it had
1495   attached to the inferior or not.  */
1496
1497static struct inferior *
1498remote_add_inferior (int fake_pid_p, int pid, int attached)
1499{
1500  struct inferior *inf;
1501
1502  /* Check whether this process we're learning about is to be
1503     considered attached, or if is to be considered to have been
1504     spawned by the stub.  */
1505  if (attached == -1)
1506    attached = remote_query_attached (pid);
1507
1508  if (gdbarch_has_global_solist (target_gdbarch ()))
1509    {
1510      /* If the target shares code across all inferiors, then every
1511	 attach adds a new inferior.  */
1512      inf = add_inferior (pid);
1513
1514      /* ... and every inferior is bound to the same program space.
1515	 However, each inferior may still have its own address
1516	 space.  */
1517      inf->aspace = maybe_new_address_space ();
1518      inf->pspace = current_program_space;
1519    }
1520  else
1521    {
1522      /* In the traditional debugging scenario, there's a 1-1 match
1523	 between program/address spaces.  We simply bind the inferior
1524	 to the program space's address space.  */
1525      inf = current_inferior ();
1526      inferior_appeared (inf, pid);
1527    }
1528
1529  inf->attach_flag = attached;
1530  inf->fake_pid_p = fake_pid_p;
1531
1532  return inf;
1533}
1534
1535/* Add thread PTID to GDB's thread list.  Tag it as executing/running
1536   according to RUNNING.  */
1537
1538static void
1539remote_add_thread (ptid_t ptid, int running)
1540{
1541  struct remote_state *rs = get_remote_state ();
1542
1543  /* GDB historically didn't pull threads in the initial connection
1544     setup.  If the remote target doesn't even have a concept of
1545     threads (e.g., a bare-metal target), even if internally we
1546     consider that a single-threaded target, mentioning a new thread
1547     might be confusing to the user.  Be silent then, preserving the
1548     age old behavior.  */
1549  if (rs->starting_up)
1550    add_thread_silent (ptid);
1551  else
1552    add_thread (ptid);
1553
1554  set_executing (ptid, running);
1555  set_running (ptid, running);
1556}
1557
1558/* Come here when we learn about a thread id from the remote target.
1559   It may be the first time we hear about such thread, so take the
1560   opportunity to add it to GDB's thread list.  In case this is the
1561   first time we're noticing its corresponding inferior, add it to
1562   GDB's inferior list as well.  */
1563
1564static void
1565remote_notice_new_inferior (ptid_t currthread, int running)
1566{
1567  /* If this is a new thread, add it to GDB's thread list.
1568     If we leave it up to WFI to do this, bad things will happen.  */
1569
1570  if (in_thread_list (currthread) && is_exited (currthread))
1571    {
1572      /* We're seeing an event on a thread id we knew had exited.
1573	 This has to be a new thread reusing the old id.  Add it.  */
1574      remote_add_thread (currthread, running);
1575      return;
1576    }
1577
1578  if (!in_thread_list (currthread))
1579    {
1580      struct inferior *inf = NULL;
1581      int pid = ptid_get_pid (currthread);
1582
1583      if (ptid_is_pid (inferior_ptid)
1584	  && pid == ptid_get_pid (inferior_ptid))
1585	{
1586	  /* inferior_ptid has no thread member yet.  This can happen
1587	     with the vAttach -> remote_wait,"TAAthread:" path if the
1588	     stub doesn't support qC.  This is the first stop reported
1589	     after an attach, so this is the main thread.  Update the
1590	     ptid in the thread list.  */
1591	  if (in_thread_list (pid_to_ptid (pid)))
1592	    thread_change_ptid (inferior_ptid, currthread);
1593	  else
1594	    {
1595	      remote_add_thread (currthread, running);
1596	      inferior_ptid = currthread;
1597	    }
1598	  return;
1599	}
1600
1601      if (ptid_equal (magic_null_ptid, inferior_ptid))
1602	{
1603	  /* inferior_ptid is not set yet.  This can happen with the
1604	     vRun -> remote_wait,"TAAthread:" path if the stub
1605	     doesn't support qC.  This is the first stop reported
1606	     after an attach, so this is the main thread.  Update the
1607	     ptid in the thread list.  */
1608	  thread_change_ptid (inferior_ptid, currthread);
1609	  return;
1610	}
1611
1612      /* When connecting to a target remote, or to a target
1613	 extended-remote which already was debugging an inferior, we
1614	 may not know about it yet.  Add it before adding its child
1615	 thread, so notifications are emitted in a sensible order.  */
1616      if (!in_inferior_list (ptid_get_pid (currthread)))
1617	{
1618	  struct remote_state *rs = get_remote_state ();
1619	  int fake_pid_p = !remote_multi_process_p (rs);
1620
1621	  inf = remote_add_inferior (fake_pid_p,
1622				     ptid_get_pid (currthread), -1);
1623	}
1624
1625      /* This is really a new thread.  Add it.  */
1626      remote_add_thread (currthread, running);
1627
1628      /* If we found a new inferior, let the common code do whatever
1629	 it needs to with it (e.g., read shared libraries, insert
1630	 breakpoints), unless we're just setting up an all-stop
1631	 connection.  */
1632      if (inf != NULL)
1633	{
1634	  struct remote_state *rs = get_remote_state ();
1635
1636	  if (non_stop || !rs->starting_up)
1637	    notice_new_inferior (currthread, running, 0);
1638	}
1639    }
1640}
1641
1642/* Return the private thread data, creating it if necessary.  */
1643
1644static struct private_thread_info *
1645demand_private_info (ptid_t ptid)
1646{
1647  struct thread_info *info = find_thread_ptid (ptid);
1648
1649  gdb_assert (info);
1650
1651  if (!info->private)
1652    {
1653      info->private = xmalloc (sizeof (*(info->private)));
1654      info->private_dtor = free_private_thread_info;
1655      info->private->core = -1;
1656      info->private->extra = 0;
1657    }
1658
1659  return info->private;
1660}
1661
1662/* Call this function as a result of
1663   1) A halt indication (T packet) containing a thread id
1664   2) A direct query of currthread
1665   3) Successful execution of set thread */
1666
1667static void
1668record_currthread (struct remote_state *rs, ptid_t currthread)
1669{
1670  rs->general_thread = currthread;
1671}
1672
1673/* If 'QPassSignals' is supported, tell the remote stub what signals
1674   it can simply pass through to the inferior without reporting.  */
1675
1676static void
1677remote_pass_signals (struct target_ops *self,
1678		     int numsigs, unsigned char *pass_signals)
1679{
1680  if (packet_support (PACKET_QPassSignals) != PACKET_DISABLE)
1681    {
1682      char *pass_packet, *p;
1683      int count = 0, i;
1684      struct remote_state *rs = get_remote_state ();
1685
1686      gdb_assert (numsigs < 256);
1687      for (i = 0; i < numsigs; i++)
1688	{
1689	  if (pass_signals[i])
1690	    count++;
1691	}
1692      pass_packet = xmalloc (count * 3 + strlen ("QPassSignals:") + 1);
1693      strcpy (pass_packet, "QPassSignals:");
1694      p = pass_packet + strlen (pass_packet);
1695      for (i = 0; i < numsigs; i++)
1696	{
1697	  if (pass_signals[i])
1698	    {
1699	      if (i >= 16)
1700		*p++ = tohex (i >> 4);
1701	      *p++ = tohex (i & 15);
1702	      if (count)
1703		*p++ = ';';
1704	      else
1705		break;
1706	      count--;
1707	    }
1708	}
1709      *p = 0;
1710      if (!rs->last_pass_packet || strcmp (rs->last_pass_packet, pass_packet))
1711	{
1712	  putpkt (pass_packet);
1713	  getpkt (&rs->buf, &rs->buf_size, 0);
1714	  packet_ok (rs->buf, &remote_protocol_packets[PACKET_QPassSignals]);
1715	  if (rs->last_pass_packet)
1716	    xfree (rs->last_pass_packet);
1717	  rs->last_pass_packet = pass_packet;
1718	}
1719      else
1720	xfree (pass_packet);
1721    }
1722}
1723
1724/* If 'QProgramSignals' is supported, tell the remote stub what
1725   signals it should pass through to the inferior when detaching.  */
1726
1727static void
1728remote_program_signals (struct target_ops *self,
1729			int numsigs, unsigned char *signals)
1730{
1731  if (packet_support (PACKET_QProgramSignals) != PACKET_DISABLE)
1732    {
1733      char *packet, *p;
1734      int count = 0, i;
1735      struct remote_state *rs = get_remote_state ();
1736
1737      gdb_assert (numsigs < 256);
1738      for (i = 0; i < numsigs; i++)
1739	{
1740	  if (signals[i])
1741	    count++;
1742	}
1743      packet = xmalloc (count * 3 + strlen ("QProgramSignals:") + 1);
1744      strcpy (packet, "QProgramSignals:");
1745      p = packet + strlen (packet);
1746      for (i = 0; i < numsigs; i++)
1747	{
1748	  if (signal_pass_state (i))
1749	    {
1750	      if (i >= 16)
1751		*p++ = tohex (i >> 4);
1752	      *p++ = tohex (i & 15);
1753	      if (count)
1754		*p++ = ';';
1755	      else
1756		break;
1757	      count--;
1758	    }
1759	}
1760      *p = 0;
1761      if (!rs->last_program_signals_packet
1762	  || strcmp (rs->last_program_signals_packet, packet) != 0)
1763	{
1764	  putpkt (packet);
1765	  getpkt (&rs->buf, &rs->buf_size, 0);
1766	  packet_ok (rs->buf, &remote_protocol_packets[PACKET_QProgramSignals]);
1767	  xfree (rs->last_program_signals_packet);
1768	  rs->last_program_signals_packet = packet;
1769	}
1770      else
1771	xfree (packet);
1772    }
1773}
1774
1775/* If PTID is MAGIC_NULL_PTID, don't set any thread.  If PTID is
1776   MINUS_ONE_PTID, set the thread to -1, so the stub returns the
1777   thread.  If GEN is set, set the general thread, if not, then set
1778   the step/continue thread.  */
1779static void
1780set_thread (struct ptid ptid, int gen)
1781{
1782  struct remote_state *rs = get_remote_state ();
1783  ptid_t state = gen ? rs->general_thread : rs->continue_thread;
1784  char *buf = rs->buf;
1785  char *endbuf = rs->buf + get_remote_packet_size ();
1786
1787  if (ptid_equal (state, ptid))
1788    return;
1789
1790  *buf++ = 'H';
1791  *buf++ = gen ? 'g' : 'c';
1792  if (ptid_equal (ptid, magic_null_ptid))
1793    xsnprintf (buf, endbuf - buf, "0");
1794  else if (ptid_equal (ptid, any_thread_ptid))
1795    xsnprintf (buf, endbuf - buf, "0");
1796  else if (ptid_equal (ptid, minus_one_ptid))
1797    xsnprintf (buf, endbuf - buf, "-1");
1798  else
1799    write_ptid (buf, endbuf, ptid);
1800  putpkt (rs->buf);
1801  getpkt (&rs->buf, &rs->buf_size, 0);
1802  if (gen)
1803    rs->general_thread = ptid;
1804  else
1805    rs->continue_thread = ptid;
1806}
1807
1808static void
1809set_general_thread (struct ptid ptid)
1810{
1811  set_thread (ptid, 1);
1812}
1813
1814static void
1815set_continue_thread (struct ptid ptid)
1816{
1817  set_thread (ptid, 0);
1818}
1819
1820/* Change the remote current process.  Which thread within the process
1821   ends up selected isn't important, as long as it is the same process
1822   as what INFERIOR_PTID points to.
1823
1824   This comes from that fact that there is no explicit notion of
1825   "selected process" in the protocol.  The selected process for
1826   general operations is the process the selected general thread
1827   belongs to.  */
1828
1829static void
1830set_general_process (void)
1831{
1832  struct remote_state *rs = get_remote_state ();
1833
1834  /* If the remote can't handle multiple processes, don't bother.  */
1835  if (!rs->extended || !remote_multi_process_p (rs))
1836    return;
1837
1838  /* We only need to change the remote current thread if it's pointing
1839     at some other process.  */
1840  if (ptid_get_pid (rs->general_thread) != ptid_get_pid (inferior_ptid))
1841    set_general_thread (inferior_ptid);
1842}
1843
1844
1845/* Return nonzero if this is the main thread that we made up ourselves
1846   to model non-threaded targets as single-threaded.  */
1847
1848static int
1849remote_thread_always_alive (struct target_ops *ops, ptid_t ptid)
1850{
1851  struct remote_state *rs = get_remote_state ();
1852  char *p, *endp;
1853
1854  if (ptid_equal (ptid, magic_null_ptid))
1855    /* The main thread is always alive.  */
1856    return 1;
1857
1858  if (ptid_get_pid (ptid) != 0 && ptid_get_lwp (ptid) == 0)
1859    /* The main thread is always alive.  This can happen after a
1860       vAttach, if the remote side doesn't support
1861       multi-threading.  */
1862    return 1;
1863
1864  return 0;
1865}
1866
1867/* Return nonzero if the thread PTID is still alive on the remote
1868   system.  */
1869
1870static int
1871remote_thread_alive (struct target_ops *ops, ptid_t ptid)
1872{
1873  struct remote_state *rs = get_remote_state ();
1874  char *p, *endp;
1875
1876  /* Check if this is a thread that we made up ourselves to model
1877     non-threaded targets as single-threaded.  */
1878  if (remote_thread_always_alive (ops, ptid))
1879    return 1;
1880
1881  p = rs->buf;
1882  endp = rs->buf + get_remote_packet_size ();
1883
1884  *p++ = 'T';
1885  write_ptid (p, endp, ptid);
1886
1887  putpkt (rs->buf);
1888  getpkt (&rs->buf, &rs->buf_size, 0);
1889  return (rs->buf[0] == 'O' && rs->buf[1] == 'K');
1890}
1891
1892/* About these extended threadlist and threadinfo packets.  They are
1893   variable length packets but, the fields within them are often fixed
1894   length.  They are redundent enough to send over UDP as is the
1895   remote protocol in general.  There is a matching unit test module
1896   in libstub.  */
1897
1898/* WARNING: This threadref data structure comes from the remote O.S.,
1899   libstub protocol encoding, and remote.c.  It is not particularly
1900   changable.  */
1901
1902/* Right now, the internal structure is int. We want it to be bigger.
1903   Plan to fix this.  */
1904
1905typedef int gdb_threadref;	/* Internal GDB thread reference.  */
1906
1907/* gdb_ext_thread_info is an internal GDB data structure which is
1908   equivalent to the reply of the remote threadinfo packet.  */
1909
1910struct gdb_ext_thread_info
1911  {
1912    threadref threadid;		/* External form of thread reference.  */
1913    int active;			/* Has state interesting to GDB?
1914				   regs, stack.  */
1915    char display[256];		/* Brief state display, name,
1916				   blocked/suspended.  */
1917    char shortname[32];		/* To be used to name threads.  */
1918    char more_display[256];	/* Long info, statistics, queue depth,
1919				   whatever.  */
1920  };
1921
1922/* The volume of remote transfers can be limited by submitting
1923   a mask containing bits specifying the desired information.
1924   Use a union of these values as the 'selection' parameter to
1925   get_thread_info.  FIXME: Make these TAG names more thread specific.  */
1926
1927#define TAG_THREADID 1
1928#define TAG_EXISTS 2
1929#define TAG_DISPLAY 4
1930#define TAG_THREADNAME 8
1931#define TAG_MOREDISPLAY 16
1932
1933#define BUF_THREAD_ID_SIZE (OPAQUETHREADBYTES * 2)
1934
1935static char *unpack_nibble (char *buf, int *val);
1936
1937static char *unpack_byte (char *buf, int *value);
1938
1939static char *pack_int (char *buf, int value);
1940
1941static char *unpack_int (char *buf, int *value);
1942
1943static char *unpack_string (char *src, char *dest, int length);
1944
1945static char *pack_threadid (char *pkt, threadref *id);
1946
1947static char *unpack_threadid (char *inbuf, threadref *id);
1948
1949void int_to_threadref (threadref *id, int value);
1950
1951static int threadref_to_int (threadref *ref);
1952
1953static void copy_threadref (threadref *dest, threadref *src);
1954
1955static int threadmatch (threadref *dest, threadref *src);
1956
1957static char *pack_threadinfo_request (char *pkt, int mode,
1958				      threadref *id);
1959
1960static int remote_unpack_thread_info_response (char *pkt,
1961					       threadref *expectedref,
1962					       struct gdb_ext_thread_info
1963					       *info);
1964
1965
1966static int remote_get_threadinfo (threadref *threadid,
1967				  int fieldset,	/*TAG mask */
1968				  struct gdb_ext_thread_info *info);
1969
1970static char *pack_threadlist_request (char *pkt, int startflag,
1971				      int threadcount,
1972				      threadref *nextthread);
1973
1974static int parse_threadlist_response (char *pkt,
1975				      int result_limit,
1976				      threadref *original_echo,
1977				      threadref *resultlist,
1978				      int *doneflag);
1979
1980static int remote_get_threadlist (int startflag,
1981				  threadref *nextthread,
1982				  int result_limit,
1983				  int *done,
1984				  int *result_count,
1985				  threadref *threadlist);
1986
1987typedef int (*rmt_thread_action) (threadref *ref, void *context);
1988
1989static int remote_threadlist_iterator (rmt_thread_action stepfunction,
1990				       void *context, int looplimit);
1991
1992static int remote_newthread_step (threadref *ref, void *context);
1993
1994
1995/* Write a PTID to BUF.  ENDBUF points to one-passed-the-end of the
1996   buffer we're allowed to write to.  Returns
1997   BUF+CHARACTERS_WRITTEN.  */
1998
1999static char *
2000write_ptid (char *buf, const char *endbuf, ptid_t ptid)
2001{
2002  int pid, tid;
2003  struct remote_state *rs = get_remote_state ();
2004
2005  if (remote_multi_process_p (rs))
2006    {
2007      pid = ptid_get_pid (ptid);
2008      if (pid < 0)
2009	buf += xsnprintf (buf, endbuf - buf, "p-%x.", -pid);
2010      else
2011	buf += xsnprintf (buf, endbuf - buf, "p%x.", pid);
2012    }
2013  tid = ptid_get_lwp (ptid);
2014  if (tid < 0)
2015    buf += xsnprintf (buf, endbuf - buf, "-%x", -tid);
2016  else
2017    buf += xsnprintf (buf, endbuf - buf, "%x", tid);
2018
2019  return buf;
2020}
2021
2022/* Extract a PTID from BUF.  If non-null, OBUF is set to the to one
2023   passed the last parsed char.  Returns null_ptid on error.  */
2024
2025static ptid_t
2026read_ptid (char *buf, char **obuf)
2027{
2028  char *p = buf;
2029  char *pp;
2030  ULONGEST pid = 0, tid = 0;
2031
2032  if (*p == 'p')
2033    {
2034      /* Multi-process ptid.  */
2035      pp = unpack_varlen_hex (p + 1, &pid);
2036      if (*pp != '.')
2037	error (_("invalid remote ptid: %s"), p);
2038
2039      p = pp;
2040      pp = unpack_varlen_hex (p + 1, &tid);
2041      if (obuf)
2042	*obuf = pp;
2043      return ptid_build (pid, tid, 0);
2044    }
2045
2046  /* No multi-process.  Just a tid.  */
2047  pp = unpack_varlen_hex (p, &tid);
2048
2049  /* Since the stub is not sending a process id, then default to
2050     what's in inferior_ptid, unless it's null at this point.  If so,
2051     then since there's no way to know the pid of the reported
2052     threads, use the magic number.  */
2053  if (ptid_equal (inferior_ptid, null_ptid))
2054    pid = ptid_get_pid (magic_null_ptid);
2055  else
2056    pid = ptid_get_pid (inferior_ptid);
2057
2058  if (obuf)
2059    *obuf = pp;
2060  return ptid_build (pid, tid, 0);
2061}
2062
2063static int
2064stubhex (int ch)
2065{
2066  if (ch >= 'a' && ch <= 'f')
2067    return ch - 'a' + 10;
2068  if (ch >= '0' && ch <= '9')
2069    return ch - '0';
2070  if (ch >= 'A' && ch <= 'F')
2071    return ch - 'A' + 10;
2072  return -1;
2073}
2074
2075static int
2076stub_unpack_int (char *buff, int fieldlength)
2077{
2078  int nibble;
2079  int retval = 0;
2080
2081  while (fieldlength)
2082    {
2083      nibble = stubhex (*buff++);
2084      retval |= nibble;
2085      fieldlength--;
2086      if (fieldlength)
2087	retval = retval << 4;
2088    }
2089  return retval;
2090}
2091
2092static char *
2093unpack_nibble (char *buf, int *val)
2094{
2095  *val = fromhex (*buf++);
2096  return buf;
2097}
2098
2099static char *
2100unpack_byte (char *buf, int *value)
2101{
2102  *value = stub_unpack_int (buf, 2);
2103  return buf + 2;
2104}
2105
2106static char *
2107pack_int (char *buf, int value)
2108{
2109  buf = pack_hex_byte (buf, (value >> 24) & 0xff);
2110  buf = pack_hex_byte (buf, (value >> 16) & 0xff);
2111  buf = pack_hex_byte (buf, (value >> 8) & 0x0ff);
2112  buf = pack_hex_byte (buf, (value & 0xff));
2113  return buf;
2114}
2115
2116static char *
2117unpack_int (char *buf, int *value)
2118{
2119  *value = stub_unpack_int (buf, 8);
2120  return buf + 8;
2121}
2122
2123#if 0			/* Currently unused, uncomment when needed.  */
2124static char *pack_string (char *pkt, char *string);
2125
2126static char *
2127pack_string (char *pkt, char *string)
2128{
2129  char ch;
2130  int len;
2131
2132  len = strlen (string);
2133  if (len > 200)
2134    len = 200;		/* Bigger than most GDB packets, junk???  */
2135  pkt = pack_hex_byte (pkt, len);
2136  while (len-- > 0)
2137    {
2138      ch = *string++;
2139      if ((ch == '\0') || (ch == '#'))
2140	ch = '*';		/* Protect encapsulation.  */
2141      *pkt++ = ch;
2142    }
2143  return pkt;
2144}
2145#endif /* 0 (unused) */
2146
2147static char *
2148unpack_string (char *src, char *dest, int length)
2149{
2150  while (length--)
2151    *dest++ = *src++;
2152  *dest = '\0';
2153  return src;
2154}
2155
2156static char *
2157pack_threadid (char *pkt, threadref *id)
2158{
2159  char *limit;
2160  unsigned char *altid;
2161
2162  altid = (unsigned char *) id;
2163  limit = pkt + BUF_THREAD_ID_SIZE;
2164  while (pkt < limit)
2165    pkt = pack_hex_byte (pkt, *altid++);
2166  return pkt;
2167}
2168
2169
2170static char *
2171unpack_threadid (char *inbuf, threadref *id)
2172{
2173  char *altref;
2174  char *limit = inbuf + BUF_THREAD_ID_SIZE;
2175  int x, y;
2176
2177  altref = (char *) id;
2178
2179  while (inbuf < limit)
2180    {
2181      x = stubhex (*inbuf++);
2182      y = stubhex (*inbuf++);
2183      *altref++ = (x << 4) | y;
2184    }
2185  return inbuf;
2186}
2187
2188/* Externally, threadrefs are 64 bits but internally, they are still
2189   ints.  This is due to a mismatch of specifications.  We would like
2190   to use 64bit thread references internally.  This is an adapter
2191   function.  */
2192
2193void
2194int_to_threadref (threadref *id, int value)
2195{
2196  unsigned char *scan;
2197
2198  scan = (unsigned char *) id;
2199  {
2200    int i = 4;
2201    while (i--)
2202      *scan++ = 0;
2203  }
2204  *scan++ = (value >> 24) & 0xff;
2205  *scan++ = (value >> 16) & 0xff;
2206  *scan++ = (value >> 8) & 0xff;
2207  *scan++ = (value & 0xff);
2208}
2209
2210static int
2211threadref_to_int (threadref *ref)
2212{
2213  int i, value = 0;
2214  unsigned char *scan;
2215
2216  scan = *ref;
2217  scan += 4;
2218  i = 4;
2219  while (i-- > 0)
2220    value = (value << 8) | ((*scan++) & 0xff);
2221  return value;
2222}
2223
2224static void
2225copy_threadref (threadref *dest, threadref *src)
2226{
2227  int i;
2228  unsigned char *csrc, *cdest;
2229
2230  csrc = (unsigned char *) src;
2231  cdest = (unsigned char *) dest;
2232  i = 8;
2233  while (i--)
2234    *cdest++ = *csrc++;
2235}
2236
2237static int
2238threadmatch (threadref *dest, threadref *src)
2239{
2240  /* Things are broken right now, so just assume we got a match.  */
2241#if 0
2242  unsigned char *srcp, *destp;
2243  int i, result;
2244  srcp = (char *) src;
2245  destp = (char *) dest;
2246
2247  result = 1;
2248  while (i-- > 0)
2249    result &= (*srcp++ == *destp++) ? 1 : 0;
2250  return result;
2251#endif
2252  return 1;
2253}
2254
2255/*
2256   threadid:1,        # always request threadid
2257   context_exists:2,
2258   display:4,
2259   unique_name:8,
2260   more_display:16
2261 */
2262
2263/* Encoding:  'Q':8,'P':8,mask:32,threadid:64 */
2264
2265static char *
2266pack_threadinfo_request (char *pkt, int mode, threadref *id)
2267{
2268  *pkt++ = 'q';				/* Info Query */
2269  *pkt++ = 'P';				/* process or thread info */
2270  pkt = pack_int (pkt, mode);		/* mode */
2271  pkt = pack_threadid (pkt, id);	/* threadid */
2272  *pkt = '\0';				/* terminate */
2273  return pkt;
2274}
2275
2276/* These values tag the fields in a thread info response packet.  */
2277/* Tagging the fields allows us to request specific fields and to
2278   add more fields as time goes by.  */
2279
2280#define TAG_THREADID 1		/* Echo the thread identifier.  */
2281#define TAG_EXISTS 2		/* Is this process defined enough to
2282				   fetch registers and its stack?  */
2283#define TAG_DISPLAY 4		/* A short thing maybe to put on a window */
2284#define TAG_THREADNAME 8	/* string, maps 1-to-1 with a thread is.  */
2285#define TAG_MOREDISPLAY 16	/* Whatever the kernel wants to say about
2286				   the process.  */
2287
2288static int
2289remote_unpack_thread_info_response (char *pkt, threadref *expectedref,
2290				    struct gdb_ext_thread_info *info)
2291{
2292  struct remote_state *rs = get_remote_state ();
2293  int mask, length;
2294  int tag;
2295  threadref ref;
2296  char *limit = pkt + rs->buf_size; /* Plausible parsing limit.  */
2297  int retval = 1;
2298
2299  /* info->threadid = 0; FIXME: implement zero_threadref.  */
2300  info->active = 0;
2301  info->display[0] = '\0';
2302  info->shortname[0] = '\0';
2303  info->more_display[0] = '\0';
2304
2305  /* Assume the characters indicating the packet type have been
2306     stripped.  */
2307  pkt = unpack_int (pkt, &mask);	/* arg mask */
2308  pkt = unpack_threadid (pkt, &ref);
2309
2310  if (mask == 0)
2311    warning (_("Incomplete response to threadinfo request."));
2312  if (!threadmatch (&ref, expectedref))
2313    {			/* This is an answer to a different request.  */
2314      warning (_("ERROR RMT Thread info mismatch."));
2315      return 0;
2316    }
2317  copy_threadref (&info->threadid, &ref);
2318
2319  /* Loop on tagged fields , try to bail if somthing goes wrong.  */
2320
2321  /* Packets are terminated with nulls.  */
2322  while ((pkt < limit) && mask && *pkt)
2323    {
2324      pkt = unpack_int (pkt, &tag);	/* tag */
2325      pkt = unpack_byte (pkt, &length);	/* length */
2326      if (!(tag & mask))		/* Tags out of synch with mask.  */
2327	{
2328	  warning (_("ERROR RMT: threadinfo tag mismatch."));
2329	  retval = 0;
2330	  break;
2331	}
2332      if (tag == TAG_THREADID)
2333	{
2334	  if (length != 16)
2335	    {
2336	      warning (_("ERROR RMT: length of threadid is not 16."));
2337	      retval = 0;
2338	      break;
2339	    }
2340	  pkt = unpack_threadid (pkt, &ref);
2341	  mask = mask & ~TAG_THREADID;
2342	  continue;
2343	}
2344      if (tag == TAG_EXISTS)
2345	{
2346	  info->active = stub_unpack_int (pkt, length);
2347	  pkt += length;
2348	  mask = mask & ~(TAG_EXISTS);
2349	  if (length > 8)
2350	    {
2351	      warning (_("ERROR RMT: 'exists' length too long."));
2352	      retval = 0;
2353	      break;
2354	    }
2355	  continue;
2356	}
2357      if (tag == TAG_THREADNAME)
2358	{
2359	  pkt = unpack_string (pkt, &info->shortname[0], length);
2360	  mask = mask & ~TAG_THREADNAME;
2361	  continue;
2362	}
2363      if (tag == TAG_DISPLAY)
2364	{
2365	  pkt = unpack_string (pkt, &info->display[0], length);
2366	  mask = mask & ~TAG_DISPLAY;
2367	  continue;
2368	}
2369      if (tag == TAG_MOREDISPLAY)
2370	{
2371	  pkt = unpack_string (pkt, &info->more_display[0], length);
2372	  mask = mask & ~TAG_MOREDISPLAY;
2373	  continue;
2374	}
2375      warning (_("ERROR RMT: unknown thread info tag."));
2376      break;			/* Not a tag we know about.  */
2377    }
2378  return retval;
2379}
2380
2381static int
2382remote_get_threadinfo (threadref *threadid, int fieldset,	/* TAG mask */
2383		       struct gdb_ext_thread_info *info)
2384{
2385  struct remote_state *rs = get_remote_state ();
2386  int result;
2387
2388  pack_threadinfo_request (rs->buf, fieldset, threadid);
2389  putpkt (rs->buf);
2390  getpkt (&rs->buf, &rs->buf_size, 0);
2391
2392  if (rs->buf[0] == '\0')
2393    return 0;
2394
2395  result = remote_unpack_thread_info_response (rs->buf + 2,
2396					       threadid, info);
2397  return result;
2398}
2399
2400/*    Format: i'Q':8,i"L":8,initflag:8,batchsize:16,lastthreadid:32   */
2401
2402static char *
2403pack_threadlist_request (char *pkt, int startflag, int threadcount,
2404			 threadref *nextthread)
2405{
2406  *pkt++ = 'q';			/* info query packet */
2407  *pkt++ = 'L';			/* Process LIST or threadLIST request */
2408  pkt = pack_nibble (pkt, startflag);		/* initflag 1 bytes */
2409  pkt = pack_hex_byte (pkt, threadcount);	/* threadcount 2 bytes */
2410  pkt = pack_threadid (pkt, nextthread);	/* 64 bit thread identifier */
2411  *pkt = '\0';
2412  return pkt;
2413}
2414
2415/* Encoding:   'q':8,'M':8,count:16,done:8,argthreadid:64,(threadid:64)* */
2416
2417static int
2418parse_threadlist_response (char *pkt, int result_limit,
2419			   threadref *original_echo, threadref *resultlist,
2420			   int *doneflag)
2421{
2422  struct remote_state *rs = get_remote_state ();
2423  char *limit;
2424  int count, resultcount, done;
2425
2426  resultcount = 0;
2427  /* Assume the 'q' and 'M chars have been stripped.  */
2428  limit = pkt + (rs->buf_size - BUF_THREAD_ID_SIZE);
2429  /* done parse past here */
2430  pkt = unpack_byte (pkt, &count);	/* count field */
2431  pkt = unpack_nibble (pkt, &done);
2432  /* The first threadid is the argument threadid.  */
2433  pkt = unpack_threadid (pkt, original_echo);	/* should match query packet */
2434  while ((count-- > 0) && (pkt < limit))
2435    {
2436      pkt = unpack_threadid (pkt, resultlist++);
2437      if (resultcount++ >= result_limit)
2438	break;
2439    }
2440  if (doneflag)
2441    *doneflag = done;
2442  return resultcount;
2443}
2444
2445/* Fetch the next batch of threads from the remote.  Returns -1 if the
2446   qL packet is not supported, 0 on error and 1 on success.  */
2447
2448static int
2449remote_get_threadlist (int startflag, threadref *nextthread, int result_limit,
2450		       int *done, int *result_count, threadref *threadlist)
2451{
2452  struct remote_state *rs = get_remote_state ();
2453  int result = 1;
2454
2455  /* Trancate result limit to be smaller than the packet size.  */
2456  if ((((result_limit + 1) * BUF_THREAD_ID_SIZE) + 10)
2457      >= get_remote_packet_size ())
2458    result_limit = (get_remote_packet_size () / BUF_THREAD_ID_SIZE) - 2;
2459
2460  pack_threadlist_request (rs->buf, startflag, result_limit, nextthread);
2461  putpkt (rs->buf);
2462  getpkt (&rs->buf, &rs->buf_size, 0);
2463  if (*rs->buf == '\0')
2464    {
2465      /* Packet not supported.  */
2466      return -1;
2467    }
2468
2469  *result_count =
2470    parse_threadlist_response (rs->buf + 2, result_limit,
2471			       &rs->echo_nextthread, threadlist, done);
2472
2473  if (!threadmatch (&rs->echo_nextthread, nextthread))
2474    {
2475      /* FIXME: This is a good reason to drop the packet.  */
2476      /* Possably, there is a duplicate response.  */
2477      /* Possabilities :
2478         retransmit immediatly - race conditions
2479         retransmit after timeout - yes
2480         exit
2481         wait for packet, then exit
2482       */
2483      warning (_("HMM: threadlist did not echo arg thread, dropping it."));
2484      return 0;			/* I choose simply exiting.  */
2485    }
2486  if (*result_count <= 0)
2487    {
2488      if (*done != 1)
2489	{
2490	  warning (_("RMT ERROR : failed to get remote thread list."));
2491	  result = 0;
2492	}
2493      return result;		/* break; */
2494    }
2495  if (*result_count > result_limit)
2496    {
2497      *result_count = 0;
2498      warning (_("RMT ERROR: threadlist response longer than requested."));
2499      return 0;
2500    }
2501  return result;
2502}
2503
2504/* Fetch the list of remote threads, with the qL packet, and call
2505   STEPFUNCTION for each thread found.  Stops iterating and returns 1
2506   if STEPFUNCTION returns true.  Stops iterating and returns 0 if the
2507   STEPFUNCTION returns false.  If the packet is not supported,
2508   returns -1.  */
2509
2510static int
2511remote_threadlist_iterator (rmt_thread_action stepfunction, void *context,
2512			    int looplimit)
2513{
2514  struct remote_state *rs = get_remote_state ();
2515  int done, i, result_count;
2516  int startflag = 1;
2517  int result = 1;
2518  int loopcount = 0;
2519
2520  done = 0;
2521  while (!done)
2522    {
2523      if (loopcount++ > looplimit)
2524	{
2525	  result = 0;
2526	  warning (_("Remote fetch threadlist -infinite loop-."));
2527	  break;
2528	}
2529      result = remote_get_threadlist (startflag, &rs->nextthread,
2530				      MAXTHREADLISTRESULTS,
2531				      &done, &result_count,
2532				      rs->resultthreadlist);
2533      if (result <= 0)
2534	break;
2535      /* Clear for later iterations.  */
2536      startflag = 0;
2537      /* Setup to resume next batch of thread references, set nextthread.  */
2538      if (result_count >= 1)
2539	copy_threadref (&rs->nextthread,
2540			&rs->resultthreadlist[result_count - 1]);
2541      i = 0;
2542      while (result_count--)
2543	{
2544	  if (!(*stepfunction) (&rs->resultthreadlist[i++], context))
2545	    {
2546	      result = 0;
2547	      break;
2548	    }
2549	}
2550    }
2551  return result;
2552}
2553
2554/* A thread found on the remote target.  */
2555
2556typedef struct thread_item
2557{
2558  /* The thread's PTID.  */
2559  ptid_t ptid;
2560
2561  /* The thread's extra info.  May be NULL.  */
2562  char *extra;
2563
2564  /* The core the thread was running on.  -1 if not known.  */
2565  int core;
2566} thread_item_t;
2567DEF_VEC_O(thread_item_t);
2568
2569/* Context passed around to the various methods listing remote
2570   threads.  As new threads are found, they're added to the ITEMS
2571   vector.  */
2572
2573struct threads_listing_context
2574{
2575  /* The threads found on the remote target.  */
2576  VEC (thread_item_t) *items;
2577};
2578
2579/* Discard the contents of the constructed thread listing context.  */
2580
2581static void
2582clear_threads_listing_context (void *p)
2583{
2584  struct threads_listing_context *context = p;
2585  int i;
2586  struct thread_item *item;
2587
2588  for (i = 0; VEC_iterate (thread_item_t, context->items, i, item); ++i)
2589    xfree (item->extra);
2590
2591  VEC_free (thread_item_t, context->items);
2592}
2593
2594static int
2595remote_newthread_step (threadref *ref, void *data)
2596{
2597  struct threads_listing_context *context = data;
2598  struct thread_item item;
2599  int pid = ptid_get_pid (inferior_ptid);
2600
2601  item.ptid = ptid_build (pid, threadref_to_int (ref), 0);
2602  item.core = -1;
2603  item.extra = NULL;
2604
2605  VEC_safe_push (thread_item_t, context->items, &item);
2606
2607  return 1;			/* continue iterator */
2608}
2609
2610#define CRAZY_MAX_THREADS 1000
2611
2612static ptid_t
2613remote_current_thread (ptid_t oldpid)
2614{
2615  struct remote_state *rs = get_remote_state ();
2616
2617  putpkt ("qC");
2618  getpkt (&rs->buf, &rs->buf_size, 0);
2619  if (rs->buf[0] == 'Q' && rs->buf[1] == 'C')
2620    return read_ptid (&rs->buf[2], NULL);
2621  else
2622    return oldpid;
2623}
2624
2625/* List remote threads using the deprecated qL packet.  */
2626
2627static int
2628remote_get_threads_with_ql (struct target_ops *ops,
2629			    struct threads_listing_context *context)
2630{
2631  if (remote_threadlist_iterator (remote_newthread_step, context,
2632				  CRAZY_MAX_THREADS) >= 0)
2633    return 1;
2634
2635  return 0;
2636}
2637
2638#if defined(HAVE_LIBEXPAT)
2639
2640static void
2641start_thread (struct gdb_xml_parser *parser,
2642	      const struct gdb_xml_element *element,
2643	      void *user_data, VEC(gdb_xml_value_s) *attributes)
2644{
2645  struct threads_listing_context *data = user_data;
2646
2647  struct thread_item item;
2648  char *id;
2649  struct gdb_xml_value *attr;
2650
2651  id = xml_find_attribute (attributes, "id")->value;
2652  item.ptid = read_ptid (id, NULL);
2653
2654  attr = xml_find_attribute (attributes, "core");
2655  if (attr != NULL)
2656    item.core = *(ULONGEST *) attr->value;
2657  else
2658    item.core = -1;
2659
2660  item.extra = 0;
2661
2662  VEC_safe_push (thread_item_t, data->items, &item);
2663}
2664
2665static void
2666end_thread (struct gdb_xml_parser *parser,
2667	    const struct gdb_xml_element *element,
2668	    void *user_data, const char *body_text)
2669{
2670  struct threads_listing_context *data = user_data;
2671
2672  if (body_text && *body_text)
2673    VEC_last (thread_item_t, data->items)->extra = xstrdup (body_text);
2674}
2675
2676const struct gdb_xml_attribute thread_attributes[] = {
2677  { "id", GDB_XML_AF_NONE, NULL, NULL },
2678  { "core", GDB_XML_AF_OPTIONAL, gdb_xml_parse_attr_ulongest, NULL },
2679  { NULL, GDB_XML_AF_NONE, NULL, NULL }
2680};
2681
2682const struct gdb_xml_element thread_children[] = {
2683  { NULL, NULL, NULL, GDB_XML_EF_NONE, NULL, NULL }
2684};
2685
2686const struct gdb_xml_element threads_children[] = {
2687  { "thread", thread_attributes, thread_children,
2688    GDB_XML_EF_REPEATABLE | GDB_XML_EF_OPTIONAL,
2689    start_thread, end_thread },
2690  { NULL, NULL, NULL, GDB_XML_EF_NONE, NULL, NULL }
2691};
2692
2693const struct gdb_xml_element threads_elements[] = {
2694  { "threads", NULL, threads_children,
2695    GDB_XML_EF_NONE, NULL, NULL },
2696  { NULL, NULL, NULL, GDB_XML_EF_NONE, NULL, NULL }
2697};
2698
2699#endif
2700
2701/* List remote threads using qXfer:threads:read.  */
2702
2703static int
2704remote_get_threads_with_qxfer (struct target_ops *ops,
2705			       struct threads_listing_context *context)
2706{
2707#if defined(HAVE_LIBEXPAT)
2708  if (packet_support (PACKET_qXfer_threads) == PACKET_ENABLE)
2709    {
2710      char *xml = target_read_stralloc (ops, TARGET_OBJECT_THREADS, NULL);
2711      struct cleanup *back_to = make_cleanup (xfree, xml);
2712
2713      if (xml != NULL && *xml != '\0')
2714	{
2715	  gdb_xml_parse_quick (_("threads"), "threads.dtd",
2716			       threads_elements, xml, context);
2717	}
2718
2719      do_cleanups (back_to);
2720      return 1;
2721    }
2722#endif
2723
2724  return 0;
2725}
2726
2727/* List remote threads using qfThreadInfo/qsThreadInfo.  */
2728
2729static int
2730remote_get_threads_with_qthreadinfo (struct target_ops *ops,
2731				     struct threads_listing_context *context)
2732{
2733  struct remote_state *rs = get_remote_state ();
2734
2735  if (rs->use_threadinfo_query)
2736    {
2737      char *bufp;
2738
2739      putpkt ("qfThreadInfo");
2740      getpkt (&rs->buf, &rs->buf_size, 0);
2741      bufp = rs->buf;
2742      if (bufp[0] != '\0')		/* q packet recognized */
2743	{
2744	  while (*bufp++ == 'm')	/* reply contains one or more TID */
2745	    {
2746	      do
2747		{
2748		  struct thread_item item;
2749
2750		  item.ptid = read_ptid (bufp, &bufp);
2751		  item.core = -1;
2752		  item.extra = NULL;
2753
2754		  VEC_safe_push (thread_item_t, context->items, &item);
2755		}
2756	      while (*bufp++ == ',');	/* comma-separated list */
2757	      putpkt ("qsThreadInfo");
2758	      getpkt (&rs->buf, &rs->buf_size, 0);
2759	      bufp = rs->buf;
2760	    }
2761	  return 1;
2762	}
2763      else
2764	{
2765	  /* Packet not recognized.  */
2766	  rs->use_threadinfo_query = 0;
2767	}
2768    }
2769
2770  return 0;
2771}
2772
2773/* Implement the to_update_thread_list function for the remote
2774   targets.  */
2775
2776static void
2777remote_update_thread_list (struct target_ops *ops)
2778{
2779  struct remote_state *rs = get_remote_state ();
2780  struct threads_listing_context context;
2781  struct cleanup *old_chain;
2782  int got_list = 0;
2783
2784  context.items = NULL;
2785  old_chain = make_cleanup (clear_threads_listing_context, &context);
2786
2787  /* We have a few different mechanisms to fetch the thread list.  Try
2788     them all, starting with the most preferred one first, falling
2789     back to older methods.  */
2790  if (remote_get_threads_with_qxfer (ops, &context)
2791      || remote_get_threads_with_qthreadinfo (ops, &context)
2792      || remote_get_threads_with_ql (ops, &context))
2793    {
2794      int i;
2795      struct thread_item *item;
2796      struct thread_info *tp, *tmp;
2797
2798      got_list = 1;
2799
2800      if (VEC_empty (thread_item_t, context.items)
2801	  && remote_thread_always_alive (ops, inferior_ptid))
2802	{
2803	  /* Some targets don't really support threads, but still
2804	     reply an (empty) thread list in response to the thread
2805	     listing packets, instead of replying "packet not
2806	     supported".  Exit early so we don't delete the main
2807	     thread.  */
2808	  do_cleanups (old_chain);
2809	  return;
2810	}
2811
2812      /* CONTEXT now holds the current thread list on the remote
2813	 target end.  Delete GDB-side threads no longer found on the
2814	 target.  */
2815      ALL_NON_EXITED_THREADS_SAFE (tp, tmp)
2816        {
2817	  for (i = 0;
2818	       VEC_iterate (thread_item_t, context.items, i, item);
2819	       ++i)
2820	    {
2821	      if (ptid_equal (item->ptid, tp->ptid))
2822		break;
2823	    }
2824
2825	  if (i == VEC_length (thread_item_t, context.items))
2826	    {
2827	      /* Not found.  */
2828	      delete_thread (tp->ptid);
2829	    }
2830        }
2831
2832      /* And now add threads we don't know about yet to our list.  */
2833      for (i = 0;
2834	   VEC_iterate (thread_item_t, context.items, i, item);
2835	   ++i)
2836	{
2837	  if (!ptid_equal (item->ptid, null_ptid))
2838	    {
2839	      struct private_thread_info *info;
2840	      /* In non-stop mode, we assume new found threads are
2841		 running until proven otherwise with a stop reply.  In
2842		 all-stop, we can only get here if all threads are
2843		 stopped.  */
2844	      int running = non_stop ? 1 : 0;
2845
2846	      remote_notice_new_inferior (item->ptid, running);
2847
2848	      info = demand_private_info (item->ptid);
2849	      info->core = item->core;
2850	      info->extra = item->extra;
2851	      item->extra = NULL;
2852	    }
2853	}
2854    }
2855
2856  if (!got_list)
2857    {
2858      /* If no thread listing method is supported, then query whether
2859	 each known thread is alive, one by one, with the T packet.
2860	 If the target doesn't support threads at all, then this is a
2861	 no-op.  See remote_thread_alive.  */
2862      prune_threads ();
2863    }
2864
2865  do_cleanups (old_chain);
2866}
2867
2868/*
2869 * Collect a descriptive string about the given thread.
2870 * The target may say anything it wants to about the thread
2871 * (typically info about its blocked / runnable state, name, etc.).
2872 * This string will appear in the info threads display.
2873 *
2874 * Optional: targets are not required to implement this function.
2875 */
2876
2877static char *
2878remote_threads_extra_info (struct target_ops *self, struct thread_info *tp)
2879{
2880  struct remote_state *rs = get_remote_state ();
2881  int result;
2882  int set;
2883  threadref id;
2884  struct gdb_ext_thread_info threadinfo;
2885  static char display_buf[100];	/* arbitrary...  */
2886  int n = 0;                    /* position in display_buf */
2887
2888  if (rs->remote_desc == 0)		/* paranoia */
2889    internal_error (__FILE__, __LINE__,
2890		    _("remote_threads_extra_info"));
2891
2892  if (ptid_equal (tp->ptid, magic_null_ptid)
2893      || (ptid_get_pid (tp->ptid) != 0 && ptid_get_lwp (tp->ptid) == 0))
2894    /* This is the main thread which was added by GDB.  The remote
2895       server doesn't know about it.  */
2896    return NULL;
2897
2898  if (packet_support (PACKET_qXfer_threads) == PACKET_ENABLE)
2899    {
2900      struct thread_info *info = find_thread_ptid (tp->ptid);
2901
2902      if (info && info->private)
2903	return info->private->extra;
2904      else
2905	return NULL;
2906    }
2907
2908  if (rs->use_threadextra_query)
2909    {
2910      char *b = rs->buf;
2911      char *endb = rs->buf + get_remote_packet_size ();
2912
2913      xsnprintf (b, endb - b, "qThreadExtraInfo,");
2914      b += strlen (b);
2915      write_ptid (b, endb, tp->ptid);
2916
2917      putpkt (rs->buf);
2918      getpkt (&rs->buf, &rs->buf_size, 0);
2919      if (rs->buf[0] != 0)
2920	{
2921	  n = min (strlen (rs->buf) / 2, sizeof (display_buf));
2922	  result = hex2bin (rs->buf, (gdb_byte *) display_buf, n);
2923	  display_buf [result] = '\0';
2924	  return display_buf;
2925	}
2926    }
2927
2928  /* If the above query fails, fall back to the old method.  */
2929  rs->use_threadextra_query = 0;
2930  set = TAG_THREADID | TAG_EXISTS | TAG_THREADNAME
2931    | TAG_MOREDISPLAY | TAG_DISPLAY;
2932  int_to_threadref (&id, ptid_get_lwp (tp->ptid));
2933  if (remote_get_threadinfo (&id, set, &threadinfo))
2934    if (threadinfo.active)
2935      {
2936	if (*threadinfo.shortname)
2937	  n += xsnprintf (&display_buf[0], sizeof (display_buf) - n,
2938			  " Name: %s,", threadinfo.shortname);
2939	if (*threadinfo.display)
2940	  n += xsnprintf (&display_buf[n], sizeof (display_buf) - n,
2941			  " State: %s,", threadinfo.display);
2942	if (*threadinfo.more_display)
2943	  n += xsnprintf (&display_buf[n], sizeof (display_buf) - n,
2944			  " Priority: %s", threadinfo.more_display);
2945
2946	if (n > 0)
2947	  {
2948	    /* For purely cosmetic reasons, clear up trailing commas.  */
2949	    if (',' == display_buf[n-1])
2950	      display_buf[n-1] = ' ';
2951	    return display_buf;
2952	  }
2953      }
2954  return NULL;
2955}
2956
2957
2958static int
2959remote_static_tracepoint_marker_at (struct target_ops *self, CORE_ADDR addr,
2960				    struct static_tracepoint_marker *marker)
2961{
2962  struct remote_state *rs = get_remote_state ();
2963  char *p = rs->buf;
2964
2965  xsnprintf (p, get_remote_packet_size (), "qTSTMat:");
2966  p += strlen (p);
2967  p += hexnumstr (p, addr);
2968  putpkt (rs->buf);
2969  getpkt (&rs->buf, &rs->buf_size, 0);
2970  p = rs->buf;
2971
2972  if (*p == 'E')
2973    error (_("Remote failure reply: %s"), p);
2974
2975  if (*p++ == 'm')
2976    {
2977      parse_static_tracepoint_marker_definition (p, &p, marker);
2978      return 1;
2979    }
2980
2981  return 0;
2982}
2983
2984static VEC(static_tracepoint_marker_p) *
2985remote_static_tracepoint_markers_by_strid (struct target_ops *self,
2986					   const char *strid)
2987{
2988  struct remote_state *rs = get_remote_state ();
2989  VEC(static_tracepoint_marker_p) *markers = NULL;
2990  struct static_tracepoint_marker *marker = NULL;
2991  struct cleanup *old_chain;
2992  char *p;
2993
2994  /* Ask for a first packet of static tracepoint marker
2995     definition.  */
2996  putpkt ("qTfSTM");
2997  getpkt (&rs->buf, &rs->buf_size, 0);
2998  p = rs->buf;
2999  if (*p == 'E')
3000    error (_("Remote failure reply: %s"), p);
3001
3002  old_chain = make_cleanup (free_current_marker, &marker);
3003
3004  while (*p++ == 'm')
3005    {
3006      if (marker == NULL)
3007	marker = XCNEW (struct static_tracepoint_marker);
3008
3009      do
3010	{
3011	  parse_static_tracepoint_marker_definition (p, &p, marker);
3012
3013	  if (strid == NULL || strcmp (strid, marker->str_id) == 0)
3014	    {
3015	      VEC_safe_push (static_tracepoint_marker_p,
3016			     markers, marker);
3017	      marker = NULL;
3018	    }
3019	  else
3020	    {
3021	      release_static_tracepoint_marker (marker);
3022	      memset (marker, 0, sizeof (*marker));
3023	    }
3024	}
3025      while (*p++ == ',');	/* comma-separated list */
3026      /* Ask for another packet of static tracepoint definition.  */
3027      putpkt ("qTsSTM");
3028      getpkt (&rs->buf, &rs->buf_size, 0);
3029      p = rs->buf;
3030    }
3031
3032  do_cleanups (old_chain);
3033  return markers;
3034}
3035
3036
3037/* Implement the to_get_ada_task_ptid function for the remote targets.  */
3038
3039static ptid_t
3040remote_get_ada_task_ptid (struct target_ops *self, long lwp, long thread)
3041{
3042  return ptid_build (ptid_get_pid (inferior_ptid), lwp, 0);
3043}
3044
3045
3046/* Restart the remote side; this is an extended protocol operation.  */
3047
3048static void
3049extended_remote_restart (void)
3050{
3051  struct remote_state *rs = get_remote_state ();
3052
3053  /* Send the restart command; for reasons I don't understand the
3054     remote side really expects a number after the "R".  */
3055  xsnprintf (rs->buf, get_remote_packet_size (), "R%x", 0);
3056  putpkt (rs->buf);
3057
3058  remote_fileio_reset ();
3059}
3060
3061/* Clean up connection to a remote debugger.  */
3062
3063static void
3064remote_close (struct target_ops *self)
3065{
3066  struct remote_state *rs = get_remote_state ();
3067
3068  if (rs->remote_desc == NULL)
3069    return; /* already closed */
3070
3071  /* Make sure we leave stdin registered in the event loop, and we
3072     don't leave the async SIGINT signal handler installed.  */
3073  remote_terminal_ours (self);
3074
3075  serial_close (rs->remote_desc);
3076  rs->remote_desc = NULL;
3077
3078  /* We don't have a connection to the remote stub anymore.  Get rid
3079     of all the inferiors and their threads we were controlling.
3080     Reset inferior_ptid to null_ptid first, as otherwise has_stack_frame
3081     will be unable to find the thread corresponding to (pid, 0, 0).  */
3082  inferior_ptid = null_ptid;
3083  discard_all_inferiors ();
3084
3085  /* We are closing the remote target, so we should discard
3086     everything of this target.  */
3087  discard_pending_stop_replies_in_queue (rs);
3088
3089  if (remote_async_inferior_event_token)
3090    delete_async_event_handler (&remote_async_inferior_event_token);
3091
3092  remote_notif_state_xfree (rs->notif_state);
3093
3094  trace_reset_local_state ();
3095}
3096
3097/* Query the remote side for the text, data and bss offsets.  */
3098
3099static void
3100get_offsets (void)
3101{
3102  struct remote_state *rs = get_remote_state ();
3103  char *buf;
3104  char *ptr;
3105  int lose, num_segments = 0, do_sections, do_segments;
3106  CORE_ADDR text_addr, data_addr, bss_addr, segments[2];
3107  struct section_offsets *offs;
3108  struct symfile_segment_data *data;
3109
3110  if (symfile_objfile == NULL)
3111    return;
3112
3113  putpkt ("qOffsets");
3114  getpkt (&rs->buf, &rs->buf_size, 0);
3115  buf = rs->buf;
3116
3117  if (buf[0] == '\000')
3118    return;			/* Return silently.  Stub doesn't support
3119				   this command.  */
3120  if (buf[0] == 'E')
3121    {
3122      warning (_("Remote failure reply: %s"), buf);
3123      return;
3124    }
3125
3126  /* Pick up each field in turn.  This used to be done with scanf, but
3127     scanf will make trouble if CORE_ADDR size doesn't match
3128     conversion directives correctly.  The following code will work
3129     with any size of CORE_ADDR.  */
3130  text_addr = data_addr = bss_addr = 0;
3131  ptr = buf;
3132  lose = 0;
3133
3134  if (strncmp (ptr, "Text=", 5) == 0)
3135    {
3136      ptr += 5;
3137      /* Don't use strtol, could lose on big values.  */
3138      while (*ptr && *ptr != ';')
3139	text_addr = (text_addr << 4) + fromhex (*ptr++);
3140
3141      if (strncmp (ptr, ";Data=", 6) == 0)
3142	{
3143	  ptr += 6;
3144	  while (*ptr && *ptr != ';')
3145	    data_addr = (data_addr << 4) + fromhex (*ptr++);
3146	}
3147      else
3148	lose = 1;
3149
3150      if (!lose && strncmp (ptr, ";Bss=", 5) == 0)
3151	{
3152	  ptr += 5;
3153	  while (*ptr && *ptr != ';')
3154	    bss_addr = (bss_addr << 4) + fromhex (*ptr++);
3155
3156	  if (bss_addr != data_addr)
3157	    warning (_("Target reported unsupported offsets: %s"), buf);
3158	}
3159      else
3160	lose = 1;
3161    }
3162  else if (strncmp (ptr, "TextSeg=", 8) == 0)
3163    {
3164      ptr += 8;
3165      /* Don't use strtol, could lose on big values.  */
3166      while (*ptr && *ptr != ';')
3167	text_addr = (text_addr << 4) + fromhex (*ptr++);
3168      num_segments = 1;
3169
3170      if (strncmp (ptr, ";DataSeg=", 9) == 0)
3171	{
3172	  ptr += 9;
3173	  while (*ptr && *ptr != ';')
3174	    data_addr = (data_addr << 4) + fromhex (*ptr++);
3175	  num_segments++;
3176	}
3177    }
3178  else
3179    lose = 1;
3180
3181  if (lose)
3182    error (_("Malformed response to offset query, %s"), buf);
3183  else if (*ptr != '\0')
3184    warning (_("Target reported unsupported offsets: %s"), buf);
3185
3186  offs = ((struct section_offsets *)
3187	  alloca (SIZEOF_N_SECTION_OFFSETS (symfile_objfile->num_sections)));
3188  memcpy (offs, symfile_objfile->section_offsets,
3189	  SIZEOF_N_SECTION_OFFSETS (symfile_objfile->num_sections));
3190
3191  data = get_symfile_segment_data (symfile_objfile->obfd);
3192  do_segments = (data != NULL);
3193  do_sections = num_segments == 0;
3194
3195  if (num_segments > 0)
3196    {
3197      segments[0] = text_addr;
3198      segments[1] = data_addr;
3199    }
3200  /* If we have two segments, we can still try to relocate everything
3201     by assuming that the .text and .data offsets apply to the whole
3202     text and data segments.  Convert the offsets given in the packet
3203     to base addresses for symfile_map_offsets_to_segments.  */
3204  else if (data && data->num_segments == 2)
3205    {
3206      segments[0] = data->segment_bases[0] + text_addr;
3207      segments[1] = data->segment_bases[1] + data_addr;
3208      num_segments = 2;
3209    }
3210  /* If the object file has only one segment, assume that it is text
3211     rather than data; main programs with no writable data are rare,
3212     but programs with no code are useless.  Of course the code might
3213     have ended up in the data segment... to detect that we would need
3214     the permissions here.  */
3215  else if (data && data->num_segments == 1)
3216    {
3217      segments[0] = data->segment_bases[0] + text_addr;
3218      num_segments = 1;
3219    }
3220  /* There's no way to relocate by segment.  */
3221  else
3222    do_segments = 0;
3223
3224  if (do_segments)
3225    {
3226      int ret = symfile_map_offsets_to_segments (symfile_objfile->obfd, data,
3227						 offs, num_segments, segments);
3228
3229      if (ret == 0 && !do_sections)
3230	error (_("Can not handle qOffsets TextSeg "
3231		 "response with this symbol file"));
3232
3233      if (ret > 0)
3234	do_sections = 0;
3235    }
3236
3237  if (data)
3238    free_symfile_segment_data (data);
3239
3240  if (do_sections)
3241    {
3242      offs->offsets[SECT_OFF_TEXT (symfile_objfile)] = text_addr;
3243
3244      /* This is a temporary kludge to force data and bss to use the
3245	 same offsets because that's what nlmconv does now.  The real
3246	 solution requires changes to the stub and remote.c that I
3247	 don't have time to do right now.  */
3248
3249      offs->offsets[SECT_OFF_DATA (symfile_objfile)] = data_addr;
3250      offs->offsets[SECT_OFF_BSS (symfile_objfile)] = data_addr;
3251    }
3252
3253  objfile_relocate (symfile_objfile, offs);
3254}
3255
3256/* Callback for iterate_over_threads.  Set the STOP_REQUESTED flags in
3257   threads we know are stopped already.  This is used during the
3258   initial remote connection in non-stop mode --- threads that are
3259   reported as already being stopped are left stopped.  */
3260
3261static int
3262set_stop_requested_callback (struct thread_info *thread, void *data)
3263{
3264  /* If we have a stop reply for this thread, it must be stopped.  */
3265  if (peek_stop_reply (thread->ptid))
3266    set_stop_requested (thread->ptid, 1);
3267
3268  return 0;
3269}
3270
3271/* Send interrupt_sequence to remote target.  */
3272static void
3273send_interrupt_sequence (void)
3274{
3275  struct remote_state *rs = get_remote_state ();
3276
3277  if (interrupt_sequence_mode == interrupt_sequence_control_c)
3278    remote_serial_write ("\x03", 1);
3279  else if (interrupt_sequence_mode == interrupt_sequence_break)
3280    serial_send_break (rs->remote_desc);
3281  else if (interrupt_sequence_mode == interrupt_sequence_break_g)
3282    {
3283      serial_send_break (rs->remote_desc);
3284      remote_serial_write ("g", 1);
3285    }
3286  else
3287    internal_error (__FILE__, __LINE__,
3288		    _("Invalid value for interrupt_sequence_mode: %s."),
3289		    interrupt_sequence_mode);
3290}
3291
3292
3293/* If STOP_REPLY is a T stop reply, look for the "thread" register,
3294   and extract the PTID.  Returns NULL_PTID if not found.  */
3295
3296static ptid_t
3297stop_reply_extract_thread (char *stop_reply)
3298{
3299  if (stop_reply[0] == 'T' && strlen (stop_reply) > 3)
3300    {
3301      char *p;
3302
3303      /* Txx r:val ; r:val (...)  */
3304      p = &stop_reply[3];
3305
3306      /* Look for "register" named "thread".  */
3307      while (*p != '\0')
3308	{
3309	  char *p1;
3310
3311	  p1 = strchr (p, ':');
3312	  if (p1 == NULL)
3313	    return null_ptid;
3314
3315	  if (strncmp (p, "thread", p1 - p) == 0)
3316	    return read_ptid (++p1, &p);
3317
3318	  p1 = strchr (p, ';');
3319	  if (p1 == NULL)
3320	    return null_ptid;
3321	  p1++;
3322
3323	  p = p1;
3324	}
3325    }
3326
3327  return null_ptid;
3328}
3329
3330/* Determine the remote side's current thread.  If we have a stop
3331   reply handy (in WAIT_STATUS), maybe it's a T stop reply with a
3332   "thread" register we can extract the current thread from.  If not,
3333   ask the remote which is the current thread with qC.  The former
3334   method avoids a roundtrip.  */
3335
3336static ptid_t
3337get_current_thread (char *wait_status)
3338{
3339  ptid_t ptid;
3340
3341  /* Note we don't use remote_parse_stop_reply as that makes use of
3342     the target architecture, which we haven't yet fully determined at
3343     this point.  */
3344  if (wait_status != NULL)
3345    ptid = stop_reply_extract_thread (wait_status);
3346  if (ptid_equal (ptid, null_ptid))
3347    ptid = remote_current_thread (inferior_ptid);
3348
3349  return ptid;
3350}
3351
3352/* Query the remote target for which is the current thread/process,
3353   add it to our tables, and update INFERIOR_PTID.  The caller is
3354   responsible for setting the state such that the remote end is ready
3355   to return the current thread.
3356
3357   This function is called after handling the '?' or 'vRun' packets,
3358   whose response is a stop reply from which we can also try
3359   extracting the thread.  If the target doesn't support the explicit
3360   qC query, we infer the current thread from that stop reply, passed
3361   in in WAIT_STATUS, which may be NULL.  */
3362
3363static void
3364add_current_inferior_and_thread (char *wait_status)
3365{
3366  struct remote_state *rs = get_remote_state ();
3367  int fake_pid_p = 0;
3368  ptid_t ptid = null_ptid;
3369
3370  inferior_ptid = null_ptid;
3371
3372  /* Now, if we have thread information, update inferior_ptid.  */
3373  ptid = get_current_thread (wait_status);
3374
3375  if (!ptid_equal (ptid, null_ptid))
3376    {
3377      if (!remote_multi_process_p (rs))
3378	fake_pid_p = 1;
3379
3380      inferior_ptid = ptid;
3381    }
3382  else
3383    {
3384      /* Without this, some commands which require an active target
3385	 (such as kill) won't work.  This variable serves (at least)
3386	 double duty as both the pid of the target process (if it has
3387	 such), and as a flag indicating that a target is active.  */
3388      inferior_ptid = magic_null_ptid;
3389      fake_pid_p = 1;
3390    }
3391
3392  remote_add_inferior (fake_pid_p, ptid_get_pid (inferior_ptid), -1);
3393
3394  /* Add the main thread.  */
3395  add_thread_silent (inferior_ptid);
3396}
3397
3398static void
3399remote_start_remote (int from_tty, struct target_ops *target, int extended_p)
3400{
3401  struct remote_state *rs = get_remote_state ();
3402  struct packet_config *noack_config;
3403  char *wait_status = NULL;
3404
3405  immediate_quit++;		/* Allow user to interrupt it.  */
3406  QUIT;
3407
3408  if (interrupt_on_connect)
3409    send_interrupt_sequence ();
3410
3411  /* Ack any packet which the remote side has already sent.  */
3412  serial_write (rs->remote_desc, "+", 1);
3413
3414  /* Signal other parts that we're going through the initial setup,
3415     and so things may not be stable yet.  */
3416  rs->starting_up = 1;
3417
3418  /* The first packet we send to the target is the optional "supported
3419     packets" request.  If the target can answer this, it will tell us
3420     which later probes to skip.  */
3421  remote_query_supported ();
3422
3423  /* If the stub wants to get a QAllow, compose one and send it.  */
3424  if (packet_support (PACKET_QAllow) != PACKET_DISABLE)
3425    remote_set_permissions (target);
3426
3427  /* Next, we possibly activate noack mode.
3428
3429     If the QStartNoAckMode packet configuration is set to AUTO,
3430     enable noack mode if the stub reported a wish for it with
3431     qSupported.
3432
3433     If set to TRUE, then enable noack mode even if the stub didn't
3434     report it in qSupported.  If the stub doesn't reply OK, the
3435     session ends with an error.
3436
3437     If FALSE, then don't activate noack mode, regardless of what the
3438     stub claimed should be the default with qSupported.  */
3439
3440  noack_config = &remote_protocol_packets[PACKET_QStartNoAckMode];
3441  if (packet_config_support (noack_config) != PACKET_DISABLE)
3442    {
3443      putpkt ("QStartNoAckMode");
3444      getpkt (&rs->buf, &rs->buf_size, 0);
3445      if (packet_ok (rs->buf, noack_config) == PACKET_OK)
3446	rs->noack_mode = 1;
3447    }
3448
3449  if (extended_p)
3450    {
3451      /* Tell the remote that we are using the extended protocol.  */
3452      putpkt ("!");
3453      getpkt (&rs->buf, &rs->buf_size, 0);
3454    }
3455
3456  /* Let the target know which signals it is allowed to pass down to
3457     the program.  */
3458  update_signals_program_target ();
3459
3460  /* Next, if the target can specify a description, read it.  We do
3461     this before anything involving memory or registers.  */
3462  target_find_description ();
3463
3464  /* Next, now that we know something about the target, update the
3465     address spaces in the program spaces.  */
3466  update_address_spaces ();
3467
3468  /* On OSs where the list of libraries is global to all
3469     processes, we fetch them early.  */
3470  if (gdbarch_has_global_solist (target_gdbarch ()))
3471    solib_add (NULL, from_tty, target, auto_solib_add);
3472
3473  if (non_stop)
3474    {
3475      if (packet_support (PACKET_QNonStop) != PACKET_ENABLE)
3476	error (_("Non-stop mode requested, but remote "
3477		 "does not support non-stop"));
3478
3479      putpkt ("QNonStop:1");
3480      getpkt (&rs->buf, &rs->buf_size, 0);
3481
3482      if (strcmp (rs->buf, "OK") != 0)
3483	error (_("Remote refused setting non-stop mode with: %s"), rs->buf);
3484
3485      /* Find about threads and processes the stub is already
3486	 controlling.  We default to adding them in the running state.
3487	 The '?' query below will then tell us about which threads are
3488	 stopped.  */
3489      remote_update_thread_list (target);
3490    }
3491  else if (packet_support (PACKET_QNonStop) == PACKET_ENABLE)
3492    {
3493      /* Don't assume that the stub can operate in all-stop mode.
3494	 Request it explicitly.  */
3495      putpkt ("QNonStop:0");
3496      getpkt (&rs->buf, &rs->buf_size, 0);
3497
3498      if (strcmp (rs->buf, "OK") != 0)
3499	error (_("Remote refused setting all-stop mode with: %s"), rs->buf);
3500    }
3501
3502  /* Upload TSVs regardless of whether the target is running or not.  The
3503     remote stub, such as GDBserver, may have some predefined or builtin
3504     TSVs, even if the target is not running.  */
3505  if (remote_get_trace_status (target, current_trace_status ()) != -1)
3506    {
3507      struct uploaded_tsv *uploaded_tsvs = NULL;
3508
3509      remote_upload_trace_state_variables (target, &uploaded_tsvs);
3510      merge_uploaded_trace_state_variables (&uploaded_tsvs);
3511    }
3512
3513  /* Check whether the target is running now.  */
3514  putpkt ("?");
3515  getpkt (&rs->buf, &rs->buf_size, 0);
3516
3517  if (!non_stop)
3518    {
3519      ptid_t ptid;
3520      int fake_pid_p = 0;
3521      struct inferior *inf;
3522
3523      if (rs->buf[0] == 'W' || rs->buf[0] == 'X')
3524	{
3525	  if (!extended_p)
3526	    error (_("The target is not running (try extended-remote?)"));
3527
3528	  /* We're connected, but not running.  Drop out before we
3529	     call start_remote.  */
3530	  rs->starting_up = 0;
3531	  return;
3532	}
3533      else
3534	{
3535	  /* Save the reply for later.  */
3536	  wait_status = alloca (strlen (rs->buf) + 1);
3537	  strcpy (wait_status, rs->buf);
3538	}
3539
3540      /* Fetch thread list.  */
3541      target_update_thread_list ();
3542
3543      /* Let the stub know that we want it to return the thread.  */
3544      set_continue_thread (minus_one_ptid);
3545
3546      if (thread_count () == 0)
3547	{
3548	  /* Target has no concept of threads at all.  GDB treats
3549	     non-threaded target as single-threaded; add a main
3550	     thread.  */
3551	  add_current_inferior_and_thread (wait_status);
3552	}
3553      else
3554	{
3555	  /* We have thread information; select the thread the target
3556	     says should be current.  If we're reconnecting to a
3557	     multi-threaded program, this will ideally be the thread
3558	     that last reported an event before GDB disconnected.  */
3559	  inferior_ptid = get_current_thread (wait_status);
3560	  if (ptid_equal (inferior_ptid, null_ptid))
3561	    {
3562	      /* Odd... The target was able to list threads, but not
3563		 tell us which thread was current (no "thread"
3564		 register in T stop reply?).  Just pick the first
3565		 thread in the thread list then.  */
3566	      inferior_ptid = thread_list->ptid;
3567	    }
3568	}
3569
3570      /* init_wait_for_inferior should be called before get_offsets in order
3571	 to manage `inserted' flag in bp loc in a correct state.
3572	 breakpoint_init_inferior, called from init_wait_for_inferior, set
3573	 `inserted' flag to 0, while before breakpoint_re_set, called from
3574	 start_remote, set `inserted' flag to 1.  In the initialization of
3575	 inferior, breakpoint_init_inferior should be called first, and then
3576	 breakpoint_re_set can be called.  If this order is broken, state of
3577	 `inserted' flag is wrong, and cause some problems on breakpoint
3578	 manipulation.  */
3579      init_wait_for_inferior ();
3580
3581      get_offsets ();		/* Get text, data & bss offsets.  */
3582
3583      /* If we could not find a description using qXfer, and we know
3584	 how to do it some other way, try again.  This is not
3585	 supported for non-stop; it could be, but it is tricky if
3586	 there are no stopped threads when we connect.  */
3587      if (remote_read_description_p (target)
3588	  && gdbarch_target_desc (target_gdbarch ()) == NULL)
3589	{
3590	  target_clear_description ();
3591	  target_find_description ();
3592	}
3593
3594      /* Use the previously fetched status.  */
3595      gdb_assert (wait_status != NULL);
3596      strcpy (rs->buf, wait_status);
3597      rs->cached_wait_status = 1;
3598
3599      immediate_quit--;
3600      start_remote (from_tty); /* Initialize gdb process mechanisms.  */
3601    }
3602  else
3603    {
3604      /* Clear WFI global state.  Do this before finding about new
3605	 threads and inferiors, and setting the current inferior.
3606	 Otherwise we would clear the proceed status of the current
3607	 inferior when we want its stop_soon state to be preserved
3608	 (see notice_new_inferior).  */
3609      init_wait_for_inferior ();
3610
3611      /* In non-stop, we will either get an "OK", meaning that there
3612	 are no stopped threads at this time; or, a regular stop
3613	 reply.  In the latter case, there may be more than one thread
3614	 stopped --- we pull them all out using the vStopped
3615	 mechanism.  */
3616      if (strcmp (rs->buf, "OK") != 0)
3617	{
3618	  struct notif_client *notif = &notif_client_stop;
3619
3620	  /* remote_notif_get_pending_replies acks this one, and gets
3621	     the rest out.  */
3622	  rs->notif_state->pending_event[notif_client_stop.id]
3623	    = remote_notif_parse (notif, rs->buf);
3624	  remote_notif_get_pending_events (notif);
3625
3626	  /* Make sure that threads that were stopped remain
3627	     stopped.  */
3628	  iterate_over_threads (set_stop_requested_callback, NULL);
3629	}
3630
3631      if (target_can_async_p ())
3632	target_async (inferior_event_handler, 0);
3633
3634      if (thread_count () == 0)
3635	{
3636	  if (!extended_p)
3637	    error (_("The target is not running (try extended-remote?)"));
3638
3639	  /* We're connected, but not running.  Drop out before we
3640	     call start_remote.  */
3641	  rs->starting_up = 0;
3642	  return;
3643	}
3644
3645      /* Let the stub know that we want it to return the thread.  */
3646
3647      /* Force the stub to choose a thread.  */
3648      set_general_thread (null_ptid);
3649
3650      /* Query it.  */
3651      inferior_ptid = remote_current_thread (minus_one_ptid);
3652      if (ptid_equal (inferior_ptid, minus_one_ptid))
3653	error (_("remote didn't report the current thread in non-stop mode"));
3654
3655      get_offsets ();		/* Get text, data & bss offsets.  */
3656
3657      /* In non-stop mode, any cached wait status will be stored in
3658	 the stop reply queue.  */
3659      gdb_assert (wait_status == NULL);
3660
3661      /* Report all signals during attach/startup.  */
3662      remote_pass_signals (target, 0, NULL);
3663    }
3664
3665  /* If we connected to a live target, do some additional setup.  */
3666  if (target_has_execution)
3667    {
3668      if (symfile_objfile) 	/* No use without a symbol-file.  */
3669	remote_check_symbols ();
3670    }
3671
3672  /* Possibly the target has been engaged in a trace run started
3673     previously; find out where things are at.  */
3674  if (remote_get_trace_status (target, current_trace_status ()) != -1)
3675    {
3676      struct uploaded_tp *uploaded_tps = NULL;
3677
3678      if (current_trace_status ()->running)
3679	printf_filtered (_("Trace is already running on the target.\n"));
3680
3681      remote_upload_tracepoints (target, &uploaded_tps);
3682
3683      merge_uploaded_tracepoints (&uploaded_tps);
3684    }
3685
3686  /* The thread and inferior lists are now synchronized with the
3687     target, our symbols have been relocated, and we're merged the
3688     target's tracepoints with ours.  We're done with basic start
3689     up.  */
3690  rs->starting_up = 0;
3691
3692  /* Maybe breakpoints are global and need to be inserted now.  */
3693  if (breakpoints_should_be_inserted_now ())
3694    insert_breakpoints ();
3695}
3696
3697/* Open a connection to a remote debugger.
3698   NAME is the filename used for communication.  */
3699
3700static void
3701remote_open (const char *name, int from_tty)
3702{
3703  remote_open_1 (name, from_tty, &remote_ops, 0);
3704}
3705
3706/* Open a connection to a remote debugger using the extended
3707   remote gdb protocol.  NAME is the filename used for communication.  */
3708
3709static void
3710extended_remote_open (const char *name, int from_tty)
3711{
3712  remote_open_1 (name, from_tty, &extended_remote_ops, 1 /*extended_p */);
3713}
3714
3715/* Reset all packets back to "unknown support".  Called when opening a
3716   new connection to a remote target.  */
3717
3718static void
3719reset_all_packet_configs_support (void)
3720{
3721  int i;
3722
3723  for (i = 0; i < PACKET_MAX; i++)
3724    remote_protocol_packets[i].support = PACKET_SUPPORT_UNKNOWN;
3725}
3726
3727/* Initialize all packet configs.  */
3728
3729static void
3730init_all_packet_configs (void)
3731{
3732  int i;
3733
3734  for (i = 0; i < PACKET_MAX; i++)
3735    {
3736      remote_protocol_packets[i].detect = AUTO_BOOLEAN_AUTO;
3737      remote_protocol_packets[i].support = PACKET_SUPPORT_UNKNOWN;
3738    }
3739}
3740
3741/* Symbol look-up.  */
3742
3743static void
3744remote_check_symbols (void)
3745{
3746  struct remote_state *rs = get_remote_state ();
3747  char *msg, *reply, *tmp;
3748  struct bound_minimal_symbol sym;
3749  int end;
3750
3751  /* The remote side has no concept of inferiors that aren't running
3752     yet, it only knows about running processes.  If we're connected
3753     but our current inferior is not running, we should not invite the
3754     remote target to request symbol lookups related to its
3755     (unrelated) current process.  */
3756  if (!target_has_execution)
3757    return;
3758
3759  if (packet_support (PACKET_qSymbol) == PACKET_DISABLE)
3760    return;
3761
3762  /* Make sure the remote is pointing at the right process.  Note
3763     there's no way to select "no process".  */
3764  set_general_process ();
3765
3766  /* Allocate a message buffer.  We can't reuse the input buffer in RS,
3767     because we need both at the same time.  */
3768  msg = alloca (get_remote_packet_size ());
3769
3770  /* Invite target to request symbol lookups.  */
3771
3772  putpkt ("qSymbol::");
3773  getpkt (&rs->buf, &rs->buf_size, 0);
3774  packet_ok (rs->buf, &remote_protocol_packets[PACKET_qSymbol]);
3775  reply = rs->buf;
3776
3777  while (strncmp (reply, "qSymbol:", 8) == 0)
3778    {
3779      struct bound_minimal_symbol sym;
3780
3781      tmp = &reply[8];
3782      end = hex2bin (tmp, (gdb_byte *) msg, strlen (tmp) / 2);
3783      msg[end] = '\0';
3784      sym = lookup_minimal_symbol (msg, NULL, NULL);
3785      if (sym.minsym == NULL)
3786	xsnprintf (msg, get_remote_packet_size (), "qSymbol::%s", &reply[8]);
3787      else
3788	{
3789	  int addr_size = gdbarch_addr_bit (target_gdbarch ()) / 8;
3790	  CORE_ADDR sym_addr = BMSYMBOL_VALUE_ADDRESS (sym);
3791
3792	  /* If this is a function address, return the start of code
3793	     instead of any data function descriptor.  */
3794	  sym_addr = gdbarch_convert_from_func_ptr_addr (target_gdbarch (),
3795							 sym_addr,
3796							 &current_target);
3797
3798	  xsnprintf (msg, get_remote_packet_size (), "qSymbol:%s:%s",
3799		     phex_nz (sym_addr, addr_size), &reply[8]);
3800	}
3801
3802      putpkt (msg);
3803      getpkt (&rs->buf, &rs->buf_size, 0);
3804      reply = rs->buf;
3805    }
3806}
3807
3808static struct serial *
3809remote_serial_open (const char *name)
3810{
3811  static int udp_warning = 0;
3812
3813  /* FIXME: Parsing NAME here is a hack.  But we want to warn here instead
3814     of in ser-tcp.c, because it is the remote protocol assuming that the
3815     serial connection is reliable and not the serial connection promising
3816     to be.  */
3817  if (!udp_warning && strncmp (name, "udp:", 4) == 0)
3818    {
3819      warning (_("The remote protocol may be unreliable over UDP.\n"
3820		 "Some events may be lost, rendering further debugging "
3821		 "impossible."));
3822      udp_warning = 1;
3823    }
3824
3825  return serial_open (name);
3826}
3827
3828/* Inform the target of our permission settings.  The permission flags
3829   work without this, but if the target knows the settings, it can do
3830   a couple things.  First, it can add its own check, to catch cases
3831   that somehow manage to get by the permissions checks in target
3832   methods.  Second, if the target is wired to disallow particular
3833   settings (for instance, a system in the field that is not set up to
3834   be able to stop at a breakpoint), it can object to any unavailable
3835   permissions.  */
3836
3837void
3838remote_set_permissions (struct target_ops *self)
3839{
3840  struct remote_state *rs = get_remote_state ();
3841
3842  xsnprintf (rs->buf, get_remote_packet_size (), "QAllow:"
3843	     "WriteReg:%x;WriteMem:%x;"
3844	     "InsertBreak:%x;InsertTrace:%x;"
3845	     "InsertFastTrace:%x;Stop:%x",
3846	     may_write_registers, may_write_memory,
3847	     may_insert_breakpoints, may_insert_tracepoints,
3848	     may_insert_fast_tracepoints, may_stop);
3849  putpkt (rs->buf);
3850  getpkt (&rs->buf, &rs->buf_size, 0);
3851
3852  /* If the target didn't like the packet, warn the user.  Do not try
3853     to undo the user's settings, that would just be maddening.  */
3854  if (strcmp (rs->buf, "OK") != 0)
3855    warning (_("Remote refused setting permissions with: %s"), rs->buf);
3856}
3857
3858/* This type describes each known response to the qSupported
3859   packet.  */
3860struct protocol_feature
3861{
3862  /* The name of this protocol feature.  */
3863  const char *name;
3864
3865  /* The default for this protocol feature.  */
3866  enum packet_support default_support;
3867
3868  /* The function to call when this feature is reported, or after
3869     qSupported processing if the feature is not supported.
3870     The first argument points to this structure.  The second
3871     argument indicates whether the packet requested support be
3872     enabled, disabled, or probed (or the default, if this function
3873     is being called at the end of processing and this feature was
3874     not reported).  The third argument may be NULL; if not NULL, it
3875     is a NUL-terminated string taken from the packet following
3876     this feature's name and an equals sign.  */
3877  void (*func) (const struct protocol_feature *, enum packet_support,
3878		const char *);
3879
3880  /* The corresponding packet for this feature.  Only used if
3881     FUNC is remote_supported_packet.  */
3882  int packet;
3883};
3884
3885static void
3886remote_supported_packet (const struct protocol_feature *feature,
3887			 enum packet_support support,
3888			 const char *argument)
3889{
3890  if (argument)
3891    {
3892      warning (_("Remote qSupported response supplied an unexpected value for"
3893		 " \"%s\"."), feature->name);
3894      return;
3895    }
3896
3897  remote_protocol_packets[feature->packet].support = support;
3898}
3899
3900static void
3901remote_packet_size (const struct protocol_feature *feature,
3902		    enum packet_support support, const char *value)
3903{
3904  struct remote_state *rs = get_remote_state ();
3905
3906  int packet_size;
3907  char *value_end;
3908
3909  if (support != PACKET_ENABLE)
3910    return;
3911
3912  if (value == NULL || *value == '\0')
3913    {
3914      warning (_("Remote target reported \"%s\" without a size."),
3915	       feature->name);
3916      return;
3917    }
3918
3919  errno = 0;
3920  packet_size = strtol (value, &value_end, 16);
3921  if (errno != 0 || *value_end != '\0' || packet_size < 0)
3922    {
3923      warning (_("Remote target reported \"%s\" with a bad size: \"%s\"."),
3924	       feature->name, value);
3925      return;
3926    }
3927
3928  if (packet_size > MAX_REMOTE_PACKET_SIZE)
3929    {
3930      warning (_("limiting remote suggested packet size (%d bytes) to %d"),
3931	       packet_size, MAX_REMOTE_PACKET_SIZE);
3932      packet_size = MAX_REMOTE_PACKET_SIZE;
3933    }
3934
3935  /* Record the new maximum packet size.  */
3936  rs->explicit_packet_size = packet_size;
3937}
3938
3939static const struct protocol_feature remote_protocol_features[] = {
3940  { "PacketSize", PACKET_DISABLE, remote_packet_size, -1 },
3941  { "qXfer:auxv:read", PACKET_DISABLE, remote_supported_packet,
3942    PACKET_qXfer_auxv },
3943  { "qXfer:features:read", PACKET_DISABLE, remote_supported_packet,
3944    PACKET_qXfer_features },
3945  { "qXfer:libraries:read", PACKET_DISABLE, remote_supported_packet,
3946    PACKET_qXfer_libraries },
3947  { "qXfer:libraries-svr4:read", PACKET_DISABLE, remote_supported_packet,
3948    PACKET_qXfer_libraries_svr4 },
3949  { "augmented-libraries-svr4-read", PACKET_DISABLE,
3950    remote_supported_packet, PACKET_augmented_libraries_svr4_read_feature },
3951  { "qXfer:memory-map:read", PACKET_DISABLE, remote_supported_packet,
3952    PACKET_qXfer_memory_map },
3953  { "qXfer:spu:read", PACKET_DISABLE, remote_supported_packet,
3954    PACKET_qXfer_spu_read },
3955  { "qXfer:spu:write", PACKET_DISABLE, remote_supported_packet,
3956    PACKET_qXfer_spu_write },
3957  { "qXfer:osdata:read", PACKET_DISABLE, remote_supported_packet,
3958    PACKET_qXfer_osdata },
3959  { "qXfer:threads:read", PACKET_DISABLE, remote_supported_packet,
3960    PACKET_qXfer_threads },
3961  { "qXfer:traceframe-info:read", PACKET_DISABLE, remote_supported_packet,
3962    PACKET_qXfer_traceframe_info },
3963  { "QPassSignals", PACKET_DISABLE, remote_supported_packet,
3964    PACKET_QPassSignals },
3965  { "QProgramSignals", PACKET_DISABLE, remote_supported_packet,
3966    PACKET_QProgramSignals },
3967  { "QStartNoAckMode", PACKET_DISABLE, remote_supported_packet,
3968    PACKET_QStartNoAckMode },
3969  { "multiprocess", PACKET_DISABLE, remote_supported_packet,
3970    PACKET_multiprocess_feature },
3971  { "QNonStop", PACKET_DISABLE, remote_supported_packet, PACKET_QNonStop },
3972  { "qXfer:siginfo:read", PACKET_DISABLE, remote_supported_packet,
3973    PACKET_qXfer_siginfo_read },
3974  { "qXfer:siginfo:write", PACKET_DISABLE, remote_supported_packet,
3975    PACKET_qXfer_siginfo_write },
3976  { "ConditionalTracepoints", PACKET_DISABLE, remote_supported_packet,
3977    PACKET_ConditionalTracepoints },
3978  { "ConditionalBreakpoints", PACKET_DISABLE, remote_supported_packet,
3979    PACKET_ConditionalBreakpoints },
3980  { "BreakpointCommands", PACKET_DISABLE, remote_supported_packet,
3981    PACKET_BreakpointCommands },
3982  { "FastTracepoints", PACKET_DISABLE, remote_supported_packet,
3983    PACKET_FastTracepoints },
3984  { "StaticTracepoints", PACKET_DISABLE, remote_supported_packet,
3985    PACKET_StaticTracepoints },
3986  {"InstallInTrace", PACKET_DISABLE, remote_supported_packet,
3987   PACKET_InstallInTrace},
3988  { "DisconnectedTracing", PACKET_DISABLE, remote_supported_packet,
3989    PACKET_DisconnectedTracing_feature },
3990  { "ReverseContinue", PACKET_DISABLE, remote_supported_packet,
3991    PACKET_bc },
3992  { "ReverseStep", PACKET_DISABLE, remote_supported_packet,
3993    PACKET_bs },
3994  { "TracepointSource", PACKET_DISABLE, remote_supported_packet,
3995    PACKET_TracepointSource },
3996  { "QAllow", PACKET_DISABLE, remote_supported_packet,
3997    PACKET_QAllow },
3998  { "EnableDisableTracepoints", PACKET_DISABLE, remote_supported_packet,
3999    PACKET_EnableDisableTracepoints_feature },
4000  { "qXfer:fdpic:read", PACKET_DISABLE, remote_supported_packet,
4001    PACKET_qXfer_fdpic },
4002  { "qXfer:uib:read", PACKET_DISABLE, remote_supported_packet,
4003    PACKET_qXfer_uib },
4004  { "QDisableRandomization", PACKET_DISABLE, remote_supported_packet,
4005    PACKET_QDisableRandomization },
4006  { "QAgent", PACKET_DISABLE, remote_supported_packet, PACKET_QAgent},
4007  { "QTBuffer:size", PACKET_DISABLE,
4008    remote_supported_packet, PACKET_QTBuffer_size},
4009  { "tracenz", PACKET_DISABLE, remote_supported_packet, PACKET_tracenz_feature },
4010  { "Qbtrace:off", PACKET_DISABLE, remote_supported_packet, PACKET_Qbtrace_off },
4011  { "Qbtrace:bts", PACKET_DISABLE, remote_supported_packet, PACKET_Qbtrace_bts },
4012  { "qXfer:btrace:read", PACKET_DISABLE, remote_supported_packet,
4013    PACKET_qXfer_btrace }
4014};
4015
4016static char *remote_support_xml;
4017
4018/* Register string appended to "xmlRegisters=" in qSupported query.  */
4019
4020void
4021register_remote_support_xml (const char *xml)
4022{
4023#if defined(HAVE_LIBEXPAT)
4024  if (remote_support_xml == NULL)
4025    remote_support_xml = concat ("xmlRegisters=", xml, (char *) NULL);
4026  else
4027    {
4028      char *copy = xstrdup (remote_support_xml + 13);
4029      char *p = strtok (copy, ",");
4030
4031      do
4032	{
4033	  if (strcmp (p, xml) == 0)
4034	    {
4035	      /* already there */
4036	      xfree (copy);
4037	      return;
4038	    }
4039	}
4040      while ((p = strtok (NULL, ",")) != NULL);
4041      xfree (copy);
4042
4043      remote_support_xml = reconcat (remote_support_xml,
4044				     remote_support_xml, ",", xml,
4045				     (char *) NULL);
4046    }
4047#endif
4048}
4049
4050static char *
4051remote_query_supported_append (char *msg, const char *append)
4052{
4053  if (msg)
4054    return reconcat (msg, msg, ";", append, (char *) NULL);
4055  else
4056    return xstrdup (append);
4057}
4058
4059static void
4060remote_query_supported (void)
4061{
4062  struct remote_state *rs = get_remote_state ();
4063  char *next;
4064  int i;
4065  unsigned char seen [ARRAY_SIZE (remote_protocol_features)];
4066
4067  /* The packet support flags are handled differently for this packet
4068     than for most others.  We treat an error, a disabled packet, and
4069     an empty response identically: any features which must be reported
4070     to be used will be automatically disabled.  An empty buffer
4071     accomplishes this, since that is also the representation for a list
4072     containing no features.  */
4073
4074  rs->buf[0] = 0;
4075  if (packet_support (PACKET_qSupported) != PACKET_DISABLE)
4076    {
4077      char *q = NULL;
4078      struct cleanup *old_chain = make_cleanup (free_current_contents, &q);
4079
4080      q = remote_query_supported_append (q, "multiprocess+");
4081
4082      if (remote_support_xml)
4083	q = remote_query_supported_append (q, remote_support_xml);
4084
4085      q = remote_query_supported_append (q, "qRelocInsn+");
4086
4087      q = reconcat (q, "qSupported:", q, (char *) NULL);
4088      putpkt (q);
4089
4090      do_cleanups (old_chain);
4091
4092      getpkt (&rs->buf, &rs->buf_size, 0);
4093
4094      /* If an error occured, warn, but do not return - just reset the
4095	 buffer to empty and go on to disable features.  */
4096      if (packet_ok (rs->buf, &remote_protocol_packets[PACKET_qSupported])
4097	  == PACKET_ERROR)
4098	{
4099	  warning (_("Remote failure reply: %s"), rs->buf);
4100	  rs->buf[0] = 0;
4101	}
4102    }
4103
4104  memset (seen, 0, sizeof (seen));
4105
4106  next = rs->buf;
4107  while (*next)
4108    {
4109      enum packet_support is_supported;
4110      char *p, *end, *name_end, *value;
4111
4112      /* First separate out this item from the rest of the packet.  If
4113	 there's another item after this, we overwrite the separator
4114	 (terminated strings are much easier to work with).  */
4115      p = next;
4116      end = strchr (p, ';');
4117      if (end == NULL)
4118	{
4119	  end = p + strlen (p);
4120	  next = end;
4121	}
4122      else
4123	{
4124	  *end = '\0';
4125	  next = end + 1;
4126
4127	  if (end == p)
4128	    {
4129	      warning (_("empty item in \"qSupported\" response"));
4130	      continue;
4131	    }
4132	}
4133
4134      name_end = strchr (p, '=');
4135      if (name_end)
4136	{
4137	  /* This is a name=value entry.  */
4138	  is_supported = PACKET_ENABLE;
4139	  value = name_end + 1;
4140	  *name_end = '\0';
4141	}
4142      else
4143	{
4144	  value = NULL;
4145	  switch (end[-1])
4146	    {
4147	    case '+':
4148	      is_supported = PACKET_ENABLE;
4149	      break;
4150
4151	    case '-':
4152	      is_supported = PACKET_DISABLE;
4153	      break;
4154
4155	    case '?':
4156	      is_supported = PACKET_SUPPORT_UNKNOWN;
4157	      break;
4158
4159	    default:
4160	      warning (_("unrecognized item \"%s\" "
4161			 "in \"qSupported\" response"), p);
4162	      continue;
4163	    }
4164	  end[-1] = '\0';
4165	}
4166
4167      for (i = 0; i < ARRAY_SIZE (remote_protocol_features); i++)
4168	if (strcmp (remote_protocol_features[i].name, p) == 0)
4169	  {
4170	    const struct protocol_feature *feature;
4171
4172	    seen[i] = 1;
4173	    feature = &remote_protocol_features[i];
4174	    feature->func (feature, is_supported, value);
4175	    break;
4176	  }
4177    }
4178
4179  /* If we increased the packet size, make sure to increase the global
4180     buffer size also.  We delay this until after parsing the entire
4181     qSupported packet, because this is the same buffer we were
4182     parsing.  */
4183  if (rs->buf_size < rs->explicit_packet_size)
4184    {
4185      rs->buf_size = rs->explicit_packet_size;
4186      rs->buf = xrealloc (rs->buf, rs->buf_size);
4187    }
4188
4189  /* Handle the defaults for unmentioned features.  */
4190  for (i = 0; i < ARRAY_SIZE (remote_protocol_features); i++)
4191    if (!seen[i])
4192      {
4193	const struct protocol_feature *feature;
4194
4195	feature = &remote_protocol_features[i];
4196	feature->func (feature, feature->default_support, NULL);
4197      }
4198}
4199
4200/* Remove any of the remote.c targets from target stack.  Upper targets depend
4201   on it so remove them first.  */
4202
4203static void
4204remote_unpush_target (void)
4205{
4206  pop_all_targets_above (process_stratum - 1);
4207}
4208
4209static void
4210remote_open_1 (const char *name, int from_tty,
4211	       struct target_ops *target, int extended_p)
4212{
4213  struct remote_state *rs = get_remote_state ();
4214
4215  if (name == 0)
4216    error (_("To open a remote debug connection, you need to specify what\n"
4217	   "serial device is attached to the remote system\n"
4218	   "(e.g. /dev/ttyS0, /dev/ttya, COM1, etc.)."));
4219
4220  /* See FIXME above.  */
4221  if (!target_async_permitted)
4222    wait_forever_enabled_p = 1;
4223
4224  /* If we're connected to a running target, target_preopen will kill it.
4225     Ask this question first, before target_preopen has a chance to kill
4226     anything.  */
4227  if (rs->remote_desc != NULL && !have_inferiors ())
4228    {
4229      if (from_tty
4230	  && !query (_("Already connected to a remote target.  Disconnect? ")))
4231	error (_("Still connected."));
4232    }
4233
4234  /* Here the possibly existing remote target gets unpushed.  */
4235  target_preopen (from_tty);
4236
4237  /* Make sure we send the passed signals list the next time we resume.  */
4238  xfree (rs->last_pass_packet);
4239  rs->last_pass_packet = NULL;
4240
4241  /* Make sure we send the program signals list the next time we
4242     resume.  */
4243  xfree (rs->last_program_signals_packet);
4244  rs->last_program_signals_packet = NULL;
4245
4246  remote_fileio_reset ();
4247  reopen_exec_file ();
4248  reread_symbols ();
4249
4250  rs->remote_desc = remote_serial_open (name);
4251  if (!rs->remote_desc)
4252    perror_with_name (name);
4253
4254  if (baud_rate != -1)
4255    {
4256      if (serial_setbaudrate (rs->remote_desc, baud_rate))
4257	{
4258	  /* The requested speed could not be set.  Error out to
4259	     top level after closing remote_desc.  Take care to
4260	     set remote_desc to NULL to avoid closing remote_desc
4261	     more than once.  */
4262	  serial_close (rs->remote_desc);
4263	  rs->remote_desc = NULL;
4264	  perror_with_name (name);
4265	}
4266    }
4267
4268  serial_raw (rs->remote_desc);
4269
4270  /* If there is something sitting in the buffer we might take it as a
4271     response to a command, which would be bad.  */
4272  serial_flush_input (rs->remote_desc);
4273
4274  if (from_tty)
4275    {
4276      puts_filtered ("Remote debugging using ");
4277      puts_filtered (name);
4278      puts_filtered ("\n");
4279    }
4280  push_target (target);		/* Switch to using remote target now.  */
4281
4282  /* Register extra event sources in the event loop.  */
4283  remote_async_inferior_event_token
4284    = create_async_event_handler (remote_async_inferior_event_handler,
4285				  NULL);
4286  rs->notif_state = remote_notif_state_allocate ();
4287
4288  /* Reset the target state; these things will be queried either by
4289     remote_query_supported or as they are needed.  */
4290  reset_all_packet_configs_support ();
4291  rs->cached_wait_status = 0;
4292  rs->explicit_packet_size = 0;
4293  rs->noack_mode = 0;
4294  rs->extended = extended_p;
4295  rs->waiting_for_stop_reply = 0;
4296  rs->ctrlc_pending_p = 0;
4297
4298  rs->general_thread = not_sent_ptid;
4299  rs->continue_thread = not_sent_ptid;
4300  rs->remote_traceframe_number = -1;
4301
4302  /* Probe for ability to use "ThreadInfo" query, as required.  */
4303  rs->use_threadinfo_query = 1;
4304  rs->use_threadextra_query = 1;
4305
4306  if (target_async_permitted)
4307    {
4308      /* With this target we start out by owning the terminal.  */
4309      remote_async_terminal_ours_p = 1;
4310
4311      /* FIXME: cagney/1999-09-23: During the initial connection it is
4312	 assumed that the target is already ready and able to respond to
4313	 requests.  Unfortunately remote_start_remote() eventually calls
4314	 wait_for_inferior() with no timeout.  wait_forever_enabled_p gets
4315	 around this.  Eventually a mechanism that allows
4316	 wait_for_inferior() to expect/get timeouts will be
4317	 implemented.  */
4318      wait_forever_enabled_p = 0;
4319    }
4320
4321  /* First delete any symbols previously loaded from shared libraries.  */
4322  no_shared_libraries (NULL, 0);
4323
4324  /* Start afresh.  */
4325  init_thread_list ();
4326
4327  /* Start the remote connection.  If error() or QUIT, discard this
4328     target (we'd otherwise be in an inconsistent state) and then
4329     propogate the error on up the exception chain.  This ensures that
4330     the caller doesn't stumble along blindly assuming that the
4331     function succeeded.  The CLI doesn't have this problem but other
4332     UI's, such as MI do.
4333
4334     FIXME: cagney/2002-05-19: Instead of re-throwing the exception,
4335     this function should return an error indication letting the
4336     caller restore the previous state.  Unfortunately the command
4337     ``target remote'' is directly wired to this function making that
4338     impossible.  On a positive note, the CLI side of this problem has
4339     been fixed - the function set_cmd_context() makes it possible for
4340     all the ``target ....'' commands to share a common callback
4341     function.  See cli-dump.c.  */
4342  {
4343    volatile struct gdb_exception ex;
4344
4345    TRY_CATCH (ex, RETURN_MASK_ALL)
4346      {
4347	remote_start_remote (from_tty, target, extended_p);
4348      }
4349    if (ex.reason < 0)
4350      {
4351	/* Pop the partially set up target - unless something else did
4352	   already before throwing the exception.  */
4353	if (rs->remote_desc != NULL)
4354	  remote_unpush_target ();
4355	if (target_async_permitted)
4356	  wait_forever_enabled_p = 1;
4357	throw_exception (ex);
4358      }
4359  }
4360
4361  if (target_async_permitted)
4362    wait_forever_enabled_p = 1;
4363}
4364
4365/* This takes a program previously attached to and detaches it.  After
4366   this is done, GDB can be used to debug some other program.  We
4367   better not have left any breakpoints in the target program or it'll
4368   die when it hits one.  */
4369
4370static void
4371remote_detach_1 (const char *args, int from_tty, int extended)
4372{
4373  int pid = ptid_get_pid (inferior_ptid);
4374  struct remote_state *rs = get_remote_state ();
4375
4376  if (args)
4377    error (_("Argument given to \"detach\" when remotely debugging."));
4378
4379  if (!target_has_execution)
4380    error (_("No process to detach from."));
4381
4382  if (from_tty)
4383    {
4384      char *exec_file = get_exec_file (0);
4385      if (exec_file == NULL)
4386	exec_file = "";
4387      printf_unfiltered (_("Detaching from program: %s, %s\n"), exec_file,
4388			 target_pid_to_str (pid_to_ptid (pid)));
4389      gdb_flush (gdb_stdout);
4390    }
4391
4392  /* Tell the remote target to detach.  */
4393  if (remote_multi_process_p (rs))
4394    xsnprintf (rs->buf, get_remote_packet_size (), "D;%x", pid);
4395  else
4396    strcpy (rs->buf, "D");
4397
4398  putpkt (rs->buf);
4399  getpkt (&rs->buf, &rs->buf_size, 0);
4400
4401  if (rs->buf[0] == 'O' && rs->buf[1] == 'K')
4402    ;
4403  else if (rs->buf[0] == '\0')
4404    error (_("Remote doesn't know how to detach"));
4405  else
4406    error (_("Can't detach process."));
4407
4408  if (from_tty && !extended)
4409    puts_filtered (_("Ending remote debugging.\n"));
4410
4411  target_mourn_inferior ();
4412}
4413
4414static void
4415remote_detach (struct target_ops *ops, const char *args, int from_tty)
4416{
4417  remote_detach_1 (args, from_tty, 0);
4418}
4419
4420static void
4421extended_remote_detach (struct target_ops *ops, const char *args, int from_tty)
4422{
4423  remote_detach_1 (args, from_tty, 1);
4424}
4425
4426/* Same as remote_detach, but don't send the "D" packet; just disconnect.  */
4427
4428static void
4429remote_disconnect (struct target_ops *target, const char *args, int from_tty)
4430{
4431  if (args)
4432    error (_("Argument given to \"disconnect\" when remotely debugging."));
4433
4434  /* Make sure we unpush even the extended remote targets; mourn
4435     won't do it.  So call remote_mourn_1 directly instead of
4436     target_mourn_inferior.  */
4437  remote_mourn_1 (target);
4438
4439  if (from_tty)
4440    puts_filtered ("Ending remote debugging.\n");
4441}
4442
4443/* Attach to the process specified by ARGS.  If FROM_TTY is non-zero,
4444   be chatty about it.  */
4445
4446static void
4447extended_remote_attach_1 (struct target_ops *target, const char *args,
4448			  int from_tty)
4449{
4450  struct remote_state *rs = get_remote_state ();
4451  int pid;
4452  char *wait_status = NULL;
4453
4454  pid = parse_pid_to_attach (args);
4455
4456  /* Remote PID can be freely equal to getpid, do not check it here the same
4457     way as in other targets.  */
4458
4459  if (packet_support (PACKET_vAttach) == PACKET_DISABLE)
4460    error (_("This target does not support attaching to a process"));
4461
4462  if (from_tty)
4463    {
4464      char *exec_file = get_exec_file (0);
4465
4466      if (exec_file)
4467	printf_unfiltered (_("Attaching to program: %s, %s\n"), exec_file,
4468			   target_pid_to_str (pid_to_ptid (pid)));
4469      else
4470	printf_unfiltered (_("Attaching to %s\n"),
4471			   target_pid_to_str (pid_to_ptid (pid)));
4472
4473      gdb_flush (gdb_stdout);
4474    }
4475
4476  xsnprintf (rs->buf, get_remote_packet_size (), "vAttach;%x", pid);
4477  putpkt (rs->buf);
4478  getpkt (&rs->buf, &rs->buf_size, 0);
4479
4480  switch (packet_ok (rs->buf,
4481		     &remote_protocol_packets[PACKET_vAttach]))
4482    {
4483    case PACKET_OK:
4484      if (!non_stop)
4485	{
4486	  /* Save the reply for later.  */
4487	  wait_status = alloca (strlen (rs->buf) + 1);
4488	  strcpy (wait_status, rs->buf);
4489	}
4490      else if (strcmp (rs->buf, "OK") != 0)
4491	error (_("Attaching to %s failed with: %s"),
4492	       target_pid_to_str (pid_to_ptid (pid)),
4493	       rs->buf);
4494      break;
4495    case PACKET_UNKNOWN:
4496      error (_("This target does not support attaching to a process"));
4497    default:
4498      error (_("Attaching to %s failed"),
4499	     target_pid_to_str (pid_to_ptid (pid)));
4500    }
4501
4502  set_current_inferior (remote_add_inferior (0, pid, 1));
4503
4504  inferior_ptid = pid_to_ptid (pid);
4505
4506  if (non_stop)
4507    {
4508      struct thread_info *thread;
4509
4510      /* Get list of threads.  */
4511      remote_update_thread_list (target);
4512
4513      thread = first_thread_of_process (pid);
4514      if (thread)
4515	inferior_ptid = thread->ptid;
4516      else
4517	inferior_ptid = pid_to_ptid (pid);
4518
4519      /* Invalidate our notion of the remote current thread.  */
4520      record_currthread (rs, minus_one_ptid);
4521    }
4522  else
4523    {
4524      /* Now, if we have thread information, update inferior_ptid.  */
4525      inferior_ptid = remote_current_thread (inferior_ptid);
4526
4527      /* Add the main thread to the thread list.  */
4528      add_thread_silent (inferior_ptid);
4529    }
4530
4531  /* Next, if the target can specify a description, read it.  We do
4532     this before anything involving memory or registers.  */
4533  target_find_description ();
4534
4535  if (!non_stop)
4536    {
4537      /* Use the previously fetched status.  */
4538      gdb_assert (wait_status != NULL);
4539
4540      if (target_can_async_p ())
4541	{
4542	  struct notif_event *reply
4543	    =  remote_notif_parse (&notif_client_stop, wait_status);
4544
4545	  push_stop_reply ((struct stop_reply *) reply);
4546
4547	  target_async (inferior_event_handler, 0);
4548	}
4549      else
4550	{
4551	  gdb_assert (wait_status != NULL);
4552	  strcpy (rs->buf, wait_status);
4553	  rs->cached_wait_status = 1;
4554	}
4555    }
4556  else
4557    gdb_assert (wait_status == NULL);
4558}
4559
4560static void
4561extended_remote_attach (struct target_ops *ops, const char *args, int from_tty)
4562{
4563  extended_remote_attach_1 (ops, args, from_tty);
4564}
4565
4566/* Implementation of the to_post_attach method.  */
4567
4568static void
4569extended_remote_post_attach (struct target_ops *ops, int pid)
4570{
4571  /* In certain cases GDB might not have had the chance to start
4572     symbol lookup up until now.  This could happen if the debugged
4573     binary is not using shared libraries, the vsyscall page is not
4574     present (on Linux) and the binary itself hadn't changed since the
4575     debugging process was started.  */
4576  if (symfile_objfile != NULL)
4577    remote_check_symbols();
4578}
4579
4580
4581/* Check for the availability of vCont.  This function should also check
4582   the response.  */
4583
4584static void
4585remote_vcont_probe (struct remote_state *rs)
4586{
4587  char *buf;
4588
4589  strcpy (rs->buf, "vCont?");
4590  putpkt (rs->buf);
4591  getpkt (&rs->buf, &rs->buf_size, 0);
4592  buf = rs->buf;
4593
4594  /* Make sure that the features we assume are supported.  */
4595  if (strncmp (buf, "vCont", 5) == 0)
4596    {
4597      char *p = &buf[5];
4598      int support_s, support_S, support_c, support_C;
4599
4600      support_s = 0;
4601      support_S = 0;
4602      support_c = 0;
4603      support_C = 0;
4604      rs->supports_vCont.t = 0;
4605      rs->supports_vCont.r = 0;
4606      while (p && *p == ';')
4607	{
4608	  p++;
4609	  if (*p == 's' && (*(p + 1) == ';' || *(p + 1) == 0))
4610	    support_s = 1;
4611	  else if (*p == 'S' && (*(p + 1) == ';' || *(p + 1) == 0))
4612	    support_S = 1;
4613	  else if (*p == 'c' && (*(p + 1) == ';' || *(p + 1) == 0))
4614	    support_c = 1;
4615	  else if (*p == 'C' && (*(p + 1) == ';' || *(p + 1) == 0))
4616	    support_C = 1;
4617	  else if (*p == 't' && (*(p + 1) == ';' || *(p + 1) == 0))
4618	    rs->supports_vCont.t = 1;
4619	  else if (*p == 'r' && (*(p + 1) == ';' || *(p + 1) == 0))
4620	    rs->supports_vCont.r = 1;
4621
4622	  p = strchr (p, ';');
4623	}
4624
4625      /* If s, S, c, and C are not all supported, we can't use vCont.  Clearing
4626         BUF will make packet_ok disable the packet.  */
4627      if (!support_s || !support_S || !support_c || !support_C)
4628	buf[0] = 0;
4629    }
4630
4631  packet_ok (buf, &remote_protocol_packets[PACKET_vCont]);
4632}
4633
4634/* Helper function for building "vCont" resumptions.  Write a
4635   resumption to P.  ENDP points to one-passed-the-end of the buffer
4636   we're allowed to write to.  Returns BUF+CHARACTERS_WRITTEN.  The
4637   thread to be resumed is PTID; STEP and SIGGNAL indicate whether the
4638   resumed thread should be single-stepped and/or signalled.  If PTID
4639   equals minus_one_ptid, then all threads are resumed; if PTID
4640   represents a process, then all threads of the process are resumed;
4641   the thread to be stepped and/or signalled is given in the global
4642   INFERIOR_PTID.  */
4643
4644static char *
4645append_resumption (char *p, char *endp,
4646		   ptid_t ptid, int step, enum gdb_signal siggnal)
4647{
4648  struct remote_state *rs = get_remote_state ();
4649
4650  if (step && siggnal != GDB_SIGNAL_0)
4651    p += xsnprintf (p, endp - p, ";S%02x", siggnal);
4652  else if (step
4653	   /* GDB is willing to range step.  */
4654	   && use_range_stepping
4655	   /* Target supports range stepping.  */
4656	   && rs->supports_vCont.r
4657	   /* We don't currently support range stepping multiple
4658	      threads with a wildcard (though the protocol allows it,
4659	      so stubs shouldn't make an active effort to forbid
4660	      it).  */
4661	   && !(remote_multi_process_p (rs) && ptid_is_pid (ptid)))
4662    {
4663      struct thread_info *tp;
4664
4665      if (ptid_equal (ptid, minus_one_ptid))
4666	{
4667	  /* If we don't know about the target thread's tid, then
4668	     we're resuming magic_null_ptid (see caller).  */
4669	  tp = find_thread_ptid (magic_null_ptid);
4670	}
4671      else
4672	tp = find_thread_ptid (ptid);
4673      gdb_assert (tp != NULL);
4674
4675      if (tp->control.may_range_step)
4676	{
4677	  int addr_size = gdbarch_addr_bit (target_gdbarch ()) / 8;
4678
4679	  p += xsnprintf (p, endp - p, ";r%s,%s",
4680			  phex_nz (tp->control.step_range_start,
4681				   addr_size),
4682			  phex_nz (tp->control.step_range_end,
4683				   addr_size));
4684	}
4685      else
4686	p += xsnprintf (p, endp - p, ";s");
4687    }
4688  else if (step)
4689    p += xsnprintf (p, endp - p, ";s");
4690  else if (siggnal != GDB_SIGNAL_0)
4691    p += xsnprintf (p, endp - p, ";C%02x", siggnal);
4692  else
4693    p += xsnprintf (p, endp - p, ";c");
4694
4695  if (remote_multi_process_p (rs) && ptid_is_pid (ptid))
4696    {
4697      ptid_t nptid;
4698
4699      /* All (-1) threads of process.  */
4700      nptid = ptid_build (ptid_get_pid (ptid), -1, 0);
4701
4702      p += xsnprintf (p, endp - p, ":");
4703      p = write_ptid (p, endp, nptid);
4704    }
4705  else if (!ptid_equal (ptid, minus_one_ptid))
4706    {
4707      p += xsnprintf (p, endp - p, ":");
4708      p = write_ptid (p, endp, ptid);
4709    }
4710
4711  return p;
4712}
4713
4714/* Append a vCont continue-with-signal action for threads that have a
4715   non-zero stop signal.  */
4716
4717static char *
4718append_pending_thread_resumptions (char *p, char *endp, ptid_t ptid)
4719{
4720  struct thread_info *thread;
4721
4722  ALL_NON_EXITED_THREADS (thread)
4723    if (ptid_match (thread->ptid, ptid)
4724	&& !ptid_equal (inferior_ptid, thread->ptid)
4725	&& thread->suspend.stop_signal != GDB_SIGNAL_0)
4726      {
4727	p = append_resumption (p, endp, thread->ptid,
4728			       0, thread->suspend.stop_signal);
4729	thread->suspend.stop_signal = GDB_SIGNAL_0;
4730      }
4731
4732  return p;
4733}
4734
4735/* Resume the remote inferior by using a "vCont" packet.  The thread
4736   to be resumed is PTID; STEP and SIGGNAL indicate whether the
4737   resumed thread should be single-stepped and/or signalled.  If PTID
4738   equals minus_one_ptid, then all threads are resumed; the thread to
4739   be stepped and/or signalled is given in the global INFERIOR_PTID.
4740   This function returns non-zero iff it resumes the inferior.
4741
4742   This function issues a strict subset of all possible vCont commands at the
4743   moment.  */
4744
4745static int
4746remote_vcont_resume (ptid_t ptid, int step, enum gdb_signal siggnal)
4747{
4748  struct remote_state *rs = get_remote_state ();
4749  char *p;
4750  char *endp;
4751
4752  if (packet_support (PACKET_vCont) == PACKET_SUPPORT_UNKNOWN)
4753    remote_vcont_probe (rs);
4754
4755  if (packet_support (PACKET_vCont) == PACKET_DISABLE)
4756    return 0;
4757
4758  p = rs->buf;
4759  endp = rs->buf + get_remote_packet_size ();
4760
4761  /* If we could generate a wider range of packets, we'd have to worry
4762     about overflowing BUF.  Should there be a generic
4763     "multi-part-packet" packet?  */
4764
4765  p += xsnprintf (p, endp - p, "vCont");
4766
4767  if (ptid_equal (ptid, magic_null_ptid))
4768    {
4769      /* MAGIC_NULL_PTID means that we don't have any active threads,
4770	 so we don't have any TID numbers the inferior will
4771	 understand.  Make sure to only send forms that do not specify
4772	 a TID.  */
4773      append_resumption (p, endp, minus_one_ptid, step, siggnal);
4774    }
4775  else if (ptid_equal (ptid, minus_one_ptid) || ptid_is_pid (ptid))
4776    {
4777      /* Resume all threads (of all processes, or of a single
4778	 process), with preference for INFERIOR_PTID.  This assumes
4779	 inferior_ptid belongs to the set of all threads we are about
4780	 to resume.  */
4781      if (step || siggnal != GDB_SIGNAL_0)
4782	{
4783	  /* Step inferior_ptid, with or without signal.  */
4784	  p = append_resumption (p, endp, inferior_ptid, step, siggnal);
4785	}
4786
4787      /* Also pass down any pending signaled resumption for other
4788	 threads not the current.  */
4789      p = append_pending_thread_resumptions (p, endp, ptid);
4790
4791      /* And continue others without a signal.  */
4792      append_resumption (p, endp, ptid, /*step=*/ 0, GDB_SIGNAL_0);
4793    }
4794  else
4795    {
4796      /* Scheduler locking; resume only PTID.  */
4797      append_resumption (p, endp, ptid, step, siggnal);
4798    }
4799
4800  gdb_assert (strlen (rs->buf) < get_remote_packet_size ());
4801  putpkt (rs->buf);
4802
4803  if (non_stop)
4804    {
4805      /* In non-stop, the stub replies to vCont with "OK".  The stop
4806	 reply will be reported asynchronously by means of a `%Stop'
4807	 notification.  */
4808      getpkt (&rs->buf, &rs->buf_size, 0);
4809      if (strcmp (rs->buf, "OK") != 0)
4810	error (_("Unexpected vCont reply in non-stop mode: %s"), rs->buf);
4811    }
4812
4813  return 1;
4814}
4815
4816/* Tell the remote machine to resume.  */
4817
4818static void
4819remote_resume (struct target_ops *ops,
4820	       ptid_t ptid, int step, enum gdb_signal siggnal)
4821{
4822  struct remote_state *rs = get_remote_state ();
4823  char *buf;
4824
4825  /* In all-stop, we can't mark REMOTE_ASYNC_GET_PENDING_EVENTS_TOKEN
4826     (explained in remote-notif.c:handle_notification) so
4827     remote_notif_process is not called.  We need find a place where
4828     it is safe to start a 'vNotif' sequence.  It is good to do it
4829     before resuming inferior, because inferior was stopped and no RSP
4830     traffic at that moment.  */
4831  if (!non_stop)
4832    remote_notif_process (rs->notif_state, &notif_client_stop);
4833
4834  rs->last_sent_signal = siggnal;
4835  rs->last_sent_step = step;
4836
4837  /* The vCont packet doesn't need to specify threads via Hc.  */
4838  /* No reverse support (yet) for vCont.  */
4839  if (execution_direction != EXEC_REVERSE)
4840    if (remote_vcont_resume (ptid, step, siggnal))
4841      goto done;
4842
4843  /* All other supported resume packets do use Hc, so set the continue
4844     thread.  */
4845  if (ptid_equal (ptid, minus_one_ptid))
4846    set_continue_thread (any_thread_ptid);
4847  else
4848    set_continue_thread (ptid);
4849
4850  buf = rs->buf;
4851  if (execution_direction == EXEC_REVERSE)
4852    {
4853      /* We don't pass signals to the target in reverse exec mode.  */
4854      if (info_verbose && siggnal != GDB_SIGNAL_0)
4855	warning (_(" - Can't pass signal %d to target in reverse: ignored."),
4856		 siggnal);
4857
4858      if (step && packet_support (PACKET_bs) == PACKET_DISABLE)
4859	error (_("Remote reverse-step not supported."));
4860      if (!step && packet_support (PACKET_bc) == PACKET_DISABLE)
4861	error (_("Remote reverse-continue not supported."));
4862
4863      strcpy (buf, step ? "bs" : "bc");
4864    }
4865  else if (siggnal != GDB_SIGNAL_0)
4866    {
4867      buf[0] = step ? 'S' : 'C';
4868      buf[1] = tohex (((int) siggnal >> 4) & 0xf);
4869      buf[2] = tohex (((int) siggnal) & 0xf);
4870      buf[3] = '\0';
4871    }
4872  else
4873    strcpy (buf, step ? "s" : "c");
4874
4875  putpkt (buf);
4876
4877 done:
4878  /* We are about to start executing the inferior, let's register it
4879     with the event loop.  NOTE: this is the one place where all the
4880     execution commands end up.  We could alternatively do this in each
4881     of the execution commands in infcmd.c.  */
4882  /* FIXME: ezannoni 1999-09-28: We may need to move this out of here
4883     into infcmd.c in order to allow inferior function calls to work
4884     NOT asynchronously.  */
4885  if (target_can_async_p ())
4886    target_async (inferior_event_handler, 0);
4887
4888  /* We've just told the target to resume.  The remote server will
4889     wait for the inferior to stop, and then send a stop reply.  In
4890     the mean time, we can't start another command/query ourselves
4891     because the stub wouldn't be ready to process it.  This applies
4892     only to the base all-stop protocol, however.  In non-stop (which
4893     only supports vCont), the stub replies with an "OK", and is
4894     immediate able to process further serial input.  */
4895  if (!non_stop)
4896    rs->waiting_for_stop_reply = 1;
4897}
4898
4899
4900/* Set up the signal handler for SIGINT, while the target is
4901   executing, ovewriting the 'regular' SIGINT signal handler.  */
4902static void
4903async_initialize_sigint_signal_handler (void)
4904{
4905  signal (SIGINT, async_handle_remote_sigint);
4906}
4907
4908/* Signal handler for SIGINT, while the target is executing.  */
4909static void
4910async_handle_remote_sigint (int sig)
4911{
4912  signal (sig, async_handle_remote_sigint_twice);
4913  /* Note we need to go through gdb_call_async_signal_handler in order
4914     to wake up the event loop on Windows.  */
4915  gdb_call_async_signal_handler (async_sigint_remote_token, 0);
4916}
4917
4918/* Signal handler for SIGINT, installed after SIGINT has already been
4919   sent once.  It will take effect the second time that the user sends
4920   a ^C.  */
4921static void
4922async_handle_remote_sigint_twice (int sig)
4923{
4924  signal (sig, async_handle_remote_sigint);
4925  /* See note in async_handle_remote_sigint.  */
4926  gdb_call_async_signal_handler (async_sigint_remote_twice_token, 0);
4927}
4928
4929/* Perform the real interruption of the target execution, in response
4930   to a ^C.  */
4931static void
4932async_remote_interrupt (gdb_client_data arg)
4933{
4934  if (remote_debug)
4935    fprintf_unfiltered (gdb_stdlog, "async_remote_interrupt called\n");
4936
4937  target_stop (inferior_ptid);
4938}
4939
4940/* Perform interrupt, if the first attempt did not succeed.  Just give
4941   up on the target alltogether.  */
4942static void
4943async_remote_interrupt_twice (gdb_client_data arg)
4944{
4945  if (remote_debug)
4946    fprintf_unfiltered (gdb_stdlog, "async_remote_interrupt_twice called\n");
4947
4948  interrupt_query ();
4949}
4950
4951/* Reinstall the usual SIGINT handlers, after the target has
4952   stopped.  */
4953static void
4954async_cleanup_sigint_signal_handler (void *dummy)
4955{
4956  signal (SIGINT, handle_sigint);
4957}
4958
4959/* Send ^C to target to halt it.  Target will respond, and send us a
4960   packet.  */
4961static void (*ofunc) (int);
4962
4963/* The command line interface's stop routine.  This function is installed
4964   as a signal handler for SIGINT.  The first time a user requests a
4965   stop, we call remote_stop to send a break or ^C.  If there is no
4966   response from the target (it didn't stop when the user requested it),
4967   we ask the user if he'd like to detach from the target.  */
4968static void
4969sync_remote_interrupt (int signo)
4970{
4971  /* If this doesn't work, try more severe steps.  */
4972  signal (signo, sync_remote_interrupt_twice);
4973
4974  gdb_call_async_signal_handler (async_sigint_remote_token, 1);
4975}
4976
4977/* The user typed ^C twice.  */
4978
4979static void
4980sync_remote_interrupt_twice (int signo)
4981{
4982  signal (signo, ofunc);
4983  gdb_call_async_signal_handler (async_sigint_remote_twice_token, 1);
4984  signal (signo, sync_remote_interrupt);
4985}
4986
4987/* Non-stop version of target_stop.  Uses `vCont;t' to stop a remote
4988   thread, all threads of a remote process, or all threads of all
4989   processes.  */
4990
4991static void
4992remote_stop_ns (ptid_t ptid)
4993{
4994  struct remote_state *rs = get_remote_state ();
4995  char *p = rs->buf;
4996  char *endp = rs->buf + get_remote_packet_size ();
4997
4998  if (packet_support (PACKET_vCont) == PACKET_SUPPORT_UNKNOWN)
4999    remote_vcont_probe (rs);
5000
5001  if (!rs->supports_vCont.t)
5002    error (_("Remote server does not support stopping threads"));
5003
5004  if (ptid_equal (ptid, minus_one_ptid)
5005      || (!remote_multi_process_p (rs) && ptid_is_pid (ptid)))
5006    p += xsnprintf (p, endp - p, "vCont;t");
5007  else
5008    {
5009      ptid_t nptid;
5010
5011      p += xsnprintf (p, endp - p, "vCont;t:");
5012
5013      if (ptid_is_pid (ptid))
5014	  /* All (-1) threads of process.  */
5015	nptid = ptid_build (ptid_get_pid (ptid), -1, 0);
5016      else
5017	{
5018	  /* Small optimization: if we already have a stop reply for
5019	     this thread, no use in telling the stub we want this
5020	     stopped.  */
5021	  if (peek_stop_reply (ptid))
5022	    return;
5023
5024	  nptid = ptid;
5025	}
5026
5027      write_ptid (p, endp, nptid);
5028    }
5029
5030  /* In non-stop, we get an immediate OK reply.  The stop reply will
5031     come in asynchronously by notification.  */
5032  putpkt (rs->buf);
5033  getpkt (&rs->buf, &rs->buf_size, 0);
5034  if (strcmp (rs->buf, "OK") != 0)
5035    error (_("Stopping %s failed: %s"), target_pid_to_str (ptid), rs->buf);
5036}
5037
5038/* All-stop version of target_stop.  Sends a break or a ^C to stop the
5039   remote target.  It is undefined which thread of which process
5040   reports the stop.  */
5041
5042static void
5043remote_stop_as (ptid_t ptid)
5044{
5045  struct remote_state *rs = get_remote_state ();
5046
5047  rs->ctrlc_pending_p = 1;
5048
5049  /* If the inferior is stopped already, but the core didn't know
5050     about it yet, just ignore the request.  The cached wait status
5051     will be collected in remote_wait.  */
5052  if (rs->cached_wait_status)
5053    return;
5054
5055  /* Send interrupt_sequence to remote target.  */
5056  send_interrupt_sequence ();
5057}
5058
5059/* This is the generic stop called via the target vector.  When a target
5060   interrupt is requested, either by the command line or the GUI, we
5061   will eventually end up here.  */
5062
5063static void
5064remote_stop (struct target_ops *self, ptid_t ptid)
5065{
5066  if (remote_debug)
5067    fprintf_unfiltered (gdb_stdlog, "remote_stop called\n");
5068
5069  if (non_stop)
5070    remote_stop_ns (ptid);
5071  else
5072    remote_stop_as (ptid);
5073}
5074
5075/* Ask the user what to do when an interrupt is received.  */
5076
5077static void
5078interrupt_query (void)
5079{
5080  target_terminal_ours ();
5081
5082  if (target_is_async_p ())
5083    {
5084      signal (SIGINT, handle_sigint);
5085      quit ();
5086    }
5087  else
5088    {
5089      if (query (_("Interrupted while waiting for the program.\n\
5090Give up (and stop debugging it)? ")))
5091	{
5092	  remote_unpush_target ();
5093	  quit ();
5094	}
5095    }
5096
5097  target_terminal_inferior ();
5098}
5099
5100/* Enable/disable target terminal ownership.  Most targets can use
5101   terminal groups to control terminal ownership.  Remote targets are
5102   different in that explicit transfer of ownership to/from GDB/target
5103   is required.  */
5104
5105static void
5106remote_terminal_inferior (struct target_ops *self)
5107{
5108  if (!target_async_permitted)
5109    /* Nothing to do.  */
5110    return;
5111
5112  /* FIXME: cagney/1999-09-27: Make calls to target_terminal_*()
5113     idempotent.  The event-loop GDB talking to an asynchronous target
5114     with a synchronous command calls this function from both
5115     event-top.c and infrun.c/infcmd.c.  Once GDB stops trying to
5116     transfer the terminal to the target when it shouldn't this guard
5117     can go away.  */
5118  if (!remote_async_terminal_ours_p)
5119    return;
5120  delete_file_handler (input_fd);
5121  remote_async_terminal_ours_p = 0;
5122  async_initialize_sigint_signal_handler ();
5123  /* NOTE: At this point we could also register our selves as the
5124     recipient of all input.  Any characters typed could then be
5125     passed on down to the target.  */
5126}
5127
5128static void
5129remote_terminal_ours (struct target_ops *self)
5130{
5131  if (!target_async_permitted)
5132    /* Nothing to do.  */
5133    return;
5134
5135  /* See FIXME in remote_terminal_inferior.  */
5136  if (remote_async_terminal_ours_p)
5137    return;
5138  async_cleanup_sigint_signal_handler (NULL);
5139  add_file_handler (input_fd, stdin_event_handler, 0);
5140  remote_async_terminal_ours_p = 1;
5141}
5142
5143static void
5144remote_console_output (char *msg)
5145{
5146  char *p;
5147
5148  for (p = msg; p[0] && p[1]; p += 2)
5149    {
5150      char tb[2];
5151      char c = fromhex (p[0]) * 16 + fromhex (p[1]);
5152
5153      tb[0] = c;
5154      tb[1] = 0;
5155      fputs_unfiltered (tb, gdb_stdtarg);
5156    }
5157  gdb_flush (gdb_stdtarg);
5158}
5159
5160typedef struct cached_reg
5161{
5162  int num;
5163  gdb_byte data[MAX_REGISTER_SIZE];
5164} cached_reg_t;
5165
5166DEF_VEC_O(cached_reg_t);
5167
5168typedef struct stop_reply
5169{
5170  struct notif_event base;
5171
5172  /* The identifier of the thread about this event  */
5173  ptid_t ptid;
5174
5175  /* The remote state this event is associated with.  When the remote
5176     connection, represented by a remote_state object, is closed,
5177     all the associated stop_reply events should be released.  */
5178  struct remote_state *rs;
5179
5180  struct target_waitstatus ws;
5181
5182  /* Expedited registers.  This makes remote debugging a bit more
5183     efficient for those targets that provide critical registers as
5184     part of their normal status mechanism (as another roundtrip to
5185     fetch them is avoided).  */
5186  VEC(cached_reg_t) *regcache;
5187
5188  int stopped_by_watchpoint_p;
5189  CORE_ADDR watch_data_address;
5190
5191  int core;
5192} *stop_reply_p;
5193
5194DECLARE_QUEUE_P (stop_reply_p);
5195DEFINE_QUEUE_P (stop_reply_p);
5196/* The list of already fetched and acknowledged stop events.  This
5197   queue is used for notification Stop, and other notifications
5198   don't need queue for their events, because the notification events
5199   of Stop can't be consumed immediately, so that events should be
5200   queued first, and be consumed by remote_wait_{ns,as} one per
5201   time.  Other notifications can consume their events immediately,
5202   so queue is not needed for them.  */
5203static QUEUE (stop_reply_p) *stop_reply_queue;
5204
5205static void
5206stop_reply_xfree (struct stop_reply *r)
5207{
5208  notif_event_xfree ((struct notif_event *) r);
5209}
5210
5211static void
5212remote_notif_stop_parse (struct notif_client *self, char *buf,
5213			 struct notif_event *event)
5214{
5215  remote_parse_stop_reply (buf, (struct stop_reply *) event);
5216}
5217
5218static void
5219remote_notif_stop_ack (struct notif_client *self, char *buf,
5220		       struct notif_event *event)
5221{
5222  struct stop_reply *stop_reply = (struct stop_reply *) event;
5223
5224  /* acknowledge */
5225  putpkt ((char *) self->ack_command);
5226
5227  if (stop_reply->ws.kind == TARGET_WAITKIND_IGNORE)
5228      /* We got an unknown stop reply.  */
5229      error (_("Unknown stop reply"));
5230
5231  push_stop_reply (stop_reply);
5232}
5233
5234static int
5235remote_notif_stop_can_get_pending_events (struct notif_client *self)
5236{
5237  /* We can't get pending events in remote_notif_process for
5238     notification stop, and we have to do this in remote_wait_ns
5239     instead.  If we fetch all queued events from stub, remote stub
5240     may exit and we have no chance to process them back in
5241     remote_wait_ns.  */
5242  mark_async_event_handler (remote_async_inferior_event_token);
5243  return 0;
5244}
5245
5246static void
5247stop_reply_dtr (struct notif_event *event)
5248{
5249  struct stop_reply *r = (struct stop_reply *) event;
5250
5251  VEC_free (cached_reg_t, r->regcache);
5252}
5253
5254static struct notif_event *
5255remote_notif_stop_alloc_reply (void)
5256{
5257  struct notif_event *r
5258    = (struct notif_event *) XNEW (struct stop_reply);
5259
5260  r->dtr = stop_reply_dtr;
5261
5262  return r;
5263}
5264
5265/* A client of notification Stop.  */
5266
5267struct notif_client notif_client_stop =
5268{
5269  "Stop",
5270  "vStopped",
5271  remote_notif_stop_parse,
5272  remote_notif_stop_ack,
5273  remote_notif_stop_can_get_pending_events,
5274  remote_notif_stop_alloc_reply,
5275  REMOTE_NOTIF_STOP,
5276};
5277
5278/* A parameter to pass data in and out.  */
5279
5280struct queue_iter_param
5281{
5282  void *input;
5283  struct stop_reply *output;
5284};
5285
5286/* Remove stop replies in the queue if its pid is equal to the given
5287   inferior's pid.  */
5288
5289static int
5290remove_stop_reply_for_inferior (QUEUE (stop_reply_p) *q,
5291				QUEUE_ITER (stop_reply_p) *iter,
5292				stop_reply_p event,
5293				void *data)
5294{
5295  struct queue_iter_param *param = data;
5296  struct inferior *inf = param->input;
5297
5298  if (ptid_get_pid (event->ptid) == inf->pid)
5299    {
5300      stop_reply_xfree (event);
5301      QUEUE_remove_elem (stop_reply_p, q, iter);
5302    }
5303
5304  return 1;
5305}
5306
5307/* Discard all pending stop replies of inferior INF.  */
5308
5309static void
5310discard_pending_stop_replies (struct inferior *inf)
5311{
5312  int i;
5313  struct queue_iter_param param;
5314  struct stop_reply *reply;
5315  struct remote_state *rs = get_remote_state ();
5316  struct remote_notif_state *rns = rs->notif_state;
5317
5318  /* This function can be notified when an inferior exists.  When the
5319     target is not remote, the notification state is NULL.  */
5320  if (rs->remote_desc == NULL)
5321    return;
5322
5323  reply = (struct stop_reply *) rns->pending_event[notif_client_stop.id];
5324
5325  /* Discard the in-flight notification.  */
5326  if (reply != NULL && ptid_get_pid (reply->ptid) == inf->pid)
5327    {
5328      stop_reply_xfree (reply);
5329      rns->pending_event[notif_client_stop.id] = NULL;
5330    }
5331
5332  param.input = inf;
5333  param.output = NULL;
5334  /* Discard the stop replies we have already pulled with
5335     vStopped.  */
5336  QUEUE_iterate (stop_reply_p, stop_reply_queue,
5337		 remove_stop_reply_for_inferior, &param);
5338}
5339
5340/* If its remote state is equal to the given remote state,
5341   remove EVENT from the stop reply queue.  */
5342
5343static int
5344remove_stop_reply_of_remote_state (QUEUE (stop_reply_p) *q,
5345				   QUEUE_ITER (stop_reply_p) *iter,
5346				   stop_reply_p event,
5347				   void *data)
5348{
5349  struct queue_iter_param *param = data;
5350  struct remote_state *rs = param->input;
5351
5352  if (event->rs == rs)
5353    {
5354      stop_reply_xfree (event);
5355      QUEUE_remove_elem (stop_reply_p, q, iter);
5356    }
5357
5358  return 1;
5359}
5360
5361/* Discard the stop replies for RS in stop_reply_queue.  */
5362
5363static void
5364discard_pending_stop_replies_in_queue (struct remote_state *rs)
5365{
5366  struct queue_iter_param param;
5367
5368  param.input = rs;
5369  param.output = NULL;
5370  /* Discard the stop replies we have already pulled with
5371     vStopped.  */
5372  QUEUE_iterate (stop_reply_p, stop_reply_queue,
5373		 remove_stop_reply_of_remote_state, &param);
5374}
5375
5376/* A parameter to pass data in and out.  */
5377
5378static int
5379remote_notif_remove_once_on_match (QUEUE (stop_reply_p) *q,
5380				   QUEUE_ITER (stop_reply_p) *iter,
5381				   stop_reply_p event,
5382				   void *data)
5383{
5384  struct queue_iter_param *param = data;
5385  ptid_t *ptid = param->input;
5386
5387  if (ptid_match (event->ptid, *ptid))
5388    {
5389      param->output = event;
5390      QUEUE_remove_elem (stop_reply_p, q, iter);
5391      return 0;
5392    }
5393
5394  return 1;
5395}
5396
5397/* Remove the first reply in 'stop_reply_queue' which matches
5398   PTID.  */
5399
5400static struct stop_reply *
5401remote_notif_remove_queued_reply (ptid_t ptid)
5402{
5403  struct queue_iter_param param;
5404
5405  param.input = &ptid;
5406  param.output = NULL;
5407
5408  QUEUE_iterate (stop_reply_p, stop_reply_queue,
5409		 remote_notif_remove_once_on_match, &param);
5410  if (notif_debug)
5411    fprintf_unfiltered (gdb_stdlog,
5412			"notif: discard queued event: 'Stop' in %s\n",
5413			target_pid_to_str (ptid));
5414
5415  return param.output;
5416}
5417
5418/* Look for a queued stop reply belonging to PTID.  If one is found,
5419   remove it from the queue, and return it.  Returns NULL if none is
5420   found.  If there are still queued events left to process, tell the
5421   event loop to get back to target_wait soon.  */
5422
5423static struct stop_reply *
5424queued_stop_reply (ptid_t ptid)
5425{
5426  struct stop_reply *r = remote_notif_remove_queued_reply (ptid);
5427
5428  if (!QUEUE_is_empty (stop_reply_p, stop_reply_queue))
5429    /* There's still at least an event left.  */
5430    mark_async_event_handler (remote_async_inferior_event_token);
5431
5432  return r;
5433}
5434
5435/* Push a fully parsed stop reply in the stop reply queue.  Since we
5436   know that we now have at least one queued event left to pass to the
5437   core side, tell the event loop to get back to target_wait soon.  */
5438
5439static void
5440push_stop_reply (struct stop_reply *new_event)
5441{
5442  QUEUE_enque (stop_reply_p, stop_reply_queue, new_event);
5443
5444  if (notif_debug)
5445    fprintf_unfiltered (gdb_stdlog,
5446			"notif: push 'Stop' %s to queue %d\n",
5447			target_pid_to_str (new_event->ptid),
5448			QUEUE_length (stop_reply_p,
5449				      stop_reply_queue));
5450
5451  mark_async_event_handler (remote_async_inferior_event_token);
5452}
5453
5454static int
5455stop_reply_match_ptid_and_ws (QUEUE (stop_reply_p) *q,
5456			      QUEUE_ITER (stop_reply_p) *iter,
5457			      struct stop_reply *event,
5458			      void *data)
5459{
5460  ptid_t *ptid = data;
5461
5462  return !(ptid_equal (*ptid, event->ptid)
5463	   && event->ws.kind == TARGET_WAITKIND_STOPPED);
5464}
5465
5466/* Returns true if we have a stop reply for PTID.  */
5467
5468static int
5469peek_stop_reply (ptid_t ptid)
5470{
5471  return !QUEUE_iterate (stop_reply_p, stop_reply_queue,
5472			 stop_reply_match_ptid_and_ws, &ptid);
5473}
5474
5475/* Parse the stop reply in BUF.  Either the function succeeds, and the
5476   result is stored in EVENT, or throws an error.  */
5477
5478static void
5479remote_parse_stop_reply (char *buf, struct stop_reply *event)
5480{
5481  struct remote_arch_state *rsa = get_remote_arch_state ();
5482  ULONGEST addr;
5483  char *p;
5484
5485  event->ptid = null_ptid;
5486  event->rs = get_remote_state ();
5487  event->ws.kind = TARGET_WAITKIND_IGNORE;
5488  event->ws.value.integer = 0;
5489  event->stopped_by_watchpoint_p = 0;
5490  event->regcache = NULL;
5491  event->core = -1;
5492
5493  switch (buf[0])
5494    {
5495    case 'T':		/* Status with PC, SP, FP, ...	*/
5496      /* Expedited reply, containing Signal, {regno, reg} repeat.  */
5497      /*  format is:  'Tssn...:r...;n...:r...;n...:r...;#cc', where
5498	    ss = signal number
5499	    n... = register number
5500	    r... = register contents
5501      */
5502
5503      p = &buf[3];	/* after Txx */
5504      while (*p)
5505	{
5506	  char *p1;
5507	  char *p_temp;
5508	  int fieldsize;
5509	  LONGEST pnum = 0;
5510
5511	  /* If the packet contains a register number, save it in
5512	     pnum and set p1 to point to the character following it.
5513	     Otherwise p1 points to p.  */
5514
5515	  /* If this packet is an awatch packet, don't parse the 'a'
5516	     as a register number.  */
5517
5518	  if (strncmp (p, "awatch", strlen("awatch")) != 0
5519	      && strncmp (p, "core", strlen ("core")) != 0)
5520	    {
5521	      /* Read the ``P'' register number.  */
5522	      pnum = strtol (p, &p_temp, 16);
5523	      p1 = p_temp;
5524	    }
5525	  else
5526	    p1 = p;
5527
5528	  if (p1 == p)	/* No register number present here.  */
5529	    {
5530	      p1 = strchr (p, ':');
5531	      if (p1 == NULL)
5532		error (_("Malformed packet(a) (missing colon): %s\n\
5533Packet: '%s'\n"),
5534		       p, buf);
5535	      if (strncmp (p, "thread", p1 - p) == 0)
5536		event->ptid = read_ptid (++p1, &p);
5537	      else if ((strncmp (p, "watch", p1 - p) == 0)
5538		       || (strncmp (p, "rwatch", p1 - p) == 0)
5539		       || (strncmp (p, "awatch", p1 - p) == 0))
5540		{
5541		  event->stopped_by_watchpoint_p = 1;
5542		  p = unpack_varlen_hex (++p1, &addr);
5543		  event->watch_data_address = (CORE_ADDR) addr;
5544		}
5545	      else if (strncmp (p, "library", p1 - p) == 0)
5546		{
5547		  p1++;
5548		  p_temp = p1;
5549		  while (*p_temp && *p_temp != ';')
5550		    p_temp++;
5551
5552		  event->ws.kind = TARGET_WAITKIND_LOADED;
5553		  p = p_temp;
5554		}
5555	      else if (strncmp (p, "replaylog", p1 - p) == 0)
5556		{
5557		  event->ws.kind = TARGET_WAITKIND_NO_HISTORY;
5558		  /* p1 will indicate "begin" or "end", but it makes
5559		     no difference for now, so ignore it.  */
5560		  p_temp = strchr (p1 + 1, ';');
5561		  if (p_temp)
5562		    p = p_temp;
5563		}
5564	      else if (strncmp (p, "core", p1 - p) == 0)
5565		{
5566		  ULONGEST c;
5567
5568		  p = unpack_varlen_hex (++p1, &c);
5569		  event->core = c;
5570		}
5571	      else
5572		{
5573		  /* Silently skip unknown optional info.  */
5574		  p_temp = strchr (p1 + 1, ';');
5575		  if (p_temp)
5576		    p = p_temp;
5577		}
5578	    }
5579	  else
5580	    {
5581	      struct packet_reg *reg = packet_reg_from_pnum (rsa, pnum);
5582	      cached_reg_t cached_reg;
5583
5584	      p = p1;
5585
5586	      if (*p != ':')
5587		error (_("Malformed packet(b) (missing colon): %s\n\
5588Packet: '%s'\n"),
5589		       p, buf);
5590	      ++p;
5591
5592	      if (reg == NULL)
5593		error (_("Remote sent bad register number %s: %s\n\
5594Packet: '%s'\n"),
5595		       hex_string (pnum), p, buf);
5596
5597	      cached_reg.num = reg->regnum;
5598
5599	      fieldsize = hex2bin (p, cached_reg.data,
5600				   register_size (target_gdbarch (),
5601						  reg->regnum));
5602	      p += 2 * fieldsize;
5603	      if (fieldsize < register_size (target_gdbarch (),
5604					     reg->regnum))
5605		warning (_("Remote reply is too short: %s"), buf);
5606
5607	      VEC_safe_push (cached_reg_t, event->regcache, &cached_reg);
5608	    }
5609
5610	  if (*p != ';')
5611	    error (_("Remote register badly formatted: %s\nhere: %s"),
5612		   buf, p);
5613	  ++p;
5614	}
5615
5616      if (event->ws.kind != TARGET_WAITKIND_IGNORE)
5617	break;
5618
5619      /* fall through */
5620    case 'S':		/* Old style status, just signal only.  */
5621      {
5622	int sig;
5623
5624	event->ws.kind = TARGET_WAITKIND_STOPPED;
5625	sig = (fromhex (buf[1]) << 4) + fromhex (buf[2]);
5626	if (GDB_SIGNAL_FIRST <= sig && sig < GDB_SIGNAL_LAST)
5627	  event->ws.value.sig = (enum gdb_signal) sig;
5628	else
5629	  event->ws.value.sig = GDB_SIGNAL_UNKNOWN;
5630      }
5631      break;
5632    case 'W':		/* Target exited.  */
5633    case 'X':
5634      {
5635	char *p;
5636	int pid;
5637	ULONGEST value;
5638
5639	/* GDB used to accept only 2 hex chars here.  Stubs should
5640	   only send more if they detect GDB supports multi-process
5641	   support.  */
5642	p = unpack_varlen_hex (&buf[1], &value);
5643
5644	if (buf[0] == 'W')
5645	  {
5646	    /* The remote process exited.  */
5647	    event->ws.kind = TARGET_WAITKIND_EXITED;
5648	    event->ws.value.integer = value;
5649	  }
5650	else
5651	  {
5652	    /* The remote process exited with a signal.  */
5653	    event->ws.kind = TARGET_WAITKIND_SIGNALLED;
5654	    if (GDB_SIGNAL_FIRST <= value && value < GDB_SIGNAL_LAST)
5655	      event->ws.value.sig = (enum gdb_signal) value;
5656	    else
5657	      event->ws.value.sig = GDB_SIGNAL_UNKNOWN;
5658	  }
5659
5660	/* If no process is specified, assume inferior_ptid.  */
5661	pid = ptid_get_pid (inferior_ptid);
5662	if (*p == '\0')
5663	  ;
5664	else if (*p == ';')
5665	  {
5666	    p++;
5667
5668	    if (p == '\0')
5669	      ;
5670	    else if (strncmp (p,
5671			      "process:", sizeof ("process:") - 1) == 0)
5672	      {
5673		ULONGEST upid;
5674
5675		p += sizeof ("process:") - 1;
5676		unpack_varlen_hex (p, &upid);
5677		pid = upid;
5678	      }
5679	    else
5680	      error (_("unknown stop reply packet: %s"), buf);
5681	  }
5682	else
5683	  error (_("unknown stop reply packet: %s"), buf);
5684	event->ptid = pid_to_ptid (pid);
5685      }
5686      break;
5687    }
5688
5689  if (non_stop && ptid_equal (event->ptid, null_ptid))
5690    error (_("No process or thread specified in stop reply: %s"), buf);
5691}
5692
5693/* When the stub wants to tell GDB about a new notification reply, it
5694   sends a notification (%Stop, for example).  Those can come it at
5695   any time, hence, we have to make sure that any pending
5696   putpkt/getpkt sequence we're making is finished, before querying
5697   the stub for more events with the corresponding ack command
5698   (vStopped, for example).  E.g., if we started a vStopped sequence
5699   immediately upon receiving the notification, something like this
5700   could happen:
5701
5702    1.1) --> Hg 1
5703    1.2) <-- OK
5704    1.3) --> g
5705    1.4) <-- %Stop
5706    1.5) --> vStopped
5707    1.6) <-- (registers reply to step #1.3)
5708
5709   Obviously, the reply in step #1.6 would be unexpected to a vStopped
5710   query.
5711
5712   To solve this, whenever we parse a %Stop notification successfully,
5713   we mark the REMOTE_ASYNC_GET_PENDING_EVENTS_TOKEN, and carry on
5714   doing whatever we were doing:
5715
5716    2.1) --> Hg 1
5717    2.2) <-- OK
5718    2.3) --> g
5719    2.4) <-- %Stop
5720      <GDB marks the REMOTE_ASYNC_GET_PENDING_EVENTS_TOKEN>
5721    2.5) <-- (registers reply to step #2.3)
5722
5723   Eventualy after step #2.5, we return to the event loop, which
5724   notices there's an event on the
5725   REMOTE_ASYNC_GET_PENDING_EVENTS_TOKEN event and calls the
5726   associated callback --- the function below.  At this point, we're
5727   always safe to start a vStopped sequence. :
5728
5729    2.6) --> vStopped
5730    2.7) <-- T05 thread:2
5731    2.8) --> vStopped
5732    2.9) --> OK
5733*/
5734
5735void
5736remote_notif_get_pending_events (struct notif_client *nc)
5737{
5738  struct remote_state *rs = get_remote_state ();
5739
5740  if (rs->notif_state->pending_event[nc->id] != NULL)
5741    {
5742      if (notif_debug)
5743	fprintf_unfiltered (gdb_stdlog,
5744			    "notif: process: '%s' ack pending event\n",
5745			    nc->name);
5746
5747      /* acknowledge */
5748      nc->ack (nc, rs->buf, rs->notif_state->pending_event[nc->id]);
5749      rs->notif_state->pending_event[nc->id] = NULL;
5750
5751      while (1)
5752	{
5753	  getpkt (&rs->buf, &rs->buf_size, 0);
5754	  if (strcmp (rs->buf, "OK") == 0)
5755	    break;
5756	  else
5757	    remote_notif_ack (nc, rs->buf);
5758	}
5759    }
5760  else
5761    {
5762      if (notif_debug)
5763	fprintf_unfiltered (gdb_stdlog,
5764			    "notif: process: '%s' no pending reply\n",
5765			    nc->name);
5766    }
5767}
5768
5769/* Called when it is decided that STOP_REPLY holds the info of the
5770   event that is to be returned to the core.  This function always
5771   destroys STOP_REPLY.  */
5772
5773static ptid_t
5774process_stop_reply (struct stop_reply *stop_reply,
5775		    struct target_waitstatus *status)
5776{
5777  ptid_t ptid;
5778
5779  *status = stop_reply->ws;
5780  ptid = stop_reply->ptid;
5781
5782  /* If no thread/process was reported by the stub, assume the current
5783     inferior.  */
5784  if (ptid_equal (ptid, null_ptid))
5785    ptid = inferior_ptid;
5786
5787  if (status->kind != TARGET_WAITKIND_EXITED
5788      && status->kind != TARGET_WAITKIND_SIGNALLED)
5789    {
5790      struct remote_state *rs = get_remote_state ();
5791
5792      /* Expedited registers.  */
5793      if (stop_reply->regcache)
5794	{
5795	  struct regcache *regcache
5796	    = get_thread_arch_regcache (ptid, target_gdbarch ());
5797	  cached_reg_t *reg;
5798	  int ix;
5799
5800	  for (ix = 0;
5801	       VEC_iterate(cached_reg_t, stop_reply->regcache, ix, reg);
5802	       ix++)
5803	    regcache_raw_supply (regcache, reg->num, reg->data);
5804	  VEC_free (cached_reg_t, stop_reply->regcache);
5805	}
5806
5807      rs->remote_stopped_by_watchpoint_p = stop_reply->stopped_by_watchpoint_p;
5808      rs->remote_watch_data_address = stop_reply->watch_data_address;
5809
5810      remote_notice_new_inferior (ptid, 0);
5811      demand_private_info (ptid)->core = stop_reply->core;
5812    }
5813
5814  stop_reply_xfree (stop_reply);
5815  return ptid;
5816}
5817
5818/* The non-stop mode version of target_wait.  */
5819
5820static ptid_t
5821remote_wait_ns (ptid_t ptid, struct target_waitstatus *status, int options)
5822{
5823  struct remote_state *rs = get_remote_state ();
5824  struct stop_reply *stop_reply;
5825  int ret;
5826  int is_notif = 0;
5827
5828  /* If in non-stop mode, get out of getpkt even if a
5829     notification is received.	*/
5830
5831  ret = getpkt_or_notif_sane (&rs->buf, &rs->buf_size,
5832			      0 /* forever */, &is_notif);
5833  while (1)
5834    {
5835      if (ret != -1 && !is_notif)
5836	switch (rs->buf[0])
5837	  {
5838	  case 'E':		/* Error of some sort.	*/
5839	    /* We're out of sync with the target now.  Did it continue
5840	       or not?  We can't tell which thread it was in non-stop,
5841	       so just ignore this.  */
5842	    warning (_("Remote failure reply: %s"), rs->buf);
5843	    break;
5844	  case 'O':		/* Console output.  */
5845	    remote_console_output (rs->buf + 1);
5846	    break;
5847	  default:
5848	    warning (_("Invalid remote reply: %s"), rs->buf);
5849	    break;
5850	  }
5851
5852      /* Acknowledge a pending stop reply that may have arrived in the
5853	 mean time.  */
5854      if (rs->notif_state->pending_event[notif_client_stop.id] != NULL)
5855	remote_notif_get_pending_events (&notif_client_stop);
5856
5857      /* If indeed we noticed a stop reply, we're done.  */
5858      stop_reply = queued_stop_reply (ptid);
5859      if (stop_reply != NULL)
5860	return process_stop_reply (stop_reply, status);
5861
5862      /* Still no event.  If we're just polling for an event, then
5863	 return to the event loop.  */
5864      if (options & TARGET_WNOHANG)
5865	{
5866	  status->kind = TARGET_WAITKIND_IGNORE;
5867	  return minus_one_ptid;
5868	}
5869
5870      /* Otherwise do a blocking wait.  */
5871      ret = getpkt_or_notif_sane (&rs->buf, &rs->buf_size,
5872				  1 /* forever */, &is_notif);
5873    }
5874}
5875
5876/* Wait until the remote machine stops, then return, storing status in
5877   STATUS just as `wait' would.  */
5878
5879static ptid_t
5880remote_wait_as (ptid_t ptid, struct target_waitstatus *status, int options)
5881{
5882  struct remote_state *rs = get_remote_state ();
5883  ptid_t event_ptid = null_ptid;
5884  char *buf;
5885  struct stop_reply *stop_reply;
5886
5887 again:
5888
5889  status->kind = TARGET_WAITKIND_IGNORE;
5890  status->value.integer = 0;
5891
5892  stop_reply = queued_stop_reply (ptid);
5893  if (stop_reply != NULL)
5894    return process_stop_reply (stop_reply, status);
5895
5896  if (rs->cached_wait_status)
5897    /* Use the cached wait status, but only once.  */
5898    rs->cached_wait_status = 0;
5899  else
5900    {
5901      int ret;
5902      int is_notif;
5903
5904      if (!target_is_async_p ())
5905	{
5906	  ofunc = signal (SIGINT, sync_remote_interrupt);
5907	  /* If the user hit C-c before this packet, or between packets,
5908	     pretend that it was hit right here.  */
5909	  if (check_quit_flag ())
5910	    {
5911	      clear_quit_flag ();
5912	      sync_remote_interrupt (SIGINT);
5913	    }
5914	}
5915
5916      /* FIXME: cagney/1999-09-27: If we're in async mode we should
5917	 _never_ wait for ever -> test on target_is_async_p().
5918	 However, before we do that we need to ensure that the caller
5919	 knows how to take the target into/out of async mode.  */
5920      ret = getpkt_or_notif_sane (&rs->buf, &rs->buf_size,
5921				  wait_forever_enabled_p, &is_notif);
5922
5923      if (!target_is_async_p ())
5924	signal (SIGINT, ofunc);
5925
5926      /* GDB gets a notification.  Return to core as this event is
5927	 not interesting.  */
5928      if (ret != -1 && is_notif)
5929	return minus_one_ptid;
5930    }
5931
5932  buf = rs->buf;
5933
5934  rs->remote_stopped_by_watchpoint_p = 0;
5935
5936  /* We got something.  */
5937  rs->waiting_for_stop_reply = 0;
5938
5939  /* Assume that the target has acknowledged Ctrl-C unless we receive
5940     an 'F' or 'O' packet.  */
5941  if (buf[0] != 'F' && buf[0] != 'O')
5942    rs->ctrlc_pending_p = 0;
5943
5944  switch (buf[0])
5945    {
5946    case 'E':		/* Error of some sort.	*/
5947      /* We're out of sync with the target now.  Did it continue or
5948	 not?  Not is more likely, so report a stop.  */
5949      warning (_("Remote failure reply: %s"), buf);
5950      status->kind = TARGET_WAITKIND_STOPPED;
5951      status->value.sig = GDB_SIGNAL_0;
5952      break;
5953    case 'F':		/* File-I/O request.  */
5954      remote_fileio_request (buf, rs->ctrlc_pending_p);
5955      rs->ctrlc_pending_p = 0;
5956      break;
5957    case 'T': case 'S': case 'X': case 'W':
5958      {
5959	struct stop_reply *stop_reply
5960	  = (struct stop_reply *) remote_notif_parse (&notif_client_stop,
5961						      rs->buf);
5962
5963	event_ptid = process_stop_reply (stop_reply, status);
5964	break;
5965      }
5966    case 'O':		/* Console output.  */
5967      remote_console_output (buf + 1);
5968
5969      /* The target didn't really stop; keep waiting.  */
5970      rs->waiting_for_stop_reply = 1;
5971
5972      break;
5973    case '\0':
5974      if (rs->last_sent_signal != GDB_SIGNAL_0)
5975	{
5976	  /* Zero length reply means that we tried 'S' or 'C' and the
5977	     remote system doesn't support it.  */
5978	  target_terminal_ours_for_output ();
5979	  printf_filtered
5980	    ("Can't send signals to this remote system.  %s not sent.\n",
5981	     gdb_signal_to_name (rs->last_sent_signal));
5982	  rs->last_sent_signal = GDB_SIGNAL_0;
5983	  target_terminal_inferior ();
5984
5985	  strcpy ((char *) buf, rs->last_sent_step ? "s" : "c");
5986	  putpkt ((char *) buf);
5987
5988	  /* We just told the target to resume, so a stop reply is in
5989	     order.  */
5990	  rs->waiting_for_stop_reply = 1;
5991	  break;
5992	}
5993      /* else fallthrough */
5994    default:
5995      warning (_("Invalid remote reply: %s"), buf);
5996      /* Keep waiting.  */
5997      rs->waiting_for_stop_reply = 1;
5998      break;
5999    }
6000
6001  if (status->kind == TARGET_WAITKIND_IGNORE)
6002    {
6003      /* Nothing interesting happened.  If we're doing a non-blocking
6004	 poll, we're done.  Otherwise, go back to waiting.  */
6005      if (options & TARGET_WNOHANG)
6006	return minus_one_ptid;
6007      else
6008	goto again;
6009    }
6010  else if (status->kind != TARGET_WAITKIND_EXITED
6011	   && status->kind != TARGET_WAITKIND_SIGNALLED)
6012    {
6013      if (!ptid_equal (event_ptid, null_ptid))
6014	record_currthread (rs, event_ptid);
6015      else
6016	event_ptid = inferior_ptid;
6017    }
6018  else
6019    /* A process exit.  Invalidate our notion of current thread.  */
6020    record_currthread (rs, minus_one_ptid);
6021
6022  return event_ptid;
6023}
6024
6025/* Wait until the remote machine stops, then return, storing status in
6026   STATUS just as `wait' would.  */
6027
6028static ptid_t
6029remote_wait (struct target_ops *ops,
6030	     ptid_t ptid, struct target_waitstatus *status, int options)
6031{
6032  ptid_t event_ptid;
6033
6034  if (non_stop)
6035    event_ptid = remote_wait_ns (ptid, status, options);
6036  else
6037    event_ptid = remote_wait_as (ptid, status, options);
6038
6039  if (target_is_async_p ())
6040    {
6041      /* If there are are events left in the queue tell the event loop
6042	 to return here.  */
6043      if (!QUEUE_is_empty (stop_reply_p, stop_reply_queue))
6044	mark_async_event_handler (remote_async_inferior_event_token);
6045    }
6046
6047  return event_ptid;
6048}
6049
6050/* Fetch a single register using a 'p' packet.  */
6051
6052static int
6053fetch_register_using_p (struct regcache *regcache, struct packet_reg *reg)
6054{
6055  struct remote_state *rs = get_remote_state ();
6056  char *buf, *p;
6057  char regp[MAX_REGISTER_SIZE];
6058  int i;
6059
6060  if (packet_support (PACKET_p) == PACKET_DISABLE)
6061    return 0;
6062
6063  if (reg->pnum == -1)
6064    return 0;
6065
6066  p = rs->buf;
6067  *p++ = 'p';
6068  p += hexnumstr (p, reg->pnum);
6069  *p++ = '\0';
6070  putpkt (rs->buf);
6071  getpkt (&rs->buf, &rs->buf_size, 0);
6072
6073  buf = rs->buf;
6074
6075  switch (packet_ok (buf, &remote_protocol_packets[PACKET_p]))
6076    {
6077    case PACKET_OK:
6078      break;
6079    case PACKET_UNKNOWN:
6080      return 0;
6081    case PACKET_ERROR:
6082      error (_("Could not fetch register \"%s\"; remote failure reply '%s'"),
6083	     gdbarch_register_name (get_regcache_arch (regcache),
6084				    reg->regnum),
6085	     buf);
6086    }
6087
6088  /* If this register is unfetchable, tell the regcache.  */
6089  if (buf[0] == 'x')
6090    {
6091      regcache_raw_supply (regcache, reg->regnum, NULL);
6092      return 1;
6093    }
6094
6095  /* Otherwise, parse and supply the value.  */
6096  p = buf;
6097  i = 0;
6098  while (p[0] != 0)
6099    {
6100      if (p[1] == 0)
6101	error (_("fetch_register_using_p: early buf termination"));
6102
6103      regp[i++] = fromhex (p[0]) * 16 + fromhex (p[1]);
6104      p += 2;
6105    }
6106  regcache_raw_supply (regcache, reg->regnum, regp);
6107  return 1;
6108}
6109
6110/* Fetch the registers included in the target's 'g' packet.  */
6111
6112static int
6113send_g_packet (void)
6114{
6115  struct remote_state *rs = get_remote_state ();
6116  int buf_len;
6117
6118  xsnprintf (rs->buf, get_remote_packet_size (), "g");
6119  remote_send (&rs->buf, &rs->buf_size);
6120
6121  /* We can get out of synch in various cases.  If the first character
6122     in the buffer is not a hex character, assume that has happened
6123     and try to fetch another packet to read.  */
6124  while ((rs->buf[0] < '0' || rs->buf[0] > '9')
6125	 && (rs->buf[0] < 'A' || rs->buf[0] > 'F')
6126	 && (rs->buf[0] < 'a' || rs->buf[0] > 'f')
6127	 && rs->buf[0] != 'x')	/* New: unavailable register value.  */
6128    {
6129      if (remote_debug)
6130	fprintf_unfiltered (gdb_stdlog,
6131			    "Bad register packet; fetching a new packet\n");
6132      getpkt (&rs->buf, &rs->buf_size, 0);
6133    }
6134
6135  buf_len = strlen (rs->buf);
6136
6137  /* Sanity check the received packet.  */
6138  if (buf_len % 2 != 0)
6139    error (_("Remote 'g' packet reply is of odd length: %s"), rs->buf);
6140
6141  return buf_len / 2;
6142}
6143
6144static void
6145process_g_packet (struct regcache *regcache)
6146{
6147  struct gdbarch *gdbarch = get_regcache_arch (regcache);
6148  struct remote_state *rs = get_remote_state ();
6149  struct remote_arch_state *rsa = get_remote_arch_state ();
6150  int i, buf_len;
6151  char *p;
6152  char *regs;
6153
6154  buf_len = strlen (rs->buf);
6155
6156  /* Further sanity checks, with knowledge of the architecture.  */
6157  if (buf_len > 2 * rsa->sizeof_g_packet)
6158    error (_("Remote 'g' packet reply is too long: %s"), rs->buf);
6159
6160  /* Save the size of the packet sent to us by the target.  It is used
6161     as a heuristic when determining the max size of packets that the
6162     target can safely receive.  */
6163  if (rsa->actual_register_packet_size == 0)
6164    rsa->actual_register_packet_size = buf_len;
6165
6166  /* If this is smaller than we guessed the 'g' packet would be,
6167     update our records.  A 'g' reply that doesn't include a register's
6168     value implies either that the register is not available, or that
6169     the 'p' packet must be used.  */
6170  if (buf_len < 2 * rsa->sizeof_g_packet)
6171    {
6172      rsa->sizeof_g_packet = buf_len / 2;
6173
6174      for (i = 0; i < gdbarch_num_regs (gdbarch); i++)
6175	{
6176	  if (rsa->regs[i].pnum == -1)
6177	    continue;
6178
6179	  if (rsa->regs[i].offset >= rsa->sizeof_g_packet)
6180	    rsa->regs[i].in_g_packet = 0;
6181	  else
6182	    rsa->regs[i].in_g_packet = 1;
6183	}
6184    }
6185
6186  regs = alloca (rsa->sizeof_g_packet);
6187
6188  /* Unimplemented registers read as all bits zero.  */
6189  memset (regs, 0, rsa->sizeof_g_packet);
6190
6191  /* Reply describes registers byte by byte, each byte encoded as two
6192     hex characters.  Suck them all up, then supply them to the
6193     register cacheing/storage mechanism.  */
6194
6195  p = rs->buf;
6196  for (i = 0; i < rsa->sizeof_g_packet; i++)
6197    {
6198      if (p[0] == 0 || p[1] == 0)
6199	/* This shouldn't happen - we adjusted sizeof_g_packet above.  */
6200	internal_error (__FILE__, __LINE__,
6201			_("unexpected end of 'g' packet reply"));
6202
6203      if (p[0] == 'x' && p[1] == 'x')
6204	regs[i] = 0;		/* 'x' */
6205      else
6206	regs[i] = fromhex (p[0]) * 16 + fromhex (p[1]);
6207      p += 2;
6208    }
6209
6210  for (i = 0; i < gdbarch_num_regs (gdbarch); i++)
6211    {
6212      struct packet_reg *r = &rsa->regs[i];
6213
6214      if (r->in_g_packet)
6215	{
6216	  if (r->offset * 2 >= strlen (rs->buf))
6217	    /* This shouldn't happen - we adjusted in_g_packet above.  */
6218	    internal_error (__FILE__, __LINE__,
6219			    _("unexpected end of 'g' packet reply"));
6220	  else if (rs->buf[r->offset * 2] == 'x')
6221	    {
6222	      gdb_assert (r->offset * 2 < strlen (rs->buf));
6223	      /* The register isn't available, mark it as such (at
6224		 the same time setting the value to zero).  */
6225	      regcache_raw_supply (regcache, r->regnum, NULL);
6226	    }
6227	  else
6228	    regcache_raw_supply (regcache, r->regnum,
6229				 regs + r->offset);
6230	}
6231    }
6232}
6233
6234static void
6235fetch_registers_using_g (struct regcache *regcache)
6236{
6237  send_g_packet ();
6238  process_g_packet (regcache);
6239}
6240
6241/* Make the remote selected traceframe match GDB's selected
6242   traceframe.  */
6243
6244static void
6245set_remote_traceframe (void)
6246{
6247  int newnum;
6248  struct remote_state *rs = get_remote_state ();
6249
6250  if (rs->remote_traceframe_number == get_traceframe_number ())
6251    return;
6252
6253  /* Avoid recursion, remote_trace_find calls us again.  */
6254  rs->remote_traceframe_number = get_traceframe_number ();
6255
6256  newnum = target_trace_find (tfind_number,
6257			      get_traceframe_number (), 0, 0, NULL);
6258
6259  /* Should not happen.  If it does, all bets are off.  */
6260  if (newnum != get_traceframe_number ())
6261    warning (_("could not set remote traceframe"));
6262}
6263
6264static void
6265remote_fetch_registers (struct target_ops *ops,
6266			struct regcache *regcache, int regnum)
6267{
6268  struct remote_arch_state *rsa = get_remote_arch_state ();
6269  int i;
6270
6271  set_remote_traceframe ();
6272  set_general_thread (inferior_ptid);
6273
6274  if (regnum >= 0)
6275    {
6276      struct packet_reg *reg = packet_reg_from_regnum (rsa, regnum);
6277
6278      gdb_assert (reg != NULL);
6279
6280      /* If this register might be in the 'g' packet, try that first -
6281	 we are likely to read more than one register.  If this is the
6282	 first 'g' packet, we might be overly optimistic about its
6283	 contents, so fall back to 'p'.  */
6284      if (reg->in_g_packet)
6285	{
6286	  fetch_registers_using_g (regcache);
6287	  if (reg->in_g_packet)
6288	    return;
6289	}
6290
6291      if (fetch_register_using_p (regcache, reg))
6292	return;
6293
6294      /* This register is not available.  */
6295      regcache_raw_supply (regcache, reg->regnum, NULL);
6296
6297      return;
6298    }
6299
6300  fetch_registers_using_g (regcache);
6301
6302  for (i = 0; i < gdbarch_num_regs (get_regcache_arch (regcache)); i++)
6303    if (!rsa->regs[i].in_g_packet)
6304      if (!fetch_register_using_p (regcache, &rsa->regs[i]))
6305	{
6306	  /* This register is not available.  */
6307	  regcache_raw_supply (regcache, i, NULL);
6308	}
6309}
6310
6311/* Prepare to store registers.  Since we may send them all (using a
6312   'G' request), we have to read out the ones we don't want to change
6313   first.  */
6314
6315static void
6316remote_prepare_to_store (struct target_ops *self, struct regcache *regcache)
6317{
6318  struct remote_arch_state *rsa = get_remote_arch_state ();
6319  int i;
6320  gdb_byte buf[MAX_REGISTER_SIZE];
6321
6322  /* Make sure the entire registers array is valid.  */
6323  switch (packet_support (PACKET_P))
6324    {
6325    case PACKET_DISABLE:
6326    case PACKET_SUPPORT_UNKNOWN:
6327      /* Make sure all the necessary registers are cached.  */
6328      for (i = 0; i < gdbarch_num_regs (get_regcache_arch (regcache)); i++)
6329	if (rsa->regs[i].in_g_packet)
6330	  regcache_raw_read (regcache, rsa->regs[i].regnum, buf);
6331      break;
6332    case PACKET_ENABLE:
6333      break;
6334    }
6335}
6336
6337/* Helper: Attempt to store REGNUM using the P packet.  Return fail IFF
6338   packet was not recognized.  */
6339
6340static int
6341store_register_using_P (const struct regcache *regcache,
6342			struct packet_reg *reg)
6343{
6344  struct gdbarch *gdbarch = get_regcache_arch (regcache);
6345  struct remote_state *rs = get_remote_state ();
6346  /* Try storing a single register.  */
6347  char *buf = rs->buf;
6348  gdb_byte regp[MAX_REGISTER_SIZE];
6349  char *p;
6350
6351  if (packet_support (PACKET_P) == PACKET_DISABLE)
6352    return 0;
6353
6354  if (reg->pnum == -1)
6355    return 0;
6356
6357  xsnprintf (buf, get_remote_packet_size (), "P%s=", phex_nz (reg->pnum, 0));
6358  p = buf + strlen (buf);
6359  regcache_raw_collect (regcache, reg->regnum, regp);
6360  bin2hex (regp, p, register_size (gdbarch, reg->regnum));
6361  putpkt (rs->buf);
6362  getpkt (&rs->buf, &rs->buf_size, 0);
6363
6364  switch (packet_ok (rs->buf, &remote_protocol_packets[PACKET_P]))
6365    {
6366    case PACKET_OK:
6367      return 1;
6368    case PACKET_ERROR:
6369      error (_("Could not write register \"%s\"; remote failure reply '%s'"),
6370	     gdbarch_register_name (gdbarch, reg->regnum), rs->buf);
6371    case PACKET_UNKNOWN:
6372      return 0;
6373    default:
6374      internal_error (__FILE__, __LINE__, _("Bad result from packet_ok"));
6375    }
6376}
6377
6378/* Store register REGNUM, or all registers if REGNUM == -1, from the
6379   contents of the register cache buffer.  FIXME: ignores errors.  */
6380
6381static void
6382store_registers_using_G (const struct regcache *regcache)
6383{
6384  struct remote_state *rs = get_remote_state ();
6385  struct remote_arch_state *rsa = get_remote_arch_state ();
6386  gdb_byte *regs;
6387  char *p;
6388
6389  /* Extract all the registers in the regcache copying them into a
6390     local buffer.  */
6391  {
6392    int i;
6393
6394    regs = alloca (rsa->sizeof_g_packet);
6395    memset (regs, 0, rsa->sizeof_g_packet);
6396    for (i = 0; i < gdbarch_num_regs (get_regcache_arch (regcache)); i++)
6397      {
6398	struct packet_reg *r = &rsa->regs[i];
6399
6400	if (r->in_g_packet)
6401	  regcache_raw_collect (regcache, r->regnum, regs + r->offset);
6402      }
6403  }
6404
6405  /* Command describes registers byte by byte,
6406     each byte encoded as two hex characters.  */
6407  p = rs->buf;
6408  *p++ = 'G';
6409  /* remote_prepare_to_store insures that rsa->sizeof_g_packet gets
6410     updated.  */
6411  bin2hex (regs, p, rsa->sizeof_g_packet);
6412  putpkt (rs->buf);
6413  getpkt (&rs->buf, &rs->buf_size, 0);
6414  if (packet_check_result (rs->buf) == PACKET_ERROR)
6415    error (_("Could not write registers; remote failure reply '%s'"),
6416	   rs->buf);
6417}
6418
6419/* Store register REGNUM, or all registers if REGNUM == -1, from the contents
6420   of the register cache buffer.  FIXME: ignores errors.  */
6421
6422static void
6423remote_store_registers (struct target_ops *ops,
6424			struct regcache *regcache, int regnum)
6425{
6426  struct remote_arch_state *rsa = get_remote_arch_state ();
6427  int i;
6428
6429  set_remote_traceframe ();
6430  set_general_thread (inferior_ptid);
6431
6432  if (regnum >= 0)
6433    {
6434      struct packet_reg *reg = packet_reg_from_regnum (rsa, regnum);
6435
6436      gdb_assert (reg != NULL);
6437
6438      /* Always prefer to store registers using the 'P' packet if
6439	 possible; we often change only a small number of registers.
6440	 Sometimes we change a larger number; we'd need help from a
6441	 higher layer to know to use 'G'.  */
6442      if (store_register_using_P (regcache, reg))
6443	return;
6444
6445      /* For now, don't complain if we have no way to write the
6446	 register.  GDB loses track of unavailable registers too
6447	 easily.  Some day, this may be an error.  We don't have
6448	 any way to read the register, either...  */
6449      if (!reg->in_g_packet)
6450	return;
6451
6452      store_registers_using_G (regcache);
6453      return;
6454    }
6455
6456  store_registers_using_G (regcache);
6457
6458  for (i = 0; i < gdbarch_num_regs (get_regcache_arch (regcache)); i++)
6459    if (!rsa->regs[i].in_g_packet)
6460      if (!store_register_using_P (regcache, &rsa->regs[i]))
6461	/* See above for why we do not issue an error here.  */
6462	continue;
6463}
6464
6465
6466/* Return the number of hex digits in num.  */
6467
6468static int
6469hexnumlen (ULONGEST num)
6470{
6471  int i;
6472
6473  for (i = 0; num != 0; i++)
6474    num >>= 4;
6475
6476  return max (i, 1);
6477}
6478
6479/* Set BUF to the minimum number of hex digits representing NUM.  */
6480
6481static int
6482hexnumstr (char *buf, ULONGEST num)
6483{
6484  int len = hexnumlen (num);
6485
6486  return hexnumnstr (buf, num, len);
6487}
6488
6489
6490/* Set BUF to the hex digits representing NUM, padded to WIDTH characters.  */
6491
6492static int
6493hexnumnstr (char *buf, ULONGEST num, int width)
6494{
6495  int i;
6496
6497  buf[width] = '\0';
6498
6499  for (i = width - 1; i >= 0; i--)
6500    {
6501      buf[i] = "0123456789abcdef"[(num & 0xf)];
6502      num >>= 4;
6503    }
6504
6505  return width;
6506}
6507
6508/* Mask all but the least significant REMOTE_ADDRESS_SIZE bits.  */
6509
6510static CORE_ADDR
6511remote_address_masked (CORE_ADDR addr)
6512{
6513  unsigned int address_size = remote_address_size;
6514
6515  /* If "remoteaddresssize" was not set, default to target address size.  */
6516  if (!address_size)
6517    address_size = gdbarch_addr_bit (target_gdbarch ());
6518
6519  if (address_size > 0
6520      && address_size < (sizeof (ULONGEST) * 8))
6521    {
6522      /* Only create a mask when that mask can safely be constructed
6523         in a ULONGEST variable.  */
6524      ULONGEST mask = 1;
6525
6526      mask = (mask << address_size) - 1;
6527      addr &= mask;
6528    }
6529  return addr;
6530}
6531
6532/* Determine whether the remote target supports binary downloading.
6533   This is accomplished by sending a no-op memory write of zero length
6534   to the target at the specified address. It does not suffice to send
6535   the whole packet, since many stubs strip the eighth bit and
6536   subsequently compute a wrong checksum, which causes real havoc with
6537   remote_write_bytes.
6538
6539   NOTE: This can still lose if the serial line is not eight-bit
6540   clean.  In cases like this, the user should clear "remote
6541   X-packet".  */
6542
6543static void
6544check_binary_download (CORE_ADDR addr)
6545{
6546  struct remote_state *rs = get_remote_state ();
6547
6548  switch (packet_support (PACKET_X))
6549    {
6550    case PACKET_DISABLE:
6551      break;
6552    case PACKET_ENABLE:
6553      break;
6554    case PACKET_SUPPORT_UNKNOWN:
6555      {
6556	char *p;
6557
6558	p = rs->buf;
6559	*p++ = 'X';
6560	p += hexnumstr (p, (ULONGEST) addr);
6561	*p++ = ',';
6562	p += hexnumstr (p, (ULONGEST) 0);
6563	*p++ = ':';
6564	*p = '\0';
6565
6566	putpkt_binary (rs->buf, (int) (p - rs->buf));
6567	getpkt (&rs->buf, &rs->buf_size, 0);
6568
6569	if (rs->buf[0] == '\0')
6570	  {
6571	    if (remote_debug)
6572	      fprintf_unfiltered (gdb_stdlog,
6573				  "binary downloading NOT "
6574				  "supported by target\n");
6575	    remote_protocol_packets[PACKET_X].support = PACKET_DISABLE;
6576	  }
6577	else
6578	  {
6579	    if (remote_debug)
6580	      fprintf_unfiltered (gdb_stdlog,
6581				  "binary downloading supported by target\n");
6582	    remote_protocol_packets[PACKET_X].support = PACKET_ENABLE;
6583	  }
6584	break;
6585      }
6586    }
6587}
6588
6589/* Write memory data directly to the remote machine.
6590   This does not inform the data cache; the data cache uses this.
6591   HEADER is the starting part of the packet.
6592   MEMADDR is the address in the remote memory space.
6593   MYADDR is the address of the buffer in our space.
6594   LEN is the number of bytes.
6595   PACKET_FORMAT should be either 'X' or 'M', and indicates if we
6596   should send data as binary ('X'), or hex-encoded ('M').
6597
6598   The function creates packet of the form
6599       <HEADER><ADDRESS>,<LENGTH>:<DATA>
6600
6601   where encoding of <DATA> is termined by PACKET_FORMAT.
6602
6603   If USE_LENGTH is 0, then the <LENGTH> field and the preceding comma
6604   are omitted.
6605
6606   Return the transferred status, error or OK (an
6607   'enum target_xfer_status' value).  Save the number of bytes
6608   transferred in *XFERED_LEN.  Only transfer a single packet.  */
6609
6610static enum target_xfer_status
6611remote_write_bytes_aux (const char *header, CORE_ADDR memaddr,
6612			const gdb_byte *myaddr, ULONGEST len,
6613			ULONGEST *xfered_len, char packet_format,
6614			int use_length)
6615{
6616  struct remote_state *rs = get_remote_state ();
6617  char *p;
6618  char *plen = NULL;
6619  int plenlen = 0;
6620  int todo;
6621  int nr_bytes;
6622  int payload_size;
6623  int payload_length;
6624  int header_length;
6625
6626  if (packet_format != 'X' && packet_format != 'M')
6627    internal_error (__FILE__, __LINE__,
6628		    _("remote_write_bytes_aux: bad packet format"));
6629
6630  if (len == 0)
6631    return TARGET_XFER_EOF;
6632
6633  payload_size = get_memory_write_packet_size ();
6634
6635  /* The packet buffer will be large enough for the payload;
6636     get_memory_packet_size ensures this.  */
6637  rs->buf[0] = '\0';
6638
6639  /* Compute the size of the actual payload by subtracting out the
6640     packet header and footer overhead: "$M<memaddr>,<len>:...#nn".  */
6641
6642  payload_size -= strlen ("$,:#NN");
6643  if (!use_length)
6644    /* The comma won't be used.  */
6645    payload_size += 1;
6646  header_length = strlen (header);
6647  payload_size -= header_length;
6648  payload_size -= hexnumlen (memaddr);
6649
6650  /* Construct the packet excluding the data: "<header><memaddr>,<len>:".  */
6651
6652  strcat (rs->buf, header);
6653  p = rs->buf + strlen (header);
6654
6655  /* Compute a best guess of the number of bytes actually transfered.  */
6656  if (packet_format == 'X')
6657    {
6658      /* Best guess at number of bytes that will fit.  */
6659      todo = min (len, payload_size);
6660      if (use_length)
6661	payload_size -= hexnumlen (todo);
6662      todo = min (todo, payload_size);
6663    }
6664  else
6665    {
6666      /* Num bytes that will fit.  */
6667      todo = min (len, payload_size / 2);
6668      if (use_length)
6669	payload_size -= hexnumlen (todo);
6670      todo = min (todo, payload_size / 2);
6671    }
6672
6673  if (todo <= 0)
6674    internal_error (__FILE__, __LINE__,
6675		    _("minimum packet size too small to write data"));
6676
6677  /* If we already need another packet, then try to align the end
6678     of this packet to a useful boundary.  */
6679  if (todo > 2 * REMOTE_ALIGN_WRITES && todo < len)
6680    todo = ((memaddr + todo) & ~(REMOTE_ALIGN_WRITES - 1)) - memaddr;
6681
6682  /* Append "<memaddr>".  */
6683  memaddr = remote_address_masked (memaddr);
6684  p += hexnumstr (p, (ULONGEST) memaddr);
6685
6686  if (use_length)
6687    {
6688      /* Append ",".  */
6689      *p++ = ',';
6690
6691      /* Append <len>.  Retain the location/size of <len>.  It may need to
6692	 be adjusted once the packet body has been created.  */
6693      plen = p;
6694      plenlen = hexnumstr (p, (ULONGEST) todo);
6695      p += plenlen;
6696    }
6697
6698  /* Append ":".  */
6699  *p++ = ':';
6700  *p = '\0';
6701
6702  /* Append the packet body.  */
6703  if (packet_format == 'X')
6704    {
6705      /* Binary mode.  Send target system values byte by byte, in
6706	 increasing byte addresses.  Only escape certain critical
6707	 characters.  */
6708      payload_length = remote_escape_output (myaddr, todo, (gdb_byte *) p,
6709					     &nr_bytes, payload_size);
6710
6711      /* If not all TODO bytes fit, then we'll need another packet.  Make
6712	 a second try to keep the end of the packet aligned.  Don't do
6713	 this if the packet is tiny.  */
6714      if (nr_bytes < todo && nr_bytes > 2 * REMOTE_ALIGN_WRITES)
6715	{
6716	  int new_nr_bytes;
6717
6718	  new_nr_bytes = (((memaddr + nr_bytes) & ~(REMOTE_ALIGN_WRITES - 1))
6719			  - memaddr);
6720	  if (new_nr_bytes != nr_bytes)
6721	    payload_length = remote_escape_output (myaddr, new_nr_bytes,
6722						   (gdb_byte *) p, &nr_bytes,
6723						   payload_size);
6724	}
6725
6726      p += payload_length;
6727      if (use_length && nr_bytes < todo)
6728	{
6729	  /* Escape chars have filled up the buffer prematurely,
6730	     and we have actually sent fewer bytes than planned.
6731	     Fix-up the length field of the packet.  Use the same
6732	     number of characters as before.  */
6733	  plen += hexnumnstr (plen, (ULONGEST) nr_bytes, plenlen);
6734	  *plen = ':';  /* overwrite \0 from hexnumnstr() */
6735	}
6736    }
6737  else
6738    {
6739      /* Normal mode: Send target system values byte by byte, in
6740	 increasing byte addresses.  Each byte is encoded as a two hex
6741	 value.  */
6742      nr_bytes = bin2hex (myaddr, p, todo);
6743      p += 2 * nr_bytes;
6744    }
6745
6746  putpkt_binary (rs->buf, (int) (p - rs->buf));
6747  getpkt (&rs->buf, &rs->buf_size, 0);
6748
6749  if (rs->buf[0] == 'E')
6750    return TARGET_XFER_E_IO;
6751
6752  /* Return NR_BYTES, not TODO, in case escape chars caused us to send
6753     fewer bytes than we'd planned.  */
6754  *xfered_len = (ULONGEST) nr_bytes;
6755  return TARGET_XFER_OK;
6756}
6757
6758/* Write memory data directly to the remote machine.
6759   This does not inform the data cache; the data cache uses this.
6760   MEMADDR is the address in the remote memory space.
6761   MYADDR is the address of the buffer in our space.
6762   LEN is the number of bytes.
6763
6764   Return the transferred status, error or OK (an
6765   'enum target_xfer_status' value).  Save the number of bytes
6766   transferred in *XFERED_LEN.  Only transfer a single packet.  */
6767
6768static enum target_xfer_status
6769remote_write_bytes (CORE_ADDR memaddr, const gdb_byte *myaddr, ULONGEST len,
6770		    ULONGEST *xfered_len)
6771{
6772  char *packet_format = 0;
6773
6774  /* Check whether the target supports binary download.  */
6775  check_binary_download (memaddr);
6776
6777  switch (packet_support (PACKET_X))
6778    {
6779    case PACKET_ENABLE:
6780      packet_format = "X";
6781      break;
6782    case PACKET_DISABLE:
6783      packet_format = "M";
6784      break;
6785    case PACKET_SUPPORT_UNKNOWN:
6786      internal_error (__FILE__, __LINE__,
6787		      _("remote_write_bytes: bad internal state"));
6788    default:
6789      internal_error (__FILE__, __LINE__, _("bad switch"));
6790    }
6791
6792  return remote_write_bytes_aux (packet_format,
6793				 memaddr, myaddr, len, xfered_len,
6794				 packet_format[0], 1);
6795}
6796
6797/* Read memory data directly from the remote machine.
6798   This does not use the data cache; the data cache uses this.
6799   MEMADDR is the address in the remote memory space.
6800   MYADDR is the address of the buffer in our space.
6801   LEN is the number of bytes.
6802
6803   Return the transferred status, error or OK (an
6804   'enum target_xfer_status' value).  Save the number of bytes
6805   transferred in *XFERED_LEN.  */
6806
6807static enum target_xfer_status
6808remote_read_bytes_1 (CORE_ADDR memaddr, gdb_byte *myaddr, ULONGEST len,
6809		     ULONGEST *xfered_len)
6810{
6811  struct remote_state *rs = get_remote_state ();
6812  int max_buf_size;		/* Max size of packet output buffer.  */
6813  char *p;
6814  int todo;
6815  int i;
6816
6817  max_buf_size = get_memory_read_packet_size ();
6818  /* The packet buffer will be large enough for the payload;
6819     get_memory_packet_size ensures this.  */
6820
6821  /* Number if bytes that will fit.  */
6822  todo = min (len, max_buf_size / 2);
6823
6824  /* Construct "m"<memaddr>","<len>".  */
6825  memaddr = remote_address_masked (memaddr);
6826  p = rs->buf;
6827  *p++ = 'm';
6828  p += hexnumstr (p, (ULONGEST) memaddr);
6829  *p++ = ',';
6830  p += hexnumstr (p, (ULONGEST) todo);
6831  *p = '\0';
6832  putpkt (rs->buf);
6833  getpkt (&rs->buf, &rs->buf_size, 0);
6834  if (rs->buf[0] == 'E'
6835      && isxdigit (rs->buf[1]) && isxdigit (rs->buf[2])
6836      && rs->buf[3] == '\0')
6837    return TARGET_XFER_E_IO;
6838  /* Reply describes memory byte by byte, each byte encoded as two hex
6839     characters.  */
6840  p = rs->buf;
6841  i = hex2bin (p, myaddr, todo);
6842  /* Return what we have.  Let higher layers handle partial reads.  */
6843  *xfered_len = (ULONGEST) i;
6844  return TARGET_XFER_OK;
6845}
6846
6847/* Using the set of read-only target sections of remote, read live
6848   read-only memory.
6849
6850   For interface/parameters/return description see target.h,
6851   to_xfer_partial.  */
6852
6853static enum target_xfer_status
6854remote_xfer_live_readonly_partial (struct target_ops *ops, gdb_byte *readbuf,
6855				   ULONGEST memaddr, ULONGEST len,
6856				   ULONGEST *xfered_len)
6857{
6858  struct target_section *secp;
6859  struct target_section_table *table;
6860
6861  secp = target_section_by_addr (ops, memaddr);
6862  if (secp != NULL
6863      && (bfd_get_section_flags (secp->the_bfd_section->owner,
6864				 secp->the_bfd_section)
6865	  & SEC_READONLY))
6866    {
6867      struct target_section *p;
6868      ULONGEST memend = memaddr + len;
6869
6870      table = target_get_section_table (ops);
6871
6872      for (p = table->sections; p < table->sections_end; p++)
6873	{
6874	  if (memaddr >= p->addr)
6875	    {
6876	      if (memend <= p->endaddr)
6877		{
6878		  /* Entire transfer is within this section.  */
6879		  return remote_read_bytes_1 (memaddr, readbuf, len,
6880					      xfered_len);
6881		}
6882	      else if (memaddr >= p->endaddr)
6883		{
6884		  /* This section ends before the transfer starts.  */
6885		  continue;
6886		}
6887	      else
6888		{
6889		  /* This section overlaps the transfer.  Just do half.  */
6890		  len = p->endaddr - memaddr;
6891		  return remote_read_bytes_1 (memaddr, readbuf, len,
6892					      xfered_len);
6893		}
6894	    }
6895	}
6896    }
6897
6898  return TARGET_XFER_EOF;
6899}
6900
6901/* Similar to remote_read_bytes_1, but it reads from the remote stub
6902   first if the requested memory is unavailable in traceframe.
6903   Otherwise, fall back to remote_read_bytes_1.  */
6904
6905static enum target_xfer_status
6906remote_read_bytes (struct target_ops *ops, CORE_ADDR memaddr,
6907		   gdb_byte *myaddr, ULONGEST len, ULONGEST *xfered_len)
6908{
6909  if (len == 0)
6910    return TARGET_XFER_EOF;
6911
6912  if (get_traceframe_number () != -1)
6913    {
6914      VEC(mem_range_s) *available;
6915
6916      /* If we fail to get the set of available memory, then the
6917	 target does not support querying traceframe info, and so we
6918	 attempt reading from the traceframe anyway (assuming the
6919	 target implements the old QTro packet then).  */
6920      if (traceframe_available_memory (&available, memaddr, len))
6921	{
6922	  struct cleanup *old_chain;
6923
6924	  old_chain = make_cleanup (VEC_cleanup(mem_range_s), &available);
6925
6926	  if (VEC_empty (mem_range_s, available)
6927	      || VEC_index (mem_range_s, available, 0)->start != memaddr)
6928	    {
6929	      enum target_xfer_status res;
6930
6931	      /* Don't read into the traceframe's available
6932		 memory.  */
6933	      if (!VEC_empty (mem_range_s, available))
6934		{
6935		  LONGEST oldlen = len;
6936
6937		  len = VEC_index (mem_range_s, available, 0)->start - memaddr;
6938		  gdb_assert (len <= oldlen);
6939		}
6940
6941	      do_cleanups (old_chain);
6942
6943	      /* This goes through the topmost target again.  */
6944	      res = remote_xfer_live_readonly_partial (ops, myaddr, memaddr,
6945						       len, xfered_len);
6946	      if (res == TARGET_XFER_OK)
6947		return TARGET_XFER_OK;
6948	      else
6949		{
6950		  /* No use trying further, we know some memory starting
6951		     at MEMADDR isn't available.  */
6952		  *xfered_len = len;
6953		  return TARGET_XFER_UNAVAILABLE;
6954		}
6955	    }
6956
6957	  /* Don't try to read more than how much is available, in
6958	     case the target implements the deprecated QTro packet to
6959	     cater for older GDBs (the target's knowledge of read-only
6960	     sections may be outdated by now).  */
6961	  len = VEC_index (mem_range_s, available, 0)->length;
6962
6963	  do_cleanups (old_chain);
6964	}
6965    }
6966
6967  return remote_read_bytes_1 (memaddr, myaddr, len, xfered_len);
6968}
6969
6970
6971
6972/* Sends a packet with content determined by the printf format string
6973   FORMAT and the remaining arguments, then gets the reply.  Returns
6974   whether the packet was a success, a failure, or unknown.  */
6975
6976static enum packet_result
6977remote_send_printf (const char *format, ...)
6978{
6979  struct remote_state *rs = get_remote_state ();
6980  int max_size = get_remote_packet_size ();
6981  va_list ap;
6982
6983  va_start (ap, format);
6984
6985  rs->buf[0] = '\0';
6986  if (vsnprintf (rs->buf, max_size, format, ap) >= max_size)
6987    internal_error (__FILE__, __LINE__, _("Too long remote packet."));
6988
6989  if (putpkt (rs->buf) < 0)
6990    error (_("Communication problem with target."));
6991
6992  rs->buf[0] = '\0';
6993  getpkt (&rs->buf, &rs->buf_size, 0);
6994
6995  return packet_check_result (rs->buf);
6996}
6997
6998static void
6999restore_remote_timeout (void *p)
7000{
7001  int value = *(int *)p;
7002
7003  remote_timeout = value;
7004}
7005
7006/* Flash writing can take quite some time.  We'll set
7007   effectively infinite timeout for flash operations.
7008   In future, we'll need to decide on a better approach.  */
7009static const int remote_flash_timeout = 1000;
7010
7011static void
7012remote_flash_erase (struct target_ops *ops,
7013                    ULONGEST address, LONGEST length)
7014{
7015  int addr_size = gdbarch_addr_bit (target_gdbarch ()) / 8;
7016  int saved_remote_timeout = remote_timeout;
7017  enum packet_result ret;
7018  struct cleanup *back_to = make_cleanup (restore_remote_timeout,
7019                                          &saved_remote_timeout);
7020
7021  remote_timeout = remote_flash_timeout;
7022
7023  ret = remote_send_printf ("vFlashErase:%s,%s",
7024			    phex (address, addr_size),
7025			    phex (length, 4));
7026  switch (ret)
7027    {
7028    case PACKET_UNKNOWN:
7029      error (_("Remote target does not support flash erase"));
7030    case PACKET_ERROR:
7031      error (_("Error erasing flash with vFlashErase packet"));
7032    default:
7033      break;
7034    }
7035
7036  do_cleanups (back_to);
7037}
7038
7039static enum target_xfer_status
7040remote_flash_write (struct target_ops *ops, ULONGEST address,
7041		    ULONGEST length, ULONGEST *xfered_len,
7042		    const gdb_byte *data)
7043{
7044  int saved_remote_timeout = remote_timeout;
7045  enum target_xfer_status ret;
7046  struct cleanup *back_to = make_cleanup (restore_remote_timeout,
7047					  &saved_remote_timeout);
7048
7049  remote_timeout = remote_flash_timeout;
7050  ret = remote_write_bytes_aux ("vFlashWrite:", address, data, length,
7051				xfered_len,'X', 0);
7052  do_cleanups (back_to);
7053
7054  return ret;
7055}
7056
7057static void
7058remote_flash_done (struct target_ops *ops)
7059{
7060  int saved_remote_timeout = remote_timeout;
7061  int ret;
7062  struct cleanup *back_to = make_cleanup (restore_remote_timeout,
7063                                          &saved_remote_timeout);
7064
7065  remote_timeout = remote_flash_timeout;
7066  ret = remote_send_printf ("vFlashDone");
7067  do_cleanups (back_to);
7068
7069  switch (ret)
7070    {
7071    case PACKET_UNKNOWN:
7072      error (_("Remote target does not support vFlashDone"));
7073    case PACKET_ERROR:
7074      error (_("Error finishing flash operation"));
7075    default:
7076      break;
7077    }
7078}
7079
7080static void
7081remote_files_info (struct target_ops *ignore)
7082{
7083  puts_filtered ("Debugging a target over a serial line.\n");
7084}
7085
7086/* Stuff for dealing with the packets which are part of this protocol.
7087   See comment at top of file for details.  */
7088
7089/* Close/unpush the remote target, and throw a TARGET_CLOSE_ERROR
7090   error to higher layers.  Called when a serial error is detected.
7091   The exception message is STRING, followed by a colon and a blank,
7092   the system error message for errno at function entry and final dot
7093   for output compatibility with throw_perror_with_name.  */
7094
7095static void
7096unpush_and_perror (const char *string)
7097{
7098  int saved_errno = errno;
7099
7100  remote_unpush_target ();
7101  throw_error (TARGET_CLOSE_ERROR, "%s: %s.", string,
7102	       safe_strerror (saved_errno));
7103}
7104
7105/* Read a single character from the remote end.  */
7106
7107static int
7108readchar (int timeout)
7109{
7110  int ch;
7111  struct remote_state *rs = get_remote_state ();
7112
7113  ch = serial_readchar (rs->remote_desc, timeout);
7114
7115  if (ch >= 0)
7116    return ch;
7117
7118  switch ((enum serial_rc) ch)
7119    {
7120    case SERIAL_EOF:
7121      remote_unpush_target ();
7122      throw_error (TARGET_CLOSE_ERROR, _("Remote connection closed"));
7123      /* no return */
7124    case SERIAL_ERROR:
7125      unpush_and_perror (_("Remote communication error.  "
7126			   "Target disconnected."));
7127      /* no return */
7128    case SERIAL_TIMEOUT:
7129      break;
7130    }
7131  return ch;
7132}
7133
7134/* Wrapper for serial_write that closes the target and throws if
7135   writing fails.  */
7136
7137static void
7138remote_serial_write (const char *str, int len)
7139{
7140  struct remote_state *rs = get_remote_state ();
7141
7142  if (serial_write (rs->remote_desc, str, len))
7143    {
7144      unpush_and_perror (_("Remote communication error.  "
7145			   "Target disconnected."));
7146    }
7147}
7148
7149/* Send the command in *BUF to the remote machine, and read the reply
7150   into *BUF.  Report an error if we get an error reply.  Resize
7151   *BUF using xrealloc if necessary to hold the result, and update
7152   *SIZEOF_BUF.  */
7153
7154static void
7155remote_send (char **buf,
7156	     long *sizeof_buf)
7157{
7158  putpkt (*buf);
7159  getpkt (buf, sizeof_buf, 0);
7160
7161  if ((*buf)[0] == 'E')
7162    error (_("Remote failure reply: %s"), *buf);
7163}
7164
7165/* Return a pointer to an xmalloc'ed string representing an escaped
7166   version of BUF, of len N.  E.g. \n is converted to \\n, \t to \\t,
7167   etc.  The caller is responsible for releasing the returned
7168   memory.  */
7169
7170static char *
7171escape_buffer (const char *buf, int n)
7172{
7173  struct cleanup *old_chain;
7174  struct ui_file *stb;
7175  char *str;
7176
7177  stb = mem_fileopen ();
7178  old_chain = make_cleanup_ui_file_delete (stb);
7179
7180  fputstrn_unfiltered (buf, n, '\\', stb);
7181  str = ui_file_xstrdup (stb, NULL);
7182  do_cleanups (old_chain);
7183  return str;
7184}
7185
7186/* Display a null-terminated packet on stdout, for debugging, using C
7187   string notation.  */
7188
7189static void
7190print_packet (const char *buf)
7191{
7192  puts_filtered ("\"");
7193  fputstr_filtered (buf, '"', gdb_stdout);
7194  puts_filtered ("\"");
7195}
7196
7197int
7198putpkt (const char *buf)
7199{
7200  return putpkt_binary (buf, strlen (buf));
7201}
7202
7203/* Send a packet to the remote machine, with error checking.  The data
7204   of the packet is in BUF.  The string in BUF can be at most
7205   get_remote_packet_size () - 5 to account for the $, # and checksum,
7206   and for a possible /0 if we are debugging (remote_debug) and want
7207   to print the sent packet as a string.  */
7208
7209static int
7210putpkt_binary (const char *buf, int cnt)
7211{
7212  struct remote_state *rs = get_remote_state ();
7213  int i;
7214  unsigned char csum = 0;
7215  char *buf2 = alloca (cnt + 6);
7216
7217  int ch;
7218  int tcount = 0;
7219  char *p;
7220  char *message;
7221
7222  /* Catch cases like trying to read memory or listing threads while
7223     we're waiting for a stop reply.  The remote server wouldn't be
7224     ready to handle this request, so we'd hang and timeout.  We don't
7225     have to worry about this in synchronous mode, because in that
7226     case it's not possible to issue a command while the target is
7227     running.  This is not a problem in non-stop mode, because in that
7228     case, the stub is always ready to process serial input.  */
7229  if (!non_stop && target_is_async_p () && rs->waiting_for_stop_reply)
7230    {
7231      error (_("Cannot execute this command while the target is running.\n"
7232	       "Use the \"interrupt\" command to stop the target\n"
7233	       "and then try again."));
7234    }
7235
7236  /* We're sending out a new packet.  Make sure we don't look at a
7237     stale cached response.  */
7238  rs->cached_wait_status = 0;
7239
7240  /* Copy the packet into buffer BUF2, encapsulating it
7241     and giving it a checksum.  */
7242
7243  p = buf2;
7244  *p++ = '$';
7245
7246  for (i = 0; i < cnt; i++)
7247    {
7248      csum += buf[i];
7249      *p++ = buf[i];
7250    }
7251  *p++ = '#';
7252  *p++ = tohex ((csum >> 4) & 0xf);
7253  *p++ = tohex (csum & 0xf);
7254
7255  /* Send it over and over until we get a positive ack.  */
7256
7257  while (1)
7258    {
7259      int started_error_output = 0;
7260
7261      if (remote_debug)
7262	{
7263	  struct cleanup *old_chain;
7264	  char *str;
7265
7266	  *p = '\0';
7267	  str = escape_buffer (buf2, p - buf2);
7268	  old_chain = make_cleanup (xfree, str);
7269	  fprintf_unfiltered (gdb_stdlog, "Sending packet: %s...", str);
7270	  gdb_flush (gdb_stdlog);
7271	  do_cleanups (old_chain);
7272	}
7273      remote_serial_write (buf2, p - buf2);
7274
7275      /* If this is a no acks version of the remote protocol, send the
7276	 packet and move on.  */
7277      if (rs->noack_mode)
7278        break;
7279
7280      /* Read until either a timeout occurs (-2) or '+' is read.
7281	 Handle any notification that arrives in the mean time.  */
7282      while (1)
7283	{
7284	  ch = readchar (remote_timeout);
7285
7286	  if (remote_debug)
7287	    {
7288	      switch (ch)
7289		{
7290		case '+':
7291		case '-':
7292		case SERIAL_TIMEOUT:
7293		case '$':
7294		case '%':
7295		  if (started_error_output)
7296		    {
7297		      putchar_unfiltered ('\n');
7298		      started_error_output = 0;
7299		    }
7300		}
7301	    }
7302
7303	  switch (ch)
7304	    {
7305	    case '+':
7306	      if (remote_debug)
7307		fprintf_unfiltered (gdb_stdlog, "Ack\n");
7308	      return 1;
7309	    case '-':
7310	      if (remote_debug)
7311		fprintf_unfiltered (gdb_stdlog, "Nak\n");
7312	      /* FALLTHROUGH */
7313	    case SERIAL_TIMEOUT:
7314	      tcount++;
7315	      if (tcount > 3)
7316		return 0;
7317	      break;		/* Retransmit buffer.  */
7318	    case '$':
7319	      {
7320	        if (remote_debug)
7321		  fprintf_unfiltered (gdb_stdlog,
7322				      "Packet instead of Ack, ignoring it\n");
7323		/* It's probably an old response sent because an ACK
7324		   was lost.  Gobble up the packet and ack it so it
7325		   doesn't get retransmitted when we resend this
7326		   packet.  */
7327		skip_frame ();
7328		remote_serial_write ("+", 1);
7329		continue;	/* Now, go look for +.  */
7330	      }
7331
7332	    case '%':
7333	      {
7334		int val;
7335
7336		/* If we got a notification, handle it, and go back to looking
7337		   for an ack.  */
7338		/* We've found the start of a notification.  Now
7339		   collect the data.  */
7340		val = read_frame (&rs->buf, &rs->buf_size);
7341		if (val >= 0)
7342		  {
7343		    if (remote_debug)
7344		      {
7345			struct cleanup *old_chain;
7346			char *str;
7347
7348			str = escape_buffer (rs->buf, val);
7349			old_chain = make_cleanup (xfree, str);
7350			fprintf_unfiltered (gdb_stdlog,
7351					    "  Notification received: %s\n",
7352					    str);
7353			do_cleanups (old_chain);
7354		      }
7355		    handle_notification (rs->notif_state, rs->buf);
7356		    /* We're in sync now, rewait for the ack.  */
7357		    tcount = 0;
7358		  }
7359		else
7360		  {
7361		    if (remote_debug)
7362		      {
7363			if (!started_error_output)
7364			  {
7365			    started_error_output = 1;
7366			    fprintf_unfiltered (gdb_stdlog, "putpkt: Junk: ");
7367			  }
7368			fputc_unfiltered (ch & 0177, gdb_stdlog);
7369			fprintf_unfiltered (gdb_stdlog, "%s", rs->buf);
7370		      }
7371		  }
7372		continue;
7373	      }
7374	      /* fall-through */
7375	    default:
7376	      if (remote_debug)
7377		{
7378		  if (!started_error_output)
7379		    {
7380		      started_error_output = 1;
7381		      fprintf_unfiltered (gdb_stdlog, "putpkt: Junk: ");
7382		    }
7383		  fputc_unfiltered (ch & 0177, gdb_stdlog);
7384		}
7385	      continue;
7386	    }
7387	  break;		/* Here to retransmit.  */
7388	}
7389
7390#if 0
7391      /* This is wrong.  If doing a long backtrace, the user should be
7392         able to get out next time we call QUIT, without anything as
7393         violent as interrupt_query.  If we want to provide a way out of
7394         here without getting to the next QUIT, it should be based on
7395         hitting ^C twice as in remote_wait.  */
7396      if (quit_flag)
7397	{
7398	  quit_flag = 0;
7399	  interrupt_query ();
7400	}
7401#endif
7402    }
7403  return 0;
7404}
7405
7406/* Come here after finding the start of a frame when we expected an
7407   ack.  Do our best to discard the rest of this packet.  */
7408
7409static void
7410skip_frame (void)
7411{
7412  int c;
7413
7414  while (1)
7415    {
7416      c = readchar (remote_timeout);
7417      switch (c)
7418	{
7419	case SERIAL_TIMEOUT:
7420	  /* Nothing we can do.  */
7421	  return;
7422	case '#':
7423	  /* Discard the two bytes of checksum and stop.  */
7424	  c = readchar (remote_timeout);
7425	  if (c >= 0)
7426	    c = readchar (remote_timeout);
7427
7428	  return;
7429	case '*':		/* Run length encoding.  */
7430	  /* Discard the repeat count.  */
7431	  c = readchar (remote_timeout);
7432	  if (c < 0)
7433	    return;
7434	  break;
7435	default:
7436	  /* A regular character.  */
7437	  break;
7438	}
7439    }
7440}
7441
7442/* Come here after finding the start of the frame.  Collect the rest
7443   into *BUF, verifying the checksum, length, and handling run-length
7444   compression.  NUL terminate the buffer.  If there is not enough room,
7445   expand *BUF using xrealloc.
7446
7447   Returns -1 on error, number of characters in buffer (ignoring the
7448   trailing NULL) on success. (could be extended to return one of the
7449   SERIAL status indications).  */
7450
7451static long
7452read_frame (char **buf_p,
7453	    long *sizeof_buf)
7454{
7455  unsigned char csum;
7456  long bc;
7457  int c;
7458  char *buf = *buf_p;
7459  struct remote_state *rs = get_remote_state ();
7460
7461  csum = 0;
7462  bc = 0;
7463
7464  while (1)
7465    {
7466      c = readchar (remote_timeout);
7467      switch (c)
7468	{
7469	case SERIAL_TIMEOUT:
7470	  if (remote_debug)
7471	    fputs_filtered ("Timeout in mid-packet, retrying\n", gdb_stdlog);
7472	  return -1;
7473	case '$':
7474	  if (remote_debug)
7475	    fputs_filtered ("Saw new packet start in middle of old one\n",
7476			    gdb_stdlog);
7477	  return -1;		/* Start a new packet, count retries.  */
7478	case '#':
7479	  {
7480	    unsigned char pktcsum;
7481	    int check_0 = 0;
7482	    int check_1 = 0;
7483
7484	    buf[bc] = '\0';
7485
7486	    check_0 = readchar (remote_timeout);
7487	    if (check_0 >= 0)
7488	      check_1 = readchar (remote_timeout);
7489
7490	    if (check_0 == SERIAL_TIMEOUT || check_1 == SERIAL_TIMEOUT)
7491	      {
7492		if (remote_debug)
7493		  fputs_filtered ("Timeout in checksum, retrying\n",
7494				  gdb_stdlog);
7495		return -1;
7496	      }
7497	    else if (check_0 < 0 || check_1 < 0)
7498	      {
7499		if (remote_debug)
7500		  fputs_filtered ("Communication error in checksum\n",
7501				  gdb_stdlog);
7502		return -1;
7503	      }
7504
7505	    /* Don't recompute the checksum; with no ack packets we
7506	       don't have any way to indicate a packet retransmission
7507	       is necessary.  */
7508	    if (rs->noack_mode)
7509	      return bc;
7510
7511	    pktcsum = (fromhex (check_0) << 4) | fromhex (check_1);
7512	    if (csum == pktcsum)
7513              return bc;
7514
7515	    if (remote_debug)
7516	      {
7517		struct cleanup *old_chain;
7518		char *str;
7519
7520		str = escape_buffer (buf, bc);
7521		old_chain = make_cleanup (xfree, str);
7522		fprintf_unfiltered (gdb_stdlog,
7523				    "Bad checksum, sentsum=0x%x, "
7524				    "csum=0x%x, buf=%s\n",
7525				    pktcsum, csum, str);
7526		do_cleanups (old_chain);
7527	      }
7528	    /* Number of characters in buffer ignoring trailing
7529               NULL.  */
7530	    return -1;
7531	  }
7532	case '*':		/* Run length encoding.  */
7533          {
7534	    int repeat;
7535
7536 	    csum += c;
7537	    c = readchar (remote_timeout);
7538	    csum += c;
7539	    repeat = c - ' ' + 3;	/* Compute repeat count.  */
7540
7541	    /* The character before ``*'' is repeated.  */
7542
7543	    if (repeat > 0 && repeat <= 255 && bc > 0)
7544	      {
7545		if (bc + repeat - 1 >= *sizeof_buf - 1)
7546		  {
7547		    /* Make some more room in the buffer.  */
7548		    *sizeof_buf += repeat;
7549		    *buf_p = xrealloc (*buf_p, *sizeof_buf);
7550		    buf = *buf_p;
7551		  }
7552
7553		memset (&buf[bc], buf[bc - 1], repeat);
7554		bc += repeat;
7555		continue;
7556	      }
7557
7558	    buf[bc] = '\0';
7559	    printf_filtered (_("Invalid run length encoding: %s\n"), buf);
7560	    return -1;
7561	  }
7562	default:
7563	  if (bc >= *sizeof_buf - 1)
7564	    {
7565	      /* Make some more room in the buffer.  */
7566	      *sizeof_buf *= 2;
7567	      *buf_p = xrealloc (*buf_p, *sizeof_buf);
7568	      buf = *buf_p;
7569	    }
7570
7571	  buf[bc++] = c;
7572	  csum += c;
7573	  continue;
7574	}
7575    }
7576}
7577
7578/* Read a packet from the remote machine, with error checking, and
7579   store it in *BUF.  Resize *BUF using xrealloc if necessary to hold
7580   the result, and update *SIZEOF_BUF.  If FOREVER, wait forever
7581   rather than timing out; this is used (in synchronous mode) to wait
7582   for a target that is is executing user code to stop.  */
7583/* FIXME: ezannoni 2000-02-01 this wrapper is necessary so that we
7584   don't have to change all the calls to getpkt to deal with the
7585   return value, because at the moment I don't know what the right
7586   thing to do it for those.  */
7587void
7588getpkt (char **buf,
7589	long *sizeof_buf,
7590	int forever)
7591{
7592  int timed_out;
7593
7594  timed_out = getpkt_sane (buf, sizeof_buf, forever);
7595}
7596
7597
7598/* Read a packet from the remote machine, with error checking, and
7599   store it in *BUF.  Resize *BUF using xrealloc if necessary to hold
7600   the result, and update *SIZEOF_BUF.  If FOREVER, wait forever
7601   rather than timing out; this is used (in synchronous mode) to wait
7602   for a target that is is executing user code to stop.  If FOREVER ==
7603   0, this function is allowed to time out gracefully and return an
7604   indication of this to the caller.  Otherwise return the number of
7605   bytes read.  If EXPECTING_NOTIF, consider receiving a notification
7606   enough reason to return to the caller.  *IS_NOTIF is an output
7607   boolean that indicates whether *BUF holds a notification or not
7608   (a regular packet).  */
7609
7610static int
7611getpkt_or_notif_sane_1 (char **buf, long *sizeof_buf, int forever,
7612			int expecting_notif, int *is_notif)
7613{
7614  struct remote_state *rs = get_remote_state ();
7615  int c;
7616  int tries;
7617  int timeout;
7618  int val = -1;
7619
7620  /* We're reading a new response.  Make sure we don't look at a
7621     previously cached response.  */
7622  rs->cached_wait_status = 0;
7623
7624  strcpy (*buf, "timeout");
7625
7626  if (forever)
7627    timeout = watchdog > 0 ? watchdog : -1;
7628  else if (expecting_notif)
7629    timeout = 0; /* There should already be a char in the buffer.  If
7630		    not, bail out.  */
7631  else
7632    timeout = remote_timeout;
7633
7634#define MAX_TRIES 3
7635
7636  /* Process any number of notifications, and then return when
7637     we get a packet.  */
7638  for (;;)
7639    {
7640      /* If we get a timeout or bad checksum, retry up to MAX_TRIES
7641	 times.  */
7642      for (tries = 1; tries <= MAX_TRIES; tries++)
7643	{
7644	  /* This can loop forever if the remote side sends us
7645	     characters continuously, but if it pauses, we'll get
7646	     SERIAL_TIMEOUT from readchar because of timeout.  Then
7647	     we'll count that as a retry.
7648
7649	     Note that even when forever is set, we will only wait
7650	     forever prior to the start of a packet.  After that, we
7651	     expect characters to arrive at a brisk pace.  They should
7652	     show up within remote_timeout intervals.  */
7653	  do
7654	    c = readchar (timeout);
7655	  while (c != SERIAL_TIMEOUT && c != '$' && c != '%');
7656
7657	  if (c == SERIAL_TIMEOUT)
7658	    {
7659	      if (expecting_notif)
7660		return -1; /* Don't complain, it's normal to not get
7661			      anything in this case.  */
7662
7663	      if (forever)	/* Watchdog went off?  Kill the target.  */
7664		{
7665		  QUIT;
7666		  remote_unpush_target ();
7667		  throw_error (TARGET_CLOSE_ERROR,
7668			       _("Watchdog timeout has expired.  "
7669				 "Target detached."));
7670		}
7671	      if (remote_debug)
7672		fputs_filtered ("Timed out.\n", gdb_stdlog);
7673	    }
7674	  else
7675	    {
7676	      /* We've found the start of a packet or notification.
7677		 Now collect the data.  */
7678	      val = read_frame (buf, sizeof_buf);
7679	      if (val >= 0)
7680		break;
7681	    }
7682
7683	  remote_serial_write ("-", 1);
7684	}
7685
7686      if (tries > MAX_TRIES)
7687	{
7688	  /* We have tried hard enough, and just can't receive the
7689	     packet/notification.  Give up.  */
7690	  printf_unfiltered (_("Ignoring packet error, continuing...\n"));
7691
7692	  /* Skip the ack char if we're in no-ack mode.  */
7693	  if (!rs->noack_mode)
7694	    remote_serial_write ("+", 1);
7695	  return -1;
7696	}
7697
7698      /* If we got an ordinary packet, return that to our caller.  */
7699      if (c == '$')
7700	{
7701	  if (remote_debug)
7702	    {
7703	     struct cleanup *old_chain;
7704	     char *str;
7705
7706	     str = escape_buffer (*buf, val);
7707	     old_chain = make_cleanup (xfree, str);
7708	     fprintf_unfiltered (gdb_stdlog, "Packet received: %s\n", str);
7709	     do_cleanups (old_chain);
7710	    }
7711
7712	  /* Skip the ack char if we're in no-ack mode.  */
7713	  if (!rs->noack_mode)
7714	    remote_serial_write ("+", 1);
7715	  if (is_notif != NULL)
7716	    *is_notif = 0;
7717	  return val;
7718	}
7719
7720       /* If we got a notification, handle it, and go back to looking
7721	 for a packet.  */
7722      else
7723	{
7724	  gdb_assert (c == '%');
7725
7726	  if (remote_debug)
7727	    {
7728	      struct cleanup *old_chain;
7729	      char *str;
7730
7731	      str = escape_buffer (*buf, val);
7732	      old_chain = make_cleanup (xfree, str);
7733	      fprintf_unfiltered (gdb_stdlog,
7734				  "  Notification received: %s\n",
7735				  str);
7736	      do_cleanups (old_chain);
7737	    }
7738	  if (is_notif != NULL)
7739	    *is_notif = 1;
7740
7741	  handle_notification (rs->notif_state, *buf);
7742
7743	  /* Notifications require no acknowledgement.  */
7744
7745	  if (expecting_notif)
7746	    return val;
7747	}
7748    }
7749}
7750
7751static int
7752getpkt_sane (char **buf, long *sizeof_buf, int forever)
7753{
7754  return getpkt_or_notif_sane_1 (buf, sizeof_buf, forever, 0, NULL);
7755}
7756
7757static int
7758getpkt_or_notif_sane (char **buf, long *sizeof_buf, int forever,
7759		      int *is_notif)
7760{
7761  return getpkt_or_notif_sane_1 (buf, sizeof_buf, forever, 1,
7762				 is_notif);
7763}
7764
7765
7766static void
7767remote_kill (struct target_ops *ops)
7768{
7769  volatile struct gdb_exception ex;
7770
7771  /* Catch errors so the user can quit from gdb even when we
7772     aren't on speaking terms with the remote system.  */
7773  TRY_CATCH (ex, RETURN_MASK_ERROR)
7774    {
7775      putpkt ("k");
7776    }
7777  if (ex.reason < 0)
7778    {
7779      if (ex.error == TARGET_CLOSE_ERROR)
7780	{
7781	  /* If we got an (EOF) error that caused the target
7782	     to go away, then we're done, that's what we wanted.
7783	     "k" is susceptible to cause a premature EOF, given
7784	     that the remote server isn't actually required to
7785	     reply to "k", and it can happen that it doesn't
7786	     even get to reply ACK to the "k".  */
7787	  return;
7788	}
7789
7790	/* Otherwise, something went wrong.  We didn't actually kill
7791	   the target.  Just propagate the exception, and let the
7792	   user or higher layers decide what to do.  */
7793	throw_exception (ex);
7794    }
7795
7796  /* We've killed the remote end, we get to mourn it.  Since this is
7797     target remote, single-process, mourning the inferior also
7798     unpushes remote_ops.  */
7799  target_mourn_inferior ();
7800}
7801
7802static int
7803remote_vkill (int pid, struct remote_state *rs)
7804{
7805  if (packet_support (PACKET_vKill) == PACKET_DISABLE)
7806    return -1;
7807
7808  /* Tell the remote target to detach.  */
7809  xsnprintf (rs->buf, get_remote_packet_size (), "vKill;%x", pid);
7810  putpkt (rs->buf);
7811  getpkt (&rs->buf, &rs->buf_size, 0);
7812
7813  switch (packet_ok (rs->buf,
7814		     &remote_protocol_packets[PACKET_vKill]))
7815    {
7816    case PACKET_OK:
7817      return 0;
7818    case PACKET_ERROR:
7819      return 1;
7820    case PACKET_UNKNOWN:
7821      return -1;
7822    default:
7823      internal_error (__FILE__, __LINE__, _("Bad result from packet_ok"));
7824    }
7825}
7826
7827static void
7828extended_remote_kill (struct target_ops *ops)
7829{
7830  int res;
7831  int pid = ptid_get_pid (inferior_ptid);
7832  struct remote_state *rs = get_remote_state ();
7833
7834  res = remote_vkill (pid, rs);
7835  if (res == -1 && !(rs->extended && remote_multi_process_p (rs)))
7836    {
7837      /* Don't try 'k' on a multi-process aware stub -- it has no way
7838	 to specify the pid.  */
7839
7840      putpkt ("k");
7841#if 0
7842      getpkt (&rs->buf, &rs->buf_size, 0);
7843      if (rs->buf[0] != 'O' || rs->buf[0] != 'K')
7844	res = 1;
7845#else
7846      /* Don't wait for it to die.  I'm not really sure it matters whether
7847	 we do or not.  For the existing stubs, kill is a noop.  */
7848      res = 0;
7849#endif
7850    }
7851
7852  if (res != 0)
7853    error (_("Can't kill process"));
7854
7855  target_mourn_inferior ();
7856}
7857
7858static void
7859remote_mourn (struct target_ops *ops)
7860{
7861  remote_mourn_1 (ops);
7862}
7863
7864/* Worker function for remote_mourn.  */
7865static void
7866remote_mourn_1 (struct target_ops *target)
7867{
7868  unpush_target (target);
7869
7870  /* remote_close takes care of doing most of the clean up.  */
7871  generic_mourn_inferior ();
7872}
7873
7874static void
7875extended_remote_mourn_1 (struct target_ops *target)
7876{
7877  struct remote_state *rs = get_remote_state ();
7878
7879  /* In case we got here due to an error, but we're going to stay
7880     connected.  */
7881  rs->waiting_for_stop_reply = 0;
7882
7883  /* If the current general thread belonged to the process we just
7884     detached from or has exited, the remote side current general
7885     thread becomes undefined.  Considering a case like this:
7886
7887     - We just got here due to a detach.
7888     - The process that we're detaching from happens to immediately
7889       report a global breakpoint being hit in non-stop mode, in the
7890       same thread we had selected before.
7891     - GDB attaches to this process again.
7892     - This event happens to be the next event we handle.
7893
7894     GDB would consider that the current general thread didn't need to
7895     be set on the stub side (with Hg), since for all it knew,
7896     GENERAL_THREAD hadn't changed.
7897
7898     Notice that although in all-stop mode, the remote server always
7899     sets the current thread to the thread reporting the stop event,
7900     that doesn't happen in non-stop mode; in non-stop, the stub *must
7901     not* change the current thread when reporting a breakpoint hit,
7902     due to the decoupling of event reporting and event handling.
7903
7904     To keep things simple, we always invalidate our notion of the
7905     current thread.  */
7906  record_currthread (rs, minus_one_ptid);
7907
7908  /* Unlike "target remote", we do not want to unpush the target; then
7909     the next time the user says "run", we won't be connected.  */
7910
7911  /* Call common code to mark the inferior as not running.	*/
7912  generic_mourn_inferior ();
7913
7914  if (!have_inferiors ())
7915    {
7916      if (!remote_multi_process_p (rs))
7917	{
7918	  /* Check whether the target is running now - some remote stubs
7919	     automatically restart after kill.	*/
7920	  putpkt ("?");
7921	  getpkt (&rs->buf, &rs->buf_size, 0);
7922
7923	  if (rs->buf[0] == 'S' || rs->buf[0] == 'T')
7924	    {
7925	      /* Assume that the target has been restarted.  Set
7926		 inferior_ptid so that bits of core GDB realizes
7927		 there's something here, e.g., so that the user can
7928		 say "kill" again.  */
7929	      inferior_ptid = magic_null_ptid;
7930	    }
7931	}
7932    }
7933}
7934
7935static void
7936extended_remote_mourn (struct target_ops *ops)
7937{
7938  extended_remote_mourn_1 (ops);
7939}
7940
7941static int
7942extended_remote_supports_disable_randomization (struct target_ops *self)
7943{
7944  return packet_support (PACKET_QDisableRandomization) == PACKET_ENABLE;
7945}
7946
7947static void
7948extended_remote_disable_randomization (int val)
7949{
7950  struct remote_state *rs = get_remote_state ();
7951  char *reply;
7952
7953  xsnprintf (rs->buf, get_remote_packet_size (), "QDisableRandomization:%x",
7954	     val);
7955  putpkt (rs->buf);
7956  reply = remote_get_noisy_reply (&target_buf, &target_buf_size);
7957  if (*reply == '\0')
7958    error (_("Target does not support QDisableRandomization."));
7959  if (strcmp (reply, "OK") != 0)
7960    error (_("Bogus QDisableRandomization reply from target: %s"), reply);
7961}
7962
7963static int
7964extended_remote_run (char *args)
7965{
7966  struct remote_state *rs = get_remote_state ();
7967  int len;
7968
7969  /* If the user has disabled vRun support, or we have detected that
7970     support is not available, do not try it.  */
7971  if (packet_support (PACKET_vRun) == PACKET_DISABLE)
7972    return -1;
7973
7974  strcpy (rs->buf, "vRun;");
7975  len = strlen (rs->buf);
7976
7977  if (strlen (remote_exec_file) * 2 + len >= get_remote_packet_size ())
7978    error (_("Remote file name too long for run packet"));
7979  len += 2 * bin2hex ((gdb_byte *) remote_exec_file, rs->buf + len,
7980		      strlen (remote_exec_file));
7981
7982  gdb_assert (args != NULL);
7983  if (*args)
7984    {
7985      struct cleanup *back_to;
7986      int i;
7987      char **argv;
7988
7989      argv = gdb_buildargv (args);
7990      back_to = make_cleanup_freeargv (argv);
7991      for (i = 0; argv[i] != NULL; i++)
7992	{
7993	  if (strlen (argv[i]) * 2 + 1 + len >= get_remote_packet_size ())
7994	    error (_("Argument list too long for run packet"));
7995	  rs->buf[len++] = ';';
7996	  len += 2 * bin2hex ((gdb_byte *) argv[i], rs->buf + len,
7997			      strlen (argv[i]));
7998	}
7999      do_cleanups (back_to);
8000    }
8001
8002  rs->buf[len++] = '\0';
8003
8004  putpkt (rs->buf);
8005  getpkt (&rs->buf, &rs->buf_size, 0);
8006
8007  switch (packet_ok (rs->buf, &remote_protocol_packets[PACKET_vRun]))
8008    {
8009    case PACKET_OK:
8010      /* We have a wait response.  All is well.  */
8011      return 0;
8012    case PACKET_UNKNOWN:
8013      return -1;
8014    case PACKET_ERROR:
8015      if (remote_exec_file[0] == '\0')
8016	error (_("Running the default executable on the remote target failed; "
8017		 "try \"set remote exec-file\"?"));
8018      else
8019	error (_("Running \"%s\" on the remote target failed"),
8020	       remote_exec_file);
8021    default:
8022      gdb_assert_not_reached (_("bad switch"));
8023    }
8024}
8025
8026/* In the extended protocol we want to be able to do things like
8027   "run" and have them basically work as expected.  So we need
8028   a special create_inferior function.  We support changing the
8029   executable file and the command line arguments, but not the
8030   environment.  */
8031
8032static void
8033extended_remote_create_inferior (struct target_ops *ops,
8034				 char *exec_file, char *args,
8035				 char **env, int from_tty)
8036{
8037  int run_worked;
8038  char *stop_reply;
8039  struct remote_state *rs = get_remote_state ();
8040
8041  /* If running asynchronously, register the target file descriptor
8042     with the event loop.  */
8043  if (target_can_async_p ())
8044    target_async (inferior_event_handler, 0);
8045
8046  /* Disable address space randomization if requested (and supported).  */
8047  if (extended_remote_supports_disable_randomization (ops))
8048    extended_remote_disable_randomization (disable_randomization);
8049
8050  /* Now restart the remote server.  */
8051  run_worked = extended_remote_run (args) != -1;
8052  if (!run_worked)
8053    {
8054      /* vRun was not supported.  Fail if we need it to do what the
8055	 user requested.  */
8056      if (remote_exec_file[0])
8057	error (_("Remote target does not support \"set remote exec-file\""));
8058      if (args[0])
8059	error (_("Remote target does not support \"set args\" or run <ARGS>"));
8060
8061      /* Fall back to "R".  */
8062      extended_remote_restart ();
8063    }
8064
8065  if (!have_inferiors ())
8066    {
8067      /* Clean up from the last time we ran, before we mark the target
8068	 running again.  This will mark breakpoints uninserted, and
8069	 get_offsets may insert breakpoints.  */
8070      init_thread_list ();
8071      init_wait_for_inferior ();
8072    }
8073
8074  /* vRun's success return is a stop reply.  */
8075  stop_reply = run_worked ? rs->buf : NULL;
8076  add_current_inferior_and_thread (stop_reply);
8077
8078  /* Get updated offsets, if the stub uses qOffsets.  */
8079  get_offsets ();
8080}
8081
8082
8083/* Given a location's target info BP_TGT and the packet buffer BUF,  output
8084   the list of conditions (in agent expression bytecode format), if any, the
8085   target needs to evaluate.  The output is placed into the packet buffer
8086   started from BUF and ended at BUF_END.  */
8087
8088static int
8089remote_add_target_side_condition (struct gdbarch *gdbarch,
8090				  struct bp_target_info *bp_tgt, char *buf,
8091				  char *buf_end)
8092{
8093  struct agent_expr *aexpr = NULL;
8094  int i, ix;
8095  char *pkt;
8096  char *buf_start = buf;
8097
8098  if (VEC_empty (agent_expr_p, bp_tgt->conditions))
8099    return 0;
8100
8101  buf += strlen (buf);
8102  xsnprintf (buf, buf_end - buf, "%s", ";");
8103  buf++;
8104
8105  /* Send conditions to the target and free the vector.  */
8106  for (ix = 0;
8107       VEC_iterate (agent_expr_p, bp_tgt->conditions, ix, aexpr);
8108       ix++)
8109    {
8110      xsnprintf (buf, buf_end - buf, "X%x,", aexpr->len);
8111      buf += strlen (buf);
8112      for (i = 0; i < aexpr->len; ++i)
8113	buf = pack_hex_byte (buf, aexpr->buf[i]);
8114      *buf = '\0';
8115    }
8116  return 0;
8117}
8118
8119static void
8120remote_add_target_side_commands (struct gdbarch *gdbarch,
8121				 struct bp_target_info *bp_tgt, char *buf)
8122{
8123  struct agent_expr *aexpr = NULL;
8124  int i, ix;
8125
8126  if (VEC_empty (agent_expr_p, bp_tgt->tcommands))
8127    return;
8128
8129  buf += strlen (buf);
8130
8131  sprintf (buf, ";cmds:%x,", bp_tgt->persist);
8132  buf += strlen (buf);
8133
8134  /* Concatenate all the agent expressions that are commands into the
8135     cmds parameter.  */
8136  for (ix = 0;
8137       VEC_iterate (agent_expr_p, bp_tgt->tcommands, ix, aexpr);
8138       ix++)
8139    {
8140      sprintf (buf, "X%x,", aexpr->len);
8141      buf += strlen (buf);
8142      for (i = 0; i < aexpr->len; ++i)
8143	buf = pack_hex_byte (buf, aexpr->buf[i]);
8144      *buf = '\0';
8145    }
8146}
8147
8148/* Insert a breakpoint.  On targets that have software breakpoint
8149   support, we ask the remote target to do the work; on targets
8150   which don't, we insert a traditional memory breakpoint.  */
8151
8152static int
8153remote_insert_breakpoint (struct target_ops *ops,
8154			  struct gdbarch *gdbarch,
8155			  struct bp_target_info *bp_tgt)
8156{
8157  /* Try the "Z" s/w breakpoint packet if it is not already disabled.
8158     If it succeeds, then set the support to PACKET_ENABLE.  If it
8159     fails, and the user has explicitly requested the Z support then
8160     report an error, otherwise, mark it disabled and go on.  */
8161
8162  if (packet_support (PACKET_Z0) != PACKET_DISABLE)
8163    {
8164      CORE_ADDR addr = bp_tgt->reqstd_address;
8165      struct remote_state *rs;
8166      char *p, *endbuf;
8167      int bpsize;
8168      struct condition_list *cond = NULL;
8169
8170      /* Make sure the remote is pointing at the right process, if
8171	 necessary.  */
8172      if (!gdbarch_has_global_breakpoints (target_gdbarch ()))
8173	set_general_process ();
8174
8175      gdbarch_remote_breakpoint_from_pc (gdbarch, &addr, &bpsize);
8176
8177      rs = get_remote_state ();
8178      p = rs->buf;
8179      endbuf = rs->buf + get_remote_packet_size ();
8180
8181      *(p++) = 'Z';
8182      *(p++) = '0';
8183      *(p++) = ',';
8184      addr = (ULONGEST) remote_address_masked (addr);
8185      p += hexnumstr (p, addr);
8186      xsnprintf (p, endbuf - p, ",%d", bpsize);
8187
8188      if (remote_supports_cond_breakpoints (ops))
8189	remote_add_target_side_condition (gdbarch, bp_tgt, p, endbuf);
8190
8191      if (remote_can_run_breakpoint_commands (ops))
8192	remote_add_target_side_commands (gdbarch, bp_tgt, p);
8193
8194      putpkt (rs->buf);
8195      getpkt (&rs->buf, &rs->buf_size, 0);
8196
8197      switch (packet_ok (rs->buf, &remote_protocol_packets[PACKET_Z0]))
8198	{
8199	case PACKET_ERROR:
8200	  return -1;
8201	case PACKET_OK:
8202	  bp_tgt->placed_address = addr;
8203	  bp_tgt->placed_size = bpsize;
8204	  return 0;
8205	case PACKET_UNKNOWN:
8206	  break;
8207	}
8208    }
8209
8210  /* If this breakpoint has target-side commands but this stub doesn't
8211     support Z0 packets, throw error.  */
8212  if (!VEC_empty (agent_expr_p, bp_tgt->tcommands))
8213    throw_error (NOT_SUPPORTED_ERROR, _("\
8214Target doesn't support breakpoints that have target side commands."));
8215
8216  return memory_insert_breakpoint (ops, gdbarch, bp_tgt);
8217}
8218
8219static int
8220remote_remove_breakpoint (struct target_ops *ops,
8221			  struct gdbarch *gdbarch,
8222			  struct bp_target_info *bp_tgt)
8223{
8224  CORE_ADDR addr = bp_tgt->placed_address;
8225  struct remote_state *rs = get_remote_state ();
8226
8227  if (packet_support (PACKET_Z0) != PACKET_DISABLE)
8228    {
8229      char *p = rs->buf;
8230      char *endbuf = rs->buf + get_remote_packet_size ();
8231
8232      /* Make sure the remote is pointing at the right process, if
8233	 necessary.  */
8234      if (!gdbarch_has_global_breakpoints (target_gdbarch ()))
8235	set_general_process ();
8236
8237      *(p++) = 'z';
8238      *(p++) = '0';
8239      *(p++) = ',';
8240
8241      addr = (ULONGEST) remote_address_masked (bp_tgt->placed_address);
8242      p += hexnumstr (p, addr);
8243      xsnprintf (p, endbuf - p, ",%d", bp_tgt->placed_size);
8244
8245      putpkt (rs->buf);
8246      getpkt (&rs->buf, &rs->buf_size, 0);
8247
8248      return (rs->buf[0] == 'E');
8249    }
8250
8251  return memory_remove_breakpoint (ops, gdbarch, bp_tgt);
8252}
8253
8254static int
8255watchpoint_to_Z_packet (int type)
8256{
8257  switch (type)
8258    {
8259    case hw_write:
8260      return Z_PACKET_WRITE_WP;
8261      break;
8262    case hw_read:
8263      return Z_PACKET_READ_WP;
8264      break;
8265    case hw_access:
8266      return Z_PACKET_ACCESS_WP;
8267      break;
8268    default:
8269      internal_error (__FILE__, __LINE__,
8270		      _("hw_bp_to_z: bad watchpoint type %d"), type);
8271    }
8272}
8273
8274static int
8275remote_insert_watchpoint (struct target_ops *self,
8276			  CORE_ADDR addr, int len, int type,
8277			  struct expression *cond)
8278{
8279  struct remote_state *rs = get_remote_state ();
8280  char *endbuf = rs->buf + get_remote_packet_size ();
8281  char *p;
8282  enum Z_packet_type packet = watchpoint_to_Z_packet (type);
8283
8284  if (packet_support (PACKET_Z0 + packet) == PACKET_DISABLE)
8285    return 1;
8286
8287  /* Make sure the remote is pointing at the right process, if
8288     necessary.  */
8289  if (!gdbarch_has_global_breakpoints (target_gdbarch ()))
8290    set_general_process ();
8291
8292  xsnprintf (rs->buf, endbuf - rs->buf, "Z%x,", packet);
8293  p = strchr (rs->buf, '\0');
8294  addr = remote_address_masked (addr);
8295  p += hexnumstr (p, (ULONGEST) addr);
8296  xsnprintf (p, endbuf - p, ",%x", len);
8297
8298  putpkt (rs->buf);
8299  getpkt (&rs->buf, &rs->buf_size, 0);
8300
8301  switch (packet_ok (rs->buf, &remote_protocol_packets[PACKET_Z0 + packet]))
8302    {
8303    case PACKET_ERROR:
8304      return -1;
8305    case PACKET_UNKNOWN:
8306      return 1;
8307    case PACKET_OK:
8308      return 0;
8309    }
8310  internal_error (__FILE__, __LINE__,
8311		  _("remote_insert_watchpoint: reached end of function"));
8312}
8313
8314static int
8315remote_watchpoint_addr_within_range (struct target_ops *target, CORE_ADDR addr,
8316				     CORE_ADDR start, int length)
8317{
8318  CORE_ADDR diff = remote_address_masked (addr - start);
8319
8320  return diff < length;
8321}
8322
8323
8324static int
8325remote_remove_watchpoint (struct target_ops *self,
8326			  CORE_ADDR addr, int len, int type,
8327			  struct expression *cond)
8328{
8329  struct remote_state *rs = get_remote_state ();
8330  char *endbuf = rs->buf + get_remote_packet_size ();
8331  char *p;
8332  enum Z_packet_type packet = watchpoint_to_Z_packet (type);
8333
8334  if (packet_support (PACKET_Z0 + packet) == PACKET_DISABLE)
8335    return -1;
8336
8337  /* Make sure the remote is pointing at the right process, if
8338     necessary.  */
8339  if (!gdbarch_has_global_breakpoints (target_gdbarch ()))
8340    set_general_process ();
8341
8342  xsnprintf (rs->buf, endbuf - rs->buf, "z%x,", packet);
8343  p = strchr (rs->buf, '\0');
8344  addr = remote_address_masked (addr);
8345  p += hexnumstr (p, (ULONGEST) addr);
8346  xsnprintf (p, endbuf - p, ",%x", len);
8347  putpkt (rs->buf);
8348  getpkt (&rs->buf, &rs->buf_size, 0);
8349
8350  switch (packet_ok (rs->buf, &remote_protocol_packets[PACKET_Z0 + packet]))
8351    {
8352    case PACKET_ERROR:
8353    case PACKET_UNKNOWN:
8354      return -1;
8355    case PACKET_OK:
8356      return 0;
8357    }
8358  internal_error (__FILE__, __LINE__,
8359		  _("remote_remove_watchpoint: reached end of function"));
8360}
8361
8362
8363int remote_hw_watchpoint_limit = -1;
8364int remote_hw_watchpoint_length_limit = -1;
8365int remote_hw_breakpoint_limit = -1;
8366
8367static int
8368remote_region_ok_for_hw_watchpoint (struct target_ops *self,
8369				    CORE_ADDR addr, int len)
8370{
8371  if (remote_hw_watchpoint_length_limit == 0)
8372    return 0;
8373  else if (remote_hw_watchpoint_length_limit < 0)
8374    return 1;
8375  else if (len <= remote_hw_watchpoint_length_limit)
8376    return 1;
8377  else
8378    return 0;
8379}
8380
8381static int
8382remote_check_watch_resources (struct target_ops *self,
8383			      int type, int cnt, int ot)
8384{
8385  if (type == bp_hardware_breakpoint)
8386    {
8387      if (remote_hw_breakpoint_limit == 0)
8388	return 0;
8389      else if (remote_hw_breakpoint_limit < 0)
8390	return 1;
8391      else if (cnt <= remote_hw_breakpoint_limit)
8392	return 1;
8393    }
8394  else
8395    {
8396      if (remote_hw_watchpoint_limit == 0)
8397	return 0;
8398      else if (remote_hw_watchpoint_limit < 0)
8399	return 1;
8400      else if (ot)
8401	return -1;
8402      else if (cnt <= remote_hw_watchpoint_limit)
8403	return 1;
8404    }
8405  return -1;
8406}
8407
8408static int
8409remote_stopped_by_watchpoint (struct target_ops *ops)
8410{
8411  struct remote_state *rs = get_remote_state ();
8412
8413  return rs->remote_stopped_by_watchpoint_p;
8414}
8415
8416static int
8417remote_stopped_data_address (struct target_ops *target, CORE_ADDR *addr_p)
8418{
8419  struct remote_state *rs = get_remote_state ();
8420  int rc = 0;
8421
8422  if (remote_stopped_by_watchpoint (target))
8423    {
8424      *addr_p = rs->remote_watch_data_address;
8425      rc = 1;
8426    }
8427
8428  return rc;
8429}
8430
8431
8432static int
8433remote_insert_hw_breakpoint (struct target_ops *self, struct gdbarch *gdbarch,
8434			     struct bp_target_info *bp_tgt)
8435{
8436  CORE_ADDR addr = bp_tgt->reqstd_address;
8437  struct remote_state *rs;
8438  char *p, *endbuf;
8439  char *message;
8440  int bpsize;
8441
8442  /* The length field should be set to the size of a breakpoint
8443     instruction, even though we aren't inserting one ourselves.  */
8444
8445  gdbarch_remote_breakpoint_from_pc (gdbarch, &addr, &bpsize);
8446
8447  if (packet_support (PACKET_Z1) == PACKET_DISABLE)
8448    return -1;
8449
8450  /* Make sure the remote is pointing at the right process, if
8451     necessary.  */
8452  if (!gdbarch_has_global_breakpoints (target_gdbarch ()))
8453    set_general_process ();
8454
8455  rs = get_remote_state ();
8456  p = rs->buf;
8457  endbuf = rs->buf + get_remote_packet_size ();
8458
8459  *(p++) = 'Z';
8460  *(p++) = '1';
8461  *(p++) = ',';
8462
8463  addr = remote_address_masked (addr);
8464  p += hexnumstr (p, (ULONGEST) addr);
8465  xsnprintf (p, endbuf - p, ",%x", bpsize);
8466
8467  if (remote_supports_cond_breakpoints (self))
8468    remote_add_target_side_condition (gdbarch, bp_tgt, p, endbuf);
8469
8470  if (remote_can_run_breakpoint_commands (self))
8471    remote_add_target_side_commands (gdbarch, bp_tgt, p);
8472
8473  putpkt (rs->buf);
8474  getpkt (&rs->buf, &rs->buf_size, 0);
8475
8476  switch (packet_ok (rs->buf, &remote_protocol_packets[PACKET_Z1]))
8477    {
8478    case PACKET_ERROR:
8479      if (rs->buf[1] == '.')
8480        {
8481          message = strchr (rs->buf + 2, '.');
8482          if (message)
8483            error (_("Remote failure reply: %s"), message + 1);
8484        }
8485      return -1;
8486    case PACKET_UNKNOWN:
8487      return -1;
8488    case PACKET_OK:
8489      bp_tgt->placed_address = addr;
8490      bp_tgt->placed_size = bpsize;
8491      return 0;
8492    }
8493  internal_error (__FILE__, __LINE__,
8494		  _("remote_insert_hw_breakpoint: reached end of function"));
8495}
8496
8497
8498static int
8499remote_remove_hw_breakpoint (struct target_ops *self, struct gdbarch *gdbarch,
8500			     struct bp_target_info *bp_tgt)
8501{
8502  CORE_ADDR addr;
8503  struct remote_state *rs = get_remote_state ();
8504  char *p = rs->buf;
8505  char *endbuf = rs->buf + get_remote_packet_size ();
8506
8507  if (packet_support (PACKET_Z1) == PACKET_DISABLE)
8508    return -1;
8509
8510  /* Make sure the remote is pointing at the right process, if
8511     necessary.  */
8512  if (!gdbarch_has_global_breakpoints (target_gdbarch ()))
8513    set_general_process ();
8514
8515  *(p++) = 'z';
8516  *(p++) = '1';
8517  *(p++) = ',';
8518
8519  addr = remote_address_masked (bp_tgt->placed_address);
8520  p += hexnumstr (p, (ULONGEST) addr);
8521  xsnprintf (p, endbuf  - p, ",%x", bp_tgt->placed_size);
8522
8523  putpkt (rs->buf);
8524  getpkt (&rs->buf, &rs->buf_size, 0);
8525
8526  switch (packet_ok (rs->buf, &remote_protocol_packets[PACKET_Z1]))
8527    {
8528    case PACKET_ERROR:
8529    case PACKET_UNKNOWN:
8530      return -1;
8531    case PACKET_OK:
8532      return 0;
8533    }
8534  internal_error (__FILE__, __LINE__,
8535		  _("remote_remove_hw_breakpoint: reached end of function"));
8536}
8537
8538/* Verify memory using the "qCRC:" request.  */
8539
8540static int
8541remote_verify_memory (struct target_ops *ops,
8542		      const gdb_byte *data, CORE_ADDR lma, ULONGEST size)
8543{
8544  struct remote_state *rs = get_remote_state ();
8545  unsigned long host_crc, target_crc;
8546  char *tmp;
8547
8548  /* It doesn't make sense to use qCRC if the remote target is
8549     connected but not running.  */
8550  if (target_has_execution && packet_support (PACKET_qCRC) != PACKET_DISABLE)
8551    {
8552      enum packet_result result;
8553
8554      /* Make sure the remote is pointing at the right process.  */
8555      set_general_process ();
8556
8557      /* FIXME: assumes lma can fit into long.  */
8558      xsnprintf (rs->buf, get_remote_packet_size (), "qCRC:%lx,%lx",
8559		 (long) lma, (long) size);
8560      putpkt (rs->buf);
8561
8562      /* Be clever; compute the host_crc before waiting for target
8563	 reply.  */
8564      host_crc = xcrc32 (data, size, 0xffffffff);
8565
8566      getpkt (&rs->buf, &rs->buf_size, 0);
8567
8568      result = packet_ok (rs->buf,
8569			  &remote_protocol_packets[PACKET_qCRC]);
8570      if (result == PACKET_ERROR)
8571	return -1;
8572      else if (result == PACKET_OK)
8573	{
8574	  for (target_crc = 0, tmp = &rs->buf[1]; *tmp; tmp++)
8575	    target_crc = target_crc * 16 + fromhex (*tmp);
8576
8577	  return (host_crc == target_crc);
8578	}
8579    }
8580
8581  return simple_verify_memory (ops, data, lma, size);
8582}
8583
8584/* compare-sections command
8585
8586   With no arguments, compares each loadable section in the exec bfd
8587   with the same memory range on the target, and reports mismatches.
8588   Useful for verifying the image on the target against the exec file.  */
8589
8590static void
8591compare_sections_command (char *args, int from_tty)
8592{
8593  asection *s;
8594  struct cleanup *old_chain;
8595  gdb_byte *sectdata;
8596  const char *sectname;
8597  bfd_size_type size;
8598  bfd_vma lma;
8599  int matched = 0;
8600  int mismatched = 0;
8601  int res;
8602  int read_only = 0;
8603
8604  if (!exec_bfd)
8605    error (_("command cannot be used without an exec file"));
8606
8607  /* Make sure the remote is pointing at the right process.  */
8608  set_general_process ();
8609
8610  if (args != NULL && strcmp (args, "-r") == 0)
8611    {
8612      read_only = 1;
8613      args = NULL;
8614    }
8615
8616  for (s = exec_bfd->sections; s; s = s->next)
8617    {
8618      if (!(s->flags & SEC_LOAD))
8619	continue;		/* Skip non-loadable section.  */
8620
8621      if (read_only && (s->flags & SEC_READONLY) == 0)
8622	continue;		/* Skip writeable sections */
8623
8624      size = bfd_get_section_size (s);
8625      if (size == 0)
8626	continue;		/* Skip zero-length section.  */
8627
8628      sectname = bfd_get_section_name (exec_bfd, s);
8629      if (args && strcmp (args, sectname) != 0)
8630	continue;		/* Not the section selected by user.  */
8631
8632      matched = 1;		/* Do this section.  */
8633      lma = s->lma;
8634
8635      sectdata = xmalloc (size);
8636      old_chain = make_cleanup (xfree, sectdata);
8637      bfd_get_section_contents (exec_bfd, s, sectdata, 0, size);
8638
8639      res = target_verify_memory (sectdata, lma, size);
8640
8641      if (res == -1)
8642	error (_("target memory fault, section %s, range %s -- %s"), sectname,
8643	       paddress (target_gdbarch (), lma),
8644	       paddress (target_gdbarch (), lma + size));
8645
8646      printf_filtered ("Section %s, range %s -- %s: ", sectname,
8647		       paddress (target_gdbarch (), lma),
8648		       paddress (target_gdbarch (), lma + size));
8649      if (res)
8650	printf_filtered ("matched.\n");
8651      else
8652	{
8653	  printf_filtered ("MIS-MATCHED!\n");
8654	  mismatched++;
8655	}
8656
8657      do_cleanups (old_chain);
8658    }
8659  if (mismatched > 0)
8660    warning (_("One or more sections of the target image does not match\n\
8661the loaded file\n"));
8662  if (args && !matched)
8663    printf_filtered (_("No loaded section named '%s'.\n"), args);
8664}
8665
8666/* Write LEN bytes from WRITEBUF into OBJECT_NAME/ANNEX at OFFSET
8667   into remote target.  The number of bytes written to the remote
8668   target is returned, or -1 for error.  */
8669
8670static enum target_xfer_status
8671remote_write_qxfer (struct target_ops *ops, const char *object_name,
8672                    const char *annex, const gdb_byte *writebuf,
8673                    ULONGEST offset, LONGEST len, ULONGEST *xfered_len,
8674                    struct packet_config *packet)
8675{
8676  int i, buf_len;
8677  ULONGEST n;
8678  struct remote_state *rs = get_remote_state ();
8679  int max_size = get_memory_write_packet_size ();
8680
8681  if (packet->support == PACKET_DISABLE)
8682    return TARGET_XFER_E_IO;
8683
8684  /* Insert header.  */
8685  i = snprintf (rs->buf, max_size,
8686		"qXfer:%s:write:%s:%s:",
8687		object_name, annex ? annex : "",
8688		phex_nz (offset, sizeof offset));
8689  max_size -= (i + 1);
8690
8691  /* Escape as much data as fits into rs->buf.  */
8692  buf_len = remote_escape_output
8693    (writebuf, len, (gdb_byte *) rs->buf + i, &max_size, max_size);
8694
8695  if (putpkt_binary (rs->buf, i + buf_len) < 0
8696      || getpkt_sane (&rs->buf, &rs->buf_size, 0) < 0
8697      || packet_ok (rs->buf, packet) != PACKET_OK)
8698    return TARGET_XFER_E_IO;
8699
8700  unpack_varlen_hex (rs->buf, &n);
8701
8702  *xfered_len = n;
8703  return TARGET_XFER_OK;
8704}
8705
8706/* Read OBJECT_NAME/ANNEX from the remote target using a qXfer packet.
8707   Data at OFFSET, of up to LEN bytes, is read into READBUF; the
8708   number of bytes read is returned, or 0 for EOF, or -1 for error.
8709   The number of bytes read may be less than LEN without indicating an
8710   EOF.  PACKET is checked and updated to indicate whether the remote
8711   target supports this object.  */
8712
8713static enum target_xfer_status
8714remote_read_qxfer (struct target_ops *ops, const char *object_name,
8715		   const char *annex,
8716		   gdb_byte *readbuf, ULONGEST offset, LONGEST len,
8717		   ULONGEST *xfered_len,
8718		   struct packet_config *packet)
8719{
8720  struct remote_state *rs = get_remote_state ();
8721  LONGEST i, n, packet_len;
8722
8723  if (packet->support == PACKET_DISABLE)
8724    return TARGET_XFER_E_IO;
8725
8726  /* Check whether we've cached an end-of-object packet that matches
8727     this request.  */
8728  if (rs->finished_object)
8729    {
8730      if (strcmp (object_name, rs->finished_object) == 0
8731	  && strcmp (annex ? annex : "", rs->finished_annex) == 0
8732	  && offset == rs->finished_offset)
8733	return TARGET_XFER_EOF;
8734
8735
8736      /* Otherwise, we're now reading something different.  Discard
8737	 the cache.  */
8738      xfree (rs->finished_object);
8739      xfree (rs->finished_annex);
8740      rs->finished_object = NULL;
8741      rs->finished_annex = NULL;
8742    }
8743
8744  /* Request only enough to fit in a single packet.  The actual data
8745     may not, since we don't know how much of it will need to be escaped;
8746     the target is free to respond with slightly less data.  We subtract
8747     five to account for the response type and the protocol frame.  */
8748  n = min (get_remote_packet_size () - 5, len);
8749  snprintf (rs->buf, get_remote_packet_size () - 4, "qXfer:%s:read:%s:%s,%s",
8750	    object_name, annex ? annex : "",
8751	    phex_nz (offset, sizeof offset),
8752	    phex_nz (n, sizeof n));
8753  i = putpkt (rs->buf);
8754  if (i < 0)
8755    return TARGET_XFER_E_IO;
8756
8757  rs->buf[0] = '\0';
8758  packet_len = getpkt_sane (&rs->buf, &rs->buf_size, 0);
8759  if (packet_len < 0 || packet_ok (rs->buf, packet) != PACKET_OK)
8760    return TARGET_XFER_E_IO;
8761
8762  if (rs->buf[0] != 'l' && rs->buf[0] != 'm')
8763    error (_("Unknown remote qXfer reply: %s"), rs->buf);
8764
8765  /* 'm' means there is (or at least might be) more data after this
8766     batch.  That does not make sense unless there's at least one byte
8767     of data in this reply.  */
8768  if (rs->buf[0] == 'm' && packet_len == 1)
8769    error (_("Remote qXfer reply contained no data."));
8770
8771  /* Got some data.  */
8772  i = remote_unescape_input ((gdb_byte *) rs->buf + 1,
8773			     packet_len - 1, readbuf, n);
8774
8775  /* 'l' is an EOF marker, possibly including a final block of data,
8776     or possibly empty.  If we have the final block of a non-empty
8777     object, record this fact to bypass a subsequent partial read.  */
8778  if (rs->buf[0] == 'l' && offset + i > 0)
8779    {
8780      rs->finished_object = xstrdup (object_name);
8781      rs->finished_annex = xstrdup (annex ? annex : "");
8782      rs->finished_offset = offset + i;
8783    }
8784
8785  if (i == 0)
8786    return TARGET_XFER_EOF;
8787  else
8788    {
8789      *xfered_len = i;
8790      return TARGET_XFER_OK;
8791    }
8792}
8793
8794static enum target_xfer_status
8795remote_xfer_partial (struct target_ops *ops, enum target_object object,
8796		     const char *annex, gdb_byte *readbuf,
8797		     const gdb_byte *writebuf, ULONGEST offset, ULONGEST len,
8798		     ULONGEST *xfered_len)
8799{
8800  struct remote_state *rs;
8801  int i;
8802  char *p2;
8803  char query_type;
8804
8805  set_remote_traceframe ();
8806  set_general_thread (inferior_ptid);
8807
8808  rs = get_remote_state ();
8809
8810  /* Handle memory using the standard memory routines.  */
8811  if (object == TARGET_OBJECT_MEMORY)
8812    {
8813      /* If the remote target is connected but not running, we should
8814	 pass this request down to a lower stratum (e.g. the executable
8815	 file).  */
8816      if (!target_has_execution)
8817	return TARGET_XFER_EOF;
8818
8819      if (writebuf != NULL)
8820	return remote_write_bytes (offset, writebuf, len, xfered_len);
8821      else
8822	return remote_read_bytes (ops, offset, readbuf, len, xfered_len);
8823    }
8824
8825  /* Handle SPU memory using qxfer packets.  */
8826  if (object == TARGET_OBJECT_SPU)
8827    {
8828      if (readbuf)
8829	return remote_read_qxfer (ops, "spu", annex, readbuf, offset, len,
8830				  xfered_len, &remote_protocol_packets
8831				  [PACKET_qXfer_spu_read]);
8832      else
8833	return remote_write_qxfer (ops, "spu", annex, writebuf, offset, len,
8834				   xfered_len, &remote_protocol_packets
8835				   [PACKET_qXfer_spu_write]);
8836    }
8837
8838  /* Handle extra signal info using qxfer packets.  */
8839  if (object == TARGET_OBJECT_SIGNAL_INFO)
8840    {
8841      if (readbuf)
8842	return remote_read_qxfer (ops, "siginfo", annex, readbuf, offset, len,
8843				  xfered_len, &remote_protocol_packets
8844				  [PACKET_qXfer_siginfo_read]);
8845      else
8846	return remote_write_qxfer (ops, "siginfo", annex,
8847				   writebuf, offset, len, xfered_len,
8848				   &remote_protocol_packets
8849				   [PACKET_qXfer_siginfo_write]);
8850    }
8851
8852  if (object == TARGET_OBJECT_STATIC_TRACE_DATA)
8853    {
8854      if (readbuf)
8855	return remote_read_qxfer (ops, "statictrace", annex,
8856				  readbuf, offset, len, xfered_len,
8857				  &remote_protocol_packets
8858				  [PACKET_qXfer_statictrace_read]);
8859      else
8860	return TARGET_XFER_E_IO;
8861    }
8862
8863  /* Only handle flash writes.  */
8864  if (writebuf != NULL)
8865    {
8866      LONGEST xfered;
8867
8868      switch (object)
8869	{
8870	case TARGET_OBJECT_FLASH:
8871	  return remote_flash_write (ops, offset, len, xfered_len,
8872				     writebuf);
8873
8874	default:
8875	  return TARGET_XFER_E_IO;
8876	}
8877    }
8878
8879  /* Map pre-existing objects onto letters.  DO NOT do this for new
8880     objects!!!  Instead specify new query packets.  */
8881  switch (object)
8882    {
8883    case TARGET_OBJECT_AVR:
8884      query_type = 'R';
8885      break;
8886
8887    case TARGET_OBJECT_AUXV:
8888      gdb_assert (annex == NULL);
8889      return remote_read_qxfer (ops, "auxv", annex, readbuf, offset, len,
8890				xfered_len,
8891				&remote_protocol_packets[PACKET_qXfer_auxv]);
8892
8893    case TARGET_OBJECT_AVAILABLE_FEATURES:
8894      return remote_read_qxfer
8895	(ops, "features", annex, readbuf, offset, len, xfered_len,
8896	 &remote_protocol_packets[PACKET_qXfer_features]);
8897
8898    case TARGET_OBJECT_LIBRARIES:
8899      return remote_read_qxfer
8900	(ops, "libraries", annex, readbuf, offset, len, xfered_len,
8901	 &remote_protocol_packets[PACKET_qXfer_libraries]);
8902
8903    case TARGET_OBJECT_LIBRARIES_SVR4:
8904      return remote_read_qxfer
8905	(ops, "libraries-svr4", annex, readbuf, offset, len, xfered_len,
8906	 &remote_protocol_packets[PACKET_qXfer_libraries_svr4]);
8907
8908    case TARGET_OBJECT_MEMORY_MAP:
8909      gdb_assert (annex == NULL);
8910      return remote_read_qxfer (ops, "memory-map", annex, readbuf, offset, len,
8911				 xfered_len,
8912				&remote_protocol_packets[PACKET_qXfer_memory_map]);
8913
8914    case TARGET_OBJECT_OSDATA:
8915      /* Should only get here if we're connected.  */
8916      gdb_assert (rs->remote_desc);
8917      return remote_read_qxfer
8918	(ops, "osdata", annex, readbuf, offset, len, xfered_len,
8919        &remote_protocol_packets[PACKET_qXfer_osdata]);
8920
8921    case TARGET_OBJECT_THREADS:
8922      gdb_assert (annex == NULL);
8923      return remote_read_qxfer (ops, "threads", annex, readbuf, offset, len,
8924				xfered_len,
8925				&remote_protocol_packets[PACKET_qXfer_threads]);
8926
8927    case TARGET_OBJECT_TRACEFRAME_INFO:
8928      gdb_assert (annex == NULL);
8929      return remote_read_qxfer
8930	(ops, "traceframe-info", annex, readbuf, offset, len, xfered_len,
8931	 &remote_protocol_packets[PACKET_qXfer_traceframe_info]);
8932
8933    case TARGET_OBJECT_FDPIC:
8934      return remote_read_qxfer (ops, "fdpic", annex, readbuf, offset, len,
8935				xfered_len,
8936				&remote_protocol_packets[PACKET_qXfer_fdpic]);
8937
8938    case TARGET_OBJECT_OPENVMS_UIB:
8939      return remote_read_qxfer (ops, "uib", annex, readbuf, offset, len,
8940				xfered_len,
8941				&remote_protocol_packets[PACKET_qXfer_uib]);
8942
8943    case TARGET_OBJECT_BTRACE:
8944      return remote_read_qxfer (ops, "btrace", annex, readbuf, offset, len,
8945				xfered_len,
8946        &remote_protocol_packets[PACKET_qXfer_btrace]);
8947
8948    default:
8949      return TARGET_XFER_E_IO;
8950    }
8951
8952  /* Minimum outbuf size is get_remote_packet_size ().  If LEN is not
8953     large enough let the caller deal with it.  */
8954  if (len < get_remote_packet_size ())
8955    return TARGET_XFER_E_IO;
8956  len = get_remote_packet_size ();
8957
8958  /* Except for querying the minimum buffer size, target must be open.  */
8959  if (!rs->remote_desc)
8960    error (_("remote query is only available after target open"));
8961
8962  gdb_assert (annex != NULL);
8963  gdb_assert (readbuf != NULL);
8964
8965  p2 = rs->buf;
8966  *p2++ = 'q';
8967  *p2++ = query_type;
8968
8969  /* We used one buffer char for the remote protocol q command and
8970     another for the query type.  As the remote protocol encapsulation
8971     uses 4 chars plus one extra in case we are debugging
8972     (remote_debug), we have PBUFZIZ - 7 left to pack the query
8973     string.  */
8974  i = 0;
8975  while (annex[i] && (i < (get_remote_packet_size () - 8)))
8976    {
8977      /* Bad caller may have sent forbidden characters.  */
8978      gdb_assert (isprint (annex[i]) && annex[i] != '$' && annex[i] != '#');
8979      *p2++ = annex[i];
8980      i++;
8981    }
8982  *p2 = '\0';
8983  gdb_assert (annex[i] == '\0');
8984
8985  i = putpkt (rs->buf);
8986  if (i < 0)
8987    return TARGET_XFER_E_IO;
8988
8989  getpkt (&rs->buf, &rs->buf_size, 0);
8990  strcpy ((char *) readbuf, rs->buf);
8991
8992  *xfered_len = strlen ((char *) readbuf);
8993  return TARGET_XFER_OK;
8994}
8995
8996static int
8997remote_search_memory (struct target_ops* ops,
8998		      CORE_ADDR start_addr, ULONGEST search_space_len,
8999		      const gdb_byte *pattern, ULONGEST pattern_len,
9000		      CORE_ADDR *found_addrp)
9001{
9002  int addr_size = gdbarch_addr_bit (target_gdbarch ()) / 8;
9003  struct remote_state *rs = get_remote_state ();
9004  int max_size = get_memory_write_packet_size ();
9005  struct packet_config *packet =
9006    &remote_protocol_packets[PACKET_qSearch_memory];
9007  /* Number of packet bytes used to encode the pattern;
9008     this could be more than PATTERN_LEN due to escape characters.  */
9009  int escaped_pattern_len;
9010  /* Amount of pattern that was encodable in the packet.  */
9011  int used_pattern_len;
9012  int i;
9013  int found;
9014  ULONGEST found_addr;
9015
9016  /* Don't go to the target if we don't have to.
9017     This is done before checking packet->support to avoid the possibility that
9018     a success for this edge case means the facility works in general.  */
9019  if (pattern_len > search_space_len)
9020    return 0;
9021  if (pattern_len == 0)
9022    {
9023      *found_addrp = start_addr;
9024      return 1;
9025    }
9026
9027  /* If we already know the packet isn't supported, fall back to the simple
9028     way of searching memory.  */
9029
9030  if (packet_config_support (packet) == PACKET_DISABLE)
9031    {
9032      /* Target doesn't provided special support, fall back and use the
9033	 standard support (copy memory and do the search here).  */
9034      return simple_search_memory (ops, start_addr, search_space_len,
9035				   pattern, pattern_len, found_addrp);
9036    }
9037
9038  /* Make sure the remote is pointing at the right process.  */
9039  set_general_process ();
9040
9041  /* Insert header.  */
9042  i = snprintf (rs->buf, max_size,
9043		"qSearch:memory:%s;%s;",
9044		phex_nz (start_addr, addr_size),
9045		phex_nz (search_space_len, sizeof (search_space_len)));
9046  max_size -= (i + 1);
9047
9048  /* Escape as much data as fits into rs->buf.  */
9049  escaped_pattern_len =
9050    remote_escape_output (pattern, pattern_len, (gdb_byte *) rs->buf + i,
9051			  &used_pattern_len, max_size);
9052
9053  /* Bail if the pattern is too large.  */
9054  if (used_pattern_len != pattern_len)
9055    error (_("Pattern is too large to transmit to remote target."));
9056
9057  if (putpkt_binary (rs->buf, i + escaped_pattern_len) < 0
9058      || getpkt_sane (&rs->buf, &rs->buf_size, 0) < 0
9059      || packet_ok (rs->buf, packet) != PACKET_OK)
9060    {
9061      /* The request may not have worked because the command is not
9062	 supported.  If so, fall back to the simple way.  */
9063      if (packet->support == PACKET_DISABLE)
9064	{
9065	  return simple_search_memory (ops, start_addr, search_space_len,
9066				       pattern, pattern_len, found_addrp);
9067	}
9068      return -1;
9069    }
9070
9071  if (rs->buf[0] == '0')
9072    found = 0;
9073  else if (rs->buf[0] == '1')
9074    {
9075      found = 1;
9076      if (rs->buf[1] != ',')
9077	error (_("Unknown qSearch:memory reply: %s"), rs->buf);
9078      unpack_varlen_hex (rs->buf + 2, &found_addr);
9079      *found_addrp = found_addr;
9080    }
9081  else
9082    error (_("Unknown qSearch:memory reply: %s"), rs->buf);
9083
9084  return found;
9085}
9086
9087static void
9088remote_rcmd (struct target_ops *self, const char *command,
9089	     struct ui_file *outbuf)
9090{
9091  struct remote_state *rs = get_remote_state ();
9092  char *p = rs->buf;
9093
9094  if (!rs->remote_desc)
9095    error (_("remote rcmd is only available after target open"));
9096
9097  /* Send a NULL command across as an empty command.  */
9098  if (command == NULL)
9099    command = "";
9100
9101  /* The query prefix.  */
9102  strcpy (rs->buf, "qRcmd,");
9103  p = strchr (rs->buf, '\0');
9104
9105  if ((strlen (rs->buf) + strlen (command) * 2 + 8/*misc*/)
9106      > get_remote_packet_size ())
9107    error (_("\"monitor\" command ``%s'' is too long."), command);
9108
9109  /* Encode the actual command.  */
9110  bin2hex ((const gdb_byte *) command, p, strlen (command));
9111
9112  if (putpkt (rs->buf) < 0)
9113    error (_("Communication problem with target."));
9114
9115  /* get/display the response */
9116  while (1)
9117    {
9118      char *buf;
9119
9120      /* XXX - see also remote_get_noisy_reply().  */
9121      QUIT;			/* Allow user to bail out with ^C.  */
9122      rs->buf[0] = '\0';
9123      if (getpkt_sane (&rs->buf, &rs->buf_size, 0) == -1)
9124        {
9125          /* Timeout.  Continue to (try to) read responses.
9126             This is better than stopping with an error, assuming the stub
9127             is still executing the (long) monitor command.
9128             If needed, the user can interrupt gdb using C-c, obtaining
9129             an effect similar to stop on timeout.  */
9130          continue;
9131        }
9132      buf = rs->buf;
9133      if (buf[0] == '\0')
9134	error (_("Target does not support this command."));
9135      if (buf[0] == 'O' && buf[1] != 'K')
9136	{
9137	  remote_console_output (buf + 1); /* 'O' message from stub.  */
9138	  continue;
9139	}
9140      if (strcmp (buf, "OK") == 0)
9141	break;
9142      if (strlen (buf) == 3 && buf[0] == 'E'
9143	  && isdigit (buf[1]) && isdigit (buf[2]))
9144	{
9145	  error (_("Protocol error with Rcmd"));
9146	}
9147      for (p = buf; p[0] != '\0' && p[1] != '\0'; p += 2)
9148	{
9149	  char c = (fromhex (p[0]) << 4) + fromhex (p[1]);
9150
9151	  fputc_unfiltered (c, outbuf);
9152	}
9153      break;
9154    }
9155}
9156
9157static VEC(mem_region_s) *
9158remote_memory_map (struct target_ops *ops)
9159{
9160  VEC(mem_region_s) *result = NULL;
9161  char *text = target_read_stralloc (&current_target,
9162				     TARGET_OBJECT_MEMORY_MAP, NULL);
9163
9164  if (text)
9165    {
9166      struct cleanup *back_to = make_cleanup (xfree, text);
9167
9168      result = parse_memory_map (text);
9169      do_cleanups (back_to);
9170    }
9171
9172  return result;
9173}
9174
9175static void
9176packet_command (char *args, int from_tty)
9177{
9178  struct remote_state *rs = get_remote_state ();
9179
9180  if (!rs->remote_desc)
9181    error (_("command can only be used with remote target"));
9182
9183  if (!args)
9184    error (_("remote-packet command requires packet text as argument"));
9185
9186  puts_filtered ("sending: ");
9187  print_packet (args);
9188  puts_filtered ("\n");
9189  putpkt (args);
9190
9191  getpkt (&rs->buf, &rs->buf_size, 0);
9192  puts_filtered ("received: ");
9193  print_packet (rs->buf);
9194  puts_filtered ("\n");
9195}
9196
9197#if 0
9198/* --------- UNIT_TEST for THREAD oriented PACKETS ------------------- */
9199
9200static void display_thread_info (struct gdb_ext_thread_info *info);
9201
9202static void threadset_test_cmd (char *cmd, int tty);
9203
9204static void threadalive_test (char *cmd, int tty);
9205
9206static void threadlist_test_cmd (char *cmd, int tty);
9207
9208int get_and_display_threadinfo (threadref *ref);
9209
9210static void threadinfo_test_cmd (char *cmd, int tty);
9211
9212static int thread_display_step (threadref *ref, void *context);
9213
9214static void threadlist_update_test_cmd (char *cmd, int tty);
9215
9216static void init_remote_threadtests (void);
9217
9218#define SAMPLE_THREAD  0x05060708	/* Truncated 64 bit threadid.  */
9219
9220static void
9221threadset_test_cmd (char *cmd, int tty)
9222{
9223  int sample_thread = SAMPLE_THREAD;
9224
9225  printf_filtered (_("Remote threadset test\n"));
9226  set_general_thread (sample_thread);
9227}
9228
9229
9230static void
9231threadalive_test (char *cmd, int tty)
9232{
9233  int sample_thread = SAMPLE_THREAD;
9234  int pid = ptid_get_pid (inferior_ptid);
9235  ptid_t ptid = ptid_build (pid, sample_thread, 0);
9236
9237  if (remote_thread_alive (ptid))
9238    printf_filtered ("PASS: Thread alive test\n");
9239  else
9240    printf_filtered ("FAIL: Thread alive test\n");
9241}
9242
9243void output_threadid (char *title, threadref *ref);
9244
9245void
9246output_threadid (char *title, threadref *ref)
9247{
9248  char hexid[20];
9249
9250  pack_threadid (&hexid[0], ref);	/* Convert threead id into hex.  */
9251  hexid[16] = 0;
9252  printf_filtered ("%s  %s\n", title, (&hexid[0]));
9253}
9254
9255static void
9256threadlist_test_cmd (char *cmd, int tty)
9257{
9258  int startflag = 1;
9259  threadref nextthread;
9260  int done, result_count;
9261  threadref threadlist[3];
9262
9263  printf_filtered ("Remote Threadlist test\n");
9264  if (!remote_get_threadlist (startflag, &nextthread, 3, &done,
9265			      &result_count, &threadlist[0]))
9266    printf_filtered ("FAIL: threadlist test\n");
9267  else
9268    {
9269      threadref *scan = threadlist;
9270      threadref *limit = scan + result_count;
9271
9272      while (scan < limit)
9273	output_threadid (" thread ", scan++);
9274    }
9275}
9276
9277void
9278display_thread_info (struct gdb_ext_thread_info *info)
9279{
9280  output_threadid ("Threadid: ", &info->threadid);
9281  printf_filtered ("Name: %s\n ", info->shortname);
9282  printf_filtered ("State: %s\n", info->display);
9283  printf_filtered ("other: %s\n\n", info->more_display);
9284}
9285
9286int
9287get_and_display_threadinfo (threadref *ref)
9288{
9289  int result;
9290  int set;
9291  struct gdb_ext_thread_info threadinfo;
9292
9293  set = TAG_THREADID | TAG_EXISTS | TAG_THREADNAME
9294    | TAG_MOREDISPLAY | TAG_DISPLAY;
9295  if (0 != (result = remote_get_threadinfo (ref, set, &threadinfo)))
9296    display_thread_info (&threadinfo);
9297  return result;
9298}
9299
9300static void
9301threadinfo_test_cmd (char *cmd, int tty)
9302{
9303  int athread = SAMPLE_THREAD;
9304  threadref thread;
9305  int set;
9306
9307  int_to_threadref (&thread, athread);
9308  printf_filtered ("Remote Threadinfo test\n");
9309  if (!get_and_display_threadinfo (&thread))
9310    printf_filtered ("FAIL cannot get thread info\n");
9311}
9312
9313static int
9314thread_display_step (threadref *ref, void *context)
9315{
9316  /* output_threadid(" threadstep ",ref); *//* simple test */
9317  return get_and_display_threadinfo (ref);
9318}
9319
9320static void
9321threadlist_update_test_cmd (char *cmd, int tty)
9322{
9323  printf_filtered ("Remote Threadlist update test\n");
9324  remote_threadlist_iterator (thread_display_step, 0, CRAZY_MAX_THREADS);
9325}
9326
9327static void
9328init_remote_threadtests (void)
9329{
9330  add_com ("tlist", class_obscure, threadlist_test_cmd,
9331	   _("Fetch and print the remote list of "
9332	     "thread identifiers, one pkt only"));
9333  add_com ("tinfo", class_obscure, threadinfo_test_cmd,
9334	   _("Fetch and display info about one thread"));
9335  add_com ("tset", class_obscure, threadset_test_cmd,
9336	   _("Test setting to a different thread"));
9337  add_com ("tupd", class_obscure, threadlist_update_test_cmd,
9338	   _("Iterate through updating all remote thread info"));
9339  add_com ("talive", class_obscure, threadalive_test,
9340	   _(" Remote thread alive test "));
9341}
9342
9343#endif /* 0 */
9344
9345/* Convert a thread ID to a string.  Returns the string in a static
9346   buffer.  */
9347
9348static char *
9349remote_pid_to_str (struct target_ops *ops, ptid_t ptid)
9350{
9351  static char buf[64];
9352  struct remote_state *rs = get_remote_state ();
9353
9354  if (ptid_equal (ptid, null_ptid))
9355    return normal_pid_to_str (ptid);
9356  else if (ptid_is_pid (ptid))
9357    {
9358      /* Printing an inferior target id.  */
9359
9360      /* When multi-process extensions are off, there's no way in the
9361	 remote protocol to know the remote process id, if there's any
9362	 at all.  There's one exception --- when we're connected with
9363	 target extended-remote, and we manually attached to a process
9364	 with "attach PID".  We don't record anywhere a flag that
9365	 allows us to distinguish that case from the case of
9366	 connecting with extended-remote and the stub already being
9367	 attached to a process, and reporting yes to qAttached, hence
9368	 no smart special casing here.  */
9369      if (!remote_multi_process_p (rs))
9370	{
9371	  xsnprintf (buf, sizeof buf, "Remote target");
9372	  return buf;
9373	}
9374
9375      return normal_pid_to_str (ptid);
9376    }
9377  else
9378    {
9379      if (ptid_equal (magic_null_ptid, ptid))
9380	xsnprintf (buf, sizeof buf, "Thread <main>");
9381      else if (rs->extended && remote_multi_process_p (rs))
9382	xsnprintf (buf, sizeof buf, "Thread %d.%ld",
9383		   ptid_get_pid (ptid), ptid_get_lwp (ptid));
9384      else
9385	xsnprintf (buf, sizeof buf, "Thread %ld",
9386		   ptid_get_lwp (ptid));
9387      return buf;
9388    }
9389}
9390
9391/* Get the address of the thread local variable in OBJFILE which is
9392   stored at OFFSET within the thread local storage for thread PTID.  */
9393
9394static CORE_ADDR
9395remote_get_thread_local_address (struct target_ops *ops,
9396				 ptid_t ptid, CORE_ADDR lm, CORE_ADDR offset)
9397{
9398  if (packet_support (PACKET_qGetTLSAddr) != PACKET_DISABLE)
9399    {
9400      struct remote_state *rs = get_remote_state ();
9401      char *p = rs->buf;
9402      char *endp = rs->buf + get_remote_packet_size ();
9403      enum packet_result result;
9404
9405      strcpy (p, "qGetTLSAddr:");
9406      p += strlen (p);
9407      p = write_ptid (p, endp, ptid);
9408      *p++ = ',';
9409      p += hexnumstr (p, offset);
9410      *p++ = ',';
9411      p += hexnumstr (p, lm);
9412      *p++ = '\0';
9413
9414      putpkt (rs->buf);
9415      getpkt (&rs->buf, &rs->buf_size, 0);
9416      result = packet_ok (rs->buf,
9417			  &remote_protocol_packets[PACKET_qGetTLSAddr]);
9418      if (result == PACKET_OK)
9419	{
9420	  ULONGEST result;
9421
9422	  unpack_varlen_hex (rs->buf, &result);
9423	  return result;
9424	}
9425      else if (result == PACKET_UNKNOWN)
9426	throw_error (TLS_GENERIC_ERROR,
9427		     _("Remote target doesn't support qGetTLSAddr packet"));
9428      else
9429	throw_error (TLS_GENERIC_ERROR,
9430		     _("Remote target failed to process qGetTLSAddr request"));
9431    }
9432  else
9433    throw_error (TLS_GENERIC_ERROR,
9434		 _("TLS not supported or disabled on this target"));
9435  /* Not reached.  */
9436  return 0;
9437}
9438
9439/* Provide thread local base, i.e. Thread Information Block address.
9440   Returns 1 if ptid is found and thread_local_base is non zero.  */
9441
9442static int
9443remote_get_tib_address (struct target_ops *self, ptid_t ptid, CORE_ADDR *addr)
9444{
9445  if (packet_support (PACKET_qGetTIBAddr) != PACKET_DISABLE)
9446    {
9447      struct remote_state *rs = get_remote_state ();
9448      char *p = rs->buf;
9449      char *endp = rs->buf + get_remote_packet_size ();
9450      enum packet_result result;
9451
9452      strcpy (p, "qGetTIBAddr:");
9453      p += strlen (p);
9454      p = write_ptid (p, endp, ptid);
9455      *p++ = '\0';
9456
9457      putpkt (rs->buf);
9458      getpkt (&rs->buf, &rs->buf_size, 0);
9459      result = packet_ok (rs->buf,
9460			  &remote_protocol_packets[PACKET_qGetTIBAddr]);
9461      if (result == PACKET_OK)
9462	{
9463	  ULONGEST result;
9464
9465	  unpack_varlen_hex (rs->buf, &result);
9466	  if (addr)
9467	    *addr = (CORE_ADDR) result;
9468	  return 1;
9469	}
9470      else if (result == PACKET_UNKNOWN)
9471	error (_("Remote target doesn't support qGetTIBAddr packet"));
9472      else
9473	error (_("Remote target failed to process qGetTIBAddr request"));
9474    }
9475  else
9476    error (_("qGetTIBAddr not supported or disabled on this target"));
9477  /* Not reached.  */
9478  return 0;
9479}
9480
9481/* Support for inferring a target description based on the current
9482   architecture and the size of a 'g' packet.  While the 'g' packet
9483   can have any size (since optional registers can be left off the
9484   end), some sizes are easily recognizable given knowledge of the
9485   approximate architecture.  */
9486
9487struct remote_g_packet_guess
9488{
9489  int bytes;
9490  const struct target_desc *tdesc;
9491};
9492typedef struct remote_g_packet_guess remote_g_packet_guess_s;
9493DEF_VEC_O(remote_g_packet_guess_s);
9494
9495struct remote_g_packet_data
9496{
9497  VEC(remote_g_packet_guess_s) *guesses;
9498};
9499
9500static struct gdbarch_data *remote_g_packet_data_handle;
9501
9502static void *
9503remote_g_packet_data_init (struct obstack *obstack)
9504{
9505  return OBSTACK_ZALLOC (obstack, struct remote_g_packet_data);
9506}
9507
9508void
9509register_remote_g_packet_guess (struct gdbarch *gdbarch, int bytes,
9510				const struct target_desc *tdesc)
9511{
9512  struct remote_g_packet_data *data
9513    = gdbarch_data (gdbarch, remote_g_packet_data_handle);
9514  struct remote_g_packet_guess new_guess, *guess;
9515  int ix;
9516
9517  gdb_assert (tdesc != NULL);
9518
9519  for (ix = 0;
9520       VEC_iterate (remote_g_packet_guess_s, data->guesses, ix, guess);
9521       ix++)
9522    if (guess->bytes == bytes)
9523      internal_error (__FILE__, __LINE__,
9524		      _("Duplicate g packet description added for size %d"),
9525		      bytes);
9526
9527  new_guess.bytes = bytes;
9528  new_guess.tdesc = tdesc;
9529  VEC_safe_push (remote_g_packet_guess_s, data->guesses, &new_guess);
9530}
9531
9532/* Return 1 if remote_read_description would do anything on this target
9533   and architecture, 0 otherwise.  */
9534
9535static int
9536remote_read_description_p (struct target_ops *target)
9537{
9538  struct remote_g_packet_data *data
9539    = gdbarch_data (target_gdbarch (), remote_g_packet_data_handle);
9540
9541  if (!VEC_empty (remote_g_packet_guess_s, data->guesses))
9542    return 1;
9543
9544  return 0;
9545}
9546
9547static const struct target_desc *
9548remote_read_description (struct target_ops *target)
9549{
9550  struct remote_g_packet_data *data
9551    = gdbarch_data (target_gdbarch (), remote_g_packet_data_handle);
9552
9553  /* Do not try this during initial connection, when we do not know
9554     whether there is a running but stopped thread.  */
9555  if (!target_has_execution || ptid_equal (inferior_ptid, null_ptid))
9556    return target->beneath->to_read_description (target->beneath);
9557
9558  if (!VEC_empty (remote_g_packet_guess_s, data->guesses))
9559    {
9560      struct remote_g_packet_guess *guess;
9561      int ix;
9562      int bytes = send_g_packet ();
9563
9564      for (ix = 0;
9565	   VEC_iterate (remote_g_packet_guess_s, data->guesses, ix, guess);
9566	   ix++)
9567	if (guess->bytes == bytes)
9568	  return guess->tdesc;
9569
9570      /* We discard the g packet.  A minor optimization would be to
9571	 hold on to it, and fill the register cache once we have selected
9572	 an architecture, but it's too tricky to do safely.  */
9573    }
9574
9575  return target->beneath->to_read_description (target->beneath);
9576}
9577
9578/* Remote file transfer support.  This is host-initiated I/O, not
9579   target-initiated; for target-initiated, see remote-fileio.c.  */
9580
9581/* If *LEFT is at least the length of STRING, copy STRING to
9582   *BUFFER, update *BUFFER to point to the new end of the buffer, and
9583   decrease *LEFT.  Otherwise raise an error.  */
9584
9585static void
9586remote_buffer_add_string (char **buffer, int *left, char *string)
9587{
9588  int len = strlen (string);
9589
9590  if (len > *left)
9591    error (_("Packet too long for target."));
9592
9593  memcpy (*buffer, string, len);
9594  *buffer += len;
9595  *left -= len;
9596
9597  /* NUL-terminate the buffer as a convenience, if there is
9598     room.  */
9599  if (*left)
9600    **buffer = '\0';
9601}
9602
9603/* If *LEFT is large enough, hex encode LEN bytes from BYTES into
9604   *BUFFER, update *BUFFER to point to the new end of the buffer, and
9605   decrease *LEFT.  Otherwise raise an error.  */
9606
9607static void
9608remote_buffer_add_bytes (char **buffer, int *left, const gdb_byte *bytes,
9609			 int len)
9610{
9611  if (2 * len > *left)
9612    error (_("Packet too long for target."));
9613
9614  bin2hex (bytes, *buffer, len);
9615  *buffer += 2 * len;
9616  *left -= 2 * len;
9617
9618  /* NUL-terminate the buffer as a convenience, if there is
9619     room.  */
9620  if (*left)
9621    **buffer = '\0';
9622}
9623
9624/* If *LEFT is large enough, convert VALUE to hex and add it to
9625   *BUFFER, update *BUFFER to point to the new end of the buffer, and
9626   decrease *LEFT.  Otherwise raise an error.  */
9627
9628static void
9629remote_buffer_add_int (char **buffer, int *left, ULONGEST value)
9630{
9631  int len = hexnumlen (value);
9632
9633  if (len > *left)
9634    error (_("Packet too long for target."));
9635
9636  hexnumstr (*buffer, value);
9637  *buffer += len;
9638  *left -= len;
9639
9640  /* NUL-terminate the buffer as a convenience, if there is
9641     room.  */
9642  if (*left)
9643    **buffer = '\0';
9644}
9645
9646/* Parse an I/O result packet from BUFFER.  Set RETCODE to the return
9647   value, *REMOTE_ERRNO to the remote error number or zero if none
9648   was included, and *ATTACHMENT to point to the start of the annex
9649   if any.  The length of the packet isn't needed here; there may
9650   be NUL bytes in BUFFER, but they will be after *ATTACHMENT.
9651
9652   Return 0 if the packet could be parsed, -1 if it could not.  If
9653   -1 is returned, the other variables may not be initialized.  */
9654
9655static int
9656remote_hostio_parse_result (char *buffer, int *retcode,
9657			    int *remote_errno, char **attachment)
9658{
9659  char *p, *p2;
9660
9661  *remote_errno = 0;
9662  *attachment = NULL;
9663
9664  if (buffer[0] != 'F')
9665    return -1;
9666
9667  errno = 0;
9668  *retcode = strtol (&buffer[1], &p, 16);
9669  if (errno != 0 || p == &buffer[1])
9670    return -1;
9671
9672  /* Check for ",errno".  */
9673  if (*p == ',')
9674    {
9675      errno = 0;
9676      *remote_errno = strtol (p + 1, &p2, 16);
9677      if (errno != 0 || p + 1 == p2)
9678	return -1;
9679      p = p2;
9680    }
9681
9682  /* Check for ";attachment".  If there is no attachment, the
9683     packet should end here.  */
9684  if (*p == ';')
9685    {
9686      *attachment = p + 1;
9687      return 0;
9688    }
9689  else if (*p == '\0')
9690    return 0;
9691  else
9692    return -1;
9693}
9694
9695/* Send a prepared I/O packet to the target and read its response.
9696   The prepared packet is in the global RS->BUF before this function
9697   is called, and the answer is there when we return.
9698
9699   COMMAND_BYTES is the length of the request to send, which may include
9700   binary data.  WHICH_PACKET is the packet configuration to check
9701   before attempting a packet.  If an error occurs, *REMOTE_ERRNO
9702   is set to the error number and -1 is returned.  Otherwise the value
9703   returned by the function is returned.
9704
9705   ATTACHMENT and ATTACHMENT_LEN should be non-NULL if and only if an
9706   attachment is expected; an error will be reported if there's a
9707   mismatch.  If one is found, *ATTACHMENT will be set to point into
9708   the packet buffer and *ATTACHMENT_LEN will be set to the
9709   attachment's length.  */
9710
9711static int
9712remote_hostio_send_command (int command_bytes, int which_packet,
9713			    int *remote_errno, char **attachment,
9714			    int *attachment_len)
9715{
9716  struct remote_state *rs = get_remote_state ();
9717  int ret, bytes_read;
9718  char *attachment_tmp;
9719
9720  if (!rs->remote_desc
9721      || packet_support (which_packet) == PACKET_DISABLE)
9722    {
9723      *remote_errno = FILEIO_ENOSYS;
9724      return -1;
9725    }
9726
9727  putpkt_binary (rs->buf, command_bytes);
9728  bytes_read = getpkt_sane (&rs->buf, &rs->buf_size, 0);
9729
9730  /* If it timed out, something is wrong.  Don't try to parse the
9731     buffer.  */
9732  if (bytes_read < 0)
9733    {
9734      *remote_errno = FILEIO_EINVAL;
9735      return -1;
9736    }
9737
9738  switch (packet_ok (rs->buf, &remote_protocol_packets[which_packet]))
9739    {
9740    case PACKET_ERROR:
9741      *remote_errno = FILEIO_EINVAL;
9742      return -1;
9743    case PACKET_UNKNOWN:
9744      *remote_errno = FILEIO_ENOSYS;
9745      return -1;
9746    case PACKET_OK:
9747      break;
9748    }
9749
9750  if (remote_hostio_parse_result (rs->buf, &ret, remote_errno,
9751				  &attachment_tmp))
9752    {
9753      *remote_errno = FILEIO_EINVAL;
9754      return -1;
9755    }
9756
9757  /* Make sure we saw an attachment if and only if we expected one.  */
9758  if ((attachment_tmp == NULL && attachment != NULL)
9759      || (attachment_tmp != NULL && attachment == NULL))
9760    {
9761      *remote_errno = FILEIO_EINVAL;
9762      return -1;
9763    }
9764
9765  /* If an attachment was found, it must point into the packet buffer;
9766     work out how many bytes there were.  */
9767  if (attachment_tmp != NULL)
9768    {
9769      *attachment = attachment_tmp;
9770      *attachment_len = bytes_read - (*attachment - rs->buf);
9771    }
9772
9773  return ret;
9774}
9775
9776/* Open FILENAME on the remote target, using FLAGS and MODE.  Return a
9777   remote file descriptor, or -1 if an error occurs (and set
9778   *REMOTE_ERRNO).  */
9779
9780static int
9781remote_hostio_open (struct target_ops *self,
9782		    const char *filename, int flags, int mode,
9783		    int *remote_errno)
9784{
9785  struct remote_state *rs = get_remote_state ();
9786  char *p = rs->buf;
9787  int left = get_remote_packet_size () - 1;
9788
9789  remote_buffer_add_string (&p, &left, "vFile:open:");
9790
9791  remote_buffer_add_bytes (&p, &left, (const gdb_byte *) filename,
9792			   strlen (filename));
9793  remote_buffer_add_string (&p, &left, ",");
9794
9795  remote_buffer_add_int (&p, &left, flags);
9796  remote_buffer_add_string (&p, &left, ",");
9797
9798  remote_buffer_add_int (&p, &left, mode);
9799
9800  return remote_hostio_send_command (p - rs->buf, PACKET_vFile_open,
9801				     remote_errno, NULL, NULL);
9802}
9803
9804/* Write up to LEN bytes from WRITE_BUF to FD on the remote target.
9805   Return the number of bytes written, or -1 if an error occurs (and
9806   set *REMOTE_ERRNO).  */
9807
9808static int
9809remote_hostio_pwrite (struct target_ops *self,
9810		      int fd, const gdb_byte *write_buf, int len,
9811		      ULONGEST offset, int *remote_errno)
9812{
9813  struct remote_state *rs = get_remote_state ();
9814  char *p = rs->buf;
9815  int left = get_remote_packet_size ();
9816  int out_len;
9817
9818  remote_buffer_add_string (&p, &left, "vFile:pwrite:");
9819
9820  remote_buffer_add_int (&p, &left, fd);
9821  remote_buffer_add_string (&p, &left, ",");
9822
9823  remote_buffer_add_int (&p, &left, offset);
9824  remote_buffer_add_string (&p, &left, ",");
9825
9826  p += remote_escape_output (write_buf, len, (gdb_byte *) p, &out_len,
9827			     get_remote_packet_size () - (p - rs->buf));
9828
9829  return remote_hostio_send_command (p - rs->buf, PACKET_vFile_pwrite,
9830				     remote_errno, NULL, NULL);
9831}
9832
9833/* Read up to LEN bytes FD on the remote target into READ_BUF
9834   Return the number of bytes read, or -1 if an error occurs (and
9835   set *REMOTE_ERRNO).  */
9836
9837static int
9838remote_hostio_pread (struct target_ops *self,
9839		     int fd, gdb_byte *read_buf, int len,
9840		     ULONGEST offset, int *remote_errno)
9841{
9842  struct remote_state *rs = get_remote_state ();
9843  char *p = rs->buf;
9844  char *attachment;
9845  int left = get_remote_packet_size ();
9846  int ret, attachment_len;
9847  int read_len;
9848
9849  remote_buffer_add_string (&p, &left, "vFile:pread:");
9850
9851  remote_buffer_add_int (&p, &left, fd);
9852  remote_buffer_add_string (&p, &left, ",");
9853
9854  remote_buffer_add_int (&p, &left, len);
9855  remote_buffer_add_string (&p, &left, ",");
9856
9857  remote_buffer_add_int (&p, &left, offset);
9858
9859  ret = remote_hostio_send_command (p - rs->buf, PACKET_vFile_pread,
9860				    remote_errno, &attachment,
9861				    &attachment_len);
9862
9863  if (ret < 0)
9864    return ret;
9865
9866  read_len = remote_unescape_input ((gdb_byte *) attachment, attachment_len,
9867				    read_buf, len);
9868  if (read_len != ret)
9869    error (_("Read returned %d, but %d bytes."), ret, (int) read_len);
9870
9871  return ret;
9872}
9873
9874/* Close FD on the remote target.  Return 0, or -1 if an error occurs
9875   (and set *REMOTE_ERRNO).  */
9876
9877static int
9878remote_hostio_close (struct target_ops *self, int fd, int *remote_errno)
9879{
9880  struct remote_state *rs = get_remote_state ();
9881  char *p = rs->buf;
9882  int left = get_remote_packet_size () - 1;
9883
9884  remote_buffer_add_string (&p, &left, "vFile:close:");
9885
9886  remote_buffer_add_int (&p, &left, fd);
9887
9888  return remote_hostio_send_command (p - rs->buf, PACKET_vFile_close,
9889				     remote_errno, NULL, NULL);
9890}
9891
9892/* Unlink FILENAME on the remote target.  Return 0, or -1 if an error
9893   occurs (and set *REMOTE_ERRNO).  */
9894
9895static int
9896remote_hostio_unlink (struct target_ops *self,
9897		      const char *filename, int *remote_errno)
9898{
9899  struct remote_state *rs = get_remote_state ();
9900  char *p = rs->buf;
9901  int left = get_remote_packet_size () - 1;
9902
9903  remote_buffer_add_string (&p, &left, "vFile:unlink:");
9904
9905  remote_buffer_add_bytes (&p, &left, (const gdb_byte *) filename,
9906			   strlen (filename));
9907
9908  return remote_hostio_send_command (p - rs->buf, PACKET_vFile_unlink,
9909				     remote_errno, NULL, NULL);
9910}
9911
9912/* Read value of symbolic link FILENAME on the remote target.  Return
9913   a null-terminated string allocated via xmalloc, or NULL if an error
9914   occurs (and set *REMOTE_ERRNO).  */
9915
9916static char *
9917remote_hostio_readlink (struct target_ops *self,
9918			const char *filename, int *remote_errno)
9919{
9920  struct remote_state *rs = get_remote_state ();
9921  char *p = rs->buf;
9922  char *attachment;
9923  int left = get_remote_packet_size ();
9924  int len, attachment_len;
9925  int read_len;
9926  char *ret;
9927
9928  remote_buffer_add_string (&p, &left, "vFile:readlink:");
9929
9930  remote_buffer_add_bytes (&p, &left, (const gdb_byte *) filename,
9931			   strlen (filename));
9932
9933  len = remote_hostio_send_command (p - rs->buf, PACKET_vFile_readlink,
9934				    remote_errno, &attachment,
9935				    &attachment_len);
9936
9937  if (len < 0)
9938    return NULL;
9939
9940  ret = xmalloc (len + 1);
9941
9942  read_len = remote_unescape_input ((gdb_byte *) attachment, attachment_len,
9943				    (gdb_byte *) ret, len);
9944  if (read_len != len)
9945    error (_("Readlink returned %d, but %d bytes."), len, read_len);
9946
9947  ret[len] = '\0';
9948  return ret;
9949}
9950
9951static int
9952remote_fileio_errno_to_host (int errnum)
9953{
9954  switch (errnum)
9955    {
9956      case FILEIO_EPERM:
9957        return EPERM;
9958      case FILEIO_ENOENT:
9959        return ENOENT;
9960      case FILEIO_EINTR:
9961        return EINTR;
9962      case FILEIO_EIO:
9963        return EIO;
9964      case FILEIO_EBADF:
9965        return EBADF;
9966      case FILEIO_EACCES:
9967        return EACCES;
9968      case FILEIO_EFAULT:
9969        return EFAULT;
9970      case FILEIO_EBUSY:
9971        return EBUSY;
9972      case FILEIO_EEXIST:
9973        return EEXIST;
9974      case FILEIO_ENODEV:
9975        return ENODEV;
9976      case FILEIO_ENOTDIR:
9977        return ENOTDIR;
9978      case FILEIO_EISDIR:
9979        return EISDIR;
9980      case FILEIO_EINVAL:
9981        return EINVAL;
9982      case FILEIO_ENFILE:
9983        return ENFILE;
9984      case FILEIO_EMFILE:
9985        return EMFILE;
9986      case FILEIO_EFBIG:
9987        return EFBIG;
9988      case FILEIO_ENOSPC:
9989        return ENOSPC;
9990      case FILEIO_ESPIPE:
9991        return ESPIPE;
9992      case FILEIO_EROFS:
9993        return EROFS;
9994      case FILEIO_ENOSYS:
9995        return ENOSYS;
9996      case FILEIO_ENAMETOOLONG:
9997        return ENAMETOOLONG;
9998    }
9999  return -1;
10000}
10001
10002static char *
10003remote_hostio_error (int errnum)
10004{
10005  int host_error = remote_fileio_errno_to_host (errnum);
10006
10007  if (host_error == -1)
10008    error (_("Unknown remote I/O error %d"), errnum);
10009  else
10010    error (_("Remote I/O error: %s"), safe_strerror (host_error));
10011}
10012
10013static void
10014remote_hostio_close_cleanup (void *opaque)
10015{
10016  int fd = *(int *) opaque;
10017  int remote_errno;
10018
10019  remote_hostio_close (find_target_at (process_stratum), fd, &remote_errno);
10020}
10021
10022
10023static void *
10024remote_bfd_iovec_open (struct bfd *abfd, void *open_closure)
10025{
10026  const char *filename = bfd_get_filename (abfd);
10027  int fd, remote_errno;
10028  int *stream;
10029
10030  gdb_assert (remote_filename_p (filename));
10031
10032  fd = remote_hostio_open (find_target_at (process_stratum),
10033			   filename + 7, FILEIO_O_RDONLY, 0, &remote_errno);
10034  if (fd == -1)
10035    {
10036      errno = remote_fileio_errno_to_host (remote_errno);
10037      bfd_set_error (bfd_error_system_call);
10038      return NULL;
10039    }
10040
10041  stream = xmalloc (sizeof (int));
10042  *stream = fd;
10043  return stream;
10044}
10045
10046static int
10047remote_bfd_iovec_close (struct bfd *abfd, void *stream)
10048{
10049  int fd = *(int *)stream;
10050  int remote_errno;
10051
10052  xfree (stream);
10053
10054  /* Ignore errors on close; these may happen if the remote
10055     connection was already torn down.  */
10056  remote_hostio_close (find_target_at (process_stratum), fd, &remote_errno);
10057
10058  /* Zero means success.  */
10059  return 0;
10060}
10061
10062static file_ptr
10063remote_bfd_iovec_pread (struct bfd *abfd, void *stream, void *buf,
10064			file_ptr nbytes, file_ptr offset)
10065{
10066  int fd = *(int *)stream;
10067  int remote_errno;
10068  file_ptr pos, bytes;
10069
10070  pos = 0;
10071  while (nbytes > pos)
10072    {
10073      bytes = remote_hostio_pread (find_target_at (process_stratum),
10074				   fd, (gdb_byte *) buf + pos, nbytes - pos,
10075				   offset + pos, &remote_errno);
10076      if (bytes == 0)
10077        /* Success, but no bytes, means end-of-file.  */
10078        break;
10079      if (bytes == -1)
10080	{
10081	  errno = remote_fileio_errno_to_host (remote_errno);
10082	  bfd_set_error (bfd_error_system_call);
10083	  return -1;
10084	}
10085
10086      pos += bytes;
10087    }
10088
10089  return pos;
10090}
10091
10092static int
10093remote_bfd_iovec_stat (struct bfd *abfd, void *stream, struct stat *sb)
10094{
10095  /* FIXME: We should probably implement remote_hostio_stat.  */
10096  sb->st_size = INT_MAX;
10097  return 0;
10098}
10099
10100int
10101remote_filename_p (const char *filename)
10102{
10103  return strncmp (filename,
10104		  REMOTE_SYSROOT_PREFIX,
10105		  sizeof (REMOTE_SYSROOT_PREFIX) - 1) == 0;
10106}
10107
10108bfd *
10109remote_bfd_open (const char *remote_file, const char *target)
10110{
10111  bfd *abfd = gdb_bfd_openr_iovec (remote_file, target,
10112				   remote_bfd_iovec_open, NULL,
10113				   remote_bfd_iovec_pread,
10114				   remote_bfd_iovec_close,
10115				   remote_bfd_iovec_stat);
10116
10117  return abfd;
10118}
10119
10120void
10121remote_file_put (const char *local_file, const char *remote_file, int from_tty)
10122{
10123  struct cleanup *back_to, *close_cleanup;
10124  int retcode, fd, remote_errno, bytes, io_size;
10125  FILE *file;
10126  gdb_byte *buffer;
10127  int bytes_in_buffer;
10128  int saw_eof;
10129  ULONGEST offset;
10130  struct remote_state *rs = get_remote_state ();
10131
10132  if (!rs->remote_desc)
10133    error (_("command can only be used with remote target"));
10134
10135  file = gdb_fopen_cloexec (local_file, "rb");
10136  if (file == NULL)
10137    perror_with_name (local_file);
10138  back_to = make_cleanup_fclose (file);
10139
10140  fd = remote_hostio_open (find_target_at (process_stratum),
10141			   remote_file, (FILEIO_O_WRONLY | FILEIO_O_CREAT
10142					 | FILEIO_O_TRUNC),
10143			   0700, &remote_errno);
10144  if (fd == -1)
10145    remote_hostio_error (remote_errno);
10146
10147  /* Send up to this many bytes at once.  They won't all fit in the
10148     remote packet limit, so we'll transfer slightly fewer.  */
10149  io_size = get_remote_packet_size ();
10150  buffer = xmalloc (io_size);
10151  make_cleanup (xfree, buffer);
10152
10153  close_cleanup = make_cleanup (remote_hostio_close_cleanup, &fd);
10154
10155  bytes_in_buffer = 0;
10156  saw_eof = 0;
10157  offset = 0;
10158  while (bytes_in_buffer || !saw_eof)
10159    {
10160      if (!saw_eof)
10161	{
10162	  bytes = fread (buffer + bytes_in_buffer, 1,
10163			 io_size - bytes_in_buffer,
10164			 file);
10165	  if (bytes == 0)
10166	    {
10167	      if (ferror (file))
10168		error (_("Error reading %s."), local_file);
10169	      else
10170		{
10171		  /* EOF.  Unless there is something still in the
10172		     buffer from the last iteration, we are done.  */
10173		  saw_eof = 1;
10174		  if (bytes_in_buffer == 0)
10175		    break;
10176		}
10177	    }
10178	}
10179      else
10180	bytes = 0;
10181
10182      bytes += bytes_in_buffer;
10183      bytes_in_buffer = 0;
10184
10185      retcode = remote_hostio_pwrite (find_target_at (process_stratum),
10186				      fd, buffer, bytes,
10187				      offset, &remote_errno);
10188
10189      if (retcode < 0)
10190	remote_hostio_error (remote_errno);
10191      else if (retcode == 0)
10192	error (_("Remote write of %d bytes returned 0!"), bytes);
10193      else if (retcode < bytes)
10194	{
10195	  /* Short write.  Save the rest of the read data for the next
10196	     write.  */
10197	  bytes_in_buffer = bytes - retcode;
10198	  memmove (buffer, buffer + retcode, bytes_in_buffer);
10199	}
10200
10201      offset += retcode;
10202    }
10203
10204  discard_cleanups (close_cleanup);
10205  if (remote_hostio_close (find_target_at (process_stratum), fd, &remote_errno))
10206    remote_hostio_error (remote_errno);
10207
10208  if (from_tty)
10209    printf_filtered (_("Successfully sent file \"%s\".\n"), local_file);
10210  do_cleanups (back_to);
10211}
10212
10213void
10214remote_file_get (const char *remote_file, const char *local_file, int from_tty)
10215{
10216  struct cleanup *back_to, *close_cleanup;
10217  int fd, remote_errno, bytes, io_size;
10218  FILE *file;
10219  gdb_byte *buffer;
10220  ULONGEST offset;
10221  struct remote_state *rs = get_remote_state ();
10222
10223  if (!rs->remote_desc)
10224    error (_("command can only be used with remote target"));
10225
10226  fd = remote_hostio_open (find_target_at (process_stratum),
10227			   remote_file, FILEIO_O_RDONLY, 0, &remote_errno);
10228  if (fd == -1)
10229    remote_hostio_error (remote_errno);
10230
10231  file = gdb_fopen_cloexec (local_file, "wb");
10232  if (file == NULL)
10233    perror_with_name (local_file);
10234  back_to = make_cleanup_fclose (file);
10235
10236  /* Send up to this many bytes at once.  They won't all fit in the
10237     remote packet limit, so we'll transfer slightly fewer.  */
10238  io_size = get_remote_packet_size ();
10239  buffer = xmalloc (io_size);
10240  make_cleanup (xfree, buffer);
10241
10242  close_cleanup = make_cleanup (remote_hostio_close_cleanup, &fd);
10243
10244  offset = 0;
10245  while (1)
10246    {
10247      bytes = remote_hostio_pread (find_target_at (process_stratum),
10248				   fd, buffer, io_size, offset, &remote_errno);
10249      if (bytes == 0)
10250	/* Success, but no bytes, means end-of-file.  */
10251	break;
10252      if (bytes == -1)
10253	remote_hostio_error (remote_errno);
10254
10255      offset += bytes;
10256
10257      bytes = fwrite (buffer, 1, bytes, file);
10258      if (bytes == 0)
10259	perror_with_name (local_file);
10260    }
10261
10262  discard_cleanups (close_cleanup);
10263  if (remote_hostio_close (find_target_at (process_stratum), fd, &remote_errno))
10264    remote_hostio_error (remote_errno);
10265
10266  if (from_tty)
10267    printf_filtered (_("Successfully fetched file \"%s\".\n"), remote_file);
10268  do_cleanups (back_to);
10269}
10270
10271void
10272remote_file_delete (const char *remote_file, int from_tty)
10273{
10274  int retcode, remote_errno;
10275  struct remote_state *rs = get_remote_state ();
10276
10277  if (!rs->remote_desc)
10278    error (_("command can only be used with remote target"));
10279
10280  retcode = remote_hostio_unlink (find_target_at (process_stratum),
10281				  remote_file, &remote_errno);
10282  if (retcode == -1)
10283    remote_hostio_error (remote_errno);
10284
10285  if (from_tty)
10286    printf_filtered (_("Successfully deleted file \"%s\".\n"), remote_file);
10287}
10288
10289static void
10290remote_put_command (char *args, int from_tty)
10291{
10292  struct cleanup *back_to;
10293  char **argv;
10294
10295  if (args == NULL)
10296    error_no_arg (_("file to put"));
10297
10298  argv = gdb_buildargv (args);
10299  back_to = make_cleanup_freeargv (argv);
10300  if (argv[0] == NULL || argv[1] == NULL || argv[2] != NULL)
10301    error (_("Invalid parameters to remote put"));
10302
10303  remote_file_put (argv[0], argv[1], from_tty);
10304
10305  do_cleanups (back_to);
10306}
10307
10308static void
10309remote_get_command (char *args, int from_tty)
10310{
10311  struct cleanup *back_to;
10312  char **argv;
10313
10314  if (args == NULL)
10315    error_no_arg (_("file to get"));
10316
10317  argv = gdb_buildargv (args);
10318  back_to = make_cleanup_freeargv (argv);
10319  if (argv[0] == NULL || argv[1] == NULL || argv[2] != NULL)
10320    error (_("Invalid parameters to remote get"));
10321
10322  remote_file_get (argv[0], argv[1], from_tty);
10323
10324  do_cleanups (back_to);
10325}
10326
10327static void
10328remote_delete_command (char *args, int from_tty)
10329{
10330  struct cleanup *back_to;
10331  char **argv;
10332
10333  if (args == NULL)
10334    error_no_arg (_("file to delete"));
10335
10336  argv = gdb_buildargv (args);
10337  back_to = make_cleanup_freeargv (argv);
10338  if (argv[0] == NULL || argv[1] != NULL)
10339    error (_("Invalid parameters to remote delete"));
10340
10341  remote_file_delete (argv[0], from_tty);
10342
10343  do_cleanups (back_to);
10344}
10345
10346static void
10347remote_command (char *args, int from_tty)
10348{
10349  help_list (remote_cmdlist, "remote ", all_commands, gdb_stdout);
10350}
10351
10352static int
10353remote_can_execute_reverse (struct target_ops *self)
10354{
10355  if (packet_support (PACKET_bs) == PACKET_ENABLE
10356      || packet_support (PACKET_bc) == PACKET_ENABLE)
10357    return 1;
10358  else
10359    return 0;
10360}
10361
10362static int
10363remote_supports_non_stop (struct target_ops *self)
10364{
10365  return 1;
10366}
10367
10368static int
10369remote_supports_disable_randomization (struct target_ops *self)
10370{
10371  /* Only supported in extended mode.  */
10372  return 0;
10373}
10374
10375static int
10376remote_supports_multi_process (struct target_ops *self)
10377{
10378  struct remote_state *rs = get_remote_state ();
10379
10380  /* Only extended-remote handles being attached to multiple
10381     processes, even though plain remote can use the multi-process
10382     thread id extensions, so that GDB knows the target process's
10383     PID.  */
10384  return rs->extended && remote_multi_process_p (rs);
10385}
10386
10387static int
10388remote_supports_cond_tracepoints (void)
10389{
10390  return packet_support (PACKET_ConditionalTracepoints) == PACKET_ENABLE;
10391}
10392
10393static int
10394remote_supports_cond_breakpoints (struct target_ops *self)
10395{
10396  return packet_support (PACKET_ConditionalBreakpoints) == PACKET_ENABLE;
10397}
10398
10399static int
10400remote_supports_fast_tracepoints (void)
10401{
10402  return packet_support (PACKET_FastTracepoints) == PACKET_ENABLE;
10403}
10404
10405static int
10406remote_supports_static_tracepoints (void)
10407{
10408  return packet_support (PACKET_StaticTracepoints) == PACKET_ENABLE;
10409}
10410
10411static int
10412remote_supports_install_in_trace (void)
10413{
10414  return packet_support (PACKET_InstallInTrace) == PACKET_ENABLE;
10415}
10416
10417static int
10418remote_supports_enable_disable_tracepoint (struct target_ops *self)
10419{
10420  return (packet_support (PACKET_EnableDisableTracepoints_feature)
10421	  == PACKET_ENABLE);
10422}
10423
10424static int
10425remote_supports_string_tracing (struct target_ops *self)
10426{
10427  return packet_support (PACKET_tracenz_feature) == PACKET_ENABLE;
10428}
10429
10430static int
10431remote_can_run_breakpoint_commands (struct target_ops *self)
10432{
10433  return packet_support (PACKET_BreakpointCommands) == PACKET_ENABLE;
10434}
10435
10436static void
10437remote_trace_init (struct target_ops *self)
10438{
10439  putpkt ("QTinit");
10440  remote_get_noisy_reply (&target_buf, &target_buf_size);
10441  if (strcmp (target_buf, "OK") != 0)
10442    error (_("Target does not support this command."));
10443}
10444
10445static void free_actions_list (char **actions_list);
10446static void free_actions_list_cleanup_wrapper (void *);
10447static void
10448free_actions_list_cleanup_wrapper (void *al)
10449{
10450  free_actions_list (al);
10451}
10452
10453static void
10454free_actions_list (char **actions_list)
10455{
10456  int ndx;
10457
10458  if (actions_list == 0)
10459    return;
10460
10461  for (ndx = 0; actions_list[ndx]; ndx++)
10462    xfree (actions_list[ndx]);
10463
10464  xfree (actions_list);
10465}
10466
10467/* Recursive routine to walk through command list including loops, and
10468   download packets for each command.  */
10469
10470static void
10471remote_download_command_source (int num, ULONGEST addr,
10472				struct command_line *cmds)
10473{
10474  struct remote_state *rs = get_remote_state ();
10475  struct command_line *cmd;
10476
10477  for (cmd = cmds; cmd; cmd = cmd->next)
10478    {
10479      QUIT;	/* Allow user to bail out with ^C.  */
10480      strcpy (rs->buf, "QTDPsrc:");
10481      encode_source_string (num, addr, "cmd", cmd->line,
10482			    rs->buf + strlen (rs->buf),
10483			    rs->buf_size - strlen (rs->buf));
10484      putpkt (rs->buf);
10485      remote_get_noisy_reply (&target_buf, &target_buf_size);
10486      if (strcmp (target_buf, "OK"))
10487	warning (_("Target does not support source download."));
10488
10489      if (cmd->control_type == while_control
10490	  || cmd->control_type == while_stepping_control)
10491	{
10492	  remote_download_command_source (num, addr, *cmd->body_list);
10493
10494	  QUIT;	/* Allow user to bail out with ^C.  */
10495	  strcpy (rs->buf, "QTDPsrc:");
10496	  encode_source_string (num, addr, "cmd", "end",
10497				rs->buf + strlen (rs->buf),
10498				rs->buf_size - strlen (rs->buf));
10499	  putpkt (rs->buf);
10500	  remote_get_noisy_reply (&target_buf, &target_buf_size);
10501	  if (strcmp (target_buf, "OK"))
10502	    warning (_("Target does not support source download."));
10503	}
10504    }
10505}
10506
10507static void
10508remote_download_tracepoint (struct target_ops *self, struct bp_location *loc)
10509{
10510#define BUF_SIZE 2048
10511
10512  CORE_ADDR tpaddr;
10513  char addrbuf[40];
10514  char buf[BUF_SIZE];
10515  char **tdp_actions;
10516  char **stepping_actions;
10517  int ndx;
10518  struct cleanup *old_chain = NULL;
10519  struct agent_expr *aexpr;
10520  struct cleanup *aexpr_chain = NULL;
10521  char *pkt;
10522  struct breakpoint *b = loc->owner;
10523  struct tracepoint *t = (struct tracepoint *) b;
10524
10525  encode_actions_rsp (loc, &tdp_actions, &stepping_actions);
10526  old_chain = make_cleanup (free_actions_list_cleanup_wrapper,
10527			    tdp_actions);
10528  (void) make_cleanup (free_actions_list_cleanup_wrapper,
10529		       stepping_actions);
10530
10531  tpaddr = loc->address;
10532  sprintf_vma (addrbuf, tpaddr);
10533  xsnprintf (buf, BUF_SIZE, "QTDP:%x:%s:%c:%lx:%x", b->number,
10534	     addrbuf, /* address */
10535	     (b->enable_state == bp_enabled ? 'E' : 'D'),
10536	     t->step_count, t->pass_count);
10537  /* Fast tracepoints are mostly handled by the target, but we can
10538     tell the target how big of an instruction block should be moved
10539     around.  */
10540  if (b->type == bp_fast_tracepoint)
10541    {
10542      /* Only test for support at download time; we may not know
10543	 target capabilities at definition time.  */
10544      if (remote_supports_fast_tracepoints ())
10545	{
10546	  int isize;
10547
10548	  if (gdbarch_fast_tracepoint_valid_at (target_gdbarch (),
10549						tpaddr, &isize, NULL))
10550	    xsnprintf (buf + strlen (buf), BUF_SIZE - strlen (buf), ":F%x",
10551		       isize);
10552	  else
10553	    /* If it passed validation at definition but fails now,
10554	       something is very wrong.  */
10555	    internal_error (__FILE__, __LINE__,
10556			    _("Fast tracepoint not "
10557			      "valid during download"));
10558	}
10559      else
10560	/* Fast tracepoints are functionally identical to regular
10561	   tracepoints, so don't take lack of support as a reason to
10562	   give up on the trace run.  */
10563	warning (_("Target does not support fast tracepoints, "
10564		   "downloading %d as regular tracepoint"), b->number);
10565    }
10566  else if (b->type == bp_static_tracepoint)
10567    {
10568      /* Only test for support at download time; we may not know
10569	 target capabilities at definition time.  */
10570      if (remote_supports_static_tracepoints ())
10571	{
10572	  struct static_tracepoint_marker marker;
10573
10574	  if (target_static_tracepoint_marker_at (tpaddr, &marker))
10575	    strcat (buf, ":S");
10576	  else
10577	    error (_("Static tracepoint not valid during download"));
10578	}
10579      else
10580	/* Fast tracepoints are functionally identical to regular
10581	   tracepoints, so don't take lack of support as a reason
10582	   to give up on the trace run.  */
10583	error (_("Target does not support static tracepoints"));
10584    }
10585  /* If the tracepoint has a conditional, make it into an agent
10586     expression and append to the definition.  */
10587  if (loc->cond)
10588    {
10589      /* Only test support at download time, we may not know target
10590	 capabilities at definition time.  */
10591      if (remote_supports_cond_tracepoints ())
10592	{
10593	  aexpr = gen_eval_for_expr (tpaddr, loc->cond);
10594	  aexpr_chain = make_cleanup_free_agent_expr (aexpr);
10595	  xsnprintf (buf + strlen (buf), BUF_SIZE - strlen (buf), ":X%x,",
10596		     aexpr->len);
10597	  pkt = buf + strlen (buf);
10598	  for (ndx = 0; ndx < aexpr->len; ++ndx)
10599	    pkt = pack_hex_byte (pkt, aexpr->buf[ndx]);
10600	  *pkt = '\0';
10601	  do_cleanups (aexpr_chain);
10602	}
10603      else
10604	warning (_("Target does not support conditional tracepoints, "
10605		   "ignoring tp %d cond"), b->number);
10606    }
10607
10608  if (b->commands || *default_collect)
10609    strcat (buf, "-");
10610  putpkt (buf);
10611  remote_get_noisy_reply (&target_buf, &target_buf_size);
10612  if (strcmp (target_buf, "OK"))
10613    error (_("Target does not support tracepoints."));
10614
10615  /* do_single_steps (t); */
10616  if (tdp_actions)
10617    {
10618      for (ndx = 0; tdp_actions[ndx]; ndx++)
10619	{
10620	  QUIT;	/* Allow user to bail out with ^C.  */
10621	  xsnprintf (buf, BUF_SIZE, "QTDP:-%x:%s:%s%c",
10622		     b->number, addrbuf, /* address */
10623		     tdp_actions[ndx],
10624		     ((tdp_actions[ndx + 1] || stepping_actions)
10625		      ? '-' : 0));
10626	  putpkt (buf);
10627	  remote_get_noisy_reply (&target_buf,
10628				  &target_buf_size);
10629	  if (strcmp (target_buf, "OK"))
10630	    error (_("Error on target while setting tracepoints."));
10631	}
10632    }
10633  if (stepping_actions)
10634    {
10635      for (ndx = 0; stepping_actions[ndx]; ndx++)
10636	{
10637	  QUIT;	/* Allow user to bail out with ^C.  */
10638	  xsnprintf (buf, BUF_SIZE, "QTDP:-%x:%s:%s%s%s",
10639		     b->number, addrbuf, /* address */
10640		     ((ndx == 0) ? "S" : ""),
10641		     stepping_actions[ndx],
10642		     (stepping_actions[ndx + 1] ? "-" : ""));
10643	  putpkt (buf);
10644	  remote_get_noisy_reply (&target_buf,
10645				  &target_buf_size);
10646	  if (strcmp (target_buf, "OK"))
10647	    error (_("Error on target while setting tracepoints."));
10648	}
10649    }
10650
10651  if (packet_support (PACKET_TracepointSource) == PACKET_ENABLE)
10652    {
10653      if (b->addr_string)
10654	{
10655	  strcpy (buf, "QTDPsrc:");
10656	  encode_source_string (b->number, loc->address,
10657				"at", b->addr_string, buf + strlen (buf),
10658				2048 - strlen (buf));
10659
10660	  putpkt (buf);
10661	  remote_get_noisy_reply (&target_buf, &target_buf_size);
10662	  if (strcmp (target_buf, "OK"))
10663	    warning (_("Target does not support source download."));
10664	}
10665      if (b->cond_string)
10666	{
10667	  strcpy (buf, "QTDPsrc:");
10668	  encode_source_string (b->number, loc->address,
10669				"cond", b->cond_string, buf + strlen (buf),
10670				2048 - strlen (buf));
10671	  putpkt (buf);
10672	  remote_get_noisy_reply (&target_buf, &target_buf_size);
10673	  if (strcmp (target_buf, "OK"))
10674	    warning (_("Target does not support source download."));
10675	}
10676      remote_download_command_source (b->number, loc->address,
10677				      breakpoint_commands (b));
10678    }
10679
10680  do_cleanups (old_chain);
10681}
10682
10683static int
10684remote_can_download_tracepoint (struct target_ops *self)
10685{
10686  struct remote_state *rs = get_remote_state ();
10687  struct trace_status *ts;
10688  int status;
10689
10690  /* Don't try to install tracepoints until we've relocated our
10691     symbols, and fetched and merged the target's tracepoint list with
10692     ours.  */
10693  if (rs->starting_up)
10694    return 0;
10695
10696  ts = current_trace_status ();
10697  status = remote_get_trace_status (self, ts);
10698
10699  if (status == -1 || !ts->running_known || !ts->running)
10700    return 0;
10701
10702  /* If we are in a tracing experiment, but remote stub doesn't support
10703     installing tracepoint in trace, we have to return.  */
10704  if (!remote_supports_install_in_trace ())
10705    return 0;
10706
10707  return 1;
10708}
10709
10710
10711static void
10712remote_download_trace_state_variable (struct target_ops *self,
10713				      struct trace_state_variable *tsv)
10714{
10715  struct remote_state *rs = get_remote_state ();
10716  char *p;
10717
10718  xsnprintf (rs->buf, get_remote_packet_size (), "QTDV:%x:%s:%x:",
10719	     tsv->number, phex ((ULONGEST) tsv->initial_value, 8),
10720	     tsv->builtin);
10721  p = rs->buf + strlen (rs->buf);
10722  if ((p - rs->buf) + strlen (tsv->name) * 2 >= get_remote_packet_size ())
10723    error (_("Trace state variable name too long for tsv definition packet"));
10724  p += 2 * bin2hex ((gdb_byte *) (tsv->name), p, strlen (tsv->name));
10725  *p++ = '\0';
10726  putpkt (rs->buf);
10727  remote_get_noisy_reply (&target_buf, &target_buf_size);
10728  if (*target_buf == '\0')
10729    error (_("Target does not support this command."));
10730  if (strcmp (target_buf, "OK") != 0)
10731    error (_("Error on target while downloading trace state variable."));
10732}
10733
10734static void
10735remote_enable_tracepoint (struct target_ops *self,
10736			  struct bp_location *location)
10737{
10738  struct remote_state *rs = get_remote_state ();
10739  char addr_buf[40];
10740
10741  sprintf_vma (addr_buf, location->address);
10742  xsnprintf (rs->buf, get_remote_packet_size (), "QTEnable:%x:%s",
10743	     location->owner->number, addr_buf);
10744  putpkt (rs->buf);
10745  remote_get_noisy_reply (&rs->buf, &rs->buf_size);
10746  if (*rs->buf == '\0')
10747    error (_("Target does not support enabling tracepoints while a trace run is ongoing."));
10748  if (strcmp (rs->buf, "OK") != 0)
10749    error (_("Error on target while enabling tracepoint."));
10750}
10751
10752static void
10753remote_disable_tracepoint (struct target_ops *self,
10754			   struct bp_location *location)
10755{
10756  struct remote_state *rs = get_remote_state ();
10757  char addr_buf[40];
10758
10759  sprintf_vma (addr_buf, location->address);
10760  xsnprintf (rs->buf, get_remote_packet_size (), "QTDisable:%x:%s",
10761	     location->owner->number, addr_buf);
10762  putpkt (rs->buf);
10763  remote_get_noisy_reply (&rs->buf, &rs->buf_size);
10764  if (*rs->buf == '\0')
10765    error (_("Target does not support disabling tracepoints while a trace run is ongoing."));
10766  if (strcmp (rs->buf, "OK") != 0)
10767    error (_("Error on target while disabling tracepoint."));
10768}
10769
10770static void
10771remote_trace_set_readonly_regions (struct target_ops *self)
10772{
10773  asection *s;
10774  bfd *abfd = NULL;
10775  bfd_size_type size;
10776  bfd_vma vma;
10777  int anysecs = 0;
10778  int offset = 0;
10779
10780  if (!exec_bfd)
10781    return;			/* No information to give.  */
10782
10783  strcpy (target_buf, "QTro");
10784  offset = strlen (target_buf);
10785  for (s = exec_bfd->sections; s; s = s->next)
10786    {
10787      char tmp1[40], tmp2[40];
10788      int sec_length;
10789
10790      if ((s->flags & SEC_LOAD) == 0 ||
10791      /*  (s->flags & SEC_CODE) == 0 || */
10792	  (s->flags & SEC_READONLY) == 0)
10793	continue;
10794
10795      anysecs = 1;
10796      vma = bfd_get_section_vma (abfd, s);
10797      size = bfd_get_section_size (s);
10798      sprintf_vma (tmp1, vma);
10799      sprintf_vma (tmp2, vma + size);
10800      sec_length = 1 + strlen (tmp1) + 1 + strlen (tmp2);
10801      if (offset + sec_length + 1 > target_buf_size)
10802	{
10803	  if (packet_support (PACKET_qXfer_traceframe_info) != PACKET_ENABLE)
10804	    warning (_("\
10805Too many sections for read-only sections definition packet."));
10806	  break;
10807	}
10808      xsnprintf (target_buf + offset, target_buf_size - offset, ":%s,%s",
10809		 tmp1, tmp2);
10810      offset += sec_length;
10811    }
10812  if (anysecs)
10813    {
10814      putpkt (target_buf);
10815      getpkt (&target_buf, &target_buf_size, 0);
10816    }
10817}
10818
10819static void
10820remote_trace_start (struct target_ops *self)
10821{
10822  putpkt ("QTStart");
10823  remote_get_noisy_reply (&target_buf, &target_buf_size);
10824  if (*target_buf == '\0')
10825    error (_("Target does not support this command."));
10826  if (strcmp (target_buf, "OK") != 0)
10827    error (_("Bogus reply from target: %s"), target_buf);
10828}
10829
10830static int
10831remote_get_trace_status (struct target_ops *self, struct trace_status *ts)
10832{
10833  /* Initialize it just to avoid a GCC false warning.  */
10834  char *p = NULL;
10835  /* FIXME we need to get register block size some other way.  */
10836  extern int trace_regblock_size;
10837  volatile struct gdb_exception ex;
10838  enum packet_result result;
10839
10840  if (packet_support (PACKET_qTStatus) == PACKET_DISABLE)
10841    return -1;
10842
10843  trace_regblock_size = get_remote_arch_state ()->sizeof_g_packet;
10844
10845  putpkt ("qTStatus");
10846
10847  TRY_CATCH (ex, RETURN_MASK_ERROR)
10848    {
10849      p = remote_get_noisy_reply (&target_buf, &target_buf_size);
10850    }
10851  if (ex.reason < 0)
10852    {
10853      if (ex.error != TARGET_CLOSE_ERROR)
10854	{
10855	  exception_fprintf (gdb_stderr, ex, "qTStatus: ");
10856	  return -1;
10857	}
10858      throw_exception (ex);
10859    }
10860
10861  result = packet_ok (p, &remote_protocol_packets[PACKET_qTStatus]);
10862
10863  /* If the remote target doesn't do tracing, flag it.  */
10864  if (result == PACKET_UNKNOWN)
10865    return -1;
10866
10867  /* We're working with a live target.  */
10868  ts->filename = NULL;
10869
10870  if (*p++ != 'T')
10871    error (_("Bogus trace status reply from target: %s"), target_buf);
10872
10873  /* Function 'parse_trace_status' sets default value of each field of
10874     'ts' at first, so we don't have to do it here.  */
10875  parse_trace_status (p, ts);
10876
10877  return ts->running;
10878}
10879
10880static void
10881remote_get_tracepoint_status (struct target_ops *self, struct breakpoint *bp,
10882			      struct uploaded_tp *utp)
10883{
10884  struct remote_state *rs = get_remote_state ();
10885  char *reply;
10886  struct bp_location *loc;
10887  struct tracepoint *tp = (struct tracepoint *) bp;
10888  size_t size = get_remote_packet_size ();
10889
10890  if (tp)
10891    {
10892      tp->base.hit_count = 0;
10893      tp->traceframe_usage = 0;
10894      for (loc = tp->base.loc; loc; loc = loc->next)
10895	{
10896	  /* If the tracepoint was never downloaded, don't go asking for
10897	     any status.  */
10898	  if (tp->number_on_target == 0)
10899	    continue;
10900	  xsnprintf (rs->buf, size, "qTP:%x:%s", tp->number_on_target,
10901		     phex_nz (loc->address, 0));
10902	  putpkt (rs->buf);
10903	  reply = remote_get_noisy_reply (&target_buf, &target_buf_size);
10904	  if (reply && *reply)
10905	    {
10906	      if (*reply == 'V')
10907		parse_tracepoint_status (reply + 1, bp, utp);
10908	    }
10909	}
10910    }
10911  else if (utp)
10912    {
10913      utp->hit_count = 0;
10914      utp->traceframe_usage = 0;
10915      xsnprintf (rs->buf, size, "qTP:%x:%s", utp->number,
10916		 phex_nz (utp->addr, 0));
10917      putpkt (rs->buf);
10918      reply = remote_get_noisy_reply (&target_buf, &target_buf_size);
10919      if (reply && *reply)
10920	{
10921	  if (*reply == 'V')
10922	    parse_tracepoint_status (reply + 1, bp, utp);
10923	}
10924    }
10925}
10926
10927static void
10928remote_trace_stop (struct target_ops *self)
10929{
10930  putpkt ("QTStop");
10931  remote_get_noisy_reply (&target_buf, &target_buf_size);
10932  if (*target_buf == '\0')
10933    error (_("Target does not support this command."));
10934  if (strcmp (target_buf, "OK") != 0)
10935    error (_("Bogus reply from target: %s"), target_buf);
10936}
10937
10938static int
10939remote_trace_find (struct target_ops *self,
10940		   enum trace_find_type type, int num,
10941		   CORE_ADDR addr1, CORE_ADDR addr2,
10942		   int *tpp)
10943{
10944  struct remote_state *rs = get_remote_state ();
10945  char *endbuf = rs->buf + get_remote_packet_size ();
10946  char *p, *reply;
10947  int target_frameno = -1, target_tracept = -1;
10948
10949  /* Lookups other than by absolute frame number depend on the current
10950     trace selected, so make sure it is correct on the remote end
10951     first.  */
10952  if (type != tfind_number)
10953    set_remote_traceframe ();
10954
10955  p = rs->buf;
10956  strcpy (p, "QTFrame:");
10957  p = strchr (p, '\0');
10958  switch (type)
10959    {
10960    case tfind_number:
10961      xsnprintf (p, endbuf - p, "%x", num);
10962      break;
10963    case tfind_pc:
10964      xsnprintf (p, endbuf - p, "pc:%s", phex_nz (addr1, 0));
10965      break;
10966    case tfind_tp:
10967      xsnprintf (p, endbuf - p, "tdp:%x", num);
10968      break;
10969    case tfind_range:
10970      xsnprintf (p, endbuf - p, "range:%s:%s", phex_nz (addr1, 0),
10971		 phex_nz (addr2, 0));
10972      break;
10973    case tfind_outside:
10974      xsnprintf (p, endbuf - p, "outside:%s:%s", phex_nz (addr1, 0),
10975		 phex_nz (addr2, 0));
10976      break;
10977    default:
10978      error (_("Unknown trace find type %d"), type);
10979    }
10980
10981  putpkt (rs->buf);
10982  reply = remote_get_noisy_reply (&(rs->buf), &rs->buf_size);
10983  if (*reply == '\0')
10984    error (_("Target does not support this command."));
10985
10986  while (reply && *reply)
10987    switch (*reply)
10988      {
10989      case 'F':
10990	p = ++reply;
10991	target_frameno = (int) strtol (p, &reply, 16);
10992	if (reply == p)
10993	  error (_("Unable to parse trace frame number"));
10994	/* Don't update our remote traceframe number cache on failure
10995	   to select a remote traceframe.  */
10996	if (target_frameno == -1)
10997	  return -1;
10998	break;
10999      case 'T':
11000	p = ++reply;
11001	target_tracept = (int) strtol (p, &reply, 16);
11002	if (reply == p)
11003	  error (_("Unable to parse tracepoint number"));
11004	break;
11005      case 'O':		/* "OK"? */
11006	if (reply[1] == 'K' && reply[2] == '\0')
11007	  reply += 2;
11008	else
11009	  error (_("Bogus reply from target: %s"), reply);
11010	break;
11011      default:
11012	error (_("Bogus reply from target: %s"), reply);
11013      }
11014  if (tpp)
11015    *tpp = target_tracept;
11016
11017  rs->remote_traceframe_number = target_frameno;
11018  return target_frameno;
11019}
11020
11021static int
11022remote_get_trace_state_variable_value (struct target_ops *self,
11023				       int tsvnum, LONGEST *val)
11024{
11025  struct remote_state *rs = get_remote_state ();
11026  char *reply;
11027  ULONGEST uval;
11028
11029  set_remote_traceframe ();
11030
11031  xsnprintf (rs->buf, get_remote_packet_size (), "qTV:%x", tsvnum);
11032  putpkt (rs->buf);
11033  reply = remote_get_noisy_reply (&target_buf, &target_buf_size);
11034  if (reply && *reply)
11035    {
11036      if (*reply == 'V')
11037	{
11038	  unpack_varlen_hex (reply + 1, &uval);
11039	  *val = (LONGEST) uval;
11040	  return 1;
11041	}
11042    }
11043  return 0;
11044}
11045
11046static int
11047remote_save_trace_data (struct target_ops *self, const char *filename)
11048{
11049  struct remote_state *rs = get_remote_state ();
11050  char *p, *reply;
11051
11052  p = rs->buf;
11053  strcpy (p, "QTSave:");
11054  p += strlen (p);
11055  if ((p - rs->buf) + strlen (filename) * 2 >= get_remote_packet_size ())
11056    error (_("Remote file name too long for trace save packet"));
11057  p += 2 * bin2hex ((gdb_byte *) filename, p, strlen (filename));
11058  *p++ = '\0';
11059  putpkt (rs->buf);
11060  reply = remote_get_noisy_reply (&target_buf, &target_buf_size);
11061  if (*reply == '\0')
11062    error (_("Target does not support this command."));
11063  if (strcmp (reply, "OK") != 0)
11064    error (_("Bogus reply from target: %s"), reply);
11065  return 0;
11066}
11067
11068/* This is basically a memory transfer, but needs to be its own packet
11069   because we don't know how the target actually organizes its trace
11070   memory, plus we want to be able to ask for as much as possible, but
11071   not be unhappy if we don't get as much as we ask for.  */
11072
11073static LONGEST
11074remote_get_raw_trace_data (struct target_ops *self,
11075			   gdb_byte *buf, ULONGEST offset, LONGEST len)
11076{
11077  struct remote_state *rs = get_remote_state ();
11078  char *reply;
11079  char *p;
11080  int rslt;
11081
11082  p = rs->buf;
11083  strcpy (p, "qTBuffer:");
11084  p += strlen (p);
11085  p += hexnumstr (p, offset);
11086  *p++ = ',';
11087  p += hexnumstr (p, len);
11088  *p++ = '\0';
11089
11090  putpkt (rs->buf);
11091  reply = remote_get_noisy_reply (&target_buf, &target_buf_size);
11092  if (reply && *reply)
11093    {
11094      /* 'l' by itself means we're at the end of the buffer and
11095	 there is nothing more to get.  */
11096      if (*reply == 'l')
11097	return 0;
11098
11099      /* Convert the reply into binary.  Limit the number of bytes to
11100	 convert according to our passed-in buffer size, rather than
11101	 what was returned in the packet; if the target is
11102	 unexpectedly generous and gives us a bigger reply than we
11103	 asked for, we don't want to crash.  */
11104      rslt = hex2bin (target_buf, buf, len);
11105      return rslt;
11106    }
11107
11108  /* Something went wrong, flag as an error.  */
11109  return -1;
11110}
11111
11112static void
11113remote_set_disconnected_tracing (struct target_ops *self, int val)
11114{
11115  struct remote_state *rs = get_remote_state ();
11116
11117  if (packet_support (PACKET_DisconnectedTracing_feature) == PACKET_ENABLE)
11118    {
11119      char *reply;
11120
11121      xsnprintf (rs->buf, get_remote_packet_size (), "QTDisconnected:%x", val);
11122      putpkt (rs->buf);
11123      reply = remote_get_noisy_reply (&target_buf, &target_buf_size);
11124      if (*reply == '\0')
11125	error (_("Target does not support this command."));
11126      if (strcmp (reply, "OK") != 0)
11127        error (_("Bogus reply from target: %s"), reply);
11128    }
11129  else if (val)
11130    warning (_("Target does not support disconnected tracing."));
11131}
11132
11133static int
11134remote_core_of_thread (struct target_ops *ops, ptid_t ptid)
11135{
11136  struct thread_info *info = find_thread_ptid (ptid);
11137
11138  if (info && info->private)
11139    return info->private->core;
11140  return -1;
11141}
11142
11143static void
11144remote_set_circular_trace_buffer (struct target_ops *self, int val)
11145{
11146  struct remote_state *rs = get_remote_state ();
11147  char *reply;
11148
11149  xsnprintf (rs->buf, get_remote_packet_size (), "QTBuffer:circular:%x", val);
11150  putpkt (rs->buf);
11151  reply = remote_get_noisy_reply (&target_buf, &target_buf_size);
11152  if (*reply == '\0')
11153    error (_("Target does not support this command."));
11154  if (strcmp (reply, "OK") != 0)
11155    error (_("Bogus reply from target: %s"), reply);
11156}
11157
11158static struct traceframe_info *
11159remote_traceframe_info (struct target_ops *self)
11160{
11161  char *text;
11162
11163  text = target_read_stralloc (&current_target,
11164			       TARGET_OBJECT_TRACEFRAME_INFO, NULL);
11165  if (text != NULL)
11166    {
11167      struct traceframe_info *info;
11168      struct cleanup *back_to = make_cleanup (xfree, text);
11169
11170      info = parse_traceframe_info (text);
11171      do_cleanups (back_to);
11172      return info;
11173    }
11174
11175  return NULL;
11176}
11177
11178/* Handle the qTMinFTPILen packet.  Returns the minimum length of
11179   instruction on which a fast tracepoint may be placed.  Returns -1
11180   if the packet is not supported, and 0 if the minimum instruction
11181   length is unknown.  */
11182
11183static int
11184remote_get_min_fast_tracepoint_insn_len (struct target_ops *self)
11185{
11186  struct remote_state *rs = get_remote_state ();
11187  char *reply;
11188
11189  /* If we're not debugging a process yet, the IPA can't be
11190     loaded.  */
11191  if (!target_has_execution)
11192    return 0;
11193
11194  /* Make sure the remote is pointing at the right process.  */
11195  set_general_process ();
11196
11197  xsnprintf (rs->buf, get_remote_packet_size (), "qTMinFTPILen");
11198  putpkt (rs->buf);
11199  reply = remote_get_noisy_reply (&target_buf, &target_buf_size);
11200  if (*reply == '\0')
11201    return -1;
11202  else
11203    {
11204      ULONGEST min_insn_len;
11205
11206      unpack_varlen_hex (reply, &min_insn_len);
11207
11208      return (int) min_insn_len;
11209    }
11210}
11211
11212static void
11213remote_set_trace_buffer_size (struct target_ops *self, LONGEST val)
11214{
11215  if (packet_support (PACKET_QTBuffer_size) != PACKET_DISABLE)
11216    {
11217      struct remote_state *rs = get_remote_state ();
11218      char *buf = rs->buf;
11219      char *endbuf = rs->buf + get_remote_packet_size ();
11220      enum packet_result result;
11221
11222      gdb_assert (val >= 0 || val == -1);
11223      buf += xsnprintf (buf, endbuf - buf, "QTBuffer:size:");
11224      /* Send -1 as literal "-1" to avoid host size dependency.  */
11225      if (val < 0)
11226	{
11227	  *buf++ = '-';
11228          buf += hexnumstr (buf, (ULONGEST) -val);
11229	}
11230      else
11231	buf += hexnumstr (buf, (ULONGEST) val);
11232
11233      putpkt (rs->buf);
11234      remote_get_noisy_reply (&rs->buf, &rs->buf_size);
11235      result = packet_ok (rs->buf,
11236		  &remote_protocol_packets[PACKET_QTBuffer_size]);
11237
11238      if (result != PACKET_OK)
11239	warning (_("Bogus reply from target: %s"), rs->buf);
11240    }
11241}
11242
11243static int
11244remote_set_trace_notes (struct target_ops *self,
11245			const char *user, const char *notes,
11246			const char *stop_notes)
11247{
11248  struct remote_state *rs = get_remote_state ();
11249  char *reply;
11250  char *buf = rs->buf;
11251  char *endbuf = rs->buf + get_remote_packet_size ();
11252  int nbytes;
11253
11254  buf += xsnprintf (buf, endbuf - buf, "QTNotes:");
11255  if (user)
11256    {
11257      buf += xsnprintf (buf, endbuf - buf, "user:");
11258      nbytes = bin2hex ((gdb_byte *) user, buf, strlen (user));
11259      buf += 2 * nbytes;
11260      *buf++ = ';';
11261    }
11262  if (notes)
11263    {
11264      buf += xsnprintf (buf, endbuf - buf, "notes:");
11265      nbytes = bin2hex ((gdb_byte *) notes, buf, strlen (notes));
11266      buf += 2 * nbytes;
11267      *buf++ = ';';
11268    }
11269  if (stop_notes)
11270    {
11271      buf += xsnprintf (buf, endbuf - buf, "tstop:");
11272      nbytes = bin2hex ((gdb_byte *) stop_notes, buf, strlen (stop_notes));
11273      buf += 2 * nbytes;
11274      *buf++ = ';';
11275    }
11276  /* Ensure the buffer is terminated.  */
11277  *buf = '\0';
11278
11279  putpkt (rs->buf);
11280  reply = remote_get_noisy_reply (&target_buf, &target_buf_size);
11281  if (*reply == '\0')
11282    return 0;
11283
11284  if (strcmp (reply, "OK") != 0)
11285    error (_("Bogus reply from target: %s"), reply);
11286
11287  return 1;
11288}
11289
11290static int
11291remote_use_agent (struct target_ops *self, int use)
11292{
11293  if (packet_support (PACKET_QAgent) != PACKET_DISABLE)
11294    {
11295      struct remote_state *rs = get_remote_state ();
11296
11297      /* If the stub supports QAgent.  */
11298      xsnprintf (rs->buf, get_remote_packet_size (), "QAgent:%d", use);
11299      putpkt (rs->buf);
11300      getpkt (&rs->buf, &rs->buf_size, 0);
11301
11302      if (strcmp (rs->buf, "OK") == 0)
11303	{
11304	  use_agent = use;
11305	  return 1;
11306	}
11307    }
11308
11309  return 0;
11310}
11311
11312static int
11313remote_can_use_agent (struct target_ops *self)
11314{
11315  return (packet_support (PACKET_QAgent) != PACKET_DISABLE);
11316}
11317
11318struct btrace_target_info
11319{
11320  /* The ptid of the traced thread.  */
11321  ptid_t ptid;
11322};
11323
11324/* Check whether the target supports branch tracing.  */
11325
11326static int
11327remote_supports_btrace (struct target_ops *self)
11328{
11329  if (packet_support (PACKET_Qbtrace_off) != PACKET_ENABLE)
11330    return 0;
11331  if (packet_support (PACKET_Qbtrace_bts) != PACKET_ENABLE)
11332    return 0;
11333  if (packet_support (PACKET_qXfer_btrace) != PACKET_ENABLE)
11334    return 0;
11335
11336  return 1;
11337}
11338
11339/* Enable branch tracing.  */
11340
11341static struct btrace_target_info *
11342remote_enable_btrace (struct target_ops *self, ptid_t ptid)
11343{
11344  struct btrace_target_info *tinfo = NULL;
11345  struct packet_config *packet = &remote_protocol_packets[PACKET_Qbtrace_bts];
11346  struct remote_state *rs = get_remote_state ();
11347  char *buf = rs->buf;
11348  char *endbuf = rs->buf + get_remote_packet_size ();
11349
11350  if (packet_config_support (packet) != PACKET_ENABLE)
11351    error (_("Target does not support branch tracing."));
11352
11353  set_general_thread (ptid);
11354
11355  buf += xsnprintf (buf, endbuf - buf, "%s", packet->name);
11356  putpkt (rs->buf);
11357  getpkt (&rs->buf, &rs->buf_size, 0);
11358
11359  if (packet_ok (rs->buf, packet) == PACKET_ERROR)
11360    {
11361      if (rs->buf[0] == 'E' && rs->buf[1] == '.')
11362	error (_("Could not enable branch tracing for %s: %s"),
11363	       target_pid_to_str (ptid), rs->buf + 2);
11364      else
11365	error (_("Could not enable branch tracing for %s."),
11366	       target_pid_to_str (ptid));
11367    }
11368
11369  tinfo = xzalloc (sizeof (*tinfo));
11370  tinfo->ptid = ptid;
11371
11372  return tinfo;
11373}
11374
11375/* Disable branch tracing.  */
11376
11377static void
11378remote_disable_btrace (struct target_ops *self,
11379		       struct btrace_target_info *tinfo)
11380{
11381  struct packet_config *packet = &remote_protocol_packets[PACKET_Qbtrace_off];
11382  struct remote_state *rs = get_remote_state ();
11383  char *buf = rs->buf;
11384  char *endbuf = rs->buf + get_remote_packet_size ();
11385
11386  if (packet_config_support (packet) != PACKET_ENABLE)
11387    error (_("Target does not support branch tracing."));
11388
11389  set_general_thread (tinfo->ptid);
11390
11391  buf += xsnprintf (buf, endbuf - buf, "%s", packet->name);
11392  putpkt (rs->buf);
11393  getpkt (&rs->buf, &rs->buf_size, 0);
11394
11395  if (packet_ok (rs->buf, packet) == PACKET_ERROR)
11396    {
11397      if (rs->buf[0] == 'E' && rs->buf[1] == '.')
11398	error (_("Could not disable branch tracing for %s: %s"),
11399	       target_pid_to_str (tinfo->ptid), rs->buf + 2);
11400      else
11401	error (_("Could not disable branch tracing for %s."),
11402	       target_pid_to_str (tinfo->ptid));
11403    }
11404
11405  xfree (tinfo);
11406}
11407
11408/* Teardown branch tracing.  */
11409
11410static void
11411remote_teardown_btrace (struct target_ops *self,
11412			struct btrace_target_info *tinfo)
11413{
11414  /* We must not talk to the target during teardown.  */
11415  xfree (tinfo);
11416}
11417
11418/* Read the branch trace.  */
11419
11420static enum btrace_error
11421remote_read_btrace (struct target_ops *self,
11422		    VEC (btrace_block_s) **btrace,
11423		    struct btrace_target_info *tinfo,
11424		    enum btrace_read_type type)
11425{
11426  struct packet_config *packet = &remote_protocol_packets[PACKET_qXfer_btrace];
11427  struct remote_state *rs = get_remote_state ();
11428  struct cleanup *cleanup;
11429  const char *annex;
11430  char *xml;
11431
11432  if (packet_config_support (packet) != PACKET_ENABLE)
11433    error (_("Target does not support branch tracing."));
11434
11435#if !defined(HAVE_LIBEXPAT)
11436  error (_("Cannot process branch tracing result. XML parsing not supported."));
11437#endif
11438
11439  switch (type)
11440    {
11441    case BTRACE_READ_ALL:
11442      annex = "all";
11443      break;
11444    case BTRACE_READ_NEW:
11445      annex = "new";
11446      break;
11447    case BTRACE_READ_DELTA:
11448      annex = "delta";
11449      break;
11450    default:
11451      internal_error (__FILE__, __LINE__,
11452		      _("Bad branch tracing read type: %u."),
11453		      (unsigned int) type);
11454    }
11455
11456  xml = target_read_stralloc (&current_target,
11457                              TARGET_OBJECT_BTRACE, annex);
11458  if (xml == NULL)
11459    return BTRACE_ERR_UNKNOWN;
11460
11461  cleanup = make_cleanup (xfree, xml);
11462  *btrace = parse_xml_btrace (xml);
11463  do_cleanups (cleanup);
11464
11465  return BTRACE_ERR_NONE;
11466}
11467
11468static int
11469remote_augmented_libraries_svr4_read (struct target_ops *self)
11470{
11471  return (packet_support (PACKET_augmented_libraries_svr4_read_feature)
11472	  == PACKET_ENABLE);
11473}
11474
11475/* Implementation of to_load.  */
11476
11477static void
11478remote_load (struct target_ops *self, const char *name, int from_tty)
11479{
11480  generic_load (name, from_tty);
11481}
11482
11483static void
11484init_remote_ops (void)
11485{
11486  remote_ops.to_shortname = "remote";
11487  remote_ops.to_longname = "Remote serial target in gdb-specific protocol";
11488  remote_ops.to_doc =
11489    "Use a remote computer via a serial line, using a gdb-specific protocol.\n\
11490Specify the serial device it is connected to\n\
11491(e.g. /dev/ttyS0, /dev/ttya, COM1, etc.).";
11492  remote_ops.to_open = remote_open;
11493  remote_ops.to_close = remote_close;
11494  remote_ops.to_detach = remote_detach;
11495  remote_ops.to_disconnect = remote_disconnect;
11496  remote_ops.to_resume = remote_resume;
11497  remote_ops.to_wait = remote_wait;
11498  remote_ops.to_fetch_registers = remote_fetch_registers;
11499  remote_ops.to_store_registers = remote_store_registers;
11500  remote_ops.to_prepare_to_store = remote_prepare_to_store;
11501  remote_ops.to_files_info = remote_files_info;
11502  remote_ops.to_insert_breakpoint = remote_insert_breakpoint;
11503  remote_ops.to_remove_breakpoint = remote_remove_breakpoint;
11504  remote_ops.to_stopped_by_watchpoint = remote_stopped_by_watchpoint;
11505  remote_ops.to_stopped_data_address = remote_stopped_data_address;
11506  remote_ops.to_watchpoint_addr_within_range =
11507    remote_watchpoint_addr_within_range;
11508  remote_ops.to_can_use_hw_breakpoint = remote_check_watch_resources;
11509  remote_ops.to_insert_hw_breakpoint = remote_insert_hw_breakpoint;
11510  remote_ops.to_remove_hw_breakpoint = remote_remove_hw_breakpoint;
11511  remote_ops.to_region_ok_for_hw_watchpoint
11512     = remote_region_ok_for_hw_watchpoint;
11513  remote_ops.to_insert_watchpoint = remote_insert_watchpoint;
11514  remote_ops.to_remove_watchpoint = remote_remove_watchpoint;
11515  remote_ops.to_kill = remote_kill;
11516  remote_ops.to_load = remote_load;
11517  remote_ops.to_mourn_inferior = remote_mourn;
11518  remote_ops.to_pass_signals = remote_pass_signals;
11519  remote_ops.to_program_signals = remote_program_signals;
11520  remote_ops.to_thread_alive = remote_thread_alive;
11521  remote_ops.to_update_thread_list = remote_update_thread_list;
11522  remote_ops.to_pid_to_str = remote_pid_to_str;
11523  remote_ops.to_extra_thread_info = remote_threads_extra_info;
11524  remote_ops.to_get_ada_task_ptid = remote_get_ada_task_ptid;
11525  remote_ops.to_stop = remote_stop;
11526  remote_ops.to_xfer_partial = remote_xfer_partial;
11527  remote_ops.to_rcmd = remote_rcmd;
11528  remote_ops.to_log_command = serial_log_command;
11529  remote_ops.to_get_thread_local_address = remote_get_thread_local_address;
11530  remote_ops.to_stratum = process_stratum;
11531  remote_ops.to_has_all_memory = default_child_has_all_memory;
11532  remote_ops.to_has_memory = default_child_has_memory;
11533  remote_ops.to_has_stack = default_child_has_stack;
11534  remote_ops.to_has_registers = default_child_has_registers;
11535  remote_ops.to_has_execution = default_child_has_execution;
11536  remote_ops.to_has_thread_control = tc_schedlock;    /* can lock scheduler */
11537  remote_ops.to_can_execute_reverse = remote_can_execute_reverse;
11538  remote_ops.to_magic = OPS_MAGIC;
11539  remote_ops.to_memory_map = remote_memory_map;
11540  remote_ops.to_flash_erase = remote_flash_erase;
11541  remote_ops.to_flash_done = remote_flash_done;
11542  remote_ops.to_read_description = remote_read_description;
11543  remote_ops.to_search_memory = remote_search_memory;
11544  remote_ops.to_can_async_p = remote_can_async_p;
11545  remote_ops.to_is_async_p = remote_is_async_p;
11546  remote_ops.to_async = remote_async;
11547  remote_ops.to_terminal_inferior = remote_terminal_inferior;
11548  remote_ops.to_terminal_ours = remote_terminal_ours;
11549  remote_ops.to_supports_non_stop = remote_supports_non_stop;
11550  remote_ops.to_supports_multi_process = remote_supports_multi_process;
11551  remote_ops.to_supports_disable_randomization
11552    = remote_supports_disable_randomization;
11553  remote_ops.to_fileio_open = remote_hostio_open;
11554  remote_ops.to_fileio_pwrite = remote_hostio_pwrite;
11555  remote_ops.to_fileio_pread = remote_hostio_pread;
11556  remote_ops.to_fileio_close = remote_hostio_close;
11557  remote_ops.to_fileio_unlink = remote_hostio_unlink;
11558  remote_ops.to_fileio_readlink = remote_hostio_readlink;
11559  remote_ops.to_supports_enable_disable_tracepoint = remote_supports_enable_disable_tracepoint;
11560  remote_ops.to_supports_string_tracing = remote_supports_string_tracing;
11561  remote_ops.to_supports_evaluation_of_breakpoint_conditions = remote_supports_cond_breakpoints;
11562  remote_ops.to_can_run_breakpoint_commands = remote_can_run_breakpoint_commands;
11563  remote_ops.to_trace_init = remote_trace_init;
11564  remote_ops.to_download_tracepoint = remote_download_tracepoint;
11565  remote_ops.to_can_download_tracepoint = remote_can_download_tracepoint;
11566  remote_ops.to_download_trace_state_variable
11567    = remote_download_trace_state_variable;
11568  remote_ops.to_enable_tracepoint = remote_enable_tracepoint;
11569  remote_ops.to_disable_tracepoint = remote_disable_tracepoint;
11570  remote_ops.to_trace_set_readonly_regions = remote_trace_set_readonly_regions;
11571  remote_ops.to_trace_start = remote_trace_start;
11572  remote_ops.to_get_trace_status = remote_get_trace_status;
11573  remote_ops.to_get_tracepoint_status = remote_get_tracepoint_status;
11574  remote_ops.to_trace_stop = remote_trace_stop;
11575  remote_ops.to_trace_find = remote_trace_find;
11576  remote_ops.to_get_trace_state_variable_value
11577    = remote_get_trace_state_variable_value;
11578  remote_ops.to_save_trace_data = remote_save_trace_data;
11579  remote_ops.to_upload_tracepoints = remote_upload_tracepoints;
11580  remote_ops.to_upload_trace_state_variables
11581    = remote_upload_trace_state_variables;
11582  remote_ops.to_get_raw_trace_data = remote_get_raw_trace_data;
11583  remote_ops.to_get_min_fast_tracepoint_insn_len = remote_get_min_fast_tracepoint_insn_len;
11584  remote_ops.to_set_disconnected_tracing = remote_set_disconnected_tracing;
11585  remote_ops.to_set_circular_trace_buffer = remote_set_circular_trace_buffer;
11586  remote_ops.to_set_trace_buffer_size = remote_set_trace_buffer_size;
11587  remote_ops.to_set_trace_notes = remote_set_trace_notes;
11588  remote_ops.to_core_of_thread = remote_core_of_thread;
11589  remote_ops.to_verify_memory = remote_verify_memory;
11590  remote_ops.to_get_tib_address = remote_get_tib_address;
11591  remote_ops.to_set_permissions = remote_set_permissions;
11592  remote_ops.to_static_tracepoint_marker_at
11593    = remote_static_tracepoint_marker_at;
11594  remote_ops.to_static_tracepoint_markers_by_strid
11595    = remote_static_tracepoint_markers_by_strid;
11596  remote_ops.to_traceframe_info = remote_traceframe_info;
11597  remote_ops.to_use_agent = remote_use_agent;
11598  remote_ops.to_can_use_agent = remote_can_use_agent;
11599  remote_ops.to_supports_btrace = remote_supports_btrace;
11600  remote_ops.to_enable_btrace = remote_enable_btrace;
11601  remote_ops.to_disable_btrace = remote_disable_btrace;
11602  remote_ops.to_teardown_btrace = remote_teardown_btrace;
11603  remote_ops.to_read_btrace = remote_read_btrace;
11604  remote_ops.to_augmented_libraries_svr4_read =
11605    remote_augmented_libraries_svr4_read;
11606}
11607
11608/* Set up the extended remote vector by making a copy of the standard
11609   remote vector and adding to it.  */
11610
11611static void
11612init_extended_remote_ops (void)
11613{
11614  extended_remote_ops = remote_ops;
11615
11616  extended_remote_ops.to_shortname = "extended-remote";
11617  extended_remote_ops.to_longname =
11618    "Extended remote serial target in gdb-specific protocol";
11619  extended_remote_ops.to_doc =
11620    "Use a remote computer via a serial line, using a gdb-specific protocol.\n\
11621Specify the serial device it is connected to (e.g. /dev/ttya).";
11622  extended_remote_ops.to_open = extended_remote_open;
11623  extended_remote_ops.to_create_inferior = extended_remote_create_inferior;
11624  extended_remote_ops.to_mourn_inferior = extended_remote_mourn;
11625  extended_remote_ops.to_detach = extended_remote_detach;
11626  extended_remote_ops.to_attach = extended_remote_attach;
11627  extended_remote_ops.to_post_attach = extended_remote_post_attach;
11628  extended_remote_ops.to_kill = extended_remote_kill;
11629  extended_remote_ops.to_supports_disable_randomization
11630    = extended_remote_supports_disable_randomization;
11631}
11632
11633static int
11634remote_can_async_p (struct target_ops *ops)
11635{
11636  struct remote_state *rs = get_remote_state ();
11637
11638  if (!target_async_permitted)
11639    /* We only enable async when the user specifically asks for it.  */
11640    return 0;
11641
11642  /* We're async whenever the serial device is.  */
11643  return serial_can_async_p (rs->remote_desc);
11644}
11645
11646static int
11647remote_is_async_p (struct target_ops *ops)
11648{
11649  struct remote_state *rs = get_remote_state ();
11650
11651  if (!target_async_permitted)
11652    /* We only enable async when the user specifically asks for it.  */
11653    return 0;
11654
11655  /* We're async whenever the serial device is.  */
11656  return serial_is_async_p (rs->remote_desc);
11657}
11658
11659/* Pass the SERIAL event on and up to the client.  One day this code
11660   will be able to delay notifying the client of an event until the
11661   point where an entire packet has been received.  */
11662
11663static serial_event_ftype remote_async_serial_handler;
11664
11665static void
11666remote_async_serial_handler (struct serial *scb, void *context)
11667{
11668  struct remote_state *rs = context;
11669
11670  /* Don't propogate error information up to the client.  Instead let
11671     the client find out about the error by querying the target.  */
11672  rs->async_client_callback (INF_REG_EVENT, rs->async_client_context);
11673}
11674
11675static void
11676remote_async_inferior_event_handler (gdb_client_data data)
11677{
11678  inferior_event_handler (INF_REG_EVENT, NULL);
11679}
11680
11681static void
11682remote_async (struct target_ops *ops,
11683	      void (*callback) (enum inferior_event_type event_type,
11684				void *context),
11685	      void *context)
11686{
11687  struct remote_state *rs = get_remote_state ();
11688
11689  if (callback != NULL)
11690    {
11691      serial_async (rs->remote_desc, remote_async_serial_handler, rs);
11692      rs->async_client_callback = callback;
11693      rs->async_client_context = context;
11694
11695      /* If there are pending events in the stop reply queue tell the
11696	 event loop to process them.  */
11697      if (!QUEUE_is_empty (stop_reply_p, stop_reply_queue))
11698	mark_async_event_handler (remote_async_inferior_event_token);
11699    }
11700  else
11701    {
11702      serial_async (rs->remote_desc, NULL, NULL);
11703      clear_async_event_handler (remote_async_inferior_event_token);
11704    }
11705}
11706
11707static void
11708set_remote_cmd (char *args, int from_tty)
11709{
11710  help_list (remote_set_cmdlist, "set remote ", all_commands, gdb_stdout);
11711}
11712
11713static void
11714show_remote_cmd (char *args, int from_tty)
11715{
11716  /* We can't just use cmd_show_list here, because we want to skip
11717     the redundant "show remote Z-packet" and the legacy aliases.  */
11718  struct cleanup *showlist_chain;
11719  struct cmd_list_element *list = remote_show_cmdlist;
11720  struct ui_out *uiout = current_uiout;
11721
11722  showlist_chain = make_cleanup_ui_out_tuple_begin_end (uiout, "showlist");
11723  for (; list != NULL; list = list->next)
11724    if (strcmp (list->name, "Z-packet") == 0)
11725      continue;
11726    else if (list->type == not_set_cmd)
11727      /* Alias commands are exactly like the original, except they
11728	 don't have the normal type.  */
11729      continue;
11730    else
11731      {
11732	struct cleanup *option_chain
11733	  = make_cleanup_ui_out_tuple_begin_end (uiout, "option");
11734
11735	ui_out_field_string (uiout, "name", list->name);
11736	ui_out_text (uiout, ":  ");
11737	if (list->type == show_cmd)
11738	  do_show_command ((char *) NULL, from_tty, list);
11739	else
11740	  cmd_func (list, NULL, from_tty);
11741	/* Close the tuple.  */
11742	do_cleanups (option_chain);
11743      }
11744
11745  /* Close the tuple.  */
11746  do_cleanups (showlist_chain);
11747}
11748
11749
11750/* Function to be called whenever a new objfile (shlib) is detected.  */
11751static void
11752remote_new_objfile (struct objfile *objfile)
11753{
11754  struct remote_state *rs = get_remote_state ();
11755
11756  if (rs->remote_desc != 0)		/* Have a remote connection.  */
11757    remote_check_symbols ();
11758}
11759
11760/* Pull all the tracepoints defined on the target and create local
11761   data structures representing them.  We don't want to create real
11762   tracepoints yet, we don't want to mess up the user's existing
11763   collection.  */
11764
11765static int
11766remote_upload_tracepoints (struct target_ops *self, struct uploaded_tp **utpp)
11767{
11768  struct remote_state *rs = get_remote_state ();
11769  char *p;
11770
11771  /* Ask for a first packet of tracepoint definition.  */
11772  putpkt ("qTfP");
11773  getpkt (&rs->buf, &rs->buf_size, 0);
11774  p = rs->buf;
11775  while (*p && *p != 'l')
11776    {
11777      parse_tracepoint_definition (p, utpp);
11778      /* Ask for another packet of tracepoint definition.  */
11779      putpkt ("qTsP");
11780      getpkt (&rs->buf, &rs->buf_size, 0);
11781      p = rs->buf;
11782    }
11783  return 0;
11784}
11785
11786static int
11787remote_upload_trace_state_variables (struct target_ops *self,
11788				     struct uploaded_tsv **utsvp)
11789{
11790  struct remote_state *rs = get_remote_state ();
11791  char *p;
11792
11793  /* Ask for a first packet of variable definition.  */
11794  putpkt ("qTfV");
11795  getpkt (&rs->buf, &rs->buf_size, 0);
11796  p = rs->buf;
11797  while (*p && *p != 'l')
11798    {
11799      parse_tsv_definition (p, utsvp);
11800      /* Ask for another packet of variable definition.  */
11801      putpkt ("qTsV");
11802      getpkt (&rs->buf, &rs->buf_size, 0);
11803      p = rs->buf;
11804    }
11805  return 0;
11806}
11807
11808/* The "set/show range-stepping" show hook.  */
11809
11810static void
11811show_range_stepping (struct ui_file *file, int from_tty,
11812		     struct cmd_list_element *c,
11813		     const char *value)
11814{
11815  fprintf_filtered (file,
11816		    _("Debugger's willingness to use range stepping "
11817		      "is %s.\n"), value);
11818}
11819
11820/* The "set/show range-stepping" set hook.  */
11821
11822static void
11823set_range_stepping (char *ignore_args, int from_tty,
11824		    struct cmd_list_element *c)
11825{
11826  struct remote_state *rs = get_remote_state ();
11827
11828  /* Whene enabling, check whether range stepping is actually
11829     supported by the target, and warn if not.  */
11830  if (use_range_stepping)
11831    {
11832      if (rs->remote_desc != NULL)
11833	{
11834	  if (packet_support (PACKET_vCont) == PACKET_SUPPORT_UNKNOWN)
11835	    remote_vcont_probe (rs);
11836
11837	  if (packet_support (PACKET_vCont) == PACKET_ENABLE
11838	      && rs->supports_vCont.r)
11839	    return;
11840	}
11841
11842      warning (_("Range stepping is not supported by the current target"));
11843    }
11844}
11845
11846void
11847_initialize_remote (void)
11848{
11849  struct remote_state *rs;
11850  struct cmd_list_element *cmd;
11851  const char *cmd_name;
11852
11853  /* architecture specific data */
11854  remote_gdbarch_data_handle =
11855    gdbarch_data_register_post_init (init_remote_state);
11856  remote_g_packet_data_handle =
11857    gdbarch_data_register_pre_init (remote_g_packet_data_init);
11858
11859  /* Initialize the per-target state.  At the moment there is only one
11860     of these, not one per target.  Only one target is active at a
11861     time.  */
11862  remote_state = new_remote_state ();
11863
11864  init_remote_ops ();
11865  add_target (&remote_ops);
11866
11867  init_extended_remote_ops ();
11868  add_target (&extended_remote_ops);
11869
11870  /* Hook into new objfile notification.  */
11871  observer_attach_new_objfile (remote_new_objfile);
11872  /* We're no longer interested in notification events of an inferior
11873     when it exits.  */
11874  observer_attach_inferior_exit (discard_pending_stop_replies);
11875
11876  /* Set up signal handlers.  */
11877  async_sigint_remote_token =
11878    create_async_signal_handler (async_remote_interrupt, NULL);
11879  async_sigint_remote_twice_token =
11880    create_async_signal_handler (async_remote_interrupt_twice, NULL);
11881
11882#if 0
11883  init_remote_threadtests ();
11884#endif
11885
11886  stop_reply_queue = QUEUE_alloc (stop_reply_p, stop_reply_xfree);
11887  /* set/show remote ...  */
11888
11889  add_prefix_cmd ("remote", class_maintenance, set_remote_cmd, _("\
11890Remote protocol specific variables\n\
11891Configure various remote-protocol specific variables such as\n\
11892the packets being used"),
11893		  &remote_set_cmdlist, "set remote ",
11894		  0 /* allow-unknown */, &setlist);
11895  add_prefix_cmd ("remote", class_maintenance, show_remote_cmd, _("\
11896Remote protocol specific variables\n\
11897Configure various remote-protocol specific variables such as\n\
11898the packets being used"),
11899		  &remote_show_cmdlist, "show remote ",
11900		  0 /* allow-unknown */, &showlist);
11901
11902  add_cmd ("compare-sections", class_obscure, compare_sections_command, _("\
11903Compare section data on target to the exec file.\n\
11904Argument is a single section name (default: all loaded sections).\n\
11905To compare only read-only loaded sections, specify the -r option."),
11906	   &cmdlist);
11907
11908  add_cmd ("packet", class_maintenance, packet_command, _("\
11909Send an arbitrary packet to a remote target.\n\
11910   maintenance packet TEXT\n\
11911If GDB is talking to an inferior via the GDB serial protocol, then\n\
11912this command sends the string TEXT to the inferior, and displays the\n\
11913response packet.  GDB supplies the initial `$' character, and the\n\
11914terminating `#' character and checksum."),
11915	   &maintenancelist);
11916
11917  add_setshow_boolean_cmd ("remotebreak", no_class, &remote_break, _("\
11918Set whether to send break if interrupted."), _("\
11919Show whether to send break if interrupted."), _("\
11920If set, a break, instead of a cntrl-c, is sent to the remote target."),
11921			   set_remotebreak, show_remotebreak,
11922			   &setlist, &showlist);
11923  cmd_name = "remotebreak";
11924  cmd = lookup_cmd (&cmd_name, setlist, "", -1, 1);
11925  deprecate_cmd (cmd, "set remote interrupt-sequence");
11926  cmd_name = "remotebreak"; /* needed because lookup_cmd updates the pointer */
11927  cmd = lookup_cmd (&cmd_name, showlist, "", -1, 1);
11928  deprecate_cmd (cmd, "show remote interrupt-sequence");
11929
11930  add_setshow_enum_cmd ("interrupt-sequence", class_support,
11931			interrupt_sequence_modes, &interrupt_sequence_mode,
11932			_("\
11933Set interrupt sequence to remote target."), _("\
11934Show interrupt sequence to remote target."), _("\
11935Valid value is \"Ctrl-C\", \"BREAK\" or \"BREAK-g\". The default is \"Ctrl-C\"."),
11936			NULL, show_interrupt_sequence,
11937			&remote_set_cmdlist,
11938			&remote_show_cmdlist);
11939
11940  add_setshow_boolean_cmd ("interrupt-on-connect", class_support,
11941			   &interrupt_on_connect, _("\
11942Set whether interrupt-sequence is sent to remote target when gdb connects to."), _("		\
11943Show whether interrupt-sequence is sent to remote target when gdb connects to."), _("		\
11944If set, interrupt sequence is sent to remote target."),
11945			   NULL, NULL,
11946			   &remote_set_cmdlist, &remote_show_cmdlist);
11947
11948  /* Install commands for configuring memory read/write packets.  */
11949
11950  add_cmd ("remotewritesize", no_class, set_memory_write_packet_size, _("\
11951Set the maximum number of bytes per memory write packet (deprecated)."),
11952	   &setlist);
11953  add_cmd ("remotewritesize", no_class, show_memory_write_packet_size, _("\
11954Show the maximum number of bytes per memory write packet (deprecated)."),
11955	   &showlist);
11956  add_cmd ("memory-write-packet-size", no_class,
11957	   set_memory_write_packet_size, _("\
11958Set the maximum number of bytes per memory-write packet.\n\
11959Specify the number of bytes in a packet or 0 (zero) for the\n\
11960default packet size.  The actual limit is further reduced\n\
11961dependent on the target.  Specify ``fixed'' to disable the\n\
11962further restriction and ``limit'' to enable that restriction."),
11963	   &remote_set_cmdlist);
11964  add_cmd ("memory-read-packet-size", no_class,
11965	   set_memory_read_packet_size, _("\
11966Set the maximum number of bytes per memory-read packet.\n\
11967Specify the number of bytes in a packet or 0 (zero) for the\n\
11968default packet size.  The actual limit is further reduced\n\
11969dependent on the target.  Specify ``fixed'' to disable the\n\
11970further restriction and ``limit'' to enable that restriction."),
11971	   &remote_set_cmdlist);
11972  add_cmd ("memory-write-packet-size", no_class,
11973	   show_memory_write_packet_size,
11974	   _("Show the maximum number of bytes per memory-write packet."),
11975	   &remote_show_cmdlist);
11976  add_cmd ("memory-read-packet-size", no_class,
11977	   show_memory_read_packet_size,
11978	   _("Show the maximum number of bytes per memory-read packet."),
11979	   &remote_show_cmdlist);
11980
11981  add_setshow_zinteger_cmd ("hardware-watchpoint-limit", no_class,
11982			    &remote_hw_watchpoint_limit, _("\
11983Set the maximum number of target hardware watchpoints."), _("\
11984Show the maximum number of target hardware watchpoints."), _("\
11985Specify a negative limit for unlimited."),
11986			    NULL, NULL, /* FIXME: i18n: The maximum
11987					   number of target hardware
11988					   watchpoints is %s.  */
11989			    &remote_set_cmdlist, &remote_show_cmdlist);
11990  add_setshow_zinteger_cmd ("hardware-watchpoint-length-limit", no_class,
11991			    &remote_hw_watchpoint_length_limit, _("\
11992Set the maximum length (in bytes) of a target hardware watchpoint."), _("\
11993Show the maximum length (in bytes) of a target hardware watchpoint."), _("\
11994Specify a negative limit for unlimited."),
11995			    NULL, NULL, /* FIXME: i18n: The maximum
11996                                           length (in bytes) of a target
11997                                           hardware watchpoint is %s.  */
11998			    &remote_set_cmdlist, &remote_show_cmdlist);
11999  add_setshow_zinteger_cmd ("hardware-breakpoint-limit", no_class,
12000			    &remote_hw_breakpoint_limit, _("\
12001Set the maximum number of target hardware breakpoints."), _("\
12002Show the maximum number of target hardware breakpoints."), _("\
12003Specify a negative limit for unlimited."),
12004			    NULL, NULL, /* FIXME: i18n: The maximum
12005					   number of target hardware
12006					   breakpoints is %s.  */
12007			    &remote_set_cmdlist, &remote_show_cmdlist);
12008
12009  add_setshow_zuinteger_cmd ("remoteaddresssize", class_obscure,
12010			     &remote_address_size, _("\
12011Set the maximum size of the address (in bits) in a memory packet."), _("\
12012Show the maximum size of the address (in bits) in a memory packet."), NULL,
12013			     NULL,
12014			     NULL, /* FIXME: i18n: */
12015			     &setlist, &showlist);
12016
12017  init_all_packet_configs ();
12018
12019  add_packet_config_cmd (&remote_protocol_packets[PACKET_X],
12020			 "X", "binary-download", 1);
12021
12022  add_packet_config_cmd (&remote_protocol_packets[PACKET_vCont],
12023			 "vCont", "verbose-resume", 0);
12024
12025  add_packet_config_cmd (&remote_protocol_packets[PACKET_QPassSignals],
12026			 "QPassSignals", "pass-signals", 0);
12027
12028  add_packet_config_cmd (&remote_protocol_packets[PACKET_QProgramSignals],
12029			 "QProgramSignals", "program-signals", 0);
12030
12031  add_packet_config_cmd (&remote_protocol_packets[PACKET_qSymbol],
12032			 "qSymbol", "symbol-lookup", 0);
12033
12034  add_packet_config_cmd (&remote_protocol_packets[PACKET_P],
12035			 "P", "set-register", 1);
12036
12037  add_packet_config_cmd (&remote_protocol_packets[PACKET_p],
12038			 "p", "fetch-register", 1);
12039
12040  add_packet_config_cmd (&remote_protocol_packets[PACKET_Z0],
12041			 "Z0", "software-breakpoint", 0);
12042
12043  add_packet_config_cmd (&remote_protocol_packets[PACKET_Z1],
12044			 "Z1", "hardware-breakpoint", 0);
12045
12046  add_packet_config_cmd (&remote_protocol_packets[PACKET_Z2],
12047			 "Z2", "write-watchpoint", 0);
12048
12049  add_packet_config_cmd (&remote_protocol_packets[PACKET_Z3],
12050			 "Z3", "read-watchpoint", 0);
12051
12052  add_packet_config_cmd (&remote_protocol_packets[PACKET_Z4],
12053			 "Z4", "access-watchpoint", 0);
12054
12055  add_packet_config_cmd (&remote_protocol_packets[PACKET_qXfer_auxv],
12056			 "qXfer:auxv:read", "read-aux-vector", 0);
12057
12058  add_packet_config_cmd (&remote_protocol_packets[PACKET_qXfer_features],
12059			 "qXfer:features:read", "target-features", 0);
12060
12061  add_packet_config_cmd (&remote_protocol_packets[PACKET_qXfer_libraries],
12062			 "qXfer:libraries:read", "library-info", 0);
12063
12064  add_packet_config_cmd (&remote_protocol_packets[PACKET_qXfer_libraries_svr4],
12065			 "qXfer:libraries-svr4:read", "library-info-svr4", 0);
12066
12067  add_packet_config_cmd (&remote_protocol_packets[PACKET_qXfer_memory_map],
12068			 "qXfer:memory-map:read", "memory-map", 0);
12069
12070  add_packet_config_cmd (&remote_protocol_packets[PACKET_qXfer_spu_read],
12071                         "qXfer:spu:read", "read-spu-object", 0);
12072
12073  add_packet_config_cmd (&remote_protocol_packets[PACKET_qXfer_spu_write],
12074                         "qXfer:spu:write", "write-spu-object", 0);
12075
12076  add_packet_config_cmd (&remote_protocol_packets[PACKET_qXfer_osdata],
12077                        "qXfer:osdata:read", "osdata", 0);
12078
12079  add_packet_config_cmd (&remote_protocol_packets[PACKET_qXfer_threads],
12080			 "qXfer:threads:read", "threads", 0);
12081
12082  add_packet_config_cmd (&remote_protocol_packets[PACKET_qXfer_siginfo_read],
12083                         "qXfer:siginfo:read", "read-siginfo-object", 0);
12084
12085  add_packet_config_cmd (&remote_protocol_packets[PACKET_qXfer_siginfo_write],
12086                         "qXfer:siginfo:write", "write-siginfo-object", 0);
12087
12088  add_packet_config_cmd
12089    (&remote_protocol_packets[PACKET_qXfer_traceframe_info],
12090     "qXfer:traceframe-info:read", "traceframe-info", 0);
12091
12092  add_packet_config_cmd (&remote_protocol_packets[PACKET_qXfer_uib],
12093			 "qXfer:uib:read", "unwind-info-block", 0);
12094
12095  add_packet_config_cmd (&remote_protocol_packets[PACKET_qGetTLSAddr],
12096			 "qGetTLSAddr", "get-thread-local-storage-address",
12097			 0);
12098
12099  add_packet_config_cmd (&remote_protocol_packets[PACKET_qGetTIBAddr],
12100			 "qGetTIBAddr", "get-thread-information-block-address",
12101			 0);
12102
12103  add_packet_config_cmd (&remote_protocol_packets[PACKET_bc],
12104			 "bc", "reverse-continue", 0);
12105
12106  add_packet_config_cmd (&remote_protocol_packets[PACKET_bs],
12107			 "bs", "reverse-step", 0);
12108
12109  add_packet_config_cmd (&remote_protocol_packets[PACKET_qSupported],
12110			 "qSupported", "supported-packets", 0);
12111
12112  add_packet_config_cmd (&remote_protocol_packets[PACKET_qSearch_memory],
12113			 "qSearch:memory", "search-memory", 0);
12114
12115  add_packet_config_cmd (&remote_protocol_packets[PACKET_qTStatus],
12116			 "qTStatus", "trace-status", 0);
12117
12118  add_packet_config_cmd (&remote_protocol_packets[PACKET_vFile_open],
12119			 "vFile:open", "hostio-open", 0);
12120
12121  add_packet_config_cmd (&remote_protocol_packets[PACKET_vFile_pread],
12122			 "vFile:pread", "hostio-pread", 0);
12123
12124  add_packet_config_cmd (&remote_protocol_packets[PACKET_vFile_pwrite],
12125			 "vFile:pwrite", "hostio-pwrite", 0);
12126
12127  add_packet_config_cmd (&remote_protocol_packets[PACKET_vFile_close],
12128			 "vFile:close", "hostio-close", 0);
12129
12130  add_packet_config_cmd (&remote_protocol_packets[PACKET_vFile_unlink],
12131			 "vFile:unlink", "hostio-unlink", 0);
12132
12133  add_packet_config_cmd (&remote_protocol_packets[PACKET_vFile_readlink],
12134			 "vFile:readlink", "hostio-readlink", 0);
12135
12136  add_packet_config_cmd (&remote_protocol_packets[PACKET_vAttach],
12137			 "vAttach", "attach", 0);
12138
12139  add_packet_config_cmd (&remote_protocol_packets[PACKET_vRun],
12140			 "vRun", "run", 0);
12141
12142  add_packet_config_cmd (&remote_protocol_packets[PACKET_QStartNoAckMode],
12143			 "QStartNoAckMode", "noack", 0);
12144
12145  add_packet_config_cmd (&remote_protocol_packets[PACKET_vKill],
12146			 "vKill", "kill", 0);
12147
12148  add_packet_config_cmd (&remote_protocol_packets[PACKET_qAttached],
12149			 "qAttached", "query-attached", 0);
12150
12151  add_packet_config_cmd (&remote_protocol_packets[PACKET_ConditionalTracepoints],
12152			 "ConditionalTracepoints",
12153			 "conditional-tracepoints", 0);
12154
12155  add_packet_config_cmd (&remote_protocol_packets[PACKET_ConditionalBreakpoints],
12156			 "ConditionalBreakpoints",
12157			 "conditional-breakpoints", 0);
12158
12159  add_packet_config_cmd (&remote_protocol_packets[PACKET_BreakpointCommands],
12160			 "BreakpointCommands",
12161			 "breakpoint-commands", 0);
12162
12163  add_packet_config_cmd (&remote_protocol_packets[PACKET_FastTracepoints],
12164			 "FastTracepoints", "fast-tracepoints", 0);
12165
12166  add_packet_config_cmd (&remote_protocol_packets[PACKET_TracepointSource],
12167			 "TracepointSource", "TracepointSource", 0);
12168
12169  add_packet_config_cmd (&remote_protocol_packets[PACKET_QAllow],
12170			 "QAllow", "allow", 0);
12171
12172  add_packet_config_cmd (&remote_protocol_packets[PACKET_StaticTracepoints],
12173			 "StaticTracepoints", "static-tracepoints", 0);
12174
12175  add_packet_config_cmd (&remote_protocol_packets[PACKET_InstallInTrace],
12176			 "InstallInTrace", "install-in-trace", 0);
12177
12178  add_packet_config_cmd (&remote_protocol_packets[PACKET_qXfer_statictrace_read],
12179                         "qXfer:statictrace:read", "read-sdata-object", 0);
12180
12181  add_packet_config_cmd (&remote_protocol_packets[PACKET_qXfer_fdpic],
12182			 "qXfer:fdpic:read", "read-fdpic-loadmap", 0);
12183
12184  add_packet_config_cmd (&remote_protocol_packets[PACKET_QDisableRandomization],
12185			 "QDisableRandomization", "disable-randomization", 0);
12186
12187  add_packet_config_cmd (&remote_protocol_packets[PACKET_QAgent],
12188			 "QAgent", "agent", 0);
12189
12190  add_packet_config_cmd (&remote_protocol_packets[PACKET_QTBuffer_size],
12191			 "QTBuffer:size", "trace-buffer-size", 0);
12192
12193  add_packet_config_cmd (&remote_protocol_packets[PACKET_Qbtrace_off],
12194       "Qbtrace:off", "disable-btrace", 0);
12195
12196  add_packet_config_cmd (&remote_protocol_packets[PACKET_Qbtrace_bts],
12197       "Qbtrace:bts", "enable-btrace", 0);
12198
12199  add_packet_config_cmd (&remote_protocol_packets[PACKET_qXfer_btrace],
12200       "qXfer:btrace", "read-btrace", 0);
12201
12202  /* Assert that we've registered commands for all packet configs.  */
12203  {
12204    int i;
12205
12206    for (i = 0; i < PACKET_MAX; i++)
12207      {
12208	/* Ideally all configs would have a command associated.  Some
12209	   still don't though.  */
12210	int excepted;
12211
12212	switch (i)
12213	  {
12214	  case PACKET_QNonStop:
12215	  case PACKET_multiprocess_feature:
12216	  case PACKET_EnableDisableTracepoints_feature:
12217	  case PACKET_tracenz_feature:
12218	  case PACKET_DisconnectedTracing_feature:
12219	  case PACKET_augmented_libraries_svr4_read_feature:
12220	  case PACKET_qCRC:
12221	    /* Additions to this list need to be well justified:
12222	       pre-existing packets are OK; new packets are not.  */
12223	    excepted = 1;
12224	    break;
12225	  default:
12226	    excepted = 0;
12227	    break;
12228	  }
12229
12230	/* This catches both forgetting to add a config command, and
12231	   forgetting to remove a packet from the exception list.  */
12232	gdb_assert (excepted == (remote_protocol_packets[i].name == NULL));
12233      }
12234  }
12235
12236  /* Keep the old ``set remote Z-packet ...'' working.  Each individual
12237     Z sub-packet has its own set and show commands, but users may
12238     have sets to this variable in their .gdbinit files (or in their
12239     documentation).  */
12240  add_setshow_auto_boolean_cmd ("Z-packet", class_obscure,
12241				&remote_Z_packet_detect, _("\
12242Set use of remote protocol `Z' packets"), _("\
12243Show use of remote protocol `Z' packets "), _("\
12244When set, GDB will attempt to use the remote breakpoint and watchpoint\n\
12245packets."),
12246				set_remote_protocol_Z_packet_cmd,
12247				show_remote_protocol_Z_packet_cmd,
12248				/* FIXME: i18n: Use of remote protocol
12249				   `Z' packets is %s.  */
12250				&remote_set_cmdlist, &remote_show_cmdlist);
12251
12252  add_prefix_cmd ("remote", class_files, remote_command, _("\
12253Manipulate files on the remote system\n\
12254Transfer files to and from the remote target system."),
12255		  &remote_cmdlist, "remote ",
12256		  0 /* allow-unknown */, &cmdlist);
12257
12258  add_cmd ("put", class_files, remote_put_command,
12259	   _("Copy a local file to the remote system."),
12260	   &remote_cmdlist);
12261
12262  add_cmd ("get", class_files, remote_get_command,
12263	   _("Copy a remote file to the local system."),
12264	   &remote_cmdlist);
12265
12266  add_cmd ("delete", class_files, remote_delete_command,
12267	   _("Delete a remote file."),
12268	   &remote_cmdlist);
12269
12270  remote_exec_file = xstrdup ("");
12271  add_setshow_string_noescape_cmd ("exec-file", class_files,
12272				   &remote_exec_file, _("\
12273Set the remote pathname for \"run\""), _("\
12274Show the remote pathname for \"run\""), NULL, NULL, NULL,
12275				   &remote_set_cmdlist, &remote_show_cmdlist);
12276
12277  add_setshow_boolean_cmd ("range-stepping", class_run,
12278			   &use_range_stepping, _("\
12279Enable or disable range stepping."), _("\
12280Show whether target-assisted range stepping is enabled."), _("\
12281If on, and the target supports it, when stepping a source line, GDB\n\
12282tells the target to step the corresponding range of addresses itself instead\n\
12283of issuing multiple single-steps.  This speeds up source level\n\
12284stepping.  If off, GDB always issues single-steps, even if range\n\
12285stepping is supported by the target.  The default is on."),
12286			   set_range_stepping,
12287			   show_range_stepping,
12288			   &setlist,
12289			   &showlist);
12290
12291  /* Eventually initialize fileio.  See fileio.c */
12292  initialize_remote_fileio (remote_set_cmdlist, remote_show_cmdlist);
12293
12294  /* Take advantage of the fact that the TID field is not used, to tag
12295     special ptids with it set to != 0.  */
12296  magic_null_ptid = ptid_build (42000, -1, 1);
12297  not_sent_ptid = ptid_build (42000, -2, 1);
12298  any_thread_ptid = ptid_build (42000, 0, 1);
12299
12300  target_buf_size = 2048;
12301  target_buf = xmalloc (target_buf_size);
12302}
12303
12304