Re: [Haskell-cafe] Ambiguous type variable - help!

2009-07-20 Thread phil


On 19 Jul 2009, at 21:18, Yitzchak Gale wrote:


Hi Phil,






I've concocted a very simple example to illustrate this (below) - but
it doesn't compile because ghc complains that my type is ambiguous  
arising

from my use of 'fromSeq'.


Notice that you have given two completely separate sets
of instructions of what to do depending on whether Int
or Double is selected. You have not given any indication
of how to choose between them, even at runtime. Of course,
the compiler doesn't care that your string constants Int and
Double happen also to be the names of types if unquoted.


I see now.  I'm passing fromSeq a SeqType, but it has no way
of knowing if I want to process it as an Int or a Double.
The only thing which is polymorphic is nextSeq as it must handle
the underlying state of Int and Double.

Your result function handles the general case and the typeclass
instances deal with the specialization depending on the state's type.

The printResult function takes in a SeqType and then parses (for  
want of

a better word) out the
underlying type of Int or Double.  It then calls results against the  
Int or Double which

in turn will invoke the correct version of nextSeq.


Thank you very much for explaining this!


Phil.



import Control.Monad.State -- Why Strict? Haskell is lazy by default.



Ahh, no reason for the Strict - in the large program I'm righting it  
is required
because otherwise I end up with almighty thunks.  But here it serves  
no purpose.


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


[Haskell-cafe] Ambiguous type variable - help!

2009-07-19 Thread phil

Hi,

I'm trying to work out how to handle a choice at runtime which  
determines what instance of a State monad should be used.  The choice  
will dictate the internal state of the monad so different  
implementations are needed for each.  I've concocted a very simple  
example to illustrate this (below) - but it doesn't compile because  
ghc complains that my type is ambiguous arising from my use of  
'fromSeq'.  I can kind-of see what the compiler is complaining about,  
I'm guessing because it is the internals of my type which dictate  
which state Monad to use and it can't know that?


Thinking about it I tried making SeqType an instance of Sequence  
class, but had no luck here.


I understand that haskell is static at compile time, so I'm looking  
for something like a template solution in C++ (rather than a virtual  
function style implementation).  I see there are libraries out their  
which do this, but I was wondering in my simple example if there was a  
way of doing this without writing a load of boilerplate code in main  
(this would get ugly very quickly if you had loads of choices).  If  
this is impossible does anyone have an example / advice of  
implementing simple template style code in Haskell?


Any help or suggestions would be really appreciated.

Many Thanks,

Phil.

Thus just implements a state Monad which counts up from 1 to 10, using  
either an Int or a Double depending on user choice.  It's pointless of  
course, but illustrates my point.


{-# LANGUAGE TypeSynonymInstances #-}

import Control.Monad.State.Strict

data SeqType = SeqDouble Double | SeqInt Int

class SequenceClass a where
  nextSeq :: State a Int
  fromSeq :: SeqType - a

instance SequenceClass Int where
  nextSeq = State $ \s - (s,s+1)
  fromSeq (SeqInt i) = i
  fromSeq _ = 0

instance SequenceClass Double where
  nextSeq = State $ \s - (truncate s,s+1.0)
  fromSeq (SeqDouble d) = d
  fromSeq _ = 0.0


chooser :: String - SeqType
chooser inStr | inStr == Double = SeqDouble 1.0
  | inStr == Int= SeqInt 1
  | otherwise = SeqInt 1

main :: IO()
main = do userInput - getLine
  let result = evalState (do replicateM 10 nextSeq) $ fromSeq  
$ chooser userInput

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


Re: [Haskell-cafe] Ambiguous type variable - help!

2009-07-19 Thread Yitzchak Gale
Hi Phil,

 I'm trying to work out how to handle a choice at runtime
 which determines what instance of a State monad should
 be used.

First of all, you should realize that you'll almost never want
to do something like that in Haskell.

In my opinion, if you're coming from an OO language, you
should ban yourself from defining Haskell classes or using
existential types until you are completely comfortable with
how different Haskell is from OO. You can get along fine
without them.

 I've concocted a very simple example to illustrate this (below) - but
 it doesn't compile because ghc complains that my type is ambiguous arising
 from my use of 'fromSeq'.

Notice that you have given two completely separate sets
of instructions of what to do depending on whether Int
or Double is selected. You have not given any indication
of how to choose between them, even at runtime. Of course,
the compiler doesn't care that your string constants Int and
Double happen also to be the names of types if unquoted.

The way you avoid boilerplate in Haskell in these kinds of
cases is by using polymorphism. Note that there could still
remain a small amount of boilerplate - you move the actual
hard work into a single polymorphic function, but then you
may still need to mention that function once for each type.
If that bothers you, there are more advanced tools to get
rid of that last bit of boilerplate, like Template Haskell or
Scrap Your Boilerplate.

Below is one way to fix up your example, with a few other minor
bits of polish.

Regards,
Yitz

import Control.Monad.State -- Why Strict? Haskell is lazy by default.

data SeqType = SeqInt Int | SeqDouble Double

class SequenceClass a where
 nextSeq :: State a Int

instance SequenceClass Int where
 nextSeq = State $ \s - (s, s + 1)

instance SequenceClass Double where
 nextSeq = State $ \s - (truncate s, s + 1)

chooser :: String - SeqType
chooser inStr | inStr == Double = SeqDouble 1
  | otherwise = SeqInt 1

-- Here is the polymorphism.
-- Make this a function so that we can move it
-- out of main.
result :: SequenceClass a = a - [Int]
result = evalState $ replicateM 10 nextSeq

-- Here is the only boilerplate needed
printResult :: SeqType - IO ()
printResult (SeqInt i)= print $ result i
printResult (SeqDouble x) = print $ result x

main :: IO()
main = do userInput - getLine
  printResult $ chooser userInput

-- or you could just say
-- main = getLine = printResult . chooser
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe