Re: Help on Homework help
G'day all. On Wed, Sep 03, 2003 at 08:34:58AM +0100, Simon Peyton-Jones wrote: > One suggestion: it'd be good to suggest *strongly* that people only > send their homework-style questions to Haskell-café, not to the main > Haskell list. Done, thanks. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Help on Homework help
G'day all. In response to the recent poll, and because I promised to, here is a first attempt at a page to direct people to, should they ask for homework help in the wrong way: http://haskell.org/hawiki/HomeworkHelp Comments, criticisms and contributions are most welcome. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Poll: How to respond to homework questions
G'day all. On Thu, Aug 28, 2003 at 11:25:43AM +0200, Ketil Z. Malde wrote: > I suppose C is one way to do F, in particular by providing a working > program so complex and opaque that no first-year could possibly have > written it. Uhm... yes. > I'm not sure I care much for politesse. Understood (and I'm as guilty of strategy (C) as anyone), however, it can occasionally be hard to tell the difference between someone who is "testing the waters" and someone who is just lazy, and it may be worth giving people the benefit of the doubt. In addition, ridiculing the lazy may turn away people who may otherwise be tempted to ask for help "properly". > And hey, 'fun' is an important part of all this. :-) Certainly! Speaking of FAQs, this is quite good: http://www.catb.org/~esr/faqs/smart-questions.html Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Prefix and postfix operators
G'day all. On Thu, Aug 28, 2003 at 11:05:52AM +0200, Ketil Z. Malde wrote: > We already have prefix operators, don't we? I.e., regular functions > are prefix? Not really. This: - sqrt x Doesn't mean the same thing as this: negate sqrt x I think the difficulty is that it's very hard to convert a general operator grammar into a context-free grammar, particularly if you can set precedences and associativities at run-time. See, for example: http://citeseer.nj.nec.com/aasa91precedences.html Effectively you end up writing a whole other parser just to handle operators. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Poll: How to respond to homework questions
G'day all. On Wed, Aug 27, 2003 at 05:50:14PM -0400, Matthew Donadio wrote: > For the first case, I would vote for D and/or E as appropriate. For the > second case, I vote for (F) Ignore. IMO, based on the result of this poll, we should develop some kind of short FAQ (e.g. on the wiki) which we can include in the list subscription information and can also send to people who ask for the kind of homework help that we don't like to see. IMO, this is better than ignoring, and far more polite than giving a correct but highly useless answer, fun though that might be. I'd be happy to write something once the vote comes in. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: IO StateTransformer with an escape clause
G'day all. On Tue, Aug 26, 2003 at 02:33:28PM +1000, Thomas L. Bevan wrote: > I'd like some help building an IO StateTransformer which can be > escaped midway through without losing the state accummulated up to > that point. A simple way to do this is to use a ReaderT monad stacked on top of IO, where the reader state is an IORef to whatever your "real" state is, then write wrapper functions to access the IORef like a state monad. For example, if you had: newtype PersistentStateT s m a = PersistentStateT (ReaderT (IORef s) m a) then you could write: -- WARNING: Unchecked code follows! instance (MonadIO m) => MonadState s (PersistentState s m) where get = PersistentStateT $ do r <- ask liftIO (readIORef r) set s = PersistentStateT $ do r <- ask liftIO (writeIORef r s) The drawback is that the state is no longer backtrackable, say, if you use a nondeterminism monad transformer stacked over this. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Homework
G'day all. On Fri, Aug 22, 2003 at 03:41:14PM +1000, [EMAIL PROTECTED] wrote: > Seeing as its thst time of year again and everyone is posting their > homework, has anyone got any good puzzles to do? > I wouldn't mind having a go at something a bit tricky. OK, here's a tricky problem. Take a list S. Delete some elements from the list. What you have left is a subsequence of S. For example, [1,3,2] is a subsequence of [2,1,2,1,3,2,1,3]. Consider the following list: [1,2,3,1,2,3,1] This list contains all permutations of the list [1,2,3] as subsequences. It is also minimal, in the sense that there is no shorter subsequence which will do (though there are potentially many minimal subsequences). We will call such a list a shortest supersequence over the alphabet [1..3]. The challenge is multi-part. You may answer as many or as few questions as you want. 1. Write a function sss :: Int -> [Int] where sss n is a shortest supersequence over the alphabet [1..n]. Make this as efficient as possible. Prove an upper-bound complexity on your function. 2. Write a function sss_length :: Int -> Int where sss_length n is the length of a shortest supersequence over the alphabet [1..n]. Make this as efficient as possible. Prove an upper-bound complexity on your function. If you can't solve this problem efficiently, write a function sss_length_bounds :: Int -> (Int,Int) which returns the best upper and lower bounds that you can. (Hint: n is a trivial lower bound, n^2 is a trivial upper bound. A tighter upper bound is n^2-n+1. Prove this as an exercise.) 3. Write a function sss_count :: Int -> Int where sss_count n is the number of shortest supersequences over the alphabet [1..n]. Make this as efficient as possible. Prove an upper-bound complexity on your function. (Hint: sss_count n must be a multiple of n factorial. Why?) If you can't solve this problem efficiently, write a function sss_count_bounds :: Int -> (Int,Int) which returns the best upper and lower bounds that you can. Incidentally, I don't have sub-exponential answers to any of these questions. You did ask for something "a bit tricky". Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Pascal Line in Haskell
G'day all. On Fri, Aug 22, 2003 at 09:40:12AM +1000, Job L. Napitupulu wrote: > Can anyone help me how to make a function which takes an integer n > 0 and > returns the list of integers in Line of Pascal's Triangle. For examples, > > pascalLine 4 -> [1,4,6,4,1] > pascalLine 7 -> [1,7,21,35,35,21,7,1] This should do the trick. Cheers, Andrew Bromage 8<---CUT HERE---8< type InfTable a = [(Integer, BinTree a)] data BinTree a = Leaf a | Node Integer (BinTree a) (BinTree a) swing :: Integer -> Integer swing n = rec n (\_ _ r -> r) where rec :: Integer -> (Integer -> Integer -> Integer -> Integer) -> Integer rec n k | n < 2 = k 1 1 1 | otherwise = rec (n `div` 2) (\nn ff r -> swing' n nn ff (\nn' ff' -> k nn' ff' $! (r*r*ff'))) swing' :: Integer -> Integer -> Integer -> (Integer -> Integer -> Integer) -> Integer swing' n nn ff k | nn `mod` 2 == 1 = swing_odd k nn ff | otherwise = swing_even k nn ff where swing_odd k nn ff | nn <= n = swing_even k (nn+1) $! (ff*nn) | otherwise = k nn ff swing_even k nn ff | nn <= n = swing_odd k (nn+1) $! (ff*4 `div` nn) | otherwise = k nn ff recProd :: Integer -> Integer -> Integer recProd b n | n < 5 = case n of 0 -> 1 1 -> b 2 -> b*(b+1) 3 -> b*(b+1)*(b+2) 4 -> (b*(b+1))*((b+2)*(b+3)) | otherwise = let n2 = n `div` 2 in recProd b n2 * recProd (b+n2) (n-n2) pascalLine :: Integer -> [Integer] pascalLine n | n >= 0 = searchTable n table where table :: InfTable [Integer] table = buildInfTable 1 5 buildInfTable n i = (nextn, buildInfTable' n i) : buildInfTable nextn (i+1) where nextn = n + 2^i buildInfTable' base 0 = Leaf [ c base k | k <- [0..base] ] where c m n | m < 0 = 0 | n < 0 || n > m = 0 | n > m `div` 2 = c' n (m-n) | otherwise = c' (m-n) n c' i j = recProd (i+1) j `div` swing j buildInfTable' base i = Node (base + midSize) (buildInfTable' base (i-1)) (buildInfTable' (base + midSize) (i-1)) where midSize = 2 ^ (i-1) searchTable x ((x',tree):ms) | x < x'= searchTree x tree | otherwise = searchTable x ms searchTree x (Leaf y) = y searchTree x (Node mid l r) | x < mid = searchTree x l | otherwise = searchTree x r ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: More type design questions
G'day all. On Tue, Aug 19, 2003 at 12:31:08PM +0200, Konrad Hinsen wrote: > Under what conditions would Haskell programmers make some type an instance of > Functor? Whenever it could possibly be done (i.e. whenever fmap makes sense)? > Or just when fmap would be used frequently for some type? Like anything else in software development, it's a judgement call. The questions you have to ask might include: - Does it make sense? - Is it an appropriate abstraction for this type? - Would I want to encourage another programmer to use it? - Do I want to use it myself? - Would it unnecessarily limit the possible implementations of this abstract type? The last point is particularly important to consider. A Set-like type, for example, is mathematically a functor, but any implementation of fmap will in general change the relative orderings, hash values etc of member elements. This means that supporting fmap efficiently might rule out many interesting implementations of this container. If in doubt, don't implement it (yet). Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: IO Bool -> Bool
G'day all. On Thu, Aug 14, 2003 at 11:30:11AM -0700, Brandon Michael Moore wrote: > I'm surprise nobody has mentioned unsafePerformIO (:: IO a -> a). > As the name suggests, it isn't referentially transparent. I'm not surprised. First, it's not standard Haskell. Second, people tend not to mention it because you really shouldn't use it unless you know what you're doing. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Type design question
G'day all. On Tue, Jul 29, 2003 at 12:11:29PM +0200, Konrad Hinsen wrote: > I think that C++ was a lot worse, even the accepted features (e.g. templates) > didn't work the same with all compilers. All non-trivial code came with a > list of supported compilers. True. If we had more Haskell implementations, we might be in the same boat. Our situation is much simpler. Code is either written for Haskell 98, or for "Glasgow extensions". Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Type design question
G'day all. On Mon, Jul 28, 2003 at 03:42:11PM +0200, Konrad Hinsen wrote: > What is the general attitude in the Haskell community towards > compiler-specific extensions? My past experience with Fortran and C/C++ tells > me to stay away from them. Portability is an important criterion for me. There is no ISO standard Haskell. There is Haskell 98, but that was deliberately designed to be a simpler language than what came before it, with no experimental features, partly to make teaching the language easier. (You can't write a textbook for a moving target.) The situation with Haskell today is somewhat analogous to C++ _during_ its standardisation process, when people were proposing all kinds of proposed language features (exceptions spring to mind as one example) which not everyone supported and some supported incompletely. As others have noted, using features which are almost certainly going to end up in the next "official" standard is a pretty safe bet, because your code will work everywhere eventually. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Type design question
G'day all. On Sun, Jul 27, 2003 at 10:36:46PM -0400, Dylan Thurston wrote: > However, I would be sure to distinguish between an inner product space > and a vector space. That's true. If you're after a completely generic solution, this might be an issue. > An inner product space has the 'innerProduct' operation you > mention; as you say, there is very frequently more than one interesting > inner product. I might also add that normalisation doesn't necessarily make sense on every inner product space. In my situation, for example, the scalar field is Rational, so it wasn't closed under square root. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Type design question
G'day all. On Fri, Jul 25, 2003 at 03:48:15PM -0400, Dylan Thurston wrote: > Another approach is to make Universe a multi-parameter type class: > > class (RealFrac a, Floating a) => Universe u a | u -> a where > distanceVector :: u -> Vector a -> Vector a -> Vector a > ... Actually, this is a nice way to represent vector spaces, too: class (Num v, Fractional f) => VectorSpace vs v f | vs -> v f where scale :: vs -> f -> v -> v innerProduct :: vs -> v -> v -> f The reason why you may want to do this is that you may in general want different inner products on the same vectors, which result in different vector spaces. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Old alternative syntax for list comprehensions?
G'day all. On Mon, Jul 14, 2003 at 11:08:55PM -0400, Ken Shan wrote: > I just wanted to see that asterisk again. ...and semicolons returned to their rightful place as separators for list comprehension/diagonalisation qualifiers. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Handling large ini files.
G'day all. On Sun, Jul 13, 2003 at 10:09:21AM +1000, Andrew Rock wrote: > I think that each being a customisation *is* sufficient for coherence > of one data structure to hold them all. I agree, though using different data structures for each set of configuration parameters which will be used together is also something to consider. Also, if you're using GHC, -funbox-strict-fields is one flag you may look into. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Hugs Humor
G'day all. On Tue, Jul 08, 2003 at 01:06:23PM +0100, Jon Fairbairn wrote: > Unfortunately we don't have Real (in > libraries as far as I remember -- if you have a continued > fraction implementation of it, it ought to go to the > libraries list). Not one, but TWO implementations! One using continued fractions, one using LFTs. http://cvs.sourceforge.net/cgi-bin/viewcvs.cgi/haskell-libs/libs/exactreal/ Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Representing cyclic data structures efficiently in Haskell
G'day all. On Mon, Jul 07, 2003 at 04:37:46PM +0100, Sarah Thompson wrote: > I'd considered something like embedding the type in the IO monad, with > links between components implemented as IORefs, but I'd really prefer > something cleaner (pure functional). If the code ends up horribly > complicated in order to get decent performance, I might as well fold and > use C++ instead. At the risk of stating the obvious, IORefs _are_ pure functional. :-) > I'm currently wondering about going for an adjacency list approach (as > used by most graph libraries), with the tuples in the adjacency list > extended to include input/output labels, resulting in a 4-ary tuple > rather than the usual 2-ary. But, I don't want to be stuck with > representing this as a list -- I really need log N lookups or > performance will stink horribly as circuits get big. Maybe a pair of > finite maps, allowing the edges to be traversed in either direction? You could do that. Or you could use just one FiniteMap and reverse the iterator before you use it. (Remember that reverse is an amortised O(1) operation, assuming you need to traverse the whole list.) Or you could take a copy of the FiniteMap source code and add your own reverse iterator to complement the forward iterator which is already there. You could even submit a patch. :-) Or you could use a different data structure, say, one with O(n) iteration from either end, O(log n) search and O(1) insertion onto either end. There are several of these floating around. This one is quite good: http://citeseer.nj.nec.com/25942.html Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Representing cyclic data structures efficiently in Haskell
G'day all. On Mon, Jul 07, 2003 at 04:04:17PM +0100, Sarah Thompson wrote: > > I would also need to implement efficient indexes into the data structure > > -- flat searching will be too slow for non-trivial amounts of data. In > > C++, I'd implement one or more external (probably STL-based) indexes > > that point into the main data structure. I replied: > The direct Haskell equivalent is to use Refs; either IORefs or > STRefs. (I'd personally use IORefs, but that's because I like > having IO around.) Dereferencing an IORef is a constant-time > operation, just like chasing a pointer in C. I forgot to give an example. :-) Suppose you want some kind of electronic circuit, as you suggested. Abstractly, you want something like this: data Node = Node NodeState [Component] data Component = Resistor ResistorCharacteristics Node Node | Transistor TransistorCharacteristics Node Node Node | {- etc -} You can make this indirect in introducing refs: type NodeRef = IORef Node type ComponentRef = IORef Component data Node = Node NodeState [ComponentRef] data Component = Resistor ResistorCharacteristics NodeRef NodeRef | Transistor TransistorCharacteristics NodeRef NodeRef NodeRef The data structures are mutable: getNodeState :: NodeRef -> IO NodeState getNodeState node = do Node state _ <- readIORef node return state setNodeState :: NodeRef -> NodeState -> IO () setNodeState node state = do modifyIORef (\Node _ cs -> Node state cs) node and it's straightforward to construct an index into the middle somewhere: type NamedNodeIndex = FiniteMap String NodeRef Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Representing cyclic data structures efficiently in Haskell
G'day all. As you note, some kind of indirection is what you want here. On Mon, Jul 07, 2003 at 04:04:17PM +0100, Sarah Thompson wrote: > I would also need to implement efficient indexes into the data structure > -- flat searching will be too slow for non-trivial amounts of data. In > C++, I'd implement one or more external (probably STL-based) indexes > that point into the main data structure. The direct Haskell equivalent is to use Refs; either IORefs or STRefs. (I'd personally use IORefs, but that's because I like having IO around.) Dereferencing an IORef is a constant-time operation, just like chasing a pointer in C. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Hugs Humor
G'day all. On Mon, Jul 07, 2003 at 12:01:09PM +0200, Jerzy Karczmarczuk wrote: > I don't understand the remark that the internal arithmetic is > binary. Sure, it is, so what? The reason is that you can get the Rational representation even faster than using continued fractions. :-) toFrac :: (RealFloat a) => a -> Rational toFrac x | m == 0= 0 | otherwise = fromInteger m * 2^^(toInteger n) where (m,n) = decodeFloat x Prelude> toFrac 0.1 13421773 % 134217728 Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Hugs Humor
G'day all. On Sat, Jul 05, 2003 at 07:43:18PM +0200, Steffen Mazanek wrote: > Prelude> 0.1::Rational > 13421773 % 134217728 That's allowed. The Rational only has to be correct to the limit of machine precision. (Incidentally, if it's any help in working out how this Rational was computed, the denominator is 2^27.) > Prelude> 13421773/134217728 > 0.1 Also allowed for the same reason. > Ok, ok, it is no bug... No, but this might be: Prelude> 13421773/134217728 - 0.1 1.4901161138336505e-9 I think that the language spec is sufficiently vague on this point that Hugs' behaviour is reasonable. When using floating point, you have to work with the numeric error rather than ignore it. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Non-determinism, backtracking and Monads
G'day all. On Wed, Jun 11, 2003 at 12:36:30PM +0200, Jerzy Karczmarczuk wrote: > It is possible, instead of implementing the *data backtracking* through lazy > lists, to make lazy "backtrackable" continuations, permitting to redirect > the flow of control to produce something else. The two ways are - perhaps not > entirely equivalent, but essentially two orchestrations of the same > theme. > I lost my references, perhaps somebody?... If you're referring to the paper(s) by Ralf Hinze, they are most certainly equivalent. WARNING: Long post follows. Consider the simplified term implementation of a nondeterminism monad, which basically operates on lists: data Nondet1 a = Cons a (Nondet1 a) | Fail -- This is the "observer" method runNondet1 :: (Monad m) => Nondet1 a -> m a runNondet1 m = case m of Cons x _ -> return x Fail -> fail "no solutions" return a = Cons a Fail m >>= k = case m of Cons a n -> mplus (k a) (n >>= k) Fail -> Fail mzero = Fail mplus m n = case m of Cons a m' -> Cons a (mplus m' n) Fail -> n You can derive a continuation-passing implementation by transforming away the data structures. This is a technique well-known to practitioners of traditional lambda calculus. We'll start by abstracting the data structures out. We need replacements for both constructor functions (i.e. Cons and Fail) and the pattern matching used above. data Nondet1 a = Fail | Cons a (Nondet1 a) cons1 :: a -> Nondet1 a -> Nondet1 a cons1 a m = Cons a m fail1 :: Nondet1 a fail1 = Fail unpack1 :: Nondet1 a -> (a -> Nondet1 a -> b) -> b -> b unpack1 (Cons a m) c f = c a m unpack1 Fail c f = f The monad can now be re-implemented in terms of these operations: runNondet1 :: (Monad m) => Nondet1 a -> m a runNondet1 m = unpack1 m (\x _ -> return x) (fail "no solutions") return a = cons1 a fail1 m >>= k = unpack1 m (\a n -> k a `mplus` n >>= k) fail1 mzero = fail1 mplus m n = unpack1 m (\a m' -> cons1 a (mplus m' n)) n Note that there are now no data structures in here, only calls to fail1, cons1 and unpack1. We can implement these how we like so long as these properties hold: unpack1 fail1 c f = f unpack1 (cons1 x xs) c f = c x xs The lambda calculus solution is to make unpack1 the identity function. Unfortunately that doesn't entirely work in Haskell because of the type system, but we can get pretty close by using rank-2 types and a newtype constructor: -- Compare this with the type of unpack1 above newtype Nondet2 a = Nondet2 (forall b. (a -> Nondet2 a -> b) -> b -> b) fail2 :: Nondet2 a fail2 = Nondet2 (\c f -> f) cons2 :: a -> Nondet2 a -> Nondet2 a cons2 a m = Nondet2 (\c f -> c a m) unpack2 :: Nondet2 a -> (a -> Nondet2 a -> b) -> b -> b unpack2 (Nondet2 m) = m We can inline these functions everywhere to get: runNondet2 :: (Monad m) => Nondet2 a -> m a runNondet2 (Nondet2 m) = m (\x _ -> return x) (fail "no solutions") return a = Nondet2 (\c _ -> c a (Nondet2 (\_ f -> f))) (Nondet2 m) >>= k = m (\a n -> mplus (k a) (n >>= k)) (Nondet2 (\_ f -> f)) mzero = Nondet2 (\_ f -> f) mplus (Nondet2 m) n = m (\a m' -> Nondet2 (\c _ -> c a (mplus m' n))) n ...and we have a continuation-passing implementation. Note that this is not 100% identical to the one from Ralf's paper and tech report. Transforming the above code into Ralf's is left as an exercise. (It's tricky but mechanical.) Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Non-determinism, backtracking and Monads
G'day all. On Wed, Jun 11, 2003 at 08:37:48AM +0100, Graham Klyne wrote: > I was thinking some more about this comment of yours, and my own experience > with the ease of using lists to implement prolog-style generators, and > think I come to some better understanding. You might find this amusing: http://cvs.sourceforge.net/cgi-bin/viewcvs.cgi/hfl/hfl/mtl/Logic.hs?rev=1.2 This monad and monad transformer basically implement ground-moded logic programming, including if-then-else with soft cut. (It doesn't implement Prolog cut, but you really don't want it.) > So there seems to be a very close relationship between the lazy list and > non-deterministic computations, but what about other data structures? I > speculate that other structures, lazily evaluated, may also be used to > represent the results of non-deterministic computations, yet allow the > results to be accessed in a different order. Yes. The different data structures would, in general I think, correspond to different search rules. Using a lazy list corresponds to depth-first search. Your tree monad actually returns the entire computation tree, which can then be traversed in depth-first order, breadth-first order, or whatever order you want. You have to be careful with monad transformers stacked on top of non-commutative monads, though. Most programmers would expect, in this code: (lift m1 `mplus` lift m2) `mplus` lift m3 that both m1 and m2 will be evaluated before m3; at least in circumstances where it mattered. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: powerset
G'day all. On Wed, Jun 04, 2003 at 02:00:08PM +0100, Keith Wansbrough wrote: > This formulation is particularly nice because in memory, you *share* > all of the lists from the previous iteration, rather than making > copies. [...] > Notice all the sharing - this is a very efficient representation! You > save on copying, and you save on memory use. I can never resist a can labelled "worms". Let me get out my tin opener... You do save on memory allocations. If, however, you consume the list lazily and discard the results as you consume them (which is the common way lazy programs are written), you actually use more memory at once. Try it if you don't believe me. Test it with this program, using each definition of powerset: summer :: [[a]] -> Integer summer xss = foldl' (\xs r -> r + toInteger (length xs)) 0 xss n :: Int n = 32 main :: IO () main = print (summer (powerset [1..n])) You'll find that one of them runs in O(n) space and the other most likely blows the heap. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Tokenizing Strings
G'day all. On Wed, Apr 02, 2003 at 11:26:46AM +1000, [EMAIL PROTECTED] wrote: > in this case, I have a string containing multiples fields seperated by *two* > blank lines (\n\n). I can't just break on the newline character, as single > newline characters can be found inside each field. > > any idea how I can do this without too much hassle? Here's some code I wrote some time ago which does Knuth-Morris-Pratt string searching: http://haskell.org/wiki/wiki?RunTimeCompilation Note that there are a couple of differences between matchKMP and break which you will no doubt discover. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: speedup help update
G'day all. On Mon, Mar 03, 2003 at 09:53:24PM -0500, Damien R. Sullivan wrote: > Time to look at arrays, finally. This might help: http://haskell.org/wiki/wiki?MemoisingCafs Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: speedup help
G'day all. On Mon, Mar 03, 2003 at 04:59:21PM -0800, Hal Daume III wrote: > I think you would get a big speed-up if you got rid of all the rational > stuff and just used: > > comb m n = fact m `div` (fact n * fact (m-n)) Or, even better, if you didn't multiply stuff that you're just going to divide out in the first place. choose :: (Integral a) => a -> a -> Integer choose m n | m < 0 = 0 | n < 0 || n > m = 0 | n > m `div` 2 = choose' n (m-n) | otherwise = choose' (m-n) n where choose' i' j' = let i = toInteger i' j = toInteger j' in productRange (i+1) j `div` factorial j factorial :: (Integral a) => a -> Integer factorial n = productRange 1 n productRange :: (Integral a) => Integer -> a -> Integer productRange b n | n < 5 = case n of 0 -> 1 1 -> b 2 -> b*(b+1) 3 -> (b*(b+1))*(b+2) 4 -> (b*(b+3))*((b+1)*(b+2)) _ -> 0 | otherwise = let n2 = n `div` 2 in productRange b n2 * productRange (b+toInteger n2) (n-n2) Note that productRange uses a divide-and-conquer algorithm. The reason for this is that it's more efficient to multiply similarly-sized Integers than dissimilarly-sized Integers using GMP. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: is identity the only polymorphic function without typeclasses?
G'day. On Mon, Mar 03, 2003 at 11:49:29AM +0200, Cagdas Ozgenc wrote: > Yes, I thought about these too. Do you find these functions practically > useful? Can you give an example where I can utilize these functions? Functions like this are useful for plugging into higher-order functions to tailor them for your specific needs. Here's an artificial example: length = sum . map (const 1) Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: is identity the only polymorphic function without typeclasses?
G'day all. On Sun, Mar 02, 2003 at 10:18:13AM +0200, Cagdas Ozgenc wrote: > Is identity function the only meaningful function one can write > without constraining the type variable using a typeclass? If not, > could you please give a counter-example? This might help: @incollection{ wadler89theorems, author = "Philip Wadler", title = "Theorems for Free!", booktitle = "Proceedings 4th Int.\ Conf.\ on Funct.\ Prog.\ Languages and Computer Arch., {FPCA}'89, London, {UK}, 11--13 Sept 1989", publisher = "ACM Press", address = "New York", pages = "347--359", year = "1989" } Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: a monadic if or case?
G'day all. On Thu, Feb 13, 2003 at 02:54:42PM -0500, David Roundy wrote: > That's pretty nice (although not quite as nice as it would be to be able to > use real ifs with no extra parentheses). Any idea how to do something like > this with a case? http://www.haskell.org/mailman/listinfo/haskell-cafe In the case of Maybe, what you're really trying to do there is a kind of exception handling. You may or may not be better off using a real exception monad transformer on top of IO (or whatever the underlying monad is). One possibility is Control.Monad.Error (fromt he MTL). Here's another possibility: http://cvs.sourceforge.net/cgi-bin/viewcvs.cgi/hfl/hfl/mtl/Negate.hs?rev=1.2 I know this didn't directly answer your question, but it's good to explore the design space. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: separate compilation [was Re: Global variables?]
G'day all. On Wed, Feb 05, 2003 at 09:28:05PM -0600, Jon Cast wrote: > I think I see what you're saying. I still maintain, however, that, > since you've changed the type of B.b (admittedly implicitly), and B.b is > exported from B, that you've changed B's interface. > > There is a reason make is designed to re-build B /and/ (potentially) A > when C changes, after all. In principle, it shouldn't. If module D imports module E, changing E's implementation should not force a recompilation of module D (assuming no intermodule optimisation, of course). In GHC terms, D.o should only depend on D.hs and E.hi. However, this isn't my main problem. This is at best a big pain, and at worst a potential waste of an expensive software engineer's time. Software engineers like it when they can predict how long a compilation will take. The unknowns are an acceptible risk when intermodule optimisation is turned on, but if I'm being paid by the hour to hack Haskell code, I want a way to turn that off in order to better schedule my day. I digress. My main problem is that under H98, it's not possible, in general, to determine what the public interface of a module actually _is_ without intermodule analysis. This, IMO, breaks pretty much every sensible meaning that you could assign to the term "separate compilation". Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: separate compilation [was Re: Global variables?]
G'day all. On Wed, Feb 05, 2003 at 08:05:56PM -0600, Jon Cast wrote: > I'm not sure I follow this. If you change the type of a value exported > from a given module, that's a public change, no? And if you don't, why > should re-compilation be needed? Consider this: << module A where import B {- use B.b -} >> << module B (b) where import C b = C.c >> << module C (c) where c :: Int >> Changing the type of c requires recompiling module A. You would expect that changing c's type forces a recompilation of B, since you changed C's public interface. However, this also changes B's public interface even though you did not touch the text of module B. The reason is that B's public interface is partly based on modules which it _privately_ imports, even if it does not re-export any symbols from those modules. One fix is to require all exported symbols to have explicit type declarations. Since this is good practice anyway, I would be in favour of making it a language requirement in Haskell 2. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: separate compilation [was Re: Global variables?]
G'day all. I noticed a mistake. On Thu, Feb 06, 2003 at 11:42:21AM +1100, Andrew J Bromage wrote: > Because of type inference over recursive module imports. I meant to say _transitive_ module imports, which includes recursive module imports. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: separate compilation [was Re: Global variables?]
G'day all. On Wed, Feb 05, 2003 at 04:16:33PM -0800, Iavor S. Diatchki wrote: > why do you think separate compilation is difficult to achieve in Haskell > 98? Because of type inference over recursive module imports. Determining the type of a function may, in general, require inferring types from an arbitrary number of other modules, and may require inference to occur at the level of granularity of a clique in the import graph, rather than at the level of a single module. Requiring an implementation to perform static analysis a clique at a time is not "separate compilation", because changing something which is private to one module may in general require an unbounded number of other modules to be recompiled, even if inter-module optimisation is turned off. > as simon pointed out, GHC does it and has been doing it for a long > time. GHC does separate compilation by requiring the programmer to step outside H98, by writing GHC-specific hi-boot files. I agree that GHC therefore supports separate compilation, but, as Fergus pointed out, it does not support separate compilation within H98. > dealing with mutually recusrive modules is i think a separate > issue. Why is it a separate issue? > even though GHC doesn't quite do it, it is certainly possible, > and not very difficult to do. in fact we have it implemented in one of > the projects i am currently working on. hopefully one day GHC will also > dispense with the hi-boot files. I would certainly like to see this, but it doesn't fix the concern noted above, that changing something private to one module may cause an arbitrary number of other modules to be recompiled. That is not "separate compilation" by any definition of the word "separate" that I am aware of. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Global variables?
G'day. On 05-Feb-2003, Simon Peyton-Jones <[EMAIL PROTECTED]> wrote: > > H98 has nothing to say about the separate compilation; it's an issue for > > the implementation. H98 indeed says nothing about separate compilation, and it is indeed an issue for the implementation. What H98 does is it defines a language for which separate compilation is at best extremely difficult and at worst virtually impossible without extra information which is not part of H98 (such as GHC's hi-boot files). On Wed, Feb 05, 2003 at 07:41:52PM +1100, Fergus Henderson wrote: > In other words, GHC doesn't support separate compilation of > Haskell 98 -- it supports separate compilation of a closely related > but distinct language which we can call "Haskell 98 + GHC hi-boot files". Exactly. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Stacking up state transformers
G'day. On Tue, Feb 04, 2003 at 05:24:29PM -, Guest, Simon wrote: > I can still access my backtracked state using Control.Monad.State.{get,put}, but > I can't access my non-backtracked state. Iavor mentioned using "lift", plus some other ideas. That's what I'd do: liftNondet = lift liftOuterState = lift . lift (Naturally I'd call these something more meaningful.) As a matter of style, I generally advocate the philosophy that your basic operations should be semantically meaningful, rather than operationally meaningful. So, for example, rather than: type FooM a = StateT Bar (StateT Baz IO) a munch :: FooM () munch = do baz <- lift (lift get) doStuffWith baz I prefer: type FooM a = StateT Bar (StateT Baz IO) a getBaz :: FooM Baz getBaz = lift (lift get) munch :: FooM () munch = do baz <- getBaz doStuffWith baz Not only is it more readable, it's also more robust in the face of change (e.g. when you decide to change to ReaderT instead). In your case, it's a state monad you're trying to get at, and a state monad only supports a few meaningful operations (get, put, modify, gets) not all of which are generally useful for a given kind of state. I think it makes more sense to specify a "public interface" for your monad and use only that. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Global variables?
G'day all. On Mon, Feb 03, 2003 at 03:24:49PM -0600, Jon Cast wrote: > I, personally, haven't written a program whose bulk will fit in a single > file in several years, and I doubt I ever will again. So, support for > separate compilation is a necessity. How do you intend to handle this? Haskell 98 has never supported separate compilation. That's why we have hi-boot files (or something similar). So, yes, I'd like to know how the language designers intend to support separate compilation in the next version. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Problem with backtracking monad transformer
G'day all. On Fri, Jan 31, 2003 at 09:05:11AM -, Guest, Simon wrote: > This bit I don't understand. I only have one monad transformer, which I use to > transform my SM monad. What I mean is (and recall that I have not looked very hard at your program, just the BACKTR implementation, so I'm not sure what semantics you were really after) you may have meant to stack a state monad transformer on top of BACKTR, rather than the other way. Good luck. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Global variables?
G'day all. On Fri, Jan 31, 2003 at 01:54:26PM -0600, Jon Cast wrote: > Otherwise, though, see my other post on this subject: unsafePerformIO > will perform its action when the variable is accessed, so you can't > write a Haskell program which differentiates between what any compiler > actually does and running the variable allocations before main. As has been pointed out, there is no language requirement for a Haskell implementation to be "fully lazy". In particular, it is technically possible for an implementation to garbage collect globalVar and re-evaluate it on the next call. Haskell 2 should probably have a pragma controlling this. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Global variables?
G'day all. On Fri, Jan 31, 2003 at 09:08:22AM +0100, Ralf Hinze wrote: > John Hughes wrote a nice pearl on the subject, see > > http://www.math.chalmers.se/~rjmh/Globals.ps Nice! Why isn't RefMonad in hslibs? Possibly because of the class signature: class Monad m => RefMonad m r | m -> r where {- etc -} It makes perfect sense for there to be more than one kind of "ref" for a given monad. Indeed, sometimes it's important. Quite often, I use a custom ref built on top of IORef which supports Ord, as this is needed for hash consing. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Problem with backtracking monad transformer
G'day all. On Thu, Jan 30, 2003 at 01:55:50PM -, Guest, Simon wrote: > I'm trying to make a backtracking state monad using Ralf Hinze's > backtracking monad transformer. My problem is that it won't backtrack > very far. > > Suppose I try ( a >> b ) `mplus` c. > > If b fails, it should try c, but it doesn't rewind past a. I added this to your source file: testBACKTR :: (Monad m) => BACKTR m Int testBACKTR = ( return 1 >> M.mzero ) `M.mplus` (return 2) main :: IO () main = putStrLn (show (observe testBACKTR :: Maybe Int)) The result is "Just 2", so I don't think there's anything wrong with your implementation of BACKTR. I've compared it with my own well-tested implementation and it seems identical modulo renamings. In case you want to compare: http://cvs.sourceforge.net/cgi-bin/viewcvs.cgi/hfl/hfl/mtl/ I didn't follow the rest of the code, so I suspect the problem is elsewhere. One place to look is here: > -- backtracking state monad > -- > type NDSM st a = BACKTR (SM st) a You may have meant to stack the monad transformers in a different order. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: comonads, io
G'day all. On Thu, Jan 02, 2003 at 08:08:20PM -0800, Ashley Yakeley wrote: > So is Kieburtz smoking crack, or are we writing OI-style programs > incorrectly? I mailed him the example and asked. (I phrased the question a bit differently, though.) > One possibility is that comonads are useful for some > things, but not for doing IO actions safely. Another possibility is that comonads aren't as suited for "standard" pipes as monads. The problem only happens with an implicit file handle, as you have with getChar. Using hGetChar it's perfectly safe because the Handle is embedded in an OI comonad. Yet another possibility is that we haven't quite gotten the type signatures right on the OI primitives. A third possibility is that everything is okay and we're just missing something very obvious. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Ambiguous defaults
G'day all. On Thu, Jan 02, 2003 at 05:49:41PM +0100, Ferenc Wagner wrote: > What's the way to express the following: a compound object > is generally made up of two components with identical type. This should work: \begin{code} module Test where class Component b where property :: b -> Int class (Component b) => Compound a b | a -> b where decompose :: a -> (b,b) additive :: a -> Int additive x = property l + property r where (l,r) = decompose x \end{code} Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: comonads, io
G'day all. On Wed, Jan 01, 2003 at 01:15:09PM +0100, Nicolas.Oury wrote: > From this, I think the safety become intuitive. Maybe. Using the OI module from Richard Kieburtz' paper, I can write this: -- Bootstrap into the OI comonad main :: IO () main = return $! comain stdOI -- The following are the OI functions which we use. -- stdGetChar :: OI () -> Char -- stdPutStrLn :: OI String -> () comain :: OI a -> () comain w = coeval (w .>> show (a,b) =>> stdPutStrLn) where a = coeval (w .>> () =>> stdGetChar) b = coeval (w .>> () =>> stdGetChar) Even though a and b are identical, they return different values. I see two possibilities: Either my intuition is way off, or the OI comonad breaks referential transparency. It's possible that it's a fault in the implementation. It was clearly intended as an example only, after all. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Error Handling
G'day all. Slight correction... On Mon, Dec 09, 2002 at 12:03:03PM +1100, Andrew J Bromage wrote: > main = runErrorT main' Of course you need to define an error type and do something with the result of runErrorT, but you get the general idea. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Error Handling
G'day all. On Mon, Dec 09, 2002 at 11:35:54AM +1100, Thomas L. Bevan wrote: > main = do (a:b:cs) <- getArgs > i <- return (read a :: Int) > j <- return (read b :: Int) > putStr $ i + j > > How can I catch any possible cast exception? How about this? readM :: (Read a, Monad m) => String -> m a readM s = case readEither s of Left err -> fail err Right x -> return x main = runErrorT main' main' = do (a:b:cs) <- liftIO getArgs (i::Int) <- readM a (j::Int) <- readM b liftIO (putStr $ i + j) Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: AW: Editor Tab Expansion
G'day all. On Fri, Dec 06, 2002 at 05:40:28PM +0100, Ingo Wechsung wrote: > No. It didn't hamper portability with C, Java, Perl or any other *nix stuff > since more than 30 years except with COBOL, Python (?) and Haskell, [...] Add to that: Fortran, Occam and Makefiles. There's probably also a lot of application-specific files (like Makefiles) that others know of. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Editor Tab Expansion
G'day all. Simon wrote: > >There's no reason not to use 8 column tab stops, so please don't do it. On Fri, Dec 06, 2002 at 02:52:13PM +0100, Ingo Wechsung wrote: > Ok, if "it just looks better to me" is no reason, As Simon pointed out, spaces and tabs are visually indistinguishable. 4-column tab stops look no different from multiples of 4-spaces, or a combination of 8-column tab stops and 4 spaces where appropriate. The only thing I can think that you mean by this is that editing code which is already formatted in 8 column indents (i.e. other peoples' code) looks better to you when formatted in 4 column indents. That may be true, but you're breaking their coding standard. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Editor Tab Expansion
G'day all. On Thu, Dec 05, 2002 at 06:36:22PM -0800, Ashley Yakeley wrote: > Haven't we all been through this argument several months ago? I believe > the conclusion was "people have different preferences, and Haskell allows > for that". Sure, but that's a separate issue. My remark was merely in response to the claim that Haskell cares whether you put tabs or spaces in your files. It does not, so long as the tabs are of length 8. If your editor produces tabs of a different size, that's a problem with your editor or the way you dislike Haskell's layout rules. Or, to look at it another way, there are better reasons to dislike Haskell's layout rules than this. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Editor Tab Expansion
G'day all. On Thu, Dec 05, 2002 at 09:49:27PM +0100, Ingo Wechsung wrote: > I am not going to change my editing habits just to make hugs or ghc happy. What editor do you use? If you use a relatively smart one (e.g. vim, emacs etc), you should be able to configure it to do it to do what you want when the extension is .hs or .lhs or whatever. I use vim and I have been known to use the following: set ts=8 set sts=4 " Or sometimes 2 With either expandtab or noexpandtab as the mood takes me. That way, when I hit "tab" I get 2 or 4 spaces, which are expanded to an 8-space tab if I hit it enough times. > Wether spaces or tabs are better in source files is a matter of taste and > a language should not force me to use one or another. The language does not force you to do anything of the sort. It's your editor's fault if it can't decouple the concept of hitting the tab key from the concept of putting a ^I character in your file. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Random Color
G'day all. On Wed, Nov 20, 2002 at 08:44:36PM -0500, Mike T. Machenry wrote: > I am trying to construct an infinate list of pairs of random colors. > I am hung up on getting a random color. I have: > > data Color = Blue | Red | Green deriving (Eq, Ord, Show) > > am I supposed to instantiate a Random class instance from color? You could derive instances of Enum (and possibly also Bounded) and create random elements that way. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: library of monadic functions [was: Why no findM ? simple Cat revisited]
G'day all. On Wed, Nov 20, 2002 at 08:25:46PM +, Jorge Adriano wrote: > I think both versions can be very useful: > findM :: (Monad m) => (a -> m Bool) -> [a] -> m (Maybe a) > findM' :: (Monad m) => (a -> Bool) -> [m a] -> m (Maybe a) I can also make a case for: findM'' :: (Monad m) => (a -> Bool) -> [m a] -> m a findM'' p [] = fail "findM'': not found" findM'' p (x:xs) = p x >>= \b -> if b then return x else findM'' p xs This goes with the philosophy that library functions shouldn't just return Maybe. Somewhere, somehow, there is a most general version of findM to be found. :-) Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Calling Haskell from Python / C++
G'day all. On Thu, Nov 14, 2002 at 05:17:49PM +, Keith Wansbrough wrote: > You might be able to get away with running the Haskell program as a > separate process, communicating via pipes. IMO, this is almost never the right thing to do. Unless your programs are really stream processors, or you want to fork a child, wait for it to finish and use its output, it's almost always better to use a true RPC or distributed object mechanism rather than trying to simulate it over pipes. HaskellDirect for the Win32/COM world has already been mentioned. There's also this, if you're in the Unix/CORBA world: http://haskell-corba.sourceforge.net/ Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
deriving (was Re: storing to a file)
G'day all. On Thu, Nov 14, 2002 at 09:56:24AM -0500, Mark Carroll wrote: > Actually, "deriving binary" would be a nice > thing to have in general - even more, a way to add your own "deriving" > things from within Haskell, although I have no idea how such a thing would > work. Actually, there's one situation where it would work easily, and that is when used with newtype. Apart from "Show" and "Read", which are special cases anyway, the "deriving" operation on newtype has a simple meaning: inherit instances from the type being wrapped. Thoughts? Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Record of STRefs better than STRef to a Record?
G'day all. On Wed, Nov 13, 2002 at 04:05:42AM +, Jorge Adriano wrote: > If I use an STRef to a record, will a new record be created each time I want > to update a single field? Basically, yes. > Right now I'm using a record of STRefs, like: > data E s = E{ > refi :: STRef s Int, > refc :: STRef s Char > } > > but it can get a little messy, since thread s propagates to every datatype > that uses the record type in it's definition. You could always use IORefs, if you don't mind having the IO monad threaded through. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: can't find sequence?
G'day all. On Wed, Oct 30, 2002 at 10:06:48AM +, Ross Paterson wrote: > The library needs updating to account for change in Haskell 98: method > definitions in instance declarations are no longer qualified, Thanks. I'll set to work on that now. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: can't find sequence?
G'day. On Wed, Oct 30, 2002 at 01:49:37PM +1300, Jason Smith wrote: > i.e. TernaryTrie.hs:165: Data constructor not in scope: `M' There is no M in that module anywhere, and I'm pretty sure there never was. Please update your copy from CVS and, if it still isn't working, send a bug report to [EMAIL PROTECTED] Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: can't find sequence?
G'day all. On Wed, Oct 30, 2002 at 12:56:51PM +1300, Jason Smith wrote: > Yes Andrew, I'm using the TernaryTrie that u created.I tired the > suggestion that Alastair gave me regarding the use of -package data but it > still complained saying that it could not find module > Control.Monad.Identity... > > How are u compiling it? Note that I'm using ghc 5.02.2 on windows. Like Hal said, I'm using 5.04. Importing MonadIdentity (using -package lang) will probably work, but you'll have to change it everywhere, unfortunately. If it's at all possible, you should definitely upgrade your version of GHC, particularly if you want to track the CVS tree for HFL. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: can't find sequence?
G'day all. On Tue, Oct 29, 2002 at 11:40:40AM +, Alastair Reid wrote: > > In particular, Hugs is not currently a Supported Platform(tm). > > Please let us know if there's anything in the forthcoming release > that needs changed to support this library. There probably won't be any problems apart from unportable code and/or unportable build systems on my part, but I'll try to give it a go anyway. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Last generator in do {...}
G'day all. On Tue, Oct 29, 2002 at 11:20:47AM +0200, George Kosmidis wrote: > I am sure there are a billion errors in this. > This is the first one: > Line:17 - Last generator in do {...} must be an expression What this means is that the compiler has interpreted the last line of a do expression to be a generator (i.e. pat <- exp), which is bad Haskell. In your case, here is main: > main=do userText<-getText Occasionally, this may be caused by offside errors: main = do foo <- bar return foo ^ offside error, Haskell interprets this as not being part of the do expression Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: can't find sequence?
G'day all. On Mon, Oct 28, 2002 at 08:47:08AM +, Alastair Reid wrote: > (btw There were some remarks that Chris's library might be dropped > from distributions because no-one is supporting it. I don't recall > whether a decision was made on this.) If Jason is using a version of Edison that requires Control.Monad.Identity, it's almost certainly the HFL version, which is indeed supported (by me, mostly). However it is very alpha (especially the interface), so I wouldn't recommend packaging it at the moment. In particular, Hugs is not currently a Supported Platform(tm). Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: dozen
G'day all. On Sat, Oct 26, 2002 at 11:40:04AM -0700, Nuno Silva wrote: > can anyone help me how to get the dozen number? using Int > > example > > dozen 1020 > > the expected result is: 2 dozen :: Int -> Int dozen 1020 = 2 Hope this helps. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: representation getting verbose...
G'day all. On Thu, Oct 17, 2002 at 11:08:57AM -0400, [EMAIL PROTECTED] wrote: > For an > interpreter I'm writing, I found myself writing a function > "constructVarExpr :: String -> Expr" just to make it easier. As an alternative opinion, I don't think there's anything wrong with this. A constructor is just a function, and if you need to do more work than just construct one constructor, there's no reason not to use a real function. In OO design pattern terminology they call this a "factory function", though in Haskell the term "smart constructor" might also apply if the function does real work. Were the wiki working, I would point you to the relevant page there, but it isn't, so I won't. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: infinite (fractional) precision
G'day all. On Thu, Oct 10, 2002 at 11:50:39AM +0200, Jerzy Karczmarczuk wrote: > There are of course more serious approaches: intervals, etc. The infinite- > precision arithmetic is a mature domain, developed by many people. Actually > the Gosper arithmetic of continued fractions is also based on co-recursive > expansion, although I have never seen anybody implementing it using a lazy > language, and a lazy protocol. > > Anybody wants to do it with me? (Serious offers only...) Already did it. It's not pretty, but I'll send you my implementation off-list. One thing I'd like to see is a lazy implementation of linear fractional transformations. The reason I'd like to see this is that it's easier to implement fixpoint-style computations (e.g. transcendental functions) using LFTs than using continued fractions. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: need help optimizing a function
G'day all. On Wed, Oct 09, 2002 at 02:29:26PM -0400, David Roundy wrote: > I get a speedup of about a factor of 6 for the test files I was using (of > course, this would depend on file size), and find that now only 2% of my > time is spent in that function. I'm still something like 100 times slower > than GNU diff, so I think (hope, certainly!) there's still room for more > improvement (another day). I'm sure I'll have more questions in a few > days, once I've tracked down what the new bottlenecks are. If you understand logic languages, you might want to look at the diff implementation which I wrote for the Mercury distribution: http://www.cs.mu.oz.au/research/mercury/ It's pretty close to GNU diff in speed. In fact, it was indistinguishable on every test case I could think of. There are, two main differences to what I could gather from your implementation. First thing was that I noticed that a lot of time was being spent doing string comparisons. I inserted a pre-pass which mapped strings to (unboxed) integers with the constraint that the integers are equal if and only if the strings are equal. This also turned out to be critical for implementing flags such as --ignore-space-change. The other was I used a different algorithm than you did: Eugene W. Myers. "An O(ND) difference algorithm and its variations." Algorithmica, 1:251-266, 1986. I found it to be much faster than the O(n log n) algorithm, even on cases where you would expect it to perform poorly (i.e. where D is large), partly because the constant factors are really, really low and because in the pre-pass you can optimise the case where you have a number of consecutive lines none of which appear anywhere else, which is typical for most uses of diff. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Dealing with configuration data
G'day all. On Fri, Sep 27, 2002 at 12:56:38PM -0400, Dean Herington wrote: > I'm not sure why you consider the code you refer to above so ugly. Anything which relies on unsafePerformIO (or seq, for that matter) is ugly. Personal opinion, of course. :-) > Question: > Why do you use `seq` on `globalTableRef`? Good question. It's actually a form of documentation. I wasn't 100% sure how concurrency and CAFs interact at the time (and I'm still not), so I left that in as a sort of note to myself to check this out. Admittedly a comment would have been clearer. :-) > You use `addToFM` to replace entries in your table. Without additional > logic to increase strictness, I think you unnecessarily risk stack > overflow. That's true, although the case of many writes followed by a single read I would expect to be rare in practice. Besides, IOGlobal is not designed for performance. It's designed for quick hacks. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Dealing with configuration data
G'day all. On Thu, Sep 26, 2002 at 12:06:36AM +0100, Liyang Hu wrote: > The problem I'm having is with the preferences: How do I make it > available throughout the entire program? (FWIW, most of the work is > effectively done inside the IO monad.) I could explicitly pass the > record around everywhere, but that seems a trifle inelegant. > > My current solution is to use a global ('scuse my terminology, I'm not > sure that's the right word to use here) variable of type IORef Config > obtained through unsafePerformIO. It works, but strikes me as a rather > barbaric solution to a seemingly tame enough problem... One solution is to do precisely as you suggested, using a state monad to wrap the IORef. For example: import Control.Monad.Reader import Data.IORef type MyIO a = ReaderT (IORef Config) IO a main = do config <- readConfigurationStuff configref <- newIORef config runReaderT configref main' getConfig :: MyIO Config getConfig = do configref <- ask liftIO (readIORef configref) -- Same as above, but you can supply a projection function. getsConfig :: (Config -> a) -> MyIO a getsConfig f = do config <- getConfig return (f config) -- ...and this is where the code REALLY starts. main' :: MyIO () main' = do config <- getConfig liftIO (putStrLn (show config)) -- etc You can wrap whole slabs of existing code in liftIO if it uses IO but does not need to read the configuration. There's also a much uglier solution which I occasionally use if I need an "ad hoc" global variable. Rather than using IORefs, I use Strings as keys. The code is here: http://cvs.sourceforge.net/cgi-bin/viewcvs.cgi/hfl/hfl/ioext/ Example of use: import IOGlobal main :: IO () main = do writeIOGlobalM "foo" "Foo data" writeIOGlobalM "bar" ("Bar", ["data"]) foo <- readIOGlobalM "foo" putStrLn foo bar <- readIOGlobalM "bar" putStrLn (show (bar :: (String, [String]))) Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Monad Maybe?
G'day all. On Sat, Sep 21, 2002 at 12:56:13PM -0700, Russell O'Connor wrote: > case (number g) of > Just n -> Just (show n) > Nothing -> > case (fraction g) of >Just n -> Just (show n) >Nothing -> > case (nimber g) of > Just n -> Just ("*"++(show n)) > Nothing -> Nothing This isn't exactly the most beautiful way of doing it, but... (number g >>= return . show) `mplus` (fraction g >>= return . show) `mplus` (nimber g >>= return . ('*':) . show) Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Question about use of | in a class declaration
G'day all. On Wed, Aug 21, 2002 at 02:31:05PM +0100, Guest, Simon wrote: > Please could someone explain the meaning of | in this class > declaration (from Andrew's example): > > class (Ord k) => Map m k v | m -> k v where > lookupM :: m -> k -> Maybe v Others have answered the question about what it means. However, this doesn't explain why I used a fundep when Haskell has perfectly good constructor classes. I could have written: class (Ord k) => Map m k v where lookupM :: m k v -> k -> Maybe v instance (Ord k) => Map FiniteMap k v where lookupM = lookupFM However, this would not work for the other two cases (the assoc list and the function). For that, I'd have to introduce a new type, such as: newtype MapFunc k v = MapFunc (k -> Maybe v) instance (Ord k) => Map MapFunc k v where lookupM (MapFunc f) = f A good Haskell compiler would optimise the representation of the type, so it wouldn't cost much (or possibly _anything_) at run time, but it's still a pain to program with. You need to pack and unpack the MapFunc type at awkward places, when all you really want to do is rearrange type variables for one declaration. Fundeps let you avoid many of these "artificial" constructors. Unfortunately, I don't think that fundeps will help you to get rid of all of them. For example, the standard state transformer monad: newtype State s a = State { runState :: s -> (a, s) } I don't think you can get rid of the constructor here. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Question about use of | in a class declaration
G'day all. On Wed, Aug 21, 2002 at 02:46:16PM -0400, Mark Carroll wrote: > One issue we have here is that any Haskell we write is stuff we'll > probably want to keep using for a while so, although we've only just got > most of the bugs out of the H98 report, I'll certainly watch with interest > as people come to a consensus about multi-parameter typeclasses, > concurrency libraries, etc. and such things start to look very much like > they'll be fixed in the next round of standardisation. It's hard to know > which are experiments that ultimately will be shunned in favour of > something else, and which are just all-round good ideas. (-: Apart from the mailing lists, there are two forums which are sort of used for this. One is the wiki: http://haskell.org/wiki/wiki?HaskellTwo ...which, as those of us who use it regularly know, is down at the moment. The other is the Haskell Wish List: http://www.pms.informatik.uni-muenchen.de/forschung/haskell-wish-list/ ...which has also been down for some time. Clearly whichever malevolent forces are responsible for downtime don't want Haskell to evolve. :-) Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Question about sets
G'day all. On Tue, Aug 20, 2002 at 10:57:36AM -0700, Hal Daume III wrote: > Lists with arbitrary > elements are possible, but not very useful. After all, what could you do > with them? It's often useful to have containers of arbitrary _constrained_ types, because then you can do something with them. For example, given the class of partial mappings on orderable keys: class (Ord k) => Map m k v | m -> k v where lookupM :: m -> k -> Maybe v instance (Ord k) => Map (FiniteMap k v) k v where lookupM = lookupFM instance (Ord k) => Map [(k,v)] k v where lookupM m k = case [ v | (k',v) <- m, k == k' ] of []-> Nothing (v:_) -> Just v instance (Ord k) => Map (k -> Maybe v) k v where lookupM = id You can make a list of elements, which can be any type so long as they are a member of that class: data MAP k v = forall m. (Map m k v) => MAP m type ListOfMap k v = [MAP k v] Then you can do things with it: lookupLom :: (Ord k) => ListOfMap k v -> k -> [ Maybe v ] lookupLom xs k = [ lookupM a k | MAP a <- xs ] test :: [Maybe Int] test = lookupLom maps 1 where maps = [ MAP finiteMap, MAP assocListMap, MAP functionMap ] finiteMap = listToFM [(1,2)] assocListMap = [(1,3)] functionMap = \k -> if k == 1 then Just 4 else Nothing It's a little unfortunate that you have to introduce the MAP type here. You can in fact construct a list of this type: type ListOfMap k v = [ forall m. (Map m k v) => m ] But then you can't use the elements in the list because the Haskell type checker can't find the (Map m k v) constraint. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Question about sets
G'day all. On Tue, Aug 20, 2002 at 05:39:41AM +0200, Scott J. wrote: > I have a question. Why are sets not implemented in Haskell? . I have read a > bit how the compiler is made. Ok lists are easier to implement but sets > could have been implemented too. > So why didn't the implementors not do it? Almost certainly because the most efficient implementation of sets depends on data type and usage. For many applications, binary trees may be the most appropriate method. For others, hash tables might be better. For others, dense bit vectors and for yet others, sorted lists. Of course Haskell could have defined signatures and some implementations and left any specialist implementations up to the developer, however, the "most correct" type signatures require fundeps, which are not in Haskell 98. Incidentally, if someone wants an interesting project, Edison hasn't been touched in a while. Getting it a) fundep-compliant, b) complete and c) playing with the Monad Template Library would be a pretty useful thing. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Haskell wiki problems
G'day all. On Mon, Aug 12, 2002 at 04:19:38AM -0700, John Meacham wrote: > grr. this used to be in a FAQ at the Wiki. whatever happened to that? Unfortunately, the ReportingProblems page is one of the ones which died. It's also not in the google cache. Does anyone know who's responsible for the wiki? Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Newbie question on "statefullness"
G'day all. On Mon, Aug 12, 2002 at 10:06:51PM +0100, Alistair Bayley wrote: > OTOH, if you want to do anything useful with any language you have to learn > to do IO (and simple IO is tackled early in most languages), and therefore > you must deal with Monads. I often wish that Haskell books and tutorials > would introduce IO earlier; it is often near the end, in the "advanced" > topics (after you've been dazzled/saturated by the magic you can do with list > functions and comprehensions, and how easy it is to create abstract > datatypes, and write parsers, etc...). Being fair for a moment, most Haskell books are intended as undergraduate computer science textbooks. There are many purposes of these introductory courses, but learning a particular programming language is not one of them. You can teach a lot of computer science without getting bogged down in the details of doing IO. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Newbie question on "statefullness"
G'day all. On Sun, Aug 11, 2002 at 05:36:21PM -0700, Alex Peake wrote: > I am new to Haskell. I want to do something very simple (I thought) > but got lost in the world of Monads. > > I want to implement something like the C idea of: > n += i > > So how does one doe this in Haskell? I think this needs to be an FAQ. The short answer is that if you find yourself needing to do this, especially if you're new to Haskell, you're probably thinking about the problem in the wrong way. Haskell does not support the "n += i" idiom in the same way that C does not support, say, higher-order functions. The flip side is that Haskell _does_ support the "n += i" idiom in the same way that C _does_ support higher-order functions, in that with some effort (sometimes a little, sometimes a lot) you can simulate the same functionality if you find you really need it (using monads, continuations or whatever). However, most of the time where you would use this idiom in C, you would not use it in the equivalent Haskell program, simply because there's usually a more appropriate way of phrasing your intentions. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Newbie question on "statefullness"
G'day all. On Sun, Aug 11, 2002 at 07:03:04PM -0700, Alex Peake wrote: > I am trying to implement a long-lived "accumulator" How long is long? Over what kind of code must it be preserved? In what kind of code do you want to modify it and in what kind of code do you want to read it? By "what kind", I mean things like: - Is it just needed at the "top level" of your program? - Do you need I/O (or some other monadic construction) in the same places as this accumulator or is it in different places? - What other "state" do you have? How cleanly does it separate from the rest of your code? - Is there some identifiable part of your program where the "state" is "read only", some where it is "write only" and/or some where it is "read/write"? These are important considerations. C has no automatic memory management, so you must (usually) structure your code around the lifetimes of your data. Similarly, Haskell has no automatic state, so you must (usually) structure your code around the scope of the state that you intend to simulate. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Combining type constraints
G'day all. I have a large number of functions all of which use the same set of type constraints, such as: > foo :: (Monad m, Ord t, Show t) => ... Ideally, I'd like to combine them into one typeclass. At the moment, I'm using the equivalent of: > class (Monad m, Ord t, Show t) => Constraints m t where { } > instance (Monad m, Ord t, Show t) => Constraints m t where { } > foo :: (Constraints m t) => ... This requires undecidable instances. Is there a way to do this that doesn't require non-98 features apart from multi-parameter type classes? If not, is there an argument for a language construction which supports this idiom, analogous to type synonyms, except for type classes? Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: can a lazy language give fast code?
G'day all. On Wed, Jul 31, 2002 at 09:59:31AM +0100, D. Tweed wrote: > It's in saying this is warranted by `almost all' > processes being bound by things other than throughput which may be true in > the average sense, but I don't think that all programmers have almost all > their programming tasks being dominated by something other than raw > throughput but rather there are sets of programmers who have all of the > tasks being dominated by the need something else (robustness, say) and > some who have all their tasks being dominated by the need for raw > throughput. Fair enough. I was speaking in generalities and average cases and deliberately avoiding the special needs of many programmers and applications. I've worked in enterprise applications, web applications and high-performance servers (both CPU-bound and I/O-bound) and the concerns of all of them are different. Perhaps if I cut down on the superlatives I can say something that everyone agrees with: An awful lot of new code today is written in languages like Visual Basic and Java, despite their relative unsuitability for high "throughput". If it doesn't stop the use of those kinds of languages, it shouldn't stop the use of Haskell either, especially since Haskell arguably scales much better. Therefore were I someone with a stake in the future of Haskell, I would not be not overly concerned about these kinds of benchmarks. Speed is important, and it should be worked on, but it's not as important as the things which Haskell already does better. > You make very good points in what I've snipped below, again it's just > the use of `most' in a way that implies (to me) taking an average as > the representative of what everyone has to deal with that I `disagree > with'. Sure. I wasn't implying that it was representative of what everyone has to deal with. It's certainly not representative of what I do for a living, though it's pretty close to something I used to do. Perhaps the quibble is over the word "average". While I don't think I used that word, if I did, I'd mean "mode" rather than "mean". :-) Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: can a lazy language give fast code?
G'day all. On Tue, Jul 30, 2002 at 01:57:58PM +0200, Josef Svenningsson wrote: > I think the reason why Haskell compilers aren't generating any faster code > is that there is a lack of competition among different compilers. And I > think that the lack of competition depends on that noone wants to write a > front-end to Haskell. There's no competition in Haskell compilers because there is no money in it. It might not even be "boring work" in most cases. The reality is that if there's no research quota or postgraduate degree to be gained, nobody will fund a university or other research institution to actually do the work. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: can a lazy language give fast code?
G'day all. On Tue, Jul 30, 2002 at 08:14:27AM +0100, D. Tweed wrote: > Mmm, such statements really assume that there's a sensible meaning to > `almost always' when applied to the set of all programmers, whereas I > think a much more realistic assumption is that `there's lots of people out > there, all with different priorities' and present things in way which > lets people perform their own evaluations. Let me clarify what I meant by that and see if you still disagree. Realistically, _most_ new software installations today (I deliberately ignore legacy systems etc) are not overloaded, in that there are more "computrons" available than are required to perform the task required of them. Of course this is partly because when you do a new installation, you add more than you need because you expect to grow. Secondly, most non-embedded CPUs in the world are not overloaded either. Chances are for a given desktop machine, it spends most of its waking hours waiting for the next keystroke or mouse movement. Web developers in particular know this: For the typical case, your application server runs at the speed of the network. If you agree with me so far, it follows that for most _new_ software, "throughput" is not as great a consideration as other performance metrics, because "throughput" measures the saturation point of your system, and most new systems don't get saturated. Of course I'm speaking in generalities, and there are an awful lot of situations where throughput is an issue. I've worked in a few of those situations before. I'm working in that situation right now, in fact. Throughput measures are important to have if this is the situation that you're in. More information is good. Perhaps the problem is I don't trust everyone to use the information wisely? > The problem with language > benchmarks is not that they `over-rate' the importance of performance but > that they assume per se that choice of language is a single-variable > (execution speed) optimization problem; there's no attempt to measure the > other items in your list, most especially flexibility. While I agree with you here, I don't even claim that language benchmarks of this kind "over-rate" the value of performance. I claim that they don't measure "performance" _at_all_! They measure (in this case) two possible measures of performance, namely memory usage and execution speed, but ignores factors like scalability and latency, which are IMO often more important. > Of more > concern to me is, when's the last time you actually got a well specified > computational problem and a reasonable amount of time to write a carefully > crafted program to solve it, (particularly when you had some reassurance > that the very specification of what to solve wouldn't change after the > first time you ran the code :-) )? Perhaps the ICFP contests are actually fairer as benchmarks than as competitions? Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: can a lazy language give fast code?
G'day all. On Mon, Jul 29, 2002 at 10:23:05AM +0100, Simon Marlow wrote: > Many of those programs can be written differently to improve > performance. To be fair, Doug admits this as well as a lot more: http://www.bagley.org/~doug/shootout/method.shtml#flaws Despite these flaws, I did notice that ghc is right in the middle in his CRAPS score system (which is really interesting; all due respect to the GHC guys, but I expected it to be lower ). I also noticed that the majority of cases where Haskell does significantly worse than average are "same way" tests, designed to test the performance of various constructs (e.g. array access, dictionary lookup) as opposed to "same thing" tests, designed to test native idioms. In the end, though, benchmarks ignore one of the most important rules of software performance: "throughput" (i.e. the amount of processing that your system can do just prior to being overloaded) is almost never the most important consideration. Other considerations such as flexibility, robustness, responsiveness and scalability are almost always more important. I've thought for a while that what we need is more benchmarks like pseudoknot: Real tasks which real people want to do. Computing Ackermann's function is all well and good, but when's the last time you actually needed to compute it in a real program? Off the top of my head, some "real" tasks which could be benchmarked include: - MPEG video compression. - Code scheduling/register allocation for a CPU like the MIPS/Alpha or even the IA64. - Fluid simulation. - Solving chess problems. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: converting capital letters into small letters
G'day all. On Fri, Jul 26, 2002 at 01:27:48AM +, Karen Y wrote: > 1. How would I convert capital letters into small letters? > 2. How would I remove vowels from a string? As you've probably found out, these are very hard problems. Haskell gets it a little wrong here, since the result of some of the UnicodePrims functions (see chapter 9, Haskell 98 library report) should really be locale-dependent and therefore _impure_ if you allow changes of locale. Of course, Haskell currently only supports time and data locale information, so this wouldn't help you anyway. Glossing over that concern, current implementations don't support the relevant UnicodePrims fully, so to do it properly you'll probably need to parse the case folding files yourself. See: http://www.unicode.org/unicode/reports/tr21/ Vowels are even harder because I don't think the Unicode standard even defines what a "vowel" is. Removing vowel _marks_ should be straightforward once you expand combining characters, but that doesn't help with the general case. Frankly, I don't like your chances. Can anyone else think up a good solution? Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: LRparsing combinators
G'day all. On Fri, Jul 05, 2002 at 11:04:01AM -0700, andy wrote: > Has anyone seen or have a reference to LR based > parsing combinators? Sorry, I just came by this message. I looked into them some time ago and, basically, they're not a good fit since they don't decompose bottom-up like LL parsers. The best you can apparently do is build a data structure representing the grammar then compile it at run time. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Writing a counter function
G'day all. On Sun, Jun 30, 2002 at 01:51:56PM +0100, Peter G. Hancock wrote: > Why not have a monad m a = Int -> (a,Int) which is a state monad plus > the operation bump : Int -> m Int > > bump k n = (n,n+k) Oh, ye of insufficient genericity. We can do better than that... import MonadTrans class (Monad m, Enum i) => MonadCounter i m | m -> i where bump :: Int -> m i newtype CounterT i m a = CounterT { runCounterT :: i -> m (a,i) } instance (Monad m, Enum i) => Monad (CounterT i m) where return a = CounterT $ \x -> return (a, x) m >>= k = CounterT $ \x -> do (a, x') <- runCounterT m x runCounterT (k a) x' fail str = CounterT $ \_ -> fail str instance (Monad m, Enum i) => MonadCounter i (CounterT i m) where bump k = CounterT $ \x -> let (next:_) = drop k [x..] in return (x, next) instance (Enum i) => MonadTrans (CounterT i) where lift m = CounterT $ \x -> do a <- m return (a, x) evalCounterT :: (Monad m, Enum i) => CounterT i m a -> i -> m a evalCounterT m x = do (a, _) <- runCounterT m x return a -- Example code follows main :: IO () main = evalCounterT count 0 count :: CounterT Int IO () count = do x1 <- bump 1 x2 <- bump 5 x3 <- bump 0 x4 <- bump 1 lift (putStrLn $ show [x1,x2,x3,x4]) I'd better get back to work now. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Writing a counter function
G'day all. On Sat, Jun 29, 2002 at 05:26:46PM -0500, Mark Carroll wrote: > Do any of the experimental extensions to Haskell allow a what-he-wanted > solution? I couldn't arrange one in H98 without something having an > infinitely-recursive type signature. I'm sure it would have been easy in > Lisp, and he already gave a Perl equivalent, so I'm wondering if it could > be at all sane for Haskell to allow such stuff and if Haskell is somehow > keeping us on the straight and narrow by disallowing the exact counter > that was originally requested. In principle it's perfectly possible to have a type system which works over regular trees. The main difficulty is how to actually express a type. You'd need something like letrec for types. typedef Counter = letrec x = Int -> (Int, x) in x It makes a few type-related things more inefficient, but it need not impose a huge cost in places where it's not used. It's fairly straightforward to optimise non-recursive types to the way they are handled at the moment at the cost of a more complex compiler. At least that's the story before you add all the other features of Haskell's type system. I'm not sure, for example, how it would interact with overlapping typeclass instances. This is the central problem with extensions to the type system: how well or badly it combines with all the other extensions that have been added over the years. In this case, I really don't see that you would get much in the way of extra expressiveness. Breaking recursion is as simple as introducing a newtype. Moreover, it's arguably "the Haskell way" just to introduce a new type whenever you need one, because it's so cheap to do. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: type equivalency
G'day all. On Wed, Jun 05, 2002 at 10:35:52PM -0500, Jon Cast wrote: > > One general rule of strongly-typed programming is: A program is type > > correct if it is accepted by my favourite type checker. A corollary > > is that what you call a type, I reserve the right to call a > > precondition. > > If I accepted that, I would be un-defining crucial terms. That would > destroy the potential for discussion here, no? I think you might have missed the sarcasm. :-) Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: type equivalency
G'day all. On Wed, Jun 05, 2002 at 08:20:03PM -0500, Jon Cast wrote: > I think you're confused about what the type declarations mean. When > you say > > > sqrt :: Float -> Float > > you're promising to operate over /all/ Floats. That would be true of Haskell functions were constrained to be total functions. They are not. Sqrt takes values of type Float, but it just happens to be a partial function over that type. > Unfortunately, Haskell > doesn't allow {x :: Float | x >= 0} as a type, nor does it provide a > positive-only floating point type. One general rule of strongly-typed programming is: A program is type correct if it is accepted by my favourite type checker. A corollary is that what you call a type, I reserve the right to call a precondition. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe