Re: [Haskell-cafe] Help understanding type error

2007-09-06 Thread Stuart Cook
because f is required to accept *any* Show instance as an argument type, and so is happy to work for whatever particular type b happens to inhabit. Stuart Cook ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo

Re: [Haskell-cafe] Help understanding type error

2007-09-07 Thread Stuart Cook
On 9/8/07, Ryan Ingram [EMAIL PROTECTED] wrote: This does what you want, I think: {-# LANGUAGE ExistentialQuantification #-} module Exist where data Showable = forall a. (Show a) = Showable a instance Show Showable where showsPrec p (Showable a) = showsPrec p a show (Showable a) =

[Haskell-cafe] ((a - b) - c) - (a - m b) - m c

2007-09-08 Thread Stuart Cook
suspect that even in a strict language, lambda-abstractions would cause similar trouble. [1] http://programming.reddit.com/info/2n6eh/comments Stuart Cook ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell-cafe] ((a - b) - c) - (a - m b) - m c

2007-09-09 Thread Stuart Cook
On 9/9/07, Henning Thielemann [EMAIL PROTECTED] wrote: If the signature would be (Monad m) = ((a - b) - c) - m (a - b) - m c it would be possible, and the implementation would be 'liftM'/'fmap'. Thanks, that's the kind of insight I was looking for. Hmm. A key distinction between (a - m

Re: [Haskell-cafe] Comments and/or Criticisms

2007-09-09 Thread Stuart Cook
On 9/10/07, PR Stanley [EMAIL PROTECTED] wrote: Can anyone come up with a better alternative? *puts on his pointfree hat* import Control.Arrow (()) import Data.List (group, sort) countCS :: [Char] - [(Char, Int)] -- Char can be generalised to any Ord countCS = map (head length) .

Re: [Haskell-cafe] Comments and/or Criticisms

2007-09-09 Thread Stuart Cook
On 9/10/07, PR Stanley [EMAIL PROTECTED] wrote: Hi Any comments and/or criticisms would be most appreciated: --count the occurrences of char in string countC :: Char - [Char] - Int countC x xs = sum [1 | c - xs, c == x] That's a clever implementation, but I think there are clearer ways of

Re: [Haskell-cafe] MonadGL - Partitioning effects without giving up type inference

2007-09-13 Thread Stuart Cook
On 9/14/07, Jules Bean [EMAIL PROTECTED] wrote: {-# OPTIONS -fglasgow-exts #-} (extensions are only for deriving (Monad), it's not important) If that's the case, you should be able to write (assuming GHC 6.6+) {-# LANGUAGE GeneralizedNewtypeDeriving #-} though I don't know how well other

Re: [Haskell-cafe] How can I stop GHCi from calling show for IO actions?

2007-09-16 Thread Stuart Cook
On 9/16/07, Ryan Ingram [EMAIL PROTECTED] wrote: Is there a way to make GHCi not print the result of an action but still make my variables get bound? This seems to be a common question (I myself asked it recently), so I've added an entry to the GHCi page on the wiki.

Re: [Haskell-cafe] How can I stop GHCi from calling show for IO actions?

2007-09-17 Thread Stuart Cook
On 9/17/07, Martin Lütke [EMAIL PROTECTED] wrote: What is the url for the wiki entry? There was already a page at http://haskell.org/haskellwiki/GHC/GHCi so I put it there, but I also took the liberty of creating some #REDIRECTs, so http://haskell.org/haskellwiki/ghci should work just

Re: [Haskell-cafe] are some of these reverse algos better than others? is there a quick and dirty way to reveal this fact?

2007-09-22 Thread Stuart Cook
On 9/23/07, Thomas Hartman [EMAIL PROTECTED] wrote: -- this is the usual implementation right? myreverse xs = foldl f [] xs where f accum el = el : accum This is often written reverse = foldl (flip (:)) [] which I quite like, because you can contrast it with foldr (:) [] which of

Re: [Haskell-cafe] Curry and uncurry

2007-10-03 Thread Stuart Cook
On 10/3/07, PR Stanley [EMAIL PROTECTED] wrote: Without looking at the standard prelude, define the higher-order library function curry that converts a function on pairs into a curried function, and conversely, the function uncurry that converts a

Re: [Haskell-cafe] Re: Function composition

2007-10-04 Thread Stuart Cook
On 10/4/07, Dominic Steinitz [EMAIL PROTECTED] wrote: Look at the type of (.).(.).(.) Indeed, this generalizes to functions of any arity on the RHS: Prelude :t (.) (.) :: (b - c) - (a - b) - a - c Prelude :t (.).(.) (.).(.) :: (b - c) - (a - a1 - b) - a - a1 - c Prelude :t

Re: [Haskell-cafe] Puzzled

2007-10-06 Thread Stuart Cook
On 10/6/07, Bertram Felgenhauer [EMAIL PROTECTED] wrote: This is a language extension, you need -fbang-patterns to allow it, or with a recent ghc (6.7, 6.9 or a 6.8 rc) a {-# LANGUAGE BangPatterns #-} pragma, or -XBangPatterns. LANGUAGE pragmas (including BangPatterns) work just fine in 6.6,

Re: [Haskell-cafe] RE: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Stuart Cook
On 10/16/07, Bayley, Alistair [EMAIL PROTECTED] wrote: Just a minor point, but would mind explaining exactly what lexicographic ordering implies? It appears to me that e.g. version 9.3 of a package would be preferred over version 10.0. That strikes me as counter-intuitive. I believe the

Re: [Haskell-cafe] Strange subtract operator behavior - and lazy naturals

2007-10-17 Thread Stuart Cook
On 10/17/07, John Meacham [EMAIL PROTECTED] wrote: if anyone is interested, Although I bet this has been implemented a hundred times over, I have attached my lazy naturals module below just for larks. It is quite efficient as such things go and very lazy. for instance (genericLength xs 5)

Re: [Haskell-cafe] Suspected stupid Haskell Question

2007-10-17 Thread Stuart Cook
On 10/17/07, Peter Verswyvelen [EMAIL PROTECTED] wrote: So in that case, the result should be a list of ordered pairs like: [(egg, 2), (cheese, 1)]. Or a pair of two lists, like ([egg, cheese), (2,1)]. Otherwise you would not know which frequency belongs to which element? However, I suspect

Re: [Haskell-cafe] Class invariants/laws

2007-10-18 Thread Stuart Cook
On 10/18/07, Simon Peyton-Jones [EMAIL PROTECTED] wrote: I don't believe GHC relies on any class laws. It'd be pretty dangerous to do so, I think. Incidentally, I consider it a slight infelicity that the H98 spec doesn't seem to mention the implied laws of classes like Eq and Ord, not even to

Re: [Haskell-cafe] using an external application

2007-11-02 Thread Stuart Cook
On 11/2/07, Petr Hoffmann [EMAIL PROTECTED] wrote: import System.Cmd main = do System.Cmd.system echo hello output.txt -- use the external application to create an output file o1 - readFile output.txt System.Cmd.system echo bye output.txt -- the second call to

Re: [Haskell-cafe] using an external application

2007-11-02 Thread Stuart Cook
On 11/2/07, Andrew Butterfield [EMAIL PROTECTED] wrote: I'm puzzled - when I run this on GHCi (v6.4, Windows XP) I get the following outcome *Mainmain The process cannot access the file because it is being used by another process. hello *Main Under GHCi 6.6 I get this: *Main main bye

Re: [Haskell-cafe] generating Maybe

2007-11-07 Thread Stuart Cook
On 11/8/07, Tim Newsham [EMAIL PROTECTED] wrote: Data.Maybe has functions for processing Maybe's but nothing useful for creating maybe. I think the following would be a very useful addition, a guarded function: guarded :: (a - Bool) - (a - b) - a - Maybe b guarded p f x | p x

Re: [Haskell-cafe] About Fibonacci again...

2007-11-07 Thread Stuart Cook
On 11/8/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote: Would somebody try to solve it, before I unveil the solution? It isn't difficult. *** SPOILER WARNING *** Here's my attempt, which I wrote without peeking: let fibs' = 1 : 2 : zipWith (+) fibs' (tail fibs') rabbits = 1 : 0 :

Re: [Haskell-cafe] About Fibonacci again...

2007-11-08 Thread Stuart Cook
On 11/8/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote: I have a vague impression that the solution of Alfonso Acosta: rs_aa = let acum a1 a2 = a2 ++ acum (a1++a2) a1 in 1 : acum [1] [0] is also somehow related to this limit stuff, although it is simpler, and formulated differently. I

Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-17 Thread Stuart Cook
On Dec 17, 2007 10:47 PM, Nicholls, Mark [EMAIL PROTECTED] wrote: The constructor of a newtype must have exactly one field but `R' has two In the newtype declaration for `Rectangle' It doesn't like newtype Rectangle = R Int Int A newtype can only have one constructor, with one argument,

Re: [Haskell-cafe] Is StateT what I need?

2007-12-19 Thread Stuart Cook
On Dec 19, 2007 11:28 AM, Andre Nathan [EMAIL PROTECTED] wrote: I guess I could do away with StateT and just pass the PsMap around as a parameter, but I guess that wouldn't be the haskell way... I wouldn't say that. Manual state-passing is a perfectly legitimate technique, and can be clearer in

Re: [Haskell-cafe] Specializing classes with classes

2007-12-30 Thread Stuart Cook
On Dec 30, 2007 2:43 PM, Jake McArthur [EMAIL PROTECTED] wrote: Really? This code doesn't even really make any sense to me. In order to be an instance of Bar, t has to already be an instance of Foo, implying that the function hi is already defined for t. What would the function in this example

Re: [Haskell-cafe] Field updates in a state monad

2008-01-10 Thread Stuart Cook
On Jan 11, 2008 2:01 AM, Michael Roth [EMAIL PROTECTED] wrote: Hello list, Exists there a way to write this cleaner without writing countless set_xyz helper functions? The set_xyz methods have to be written, but that doesn't mean *you* have to write them. You can use Template Haskell to

Re: [Haskell-cafe] Filter by several predicates at once

2008-01-17 Thread Stuart Cook
On Jan 18, 2008 1:46 AM, Isaac Dupree [EMAIL PROTECTED] wrote: Neil Mitchell wrote: Hi passall, passany :: [a - Bool] - a - Bool passall ps v = and $ map ($v) ps passany ps v = or $ map ($v) ps or something similar defined anywhere? Such that one can write nearly; using Prelude:

[Haskell-cafe] ANN: bimap 0.1 - a bidirectional map

2008-02-03 Thread Stuart Cook
://code.haskell.org/~scook0/haddock/bimap/ Darcs: darcs get http://code.haskell.org/bimap Stuart Cook ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] ANN: bimap 0.1 - a bidirectional map

2008-02-04 Thread Stuart Cook
On Mon, Feb 4, 2008 at 7:56 PM, Neil Mitchell [EMAIL PROTECTED] wrote: A few design differences from your one: * I called my module BiMap rather than Bimap - I debated this with a collegue, and we settled on the capital M, but it was a very close call. Mine was also originally BiMap, but

[Haskell-cafe] bimap 0.2

2008-02-04 Thread Stuart Cook
I've updated the bimap package to version 0.2. http://hackage.haskell.org/cgi-bin/hackage-scripts/package/bimap-0.2 The main difference is a pretty comprehensive interface shakeup: the Either variants have been dropped, all L variants have had the L removed from their name, and a few functions

Re: [Haskell-cafe] bimap 0.2

2008-02-05 Thread Stuart Cook
On Tue, Feb 5, 2008 at 9:11 PM, Neil Mitchell [EMAIL PROTECTED] wrote: Hi The main difference is a pretty comprehensive interface shakeup: the Either variants have been dropped, all L variants have had the L removed from their name, and a few functions have been curried. The end

[Haskell-cafe] Re: bimap 0.2

2008-02-05 Thread Stuart Cook
On Tue, Feb 5, 2008 at 11:33 PM, Christian Maeder [EMAIL PROTECTED] wrote: Neil Mitchell wrote: Yes, an MTL dependency is nothing to worry about at all, and isn't worth even thinking about removing given its actually used. I would appreciate haskell98 portability! My development version

[Haskell-cafe] Re: bimap 0.2

2008-02-05 Thread Stuart Cook
On Wed, Feb 6, 2008 at 11:43 AM, Stuart Cook [EMAIL PROTECTED] wrote: My development version has removed the need for Control.Monad.Exception and Control.Arrow. The only remaining H98 incompatibility I can think of is the use of foldl' in fromList. Version 0.2.1 features: * almost-H98

[Haskell-cafe] Re: Create a list without duplicates from a list with duplicates

2008-02-09 Thread Stuart Cook
On Sun, Feb 10, 2008 at 12:19 AM, ChrisK [EMAIL PROTECTED] wrote: For Bimap is there anything like Data.Map.insertWithKey ? No. I wanted to implement the insertWith family, but it wasn't clear to me what should happen if the value produced by the user's function already exists, bound to

[Haskell-cafe] ANN: unix-pty-light 0.1

2008-02-13 Thread Stuart Cook
-0.1 Darcs: http://code.haskell.org/~scook0/unix-pty-light/ Haddock: http://code.haskell.org/~scook0/haddock/unix-pty-light/ Stuart Cook ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] naming a data structure for weighted random selection without replacement

2008-02-17 Thread Stuart Cook
A while ago I wrote a little data structure that allows weighted random selection-without-replacement from a collection of values in O(log n) time.[1] I'm now in the process of packaging it up for Hackage, but I'm looking for good names for both the type and its operations. The name I have at the

Re: [Haskell-cafe] naming a data structure for weighted random selection without replacement

2008-02-18 Thread Stuart Cook
On Tue, Feb 19, 2008 at 1:27 PM, Isaac Dupree [EMAIL PROTECTED] wrote: the without replacement thing is more specific. Although maybe the design could accomodate selection-with-replacement in the same package too Once you have without-replacement, with-replacement is easy: just re-use the old

Re: [Haskell-cafe] Trouble with numbers

2008-02-29 Thread Stuart Cook
On Fri, Feb 29, 2008 at 7:09 PM, Lloyd Smith [EMAIL PROTECTED] wrote: I mixed up my types when finding the allocated and unallocated, but I am not sure why it produces an error when unallocated and allocated are never used? Shouldn't the two functions be compiled down to the same thing?

Re: [Haskell-cafe] testing for same characters in lists of strings

2008-04-07 Thread Stuart Cook
On Tue, Apr 8, 2008 at 1:51 PM, Jackm139 [EMAIL PROTECTED] wrote: I have an assignment to make a program to test whether two lists use the same characters for each string. e.g. sameCharacter [rock, cab] [cork, abc] True I would start with something smaller: try defining a function that

Re: [Haskell-cafe] functional update

2008-04-21 Thread Stuart Cook
On Tue, Apr 22, 2008 at 4:12 AM, Evan Laforge [EMAIL PROTECTED] wrote: Has there been any work on improving update syntax in haskell? Possibly some improvement could be made with a typeclass or two and a few custom operators, to unify some of the disparate syntax. Maybe more improvement

Re: [Haskell-cafe] n00b circular dep question

2008-04-26 Thread Stuart Cook
On Sat, Apr 26, 2008 at 4:07 AM, Bulat Ziganshin [EMAIL PROTECTED] wrote: 2. ghc supports this part of standard in a rather awkward way - you need to generate .hs-boot files using some switch (look into docs). which is like .h files generated automatic from .cpp. once these files

Re: [Haskell-cafe] problems with derive/TH

2008-05-23 Thread Stuart Cook
On Sat, May 24, 2008 at 1:11 AM, Thomas Hartman [EMAIL PROTECTED] wrote: World.hs:42:0: No instances for (Eq (a (M.Map String Player)), Eq (a (M.Map ItemId Item)), Eq (a (M.Map PlayerId Player)), Eq (a (M.Map RoomId Room)),

Re: [Haskell-cafe] Alternatives to convoluted record syntax

2008-07-03 Thread Stuart Cook
On Thu, Jul 3, 2008 at 8:00 PM, Dougal Stanton [EMAIL PROTECTED] wrote: Here's a snippet from the parser for one option (others omitted for clarity): options :: [OptDescr (Opts - Opts)] options = [ Option b [bus] (ReqArg busNum NUM) Bus number , ... ] where busNum n os = let

Re: [Haskell-cafe] Qualified import syntax badly designed (?)

2008-07-09 Thread Stuart Cook
On Wed, Jul 9, 2008 at 10:01 AM, Neil Mitchell [EMAIL PROTECTED] wrote: It seems that the qualified import syntax is a bit awkward. At the moment, its common to see: import qualified Data.Map as M import Data.Map(Map) i.e. import a module, give it an alias (M), and put some things in the

Re: [Haskell-cafe] Mutually recursive modules and google protocol-buffers

2008-07-15 Thread Stuart Cook
On Wed, Jul 16, 2008 at 12:54 AM, Henning Thielemann [EMAIL PROTECTED] wrote: Sooner or later you want generalize your datatypes. Then you can define data A b = A b and you do not need to import B any longer. I do not know if this is a generally applicable approach, but it helped me in some

Re: [Haskell-cafe] namespaces for values, types, and classes

2009-11-29 Thread Stuart Cook
On Sun, Nov 29, 2009 at 8:42 AM, pbrowne patrick.bro...@comp.dit.ie wrote: Question 3) Instances are not named so can they be imported? Whenever you import a module, you automatically import all of its instances as well. In fact, there is no way to *not* include instances when importing a

Re: [Haskell-cafe] How to present the commonness of some objects?

2009-07-03 Thread Stuart Cook
2009/7/3 Luke Palmer lrpal...@gmail.com: Keep in mind that with this solution *and* with the ExistentialQuantification solution, there is no possibility of downcasting.  I.e. if you were planning on making a GraphicalWidget subclass, and them somewhere seeing if a a Widget is actually a

Re: [Haskell-cafe] gbp sign showing as unknown character by GHC

2009-08-20 Thread Stuart Cook
On Thu, Aug 20, 2009 at 4:28 PM, Colin Paul Adamsco...@colina.demon.co.uk wrote: But how do you get Latin-1 bytes from a Unicode string? This would need a transcoding process. The first 256 code-points of Unicode coincide with Latin-1. Therefore, if you truncate Unicode characters down to 8

Re: [Haskell-cafe] gbp sign showing as unknown character by GHC

2009-08-20 Thread Stuart Cook
On Thu, Aug 20, 2009 at 5:12 PM, Colin Paul Adamsco...@colina.demon.co.uk wrote: Yes, but surely this will work both ways. The same bytes on input should come back on output, shouldn't they? I would have thought so, but apparently this isn't actually what happens. GHCi, version 6.8.2:

Re: [Haskell-cafe] an array of pointers in FFI?

2008-08-01 Thread Stuart Cook
2008/8/1 Galchin, Vasili [EMAIL PROTECTED]: Thanks Bulat! So since we are talking ;^) is there a function already in Foreign that will allow me to ... [a] - Ptr (Ptr ()) i.e. map a list of type a to an array of ptrs of type a? I think this is going to be a two-part operation: first

Re: [Haskell-cafe] Type safety in foreign pointer

2008-10-15 Thread Stuart Cook
On Thu, Oct 16, 2008 at 12:53 AM, Bulat Ziganshin [EMAIL PROTECTED] wrote: data SomeStruct = SomeStruct You can even go one step further and do data SomeStruct which will prevent you from accidentally trying to the dummy constructor. However, you'll need {-# LANGUAGE EmptyDataDecls #-}

Re: [Haskell-cafe] Time consumption nub

2007-07-18 Thread Stuart Cook
On 7/18/07, Arie Groeneveld [EMAIL PROTECTED] wrote: Ok, so when do I use nub instead of 'map head.group.sort' ? Using nub gave me a lot of trouble in terms of time consumption while handling long lists. Well, nub is non-strict, so you can use it on infinite or partial lists, provided you

Re: [Haskell-cafe] Re: Avoiding boilerplate retrieving GetOpt cmd line args

2007-07-27 Thread Stuart Cook
On 7/27/07, Eric Y. Kow [EMAIL PROTECTED] wrote: Solution #3 No lists, just records (lhs2TeX) -- Advantages: very convenient/compact; have to write (i) Flag type (ii) Settings record type/GetOpt in one go (iii) default Settings easy to

Re: [Haskell-cafe] Monad Description For Imperative Programmer

2007-08-02 Thread Stuart Cook
received my first monadic enlightenment from Bird's Introduction to Functional Programming using Haskell, which also uses the same approach. I think it's an excellent way to approach the topic. Stuart Cook ___ Haskell-Cafe mailing list Haskell-Cafe

Re: [Haskell-cafe] renderString problems

2007-08-02 Thread Stuart Cook
On 8/2/07, Dave Tapley [EMAIL PROTECTED] wrote: Using a BitmapFont I can get strings to appear but they demonstrate the odd behaviour of translating themselves a distance equal to their length every time my displayCallback function is evaluated. I've never used OpenGL from Haskell, but it

Re: [Haskell-cafe] IO semantics and evaluation - summary

2009-02-14 Thread Stuart Cook
From Fixing Haskell IO: We can summarize the SDIOH (Standard Definition of IO in Haskell) as a value of type IO a is a value, that performs, then delivers a value of type a. I think you've already made a critical mistake here. The quotes you give all describe an IO value as something that when

Re: [Haskell-cafe] Re: Basic problem in Haskell language design?

2009-03-01 Thread Stuart Cook
On Mon, Mar 2, 2009 at 12:35 AM, Achim Schneider bars...@web.de wrote: -Wall? The number of -W options enabled should scale (at least) linearly with code size. To make this a little more clear: You should probably be using the -Wall compiler option, which will produce a message for code