Constrained genericity

From Rosetta Code
Task
Constrained genericity
You are encouraged to solve this task according to the task description, using any language you may know.

Constrained genericity or bounded quantification means that a parametrized type or function (see parametric polymorphism) can only be instantiated on types fulfilling some conditions, even if those conditions are not used in that function.

Say a type is called "eatable" if you can call the function eat on it. Write a generic type FoodBox which contains a collection of objects of a type given as parameter, but can only be instantiated on eatable types. The FoodBox shall not use the function eat in any way (i.e. without the explicit restriction, it could be instantiated on any type). The specification of a type being eatable should be as generic as possible in your language (i.e. the restrictions on the implementation of eatable types should be as minimal as possible). Also explain the restrictions, if any, on the implementation of eatable types, and show at least one example of an eatable type.

Ada

Ada allows various constraints to be specified in parameters of generics. A formal type constrained to be derived from certain base is one of them: <lang ada>with Ada.Containers.Indefinite_Vectors;

package Nutrition is

  type Food is interface;
  procedure Eat (Object : in out Food) is abstract;

end Nutrition;

with Ada.Containers; with Nutrition;

generic

  type New_Food is new Nutrition.Food;

package Food_Boxes is

 package Food_Vectors is
     new Ada.Containers.Indefinite_Vectors
         (  Index_Type   => Positive,
            Element_Type => New_Food
         );
  subtype Food_Box is Food_Vectors.Vector;

end Food_Boxes;</lang> The package Nutrition defines an interface of an eatable object, that is, the procedure Eat. Then a generic container package is defined with the elements to be of some type derived from Food. Example of use: <lang ada>type Banana is new Food with null record; overriding procedure Eat (Object : in out Banana) is null; package Banana_Box is new Food_Boxes (Banana);

type Tomato is new Food with null record; overriding procedure Eat (Object : in out Tomato) is null; package Tomato_Box is new Food_Boxes (Tomato); -- We have declared Banana and Tomato as a Food.</lang> The Tomato_Box can only contain tomatoes; the Banana_Box can only contain bananas. You can only create boxes of eatable objects.

C#

In C#, type constraints are made on the type hierarchy, so here we make IEatable an interface, with an Eat method. Types which are eatable would have to implement the IEatable interface and provide an Eat method. <lang csharp>interface IEatable {

   void Eat();

}</lang> Type constraints in type parameters can be made via the where keyword, which allows us to qualify T. In this case, we indicate that the type argument must be a type that is a subtype of IEatable. <lang csharp>using System.Collections.Generic;

class FoodBox<T> where T : IEatable {

   List<T> food;

}</lang> For example, an eatable Apple: <lang csharp>class Apple : IEatable {

   public void Eat()
   {
       System.Console.WriteLine("Apple has been eaten");
   }

}</lang> C# also has the interesting functionality of being able to require that a generic type have a default constructor. This means that the generic type can actually instantiate the objects without ever knowing the concrete type. To do so, we constrain the where clause with an additional term "new()". This must come after any other constraints. In this example, any type with a default constructor that implements IEatable is allowed. <lang csharp>using System.Collections.Generic

class FoodMakingBox<T> where T : IEatable, new() {

   List<T> food;
   void Make(int numberOfFood)
   {
       this.food = new List<T>();
       for (int i = 0; i < numberOfFood; i++)
       {
           this.food.Add(new T());
       }
   }

}</lang>

Common Lisp

The technique used here is like that in the Abstract type task.

The task says that this task is only for statically typed languages, and Common Lisp is dynamically typed. However, there are many places where type declarations can be provided to the compiler, and there is user access to the type system (e.g., a user can ask whether an object is of a particular type). Via the latter mechanism, one could write a class containing a collection such that the insert method checked that the object to be inserted is of an appropriate type.

In this example, we define a class food, and two subclasses, inedible-food and edible-food. We define a generic function eat, and specialize it only for edible-food. We then define a predicate eatable-p which returns true only on objects for which eat methods have been defined. Then, using deftype with a satisfies type specifier, we define a type eatable to which only objects satisfying eatable-p belong. Finally, we define a function make-food-box which takes, in addition to typical array creation arguments, a type specifier. The array is declared to have elements of the type that is the intersection of food and the provided type. make-eatable-food-box simply calls make-food-box with the type eatable.

The only shortcoming here is that the compiler isn't required to enforce the type specifications for the arrays. A custom insert function, however, could remember the specified type for the collection, and assert that inserted elements are of that type. <lang lisp>(defclass food () ())

(defclass inedible-food (food) ())

(defclass edible-food (food) ())

(defgeneric eat (foodstuff)

 (:documentation "Eat the foodstuff."))

(defmethod eat ((foodstuff edible-food))

 "A specialized method for eating edible-food."
 (format nil "Eating ~w." foodstuff))

(defun eatable-p (thing)

 "Returns true if there are eat methods defined for thing."
 (not (endp (compute-applicable-methods #'eat (list thing)))))

(deftype eatable ()

 "Eatable objects are those satisfying eatable-p."
 '(satisfies eatable-p))

(defun make-food-box (extra-type &rest array-args)

 "Returns an array whose element-type is (and extra-type food).

array-args should be suitable for MAKE-ARRAY, and any provided element-type keyword argument is ignored."

 (destructuring-bind (dimensions &rest array-args) array-args
   (apply 'make-array dimensions
          :element-type `(and ,extra-type food)
          array-args)))

(defun make-eatable-food-box (&rest array-args)

 "Return an array whose elements are declared to be of type (and

eatable food)."

 (apply 'make-food-box 'eatable array-args))</lang>

D

Template Version

<lang d>enum IsEdible(T) = is(typeof(T.eat));

struct FoodBox(T) if (IsEdible!T) {

   T[] food;
   alias food this;

}

struct Carrot {

   void eat() {}

}

static struct Car {}

void main() {

   FoodBox!Carrot carrotsBox; // OK
   carrotsBox ~= Carrot();    // Adds a carrot
   //FoodBox!Car carsBox;     // Not allowed

}</lang>

Interface Version

<lang d>interface IEdible { void eat(); }

struct FoodBox(T : IEdible) {

   T[] food;
   alias food this;

}

class Carrot : IEdible {

   void eat() {}

}

class Car {}

void main() {

   FoodBox!Carrot carrotBox; // OK
   //FoodBox!Car carBox;     // Not allowed

}</lang>

E

It is surely arguable whether this constitutes an implementation of the above task: <lang e>/** Guard accepting only objects with an 'eat' method */ def Eatable {

   to coerce(specimen, ejector) {
       if (Ref.isNear(specimen) && specimen.__respondsTo("eat", 0)) {
           return specimen
       } else {
           throw.eject(ejector, `inedible: $specimen`)
       }
   }

}

def makeFoodBox() {

   return [].diverge(Eatable) # A guard-constrained list

}</lang>

Eiffel

Eiffel has included support for constrained genericty since its earliest implementations (as shown in Bertrand Meyer's paper from OOPSLA '86, available online.)

The "eatable" characteristic is modeled by a deferred class (deferred classes are similar to abstract classes in some other languages).

<lang eiffel > deferred class

   EATABLE

feature -- Basic operations

   eat
           -- Eat this eatable substance
       deferred
       end

end </lang>

Class EATABLE can then be inherited by any other class, with the understanding that the inheriting class will have to provide an implementation for the procedure eat. Here are two such classes, APPLE and PEAR:

<lang eiffel > class

   APPLE

inherit

   EATABLE

feature -- Basic operations

   eat
           -- Consume
       do
           print ("One apple eaten%N")
       end

end </lang>


<lang eiffel > class

   PEAR

inherit

   EATABLE

feature -- Basic operations

   eat
           -- Consume
       do
           print ("One pear eaten%N")
       end

end </lang>

Instances of the generic class FOOD_BOX can contain any types of EATABLE items. The constraint is shown in the formal generics part of the class declaration for FOOD_BOX:

<lang eiffel> class

   FOOD_BOX [G -> EATABLE]

inherit

   ARRAYED_LIST [G]

create

   make

end </lang>

So, any declaration of type FOOD_BOX can constrain its contents to any particular eatable type. For example:

<lang eiffel>

   my_apple_box: FOOD_BOX [APPLE]

</lang>

The entity my_apple_box is declared as a FOOD_BOX which can contain only apples.

Of course, constraining a particular FOOD_BOX to all types which are eatable is also allowed, and could be appropriate in certain cases, such as:

<lang eiffel>

   my_refrigerator: FOOD_BOX [EATABLE]

</lang>

Here's a small application that uses a FOOD_BOX constrained to contain only apples:

<lang eiffel > class

   APPLICATION

create

   make

feature {NONE} -- Initialization

   make
           -- Run application.
       do
           create my_apple_box.make (10)
           create one_apple
           create one_pear
           my_apple_box.extend (one_apple)

-- my_apple_box.extend (one_pear)

           across
               my_apple_box as ic
           loop
               ic.item.eat
           end
       end

feature -- Access

   my_apple_box: FOOD_BOX [APPLE]
           -- My apple box
   one_apple: APPLE
           -- An apple
   one_pear: PEAR
           -- A pear

end </lang>

Notice that an instance of PEAR is also created, and a line of code is present as a comment which would attempt to place the pear in the apple box:

<lang eiffel> -- my_apple_box.extend (one_pear) </lang>

If the comment mark "--" were removed from this line of code, an compile error would occur because of the attempt to violate my_apple_bos's constraint.

F#

It is possible to constrain type parameters in a number of ways, including inheritance relationships and interface implementation. But for this task, the natural choice is an explicit member constraint. <lang fsharp>type ^a FoodBox // a generic type FoodBox

 when ^a: (member eat: unit -> string) // with an explicit member constraint on ^a,
 (items:^a list) =                     // a one-argument constructor
 member inline x.foodItems = items     // and a public read-only property

// a class type that fullfills the member constraint type Banana() =

 member x.eat() = "I'm eating a banana."

// an instance of a Banana FoodBox let someBananas = FoodBox [Banana(); Banana()]</lang>

Forth

Works with: Forth

Works with any ANS Forth with one dependency

Needs the FMS-SI (single inheritance) library code located here: http://soton.mpeforth.com/flag/fms/index.html <lang forth>include FMS-SI.f include FMS-SILib.f

\ This code uses an implementation dependent word dfa>xt \ which converts a data-field address to an executable token.

dfa>xt ( a-addr -- xt ) \ implementation dependent for VFX Forth
 5 - ;
where { class-xt where-xt -- flag }
    begin
      class-xt ['] object <> 
    while
      class-xt where-xt = if true exit then
      class-xt >body sfa @ dfa>xt to class-xt
    repeat false ;
class Eatable
 :m eat ;m
class

\ FoodBox is defined without using eat in any way.

class FoodBox
 object-list eatable-types
 :m fill: { n class-xt -- }
    class-xt ['] Eatable where 
    if   n 0 do class-xt eatable-types xtadd: loop
    else ." not an eatable type " 
    then ;m
 :m test:
    begin eatable-types each:
    while eat cr ." successful eat"
    repeat ;m
class

FoodBox fb 3 ' Eatable fb fill: fb test: successful eat successful eat successful eat

FoodBox fb1 5 ' object fb1 fill: \ => not an eatable type

class apple <super Eatable
class
class green-apple <super apple
class

5 ' green-apple fb1 fill: fb1 test: successful eat successful eat successful eat successful eat successful eat </lang>


Go

Go's interfaces do exactly what this task wants. Eatable looks like this: <lang go>type eatable interface {

   eat()

}</lang> And the following is all it takes to define foodbox as a slice of eatables. The result is that an object of type foodbox can hold objects of any type that implements the eat method (with the function signature specified in eatable.) The definition of foodbox though, doesn't even need to enumerate the functions of eatable, much less call them. Whatever is in the interface is okay. <lang go>type foodbox []eatable</lang> Here is an example of an eatable type. <lang go>type peelfirst string

func (f peelfirst) eat() {

   // peel code goes here
   fmt.Println("mm, that", f, "was good!")

}</lang> The only thing it takes to make peelfirst eatable is the definition of the eat method. When the eat method is defined, peelfirst automatically becomes an eatable. We say it satisfies the interface. Notice that "eatable" appears nowhere in the definition of peelfirst or the eat method of peelfirst.

Here is a complete program using these types. <lang go>package main

import "fmt"

type eatable interface {

   eat()

}

type foodbox []eatable

type peelfirst string

func (f peelfirst) eat() {

   // peel code goes here
   fmt.Println("mm, that", f, "was good!")

}

func main() {

   fb := foodbox{peelfirst("banana"), peelfirst("mango")}
   f0 := fb[0]
   f0.eat()

}</lang>

Output:
mm, that banana was good!

Haskell

A type class defines a set of operations that must be implemented by a type: <lang haskell>class Eatable a where

 eat :: a -> String</lang>

We just require that instances of this type class implement a function eat which takes in the type and returns a string (I arbitrarily decided).

The FoodBox type could be implemented as follows: <lang haskell>data (Eatable a) => FoodBox a = F [a]</lang> The stuff before the => specify what type classes the type variable a must belong to.

We can create an instance of Eatable at any time by providing an implementation for the function eat. Here we define a new type Banana, and make it an instance of Eatable. <lang haskell>data Banana = Foo -- the implementation doesn't really matter in this case instance Eatable Banana where

 eat _ = "I'm eating a banana"</lang>

We can declare existing types to be instances in the exact same way. The following makes Double an eatable type: <lang haskell>instance Eatable Double where

 eat d = "I'm eating " ++ show d</lang>

Another way to make an existing type eatable is to declare all instances of another type class instances of this one. Let's assume we have another type class Food which looks like this; <lang haskell>class Food a where

 munch :: a -> String</lang>

Then we can make all instances of Food eatable using munch for eat with the following instance declaration: <lang haskell>instance (Food a) => Eatable a where

 eat x = munch x</lang>

Icon and Unicon

Neither Icon nor Unicon are statically typed. In Unicon, new types can be defined as classes. The solution shown follows the Scala approach. <lang unicon>import Utils # From the UniLib package to get the Class class.

class Eatable:Class() end

class Fish:Eatable(name)

   method eat(); write("Eating "+name); end

end

class Rock:Class(name)

   method eat(); write("Eating "+name); end

end

class FoodBox(A) initially

   every item := !A do if "Eatable" == item.Type() then next else bad := "yes" 
   return /bad

end

procedure main()

   if FoodBox([Fish("salmon")]) then write("Edible") else write("Inedible")
   if FoodBox([Rock("granite")]) then write("Edible") else write("Inedible")

end</lang>

Sample run:

->cg
Edible
Inedible
->

J

J is not a statically typed language, but I do not see why we should not implement this in J: <lang j>coclass'Connoisseur' isEdible=:3 :0

 0<nc<'eat__y'

)

coclass'FoodBox' create=:3 :0

 assert isEdible_Connoisseur_ type=:y
 collection=: 0#y

) add=:3 :0"0

 'inedible' assert type e. copath y
 collection=: collection, y

)</lang> An edible type would be a class that has a verb with the name 'eat'. For example: <lang j>coclass'Apple' eat=:3 :0

 smoutput'delicious'

)</lang> And here is a quicky demo of the above: <lang j>

  lunch=:(<'Apple') conew 'FoodBox'
  a1=: conew 'Apple'
  a2=: conew 'Apple'
  add__lunch a1
  add__lunch a2
  george=: conew 'Connoisseur'
  add__lunch george

|inedible: assert</lang>

Java

Works with: Java version 5

In Java type constraints are made on the type hierarchy, so here we make Eatable an interface, with an eat method. Types which are Eatable would have to implement the Eatable interface and provide an eat method. <lang java5>interface Eatable {

   void eat();

}</lang> Type constraints in type parameters can be made via the extends keyword, indicating in this case that the type argument must be a type that is a subtype of Eatable. <lang java5>import java.util.List;

class FoodBox<T extends Eatable> {

   public List<T> food;

}</lang> Similarly a generic method can constrain its type parameters <lang java5>public <T extends Eatable> void foo(T x) { } // although in this case this is no more useful than just "public void foo(Eatable x)"</lang> This T does not necessarily have to be defined in the class declaration. Another method may be declared like this: <lang java5>public class Test{

  public <T extends Eatable> void bar(){ }

}</lang> which has no indication of where T is coming from. This method could be called like this: <lang java5>test.<EatableClass>bar();</lang> The foo method from before can figure out T from its parameter, but this bar method needs to be told what T is.

Nemerle

<lang Nemerle>using System.Collections.Generic;

interface IEatable {

   Eat() : void;

}

class FoodBox[T] : IEnumerable[T]

 where T : IEatable

{

   private _foods : list[T] = [];
   
   public this() {}
   
   public this(items : IEnumerable[T])
   {
       this._foods = $[food | food in items];
   }
   
   public Add(food : T) : FoodBox[T]
   {
       FoodBox(food::_foods);
   }
   
   public GetEnumerator() : IEnumerator[T]
   {
       _foods.GetEnumerator();
   }

}

class Apple : IEatable {

   public this() {}
   
   public Eat() : void
   {
       System.Console.WriteLine("nom..nom..nom");
   }

}

mutable appleBox = FoodBox(); repeat(3) {

   appleBox = appleBox.Add(Apple());

}

foreach (apple in appleBox) apple.Eat();</lang>

Output:
nom..nom..nom
nom..nom..nom
nom..nom..nom

Nim

<lang nim>type

 Eatable = generic e
   eat(e)
 FoodBox[e: Eatable] = seq[e]
 Food = object
   name: string
   count: int

proc eat(x: int) = echo "Eating the int: ", x proc eat(x: Food) = echo "Eating ", x.count, " ", x.name, "s"

var ints = FoodBox[int](@[1,2,3,4,5]) var fs = FoodBox[Food](@[])

fs.add Food(name: "Hamburger", count: 3) fs.add Food(name: "Cheeseburger", count: 5)

for f in fs:

 eat(f)</lang>

OCaml

OCaml handles type constraints through modules and module types.

A module type defines a set of operations that must be implemented by a module: <lang ocaml>module type Eatable = sig

 type t
 val eat : t -> unit

end</lang> We just require that module instances of this module type describe a type t and implement a function eat which takes in the type and returns nothing.

The FoodBox generic type could be implemented as a functor (something which takes a module as an argument and returns another module): <lang ocaml>module MakeFoodBox(A : Eatable) = struct

 type elt = A.t
 type t = F of elt list
 let make_box_from_list xs = F xs

end</lang>

We can create a module that is an instance of Eatable by specifying a type providing an implementation for the function eat. Here we define a module Banana, and make it an instance of Eatable. <lang ocaml>type banana = Foo (* a dummy type *)

module Banana : Eatable with type t = banana = struct

 type t = banana
 let eat _ = print_endline "I'm eating a banana"

end</lang>

We can also create modules that use an existing type as its t. The following module uses float as its type: <lang ocaml>module EatFloat : Eatable with type t = float = struct

 type t = float
 let eat f = Printf.printf "I'm eating %f\n%!" f

end</lang> Then, to make a FoodBox out of one of these modules, we need to call the functor on the module that specifies the type parameter: <lang ocaml>module BananaBox = MakeFoodBox (Banana) module FloatBox = MakeFoodBox (EatFloat)

let my_box = BananaBox.make_box_from_list [Foo] let your_box = FloatBox.make_box_from_list [2.3; 4.5]</lang> Unfortunately, it is kind of cumbersome in that, for every type parameter we want to use for this generic type, we will have to explicitly create a module for the resulting type (i.e. BananaBox, FloatBox). And the operations on that resulting type (i.e. make_box_from_list) are tied to each specific module.

ooRexx

ooRexx methods, routines, and collections are all untyped, so there are no language-level checks for type matches. Tests for identity need to be performed at runtime using mechanisms such as the object isA method. <lang ooRexx> call dinnerTime "yogurt" call dinnerTime .pizza~new call dinnerTime .broccoli~new


-- a mixin class that defines the interface for being "food", and -- thus expected to implement an "eat" method

class food mixinclass object
method eat abstract
class pizza subclass food
method eat
 Say "mmmmmmmm, pizza".

-- mixin classes can also be used for multiple inheritance

class broccoli inherit food
method eat
 Say "ugh, do I have to?".
routine dinnerTime
 use arg dish
 -- ooRexx arguments are typeless, so tests for constrained
 -- types must be peformed at run time.  The isA method will
 -- check if an object is of the required type
 if \dish~isA(.food) then do
    say "I can't eat that!"
    return
 end
 else dish~eat

</lang>


OxygenBasic

Generic but not too generic I trust. <lang oxygenbasic> macro Gluttony(vartype, capacity, foodlist) '==========================================

typedef vartype physical

enum food foodlist

type ActualFood

 sys      name
 physical size
 physical quantity

end type

Class foodbox '============ has ActualFood Item[capacity] sys max

method put(sys f, physical s,q)

 max++
 Item[max]<=f,s,q

end method

method GetNext(ActualFood *Stuff)

 if max then
   copy @stuff,@Item[max], sizeof Item
   max--
 end if

end method

end class

Class Gourmand '============= physical WeightGain, SleepTime

method eats(ActualFood *stuff)

 WeightGain+=stuff.size*stuff.quantity*0.75
 stuff.size=0
 stuff.quantity=0

end method

end class

end macro


'IMPLEMENTATION '==============


Gluttony ( double,100,{ oyster,trout,bloater, chocolate,truffles, cheesecake,cream,pudding,pie })

% small 1 % medium 2 % large 3 % huge 7

% none 0 % single 1 % few 3 % several 7 % many 12

'INSTANCE '========

FoodBox Hamper Gourmand MrG

'TEST '====

Hamper.put food.pudding,large,several Hamper.put food.pie,huge,few ActualFood Course Hamper.GetNext Course MrG.eats Course

print MrG.WeightGain 'result 15.75 </lang>

Perl 6

Works with: Rakudo version 2010.09.17

<lang perl6>subset Eatable of Any where { .^can('eat') };

class Cake { method eat() {...} }

role FoodBox[Eatable ::T] {

   has T %.foodbox;

}

class Yummy does FoodBox[Cake] { } # composes correctly

  1. class Yucky does FoodBox[Int] { } # fails to compose

my Yummy $foodbox .= new; say $foodbox.perl;</lang>

Output:

<lang>Yummy.new(foodbox => {})</lang>

PicoLisp

<lang PicoLisp>(class +Eatable)

(dm eat> ()

  (prinl "I'm eatable") )


(class +FoodBox)

  1. obj

(dm set> (Obj)

  (unless (method 'eat> Obj)                # Check if the object is eatable
     (quit "Object is not eatable" Obj) )
  (=: obj Obj) )                            # If so, set the object


(let (Box (new '(+FoodBox)) Eat (new '(+Eatable)) NoEat (new '(+Bla)))

  (set> Box Eat)       # Works
  (set> Box NoEat) )   # Gives an error</lang>
Output:
$384320489 -- Object is not eatable

? (show Box)          
$384320487 (+FoodBox)
   obj $384320488

? (show Box 'obj)
$384320488 (+Eatable)

? (show NoEat)   
$384320489 (+Bla)

Racket

edible<%> objects simply need to state that they implement the interface in the second argument to class*. By doing so they will be forced to implement eat.

<lang racket>#lang racket (module+ test (require tests/eli-tester))

This is all that an object should need to properly implement.

(define edible<%>

 (interface () [eat (->m void?)]))

(define (generic-container<%> containee/c)

 (interface ()
   [contents  (->m (listof containee/c))]
   [insert    (->m containee/c void?)]
   [remove-at (->m exact-nonnegative-integer? containee/c)]
   [count     (->m exact-nonnegative-integer?)]))

(define ((generic-box-mixin containee/c) %)

 (->i ([containee/c contract?])
      (rv (containee/c) (implementation?/c (generic-container<%> containee/c))))
 (class* % ((generic-container<%> containee/c))
   (super-new)
   (define l empty)
   (define/public (contents) l)
   (define/public (insert o) (set! l (cons o l)))
   (define/public (remove-at i)
     (begin0 (list-ref l i)
             (append (take l i) (drop l (add1 i)))))
   (define/public (count) (length l))))
As I understand it, a "Food Box" from the task is still a generic... i.e.
you will specify it down ;; to an "apple-box%" so
food-box%-generic is still
generic. food-box% will take any kind of food.

(define/contract (food-box-mixin T%)

 (-> (or/c (λ (i) (eq? edible<%> i)) (implementation?/c edible<%>))
  (make-mixin-contract))
 (generic-box-mixin (and/c (is-a?/c edible<%>) (is-a?/c T%))))

(module+ test

 (define integer-box% ((generic-box-mixin integer?) object%))
 (define integer-box  (new integer-box%))
 
 (define apple%
   (class* object% (edible<%>)
     (super-new)
     (define/public (eat)
       (displayln "nom!"))))
 
 (define banana%
   (class* object% (edible<%>)
     (super-new)
     (define/public (eat)
       (displayln "peel.. peel... nom... nom!"))))
 
 (define semolina%
   (class* object% () ; <-- empty interfaces clause
     (super-new)
     ;; you can call eat on it... but it's not explicitly (or even vaguely)
     ;; edible<%>
     (define/public (eat) (displayln "blech!"))))
 
 ;; this will take any object that is edible<%> and edible<%> (therefore all
 ;; edible<%> objects)
 (define any-food-box (new ((food-box-mixin edible<%>) object%)))
 
 ;; this will take any object that is edible and an apple<%>
 ;; (therefore only apple<%>s)
 (define apple-food-box (new ((food-box-mixin apple%) object%)))
 
 (test
  ;; Test generic boxes
  (send integer-box insert 22)
  (send integer-box insert "a string") =error> exn:fail:contract?
  
  ;; Test the food box that takes any edible<%>
  (send any-food-box insert (new apple%))
  (send any-food-box insert (new banana%))
  (send any-food-box insert (new semolina%)) =error> exn:fail:contract?
  
  ;; Test the food box that takes any apple%
  (send apple-food-box insert (new apple%))
  (send apple-food-box insert (new banana%)) =error> exn:fail:contract?
  (send apple-food-box insert (new semolina%)) =error> exn:fail:contract?
  (send apple-food-box count) => 1
  
  ;; Show that you cannot make a food-box from the non-edible<%> semolina cannot
  (implementation? semolina% edible<%>) => #f
  (new ((food-box-mixin semolina%) object%)) =error> exn:fail:contract?))</lang>

All the tests pass. Look at the tests to see what generates an exception (i.e. not allowed at runtime) and what does not.

Sather

<lang sather>abstract class $EDIBLE is

 eat;

end;

class FOOD < $EDIBLE is

 readonly attr name:STR;
 eat is
   #OUT + "eating " + self.name + "\n";
 end;
 create(name:STR):SAME is
   res ::= new;
   res.name := name;
   return res;
 end;

end;

class CAR is

 readonly attr name:STR;
 create(name:STR):SAME is
   res ::= new;
   res.name := name;
   return res;
 end;

end;

class FOODBOX{T < $EDIBLE} is

 private attr list:LLIST{T};
 create:SAME is
   res ::= new;
   res.list := #;
   return res;
 end;
 add(c :T) is
   self.list.insert_back(c);
 end;
 elt!:T is loop yield self.list.elt!; end; end;

end;

class MAIN is

 main is
   box  ::= #FOODBOX{FOOD}; -- ok
   box.add(#FOOD("Banana"));
   box.add(#FOOD("Amanita Muscaria"));
   box2 ::= #FOODBOX{CAR};  -- not ok
   box2.add(#CAR("Punto")); -- but compiler let it pass!
   -- eat everything
   loop box.elt!.eat; end;
 end;

end;</lang> The GNU Sather compiler v1.2.3 let the "box2" pass, even though it shouldn't. Read e.g. this tutorial's section

Scala

Scala can constrain types in many different ways. This specific constrain, for the type to contain a particular method, can be written as this: <lang scala>type Eatable = { def eat: Unit }

class FoodBox(coll: List[Eatable])

case class Fish(name: String) {

 def eat {
   println("Eating "+name)
 }

}

val foodBox = new FoodBox(List(new Fish("salmon")))</lang> A more extensive discussion on genericity in Scala and some of the constrains that can be imposed can be found on Parametric Polymorphism.

Swift

Here we make Eatable a protocol, with an eat method. Types which are Eatable would have to conform to the Eatable protocol and provide an eat method. <lang swift>protocol Eatable {

   func eat()

}</lang> Type constraints in type parameters can be made via the : syntax, indicating in this case that the type argument must be a type that is a subtype of Eatable. <lang swift>struct FoodBox<T: Eatable> {

   var food: [T]

}</lang> Similarly a generic function or method can constrain its type parameters <lang swift>func foo<T: Eatable>(x: T) { } // although in this case this is no more useful than just "func foo(x: Eatable)"</lang>

zkl

zkl isn't statically typed so the test is done at runtime.

This is a slightly different take on the task, keeping the editables and rejecting the garbage. <lang zkl>class Eatable{ var v;

  fcn eat{ println("munching ",self.topdog.name); }

} class FoodBox{

  fcn init(food1,food2,etc){
     editable,garbage:=vm.arglist.filter22("isChildOf",Eatable);
     var contents=editable;
     if(garbage) println("Rejecting: ",garbage);
  }

}</lang> <lang zkl>class Apple(Eatable){} class Nuts(Eatable){} class Foo{} FoodBox(Apple,"boogers",Nuts,Foo).contents.apply2("eat");</lang>

Output:
Rejecting: L("boogers",Class(Foo))
munching Apple
munching Nuts