
I'm sure there's a way to do this, but it's escaping me at present. I want to do something like this: data Foo = Bar a => Foo a Bool ... That is, I want to create a new type, Foo, whose constructor takes both a Boolean and a value of a type of class Bar.

On Sat, Dec 27, 2008 at 2:24 PM, Andrew Wagner
I'm sure there's a way to do this, but it's escaping me at present. I want to do something like this:
data Foo = Bar a => Foo a Bool ...
That is, I want to create a new type, Foo, whose constructor takes both a Boolean and a value of a type of class Bar.
Try this:
{-# LANGUAGE ExistentialQuantification #-}
data Foo = forall a. Bar a => Foo a Bool
--
Dave Menendez

On Sat, Dec 27, 2008 at 12:44 PM, David Menendez
On Sat, Dec 27, 2008 at 2:24 PM, Andrew Wagner
wrote: I'm sure there's a way to do this, but it's escaping me at present. I want to do something like this:
data Foo = Bar a => Foo a Bool ...
That is, I want to create a new type, Foo, whose constructor takes both a Boolean and a value of a type of class Bar.
Try this:
{-# LANGUAGE ExistentialQuantification #-}
data Foo = forall a. Bar a => Foo a Bool
Though for existentials, I find GADT more natural (actually I find GADT more natural in most cases): data Foo where Foo :: Bar a => a -> Foo Luke

There is a disadvantage in GADTs. They don't work in Hugs. On 27 Dec 2008, at 22:49, Luke Palmer wrote:
wrote: I'm sure there's a way to do this, but it's escaping me at
On Sat, Dec 27, 2008 at 12:44 PM, David Menendez
wrote: On Sat, Dec 27, 2008 at 2:24 PM, Andrew Wagner to do something like this:
data Foo = Bar a => Foo a Bool ...
That is, I want to create a new type, Foo, whose constructor takes both a Boolean and a value of a type of class Bar.
Try this:
{-# LANGUAGE ExistentialQuantification #-}
data Foo = forall a. Bar a => Foo a Bool
Though for existentials, I find GADT more natural (actually I find GADT more natural in most cases):
data Foo where Foo :: Bar a => a -> Foo
Luke
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hmm, I actually simplified my problem too much. What I actually want is:
data Foo a = forall a. Bar a => Foo a Bool
...except I want the 'a' on the left to match the 'a' on the right, so
that you can only construct values out of values of the parameterized
type, which also must be of the Bar class.
On Dec 27, 2008, at 1:44 PM, "David Menendez"
On Sat, Dec 27, 2008 at 2:24 PM, Andrew Wagner
wrote: I'm sure there's a way to do this, but it's escaping me at present. I want to do something like this:
data Foo = Bar a => Foo a Bool ...
That is, I want to create a new type, Foo, whose constructor takes both a Boolean and a value of a type of class Bar.
Try this:
{-# LANGUAGE ExistentialQuantification #-}
data Foo = forall a. Bar a => Foo a Bool
-- Dave Menendez
http://www.eyrie.org/~zednenem/

Oh! That's much simplier: data Bar a => Foo a = Foo a Bool On 27 Dec 2008, at 23:09, Andrew Wagner wrote:
Hmm, I actually simplified my problem too much. What I actually want is: data Foo a = forall a. Bar a => Foo a Bool
...except I want the 'a' on the left to match the 'a' on the right, so that you can only construct values out of values of the parameterized type, which also must be of the Bar class.
On Dec 27, 2008, at 1:44 PM, "David Menendez"
wrote: On Sat, Dec 27, 2008 at 2:24 PM, Andrew Wagner
wrote: I'm sure there's a way to do this, but it's escaping me at present. I want to do something like this:
data Foo = Bar a => Foo a Bool ...
That is, I want to create a new type, Foo, whose constructor takes both a Boolean and a value of a type of class Bar.
Try this:
{-# LANGUAGE ExistentialQuantification #-}
data Foo = forall a. Bar a => Foo a Bool
-- Dave Menendez
http://www.eyrie.org/~zednenem/
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Andrew Wagner wrote:
Hmm, I actually simplified my problem too much. What I actually want is: data Foo a = forall a. Bar a => Foo a Bool
...except I want the 'a' on the left to match the 'a' on the right, so that you can only construct values out of values of the parameterized type, which also must be of the Bar class.
Well, you can ignore my previous contribution to this thread anyway. I failed to see the numerous other responses suggesting the same thing. I recommend against what you are wanting to do. It is probably nicer to have something like this: data Foo a = Foo a Bool -- don't export this foo :: Bar a => a -> Bool -> Foo a -- export this foo = Foo You can also use GHC's new ViewPatterns extension if you would still like to be able to pattern match on Foo values in other modules and don't mind being restricted to more recent versions of GHC. - Jake

On Sat, Dec 27, 2008 at 3:09 PM, Andrew Wagner
Hmm, I actually simplified my problem too much. What I actually want is: data Foo a = forall a. Bar a => Foo a Bool
...except I want the 'a' on the left to match the 'a' on the right, so that you can only construct values out of values of the parameterized type, which also must be of the Bar class.
Something like this?
{-# LANGUAGE ExistentialQuantification #-}
class Bar a where
bar :: a -> a
data Foo a = (Bar a) => Foo a Bool
baz :: Foo a -> a
baz (Foo a _) = bar a
This works fine for me with GHC 6.8, but I'd expect Hugs and earlier
versions of GHC to reject it.
See section 8.4.5 of the GHC manual.
http://www.haskell.org/ghc/docs/latest/html/users_guide/data-type-extensions...
--
Dave Menendez

Seems like you want an existential type: data Foo = forall a. Bar a => Foo a Bool On 27 Dec 2008, at 22:24, Andrew Wagner wrote:
I'm sure there's a way to do this, but it's escaping me at present. I want to do something like this:
data Foo = Bar a => Foo a Bool ...
That is, I want to create a new type, Foo, whose constructor takes both a Boolean and a value of a type of class Bar. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Andrew Wagner
I'm sure there's a way to do this, but it's escaping me at present. I want to do something like this:
data Foo = Bar a => Foo a Bool ...
That is, I want to create a new type, Foo, whose constructor takes both a Boolean and a value of a type of class Bar.
Sometimes it's enough to declare data Foo a = Foo a Bool and to put the 'Bar a =>' context onto the functions and instances that involve Foo. For example, in Chris Okasaki's book Purely Functional Data Structures, the h in data BootstrapHeap h a = ... is always meant to satisfy 'Heap h =>', but this is ensured by putting the context at all the points where a BootstrapHeap is created, and not exporting BootstrapHeap's data constructors. Regards, Tom

Tom Pledger wrote:
Andrew Wagner
writes: I'm sure there's a way to do this, but it's escaping me at present. I want to do something like this:
data Foo = Bar a => Foo a Bool ...
That is, I want to create a new type, Foo, whose constructor takes both a Boolean and a value of a type of class Bar.
Sometimes it's enough to declare
data Foo a = Foo a Bool
and to put the 'Bar a =>' context onto the functions and instances that involve Foo.
Although, if you really want to omit the `a` from the type, you can use the ExistentialQuantification extension or GADTs to do something like: -- with ExistentialQuantification data Foo = forall a . Bar a => Foo a Bool -- with GADTs data Foo where forall a . Bar a => Foo a Bool I haven't used either extension in a few months though, so I may have gotten the syntax wrong. You can look them up to be sure. - Jake
participants (6)
-
Andrew Wagner
-
David Menendez
-
Jake McArthur
-
Luke Palmer
-
Miguel Mitrofanov
-
Tom Pledger