Re: [Haskell-cafe] ambiguous constraint errors

2008-05-29 Thread Daniil Elovkov

Hello

Evan Laforge wrote:

I have two related questions:

#1

I'm getting some annoying type errors that I don't fully understand,
and wind up having to do a workaround that I don't totally like.
Here's a simplified version of my situation:

data Ambi m = Ambi {
ambi_monad :: m Int
, ambi_int :: Int
}

some_ambi :: Monad m = Ambi m
some_ambi = Ambi (return 5) 10

ambi_table :: Monad m = [(String, Ambi m)]
ambi_table = [(default, some_ambi)]
.
get_int :: String - Maybe Int
get_int sym = fmap ambi_int (lookup sym ambi_table)

---

get_int produces:
Ambiguous type variable `m' in the constraint:
  `Monad m' arising from a use of `ambi_table' at ambi.hs:13:40-49

So I guess this means I'm not telling it which 'm', so it doesn't know
how to resolve the 'return'... but the thing is, I'm not even using
that value, so it doesn't matter what it resolves to.  So it works if
I pick some random monad:

get_int sym = fmap ambi_int (lookup sym ambi_table :: Maybe (Ambi Maybe))


Of you and the type system you're the only one who knows that that value 
is not used. The type system doesn't use (all) the rules you have in 
your mind. It follows more simple ones.


You judge by values, not only types here. That is, you look at the value 
of ambi_int and see that it's just 10 in your (value again) some_ambi. 
You see that it's not


ambi_int = (some_return_from_monad ambi_monad) * 3

(If there were function returning from a monad)

In this case you wouldn't complain because the compiler definitely would 
have to know what monad it is.


Haskell type system doesn't look that far to distinguish those 2 cases. 
It doesn't deal with values (well, in a sense :).


Also compare with this

x :: Int
x = Five

main = putStrLn Hello

This program doesn't use x, so the type error would definitely not 
bother us at run-time. But it's nevertheless not ignored.






Note that I can't leave it as 'Monad m = Ambi m' because I still get
an ambiguous type variable complaint.

I'm a little disconcerted by having to pick some random dummy monad.
Even worse, everything this type touches starts requiring explicit
type declarations everywhere.  Is there some easier way to do this?


I tried to fiddle with forall, but it seems a lot more simple to say 
Identity. It will be entirely local to get_int function. Maybe it's not 
so bad...



#2

This is somewhat related to another issue I've been having, which is
that I have some kind of complicated type, e.g. '(SomeMonad some,
Monad m) = some (SomethingM m Status)' that I use in a lot of places.
 It would be a lot less typing and easier to modify later if I wrote a
type alias:

type Command = (Monad some, Monad m) = some (State.StateT () m Status)

but of course, this isn't allowed, since the type variables don't
appear on the lhs, and if I put a context there, it's a syntax error.
While I can write it with data:

data (Monad some, Monad m) = Command some m = Command (some
(State.StateT () m Status))

I've been told this doesn't mean what I expect it to, which is that
the context constraints propagate up to and unify with the containing
type (out of curiosity, since it's accepted, what *does* this do?  I
think I read it somewhere once, but now I forget and can't find it).
And sure enough, using this type doesn't make my type declarations
have the right contexts.



Well it means that you can't call any data constructor of this type with 
arguments not satisfying those constraints. Effectively it means that 
you won't ever have a value of type (Command some m) in your program 
where the pair (some,m) doesn't satisfy them.


However, the type system won't leverage that fact. And when you use a 
value of type Command some m somewhere you have to repeat the constraints.


afaik it is officially considered a Haskell mis-feature.

Am I wrong or it can be fixed by a compiler option (ghc)?

Operationally, if I get it right, it has to do with (not) attaching 
dictionaries to data constructors. If a dictionary was attached at the 
stage of constructing a Command, it could be easily re-used anywhere. If 
it's not attached you have to pass it later.




So the first problem means that I have to declare types in various
inconvenient places, and the second one means that I have to type out
all the various class constraints (I can still alias away the
non-polymorphic bits), and all my type declarations start looking much
more complicated than they are.

The solution I've been using for some of this is just to remove the
polymorphism, so I can write a simple alias like

type Command = SomethingM (State.StateT () Identity Status)

and now I can think of a command and have various functions that
take and return Commands, without caring that it's some kind of monad
with context constraints.  But of course, this isn't always possible
since sometimes I need the type to remain polymorphic (i.e. while most
of these I don't *think* will run in some other monad, some of them
definitely get 

Re: [Haskell-cafe] ambiguous constraint errors

2008-05-29 Thread Isaac Dupree

Evan Laforge wrote:

I have two related questions:

#1

I'm getting some annoying type errors that I don't fully understand,
and wind up having to do a workaround that I don't totally like.
Here's a simplified version of my situation:

data Ambi m = Ambi {
ambi_monad :: m Int
, ambi_int :: Int
}

some_ambi :: Monad m = Ambi m
some_ambi = Ambi (return 5) 10

ambi_table :: Monad m = [(String, Ambi m)]
ambi_table = [(default, some_ambi)]

get_int :: String - Maybe Int
get_int sym = fmap ambi_int (lookup sym ambi_table)

---

get_int produces:
Ambiguous type variable `m' in the constraint:
  `Monad m' arising from a use of `ambi_table' at ambi.hs:13:40-49

So I guess this means I'm not telling it which 'm', so it doesn't know
how to resolve the 'return'... but the thing is, I'm not even using
that value, so it doesn't matter what it resolves to.  So it works if
I pick some random monad:

get_int sym = fmap ambi_int (lookup sym ambi_table :: Maybe (Ambi Maybe))

Note that I can't leave it as 'Monad m = Ambi m' because I still get
an ambiguous type variable complaint.

I'm a little disconcerted by having to pick some random dummy monad.
Even worse, everything this type touches starts requiring explicit
type declarations everywhere.  Is there some easier way to do this?

#2

This is somewhat related to another issue I've been having, which is
that I have some kind of complicated type, e.g. '(SomeMonad some,
Monad m) = some (SomethingM m Status)' that I use in a lot of places.
 It would be a lot less typing and easier to modify later if I wrote a
type alias:

type Command = (Monad some, Monad m) = some (State.StateT () m Status)

but of course, this isn't allowed, since the type variables don't
appear on the lhs, and if I put a context there, it's a syntax error.


-fglasgow-exts (not sure which extension) allows the above, though I'm 
not quite sure what it *means*.  It also allows
type Command some m = (Monad some, Monad m) = some (State.StateT () m 
Status)
which allows the polymorphism in the types to be shared across more of 
the function that's defined using Command: more opportunity for 
explicitness.



While I can write it with data:

data (Monad some, Monad m) = Command some m = Command (some
(State.StateT () m Status))

I've been told this doesn't mean what I expect it to, which is that
the context constraints propagate up to and unify with the containing
type (out of curiosity, since it's accepted, what *does* this do?  I
think I read it somewhere once, but now I forget and can't find it).
And sure enough, using this type doesn't make my type declarations
have the right contexts.
That Haskell-98 syntax only tells the compiler to break some times when 
the context isn't met.  But you want the compiler to not-break at other 
times by supplying the information about the context being available 
when something else requires it.


with {-# LANGUAGE GADTs #-} you should be able to use a different syntax 
for the same sort of thing but with the meaning you wanted:  (beware of 
layout messed up by e-mail line wrapping) :

data Command some m where
  Command :: (Monad some, Monad m) = some (State.StateT () m Status) 
- Command some m


This might be a better choice than the type synonym actually, since it's 
in some ways less unpredictable in meaning to the type system (well, 
again assuming that GHC is the only Haskell implementation that matters 
to you).



So the first problem means that I have to declare types in various
inconvenient places, and the second one means that I have to type out
all the various class constraints (I can still alias away the
non-polymorphic bits), and all my type declarations start looking much
more complicated than they are.


It's a really annoying problem!  The multi-param-type-class hack Daniil 
Elovkov mentioned is another way it's done sometimes, that also uses a 
few compiler extensions.  CPP macros are even uglier but they can work 
too.  Choose whatever suits you best.  None of the solutions that make 
polymorphism more syntactically convenient will get rid of your 
ambiguity annoyances, and I'm not sure if the Haskell98 default()ing 
system is willing to default Monads.


-Isaac
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ambiguous constraint errors

2008-05-29 Thread Evan Laforge
 get_int sym = fmap ambi_int (lookup sym ambi_table :: Maybe (Ambi Maybe))

 Of you and the type system you're the only one who knows that that value is
 not used. The type system doesn't use (all) the rules you have in your mind.
 It follows more simple ones.

 You judge by values, not only types here. That is, you look at the value of
 ambi_int and see that it's just 10 in your (value again) some_ambi. You see
 that it's not

 ambi_int = (some_return_from_monad ambi_monad) * 3

I'm not totally understanding, but I think you're saying that I could
write ambi_int in a way that it still had type Ambi m - Int but
depended on the type of 'm'.  I guess that makes sense, because it
could run m internally and return an Int based on the result, which
therefore depends on the type of 'm'.

 Also compare with this

 x :: Int
 x = Five

 main = putStrLn Hello

 This program doesn't use x, so the type error would definitely not bother us
 at run-time. But it's nevertheless not ignored.

Sure, my intuition has much less trouble with that one.  It's off
topic, but I wonder if there's lazy equivalent for type checkers.
I.e. at the value level I could call it 'undefined' which works with
any type (since all types include _|_ I guess), and as long as it's
not evaluated, there's no problem at runtime.  A type level equivalent
could have a type bottom which represents a type checking failure,
but it only affects the results of type functions if they demand it.

I guess a more appealing direction is to try to make the value system
total, not make the type system partial :)
And it might destroy separate compilation.

 I've been told this doesn't mean what I expect it to, which is that
 the context constraints propagate up to and unify with the containing
 type (out of curiosity, since it's accepted, what *does* this do?  I
 think I read it somewhere once, but now I forget and can't find it).
 And sure enough, using this type doesn't make my type declarations
 have the right contexts.

 Well it means that you can't call any data constructor of this type with
 arguments not satisfying those constraints. Effectively it means that you
 won't ever have a value of type (Command some m) in your program where the
 pair (some,m) doesn't satisfy them.

 However, the type system won't leverage that fact. And when you use a value
 of type Command some m somewhere you have to repeat the constraints.

 afaik it is officially considered a Haskell mis-feature.

Interesting.  Are there any valid uses for data context?  If not, is
it slated for removal?

 Maybe something like

 class MyAlias t1 t2 ...

 instance (Monad some, Monad m, ...) = MyAlias some m ...

I see, so sort of like using classes as class aliases which can
reduce the amount of junk in the context.  I think I've seen that
convention in use before.


[ isaac dupree ]

 with {-# LANGUAGE GADTs #-} you should be able to use a different syntax for
 the same sort of thing but with the meaning you wanted:  (beware of layout
 messed up by e-mail line wrapping) :
 data Command some m where
  Command :: (Monad some, Monad m) = some (State.StateT () m Status) -
 Command some m

Interesting, I'll have to try that out.

 It's a really annoying problem!  The multi-param-type-class hack Daniil
 Elovkov mentioned is another way it's done sometimes, that also uses a few
 compiler extensions.  CPP macros are even uglier but they can work too.

I guess I'll just type them out explicitly, and add automatic context
propagation to my ghc wishlist, along with records and
srcloc_annotate, and other random stuff.

I'm not even sure what such a feature would look like, or if it would
be feasible though...


Thanks for the pointers!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ambiguous constraint errors

2008-05-29 Thread Isaac Dupree

Evan Laforge wrote:

get_int sym = fmap ambi_int (lookup sym ambi_table :: Maybe (Ambi Maybe))

Of you and the type system you're the only one who knows that that value is
not used. The type system doesn't use (all) the rules you have in your mind.
It follows more simple ones.

You judge by values, not only types here. That is, you look at the value of
ambi_int and see that it's just 10 in your (value again) some_ambi. You see
that it's not

ambi_int = (some_return_from_monad ambi_monad) * 3


I'm not totally understanding, but I think you're saying that I could
write ambi_int in a way that it still had type Ambi m - Int but
depended on the type of 'm'.  I guess that makes sense, because it
could run m internally and return an Int based on the result, which
therefore depends on the type of 'm'.


It's more obvious with other type classes.

e.g. the snd of a value of type
(Num a) = (a, Bool)

Because what if the record/tuple was:
canOverflow = (ridiculous, ridiculous = 40)
  ridiculous = 40 ^ 5

Then it depends on whether you pick Int or Integer (or something else) 
for a, even if you only look at the Bool.



-Isaac
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ambiguous constraint errors

2008-05-29 Thread Ryan Ingram
On 5/28/08, Evan Laforge [EMAIL PROTECTED] wrote:
 I have two related questions:

 #1

 I'm getting some annoying type errors that I don't fully understand,
 and wind up having to do a workaround that I don't totally like.
 Here's a simplified version of my situation:

 data Ambi m = Ambi {
ambi_monad :: m Int
, ambi_int :: Int
}

 some_ambi :: Monad m = Ambi m
 some_ambi = Ambi (return 5) 10

 ambi_table :: Monad m = [(String, Ambi m)]
 ambi_table = [(default, some_ambi)]

 get_int :: String - Maybe Int
 get_int sym = fmap ambi_int (lookup sym ambi_table)

 ---

 get_int produces:
Ambiguous type variable `m' in the constraint:
  `Monad m' arising from a use of `ambi_table' at ambi.hs:13:40-49

You can let the caller choose m:

get_int :: Monad m = m () - String - Maybe Int
get_int _ sym = fmap ambi_int (lookup sym ambi_table)

which can be called like so:

get_int (error shouldn't evaluate :: IO ()) test
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ambiguous constraint errors

2008-05-28 Thread Evan Laforge
I have two related questions:

#1

I'm getting some annoying type errors that I don't fully understand,
and wind up having to do a workaround that I don't totally like.
Here's a simplified version of my situation:

data Ambi m = Ambi {
ambi_monad :: m Int
, ambi_int :: Int
}

some_ambi :: Monad m = Ambi m
some_ambi = Ambi (return 5) 10

ambi_table :: Monad m = [(String, Ambi m)]
ambi_table = [(default, some_ambi)]

get_int :: String - Maybe Int
get_int sym = fmap ambi_int (lookup sym ambi_table)

---

get_int produces:
Ambiguous type variable `m' in the constraint:
  `Monad m' arising from a use of `ambi_table' at ambi.hs:13:40-49

So I guess this means I'm not telling it which 'm', so it doesn't know
how to resolve the 'return'... but the thing is, I'm not even using
that value, so it doesn't matter what it resolves to.  So it works if
I pick some random monad:

get_int sym = fmap ambi_int (lookup sym ambi_table :: Maybe (Ambi Maybe))

Note that I can't leave it as 'Monad m = Ambi m' because I still get
an ambiguous type variable complaint.

I'm a little disconcerted by having to pick some random dummy monad.
Even worse, everything this type touches starts requiring explicit
type declarations everywhere.  Is there some easier way to do this?

#2

This is somewhat related to another issue I've been having, which is
that I have some kind of complicated type, e.g. '(SomeMonad some,
Monad m) = some (SomethingM m Status)' that I use in a lot of places.
 It would be a lot less typing and easier to modify later if I wrote a
type alias:

type Command = (Monad some, Monad m) = some (State.StateT () m Status)

but of course, this isn't allowed, since the type variables don't
appear on the lhs, and if I put a context there, it's a syntax error.
While I can write it with data:

data (Monad some, Monad m) = Command some m = Command (some
(State.StateT () m Status))

I've been told this doesn't mean what I expect it to, which is that
the context constraints propagate up to and unify with the containing
type (out of curiosity, since it's accepted, what *does* this do?  I
think I read it somewhere once, but now I forget and can't find it).
And sure enough, using this type doesn't make my type declarations
have the right contexts.


So the first problem means that I have to declare types in various
inconvenient places, and the second one means that I have to type out
all the various class constraints (I can still alias away the
non-polymorphic bits), and all my type declarations start looking much
more complicated than they are.

The solution I've been using for some of this is just to remove the
polymorphism, so I can write a simple alias like

type Command = SomethingM (State.StateT () Identity Status)

and now I can think of a command and have various functions that
take and return Commands, without caring that it's some kind of monad
with context constraints.  But of course, this isn't always possible
since sometimes I need the type to remain polymorphic (i.e. while most
of these I don't *think* will run in some other monad, some of them
definitely get called in multiple contexts).

Is there any nicer way around this?  And what's the underlying issue
that makes this necessary?  I can live with all the context hair
everywhere, but it sure would be nicer to be able to define it once
and for all in one place.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe