[Haskell-cafe] Template Haskell.

2006-11-10 Thread [EMAIL PROTECTED]

Why doesn't reify return function body?

reify (mkName somefunction) for a function defined in the same module 
returns constructor VarI (of data type Info) that does not contain 
function declaration in (Maybe Dec) part.


What actions should I perform to get a function body with patterns, 
expressions and all that?



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


Re: [Haskell-cafe] Re: non-total operator precedence order (was:Fractional/negative fixity?)

2006-11-10 Thread Henning Thielemann

On Fri, 10 Nov 2006, Benjamin Franksen wrote:

 Although one could view this as a bug in the offending module it makes
 me somewhat uneasy that one additional import can have such a drastic
 effect on the code in a module /even if you don't use anything from that
 module/.

It's the same as with instance declarations, isn't it? I don't want to
defend the problems arising with todays anonymous instance declarations,
but I think a simple error report is better than trying to solve the
problem automatically and thus hide it from the programmer.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell Quiz Solution - Haskell Newbie Requesting Review

2006-11-10 Thread Justin Bailey

On 11/9/06, Brandon Moore [EMAIL PROTECTED] wrote:

Looks nice, especially if you're just getting started.

The overall structure looks good, I've just made a bunch of
little changes to the details. Mostly I found repeated patterns
to replace with library functions or extract as helper functions.


Thanks very much! I really appreciate you taking the time to look
through this code and perform the refactoring you did. Now, I hope you
don't mind me asking a lot of questions about it :)



Getting a little fancier, defining the fold over your expression type
captures the recursion pattern in eval and generate. It's fairly
handy for defining constant folding too, if you want that.


Do you have any tips for recognizing these patterns? Its still hard
for me to see them. Is there a general way to think of them? Comparing
the two code pieces, I can see how the structure of the recursion was
similar, but not the same. Is there a pattern for which pieces are
common and which are unique? For example, I can think of foldl as
folding a function over a list, with a given base case. Is there
something similar for thinking about recursion?


I wonder, what's the programming equivalent of a black hole?


To stretch the analogy to the breaking point, what about virtual
particles and Hawking radiation? And what does the event horizon look
like? LOL.


foldExpression val stmt = f
  where f (Val n) = val n
f (Statement op l r) = stmt op (f l) (f r)


This is great. It took me a while to realize that 'val' is a function
for translating values, and 'stmt' is for translating statements.
Really cool!


   number  = fmap (Val . read) (many1 digit) ? number


How is this working? I read it as 'map (Val (read)) (string)' ('map',
because its applied the List version of fmap).  Is that correct? How
does 'read' get the string argument? I would assume read is evaluated,
and then its result and the string would be passed as arguments to
Val. Clearly that's not right - can you correct me?



-- Takes an AST and turns it into a byte code list
generate = foldExpression generateVal (\op l r - l ++ r ++ generateOp op)
where generateVal n = if abs n  2^(2*8)-1
 then [CONST n]
 else [LCONST n]
  generateOp op = case op of
  Plus - [ADD]
  Minus - [SUB]
  Mult - [MUL]
  Div - [DIV]
  Mod - [MOD]
  Pow - [POW]


This is what clued me into how foldExpression was working. I
especially like how the lambda works to generate the correct bytecode
for the operator, and how l and r are already recursively
evaluated by the f function returned from foldExpression. I just
wonder how I'll ever spot similar patterns ;)


eval_tests = suiteResults (checkResult (eval . parse))

generate_tests = suiteResults (showResult (generate . parse))

interpret_tests = suiteResults (checkResult (fromIntegral . interpret []
. compile))


Above are all more examples of partial functions and function
composition. I understand the first concept, but function composition
escapes me somehow. What are the rules for partial functions getting
arguments when they are eventually supplied? For example, in
'interpret_tests' I can see that the function (fromIntegral .
interpret . compile) gets applied to the statement via 'checkResult',
but it seems to me that fromIntegral should get teh argument (i.e.
because I read it is '(fromIntegral (interpret (compile)))'). Clearly,
I'm wrong. Do arguments get consumed by partially applied functions
regardless of their depth?

Thanks again for your time looking at this code and maybe even
answering these questions. I've already learned a ton just seeing the
refactor.

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


[Haskell-cafe] Re: Re: non-total operator precedence order (was:Fractional/negative fixity?)

2006-11-10 Thread Benjamin Franksen
Henning Thielemann wrote:
 On Fri, 10 Nov 2006, Benjamin Franksen wrote:
 Although one could view this as a bug in the offending module it makes
 me somewhat uneasy that one additional import can have such a drastic
 effect on the code in a module /even if you don't use anything from that
 module/.
 
 It's the same as with instance declarations, isn't it? I don't want to
 defend the problems arising with todays anonymous instance declarations,

Right. However, with instances I can imagine solutions that avoid naming
them, that is, I could imagine to write something like

  select instance C T1 T2 ... Tn from module M

or

  import M hiding (instance C T1 T2 ... Tn, )

Such a feature could prove extremely useful in practice.

Disclaimer: I am almost sure that there is something I have overlooked that
makes such a simple solution impossible, otherwise it would have been
proposed and implemented long ago...

 but I think a simple error report is better than trying to solve the
 problem automatically and thus hide it from the programmer.

I agree 100% that error is better than silently change (fix) semantics.
However the fact that there is currently no way to manually resolve
instance clashes coming from imported (library) modules is really
problematic, IMHO. I think the only reason this hasn't yet produced major
upheaval is that Haskell community is still quite small so library writers
can still have most of the field in their eyeview, so to speak. If Haskell
libraries were written and used in multitudes such as seen e.g. on CPAN,
then the probability of conflicting instances would be a lot greater, in
turn causing many libraries to be incompatible with each other. IMHO, this
must be fixed before Haskell reaches even a fraction of that level of
popularity.

Non-total precedence order will give us more potential incompatibilities
that the programmer has no way of resolving satisfactorily, so I'd rather
stick with the current system, however limited. (And yes, I /have/ changed
my mind on this. I'd /love/ to be convinced that this is not really going
to be a problem but I am not and I hate it.)

Cheers
Ben

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


Re: [Haskell-cafe] Haskell Quiz Solution - Haskell Newbie Requesting Review

2006-11-10 Thread Dougal Stanton
Quoth Justin Bailey, nevermore,
 Above are all more examples of partial functions and function
 composition. I understand the first concept, but function composition
 escapes me somehow. What are the rules for partial functions getting
 arguments when they are eventually supplied? For example, in
 'interpret_tests' I can see that the function (fromIntegral .
 interpret . compile) gets applied to the statement via 'checkResult',
 but it seems to me that fromIntegral should get teh argument (i.e.
 because I read it is '(fromIntegral (interpret (compile)))'). Clearly,
 I'm wrong. Do arguments get consumed by partially applied functions
 regardless of their depth?

The operators (.) and ($) are used to join functions together, but in
slightly different ways. Taking your example above, we would use ($) to
obtain nested functions:

 fromIntegral $ interpret $ compile ==
 fromIntegral (interpret (compile))

As you noted that doesn't seem right --- how does compile capture its
input? Well, the (.) operator is slightly different. It captures
variables and passes them into the 'innermost' function, a bit like
this:

 f . g = \x - f (g x)

In this respect you can treat 'f . g' as a single functional entity
which takes the same number and type of functions as 'g' and return
whatever type 'f' returns. As in the type signature:

 (.) :: (b - c) - (a - b) - a - c

If it helps, think of something like 

 map (f . g . h) xs

as identical to the following (although obviously much more succinct and
orders of magnitude clearer)

 map (f') xs
   where f' = \x - f (g (h x))

Cheers,

D.

-- 
Dougal Stanton [EMAIL PROTECTED]
http://brokenhut.livejournal.com
Word attachments considered harmful.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell Quiz Solution - Haskell Newbie Requesting Review

2006-11-10 Thread Justin Bailey

On 11/10/06, Dougal Stanton [EMAIL PROTECTED] wrote:


As you noted that doesn't seem right --- how does compile capture its
input? Well, the (.) operator is slightly different. It captures
variables and passes them into the 'innermost' function, a bit like
this:


That is a great explanation. I've got a much better understanding of
the operator now - thanks very much!

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


Re: [Haskell-cafe] Re: non-total operator precedence order (was:Fractional/negative fixity?)

2006-11-10 Thread Jan-Willem Maessen


On Nov 9, 2006, at 7:16 PM, Benjamin Franksen wrote:


Carl Witty wrote:


On Thu, 2006-11-09 at 22:20 +0100, Benjamin Franksen wrote:

Henning Thielemann wrote:
 Maybe making fixity declarations like type class instance  
declarations

 is
good.


I thought so too at first but, having thought about it for a  
while, I now

see this will cause /major/ problems. The precedence relations as
declared explicitly by the programmer must form a DAG, with the  
vertices
being the operator classes with equal precedence. There are two  
ways you
can break the DAG: by introducing a 'smaller' or 'larger'  
relation when
another module has already declared them to have equal precedence  
(resp.

the other way around); or by introducing a cycle. Both can be caused
simply by importing yet another module. I think it would be  
unacceptable
not to provide some way for the programmer to resolve such  
conflicts.


[ ... possibilities for resolving conflicts omitted ... ]

Another possibility is:

If you have operators op1 and op2, where the compiler sees  
conflicting
requirements for the precedence of op1 and op2, then they are  
treated as

non-associative relative to each other: the expression
  a op1 b op2 c
is illegal, and the programmer must instead write
  (a op1 b) op2 c
or
  a op1 (b op2 c)


It's a possibility. However, I fear that such conflicting  
precedences might
not come in nice little isolated pairs. For instance, each operator  
that is
in the same precedence class as op1 (i.e. has been declared as  
having equal
precedence) will now be 'incompatible' with any that is in the same  
class

as op2, right?


Well, look at it from the perspective of the reader.  Does the reader  
of your code know beyond a shadow of a doubt what the intended  
precedence will be in these cases?  If not, there should be  
parentheses there---quite apart from what the parser may or may not  
permit you to do.  If the parser can't figure it out, you can bet  
your readers will have trouble as well.



It gets worse if the conflict creates a cycle in a chain of
large operator classes. Thus one single bad declaration can tear a  
gaping

hole into an otherwise perfectly nice and consistent DAG of precedence
order relations, possibly invalidating a whole lot of code.


Requiring parenthesization solves these problems in a stroke.

-Jan-Willem Maessen
 who can't reliably parenthesize the C expression   a==b  34 | 17
 (yes, the horrific whitespace is deliberate!)



Although one
could view this as a bug in the offending module it makes me somewhat
uneasy that one additional import can have such a drastic effect on  
the

code in a module /even if you don't use anything from that module/.

Ben

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




smime.p7s
Description: S/MIME cryptographic signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Template Haskell.

2006-11-10 Thread Jason Dagit

On 11/10/06, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:

Why doesn't reify return function body?

reify (mkName somefunction) for a function defined in the same module
returns constructor VarI (of data type Info) that does not contain
function declaration in (Maybe Dec) part.

What actions should I perform to get a function body with patterns,
expressions and all that?


I'm not sure, but when faced a similar problem I used the Haskell98
parser to get at the AST of the functions.  In my case the functions
were defined in a different module so TH definitely couldn't get at
the internals.  The details of what I did are here:
http://blog.codersbase.com/2006/09/01/simple-unit-testing-in-haskell/

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


[Haskell-cafe] Re: Re: non-total operator precedence order (was:Fractional/negative fixity?)

2006-11-10 Thread Benjamin Franksen
Jan-Willem Maessen wrote:
 On Nov 9, 2006, at 7:16 PM, Benjamin Franksen wrote:
 Carl Witty wrote:
 If you have operators op1 and op2, where the compiler sees
 conflicting
 requirements for the precedence of op1 and op2, then they are
 treated as
 non-associative relative to each other: the expression
   a op1 b op2 c
 is illegal, and the programmer must instead write
   (a op1 b) op2 c
 or
   a op1 (b op2 c)

 It's a possibility. However, I fear that such conflicting
 precedences might
 not come in nice little isolated pairs. For instance, each operator
 that is
 in the same precedence class as op1 (i.e. has been declared as
 having equal
 precedence) will now be 'incompatible' with any that is in the same
 class
 as op2, right?
 
 Well, look at it from the perspective of the reader.  Does the reader
 of your code know beyond a shadow of a doubt what the intended
 precedence will be in these cases?  If not, there should be
 parentheses there---quite apart from what the parser may or may not
 permit you to do.  If the parser can't figure it out, you can bet
 your readers will have trouble as well.

Imagine op1=(+), op2=(*). Would you think that it is acceptable if any wild
module can come along and destroy the relative precedence order everyone
espects to hold between those two?

For this to happen it would be enough if M1 says

  prec (+) = prec (+)
  prec (*) = prec (*)

while M2 says

  prec () = prec (*)

and M3

  prec () = prec (+)

All modules M1, M2, and M3, when viewed independently, and even when viewed
in pairwise combination, don't do anything bad. It is only the combination
of all three that cause the expression

  3 + 4 * 3

to become a syntax error!

Ben

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


[Haskell-cafe] Re: Fractional/negative fixity?

2006-11-10 Thread Ben Rudiak-Gould
I'm surprised that no one has mentioned showsPrec and readsPrec. Anything 
more complicated than negative fixities would require their interfaces to be 
changed.


-- Ben

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


Re: [Haskell-cafe] Re: Livecoding music in Haskell

2006-11-10 Thread Henning Thielemann

On Wed, 8 Nov 2006, Rohan Drape wrote:

 import Sound.SC3
 import Control.Concurrent (forkIO)
 
 ping f a = out 0 (sinOsc AR f 0 * e)
  where c = EnvNum (-4.0)
e = envGen KR 1 a 0 1 removeSynth (envPerc 0.1 0.6 1 [c,c])
 
 latency = 0.01
 
 bundle t m = OscB (t + latency) m
 
 pinger = do now - utc
 at (fromIntegral (ceiling now)) f
 where f t = do fd - sc
send' fd (bundle t [s_new ping (-1) AddToTail 1])
putStrLn Sending ping
return 1.0
 
 main = do fd - sc
   putStrLn Sending Ping Instrument
   sync' fd (d_recv' ping (ping 440 0.1))
   putStrLn Resetting scsynth
   reset fd
   putStrLn Starting schedule thread
   forkIO pinger
   putStrLn Delaying main thread
   pause 30
   putStrLn End of delay, exiting

When I run this, then SuperCollider emits the error
 FAILURE ew Command not found

Do you use some new feature? (I could even not tell you my SuperCollider 
version, 'scsynth --version', 'scsynth -v' and the like, don't tell me. 
:-(

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


Re: [Haskell-cafe] Great language shootout: reloaded

2006-11-10 Thread Henk-Jan van Tuyl


On Fri, 10 Nov 2006 01:44:15 +0100, Donald Bruce Stewart
[EMAIL PROTECTED] wrote:


So back in January we had lots of fun tuning up Haskell code for the
Great Language Shootout[1]. We did quite well at the time, at one point
ranking overall first[2]. [...]


Haskell suddenly dropped several places in the overall socre, when the
size measurement changed from line-count to number-of-bytes after
gzipping. Maybe it's worth it, to study why this is; Haskell programs are
often much more compact then programs in other languages, but after
gzipping, other languages do much better. One reason I can think of, is
that for very short programs, the import statements weigh heavily.

--
Met vriendelijke groet,
Henk-Jan van Tuyl


--
http://Van.Tuyl.eu/
--

Using Opera's revolutionary e-mail client:
https://secure.bmtmicro.com/opera/buy-opera.html?AID=789433

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


Re: [Haskell-cafe] Great language shootout: reloaded

2006-11-10 Thread Sebastian Sylvan

On 11/10/06, Henk-Jan van Tuyl [EMAIL PROTECTED] wrote:


On Fri, 10 Nov 2006 01:44:15 +0100, Donald Bruce Stewart
[EMAIL PROTECTED] wrote:

 So back in January we had lots of fun tuning up Haskell code for the
 Great Language Shootout[1]. We did quite well at the time, at one point
 ranking overall first[2]. [...]

Haskell suddenly dropped several places in the overall socre, when the
size measurement changed from line-count to number-of-bytes after
gzipping. Maybe it's worth it, to study why this is; Haskell programs are
often much more compact then programs in other languages, but after
gzipping, other languages do much better. One reason I can think of, is
that for very short programs, the import statements weigh heavily.


I think the main factor is that languages with large syntactic
redundancy get that compressed away. I.e if you write:

MyVeryLongAndConvlutedClassName MyVeryLargeAndConvulutedObject new
MyVeryLongAndConvolutedClassName( somOtherLongVariableName );

Or something like that, that makes the code clumpsy and difficult to
read, but it won't affect the gzipped byte count very much.
Their current way of meassuring is pretty much pointless, since the
main thing the gzipping does is remove the impact of clunky syntax.
Meassuring lines of code is certainly not perfect, but IMO it's a lot
more useful as a metric then gzipped bytes.

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


Re: [Haskell-cafe] Great language shootout: reloaded

2006-11-10 Thread Tony Morris

Sebastian Sylvan wrote:

On 11/10/06, Henk-Jan van Tuyl [EMAIL PROTECTED] wrote:


On Fri, 10 Nov 2006 01:44:15 +0100, Donald Bruce Stewart
[EMAIL PROTECTED] wrote:

 So back in January we had lots of fun tuning up Haskell code for the
 Great Language Shootout[1]. We did quite well at the time, at one 
point

 ranking overall first[2]. [...]

Haskell suddenly dropped several places in the overall socre, when the
size measurement changed from line-count to number-of-bytes after
gzipping. Maybe it's worth it, to study why this is; Haskell programs 
are

often much more compact then programs in other languages, but after
gzipping, other languages do much better. One reason I can think of, is
that for very short programs, the import statements weigh heavily.


I think the main factor is that languages with large syntactic
redundancy get that compressed away. I.e if you write:

MyVeryLongAndConvlutedClassName MyVeryLargeAndConvulutedObject new
MyVeryLongAndConvolutedClassName( somOtherLongVariableName );

Or something like that, that makes the code clumpsy and difficult to
read, but it won't affect the gzipped byte count very much.
Their current way of meassuring is pretty much pointless, since the
main thing the gzipping does is remove the impact of clunky syntax.
Meassuring lines of code is certainly not perfect, but IMO it's a lot
more useful as a metric then gzipped bytes.

It may not be useful on its own, but it is not entirely meaningless. By 
using a lossless compression algorithm, you might infer some meaning 
about the code. Where it fails though is that if the algorithm was ideal 
(preferring low space at the expense of time), then the resulting bytes 
should be exactly the same. If it is not, then the samples did not do 
the exact same thing in the first place and so are not comparable! So, 
assuming gzip is ideal, then it is considered a win by having a higher 
compressed output!


It is not that the method is pointless, it is the extrapolation and 
interpretation of the results. You could argue that the gzipped output 
is just the same thing written in a new programming language - of 
course, it is not very readable (at least not to me since I do not have 
gunzip installed in my brain, but I do have a Haskell interpreter of 
some sort). Achieving minimum expressiveness at the source code level is 
entirely subjective and is based on an interpretation by the observer. 
Using gzip attempts to minimise this subjectivity - whether or not it is 
successful is not entirely decidable, but it is at least better. 
Unfortunately, the results have been misinterpreted.


Just smile and nod, I do :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Great language shootout: reloaded

2006-11-10 Thread Isaac Gouy
 On 11/10/06, Henk-Jan van Tuyl hjgtuyl at chello.nl wrote:

 Haskell suddenly dropped several places in the overall socre, when
the
 size measurement changed from line-count to number-of-bytes after
 gzipping. Maybe it's worth it, to study why this is; Haskell
programs 
 are
 often much more compact then programs in other languages, but after
 gzipping, other languages do much better. One reason I can think of,
is
 that for very short programs, the import statements weigh heavily.


Before this gets out-of-hand, my memory is certainly fallible but as I
recall Haskell /did not/ drop several places because size measurement
changed from line-count to gzip byte-count.


1) Check the webpage that Don Stewart cached and note the values for
the memory use and code-lines multipliers, and note the values for the
benchmark weights
   http://www.cse.unsw.edu.au/~dons/data/haskell_1.html
 
Now go to the computer language shootout website and note the
multipliers and benchmark weights.


2) Some Haskell programs were pushed into 'interesting alternative
implementations' because they'd strayed so far from the spirit of the
benchmark. (It takes a while for people to notice and complain, but
eventually they do.)



 

Do you Yahoo!?
Everyone is raving about the all-new Yahoo! Mail beta.
http://new.mail.yahoo.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Great language shootout: reloaded

2006-11-10 Thread Donald Bruce Stewart
igouy2:
  On 11/10/06, Henk-Jan van Tuyl hjgtuyl at chello.nl wrote:
 
  Haskell suddenly dropped several places in the overall socre, when
 the
  size measurement changed from line-count to number-of-bytes after
  gzipping. Maybe it's worth it, to study why this is; Haskell
 programs 
  are
  often much more compact then programs in other languages, but after
  gzipping, other languages do much better. One reason I can think of,
 is
  that for very short programs, the import statements weigh heavily.
 
 
 Before this gets out-of-hand, my memory is certainly fallible but as I
 recall Haskell /did not/ drop several places because size measurement
 changed from line-count to gzip byte-count.
 
 
 1) Check the webpage that Don Stewart cached and note the values for
 the memory use and code-lines multipliers, and note the values for the
 benchmark weights
http://www.cse.unsw.edu.au/~dons/data/haskell_1.html
  
 Now go to the computer language shootout website and note the
 multipliers and benchmark weights.
 
 
 2) Some Haskell programs were pushed into 'interesting alternative
 implementations' because they'd strayed so far from the spirit of the
 benchmark. (It takes a while for people to notice and complain, but
 eventually they do.)

I agree. Breaking the rules was mainly the reason for the drop. Entries
like chameneos and fasta. Also, the other language teams kept improving
things.  

Other language (perl, iirc) were affected far worse by the gzipping.
gzip is an interesting measurement, and it doesn't hurt Haskell too much
either way -- short Haskell programs stay short when compressed.

As a result, rewriting verbose entries to ByteString will probably be
much more useful :)

Btw, Isaac, are we going to have any new parallelism benchmarks? I'd
love to try out the SMP runtime ;)

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


Re: [Haskell-cafe] Re: Livecoding music in Haskell

2006-11-10 Thread Rohan Drape
 When I run this, then SuperCollider emits the error
  FAILURE ew Command not found
 Do you use some new feature? 

No, however you may need to run darcs update, there was an error in
the OSC bundle encoder that I located writing that example:

 Wed Nov  8 21:29:28 EST 2006  Rohan Drape [EMAIL PROTECTED]
   * Fix error in OSC bundle encoder

hence the sly reference to current repository in the post!

Regards,
Rohan

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


Re: [Haskell-cafe] Re: aggressiveness of functional dependencies

2006-11-10 Thread Nicolas Frisby

First off, thanks for the reply.

I am accustomed to GHC ignoring instance contexts as you mentioned.
It's the mostly part that I'm curious about: mostly implies there's
some phases that don't ignore context. Is that only the checking the
type of the method definitions and absolutely nothing else? So it
seems...

My project is rather committed to GHC, but could you elaborate on your
reference to Hugs being different?

Thanks again,
Nick

On 11/9/06, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:

Nicolas Frisby wrote:

  The inferred type for rite_t1 is
  rite_t1 :: (Iso (Either Char a) (Either f' g')) = () - Either f' g'
 
  Why isn't the inferred type of rite_t1 the same as the ascribed type
  of rite_t1'?
 
   rite_t1' :: Iso b b' = () - Either MyChar b'
   rite_t1' () = rite t1

I think GHC does not know whether the given instance declaration

   instance ... = Iso (Either a b) (Either a' b')

even applies to the special case of (a = Char) because it mostly ignores
the preconditions on the left side of (=). Hugs is much different.
Maybe  throwing away undecidable instances will drastically change things.

 Last post until a response I promise! Another demonstration:

 bar () = runIdentity . flip runStateT 0 $ return 'c'

 Inferred signature:
   bar :: (Monad (StateT s Identity), Num s) = () - (Char, s)

 Why not?
   bar :: Num s = () - (Char, s)

 I am not coming up with an s that could prevent (StateT s Identity)
 from being a monad. Is there one?

The same might go on for this case. By not looking at the preconditions
in the instance declaration

instance Monad m = Monad (StateT s m)

GHC concludes that (Monad (StateT s Identity)) might or might not hold
depending on s.

Regards,
apfelmus

___
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