Re: [Haskell-cafe] type/class question: toString

2007-11-08 Thread Graham Fawcett
On Nov 7, 2007 4:34 PM, Nicholas Messenger [EMAIL PROTECTED] wrote:
 If you're willing to have an extra Typeable constraint, this does what you 
 want:

  import Data.Typeable (Typeable, cast)
  import Data.Maybe (fromMaybe)
 
  toString :: (Show a, Typeable a) = a - String
  toString x = fromMaybe (show x) (cast x)


Nice! Thank you for introducing me to the Typeable class (and by
extension, Dynamic) -- I hadn't realized there was library support for
dynamic types.

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


Re: [Haskell-cafe] type/class question: toString

2007-11-07 Thread Nicholas Messenger
If you're willing to have an extra Typeable constraint, this does what you want:

 import Data.Typeable (Typeable, cast)
 import Data.Maybe (fromMaybe)

 toString :: (Show a, Typeable a) = a - String
 toString x = fromMaybe (show x) (cast x)

*Main toString blah
blah
*Main toString 1
1
*Main toString (Just 0.5)
Just 0.5

So Strings are just cast into the result.  Non-strings become Nothing,
which fromMaybe turns into (show x).

--
Nicholas Messenger
[EMAIL PROTECTED]


On Nov 6, 2007 4:23 PM, Graham Fawcett [EMAIL PROTECTED] wrote:
 On Nov 6, 2007 3:29 PM, Graham Fawcett [EMAIL PROTECTED] wrote:
  On Nov 6, 2007 2:21 PM, Jeff Polakow [EMAIL PROTECTED] wrote:
 Have you tried using -fglasgow-exts? That should enable all ghc
   extensions.

 If anyone's interested, I had best results when I added the flag
 -fallow-incoherent-instances. Without it, I could not handle numbers
 without declaring their types, e.g. 'toString (33 :: Int)' would work,
 but 'toString 33' would lead to:

 Ambiguous type variable `t' in the constraints:
   `ToString t'
 arising from use of `toString'
 at /home/graham/tmp/ToString.hs:13:15-25
   `Num t'
 arising from the literal `33'
 at /home/graham/tmp/ToString.hs:13:24-25
 Probable fix: add a type signature that fixes these type variable(s)

 Here's the code I ended up with.

 {-# OPTIONS -fglasgow-exts -fallow-overlapping-instances #-}
 {-# OPTIONS -fallow-incoherent-instances -fallow-undecidable-instances #-}

 module ToString (ToString(..)) where

 class Show a = ToString a  where toString :: a - String
 instance ToString Stringwhere toString s = s
 instance (Show a) = ToString a where toString s = show s


 Thanks to all who responded; I learned a lot from this.

 Graham

 ___
 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 question: toString

2007-11-06 Thread Bayley, Alistair
 From: [EMAIL PROTECTED] 
 [mailto:[EMAIL PROTECTED] On Behalf Of Graham Fawcett
 
 Is there a way to declare a 'toString' function, such that
 
 toString x | x is a String = x
 toString x | x's type is an instance of Show = show x
 
 Perhaps, in the type system, there's a way to declare a ToString
 class, and somehow inherit all instances of Show as ToString
 instances?


I'm assuming you're not fond of the way the print function handles
Strings?

With GHC you can do this:

 {-# OPTIONS -fallow-overlapping-instances #-}
 {-# OPTIONS -fallow-undecidable-instances #-}

 class Show a = MyShow a where show_ :: a - String
 instance MyShow String where show_ s = s
 instance (Show a) = MyShow a where show_ s = show s


Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type/class question: toString

2007-11-06 Thread Graham Fawcett
On Nov 6, 2007 10:30 AM, Bayley, Alistair
[EMAIL PROTECTED] wrote:
  From: [EMAIL PROTECTED]
  [mailto:[EMAIL PROTECTED] On Behalf Of Graham Fawcett
  Is there a way to declare a 'toString' function, such that
  toString x | x is a String = x
  toString x | x's type is an instance of Show = show x
 I'm assuming you're not fond of the way the print function handles
 Strings?

More a curiosity about the flexibility of the type system -- but yes,
I could see cases where such a thing could be useful.

 With GHC you can do this:
  {-# OPTIONS -fallow-overlapping-instances #-}
  {-# OPTIONS -fallow-undecidable-instances #-}
 
  class Show a = MyShow a where show_ :: a - String
  instance MyShow String where show_ s = s
  instance (Show a) = MyShow a where show_ s = show s

This doesn't want to compile for me:

$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.6.1

$ ghc ToString.hs   # your code, verbatim

ToString.hs:5:0:
Illegal instance declaration for `MyShow String'
(The instance type must be of form (T a b c)
 where T is not a synonym, and a,b,c are distinct type variables)
In the instance declaration for `MyShow String'

ToString.hs:6:0:
Illegal instance declaration for `MyShow a'
(The instance type must be of form (T a b c)
 where T is not a synonym, and a,b,c are distinct type variables)
In the instance declaration for `MyShow a'

I'll read up on those two GHC options, and try to figure it out myself
(but hints are welcome).

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


Re: [Haskell-cafe] type/class question: toString

2007-11-06 Thread David Benbennick
On 11/6/07, Graham Fawcett [EMAIL PROTECTED] wrote:
 ToString.hs:5:0:
 Illegal instance declaration for `MyShow String'
 (The instance type must be of form (T a b c)
  where T is not a synonym, and a,b,c are distinct type variables)
 In the instance declaration for `MyShow String'

 ToString.hs:6:0:
 Illegal instance declaration for `MyShow a'
 (The instance type must be of form (T a b c)
  where T is not a synonym, and a,b,c are distinct type variables)
 In the instance declaration for `MyShow a'

In ghc 6.8.1, the error messages are more helpful:

foo.hs:5:0:
Illegal instance declaration for `MyShow String'
(All instance types must be of the form (T t1 ... tn)
 where T is not a synonym.
 Use -XTypeSynonymInstances if you want to disable this.)
In the instance declaration for `MyShow String'

foo.hs:6:0:
Illegal instance declaration for `MyShow a'
(All instance types must be of the form (T a1 ... an)
 where a1 ... an are distinct type *variables*
 Use -XFlexibleInstances if you want to disable this.)
In the instance declaration for `MyShow a'

When I run with -XTypeSynonymInstances -XFlexibleInstances it works.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type/class question: toString

2007-11-06 Thread Luke Palmer
 I'm assuming you're not fond of the way the print function handles
 Strings?

 With GHC you can do this:

  {-# OPTIONS -fallow-overlapping-instances #-}
  {-# OPTIONS -fallow-undecidable-instances #-}
 
  class Show a = MyShow a where show_ :: a - String
  instance MyShow String where show_ s = s
  instance (Show a) = MyShow a where show_ s = show s

I'm curious why this works.  How does GHC know to pick the MyShow String
instance instead of the one coming from Show String?

I expect there's no way to do this without undecidable instances, is there?
I try to stay away from that flag nowadays, since I've seen some strange
unpredictable behavior from it in the past  (the unpredictability of the
behavior may come from the fact that I don't know how the inference algorithm
works).

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


Re: [Haskell-cafe] type/class question: toString

2007-11-06 Thread Thomas Schilling
On Tue, 2007-11-06 at 09:18 -0500, Graham Fawcett wrote:
 Hi folks,
 
 Is there a way to declare a 'toString' function, such that
 
 toString x | x is a String = x
 toString x | x's type is an instance of Show = show x
 
 Perhaps, in the type system, there's a way to declare a ToString
 class, and somehow inherit all instances of Show as ToString
 instances?

I think the simpler solution (for your particular problem) is to tag
strings that should be printed as-is:

newtype Literal = Literal String

instance Show Literal where show (Literal x) = x

lit :: String - Literal
lit = Literal 

I generally try to keep the law

  read . show == id

Thus, for anything that needs to be printed in a nicer way I use
something like this:

class PPrint a where
  pretty :: a - Doc   


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


Re: [Haskell-cafe] type/class question: toString

2007-11-06 Thread Jeff Polakow
Hello,

  Have you tried using -fglasgow-exts? That should enable all ghc 
extensions.

-Jeff

[EMAIL PROTECTED] wrote on 11/06/2007 02:02:11 PM:

 On Nov 6, 2007 12:15 PM, David Benbennick [EMAIL PROTECTED] wrote:
  In ghc 6.8.1, the error messages are more helpful:
 
  foo.hs:5:0:
  Illegal instance declaration for `MyShow String'
  (All instance types must be of the form (T t1 ... tn)
   where T is not a synonym.
   Use -XTypeSynonymInstances if you want to disable this.)
  In the instance declaration for `MyShow String'
 
 
 Thanks for the tip. I might give 6.8.1 a try; I still cannot get it to
 work in 6.6.1. The problem may exist between the keyboard and the
 chair.
 
 G
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type/class question: toString

2007-11-06 Thread Graham Fawcett
On Nov 6, 2007 12:03 PM, Thomas Schilling [EMAIL PROTECTED] wrote:
 On Tue, 2007-11-06 at 09:18 -0500, Graham Fawcett wrote:
  Hi folks,
  Is there a way to declare a 'toString' function, such that
  toString x | x is a String = x
  toString x | x's type is an instance of Show = show x
 I think the simpler solution (for your particular problem) is to tag
 strings that should be printed as-is:

 newtype Literal = Literal String
 instance Show Literal where show (Literal x) = x
 lit :: String - Literal
 lit = Literal

I almost replied to ask, doesn't that solve a different problem? But
I see that in practice, it leads to a similar result, and without
type-system trickery.

The type-system trickery is still devilishly interesting, though. ;-)

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


Re: [Haskell-cafe] type/class question: toString

2007-11-06 Thread Graham Fawcett
On Nov 6, 2007 2:21 PM, Jeff Polakow [EMAIL PROTECTED] wrote:
   Have you tried using -fglasgow-exts? That should enable all ghc
 extensions.

Ah thanks, that does it.
G
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type/class question: toString

2007-11-06 Thread Graham Fawcett
On Nov 6, 2007 3:29 PM, Graham Fawcett [EMAIL PROTECTED] wrote:
 On Nov 6, 2007 2:21 PM, Jeff Polakow [EMAIL PROTECTED] wrote:
Have you tried using -fglasgow-exts? That should enable all ghc
  extensions.

If anyone's interested, I had best results when I added the flag
-fallow-incoherent-instances. Without it, I could not handle numbers
without declaring their types, e.g. 'toString (33 :: Int)' would work,
but 'toString 33' would lead to:

Ambiguous type variable `t' in the constraints:
  `ToString t'
arising from use of `toString'
at /home/graham/tmp/ToString.hs:13:15-25
  `Num t'
arising from the literal `33'
at /home/graham/tmp/ToString.hs:13:24-25
Probable fix: add a type signature that fixes these type variable(s)

Here's the code I ended up with.

{-# OPTIONS -fglasgow-exts -fallow-overlapping-instances #-}
{-# OPTIONS -fallow-incoherent-instances -fallow-undecidable-instances #-}

module ToString (ToString(..)) where

class Show a = ToString a  where toString :: a - String
instance ToString Stringwhere toString s = s
instance (Show a) = ToString a where toString s = show s


Thanks to all who responded; I learned a lot from this.

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