Re: [Haskell-cafe] Re: Just for a laugh...

2007-06-02 Thread Udo Stenzel
Andrew Coppin wrote: > Note that the challenge asks for the "internal" bitmap representation of > an IEEE double-precision integer Actually it didn't. It asked for the machine's internal representation of a double precision float, and you are not guaranteed that this representation conforms to I

Re: [Haskell-cafe] Re: Compiling packages for GHCi

2007-06-06 Thread Udo Stenzel
Grzegorz wrote: > > mkdir libmaxent > > cd libmaxent > > ar x /usr/local/lib/libmaxent.a > > cd .. > > ghci (...) libmaxent/*.o > > This doesn't quite work: > ghc-6.6.1: libmaxent/trainer.o: unknown symbol `_ZNSt8ios_base4InitC1Ev' > final link ... ghc-6.6.1: linking extra libraries/objects fail

[Haskell-cafe] dangerous inlinePerformIO in Data.Binary(?)

2007-06-14 Thread Udo Stenzel
Greetings, I was trying to understand the magic inside Data.Binary, and found two somewhat suspicious uses of inlinePerformIO, which imho has a far too innocuous name: | toLazyByteString :: Builder -> L.ByteString | toLazyByteString m = S.LPS $ inlinePerformIO $ do | buf <- newBuffer defaultS

Re: [Haskell-cafe] dangerous inlinePerformIO in Data.Binary(?)

2007-06-17 Thread Udo Stenzel
Roberto Zunino wrote: > Floating out (newBuffer defaultSize) as in > > | foo = newBuffer defaultSize > | > | toLazyByteString m = S.LPS $ inlinePerformIO $ do > | buf <- foo > | return (runBuilder (m `append` flush) (const []) buf) > > would still be safe, AFAICS. Floating out buf instead

Re: [Haskell-cafe] XmlSerializer.deserialize?

2007-06-24 Thread Udo Stenzel
Hugh Perkins wrote: > Hi, > > Trying to write a function to deserialize a haskell type from xml. > > deserializeXml :: Data(a) => String -> a That type signature describes a function that can deliver *anything* (that is in class Data), whatever you ask from it. From your description (also the o

Re: [Haskell-cafe] XmlSerializer.deserialize?

2007-06-26 Thread Udo Stenzel
Hugh Perkins wrote: > Is reflection hard in Haskell? In C# its easy, and its one of the most > powerful features of C# That's another way of saying that the truly powerful features are missing from C#... > Yes, but I'm kindof stuck giving useful input to makeConstrM, so if > anyone has any idea

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

2006-11-23 Thread Udo Stenzel
Niko Korhonen wrote: > I have the following code whose purpose is to add dither (noise) to a given > array. The code looks very straightforward but apparently it has a memory leak > somewhere. No, it doesn't. It can't, because it doesn't even compile. After correcting the obvious > (lo,

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

2006-11-23 Thread Udo Stenzel
[EMAIL PROTECTED] wrote: > >> (lo, hi) <- getBounds buf > > > > to > > > > let (lo,hi) = bounds buf > > The interface changed between GHC 6.4.2 and 6.6. > But no honorable Haskell paladin would ever dare to use UndeadArrays. Hm, and 'bounds' is simply gone? Hope that doesn't

Re: [Haskell-cafe] Equivalent of if/then/else for IO Bool?

2006-11-24 Thread Udo Stenzel
Dougal Stanton wrote: > Is there some sort of equivalent of the if/then/else construct for use > in the IO monad? For instance the following can get quite tedious: > > > do bool <- doesFileExist filename > >if bool > >then sth > >else sth' > > Is there a more compact way of writing th

Re: [Haskell-cafe] Beginner: IORef constructor?

2006-12-01 Thread Udo Stenzel
TJ wrote: > -- > module Global where > > import Data.IORef > > theGlobalVariable = newIORef [] > > testIt = do ref <- theGlobalVariable >original <- readIORef ref >print original >writeIORef ref [1,2,3] >

Re: [Haskell-cafe] Dynamic types through unsafeCoerce

2006-12-09 Thread Udo Stenzel
Alfonso Acosta wrote: > I've been using Data.Dynamic but the Typeable requirement doesn't go > well with FFI declarations (which don't accept type contexts). You wouldn't need a Typeable context anyway; what's biting you is that Dynamic is not one of the primitive types that can pass across the FF

Re: [Haskell-cafe] Dynamic types through unsafeCoerce

2006-12-12 Thread Udo Stenzel
Alfonso Acosta wrote: > If anyone finds a way of implementing something equivalent to this code > without unsafeCoerce# and ... > > * Not changing chooseDesc or finding an equivalent > * Not splitting or changing Descriptor type (I already found an > equivalent way which uses existentials and i

Re: [Haskell-cafe] Dynamic types through unsafeCoerce

2006-12-13 Thread Udo Stenzel
Alfonso Acosta wrote: > On 12/13/06, Udo Stenzel <[EMAIL PROTECTED]> wrote: > >Finished! Look Ma, no existentials, no Typeable, no wrappers, even the > >types have become simple! > > I like the fact that type parameters are removed, which makes them > homegeneus and

Re: [Haskell-cafe] State separation/combination pattern question

2006-12-22 Thread Udo Stenzel
Reto Kramer wrote: > What I'm really looking for is not so much the chaining of StateT > compositions, but rather the isolation of StateA from StateB while > they both flow from the search loop into the respective library calls > (foo, bar) transparently to the application programmer. How ab

Re: [Haskell-cafe] Re: Seeking advice on a style question

2006-12-29 Thread Udo Stenzel
Steve Schafer wrote: > Here's the essence of the problem. If I have this: > > process1 x y = >let u = foo x y; >v = bar u; >w = baz v >in w > > I can easily rewrite it in point-free style: > > process1 = baz . bar . foo That should have been process1 = (.) (baz . b

Re: [Haskell-cafe] Arrays performance

2007-01-01 Thread Udo Stenzel
[EMAIL PROTECTED] wrote: > I'm timing the following script.I'm not expert to evaluate th O'ness > of this code, I hope someone can do it. The program clusters n > integers in m buckets based on their distance. Anyway I thing should > be linear.So I timed som executions changing the first arg. > [

Re: [Haskell-cafe] Composing functions with runST

2007-01-01 Thread Udo Stenzel
Yitzchak Gale wrote: > It seems to me that a natural notion of a state transformer > in the ST monad is the type: > > STRef s st -> ST s a Are there any useful functions of this type? I guess, your intention is that this "transformer" makes no other use of the ST monad than reading or writing a

Re: [Haskell-cafe] Composing functions with runST

2007-01-03 Thread Udo Stenzel
Yitzchak Gale wrote: > Here is a concrete example: > > Let's say you want to shuffle a large list randomly, > within a larger application that lives inside some > MTL monad stack. Among other things, your monad > m satisfies (RandomGen g, MonadState g m), perhaps > after a lift. > > Well, it turn

Re: [Haskell-cafe] State monad strictness - how?

2007-01-11 Thread Udo Stenzel
Yitzchak Gale wrote: > You're right, it is not in the docs. I don't think anyone would > have planned it that way. StateT is strict only because there > happens to be a line in a do-expression that looks like: > (a, s') <- runStateT m s > The tuple pattern-match causes the strictness.

Re: [Haskell-cafe] State monad strictness - how?

2007-01-11 Thread Udo Stenzel
Ross Paterson wrote: > This (like StateT) gives you strictness in the pair, but doesn't give > the strictness in the state that the original poster wanted. I think the OP wanted both. If State is lazy in the pair, a long chain of the form (a >>= (b >>= (c >>= ... >>= z))) gets build up and blows

Re: [Haskell-cafe] mapTuple

2007-01-11 Thread Udo Stenzel
Marco Túlio Gontijo e Silva wrote: > is there a way to defined something as a map to use in tuples? I tried > this: > > mapTuple f (a, b) = (f a, f b) > > But the type inferred to it is not as generic as I wanted: > > mapTuple :: (t -> t1) -> (t, t) -> (t1, t1) What you seem to want to do is im

Re: [Haskell-cafe] Trouble understanding records and existential types

2007-01-26 Thread Udo Stenzel
John Ky wrote: > On 1/25/07, BBrraannddoonn SS.. AAllllbbeerryy > KKFF88NNHH <[EMAIL PROTECTED]> wrote: > I'm probably missing something, but: > > (a) Why not: > > data ANode = Branch { name :: String, description :: String, > children :: [AnyNode] } >

Re: [Haskell-cafe] nested maybes

2007-02-04 Thread Udo Stenzel
J. Garrett Morris wrote: > Maybe has a Monad instance, so you can write this as follows (untested): > > exists str wmap = boolFromMaybe exists' >where exists' = > do x <- Map.lookup (sort str) wmap > find (== str) (snd x) > boolFromMaybe (Just _) = True >

Re: [Haskell-cafe] Strange behaviour with writeFile

2007-02-04 Thread Udo Stenzel
C.M.Brown wrote: > I've found that: > > let (answer2, remainder) = parseAnswer (force answer) > > where > > force :: Eq a => a -> a > force x = if x==x then x else x > > Seems to do the trick. ...but I'd advise against using it. If the power fails at the right time, you're left with no file

Re: [Haskell-cafe] nested maybes

2007-02-04 Thread Udo Stenzel
J. Garrett Morris wrote: > On 2/4/07, Udo Stenzel <[EMAIL PROTECTED]> wrote: > >> exists s wmap = isJust $ Map.lookup (sort s) wmap >>= find (== s) . snd > > If you're going to write it all on one line, I prefer to keep things > going the same direction:

Re: [Haskell-cafe] Re: nested maybes

2007-02-05 Thread Udo Stenzel
Benjamin Franksen wrote: > Udo Stenzel wrote: > > Sure, you're right, everything flowing in the same direction is usually > > nicer, and in central Europe, that order is from the left to the right. > > What a shame that the Haskell gods chose to give the arguments to

Re: [Haskell-cafe] LGPL libraries

2007-03-06 Thread Udo Stenzel
Neil Mitchell wrote: > As others have said though, I wouldn't worry overly about it. The > whole concept of static linking being wrong, but dynamic linking being > fine, when you can flip between the modes just by changing compiler, > is just silly. You don't infringe (or uninfringe) copyright with

Re: [Haskell-cafe] Newbie vs. laziness

2007-03-21 Thread Udo Stenzel
Alex Queiroz wrote: > > I don't quite get how ($!) works. I have this function: > > ids <- liftM (map fromSql . concat ) $! quickQuery con query [] There's a difference between an IO action and the result of said action, and similarly there's a difference between making sure an action is e

Re: [Haskell-cafe] newbie "concatenating" monad question

2007-03-24 Thread Udo Stenzel
Leandro Penz wrote: > buildStuff = > func1 ++ func2 ++ func3 ++ func4 > > My idea is to have a monad with a concatenating >>, so that I can: > > bulidStuff = do > func1 > func2 > func3 > func4 buildStuff = concat [ func1, func2, func3, func4 ] Remember,

Re: [Haskell-cafe] runInteractiveCommand

2007-04-09 Thread Udo Stenzel
Sergey Perminov wrote: > I wished to get output of unix commands in haskell code. > > So i wrote: > -- > import System.IO > import System.Process > > eval :: String -> IO String > eval s = do (_,hOutput,_,hProcess) <-

Re: [Haskell-cafe] Why Perl is more learnable than Haskell

2007-04-12 Thread Udo Stenzel
kynn wrote: > (I don't need elegant > factorial or Fibonacci functions in my everyday work.) I think you do. Most of your utility programs probably fit into the simple frame of main = interact $ unlines . map f . lines for suitable f. Of course, f is hardly ever the factorial function, but it

Re: [Haskell-cafe] Re: Haskell version of Norvig's Python Spelling Corrector

2007-04-24 Thread Udo Stenzel
Pete Kazmier wrote: > train:: [B.ByteString] -> WordFreq > train words = frequencyMap > where > frequencyMap = foldr incWordCount M.empty words > incWordCount w m = M.insertWith (+) w 1 m > > So is 'incWordCount' strict in its second argument? I'm still not > sure ex

Re: [Haskell-cafe] Re: Haskell version of Norvig's Python Spelling Corrector

2007-04-24 Thread Udo Stenzel
Bryan O'Sullivan wrote: > Udo Stenzel wrote: > > >There is another bug of this sort in your code. Consider > > > >>incWordCount w m = M.insertWith (+) w 1 m > > > >There is no reason to evaluate the sum inside the map, instead an > >

Re: [Haskell-cafe] Is Excel a FP language?

2007-04-25 Thread Udo Stenzel
Albert Y. C. Lai wrote: > I say Excel is a functional language. If there needs to be the quoted > distinction, fine: Excel the language is a functional language, and > Excel the application is an interpreter of said language. Excel has functions, but does it treat functions as it treats other da

Re: [Haskell-cafe] run-time type testing in haskell?

2007-04-28 Thread Udo Stenzel
Eric wrote: > (1) Have Handlers implement a method handle(m: Msg). To add new types of > message, we declare message types which extend Msg. The Handler then > uses runtime type testing to decide how to deal with each message. The > advantage of this design is that we can add new Handler and new

Re: [Haskell-cafe] Vectors in Haskell

2005-12-23 Thread Udo Stenzel
[EMAIL PROTECTED] wrote: > {- >This code is works with Glasgow, ghci, with these options: > -fglasgow-exts > -fallow-undecidable-instances > -fno-monomorphism-restriction > -fallow-incoherent-instances > -} First off, try lighter weapons first. Be switching on all possible extensions

Re: [Haskell-cafe] strange stack overflow with Data.Map

2005-12-28 Thread Udo Stenzel
David Roundy wrote: > > stats elems = foldl add_elem Map.empty elems > > add_elem m x = Map.insertWith (+) x 1 m > [...] > I tried defining > > add_elem m x = let m' = Map.insertWith (+) x 1 m >Just num = Map.lookup x m' >in seq num m' > to force the (+) to be e

Re: [Haskell-cafe] strange stack overflow with Data.Map

2005-12-29 Thread Udo Stenzel
David Roundy wrote: > Should the Map modules have an additional Map.insertWith' that behaves > strictly, or might it be the case that you always want strict behavior when > using insertWith? I think so. Once strictness is lost, there's nothing the user of a library could do about it. If a contai

Re: [Haskell-cafe] Can this be improved?

2005-12-30 Thread Udo Stenzel
Chris Kuklewicz wrote: > > *MyShow> main > > Hello" ""World #"[17,18,19]"!" > > I also think [4,5,6]" and "7" are ""cool""." > > The extra double quotes being what I am trying to avoid with MyShow This is your only special case, a single list of a sigle type that is different from other lists? T

Re: [Haskell-cafe] How to print a string (lazily)

2006-01-03 Thread Udo Stenzel
Daniel Carrera wrote: > I've been studying more Haskell and I've improved a lot. But I just hit > a small problem. I want to print all the elements of a linst (putStr). > I'd like to write something like this: > > print_list [] = do putStr "" This looks as if you're confused. The keyword "do"

Re: [Haskell-cafe] Shootout favoring imperative code

2006-01-05 Thread Udo Stenzel
Sebastian Sylvan wrote: > On 1/5/06, Chris Kuklewicz <[EMAIL PROTECTED]> wrote: > > There is no need to beat a dead horse, though. This benchmark sets out > > to test fgets / atoi, and that is all. There are better benchmarks to > > spend time on. > > I agree. The benchmark really is about how f

Re: [Haskell-cafe] enforcing strictness on arbitrary subexpressions

2006-02-16 Thread Udo Stenzel
Matthias Fischmann wrote: > I want to force evaluation on an arbitrary expression. > [...] > main :: IO () > main = do >hPutStr stdout veryLongString -- lazy >veryLongString `seq` hPutStr stdout veryLongString -- still lazy? >(StrictThingy veryLongString) `seq` hPutStr st

Re: [Haskell-cafe] Badly designed Parsec combinators?

2006-02-16 Thread Udo Stenzel
Juan Carlos Arevalo Baeza wrote: > myParser :: Parser () > myParser = >do string "Hello" >optional (string ", world!") > > It makes no sense for myParser to generate any values, especially not > the result from the optional statement, so it is set to return (). Don't you t

Re: [Haskell-cafe] Badly designed Parsec combinators?

2006-02-16 Thread Udo Stenzel
Juan Carlos Arevalo Baeza wrote: > Udo Stenzel wrote: > >Don't you think this will interfere somehow with type inference? > > With type inference? No, why? I mean... specifying the type of a > function [...] Okay, so want an implicit (return ()) only if the type o

Re: [Haskell-cafe] (Newbie Question) How to get the value of an "IO String" Monad?

2006-02-17 Thread Udo Stenzel
Peter wrote: > So, How am I supposed to get the value of an IO Monad, such as "IO > String", without returning an IO Monad? You read correctly, this is impossible. You already got some valid answers, and here's another variant that preserves most of the nice guarded expressions: recv_headers' :

Re: [Haskell-cafe] |> vs. $ (was: request for code review)

2006-03-06 Thread Udo Stenzel
Shannon -jj Behrens wrote: > I find "ctx |> currTok |> tokenType" to be more readable than > "tokenType $ currTok $ ctx" because you're not reading the code in > reverse. That's my primary complaint with "." and "$". Seconded. That's why I'd like to see the arguments to (.) swapped, but it's too

Re: [Haskell-cafe] Dropping trailing nulls from a list of list

2006-03-08 Thread Udo Stenzel
[EMAIL PROTECTED] wrote: > > Today, I reviewed a function I wrote a few months ago. The function, > dropTrailNulls, takes a list of lists and drops trailing null lists. For > instance: > > *Main> dropTrailNulls [[1],[2,3],[],[]] > [[1],[2,3]] dropTrailNulls = foldr dtn [] where dtn [] []

Re: [Haskell-cafe] Lists of Lists

2006-03-08 Thread Udo Stenzel
zell_ffhut wrote: > Imagine the strings are set out in a 9x9 grid type way, and i have to find > the value of a set position given 2 gird values. > > > getCharFromGrid (row,col) g = concat g !!(row * 9) + col This isn't by chance evolving into the world's ugliest sudoku solver? Are you sure, you

Re: [Haskell-cafe] Re: request for code review

2006-03-15 Thread Udo Stenzel
Shannon -jj Behrens wrote: > o How important is it that I switch from using the State monad to using > arrows? Your problem seems to be naturally soved by the State monad, therefore you should use that. > o How important is it that I switch from using |> or $ to using > arrows? Unimportant. Ho

Re: [Haskell-cafe] Wheres this going wrong

2006-03-22 Thread Udo Stenzel
Neil Rutland wrote: > ttyyppee LLiinnee == > [[((((SSttrriinngg,,SSttrriinngg)),,((SSttrriinngg,,IInntt)),,((SSttrriinngg,,IInntt)),,((SSttrriinngg,,BBooooll)),, > ((SSttrriinngg,,BBooooll)),,((SSttrriinngg,,B

Re: [Haskell-cafe] Advice needed on best way to simulate an STL vector

2006-04-19 Thread Udo Stenzel
Brian Hulley wrote: > In C++, STL provides a vector class which behaves as an array except you > can insert/delete elements from it. Though you shouldn't. If you constantly insert and delete in the middle of a std::vector, you're not using the right data structure. In fact, std::vector is almos

Re: [Haskell-cafe] Advice needed on best way to simulate an STL vector

2006-04-19 Thread Udo Stenzel
Brian Hulley wrote: > in my particular case (which was a text buffer > for an edit control implemented as a std::vector of lines where each line > contains some book-keeping info plus a std::vector of character info) > [...] > I'm keen to learn what the Haskell way is rather than just porting my

Re: [Haskell-cafe] Re: develop new Haskell shell?

2006-05-12 Thread Udo Stenzel
Ben Rudiak-Gould wrote: > My reaction to this thread is the same as Donn Cave's: even after reading > through the whole thread, I don't understand what a Haskell shell is > supposed to be. I'd like one as a scripting environment, a bit like scsh, just strongly typed and easier on the eyes. Hask

Re: [Haskell-cafe] [newbie] processing large logs

2006-05-13 Thread Udo Stenzel
Eugene Crosser wrote: > This is my program: > > module Main where > import Data.Map > main = printMax . (foldr processLine empty) . lines =<< getContents > processLine line map = insertWith (\new old -> new + old) line 1 map > printMax map = putStrLn $ show $ foldWithKey >(\key val acc

Re: [Haskell-cafe] [newbie] processing large logs

2006-05-14 Thread Udo Stenzel
Eugene Crosser wrote: > Having read "Yet another Haskell tutorial" (note on p.20), doesn't foldl > have to read the complete list before it can start processing it > (beginning from the last element)? As opposed to foldr that can fetch > elements one by one as they are needed? Both foldl and fold

Re: [Haskell-cafe] [newbie] processing large logs

2006-05-14 Thread Udo Stenzel
Eugene Crosser wrote: > Anyway, I understand that you used 'seq' in your example as a way to > "strictify" the function that updates accumulator. Could you (or > anyone) explain (in plain English, preferably:) the reason why 'seq' is > the way it is. In the first place, why does it have the first

Re: [Haskell-cafe] parsing machine-generated natural text

2006-05-20 Thread Udo Stenzel
Evan Martin wrote: > Unfortunately, the output is intended to be human-readable, and this > makes parsing it a bit of a pain. Here are some sample lines from its > output: > > France: Army Marseilles SUPPORT Army Paris -> Burgundy. > Russia: Fleet St Petersburg (south coast) -> Gulf of Bothnia. >

Re: [Haskell-cafe] parsing machine-generated natural text

2006-05-21 Thread Udo Stenzel
Evan Martin wrote: > Here's the beginning of > the file, where it's not obvious to me how to distinguish elements in > the "::" section from the rest of the file. > :: Judge: USDP Game: dip Variant: standard > :: Deadline: F1901M Mon 20 Feb 2006 20:00 PST > :: URL: http://www.diplom.org/dpjudg

Re: [Haskell-cafe] parsing machine-generated natural text

2006-05-21 Thread Udo Stenzel
Jason Dagit wrote: > > reserved "units." <|> reserved "unit." > > I always struggle with when I need to use 'try' with parsec. > > My understanding is that if 'unit.' appears in the input the first > parser will parse up to the '.' and then fail and consume the input up > to that point, leaving

Re: [Haskell-cafe] Problem trying to get class Bounded to work

2006-05-23 Thread Udo Stenzel
Jacques Carette wrote: > Bulat Ziganshin wrote: > > >malloc :: Storable a => IO (Ptr a) > >malloc = doMalloc undefined > > where > > doMalloc :: Storable b => b -> IO (Ptr b) > > doMalloc dummy = mallocBytes (sizeOf dummy) > > > > > Is there any reason to not code this as > > malloc

Re: [Haskell-cafe] Combinations

2006-06-06 Thread Udo Stenzel
[EMAIL PROTECTED] wrote: > I need a functions which takes as argument a list of lists like this one: > > [[1,2],[3],[4]] > > and gives me a list of list with all the possible combinations like this one: > > [[1,3,4],[2,3,4]] sequence Finding out why it is named that strangely is left as an exc

Re: [Haskell-cafe] what do you think of haskell ? (yes, it's a bit general ...:)

2006-06-15 Thread Udo Stenzel
minh thu wrote: > but i consider to move back to c/c++. I'm led to believe that you just haven't got the hang of the things that just aren't there in C, such as Monads and higher order functions. So you cannot yet see what you would miss in C. (And I guess, you're not feeling at home in C++ eith

Re: [Haskell-cafe] ACross

2006-06-20 Thread Udo Stenzel
Jenny678 wrote: > Can somebody help me > My Problem is to define a code for: > > >cross 7 -- means 7*7 > >+++ > >++ ++ > >+ + + + > >+++ > >+ + + + > >++ ++ > >+++ As always, try to decompose a hard problem into simple steps. It's probably adequate to repr

Re: [Haskell-cafe] Simple matrix

2006-06-22 Thread Udo Stenzel
Bjorn Lisper wrote: > Here is one way to do it. First, you have to interpret operations on > matrices as being elementwise applied. E.g, (*) is interpreted as zipWith > (zipWith (*)) rather than matrix multiply What's this, the principle of greatest surprise at work? Nonono, (*) should be matrix

Re: [Haskell-cafe] Functional progr., images, laziness and all the rest

2006-06-22 Thread Udo Stenzel
[EMAIL PROTECTED] wrote: > apparently - Clean has better handling of strictness > issues [saying at the same time that he/she doesn't use Clean...] Uhm... well... and does it? From what I've heard, Clean has the same mechanism as Haskell, which is the 'seq' primitive. Clean just adds some syntac

Re: [Haskell-cafe] user type declarations in Haskell

2006-06-22 Thread Udo Stenzel
Vladimir Portnykh wrote: > I am trying to define the following types > > data MyStringType a = String deriving (Eq, Ord, Show) > data QADouble a = Double deriving (Eq, Ord, Show) These are not what you think they are. MyStringType has a phantom type parameter and only one value, which is the con

Re: [Haskell-cafe] Simple matrix

2006-06-22 Thread Udo Stenzel
Bjorn Lisper wrote: > - your definition of fromInteger will behave strangely with the elementwise > extended operations, like (+). 1 + [[1,2],[3,4]] will become > [[2,2],[3,5]] rather than [[2,3],[4,5]]. Array languages supporting this > kind of overloading invariably have the second form of

Re: [Haskell-cafe] A question about stack overflow

2006-06-27 Thread Udo Stenzel
Neil Mitchell wrote: > Or if you don't want to go for a fold next, in a style more similar to > the original: > > maximum [] = undefined > maximum [x] = x > maximum (a:b:xs) = maximum (max a b : xs) It even reproduces the stack overflow, though for a different reason. Better write it this way: m

Re: [Haskell-cafe] Defining show for a function type.

2006-07-10 Thread Udo Stenzel
Johan Grönqvist wrote: > I would like use a list (as stack) that can contain several kinds of values. > > data Element = Int Int | Float Float | Func : Machine -> Machine | ... > > Now I would like to have this type be an instance of the class Show, so > that I can see what the stack contains i

Re: Re[2]: [Haskell-cafe] REALLY simple STRef examples

2006-07-20 Thread Udo Stenzel
Chad Scherrer wrote: > But why should this... > > >sumArrays [] = error "Can't apply sumArrays to an empty list" > >sumArrays (x:xs) = runSTArray (result x) > >where > >result x = do x0 <- thaw x > > mapM_ (x0 +=) xs > > return x0 > > work differently tha

Re: [Haskell-cafe] RE: ANN: System.FilePath 0.9

2006-07-26 Thread Udo Stenzel
Andrew Pimlott wrote: > > The drive functions stand on their own as a chunk, and are possibly > > not well suited to a Posix system, but are critical for a Windows > > system. > > Why are they critical for portable code? I am fine with > Windows-specific functions, but I think it's a mistake to b

Re: [Haskell-cafe] RE: ANN: System.FilePath 0.9

2006-07-26 Thread Udo Stenzel
Duncan Coutts wrote: > On Wed, 2006-07-26 at 15:29 +0200, Udo Stenzel wrote: > > > Exactly. I believe, a FilePath should be an algebraic datatype. > > We've had this discussion before. The main problem is that all the > current IO functions (readFile, etc) use the File

Re: [Haskell-cafe] RE: ANN: System.FilePath 0.9

2006-07-26 Thread Udo Stenzel
Andrew Pimlott wrote: > Maybe the trailing slash is important enough to take into account. No, not the trailing slash. The difference between a directory and its contents is important enough. This is ususally encoded using a trailing slash, but I'd rather not worry about that detail in a program

Re: [Haskell-cafe] RE: ANN: System.FilePath 0.9

2006-07-26 Thread Udo Stenzel
Duncan Coutts wrote: > In practise in the short term, the choice is between each application > fumbling with strings in different incorrect ways or a library that > fumbles with strings in a rather more considered and portable way. Honestly I don't see a reason to bother with (++) and takeWhile an

Re: [Haskell-cafe] RE: ANN: System.FilePath 0.9

2006-07-27 Thread Udo Stenzel
Neil Mitchell wrote: > How about > > class FilePathLike a where >getRealFilePath :: a -> String > > Then convert readFile etc. to take a FilePathLike, rather than a filepath? Uhm, just a minute ago the argument was that we can't change the IO library... Anyway, my gut says, it dislikes 'cla

Re: [Haskell-cafe] RE: ANN: System.FilePath 0.9

2006-07-28 Thread Udo Stenzel
Andrew Pimlott wrote: > On Wed, Jul 26, 2006 at 05:06:41PM -0400, David Roundy wrote: > > This doesn't apply uniformly to all programs--except that we can say > > that any path with a trailing '/' is intended to be a directory, and > > if it's not, then that's an error. > > I thought some more abo

Re: [Haskell-cafe] RE: ANN: System.FilePath 0.9

2006-07-29 Thread Udo Stenzel
Andrew Pimlott wrote: > On Thu, Jul 27, 2006 at 09:59:37PM +0200, Udo Stenzel wrote: > > In fact, that's consistent with the current documentation, because > > > > *> getFileName "foo" == "foo" > > *> getFileName "foo/" == "

Re: [Haskell-cafe] [Parsec] Backtracking with try does not work for me?

2006-07-31 Thread Udo Stenzel
Stephane Bortzmeyer wrote: > minilang = do >char 'a' >try (optional (do {comma ; char 'b'})) >optional (do {comma ; char 'c'}) >eof >return "OK" > > * CUT HERE *** > > parse error at (line 1, column 2): > unexpected "c" > expecting "

Re: [Haskell-cafe] Re: [Parsec] Backtracking with try does not work for me?

2006-08-01 Thread Udo Stenzel
Stephane Bortzmeyer wrote: > > The first would be to test whether "bb" is followed by "eof" or > > "comma" before accepting it. > > notFollowedBy actually does the opposite (checking that there are no > more letters). Are you sure that you don't actually want *> many1 letter `sepBy1` comma ? J

Re: [Haskell-cafe] Filtering a big list into the IO monad

2006-08-03 Thread Udo Stenzel
Gabriel Sztorc wrote: > I want to filter a list with a predicate that returns a IO value, > something that filterM is supposed to do. The problem is, filterM > overflows the stack for really big lists Are you sure it's filterM's fault? Can you post the code in question? Stack overflows are usua

Re: [Haskell-cafe] Why Not Haskell?

2006-08-04 Thread Udo Stenzel
Hans van Thiel wrote: > I'm wondering why I can't find any commercial Haskell applications on > the Internet. Is there any reason for this? Of course. Corporations are conservative to the point of being boneheaded. So to avoid risk, they all went on the internet and said, "Gee, I can't find any

Re: [Haskell-cafe] Why Not Haskell?

2006-08-04 Thread Udo Stenzel
Jason Dagit wrote: > On 8/4/06, Donn Cave <[EMAIL PROTECTED]> wrote: > >6. Instability - available for 15 years, you say, but does the Haskell > >of 15 years ago support today's programs? Does standard Haskell > >even support today's programs? Uh, this one's wrong. Does C++ of 15 years

Re: [Haskell-cafe] Why shouldn't variable names be capitalized?

2006-08-04 Thread Udo Stenzel
Martin Percossi wrote: > Paul Hudak wrote: > >foo x y = ... > > > >We know that x and y are formal parameters, whereas if they were > >capitalized we'd know that they were constructors. > > I agree that naming can be abused. But I think it should be *me* ... Oh, you like to decide lexical ambigu

Re: [Haskell-cafe] Why Not Haskell? (sidenote on licensing)

2006-08-07 Thread Udo Stenzel
Matthias Fischmann wrote: > But if GPL is stuck to any part of the code and > manages to infect the rest, the client can make you sign as many NDAs > as there can be. The GPL still entitles you to sell it. Nonsense. The GPL says, *if* you distribute a binary, *then* you also have to distribute t

Re: [Haskell-cafe] Why Not Haskell? (sidenote on licensing)

2006-08-07 Thread Udo Stenzel
Matthias Fischmann wrote: > And it's really not as easy to control as you suggest: If you ever > take in a single patch under the GPL, This kind of thing doesn't happen by accident. Patches don't magically creep into your code, you have to apply them deliberately and you should always know whethe

Re: [Haskell-cafe] How can we detect and fix memory leak due to lazyness?

2006-08-08 Thread Udo Stenzel
Ahn, Ki Yung wrote: > Recently, I'm facing the dark side of laziness > -- the memory leak because of laziness. > > Are there standardized approaches for detecting and fixing > these kind of problems? Not really. As Don S. already said, try heap profiling. The function that is too lazy will show

Re: [Haskell-cafe] creating tree with level subnodes and incrementing number?

2006-08-08 Thread Udo Stenzel
Marc Weber wrote: > I've tried as an exercise to learn how to use the state monad to create > a tree this way: > > createTree :: Int -> Int -> (Tree Int, Int) > createTree 4 = runState $ State $ \s -> (Node s [] , s+1) -- stop at level 4 > createTree level = runState (do item <- State $ (\s -> (s,

Re: [Haskell-cafe] Last statement in 'do' must be an expression error.

2006-08-17 Thread Udo Stenzel
Szymon Z??bkiewicz wrote: > The compiler tells me thats there's an error on line 10: > "The last statement in a 'do' construct must be an expression" I think, you have reached the point where treating do-notation as magic won't help you. Remember, > do > nr1 <- read (prompt "enter 1. number

Re: [Haskell-cafe] Writing binary files

2006-08-21 Thread Udo Stenzel
Neil Mitchell wrote: > I'm trying to write out a binary file, in particular I want the > following functions: > > hPutInt :: Handle -> Int -> IO () > > hGetInt :: Handle -> IO Int > > For the purposes of these functions, Int = 32 bits, and its got to > roundtrip - Put then Get must be the same.

Re: [Haskell-cafe] stack overflow when using ST monad

2006-08-24 Thread Udo Stenzel
Hi Gregory, Gregory Wright wrote: > step :: Tag s -> ST s (Maybe Integer) > step t = do > c <- readSTRef (count t) > s <- readSTRef (state t) > writeSTRef (count t) (c - 1) > writeSTRef (state t) (nextState s) > if (c <= 0) then return Nothing else return (J

Re: [Haskell-cafe] difference between type and newtype

2006-08-26 Thread Udo Stenzel
Andrea Rossato wrote: > this is what I'm trying to do, sort of: turn the code at the button > into the do-notation.[1] > type MSO a = State -> (a, State, Output) > > mkMSO :: a -> MSO a > mkMSO a = \s -> (a, s, "") > > bindMSO :: MSO a -> (a -> MSO b) -> MSO b > bindMSO m f = \x -> >

Re: [Haskell-cafe] Space leak whilst implementing streams

2006-08-26 Thread Udo Stenzel
[EMAIL PROTECTED] wrote: > I found a way to remove this space leak, however, I do not really > understand why there was a space leak in the first place. I would > really appreciate any light that could be shed on this. > instance ArrowChoice SF where > left (SF f) > = SF (\xs -> combine xs

Re: [Haskell-cafe] state and exception or types again...

2006-08-29 Thread Udo Stenzel
Andrea Rossato wrote: > Il Mon, Aug 28, 2006 at 09:28:02PM +0100, Brian Hulley ebbe a scrivere: > > data Eval_SOI a = SOIE {runSOIE :: State -> (a, State, Output, Bool)} > > well, I thought that this was not possible: > (>>=) :: m a -> (a -> m b) -> m b And you are right. In case of an exception

Re: [Haskell-cafe] [Parsec] A combinator to match between M and N times?

2006-08-29 Thread Udo Stenzel
Stephane Bortzmeyer wrote: > Parsec provides "count n p" to run the parser p exactly n times. I'm > looking for a combinator "countBetween m n p" which will run the > parser between m and n times. It does not exist in Parsec. infixr 2 <:> (<:>) = ap . ap (return (:)) countBetween 0 0 _ = return [

Re: [Haskell-cafe] [Parsec] A combinator to match between M and N times?

2006-08-29 Thread Udo Stenzel
Chris Kuklewicz wrote: > Again, Parsec requires you to put "try" where you need it I'm pretty sure it does, although this > Udo Stenzel wrote: > >countBetween 0 n p = p <:> countBetween 0 (n-1) p <|> return [] is a place where it's not needed in

Re: [Haskell-cafe] ReadP question

2006-08-31 Thread Udo Stenzel
Chris Kuklewicz wrote: > I just tried to mimic regular expression matching with ReadP and got what > seems like a non-terminating program. Is there another way to use ReadP to > do this? > > >-- Simulate "(a?|b+|c*)*d" regular expression > >test = star (choice [quest (c 'a') > >

Re: [Haskell-cafe] Exercise in point free-style

2006-09-01 Thread Udo Stenzel
Julien Oster wrote: > While we're at it: The best thing I could come up for > > func2 f g l = filter f (map g l) > > is > > func2p f g = (filter f) . (map g) > > Which isn't exactly point-_free_. Is it possible to reduce that further? Sure it is: func2 f g l = filter f (map g l) func2 f g = (

Re: [Haskell-cafe] Re: Re: A free monad theorem?

2006-09-02 Thread Udo Stenzel
Benjamin Franksen wrote: > Sure. Your definition of bind (>>=): > ... > applies f to something that it has extracted from m, via deconstructor > unpack, namely a. Thus, your bind implementation must know how to produce > an a from its first argument m. I still have no idea what you're driving at,

Re: [Haskell-cafe] Re: Re: A free monad theorem?

2006-09-03 Thread Udo Stenzel
Lennart Augustsson wrote: > Well, bind is extracting an 'a'. I clearly see a '\ a -> ...'; it > getting an 'a' so it can give that to g. Granted, the extraction is > very convoluted, but it's there. Oh, that can be remedied... > m >>= g = m . flip g In fact, why even mention m? > (>>=) =

Re: [Haskell-cafe] Why does this program eat RAM?

2006-09-05 Thread Udo Stenzel
John Goerzen wrote: > I have the below program, and I'm trying to run it on an input of about > 90MB. It eats RAM like crazy, and I can't figure out why. > > wordfreq inp = Map.toList $ foldl' updatemap (Map.empty::Map.Map String Int) > inp > where updatemap nm word = Map.insertWith updatefu

  1   2   >