[Haskell-cafe] Very fast searching of byte strings

2007-08-17 Thread ChrisK
Post the the library mailing list at [1] is the Boyer-Moore algorithm implemented for strict and lazy bytestrings (and combinations thereof). It finds all the overlapping instances of the pattern inside the target. I have performance tuned it. But the performance for searching a strict

[Haskell-cafe] Re: trouble compiling import GHC.Prim(MutableByteArray#, ..... (building regex-tdfa from darcs) -- what's that # sign doing?

2007-08-19 Thread ChrisK
Stefan O'Rear wrote: On Fri, Aug 17, 2007 at 04:27:29PM -0400, Thomas Hartman wrote: trying to compile regex-tdfa, I ran into another issue. (earlier I had a cabal problem but that's resolved.) there's a line that won't compile, neither for ghc 6.6.1 nor 6.7 import

[Haskell-cafe] Re: Tying the knot with unknown keys

2007-08-21 Thread ChrisK
David Ritchie MacIver wrote: I was playing with some code for compiling regular expressions to finite state machines and I ran into the following problem. I've solved it, but I'm not terribly happy with my solution and was wondering if someone could come up with a better one. :-)

[Haskell-cafe] Re: Remember the future

2007-08-24 Thread ChrisK
Benjamin Franksen wrote: Simon Peyton-Jones wrote: | It is unfortunate that the [ghc] manual does not give the translation rules, or at | least the translation for the given example. Hmm. OK. I've improved the manual with a URL to the main paper

[Haskell-cafe] Re: Parsec is being weird at me

2007-08-25 Thread ChrisK
Andrew Coppin wrote: Anybody want to explain to me why this doesn't work? ___ ___ _ / _ \ /\ /\/ __(_) / /_\// /_/ / / | | GHC Interactive, version 6.6.1, for Haskell 98. / /_\\/ __ / /___| | http://www.haskell.org/ghc/ \/\/ /_/\/|_| Type :? for help.

[Haskell-cafe] Re: [ANN] An efficient lazy suffix tree library

2007-08-27 Thread ChrisK
Gleb Alexeyev wrote: Bryan O'Sullivan wrote: I just posted a library named suffixtree to Hackage. http://www.serpentine.com/software/suffixtree/ It implements Giegerich and Kurtz's lazy construction algorithm, with a few tweaks for better performance and resource usage. API docs:

[Haskell-cafe] Re: Are type synonym families really equivalent to fundeps?

2007-09-03 Thread ChrisK
Chris Smith wrote: The following code builds and appears to work great (assuming one allows undecidable instances). I have tried both a natural translation into type synonym families, and also the mechanical transformation in http://www.cse.unsw.edu.au/~chak/papers/tyfuns.pdf -- but I

[Haskell-cafe] Re: Are type synonym families really equivalent to fundeps?

2007-09-03 Thread ChrisK
Ah... I see that I have a bug in my proposal, perhaps corrected below. 2. In the second and fourth instances, the type variable x appears twice in the parameters of the type function built from the fundep (a b - c). This causes an error. If I try adding (x ~ x') to the context and

[Haskell-cafe] Re: Are type synonym families really equivalent to fundeps?

2007-09-03 Thread ChrisK
There is are two oddities with your example that I am confused by. Code with fundeps is: data Var a = Var Int (Maybe String) data RHS a b = RHS a b class Action t a b c | a - t, a b - c, a c - b instance Action t () y y instance

[Haskell-cafe] Re: Extending the idea of a general Num to other types?

2007-09-07 Thread ChrisK
Dan Piponi wrote: On 9/5/07, Ketil Malde [EMAIL PROTECTED] wrote: On Wed, 2007-09-05 at 08:19 +0100, Simon Peyton-Jones wrote: Error message from GHCi: test/error.hs:2:8: No instance for (Num String) arising from use of `+' at test/error.hs:2:8-17 Possible fix:

[Haskell-cafe] Re: Is take behaving correctly?

2007-09-12 Thread ChrisK
Conor McBride wrote: Hi folks On 12 Sep 2007, at 00:38, Brent Yorgey wrote: On 9/11/07, PR Stanley [EMAIL PROTECTED] wrote: Hi take 1000 [1..3] still yields [1,2,3] I thought it was supposed to return an error. [..] If for some reason you want a version that does return an error in

[Haskell-cafe] Re: Building production stable software in Haskell

2007-09-17 Thread ChrisK
Philippa Cowderoy wrote: On Mon, 17 Sep 2007, Adrian Hey wrote: Ideally the way to deal with this is via standardised interfaces (using type classes with Haskell), not standardised implementations. Even this level of standardisation is not a trivial clear cut design exercise. e.g we

[Haskell-cafe] Re: Haskell Cheat Sheet?

2007-09-25 Thread ChrisK
I disagree -- see below Dan Weston wrote: I suggest that it be removed and the real Control.Monad.Fix.fix function be defined in its own section, with an side-by-side comparison with a named recursive function. This would be useful because the type fix :: (a - a) - a is highly

[Haskell-cafe] Re: Troubles understanding memoization in SOE

2007-09-26 Thread ChrisK
Peter Verswyvelen wrote: Paul L wrote: We recently wrote a paper about the leak problem. The draft is at http://www.cs.yale.edu/~hl293/download/leak.pdf. Comments are welcome! I'm trying to understand the following in this paper: (A) repeat x = x : repeat x or, in lambdas: (B) repeat =

[Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-10-02 Thread ChrisK
Deborah Goldsmith wrote: UTF-16 is the native encoding used for Cocoa, Java, ICU, and Carbon, and is what appears in the APIs for all of them. UTF-16 is also what's stored in the volume catalog on Mac disks. UTF-8 is only used in BSD APIs for backward compatibility. It's also used in plain

[Haskell-cafe] Re: Space and time leaks

2007-10-05 Thread ChrisK
Dan Weston wrote: Ronald Guida wrote: I need some help with space and time leaks. I know of two types of space leak. The first type of leak occurs when a function uses unnecessary stack or heap space. GHCi sum [1..10^6] *** Exception: stack overflow Apparently, the default definition

[Haskell-cafe] Re: Manual constructor specialization

2007-10-09 Thread ChrisK
Johan Tibell wrote: On 10/9/07, David Benbennick [EMAIL PROTECTED] wrote: On 10/9/07, Johan Tibell [EMAIL PROTECTED] wrote: data Rope = Empty | Leaf | Node !Rope !Rope The point is that Empty can only appear at the top by construction How about indicating this in your

[Haskell-cafe] Re: pi

2007-10-10 Thread ChrisK
[EMAIL PROTECTED] wrote: Yitzchak Gale writes: Dan Piponi wrote: The reusability of Num varies inversely with how many assumptions you make about it. A default implementation of pi would only increase usability, not decrease it. Suppose I believe you. (Actually, I am afraid, I have

[Haskell-cafe] Re: do

2007-10-15 Thread ChrisK
[EMAIL PROTECTED] wrote: Peter Verswyvelen writes about non-monadic IO, unique external worlds: But... isn't this what the Haskell compiler runtime do internally when IO monads are executed? Passing the RealWorld singleton from action to action? In GHC, yes. I never looked into any

[Haskell-cafe] Re: do

2007-10-15 Thread ChrisK
Brandon S. Allbery KF8NH wrote: On Oct 15, 2007, at 13:32 , Peter Verswyvelen wrote: [EMAIL PROTECTED] wrote: Yes, *different approach*. So, there *are* differences. Compilers, anyway, are special applications. I wanted to see - responding to Brandon - a normal Haskell program, which

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

2007-10-16 Thread ChrisK
Simon Marlow wrote: Ultimately when things settle down it might make sense to do this kind of thing, but right now I think an easier approach is to just fix packages when dependencies change, and to identify sets of mutually-compatible packages (we've talked about doing this on Hackage

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

2007-10-16 Thread ChrisK
Don Stewart wrote: stefanor: On Mon, Oct 15, 2007 at 10:57:48PM +0100, Claus Reinke wrote: so i wonder why everyone else claims to be happy with the status quo? We aren't happy with the status quo. Rather, we know that no matter how much we do, the situation will never improve, so most of us

[Haskell-cafe] Proposal: register a package as providing several API versions

2007-10-16 Thread ChrisK
Simon Marlow wrote: Several good points have been raised in this thread, and while I might not agree with everything, I think we can all agree on the goal: things shouldn't break so often. I have another concrete proposal to avoid things breaking so often. Let us steal from something that

[Haskell-cafe] Re: Proposal: register a package asprovidingseveralAPI versions

2007-10-17 Thread ChrisK
I disagree with Simon Marlow here. In practice I think Claus' definition of compatible is good enough: Simon Marlow wrote: Claus Reinke wrote: - consider adding a new monad transformer to a monad transformer library, or a new regex variant to a regex library - surely the new package

[Haskell-cafe] Regex API ideas

2007-11-01 Thread ChrisK
Hi Bryan, I wrote the current regex API, so your suggestions are interesting to me. The also goes for anyone else's regex API opinions, of course. Bryan O'Sullivan wrote: Ketil Malde wrote: Python used to do pretty well here compared to Haskell, with rather efficient hashes and text

[Haskell-cafe] Re: Need help from a newby

2007-11-01 Thread ChrisK
karle wrote: My declaration is as followed:- type Address = Int data Port = C | D deriving(Eq,Show) data Payload = UP[Char] | RTDP(Address,Port) deriving(Eq,Show) data Pkgtype = RTD | U deriving(Eq,Show) type Pkg = (Pkgtype,Address,Payload) type Table = [(Address,Port)]

[Haskell-cafe] Re: ByteString search code available in easy-to-digest form

2007-11-09 Thread ChrisK
Yeah, my code wants to open up the internals of Lazy bytestrings. Until recently this was possible toChunks, but it would be best to rewrite it for the newest Lazy representation (which comes with new shiny ghc 6.8.1). It is a trivial change, but I due to ghc-6.8.1 failing on ppc G4 OS X, I

[Haskell-cafe] Odd error report against ghc-6.8.1

2007-11-09 Thread ChrisK
[EMAIL PROTECTED] has sent me a new bug report. Apparently he can crash ghc-6.8.1 when compiling regex-tdfa-0.93 (darcs under http://darcs.haskell.org/packages/regex-unstable/regex-tdfa/ ). Should I open a ticket for this? I darcs got the newest regex-tdfa (0.93 iirc) and made all the

[Haskell-cafe] Re: checking regular expressions

2007-11-09 Thread ChrisK
Hi, I wrote the regex-base API you are looking at. Uwe Schmidt wrote: Hi all, what's the simplest way to check, whether a given string is a wellformed regular expression? import Text.Regex.Posix.String(compile) or import Text.Regex.Posix.ByteString(compile) etc.. In the API there's

[Haskell-cafe] Re: let vs. where

2007-11-13 Thread ChrisK
Dan Piponi wrote: On Nov 13, 2007 1:24 PM, Ryan Ingram [EMAIL PROTECTED] wrote: I tend to prefer where, but I think that guards function declarations are more readable than giant if-thens and case constructs. Up until yesterday I had presumed that guards only applied to functions. But I

[Haskell-cafe] Re: Weird ghci behaviour?

2007-11-14 Thread ChrisK
' versus 'Main' prompt is a UI feature for experts, not for new users. Making this more obvious or verbose or better documented does not fix the lack of control the user feels. The only flags that the user can easily find are those listed by --help: chrisk$ ghci --help Usage: ghci

[Haskell-cafe] Re: Knot tying vs monads

2007-11-19 Thread ChrisK
John D. Ramsdell wrote: On Nov 17, 2007 3:04 PM, apfelmus [EMAIL PROTECTED] mailto:[EMAIL PROTECTED] wrote: Unfortunately, I don't have Paulson's book (or any other ML book :) at home. I'm too lazy to figure out the specification from the source code, I guess the code is too opaque,

[Haskell-cafe] Re: Knot tying vs monads

2007-11-19 Thread ChrisK
The data dependency is circular. The case e of Str and Brk are not-circular: layout examines the input parameters to determine column'. Then column' is used to compute columnOut and s'. Then the current data is prepended to s'. The Blo case is the circular one. Pushing the circular

[Haskell-cafe] Re: user error when using Text.Regex.PCRE

2007-11-20 Thread ChrisK
Thank you very much for the error report. I have tracked down the cause. You are searching against an empty Bytestring. This is now represented by -- | /O(1)/ The empty 'ByteString' empty :: ByteString empty = PS nullForeignPtr 0 0 And while the useAsCString and useAsCStringLen functions

[Haskell-cafe] ANNOUNCE: Important bug fix for regex-pcre ByteStrings.

2007-11-20 Thread ChrisK
Greetings, There are new version 0.82 and 0.93 of regex-posix. If you use regex-posix with Data.ByteString then you should upgrade to obtain a fix for a crash error. There are new version of regex-pcre available on hackage and the two darcs repositories:

[Haskell-cafe] Re: Dynamically find out instances of classes (pluginsystem for haskell)

2007-11-22 Thread ChrisK
the standard way to do that is use an existential wrapper: (This needs -fglasgow-exts or some flags) module Main where class Interface x where withName :: x - String data A = A String instance Interface A where withName (A string) = Interface A with ++ string ++ data B = B

[Haskell-cafe] Re: Dynamically find out instances of classes (pluginsystem for haskell)

2007-11-22 Thread ChrisK
Jason Dusek wrote: ChrisK [EMAIL PROTECTED] wrote: the standard way to do that is use an existential wrapper: Does this relate to the basket of fruit problem in object oriented languages? You created the existential wrapper to allow a multimorphic list type? When you access

[Haskell-cafe] Re: Waiting for thread to finish

2007-11-27 Thread ChrisK
Maurí­cio wrote: Hi, After I have spawned a thread with 'forkIO', how can I check if that thread work has finished already? Or wait for it? Thanks, Maurício The best way to do this is using Control.Exception.finally: myFork :: IO () - IO (ThreadId,MVar ()) myFork todo = m -

[Haskell-cafe] Re: Waiting for thread to finish

2007-11-28 Thread ChrisK
A safer gimmick... Ben Franksen wrote: tickWhileDoing :: String - IO a - IO a tickWhileDoing msg act = do hPutStr stderr msg hPutChar stderr ' ' hFlush stderr start_time - getCPUTime tickerId - forkIO ticker ... an async exception here will leave the ticker runnning res -

[Haskell-cafe] Re: Array copying

2007-12-02 Thread ChrisK
Andrew Coppin wrote: Andrew Coppin wrote: copy :: Word32 - IOUArray Word32 Bool - Word32 - IO (IOUArray Word32 Bool) copy p grid size = do let size' = size * p grid' - newArray (1,size') False mapM_ (\n - do b - readArray grid n if b then mapM_ (\x - writeArray

[Haskell-cafe] Re: Array copying

2007-12-03 Thread ChrisK
Reinier Lamers wrote: ChrisK wrote: For GHC 6.6 I created foreign import ccall unsafe memcpy memcpy :: MutableByteArray# RealWorld - MutableByteArray# RealWorld - Int# - IO () {-# INLINE copySTU #-} copySTU :: (Show i,Ix i,MArray (STUArray s) e (ST s)) = STUArray s i e

[Haskell-cafe] Re: Array copying

2007-12-03 Thread ChrisK
Andrew Coppin wrote: ChrisK wrote: For GHC 6.6 I created foreign import ccall unsafe memcpy memcpy :: MutableByteArray# RealWorld - MutableByteArray# RealWorld - Int# - IO () {-# INLINE copySTU #-} copySTU :: (Show i,Ix i,MArray (STUArray s) e (ST s)) = STUArray s i e

[Haskell-cafe] Re: Looking for smallest power of 2 = Integer

2007-12-04 Thread ChrisK
Sterling Clover wrote: Actually, I suspect GHC's strictness analyzer will give you reasonable performance with even the naive version, but fancier ideas are at http://graphics.stanford.edu/~seander/bithacks.html#IntegerLog If given an 'n' you are looking for the (2^x) such that 2^x = n

[Haskell-cafe] Re: Waiting for thread to finish

2007-12-06 Thread ChrisK
Jules Bean wrote: ChrisK wrote: A safer gimmick... Ben Franksen wrote: tickWhileDoing :: String - IO a - IO a tickWhileDoing msg act = do hPutStr stderr msg hPutChar stderr ' ' hFlush stderr start_time - getCPUTime tickerId - forkIO ticker ... an async exception here will leave

[Haskell-cafe] Re: regex package for yhc?

2007-12-06 Thread ChrisK
Thomas Hartman wrote: Is there some way to use any of the various regex packages on hackage via yhc? Has anyone installed one them successfully? I'd like regex-tdfa, but would settle for regex-posix, or really, anything that brings the convenience of regex to yhc. In general, is there a

[Haskell-cafe] Re: IO is a bad example for Monads

2007-12-11 Thread ChrisK
Michael Vanier wrote: I haven't been following this thread closely, but would it be rude to suggest that someone who doesn't want to put the effort into learning the (admittedly difficult) concepts that Haskell embodies shouldn't be using the language? Sorry Michael, but I will take your

[Haskell-cafe] Re: array documentation is missing

2007-12-17 Thread ChrisK
I have received patches which will help Cabal make ghc-6.6 and gc-6.8 friendly regex-tdfa. The problem below is from a change in STUArray from 3 to 4 parameters going from 6.6 to 6.8. I think adding another '_' to each pattern match makes it work for 6.8. Once I get these patches working

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

2007-12-17 Thread ChrisK
Andre Nathan wrote: Hello (Newbie question ahead : I tried this for insertProc, but it obviously doesn't work... what would be the correct way to do this? insertProc :: Pid - StateT PsMap IO PsInfo insertProc pid = do proc - procInfo pid -- XXX this is obviously wrong... psMap - get

[Haskell-cafe] Re: data vs newtype

2007-12-18 Thread ChrisK
Jonathan Cast wrote: So there is a program (or, rather, type) you can write with newtype that can't be written with data: newtype T = T T That compiles, and anything of type T is ⊥. But it breaks my mental model of what the compiler does for newtypes. I always think of them as differently

[Haskell-cafe] Re: what does @ mean?.....

2007-12-28 Thread ChrisK
Nicholls, Mark wrote: Hello, I wonder if someone could answer the following… The short question is what does @ mean in mulNat a b | a = b = mulNat' a b b | otherwise = mulNat' b a a where mulNat' x@(S a) y orig | x == one = y

[Haskell-cafe] Re: Wikipedia on first-class object

2007-12-28 Thread ChrisK
This thread is obviously a source of much fun. I will play too. Cristian Baboi wrote: On Fri, 28 Dec 2007 18:32:05 +0200, Jules Bean [EMAIL PROTECTED] wrote: Cristian Baboi wrote: Let me ask you 3 simple questions. Can one use Haskell to make dynamically linked libraries (DLL on Windows,

[Haskell-cafe] Re: Missing join and split

2007-12-28 Thread ChrisK
Lihn, Steve wrote: Programmer with perl background would think split like: list of string = split regex original string Since regex is involved, it is specific to (Byte)String, not a generic list. Also it appears one would need help from Text.Regex(.PCRE) to do that. intercalate a

[Haskell-cafe] Re: Doing some things right

2007-12-28 Thread ChrisK
Brian Sniffen wrote: On Dec 28, 2007 6:05 AM, Andrew Coppin [EMAIL PROTECTED] wrote: [I actually heard a number of people tell me that learning LISP would change my life forever because LISP has something called macros. I tried to learn it, and disliked it greatly. It's too messy. And what the

[Haskell-cafe] Re: Missing join and split

2007-12-29 Thread ChrisK
Mitar wrote: Hi! On Dec 28, 2007 5:51 PM, Lihn, Steve [EMAIL PROTECTED] wrote: Since regex is involved, it is specific to (Byte)String, not a generic list. Oh, this gives me an interesting idea: making regular expressions more generic. The new regex-base API is fairly generic. If you

[Haskell-cafe] Re: Missing join and split

2007-12-29 Thread ChrisK
Albert Y. C. Lai wrote: Mitar wrote: I am really missing the (general) split function built in standard Haskell. I do not understand why there is something so specific as words and lines but not a simple split? The same goes for join. Don't forget Text.Regex.splitRegex. Which is just:

[Haskell-cafe] Re: Quanta. Was: Wikipedia on first-class object

2008-01-06 Thread ChrisK
Brandon S. Allbery KF8NH wrote: On Jan 6, 2008, at 15:02 , Ketil Malde wrote: More seriously, perhaps quantum enters into the equation in how the brain works, perhaps it is even necessary for thought. However, I get worried it's just another mystical mantra, a gratuitous factor that, lacking

[Haskell-cafe] Re: Implicit parameters and Arrows/Yampa?

2008-01-07 Thread ChrisK
Could I has one question? What is the purpose of the stream function in the ArrowLoop instance? Is it just to catch an unexpected [] at runtime? 8 module Main where import Control.Arrow import Control.Arrow.Operations import Control.Arrow.Transformer.Reader -- -- Standard

[Haskell-cafe] ANN: Build fixed for regex-base,posix,compat,pcre

2008-01-07 Thread ChrisK
ANNOUNCEMENT: Build fixed for regex-base, regex-posix, regex-compat, regex-pcre The changes are mainly to the Cabal build files to support ghc-6.8 and ghc-6.6 simultaneously. They definitely work with cabal version 1.2.3.0 (required for regex-pcre). The regex-base, regex-posix, and

[Haskell-cafe] Re: \_ - not equivalent to const $

2008-01-15 Thread ChrisK
Luke Palmer wrote: In attempting to devise a variant of cycle which did not keep its argument alive (for the purpose of cycle [1::Int..]), I came across this peculiar behavior: import Debug.Trace cycle' :: (a - [b]) - [b] cycle' xs = xs undefined ++ cycle' xs take 20 $ cycle' (const $

[Haskell-cafe] Re: Haskell and GUI

2008-01-15 Thread ChrisK
The advice below is for Mac OS X 10.4 and below. Starting with Mac OS X 10.5 (Leopard) the DISPLAY is set for you by the operating system. Mine is currently /tmp/launch-sQZXQV/:0 which looks very strange because it is used to cause the launchd daemon to start the X server on demand (i.e.

[Haskell-cafe] Re: Why functional programming matters

2008-01-24 Thread ChrisK
Achim Schneider wrote: Don Stewart [EMAIL PROTECTED] wrote: jwlato: In addition to STM, another item that should interest serious programmers is forkIO. Lightweight threads that (unlike in Python) can use multiple cpu's. Coming from Python, I personally appreciate this. Using STM to handle

[Haskell-cafe] Re: Why functional programming matters

2008-01-25 Thread ChrisK
Simon Peyton-Jones wrote: 1. Small examples of actual code. I particularly like the lazy way of counting change example (also works for picking items off a menu). The code below show 3 approaches : a function for computing the coins used in each way as a verbose list a function for

[Haskell-cafe] Security Notice: Buffer overflow fixed in PCRE library

2008-01-30 Thread ChrisK
The PCRE library has just fixed a buffer overflow (related to UTF-8 mode). There are several haskell wrappers for the pcre library. If you use a wrapper for the PCRE library (libpcre) then you may want to upgrade the underlying library. http://pcre.org/news.txt states: News about PCRE

[Haskell-cafe] Re: A handy little consequence of the Cont monad

2008-02-01 Thread ChrisK
The bit of a mess that comes from avoiding monads is (my version): import Foreign.Marshal.Array(withArray0) import Foreign.Ptr(nullPtr,Ptr) import Foreign.C.String(withCString,CString) This uses withCString in order of the supplied strings, and a difference list ([CString]-[CString])

[Haskell-cafe] Re: weird ghci behavior with gadts and existentials

2008-02-06 Thread ChrisK
Let me add: data ExpGADT t where ExpInt :: Int - ExpGADT Int ExpChar :: Char - ExpGADT Char Which type do you think 'unHide' and 'wierd' should have: unHide h = case h of Hidden (_,e) - e wierd = unHide (Hidden (TyInt,ExpInt 3)) either: unHide :: HiddenTypeExp -

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

2008-02-09 Thread ChrisK
For Bimap is there anything like Data.Map.insertWithKey ? Stuart Cook wrote: On Sat, Feb 9, 2008 at 7:36 AM, Dan Weston [EMAIL PROTECTED] wrote: If order is important, the new bijective Data.Bimap class http://code.haskell.org/~scook0/haddock/bimap/Data-Bimap.html may be your best bet (I

[Haskell-cafe] Re: Small displeasure with associated type synonyms

2008-03-06 Thread ChrisK
Tom Schrijvers wrote: Stefan, I tried lexically scoped type variables, but to no avail: instance forall a b. (C a, C b) = C (a, b) where type T (a, b) = (T a, T b) val = (val :: T a, val :: T b) The problem is ambiguity. The type checker can't determine which val function to

[Haskell-cafe] Re: Small displeasure with associated type synonyms

2008-03-06 Thread ChrisK
Okay, I get the difference. The T a annotation in val :: T a)and val :: T a does not help choose the C a dictionary. But the val :: a- T a and val (undefined :: a) allows a to successfully choose the C a dictionary. val :: T a fixes T a but does not imply C a. (undefined :: a) fixes a and

[Haskell-cafe] Re: Dynamic typing makes you more productive?

2008-03-18 Thread ChrisK
Jules Bean wrote: Justin Bailey wrote: From a recent interview[1] with the guy leading Ruby development on .NET at Microsoft: You spend less time writing software than you spend maintaining software. Optimizing for writing software versus maintaining software is probably the wrong thing

[Haskell-cafe] Re: Longest increasing subsequence

2008-04-11 Thread ChrisK
It is late, but I was not sleepy enough, so here is my first translation of the algorithm to a functional approach... {- Quote wikipedia: http://en.wikipedia.org/wiki/Longest_increasing_subsequence L = 0 M[0] = 0 for i = 1, 2, ... n: binary search for the largest j ≤ L such that

[Haskell-cafe] Re: Longest increasing subsequence

2008-04-11 Thread ChrisK
My late night suggestions were nearly correct. I have actually written the code now. Once keeping track of indices, and a second time without them: {-# LANGUAGE BangPatterns #-} -- By Chris Kuklewicz, copyright 2008, BSD3 license -- Longest increasing subsequence -- (see

[Haskell-cafe] Re: Type families and GADTs in 6.9

2008-04-12 Thread ChrisK
The length calculation looked complicated. So I reformulated it as a comparison using HasIndex. But ghc-6.8.2 was not inferring the recursive constraint on proj, so I split proj into proj_unsafe without the constraint and proj with the constraint checked only once. I also renamed ZT to Nil

[Haskell-cafe] Re: semi-closed handles

2008-04-15 Thread ChrisK
Ryan Ingram wrote: I usually use something like this instead: hStrictGetContents :: Handle - IO String hStrictGetContents h = do s - hGetContents h length s `seq` hClose h return s A small idiomatic nitpick: When I see (length s) gets computed and thrown away I wince at the

[Haskell-cafe] Re: Wrong Answer Computing Graph Dominators

2008-04-18 Thread ChrisK
More algebraically, including 'or' for symmtry: and xs = foldr () True xs or xs = foldr (||) False xs The True and False are the (monoid) identities with respect to and || : True x == x x True == x False || x == x x || False == x And so an empty list, if defined at all, should be the

[Haskell-cafe] Re: Caching the Result of a Transaction?

2008-04-28 Thread ChrisK
The garbage collector never gets to collect either the action used to populate the cached value, or the private TMVar used to hold the cached value. A better type for TIVal is given below. It is a newtype of a TVal. The contents are either a delayed computation or the previously forced

[Haskell-cafe] Re: Writing an 'expect'-like program with runInteractiveCommand

2008-05-01 Thread ChrisK
Are you adjusting 'System.IO.hSetBuffering' to NoBuffering for those handles? Graham Fawcett wrote: Hi folks, I would like to communicate with an external, line-oriented process, which takes a sequence of one-line commands, each returning an arbitrary number of lines, and waits for another

[Haskell-cafe] Re: A Monad for on-demand file generation?

2008-07-02 Thread ChrisK
hen, the readFileOD could put the timestamp of the read file in a Monad-local state and the writeFileOD could, if the output is newer then all inputs listed in the state, skip the writing and thus the unsafeInterleaveIO’ed file reads are skipped as well, if they were not required for deciding the

[Haskell-cafe] Re: A Monad for on-demand file generation?

2008-07-03 Thread ChrisK
Joachim Breitner wrote: * The 5th line does not have this effect. Because this gets desugared to (), the special implementation of () means that the next line still sees the same dependency state as the before the call to liftIO. You are violating the monad laws. (f k) and (f = \_ - k)

[Haskell-cafe] Template Haskell and haskell-src-exts

2008-07-10 Thread ChrisK
Hi, Can one represent the ''Type template Haskell syntax of $( makeMergeable ''FileDescriptorProto ) in haskell-src.exts Language.Haskell.Exts.Syntax ? And what are the HsReify data (e.g. HsReifyType and HsReifyDecl and HsReifyFixity )? I don't see any pretty print capability to produce

[Haskell-cafe] Re: ANN: haskell-src-exts 0.3.5

2008-07-15 Thread ChrisK
Thanks for the fix. I have gotten the darcs version and I am compiling... Niklas Broberg wrote: Hi all, I'm pleased to report that haskell-src-exts is now updated to understand Template Haskell syntax (it used to understand pre-6.4 TH, but now it works with the current version). At least I

Re: [Haskell-cafe] Coin changing algorithm

2005-07-13 Thread ChrisK
Well, I don't have time to do more than comment, but here are few improvements: Sort the list of integers, highest at the front of the list. (And perhaps remove duplicates with nub) When you pop the first element you can already compute the range of quantity you will need, and can perhaps

Re: [Haskell-cafe] Coin changing algorithm

2005-07-13 Thread ChrisK
Okay, I like Cale's extra guard short circuit so much I must add it to my pseudo-example. Cale's guard: amount `div` maximum coins maxCoins = [] -- optimisation Mine, updated. partition (x:xs) m k | xm = partition xs m k-- x is too big parititon (x:_) m k | x*k m = []

Re: [Haskell-cafe] Coin changing algorithm

2005-07-13 Thread ChrisK
(= x coins)) over and over again. Radu Grigore wrote: On 7/13/05, ChrisK [EMAIL PROTECTED] wrote: Sort the list of integers, highest at the front of the list. (And perhaps remove duplicates with nub) The first time I wrote in the comments that 'partition' takes a decreasing list of integers

Re: [Haskell-cafe] Re: Coin changing algorithm

2005-07-14 Thread ChrisK
The combinator is really elegant, but I want to ask a question about the arrays that get built. The 3D array index is by (m,n,i) and a single array should be good for all of the results. If I say let {x=change 10 5; y=change 5 10;} then it looks like dp (10,5,8) and dp (5,10,8) get evaluated.

Re: [Haskell-cafe] How to use STArray?

2005-08-26 Thread ChrisK
Hi, There are also STArray examples on the wiki at http://haskell.org/hawiki/ImperativeHaskell This includes a very high performance use of STUArray example (from Autrijus), and a ST.Lazy example that I wrote that uses STArray. -- Chris ___

Re: [Haskell-cafe] How to use STArray?

2005-08-26 Thread ChrisK
Alistair Bayley wrote: There are also STArray examples on the wiki at http://haskell.org/hawiki/ImperativeHaskell This includes a very high performance use of STUArray example (from Autrijus), and a ST.Lazy example that I wrote that uses STArray. Thanks. I saw these, but couldn't quite

Re: [Haskell-cafe] Eq Type Class: Overloading (==)

2005-09-16 Thread ChrisK
You would have to preempt the Standard Prelude. For ghc there is a command line switch I have neer used: -fno-implicit-prelude See section 7.3.5 in the GHC user's guide for more. There are some internal caveats: However, the standard Prelude Eq class is still used for the equality test

Re: [Haskell-cafe] Typing problems with basic arithmetic - help!

2005-09-23 Thread ChrisK
Well...your recursion will fail if (a:r) is matched against the empty set. That will trigger your Exception. So does your code avoid this ? No, it does not. cus 2 [1,2,3,4,5] recurses to cus 1 [2,3,4,5] to cus 0 [3,4,5] to cus (-1) [4,5] to cus (-2) [5] to cus

Re: [Haskell-cafe] Help wanted: Lazy multiway zipper with mismached intervals

2005-09-26 Thread ChrisK
Rene de Visser wrote: Hello, I need to zip together multiple lists. The lists are sorted by date, and each entry in the list represents data for a time interval. The time intervals between the lists may be missmatched from each other. Does a single list have only disjoint intervals?

Re: [Haskell-cafe] Trouble understanding NewBinary

2005-10-07 Thread ChrisK
In GHC.Exts are the definitions data Char = C# Char# data Int = I# Int# data Integer = S# Int# | J# Int# ByteArray# data Double = D# Double# data Float = F# Float# Found with ghci using :m + GHC.Exts :browse GHC.Exts Joel Reymont wrote: Folks, In

Re: [Haskell-cafe] Monads as control structures?

2005-10-27 Thread ChrisK
Try this: This line is before the loop sequence_ $ replicate 10 $ do line 1 line 2 ... last line This line is after the loop Now you can use shorthand via loopN n block = sequence_ $ replicate n block So that you can write: This line is before the loop loopN 10 $ do line 1 line 2

Re: [Haskell-cafe] Threads talking back to parent

2005-10-31 Thread ChrisK
Or perhaps a TChan, if that is more appropriate: http://www.haskell.org/ghc/docs/latest/html/libraries/stm/Control-Concurrent-STM-TChan.html I like the curried command idiom: do chan - newChan let logToParent = writeChan chan do tChan - newTChan let logToParentSTM = writeTChan tChan

Re: [Haskell-cafe] Threads talking back to parent

2005-11-03 Thread ChrisK
Joel Reymont wrote: So when should I use a STM TChan instead of a regular Chan? On Oct 31, 2005, at 10:08 PM, ChrisK wrote: Or perhaps a TChan, if that is more appropriate: http://www.haskell.org/ghc/docs/latest/html/libraries/stm/Control- Concurrent-STM-TChan.html I like the curried

[Haskell-cafe] ANN: BUG FIX release of regex-tdfa-1.1.2

2009-05-05 Thread ChrisK
Hello, While occasionally and slowly updating the future version of regex-tdfa I found a bug that exists in the released 1.1.1 version. It was just a matter of passing the wrong value into a function, so was easy to fix when I figured it out. The test case triggered an impossible error

[Haskell-cafe] Re: Brainstorming on how to parse IMAP

2008-08-05 Thread ChrisK
Hi John, I recently posted new and fancy binary Get monads in http://article.gmane.org/gmane.comp.lang.haskell.libraries/9691 and http://article.gmane.org/gmane.comp.lang.haskell.libraries/9756 which might be of interest since network protocol are usually specified in bytes at the wire level.

[Haskell-cafe] Re: Brainstorming on how to parse IMAP

2008-08-05 Thread ChrisK
I am glad you asked Ben, Short answer: It can return a Seq of your values. The values in the Seq are lazy, the Seq itself is finite. It can return what it has so far before it finishes parsing (or even before the rest of the input has arrived from the network). Ben Franksen wrote: ChrisK

[Haskell-cafe] Re: [Haskell] The initial view on typed sprintf and sscanf

2008-09-02 Thread ChrisK
Matthew Brecknell wrote: Unfortunately, I don't seem to be able to make the expected fprintf function, because printf's format-dependent parameter list makes it impossible to find a place to pass the handle. Hence the C++-like () ugliness. How about this: fprintf :: Handle - F (IO ()) b -

[Haskell-cafe] Re: STM and FFI

2008-09-10 Thread ChrisK
There are some examples of adding IO actions to commit and rollback events at http://www.haskell.org/haskellwiki/New_monads/MonadAdvSTM Disclaimer: I wrote this instance of the code, but have not used it much. Cheers, Chris ___ Haskell-Cafe

[Haskell-cafe] ANNOUNCE: protocol-buffers-0.2.9 for Haskell is ready

2008-09-20 Thread ChrisK
Hello one and all, Amid much rejoicing, my Haskell version of protocol-buffer is now released (version 0.2.9). What is this for? What does it do? Why? Shorter answer: It generates Haskell data types that can be converted back and forth to lazy ByteStrings that interoperate with Google's

[Haskell-cafe] Re: Climbing up the shootout...

2008-09-22 Thread ChrisK
And, though I had never seen it before, the current winner for speed is ATS ( http://www.ats-lang.org/ ) which is dependently-typed functional language. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

  1   2   >