[Haskell-cafe] Fwd: [Haskell-beginners] RankNTypes + ConstraintKinds to use Either as a union

2013-10-09 Thread Thiago Negri
(from thread:
http://www.haskell.org/pipermail/beginners/2013-October/012703.html)

Why type inference can't resolve this code?

 {-# LANGUAGE RankNTypes, ConstraintKinds #-}

 bar :: (Num a, Num b) = (forall c. Num c = c - c) - Either a b -
Either a b
 bar f (Left a) = Left (f a)
 bar f (Right b) = Right (f b)

 bar' = bar (+ 2) -- This compiles ok

 foo :: (tc a, tc b) = (forall c. tc c = c - c) - Either a b - Either
a b
 foo f (Left a) = Left (f a)
 foo f (Right b) = Right (f b)

 foo' = foo (+ 2) -- This doesn't compile because foo' does not typecheck

 -- Kim-Ee pointed out that this works:
 type F tc a b =  (tc a, tc b) = (forall c. tc c = c - c) - Either a b
- Either a b
 foo' = (foo :: F Num a b) (+2)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Proposal: new function for lifting

2013-09-27 Thread Thiago Negri
Everybody is claiming that using lift is a bad thing.
So, I come to remedy this problem.

Stop lifting, start using shinny operators like this one:

(^$) :: Monad m = m a - (a - b - c) - m b - m c
(^$) = flip liftM2

Then you can do wonderful stuff and you will never read the four-letter
word in your code again:

\ Just 42 ^$(+)$ Nothing
Nothing
\ Just 10 ^$(+)$ Just 20
Just 30
\ let add = (+)
\ Just 30 ^$ add $ Just 12
Just 42
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Package compatibility (SemVer, PVP, ECT)

2013-09-12 Thread Thiago Negri
I've just read Semantic Versioning (SemVer) [1], Package Versioning Policy
(PVP) [2] and Eternal Compatibility in Theory (ECT) [3].

Is PVP the one that every package on Hackage should use?
SemVer seems to make more sense to me.

Also, ECT looks very promising, but it is dated back to 2005 and I didn't
see any package using it. Why?

If Cabal could map the package version number to the versioned module name,
there will be no need to uglify the client code. I mean, when I import
module A and define in dependencies a == 1.8.3, Cabal would map that to
module A_7 and bind that to the A I've imported. We would be locked in
with Cabal, but that seems to be a good tradeoff.

[1] http://semver.org
[2] http://www.haskell.org/haskellwiki/Pvp
[3]
http://www.haskell.org/haskellwiki/The_Monad.Reader/Issue2/EternalCompatibilityInTheory
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proposal: New syntax for Haskell

2013-09-10 Thread Thiago Negri
Gherkin is the language that Cucumber understands. It is a Business
Readable, Domain Specific Language that lets you describe software’s
behaviour without detailing how that behaviour is implemented. [1]

The example detailed how foldl is implemented.

Also, as it is intended to be a DSL for *business*, I think it has nothing
to do with Haskell (the *technology*), i.e. no need for a hs in the file
extension, just call it whatever.gherkin and pass it to a
Gherkin-interpreter or something.

[1] https://github.com/cucumber/cucumber/wiki/Gherkin
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proposal: New syntax for Haskell

2013-09-10 Thread Thiago Negri
I hope these jokes do not cause people to be afraid to post new ideas.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] GLFW not working in Cabal 1.18

2013-09-10 Thread Thiago Negri
The package GLFW is not building in Cabal 1.18.

Setup.hs [1] depends on `rawSystemStdInOut` [2] that changed signature
between 1.16 and 1.18.

Is this considered a public API of Cabal?


Cabal 1.16
rawSystemStdInOut
 :: Verbosity
 - FilePath
 - [String]
 - Maybe (String, Bool)
 - Bool
 - IO (String, String, ExitCode)


Cabal 1.18
rawSystemStdInOut
 :: Verbosity
 - FilePath
 - [String]
 - Maybe FilePath -- new arg
 - Maybe [(String, String)] -- new arg
 - Maybe (String, Bool)
 - Bool
 - IO (String, String, ExitCode)



Compilation output:

[1 of 1] Compiling Main (
/tmp/GLFW-0.5.1.0-4035/GLFW-0.5.1.0/Setup.hs,
/tmp/GLFW-0.5.1.0-4035/GLFW-0.5.1.0/dist/setup/Main.o )

/tmp/GLFW-0.5.1.0-4035/GLFW-0.5.1.0/Setup.hs:167:33:
Couldn't match expected type `IO (t0, t1, ExitCode)'
with actual type `Maybe (String, Bool)
  - Bool - IO (String, String, ExitCode)'
In the return type of a call of `rawSystemStdInOut'
Probable cause: `rawSystemStdInOut' is applied to too few arguments
In a stmt of a 'do' block:
  (out, err, exitCode) - rawSystemStdInOut
verbosity cc ([-c, path, -o, objPath]
++ flags) Nothing False
In the expression:
  do { hClose outHandle;
   hPutStr inHandle contents;
   hClose inHandle;
   (out, err, exitCode) - rawSystemStdInOut
 verbosity cc ([-c, path, ] ++
flags) Nothing False;
    }

/tmp/GLFW-0.5.1.0-4035/GLFW-0.5.1.0/Setup.hs:167:113:
Couldn't match expected type `Maybe [(String, String)]'
with actual type `Bool'
In the fifth argument of `rawSystemStdInOut', namely `False'
In a stmt of a 'do' block:
  (out, err, exitCode) - rawSystemStdInOut
verbosity cc ([-c, path, -o, objPath]
++ flags) Nothing False
In the expression:
  do { hClose outHandle;
   hPutStr inHandle contents;
   hClose inHandle;
   (out, err, exitCode) - rawSystemStdInOut
 verbosity cc ([-c, path, ] ++
flags) Nothing False;
    }
Failed to install GLFW-0.5.1.0


[1] http://code.haskell.org/GLFW/Setup.hs
[2]
https://github.com/haskell/cabal/blob/d16c307c33fb7af19d8f17a2ad8be4902a3af21e/Cabal/Distribution/Simple/Utils.hs#L454
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Tasty not compiling

2013-08-29 Thread Thiago Negri
I can't install tasty with cabal. Anyone with the same issue or a fix?

$ cabal install tasty
...
Test\Tasty\Core.hs:147:11: Not in scope: `witness'
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Lifting strictness to types

2013-08-22 Thread Thiago Negri
I've just read the post Destroying Performance with Strictness by Neil
Mitchell [1].

One of the comments from an Anonymous says:

How hard would it be to lift strictness annotations to type-level? E.g.
instead of
f :: Int - Int
f !x = x + 1
write
f :: !Int - Int
f x = x + 1
which would have the same effect. At least it would be transparent to the
developer using a particular function.
The problem I see with this approach is on type classes, as it would be
impossible to declare a type instance with strict implementation to a type
class that used lazy types.

Is this a real problem? Is it the only one?

[1]
http://neilmitchell.blogspot.ru/2013/08/destroying-performance-with-strictness.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lifting strictness to types

2013-08-22 Thread Thiago Negri
I think Scala has this optional laziness too.
The problem with default-strictness is that libraries that are built with
no laziness in mind turn up to be too strict.
Going from lazy to strict is possible in the client side, but the other way
is impossible.



2013/8/22 Tom Ellis tom-lists-haskell-cafe-2...@jaguarpaw.co.uk

 On Thu, Aug 22, 2013 at 12:51:24PM -0300, Thiago Negri wrote:
  How hard would it be to lift strictness annotations to type-level? E.g.
  instead of
  f :: Int - Int
  f !x = x + 1
  write
  f :: !Int - Int
  f x = x + 1
  which would have the same effect. At least it would be transparent to the
  developer using a particular function.

 See also the recent Reddit thread


 http://www.reddit.com/r/haskell/comments/1ksu0v/reasoning_about_space_leaks_with_space_invariants/cbsac5m

 where I and others considered the possibility of a strict language with
 explicit thunk datatype.  NB OCaml essentially already has this

 http://caml.inria.fr/pub/docs/manual-ocaml/libref/Lazy.html

 but I think Haskellers would do it better because we have a lot of
 experience with purity, laziness and monad and comonad transformers.

 Tom

 ___
 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] Applicative is like an Arrow

2013-08-16 Thread Thiago Negri
I just stumbled upon the Applicative term.
Arrows are quite difficult for me to understand at the moment.
I guess it needs time to digest.

But, as I understand so far, Applicative and Arrows looks like the same
thing.

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


Re: [Haskell-cafe] Applicative is like an Arrow

2013-08-16 Thread Thiago Negri
You just made my day.
I was trying to understand these things so hard and couldn't get it.
Your analogies were brilliant.

I'll read all links/papers posted here to get a deeper understanding of
these things.
I'll just skip dependently typed stuff for now, heh.

Thank you,
Thiago.



2013/8/16 Mathijs Kwik math...@bluescreen303.nl

 Thiago Negri evoh...@gmail.com writes:

  I just stumbled upon the Applicative term.
  Arrows are quite difficult for me to understand at the moment.
  I guess it needs time to digest.
 
  But, as I understand so far, Applicative and Arrows looks like the same
  thing.
 
  Please, enlight me.

 I would like to point out this paper:
 http://homepages.inf.ed.ac.uk/slindley/papers/idioms-arrows-monads.pdf

 In short: arrows are a bit more powerful than idioms (applicative) but a
 bit less than monads. However, power sometimes comes at a price.
 All 3 have to do with combining / sequencing effects, but they differ in
 subtle but important ways. Every idiom is an arrow and every arrow is a
 monad, but not the other way around.

 I will first give an overview of the differences, then try to explain
 what I mean... (my terminology might be a bit awkward/wrong)

 Idiom:
 Basic combining strategy: i (a - b) - i a - i b
 Sequencing: effects are applied in sequence
 values (stuff inside) are isolated
 Shape depends on values: no

 Arrow:
 Basic combining strategy: a b c - a c d - a b d
 Sequencing: effects are applied in sequence
 values are sequenced too
 values can see upstream results
 Shape depends on values: static choices only

 Monad:
 Basic combining strategy: m a - (a - m b) - m b
 Sequencing: effects are applied in sequence
 values are sequenced too
 values can see upstream results
 Shape depends on values: yes, fully dynamic


 Now, what do I mean by all this?
 Basically these 3 abstractions consist of 3 things:
 - effects
 - values
 - shape
 Effects can be things like carries state around(State), can
 fail(Maybe), multiple answers(List) and more. Values are the pure
 stuff inside, and what I call 'shape' is the general control flow of a
 computation.
 Furthermore, I visualize these abstractions by thinking of a factory
 hall with boxes (values), people (effects) and an assembly line
 (shape).


 Idioms are fully static: values cannot see/depend on each other or on
 the result of effects. Basically the computation is split into 2 phases:
 - effects+gather
 - apply gathered results
 example:
 pure (+) * Just 3 * Just 5
 The first phase just works through the parts (in sequence) and collects
 the (pure) contents. In this case (Maybe) this means looking for the
 Just constructor to continue, or halting on Nothing. The content inside
 is being treated like a black box. It is not made aware of the effects
 (whether or not Nothing was found somewhere) and it is not being
 examined to choose a different codepath.
 Then if everything worked out (no Nothings were found), the collected
 results are taken out of their black boxes and applied. In this phase
 these results (the +, the 3 and the 5) don't know anything about the
 effects that happened.

 In factory visualization: every part of the computation (stuff between
 *) is a person that will need to perform some task(effect) and deliver
 some result in a box. They will only start performing their task when
 they see a box passing by from the person upstream. They cannot look in
 that box or make decisions based on it or take it off. At the end of the
 line, some manager receives all the boxes and opens them to combine the
 results.

 This is fine for a whole lot of applications and has the advantage that
 the shape of the entire assembly line is clear even before starting
 it. This means (static) optimization can be performed and it's easy to
 reason about the program/costs. Garbage collection (sending workers
 home) is easier, because it's very clear what data is needed where and
 when. I will talk a bit more about these optimizations a bit further
 down. Of course this assembly line is not flexible enough for more
 advanced cases.

 Let's see an example of that(State):
 pure const * get * put 8
 This is a perfectly fine idiom, albeit not very useful.
 When run (with initial state 4) the first worker will package up a box
 with const and send it downstream. The second worker gets the seeded
 state from the state cupboard and put it in a box (4). When that box
 passes by worker 3, he will walk to the state cupboard and put 8 in
 it. Then to signal he's ready, he packs a box with (). At the end of the
 line, someone opens the boxes const 4 and (), which computes to
 just 4. So we end up with the answer 4 and an updated cupboard
 containing 8.

 Why is this not very useful? Well we would probably want to be able to
 put state in that depends on certain stuff we got out earlier, instead
 of just supplying a hard coded 8 that was known before starting the
 line. Unfortunately

Re: [Haskell-cafe] Handling exceptions or gracefully releasing resources

2013-01-30 Thread Thiago Negri
Felipe, I'm trying to use your Hipmunk package. :)
The resources I need to keep around are the objects used for the simulation.
Do you recomend using resourcet to handle this or something else?

Thanks.


2013/1/30 Felipe Almeida Lessa felipe.le...@gmail.com

 Everything that Johan Tibell said + you may be interested in the
 resourcet package [1] (which is used by conduit to handle resources).

 Cheers,

 [1] http://hackage.haskell.org/package/resourcet

 On Tue, Jan 29, 2013 at 8:59 PM, Thiago Negri evoh...@gmail.com wrote:
  `Control.Exception.bracket` is a nice function to acquire and release a
  resource in a small context.
 
  But, how should I handle resources that are hold for a long time?
 
  Should I put `Control.Exception.finally` on every single line of my
  finalizers?
  What exceptions may occur on an IO operation?
  Every IO function has the risk of throwing an exception?
 
  Thanks,
  Thiago.
 
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 



 --
 Felipe.

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


[Haskell-cafe] Handling exceptions or gracefully releasing resources

2013-01-29 Thread Thiago Negri
`Control.Exception.bracket` is a nice function to acquire and release a
resource in a small context.

But, how should I handle resources that are hold for a long time?

Should I put `Control.Exception.finally` on every single line of my
finalizers?
What exceptions may occur on an IO operation?
Every IO function has the risk of throwing an exception?

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


Re: [Haskell-cafe] Suggestiong for inter-thread communication

2013-01-26 Thread Thiago Negri
Do you need advice on what? I didn't understand your last phrase.
Em 26/01/2013 06:25, Erik de Castro Lopo mle...@mega-nerd.com escreveu:

 Hi all,

 I am in the process of writing a Haskell program consisting of two
 threads, one for performing a calculation and one for an Ncurses UI
 (haskell-ncurses).

 The calculation thread needs to feed a stream of numbers back to the
 UI thread (about 1 value per second) and the UI needs to take input
 from the user and will pass parameter changes to the calculation
 thread using an IORef and atomicModifyIORef.

 However, I'm not sure how to hande the UI thread. The UI thread would
 normally wait for Ncurses input using getEvent, but I need advice on
 how to the the data from the calculation thread.

 Any advice or things to try?

 Cheers,
 Erik
 --
 --
 Erik de Castro Lopo
 http://www.mega-nerd.com/

 ___
 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] SDL and ALUT on Windows: stdin Bad file descriptor

2013-01-26 Thread Thiago Negri
I'm trying SDL on Windows, and things are getting really weird.
I can compile the code (links on the end).
When I run it, if I try using `stdin` the program crashes with this
message:

stdin: hGetLine: invalid argument (Bad file descriptor)

Is it something to do with SDL itself?
What am I doing wrong? :(

Code: http://hpaste.org/81321
Cabal file: http://hpaste.org/81322

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


Re: [Haskell-cafe] SDL and ALUT on Windows: stdin Bad file descriptor

2013-01-26 Thread Thiago Negri
I didn't use `-optl-mwindows`. I guess the dependency on SDL is doing this.
Anyway, I was trying to print some debug messages to see what was going
wrong.
Replaces the debugs message with on-screen messages using `SDL-ttf` package.

Thanks,
Thiago.


2013/1/26 Henk-Jan van Tuyl hjgt...@chello.nl

 On Sat, 26 Jan 2013 21:52:03 +0100, Brandon Allbery allber...@gmail.com
 wrote:

  On Sat, Jan 26, 2013 at 3:34 PM, Thiago Negri evoh...@gmail.com wrote:

  I'm trying SDL on Windows, and things are getting really weird.
 I can compile the code (links on the end).
 When I run it, if I try using `stdin` the program crashes with this
 message:

 stdin: hGetLine: invalid argument (Bad file descriptor)


 You haven't even touched SDL at that point in that source code.

 If I had to guess, something (possibly a linker option embedded in the SDL
 binding) is causing your program to be built as a Windows GUI (as opposed
 to Windows Console) so it has no stdin.  I couldn't tell you much more
 than
 that, though; the ways of Windows development are foreign to me.


 You probably used -optl-mwindows in the compile command, to prevent the
 DOS-shell appearing behind your window.

 Regards,
 Henk-Jan van Tuyl


 --
 http://Van.Tuyl.eu/
 http://members.chello.nl/**hjgtuyl/tourdemonad.htmlhttp://members.chello.nl/hjgtuyl/tourdemonad.html
 Haskell programming
 --

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


Re: [Haskell-cafe] Chordify, a new web startup using Haskell

2013-01-18 Thread Thiago Negri
Is it possible to play the generated chords as a melody by itself, without
the original music over it?


2013/1/18 Alfredo Di Napoli alfredo.dinap...@gmail.com

 Congratulations!
 Keep up the good work, especially in using Haskell at a commercial level :)

 Bye!
 Alfredo


 On 18 January 2013 07:34, Alp Mestanogullari alpmes...@gmail.com wrote:

 That's awesome, works like a charm on the samples I've tried it on!
 Cheers to the Chordify team, I will use it and give any useful feedback if
 I have any.


 On Fri, Jan 18, 2013 at 12:07 AM, José Pedro Magalhães j...@cs.uu.nlwrote:

  Hi all,

 I'd like to introduce Chordify http://chordify.net/ [1], an online
 music player that extracts chords from musical sources like Soundcloud,
 Youtube or your own files, and shows you which chord to play when. Here's
 an example song:
 http://chordify.net/chords/passenger-let-her-go-official-video-passengermusic

 The aim of Chordify is to make state-of-the-art music technology
 accessible to a broader audience. Behind the scenes, Chordify uses the
 HarmTrace Haskell package to compute chords from audio. I've been working
 on this project with a couple of colleagues for a while now, and recently
 we have made the website public, free to use for everyone.

 We do not use Haskell for any of the frontend/user interface, but the
 backend is entirely written in Haskell (and it uses pretty advanced
 features, such as GADTs and type families [3]). We're particularly
 interested in user feedback at this stage, so if you're interested in music
 and could use an automatic chord transcription service, please try Chordify!


 Cheers,
 Pedro

 [1] http://chordify.net/
 [2] http://hackage.haskell.org/package/HarmTrace
 [3] José Pedro Magalhães and W. Bas de Haas. Functional Modelling of
 Musical Harmony: an Experience Report. In Proceedings of the 16th ACM
 SIGPLAN International Conference on Functional Programming (ICFP'11), pp.
 156–162, ACM, 2011. http://dreixel.net/research/pdf/fmmh.pdf


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




 --
 Alp Mestanogullari

 ___
 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


[Haskell-cafe] Type hierarchy

2013-01-16 Thread Thiago Negri
Hello.

How do I achieve type hierarchy in Haskell?

Suppose we have the following code:

foo :: A - C
bar :: B - C

I want something that allow me to say that B is a subtype of A, meaning:
1. I can use a value of type A where a value of type A is needed.
2. I can use a value of type B where a value of type B is needed.
3. I can use a value of type B where a value of type A is needed.
4. I can't use a value of type A where a value of type B is needed.

What are my options?

I've thought in type classes and data types with an attribute representing
the extension. Any other way to do this?

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


Re: [Haskell-cafe] Type hierarchy

2013-01-16 Thread Thiago Negri
Thanks for the answer, but I'm trying to avoid type classes.

By the way, I'm not trying to embed OO into Haskell.
I'm trying to solve this issue:
https://github.com/haskell-opengl/OpenGLRaw/issues/15

The binding to OpenGL declares GLenum as CUInt and GLboolean as CUChar,
meaning I can't use a GLenum as a GLboolean or vice-versa.
The C spec allows the use of GLboolean values where GLenums are expected.

Maybe I'm taking the wrong approach...


2013/1/16 Felipe Almeida Lessa felipe.le...@gmail.com

 For your particular constraints, it can be as easy as:

   class IsA a where
 toA :: a - A

   foo' :: IsA a = a - C
   foo' = foo . toA

 However, you may asking the wrong question since it smells like you're
 trying to embed OO into Haskell =).

 Cheers,

 On Wed, Jan 16, 2013 at 1:03 PM, Thiago Negri evoh...@gmail.com wrote:
  Hello.
 
  How do I achieve type hierarchy in Haskell?
 
  Suppose we have the following code:
 
  foo :: A - C
  bar :: B - C
 
  I want something that allow me to say that B is a subtype of A, meaning:
  1. I can use a value of type A where a value of type A is needed.
  2. I can use a value of type B where a value of type B is needed.
  3. I can use a value of type B where a value of type A is needed.
  4. I can't use a value of type A where a value of type B is needed.
 
  What are my options?
 
  I've thought in type classes and data types with an attribute
 representing
  the extension. Any other way to do this?
 
  Thanks,
  Thiago.
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 



 --
 Felipe.

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


[Haskell-cafe] Handling Joystick with GLFW

2012-12-31 Thread Thiago Negri
I'm trying to handle my usb controller (xbox model) via GLFW.

I can get it's input, but I see a strange behaviour in my sample
application that I couldn't explain.
Can you enlight me please?

If I disable automatic event polling on buffer swapping (line A), the
screen content is refreshed but OS part is unresposive: I can't resize,
move, etc.

With automatic event polling enabled, everything is fine.

I tried disabling automatic event polling and calling waitEvents (line
B) before refreshing the screen. But, changes to the joystick input do
not generate any event, so I need to move the mouse or type a key to
release waitEvents call.

What am I missing?

I'm using Windows 7 64-bit.

The code is available here: http://hpaste.org/80031
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] foldr (.) id

2012-10-26 Thread Thiago Negri
Can you please show some examples where it might be useful?
I miss the point.

Thanks,
Thiago.

2012/10/26 John Wiegley jo...@newartisans.com:
 Greg Fitzgerald gari...@gmail.com writes:

 I've recently found myself using the expression: foldr (.) id to compose a
 list (or Foldable) of functions.

 You want the Endo monoid:

 ghci appEndo (Endo (+ 10)  Endo (+ 20)) $ 3
   33

 John


 ___
 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] Teaching Haskell @ MOOCs like Coursera or Udacity

2012-10-18 Thread Thiago Negri
+1

2012/10/18 niket niketku...@gmail.com:
 I would love to see Haskell growing on such new platforms!

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


[Haskell-cafe] Windows - Creating FreeGLUT DLL

2012-10-05 Thread Thiago Negri
I'm trying OpenGL on Haskell and couldn't create the FreeGLUT DLL myself.

I did follow this tutorial:
http://netsuperbrain.com/blog/posts/freeglut-windows-hopengl-hglut/

But when I put my DLL on the folder of the binary, it complains about
initGlut.

Using the DLL pointed by FreeGLUT official site, created by other
person, works fine.

I don't know what I did wrong.

Anyone had this problem?

Thanks.

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


[Haskell-cafe] Pattern matching: multi constructors to same branch

2012-09-11 Thread Thiago Negri
Is it possible to capture more than one constructor in a single
pattern matching?
I mean, is it possible to generalize the following pattern matching of
A and B to a single branch?

g f C = [f C]
g f v@(A _ n) = f v : g n
g f v@(B _ n) = f v : g n

For example:

g f C = [f C]
g f v@(A|B _ n) = f v : g n

Or:

g f v =
case v of
C - [f C]
A|B - f v : g (n v)


Thanks.

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


[Haskell-cafe] Yesod a href render issue

2012-08-31 Thread Thiago Negri
I'm following Yesod tutorial that gives this as the first example for
type-safe URLs:

| getHomeR  = defaultLayout [whamlet|a href=@{Page1R}Go to page 1!|]

Worked fine, the a href generated looks perfect.
Then I tried this:

| getHomeR  = defaultLayout [whamlet|Hello!a href=@{Page1R}Go to page 1!|]

And got a a href referecing a URL without quotes and with no end tag
for a, something like this:

| htmlheadtitle/title/headbodyHelloa href=/page1Go to
page 1!/body/html

I tried in many different ways, and the only way to get it working
properly was to set the a tag in a line by itself:

| getHomeR  = defaultLayout [whamlet|Hello!
| a href=@{Page1R}Go to page 1!
| |]

Is this a failure of Yesod quasiquotation or am I missing something?
I know Yesod clearly states that the best approach is to use external
files instead of quasiquotes, but as I'm making my first steps into
Yesod, I would like to use the practical embedded quasiquotes.

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


[Haskell-cafe] Compiling Haskell targetting different OS/arch

2012-08-24 Thread Thiago Negri
Is it possible to compile Haskell code targetting a OS/arch that
differs from the one where the compiler (GHC) is running?

Thanks.

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


[Haskell-cafe] Bringing knowledge from Haskell to Java

2012-08-23 Thread Thiago Negri
Hello everyone.

I just posted about a fact that happens to everyone who codes in Java
while learning Haskell.
You end up trading knowledge from both sides.

I'll appreciate if you could read and send me feedbacks:
http://me-hunz.blogspot.com.br/2012/08/bringing-knowledge-from-haskell-to-java.html

Thanks,
Thiago.

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


Re: [Haskell-cafe] Cloud Haskell real usage example

2012-08-22 Thread Thiago Negri
| I have pasted a version of your code that uses Template Haskell at
| http://hpaste.org/73520. Where did you get stuck?

Your version worked like a charm. I'm quite new to Haskell, so I was
trying desperately to get TH working: forgot to quote worker at
mkClosure.


| 1. A bug in the SimpleLocalnet backend meant that if you dropped a
| worker node findSlaves might not return. I have fixed this and
| uploaded it to Hackage as version 0.2.0.5.

Updated to version 0.2.0.5 and it's working now. :-)


| 2. But even with this fix, you will still need to take into account
| that workers may disappear once they have been reported by findSlaves.
| spawn will actually throw an exception if the specified node is
| unreachable (it is debatable whether this is the right behaviour --
| see below).

Added exception catching, thanks.


| Note that with these modifications there is still something slightly
| unfortunate: if you delete a worker, and then restart it *at the same
| port*, the master will not see it. There is a very good reason for
| this: Cloud Haskell guarantees reliable ordered message passing, and
| we want a clear semantics for this (unlike, say, in Erlang, where you
| might send messages M1, M2 and M3 from P to Q, and Q might receive M1,
| M3 but not M2, under certain circumstances). We (developers of Cloud
| Haskell, Simon Peyton-Jones and some others) are still debating over
| what the best approach is here; in the meantime, if you restart a
| worker node, just give a different port number.

I trust you will make a good decision on this.


By the way, my new code with TH and exception catching: http://hpaste.org/73548

Thanks,
Thiago.

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


[Haskell-cafe] Cloud Haskell real usage example

2012-08-21 Thread Thiago Negri
Hello everyone. I'm taking my first steps in Cloud Haskell and got
some unexpected behaviors.

I used the code from Raspberry Pi in a Haskell Cloud [1] as a first
example. Did try to switch the code to use Template Haskell with no
luck, stick with the verbose style.
I changed some of the code, from ProcessId-based messaging to typed
channel to receive the Pong; using startSlave to start the worker
nodes; and changed the master node to loop forever sending pings to
the worker nodes.

The unexpected behaviors:
- Dropping a worker node while the master is running makes the master
node to crash.
- Master node do not see worker nodes started after the master process.

In order to fix this, I tried to findSlaves at the start of the
master process and send ping to only these ones, ignoring the list of
NodeId enforced by the type signature of startMaster.

Now the master finds new slaves. The bad thing is that when I close
one of the workers, the master process freezes. It simply stop doing
anything. No more messages and no more Pings to other slaves. :(


My view of Cloud Haskell usage would be something similar to this: a
master node sending work to slaves; slave instances getting up or down
based on demand. So, the master node should be slave-failure-proof and
also find new slaves somehow.

Am I misunderstanding the big picture of Cloud Haskell or doing
anything wrong in the following code?

Code (skipped imports and wiring stuff):

--
newtype Ping = Ping (SendPort Pong)
deriving (Typeable, Binary, Show)

newtype Pong = Pong ProcessId
deriving (Typeable, Binary, Show)

worker :: Ping - Process ()
worker (Ping sPong) = do
  wId - getSelfPid
  say Got a Ping!
  sendChan sPong (Pong wId)

master :: Backend - [NodeId] - Process ()
master backend _ = forever $ do
  workers - findSlaves backend
  say $ Slaves:  ++ show workers

  (sPong, rPong) - newChan

  forM_ workers $ \w - do
say $ Sending a Ping to  ++ (show w) ++ ...
spawn w (workerClosure (Ping sPong))

  say $ Waiting for reply from  ++ (show (length workers)) ++  worker(s)

  replicateM_ (length workers) $ do
  (Pong wId) - receiveChan rPong
  say $ Got back a Pong from  ++ (show $ processNodeId wId) ++ !

  (liftIO . threadDelay) 200 -- Wait a bit before return

main = do
  prog - getProgName
  args - getArgs

  case args of
[master, host, port] - do
  backend - initializeBackend host port remoteTable
  startMaster backend (master backend)

[worker, host, port] - do
  backend - initializeBackend host port remoteTable
  startSlave backend

_ -
  putStrLn $ usage:  ++ prog ++  (master | worker) host port
--

[1] http://alenribic.com/writings/post/raspberry-pi-in-a-haskell-cloud

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


Re: [Haskell-cafe] What Haskell Records Need

2012-08-02 Thread Thiago Negri
I'm new to Haskell, but I do like your idea.

I prefer this as a built-in feature because it will create a standard
way of doing this, making the question wich package should I use to
get mutatos? lens-foo, lens-bar, monad-lens, lens-lens-foo-bar, ...?
simply go away.

So, yes, I up-vote your idea to write an official proposal.

Thiago.

2012/8/2 Jonathan Geddes geddes.jonat...@gmail.com:

 Richard O'Keefe Said:
 Ouch! And that's not even very deeply nested.
 Imagine 4 or 5 levels deep. It really makes
 Haskell feel clunky next to `a.b.c.d = val`
 that you see in other languages.

I was taught that this kind of thing violates the Law of Demeter
and that an object should not be mutating the parts of an
acquaintance's parts, but should ask the acquaintance to do so.
I'd say that a.b.c.d = val is at the very least a sign that
some encapsulation did not happen.

 Absolutely! But in Haskell how do you do the
 asking? I guess that's what I'm proposing is
 a built in way of doing just that! I'm
 shooting for as-easy-as the built in getters.

 Erik Hesselink said:
Isn't this exactly the problem solved by all the lens packages?

 Yes it is. I think the existence of these
 packages along with all the proposals to
 change records is an indication that
 something is missing from the language as a
 whole. What I'm proposing is that the
 language give you something that is
 lightweight and easy to use to address this
 issue. You can still use lenses on top of all
 of this.

 makeLens myField myField'

 If I remember correctly, one of the problems
 with lenses is that they cannot support
 polymorphic updates (updates which change a
 type variable of the data). SEC functions, on
 the other hand support polymorphic updates.

 --Jonathan

 On Thu, Aug 2, 2012 at 4:48 AM, Andrew Butterfield
 andrew.butterfi...@scss.tcd.ie wrote:

 Ah yes - the joy of Haskell

 It so easy to roll your own, rather than search to find someone else's
 (better/more elegant) solution...   :-)


 On 2 Aug 2012, at 11:41, Erik Hesselink wrote:

  On Thu, Aug 2, 2012 at 12:30 PM, Andrew Butterfield
  andrew.butterfi...@scss.tcd.ie wrote:
 
  On 2 Aug 2012, at 09:25, Erik Hesselink wrote:
 
  Isn't this exactly the problem solved by all the lens packages?
  Current popular ones are fclabels [0] and data-lens [1].
 
  [0] http://hackage.haskell.org/package/fclabels
  [1] http://hackage.haskell.org/package/data-lens
 
  Not sure what all of these do, but I have a simple solution I use
  in my work:
 
  They do exactly that. They create 'lenses' which are
  getters/setters/modifiers combined, and allow you to compose these to
  get/set/modify deep inside nested data types. Look at the examples in
  the fclabels documentation [2] for more details.
 
  [2]
  http://hackage.haskell.org/packages/archive/fclabels/1.1.4/doc/html/Data-Label.html

 
 Andrew Butterfield Tel: +353-1-896-2517 Fax: +353-1-677-2204
 Lero@TCD, Head of Foundations  Methods Research Group
 Director of Teaching and Learning - Undergraduate,
 School of Computer Science and Statistics,
 Room G.39, O'Reilly Institute, Trinity College, University of Dublin
   http://www.scss.tcd.ie/Andrew.Butterfield/
 


 ___
 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] How to define a Monad instance

2012-07-31 Thread Thiago Negri
Thanks for the reply Ryan.

That's exactly the type of thing I was trying to do: use the
syntactical sugar of do-notation to express some replacement rules.

Why am I doing this?

A long time ago, when I was learning C, I did a small project
(spaghetti code) to encrypt text files in some user-defined language.
It supported exact replacement (char - char) and some other stuff
that I called sessions of encryption and masked string replacement.

The sessions can be turned on or off at the same time of matching a
char, e.g. the user could define that when the char 'a' was matched
inside the session foo, it will change it to a 'b', turn off the
session foo and turn on the sessions bar and baz.

So, I'm trying to create a similar thing in Haskell.

In my view, it fits in the Monad class, as I'm doing pattern matching
and replacing at the same time as sequencing other things like
changing the state of the replacement machine.

The char-to-char replacement is the first step.

I'll try your exercises later, when I get home.

Thanks,
Thiago.

2012/7/31 Ryan Ingram ryani.s...@gmail.com:
 A couple typos:

 instance Monad Replacer1 where
 -
 instance Monad (Replacer1 k) where


 instance Monad Replacer2 k where
 -
 instance Monad (Replacer2 k) where

 I haven't tested any of this code, so you may have to fix some minor type
 errors.


 On Mon, Jul 30, 2012 at 10:38 PM, Ryan Ingram ryani.s...@gmail.com wrote:

 To take this a step further, if what you really want is the syntax sugar
 for do-notation (and I understand that, I love sweet, sweet syntactical
 sugar), you are probably implementing a Writer monad over some monoid.

 Here's two data structures that can encode this type;

 data Replacer1 k a = Replacer1 (k - Maybe k) a
 data Replacer2 k a = Replacer2 [(k,k)] a

 instance Monad Replacer1 where
 return x = Replacer1 (\_ - Nothing) x
 Replacer1 ka a = f = result where
 Replacer1 kb b = f a
 result = Replacer1 (\x - ka x `mplus` kb x) b

 (!) :: Eq k = k - k - Replacer1 k ()
 x ! y = Replacer1 (\k - if k == x then Just y else Nothing) ()

 replace1 :: Replacer1 k () - [k] - [k]-- look ma, no Eq requirement!
 replace1 (Replacer k ()) = map (\x - fromMaybe x $ k x) -- from
 Data.Maybe

 table1 :: Replacer1 Char ()
 table1 = do
 'a' ! 'b'
 'A' ! 'B'

 test = replace1 table1 All I want

 -- Exercise: what changes if we switch ka and kb in the result of (=)?
 When does it matter?

 -- Exercises for you to implement:
 instance Monad Replacer2 k where
 replacer :: Eq k = Replacer2 k - [k] - [k]
 ($) :: k - k - Replacer2 k

 -- Exercise: Lets make use of the fact that we're a monad!
 --
 -- What if the operator ! had a different type?
 -- (!) :: Eq k = k - k - Replacer k Integer
 -- which returns the count of replacements done.
 --
 -- table3 = do
 -- count - 'a' ! 'b'
 -- when (count  3) ('A' ! 'B')
 -- return ()
 --
 -- Do any of the data structures I've given work?  Why or why not?
 -- Can you come up with a way to implement this?

   -- ryan


 On Sat, Jul 28, 2012 at 10:07 AM, Steffen Schuldenzucker
 sschuldenzuc...@uni-bonn.de wrote:

 On 07/28/2012 03:35 PM, Thiago Negri wrote:
  [...]

 As Monads are used for sequencing, first thing I did was to define the
 following data type:

 data TableDefinition a = Match a a (TableDefinition a) | Restart


 So TableDefinition a is like [(a, a)].

 [...]

 

 So, to create a replacement table:

 table' :: TableDefinition Char
 table' =
  Match 'a' 'b'
  (Match 'A' 'B'
   Restart)

 It look like a Monad (for me), as I can sequence any number of
 replacement values:

 table'' :: TableDefinition Char
 table'' = Match 'a' 'c'
   (Match 'c' 'a'
   (Match 'b' 'e'
   (Match 'e' 'b'
Restart)))


 Yes, but monads aren't just about sequencing. I like to see a monad as a
 generalized computation (e.g. nondeterministic, involving IO, involving
 state etc). Therefore, you should ask yourself if TableDefinition can be
 seen as some kind of abstract computation. In particular, can you
 execute a computation and extract its result? as in

   do
 r - Match 'a' 'c' Restart
 if r == 'y' then Restart else Match 2 3 (Match 3 4 Restart)

 Doesn't immediately make sense to me. In particular think about the
 different possible result types of a TableDefinition computation.

 If all you want is sequencing, you might be looking for a Monoid instance
 instead, corresponding to the Monoid instance of [b], where b=(a,a) here.

  [...]

 

 I'd like to define the same data structure as:

 newTable :: TableDefinition Char
 newTable = do
  'a' :  'b'
  'A' :  'B'

 But I can't figure a way to define a Monad instance for that. :(


 The desugaring of the example looks like this:

   ('a' : 'b')  ('A' : 'B')

 Only () is used, but not (=) (i.e. results are always discarded). If
 this is the only case that makes sense, you're probably looking for a Monoid
 instead (see above

[Haskell-cafe] How to define a Monad instance

2012-07-28 Thread Thiago Negri
Hello.

I'm trying to understand Monads. In order to do so, I decided to
create my own Monad for a simple domain-specific language.
The idea is to define a way to describe a multi-value replacement
inside do-notation.

Example of a function doing what I want (without Monads):

replaceAll :: (a - Maybe a) - [a] - [a]
replaceAll f xs = go f xs []
  where go :: (a - Maybe a) - [a] - [a] - [a]
go _ [] acc = acc
go f (x:xs) acc = let acc' = acc ++ [fromMaybe x (f x)] in
acc' `seq` go f xs acc'

Example of a replacement table:

table :: Char - Maybe Char
table x = case x of
'a' - Just 'b'
'A' - Just 'B'
_   - Nothing

Example of use:

\ replaceAll table All I want
Bll I wbnt


Now, want I tried to do...
As Monads are used for sequencing, first thing I did was to define the
following data type:

data TableDefinition a = Match a a (TableDefinition a) | Restart

So, to create a replacement table:

table' :: TableDefinition Char
table' =
Match 'a' 'b'
(Match 'A' 'B'
 Restart)

It look like a Monad (for me), as I can sequence any number of
replacement values:

table'' :: TableDefinition Char
table'' = Match 'a' 'c'
 (Match 'c' 'a'
 (Match 'b' 'e'
 (Match 'e' 'b'
  Restart)))

In order to run the replacement over a list, I've defined the
following function:

runTable :: Eq a = TableDefinition a - [a] - [a]
runTable t = go t t []
  where go _ _ acc []= acc
go s Restart   acc (x:xs)= let acc' = (acc ++ [x]) in
   acc' `seq` go s s acc' xs
go s (Match a b m) acc ci@(x:xs) | x == a= let acc' = (acc
++ [b]) in
   acc' `seq`
go s m acc' xs
 | otherwise = go s m acc ci

The result is still the same:

\ runTable table' All I want
Bll I wbnt

I'd like to define the same data structure as:

newTable :: TableDefinition Char
newTable = do
'a' : 'b'
'A' : 'B'

But I can't figure a way to define a Monad instance for that. :(

Can you help me?

Thanks,
Thiago.

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


[Haskell-cafe] MonadPlus m = Maybe a - m a

2012-07-28 Thread Thiago Negri
I'm solving this exercise:
http://www.haskell.org/haskellwiki/All_About_Monads#Exercise_4:_Using_the_Monad_class_constraint

I'm missing a function to transform a Maybe a into a MonadPlus m = m a.
I did search on Hoogle with no luck.

There is no standard definition for the g function I'm defining?

My take on the exercise:

data Sheep = Sheep {
mother :: Maybe Sheep,
father :: Maybe Sheep,
name :: String }

instance Show Sheep where -- for testing
show = name

g :: (MonadPlus m) = Maybe a - m a
g Nothing = mzero
g (Just a) = return a

mother' :: (MonadPlus m) = Sheep - m Sheep
mother' = g . mother

father' :: (MonadPlus m) = Sheep - m Sheep
father' = g . father

parent'' :: (MonadPlus m) = Sheep - m Sheep
parent'' s = mother' s `mplus` father' s

grandparent'' :: (MonadPlus m) = Sheep - m Sheep
grandparent'' s = parent'' s = parent''

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


[Haskell-cafe] Understanding GC time

2012-03-10 Thread Thiago Negri
Hi all.

I wrote a very simple program to try out parallel Haskel and check how
it would look like to make use of more than one core in this language.

When I tried the program with RTS option -N1, total time shows it took
2.48 seconds to complete and around 65% of that time was taken by GC.

Then I tried the same program with RTS options -N2 and total time
decreased to 1.15 seconds as I expected a gain here. But what I didn't
expect is the GC time to drop to 0%.

I guess I'm having trouble to understand the output of the RTS option -s.
Can you enlighten me?


The source for the testing program:

 module Main where

 import Data.List (foldl1')
 import Control.Parallel (par, pseq)
 import Control.Arrow (())

 f `parApp` (a, b) = a `par` (b `pseq` (f a b))
 seqApp = uncurry

 main = print result
   where result = (+) `parApp` minMax list
 minMax = minlist  maxlist
 minlist = foldl1' min
 maxlist = foldl1' max
 list = [1..1999]


The results on a Windows 7 64bits with an Intel Core 2 Duo, compiled
with GHC from Haskell Platform:

c:\tmp\hspar +RTS -s -N1
par +RTS -s -N1
2000
 803,186,152 bytes allocated in the heap
 859,916,960 bytes copied during GC
 233,465,740 bytes maximum residency (10 sample(s))
  30,065,860 bytes maximum slop
 483 MB total memory in use (0 MB lost due to fragmentation)

  Generation 0:  1523 collections, 0 parallel,  0.80s,  0.75s elapsed
  Generation 1:10 collections, 0 parallel,  0.83s,  0.99s elapsed

  Parallel GC work balance: nan (0 / 0, ideal 1)

MUT time (elapsed)   GC time  (elapsed)
  Task  0 (worker) :0.00s(  0.90s)   0.00s(  0.06s)
  Task  1 (worker) :0.00s(  0.90s)   0.00s(  0.00s)
  Task  2 (bound)  :0.86s(  0.90s)   1.62s(  1.69s)

  SPARKS: 1 (0 converted, 0 pruned)

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time0.86s  (  0.90s elapsed)
  GCtime1.62s  (  1.74s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time2.48s  (  2.65s elapsed)

  %GC time  65.4%  (65.9% elapsed)

  Alloc rate936,110,032 bytes per MUT second

  Productivity  34.6% of total user, 32.4% of total elapsed

gc_alloc_block_sync: 0
whitehole_spin: 0
gen[0].sync_large_objects: 0
gen[1].sync_large_objects: 0


c:\tmp\hspar +RTS -s -N2
par +RTS -s -N2
2000
   1,606,279,644 bytes allocated in the heap
  74,924 bytes copied during GC
  28,340 bytes maximum residency (1 sample(s))
  29,004 bytes maximum slop
   2 MB total memory in use (0 MB lost due to fragmentation)

  Generation 0:  1566 collections,  1565 parallel,  0.00s,  0.01s elapsed
  Generation 1: 1 collections, 1 parallel,  0.00s,  0.00s elapsed

  Parallel GC work balance: 1.78 (15495 / 8703, ideal 2)

MUT time (elapsed)   GC time  (elapsed)
  Task  0 (worker) :0.00s(  0.59s)   0.00s(  0.00s)
  Task  1 (worker) :0.58s(  0.59s)   0.00s(  0.01s)
  Task  2 (bound)  :0.58s(  0.59s)   0.00s(  0.00s)
  Task  3 (worker) :0.00s(  0.59s)   0.00s(  0.00s)

  SPARKS: 1 (1 converted, 0 pruned)

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time1.15s  (  0.59s elapsed)
  GCtime0.00s  (  0.01s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time1.15s  (  0.61s elapsed)

  %GC time   0.0%  (2.4% elapsed)

  Alloc rate1,391,432,695 bytes per MUT second

  Productivity 100.0% of total user, 190.3% of total elapsed

gc_alloc_block_sync: 90
whitehole_spin: 0
gen[0].sync_large_objects: 0
gen[1].sync_large_objects: 0

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


Re: [Haskell-cafe] Understanding GC time

2012-03-10 Thread Thiago Negri
I see. Thanks for the answers.

Any data structure or source annotation that would prevent that?

For example, if I try the same program to run on a
[1..] list, I'll get an out of memory error for the
single-threaded version. Any way to prevent it without declaring two
different versions of list?


2012/3/10 Anthony Cowley acow...@gmail.com:
 From that profiling data, I think you're just seeing a decrease in sharing. 
 With one thread, you create the list structure in memory: the first fold 
 could consume it in-place, but the second fold is still waiting for its turn. 
  The list is built on the heap so the two folds can both refer to the same 
 list.

 With two threads, GHC is being clever and inlining the definition you give 
 for list, which is then optimized into two parallel loops. No list on the 
 heap means there's not much for the GC to do.

 Sharing of index lists like this is a common source of problems. In 
 particular, nested loops can make it even trickier to prevent sharing as 
 there may not be an opportunity for parallel evaluation.

 Anthony

 On Mar 10, 2012, at 10:21 AM, Thiago Negri evoh...@gmail.com wrote:

 Hi all.

 I wrote a very simple program to try out parallel Haskel and check how
 it would look like to make use of more than one core in this language.

 When I tried the program with RTS option -N1, total time shows it took
 2.48 seconds to complete and around 65% of that time was taken by GC.

 Then I tried the same program with RTS options -N2 and total time
 decreased to 1.15 seconds as I expected a gain here. But what I didn't
 expect is the GC time to drop to 0%.

 I guess I'm having trouble to understand the output of the RTS option -s.
 Can you enlighten me?


 The source for the testing program:

 module Main where

 import Data.List (foldl1')
 import Control.Parallel (par, pseq)
 import Control.Arrow (())

 f `parApp` (a, b) = a `par` (b `pseq` (f a b))
 seqApp = uncurry

 main = print result
  where result = (+) `parApp` minMax list
        minMax = minlist  maxlist
        minlist = foldl1' min
        maxlist = foldl1' max
        list = [1..1999]


 The results on a Windows 7 64bits with an Intel Core 2 Duo, compiled
 with GHC from Haskell Platform:

 c:\tmp\hspar +RTS -s -N1
 par +RTS -s -N1
 2000
     803,186,152 bytes allocated in the heap
     859,916,960 bytes copied during GC
     233,465,740 bytes maximum residency (10 sample(s))
      30,065,860 bytes maximum slop
             483 MB total memory in use (0 MB lost due to fragmentation)

  Generation 0:  1523 collections,     0 parallel,  0.80s,  0.75s elapsed
  Generation 1:    10 collections,     0 parallel,  0.83s,  0.99s elapsed

  Parallel GC work balance: nan (0 / 0, ideal 1)

                        MUT time (elapsed)       GC time  (elapsed)
  Task  0 (worker) :    0.00s    (  0.90s)       0.00s    (  0.06s)
  Task  1 (worker) :    0.00s    (  0.90s)       0.00s    (  0.00s)
  Task  2 (bound)  :    0.86s    (  0.90s)       1.62s    (  1.69s)

  SPARKS: 1 (0 converted, 0 pruned)

  INIT  time    0.00s  (  0.00s elapsed)
  MUT   time    0.86s  (  0.90s elapsed)
  GC    time    1.62s  (  1.74s elapsed)
  EXIT  time    0.00s  (  0.00s elapsed)
  Total time    2.48s  (  2.65s elapsed)

  %GC time      65.4%  (65.9% elapsed)

  Alloc rate    936,110,032 bytes per MUT second

  Productivity  34.6% of total user, 32.4% of total elapsed

 gc_alloc_block_sync: 0
 whitehole_spin: 0
 gen[0].sync_large_objects: 0
 gen[1].sync_large_objects: 0


 c:\tmp\hspar +RTS -s -N2
 par +RTS -s -N2
 2000
   1,606,279,644 bytes allocated in the heap
          74,924 bytes copied during GC
          28,340 bytes maximum residency (1 sample(s))
          29,004 bytes maximum slop
               2 MB total memory in use (0 MB lost due to fragmentation)

  Generation 0:  1566 collections,  1565 parallel,  0.00s,  0.01s elapsed
  Generation 1:     1 collections,     1 parallel,  0.00s,  0.00s elapsed

  Parallel GC work balance: 1.78 (15495 / 8703, ideal 2)

                        MUT time (elapsed)       GC time  (elapsed)
  Task  0 (worker) :    0.00s    (  0.59s)       0.00s    (  0.00s)
  Task  1 (worker) :    0.58s    (  0.59s)       0.00s    (  0.01s)
  Task  2 (bound)  :    0.58s    (  0.59s)       0.00s    (  0.00s)
  Task  3 (worker) :    0.00s    (  0.59s)       0.00s    (  0.00s)

  SPARKS: 1 (1 converted, 0 pruned)

  INIT  time    0.00s  (  0.00s elapsed)
  MUT   time    1.15s  (  0.59s elapsed)
  GC    time    0.00s  (  0.01s elapsed)
  EXIT  time    0.00s  (  0.00s elapsed)
  Total time    1.15s  (  0.61s elapsed)

  %GC time       0.0%  (2.4% elapsed)

  Alloc rate    1,391,432,695 bytes per MUT second

  Productivity 100.0% of total user, 190.3% of total elapsed

 gc_alloc_block_sync: 90
 whitehole_spin: 0
 gen[0].sync_large_objects: 0
 gen[1].sync_large_objects: 0

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http

Re: [Haskell-cafe] Functional programming podcast

2012-02-22 Thread Thiago Negri
I will enjoy listening to a podcast like that.
The community can provide interesting content (links, posts, papers, ...).
Sort of a central feed to submit your suggestion to be discussed in
subsequent podcasts.

Thiago.

2012/2/22 Christopher Done chrisd...@googlemail.com:
 With permission I forward that Justin has offered to help cutting it
 up and would also be on it.

 On 22 February 2012 04:39, serialhex serial...@gmail.com wrote:
  So I'm not a very good haskell (or fp) programmer, though I wouldn't mind
  doing the audio splicing (which I've done amore than a bit of) or even 
  being
  on the podcast myself - though like I said, right now I'm better at theory
  than practice, and I'm still learning theory!  So as a good host or regular
  speaker I'm not sure id do so well, but I am willing to do what I can to 
  get
  this off the ground!
  Justin

 ___
 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] where to put general-purpose utility functions

2012-01-21 Thread Thiago Negri
There is also Hoogle, pretty equivalent I guess.

http://www.haskell.org/hoogle/

Thiago.

2012/1/21 Christoph Breitkopf chbreitk...@googlemail.com:
 One thing I found useful when looking if a function already exists under a
 different name is to use Hayoo to search for the type, i.e.:

 http://holumbus.fh-wedel.de/hayoo/hayoo.html#0:(a%20-%3E%20Bool)%20-%3E%20%5Ba%5D%20-%3E%20(%5Ba%5D%2C%5Ba%5D)

 - Chris

 ___
 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] Solved but strange error in type inference

2012-01-04 Thread Thiago Negri
Do not compile:

f :: a - a
f x = x :: a

Couldn't match type `a' with `a1'
  `a' is a rigid type variable bound by
  the type signature for f :: a - a at C:\teste.hs:4:1
  `a1' is a rigid type variable bound by
   an expression type signature: a1 at C:\teste.hs:4:7
In the expression: x :: a
In an equation for `f': f x = x :: a


Any of these compiles:

f :: a - a
f x = undefined :: a

f :: Num a = a - a
f x = undefined :: a

f :: Int - Int
f x = undefined :: a

f :: Int - Int
f x = 3 :: (Num a = a)


Can someone explain case by case?

Thanks,
Thiago.

2012/1/4 Yves Parès limestr...@gmail.com:
 I don't see the point in universally quantifying over types which are
 already present in the environment

 I think it reduces the indeterminacy you come across when you read your
 program (where does this type variable come from, btw?)


 So is there anyway to force the scoping of variables, so that
 f :: a - a
 f x = x :: a
 becomes valid?

 You mean either than compiling with ScopedTypeVariables and adding the
 explicit forall a. on f? I don't think.

 2012/1/4 Brandon Allbery allber...@gmail.com

 On Wed, Jan 4, 2012 at 08:41, Yves Parès limestr...@gmail.com wrote:

 Would you try:

 f :: a - a

 f x = undefined :: a

 And tell me if it works? IMO it doesn't.

  It won't

 Apparently, Yucheng says it does.

 ___
 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] Solved but strange error in type inference

2012-01-04 Thread Thiago Negri
Got it. Thanks. :)

The gotcha for me is that I was thinking as a generic type 'a' that I
may  and not in terms if something is typed a generic 'a', then it
must fit in ANY type. I think this is a common mistake, as I did read
about it more than once.

I.e.,

undefined :: a means a value that can fit in any type.

(Num a = a) means a value that can fit int any type that has an
instance for Num.

My O.O. mind reacted to that as: Num a = a is a numeric type, it may
or may not be a Int.
Like type hierarchy in Java. A variable declared as Object does not
mean that it fits in any type. It just means that you have no
information about it's real type.

Thiago.

2012/1/4 Antoine Latter aslat...@gmail.com:
 On Wed, Jan 4, 2012 at 9:08 AM, Thiago Negri evoh...@gmail.com wrote:
 Do not compile:

 f :: a - a
 f x = x :: a

    Couldn't match type `a' with `a1'
      `a' is a rigid type variable bound by
          the type signature for f :: a - a at C:\teste.hs:4:1
      `a1' is a rigid type variable bound by
           an expression type signature: a1 at C:\teste.hs:4:7
    In the expression: x :: a
    In an equation for `f': f x = x :: a


 Any of these compiles:

 f :: a - a
 f x = undefined :: a

 Re-written:

 f :: forall a . a - a
 f x = undefined :: forall a . a

 Renaming variables to avoid shadowing:

 f :: forall a . a - a
 f x = undefined :: forall b . b

 Which is allowed.

 The rest of your examples are similar - a new value is introduced with
 a new type that can unify with the required type.

 This is different from the failing case:

 g :: a - a
 g x = x :: a

 Let's go through the same process.

 Insert foralls:

 g :: forall a . a - a
 g x = x :: forall a . a

 Rename shadowed variables:

 g :: forall a . a - a
 g x = x :: forall b . b

 In the function body we have declared that the value 'x' may take on
 any value. But that's not true! The value 'x' comes from the input to
 the function, which is a fixed 'a' decided by the caller.

 So it does not type-check.

 Antoine


 f :: Num a = a - a
 f x = undefined :: a

 f :: Int - Int
 f x = undefined :: a

 f :: Int - Int
 f x = 3 :: (Num a = a)


 Can someone explain case by case?

 Thanks,
 Thiago.

 2012/1/4 Yves Parès limestr...@gmail.com:
 I don't see the point in universally quantifying over types which are
 already present in the environment

 I think it reduces the indeterminacy you come across when you read your
 program (where does this type variable come from, btw?)


 So is there anyway to force the scoping of variables, so that
 f :: a - a
 f x = x :: a
 becomes valid?

 You mean either than compiling with ScopedTypeVariables and adding the
 explicit forall a. on f? I don't think.

 2012/1/4 Brandon Allbery allber...@gmail.com

 On Wed, Jan 4, 2012 at 08:41, Yves Parès limestr...@gmail.com wrote:

 Would you try:

 f :: a - a

 f x = undefined :: a

 And tell me if it works? IMO it doesn't.

  It won't

 Apparently, Yucheng says it does.

 ___
 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] strict, lazy, non-strict, eager

2011-12-28 Thread Thiago Negri
I got a glimpse of understanding of what you are talking about after
reading the wiki [1].

Still difficult to reason about the difference between lazy and
non-strict without taking a look at the text.

I hope somebody will make an effort to better explain the differences
and persist it in the wiki or in a feed (maybe planet haskell).

[1] http://www.haskell.org/haskellwiki/Lazy_vs._non-strict

2011/12/28 Yves Parès limestr...@gmail.com:
 - Adjective strict can be applied both to a global evaluation method and a
 specific function: if applied to an eval method then it's a synonym of
 strict

 I of course meant a synonym of eager. Sorry.

 I admit this definition might be a little liberal, but it helps understand.



 2011/12/28 Yves Parès limestr...@gmail.com

 When I explain to people what strict/lazy/eager mean, I often say
 something like :

 - Adjectives eager and lazy apply only to a global evaluation method:
 eager is C evaluation style and lazy is that of Haskell.
 - Adjective strict can be applied both to a global evaluation method and a
 specific function: if applied to an eval method then it's a synonym of
 strict, and if applied to a function f it means 'f ⊥ = ⊥' (which I detail
 a little more), which is true for strict State monad for istance (= would
 not allow its left argument to return ⊥).

 Thus explaining why datatypes such as State or Bytestring exist in strict
 and lazy flavours.


 2011/12/28 Albert Y. C. Lai tre...@vex.net

 There are two flavours of MonadState, Control.Monad.State.Lazy and
 Control.Monad.State.Strict. There are two flavours of ByteString,
 Data.ByteString.Lazy and Data.Bytestring (whose doc says strict). There
 are two flavours of I/O libraries, lazy and strict. There are advices of the
 form: the program uses too much memory because it is too lazy; try making
 this part more strict. Eventually, someone will ask what are lazy and
 strict. Perhaps you answer this (but there are other answers, we'll see):

 lazy refers to such-and-such evaluation order. strict refers to f ⊥ = ⊥,
 but it doesn't specify evaluation order.

 That doesn't answer the question. That begs the question: Why do
 libraries seem to make them a dichotomy, when they don't even talk about the
 same level? And the make-it-more-strict advice now becomes: the program
 uses too much memory because of the default, known evaluation order; try
 making this part use an unknown evaluation order, and this unknown is
 supposed to use less memory because...?

 I answer memory questions like this: the program uses too much memory
 because it is too lazy---or nevermind lazy, here is the current evaluation
 order of the specific compiler, this is why it uses much memory; now change
 this part to the other order, it uses less memory. I wouldn't bring in the
 denotational level; there is no need.

 (Sure, I use seq to change evaluation order, which may be overriden by
 optimizations in rare cases. So change my answer to: now add seq here, which
 normally uses the other order, but optimizations may override it in rare
 cases, so don't forget to test. Or use pseq.)

 I said people, make up your mind. I do not mean a whole group of people
 for the rest of their lives make up the same mind and choose the same one
 semantics. I mean this: Each individual, in each context, for each problem,
 just how many levels of semantics do you need to solve it? (Sure sure, I
 know contexts that need 4. What about daily programming problems: time,
 memory, I/O order?)

 MigMit questioned me on the importance of using the words properly.
 Actually, I am fine with using the words improperly, too: the program uses
 too much memory because it is too lazy, lazy refers to such-and-such
 evaluation order; try making this part more strict, strict refers to
 so-and-so evaluation order.



 ___
 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] strict, lazy, non-strict, eager

2011-12-28 Thread Thiago Negri
I did read other wiki pages, and I guess I finally got it.
Anyone who still feel lost, take a look at them [1,2,3,4].

If the HaskellWiki is right, then the Wikipedia article for evaluation
strategies [5] is a bit misleading, as it classifies optimistic
evaluation under nondeterministic strategies when it should be under
the non-strict section.
Also, it mixes the word evaluation with strict and non-strict, e.g.:
In non-strict evaluation, arguments to a function are not evaluated
unless they are actually used in the evaluation of the function body.

This is lazy evaluation. A non-strict implementation may evaluate the
arguments of a function before calling it. The main diference is:

Strict semantics: the value of the function is 100% dependent of the
value of all arguments, any arguments yielding
bottom/error/non-termination/exception will result in the same
_error-value_ for the function.

A correct implementation of strict semantics is eager evaluation,
where all the arguments are evaluated before evaluating the function.


Non-strict semantics: the value of the function may not need it's
arguments' values to be produced, if the function can produce it's
value without the need of an argument's value, the function evaluates
correctly even if the unnused argument yields
bottom/error/non-termination/exception.

Lazy evaluation is one implementation of non-strict semantics, where
the arguments are evaluated only when they are needed.

Despite Haskell (GHC) don't do this, (0 * _|_) may yield 0 on a
non-strict implementation.


Did I got it right?


[1] http://www.haskell.org/haskellwiki/Non-strict_semantics
[2] http://www.haskell.org/haskellwiki/Strict_semantics
[3] http://www.haskell.org/haskellwiki/Lazy_evaluation
[4] http://www.haskell.org/haskellwiki/Eager_evaluation
[5] http://en.wikipedia.org/wiki/Evaluation_strategy

2011/12/28 Thiago Negri evoh...@gmail.com:
 I got a glimpse of understanding of what you are talking about after
 reading the wiki [1].

 Still difficult to reason about the difference between lazy and
 non-strict without taking a look at the text.

 I hope somebody will make an effort to better explain the differences
 and persist it in the wiki or in a feed (maybe planet haskell).

 [1] http://www.haskell.org/haskellwiki/Lazy_vs._non-strict

 2011/12/28 Yves Parès limestr...@gmail.com:
 - Adjective strict can be applied both to a global evaluation method and a
 specific function: if applied to an eval method then it's a synonym of
 strict

 I of course meant a synonym of eager. Sorry.

 I admit this definition might be a little liberal, but it helps understand.



 2011/12/28 Yves Parès limestr...@gmail.com

 When I explain to people what strict/lazy/eager mean, I often say
 something like :

 - Adjectives eager and lazy apply only to a global evaluation method:
 eager is C evaluation style and lazy is that of Haskell.
 - Adjective strict can be applied both to a global evaluation method and a
 specific function: if applied to an eval method then it's a synonym of
 strict, and if applied to a function f it means 'f ⊥ = ⊥' (which I detail
 a little more), which is true for strict State monad for istance (= would
 not allow its left argument to return ⊥).

 Thus explaining why datatypes such as State or Bytestring exist in strict
 and lazy flavours.


 2011/12/28 Albert Y. C. Lai tre...@vex.net

 There are two flavours of MonadState, Control.Monad.State.Lazy and
 Control.Monad.State.Strict. There are two flavours of ByteString,
 Data.ByteString.Lazy and Data.Bytestring (whose doc says strict). There
 are two flavours of I/O libraries, lazy and strict. There are advices of 
 the
 form: the program uses too much memory because it is too lazy; try making
 this part more strict. Eventually, someone will ask what are lazy and
 strict. Perhaps you answer this (but there are other answers, we'll see):

 lazy refers to such-and-such evaluation order. strict refers to f ⊥ = ⊥,
 but it doesn't specify evaluation order.

 That doesn't answer the question. That begs the question: Why do
 libraries seem to make them a dichotomy, when they don't even talk about 
 the
 same level? And the make-it-more-strict advice now becomes: the program
 uses too much memory because of the default, known evaluation order; try
 making this part use an unknown evaluation order, and this unknown is
 supposed to use less memory because...?

 I answer memory questions like this: the program uses too much memory
 because it is too lazy---or nevermind lazy, here is the current 
 evaluation
 order of the specific compiler, this is why it uses much memory; now change
 this part to the other order, it uses less memory. I wouldn't bring in the
 denotational level; there is no need.

 (Sure, I use seq to change evaluation order, which may be overriden by
 optimizations in rare cases. So change my answer to: now add seq here, 
 which
 normally uses the other order, but optimizations may override it in rare
 cases, so don't forget

Re: [Haskell-cafe] strict, lazy, non-strict, eager

2011-12-28 Thread Thiago Negri
2011/12/28 Jon Fairbairn jon.fairba...@cl.cam.ac.uk:
 * non-strict semantics require that no argument is evaluated
  unless needed.

That's not the case on optimistic evaluation.

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


Re: [Haskell-cafe] On the purity of Haskell

2011-12-28 Thread Thiago Negri
We can do functional programming on Java. We use all the design patterns
for that.

At the very end, everything is just some noisy, hairy, side-effectfull,
gotofull machinery code.

The beauty of Haskell is that it allows you to limit the things you need to
reason about. If I see a function with the type (a, b) - a I don't need
to read a man page to see where I should use it or not. I know what it can
do by its type. In C I can not do this. What can I say about a function
int foo(char* bar)? Does it allocate memory? Does it asks a number for
the user on stdin? Or does it returns the length of a zero-ending char
sequence? In fact it can do anything, and I can't forbid that. I can't
guarantee that my function has good behaviour. You need to trust the man
page.
Em 28/12/2011 22:24, Steve Horne sh006d3...@blueyonder.co.uk escreveu:

 On 28/12/2011 23:56, Bernie Pope wrote:

 On 29 December 2011 10:51, Steve 
 Hornesh006d3592@blueyonder.**co.uksh006d3...@blueyonder.co.uk
  wrote:

  As Simon Baron-Cohen says in Tackling the Awkward Squad...

 I think you've mixed up your Simons; that should be Simon Peyton Jones.

  Oops - sorry about that.

 FWIW - I'm diagnosed Aspergers. SBC diagnosed me back in 2001, shortly
 after 9/1/1.

 Yes, I *am* pedantic - which doesn't always mean right, of course.

 Not relevant, but what the hell.


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://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] If you'd design a Haskell-like language, what would you do different?

2011-12-20 Thread Thiago Negri
How would you represent it then?

Would it cause a compiler error?

Thiago.

2011/12/20 Ben Lippmeier b...@ouroborus.net:

 On 20/12/2011, at 6:06 PM, Roman Cheplyaka wrote:

 * Alexander Solla alex.so...@gmail.com [2011-12-19 19:10:32-0800]
 * Documentation that discourages thinking about bottom as a 'value'.  It's
 not a value, and that is what defines it.

 In denotational semantics, every well-formed term in the language must
 have a value. So, what is a value of fix id?

 There isn't one!

 Bottoms will be the null pointers of the 2010's, you watch.

 Ben.


 ___
 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] If you'd design a Haskell-like language, what would you do different?

2011-12-20 Thread Thiago Negri
What I think to be the hard part to do is to put this on the type system, e.g.:

intDiv x y = if y  x then 0 else 1 + (intDiv (x - y) y)

Should not compile. Otherwise you will need the bottom value.

Am I missing something?

Thiago.


2011/12/20 Jesse Schalken jesseschal...@gmail.com:
 On Tue, Dec 20, 2011 at 10:43 PM, Gregory Crosswhite gcrosswh...@gmail.com
 wrote:


 On Dec 20, 2011, at 9:18 PM, Jesse Schalken wrote:

 Why do you have to solve the halting problem?


 You have to solve the halting problem if you want to replace every place
 where _|_ could occur with an Error monad (or something similar), because
 _|_ includes occasions when functions will never terminate.


 I think we're talking about different things. By bottom I mean the
 function explicitly returns error ... or undefined. In those cases, it
 should go in an error monad instead. In cases where there is an infinite
 loop, the function doesn't return anything because it never finishes, and
 indeed this separate problem will never be solved while remaining Turing
 complete because it is the halting problem.



 Consider integer division by 0.  [...]
 This is all I was talking about.


 But imagine there was an occasion where you *knew* that the divisor was
 never zero --- say, because the divisor was constructed to be a natural
 number.


 Then use a separate type for natural numbers excluding 0. Then you can
 define a total integer division function on it (although the return value
 may be zero and so needs a different type).


 Now there is no point in running in the Error monad because there will
 never such a runtime error;  in fact, it is not clear what you would even
 *do* with a Left value anyway, short of terminating the program and printing
 and error, which is what would have happened anyway.


 What you do with a Left value is up to you - that's the point, you now have
 a choice. In fact, the value might not even be being handled by you, in
 which case someone else now has a choice.  Handling of the error is done in
 the same place as handling of the result, no IO needed.


 Furthermore, it is easy to imagine circumstances where you have now forced
 your entire program to run in the Error monad, which makes everything
 incredibly inconvenient with no benefit at all.


 This inconvenience I imagine is the extra code required to compose
 functions which return values in a monad as opposed to straight values. To
 me this is a small price to pay for knowing my code won't randomly crash,
 and I would rather this be handled syntactically to make composing monadic
 values more concise.

 The point is your program shouldn't be able to make assumptions about values
 without proving them with types. It's often easier not to make the
 assumption and propagate some error in an error monad instead, but that's
 better than getting away with the assumption and having the program crash or
 behave erratically because the assumption turned out false.

 This is the problem with arguments against partial functions;  they don't
 solve any problems at all except in the case where you have untrusted data
 in which case you should be using a different function or manually checking
 it anyway, and they add a lot of wasted overhead.


 The whole term untrusted data baffles me. How often can you actually
 trust your data? When you send your software out into the wild, what
 assumptions can you make about its input? What assumptions can you make
 about the input to a small part of a larger program which is millions of
 lines? You can often deduce that certain values do/do not occur in small
 parts of code, but the difficulty of such deductions increases exponentially
 with the size of the codebase, and is a job done much better by a type
 system.

 Also I would like to think this wasted overhead can be optimised away at
 some stage of compilation, or somehow removed without the programmer needing
 to think about it. Maybe I'm just dreaming on those fronts, however.

 Cheers,
 Greg



 ___
 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] Help understanding Haskell runtime costs

2011-08-11 Thread Thiago Negri
So, thanks to Henning Thielemann I was able to make a code a little
more functional.
I did find ByteString module that really speed things up.

I got 0.04 seconds with the following snippet:

-- code start
import qualified Data.ByteString.Char8 as BS
import Data.Char (toLower)

main :: IO ()
main = interact' $ unlines' . solveAll . takeWhile ((/= '*') . head') . lines'

solveAll :: [String'] - [String']
solveAll = map $ toStr . solve

toStr :: Bool - String'
toStr True = makeString' Y
toStr False = makeString' N

solve :: String' - Bool
solve = isTautogram . words'

isTautogram :: [String'] - Bool
isTautogram (x:xs) = all ((== firstChar) . normalizeHead) xs
where firstChar = normalizeHead x

normalizeHead :: String' - Char
normalizeHead = toLower . head'

-- optimizations
type String' = BS.ByteString
interact' = BS.interact
unlines' = BS.unlines
lines' = BS.lines
head' = BS.head
words' = BS.words
makeString' = BS.pack
-- code end

Thanks all,
Thiago.

2011/8/11 Henning Thielemann schlepp...@henning-thielemann.de:
 On 09.08.2011 01:43, Thiago Negri wrote:

 Hello all,

 I'm relatively new to Haskell and trying to solve some online judge's
 problems in it.
 One of the problems is to say if a given sentence is a tautogram or not.
 A tautogram is just a sentence with all the words starting with the same
 letter.

 My first try (solution is ok) was to do it as haskeller as possible,
 trying to overcome my imperative mind.
 But it did bad at performance (0.30 secs of runtime, 4.6 mb of memory):

 -- code start
 import Data.Char (toLower)

 main = getContents=  mapM_ (putStrLn . toStr . isTautogram . words)
 . takeWhile (/= *) . lines

 That's still imperative! :-)

 How about 'interact' and using 'unlines' instead of 'putStrLn' ?


 toStr :: Bool -  [Char]

 You may want to write String instead of [Char] for clarity.

 toStr True = Y
 toStr False = N

 isTautogram :: [[Char]] -  Bool
 isTautogram (x:[]) = True

 I assume this case is not necessary, since  all [] == True  anyway.

 isTautogram (x:xs) = all ((== firstChar) . toLower . head) xs
     where firstChar = toLower . head $ x

 It is maybe more elegant, not to compare all words with the first one, but
 to compare adjacent words in the list:

 all (zipWith (...) xs (drop 1 xs))


 Note that the only thing that changed between the two tries was the
 main-loop.
 The second version runs faster (got 0.11 secs) and with less memory (3.6
 mb)

 Can someone explain to me what is really going on?
 Maybe pointing out how I can achieve these optimizations using
 profiling information...

 Interesting observation. I do not see a problem quickly.

 ___
 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] Help understanding Haskell runtime costs

2011-08-08 Thread Thiago Negri
Hello all,

I'm relatively new to Haskell and trying to solve some online judge's
problems in it.
One of the problems is to say if a given sentence is a tautogram or not.
A tautogram is just a sentence with all the words starting with the same letter.

My first try (solution is ok) was to do it as haskeller as possible,
trying to overcome my imperative mind.
But it did bad at performance (0.30 secs of runtime, 4.6 mb of memory):

-- code start
import Data.Char (toLower)

main = getContents =  mapM_ (putStrLn . toStr . isTautogram . words)
. takeWhile (/= *) . lines

toStr :: Bool - [Char]
toStr True = Y
toStr False = N

isTautogram :: [[Char]] - Bool
isTautogram (x:[]) = True
isTautogram (x:xs) = all ((== firstChar) . toLower . head) xs
where firstChar = toLower . head $ x
-- code end

I tried to profile the code, but didn't find anything useful.
My bet is that all this words . lines is consuming more memory than
necessary, maybe saving space for the lines already processed.
Then I tried a some-what tail-call function, consuming one line at
each iteration:

-- code start
import Data.Char (toLower)

main :: IO ()
main = getLine = mainLoop

mainLoop :: [Char] - IO ()
mainLoop s | (head s) == '*' = return ()
   | otherwise   = (putStrLn . toStr . isTautogram . words
$ s)  main

toStr :: Bool - [Char]
toStr True = Y
toStr False = N

isTautogram :: [[Char]] - Bool
isTautogram (x:[]) = True
isTautogram (x:xs) = all ((== firstChar) . toLower . head) xs
where firstChar = toLower . head $ x
-- code end

Note that the only thing that changed between the two tries was the main-loop.
The second version runs faster (got 0.11 secs) and with less memory (3.6 mb)

Can someone explain to me what is really going on?
Maybe pointing out how I can achieve these optimizations using
profiling information...

Thanks,
Thiago.

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


Re: [Haskell-cafe] pointer equality

2011-07-20 Thread Thiago Negri
Hello all,
I'm a newbie at Haskell and I was not aware of this problem.
So, equality comparison can run into an infinite-loop?

My current knowledge of the language tells me that everything is
Haskell is a thunk until it's value is really needed.
Is it possible to implement (==) that first check these thunks before
evaluating it? (Considering both arguments has pure types).


E.g.,

Equivalent thunks, evaluates to True, does not need to evaluate its arguments:
[1..] == [1..]


Another case:

fib = 1:1:zipWith (+) fib (tail fib)
fibA = 1:tail fib
fib == fibA -- True


Evaluating:

1:1:zipWith (+) fib (tail fib) == 1:tail fib -- first item match, check further
1:zipWith (+) fib (tail fib) == tail fib -- thunks do not match,
evaluate arguments
1:zipWith (+) fib (tail fib) == 1:zipWith (+) fib (tail fib) -- thunks
matches, comparison stops and the value is True


As I said before, I'm a newbie at Haskell. Sorry if my question or
examples makes no sense.

Thanks,
Thiago.

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