Re: [Haskell-cafe] Best way to build strings?
On Wed, 2005-07-20 at 17:06 +0100, Andy Gimblett wrote: > A small stylistic question: what's the "best" way to build strings > containing other values? For example, I have: > > data Process = Stop | >Prefix String Process | >External Process Process > > instance Show Process where > show Stop = "Stop" > show (Prefix l p) = "(" ++ l ++ "->" ++ show p ++ ")" > show (External p q) = "(" ++ show p ++ " [] " ++ show q ++ ")" > > but to me the extensive use of ++ is not particularly readable. It is also inefficient because append has complexity proportional to the length of its left argument. That's why the Prelude defines: type ShowS = String -> String and functions like showsPrec, shows, showChar > Is there a facility like this in Haskell? Or something else I should > be using, other than lots of ++ ? It looks to me like you are doing some kind of pretty printing - that is you are not printing the term using Haskell syntax. My preference is to only use Show where it is derived from the data declaration, and use a hand-written pretty printer for other tasks, for example Text.PrettyPrint Cheers, Bernie. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Updating the Haskell Standard
On 20-Jul-2005, David Barton <[EMAIL PROTECTED]> wrote: > I can contribute some experience from commercial standardization efforts. > ANSI, IEEE, and ISO standards require re-ballotting every five years, > otherwise the standards lapse. Reballotting may or may not be accompanied > by changes in the standard; for a standard as complex as a language, new > versions at least every five years seems to be fairly common with "newer" > standards [...] Five years is > what the general industry seems to have settled on as a good average, but > it may or may not apply here; the circumstances are different. ANSI/ISO programming language standards typically undergo major updates every 10 years or so: Fortran 66, 77, 95, 2003; COBOL 68, 74, 85, 2002; Ada 83, 95, 2005; C 89, 99; C++ 98, 200x (for some x >= 5). > (ANSI C has not changed in newer standardization ballots as far > as I know). A major new update to the ANSI/ISO C standard was issued in 1999. -- Fergus J. Henderson | "I have always known that the pursuit Galois Connections, Inc.| of excellence is a lethal habit" Phone: +1 503 626 6616 | -- the last words of T. S. Garp. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
RE: [Haskell-cafe] Re: FFI and callbacks
On 20 July 2005 18:49, John Goerzen wrote: > On 2005-07-20, Simon Marlow <[EMAIL PROTECTED]> wrote: >> This paper might help shed some light: >> >> http://www.haskell.org/~simonmar/papers/conc-ffi.pdf > > Forgot to reply to this. *Very helpful* link, I had always wondered > what the bound thread functions in Control.Concurrent were for :-) > > So let me see if I understand this correctly. > > Let's say that I have: > > * A program that uses multiple lightweight Haskell threads (all >started with plain forkIO calls) > > * An event-driven C library, not not thread-aware, with a blocking >main loop > > * GHC 6.4 > > * My C calls all imported "safe". > > Now then, if I understand this correctly, that a call to the C main > loop will create a new bound OS thread, so it will not interrupt any > other forkIO'd threads in Haskell. Not necessarily a *bound* OS thread. A bound thread is only created by an in-call to Haskell. An out-call may happen in a separate OS thread if the foreign import is "safe", that is, another OS thread will continue to run the remaining Haskell threads while the call is in progress. > However, if one of my Haskell-based callbacks creates new threads with > forkIO, I could be in trouble; if they make any calls into C, a new > bound OS thread would be created for them, and this could wind up > causing trouble in C. I would probably need some sort of "global > MVar" to synchronize access into the C world. Bingo. This is why you need to make all your calls to the C library from a single thread. > I also have some follow-up questions after looking at the > Control.Concurrent API: > > 1. It seems that there is no function that says "block the current > thread until the thread given by ThreadId dies" You can do something like this with an exception handler and an MVar or TVar: do died <- atomically $ newTVar False forkIO (later (atomically $ writeTVar died True) $ ...) let wait = atomically $ do b <- readTVar died when (not b) retry where later = flip finally granted, it's hard to implement exactly what you were asking for. Another way to do it would be to put a finalizer on the ThreadId, but that would incur a delay until the GC discovered the thread was unreachable. Hmm, perhaps we should have threadIsAlive :: ThreadId -> STM Bool > 2. What is the preferred way to implement a simple lock? With an > MVar? TVars are the way to go, although MVars do perform slightly better at the moment (at least if you stick to the simple putMVar/takeMVar operations). Cheers, Simon ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Updating the Haskell Standard
John Goerzen writes: There was a brief discussion on #haskell today about the Haskell standard. I'd like to get opinions from more people, and ask if there is any effort being done in this direction presently. I know that some people would like to hold off on such a process until their favorite feature (we'll call it feature X) is finished. I would argue that incremental addendums to the standard should be made more frequently, so that new features can be standardized more easily. Thoughts? I can contribute some experience from commercial standardization efforts. ANSI, IEEE, and ISO standards require re-ballotting every five years, otherwise the standards lapse. Reballotting may or may not be accompanied by changes in the standard; for a standard as complex as a language, new versions at least every five years seems to be fairly common with "newer" standards (ANSI C has not changed in newer standardization ballots as far as I know). The trade-off for standards is between stability for tool developers and learners and stagnation. If the standard changes too often, there will be only one developer (the one effectively "in charge" of the standard) and it will tend to not be taught anywhere (because what students learn is obsolete too quickly). If the standard is unchanged too long, it becomes irrelevant and obsolete and no one pays attention to it. Five years is what the general industry seems to have settled on as a good average, but it may or may not apply here; the circumstances are different. Developers of Haskell are pretty much volunteers and academics; that changes things. On the other hand, it is a rapidly developing field. How all this shakes out is something for the community at large to decide; however, that is what happens in other standards bodies. Dave Barton EDAptive Computing ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Updating the Haskell Standard
There was a brief discussion on #haskell today about the Haskell standard. I'd like to get opinions from more people, and ask if there is any effort being done in this direction presently. I think an updated standard is overdue. I find it difficult anymore to write any but the most trivial of programs using pure Haskell 98. Some notable, and widely-used, features developed since then include: * Overlapping instances * FFI * Hierarchical namespace * Undecidable instances * All sorts of updates to the standard library It has been awhile since I wrote a Haskell program that can compile in pure Haskell 98 mode. I think it would benefit everyone if a more up-to-date standard were made available. I know that some people would like to hold off on such a process until their favorite feature (we'll call it feature X) is finished. I would argue that incremental addendums to the standard should be made more frequently, so that new features can be standardized more easily. Thoughts? Who organized the standardization effort last time? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: FFI and callbacks
On 2005-07-20, Simon Marlow <[EMAIL PROTECTED]> wrote: > This paper might help shed some light: > > http://www.haskell.org/~simonmar/papers/conc-ffi.pdf Forgot to reply to this. *Very helpful* link, I had always wondered what the bound thread functions in Control.Concurrent were for :-) So let me see if I understand this correctly. Let's say that I have: * A program that uses multiple lightweight Haskell threads (all started with plain forkIO calls) * An event-driven C library, not not thread-aware, with a blocking main loop * GHC 6.4 * My C calls all imported "safe". Now then, if I understand this correctly, that a call to the C main loop will create a new bound OS thread, so it will not interrupt any other forkIO'd threads in Haskell. However, if one of my Haskell-based callbacks creates new threads with forkIO, I could be in trouble; if they make any calls into C, a new bound OS thread would be created for them, and this could wind up causing trouble in C. I would probably need some sort of "global MVar" to synchronize access into the C world. I also have some follow-up questions after looking at the Control.Concurrent API: 1. It seems that there is no function that says "block the current thread until the thread given by ThreadId dies" 2. What is the preferred way to implement a simple lock? With an MVar? Thanks. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Best way to build strings?
On Wed, Jul 20, 2005 at 07:00:22PM +0200, Lemmih wrote: > On 7/20/05, Andy Gimblett <[EMAIL PROTECTED]> wrote: > > > > Is there a facility like this in Haskell? Or something else I should > > be using, other than lots of ++ ? > > There's Text.Printf: > > Prelude Text.Printf> printf "(%s [] %s)" "hello" "world" :: String > "(hello [] world)" If you only use GHC, you can also implement (or borrow) a type-safe printf using Template Haskell. I think there's some implementation made by Ian Lynagh. Recently I needed to build strings containing shell commands and I also didn't like the ++ approach. I didn't like the printf approach, but rather wanted something more like shell's or Perl's string interpolation, so I could write something like "($p [] $q)" and have $p and $q expanded to values of p and q. I created a small TH library for this (attached). It uses such syntax: $(interp "(%{p} [] %{q})"). I used % because I knew I would often have to use literal $'s. Unfortunately it has some problems. First, TH sometimes doesn't like when I use a global variable in %{ }. I had to work around it by defining additional local helper variables. Second, it would be nice to be able to put arbitrary Haskell expressions inside %{ } - but I couldn't find a Haskell syntax parser producing TH ASTs. There must be some - I guess Template Haskell uses one internally. Best regards Tomasz {-# OPTIONS -fglasgow-exts #-} module Interpolate where import Text.ParserCombinators.Parsec import Language.Haskell.TH interp s = do parts <- case parse (do ps <- many interp_part; eof; return ps) s s of Left err -> fail (show err) Right x -> return x [| concat $(return (ListE parts)) |] interp_part = choice [do char '%' choice [do char '%' return (LitE (StringL "%")) ,do char '{' name <- many1 (noneOf "}") char '}' return (VarE (mkName name)) ] ,do cs <- many1 (noneOf "%") return (LitE (StringL cs)) ] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: FFI and callbacks
On 2005-07-20, Simon Marlow <[EMAIL PROTECTED]> wrote: > You could forkIO the main loop if you want; it shouldn't make any > difference, except that GHC terminates the program when the main thread > completes, so it's more convenient to have the main loop run in the main > thread, so that the program terminates when the main loop returns. Here's my concern. I assume that, internally, forkIO is implemented using poll() or select(). This obviously requires that all parts of the program cooperate with this mechanism. If this mainloop never returns (that is, it blocks until the UI is destroyed), how do other forkIO'd threads ever get a chance to run? Assuming my program uses only forkIO threads, does the C library really need to be thread-safe? -- John ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Best way to build strings?
On 7/20/05, Andy Gimblett <[EMAIL PROTECTED]> wrote: > A small stylistic question: what's the "best" way to build strings > containing other values? For example, I have: > > data Process = Stop | >Prefix String Process | >External Process Process > > instance Show Process where > show Stop = "Stop" > show (Prefix l p) = "(" ++ l ++ "->" ++ show p ++ ")" > show (External p q) = "(" ++ show p ++ " [] " ++ show q ++ ")" How about leaving the Show instance automatically derived and defining this instead: showProcess :: Process -> ShowS showProcess Stop = showString "Stop" showProcess (Prefix l p) = showBody (showString l) (showProcess p) showProcess (External p q) = showBody (showProcess p) (showProcess q) showBody :: ShowS -> ShowS -> ShowS showBody a b = showParen True (a . showString " [] " . b) > but to me the extensive use of ++ is not particularly readable. > > I'm very fond of Python's interpolation approach, where we'd have > something like the following for the External case: > > def __str__(self): > return "(%s [] %s)" % (self.p, self.q) > > which to me seems clearer, or at least easier to work out roughly what > the string's going to look like. (The %s does an implicit "convert to > string", btw). > > Is there a facility like this in Haskell? Or something else I should > be using, other than lots of ++ ? There's Text.Printf: Prelude Text.Printf> printf "(%s [] %s)" "hello" "world" :: String "(hello [] world)" -- Friendly, Lemmih ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Best way to build strings?
Hello there, > I'm very fond of Python's interpolation approach, where we'd have > something like the following for the External case: > > def __str__(self): > return "(%s [] %s)" % (self.p, self.q) are you familiar with C's printf procedure? It's where that kind of notation comes from. You can use Text.Printf which provides the function printf :: PrintfType r => String -> r Thus you can write show (Prefix l p) = printf "(%s->%s)" l q show (External p q) = printf "(%s [] %s)" p q Alas, I couldn't test it, because the Text module seems to not be installed on my computer (sad thing not being the admin, isn't it?) Nevertheless, take a look at http://www.haskell.org/ghc/docs/latest/html/libraries/base/Text.Printf.html Regards, Frank-Andre Riess ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Best way to build strings?
How about this? instance Show Process where show Stop = "Stop" show (Prefix l p) = concat ["(", l, "->", show p, ")"] show (External p q) = concat ["(", show p, " [] ", show q, ")"] Hope that helps, Bryn Andy Gimblett wrote: A small stylistic question: what's the "best" way to build strings containing other values? For example, I have: data Process = Stop | Prefix String Process | External Process Process instance Show Process where show Stop = "Stop" show (Prefix l p) = "(" ++ l ++ "->" ++ show p ++ ")" show (External p q) = "(" ++ show p ++ " [] " ++ show q ++ ")" but to me the extensive use of ++ is not particularly readable. I'm very fond of Python's interpolation approach, where we'd have something like the following for the External case: def __str__(self): return "(%s [] %s)" % (self.p, self.q) which to me seems clearer, or at least easier to work out roughly what the string's going to look like. (The %s does an implicit "convert to string", btw). Is there a facility like this in Haskell? Or something else I should be using, other than lots of ++ ? Thanks, -Andy ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] file line operation perhaps need loop
On Wednesday 20 July 2005 08:27, Sun Yi Ming wrote: > Hello, > I have two txt file,and i want to mix the two files line by line, > [...] > import System.IO > > mix :: [a] -> [a] -> [a] > mix [] ys = ys > mix xs [] = xs > mix (x:xs) (y:ys) = [x,y] ++ mix xs ys > > f1 = do contents1 <- readFile "url1.txt" > contents2 <- readFile "url2.txt" > let urls1 = lines contents1 > urls2 = lines contents2 > urls = mix urls1 urls2 > writeFile "aha.txt" (unlines urls) > -- > this works fine, but i think if the two file are very big, and the > readFile will consume too many mem. No. Both files are read lazily (on demand). THis is how 'readFile' is specified. The program should work fine even with very large files. Try it. Ben ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] How to parsing files
On Wed, 20 Jul 2005, Jake Luck wrote: > > I need to parse a file in this format: > > float float float > > float float float > > Each row has 3-columns of floating procision number divided by white > > space. The number of lines is undefined. I use (lines (readFile "...")) > > to read the file. > > Text.ParserCombinators.Parsec sounds perfect, no? That's certainly overkill since 'lines', 'words', 'read' will suffice. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] How to parsing files
I need to parse a file in this format: float float float float float float Each row has 3-columns of floating procision number divided by white space. The number of lines is undefined. I use (lines (readFile "...")) to read the file. Text.ParserCombinators.Parsec sounds perfect, no? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Best way to build strings?
A small stylistic question: what's the "best" way to build strings containing other values? For example, I have: data Process = Stop | Prefix String Process | External Process Process instance Show Process where show Stop = "Stop" show (Prefix l p) = "(" ++ l ++ "->" ++ show p ++ ")" show (External p q) = "(" ++ show p ++ " [] " ++ show q ++ ")" but to me the extensive use of ++ is not particularly readable. I'm very fond of Python's interpolation approach, where we'd have something like the following for the External case: def __str__(self): return "(%s [] %s)" % (self.p, self.q) which to me seems clearer, or at least easier to work out roughly what the string's going to look like. (The %s does an implicit "convert to string", btw). Is there a facility like this in Haskell? Or something else I should be using, other than lots of ++ ? Thanks, -Andy -- Andy Gimblett Computer Science Department University of Wales Swansea http://www.cs.swan.ac.uk/~csandy/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
RE: [Haskell-cafe] FFI and callbacks
On 20 July 2005 16:23, John Goerzen wrote: > On Wed, Jul 20, 2005 at 04:10:38PM +0100, Simon Marlow wrote: >> On 20 July 2005 14:35, John Goerzen wrote: >>> These systems generally have some sort of an opaque main loop, >>> implemented in C. This loop would usually never return, or perhaps >>> only return once the UI is destroyed. >> >> Is the library thread-safe or not? I mean OS-thread safe. If it is, >> then you're home and dry: just compile your program with GHC's >> -threaded option, and any foreign calls that need to run >> concurrently with Haskell threads must be declared "safe" (which is >> the default in fact, so instead I should really advise you to mark >> all calls that don't need to run concurrently as "unsafe", because >> that's good for performance). > > That's half of the question. The other half is: what is the canonical > way of handling this mainloop that doesn't return from Haskell? Do we > just treat it that way in Haskell as well, or would some people forkIO > it? You could forkIO the main loop if you want; it shouldn't make any difference, except that GHC terminates the program when the main thread completes, so it's more convenient to have the main loop run in the main thread, so that the program terminates when the main loop returns. > Does any part of your answer vary depending on whether the Haskell > threads in question are forkIO threads or forkOS threads? I imagine > that it might. No, and I don't think you need forkOS here. This paper might help shed some light: http://www.haskell.org/~simonmar/papers/conc-ffi.pdf >> If the library isn't thread-safe, then you're in the same boat as Gtk >> and wxHaskell (I believe) where there are known problems with having >> a multithreaded Haskell GUI app. You can only have one OS thread >> (and hence only one Haskell thread) doing GUI operations, and that >> is the > > What about multiple forkIO threads? You should think of Haskell as having a one-to-one mapping between OS threads and Haskell threads. The only difference between forkIO and forkOS is that a forkIO thread can migrate from one OS thread to another, whereas a forkOS thread always runs on the same OS thread. This difference is therefore only visible when you make FFI calls, because there's no way in Haskell to tell what OS thread you're running on. In practice, GHC uses an optimised implementation to take advantage of the fact that forkIO threads are allowed to migrate from one OS thread to another, and it runs all the forkIO threads using a small pool of worker OS threads. The design of forkIO/forkOS and the FFI is carefully crafted to accommodate both GHC's optimised implementation and simpler implementations such as one-to-one or a giant lock. >> thread in the main loop. You have to somehow set up a communication >> between your other Haskell threads and the thread running the main >> loop - perhaps you can send requests of type (IO ()) down a channel >> to the main loop thread which wakes up occasionally to run them, for >> example. > > I imagine there could be exceptions to this.. For instance, perhaps a > given operation needs to do 5 things, perhaps simultaneously, before > displaying a result. It could, perhaps, fire off five threads and > just not display a result until all five have terminated, yes? Sure, but it's just a matter of converting direct GUI calls into RPCs to the GUI thread, using some appropriate RPC mechanism. Cheers, Simon ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] FFI and callbacks
On Wed, Jul 20, 2005 at 04:10:38PM +0100, Simon Marlow wrote: > On 20 July 2005 14:35, John Goerzen wrote: > > These systems generally have some sort of an opaque main loop, > > implemented in C. This loop would usually never return, or perhaps > > only return once the UI is destroyed. > > Is the library thread-safe or not? I mean OS-thread safe. If it is, > then you're home and dry: just compile your program with GHC's -threaded > option, and any foreign calls that need to run concurrently with Haskell > threads must be declared "safe" (which is the default in fact, so > instead I should really advise you to mark all calls that don't need to > run concurrently as "unsafe", because that's good for performance). That's half of the question. The other half is: what is the canonical way of handling this mainloop that doesn't return from Haskell? Do we just treat it that way in Haskell as well, or would some people forkIO it? Does any part of your answer vary depending on whether the Haskell threads in question are forkIO threads or forkOS threads? I imagine that it might. Unfortunately, the library I'm leaning towards packaging is not thread-safe. There is another library that is, but it is written in C++, and making a Haskell binding for that is a little more than I have the skills to do at the moment. > If the library isn't thread-safe, then you're in the same boat as Gtk > and wxHaskell (I believe) where there are known problems with having a > multithreaded Haskell GUI app. You can only have one OS thread (and > hence only one Haskell thread) doing GUI operations, and that is the What about multiple forkIO threads? > thread in the main loop. You have to somehow set up a communication > between your other Haskell threads and the thread running the main loop > - perhaps you can send requests of type (IO ()) down a channel to the > main loop thread which wakes up occasionally to run them, for example. I imagine there could be exceptions to this.. For instance, perhaps a given operation needs to do 5 things, perhaps simultaneously, before displaying a result. It could, perhaps, fire off five threads and just not display a result until all five have terminated, yes? Thanks, -- John ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
RE: [Haskell-cafe] FFI and callbacks
On 20 July 2005 14:35, John Goerzen wrote: > I'm looking at packaging an event-driven console widget set (CDK) for > Haskell using FFI. I know that other event-driven widget sets have > Haskell bindings, but I'm not quite sure how to make everything play > nice with forkIO. > > These systems generally have some sort of an opaque main loop, > implemented in C. This loop would usually never return, or perhaps > only return once the UI is destroyed. Is the library thread-safe or not? I mean OS-thread safe. If it is, then you're home and dry: just compile your program with GHC's -threaded option, and any foreign calls that need to run concurrently with Haskell threads must be declared "safe" (which is the default in fact, so instead I should really advise you to mark all calls that don't need to run concurrently as "unsafe", because that's good for performance). If the library isn't thread-safe, then you're in the same boat as Gtk and wxHaskell (I believe) where there are known problems with having a multithreaded Haskell GUI app. You can only have one OS thread (and hence only one Haskell thread) doing GUI operations, and that is the thread in the main loop. You have to somehow set up a communication between your other Haskell threads and the thread running the main loop - perhaps you can send requests of type (IO ()) down a channel to the main loop thread which wakes up occasionally to run them, for example. Cheers, Simon ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re[2]: [Haskell-cafe] matrix computations based on the GSL
Hello Alberto, Tuesday, July 19, 2005, 5:11:27 PM, you wrote: AR> Hello Bulat, thanks a lot for your message, the RULES pragma is just what we AR> need! AR> However, in some initial experiments I have observed some strange behavior. AR> For instance, in the following program: 1) there is no guaranties of any kind, explicit or implied, that your RULE will be ever used :) 2) you can report this as misfeature to GHC team -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Named data type members
Hello yin, Wednesday, July 20, 2005, 1:18:25 AM, you wrote: y> data SomeData = y> SomeData { y> int1 :: Int, y> int2 :: Int y> } y> class SomeClass where y>infix 1 `i_` y>i_ :: SomeData -> Int -> SomeData y>infix 1 `_i` y>_i :: SomeData -> Int -> SomeData y> instance SomeClass SomeData where y>(SomeData int1 int2) `i_` i = SomeData (int1 + i) int2 y>(SomeData int1 int2) `_i` i = SomeData int1 (int2 + i) data SomeData = SomeData { int1 :: Int, int2 :: Int } infix 1 `i_` i_ :: SomeData -> Int -> SomeData (SomeData int1 int2) `i_` i = SomeData (int1 + i) int2 infix 1 `_i` _i :: SomeData -> Int -> SomeData (SomeData int1 int2) `_i` i = SomeData int1 (int2 + i) y> -- SomeData is now very complex y> initsomeData :: SomeData y> initsomeData = do y> var1 <- init... y> ... y> SomeData 0 0 0 1 1 True False (-1) var1 var2 ... initsomeData :: IO SomeData initsomeData = do var1 <- init... ... return$ SomeData { int1 = 0 , int2 = 0 } if you will use postional notation, your program can get hard bugs when you will add new fields to the structure y> main = do p <- initAplication y>processEvents p main = do p <- initAplication processEvents p y> -- First Function y> processEvents :: SomeData -> IO () y> processEvents p = do y>event <- pollEvent y>case event of y> Event1 -> do y> processEvents (SomeData v1 v2 v3 (v4*2) ... v100) y> Event2 -> do y> processEvents (SomeData v1 ... False ... v100) y> Event2' -> do y> processEvents (SomeData v1 ... True ... v100) y> EventQuit -> do y> return () y> NoMoreEvents -> do computeNext p y> _ -> processEvents p y>where (SomeData v1 v2 v3 v4 v5 ... v100) = p processEvents :: SomeData -> IO () processEvents p = do event <- pollEvent case event of Event1 -> processEvents p{ int3 = (int3 p) * 2 } Event2 -> processEvents p{ bool1 = False } EventQuit-> return () NoMoreEvents -> computeNext p _-> processEvents p y> -- An time based function y> computeNextStep = do y> timeDelta <- getTimeDelta y> let y> i1' = compute1 i1 i2 i3 ... i50 y> i2' = compute2 i1 i2 i3 ... i50 y>... y>if (condition) then y> -- need more computing y> computeNextStep (SomeData u1 u2 ... u50 i1 i2 ... i50) y>else do y> p' <- (SomeData u1 u2 ... u50 i1 i2 ... i50) let p = p {i1=1, i2=2} -- other fields will left unchanged y> draw p' y> processEvents p' y>where (SomeData u1 u2 ... u50 i1 i2 ... i50) = p y> -- ux - uninteresting (State variables, like left-key-down y> was last left-key related event: move left) y> -- ix - interesting for computing y> -- where x = 1, 2 ... 50 y> ... y> ... y> 3b. every funtion needs only a part of the data... can I build for every y> fintion a class with defined operators to manipulate with the data and then: y> * pass the variable in func1 known as class A to func2, which is y> infering a class B? i don't understand what you mean -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
RE: [Haskell-cafe] FFI and callbacks
> From: John Goerzen [mailto:[EMAIL PROTECTED] > > How would I make this sort of system play nice with Haskell threads? > > Also, the brief FFI docs that I've found don't really explain > callbacks > in FFI very well to me. Are there any other resources on > this anywhere? This might help: http://www.haskell.org/ghc/docs/latest/html/libraries/base/Foreign.Ptr.html# t%3AFunPtr ...and I can also show you some code which uses a simple callback. Or are you past that stage now, and more worried about interaction of callbacks and threads? Alistair. - * Confidentiality Note: The information contained in this message, and any attachments, may contain confidential and/or privileged material. It is intended solely for the person(s) or entity to which it is addressed. Any review, retransmission, dissemination, or taking of any action in reliance upon this information by persons or entities other than the intended recipient(s) is prohibited. If you received this in error, please contact the sender and delete the material from any computer. * ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] FFI and callbacks
Hi, I'm looking at packaging an event-driven console widget set (CDK) for Haskell using FFI. I know that other event-driven widget sets have Haskell bindings, but I'm not quite sure how to make everything play nice with forkIO. These systems generally have some sort of an opaque main loop, implemented in C. This loop would usually never return, or perhaps only return once the UI is destroyed. How would I make this sort of system play nice with Haskell threads? Also, the brief FFI docs that I've found don't really explain callbacks in FFI very well to me. Are there any other resources on this anywhere? Thanks, -- John ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Word32 to Int converions
On Wed, 20 Jul 2005, yin wrote: > Bernard Pope wrote: > > >On Wed, 2005-07-20 at 11:43 +0200, yin wrote: > > > >> > >>how do I convert an Word32 (or WordXYZ) to Int, or Integer, or Float, > >>...? The Int conversion is the priority. > >> > >> > >fromIntegral to convert to an instance of Integral, such as Int, Integer > >etc > > > Thank you, but how to "Work32 -> Int"? Note that this compiles: foo :: Word32 -> Int foo = fromIntegral fromIntegral really is what you want. -- Mark ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] How to parsing files
Hi, I need to parse a file in this format: float float float float float float Each row has 3-columns of floating procision number divided by white space. The number of lines is undefined. I use (lines (readFile "...")) to read the file. Thnks. Matej 'Yin' Gagyi ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
RE: [Haskell-cafe] Strict and non-strict vs eager and lazy, was Confused about Cyclic struture
On 18 July 2005 15:19, Bayley, Alistair wrote: > Not a taker (yet - where can I find information about non-lazy > implementation of non-strict languages? From Google so far: > speculative evaluation (Eager Haskell), call-by-name vs call-by-need.) > > Wikipedia frustratingly hints that "other evaluation strategies are > possible", but that's all it says: > http://en.wikipedia.org/wiki/Non-strict_programming_language While most of Haskell admits other evaluation strategies, lazy I/O pretty much requires lazy evaluation for lazy input streams. If the list returned by getContents is evaluated mulitple times, you don't want to read more data from the input each time, hence previous evaluations must be shared. Cheers, Simon "down with lazy I/O" Marlow ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Haskell, SDL, OpenGL
On 7/20/05, Sven Panne <[EMAIL PROTECTED]> wrote: > Am Montag, 18. Juli 2005 18:46 schrieb yin: > > [...] > > ld-options: -L/usr/lib -Wl -rpath /usr/lib -lSDL > > This looks a bit suspicious: The syntax for ld options is "-rpath DIR", so the > option for gcc should be "-Wl,-rpath,DIR". Ugly, but I didn't invent > that. :-) Furthermore, I've never seen a Linux/*nix system where the > (dynamic) linker doesn't look into /usr/lib, so probably the best way is to > simply use: > >ld-options: -lSDL > > In addition, the -rpath option can be a bit surprising for the user of the > executable later, depending on OS/platform peculiarities. 'sdl-config' is used to set 'ld-options'. Hard coding it is not an option. -- Friendly, Lemmih ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Word32 to Int converions
Bernard Pope wrote: >On Wed, 2005-07-20 at 11:43 +0200, yin wrote: > >> >>how do I convert an Word32 (or WordXYZ) to Int, or Integer, or Float, >>...? The Int conversion is the priority. >> >> >fromIntegral to convert to an instance of Integral, such as Int, Integer >etc > Thank you, but how to "Work32 -> Int"? Matej 'Yin' Gagyi ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] file line operation perhaps need loop
Arthur van Leeuwen <[EMAIL PROTECTED]> worte: > Ah, but this is exactly where lazyness wins bigtime: a smart > implementation > of readFile will lazily read the actual file for as far as needed. Thus, > reading with readFile will not read the entire file into memory at once. > What will happen is that writeFile starts writing, and upon discovery of > needing the value of urls it will then start reading. Any value already > written in this case obviously turns into garbage and will be garbage > collected. I would be slightly surprised if this code uses more than > constant memory. > >> so i need to read the file >> line by line but stunned by the loop in IO Monad: >> --- >> main = do h1 <- openFile "url1.txt" ReadMode >> h2 <- openFile "url2.txt" ReadMode >> line1 <- hGetLine h1 >> line2 <- hGetLine h2 >> print $ line1 : line2 : [] -- i don't howto do >> hClose h1 >> hClose h2 >> -- >> any ideas? thank you all. > > Yes. You need to split the lines > >line1 <- hGetLine h1 >line2 <- hGetLine h2 >print $ line1 : line2: [] > > into a separate function that will then recurse over the file. ah, readFile is lazy,that's great! my hat's off to the haskell design/implement teams for their robust and elegant work. thank all you guys! BTW, sorry to Doei Arthur for my reply to you by mistake. -- Sun Yi Ming ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] file line operation perhaps need loop
On Wed, 20 Jul 2005, Sun Yi Ming wrote: > mix :: [a] -> [a] -> [a] > mix [] ys = ys > mix xs [] = xs > mix (x:xs) (y:ys) = [x,y] ++ mix xs ys mix xs ys = concat (Data.List.transpose [xs,ys]) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Word32 to Int converions
On Wed, 2005-07-20 at 11:43 +0200, yin wrote: > hello, > > how do I convert an Word32 (or WordXYZ) to Int, or Integer, or Float, > ...? The Int conversion is the priority. > > Thanks. > > Matej 'Yin' Gagyi fromIntegral to convert to an instance of Integral, such as Int, Integer etc Cheers, Bernie. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Error with Float
To get exact fractions, use the Ratio module (import Ratio) and the Rational type which is defined there. Thanks dude, it works The code you wrote below has a serious style problem that I thought I'd point out: you shouldn't use the IO monad for pure functions. I've never known that, thanks a lot TuanAnh _ It's fast, it's easy and it's free. Get MSN Messenger 7.0 today! http://messenger.msn.co.uk ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Word32 to Int converions
hello, how do I convert an Word32 (or WordXYZ) to Int, or Integer, or Float, ...? The Int conversion is the priority. Thanks. Matej 'Yin' Gagyi ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] file line operation perhaps need loop
On Wed, 2005-07-20 at 14:27 +0800, Sun Yi Ming wrote: [snip] > i first write this snippet of code: > --- > import System.IO > > mix :: [a] -> [a] -> [a] > mix [] ys = ys > mix xs [] = xs > mix (x:xs) (y:ys) = [x,y] ++ mix xs ys > > f1 = do contents1 <- readFile "url1.txt" > contents2 <- readFile "url2.txt" > let urls1 = lines contents1 > urls2 = lines contents2 > urls = mix urls1 urls2 > writeFile "aha.txt" (unlines urls) > -- > this works fine, but i think if the two file are very big, and the readFile > will consume too many mem.so i need to read the file line by line but stunned > by the loop in IO Monad: Did you try it on a big file to see what happens? There should not be any problem because readFile is lazy. That is it reads the contents of the file on demand, not all at once. The only thing you have to be careful about is that you do not require all the contents of the file before any output can be produced. Bernie. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Haskell, SDL, OpenGL
Am Montag, 18. Juli 2005 18:46 schrieb yin: > [...] > ld-options: -L/usr/lib -Wl -rpath /usr/lib -lSDL This looks a bit suspicious: The syntax for ld options is "-rpath DIR", so the option for gcc should be "-Wl,-rpath,DIR". Ugly, but I didn't invent that. :-) Furthermore, I've never seen a Linux/*nix system where the (dynamic) linker doesn't look into /usr/lib, so probably the best way is to simply use: ld-options: -lSDL In addition, the -rpath option can be a bit surprising for the user of the executable later, depending on OS/platform peculiarities. Cheers, S. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] file line operation perhaps need loop
On Wed, Jul 20, 2005 at 02:27:36PM +0800, Sun Yi Ming wrote: > Hello, > I have two txt file,and i want to mix the two files line by line, e.g. > $ cat url1.txt >url1_1.line >url1_2.line > $ cat url2.txt >url2_1.line >url2_2.line > and i want this file as result: > $ cat aha.txt >url1_1.line >url2_1.line >url1_2.line >url2_2.line > > i first write this snippet of code: > --- > import System.IO > > mix :: [a] -> [a] -> [a] > mix [] ys = ys > mix xs [] = xs > mix (x:xs) (y:ys) = [x,y] ++ mix xs ys > > f1 = do contents1 <- readFile "url1.txt" > contents2 <- readFile "url2.txt" > let urls1 = lines contents1 > urls2 = lines contents2 > urls = mix urls1 urls2 > writeFile "aha.txt" (unlines urls) > -- > this works fine, but i think if the two file are very big, and the > readFile will consume too many mem. Ah, but this is exactly where lazyness wins bigtime: a smart implementation of readFile will lazily read the actual file for as far as needed. Thus, reading with readFile will not read the entire file into memory at once. What will happen is that writeFile starts writing, and upon discovery of needing the value of urls it will then start reading. Any value already written in this case obviously turns into garbage and will be garbage collected. I would be slightly surprised if this code uses more than constant memory. > so i need to read the file > line by line but stunned by the loop in IO Monad: > --- > main = do h1 <- openFile "url1.txt" ReadMode > h2 <- openFile "url2.txt" ReadMode > line1 <- hGetLine h1 > line2 <- hGetLine h2 > print $ line1 : line2 : [] -- i don't howto do > hClose h1 > hClose h2 > -- > any ideas? thank you all. Yes. You need to split the lines line1 <- hGetLine h1 line2 <- hGetLine h2 print $ line1 : line2: [] into a separate function that will then recurse over the file. Doei, Arthur. -- /\/ | [EMAIL PROTECTED] | Work like you don't need the money /__\ / | A friend is someone with whom | Love like you have never been hurt /\/__ | you can dare to be yourself | Dance like there's nobody watching ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] file line operation perhaps need loop
Sun Yi Ming wrote: > Hello, Hello, > this works fine, but i think if the two file are very big, and the > readFile will consume too many mem.so i need to read the file line by > line but stunned by the loop in IO Monad: > > main = do h1 <- openFile "url1.txt" ReadMode > h2 <- openFile "url2.txt" ReadMode > line1 <- hGetLine h1 > line2 <- hGetLine h2 > print $ line1 : line2 : [] -- i don't howto do > hClose h1 > hClose h2 Don't worry about memory... GNU tools differs from unix-like systems: they don't utilizing IO by computing, they "slurp", or mmap entire file into memory and then process it. main = do h1 <- openFile "url1.lsm" h2 <- openFile "url2.lsm" print (zipFiles h1 h2) zipFiles :: Handle -> Handle -> IO [String] zipFiles h1 h2 = do eof1 <- hIsEOF h eof2 <- hIsEOF h case (eof1, eof2) of (False, False) -> do l1 <- hGetLine h1 l2 <- hGetLine h2 return l1:l2:(zipFiles h1 h2) (False, True) -> return (readFile h1) (True, False) -> return (readFile h2) _ -> [] I didn't tested it, but it should work... (I like fixed-width font and text-only mails... please, if you mail me, then send me only text, not html). Matej 'Yin' Gagyi ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe