comp.lang.ada
 help / color / mirror / Atom feed
* confusing string error
@ 2014-02-14 12:38 agent
  2014-02-14 13:03 ` Jacob Sparre Andersen
  0 siblings, 1 reply; 13+ messages in thread
From: agent @ 2014-02-14 12:38 UTC (permalink / raw)


Code fragment:

type FSATyp is (delim, op, dgt, allelse);
type TokenType is record
  Ustr : unbounded_string;
  State : FSATyp;
  delimCH : Character;
  delimstate : FSATyp;
end record;

ch: character;

begin
 ...

Token.uStr := null_unbounded_string;

ch now contains a plus sign, or an asterisk
Token.uStr := Token.uStr & ch

this last line fails with error Ada.Strings.INDEX_ERROR

I don't understand this.  

When ch has a digit or an alphabetic character this code works.

^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: confusing string error
  2014-02-14 12:38 confusing string error agent
@ 2014-02-14 13:03 ` Jacob Sparre Andersen
  2014-02-15  0:46   ` agent
  0 siblings, 1 reply; 13+ messages in thread
From: Jacob Sparre Andersen @ 2014-02-14 13:03 UTC (permalink / raw)


agent@drrob1.com writes:

> Code fragment:
>
> type FSATyp is (delim, op, dgt, allelse);
> type TokenType is record
>   Ustr : unbounded_string;
>   State : FSATyp;
>   delimCH : Character;
>   delimstate : FSATyp;
> end record;
>
> ch: character;
>
> begin
>  ...
>
> Token.uStr := null_unbounded_string;
>
> ch now contains a plus sign, or an asterisk
> Token.uStr := Token.uStr & ch
>
> this last line fails with error Ada.Strings.INDEX_ERROR

You haven't provided enough information to compile and evaluate your
example.

Greetings,

Jacob
-- 
»You know the world has gone crazy when the best rapper is a
 white guy, the best golfer is a black guy, the swiss hold
 the America's cup, France is accusing the U.S. of
 arrogance, and Germany doesn't want to go to war«

^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: confusing string error
  2014-02-14 13:03 ` Jacob Sparre Andersen
@ 2014-02-15  0:46   ` agent
  2014-02-15  1:50     ` adambeneschan
                       ` (2 more replies)
  0 siblings, 3 replies; 13+ messages in thread
From: agent @ 2014-02-15  0:46 UTC (permalink / raw)


On Fri, 14 Feb 2014 14:03:24 +0100, Jacob Sparre Andersen
<jacob@jacob-sparre.dk> wrote:

>agent@drrob1.com writes:
>
>> Code fragment:
>>
>
>You haven't provided enough information to compile and evaluate your
>example.
>
>Greetings,
>
>Jacob

I was trying not to bomb the newsgroup.  But it seems you want it.  So
here we go.  Assume that a valid spec file exists.  I included the
relevent types I define in it in my comments, as it is in my actual
code.

Package body tokenizea is
      TKNMAXSIZ : constant := 80;
      DGTMAXSIZ : constant := 9;
      OPMAXSIZ  : constant := 2;
      POUNDSIGN : constant Character := '#';  -- (* 35 *)
      PLUSSIGN  : constant Character := '+';  -- (* 43 *)
      COMMA     : constant Character := ',';  -- (* 44 *)
      MINUSSIGN : constant Character := '-';  -- (* 45 *)
      SEMCOL    : constant Character := ';';  -- (* 59 *)
      LTSIGN    : constant Character := '<';  -- (* 60 *)
      EQUALSIGN : constant Character := '=';  -- (* 61 *)
      GTSIGN    : constant Character := '>';  -- (* 62 *)
      MULTSIGN  : constant Character := '*';
      DIVSIGN   : constant Character := '/';
      ASCZERO   : constant :=  Character'Pos('0'); -- 48, 30H.
      SQUOTE    : constant Character := ''';  -- Character'Val(39)
      DQUOTE    : constant Character := '"';  -- Character'Val(34);
      NullChar  : constant Character :=  Character'Val(0);
      CharDgt0  : constant Character := '0';
      CharDgt9  : constant Character := '9';

-- Now declared in package spec file
--  TYPE FSATYP is (DELIM, OP, DGT, ALLELSE);
--  Type TokenType is Record
--    uStr: Unbound_String;
--    State : FSATYP;
--    delimCH : Character;
--    DelimState: FSATYP;
--    Sum : Integer;
--  END Record;
--  Type CharType is Record
--    ch : Character;
--    State : FSATYP;
--  END Record;

--  These variables are declared here to make the variable static so
-- to maintain
--  their values between procedure calls.
  CURPOSN,HOLDCURPOSN,PREVPOSN : Natural;
  TKNBUF,HOLDTKNBUF : Unbounded_String;
  FSAARRAY  : ARRAY (Character) OF FSATYP;
  out_of_range, token_too_long : EXCEPTION  ;

PROCEDURE InitFSAArray is
BEGIN
  FSAARRAY := (others => AllElse) ;
  FOR C in CharDgt0 .. CharDgt9 Loop
    FSAARRAY(C) := DGT;
  END Loop;
  FSAARRAY(NullChar) := DELIM;
  FSAARRAY(' ') := DELIM;
  FSAARRAY(',') := DELIM;
  FSAARRAY(';') := DELIM; -- (* semcol *)
  FSAARRAY('#') := OP;    -- (* poundsign *)
  FSAARRAY('*') := OP;    -- (* multsign *)
  FSAARRAY('+') := OP;    -- (* plussign *)
  FSAARRAY('-') := OP;    -- (* minussign *)
  FSAARRAY('/') := OP;    -- (* divsign *)
  FSAARRAY('<') := OP;    -- (* LTSIGN *)
  FSAARRAY('=') := OP;    -- (* EQUAL *)
  FSAARRAY('>') := OP;    -- (* GTSIGN *)
END InitFSAArray;

PROCEDURE INI1TKN(Str : String) is
-- *************************** INI1TKN 
--INITIALIZE TOKEN.
BEGIN
    CURPOSN  := 1;
    TKNBUF   := To_Unbounded_String(Str);
    PREVPOSN := 0;
    InitFSAArray;
END INI1TKN;

PROCEDURE PeekCHR(Char: OUT CharType; EOL : Out BOOLEAN) is
BEGIN
  IF CURPOSN > LENGTH(TKNBUF) THEN
    EOL := TRUE;
    Char.ch := NullChar;
    Char.State := DELIM;
    RETURN;
  ELSE
    EOL := FALSE;
  END IF;
  Char.CH := CAP(Element(TKNBUF,CURPOSN));
  Char.State := FSAARRAY(Char.CH);
END PeekCHR;

Procedure NextChr is
BEGIN
  CURPOSN := CurPosn + 1;
End NextChr;

PROCEDURE GETCHR(Char: OUT CharType; EOL : Out BOOLEAN) is
BEGIN
	PeekChr(Char, EOL);
	NextChr;
END GETCHR;

PROCEDURE UNGETCHR is
-- ********************************* UNGETCHR 
BEGIN
  IF (CURPOSN < 1) OR (CURPOSN > LENGTH(TKNBUF)+1) THEN
    RAISE out_of_range;
  END IF;
  CURPOSN := CurPosn - 1;
END UNGETCHR;

Function GETOPCODE(TOKEN : TokenType) RETURN Natural is
-- *************************** GETOPCODE 
-- GET OPCODE.
-- THIS ROUTINE RECEIVES A TOKEN OF FSATYP OP (MEANING IT IS AN
-- OPERATOR)
-- AND ANALYZES IT TO DETERMINE AN OPCODE, WHICH IS A 
-- Number FROM  1..15.
-- THE OPCODE ASSIGNMENTS FOR THE OP TOKENS ARE:
--  < is 1                  <= is 2
--  > is 3                  >= is 4
--  = is 5   == is 5        <> is 6    # is 7
--  + is 8                  += is 9
--  - is 10                 -= is 11
--  * is 12                 *= is 13
--  / is 14                 /= is 15
--
    CH1,CH2 : CHARacter;
    OpCode : Natural;
BEGIN
  OPCODE := 0;
  IF (LENGTH(Token.uStr) < 1) OR (LENGTH(Token.uStr) > 2) THEN
    RAISE token_too_long;
    RETURN OpCode;
  END IF;
  CH1 := Element(Token.uStr,1);
  CH2 := Element(Token.uStr,2);
  CASE CH1 is
    WHEN  LTSIGN => OPCODE := 1;
    WHEN  GTSIGN => OPCODE := 3;
    WHEN  EQUALSIGN => OPCODE := 5;
    WHEN  PLUSSIGN  => OPCODE := 8;
    WHEN  MINUSSIGN => OPCODE := 10;
    WHEN  POUNDSIGN => OPCODE := 7;
    WHEN  MULTSIGN  => OPCODE := 12;
    WHEN  DIVSIGN   => OPCODE := 14;
    WHEN OTHERS =>
      RETURN OpCode;
  END CASE;
  IF LENGTH(Token.uStr) = 1 THEN
    RETURN OpCode;
  ELSIF (CH2 = EQUALSIGN) AND (CH1 /= EQUALSIGN) AND 
      (CH1 /= POUNDSIGN) THEN
    OPCODE := OpCode + 1;
  ELSIF (CH1 = LTSIGN) AND (CH2 = GTSIGN) THEN
    OPCODE := 6;
  END IF;
  Return OpCode;
END GETOPCODE;

PROCEDURE GETTKN(TOKEN : Out TokenType; EOL : Out BOOLEAN) is
--*************************** GETTKN 
--
    NEGATV         : BOOLEAN;
    ORDCH,Len      : Natural;
    CHAR           : CHARType;
    QUOCHR         : CHARacter; --  (* Holds the active quote char *)
    QUOFLG         : BOOLEAN;
BEGIN
  QUOCHR := NullChar;
  QUOFLG := FALSE;
  PREVPOSN := CURPOSN;
  ToKeN.STATE := DELIM;
  Token.SUM := 0;
  Token.uStr := Null_Unbounded_String;
  NEGATV := FALSE;

  LOOP
    GETCHR(CHAR,EOL);
    IF EOL THEN
--  NO NEXT CHAR.  IF TKNSTATE IS DELIM, THEN GETTKN WAS CALLED WHEN
-- THERE WERE
--  NO MORE TOKENS ON LINE.  OTHERWISE IT MEANS THAT WE HAVE FETCHED
-- THE LAST
--  TOKEN ON THIS LINE.
      IF Token.STATE = DELIM THEN EOL := TRUE; END IF;
      EXIT;
    END IF;
    ORDCH := Character'Pos(Char.Ch);
    IF QUOFLG AND (Char.CH /= NullChar) THEN CHaR.STATE := ALLELSE;
END IF;
    CASE ToKeN.STATE is
      WHEN DELIM =>  -- token.state
        CASE CHaR.STATE is
          WHEN DELIM => 
-- NULL char is a special delimiter because it will
-- immediately cause a return even if there is no token yet,
-- i.e., the token is only delimiters.  This is because of
-- the NULL char is the string terminater for general strings
-- and especially for environment strings, for which this
-- TOKENIZE module was originally written. *)
                   IF CHAR.CH = NullChar THEN EXIT; END IF;
          WHEN OP => 
                     ToKeN.STATE := OP;
                     Token.uStr := Token.uStr & Char.Ch;
                     IF LENGTH(Token.uStr) > TKNMAXSIZ THEN
                       RAISE token_too_long;
                     END IF;
          WHEN DGT => 
                     Token.uStr := Token.uStr & Char.Ch;
                     ToKeN.STATE := DGT;
                     TOKEN.SUM := ORDCH - ASCZERO;
          WHEN ALLELSE => 
                     Token.uStr := Token.uStr & Char.Ch;
                     ToKeN.STATE := ALLELSE;
                     QUOFLG := (Char.CH = SQUOTE) OR (Char.CH =
DQUOTE);
                     IF QUOFLG THEN
                       QUOCHR := Char.CH;
                     ELSE
                       IF LENGTH(Token.uStr) > TKNMAXSIZ THEN
                         RAISE token_too_long;
                       END IF; -- if token too long
                       Token.SUM := ORDCH;
                     END IF; -- QUOFLG
        END CASE; -- Of Char.State
      WHEN OP => -- token.state
        CASE CHaR.STATE is
          WHEN DELIM =>
                       EXIT;
          WHEN OP =>
                    IF LENGTH(Token.uStr) > OPMAXSIZ THEN
                      RAISE token_too_long;
                    END IF;
                    Token.uStr := Token.uStr & Char.CH;
          WHEN DGT =>
                   IF (Element(Token.uStr,LENGTH(Token.uStr)) = '+')
OR
                     (Element(Token.uStr,LENGTH(Token.uStr)) = '-')
THEN
                     IF LENGTH(Token.uStr) = 1 THEN
                       IF ELEMENT(Token.uStr,1) = '-' THEN NEGATV :=
TRUE; END IF;
                       ToKeN.STATE := DGT;
-- OVERWRITE ARITHMETIC SIGN CHARACTER
                       Token.uStr := Null_Unbounded_String;
                       Token.uStr := Token.uStr & Char.CH;
                       Token.SUM := ORDCH - ASCZERO;
                     ELSE  -- TOKEN length > 1 SO MUST FIRST RETURN OP
                       UNGETCHR; -- (* UNGET THIS DIGIT CHAR *)
                       UNGETCHR; -- (* UNGET THE ARITH SIGN CHAR *)
                       Len := LENGTH(Token.uStr);
-- SO DELIMCH CORRECTLY RETURNS THE ARITH SIGN CHAR
                       Char.CH := Element(Token.uStr,Len); 
-- del last char of the token which is the sign character
                       Token.uStr := Delete(Token.uStr,Len,Len); 
                       EXIT;
                     END IF; -- if length of the token = 1
                   ELSE -- IF have a sign character
                     UNGETCHR;
                     EXIT;
                   END IF; -- If have a sign character
          WHEN ALLELSE =>
                   UNGETCHR;
                   EXIT;
        END CASE; -- Char.State
      WHEN DGT => -- tokenstate
        CASE CHaR.STATE is
          WHEN DELIM => EXIT;
          WHEN OP =>
                    UNGETCHR;
                    EXIT;
          WHEN DGT =>
                    Token.uStr := Token.uStr & Char.CH;
                    Token.SUM := 10*Token.SUM + ORDCH - ASCZERO;
          WHEN ALLELSE => 
                         UNGETCHR;
                         EXIT;
        END CASE; -- Char.State
      WHEN ALLELSE => -- tokenstate
        CASE CHaR.STATE is
          WHEN DELIM =>
--  Always exit if get a NULL char as a delim.  A quoted string can
-- only get here if CH is NULL.
                       EXIT;
          WHEN OP =>
                    UNGETCHR;
                    EXIT;
          WHEN DGT =>
                     IF LENGTH(Token.uStr) > TKNMAXSIZ THEN
                       RAISE token_too_long;
                     END IF; -- if token too long
                     Token.uStr := Token.uStr & Char.CH;
                     Token.SUM := Token.SUM + ORDCH;
          WHEN ALLELSE =>
                     IF Char.CH = QUOCHR THEN
                       QUOFLG := FALSE;
                       CHaR.STATE := DELIM; 
                       EXIT;
                     ELSE
                       IF LENGTH(Token.uStr) > TKNMAXSIZ THEN
                         RAISE token_too_long;
                       END IF; -- if token too long
                       Token.uStr := Token.uStr & Char.CH;
                       Token.SUM := Token.SUM + ORDCH;
                     END IF; -- if char is a quote char
        END CASE; --  Char.State
    END CASE; -- of Token.State
  END LOOP; -- to process characters
  Token.DELIMCH    := Char.CH;
  Token.DELIMSTATE := CHaR.STATE;
  IF (ToKeN.STATE = DGT) AND NEGATV THEN Token.SUM := -Token.SUM; END
IF;
--  For OP tokens, must return the opcode as the sum value.  Do this
--  by calling GETOPCODE.
  IF ToKeN.STATE = OP THEN
    Token.SUM := GetOpCode(Token);
  END IF;
END GETTKN;

BEGIN  -- main package body routine.
  HOLDCURPOSN := 0;  -- probably not needed in Ada.
  HOLDTKNBUF := Null_unbounded_string; -- looks like Ada automatically
init's all declarations to either 0 or null, as suits the data type
  InitFSAArray;
END tokenizea;



with tokenizea; use tokenizea;
Procedure testtokenizea is

  subType Str255Type is String(1..256);

  INBUF,s : Str255type;
  Token   : TokenType;
  Char    : CharType;
  I,J     : INTEGER;
  Last    : Natural;
  L       : LONG_INTeger;
  CH      : CHARacter;
  EOL     : Boolean;

BEGIN
    Put(" Input line : ");
    Get_Line(s,Last);
    New_line;
    I := s'last;
    Put(" Number of characters read is "); Put(Last);
    Put(".  Value of s'last is "); Put(I);
    INI1TKN(s(1..Last));
    LOOP
      GETTKN(TOKEN,EOL);
      Put(To_String(TOKEN.uStr));
      put(", token.state = ");
      Put(FSATyp'Image(ToKeN.STATE));
      Put(", sum=");
      Put(Token.Sum);
      Put(", DELIMCH= ");
      Put(Token.DELIMCH);
      Put(", DELIMSTATE= ");
      Put(FSATyp'Image(Token.DELIMSTATE));
      New_Line;
      EXIT When EOL;
    END LOOP; -- getting subsequent tokens on same line
END testtokenizea;



Thanks in advance

--Rob


^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: confusing string error
  2014-02-15  0:46   ` agent
@ 2014-02-15  1:50     ` adambeneschan
  2014-02-15  8:41       ` Simon Wright
  2014-02-15  1:57     ` adambeneschan
  2014-02-15  9:33     ` Simon Wright
  2 siblings, 1 reply; 13+ messages in thread
From: adambeneschan @ 2014-02-15  1:50 UTC (permalink / raw)


On Friday, February 14, 2014 4:46:51 PM UTC-8, ag...@drrob1.com wrote:

Just one note: this comment:

  HOLDTKNBUF := Null_unbounded_string; -- looks like Ada automatically 
init's all declarations to either 0 or null, as suits the data type

is wrong.  Integers are not initialized to anything and cannot be counted on; same for floats, booleans, other enumeration types, etc.  Access types *are* initialized to null by default, though, and the language specifically requires that Unbounded_String types be initialized by default.  It's possible that everything could get initialized to 0 in a particular implementation, though, either because the compiler vendors decided to make the code do that, or the OS does that when loading the program, or often just by luck.

                               -- Adam


^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: confusing string error
  2014-02-15  0:46   ` agent
  2014-02-15  1:50     ` adambeneschan
@ 2014-02-15  1:57     ` adambeneschan
  2014-02-15  9:33     ` Simon Wright
  2 siblings, 0 replies; 13+ messages in thread
From: adambeneschan @ 2014-02-15  1:57 UTC (permalink / raw)


On Friday, February 14, 2014 4:46:51 PM UTC-8, ag...@drrob1.com wrote:

I don't know what input you're entering.  I get the error on this line:

  CH2 := Element(Token.uStr,2);

which would make sense if the string's length is only 1.  I'm not sure why you think the error is on this line:

  Token.uStr := Token.uStr & ch;

which shouldn't be raising an Index_Error.

                          -- Adam

^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: confusing string error
  2014-02-15  1:50     ` adambeneschan
@ 2014-02-15  8:41       ` Simon Wright
  0 siblings, 0 replies; 13+ messages in thread
From: Simon Wright @ 2014-02-15  8:41 UTC (permalink / raw)


adambeneschan@gmail.com writes:

> It's possible that everything could get initialized to 0 in a
> particular implementation, though, either because the compiler vendors
> decided to make the code do that, or the OS does that when loading the
> program, or often just by luck.

A colleague's code failed disastrously when moved from Windows (the
development environment) to VxWorks (the target), precisely because
allocated records weren't initialized to zeros on the target.


^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: confusing string error
  2014-02-15  0:46   ` agent
  2014-02-15  1:50     ` adambeneschan
  2014-02-15  1:57     ` adambeneschan
@ 2014-02-15  9:33     ` Simon Wright
  2014-02-15 12:53       ` agent
  2014-02-15 13:15       ` agent
  2 siblings, 2 replies; 13+ messages in thread
From: Simon Wright @ 2014-02-15  9:33 UTC (permalink / raw)


agent@drrob1.com writes:

> I was trying not to bomb the newsgroup.  But it seems you want it.  So
> here we go.  Assume that a valid spec file exists.  I included the
> relevent types I define in it in my comments, as it is in my actual
> code.

You are the one asking the questions, we are the ones who are trying to
help. You do not make it easy; it just took me about half an hour to get
the code you supply to the state where it compiles; and I still don't
know what CAP is in

   Char.CH := CAP(Element(TKNBUF,CURPOSN));

so I just removed it (guessing it's supposed to convert to upper case).

There is no problem if I enter "12345" or "abcde" or "1+2". However, if
I enter "1+" or "1+2+" I get the same index error as Adam, on

      CH2 := Element(Token.UStr,2);

Postponing this statement to the point where we know the length is
greater than 1, I get no exceptions.

Perhaps, for the purposes of asking the question here, you should change
Testtokenizea so that the problematic input is a constant string rather
than being read from the input.

See for example http://stackoverflow.com/help/mcve - the 'minimal' isn't
quite so important as the 'complete', 'tested', and 'readable'.

^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: confusing string error
  2014-02-15  9:33     ` Simon Wright
@ 2014-02-15 12:53       ` agent
  2014-02-15 16:58         ` adambeneschan
  2014-02-15 13:15       ` agent
  1 sibling, 1 reply; 13+ messages in thread
From: agent @ 2014-02-15 12:53 UTC (permalink / raw)


On Sat, 15 Feb 2014 09:33:25 +0000, Simon Wright <simon@pushface.org>
wrote:

>agent@drrob1.com writes:
>
>> I was trying not to bomb the newsgroup.  But it seems you want it.  So
>> here we go.  Assume that a valid spec file exists.  I included the
>> relevent types I define in it in my comments, as it is in my actual
>> code.
>
>You are the one asking the questions, we are the ones who are trying to
>help. You do not make it easy; it just took me about half an hour to get
>the code you supply to the state where it compiles; and I still don't
>know what CAP is in
>
>   Char.CH := CAP(Element(TKNBUF,CURPOSN));
>
>so I just removed it (guessing it's supposed to convert to upper case).
>
>There is no problem if I enter "12345" or "abcde" or "1+2". However, if
>I enter "1+" or "1+2+" I get the same index error as Adam, on
>
>      CH2 := Element(Token.UStr,2);
>
>Postponing this statement to the point where we know the length is
>greater than 1, I get no exceptions.
>
>Perhaps, for the purposes of asking the question here, you should change
>Testtokenizea so that the problematic input is a constant string rather
>than being read from the input.
>
>See for example http://stackoverflow.com/help/mcve - the 'minimal' isn't
>quite so important as the 'complete', 'tested', and 'readable'.


I guess this is a case of the error code does not match the error.  I
kept getting an error message about the character appending line.

I tried GDB and stepped through, and seemed to get the same error.

I don't know why, but I agree that is the error.  I understand now
that I knew that in Modula-2 when the token was 1 character, then CH2
would just get the null termination character for all strings.

I still don't understand why stepping line by line did not show me the
correct failure point.

Thanks guys for your help

--rob

PS: CAP is a holdover from Modula-2.  I am used to it, and it is
defined in my spec file to renames Ada.Character.Handling.To_Upper

^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: confusing string error
  2014-02-15  9:33     ` Simon Wright
  2014-02-15 12:53       ` agent
@ 2014-02-15 13:15       ` agent
  2014-02-15 17:56         ` Jeffrey Carter
  1 sibling, 1 reply; 13+ messages in thread
From: agent @ 2014-02-15 13:15 UTC (permalink / raw)


On Sat, 15 Feb 2014 09:33:25 +0000, Simon Wright <simon@pushface.org>
wrote:

>agent@drrob1.com writes:
>
>> I was trying not to bomb the newsgroup.  But it seems you want it.  So
>> here we go.  Assume that a valid spec file exists.  I included the
>> relevent types I define in it in my comments, as it is in my actual
>> code.
>
>You are the one asking the questions, we are the ones who are trying to
>help. You do not make it easy; it just took me about half an hour to get
>the code you supply to the state where it compiles; and I still don't
>know what CAP is in
>
ok.  Next time I will post the .ads also.  As I said, I didn't want to
bomb the group.  I guess posting code is not bombing it.

--rob

^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: confusing string error
  2014-02-15 12:53       ` agent
@ 2014-02-15 16:58         ` adambeneschan
  2014-02-15 18:29           ` Simon Wright
  0 siblings, 1 reply; 13+ messages in thread
From: adambeneschan @ 2014-02-15 16:58 UTC (permalink / raw)


On Saturday, February 15, 2014 4:53:42 AM UTC-8, ag...@drrob1.com wrote:
> On Sat, 15 Feb 2014 09:33:25 +0000, Simon Wright wrote:

> I guess this is a case of the error code does not match the error.  I
> kept getting an error message about the character appending line.
> 
> I tried GDB and stepped through, and seemed to get the same error.

Sometimes the Put_Line debugger does a better job than other debuggers.


> I still don't understand why stepping line by line did not show me the
> correct failure point.

I don't have a way to tell.  (I found out what line it was because I tried it using Irvine Compiler's debugger, which did tell me what the correct line was.)  There are some possible reasons that I can think of why incorrect lines might show up (based on my general experience, not on any particular knowledge of GNAT/GDB).  The source files could just be out of sync; e.g. you edited a file to add some comments but didn't recompile it, or you linked using an object file from the wrong place.  If your source was in one large file, and GNATCHOP was called on to split it up, the line may refer to the larger file rather than the split-up one or vice versa.  Finally, optimization can cause problems when the compiler rearranges code; it can be very difficult to get it to display correct line numbers.  Plus we can't rule out a compiler bug.

                              -- Adam


^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: confusing string error
  2014-02-15 13:15       ` agent
@ 2014-02-15 17:56         ` Jeffrey Carter
  0 siblings, 0 replies; 13+ messages in thread
From: Jeffrey Carter @ 2014-02-15 17:56 UTC (permalink / raw)


On 02/15/2014 06:15 AM, agent@drrob1.com wrote:
>>
> ok.  Next time I will post the .ads also.  As I said, I didn't want to
> bomb the group.  I guess posting code is not bombing it.

Generally we expect some effort on the poster's part to reduce the code 
demonstrating the error as much as possible. In this case, a compilable 
main-program procedure containing the offending subprogram and calling it with a 
string that causes the error would have been helpful.

-- 
Jeff Carter
"In the frozen land of Nador they were forced to
eat Robin's minstrels, and there was much rejoicing."
Monty Python & the Holy Grail
70

^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: confusing string error
  2014-02-15 16:58         ` adambeneschan
@ 2014-02-15 18:29           ` Simon Wright
  2014-02-17 12:57             ` agent
  0 siblings, 1 reply; 13+ messages in thread
From: Simon Wright @ 2014-02-15 18:29 UTC (permalink / raw)


adambeneschan@gmail.com writes:

> On Saturday, February 15, 2014 4:53:42 AM UTC-8, ag...@drrob1.com wrote:
>> On Sat, 15 Feb 2014 09:33:25 +0000, Simon Wright wrote:
>
>> I guess this is a case of the error code does not match the error.  I
>> kept getting an error message about the character appending line.
>> 
>> I tried GDB and stepped through, and seemed to get the same error.
>
> Sometimes the Put_Line debugger does a better job than other debuggers.
>
>
>> I still don't understand why stepping line by line did not show me the
>> correct failure point.
>
> I don't have a way to tell.  (I found out what line it was because I
> tried it using Irvine Compiler's debugger, which did tell me what the
> correct line was.)  There are some possible reasons that I can think
> of why incorrect lines might show up (based on my general experience,
> not on any particular knowledge of GNAT/GDB).  The source files could
> just be out of sync; e.g. you edited a file to add some comments but
> didn't recompile it, or you linked using an object file from the wrong
> place.  If your source was in one large file, and GNATCHOP was called
> on to split it up, the line may refer to the larger file rather than
> the split-up one or vice versa.  Finally, optimization can cause
> problems when the compiler rearranges code; it can be very difficult
> to get it to display correct line numbers.  Plus we can't rule out a
> compiler bug.

GNAT/GDB finds it correctly for me;

   (gdb) catch exception
   Catchpoint 1: all Ada exceptions
   (gdb) run
   Starting program: /Users/simon/tmp/testtokenizea 
    Input line : 1+

    Number of characters read is           2.  Value of s'last is         2561, token.state = DGT, sum=          1, DELIMCH= +, DELIMSTATE= OP

   Catchpoint 1, ADA.STRINGS.INDEX_ERROR at 0x0000000100001cdb in tokenizea__getopcode (token=...) at tokenizea.adb:121
   121	      CH2 := Element(Token.UStr,2);


^ permalink raw reply	[flat|nested] 13+ messages in thread

* Re: confusing string error
  2014-02-15 18:29           ` Simon Wright
@ 2014-02-17 12:57             ` agent
  0 siblings, 0 replies; 13+ messages in thread
From: agent @ 2014-02-17 12:57 UTC (permalink / raw)


On Sat, 15 Feb 2014 18:29:29 +0000, Simon Wright <simon@pushface.org>
wrote:

>adambeneschan@gmail.com writes:
>
>> On Saturday, February 15, 2014 4:53:42 AM UTC-8, ag...@drrob1.com wrote:
>>> On Sat, 15 Feb 2014 09:33:25 +0000, Simon Wright wrote:
>>
>>> I guess this is a case of the error code does not match the error.  I
>>> kept getting an error message about the character appending line.
>>> 
>>> I tried GDB and stepped through, and seemed to get the same error.
>
>GNAT/GDB finds it correctly for me;
>
>   (gdb) catch exception
>   Catchpoint 1: all Ada exceptions
>   (gdb) run
>   Starting program: /Users/simon/tmp/testtokenizea 
>    Input line : 1+
>
>    Number of characters read is           2.  Value of s'last is         2561, token.state = DGT, sum=          1, DELIMCH= +, DELIMSTATE= OP
>
>   Catchpoint 1, ADA.STRINGS.INDEX_ERROR at 0x0000000100001cdb in tokenizea__getopcode (token=...) at tokenizea.adb:121
>   121	      CH2 := Element(Token.UStr,2);

I'll have to use the catch command in the future, now that you have
taught it to me.

Thanks
--rob


^ permalink raw reply	[flat|nested] 13+ messages in thread

end of thread, other threads:[~2014-02-17 12:57 UTC | newest]

Thread overview: 13+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2014-02-14 12:38 confusing string error agent
2014-02-14 13:03 ` Jacob Sparre Andersen
2014-02-15  0:46   ` agent
2014-02-15  1:50     ` adambeneschan
2014-02-15  8:41       ` Simon Wright
2014-02-15  1:57     ` adambeneschan
2014-02-15  9:33     ` Simon Wright
2014-02-15 12:53       ` agent
2014-02-15 16:58         ` adambeneschan
2014-02-15 18:29           ` Simon Wright
2014-02-17 12:57             ` agent
2014-02-15 13:15       ` agent
2014-02-15 17:56         ` Jeffrey Carter

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox