Re: [Haskell-cafe] Re: [Haskell] MR details (was: Implicit type of numeric constants)
My understanding of the MR is heavily influenced by the work I did on Hatchet, which is based directly on Mark Jones' paper (and code) "Typing Haskell in Haskell". I thought I would go back to that paper and see how he defines "simple" pattern bindings and the MR. I now quote directly from the relevent sections of the paper: He represents function bindings with the Alt type, which is defined on page 9: "The representation of function bindings in following sections uses alternatives, represented by values of type Alt : type Alt = ([Pat], Expr) An Alt specifies the left and right hand sides of a function definition." On page 12 he defines what simple means with repsect to the Alt type and the MR: "A single implicitly typed binding is described by a pair con- taining the name of the variable and a list of alternatives: type Impl = (Id , [Alt]) The monomorphism restriction is invoked when one or more of the entries in a list of implicitly typed bindings is simple, meaning that it has an alternative with no left-hand side patterns. restricted :: [Impl] -> Bool retricted bs = any simple bs where simple (i, alts) = any (null . fst) alts " Curiously, his Alt type does not offer any way to represent pattern bindings where the lhs is a non-variable pattern. But he addresses this point later on page 13: "In addition to the function bindings that we have seen al- ready, Haskell allows variables to be defined using pattern bindings of the form pat = expr . We do not need to deal di- rectly with such bindings because they are easily translated into the simpler framework used in this paper. For example, a binding: (x,y) = expr can be rewritten as: nv = expr x = fst nv y = snd nv where nv is a new variable. The precise definition of the monomorphism restriction in Haskell makes specific refer- ence to pattern bindings, treating any binding group that includes one as restricted. So, at first glance, it may seem that the definition of restricted binding groups in this pa- per is not quite accurate. However, if we use translations as suggested here, then it turns out to be equivalent: even if the programmer supplies explicit type signatures for x and y in the original program, the translation will still contain an implicitly typed binding for the new variable nv." It is not obvious that this is consistent with the Report; I'll have to think about it more. Cheers, Bernie. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Creating DLLs with GHC
I am having some difficulty with creating a dynamic link library using GHC on windows XP. I am attempting to follow the example in http://www.haskell.org/ghc/docs/6.4/html/users_guide/win32-dlls.html though I have a binary build of ghc 6.5 My problem (I think) is that some of my Haskell source files link to an external C library also contained in a DLL. I generate my Haskell object files when I compile my Haskell executable. I then attempt to use the object files in a ghc compiler statement like this, ghc --mk-dll -o netsim.dll ExternLib.o ExternLib_stub.o dllNet.o src1.o src1_stub.o src2.o -optl-lmatrixstack -optl-L"." My external C library is in matrixstack.dll and it has a corresponding static link stub library matrixstack.lib in the same directory as all the sources. It has references in one of the sources (say src1.hs). Unfortunately I get a host of undefined references to basically all the functions in matrixstack.dll and also some undefined references of the form Parsefile.o:ghc2996_0.hc:(.text+0x130): undefined reference to `TextziParserCombinatorsziParsecziError_show_closure' Parsefile.o:ghc2996_0.hc:(.text+0x220): undefined reference to `TextziParserCombinatorsziParsecziChar_spaces_closure' Parsefile.o:ghc2996_0.hc:(.text+0x24a): undefined reference to `TextziParserCombinatorsziParsecziChar_spaces_closure' Parsefile.o:ghc2996_0.hc:(.text+0x29c): undefined reference to `TextziParserCombinatorsziParsecziChar_spaces_closure' ... This appears to be coming from unsatisfied references to Text.ParserCombinators.Parsec, which I thought was a standard library. I note that my stand alone haskell executable links just fine and runs perfectly. What am I missing to make this work? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: [Haskell] MR details (was: Implicit type of numeric constants)
On 26/09/2006, at 12:19 AM, Christian Sievers wrote: Bernie Pope answered: 1. Why do the rules of the monomorphism restriction explicitly mention *simple* pattern bindings? Where is the difference, especially as there is a translation to simple pattern bindings? Why should p | "a"=="b" = 2 | otherwise = 3 be treated different than p = if "a"=="b" then 2 else 3 They are the same (both are simple pattern bindings). The report says in section 4.4.3.2 that the first can be translated into the second. Indeed, I meant to allude to this translation. A simple pattern binding is one where the lhs is a variable only. That's consistent with the second reason for rule one of the MR. However, the mentioned section 4.4.3.2 defines it differently: A simple pattern binding has form p = e. And if there is any doubt about what p stands for, it goes on: The pattern p ... Contrasting to that: The general form of a pattern binding is p match, where a match is the same structure as for function bindings above; in other words, a pattern binding is: p| g1= e1 | g2= e2 ... | gm= em where { decls } So according to this definition, a pattern binding is simple iff there are no guards (unless they are in the expression). Also the translation to a "simple pattern binding" only gets rid of guards. So there seems to be an error in the report, which can be fixed by either redefining "simple pattern binding", or using a differnet description in the MR. Aha, Christian I see what you mean. It seems I did not read section 4.4.3.2 carefully. In fact I think I was interpreting that section in light of the MR. So I am now as puzzled as you are. Anyway, thanks for persisting on this point. Cheers, Bernie. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Optimizing a title matcher
Hi folks, It turns out Haskell is vindicated. It's my algorithm that was slow. As Robert Dockins pointed out, the double nested loop is just going to take a long time. As evidence, it turns out my C++ version is just as slow as the Haskell version. So, I'm going to go back to Haskell, but be more selective about which titles from the reference table I choose to match against, for any given import title. Thanks, Lyle ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Optimizing a title matcher
Bertram Felgenhauer wrote: Lyle Kopnicky wrote: [snip] listRecords :: AbsString s => TextTable s -> IO [TextRecord s] listRecords (TextTable fields _ records) = do keyRecs <- HT.toList records return $ map (fromList . zip fields . elems . snd) keyRecs Doing fromList again and again can't be good. Why don't you make tableFields a map that maps names to array indices? Then you can just pass the bare arrays along, and the later lookups will be cheaper, too. That might make a difference. It does spoil the interface a bit, since now the caller has to look up a field name to get an index, then use that to look up a value, instead of just using the field name to get the value. Now due to lazyness this will probably be evaluated in matchscore, because before that the resulting Map isn't used. Which is exactly where you said a lot (most?) of the time is spent. Yes, likely. I had to run on a small pair of files in order to get the profiling to work. So, probably more time was spent in matchScore than it admitted. (The overhead of the initial read would decrease as the table size increases.) Another thing is that you should compile your code with -O, but I guess you are already doing that. Yep. Thanks. - Lyle ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Computing lazy and strict list operations at the same time
This is a follow-up to a thread from June-July[1]. The question was how to write the function initlast :: [a] -> ([a], a) initlast xs = (init xs, last xs) so that it can be consumed in fixed space: main = print $ case initlast [0..10] of (init, last) -> (length init, last) Attempts were along the lines of initlast :: [a] -> ([a], a) initlast [x]= ([], x) initlast (x:xs) = let (init, last) = initlast xs in (x:init, last) I seemed obvious to me at first (and for a long while) that ghc should force both computations in parallel; but finally at the hackathon (thanks to Simon Marlow) I realized I was expecting magic: The elements of the pair are simply independent thunks, and there's no way to "partly force" the second (ie, last) without forcing it all the way. Simon Peyton Jones graciously offered that it is "embarrassing" that we can't write this in Haskell, so to make him less embarrassed (and despite my adamance on the mailing list that the implementation be functional), I wrote an imperative version with the desired space behavior. Borrowing the insight that unsafePerform and unsafeInterleave can be thought of as hooks into the evaluator, this shows more or less what I would wish for ghc to do automatically. initlastST :: [a] -> ([a], a) initlastST xs = runST (m xs) where m xs = do r <- newSTRef undefined init <- init' r xs last <- unsafeInterleaveST (readSTRef r) return (init, last) init' r [x]= do writeSTRef r x return [] init' r (x:xs) = do writeSTRef r (last xs) liftM (x:) (unsafeInterleaveST (init' r xs)) Andrew [1] http://haskell.org/pipermail/haskell-cafe/2006-June/016171.html http://haskell.org/pipermail/haskell-cafe/2006-July/016709.html ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Optimizing a title matcher
Lyle Kopnicky wrote: [snip] > data TextTable s = TextTable { tableFields :: ![s], >keyFieldIndex :: !Int, >tableRecords :: !(HashTable s (Array Int s)) } [snip] > listRecords :: AbsString s => TextTable s -> IO [TextRecord s] > listRecords (TextTable fields _ records) = do > keyRecs <- HT.toList records > return $ map (fromList . zip fields . elems . snd) keyRecs Doing fromList again and again can't be good. Why don't you make tableFields a map that maps names to array indices? Then you can just pass the bare arrays along, and the later lookups will be cheaper, too. Now due to lazyness this will probably be evaluated in matchscore, because before that the resulting Map isn't used. Which is exactly where you said a lot (most?) of the time is spent. Another thing is that you should compile your code with -O, but I guess you are already doing that. Hope this helps, Bertram ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Optimizing a title matcher
Robert Dockins wrote: Humm... well, double nested loops seems like the wrong approach. It may be. I had hoped it would be fast enough that way. Also, if you are using GHC, it's hashtable implementation has farily well-known performance problems. If all you care about is exact matching, then the operation is essentially a finite map intersection (if I've understood what you are trying to do). No, I don't just care about exact matching. I care about very fuzzy matching. It's just that the code I've implemented so far only does exact matching on the title strings. It's a first step. This is just a guess, but I suspect you will probably get much better performance (and better-looking code!) by just using Data.Map.intersection http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-Map.html#v%3Aintersection Thanks, but that won't help with the fuzzy matching. Alternately, there is the ternary trie implementation from Edison (http://www.eecs.tufts.edu/~rdocki01) that may also work for you. That may be useful. If you need to do prefix matching, then a trie is the way to go. You can probably code up a nice prefix-intersection operation using tries that should go pretty fast. If you have some other metric other than prefix in mind for partial matches, then things probably get a lot more complicated. You're probably looking at calculating minimum distances in some feature-space, which calls for pretty sophisticated algorithms if you need good performance. Yes, that's the kind of thing I'm looking at doing. Looking at edit distance. Thanks, Lyle ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Optimizing a title matcher
Lemmih wrote: Do you have some test input online? I've attached some (very short) input files. Sorry I can't provide more - they're proprietary databases. I know that means you can't actually test the performance, but can only give me advice. At least you can run the program on them, and there is one match. - Lyle title_id|ref_title_id|importance|title|studio|run_time|rating|theatrical_release|home_video_release|box_office_gross|synopsis|actors|director 26246|157067|2|Sniper|TRI||R|29-JAN-93|04-AUG-93|18994653|A rebel leader and a wealthy drug lord are pursued in Panama by a marine sergeant and Oympic marksman.|Dale Dye;Aden Young;Tom Berenger;J.T. Walsh;Richard Lineback;Billy Zane|Luis Llosa 68308|174883|2|Northern Passage||97|||27-FEB-96|0|In the wilds of North America in the 1800s, Paul a young zoologist has pledged to keep as eye on his longtime friend's beautiful daughter, Nepeese. Nepeese and Paul fall in love, but their relationship is interrupted when an abusive fur trader kidnaps Nepeese. Starring Jeff Fahey.|Jeff Fahey;Neve Campbell| 68591|196655|2|Old Man And The Sea (1990)||97|||01-JUL-96||An old man heads out to sea, hooks a large fish, and battles a shark who has taken his catch.|Anthony Quinn;Alexis Cruz| 51506|190181|2|Shoot Out||95|||27-APR-99|||Gregory Peck;Robert F. Lyons| title_id|importance|title|studio|runtime|rating|theatrical_release|home_video_release|theatrical_box_office_gross|actors|director 214063|2|Elvis: His Best Friend Remembers|UNI||NR||30-JUL-02||Elvis Presley| 133868|2|Mighty Hercules, The - Speed Racer - V. 5||30|NR| 174883|2|Northern Passage|VMM|97|PG-13||18-JAN-00||Jeff Fahey;Neve Campbell;Jacques Weber;Lorne Brass;Genevieve Rochette|Arnaud Selignac 121430|2|Appointment With Death|WAR|||15-APR-88||960040|Peter Ustinov;Lauren Bacall;Carrie Fisher;Piper Laurie;John Gielgud;Hayley Mills;Jenny Seagrove;David Soul|Michael Winner ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Getting the latest
Hi folks, I am running GHC 6.4.1 on my Linux box at work, which is the latest packaged version for Ubuntu Dapper Drake. (They have a 6.4.2 package for Edgy, but I don't know how to install that. The Synaptic Package Manager seems to only want to install packages specifically labeled for Dapper Drake.) I tried downloading the latest binary snapshot. But when I try to unpack the archive, bzip2 tells me it's a bad archive. So, I downloaded the latest source version. That unpacked just fine, and I'm currently building it. My question is, when I do 'make install', will it just overwrite the version (6.4.1) I already have? Or will they go in separate places? I have no idea how it decides where to go. Right now ghc 6.4.1 is in /usr/local/bin/ghc. After I 'make install', will it be ghc 6.5? I don't want to screw up the installed package so it can't be updated later. Thanks, Lyle ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Optimizing a title matcher
On Tuesday 26 September 2006 16:44, Lyle Kopnicky wrote: > Hi folks, > > I'm competing in a contest at work, and we're allowed to use whatever > language we want. I decided this was my chance to prove to people that > Haskell was up to the challenge. Unfortunately, I ran into performance > problems. Since the contest ends this Friday, I've decided to switch to > C++ (gasp!). But if any of you have advice on how to speed up this code, > it could help me advocate Haskell in the future. > > It's supposed to match movie titles from an imported database to a > reference database. The version I've sent doesn't do anything very smart > - it's just doing literal title matches. The first argument to the > program is the filename of the table to be imported, and the second is > the filename of the reference table. The first line of each table is a > pipe-separated list of field names; the rest of the lines are records, > each a pipe-separated list of values. > > The import files each have 3,000 records, and the reference table has > 137,986 records. > > Building the hash tables out of the files is quick - it just takes a few > seconds. But doing the matching of title_id in one table to title_id in > the other, in a nested loop between both tables, takes way too long. > It's matching two import titles (against each of the reference titles) > per second. It needs to do at least 20 per second to qualify for the > contest, and it's not doing anything fancy yet. Humm... well, double nested loops seems like the wrong approach. Also, if you are using GHC, it's hashtable implementation has farily well-known performance problems. If all you care about is exact matching, then the operation is essentially a finite map intersection (if I've understood what you are trying to do). This is just a guess, but I suspect you will probably get much better performance (and better-looking code!) by just using Data.Map.intersection http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-Map.html#v%3Aintersection Alternately, there is the ternary trie implementation from Edison (http://www.eecs.tufts.edu/~rdocki01) that may also work for you. If you need to do prefix matching, then a trie is the way to go. You can probably code up a nice prefix-intersection operation using tries that should go pretty fast. If you have some other metric other than prefix in mind for partial matches, then things probably get a lot more complicated. You're probably looking at calculating minimum distances in some feature-space, which calls for pretty sophisticated algorithms if you need good performance. > I tried various "improvements" to speed it up. One was to specifically > use ByteString, eliminating the AbsString class. Didn't make a > difference. Another was to use arrays instead of lists to store each > record, and precompute the indices of each of the fields within those > records. I also iterated over a list of keys instead of the list of > Maps, and only converted each record to a Map one at a time, hoping they > would be disposed of sooner. Instead of speeding up the program, this > slowed it down by a factor of 20! > > I've profiled it, and I can't make much out of that. It seemed to be > spending 25% of its time doing scoring, and I though the problem must be > due to laziness, but I'm not sure. > > So if anyone has any ideas how to speed this up by a factor of at least > 10 times, it would be really appreciated! Even the Ruby solutions are > doing that, which is embarrassing. > > Thanks, > Lyle -- Rob Dockins Talk softly and drive a Sherman tank. Laugh hard, it's a long way to the bank. -- TMBG ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Optimizing a title matcher
On 9/26/06, Lyle Kopnicky <[EMAIL PROTECTED]> wrote: Hi folks, I'm competing in a contest at work, and we're allowed to use whatever language we want. I decided this was my chance to prove to people that Haskell was up to the challenge. Unfortunately, I ran into performance problems. Since the contest ends this Friday, I've decided to switch to C++ (gasp!). But if any of you have advice on how to speed up this code, it could help me advocate Haskell in the future. It's supposed to match movie titles from an imported database to a reference database. The version I've sent doesn't do anything very smart - it's just doing literal title matches. The first argument to the program is the filename of the table to be imported, and the second is the filename of the reference table. The first line of each table is a pipe-separated list of field names; the rest of the lines are records, each a pipe-separated list of values. The import files each have 3,000 records, and the reference table has 137,986 records. Building the hash tables out of the files is quick - it just takes a few seconds. But doing the matching of title_id in one table to title_id in the other, in a nested loop between both tables, takes way too long. It's matching two import titles (against each of the reference titles) per second. It needs to do at least 20 per second to qualify for the contest, and it's not doing anything fancy yet. I tried various "improvements" to speed it up. One was to specifically use ByteString, eliminating the AbsString class. Didn't make a difference. Another was to use arrays instead of lists to store each record, and precompute the indices of each of the fields within those records. I also iterated over a list of keys instead of the list of Maps, and only converted each record to a Map one at a time, hoping they would be disposed of sooner. Instead of speeding up the program, this slowed it down by a factor of 20! I've profiled it, and I can't make much out of that. It seemed to be spending 25% of its time doing scoring, and I though the problem must be due to laziness, but I'm not sure. So if anyone has any ideas how to speed this up by a factor of at least 10 times, it would be really appreciated! Even the Ruby solutions are doing that, which is embarrassing. Do you have some test input online? -- Cheers, Lemmih ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Optimizing a title matcher
Hi folks, I'm competing in a contest at work, and we're allowed to use whatever language we want. I decided this was my chance to prove to people that Haskell was up to the challenge. Unfortunately, I ran into performance problems. Since the contest ends this Friday, I've decided to switch to C++ (gasp!). But if any of you have advice on how to speed up this code, it could help me advocate Haskell in the future. It's supposed to match movie titles from an imported database to a reference database. The version I've sent doesn't do anything very smart - it's just doing literal title matches. The first argument to the program is the filename of the table to be imported, and the second is the filename of the reference table. The first line of each table is a pipe-separated list of field names; the rest of the lines are records, each a pipe-separated list of values. The import files each have 3,000 records, and the reference table has 137,986 records. Building the hash tables out of the files is quick - it just takes a few seconds. But doing the matching of title_id in one table to title_id in the other, in a nested loop between both tables, takes way too long. It's matching two import titles (against each of the reference titles) per second. It needs to do at least 20 per second to qualify for the contest, and it's not doing anything fancy yet. I tried various "improvements" to speed it up. One was to specifically use ByteString, eliminating the AbsString class. Didn't make a difference. Another was to use arrays instead of lists to store each record, and precompute the indices of each of the fields within those records. I also iterated over a list of keys instead of the list of Maps, and only converted each record to a Map one at a time, hoping they would be disposed of sooner. Instead of speeding up the program, this slowed it down by a factor of 20! I've profiled it, and I can't make much out of that. It seemed to be spending 25% of its time doing scoring, and I though the problem must be due to laziness, but I'm not sure. So if anyone has any ideas how to speed this up by a factor of at least 10 times, it would be really appreciated! Even the Ruby solutions are doing that, which is embarrassing. Thanks, Lyle {-# OPTIONS_GHC -fglasgow-exts #-} -- AbsString.hs -- An abstract string class, which makes it easier to switch string representations. module AbsString where import Prelude as P import Data.ByteString.Base (c2w, w2c) import Data.ByteString.Char8 as BSC import Data.ByteString.Lazy.Char8 as BSLC import Text.Regex as RE import Test.HUnit class (Eq s, Ord s) => AbsString s where s :: String -> s toString :: s -> String sLength :: s -> Int sAppend :: s -> s -> s sConcat :: [s] -> s putStr :: s -> IO () putStrLn :: s -> IO () readFile :: String -> IO s lines :: s -> [s] split :: Char -> s -> [s] (+++) :: AbsString s => s -> s -> s (+++) = sAppend instance AbsString String where s = id toString = id sLength = P.length sAppend = (++) sConcat = P.concat putStr = P.putStr putStrLn = P.putStrLn readFile fn = P.readFile fn lines = P.lines split c = RE.splitRegex (mkRegex (escapeRegexChar c)) regexMetaChars = "\\|()[]^.*+?{}" escapeRegexChar :: Char -> String escapeRegexChar c = if c `P.elem` regexMetaChars then "\\"++[c] else [c] instance AbsString BSC.ByteString where s = BSC.pack toString = BSC.unpack sLength = fromIntegral . BSC.length sAppend = BSC.append sConcat = BSC.concat putStr = BSC.putStr putStrLn = BSC.putStrLn readFile = BSC.readFile lines = BSC.lines split = BSC.split instance AbsString BSLC.ByteString where s = BSLC.pack toString = BSLC.unpack sLength = fromIntegral . BSLC.length sAppend = BSLC.append sConcat = BSLC.concat putStr = BSLC.putStr putStrLn = BSLC.putStrLn readFile = BSLC.readFile lines = BSLC.lines split c s = BSLC.split c s test_showString = TestCase $ do let aStr = s "Hello there" :: String assertEqual "" "Hello there" (toString aStr) test_showByteString = TestCase $ do let aStr = s "Hello there" :: BSC.ByteString assertEqual "" "Hello there" (toString aStr) test_showByteStringLazy = TestCase $ do let aStr = s "Hello there" :: BSLC.ByteString assertEqual "" "Hello there" (toString aStr) runTests = runTestTT $ TestList [TestLabel "test_showString" test_showString, TestLabel "test_showByteString" test_showByteString, TestLabel "test_showByteStringLazy" test_showByteStringLazy] {-# OPTIONS_GHC -fglasgow-exts #-} -- TextTable.hs -- Defines a TextTable type, which defines a map of strings to a record -- of text fields. module TextTable(TextTable(..),TextRecord,makeTable,lookupRecord,listKeys,listRecords) where import Prelude hiding (putStr,putStrLn,readFile,lines) import qualified Data.ByteString.Lazy as BSL
Re: [Haskell-cafe] Unable to profile program using Data.ByteString.Lazy
On 9/25/06, Lyle Kopnicky <[EMAIL PROTECTED]> wrote: Donald Bruce Stewart wrote: You're cabal version is too old then. Try updating either Cabal or GHC. -- Don It's the latest version (6.4.1) packaged for Ubuntu. I'll have to download and install a newer version manually. Unfortunately, the download site seems to be down again :( Ubuntu seems to be a bit behind then. The current official release of the 6.4 branch is at 6.4.2. Debian seems to provide this version, maybe you can use the debian package? But, if I were you I wouldn't worry so much about upgrading ghc but instead upgrading Cabal which is much simpler and takes just a second. Jason ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Haskell.org down
Paul Hudak wrote: > I had to reboot haskell this AM it was really hung. My first > assumption is abuse by web crawlers. I have denied access to all web > crawlers at the moment while I continue looking further into this > and the load is staying low. I'll keep you posted. I've seen this kind of behavior when some stupid referer spammers open hundreds of connections at the same time, typically requesting some dynamic resource, DDoSing the system. I have installed an iptables-based tar pit on my own server that seems to have solved the problem. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Haskell.org down
don't know whether this is useful/related, but - I got a whole bunch of very old haskell.org emails today (so they must have been hung up somewhere) - some of the ghc trac tickets look bogus, filled with links (#889, sent 05 Sept, received today, 26 Sept; #751, sent 05 Sept, received today, 26 Sept; see glasgow-haskell-bugs) Original Message - From: "Paul Hudak" <[EMAIL PROTECTED]> To: <[EMAIL PROTECTED]>; "Donald Bruce Stewart" <[EMAIL PROTECTED]> Cc: ; <[EMAIL PROTECTED]> Sent: Tuesday, September 26, 2006 1:46 PM Subject: Re: [Haskell-cafe] Haskell.org down Sorry to bother everyone with this, but some input I've gotten from the community has been helpful. Haskell.org is up again, and here is the latest action on part of our IT staff: If anything further develops I'll let you know. Thanks, -Paul I had to reboot haskell this AM it was really hung. My first assumption is abuse by web crawlers. I have denied access to all web crawlers at the moment while I continue looking further into this and the load is staying low. I'll keep you posted. Paul Hudak wrote: We are looking into it. Sorry for the inconvenience. -Paul Jason Dagit wrote: On 9/23/06, Donald Bruce Stewart <[EMAIL PROTECTED]> wrote: Hmm. Looks like its gone down again? And again... Seems fishy... Very. ___ 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] Haskell.org down (again)
dons: > Something's going on. Haskell.org seems to be down again. > That's the 3rd time in 4 days. And of course sending this message when the server _was_ down is guaranteed to lead to confusion when it is finally delivered, and the server is _up_. -- Don ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Is Haskell a 5GL?
Ch. A. Herrmann wrote: > do you think that Haskell is a 3GL (third generation language) or a 5GL or > that the hierarchy of programming language generations is useless? I did a literature search on language generations a few years ago when I was preparing the first incarnation of the local Principles of Programming Languages course. There were three findings: 1) I could not find where the idea comes from. 2) All sources agree what 1GL, 2GL and 3GL are. 3) There is no consensus on what 4GL and 5GL are. (Different sources define them completely differently.) Hence, I just classify all current general-purpose languages as 3GL and consider the classification mostly meaningless for today's languages. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Unable to profile program using Data.ByteString.Lazy
lists: > Donald Bruce Stewart wrote: > >Probably you didn't build fps with profiling as well? You can rebuild > >fps with: > >runhaskell Setup.hs configure -p > >as the first step. > > > That worked on my Windows box at home, but on my Linux box at work, I > got "unrecognized flag -p". You're cabal version is too old then. Try updating either Cabal or GHC. -- Don ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Is Haskell a 5GL?
The official name of the assembler for 360/370 was BAL (basic assembly language). I wrote code in it back in prehistoric times . Murray Gross Brooklyn College On Mon, 25 Sep 2006, Jerzy Karczmarczuk wrote: Alex Queiroz wrote: On 9/25/06, Ch. A. Herrmann <[EMAIL PROTECTED]> wrote: Henning Thielemann wrote: > assembly language (Assembler ist deutsch :-) for mysterious reasons it entered the English world. 'Assembly' is a language. 'Assembler' is a program. All this is absolutely essential for the progress of Humanity... But, anyway, "Assembler" was the official name of the assembly language of IBM 360/370 if I am not mistaken. And I believe that it infiltrated die Deutsche Sprache therefrom. Good followers of Konrad Duden called a compiler: Uebersetzer, so perhaps the assemblers had here and there some Wagnerian names as well... (For the CDC mainframes the assembly language was called Compass [Comprehensive Assembler]. It was a 7648764GL. You could program in it almost like in Lisp thanks to some very exquisite macros, and add another set of macros which performed some type checking and optimized the register allocation. People who used it got famous (as M. Veltman, Nobel prize in physics), or got mad.) OK, who next?... ___ 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 vs Prolog was [Haskell-cafe] Re: Is Haskell a 5GL?
Here is a paper on how to do logic programming in Haskell Deals with a logic puzzle and how the haskell and prolog solutions compare http://web.engr.oregonstate.edu/~erwig/zurg/ In terms of automated theorem proving here is another paper http://citeseer.ist.psu.edu/cache/papers/cs/5363/http:zSzzSzwww.ki.informatik.uni-frankfurt.dezSz~panitzzSzpaperzSzrussian.pdf/theorem-proving-in-a.pdf Regards David On 26/09/06, Pasqualino 'Titto' Assini <[EMAIL PROTECTED]> wrote: > -Original Message- > From: [EMAIL PROTECTED] [mailto:haskell-cafe- > [EMAIL PROTECTED] On Behalf Of Christoph Herrmann > Sent: 25 September 2006 21:22 > To: Max Vasin > Cc: haskell-cafe@haskell.org > Subject: Re: [Haskell-cafe] Re: Is Haskell a 5GL? ... > What Prolog really provides concerning automatic problem solving > is little: equation solving in term algebra; you can simulate that > in Haskell without much effort. Could you, or anyone else, elaborate a bit on how to emulate Prolog in Haskell? For example, I remember that in Prolog you can write a concat function that can be used to concatenate two lists as well as to split them: concat([1,2] ,[3,4] ,Z) --> Z = [1,2,3,4] concat([1,2] ,Y ,[1,2,3,4]) --> Y = [3,4] Now, that's powerful. How would you do that in Haskell? Regards, Titto ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe -- It chews up lies and spits out the gristle of truth http://liveatthewitchtrials.blogeasy.com/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] haskell.org down again
From: HostTracker Notifier [mailto:[EMAIL PROTECTED] Sent: 26 September 2006 01:19 To: [EMAIL PROTECTED] Subject: Error Alert Hello, The following url is down: http://haskell.org the error detected is: Http error:Http_client.No_reply Error was detected at 2006-09-26 01:14:41 Your login:titto -- Best regards, http://host-tracker.com/ support team uid:957058 tid:188350 eid:188350-209-0-0-4eee7afa9e44102989dd000c7651f68b ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Haskell.org down
We are looking into it. Sorry for the inconvenience. -Paul Jason Dagit wrote: On 9/23/06, Donald Bruce Stewart <[EMAIL PROTECTED]> wrote: Hmm. Looks like its gone down again? And again... Seems fishy... Very. Professor Paul Hudak Department of Computer ScienceOffice: (203) 432-1235 Yale University FAX:(203) 432-0593 P.O. Box 208285 email: [EMAIL PROTECTED] New Haven, CT 06520-8285 WWW:www.cs.yale.edu/~hudak ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Unable to profile program using Data.ByteString.Lazy
Donald Bruce Stewart wrote: You're cabal version is too old then. Try updating either Cabal or GHC. -- Don It's the latest version (6.4.1) packaged for Ubuntu. I'll have to download and install a newer version manually. Unfortunately, the download site seems to be down again :( - Lyle ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Haskell.org down (again)
Something's going on. Haskell.org seems to be down again. That's the 3rd time in 4 days. -- Don ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: Is Haskell a 5GL?
On Mon, 25 Sep 2006, Christoph Herrmann wrote: > I'm looking for an honest classification. The aim of the GLs is, > as I think, the degree of abstraction. The question is, how much > *intelligence* provided by preprocessing, libraries etc. is permitted. > Personally, I think Haskell should be a 5GL because Prolog is a 5GL. > What Prolog really provides concerning automatic problem solving > is little: equation solving in term algebra; you can simulate that > in Haskell without much effort. On the other hand, I saw Haskell > classified as a 3GL. The problem is that Haskell often exposes > the algorithmic structure. What people often forget is that Prolog > programs in non-trivial situations are likely to fail if you do > not prescribe the evaluation order, by features like the cut which > destroy the declarative semantics. People also forget that arithmetic > constraints in Prolog have to be directed (input/output variables), > no difference to Haskell. Compare Haskell with Computer algebra systems, where you can write root equations, and the system tells you the set of solutions. CAS let you write some infinite sum or integral, things that cannot be solved by brute force, and the system simplifies that to a fraction of pi or so. This is non-trivial and you would have to program a lot in Haskell to achieve this. > My argumentation is: > Prolog is a 5GL & Haskell is more abstract than Prolog => Haskell is a 5GL Or Prolog is better classified as 3GL. :-) > Some of the language features in Haskell that contribute to this abstraction > are: > laziness, pattern matching with guards, list comprehensions, type classes Pattern matching with guards is not more than a 'switch', list comprehension is syntactic sugar, some type relations are available in all OO languages. What remains special is laziness, higher order functions. (Did I forget something?) Indeed, these features allow for more abstraction. Maybe we could classify Haskell as 3.5 GL or so. :-) > Please note that this is not a philosophic discussion. If Haskell is a > 3GL, than it is at the same level with Java and since Java is more > common, people think they should always use Java. Haskell as a 5GL will > tell people: this is a language in which you can solve problems simpler > and safer and it will encourage people to try to solve problems instead > of resigning due to the complexity of the problem. So classification is a marketing issue? A higher level of abstraction can also scare people, if they expect efficiency. I also know Java freaks who stay away from Haskell, because they find it too abstract. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Haskell vs Prolog was [Haskell-cafe] Re: Is Haskell a 5GL?
> -Original Message- > From: [EMAIL PROTECTED] [mailto:haskell-cafe- > [EMAIL PROTECTED] On Behalf Of Christoph Herrmann > Sent: 25 September 2006 21:22 > To: Max Vasin > Cc: haskell-cafe@haskell.org > Subject: Re: [Haskell-cafe] Re: Is Haskell a 5GL? ... > What Prolog really provides concerning automatic problem solving > is little: equation solving in term algebra; you can simulate that > in Haskell without much effort. Could you, or anyone else, elaborate a bit on how to emulate Prolog in Haskell? For example, I remember that in Prolog you can write a concat function that can be used to concatenate two lists as well as to split them: concat([1,2] ,[3,4] ,Z) --> Z = [1,2,3,4] concat([1,2] ,Y ,[1,2,3,4]) --> Y = [3,4] Now, that's powerful. How would you do that in Haskell? Regards, Titto ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Curious Functor Class
Is there anything useful about the class of functors which foralls can move across? In other words, functors f, for which for any function g there is this isomorphism f (forall a. g a) <=> forall a. f (g a) In this Haskell snippet I've called the class Hoistable and the isomorphism is (hoist,unhoist): newtype All g = MkAll (forall a. g a); class (Functor f) => Hoistable f where { hoist :: forall g. (f (All g) -> (forall a. f (g a))); hoist = fmap (\(MkAll ga) -> ga); unhoist :: forall g. ((forall a. f (g a)) -> f (All g)); }; Functors that can be made instances of Hoistable: data Singleton a = MkSingleton newtype Identity a = MkIdentity a (->) p -- forall p. data Pair a = MkPair a a data Extra p a = MkExtra p a -- forall p. data Compose p q a = MkCompose (p (q a)) -- forall p q. (Hoistable p,Hoistable q) => On the other hand, Maybe and Either cannot. The key seems to be in only having one "form", i.e. no "|"s in the definition. Does this class actually have a use, or is it merely a curiosity? -- Ashley Yakeley Seattle WA ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Haskell.org down
Sorry to bother everyone with this, but some input I've gotten from the community has been helpful. Haskell.org is up again, and here is the latest action on part of our IT staff: If anything further develops I'll let you know. Thanks, -Paul I had to reboot haskell this AM it was really hung. My first assumption is abuse by web crawlers. I have denied access to all web crawlers at the moment while I continue looking further into this and the load is staying low. I'll keep you posted. Paul Hudak wrote: We are looking into it. Sorry for the inconvenience. -Paul Jason Dagit wrote: On 9/23/06, Donald Bruce Stewart <[EMAIL PROTECTED]> wrote: Hmm. Looks like its gone down again? And again... Seems fishy... Very. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Haskell.org down
On 9/23/06, Donald Bruce Stewart <[EMAIL PROTECTED]> wrote: paul.hudak: > Thanks Don. I alerted our IT staff this morning, and they seem to have > things working again, although here is their final response: > >The web server had over 150 client connections which exceeded >its limit. I restarted the web server and all is well. > >I'll keep and eye on it and see if someone is trying a denial of >server attack, or it could be you need a newer faster machine. :-) > > So either Haskell is getting really popular (on a Friday night?) or > there's something fishy going on. Hmm. Looks like its gone down again? And again... Seems fishy... Very. Is it possible that some resource on the haskell.org server isn't accessible but also doesn't time out when requested? I've seen things like that with samba shares where the requested file is never fetched and the process pretty much goes to sleep until it is fetched. Just an idea. Jason ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe