From: Ola Rinta-Koski
Subject: Class slot type declarations
Date: 
Message-ID: <x566f1focj.fsf@arenal.cyberell.com>
A file containing the following definitions:

(defclass foo ()
  ((bar :accessor bar :type simple-array)))

(defmethod baz ((foo foo))
  (aref (bar foo) 0 0))

produces, when compiled (using CMUCL 18c) with

(progn (declaim (optimize (safety 0) (speed 3))) 
       (compile-file "foo.lisp"))

the following output:

In: DEFMETHOD BAZ (FOO)
  (AREF (BAR FOO) 0 0)
--> LET* 
==>
  (KERNEL:DATA-VECTOR-REF ARRAY KERNEL:INDEX)
Note: Unable to optimize due to type uncertainty:
      The first argument is a (ARRAY * (* *)), not a SIMPLE-ARRAY.

  How should I declare the type of slot BAR to enable the associated
  compiler optimizations? I want BAR to eventually contain a 2D
  single-float array.
-- 
        Ola Rinta-Koski                                 ···@cyberell.com
        Cyberell Oy                                     +358 41 467 2502
        Rauhankatu 8 C, FIN-00170 Helsinki, FINLAND	www.cyberell.com

From: Kent M Pitman
Subject: Re: Class slot type declarations
Date: 
Message-ID: <sfwg0e5phml.fsf@world.std.com>
Ola Rinta-Koski <···@cyberell.com> writes:

> A file containing the following definitions:
> 
> (defclass foo ()
>   ((bar :accessor bar :type simple-array)))
> 
> (defmethod baz ((foo foo))
>   (aref (bar foo) 0 0))
> 
> produces, when compiled (using CMUCL 18c) with
> 
> (progn (declaim (optimize (safety 0) (speed 3))) 
>        (compile-file "foo.lisp"))
> 
> the following output:
> 
> In: DEFMETHOD BAZ (FOO)
>   (AREF (BAR FOO) 0 0)
> --> LET* 
> ==>
>   (KERNEL:DATA-VECTOR-REF ARRAY KERNEL:INDEX)
> Note: Unable to optimize due to type uncertainty:
>       The first argument is a (ARRAY * (* *)), not a SIMPLE-ARRAY.
> 
>   How should I declare the type of slot BAR to enable the associated
>   compiler optimizations? I want BAR to eventually contain a 2D
>   single-float array.

SIMPLE-ARRAY, if you check CLHS, is a synonym for (SIMPLE-ARRAY T (*)).
I'm not a CMU CL user, so can't say for sure, but it looks to me like
you probably want to say :type (simple-array * (* *)), since that at least
would be a subtype of (ARRAY * (* *)), which is what the AREF is demanding.

You can check for type compatibility using SUBTYPEP, btw.
 (subtypep 'simple-array           '(array * (* *))) => NIL, T
 (subtypep '(simple-array * (* *)) '(array * (* *))) => T, T
Any further restricted array type would also work.  For example, if you
plan to make the array be (UNSIGNED-BYTE 8), you could do
 (simple-array (unsigned-byte 8) (* *))
From: Ola Rinta-Koski
Subject: Re: Class slot type declarations
Date: 
Message-ID: <x51yppfmg7.fsf@arenal.cyberell.com>
Kent M Pitman <······@world.std.com> writes:
> SIMPLE-ARRAY, if you check CLHS, is a synonym for (SIMPLE-ARRAY T (*)).
> I'm not a CMU CL user, so can't say for sure, but it looks to me like
> you probably want to say :type (simple-array * (* *)), since that at least
> would be a subtype of (ARRAY * (* *)), which is what the AREF is demanding.
(...)
> Any further restricted array type would also work.  For example, if you
> plan to make the array be (UNSIGNED-BYTE 8), you could do
>  (simple-array (unsigned-byte 8) (* *))

  For some reason, it doesn't work: if the file contains

(defclass foo ()
  ((bar :accessor bar :type (simple-array single-float (* *)))))

(defmethod baz ((foo foo))
  (aref (bar foo) 0 0))

  I get the exact same output. Is this a bug (or missing feature) in
  CMUCL? Allegro CL 6.0 outputs, with baz modified as follows

(defmethod baz ((foo foo))
  (declare (:explain :calls :types))
  (aref (bar foo) 0 0))

  the following, which I take to indicate it can optimize the array
  reference:

CL-USER(10):  (progn (declaim (optimize (speed 3) (debug 3) (safety 0))) (compile-file "foo.lisp"))
;;; Compiling file foo.lisp
;Examining a (possibly unboxed) call to AREF with arguments:
;  call to BAR type (SIMPLE-ARRAY (SINGLE-FLOAT * *) (* *))
;  constant 0 type (INTEGER 0 0)
;  constant 0 type (INTEGER 0 0)
; which returns a value of type (SINGLE-FLOAT * *)
;Examining a call to BAR with arguments:
;  symeval FOO type #<STANDARD-CLASS FOO>
; which returns a value of type (SIMPLE-ARRAY (SINGLE-FLOAT * *) (* *))
;Generating a non-inline  call to BAR
;;; Writing fasl file foo.fasl
-- 
        Ola Rinta-Koski                                 ···@cyberell.com
        Cyberell Oy                                     +358 41 467 2502
        Rauhankatu 8 C, FIN-00170 Helsinki, FINLAND	www.cyberell.com
From: Michael Hudson
Subject: Re: Class slot type declarations
Date: 
Message-ID: <m3sni5mn1u.fsf@atrus.jesus.cam.ac.uk>
Ola Rinta-Koski <···@cyberell.com> writes:

>   For some reason, it doesn't work: if the file contains
> 
> (defclass foo ()
>   ((bar :accessor bar :type (simple-array single-float (* *)))))
> 
> (defmethod baz ((foo foo))
>   (aref (bar foo) 0 0))
> 
>   I get the exact same output. Is this a bug (or missing feature) in
>   CMUCL?

I don't think cmucl pays any attention to :type specifiers in defclass
slots.  Calling this a bug is a bit of a stretch; all you got was an
efficiency note, after all.  It would surely be nice if cmucl did
(even) more type analysis, but I don't think that's easy.

Cheers,
M.

-- 
  > Why are we talking about bricks and concrete in a lisp newsgroup?
  After long experiment it was found preferable to talking about why
  Lisp is slower than C++...
                        -- Duane Rettig & Tim Bradshaw, comp.lang.lisp
From: Ola Rinta-Koski
Subject: Re: Class slot type declarations
Date: 
Message-ID: <x5wv7he7hf.fsf@arenal.cyberell.com>
Michael Hudson <···@python.net> writes:
> Ola Rinta-Koski <···@cyberell.com> writes:
> >   For some reason, it doesn't work: if the file contains
> > 
> > (defclass foo ()
> >   ((bar :accessor bar :type (simple-array single-float (* *)))))
> > 
> > (defmethod baz ((foo foo))
> >   (aref (bar foo) 0 0))
> > 
> >   I get the exact same output. Is this a bug (or missing feature) in
> >   CMUCL?

> I don't think cmucl pays any attention to :type specifiers in defclass
> slots.  Calling this a bug is a bit of a stretch; all you got was an
> efficiency note, after all.

  The real reason I am doing this is that it seems aref, when the
  compiler is not able to optimize, does a lot of consing, when
  frankly I don't quite understand why it should do any. I guess I
  will have to take the array out of the class slot.
-- 
        Ola Rinta-Koski                                 ···@cyberell.com
        Cyberell Oy                                     +358 41 467 2502
        Rauhankatu 8 C, FIN-00170 Helsinki, FINLAND	www.cyberell.com
From: Tim Bradshaw
Subject: Re: Class slot type declarations
Date: 
Message-ID: <nkjeltpz6tp.fsf@tfeb.org>
Ola Rinta-Koski <···@cyberell.com> writes:

> 
>   The real reason I am doing this is that it seems aref, when the
>   compiler is not able to optimize, does a lot of consing, when
>   frankly I don't quite understand why it should do any. I guess I
>   will have to take the array out of the class slot.

Use THE or (LOCALLy (DECLARE (TYPE ..))) or something like that to let
the compiler know the type of the object.

It would be *seriously* hard for the compiler to infer the slot type
in the presence of possible class redefinition, however if *you* know
the slot type you can let it know in the method as above.

--tim
From: Marco Antoniotti
Subject: Re: Class slot type declarations
Date: 
Message-ID: <y6cheylgrun.fsf@octagon.mrl.nyu.edu>
Tim Bradshaw <···@tfeb.org> writes:

> Ola Rinta-Koski <···@cyberell.com> writes:
> 
> > 
> >   The real reason I am doing this is that it seems aref, when the
> >   compiler is not able to optimize, does a lot of consing, when
> >   frankly I don't quite understand why it should do any. I guess I
> >   will have to take the array out of the class slot.
> 
> Use THE or (LOCALLy (DECLARE (TYPE ..))) or something like that to let
> the compiler know the type of the object.
> 
> It would be *seriously* hard for the compiler to infer the slot type
> in the presence of possible class redefinition, however if *you* know
> the slot type you can let it know in the method as above.

Now, what would it take to have *ALL* implementors to agree on a

	(defclass la-classe (una-classe un-altra-classe)
	    ( <slots> )
            (:allows-redefinition-p nil))

and

	(defclass la-classe (una-classe un-altra-classe)
	    ( <slots> )
            (:sealed-p t))

?
Where :sealed-p implies :allows-redefinition-p EQ NIL.

Of course, in a (possibly implementation dependent) MOP, you could
always write a

	SLOT-SEALED-P class slot => slot-sealed-p slot-shared-p

When SLOT-SEALED-P returned T and T the compiler could assume some
type information about the content of the slot.

I know similar ideas have been floating around (I just did not have
the time to fish references out).

Cheers

-- 
Marco Antoniotti ========================================================
NYU Courant Bioinformatics Group        tel. +1 - 212 - 998 3488
719 Broadway 12th Floor                 fax  +1 - 212 - 995 4122
New York, NY 10003, USA                 http://bioinformatics.cat.nyu.edu
                    "Hello New York! We'll do what we can!"
                           Bill Murray in `Ghostbusters'.
From: Barry Margolin
Subject: Re: Class slot type declarations
Date: 
Message-ID: <fZyM6.24$IK2.906@burlma1-snr2>
In article <···············@tfeb.org>, Tim Bradshaw  <···@tfeb.org> wrote:
>It would be *seriously* hard for the compiler to infer the slot type
>in the presence of possible class redefinition, however if *you* know
>the slot type you can let it know in the method as above.

The same could be said of return value declarations for ordinary functions,
yet that doesn't stop type inference.

I haven't looked up the exact statement in the standard, but I think the
compiler is allowed to assume that slot type declarations won't change.
Otherwise they serve no practical purpose (if it were just for human
consumption, it could be done in a comment or :DOCUMENTATION).

-- 
Barry Margolin, ······@genuity.net
Genuity, Burlington, MA
*** DON'T SEND TECHNICAL QUESTIONS DIRECTLY TO ME, post them to newsgroups.
Please DON'T copy followups to me -- I'll assume it wasn't posted to the group.
From: Tim Bradshaw
Subject: Re: Class slot type declarations
Date: 
Message-ID: <nkjeltobaqb.fsf@tfeb.org>
Barry Margolin <······@genuity.net> writes:

> 
> The same could be said of return value declarations for ordinary functions,
> yet that doesn't stop type inference.
> 

I'm not sure how this is meant to work.  If you say (DECLAIM ...) for
a function, and then redefine the function incompatibly, are all bets
off?  I suspect they are.

> I haven't looked up the exact statement in the standard, but I think the
> compiler is allowed to assume that slot type declarations won't change.
> Otherwise they serve no practical purpose (if it were just for human
> consumption, it could be done in a comment or :DOCUMENTATION).
> 

I couldn't find anything about that (but it may exist).  I think the
CLOS case is slightly different though: since there is so much
explicit support in CLOS for redefinition and general dynamism, and no
real way of turning that off, it seems to me foolish for a compiler to
make too many assumptions about what is in a slot - the class could be
redefined so the slot doesn't exist!  As Marco Antoniotti pointed out,
I think you need a sealing declaration to do this.

--tim
From: Barry Margolin
Subject: Re: Class slot type declarations
Date: 
Message-ID: <DvSM6.3$6S3.310@burlma1-snr2>
In article <···············@tfeb.org>, Tim Bradshaw  <···@tfeb.org> wrote:
>Barry Margolin <······@genuity.net> writes:
>
>> 
>> The same could be said of return value declarations for ordinary functions,
>> yet that doesn't stop type inference.
>> 
>
>I'm not sure how this is meant to work.  If you say (DECLAIM ...) for
>a function, and then redefine the function incompatibly, are all bets
>off?  I suspect they are.
>
>> I haven't looked up the exact statement in the standard, but I think the
>> compiler is allowed to assume that slot type declarations won't change.
>> Otherwise they serve no practical purpose (if it were just for human
>> consumption, it could be done in a comment or :DOCUMENTATION).
>> 
>
>I couldn't find anything about that (but it may exist).

I found it.  3.2.2.3 Semantic Constrains says:

      Type declarations present in the compilation environment must
      accurately describe the corresponding values at run time; otherwise,
      the consequences are undefined. It is permissible for an unknown type
      to appear in a declaration at compile time, though a warning might be
      signaled in such a case.

And the description of the :TYPE slot option says that it "effectively
declares the type of the reader generic function when applied to an object
of this class."

Like I said, why would we bother with a :TYPE slot option if it didn't do
anything?

-- 
Barry Margolin, ······@genuity.net
Genuity, Burlington, MA
*** DON'T SEND TECHNICAL QUESTIONS DIRECTLY TO ME, post them to newsgroups.
Please DON'T copy followups to me -- I'll assume it wasn't posted to the group.
From: Tim Bradshaw
Subject: Re: Class slot type declarations
Date: 
Message-ID: <nkjpud8szx3.fsf@tfeb.org>
Barry Margolin <······@genuity.net> writes:

> I found it.  3.2.2.3 Semantic Constrains says:
> 
>       Type declarations present in the compilation environment must
>       accurately describe the corresponding values at run time; otherwise,
>       the consequences are undefined. It is permissible for an unknown type
>       to appear in a declaration at compile time, though a warning might be
>       signaled in such a case.
> 
> And the description of the :TYPE slot option says that it "effectively
> declares the type of the reader generic function when applied to an object
> of this class."

Ok, I hadn't correlated those two, but that's obviously right.  I
think there are still significant problems in doing compile-time
type-inference for CLOS though.  For instance in:

(defclass foo ()
  ((x :initform 0
      :accessor foo-x
      :type fixnum)))

(defmethod bar ((foo foo))
  (* (foo-x foo) 1.1))

You can't actually assume what you'd like to, because of the possibility of:

(defclass zig (foo)
  ())

(defmethod foo-x ((z zig))
  1.0)

and calling BAR with a ZIG.

So I think you really do need sealing to do anything much - in
particular you need to know that either there are no subclasses of
FOO, or if there are any they do not override FOO-X to do anything
different. I guess a heroic compiler could do some clever thing of
compiling special code which got invoked if the object it got was
something about which it new enough types, but without sealing I can't
see how to do this statically.

--tim
From: Barry Margolin
Subject: Re: Class slot type declarations
Date: 
Message-ID: <VZTM6.4$6S3.368@burlma1-snr2>
In article <···············@tfeb.org>, Tim Bradshaw  <···@tfeb.org> wrote:
>Ok, I hadn't correlated those two, but that's obviously right.  I
>think there are still significant problems in doing compile-time
>type-inference for CLOS though.  For instance in:
>
>(defclass foo ()
>  ((x :initform 0
>      :accessor foo-x
>      :type fixnum)))
>
>(defmethod bar ((foo foo))
>  (* (foo-x foo) 1.1))
>
>You can't actually assume what you'd like to, because of the possibility of:
>
>(defclass zig (foo)
>  ())
>
>(defmethod foo-x ((z zig))
>  1.0)
>
>and calling BAR with a ZIG.

I think the implication of the sections I quoted is that this ZIG method is
not valid.  The declaration in the FOO class means "if (foo-x y) is called
and y for which (typep y 'foo) is true, the result z will satisfy (typep z
'fixnum)."  If you override a method that's specialized on a superclass,
the return type must be a subclass of the return type of the superclass's
method, in order to satisfy the semantic compile-time/run-time consistency
rules that the compiler is allowed to assume.  However, I don't think this
relationship is ever stated explicitly in the standard.

However, I suspect that the reason for the CMUCL optimization warning in
the original post is that it doesn't make this deep an assumption.

An interesting, related issue is that CLTL1 originally specified the
FUNCTION type declaration in a way that's similar to what I wrote above.
You could write:

(declaim (ftype (function (foo) fixnum) foo-x))

and this would declare the return type of FOO-X only in cases where it was
given FOO arguments, but doesn't limit the function to taking only FOO
arguments.  But this meaning of FTYPE wasn't very useful to implementors
and was unexpected by users, so X3J13 changed it to the meaning we
currently have, which is more like function declarations in conventional
languages (Pascal, Ada, C).  But the :TYPE slot option seems to create
declarations behind the scenes that work like the old FTYPE declarations.
Since implementors didn't find it useful when it was an explicitly
available feature of the language, it's hardly surprising that they
wouldn't optimize it in the more limited case of slots.

-- 
Barry Margolin, ······@genuity.net
Genuity, Burlington, MA
*** DON'T SEND TECHNICAL QUESTIONS DIRECTLY TO ME, post them to newsgroups.
Please DON'T copy followups to me -- I'll assume it wasn't posted to the group.
From: Tim Bradshaw
Subject: Re: Class slot type declarations
Date: 
Message-ID: <ey3pud71yr0.fsf@cley.com>
* Barry Margolin wrote:

> I think the implication of the sections I quoted is that this ZIG method is
> not valid.  The declaration in the FOO class means "if (foo-x y) is called
> and y for which (typep y 'foo) is true, the result z will satisfy (typep z
> 'fixnum)."  If you override a method that's specialized on a superclass,
> the return type must be a subclass of the return type of the superclass's
> method, in order to satisfy the semantic compile-time/run-time consistency
> rules that the compiler is allowed to assume.  However, I don't think this
> relationship is ever stated explicitly in the standard.

Hmm.  I guess that's the right interpretation, but it hinges on what
is meant by `an object of this class', which I'd taken to mean `an
object of exactly this class', probably wrongly.

Anyway, I'd *still* much rather have sealing which would resolve all
of this since the issues of what could be redefined would disappear.


--tim
From: Kent M Pitman
Subject: Re: Class slot type declarations
Date: 
Message-ID: <sfwy9rv8w36.fsf@world.std.com>
Tim Bradshaw <···@cley.com> writes:

> * Barry Margolin wrote:
> 
> > I think the implication of the sections I quoted is that this ZIG method is
> > not valid.  The declaration in the FOO class means "if (foo-x y) is called
> > and y for which (typep y 'foo) is true, the result z will satisfy (typep z
> > 'fixnum)."  If you override a method that's specialized on a superclass,
> > the return type must be a subclass of the return type of the superclass's
> > method, in order to satisfy the semantic compile-time/run-time consistency
> > rules that the compiler is allowed to assume.  However, I don't think this
> > relationship is ever stated explicitly in the standard.
> 
> Hmm.  I guess that's the right interpretation, but it hinges on what
> is meant by `an object of this class', which I'd taken to mean `an
> object of exactly this class', probably wrongly.
> 
> Anyway, I'd *still* much rather have sealing which would resolve all
> of this since the issues of what could be redefined would disappear.

Me, I think the right answer is (or should be) that when you declare
type information for something that inherits, you have to AND it with
outer declarations already in force.  I don't think it's legit to
declare the type of a slot if you're going to override it in a
subclass, which is to say I don't think it's right to make the
subclass do something inconsistent with something already in force
declarationwise.

I went looking for where it might say this and couldn't find it.  But 
I seem to recall this issue coming up with cascaded declarations of specials,
which have a conceptually similar issue and I would think need a conceptually
consistent solution.

All of this just random recollection and opinion, since I'm not citing any
references yet to back me up...
From: Barry Margolin
Subject: Re: Class slot type declarations
Date: 
Message-ID: <3rYM6.10$6S3.334@burlma1-snr2>
In article <···············@world.std.com>,
Kent M Pitman  <······@world.std.com> wrote:
>Tim Bradshaw <···@cley.com> writes:
>
>> * Barry Margolin wrote:
>> 
>> > I think the implication of the sections I quoted is that this ZIG method is
>> > not valid.  The declaration in the FOO class means "if (foo-x y) is called
>> > and y for which (typep y 'foo) is true, the result z will satisfy (typep z
>> > 'fixnum)."  If you override a method that's specialized on a superclass,
>> > the return type must be a subclass of the return type of the superclass's
>> > method, in order to satisfy the semantic compile-time/run-time consistency
>> > rules that the compiler is allowed to assume.  However, I don't think this
>> > relationship is ever stated explicitly in the standard.
>> 
>> Hmm.  I guess that's the right interpretation, but it hinges on what
>> is meant by `an object of this class', which I'd taken to mean `an
>> object of exactly this class', probably wrongly.
>> 
>> Anyway, I'd *still* much rather have sealing which would resolve all
>> of this since the issues of what could be redefined would disappear.
>
>Me, I think the right answer is (or should be) that when you declare
>type information for something that inherits, you have to AND it with
>outer declarations already in force.  I don't think it's legit to
>declare the type of a slot if you're going to override it in a
>subclass, which is to say I don't think it's right to make the
>subclass do something inconsistent with something already in force
>declarationwise.

I'm pretty sure there's already something that says that when a subclass
redefines a slot, its :TYPE is ANDed with the :TYPE inherited from the
superclass.  However, that's not what Tim did in his example.  Rather than
redefine the slot, he overrode the accessor method using DEFMETHOD.

Another point in favor of my interpretation: if we had wanted to allow such
method overriding, we might have said that :TYPE specifies the return type
of SLOT-VALUE rather than referring specifically to the reader generic
function.  Then again, whoever wrote that sentence might just have not
thought through the implications of one wording versus the other.

-- 
Barry Margolin, ······@genuity.net
Genuity, Burlington, MA
*** DON'T SEND TECHNICAL QUESTIONS DIRECTLY TO ME, post them to newsgroups.
Please DON'T copy followups to me -- I'll assume it wasn't posted to the group.
From: Tim Bradshaw
Subject: Re: Class slot type declarations
Date: 
Message-ID: <nkjofsryog9.fsf@tfeb.org>
Barry Margolin <······@genuity.net> writes:

> 
> I'm pretty sure there's already something that says that when a subclass
> redefines a slot, its :TYPE is ANDed with the :TYPE inherited from the
> superclass.  However, that's not what Tim did in his example.  Rather than
> redefine the slot, he overrode the accessor method using DEFMETHOD.

Yes I think that is in 7.5.3.  I also think that my overriding the
accessor method to return a non-subtype is pretty rotten style, and
I'm quite happy thqat it isn't (or may not be) legal!

--tim
From: Tim Moore
Subject: Re: Class slot type declarations
Date: 
Message-ID: <9e12oo$aau$0@216.39.145.192>
On 17 May 2001, Tim Bradshaw wrote:

> So I think you really do need sealing to do anything much - in
> particular you need to know that either there are no subclasses of
> FOO, or if there are any they do not override FOO-X to do anything
> different. I guess a heroic compiler could do some clever thing of
> compiling special code which got invoked if the object it got was
> something about which it new enough types, but without sealing I can't
> see how to do this statically.

Or, instead of wimping out with sealing :), you take a JIT compilation
approach and compile, at runtime, a version that takes uses the type
declaration if the method is called with that class enough times.

There's been quite a few papers written about JIT with respect to Self and
Java; anyone know of comparable research in Lisp?

Tim
From: David Bakhash
Subject: Re: Class slot type declarations
Date: 
Message-ID: <m3k838b70k.fsf@alum.mit.edu>
>>>>> "tim" == Tim Bradshaw <···@tfeb.org> writes:

 >> And the description of the :TYPE slot option says that it
 >> "effectively declares the type of the reader generic function when
 >> applied to an object of this class."

Furthermore, in case no one has mentioned it just yet...

the :type declaration of slots in a DEFCLASS form are inherited by
subclasses unless over-written in the subclasses.  While the standard
_does_ permit the over-riding type declaration in the subclass to be
disjoint from the superclass's type declaration, this is definitely
poor style.  If you define a subclass and redefine the :type slot of
an existing slot, then you should be sure that it's a subtype of the
parent's slot.

If this were mandated in the standard, it certainly wouldn't hurt the
overall ability of compilers to optimize the slot access and storage.

In my opinion, a good CLOS implementation will emit a warning if
someone redefines the type of a slot in a subclass that is not a
proper subtype of the slot definition in the parent.

dave
From: Barry Margolin
Subject: Re: Class slot type declarations
Date: 
Message-ID: <6uWO6.31$XB6.880@burlma1-snr2>
In article <··············@alum.mit.edu>,
David Bakhash  <·····@alum.mit.edu> wrote:
>the :type declaration of slots in a DEFCLASS form are inherited by
>subclasses unless over-written in the subclasses.  While the standard
>_does_ permit the over-riding type declaration in the subclass to be
>disjoint from the superclass's type declaration, this is definitely
>poor style.  If you define a subclass and redefine the :type slot of
>an existing slot, then you should be sure that it's a subtype of the
>parent's slot.

No, the standard does *not* permit the types to be disjoint.  Section 7.5.3
says "The contents of a slot will always be of type (and T1 ... Tn) where
T1 ...Tn are the values of the :type slot options contained in all of the
slot specifiers."

If any of the types are disjoint, (and T1 ... Tn) will be NIL, thus no
object could be stored in the slot.

However, you're correct that the subclass's slot type doesn't have to be a
subtype of the superclass's slot type, they only need to overlap, and the
effective type is the intersection.  But this effective type will, by
definition, be a subtype of both class's slot types (the type (and T1 T2)
is always a subtype of both T1 and T2).  So any optimizations that depend
on this subtype relationship are permitted.

-- 
Barry Margolin, ······@genuity.net
Genuity, Burlington, MA
*** DON'T SEND TECHNICAL QUESTIONS DIRECTLY TO ME, post them to newsgroups.
Please DON'T copy followups to me -- I'll assume it wasn't posted to the group.
From: Tim Bradshaw
Subject: Re: Class slot type declarations
Date: 
Message-ID: <nkjzoc3aymp.fsf@tfeb.org>
David Bakhash <·····@alum.mit.edu> writes:

> the :type declaration of slots in a DEFCLASS form are inherited by
> subclasses unless over-written in the subclasses.  While the standard
> _does_ permit the over-riding type declaration in the subclass to be
> disjoint from the superclass's type declaration, this is definitely
> poor style.  If you define a subclass and redefine the :type slot of
> an existing slot, then you should be sure that it's a subtype of the
> parent's slot.
> 

No it doesn't permit them to be disjoint, they are ANDed together, so
they must overlap or the slot cann never have a value.

--tim
From: Ola Rinta-Koski
Subject: Re: Class slot type declarations
Date: 
Message-ID: <x5sni4e6ge.fsf@arenal.cyberell.com>
Tim Bradshaw <···@tfeb.org> writes:
> Ola Rinta-Koski <···@cyberell.com> writes:
> >   The real reason I am doing this is that it seems aref, when the
> >   compiler is not able to optimize, does a lot of consing, when
> >   frankly I don't quite understand why it should do any. I guess I
> >   will have to take the array out of the class slot.

> Use THE or (LOCALLy (DECLARE (TYPE ..))) or something like that to let
> the compiler know the type of the object.

  I am a bit confused with the exact syntax when referring to
  something in a class slot here.

  So if I have a class

  (defclass foo ()
    ((bar :accessor bar 
          :type (simple-array single-float (* *)))))

  what do I replace ??? with in the following?

  (locally (declare (type (simple-array single-float (* *)) ???)) ...)
-- 
        Ola Rinta-Koski                                 ···@cyberell.com
        Cyberell Oy                                     +358 41 467 2502
        Rauhankatu 8 C, FIN-00170 Helsinki, FINLAND	www.cyberell.com
From: Tim Bradshaw
Subject: Re: Class slot type declarations
Date: 
Message-ID: <nkjd798ba0d.fsf@tfeb.org>
Ola Rinta-Koski <···@cyberell.com> writes:

> 
>   I am a bit confused with the exact syntax when referring to
>   something in a class slot here.
> 
>   So if I have a class
> 
>   (defclass foo ()
>     ((bar :accessor bar 
>           :type (simple-array single-float (* *)))))
> 
>   what do I replace ??? with in the following?
> 
>   (locally (declare (type (simple-array single-float (* *)) ???)) ...)

What I meant was that when you access the slot you can make a
declaration for the type of the thing you get back - in fact it's
probably better just to use LET and a declaration, or to use THE
around the SLOT-VALUE form.

The other thing you could do is use an accessor and make a declaration
for the return type of the accessor.

On the other hand, I tried using / not using THE in CMUCL on a
SLOT-VALUE and I couldn't get the compiler to complain about not being
able to optimise, so I'm not sure that what I've suggested is enough.
My approach to CMUCl has always been to keep hacking at it until the
compiler stops complaining, so without any complaints I'm not sure if
what I'm suggesting does any good.

--tim
From: Kent M Pitman
Subject: Re: Class slot type declarations
Date: 
Message-ID: <sfw7kzgp2l0.fsf@world.std.com>
Ola Rinta-Koski <···@cyberell.com> writes:

> Tim Bradshaw <···@tfeb.org> writes:
> > Ola Rinta-Koski <···@cyberell.com> writes:
> > >   The real reason I am doing this is that it seems aref, when the
> > >   compiler is not able to optimize, does a lot of consing, when
> > >   frankly I don't quite understand why it should do any. I guess I
> > >   will have to take the array out of the class slot.
> 
> > Use THE or (LOCALLy (DECLARE (TYPE ..))) or something like that to let
> > the compiler know the type of the object.
> 
>   I am a bit confused with the exact syntax when referring to
>   something in a class slot here.
> 
>   So if I have a class
> 
>   (defclass foo ()
>     ((bar :accessor bar 
>           :type (simple-array single-float (* *)))))
> 
>   what do I replace ??? with in the following?
> 
>   (locally (declare (type (simple-array single-float (* *)) ???)) ...)

Probably he means something like:

(deflass foo ()
  ((bar)))

(defmethod bar-ref ((foo foo) n m)
  (declare (fixnum n m))
  (with-slots (bar) foo
    (locally (declare (type (simple-array single-float (* *)) bar)))
    (aref foo n m)))

or [which is slightly different because it declares the return type of the 
array rather than its element type; remember, a more general array could
still have the same return type depending on what you knew about what you
stored into it]:

(deflass foo ()
  ((bar)))

(defmethod bar-ref ((foo foo) n m)
  (with-slots (bar) foo
    (the single-float
      (aref foo (the integer n) (the integer m)))))


(defmethod (setf bar-ref) (float (foo foo) n m)
  (with-slots (bar) foo
    (the single-float
      (setf (aref foo (the integer n) (the integer m))
            (the single-float new-float)))))

#|| ;Could also be written like this, though might slow down dispatching
    ;in some implementations because new-float is needlessly discriminated
    ;upon

(defmethod (setf bar-ref) ((new-float single-float) (foo foo) n m)
  (with-slots (bar) foo
    (the single-float
      (setf (aref foo (the integer n) (the integer m))
            new-float))))

||#

or else

(defclass foo ()
  ((bar :accessor bar-internal)))

(defmacro bar (foo)
  ;; Allows use of (bar foo-17) and (setf (bar foo-17) ...)
  ;; but not #'bar (e.g., with apply, funcall, map, etc.)
  ;; since macros are not fbound.
  `(the (simple-array single-float (* *))
        (bar-internal ,foo)))

or else the following, which I think mostly repairs the problem of only
working for forms (bar ...) and not for #'bar.  Open-coding [due to the
inline] probably propagates the type info in most implementations that
do open coding; CMU CL might be more aggressive and propagate the type
info anyway, but I think most implementations wouldn't do that on a closed
coded call.

(defclass foo ()
  ((bar :accessor bar-internal)))

(declaim (inline bar))
(defun bar (foo)
  (the (simple-array single-float (* *))
       (bar-internal foo)))

(declaim (inline (setf bar)))
(defun (setf bar) (new-float foo)
  (setf (the (simple-array single-float (* *))
             (bar-internal foo))
        (the single-float new-float)))