comp.lang.ada
 help / color / mirror / Atom feed
* Re: VAX Ada question.
@ 1991-09-18 23:54 agate!bionet!uwm.edu!cs.utexas.edu!qt.cs.utexas.edu!zaphod.mps.ohio-state
  0 siblings, 0 replies; 3+ messages in thread
From: agate!bionet!uwm.edu!cs.utexas.edu!qt.cs.utexas.edu!zaphod.mps.ohio-state @ 1991-09-18 23:54 UTC (permalink / raw)


In article <1991Sep18.043715.13529@ennews.eas.asu.edu> yhartojo@enuxha.eas.asu.
edu (Francis Hartojo) writes:
>
>	Hi netters, I just have one quick question and it should be trivial for
>VAX Ada experts.
>
>	I want to invoke a command line string from an Ada program, how can I
>do that?  I mean what package should I use?  And exactly which procedure will
>allow me to do it?
>
>	I am sorry if turns out that there are more than one question.  Any
>help, suggestion will be greatly appreciated.
>
>n.b.:  if you guys do not mind, I have one additional question (believe me,
>       this time there is really only one), how do you handle command line
>       parameters in VAX Ada?
>
>--
>Francis Hartojo                  | DECnet:   ENVMSA::YHARTOJO
>                                 | Bitnet:   AUYXH@ASUACVAX.BITNET
>Comp. Science & Engr. Department | Internet: YHARTOJO@ENVMSA.EAS.ASU.EDU
>Arizona State University         | Phone:    (602) 921-1342


--
-- VMS RTL_Routines LIB$ LIB$GET_FOREIGN
-- =====================================
--
-- LIB$GET_FOREIGN  requests  the  calling  image's  Command   Language
-- Interpreter  (CLI)  to  return the contents of the "foreign command"
-- line that activated the current image.
--
--    Format:
--
--      LIB$GET_FOREIGN  get-str [,user-prompt] [,out-len]
--                       [,force-prompt]
--
--    Arguments:
--
-- get-str
--
-- VMS usage: char_string
-- type: character string
-- access: write only
-- mechanism: by descriptor
--
-- String which LIB$GET_FOREIGN uses to  receive  the  foreign  command
-- line.   The get-str argument is the address of a descriptor pointing
-- to this string.  If the foreign command text returned  was  obtained
-- by prompting to SYS$INPUT (see the description of force-prompt), the
-- text is translated to uppercase so as to  be  more  consistent  with
-- text returned from the CLI.
--
-- user-prompt
--
-- VMS usage: char_string
-- type: character string
-- access: read only
-- mechanism: by descriptor
--
-- Optional user-supplied prompt for text which LIB$GET_FOREIGN uses if
-- no  command-line text is available.  The user-prompt argument is the
-- address of a descriptor pointing to the user prompt.  If omitted, no
-- prompting  is  performed.   It  is  recommended  that user-prompt be
-- specified.  If user-prompt is omitted and if no command-line text is
-- available, a zero-length string will be returned.
--
-- out-len
--
-- VMS usage: word_unsigned
-- type: word (unsigned)
-- access: write only
-- mechanism: by reference
--
-- Number  of  bytes  written  into  get-str  by  LIB$GET_FOREIGN,  not
-- counting padding in the case of a fixed-length get-str.  The out-len
-- argument  is  the  address  of   an   unsigned   word   into   which
-- LIB$GET_FOREIGN writes the number of bytes.
--
-- force-prompt
--
-- VMS usage: longword_signed
-- type: longword integer (signed)
-- access: modify
-- mechanism: by reference
--
-- Value which LIB$GET_FOREIGN uses to control whether or not prompting
-- is  to  be performed.  The force-prompt argument is the address of a
-- signed longword integer containing this value.  If the  low  bit  of
-- force-prompt  is  zero,  or if force-prompt is omitted, prompting is
-- done only if the CLI does not return a command line.  If the low bit
-- is 1, prompting is done unconditionally.  If specified, force-prompt
-- is set to 1 before returning to the caller.
--

package FOREIGN_COMMAND_LINE is

  procedure Get_Foreign(
      Condition      : out integer;
      Command_Line   : out string;
      User_Prompt    : in  string;
      Command_Length : out short_integer;
      Force_Prompt   : in out integer );
  pragma interface( system, Get_Foreign );
  pragma import_valued_procedure( Get_Foreign, "LIB$get_foreign",
         ( integer, string,     string,     short_integer, integer   ),
         ( value,   descriptor, descriptor, reference,     reference ));

  function Get_Foreign( Prompt : string := "Argument: " ) return string;
  -- This simplified form is normally easier to use.

  Foreign_Command_Line_Exception : exception;

end FOREIGN_COMMAND_LINE;

package body FOREIGN_COMMAND_LINE is

  function Get_Foreign( Prompt : string := "Argument: "
         ) return string is
    Argument_Line   : string(1..512);
    Argument_Length : short_integer;
    Condition       : integer;
    Force_Prompt    : integer := 0;
  begin
    Get_Foreign( Condition, Argument_Line, Prompt, 
                 Argument_Length, Force_Prompt );
    if Condition rem 2 = 0 then
      -- VMS success codes are always odd.
      -- So if the code is a failure, we must ...
      raise Foreign_Command_Line_Exception;
    end if;
    return Argument_Line( 1.. integer( Argument_Length ));
  end Get_Foreign;

end FOREIGN_COMMAND_LINE;

--
-- The following program is used to illustrate the use of the VMS
-- facility which accesses the command line parameters.  For proper
-- installation of this command, the following DCL command should be
-- used prior to running this program:
--         $ Get_Foreign :== $SYS$SERDAC:[COMPSCI.MACKEY]GET_FOREIGN
-- or whatever the complete path to the .EXE file actually is.  The
-- command is then used as follows, for example:
--         $ Get_Foreign /this is a parameter list.
-- If the run command is used to execute this program, a prompt will
-- always be given to request the command line.
--

with TEXT_IO, FOREIGN_COMMAND_LINE;
use  TEXT_IO, FOREIGN_COMMAND_LINE;
procedure Get_Foreign is
  Parameter : constant string := Get_Foreign( "Parameters: " );
begin
  put_line( "System_parameters: ``" & Parameter & "''" );
end Get_Foreign;


--
-- Wesley Mackey, Ph.D., Lecturer and Laboratory Director
-- School of Computer Science, ECS-359, University Park Campus
-- Florida International University, Miami, FL 33199
-- Phone: 305-348-2744 (x2012), FAX: 305-348-3549
-- E-mail: Mackey@servax.bitnet, Mackey@fiu.edu
--

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

* Re: VAX Ada question.
@ 1991-09-18 23:54 agate!bionet!uwm.edu!cs.utexas.edu!qt.cs.utexas.edu!zaphod.mps.ohio-state
  0 siblings, 0 replies; 3+ messages in thread
From: agate!bionet!uwm.edu!cs.utexas.edu!qt.cs.utexas.edu!zaphod.mps.ohio-state @ 1991-09-18 23:54 UTC (permalink / raw)


In article <1991Sep18.043715.13529@ennews.eas.asu.edu> yhartojo@enuxha.eas.asu.
edu (Francis Hartojo) writes:
>
>	Hi netters, I just have one quick question and it should be trivial for
>VAX Ada experts.
>
>	I want to invoke a command line string from an Ada program, how can I
>do that?  I mean what package should I use?  And exactly which procedure will
>allow me to do it?
>
>	I am sorry if turns out that there are more than one question.  Any
>help, suggestion will be greatly appreciated.
>
>n.b.:  if you guys do not mind, I have one additional question (believe me,
>       this time there is really only one), how do you handle command line
>       parameters in VAX Ada?
>
>--
>Francis Hartojo                  | DECnet:   ENVMSA::YHARTOJO
>                                 | Bitnet:   AUYXH@ASUACVAX.BITNET
>Comp. Science & Engr. Department | Internet: YHARTOJO@ENVMSA.EAS.ASU.EDU
>Arizona State University         | Phone:    (602) 921-1342


with Condition_Handling;
package System_Parameters is
   -- Copyright (c) 1990, by Wesley F. Mackey.  All rights reserved.

   type Sysparam  is access string;
   type Sysparams is array( natural range <> ) of Sysparam;

   System_Parameters_Error : exception;

   type character_class_kind is ( space, switch, simple, quote, done );
   type character_class      is array( character ) of character_class_kind;
   pragma pack( character_class );

   which_class : constant character_class 
               := character_class'( ASCII.NUL => done,
                                    ASCII.SOH .. ' ' | ASCII.DEL => space,
                                    '=' | ',' | '+' | '/' => switch,
                                    '"' => quote,
                                    others => simple );

   type character_set is array( character ) of boolean;
   pragma pack( character_set );

   is_space  : character_set
             := character_set'( ASCII.NUL .. ' ' | ASCII.DEL => true,
                                '!' .. '~' => false );
   is_switch : character_set 
             := character_set'( '/' | ',' | '+' | '=' => true, 
                                others => false );
   is_quote  : character_set
             := character_set'( '"' => true, others => false );

   function Get_Sysparams( Min_Count : natural := 0;
                           Prompt    : string := "Parameters: " 
                         ) return Sysparams;

   function Last_status return Condition_Handling.Cond_value_type;

end System_Parameters;

with Unchecked_Conversion, STARLET, SYSTEM;
package body System_Parameters is
   -- Copyright (c) 1990, by Wesley F. Mackey.  All rights reserved.

   Last_status_returned : CONDITION_HANDLING.Cond_value_type;

   function Last_status return CONDITION_HANDLING.Cond_value_type is
   begin
      return Last_status_returned;
   end Last_status;

   procedure Get_Foreign(
      Condition      : out CONDITION_HANDLING.Cond_value_type;
      Command_Line   : out string;
      User_Prompt    : in  string;
      Command_Length : out short_integer;
      Force_Prompt   : in out integer );
   pragma interface( system, Get_Foreign );
   pragma import_valued_procedure( Get_Foreign, "LIB$get_foreign",
         ( CONDITION_HANDLING.Cond_value_type, string, string, short_integer,
           integer ),
         ( value, descriptor, descriptor, reference, reference ));

   procedure get_Image_Name( Name_param : out Sysparam ) is
      Image_Name        : string( 1 .. 256 );
      Image_Name_Length : SYSTEM.Unsigned_word;
      -- The following code requires understanding of packages SYSTEM and
      -- STARLET as well as the standard VMS interfaces in order to be
      -- understood.  See the appropriate VMS reference manuals.
      -- It is, however, an example of how Ada can handle anything assembly
      -- language can handle.
      Single_Item_Rec : STARLET.Item_list_type( 1..2 )
              :=( 1=>( buf_len    => SYSTEM.Unsigned_word(
                                 Image_Name'size / SYSTEM.Storage_unit ),
                       item_code  => STARLET.JPI_IMAGNAME,
                       buf_address=> Image_Name'address,
                       ret_address=> Image_Name_Length'address ),
                  2=>( 0, 0, SYSTEM.To_address(0), SYSTEM.To_address(0) ));
   begin
      STARLET.GETJPIW( Last_status_returned, itmlst=> Single_Item_Rec );
      if not CONDITION_HANDLING.Success( Last_status_returned ) then
         raise System_Parameters_Error;
      end if;
      Name_param := new string'( 
                       Image_Name( 1 .. integer( Image_Name_Length )));
   end get_Image_Name;

pragma page;
   function Get_Sysparams( Min_Count : natural := 0;
                           Prompt    : string := "Parameters: " 
                         ) return Sysparams is
      subtype Param_Range is integer range 1 .. 1024;
      type    Scan_state  is ( skipping, in_param, in_quote, stop );
      type    Scan_action is ( nothing, start, finish, change );
      type    Transition  is record
                 state       : Scan_state;
                 action      : Scan_action;
              end record;
      type    DFSM_type   is array( Scan_state, 
                                    character_class_kind ) of Transition;

      DFSM : DFSM_type := DFSM_type'(
         skipping => ( space  => ( action => nothing, state => skipping ),
                       switch => ( action => start  , state => in_param ),
                       simple => ( action => start  , state => in_param ),
                       quote  => ( action => start  , state => in_quote ),
                       done   => ( action => nothing, state => stop     )),
         in_param => ( space  => ( action => finish , state => skipping ), 
                       switch => ( action => change , state => in_param ),
                       simple => ( action => nothing, state => in_param ),
                       quote  => ( action => nothing, state => in_quote ),
                       done   => ( action => finish , state => stop     )),
         in_quote => ( space  => ( action => nothing, state => in_quote ), 
                       switch => ( action => nothing, state => in_quote ),
                       simple => ( action => nothing, state => in_quote ),
                       quote  => ( action => nothing, state => in_param ),
                       done   => ( action => finish , state => stop     )),
         stop     => ( others => ( action => nothing, state => stop     )));

      Param_Line    : string( Param_Range );
      Param_Length  : short_integer;
      Param_index   : integer := Param_line'first;

      Param_First   : array( Param_Range ) of integer;
      Param_Last    : array( Param_Range ) of integer;
      Param_count   : natural := Param_Range'first - 1;
      Param_max     : natural;

      Current_state : Scan_state := skipping;
      Current_Trans : Transition;

      Force_Prompt  : integer := 0;

   begin
      Get_Foreign( Last_status_returned, Param_Line, Prompt, 
                   Param_Length, Force_Prompt );
      if natural( Param_Length ) >= Param_line'last or else
            not CONDITION_HANDLING.Success( Last_status_returned ) then
         raise System_Parameters_Error;
      end if;
      Param_Line( natural( Param_Length ) + 1 ) := ASCII.NUL;

      while Current_state /= stop loop
         Current_Trans := DFSM( Current_state, 
                                which_class( Param_Line( Param_index )));
         case Current_trans.action is
            when nothing => null;
            when start   => Param_count := Param_count + 1;
                            Param_first( Param_count ) := Param_index;
            when finish  => Param_last( Param_count ) := Param_index - 1;
            when change  => Param_last( Param_count ) := Param_index - 1;
                            Param_count := Param_count + 1;
                            Param_first( Param_count ) := Param_index;
         end case;
         Param_index := Param_index + 1;
         Current_state := Current_Trans.state;
      end loop;

      if Param_count > Min_Count then Param_max := Param_count;
                                 else Param_max := Min_Count;
      end if;
      declare
         Result : Sysparams( Param_Range'first - 1 .. Param_max );
      begin
         get_Image_Name( Result( Result'first ));
         for index in Result'first + 1 .. Param_count loop
            Result( index ) := new string'( 
                  Param_Line( Param_first( index ) .. Param_last( index )));
         end loop;
         for index in Param_count + 1 .. Result'last loop
            Result( index ) := new string'( "" );
         end loop;
         return Result;
      end;
   end Get_Sysparams;

end System_Parameters;

with System_Parameters, Text_IO, Integer_Text_IO;
use  System_Parameters, Text_IO, Integer_Text_IO;
procedure sys_params is
   Parameters : constant Sysparams := Get_Sysparams;
begin
   for index in Parameters'range loop
      put( "Parameter(" );
      put( index, width=> 3 );
      put( " ) = ``" );
      put( Parameters( index ).all );
      put( "''" );
      new_line;
   end loop;
end sys_params;



--
-- Wesley Mackey, Ph.D., Lecturer and Laboratory Director
-- School of Computer Science, ECS-359, University Park Campus
-- Florida International University, Miami, FL 33199
-- Phone: 305-348-2744 (x2012), FAX: 305-348-3549
-- E-mail: Mackey@servax.bitnet, Mackey@fiu.edu
--

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

* Re: VAX Ada question.
@ 1991-09-19 15:47 swrinde!zaphod.mps.ohio-state.edu!caen!uvaarpa!software.org!blakemor
  0 siblings, 0 replies; 3+ messages in thread
From: swrinde!zaphod.mps.ohio-state.edu!caen!uvaarpa!software.org!blakemor @ 1991-09-19 15:47 UTC (permalink / raw)


>In article <1991Sep18.043715.13529@ennews.eas.asu.edu> yhartojo@enuxha.eas.asu
.edu (Francis Hartojo) writes:
>>       how do you handle command line parameters in VAX Ada?

In article <4590@kluge.fiu.edu> mackey@scs.fiu.edu writes:
> use  VMS RTL_Routines LIB$ LIB$GET_FOREIGN

a better way (at least if you want to look and feel like a VAX command)
is to use the VMS command line interface routines (CLI).  This allows
you to define you command line syntax/defaults and rules about
which qualifiers go with others etc in a text file instead of your program.
you get default VMS behavior regarding abbreviations - prompting for missing
params etc, your application looks just like it came from DEC.
(foreign commands look just like that "foreign" to the VMS environment)

VMS Ada provides a package called CLI which serves as an Ada interface
to the CLI routines (use acs extract source to see it) its in every Ada
library (not sublibrary)

the spec isnt terribly readable, you probably should read the manual.

the name of the manual you want is the VMS Command Definition Utility Manual.
-- 
---------------------------------------------------------------------
Alex Blakemore           blakemore@software.org        (703) 742-7125
Software Productivity Consortium  2214 Rock Hill Rd, Herndon VA 22070

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

end of thread, other threads:[~1991-09-19 15:47 UTC | newest]

Thread overview: 3+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
1991-09-19 15:47 VAX Ada question swrinde!zaphod.mps.ohio-state.edu!caen!uvaarpa!software.org!blakemor
  -- strict thread matches above, loose matches on Subject: below --
1991-09-18 23:54 agate!bionet!uwm.edu!cs.utexas.edu!qt.cs.utexas.edu!zaphod.mps.ohio-state
1991-09-18 23:54 agate!bionet!uwm.edu!cs.utexas.edu!qt.cs.utexas.edu!zaphod.mps.ohio-state

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