[Haskell-cafe] Type Classes in Haskell - how can I make GHC make a choice of types, when the type chosen doesn't matter?

2011-04-14 Thread Chris Dew
This is a question about the use of type classes in Haskell.

I get an error (below) when trying to compile the code (below and at
https://github.com/chrisdew/haskell-sandbox/blob/master/not_working_but_clean.hs
).

As someone just learning Haskell, I have tried following GHC's advice,
but I think the cause is different.

I believe the problem is that either of the types 'IO String' or plain
'String' could be the type of 'lhello - lbracket', but GHC doesn't
know which.

The problem is that it doesn't matter, either type would work fine.

I have posted a working version of the code at
https://github.com/chrisdew/haskell-sandbox/blob/master/working_but_ugly.hs
.  This replaces one of the - operators with a new (non type class)
operator '-' which forces 'lhello - lbracket' to be of type 'IO
String'.

* Is my analysis correct?  Or is there something else going on here?

* Is there any way of informing GHC what the type of 'lhello -
lbracket' doen't matter and that is should just chose either of the
two possibilities.  Or perhaps theres a LANGUAGE option which will let
me specify that 'lastest declared matching instance of the class wins'
if anything is undecided.

Thanks,

Chris.


Error:
chris@chris-linux-desktop:~/nonworkspace/haskell-sandbox$ ghc
not_working_but_clean.hs

not_working_but_clean.hs:40:16:
No instance for (Stream (IO String) (IO String) (IO String) d)
  arising from a use of `-' at not_working_but_clean.hs:40:16-34
Possible fix:
  add an instance declaration for
  (Stream (IO String) (IO String) (IO String) d)
In the first argument of `(-)', namely `lhello - lbracket'
In the second argument of `($)', namely
`lhello - lbracket - putStrLn'
In a stmt of a 'do' expression:
  forkIO $ lhello - lbracket - putStrLn

not_working_but_clean.hs:40:16:
No instance for (Stream d String (IO ()) (IO ()))
  arising from a use of `-' at not_working_but_clean.hs:40:16-47
Possible fix:
  add an instance declaration for (Stream d String (IO ()) (IO ()))
In the second argument of `($)', namely
`lhello - lbracket - putStrLn'
In a stmt of a 'do' expression:
  forkIO $ lhello - lbracket - putStrLn
In the expression:
do { forkIO $ (bracket $ hello) - putStrLn;
 forkIO $ lhello - lbracket - putStrLn;
 forkIO $ bracket hello - putStrLn;
 forkIO $ lbracket lhello - putStrLn;
    }



not_working_but_clean.hs:
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances,
TypeSynonymInstances, OverlappingInstances #-}
{-# OPTIONS_GHC #-}

module Main (
main
)
where

import Control.Concurrent (forkIO, MVar, newEmptyMVar, putMVar,
takeMVar, ThreadId, threadDelay)
import Control.Monad (forever, liftM)

class Stream a b c d where
(-) :: a - (b - c) - d

instance Stream (IO d) d (IO c) (IO c) where
f - g = f = g

instance Stream d d (IO c) (IO c) where
f - g = g f

instance Stream d d c c where
x - y = y $ x

-- This simply wraps a string in brackets.
bracket :: String - String
bracket x = ( ++ x ++ )

lbracket :: IO String - IO String
lbracket x = liftM bracket x

hello :: String
hello = Hello World!

lhello :: IO String
lhello = do return hello

main :: IO ()
main = do
   forkIO $ (bracket $ hello) - putStrLn
   forkIO $ lhello - lbracket - putStrLn
   forkIO $ bracket hello - putStrLn
   forkIO $ lbracket lhello - putStrLn
   threadDelay 1000 -- Sleep for at least 10 seconds before exiting.



working_but_ugly.hs:
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances,
TypeSynonymInstances, OverlappingInstances #-}
{-# OPTIONS_GHC #-}

module Main (
main
)
where

import Control.Concurrent (forkIO, MVar, newEmptyMVar, putMVar,
takeMVar, ThreadId, threadDelay)
import Control.Monad (forever, liftM)

class Stream a b c d where
(-) :: a - (b - c) - d

instance Stream (IO d) d (IO c) (IO c) where
f - g = f = g

instance Stream d d (IO c) (IO c) where
f - g = g f

instance Stream d d c c where
x - y = y $ x

x - y = y $ x

-- This simply wraps a string in brackets.
bracket :: String - String
bracket x = ( ++ x ++ )

lbracket :: IO String - IO String
lbracket x = liftM bracket x

hello :: String
hello = Hello World!

lhello :: IO String
lhello = do return hello

main :: IO ()
main = do
   forkIO $ (bracket $ hello) - putStrLn
   forkIO $ lhello - lbracket - putStrLn
   forkIO $ bracket hello - putStrLn
   forkIO $ lbracket lhello - putStrLn
   threadDelay 1000 -- Sleep for at least 10 seconds before exiting.

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


Re: [Haskell-cafe] Type Classes in Haskell - how can I make GHC make a choice of types, when the type chosen doesn't matter?

2011-04-14 Thread Neil Brown

On 14/04/11 13:00, Chris Dew wrote:

class Stream a b c d where
 (-) :: a -  (b -  c) -  d

instance Stream (IO d) d (IO c) (IO c) where
 f -  g = f= g

instance Stream d d (IO c) (IO c) where
 f -  g = g f

instance Stream d d c c where
 x -  y = y $ x



I notice that in all your instances, the last two types are the same.  
So do you need the final type parameter?  Could you not make it:


class Stream a b c where
  (-) :: a - (b - c) - c

I quickly tried this, and it fixes the errors you were getting.  If that 
doesn't hold for all instances you have in mind, then you may want to 
use functional dependencies or type families to specify a relationship 
between the types.


Thanks,

Neil.


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


Re: [Haskell-cafe] Type Classes in Haskell - how can I make GHC make a choice of types, when the type chosen doesn't matter?

2011-04-14 Thread Stephen Tetley
Hi Chris

What does the Stream class *do* though?

class Stream a b c d where
(-) :: a -  (b -  c) -  d

Even with Neil's change its still quite unusual:

class Stream a b c where
 (-) :: a - (b - c) - c

In the first formulation there is an input of type a, a function (b -
c) and a result of a completely different type d.

In Neil's class the function relates to the type of the answer but not
to the input.

The difficult type classes in Haskell - Applicative, Monad, and
Arrows / Category - are related to some degree to fairly standard
combinators on functions. But they generalize the combinators to
operate on other types than the function type (-). As there isn't a
relation between input and output, I don't quite see how the Stream
type could start as a combinator.

Best wishes

Stephen

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


Re: [Haskell-cafe] Type Classes in Haskell - how can I make GHC make a choice of types, when the type chosen doesn't matter?

2011-04-14 Thread Chris Dew
@Neil Brown - That did it.  It's not the ideal solution, as all -
are 'coerced' into being 'IO x' (if the rightmost term is an 'IO x'.
But it'll do for the time being.

Many thanks,

Chris.

On 14 April 2011 13:50, Neil Brown nc...@kent.ac.uk wrote:
 On 14/04/11 13:00, Chris Dew wrote:

 class Stream a b c d where
     (-) :: a -  (b -  c) -  d

 instance Stream (IO d) d (IO c) (IO c) where
     f -  g = f= g

 instance Stream d d (IO c) (IO c) where
     f -  g = g f

 instance Stream d d c c where
     x -  y = y $ x


 I notice that in all your instances, the last two types are the same.  So do
 you need the final type parameter?  Could you not make it:

 class Stream a b c where
  (-) :: a - (b - c) - c

 I quickly tried this, and it fixes the errors you were getting.  If that
 doesn't hold for all instances you have in mind, then you may want to use
 functional dependencies or type families to specify a relationship between
 the types.

 Thanks,

 Neil.



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


Re: [Haskell-cafe] Type Classes in Haskell - how can I make GHC make a choice of types, when the type chosen doesn't matter?

2011-04-14 Thread Chris Dew
@Stephen Tetley - The stream class exists simply to allow for the
creation of a - operator which can be used to 'Stream' data through
multiple pure and IO functions, on the way to some form of output.
It's probably not a great idea, as there are more idiomatic solutions
in Haskell - I'm sure someone will mention arrows.

I want the result of (-) to be what the following function requires,
either an 'a' or and 'IO a'.  This is too unconstrained if the
following function is flexible in it's input.  (e.g. another
application of (-)).   Hence my original problem.

a and b have are related, but not in a way I know how to express in
Haskell.  They are constrained to: a == b || IO a == b || a == IO b. c
and d have a similar constraint.

Could you suggest how these constraints could be expressed in the
Haskell type system?

Thanks,

Chris.

On 14 April 2011 14:28, Stephen Tetley stephen.tet...@gmail.com wrote:
 Hi Chris

 What does the Stream class *do* though?

 class Stream a b c d where
    (-) :: a -  (b -  c) -  d

 Even with Neil's change its still quite unusual:

 class Stream a b c where
  (-) :: a - (b - c) - c

 In the first formulation there is an input of type a, a function (b -
 c) and a result of a completely different type d.

 In Neil's class the function relates to the type of the answer but not
 to the input.

 The difficult type classes in Haskell - Applicative, Monad, and
 Arrows / Category - are related to some degree to fairly standard
 combinators on functions. But they generalize the combinators to
 operate on other types than the function type (-). As there isn't a
 relation between input and output, I don't quite see how the Stream
 type could start as a combinator.

 Best wishes

 Stephen

 ___
 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 Classes in Haskell - how can I make GHC make a choice of types, when the type chosen doesn't matter?

2011-04-14 Thread Stephen Tetley
On 14 April 2011 20:35, Chris Dew cms...@gmail.com wrote:

 Could you suggest how these constraints could be expressed in the
 Haskell type system?


Hi Chris

I'm afriad I'd have to decline - generally in Haskell implicit
lifters are problematic, so it isn't something I'd be looking to
solve.


There was a thread on Haskell Cafe about them last November called
Making monadic code more concise, that you might find interesting -
especially Oleg Kiselyov's comments:

http://www.haskell.org/pipermail/haskell-cafe/2010-November/086445.html

Best wishes

Stephen

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


Re: [Haskell-cafe] Type Classes in Haskell - how can I make GHC make a choice of types, when the type chosen doesn't matter?

2011-04-14 Thread Chris Dew
Thanks, that link's very relevant to what I'm trying.  For the time
being I'll accept a partial solution where the last two types are now
the same, and try to improve it when my knowledge of Haskell improves.

I really want (hello - bracket) in (hello - bracket -
putStrLn) to have a type of String.  Using the partial solution
which Neil Brown proposed, the code will work, but (hello -
bracket) will have a type of IO String which *seems* like it will be
less efficient.

All the best,

Chris.

On 14 April 2011 21:22, Stephen Tetley stephen.tet...@gmail.com wrote:
 On 14 April 2011 20:35, Chris Dew cms...@gmail.com wrote:

 Could you suggest how these constraints could be expressed in the
 Haskell type system?


 Hi Chris

 I'm afriad I'd have to decline - generally in Haskell implicit
 lifters are problematic, so it isn't something I'd be looking to
 solve.


 There was a thread on Haskell Cafe about them last November called
 Making monadic code more concise, that you might find interesting -
 especially Oleg Kiselyov's comments:

 http://www.haskell.org/pipermail/haskell-cafe/2010-November/086445.html

 Best wishes

 Stephen

 ___
 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