Re: [Haskell-cafe] ghc static linking on Windows

2009-07-02 Thread Thomas ten Cate
You cannot link statically to a .dll file. Either link statically with the so-called import library (.lib) (there are tools to generate one from a .dll, I believe), or link statically with a static build of SQLite, which is also a .lib file. Hope that helps, Thomas On Wed, Jul 1, 2009 at 19:18,

[Haskell-cafe] golf, predicate check function for MonadPlus (was Re: How to read safely?)

2009-07-02 Thread Jon Fairbairn
Dan Doel dan.d...@gmail.com writes: There was talk of adding a readMaybe a while ago, but apparently it never happened. As it is, you can use reads, read s becomes: case reads s of [(a, rest)] | all isSpace rest - code using a _ - error case

[Haskell-cafe] Monad Input/Output and Monad Transformers

2009-07-02 Thread Maciej Piechotka
1. Learning haskell I discovered that I/O should be avoided nearly 'at all costs'. The problem is that the IO monad is the only one which have more interactive work flow. There is Reader/Writer monad but in fact AFAIU first one is about the environment and second one is about logging.

Re: [Haskell-cafe] Monad Input/Output and Monad Transformers

2009-07-02 Thread Bulat Ziganshin
Hello Maciej, Thursday, July 2, 2009, 3:31:59 PM, you wrote: class (Monad m, Monoid v) = MonadInput v m where -- | Gets an element from input (line of text [with \n], 4096 bytes, -- or something like that). mzero on end getChunk :: m v class (Monad m, Monoid v) = MonadOutput v

Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-02 Thread Jules Bean
Ross Paterson wrote: On Wed, Jul 01, 2009 at 10:55:39AM -0700, Bryan O'Sullivan wrote: Okay, here's a tentative plan that will help to figure out the answer. I'll build a fiddled base package that rewires the Monoid class to have (++) be the binary operator, and mappend as a synonym for it.

Re: [Haskell-cafe] Monad Input/Output and Monad Transformers

2009-07-02 Thread Maciej Piechotka
On Thu, 2009-07-02 at 15:43 +0400, Bulat Ziganshin wrote: Hello Maciej, Thursday, July 2, 2009, 3:31:59 PM, you wrote: class (Monad m, Monoid v) = MonadInput v m where -- | Gets an element from input (line of text [with \n], 4096 bytes, -- or something like that). mzero on

[Haskell-cafe] Fun with type functions

2009-07-02 Thread Simon Peyton-Jones
Friends Ken, Oleg, and I have finished Version 2 of our paper Fun with Type Functions, which gives a programmer's tour of what type functions are and how they are useful. http://haskell.org/haskellwiki/Simonpj/Talk:FunWithTypeFuns If you have a moment to look at, and wanted to help us improve

[Haskell-cafe] Re: Monoid wants a (++) equivalent

2009-07-02 Thread Heinrich Apfelmus
Ross Paterson wrote: On Wed, Jul 01, 2009 at 04:53:05PM +0200, Thomas Davie wrote: On 1 Jul 2009, at 16:46, Edward Kmett wrote: I'm rather fond of the () suggestion, but would be happy with anything better than mappend! ;) I find it rather ugly, it has a lot of connotations of does not

[Haskell-cafe] A Strict GCL Interpreter in Haskell

2009-07-02 Thread Hector Guilarte
Hi everyone! (First of all, I don't know Monads!) I made a GCL (Guarded Command Language) Compiler and Interpreter for my Languages and Machines course in my University with alex, happy and ghc. I still have a doubt: 1) Since Haskell is Lazy, and my GCL program is being interpreted in Haskell

Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-02 Thread Alexander Dunlap
On Wed, Jul 1, 2009 at 11:26 AM, Ross Patersonr...@soi.city.ac.uk wrote: On Wed, Jul 01, 2009 at 10:55:39AM -0700, Bryan O'Sullivan wrote: Okay, here's a tentative plan that will help to figure out the answer. I'll build a fiddled base package that rewires the Monoid class to have (++) be the

[Haskell-cafe] [ghc] kind of the function arrow

2009-07-02 Thread Dominic Orchard
I was just playing around and noticed that the kind of the function arrow in GHC is (?? - ? - *) when I (naively) expected it to be (* - * - *). After looking at (http://hackage.haskell.org/packages/archive/ghc/6.10.2/doc/html/Type.html#5) I see that the kind of (-) means that the parameter

Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-02 Thread Alexander Dunlap
On Wed, Jul 1, 2009 at 10:11 PM, David Menendezd...@zednenem.com wrote: In Wed, Jul 1, 2009 at 3:38 PM, Thomas Schillingnomin...@googlemail.com wrote: 2009/7/1 David Leimbach leim...@gmail.com Just because the compiler can figure out what I mean because it has a great type system, I might

Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-02 Thread Ross Paterson
On Thu, Jul 02, 2009 at 12:46:37PM +0100, Jules Bean wrote: I'm not the person who would have to maintain that arrangement. I guess that's a call for the people who would have to do the work. There is already a haskell98 package, I think, which is the first step? The Prelude is in the base

[Haskell-cafe] Re: Monoid wants a (++) equivalent

2009-07-02 Thread Maciej Piechotka
Ketil Malde ketil at malde.org writes: You know, this might be the right time to start expanding our vocabulary beyond seven bits. Since we're likely to keep mappend around as an alias for some time, people would have a grace period to adjust. How about U+2295 (circle with plus inside

Re: [Haskell-cafe] Re: Monoid wants a (++) equivalent

2009-07-02 Thread Johan Tibell
On Thu, Jul 2, 2009 at 6:45 PM, Maciej Piechotka uzytkown...@gmail.comwrote: I can work with any symbols as long as they are easily typeable. ++ is 3 easy key press. `mappend` is 9. In both cases I don't need to look on keyboard as I know exactly where they are. However there is no way I can

Re: [Haskell-cafe] A Strict GCL Interpreter in Haskell

2009-07-02 Thread Daniel Fischer
Am Donnerstag 02 Juli 2009 18:35:17 schrieb Hector Guilarte: Hi everyone! (First of all, I don't know Monads!) I made a GCL (Guarded Command Language) Compiler and Interpreter for my Languages and Machines course in my University with alex, happy and ghc. I still have a doubt: 1) Since

Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-02 Thread Edward Kmett
Wed, Jul 1, 2009 at 4:17 PM, Raynor Vliegendhart shinnon...@gmail.comwrote: We could use (Control.Category..) as an operator, but this would require an additional wrapping layer if we wish to use the existing Monoid instances: import Prelude hiding (id, (.)) import Control.Category

Re: [Haskell-cafe] golf, predicate check function for MonadPlus (was Re: How to read safely?)

2009-07-02 Thread Alexander Dunlap
On Thu, Jul 2, 2009 at 3:36 AM, Jon Fairbairnjon.fairba...@cl.cam.ac.uk wrote: Dan Doel dan.d...@gmail.com writes: There was talk of adding a readMaybe a while ago, but apparently it never happened. As it is, you can use reads, read s becomes:     case reads s of       [(a, rest)] | all

Re: [Haskell-cafe] Monad Input/Output and Monad Transformers

2009-07-02 Thread Luke Palmer
On Thu, Jul 2, 2009 at 5:31 AM, Maciej Piechotka uzytkown...@gmail.comwrote: 2. I find writing monad transformers annoying. Additionally if package defines transformer A and another transformer B they need to be connected 'by hand'. You have not given any concrete problems or examples, so

Re: [Haskell-cafe] Monad Input/Output and Monad Transformers

2009-07-02 Thread Jason Dagit
On Thu, Jul 2, 2009 at 1:18 PM, Luke Palmer lrpal...@gmail.com wrote: I used to approach problems by designing a monad for my whole program, using an appropriate stack of transformers. I suspect such an approach led to the claim that monads are not appropriate for large software systems in

Re[2]: [Haskell-cafe] Monad Input/Output and Monad Transformers

2009-07-02 Thread Bulat Ziganshin
Hello Luke, Friday, July 3, 2009, 12:18:21 AM, you wrote: I used to approach problems by designing a monad for my whole program, using an appropriate stack of transformers.  I suspect such an approach led to the claim that monads are not appropriate for large software systems in a popular

Re: [Haskell-cafe] ORM for haskell?

2009-07-02 Thread Mads Lindstrøm
Hi Marc Weber Hi Mads! On Tue, Jun 30, 2009 at 11:49:40PM +0200, Mads Lindstrøm wrote: Hi Marc Weber Another example: Updating the age of a pupil: row = SELECT * FROM pupils where age = 13; UPDATE pupils SET age = 14 WHERE id = the id you got above p =

Re: [Haskell-cafe] Monad Input/Output and Monad Transformers

2009-07-02 Thread Maciej Piechotka
On Thu, 2009-07-02 at 14:18 -0600, Luke Palmer wrote: On Thu, Jul 2, 2009 at 5:31 AM, Maciej Piechotka uzytkown...@gmail.com wrote: 2. I find writing monad transformers annoying. Additionally if package defines transformer A and another transformer B they need

Re: [Haskell-cafe] Monad Input/Output and Monad Transformers

2009-07-02 Thread Gwern Branwen
-BEGIN PGP SIGNED MESSAGE- Hash: SHA512 On Thu, Jul 2, 2009 at 5:05 PM, Maciej Piechotka wrote: I'd appreciate the link - google find nothing. I fall in love in Haskell about a week or two ago and I fall in love just after I started learning it ;) Research programming languages like

Re: [Haskell-cafe] A Strict GCL Interpreter in Haskell

2009-07-02 Thread Tillmann Rendel
Hi Hector, Hector Guilarte wrote: 1) Since Haskell is Lazy, and my GCL program is being interpreted in Haskell then my GCL is Lazy too (I know is not as simple as that but believe me, somehow it is behaving lazy). The problem is that it can't be lazy (said to me by my teacher on monday).

[Haskell-cafe] Flipping *-*-* kinds, or monadic finally-tagless madness

2009-07-02 Thread Kim-Ee Yeoh
I'm trying to write HOAS Show instances for the finally-tagless type-classes using actual State monads. The original code: http://okmij.org/ftp/Computation/FLOLAC/EvalTaglessF.hs Two type variables are needed: one to vary over the Symantics class (but only as a phantom type) and another to

Re: [Haskell-cafe] Network.CGI -- practical web programming example.

2009-07-02 Thread wren ng thornton
Brandon S. Allbery KF8NH wrote: Some Haskell programmers use fmap (because most Monads are also Functors), others use liftM. Both have the same effect: given a monadic computation m a, liftM f turns f into a function that operates on the enclosed a instead of the entire m a. That is,

Re: [Haskell-cafe] ORM for haskell?

2009-07-02 Thread Marc Weber
And I realize that you are not trying to replace RDBs, just building a nicer interface to them. I am just concerned that some of the nice properties are lost in the process. I think my main concern comes from seeing people create databases, by automatically generating tables from OO-classes.

Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-02 Thread Richard O'Keefe
It is claimed that making ++ become another name for the Monoid mappend operation will break some Haskell 98 code such as append = (++) That example can easily be fixed by adding a type signature, no? append :: [a] - [a] - [a] append = (++) In ghci, at any rate, using

Re: [Haskell-cafe] A Strict GCL Interpreter in Haskell

2009-07-02 Thread Tillmann Rendel
Hi Hector, Hector Guilarte wrote: I did that already, but it didn't work... Also, since this kind of error would be a run time error in my GCL Language, I don't want it to continue executing whenever an error is found, that's why I changed it back to just: evalExpr:: Expr - Tabla - Int

Re: [Haskell-cafe] Network.CGI -- practical web programming example.

2009-07-02 Thread Brandon S. Allbery KF8NH
On Jul 2, 2009, at 17:59 , wren ng thornton wrote: Brandon S. Allbery KF8NH wrote: Some Haskell programmers use fmap (because most Monads are also Functors), others use liftM. Both have the same effect: given a monadic computation m a, liftM f turns f into a function that operates on the

[Haskell-cafe] Re: Flipping *-*-* kinds, or monadic finally-tagless madness

2009-07-02 Thread Ahn, Ki Yung
Kim-Ee Yeoh wrote: The add function illustrates the kind of do-sugaring we know and love that I want to use for Symantics. lam f = unZ $ do show_c0 - get let vname = v ++ show_c0 c0 = read show_c0 :: VarCount c1 = succ c0 fz :: Z a String -

Re: [Haskell-cafe] Re: Flipping *-*-* kinds, or monadic finally-tagless madness

2009-07-02 Thread Edward Kmett
Actually the problem lies in your definition of fz, it has the wrong type to be used in lam. The Z you get out of fz as type Z b String, but you need it to have Z (a - b) String so that when you strip off the Z you have a Y String (a - b) matching the result type of lam. To get there replace your

[Haskell-cafe] here is how I made it type check

2009-07-02 Thread Ahn, Ki Yung
I don't know if this is what you want but I was at least able to make it to type check basically changing (fz . return) into simply return. I think the error message about the occurs check was because of the fz function is used wrong (or you didn't give it a correct type). {-# LANGUAGE

[Haskell-cafe] Re: Flipping *-*-* kinds, or monadic finally-tagless madness

2009-07-02 Thread Ahn, Ki Yung
Edward Kmett 쓴 글: Actually the problem lies in your definition of fz, it has the wrong type to be used in lam. The Z you get out of fz as type Z b String, but you need it to have Z (a - b) String so that when you strip off the Z you have a Y String (a - b) matching the result type of lam.

Re: [Haskell-cafe] [ghc] kind of the function arrow

2009-07-02 Thread wren ng thornton
Dominic Orchard wrote: I was just playing around and noticed that the kind of the function arrow in GHC is (?? - ? - *) when I (naively) expected it to be (* - * - *). After looking at (http://hackage.haskell.org/packages/archive/ghc/6.10.2/doc/html/Type.html#5) I see that the kind of (-)

Re: [Haskell-cafe] ANN: TernaryTrees-0.1.1.1 - An efficient ternary tree implementation of Sets and Maps

2009-07-02 Thread wren ng thornton
Don Stewart wrote: wren: Alex Mason wrote: TernaryTrees is a package that extends Data.Set ad Data.Map with some ternary tree structures, based on the article [http://www.pcplus.co.uk/node/3074/] . For the string (or rather ByteString) version:

Re: [Haskell-cafe] Flipping *-*-* kinds, or monadic finally-tagless madness

2009-07-02 Thread Edward Kmett
You might also look at doing it without all the State monad noise with something like: class Symantics repr where int :: Int - repr Int add :: repr Int - repr Int - repr Int lam :: (repr a - repr b) - repr (a-b) app :: repr (a - b) - repr a - repr b newtype Pretty a = Pretty

[Haskell-cafe] How to declare a Typeless Function

2009-07-02 Thread Fernan Bolando
Hi I have a function that swaps rows of an array of double swap :: Array (Int,Int) Double - [Int] - Array (Int,Int) Double I then create a function that swaps rows of arrays of Complex Double swap :: Array (Int, Int) (Complex Double) - [Int] - Array (Int, Int) (Complex Double) In reality the

Re: [Haskell-cafe] How to declare a Typeless Function

2009-07-02 Thread Alexander Dunlap
swap :: Array (Int, Int) a - [Int] - Array (Int, Int) a The lowercase a means that that type variable is polymorphic, i.e. it can be any type. Alex On Thu, Jul 2, 2009 at 8:05 PM, Fernan Bolandofernanbola...@mailc.net wrote: Hi I have a function that swaps rows of an array of double swap

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

2009-07-02 Thread Magicloud Magiclouds
Hi, I thought class was for this purpose. But it turns out not. Code as following could not compiled. 1 main = do 2 mapM_ (\(x, y, widget) - do 3a - widgetRun widget 4putStrLn $ show a 5 ) widgetList 6 7 widgetList :: (Widget w) = [(Integer, Integer, w)] 8

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

2009-07-02 Thread Ross Mellgren
You have a couple problems here. The first is that GHC has no idea what particular type 'w' widgetList has, because the empty list is polymorphic. The second is that it looks like you probably want a heterogeneous list of widgets -- that is, possibly different types of widget as long as

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

2009-07-02 Thread Magicloud Magiclouds
Wow, this complex Thank you. I will try that. On Fri, Jul 3, 2009 at 12:24 PM, Ross Mellgrenrmm-hask...@z.odi.ac wrote: You have a couple problems here. The first is that GHC has no idea what particular type 'w' widgetList has, because the empty list is polymorphic. The second is that