comp.lang.ada
 help / color / mirror / Atom feed
* Re: GETARG in Ada?
  1999-02-27  0:00 GETARG in Ada? Lou Glassy
  1999-02-27  0:00 ` bob
@ 1999-02-27  0:00 ` David C. Hoos, Sr.
  1999-02-27  0:00   ` bill
  1999-02-28  0:00 ` Matthew Heaney
  2 siblings, 1 reply; 8+ messages in thread
From: David C. Hoos, Sr. @ 1999-02-27  0:00 UTC (permalink / raw)



Lou Glassy wrote in message <7b9r2g$lha$1@netra.msu.montana.edu>...
>Question:  Can anyone help me clean up this program?
>           No, this is not a homework assignment.
>           I'm an old Fortran programmer, learning Ada...
>
>Here is a little Fortran program (compiles, runs with g77 under Linux)
>that prints out the arguments on the Unix command line:
>
>        PROGRAM TEST_GETARG
>        IMPLICIT NONE
>
>        INTEGER ARG_COUNT, I
>        CHARACTER(LEN=20) CURRENT_ARG
>
>        ARG_COUNT = IARGC()
>        PRINT *, 'number of args = ', ARG_COUNT
>        DO I = 1, ARG_COUNT
>                CALL GETARG(I, CURRENT_ARG)
>                PRINT *, 'ARG ', I, '=', CURRENT_ARG
>        END DO
>
>        END
>
>I'd like to do the same thing in Ada-95.  For concreteness, I'm
>using GNAT (3.10p), but I'm guessing any A95 implementation on a
>Unix box would eat something similar to the following:
>
>with TEXT_IO;           use TEXT_IO;
>with ADA.COMMAND_LINE;  use ADA.COMMAND_LINE;
>with ADA.STRINGS;       use ADA.STRINGS;
>with ADA.STRINGS.FIXED; use ADA.STRINGS.FIXED;
>
>procedure TEST_GETARG is
>
>    package INT_IO is new INTEGER_IO(INTEGER);
>    use INT_IO;
>
>    ARG_COUNT: INTEGER;
>
>    MAX_ARG_LENGTH: constant INTEGER := 80;
>
>    ARG: STRING(1..MAX_ARG_LENGTH) := (others => ' ');
>
>begin
>
>    ARG_COUNT := ADA.COMMAND_LINE.ARGUMENT_COUNT;
>    PUT("number of command-line args = ");
>    PUT(ARG_COUNT);
>    NEW_LINE;
>
>    if ARG_COUNT > 0 then
>
>        for CURRENT_ARG in 1..ARG_COUNT loop
>            PUT("arg ");
>            PUT(CURRENT_ARG);
>            PUT("=");
>            ARG(1..ADA.COMMAND_lINE.ARGUMENT(CURRENT_ARG)'LENGTH) :=
>                ADA.COMMAND_lINE.ARGUMENT(CURRENT_ARG);
>            PUT(TRIM(ARG,RIGHT));
>            NEW_LINE;
>        end loop;
>
>    end if;
>
>end TEST_GETARG;
>
>------------------------------------------
>
>My A95 "TEST_GETARG" program works, I'm just trying to figure
>out how to write it more cleanly.
>
This is the code from one of the examples supplied with GNAT.
It uses gnat-specific IO, but you could easily replace the Gnat.IO calls
with calls to Text_IO.

You've made much more work for yourself than necessary; there's no need to
"trim" or anything like that, because the put procedure will put only as
many characters as there are in the string.

By the way, 3.10p is going on two years old.  Why don't you get 3.11p?

Hope this helps.

with Ada.Command_Line;
with Gnat.Io; use Gnat.Io;

procedure Test_CL is
begin
   --  Writes out the command name (argv[0])
   Put ("      The command name : ");
   Put (Ada.Command_Line.Command_Name);
   New_Line;

   --  Writes out the number of arguments passed to the program (argc)
   Put ("The number of arguments: ");
   Put (Ada.Command_Line.Argument_Count);
   New_Line;

   --  Writes out all the arguments using the Argument function.
   --  (BE CAREFUL because if the number you pass to Argument is not
   --   in the range 1 .. Argument_Count you will get Constraint_Error!)
   for I in 1 .. Ada.Command_Line.Argument_Count loop
      Put ("             Argument ");
      Put (I);
      Put (": ");
      Put (Ada.Command_Line.Argument (I));
      New_Line;
   end loop;
end Test_CL;







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

* Re: GETARG in Ada?
  1999-02-27  0:00 ` David C. Hoos, Sr.
@ 1999-02-27  0:00   ` bill
  1999-02-28  0:00     ` James S. Rogers
  1999-03-02  0:00     ` Stephen Leake
  0 siblings, 2 replies; 8+ messages in thread
From: bill @ 1999-02-27  0:00 UTC (permalink / raw)




it should be possible to call the Unix getopt() function from Ada. why
not do this? getopt is designed to break command line arguments
easily. 

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

GETOPT(1)                                               GETOPT(1)

NAME
       getopt - parse command options (enhanced)

SYNOPSIS
       getopt optstring parameters

       getopt [options] [--] optstring parameters

       getopt [options] -o|--options optstring [options] [--] 
              parameters

DESCRIPTION
 getopt is used to break up (parse) options in command lines for 
easy parsing by shell pro-cedures, and to check for legal options.  
It uses the GNU getopt(3) routines to do this.




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

* Re: GETARG in Ada?
  1999-02-27  0:00 GETARG in Ada? Lou Glassy
@ 1999-02-27  0:00 ` bob
  1999-02-27  0:00 ` David C. Hoos, Sr.
  1999-02-28  0:00 ` Matthew Heaney
  2 siblings, 0 replies; 8+ messages in thread
From: bob @ 1999-02-27  0:00 UTC (permalink / raw)


--
-- If I were doing this, I would get rid of ALL "use" clauses except for
-- "use type". But this is just my personal preference. Since you knew the
-- numerics were integers, you could have used the "'image" clause and not
-- had to use "integer_io" at all.
-- Here is a quick set of possible mods.
-- I suspect you will get many variations on this, one for everyone who
-- responds.
-- I think the important thing is you are expanding your knowledge.
--
-- cheers...bob
--
with TEXT_IO;           use TEXT_IO;
with ADA.COMMAND_LINE;  -- use ADA.COMMAND_LINE;  
with ADA.STRINGS;       use ADA.STRINGS;
with ADA.STRINGS.FIXED; use ADA.STRINGS.FIXED;

procedure TEST_GETARG is

--    package INT_IO is new INTEGER_IO(INTEGER);
--    use INT_IO;

    ARG_COUNT: INTEGER;

    MAX_ARG_LENGTH: constant INTEGER := 80;

    ARG: STRING(1..MAX_ARG_LENGTH) := (others => ' ');

begin

    ARG_COUNT := ADA.COMMAND_LINE.ARGUMENT_COUNT;
    put_line("number of command-line args =" & integer'image(arg_count));
--    PUT("number of command-line args = ");
--    PUT(ARG_COUNT, 0);
--    NEW_LINE;

--    if ARG_COUNT > 0 then 
    
        for CURRENT_ARG in 1..ARG_COUNT loop
            PUT("arg" & integer'image(current_arg) & " = ");
--            PUT(CURRENT_ARG);
--            PUT("=");
            ARG(1..ADA.COMMAND_lINE.ARGUMENT(CURRENT_ARG)'LENGTH) := 
                ADA.COMMAND_lINE.ARGUMENT(CURRENT_ARG);
            PUT(TRIM(ARG,RIGHT));
            NEW_LINE;
        end loop;
    
--    end if;

end TEST_GETARG;
--
--  linux:~/atest> ada getarg.adb
--  gcc -c -g getarg.adb
--  getarg.adb:6:11: warning: file name does not match unit name, should be
"test_getarg.adb"
--  gnatbind -x getarg.ali
--  gnatlink -g getarg.ali
--  linux:~/atest> getarg abc def
--  number of command-line args = 2
--  arg 1 = abc
--  arg 2 = def
-- ***************************************************************
Lou Glassy <glassy@acheta.nervana.montana.edu> wrote in article
<7b9r2g$lha$1@netra.msu.montana.edu>...
> Question:  Can anyone help me clean up this program?
>            No, this is not a homework assignment.
>            I'm an old Fortran programmer, learning Ada... 
> 
> Here is a little Fortran program (compiles, runs with g77 under Linux)
> that prints out the arguments on the Unix command line:
> 
>         PROGRAM TEST_GETARG
>         IMPLICIT NONE
> 
>         INTEGER ARG_COUNT, I
>         CHARACTER(LEN=20) CURRENT_ARG
> 
>         ARG_COUNT = IARGC()
>         PRINT *, 'number of args = ', ARG_COUNT
>         DO I = 1, ARG_COUNT
>                 CALL GETARG(I, CURRENT_ARG)
>                 PRINT *, 'ARG ', I, '=', CURRENT_ARG
>         END DO 
> 
>         END
> 
> I'd like to do the same thing in Ada-95.  For concreteness, I'm 
> using GNAT (3.10p), but I'm guessing any A95 implementation on a 
> Unix box would eat something similar to the following:
> 
> with TEXT_IO;           use TEXT_IO;
> with ADA.COMMAND_LINE;  use ADA.COMMAND_LINE;  
> with ADA.STRINGS;       use ADA.STRINGS;
> with ADA.STRINGS.FIXED; use ADA.STRINGS.FIXED;
> 
> procedure TEST_GETARG is
> 
>     package INT_IO is new INTEGER_IO(INTEGER);
>     use INT_IO;
> 
>     ARG_COUNT: INTEGER;
> 
>     MAX_ARG_LENGTH: constant INTEGER := 80;
> 
>     ARG: STRING(1..MAX_ARG_LENGTH) := (others => ' ');
> 
> begin
> 
>     ARG_COUNT := ADA.COMMAND_LINE.ARGUMENT_COUNT;
>     PUT("number of command-line args = ");
>     PUT(ARG_COUNT);
>     NEW_LINE;
> 
>     if ARG_COUNT > 0 then 
>     
>         for CURRENT_ARG in 1..ARG_COUNT loop
>             PUT("arg ");
>             PUT(CURRENT_ARG);
>             PUT("=");
>             ARG(1..ADA.COMMAND_lINE.ARGUMENT(CURRENT_ARG)'LENGTH) := 
>                 ADA.COMMAND_lINE.ARGUMENT(CURRENT_ARG);
>             PUT(TRIM(ARG,RIGHT));
>             NEW_LINE;
>         end loop;
>     
>     end if;
> 
> end TEST_GETARG;
> 
> ------------------------------------------
> 
> My A95 "TEST_GETARG" program works, I'm just trying to figure
> out how to write it more cleanly.
> 
> I much appreciate Ehud Lamm's "Ada Idiom Page" and other postings 
> kind souls have made to comp.lang.ada.  My question is, how would
> an experienced Ada programmer write my little TEST_GETARG program 
> in Ada-95?  Is there an easier way to handle strings than this?
> 
> Thanks in advance...
> 
> -lou
> 
> Lou Glassy (glassy@cs.montana.edu)
> 




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

* GETARG in Ada?
@ 1999-02-27  0:00 Lou Glassy
  1999-02-27  0:00 ` bob
                   ` (2 more replies)
  0 siblings, 3 replies; 8+ messages in thread
From: Lou Glassy @ 1999-02-27  0:00 UTC (permalink / raw)


Question:  Can anyone help me clean up this program?
           No, this is not a homework assignment.
           I'm an old Fortran programmer, learning Ada... 

Here is a little Fortran program (compiles, runs with g77 under Linux)
that prints out the arguments on the Unix command line:

        PROGRAM TEST_GETARG
        IMPLICIT NONE

        INTEGER ARG_COUNT, I
        CHARACTER(LEN=20) CURRENT_ARG

        ARG_COUNT = IARGC()
        PRINT *, 'number of args = ', ARG_COUNT
        DO I = 1, ARG_COUNT
                CALL GETARG(I, CURRENT_ARG)
                PRINT *, 'ARG ', I, '=', CURRENT_ARG
        END DO 

        END

I'd like to do the same thing in Ada-95.  For concreteness, I'm 
using GNAT (3.10p), but I'm guessing any A95 implementation on a 
Unix box would eat something similar to the following:

with TEXT_IO;           use TEXT_IO;
with ADA.COMMAND_LINE;  use ADA.COMMAND_LINE;  
with ADA.STRINGS;       use ADA.STRINGS;
with ADA.STRINGS.FIXED; use ADA.STRINGS.FIXED;

procedure TEST_GETARG is

    package INT_IO is new INTEGER_IO(INTEGER);
    use INT_IO;

    ARG_COUNT: INTEGER;

    MAX_ARG_LENGTH: constant INTEGER := 80;

    ARG: STRING(1..MAX_ARG_LENGTH) := (others => ' ');

begin

    ARG_COUNT := ADA.COMMAND_LINE.ARGUMENT_COUNT;
    PUT("number of command-line args = ");
    PUT(ARG_COUNT);
    NEW_LINE;

    if ARG_COUNT > 0 then 
    
        for CURRENT_ARG in 1..ARG_COUNT loop
            PUT("arg ");
            PUT(CURRENT_ARG);
            PUT("=");
            ARG(1..ADA.COMMAND_lINE.ARGUMENT(CURRENT_ARG)'LENGTH) := 
                ADA.COMMAND_lINE.ARGUMENT(CURRENT_ARG);
            PUT(TRIM(ARG,RIGHT));
            NEW_LINE;
        end loop;
    
    end if;

end TEST_GETARG;

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

My A95 "TEST_GETARG" program works, I'm just trying to figure
out how to write it more cleanly.

I much appreciate Ehud Lamm's "Ada Idiom Page" and other postings 
kind souls have made to comp.lang.ada.  My question is, how would
an experienced Ada programmer write my little TEST_GETARG program 
in Ada-95?  Is there an easier way to handle strings than this?

Thanks in advance...

-lou

Lou Glassy (glassy@cs.montana.edu)




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

* Re: GETARG in Ada?
  1999-02-27  0:00 GETARG in Ada? Lou Glassy
  1999-02-27  0:00 ` bob
  1999-02-27  0:00 ` David C. Hoos, Sr.
@ 1999-02-28  0:00 ` Matthew Heaney
  2 siblings, 0 replies; 8+ messages in thread
From: Matthew Heaney @ 1999-02-28  0:00 UTC (permalink / raw)


Lou Glassy <glassy@acheta.nervana.montana.edu> writes:

> Question:  Can anyone help me clean up this program?
>            No, this is not a homework assignment.
>            I'm an old Fortran programmer, learning Ada... 

My version is below.  It compiles and runs using gnat v3.10p on
linuxppc.


with Ada.Command_Line; use Ada.Command_Line;
with Ada.Text_IO;      use Ada.Text_IO;

procedure Test_Getarg is

   Count : constant Natural := Argument_Count;

begin

   Put_Line
     ("number of command-line args =" &
      Integer'Image (Count));

    for I in Integer range 1 .. Count loop

       Put_Line
         ("arg" &
          Integer'Image (I) &
          "=" &
          Argument (I));

    end loop;


end Test_Getarg;







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

* Re: GETARG in Ada?
  1999-02-27  0:00   ` bill
@ 1999-02-28  0:00     ` James S. Rogers
  1999-03-02  0:00     ` Stephen Leake
  1 sibling, 0 replies; 8+ messages in thread
From: James S. Rogers @ 1999-02-28  0:00 UTC (permalink / raw)



bill@cool wrote in message <7ba3n9$kbr@drn.newsguy.com>...
>
>
>it should be possible to call the Unix getopt() function from Ada. why
>not do this? getopt is designed to break command line arguments
>easily.


This is useful if you are parsing options such as "-f File_Name".
It is, of course, only useful if you are using UNIX-like operating systems.

For simple command line arguments without accompanying arguments,
or when not using UNIX, the Ada.Command_Line package is simpler.
It is the only reasonably portable answer.

Some operating systems do not support command line arguments.  The
LRM states that Ada.Command_Line is not supported on those operating
systems.

Jim Rogers
Colorado Springs, Colorado






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

* Re: GETARG in Ada?
  1999-02-27  0:00   ` bill
  1999-02-28  0:00     ` James S. Rogers
@ 1999-03-02  0:00     ` Stephen Leake
  1999-03-02  0:00       ` nabbasi
  1 sibling, 1 reply; 8+ messages in thread
From: Stephen Leake @ 1999-03-02  0:00 UTC (permalink / raw)


bill@cool writes:

> it should be possible to call the Unix getopt() function from Ada. why
> not do this? getopt is designed to break command line arguments
> easily. 
> 
> <snip man entry>
>
> It uses the GNU getopt(3) routines to do this.

As this last line says, what you want to call from Ada is the GNU
getopt C function. I just ran across this function in some code I was
reading recently, and it does look powerful. Here's the spec from the
gcc sources (edited to remove #ifdefs that handle non-standard
compilers):

/* For communication from `getopt' to the caller.
   When `getopt' finds an option that takes an argument,
   the argument value is returned here.
   Also, when `ordering' is RETURN_IN_ORDER,
   each non-option ARGV-element is returned here.  */

extern char *optarg;

/* Index in ARGV of the next element to be scanned.
   This is used for communication to and from the caller
   and for communication between successive calls to `getopt'.

   On entry to `getopt', zero means this is the first call; initialize.

   When `getopt' returns -1, this is the index of the first of the
   non-option elements that the caller should itself scan.

   Otherwise, `optind' communicates from one call to the next
   how much of ARGV has been scanned so far.  */

extern int optind;

/* Callers store zero here to inhibit the error message `getopt' prints
   for unrecognized options.  */

extern int opterr;

/* Set to an option character which was unrecognized.  */

extern int optopt;

/* Describe the long-named options requested by the application.
   The LONG_OPTIONS argument to getopt_long or getopt_long_only is a vector
   of `struct option' terminated by an element containing a name which is
   zero.

   The field `has_arg' is:
   no_argument		(or 0) if the option does not take an argument,
   required_argument	(or 1) if the option requires an argument,
   optional_argument 	(or 2) if the option takes an optional argument.

   If the field `flag' is not NULL, it points to a variable that is set
   to the value given in the field `val' when the option is found, but
   left unchanged if the option is not found.

   To have a long-named option do something other than set an `int' to
   a compiled-in constant, such as set a value from `optarg', set the
   option's `flag' field to zero and its `val' field to a nonzero
   value (the equivalent single-letter option character, if there is
   one).  For long options that have a zero `flag' field, `getopt'
   returns the contents of the `val' field.  */

struct option
{
  const char *name;
  int has_arg;
  int *flag;
  int val;
};

/* Names for the values of the `has_arg' field of `struct option'.  */

#define	no_argument		0
#define required_argument	1
#define optional_argument	2

extern int getopt (int argc, char *const *argv, const char *shortopts);


It should be possible to write an Ada binding to this, but it's
certainly not a beginner's task. Most of the char *'s will point to
static strings, so you probably don't have to worry about dynamic
string allocation. It would be nice to hide the global variables, but
since the command line is a global resource, maybe they aren't so bad.

Anyone want to give it a shot?

-- Stephe




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

* Re: GETARG in Ada?
  1999-03-02  0:00     ` Stephen Leake
@ 1999-03-02  0:00       ` nabbasi
  0 siblings, 0 replies; 8+ messages in thread
From: nabbasi @ 1999-03-02  0:00 UTC (permalink / raw)


In article <uaexv92ug.fsf@gsfc.nasa.gov>, Stephen says...
>
 
>
>As this last line says, what you want to call from Ada is the GNU
>getopt C function. I just ran across this function in some code I was
>reading recently, and it does look powerful. Here's the spec from the
>gcc sources (edited to remove #ifdefs that handle non-standard
>compilers):
>
>/* For communication from `getopt' to the caller.

..snipp...
 
>
>Anyone want to give it a shot?
>
>-- Stephe

You can download the Ada getopt package from my ada page:

http://home.pacbell.net/nma123

Nasser




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

end of thread, other threads:[~1999-03-02  0:00 UTC | newest]

Thread overview: 8+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
1999-02-27  0:00 GETARG in Ada? Lou Glassy
1999-02-27  0:00 ` bob
1999-02-27  0:00 ` David C. Hoos, Sr.
1999-02-27  0:00   ` bill
1999-02-28  0:00     ` James S. Rogers
1999-03-02  0:00     ` Stephen Leake
1999-03-02  0:00       ` nabbasi
1999-02-28  0:00 ` Matthew Heaney

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