Re: [Haskell-cafe] Type-class conditional behavior

2011-05-09 Thread Andrew Coppin

On 08/05/2011 06:14 AM, Nicholas Tung wrote:

Dear all,

 I'd like to write a function maybeShow :: a - Maybe String,
which runs show if its argument is of class Show.


This is surely an FAQ. Is the answer listed somewhere?

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


Re: [Haskell-cafe] Type-class conditional behavior

2011-05-09 Thread Nicholas Tung
Hi Ryan,

On Sun, May 8, 2011 at 12:06 AM, Ryan Ingram ryani.s...@gmail.com wrote:

 However we know the behavior of these functions, and you can hack around it
 with a manual show instance that takes advantage of that knowledge:

 instance Show t = Show (AV t) where
 show (AVLeft a) = drop 5 $ show (Left a)


That's a creative way to think about it, but unfortunately, the types don't
quite work out:
(AVLeft a) :: AV (Either ta tb)
a :: AV ta
Left a :: Either (AV ta) tc

Since the argument of AVLeft is another AV.

All this said, I agree that the presence of 'arr' in Arrow is a problem for
 many types of generalized computing.  It overly constrains what can be an
 arrow, in my opinion.  I think a better analysis of the primitives required
 for arrow notation to work would solve a lot of problems of this type.


Yes, a graduate student here at UC Berkeley (Adam Megacz) is working on a
project (Generalized Arrows) to alleviate this difficulty. I think the arrow
notation not only unnecessarily prevents adding things like Show as
typeclass constraints, but also makes it difficult to use an alternate
Either / tuple type, like the AVLeft above, since you can't look inside the
little functions it creates, like \x - (x, x), which is ga_copy in Adam's
work.

http://www.cs.berkeley.edu/~megacz/garrows/

cheers,
Nicholas — https://ntung.com — CS and Mathematics major @ UC Berkeley
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type-class conditional behavior

2011-05-08 Thread Stephen Tetley
On 8 May 2011 06:14, Nicholas Tung nt...@ntung.com wrote:
 Dear all,
     I'd like to write a function maybeShow :: a - Maybe String, which
 runs show if its argument is of class Show.

I'm pretty sure this is not readily possible - there might be some
hack through Typeable but that would oblige but Show and Typeable
constraints on the type of a.



     The context and motivation for this are as follows. I have a GADT type
 which encapsulates abstract-value computation (or constants or error codes),
 a snippet of which is below.
 data AV t where
     AVLeft :: AV a - AV (Either a b)
     This is used to implement an arrow transformer, and due to Arrows
 mapping all Haskell functions, I cannot put some kind of qualification on
 the constructor, like AVLeft :: Show a = 

Yes you can, from the GHC docs:

http://haskell.org/ghc/docs/7.0-latest/html/users_guide/data-type-extensions.html#gadt

  data Showable where
MkShowable :: Show a = a - Showable

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


Re: [Haskell-cafe] Type-class conditional behavior

2011-05-08 Thread Ryan Ingram
The behavior you are asking for maybeShow violates parametricity, so it
can't exist without some sort of typeclass constraint.

That said, in your particular situation, it's an interesting question.

The Show instance for Either is

instance (Show a, Show b) = Show (Either a b) where ...

so we as programmers know that, given some instance Show (Either a b) that
there must be an instance for a.  But we can't get at it!

Inside the compiler, this instance looks something like this:

data ShowDict a = ShowDict {
 showsPrec :: Int - a - String - String,
 show :: a - String,
 shows :: a - String - String,
 showsList :: [a] - String - String
   }

showEither :: (ShowDict a, ShowDict b) - ShowDict (Either a b)
showEither (sda, sdb) = ShowDict ...

Note that inside the functions returned by showEither we've lost the
parent dictionaries sda/sdb.

However we know the behavior of these functions, and you can hack around it
with a manual show instance that takes advantage of that knowledge:

instance Show t = Show (AV t) where
show (AVLeft a) = drop 5 $ show (Left a)

The 'drop 5' takes off the 'Left ' in the returned string.  To be a bit
smarter you'd also look for surrounding parens and remove them as well, but
this is how you could solve your problem.

All this said, I agree that the presence of 'arr' in Arrow is a problem for
many types of generalized computing.  It overly constrains what can be an
arrow, in my opinion.  I think a better analysis of the primitives required
for arrow notation to work would solve a lot of problems of this type.

  -- ryan

On Sat, May 7, 2011 at 10:14 PM, Nicholas Tung nt...@ntung.com wrote:

 Dear all,

 I'd like to write a function maybeShow :: a - Maybe String, which
 runs show if its argument is of class Show.

 The context and motivation for this are as follows. I have a GADT type
 which encapsulates abstract-value computation (or constants or error codes),
 a snippet of which is below.

 data AV t where
 AVLeft :: AV a - AV (Either a b)

 This is used to implement an arrow transformer, and due to Arrows
 mapping all Haskell functions, I cannot put some kind of qualification on
 the constructor, like AVLeft :: Show a = 

 Of course any replies are welcome, but I do need something implemented
 and stable. If there are GHC-compatible hacks, even an unsafeShow :: a -
 String, that'd be great. I'd also prefer not to branch on all types which
 could possibly be maybeShow's argument.



 (Concretely, if I have newtype AVFunctor a b c = AVF (a (AV b) (AV
 c)), then the Arrow class declaration forces all types, c.f. variable b, to
 be potential variables of type AV),

 class (Category a) = Arrow a where
   arr :: (b - c) - a b c


 Thanks very much,
 Nicholas — https://ntung.com — CS major @ UC Berkeley

 p.s. I posted this question on StackOverflow if you care to get brownie
 points there, http://goo.gl/PrmYW

 p.s. 2 -- if there is a general dump var function in ghci, which does
 more than :info, I'd love to know :)

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


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


Re: [Haskell-cafe] Type-class conditional behavior

2011-05-08 Thread Gábor Lehel
On Sun, May 8, 2011 at 7:14 AM, Nicholas Tung nt...@ntung.com wrote:
 Dear all,
     I'd like to write a function maybeShow :: a - Maybe String, which
 runs show if its argument is of class Show.
     The context and motivation for this are as follows. I have a GADT type
 which encapsulates abstract-value computation (or constants or error codes),
 a snippet of which is below.
 data AV t where
     AVLeft :: AV a - AV (Either a b)
     This is used to implement an arrow transformer, and due to Arrows
 mapping all Haskell functions, I cannot put some kind of qualification on
 the constructor, like AVLeft :: Show a = 
     Of course any replies are welcome, but I do need something implemented
 and stable. If there are GHC-compatible hacks, even an unsafeShow :: a -
 String, that'd be great. I'd also prefer not to branch on all types which
 could possibly be maybeShow's argument.

To the best of my knowledge, this is impossible. Haskell/GHC lets you
require that certain type-level (predicates/assertions/constraints be
true? evidence/proof be supplied? I'm not sure what the correct
terminology is), but it doesn't let you branch over *whether* it is
so. A natural solution would be OverlappingInstances, but that doesn't
help in this case: instances are matched only by the instance head,
and the context is checked only afterwards. So if you have

class MaybeShow a where maybeShow :: a - Maybe String
instance MaybeShow a where maybeShow = const Nothing
instance Show a = MaybeShow a where maybeShow = Just . show

you have two instances which both match for any 'a', resulting in
overlap any time you try to use it, and rendering this 'solution'
unworkable. There's a section on advanced overlap in the wiki[1], but
it's Really Ugly and doesn't (to my mind) actually solve the problem
(you still have to branch on every potential type).

You could do:

class MaybeShow a where maybeShow :: a - Maybe String
instance MaybeShow a where maybeShow = const Nothing
newtype Showable a = Showable { getShowable :: a }
instance Show a = MaybeShow (Showable a) where maybeShow = Just .
show . getShowable

which lets you write further MaybeShow instances for specific types to
'forward' the Show instance (which isn't any worse than the
AdvancedOverlap solution, if you have to handle every type explicitly
anyways), and you can also write maybeShow (Showable x) at the use
site if you know that x has a Show instance. But at that point you
might as well perform some 'optimization' and just use show directly,
so this doesn't really get you anywhere.

[1] http://www.haskell.org/haskellwiki/GHC/AdvancedOverlap





     (Concretely, if I have newtype AVFunctor a b c = AVF (a (AV b) (AV
 c)), then the Arrow class declaration forces all types, c.f. variable b, to
 be potential variables of type AV),
 class (Category a) = Arrow a where
   arr :: (b - c) - a b c

 Thanks very much,
 Nicholas — https://ntung.com — CS major @ UC Berkeley

 p.s. I posted this question on StackOverflow if you care to get brownie
 points there, http://goo.gl/PrmYW
 p.s. 2 -- if there is a general dump var function in ghci, which does more
 than :info, I'd love to know :)
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe





-- 
Work is punishment for failing to procrastinate effectively.

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


Re: [Haskell-cafe] Type-class conditional behavior

2011-05-08 Thread dm-list-haskell-cafe
At Sat, 7 May 2011 22:14:27 -0700,
Nicholas Tung wrote:
 
 Dear all,
 
     I'd like to write a function maybeShow :: a - Maybe String, which runs
 show if its argument is of class Show.

You can't do this, because in general there is no way to know whether
an arbitrary object a is of class Show.  In fact, in the worst case,
you could even have two different instances of Show for the same type
defined in two different modules of your program.  Obviously you can't
import both modules with both instances into the same module, but what
if you didn't import either--how would the compiler know where to find
the Show function or which one to use.

The best you could hope for is to run show if type a is *known* to be
in class Show at your call site.  But that would lead to some pretty
weird behavior.  For instance, the following two functions would be
different--f1 would always return Just, and f2 would always return
Nothing, which is why I assume no combination of LANGUAGE pragmas
would allow it:

f1 :: (Show a) = a - Maybe String
f1 = maybeShow

f2 :: a - Maybe String
f2 = maybeShow

In fact, I suspect that your arrow example is more like f2, in that
you don't have a Show dictionary around, so maybeShow will always
return nothing.

Is there any way you can pass the function around explicitly, as in:

data AV t where
  AVLeft :: AV (a, a - Maybe String)
 - AV (Either (a, a - Maybe String) b)

It is also possible to pass dictionaries around explicitly using the
ExistentialQuantification extension (which is required by the standard
library exception mechanism, so is probably a reasonably safe one to
rely on).  Can you do something like the following?

{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE GADTs #-}

data Showable a = forall a. (Show a) = Showable a

data AV t where
  AVLeft :: AV (Showable a) - AV (Either (Showable a) b)

David

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


[Haskell-cafe] Type-class conditional behavior

2011-05-07 Thread Nicholas Tung
Dear all,

I'd like to write a function maybeShow :: a - Maybe String, which
runs show if its argument is of class Show.

The context and motivation for this are as follows. I have a GADT type
which encapsulates abstract-value computation (or constants or error codes),
a snippet of which is below.

data AV t where
AVLeft :: AV a - AV (Either a b)

This is used to implement an arrow transformer, and due to Arrows
mapping all Haskell functions, I cannot put some kind of qualification on
the constructor, like AVLeft :: Show a = 

Of course any replies are welcome, but I do need something implemented
and stable. If there are GHC-compatible hacks, even an unsafeShow :: a -
String, that'd be great. I'd also prefer not to branch on all types which
could possibly be maybeShow's argument.



(Concretely, if I have newtype AVFunctor a b c = AVF (a (AV b) (AV
c)), then the Arrow class declaration forces all types, c.f. variable b, to
be potential variables of type AV),

class (Category a) = Arrow a where
  arr :: (b - c) - a b c


Thanks very much,
Nicholas — https://ntung.com — CS major @ UC Berkeley

p.s. I posted this question on StackOverflow if you care to get brownie
points there, http://goo.gl/PrmYW

p.s. 2 -- if there is a general dump var function in ghci, which does more
than :info, I'd love to know :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe