home *** CD-ROM | disk | FTP | other *** search
- Path: sparky!uunet!munnari.oz.au!goanna!ok
- From: ok@goanna.cs.rmit.oz.au (Richard A. O'Keefe)
- Newsgroups: comp.lang.prolog
- Subject: Re: Time and Date in Quintus P.
- Summary: it's in the library
- Message-ID: <14396@goanna.cs.rmit.oz.au>
- Date: 8 Sep 92 04:31:47 GMT
- References: <1992Sep3.201023.6191@tom.rz.uni-passau.de>
- Organization: Comp Sci, RMIT, Melbourne, Australia
- Lines: 49
-
- In article <1992Sep3.201023.6191@tom.rz.uni-passau.de>, baier@forwiss.uni-passau.de (Joern Baier) writes:
- > For an application I need the time and date in Quintus Prolog. I wrote a
- > small predicate date/1 but I'm not content with it, because I have to
- > create an extra file.
-
- It's already in the library.
- Pick up a copy of the manual, and look in the index.
- (You do not need a paper copy of the manual, the on-line help system
- has all the same information.)
- I find, in my copy of the manual:
- "date -- library package, H-122"
- You can also find this in the table of contents, where I find
- "H.11: MIscellaneous Packages ...
- H.11-2: date.{c,pl}... H-122"
-
- The simplest method is
- ?- use_module(library(date), [date/1]).
- ?- date(TodaysDate).
- TodaysDate = date(1992,8,9).
- /* Month numbers run from 0 to 11 for compatibility with ANSI C */
-
-
- > How can I get a random number in PROLOG to create
- > unique file names?
-
- It's in the library. In fact, it's library(random). See the "Abstracts"
- section in the library manual. But if you want to generate unique file
- names, random numbers are not really the way to go. You want to use whatever
- your operating system gives us, e.g. tmpnam() in UNIX.
-
- > The main problem is that 'unix(system(date))' sends its output directly
- > to the user, regardless of the current output.
-
- Because that is what it is supposed to do. unix(system('command'))
- does exactly what system("command") would do in C, namely run the command
- with the command's input coming from _STANDARD_ input and the command's
- output going to _STANDARD_ output (not necessarily the terminal).
-
- If you want to get the output of a command, what you want is
-
- ?- use_module(library(pipe), [popen/3]).
- ?- popen(date, read, Stream),
- read_whatever_you_want_to_from(Stream),
- close(Stream).
-
- This is just like popen() in UNIX+C, and it's in the "abstracts" section
- of the library manual.
- --
- You can lie with statistics ... but not to a statistician.
-