Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: Visual Haskell prerelease 0.2

2006-12-02 Thread shelarcy
Good. That new .dll works, too.

Best Regards,

On Sat, 02 Dec 2006 16:13:01 +0900, Krasimir Angelov [EMAIL PROTECTED] wrote:
 Sorry. I was sleeping and I uploaded it to darcs.haskell.org instead
 to haskell.org. Try it now.

 On 12/2/06, shelarcy [EMAIL PROTECTED] wrote:
 On Sat, 02 Dec 2006 02:14:26 +0900, Krasimir Angelov [EMAIL PROTECTED] 
 wrote:
  The zip file is updated with .dll that is with stripped debug symbols
  but with --optdll-s as it is recommended. Could some one try whether
  it works? It is about two times smaller than the non stripped version.
 
http://www.haskell.org/visualhaskell/vs_haskell.zip

 Is this file updated one?
 I downloaded it from above url again. But file size is same.
 So, I checked hash. It noticed that current and previous files
 are same.

-- 
shelarcy shelarcycapella.freemail.ne.jp
http://page.freett.com/shelarcy/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Generate 50 random coordinates

2006-12-02 Thread apfelmus
Huazhi (Hank) Gong wrote:
 Hello,all
 
 My intention is to generate 50 random coordinates like (x,y).
 
 myrand :: Int
 myrand = randomRIO(1::Int, 100)
 
 rf=[(myrand, myrand) | a - [1..50]]
 
 My short program is like this. However, GHCI say that the return type of
 randomRIO is IO a while the function defined by me is Int. Since I only need
 a integral type as my cooridinate, could you tell me how to fix this?

Taral wrote:
 do
let myrand = randomRIO (1 :: Int, 100)
rf - replicateM 50 (liftM2 (,) myrand myrand) 

Jason Dagit wrote:
 When we look at the type of randomRIO we see:
 randomRIO :: forall a. (Random a) = (a, a) - IO a
 
 You're giving it a tuple of Int, so we can substitute Int for 'a' in
 that type signature:
 myrand :: IO Int
 

 rf=[(myrand, myrand) | a - [1..50]]
 
 Here you are creating a list of tuples.  We see from above that the
 type of the tuples would be (IO Int, IO Int), so rf :: [(IO Int, IO
 Int)].  This is because we have not run the IO action to generate the
 Int yet.

 My short program is like this. However, GHCI say that the return type of
 randomRIO is IO a while the function defined by me is Int. Since I only need
 a integral type as my cooridinate, could you tell me how to fix this?
 
 Your type signature tries to make a claim that myrand has type Int,
 but the compiler will disagree because of that pesky IO type. 

Dons wrote:
 Try initialising your random generator in 'main' , creating a list of
 infinite randoms, take the number you need, then feed that to the
 functions that need the list:
 
 import System.Random
 import Text.Printf
 import Data.Word
 
 main = do
 g - newStdGen  -- intialise a random generator
 let (a,b) = split g -- create two separate generators
 as = randoms a  -- one infinite list of randoms
 bs = randoms b  -- another
 rs = zip as bs  -- an infite list of pairs
 dump (take 50 rs)   -- take 50, and consume them


-- The IO --

Who rides so late through the bits and the bytes?
It's Haskell with his child Hank;
He has the boy type safe in his arm,
He holds him pure, he holds him warm.

My son, what makes you hide your face in fear? -
Father, don't you see the IO?
The IO with randomRIO? -
My son, it's a wisp of the outside world. -

You dear child, do come along with me!
Such lovely replicateMs I'll do with you;
Many colorful liftM2s are to be done,
My Taral does have many a golden suggestions!

My father, my father, and do you not hear
What the IO promises me so softly? -
Be quiet, stay quiet, my child;
I know he won't treat you good. -

Don't you come along with me, my fine boy?
My Jason shall do explain to you so nicely.
My Jason will do tutor you to understand 'return',
And he'll do help you and do show you and do guide you to =.

My father, my father, and do you not read over there
IO's minions in that dark post? -
My son, my son, I see it most definitely:
It's the imperative paradigm looking so grey.

I do love you; I'm charmed by your beautiful mind;
And if you're not willing, then I'll do use imperative force!
My father, my father, now he's grabbing hold of me!
IO has done, IO did do me harm! -

Haskell shudders, he rides swiftly,
He holds in his arms the moaning child.
He reaches Dons' stronghold with effort and urgency.
With the following code, the child will not fall:

   import System.Random

   randPairs :: (RandomGen g, Random a) = (a,a) - g - [(a,a)]
   randPairs range gen = zip as bs
 where  (a,b) = split gen  -- create two separate generators
as = randomRs range a  -- one infinite list of randoms
bs = randomRs range b  -- another

   seed   = 13561956 :: Int
   mygen  = mkStdGen seed

   coords :: [(Int,Int)]
   coords = take 50 $  -- 50 random coordinates derived
randPairs (1,100) mygen-- from the random seed above





Regards,
apfelmus

PS: As you may have guessed, any similarity with living people is either
randomRIO or accidental ... I hope that you accept my apologies for the
latter.

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


[Haskell-cafe] Strange type behavior in GHCi 6.4.2

2006-12-02 Thread Grady Lemoine

Hello,

I've been playing around with Dan Piponi's work on automatic
differentiation (from
http://sigfpe.blogspot.com/2005/07/automatic-differentiation.html and
http://sigfpe.blogspot.com/2006/09/practical-synthetic-differential.html)
and I'm getting some odd behavior with the inferred types of functions
in GHCi 6.4.2.  My test case is as follows:


data Dual a = D a a deriving (Show,Eq)



instance Num a = Num (Dual a) where
  fromInteger i = D (fromInteger i) 0
  (D a a')+(D b b') = D (a+b) (a'+b')
  (D a a')-(D b b') = D (a-b) (a'-b')
  (D a a')*(D b b') = D (a*b) (a*b'+a'*b)



evalDeriv f x = (v, v')
where D v v' = f (D x 1)



f x = x^3



f' = snd . (evalDeriv f)


When I load this in GHCi, I get:

*Main :t f
f :: (Num a) = a - a
*Main :t snd . (evalDeriv f)
snd . (evalDeriv f) :: (Num a, Num (Dual a)) = a - a
*Main :t f'
f' :: Integer - Integer

Why is the type of f' Integer - Integer, especially when the type of
the expression it's defined as is more general?  Is this something I'm
not understanding about Haskell, or is it more to do with GHC 6.4.2
specifically?

Any help appreciated,

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


Re: [Haskell-cafe] Strange type behavior in GHCi 6.4.2

2006-12-02 Thread Chris Kuklewicz
Grady Lemoine wrote:
 Hello,
 
 I've been playing around with Dan Piponi's work on automatic
 differentiation (from
 http://sigfpe.blogspot.com/2005/07/automatic-differentiation.html and
 http://sigfpe.blogspot.com/2006/09/practical-synthetic-differential.html)
 and I'm getting some odd behavior with the inferred types of functions
 in GHCi 6.4.2.  My test case is as follows:
 
 data Dual a = D a a deriving (Show,Eq)
 
 instance Num a = Num (Dual a) where
   fromInteger i = D (fromInteger i) 0
   (D a a')+(D b b') = D (a+b) (a'+b')
   (D a a')-(D b b') = D (a-b) (a'-b')
   (D a a')*(D b b') = D (a*b) (a*b'+a'*b)
 
 evalDeriv f x = (v, v')
 where D v v' = f (D x 1)
 
 f x = x^3
 
 f' = snd . (evalDeriv f)
 
 When I load this in GHCi, I get:
 
 *Main :t f
 f :: (Num a) = a - a
 *Main :t snd . (evalDeriv f)
 snd . (evalDeriv f) :: (Num a, Num (Dual a)) = a - a
 *Main :t f'
 f' :: Integer - Integer
 
 Why is the type of f' Integer - Integer, especially when the type of
 the expression it's defined as is more general?  Is this something I'm
 not understanding about Haskell, or is it more to do with GHC 6.4.2
 specifically?
 
 Any help appreciated,
 
 --Grady Lemoine

You have two different things making this error possible.  First there is the
default(Integer,Int) that Haskell implicitly provides.  Second, there is the
monomorphism restriction.

Try this:

 default ()
 
 data Dual a = D a a deriving (Show,Eq)
 
 instance Num a = Num (Dual a) where
   fromInteger i = D (fromInteger i) 0
   (D a a')+(D b b') = D (a+b) (a'+b')
   (D a a')-(D b b') = D (a-b) (a'-b')
   (D a a')*(D b b') = D (a*b) (a*b'+a'*b)
   abs _ = error no abs
   signum _ = error no signum
 
 evalDeriv f x = (v, v')
 where D v v' = f (D x 1)
 
 f x = x^(3::Int)
 
 f' :: (Num a) = a - a
 f' = snd . (evalDeriv f) 

I played with such things, as seen on the old wiki:
http://haskell.org/hawiki/ShortExamples_2fSymbolDifferentiation

-- 
Chris

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


Re: [Haskell-cafe] Strange type behavior in GHCi 6.4.2

2006-12-02 Thread Brian Hulley

Grady Lemoine wrote:

f x = x^3



f' = snd . (evalDeriv f)


When I load this in GHCi, I get:

*Main :t f
f :: (Num a) = a - a
*Main :t snd . (evalDeriv f)
snd . (evalDeriv f) :: (Num a, Num (Dual a)) = a - a
*Main :t f'
f' :: Integer - Integer

Why is the type of f' Integer - Integer, especially when the type of
the expression it's defined as is more general?  Is this something I'm
not understanding about Haskell, or is it more to do with GHC 6.4.2
specifically?


This is the monomorphism restriction, which basically says that any binding 
which just has a single variable on the left of the '=' is artificially 
forced to be monomorphic (unless you've given it an explicit type signature) 
eg:


   f = \x - x + 1-- Integer - Integer

whereas

   f x = x + 1-- Num a = a - a

The reason for this is that if you have something like:

   let x = e in (x,x)

you often expect the expression (e) to be evaluated at most once, and shared 
by the two components of the tuple. However if there were no monomorphism 
restriction, then (x) could be polymorphic hence (e) would have to be 
evaluated twice (once for each overloading, even if the result tuple is fed 
to another function which expects both elements to have the same type) which 
would make programs run slower than the programmer expected.


I couldn't find any page on the wiki about this, but there's lots of stuff 
scattered around on the web, and endless discussions in the Haskell mailing 
lists which make entertaining reading ;-)


(The MR is controversial - see 
http://hackage.haskell.org/trac/haskell-prime/wiki/MonomorphismRestriction 
for the latest on what might happen to it in future versions of Haskell.)


Brian.
--
http://www.metamilk.com 


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


Re: [Haskell-cafe] Functional GUI combinators for arbitrary graphs ofcomponents?

2006-12-02 Thread Paul Hudak
If you consider just Dags, I believe that this question is equivalent to 
asking what set of combinators will allow you to create an arbitrary 
composition of functions that allow sharing inputs and returning 
multiple results.  And I think that one answer to that is the set of 
combinators that make up the Arrow class.  If you want to include 
recursion (i.e. cycles), then you'd have to throw in ArrowLoop (although 
that might only provide a nested form of cycles).  It's in this sense 
that Fudgets is analogous to Fruit.


   -Paul


Brian Hulley wrote:

Brian Hulley wrote:

Anyway to get to my point, though all this sounds great, I'm
wondering how to construct an arbitrary graph of Fudgets just from a
fixed set of combinators, such that each Fudget (node in the graph)
is only mentioned once in the expression. To simplify the question,
assume we have the following data structure to describe the desired
graph:
   data LinkDesc a
   = Series a a
   | Broadcast a [a]
   | Merge [a] a

   type GraphDesc a = [LinkDesc a]


The above is more complicated than necessary. The problem can be 
captured by:


   type GraphDesc a = [(a,a)]

Brian.


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


Re: [Haskell-cafe] Re: Difficult memory leak in array processing

2006-12-02 Thread Donald Bruce Stewart
apfelmus:
 Duncan Coutts wrote:
  On Wed, 2006-11-29 at 20:27 +0100, [EMAIL PROTECTED] wrote:
  
  On the implementation level, lazy evaluation is in the way when
  crunching bytes.
  
  Something I rather enjoyed when hacking on the ByteString lib is finding
  that actually lazy evaluation is great when crunching bytes, though you
  do need to know exactly when to use it.
  
  Lazy ByteStrings rely on lazy evaluation of course. Demanding a lazy
  ByteString alternates between strictly filling in big chunks of data in
  memory with lazily suspending before producing the next chunk.
  
  As many people have observed before, FP optimisation is to a great
  extent about thinking more carefully about a better evaluation order for
  a computation and making some bits stricter and some bits lazier to get
  that better evaluation order.
 
 I completely agree. My statement was not well formulated, I actually
 meant that the overhead implied by lazy evaluation occurring at every
 single byte to be crunched is in the way. In this case, the cost is too
 high to pay off as the bytes are most likely consumed anyway. The
 detailed account keeping about every byte (is it _|_ or not?) is
 unnecessary for a (map) which invariably does look at every byte. The
 situation is already different for a (fold), though:
 
 any p = foldr (\x b - p x `or` b) False
 
 Here, the computation may stop at any position in the list.
 
 In a sense, lazy ByteStrings just reduce the cost of lazy evaluation /
 byte ratio by grouping bytes strictly. Bookkeeping becomes cheaper
 because one doesn't look up so often. Of course, with a stricter fold,
 (any) gets more costly. The aim is to make the former ratio smaller
 while not raising the latter too much. One may say that ByteString makes
 explicit what the Optimistic Haskell Compiler aimed to make implicit.

This is a very interesting insight. Indeed, it does act much this way.

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