[Haskell-cafe] Type families in export lists

2009-05-30 Thread Maurí­cio

Hi,

How do I include type families (used as associated
types) in a module export list? E.g.:

class MyClass a where
type T a :: *
coolFunction :: Ta - a
(...)

If I just include MyClass and its functions in the
list, instances in other modules complain they don't
know T, but I wasn't able to find how (where) to
include T in the list.

Thanks,
Maurício

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


Re: [Haskell-cafe] Re: Error message reform

2009-05-30 Thread Tillmann Rendel

wren ng thornton wrote:

(Though it doesn't necessarily generalize to cover similar messages like:

Prelude :t (\x - x) :: a - b
interactive:1:7:
Couldn't match expected type `b' against inferred type `a'
  `b' is a rigid type variable bound by
  the polymorphic type `forall a b. a - b' at interactive:1:0
  `a' is a rigid type variable bound by
  the polymorphic type `forall a b. a - b' at interactive:1:0
In the expression: x
)


I find this slightly more complicated case quite confusing with the 
current wording:


  Prelude :t (\x - x) :: (a - b) - (a - a)
  interactive:1:7:
  Couldn't match expected type `a' against inferred type `b'
`a' is a rigid type variable bound by
an expression type signature at interactive:1:14
`b' is a rigid type variable bound by
an expression type signature at interactive:1:19
  In the expression: x
  In the expression: (\ x - x) :: (a - b) - (a - a)

This message suggests that ghc has inferred type b for x.

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


Re: [Haskell-cafe] Re: Error message reform

2009-05-30 Thread Claus Reinke
I find this slightly more complicated case quite confusing with the 
current wording:


  Prelude :t (\x - x) :: (a - b) - (a - a)
  interactive:1:7:
  Couldn't match expected type `a' against inferred type `b'
`a' is a rigid type variable bound by
an expression type signature at interactive:1:14
`b' is a rigid type variable bound by
an expression type signature at interactive:1:19
  In the expression: x
  In the expression: (\ x - x) :: (a - b) - (a - a)

This message suggests that ghc has inferred type b for x.


Not really; but this looks like a nice simple example of what I 
was referring to: GHC is so careful not to bother the user with

scary type stuff that it mentions types as little as possible. In
particular, it never mentions the type of 'x'! 


It only mentions that it has run into 'a' and 'b' somewhere
*while looking into 'x's type*, so those are conflicting types 
for some parts of 'x's type, not 'x's type itself. 


In more complex code, this peephole view can be really
unhelpful, which is why I suggested [1] that type errors
should give types for all expressions mentioned in the 
type error context (here 'x' and '(\x-x)', the latter's

type is there only because it was part of the input).

Claus

[1] http://hackage.haskell.org/trac/ghc/ticket/1928#comment:2


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


Re: [Haskell-cafe] Parsec float

2009-05-30 Thread Bartosz Wójcik
On Saturday 30 May 2009 03:10:11 Bryan O'Sullivan wrote:
 On Fri, May 29, 2009 at 5:04 PM, Bartosz Wójcik bar...@sudety.it wrote:
  I don't undersdand what is being missed.

 Brevity.

  liftM f m1  = do { x1 - m1; return (f x1) }
  so
  liftM fromIntegral integer
  will result the same.

 Yes, and there's less code to read if you use liftM or $, hence fewer
 moving parts to understand.

OK, thats clear.  BTW: reading RWH I could not memorize what those liftM 
funtions meant. 
Best,
Bartek


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


Re: [Haskell-cafe] can someone point me to more help about Database.HDBC.ODBC?

2009-05-30 Thread Wei Hu
Try http://sites.google.com/site/haskell/notes/connecting-to-mysql-with-haskell
that I wrote up. An important thing that I don't think was documented
anywhere is that the trailing ';' is required.

On Fri, May 29, 2009 at 11:01 PM, Michael P Mossey
m...@alumni.caltech.edu wrote:
 I'm trying to use Database.HDBC.ODBC to connect to a MySQL server, and I
 cannot figure out the docs. I want to establish a connection, and I know the
 server url, username, and password. According to these docs...

 http://software.complete.org/static/hdbc-odbc/doc//HDBC-odbc/Database-HDBC-ODBC.html

 ...I am supposed to pass a string to connectODBC. These docs do not explain
 the meaning of the passed string, but refer me to a microsoft document:

 http://msdn2.microsoft.com/en-us/library/ms715433(VS.85).aspx

 I cannot make any sense of this microsoft document. I guess I don't know
 enough about database interfaces in general. Can someone explain how to make
 a connect to a specific URL, or point me to some clearer docs?

 Thanks,
 Mike


 ___
 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 families in export lists

2009-05-30 Thread Lee Duhem
On Sat, May 30, 2009 at 7:35 PM, Maurí­cio briqueabra...@yahoo.com wrote:
 Hi,

 How do I include type families (used as associated
 types) in a module export list? E.g.:

 class MyClass a where
    type T a :: *
    coolFunction :: Ta - a
    (...)

 If I just include MyClass and its functions in the
 list, instances in other modules complain they don't
 know T, but I wasn't able to find how (where) to
 include T in the list.


In export list, you can treat 'type T a' as normal type declaration, ie, write
T(..)  in export list.

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


Re: [Haskell-cafe] Parsec float

2009-05-30 Thread Jason Dusek
2009/05/30 Bartosz Wójcik bar...@sudety.it:
 ...reading RWH I could not memorize what those liftM funtions
 meant.

  The basic one, `liftM`, means `fmap`, though specialized for
  functors that are monads.

Prelude Control.Monad :t liftM
liftM :: forall a b (m :: * - *). (Monad m) = (a - b) - m a - m b
Prelude Control.Monad :t fmap
fmap :: forall a b (f :: * - *). (Functor f) = (a - b) - f a - f b

  I think we have `liftM` either to help the inferencer or due
  to the absence of a `(Functor m)` constraint in the definition
  of the `Monad` typeclass.

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


Re: [Haskell-cafe] Parsec float

2009-05-30 Thread Derek Elkins
On Sat, May 30, 2009 at 1:12 PM, Jason Dusek jason.du...@gmail.com wrote:
 2009/05/30 Bartosz Wójcik bar...@sudety.it:
 ...reading RWH I could not memorize what those liftM funtions
 meant.

  The basic one, `liftM`, means `fmap`, though specialized for
  functors that are monads.

    Prelude Control.Monad :t liftM
    liftM :: forall a b (m :: * - *). (Monad m) = (a - b) - m a - m b
    Prelude Control.Monad :t fmap
    fmap :: forall a b (f :: * - *). (Functor f) = (a - b) - f a - f b

  I think we have `liftM` either to help the inferencer or due
  to the absence of a `(Functor m)` constraint in the definition
  of the `Monad` typeclass.

It's the latter effectively.  liftM doesn't make anything easier for
the type checker.  liftM simply has a different type than fmap, not a
more specialized one, but even if Monad did have a Functor constraint,
liftM would still never lead to any ambiguity being resolved.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Concurrent Haskell Actions with Timeout

2009-05-30 Thread Cetin Sert
Hi how could one implement a function in concurrent haskell that either
returns 'a' successfully or due timeout 'b'?

timed :: Int → IO a → b → IO (Either a b)
timed max act def = do

Best Regards,
Cetin Sert
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Missing a Deriving?

2009-05-30 Thread michael rice
The following code is from Section 8.4.2, pgs. 111-112 (PDF paging) of YAHT.

It compiles fine, but upon trying it I get the following error message.

It seems to be trying to 'Show' the Computation class but I'm not sure where to 
put the 'Deriving'.

Michael




Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Main ( graph4.hs, interpreted )
Ok, modules loaded: Main.
*Main let g = Graph [(1,'a'),(2,'b'),(3,'c'),(4,'d')] 
[(1,2,'p'),(2,3,'q'),(1,4,'r'),(4,3,'s')]
*Main searchAll g 1 3

interactive:1:0:
    No instance for (Show (c [Int]))
  arising from a use of `print' at interactive:1:0-14
    Possible fix: add an instance declaration for (Show (c [Int]))
    In a stmt of a 'do' expression: print it



data Failable a = Success a | Fail String deriving (Show)

data Graph v e = Graph [(Int,v)] [(Int,Int,e)]

class Computation c where
    success :: a - c a
    failure :: String - c a
    augment :: c a - (a - c b) - c b
    combine :: c a - c a - c a

instance Computation Maybe where
    success = Just
    failure = const Nothing
    augment (Just x) f = f x
    augment Nothing _ = Nothing
    combine Nothing y = y
    combine x _ = x

instance Computation Failable where
    success = Success
    failure = Fail
    augment (Success x) f = f x
    augment (Fail s) _ = Fail s
    combine (Fail _) y = y
    combine x _ = x

instance Computation [] where
    success a = [a]
    failure = const []
    augment l f = concat (map f l)
    combine = (++)

searchAll g@(Graph vl el) src dst
    | src == dst = success [src]
    | otherwise = search' el
    where search' [] = failure no path
  search' ((u,v,_):es)
  | src == u = (searchAll g v dst `augment`
 (success . (u:)))
    `combine` search' es
  | otherwise = search' es




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


Re: [Haskell-cafe] Concurrent Haskell Actions with Timeout

2009-05-30 Thread Sebastian Sylvan
2009/5/30 Cetin Sert cetin.s...@gmail.com

 Hi how could one implement a function in concurrent haskell that either
 returns 'a' successfully or due timeout 'b'?

 timed :: Int → IO a → b → IO (Either a b)
 timed max act def = do



Something like (warning, untested code - no compiler atm).

timed timeout act fallback = do
   res - newEmptyMVar
   tid - forkIO $ act = writeMVar res
   threadDelay timeout
   stillRunning - isEmptyMVar res
   if stillRunning then killThread tid  return fallback else takeMVar res

-- 
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Concurrent Haskell Actions with Timeout

2009-05-30 Thread Cetin Sert
Thank you for your reply, I'd come up with the following:

timed :: Int → IO a → b → IO (Either b a)
timed max act def = do

  r ← new

  t ← forkIO $ do
a ← act
r ≔ Right a

  s ← forkIO $ do
wait max
e ← em r
case e of
  True  → do
kill t
r ≔ Left def

  False → return ()

  takeMVar r

-

*Network.Port.Scan timed 500 (wait 5  return 0) 'x'
Left 'x'
*Network.Port.Scan timed 50 (wait 5  return 0) 'x'
Right 0

-

before reading your reply:

timed timeout act fallback = do
   res - newEmptyMVar
   tid - forkIO $ act = writeMVar res
   threadDelay timeout
   stillRunning - isEmptyMVar res
   if stillRunning then killThread tid  return fallback else takeMVar res

-

*Network.Port.Scan timed2 500 (wait 5  return 0) 'x'

interactive:1:33:
No instance for (Num Char)
  arising from the literal `0' at interactive:1:33
Possible fix: add an instance declaration for (Num Char)
In the first argument of `return', namely `0'
In the second argument of `()', namely `return 0'
In the second argument of `timed2', namely
`(wait 5  return 0)'

Regards,
Cetin Sert

2009/5/30 Sebastian Sylvan sebastian.syl...@gmail.com



 2009/5/30 Cetin Sert cetin.s...@gmail.com

 Hi how could one implement a function in concurrent haskell that either
 returns 'a' successfully or due timeout 'b'?

 timed :: Int → IO a → b → IO (Either a b)
 timed max act def = do



 Something like (warning, untested code - no compiler atm).

 timed timeout act fallback = do
res - newEmptyMVar
tid - forkIO $ act = writeMVar res
threadDelay timeout
stillRunning - isEmptyMVar res
if stillRunning then killThread tid  return fallback else takeMVar res

 --
 Sebastian Sylvan
 +44(0)7857-300802
 UIN: 44640862

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


Re: [Haskell-cafe] Concurrent Haskell Actions with Timeout

2009-05-30 Thread Sebastian Sylvan
On Sat, May 30, 2009 at 10:32 PM, Cetin Sert cetin.s...@gmail.com wrote:

 Thank you for your reply, I'd come up with the following:

 timed :: Int → IO a → b → IO (Either b a)
 timed max act def = do

   r ← new

   t ← forkIO $ do
 a ← act
 r ≔ Right a

   s ← forkIO $ do
 wait max
 e ← em r
 case e of
   True  → do
 kill t
 r ≔ Left def

   False → return ()

   takeMVar r

 -

 *Network.Port.Scan timed 500 (wait 5  return 0) 'x'
 Left 'x'
 *Network.Port.Scan timed 50 (wait 5  return 0) 'x'
 Right 0

 -

 before reading your reply:

 timed timeout act fallback = do
res - newEmptyMVar
tid - forkIO $ act = writeMVar res
threadDelay timeout
stillRunning - isEmptyMVar res
if stillRunning then killThread tid  return fallback else takeMVar res

 -

 *Network.Port.Scan timed2 500 (wait 5  return 0) 'x'

 interactive:1:33:
 No instance for (Num Char)
   arising from the literal `0' at interactive:1:33
 Possible fix: add an instance declaration for (Num Char)
 In the first argument of `return', namely `0'
 In the second argument of `()', namely `return 0'
 In the second argument of `timed2', namely
 `(wait 5  return 0)'



Right, I forgot about the Either bit so you'd have to make sure the
action's result and the default has the same type (or modify it to return an
Either).



-- 
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread Miguel Mitrofanov
It's trying to 'Show' the 'c [Int]' type, but doesn't know which 'c'  
to use; so it's trying to find a generic instance, which doesn't  
exist. You can't fix this with 'deriving' or anything like this;  
instead, provide the type annotation like this:


*Main searchAll g 1 3 :: Maybe [Int]

On 31 May 2009, at 00:50, michael rice wrote:

The following code is from Section 8.4.2, pgs. 111-112 (PDF paging)  
of YAHT.


It compiles fine, but upon trying it I get the following error  
message.


It seems to be trying to 'Show' the Computation class but I'm not  
sure where to put the 'Deriving'.


Michael




Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Main ( graph4.hs, interpreted )
Ok, modules loaded: Main.
*Main let g = Graph [(1,'a'),(2,'b'),(3,'c'),(4,'d')] [(1,2,'p'), 
(2,3,'q'),(1,4,'r'),(4,3,'s')]

*Main searchAll g 1 3

interactive:1:0:
No instance for (Show (c [Int]))
  arising from a use of `print' at interactive:1:0-14
Possible fix: add an instance declaration for (Show (c [Int]))
In a stmt of a 'do' expression: print it



data Failable a = Success a | Fail String deriving (Show)

data Graph v e = Graph [(Int,v)] [(Int,Int,e)]

class Computation c where
success :: a - c a
failure :: String - c a
augment :: c a - (a - c b) - c b
combine :: c a - c a - c a

instance Computation Maybe where
success = Just
failure = const Nothing
augment (Just x) f = f x
augment Nothing _ = Nothing
combine Nothing y = y
combine x _ = x

instance Computation Failable where
success = Success
failure = Fail
augment (Success x) f = f x
augment (Fail s) _ = Fail s
combine (Fail _) y = y
combine x _ = x

instance Computation [] where
success a = [a]
failure = const []
augment l f = concat (map f l)
combine = (++)

searchAll g@(Graph vl el) src dst
| src == dst = success [src]
| otherwise = search' el
where search' [] = failure no path
  search' ((u,v,_):es)
  | src == u = (searchAll g v dst `augment`
 (success . (u:)))
`combine` search' es
  | otherwise = search' es


___
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] Missing a Deriving?

2009-05-30 Thread Ketil Malde
michael rice nowg...@yahoo.com writes:

 The following code is from Section 8.4.2, pgs. 111-112 (PDF paging) of YAHT.
 It compiles fine, but upon trying it I get the following error message.
 It seems to be trying to 'Show' the Computation class but I'm not sure where 
 to put the 'Deriving'.

My guess is that your expression is polymorphic, returning 
   Computation c = c [Int]

Since Haskell knows how to show this for both of the instances defined
for Computation (i.e. Maybe [Int] and [[Int]]), perhaps you could give
one of those as an explicit type signature?

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Concurrent Haskell Actions with Timeout

2009-05-30 Thread Sterling Clover
The proper way is just to wrap System.Timeout, which does some rather  
clever things with regards to exception semantics. The code for it is  
a joy to read, by the way.


--S.

On May 30, 2009, at 5:36 PM, Sebastian Sylvan wrote:




On Sat, May 30, 2009 at 10:32 PM, Cetin Sert cetin.s...@gmail.com  
wrote:

Thank you for your reply, I'd come up with the following:

timed :: Int → IO a → b → IO (Either b a)
timed max act def = do

  r ← new

  t ← forkIO $ do
a ← act
r ≔ Right a

  s ← forkIO $ do
wait max
e ← em r
case e of
  True  → do
kill t
r ≔ Left def

  False → return ()

  takeMVar r

-

*Network.Port.Scan timed 500 (wait 5  return 0) 'x'
Left 'x'
*Network.Port.Scan timed 50 (wait 5  return 0) 'x'
Right 0

-

before reading your reply:


timed timeout act fallback = do
   res - newEmptyMVar
   tid - forkIO $ act = writeMVar res
   threadDelay timeout
   stillRunning - isEmptyMVar res
   if stillRunning then killThread tid  return fallback else  
takeMVar res


-

*Network.Port.Scan timed2 500 (wait 5  return 0) 'x'

interactive:1:33:
No instance for (Num Char)
  arising from the literal `0' at interactive:1:33
Possible fix: add an instance declaration for (Num Char)
In the first argument of `return', namely `0'
In the second argument of `()', namely `return 0'
In the second argument of `timed2', namely
`(wait 5  return 0)'


Right, I forgot about the Either bit so you'd have to make sure  
the action's result and the default has the same type (or modify it  
to return an Either).




--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
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


[Haskell-cafe] get Scale of window in HOpenGL?

2009-05-30 Thread yu yang
Hi,
 
I want to move one object to the border of window, then go back to the start 
point. Does anyone one have an idea to implement it ? Thank you!


  ___ 
  好玩贺卡等你发,邮箱贺卡全新上线! 
http://card.mail.cn.yahoo.com/___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Lazy Parsing

2009-05-30 Thread GüŸnther Schmidt

Dear Doaitse,

It is my pleasure to announce that after 5 days of experimenting with 
uu-parsinglib I have absolutely no clue, whatsoever, on how to use it.


Period.

I do not even manage to write a parser for even a mere digit or a simple 
character. I have read the tutorial from a to a to z and from z to a and 
there were a few words I recognized.


I mean I'd like to be able to turn 12.05.2009 into something like (12, 
5, 2009) and got no clue what the code would have to look like. I do 
know almost every variation what the code must not look like :).


I am guessing here that when one does define a parsing function, since 
all the parser combinators aren't function but methods, one *must* also 
provide a type signature so that the compiler knows the actual 
*instance* method?



Günther


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


Re: [Haskell-cafe] Concurrent Haskell Actions with Timeout

2009-05-30 Thread Cetin Sert
-__- hehe why did I not let Hayoo or Hoogle help me there *sigh*

Thanks!!

2009/5/31 Sterling Clover s.clo...@gmail.com

 The proper way is just to wrap System.Timeout, which does some rather
 clever things with regards to exception semantics. The code for it is a joy
 to read, by the way.

 --S.


 On May 30, 2009, at 5:36 PM, Sebastian Sylvan wrote:



 On Sat, May 30, 2009 at 10:32 PM, Cetin Sert cetin.s...@gmail.com
 wrote:
 Thank you for your reply, I'd come up with the following:

 timed :: Int → IO a → b → IO (Either b a)
 timed max act def = do

  r ← new

  t ← forkIO $ do
a ← act
r ≔ Right a

  s ← forkIO $ do
wait max
e ← em r
case e of
  True  → do
kill t
r ≔ Left def

  False → return ()

  takeMVar r

 -

 *Network.Port.Scan timed 500 (wait 5  return 0) 'x'
 Left 'x'
 *Network.Port.Scan timed 50 (wait 5  return 0) 'x'
 Right 0

 -

 before reading your reply:


 timed timeout act fallback = do
   res - newEmptyMVar
   tid - forkIO $ act = writeMVar res
   threadDelay timeout
   stillRunning - isEmptyMVar res
   if stillRunning then killThread tid  return fallback else takeMVar res

 -

 *Network.Port.Scan timed2 500 (wait 5  return 0) 'x'

 interactive:1:33:
No instance for (Num Char)
  arising from the literal `0' at interactive:1:33
Possible fix: add an instance declaration for (Num Char)
In the first argument of `return', namely `0'
In the second argument of `()', namely `return 0'
In the second argument of `timed2', namely
`(wait 5  return 0)'


 Right, I forgot about the Either bit so you'd have to make sure the
 action's result and the default has the same type (or modify it to return an
 Either).



 --
 Sebastian Sylvan
 +44(0)7857-300802
 UIN: 44640862
 ___
 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

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


Re: [Haskell-cafe] [] == []

2009-05-30 Thread Derek Elkins
On Fri, May 29, 2009 at 5:36 AM, Max Rabkin max.rab...@gmail.com wrote:
 On Fri, May 29, 2009 at 12:29 PM, Paul Keir pk...@dcs.gla.ac.uk wrote:
 f''' = ([]::[()]) == ([]::[()])

 (Very pretty.)

 So why doesn't ghc have 'default' instances?

 It does. I believe Num defaults to Integer and then to Double.

 Generally, though, defaults are convenient in exploratory usage but
 confusing in compiled code. In compiled code, you don't want arbitrary
 choices of defaults to affect performance and correctness.

 I've had programs run much slower than expected because the types
 defaulted to Integer rather than Int.

http://www.haskell.org/ghc/docs/latest/html/users_guide/interactive-evaluation.html#extended-default-rules
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] HPC and derived instances

2009-05-30 Thread Felipe Lessa
Hello!

Why isn't there an option to control whether HPC, the Haskell
Program Coverage, will consider derived instances coverable.
I'm using it and my top level coverage is 52% while my expression
coverage is at 92%.  Looking carefully we see that most
non-tested top level definitions are derived Show, Eq and Ord
instances that I always derive for most data types (as this is a
library).

I think it is nice that it recognizes class instances, but there
should be a flag to ignore at least the derived ones.  Am I
missing something?

Thanks! :)

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


Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread michael rice
Hi Miguel,

That works. but it gives just a single solution [1,2,3] when there are supposed 
to be two [[1,2,3],[1,4,3]]. Of course the code in YAHT may be in error.

Also, how the heck does Haskell decide which success, failure, augment, 
and combine to use in function searchAll, since there are five 
possibilities.

MIchael

--- On Sat, 5/30/09, Miguel Mitrofanov miguelim...@yandex.ru wrote:

From: Miguel Mitrofanov miguelim...@yandex.ru
Subject: Re: [Haskell-cafe] Missing a Deriving?
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Saturday, May 30, 2009, 5:36 PM

It's trying to 'Show' the 'c [Int]' type, but doesn't know which 'c' to use; so 
it's trying to find a generic instance, which doesn't exist. You can't fix this 
with 'deriving' or anything like this; instead, provide the type annotation 
like this:

*Main searchAll g 1 3 :: Maybe [Int]

On 31 May 2009, at 00:50, michael rice wrote:

 The following code is from Section 8.4.2, pgs. 111-112 (PDF paging) of YAHT.
 
 It compiles fine, but upon trying it I get the following error message.
 
 It seems to be trying to 'Show' the Computation class but I'm not sure where 
 to put the 'Deriving'.
 
 Michael
 
 
 
 
 Loading package ghc-prim ... linking ... done.
 Loading package integer ... linking ... done.
 Loading package base ... linking ... done.
 [1 of 1] Compiling Main             ( graph4.hs, interpreted )
 Ok, modules loaded: Main.
 *Main let g = Graph [(1,'a'),(2,'b'),(3,'c'),(4,'d')] 
 [(1,2,'p'),(2,3,'q'),(1,4,'r'),(4,3,'s')]
 *Main searchAll g 1 3
 
 interactive:1:0:
     No instance for (Show (c [Int]))
       arising from a use of `print' at interactive:1:0-14
     Possible fix: add an instance declaration for (Show (c [Int]))
     In a stmt of a 'do' expression: print it
 
 
 
 data Failable a = Success a | Fail String deriving (Show)
 
 data Graph v e = Graph [(Int,v)] [(Int,Int,e)]
 
 class Computation c where
     success :: a - c a
     failure :: String - c a
     augment :: c a - (a - c b) - c b
     combine :: c a - c a - c a
 
 instance Computation Maybe where
     success = Just
     failure = const Nothing
     augment (Just x) f = f x
     augment Nothing _ = Nothing
     combine Nothing y = y
     combine x _ = x
 
 instance Computation Failable where
     success = Success
     failure = Fail
     augment (Success x) f = f x
     augment (Fail s) _ = Fail s
     combine (Fail _) y = y
     combine x _ = x
 
 instance Computation [] where
     success a = [a]
     failure = const []
     augment l f = concat (map f l)
     combine = (++)
 
 searchAll g@(Graph vl el) src dst
     | src == dst = success [src]
     | otherwise = search' el
     where search' [] = failure no path
           search' ((u,v,_):es)
               | src == u = (searchAll g v dst `augment`
                              (success . (u:)))
                             `combine` search' es
               | otherwise = search' es
 
 
 ___
 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] Missing a Deriving?

2009-05-30 Thread David Menendez
On Sat, May 30, 2009 at 9:00 PM, michael rice nowg...@yahoo.com wrote:
 That works. but it gives just a single solution [1,2,3] when there are
 supposed to be two [[1,2,3],[1,4,3]]. Of course the code in YAHT may be in
 error.

Works for me.

*Main searchAll g 1 3 :: [[Int]]
[[1,2,3],[1,4,3]]
*Main searchAll g 1 3 :: Maybe [Int]
Just [1,2,3]
*Main searchAll g 1 3 :: Failable [Int]
Success [1,2,3]


 Also, how the heck does Haskell decide which success, failure,
 augment, and combine to use in function searchAll, since there are
 five possibilities.

*Main :t searchAll
searchAll :: (Computation c) = Graph t t1 - Int - Int - c [Int]

The way searchAll is written, the choice of which functions to use
depends on the type variable c. That's determined by the calling
context of searchAll, which is why you need to provide a type
signature when using it at the GHCi command line.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread Ryan Ingram
On Sat, May 30, 2009 at 6:33 PM, David Menendez d...@zednenem.com wrote:
 *Main :t searchAll
 searchAll :: (Computation c) = Graph t t1 - Int - Int - c [Int]

 The way searchAll is written, the choice of which functions to use
 depends on the type variable c. That's determined by the calling
 context of searchAll, which is why you need to provide a type
 signature when using it at the GHCi command line.

This is actually one of the most interesting and important things to
get about typeclasses; it's not *just* like an interface, because
the instance type can appear in the result of a function and *not* in
the arguments at all.

In contrast, in Java/C++, the method to use is always chosen by the
object being called; one could argue that all of COM is an attempt to
get around this problem.

Some examples:

 fromInteger :: Num a = Integer - a
 fromDynamic :: Typeable a = Dynamic - Maybe a

In both of these cases, the choice of which instance to use is made by
the caller, and often automatically by type inference:

 test x = case fromDynamic x of
Just s - s == hello
Nothing - False

Now (test $ toDynamic hello) = True, but (test $ toDynamic 'a') =
False.  Notice that I never directly specified what type fromDynamic
should return; but the case statement forces it to return Maybe
String, since I compare (s == hello)

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


Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread michael rice
I figured out the [[Int]] case for myself, but hadn't considered the Failure 
case. Thanks.

In function searchAll, given a calling context Failable [Int],  for the line

   where search' [] = failure no path

failure would be Fail, a constructor that takes a String. Right?

But using either of the other two contexts, where failure equals either const 
Nothing or const [] it would seem like that same string argument no path 
would be passed to either Nothing or [], which doesn't make any sense. 
Explanation?

Michael

--- On Sat, 5/30/09, David Menendez d...@zednenem.com wrote:

From: David Menendez d...@zednenem.com
Subject: Re: [Haskell-cafe] Missing a Deriving?
To: michael rice nowg...@yahoo.com
Cc: Miguel Mitrofanov miguelim...@yandex.ru, haskell-cafe@haskell.org
Date: Saturday, May 30, 2009, 9:33 PM

On Sat, May 30, 2009 at 9:00 PM, michael rice nowg...@yahoo.com wrote:
 That works. but it gives just a single solution [1,2,3] when there are
 supposed to be two [[1,2,3],[1,4,3]]. Of course the code in YAHT may be in
 error.

Works for me.

*Main searchAll g 1 3 :: [[Int]]
[[1,2,3],[1,4,3]]
*Main searchAll g 1 3 :: Maybe [Int]
Just [1,2,3]
*Main searchAll g 1 3 :: Failable [Int]
Success [1,2,3]


 Also, how the heck does Haskell decide which success, failure,
 augment, and combine to use in function searchAll, since there are
 five possibilities.

*Main :t searchAll
searchAll :: (Computation c) = Graph t t1 - Int - Int - c [Int]

The way searchAll is written, the choice of which functions to use
depends on the type variable c. That's determined by the calling
context of searchAll, which is why you need to provide a type
signature when using it at the GHCi command line.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/



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


Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread michael rice
Belay that last question. I just realized that its the const function being 
used rather than a constant declaration in const Nothing and const [].

MIchael

--- On Sat, 5/30/09, David Menendez d...@zednenem.com wrote:

From: David Menendez d...@zednenem.com
Subject: Re: [Haskell-cafe] Missing a Deriving?
To: michael rice nowg...@yahoo.com
Cc: Miguel Mitrofanov miguelim...@yandex.ru, haskell-cafe@haskell.org
Date: Saturday, May 30, 2009, 9:33 PM

On Sat, May 30, 2009 at 9:00 PM, michael rice nowg...@yahoo.com wrote:
 That works. but it gives just a single solution [1,2,3] when there are
 supposed to be two [[1,2,3],[1,4,3]]. Of course the code in YAHT may be in
 error.

Works for me.

*Main searchAll g 1 3 :: [[Int]]
[[1,2,3],[1,4,3]]
*Main searchAll g 1 3 :: Maybe [Int]
Just [1,2,3]
*Main searchAll g 1 3 :: Failable [Int]
Success [1,2,3]


 Also, how the heck does Haskell decide which success, failure,
 augment, and combine to use in function searchAll, since there are
 five possibilities.

*Main :t searchAll
searchAll :: (Computation c) = Graph t t1 - Int - Int - c [Int]

The way searchAll is written, the choice of which functions to use
depends on the type variable c. That's determined by the calling
context of searchAll, which is why you need to provide a type
signature when using it at the GHCi command line.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/



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


Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread nowgate
Hi Ryan,

Is there something missing or mislabeled in your post, because I don't see any 
definition of toDynamic.

Michael

--- On Sun, 5/31/09, Ryan Ingram ryani.s...@gmail.com wrote:

From: Ryan Ingram ryani.s...@gmail.com
Subject: Re: [Haskell-cafe] Missing a Deriving?
To: David Menendez d...@zednenem.com
Cc: michael rice nowg...@yahoo.com, haskell-cafe@haskell.org, Miguel 
Mitrofanov miguelim...@yandex.ru
Date: Sunday, May 31, 2009, 12:45 AM

On Sat, May 30, 2009 at 6:33 PM, David Menendez d...@zednenem.com
 wrote:
 *Main :t searchAll
 searchAll :: (Computation c) = Graph t t1 - Int - Int - c [Int]

 The way searchAll is written, the choice of which functions to use
 depends on the type variable c. That's determined by the calling
 context of searchAll, which is why you need to provide a type
 signature when using it at the GHCi command line.

This is actually one of the most interesting and important things to
get about typeclasses; it's not *just* like an interface, because
the instance type can appear in the result of a function and *not* in
the arguments at all.

In contrast, in Java/C++, the method to use is always chosen by the
object being called; one could argue that all of COM is an attempt to
get around this problem.

Some examples:

 fromInteger :: Num a = Integer - a
 fromDynamic :: Typeable a = Dynamic - Maybe
 a

In both of these cases, the choice of which instance to use is made by
the caller, and often automatically by type inference:

 test x = case fromDynamic x of
    Just s - s == hello
    Nothing - False

Now (test $ toDynamic hello) = True, but (test $ toDynamic 'a') =
False.  Notice that I never directly specified what type fromDynamic
should return; but the case statement forces it to return Maybe
String, since I compare (s == hello)

  -- ryan



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


Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread Ryan Ingram
Oops, it's called toDyn; from Data.Dynamic [1]

 toDyn :: Typeable a = a - Dynamic

  -- ryan

[1] http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Dynamic.html

On Sat, May 30, 2009 at 10:18 PM,  nowg...@yahoo.com wrote:
 Hi Ryan,

 Is there something missing or mislabeled in your post, because I don't see
 any definition of toDynamic.

 Michael

 --- On Sun, 5/31/09, Ryan Ingram ryani.s...@gmail.com wrote:

 From: Ryan Ingram ryani.s...@gmail.com
 Subject: Re: [Haskell-cafe] Missing a Deriving?
 To: David Menendez d...@zednenem.com
 Cc: michael rice nowg...@yahoo.com, haskell-cafe@haskell.org, Miguel
 Mitrofanov miguelim...@yandex.ru
 Date: Sunday, May 31, 2009, 12:45 AM

 On Sat, May 30, 2009 at 6:33 PM, David Menendez d...@zednenem.com wrote:
 *Main :t searchAll
 searchAll :: (Computation c) = Graph t t1 - Int - Int - c [Int]

 The way searchAll is written, the choice of which functions to use
 depends on the type variable c. That's determined by the calling
 context of searchAll, which is why you need to provide a type
 signature when using it at the GHCi command line.

 This is actually one of the most interesting and important things to
 get about typeclasses; it's not *just* like an interface, because
 the instance type can appear in the result of a function and *not* in
 the arguments at all.

 In contrast, in Java/C++, the method to use is always chosen by the
 object being called; one could argue that all of COM is an attempt to
 get around this problem.

 Some examples:

 fromInteger :: Num a = Integer - a
 fromDynamic :: Typeable a = Dynamic - Maybe a

 In both of these cases, the choice of which instance to use is made by
 the caller, and often automatically by type inference:

 test x = case fromDynamic x of
    Just s - s == hello
    Nothing - False

 Now (test $ toDynamic hello) = True, but (test $ toDynamic 'a') =
 False.  Notice that I never directly specified what type fromDynamic
 should return; but the case statement forces it to return Maybe
 String, since I compare (s == hello)

   -- ryan


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