<div dir="ltr"><div>Hi Dimitri,<br><br>Did a bit of research  and found type families to be a good fit for this (<a href="http://www.haskell.org/ghc/docs/latest/html/users_guide/type-families.html">http://www.haskell.org/ghc/docs/latest/html/users_guide/type-families.html</a>).  Type families lets us define the contraints (and a lot of other things) when creating an instance.  I still do not know if this is the ideal solution, but it is still a lot better than the previous solution that I posted.<br>

<br>{-# LANGUAGE ConstraintKinds #-}<br>{-# LANGUAGE TypeFamilies #-}<br>import GHC.Exts<br><br>class Set s where<br>  type C s a :: Constraint -- Here, the explicit type that we would have given is turned into a type synonym of the kind Constraint, from GHC.Exts. <br>

  empty         :: s a <br>  insert        :: (C s a) =>  a -> s a -> s a<br>  member        :: (C s a) => a -> s a -> Bool <br><br><br>data Tree a = Empty | MkTree (Tree a) a (Tree a)<br><br>treeEmpty :: Tree a<br>

treeEmpty = Empty<br><br>treeInsert :: Ord a => a -> Tree a -> Tree a<br>treeInsert = undefined<br><br>treeMember :: Ord a => a -> Tree a -> Bool<br>treeMember = undefined<br><br>instance Set Tree where<br>

  type C Tree a = Ord a -- Here, we are setting the type constraint to Ord a, where a is again a type variable.<br>  empty  = treeEmpty<br>  member = treeMember<br>  insert = treeInsert<br><br><br></div><div>- Akash G<br>

</div><div><br></div><br><div><br></div></div><div class="gmail_extra"><br><br><div class="gmail_quote">On Wed, Aug 13, 2014 at 11:41 AM, Dimitri DeFigueiredo <span dir="ltr"><<a href="mailto:defigueiredo@ucdavis.edu" target="_blank">defigueiredo@ucdavis.edu</a>></span> wrote:<br>

<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
  
    
  
  <div bgcolor="#FFFFFF" text="#000000">
    Hi G Akash,<br>
    <br>
    Is that the only solution? I thought about that. The problem with it
    is that it changes the Set type class. I want the Set type class to
    be able to contain elements of any type, not just members of Ord. <br>
    <br>
    I think the type class represents a "Set" interface that is general.
    It is the implementation using trees that is only available for
    Ordered types. And there may be other implementations that don't
    need this constraint. So, if possible, I don't want to change the
    Set type class. Isn't there another way to fix it?<br>
    <br>
    <br>
    Thanks,<br>
    <br>
    <br>
    Dimitri<br>
    <br>
    <br>
    <div>Em 12/08/14 23:18, akash g escreveu:<br>
    </div><div><div class="h5">
    <blockquote type="cite">
      <div dir="ltr">
        <div>
          <div>Hi Dimitri,<br>
            <br>
          </div>
          You can express the constraints as below<br>
          <br>
          class Set s where<br>
            empty  :: s a               -- returns an empty set of type
          Set of a<br>
            insert :: (Ord a) => a -> s a -> s a   -- returns
          set with new element inserted<br>
            member :: (Ord a) => a -> s a -> Bool  -- True if
          element is a member of the Set<br>
          <br>
        </div>
        <div>This is because when you define tree as an instance of the
          typeclass 'Set', you don't match the constraints on the
          functions that the functions that it wants you to implement 
          That is, when you do:<br>
          <br>
          <br>
          treeInsert :: Ord a => a -> Tree a -> Tree a<br>
          treeInsert = undefined<br>
          <br>
          instance Set Tree where<br>
            empty  = treeEmpty<br>
            insert = treeInsert<br>
            member = treeMember<br>
          <br>
        </div>
        <div>The type signature doesn't match when you do
          insert=treeInsert or member=treeMember, since you have<br>
        </div>
        <div><br>
          class Set s where<br>
        </div>
        <div>   insert :: a -> s a -> s a<br>
          <br>
        </div>
        <div>Hope this helps<br>
        </div>
        <div><br>
        </div>
        <div>- G Akash <br>
        </div>
        <div>
          <div><br>
          </div>
        </div>
      </div>
      <div class="gmail_extra">
        <br>
        <br>
        <div class="gmail_quote">On Wed, Aug 13, 2014 at 8:44 AM,
          Dimitri DeFigueiredo <span dir="ltr"><<a href="mailto:defigueiredo@ucdavis.edu" target="_blank">defigueiredo@ucdavis.edu</a>></span>
          wrote:<br>
          <blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
            Hi All,<br>
            <br>
            I am working through an exercise in Chris Okasaki's book
            (#2.2). In the book, he is trying to implement a minimal
            interface for a Set. I wrote that simple interface in
            Haskell as:<br>
            <br>
            class Set s where<br>
                empty  :: s a                -- returns an empty set of
            type Set of a<br>
                insert :: a -> s a -> s a   -- returns set with
            new element inserted<br>
                member :: a -> s a -> Bool  -- True if element is
            a member of the Set<br>
            <br>
            To implement that interface with the appropriately O(log n)
            insert and member functions he suggests the use of a Binary
            Search Tree, which I translated to Haskell as:<br>
            <br>
            data Tree a = Empty | MkTree (Tree a) a (Tree a)<br>
            <br>
            But for the tree to work, we also need the "a"s to be
            totally ordered. I.e. (Ord a) is a constraint. So, it makes
            sense to write:<br>
            <br>
            treeEmpty :: Tree a<br>
            treeEmpty = Empty<br>
            <br>
            treeInsert :: Ord a => a -> Tree a -> Tree a<br>
            treeInsert = undefined<br>
            <br>
            treeMember :: Ord a => a -> Tree a -> Bool<br>
            treeMember = undefined<br>
            <br>
            Now, I would like to bind this implementation using Trees of
            an ordered type "a" to the set type class. So, I would like
            to write something like:<br>
            <br>
            instance Set Tree where<br>
                empty  = treeEmpty<br>
                insert = treeInsert<br>
                member = treeMember<br>
            <br>
            But that doesn't work. Using GHC 7.6.3, I get a:<br>
            <br>
                No instance for (Ord a) arising from a use of
            `treeInsert'<br>
                Possible fix:<br>
                  add (Ord a) to the context of<br>
                    the type signature for insert :: a -> Tree a
            -> Tree a<br>
                In the expression: treeInsert a<br>
                In an equation for `insert': insert a = treeInsert a<br>
                In the instance declaration for `Set Tree'<br>
            <br>
            Which makes sense, but I'm not sure how to express this
            constraint.<br>
            So, what is the proper way to do this?<br>
            Where have I gone wrong?<br>
            <br>
            <br>
            Thanks!<br>
            <br>
            Dimitri<br>
            <br>
            <br>
            <br>
            <br>
            <br>
            <br>
            _______________________________________________<br>
            Beginners mailing list<br>
            <a href="mailto:Beginners@haskell.org" target="_blank">Beginners@haskell.org</a><br>
            <a href="http://www.haskell.org/mailman/listinfo/beginners" target="_blank">http://www.haskell.org/mailman/listinfo/beginners</a><br>
          </blockquote>
        </div>
        <br>
      </div>
      <br>
      <fieldset></fieldset>
      <br>
      <pre>_______________________________________________
Beginners mailing list
<a href="mailto:Beginners@haskell.org" target="_blank">Beginners@haskell.org</a>
<a href="http://www.haskell.org/mailman/listinfo/beginners" target="_blank">http://www.haskell.org/mailman/listinfo/beginners</a>
</pre>
    </blockquote>
    <br>
  </div></div></div>

<br>_______________________________________________<br>
Beginners mailing list<br>
<a href="mailto:Beginners@haskell.org">Beginners@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/beginners" target="_blank">http://www.haskell.org/mailman/listinfo/beginners</a><br>
<br></blockquote></div><br></div>