On Mon, 13 Oct 2003 23:41:17 -0700 (PDT)
[EMAIL PROTECTED] wrote:
> Derek Elkins wrote:
>
> > Anyways, if another challenge is desired, I would be interested in
> > seeing how one would go about converting the implementation of
> > Dynamics in "A Lightweight Implementation of Generics and Dynamic
Derek Elkins wrote:
> Anyways, if another challenge is desired, I would be interested in
> seeing how one would go about converting the implementation of
> Dynamics in "A Lightweight Implementation of Generics and Dynamics"
> into a form that doesn't use existentials* but still provides the same
On Mon, 13 Oct 2003 11:37:43 -0400
Jan-Willem Maessen <[EMAIL PROTECTED]> wrote:
> > So, the existential quantification permits more nuanced
> > transformations -- and yet the nuances aren't observable. So, they
> > don't matter?
>
> Whether they matter or not depends upon our aims. I'm curious
Oleg replies to my message on eliminating existentials:
> Jan-Willem Maessen wrote:
>
> > > data Expr a = Val a | forall b . Apply (Expr (b -> a)) (Expr b)
>
> > I've been trying to convince myself that we really need the
> > existential types here.
> > ...
> > Now (Expr a) is really two things:
At 11:25 10/10/03 +0200, [EMAIL PROTECTED] wrote:
Hi Graham,
> Instead, I replace the class instances by a single algebraic
> data type,
> whose members are functions corresponding to OO-style class methods.
could you give an example?
The code in a previous message of mine [1] was an example of so
oleg wrote:
> Sorry I didn't know of that requirement. The desired sharing
> can easily be introduced:
That's always a risk with posting a toy example - which bits
are important can be hard to tell. You are right of course
about being able to introduce the sharing.
FWIW, after the suggestions t
Jan-Willem Maessen wrote:
> > data Expr a = Val a | forall b . Apply (Expr (b -> a)) (Expr b)
> I've been trying to convince myself that we really need the
> existential types here.
> ...
> Now (Expr a) is really two things:
> * A structural representation of a term
> * A fancy representation of
Derek Elkins <[EMAIL PROTECTED]> writes:
> On Thu, 9 Oct 2003 19:13:48 -0700 (PDT)
> [EMAIL PROTECTED] wrote:
> > ...
> > It seems that
> > (g.f) :: i -> o
> > is equivalent to stating
> > exists c. f:: (i->c) ^ g::(c->o)
> > or, in the Haskell type language
> > data P i o = forall c.
Tim Docker wrote:
> > data ColDesc rowv = forall a.
> > ColDesc (rowv -> a) ([a] -> a) (a -> String)
> >
> > calculate :: [rowv] -> ColDesc rowv -> ([String],String)
> > calculate rs (ColDesc valf sumf fmtf) =
> > let vals = map valf rs in
> > (map fmtf vals, (fmtf.sumf
Hi Graham,
> Instead, I replace the class instances by a single algebraic
> data type,
> whose members are functions corresponding to OO-style class methods.
could you give an example?
Thanks,
Markus
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
ht
types (like a sphere and a polygon and a mesh etc. etc.) but
lists need to have elements of the same type.
]]
I was reminded of very similar issues I encountered in my own development,
which for the most part I resolved without using existential types.
Originally, I had contemplated using type cl
Thanks for the comments. I think your solution misses one
point in my original example...
I wrote:
> data ColDesc rowv = forall a.
> ColDesc (rowv -> a) ([a] -> a) (a -> String)
>
> calculate :: [rowv] -> ColDesc rowv -> ([String],String)
> calculate rs (ColDesc valf sumf fmtf) =
>
On Thu, 9 Oct 2003 19:13:48 -0700 (PDT)
[EMAIL PROTECTED] wrote:
> It was derived with a simple transformation: composing (rowv -> a)
> with (a->String) to eliminate the existential type a.
>
> It seems there is a pattern here. When we write
> data Foo a b = forall ex. Foo
>
> with ex uncons
Tim Docker wrote:
> I wish to define a flexible report, consisting of a set of columns.
> The contents of each column can be defined by mapping a function to a
> row descriptor, generating a value, and then converting each value
> to a string. I also wish to present an aggregate value at the bott
Whilst on existential types, perhaps someone can tell me
if this is a valid use:
I wish to define a flexible report, consisting of a set of columns.
The contents of each column can be defined by mapping a function to a
row descriptor, generating a value, and then converting each value
to a string.
On Wed, Oct 08, 2003 at 09:40:35AM -0700, Mike Gunter wrote:
>
> Jan-Willem Maessen <[EMAIL PROTECTED]> writes:
>
> > Tomasz Zielonka <[EMAIL PROTECTED]> wrote:
> > [...]
> > > data Stat i o = -- aggregate function taking i's on input and producing o
> > > forall s. Stat
> > > s
Jan-Willem Maessen <[EMAIL PROTECTED]> writes:
> Tomasz Zielonka <[EMAIL PROTECTED]> wrote:
> [...]
> > data Stat i o = -- aggregate function taking i's on input and producing o
> > forall s. Stat
> > s -- init
> > (s -> i -> s) -- update
> > (s -> o)-- res
At 16:12 03/10/03 -0700, [EMAIL PROTECTED] wrote:
>data InjProjMap ex = InjProjMap
> { mapL2V:: String -> Maybe Univ
> , mapV2L:: Univ -> Maybe String
> }
>
>
>data Univ = UInt Integer | UBool Bool
> I have a couple of questions:
> (1) is there any purpose served b
Tomasz Zielonka <[EMAIL PROTECTED]> wrote:
> I think I have used unconstrained existentially quantified types in a
> useful way. Below is a combinator library for calculating statistics
> with aggregate functions (type Stat).
>
> [BIG SNIP]
>
> data Stat i o = -- aggregate function taking i's on
>data InjProjMap ex = InjProjMap
> { mapL2V:: String -> Maybe Univ
> , mapV2L:: Univ -> Maybe String
> }
>
>
>data Univ = UInt Integer | UBool Bool
> I have a couple of questions:
> (1) is there any purpose served by having InjProjMap parameterized with
> ex? I
At 18:42 02/10/03 -0700, [EMAIL PROTECTED] wrote:
Therefore, when you
quantify a value, you typically want to impose a constraint
forall vt. (C vt) => Datatype (DatatypeVal ex vt)
That's a useful observation, thanks.
I've had a enough cases recently where I found that a class doesn't
actu
On Fri, Oct 03, 2003 at 09:42:48AM +0200, Tomasz Zielonka wrote:
> However this approach has caveats. For example you can't store the state
> of Stat and restart it later. All steps are done within one call to
> runStat.
I was wrong. I can write:
updateStat :: Stat i o -> i -> Stat i o
updateStat
On Thu, Oct 02, 2003 at 06:42:59PM -0700, [EMAIL PROTECTED] wrote:
>
> > data Datatype ex = forall vt . Datatype (DatatypeVal ex vt)
>
> In practice one rarely would write
> forall vt. Datatype (DatatypeVal ex vt)
> unless he is writing something like the ST monad.
> You can only pass vt
> data Datatype ex = forall vt . Datatype (DatatypeVal ex vt)
In practice one rarely would write
forall vt. Datatype (DatatypeVal ex vt)
unless he is writing something like the ST monad.
You can only pass vt to functions with the signature
forall vt. vt -> C1 vt C2 C3 ...
where
I've been trying to use existential types [*] in my code.
[*] cf. Glasgow Haskell Compiler (GHC) user guide, section 7.3.12
My experiments have thrown up a couple of questions:
1. forall x introduces x as existential when it appears immediately
preceding a datatype constructor declaration, e.
25 matches
Mail list logo