C:\gfortran\clf\bind_c>type bind_c_1.f90
! File: bind_c_1.f90
! Public domain 2007 James Van Buskirk
module iface
implicit none
private
public sub1
interface
subroutine sub1(x, N) bind(C,name='SuB2')
use ISO_C_BINDING
implicit none
character(kind=C_CHAR) x(*)
integer(C_SIZE_T), value :: N
end subroutine sub1
end interface
end module iface
program test
use ISO_C_BINDING
use iface
implicit none
call sub1(C_CHAR_'Hello, world!', len(C_CHAR_'Hello, world!',C_SIZE_T))
end program test
subroutine sub3(x, N), bind(C,name='SuB2')
use ISO_C_BINDING
implicit none
character(kind=C_CHAR) x(*)
integer(C_SIZE_T), value :: N
character(80) fmt
write(fmt,'(a,i0,a)') '(',N,'a1)'
write(*,fmt) x(1:N)
end subroutine sub3
! End of file: bind_c_1.f90
C:\gfortran\clf\bind_c>c:\gfortran\win64\bin\x86_64-pc-mingw32-gfortran
bind_c_1
.f90 -obind_c_1
bind_c_1.f90:25.21:
subroutine sub3(x, N), bind(C,name='SuB2')
1
Error: Syntax error in SUBROUTINE statement at (1)
bind_c_1.f90:17.12:
program test
1
bind_c_1.f90:26.20:
use ISO_C_BINDING
2
Error: Two main PROGRAMs at (1) and (2)
Am I correct in assuming that this is an error in the standard,
where I am following n3661.pdf, notes 15.22 and 15.23 which put
a comma before the BIND(C) and not in gfortran? If both the
procedure-language-binding-spec and the RESULT clause are present
(for a function) am I correct in assuming that there should be
no comma separating the two?
In the Win32 API, optional arguments are synthesized by specifying
the dummy argument as being of type C_PTR (or C_FUNPTR) by value,
and if the actual argument is C_NULL_PTR (or C_NULL_FUNPTR) the
argument is considered to be not present.
How are you supposed to interoperate with this? If you follow the
C way, then it's easy when the argument is not present, but otherwise
the actual argument has to be of type C_PTR (or C_FUNPTR) and you
only get this when you can take the C_LOC of the string you want to
pass. You can only take the C_LOC of something which has the TARGET
attribute or of an associated POINTER. This requires contortions
if you want to pass the result of an expression.
If you follow the Fortran way as above there is no syntax for passing
the C_NULL_PTR when required. The ASSOCIATED intrinsic seems to
offer a way out for character variables in that a pointer to the
empty string is not considered to be associated with any other
POINTER but is itself considered to be associated.
C:\gfortran\clf\bind_c>type bind_c_3.f90
program test
use ISO_C_BINDING
implicit none
character(0,C_CHAR), target :: x
character(0,C_CHAR), pointer :: p
character(0,C_CHAR), pointer :: q
interface
subroutine sub1(x)
use ISO_C_BINDING
implicit none
character(1,C_CHAR) x(*)
end subroutine sub1
end interface
x = ':)'
p => x
q => x
write(*,*) associated(p)
write(*,*) associated(q)
write(*,*) associated(q,p)
call sub1(C_CHAR_'Hello, world!'//C_NULL_CHAR)
call sub1(p)
end program test
subroutine sub1(x)
use ISO_C_BINDING
implicit none
type(C_PTR), value :: x
character(1,C_CHAR), pointer :: y(:)
integer n
character(80) fmt
if(C_ASSOCIATED(x)) then
do n = 1, huge(1)
call C_F_POINTER(x, y, [n])
if(y(n) == C_NULL_CHAR) exit
end do
write(fmt,'(a,i0,a)') '(',n-1,'a1)'
write(*,*) y(1:1)(1:n-1)
else
write(*,*) 'Input not associated'
end if
end subroutine sub1
C:\gfortran\clf\bind_c>c:\gfortran\win64\bin\x86_64-pc-mingw32-gfortran
bind_c_3
.f90 -obind_c_3
bind_c_3.f90:6.13:
character(0,C_CHAR), pointer :: q
1
Warning: CHARACTER variable has zero length at (1)
bind_c_3.f90:5.13:
character(0,C_CHAR), pointer :: p
1
Warning: CHARACTER variable has zero length at (1)
bind_c_3.f90:4.13:
character(0,C_CHAR), target :: x
1
Warning: CHARACTER variable has zero length at (1)
C:\gfortran\clf\bind_c>bind_c_3
T
T
F
Hello, world!
p?"
Oh well, doesn't seem to work. I wish those warnings for zero-
length strings weren't the default, though.
--
write(*,*) transfer((/17.392111325966148d0,6.5794487871554595D-85, &
6.0134700243160014d-154/),(/'x'/)); end
> subroutine sub3(x, N), bind(C,name='SuB2')
> 1
> Error: Syntax error in SUBROUTINE statement at (1)
...
> Am I correct in assuming that this is an error in the standard,
> where I am following n3661.pdf, notes 15.22 and 15.23 which put
> a comma before the BIND(C) and not in gfortran? If both the
> procedure-language-binding-spec and the RESULT clause are present
> (for a function) am I correct in assuming that there should be
> no comma separating the two?
I'm not sure what the n3661 that you are referring to is. WG5 N numbers
haven't gotten nearly that high. N1601 is the DIS (Draft International
Standard). The equivalent J3 document is J3/04-007, which is what I keep
most handy for my personal reference.
I see no commas before the BIND(C) in notes 15.22 or 15.23 of J3/04-007.
I also see no commas here in the bnf rules for subroutien or function
statements (R1232 and R1224). The standard looks at least
self-consistent to me here.
It is possible that you might be looking at some previous draft of the
standard. I seem to recall some changes in the exact syntax details
because of syntax ambiguities or some such odd thing. The details escape
me, but it possibly could have related to commas.
--
Richard Maine | Good judgement comes from experience;
email: last name at domain . net | experience comes from bad judgement.
domain: summertriangle | -- Mark Twain
> I'm not sure what the n3661 that you are referring to is. WG5 N numbers
> haven't gotten nearly that high. N1601 is the DIS (Draft International
> Standard). The equivalent J3 document is J3/04-007, which is what I keep
> most handy for my personal reference.
It's called n3661.pdf but near the top it says:
"Reference number of working document: ISO/IEC JTC1/SC22/WG5 N1578"
So I guess the name of the song is called N1578.
> I see no commas before the BIND(C) in notes 15.22 or 15.23 of J3/04-007.
> I also see no commas here in the bnf rules for subroutien or function
> statements (R1232 and R1224). The standard looks at least
> self-consistent to me here.
> It is possible that you might be looking at some previous draft of the
> standard. I seem to recall some changes in the exact syntax details
> because of syntax ambiguities or some such odd thing. The details escape
> me, but it possibly could have related to commas.
Seems to be the case. Actually BIND(C) needs a comma when it's
not binding a procedure, so maybe that's the reason for confusion.
I find it very difficult to write any amount of code out correctly
in all details when I can't check any part of it with a compiler.
> "Richard Maine" <nos...@see.signature> wrote in message
> news:1i83fmq.dg1dbp1krkte3N%nos...@see.signature...
>> I'm not sure what the n3661 that you are referring to is. WG5 N numbers
>> haven't gotten nearly that high. N1601 is the DIS (Draft International
>> Standard). The equivalent J3 document is J3/04-007, which is what I keep
>> most handy for my personal reference.
> It's called n3661.pdf but near the top it says:
> "Reference number of working document: ISO/IEC JTC1/SC22/WG5 N1578"
Alright, I found N1601.pdf and deleted n3661.pdf. The commas indeed
are absent in N1601.pdf. I was most interested in how Fortran is
supposed to interoperate with C char * dummy arguments. I guess I'll
have to keep looking since most vendors haven't yet implemented the
TR on Directive Enhanced Compilation.
> Alright, I found N1601.pdf and deleted n3661.pdf. The commas indeed
> are absent in N1601.pdf. I was most interested in how Fortran is
> supposed to interoperate with C char * dummy arguments. I guess I'll
> have to keep looking since most vendors haven't yet implemented the
> TR on Directive Enhanced Compilation.
I found something that works in one specific case:
C:\gfortran\clf\bind_c>type bind_c_4.f90
! File: bind_c_4.f90
! Public domain 2007 James Van Buskirk
program test
use ISO_C_BINDING
implicit none
character(0,C_CHAR), target :: x
character(0,C_CHAR), pointer :: p
character(0,C_CHAR), pointer :: q
character(1,C_CHAR), pointer :: t2
interface
subroutine sub1(x) bind(C)
use ISO_C_BINDING
implicit none
character(1,C_CHAR) x(*)
end subroutine sub1
end interface
call sub1(C_CHAR_'Hello, world!'//C_NULL_CHAR)
x = ':)'
p => x
q => x
write(*,*) associated(p)
write(*,*) associated(q)
write(*,*) associated(q,p)
call sub1(p)
call C_F_POINTER(C_NULL_PTR, t2)
call sub1(t2)
end program test
subroutine sub1(x) bind(C)
use ISO_C_BINDING
implicit none
type(C_PTR), value :: x
character(1,C_CHAR), pointer :: y(:)
integer n
character(80) fmt
if(C_ASSOCIATED(x)) then
do n = 1, huge(1)
call C_F_POINTER(x, y, [n])
if(y(n) == C_NULL_CHAR) exit
end do
write(fmt,'(a,i0,a)') '(',n-1,'a1)'
write(*,fmt) y(1:n-1)(1:1)
else
write(*,*) 'Input not associated'
end if
end subroutine sub1
! End of file: bind_c_4.f90
C:\gfortran\clf\bind_c>c:\gfortran\win64\bin\x86_64-pc-mingw32-gfortran
bind_c_4
.f90 -obind_c_4
bind_c_4.f90:8.13:
character(0,C_CHAR), pointer :: q
1
Warning: CHARACTER variable has zero length at (1)
bind_c_4.f90:7.13:
character(0,C_CHAR), pointer :: p
1
Warning: CHARACTER variable has zero length at (1)
bind_c_4.f90:6.13:
character(0,C_CHAR), target :: x
1
Warning: CHARACTER variable has zero length at (1)
C:\gfortran\clf\bind_c>bind_c_4
Hello, world!
T
T
F
=+=
Input not associated
So C_F_POINTER was able to set up a pointer that wanted to
pass the C_NULL_PTR to the BIND(C) subroutine sub1. Is this
standard? gfortran doesn't complain even when std=f2003 is
set, but that is not a guarantee, especially considering
that the BIND(C) stuff is quite new in that compiler.
> "James Van Buskirk" <not_...@comcast.net> wrote in message
> news:-M-dnciObMosktTa...@comcast.com...
>
> > "Richard Maine" <nos...@see.signature> wrote in message
> > news:1i83fmq.dg1dbp1krkte3N%nos...@see.signature...
>
> >> I'm not sure what the n3661 that you are referring to is. WG5 N numbers
> >> haven't gotten nearly that high. N1601 is the DIS (Draft International
> >> Standard). The equivalent J3 document is J3/04-007, which is what I keep
> >> most handy for my personal reference.
>
> > It's called n3661.pdf but near the top it says:
>
> > "Reference number of working document: ISO/IEC JTC1/SC22/WG5 N1578"
>
> Alright, I found N1601.pdf and deleted n3661.pdf. The commas indeed
> are absent in N1601.pdf.
Ok. N1578 (I don't know how or why it got called n3661.pdf somewhere)
was the FCD (Final Committee Draft). That's pretty close, but there are
some small differences and you are better off with N1601. I have a list
of the differences between N1601 and the published standard. It is just
6 typos, none of them affecting the technical content. I don't have such
a handy list for N1578; it shouldn't be a big list, but bigger.
> I was most interested in how Fortran is
> supposed to interoperate with C char * dummy arguments.
I don't have any insight for you there that you haven't commented on
yourself. Seems to me that the problem you describe is more related to
the optionality than to char *. Perhaps I didn't read carefully enough,
but I don't see any particular problem with char *. It should match fine
with a Fortran assumed-size array of character*1 elements. But the C
convention of passing null pointers seems to force you to use C_PTR type
for cases where you want to take advantage of that. That's a bit
awkward, I agree, but I think that's the way you do it.
You'll hit the same thing with "optional" non-character arguments. I
suppose it is just more annoying in the case of character because it
forces the argument to be a variable instead of a constant. I have at
times wished that a pointer could point to a constant (or a subobject of
a constant). It seems to me not different from passing a constant as an
actual argument (In fact, the relationship between actual and dummy
arguments is a lot like that between targets and pointers; some of that
is deliberate). Yes, it implies restrictions on what you would then be
allowed to do with the pointer, but there are other cases with simillar
restrictions, so it isn't unprecedented.
Would pointers to constants address your question? If so, maybe it is
time to push for that feature, which would be handy in som eother places
as well.
> I don't have any insight for you there that you haven't commented on
> yourself. Seems to me that the problem you describe is more related to
> the optionality than to char *. Perhaps I didn't read carefully enough,
> but I don't see any particular problem with char *. It should match fine
> with a Fortran assumed-size array of character*1 elements. But the C
> convention of passing null pointers seems to force you to use C_PTR type
> for cases where you want to take advantage of that. That's a bit
> awkward, I agree, but I think that's the way you do it.
> You'll hit the same thing with "optional" non-character arguments. I
> suppose it is just more annoying in the case of character because it
> forces the argument to be a variable instead of a constant. I have at
> times wished that a pointer could point to a constant (or a subobject of
> a constant). It seems to me not different from passing a constant as an
> actual argument (In fact, the relationship between actual and dummy
> arguments is a lot like that between targets and pointers; some of that
> is deliberate). Yes, it implies restrictions on what you would then be
> allowed to do with the pointer, but there are other cases with simillar
> restrictions, so it isn't unprecedented.
> Would pointers to constants address your question? If so, maybe it is
> time to push for that feature, which would be handy in som eother places
> as well.
First of all, thanks for taking the time to respond to my difficult
questions, Richard. I don't think that passing C_PTR by value is the
way to go because it entails tearing up all your Fortran code and
turning it into C code (that your Fortran compiler then compiles.)
Here, look at
http://groups.google.com/group/comp.lang.fortran/msg/b5065aaaad9eb748
just a little bit. In that example I did change the optional dummies
to C_PTR by value and than I get constructs such as
C_LOC(lpTitle(1:1)), & ! lpTitle
where I had to create a character variable, lpTitle, with the target
attribute, but that didn't seem good enough: I couldn't take the
C_LOC of lpTitle because it's not of length unity, so I had to take
the C_LOC of its first character. Contortions like this are pervasive
in code that passes C_PTR by value. Pointers to constants is IMO
just another contortion, but this time it's affecting the standard
itself, not just a program. In C it's normal to write code like
char * x[] = {"zero", "one", "two"};
...
printf("%s\n", x[i]);
Here we can see that pointers to constants are reqired in C for
just about anything you might want to do, but I don't think that
it's worthwhile to put them in Fortran on that account.
The only reason I changed to C_PTR by value in the example cited
above is that I didn't realize that casting a character scalar
actual argument to a character array dummy was permitted in f03.
In f95 and even I think f77 the reverse transformation was
permitted (i.e. character array actual and character scalar dummy)
but character scalar to character array is new to f03. This
simplifies passing Fortran character variables to C pointers to
char no end, but if you have to pass C_PTR by value, you are
back to square one and even the big bad pipsewah didn't send you
back that far.
I had thought that perhaps you could pass C_NULL_PTR as an actual
to dummies that were CHARACTER(C_PTR) by effectively reference,
but that wouldn't work even as an extension because what would
it mean if the dummy were type(C_PTR) by effective reference?
Ive cooked up an example like this where the C prototype would
be something like
void sub1(int **x);
This is quite normal stuff in C, except that you would more
often see
void sub1(struct complicated_struct **x);
where sub1 is supposed to allocate an instance of the data
structure complicated_struct and make that instance accessible
to the caller. The int **x is thus just a taste of the
situation that would exist in real life.
C:\gfortran\clf\bind_c>type bind_c_5.f90
! File: bind_c_5.f90
! Public domain 2007 James Van Buskirk
program test
use ISO_C_BINDING
implicit none
interface
subroutine sub1(x)
use ISO_C_BINDING
implicit none
type(C_PTR) x
end subroutine sub1
end interface
type(C_PTR) a
type(C_PTR), pointer :: b
integer(C_INT), target :: c
call C_F_POINTER(C_NULL_PTR, b)
write(*,'(a)') 'Attempt to pass C_NULL_PTR to sub1'
call sub1(b)
a = C_NULL_PTR
write(*,'(/a)') 'Attempt to pass pointer to C_NULL_PTR to sub1'
call sub1(a)
allocate(b)
b = C_NULL_PTR
write(*,'(/a)') 'This should also pass pointer to C_NULL_PTR to sub1'
call sub1(b)
deallocate(b)
c = 13
a = C_LOC(c)
allocate(b)
b = a
write(*,'(/a)') 'Attempt to pass number 13 to sub1'
call sub1(b)
deallocate(b)
write(*,'(/a)') 'What happens when you pass C_NULL_PTR '// &
'itself to sub1'
call sub1(C_NULL_PTR)
end program test
subroutine sub1(x)
use ISO_C_BINDING
implicit none
type(C_PTR), value :: x
type(C_PTR), pointer :: p
integer, pointer :: q
if(C_ASSOCIATED(x)) then
call C_F_POINTER(x, p)
if(C_ASSOCIATED(p)) then
call C_F_POINTER(p, q)
! write(*,10) 'Case 3: ultimate value = ', q
!10 format(a.i0)
! write(*,'(a.i0)') 'Case 3: ultimate value = ', q
write(*,'(a,i0)') 'Case 3: ultimate value = ', q
else
write(*,'(a)') 'Case 2: pointer passed to sub1 '// &
'pointed to C_NULL_PTR'
end if
else
write(*,'(a)') 'Case 1: C_NULL_PTR passed to sub1'
end if
end subroutine sub1
! End of file: bind_c_5.f90
C:\gfortran\clf\bind_c>c:\gfortran\win64\bin\x86_64-pc-mingw32-gfortran -std=f20
03 bind_c_5.f90 -obind_c_5
C:\gfortran\clf\bind_c>bind_c_5
Attempt to pass C_NULL_PTR to sub1
Case 1: C_NULL_PTR passed to sub1
Attempt to pass pointer to C_NULL_PTR to sub1
Case 2: pointer passed to sub1 pointed to C_NULL_PTR
This should also pass pointer to C_NULL_PTR to sub1
Case 2: pointer passed to sub1 pointed to C_NULL_PTR
Attempt to pass number 13 to sub1
Case 3: ultimate value = 13
What happens when you pass C_NULL_PTR itself to sub1
Case 2: pointer passed to sub1 pointed to C_NULL_PTR
On a low level I am assuming that passing a pointer actual atgument
to an effective reference dummy makes the dummy pointer associater
with the pointer. Yeah, I know you don't like that kind of
language and the standard doesn't say it in so many words. And
the pointer association is weak in that only an assumed-shape
dummmy gets a descriptor to what the pointer points at, other
dummies only get the first address (BTW, the standard uses address
of the first element or something like that and what does it
mean if p => a(10:1:-1) ?) and then only if they're lucky and
there's no copy in/copy out.
Anyhow it's not so complicated with pointers to scalars as in my
example above. It still is pretty complicated even so, the more
so because Fortran and C have different levels of indirection
across the subroutine invocation. My eyes tend to glaze over
when analyzing code like this. The reason I don't simply pass
a nullified pointer when I want sub1 to receive C_NULL_PTR by
value is that I think the standard doesn't allow it. You may ask
why I then get away with
call C_F_POINTER(C_NULL_PTR, b)
and then passing b, because didn't that line of code above simply
nullify pointer b? Maybe it did but I can't see where it says
that explicitly in the standard. In any case, if you can't get
away with some trick such as the above then the BIND(C) stuff is
going to be awfully hard to apply to the procedure interface.
BTW there was a problem with error localization in gfortran
again with this example. If we activate the erroneaous format
statement:
write(*,10) 'Case 3: ultimate value = ', q
10 format(a.i0)
! write(*,'(a.i0)') 'Case 3: ultimate value = ', q
! write(*,'(a,i0)') 'Case 3: ultimate value = ', q
The error reporting is good:
C:\gfortran\clf\bind_c>c:\gfortran\win64\bin\x86_64-pc-mingw32-gfortran -std=f20
03 bind_c_5.f90 -obind_c_5
bind_c_5.f90:52.12:
10 format(a.i0)
1
Error: Extension: Missing comma at (1)
bind_c_5.f90:51.19:
write(*,10) 'Case 3: ultimate value = ', q
1
Error: FORMAT label 10 at (1) not defined
But if we put that erroneous format in a character constant:
! write(*,10) 'Case 3: ultimate value = ', q
!10 format(a.i0)
write(*,'(a.i0)') 'Case 3: ultimate value = ', q
! write(*,'(a,i0)') 'Case 3: ultimate value = ', q
gfortran does early evaluation of the character constant but
when an error occurs the location pointer to the error is
invalid:
C:\gfortran\clf\bind_c>c:\gfortran\win64\bin\x86_64-pc-mingw32-gfortran -std=f20
03 bind_c_5.f90 -obind_c_5
bind_c_5.f90:53.57:
write(*,'(a.i0)') 'Case 3: ultimate value = ', q
1
Error: Extension: Missing comma at (1)
That kind of thing, along with the likelyhood of ICE when something
goes wrong, are definitely worth plugging away at because it makes
it harder to develop code in gfortran.
Thanks again for your time and for the time the gfortran developers
have taken in addressing perceived problems.
> On a low level I am assuming that passing a pointer actual atgument
> to an effective reference dummy makes the dummy pointer associater
> with the pointer. Yeah, I know you don't like that kind of
> language and the standard doesn't say it in so many words.
It isn't so much not liking that kind of language as that I have no idea
what you are talking about. :-( Maybe I haven't spent enough time trying
to decode it. Sorry.
> The reason I don't simply pass
> a nullified pointer when I want sub1 to receive C_NULL_PTR by
> value is that I think the standard doesn't allow it.
Your terminology might be confusing me, but if I have it straight then
no, that isn't allowed. Don't confuse Fortran pointers and C ones. They
don't have much directly to do with one another (at least in terms of
the standard). Things like C_LOC and C_F_POINTER allow you to convert
from one to the other, but you certainly can't pass a nullified Fortran
pointer (I assume you mean a Fortran one because the term "nullified"
doesn't apply to C pointers) to *ANYTHING* in C. If you have a pointer
actual argument and a non-pointer dummy, then the target of the pointer
actual is what gets passed. That means it has to have a target.
From the Fortran perspective, something of type C_PTR is not a pointer.
It is just an object of the derived type C_PTR.
> You may ask why I then get away with
> call C_F_POINTER(C_NULL_PTR, b)
> and then passing b, because didn't that line of code above simply
> nullify pointer b? Maybe it did but I can't see where it says
> that explicitly in the standard.
Good point. I'm not sure that the wording of the standard covers that
either. Perhaps it does, but I'm not seeing it at a quick glance either.
Certainly C_LOC is rather explicit that if you pass it a pointer, the
pointer must be associated. I think I'm reading C_F_POINTER as having
simillar restrictions and thus not being able to take C_NULL_POINTER.
> "Richard Maine" <nos...@see.signature> wrote in message
> news:1i84kbg.kriyk719kkhq8N%nos...@see.signature...
(snip)
>>You'll hit the same thing with "optional" non-character arguments. I
>>suppose it is just more annoying in the case of character because it
>>forces the argument to be a variable instead of a constant. I have at
>>times wished that a pointer could point to a constant (or a subobject of
>>a constant). It seems to me not different from passing a constant as an
>>actual argument (In fact, the relationship between actual and dummy
>>arguments is a lot like that between targets and pointers; some of that
>>is deliberate). Yes, it implies restrictions on what you would then be
>>allowed to do with the pointer, but there are other cases with simillar
>>restrictions, so it isn't unprecedented.
The problem of modifying constants used as actual arguments has a
long history. C (C89, anyway) doesn't allow pointers to constants,
except that character strings are considered differently.
In K&R C character string constants were considered variable, more
like initialized variables in a DATA statement. ANSI removed that,
but as with Fortran, many compilers still support the old feature.
(snip)
> char * x[] = {"zero", "one", "two"};
> ...
> printf("%s\n", x[i]);
Yes, this is fairly common in C. Though in K&R it would be
static char * x[] = {"zero", "one", "two"};
The C alternative:
char * y[][5] = {"zero", "one", "two"};
Is an initialized array instead of an array of pointers.
> Here we can see that pointers to constants are reqired in C for
> just about anything you might want to do, but I don't think that
> it's worthwhile to put them in Fortran on that account.
You can't in C apply & to get a pointer to an integer or
floating point constant. Character string constants are special.
Maybe they should be for Fortran, too.
-- glen
----== Posted via Newsfeeds.Com - Unlimited-Unrestricted-Secure Usenet News==----
http://www.newsfeeds.com The #1 Newsgroup Service in the World! 120,000+ Newsgroups
----= East and West-Coast Server Farms - Total Privacy via Encryption =----
> James Van Buskirk <not_...@comcast.net> wrote:
>
> > "James Van Buskirk" <not_...@comcast.net> wrote in message
> > news:-M-dnciObMosktTa...@comcast.com...
> > > It's called n3661.pdf but near the top it says:
> >
> > > "Reference number of working document: ISO/IEC JTC1/SC22/WG5 N1578"
> >
> > Alright, I found N1601.pdf and deleted n3661.pdf. The commas indeed
> > are absent in N1601.pdf.
>
> Ok. N1578 (I don't know how or why it got called n3661.pdf somewhere)
> was the FCD (Final Committee Draft). That's pretty close, but there are
> some small differences and you are better off with N1601. <snip>
I believe when an FCD goes up to SC22 they assign their own number.
I recall seeing on the ANSI website, back when I was visiting it
often, an announcement of 'draft' F03 for public comment -- I don't
remember if they said FCD -- free versus the (then) USD18 for an
actual (recent) standard; and I have a file on my PC, named n3661 and
containing on the cover page "...WG5 N1578" and "Date: 2003-10-8" then
"...FCD 1539-1:2004(E)" and "Committee ...SC22" "Secretariat: ANSI",
and running title on other pages J3/03-007R2, with my file's timestamp
(presumably = when downloaded) a few weeks after that nominal date.
I haven't ever noticed ANSI doing this for any other X3/(I)NCITS-area
standard. But I haven't been watching consistently or thoroughly. It's
not like a reasonable person would expect to get useful comments from
someone who didn't at least know about J3 process. But maybe it was
required by their rules -- or someone thought it was.
- formerly david.thompson1 || achar(64) || worldnet.att.net