Re: In search of: [a->b] -> a -> [b]

2003-06-20 Thread Christian Sievers
Derek Elkins wrote:

> >  flist :: [a->b] -> a -> [b]
> >  flist fs a = map (flip ($) a) fs
> or much nicer (IMO) 
>   flist fs a = map ($ a) fs 

This is a case where I'd prefer a list comprehension:

flist fs a = [ f a | f <- fs ]

(and this could be a monad comprehension, if Haskell still had them...)

> the generalized solution being simply,
> f mf x = do
> f <- mf
> return (f x)

Or just replace map by fmap in your flist from above.


All the best
Christian Sievers
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Overlapping instances in existentials

2003-06-20 Thread Ed Komp
Simon,

Thanks for the extended response to my question about
overlapping instances.
Before my original posting, I had read a posting that included
the example with Show that you included in your response.
I believed (and still do) that my specific case is a bit different.

| To determine (SubType y Value) which is just:
|   (SubType y (Either Double BaseType))
| 
| it seems to me that GHC should (has to?) use
|instance (SubType a b) => SubType a (Either x b)
| 
| I do not see how the other alternative is applicable:
|   instance SubType a (Either a x)

Well, the "target" (Subtype y (Either Double BaseType))
can match against *both* of these instances.
It can match
instance (SubType a b) => SubType a (Either x b)
by taking a=y, x=Double, b=BaseType

*If y were instantiated to Double* it could match the second instance
declaration too.  Now, you say, y is an existential type variable, so it
can't be instantiated to Double --- but that's tricky to pin down.
Within the GHC compiler
> can't be instantiated to Double --- but that's tricky to pin down.
this may be tricky to pin down.
But, there is specific information in my example to exclude Double:
I had carefully constructed the type definitions to avoid
ambiguity.
 > | type BaseType = Either Integer ( Either Bool () )
 > |
 > | type Value = (Either Double BaseType)
 > |
 > | data Foo =  forall x. (SubType x BaseType)  => MkFoo x
 > |
 > | test :: Foo -> Value
 > | test (MkFoo x) = inj x
'x' is the variable I am concerned about.
Since it is an argument to MkFoo,
we know that (SubType x BaseType)
and we also know that:
NOT  (SubType Double BaseType), so 'x' cannot be instantiated as Double.

Am I correct when I say that:
this specific case is not ambiguous,
but the compiler does not recognize the constraint on 'x'
which dis-ambiguates this case.
OR
is this _really_ ambiguous.
I am not suggesting a change in the compiler to recognize
such specific cases (though I would not object :-);
but I want to be sure I understand what I have written.
thanks
Ed Komp
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: In search of: [a->b] -> a -> [b]

2003-06-20 Thread Derek Elkins
On Thu, 19 Jun 2003 18:05:11 +0200
Christian Sievers <[EMAIL PROTECTED]> wrote:

> Derek Elkins wrote:
> 
> > >  flist :: [a->b] -> a -> [b]
> > >  flist fs a = map (flip ($) a) fs
> > or much nicer (IMO) 
> >   flist fs a = map ($ a) fs 
> 
> This is a case where I'd prefer a list comprehension:
> 
> flist fs a = [ f a | f <- fs ]
> 
> (and this could be a monad comprehension, if Haskell still had
> them...)

I don't think Haskell ever had them (I'd have to check).
Gofer did. Anyways, do-notation is about as expressive as monad
comprehensions. With do-notation you have to add guards explicitly, but
you don't have to end with a return and you don't need to bind
variables, e.g. I believe [() | _ <- putStrLn "foo"] would be necessary
(well, not in this case, but the general one).

> > the generalized solution being simply,
> > f mf x = do
> > f <- mf
> > return (f x)
> 
> Or just replace map by fmap in your flist from above.

That generalizes it, but in a different way since (in Haskell) Monad
isn't a subclass of Functor...

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: In search of: [a->b] -> a -> [b]

2003-06-20 Thread Keith Wansbrough
Derek Elkins wrote:

> Christian Sievers <[EMAIL PROTECTED]> wrote:
>
> > (and this could be a monad comprehension, if Haskell still had
> > them...)
> 
> I don't think Haskell ever had them (I'd have to check).
> Gofer did.

They were put in for Haskell 1.4, and removed again for Haskell 98
because of the horrendously confusing error messages they caused.

http://www.haskell.org/definition/

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Overlapping instances in existentials

2003-06-20 Thread Dylan Thurston
On Thu, Jun 19, 2003 at 11:08:35AM -0500, Ed Komp wrote:
>  > | type BaseType = Either Integer ( Either Bool () )
>  > |
>  > | type Value = (Either Double BaseType)
>  > |
>  > | data Foo =  forall x. (SubType x BaseType)  => MkFoo x
>  > |
>  > | test :: Foo -> Value
>  > | test (MkFoo x) = inj x
> 
> 
> 'x' is the variable I am concerned about.
> Since it is an argument to MkFoo,
> we know that (SubType x BaseType)
> and we also know that:
> 
> NOT  (SubType Double BaseType), so 'x' cannot be instantiated as Double.

I'm missing something.  Why do we know NOT (SubType Double BaseType)?
Nothing in the code above prevents you from having such an instance,
does it?

Peace,
Dylan


pgp0.pgp
Description: PGP signature


Re: In search of: [a->b] -> a -> [b]

2003-06-20 Thread Wolfgang Lux
Christian Sievers wrote:

This is a case where I'd prefer a list comprehension:

flist fs a = [ f a | f <- fs ]

(and this could be a monad comprehension, if Haskell still had them...)
And it still has them, you just have to get accustomed to the slightly
different syntax :-)
  flist fs a = do f <- fs; return (f a)

Wolfgang

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


stack space overflow

2003-06-20 Thread Ketil Z. Malde

Hi,

I have a small function to find all indices in an array where a given
subword can be found, looking like this:

> ind i ws ar 
>   | i+length ws-1 > len e   = []
>   | and [ar!(i+j) == ws!!j | j<-[0..length ws-1]] = i : ind (i+1) ws ar
>   | otherwise   = ind (i+1) ws ar

(i::Int is the position, ws::[a] is the word to look for, while
ar::Array Int a is the array wherein to look)

This occasionally blows up with a stack overflow, perhaps I'm being
dense, but I'm not sure why.  Any suggestions?

BTW, is there a general way to track down stack overflows?  I use the
-xc option, are there any other tricks I should know about?  And does
heap profiling (GHC) imply more stack usage -- I seem to get overflows
much more easily when profiling.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: stack space overflow

2003-06-20 Thread Hal Daume
Seems to work for me.  I changed it a bit (I believe you meant 'len ar'
on the first line, with the following defintion of 'len':
  len = (1+) . uncurry (flip (-)) . bounds
, but other than that, I left your code as it is).

Can you provide input on which it fails?  It works for me on large input
like:

*Main>  ind 1 "foo" $ listArray (1,1) (concat $ repeat
"abcfoodefgfooa")

even in ghci.

--
 Hal Daume III   | [EMAIL PROTECTED]
 "Arrest this man, he talks in maths."   | www.isi.edu/~hdaume


> -Original Message-
> From: [EMAIL PROTECTED] 
> [mailto:[EMAIL PROTECTED] On Behalf Of Ketil Z. Malde
> Sent: Friday, June 20, 2003 7:05 AM
> To: [EMAIL PROTECTED]
> Subject: stack space overflow
> 
> 
> 
> Hi,
> 
> I have a small function to find all indices in an array where a given
> subword can be found, looking like this:
> 
> > ind i ws ar 
> >   | i+length ws-1 > len e   = []
> >   | and [ar!(i+j) == ws!!j | j<-[0..length ws-1]] = i : ind 
> (i+1) ws ar
> >   | otherwise   = ind (i+1) ws ar
> 
> (i::Int is the position, ws::[a] is the word to look for, while
> ar::Array Int a is the array wherein to look)
> 
> This occasionally blows up with a stack overflow, perhaps I'm being
> dense, but I'm not sure why.  Any suggestions?
> 
> BTW, is there a general way to track down stack overflows?  I use the
> -xc option, are there any other tricks I should know about?  And does
> heap profiling (GHC) imply more stack usage -- I seem to get overflows
> much more easily when profiling.
> 
> -kzm
> -- 
> If I haven't seen further, it is by standing in the 
> footprints of giants
> ___
> Haskell mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell
> 
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Overlapping instances in existentials

2003-06-20 Thread Dean Herington
Dylan Thurston wrote:

> On Thu, Jun 19, 2003 at 11:08:35AM -0500, Ed Komp wrote:
> >  > | type BaseType = Either Integer ( Either Bool () )
> >  > |
> >  > | type Value = (Either Double BaseType)
> >  > |
> >  > | data Foo =  forall x. (SubType x BaseType)  => MkFoo x
> >  > |
> >  > | test :: Foo -> Value
> >  > | test (MkFoo x) = inj x
> >
> >
> > 'x' is the variable I am concerned about.
> > Since it is an argument to MkFoo,
> > we know that (SubType x BaseType)
> > and we also know that:
> >
> > NOT  (SubType Double BaseType), so 'x' cannot be instantiated as Double.
>
> I'm missing something.  Why do we know NOT (SubType Double BaseType)?
> Nothing in the code above prevents you from having such an instance,
> does it?

Put another way, only with a "closed world" assumption could the compiler
"know" that NOT  (SubType Double BaseType).  GHC deliberately eschews such an
assumption, so that adding new instances doesn't change the semantics of a
program.

Dean

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Overlapping instances in existentials

2003-06-20 Thread oleg

Ed Komp replied to Simon Peyton-Jones:
> Within the GHC compiler
>  > can't be instantiated to Double --- but that's tricky to pin down.
> this may be tricky to pin down.
> But, there is specific information in my example to exclude Double:
> I had carefully constructed the type definitions to avoid
> ambiguity.

Indeed, the open world assumption makes it rather difficult to define
a constraint that two type variables must denote different types. I
wish it were possible to easily write
forall a b. (NotEq a b) => ...

Functional dependencies can be used to achieve a similar effect -- but
sometimes that are not applicable. I wish there were a way to assert
to the compiler that there will be no more instances of a specific
class. The compiler can record this assumption in the object
file. When the compiler builds the final executable and finds an
unexpected instance, the compiler can tell the user that he lied.

 > | class SubType a b where
 > |   inj :: a -> b
 > |   prj :: b -> Maybe a
 > |
 > | instance SubType a (Either a x) where
 > |   inj   =3D Left
 > |   prj   =3D either Just (const Nothing)
 > |
 > | instance (SubType a b) =3D> SubType a (Either x b) where
 > | inj   =3D Right . inj
 > | prj   =3D either (const Nothing) prj
 > |
 > | type BaseType = Either Integer ( Either Bool () )
 > |
 > | type Value = (Either Double BaseType)
 > |
 > | data Foo =  forall x. (SubType x BaseType)  => MkFoo x
 > |
 > | test :: Foo -> Value
 > | test (MkFoo x) = inj x


I'm quite dubious that test can be typed at all (see below). Even if
the problem with overlapping instances could be solved. I seem to
remember being on this road before. I'd be great to get GHC to run the
typechecker at run time, to choose the right instance. Alas.

In the example above, the constraint on Foo only guarantees (SubType x
BaseType). When we create MkFoo True, for example, the compiler knows
the type the value being encapsulated, chooses the right instance
(that is, the dictionary), and places the dictionary and the value
into the MkFoo envelope. The function test executes "inj x" whose
return type is different from the BaseType. that is, 'inj' implicitly
has the constraint (SubType x Value). However, MkFoo x only guarantees
(SubType x BaseType). This is not a technicality. Let us disambiguate
the instances and remove all overlapping:

> class SubType a b where
>inj :: a -> b
>prj :: b -> Maybe a

> instance SubType Bool (Either Bool x) where
>inj   = Left
>prj   = either Just (const Nothing)

> instance SubType Integer (Either Integer x) where
>inj   = Left
>prj   = either Just (const Nothing)

> instance (SubType Bool b) => SubType Bool (Either Integer b) where
>  inj   = Right . inj
>  prj   = either (const Nothing) prj

> instance (SubType Bool b) => SubType Bool (Either Double b) where
>  inj   = Right . inj
>  prj   = either (const Nothing) prj

> instance (SubType Integer b) => SubType Integer (Either Double b) where
>  inj   = Right . inj
>  prj   = either (const Nothing) prj

> type BaseType = Either Integer ( Either Bool () )

> type Value = (Either Double BaseType)

> data Foo =  forall x. (SubType x BaseType)  => MkFoo x

> -- test :: Foo -> Value
> -- test (MkFoo x) = inj x

> test1 :: Foo -> BaseType
> test1 (MkFoo x) = inj x

This code types and even runs:

*> test1 $ MkFoo True
*> Right (Left True)

Indeed, when the compiler sees MkFoo True, it chooses the right instance
of the class (SubType x BaseType), and packs the corresponding
dictionary into MkFoo. When we run test1 $ MkFoo True, the compiler
extracts the dictionary from MkFoo, extracts the field inj from that
dictionary, and runs the corresponding procedure. At this time (at run
time), the compiler does not and cannot choose instances.

If we uncomment the procedure test above, we predictably get the
error:

/tmp/k2.hs:32:
Could not deduce (SubType x Value)
from the context (SubType x BaseType)
Probable fix:
Add (SubType x Value)
to the existential context of a data constructor
Or add an instance declaration for (SubType x Value)
arising from use of `inj' at /tmp/k2.hs:32
In the definition of `test': inj x

As we saw above, we cannot widen the constraint at the run time. The
function test wants to use a different function inj -- not the one
associated with (SubType Bool BaseType) -- the chosen instance -- but
a different one, associated with an instance (SubType Bool
Value). However, we cannot chose the instance at that time because the
compiler does not know the exact type of the value in the existential
envelope. To do as you wish, the compiler would have had to compile the
typechhecer into the target executable code. Not that it would be a bad
idea.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell