Re: [Haskell-cafe] Performance of delete-and-return-last-element

2013-08-31 Thread Petr Pudlák
One solution would be to fold over a specific semigroup instead of a recursive function: |import Data.Semigroup import Data.Foldable(foldMap) import Data.Maybe(maybeToList) data Darle a =Darle {getInit :: [a],getLast ::a } deriving Show instance Semigroup (Darle a)where

Re: [Haskell-cafe] On Markdown in Haddock and why it's not going to happen

2013-08-31 Thread Omari Norman
On Thu, Aug 29, 2013 at 9:30 PM, Mateusz Kowalczyk fuuze...@fuuzetsu.co.ukwrote: Greetings café, Perhaps some saddening news for Markdown fans out there. As you might remember, there was a fair amount of push for having Markdown as an alternate syntax for Haddock. This is a little

Re: [Haskell-cafe] On Markdown in Haddock and why it's not going to happen

2013-08-31 Thread Carter Schonwald
Is there an up todate copy of the haddock manual online anywhere? On Saturday, August 31, 2013, Omari Norman wrote: On Thu, Aug 29, 2013 at 9:30 PM, Mateusz Kowalczyk fuuze...@fuuzetsu.co.uk javascript:_e({}, 'cvml', 'fuuze...@fuuzetsu.co.uk'); wrote: Greetings café, Perhaps some

Re: [Haskell-cafe] ANN: th-desugar simplifies Template Haskell processing

2013-08-31 Thread Sjoerd Visscher
Great package! One question: Do you remove/inline type synonyms? I ask because I just ran into this with some TH code. I'm looking for types that end with - a, but that fails when type synonyms are involved. Sjoerd On Aug 30, 2013, at 2:08 AM, Richard Eisenberg e...@cis.upenn.edu wrote:

Re: [Haskell-cafe] On Markdown in Haddock and why it's not going to happen

2013-08-31 Thread Mateusz Kowalczyk
On 31/08/13 16:20, Carter Schonwald wrote: Is there an up todate copy of the haddock manual online anywhere? No. You can build your own documentation. In Haddock directory, go into ‘doc’ and read the README on how to build it. That is also outdated however: for example, it doesn't provide

Re: [Haskell-cafe] On Markdown in Haddock and why it's not going to happen

2013-08-31 Thread Niklas Hambüchen
Hello, I disagree. While none of your detail points are wrong, they mainly focus on the fact that there is no 1-to-1 mapping between the existing haddock markup and Markdown. I don't think there needs to be. If Markdown can do something new, that something can be added; if something doesn't make

Re: [Haskell-cafe] On Markdown in Haddock and why it's not going to happen

2013-08-31 Thread Mateusz Kowalczyk
On 31/08/13 19:14, Niklas Hambüchen wrote: Hello, I disagree. That's fine, that's why the thread is here. While none of your detail points are wrong, they mainly focus on the fact that there is no 1-to-1 mapping between the existing haddock markup and Markdown. I don't think there needs

[Haskell-cafe] function arithmetic?

2013-08-31 Thread Christopher Howard
Hi. I was just curious about something. In one of my math textbooks I see expressions like this f + g or (f + g)(a) where f and g are functions. What is meant is f(a) + g(a) Is there a way in Haskell you can make use of syntax like that (i.e., expressions like f + g and f * g to create a

Re: [Haskell-cafe] Tasty not compiling

2013-08-30 Thread Roman Cheplyaka
* Thiago Negri evoh...@gmail.com [2013-08-29 22:27:47-0300] I can't install tasty with cabal. Anyone with the same issue or a fix? $ cabal install tasty ... Test\Tasty\Core.hs:147:11: Not in scope: `witness' You probably have a too old version of 'tagged'. I'll add the lower version bound

[Haskell-cafe] Performance of delete-and-return-last-element

2013-08-30 Thread Lucas Paul
Suppose I need to get an element from a data structure, and also modify the data structure. For example, I might need to get and delete the last element of a list: darle xs = ((last xs), (rmlast xs)) where rmlast [_] = [] rmlast (y:ys) = y:(rmlast ys) There are probably other and better ways

Re: [Haskell-cafe] Performance of delete-and-return-last-element

2013-08-30 Thread Ben
isn't this what zippers are for? b On Aug 30, 2013, at 1:04 PM, Clark Gaebel wrote: I don't think a really smart compiler can make that transformation. It looks like an exponential-time algorithm would be required, but I can't prove that. GHC definitely won't... For this specific

Re: [Haskell-cafe] Performance of delete-and-return-last-element

2013-08-30 Thread Clark Gaebel
I don't think a really smart compiler can make that transformation. It looks like an exponential-time algorithm would be required, but I can't prove that. GHC definitely won't... For this specific example, though, I'd probably do: darle :: [a] - (a, [a]) darle xs = case reverse xs of []

Re: [Haskell-cafe] Proposal: Polymorphic typeclass and Records

2013-08-29 Thread Adam Gundry
Hi, On 28/08/13 21:05, Wvv wrote: Let we have data in one module as this: data Person = Person { personId :: Int, name :: String } data Address a = Address { personId :: Int, address :: String , way :: a} It was discussed a lot in topics OverloadedRecordFields This is

Re: [Haskell-cafe] enumerators: exception that can't be catched

2013-08-29 Thread Yuras Shumovich
Hi, Thank you for the reply. Unlikely it is the case (if I understand it correctly). The exception is thrown by enumSocket, I added traces to prove that. And it is propagated to runWithSocket (

Re: [Haskell-cafe] enumerators: exception that can't be catched

2013-08-29 Thread Yuras Shumovich
Hi, Isn't it by design? Consider the next code: import Data.Enumerator (($$), (==)) import qualified Data.Enumerator as E import qualified Data.Enumerator.List as EL import Control.Exception import Control.Monad.IO.Class main :: IO () main = do res - E.run $ myEnum $$ EL.take 5

[Haskell-cafe] Template Haskell and Unit

2013-08-29 Thread Jose A. Lopes
Hi, I am positive about the following situation, but I can't find any concrete answer on the Web. Can anyone confirm this ? In template-haskell-2.7.0, the following quote [t| () |] appears as a (ConT name), where name is the name for unit. However, in template-haskell-2.8.0, the same quote

Re: [Haskell-cafe] Template Haskell and Unit

2013-08-29 Thread Richard Eisenberg
I can't answer about expected behavior, but I can say that those two constructions should be considered identical by the $(…) splice construct. For better or worse, Template Haskell often offers multiple ways of encoding the same source Haskell phrase, and any code that processes Template

Re: [Haskell-cafe] Building recent Cabal/cabal-install

2013-08-29 Thread Johan Tibell
Hi, Cabal 1.18 is still in the release candidate stage so it has in fact not been released yet. We could either bump the dependency on base to 4.8 before the 1.8 release or we could make a Cabal-1.8.0.1 release together with the GHC release that bumps the dependency. -- Johan On Wed, Aug 28,

Re: [Haskell-cafe] Template Haskell and Unit

2013-08-29 Thread Jose A. Lopes
I can't answer about expected behavior, but I can say that those two constructions should be considered identical by the $(…) splice construct. For better or worse, Template Haskell often offers multiple ways of encoding the same source Haskell phrase, and any code that processes Template

Re: [Haskell-cafe] Template Haskell and Unit

2013-08-29 Thread adam vogt
Hi Jose and Richard, haskell-src-meta has Language.Haskell.Meta.Utils.normalizeT which can help with making code treat the two constructs equivalently, though I imagine using th-desugar instead will make that process harder to mess up. Adam On Thu, Aug 29, 2013 at 10:13 AM, Richard Eisenberg

Re: [Haskell-cafe] Template Haskell and Unit

2013-08-29 Thread Richard Eisenberg
I've always considered Unit to just be a nullary tuple. This intuition has never steered me wrong, and it seems that Template Haskell is making the same assumption. If there's some reason that this conflation of ideas is wrong, I would be eager to know -- th-desugar makes this assumption in

[Haskell-cafe] Compiler stops at SpecConstr optimization

2013-08-29 Thread Daniel Díaz Casanueva
Hello. While hacking in one of my projects, one of my modules stopped to compile for apparently no reason. The compiler just freezes (like if it where in an infinite loop) while trying to compile that particular module. Since I had this problem I have been trying to reduce the problem as much as

Re: [Haskell-cafe] Compiler stops at SpecConstr optimization

2013-08-29 Thread Manuel Gómez
On Thu, Aug 29, 2013 at 12:08 PM, Daniel Díaz Casanueva dhelta.d...@gmail.com wrote: Since this problem can be OS-dependent, my system is Debian 7 and I didn't try yet to reproduce my problem in other systems (mainly because I don't have access to other systems at the moment). FWIW, it’s not

Re: [Haskell-cafe] Compiler stops at SpecConstr optimization

2013-08-29 Thread Carter Schonwald
This is a known GHC bug that (i believe?) is fixed in head. Links to the relevant tickets from when I hit this problem trying to build lambdabot are here https://github.com/mokus0/random-fu/issues/13 The work around is to build those libraries with -O1 On Thu, Aug 29, 2013 at 1:00 PM, Manuel

[Haskell-cafe] Announcing GHC iOS

2013-08-29 Thread Luke Iannini
Hi all! (in case you don't read /r/haskell : )) Stephen Blackheath and I are extremely happy to report that as of today, GHC can natively build binaries for iOS devices and the iOS Simulator. You'll find everything you need here: http://ghc.haskell.org/trac/ghc/wiki/Building/CrossCompiling/iOS

Re: [Haskell-cafe] Announcing GHC iOS

2013-08-29 Thread Luke Iannini
Stephen provided some more credits — thanks so much to all! Three connected projects concerning cross-compilation: *Registerised ARM support, added using David Terei's LLVM compiler back end with Stephen Blackheath doing an initial ARMv5 version and LLVM patch and Karel Gardas working on

[Haskell-cafe] Debugging ByteString and Data.Binary.Get memory usage

2013-08-29 Thread Kyle Hanson
OK I have a bunch of BSON documents that I convert to ByteStrings, put in a Map, and write to a socket based on the response. I noticed some high memory usage (in the GBs) so I decided to investigate. I simplified my problem into a small program that demonstrates clearer what is happening. I

Re: [Haskell-cafe] Debugging ByteString and Data.Binary.Get memory usage

2013-08-29 Thread Johan Tibell
A good starting point is to estimate how much space you think the data should take using e.g. http://blog.johantibell.com/2011/06/memory-footprints-of-some-common-data.html If you do that, is the actual space usage close to what you expected? On Thu, Aug 29, 2013 at 5:35 PM, Kyle Hanson

[Haskell-cafe] ANN: th-desugar simplifies Template Haskell processing

2013-08-29 Thread Richard Eisenberg
I've just uploaded my new th-desugar package, which enables easier processing of Template Haskell source syntax by desugaring it into a much simpler core language. The meaning of the code after desugaring is identical to before desugaring, but the syntax is much simpler. To wit, th-desugar

Re: [Haskell-cafe] Compiler stops at SpecConstr optimization

2013-08-29 Thread Ben Lippmeier
On 30/08/2013, at 2:38 AM, Daniel Díaz Casanueva wrote: While hacking in one of my projects, one of my modules stopped to compile for apparently no reason. The compiler just freezes (like if it where in an infinite loop) while trying to compile that particular module. Since I had this

[Haskell-cafe] Tasty not compiling

2013-08-29 Thread Thiago Negri
I can't install tasty with cabal. Anyone with the same issue or a fix? $ cabal install tasty ... Test\Tasty\Core.hs:147:11: Not in scope: `witness' ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] On Markdown in Haddock and why it's not going to happen

2013-08-29 Thread Mateusz Kowalczyk
Greetings café, Perhaps some saddening news for Markdown fans out there. As you might remember, there was a fair amount of push for having Markdown as an alternate syntax for Haddock. Unfortunately, this is probably not going to happen for reasons listed on the post I just published at [1].

Re: [Haskell-cafe] Debugging ByteString and Data.Binary.Get memory usage

2013-08-29 Thread Bob Ippolito
Building a map with foldr seems unwise, have you tried doing it with fromListWith instead? Or foldl'? In either case, since you don't even put the map into WHNF, none of the computation is done at all in either case until the first lookup. On Thu, Aug 29, 2013 at 3:35 PM, Kyle Hanson

Re: [Haskell-cafe] Debugging ByteString and Data.Binary.Get memory usage

2013-08-29 Thread Kyle Hanson
Thanks Bob, I made it foldr because it was meant to simulate the sequential IO action that my server uses to populate the Map. I found the problem to be that I need to force the map to evaluate so adding a little $! fixed the problem -- Kyle Hanson On Thu, Aug 29, 2013 at 9:09 PM, Bob

Re: [Haskell-cafe] Debugging ByteString and Data.Binary.Get memory usage

2013-08-29 Thread Bob Ippolito
foldl' is the right way to simulate the sequential IO action, foldr would be doing it in reverse (and for large enough input will stack overflow). On Thu, Aug 29, 2013 at 9:33 PM, Kyle Hanson hanoo...@gmail.com wrote: Thanks Bob, I made it foldr because it was meant to simulate the

Re: [Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-28 Thread Henning Thielemann
On Tue, 27 Aug 2013, John Lato wrote: [1] Most people are physically incapable of reading documents that explain why what they want to do won't work.  Even if people did read the documentation, I suspect that the people most in need of the information would be the least likely to understand

Re: [Haskell-cafe] cpphs calls error when it finds an #error declaration

2013-08-28 Thread Malcolm Wallace
On 27 Aug 2013, at 08:33, Niklas Hambüchen wrote: @Malcolm, would you mind a change towards throwing an exception that is different from error so that it can be easily caught, or even better, a change from runCpphs :: ... - IO String to runCpphs :: ... - IO (Either String

[Haskell-cafe] Proposal: Polymorphic typeclass and Records

2013-08-28 Thread Wvv
Let we have data in one module as this: data Person = Person { personId :: Int, name :: String } data Address a = Address { personId :: Int, address :: String , way :: a} It was discussed a lot in topics OverloadedRecordFields This is an alternative: Let we have polymorphic

Re: [Haskell-cafe] cpphs calls error when it finds an #error declaration

2013-08-28 Thread Niklas Hambüchen
On 29/08/13 00:43, Malcolm Wallace wrote: Have you tried simply wrapping the call to runCpphs in a catch? Something like safeRunCpphs :: ... - IO (Either String String) safeRunCpphs foo = fmap Right (runCpphs foo) `catch` (\(UserError s)- Left s Yes, that is what I'm doing at

[Haskell-cafe] Haskell Weekly News: Issue 278

2013-08-28 Thread Daniel Santa Cruz
Welcome to issue 278 of the HWN, an issue covering crowd-sourced bits of information about Haskell from around the web. This issue covers the week of August 18 to 24, 2013. Quotes of the Week * johnw: finger trees must be related to palm trees somehow * monochrom: do, or undo. there is no

[Haskell-cafe] Building recent Cabal/cabal-install

2013-08-28 Thread Mateusz Kowalczyk
Greetings café, There are some problems in Haddock to do with Template Haskell that I believe are being caused by Cabal. These were apparently addressed in 1.18 which came out recently. ‘Great!’, I thought. My problem is that I'm unsure how to use 1.18. I'm using GHC HEAD (well, 3 days old now)

Re: [Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-27 Thread Niklas Hambüchen
Thanks for your examples. On 27/08/13 13:59, Albert Y. C. Lai wrote: The correct fix is to raise the stack cap, not to avoid using the stack. Indeed, ghci raises the stack cap so high I still haven't fathomed where it is. This is why you haven't seen a stack overflow in ghci for a long

[Haskell-cafe] Template Haskell

2013-08-27 Thread Jose A. Lopes
Hi, Is it possible to retrieve all definitions contained in a module using Template Haskell ? Thanks, Jose -- Jose Antonio Lopes Ganeti Engineering Google Germany GmbH Dienerstr. 12, 80331, München Registergericht und -nummer: Hamburg, HRB 86891 Sitz der Gesellschaft: Hamburg Geschäftsführer:

Re: [Haskell-cafe] Extending Type Classes

2013-08-27 Thread Simon Peyton-Jones
See http://ghc.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances | -Original Message- | From: Haskell-Cafe [mailto:haskell-cafe-boun...@haskell.org] On Behalf | Of Henning Thielemann | Sent: 26 August 2013 20:07 | To: Frantisek Farka | Cc: Haskell Cafe | Subject: Re: [Haskell-cafe]

[Haskell-cafe] cpphs calls error when it finds an #error declaration

2013-08-27 Thread Niklas Hambüchen
Hi, after some debugging of a higher-level tool I found out that when I use cpphs as a library and the `runCpphs` function that is to produce the preprocessed output, when it comes across the #error directive it will terminate my program. This is because handling #error is implemented with

Re: [Haskell-cafe] Template Haskell

2013-08-27 Thread Niklas Hambüchen
Hi Jose, Template Haskell doesn't parse code. haskell-src-exts and the GHC API can do that. Have a look at: * ghc-mod browse (using ghc api) * hscope (using haskell-src-exts) On 27/08/13 15:45, Jose A. Lopes wrote: Hi, Is it possible to retrieve all definitions contained in a module using

Re: [Haskell-cafe] Template Haskell

2013-08-27 Thread Jose A. Lopes
Thanks, Jose -- Jose Antonio Lopes Ganeti Engineering Google Germany GmbH Dienerstr. 12, 80331, München Registergericht und -nummer: Hamburg, HRB 86891 Sitz der Gesellschaft: Hamburg Geschäftsführer: Graham Law, Christine Elizabeth Flores Steuernummer: 48/725/00206

Re: [Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-27 Thread Patrick Palka
On Mon, Aug 26, 2013 at 4:46 AM, Niklas Hambüchen m...@nh2.me wrote: On #haskell we recently had a discussion about the following: import System.Random list - replicateM 100 randomIO :: IO [Int] I would think that this gives us a list of a million random Ints. In fact, this is

Re: [Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-27 Thread Niklas Hambüchen
On 27/08/13 20:37, Patrick Palka wrote: You can use ContT to force the function to use heap instead of stack space, e.g. runContT (replicateM 100 (lift randomIO)) return That is interesting, and works. Unfortunately its pure existence will not fix sequence, mapM etc. in base.

Re: [Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-27 Thread Tom Ellis
On Mon, Aug 26, 2013 at 12:05:14PM -0700, Bryan O'Sullivan wrote: On Mon, Aug 26, 2013 at 1:46 AM, Niklas Hambüchen m...@nh2.me wrote: This is because sequence is implemented as sequence (m:ms) = do x - m xs - sequence ms return

[Haskell-cafe] enumerators: exception that can't be catched

2013-08-27 Thread Yuras Shumovich
Hello, I'm debugging an issue in websockets package, https://github.com/jaspervdj/websockets/issues/42 I'm not familiar with enumerator package (websockets are based on it), so I'm looking for help. The exception is throws inside enumSocket enumerator using throwError (

Re: [Haskell-cafe] enumerators: exception that can't be catched

2013-08-27 Thread Ben Doyle
This is partially guesswork, but the code to catchWSError looks dubious: catchWsError :: WebSockets p a - (SomeException - WebSockets p a) - WebSockets p a catchWsError act c = WebSockets $ do env - ask let it = peelWebSockets env $ act cit =

Re: [Haskell-cafe] Template Haskell: let statement in a splice put in the main = do part of a program?

2013-08-27 Thread TP
adam vogt wrote: TH quotes limited as you've noticed. One way to generate similar code is to note that: do let x = y z is the same as let x = y in do z. You can generate the latter with something like the following file, but the `a' isn't in scope for the second argument to

Re: [Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-27 Thread John Lato
IMHO it's perfectly reasonable to expect sequence/replicateM/mapM to be able to handle a list of ~1e6 elements in the Unescapable Monad (i.e. IO). All the alternate implementations in the world won't be as handy as Prelude.sequence, and no amount of documentation will prevent people from running

Re: [Haskell-cafe] Conduit : is it possible to write this function?

2013-08-26 Thread Erik de Castro Lopo
Michael Snoyman wrote: You can build this up using the = operator[1] in stm-conduit, something like: eitherSrc :: MonadResourceBase m = Source (ResourceT m) a - Source (ResourceT m) b - Source (ResourceT m) (Either a b) eitherSrc src1 src2 = do join $ lift $

Re: [Haskell-cafe] TypeLits Typeable

2013-08-26 Thread José Pedro Magalhães
Hi Nicolas, It's not intentional, but Iavor is aware of this, and we want to change it. I'm CC-ing him as he might know more about what the current plan is. Cheers, Pedro On Sat, Aug 24, 2013 at 3:20 PM, Nicolas Trangez nico...@incubaid.comwrote: Hello Cafe, I was playing around with

[Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-26 Thread Niklas Hambüchen
On #haskell we recently had a discussion about the following: import System.Random list - replicateM 100 randomIO :: IO [Int] I would think that this gives us a list of a million random Ints. In fact, this is what happens in ghci. But with ghc we get: Stack space overflow: current

Re: [Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-26 Thread Niklas Hambüchen
As an example that this actually makes problems in production code, I found this in the wildlife: https://github.com/ndmitchell/shake/blob/e0e0a43/Development/Shake/Database.hs#L394 -- Do not use a forM here as you use too much stack space bad - (\f - foldM f [] (Map.toList status)) $

Re: [Haskell-cafe] xmonad (+ mate) evince problem?

2013-08-26 Thread Johannes Waldmann
Problem solved: with mate, use atril instead of evince. (I think it is a gtk2/tgk3 issue and it's got nothing to do with xmonad.) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] ordNub

2013-08-26 Thread Niklas Hambüchen
On 14/07/13 20:20, Niklas Hambüchen wrote: As you might not know, almost *all* practical Haskell projects use it, and that in places where an Ord instance is given, e.g. happy, Xmonad, ghc-mod, Agda, darcs, QuickCheck, yesod, shake, Cabal, haddock, and 600 more (see

Re: [Haskell-cafe] Proposal: Hackage's packages should be seperated by buildable

2013-08-26 Thread Heinrich Apfelmus
He-chien Tsai wrote: I'm sick for checking whether package is obsolete or not. I think packages build failed long time ago should be collected and moved to another page until someone fix them, or hackage pages should have a filter for checking obsolete packages. People are working on it.

Re: [Haskell-cafe] TypeLits Typeable

2013-08-26 Thread Iavor Diatchki
Hi guys, Yep, we know about this and, I believe, the plan is to add custom rules to the constraint solver to solve `Typable n` constraints (where n is a number or symbol). Just for the record, the other design choice was to add instance `Typeable (n :: Symbol)`, but that conflicted with some

Re: [Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-26 Thread Bryan O'Sullivan
On Mon, Aug 26, 2013 at 1:46 AM, Niklas Hambüchen m...@nh2.me wrote: This is because sequence is implemented as sequence (m:ms) = do x - m xs - sequence ms return (x:xs) and uses stack space when used on some [IO a]. This problem

Re: [Haskell-cafe] Extending Type Classes

2013-08-26 Thread Henning Thielemann
The problem of refinement of type classes annoys me from time to time when I work on the NumericPrelude. It is an experimental type class hierarchy for mathematical types. Sometimes a new data type T shall be implemented and it turns out that you can implement only a part of all methods of

Re: [Haskell-cafe] definition of the term combinator

2013-08-26 Thread Kristopher Micinski
I've always stuck to the definition of a closed lambda term (the Y, U, S, K, etc... combinators, for example). The colloquial usage generally implies something like a higher order function that does something interesting (and possibly DSL-y). Kris On Sat, Aug 24, 2013 at 12:09 AM, damodar

Re: [Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-26 Thread Niklas Hambüchen
Maybe an unlimited stack size should be the default? As far as I understand, the only negative effect would be that some programming mistakes would not result in a stack overflow. However, I doubt the usefulness of that: * It already depends a lot on the optimisation level * If you do the same

Re: [Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-26 Thread Albert Y. C. Lai
On 13-08-26 04:46 AM, Niklas Hambüchen wrote: Effectively, sequence is a partial function. (Note: We are not trying to obtain a lazy list of random numbers, use any kind of streaming or the likes. We want the list in memory and use it.) We noticed that this problem did not happen if sequence

[Haskell-cafe] Proposal: Hackage's packages should be seperated by buildable

2013-08-25 Thread He-chien Tsai
I'm sick for checking whether package is obsolete or not. I think packages build failed long time ago should be collected and moved to another page until someone fix them, or hackage pages should have a filter for checking obsolete packages. ___

Re: [Haskell-cafe] reasons why Template Haskell does not propose something similar to Python exec() or eval()

2013-08-25 Thread TP
Tobias Dammers wrote: IIRC you can use haskell-src-exts to parse a string into TH AST structures. There might even be a quasi-quoter for that; I don't have a real computer at hand right more, so you'll need to do some research of your own. Thanks Tobias, it led me to the right path. There is

Re: [Haskell-cafe] Proposal: Hackage's packages should be seperated by buildable

2013-08-25 Thread Rogan Creswick
On Sun, Aug 25, 2013 at 12:48 AM, He-chien Tsai depot...@gmail.com wrote: I'm sick for checking whether package is obsolete or not. I think packages build failed long time ago should be collected and moved to another page until someone fix them, or hackage pages should have a filter for

Re: [Haskell-cafe] reasons why Template Haskell does not propose something similar to Python exec() or eval()

2013-08-25 Thread Dag Odenhall
There's a proposalhttp://ghc.haskell.org/trac/ghc/blog/Template%20Haskell%20Proposal#PartD:quasiquotationfor adding a proper Haskell QuasiQuoter as part of template-haskell. Until then, as others have noted your best option is the haskell-src-meta package, but be aware that this uses a separate

Re: [Haskell-cafe] Renumbered mailing list posts

2013-08-25 Thread Niklas Hambüchen
Austin: Do you have any update on this? On 11/08/13 04:48, Austin Seipp wrote: Henning, Thanks for the report. I'm currently investigating this, and think it should be possible to keep all of the old URLs intact. On Sat, Aug 10, 2013 at 11:01 AM, Niklas Hambüchen m...@nh2.me wrote: On

Re: [Haskell-cafe] Template Haskell: let statement in a splice put in the main = do part of a program?

2013-08-25 Thread adam vogt
On Sat, Aug 24, 2013 at 11:00 AM, TP paratribulati...@free.fr wrote: that has type Stmt, in an ExpQ that seems to be the only thing that we can put in a splice. I have found that it can only be done by doE (or DoE) and compE (or CompE) according to

Re: [Haskell-cafe] definition of the term combinator

2013-08-24 Thread damodar kulkarni
Thanks. I found the explanation given at the link quite useful in shedding the confusion I had had. Thanks and regards, -Damodar Kulkarni On Sat, Aug 24, 2013 at 10:57 AM, Jason Dagit dag...@gmail.com wrote: On Fri, Aug 23, 2013 at 9:09 PM, damodar kulkarni kdamodar2...@gmail.comwrote:

[Haskell-cafe] reasons why Template Haskell does not propose something similar to Python exec() or eval()

2013-08-24 Thread TP
Hi everybody, I continue to learn and test Template Haskell (one more time thanks to John Lato for his post at: http://www.mail-archive.com/haskell-cafe@haskell.org/msg106696.html that made me understand a lot of things). I have a question about the way Template Haskell is working. Why

Re: [Haskell-cafe] reasons why Template Haskell does not propose something similar to Python exec() or eval()

2013-08-24 Thread jean-christophe mincke
Hello, Maybe you could have a look at Quasi Quotationhttp://www.haskell.org/haskellwiki/Quasiquotation . Regards J-C On Sat, Aug 24, 2013 at 11:36 AM, TP paratribulati...@free.fr wrote: Hi everybody, I continue to learn and test Template Haskell (one more time thanks to John Lato for his

Re: [Haskell-cafe] reasons why Template Haskell does not propose something similar to Python exec() or eval()

2013-08-24 Thread Tobias Dammers
IIRC you can use haskell-src-exts to parse a string into TH AST structures. There might even be a quasi-quoter for that; I don't have a real computer at hand right more, so you'll need to do some research of your own. On Aug 24, 2013 11:37 AM, TP paratribulati...@free.fr wrote: Hi everybody, I

Re: [Haskell-cafe] reasons why Template Haskell does not propose something similar to Python exec() or eval()

2013-08-24 Thread Marc Weber
Excerpts from TP's message of Sat Aug 24 11:36:04 +0200 2013: Haskell does not propose something similar to Python (or bash) exec() or eval(), i.e. does not offer the possibility to take a (quoted) string in You actually have eval/exec like features. You can run ghc modules in a haskell

Re: [Haskell-cafe] GHC flags: optghc

2013-08-24 Thread Ben Doyle
That's not a GHC flag; it's a haddock flag. Haddock (which, in case you're not familiar with it, is a program to generate documentation from Haskell source code) uses GHC, and the `optghc` flag lets you pass options to GHC when you invoke Haddock. See [the Haddock docs of the 6.12 era][1], on page

[Haskell-cafe] TypeLits Typeable

2013-08-24 Thread Nicolas Trangez
Hello Cafe, I was playing around with TypeLits in combination with Typeable (using GHC 7.7.7.20130812 FWIW), but was surprised to find Symbols aren't Typeable, and as such the following doesn't work. Is this intentional, or am I missing something? Thanks, Nicolas {-# LANGUAGE DataKinds,

Re: [Haskell-cafe] Yet Another Forkable Class

2013-08-24 Thread Ozgur Akgun
Hi. On 23 August 2013 13:29, Nicolas Trangez nico...@incubaid.com wrote: Did anyone ever consider using type-level literals (strings) to 'name' effects (or transformer layers when using monad stacks)? Edwin Brady had this in his effects library in Idris.

[Haskell-cafe] Template Haskell: let statement in a splice put in the main = do part of a program?

2013-08-24 Thread TP
Hi, I continue to test Template Haskell, and I have some difficulties to use a splice $() in a do contained in the main part of a program. Here is an example. I want to make a splice that does `let a=a` in my code. $ cat MakeLetStatement.hs {-# LANGUAGE

Re: [Haskell-cafe] Template Haskell: let statement in a splice put in the main = do part of a program?

2013-08-24 Thread Brandon Allbery
On Sat, Aug 24, 2013 at 11:00 AM, TP paratribulati...@free.fr wrote: main = do $(makeLetStatement a) -- print a Is that the actual indentation you used? Because it's wrong if so, and the error you would get is the one you're reporting. Indentation matters in Haskell. In an equation for

Re: [Haskell-cafe] Template Haskell: let statement in a splice put in the main = do part of a program?

2013-08-24 Thread TP
Brandon Allbery wrote: main = do $(makeLetStatement a) -- print a Is that the actual indentation you used? Because it's wrong if so, and the error you would get is the one you're reporting. Indentation matters in Haskell. Yes, it matters, but not after main = do: all the lines can

Re: [Haskell-cafe] Hoogle vs Hayoo

2013-08-23 Thread Johannes Waldmann
Mateusz Kowalczyk fuuzetsu at fuuzetsu.co.uk writes: I always thought [hayoo] was just Hoogle with more indexed docs. Wait - there's a semantic difference: hoogle does understand type signatures (e.g., it can specialize them, or flip arguments of functions) while hayoo just treats signatures

Re: [Haskell-cafe] Yet Another Forkable Class

2013-08-23 Thread oleg
I must stress that OpenUnion1.hs described (briefly) in the paper is only one implementation of open unions, out of many possible. For example, I have two more implementations. A year-old version of the code implemented open unions *WITHOUT* overlapping instances or Typeable.

Re: [Haskell-cafe] Hoogle vs Hayoo

2013-08-23 Thread Erik Hesselink
On Thu, Aug 22, 2013 at 9:23 PM, Mateusz Kowalczyk fuuze...@fuuzetsu.co.uk wrote: On 22/08/13 19:30, jabolo...@google.com wrote: Hi, I noticed Hayoo appears as a link in the toolbox of http://hackage.haskell.org and also that Hayoo seems to display better results than Hoogle. For example,

[Haskell-cafe] Conduit : is it possible to write this function?

2013-08-23 Thread Erik de Castro Lopo
Hi all Using the Conduit library is it possible to write the function: eitherSrc :: MonadResource m = Source m a - Source m b - Source m (Either a b) which combines two sources into new output source such that data being produced aysnchronously by the original two sources will

Re: [Haskell-cafe] Hoogle vs Hayoo

2013-08-23 Thread Daniel Trstenjak
On Fri, Aug 23, 2013 at 10:12:27AM +0200, Erik Hesselink wrote: Note that the 'normal' hoogle indexes all (?) of hackage. But by default it only searches the haskell platform. You can add a package with '+' to search in that package. E.g. PublicKey +crypto-api. If the idea behind this, that

Re: [Haskell-cafe] Conduit : is it possible to write this function?

2013-08-23 Thread Michael Snoyman
You can build this up using the = operator[1] in stm-conduit, something like: eitherSrc :: MonadResourceBase m = Source (ResourceT m) a - Source (ResourceT m) b - Source (ResourceT m) (Either a b) eitherSrc src1 src2 = do join $ lift $ Data.Conduit.mapOutput Left src1 =

[Haskell-cafe] typeclass constraints

2013-08-23 Thread TP
Hi everybody, There is something I do not understand in the way typeclass constraints are inferred. 1/ Take the following function definition: sum' [] = [] sum' (x:xs) = x + sum' xs GHCI correctly gives: :t sum' sum' :: Num [a] = [[a]] - [a] So it has inferred that the type list has to

Re: [Haskell-cafe] typeclass constraints

2013-08-23 Thread Adam Gundry
Hi TP, The difference is that in your second example, you have specified the type signature p :: a - ExpQ so GHC checks whether p has this type, and correctly objects that it doesn't. If you leave off the type signature, as you did for sum', the right thing will be inferred. Hope this helps,

Re: [Haskell-cafe] typeclass constraints

2013-08-23 Thread Ivan Lazar Miljenovic
On 23 August 2013 19:23, TP paratribulati...@free.fr wrote: Hi everybody, There is something I do not understand in the way typeclass constraints are inferred. 1/ Take the following function definition: sum' [] = [] sum' (x:xs) = x + sum' xs You haven't specified a type signature here,

Re: [Haskell-cafe] typeclass constraints

2013-08-23 Thread TP
Adam Gundry wrote: If you leave off the type signature, as you did for sum', the right thing will be inferred. Thanks Adam and Ivan. Very stupid question... TP ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Yet Another Forkable Class

2013-08-23 Thread Nicolas Trangez
On Fri, 2013-08-23 at 08:06 +, o...@okmij.org wrote: It will arbitrarily pick the first match in the former and fail to compile in the latter case. Of course we can have duplicate layers. In that case, the dynamically closest handler wins -- which sounds about right (think of reset

Re: [Haskell-cafe] Hoogle vs Hayoo

2013-08-23 Thread jabolopes
It's a bit pointless, if I have to know the package, where I want to search in. Yeah! It does sound a bit pointless. Hoogle should search everything by default, and then you can refine your search by clicking on the '+' or '-' on the packages that appear on the left menu. Jose -- Jose

Re: [Haskell-cafe] Hoogle vs Hayoo

2013-08-23 Thread Mateusz Kowalczyk
On 23/08/13 14:57, jabolo...@google.com wrote: It's a bit pointless, if I have to know the package, where I want to search in. Yeah! It does sound a bit pointless. Hoogle should search everything by default, and then you can refine your search by clicking on the '+' or '-' on the packages

[Haskell-cafe] Munich Haskell Meeting, August 26th

2013-08-23 Thread Christian Neukirchen
Dear all, our monthly Haskell Meeting will take place next week, Monday the 26th of August, at 19h30 in Munich. Please note that we will meet this time at the Max-Emanuel-Brauerei[1]. Last time, much more people showed up than registered and our table was pretty cramped: thus, if you plan to

Re: [Haskell-cafe] monoids induced by Applicative/Alternative/Monad/MonadPlus?

2013-08-23 Thread Mario Blažević
On 13-08-22 04:04 PM, Petr Pudlák wrote: Or, if there are no such definitions, where would be a good place to add them? If they are to be added to the base libraries, the Data.Monoid module would be my choice. I did wish I had the AppMonoid instance on several occasions, when using

[Haskell-cafe] GHC flags: optghc

2013-08-23 Thread jabolopes
Hi, I am using GHC version 6.12.1. What is optghc ? I can't find that information anywhere... Thanks, Jose -- Jose Antonio Lopes Ganeti Engineering Google Germany GmbH Dienerstr. 12, 80331, München Registergericht und -nummer: Hamburg, HRB 86891 Sitz der Gesellschaft: Hamburg

<    3   4   5   6   7   8   9   10   11   12   >