Re: Avoiding construction of dead dictionaries

2021-08-09 Thread Claude Heiland-Allen
Hi all, On 09/08/2021 16:31, Brandon Allbery wrote: We haven't figured out what they did, but the other day we had someone in #haskell with an infinite loop evaluating a dictionary. So apparently it is possible for a dictionary to be bottom somehow. I managed to do something like this once:

add constraint to the context of the RULE

2017-03-20 Thread Claude Heiland-Allen
Hi all, I have these functions: toDouble :: (Rounding r, Precision p) => Rounded r p -> Double fromDouble :: (Rounding r, Precision p) => Double -> Rounded r p and I want to use RULES for optimization: {-# RULES "realToFrac/toDouble" realToFrac = toDouble #-} {-# RULES

Re: [Haskell] repa not running in parallel?

2013-11-07 Thread Claude Heiland-Allen
Hi Alexander, On 07/11/13 09:40, Alexander Herz wrote: Hi, I'm new to haskell and I tried to reproduce the perfomance values from the paper Regular, Shape-polymorphic, Parallel Arrays in Haskell. I modified the repa-mmult example from the repa-example package to use the mmultP from

Re: [Haskell-cafe] Increasing memory use in stream computation

2013-10-10 Thread Claude Heiland-Allen
Hi Arie, On 10/10/13 14:02, Arie Peterson wrote: (Sorry for the long email.) Summary: why does the attached program have non-constant memory use? Looking at the heap profile graph (generated with +RTS -h, no need to compile with profiling) I see the increasing memory use is split about

Re: [Haskell-cafe] more gtk help

2013-08-12 Thread Claude Heiland-Allen
Hi Brian, On 12/08/13 03:52, bri...@aracnet.com wrote: ... Couldn't match expected type ... Gtk.on Gtk.exposeEvent glCanvas $ \ _ - putStrLn foo ... I looked up the type of Gtk.on and exposeEvent : ... on :: object - Signal object callback - callback - IO (ConnectId object)

Re: [Haskell-cafe] Diagrams and GTK

2013-08-09 Thread Claude Heiland-Allen
Hi Michael, On 09/08/13 08:21, Michael Oswald wrote: Hello, I am currently writing an application which draws the structure of some packets with help of the diagrams library directly to a GTK GUI. Now the packets can have several hundreds of parameters which have to be drawn so it takes

Re: [Haskell-cafe] haskell-gtk entry question

2013-07-27 Thread Claude Heiland-Allen
Hi Brian, On 25/07/13 04:14, bri...@aracnet.com wrote: This should be simple, and I thought it had it working, but I've broken it and can't figure out why. What I want is to invoke the callback whenever the user activates and entry in a dialogbox, so I did both this : Not sure what you

Re: [Haskell-cafe] How to correctly benchmark code with Criterion?

2012-10-18 Thread Claude Heiland-Allen
Hi Janek, On 18/10/12 10:23, Janek S. wrote: during past few days I spent a lot of time trying to figure out how to write Criterion benchmarks, so that results don't get skewed by lazy evaluation. I want to benchmark different versions of an algorithm doing numerical computations on a vector.

Re: [Haskell-cafe] Ordering of BigFloats in numbers-3000.0.0.0

2012-10-08 Thread Claude Heiland-Allen
On 08/10/12 01:31, Michael Orlitzky wrote: http://hackage.haskell.org/package/variable-precision Mine may be unacceptably slow due to the dependent libraries. I gave it a try -- the speed isn't an issue for me, but I need the trig functions (which look like they pass through Double). These are

Re: [Haskell-cafe] Ordering of BigFloats in numbers-3000.0.0.0

2012-10-07 Thread Claude Heiland-Allen
On 07/10/12 19:00, Michael Orlitzky wrote: I'm trying to use, http://hackage.haskell.org/package/numbers-3000.0.0.0 You might also try my: http://hackage.haskell.org/package/variable-precision It's Ord should work, I've used it in anger, otherwise let me know and I'll fix it when I have

Re: [Haskell-cafe] a parallel mapM?

2012-09-28 Thread Claude Heiland-Allen
On 28/09/12 19:58, Patrick Mylund Nielsen wrote: Check out the parallel combinators in parallel-io: http://hackage.haskell.org/packages/archive/parallel-io/0.3.2/doc/html/Control-Concurrent-ParallelIO-Global.html also

Re: [Haskell-cafe] [Haskell] Well-Typed and Skills Matter offer Haskell courses in London in October

2012-09-24 Thread Claude Heiland-Allen
Hi Andres, list, On 19/09/12 09:41, Andres Löh wrote: Oops, I hit send too prematurely, sorry for the seeming bluntness (but it is still a blunt message, can't apologize for that I suppose): No need to apologize. There's a need for informal meetings as much (or even more) as there is for

Re: [Haskell-cafe] [Haskell] Well-Typed and Skills Matter offer Haskell courses in London in October

2012-09-19 Thread Claude Heiland-Allen
On 19/09/12 08:52, Andres Löh wrote: Registration for all these events is open. I hope to see many of you there. Is there an informal hangout without the £225 price-tag Cheers, Andres ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] [Haskell] Well-Typed and Skills Matter offer Haskell courses in London in October

2012-09-19 Thread Claude Heiland-Allen
Hi list, Oops, I hit send too prematurely, sorry for the seeming bluntness (but it is still a blunt message, can't apologize for that I suppose): On 19/09/12 09:14, Claude Heiland-Allen wrote: On 19/09/12 08:52, Andres Löh wrote: Registration for all these events is open. I hope to see many

Re: [Haskell-cafe] How to implement nested loops with tail recursion?

2012-09-19 Thread Claude Heiland-Allen
Hi! On 19/09/12 19:00, sdiy...@sjtu.edu.cn wrote: So how do I force IO actions whose results are discarded (including IO ()) to be strict? () - foo :: IO () -- should work as it pattern matches, can wrap it in a prettier combinator !_ - foo :: IO a -- could work with -XBangPatterns I've not

Re: [Haskell-cafe] Bad interface problem.

2012-07-10 Thread Claude Heiland-Allen
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 Hi, On 11/07/12 05:51, Magicloud Magiclouds wrote: I cleaned out everything, no luck On Fri, Jul 6, 2012 at 2:14 AM, Albert Y. C. Lai tre...@vex.net wrote: On 12-07-03 04:19 AM, Magicloud Magiclouds wrote:

[Haskell-cafe] ANN: prof2pretty-0.1.0.0

2012-06-30 Thread Claude Heiland-Allen
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 Hi all, I wanted to try visual-prof[1] but found it was broken by ghc RTS changes[2]. I ended up writing prof2pretty[3]: http://hackage.haskell.org/package/prof2pretty - --8-- sccpragmabomb adds SCC pragmas encoding source location. prof2pretty

Re: [Haskell-cafe] Confused by ghci output

2012-05-31 Thread Claude Heiland-Allen
Hi Clark, ghci is defaulting to Integer modexp2 forces Int Int overflows with 3^40 On 31/05/12 17:35, Clark Gaebel wrote: *X 3^40 `mod` 3 == modexp2 3 40 3 False *X fromInteger (3^40 `mod` 3) == modexp2 3 40 3 True *X modexp2 3 40 3 0 *X 3^40 `mod` 3 0 *X 3^40 `mod` 3 ::Int 2 I'm

Re: [Haskell-cafe] webcam library on github

2012-05-25 Thread Claude Heiland-Allen
Hi there, On 25/05/12 08:07, . wrote: On Fri, 2012-05-25 at 08:24 +0800, Conrad Parker wrote: I've downloaded and built this. I had to also download Claude Heiland-Allen's v4l2 source from gitorious, as that package does not seem to be on hackage (though his other related packages are). I

[Haskell-cafe] ANN: variable-precision floating point

2012-05-16 Thread Claude Heiland-Allen
Hi all, I'm pleased to announce variable-precision-0.2: http://hackage.haskell.org/package/variable-precision There was no announcement for previous versions, as I quickly found their flaws to be too irritating in practice. --8-- excerpt from the hackage page Software floating point with

[Haskell-cafe] ANN: bitwise - fast multi-dimensional unboxed bit packed Bool arrays

2012-05-01 Thread Claude Heiland-Allen
Hi all, I'm pleased to announce bitwise-0.1: http://hackage.haskell.org/package/bitwise --8-- excerpt from the hackage page Unboxed multidimensional bit packed Bool arrays with fast aggregate operations based on lifting Bool operations to bitwise operations. There are many other bit packed

[Haskell-cafe] hint and type synonyms

2012-03-31 Thread Claude Heiland-Allen
Hi all, What's the recommended way to get hint[0] to play nice with type synonyms[1]? A problem occurs with in scope type synonyms involving types not in scope. I came up with this after looking at the source[2], but it makes me feel ill: --8-- -- hint and type synonyms don't play nice

Re: [Haskell-cafe] hint and type synonyms

2012-03-31 Thread Claude Heiland-Allen
, Claude Thanks, Daniel On Mar 31, 2012, at 6:19 PM, Claude Heiland-Allen wrote: Hi all, What's the recommended way to get hint[0] to play nice with type synonyms[1]? A problem occurs with in scope type synonyms involving types not in scope. I came up with this after looking at the source[2

Re: [Haskell-cafe] Unable to call function from DLL using FFI

2012-03-14 Thread Claude Heiland-Allen
On 14/03/12 14:01, rajendra prasad wrote: My c++ code(HelloWorld.cpp) looks like this: Try adding extern C { ... } to use the C ABI instead of a C++ ABI (which usually features symbol name mangling to add type information, among other things). (This may not solve the entire problem, but is

Re: [Haskell-cafe] space leak when repeatedly calling Control.Monad.State.Strict.modify

2012-01-29 Thread Claude Heiland-Allen
Hi, On 30/01/12 01:07, Joey Hess wrote: The attached test case quickly chews up hundreds of MB of memory. If modified to call work' instead, it runs in constant space. Somehow the value repeatedly read in from the file and stored in the state is leaking. Can anyone help me understand why?

Re: [Haskell-cafe] DB vs read/show for persisting large data

2011-12-14 Thread Claude Heiland-Allen
On 14/12/11 13:59, Marc Weber wrote: Excerpts from Michael Snoyman's message of Wed Dec 14 14:34:30 +0100 2011: On Wed, Dec 14, 2011 at 3:31 PM, C K Kashyapckkash...@gmail.com wrote: Definite *don't* use read/show: if you make any updates to your data structures, all old files will be lost.

Re: [Haskell-cafe] Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Claude Heiland-Allen
On 02/11/11 09:17, Eugene Kirpichov wrote: Hello, I've got two very simple programs that draw a very simple picture using cairo, doing a couple hundred thousand of cairo calls. One program is in C++. The other is in Haskell and uses the cairo library bindings. The C++ program completes in a

Re: [Haskell-cafe] Cabal rebuilding all of the C++ code for wxHaskell

2011-09-29 Thread Claude Heiland-Allen
On 30/09/11 02:45, DukeDave wrote: 1. Is there some reason (other than 'safety') that cabal install cleans everything up? As far as I've experienced and understand it, it doesn't - it's more that GHC can detect when Haskell modules don't need recompiling while the same is not true for C or

Re: [Haskell-cafe] video for linux two (v4l2) bindings

2011-07-08 Thread Claude Heiland-Allen
Hi, On 05/07/11 10:19, Christopher Done wrote: [snip] /usr/bin/ld: /home/chris/.cabal/lib/bindings-posix-1.2.2/ghc-6.12.3/libHSbindings-posix-1.2.2.a(Signal.o):(.text+0x5dfb): error: undefined reference to 'pthread_kill' [snip] I guess on Claude's system it's linked to by default. So for

[Haskell-cafe] video for linux two (v4l2) bindings

2011-07-03 Thread Claude Heiland-Allen
Greetings all, I uploaded 4 new packages that may be of interest: bindings-linux-videodev2 0.1 - bindings to Video For Linux Two (v4l2) kernel interfaces http://hackage.haskell.org/package/bindings-linux-videodev2-0.1 bindings-mmap 0.1 - bindings to mmap for POSIX

Re: [Haskell-cafe] Data import from octave / text file

2011-06-15 Thread Claude Heiland-Allen
Hi, On 15/06/11 12:13, kaffeepause73 wrote: let m = read text :: [[Double]] signalImport: Prelude.read: no parse read :: String - [[Double]] -- expects Haskell syntax try something like: parse :: String - [[Double]] -- expects plainer syntax parse = map (map read . words) . lines

Re: [Haskell-cafe] cap 3: stopping thread 3 (stackoverflow)

2011-06-07 Thread Claude Heiland-Allen
Hi, On 07/06/11 14:22, Johannes Waldmann wrote: Would this work better with Data.Sequence instead of List? (Is there a really cheap way (O(1)) to split some Data.Sequence roughly in half?) I came up with this using immutable unboxed arrays, which gives a nice parallel speedup (and somehow

Re: [Haskell-cafe] Sub-optimal [code]

2011-02-15 Thread Claude Heiland-Allen
On 15/02/11 20:35, Daniel Fischer wrote: Which makes me wonder: unwanted sharing of lists [1 .. n] or similar is a frequent cause of space leaks, so would it be possible to teach GHC to not share such lists (unless they're bound to a name to indicate sharing is wanted)? In particular for

Re: [Haskell-cafe] HMatrix Vector/Matrix interpolation ala Matlab interp/interp2 ??

2011-01-23 Thread Claude Heiland-Allen
Hi Phil, On 22/01/11 23:13, gutti wrote: - are t a b c d points or curve parameters ? a b c d are points, t is the interpolation coefficient (between 0 and 1) - how does lifting to matrix create a 1d spline to a 2d spline ? -- I don't see how it works essentially, it creates a matrix of

Re: [Haskell-cafe] HMatrix Vector/Matrix interpolation ala Matlab interp/interp2 ??

2011-01-22 Thread Claude Heiland-Allen
Hi Phil, On 22/01/11 14:07, gutti wrote: Dear Haskellers, I'm looking for Vector and especially Matric interpolation ala: z = interp2 (xMatrix, yMatrix, zMatrix, x, y) - x and y can be single values or also vectors or matrices - indeally with the options nearest, linear,

[Haskell-cafe] implementing RealFloat decodeFloat

2010-12-22 Thread Claude Heiland-Allen
Hi everyone, I've been working on [0] Haskell bindings for [1] libqd for [2] double-double and quad-double arithmetic, and have been struggling to implement [3] RealFloat, in particular [4] decodeFloat, mostly because of its postcondition but also some issues relating to variable precision:

Re: [Haskell-cafe] concurrency vs. I/O in GHC

2010-10-24 Thread Claude Heiland-Allen
On 23/10/10 23:17, Donn Cave wrote: Quoth Claude Heiland-Allenclaudiusmaxi...@goto10.org, ... The conclusion I drew was that unsafe foreign functions block the current capability (OS thread) and any threads (Haskell forkIO etc) currently scheduled on that capability, but other capabilities and

Re: [Haskell-cafe] Error Calling Lua Function

2010-10-23 Thread Claude Heiland-Allen
Hi Aditya, The problem is not that the file was not loaded, but that in Lua, loading a file only loads it and does not execute it; Lua is a dynamic language, by which I mean that definitions are created through execution. Attached is a simple example, note that there is no proper error

Re: [Haskell-cafe] concurrency vs. I/O in GHC

2010-10-23 Thread Claude Heiland-Allen
On 23/10/10 17:42, Gregory Crosswhite wrote: On 10/23/10 7:54 AM, John Lato wrote: On Fri, Oct 22, 2010 at 6:16 PM, Bulat Ziganshin bulat.zigans...@gmail.com mailto:bulat.zigans...@gmail.com wrote: Hello John, Monday, October 18, 2010, 8:15:42 PM, you wrote: If anyone is listening, I would

Re: [Haskell-cafe] back doors into the IO monad

2010-10-23 Thread Claude Heiland-Allen
On 23/10/10 23:28, Manlio Perillo wrote: Hi. What are the available methods to execute IO actions from pure code? I know only unsafePerformIO and foreign import (to call a non pure foreign function). Assuming I want to execute external untrusted code using plugins (via the `plugins`

Re: [Haskell-cafe] Maybe to Either -- is there a better way?

2010-08-03 Thread Claude Heiland-Allen
On 02/08/10 15:14, Tom Davies wrote: I find it convenient sometimes to convert a Maybe value to an Either thus (excuse the syntax, it's CAL, not Haskell): maybeToEither :: a - Maybe b - Either a b; maybeToEither errorValue = maybe (Left errorValue) (\x - Right x); but that seemingly

[Haskell-cafe] minimizing jitter while maximizing throughput

2010-08-01 Thread Claude Heiland-Allen
Greeting, Jitter vs Throughput Scenario I have the following scenario: CPU with [C] cores concurrent program the 1 main thread uses OpenGL for animated visual output [W] worker threads uses FFI to lengthy numerical computations with the following desires :

Re: [Haskell-cafe] dear traversable

2010-07-31 Thread Claude Heiland-Allen
On 31/07/10 12:13, wren ng thornton wrote: Stephen Tetley wrote: wren ng thornton wrote: Ben wrote: unzipMap :: M.Map a (b, c) - (M.Map a b, M.Map a c) unzipMap m = (M.map fst m, M.map snd m) I don't think you can give a more efficient implementation using the public interface of Data.Map.

Re: [Haskell-cafe] dear traversable

2010-07-31 Thread Claude Heiland-Allen
On 31/07/10 13:49, Stephen Tetley wrote: Although I haven't calculated the Big-O scores suspect that original post will actually be the best, the solutions that metamorph into a list and out again look like they're doing needless extra work. They're both O(size m) time, and yes the original is

Re: [Haskell-cafe] A question about State Monad and Monad in general

2010-07-16 Thread Claude Heiland-Allen
Hi, On 16/07/10 07:35, C K Kashyap wrote: Haskell without using any standard library stuff? For example, if I wanted an image representation such as this [[(Int,Int.Int)]] - basically a list of lists of 3 tuples (rgb) and wanted to do in place replacement to set the pixel values, how could I

Re: [Haskell-cafe] How to get a list of constructors for a type?

2009-12-30 Thread Claude Heiland-Allen
Gregory Propf wrote: Say I have something like data DT a = Foo a | Bar a | Boo a I want something like a list of the constructors of DT, perhaps as [TypeRep]. I'm using Data.Typeable but can't seem to find what I need in there. Everything there operates over constructors, not types. The

Re: [Haskell-cafe] river crossing puzzle

2009-09-28 Thread Claude Heiland-Allen
pat browne wrote: Hi, Does anyone know where there are any Haskell implementations of the the River Crossing puzzle (AKA Farmer/Fox/Goose/Grain). I wrote some code to generate a map of some version of the game: https://code.goto10.org/svn/maximus/2009/boatman/BoatMan.hs ghc -O2 --make

Re: [Haskell-cafe] Parallel graphics

2009-09-23 Thread Claude Heiland-Allen
Andrew Coppin wrote: (OK, well the *best* way is to use the GPU. But AFAIK that's still a theoretical research project, so we'll leave that for now.) Works for me :-) http://claudiusmaximus.goto10.org/cm/2009-09-24_fl4m6e_in_haskell.html There doesn't need to be a sound theoretical

[Haskell-cafe] graphical user interface library for editing graphs?

2009-06-12 Thread Claude Heiland-Allen
Greetings, I have an idea for a project. The eventual aim is rather eccentric, but the specifications I have sketched out are roughly as follows (best viewed with fixed-width font due to diagrams): 0. the graphical user interface is entirely mouse driven, mouse position/clicks/releases

Re: [Haskell-cafe] When folding is there a way to pick out the last point being processed?

2009-06-11 Thread Claude Heiland-Allen
Casey Hawthorne wrote: When folding is there a way to pick out the last point being processed? I came up with these: safeHead = foldr (const . Just) Nothing safeLast = foldr (flip mplus . Just) Nothing Claude -- http://claudiusmaximus.goto10.org

Re: [Haskell-cafe] createProcess problem

2009-04-27 Thread Claude Heiland-Allen
Hi Vasili, Vasili I. Galchin wrote: [snip] import System.Process main = do handle - runProcess blastall -- executable [-p blastn] -- CLI args Try: [-p, blastn] This passes multiple command line arguments instead of just one that contains a space.

Re: [Haskell-cafe] Type question in instance of a class

2008-11-16 Thread Claude Heiland-Allen
Maurí­cio wrote: Hi, Why is this wrong? class MyClass r where function :: r - s data MyData u = MyData u instance MyClass (MyData v) where function (MyData a) = a GHC says that the type of the result of 'function' is both determined by the rigid type from MyClass and the rigid

Re: [Haskell-cafe] Dealing with CStringLen

2008-11-08 Thread Claude Heiland-Allen
Maurí­cio wrote: Hi, How is CStringLen supposed to be used? The only usual C string I'm familiar with is the null terminated sequence of chars. I remember some Pascal version where the first 2 bytes were used as an integer counting the following characters. What is the convention used in

Re: [Haskell-cafe] Looking for a more functional way to do this

2008-08-06 Thread Claude Heiland-Allen
Jefferson Heard wrote: Adrian, my understanding is that it's not that simple, because I need to preserve the state between calls to GLUT's callbacks, which all return IO (). Then maybe see: http://www.haskell.org/pipermail/haskell-cafe/2007-July/028501.html 2008/8/6 Adrian Neumann [EMAIL

Re: [Haskell-cafe] parsec linking problem

2008-07-07 Thread Claude Heiland-Allen
naruto canada wrote: I run into linking error with parsec: ghc -o /tmp/a.out accu.hs Try ghc --make, or pass appropriate package flags on the command line so that it gets linked with Parsec. Claude -- http://claudiusmaximus.goto10.org ___

Re: [Haskell-cafe] example of FFI FunPtr

2008-06-05 Thread Claude Heiland-Allen
Galchin, Vasili wrote: Hello, I want to model a Haskell function that is a callback from C. I have only found one example in the unix package's Semaphore.hsc, which apparently is not used. I want to be able to marshall a Haskell function that is a first class citizen residing in a

Re: [Haskell-cafe] Random numbers / monads - beginner question

2008-05-08 Thread Claude Heiland-Allen
Madoc wrote: Given a list of numbers, I want to modify each of those numbers by adding a random offset. However, each such modified number shall stay within certain bounds, given by the integers minValue and maxValue. After that, I want to continue computation with the resulting list of type

Re: [Haskell-cafe] sound synthesis

2008-05-02 Thread Claude Heiland-Allen
Thomas Girod wrote: Hi there. Following this advice (http://reddit.com/info/6hknz/comments/c03vdc7), I'm posting here. Recently, I read a few articles about Haskell (and FP in general) and music/sound. I remember an article ranting about how lazy evaluation would be great to do signal

Re: [Haskell-cafe] elementary Maybe Monad problem .. sigh

2008-05-01 Thread Claude Heiland-Allen
Galchin, Vasili wrote: data Bozo = Bozo { id :: Int } bonzo :: Maybe Bozo - IO () bonzo maybe_bozo = do if maybe_bozo == (Just (Bozo x)) then return () else return () ~ I want x to be a pattern that matches id ?? Try: bonzo (Just

Re: [Haskell-cafe] Beginners arrow question

2008-04-05 Thread Claude Heiland-Allen
Paul Johnson wrote: I'm using arrows for the first time, with HXT. I think I'm getting the hang of it, but one problem has me stumped. I have a function lookupFormatter which takes a string and returns an arrow, and I want to use that arrow. Something like this: myProblem :: (ArrowXml a)

Re: [Haskell-cafe] Doing without IORef

2008-04-03 Thread Claude Heiland-Allen
Jinwoo Lee wrote: Hi, Recently I wrote a code that uses readline library (System.Console.Readline). I had to maintain a state (file path) and do IO throughout the code, so I decided to use StateT monad. The problem was that in order to retrieve the current state (file path) inside the

Re: [Haskell-cafe] compilation succeeds -- execution fails

2008-03-30 Thread Claude Heiland-Allen
Jason Dusek wrote: Stefan O'Rear [EMAIL PROTECTED] wrote: The only type that you are allowed to assume corresponds to a C int is CInt, in the Foreign.C.Types module. This probably isn't the problem, but it could make problems of its own on a 64-bit or otherwise weird system. So say I

Re: [Haskell-cafe] Recursion problem in infinite list model

2008-03-27 Thread Claude Heiland-Allen
Hans Aberg wrote: When experimenting with list index sets (i.e. lists more general than provided by Haskell), I arrived at the problem that in the example code below for example h(list 6) does not (in Hugs) write out the beginning of the list lazily. It does work for list 6 first (list

Re: [Haskell-cafe] separate input calculation output

2008-03-25 Thread Claude Heiland-Allen
Thomas Engel wrote: inputvalues :: IO Input -- add a return (ve,de,...) to the end compute :: Input - Output How can I combine several function (calculations) in this function? compute1 :: Input - Output1 compute2 :: Input - Output2 combine :: Output1 - Output2 - Output compute input =

Re: [Haskell-cafe] more on FFI build error

2008-03-24 Thread Claude Heiland-Allen
Galchin Vasili wrote: line #102 ... allocaBytes (#const sizeof(struct mq_attr)) $ \ p_attrs - do definition of struct mq_attr on Linux ... struct mq_attr { long int mq_flags;/* Message queue flags. */ long int mq_maxmsg; /* Maximum number of messages. */ long int

Re: [Haskell-cafe] Re: Exporting Haskell Libraries to C Programmers

2008-03-05 Thread Claude Heiland-Allen
Bruce, Joseph R (Joe) wrote: [snip] I hadn't looked at CABAL before. It's a very useful tool and met all my library-forming needs. That's only half my problem though. I'm trying to make the use of this Haskell code as transparent as possible to the C programmers on the team. Telling them

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

2008-01-07 Thread Claude Heiland-Allen
ChrisK wrote: 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? instance ArrowLoop SF where loop (SF f) = SF $ \as - let (bs,cs) = unzip (f (zip as (stream cs))) in bs where stream

Re: [Haskell-cafe] Class/Instance : what am I doing wrong in this example ?

2007-12-20 Thread Claude Heiland-Allen
david48 wrote: | I'm really inexperienced at this : class Gadget g where fInit :: g - a - g data FString = FString !Int !String deriving Show instance Gadget FString where fInit (FString n _) s = FString n (take n s) The types of: fInit :: g - a - g and: take :: Int - [a] - [a]

Re: [Haskell-cafe] Point and link

2007-12-07 Thread Claude Heiland-Allen
Denis Bueno wrote: On Dec 7, 2007 1:50 PM, Andrew Coppin [EMAIL PROTECTED] wrote: Hi guys. Here's a fairly basic question. I have several ideas for programs that I'd like to write. They all involve placing units of some kind, and then drawing connections between those units. How feasible is it

Re: [Haskell-cafe] Haskell code in Wordpress

2007-11-23 Thread Claude Heiland-Allen
Paulo J. Matos wrote: Hi all, I'm curious about the best way to typeset haskell code in a wordpress blog. Using blockquote removes all indentation. :-( Cheers, Probably HsColour: http://www.cs.york.ac.uk/fp/darcs/hscolour/ --8-- hscolour is a small Haskell script to colourise Haskell code.

Re: [Haskell-cafe] Ideas

2007-08-26 Thread Claude Heiland-Allen
Evan Laforge wrote: The only thing I'm uncertain about is whether it would have good enough time and space performance. All the real work is writing yet another set of basic envelope, oscillator, and fft primitives. You *should* be able to go all the way down to the samples in pure haskell

Re: [Haskell-cafe] renderString problems

2007-08-02 Thread Claude Heiland-Allen
Hi Dave, everyone... Dave Tapley wrote: Hi all, I'm having a lot of trouble using renderString from Graphics.UI.GLUT.Fonts. All my attempts to render a StrokeFont have so far failed. Using a BitmapFont I can get strings to appear but they demonstrate the odd behaviour of translating themselves

[Haskell-cafe] embedding Haskell: problematic polymorphism

2007-07-11 Thread Claude Heiland-Allen
Hi people, I'm embedding Haskell into a C program with a stateful objects with message passing paradigm [0]. I want to make boxes with useful functions, then connect them together within the C program. I know how to build a working version using Data.Dynamic, but that loses polymorphism

[Haskell-cafe] FunPtr stability - suggested clarification to FFI Addendum

2007-06-14 Thread Claude Heiland-Allen
Hi, I think the FFI Addendum should make explicit that FunPtr values are stable (in the sense of StablePtr). I'm writing a Haskell plugin for an application written in C, and the control flow is: C-Haskell-C ; C-Haskell-C ; ... and I was confused by this statement in section 4.1 of