From k.bleijenberg at lijbrandt.nl Sun Dec 1 10:10:52 2013 From: k.bleijenberg at lijbrandt.nl (Kees Bleijenberg) Date: Sun, 1 Dec 2013 11:10:52 +0100 Subject: [Haskell-cafe] options for the RTS in a dll Message-ID: <000001ceee7d$9d9b5ad0$d8d21070$@bleijenberg@lijbrandt.nl> I've written a windows dll in Haskell. The calling program is written in Delphi (pascal). I want to profile this dll. Because you don't have a command line in a dll for +RTS. -RTS, I call the dll with hs_init_ghc (a exported function in the dll). I had to translate some parts of rtsopts.h to Delphi. Everyting seems okay. The program does not hang, no catastrophic failures. When I start with the parameter for rtsoptions in hs_init_ghc I get: with -t --machine-readable ->machine readable overview on the screen. with -B sounds the bell with each garbage collection, and also --info works as expected. But when I call hs_init_ghc with rtsoptions -h I get 3 lines with on each line: Can't open profiling report file .hp. With -p I get missing profiling report .prof Any idea what I'am doing wrong? Kees -------------- next part -------------- An HTML attachment was scrubbed... URL: From nicolas.wu at gmail.com Sun Dec 1 10:18:33 2013 From: nicolas.wu at gmail.com (Nicolas Wu) Date: Sun, 1 Dec 2013 10:18:33 +0000 Subject: [Haskell-cafe] options for the RTS in a dll In-Reply-To: <529b0b53.087a0e0a.51d7.ffffd3ddSMTPIN_ADDED_BROKEN@mx.google.com> References: <529b0b53.087a0e0a.51d7.ffffd3ddSMTPIN_ADDED_BROKEN@mx.google.com> Message-ID: On Sun, Dec 1, 2013 at 10:10 AM, Kees Bleijenberg wrote: > But when I call hs_init_ghc with rtsoptions ?h I get 3 lines with on each > line: Can?t open profiling report file .hp. > > With ?p I get missing profiling report .prof > > Any idea what I?am doing wrong? Sounds odd. Have you ensured you have write permissions where the profiling files will be created? From k.bleijenberg at lijbrandt.nl Sun Dec 1 11:07:20 2013 From: k.bleijenberg at lijbrandt.nl (Kees Bleijenberg) Date: Sun, 1 Dec 2013 12:07:20 +0100 Subject: [Haskell-cafe] options for the RTS in a dll In-Reply-To: References: <529b0b53.087a0e0a.51d7.ffffd3ddSMTPIN_ADDED_BROKEN@mx.google.com> Message-ID: <000001ceee85$8164c8d0$842e5a70$@bleijenberg@lijbrandt.nl> Nicolas, If I profile a test executable in the same directory with +RTS -p everything works fine. So probably it is not a permission issue. Kees -----Oorspronkelijk bericht----- Van: Nicolas Wu [mailto:nicolas.wu at gmail.com] Verzonden: zondag 1 december 2013 11:19 Aan: Kees Bleijenberg CC: haskell-cafe Onderwerp: Re: [Haskell-cafe] options for the RTS in a dll On Sun, Dec 1, 2013 at 10:10 AM, Kees Bleijenberg wrote: > But when I call hs_init_ghc with rtsoptions ?h I get 3 lines with on > each > line: Can?t open profiling report file .hp. > > With ?p I get missing profiling report .prof > > Any idea what I?am doing wrong? Sounds odd. Have you ensured you have write permissions where the profiling files will be created? From 0slemi0 at gmail.com Sun Dec 1 12:49:04 2013 From: 0slemi0 at gmail.com (Andras Slemmer) Date: Sun, 1 Dec 2013 12:49:04 +0000 Subject: [Haskell-cafe] Constraint-folding Message-ID: Hi, I stumbled upon something pretty neat, and although I'm 95% sure Oleg did this already 10 years ago in Haskell98 I thought I'd share it because I find it gorgeous! The basic issue I was having is that whenever I wrote class instances for a lifted type (we'll use Nat): class Class (n :: Nat) instance Class Zero instance (Class m) => Class (Succ m) I always had to litter my code with "(Class n) =>" restrictions even in places where they just shouldn't belong. However my gut feeling was that the generic instance "should" be implied, as we covered all cases. A while ago I proposed a new syntax to do just this ( https://ghc.haskell.org/trac/ghc/ticket/6150) which failed miserably, and for good reason! However there is a way to do it anyway:) What we need is basically a way to "construct" an instance for the fully polymorpic case: "instance Class n". We cannot do this directly as it would overlap with our original instances (and we couldn't implement it anyway), we need another way of representing class instances: type W p = forall a. (p => a) -> a W p simply "wraps" the constraint p into a function that eliminates the constraint on a passed in value. Now we can treat a constraint as a function. We will also need a way to "pattern match" on our lifted types, we will do this with an indexed GADT: data WNat n where -- W for Witness WZero :: WNat Zero WSucc :: WNat n -> WNat (Succ n) And finally the neat part; one can write a general typeclass-polymorphic induction principle on these wrapped constraints (or a "constraint-fold"): natFold :: WNat n -> W (p Zero) -> (forall m. W (p m) -> W (p (Succ m))) -> W (p n) W (p Zero) in the p ~ Class case corresponds to "instance Class Zero", and (forall m. W (p m) -> W (p (Succ m))) corresponds to "instance (Class m) => Class (Succ m)" This function is precisely what we need in order to construct the generic instance! (Note: the implementation of natFold is NOT trivial as we need to wrestle with the type checker in the inductive case, but it is a nice excercise. The solution is here: http://lpaste.net/96429) Now we can construct the generic instance: genericClass :: WNat n -> (Class n => a) -> a genericClass n = natFold n (\x -> x) (\f x -> f x) -- Cannot use id as that would try to unify away our constraints Or equivalently: class WNatClass n where witness :: WNat n instance WNatClass Zero where witness = WZero instance (WNatClass m) => WNatClass (Succ m) where witness = WSucc witness genericClass' :: (WNatClass n) => (Class n => a) -> a genericClass' = genericClass witness Now we can decouple all our "(Class n) =>" and similar constraints, all we need is a WNatClass restriction, which I think is a good enough trade-off (and it's not really a restriction anyway). What do you think? ex -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Sun Dec 1 15:56:20 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sun, 1 Dec 2013 10:56:20 -0500 Subject: [Haskell-cafe] Constraint-folding In-Reply-To: References: Message-ID: Have you looked at The singleton lib on hackage by Richard Eisenberg? Seems like it may be related. Or at least touches on related matters. On Sunday, December 1, 2013, Andras Slemmer <0slemi0 at gmail.com> wrote: > Hi, > > I stumbled upon something pretty neat, and although I'm 95% sure Oleg did > this already 10 years ago in Haskell98 I thought I'd share it because I > find it gorgeous! > > The basic issue I was having is that whenever I wrote class instances for > a lifted type (we'll use Nat): > > class Class (n :: Nat) > instance Class Zero > instance (Class m) => Class (Succ m) > > I always had to litter my code with "(Class n) =>" restrictions even in > places where they just shouldn't belong. However my gut feeling was that > the generic instance "should" be implied, as we covered all cases. A while > ago I proposed a new syntax to do just this ( > https://ghc.haskell.org/trac/ghc/ticket/6150) which failed miserably, and > for good reason! > > However there is a way to do it anyway:) > > What we need is basically a way to "construct" an instance for the fully > polymorpic case: "instance Class n". We cannot do this directly as it would > overlap with our original instances (and we couldn't implement it anyway), > we need another way of representing class instances: > > type W p = forall a. (p => a) -> a > > W p simply "wraps" the constraint p into a function that eliminates the > constraint on a passed in value. Now we can treat a constraint as a > function. > > We will also need a way to "pattern match" on our lifted types, we will do > this with an indexed GADT: > > data WNat n where -- W for Witness > WZero :: WNat Zero > WSucc :: WNat n -> WNat (Succ n) > > And finally the neat part; one can write a general typeclass-polymorphic > induction principle on these wrapped constraints (or a "constraint-fold"): > > natFold :: WNat n -> W (p Zero) -> (forall m. W (p m) -> W (p (Succ m))) > -> W (p n) > > W (p Zero) in the p ~ Class case corresponds to "instance Class Zero", and > (forall m. W (p m) -> W (p (Succ m))) corresponds to "instance (Class m) => > Class (Succ m)" > This function is precisely what we need in order to construct the generic > instance! > > (Note: the implementation of natFold is NOT trivial as we need to wrestle > with the type checker in the inductive case, but it is a nice excercise. > The solution is here: http://lpaste.net/96429) > > Now we can construct the generic instance: > > genericClass :: WNat n -> (Class n => a) -> a > genericClass n = natFold n (\x -> x) (\f x -> f x) -- Cannot use id as > that would try to unify away our constraints > > Or equivalently: > > class WNatClass n where > witness :: WNat n > instance WNatClass Zero where > witness = WZero > instance (WNatClass m) => WNatClass (Succ m) where > witness = WSucc witness > > genericClass' :: (WNatClass n) => (Class n => a) -> a > genericClass' = genericClass witness > > Now we can decouple all our "(Class n) =>" and similar constraints, all we > need is a WNatClass restriction, which I think is a good enough trade-off > (and it's not really a restriction anyway). > > What do you think? > > ex > -------------- next part -------------- An HTML attachment was scrubbed... URL: From apfelmus at quantentunnel.de Sun Dec 1 16:06:10 2013 From: apfelmus at quantentunnel.de (Heinrich Apfelmus) Date: Sun, 01 Dec 2013 17:06:10 +0100 Subject: [Haskell-cafe] free vs. operational vs. free-operational In-Reply-To: References: Message-ID: Nickolay Kudasov wrote: >> Well, that they are heavily used in practice does not mean that they are >> actually useful in practice. The thing is that as soon as your functor is a >> monad, I don't think you really need the Free type anymore -- your >> instruction type is already a monad. > > I don't?? use that myself, so I leave this for others to answer. But you > should note that `Free m` is not the same as `m`: e.g. if `m` is a > probability monad `newtype P a = P [(Double, a)]`, then `Free P` gives you > much more: the whole tree of probabilities (not only probs of final > results), so one could traverse that tree. So I believe `Free m` is rather > useful (as is deriving instances for `Free m` the way it is). Yes, but in this case, Free P is useful *regardless* of P being a monad. If you didn't declare a monad instance for the P type, then you would still get the tree of probabilities. It bugs me that the functor is expected to already be a monad. The instance MonadState s m => MonadState s (Free m) is a fancy way of saying that if the instruction type m has two instructions get and put , then the free monad will have them as well. This is fine from the perspective of variant types, but we don't need to know that m is a monad for that. Furthermore, the MonadState class suggests that the usual laws for the state monad hold -- which they do not! Here a counterexample: {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} import Control.Monad.State data Free f a = Return a | Free (f (Free f a)) instance Functor f => Monad (Free f) where return = Return (Free f) >>= k = Free $ fmap (>>= k) f instance MonadState s (Free (State s)) where state f = Free . state $ \s -> let (a,s') = f s in (Return a, s') interpret :: Free (State s) a -> (s -> s) interpret (Return a) s0 = s0 interpret (Free f ) s0 = snd (runState f s0) -- apply only the first instruction, skip the rest example1 = interpret (put 'a' >> get >> put 'b' >> get) undefined example2 = interpret (put 'b' >> get) undefined If we expect the usual laws for the state monad, then both example1 and example2 should be the same value. However, this is not the case: example1 = 'a' while example2 = 'b' . Just because you have two operations put and get doesn't mean that they can't have additional effects. And apparently, the MonadState condition is not strong enough to guarantee all the put/get laws. >> (But I think it will be impossible for MonadCont). > > It is. See https://github.com/ekmett/free/pull/33 for FreeT. FT has the > instance in HEAD already. That's surprising, I will have to check that. It appears to me that the MonadReader instance is only correct because the control operation is a morphism: local f (m >>= k) = local f m >>= local f . k Otherwise, I don't see how a general control operation can be lifted. >> Almost, but not quite. The key qualification is "while still allowing >> pattern matching". > > You're?? right. But I think it is unnecessary for a library user to pattern > match on F's structure. It is pattern matching on supplied functor that > matters. And that ability is not lost. A pattern match view :: F f a -> Either a (f (F f a)) that runs in O(1) time is very useful for implementing interpreters. For an example, see [1]. In particular, we can use the remainder to create new monadic actions with (>>=). The distinction is similar between being able to pattern match on (:) and using only fold to operate on lists. The former is more flexible. [1]: https://github.com/HeinrichApfelmus/operational/blob/master/doc/examples/BreadthFirstParsing.hs#L47 > To summarize, I currently don't see what 'free' offers that the >> 'operational' package can't do equally well with only 11 exported symbols.. > > > As far as I can tell, while with operational you can certainly do more > things, free provides more things for free (these "baked algebraic laws"). > free also provides some other interesting things, like iterative (co)monad > trasformers, cofree comonads and free applicatives/alternatives (which are > out of operational/free common area). > > That all said, I don't feel myself concerned/experienced enough to state > that one package should be preferred to another. As mentioned, I'm not a fan of the "baked in algrebraic laws" because this excludes an optimization and many laws have to be written in the interpreter anyway. But you're saying that 'free' provides other free structures besides monads. That's a good point. Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com From 0slemi0 at gmail.com Sun Dec 1 16:06:49 2013 From: 0slemi0 at gmail.com (Andras Slemmer) Date: Sun, 1 Dec 2013 16:06:49 +0000 Subject: [Haskell-cafe] Constraint-folding In-Reply-To: References: Message-ID: Yes it is very related! In particular it automatically derives the WNat / WNatClass part. In fact now that I think about it these constraint-folds can also be automatically generated for every singleton type so I'm wondering whether there is a place for them in the singletons library. On 1 December 2013 15:56, Carter Schonwald wrote: > Have you looked at The singleton lib on hackage by Richard Eisenberg? > Seems like it may be related. Or at least touches on related matters. > > > On Sunday, December 1, 2013, Andras Slemmer <0slemi0 at gmail.com> wrote: > >> Hi, >> >> I stumbled upon something pretty neat, and although I'm 95% sure Oleg did >> this already 10 years ago in Haskell98 I thought I'd share it because I >> find it gorgeous! >> >> The basic issue I was having is that whenever I wrote class instances for >> a lifted type (we'll use Nat): >> >> class Class (n :: Nat) >> instance Class Zero >> instance (Class m) => Class (Succ m) >> >> I always had to litter my code with "(Class n) =>" restrictions even in >> places where they just shouldn't belong. However my gut feeling was that >> the generic instance "should" be implied, as we covered all cases. A while >> ago I proposed a new syntax to do just this ( >> https://ghc.haskell.org/trac/ghc/ticket/6150) which failed miserably, >> and for good reason! >> >> However there is a way to do it anyway:) >> >> What we need is basically a way to "construct" an instance for the fully >> polymorpic case: "instance Class n". We cannot do this directly as it would >> overlap with our original instances (and we couldn't implement it anyway), >> we need another way of representing class instances: >> >> type W p = forall a. (p => a) -> a >> >> W p simply "wraps" the constraint p into a function that eliminates the >> constraint on a passed in value. Now we can treat a constraint as a >> function. >> >> We will also need a way to "pattern match" on our lifted types, we will >> do this with an indexed GADT: >> >> data WNat n where -- W for Witness >> WZero :: WNat Zero >> WSucc :: WNat n -> WNat (Succ n) >> >> And finally the neat part; one can write a general typeclass-polymorphic >> induction principle on these wrapped constraints (or a "constraint-fold"): >> >> natFold :: WNat n -> W (p Zero) -> (forall m. W (p m) -> W (p (Succ m))) >> -> W (p n) >> >> W (p Zero) in the p ~ Class case corresponds to "instance Class Zero", >> and (forall m. W (p m) -> W (p (Succ m))) corresponds to "instance (Class >> m) => Class (Succ m)" >> This function is precisely what we need in order to construct the generic >> instance! >> >> (Note: the implementation of natFold is NOT trivial as we need to wrestle >> with the type checker in the inductive case, but it is a nice excercise. >> The solution is here: http://lpaste.net/96429) >> >> Now we can construct the generic instance: >> >> genericClass :: WNat n -> (Class n => a) -> a >> genericClass n = natFold n (\x -> x) (\f x -> f x) -- Cannot use id as >> that would try to unify away our constraints >> >> Or equivalently: >> >> class WNatClass n where >> witness :: WNat n >> instance WNatClass Zero where >> witness = WZero >> instance (WNatClass m) => WNatClass (Succ m) where >> witness = WSucc witness >> >> genericClass' :: (WNatClass n) => (Class n => a) -> a >> genericClass' = genericClass witness >> >> Now we can decouple all our "(Class n) =>" and similar constraints, all >> we need is a WNatClass restriction, which I think is a good enough >> trade-off (and it's not really a restriction anyway). >> >> What do you think? >> >> ex >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From sergey.bushnyak at sigrlami.eu Sun Dec 1 20:11:48 2013 From: sergey.bushnyak at sigrlami.eu (Sergey Bushnyak) Date: Sun, 01 Dec 2013 22:11:48 +0200 Subject: [Haskell-cafe] Looking for reliable heterogeneous vectors Message-ID: <529B9804.70308@sigrlami.eu> Hello, everyone. I'm looking for reliable library or idea how to implement heterogenous vector properly. It may seem odd, but I want elements not only be different types but also functions, something like that, pseudocode: hvec [a b (c->d) [a] ...] -- can be any type let hvec = hvec [ "stuff" 5 getUrl [1, 4, 5]] So far I found *vector-heterogenous* package, but can't decide is it good to build on or create something on my own. Any thoughts and ideas are appreciated. Thanks. From 0slemi0 at gmail.com Sun Dec 1 20:27:06 2013 From: 0slemi0 at gmail.com (Andras Slemmer) Date: Sun, 1 Dec 2013 20:27:06 +0000 Subject: [Haskell-cafe] Looking for reliable heterogeneous vectors In-Reply-To: <529B9804.70308@sigrlami.eu> References: <529B9804.70308@sigrlami.eu> Message-ID: Sure, you can do this easily with a GADT + DataKinds for convenient indexing with lists. The construct you need is called a heterogeneous list, or HList: http://hackage.haskell.org/package/HList-0.3.0.1/docs/Data-HList-HList.html But it's a nice exercise to implement it on your own anyway. If you need "truly" heterogeneous lists where you can't even get the types of the elements from the index typelist then you'll need to existentially hide the types. This will simply be the same as HList without the indexing list. Good luck ex On 1 December 2013 20:11, Sergey Bushnyak wrote: > Hello, everyone. I'm looking for reliable library or idea how to implement > heterogenous vector properly. It may seem odd, but I want elements not only > be different types but also functions, something like that, pseudocode: > > hvec [a b (c->d) [a] ...] -- can be any type > let hvec = hvec [ "stuff" 5 getUrl [1, 4, 5]] > > So far I found *vector-heterogenous* package, but can't decide is it good > to build on or create something on my own. > > Any thoughts and ideas are appreciated. Thanks. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From alexey.skladnoy at gmail.com Sun Dec 1 20:29:08 2013 From: alexey.skladnoy at gmail.com (Aleksey Khudyakov) Date: Sun, 1 Dec 2013 21:29:08 +0100 Subject: [Haskell-cafe] Looking for reliable heterogeneous vectors In-Reply-To: <529B9804.70308@sigrlami.eu> References: <529B9804.70308@sigrlami.eu> Message-ID: On 1 December 2013 21:11, Sergey Bushnyak wrote: > Hello, everyone. I'm looking for reliable library or idea how to implement > heterogenous vector properly. It may seem odd, but I want elements not only > be different types but also functions, something like that, pseudocode: > > hvec [a b (c->d) [a] ...] -- can be any type > let hvec = hvec [ "stuff" 5 getUrl [1, 4, 5]] > > So far I found *vector-heterogenous* package, but can't decide is it good to > build on or create something on my own. > Take a look at fixed-vector-hetero[1]. It's not released yet but I hope I'll get in release ready shape by second half of December. It's an attepmt to provide API for working with arbitrary product types. General idea is to work with CPS represenation of data type [1] https://github.com/Shimuuar/fixed-vector-hetero From dennis.raddle at gmail.com Sun Dec 1 21:23:02 2013 From: dennis.raddle at gmail.com (Dennis Raddle) Date: Sun, 1 Dec 2013 13:23:02 -0800 Subject: [Haskell-cafe] possible CS major seeking advice Message-ID: Sort of off-topic for Haskell, just seeking general advice. (I do love Haskell.) I'm 45, have a B.S. from Caltech and 20+ years of programming experience with NASA (JPL), and now I'm thinking of going back to school to get a Ph.D. in computer science, with a goal of teaching at the university level. I'd like some advice about a possible path. Currently I have an illness which prevents me from handling full-time school, and I am receiving a small disability income. That's the bad news; the good news is that it looks like recovery is on the horizon, perhaps a few years out. Getting admitted to graduate school poses a problem. The only people who know my recent work are my supervisors at NASA. My work at NASA was very uncreative, just grinding through boring code. I was getting gradually sicker and my productivity was going down. Then I got laid off. I'm sure they weren't happy with my productivity. So I'm not too optimistic about getting a glowing letter from my direct boss. However, I did work with two scientists there--they were project leaders, not my boss--and I made a good impression. It's been something like five years since I worked with them and I don't know how well they will remember, but I think they would give me good letters if I can locate them and they remember me. Another possible good letter would come from a fellow I know with a Ph.D. in mathematics. We have worked closely over the years on something very hard to describe called the Feldenkrais Method. It's not math or computer science, but it does require a lot of creativity and learning about learning. I have demonstrated dedication, focus, and intelligence in my work with him. He could give me a good letter, but it's questionable how well it would be received as it's not about CS directly. Another path would be to attend a local state college first and have some professors get to know me, then get letters from them. I'm near California State University Northridge and California State University LA. I hope I could easily get admitted to the M.S. program there. I have some prerequisites to get out of the way; my CS classes at Caltech include only half the normal B.S. requirements, and I am rusty at many things (discrete mathematics, calculus, formal logic, etc.--never used any of these in my job and it's been 20+ years). Although clearly full-time school is out of the question for a few years, I could attend part-time and take some of these prerequisites. For both my M.S. and Ph.D. I want to get admitted to the very best school I can. I'm sure the school determines much of the career that follows. So I would not want to finish the M.S. at the California State schools, but rather transfer to somewhere more prestigious eventually. My next problem is determining an area of specialization. As a professor, I think it's the teaching and mentoring that will satisfy me the most. To feel good about my job I need to work with people and not stick my nose in a computer screen all the time. If I can find a job with good teaching and mentoring opportunities, I know I will LOVE it. I will talk all the time about the pleasure of having a job I love. I'll want to get up in the morning (and that was a big problem with my job at JPL; I was getting depressed). But what will be my area of specialization? As an undergrad I was most drawn to discrete mathematics and algorithms. I also love learning Haskell and would probably be interested in languages. I never really connected with any other classes. But should I specialize in algorithms or languages? I don't know. A priority for me is interacting with people collaboratively, so it might be good to specialize in an area that gets me out in the practical world sometimes. Maybe artificial intelligence? I'm even thinking about the intersection of C.S. and teaching, like devising programs that help teach mathematics and CS through artificial intelligence. But I don't know about artificial intelligence in particular. I would be interested in hearing what people think about areas of CS that would get me involved in real-world applications. Although teaching is my passion, it would be good to stay open to a job in industry should that become desirable for financial reasons. I'm poor right now, have little retirement savings, and I'm blowing through them quickly due to the high medical costs I have. Although people say, "Do what you love, the money will follow." I wonder if those people have ever been poor, especially sick and poor. At some point money becomes more important. But my first preference is teaching. I just don't want to close any doors. Any advice welcome, Dennis -------------- next part -------------- An HTML attachment was scrubbed... URL: From dennis.raddle at gmail.com Sun Dec 1 22:06:14 2013 From: dennis.raddle at gmail.com (Dennis Raddle) Date: Sun, 1 Dec 2013 14:06:14 -0800 Subject: [Haskell-cafe] possible CS major seeking advice In-Reply-To: References: Message-ID: Michal, But I'm not "better than them." My job didn't involve any CS, and my prior coursework represents only through about the junior year. I want the whole experience of a Ph.D., especially getting mentored. An earned Ph.D. also seems to give me the best job options. That's my thought, anyway. Dennis On Sun, Dec 1, 2013 at 2:00 PM, MJG wrote: > Dear Dennis, > > What about old-fashioned attempt to pass PhD exams that some schools ? > Or take online courses for the last year in the domain that you plan to > complete your PhD in, just to prove that you're as good, or better than > their students? > > I believe you're not the only one that tries to complete PhD later than > most students. (I think late mr. Jobs had a similar idea to stress out > after being kicked out of his own company.) > -- > Best regards > Michal > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From benl at ouroborus.net Sun Dec 1 22:27:31 2013 From: benl at ouroborus.net (Ben Lippmeier) Date: Mon, 2 Dec 2013 09:27:31 +1100 Subject: [Haskell-cafe] possible CS major seeking advice In-Reply-To: References: Message-ID: On 02/12/2013, at 8:23 , Dennis Raddle wrote: > > Although teaching is my passion, it would be good to stay open to a job in industry should that become desirable for financial reasons. I'm poor right now, have little retirement savings, and I'm blowing through them quickly due to the high medical costs I have. Although people say, "Do what you love, the money will follow." I wonder if those people have ever been poor, especially sick and poor. At some point money becomes more important. > > But my first preference is teaching. I just don't want to close any doors. If you're aiming for a permanent faculty position, then the top universities care primarily about research output and the ability to attract external funding. Teaching is also an important part of the job, but they assume that if you're a good researcher then you'll also be alright at teaching. I suggest starting out as a teaching assistant / tutor to get more exposure to the field. You could probably tutor for a first year programming course at a local university, just based on your past experience. While at the university, make a point of meeting the faculty members and get to know what projects they're working on. What matters is to find people working on projects that interest you, and for them to see you as an enthusiastic and useful collaborator. Reference letters and the "prestigiousness" of the university matter less than you would think. If you think CS is your thing then step 0 is to get involved in some open source projects. Ben. From mike at izbicki.me Mon Dec 2 01:58:30 2013 From: mike at izbicki.me (Mike Izbicki) Date: Sun, 1 Dec 2013 17:58:30 -0800 Subject: [Haskell-cafe] Looking for reliable heterogeneous vectors In-Reply-To: <529B9804.70308@sigrlami.eu> References: <529B9804.70308@sigrlami.eu> Message-ID: Author of vector-heterogenous here. I tried to design the package to meet use cases like you describe, but fully admit that it's not perfect. It's missing a lot of the functions you might expect from the regular vector package (some of them are because I didn't need them, and some are because the best implementation is not obvious), and syntax is still a little awkward for my tastes. So if you have any ideas on improvements, I'd definitely be willing to incorporate them. Or if you have a great idea for a complete redesign of the package, I'd be happy to replace everything and let you take over. On Sun, Dec 1, 2013 at 12:11 PM, Sergey Bushnyak < sergey.bushnyak at sigrlami.eu> wrote: > Hello, everyone. I'm looking for reliable library or idea how to implement > heterogenous vector properly. It may seem odd, but I want elements not only > be different types but also functions, something like that, pseudocode: > > hvec [a b (c->d) [a] ...] -- can be any type > let hvec = hvec [ "stuff" 5 getUrl [1, 4, 5]] > > So far I found *vector-heterogenous* package, but can't decide is it good > to build on or create something on my own. > > Any thoughts and ideas are appreciated. Thanks. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From sergey.bushnyak at sigrlami.eu Mon Dec 2 03:30:34 2013 From: sergey.bushnyak at sigrlami.eu (Sergey Bushnyak) Date: Mon, 02 Dec 2013 05:30:34 +0200 Subject: [Haskell-cafe] Looking for reliable heterogeneous vectors In-Reply-To: References: <529B9804.70308@sigrlami.eu> Message-ID: <529BFEDA.8020708@sigrlami.eu> On 12/01/2013 10:27 PM, Andras Slemmer wrote: > Sure, you can do this easily with a GADT + DataKinds for convenient > indexing with lists. The construct you need is called a heterogeneous > list, or HList: > http://hackage.haskell.org/package/HList-0.3.0.1/docs/Data-HList-HList.html > > But it's a nice exercise to implement it on your own anyway. If you > need "truly" heterogeneous lists where you can't even get the types of > the elements from the index typelist then you'll need to existentially > hide the types. This will simply be the same as HList without the > indexing list. > > > Good luck > ex > > > On 1 December 2013 20:11, Sergey Bushnyak > wrote: > > Hello, everyone. I'm looking for reliable library or idea how to > implement heterogenous vector properly. It may seem odd, but I > want elements not only be different types but also functions, > something like that, pseudocode: > > hvec [a b (c->d) [a] ...] -- can be any type > let hvec = hvec [ "stuff" 5 getUrl [1, 4, 5]] > > So far I found *vector-heterogenous* package, but can't decide is > it good to build on or create something on my own. > > Any thoughts and ideas are appreciated. Thanks. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > Thank you for suggestions, I'll look into it. -------------- next part -------------- An HTML attachment was scrubbed... URL: From sergey.bushnyak at sigrlami.eu Mon Dec 2 03:32:24 2013 From: sergey.bushnyak at sigrlami.eu (Sergey Bushnyak) Date: Mon, 02 Dec 2013 05:32:24 +0200 Subject: [Haskell-cafe] Looking for reliable heterogeneous vectors In-Reply-To: References: <529B9804.70308@sigrlami.eu> Message-ID: <529BFF48.3060109@sigrlami.eu> On 12/01/2013 10:29 PM, Aleksey Khudyakov wrote: > On 1 December 2013 21:11, Sergey Bushnyak wrote: >> Hello, everyone. I'm looking for reliable library or idea how to implement >> heterogenous vector properly. It may seem odd, but I want elements not only >> be different types but also functions, something like that, pseudocode: >> >> hvec [a b (c->d) [a] ...] -- can be any type >> let hvec = hvec [ "stuff" 5 getUrl [1, 4, 5]] >> >> So far I found *vector-heterogenous* package, but can't decide is it good to >> build on or create something on my own. >> > Take a look at fixed-vector-hetero[1]. It's not released yet but I hope I'll get > in release ready shape by second half of December. > > It's an attepmt to provide API for working with arbitrary product types. > General idea is to work with CPS represenation of data type > > > [1] https://github.com/Shimuuar/fixed-vector-hetero I like it, I'll try to play with it for couple of days and, probably, bother you a little bit with e-mails -) From sergey.bushnyak at sigrlami.eu Mon Dec 2 03:40:50 2013 From: sergey.bushnyak at sigrlami.eu (Sergey Bushnyak) Date: Mon, 02 Dec 2013 05:40:50 +0200 Subject: [Haskell-cafe] Looking for reliable heterogeneous vectors In-Reply-To: References: <529B9804.70308@sigrlami.eu> Message-ID: <529C0142.2050904@sigrlami.eu> On 12/02/2013 03:58 AM, Mike Izbicki wrote: > Author of vector-heterogenous here. I tried to design the package to > meet use cases like you describe, but fully admit that it's not > perfect. It's missing a lot of the functions you might expect from > the regular vector package (some of them are because I didn't need > them, and some are because the best implementation is not obvious), > and syntax is still a little awkward for my tastes. > > So if you have any ideas on improvements, I'd definitely be willing to > incorporate them. Or if you have a great idea for a complete redesign > of the package, I'd be happy to replace everything and let you take over. > > On Sun, Dec 1, 2013 at 12:11 PM, Sergey Bushnyak > > wrote: > > Hello, everyone. I'm looking for reliable library or idea how to > implement heterogenous vector properly. It may seem odd, but I > want elements not only be different types but also functions, > something like that, pseudocode: > > hvec [a b (c->d) [a] ...] -- can be any type > let hvec = hvec [ "stuff" 5 getUrl [1, 4, 5]] > > So far I found *vector-heterogenous* package, but can't decide is > it good to build on or create something on my own. > > Any thoughts and ideas are appreciated. Thanks. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > Mike, thank you for quick response, nice to hear you open for improvements. I'm also looking for this kind of package to be not only heterogeneous, but immutable and persistent, which leads to higher level of abstraction, something like *collection*. It will be nice to derive different types from it, like hvector, hlist etc. I'm doing small research now, if I'll understand that it's better to build upon your library or even reshape it I'll drop you an email. -------------- next part -------------- An HTML attachment was scrubbed... URL: From mike at izbicki.me Mon Dec 2 04:52:49 2013 From: mike at izbicki.me (Mike Izbicki) Date: Sun, 1 Dec 2013 20:52:49 -0800 Subject: [Haskell-cafe] Looking for reliable heterogeneous vectors In-Reply-To: <529C0142.2050904@sigrlami.eu> References: <529B9804.70308@sigrlami.eu> <529C0142.2050904@sigrlami.eu> Message-ID: I don't understand what you mean by immutable and persistant, because vector-heterogenous is both of those! It just uses a standard boxed vector as the backend and does some unsafeCoercing to get the types to line up. On Sun, Dec 1, 2013 at 7:40 PM, Sergey Bushnyak wrote: > On 12/02/2013 03:58 AM, Mike Izbicki wrote: > > Author of vector-heterogenous here. I tried to design the package to meet > use cases like you describe, but fully admit that it's not perfect. It's > missing a lot of the functions you might expect from the regular vector > package (some of them are because I didn't need them, and some are because > the best implementation is not obvious), and syntax is still a little > awkward for my tastes. > > So if you have any ideas on improvements, I'd definitely be willing to > incorporate them. Or if you have a great idea for a complete redesign of > the package, I'd be happy to replace everything and let you take over. > > On Sun, Dec 1, 2013 at 12:11 PM, Sergey Bushnyak < > sergey.bushnyak at sigrlami.eu> wrote: > >> Hello, everyone. I'm looking for reliable library or idea how to >> implement heterogenous vector properly. It may seem odd, but I want >> elements not only be different types but also functions, something like >> that, pseudocode: >> >> hvec [a b (c->d) [a] ...] -- can be any type >> let hvec = hvec [ "stuff" 5 getUrl [1, 4, 5]] >> >> So far I found *vector-heterogenous* package, but can't decide is it good >> to build on or create something on my own. >> >> Any thoughts and ideas are appreciated. Thanks. >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > Mike, thank you for quick response, nice to hear you open for > improvements. I'm also looking for this kind of package to be not only > heterogeneous, but immutable and persistent, which leads to higher level of > abstraction, something like *collection*. It will be nice to derive > different types from it, like hvector, hlist etc. > > I'm doing small research now, if I'll understand that it's better to build > upon your library or even reshape it I'll drop you an email. > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mike at quasimal.com Mon Dec 2 06:13:34 2013 From: mike at quasimal.com (Mike Ledger) Date: Mon, 02 Dec 2013 17:13:34 +1100 Subject: [Haskell-cafe] Type-level case Message-ID: <529C250E.8020307@quasimal.com> Hi. This is more of a brain dump than anything well thought out, but it's been in the back of my mind for a while. It's occurred to me that with the upcoming release of GHC 7.8, which features closed type families, we've effectively been given type-level pattern matching that behaves the same as expression-level pattern matching. What I think could follow is type-level case syntax. For example: type family Example a where Example 100 = 60 Example 120 = 15 Example x = x * 30 contrived :: Sing a -> Sing b -> Sing (Example (a+b)) might instead be expressed as: contrived :: Sing a -> Sing b -> Sing (case a+b of 100 -> 60 120 -> 15 x -> x*30) -- but with something other than -> in the patterns, -- since that conflicts with the type (->), and there -- are probably too many arrows already Similarly I think if-then-else could be lifted to the type level, also. Some problems with this are that it could pollute "complex" type signatures even further (although currently the situation isn't very good due to haddock/ghc not listing type family instances), and it would get quite cumbersome quickly to have to type out contrived2 :: Proxy (a, b) -> Sing (case a+b of { 100 -> 60; 120 -> 15; x -> x*30 }) -> ... -- Mike From paratribulations at free.fr Mon Dec 2 18:32:25 2013 From: paratribulations at free.fr (TP) Date: Mon, 02 Dec 2013 14:32:25 -0400 Subject: [Haskell-cafe] how to factorize propagation of a function over a data type Message-ID: Hi, Let us consider the following example: ----------------------- class FooClass a where foo1 :: a -> a foo2 :: a -> a instance FooClass Integer where foo1 v = 1 foo2 v = 2 data Bar = Bar1 Integer | Exp1 Bar Bar | Exp2 Bar Bar deriving Show instance FooClass Bar where foo1 b = case b of Bar1 i -> Bar1 (foo1 i) Exp1 b1 b2 -> Exp1 (foo1 b1) (foo1 b2) Exp2 b1 b2 -> Exp2 (foo1 b1) (foo1 b2) foo2 b = case b of Bar1 i -> Bar1 (foo2 i) Exp1 b1 b2 -> Exp1 (foo2 b1) (foo2 b2) Exp2 b1 b2 -> Exp2 (foo2 b1) (foo2 b2) main = do let a = Bar1 3 let b = Bar1 4 let c = Exp1 (Exp2 a b) b print c print $ foo1 c print $ foo2 c ----------------------- We obtain as expected: $ runghc propagate_with_duplicated_code.hs Exp1 (Exp2 (Bar1 3) (Bar1 4)) (Bar1 4) Exp1 (Exp2 (Bar1 1) (Bar1 1)) (Bar1 1) Exp1 (Exp2 (Bar1 2) (Bar1 2)) (Bar1 2) My question is related to the code inside the Fooclass instance definition for Bar: we have repeated code where only "foo1" or "foo2" changes. So the first idea is to write a higher-order function, but it does not work: ----------------------- class FooClass a where foo1 :: a -> a foo2 :: a -> a instance FooClass Integer where foo1 v = 1 foo2 v = 2 data Bar = Bar1 Integer | Exp1 Bar Bar | Exp2 Bar Bar deriving Show propagate :: FooClass a => a -> (a->a) -> a propagate v f = case v of Bar1 i -> Bar1 (f i) Exp1 b1 b2 -> Exp1 (f b1) (f b2) Exp2 b1 b2 -> Exp2 (f b1) (f b2) instance FooClass Bar where foo1 b = propagate b foo1 foo2 b = propagate b foo2 main = do let a = Bar1 3 let b = Bar1 4 let c = Exp1 (Exp2 a b) b print c print $ foo1 c print $ foo2 c ----------------------- The problem is that the type variable `a` in the definition of `propagate` cannot match both the type of i, i.e. an integer, and the type of b1 and b2, i.e. Bar. Putting the function propagate in the typeclass does not help. How to factorize my code? Thanks in advance, TP From trupill at gmail.com Mon Dec 2 13:44:00 2013 From: trupill at gmail.com (Alejandro Serrano Mena) Date: Mon, 2 Dec 2013 14:44:00 +0100 Subject: [Haskell-cafe] how to factorize propagation of a function over a data type In-Reply-To: References: Message-ID: I have no time now to answer completely, but I would say that type families could help. 2013/12/2 TP > Hi, > > Let us consider the following example: > > ----------------------- > class FooClass a where > foo1 :: a -> a > foo2 :: a -> a > > instance FooClass Integer where > > foo1 v = 1 > foo2 v = 2 > > data Bar = Bar1 Integer > | Exp1 Bar Bar > | Exp2 Bar Bar > deriving Show > > instance FooClass Bar where > > foo1 b = case b of > Bar1 i -> Bar1 (foo1 i) > Exp1 b1 b2 -> Exp1 (foo1 b1) (foo1 b2) > Exp2 b1 b2 -> Exp2 (foo1 b1) (foo1 b2) > > foo2 b = case b of > Bar1 i -> Bar1 (foo2 i) > Exp1 b1 b2 -> Exp1 (foo2 b1) (foo2 b2) > Exp2 b1 b2 -> Exp2 (foo2 b1) (foo2 b2) > > main = do > > let a = Bar1 3 > let b = Bar1 4 > let c = Exp1 (Exp2 a b) b > > print c > print $ foo1 c > print $ foo2 c > ----------------------- > > We obtain as expected: > > $ runghc propagate_with_duplicated_code.hs > Exp1 (Exp2 (Bar1 3) (Bar1 4)) (Bar1 4) > Exp1 (Exp2 (Bar1 1) (Bar1 1)) (Bar1 1) > Exp1 (Exp2 (Bar1 2) (Bar1 2)) (Bar1 2) > > My question is related to the code inside the Fooclass instance definition > for Bar: we have repeated code where only "foo1" or "foo2" changes. > So the first idea is to write a higher-order function, but it does not > work: > > ----------------------- > class FooClass a where > foo1 :: a -> a > foo2 :: a -> a > > instance FooClass Integer where > > foo1 v = 1 > foo2 v = 2 > > data Bar = Bar1 Integer > | Exp1 Bar Bar > | Exp2 Bar Bar > deriving Show > > propagate :: FooClass a => a -> (a->a) -> a > propagate v f = case v of > Bar1 i -> Bar1 (f i) > Exp1 b1 b2 -> Exp1 (f b1) (f b2) > Exp2 b1 b2 -> Exp2 (f b1) (f b2) > > instance FooClass Bar where > > foo1 b = propagate b foo1 > foo2 b = propagate b foo2 > > main = do > > let a = Bar1 3 > let b = Bar1 4 > let c = Exp1 (Exp2 a b) b > > print c > print $ foo1 c > print $ foo2 c > ----------------------- > > The problem is that the type variable `a` in the definition of `propagate` > cannot match both the type of i, i.e. an integer, and the type of b1 and > b2, > i.e. Bar. > Putting the function propagate in the typeclass does not help. How to > factorize my code? > > Thanks in advance, > > TP > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From daniel.trstenjak at gmail.com Mon Dec 2 13:48:20 2013 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Mon, 2 Dec 2013 14:48:20 +0100 Subject: [Haskell-cafe] how to factorize propagation of a function over a data type In-Reply-To: References: Message-ID: <20131202134819.GA4523@machine> > class FooClass a where > foo1 :: a -> a > foo2 :: a -> a > > instance FooClass Integer where > > foo1 v = 1 > foo2 v = 2 > > data Bar = Bar1 Integer > | Exp1 Bar Bar > | Exp2 Bar Bar > deriving Show > > instance FooClass Bar where > > foo1 b = case b of > Bar1 i -> Bar1 (foo1 i) > Exp1 b1 b2 -> Exp1 (foo1 b1) (foo1 b2) > Exp2 b1 b2 -> Exp2 (foo1 b1) (foo1 b2) > > foo2 b = case b of > Bar1 i -> Bar1 (foo2 i) > Exp1 b1 b2 -> Exp1 (foo2 b1) (foo2 b2) > Exp2 b1 b2 -> Exp2 (foo2 b1) (foo2 b2) I think you're really asking for a generics library like 'uniplate': http://community.haskell.org/~ndm/darcs/uniplate/uniplate.htm Greetings, Daniel From noteed at gmail.com Mon Dec 2 13:47:33 2013 From: noteed at gmail.com (Vo Minh Thu) Date: Mon, 2 Dec 2013 14:47:33 +0100 Subject: [Haskell-cafe] how to factorize propagation of a function over a data type In-Reply-To: References: Message-ID: You can replace your `propagate` function by this one: propagate :: Bar -> (Integer -> Integer) -> Bar propagate v f = case v of Bar1 i -> Bar1 (f i) Exp1 b1 b2 -> Exp1 (propagate b1 f) (propagate b2 f) Exp2 b1 b2 -> Exp2 (propagate b1 f) (propagate b2 f) In your code, you were applying the same (w.r.t. to its type) `f` to Bar and Integer. Also, your Bar data type contains, at its leaf, an Intger, not a `a`. You might want to look at functors, and `fmap` too. 2013/12/2 TP : > Hi, > > Let us consider the following example: > > ----------------------- > class FooClass a where > foo1 :: a -> a > foo2 :: a -> a > > instance FooClass Integer where > > foo1 v = 1 > foo2 v = 2 > > data Bar = Bar1 Integer > | Exp1 Bar Bar > | Exp2 Bar Bar > deriving Show > > instance FooClass Bar where > > foo1 b = case b of > Bar1 i -> Bar1 (foo1 i) > Exp1 b1 b2 -> Exp1 (foo1 b1) (foo1 b2) > Exp2 b1 b2 -> Exp2 (foo1 b1) (foo1 b2) > > foo2 b = case b of > Bar1 i -> Bar1 (foo2 i) > Exp1 b1 b2 -> Exp1 (foo2 b1) (foo2 b2) > Exp2 b1 b2 -> Exp2 (foo2 b1) (foo2 b2) > > main = do > > let a = Bar1 3 > let b = Bar1 4 > let c = Exp1 (Exp2 a b) b > > print c > print $ foo1 c > print $ foo2 c > ----------------------- > > We obtain as expected: > > $ runghc propagate_with_duplicated_code.hs > Exp1 (Exp2 (Bar1 3) (Bar1 4)) (Bar1 4) > Exp1 (Exp2 (Bar1 1) (Bar1 1)) (Bar1 1) > Exp1 (Exp2 (Bar1 2) (Bar1 2)) (Bar1 2) > > My question is related to the code inside the Fooclass instance definition > for Bar: we have repeated code where only "foo1" or "foo2" changes. > So the first idea is to write a higher-order function, but it does not work: > > ----------------------- > class FooClass a where > foo1 :: a -> a > foo2 :: a -> a > > instance FooClass Integer where > > foo1 v = 1 > foo2 v = 2 > > data Bar = Bar1 Integer > | Exp1 Bar Bar > | Exp2 Bar Bar > deriving Show > > propagate :: FooClass a => a -> (a->a) -> a > propagate v f = case v of > Bar1 i -> Bar1 (f i) > Exp1 b1 b2 -> Exp1 (f b1) (f b2) > Exp2 b1 b2 -> Exp2 (f b1) (f b2) > > instance FooClass Bar where > > foo1 b = propagate b foo1 > foo2 b = propagate b foo2 > > main = do > > let a = Bar1 3 > let b = Bar1 4 > let c = Exp1 (Exp2 a b) b > > print c > print $ foo1 c > print $ foo2 c > ----------------------- > > The problem is that the type variable `a` in the definition of `propagate` > cannot match both the type of i, i.e. an integer, and the type of b1 and b2, > i.e. Bar. > Putting the function propagate in the typeclass does not help. How to > factorize my code? > > Thanks in advance, > > TP > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From paratribulations at free.fr Mon Dec 2 19:37:14 2013 From: paratribulations at free.fr (TP) Date: Mon, 02 Dec 2013 15:37:14 -0400 Subject: [Haskell-cafe] how to factorize propagation of a function over a data type References: Message-ID: Vo Minh Thu wrote: > You can replace your `propagate` function by this one: > > propagate :: Bar -> (Integer -> Integer) -> Bar > propagate v f = case v of > Bar1 i -> Bar1 (f i) > Exp1 b1 b2 -> Exp1 (propagate b1 f) (propagate b2 f) > Exp2 b1 b2 -> Exp2 (propagate b1 f) (propagate b2 f) > > In your code, you were applying the same (w.r.t. to its type) `f` to > Bar and Integer. > Also, your Bar data type contains, at its leaf, an Intger, not a `a`. You are right, I made a stupid error in my code. The following version indeed works: ---------------- class FooClass a where foo1 :: a -> a foo2 :: a -> a instance FooClass Integer where foo1 v = 1 foo2 v = 2 data Bar = Bar1 Integer | Exp1 Bar Bar | Exp2 Bar Bar deriving Show -- The following line works because there are only integers in the leaves. propagate :: Bar -> (Integer -> Integer) -> Bar propagate v f = case v of Bar1 i -> Bar1 (f i) Exp1 b1 b2 -> Exp1 (propagate b1 f) (propagate b2 f) Exp2 b1 b2 -> Exp2 (propagate b1 f) (propagate b2 f) instance FooClass Bar where foo1 b = propagate b foo1 foo2 b = propagate b foo2 main = do let a = Bar1 3 let b = Bar1 4 let c = Exp1 (Exp2 a b) b print c print $ foo1 c print $ foo2 c ---------------- However, if we add another type in the leaves, we cannot use the solution above. ---------------- class FooClass a where foo1 :: a -> a foo2 :: a -> a instance FooClass Integer where foo1 v = 1 foo2 v = 2 instance FooClass Float where foo1 v = 0.25 foo2 v = 0.5 data Bar = Bar1 Integer | Bar2 Float | Exp1 Bar Bar | Exp2 Bar Bar deriving Show -- This time the following line does not work. propagate :: Bar -> (Integer -> Integer) -> Bar -- The following line does not work either. -- propagate :: FooClass a => Bar -> (a->a) -> Bar propagate v f = case v of Bar1 i -> Bar1 (f i) Bar2 i -> Bar2 (f i) Exp1 b1 b2 -> Exp1 (propagate b1 f) (propagate b2 f) Exp2 b1 b2 -> Exp2 (propagate b1 f) (propagate b2 f) instance FooClass Bar where foo1 b = propagate b foo1 foo2 b = propagate b foo2 main = do let a = Bar1 3 let b = Bar1 4 let c = Exp1 (Exp2 a b) b print c print $ foo1 c print $ foo2 c ---------------- From s.j.thompson at kent.ac.uk Mon Dec 2 15:25:50 2013 From: s.j.thompson at kent.ac.uk (Simon Thompson) Date: Mon, 2 Dec 2013 15:25:50 +0000 Subject: [Haskell-cafe] Call for Papers: 15th Symposium on Trends in Functional Programming, May 2014, Utrecht Message-ID: <79A3CECD-0C9C-4006-A831-8DE42D96DBD6@kent.ac.uk> ----------------------------- C A L L F O R P A P E R S ----------------------------- ======== TFP 2014 =========== 15th Symposium on Trends in Functional Programming May 26-28, 2014 Utrecht University Soesterberg, The Netherlands http://www.cs.uu.nl/wiki/TFP2014/WebHome The symposium on Trends in Functional Programming (TFP) is an international forum for researchers with interests in all aspects of functional programming, taking a broad view of current and future trends in the area. It aspires to be a lively environment for presenting the latest research results, and other contributions (see below), described in draft papers submitted prior to the symposium. A formal post-symposium refereeing process then selects a subset of the articles presented at the symposium and submitted for formal publication. Selected papers will be published as a Springer Lecture Notes in Computer Science (LNCS) volume. TFP 2014 will be the main event of a pair of functional programming events. The other is the International Workshop on Trends in Functional Programming in Education (TFPIE). TFPIE will take place on May 25th. The TFP symposium is the heir of the successful series of Scottish Functional Programming Workshops. Previous TFP symposia were held in Edinburgh (Scotland) in 2003, in Munich (Germany) in 2004, in Tallinn (Estonia) in 2005, in Nottingham (UK) in 2006, in New York (USA) in 2007, in Nijmegen (The Netherlands) in 2008, in Komarno (Slovakia) in 2009, in Oklahoma (USA) in 2010, in Madrid (Spain) in 2011, St. Andrews (UK) in 2012 and Provo (Utah, USA) in 2013. For further general information about TFP please see the TFP homepage. INVITED SPEAKERS TFP is pleased to announce talks by the following two invited speakers: John Hughes of Chalmers, Goteborg, Sweden, is well-known as author of Why Functional Programming Matters, and as one of the designers of QuickCheck (together with Koen Claessen); the paper on QuickCheck won the ICFP Most Influential Paper Award in 2010. Currently he divides his time between his professorship and Quviq, a company that performs property-based testing of software with a tool implemented in Erlang. Dr. Geoffrey Mainland received his PhD from Harvard University where he was advised by Greg Morrisett and Matt Welsh. After a two year postdoc with the Programming Principles and Tools group at Microsoft Research Cambridge, he is now an assistant professor at Drexel University. His research focuses on high-level programming language and runtime support for non-general purpose computation. SCOPE The symposium recognizes that new trends may arise through various routes. As part of the Symposium's focus on trends we therefore identify the following five article categories. High-quality articles are solicited in any of these categories: Research Articles: leading-edge, previously unpublished research work Position Articles: on what new trends should or should not be Project Articles: descriptions of recently started new projects Evaluation Articles: what lessons can be drawn from a finished project Overview Articles: summarizing work with respect to a trendy subject Articles must be original and not submitted for simultaneous publication to any other forum. They may consider any aspect of functional programming: theoretical, implementation-oriented, or more experience-oriented. Applications of functional programming techniques to other languages are also within the scope of the symposium. Topics suitable for the symposium include: Functional programming and multicore/manycore computing Functional programming in the cloud High performance functional computing Extra-functional (behavioural) properties of functional programs Dependently typed functional programming Validation and verification of functional programs Using functional techniques to reason about imperative/object-oriented programs Debugging for functional languages Functional programming in different application areas: security, mobility, telecommunications applications, embedded systems, global computing, grids, etc. Interoperability with imperative programming languages Novel memory management techniques Program analysis and transformation techniques Empirical performance studies Abstract/virtual machines and compilers for functional languages (Embedded) domain specific languages New implementation strategies Any new emerging trend in the functional programming area If you are in doubt on whether your article is within the scope of TFP, please contact the TFP 2014 program chair, Jurriaan Hage at J.Hage at uu.nl. BEST PAPER AWARDS To reward excellent contributions, TFP awards a prize for the best paper accepted for the formal proceedings. TFP traditionally pays special attention to research students, acknowledging that students are almost by definition part of new subject trends. A student paper is one for which the authors state that the paper is mainly the work of students, the students are listed as first authors, and a student would present the paper. A prize for the best student paper is awarded each year. In both cases, it is the PC of TFP that awards the prize. In case the best paper happens to be a student paper, that paper will then receive both prizes. SPONSORS TFP is financially supported by NWO (Netherlands Organisation for Scientific Research), Well-Typed and Erlang Solutions. PAPER SUBMISSIONS Acceptance of articles for presentation at the symposium is based on a lightweight peer review process of extended abstracts (4 to 10 pages in length) or full papers (16 pages). The submission must clearly indicate which category it belongs to: research, position, project, evaluation, or overview paper. It should also indicate whether the main author or authors are research students. In the case of a full student paper, the paper will receive additional feedback by one of the PC members shortly after the symposium has taken place. We shall use EasyChair for the refereeing process. IMPORTANT DATES Submission of draft papers: March 17, 2014 Notification: March 24, 2014 Registration: April 7, 2014 TFP Symposium: May 26-28, 2014 Student papers feedback: June 9th, 2014 Submission for formal review: July 1st, 2014 Notification of acceptance: September 8th, 2014 Camera ready paper: October 8th, 2014 PROGRAM COMMITTEE Peter Achten Radboud University Nijmegen Emil Axelsson Chalmers Lucilia Camarao de Figueiredo Universidade Federal de Ouro Preto Laura Castro University of A Coruna Frank Huch Christian-Albrechts-University of Kiel Matthew Fluet Rochester Institute of Technology Jurriaan Hage (chair) University of Utrecht Yukiyoshi Kameyama University of Tsukuba Andrew Kennedy Microsoft Research Tamas Kozsik Eotvos Lorand University Ben Lippmeier University of New South Wales Luc Maranget INRIA Jay McCarthy Brigham Young University Marco T. Morazan Seton Hall University Ricardo Pena Universidad Complutense de Madrid Alexey Rodriguez madvertise Sven-Bodo Scholz Heriot-Watt University Manuel Serrano INRIA Sophia Antipolis Simon Thompson University of Kent Tarmo Uustalu Inst of Cybernetics David Van Horn Maryland University Janis Voigtlaender University of Bonn Simon Thompson | Professor of Logic and Computation School of Computing | University of Kent | Canterbury, CT2 7NF, UK s.j.thompson at kent.ac.uk | M +44 7986 085754 | W www.cs.kent.ac.uk/~sjt From 0slemi0 at gmail.com Mon Dec 2 16:21:25 2013 From: 0slemi0 at gmail.com (Andras Slemmer) Date: Mon, 2 Dec 2013 16:21:25 +0000 Subject: [Haskell-cafe] how to factorize propagation of a function over a data type In-Reply-To: References: Message-ID: There are several ways to approach this problem. What you are basically trying to do is map a function over the leaves of your datastructure. So naturally a function that comes to mind is: mapBar :: (Integer -> Integer) -> (Float -> Float) -> Bar -> Bar mapBar f _ (Bar1 i) = Bar1 (f i) mapBar _ g (Bar2 r) = Bar2 (g r) mapBar f g (Exp1 e1 e2) = Exp1 (mapBar f g e1) (mapBar f g e2) mapBar f g (Exp2 e1 e2) = Exp2 (mapBar f g e1) (mapBar f g e2) And the Bar instance becomes instance FooClass Bar where foo1 = mapBar foo1 foo1 foo2 = mapBar foo2 foo2 As far as I understand this is not what you're looking for, as you want the mapBar function to be agnostic wrt what type the leaves contain. The minimal assumption that this requires is that the leaf types are a member of FooClass, and indeed you can write such a map: mapBar :: (forall a. FooClass a => a -> a) -> Bar -> Bar mapBar f (Bar1 i) = Bar1 (f i) mapBar f (Bar2 r) = Bar2 (f r) mapBar f (Exp1 e1 e2) = Exp1 (mapBar f e1) (mapBar f e2) mapBar f (Exp2 e1 e2) = Exp2 (mapBar f e1) (mapBar f e2) instance FooClass Bar where foo1 = mapBar foo1 foo2 = mapBar foo2 I think this is closer to what you were looking for. The above map requires -XRankNTypes, because mapBar requires a function that is fully polymorphic ('a' will instantiate to Integer and Float respectively). If you haven't used higher ranked types before I think it is instructive to think about why the above signature works and the one you wrote doesn't. In particular think about at which point the polymorphic type 'a' is instantiated in both cases, or rather what the "scope" of 'a' is. On 2 December 2013 19:37, TP wrote: > Vo Minh Thu wrote: > > > You can replace your `propagate` function by this one: > > > > propagate :: Bar -> (Integer -> Integer) -> Bar > > propagate v f = case v of > > Bar1 i -> Bar1 (f i) > > Exp1 b1 b2 -> Exp1 (propagate b1 f) (propagate b2 f) > > Exp2 b1 b2 -> Exp2 (propagate b1 f) (propagate b2 f) > > > > In your code, you were applying the same (w.r.t. to its type) `f` to > > Bar and Integer. > > Also, your Bar data type contains, at its leaf, an Intger, not a `a`. > > You are right, I made a stupid error in my code. The following version > indeed works: > > ---------------- > class FooClass a where > foo1 :: a -> a > foo2 :: a -> a > > instance FooClass Integer where > > foo1 v = 1 > foo2 v = 2 > > data Bar = Bar1 Integer > | Exp1 Bar Bar > | Exp2 Bar Bar > deriving Show > > -- The following line works because there are only integers in the leaves. > propagate :: Bar -> (Integer -> Integer) -> Bar > propagate v f = case v of > Bar1 i -> Bar1 (f i) > Exp1 b1 b2 -> Exp1 (propagate b1 f) (propagate b2 f) > Exp2 b1 b2 -> Exp2 (propagate b1 f) (propagate b2 f) > > instance FooClass Bar where > > foo1 b = propagate b foo1 > foo2 b = propagate b foo2 > > main = do > > let a = Bar1 3 > let b = Bar1 4 > let c = Exp1 (Exp2 a b) b > > print c > print $ foo1 c > print $ foo2 c > ---------------- > > However, if we add another type in the leaves, we cannot use the solution > above. > > ---------------- > class FooClass a where > foo1 :: a -> a > foo2 :: a -> a > > instance FooClass Integer where > > foo1 v = 1 > foo2 v = 2 > > instance FooClass Float where > > foo1 v = 0.25 > foo2 v = 0.5 > > data Bar = Bar1 Integer > | Bar2 Float > | Exp1 Bar Bar > | Exp2 Bar Bar > deriving Show > > -- This time the following line does not work. > propagate :: Bar -> (Integer -> Integer) -> Bar > -- The following line does not work either. > -- propagate :: FooClass a => Bar -> (a->a) -> Bar > propagate v f = case v of > Bar1 i -> Bar1 (f i) > Bar2 i -> Bar2 (f i) > Exp1 b1 b2 -> Exp1 (propagate b1 f) (propagate b2 f) > Exp2 b1 b2 -> Exp2 (propagate b1 f) (propagate b2 f) > > instance FooClass Bar where > > foo1 b = propagate b foo1 > foo2 b = propagate b foo2 > > main = do > > let a = Bar1 3 > let b = Bar1 4 > let c = Exp1 (Exp2 a b) b > > print c > print $ foo1 c > print $ foo2 c > ---------------- > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From eir at cis.upenn.edu Mon Dec 2 16:48:56 2013 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Mon, 2 Dec 2013 11:48:56 -0500 Subject: [Haskell-cafe] Return of the revenge of the revisit of the extensible records, reiterated In-Reply-To: References: Message-ID: A few reactions to this thread, in no particular order: - Atze, thanks for doing this work! Powering extensible records was one of the use cases I had for closed type families in the back of my head, and I'm glad someone is going ahead with this! - Closed type families, as implemented, do nothing to help with error messages that are produced by missing instances (class or type family) or missing equations of a closed type family. For a type family, if no instances/equations are applicable, the use of the type family is "stuck" -- it doesn't reduce. Detecting stuckness using an in-language mechanism risks type safety, because stuckness might change either with type improvement or (in the case of open families) by the inclusion of another module. - It is conceivable that further work can make closed type families better in this regard. For example, I could imagine a check on the use site of a closed type family that could tell that the use would *never* reduce, regardless of any type improvement that might take place. I can also imagine implementing a customizable error message to use in that case. However, these additions aren't on my current docket of work. I'd be happy to point the way forward to someone else who is interested! - I don't see how disequality guards would help with error messages. - The notion of "competing instances" for type families sounds somewhat like delayed overlap checks for class instances. For example, consider these definitions: > module A where > type instance F a b c | b /~ c = Int > module B where > import A > type instance F a b c | a /~ c = Bool Questions: 1. Are these instances overlapping? 2. How does `F Int Bool Char` reduce when written in module A? 3. How does `F Int Bool Char` reduce when written in module B? Pondering the answers to these questions makes me doubt this approach. On the other hand, perhaps we could require that all instances of a type family that have disequality guards are given in the same module. Then, the reduction of something like `F Int Bool Int` is hard to figure out. In short, I'm not sure what is gained by this approach. (Disclaimer: it is easy enough to find very counter-intuitive examples using closed type families as implemented. I ask these questions more to ponder what an alternative might look like than to say that closed type families are perfect.) - While I agree that closed type families don't fit as well with the mental model of competing instances, I believe they work better with programmers' sensibilities at the term level. One could argue which is better to aim for. - Banning instance overlap that is currently permitted would break existing code. Is this a big enough wart to incite a breaking change? Also, what would happen if two different packages define instances (mainly for internal use) that conflict? These instances would necessarily be orphans. Could these packages then be used together? Perhaps this case never comes up in practice, but it would worry me. Richard On Nov 28, 2013, at 12:32 AM, AntC wrote: >> adam vogt gmail.com> writes: >> >>> On Wed, Nov 27, 2013 at 9:22 PM, AntC wrote: >> >> Closed type families ... wait a few weeks for ghc-7.8) >> > > Yes, I'm in eager anticipation! > >>> ... >>> OTOH, I did feed raise that unhappy hack with Richard >>> at the time, as a counter-example >>> that I couldn't understand how he'd handle. >>> So perhaps he didn't.) >> >> Do you recall where that discussion was? > > http://typesandkinds.wordpress.com/2013/04/29/coincident-overlap-in-type- > families/ > My message on June 24. (It also mentions discussion on GHC-Users.) > > This is exactly an example of a records mechanism with duplicate 'labels'. > Actually being what the HList paper calls Type-Indexed Products. > > Note that the code I give there works beautifully with old-fashioned > overlapping instances; and produces a helpful error message without any > additional ancillary Fail classes. > > It works because my records are tuples, _not_ HLists. > So instance resolution is working with a 'flat' structure where it can see > all the types. Contrast that HCons effectively hides types in its tail. > I suspect that Richard's implementation also effectively hides potential > duplicates by putting them in a later 'case' of the type family. > >> ... Though it seems ghc isn't eager enough ... > > This is what I find most frustrating with ghc (as contrasted with dear old > Hugs): instance failures are 'lazy'. You have to backtrack through a lot > of code/other modules to figure out what's going wrong. > > I was hoping that with Richard's work, instance validation could be eager: > reject the instance definition as overlapping _at_the_point_of_definition_. > > I think that a long time ago ghc took a wrong turn and allowed partially > overlapping instances. It therefore has to wait until it finds a usage to > see if it is actually ambiguous. > > I think that partially overlapping instances should be banned. > Instances should be either disjunctive or wholly overlapping. > (Note that you can always reorganise a partial overlap to fit this rule.) > >> ... >> Which translates to >> >> type family G' x y where >> G' x x = Failure "mistake" () >> G' x y = () > > That's exactly the unhappy hack I was wanting to avoid. > If you still have to do that with closed type families, > then I'm disappointed. > > I wanted disequality restraints. > (See the Sulzmann and Stuckey paper I mention earlier on Richard's > discussion page.) > > Which would be one single stand-alone instance: > > type instance G'' x y | x /~ y = () > > (I also think this has more perspicuous type inference rules, > and fits better with a mental model of all the instances 'competing' to be > chosen at the use site; with type improvement progressing until exactly > one matches. This does not involve instance search, which as SPJ points > out would be death to coherence.) > > Cheers > AntC > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From paratribulations at free.fr Mon Dec 2 22:01:29 2013 From: paratribulations at free.fr (TP) Date: Mon, 02 Dec 2013 18:01:29 -0400 Subject: [Haskell-cafe] how to factorize propagation of a function over a data type References: Message-ID: Andras Slemmer wrote: > As far as I understand this is not what you're looking for, as you want > the mapBar function to be agnostic wrt what type the leaves contain. The > minimal assumption that this requires is that the leaf types are a member > of FooClass, and indeed you can write such a map: > > mapBar :: (forall a. FooClass a => a -> a) -> Bar -> Bar > mapBar f (Bar1 i) = Bar1 (f i) > mapBar f (Bar2 r) = Bar2 (f r) > mapBar f (Exp1 e1 e2) = Exp1 (mapBar f e1) (mapBar f e2) > mapBar f (Exp2 e1 e2) = Exp2 (mapBar f e1) (mapBar f e2) > > instance FooClass Bar where > foo1 = mapBar foo1 > foo2 = mapBar foo2 > > I think this is closer to what you were looking for. The above map > requires -XRankNTypes, because mapBar requires a function that is fully > polymorphic ('a' will instantiate to Integer and Float respectively). If > you haven't used higher ranked types before I think it is instructive to > think about why the above signature works and the one you wrote doesn't. > In particular think about at which point the polymorphic type 'a' is > instantiated in both cases, or rather what the "scope" of 'a' is. Thanks a lot. This solution has already been proposed to me in the afternoon by JC Mincke in a private communication. Indeed I did not know RankNTypes. I think I understand your explanation in terms of "scope" of 'a': In the type signature propagate :: (FooClass a)=> Bar -> (a->a) -> Bar which is in fact implicitly propagate :: forall a. (FooClass a)=> Bar -> (a->a) -> Bar it is supposed that the type signature of propagate is valid for a given value of the type variable a, i.e. a given type. Thus we obtain an error if we apply recursively propagate to different types in the code of propagate. Whereas in the type signature propagate :: Bar -> (forall a. (FooClass a) => a->a) -> Bar the type signature of propagate is such that it allows several values for the type variable `a` in its second argument `a->a`. PS: a working code corresponding to my last example: ------------- {-# LANGUAGE RankNTypes #-} class FooClass a where foo1 :: a -> a foo2 :: a -> a instance FooClass Integer where foo1 v = 1 foo2 v = 2 instance FooClass Float where foo1 v = 0.25 foo2 v = 0.5 data Bar = Bar1 Integer | Bar2 Float | Exp1 Bar Bar | Exp2 Bar Bar deriving Show propagate :: Bar -> (forall a. (FooClass a) => a->a) -> Bar propagate v f = case v of Bar1 i -> Bar1 (f i) Bar2 fl -> Bar2 (f fl) Exp1 b1 b2 -> Exp1 (propagate b1 f) (propagate b2 f) Exp2 b1 b2 -> Exp2 (propagate b1 f) (propagate b2 f) -- The two previous lines may be replaced by: -- Exp1 b1 b2 -> Exp1 (f b1) (f b2) -- Exp2 b1 b2 -> Exp2 (f b1) (f b2) instance FooClass Bar where foo1 b = propagate b foo1 foo2 b = propagate b foo2 main = do let a = Bar1 3 let b = Bar1 4 let c = Bar2 0.4 let d = Exp1 (Exp2 a c) b print d print $ foo1 d print $ foo2 d --------------- From paratribulations at free.fr Mon Dec 2 22:07:28 2013 From: paratribulations at free.fr (TP) Date: Mon, 02 Dec 2013 18:07:28 -0400 Subject: [Haskell-cafe] existential quantification Message-ID: <0suuma-i57.ln1@rama.universe> Hi everybody, I try to understand existential quantification. I have two questions. 1/ I have just read the answer of yairchu at http://stackoverflow.com/questions/3071136/what-does-the-forall-keyword-in-haskell-ghc-do He writes: """ So with Existential-Quantification, foralls in data definitions mean that, the value contained *can* be of *any* suitable type, not that it *must* be of *all* suitable types. """ This made me think to an error I obtained with the code: --------------- test :: Show s => s test = "foobar" --------------- The error is: Could not deduce (s ~ [Char]) from the context (Show s) bound by the type signature for test :: Show s => s [...] `s' is a rigid type variable bound by the type signature for test :: Show s => s Indeed, `test :: Show s => s` means "for any type s which is an instance of Show, test is a value of that type s". But for example "foobar" can't be an Int that is an instance of Show, so it yields an error. By comparison, --------------- test :: Num a => a test = 42 --------------- works because 42 can be a value of type Int or Integer or Float or anything else that is an instance of Num. So I thought that by using existential quantification, the first example could work: --------------- {-# LANGUAGE ExistentialQuantification #-} test :: forall s . Show s => s test = "asd" --------------- But I obtain the same error, why? 2/ Is the notion of existential type related in some way to the classical mathematical quantifier "?" (Unicode symbol U+2203: "There exists")? If yes, then why using "forall" for an "existential type"? At the following address http://www.haskell.org/ghc/docs/6.12.1/html/users_guide/data-type-extensions.html#existential we read """ 7.4.4.1. Why existential? What has this to do with existential quantification? Simply that MkFoo has the (nearly) isomorphic type MkFoo :: (exists a . (a, a -> Bool)) -> Foo But Haskell programmers can safely think of the ordinary universally quantified type given above, thereby avoiding adding a new existential quantification construct. """ But I don't understand the explanation. Thanks in advance, TP From paratribulations at free.fr Mon Dec 2 22:28:07 2013 From: paratribulations at free.fr (TP) Date: Mon, 02 Dec 2013 18:28:07 -0400 Subject: [Haskell-cafe] how to factorize propagation of a function over a data type References: Message-ID: TP wrote: > propagate :: Bar -> (forall a. (FooClass a) => a->a) -> Bar In fact, I do not understand why we have to add the typeclass constraint (FooClass a). Indeed, there is no mention to foo1 and foo2 functions (members of the FooClass typeclass) in the code of propagate: ------- propagate v f = case v of Bar1 i -> Bar1 (f i) Exp1 b1 b2 -> Exp1 (propagate b1 f) (propagate b2 f) Exp2 b1 b2 -> Exp2 (propagate b1 f) (propagate b2 f) ------- propagate deals with any function a priori, not only foo1 and foo2. So how to understand the need for this typeclass constraint? TP From allbery.b at gmail.com Mon Dec 2 17:33:48 2013 From: allbery.b at gmail.com (Brandon Allbery) Date: Mon, 2 Dec 2013 12:33:48 -0500 Subject: [Haskell-cafe] existential quantification In-Reply-To: <0suuma-i57.ln1@rama.universe> References: <0suuma-i57.ln1@rama.universe> Message-ID: On Mon, Dec 2, 2013 at 5:07 PM, TP wrote: > --------------- > test :: Show s => s > test = "foobar" > --------------- > > The error is: > > Could not deduce (s ~ [Char]) > from the context (Show s) > bound by the type signature for test :: Show s => s > [...] > `s' is a rigid type variable bound by > the type signature for test :: Show s => s > > Indeed, `test :: Show s => s` means "for any type s which is an instance of > Show, test is a value of that type s". But for example "foobar" can't be an > Int that is an instance of Show, so it yields an error. > (...) > So I thought that by using existential quantification, the first example > could work: > > --------------- > {-# LANGUAGE ExistentialQuantification #-} > > test :: forall s . Show s => s > test = "asd" > --------------- > This is actually the same as the first one; top level type variables (that is, outside of parentheses) are always `forall`. And just tossing a `forall` in there does not mean you can claim to be any type and then force a `String` down the caller's throat. Which brings us to what is *really* going on. When you write test :: Show s => s you are saying exactly and only this: Any function that calls me can request *any* type that has an instance of Show, and I will give them *that type*. It still means that if you add an explicit `forall`. It does not, nor can it be forced to mean, that you will only ever give them a String. Likewise, it does not, nor can it be forced to mean, that you can pick a different type based on (the value of a function parameter, the value of an environment variable, the phase of the moon). Haskell does not use an OO type system; there is no java.lang.Object that can be every possible type, and `forall` does not create one. You cannot represent in Haskell the kind of type that you are trying to write. (There is something you can do that is almost the same, but requires a constraint and can only represent monomorphic types. And *still* does not give you java.lang.Object; it gives you a thing which has a specific type and "contains" a thing with another specific type, but can be queried about what that type is and can be extracted *only* in a context that requires that type.) When `forall` is useful is inside parentheses in a type. I am not sure that I can provide a useful example that I can explain meaningfully until you understand the above. (But others here probably can....) > 2/ > Is the notion of existential type related in some way to the classical > mathematical quantifier "?" (Unicode symbol U+2203: "There exists")? > If yes, then why using "forall" for an "existential type"? > Because "there exists" and "for all" are related by DeMorgan's rule (think about it), and "for all" is easier to represent in GHC's type machinery. I believe UHC provides an "exists" type quantifier as well as "forall". But Haskell programmers can safely think of the ordinary universally > quantified type given above, thereby avoiding adding a new existential > quantification construct. > """ > > But I don't understand the explanation. > "You don't have to keep two different kinds of quantification in mind, or figure out how they interact with each other and non-quantified types, since you can write one in terms of the other." -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From miguelimo38 at yandex.ru Mon Dec 2 17:47:12 2013 From: miguelimo38 at yandex.ru (MigMit) Date: Mon, 2 Dec 2013 21:47:12 +0400 Subject: [Haskell-cafe] existential quantification In-Reply-To: <0suuma-i57.ln1@rama.universe> References: <0suuma-i57.ln1@rama.universe> Message-ID: <0CE80B54-4D7D-4EAB-B160-E2C04F36C18C@yandex.ru> There is just one place where "forall" means "any suitable type", and that's in "data" (or "newtype") declaration, BEFORE the data constructor. Like this: newtype T = forall s. Show s => T s Then you can have test :: T test = T "foobar". If "forall" is AFTER the data constructor, it means that the value should have ALL suitable types simultaniously. Like this: data T = T (forall s. Show s => s). Then you CAN'T have test = T "foobar" because "foobar" has only one type, String; it's not polymorphic. On the other hand, if you happen to have a value of type T, you can treat the value inside it as a value of any suitable type, like this: baz :: T -> String baz (T s) = s Same thing happens if you use "forall" without defining a new type, like test :: forall s => Show s => s It differs from the previous example just by one level of indirection, that's all. On 03 Dec 2013, at 02:07, TP wrote: > Hi everybody, > > > I try to understand existential quantification. I have two questions. > > 1/ I have just read the answer of yairchu at > > http://stackoverflow.com/questions/3071136/what-does-the-forall-keyword-in-haskell-ghc-do > > He writes: > > """ > So with Existential-Quantification, foralls in data definitions mean that, > the value contained *can* be of *any* suitable type, not that it *must* be > of *all* suitable types. > """ > > This made me think to an error I obtained with the code: > --------------- > test :: Show s => s > test = "foobar" > --------------- > > The error is: > > Could not deduce (s ~ [Char]) > from the context (Show s) > bound by the type signature for test :: Show s => s > [...] > `s' is a rigid type variable bound by > the type signature for test :: Show s => s > > Indeed, `test :: Show s => s` means "for any type s which is an instance of > Show, test is a value of that type s". But for example "foobar" can't be an > Int that is an instance of Show, so it yields an error. > By comparison, > > --------------- > test :: Num a => a > test = 42 > --------------- > > works because 42 can be a value of type Int or Integer or Float or anything > else that is an instance of Num. > So I thought that by using existential quantification, the first example > could work: > > --------------- > {-# LANGUAGE ExistentialQuantification #-} > > test :: forall s . Show s => s > test = "asd" > --------------- > > But I obtain the same error, why? > > 2/ > Is the notion of existential type related in some way to the classical > mathematical quantifier "?" (Unicode symbol U+2203: "There exists")? > If yes, then why using "forall" for an "existential type"? > > At the following address > > http://www.haskell.org/ghc/docs/6.12.1/html/users_guide/data-type-extensions.html#existential > > we read > > """ > 7.4.4.1. Why existential? > > What has this to do with existential quantification? Simply that MkFoo has > the (nearly) isomorphic type > > MkFoo :: (exists a . (a, a -> Bool)) -> Foo > > But Haskell programmers can safely think of the ordinary universally > quantified type given above, thereby avoiding adding a new existential > quantification construct. > """ > > But I don't understand the explanation. > > Thanks in advance, > > TP > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From 0slemi0 at gmail.com Mon Dec 2 19:11:29 2013 From: 0slemi0 at gmail.com (Andras Slemmer) Date: Mon, 2 Dec 2013 19:11:29 +0000 Subject: [Haskell-cafe] how to factorize propagation of a function over a data type In-Reply-To: References: Message-ID: The reason you need the typeclass constraint is not in the use of 'f' but rather in the use of propagate and what you pass in to it (foo1/foo2 here). If you leave away the typeclass constraint what you're left with is: propagate' Bar -> (forall a. a->a) -> Bar The implementation of this function is the same as before, however your use of propagate' is restricted: forall a. a->a is a very "strict" type, in fact the only inhabitant of this type is 'id' (and bottom, but disregard that here), which means the only way to call propagate is to pass in 'id'. Try it yourself! Related note: there is a proof that in fact the only inhabitant of (forall a. a -> a) is 'id' and it is the consequence of the "parametricity" property. It is a very neat result I suggest you look it up! On 2 December 2013 22:28, TP wrote: > TP wrote: > > > propagate :: Bar -> (forall a. (FooClass a) => a->a) -> Bar > > In fact, I do not understand why we have to add the typeclass constraint > (FooClass a). > Indeed, there is no mention to foo1 and foo2 functions (members of the > FooClass typeclass) in the code of propagate: > > ------- > propagate v f = case v of > Bar1 i -> Bar1 (f i) > Exp1 b1 b2 -> Exp1 (propagate b1 f) (propagate b2 f) > Exp2 b1 b2 -> Exp2 (propagate b1 f) (propagate b2 f) > ------- > > propagate deals with any function a priori, not only foo1 and foo2. So how > to understand the need for this typeclass constraint? > > TP > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From 0slemi0 at gmail.com Mon Dec 2 19:50:36 2013 From: 0slemi0 at gmail.com (Andras Slemmer) Date: Mon, 2 Dec 2013 19:50:36 +0000 Subject: [Haskell-cafe] existential quantification In-Reply-To: <0suuma-i57.ln1@rama.universe> References: <0suuma-i57.ln1@rama.universe> Message-ID: Just expanding on Brandon's answer: DeMorgan's law he's referring to goes like this: ?a.P(a) === ??a.?P(a) where 'a' is a sentence, so P is second order A special case of this is this: ?a.(R(a) -> Q) === ??a.?(R(a) -> Q) === ??a.(R(a)??Q) === ?((?a.R(a))??Q) === (?a.R(a)) -> Q (i added extra parantheses for emphasis) So what does this mean in terms of haskell? R(a) is your data definition's "body", and Q is the type you are defining. On the lhs the universally quantified version gives you the type of the constuctor you're defining, and on the rhs the existential tells you what you're constructing the type with. Or in other words the universal version says: For any 'a' give me an R(a) and i'll give you back a Q. The existential version says: If you have some 'a' for which R(a) i'll give you back a Q. (It's hard to phrase the difference without sounding stupid, they are equivalent after all). There are of course other considerations, for example introducing 'exists' would mean another keyword in the syntax. Having said that I think that the choice of 'forall' for -XExistentialQuantification is wrong, as the data body defines the type you're constructing with, not the type of the whole constructor. HOWEVER for -XGADTs forall makes perfect sense. Compare the following: data AnyType = forall a. AnyType a data AnyType where AnyType :: forall a. a -> AnyType These two definitions are operationally identical, but I think the GADT way is the one that actually corresponds to the DeMorgan law. On 2 December 2013 22:07, TP wrote: > Hi everybody, > > > I try to understand existential quantification. I have two questions. > > 1/ I have just read the answer of yairchu at > > > http://stackoverflow.com/questions/3071136/what-does-the-forall-keyword-in-haskell-ghc-do > > He writes: > > """ > So with Existential-Quantification, foralls in data definitions mean that, > the value contained *can* be of *any* suitable type, not that it *must* be > of *all* suitable types. > """ > > This made me think to an error I obtained with the code: > --------------- > test :: Show s => s > test = "foobar" > --------------- > > The error is: > > Could not deduce (s ~ [Char]) > from the context (Show s) > bound by the type signature for test :: Show s => s > [...] > `s' is a rigid type variable bound by > the type signature for test :: Show s => s > > Indeed, `test :: Show s => s` means "for any type s which is an instance of > Show, test is a value of that type s". But for example "foobar" can't be an > Int that is an instance of Show, so it yields an error. > By comparison, > > --------------- > test :: Num a => a > test = 42 > --------------- > > works because 42 can be a value of type Int or Integer or Float or anything > else that is an instance of Num. > So I thought that by using existential quantification, the first example > could work: > > --------------- > {-# LANGUAGE ExistentialQuantification #-} > > test :: forall s . Show s => s > test = "asd" > --------------- > > But I obtain the same error, why? > > 2/ > Is the notion of existential type related in some way to the classical > mathematical quantifier "?" (Unicode symbol U+2203: "There exists")? > If yes, then why using "forall" for an "existential type"? > > At the following address > > > http://www.haskell.org/ghc/docs/6.12.1/html/users_guide/data-type-extensions.html#existential > > we read > > """ > 7.4.4.1. Why existential? > > What has this to do with existential quantification? Simply that MkFoo has > the (nearly) isomorphic type > > MkFoo :: (exists a . (a, a -> Bool)) -> Foo > > But Haskell programmers can safely think of the ordinary universally > quantified type given above, thereby avoiding adding a new existential > quantification construct. > """ > > But I don't understand the explanation. > > Thanks in advance, > > TP > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom.schrijvers at ugent.be Mon Dec 2 20:14:47 2013 From: tom.schrijvers at ugent.be (Tom Schrijvers) Date: Mon, 2 Dec 2013 21:14:47 +0100 Subject: [Haskell-cafe] PhD position at Ghent University Message-ID: The Programming Languages Group of Ghent University (UGent) invites applicants for a PhD position on the project Reasoning about Coroutines under the direction of Tom Schrijvers. The project concerns reasoning techniques (like type systems and program analysis) for coroutines in its many forms (like delimited continuations and effect handlers). It is conducted in collaboration with the declarative languages group of KU Leuven university and our international partners. We seek applicants at an international level of excellence. As a successful applicant, you have a master degree in Computer Science or equivalent. Ideally, you also have a strong, documented interest in doing research. Strong problem-solving and programming skills are essential. Prior knowledge of functional programming, logic programming, type systems or program analysis are an advantage. The PhD position is for 4 years and starts between January and October 2014. The position is fully funded by the Fund for Scientific Research Flanders (FWO). The salary is compatible with other Belgian PhD rates and among the better ones in Europe and abroad. You will become part of UGent's dynamic and growing Programming Languages Group. UGent is one of the major universities in the Dutch-speaking region of Europe. It distinguishes itself as a socially committed and pluralistic university in a broad international perspective. Our university is located in the beautiful city of Ghent, which is one of Europe?s greatest discoveries, according to Lonely Planet. Please direct your inquiries and applications by e-mail to Tom Schrijvers < tom.schrijvers at ugent.be>, principal investigator on this project. To apply, send as soon as possible: 1) a letter of interest (including motivation relevant to the research topic), 2) your detailed curriculum vitae (including study curriculum rankings, relevant research experience and publications), 3) your diploma and transcripts (including translation if possible). We will determine the start date together with the selected candidate. See here for more information: * http://users.ugent.be/~tschrijv/phdposition3.html * http://users.ugent.be/~tschrijv/research.html * http://www.ugent.be/en/research/doctoralresearch -- prof. dr. ir. Tom Schrijvers Programming Languages Group Department of Applied Mathematics and Computer Science University of Ghent Krijgslaan 281 S9 9000 Gent Belgium Phone: +32 9 264 4805 http://users.ugent.be/~tschrijv/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From eir at cis.upenn.edu Mon Dec 2 20:17:50 2013 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Mon, 2 Dec 2013 15:17:50 -0500 Subject: [Haskell-cafe] Type-level case In-Reply-To: <529C250E.8020307@quasimal.com> References: <529C250E.8020307@quasimal.com> Message-ID: Some research that I'm doing right now (err? will be doing when I've caught up from a long weekend's-worth of emails) includes a type-level case, just like you're describing. I've been thinking more at a theoretical level to date, and it makes me want to cry thinking about the ambiguity of the arrows? but good point, nonetheless. The type-level case isn't much a topic of the research, as it's easily implementable in terms of closed type families, but it reduces the difference in syntax between terms and types, which is more central to the work. Richard On Dec 2, 2013, at 1:13 AM, Mike Ledger wrote: > Hi. This is more of a brain dump than anything well thought out, but it's been in the back of my mind for a while. > > It's occurred to me that with the upcoming release of GHC 7.8, which features closed type families, we've effectively been given type-level pattern matching that behaves the same as expression-level pattern matching. > > What I think could follow is type-level case syntax. For example: > > type family Example a where > Example 100 = 60 > Example 120 = 15 > Example x = x * 30 > contrived :: Sing a -> Sing b -> Sing (Example (a+b)) > > might instead be expressed as: > > contrived :: Sing a -> Sing b -> Sing (case a+b of > 100 -> 60 > 120 -> 15 > x -> x*30) -- but with something other than -> in the patterns, > -- since that conflicts with the type (->), and there > -- are probably too many arrows already > > > Similarly I think if-then-else could be lifted to the type level, also. > > Some problems with this are that it could pollute "complex" type signatures even further (although currently the situation isn't very good due to haddock/ghc not listing type family instances), and it would get quite cumbersome quickly to have to type out > > contrived2 :: Proxy (a, b) > -> Sing (case a+b of { 100 -> 60; 120 -> 15; x -> x*30 }) > -> ... > > > -- Mike > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From timon.gehr at gmx.ch Mon Dec 2 20:30:23 2013 From: timon.gehr at gmx.ch (Timon Gehr) Date: Mon, 02 Dec 2013 21:30:23 +0100 Subject: [Haskell-cafe] existential quantification In-Reply-To: <0suuma-i57.ln1@rama.universe> References: <0suuma-i57.ln1@rama.universe> Message-ID: On 12/02/2013 11:07 PM, TP wrote: > ... > So I thought that by using existential quantification, the first example > could work: > > --------------- > {-# LANGUAGE ExistentialQuantification #-} > > test :: forall s . Show s => s > test = "asd" > --------------- > > But I obtain the same error, why? > This still says that 'test' is a value of type 's' for all 's' with a 'Show' instance. Basically, 'test' gets a type 's', an instance 'Show s' and we get a value of type 's'. > 2/ > Is the notion of existential type related in some way to the classical > mathematical quantifier "?" (Unicode symbol U+2203: "There exists")? > If yes, then why using "forall" for an "existential type"? > > At the following address > > http://www.haskell.org/ghc/docs/6.12.1/html/users_guide/data-type-extensions.html#existential > > we read > > """ > 7.4.4.1. Why existential? > > What has this to do with existential quantification? Simply that MkFoo has > the (nearly) isomorphic type > > MkFoo :: (exists a . (a, a -> Bool)) -> Foo > > But Haskell programmers can safely think of the ordinary universally > quantified type given above, thereby avoiding adding a new existential > quantification construct. > """ > > But I don't understand the explanation. > Generally speaking, a typing judgement x :: A can be interpreted as a proof that type 'A' is inhabited, or in other words, there exists a value of type 'A'. (Of course in Haskell this fact alone is trivial due to 'undefined', but additional reasoning could render it meaningful. For the remainder I'll just ignore the issue of lifting.) This is somewhat related to classical existential quantification, but it is stronger in a sense, since it says that we know how to construct such a value. (The classical version in general just says that the assumption that there is no such value leads to a contradiction.) Pattern matching allows one to get back the original constructor and the arguments used to construct a value of some ADT type. A universal quantifier over a type states that we can provide any type and obtain a value of the type provided in the body where all instances of the bound variable are replaced by our type. I.e. you can interpret forall a. (...) as stating that a value of that type takes an additional implicit argument 'a' at type level. Now MkFoo is declared as follows: data Foo = forall a. MkFoo a (a -> Bool) | Nil Which gives it the type: MkFoo :: forall a. a -> (a -> Bool) -> Foo I.e. it gets a type 'a' a value of that type and a decidable predicate ranging over that type and constructs a value of type 'Foo'. Pattern matching (roughly speaking) does the opposite: It gets you back a type, a value of that type and the predicate. The type is called nearly isomorphic to the explicit existential type, because using some rounds of pattern matching one would also recover the same kinds of objects. I.e. existential quantification can be thought of as being left implicit in the typing judgement, but 'forall' is needed in order to make explicit the scope of the type variable, which otherwise would range over the entire data declaration instead of just a single constructor. -XExistentialQuantification enables uses of 'forall' necessary for using existential quantification. From paratribulations at free.fr Tue Dec 3 02:30:11 2013 From: paratribulations at free.fr (TP) Date: Mon, 02 Dec 2013 22:30:11 -0400 Subject: [Haskell-cafe] how to factorize propagation of a function over a data type References: Message-ID: Andras Slemmer wrote: > The reason you need the typeclass constraint is not in the use of 'f' but > rather in the use of propagate and what you pass in to it (foo1/foo2 > here). If you leave away the typeclass constraint what you're left with > is: > > propagate' Bar -> (forall a. a->a) -> Bar > > The implementation of this function is the same as before, however your > use of propagate' is restricted: > forall a. a->a is a very "strict" type, in fact the only inhabitant of > this type is 'id' (and bottom, but disregard that here), which means the > only way to call propagate is to pass in 'id'. Try it yourself! Indeed I have tried, it works as you say. > Related note: there is a proof that in fact the only inhabitant of (forall > a. a -> a) is 'id' and it is the consequence of the "parametricity" > property. It is a very neat result I suggest you look it up! Interesting. I have tried to google on the topic, but I find mainly research articles. For example: https://www.google.fr/search?client=ubuntu&channel=fs&q=haskell+%22parametricity+property%22&ie=utf-8&oe=utf-8&gws_rd=cr&ei=P_acUvboDse_0QX9mYDADQ#channel=fs&q=%22parametricity+property%22+haskell Are there textbooks where a proof of this fact could be found? I'm an autodidact (who also benefits from help of guys like you), I don't know what lectures on type theory at university level could look like. Thanks TP From qdunkan at gmail.com Mon Dec 2 21:43:31 2013 From: qdunkan at gmail.com (Evan Laforge) Date: Mon, 2 Dec 2013 13:43:31 -0800 Subject: [Haskell-cafe] RFC: rewrite-with-location proposal In-Reply-To: References: Message-ID: Hey, whatever happened with this? Is there anything in the way of getting this merged? Is there some way I could help? On Sun, Feb 24, 2013 at 10:06 PM, Michael Snoyman wrote: > Quite a while back, Simon Hengel and I put together a proposal[1] for a new > feature in GHC. The basic idea is pretty simple: provide a new pragma that > could be used like so: > > error :: String -> a > errorLoc :: IO Location -> String -> a > {-# REWRITE_WITH_LOCATION error errorLoc #-} > > Then all usages of `error` would be converted into calls to `errorLoc` by > the compiler, passing in the location information of where the call > originated from. Our three intended use cases are: > > * Locations for failing test cases in a test framework > * Locations for log messages > * assert/error/undefined > > Note that the current behavior of the assert function[2] already includes > this kind of approach, but it is a special case hard-coded into the > compiler. This proposal essentially generalizes that behavior and makes it > available for all functions, whether included with GHC or user-defined. > > The proposal spells out some details of this approach, and contrasts with > other methods being used today for the same purpose, such as TH and CPP. > > Michael > > [1] https://github.com/sol/rewrite-with-location > [2] > http://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Control-Exception.html#v:assert > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Mon Dec 2 21:58:49 2013 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Mon, 2 Dec 2013 21:58:49 +0000 Subject: [Haskell-cafe] how to factorize propagation of a function over a data type In-Reply-To: References: Message-ID: <20131202215849.GP10418@weber> On Mon, Dec 02, 2013 at 10:30:11PM -0400, TP wrote: > Andras Slemmer wrote: > > Related note: there is a proof that in fact the only inhabitant of (forall > > a. a -> a) is 'id' and it is the consequence of the "parametricity" > > property. It is a very neat result I suggest you look it up! > > Are there textbooks where a proof of this fact could be found? I'm an > autodidact (who also benefits from help of guys like you), I don't know what > lectures on type theory at university level could look like. I guess the most accessible reference might be Wadler 1989 "Theorems for Free". http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.38.9875 Tom From sol at typeful.net Mon Dec 2 22:06:25 2013 From: sol at typeful.net (Simon Hengel) Date: Mon, 2 Dec 2013 23:06:25 +0100 Subject: [Haskell-cafe] RFC: rewrite-with-location proposal In-Reply-To: References: Message-ID: <20131202220625.GA6022@x200> Hi Evan! On Mon, Dec 02, 2013 at 01:43:31PM -0800, Evan Laforge wrote: > Hey, whatever happened with this? My code for this is here: https://github.com/sol/ghc/commits/rewrite-with-location Revision 03e63f0a70ec8c0fece4049c2d714ea533494ec2 was fully functional, but it needs to be rebased on current master. The missing feature here is that type checking only happens on rewrite. I just added a wip commit with local modifications that do the type checking earlier, when the module with the rewrite pragma is compiled. > Is there anything in the way of getting this merged? Is there some > way I could help? This needs rebasing + I'm not sure if the wip commit currently compiles. I'm somewhat swamped, so I'm not sure when I'll have time to work on this. If you want to help, that would be awesome! I'm happy to help with any questions (solirc on freenode, feel free to say hello in #hspec ;). Cheers, Simon From paratribulations at free.fr Tue Dec 3 03:53:42 2013 From: paratribulations at free.fr (TP) Date: Mon, 02 Dec 2013 23:53:42 -0400 Subject: [Haskell-cafe] existential quantification References: <0suuma-i57.ln1@rama.universe> Message-ID: <65jvma-8j3.ln1@rama.universe> Brandon Allbery wrote: > Which brings us to what is *really* going on. When you write > > test :: Show s => s > > you are saying exactly and only this: > > Any function that calls me can request *any* type that has an instance > of Show, and I will give them *that type*. Thanks Brandon for this interpretation. I have carefully written it in my Haskell notes. TP From paratribulations at free.fr Tue Dec 3 04:10:13 2013 From: paratribulations at free.fr (TP) Date: Tue, 03 Dec 2013 00:10:13 -0400 Subject: [Haskell-cafe] existential quantification References: <0suuma-i57.ln1@rama.universe> Message-ID: <54kvma-6tl.ln1@rama.universe> Andras Slemmer wrote: > Just expanding on Brandon's answer: DeMorgan's law he's referring to goes > like this: > ?a.P(a) === ??a.?P(a) where 'a' is a sentence, so P is second order > A special case of this is this: > ?a.(R(a) -> Q) === ??a.?(R(a) -> Q) === ??a.(R(a)??Q) === ?((?a.R(a))??Q) > === (?a.R(a)) -> Q (i added extra parantheses for emphasis) > So what does this mean in terms of haskell? R(a) is your data definition's > "body", and Q is the type you are defining. On the lhs the universally > quantified version gives you the type of the constuctor you're defining, > and on the rhs the existential tells you what you're constructing the type > with. > Or in other words the universal version says: For any 'a' give me an R(a) > and i'll give you back a Q. > The existential version says: If you have some 'a' for which R(a) i'll > give you back a Q. (It's hard to phrase the difference without sounding > stupid, they are equivalent after all). > > There are of course other considerations, for example introducing 'exists' > would mean another keyword in the syntax. Thanks Andras, I have understood the developments up to that point. But below I do not understand your reasoning. > > Having said that I think that the choice of 'forall' for > -XExistentialQuantification is wrong, as the data body defines the type > you're constructing with, not the type of the whole constructor. HOWEVER > for -XGADTs forall makes perfect sense. Compare the following: > > data AnyType = forall a. AnyType a > data AnyType where > AnyType :: forall a. a -> AnyType > > These two definitions are operationally identical, but I think the GADT > way is the one that actually corresponds to the DeMorgan law. And one more question: I had lectures on logic some years ago, but I never studied type theory at university (I'm some sort of "electrical engineer"). Is there around a good textbook for "beginners", with full proofs, but only the essential ones? I would like a good "entry point" in the textbook literature. Not for experts. Are the books of Robert Harper suitable, for example http://www.amazon.com/Practical-Foundations-Programming-Languages-Professor/dp/1107029570 ? TP From 0slemi0 at gmail.com Tue Dec 3 00:47:25 2013 From: 0slemi0 at gmail.com (Andras Slemmer) Date: Tue, 3 Dec 2013 00:47:25 +0000 Subject: [Haskell-cafe] existential quantification In-Reply-To: <54kvma-6tl.ln1@rama.universe> References: <0suuma-i57.ln1@rama.universe> <54kvma-6tl.ln1@rama.universe> Message-ID: > But below I do not understand your reasoning. Given a datatype data D = D Int I call Int the type you're constructing D with, however the type of the constructor itself is Int -> D In ghc haskell there is another way of defining the same type using GADTs alongside the above "haskell98" way: data D where D :: Int -> D Notice how here we are explicitly typing the constructor. The haskell98 way defines what your datatype D is isomorphic to - here it is Int, whereas the GADT way defines how to construct a D. The problem haskell developers faced was that in order to use the haskell98 way for existentials they would've had to introduce an 'exists' quantifier, which would mess up a boatload of things in the type theory. Instead they introduced this forall hack that doesn't define an isomorphic type, rather it indicates that we are defining a way of constructing an existential. I find this ugly because it breaks the isomorphism that the = sign indicates in a haskell98 definition. The GADT way on the other hand is defining ways of construction, so a definition like: data D2 where D2 :: a -> D2 makes perfect sense > Is there around a good textbook for "beginners", with full proofs, but only the essential ones? Types and Programming Languages from Benjamin Pierce is a good one. I also plan to upload a short video lecture series from Harper on type theory (it assumes minimal knowledge of logic), i'll send you a link when it's up. On 3 December 2013 04:10, TP wrote: > Andras Slemmer wrote: > > > Just expanding on Brandon's answer: DeMorgan's law he's referring to goes > > like this: > > ?a.P(a) === ??a.?P(a) where 'a' is a sentence, so P is second order > > A special case of this is this: > > ?a.(R(a) -> Q) === ??a.?(R(a) -> Q) === ??a.(R(a)??Q) === ?((?a.R(a))??Q) > > === (?a.R(a)) -> Q (i added extra parantheses for emphasis) > > So what does this mean in terms of haskell? R(a) is your data > definition's > > "body", and Q is the type you are defining. On the lhs the universally > > quantified version gives you the type of the constuctor you're defining, > > and on the rhs the existential tells you what you're constructing the > type > > with. > > Or in other words the universal version says: For any 'a' give me an R(a) > > and i'll give you back a Q. > > The existential version says: If you have some 'a' for which R(a) i'll > > give you back a Q. (It's hard to phrase the difference without sounding > > stupid, they are equivalent after all). > > > > There are of course other considerations, for example introducing > 'exists' > > would mean another keyword in the syntax. > > Thanks Andras, I have understood the developments up to that point. But > below I do not understand your reasoning. > > > > > Having said that I think that the choice of 'forall' for > > -XExistentialQuantification is wrong, as the data body defines the type > > you're constructing with, not the type of the whole constructor. HOWEVER > > for -XGADTs forall makes perfect sense. Compare the following: > > > > data AnyType = forall a. AnyType a > > data AnyType where > > AnyType :: forall a. a -> AnyType > > > > These two definitions are operationally identical, but I think the GADT > > way is the one that actually corresponds to the DeMorgan law. > > And one more question: I had lectures on logic some years ago, but I never > studied type theory at university (I'm some sort of "electrical engineer"). > Is there around a good textbook for "beginners", with full proofs, but only > the essential ones? I would like a good "entry point" in the textbook > literature. Not for experts. > Are the books of Robert Harper suitable, for example > > > http://www.amazon.com/Practical-Foundations-Programming-Languages-Professor/dp/1107029570 > > ? > > TP > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From anthony_clayden at clear.net.nz Tue Dec 3 05:17:52 2013 From: anthony_clayden at clear.net.nz (AntC) Date: Tue, 3 Dec 2013 05:17:52 +0000 (UTC) Subject: [Haskell-cafe] =?utf-8?q?Return_of_the_revenge_of_the_revisit_of_?= =?utf-8?q?the=09extensible_records=2C_reiterated?= References: Message-ID: > Richard Eisenberg cis.upenn.edu> writes: > > A few reactions to this thread, in no particular order: > Thank you Richard for your comprehensive reply. There's been so much e-ink spilt on the subject over the years, I don't really want to repeat it, so a few key points (in reverse of your order ;-) ... > - Banning instance overlap that is currently permitted would break > existing code. Is this a big enough wart > to incite a breaking change? Errm, no: overlap is not "currently permitted". Overlap is not part of H98. Overlap is not sanctioned as part of H2010. Overlap is not even on the slate for Haskell Prime. Its status is clearly marked as experimental/unsafe. MTL was reorganised to remove Overlap. There's various trickery in the base classes to avoid overlap. (Such as showlist.) That said, I know there's plenty of code out there. (I've written it myself.) I think there is very little code with genuinely partial overlaps, as opposed to total overlaps. (And total overlaps are easily turned into disequality guards.) The difficulties that Oleg & Ralf ran into with overlaps, it turns out can be made to work -- even in Hugs. That is, if you use overlaps in a very disciplined way. That way amounts to disequality guards. I wish I had the time and competence to implement the guards idea. Then we could experiment with the issues under debate ... > - While I agree that closed type families don't fit as well with the > mental model of competing instances, I believe they work better > with programmers' sensibilities at the term level. > One could argue which is better to aim for. So I'm going to argue ;-): - Guards are already familiar at the term level. - I'm not convinced that instance selection is ever-so like the term level. (For example, you've introduced some look-ahead coincidence-checking, to improve the chances for closed families.) - We're already used to widely-scattered definitions of class methods at the term level. - I'd love Haskell to support widely-scattered definitions of functions (It's sometimes a pain to have to put all of the patterns together in sequence.) - (IOW, let's make terms more like instances, rather than v.v.) > - The notion of "competing instances" for type families sounds somewhat > like delayed overlap checks for class instances. ... No. No delay. The point is to validate eagerly at the point of declaring the instance (and whether or not it's in some other module). The guards guarantee that no instances overlap. Importing an overlapping instance is trapped immediately; no risk of incoherence. Then we know that any usage cannot possibly match more than one instance. We can let all instances compete. Whichever one 'wins', we can be sure it's the only one. (This of course doesn't guarantee there will be a winner at all; instance matching can still get 'stuck', as you say.) > For example, consider these definitions: > > > module A where > > type instance F a b c | b /~ c = Int > > > module B where > > import A > > type instance F a b c | a /~ c = Bool > > Questions: > 1. Are these instances overlapping? Yes, so compile fails at the instances. No need to look at usages. (I gave the rules by which it would fail in some message way back; it is algorithmic, and based on what I think is existing ghc behaviour for overlaps.) So your follow-on questions don't apply > 2. How does `F Int Bool Char` reduce when written in module A? > 3. How does `F Int Bool Char` reduce when written in module B? > > > - I don't see how disequality guards would help with error messages. > OK, the example is to check that there's exactly one occurence of a type- level label in an HList. This is hard, so Leijen's approach doesn't try. Having found an instance with the label, HList uses an auxiliary class `Lacks` to validate that the label doesn't appear in the Hlist's tail, like this: instance (Lacks lab l') => Has lab (HCons (lab, val) l') How to code `Lacks`? instance Lacks lab HNil -- got to the end of the tail OK instance (Lacks lab l') => Lacks lab (HCons (lab2, val) l') -- not here, recurse on the tail But that doesn't work! the instance matches even when `lab` is the same as `lab2`. We need an extra instance, which we want to treat as failure: instance (Fail SomeMessage) => Lacks lab (HCons (lab, val) l') -- repeated typevar ^^^ Deliberately to trigger the failure, we make sure there's no instance for `Fail`. So the compiler error message is 'No instance for Fail ...'; but it _means_ there _is_ an instances for `Lacks`. With a disequality guards we'd have only one instance: instance (Lacks lab l') => Lacks lab (HCons (lab2, val) l') | lab /~ lab2 And the compiler message would be 'No instance for Lacks L1 (HCons (L1, Int) ...)`. We can see the repeated label. Now I concede that all this design involves a kinda double-negative. At least we get focus on the class causing the failure. AntC From jwlato at gmail.com Tue Dec 3 05:43:55 2013 From: jwlato at gmail.com (John Lato) Date: Mon, 2 Dec 2013 21:43:55 -0800 Subject: [Haskell-cafe] Return of the revenge of the revisit of the extensible records, reiterated In-Reply-To: References: Message-ID: (a bit late to the discussion, so please ignore if this is completely off-base) On Mon, Dec 2, 2013 at 9:17 PM, AntC wrote: > > Richard Eisenberg cis.upenn.edu> writes: > > > > - The notion of "competing instances" for type families sounds somewhat > > like delayed overlap checks for class instances. ... > > No. No delay. The point is to validate eagerly at the point of declaring > the instance (and whether or not it's in some other module). > The guards guarantee that no instances overlap. > Importing an overlapping instance is trapped immediately; > no risk of incoherence. > How can this possibly work with open type families? What happens in this case? > module A where > type instance F a b c | b /~ c = Int > module B where > type instance F a b c | a /~ c = Bool During compilation, neither A nor B is aware of the other. What happens in a module that imports both? -------------- next part -------------- An HTML attachment was scrubbed... URL: From ky3 at atamo.com Tue Dec 3 06:36:41 2013 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Tue, 3 Dec 2013 13:36:41 +0700 Subject: [Haskell-cafe] existential quantification In-Reply-To: <54kvma-6tl.ln1@rama.universe> References: <0suuma-i57.ln1@rama.universe> <54kvma-6tl.ln1@rama.universe> Message-ID: On Tue, Dec 3, 2013 at 11:10 AM, TP wrote: > I would like a good "entry point" in the textbook > literature. Not for experts. > Are the books of Robert Harper suitable, for example > > > http://www.amazon.com/Practical-Foundations-Programming-Languages-Professor/dp/1107029570 > There's a draft copy on Harper's home page you can check out. It's primarily a textbook for CS graduate students entering the specialization of PL. -- Kim-Ee -------------- next part -------------- An HTML attachment was scrubbed... URL: From anthony_clayden at clear.net.nz Tue Dec 3 07:25:45 2013 From: anthony_clayden at clear.net.nz (AntC) Date: Tue, 3 Dec 2013 07:25:45 +0000 (UTC) Subject: [Haskell-cafe] Return of the revenge of the revisit of the extensible records, reiterated References: Message-ID: > John Lato gmail.com> writes: > On Mon, Dec 2, 2013 at 9:17 PM, AntC wrote: > > > ... > Importing an overlapping instance is trapped immediately; > no risk of incoherence. > > > How can this possibly work with open type families?? What happens in this case? > > module A where > > type instance F a b c | b /~ c = Int > > module B where > > type instance F a b c | a /~ c = Bool > > During compilation, neither A nor B is aware of the other.? What happens in a module that imports both? > Thanks John, a good use case! The trapping is needed with imports for any approach to open instances (not just type families). Suppose I have NoOverlappingInstances everywhere: > module A where > instance C a b c where ... > module B where > instance C a b c where ... > module D where > instance C Int Bool Char where ... And a module that imports all three. Any importer has to validate all instances sometime or other. (Currently ghc sticks its head in the sand, and hopes there won't be a usage that trips over the ambiguity.) All we're talking about is _when_ we validate. I'd rather know at the point of declaring the instance, or of importing the instance. AntC From ganesh at earth.li Tue Dec 3 07:58:25 2013 From: ganesh at earth.li (Ganesh Sittampalam) Date: Tue, 03 Dec 2013 07:58:25 +0000 Subject: [Haskell-cafe] The rmonad package is mysterious In-Reply-To: <5165AFDF.6070606@banquise.net> References: <5165AFDF.6070606@banquise.net> Message-ID: <529D8F21.60301@earth.li> Hi, This is rather late, but in case it's useful: On 10/04/2013 19:30, Simon Marechal wrote: > I tried to do something simple using the rmonad package (attached). > > I followed the example that's in haddocks (it is wrong, constraints has > no arguments), grabbed the list of extensions from rmonad's source, but > this program doesn't typecheck: > > Could not deduce (Hashable a) arising from a use of `HM.singleton' > > This seems to be an obvious use of this package ... am I missing something ? The dictionaries for the superclasses are "wrapped up" in the data constructor MonadOutcome, so you need to unwrap it. For example: instance RMonad MonadOutcome where return (x :: a) = case constraints :: Constraints MonadOutcome a of OutcomeConstraints -> MonadOutcome (HM.singleton x 1) There are helper functions in Data.Suitable for doing this, for example withResConstraints infers the right 'a' from the inferred result type: import Data.Suitable (Constraints, withResConstraints) .... instance RMonad MonadOutcome where return x = withResConstraints $ \OutcomeConstraints -> MonadOutcome (HM.singleton x 1) (>>=) = undefined The documentation on hackage gives signatures and examples: http://hackage.haskell.org/package/suitable-0.1.1/docs/Data-Suitable.html http://hackage.haskell.org/package/rmonad-0.8.0.1/docs/Control-RMonad.html (note that the Set example doesn't need constraints for 'return' because Data.Set.singleton doesn't have an Ord constraint, but you can see it in the >>= implementation) Cheers, Ganesh From oleg at okmij.org Tue Dec 3 09:47:13 2013 From: oleg at okmij.org (oleg at okmij.org) Date: 3 Dec 2013 09:47:13 -0000 Subject: [Haskell-cafe] Constraint-folding Message-ID: <20131203094713.10650.qmail@www1.g3.pair.com> Andras Slemmer wrote: > I stumbled upon something pretty neat, and although I'm 95% sure Oleg did > this already 10 years ago in Haskell98 You're quite right about this: Chung-chieh Shan and I did this reification of constraint in December 2003, and almost in Haskell 98 (we needed Rank2 types though). It was described in the following paper http://okmij.org/ftp/Haskell/types.html#Prepose We called this transformation reflection/reification. I'm writing though to show a dual formulation to your development of using singletons. It gets by without GADTs and uses very few extensions: essentially Haskell98 with Rank2 types. {-# LANGUAGE RankNTypes #-} data Zero data Succ a class Class n instance Class Zero instance (Class m) => Class (Succ m) -- Tagless final class Sym repr where z :: repr Zero s :: repr n -> repr (Succ n) newtype R x = R{unR:: x} -- the identity interpreter instance Sym R where z = R undefined s _ = R undefined newtype S x = S Integer -- for show instance Sym S where z = S 0 s (S x) = S (x + 1) newtype Reify n = Reify (forall a. (Class n => n -> a) -> a) instance Sym Reify where z = Reify (\f -> f (unR z)) s (Reify f) = Reify (\g -> f (g . unR . s . R)) genericClass :: (forall repr. Sym repr => repr n) -> (Class n => a) -> a genericClass m f = case m of Reify k -> k (const f) From P.Achten at cs.ru.nl Tue Dec 3 10:07:13 2013 From: P.Achten at cs.ru.nl (Peter Achten) Date: Tue, 03 Dec 2013 11:07:13 +0100 Subject: [Haskell-cafe] [TFP 2014] 1st Call For Papers Message-ID: <529DAD51.7060405@cs.ru.nl> Dear reader, Please find included the first call for papers for next year's Trends In Functional Programming event, organized by Jurriaan Hage from Utrecht University, The Netherlands. With kind regards, Peter Achten Communication chair TFP ----------------------------- C A L L F O R P A P E R S ----------------------------- ======== TFP 2014 =========== 15th Symposium on Trends in Functional Programming May 26-28, 2014 Utrecht University Soesterberg, The Netherlands http://www.cs.uu.nl/wiki/TFP2014/WebHome The symposium on Trends in Functional Programming (TFP) is an international forum for researchers with interests in all aspects of functional programming, taking a broad view of current and future trends in the area. It aspires to be a lively environment for presenting the latest research results, and other contributions (see below), described in draft papers submitted prior to the symposium. A formal post-symposium refereeing process then selects a subset of the articles presented at the symposium and submitted for formal publication. Selected papers will be published as a Springer Lecture Notes in Computer Science (LNCS) volume. TFP 2014 will be the main event of a pair of functional programming events. The other is the International Workshop on Trends in Functional Programming in Education (TFPIE). TFPIE will take place on May 25th. The TFP symposium is the heir of the successful series of Scottish Functional Programming Workshops. Previous TFP symposia were held in Edinburgh (Scotland) in 2003, in Munich (Germany) in 2004, in Tallinn (Estonia) in 2005, in Nottingham (UK) in 2006, in New York (USA) in 2007, in Nijmegen (The Netherlands) in 2008, in Komarno (Slovakia) in 2009, in Oklahoma (USA) in 2010, in Madrid (Spain) in 2011, St. Andrews (UK) in 2012 and Provo (Utah, USA) in 2013. For further general information about TFP please see the TFP homepage. INVITED SPEAKERS TFP is pleased to announce talks by the following two invited speakers: John Hughes of Chalmers, Goteborg, Sweden, is well-known as author of Why Functional Programming Matters, and as one of the designers of QuickCheck (together with Koen Claessen); the paper on QuickCheck won the ICFP Most Influential Paper Award in 2010. Currently he divides his time between his professorship and Quviq, a company that performs property-based testing of software with a tool implemented in Erlang. Dr. Geoffrey Mainland received his PhD from Harvard University where he was advised by Greg Morrisett and Matt Welsh. After a two year postdoc with the Programming Principles and Tools group at Microsoft Research Cambridge, he is now an assistant professor at Drexel University. His research focuses on high-level programming language and runtime support for non-general purpose computation. SCOPE The symposium recognizes that new trends may arise through various routes. As part of the Symposium's focus on trends we therefore identify the following five article categories. High-quality articles are solicited in any of these categories: Research Articles: leading-edge, previously unpublished research work Position Articles: on what new trends should or should not be Project Articles: descriptions of recently started new projects Evaluation Articles: what lessons can be drawn from a finished project Overview Articles: summarizing work with respect to a trendy subject Articles must be original and not submitted for simultaneous publication to any other forum. They may consider any aspect of functional programming: theoretical, implementation-oriented, or more experience-oriented. Applications of functional programming techniques to other languages are also within the scope of the symposium. Topics suitable for the symposium include: Functional programming and multicore/manycore computing Functional programming in the cloud High performance functional computing Extra-functional (behavioural) properties of functional programs Dependently typed functional programming Validation and verification of functional programs Using functional techniques to reason about imperative/object-oriented programs Debugging for functional languages Functional programming in different application areas: security, mobility, telecommunications applications, embedded systems, global computing, grids, etc. Interoperability with imperative programming languages Novel memory management techniques Program analysis and transformation techniques Empirical performance studies Abstract/virtual machines and compilers for functional languages (Embedded) domain specific languages New implementation strategies Any new emerging trend in the functional programming area If you are in doubt on whether your article is within the scope of TFP, please contact the TFP 2014 program chair, Jurriaan Hage at J.Hage at uu.nl. BEST PAPER AWARDS To reward excellent contributions, TFP awards a prize for the best paper accepted for the formal proceedings. TFP traditionally pays special attention to research students, acknowledging that students are almost by definition part of new subject trends. A student paper is one for which the authors state that the paper is mainly the work of students, the students are listed as first authors, and a student would present the paper. A prize for the best student paper is awarded each year. In both cases, it is the PC of TFP that awards the prize. In case the best paper happens to be a student paper, that paper will then receive both prizes. SPONSORS TFP is financially supported by NWO (Netherlands Organisation for Scientific Research), Well-Typed and Erlang Solutions. PAPER SUBMISSIONS Acceptance of articles for presentation at the symposium is based on a lightweight peer review process of extended abstracts (4 to 10 pages in length) or full papers (16 pages). The submission must clearly indicate which category it belongs to: research, position, project, evaluation, or overview paper. It should also indicate whether the main author or authors are research students. In the case of a full student paper, the paper will receive additional feedback by one of the PC members shortly after the symposium has taken place. We shall use EasyChair for the refereeing process. IMPORTANT DATES Submission of draft papers: March 17, 2014 Notification: March 24, 2014 Registration: April 7, 2014 TFP Symposium: May 26-28, 2014 Student papers feedback: June 9th, 2014 Submission for formal review: July 1st, 2014 Notification of acceptance: September 8th, 2014 Camera ready paper: October 8th, 2014 PROGRAM COMMITTEE Peter Achten Radboud University Nijmegen Emil Axelsson Chalmers Lucilia Camarao de Figueiredo Universidade Federal de Ouro Preto Laura Castro University of A Coruna Frank Huch Christian-Albrechts-University of Kiel Matthew Fluet Rochester Institute of Technology Jurriaan Hage (chair) University of Utrecht Yukiyoshi Kameyama University of Tsukuba Andrew Kennedy Microsoft Research Tamas Kozsik Eotvos Lorand University Ben Lippmeier University of New South Wales Luc Maranget INRIA Jay McCarthy Brigham Young University Marco T. Morazan Seton Hall University Ricardo Pena Universidad Complutense de Madrid Alexey Rodriguez madvertise Sven-Bodo Scholz Heriot-Watt University Manuel Serrano INRIA Sophia Antipolis Simon Thompson University of Kent Tarmo Uustalu Inst of Cybernetics David Van Horn Maryland University Janis Voigtlaender University of Bonn From annaduchene at aol.com Tue Dec 3 11:57:23 2013 From: annaduchene at aol.com (Anna) Date: Tue, 3 Dec 2013 06:57:23 -0500 Subject: [Haskell-cafe] [TFP 2014] 1st Call For Papers In-Reply-To: <529DAD51.7060405@cs.ru.nl> References: <529DAD51.7060405@cs.ru.nl> Message-ID: <736EAD12-BA71-4395-B6B9-B1800DB374B1@aol.com> Stop On Dec 3, 2013, at 5:07 AM, Peter Achten wrote: Dear reader, Please find included the first call for papers for next year's Trends In Functional Programming event, organized by Jurriaan Hage from Utrecht University, The Netherlands. With kind regards, Peter Achten Communication chair TFP ----------------------------- C A L L F O R P A P E R S ----------------------------- ======== TFP 2014 =========== 15th Symposium on Trends in Functional Programming May 26-28, 2014 Utrecht University Soesterberg, The Netherlands http://www.cs.uu.nl/wiki/TFP2014/WebHome The symposium on Trends in Functional Programming (TFP) is an international forum for researchers with interests in all aspects of functional programming, taking a broad view of current and future trends in the area. It aspires to be a lively environment for presenting the latest research results, and other contributions (see below), described in draft papers submitted prior to the symposium. A formal post-symposium refereeing process then selects a subset of the articles presented at the symposium and submitted for formal publication. Selected papers will be published as a Springer Lecture Notes in Computer Science (LNCS) volume. TFP 2014 will be the main event of a pair of functional programming events. The other is the International Workshop on Trends in Functional Programming in Education (TFPIE). TFPIE will take place on May 25th. The TFP symposium is the heir of the successful series of Scottish Functional Programming Workshops. Previous TFP symposia were held in Edinburgh (Scotland) in 2003, in Munich (Germany) in 2004, in Tallinn (Estonia) in 2005, in Nottingham (UK) in 2006, in New York (USA) in 2007, in Nijmegen (The Netherlands) in 2008, in Komarno (Slovakia) in 2009, in Oklahoma (USA) in 2010, in Madrid (Spain) in 2011, St. Andrews (UK) in 2012 and Provo (Utah, USA) in 2013. For further general information about TFP please see the TFP homepage. INVITED SPEAKERS TFP is pleased to announce talks by the following two invited speakers: John Hughes of Chalmers, Goteborg, Sweden, is well-known as author of Why Functional Programming Matters, and as one of the designers of QuickCheck (together with Koen Claessen); the paper on QuickCheck won the ICFP Most Influential Paper Award in 2010. Currently he divides his time between his professorship and Quviq, a company that performs property-based testing of software with a tool implemented in Erlang. Dr. Geoffrey Mainland received his PhD from Harvard University where he was advised by Greg Morrisett and Matt Welsh. After a two year postdoc with the Programming Principles and Tools group at Microsoft Research Cambridge, he is now an assistant professor at Drexel University. His research focuses on high-level programming language and runtime support for non-general purpose computation. SCOPE The symposium recognizes that new trends may arise through various routes. As part of the Symposium's focus on trends we therefore identify the following five article categories. High-quality articles are solicited in any of these categories: Research Articles: leading-edge, previously unpublished research work Position Articles: on what new trends should or should not be Project Articles: descriptions of recently started new projects Evaluation Articles: what lessons can be drawn from a finished project Overview Articles: summarizing work with respect to a trendy subject Articles must be original and not submitted for simultaneous publication to any other forum. They may consider any aspect of functional programming: theoretical, implementation-oriented, or more experience-oriented. Applications of functional programming techniques to other languages are also within the scope of the symposium. Topics suitable for the symposium include: Functional programming and multicore/manycore computing Functional programming in the cloud High performance functional computing Extra-functional (behavioural) properties of functional programs Dependently typed functional programming Validation and verification of functional programs Using functional techniques to reason about imperative/object-oriented programs Debugging for functional languages Functional programming in different application areas: security, mobility, telecommunications applications, embedded systems, global computing, grids, etc. Interoperability with imperative programming languages Novel memory management techniques Program analysis and transformation techniques Empirical performance studies Abstract/virtual machines and compilers for functional languages (Embedded) domain specific languages New implementation strategies Any new emerging trend in the functional programming area If you are in doubt on whether your article is within the scope of TFP, please contact the TFP 2014 program chair, Jurriaan Hage at J.Hage at uu.nl. BEST PAPER AWARDS To reward excellent contributions, TFP awards a prize for the best paper accepted for the formal proceedings. TFP traditionally pays special attention to research students, acknowledging that students are almost by definition part of new subject trends. A student paper is one for which the authors state that the paper is mainly the work of students, the students are listed as first authors, and a student would present the paper. A prize for the best student paper is awarded each year. In both cases, it is the PC of TFP that awards the prize. In case the best paper happens to be a student paper, that paper will then receive both prizes. SPONSORS TFP is financially supported by NWO (Netherlands Organisation for Scientific Research), Well-Typed and Erlang Solutions. PAPER SUBMISSIONS Acceptance of articles for presentation at the symposium is based on a lightweight peer review process of extended abstracts (4 to 10 pages in length) or full papers (16 pages). The submission must clearly indicate which category it belongs to: research, position, project, evaluation, or overview paper. It should also indicate whether the main author or authors are research students. In the case of a full student paper, the paper will receive additional feedback by one of the PC members shortly after the symposium has taken place. We shall use EasyChair for the refereeing process. IMPORTANT DATES Submission of draft papers: March 17, 2014 Notification: March 24, 2014 Registration: April 7, 2014 TFP Symposium: May 26-28, 2014 Student papers feedback: June 9th, 2014 Submission for formal review: July 1st, 2014 Notification of acceptance: September 8th, 2014 Camera ready paper: October 8th, 2014 PROGRAM COMMITTEE Peter Achten Radboud University Nijmegen Emil Axelsson Chalmers Lucilia Camarao de Figueiredo Universidade Federal de Ouro Preto Laura Castro University of A Coruna Frank Huch Christian-Albrechts-University of Kiel Matthew Fluet Rochester Institute of Technology Jurriaan Hage (chair) University of Utrecht Yukiyoshi Kameyama University of Tsukuba Andrew Kennedy Microsoft Research Tamas Kozsik Eotvos Lorand University Ben Lippmeier University of New South Wales Luc Maranget INRIA Jay McCarthy Brigham Young University Marco T. Morazan Seton Hall University Ricardo Pena Universidad Complutense de Madrid Alexey Rodriguez madvertise Sven-Bodo Scholz Heriot-Watt University Manuel Serrano INRIA Sophia Antipolis Simon Thompson University of Kent Tarmo Uustalu Inst of Cybernetics David Van Horn Maryland University Janis Voigtlaender University of Bonn _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe at haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe From dennis.raddle at gmail.com Tue Dec 3 19:43:34 2013 From: dennis.raddle at gmail.com (Dennis Raddle) Date: Tue, 3 Dec 2013 11:43:34 -0800 Subject: [Haskell-cafe] PhD at age 45? Message-ID: A more specific question than my last post. I guess I'm wondering if it's a good idea to begin a PhD in CS at age 45 (currently having a BS in CS). My goal is to obtain work that interests me, work that really draws on the skills one develops in a PhD program. Work in academia is hard to obtain, I understand, but I could take an industry job. I'm wondering if I'll just be postponing a job with no financial gain afterward and poor prospects for work. Or if there is ageism that will work against a guy coming out of school at age 52. Or, if it will truly lead to an interesting job with good pay. Dennis -------------- next part -------------- An HTML attachment was scrubbed... URL: From dagitj at gmail.com Tue Dec 3 19:54:20 2013 From: dagitj at gmail.com (Jason Dagit) Date: Tue, 3 Dec 2013 11:54:20 -0800 Subject: [Haskell-cafe] PhD at age 45? In-Reply-To: References: Message-ID: "Advice is what we ask for when we already know the answer but wish we didn't..." -- Erica Jong As I understand it, the reasons to get a PhD don't have much to do with getting a promotion or changing jobs. It's more about following a passion, doing something for yourself, and apprenticing in an area of research. I'm sure it varies from person to person. At any rate, I don't think I can give you an answer. At the company I work at we're always on the look out for folks with PhDs and I don't think we care about age. We do care a lot about other things though, such as expertise and presentation skills. I hope that helps, Jason On Tue, Dec 3, 2013 at 11:43 AM, Dennis Raddle wrote: > A more specific question than my last post. I guess I'm wondering if it's > a good idea to begin a PhD in CS at age 45 (currently having a BS in CS). > My goal is to obtain work that interests me, work that really draws on the > skills one develops in a PhD program. Work in academia is hard to obtain, I > understand, but I could take an industry job. I'm wondering if I'll just be > postponing a job with no financial gain afterward and poor prospects for > work. Or if there is ageism that will work against a guy coming out of > school at age 52. > > Or, if it will truly lead to an interesting job with good pay. > > Dennis > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From miguelimo38 at yandex.ru Tue Dec 3 20:06:56 2013 From: miguelimo38 at yandex.ru (MigMit) Date: Wed, 4 Dec 2013 00:06:56 +0400 Subject: [Haskell-cafe] PhD at age 45? In-Reply-To: References: Message-ID: <416AF7F3-5FE1-4DCD-ADE5-6D6A3422B02E@yandex.ru> Don't worry, you don't need PhD to understand monads. ?????????? ? iPhone > 03 ???. 2013 ?., ? 23:43, Dennis Raddle ???????(?): > > A more specific question than my last post. I guess I'm wondering if it's a good idea to begin a PhD in CS at age 45 (currently having a BS in CS). My goal is to obtain work that interests me, work that really draws on the skills one develops in a PhD program. Work in academia is hard to obtain, I understand, but I could take an industry job. I'm wondering if I'll just be postponing a job with no financial gain afterward and poor prospects for work. Or if there is ageism that will work against a guy coming out of school at age 52. > > Or, if it will truly lead to an interesting job with good pay. > > Dennis > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From anthony_clayden at clear.net.nz Tue Dec 3 20:20:37 2013 From: anthony_clayden at clear.net.nz (AntC) Date: Tue, 3 Dec 2013 20:20:37 +0000 (UTC) Subject: [Haskell-cafe] PhD at age 45? References: Message-ID: > Dennis Raddle gmail.com> writes: > > ... I guess I'm wondering if it's a good idea to begin a PhD in CS at > age 45 Dennis, if you have a passion or even an 'interest', follow it. Beware that a PhD is 99% perspiration, 1% inspiration. I have, sadly, seen many PhDs stifling the passion with which they were started. > My goal is to obtain work that interests me, ... Re work: curiously, I recently received an unsolicited email from Google inviting me to 'have a conversation' [managementspeak yeuch!]. This was apparently based on my volume of postings on the forum. (I suspect not on their quality ;-) I suggested that first they look at my LinkedIn page, which would have roughly revealed my age -- already greater than yours will be when you 'come out of school'. Since then, nothing. Nada. Not even an acknowledgement. Rude, I call it. I think you'll find ageism is still rife in the industry. AntC From anthony_clayden at clear.net.nz Tue Dec 3 20:23:19 2013 From: anthony_clayden at clear.net.nz (AntC) Date: Tue, 3 Dec 2013 20:23:19 +0000 (UTC) Subject: [Haskell-cafe] PhD at age 45? References: <416AF7F3-5FE1-4DCD-ADE5-6D6A3422B02E@yandex.ru> Message-ID: > MigMit yandex.ru> writes: > > Don't worry, you don't need PhD to understand monads. > Good one! So what is it that you do need? And how do I get it? ;-) AntC From allbery.b at gmail.com Tue Dec 3 20:31:55 2013 From: allbery.b at gmail.com (Brandon Allbery) Date: Tue, 3 Dec 2013 15:31:55 -0500 Subject: [Haskell-cafe] PhD at age 45? In-Reply-To: References: Message-ID: On Tue, Dec 3, 2013 at 3:20 PM, AntC wrote: > Re work: curiously, I recently received an unsolicited email from Google > inviting me to 'have a conversation' [managementspeak yeuch!]. > This was apparently based on my volume of postings on the forum. (I > suspect not on their quality ;-) I suggested that first they look at my > LinkedIn page, which would have roughly revealed my age -- already greater > than yours will be when you 'come out of school'. > > Since then, nothing. Nada. Not even an acknowledgement. Rude, I call it. > Interesting. They're still pinging me every few months, and it is not that hard to find out my age (or even get a good rough estimate by checking usenet archives). -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From coreyoconnor at gmail.com Tue Dec 3 21:29:54 2013 From: coreyoconnor at gmail.com (Corey O'Connor) Date: Tue, 3 Dec 2013 13:29:54 -0800 Subject: [Haskell-cafe] PhD at age 45? In-Reply-To: References: Message-ID: Related: Paths to becoming a professor of CS at age 45 (or so)? I don't have much interest in getting a PhD, but have plenty for teaching CS. Seems like a nice thing to pursue once I'm tired of industry. haha Cheers, Corey -Corey O'Connor coreyoconnor at gmail.com http://corebotllc.com/ On Tue, Dec 3, 2013 at 11:43 AM, Dennis Raddle wrote: > A more specific question than my last post. I guess I'm wondering if it's > a good idea to begin a PhD in CS at age 45 (currently having a BS in CS). > My goal is to obtain work that interests me, work that really draws on the > skills one develops in a PhD program. Work in academia is hard to obtain, I > understand, but I could take an industry job. I'm wondering if I'll just be > postponing a job with no financial gain afterward and poor prospects for > work. Or if there is ageism that will work against a guy coming out of > school at age 52. > > Or, if it will truly lead to an interesting job with good pay. > > Dennis > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From sschuldenzucker at uni-bonn.de Tue Dec 3 21:48:10 2013 From: sschuldenzucker at uni-bonn.de (Steffen Schuldenzucker) Date: Tue, 3 Dec 2013 22:48:10 +0100 Subject: [Haskell-cafe] Google headhunters (was: Re: PhD at age 45?) In-Reply-To: References: Message-ID: <20131203224810.6f932eaba8977dac9f58f203@uni-bonn.de> On Tue, 3 Dec 2013 20:20:37 +0000 (UTC) AntC wrote: > [...] > Re work: curiously, I recently received an unsolicited email from Google > inviting me to 'have a conversation' [managementspeak yeuch!]. > This was apparently based on my volume of postings on the forum. (I > suspect not on their quality ;-) I suggested that first they look at my > LinkedIn page, which would have roughly revealed my age -- already greater > than yours will be when you 'come out of school'. > > Since then, nothing. Nada. Not even an acknowledgement. Rude, I call it. > > I think you'll find ageism is still rife in the industry. Sorry for totally leaving the original topic here, but: Same for me: Got an e-mail from some "technical sourcer", replied (I'll actually be looking for a job soon), never got anything back. - Twice! I imagine they do a > forM_ (users haskell_cafe) $ \u -> > when ("functional" `elem` words (linkedin_page u)) $ send (std_email u) u , but with several agents which don't sync back their results. Doesn't seem to be age-related, though. (I'm 25) -- Steffen -- Steffen Schuldenzucker From trebla at vex.net Tue Dec 3 21:49:49 2013 From: trebla at vex.net (Albert Y. C. Lai) Date: Tue, 03 Dec 2013 16:49:49 -0500 Subject: [Haskell-cafe] PhD at age 45? In-Reply-To: References: Message-ID: <529E51FD.3070907@vex.net> I take a tangent to talk not about what age, but about what minds. Many smart people can solve all kinds of problems but still do poorly in PhD, most dropping out. Why? Because part of PhD is to find your problem, and cut it from open-ended to specifically scoped. Many smart people can solve all kinds of problems, but the problems have to be given to them. (Of course, finding your problem is not enough, you still have to solve it. But you already know this.) Some thesis advisors can suggest pretty specific problems; some schools sometimes actually advertise "PhD position: such-and-such specific project". If you run into one of those, good for you, someone is giving the problem to you, you're like half-done. But this is the minority. The majority is more like: the thesis advisor is too helpful and too open, he/she suggests too many problems and too many variations, so you're none the wiser. :) From achudnov at gmail.com Tue Dec 3 21:51:09 2013 From: achudnov at gmail.com (Andrey Chudnov) Date: Tue, 03 Dec 2013 16:51:09 -0500 Subject: [Haskell-cafe] PhD at age 45? In-Reply-To: References: Message-ID: <529E524D.2080109@gmail.com> Dennis, I think it would make sense for you to try and flesh out the details of the kind of "work that interests" you. I'm sorry, but what you have right now seems to be quite vague. I remember you mentioning that you wanted to teach in your previous post. So if that's really what you want, you don't have to have a PhD (although, of course, it's better to have one). I know several teaching professors (yeah, that's the term we use for the professors that don't engage in research) that don't have a PhD (only MSc) and are great at what they do. So, if I were you, I would try and look for adjunct professor positions: if you are good at teaching, the absence of a PhD probably wouldn't matter; if you are not, it's not like you would have a lot of time in grad school to work on that anyway. Also, "good pay" is generally not an attribute of academic jobs. On 12/03/2013 02:43 PM, Dennis Raddle wrote: > A more specific question than my last post. I guess I'm wondering if > it's a good idea to begin a PhD in CS at age 45 (currently having a BS > in CS). My goal is to obtain work that interests me, work that really > draws on the skills one develops in a PhD program. Work in academia is > hard to obtain, I understand, but I could take an industry job. I'm > wondering if I'll just be postponing a job with no financial gain > afterward and poor prospects for work. Or if there is ageism that will > work against a guy coming out of school at age 52. > > Or, if it will truly lead to an interesting job with good pay. From headprogrammingczar at gmail.com Tue Dec 3 22:05:23 2013 From: headprogrammingczar at gmail.com (Joe Quinn) Date: Tue, 03 Dec 2013 17:05:23 -0500 Subject: [Haskell-cafe] Google headhunters In-Reply-To: <20131203224810.6f932eaba8977dac9f58f203@uni-bonn.de> References: <20131203224810.6f932eaba8977dac9f58f203@uni-bonn.de> Message-ID: <529E55A3.80804@gmail.com> I got the same thing, but based on my github account. The person who contacted me has a consistent LinkedIn account, and his email passed SPF, DKIM, and rPTR. On 12/3/2013 4:48 PM, Steffen Schuldenzucker wrote: > On Tue, 3 Dec 2013 20:20:37 +0000 (UTC) > AntC wrote: >> [...] >> Re work: curiously, I recently received an unsolicited email from Google >> inviting me to 'have a conversation' [managementspeak yeuch!]. >> This was apparently based on my volume of postings on the forum. (I >> suspect not on their quality ;-) I suggested that first they look at my >> LinkedIn page, which would have roughly revealed my age -- already greater >> than yours will be when you 'come out of school'. >> >> Since then, nothing. Nada. Not even an acknowledgement. Rude, I call it. >> >> I think you'll find ageism is still rife in the industry. > Sorry for totally leaving the original topic here, but: > > Same for me: Got an e-mail from some "technical sourcer", replied (I'll actually be looking for a job soon), never got anything back. - Twice! > > I imagine they do a >> forM_ (users haskell_cafe) $ \u -> >> when ("functional" `elem` words (linkedin_page u)) $ send (std_email u) u > , but with several agents which don't sync back their results. > > Doesn't seem to be age-related, though. (I'm 25) > > -- Steffen > From dennis.raddle at gmail.com Tue Dec 3 22:26:36 2013 From: dennis.raddle at gmail.com (Dennis Raddle) Date: Tue, 3 Dec 2013 14:26:36 -0800 Subject: [Haskell-cafe] PhD at age 45? In-Reply-To: <529E524D.2080109@gmail.com> References: <529E524D.2080109@gmail.com> Message-ID: Hi Andrey and list, All replies have been helpful. I realize my question is vague, and that's partly because I don't know what area within CS interests me. I may have to do at least an MS to find out. I've been struggling with health problems for many years, so my work in programming has been part-time, minimal, and not very interesting to me. I'm not in a good position right now to determine what I would really like to do. I can say that my favorite class in college was discrete mathematics. And I can say that I enjoyed learning Haskell, which I am in the process of teaching to myself for personal projects. Oh yeah--I do have some personal projects. One of them is making animated videos to teach algebra, which I am doing in Haskell. And I can say that I enjoy teaching a lot. Maybe I should become a high school teacher! Right now I have a small gig teaching Python and numpy to a local psychiatrist who wants to write software for voice analysis. He is a smart guy, but of course we are starting at the beginning. It's quite pleasureful to see things click in his brain. We are working on just basic ideas, like organization of code into functions and modules. He previously dabbled on his own, and ran into problems with disorganized code, so he really appreciates the ideas I'm presenting. Dennis On Tue, Dec 3, 2013 at 1:51 PM, Andrey Chudnov wrote: > Dennis, > I think it would make sense for you to try and flesh out the details of > the kind of "work that interests" you. I'm sorry, but what you have right > now seems to be quite vague. I remember you mentioning that you wanted to > teach in your previous post. So if that's really what you want, you don't > have to have a PhD (although, of course, it's better to have one). I know > several teaching professors (yeah, that's the term we use for the > professors that don't engage in research) that don't have a PhD (only MSc) > and are great at what they do. So, if I were you, I would try and look for > adjunct professor positions: if you are good at teaching, the absence of a > PhD probably wouldn't matter; if you are not, it's not like you would have > a lot of time in grad school to work on that anyway. > > Also, "good pay" is generally not an attribute of academic jobs. > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Tue Dec 3 23:35:13 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Tue, 3 Dec 2013 18:35:13 -0500 Subject: [Haskell-cafe] existential quantification In-Reply-To: References: <0suuma-i57.ln1@rama.universe> <54kvma-6tl.ln1@rama.universe> Message-ID: yeah, its not an introductory text, but it is a great grad level reference. (nb: i read a draft a few years ago, haven't read the published version... yet) On Tue, Dec 3, 2013 at 1:36 AM, Kim-Ee Yeoh wrote: > > On Tue, Dec 3, 2013 at 11:10 AM, TP wrote: > >> I would like a good "entry point" in the textbook >> literature. Not for experts. >> Are the books of Robert Harper suitable, for example >> >> >> http://www.amazon.com/Practical-Foundations-Programming-Languages-Professor/dp/1107029570 >> > > There's a draft copy on Harper's home page you can check out. > > It's primarily a textbook for CS graduate students entering the > specialization of PL. > > -- Kim-Ee > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From achudnov at gmail.com Tue Dec 3 23:40:33 2013 From: achudnov at gmail.com (Andrey Chudnov) Date: Tue, 03 Dec 2013 18:40:33 -0500 Subject: [Haskell-cafe] PhD at age 45? In-Reply-To: References: <529E524D.2080109@gmail.com> Message-ID: <529E6BF1.7090700@gmail.com> On 12/03/2013 05:26 PM, Dennis Raddle wrote: > All replies have been helpful. I realize my question is vague, and > that's partly because I don't know what area within CS interests me. I > may have to do at least an MS to find out. What I meant was whether you would like to do research or teach (or both) -- not a specific area. While you will probably be required to teach some classes anyway (as a TA, which means grading, supervising labs and consultations), most of your time in grad school pursuing a PhD would be spent on research. That's because producing novel and relevant research results is an absolute requirement for getting a PhD (while teaching a lot of classes, on the other hand, is not). In pursuing a PhD it would help if you enjoy (or at least can tolerate) the very process of research and feel passionate about your research topic. Otherwise, you might be in for quite a few miserable years. From alpmestan at gmail.com Tue Dec 3 23:50:32 2013 From: alpmestan at gmail.com (Alp Mestanogullari) Date: Wed, 4 Dec 2013 00:50:32 +0100 Subject: [Haskell-cafe] Google headhunters In-Reply-To: <529E55A3.80804@gmail.com> References: <20131203224810.6f932eaba8977dac9f58f203@uni-bonn.de> <529E55A3.80804@gmail.com> Message-ID: I have been hit by a few since the beginning of the summer too. All of them were actual recruiters, I exchanged a few emails with some of them and had one on the phone. I think they are expanding a few teams in Europe and are just looking for "more new googlers than usual". On Tue, Dec 3, 2013 at 11:05 PM, Joe Quinn wrote: > I got the same thing, but based on my github account. The person who > contacted me has a consistent LinkedIn account, and his email passed SPF, > DKIM, and rPTR. > > On 12/3/2013 4:48 PM, Steffen Schuldenzucker wrote: > >> On Tue, 3 Dec 2013 20:20:37 +0000 (UTC) >> AntC wrote: >> >>> [...] >>> Re work: curiously, I recently received an unsolicited email from Google >>> inviting me to 'have a conversation' [managementspeak yeuch!]. >>> This was apparently based on my volume of postings on the forum. (I >>> suspect not on their quality ;-) I suggested that first they look at my >>> LinkedIn page, which would have roughly revealed my age -- already >>> greater >>> than yours will be when you 'come out of school'. >>> >>> Since then, nothing. Nada. Not even an acknowledgement. Rude, I call it. >>> >>> I think you'll find ageism is still rife in the industry. >>> >> Sorry for totally leaving the original topic here, but: >> >> Same for me: Got an e-mail from some "technical sourcer", replied (I'll >> actually be looking for a job soon), never got anything back. - Twice! >> >> I imagine they do a >> >>> forM_ (users haskell_cafe) $ \u -> >>> when ("functional" `elem` words (linkedin_page u)) $ send (std_email >>> u) u >>> >> , but with several agents which don't sync back their results. >> >> Doesn't seem to be age-related, though. (I'm 25) >> >> -- Steffen >> >> > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Alp Mestanogullari -------------- next part -------------- An HTML attachment was scrubbed... URL: From kc1956 at gmail.com Tue Dec 3 23:52:00 2013 From: kc1956 at gmail.com (KC) Date: Tue, 3 Dec 2013 15:52:00 -0800 Subject: [Haskell-cafe] PhD at age 45? In-Reply-To: References: Message-ID: Advanced degrees look better the younger you are. However look at Randy Pausch's last lecture. Barriers are there to see if you are truly interested and have the passion. Be aware of the attrition rate of those who start advanced degrees but who never finish their thesis, I believe. I knew of one gentleman who was into his 13th year of a PhD and who talked to me about "them" threatening to cut off his funding. :D On Dec 3, 2013 11:43 AM, "Dennis Raddle" wrote: > A more specific question than my last post. I guess I'm wondering if it's > a good idea to begin a PhD in CS at age 45 (currently having a BS in CS). > My goal is to obtain work that interests me, work that really draws on the > skills one develops in a PhD program. Work in academia is hard to obtain, I > understand, but I could take an industry job. I'm wondering if I'll just be > postponing a job with no financial gain afterward and poor prospects for > work. Or if there is ageism that will work against a guy coming out of > school at age 52. > > Or, if it will truly lead to an interesting job with good pay. > > Dennis > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ok at cs.otago.ac.nz Wed Dec 4 01:20:07 2013 From: ok at cs.otago.ac.nz (Richard A. O'Keefe) Date: Wed, 4 Dec 2013 14:20:07 +1300 Subject: [Haskell-cafe] PhD at age 45? In-Reply-To: References: <529E524D.2080109@gmail.com> Message-ID: <20EAA1FA-AF92-4A6F-AEF0-0CCF07A51F99@cs.otago.ac.nz> On 4/12/2013, at 11:26 AM, Dennis Raddle wrote: > Hi Andrey and list, > > All replies have been helpful. I realize my question is vague, and that's partly because I don't know what area within CS interests me. I may have to do at least an MS to find out. As someone who has supervised a number of MSc and PhD students, let me say "absolutely!" to that. Quite a lot depends on the student, quite a lot on the supervisor, and quite a lot on the working relationship between them. Your supervisor will help you with University administration procedures; your supervisor will help you look for funds; your supervisor will direct your attention to relevant related research; your supervisor will help you understand novel technical material; your supervisor will in fact be quite a helpful person. BUT your supervisor is going to expect you to take responsibility for your own work and to do it. Some of it is going to be really enjoyable, thinking up new algorithms or data structures or analysis methods or whatever. Some of it is going to be DRUDGERY grinding through getting the experimental results to show that your ideas _work_. And for a lot of students, a major thing that will help you get through the drudgery is the feeling "This is *MY* project; d--n the supervisor, *I* want the results!" > I've been struggling with health problems for many years, so my work in programming has been part-time, minimal, and not very interesting to me. I'm not in a good position right now to determine what I would really like to do. Health problems need not be an issue. I can't speak for universities where you live, but this one is pretty supportive of people with health and disability problems. As for what you would really like to do, there's really no substitute for talking to people to find out what it's like. Had you considered going to _any_ nearby University with a CS school and asking around if anyone needs a part time research assistant? That will give you an insider's view of what it's like to do research. > Right now I have a small gig teaching Python and numpy to a local psychiatrist who wants to write software for voice analysis. He is a smart guy, but of course we are starting at the beginning. It's quite pleasureful to see things click in his brain. We are working on just basic ideas, like organization of code into functions and modules. He previously dabbled on his own, and ran into problems with disorganized code, so he really appreciates the ideas I'm presenting. Have you looked at Keng-hao Chang's PhD thesis "Speech Analysis Methodologies towards Unobtrusive Mental Health Monitoring"? http://www.eecs.berkeley.edu/Pubs/TechRpts/2012/EECS-2012-55.pdf His AMMON library might be of course to you, but I was thinking that reading a PhD in an area related to something you are currently working on might be illuminating. From dennis.raddle at gmail.com Wed Dec 4 01:58:03 2013 From: dennis.raddle at gmail.com (Dennis Raddle) Date: Tue, 3 Dec 2013 17:58:03 -0800 Subject: [Haskell-cafe] PhD at age 45? In-Reply-To: <529E6BF1.7090700@gmail.com> References: <529E524D.2080109@gmail.com> <529E6BF1.7090700@gmail.com> Message-ID: Andrey, Ah, I see. Well, I guess I like both teaching and research. I don't have enough experience with either to do which I prefer more, or whether I would be happy doing just one of them for the rest of my life. But I would definitely be fascinated by the work on my PhD thesis. By the way, I did very well in national science fairs in high school (with a discrete mathematics topic). I mention this just to say that I love research and that I'm self-motivated to learn. It was poor health that derailed my plans earlier in life to get a PhD. Regarding my love for teaching, I have tutored high school students in algebra and I'm currently tutoring a doctor in Python programming. I love this. So note--I don't need to be teaching an advanced topic to be happy. I'm fascinated by how to make a topic understandable, whether it would be teaching a graduate-level class, or figuring out how to help high school students who struggle with algebra. So I guess one way to approach this question is to ask - what path offers me good *options* (i.e., I can spin from there into any number of possibilities depending on what I learn that I love most) - what downside is there to a PhD (i.e., possible student loan debt, deferring earned income and saving for retirement years which are merely 25 years away for me, and merely 18 years after I would probably start earning again, hard time finding work? [overqualified for everything?], etc.) Regarding financial considerations and retirement, one question to ask is-- would I be happy doing my job until age 80? I.e. would I love my job so much that I don't feel a need to retire? I think that I could potentially love both interesting research and fascinating teaching enough. But a boring garden-variety programming job, like the one I had before? Yuck. Couldn't wait to retire. Dennis On Tue, Dec 3, 2013 at 3:40 PM, Andrey Chudnov wrote: > On 12/03/2013 05:26 PM, Dennis Raddle wrote: > >> All replies have been helpful. I realize my question is vague, and that's >> partly because I don't know what area within CS interests me. I may have to >> do at least an MS to find out. >> > What I meant was whether you would like to do research or teach (or both) > -- not a specific area. While you will probably be required to teach some > classes anyway (as a TA, which means grading, supervising labs and > consultations), most of your time in grad school pursuing a PhD would be > spent on research. That's because producing novel and relevant research > results is an absolute requirement for getting a PhD (while teaching a lot > of classes, on the other hand, is not). In pursuing a PhD it would help if > you enjoy (or at least can tolerate) the very process of research and feel > passionate about your research topic. Otherwise, you might be in for quite > a few miserable years. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Wed Dec 4 03:21:32 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Tue, 3 Dec 2013 22:21:32 -0500 Subject: [Haskell-cafe] PhD at age 45? In-Reply-To: <20EAA1FA-AF92-4A6F-AEF0-0CCF07A51F99@cs.otago.ac.nz> References: <529E524D.2080109@gmail.com> <20EAA1FA-AF92-4A6F-AEF0-0CCF07A51F99@cs.otago.ac.nz> Message-ID: i second some of these points, quite emphatically. Well said richard! -Carter On Tue, Dec 3, 2013 at 8:20 PM, Richard A. O'Keefe wrote: > > On 4/12/2013, at 11:26 AM, Dennis Raddle wrote: > > > Hi Andrey and list, > > > > All replies have been helpful. I realize my question is vague, and > that's partly because I don't know what area within CS interests me. I may > have to do at least an MS to find out. > > As someone who has supervised a number of MSc and PhD students, > let me say "absolutely!" to that. Quite a lot depends on the > student, quite a lot on the supervisor, and quite a lot on the > working relationship between them. Your supervisor will help you > with University administration procedures; your supervisor will > help you look for funds; your supervisor will direct your > attention to relevant related research; your supervisor will help > you understand novel technical material; your supervisor will in > fact be quite a helpful person. BUT your supervisor is going to > expect you to take responsibility for your own work and to do it. > Some of it is going to be really enjoyable, thinking up new > algorithms or data structures or analysis methods or whatever. > Some of it is going to be DRUDGERY grinding through getting the > experimental results to show that your ideas _work_. And for a > lot of students, a major thing that will help you get through > the drudgery is the feeling "This is *MY* project; d--n the > supervisor, *I* want the results!" > > > I've been struggling with health problems for many years, so my work in > programming has been part-time, minimal, and not very interesting to me. > I'm not in a good position right now to determine what I would really like > to do. > > Health problems need not be an issue. I can't speak for universities > where you live, but this one is pretty supportive of people with > health and disability problems. > > As for what you would really like to do, there's really no > substitute for talking to people to find out what it's like. > > Had you considered going to _any_ nearby University with a CS > school and asking around if anyone needs a part time research > assistant? That will give you an insider's view of what it's > like to do research. > > > Right now I have a small gig teaching Python and numpy to a local > psychiatrist who wants to write software for voice analysis. He is a smart > guy, but of course we are starting at the beginning. It's quite pleasureful > to see things click in his brain. We are working on just basic ideas, like > organization of code into functions and modules. He previously dabbled on > his own, and ran into problems with disorganized code, so he really > appreciates the ideas I'm presenting. > > Have you looked at Keng-hao Chang's PhD thesis > "Speech Analysis Methodologies towards Unobtrusive > Mental Health Monitoring"? > http://www.eecs.berkeley.edu/Pubs/TechRpts/2012/EECS-2012-55.pdf > His AMMON library might be of course to you, > but I was thinking that reading a PhD in an area related to > something you are currently working on might be illuminating. > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From krismicinski at gmail.com Wed Dec 4 03:47:32 2013 From: krismicinski at gmail.com (Kristopher Micinski) Date: Tue, 3 Dec 2013 22:47:32 -0500 Subject: [Haskell-cafe] PhD at age 45? In-Reply-To: References: <529E524D.2080109@gmail.com> Message-ID: On Tue, Dec 3, 2013 at 5:26 PM, Dennis Raddle wrote: > Hi Andrey and list, > > All replies have been helpful. I realize my question is vague, and that's > partly because I don't know what area within CS interests me. I may have to > do at least an MS to find out. > > I've been struggling with health problems for many years, so my work in > programming has been part-time, minimal, and not very interesting to me. > I'm not in a good position right now to determine what I would really like > to do. > > I can say that my favorite class in college was discrete mathematics. And > I can say that I enjoyed learning Haskell, which I am in the process of > teaching to myself for personal projects. > > Oh yeah--I do have some personal projects. One of them is making animated > videos to teach algebra, which I am doing in Haskell. > > And I can say that I enjoy teaching a lot. Maybe I should become a high > school teacher! > > Right now I have a small gig teaching Python and numpy to a local > psychiatrist who wants to write software for voice analysis. He is a smart > guy, but of course we are starting at the beginning. It's quite pleasureful > to see things click in his brain. We are working on just basic ideas, like > organization of code into functions and modules. He previously dabbled on > his own, and ran into problems with disorganized code, so he really > appreciates the ideas I'm presenting. > I can think of a few potentially relevant points: - The only reason to do a PhD is because you want to learn how to do research on a very specific problem. - Being unsure of what you want to do is usually at odds with finishing your PhD. Doing a PhD --- at some level --- means allowing yourself to focus on a specific problem and not feel too tempted by other areas. - A PhD isn't really about learning, it's more about doing. - Lots of people start PhD programs because they were passionate about learning (or are the kind of people that romanticize it) as undergrads, or feel generally upset with the daily grind of work in industry, hoping that doing a PhD will change this. Doing a PhD still involves a huge amount of "the daily grind," but is nonetheless rewarding in ways that industry may not be. - MS programs can cost quite a bit of money, which is something to keep in mind: since I doubt you want to sink thousands of dollars in something that may be ultimately unnecessary. Some schools fun MS students through TA positions, but you'll have to ask. - Getting in to PhD programs can be quite difficult, especially for nonstandard applicants (e.g., without a BS in CS from a strong undergrad school with a great GPA and high test scores). This is not to say it's in any way impossible. If you're a nonstandard applicant and love doing research, you should look for great *people* to work with at schools outside of the top ~50. Rankings say very little about the quality of the faculty, but say a great deal about admissions difficulty. - If you ultimately want a PhD, getting an MS is unnecessary (at Maryland most people with MS degrees only have them because they worked in industry for a while). However, if you don't have a traditional CS background, it may be a good way to qualify yourself for PhD programs and make connections with faculty members. Overall, I think it's unwise to strongly consider PhD programs without a solid lead on your research area. Doing a PhD is a big thing, and all about research. In practice, the people that I know that do best at their PhDs don't get them because they want PhDs, it's more like "well, I really loved topic X, and it turns out if you do X long enough, and publish in obscure journals advancing the state of X, they eventually give you a PhD, because that incremental delta to human knowledge is called research." If you like teaching, but not research, it might be better to get an MS for *breadth* in CS, and then look at teaching opportunities. I agree with Dennis, however, looking to help people out may provide some insight. Then again, jumping in to an active research can be very difficult, and faculty may be hesitant to accept help from outside their department for a variety of logistical purposes (faculty typically have very little free time). However, most faculty organize some sort of reading group or seminar in their area. These are typically more open to outsiders. The best way to find out is to find faculty near you, download some of their most recent papers, and see if you can understand any. If you find some that look interesting, you can acquire more background knowledge by reading in the area (e.g., Types and Programming Languages, Software Foundations, and Certified Programming with Dependent Types, would be texts for PL). Then you might contact the faculty members and ask if they sponsored any open seminars for you to attend. Kris -------------- next part -------------- An HTML attachment was scrubbed... URL: From dennis.raddle at gmail.com Wed Dec 4 07:57:42 2013 From: dennis.raddle at gmail.com (Dennis Raddle) Date: Tue, 3 Dec 2013 23:57:42 -0800 Subject: [Haskell-cafe] PhD at age 45? In-Reply-To: References: <529E524D.2080109@gmail.com> Message-ID: On Tue, Dec 3, 2013 at 7:47 PM, Kristopher Micinski wrote: > > > I can think of a few potentially relevant points: > - The only reason to do a PhD is because you want to learn how to do > research on a very specific problem. > Thanks, Kristopher, you really made sense. What I hear you saying is that you get a PhD to do research on a problem that fascinates you. You shouldn't get a PhD if you are only doing it for what happens afterward. Are there any MOOCs on reasoning about software correctness? I just remembered that I've always enjoy proving my programs correct (with the limited resources I had) but I don't know anything formal about this. This also seems like a practical topic... seeing how much of the vital world is run by software. In the meantime I still have a lot of free time so I think I'm going to get out my calculus and discrete math books and start reviewing. Then I'll look over courses normally required for the BS and make sure I'm solid on them. Along the way I hope to run into a topic I like. I'll look up the local professors and see if they are looking for assistants, or even just volunteer tutoring. There might not be any local profs doing software verification/correctness proofs so maybe I could find someone out of the area who would be open to a phone call and working by email. Dennis -------------- next part -------------- An HTML attachment was scrubbed... URL: From jan.stolarek at p.lodz.pl Wed Dec 4 08:45:48 2013 From: jan.stolarek at p.lodz.pl (Jan Stolarek) Date: Wed, 4 Dec 2013 09:45:48 +0100 Subject: [Haskell-cafe] Google headhunters In-Reply-To: References: <529E55A3.80804@gmail.com> Message-ID: <201312040945.48382.jan.stolarek@p.lodz.pl> Same here, except that I got a reply to my reply :-) Janek Dnia ?roda, 4 grudnia 2013, Alp Mestanogullari napisa?: > I have been hit by a few since the beginning of the summer too. All of them > were actual recruiters, I exchanged a few emails with some of them and had > one on the phone. I think they are expanding a few teams in Europe and are > just looking for "more new googlers than usual". > > On Tue, Dec 3, 2013 at 11:05 PM, Joe Quinn wrote: > > I got the same thing, but based on my github account. The person who > > contacted me has a consistent LinkedIn account, and his email passed SPF, > > DKIM, and rPTR. > > > > On 12/3/2013 4:48 PM, Steffen Schuldenzucker wrote: > >> On Tue, 3 Dec 2013 20:20:37 +0000 (UTC) > >> > >> AntC wrote: > >>> [...] > >>> Re work: curiously, I recently received an unsolicited email from > >>> Google inviting me to 'have a conversation' [managementspeak yeuch!]. > >>> This was apparently based on my volume of postings on the forum. (I > >>> suspect not on their quality ;-) I suggested that first they look at my > >>> LinkedIn page, which would have roughly revealed my age -- already > >>> greater > >>> than yours will be when you 'come out of school'. > >>> > >>> Since then, nothing. Nada. Not even an acknowledgement. Rude, I call > >>> it. > >>> > >>> I think you'll find ageism is still rife in the industry. > >> > >> Sorry for totally leaving the original topic here, but: > >> > >> Same for me: Got an e-mail from some "technical sourcer", replied (I'll > >> actually be looking for a job soon), never got anything back. - Twice! > >> > >> I imagine they do a > >> > >>> forM_ (users haskell_cafe) $ \u -> > >>> when ("functional" `elem` words (linkedin_page u)) $ send (std_email > >>> u) u > >> > >> , but with several agents which don't sync back their results. > >> > >> Doesn't seem to be age-related, though. (I'm 25) > >> > >> -- Steffen > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe From miguelimo38 at yandex.ru Wed Dec 4 08:59:00 2013 From: miguelimo38 at yandex.ru (Miguel Mitrofanov) Date: Wed, 04 Dec 2013 12:59:00 +0400 Subject: [Haskell-cafe] Google headhunters In-Reply-To: <201312040945.48382.jan.stolarek@p.lodz.pl> References: <529E55A3.80804@gmail.com> <201312040945.48382.jan.stolarek@p.lodz.pl> Message-ID: <327751386147540@web9m.yandex.ru> OK, seems like there are a lot of people interested in this, so I think I'll share my own experience. I've got the same invitation, from a guy called "Robert Campbell". He asked me for my resume, which I've sent him, but, mistakenly, omitting my Skype id. He then called me on my cell, from GB, judging by the phone prefix. The connection was poor, I had to ask him to repeat his questions several times. He tried to convince me that there is only one flavor of quicksort and didn't understand me when I mentioned different approaches at choosing pivots. Then he asked something else about quicksort that I didn't understand, but before I managed to even understand what he wants we got disconnected. He called me again, but this time I couldn't hear him at all and we've got disconnected again. Then he called again, but hung up before I even managed to take his call. That ended our "conversation". I didn't try to contact him again. 04.12.2013, 12:46, "Jan Stolarek" : > Same here, except that I got a reply to my reply :-) > > Janek > > Dnia ?roda, 4 grudnia 2013, Alp Mestanogullari napisa?: > >> ?I have been hit by a few since the beginning of the summer too. All of them >> ?were actual recruiters, I exchanged a few emails with some of them and had >> ?one on the phone. I think they are expanding a few teams in Europe and are >> ?just looking for "more new googlers than usual". >> >> ?On Tue, Dec 3, 2013 at 11:05 PM, Joe Quinn wrote: >>> ?I got the same thing, but based on my github account. The person who >>> ?contacted me has a consistent LinkedIn account, and his email passed SPF, >>> ?DKIM, and rPTR. >>> >>> ?On 12/3/2013 4:48 PM, Steffen Schuldenzucker wrote: >>>> ?On Tue, 3 Dec 2013 20:20:37 +0000 (UTC) >>>> >>>> ?AntC wrote: >>>>> ?[...] >>>>> ?Re work: curiously, I recently received an unsolicited email from >>>>> ?Google inviting me to 'have a conversation' [managementspeak yeuch!]. >>>>> ?This was apparently based on my volume of postings on the forum. (I >>>>> ?suspect not on their quality ;-) I suggested that first they look at my >>>>> ?LinkedIn page, which would have roughly revealed my age -- already >>>>> ?greater >>>>> ?than yours will be when you 'come out of school'. >>>>> >>>>> ?Since then, nothing. Nada. Not even an acknowledgement. Rude, I call >>>>> ?it. >>>>> >>>>> ?I think you'll find ageism is still rife in the industry. >>>> ?Sorry for totally leaving the original topic here, but: >>>> >>>> ?Same for me: Got an e-mail from some "technical sourcer", replied (I'll >>>> ?actually be looking for a job soon), never got anything back. - Twice! >>>> >>>> ?I imagine they do a >>>>> ?forM_ (users haskell_cafe) $ \u -> >>>>> ????when ("functional" `elem` words (linkedin_page u)) $ send (std_email >>>>> ?u) u >>>> ?, but with several agents which don't sync back their results. >>>> >>>> ?Doesn't seem to be age-related, though. (I'm 25) >>>> >>>> ?-- Steffen >>> ?_______________________________________________ >>> ?Haskell-Cafe mailing list >>> ?Haskell-Cafe at haskell.org >>> ?http://www.haskell.org/mailman/listinfo/haskell-cafe > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From illissius at gmail.com Wed Dec 4 10:13:51 2013 From: illissius at gmail.com (=?ISO-8859-1?Q?G=E1bor_Lehel?=) Date: Wed, 4 Dec 2013 11:13:51 +0100 Subject: [Haskell-cafe] Google headhunters In-Reply-To: <529E55A3.80804@gmail.com> References: <20131203224810.6f932eaba8977dac9f58f203@uni-bonn.de> <529E55A3.80804@gmail.com> Message-ID: The surprising thing to me about all this is that I thought Google only hires Ph. D.s who solve difficult mathematical problems displayed on billboards. On Tue, Dec 3, 2013 at 11:05 PM, Joe Quinn wrote: > I got the same thing, but based on my github account. The person who > contacted me has a consistent LinkedIn account, and his email passed SPF, > DKIM, and rPTR. > > On 12/3/2013 4:48 PM, Steffen Schuldenzucker wrote: > >> On Tue, 3 Dec 2013 20:20:37 +0000 (UTC) >> AntC wrote: >> >>> [...] >>> Re work: curiously, I recently received an unsolicited email from Google >>> inviting me to 'have a conversation' [managementspeak yeuch!]. >>> This was apparently based on my volume of postings on the forum. (I >>> suspect not on their quality ;-) I suggested that first they look at my >>> LinkedIn page, which would have roughly revealed my age -- already >>> greater >>> than yours will be when you 'come out of school'. >>> >>> Since then, nothing. Nada. Not even an acknowledgement. Rude, I call it. >>> >>> I think you'll find ageism is still rife in the industry. >>> >> Sorry for totally leaving the original topic here, but: >> >> Same for me: Got an e-mail from some "technical sourcer", replied (I'll >> actually be looking for a job soon), never got anything back. - Twice! >> >> I imagine they do a >> >>> forM_ (users haskell_cafe) $ \u -> >>> when ("functional" `elem` words (linkedin_page u)) $ send (std_email >>> u) u >>> >> , but with several agents which don't sync back their results. >> >> Doesn't seem to be age-related, though. (I'm 25) >> >> -- Steffen >> >> > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Your ship was destroyed in a monadic eruption. -------------- next part -------------- An HTML attachment was scrubbed... URL: From jan.stolarek at p.lodz.pl Wed Dec 4 11:09:31 2013 From: jan.stolarek at p.lodz.pl (Jan Stolarek) Date: Wed, 4 Dec 2013 12:09:31 +0100 Subject: [Haskell-cafe] Google headhunters In-Reply-To: References: <529E55A3.80804@gmail.com> Message-ID: <201312041209.31165.jan.stolarek@p.lodz.pl> > The surprising thing to me about all this is that I thought Google only > hires Ph. D.s who solve difficult mathematical problems displayed on > billboards. Haha :-) And I - being a PhD and working at the university - was really surprised to be offered an "engineering position". Janek From ollie at ocharles.org.uk Wed Dec 4 11:21:17 2013 From: ollie at ocharles.org.uk (Oliver Charles) Date: Wed, 04 Dec 2013 11:21:17 +0000 Subject: [Haskell-cafe] Writer + log each computation to stdout In-Reply-To: <20131126102517.40535.qmail@www1.g3.pair.com> References: <20131126102517.40535.qmail@www1.g3.pair.com> Message-ID: <529F102D.40602@ocharles.org.uk> On 11/26/2013 10:25 AM, oleg at okmij.org wrote: > Extensible Effects designed specifically to separate a client (the > requestor of an action) from a handler, the executor of an action. A > logging client merely requests a string to be logged. It has no idea > what happens when that request is executed. Therefore, the same > client can be used with several handlers, even within the same > expression. One can also build various interceptors, such as > logIntercept, which is similar to Unix' tee. > > The following file illustrates how to solve the problem with all three > scenarios. > http://okmij.org/ftp/ Did you forget to attach a file to this email? Otherwise, I'm not sure where to find the file you're talking about and I couldn't find it on your homepage either. - ocharles -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 490 bytes Desc: OpenPGP digital signature URL: From agocorona at gmail.com Wed Dec 4 11:51:16 2013 From: agocorona at gmail.com (Alberto G. Corona ) Date: Wed, 4 Dec 2013 12:51:16 +0100 Subject: [Haskell-cafe] Writer + log each computation to stdout In-Reply-To: <20131125225420.GC5516@bry-m6300> References: <20131125225420.GC5516@bry-m6300> Message-ID: The Workflow package does logging (and recovery), and you can orchestrate the process using the normal do notation. You can also inspect the log after or during the process. You can also stop and restart it. main= exec1 "weekllystuff" $ do result <- step mylittleprocess1 result2 <- step mylittleprocess2 . ... At the end you have a single log with the intermediate result (in the folder .tcachedata/workflows) . If it is interrupted at any step, re-executing the program continue in the following step. if you use read-show instances for the intermediate result, the log will be textual and you can inspect it with a text editor. 2013/11/25 Bryan Vicknair > Hello, > > I have a bunch of little database IO functions. Each does something to the > database, and returns a log string describing what it did, and possibly a > meaningful result from the database. > > query :: IO (String, a) > update :: a -> IO (String, ()) > > ...and a few functions that orchestrate all the little functions into doing > useful work. > > syncWeek :: Week -> IO () > syncAll : : IO () > > > I don't want the individual functions to know what is done with the log > string > describing what they did. Top-level orchestrating functions should make > that > decision, which can be one of: > > 1) Collect and print all to a log once all computations are done. > 2) Print to stdout *as each computation is run*. > 3) Ignore them. > > Here is my understanding of how common monads would handle these > requirements: > > Writer: 1 and 3 are easy. This is what I originally attempted to use, but > I > couldn't figure out how to accomplish #2. > Reader: 2 and 3 can be accomplished if each function reads a shouldLog > config > variable from the reader and does a putStrLn depending on the > value. > Very ugly, as now each function has to know how to log output. > State: Not sure, but the Writer docs in the transformers package points to > this monad as maybe solving requirement #2 above. > > The use case is that when I call the top-level functions from a command > line > script, I want to see logging happening in real-time to stdout, but I may > call > the same top-level functions from a larger application that may be logging > to > somewhere other than stdout, and may call the top-level functions from yet > another larger application which doesn't want anything to be logged. > > How can I glue together a bunch of smaller computations, which may call > each other, and decide at a higher level what to do with the logging > result of > each computation? Seems like a perfect fit for Writer, except for the > requirement to be able to print to stdout at each step. > > > Bryan Vicknair > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Alberto. -------------- next part -------------- An HTML attachment was scrubbed... URL: From capn.freako at gmail.com Wed Dec 4 13:38:31 2013 From: capn.freako at gmail.com (David Banas) Date: Wed, 4 Dec 2013 05:38:31 -0800 Subject: [Haskell-cafe] Trouble cabal installing uniplate? Message-ID: Has anyone else bumped into this error, when cabal installing uniplate? Data/Generics/Uniplate/Direct.hs:78:4: error: invalid preprocessing directive #-} ^ 1 error generated. Failed to install uniplate-1.6.11 Thanks, -db -------------- next part -------------- An HTML attachment was scrubbed... URL: From nicolas.wu at gmail.com Wed Dec 4 14:12:25 2013 From: nicolas.wu at gmail.com (Nicolas Wu) Date: Wed, 4 Dec 2013 14:12:25 +0000 Subject: [Haskell-cafe] Trouble cabal installing uniplate? In-Reply-To: References: Message-ID: I had a similar error on another package, but that was because I'm on OS X and upgraded to XCode 5. See this email for more details: http://www.haskell.org/pipermail/haskell-cafe/2013-September/110320.html On Wed, Dec 4, 2013 at 1:38 PM, David Banas wrote: > Has anyone else bumped into this error, when cabal installing uniplate? > > Data/Generics/Uniplate/Direct.hs:78:4: > error: invalid preprocessing directive > #-} > ^ > 1 error generated. > Failed to install uniplate-1.6.11 > > > Thanks, > -db > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From krismicinski at gmail.com Wed Dec 4 16:41:15 2013 From: krismicinski at gmail.com (Kristopher Micinski) Date: Wed, 4 Dec 2013 11:41:15 -0500 Subject: [Haskell-cafe] PhD at age 45? In-Reply-To: References: <529E524D.2080109@gmail.com> Message-ID: On Wed, Dec 4, 2013 at 2:57 AM, Dennis Raddle wrote: > > > > On Tue, Dec 3, 2013 at 7:47 PM, Kristopher Micinski < > krismicinski at gmail.com> wrote: > >> >> >> I can think of a few potentially relevant points: >> - The only reason to do a PhD is because you want to learn how to do >> research on a very specific problem. >> > > > Thanks, Kristopher, you really made sense. What I hear you saying is that > you get a PhD to do research on a problem that fascinates you. You > shouldn't get a PhD if you are only doing it for what happens afterward. > > Are there any MOOCs on reasoning about software correctness? I just > remembered that I've always enjoy proving my programs correct (with the > limited resources I had) but I don't know anything formal about this. This > also seems like a practical topic... seeing how much of the vital world is > run by software. > I don't know of any MOOCs, but there are lots of resources to learn such things. I mentioned a few of them in my last post, but learning about program verification / certified program development is a fairly huge and well researched area. The "Software Foundations" book is very helpful. > In the meantime I still have a lot of free time so I think I'm going to > get out my calculus and discrete math books and start reviewing. Then I'll > look over courses normally required for the BS and make sure I'm solid on > them. Along the way I hope to run into a topic I like. I'll look up the > local professors and see if they are looking for assistants, or even just > volunteer tutoring. > You might try looking at their projects. They are very unlikely to be looking for tutors, since few tenure track faculty at research universities need tutors for their classes (they already have TAs). There might not be any local profs doing software verification/correctness > proofs so maybe I could find someone out of the area who would be open to a > phone call and working by email. > I would also look into open source projects. Not to be too much of a dream killer, but professors are unlikely to want to work with a non grad student at their university, simply because of a lack of free time and accessibility to you personally. (At the very least, this seems like something that most faculty I know would be hesitant to do because it's not at all in their best interests...) Kris -------------- next part -------------- An HTML attachment was scrubbed... URL: From trebla at vex.net Wed Dec 4 19:35:12 2013 From: trebla at vex.net (Albert Y. C. Lai) Date: Wed, 04 Dec 2013 14:35:12 -0500 Subject: [Haskell-cafe] Need help: Cabal rejecting stringsearch, conflict in base In-Reply-To: References: Message-ID: <529F83F0.6060700@vex.net> On 13-11-29 06:36 PM, Thiago Negri wrote: > Is `rm -rf ~/.ghc ~/.cabal` supposed to reset cabal installation? > How do I start a fresh cabal environment? Perhaps it is time to read my http://www.vex.net/~trebla/haskell/sicp.xhtml > I recompiled xmonad and it's ok, but xmobar is failing to build because > "unix" package is failing because "Signals.h" is missing (used by > System.Posix.Signals). The "unix" package comes with GHC. It is not supposed to be missing, and not supposed to be rebuilt a la carte. You may have damaged your GHC installation, or you may have completely misattributed the problem. From trebla at vex.net Wed Dec 4 19:43:32 2013 From: trebla at vex.net (Albert Y. C. Lai) Date: Wed, 04 Dec 2013 14:43:32 -0500 Subject: [Haskell-cafe] Cannot find HS*.o linked object for loading into ghci after last update In-Reply-To: References: Message-ID: <529F85E4.1090301@vex.net> On 13-11-27 07:07 AM, Thiago Padilha wrote: > After last update, cabal-install stopped generating an HSfoo-VERSION.o(assuming > the package name is 'foo') in the dist/build directory. I cannot reproduce the problem. Works for me. $ ls LICENSE Options optparse-applicative.cabal README.md Setup.hs tests $ cabal configure Resolving dependencies... Configuring optparse-applicative-0.7.0.2... $ cabal build Building optparse-applicative-0.7.0.2... Preprocessing library optparse-applicative-0.7.0.2... [...] $ ls dist/build autogen HSoptparse-applicative-0.7.0.2.o libHSoptparse-applicative-0.7.0.2.a Options HSoptparse-applicative-0.7.0.2.o is right there. How can I reproduce the problem? From dennis.raddle at gmail.com Wed Dec 4 21:25:54 2013 From: dennis.raddle at gmail.com (Dennis Raddle) Date: Wed, 4 Dec 2013 13:25:54 -0800 Subject: [Haskell-cafe] PhD at age 45? In-Reply-To: References: <529E524D.2080109@gmail.com> Message-ID: On Wed, Dec 4, 2013 at 8:41 AM, Kristopher Micinski wrote: > > > > On Wed, Dec 4, 2013 at 2:57 AM, Dennis Raddle wrote: > >> >> >> > There might not be any local profs doing software verification/correctness >> proofs so maybe I could find someone out of the area who would be open to a >> phone call and working by email. >> > > I would also look into open source projects. Not to be too much of a > dream killer, but professors are unlikely to want to work with a non grad > student at their university, simply because of a lack of free time and > accessibility to you personally. (At the very least, this seems like > something that most faculty I know would be hesitant to do because it's not > at all in their best interests...) > Just FYI, at the California State University system, which only offers up to the Master's, at two local universities I was told they would welcome a volunteer tutor. Maybe they don't have TAs. I was also told I could contribute to the research of a particular M.S. student who was struggling. Dennis -------------- next part -------------- An HTML attachment was scrubbed... URL: From oleg at okmij.org Thu Dec 5 01:05:09 2013 From: oleg at okmij.org (oleg at okmij.org) Date: 5 Dec 2013 01:05:09 -0000 Subject: [Haskell-cafe] Writer + log each computation to stdout In-Reply-To: <529F102D.40602@ocharles.org.uk> Message-ID: <20131205010509.76912.qmail@www1.g3.pair.com> > Extensible Effects designed specifically to separate a client (the > requestor of an action) from a handler, the executor of an action. A > logging client merely requests a string to be logged. It has no idea > what happens when that request is executed. Therefore, the same > client can be used with several handlers, even within the same > expression. One can also build various interceptors, such as > logIntercept, which is similar to Unix' tee. > > The following file illustrates how to solve the problem with all three > scenarios. > http://okmij.org/ftp/ I forgot to complete the link! I'm very sorry. Here is the correct link to the code solving the posed problem: http://okmij.org/ftp/Haskell/extensible/WriterEx.hs From kwangyul.seo at gmail.com Thu Dec 5 06:00:51 2013 From: kwangyul.seo at gmail.com (KwangYul Seo) Date: Thu, 5 Dec 2013 15:00:51 +0900 Subject: [Haskell-cafe] Simple script to make existing GHC or HP installation work with Xcode 5 In-Reply-To: References: Message-ID: Hi, Your script works well on my machine (OS X 10.9 and Xcode 5) though it emits the following warning while running configure: configure: WARNING: unrecognized options: --with-compiler, --with-gcc BTW, the script does not locate where my settings is. I installed Haskell Platform using Homebrew and the settings file is under /usr/local/Cellar/ghc/7.6.3/lib/ghc-7.6.3/settings. It would be good if your script checks this directory too for Homebrew users. Thanks, Kwang Yul Seo On Thu, Oct 31, 2013 at 4:04 PM, Mark Lentczner wrote: > Friends - > > I've developed a simple shell script that should enable your existing GHC > 7. or HP installation work with Xcode 5. > > https://gist.github.com/mzero/7245290 > > > Place that script somewhere, make it executable, and run it. > *Then follow the instructions it tells you!* > You will end up having to run it more than once: > > First time it will tell you where to install a copy of the script > > Second time it will patch your GHC settings file(s) > > > The script is safe to install and setup before you upgrade to Xcode 5, as > it reverts to "getting out of the way" if it detects Xcode 4 based > installation. > > It has been tested on two machines: > > - OS X 10.8 and Xcode 4 > - OS X 10.9 and Xcode 5 > > If a few more intrepid souls test it and it works, I'll post instructions > in more prominent places! > I'll be testing OS X 10.9 and Xcode 4, tomorrow, and expect it should work > fine on OS X10.8 with Xcode 5. But looking for reports that it all works. > > - Mark "Mac Packager" Lentczner > > > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Thu Dec 5 06:05:42 2013 From: allbery.b at gmail.com (Brandon Allbery) Date: Thu, 5 Dec 2013 01:05:42 -0500 Subject: [Haskell-cafe] Simple script to make existing GHC or HP installation work with Xcode 5 In-Reply-To: References: Message-ID: On Thu, Dec 5, 2013 at 1:00 AM, KwangYul Seo wrote: > Your script works well on my machine (OS X 10.9 and Xcode 5) though it > emits the following warning while running configure: > > configure: WARNING: unrecognized options: --with-compiler, --with-gcc > That's got nothing to do with the Xcode 5 compatibility script; I see it on my desktop system which is still 10.8 + Xcode 4, and on my Linux VM for work (which obviously doesn't have Xcode at all). I think it might be related to the new cabal-install (or Cabal library)? -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Thu Dec 5 12:13:33 2013 From: simonpj at microsoft.com (Simon Peyton-Jones) Date: Thu, 5 Dec 2013 12:13:33 +0000 Subject: [Haskell-cafe] RFC: rewrite-with-location proposal In-Reply-To: <20131202220625.GA6022@x200> References: <20131202220625.GA6022@x200> Message-ID: <59543203684B2244980D7E4057D5FBC1486E0A24@DB3EX14MBXC308.europe.corp.microsoft.com> Simon Interesting! There's been lot of work on this kind of thing, mostly collected here: https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack I didn't know about your work, so I've added it. I'd be happy to see progress on this front. Tristan's "Finding the needle" stuff was close to "ready" but there were some awkward points (described in his paper) that meant he didn't feel it was done. To progress this, it'd be helpful to look at his work, articulate what the differences are, perhaps take the best of both, identify weak spots, and figure out what (if anything) should be done about them. We don't want the best to be the enemy of the good, but it's also worth ensuring that we take advantage of all the land-mine-discovery that earlier work has done. Simon | -----Original Message----- | From: Haskell-Cafe [mailto:haskell-cafe-bounces at haskell.org] On Behalf | Of Simon Hengel | Sent: 02 December 2013 22:06 | To: Evan Laforge | Cc: Haskell Cafe | Subject: Re: [Haskell-cafe] RFC: rewrite-with-location proposal | | Hi Evan! | | On Mon, Dec 02, 2013 at 01:43:31PM -0800, Evan Laforge wrote: | > Hey, whatever happened with this? | | My code for this is here: | | https://github.com/sol/ghc/commits/rewrite-with-location | | Revision 03e63f0a70ec8c0fece4049c2d714ea533494ec2 was fully functional, | but it needs to be rebased on current master. The missing feature here | is that type checking only happens on rewrite. I just added a wip | commit with local modifications that do the type checking earlier, when | the module with the rewrite pragma is compiled. | | > Is there anything in the way of getting this merged? Is there some | > way I could help? | | This needs rebasing + I'm not sure if the wip commit currently compiles. | I'm somewhat swamped, so I'm not sure when I'll have time to work on | this. If you want to help, that would be awesome! I'm happy to help | with any questions (solirc on freenode, feel free to say hello in #hspec | ;). | | Cheers, | Simon | _______________________________________________ | Haskell-Cafe mailing list | Haskell-Cafe at haskell.org | http://www.haskell.org/mailman/listinfo/haskell-cafe From tpadilha84 at gmail.com Thu Dec 5 12:31:41 2013 From: tpadilha84 at gmail.com (Thiago Padilha) Date: Thu, 5 Dec 2013 10:31:41 -0200 Subject: [Haskell-cafe] Cannot find HS*.o linked object for loading into ghci after last update In-Reply-To: <529F85E4.1090301@vex.net> References: <529F85E4.1090301@vex.net> Message-ID: I dont know. I just installed the latest cabal(1.18.0.2 for cabal-install and 1.18.1.2 for cabal library) and the HS*.o file is missing. Its possible I have done something to cause this but I just cant figure it out. On Wed, Dec 4, 2013 at 4:43 PM, Albert Y. C. Lai wrote: > On 13-11-27 07:07 AM, Thiago Padilha wrote: >> >> After last update, cabal-install stopped generating an >> HSfoo-VERSION.o(assuming >> the package name is 'foo') in the dist/build directory. > > > I cannot reproduce the problem. Works for me. > > $ ls > LICENSE Options optparse-applicative.cabal README.md Setup.hs tests > $ cabal configure > Resolving dependencies... > Configuring optparse-applicative-0.7.0.2... > $ cabal build > Building optparse-applicative-0.7.0.2... > Preprocessing library optparse-applicative-0.7.0.2... > [...] > $ ls dist/build > autogen HSoptparse-applicative-0.7.0.2.o > libHSoptparse-applicative-0.7.0.2.a Options > > HSoptparse-applicative-0.7.0.2.o is right there. > > How can I reproduce the problem? > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From atzeus at gmail.com Thu Dec 5 14:38:42 2013 From: atzeus at gmail.com (Atze van der Ploeg) Date: Thu, 5 Dec 2013 15:38:42 +0100 Subject: [Haskell-cafe] Return of the revenge of the revisit of the extensible records, reiterated In-Reply-To: References: Message-ID: Dear all, I have written a document describing the design, usage and motivation for these extensible records (now called CTRex, a nod to Trex). It is available at: ====> http://www.haskell.org/haskellwiki/CTRex <====== Improvements, comments and questions welcome! Below are some long overdue responses to comments in this post. Cheers! Atze ================================================== Oleg: You said: > This is all very true. However, if we wish to pass the function f > above the record {y=0, x=0} (with permuted fields), we most likely > wish to pass that function a record {x=0, y=0, z='a'} with more > fields. Most of the time when we deal with extensible records, we > really wish to explore their extensibility. Keeping fields sorted > does not help at all in the latter problem -- we must manually insert > the call to the subtyping coercion function. Once we do that, the > problem with the order of the fields disappears. In my design such coercion calls are unnecessary, or am I missing something here? > I also would like to point out that there are two sorts of > record types. One sort is > Rec [x: Int, y:Bool] > in the imagine syntax. Current HList types are uglier versions of the > above. But there is another sort: > (HasField r x Int, HasField r y Bool) => r > It represents an extensible record type. Extensibility is build in, > and the order of the fields is immaterial. Quite a few functions on > records can be given the above type. Furthermore, the second sort can > be used not only with structural subtyping but also with nominal > subtyping. I agree. There is a difference between systems with records and row polymorphic records (if I understand you correctly). My system supports both, the former is written as: Rec ("x" ::= Int .| "y" ::= Bool .| Empty) the latter is written as Rec ("x" ::= Int .| "y" ::= Bool .| r) where r is the rest of the row, not the whole row as you write it. Notice that .| is a type level *function* (not a constructor!) that inserts a label-type value into the row. Hence Rec ("x" ::= Int .| "y" ::= Bool .| Empty) ~ Rec ("y" ::= Bool .| "x" ::= Int .| Empty) I do not understand you point about nominal subtyping, how can we nominally subtype r? It has no name? I can only imagine structural subtyping on records. ===================================================== Adam Vogt: Could you check whether the comparison with HList records is accurate? Check http://www.haskell.org/haskellwiki/CTRex#Comparison_with_other_approaches . Thanks! ============================================= AntC: You seem to have strong opinions on why allowing duplicate labels is a bad thing. Currently, my design supports both extension with scoping and the lacks predicate (see http://www.haskell.org/haskellwiki/CTRex#Duplicate_labels.2C_and_lacks). I think duplicate labels are nice in some situations and bad in other situations. 2013/12/3 AntC > > John Lato gmail.com> writes: > > > On Mon, Dec 2, 2013 at 9:17 PM, AntC wrote: > > > > > ... > > Importing an overlapping instance is trapped immediately; > > no risk of incoherence. > > > > > > How can this possibly work with open type families? What happens in this > case? > > > module A where > > > type instance F a b c | b /~ c = Int > > > module B where > > > type instance F a b c | a /~ c = Bool > > > > During compilation, neither A nor B is aware of the other. What happens > in a module that imports both? > > > > Thanks John, a good use case! > > The trapping is needed with imports for any approach to open instances (not > just type families). Suppose I have NoOverlappingInstances everywhere: > > > module A where > > instance C a b c where ... > > module B where > > instance C a b c where ... > > module D where > > instance C Int Bool Char where ... > > And a module that imports all three. > Any importer has to validate all instances sometime or other. > > (Currently ghc sticks its head in the sand, > and hopes there won't be a usage that trips over the ambiguity.) > > All we're talking about is _when_ we validate. > I'd rather know at the point of declaring the instance, > or of importing the instance. > > > AntC > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From vogt.adam at gmail.com Thu Dec 5 17:01:22 2013 From: vogt.adam at gmail.com (adam vogt) Date: Thu, 5 Dec 2013 12:01:22 -0500 Subject: [Haskell-cafe] Return of the revenge of the revisit of the extensible records, reiterated In-Reply-To: References: Message-ID: On Thu, Dec 5, 2013 at 9:38 AM, Atze van der Ploeg wrote: > Adam Vogt: > > Could you check whether the comparison with HList records is accurate? Check > http://www.haskell.org/haskellwiki/CTRex#Comparison_with_other_approaches . > Thanks! Hi Atze, I noted there is an equivalent of "constrained record operations" in HList, but it's less convenient than your Forall class. Regards, Adam From anthony_clayden at clear.net.nz Fri Dec 6 00:31:00 2013 From: anthony_clayden at clear.net.nz (AntC) Date: Fri, 6 Dec 2013 00:31:00 +0000 (UTC) Subject: [Haskell-cafe] Return of the revenge of the revisit of the extensible records, reiterated References: Message-ID: > Atze van der Ploeg gmail.com> writes: > > (see? http://www.haskell.org/haskellwiki/CTRex#Duplicate_labels.2C_and_lacks). > I think duplicate labels are nice in some situations and bad in other situations.? > Thank you Atze for a well-written description. I think there might be a couple of typos there? (c, r'') = decomp r x -- rhs s/b: decomp r' x ?? extendUnique :: (..., l :\r ) => ... -- s/b: r :\ l ?? Your "motivation" example is hard to follow without knowing what `decomp` does. (IOW, it is not showing me a motivation ;-) I'm puzzled by this in the implementation notes 4.2 Records: "Here we see that a record is actually just a map from string to the sequence of values. Notice that it is a sequence of values and not a single value, because the record may contain duplicate labels." It sounds like there's an overhead in being able to support duplicate labels (even if I don't want duplicates in my records)? Is there a performance penalty at run-time with extending/prepending and restricting/pretruncating, to keep the invariant re the i-th value? Leijen allowed duplicate labels to make a virtue of necessity IMO. There has not been an extensible records proposal before or since for duplicate labels. (TRex certainly didn't do it.) His 'necessity' was ease of implementation. This sequence of values stuff seems to make a more difficult implementation for the sake of providing a 'feature' that nobody's asked for(?) There's one 'advanced feature' of extensible records that I'd be interested in: merging records by label, as is done for 'Natural Join'. a row with labels {x, y, z} merge labels {y, z, w} returns a Maybe row with {x, y, z, w} providing the types paired with y and z are the same and the values are the same (otherwise return Nothing) It's absolutely essential _not_ to duplicate labels in this case. AntC From uribraun at eecs.harvard.edu Fri Dec 6 01:13:18 2013 From: uribraun at eecs.harvard.edu (Uri Braun) Date: Thu, 5 Dec 2013 20:13:18 -0500 Subject: [Haskell-cafe] Help with profiling Message-ID: <023b01cef220$5b31f900$1195eb00$@eecs.harvard.edu> Hi Caf?, I'm attempting to profile my rather large (~18K LOC) Haskell program that primarily manipulates graph structures based on Data.IntMap. The program is chewing up _lots_ of memory (approx. 4G for 2.5K nodes & 2.5K edges) and I have profiled it in an attempt to figure out why. It appears that the .prof and .hp (which I visualize with hp2ps -c) files do not agree on the source of the problem. The hp results are located at: http://www.eecs.harvard.edu/~uribraun/sybil.ps and the top of the .prof file looks like this: COST CENTRE MODULE %time %alloc compare Policy.Edge 21.7 50.0 eqPartition.edges Policy.EdgeQuad 6.5 3.7 toConstructedSet Types.TaggedIntMultimap 6.1 3.6 elems Types.TaggedIntMap 6.0 6.8 elems Types.TaggedIntSet 5.7 3.8 toPairs Types.TaggedIntMultimap 3.9 5.2 assocs Types.TaggedIntMap 3.2 4.1 eqIsValid Policy.EdgeQuad 2.9 0.5 rIsValid Policy.Relations 2.2 0.2 assocs.\ Types.TaggedIntMap 1.8 0.0 keysSet Types.TaggedIntMap 1.5 1.7 mergeIdenticalNodesT.exactMap Minimize.MergeIdentical 1.4 1.2 fromList Types.TaggedIntSet 1.3 1.6 tePartitionSrc Policy.TaggedEdge 1.2 0.9 null Types.TaggedIntSet 1.2 0.0 scc.comps Policy.Scc 1.2 0.9 tePartitionTgt Policy.TaggedEdge 1.1 0.8 member Types.TaggedIntSet 1.1 0.8 alter Types.TaggedIntMap 1.0 1.1 Also, the line in the .prof that corresponds to the anormUnion.name (what the hprof image claims is taking up space) looks like (some spaces removed): anormUnion.name Anormalize.Anormalize 2914 60 0.0 0.0 0.0 0.0 My main questions at this point are: 1. What are the chances the hprof image is just wrong? 2. What would you suggest I try next in debugging my space issue? This is my first big Haskell program, please do inform me of any big war tools I don?t know about. Many thanks in advance! +Uri -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben.franksen at online.de Fri Dec 6 01:39:01 2013 From: ben.franksen at online.de (Ben Franksen) Date: Fri, 06 Dec 2013 02:39:01 +0100 Subject: [Haskell-cafe] free vs. operational vs. free-operational References: <20131126105146.49662.qmail@www1.g3.pair.com> Message-ID: Ben Foppa wrote: > Uploader and current maintainer of the extensible-effects package here. > Although I'm still confused myself about the more theoretical bits of > extensible-effects, > I think I might be able to shed some light on it from a user's and > maintainer's perspective. > > extensible-effects is currently operational, and works quite well wherever > I use it. > That said, it's a new package and I'd expect some shifts before it settles > down. Let me first say that I like the general idea very much. I just read the paper and it all looks extremely promising. And I greatly appreciate your effort to put it on hackage and maintain it. It is a good thing that the library is not yet settled, though, because I think some of the names should be re-considered. For instance, why Eff and not Effect? Or why type Exn but corresponding functions throwError and catchError? (IMO such slips are okay for a paper, or a proof-of-concept implementation, but not for a library that aspires to overthrow monad transformers.) Cheers Ben -- "Make it so they have to reboot after every typo." -- Scott Adams From ben.franksen at online.de Fri Dec 6 01:48:19 2013 From: ben.franksen at online.de (Ben Franksen) Date: Fri, 06 Dec 2013 02:48:19 +0100 Subject: [Haskell-cafe] free vs. operational vs. free-operational References: <20131126105146.49662.qmail@www1.g3.pair.com> Message-ID: Ben Franksen wrote: > Or why type Exn (I meant to write Exc) > but corresponding functions throwError and > catchError? Ah, I just saw that this inconsistency is already fixed, it's Exc consistently in the latest version on hackage. I guess Exc has been chosen to avoid collisions when importing the library unqualified? Cheers Ben -- "Make it so they have to reboot after every typo." -- Scott Adams From carter.schonwald at gmail.com Fri Dec 6 02:00:22 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 5 Dec 2013 21:00:22 -0500 Subject: [Haskell-cafe] Help with profiling In-Reply-To: <023b01cef220$5b31f900$1195eb00$@eecs.harvard.edu> References: <023b01cef220$5b31f900$1195eb00$@eecs.harvard.edu> Message-ID: Hey Uri, could you explain what those numbers represent? many of use the profiling tools, but we may not remember what columns / numbers mean what. What number seems wrong and what does the number mean? Also its very hard to help debug if you don't link to the code If you're hitting space leak problems, one culprit could be your data structure or the operations acting on it is too lazy! Have you tried making it stricter? cheers -Carter On Thu, Dec 5, 2013 at 8:13 PM, Uri Braun wrote: > Hi Caf?, > > I'm attempting to profile my rather large (~18K LOC) Haskell program that > primarily manipulates graph structures based on Data.IntMap. The program > is chewing up _lots_ of memory (approx. 4G for 2.5K nodes & 2.5K edges)and I have profiled it in an attempt to figure out why. It > appears that the .prof and .hp (which I visualize with hp2ps -c) files do > not agree on the source of the problem. The hp results are located at: > *http://www.eecs.harvard.edu/~uribraun/sybil.ps*and the top of the .prof file looks like this: > > COST CENTRE MODULE %time %alloc > > compare Policy.Edge 21.7 50.0 > > eqPartition.edges Policy.EdgeQuad 6.5 3.7 > > toConstructedSet Types.TaggedIntMultimap 6.1 3.6 > > elems Types.TaggedIntMap 6.0 6.8 > > elems Types.TaggedIntSet 5.7 3.8 > > toPairs Types.TaggedIntMultimap 3.9 5.2 > > assocs Types.TaggedIntMap 3.2 4.1 > > eqIsValid Policy.EdgeQuad 2.9 0.5 > > rIsValid Policy.Relations 2.2 0.2 > > assocs.\ Types.TaggedIntMap 1.8 0.0 > > keysSet Types.TaggedIntMap 1.5 1.7 > > mergeIdenticalNodesT.exactMap Minimize.MergeIdentical 1.4 1.2 > > fromList Types.TaggedIntSet 1.3 1.6 > > tePartitionSrc Policy.TaggedEdge 1.2 0.9 > > null Types.TaggedIntSet 1.2 0.0 > > scc.comps Policy.Scc 1.2 0.9 > > tePartitionTgt Policy.TaggedEdge 1.1 0.8 > > member Types.TaggedIntSet 1.1 0.8 > > alter Types.TaggedIntMap 1.0 1.1 > > Also, the line in the .prof that corresponds to the anormUnion.name > (what the hprof image claims is taking up space) looks like (some spaces > removed): > > anormUnion.name Anormalize.Anormalize 2914 60 > 0.0 0.0 0.0 0.0 > > My main questions at this point are: > > 1. What are the chances the hprof image is just wrong? > > 2. What would you suggest I try next in debugging my space issue? > > This is my first big Haskell program, please do inform me of any big war > tools I don?t know about. > > Many thanks in advance! > > +Uri > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Fri Dec 6 02:02:09 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 5 Dec 2013 21:02:09 -0500 Subject: [Haskell-cafe] Help with profiling In-Reply-To: References: <023b01cef220$5b31f900$1195eb00$@eecs.harvard.edu> Message-ID: you may want to try out using the Strict variant of IntMap http://hackage.haskell.org/package/containers-0.5.3.1/docs/Data-IntMap-Strict.html I've definitely had some scary space usage explosions with the lazy one on occasions! (one embarrassing instance nearly two years ago was a 40gb space blowup that turned into 100mb usage once i switched to a strict map) On Thu, Dec 5, 2013 at 9:00 PM, Carter Schonwald wrote: > Hey Uri, > could you explain what those numbers represent? many of use the profiling > tools, but we may not remember what columns / numbers mean what. What > number seems wrong and what does the number mean? Also its very hard to > help debug if you don't link to the code > > If you're hitting space leak problems, one culprit could be your data > structure or the operations acting on it is too lazy! Have you tried making > it stricter? > > cheers > -Carter > > > On Thu, Dec 5, 2013 at 8:13 PM, Uri Braun wrote: > >> Hi Caf?, >> >> I'm attempting to profile my rather large (~18K LOC) Haskell program that >> primarily manipulates graph structures based on Data.IntMap. The program >> is chewing up _lots_ of memory (approx. 4G for 2.5K nodes & 2.5K edges)and I have profiled it in an attempt to figure out why. It >> appears that the .prof and .hp (which I visualize with hp2ps -c) files >> do not agree on the source of the problem. The hp results are located at: >> *http://www.eecs.harvard.edu/~uribraun/sybil.ps*and the top of the .prof file looks like this: >> >> COST CENTRE MODULE %time %alloc >> >> compare Policy.Edge 21.7 50.0 >> >> eqPartition.edges Policy.EdgeQuad 6.5 3.7 >> >> toConstructedSet Types.TaggedIntMultimap 6.1 3.6 >> >> elems Types.TaggedIntMap 6.0 6.8 >> >> elems Types.TaggedIntSet 5.7 3.8 >> >> toPairs Types.TaggedIntMultimap 3.9 5.2 >> >> assocs Types.TaggedIntMap 3.2 4.1 >> >> eqIsValid Policy.EdgeQuad 2.9 0.5 >> >> rIsValid Policy.Relations 2.2 0.2 >> >> assocs.\ Types.TaggedIntMap 1.8 0.0 >> >> keysSet Types.TaggedIntMap 1.5 1.7 >> >> mergeIdenticalNodesT.exactMap Minimize.MergeIdentical 1.4 1.2 >> >> fromList Types.TaggedIntSet 1.3 1.6 >> >> tePartitionSrc Policy.TaggedEdge 1.2 0.9 >> >> null Types.TaggedIntSet 1.2 0.0 >> >> scc.comps Policy.Scc 1.2 0.9 >> >> tePartitionTgt Policy.TaggedEdge 1.1 0.8 >> >> member Types.TaggedIntSet 1.1 0.8 >> >> alter Types.TaggedIntMap 1.0 1.1 >> >> Also, the line in the .prof that corresponds to the anormUnion.name >> (what the hprof image claims is taking up space) looks like (some spaces >> removed): >> >> anormUnion.name Anormalize.Anormalize 2914 60 >> 0.0 0.0 0.0 0.0 >> >> My main questions at this point are: >> >> 1. What are the chances the hprof image is just wrong? >> >> 2. What would you suggest I try next in debugging my space issue? >> >> This is my first big Haskell program, please do inform me of any big war >> tools I don?t know about. >> >> Many thanks in advance! >> >> +Uri >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From anthony_clayden at clear.net.nz Fri Dec 6 02:50:47 2013 From: anthony_clayden at clear.net.nz (AntC) Date: Fri, 6 Dec 2013 02:50:47 +0000 (UTC) Subject: [Haskell-cafe] =?utf-8?q?Return_of_the_revenge_of_the_revisit_of_?= =?utf-8?q?the=09extensible_records=2C_reiterated?= References: Message-ID: > AntC clear.net.nz> writes: Actually, I think there's more wrong with that line than a typo: > > extendUnique :: (..., l :\r ) => ... > -- s/b: r :\ l ?? > (It's supposed to do renaming with non-duplicate labels?) Talking of renaming, how does it go with duplicate labels? The comment on `rename` says it can be expressed using the "above operations" (presumably restrict followed by extend with the new label, as per Gastar&Jones and Leijen). If that's genuinely equivalent, then rename will 'unhide' any duplicate label. So presumably the implementation must split the HashMap into two keys, rather than changing the label on the existing Seq(?) AntC From atzeus at gmail.com Fri Dec 6 10:04:12 2013 From: atzeus at gmail.com (Atze van der Ploeg) Date: Fri, 6 Dec 2013 11:04:12 +0100 Subject: [Haskell-cafe] Return of the revenge of the revisit of the extensible records, reiterated In-Reply-To: References: Message-ID: > Thank you Atze for a well-written description. Cheers! :) > I think there might be a couple of typos there? Sadly, due to the finiteness of life I cannot guarantee perfection in all my communication. However, if you see typos, I would greatly appreciate it if you fix them (it's a wiki). :) > (c, r'') = decomp r x -- rhs s/b: decomp r' x ?? > Your "motivation" example is hard to follow without knowing what `decomp` > does. (IOW, it is not showing me a motivation ;-) Woops! Sorry! I messed up the example, i've changed it now to: g :: Rec r -> Rec ("p" ::= String .| r) g r = let r' = f (x := 10 .| r) (c,r'') = (r'.!x, r' .- x) v = if c then "Yes" else "Nope" in p := v .| r'' > I'm puzzled by this in the implementation notes 4.2 Records: > "Here we see that a record is actually just a map from string to the > sequence of values. Notice that it is a sequence of values and not a > single value, because the record may contain duplicate labels." > It sounds like there's an overhead in being able to support duplicate > labels (even if I don't want duplicates in my records)? > Is there a performance penalty at run-time with extending/prepending and > restricting/pretruncating, to keep the invariant re the i-th value? Well, supposing you have no duplicate labels, then all sequences are of length 1. Hence the overhead is that we have a sequence of length 1 instead of just a value (i.e. one extra reference to follow). This is a very small overhead, and in my opinion is justified by the advantages of allowing duplicate labels. Notice also that (.!) always accesses the head of the sequence, since only the leftmost label is accessible (to access shadowed labels, restrict the record with that label). > Leijen allowed duplicate labels to make a virtue of necessity IMO. There > has not been an extensible records proposal before or since for duplicate > labels. (TRex certainly didn't do it.) His 'necessity' was ease of > implementation. > This sequence of values stuff seems to make a more difficult > implementation for the sake of providing a 'feature' that nobody's asked > for(?) Well, I think Leijen makes two points: * Duplicate labels are nice and allow shadowing in records, which is good. * Duplicate labels allow us to construct a type system lacking a "lacks" predicate, which makes it simpler. I am mainly interested in the first point, see my example. As I said, whether you want duplicate labels depends on the situation. As another use case for duplicate labels: consider implementing an interpreter for some embedded DSL, and you want to carry the state of the variables in the an extensible record. Declaring a new variable in the embedded language then causes us to extend the record. Since the embedded language allows shadowing (as most languages do), we can simply extend the record, we do not have to jump through hoops to make sure there are no duplicate labels. Once the variable goes out of scope, we remove the label again to bring the old "variable" into scope. > Actually, I think there's more wrong with that line than a typo: > > extendUnique :: (..., l :\r ) => ... > -- s/b: r :\ l ?? > > (It's supposed to do renaming with non-duplicate labels?) Sorry! Another mistake, I've fixed it. It is now as follows: renameUnique :: (KnownSymbol l, KnownSymbol l', r :\ l') => Label l -> Label l' -> Rec r -> Rec (Rename l l' r) > Talking of renaming, how does it go with duplicate labels? > The comment on `rename` says it can be expressed using the "above > operations" (presumably restrict followed by extend with the new label, as > per Gastar&Jones and Leijen). > If that's genuinely equivalent, then rename will 'unhide' any duplicate > label. So presumably the implementation must split the HashMap into two > keys, rather than changing the label on the existing Seq(?) Yes, exactly. Renaming is implemented as follows, which is equivalent to what you said: rename :: (KnownSymbol l, KnownSymbol l') => Label l -> Label l' -> Rec r -> Rec (Rename l l' r) rename l l' r = extend l' (r .! l) (r .- l) renameUnique :: (KnownSymbol l, KnownSymbol l', r :\ l') => Label l -> Label l' -> Rec r -> Rec (Rename l l' r) renameUnique = rename 2013/12/6 AntC > > Atze van der Ploeg gmail.com> writes: > > > > (see > http://www.haskell.org/haskellwiki/CTRex#Duplicate_labels.2C_and_lacks). > > I think duplicate labels are nice in some situations and bad in other > situations. > > > > Thank you Atze for a well-written description. > > I think there might be a couple of typos there? > > (c, r'') = decomp r x -- rhs s/b: decomp r' x ?? > > extendUnique :: (..., l :\r ) => ... > -- s/b: r :\ l ?? > > Your "motivation" example is hard to follow without knowing what `decomp` > does. (IOW, it is not showing me a motivation ;-) > > I'm puzzled by this in the implementation notes 4.2 Records: > "Here we see that a record is actually just a map from string to the > sequence of values. Notice that it is a sequence of values and not a > single value, because the record may contain duplicate labels." > > It sounds like there's an overhead in being able to support duplicate > labels (even if I don't want duplicates in my records)? > Is there a performance penalty at run-time with extending/prepending and > restricting/pretruncating, to keep the invariant re the i-th value? > > Leijen allowed duplicate labels to make a virtue of necessity IMO. There > has not been an extensible records proposal before or since for duplicate > labels. (TRex certainly didn't do it.) His 'necessity' was ease of > implementation. > This sequence of values stuff seems to make a more difficult > implementation for the sake of providing a 'feature' that nobody's asked > for(?) > > > There's one 'advanced feature' of extensible records that I'd be > interested in: merging records by label, as is done for 'Natural Join'. > > a row with labels {x, y, z} merge labels {y, z, w} > returns a Maybe row with {x, y, z, w} > providing the types paired with y and z are the same > and the values are the same > (otherwise return Nothing) > > It's absolutely essential _not_ to duplicate labels in this case. > > AntC > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From atzeus at gmail.com Fri Dec 6 10:13:20 2013 From: atzeus at gmail.com (Atze van der Ploeg) Date: Fri, 6 Dec 2013 11:13:20 +0100 Subject: [Haskell-cafe] Return of the revenge of the revisit of the extensible records, reiterated In-Reply-To: References: Message-ID: You might also wonder why wonder why I use a Sequence instead of a List, since we only query the head and prepend. This is implement record merge (.+) more efficiently since we can then use (><) (O(1)) instead of (++) (O(n)) as follows: (.++) :: Rec l -> Rec r -> Rec (l :++ r) (OR l) .++ (OR r) = OR $ M.unionWith (><) l r 2013/12/6 Atze van der Ploeg > > Thank you Atze for a well-written description. > > Cheers! :) > > > I think there might be a couple of typos there? > > Sadly, due to the finiteness of life I cannot guarantee perfection in all > my communication. However, if you see typos, I would greatly appreciate it > if you fix them (it's a wiki). :) > > > (c, r'') = decomp r x -- rhs s/b: decomp r' x ?? > > Your "motivation" example is hard to follow without knowing what `decomp` > > does. (IOW, it is not showing me a motivation ;-) > > Woops! Sorry! I messed up the example, i've changed it now to: > > g :: Rec r -> Rec ("p" ::= String .| r) > g r = let r' = f (x := 10 .| r) > (c,r'') = (r'.!x, r' .- x) > v = if c then "Yes" else "Nope" > in p := v .| r'' > > > > I'm puzzled by this in the implementation notes 4.2 Records: > > > "Here we see that a record is actually just a map from string to the > > sequence of values. Notice that it is a sequence of values and not a > > single value, because the record may contain duplicate labels." > > > It sounds like there's an overhead in being able to support duplicate > > labels (even if I don't want duplicates in my records)? > > Is there a performance penalty at run-time with extending/prepending and > > restricting/pretruncating, to keep the invariant re the i-th value? > > Well, supposing you have no duplicate labels, then all sequences are of > length 1. > Hence the overhead is that we have a sequence of length 1 instead of just > a value (i.e. one extra reference to follow). > This is a very small overhead, and in my opinion is justified by the > advantages of allowing duplicate labels. > Notice also that (.!) always accesses the head of the sequence, since only > the leftmost label is accessible (to access shadowed labels, restrict the > record with that label). > > > > Leijen allowed duplicate labels to make a virtue of necessity IMO. There > > has not been an extensible records proposal before or since for duplicate > > labels. (TRex certainly didn't do it.) His 'necessity' was ease of > > implementation. > > This sequence of values stuff seems to make a more difficult > > implementation for the sake of providing a 'feature' that nobody's asked > > for(?) > > Well, I think Leijen makes two points: > * Duplicate labels are nice and allow shadowing in records, which is good. > * Duplicate labels allow us to construct a type system lacking a "lacks" > predicate, which makes it simpler. > > I am mainly interested in the first point, see my example. As I said, > whether you want duplicate labels depends on the situation. > > As another use case for duplicate labels: consider implementing an > interpreter for some embedded DSL, and you want to carry the > state of the variables in the an extensible record. Declaring a new > variable in the embedded language then > causes us to extend the record. Since the embedded language allows > shadowing (as most languages do), we can simply > extend the record, we do not have to jump through hoops to make sure there > are no duplicate labels. Once the variable > goes out of scope, we remove the label again to bring the old "variable" > into scope. > > > Actually, I think there's more wrong with that line than a typo: > > > > > extendUnique :: (..., l :\r ) => ... > > -- s/b: r :\ l ?? > > > > (It's supposed to do renaming with non-duplicate labels?) > > Sorry! Another mistake, I've fixed it. It is now as follows: > > renameUnique :: (KnownSymbol l, KnownSymbol l', r :\ l') => Label l -> > Label l' -> Rec r -> Rec (Rename l l' r) > > > > Talking of renaming, how does it go with duplicate labels? > > The comment on `rename` says it can be expressed using the "above > > operations" (presumably restrict followed by extend with the new label, > as > > per Gastar&Jones and Leijen). > > > If that's genuinely equivalent, then rename will 'unhide' any duplicate > > label. So presumably the implementation must split the HashMap into two > > keys, rather than changing the label on the existing Seq(?) > > Yes, exactly. Renaming is implemented as follows, which is equivalent to > what you said: > > rename :: (KnownSymbol l, KnownSymbol l') => Label l -> Label l' -> Rec r -> Rec (Rename l l' r) > rename l l' r = extend l' (r .! l) (r .- l) > renameUnique :: (KnownSymbol l, KnownSymbol l', r :\ l') => Label l -> Label l' -> Rec r -> Rec (Rename l l' r) > renameUnique = rename > > > > > 2013/12/6 AntC > >> > Atze van der Ploeg gmail.com> writes: >> > >> > (see >> http://www.haskell.org/haskellwiki/CTRex#Duplicate_labels.2C_and_lacks). >> > I think duplicate labels are nice in some situations and bad in other >> situations. >> > >> >> Thank you Atze for a well-written description. >> >> I think there might be a couple of typos there? >> >> (c, r'') = decomp r x -- rhs s/b: decomp r' x ?? >> >> extendUnique :: (..., l :\r ) => ... >> -- s/b: r :\ l ?? >> >> Your "motivation" example is hard to follow without knowing what `decomp` >> does. (IOW, it is not showing me a motivation ;-) >> >> I'm puzzled by this in the implementation notes 4.2 Records: >> "Here we see that a record is actually just a map from string to the >> sequence of values. Notice that it is a sequence of values and not a >> single value, because the record may contain duplicate labels." >> >> It sounds like there's an overhead in being able to support duplicate >> labels (even if I don't want duplicates in my records)? >> Is there a performance penalty at run-time with extending/prepending and >> restricting/pretruncating, to keep the invariant re the i-th value? >> >> Leijen allowed duplicate labels to make a virtue of necessity IMO. There >> has not been an extensible records proposal before or since for duplicate >> labels. (TRex certainly didn't do it.) His 'necessity' was ease of >> implementation. >> This sequence of values stuff seems to make a more difficult >> implementation for the sake of providing a 'feature' that nobody's asked >> for(?) >> >> >> There's one 'advanced feature' of extensible records that I'd be >> interested in: merging records by label, as is done for 'Natural Join'. >> >> a row with labels {x, y, z} merge labels {y, z, w} >> returns a Maybe row with {x, y, z, w} >> providing the types paired with y and z are the same >> and the values are the same >> (otherwise return Nothing) >> >> It's absolutely essential _not_ to duplicate labels in this case. >> >> AntC >> >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ketil at malde.org Fri Dec 6 12:45:31 2013 From: ketil at malde.org (Ketil Malde) Date: Fri, 06 Dec 2013 13:45:31 +0100 Subject: [Haskell-cafe] hash tables, judy arrays, and more Message-ID: <87haamgnbo.fsf@wespe.malde.org> Hi, As some of you may know?, I've been playing around with associative data structures, and in particular Judy arrays, using the "judy" package by Don S. Now, I find these to be fast and (more importantly) frugal concerning memory - but now I see what I can only interpret as memory corruption - a bit depending on the ordering of the code and/or insertion of print statements, output is truncated or contaminated. The strange thing is that this only occurs when I also use Data.Vector or Data.HashTable.IO in the same program - if it's all Judy, then things work as expected - as far as I have seen, anyway. First I thought it was my dubious "insertWith" function, but when I reverted to separate "insert" and "lookup", I can still provoke the behavior. Has anybody else seen anything similar? Any idea how to debug something like this? Then I thought I'd look at hash tables, using the 'hashtables' package. I haven't tested it much yet, but it appears to be a lot slower than Judy (maybe as much as 10x), and uses a lot more memory (also perhaps a factor of 10). I guess I might be able to improve things a bit by judiciously applying strictness, but it seems to be storing both keys and values unboxed, so I don't expect to come close to Judy - I guess there isn't any unboxed hash table implementations around? Anyway - I seem to have programmed myself into a corner here, so suggestions welcome! -k ? http://blog.malde.org/posts/frequency-counting.html and http://blog.malde.org/posts/k-mer-counting.html -- If I haven't seen further, it is by standing in the footprints of giants From greg at gregorycollins.net Fri Dec 6 13:52:46 2013 From: greg at gregorycollins.net (Gregory Collins) Date: Fri, 6 Dec 2013 14:52:46 +0100 Subject: [Haskell-cafe] hash tables, judy arrays, and more In-Reply-To: <87haamgnbo.fsf@wespe.malde.org> References: <87haamgnbo.fsf@wespe.malde.org> Message-ID: On Fri, Dec 6, 2013 at 1:45 PM, Ketil Malde wrote: > Then I thought I'd look at hash tables, using the 'hashtables' package. > I haven't tested it much yet, but it appears to be a lot slower than > Judy (maybe as much as 10x), and uses a lot more memory (also perhaps a > factor of 10). I guess I might be able to improve things a bit by > judiciously applying strictness, but it seems to be storing both keys > and values unboxed, so I don't expect to come close to Judy - I guess > there isn't any unboxed hash table implementations around? > If you want to try the git master version of the hashtables library, I've made some performance and memory overhead improvements that haven't been released yet (I still need to run more benchmarks before release). Try both the "basic" and "cuckoo" hash tables (cuckoo might be better). IIRC we force keys stored in the hash tables but not the values -- you might want to confirm you're not building up value thunks. G -- Gregory Collins -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at joachim-breitner.de Fri Dec 6 17:51:03 2013 From: mail at joachim-breitner.de (Joachim Breitner) Date: Fri, 06 Dec 2013 17:51:03 +0000 Subject: [Haskell-cafe] Higher order functions and strictness Message-ID: <1386352263.7910.12.camel@kirk> Hi, we currently have a pattern where a higher order function (like foldl, or Map.unionWith), which naively build thunks without the passed function having a chance to prevent that. Therefore, there are variants like foldl', which seq the result of the function. Can one have one function that allows for both? I take mapMaybe :: (a -> b) -> Maybe a -> Maybe b as an (simple, and not very relevant) example. With that signature, there is not much "mapMaybe f x" can do. It either applies f lazily to x, or strictly. One could have data Box a = Box a mapMaybe :: (a -> Box b) -> Maybe a -> Maybe b and have mapMaybe pattern-match on Box. Then it will evaluate _something_ of the return value of f, and f can have control over whether the thing inside the box is evaluated or not. So this is nice, but unfortunately we now allocate and destruct a box that we do not care about. But since I had been looking at some unboxed tuples recently, I noticed that the singleton unboxed tuple allows for exactly that: Call a function in a way that it has control (i.e. can force stuff), but do not necessarily evaluate its result, and all that without extra allocations. Here is some example code: {-# LANGUAGE UnboxedTuples #-} import GHC.HeapView mapMaybe :: (a -> (# b #) ) -> Maybe a -> Maybe b mapMaybe _ Nothing = Nothing mapMaybe f (Just x) = case f x of (# y #) -> Just y f_plain :: Int -> Int f_plain x = x + 1 f_lazy :: Int -> (# Int #) f_lazy x = (# x + 1 #) f_strict :: Int -> (# Int #) f_strict x = let y = x + 1 in y `seq` (# y #) main = do let x = Just 1 Just y1 <- return $ fmap f_plain x Just y2 <- return $ mapMaybe f_lazy x Just y3 <- return $ mapMaybe f_strict x let results = (y1,y2,y3) buildHeapTree 10 (asBox results) >>= putStrLn . ppHeapTree and here the result: (_thunk _fun{0} (I# 1),_thunk (I# 1),I# 2) as expected and desired, fmap and mapMaybe with the lazy f left a thunk in the Just constructor, while the strict f had a chance to evaluate its result. Of course (#..#) has it downsides, e.g. you cannot make a newtype for it (newtype Box a = (# x #)) does not work... but it might be an interesting design pattern if you need it ? imagine a "mapTuple10", which takes 10 function arguments ? you can?t have '-variants for every 2^10 possible strictness combinations. Greetings, Joachim -- Joachim ?nomeata? Breitner mail at joachim-breitner.de ? http://www.joachim-breitner.de/ Jabber: nomeata at joachim-breitner.de ? GPG-Key: 0x4743206C Debian Developer: nomeata at debian.org -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 198 bytes Desc: This is a digitally signed message part URL: From joe at begriffs.com Fri Dec 6 18:22:23 2013 From: joe at begriffs.com (Joe Nelson) Date: Fri, 6 Dec 2013 10:22:23 -0800 Subject: [Haskell-cafe] Haskell on Heroku (improved) Message-ID: <052AED25-F66E-42DF-AC65-5D60161FB5CC@begriffs.com> Hey all, I just created a buildpack to deploy Haskell apps to Heroku. If you use Yesod or Snap or whatever give it a try. It uses GHC 7.6.3 and Cabal 1.18 so it should support all the modern goodies you like to use. https://github.com/begriffs/heroku-buildpack-ghc Also some people have reported an issue with cabal-install choosing the wrong versions of packages. Anyone run into this kind of thing before? https://github.com/begriffs/heroku-buildpack-ghc/issues/7 Regards, Joe Nelson From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Fri Dec 6 20:52:59 2013 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Fri, 6 Dec 2013 20:52:59 +0000 Subject: [Haskell-cafe] Higher order functions and strictness In-Reply-To: <1386352263.7910.12.camel@kirk> References: <1386352263.7910.12.camel@kirk> Message-ID: <20131206205259.GD14883@weber> On Fri, Dec 06, 2013 at 05:51:03PM +0000, Joachim Breitner wrote: > But since I had been looking at some unboxed tuples recently, I noticed > that the singleton unboxed tuple allows for exactly that: Call a > function in a way that it has control (i.e. can force stuff), but do not > necessarily evaluate its result, and all that without extra allocations. This is a very, very neat observation! It seems that the unboxed singleton allows fine grained control over order of evaluation without imposing any datastructure overhead. I am (very slowly) working on an alternative type-system for GHC which will make it look like a strict language with explicit thunk datatype (although it will still be good old GHC under the hood). Your observation will be helpful for performance. > Of course (#..#) has it downsides, e.g. you cannot make a newtype for it > (newtype Box a = (# x #)) does not work... This is a shame, although it seems like in principle it may be possible https://ghc.haskell.org/trac/ghc/ticket/1311 Still if SPJ's 'brain is too small to figure out all the ramifications of dropping the "newtypes are always boxed" assumption' then I don't hold out much hope that /anyone/ will be able to do anything about this restriction :) Tom From keydana at gmx.de Sat Dec 7 17:58:14 2013 From: keydana at gmx.de (keydana at gmx.de) Date: Sat, 7 Dec 2013 18:58:14 +0100 Subject: [Haskell-cafe] converting between a Ptr a and an Integer Message-ID: Hi, is there any way to convert between a Ptr a and an Integer? (I would like to attach to shared memory and dereference pointers to certain memory addresses, as you would do in C.) If there is no way at all, I think I could still get along by defining c_shmat as c_shmat :: CInt -> CInt -> CInt -> IO (Ptr a) and perform calculations using plusPtr, but then how do I check if I got back the correct address, and not (void *) -1, which is what shmat returns on error? Any help very much appreciated! Thanks Sigrid From hsyl20 at gmail.com Sat Dec 7 18:16:10 2013 From: hsyl20 at gmail.com (Sylvain HENRY) Date: Sat, 07 Dec 2013 19:16:10 +0100 Subject: [Haskell-cafe] converting between a Ptr a and an Integer In-Reply-To: References: Message-ID: <52A365EA.7030402@gmail.com> Hi, You can use: ptrToIntPtr :: Ptr a -> IntPtr intPtrToPtr :: IntPtr -> Ptr a Cheers Sylvain Le 07/12/2013 18:58, keydana at gmx.de a ?crit : > Hi, > > is there any way to convert between a Ptr a and an Integer? > (I would like to attach to shared memory and dereference pointers to certain memory addresses, as you would do in C.) > > If there is no way at all, I think I could still get along by defining c_shmat as > > c_shmat :: CInt -> CInt -> CInt -> IO (Ptr a) > > and perform calculations using plusPtr, > > but then how do I check if I got back the correct address, and not (void *) -1, which is what shmat returns on error? > > Any help very much appreciated! > > Thanks > Sigrid > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From carter.schonwald at gmail.com Sat Dec 7 18:18:32 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sat, 7 Dec 2013 13:18:32 -0500 Subject: [Haskell-cafe] converting between a Ptr a and an Integer In-Reply-To: <52A365EA.7030402@gmail.com> References: <52A365EA.7030402@gmail.com> Message-ID: There is a module in base that let's you do pointer arith in Haskell. I forget where it is. But it's there. No need to cast your pointer to an int and back. On Saturday, December 7, 2013, Sylvain HENRY wrote: > Hi, > > You can use: > ptrToIntPtr :: Ptr a -> IntPtr > intPtrToPtr :: IntPtr -> Ptr a > > Cheers > Sylvain > > > Le 07/12/2013 18:58, keydana at gmx.de a ?crit : > >> Hi, >> >> is there any way to convert between a Ptr a and an Integer? >> (I would like to attach to shared memory and dereference pointers to >> certain memory addresses, as you would do in C.) >> >> If there is no way at all, I think I could still get along by defining >> c_shmat as >> >> c_shmat :: CInt -> CInt -> CInt -> IO (Ptr a) >> >> and perform calculations using plusPtr, >> >> but then how do I check if I got back the correct address, and not (void >> *) -1, which is what shmat returns on error? >> >> Any help very much appreciated! >> >> Thanks >> Sigrid >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From krajcevski at gmail.com Sat Dec 7 21:35:32 2013 From: krajcevski at gmail.com (Pavel Krajcevski) Date: Sat, 7 Dec 2013 16:35:32 -0500 Subject: [Haskell-cafe] STM interfacing with GLFW Message-ID: Hi, I'm new to STM and to Haskell in general. I've been writing a small library to try some graphics algorithms in Haskell, but using GLFW's callbacks seems to be causing me problems. I have a (relatively heavyweight?) object wrapped in a TVar (Data.Set) that I'm sharing across all threads. Unfortunately, once I run the program, it becomes unresponsive although the main loop is still running. I'm not sure exactly what the semantics are for getting STM right, but ideally I'm trying to modify the TVar in GLFW event callbacks and then finally read out the value of the TVar at the end (or beginning) of my rendering loop. I've been able to get a small program working that reproduces my problem: https://gist.github.com/Mokosha/34eda7bd2d6b5cafd5a3 Any help would be great! Thanks! - Pavel -------------- next part -------------- An HTML attachment was scrubbed... URL: From krajcevski at gmail.com Sat Dec 7 22:33:55 2013 From: krajcevski at gmail.com (Pavel Krajcevski) Date: Sat, 7 Dec 2013 17:33:55 -0500 Subject: [Haskell-cafe] STM interfacing with GLFW In-Reply-To: References: Message-ID: Turns out this was a bug from removing the GLFW.pollEvents call, rather than anything having to do with STM. Sorry for the spam! - Pavel On Sat, Dec 7, 2013 at 4:35 PM, Pavel Krajcevski wrote: > Hi, > > I'm new to STM and to Haskell in general. I've been writing a small > library to try some graphics algorithms in Haskell, but using GLFW's > callbacks seems to be causing me problems. I have a (relatively > heavyweight?) object wrapped in a TVar (Data.Set) that I'm sharing across > all threads. > > Unfortunately, once I run the program, it becomes unresponsive although > the main loop is still running. I'm not sure exactly what the semantics are > for getting STM right, but ideally I'm trying to modify the TVar in GLFW > event callbacks and then finally read out the value of the TVar at the end > (or beginning) of my rendering loop. I've been able to get a small program > working that reproduces my problem: > > https://gist.github.com/Mokosha/34eda7bd2d6b5cafd5a3 > > Any help would be great! > > Thanks! > > - Pavel > -------------- next part -------------- An HTML attachment was scrubbed... URL: From dennis.raddle at gmail.com Sat Dec 7 23:54:21 2013 From: dennis.raddle at gmail.com (Dennis Raddle) Date: Sat, 7 Dec 2013 15:54:21 -0800 Subject: [Haskell-cafe] finding "good work" in CS Message-ID: It's me again, guy aged 45 thinking about doing graduate work in CS. I read this ebook about a guy's CS PhD, "The PhD Grind": It was enlightening. I used to think that software in the C.S. academic world must be well-written, seeing as it was written by computer scientists. (I didn't like the poorly organized and simple-minded code involved in my last job at NASA.) Turns out that academic code can be very poor indeed, sometimes just a hacked prototype meant to demonstrate an idea to get it published. It may be the youngest PhD students who are assigned the job of cranking out such prototypes. So what do I want to do for my life's work, once I can overcome this illness and get back to work full-time? I hope I can work with beauty in some form. I find Haskell to be beautiful, for instance. I like ideas, but I also like the process of implementing ideas in a quality way. I may not be suited to the academic world because I need to spend at least some of my time as a craftsman of code, doing something well. Is there an area with CS academia that is more about elegance, less about hacking up prototypes? The study of languages? Second, what if I thought of PhD not as a way to enter academia, but as a way to qualify me for the more interesting and creative C.S. jobs out there? What kinds of C.S. jobs involve real creative control, an opportunity to do things in an elegant way? I know that's a very broad question, so maybe those reading could mention single examples or things they've run into. No need to cover everything. Thanks, Dennis -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Sun Dec 8 01:33:51 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sat, 7 Dec 2013 20:33:51 -0500 Subject: [Haskell-cafe] finding "good work" in CS In-Reply-To: References: Message-ID: the best way to get cool work is to create opportunities! Do great work and make it visible, reach out to businesses. etc while theres many people on haskell cafe who are happy to try to give advice, i think we're the wrong group to give advice. 1) reach out to your universities alumni network, there'll be many folks in many organizations who may be willing to help / give you advice 2) email organizations that are hiring that you're excited by and where you have some basic fluency in the the skills they need. The fact of the matter is that for jumpstarting/resuming a career thats been on hiatus, taking a junior role is the best way to get it started. One good listing that happens every month is the hacker news who's hiring thread, and they list many remote ok jobs too! best of luck _Carter On Sat, Dec 7, 2013 at 6:54 PM, Dennis Raddle wrote: > It's me again, guy aged 45 thinking about doing graduate work in CS. > > I read this ebook about a guy's CS PhD, "The PhD Grind": > > > > It was enlightening. I used to think that software in the C.S. academic > world must be well-written, seeing as it was written by computer > scientists. (I didn't like the poorly organized and simple-minded code > involved in my last job at NASA.) Turns out that academic code can be very > poor indeed, sometimes just a hacked prototype meant to demonstrate an idea > to get it published. It may be the youngest PhD students who are assigned > the job of cranking out such prototypes. > > So what do I want to do for my life's work, once I can overcome this > illness and get back to work full-time? > > I hope I can work with beauty in some form. I find Haskell to be > beautiful, for instance. I like ideas, but I also like the process of > implementing ideas in a quality way. I may not be suited to the academic > world because I need to spend at least some of my time as a craftsman of > code, doing something well. > > Is there an area with CS academia that is more about elegance, less about > hacking up prototypes? The study of languages? > > Second, what if I thought of PhD not as a way to enter academia, but as a > way to qualify me for the more interesting and creative C.S. jobs out > there? What kinds of C.S. jobs involve real creative control, an > opportunity to do things in an elegant way? > > I know that's a very broad question, so maybe those reading could mention > single examples or things they've run into. No need to cover everything. > > Thanks, > Dennis > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From 0slemi0 at gmail.com Sun Dec 8 09:23:39 2013 From: 0slemi0 at gmail.com (Andras Slemmer) Date: Sun, 8 Dec 2013 09:23:39 +0000 Subject: [Haskell-cafe] existential quantification In-Reply-To: <54kvma-6tl.ln1@rama.universe> References: <0suuma-i57.ln1@rama.universe> <54kvma-6tl.ln1@rama.universe> Message-ID: I uploaded the Harper video series, here is a link to the first lecture: https://www.youtube.com/watch?v=ev7AYsLljxk&list=PL8Ky8lYL8-Oh7awp0sqa82o7Ggt4AGhyf&index=5 This is more of an introduction to dependent type theory, but it's worth a watch! On 3 December 2013 04:10, TP wrote: > Andras Slemmer wrote: > > > Just expanding on Brandon's answer: DeMorgan's law he's referring to goes > > like this: > > ?a.P(a) === ??a.?P(a) where 'a' is a sentence, so P is second order > > A special case of this is this: > > ?a.(R(a) -> Q) === ??a.?(R(a) -> Q) === ??a.(R(a)??Q) === ?((?a.R(a))??Q) > > === (?a.R(a)) -> Q (i added extra parantheses for emphasis) > > So what does this mean in terms of haskell? R(a) is your data > definition's > > "body", and Q is the type you are defining. On the lhs the universally > > quantified version gives you the type of the constuctor you're defining, > > and on the rhs the existential tells you what you're constructing the > type > > with. > > Or in other words the universal version says: For any 'a' give me an R(a) > > and i'll give you back a Q. > > The existential version says: If you have some 'a' for which R(a) i'll > > give you back a Q. (It's hard to phrase the difference without sounding > > stupid, they are equivalent after all). > > > > There are of course other considerations, for example introducing > 'exists' > > would mean another keyword in the syntax. > > Thanks Andras, I have understood the developments up to that point. But > below I do not understand your reasoning. > > > > > Having said that I think that the choice of 'forall' for > > -XExistentialQuantification is wrong, as the data body defines the type > > you're constructing with, not the type of the whole constructor. HOWEVER > > for -XGADTs forall makes perfect sense. Compare the following: > > > > data AnyType = forall a. AnyType a > > data AnyType where > > AnyType :: forall a. a -> AnyType > > > > These two definitions are operationally identical, but I think the GADT > > way is the one that actually corresponds to the DeMorgan law. > > And one more question: I had lectures on logic some years ago, but I never > studied type theory at university (I'm some sort of "electrical engineer"). > Is there around a good textbook for "beginners", with full proofs, but only > the essential ones? I would like a good "entry point" in the textbook > literature. Not for experts. > Are the books of Robert Harper suitable, for example > > > http://www.amazon.com/Practical-Foundations-Programming-Languages-Professor/dp/1107029570 > > ? > > TP > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From keydana at gmx.de Sun Dec 8 18:56:13 2013 From: keydana at gmx.de (keydana at gmx.de) Date: Sun, 8 Dec 2013 19:56:13 +0100 Subject: [Haskell-cafe] converting between a Ptr a and an Integer In-Reply-To: References: Message-ID: <1ABDE71F-05DB-4C43-B6BC-23B7BD6FD9FD@gmx.de> Hi, thanks for your answers, I've found a way (or rather, was pointed to it ;-) ) in the meantime, using something like nullPtr `plusPtr` Thanks all the same, Sigrid From omeragacan at gmail.com Mon Dec 9 00:05:17 2013 From: omeragacan at gmail.com (=?ISO-8859-9?Q?=D6mer_Sinan_A=F0acan?=) Date: Mon, 9 Dec 2013 02:05:17 +0200 Subject: [Haskell-cafe] Is anyone currently working on SDL2 FFI ? Message-ID: Hello everyone, I was wondering if anyone is currently working on SDL2 FFI. I really need that library and I'm willing to contribute to the work, but I can't currently spare enough time to start it from scratch(it's very big library). I know we have OpenGL and GLFW bindings and gloss for 2D stuff etc. but for several reasons I want this particular library. (just wanted to make this clear because I presume people point me alternatives otherwise :-) ) Thanks, --- ?mer Sinan A?acan http://osa1.net From carter.schonwald at gmail.com Mon Dec 9 00:08:46 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sun, 8 Dec 2013 19:08:46 -0500 Subject: [Haskell-cafe] Is anyone currently working on SDL2 FFI ? In-Reply-To: References: Message-ID: good question! you should ask on #haskell-game(s?) irc channel, i'd be surprised if no one is working on it. On Sun, Dec 8, 2013 at 7:05 PM, ?mer Sinan A?acan wrote: > Hello everyone, > > I was wondering if anyone is currently working on SDL2 FFI. I really > need that library and I'm willing to contribute to the work, but I > can't currently spare enough time to start it from scratch(it's very > big library). > > I know we have OpenGL and GLFW bindings and gloss for 2D stuff etc. > but for several reasons I want this particular library. (just wanted > to make this clear because I presume people point me alternatives > otherwise :-) ) > > Thanks, > > --- > ?mer Sinan A?acan > http://osa1.net > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ok at cs.otago.ac.nz Mon Dec 9 03:00:11 2013 From: ok at cs.otago.ac.nz (Richard A. O'Keefe) Date: Mon, 9 Dec 2013 16:00:11 +1300 Subject: [Haskell-cafe] finding "good work" in CS In-Reply-To: References: Message-ID: On 8/12/2013, at 12:54 PM, Dennis Raddle wrote: > It's me again, guy aged 45 thinking about doing graduate work in CS. > > I read this ebook about a guy's CS PhD, "The PhD Grind": > > > > It was enlightening. I used to think that software in the C.S. academic world must be well-written, seeing as it was written by computer scientists. There is a huge difference between *computer science* and *programming*. I remember two excellent computer scientists I used to know, neither of whom had any idea of indentation. (Seriously, one of them began each function on a new line, and pressed the RETURN key only at the very end of it.) Come to think of it, I met another computer scientist who was writing a library for an exotic flavour of priority queue -- which he understood to a depth I shall never reach -- and was interested in comparing it against some other priority queue implementations, and asked me for some advice about the coding. I suggested including the classic binary-heap-in-an- array as a baseline. It beat the pants off _all_ the other priority queue implementations. Here's a piece of computer science that I would like some help with. I call it the Indirect Cycle Detection problem. Given: Domains P and E, functions f : P -> Maybe P g : P -> E Define to_list :: Maybe P -> [E] to_list Nothing = [] to_list (Just p) = g p : to_list (f p) Given: That f is cyclic starting at p0. Find: The shortest alpha, beta such that to_list p0 is alpha ++ cycle beta and do so *efficiently*. Now, I can use tortoise-and-hare to find a cycle in f and then use brute force to find a shortest prefix and cycle of to_list ... The stuff I've checked so far about periods in strings has nothing to say about periods that begin _after_ a non-empty prefix. The point here is that this is a computer science question which can be answered by someone who has no knowledge of any programming language. Indeed, I don't see any reason to expect that programming skill would help. > (I didn't like the poorly organized and simple-minded code involved in my last job at NASA.) And yet we hear amazing things about NASA code quality. > Turns out that academic code can be very poor indeed, sometimes just a hacked prototype meant to demonstrate an idea to get it published. Since the declared *aim* of Universities is *published* research, it is *rational* for code quality to be no higher than is required to get that job done. Basically, Sturgeon's Revelation -- see http://http://en.wikipedia.org/wiki/Sturgeon's_Law -- is a universal truth. I remember a certain company whose compilers and operating system were gems of care and readability, yet provided a statistics package whose code was _nightmarish_, pointlessly bulky, and would happily invert a singular matrix and keep running. Had you considered building software checking tools as a topic? From eijiro.sumii at gmail.com Mon Dec 9 05:41:07 2013 From: eijiro.sumii at gmail.com (Eijiro Sumii) Date: Mon, 09 Dec 2013 14:41:07 +0900 (JST) Subject: [Haskell-cafe] FLOPS 2014 Final CFP (Reminder) Message-ID: <20131209.144107.200745603266639624.sumii@ecei.tohoku.ac.jp> Final Call For Papers ===================== Twelfth International Symposium on Functional and Logic Programming (FLOPS 2014) June 4-6, 2014 Kanazawa, Japan http://www.jaist.ac.jp/flops2014/ ---------------------------------------------------------------------- - Submission deadline: December 13, 2013 - Journal publications in JFP (Jounral of Functional Programming) and TPLP (Theory and Practice of Logic Programming) are planned (see below). - Hyakumangoku Matsuri ( https://www.google.com/search?q=hyakumangoku%20matsuri&tbm=isch ) is scheduled *just* after FLOPS 2014. ---------------------------------------------------------------------- FLOPS is a forum for research on all issues concerning declarative programming, including functional programming and logic programming, and aims to promote cross-fertilization and integration between the two paradigms. Previous FLOPS meetings were held at Fuji Susono (1995), Shonan Village (1996), Kyoto (1998), Tsukuba (1999), Tokyo (2001), Aizu (2002), Nara (2004), Fuji Susono (2006), Ise (2008), Sendai (2010), and Kobe (2012). Topics ====== FLOPS solicits original papers in all areas of functional and logic programming, including (but not limited to): - Language issues: language design and constructs, programming methodology, integration of paradigms, interfacing with other languages, type systems, constraints, concurrency and distributed computing. - Foundations: logic and semantics, rewrite systems and narrowing, type theory, proof systems. - Implementation issues: compilation techniques, memory management, program analysis and transformation, partial evaluation, parallelism. - Applications: case studies, real-world applications, graphical user interfaces, Internet applications, XML, databases, formal methods and model checking. The proceedings will be published as an LNCS volume. The proceedings of the previous meetings (FLOPS 1999, 2001, 2002, 2004, 2006, 2008, 2010, and 2012) were published as LNCS 1722, 2024, 2441, 2998, 3945, 4989, 6009, and 7294. PC Co-Chairs ============ Michael Codish (Ben-Gurion University of the Negev) Eijiro Sumii (Tohoku University) PC Members ========== Lars Birkedal (Aarhus University) Michael Codish (Ben-Gurion University of the Negev) [co-chair] Marina De Vos (University of Bath) Moreno Falaschi (Universita degli studi di Udine) Carsten Fuhs (University College London) John Gallagher (Roskilde Universitet / IMDEA Software Institute) Samir Genaim (Universidad Complutense de Madrid) Laura Giordano (Universita del Piemonte Orientale) Ichiro Hasuo (University of Tokyo) Fritz Henglein (University of Copenhagen) Andy King (University of Kent) Oleg Kiselyov Vitaly Lagoon (MathWorks) Shin-Cheng Mu (Academia Sinica) Keiko Nakata (Institute of Cybernetics at Tallinn University of Technology) Luke Ong (University of Oxford) Peter Schachte (University of Melbourne) Takehide Soh (Kobe University) Eijiro Sumii (Tohoku University) [co-chair] Tachio Terauchi (Nagoya University) Joost Vennekens (KU Leuven) Janis Voigtlaender (Universitaet Bonn) Stephanie Weirich (University of Pennsylvania) Local Chair =========== Yuki Chiba (JAIST) Submission ========== Submissions must be unpublished and not submitted for publication elsewhere. Work that already appeared in unpublished or informally published workshops proceedings may be submitted. See also ACM SIGPLAN Republication Policy: http://www.sigplan.org/Resources/Policies/Republication Submissions should fall into one of the following categories: - Regular research papers: they should describe new results and will be judged on originality, correctness, and significance. - System descriptions: they should contain a link to a working system and will be judged on originality, usefulness, and design. - Declarative pearls: new and excellent declarative programs or theories with illustrative applications. System descriptions and declarative pearls must be explicitly marked as such in the title. Submissions must be written in English and can be up to 15 pages long including references, though pearls are typically shorter. Authors are required to use LaTeX2e and the Springer llncs class file, available at: http://www.springer.de/comp/lncs/authors.html Regular research papers should be supported by proofs and/or experimental results. In case of lack of space, this supporting information should be made accessible otherwise (e.g., a link to a Web page, or an appendix). Papers should be submitted electronically at: https://www.easychair.org/conferences/?conf=flops2014 Important Dates =============== Submission deadline: December 13, 2013 Author notification: February 10, 2014 Camera-ready copy: March 7, 2014 Journal Publication =================== - Journal of Functional Programming and - Theory and Practice of Logic Programming 2-4 of the best papers in each of the two areas: Functional Programming and Logic Programming, will be invited for inclusion in a designated FLOPS section within each of the two journals. The Theory and Practice of Logic Programming papers will appear as "Rapid Publications". All of the these submissions are expected to represent high-quality revisions and extensions of the selected FLOPS papers and will be reviewed under the standard criteria of each journal. Venue ===== Main Hall, Ishikawa Prefectural Museum of Art, 2-1 Dewa-machi, Kanazawa, Ishikawa 920-0963 JAPAN. Some Previous FLOPS =================== FLOPS 2012, Kobe: http://www.org.kobe-u.ac.jp/flops2012/ FLOPS 2010, Sendai: http://www.kb.ecei.tohoku.ac.jp/flops2010/ FLOPS 2008, Ise: http://www.math.nagoya-u.ac.jp/~garrigue/FLOPS2008/ Sponsor ======= Japan Society for Software Science and Technology (JSSST), Special Interest Group on Programming and Programming Languages (SIG-PPL) In Cooperation With =================== ACM SIGPLAN Asian Association for Foundation of Software (AAFS) Association for Logic Programming (ALP) From ker0sin at yandex.ru Mon Dec 9 06:43:00 2013 From: ker0sin at yandex.ru (Alexander Pakhomov) Date: Mon, 09 Dec 2013 10:43:00 +0400 Subject: [Haskell-cafe] GHCi linker Message-ID: <109211386571380@web4j.yandex.ru> Hi. Trying to runhaskell following: import Graphics.UI.Gtk main = print "OK" I got GHCi runtime linker: fatal error: I found a duplicate definition for symbol locale_charset whilst processing object file /usr/local/lib/libintl.a This could be caused by: * Loading two different object files which export the same symbol * Specifying the same object file twice on the GHCi command line * An incorrect `package.conf' entry, causing some object to be loaded twice. GHCi cannot safely continue in this situation. Exiting now. Sorry. ghc works fine and creates working executable. In ghci "import Graphics.UI.Gtk" works too. What is the difference between runhaskell, ghci interactive and ghc linkers? ghc 7.6.3 running on OpenBSD. It is built from ports system with default patches. I don't see any patch that touches GHCi linker. From carter.schonwald at gmail.com Mon Dec 9 06:57:45 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Mon, 9 Dec 2013 01:57:45 -0500 Subject: [Haskell-cafe] GHCi linker In-Reply-To: <109211386571380@web4j.yandex.ru> References: <109211386571380@web4j.yandex.ru> Message-ID: ghci in 7.6 and older uses its own special linker.This is responsible to many many linking bugs in ghci try GHC head (and soon ghc 7.8) and see if the problem goes away. GHCi in HEAD / 7.7 uses the system linker. Otherwise please please please file a ticket on GHC Trac so it can be fixed asap. NB: there may or may not be problems with one of the *BSD dynamic linkers, I don't recall. But if you hit troubles with GHC head, please report them and the ghc devs will work with you to figure out a fix. On Mon, Dec 9, 2013 at 1:43 AM, Alexander Pakhomov wrote: > Hi. Trying to runhaskell following: > > import Graphics.UI.Gtk > > main = print "OK" > > I got > GHCi runtime linker: fatal error: I found a duplicate definition for symbol > locale_charset > whilst processing object file > /usr/local/lib/libintl.a > This could be caused by: > * Loading two different object files which export the same symbol > * Specifying the same object file twice on the GHCi command line > * An incorrect `package.conf' entry, causing some object to be > loaded twice. > GHCi cannot safely continue in this situation. Exiting now. Sorry. > > ghc works fine and creates working executable. In ghci "import > Graphics.UI.Gtk" works too. > > What is the difference between runhaskell, ghci interactive and ghc > linkers? > ghc 7.6.3 running on OpenBSD. It is built from ports system with default > patches. I don't see any patch that touches GHCi linker. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From alfredo.dinapoli at gmail.com Mon Dec 9 08:30:59 2013 From: alfredo.dinapoli at gmail.com (Alfredo Di Napoli) Date: Mon, 9 Dec 2013 08:30:59 +0000 Subject: [Haskell-cafe] Is anyone currently working on SDL2 FFI ? In-Reply-To: References: Message-ID: As far as I know Lemmih and Oliver Charles are working on it: https://github.com/Lemmih/hsSDL2 Me and another guy recently revamped its bindings for SFML 2.x, and created and organisation for it: https://github.com/SFML-haskell Feel free to browse and stop by. I hope I satisfied your thirst for bindings :) Alfredo On 9 December 2013 00:08, Carter Schonwald wrote: > good question! > you should ask on #haskell-game(s?) irc channel, i'd be surprised if no > one is working on it. > > > On Sun, Dec 8, 2013 at 7:05 PM, ?mer Sinan A?acan wrote: > >> Hello everyone, >> >> I was wondering if anyone is currently working on SDL2 FFI. I really >> need that library and I'm willing to contribute to the work, but I >> can't currently spare enough time to start it from scratch(it's very >> big library). >> >> I know we have OpenGL and GLFW bindings and gloss for 2D stuff etc. >> but for several reasons I want this particular library. (just wanted >> to make this clear because I presume people point me alternatives >> otherwise :-) ) >> >> Thanks, >> >> --- >> ?mer Sinan A?acan >> http://osa1.net >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ollie at ocharles.org.uk Mon Dec 9 12:10:43 2013 From: ollie at ocharles.org.uk (Oliver Charles) Date: Mon, 09 Dec 2013 12:10:43 +0000 Subject: [Haskell-cafe] Is anyone currently working on SDL2 FFI ? In-Reply-To: References: Message-ID: <52A5B343.8020200@ocharles.org.uk> On 12/09/2013 08:30 AM, Alfredo Di Napoli wrote: > As far as I know Lemmih and Oliver Charles are working on it: > > https://github.com/Lemmih/hsSDL2 That's right, though recently I don't think there has been much activity. I need to touch base with David and see where we stand, and whether we should just release it as-is and let people report issues for the important bindings that are missing. - ocharles -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 490 bytes Desc: OpenPGP digital signature URL: From omeragacan at gmail.com Mon Dec 9 12:48:04 2013 From: omeragacan at gmail.com (=?ISO-8859-9?Q?=D6mer_Sinan_A=F0acan?=) Date: Mon, 9 Dec 2013 14:48:04 +0200 Subject: [Haskell-cafe] Is anyone currently working on SDL2 FFI ? In-Reply-To: <52A5B343.8020200@ocharles.org.uk> References: <52A5B343.8020200@ocharles.org.uk> Message-ID: Thank you everyone. Oliver, I want to get involved in hsSDL2 development. In fact, I just sent my first pull request and I'll send lots of others too(starting from TTF extension). Can you also include me in your discussions about future of hsSDL2 ? --- ?mer Sinan A?acan http://osa1.net 2013/12/9 Oliver Charles : > On 12/09/2013 08:30 AM, Alfredo Di Napoli wrote: >> As far as I know Lemmih and Oliver Charles are working on it: >> >> https://github.com/Lemmih/hsSDL2 > > That's right, though recently I don't think there has been much > activity. I need to touch base with David and see where we stand, and > whether we should just release it as-is and let people report issues for > the important bindings that are missing. > > - ocharles > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From J.Hage at uu.nl Mon Dec 9 13:02:28 2013 From: J.Hage at uu.nl (Jurriaan Hage) Date: Mon, 9 Dec 2013 14:02:28 +0100 Subject: [Haskell-cafe] Call for Participation PEPM 2014 (co-located with POPL 2014) References: Message-ID: <47FD7FDD-CAD3-41D7-9602-E1A70F768621@uu.nl> Dear all, Note the presence of Haskell papers in the program. Hope to see many of you there. best, Jur (co-chair of PEPM 2014) =========== PEPM 2014 =============== ACM SIGPLAN Workshop on Partial Evaluation and Program Manipulation http://www.program-transformation.org/PEPM14 January 20-21, 2014 San Diego, CA, USA (Affiliated with POPL 2014) CALL FOR PARTICIPATION IMPORTANT DATES * Hotel reservation deadline: December 21, 2013 * Early registration deadline: December 31, 2013 VENUE PEPM'14 and all POPL'14 affiliated events will take place at the US Grant in San Diego, CA, USA. SCOPE The PEPM Symposium/Workshop series aims at bringing together researchers and practitioners working in the areas of program manipulation, partial evaluation, and program generation. PEPM focuses on techniques, theory, tools, and applications of analysis and manipulation of programs. INVITED TALKS: * Manuel Fahndrich (Microsoft Research, USA) on Lessons from a Web-Based IDE and Runtime * Sven-Bodo Scholz (Heriott-Watt University, Scotland) on Partial Evaluation as Universal Compiler Tool (experiences from the SAC eco system) PROGRAM CHAIRS Wei Ngan Chin (National University of Singapore, Singapore) Jurriaan Hage (Utrecht University, Netherlands) PROGRAM COMMITTEE Evelyne Contejean (LRI, CNRS, Universit? Paris-Sud, France) Cristina David (University of Oxford, UK) Alain Frisch (LexiFi, France) Ronald Garcia (University of British Columbia, Canada) Zhenjiang Hu (National Institute of Informatics, Japan) Paul H J Kelly (Imperial College, UK) Oleg Kiselyov (Monterey, USA) Naoki Kobayashi (University of Tokyo, Japan) Jens Krinke (University College London, UK) Ryan Newton (University of Indiana, USA) Alberto Pardo (Universidad de la Rep?blica, Uruguay) Sungwoo Park (Pohang University of Science and Technology, South Korea) Tiark Rompf (Oracle Labs & EPFL, Switzerland) Sukyoung Ryu (KAIST, South Korea) Kostis Sagonas (Uppsala University, Sweden) Max Schaefer (Nanyang Technological University, Singapore) Harald S?ndergaard (The University of Melbourne, Australia) Eijiro Sumii (Tohoku University, Japan) Eric Van Wyk (University of Minnesota, USA) Jeremy Yallop (University of Cambridge, UK) PRELIMINARY PROGRAM DAY 1: Monday, January 20th, 2014 ================================== 09:00 - 10:00 Invited Talk =========================== Lessons from a Web-Based IDE and Runtime Manuel Fahndrich 10:30 - 12:00 Meta-Programming ------------------------------- Combinators for Impure yet Hygienic Code Generation Yukiyoshi Kameyama, Oleg Kiselyov, Chung-Chieh Shan Effective Quotation James Cheney, Sam Lindley, Gabriel Radanne, Philip Wadler Compile-time Reflection and Metaprogramming for Java Weiyu Miao, Jeremy Siek 14:00 - 15:25 Bidirectional Transformations -------------------------------------------- Monadic Combinators for "Putback" Style Bidirectional Programming Hugo Pacheco, Zhenjiang Hu and Sebastian Fischer Semantic Bidirectionalization Revisited Meng Wang and Shayan Najd Generating Attribute Grammar-based Bidirectional Transformations from Rewrite Rules Pedro Martins, Joao Paulo Fernandes, Joao Saraiva and Eric Van Wyk 16:00 - 17:00 Static Analysis and Optimization ----------------------------------------------- Optimizing SYB is Easy! Michael D. Adams, Andrew Farmer, Jose Pedro Magalhaes: QEMU/CPC: Static Analysis and CPS Conversion for Safe, Portable, and Efficient Coroutines Gabriel Kerneis, Charlie Shepherd, Stefan Hajnoczi ================================= DAY 2: Tuesday, January 21, 2014 ================================= 09:00 - 10:00 Invited Talk --------------------------- Partial Evaluation as Universal Compiler Tool (experiences from the SAC eco system) Sven-Bodo Scholz 10:30 - 12:00 Program Transformation -------------------------------------- The HERMIT in the Stream Andrew Farmer, Christian Hoener Zu Siederdissen, Andy Gill Type-Changing Rewriting and Semantics-Preserving Transformation Sean Leather, Johan Jeuring, Andres Loeh, Bram Schuur An Operational Semantics for Android Activities Etienne Payet, Fausto Spoto 14:00 - 15:30 Type Systems ---------------------------- Early Detection of Type Errors in C++ Templates Sheng Chen, Martin Erwig Lazy Stateless Incremental Evaluation Machinery for Attribute Grammars Jeroen Bransen, Atze Dijkstra, Doaitse Swierstra Deriving Interpretations of the Gradually-Typed Lambda Calculus. Alvaro Garcia-Perez, Pablo Nogueira, Ilya Sergey 16:00 - 17:20 Program Analysis/Testing ---------------------------------------- Automating Property-based Testing of Evolving Web Services Huiqing Li, Simon Thompson, Pablo Lamela Seijas, Miguel Angel Francisco A Modular and Generic Analysis Server System for Functional Logic Programs Michael Hanus, Fabian Skrlac HIPimm: Verifying Granular Immutability Guarantees Andreea Costea, Asankhaya Sharma, Cristina David -------------- next part -------------- An HTML attachment was scrubbed... URL: From ker0sin at yandex.ru Mon Dec 9 22:07:13 2013 From: ker0sin at yandex.ru (Alexander Pakhomov) Date: Tue, 10 Dec 2013 02:07:13 +0400 Subject: [Haskell-cafe] cmm Message-ID: <281101386626833@web16j.yandex.ru> Hi. Trying to compile ghc-7.7.20130828 on OpenBSD I got an error: rts/HeapStackCheck.cmm:97:18: parse error on input `[' The code is following: 96 if (HpAlloc <= BLOCK_SIZE 97 && bdescr_link(CurrentNursery) != NULL) { which preprocesses to: if (HpAlloc <= (1<<12) && b0[CurrentNursery+15] != (0::bits64)) { This is the first occurrence of b0 in preprocessed file. I believe that it is due to undefined b0. Command that fails is: "inplace/bin/ghc-stage1" -static -H32m -O -Iincludes -Iincludes/dist -Iincludes/dist-derivedconstants/header -Iincludes/dist-ghcconstants/header -Irts -Irts/dist/build -DCOMPILING_RTS -package-name rts -dcmm-lint -i -irts -irts/dist/build -irts/dist/build/autogen -Irts/dist/build -Irts/dist/build/autogen -O2 -c rts/HeapStackCheck.cmm -o rts/dist/build/HeapStackCheck.o To preprocess do the following: cpp -O -Iincludes -Iincludes/dist -Iincludes/dist-derivedconstants/header -Iincludes/dist-ghcconstants/header -Irts -Irts/dist/build -DCOMPILING_RTS -Irts/dist/build -Irts/dist/build/autogen rts/HeapStackCheck.cmm | less Can you please find source of b0 in preprocessed file? From carter.schonwald at gmail.com Mon Dec 9 22:15:17 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Mon, 9 Dec 2013 17:15:17 -0500 Subject: [Haskell-cafe] cmm In-Reply-To: <281101386626833@web16j.yandex.ru> References: <281101386626833@web16j.yandex.ru> Message-ID: are you using clang or gcc? 2013 08 28 is from a while a go, please clone GHC HEAD from today. If you still have problems, please file a ticket on ghc track, and/or email ghc-devs On Mon, Dec 9, 2013 at 5:07 PM, Alexander Pakhomov wrote: > Hi. Trying to compile ghc-7.7.20130828 on OpenBSD I got an error: > rts/HeapStackCheck.cmm:97:18: parse error on input `[' > The code is following: > 96 if (HpAlloc <= BLOCK_SIZE > 97 && bdescr_link(CurrentNursery) != NULL) { > which preprocesses to: > if (HpAlloc <= (1<<12) > && b0[CurrentNursery+15] != (0::bits64)) { > This is the first occurrence of b0 in preprocessed file. I believe that it > is due to undefined b0. > Command that fails is: > "inplace/bin/ghc-stage1" -static -H32m -O -Iincludes -Iincludes/dist > -Iincludes/dist-derivedconstants/header -Iincludes/dist-ghcconstants/header > -Irts -Irts/dist/build -DCOMPILING_RTS -package-name rts -dcmm-lint -i > -irts -irts/dist/build -irts/dist/build/autogen -Irts/dist/build > -Irts/dist/build/autogen -O2 -c rts/HeapStackCheck.cmm -o > rts/dist/build/HeapStackCheck.o > To preprocess do the following: > cpp -O -Iincludes -Iincludes/dist -Iincludes/dist-derivedconstants/header > -Iincludes/dist-ghcconstants/header -Irts -Irts/dist/build -DCOMPILING_RTS > -Irts/dist/build -Irts/dist/build/autogen rts/HeapStackCheck.cmm | > less > > Can you please find source of b0 in preprocessed file? > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ker0sin at yandex.ru Mon Dec 9 22:19:25 2013 From: ker0sin at yandex.ru (Alexander Pakhomov) Date: Tue, 10 Dec 2013 02:19:25 +0400 Subject: [Haskell-cafe] cmm In-Reply-To: References: <281101386626833@web16j.yandex.ru> Message-ID: <285461386627565@web16j.yandex.ru> An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Mon Dec 9 22:39:24 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Mon, 9 Dec 2013 17:39:24 -0500 Subject: [Haskell-cafe] cmm In-Reply-To: <285461386627565@web16j.yandex.ru> References: <281101386626833@web16j.yandex.ru> <285461386627565@web16j.yandex.ru> Message-ID: ummm, cmm in 7.6 and HEAD are different languages please follow the directions here https://ghc.haskell.org/trac/ghc/wiki/Building On Mon, Dec 9, 2013 at 5:19 PM, Alexander Pakhomov wrote: > I have both. Think it's gcc. It is quite weird if that cpp (preprocessor) > differs. AFAIK cmm files are compiled directly by ghc. The problem seem to > be in cmm file, since ghc-7.6.3 fails with the same message. > > 10.12.2013, 02:15, "Carter Schonwald" : > > are you using clang or gcc? 2013 08 28 is from a while a go, please > clone GHC HEAD from today. If you still have problems, please file a ticket > on ghc track, and/or email ghc-devs > > > > > On Mon, Dec 9, 2013 at 5:07 PM, Alexander Pakhomov wrote: > > Hi. Trying to compile ghc-7.7.20130828 on OpenBSD I got an error: > rts/HeapStackCheck.cmm:97:18: parse error on input `[' > The code is following: > 96 if (HpAlloc <= BLOCK_SIZE > 97 && bdescr_link(CurrentNursery) != NULL) { > which preprocesses to: > if (HpAlloc <= (1<<12) > && b0[CurrentNursery+15] != (0::bits64)) { > This is the first occurrence of b0 in preprocessed file. I believe that it > is due to undefined b0. > Command that fails is: > "inplace/bin/ghc-stage1" -static -H32m -O -Iincludes -Iincludes/dist > -Iincludes/dist-derivedconstants/header -Iincludes/dist-ghcconstants/header > -Irts -Irts/dist/build -DCOMPILING_RTS -package-name rts -dcmm-lint -i > -irts -irts/dist/build -irts/dist/build/autogen -Irts/dist/build > -Irts/dist/build/autogen -O2 -c rts/HeapStackCheck.cmm -o > rts/dist/build/HeapStackCheck.o > To preprocess do the following: > cpp -O -Iincludes -Iincludes/dist -Iincludes/dist-derivedconstants/header > -Iincludes/dist-ghcconstants/header -Irts -Irts/dist/build -DCOMPILING_RTS > -Irts/dist/build -Irts/dist/build/autogen rts/HeapStackCheck.cmm | > less > > Can you please find source of b0 in preprocessed file? > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ker0sin at yandex.ru Mon Dec 9 22:43:28 2013 From: ker0sin at yandex.ru (Alexander Pakhomov) Date: Tue, 10 Dec 2013 02:43:28 +0400 Subject: [Haskell-cafe] cmm In-Reply-To: References: <281101386626833@web16j.yandex.ru> <285461386627565@web16j.yandex.ru> Message-ID: <56451386629008@web5h.yandex.ru> An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Mon Dec 9 22:48:33 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Mon, 9 Dec 2013 17:48:33 -0500 Subject: [Haskell-cafe] cmm In-Reply-To: <56451386629008@web5h.yandex.ru> References: <281101386626833@web16j.yandex.ru> <285461386627565@web16j.yandex.ru> <56451386629008@web5h.yandex.ru> Message-ID: yes, you need a ghc to build ghc. please follow the build directions, and if you have a build failure with today's GHC head (rather than the one from ~ 4 months ago), please report the bug on GHC trac. On Mon, Dec 9, 2013 at 5:43 PM, Alexander Pakhomov wrote: > > > 10.12.2013, 02:39, "Carter Schonwald" : > > ummm, cmm in 7.6 and HEAD are different languages > > please follow the directions here > https://ghc.haskell.org/trac/ghc/wiki/Building > > > > > Is it OK that ./configure && make runs system (/usr/local/bin/ghc) ghc? > > > > On Mon, Dec 9, 2013 at 5:19 PM, Alexander Pakhomov wrote: > > I have both. Think it's gcc. It is quite weird if that cpp (preprocessor) > differs. AFAIK cmm files are compiled directly by ghc. The problem seem to > be in cmm file, since ghc-7.6.3 fails with the same message. > > > OK. That was a try to figure out problem. > > > 10.12.2013, 02:15, "Carter Schonwald" : > > are you using clang or gcc? 2013 08 28 is from a while a go, please > clone GHC HEAD from today. If you still have problems, please file a ticket > on ghc track, and/or email ghc-devs > > > > > On Mon, Dec 9, 2013 at 5:07 PM, Alexander Pakhomov wrote: > > Hi. Trying to compile ghc-7.7.20130828 on OpenBSD I got an error: > rts/HeapStackCheck.cmm:97:18: parse error on input `[' > The code is following: > 96 if (HpAlloc <= BLOCK_SIZE > 97 && bdescr_link(CurrentNursery) != NULL) { > which preprocesses to: > if (HpAlloc <= (1<<12) > && b0[CurrentNursery+15] != (0::bits64)) { > This is the first occurrence of b0 in preprocessed file. I believe that it > is due to undefined b0. > Command that fails is: > "inplace/bin/ghc-stage1" -static -H32m -O -Iincludes -Iincludes/dist > -Iincludes/dist-derivedconstants/header -Iincludes/dist-ghcconstants/header > -Irts -Irts/dist/build -DCOMPILING_RTS -package-name rts -dcmm-lint -i > -irts -irts/dist/build -irts/dist/build/autogen -Irts/dist/build > -Irts/dist/build/autogen -O2 -c rts/HeapStackCheck.cmm -o > rts/dist/build/HeapStackCheck.o > To preprocess do the following: > cpp -O -Iincludes -Iincludes/dist -Iincludes/dist-derivedconstants/header > -Iincludes/dist-ghcconstants/header -Irts -Irts/dist/build -DCOMPILING_RTS > -Irts/dist/build -Irts/dist/build/autogen rts/HeapStackCheck.cmm | > less > > Can you please find source of b0 in preprocessed file? > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From temporalabstraction at gmail.com Tue Dec 10 03:57:40 2013 From: temporalabstraction at gmail.com (EatsKittens) Date: Tue, 10 Dec 2013 04:57:40 +0100 Subject: [Haskell-cafe] XEventPtr in Xlib? Message-ID: Xlib.Event seems to define the interestingly recursive type data XEvent = XEvent (Ptr XEvent) and otherwise give no information about that type. I need this type to send an XEvent message to a window, is this a mistake or am I overlooking something in how to use it, or is the idea that the only way to make XEvent data is to make it in C and import it from there? -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Tue Dec 10 05:22:43 2013 From: allbery.b at gmail.com (Brandon Allbery) Date: Tue, 10 Dec 2013 00:22:43 -0500 Subject: [Haskell-cafe] XEventPtr in Xlib? In-Reply-To: References: Message-ID: On Mon, Dec 9, 2013 at 10:57 PM, EatsKittens wrote: > Xlib.Event seems to define the interestingly recursive type data XEvent = > XEvent (Ptr XEvent) and otherwise give no information about that type. > Anything on the far side of a Ptr is defined by C and accessed via the FFI. In this case, you're looking for the XEvent structure defined by the C Xlib and described in X11/X.h (constants) and X11/Xlib.h (structs; note that there is a separate struct for each event type although they all have a common preamble). You may be better served by the event definitions in http://xmonad.org/xmonad-docs/X11/Graphics-X11-Xlib-Extras.html which is a Haskell, instead of FFI, interface. (I pointed to the xmonad copy of the docs because that's what I already have loaded in a tab, but it's part of the same X11 binding as Graphics.X11.Xlib.Event.) I need this type to send an XEvent message to a window, is this a mistake > or am I overlooking something in how to use it, or is the idea that the > only way to make XEvent data is to make it in C and import it from there? > allocaXEvent is defined in Graphics.X11.Xlib.Event, but you need to refer to the C Xlib definitions and use FFI marshaling to work with it (and may need to know C type sizes and how the C compiler packs structs on your system). There's some code in xmonad-contrib which uses that interface to send custom events. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From carlo at carlo-hamalainen.net Tue Dec 10 08:02:59 2013 From: carlo at carlo-hamalainen.net (Carlo Hamalainen) Date: Tue, 10 Dec 2013 09:02:59 +0100 Subject: [Haskell-cafe] Does anyone use ghc-mod with Yesod? Message-ID: <52A6CAB3.3020406@carlo-hamalainen.net> Hi, I have been using ghc-mod (via ghcmod-vim) recently and it's fantastic but I can't get it to work on one of my Yesod projects. This is what happens on a minimal scaffolded Yesod project: $ yesod init # create project Foo, sqlite, no other options $ cd Foo $ cabal install # builds ok, no issues $ ghc-mod check Handler/Home.hs Handler/Home.hs:0:0:Error:: cannot satisfy -package yesod-test (use -v for more information) I've reported the error on github [1] but I was wondering if anyone here had a workaround, maybe using cabal-dev or sandboxing or something? Cheers, -- Carlo Hamalainen http://carlo-hamalainen.net [1] https://github.com/kazu-yamamoto/ghc-mod/issues/170 From alfredo.dinapoli at gmail.com Tue Dec 10 11:51:32 2013 From: alfredo.dinapoli at gmail.com (Alfredo Di Napoli) Date: Tue, 10 Dec 2013 11:51:32 +0000 Subject: [Haskell-cafe] [ANN] SFML and SFML-control Message-ID: Hello guys, I will send you the link back to the original Reddit discussion that, for some unfathomable reason is not showing up directly in /r/haskell. http://www.reddit.com/r/haskell/comments/1sjemq/ann_sfml_and_sfmlcontrol/ Feedback appreciated! Alfredo -------------- next part -------------- An HTML attachment was scrubbed... URL: From Neena.Singh at henlowgroup.com Tue Dec 10 14:58:43 2013 From: Neena.Singh at henlowgroup.com (Neena Singh) Date: Tue, 10 Dec 2013 14:58:43 +0000 Subject: [Haskell-cafe] SENIOR HASKELL OPPORTUNITY Message-ID: <2252CC638F64CD4FBB38CD13A85C6D8801C82C71@GYRO.henlow.local> Hello, I have been retained by a leading Hedge Fund who are looking for an experienced Haskell developer to join their highly regarded front office technology team. This is a great opportunity for a passionate technologist to join a group working very closely with the trading floor on advanced Haskell projects. Previous finance experience is not a pre-requisite however a passion for Haskell is a must. If you are interested learning more about this opportunity and potential salary ranges please call me on 020 7871 4482 or email me Neena.singh at henlowgroup.com. I look forward to hearing from you, Regards, Neena Neena Singh Analyst Henlow Recruitment Group +44(0)20 7871 1834 neena.singh at henlowgroup.com www.henlowgroup.com [cid:image017.jpg at 01CECB15.783A6E10] [cid:image019.png at 01CECB15.783A6E10] [cid:image005.png at 01CEDA27.B1142430] This e-mail contains proprietary information some or all of which may be legally privileged. It is for the intended recipient only. If an address or transmission error has misdirected this email, please notify the author by replying to this e-mail. If you are not the intended recipient you must not use, disclose, distribute, copy, print, rely on or retain this e-mail. This email and any attached files have been scanned for the presence of computer viruses, however you are advised that you open any attachments at your own risk. All e-mails including CV's are subject to our standard terms and conditions of business. The acceptance of any CV's constitutes the acceptance of our standard terms and conditions of business unless there has been written prior agreement. Any views or opinions presented here may be solely those of the originator and are not necessarily those of Henlow Recruitment Group. Henlow Recruitment Group reserves the right to share information between companies within our group. Please read Henlow Recruitment Groups' privacy policy at http://www.henlowgroup.com/privacy-policy to understand how Henlow Recruitment Group uses and protects the information you provide. -------------- next part -------------- An HTML attachment was scrubbed... URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: image001.jpg Type: image/jpeg Size: 923 bytes Desc: image001.jpg URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: image002.png Type: image/png Size: 1192 bytes Desc: image002.png URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: image003.png Type: image/png Size: 4995 bytes Desc: image003.png URL: From haskell-cafe at maartenfaddegon.nl Tue Dec 10 15:48:57 2013 From: haskell-cafe at maartenfaddegon.nl (Maarten Faddegon) Date: Tue, 10 Dec 2013 15:48:57 +0000 Subject: [Haskell-cafe] No instance for (Constructor Main.D1MyData) Message-ID: <52A737E9.8090002@maartenfaddegon.nl> Dear list, I try to implement the generic show of section 3.6 from the paper Magelheas et al., "A Generic Deriving Mechanism for Haskell" but run into problems with the Constructor class. If someone could point out what is wrong here I would be most grateful. I import generics: > import GHC.Generics And I define my own "Show" class named "Toonbaar", and a generic version of the class "GToonbaar": > class Toonbaar a where > toon :: a -> String > > default toon :: (Generic a, GToonbaar (Rep a)) => a -> String > toon a = gtoon (from a) > > instance Toonbaar Int where > toon i = show i > > class GToonbaar f where > gtoon :: f a -> String Next I want implement instances of gtoon for the 5 primitive types that are used to by the "from" function to represent data types. Most interisting is the meta-information instance here, where I use the "conName" function. Most of the rest I copied from the serialization example on the wiki: http://www.haskell.org/haskellwiki/GHC.Generics#Complete_working_example > -- | Meta-information (constructor names, etc.) > instance (GToonbaar a, Constructor c) => GToonbaar (M1 i c a) where > gtoon m@(M1 _) = conName m > > -- | Unit: used for constructors without arguments > instance GToonbaar U1 where > gtoon _ = "Unit" > > -- | Constants, additional parameters and recursion of kind * > instance (GToonbaar a, GToonbaar b) => GToonbaar (a :*: b) where > gtoon _ = "Constant" > > > -- | Sums: encode choice between constructors > instance (GToonbaar a, GToonbaar b) => GToonbaar (a :+: b) where > gtoon x = gtoon x > > -- | Products: encode multiple arguments to constructors > instance (Toonbaar a) => GToonbaar (K1 i a) where > gtoon (K1 x) = toon x I define a data type, deriving Generic and make it an instance of Toonbaar. > data MyData = MyInt Int > deriving (Generic) > instance Toonbaar MyData > > main = putStrLn (toon (MyInt 42)) When I try to compile the above, ghc emits the following error: No instance for (Constructor Main.D1MyData) arising from a use of `Main.$gdmtoon' Possible fix: add an instance declaration for (Constructor Main.D1MyData) In the expression: (Main.$gdmtoon) In an equation for `toon': toon = (Main.$gdmtoon) In the instance declaration for `Toonbaar MyData' There are 2 things here that I do not understand: 1. I was under the impression that Constructor can be derived, but this does not seem to be the case. (I tried adding it to the line where I also derive Generic). Is there another way to derive it? 2. Why is the error message referring to D1MyData and not to MyData? And $gdmtoon instead of toon or gtoon? Thanks, Maarten From jpm at cs.uu.nl Tue Dec 10 16:34:49 2013 From: jpm at cs.uu.nl (=?ISO-8859-1?Q?Jos=E9_Pedro_Magalh=E3es?=) Date: Tue, 10 Dec 2013 16:34:49 +0000 Subject: [Haskell-cafe] No instance for (Constructor Main.D1MyData) In-Reply-To: <52A737E9.8090002@maartenfaddegon.nl> References: <52A737E9.8090002@maartenfaddegon.nl> Message-ID: Hi Maarten, On Tue, Dec 10, 2013 at 3:48 PM, Maarten Faddegon < haskell-cafe at maartenfaddegon.nl> wrote: > Dear list, > > > -- | Meta-information (constructor names, etc.) >> instance (GToonbaar a, Constructor c) => GToonbaar (M1 i c a) where >> > This is not good; an instance of |Constructor c| will only be available when your |M1 i c a| is actually |M1 C c a| (so |i ~ C|). In the other cases (that is, when |i| is either |D| or |S|), that instance will not exist (there will be |Datatype| and |Selector| instances, respectively). You can find a generic show using GHC.Generics here: http://hackage.haskell.org/package/generic-deriving-1.6.2/docs/src/Generics-Deriving-Show.html > >> -- | Sums: encode choice between constructors >> instance (GToonbaar a, GToonbaar b) => GToonbaar (a :+: b) where >> gtoon x = gtoon x >> > This will cause your code to loop, btw. > >> When I try to compile the above, ghc emits the following error: > > No instance for (Constructor Main.D1MyData) > arising from a use of `Main.$gdmtoon' > Possible fix: > add an instance declaration for (Constructor Main.D1MyData) > In the expression: (Main.$gdmtoon) > In an equation for `toon': toon = (Main.$gdmtoon) > In the instance declaration for `Toonbaar MyData' > It's not the most beautiful of errors, but it does say that there is no |Constructor| instance for |D1MyData|, and |D1MyData| is the automatically generated datatype to encode the *datatype* meta-information for |MyData|. Hope that helps, Pedro -------------- next part -------------- An HTML attachment was scrubbed... URL: From doug at cs.dartmouth.edu Tue Dec 10 16:45:11 2013 From: doug at cs.dartmouth.edu (Doug McIlroy) Date: Tue, 10 Dec 2013 11:45:11 -0500 Subject: [Haskell-cafe] f^n for functional iteration Message-ID: <201312101645.rBAGjBD0006363@stowe.cs.dartmouth.edu> Is there a trick whereby the customary notation f^n for iterated functional composition ((\n f -> foldl (.) id (replicate n f)) n f) can be defined in Haskell? Doug McIlroy From danny.gratzer at gmail.com Tue Dec 10 16:51:51 2013 From: danny.gratzer at gmail.com (Danny Gratzer) Date: Tue, 10 Dec 2013 10:51:51 -0600 Subject: [Haskell-cafe] f^n for functional iteration In-Reply-To: <201312101645.rBAGjBD0006363@stowe.cs.dartmouth.edu> References: <201312101645.rBAGjBD0006363@stowe.cs.dartmouth.edu> Message-ID: Well (^) is already used for their traditional meaning and using this exact operator would require 1. Shadowing (^) from prelude 2. Making (a -> a) an instance of Num (impossible to do sanely) You can just use a different operator f .^. n = foldl (.) id $ replicate n f main = print . (+1) .^. 5 $ 1 Will print 6 Cheers, Danny Gratzer On Tue, Dec 10, 2013 at 10:45 AM, Doug McIlroy wrote: > Is there a trick whereby the customary notation f^n for iterated > functional composition ((\n f -> foldl (.) id (replicate n f)) n f) can > be defined in Haskell? > > Doug McIlroy > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From rustompmody at gmail.com Tue Dec 10 17:00:04 2013 From: rustompmody at gmail.com (Rustom Mody) Date: Tue, 10 Dec 2013 22:30:04 +0530 Subject: [Haskell-cafe] finding "good work" in CS In-Reply-To: References: Message-ID: On Sun, Dec 8, 2013 at 5:24 AM, Dennis Raddle wrote: > It's me again, guy aged 45 thinking about doing graduate work in CS. > > > Is there an area with CS academia that is more about elegance, less about > hacking up prototypes? The study of languages? > > http://alexandria.tue.nl/extra3/proefschrift/PRF6A/8811641.pdf about beauty in mathematical proofs [And in case you wonder what that has to do with CS -- the guide was E W Dijkstra] -------------- next part -------------- An HTML attachment was scrubbed... URL: From temporalabstraction at gmail.com Tue Dec 10 17:24:32 2013 From: temporalabstraction at gmail.com (EatsKittens) Date: Tue, 10 Dec 2013 18:24:32 +0100 Subject: [Haskell-cafe] XEventPtr in Xlib? Message-ID: Hmm, I think I now know how to work with XEventPtr's with allocaXEvent event, what I have now is this: raiseWin :: Win -> IO (); raiseWin w = let { d = disp w; r = root w; xID = xid w; } in do { ctime <- Monad.liftM (\(Time.TOD t _) -> fromIntegral t) Time.getClockTime; atom <- Xlib.Atom.internAtom d "_NET_ACTIVE_WINDOW" True; Xlib.Event.allocaXEvent $ \ePtr -> do { Xlib.Extras.setEventType ePtr XTypes.clientMessage; Xlib.Extras.setClientMessageEvent ePtr xID atom 32 2 ctime; Xlib.Event.sendEvent d r False (Xlib.substructureNotifyMask .|. Xlib.substructureRedirectMask) ePtr; }; }; where root in the Win record is derived from: (root, parent, _) <- Xlib.Extras.queryTree d xid; The code compiles and type checks, it just doesn't... work, it does nothing. Replacing the code with: raiseWin w = System.Process.rawSystem "xdotool" ["windowactivate", show x] >> return () where { x = xid w; } Makes it work without errors, inspecting the code of xdotool makes it reveal to use the "_NET_ACTIVE_WINDOW" client message to the root hole? Any idea what I could be doing wrongly, is this the correct root window? On 10 December 2013 06:22, Brandon Allbery wrote: > On Mon, Dec 9, 2013 at 10:57 PM, EatsKittens < > temporalabstraction at gmail.com> wrote: > >> Xlib.Event seems to define the interestingly recursive type data XEvent = >> XEvent (Ptr XEvent) and otherwise give no information about that type. >> > > Anything on the far side of a Ptr is defined by C and accessed via the > FFI. In this case, you're looking for the XEvent structure defined by the C > Xlib and described in X11/X.h (constants) and X11/Xlib.h (structs; note > that there is a separate struct for each event type although they all have > a common preamble). > > You may be better served by the event definitions in > http://xmonad.org/xmonad-docs/X11/Graphics-X11-Xlib-Extras.html which is > a Haskell, instead of FFI, interface. (I pointed to the xmonad copy of the > docs because that's what I already have loaded in a tab, but it's part of > the same X11 binding as Graphics.X11.Xlib.Event.) > > I need this type to send an XEvent message to a window, is this a mistake >> or am I overlooking something in how to use it, or is the idea that the >> only way to make XEvent data is to make it in C and import it from there? >> > > allocaXEvent is defined in Graphics.X11.Xlib.Event, but you need to refer > to the C Xlib definitions and use FFI marshaling to work with it (and may > need to know C type sizes and how the C compiler packs structs on your > system). There's some code in xmonad-contrib which uses that interface to > send custom events. > > -- > brandon s allbery kf8nh sine nomine > associates > allbery.b at gmail.com > ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad > http://sinenomine.net > -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Tue Dec 10 18:03:15 2013 From: allbery.b at gmail.com (Brandon Allbery) Date: Tue, 10 Dec 2013 13:03:15 -0500 Subject: [Haskell-cafe] XEventPtr in Xlib? In-Reply-To: References: Message-ID: On Tue, Dec 10, 2013 at 12:24 PM, EatsKittens wrote: > where root in the Win record is derived from: > > (root, parent, _) > <- Xlib.Extras.queryTree d xid; > That looks like it should be the right one, but normally I'd just get the root window of the default Screen. For what it's worth, I see one issue: setClientMessageEvent does only the basic information necessary for a client message, which is insufficient for the _NET_ACTIVE_WINDOW message. (It's missing the client active window, which in this case should probably be 0 anyway so it may not be an issue that it's missing.) > The code compiles and type checks, it just doesn't... work, it does > nothing. Replacing the code with: > > raiseWin w = > System.Process.rawSystem "xdotool" ["windowactivate", show x] >> > return () where { > x = xid w; > } > > Makes it work without errors, inspecting the code of xdotool makes it > reveal to use the "_NET_ACTIVE_WINDOW" client message to the root hole? Any > idea what I could be doing wrongly, is this the correct root window? > You might use something like xtrace/xscope/xmon to make sure that xdotool and your program are actually sending the same client message. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From jeffersoncarpenter2 at gmail.com Tue Dec 10 21:44:24 2013 From: jeffersoncarpenter2 at gmail.com (Jefferson Carpenter) Date: Tue, 10 Dec 2013 15:44:24 -0600 Subject: [Haskell-cafe] finding "good work" in CS In-Reply-To: References: Message-ID: On Sat, Dec 7, 2013 at 5:54 PM, Dennis Raddle wrote: > Turns out that academic code can be very poor indeed, sometimes just a > hacked prototype meant to demonstrate an idea to get it published. > In that case, it can be helpful to use the right license: http://matt.might.net/articles/crapl/CRAPL-LICENSE.txt -------------- next part -------------- An HTML attachment was scrubbed... URL: From temporalabstraction at gmail.com Tue Dec 10 23:32:36 2013 From: temporalabstraction at gmail.com (EatsKittens) Date: Wed, 11 Dec 2013 00:32:36 +0100 Subject: [Haskell-cafe] XEventPtr in Xlib? In-Reply-To: References: Message-ID: xtrace revealed to me that Haskell Xlib was not even sending the event. After some further inspection of XMonad code they apparently call Xlib.Event.Sync d False a lot at. I'm not entirely sure why Haskell needs it as the Xlib pages say it shouldn't be needed but it works when calling it. xdotool does not seem to use it in it's C code. Is there any reason why Haskell's Xlib needs it? On 10 December 2013 19:03, Brandon Allbery wrote: > On Tue, Dec 10, 2013 at 12:24 PM, EatsKittens < > temporalabstraction at gmail.com> wrote: > >> where root in the Win record is derived from: >> >> (root, parent, _) >> <- Xlib.Extras.queryTree d xid; >> > > That looks like it should be the right one, but normally I'd just get the > root window of the default Screen. > > For what it's worth, I see one issue: setClientMessageEvent does only the > basic information necessary for a client message, which is insufficient for > the _NET_ACTIVE_WINDOW message. (It's missing the client active window, > which in this case should probably be 0 anyway so it may not be an issue > that it's missing.) > > >> The code compiles and type checks, it just doesn't... work, it does >> nothing. Replacing the code with: >> >> raiseWin w = >> System.Process.rawSystem "xdotool" ["windowactivate", show x] >> >> return () where { >> x = xid w; >> } >> >> Makes it work without errors, inspecting the code of xdotool makes it >> reveal to use the "_NET_ACTIVE_WINDOW" client message to the root hole? Any >> idea what I could be doing wrongly, is this the correct root window? >> > > You might use something like xtrace/xscope/xmon to make sure that xdotool > and your program are actually sending the same client message. > > -- > brandon s allbery kf8nh sine nomine > associates > allbery.b at gmail.com > ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad > http://sinenomine.net > -------------- next part -------------- An HTML attachment was scrubbed... URL: From roma at ro-che.info Wed Dec 11 00:00:14 2013 From: roma at ro-che.info (Roman Cheplyaka) Date: Wed, 11 Dec 2013 02:00:14 +0200 Subject: [Haskell-cafe] ANN: tasty-0.5 Message-ID: <20131211000014.GA27454@sniper> The new version of Tasty, a modern and extensible testing framework for Haskell, is out. The major new feature in this release is resources, described in detail in the article http://ro-che.info/articles/2013-12-10-tasty-resources.html Although I haven't posted here since the very first release of tasty, there have been many small improvements and some new big features, such as resources and ingredients. The core Tasty packages are now part of Stackage, which means that you can use them in FP Haskell Center? and School of Haskell. It's also great to see third-party packages appearing, which was the main motivation behind Tasty's extensible design: http://hackage.haskell.org/package/tasty-th, by Benno F?nfst?ck http://hackage.haskell.org/package/tasty-hspec, by Mitchell Rosen http://hackage.haskell.org/package/tasty-ant-xml, by Oliver Charles To learn more about Tasty, please see: http://documentup.com/feuerbach/tasty ? the README http://hackage.haskell.org/package/tasty-0.5.1/docs/Test-Tasty.html ? the haddock documentation https://github.com/feuerbach/tasty/blob/master/CHANGES.md ? the changelog http://ocharles.org.uk/blog/posts/2013-12-03-24-days-of-hackage-tasty.html ? this year's ?24 days of Hackage? article about Tasty Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: Digital signature URL: From miguelimo38 at yandex.ru Wed Dec 11 05:03:46 2013 From: miguelimo38 at yandex.ru (MigMit) Date: Wed, 11 Dec 2013 09:03:46 +0400 Subject: [Haskell-cafe] SENIOR HASKELL OPPORTUNITY In-Reply-To: <2252CC638F64CD4FBB38CD13A85C6D8801C82C71@GYRO.henlow.local> References: <2252CC638F64CD4FBB38CD13A85C6D8801C82C71@GYRO.henlow.local> Message-ID: <05E70037-A4F5-44DD-819D-EA5F3C137AAA@yandex.ru> Wait a sec, is that yours: http://www.haskellers.com/jobs/59 ? I loved the required skill "Object oriented programming experience in Haskell". On 10 Dec 2013, at 18:58, Neena Singh wrote: > Hello, > > I have been retained by a leading Hedge Fund who are looking for an experienced Haskell developer to join their highly regarded front office technology team. This is a great opportunity for a passionate technologist to join a group working very closely with the trading floor on advanced Haskell projects. Previous finance experience is not a pre-requisite however a passion for Haskell is a must. > > If you are interested learning more about this opportunity and potential salary ranges please call me on 020 7871 4482 or email me Neena.singh at henlowgroup.com. > > I look forward to hearing from you, > > Regards, > > Neena From cgaebel at uwaterloo.ca Wed Dec 11 05:09:37 2013 From: cgaebel at uwaterloo.ca (Clark Gaebel) Date: Wed, 11 Dec 2013 00:09:37 -0500 Subject: [Haskell-cafe] SENIOR HASKELL OPPORTUNITY In-Reply-To: <05E70037-A4F5-44DD-819D-EA5F3C137AAA@yandex.ru> References: <2252CC638F64CD4FBB38CD13A85C6D8801C82C71@GYRO.henlow.local> <05E70037-A4F5-44DD-819D-EA5F3C137AAA@yandex.ru> Message-ID: Well how else would you expect to earn that "business bonus"? On Wed, Dec 11, 2013 at 12:03 AM, MigMit wrote: > Wait a sec, is that yours: http://www.haskellers.com/jobs/59 ? > > I loved the required skill "Object oriented programming experience in > Haskell". > > On 10 Dec 2013, at 18:58, Neena Singh wrote: > > > Hello, > > > > I have been retained by a leading Hedge Fund who are looking for an > experienced Haskell developer to join their highly regarded front office > technology team. This is a great opportunity for a passionate technologist > to join a group working very closely with the trading floor on advanced > Haskell projects. Previous finance experience is not a pre-requisite > however a passion for Haskell is a must. > > > > If you are interested learning more about this opportunity and potential > salary ranges please call me on 020 7871 4482 or email me > Neena.singh at henlowgroup.com. > > > > I look forward to hearing from you, > > > > Regards, > > > > Neena > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Clark. Key ID : 0x78099922 Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 -------------- next part -------------- An HTML attachment was scrubbed... URL: From carlo at carlo-hamalainen.net Wed Dec 11 07:48:16 2013 From: carlo at carlo-hamalainen.net (Carlo Hamalainen) Date: Wed, 11 Dec 2013 08:48:16 +0100 Subject: [Haskell-cafe] Does anyone use ghc-mod with Yesod? In-Reply-To: References: <52A6CAB3.3020406@carlo-hamalainen.net> Message-ID: <52A818C0.3060404@carlo-hamalainen.net> On 11/12/13 01:36, Curtis Carter wrote: > I believe you just need to install that lib. It's not in the main > dependencies but in the test ones. That did the trick. I thought that yesod-test would be installed automatically when I ran cabal install in the Yesod project directory. I can confirm that ghc-mod works fine on a Yesod project via ghcmod-vim. Thanks, -- Carlo Hamalainen http://carlo-hamalainen.net From rhymoid at gmail.com Wed Dec 11 09:06:26 2013 From: rhymoid at gmail.com (Stijn van Drongelen) Date: Wed, 11 Dec 2013 10:06:26 +0100 Subject: [Haskell-cafe] SENIOR HASKELL OPPORTUNITY In-Reply-To: References: <2252CC638F64CD4FBB38CD13A85C6D8801C82C71@GYRO.henlow.local> <05E70037-A4F5-44DD-819D-EA5F3C137AAA@yandex.ru> Message-ID: "Maths skills are not essential [...]." "EXPERIENCE REQUIRED: [...] * - PHD / High Level degree in Computer Science." Huh. On Wed, Dec 11, 2013 at 6:09 AM, Clark Gaebel wrote: > Well how else would you expect to earn that "business bonus"? > > > On Wed, Dec 11, 2013 at 12:03 AM, MigMit wrote: > >> Wait a sec, is that yours: http://www.haskellers.com/jobs/59 ? >> >> I loved the required skill "Object oriented programming experience in >> Haskell". >> >> On 10 Dec 2013, at 18:58, Neena Singh >> wrote: >> >> > Hello, >> > >> > I have been retained by a leading Hedge Fund who are looking for an >> experienced Haskell developer to join their highly regarded front office >> technology team. This is a great opportunity for a passionate technologist >> to join a group working very closely with the trading floor on advanced >> Haskell projects. Previous finance experience is not a pre-requisite >> however a passion for Haskell is a must. >> > >> > If you are interested learning more about this opportunity and >> potential salary ranges please call me on 020 7871 4482 or email me >> Neena.singh at henlowgroup.com. >> > >> > I look forward to hearing from you, >> > >> > Regards, >> > >> > Neena >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > > > -- > Clark. > > Key ID : 0x78099922 > Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From noteed at gmail.com Wed Dec 11 09:15:45 2013 From: noteed at gmail.com (Vo Minh Thu) Date: Wed, 11 Dec 2013 10:15:45 +0100 Subject: [Haskell-cafe] SENIOR HASKELL OPPORTUNITY In-Reply-To: References: <2252CC638F64CD4FBB38CD13A85C6D8801C82C71@GYRO.henlow.local> <05E70037-A4F5-44DD-819D-EA5F3C137AAA@yandex.ru> Message-ID: HR people are not technical people, there is no point reading too meticulously their copy (perfectly good companies have crappy job postings all the time). All job postings will tell you they have bright people on board, they have nice salary package, and so on. So there is no added information when they tell you that, but they sure will repeat it everywhere they can. 2013/12/11 Stijn van Drongelen : > "Maths skills are not essential [...]." > > "EXPERIENCE REQUIRED: > [...] > * - PHD / High Level degree in Computer Science." > > Huh. > > > On Wed, Dec 11, 2013 at 6:09 AM, Clark Gaebel wrote: >> >> Well how else would you expect to earn that "business bonus"? >> >> >> On Wed, Dec 11, 2013 at 12:03 AM, MigMit wrote: >>> >>> Wait a sec, is that yours: http://www.haskellers.com/jobs/59 ? >>> >>> I loved the required skill "Object oriented programming experience in >>> Haskell". >>> >>> On 10 Dec 2013, at 18:58, Neena Singh >>> wrote: >>> >>> > Hello, >>> > >>> > I have been retained by a leading Hedge Fund who are looking for an >>> > experienced Haskell developer to join their highly regarded front office >>> > technology team. This is a great opportunity for a passionate technologist >>> > to join a group working very closely with the trading floor on advanced >>> > Haskell projects. Previous finance experience is not a pre-requisite however >>> > a passion for Haskell is a must. >>> > >>> > If you are interested learning more about this opportunity and >>> > potential salary ranges please call me on 020 7871 4482 or email me >>> > Neena.singh at henlowgroup.com. >>> > >>> > I look forward to hearing from you, >>> > >>> > Regards, >>> > >>> > Neena >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> >> >> >> -- >> Clark. >> >> Key ID : 0x78099922 >> Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From Neena.Singh at henlowgroup.com Wed Dec 11 09:34:02 2013 From: Neena.Singh at henlowgroup.com (Neena Singh) Date: Wed, 11 Dec 2013 09:34:02 +0000 Subject: [Haskell-cafe] SENIOR HASKELL OPPORTUNITY In-Reply-To: References: <2252CC638F64CD4FBB38CD13A85C6D8801C82C71@GYRO.henlow.local> <05E70037-A4F5-44DD-819D-EA5F3C137AAA@yandex.ru> Message-ID: <2252CC638F64CD4FBB38CD13A85C6D8801C82FEE@GYRO.henlow.local> Yes, this is correct. A number of (quant) developers have a PhD or Masters in Computer Science but have not used their maths skills extensively for many years. When hiring for a (quant) developer many financial organisations will look for strong maths skills and will therefore ask many probability and other mathematical questions as part of the interview process which many developers find difficult and is often the reason they are not successful in the interview process. For this particular opportunity they are looking for someone with a PhD or High Level degree but will not be extensively testing a candidate's mathematical ability. This opportunity is therefore an option for someone who is technically very strong but has not used their more advanced maths skills for many years. Thanks Neena From: Haskell-Cafe [mailto:haskell-cafe-bounces at haskell.org] On Behalf Of Stijn van Drongelen Sent: 11 December 2013 09:06 To: Clark Gaebel Cc: haskell-cafe at haskell.org; MigMit Subject: Re: [Haskell-cafe] SENIOR HASKELL OPPORTUNITY "Maths skills are not essential [...]." "EXPERIENCE REQUIRED: [...] * - PHD / High Level degree in Computer Science." Huh. On Wed, Dec 11, 2013 at 6:09 AM, Clark Gaebel > wrote: Well how else would you expect to earn that "business bonus"? On Wed, Dec 11, 2013 at 12:03 AM, MigMit > wrote: Wait a sec, is that yours: http://www.haskellers.com/jobs/59 ? I loved the required skill "Object oriented programming experience in Haskell". On 10 Dec 2013, at 18:58, Neena Singh > wrote: > Hello, > > I have been retained by a leading Hedge Fund who are looking for an experienced Haskell developer to join their highly regarded front office technology team. This is a great opportunity for a passionate technologist to join a group working very closely with the trading floor on advanced Haskell projects. Previous finance experience is not a pre-requisite however a passion for Haskell is a must. > > If you are interested learning more about this opportunity and potential salary ranges please call me on 020 7871 4482 or email me Neena.singh at henlowgroup.com. > > I look forward to hearing from you, > > Regards, > > Neena _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe at haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe -- Clark. Key ID : 0x78099922 Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe at haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- An HTML attachment was scrubbed... URL: From krismicinski at gmail.com Wed Dec 11 20:52:27 2013 From: krismicinski at gmail.com (Kristopher Micinski) Date: Wed, 11 Dec 2013 15:52:27 -0500 Subject: [Haskell-cafe] SENIOR HASKELL OPPORTUNITY In-Reply-To: <2252CC638F64CD4FBB38CD13A85C6D8801C82FEE@GYRO.henlow.local> References: <2252CC638F64CD4FBB38CD13A85C6D8801C82C71@GYRO.henlow.local> <05E70037-A4F5-44DD-819D-EA5F3C137AAA@yandex.ru> <2252CC638F64CD4FBB38CD13A85C6D8801C82FEE@GYRO.henlow.local> Message-ID: I think the point is that people who have PhDs in CS have very strong math skills, but that the definition of "math" may differ from person to person. If your definition of math is "really hard integrals" then maybe not, but almost everyone with a PhD in CS is very good at some form of advanced math :-).. Kris On Wed, Dec 11, 2013 at 4:34 AM, Neena Singh wrote: > Yes, this is correct. > > > > A number of (quant) developers have a PhD or Masters in Computer Science but > have not used their maths skills extensively for many years. > > > > When hiring for a (quant) developer many financial organisations will look > for strong maths skills and will therefore ask many probability and other > mathematical questions as part of the interview process which many > developers find difficult and is often the reason they are not successful in > the interview process. > > > > For this particular opportunity they are looking for someone with a PhD or > High Level degree but will not be extensively testing a candidate?s > mathematical ability. This opportunity is therefore an option for someone > who is technically very strong but has not used their more advanced maths > skills for many years. > > > > Thanks > > > > Neena > > > > From: Haskell-Cafe [mailto:haskell-cafe-bounces at haskell.org] On Behalf Of > Stijn van Drongelen > Sent: 11 December 2013 09:06 > To: Clark Gaebel > Cc: haskell-cafe at haskell.org; MigMit > Subject: Re: [Haskell-cafe] SENIOR HASKELL OPPORTUNITY > > > > "Maths skills are not essential [...]." > > "EXPERIENCE REQUIRED: > [...] > * - PHD / High Level degree in Computer Science." > > Huh. > > > > On Wed, Dec 11, 2013 at 6:09 AM, Clark Gaebel wrote: > > Well how else would you expect to earn that "business bonus"? > > > > On Wed, Dec 11, 2013 at 12:03 AM, MigMit wrote: > > Wait a sec, is that yours: http://www.haskellers.com/jobs/59 ? > > I loved the required skill "Object oriented programming experience in > Haskell". > > > On 10 Dec 2013, at 18:58, Neena Singh wrote: > >> Hello, >> >> I have been retained by a leading Hedge Fund who are looking for an >> experienced Haskell developer to join their highly regarded front office >> technology team. This is a great opportunity for a passionate technologist >> to join a group working very closely with the trading floor on advanced >> Haskell projects. Previous finance experience is not a pre-requisite however >> a passion for Haskell is a must. >> >> If you are interested learning more about this opportunity and potential >> salary ranges please call me on 020 7871 4482 or email me >> Neena.singh at henlowgroup.com. >> >> I look forward to hearing from you, >> >> Regards, >> >> Neena > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > -- > > Clark. > > Key ID : 0x78099922 > Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From ky3 at atamo.com Wed Dec 11 21:05:41 2013 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Thu, 12 Dec 2013 04:05:41 +0700 Subject: [Haskell-cafe] finding "good work" in CS In-Reply-To: References: Message-ID: On Sun, Dec 8, 2013 at 6:54 AM, Dennis Raddle wrote: > So what do I want to do for my life's work, once I can overcome this > illness and get back to work full-time? > > I hope I can work with beauty in some form. > Beauty is very much in the eye of the beholder. Have you looked at "Land the Tech Job You Love" by the Pragmatic label? Chapter 1 might be free and well worth the read, approx 10 pages. Something that strikes me about your emails is that you're focused on your wants and needs. Which is important. But a job is ultimately a trade: you give up X in return for Y. Grad school these days is no different; admissions DO actively look for that X, even if that X is different from that of a commercial setting. Think about what those X's might be -- as in, what does the other party want. Feel free to continue the convo on this list! -- Kim-Ee -------------- next part -------------- An HTML attachment was scrubbed... URL: From fritsch at joerg.cc Wed Dec 11 21:37:55 2013 From: fritsch at joerg.cc (Joerg Fritsch) Date: Wed, 11 Dec 2013 22:37:55 +0100 Subject: [Haskell-cafe] striping non-alphanumericals Message-ID: <005a01cef6b9$4114d4f0$c33e7ed0$@joerg.cc> I have the following code snippet: import System.IO import Data.String.Utils main = withFile "test.txt" ReadMode $ \handle -> do xs <- getwords handle sequence_ $ map putStrLn (escapeRe xs) getwords :: Handle -> IO [String] getwords h = hGetContents h >>= return . words What I want to to there is to get i.e. "word," or "word!" etc. and arrive at "word". I understand that escapeRe may do this. However, I always get some sort of mismatch errors like this: test.hs:6:38: Couldn't match type `Char' with `[Char]' Expected type: [String] Actual type: String In the return type of a call of `escapeRe' In the second argument of `map', namely `(escapeRe xs)' In the second argument of `($)', namely `map putStrLn (escapeRe xs)' test.hs:6:47: Couldn't match type `[Char]' with `Char' Expected type: String Actual type: [String] In the first argument of `escapeRe', namely `xs' In the second argument of `map', namely `(escapeRe xs)' In the second argument of `($)', namely `map putStrLn (escapeRe xs)' Now I have three questions: 1. Is escapeRe the right function to use here? 2. What do I do wrong? 3. I read in the Real World Haskell book that actually all these file/string operations are very very slow. The recommendation is to work with bytestrings instead. Is there any (fast) way to strip non-alphanumericals from bytestrings? Thanks, --Joerg -------------- next part -------------- An HTML attachment was scrubbed... URL: From bob at redivi.com Wed Dec 11 22:01:41 2013 From: bob at redivi.com (Bob Ippolito) Date: Wed, 11 Dec 2013 14:01:41 -0800 Subject: [Haskell-cafe] striping non-alphanumericals In-Reply-To: <005a01cef6b9$4114d4f0$c33e7ed0$@joerg.cc> References: <005a01cef6b9$4114d4f0$c33e7ed0$@joerg.cc> Message-ID: On Wed, Dec 11, 2013 at 1:37 PM, Joerg Fritsch wrote: > I have the following code snippet: > > import System.IO > > import Data.String.Utils > > main = withFile "test.txt" ReadMode $ \handle -> do > > xs <- getwords handle > > sequence_ $ map putStrLn (escapeRe xs) > > getwords :: Handle -> IO [String] > > getwords h = hGetContents h >>= return . words > > > > What I want to to there is to get i.e. ?word,? or ?word!? etc. and arrive > at ?word?. I understand that escapeRe may do this. However, I always get > some sort of mismatch errors like this: > > > > test.hs:6:38: > > Couldn't match type `Char' with `[Char]' > > Expected type: [String] > > Actual type: String > > In the return type of a call of `escapeRe' > > In the second argument of `map', namely `(escapeRe xs)' > > In the second argument of `($)', namely > > `map putStrLn (escapeRe xs)' > > test.hs:6:47: > > Couldn't match type `[Char]' with `Char' > > Expected type: String > > Actual type: [String] > > In the first argument of `escapeRe', namely `xs' > > In the second argument of `map', namely `(escapeRe xs)' > > In the second argument of `($)', namely > > `map putStrLn (escapeRe xs)' > > Now I have three questions: > > 1. Is escapeRe the right function to use here? > `escapeRe` is not the correct function to use. That is the function you would use if you were trying to create a regular expression to match the given input, but this is not at all what you are doing. > 2. What do I do wrong? > Well, the type is wrong because you did `sequence_ $ map putStrLn (escapeRe xs)` instead of `sequence_ $ map (putStrLn . escapeRe) xs`. Note that `sequence_ $ map f xs` can be written as `mapM_ f xs` which is much shorter and more clear. This is what I would write: mapM_ (putStrLn . escapeRe) xs That said, `escapeRe` is not at all useful for what you are trying to do. You should probably use `filter` and `isAlphaNum` from Data.Char. 3. I read in the Real World Haskell book that actually all these > file/string operations are very very slow. The recommendation is to work > with bytestrings instead. Is there any (fast) way to strip > non-alphanumericals from bytestrings? > This is true. You should use Text or ByteString for performance. Text is probably more appropriate for your use case. You can efficiently solve this exercise with functionality from Data.Char, Data.Text, and Data.Text.IO. Note that this sort of question might be more appropriate for haskell-beginners: http://www.haskell.org/mailman/listinfo/beginners -bob -------------- next part -------------- An HTML attachment was scrubbed... URL: From malcolm.wallace at me.com Wed Dec 11 22:02:02 2013 From: malcolm.wallace at me.com (Malcolm Wallace) Date: Wed, 11 Dec 2013 22:02:02 +0000 Subject: [Haskell-cafe] SENIOR HASKELL OPPORTUNITY In-Reply-To: References: <2252CC638F64CD4FBB38CD13A85C6D8801C82C71@GYRO.henlow.local> <05E70037-A4F5-44DD-819D-EA5F3C137AAA@yandex.ru> <2252CC638F64CD4FBB38CD13A85C6D8801C82FEE@GYRO.henlow.local> Message-ID: <45DC9340-78FC-432C-98C5-10914BF5F0A2@me.com> Typically, finance jobs that ask for mathematical skill, really do mean hard integrals, partial differential equations, and other numerical stuff that most CS people quail at. > On 11 Dec 2013, at 20:52, Kristopher Micinski wrote: > > I think the point is that people who have PhDs in CS have very strong > math skills, but that the definition of "math" may differ from person > to person. If your definition of math is "really hard integrals" then > maybe not, but almost everyone with a PhD in CS is very good at some > form of advanced math :-).. > > Kris > > > On Wed, Dec 11, 2013 at 4:34 AM, Neena Singh > wrote: >> Yes, this is correct. >> >> >> >> A number of (quant) developers have a PhD or Masters in Computer Science but >> have not used their maths skills extensively for many years. >> >> >> >> When hiring for a (quant) developer many financial organisations will look >> for strong maths skills and will therefore ask many probability and other >> mathematical questions as part of the interview process which many >> developers find difficult and is often the reason they are not successful in >> the interview process. >> >> >> >> For this particular opportunity they are looking for someone with a PhD or >> High Level degree but will not be extensively testing a candidate?s >> mathematical ability. This opportunity is therefore an option for someone >> who is technically very strong but has not used their more advanced maths >> skills for many years. >> >> >> >> Thanks >> >> >> >> Neena >> >> >> >> From: Haskell-Cafe [mailto:haskell-cafe-bounces at haskell.org] On Behalf Of >> Stijn van Drongelen >> Sent: 11 December 2013 09:06 >> To: Clark Gaebel >> Cc: haskell-cafe at haskell.org; MigMit >> Subject: Re: [Haskell-cafe] SENIOR HASKELL OPPORTUNITY >> >> >> >> "Maths skills are not essential [...]." >> >> "EXPERIENCE REQUIRED: >> [...] >> * - PHD / High Level degree in Computer Science." >> >> Huh. >> >> >> >> On Wed, Dec 11, 2013 at 6:09 AM, Clark Gaebel wrote: >> >> Well how else would you expect to earn that "business bonus"? >> >> >> >> On Wed, Dec 11, 2013 at 12:03 AM, MigMit wrote: >> >> Wait a sec, is that yours: http://www.haskellers.com/jobs/59 ? >> >> I loved the required skill "Object oriented programming experience in >> Haskell". >> >> >>> On 10 Dec 2013, at 18:58, Neena Singh wrote: >>> >>> Hello, >>> >>> I have been retained by a leading Hedge Fund who are looking for an >>> experienced Haskell developer to join their highly regarded front office >>> technology team. This is a great opportunity for a passionate technologist >>> to join a group working very closely with the trading floor on advanced >>> Haskell projects. Previous finance experience is not a pre-requisite however >>> a passion for Haskell is a must. >>> >>> If you are interested learning more about this opportunity and potential >>> salary ranges please call me on 020 7871 4482 or email me >>> Neena.singh at henlowgroup.com. >>> >>> I look forward to hearing from you, >>> >>> Regards, >>> >>> Neena >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> >> >> -- >> >> Clark. >> >> Key ID : 0x78099922 >> Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From carter.schonwald at gmail.com Wed Dec 11 22:51:31 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Wed, 11 Dec 2013 17:51:31 -0500 Subject: [Haskell-cafe] SENIOR HASKELL OPPORTUNITY In-Reply-To: <45DC9340-78FC-432C-98C5-10914BF5F0A2@me.com> References: <2252CC638F64CD4FBB38CD13A85C6D8801C82C71@GYRO.henlow.local> <05E70037-A4F5-44DD-819D-EA5F3C137AAA@yandex.ru> <2252CC638F64CD4FBB38CD13A85C6D8801C82FEE@GYRO.henlow.local> <45DC9340-78FC-432C-98C5-10914BF5F0A2@me.com> Message-ID: basically, fun stuff! :) On Wed, Dec 11, 2013 at 5:02 PM, Malcolm Wallace wrote: > Typically, finance jobs that ask for mathematical skill, really do mean > hard integrals, partial differential equations, and other numerical stuff > that most CS people quail at. > > > On 11 Dec 2013, at 20:52, Kristopher Micinski > wrote: > > > > I think the point is that people who have PhDs in CS have very strong > > math skills, but that the definition of "math" may differ from person > > to person. If your definition of math is "really hard integrals" then > > maybe not, but almost everyone with a PhD in CS is very good at some > > form of advanced math :-).. > > > > Kris > > > > > > On Wed, Dec 11, 2013 at 4:34 AM, Neena Singh > > wrote: > >> Yes, this is correct. > >> > >> > >> > >> A number of (quant) developers have a PhD or Masters in Computer > Science but > >> have not used their maths skills extensively for many years. > >> > >> > >> > >> When hiring for a (quant) developer many financial organisations will > look > >> for strong maths skills and will therefore ask many probability and > other > >> mathematical questions as part of the interview process which many > >> developers find difficult and is often the reason they are not > successful in > >> the interview process. > >> > >> > >> > >> For this particular opportunity they are looking for someone with a PhD > or > >> High Level degree but will not be extensively testing a candidate?s > >> mathematical ability. This opportunity is therefore an option for > someone > >> who is technically very strong but has not used their more advanced > maths > >> skills for many years. > >> > >> > >> > >> Thanks > >> > >> > >> > >> Neena > >> > >> > >> > >> From: Haskell-Cafe [mailto:haskell-cafe-bounces at haskell.org] On Behalf > Of > >> Stijn van Drongelen > >> Sent: 11 December 2013 09:06 > >> To: Clark Gaebel > >> Cc: haskell-cafe at haskell.org; MigMit > >> Subject: Re: [Haskell-cafe] SENIOR HASKELL OPPORTUNITY > >> > >> > >> > >> "Maths skills are not essential [...]." > >> > >> "EXPERIENCE REQUIRED: > >> [...] > >> * - PHD / High Level degree in Computer Science." > >> > >> Huh. > >> > >> > >> > >> On Wed, Dec 11, 2013 at 6:09 AM, Clark Gaebel > wrote: > >> > >> Well how else would you expect to earn that "business bonus"? > >> > >> > >> > >> On Wed, Dec 11, 2013 at 12:03 AM, MigMit wrote: > >> > >> Wait a sec, is that yours: http://www.haskellers.com/jobs/59 ? > >> > >> I loved the required skill "Object oriented programming experience in > >> Haskell". > >> > >> > >>> On 10 Dec 2013, at 18:58, Neena Singh > wrote: > >>> > >>> Hello, > >>> > >>> I have been retained by a leading Hedge Fund who are looking for an > >>> experienced Haskell developer to join their highly regarded front > office > >>> technology team. This is a great opportunity for a passionate > technologist > >>> to join a group working very closely with the trading floor on advanced > >>> Haskell projects. Previous finance experience is not a pre-requisite > however > >>> a passion for Haskell is a must. > >>> > >>> If you are interested learning more about this opportunity and > potential > >>> salary ranges please call me on 020 7871 4482 or email me > >>> Neena.singh at henlowgroup.com. > >>> > >>> I look forward to hearing from you, > >>> > >>> Regards, > >>> > >>> Neena > >> > >> _______________________________________________ > >> Haskell-Cafe mailing list > >> Haskell-Cafe at haskell.org > >> http://www.haskell.org/mailman/listinfo/haskell-cafe > >> > >> > >> > >> -- > >> > >> Clark. > >> > >> Key ID : 0x78099922 > >> Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 > >> > >> > >> _______________________________________________ > >> Haskell-Cafe mailing list > >> Haskell-Cafe at haskell.org > >> http://www.haskell.org/mailman/listinfo/haskell-cafe > >> > >> > >> > >> > >> _______________________________________________ > >> Haskell-Cafe mailing list > >> Haskell-Cafe at haskell.org > >> http://www.haskell.org/mailman/listinfo/haskell-cafe > >> > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ok at cs.otago.ac.nz Wed Dec 11 23:48:31 2013 From: ok at cs.otago.ac.nz (ok at cs.otago.ac.nz) Date: Thu, 12 Dec 2013 12:48:31 +1300 Subject: [Haskell-cafe] striping non-alphanumericals In-Reply-To: <005a01cef6b9$4114d4f0$c33e7ed0$@joerg.cc> References: <005a01cef6b9$4114d4f0$c33e7ed0$@joerg.cc> Message-ID: <9bfcc9dfa975f0fa48e351f8d414b3ac.squirrel@chasm.otago.ac.nz> > What I want to to there is to get i.e. "word," or "word!" etc. and arrive > at > "word". I understand that escapeRe may do this. Why not do it the easy way? import Char(isAlpha) keep_letters = filter isAlphs Then keep_letters "word," = keep_letters "(w)ord" = "word". If you are content to work with Unicode, you get use getLine :: IO ByteString and splitWith :: (Word8 -> Bool) -> ByteString -> [ByteString] with predicate not . isAlpha . chr . fromIntegral and then filter out the empty ByteStrings From doug at cs.dartmouth.edu Thu Dec 12 03:37:43 2013 From: doug at cs.dartmouth.edu (Doug McIlroy) Date: Wed, 11 Dec 2013 22:37:43 -0500 Subject: [Haskell-cafe] f^n for functional iteration Message-ID: <201312120337.rBC3bhWO028627@stowe.cs.dartmouth.edu> Agreeing with the analysis, I will sharpen my question. Is option 2 possible at all, regardless of sanity concerns (e.g. incomplete implementation of Num). Doug > On Tue, 10 Dec 2013 at 10:51 AM, Danny Gratzer wrote > > Well (^) is already used for their traditional meaning and using this exact > operator would require > > 1. Shadowing (^) from prelude > 2. Making (a -> a) an instance of Num (impossible to do sanely) > > You can just use a different operator > > f .^. n = foldl (.) id $ replicate n f > > On Tue, Dec 10, 2013 at 10:45 AM, Doug McIlroy wrote: > > > Is there a trick whereby the customary notation f^n for iterated > > functional composition ((\n f -> foldl (.) id (replicate n f)) n f) can > > be defined in Haskell? > > > > Doug McIlroy From dstcruz at gmail.com Thu Dec 12 03:47:47 2013 From: dstcruz at gmail.com (Daniel Santa Cruz) Date: Wed, 11 Dec 2013 22:47:47 -0500 Subject: [Haskell-cafe] Haskell Weekly News: Issue 287 Message-ID: Welcome to (the "I'm not dead yet") issue 287 of the HWN, an issue covering crowd-sourced bits of information about Haskell from around the web. This issue covers the very long span of time from November 10 to December 07, 2013. Quotes of the Week * chrisdone: monads are like a finger pointing away to the moon. *smack* don't look at the finger or you will miss all that heavenly glory * quchen: A group with an associative law is called a group. * chrisdone: i swim in a sea of parens and it warms me like rays of the sun * zomg: my client tells me weekly how I've saved his company. Then I goto haskell and I'm like "I have no idea what I'm doing lul" * pigworker: The usual style is to write as if everything is inductive, and if it still works on infinite data, to pat ourselves on the back for using Haskell rather than ML. Top Reddit Stories * Honorary Doctorate for Simon Peyton Jones - On December 3 2013 Simon Peyton Jones was honoured by the University of Glasgow with the honorary degree of Doctor of Science. Domain: dcs.gla.ac.uk, Score: 166, Comments: 18 On Reddit: [1] http://goo.gl/XLezZO Original: [2] http://goo.gl/WqC2EN * Hell: A Haskell shell Domain: github.com, Score: 114, Comments: 53 On Reddit: [3] http://goo.gl/6ogD6n Original: [4] http://goo.gl/YCzNT3 * L?b and m?b: strange loops in Haskell Domain: github.com, Score: 95, Comments: 35 On Reddit: [5] http://goo.gl/8bF5Op Original: [6] http://goo.gl/GqzuP0 * Explanation of the new Haskell records extension Domain: well-typed.com, Score: 88, Comments: 70 On Reddit: [7] http://goo.gl/419sYv Original: [8] http://goo.gl/g24kLB * FP Complete IDE now free for community use. Give it a try! Domain: fpcomplete.com, Score: 86, Comments: 65 On Reddit: [9] http://goo.gl/OJh2Oz Original: [10] http://goo.gl/2FYHa * The Haskell Cast #4 - Simon Marlow on Parallelism and Concurrency Domain: haskellcast.com, Score: 82, Comments: 13 On Reddit: [11] http://goo.gl/kzNEz3 Original: [12] http://goo.gl/yrUDXL * 24 Days of Hackage: scotty Domain: ocharles.org.uk, Score: 74, Comments: 16 On Reddit: [13] http://goo.gl/CoUanr Original: [14] http://goo.gl/a83HZg * Idris 0.9.10 released Domain: idris-lang.org, Score: 73, Comments: 21 On Reddit: [15] http://goo.gl/0OnlPV Original: [16] http://goo.gl/MKtbxu * 24 Days of Hackage: threepenny-gui Domain: ocharles.org.uk, Score: 68, Comments: 4 On Reddit: [17] http://goo.gl/vSTpc0 Original: [18] http://goo.gl/Hmjqzq * 24 Days of Hackage: linear Domain: ocharles.org.uk, Score: 66, Comments: 43 On Reddit: [19] http://goo.gl/dcFHGg Original: [20] http://goo.gl/R9c0bh * 24 Days of Hackage: tasty Domain: ocharles.org.uk, Score: 65, Comments: 4 On Reddit: [21] http://goo.gl/xIwvgk Original: [22] http://goo.gl/aUJGLJ * 24 Days of Hackage: 2013 in Review Domain: ocharles.org.uk, Score: 64, Comments: 11 On Reddit: [23] http://goo.gl/ideT63 Original: [24] http://goo.gl/DQYDar * Hacking Haskell in nightclubs (x-post from /r/programming) Domain: vice.com, Score: 60, Comments: 30 On Reddit: [25] http://goo.gl/ezuhIJ Original: [26] http://goo.gl/bD3vnN * 24 Days of Hackage: extensible-effects Domain: ocharles.org.uk, Score: 60, Comments: 25 On Reddit: [27] http://goo.gl/5T2brL Original: [28] http://goo.gl/q2hVM0 * From Object Oriented Programming to Functional Programming - Inheritance and the Expression Problem Domain: github.com, Score: 58, Comments: 62 On Reddit: [29] http://goo.gl/fFldOR Original: [30] http://goo.gl/n5nHYo * I've been working on a small roguelike in Haskell Domain: github.com, Score: 56, Comments: 26 On Reddit: [31] http://goo.gl/mojdIu Original: [32] http://goo.gl/fT9DLB * Chordify: Get the chords to any song, using Haskell ! Domain: chordify.net, Score: 55, Comments: 19 On Reddit: [33] http://goo.gl/YfcHEu Original: [34] http://goo.gl/19apd * Merging, Folding, Monoids, and Foldable Domain: mtnviewmark.wordpress.com, Score: 53, Comments: 5 On Reddit: [35] http://goo.gl/GtoDKp Original: [36] http://goo.gl/QJsd7L * 24 Days of Hackage: persistent & esqueleto Domain: ocharles.org.uk, Score: 49, Comments: 14 On Reddit: [37] http://goo.gl/97eeUF Original: [38] http://goo.gl/TL8P7V * Haskell From Scratch - Series about making a non-trivial app from the ground up. Domain: youtube.com, Score: 46, Comments: 2 On Reddit: [39] http://goo.gl/sPV7rs Original: [40] http://goo.gl/KslDE4 Top StackOverflow Questions * What does (f .) . g mean in Haskell? votes: 17, answers: 2 Read on SO: [41] http://goo.gl/2i3GNc * LaTeX natural deduction proofs using Haskell votes: 13, answers: 0 Read on SO: [42] http://goo.gl/uH1K2u * Lazily Tying the Knot for 1 Dimensional Dynamic Programming votes: 13, answers: 4 Read on SO: [43] http://goo.gl/1kZQkK * What does Clojure borrow from Haskell? [on hold] votes: 12, answers: 0 Read on SO: [44] http://goo.gl/DsqKhp * Meaning of `<-` in do block in Haskell votes: 10, answers: 4 Read on SO: [45] http://goo.gl/JOJiFy * Why is function composition in Haskell right associative? votes: 10, answers: 1 Read on SO: [46] http://goo.gl/mURUDZ * Is there a library or typeclass for getting the transformer version of a monad? votes: 9, answers: 1 Read on SO: [47] http://goo.gl/k81E1h * How to implement B+ tree in Haskell? votes: 9, answers: 2 Read on SO: [48] http://goo.gl/lkwh8Z * Delimiting the IO monad votes: 9, answers: 2 Read on SO: [49] http://goo.gl/x3RlXO Until next time, [50]+Daniel Santa Cruz References 1. http://www.dcs.gla.ac.uk/~muffy/SPJ_oration.pdf 2. http://www.reddit.com/r/haskell/comments/1sbfmb/honorary_doctorate_for_simon_peyton_jones_on/ 3. https://github.com/chrisdone/hell 4. http://www.reddit.com/r/haskell/comments/1r755t/hell_a_haskell_shell/ 5. https://github.com/quchen/articles/blob/master/loeb-moeb.md 6. http://www.reddit.com/r/haskell/comments/1qwjk6/l%C3%B6b_and_m%C3%B6b_strange_loops_in_haskell/ 7. http://www.well-typed.com/blog/84 8. http://www.reddit.com/r/haskell/comments/1rpte3/explanation_of_the_new_haskell_records_extension/ 9. https://www.fpcomplete.com/ 10. http://www.reddit.com/r/haskell/comments/1qzioh/fp_complete_ide_now_free_for_community_use_give/ 11. http://www.haskellcast.com/episode/004-simon-marlow-on-parallelism-and-concurrency 12. http://www.reddit.com/r/haskell/comments/1rexqq/the_haskell_cast_4_simon_marlow_on_parallelism/ 13. http://ocharles.org.uk/blog/posts/2013-12-05-24-days-of-hackage-scotty.html 14. http://www.reddit.com/r/haskell/comments/1s65bl/24_days_of_hackage_scotty/ 15. http://www.idris-lang.org/idris-0-9-10-released/ 16. http://www.reddit.com/r/haskell/comments/1rn4d6/idris_0910_released/ 17. http://ocharles.org.uk/blog/posts/2013-12-07-24-days-of-hackage-threepenny-gui.html 18. http://www.reddit.com/r/haskell/comments/1sc67q/24_days_of_hackage_threepennygui/ 19. http://ocharles.org.uk/blog/posts/2013-12-02-24-days-of-hackage-linear.html 20. http://www.reddit.com/r/haskell/comments/1rximk/24_days_of_hackage_linear/ 21. http://ocharles.org.uk/blog/posts/2013-12-03-24-days-of-hackage-tasty.html 22. http://www.reddit.com/r/haskell/comments/1s0t1f/24_days_of_hackage_tasty/ 23. http://ocharles.org.uk/blog/posts/2013-12-01-24-days-of-hackage-intro.html 24. http://www.reddit.com/r/haskell/comments/1rv45n/24_days_of_hackage_2013_in_review/ 25. http://www.vice.com/read/algorave-is-the-future-of-dance-music-if-youre-an-html-coder 26. http://www.reddit.com/r/haskell/comments/1riror/hacking_haskell_in_nightclubs_xpost_from/ 27. http://ocharles.org.uk/blog/posts/2013-12-04-24-days-of-hackage-extensible-effects.html 28. http://www.reddit.com/r/haskell/comments/1s3oba/24_days_of_hackage_extensibleeffects/ 29. https://github.com/Dobiasd/articles/blob/master/from_oop_to_fp_-_inheritance_and_the_expression_problem.md 30. http://www.reddit.com/r/haskell/comments/1quhrl/from_object_oriented_programming_to_functional/ 31. https://github.com/dvolk/hoodie 32. http://www.reddit.com/r/haskell/comments/1r248j/ive_been_working_on_a_small_roguelike_in_haskell/ 33. http://chordify.net/ 34. http://www.reddit.com/r/haskell/comments/1r7sh1/chordify_get_the_chords_to_any_song_using_haskell/ 35. https://mtnviewmark.wordpress.com/2013/12/02/mfmf/ 36. http://www.reddit.com/r/haskell/comments/1rz8cn/merging_folding_monoids_and_foldable/ 37. http://ocharles.org.uk/blog/posts/2013-12-06-24-days-of-hackage-persistent-esqueleto.html 38. http://www.reddit.com/r/haskell/comments/1s9fyb/24_days_of_hackage_persistent_esqueleto/ 39. https://www.youtube.com/playlist?list=PLxj9UAX4Em-Ij4TKwKvo-SLp-Zbv-hB4B 40. http://www.reddit.com/r/haskell/comments/1s48bm/haskell_from_scratch_series_about_making_a/ 41. http://stackoverflow.com/questions/20279306/what-does-f-g-mean-in-haskell 42. http://stackoverflow.com/questions/19919431/latex-natural-deduction-proofs-using-haskell 43. http://stackoverflow.com/questions/20159269/lazily-tying-the-knot-for-1-dimensional-dynamic-programming 44. http://stackoverflow.com/questions/20411148/what-does-clojure-borrow-from-haskell 45. http://stackoverflow.com/questions/19961941/meaning-of-in-do-block-in-haskell 46. http://stackoverflow.com/questions/20342860/why-is-function-composition-in-haskell-right-associative 47. http://stackoverflow.com/questions/20066858/is-there-a-library-or-typeclass-for-getting-the-transformer-version-of-a-monad 48. http://stackoverflow.com/questions/20309501/how-to-implement-b-tree-in-haskell 49. http://stackoverflow.com/questions/20318936/delimiting-the-io-monad 50. https://plus.google.com/105107667630152149014/about -------------- next part -------------- An HTML attachment was scrubbed... URL: From danny.gratzer at gmail.com Thu Dec 12 03:48:32 2013 From: danny.gratzer at gmail.com (Danny Gratzer) Date: Wed, 11 Dec 2013 21:48:32 -0600 Subject: [Haskell-cafe] f^n for functional iteration In-Reply-To: <201312120337.rBC3bhWO028627@stowe.cs.dartmouth.edu> References: <201312120337.rBC3bhWO028627@stowe.cs.dartmouth.edu> Message-ID: This seems to work {-# LANGUAGE FlexibleInstances #-} instance Num (a -> a) where (*) = (.) Of course, using anything else from the Num class will blow up in your face so it's probably not worth it. Cheers, Danny Gratzer -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Thu Dec 12 03:55:09 2013 From: allbery.b at gmail.com (Brandon Allbery) Date: Wed, 11 Dec 2013 22:55:09 -0500 Subject: [Haskell-cafe] f^n for functional iteration In-Reply-To: References: <201312120337.rBC3bhWO028627@stowe.cs.dartmouth.edu> Message-ID: On Wed, Dec 11, 2013 at 10:48 PM, Danny Gratzer wrote: > This seems to work > > {-# LANGUAGE FlexibleInstances #-} > instance Num (a -> a) where > (*) = (.) > > Of course, using anything else from the Num class will blow up in your > face so it's probably not worth it. > And the hidden danger is that Num is special cased such that the compiler more or less has an open license to infer Num instances all over the place (see: defaulting, and its interaction with the monomorphism restriction), and as a result it will infer things you would never have imagined. In other words, the price of this is that type inference is no longer reliable and type errors will be reported incomprehensibly, depending on how consistently you specify type signatures (that is, the more you have, the more comprehensible the errors; but few people actually use type signatures *everywhere* they can be specified). -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From eijiro.sumii at gmail.com Thu Dec 12 05:05:36 2013 From: eijiro.sumii at gmail.com (Eijiro Sumii) Date: Thu, 12 Dec 2013 14:05:36 +0900 Subject: [Haskell-cafe] Deadline extended: FLOPS 2014 call for papers Message-ID: ********************************************************************** NEWS: Submission deadline extended. - Title, abstract, and draft paper by December 13, 2013 - Full paper by December 15, 2013 (23:59 anywhere in the world) ********************************************************************** Call For Papers =============== Twelfth International Symposium on Functional and Logic Programming (FLOPS 2014) June 4-6, 2014 Kanazawa, Japan http://www.jaist.ac.jp/flops2014/ ---------------------------------------------------------------------- - Journal publications in JFP (Jounral of Functional Programming) and TPLP (Theory and Practice of Logic Programming) are planned (see below). - Hyakumangoku Matsuri ( https://www.google.com/search?q=hyakumangoku%20matsuri&tbm=isch ) is scheduled *just* after FLOPS 2014. ---------------------------------------------------------------------- FLOPS is a forum for research on all issues concerning declarative programming, including functional programming and logic programming, and aims to promote cross-fertilization and integration between the two paradigms. Previous FLOPS meetings were held at Fuji Susono (1995), Shonan Village (1996), Kyoto (1998), Tsukuba (1999), Tokyo (2001), Aizu (2002), Nara (2004), Fuji Susono (2006), Ise (2008), Sendai (2010), and Kobe (2012). Topics ====== FLOPS solicits original papers in all areas of functional and logic programming, including (but not limited to): - Language issues: language design and constructs, programming methodology, integration of paradigms, interfacing with other languages, type systems, constraints, concurrency and distributed computing. - Foundations: logic and semantics, rewrite systems and narrowing, type theory, proof systems. - Implementation issues: compilation techniques, memory management, program analysis and transformation, partial evaluation, parallelism. - Applications: case studies, real-world applications, graphical user interfaces, Internet applications, XML, databases, formal methods and model checking. The proceedings will be published as an LNCS volume. The proceedings of the previous meetings (FLOPS 1999, 2001, 2002, 2004, 2006, 2008, 2010, and 2012) were published as LNCS 1722, 2024, 2441, 2998, 3945, 4989, 6009, and 7294. PC Co-Chairs ============ Michael Codish (Ben-Gurion University of the Negev) Eijiro Sumii (Tohoku University) PC Members ========== Lars Birkedal (Aarhus University) Michael Codish (Ben-Gurion University of the Negev) [co-chair] Marina De Vos (University of Bath) Moreno Falaschi (Universita degli studi di Udine) Carsten Fuhs (University College London) John Gallagher (Roskilde Universitet / IMDEA Software Institute) Samir Genaim (Universidad Complutense de Madrid) Laura Giordano (Universita del Piemonte Orientale) Ichiro Hasuo (University of Tokyo) Fritz Henglein (University of Copenhagen) Andy King (University of Kent) Oleg Kiselyov Vitaly Lagoon (MathWorks) Shin-Cheng Mu (Academia Sinica) Keiko Nakata (Institute of Cybernetics at Tallinn University of Technology) Luke Ong (University of Oxford) Peter Schachte (University of Melbourne) Takehide Soh (Kobe University) Eijiro Sumii (Tohoku University) [co-chair] Tachio Terauchi (Nagoya University) Joost Vennekens (KU Leuven) Janis Voigtlaender (Universitaet Bonn) Stephanie Weirich (University of Pennsylvania) Local Chair =========== Yuki Chiba (JAIST) Submission ========== Submissions must be unpublished and not submitted for publication elsewhere. Work that already appeared in unpublished or informally published workshops proceedings may be submitted. See also ACM SIGPLAN Republication Policy: http://www.sigplan.org/Resources/Policies/Republication Submissions should fall into one of the following categories: - Regular research papers: they should describe new results and will be judged on originality, correctness, and significance. - System descriptions: they should contain a link to a working system and will be judged on originality, usefulness, and design. - Declarative pearls: new and excellent declarative programs or theories with illustrative applications. System descriptions and declarative pearls must be explicitly marked as such in the title. Submissions must be written in English and can be up to 15 pages long including references, though pearls are typically shorter. Authors are required to use LaTeX2e and the Springer llncs class file, available at: http://www.springer.de/comp/lncs/authors.html Regular research papers should be supported by proofs and/or experimental results. In case of lack of space, this supporting information should be made accessible otherwise (e.g., a link to a Web page, or an appendix). Papers should be submitted electronically at: https://www.easychair.org/conferences/?conf=flops2014 Important Dates =============== Submission deadline (EXTENDED): - Title, abstract, and draft paper by December 13, 2013 - Full paper by December 15, 2013 (23:59 anywhere in the world) Author notification: February 10, 2014 Camera-ready copy: March 7, 2014 Journal Publication =================== - Journal of Functional Programming and - Theory and Practice of Logic Programming 2-4 of the best papers in each of the two areas: Functional Programming and Logic Programming, will be invited for inclusion in a designated FLOPS section within each of the two journals. The Theory and Practice of Logic Programming papers will appear as "Rapid Publications". All of the these submissions are expected to represent high-quality revisions and extensions of the selected FLOPS papers and will be reviewed under the standard criteria of each journal. Venue ===== Main Hall, Ishikawa Prefectural Museum of Art, 2-1 Dewa-machi, Kanazawa, Ishikawa 920-0963 JAPAN. Some Previous FLOPS =================== FLOPS 2012, Kobe: http://www.org.kobe-u.ac.jp/flops2012/ FLOPS 2010, Sendai: http://www.kb.ecei.tohoku.ac.jp/flops2010/ FLOPS 2008, Ise: http://www.math.nagoya-u.ac.jp/~garrigue/FLOPS2008/ Sponsor ======= Japan Society for Software Science and Technology (JSSST), Special Interest Group on Programming and Programming Languages (SIG-PPL) In Cooperation With =================== ACM SIGPLAN Asian Association for Foundation of Software (AAFS) Association for Logic Programming (ALP) From madjestic13 at gmail.com Thu Dec 12 08:42:28 2013 From: madjestic13 at gmail.com (Vlad Lopatin) Date: Thu, 12 Dec 2013 09:42:28 +0100 Subject: [Haskell-cafe] GLFW/GLFW-b ambiguity Message-ID: Hey guys, I am messing with OpenGL and here's the question: GLFW-b is supposed to be based on GLFW and extend it. How come GLFW-b naming is ambiguous with GLFW? GLFW-b main module is named the same as GLFW (import Graphics.UI.GLFW), making it necessary to hide one of the libraries via ghc-pkg hide, or to use a language extension in order to solve ambiguity. I am tempted to consider it a bug, unless somebody knows a good reason for it to be called a feature. Am I missing something? Regards, Vladimir -------------- next part -------------- An HTML attachment was scrubbed... URL: From christiaan.baaij at gmail.com Thu Dec 12 09:35:33 2013 From: christiaan.baaij at gmail.com (Christiaan Baaij) Date: Thu, 12 Dec 2013 10:35:33 +0100 Subject: [Haskell-cafe] GLFW/GLFW-b ambiguity In-Reply-To: References: Message-ID: <5F32F83D-2789-4585-9B2D-8108BD18E875@gmail.com> The GLFW and GLFW-b package on hackage are _both_ wrappers around the C-library GLFW. So, GLFW-b "extends" the GLFW C-library, _not_ the GLFW haskell package. Hope everything is clear now. -- Christiaan On Dec 12, 2013, at 9:42 AM, Vlad Lopatin wrote: > Hey guys, > > I am messing with OpenGL and here's the question: > > GLFW-b is supposed to be based on GLFW and extend it. How come GLFW-b naming is ambiguous with GLFW? GLFW-b main module is named the same as GLFW (import Graphics.UI.GLFW), making it necessary to hide one of the libraries via ghc-pkg hide, or to use a language extension in order to solve ambiguity. I am tempted to consider it a bug, unless somebody knows a good reason for it to be called a feature. > > Am I missing something? > > Regards, > Vladimir > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From madjestic13 at gmail.com Thu Dec 12 09:55:12 2013 From: madjestic13 at gmail.com (Vlad Lopatin) Date: Thu, 12 Dec 2013 10:55:12 +0100 Subject: [Haskell-cafe] GLFW/GLFW-b ambiguity In-Reply-To: <5F32F83D-2789-4585-9B2D-8108BD18E875@gmail.com> References: <5F32F83D-2789-4585-9B2D-8108BD18E875@gmail.com> Message-ID: Thanks, Christiaan Does it mean that GLFW-b and GLFW (haskell package) are not meant to be used together? I like some GLFW-b functionality, but I also like to be able to call some of GLFW haskell package functions. If I try to import GLFW-b and GLFW at the same time - I get the 'ambigous name' error. Is there a recommendation for a good coding practice here? Regards, Vladimir On 12 December 2013 10:35, Christiaan Baaij wrote: > The GLFW and GLFW-b package on hackage are _both_ wrappers around the > C-library GLFW. > So, GLFW-b "extends" the GLFW C-library, _not_ the GLFW haskell package. > > Hope everything is clear now. > > -- Christiaan > > On Dec 12, 2013, at 9:42 AM, Vlad Lopatin wrote: > > > Hey guys, > > > > I am messing with OpenGL and here's the question: > > > > GLFW-b is supposed to be based on GLFW and extend it. How come GLFW-b > naming is ambiguous with GLFW? GLFW-b main module is named the same as > GLFW (import Graphics.UI.GLFW), making it necessary to hide one of the > libraries via ghc-pkg hide, or to use a language extension in order to > solve ambiguity. I am tempted to consider it a bug, unless somebody knows > a good reason for it to be called a feature. > > > > Am I missing something? > > > > Regards, > > Vladimir > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From madjestic13 at gmail.com Thu Dec 12 10:07:04 2013 From: madjestic13 at gmail.com (Vlad Lopatin) Date: Thu, 12 Dec 2013 11:07:04 +0100 Subject: [Haskell-cafe] GLUT, FLGW, FLGW-b Message-ID: Hey guys, I keep reading (wiki) that GLUT is a legacy package and some libraries (e.g. GLFW) are meant to replace it. I also see that some of the GLUT functionality is based on fixed pipeline. What is the current status of Haskell GLUT? Is it 'to stay' or something that is going to be deprecated at some point? Should one try replacing it with GLFW(-b) in a project, if fixed pipeline is not expected to be used? Regards, Vladimir. -------------- next part -------------- An HTML attachment was scrubbed... URL: From christiaan.baaij at gmail.com Thu Dec 12 10:47:42 2013 From: christiaan.baaij at gmail.com (Christiaan Baaij) Date: Thu, 12 Dec 2013 11:47:42 +0100 Subject: [Haskell-cafe] GLFW/GLFW-b ambiguity In-Reply-To: References: <5F32F83D-2789-4585-9B2D-8108BD18E875@gmail.com> Message-ID: <21B461CD-E663-4DA5-AF04-BA0FF2114BC7@gmail.com> I can't comment on good coding practices, I only know that some people don't like the PackageImports extension of GHC. GLFW-b and GLFW are both simple wrapper around the C-library as far as I know, so you can use them together. Just be careful with your version of GLFW-b, the latest releases are based on the 3.* version of the C-library; while the GLFW package uses version 2.7.* of the C-library. -- Christiaan On Dec 12, 2013, at 10:55 AM, Vlad Lopatin wrote: > Thanks, Christiaan > > Does it mean that GLFW-b and GLFW (haskell package) are not meant to be used together? > > I like some GLFW-b functionality, but I also like to be able to call some of GLFW haskell package functions. If I try to import GLFW-b and GLFW at the same time - I get the 'ambigous name' error. Is there a recommendation for a good coding practice here? > > > Regards, > Vladimir > > > On 12 December 2013 10:35, Christiaan Baaij wrote: > The GLFW and GLFW-b package on hackage are _both_ wrappers around the C-library GLFW. > So, GLFW-b "extends" the GLFW C-library, _not_ the GLFW haskell package. > > Hope everything is clear now. > > -- Christiaan > > On Dec 12, 2013, at 9:42 AM, Vlad Lopatin wrote: > > > Hey guys, > > > > I am messing with OpenGL and here's the question: > > > > GLFW-b is supposed to be based on GLFW and extend it. How come GLFW-b naming is ambiguous with GLFW? GLFW-b main module is named the same as GLFW (import Graphics.UI.GLFW), making it necessary to hide one of the libraries via ghc-pkg hide, or to use a language extension in order to solve ambiguity. I am tempted to consider it a bug, unless somebody knows a good reason for it to be called a feature. > > > > Am I missing something? > > > > Regards, > > Vladimir > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > From svenpanne at gmail.com Thu Dec 12 11:05:10 2013 From: svenpanne at gmail.com (Sven Panne) Date: Thu, 12 Dec 2013 12:05:10 +0100 Subject: [Haskell-cafe] GLUT, FLGW, FLGW-b In-Reply-To: References: Message-ID: 2013/12/12 Vlad Lopatin : > I keep reading (wiki) that GLUT is a legacy package and some libraries (e.g. > GLFW) are meant to replace it. I also see that some of the GLUT > functionality is based on fixed pipeline. What is the current status of > Haskell GLUT? Is it 'to stay' or something that is going to be deprecated > at some point? Should one try replacing it with GLFW(-b) in a project, if > fixed pipeline is not expected to be used? I think this really depends on your needs: GLUT was designed as a simple cross-platform API for OpenGL demos and tutorials, perhaps even some programs of medium complexity. It was definitely not designed for programs with complex GUI requirements. Of course you can build your own GUI on top of OpenGL, but GLUT provides no help for that. If you only need to create a few windows or use fullscreen, and if you are happy with GLUT's simple event model, you can happily use it. If you don't use forward-compatible OpenGL contexts, you can even use GLUT's menus, fonts and geometric objects, because these are the parts of GLUT which use the fixed pipeline internally IIRC. Furthermore, I intend to continue maintaining the GLUT package, but there is not that much left to do, because the underlying C library (freeglut nowadays) hasn't really changed that much in the last few years and I think the Haskell binding is feature-complete. If not: https://github.com/haskell-opengl/GLUT/issues ;-) From efsubenovex at gmail.com Thu Dec 12 16:53:57 2013 From: efsubenovex at gmail.com (Schell Scivally) Date: Thu, 12 Dec 2013 08:53:57 -0800 Subject: [Haskell-cafe] GLFW/GLFW-b ambiguity In-Reply-To: References: <5F32F83D-2789-4585-9B2D-8108BD18E875@gmail.com> Message-ID: GLFW and GLFW-b aren't _meant_ to be used together, though I don't see why you _couldn't_ use them together. People in the #haskell-game channel on irc.freenode.net may be able to help you, as well as the package maintainers. I know Brian Lewis (glfw-b) is pretty fast to respond. On Thu, Dec 12, 2013 at 1:55 AM, Vlad Lopatin wrote: > Thanks, Christiaan > > Does it mean that GLFW-b and GLFW (haskell package) are not meant to be > used together? > > I like some GLFW-b functionality, but I also like to be able to call some > of GLFW haskell package functions. If I try to import GLFW-b and GLFW at > the same time - I get the 'ambigous name' error. Is there a recommendation > for a good coding practice here? > > > Regards, > Vladimir > > > On 12 December 2013 10:35, Christiaan Baaij > wrote: > > The GLFW and GLFW-b package on hackage are _both_ wrappers around the >> C-library GLFW. >> So, GLFW-b "extends" the GLFW C-library, _not_ the GLFW haskell package. >> >> Hope everything is clear now. >> >> -- Christiaan >> >> On Dec 12, 2013, at 9:42 AM, Vlad Lopatin wrote: >> >> > Hey guys, >> > >> > I am messing with OpenGL and here's the question: >> > >> > GLFW-b is supposed to be based on GLFW and extend it. How come GLFW-b >> naming is ambiguous with GLFW? GLFW-b main module is named the same as >> GLFW (import Graphics.UI.GLFW), making it necessary to hide one of the >> libraries via ghc-pkg hide, or to use a language extension in order to >> solve ambiguity. I am tempted to consider it a bug, unless somebody knows >> a good reason for it to be called a feature. >> > >> > Am I missing something? >> > >> > Regards, >> > Vladimir >> > _______________________________________________ >> > Haskell-Cafe mailing list >> > Haskell-Cafe at haskell.org >> > http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -- Schell Scivally http://blog.efnx.com http://github.com/schell http://twitter.com/schellsan -------------- next part -------------- An HTML attachment was scrubbed... URL: From krismicinski at gmail.com Thu Dec 12 17:11:13 2013 From: krismicinski at gmail.com (Kristopher Micinski) Date: Thu, 12 Dec 2013 12:11:13 -0500 Subject: [Haskell-cafe] SENIOR HASKELL OPPORTUNITY In-Reply-To: <45DC9340-78FC-432C-98C5-10914BF5F0A2@me.com> References: <2252CC638F64CD4FBB38CD13A85C6D8801C82C71@GYRO.henlow.local> <05E70037-A4F5-44DD-819D-EA5F3C137AAA@yandex.ru> <2252CC638F64CD4FBB38CD13A85C6D8801C82FEE@GYRO.henlow.local> <45DC9340-78FC-432C-98C5-10914BF5F0A2@me.com> Message-ID: I completely agree, hence my agreeing that this is not necessarily ill formed...! Kris On Wed, Dec 11, 2013 at 5:02 PM, Malcolm Wallace wrote: > Typically, finance jobs that ask for mathematical skill, really do mean hard integrals, partial differential equations, and other numerical stuff that most CS people quail at. > >> On 11 Dec 2013, at 20:52, Kristopher Micinski wrote: >> >> I think the point is that people who have PhDs in CS have very strong >> math skills, but that the definition of "math" may differ from person >> to person. If your definition of math is "really hard integrals" then >> maybe not, but almost everyone with a PhD in CS is very good at some >> form of advanced math :-).. >> >> Kris >> >> >> On Wed, Dec 11, 2013 at 4:34 AM, Neena Singh >> wrote: >>> Yes, this is correct. >>> >>> >>> >>> A number of (quant) developers have a PhD or Masters in Computer Science but >>> have not used their maths skills extensively for many years. >>> >>> >>> >>> When hiring for a (quant) developer many financial organisations will look >>> for strong maths skills and will therefore ask many probability and other >>> mathematical questions as part of the interview process which many >>> developers find difficult and is often the reason they are not successful in >>> the interview process. >>> >>> >>> >>> For this particular opportunity they are looking for someone with a PhD or >>> High Level degree but will not be extensively testing a candidate?s >>> mathematical ability. This opportunity is therefore an option for someone >>> who is technically very strong but has not used their more advanced maths >>> skills for many years. >>> >>> >>> >>> Thanks >>> >>> >>> >>> Neena >>> >>> >>> >>> From: Haskell-Cafe [mailto:haskell-cafe-bounces at haskell.org] On Behalf Of >>> Stijn van Drongelen >>> Sent: 11 December 2013 09:06 >>> To: Clark Gaebel >>> Cc: haskell-cafe at haskell.org; MigMit >>> Subject: Re: [Haskell-cafe] SENIOR HASKELL OPPORTUNITY >>> >>> >>> >>> "Maths skills are not essential [...]." >>> >>> "EXPERIENCE REQUIRED: >>> [...] >>> * - PHD / High Level degree in Computer Science." >>> >>> Huh. >>> >>> >>> >>> On Wed, Dec 11, 2013 at 6:09 AM, Clark Gaebel wrote: >>> >>> Well how else would you expect to earn that "business bonus"? >>> >>> >>> >>> On Wed, Dec 11, 2013 at 12:03 AM, MigMit wrote: >>> >>> Wait a sec, is that yours: http://www.haskellers.com/jobs/59 ? >>> >>> I loved the required skill "Object oriented programming experience in >>> Haskell". >>> >>> >>>> On 10 Dec 2013, at 18:58, Neena Singh wrote: >>>> >>>> Hello, >>>> >>>> I have been retained by a leading Hedge Fund who are looking for an >>>> experienced Haskell developer to join their highly regarded front office >>>> technology team. This is a great opportunity for a passionate technologist >>>> to join a group working very closely with the trading floor on advanced >>>> Haskell projects. Previous finance experience is not a pre-requisite however >>>> a passion for Haskell is a must. >>>> >>>> If you are interested learning more about this opportunity and potential >>>> salary ranges please call me on 020 7871 4482 or email me >>>> Neena.singh at henlowgroup.com. >>>> >>>> I look forward to hearing from you, >>>> >>>> Regards, >>>> >>>> Neena >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >>> >>> >>> -- >>> >>> Clark. >>> >>> Key ID : 0x78099922 >>> Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 >>> >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >>> >>> >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From dagitj at gmail.com Thu Dec 12 18:15:30 2013 From: dagitj at gmail.com (Jason Dagit) Date: Thu, 12 Dec 2013 10:15:30 -0800 Subject: [Haskell-cafe] GLUT, FLGW, FLGW-b In-Reply-To: References: Message-ID: On Thu, Dec 12, 2013 at 3:05 AM, Sven Panne wrote: > 2013/12/12 Vlad Lopatin : > > I keep reading (wiki) that GLUT is a legacy package and some libraries > (e.g. > > GLFW) are meant to replace it. I also see that some of the GLUT > > functionality is based on fixed pipeline. What is the current status of > > Haskell GLUT? Is it 'to stay' or something that is going to be > deprecated > > at some point? Should one try replacing it with GLFW(-b) in a project, > if > > fixed pipeline is not expected to be used? > > I think this really depends on your needs: GLUT was designed as a > simple cross-platform API for OpenGL demos and tutorials, perhaps even > some programs of medium complexity. I prefer GLFW-b for cross platform programs for the simple reason that on windows GLUT requires you to install a DLL and make sure it's in the path. I prefer GLFW-b more generally because it's more modern, fully open source, and under active development. The license for GLUT is open in practice but it's not a clean open source license. I guess most people use freeglut instead. Jason -------------- next part -------------- An HTML attachment was scrubbed... URL: From hoerdegen at funktional.info Thu Dec 12 18:44:33 2013 From: hoerdegen at funktional.info (=?ISO-8859-15?Q?Heinrich_H=F6rdegen?=) Date: Thu, 12 Dec 2013 19:44:33 +0100 Subject: [Haskell-cafe] Munich Haskell Christmas Meeting Message-ID: <52AA0411.9010106@funktional.info> Dear all, on Thursday, 19th of December, we will meet for a Christmas get-together. The event is organised together with the Munich Lambda Group. We will have Gl?hwein & Lebkuchen (mulled wine & gingerbread). Check out the details: http://www.meetup.com/Munich-Lambda/events/155219402/ I also updated our homepage. New meeting dates are available for next year: http://www.haskell-munich.de/dates And check out also the links that were sent for our last meeting. Thanks to everyone who contributed interesting links for our web site during this year. I wish all of you happy Chrismas and a happy new year! Heinrich From anton.kholomiov at gmail.com Thu Dec 12 18:55:31 2013 From: anton.kholomiov at gmail.com (Anton Kholomiov) Date: Thu, 12 Dec 2013 22:55:31 +0400 Subject: [Haskell-cafe] ANN - csound-expression 3.1 library for electronic music Message-ID: I'm glad to announce the new version of the csound-expression [1] package. It's the library for electronic music and sound design. Here is a full description [2] In the new version it supports GUI-widgets. You can not only create sound instruments but update parameters onlne with sliders, knobs and buttons. There are many other widgets. You can find out the details in the quick start guide [3] and the examples [4]. Anton [1] http://hackage.haskell.org/package/csound-expression [2] https://github.com/anton-k/csound-expression [3] https://github.com/anton-k/csound-expression/blob/master/tutorial/QuickStart.markdown [4] https://github.com/anton-k/csound-expression/tree/master/examples/Gui -------------- next part -------------- An HTML attachment was scrubbed... URL: From efsubenovex at gmail.com Thu Dec 12 18:58:22 2013 From: efsubenovex at gmail.com (Schell Scivally) Date: Thu, 12 Dec 2013 10:58:22 -0800 Subject: [Haskell-cafe] ANN - csound-expression 3.1 library for electronic music In-Reply-To: References: Message-ID: Cool! Many thanks. On Thu, Dec 12, 2013 at 10:55 AM, Anton Kholomiov wrote: > I'm glad to announce the new version of the csound-expression [1] package. > It's the library for electronic music and sound design. Here is a full > description [2] > In the new version it supports GUI-widgets. You can not only > create sound instruments but update parameters onlne with sliders, > knobs and buttons. There are many other widgets. > > You can find out the details in the quick start guide [3] and the examples > [4]. > > Anton > > [1] http://hackage.haskell.org/package/csound-expression > [2] https://github.com/anton-k/csound-expression > [3] > https://github.com/anton-k/csound-expression/blob/master/tutorial/QuickStart.markdown > [4] https://github.com/anton-k/csound-expression/tree/master/examples/Gui > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -- Schell Scivally http://blog.efnx.com http://github.com/schell http://twitter.com/schellsan -------------- next part -------------- An HTML attachment was scrubbed... URL: From temporalabstraction at gmail.com Thu Dec 12 19:19:35 2013 From: temporalabstraction at gmail.com (EatsKittens) Date: Thu, 12 Dec 2013 20:19:35 +0100 Subject: [Haskell-cafe] Way to implement toFloat :: (Num a) => a -> Float Message-ID: Is there a way to add a method to a typeclass like num to implement this concept? A function that converts any number to floats? -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Thu Dec 12 19:28:00 2013 From: allbery.b at gmail.com (Brandon Allbery) Date: Thu, 12 Dec 2013 14:28:00 -0500 Subject: [Haskell-cafe] Way to implement toFloat :: (Num a) => a -> Float In-Reply-To: References: Message-ID: On Thu, Dec 12, 2013 at 2:19 PM, EatsKittens wrote: > Is there a way to add a method to a typeclass like num to implement this > concept? A function that converts any number to floats? > What does it mean for (Complex Double)? What does it mean for (a -> a) (NumInstances)? -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From haskell at nand.wakku.to Thu Dec 12 19:29:22 2013 From: haskell at nand.wakku.to (Niklas Haas) Date: Thu, 12 Dec 2013 20:29:22 +0100 Subject: [Haskell-cafe] Way to implement toFloat :: (Num a) => a -> Float In-Reply-To: References: Message-ID: <20131212202922.GA11719@nanodesu.talocan.mine.nu> On Thu, 12 Dec 2013 20:19:35 +0100, EatsKittens wrote: > Is there a way to add a method to a typeclass like num to implement this > concept? A function that converts any number to floats? Non-text part: text/html > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe The typeclass Real has this in a slightly different form: toRational :: Real a => a -> Rational You can use fromRational :: Rational -> Float together with this to implement your function. From benjamin.foppa at gmail.com Thu Dec 12 19:34:13 2013 From: benjamin.foppa at gmail.com (Ben Foppa) Date: Thu, 12 Dec 2013 14:34:13 -0500 Subject: [Haskell-cafe] Way to implement toFloat :: (Num a) => a -> Float In-Reply-To: <20131212202922.GA11719@nanodesu.talocan.mine.nu> References: <20131212202922.GA11719@nanodesu.talocan.mine.nu> Message-ID: > toRational :: Real a => a -> Rational This, combined with fromRational :: Fractional a => Rational -> a forms realToFrac :: (Real a, Fractional b) => a -> b On Thu, Dec 12, 2013 at 2:29 PM, Niklas Haas wrote: > On Thu, 12 Dec 2013 20:19:35 +0100, EatsKittens < > temporalabstraction at gmail.com> wrote: > > Is there a way to add a method to a typeclass like num to implement this > > concept? A function that converts any number to floats? > Non-text part: text/html > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > The typeclass Real has this in a slightly different form: > > toRational :: Real a => a -> Rational > > You can use fromRational :: Rational -> Float together with this to > implement your function. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From bgamari.foss at gmail.com Thu Dec 12 19:39:59 2013 From: bgamari.foss at gmail.com (Ben Gamari) Date: Thu, 12 Dec 2013 14:39:59 -0500 Subject: [Haskell-cafe] Way to implement toFloat :: (Num a) => a -> Float In-Reply-To: References: Message-ID: <87sitxx3hs.fsf@gmail.com> EatsKittens writes: > Is there a way to add a method to a typeclass like num to implement this > concept? A function that converts any number to floats? > Does the following do what you expect? realToFrac :: (Fractional b, Real a) => a -> b realToFrac' :: (Real a) => a -> Float realToFrac' = realToFrac :: (Real a) => a -> Float Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 489 bytes Desc: not available URL: From temporalabstraction at gmail.com Thu Dec 12 19:55:45 2013 From: temporalabstraction at gmail.com (EatsKittens) Date: Thu, 12 Dec 2013 20:55:45 +0100 Subject: [Haskell-cafe] Way to implement toFloat :: (Num a) => a -> Float In-Reply-To: <87sitxx3hs.fsf@gmail.com> References: <87sitxx3hs.fsf@gmail.com> Message-ID: Ah, I had no ideal the real typeclass existed, that completely solves my issue. On 12 December 2013 20:39, Ben Gamari wrote: > EatsKittens writes: > > > Is there a way to add a method to a typeclass like num to implement this > > concept? A function that converts any number to floats? > > > Does the following do what you expect? > > realToFrac :: (Fractional b, Real a) => a -> b > > realToFrac' :: (Real a) => a -> Float > realToFrac' = realToFrac :: (Real a) => a -> Float > > Cheers, > > - Ben > -------------- next part -------------- An HTML attachment was scrubbed... URL: From qdunkan at gmail.com Thu Dec 12 20:32:41 2013 From: qdunkan at gmail.com (Evan Laforge) Date: Thu, 12 Dec 2013 12:32:41 -0800 Subject: [Haskell-cafe] Way to implement toFloat :: (Num a) => a -> Float In-Reply-To: References: <87sitxx3hs.fsf@gmail.com> Message-ID: Just be careful, realToFrac goes through rational first, which can't represent special values like NaN and Infinity, so those will turn into random numbers. Also it can be very inefficient. Still, it's acceptable for a generic "any to Float" conversion. For conversion between Doubles and Floats (or newtypes thereof), however, I use things like d2f :: Double -> Float d2f (Types.D# d) = Types.F# (Prim.double2Float# d) On Thu, Dec 12, 2013 at 11:55 AM, EatsKittens wrote: > Ah, I had no ideal the real typeclass existed, that completely solves my > issue. > > > On 12 December 2013 20:39, Ben Gamari wrote: >> >> EatsKittens writes: >> >> > Is there a way to add a method to a typeclass like num to implement this >> > concept? A function that converts any number to floats? >> > >> Does the following do what you expect? >> >> realToFrac :: (Fractional b, Real a) => a -> b >> >> realToFrac' :: (Real a) => a -> Float >> realToFrac' = realToFrac :: (Real a) => a -> Float >> >> Cheers, >> >> - Ben > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From madjestic13 at gmail.com Thu Dec 12 21:45:21 2013 From: madjestic13 at gmail.com (Vlad Lopatin) Date: Thu, 12 Dec 2013 22:45:21 +0100 Subject: [Haskell-cafe] GLUT, FLGW, FLGW-b In-Reply-To: References: Message-ID: Thanks, Jason What makes you prefer GLFW-b instead GLFW? On 12 December 2013 19:15, Jason Dagit wrote: > > > > On Thu, Dec 12, 2013 at 3:05 AM, Sven Panne wrote: > >> 2013/12/12 Vlad Lopatin : >> > I keep reading (wiki) that GLUT is a legacy package and some libraries >> (e.g. >> > GLFW) are meant to replace it. I also see that some of the GLUT >> > functionality is based on fixed pipeline. What is the current status of >> > Haskell GLUT? Is it 'to stay' or something that is going to be >> deprecated >> > at some point? Should one try replacing it with GLFW(-b) in a project, >> if >> > fixed pipeline is not expected to be used? >> >> I think this really depends on your needs: GLUT was designed as a >> simple cross-platform API for OpenGL demos and tutorials, perhaps even >> some programs of medium complexity. > > > I prefer GLFW-b for cross platform programs for the simple reason that on > windows GLUT requires you to install a DLL and make sure it's in the path. > > I prefer GLFW-b more generally because it's more modern, fully open > source, and under active development. The license for GLUT is open in > practice but it's not a clean open source license. I guess most people use > freeglut instead. > > Jason > -------------- next part -------------- An HTML attachment was scrubbed... URL: From dagitj at gmail.com Thu Dec 12 22:49:33 2013 From: dagitj at gmail.com (Jason Dagit) Date: Thu, 12 Dec 2013 14:49:33 -0800 Subject: [Haskell-cafe] GLUT, FLGW, FLGW-b In-Reply-To: References: Message-ID: I started using it after making the following comparison several years ago: http://blog.codersbase.com/posts/2011-03-17-picking-gui-library.html Maybe that analysis is useful to you as well? Just so you know, it's probably out of date by now, so you might want to double check some of my claims. For example, the C library for GLFW doesn't use atexit() anymore (which is a good thing). Getting back to your question: As I recall, it's better maintained, lighter weight, and it has better dependencies. With GLFW-b you can use either OpenGL or OpenGLRaw, whereas GLFW depends directly on OpenGL. The main drawback, for me, is that GLFW-b doesn't support fonts. My proposed solution to that was to make a binding to the freetype2 library (you can find my binding on hackage/github). I never really finished that project. The binding should work but it's very low level. A few people have sent me example code they wrote to use it with OpenGL. It's really something I should finish :) The other cool thing about using freetype for fonts is that you can easily make it part of a rendering system that doesn't use any OS rendering libraries (eg., add font support to a ray-tracer). Jason On Thu, Dec 12, 2013 at 1:45 PM, Vlad Lopatin wrote: > Thanks, Jason > > What makes you prefer GLFW-b instead GLFW? > > > On 12 December 2013 19:15, Jason Dagit wrote: > >> >> >> >> On Thu, Dec 12, 2013 at 3:05 AM, Sven Panne wrote: >> >>> 2013/12/12 Vlad Lopatin : >>> > I keep reading (wiki) that GLUT is a legacy package and some libraries >>> (e.g. >>> > GLFW) are meant to replace it. I also see that some of the GLUT >>> > functionality is based on fixed pipeline. What is the current status >>> of >>> > Haskell GLUT? Is it 'to stay' or something that is going to be >>> deprecated >>> > at some point? Should one try replacing it with GLFW(-b) in a >>> project, if >>> > fixed pipeline is not expected to be used? >>> >>> I think this really depends on your needs: GLUT was designed as a >>> simple cross-platform API for OpenGL demos and tutorials, perhaps even >>> some programs of medium complexity. >> >> >> I prefer GLFW-b for cross platform programs for the simple reason that on >> windows GLUT requires you to install a DLL and make sure it's in the path. >> >> I prefer GLFW-b more generally because it's more modern, fully open >> source, and under active development. The license for GLUT is open in >> practice but it's not a clean open source license. I guess most people use >> freeglut instead. >> >> Jason >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From tim at blitzcode.net Fri Dec 13 09:01:02 2013 From: tim at blitzcode.net (Tim C. Schroeder) Date: Fri, 13 Dec 2013 10:01:02 +0100 Subject: [Haskell-cafe] GLUT, FLGW, FLGW-b In-Reply-To: References: Message-ID: <3CD0270E-5B09-45BA-AAD3-37BAF8393965@blitzcode.net> I'd agree, use GLFW-b. I'm very happy with it! As far as the font rendering is concerned, if all you need is a basic bitmap font to get some text on the screen, you might be able to use some code I wrote as a self-contained, drop-in replacement: https://github.com/blitzcode/haskell-gol/blob/master/parallel-glfwb/src/Font.hs (Looking at that code now, might want to bracket inside of withFontTexture. That code was written before Simon Marlow's book taught me about the wonders of Haskell exception handling...) I also wrote a Haskell FT2 binding. It's a very nice library with a decent API and few dependencies, so that was quite doable. The problem is that FT2 is really 'just' a glyph rasterizer. All other functionality is either rudimentary (kerning, glyph mapping) or out of the scope of the library (ligatures, glyph substitution, OpenType text layout in general). You'll need another library on top / besides it to get text rendering quality like in native GUI toolkits or a web browser. Obvious choices would be Pango or HarfBuzz, but those are more complicated to write a Haskell binding for (dependencies, C++, etc.). A 'just works' solution for platform and giant-GUI-toolkit independent, high-quality text rendering is sorely missing from the Haskell ecosystem, as far as I can tell. Doing an FT2 binding and the OpenGL glyph caching / texture atlas generation etc. is fine, but I'm afraid getting something like HarfBuzz/Pango up and running exceeds my Cabal-fu, for now. Cheers, Tim On Dec 12, 2013, at 11:49 PM, Jason Dagit wrote: > I started using it after making the following comparison several years ago: http://blog.codersbase.com/posts/2011-03-17-picking-gui-library.html > > Maybe that analysis is useful to you as well? Just so you know, it's probably out of date by now, so you might want to double check some of my claims. For example, the C library for GLFW doesn't use atexit() anymore (which is a good thing). > > Getting back to your question: As I recall, it's better maintained, lighter weight, and it has better dependencies. With GLFW-b you can use either OpenGL or OpenGLRaw, whereas GLFW depends directly on OpenGL. The main drawback, for me, is that GLFW-b doesn't support fonts. > > My proposed solution to that was to make a binding to the freetype2 library (you can find my binding on hackage/github). I never really finished that project. The binding should work but it's very low level. A few people have sent me example code they wrote to use it with OpenGL. It's really something I should finish :) The other cool thing about using freetype for fonts is that you can easily make it part of a rendering system that doesn't use any OS rendering libraries (eg., add font support to a ray-tracer). > > Jason > > > On Thu, Dec 12, 2013 at 1:45 PM, Vlad Lopatin wrote: > Thanks, Jason > > What makes you prefer GLFW-b instead GLFW? > > > On 12 December 2013 19:15, Jason Dagit wrote: > > > > On Thu, Dec 12, 2013 at 3:05 AM, Sven Panne wrote: > 2013/12/12 Vlad Lopatin : > > I keep reading (wiki) that GLUT is a legacy package and some libraries (e.g. > > GLFW) are meant to replace it. I also see that some of the GLUT > > functionality is based on fixed pipeline. What is the current status of > > Haskell GLUT? Is it 'to stay' or something that is going to be deprecated > > at some point? Should one try replacing it with GLFW(-b) in a project, if > > fixed pipeline is not expected to be used? > > I think this really depends on your needs: GLUT was designed as a > simple cross-platform API for OpenGL demos and tutorials, perhaps even > some programs of medium complexity. > > I prefer GLFW-b for cross platform programs for the simple reason that on windows GLUT requires you to install a DLL and make sure it's in the path. > > I prefer GLFW-b more generally because it's more modern, fully open source, and under active development. The license for GLUT is open in practice but it's not a clean open source license. I guess most people use freeglut instead. > > Jason > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From me at lelf.lu Fri Dec 13 14:59:26 2013 From: me at lelf.lu (Antonio Nikishaev) Date: Fri, 13 Dec 2013 18:59:26 +0400 Subject: [Haskell-cafe] f^n for functional iteration References: <201312120337.rBC3bhWO028627@stowe.cs.dartmouth.edu> Message-ID: Doug McIlroy writes: http://hackage.haskell.org/package/NumInstances > Agreeing with the analysis, I will sharpen my question. > Is option 2 possible at all, regardless of sanity concerns > (e.g. incomplete implementation of Num). > > Doug > >> On Tue, 10 Dec 2013 at 10:51 AM, Danny Gratzer wrote >> >> Well (^) is already used for their traditional meaning and using this exact >> operator would require >> >> 1. Shadowing (^) from prelude >> 2. Making (a -> a) an instance of Num (impossible to do sanely) >> >> You can just use a different operator >> >> f .^. n = foldl (.) id $ replicate n f >> >> On Tue, Dec 10, 2013 at 10:45 AM, Doug McIlroy wrote: >> >> > Is there a trick whereby the customary notation f^n for iterated >> > functional composition ((\n f -> foldl (.) id (replicate n f)) n f) can >> > be defined in Haskell? >> > >> > Doug McIlroy From danny.gratzer at gmail.com Fri Dec 13 15:04:38 2013 From: danny.gratzer at gmail.com (Danny Gratzer) Date: Fri, 13 Dec 2013 09:04:38 -0600 Subject: [Haskell-cafe] f^n for functional iteration In-Reply-To: References: <201312120337.rBC3bhWO028627@stowe.cs.dartmouth.edu> Message-ID: @Antonio, that defines sane instances for (a -> a), he needs [f ^ x] to be [f . f . f . f . ....] which means that [f * f] is [f . f] not the [liftA2 (*)] that they use. Cheers, Danny Gratzer On Fri, Dec 13, 2013 at 8:59 AM, Antonio Nikishaev wrote: > Doug McIlroy writes: > > http://hackage.haskell.org/package/NumInstances > > > Agreeing with the analysis, I will sharpen my question. > > Is option 2 possible at all, regardless of sanity concerns > > (e.g. incomplete implementation of Num). > > > > Doug > > > >> On Tue, 10 Dec 2013 at 10:51 AM, Danny Gratzer > wrote > >> > >> Well (^) is already used for their traditional meaning and using this > exact > >> operator would require > >> > >> 1. Shadowing (^) from prelude > >> 2. Making (a -> a) an instance of Num (impossible to do sanely) > >> > >> You can just use a different operator > >> > >> f .^. n = foldl (.) id $ replicate n f > >> > >> On Tue, Dec 10, 2013 at 10:45 AM, Doug McIlroy >wrote: > >> > >> > Is there a trick whereby the customary notation f^n for iterated > >> > functional composition ((\n f -> foldl (.) id (replicate n f)) n f) > can > >> > be defined in Haskell? > >> > > >> > Doug McIlroy > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From nikita at karetnikov.org Fri Dec 13 16:00:54 2013 From: nikita at karetnikov.org (Nikita Karetnikov) Date: Fri, 13 Dec 2013 20:00:54 +0400 Subject: [Haskell-cafe] Writing a Storable instance for a C union Message-ID: <87r49gagg9.fsf@karetnikov.org> Could anyone explain how to write a Storable instance for MyStruct? (The key field allows to determine the type of a value inside the union.) typedef enum Key_ { ONE = 1, FOUR = 4, TWENTY = 20 } Key; struct MyStruct { Key key; union { Foo one; uint64_t four; void *twenty; }; }; Also, should I use hsc2hs to make the resulting code portable? -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 835 bytes Desc: not available URL: From andreas.abel at ifi.lmu.de Fri Dec 13 16:20:04 2013 From: andreas.abel at ifi.lmu.de (Andreas Abel) Date: Fri, 13 Dec 2013 17:20:04 +0100 Subject: [Haskell-cafe] [high-order-munich] Munich Haskell Christmas Meeting In-Reply-To: <52AA0411.9010106@funktional.info> References: <52AA0411.9010106@funktional.info> Message-ID: <52AB33B4.5090004@ifi.lmu.de> Dear Munich Haskellers, unfortunately I will miss this meeting since I am only in Munich from 20th December. Anyone up for a "in between the years" meeting (Dec 28 or later?). Cheers, Andreas On 12.12.2013 19:44, Heinrich H?rdegen wrote: > > Dear all, > > on Thursday, 19th of December, we will meet for a Christmas > get-together. The event is organised together with the Munich Lambda > Group. We will have Gl?hwein & Lebkuchen (mulled wine & gingerbread). > Check out the details: > > http://www.meetup.com/Munich-Lambda/events/155219402/ > > I also updated our homepage. New meeting dates are available for next year: > > http://www.haskell-munich.de/dates > > And check out also the links that were sent for our last meeting. Thanks > to everyone who contributed interesting links for our web site during > this year. > > I wish all of you happy Chrismas and a happy new year! > > Heinrich > > _______________________________________________ > high-order-munich mailing list > high-order-munich at fs.lmu.de > https://lists.fs.lmu.de/mailman/listinfo/high-order-munich > -- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel at ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/ From jgbailey at gmail.com Fri Dec 13 16:42:22 2013 From: jgbailey at gmail.com (Justin Bailey) Date: Fri, 13 Dec 2013 08:42:22 -0800 Subject: [Haskell-cafe] Alternatives to ThreadScope? Message-ID: Are there any other GUI tools that do something similar? Maybe something web-based? Justin From simon at banquise.net Fri Dec 13 16:44:33 2013 From: simon at banquise.net (Simon Marechal) Date: Fri, 13 Dec 2013 17:44:33 +0100 Subject: [Haskell-cafe] Writing a Storable instance for a C union In-Reply-To: <87r49gagg9.fsf@karetnikov.org> References: <87r49gagg9.fsf@karetnikov.org> Message-ID: <52AB3971.30305@banquise.net> On 12/13/2013 05:00 PM, Nikita Karetnikov wrote: > Could anyone explain how to write a Storable instance for MyStruct? > (The key field allows to determine the type of a value inside the > union.) You can peek the "key", and then, depending on its value, return a different constructor : data MyStruct = MyStructOne Foo | MyStructFour Integer | MyStructTwenty [Blah] From mark.m.fredrickson at gmail.com Fri Dec 13 16:57:44 2013 From: mark.m.fredrickson at gmail.com (Mark Fredrickson) Date: Fri, 13 Dec 2013 10:57:44 -0600 Subject: [Haskell-cafe] Odd behavior with Num instance for lists (was: f^n for functional iteration) Message-ID: On Fri, Dec 13, 2013 at 8:59 AM, Antonio Nikishaev wrote: > > http://hackage.haskell.org/package/NumInstances > The previous exchange prompted me to whip up a Num instance for lists: instance Num a => Num [a] where negate = fmap negate (+) = zipWith (+) (*) = zipWith (+) fromInteger x = [fromInteger x] abs = fmap abs signum = fmap signum It mostly behaves how one would expect: let a = [1,2,3] ghci> let b = [4,5,6,7] ghci> a + b [5,7,9] ghci> 1 + a [2] I was wondering whey `1 + a` succeeds. At first I thought it could be the `fromInteger` definition, but this explanation were true, I should be able to add integers and doubles freely, which I can't: ghci> fromInteger (1::Integer) + (1.0::Double) 2.0 ghci> (1::Integer) + (1.0::Double) :30:17: Couldn't match expected type `Integer' with actual type `Double' In the second argument of `(+)', namely `(1.0 :: Double)' ... Thanks for enlightening me. -M -------------- next part -------------- An HTML attachment was scrubbed... URL: From bob at redivi.com Fri Dec 13 17:24:56 2013 From: bob at redivi.com (Bob Ippolito) Date: Fri, 13 Dec 2013 09:24:56 -0800 Subject: [Haskell-cafe] Odd behavior with Num instance for lists (was: f^n for functional iteration) In-Reply-To: References: Message-ID: On Fri, Dec 13, 2013 at 8:57 AM, Mark Fredrickson < mark.m.fredrickson at gmail.com> wrote: > On Fri, Dec 13, 2013 at 8:59 AM, Antonio Nikishaev wrote: > >> >> http://hackage.haskell.org/package/NumInstances >> > > The previous exchange prompted me to whip up a Num instance for lists: > > instance Num a => Num [a] where > negate = fmap negate > (+) = zipWith (+) > (*) = zipWith (+) > fromInteger x = [fromInteger x] > abs = fmap abs > signum = fmap signum > > It mostly behaves how one would expect: > > let a = [1,2,3] > ghci> let b = [4,5,6,7] > ghci> a + b > [5,7,9] > ghci> 1 + a > [2] > > I was wondering whey `1 + a` succeeds. At first I thought it could be the > `fromInteger` definition, but this explanation were true, I should be able > to add integers and doubles freely, which I can't: > > ghci> fromInteger (1::Integer) + (1.0::Double) > 2.0 > ghci> (1::Integer) + (1.0::Double) > > :30:17: > Couldn't match expected type `Integer' with actual type `Double' > In the second argument of `(+)', namely `(1.0 :: Double)' > ... > > Thanks for enlightening me. > `1 + a` works for the same reason `1 + (1.0::Double)` works: type inference. `1 + a` in this instance is equivalent to `(1 :: Num [Integer]) + a` which should compile down to something equivalent to `fromInteger 1 + a`. -bob -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Fri Dec 13 18:07:36 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 13 Dec 2013 13:07:36 -0500 Subject: [Haskell-cafe] Alternatives to ThreadScope? In-Reply-To: References: Message-ID: I don't think so. Maybe you should write one using three penny GUI! On Friday, December 13, 2013, Justin Bailey wrote: > Are there any other GUI tools that do something similar? Maybe > something web-based? > > Justin > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From berdario at gmail.com Fri Dec 13 18:15:03 2013 From: berdario at gmail.com (Dario Bertini) Date: Fri, 13 Dec 2013 18:15:03 +0000 Subject: [Haskell-cafe] Odd behavior with Num instance for lists (was: f^n for functional iteration) In-Reply-To: References: Message-ID: I guess you meant (*) = zipWith (*) ? Dumb question: would it be fine to use such an instance in real world application code (in contrast with library code... I guess it would be frowned upon there?) are there any "dangers"... weird interactions? -- xmpp: berdario at gmail.com bitmessage: BM-2cTYXfGiSTsnx3righ6aHcJSWe4MV17jDP gpg fingerprint: 3F8D53518012716C4EEF7DF67B498306B3BF75A0 (used just for signing commits) From danburton.email at gmail.com Fri Dec 13 18:57:10 2013 From: danburton.email at gmail.com (Dan Burton) Date: Fri, 13 Dec 2013 10:57:10 -0800 Subject: [Haskell-cafe] Odd behavior with Num instance for lists (was: f^n for functional iteration) In-Reply-To: References: Message-ID: When using this hack, I prefer `fromInteger x = repeat (fromInteger x)`. That way, you get > 2 * [1,2,3] [2,4,6] It's cute for playing around, but the Num instance for lists is somewhat discouraged in "real" code. -- Dan Burton On Fri, Dec 13, 2013 at 10:15 AM, Dario Bertini wrote: > I guess you meant > > (*) = zipWith (*) > ? > > Dumb question: would it be fine to use such an instance in real world > application code (in contrast with library code... I guess it would be > frowned upon there?) > > are there any "dangers"... weird interactions? > > -- > xmpp: berdario at gmail.com > bitmessage: BM-2cTYXfGiSTsnx3righ6aHcJSWe4MV17jDP > gpg fingerprint: 3F8D53518012716C4EEF7DF67B498306B3BF75A0 (used just > for signing commits) > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From hesselink at gmail.com Fri Dec 13 19:04:40 2013 From: hesselink at gmail.com (Erik Hesselink) Date: Fri, 13 Dec 2013 20:04:40 +0100 Subject: [Haskell-cafe] Odd behavior with Num instance for lists (was: f^n for functional iteration) In-Reply-To: References: Message-ID: On Fri, Dec 13, 2013 at 5:57 PM, Mark Fredrickson wrote: > On Fri, Dec 13, 2013 at 8:59 AM, Antonio Nikishaev wrote: >> >> >> http://hackage.haskell.org/package/NumInstances > > > The previous exchange prompted me to whip up a Num instance for lists: > > instance Num a => Num [a] where > negate = fmap negate > (+) = zipWith (+) > (*) = zipWith (+) > fromInteger x = [fromInteger x] > abs = fmap abs > signum = fmap signum Wouldn't it make more sense to have fromInteger be `repeat . fromInteger`? This would make it an instance for ZipList, not list. You could even give a general instance for applicatives: instance (Num a, Applicative f) => Num (f a) where negate = fmap negate (+) = liftA2 (+) (*) = liftA2 (*) fromInteger = pure . fromInteger abs = fmap abs signum = fmap signum For ZipList this behaves like your instance, except fromInteger produces an infinite list like 'repeat . fromInteger'. The list instance instead computes all possiblities: ghci> [1,2,3] + [4,5,6,7] [5,6,7,8,6,7,8,9,7,8,9,10] Erik From efsubenovex at gmail.com Fri Dec 13 19:28:03 2013 From: efsubenovex at gmail.com (Schell Scivally) Date: Fri, 13 Dec 2013 11:28:03 -0800 Subject: [Haskell-cafe] GLUT, FLGW, FLGW-b In-Reply-To: <3CD0270E-5B09-45BA-AAD3-37BAF8393965@blitzcode.net> References: <3CD0270E-5B09-45BA-AAD3-37BAF8393965@blitzcode.net> Message-ID: I've also used a little bitmap font rendering for my tetris clone. It's very simple and I *think* that the process for using freetype is pretty similar: 1. Render all glyphs of the font into a texture. 2. Draw 2D shapes using the texture. https://github.com/schell/blocks/blob/master/src/Graphics/TextRenderer.hs#L90 On Fri, Dec 13, 2013 at 1:01 AM, Tim C. Schroeder wrote: > I'd agree, use GLFW-b. I'm very happy with it! > > As far as the font rendering is concerned, if all you need is a basic > bitmap font to get some text on the screen, you might be able to use some > code I wrote as a self-contained, drop-in replacement: > > > https://github.com/blitzcode/haskell-gol/blob/master/parallel-glfwb/src/Font.hs > > (Looking at that code now, might want to bracket inside of > withFontTexture. That code was written before Simon Marlow's book taught me > about the wonders of Haskell exception handling...) > > I also wrote a Haskell FT2 binding. It's a very nice library with a decent > API and few dependencies, so that was quite doable. The problem is that FT2 > is really 'just' a glyph rasterizer. All other functionality is either > rudimentary (kerning, glyph mapping) or out of the scope of the library > (ligatures, glyph substitution, OpenType text layout in general). You'll > need another library on top / besides it to get text rendering quality like > in native GUI toolkits or a web browser. Obvious choices would be Pango or > HarfBuzz, but those are more complicated to write a Haskell binding for > (dependencies, C++, etc.). > > A 'just works' solution for platform and giant-GUI-toolkit independent, > high-quality text rendering is sorely missing from the Haskell ecosystem, > as far as I can tell. Doing an FT2 binding and the OpenGL glyph caching / > texture atlas generation etc. is fine, but I'm afraid getting something > like HarfBuzz/Pango up and running exceeds my Cabal-fu, for now. > > Cheers, > Tim > > On Dec 12, 2013, at 11:49 PM, Jason Dagit wrote: > > > I started using it after making the following comparison several years > ago: http://blog.codersbase.com/posts/2011-03-17-picking-gui-library.html > > > > Maybe that analysis is useful to you as well? Just so you know, it's > probably out of date by now, so you might want to double check some of my > claims. For example, the C library for GLFW doesn't use atexit() anymore > (which is a good thing). > > > > Getting back to your question: As I recall, it's better maintained, > lighter weight, and it has better dependencies. With GLFW-b you can use > either OpenGL or OpenGLRaw, whereas GLFW depends directly on OpenGL. The > main drawback, for me, is that GLFW-b doesn't support fonts. > > > > My proposed solution to that was to make a binding to the freetype2 > library (you can find my binding on hackage/github). I never really > finished that project. The binding should work but it's very low level. A > few people have sent me example code they wrote to use it with OpenGL. It's > really something I should finish :) The other cool thing about using > freetype for fonts is that you can easily make it part of a rendering > system that doesn't use any OS rendering libraries (eg., add font support > to a ray-tracer). > > > > Jason > > > > > > On Thu, Dec 12, 2013 at 1:45 PM, Vlad Lopatin > wrote: > > Thanks, Jason > > > > What makes you prefer GLFW-b instead GLFW? > > > > > > On 12 December 2013 19:15, Jason Dagit wrote: > > > > > > > > On Thu, Dec 12, 2013 at 3:05 AM, Sven Panne wrote: > > 2013/12/12 Vlad Lopatin : > > > I keep reading (wiki) that GLUT is a legacy package and some libraries > (e.g. > > > GLFW) are meant to replace it. I also see that some of the GLUT > > > functionality is based on fixed pipeline. What is the current status > of > > > Haskell GLUT? Is it 'to stay' or something that is going to be > deprecated > > > at some point? Should one try replacing it with GLFW(-b) in a > project, if > > > fixed pipeline is not expected to be used? > > > > I think this really depends on your needs: GLUT was designed as a > > simple cross-platform API for OpenGL demos and tutorials, perhaps even > > some programs of medium complexity. > > > > I prefer GLFW-b for cross platform programs for the simple reason that > on windows GLUT requires you to install a DLL and make sure it's in the > path. > > > > I prefer GLFW-b more generally because it's more modern, fully open > source, and under active development. The license for GLUT is open in > practice but it's not a clean open source license. I guess most people use > freeglut instead. > > > > Jason > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Schell Scivally http://blog.efnx.com http://github.com/schell http://twitter.com/schellsan -------------- next part -------------- An HTML attachment was scrubbed... URL: From mark.m.fredrickson at gmail.com Fri Dec 13 20:26:42 2013 From: mark.m.fredrickson at gmail.com (Mark Fredrickson) Date: Fri, 13 Dec 2013 14:26:42 -0600 Subject: [Haskell-cafe] Odd behavior with Num instance for lists (was: f^n for functional iteration) In-Reply-To: References: Message-ID: > > Wouldn't it make more sense to have fromInteger be `repeat . > fromInteger`? This would make it an instance for ZipList, not list. > You could even give a general instance for applicatives: > Very neat. I had tried using the standard Applicative instance for lists, as I wasn't aware of the ZipList newtype. Very useful. On the question of whether any of this is a good idea, I found this discussion that mostly dismissed it based on the handling of literals (which if I understand it, is the source of my original question): http://www.haskell.org/pipermail/libraries/2012-October/018663.html At the end Conal Elliot points to the applicative-numbers package that has a nearly verbatim implementation of Num (f a). -M -------------- next part -------------- An HTML attachment was scrubbed... URL: From madjestic13 at gmail.com Fri Dec 13 21:13:36 2013 From: madjestic13 at gmail.com (Vlad Lopatin) Date: Fri, 13 Dec 2013 22:13:36 +0100 Subject: [Haskell-cafe] GLUT, FLGW, FLGW-b In-Reply-To: References: Message-ID: >> With GLFW-b you can use either OpenGL or OpenGLRaw, whereas GLFW depends >> directly on OpenGL Excuse me, Jason, I do not understand you here. What are you trying to say here? Regards, Vladimir On 12 December 2013 23:49, Jason Dagit wrote: > I started using it after making the following comparison several years > ago: http://blog.codersbase.com/posts/2011-03-17-picking-gui-library.html > > Maybe that analysis is useful to you as well? Just so you know, it's > probably out of date by now, so you might want to double check some of my > claims. For example, the C library for GLFW doesn't use atexit() anymore > (which is a good thing). > > Getting back to your question: As I recall, it's better maintained, > lighter weight, and it has better dependencies. With GLFW-b you can use > either OpenGL or OpenGLRaw, whereas GLFW depends directly on OpenGL. The > main drawback, for me, is that GLFW-b doesn't support fonts. > > My proposed solution to that was to make a binding to the freetype2 > library (you can find my binding on hackage/github). I never really > finished that project. The binding should work but it's very low level. A > few people have sent me example code they wrote to use it with OpenGL. It's > really something I should finish :) The other cool thing about using > freetype for fonts is that you can easily make it part of a rendering > system that doesn't use any OS rendering libraries (eg., add font support > to a ray-tracer). > > Jason > > > On Thu, Dec 12, 2013 at 1:45 PM, Vlad Lopatin wrote: > >> Thanks, Jason >> >> What makes you prefer GLFW-b instead GLFW? >> >> >> On 12 December 2013 19:15, Jason Dagit wrote: >> >>> >>> >>> >>> On Thu, Dec 12, 2013 at 3:05 AM, Sven Panne wrote: >>> >>>> 2013/12/12 Vlad Lopatin : >>>> > I keep reading (wiki) that GLUT is a legacy package and some >>>> libraries (e.g. >>>> > GLFW) are meant to replace it. I also see that some of the GLUT >>>> > functionality is based on fixed pipeline. What is the current status >>>> of >>>> > Haskell GLUT? Is it 'to stay' or something that is going to be >>>> deprecated >>>> > at some point? Should one try replacing it with GLFW(-b) in a >>>> project, if >>>> > fixed pipeline is not expected to be used? >>>> >>>> I think this really depends on your needs: GLUT was designed as a >>>> simple cross-platform API for OpenGL demos and tutorials, perhaps even >>>> some programs of medium complexity. >>> >>> >>> I prefer GLFW-b for cross platform programs for the simple reason that >>> on windows GLUT requires you to install a DLL and make sure it's in the >>> path. >>> >>> I prefer GLFW-b more generally because it's more modern, fully open >>> source, and under active development. The license for GLUT is open in >>> practice but it's not a clean open source license. I guess most people use >>> freeglut instead. >>> >>> Jason >>> >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From dagitj at gmail.com Fri Dec 13 21:26:48 2013 From: dagitj at gmail.com (Jason Dagit) Date: Fri, 13 Dec 2013 13:26:48 -0800 Subject: [Haskell-cafe] GLUT, FLGW, FLGW-b In-Reply-To: References: Message-ID: The GLFW-b package only depends on base and bindings-GLFW. The GLFW package depends on base and the OpenGL Haskell package. I often use the Haskell OpenGLRaw package instead of OpenGL. Mostly because OpenGLRaw matches the C API for OpenGL. That's nice when you're following documentation as it's almost always for the C API. So then I save myself the step of translating from C OpenGL to the Haskell OpenGL package conventions. I could probably still use OpenGLRaw with GLFW, but it's an unnecessary dependency. I also know that GLFW-b installs cleanly just using cabal on Windows, OSX, and Linux. I don't recall if GLFW has that property. I think it might require you to install the C GLFW library separately. I hope that helps, Jason On Fri, Dec 13, 2013 at 1:13 PM, Vlad Lopatin wrote: > >> With GLFW-b you can use either OpenGL or OpenGLRaw, whereas GLFW > depends >> directly on OpenGL > Excuse me, Jason, I do not understand you here. What are you trying to > say here? > > Regards, > Vladimir > > > On 12 December 2013 23:49, Jason Dagit wrote: > >> I started using it after making the following comparison several years >> ago: http://blog.codersbase.com/posts/2011-03-17-picking-gui-library.html >> >> Maybe that analysis is useful to you as well? Just so you know, it's >> probably out of date by now, so you might want to double check some of my >> claims. For example, the C library for GLFW doesn't use atexit() anymore >> (which is a good thing). >> >> Getting back to your question: As I recall, it's better maintained, >> lighter weight, and it has better dependencies. With GLFW-b you can use >> either OpenGL or OpenGLRaw, whereas GLFW depends directly on OpenGL. The >> main drawback, for me, is that GLFW-b doesn't support fonts. >> >> My proposed solution to that was to make a binding to the freetype2 >> library (you can find my binding on hackage/github). I never really >> finished that project. The binding should work but it's very low level. A >> few people have sent me example code they wrote to use it with OpenGL. It's >> really something I should finish :) The other cool thing about using >> freetype for fonts is that you can easily make it part of a rendering >> system that doesn't use any OS rendering libraries (eg., add font support >> to a ray-tracer). >> >> Jason >> >> >> On Thu, Dec 12, 2013 at 1:45 PM, Vlad Lopatin wrote: >> >>> Thanks, Jason >>> >>> What makes you prefer GLFW-b instead GLFW? >>> >>> >>> On 12 December 2013 19:15, Jason Dagit wrote: >>> >>>> >>>> >>>> >>>> On Thu, Dec 12, 2013 at 3:05 AM, Sven Panne wrote: >>>> >>>>> 2013/12/12 Vlad Lopatin : >>>>> > I keep reading (wiki) that GLUT is a legacy package and some >>>>> libraries (e.g. >>>>> > GLFW) are meant to replace it. I also see that some of the GLUT >>>>> > functionality is based on fixed pipeline. What is the current >>>>> status of >>>>> > Haskell GLUT? Is it 'to stay' or something that is going to be >>>>> deprecated >>>>> > at some point? Should one try replacing it with GLFW(-b) in a >>>>> project, if >>>>> > fixed pipeline is not expected to be used? >>>>> >>>>> I think this really depends on your needs: GLUT was designed as a >>>>> simple cross-platform API for OpenGL demos and tutorials, perhaps even >>>>> some programs of medium complexity. >>>> >>>> >>>> I prefer GLFW-b for cross platform programs for the simple reason that >>>> on windows GLUT requires you to install a DLL and make sure it's in the >>>> path. >>>> >>>> I prefer GLFW-b more generally because it's more modern, fully open >>>> source, and under active development. The license for GLUT is open in >>>> practice but it's not a clean open source license. I guess most people use >>>> freeglut instead. >>>> >>>> Jason >>>> >>> >>> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carlo at carlo-hamalainen.net Fri Dec 13 21:50:40 2013 From: carlo at carlo-hamalainen.net (Carlo Hamalainen) Date: Fri, 13 Dec 2013 22:50:40 +0100 Subject: [Haskell-cafe] How to determine the right path to haddock html documentation? Message-ID: <52AB8130.3030903@carlo-hamalainen.net> Hi, I'm writing a patch for ghcmod-vim so that a user can look up the haddock html documentation for a symbol. My code makes three system calls, e.g. to look up "Just" it does: $ ghc-mod info foo.hs Foo Just data Maybe a = ... | Just a -- Defined in `Data.Maybe' $ ghc-pkg find-module Data.Maybe --simple-output haskell2010-1.1.1.0 base-4.6.0.1 $ ghc-pkg field base-4.6.0.1 haddock-html haddock-html: /home/carlo/opt/ghc-7.6.3_build/share/doc/ghc/html/libraries/base-4.6.0.1 Then "Data.Maybe" is changed to Data-Maybe.html" and appended to the haddock-html value. But this procedure doesn't work in general, for example when looking up String: $ ghc-mod info foo.hs Foo String type String = [Char] -- Defined in `GHC.Base' $ ghc-pkg find-module GHC.Base /home/carlo/opt/ghc-7.6.3_build/lib/ghc-7.6.3/package.conf.d base-4.6.0.1 /home/carlo/.ghc/x86_64-linux-7.6.3/package.conf.d $ ghc-pkg field base-4.6.0.1 haddock-html haddock-html: /home/carlo/opt/ghc-7.6.3_build/share/doc/ghc/html/libraries/base-4.6.0.1 $ ls /home/carlo/opt/ghc-7.6.3_build/share/doc/ghc/html/libraries/base-4.6.0.1/GHC-Base.html ls: cannot access /home/carlo/opt/ghc-7.6.3_build/share/doc/ghc/html/libraries/base-4.6.0.1/GHC-Base.html: No such file or directory because the html is in the src subdirectory: $ ls /home/carlo/opt/ghc-7.6.3_build/share/doc/ghc/html/libraries/base-4.6.0.1/src/GHC-Base.html /home/carlo/opt/ghc-7.6.3_build/share/doc/ghc/html/libraries/base-4.6.0.1/src/GHC-Base.html But this isn't even the right place to go, one should look at the Prelude file http://hackage.haskell.org/package/base-4.6.0.1/docs/Prelude.html#t:String which is what Hoogle suggests. How does Hoogle get it right? It looks like haskell-mode for emacs runs into a similar problem: https://github.com/haskell/haskell-mode/blob/master/inf-haskell.el#L734-L740 ------------------------------- (defvar inferior-haskell-ghc-internal-ident-alist ;; FIXME: Fill this table, ideally semi-automatically. '(("GHC.Base.return" . "Control.Monad.return") ("GHC.List" . "Data.List"))) (defun inferior-haskell-map-internal-ghc-ident (ident) "Try to translate some internal GHC identifier to its alter ego in haskell docs." ------------------------------- Thanks, -- Carlo Hamalainen http://carlo-hamalainen.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From roma at ro-che.info Fri Dec 13 22:28:27 2013 From: roma at ro-che.info (Roman Cheplyaka) Date: Sat, 14 Dec 2013 00:28:27 +0200 Subject: [Haskell-cafe] How to determine the right path to haddock html documentation? In-Reply-To: <52AB8130.3030903@carlo-hamalainen.net> References: <52AB8130.3030903@carlo-hamalainen.net> Message-ID: <20131213222827.GA31144@sniper> String is defined in GHC.Base, but GHC.Base is an internal (not exposed) module of the base package; that's why there's no documentation for it. Instead of asking where the thing is defined, you should be asking where it's exported from. In this case, String is re-exported from Prelude. Roman * Carlo Hamalainen [2013-12-13 22:50:40+0100] > Hi, > > I'm writing a patch for ghcmod-vim so that a user can look up the > haddock html documentation for a symbol. My code makes three system > calls, e.g. to look up "Just" it does: > > $ ghc-mod info foo.hs Foo Just > data Maybe a = ... | Just a -- Defined in `Data.Maybe' > > $ ghc-pkg find-module Data.Maybe --simple-output > haskell2010-1.1.1.0 base-4.6.0.1 > > $ ghc-pkg field base-4.6.0.1 haddock-html > haddock-html: > /home/carlo/opt/ghc-7.6.3_build/share/doc/ghc/html/libraries/base-4.6.0.1 > > Then "Data.Maybe" is changed to Data-Maybe.html" and appended to the > haddock-html value. But this procedure doesn't work in general, for > example when looking up String: > > $ ghc-mod info foo.hs Foo String > type String = [Char] -- Defined in `GHC.Base' > > $ ghc-pkg find-module GHC.Base > /home/carlo/opt/ghc-7.6.3_build/lib/ghc-7.6.3/package.conf.d > base-4.6.0.1 > /home/carlo/.ghc/x86_64-linux-7.6.3/package.conf.d > > $ ghc-pkg field base-4.6.0.1 haddock-html > haddock-html: > /home/carlo/opt/ghc-7.6.3_build/share/doc/ghc/html/libraries/base-4.6.0.1 > > $ ls > /home/carlo/opt/ghc-7.6.3_build/share/doc/ghc/html/libraries/base-4.6.0.1/GHC-Base.html > ls: cannot access > /home/carlo/opt/ghc-7.6.3_build/share/doc/ghc/html/libraries/base-4.6.0.1/GHC-Base.html: > No such file or directory > > because the html is in the src subdirectory: > > $ ls > /home/carlo/opt/ghc-7.6.3_build/share/doc/ghc/html/libraries/base-4.6.0.1/src/GHC-Base.html > > /home/carlo/opt/ghc-7.6.3_build/share/doc/ghc/html/libraries/base-4.6.0.1/src/GHC-Base.html > > But this isn't even the right place to go, one should look at the > Prelude file > > http://hackage.haskell.org/package/base-4.6.0.1/docs/Prelude.html#t:String > > which is what Hoogle suggests. How does Hoogle get it right? > > It looks like haskell-mode for emacs runs into a similar problem: > > https://github.com/haskell/haskell-mode/blob/master/inf-haskell.el#L734-L740 > > ------------------------------- > (defvar inferior-haskell-ghc-internal-ident-alist > ;; FIXME: Fill this table, ideally semi-automatically. > '(("GHC.Base.return" . "Control.Monad.return") > ("GHC.List" . "Data.List"))) > > (defun inferior-haskell-map-internal-ghc-ident (ident) > "Try to translate some internal GHC identifier to its alter ego in > haskell docs." > ------------------------------- > > Thanks, > > -- > Carlo Hamalainen > http://carlo-hamalainen.net > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: Digital signature URL: From nikita at karetnikov.org Fri Dec 13 23:24:29 2013 From: nikita at karetnikov.org (Nikita Karetnikov) Date: Sat, 14 Dec 2013 03:24:29 +0400 Subject: [Haskell-cafe] Writing a Storable instance for a C union In-Reply-To: <52AB3971.30305@banquise.net> (Simon Marechal's message of "Fri, 13 Dec 2013 17:44:33 +0100") References: <87r49gagg9.fsf@karetnikov.org> <52AB3971.30305@banquise.net> Message-ID: <8761qs2v2q.fsf@karetnikov.org> > You can peek the "key", and then, depending on its value, return a > different constructor : > data MyStruct = MyStructOne Foo > | MyStructFour Integer > | MyStructTwenty [Blah] OK, but how can I pick one of the union fields? Also, I?d rather change MyStruct to Union in the above since I already defined MyStruct, which has a Storable instance that looks like so (omitting sizeOf, alignment, and poke): instance Storable MyStruct where peek p = do v0 <- peekByteOff p 0 return $ MyStruct v0 This allows to get the value of key, and I could change it to get one of the union fields: instance Storable MyStruct where peek p = do v0 <- peekByteOff p 0 v1 <- peekByteOff p 4 return $ MyStruct v0 v1 But that would require to define a Storable instance for the Union type, which is exactly the point of the thread. How can I do so? (Note that Foo, Word64, and (Ptr a) are instances of Storable themselves.) The other question that remains unanswered is how to make such code portable. Should I rely on hsc2hs to determine things like sizeOf and alignment? -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 835 bytes Desc: not available URL: From simon at joyful.com Sat Dec 14 03:47:44 2013 From: simon at joyful.com (Simon Michael) Date: Fri, 13 Dec 2013 19:47:44 -0800 Subject: [Haskell-cafe] ANN: hledger 0.22 Message-ID: <1386992864.13445.59458157.12E3C40E@webmail.messagingengine.com> Hi all. I have released hledger and hledger-web 0.22. hledger is a command-line tool and haskell library for tracking financial transactions, which are stored in a human-readable plain text format. In addition to reporting, it can also help you record new transactions, or convert CSV data from your bank. Add-on packages include hledger-web (providing a web interface), hledger-irr and hledger-interest. hledger is inspired by and compatible with John Wiegley's Ledger. For more, see http://hledger.org . Install it: cabal update; cabal install hledger [hledger-web] For more installation help, see http://hledger.org/MANUAL.html#installing . Or, sponsor a ready-to-run binary for your platform: http://hledger.org/DOWNLOAD.html . Release notes (http://hledger.org/NEWS.html#hledger-0.22): **New:** - balance: with a reporting interval (monthly, yearly etc.), the [balance command](MANUAL.html#balance) will now show a multi-column report, showing either the per-period changes in balance (by default), the period ending balances starting from zero (`--cumulative`), or the actual period ending balances (`--historical`). A more detailed specification of the balance command's behaviour has been added to Hledger.Cli.Balance. - csv: rules files can now include other rules files, useful for factoring out common rules - queries: `sym:REGEXP` matches commodity symbols - register: `--average/-A` shows a running average, like ledger - in period expressions, `-` (hyphen) can be used as a more compact synonym for `from` and `to`. Eg: `-p 2012/12/1-2013/2/1` or `date:aug-`. - the add-on script examples in extra/ have been updated; get the hledger source and add .../hledger/extra/ to your PATH to make them available. They include: hledger-accountnames.hs - print account names hledger-balance-csv.hs - print a balance report as CSV hledger-equity.hs - print an entry matching all account balances hledger-print-unique.hs - print only journal entries unique descriptions hledger-register-csv.hs - print a register report as CSV **Improved:** - balancesheet: now shows just assets and liabilities, not equity - print: comment positions (same line or next line) are now preserved - queries: `amt` now uses the = operator by default, eg `amt:50` is equivalent to `amt:=50` - command line processing has been overhauled and made more consistent, and now has tests and debug output. More flags now work both before and after COMMAND: `-f`, `--rule-file`, `--alias`, `--help`, `--debug`, `--version`. Command line help, command aliases, API docs and code have been improved. - `--debug` now takes an optional numeric argument to set the debug level higher than 1, for more verbose debug output in a few cases. **Fixed:** - csv: CSV data containing non-ascii characters is now supported - build with latest versions of dependencies (text, warp, http-conduit etc.) **Release contributors:** Marko Koci?, Max Bolingbroke, and a big welcome to first-time committer John Wiegley! :) There's a rumour that a 1.0 release could be next, depending on how this one fares. All feedback welcome. Best! - Simon From simon at banquise.net Sat Dec 14 07:58:04 2013 From: simon at banquise.net (Simon Marechal) Date: Sat, 14 Dec 2013 08:58:04 +0100 Subject: [Haskell-cafe] Writing a Storable instance for a C union In-Reply-To: <8761qs2v2q.fsf@karetnikov.org> References: <87r49gagg9.fsf@karetnikov.org> <52AB3971.30305@banquise.net> <8761qs2v2q.fsf@karetnikov.org> Message-ID: <52AC0F8C.3040208@banquise.net> On 12/14/2013 12:24 AM, Nikita Karetnikov wrote: > instance Storable MyStruct where peek p = do v0 <- peekByteOff p 0 > v1 <- peekByteOff p 4 return $ MyStruct v0 v1 > > But that would require to define a Storable instance for the Union > type, which is exactly the point of the thread. How can I do so? > (Note that Foo, Word64, and (Ptr a) are instances of Storable > themselves.) It's as simple as : peek p = do v0 <- peekByteOff p 0 case v0 of 1 -> MyStruct <$> peekByteOff p 4 2 -> FooStruct <$> peek... But this function can only have a single type, hence my suggestion that you should create a union type to represent the C union : type SomeUnion = MyStruct Byte | FooStruct Integer | ... From eijiro.sumii at gmail.com Sat Dec 14 10:21:15 2013 From: eijiro.sumii at gmail.com (Eijiro Sumii) Date: Sat, 14 Dec 2013 19:21:15 +0900 (JST) Subject: [Haskell-cafe] Deadline extended: FLOPS 2014 call for papers In-Reply-To: References: Message-ID: <20131214.192115.41652173.sumii@ecei.tohoku.ac.jp> [Because of a number of requests, the submission deadline is extended again to December the 25th, 23:59 UTC (but please register your title and abstract as soon as possible on EasyChair).] Call For Papers =============== Twelfth International Symposium on Functional and Logic Programming (FLOPS 2014) June 4-6, 2014 Kanazawa, Japan http://www.jaist.ac.jp/flops2014/ ---------------------------------------------------------------------- - Journal publications in JFP (Jounral of Functional Programming) and TPLP (Theory and Practice of Logic Programming) are planned (see below). - Hyakumangoku Matsuri ( https://www.google.com/search?q=hyakumangoku%20matsuri&tbm=isch ) is scheduled *just* after FLOPS 2014. ---------------------------------------------------------------------- FLOPS is a forum for research on all issues concerning declarative programming, including functional programming and logic programming, and aims to promote cross-fertilization and integration between the two paradigms. Previous FLOPS meetings were held at Fuji Susono (1995), Shonan Village (1996), Kyoto (1998), Tsukuba (1999), Tokyo (2001), Aizu (2002), Nara (2004), Fuji Susono (2006), Ise (2008), Sendai (2010), and Kobe (2012). Topics ====== FLOPS solicits original papers in all areas of functional and logic programming, including (but not limited to): - Language issues: language design and constructs, programming methodology, integration of paradigms, interfacing with other languages, type systems, constraints, concurrency and distributed computing. - Foundations: logic and semantics, rewrite systems and narrowing, type theory, proof systems. - Implementation issues: compilation techniques, memory management, program analysis and transformation, partial evaluation, parallelism. - Applications: case studies, real-world applications, graphical user interfaces, Internet applications, XML, databases, formal methods and model checking. The proceedings will be published as an LNCS volume. The proceedings of the previous meetings (FLOPS 1999, 2001, 2002, 2004, 2006, 2008, 2010, and 2012) were published as LNCS 1722, 2024, 2441, 2998, 3945, 4989, 6009, and 7294. PC Co-Chairs ============ Michael Codish (Ben-Gurion University of the Negev) Eijiro Sumii (Tohoku University) PC Members ========== Lars Birkedal (Aarhus University) Michael Codish (Ben-Gurion University of the Negev) [co-chair] Marina De Vos (University of Bath) Moreno Falaschi (Universita degli studi di Udine) Carsten Fuhs (University College London) John Gallagher (Roskilde Universitet / IMDEA Software Institute) Samir Genaim (Universidad Complutense de Madrid) Laura Giordano (Universita del Piemonte Orientale) Ichiro Hasuo (University of Tokyo) Fritz Henglein (University of Copenhagen) Andy King (University of Kent) Oleg Kiselyov Vitaly Lagoon (MathWorks) Shin-Cheng Mu (Academia Sinica) Keiko Nakata (Institute of Cybernetics at Tallinn University of Technology) Luke Ong (University of Oxford) Peter Schachte (University of Melbourne) Takehide Soh (Kobe University) Eijiro Sumii (Tohoku University) [co-chair] Tachio Terauchi (Nagoya University) Joost Vennekens (KU Leuven) Janis Voigtlaender (Universitaet Bonn) Stephanie Weirich (University of Pennsylvania) Local Chair =========== Yuki Chiba (JAIST) Submission ========== Submissions must be unpublished and not submitted for publication elsewhere. Work that already appeared in unpublished or informally published workshops proceedings may be submitted. See also ACM SIGPLAN Republication Policy: http://www.sigplan.org/Resources/Policies/Republication Submissions should fall into one of the following categories: - Regular research papers: they should describe new results and will be judged on originality, correctness, and significance. - System descriptions: they should contain a link to a working system and will be judged on originality, usefulness, and design. - Declarative pearls: new and excellent declarative programs or theories with illustrative applications. System descriptions and declarative pearls must be explicitly marked as such in the title. Submissions must be written in English and can be up to 15 pages long including references, though pearls are typically shorter. Authors are required to use LaTeX2e and the Springer llncs class file, available at: http://www.springer.de/comp/lncs/authors.html Regular research papers should be supported by proofs and/or experimental results. In case of lack of space, this supporting information should be made accessible otherwise (e.g., a link to a Web page, or an appendix). Papers should be submitted electronically at: https://www.easychair.org/conferences/?conf=flops2014 Important Dates =============== Submission deadline (EXTENDED): December 25, 2013 (23:59 UTC) Author notification: February 10, 2014 Camera-ready copy: March 7, 2014 Journal Publication =================== - Journal of Functional Programming and - Theory and Practice of Logic Programming 2-4 of the best papers in each of the two areas: Functional Programming and Logic Programming, will be invited for inclusion in a designated FLOPS section within each of the two journals. The Theory and Practice of Logic Programming papers will appear as "Rapid Publications". All of the these submissions are expected to represent high-quality revisions and extensions of the selected FLOPS papers and will be reviewed under the standard criteria of each journal. Venue ===== Main Hall, Ishikawa Prefectural Museum of Art, 2-1 Dewa-machi, Kanazawa, Ishikawa 920-0963 JAPAN. Some Previous FLOPS =================== FLOPS 2012, Kobe: http://www.org.kobe-u.ac.jp/flops2012/ FLOPS 2010, Sendai: http://www.kb.ecei.tohoku.ac.jp/flops2010/ FLOPS 2008, Ise: http://www.math.nagoya-u.ac.jp/~garrigue/FLOPS2008/ Sponsor ======= Japan Society for Software Science and Technology (JSSST), Special Interest Group on Programming and Programming Languages (SIG-PPL) In Cooperation With =================== ACM SIGPLAN Asian Association for Foundation of Software (AAFS) Association for Logic Programming (ALP) From apfelmus at quantentunnel.de Sat Dec 14 10:35:04 2013 From: apfelmus at quantentunnel.de (Heinrich Apfelmus) Date: Sat, 14 Dec 2013 11:35:04 +0100 Subject: [Haskell-cafe] Alternatives to ThreadScope? In-Reply-To: References: Message-ID: Carter Schonwald wrote: > I don't think so. Maybe you should write one using three penny GUI! Threepenny-gui, the reasonable alternative to hard-to-install-gui. http://www.haskell.org/haskellwiki/Threepenny-gui Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com From hoerdegen at funktional.info Sat Dec 14 11:32:26 2013 From: hoerdegen at funktional.info (=?ISO-8859-1?Q?Heinrich_H=F6rdegen?=) Date: Sat, 14 Dec 2013 12:32:26 +0100 Subject: [Haskell-cafe] Munich Haskell Holiday Meeting In-Reply-To: <52AB33B4.5090004@ifi.lmu.de> References: <52AA0411.9010106@funktional.info> <52AB33B4.5090004@ifi.lmu.de> Message-ID: <52AC41CA.5010204@funktional.info> Dear all, there have been questions for a holiday meeting for the Munich Haskell user group. I set up a doodle. Follow the link and subscribe, if you want to join: http://doodle.com/fq3xv3dwhwxswy7s See you soon, Heinrich Am 13.12.2013 17:20, schrieb Andreas Abel: > Dear Munich Haskellers, > > unfortunately I will miss this meeting since I am only in Munich from > 20th December. > > Anyone up for a "in between the years" meeting (Dec 28 or later?). > > Cheers, > Andreas > > On 12.12.2013 19:44, Heinrich H?rdegen wrote: >> >> Dear all, >> >> on Thursday, 19th of December, we will meet for a Christmas >> get-together. The event is organised together with the Munich Lambda >> Group. We will have Gl?hwein & Lebkuchen (mulled wine & gingerbread). >> Check out the details: >> >> http://www.meetup.com/Munich-Lambda/events/155219402/ >> >> I also updated our homepage. New meeting dates are available for next >> year: >> >> http://www.haskell-munich.de/dates >> >> And check out also the links that were sent for our last meeting. Thanks >> to everyone who contributed interesting links for our web site during >> this year. >> >> I wish all of you happy Chrismas and a happy new year! >> >> Heinrich >> >> _______________________________________________ >> high-order-munich mailing list >> high-order-munich at fs.lmu.de >> https://lists.fs.lmu.de/mailman/listinfo/high-order-munich >> > > -- -- Funktionale Programmierung Dr. Heinrich H?rdegen Gutenbergstr. 26 80638 M?nchen FON: +49 (89) 12 59 79 49 FAX: +49 (89) 12 59 79 50 hoerdegen at funktional.info www.funktional.info -- From roma at ro-che.info Sat Dec 14 12:01:42 2013 From: roma at ro-che.info (Roman Cheplyaka) Date: Sat, 14 Dec 2013 14:01:42 +0200 Subject: [Haskell-cafe] Proposal: move ansi-terminal to haskell-pkg-janitors Message-ID: <20131214120142.GA23146@sniper> ansi-terminal is a useful and important package providing colorful console output. It has 50 direct reverse dependencies, and a huge number of indirect ones (through testing frameworks, for example). ansi-terminal was written and maintained by Max Bolingbroke, but he doesn't seem to be active in the Haskell community anymore. The package itself hasn't been updated for a year. Unless he (or someone else) objects, I propose to move ansi-terminal under maintainership of the haskell-pkg-janitors group. Is there any venue for haskell-pkg-janitors, such as a mailing list or IRC channel? Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: Digital signature URL: From carlo at carlo-hamalainen.net Sat Dec 14 13:52:04 2013 From: carlo at carlo-hamalainen.net (Carlo Hamalainen) Date: Sat, 14 Dec 2013 14:52:04 +0100 Subject: [Haskell-cafe] How to determine the right path to haddock html documentation? In-Reply-To: <20131213222827.GA31144@sniper> References: <52AB8130.3030903@carlo-hamalainen.net> <20131213222827.GA31144@sniper> Message-ID: <52AC6284.1080103@carlo-hamalainen.net> On 13/12/13 23:28, Roman Cheplyaka wrote: > String is defined in GHC.Base, but GHC.Base is an internal (not exposed) > module of the base package; that's why there's no documentation for it. Right. > Instead of asking where the thing is defined, you should be asking where > it's exported from. In this case, String is re-exported from Prelude. To do this will I have to dig into the GHC API? Perhaps I could extract the imports from a file, then use parseImportDecl to parse them, and then do interactive imports, using IIDecl (ImportDecl RdrName) Bring the exports of a particular module (filtered by an import decl) into scope until the name appears in scope, checking with getNamesInScope? I haven't used the GHC API before so I may be barking up the wrong tree. Thanks, -- Carlo Hamalainen http://carlo-hamalainen.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From roma at ro-che.info Sat Dec 14 14:02:15 2013 From: roma at ro-che.info (Roman Cheplyaka) Date: Sat, 14 Dec 2013 16:02:15 +0200 Subject: [Haskell-cafe] How to determine the right path to haddock html documentation? In-Reply-To: <52AC6284.1080103@carlo-hamalainen.net> References: <52AB8130.3030903@carlo-hamalainen.net> <20131213222827.GA31144@sniper> <52AC6284.1080103@carlo-hamalainen.net> Message-ID: <20131214140215.GA970@sniper> * Carlo Hamalainen [2013-12-14 14:52:04+0100] > On 13/12/13 23:28, Roman Cheplyaka wrote: > > String is defined in GHC.Base, but GHC.Base is an internal (not exposed) > > module of the base package; that's why there's no documentation for it. > > Right. > > > Instead of asking where the thing is defined, you should be asking where > > it's exported from. In this case, String is re-exported from Prelude. > > To do this will I have to dig into the GHC API? Yes. haskell-names can also do this (it's used in halberd to solve a similar task: https://github.com/haskell-suite/halberd) But since ghc-mod is based on the GHC API, you should probably stick to it. I'm not familiar with the GHC API either; hopefully, someone else will help you here. Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: Digital signature URL: From nikita at karetnikov.org Sat Dec 14 16:46:59 2013 From: nikita at karetnikov.org (Nikita Karetnikov) Date: Sat, 14 Dec 2013 20:46:59 +0400 Subject: [Haskell-cafe] Writing a Storable instance for a C union In-Reply-To: <52AC0F8C.3040208@banquise.net> (Simon Marechal's message of "Sat, 14 Dec 2013 08:58:04 +0100") References: <87r49gagg9.fsf@karetnikov.org> <52AB3971.30305@banquise.net> <8761qs2v2q.fsf@karetnikov.org> <52AC0F8C.3040208@banquise.net> Message-ID: <87zjo3mlbw.fsf@karetnikov.org> > It's as simple as : > peek p = do > v0 <- peekByteOff p 0 > case v0 of > 1 -> MyStruct <$> peekByteOff p 4 > 2 -> FooStruct <$> peek... > But this function can only have a single type, hence my suggestion > that you should create a union type to represent the C union : > type SomeUnion = MyStruct Byte | FooStruct Integer | ... Yes, but I also want to poke, so SomeUnion must be an instance of Storable. Could you show how to define it properly or provide a workaround? I?m attaching some code, which is in the public domain, to demonstrate the problem. It was generated using c2hsc and hsc2hs. The lines marked with XXX were either modified or added by me. -------------- next part -------------- A non-text attachment was scrubbed... Name: Test.hs Type: text/x-haskell Size: 2766 bytes Desc: not available URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 835 bytes Desc: not available URL: From simon at banquise.net Sat Dec 14 18:22:12 2013 From: simon at banquise.net (Simon Marechal) Date: Sat, 14 Dec 2013 19:22:12 +0100 Subject: [Haskell-cafe] Writing a Storable instance for a C union In-Reply-To: <87zjo3mlbw.fsf@karetnikov.org> References: <87r49gagg9.fsf@karetnikov.org> <52AB3971.30305@banquise.net> <8761qs2v2q.fsf@karetnikov.org> <52AC0F8C.3040208@banquise.net> <87zjo3mlbw.fsf@karetnikov.org> Message-ID: <52ACA1D4.7030407@banquise.net> On 12/14/2013 05:46 PM, Nikita Karetnikov wrote: > Yes, but I also want to poke, so SomeUnion must be an instance of > Storable. Could you show how to define it properly or provide a > workaround? You do not need to store the "key", or have an additional C'MyStruct data type, as you already have this information in Haskell : data SomeUnion = UnionFoo C'Foo | UnionWord64 Word64 | UnionVoid (Ptr ()) deriving (Show, Eq) instance Storable SomeUnion where sizeOf _ = 12 alignment _ = 4 peek p = do v0 <- peekByteOff p 0 case v0 of 1 -> UnionFoo `fmap` peekByteOff p 4 4 -> UnionWord64 `fmap` peekByteOff p 4 20 -> UnionVoid `fmap` peekByteOff p 4 _ -> fail "you should probably handle this case" poke p (UnionFoo v1) = pokeByteOff p 0 1 >> pokeByteOff p 4 v1 poke p (UnionWord64 v1) = pokeByteOff p 4 1 >> pokeByteOff p 4 v1 poke p (UnionVoid v1) = pokeByteOff p 20 1 >> pokeByteOff p 4 v1 From difrumin at gmail.com Sat Dec 14 18:51:30 2013 From: difrumin at gmail.com (Daniil Frumin) Date: Sat, 14 Dec 2013 22:51:30 +0400 Subject: [Haskell-cafe] Cabal sandbox status in your ZSH prompt Message-ID: Hi everyone, I made a simple script for my zsh setup that allows me to see whether am I in a cabalized sandbox environment or not. On my machine it looks like this: The script itself is here: The result of checking for the sandbox is cached, which---as I've realized only moments ago---is probably unnecessary; it updates only when the user performs a `cabal` command or changes a directory. -- Sincerely yours, -- Daniil Frumin From simon at joyful.com Sun Dec 15 03:50:30 2013 From: simon at joyful.com (Simon Michael) Date: Sat, 14 Dec 2013 19:50:30 -0800 Subject: [Haskell-cafe] ANN: hledger 0.22 In-Reply-To: References: <1386992864.13445.59458157.12E3C40E@webmail.messagingengine.com> Message-ID: <1387079430.31318.59728549.7EBD75D0@webmail.messagingengine.com> It works for me in a fresh cabal-dev package db, which I think yours is not, right ? Installs into an already-populated package db are more troublesome than usual right now because of the recent major version bumps to text, wai, warp, http-conduit etc. On Sat, Dec 14, 2013, at 10:27 AM, Marko Koci? wrote: I have build problems again after pulling from git. ~/src/hledger$ cabal-dev install ./hledger ./hledger-lib/ ./hledger-web/ Resolving dependencies... cabal: Could not resolve dependencies: trying: hledger-0.22 (user goal) trying: utf8-string-0.3.7 (dependency of hledger-0.22) rejecting: utf8-string-0.3.7:+bytestring-in-base (conflict: base==4.6.0.1/installed-ced..., utf8-string-0.3.7:bytestring-in-base => base>=2.0 && <2.2) trying: utf8-string-0.3.7:-bytestring-in-base trying: bytestring-0.10.0.2/installed-0b6... (dependency of utf8-string-0.3.7:-bytestring-in-base) trying: text-1.0.0.0 (dependency of hledger-0.22) trying: shakespeare-text-1.0.0.10 (dependency of hledger-0.22) trying: shakespeare-1.2.0.3 (dependency of shakespeare-text-1.0.0.10) next goal: system-fileio (dependency of shakespeare-1.2.0.3) rejecting: system-fileio-0.3.11, 0.3.10 (conflict: text==1.0.0.0, system-fileio => text>=0.7.1 && <0.12) rejecting: system-fileio-0.3.9, 0.3.8, 0.3.7, 0.3.6, 0.3.5, 0.3.4, 0.3.3, 0.3.2.1, 0.3.2, 0.3.1, 0.3 (conflict: bytestring==0.10.0.2/installed-0b6..., system-fileio => bytestring>=0.9 && <0.10) rejecting: system-fileio-0.2.7, 0.2.6, 0.2.5, 0.2.4, 0.2.3, 0.2.2.1, 0.2.2, 0.2.1, 0.2, 0.1.1, 0.1 (conflict: shakespeare => system-fileio>=0.3) Backjump limit reached (change with --max-backjumps). marko at monet:~/src/hledger$ ghc --version The Glorious Glasgow Haskell Compilation System, version 7.6.3 -- -- You received this message because you are subscribed to the Google Groups hledger group. To post to this group, send email to hledger at googlegroups.com. To unsubscribe from this group, send email to hledger+unsubscribe at googlegroups.com. For more options, visit this group at [1]https://groups.google.com/d/forum/hledger?hl=en --- You received this message because you are subscribed to the Google Groups "hledger" group. To unsubscribe from this group and stop receiving emails from it, send an email to hledger+unsubscribe at googlegroups.com. For more options, visit [2]https://groups.google.com/groups/opt_out. References 1. https://groups.google.com/d/forum/hledger?hl=en 2. https://groups.google.com/groups/opt_out -------------- next part -------------- An HTML attachment was scrubbed... URL: From gtener at gmail.com Sun Dec 15 09:29:32 2013 From: gtener at gmail.com (=?UTF-8?Q?Krzysztof_Skrz=C4=99tnicki?=) Date: Sun, 15 Dec 2013 10:29:32 +0100 Subject: [Haskell-cafe] Cabal sandbox status in your ZSH prompt In-Reply-To: References: Message-ID: Looks great, thanks for sharing! I think I'll give it a try. All best, Krzysztof Skrz?tnicki On Sat, Dec 14, 2013 at 7:51 PM, Daniil Frumin wrote: > Hi everyone, I made a simple script for my zsh setup that allows me to > see whether am I in a cabalized sandbox environment or not. > > On my machine it looks like this: > > The script itself is here: > > The result of checking for the sandbox is cached, which---as I've > realized only moments ago---is probably unnecessary; it updates only > when the user performs a `cabal` command or changes a directory. > > -- > Sincerely yours, > -- Daniil Frumin > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From temporalabstraction at gmail.com Sun Dec 15 11:39:20 2013 From: temporalabstraction at gmail.com (EatsKittens) Date: Sun, 15 Dec 2013 12:39:20 +0100 Subject: [Haskell-cafe] RFC: Top level mutable state in terms of pure-function initialization? Message-ID: A pure function (enumToIORef :: (Enum a, Defaultable b) => a -> IORef b). This function returns referentially transparently an IORef as a function of its "seed" with the guarantee that the IORef returned is identical if and only if the seed is. This function can be used to implement top level mutable state in a module. The module can specifically create an enumerated type for this and not export it, thereby removing any possibility of another module passing the seed type and conflicting. The Defaultable class is added in this case to implement only a single method (defaultValue :: Defaultable a => a -> a). This is conceptionally the 'simplest' value of the type, such as the empty list, the number 0, False, the null character &c. The IORef returned by enumToIORef would be initialized before being written to to this specific default value of its type. This approach is chosen because it is impossible to initialize it to user specified value because enumToIORef can be called twice with the same seed but a different initial value. In the alternative it is also possible to do without the default value and say the IORef returned is the same if and only if the seed and the initial value given are the same. Allowing the function to remain referentially transparent as well. This would probably require for good semantics the underlying type of the IORef to be a member of EQ...? All this would of course require that newIORef and enumToIORef never produce the same IORef. Aside its limitations of the type IORef's initialized with this method can carry, I do believe they cover the vast majority of use cases of top level mutable state? Caveats? -------------- next part -------------- An HTML attachment was scrubbed... URL: From headprogrammingczar at gmail.com Sun Dec 15 13:00:17 2013 From: headprogrammingczar at gmail.com (Joe Quinn) Date: Sun, 15 Dec 2013 08:00:17 -0500 Subject: [Haskell-cafe] RFC: Top level mutable state in terms of pure-function initialization? In-Reply-To: References: Message-ID: <52ADA7E1.8020109@gmail.com> This has the same issue as just using a top-level (IORef b). Assume two use cases: let x = enumToIORef 5 in (x, x) (enumToIORef 5, enumToIORef 5) It's "obvious" in the first case that you have one ref that is used twice, while it is "obvious" in the second case that you have two refs containing the same value. But this breaks the rule that (let x = y in f x) = (f y), because the left is a single ref while the right is two refs. There's likely other problems with it too, but this is what stands out to me. On 12/15/2013 6:39 AM, EatsKittens wrote: > A pure function (enumToIORef :: (Enum a, Defaultable b) => a -> IORef > b). This function returns referentially transparently an IORef as a > function of its "seed" with the guarantee that the IORef returned is > identical if and only if the seed is. This function can be used to > implement top level mutable state in a module. The module can > specifically create an enumerated type for this and not export it, > thereby removing any possibility of another module passing the seed > type and conflicting. > > The Defaultable class is added in this case to implement only a single > method (defaultValue :: Defaultable a => a -> a). This is > conceptionally the 'simplest' value of the type, such as the empty > list, the number 0, False, the null character &c. The IORef returned > by enumToIORef would be initialized before being written to to this > specific default value of its type. This approach is chosen because it > is impossible to initialize it to user specified value because > enumToIORef can be called twice with the same seed but a different > initial value. > > In the alternative it is also possible to do without the default value > and say the IORef returned is the same if and only if the seed and the > initial value given are the same. Allowing the function to remain > referentially transparent as well. This would probably require for > good semantics the underlying type of the IORef to be a member of EQ...? > > All this would of course require that newIORef and enumToIORef never > produce the same IORef. > > Aside its limitations of the type IORef's initialized with this method > can carry, I do believe they cover the vast majority of use cases of > top level mutable state? > > Caveats? > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- An HTML attachment was scrubbed... URL: From roma at ro-che.info Sun Dec 15 13:38:53 2013 From: roma at ro-che.info (Roman Cheplyaka) Date: Sun, 15 Dec 2013 15:38:53 +0200 Subject: [Haskell-cafe] RFC: Top level mutable state in terms of pure-function initialization? In-Reply-To: References: Message-ID: <20131215133853.GA8304@sniper> 1. Well, that creates a loophole in the type system: let x :: IORef Int x = enumToIORef 0 y :: IORef Bool y = enumToIORef 0 in writeIORef x (5 :: Int) >> (readIORef y :: IO Bool) 2. There's also a less obvious loophole with your Defaultable version: let x :: Defaultable a => IORef a x = enumToIORef 0 in writeIORef x (5 :: Int) >> (readIORef x :: IO Bool) 3. In your default-less version there's a problem of doing this: x = enumToIORef 0 True y = enumToIORef 0 False Now, x and y presumably refer to the same IORef, but the initial contents of that IORef will depend on whether you access it through x or y. 4. Finally, the implementation of enumToIORef can only inspect it by converting to Int, and cannot distinguish different enums that correspond to the same number. This last problem can be solved by adding a Typeable constraint, because TypeReps carry the information about where (module, package) the type was defined. Roman * EatsKittens [2013-12-15 12:39:20+0100] > A pure function (enumToIORef :: (Enum a, Defaultable b) => a -> IORef b). > This function returns referentially transparently an IORef as a function of > its "seed" with the guarantee that the IORef returned is identical if and > only if the seed is. This function can be used to implement top level > mutable state in a module. The module can specifically create an enumerated > type for this and not export it, thereby removing any possibility of > another module passing the seed type and conflicting. > > The Defaultable class is added in this case to implement only a single > method (defaultValue :: Defaultable a => a -> a). This is conceptionally > the 'simplest' value of the type, such as the empty list, the number 0, > False, the null character &c. The IORef returned by enumToIORef would be > initialized before being written to to this specific default value of its > type. This approach is chosen because it is impossible to initialize it to > user specified value because enumToIORef can be called twice with the same > seed but a different initial value. > > In the alternative it is also possible to do without the default value and > say the IORef returned is the same if and only if the seed and the initial > value given are the same. Allowing the function to remain referentially > transparent as well. This would probably require for good semantics the > underlying type of the IORef to be a member of EQ...? > > All this would of course require that newIORef and enumToIORef never > produce the same IORef. > > Aside its limitations of the type IORef's initialized with this method can > carry, I do believe they cover the vast majority of use cases of top level > mutable state? > > Caveats? > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: Digital signature URL: From temporalabstraction at gmail.com Sun Dec 15 14:05:40 2013 From: temporalabstraction at gmail.com (EatsKittens) Date: Sun, 15 Dec 2013 15:05:40 +0100 Subject: [Haskell-cafe] RFC: Top level mutable state in terms of pure-function initialization? In-Reply-To: <20131215133853.GA8304@sniper> References: <20131215133853.GA8304@sniper> Message-ID: 1. Well, since x and y are not of the same type they would in this case contain a different IORef. The read in this case would read False since y is initialized to false as the default of Bool. 2. In this example it would again be two different IO refs since the type is different. It would again on demand create a different IORef for Int and Bool. 3. No, they refer to a different one as I said, the default-less version creates the IORef to be unique if and only if both the seed and initialization are the same. 4. Agreed, I overlooked that not all enum instances are typable. (I believe they also need to be an instance of EQ?) On 15 December 2013 14:38, Roman Cheplyaka wrote: > 1. Well, that creates a loophole in the type system: > > let > x :: IORef Int > x = enumToIORef 0 > > y :: IORef Bool > y = enumToIORef 0 > in writeIORef x (5 :: Int) >> (readIORef y :: IO Bool) > > 2. There's also a less obvious loophole with your Defaultable version: > > let > x :: Defaultable a => IORef a > x = enumToIORef 0 > in writeIORef x (5 :: Int) >> (readIORef x :: IO Bool) > > 3. In your default-less version there's a problem of doing this: > > x = enumToIORef 0 True > y = enumToIORef 0 False > > Now, x and y presumably refer to the same IORef, but the initial > contents of that IORef will depend on whether you access it through x or > y. > > 4. Finally, the implementation of enumToIORef can only inspect it by > converting to Int, and cannot distinguish different enums that > correspond to the same number. > > This last problem can be solved by adding a Typeable constraint, > because TypeReps carry the information about where (module, package) the > type was defined. > > Roman > > * EatsKittens [2013-12-15 12:39:20+0100] > > A pure function (enumToIORef :: (Enum a, Defaultable b) => a -> IORef b). > > This function returns referentially transparently an IORef as a function > of > > its "seed" with the guarantee that the IORef returned is identical if and > > only if the seed is. This function can be used to implement top level > > mutable state in a module. The module can specifically create an > enumerated > > type for this and not export it, thereby removing any possibility of > > another module passing the seed type and conflicting. > > > > The Defaultable class is added in this case to implement only a single > > method (defaultValue :: Defaultable a => a -> a). This is conceptionally > > the 'simplest' value of the type, such as the empty list, the number 0, > > False, the null character &c. The IORef returned by enumToIORef would be > > initialized before being written to to this specific default value of its > > type. This approach is chosen because it is impossible to initialize it > to > > user specified value because enumToIORef can be called twice with the > same > > seed but a different initial value. > > > > In the alternative it is also possible to do without the default value > and > > say the IORef returned is the same if and only if the seed and the > initial > > value given are the same. Allowing the function to remain referentially > > transparent as well. This would probably require for good semantics the > > underlying type of the IORef to be a member of EQ...? > > > > All this would of course require that newIORef and enumToIORef never > > produce the same IORef. > > > > Aside its limitations of the type IORef's initialized with this method > can > > carry, I do believe they cover the vast majority of use cases of top > level > > mutable state? > > > > Caveats? > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From roma at ro-che.info Sun Dec 15 14:47:58 2013 From: roma at ro-che.info (Roman Cheplyaka) Date: Sun, 15 Dec 2013 16:47:58 +0200 Subject: [Haskell-cafe] RFC: Top level mutable state in terms of pure-function initialization? In-Reply-To: References: <20131215133853.GA8304@sniper> Message-ID: <20131215144758.GA9661@sniper> Ok, it could work, but it can lead to very subtle bugs. You change the type of IORef during refactoring (and forget to change it in a different place), and your program now works wrong (but silently so), because now it's creating two IORefs instead of one. A better way would be to have phantomly-typed identifiers, like class IsRefId c where initialContents :: c a -> a toInt :: c a -> Int data MyRefId a where Ref1 :: RefId Int Ref2 :: RefId Bool ... instance IsRefId MyRefId where ... idToIORef :: IsRefId c => c a -> IORef a Still can be abused (by not constraining phantom types properly), but can also provide safety if used right. (And no, Eq is not strictly necessary, because you convert to integers anyway.) Roman * EatsKittens [2013-12-15 15:05:40+0100] > 1. Well, since x and y are not of the same type they would in this case > contain a different IORef. The read in this case would read False since y > is initialized to false as the default of Bool. > > 2. In this example it would again be two different IO refs since the type > is different. It would again on demand create a different IORef for Int and > Bool. > > 3. No, they refer to a different one as I said, the default-less version > creates the IORef to be unique if and only if both the seed and > initialization are the same. > > 4. Agreed, I overlooked that not all enum instances are typable. (I believe > they also need to be an instance of EQ?) > > > On 15 December 2013 14:38, Roman Cheplyaka wrote: > > > 1. Well, that creates a loophole in the type system: > > > > let > > x :: IORef Int > > x = enumToIORef 0 > > > > y :: IORef Bool > > y = enumToIORef 0 > > in writeIORef x (5 :: Int) >> (readIORef y :: IO Bool) > > > > 2. There's also a less obvious loophole with your Defaultable version: > > > > let > > x :: Defaultable a => IORef a > > x = enumToIORef 0 > > in writeIORef x (5 :: Int) >> (readIORef x :: IO Bool) > > > > 3. In your default-less version there's a problem of doing this: > > > > x = enumToIORef 0 True > > y = enumToIORef 0 False > > > > Now, x and y presumably refer to the same IORef, but the initial > > contents of that IORef will depend on whether you access it through x or > > y. > > > > 4. Finally, the implementation of enumToIORef can only inspect it by > > converting to Int, and cannot distinguish different enums that > > correspond to the same number. > > > > This last problem can be solved by adding a Typeable constraint, > > because TypeReps carry the information about where (module, package) the > > type was defined. > > > > Roman > > > > * EatsKittens [2013-12-15 12:39:20+0100] > > > A pure function (enumToIORef :: (Enum a, Defaultable b) => a -> IORef b). > > > This function returns referentially transparently an IORef as a function > > of > > > its "seed" with the guarantee that the IORef returned is identical if and > > > only if the seed is. This function can be used to implement top level > > > mutable state in a module. The module can specifically create an > > enumerated > > > type for this and not export it, thereby removing any possibility of > > > another module passing the seed type and conflicting. > > > > > > The Defaultable class is added in this case to implement only a single > > > method (defaultValue :: Defaultable a => a -> a). This is conceptionally > > > the 'simplest' value of the type, such as the empty list, the number 0, > > > False, the null character &c. The IORef returned by enumToIORef would be > > > initialized before being written to to this specific default value of its > > > type. This approach is chosen because it is impossible to initialize it > > to > > > user specified value because enumToIORef can be called twice with the > > same > > > seed but a different initial value. > > > > > > In the alternative it is also possible to do without the default value > > and > > > say the IORef returned is the same if and only if the seed and the > > initial > > > value given are the same. Allowing the function to remain referentially > > > transparent as well. This would probably require for good semantics the > > > underlying type of the IORef to be a member of EQ...? > > > > > > All this would of course require that newIORef and enumToIORef never > > > produce the same IORef. > > > > > > Aside its limitations of the type IORef's initialized with this method > > can > > > carry, I do believe they cover the vast majority of use cases of top > > level > > > mutable state? > > > > > > Caveats? > > > > > _______________________________________________ > > > Haskell-Cafe mailing list > > > Haskell-Cafe at haskell.org > > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: Digital signature URL: From simon at joyful.com Sun Dec 15 18:43:31 2013 From: simon at joyful.com (Simon Michael) Date: Sun, 15 Dec 2013 10:43:31 -0800 Subject: [Haskell-cafe] ANN: hledger 0.22 In-Reply-To: <11ab052e-26cb-4a7d-bb0d-971d8721f2a0@googlegroups.com> References: <1386992864.13445.59458157.12E3C40E@webmail.messagingengine.com> <1387079430.31318.59728549.7EBD75D0@webmail.messagingengine.com> <11ab052e-26cb-4a7d-bb0d-971d8721f2a0@googlegroups.com> Message-ID: <1387133011.31483.59885701.2AEBCD4C@webmail.messagingengine.com> That's odd. Here I have ubuntu raring, ghc 7.6.3, cabal-dev 0.9.2 using Cabal 1.16.0, cabal-install 1.18.0.2 using Cabal 1.18.1. Do you see the same problem with cabal sandbox init; cabal install ./hledger-lib ./hledger ./hledger-web ? On Sun, Dec 15, 2013, at 03:36 AM, Marko Koci? wrote: I also had fresh cabal-dev repo, and it didn't work. However, I was able to build when I added --max-backjumps=10000 to the build line. Regards, Marko On Sunday, December 15, 2013 4:50:30 AM UTC+1, Simon Michael (sm) wrote: It works for me in a fresh cabal-dev package db, which I think yours is not, right ? Installs into an already-populated package db are more troublesome than usual right now because of the recent major version bumps to text, wai, warp, http-conduit etc. On Sat, Dec 14, 2013, at 10:27 AM, Marko Koci? wrote: I have build problems again after pulling from git. ~/src/hledger$ cabal-dev install ./hledger ./hledger-lib/ ./hledger-web/ Resolving dependencies... cabal: Could not resolve dependencies: trying: hledger-0.22 (user goal) trying: utf8-string-0.3.7 (dependency of hledger-0.22) rejecting: utf8-string-0.3.7:+bytestring-in-base (conflict: base==[1]4.6.0.1/installed-ced..., utf8-string-0.3.7:bytestring-in-base => base>=2.0 && <2.2) trying: utf8-string-0.3.7:-bytestring-in-base trying: bytestring-0.10.0.2/installed-0b6... (dependency of utf8-string-0.3.7:-bytestring-in-base) trying: text-1.0.0.0 (dependency of hledger-0.22) trying: shakespeare-text-1.0.0.10 (dependency of hledger-0.22) trying: shakespeare-1.2.0.3 (dependency of shakespeare-text-1.0.0.10) next goal: system-fileio (dependency of shakespeare-1.2.0.3) rejecting: system-fileio-0.3.11, 0.3.10 (conflict: text==1.0.0.0, system-fileio => text>=0.7.1 && <0.12) rejecting: system-fileio-0.3.9, 0.3.8, 0.3.7, 0.3.6, 0.3.5, 0.3.4, 0.3.3, 0.3.2.1, 0.3.2, 0.3.1, 0.3 (conflict: bytestring==[2]0.10.0.2/installed-0b6..., system-fileio => bytestring>=0.9 && <0.10) rejecting: system-fileio-0.2.7, 0.2.6, 0.2.5, 0.2.4, 0.2.3, 0.2.2.1, 0.2.2, 0.2.1, 0.2, 0.1.1, 0.1 (conflict: shakespeare => system-fileio>=0.3) Backjump limit reached (change with --max-backjumps). marko at monet:~/src/hledger$ ghc --version The Glorious Glasgow Haskell Compilation System, version 7.6.3 -- -- You received this message because you are subscribed to the Google Groups hledger group. To post to this group, send email to hle... at googlegroups.com. To unsubscribe from this group, send email to hledger+u... at googlegroups.com. For more options, visit this group at [3]https://groups.google.com/d/forum/hledger?hl=en --- You received this message because you are subscribed to the Google Groups "hledger" group. To unsubscribe from this group and stop receiving emails from it, send an email to hledger+u... at googlegroups.com. For more options, visit [4]https://groups.google.com/groups/opt_out. -- -- You received this message because you are subscribed to the Google Groups hledger group. To post to this group, send email to hledger at googlegroups.com. To unsubscribe from this group, send email to hledger+unsubscribe at googlegroups.com. For more options, visit this group at [5]https://groups.google.com/d/forum/hledger?hl=en --- You received this message because you are subscribed to the Google Groups "hledger" group. To unsubscribe from this group and stop receiving emails from it, send an email to hledger+unsubscribe at googlegroups.com. For more options, visit [6]https://groups.google.com/groups/opt_out. References 1. http://4.6.0.1/installed-ced.. 2. http://0.10.0.2/installed-0b6.. 3. https://groups.google.com/d/forum/hledger?hl=en 4. https://groups.google.com/groups/opt_out 5. https://groups.google.com/d/forum/hledger?hl=en 6. https://groups.google.com/groups/opt_out -------------- next part -------------- An HTML attachment was scrubbed... URL: From simon at joyful.com Sun Dec 15 19:52:02 2013 From: simon at joyful.com (Simon Michael) Date: Sun, 15 Dec 2013 11:52:02 -0800 Subject: [Haskell-cafe] ANN: hledger 0.22 In-Reply-To: References: <1386992864.13445.59458157.12E3C40E@webmail.messagingengine.com> <1387079430.31318.59728549.7EBD75D0@webmail.messagingengine.com> <11ab052e-26cb-4a7d-bb0d-971d8721f2a0@googlegroups.com> <1387133011.31483.59885701.2AEBCD4C@webmail.messagingengine.com> Message-ID: <1387137122.17383.59904193.78200AB3@webmail.messagingengine.com> Well that's a mystery to me. Given that we've both done a cabal update, I can't think what is causing my cabal to find an install plan with default maxjump and yours not to. Maybe a someone will enlighten us. (I've belatedly dropped the haskell list from this thread.) On Sun, Dec 15, 2013, at 11:31 AM, Marko Koci? wrote: Yes, I have the same problem with cabal sandbox. I'm on Ubuntu 12.04 with binary downloaded ghc-7.6.3, cabal-1.18.0.2 and cabal-dev-0.9.2 Regards, Marko On Sun, Dec 15, 2013 at 7:43 PM, Simon Michael <[1]simon at joyful.com> wrote: That's odd. Here I have ubuntu raring, ghc 7.6.3, cabal-dev 0.9.2 using Cabal 1.16.0, cabal-install 1.18.0.2 using Cabal 1.18.1. Do you see the same problem with cabal sandbox init; cabal install ./hledger-lib ./hledger ./hledger-web ? On Sun, Dec 15, 2013, at 03:36 AM, Marko Koci? wrote: I also had fresh cabal-dev repo, and it didn't work. However, I was able to build when I added --max-backjumps=10000 to the build line. Regards, Marko On Sunday, December 15, 2013 4:50:30 AM UTC+1, Simon Michael (sm) wrote: It works for me in a fresh cabal-dev package db, which I think yours is not, right ? Installs into an already-populated package db are more troublesome than usual right now because of the recent major version bumps to text, wai, warp, http-conduit etc. On Sat, Dec 14, 2013, at 10:27 AM, Marko Koci? wrote: I have build problems again after pulling from git. ~/src/hledger$ cabal-dev install ./hledger ./hledger-lib/ ./hledger-web/ Resolving dependencies... cabal: Could not resolve dependencies: trying: hledger-0.22 (user goal) trying: utf8-string-0.3.7 (dependency of hledger-0.22) rejecting: utf8-string-0.3.7:+bytestring-in-base (conflict: base==[2]4.6.0.1/installed-ced..., utf8-string-0.3.7:bytestring-in-base => base>=2.0 && <2.2) trying: utf8-string-0.3.7:-bytestring-in-base trying: bytestring-0.10.0.2/installed-0b6... (dependency of utf8-string-0.3.7:-bytestring-in-base) trying: text-1.0.0.0 (dependency of hledger-0.22) trying: shakespeare-text-1.0.0.10 (dependency of hledger-0.22) trying: shakespeare-1.2.0.3 (dependency of shakespeare-text-1.0.0.10) next goal: system-fileio (dependency of shakespeare-1.2.0.3) rejecting: system-fileio-0.3.11, 0.3.10 (conflict: text==1.0.0.0, system-fileio => text>=0.7.1 && <0.12) rejecting: system-fileio-0.3.9, 0.3.8, 0.3.7, 0.3.6, 0.3.5, 0.3.4, 0.3.3, 0.3.2.1, 0.3.2, 0.3.1, 0.3 (conflict: bytestring==[3]0.10.0.2/installed-0b6..., system-fileio => bytestring>=0.9 && <0.10) rejecting: system-fileio-0.2.7, 0.2.6, 0.2.5, 0.2.4, 0.2.3, 0.2.2.1, 0.2.2, 0.2.1, 0.2, 0.1.1, 0.1 (conflict: shakespeare => system-fileio>=0.3) Backjump limit reached (change with --max-backjumps). marko at monet:~/src/hledger$ ghc --version The Glorious Glasgow Haskell Compilation System, version 7.6.3 -- -- You received this message because you are subscribed to the Google Groups hledger group. To post to this group, send email to hle... at googlegroups.com. To unsubscribe from this group, send email to hledger+u... at googlegroups.com. For more options, visit this group at [4]https://groups.google.com/d/forum/hledger?hl=en --- You received this message because you are subscribed to the Google Groups "hledger" group. To unsubscribe from this group and stop receiving emails from it, send an email to hledger+u... at googlegroups.com. For more options, visit [5]https://groups.google.com/groups/opt_out. -- -- You received this message because you are subscribed to the Google Groups hledger group. To post to this group, send email to [6]hledger at googlegroups.com. To unsubscribe from this group, send email to [7]hledger+unsubscribe at googlegroups.com. For more options, visit this group at [8]https://groups.google.com/d/forum/hledger?hl=en --- You received this message because you are subscribed to the Google Groups "hledger" group. To unsubscribe from this group and stop receiving emails from it, send an email to [9]hledger+unsubscribe at googlegroups.com. For more options, visit [10]https://groups.google.com/groups/opt_out. -- -- You received this message because you are subscribed to the Google Groups hledger group. To post to this group, send email to [11]hledger at googlegroups.com. To unsubscribe from this group, send email to [12]hledger+unsubscribe at googlegroups.com. For more options, visit this group at [13]https://groups.google.com/d/forum/hledger?hl=en --- You received this message because you are subscribed to a topic in the Google Groups "hledger" group. To unsubscribe from this topic, visit [14]https://groups.google.com/d/topic/hledger/FdWGTSAVzYU/unsubscribe. To unsubscribe from this group and all its topics, send an email to [15]hledger+unsubscribe at googlegroups.com. For more options, visit [16]https://groups.google.com/groups/opt_out. -- -- You received this message because you are subscribed to the Google Groups hledger group. To post to this group, send email to hledger at googlegroups.com. To unsubscribe from this group, send email to hledger+unsubscribe at googlegroups.com. For more options, visit this group at [17]https://groups.google.com/d/forum/hledger?hl=en --- You received this message because you are subscribed to the Google Groups "hledger" group. To unsubscribe from this group and stop receiving emails from it, send an email to hledger+unsubscribe at googlegroups.com. For more options, visit [18]https://groups.google.com/groups/opt_out. References 1. mailto:simon at joyful.com 2. http://4.6.0.1/installed-ced.. 3. http://0.10.0.2/installed-0b6.. 4. https://groups.google.com/d/forum/hledger?hl=en 5. https://groups.google.com/groups/opt_out 6. mailto:hledger at googlegroups.com 7. mailto:hledger%2Bunsubscribe at googlegroups.com 8. https://groups.google.com/d/forum/hledger?hl=en 9. mailto:hledger%2Bunsubscribe at googlegroups.com 10. https://groups.google.com/groups/opt_out 11. mailto:hledger at googlegroups.com 12. mailto:hledger%2Bunsubscribe at googlegroups.com 13. https://groups.google.com/d/forum/hledger?hl=en 14. https://groups.google.com/d/topic/hledger/FdWGTSAVzYU/unsubscribe 15. mailto:hledger%2Bunsubscribe at googlegroups.com 16. https://groups.google.com/groups/opt_out 17. https://groups.google.com/d/forum/hledger?hl=en 18. https://groups.google.com/groups/opt_out -------------- next part -------------- An HTML attachment was scrubbed... URL: From nikita at karetnikov.org Sun Dec 15 20:32:49 2013 From: nikita at karetnikov.org (Nikita Karetnikov) Date: Mon, 16 Dec 2013 00:32:49 +0400 Subject: [Haskell-cafe] Using unsafePerformIO and free with CString Message-ID: <87a9g1x3bi.fsf@karetnikov.org> I?m trying to write a wrapper for a C function. Here is an example of such code: {-# LANGUAGE ForeignFunctionInterface #-} import Foreign.C.String import Foreign.C.Types import System.IO.Unsafe import Foreign.Marshal.Alloc foreign import ccall "string.h strcmp" c_strcmp :: CString -> CString -> CInt strcmp :: String -> String -> Ordering strcmp s t = unsafePerformIO $ do s' <- newCString s t' <- newCString t let n = c_strcmp s' t' -- free s' -- free t' return $ case () of _ | n == 0 -> EQ | n < 0 -> LT | otherwise -> GT Two questions: 1. May I safely use unsafePerformIO in such cases? 2. What?s the proper way of using free here? If I uncomment the above, the function returns incorrect results. -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 835 bytes Desc: not available URL: From allbery.b at gmail.com Sun Dec 15 20:42:37 2013 From: allbery.b at gmail.com (Brandon Allbery) Date: Sun, 15 Dec 2013 15:42:37 -0500 Subject: [Haskell-cafe] Using unsafePerformIO and free with CString In-Reply-To: <87a9g1x3bi.fsf@karetnikov.org> References: <87a9g1x3bi.fsf@karetnikov.org> Message-ID: On Sun, Dec 15, 2013 at 3:32 PM, Nikita Karetnikov wrote: > let n = c_strcmp s' t' > -- free s' > -- free t' > return $ case () of > _ | n == 0 -> EQ > | n < 0 -> LT > | otherwise -> GT > > Two questions: > > 1. May I safely use unsafePerformIO in such cases? > Yes, although you might prefer to use the variant specified by the FFI standard, unsafeLocalState. > 2. What?s the proper way of using free here? If I uncomment the above, > the function returns incorrect results. > Note that you have not forced evaluation of `n` when you free the CString-s, so `c_strcmp` has not necessarily been called yet. Control.Exception.evaluate may be of use here. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From joeyadams3.14159 at gmail.com Sun Dec 15 21:22:30 2013 From: joeyadams3.14159 at gmail.com (Joey Adams) Date: Sun, 15 Dec 2013 16:22:30 -0500 Subject: [Haskell-cafe] Using unsafePerformIO and free with CString In-Reply-To: References: <87a9g1x3bi.fsf@karetnikov.org> Message-ID: On Sun, Dec 15, 2013 at 3:32 PM, Nikita Karetnikov wrote: > I?m trying to write a wrapper for a C function. Here is an example of > such code: > > ... > s' <- newCString s > t' <- newCString t > let n = c_strcmp s' t' > -- free s' > -- free t' ... > It'd be better to use withCString [1] instead, to avoid a memory leak if an exception occurs between newCString and free. Also, make c_strcmp an IO function: foreign import ccall "string.h strcmp" c_strcmp :: CString -> CString -> IO CInt The way you had it, c_strcmp had an implicit unsafePerformIO, which we don't want or need here. strcmp has the side effect of reading from pointers at a given moment in time. As Brandon brought up, right now, your code might as well say: strcmp s t = unsafePerformIO $ do s' <- newCString s t' <- newCString t -- free s' -- free t' return $ case c_strcmp s' t' of _ | n == 0 -> EQ | n < 0 -> LT | otherwise -> GT Because of laziness, n = c_strcmp s' t' isn't evaluated until it is needed. What you should say instead is: ... n <- c_strcmp s' t' ... This places the strcmp in the monadic chain so it will run at the right time (after newCString and before freeCString). [1]: http://hackage.haskell.org/package/base/docs/Foreign-C-String.html#v:withCString -------------- next part -------------- An HTML attachment was scrubbed... URL: From doug at cs.dartmouth.edu Sun Dec 15 21:28:53 2013 From: doug at cs.dartmouth.edu (Doug McIlroy) Date: Sun, 15 Dec 2013 16:28:53 -0500 Subject: [Haskell-cafe] getting source Message-ID: <201312152128.rBFLSrMh026697@stowe.cs.dartmouth.edu> It is a shame that when you look something up in Hayoo, you can immediately look at the source--but you can't From doug at cs.dartmouth.edu Sun Dec 15 21:56:52 2013 From: doug at cs.dartmouth.edu (Doug McIlroy) Date: Sun, 15 Dec 2013 16:56:52 -0500 Subject: [Haskell-cafe] source from hayoo Message-ID: <201312152156.rBFLuqFI026779@stowe.cs.dartmouth.edu> A non-text attachment was scrubbed... Name: not available Type: application/octet-stream Size: 403 bytes Desc: not available URL: From mail at nh2.me Mon Dec 16 02:13:50 2013 From: mail at nh2.me (=?ISO-8859-1?Q?Niklas_Hamb=FCchen?=) Date: Mon, 16 Dec 2013 02:13:50 +0000 Subject: [Haskell-cafe] Data.Vector with stride Message-ID: <52AE61DE.3040504@nh2.me> For low-level performance, especially when dealing with images, pixel buffers, camera devices etc, arrays can have a "stride" to align rows to word boundaries. http://en.wikipedia.org/wiki/Stride_of_an_array Data.Vector does not support strides (as mentioned in http://u.arboreus.com/2011/03/how-to-choose-haskell-array-library.html), but it would be nice to have them, especially for Storable vectors and interfacing with C imaging libraries. Is there a particular reason / difficulty that would go against an implementation of a Data.Vector.Storable.Stride and the corresponding generic vector instances? From mike at quasimal.com Mon Dec 16 02:42:15 2013 From: mike at quasimal.com (Mike Ledger) Date: Mon, 16 Dec 2013 13:42:15 +1100 Subject: [Haskell-cafe] Data.Vector with stride In-Reply-To: <52AE61DE.3040504@nh2.me> References: <52AE61DE.3040504@nh2.me> Message-ID: <52AE6887.2030909@quasimal.com> A quick and dirty way do have strides with Data.Vector.Storable might be to use a newtype around a type, and have its sizeOf be the stride. On Monday, December 16, 2013 1:13:50 PM, Niklas Hamb?chen wrote: > For low-level performance, especially when dealing with images, pixel > buffers, camera devices etc, arrays can have a "stride" to align rows to > word boundaries. > > http://en.wikipedia.org/wiki/Stride_of_an_array > > Data.Vector does not support strides (as mentioned in > http://u.arboreus.com/2011/03/how-to-choose-haskell-array-library.html), > but it would be nice to have them, especially for Storable vectors and > interfacing with C imaging libraries. > > Is there a particular reason / difficulty that would go against an > implementation of a Data.Vector.Storable.Stride and the corresponding > generic vector instances? > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From tonymorris at gmail.com Mon Dec 16 03:43:22 2013 From: tonymorris at gmail.com (Tony Morris) Date: Mon, 16 Dec 2013 13:43:22 +1000 Subject: [Haskell-cafe] [ANN] Canberra -- Introduction to Functional Programming course (free) Message-ID: <52AE76DA.7030209@gmail.com> *Title: *Introduction to Functional Programming *Presenters:* Mark Hibberd and Tony Morris *When: * Tuesday 4th, Wednesday 5^th & Thursday 6^th February, 9.00am -- 5.00pm (lunch will be provided) *Where: *NICTA CRL, Tower A, 7 London Circuit, Canberra ACT *Cost:* Free *Abstract:*NICTA will be hosting a hands-on, three day Introduction to Functional Programming, for interested participants (internal and external). We will be using the Haskell programming language for our journey over the three days and this session requires no prior experience with functional programming. You will be required to bring a suitable development machine (portable) for working through the exercises. You will also need to install Glasgow Haskell Compiler (http://www.haskell.org/ghc/) version 7 or higher on that machine. There are no other primary requirements. Each session will be instructed by Mark Hibberd (NICTA) and Tony Morris (NICTA), to help you along your path of FP discovery, wherever that might be. If you are interested in attending this course, please email your EOI to the below email address. In your response, it is very helpful for us to understand your goals in order to make the best of the time we will have, so please take the time to answer the below questions in your response. Your answers will not be shared- just used to construct the course structure/ material. Attendees will be selected based on the answers provided: 1. How would you rate your level of understanding of functional programming? 2. What would you hope to get out of the session? *Expression of Interest:*To haylee.alder at nicta.com.au by *Friday 24 January, 5pm*. -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Mon Dec 16 03:43:31 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sun, 15 Dec 2013 22:43:31 -0500 Subject: [Haskell-cafe] Data.Vector with stride In-Reply-To: <52AE6887.2030909@quasimal.com> References: <52AE61DE.3040504@nh2.me> <52AE6887.2030909@quasimal.com> Message-ID: Hey niklas, I'll releasing an abstraction layer on top of vector soon that'll have support for striding, and I definitely agree that such info is key for easy interop On Sun, Dec 15, 2013 at 9:42 PM, Mike Ledger wrote: > A quick and dirty way do have strides with Data.Vector.Storable might be > to use a newtype around a type, and have its sizeOf be the stride. > > > On Monday, December 16, 2013 1:13:50 PM, Niklas Hamb?chen wrote: > >> For low-level performance, especially when dealing with images, pixel >> buffers, camera devices etc, arrays can have a "stride" to align rows to >> word boundaries. >> >> http://en.wikipedia.org/wiki/Stride_of_an_array >> >> Data.Vector does not support strides (as mentioned in >> http://u.arboreus.com/2011/03/how-to-choose-haskell-array-library.html), >> but it would be nice to have them, especially for Storable vectors and >> interfacing with C imaging libraries. >> >> Is there a particular reason / difficulty that would go against an >> implementation of a Data.Vector.Storable.Stride and the corresponding >> generic vector instances? >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From temporalabstraction at gmail.com Mon Dec 16 04:30:31 2013 From: temporalabstraction at gmail.com (EatsKittens) Date: Sun, 15 Dec 2013 20:30:31 -0800 (PST) Subject: [Haskell-cafe] RFC: Top level mutable state in terms of pure-function initialization? In-Reply-To: <52ADA7E1.8020109@gmail.com> References: <52ADA7E1.8020109@gmail.com> Message-ID: <09ac5225-0abc-46be-b7e4-c798db779979@googlegroups.com> I don't think you understood me, maybe I wasn't clear enough but what I meant was that the ref was identical if and only if the enum seed is identical. (enumToIORef 5, enumToIORef 5) consists of two identical references. The enumToIORef function is completely reverentially transparent and its order of execution should not matter. (enumToIORef 5) :: Defaultable a => IORef a should always return the same ref. It will return a different ref however for each type a. In this sense, the hypothetical program: x = enumToIORef 0; y = enumToIORef 0; main = do { writeIORef x "Hello, World"; -- writes to ref x message <- readIORef y; -- reads from ref y, which is identical putStrLn message; }; Should output "Hello, World\n" However, as noted by Roman, a subtle bug occurs in this case: x = enumToIORef 0; y = enumToIORef 0; main = do { writeIORef x "Hello, World"; -- writes to ref x message <- readIORef y; -- reads from ref y, which is NOT identical print (message + 1); }; In this case the compiler deduces (with monomorphic restriction) that (y :: IORef Int) while (x :: IORef String), as such since enumToIORef is asked to return two different types each time it returns two different references. message is in this case read from the default value of 0 and "1\n" is output. On Sunday, 15 December 2013 14:00:17 UTC+1, Joe Quinn wrote: > > This has the same issue as just using a top-level (IORef b). Assume two > use cases: > > let x = enumToIORef 5 in (x, x) > (enumToIORef 5, enumToIORef 5) > > It's "obvious" in the first case that you have one ref that is used twice, > while it is "obvious" in the second case that you have two refs containing > the same value. But this breaks the rule that (let x = y in f x) = (f y), > because the left is a single ref while the right is two refs. > > There's likely other problems with it too, but this is what stands out to > me. > > On 12/15/2013 6:39 AM, EatsKittens wrote: > > A pure function (enumToIORef :: (Enum a, Defaultable b) => a -> IORef > b). This function returns referentially transparently an IORef as a > function of its "seed" with the guarantee that the IORef returned is > identical if and only if the seed is. This function can be used to > implement top level mutable state in a module. The module can specifically > create an enumerated type for this and not export it, thereby removing any > possibility of another module passing the seed type and conflicting. > > The Defaultable class is added in this case to implement only a single > method (defaultValue :: Defaultable a => a -> a). This is conceptionally > the 'simplest' value of the type, such as the empty list, the number 0, > False, the null character &c. The IORef returned by enumToIORef would be > initialized before being written to to this specific default value of its > type. This approach is chosen because it is impossible to initialize it to > user specified value because enumToIORef can be called twice with the same > seed but a different initial value. > > In the alternative it is also possible to do without the default value > and say the IORef returned is the same if and only if the seed and the > initial value given are the same. Allowing the function to remain > referentially transparent as well. This would probably require for good > semantics the underlying type of the IORef to be a member of EQ...? > > All this would of course require that newIORef and enumToIORef never > produce the same IORef. > > Aside its limitations of the type IORef's initialized with this method > can carry, I do believe they cover the vast majority of use cases of top > level mutable state? > > Caveats? > > > > _______________________________________________ > Haskell-Cafe mailing listHaskel... at haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jeanchristophe.mincke at gmail.com Mon Dec 16 06:37:18 2013 From: jeanchristophe.mincke at gmail.com (jean-christophe mincke) Date: Mon, 16 Dec 2013 07:37:18 +0100 Subject: [Haskell-cafe] Real world project with Cloud Haskell Message-ID: Hello, Has anybody heard about (or better, made) a real world project using Cloud Haskell? Thank you Regards J-C -------------- next part -------------- An HTML attachment was scrubbed... URL: From orblivion at gmail.com Mon Dec 16 07:09:57 2013 From: orblivion at gmail.com (Dan Krol) Date: Sun, 15 Dec 2013 23:09:57 -0800 Subject: [Haskell-cafe] Clearing up the status of GHCi on Raspberry Pi Message-ID: Hello, There seems to be a bit of confusing information out there regarding what is possible with regard to Haskell and Raspberry Pi. Specifically, availability of GHCi (and as such, the ability to compile certain thing such as Vector) in various versions of ghc. Debian Weezy came with GHC 7.4.1. It doesn't come with GHCi. This fact was reflected in what I've read online. So far so good. Now, we come to GHC 7.4.2.: http://www.haskell.org/haskellwiki/Raspberry_Pi#GHC_Status This currently says the following: "Note: GHCi does not currently work on ARM below version 7.4.2. See this post on haskell-cafe for information on this djhuk has been able to compile and install GHC-7.4.2 via QEMU to the Raspberry Pi but there still seems to be some work to do." This seems to imply that GHC 7.4.2. will include GHCi on arm. It implies that, though there were at the time of writing some unspecified problems, if one could get 7.4.2. working on their Rasperry Pi, one would get GHCi. Futher, I extrapolated this to mean that any version later than 7.4.2. would surely also have GHCi. Under the "Found on mailing lists" of this link: http://www.haskell.org/haskellwiki/ARM I similarly found: "GHCi (7.4.2) is working on ARM (Cubieboard with Ubuntu)" granted it doesn't say anything about Raspberry Pi. Well, my experience has shown otherwise. I upgraded my Raspberry Pi to Debian Jesse (currently the testing release), which gives me ghc as high as 7.6.3. GHCi? "command not found". I asked about this in #haskell on freenode, and somebody pointed me here: https://ghc.haskell.org/trac/ghc/wiki/Platforms This seems to imply that ARM does not have GHCi (though version is not specified in these tables). In fact, according to this same person, GHC altogether will not officially be supported on ARM until version 7.8. I'm not sure how that is reflected here. It seems to be Tier 2. Some Tier 2 things have GHCi. I figure we should sort this out, I'd be happy to edit the wikis myself but I want to make sure I understand what's going on. I understand this probably comes down to some nuances that are not expressed here. For user friendliness of the language and ecosystem I think such things should be made clear. As somebody coming to this wanting to accomplish something, I want a clear answer on what is available to me. It's been a source of frustration for me. Could somebody clear all this up for me? And while I'm at it, I would be grateful if somebody could explain to me how it is possible (if at all) to have ghci on my Raspberry Pi, short of compiling it myself. I'm not against compiling ghc, but I am against compiling it on my Raspberry Pi. Qemu I will consider, though. Thanks a lot, Dan -------------- next part -------------- An HTML attachment was scrubbed... URL: From alfredo.dinapoli at gmail.com Mon Dec 16 08:46:39 2013 From: alfredo.dinapoli at gmail.com (Alfredo Di Napoli) Date: Mon, 16 Dec 2013 08:46:39 +0000 Subject: [Haskell-cafe] Real world project with Cloud Haskell In-Reply-To: References: Message-ID: As far as I know Parallel Scientific uses Cloud Haskell for some of their projects. I think it's not surprising since Jeff Epstein was the first implementor of Cloud Haskell, which is nowadays "hand-overed" to WT: http://research.microsoft.com/en-us/um/people/simonpj/papers/parallel/remote.pdf On 16 December 2013 06:37, jean-christophe mincke < jeanchristophe.mincke at gmail.com> wrote: > Hello, > > Has anybody heard about (or better, made) a real world project using Cloud > Haskell? > > Thank you > > Regards > > J-C > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From Graham.Hutton at nottingham.ac.uk Mon Dec 16 09:38:17 2013 From: Graham.Hutton at nottingham.ac.uk (Graham Hutton) Date: Mon, 16 Dec 2013 09:38:17 +0000 Subject: [Haskell-cafe] 10 PhD studentships in Nottingham Message-ID: Dear all, The School of Computer Science in Nottingham is advertising 10 fully-funded PhD studentships. Applicants in the area of the Functional Programming lab (fp.cs.nott.ac.uk) are encouraged! If you are interested in applying, please contact a potential supervisor in the FP lab prior to submitting your application: Thorsten Altenkirch - constructive logic, proof assistants, type theory, category theory, lambda calculus, quantum computing. Venanzio Capretta - type theory, mathematical logic, corecursive structures, proof assistants, dependently-typed programming. Graham Hutton - program construction and verification, category theory, recursion operators, coinductive types. Henrik Nilsson - functional reactive programming, modelling and simulation languages, domain-specific languages. Best wishes, Graham +-----------------------------------------------------------+ 10 Fully-Funded PhD Studentships School of Computer Science University of Nottingham, UK Applications are invited for up to ten fully-funded PhD studentships in the School of Computer Science at the University of Nottingham, starting on 1st October 2014. The topics for the studentships are open, but should relate to the interests of one of the School?s research groups: Agents Lab; Automated Scheduling, Optimisation and Planning; Computer Vision Lab; Functional Programming Lab; Intelligent Modelling and Analysis; Mixed Reality Lab; Networked Systems. The studentships are for three years and include a stipend of ?13,726 per year and tuition fees, and are available to students of any nationality. Applicants are normally expected to have a first-class Undergraduate or Masters degree in Computer Science or a related discipline, and should discuss their interest and obtain the support of a potential supervisor in the School before applying. To apply, please submit the following items by email to : (1) a brief covering letter that describes your reasons for wishing to pursue a PhD, any ideas you have regarding possible areas or topics, and the name of a potential supervisor; (2) a copy of your CV, including your actual or expected degree class(es), and results of all University examinations; (3) an example of your technical writing, such as a project report or dissertation; (4) contact details for two academic referees. Closing date for applications: 10th January 2014 +-----------------------------------------------------------+ -- Prof Graham Hutton Functional Programming Lab School of Computer Science University of Nottingham, UK http://www.cs.nott.ac.uk/~gmh This message and any attachment are intended solely for the addressee and may contain confidential information. If you have received this message in error, please send it back to me, and immediately delete it. Please do not use, copy or disclose the information contained in this message or in any attachment. Any views or opinions expressed by the author of this email do not necessarily reflect the views of the University of Nottingham. This message has been checked for viruses but the contents of an attachment may still contain software viruses which could damage your computer system, you are advised to perform your own checks. Email communications with the University of Nottingham may be monitored as permitted by UK legislation. From hjgtuyl at chello.nl Mon Dec 16 10:41:51 2013 From: hjgtuyl at chello.nl (Henk-Jan van Tuyl) Date: Mon, 16 Dec 2013 11:41:51 +0100 Subject: [Haskell-cafe] getting source In-Reply-To: <201312152128.rBFLSrMh026697@stowe.cs.dartmouth.edu> References: <201312152128.rBFLSrMh026697@stowe.cs.dartmouth.edu> Message-ID: On Sun, 15 Dec 2013 22:28:53 +0100, Doug McIlroy wrote: > It is a shame that when you look something up in Hayoo, > you can immediately look at the source--but you can't You can, but not for every package; try looking up the "map" function, you will see a link to the source at the right of the page. Regards, Henk-Jan van Tuyl -- Prelude Data.Functor> pred <$> "IBM" "HAL" -- From iricanaycan at gmail.com Mon Dec 16 10:50:39 2013 From: iricanaycan at gmail.com (Aycan iRiCAN) Date: Mon, 16 Dec 2013 12:50:39 +0200 Subject: [Haskell-cafe] Real world project with Cloud Haskell In-Reply-To: References: Message-ID: Hi, In Picus Security, we're using distributed-process in our security assessment and monitoring product. Regards, On Mon, Dec 16, 2013 at 8:37 AM, jean-christophe mincke < jeanchristophe.mincke at gmail.com> wrote: > Hello, > > Has anybody heard about (or better, made) a real world project using Cloud > Haskell? > > Thank you > > Regards > > J-C > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -- http://www.google.com/profiles/iricanaycan -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at nh2.me Mon Dec 16 20:08:29 2013 From: mail at nh2.me (=?UTF-8?B?TmlrbGFzIEhhbWLDvGNoZW4=?=) Date: Mon, 16 Dec 2013 20:08:29 +0000 Subject: [Haskell-cafe] Data.Vector with stride In-Reply-To: References: <52AE61DE.3040504@nh2.me> <52AE6887.2030909@quasimal.com> Message-ID: <52AF5DBD.50801@nh2.me> Great, I will definitely try that! On Mon 16 Dec 2013 03:43:31 GMT, Carter Schonwald wrote: > Hey niklas, I'll releasing an abstraction layer on top of vector soon > that'll have support for striding, and I definitely agree that such > info is key for easy interop From carlo at carlo-hamalainen.net Mon Dec 16 12:54:55 2013 From: carlo at carlo-hamalainen.net (Carlo Hamalainen) Date: Mon, 16 Dec 2013 13:54:55 +0100 Subject: [Haskell-cafe] How to determine the right path to haddock html documentation? In-Reply-To: <20131214140215.GA970@sniper> References: <52AB8130.3030903@carlo-hamalainen.net> <20131213222827.GA31144@sniper> <52AC6284.1080103@carlo-hamalainen.net> <20131214140215.GA970@sniper> Message-ID: <52AEF81F.7010200@carlo-hamalainen.net> On 14/12/13 15:02, Roman Cheplyaka wrote: > haskell-names can also do this (it's used in halberd to solve a similar > task: https://github.com/haskell-suite/halberd) This is quite useful, thanks. For the benefit of the list archive, here is what I have worked out so far. I took the example from http://www.haskell.org/haskellwiki/GHC/As_a_library which uses getNamesInScope (I thought that this was promising). But it returned an empty list for the list of names (variable 'n'). I found out that you have to set the context before the call to getNamesInScope, like so: https://github.com/carlohamalainen/playground/blob/master/haskell/ghc_symbol_lookup/A.hs target <- guessTarget targetFile Nothing setTargets [target] load LoadAllTargets -- http://stackoverflow.com/questions/11571520/reify-a-module-into-a-record setContext [IIDecl (simpleImportDecl (mkModuleName "B"))] modSum <- getModSummary $ mkModuleName "B" For example on this file, -- B.hs module B where import Data.Maybe f :: a -> Maybe a f x = Just x s = "boo" :: String main = print "Hello, World!" we can get the list of names and also the imports: $ runhaskell A.hs ([B.main, B.f, B.s], [main, B.main, f, B.f, s, B.s], [], [import (implicit) Prelude, import Data.Maybe]) I'm not sure why, but the "source imports" is an empty list, while the "textual imports" gives the implicit Prelude and Data.Maybe. Also the names are the program names like f, s, and main, and don't include things like String, Int, Just, and so on. Independently of that, I tweaked an example from the haskell-names docs and this lets me see where String comes from, e.g. https://github.com/carlohamalainen/playground/blob/master/haskell/ghc_symbol_lookup/haskell_names_example.hs $ cat B.hs | runhaskell haskell_names_example.hs Relevant bits: "Prelude" SymType {st_origName = OrigName { origPackage = Just (PackageIdentifier { pkgName = PackageName "base" , pkgVersion = Version {versionBranch = [4,7,0,0] , versionTags = []}}) , origGName = GName { gModule = "GHC.Base" , gName = "String"}} , st_fixity = Nothing} "Data.Maybe" SymConstructor {sv_origName = OrigName { origPackage = Just (PackageIdentifier { pkgName = PackageName "base" , pkgVersion = Version {versionBranch = [4,7,0,0] , versionTags = []}}) , origGName = GName { gModule = "Data.Maybe" , gName = "Just"}} , sv_fixity = Nothing , sv_typeName = OrigName { origPackage = Just (PackageIdentifier { pkgName = PackageName "base" , pkgVersion = Version { versionBranch = [4,7,0,0] , versionTags = []}}) , origGName = GName { gModule = "Data.Maybe" , gName = "Maybe"}}} This is pretty much what I'm after. The first block shows us that String is exported from the Prelude, even though it's defined in GHC.Base. The second block says that the constructor Just is actually exported from Data.Maybe. So these ought to able to be stitched together: work through the textual imports one at a time until a symbol appears and then find the haddock_html field for the package using ghc-pkg. -- Carlo Hamalainen http://carlo-hamalainen.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From roma at ro-che.info Mon Dec 16 13:06:31 2013 From: roma at ro-che.info (Roman Cheplyaka) Date: Mon, 16 Dec 2013 15:06:31 +0200 Subject: [Haskell-cafe] ANN: ansi-terminal-0.6.1 In-Reply-To: <20131214120142.GA23146@sniper> References: <20131214120142.GA23146@sniper> Message-ID: <20131216130631.GA28061@sniper> Heads up: I've uploaded a new version of ansi-terminal. It contains two changes for Windows: * `BoldIntensity` no longer changes background color on Windows * `setSGR []` was not equivalent to `setSGR [Reset]` on Windows, even though it should be according to the documentation. This is now fixed. Both change the semantics, and while I believe they are beneficial, there may be subtle regressions if some code relied on the old behavior in unexpected ways. If you use any Haskell programs or libraries on Windows that do colorful terminal output, please test them with ansi-terminal-0.6.1 and report any problems. Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: Digital signature URL: From nomeata at debian.org Mon Dec 16 13:18:27 2013 From: nomeata at debian.org (Joachim Breitner) Date: Mon, 16 Dec 2013 14:18:27 +0100 Subject: [Haskell-cafe] Clearing up the status of GHCi on Raspberry Pi In-Reply-To: References: Message-ID: <1387199907.7084.4.camel@kirk> Hi, Am Sonntag, den 15.12.2013, 23:09 -0800 schrieb Dan Krol: > Could somebody clear all this up for me? from what I recalled, 7.4.1 in debian contained a few patches (which are included in 7.4.2) that made GHCi work on armel, and probably since 7.4.0.20111219-4 ghci was enabled in the Debian package. But later, it turned out that it was broken in various ways (see https://ghc.haskell.org/trac/ghc/ticket/7794 and https://ghc.haskell.org/trac/ghc/ticket/8380), so Debian disabled GHCi on arm again in 7.6.3-3. Greetings, Joachim -- Joachim "nomeata" Breitner Debian Developer nomeata at debian.org | ICQ# 74513189 | GPG-Keyid: 4743206C JID: nomeata at joachim-breitner.de | http://people.debian.org/~nomeata -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 198 bytes Desc: This is a digitally signed message part URL: From allbery.b at gmail.com Mon Dec 16 14:40:23 2013 From: allbery.b at gmail.com (Brandon Allbery) Date: Mon, 16 Dec 2013 09:40:23 -0500 Subject: [Haskell-cafe] How to determine the right path to haddock html documentation? In-Reply-To: <52AEF81F.7010200@carlo-hamalainen.net> References: <52AB8130.3030903@carlo-hamalainen.net> <20131213222827.GA31144@sniper> <52AC6284.1080103@carlo-hamalainen.net> <20131214140215.GA970@sniper> <52AEF81F.7010200@carlo-hamalainen.net> Message-ID: On Mon, Dec 16, 2013 at 7:54 AM, Carlo Hamalainen < carlo at carlo-hamalainen.net> wrote: > I'm not sure why, but the "source imports" is an empty list, while the > "textual imports" gives the implicit Prelude and Data.Maybe. Also the names > are the program names like f, s, and main, and don't include things like > String, Int, Just, and so on. > "source imports" likely relates to the SOURCE pragma; see http://www.haskell.org/ghc/docs/latest/html/users_guide/separate-compilation.html#mutual-recursionfor details. I would expect that you get the names *defined* in the module, not those *imported* into it; to get those, you would follow the import lists, as you have already determined. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From roma at ro-che.info Mon Dec 16 15:01:03 2013 From: roma at ro-che.info (Roman Cheplyaka) Date: Mon, 16 Dec 2013 17:01:03 +0200 Subject: [Haskell-cafe] How to determine the right path to haddock html documentation? In-Reply-To: <52AEF81F.7010200@carlo-hamalainen.net> References: <52AB8130.3030903@carlo-hamalainen.net> <20131213222827.GA31144@sniper> <52AC6284.1080103@carlo-hamalainen.net> <20131214140215.GA970@sniper> <52AEF81F.7010200@carlo-hamalainen.net> Message-ID: <20131216150103.GA2372@sniper> I'm glad that you've had positive experience with haskell-names. Here's one caveat: haskell-names cannot use ghc's interface files to get information about installed modules. Instead, it maintains its own interface files. Which means that you'll have to install separately all packages that you need to access using the hs-gen-iface compiler, as described in the README. Additionally, not all packages that can be compiled by ghc can be compiled by haskell-names yet. It's up to you and other ghc-mod users to decide whether this is acceptable. Roman * Carlo Hamalainen [2013-12-16 13:54:55+0100] > On 14/12/13 15:02, Roman Cheplyaka wrote: > > haskell-names can also do this (it's used in halberd to solve a similar > > task: https://github.com/haskell-suite/halberd) > > This is quite useful, thanks. > > For the benefit of the list archive, here is what I have worked out so far. > > I took the example from > http://www.haskell.org/haskellwiki/GHC/As_a_library which uses > getNamesInScope (I thought that this was promising). But it returned an > empty list for the list of names (variable 'n'). I found out that you > have to set the context before the call to getNamesInScope, like so: > > https://github.com/carlohamalainen/playground/blob/master/haskell/ghc_symbol_lookup/A.hs > > > target <- guessTarget targetFile Nothing > setTargets [target] > load LoadAllTargets > > -- > http://stackoverflow.com/questions/11571520/reify-a-module-into-a-record > setContext [IIDecl (simpleImportDecl (mkModuleName "B"))] > > modSum <- getModSummary $ mkModuleName "B" > > For example on this file, > > -- B.hs > module B where > > import Data.Maybe > > f :: a -> Maybe a > f x = Just x > > s = "boo" :: String > > main = print "Hello, World!" > > we can get the list of names and also the imports: > > $ runhaskell A.hs > ([B.main, B.f, B.s], > [main, B.main, f, B.f, s, B.s], > [], > [import (implicit) Prelude, import Data.Maybe]) > > I'm not sure why, but the "source imports" is an empty list, while the > "textual imports" gives the implicit Prelude and Data.Maybe. Also the > names are the program names like f, s, and main, and don't include > things like String, Int, Just, and so on. > > Independently of that, I tweaked an example from the haskell-names docs > and this lets me see where String comes from, e.g. > > https://github.com/carlohamalainen/playground/blob/master/haskell/ghc_symbol_lookup/haskell_names_example.hs > > > $ cat B.hs | runhaskell haskell_names_example.hs > > Relevant bits: > > "Prelude" > > SymType {st_origName = OrigName { origPackage = Just (PackageIdentifier > { pkgName = PackageName "base" > > , pkgVersion = Version {versionBranch = [4,7,0,0] > > , versionTags = []}}) > , origGName = GName { gModule = "GHC.Base" > , gName = "String"}} > , st_fixity = Nothing} > > > "Data.Maybe" > > SymConstructor {sv_origName = OrigName { origPackage = Just > (PackageIdentifier { pkgName = PackageName "base" > > , pkgVersion = Version {versionBranch = [4,7,0,0] > > , versionTags = []}}) > , origGName = GName { gModule = > "Data.Maybe" > , gName = > "Just"}} > , sv_fixity = > Nothing > , sv_typeName > = OrigName { origPackage = Just (PackageIdentifier { pkgName = > PackageName "base" > > , pkgVersion = Version { versionBranch = [4,7,0,0] > > , versionTags = []}}) > > , origGName = GName { gModule = "Data.Maybe" > > , gName = "Maybe"}}} > > > > This is pretty much what I'm after. The first block shows us that String > is exported from the Prelude, even though it's defined in GHC.Base. The > second block says that the constructor Just is actually exported from > Data.Maybe. > > So these ought to able to be stitched together: work through the textual > imports one at a time until a symbol appears and then find the > haddock_html field for the package using ghc-pkg. > > -- > Carlo Hamalainen > http://carlo-hamalainen.net > -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: Digital signature URL: From doug at cs.dartmouth.edu Mon Dec 16 15:08:58 2013 From: doug at cs.dartmouth.edu (Doug McIlroy) Date: Mon, 16 Dec 2013 10:08:58 -0500 Subject: [Haskell-cafe] getting source Message-ID: <201312161508.rBGF8w5b030769@stowe.cs.dartmouth.edu> > > It is a shame that when you look something up in Hayoo, > > you can immediately look at the source--but you can't > > You can, but not for every package; try looking up the "map" function, you > will see a link to the source at the right of the page. > > Regards, > Henk-Jan van Tuyl Yes, I said you can look at the source, but not compile it. Hayoo's yellow "source" links get HTML generated from source-- a rendering intended for eyeballs, not compilers. What I suggested is that the HTML include a link to the underlying .hs file. Why should you have to go hassle with git or some other repository, and maybe cabal too, to get code that's right before your eyes? Doug From roma at ro-che.info Mon Dec 16 15:30:13 2013 From: roma at ro-che.info (Roman Cheplyaka) Date: Mon, 16 Dec 2013 17:30:13 +0200 Subject: [Haskell-cafe] getting source In-Reply-To: <201312161508.rBGF8w5b030769@stowe.cs.dartmouth.edu> References: <201312161508.rBGF8w5b030769@stowe.cs.dartmouth.edu> Message-ID: <20131216153013.GA3531@sniper> * Doug McIlroy [2013-12-16 10:08:58-0500] > > > It is a shame that when you look something up in Hayoo, > > > you can immediately look at the source--but you can't > > > > You can, but not for every package; try looking up the "map" function, you > > will see a link to the source at the right of the page. > > > > Regards, > > Henk-Jan van Tuyl > > Yes, I said you can look at the source, but not compile it. > Hayoo's yellow "source" links get HTML generated from source-- > a rendering intended for eyeballs, not compilers. > What I suggested is that the HTML include a link to the > underlying .hs file. Why should you have to go hassle with > git or some other repository, and maybe cabal too, to get > code that's right before your eyes? Most of the time it wouldn't compile anyway. The cabal file may contain information about other packages and their versions required to build this code, language extensions that have to be enabled, and so on. Also, there's a high probability that the module will import other modules from the same package. Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: Digital signature URL: From bgamari.foss at gmail.com Mon Dec 16 16:22:11 2013 From: bgamari.foss at gmail.com (Ben Gamari) Date: Mon, 16 Dec 2013 11:22:11 -0500 Subject: [Haskell-cafe] Clearing up the status of GHCi on Raspberry Pi In-Reply-To: References: Message-ID: <87r49cu5os.fsf@gmail.com> Dan Krol writes: ... > I figure we should sort this out, I'd be happy to edit the wikis myself but > I want to make sure I understand what's going on. I understand this > probably comes down to some nuances that are not expressed here. For user > friendliness of the language and ecosystem I think such things should be > made clear. As somebody coming to this wanting to accomplish something, I > want a clear answer on what is available to me. It's been a source of > frustration for me. > > Could somebody clear all this up for me? And while I'm at it, I would be > grateful if somebody could explain to me how it is possible (if at all) to > have ghci on my Raspberry Pi, short of compiling it myself. I'm not against > compiling ghc, but I am against compiling it on my Raspberry Pi. Qemu I > will consider, though. > The situation is a bit complicated and I've been pretty poor at keeping the existing documentation up-to-date. ARM support has in principle existed in the tree through the LLVM code generator for some time. The code generator itself is in my experience quite robust. There are, however, a number of details in the runtime system which break GHCi. One of these is the runtime linker which until recently had effectively no support for ARM. I worked some initial ARM support in to 7.6.1 (b22501b408ddb0503a06a188b06d9cff9be697cd) and while things largely worked at the time, there were still some rough edges. For this reason, 7.6 can't really considered to support GHCi on ARM. Unfortunately at this point I became quite busy and didn't have time to look into the remaining issues. This was in late 2011. In the last few weeks I've had time to have another look at this problem. It turns out one of the issues (lack of jump code, documented in bug #8380) was quite straightforward to fix (up to some cache coherency issues which I believe thoughtpolice has now sorted out, see 5bab1a57f572e29dfdffd6d1ce8e53a2772b18fd). Unfortunately after fixing this I found that there was still occassional crashes during the build process. I spent a fair bit of time poking around looking for the root cause but have still come up with no compelling leads. It's very likely that the culprit is the runtime linker, although I haven't found a way to narrow things down any further. Frankly, implementing a runtime linker is non-trivial business and in my opinion the limited man-hours working on GHC are better spent elsewhere. Having our own runtime linker has its advantages, but for an architecture that is currently *barely* supported, it makes more sense to punt as much of this responsibility to other parties as possible. For this reason I think it would be wise to focus on moving this functionality to the system's runtime linker by using dynamic linking. Dynamic linking has been working for some time now on x86 with the native code generator. Unfortunately, there have been rumors that things are broken when the LLVM code generator is used (which is the only option on ARM). I started looking into this late last week and believe I have the problem identified (thanks to help from Peter Wortmann, see [1]) and have something of a solution. At this point I'm running into build system issues[2] which prevent me from verifying my hacked work-around^H^H^Hsolution. Assuming that I can validate the fix, I'm hoping there's a chance it (or something like it) can make it in to 7.8. As far as I can tell, this is the last major impediment to have GHC working well on ARM. Moreover, by switching to dynamic linking on ARM we will have eliminated a major source of trouble from the equation. This would mean that 7.8 would finally have (hopefully) robust support on ARM. Cheers, - Ben [1] http://www.haskell.org/pipermail/ghc-devs/2013-December/003484.html [2] http://www.haskell.org/pipermail/ghc-devs/2013-December/003488.html -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 489 bytes Desc: not available URL: From andrew.gibiansky at gmail.com Mon Dec 16 20:40:57 2013 From: andrew.gibiansky at gmail.com (Andrew Gibiansky) Date: Mon, 16 Dec 2013 12:40:57 -0800 Subject: [Haskell-cafe] [ANN] IHaskell Update -- Call for Help/Suggestions Message-ID: Hey everyone! I'm excited to announce a significant update to IHaskell. I originally announced IHaskell a few months ago, but there's been a few exciting changes: Significantly more stable and less buggy. It's been updated to use the GHC API for parsing and evaluation, so behavior should be very similar to GHCi in most places. You can now defined modules in cells instead of just interactive code. These modules are compiled to object code and loaded and provide fast runtime compared to interactive code. Most important: IHaskell can now load additional packages in order to provide rich display capabilities for specific data types. This means that it can be augmented through separate packages. If you have interest in providing a rich display mechanism for a data type, please consider writing an IHaskell extension package to do so! (If there are any data types that you think would be particularly useful but don't have time to implement yourself, let me know, too!) The extensibility is provided through an IHaskell.Display module. For instance, if you are creating an extension for a particular package foo, you should create a package called ihaskell-foo. This package should contain a module along the following lines: -- The name is important module IHaskell.Display.Foo where import Foo (DataThing) import IHaskell.Display -- Define how to display my data thing instance IHaskellDisplay DataThing where display myDataThing = [ plain "Plain Text output" , html "HTML output"] I would love to work with anyone who's interested in helping create these packages to make IHaskell as useful as possible. In addition, if you have any features you think would really make this more useful or bugs you've found, let me know! If you have any issues with installation, please let me know. I've had some trouble with getting a Hackage-based installation to work, so for now it's just from the Github repository, but I'd be happy to help people individually. -------------- next part -------------- An HTML attachment was scrubbed... URL: From s.j.thompson at kent.ac.uk Mon Dec 16 21:19:27 2013 From: s.j.thompson at kent.ac.uk (Simon Thompson) Date: Mon, 16 Dec 2013 21:19:27 +0000 Subject: [Haskell-cafe] SBLP 2014 - Preliminary Call for Papers Message-ID: PRELIMINARY CALL FOR PAPERS 18th Brazilian Symposium on Programming Languages (SBLP 2014) A member of CBSoft joint conference http://www.ic.ufal.br/evento/cbsoft2014/ to be held in Maceio, Brazil. CBSoft dates are September 28, 2014 to October 3, 2014 (SBLP dates are yet to be decided.) IMPORTANT DATES Paper abstract submission: May 2nd, 2014 Full paper submission: May 9th, 2014 Notification of acceptance: June 13th, 2014 Final papers due: July 4th, 2014 INTRODUCTION The 18th Brazilian Symposium on Programming Languages, SBLP 2014, will be held in Maceio, a beautiful cite in the Northeastern part of Brazil. The conference will happen between September 28th and October 3rd, 2014. SBLP provides a venue for researchers and practitioners interested in the fundamental principles and innovations in the design and implementation of programming languages and systems. SBLP 2014 invites authors to contribute with technical papers related (but not limited) to: * Program generation and transformation, including domain-specific languages and model-driven development in the context of programming languages. * Programming paradigms and styles, including functional, object-oriented, aspect-oriented, scripting languages, real-time, service-oriented, multithreaded, parallel, and distributed programming. * Formal semantics and theoretical foundations, including denotational, operational, algebraic and categorical. * Program analysis and verification, including type systems, static analysis and abstract interpretation. * Programming language design and implementation, including new programming models, programming language environments, compilation and interpretation techniques. SUBMISSIONS Contributions should be written in Portuguese or English. Papers should fall into one of two different categories: full papers, with at most 15 pages, or short papers, with at most 5 pages. Full papers submitted in English will be published in a volume of Lecture Notes in Computer Science (LNCS), by Springer. For this reason, all papers must be prepared using the LNCS template, available at http://www.springer.com/computer/lncs?SGWID=0-164-6-793341-0. We encourage the submission of short papers reporting partial results of on-going master dissertations or doctoral theses. All accepted papers will be published in the conference proceedings distributed in a digital media by the CBSOFT organizers. Submissions should be done through the SBLP 2014 page at EasyChair, which is available at http://www.easychair.org/conferences/?conf=sblp2014. As in previous editions, a journal's special issue, with selected papers from accepted contributions, is anticipated. Selected papers from the 2003 to the 2008 editions of SBLP were published in special issues of the Journal of Universal Computer Science, by Springer. The post-proceedings of SBLP from 2009 to 2012, also with selected papers from the conference, have been published as special issues of Science of Computer Programming, by Elsevier. KEYNOTE SPEAKERS Louis-Noel Pouchet, University of California Los Angeles Fabrice Rastello, INRIA PROGRAMME CHAIR Fernando Magno Quintao Pereira, UFMG PROGRAMME COMMITTEE Alberto Pardo, Universidad de la Rep?blica Alex Garcia, IME Alvaro Moreira, Federal University of Rio Grande do Sul Andre Rauber Du Bois, Federal University of Pelotas Carlos Camar?o, Federal University of Minas Gerais Christiano Braga, Fluminense Federal University Fabio Mascarenhas, Federal University of Rio de Janeiro Fernando Pereira, Federal University of Minas Gerais Fernando Castor, Federal University of Pernambuco Francisco Carvalho-Junior, Federal University of Ceara Hans-Wolfgang Loidl, Heriot-Watt University Jo?o Saraiva, University of Minho Joao F. Ferreira, Teesside University Louis-Noel Pouchet, University of California, Los Angeles Lucilia Figueiredo, Federal University of Ouro Preto Luis Barbosa, University of Minho Manuel A. Martins, University of Aveiro Marcello Bonsangue, Leiden University Marcelo Maia, Federal University of Uberl?ndia Marcelo D'Amorim, Federal University of Pernambuco Mariza Bigonha, Federal University of Minas Gerais Martin Musicante, Federal University of Rio Grande do Norte Noemi Rodriguez, PUC-Rio Peter Mosses, Swansea University Rafael Lins, Federal University of Pernambuco Renato Cerqueira, PUC-Rio Roberto Bigonha, Federal University of Minas Gerais Rodrigo Geraldo, Federal University of Ouro Preto Sandro Rigo, State University of Campinas S?rgio Medeiros, Federal University of Sergipe Simon Thompson, University of Kent Varmo Vene, University of Tartu Simon Thompson | Professor of Logic and Computation School of Computing | University of Kent | Canterbury, CT2 7NF, UK s.j.thompson at kent.ac.uk | M +44 7986 085754 | W www.cs.kent.ac.uk/~sjt From jgbailey at gmail.com Mon Dec 16 22:18:18 2013 From: jgbailey at gmail.com (Justin Bailey) Date: Mon, 16 Dec 2013 14:18:18 -0800 Subject: [Haskell-cafe] Alternatives to ThreadScope? In-Reply-To: References: Message-ID: Thanks for the pointers! I didn't know about threepenny-gui before - now I do. On Sat, Dec 14, 2013 at 2:35 AM, Heinrich Apfelmus wrote: > Carter Schonwald wrote: >> >> I don't think so. Maybe you should write one using three penny GUI! > > > Threepenny-gui, the reasonable alternative to hard-to-install-gui. > > http://www.haskell.org/haskellwiki/Threepenny-gui > > > Best regards, > Heinrich Apfelmus > > -- > http://apfelmus.nfshost.com > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From hans at hanshoglund.se Tue Dec 17 00:37:19 2013 From: hans at hanshoglund.se (=?iso-8859-1?Q?Hans_H=F6glund?=) Date: Tue, 17 Dec 2013 01:37:19 +0100 Subject: [Haskell-cafe] Polymorphic updating with TC/TFs? Message-ID: <2B203300-3868-4B9B-8F9B-2EEF322D6553@hanshoglund.se> Hello, I am working with a set of type classes of the following form (http://lpaste.net/97110). The idea is that every such class provide an associated type Foo, and a lens to the Foo in every instance. I.e. this class is used to provide view/set/modify for all types that contain a Foo somewhere deep in its structure. For "simple lenses", i.e. functions that does not modify the associated Foo, this is straightforward. However to support polymorphic updates it seems necessary to add another associated type NoFoo, which must be used to constraint the return type of set. What bothers me is the redundancy of the two set functions. I would intuitively expect set' to be implemented in terms of set (as it seems to be a restriction of that function), but this is not possible, as the compiler can not deduce that (NoFoo a (Foo a) ~ a). Is there a way to add this constraint to the type class? Hans From fuuzetsu at fuuzetsu.co.uk Tue Dec 17 01:14:17 2013 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Tue, 17 Dec 2013 01:14:17 +0000 Subject: [Haskell-cafe] Building applications with profiling Message-ID: <52AFA569.1020902@fuuzetsu.co.uk> Greetings, I want to profile the Yi text editor. A quick look on the Haskell wiki suggests that I need --enable-executable-profiling, however enabling that complains that the yi libraries weren't built with profiling. Additionally enabling --enable-library-profiling allows me to recompile the libs but at the very end I get an error about ?mtl? not having been built with profiling. >src/library/Yi/Boot.hs:9:8: > Could not find module `Control.Monad.State' > Perhaps you haven't installed the profiling libraries for package >`mtl-2.1.2'? > Use -v to see a list of the files searched for. I can't really recompile mtl with profiling considering that just about every single package on my system seems to depend on it and they would (probably?) all break. Does anyone have any suggestions on how to approach the problem? Am I doing it all wrong? Thanks -- Mateusz K. From allbery.b at gmail.com Tue Dec 17 01:37:18 2013 From: allbery.b at gmail.com (Brandon Allbery) Date: Mon, 16 Dec 2013 20:37:18 -0500 Subject: [Haskell-cafe] Building applications with profiling In-Reply-To: <52AFA569.1020902@fuuzetsu.co.uk> References: <52AFA569.1020902@fuuzetsu.co.uk> Message-ID: On Mon, Dec 16, 2013 at 8:14 PM, Mateusz Kowalczyk wrote: > I can't really recompile mtl with profiling considering that just about > every single package on my system seems to depend on it and they would > (probably?) all break. > > Does anyone have any suggestions on how to approach the problem? Am I > doing it all wrong? > How did you install ghc and the Haskell Platform? Vendor packages on Linux may split out the profiling libraries into separate packages (e.g. on Fedora 19 ghc-mtl-devel includes the profiling libraries, but on Debian wheezy they're separated into libghc-ghc-mtl-prof instead of being in libghc-ghc-mtl-dev). Installing such packages will not break anything using the existing -dev packages' libraries. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From fuuzetsu at fuuzetsu.co.uk Tue Dec 17 02:19:30 2013 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Tue, 17 Dec 2013 02:19:30 +0000 Subject: [Haskell-cafe] Building applications with profiling In-Reply-To: References: <52AFA569.1020902@fuuzetsu.co.uk> Message-ID: <52AFB4B2.4060902@fuuzetsu.co.uk> On 17/12/13 01:37, Brandon Allbery wrote: > On Mon, Dec 16, 2013 at 8:14 PM, Mateusz Kowalczyk > wrote: > >> I can't really recompile mtl with profiling considering that just about >> every single package on my system seems to depend on it and they would >> (probably?) all break. >> >> Does anyone have any suggestions on how to approach the problem? Am I >> doing it all wrong? >> > > How did you install ghc and the Haskell Platform? Vendor packages on Linux > may split out the profiling libraries into separate packages (e.g. on > Fedora 19 ghc-mtl-devel includes the profiling libraries, but on Debian > wheezy they're separated into libghc-ghc-mtl-prof instead of being in > libghc-ghc-mtl-dev). Installing such packages will not break anything using > the existing -dev packages' libraries. > I compiled it all myself and am not using my distro's (Gentoo) package manager for any Haskell packages. Will I have to recompile GHC (and everything that comes with it)? If yes, what flags should I pass to get profiling for the libs? The version in question is 7.6.3. -- Mateusz K. From allbery.b at gmail.com Tue Dec 17 02:33:10 2013 From: allbery.b at gmail.com (Brandon Allbery) Date: Mon, 16 Dec 2013 21:33:10 -0500 Subject: [Haskell-cafe] Building applications with profiling In-Reply-To: <52AFB4B2.4060902@fuuzetsu.co.uk> References: <52AFA569.1020902@fuuzetsu.co.uk> <52AFB4B2.4060902@fuuzetsu.co.uk> Message-ID: On Mon, Dec 16, 2013 at 9:19 PM, Mateusz Kowalczyk wrote: > I compiled it all myself and am not using my distro's (Gentoo) package > manager for any Haskell packages. > > Will I have to recompile GHC (and everything that comes with it)? If > yes, what flags should I pass to get profiling for the libs? > > The version in question is 7.6.3. You need to adjust build.mk as described in < https://ghc.haskell.org/trac/ghc/wiki/Building/Using#Commonbuild.mkoptions>, and yes, you'll have to reinstall everything else afterward. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From vogt.adam at gmail.com Tue Dec 17 05:03:24 2013 From: vogt.adam at gmail.com (adam vogt) Date: Tue, 17 Dec 2013 00:03:24 -0500 Subject: [Haskell-cafe] Fwd: Polymorphic updating with TC/TFs? In-Reply-To: References: <2B203300-3868-4B9B-8F9B-2EEF322D6553@hanshoglund.se> Message-ID: Hello Hans, You can move the setFoo into a multiparameter type class, to which you can add that constraint: class (HasFoo a, HasFoo b, b ~ NoFoo a (Foo b)) => SetFoo a b where setFoo :: Foo b -> a -> b instance (HasFoo b, b ~ NoFoo (FooT f a) (Foo b)) => SetFoo (FooT f a) b where setFoo f (FooT _ x) = FooT f x In my opinion, that's not as nice as the fundep solution which has less names: class Has s t a b | s -> a, t -> b, s b -> t, t a -> s On the topic of defining setFoo in terms of setFoo', you might be interested in -XDefaultSignatures, which can work with the SetFoo class defined above: class HasFoo a where default setFoo' :: SetFoo a a => Foo a -> a -> a setFoo' = setFoo setFoo' :: Foo a -> a -> a Finally, there seems to be some overlap with generic programming. Changing type parameters isn't supported by the ones I know (syb), but you can still fake it: . Regards, Adam On Mon, Dec 16, 2013 at 7:37 PM, Hans H?glund wrote: > Hello, > > I am working with a set of type classes of the following form (http://lpaste.net/97110). The idea is that every such class provide an associated type Foo, and a lens to the Foo in every instance. I.e. this class is used to provide view/set/modify for all types that contain a Foo somewhere deep in its structure. > > For "simple lenses", i.e. functions that does not modify the associated Foo, this is straightforward. However to support polymorphic updates it seems necessary to add another associated type NoFoo, which must be used to constraint the return type of set. > > What bothers me is the redundancy of the two set functions. I would intuitively expect set' to be implemented in terms of set (as it seems to be a restriction of that function), but this is not possible, as the compiler can not deduce that (NoFoo a (Foo a) ~ a). Is there a way to add this constraint to the type class? > > Hans > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From alfredo.dinapoli at gmail.com Tue Dec 17 08:15:29 2013 From: alfredo.dinapoli at gmail.com (Alfredo Di Napoli) Date: Tue, 17 Dec 2013 08:15:29 +0000 Subject: [Haskell-cafe] Cabal sandbox status in your ZSH prompt In-Reply-To: References: Message-ID: Really useful, thanks! On 15 December 2013 09:29, Krzysztof Skrz?tnicki wrote: > Looks great, thanks for sharing! I think I'll give it a try. > > All best, > Krzysztof Skrz?tnicki > > > On Sat, Dec 14, 2013 at 7:51 PM, Daniil Frumin wrote: > >> Hi everyone, I made a simple script for my zsh setup that allows me to >> see whether am I in a cabalized sandbox environment or not. >> >> On my machine it looks like this: >> >> The script itself is here: >> >> The result of checking for the sandbox is cached, which---as I've >> realized only moments ago---is probably unnecessary; it updates only >> when the user performs a `cabal` command or changes a directory. >> >> -- >> Sincerely yours, >> -- Daniil Frumin >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carlo at carlo-hamalainen.net Tue Dec 17 10:09:42 2013 From: carlo at carlo-hamalainen.net (Carlo Hamalainen) Date: Tue, 17 Dec 2013 11:09:42 +0100 Subject: [Haskell-cafe] How to determine the right path to haddock html documentation? In-Reply-To: <20131216150103.GA2372@sniper> References: <52AB8130.3030903@carlo-hamalainen.net> <20131213222827.GA31144@sniper> <52AC6284.1080103@carlo-hamalainen.net> <20131214140215.GA970@sniper> <52AEF81F.7010200@carlo-hamalainen.net> <20131216150103.GA2372@sniper> Message-ID: <52B022E6.1090408@carlo-hamalainen.net> On 16/12/13 16:01, Roman Cheplyaka wrote: > Here's one caveat: haskell-names cannot use ghc's interface files to get > information about installed modules. Instead, it maintains its own > interface files. Which means that you'll have to install separately all > packages that you need to access using the hs-gen-iface compiler, as > described in the README. Additionally, not all packages that can be > compiled by ghc can be compiled by haskell-names yet. > > It's up to you and other ghc-mod users to decide whether this is > acceptable. So if I use the branch of Cabal [1] then the local database file $HOME/.cabal/share/x86_64-linux-ghc-7.6.3/haskell-names-0.3.2.2/libraries/packages.db will be updated automatically? What packages are currently known to have problems with haskell-names? [1] https://github.com/feuerbach/Cabal Thanks, -- Carlo Hamalainen http://carlo-hamalainen.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From roma at ro-che.info Tue Dec 17 10:32:55 2013 From: roma at ro-che.info (Roman Cheplyaka) Date: Tue, 17 Dec 2013 12:32:55 +0200 Subject: [Haskell-cafe] How to determine the right path to haddock html documentation? In-Reply-To: <52B022E6.1090408@carlo-hamalainen.net> References: <52AB8130.3030903@carlo-hamalainen.net> <20131213222827.GA31144@sniper> <52AC6284.1080103@carlo-hamalainen.net> <20131214140215.GA970@sniper> <52AEF81F.7010200@carlo-hamalainen.net> <20131216150103.GA2372@sniper> <52B022E6.1090408@carlo-hamalainen.net> Message-ID: <20131217103255.GA10438@sniper> * Carlo Hamalainen [2013-12-17 11:09:42+0100] > On 16/12/13 16:01, Roman Cheplyaka wrote: > > Here's one caveat: haskell-names cannot use ghc's interface files to get > > information about installed modules. Instead, it maintains its own > > interface files. Which means that you'll have to install separately all > > packages that you need to access using the hs-gen-iface compiler, as > > described in the README. Additionally, not all packages that can be > > compiled by ghc can be compiled by haskell-names yet. > > > > It's up to you and other ghc-mod users to decide whether this is > > acceptable. > > So if I use the branch of Cabal [1] then the local database file > > $HOME/.cabal/share/x86_64-linux-ghc-7.6.3/haskell-names-0.3.2.2/libraries/packages.db > > will be updated automatically? First, no need to use that fork ? all patches have been merged into Cabal master at https://github.com/haskell/Cabal. (However, they are not released yet, so you still have to build the git version.) Second, no, installation won't happen automatically. At the moment you have to do that manually, like this: cabal install --haskell-suite -w hs-gen-iface mtl It'd be nice to add a cabal.config option to do that automatically. > What packages are currently known to have problems with haskell-names? * Packages that use the latest GHC extensions which haven't been added yet to haskell-src-exts * Packages that rely on custom Setup.hs usually have to be patched, because hs-gen-iface cannot compile Setup.hs, obviously If you run into any (other) problems, please report them (or, better yet, investigate them!) Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: Digital signature URL: From waldmann at imn.htwk-leipzig.de Tue Dec 17 12:09:28 2013 From: waldmann at imn.htwk-leipzig.de (Johannes Waldmann) Date: Tue, 17 Dec 2013 12:09:28 +0000 (UTC) Subject: [Haskell-cafe] haddock for all modules (exposed and other) in a cabalized project? Message-ID: I have a cabalized project with few "exposed-modules", and a lot of "other-modules". How can I invoke "cabal haddock --hyperlink-source" for *all* modules? - Thanks, J.W. From alfredo.dinapoli at gmail.com Tue Dec 17 12:33:50 2013 From: alfredo.dinapoli at gmail.com (Alfredo Di Napoli) Date: Tue, 17 Dec 2013 12:33:50 +0000 Subject: [Haskell-cafe] ANN: ansi-terminal-0.6.1 In-Reply-To: <20131216130631.GA28061@sniper> References: <20131214120142.GA23146@sniper> <20131216130631.GA28061@sniper> Message-ID: Thanks Roman! I guess, following your recent ML thread, that you are now maintaining it or at least plan to move it under package-janitors. Is this correct? Really happy to see ansi-terminal revamped! A. On 16 December 2013 13:06, Roman Cheplyaka wrote: > Heads up: I've uploaded a new version of ansi-terminal. It contains two > changes for Windows: > > * `BoldIntensity` no longer changes background color on Windows > * `setSGR []` was not equivalent to `setSGR [Reset]` on Windows, even > though it > should be according to the documentation. This is now fixed. > > Both change the semantics, and while I believe they are beneficial, > there may be subtle regressions if some code relied on the old behavior > in unexpected ways. > > If you use any Haskell programs or libraries on Windows that do colorful > terminal output, please test them with ansi-terminal-0.6.1 and report > any problems. > > Roman > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From svenpanne at gmail.com Tue Dec 17 13:07:26 2013 From: svenpanne at gmail.com (Sven Panne) Date: Tue, 17 Dec 2013 14:07:26 +0100 Subject: [Haskell-cafe] ANNOUNCE: New OpenAL packages Message-ID: New versions of the OpenAL packages are available on Hackage: * OpenAL 1.5.0.0 * ALUT 2.3.0.0 The main change is that the installation doesn't require autoconf anymore, instead of that, a pure Cabal-based build system is used now. This should make installing the packages on non-Linux systems much easier. Apart from that, uniqueBuffers works now and iOS is a supported platform, thanks to Stephen Blackheath. The packages depend on OpenGL now instead of ObjectName/StateVar/Tensor, because the latter packages were assimilated into OpenGL and there are probably very few programs using OpenAL without OpenGL. Have fun, S. From althainz at gmail.com Tue Dec 17 15:19:22 2013 From: althainz at gmail.com (Peter Althainz) Date: Tue, 17 Dec 2013 16:19:22 +0100 Subject: [Haskell-cafe] Frankfurt Haskell User Group Meetup - Wed. 18.12. Message-ID: Dear All, The next meeting of Frankfurt Haskell meetup takes place on Wednesday, 18th of Dec. and is about programming a game with HGamer3D. See game video here: http://www.youtube.com/watch?v=DKq0YsWRPoc and link to invitation here: http://www.meetup.com/Frankfurt-Haskell-User-Group/events/150475792/. Also we will have time for hacking on HWebUI. Peter -------------- next part -------------- An HTML attachment was scrubbed... URL: From roma at ro-che.info Tue Dec 17 15:37:18 2013 From: roma at ro-che.info (Roman Cheplyaka) Date: Tue, 17 Dec 2013 17:37:18 +0200 Subject: [Haskell-cafe] How to determine the right path to haddock html documentation? In-Reply-To: <52B03F43.8070506@carlo-hamalainen.net> References: <52AB8130.3030903@carlo-hamalainen.net> <20131213222827.GA31144@sniper> <52AC6284.1080103@carlo-hamalainen.net> <20131214140215.GA970@sniper> <52AEF81F.7010200@carlo-hamalainen.net> <20131216150103.GA2372@sniper> <52B022E6.1090408@carlo-hamalainen.net> <20131217103255.GA10438@sniper> <52B03F43.8070506@carlo-hamalainen.net> Message-ID: <20131217153718.GA13077@sniper> * Carlo Hamalainen [2013-12-17 13:10:43+0100] > On 17/12/13 11:32, Roman Cheplyaka wrote: > > > > First, no need to use that fork ? all patches have been merged into > > Cabal master at https://github.com/haskell/Cabal. (However, they are not > > released yet, so you still have to build the git version.) > > OK, I've built cabal from github in a clean test account. > > > Second, no, installation won't happen automatically. At the moment you > > have to do that manually, like this: > > > > cabal install --haskell-suite -w hs-gen-iface mtl > > I may be missing something obvious, but which package provides > haskell-suite? I see that it's a group of repositories on github. haskell-suite is not a real package or program. In this context, it's the name of a "virtual compiler" known to cabal. > $ cabal install --haskell-suite -w parsec > cabal: The program haskell-suite is required but it could not be found. The correct command is $ cabal install --haskell-suite -w hs-gen-iface parsec The -w flag lets cabal know that you want to compile using hs-gen-iface, which is a concrete compiler implementing the haskell-suite interface. > > It'd be nice to add a cabal.config option to do that automatically. > > Ditto for --haddock-hyperlink-source which I use all the time so that I > get locally built documentation. Very handy for when I work at a cafe. Yeah, ideally haddock and hscolor should be just separate compilers, just like ghc and hs-gen-iface are. The user would then specify in cabal.config what set of compilers to use for simple `cabal install $pkg`. > I want to make the development process in Vim as smooth as possible. A > newbie should be able to ask "what's this?" or "where is this from?" and > get a quick answer, right there in the editor. Hoogle is very useful but > there should be an editor-integrated solution that works locally and > gives an answer like "this symbol in this file comes from this module on > this system". Then you may be also interested in Ariadne :) https://github.com/feuerbach/ariadne Roman From roma at ro-che.info Tue Dec 17 15:42:25 2013 From: roma at ro-che.info (Roman Cheplyaka) Date: Tue, 17 Dec 2013 17:42:25 +0200 Subject: [Haskell-cafe] ANN: ansi-terminal-0.6.1 In-Reply-To: References: <20131214120142.GA23146@sniper> <20131216130631.GA28061@sniper> Message-ID: <20131217154225.GB13077@sniper> Yeah, the plan with haskell-pkg-janitors didn't really work out, so I just took over ansi-terminal myself. * Alfredo Di Napoli [2013-12-17 12:33:50+0000] > Thanks Roman! > I guess, following your recent ML thread, that you are now maintaining it > or at least plan to move it under package-janitors. > Is this correct? > > Really happy to see ansi-terminal revamped! > > A. > > > On 16 December 2013 13:06, Roman Cheplyaka wrote: > > > Heads up: I've uploaded a new version of ansi-terminal. It contains two > > changes for Windows: > > > > * `BoldIntensity` no longer changes background color on Windows > > * `setSGR []` was not equivalent to `setSGR [Reset]` on Windows, even > > though it > > should be according to the documentation. This is now fixed. > > > > Both change the semantics, and while I believe they are beneficial, > > there may be subtle regressions if some code relied on the old behavior > > in unexpected ways. > > > > If you use any Haskell programs or libraries on Windows that do colorful > > terminal output, please test them with ansi-terminal-0.6.1 and report > > any problems. > > > > Roman > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: Digital signature URL: From orblivion at gmail.com Tue Dec 17 17:29:27 2013 From: orblivion at gmail.com (Dan Krol) Date: Tue, 17 Dec 2013 09:29:27 -0800 Subject: [Haskell-cafe] Clearing up the status of GHCi on Raspberry Pi In-Reply-To: <87r49cu5os.fsf@gmail.com> References: <87r49cu5os.fsf@gmail.com> Message-ID: Thanks so much for the detailed response. When I have a moment I will try to come up with some appropriate edits to the Wikis, I will run them by you first to make sure they're accurate. And even moreso, thanks for your work in this area. When is 7.8 looking like it's coming out? And, how hard would it be to install it onto my Pi? Would I have to compile it? I'm assuming it won't make it into the Jesse repository (or will it?) -Dan On Mon, Dec 16, 2013 at 8:22 AM, Ben Gamari wrote: > Dan Krol writes: > > ... > > I figure we should sort this out, I'd be happy to edit the wikis myself > but > > I want to make sure I understand what's going on. I understand this > > probably comes down to some nuances that are not expressed here. For user > > friendliness of the language and ecosystem I think such things should be > > made clear. As somebody coming to this wanting to accomplish something, I > > want a clear answer on what is available to me. It's been a source of > > frustration for me. > > > > Could somebody clear all this up for me? And while I'm at it, I would be > > grateful if somebody could explain to me how it is possible (if at all) > to > > have ghci on my Raspberry Pi, short of compiling it myself. I'm not > against > > compiling ghc, but I am against compiling it on my Raspberry Pi. Qemu I > > will consider, though. > > > The situation is a bit complicated and I've been pretty poor at keeping > the existing documentation up-to-date. ARM support has in principle existed > in the tree through the LLVM code generator for some time. The code > generator itself is in my experience quite robust. > > There are, however, a number of details in the runtime system which > break GHCi. One of these is the runtime linker which until recently had > effectively no support for ARM. I worked some initial ARM support in to > 7.6.1 (b22501b408ddb0503a06a188b06d9cff9be697cd) and while things > largely worked at the time, there were still some rough edges. For this > reason, 7.6 can't really considered to support GHCi on ARM. > Unfortunately at this point I became quite busy and didn't have time to > look into the remaining issues. This was in late 2011. > > In the last few weeks I've had time to have another look at this > problem. It turns out one of the issues (lack of jump code, documented > in bug #8380) was quite straightforward to fix > (up to some cache coherency issues which I believe thoughtpolice has now > sorted out, see 5bab1a57f572e29dfdffd6d1ce8e53a2772b18fd). Unfortunately > after fixing this I found that there was still occassional crashes > during the build process. I spent a fair bit of time poking around > looking for the root cause but have still come up with no compelling > leads. It's very likely that the culprit is the runtime linker, although > I haven't found a way to narrow things down any further. > > Frankly, implementing a runtime linker is non-trivial business and in my > opinion the limited man-hours working on GHC are better spent > elsewhere. Having our own runtime linker has its advantages, but for an > architecture that is currently *barely* supported, it makes more sense > to punt as much of this responsibility to other parties as possible. For > this reason I think it would be wise to focus on moving this > functionality to the system's runtime linker by using dynamic linking. > > Dynamic linking has been working for some time now on x86 with the > native code generator. Unfortunately, there have been rumors that things > are broken when the LLVM code generator is used (which is the only > option on ARM). I started looking into this late last week and believe I > have the problem identified (thanks to help from Peter Wortmann, see > [1]) and have something of a solution. At this point I'm running into > build system issues[2] which prevent me from verifying my hacked > work-around^H^H^Hsolution. > > Assuming that I can validate the fix, I'm hoping there's a chance it (or > something like it) can make it in to 7.8. As far as I can tell, this is > the last major impediment to have GHC working well on ARM. Moreover, by > switching to dynamic linking on ARM we will have eliminated a major > source of trouble from the equation. This would mean that 7.8 would > finally have (hopefully) robust support on ARM. > > Cheers, > > - Ben > > > [1] http://www.haskell.org/pipermail/ghc-devs/2013-December/003484.html > [2] http://www.haskell.org/pipermail/ghc-devs/2013-December/003488.html > -------------- next part -------------- An HTML attachment was scrubbed... URL: From Tillmann.Vogt at rwth-aachen.de Tue Dec 17 21:03:49 2013 From: Tillmann.Vogt at rwth-aachen.de (Tillmann Vogt) Date: Tue, 17 Dec 2013 22:03:49 +0100 Subject: [Haskell-cafe] text 1.0.0.0 producing cabal hell? Message-ID: <52B0BC35.1080507@rwth-aachen.de> Check this out: http://packdeps.haskellers.com/reverse/text 306 outdated dependencies! I am guessing that most libraries could easily change the boundaries to >=0.11 && <1.1 because the API hasn't changed a lot. As far as I can see only a function was added. Or is everybody using sandboxing tools? Maybe the author of a library should have the right to change the boundary of all reverse dependencies. So that Brian has to adjust all 306 boundaries if he knows that this would work :-) Just the boundaries, not the code. -Tillmann -------------- next part -------------- An HTML attachment was scrubbed... URL: From spam at scientician.net Tue Dec 17 21:20:52 2013 From: spam at scientician.net (Bardur Arantsson) Date: Tue, 17 Dec 2013 22:20:52 +0100 Subject: [Haskell-cafe] text 1.0.0.0 producing cabal hell? In-Reply-To: <52B0BC35.1080507@rwth-aachen.de> References: <52B0BC35.1080507@rwth-aachen.de> Message-ID: On 2013-12-17 22:03, Tillmann Vogt wrote: > Check this out: > > http://packdeps.haskellers.com/reverse/text > > 306 outdated dependencies! > I am guessing that most libraries could easily change the boundaries to >>=0.11 && <1.1 > > because the API hasn't changed a lot. As far as I can see only a > function was added. > Or is everybody using sandboxing tools? > Maybe the author of a library should have the right to change the > boundary of all reverse dependencies. So that Brian has to adjust all > 306 boundaries if he knows that this would work :-) > Just the boundaries, not the code. > Devil's advocate question: Should bumping a package major version *even if there are no incompatible changes* be allowed according to the PVP? It seems it causes a lot of inconvenience for people who are following the PVP in their dependency declarations. @bos: Of course, I understand that this was probably to signal stability, and as such fully support the bump (not that you need my support), I'm just playing devil's advocate regarding the PVP. Regards, From cgaebel at uwaterloo.ca Tue Dec 17 21:24:41 2013 From: cgaebel at uwaterloo.ca (Clark Gaebel) Date: Tue, 17 Dec 2013 16:24:41 -0500 Subject: [Haskell-cafe] text 1.0.0.0 producing cabal hell? In-Reply-To: References: <52B0BC35.1080507@rwth-aachen.de> Message-ID: Is there any way we can get packdeps to show the current maintainer (name + email) so we can easily ctrl+f ourselves in the list? - Clark On Tue, Dec 17, 2013 at 4:20 PM, Bardur Arantsson wrote: > On 2013-12-17 22:03, Tillmann Vogt wrote: > > Check this out: > > > > http://packdeps.haskellers.com/reverse/text > > > > 306 outdated dependencies! > > I am guessing that most libraries could easily change the boundaries to > >>=0.11 && <1.1 > > > > because the API hasn't changed a lot. As far as I can see only a > > function was added. > > Or is everybody using sandboxing tools? > > Maybe the author of a library should have the right to change the > > boundary of all reverse dependencies. So that Brian has to adjust all > > 306 boundaries if he knows that this would work :-) > > Just the boundaries, not the code. > > > > Devil's advocate question: Should bumping a package major version *even > if there are no incompatible changes* be allowed according to the PVP? > It seems it causes a lot of inconvenience for people who are following > the PVP in their dependency declarations. > > @bos: Of course, I understand that this was probably to signal > stability, and as such fully support the bump (not that you need my > support), I'm just playing devil's advocate regarding the PVP. > > Regards, > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Clark. Key ID : 0x78099922 Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 -------------- next part -------------- An HTML attachment was scrubbed... URL: From jwlato at gmail.com Tue Dec 17 23:24:09 2013 From: jwlato at gmail.com (John Lato) Date: Tue, 17 Dec 2013 15:24:09 -0800 Subject: [Haskell-cafe] ANN: ansi-terminal-0.6.1 In-Reply-To: <20131217154225.GB13077@sniper> References: <20131214120142.GA23146@sniper> <20131216130631.GA28061@sniper> <20131217154225.GB13077@sniper> Message-ID: On Tue, Dec 17, 2013 at 7:42 AM, Roman Cheplyaka wrote: > Yeah, the plan with haskell-pkg-janitors didn't really work out, so I > just took over ansi-terminal myself. > Why not? Did you get a reply to your first question, or is it because of a lack of response (although it hasn't been that long considering we're talking about changing maintainership of an abandoned package). I think haskell-pkg-janitors is a good idea, but it does seem to be very loosely organized. Regardless, it seems to be very github-centric, so perhaps raising an issue would be the best way to contact them about things like adding new packages. If you could identify the reason haskell-pkg-janitors didn't work out, perhaps those problems could be addressed? John L. > * Alfredo Di Napoli [2013-12-17 > 12:33:50+0000] > > Thanks Roman! > > I guess, following your recent ML thread, that you are now maintaining it > > or at least plan to move it under package-janitors. > > Is this correct? > > > > Really happy to see ansi-terminal revamped! > > > > A. > > > > > > On 16 December 2013 13:06, Roman Cheplyaka wrote: > > > > > Heads up: I've uploaded a new version of ansi-terminal. It contains two > > > changes for Windows: > > > > > > * `BoldIntensity` no longer changes background color on Windows > > > * `setSGR []` was not equivalent to `setSGR [Reset]` on Windows, even > > > though it > > > should be according to the documentation. This is now fixed. > > > > > > Both change the semantics, and while I believe they are beneficial, > > > there may be subtle regressions if some code relied on the old behavior > > > in unexpected ways. > > > > > > If you use any Haskell programs or libraries on Windows that do > colorful > > > terminal output, please test them with ansi-terminal-0.6.1 and report > > > any problems. > > > > > > Roman > > > > > > _______________________________________________ > > > Haskell-Cafe mailing list > > > Haskell-Cafe at haskell.org > > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jwlato at gmail.com Tue Dec 17 23:29:16 2013 From: jwlato at gmail.com (John Lato) Date: Tue, 17 Dec 2013 15:29:16 -0800 Subject: [Haskell-cafe] text 1.0.0.0 producing cabal hell? In-Reply-To: References: <52B0BC35.1080507@rwth-aachen.de> Message-ID: If you go to a URL like http://packdeps.haskellers.com/feed?needle=cgaebel you should get a nice report of all packages matching that string, along with their restrictive dependency bounds. There's an RSS feed also (linked from that page), if you're into that sort of thing. John L On Tue, Dec 17, 2013 at 1:24 PM, Clark Gaebel wrote: > Is there any way we can get packdeps to show the current maintainer (name > + email) so we can easily ctrl+f ourselves in the list? > > - Clark > > > On Tue, Dec 17, 2013 at 4:20 PM, Bardur Arantsson wrote: > >> On 2013-12-17 22:03, Tillmann Vogt wrote: >> > Check this out: >> > >> > http://packdeps.haskellers.com/reverse/text >> > >> > 306 outdated dependencies! >> > I am guessing that most libraries could easily change the boundaries to >> >>=0.11 && <1.1 >> > >> > because the API hasn't changed a lot. As far as I can see only a >> > function was added. >> > Or is everybody using sandboxing tools? >> > Maybe the author of a library should have the right to change the >> > boundary of all reverse dependencies. So that Brian has to adjust all >> > 306 boundaries if he knows that this would work :-) >> > Just the boundaries, not the code. >> > >> >> Devil's advocate question: Should bumping a package major version *even >> if there are no incompatible changes* be allowed according to the PVP? >> It seems it causes a lot of inconvenience for people who are following >> the PVP in their dependency declarations. >> >> @bos: Of course, I understand that this was probably to signal >> stability, and as such fully support the bump (not that you need my >> support), I'm just playing devil's advocate regarding the PVP. >> >> Regards, >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > > > -- > Clark. > > Key ID : 0x78099922 > Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From roma at ro-che.info Tue Dec 17 23:52:54 2013 From: roma at ro-che.info (Roman Cheplyaka) Date: Wed, 18 Dec 2013 01:52:54 +0200 Subject: [Haskell-cafe] ANN: ansi-terminal-0.6.1 In-Reply-To: References: <20131214120142.GA23146@sniper> <20131216130631.GA28061@sniper> <20131217154225.GB13077@sniper> Message-ID: <20131217235254.GA24581@sniper> There's no information about the group, no mailing list or IRC channel. It doesn't look like there's much collaboration inside the group. Nor did I get any response (except a short IRC chat with Daniel Wagner, who confirmed the above). Of course these problems could be addressed, but the very fact that they still aren't (after 2 years) is a sign for me that there's not much interest and it's not worth the effort on my side. Roman * John Lato [2013-12-17 15:24:09-0800] > On Tue, Dec 17, 2013 at 7:42 AM, Roman Cheplyaka wrote: > > > Yeah, the plan with haskell-pkg-janitors didn't really work out, so I > > just took over ansi-terminal myself. > > > > Why not? Did you get a reply to your first question, or is it because of a > lack of response (although it hasn't been that long considering we're > talking about changing maintainership of an abandoned package). > > I think haskell-pkg-janitors is a good idea, but it does seem to be very > loosely organized. Regardless, it seems to be very github-centric, so > perhaps raising an issue would be the best way to contact them about things > like adding new packages. > > If you could identify the reason haskell-pkg-janitors didn't work out, > perhaps those problems could be addressed? > > John L. > > > > * Alfredo Di Napoli [2013-12-17 > > 12:33:50+0000] > > > Thanks Roman! > > > I guess, following your recent ML thread, that you are now maintaining it > > > or at least plan to move it under package-janitors. > > > Is this correct? > > > > > > Really happy to see ansi-terminal revamped! > > > > > > A. > > > > > > > > > On 16 December 2013 13:06, Roman Cheplyaka wrote: > > > > > > > Heads up: I've uploaded a new version of ansi-terminal. It contains two > > > > changes for Windows: > > > > > > > > * `BoldIntensity` no longer changes background color on Windows > > > > * `setSGR []` was not equivalent to `setSGR [Reset]` on Windows, even > > > > though it > > > > should be according to the documentation. This is now fixed. > > > > > > > > Both change the semantics, and while I believe they are beneficial, > > > > there may be subtle regressions if some code relied on the old behavior > > > > in unexpected ways. > > > > > > > > If you use any Haskell programs or libraries on Windows that do > > colorful > > > > terminal output, please test them with ansi-terminal-0.6.1 and report > > > > any problems. > > > > > > > > Roman > > > > > > > > _______________________________________________ > > > > Haskell-Cafe mailing list > > > > Haskell-Cafe at haskell.org > > > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: Digital signature URL: From jeanchristophe.mincke at gmail.com Wed Dec 18 07:41:15 2013 From: jeanchristophe.mincke at gmail.com (jean-christophe mincke) Date: Wed, 18 Dec 2013 08:41:15 +0100 Subject: [Haskell-cafe] Haskell and Big Data Message-ID: Hello Cafe, Big Data is a bit trendy these days. Does anybody know about plans to develop an Haskell eco-system in that domain? I.e tools such as Storm or Spark (possibly on top of Cloud Haskell) or, at least, bindings to tools which exist in other languages. Thank you Regards J-C -------------- next part -------------- An HTML attachment was scrubbed... URL: From ezyang at mit.edu Wed Dec 18 03:35:18 2013 From: ezyang at mit.edu (Edward Z. Yang) Date: Wed, 18 Dec 2013 11:35:18 +0800 Subject: [Haskell-cafe] Monad.Reader #23 call for copy Message-ID: <1387337224-sup-6516@sabre> Call for Copy: The Monad.Reader - Issue 23 -------------------------------------------- Whether you're an established academic or have only just started learning Haskell, if you have something to say, please consider writing an article for The Monad.Reader! The submission deadline for Issue 23 will be: **Friday, January 17, 2014** The Monad.Reader ~~~~~~~~~~~~~~~~ The Monad.Reader is a electronic magazine about all things Haskell. It is less formal than journal, but somehow more enduring than a wiki- page. There have been a wide variety of articles: exciting code fragments, intriguing puzzles, book reviews, tutorials, and even half-baked research ideas. Submission Details ~~~~~~~~~~~~~~~~~~ Get in touch with me if you intend to submit something -- the sooner you let me know what you're up to, the better. Please submit articles for the next issue to me by e-mail (ezyang at mit.edu). Articles should be written according to the guidelines available from http://themonadreader.wordpress.com/contributing/ Please submit your article in PDF, together with any source files you used. The sources will be released together with the magazine under a BSD license. If you would like to submit an article, but have trouble with LaTeX please let me know and we'll work something out. From oleg at okmij.org Wed Dec 18 09:06:20 2013 From: oleg at okmij.org (oleg at okmij.org) Date: 18 Dec 2013 09:06:20 -0000 Subject: [Haskell-cafe] SYB supports genuine gmap. [Was: Polymorphic updating with TC/TFs?] Message-ID: <20131218090620.70627.qmail@www1.g3.pair.com> adam vogt wrote > Changing type parameters isn't supported by the ones I know (syb), but > you can still fake it: . SYB supports the type-changing generic map, of the signature > gmap2 :: forall a b c . (Data a, Data b, > Data (c a), Data (c b), Data (c X)) => > (a -> b) -> c a -> c b It was discovered back in 2008. Please see the following thread starting http://www.haskell.org/pipermail/generics/2008-July/000349.html The fake described in haskellwiki/SYB#fmap with unsafeCoerce is not needed at all. There is a genuine gmap. From mno2.111 at gmail.com Wed Dec 18 10:12:52 2013 From: mno2.111 at gmail.com (Paul Meng) Date: Wed, 18 Dec 2013 02:12:52 -0800 (PST) Subject: [Haskell-cafe] Haskell Singapore Meetup Message-ID: <8e682203-ee48-4536-99af-276a2a56a573@googlegroups.com> Hi all, I've already posted on the reddit but forgot to post it here. It's going to be Christmas, and a good way to celebrate it is to have a Haskell meetup. On this Friday, Dec 20. We are going to host it at Google Singapore office. http://www.meetup.com/HASKELL-SG/events/154702892/ There would be a short sharing and have some time to meet with other Haskell programmers (or FP programmer in general) after the talk. If you happen to be in Singapore, welcome to stop by! For people signed up before, notice that we are moving from Zalora to Google's office to have a bigger meeting room. And due to the access policy, please fill out your full name, e-mail and company in the following form. https://docs.google.com/forms/d/1pTQA3eK7Qsxbq_Tw8nPPX6MIUnQuGsm23rT5bfhtw-8/viewform Paul Meng -------------- next part -------------- An HTML attachment was scrubbed... URL: From agocorona at gmail.com Wed Dec 18 10:40:21 2013 From: agocorona at gmail.com (Alberto G. Corona ) Date: Wed, 18 Dec 2013 11:40:21 +0100 Subject: [Haskell-cafe] [Haskell] Monad.Reader #23 call for copy In-Reply-To: <1387337224-sup-6516@sabre> References: <1387337224-sup-6516@sabre> Message-ID: Hi Edward: I will send to you an updated copy of article about MFlow that I sent to you for the past issue of TMR. If you remember, we agreed to postpone it due to the quantity of material. So I have priority now!. Thanks 2013/12/18 Edward Z. Yang > Call for Copy: The Monad.Reader - Issue 23 > -------------------------------------------- > > Whether you're an established academic or have only just started > learning Haskell, if you have something to say, please consider writing > an article for The Monad.Reader! The submission deadline for Issue 23 > will be: > > **Friday, January 17, 2014** > > The Monad.Reader > ~~~~~~~~~~~~~~~~ > > The Monad.Reader is a electronic magazine about all things Haskell. It > is less formal than journal, but somehow more enduring than a wiki- > page. There have been a wide variety of articles: exciting code > fragments, intriguing puzzles, book reviews, tutorials, and even > half-baked research ideas. > > Submission Details > ~~~~~~~~~~~~~~~~~~ > > Get in touch with me if you intend to submit something -- the sooner > you let me know what you're up to, the better. > > Please submit articles for the next issue to me by e-mail (ezyang at mit.edu > ). > > Articles should be written according to the guidelines available from > > http://themonadreader.wordpress.com/contributing/ > > Please submit your article in PDF, together with any source files you > used. The sources will be released together with the magazine under a > BSD license. > > If you would like to submit an article, but have trouble with LaTeX > please let me know and we'll work something out. > _______________________________________________ > Haskell mailing list > Haskell at haskell.org > http://www.haskell.org/mailman/listinfo/haskell > -- Alberto. -------------- next part -------------- An HTML attachment was scrubbed... URL: From fvillanustre at gmail.com Wed Dec 18 12:29:15 2013 From: fvillanustre at gmail.com (Flavio Villanustre) Date: Wed, 18 Dec 2013 07:29:15 -0500 Subject: [Haskell-cafe] Haskell and Big Data In-Reply-To: References: Message-ID: J-C, I've been trying to port Haskell to the Open Source HPCC Systems platform ( http://hpccsystems.com/) over the last couple of months, but been swamped by work and personal stuff, so I didn't move too far. In case you don't know much about it, this is a Big Data platform originally designed and built by LexisNexis (Reed Elsevier) about 15 years ago and released under an Apache 2.0 license a couple of years ago. This platform continues to be actively developed and extended and leverages clusters of nodes with share nothing architectures and local storage, over IP based networks. It presents several nice synergies with Haskell: the platform is coded in C++ (as opposed to Java) and has a high level dataflow programming language called ECL, which is compiled to C++, and already allows for embedding C++, Java, Python, Javascript and R, so adding Haskell using any of those existing examples should be fairly trivial and could be probably done in just a few hours worth of work (see python, for example: https://github.com/hpcc-systems/HPCC-Platform/blob/master/plugins/pyembed/pyembed.cpp). Since ECL advocates non-strictness through purity too, with pure Haskell code the ECL compiler should be fairly free to distribute and parallelize Haskell code quite efficiently across the entire cluster. Another interesting aspect of the HPCC Systems platform is that it has a programmable distributed real-time data retrieval component called Roxie (programmable in ECL too), so this same work would also give Haskellers a distributed system for real-time large scale data delivery. I'm posting this response here, with the hope that someone may be willing to help out with this integration effort too. Kind regards, Flavio Flavio Villanustre On Wed, Dec 18, 2013 at 2:41 AM, jean-christophe mincke < jeanchristophe.mincke at gmail.com> wrote: > Hello Cafe, > > Big Data is a bit trendy these days. > > Does anybody know about plans to develop an Haskell eco-system in that > domain? > I.e tools such as Storm or Spark (possibly on top of Cloud Haskell) or, at > least, bindings to tools which exist in other languages. > > Thank you > > Regards > > J-C > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From vogt.adam at gmail.com Wed Dec 18 16:41:34 2013 From: vogt.adam at gmail.com (adam vogt) Date: Wed, 18 Dec 2013 11:41:34 -0500 Subject: [Haskell-cafe] SYB supports genuine gmap. [Was: Polymorphic updating with TC/TFs?] In-Reply-To: <20131218090620.70627.qmail@www1.g3.pair.com> References: <20131218090620.70627.qmail@www1.g3.pair.com> Message-ID: Hi Oleg, Interesting. I wasn't aware of that one when I wrote the "fake" version. I can see one small disadvantage for the "real" one: many hand-written data instances (ex. Data.Map) have defined: gunfold _ _ = error "gunfold" So the "real" version will fail there. On the other hand, the gfoldl defined in such instances is enough to support functions like `everywhere (mkT (+ (1::Integer)))'. For reference, the code moved from darcs.haskell.org to: Regards, Adam On Wed, Dec 18, 2013 at 4:06 AM, wrote: > > adam vogt wrote >> Changing type parameters isn't supported by the ones I know (syb), but >> you can still fake it: . > > SYB supports the type-changing generic map, of the signature >> gmap2 :: forall a b c . (Data a, Data b, >> Data (c a), Data (c b), Data (c X)) => >> (a -> b) -> c a -> c b > > It was discovered back in 2008. Please see the following thread starting > > http://www.haskell.org/pipermail/generics/2008-July/000349.html > > > The fake described in haskellwiki/SYB#fmap with unsafeCoerce is not > needed at all. There is a genuine gmap. > > From kiwamu at debian.or.jp Wed Dec 18 17:07:32 2013 From: kiwamu at debian.or.jp (Kiwamu Okabe) Date: Thu, 19 Dec 2013 02:07:32 +0900 Subject: [Haskell-cafe] ANNOUNCE: Ajhc Haskell Compiler 0.8.0.10 Release Message-ID: We are happy to announce Ajhc 0.8.0.10 as Christmas release! You can get Ajhc using "cabal install drift && cabal install ajhc" command. The usage is found at Ajhc's project web site http://ajhc.metasepi.org/. The source code at https://github.com/ajhc/ajhc. Welcome sending any bugs or your ideas to https://github.com/ajhc/ajhc/issues. ## News ### Android demo Android demo application using Haskell is available at Google Play. https://play.google.com/store/apps/details?id=org.metasepi.ajhc.android.cube ### Clear license notification * Runtime: [MIT License](https://github.com/ajhc/ajhc/blob/master/rts/LICENSE) * Haskell libraries: [MIT License](https://github.com/ajhc/ajhc/blob/master/lib/LICENSE) * The others: [GPLv2 or Later](https://github.com/ajhc/ajhc/blob/arafura/COPYING) ## Other changes * Depend on DrIFT again / Do not need derive * Fix GC root BUG * Use findExecutable instead of the raw `which` * Come back bytestring * And fix other BUGs Enjoy! :) - - - Metasepi team From andrew at operationaldynamics.com Thu Dec 19 00:58:21 2013 From: andrew at operationaldynamics.com (Andrew Cowie) Date: Thu, 19 Dec 2013 11:58:21 +1100 Subject: [Haskell-cafe] Persisting a Map Message-ID: <1387414701.14211.40.camel@nervous-energy.bridge.anchor.net.au> I have a Map. It's a lovely Map, with keys and values and everything. It's not _that_ large. Few 10s of MB at most. Unfortunately, I need to persist it somewhat reliably. I'd somewhat like to avoid having to use an external database (obviously a key/value store like Riak would work, but that's a major dependency to impose on the system) so I'm wondering if there is a low tech way to do this. I can control concurrent access to the file (or whatever), and the file system is robust. So that part is fine. I just need to externalize the map. I'm wondering if just using cereal or so would be sufficient (there is a Serialize instance, of course), or whether I should be using some acid-state thing, or a Haskell binding to gdbm, or sqlite, or... Any suggestions? AfC Sydney From cgaebel at uwaterloo.ca Thu Dec 19 02:30:54 2013 From: cgaebel at uwaterloo.ca (Clark Gaebel) Date: Wed, 18 Dec 2013 21:30:54 -0500 Subject: [Haskell-cafe] Persisting a Map In-Reply-To: <1387414701.14211.40.camel@nervous-energy.bridge.anchor.net.au> References: <1387414701.14211.40.camel@nervous-energy.bridge.anchor.net.au> Message-ID: Maybe acid-state [1]? [1] http://hackage.haskell.org/package/acid-state-0.12.1/docs/Data-Acid.html On Wed, Dec 18, 2013 at 7:58 PM, Andrew Cowie < andrew at operationaldynamics.com> wrote: > I have a Map. It's a lovely Map, with keys and values and everything. > It's not _that_ large. Few 10s of MB at most. Unfortunately, I need to > persist it somewhat reliably. > > I'd somewhat like to avoid having to use an external database (obviously > a key/value store like Riak would work, but that's a major dependency to > impose on the system) so I'm wondering if there is a low tech way to do > this. > > I can control concurrent access to the file (or whatever), and the file > system is robust. So that part is fine. I just need to externalize the > map. > > I'm wondering if just using cereal or so would be sufficient (there is a > Serialize instance, of course), or whether I should be using some > acid-state thing, or a Haskell binding to gdbm, or sqlite, or... > > Any suggestions? > > AfC > Sydney > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Clark. Key ID : 0x78099922 Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 -------------- next part -------------- An HTML attachment was scrubbed... URL: From ozgurakgun at gmail.com Thu Dec 19 03:11:24 2013 From: ozgurakgun at gmail.com (Ozgur Akgun) Date: Thu, 19 Dec 2013 03:11:24 +0000 Subject: [Haskell-cafe] Persisting a Map In-Reply-To: <1387414701.14211.40.camel@nervous-energy.bridge.anchor.net.au> References: <1387414701.14211.40.camel@nervous-energy.bridge.anchor.net.au> Message-ID: Hi. On 19 December 2013 00:58, Andrew Cowie wrote: > I'm wondering if just using cereal or so would be sufficient (there is a > Serialize instance, of course), or whether I should be using some > acid-state thing, or a Haskell binding to gdbm, or sqlite, or... > I've used cereal without any problems for a similar purpose before. I'd say go for it: it is very easy to use and pretty fast as well. Ozgur -------------- next part -------------- An HTML attachment was scrubbed... URL: From conrad at metadecks.org Thu Dec 19 03:24:20 2013 From: conrad at metadecks.org (Conrad Parker) Date: Thu, 19 Dec 2013 14:24:20 +1100 Subject: [Haskell-cafe] Persisting a Map In-Reply-To: <1387414701.14211.40.camel@nervous-energy.bridge.anchor.net.au> References: <1387414701.14211.40.camel@nervous-energy.bridge.anchor.net.au> Message-ID: On 19 December 2013 11:58, Andrew Cowie wrote: > I have a Map. It's a lovely Map, with keys and values and everything. > It's not _that_ large. Few 10s of MB at most. Unfortunately, I need to > persist it somewhat reliably. > > I'd somewhat like to avoid having to use an external database (obviously > a key/value store like Riak would work, but that's a major dependency to > impose on the system) so I'm wondering if there is a low tech way to do > this. > > I can control concurrent access to the file (or whatever), and the file > system is robust. So that part is fine. I just need to externalize the > map. > > I'm wondering if just using cereal or so would be sufficient (there is a > Serialize instance, of course), or whether I should be using some > acid-state thing, or a Haskell binding to gdbm, or sqlite, or... > > Any suggestions? > Do you need concurrent access to the on-disk map, or will you just load, modify, then store explicitly? Do you care about data corruption, eg. if your program/hardware fails during writing? I'd probably just use sqlite via something like esqueleto, because it's easy to inspect the stored data outside of your program. Conrad. -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at orlitzky.com Thu Dec 19 03:46:34 2013 From: michael at orlitzky.com (Michael Orlitzky) Date: Wed, 18 Dec 2013 22:46:34 -0500 Subject: [Haskell-cafe] Abstracting configuration directories Message-ID: <52B26C1A.7090206@orlitzky.com> I'm writing a small utility whose only non-portable code involves the two paths, /etc/htsnrc $HOME/.htsnrc These have sort-of analogues under Windows; in .NET they are available through something like, Environment.SpecialFolder.CommonApplicationData Environment.SpecialFolder.ApplicationData I personally will only ever need to run on Linux, but as a matter of principle I'd like to abstract the paths. Is there a library that can do this already? From andrew at operationaldynamics.com Thu Dec 19 05:29:14 2013 From: andrew at operationaldynamics.com (Andrew Cowie) Date: Thu, 19 Dec 2013 16:29:14 +1100 Subject: [Haskell-cafe] Persisting a Map In-Reply-To: References: <1387414701.14211.40.camel@nervous-energy.bridge.anchor.net.au> Message-ID: <1387430954.14211.47.camel@nervous-energy.bridge.anchor.net.au> Hey Conrad, On Thu, 2013-12-19 at 14:24 +1100, Conrad Parker wrote: > Do you need concurrent access to the on-disk map, or will you just > load, modify, then store explicitly? The latter. There will be occasional updates to the map, but I can signal the workers using it to reload and/or restart them periodically. > Do you care about data corruption, eg. if your program/hardware fails > during writing? My backing store gives me atomic writes, so that's not a problem here [makes lots of problems go away. Remarkable, really]. > I'd probably just use sqlite via something like esqueleto, because > it's easy to inspect the stored data outside of your program. Yeah, if external inspection were necessary that'd definitely be a good reason to go that way for sure. The report from Ozgur that just serializing out a Map structure was workable is encouraging, though. I'll start with that. AfC Sydney From tim at blitzcode.net Thu Dec 19 06:40:02 2013 From: tim at blitzcode.net (Tim C. Schroeder) Date: Thu, 19 Dec 2013 07:40:02 +0100 Subject: [Haskell-cafe] Abstracting configuration directories In-Reply-To: <52B26C1A.7090206@orlitzky.com> References: <52B26C1A.7090206@orlitzky.com> Message-ID: I think this is what you're looking for: http://hackage.haskell.org/package/directory-1.2.0.1/docs/System-Directory.html#g:2 Cheers, Tim On Dec 19, 2013, at 4:46 AM, Michael Orlitzky wrote: > I'm writing a small utility whose only non-portable code involves the > two paths, > > /etc/htsnrc > $HOME/.htsnrc > > These have sort-of analogues under Windows; in .NET they are available > through something like, > > Environment.SpecialFolder.CommonApplicationData > Environment.SpecialFolder.ApplicationData > > I personally will only ever need to run on Linux, but as a matter of > principle I'd like to abstract the paths. Is there a library that can do > this already? > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From mbrock at goula.sh Thu Dec 19 09:42:15 2013 From: mbrock at goula.sh (Mikael Brockman) Date: Thu, 19 Dec 2013 10:42:15 +0100 Subject: [Haskell-cafe] Persisting a Map References: <1387414701.14211.40.camel@nervous-energy.bridge.anchor.net.au> <1387430954.14211.47.camel@nervous-energy.bridge.anchor.net.au> Message-ID: Andrew Cowie writes: > Yeah, if external inspection were necessary that'd definitely be a good > reason to go that way for sure. The report from Ozgur that just > serializing out a Map structure was workable is encouraging, though. > I'll start with that. Pardon the digression, but I'd just like to appreciate this way of thinking. There's a rant by Bob Martin [1] that concludes: > "We are heading into an interesting time. A time when the prohibition > against different data storage mechanisms has been lifted, and we are > free to experiment with many novel new approaches. But as we play with > our CouchDBs and our Mongos and BigTables, remember this: The database > is just a detail that you don?t need to figure out right away." A project I'm working on uses a persistent append-only list, which is currently implemented like this, almost verbatim: async . forever $ atomically (readTChan queue) >>= writeFile path . Aeson.encode Files are trivial to back up and generally easy to work with. Since it's just JSON, I can grep and mess with it easily with command-line tools. And since the writing is done in a separate thread reading from a queue, I don't need to worry about locking. I think this will be alright for a good while, and when the project outgrows it, I'll just migrate to some other solution. Probably acid-state, because the version migration stuff seems really useful. [1]: Bob Martin's rant "No DB", http://blog.8thlight.com/uncle-bob/2012/05/15/NODB.html -- Mikael Brockman From agocorona at gmail.com Thu Dec 19 11:21:15 2013 From: agocorona at gmail.com (Alberto G. Corona ) Date: Thu, 19 Dec 2013 12:21:15 +0100 Subject: [Haskell-cafe] Persisting a Map In-Reply-To: References: <1387414701.14211.40.camel@nervous-energy.bridge.anchor.net.au> <1387430954.14211.47.camel@nervous-energy.bridge.anchor.net.au> Message-ID: Thanks for the reference. I agree with the rant word by word. I use tcache . It is a cache with access and update in the STM monad and each element can have its own persistence, defined by the programmer. So an element can be the result of a web service request for example from AWS, another from a database and a third from anywhere. the three can participate in the same STM transaction in memory and update their respective storages, if they are modified. These are the kinds of things are not possible in conventional databases. It is easy to create a almost a perfect product if you establishes the rules of perfection and you sit at the center of the development process that is what the SQL databases did for a long time. The DBs stayed at the protective womb of the back-office, with a few queries per second and being consistent with themselves and with nothing else. Now things have changed. We need their STM transactions working for us close to fresh application data at full speed, not in the backoffice. We need our data spread across different locations. We have no other option. We need to synchronize and integrate more than ever, so we need software and developers that can figure out what the data is about by looking at it, so the schema must be implicit in the data and so on. 2013/12/19 Mikael Brockman > Andrew Cowie writes: > > > Yeah, if external inspection were necessary that'd definitely be a good > > reason to go that way for sure. The report from Ozgur that just > > serializing out a Map structure was workable is encouraging, though. > > I'll start with that. > > Pardon the digression, but I'd just like to appreciate this way of > thinking. There's a rant by Bob Martin [1] that concludes: > > > "We are heading into an interesting time. A time when the prohibition > > against different data storage mechanisms has been lifted, and we are > > free to experiment with many novel new approaches. But as we play with > > our CouchDBs and our Mongos and BigTables, remember this: The database > > is just a detail that you don?t need to figure out right away." > > A project I'm working on uses a persistent append-only list, which is > currently implemented like this, almost verbatim: > > async . forever $ > atomically (readTChan queue) >>= writeFile path . Aeson.encode > > Files are trivial to back up and generally easy to work with. Since > it's just JSON, I can grep and mess with it easily with command-line > tools. And since the writing is done in a separate thread reading from > a queue, I don't need to worry about locking. > > I think this will be alright for a good while, and when the project > outgrows it, I'll just migrate to some other solution. Probably > acid-state, because the version migration stuff seems really useful. > > [1]: Bob Martin's rant "No DB", > http://blog.8thlight.com/uncle-bob/2012/05/15/NODB.html > > -- > Mikael Brockman > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Alberto. -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at orlitzky.com Thu Dec 19 17:15:09 2013 From: michael at orlitzky.com (Michael Orlitzky) Date: Thu, 19 Dec 2013 12:15:09 -0500 Subject: [Haskell-cafe] Abstracting configuration directories In-Reply-To: References: <52B26C1A.7090206@orlitzky.com> Message-ID: <52B3299D.201@orlitzky.com> On 12/19/2013 01:40 AM, Tim C. Schroeder wrote: > I think this is what you're looking for: > > http://hackage.haskell.org/package/directory-1.2.0.1/docs/System-Directory.html#g:2 > getAppUserDataDirectory will give me the user's configuration directory (ala $HOME/.htsnrc), but not the global one (whatever I'm supposed to use instead of /etc on Windows). A non-default config is necessary for the application to work at all, so it would be nice to be able to install one globally (so each user doesn't have to copy the example and modify it). Then again, until my patches allowing cabal to emit electric shocks are accepted, that may just have to be the punishment for using Windows. From depot051 at gmail.com Thu Dec 19 17:15:18 2013 From: depot051 at gmail.com (He-chien Tsai) Date: Fri, 20 Dec 2013 01:15:18 +0800 Subject: [Haskell-cafe] Haskell and Big Data In-Reply-To: References: Message-ID: have you took a look at hlearn and statistics packages? it's even easy to parallellize hlearn on cluster because it's training result is designed for composable, which means you can create two model , train them seperately and finally combine them. you can also use other database such as redis or cassandra,which has haskell binding, as backend. for parallellizing on clusters, hdph is also good. I personally prefer python for data science because it has much more mature packages and is more interactive and more effective (not kidding. you can create compiled C for core datas and algorithms by python-like cython and call it from python, and exploit gpus for accelerating by theano) than haskell and scala, spark also has a unfinish python binding. 2013/12/18 ??3:41 ? "jean-christophe mincke" < jeanchristophe.mincke at gmail.com> ??? > > Hello Cafe, > > Big Data is a bit trendy these days. > > Does anybody know about plans to develop an Haskell eco-system in that domain? > I.e tools such as Storm or Spark (possibly on top of Cloud Haskell) or, at least, bindings to tools which exist in other languages. > > Thank you > > Regards > > J-C > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From horstmey at Mathematik.Uni-Marburg.de Thu Dec 19 17:16:17 2013 From: horstmey at Mathematik.Uni-Marburg.de (Thomas Horstmeyer) Date: Thu, 19 Dec 2013 18:16:17 +0100 Subject: [Haskell-cafe] Indirect Cycle Detection problem [was: finding "good work" in CS] In-Reply-To: References: Message-ID: <52B329E1.1040109@informatik.uni-marburg.de> Hi Richard, Am 09.12.2013 04:00, schrieb Richard A. O'Keefe: > > [...] > Here's a piece of computer science that I would like some help > with. I call it the Indirect Cycle Detection problem. > > Given: Domains P and E, > functions f : P -> Maybe P > g : P -> E > > Define to_list :: Maybe P -> [E] > to_list Nothing = [] > to_list (Just p) = g p : to_list (f p) > > Given: That f is cyclic starting at p0. > > Find: The shortest alpha, beta such that > to_list p0 is alpha ++ cycle beta > and do so *efficiently*. > > Now, I can use tortoise-and-hare to find a cycle in f > and then use brute force to find a shortest prefix and > cycle of to_list ... The stuff I've checked so far > about periods in strings has nothing to say about > periods that begin _after_ a non-empty prefix. > I am not sure if you're really looking for help here or just wanted to present an example. I assume the former. Also, I can not see where this "non-empty prefix" notion comes from. Perhaps you have a different definition for cyclic? For me: "f is cyclic starting at p0" means there exist an N>0 such that f^N p0 == p0. Let's assume n to be the smallest number that fulfills this condition and call it the period length of f_p0. f_p0 defines a periodic list ps with the same period length n. ps = map fromJust $ iterate (>>= f) (Just p0) Your (to_list p0), which I'd like to call es could now be written as: es = map g ps We know that es has a period of length n, but if g is not injective, its smallest period of length k may be smaller than n. period_n = take n es To find k, we search for the second occurrence of period_n in (period_n ++ period_n), knowing that it will be at position n, if it is not found at positions [1..n-1]. We might use the fact that it can only be in positions that divide n. On the other hand, we could just use any of the well known string-search-methods. Efficiency: - If computation of f is done in constant time, finding n takes Theta(n) time. Just apply f until you reach p0 again. - Searching a pattern of size n in a text of size 2n can be done in O(n) using the Knuth-Morris-Pratt-algorithm. In total you have a linear algorithm for finding your result: alpha = [] beta = take k es = take k period_n ***** Of course, I guess now you're going to tell me that your "non-empty prefix" means that the period of f is not starting at p0 but at some pi that is reached by applying f i times to p0. You can adapt to that, but you have to pay for it ;-) In this case, ps has the form (prefix ++ (cycle p_period_n)) and to find this structure, you need to find the first element of ps that occurs twice. (Before, you knew this would be p0.) For that, you need a set implementation for elements of P that gives you efficient adding of one element and lookup. Since we know nothing about P's elements, we use the list itself and get a runtime of Theta((i+n)^2). Finding the (smallest) period k in es is exactly the same as before, i.e. we look for the second occurrence of period_n in (period_n ++ period_n) with period_n = map g p_period_n The prefix does not bother us here, because we know that we are looking at the periodic part. Now that we know the period length k, we still have to find where it starts. For that we start at position i and go backwards until we find a difference to the found out period. That is, we find the position of the first mismatch between (reverse $ take i es) and (cycle (reverse $ take k period_n)). The index tells us the length of alpha and the rotation needed to get beta from (take k period_n). The cost for that is O(i). So, the total cost in this case would be O((i+n)^2 + n + i). I could have implemented this in Haskell, but since the point in the original discussion was about not needing programmer skills, but CS skills, I refrained from it. Haskell is only used to clarify points, in a language which both he recipient and the recipient know. :-) Thomas From carter.schonwald at gmail.com Thu Dec 19 17:26:09 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 19 Dec 2013 12:26:09 -0500 Subject: [Haskell-cafe] Haskell and Big Data In-Reply-To: References: Message-ID: There are a number of Haskell projects for large scale data analysis that are likely to be released over the coming months. On the high performance front, it's worth noting that pretty much every usable python tool for gpu computing has to replicate the typing discipline that Haskell libs like accelerate get for free. On Thursday, December 19, 2013, He-chien Tsai wrote: > have you took a look at hlearn and statistics packages? it's even easy to > parallellize hlearn on cluster because it's training result is designed for > composable, which means you can create two model , train them seperately > and finally combine them. you can also use other database such as redis or > cassandra,which has haskell binding, as backend. for parallellizing on > clusters, hdph is also good. > > I personally prefer python for data science because it has much more > mature packages and is more interactive and more effective (not kidding. > you can create compiled C for core datas and algorithms by python-like > cython and call it from python, and exploit gpus for accelerating by > theano) than haskell and scala, spark also has a unfinish python binding. > > 2013/12/18 ??3:41 ? "jean-christophe mincke" < > jeanchristophe.mincke at gmail.com 'jeanchristophe.mincke at gmail.com');>> ??? > > > > Hello Cafe, > > > > Big Data is a bit trendy these days. > > > > Does anybody know about plans to develop an Haskell eco-system in that > domain? > > I.e tools such as Storm or Spark (possibly on top of Cloud Haskell) or, > at least, bindings to tools which exist in other languages. > > > > Thank you > > > > Regards > > > > J-C > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org 'Haskell-Cafe at haskell.org');> > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From colinpauladams at gmail.com Thu Dec 19 17:29:02 2013 From: colinpauladams at gmail.com (Colin Adams) Date: Thu, 19 Dec 2013 17:29:02 +0000 Subject: [Haskell-cafe] Abstracting configuration directories In-Reply-To: <52B3299D.201@orlitzky.com> References: <52B26C1A.7090206@orlitzky.com> <52B3299D.201@orlitzky.com> Message-ID: On 19 December 2013 17:15, Michael Orlitzky wrote: > > Then again, until my > patches allowing cabal to emit electric shocks are accepted, that may > just have to be the punishment for using Windows. > The virus writers' union might object to that - that's there job. > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From iavor.diatchki at gmail.com Thu Dec 19 17:34:57 2013 From: iavor.diatchki at gmail.com (Iavor Diatchki) Date: Thu, 19 Dec 2013 09:34:57 -0800 Subject: [Haskell-cafe] Job opportunities at Galois Inc. Message-ID: Hello, Galois is still hiring! We are located in beautiful Portland, Oregon and are currently looking for researchers, principal investigators, and software engineers, including those with expertise in functional programming, formal methods, computer security, control systems, informatics, or networking. For more information, take a look at http://corp.galois.com/careers and please feel free to drop me an e-mail if you have questions. Happy Holidays, -Iavor -------------- next part -------------- An HTML attachment was scrubbed... URL: From dstcruz at gmail.com Fri Dec 20 04:02:05 2013 From: dstcruz at gmail.com (Daniel Santa Cruz) Date: Thu, 19 Dec 2013 23:02:05 -0500 Subject: [Haskell-cafe] Haskell Weekly News: Issue 288 Message-ID: Welcome to issue 288 of the HWN, an issue covering crowd-sourced bits of information about Haskell from around the web. This issue covers the week from December 08 to 14, 2013. Quotes of the Week * nlogax: With FRP.Sodium and Graphics.UI.GLUT you could put together a MonadSodium GLUTamate Top Reddit Stories * The reason why `cabal update` takes so long Domain: github.com, Score: 175, Comments: 89 On Reddit: [1] http://goo.gl/NCsf34 Original: [2] http://goo.gl/BLp5LB * structured-haskell-mode ?? Structured editing minor mode for Haskell in Emacs Domain: github.com, Score: 103, Comments: 37 On Reddit: [3] http://goo.gl/t8dyd9 Original: [4] http://goo.gl/v6W7js * Amazing LVars talk by Linsey Kuper Domain: youtu.be, Score: 86, Comments: 20 On Reddit: [5] http://goo.gl/JcbNQn Original: [6] http://goo.gl/JPyVnG * 24 Days of Hackage: acid-state Domain: ocharles.org.uk, Score: 84, Comments: 15 On Reddit: [7] http://goo.gl/CBU18T Original: [8] http://goo.gl/W4u7GG * 24 Days of Hackage: pandoc Domain: ocharles.org.uk, Score: 66, Comments: 14 On Reddit: [9] http://goo.gl/rUO2yc Original: [10] http://goo.gl/PhTTFC * text 1.0.0.0 Domain: hackage.haskell.org, Score: 64, Comments: 25 On Reddit: [11] http://goo.gl/9k7ksP Original: [12] http://goo.gl/ISESbc * 24 Days of Hackage: async Domain: ocharles.org.uk, Score: 59, Comments: 11 On Reddit: [13] http://goo.gl/rhrdgM Original: [14] http://goo.gl/C4sQeh * 24 Days of Hackage: sbv (guest post by Tikhon Jelvis) Domain: ocharles.org.uk, Score: 57, Comments: 21 On Reddit: [15] http://goo.gl/YkLqo9 Original: [16] http://goo.gl/frHdyn * 24 Days of Hackage: data-memocombinators Domain: ocharles.org.uk, Score: 56, Comments: 18 On Reddit: [17] http://goo.gl/0FgDo6 Original: [18] http://goo.gl/4GcFKd * Bryan O'Sullivan - Package dependency management: more debate is needed Domain: plus.google.com, Score: 51, Comments: 45 On Reddit: [19] http://goo.gl/Xr7NkU Original: [20] http://goo.gl/f1VPxt * 24 Days of Hackage: gloss Domain: ocharles.org.uk, Score: 49, Comments: 10 On Reddit: [21] http://goo.gl/yBAlXk Original: [22] http://goo.gl/mplvhP * The future of array-oriented computing in Haskell ? a survey Domain: justtesting.org, Score: 45, Comments: 11 On Reddit: [23] http://goo.gl/doVpgz Original: [24] http://goo.gl/ezkftd * Progress Reporting in Shake Domain: neilmitchell.blogspot.it, Score: 42, Comments: 3 On Reddit: [25] http://goo.gl/1hvu6c Original: [26] http://goo.gl/4izrhK * [ANN] SFML and SFML-control Domain: self.haskell, Score: 40, Comments: 20 On Reddit: [27] http://goo.gl/NhMJbR Original: [28] http://goo.gl/NhMJbR * 24 Days of Hackage: heist Domain: ocharles.org.uk, Score: 40, Comments: 28 On Reddit: [29] http://goo.gl/FtvnLs Original: [30] http://goo.gl/nEU9Hw Top StackOverflow Questions * How are J/K/APL classified in terms of common paradigms? votes: 10, answers: 1 Read on SO: [31] http://goo.gl/ImISrG * Is it possible to extend free monad interpreters? votes: 9, answers: 5 Read on SO: [32] http://goo.gl/CiJupH * How to detect a Monad? votes: 8, answers: 4 Read on SO: [33] http://goo.gl/WiUhba * Why do Haskell type signature declarations have multiple arrows? votes: 7, answers: 3 Read on SO: [34] http://goo.gl/0LWfMb * ?Inheriting? instance of wrapped type votes: 7, answers: 1 Read on SO: [35] http://goo.gl/qBhrqD * Equality function for pair components votes: 7, answers: 1 Read on SO: [36] http://goo.gl/mLk49N * Motivation of having Functional Dependencies votes: 7, answers: 1 Read on SO: [37] http://goo.gl/E31zjJ * Haskell - Lenses, use of 'to' function votes: 7, answers: 1 Read on SO: [38] http://goo.gl/5A028y * What does PINNED mean in -hc profile of Haskell program? votes: 6, answers: 1 Read on SO: [39] http://goo.gl/Qx9eJB Until next time, [40]+Daniel Santa Cruz References 1. https://github.com/nominolo/HTTP/commit/b9bd0a08fa09c6403f91422e3b23f08d339612eb 2. http://www.reddit.com/r/haskell/comments/1sh67u/the_reason_why_cabal_update_takes_so_long/ 3. https://github.com/chrisdone/structured-haskell-mode 4. http://www.reddit.com/r/haskell/comments/1sd3aj/structuredhaskellmode_structured_editing_minor/ 5. http://youtu.be/8dFO5Ir0xqY 6. http://www.reddit.com/r/haskell/comments/1skf3x/amazing_lvars_talk_by_linsey_kuper/ 7. http://ocharles.org.uk/blog/posts/2013-12-14-24-days-of-hackage-acid-state.html 8. http://www.reddit.com/r/haskell/comments/1svlm2/24_days_of_hackage_acidstate/ 9. http://ocharles.org.uk/blog/guest-posts/2013-12-12-24-days-of-hackage-pandoc.html 10. http://www.reddit.com/r/haskell/comments/1srcz6/24_days_of_hackage_pandoc/ 11. http://hackage.haskell.org/package/text-1.0.0.0 12. http://www.reddit.com/r/haskell/comments/1st4jl/text_1000/ 13. http://ocharles.org.uk/blog/posts/2013-12-13-24-days-of-hackage-async.html 14. http://www.reddit.com/r/haskell/comments/1stf7l/24_days_of_hackage_async/ 15. http://ocharles.org.uk/blog/guest-posts/2013-12-09-24-days-of-hackage-sbv.html 16. http://www.reddit.com/r/haskell/comments/1shnr7/24_days_of_hackage_sbv_guest_post_by_tikhon_jelvis/ 17. http://ocharles.org.uk/blog/posts/2013-12-08-24-days-of-hackage-data-memocombinators.html 18. http://www.reddit.com/r/haskell/comments/1settx/24_days_of_hackage_datamemocombinators/ 19. https://plus.google.com/103469090998089605155/posts/HdC6oCy8RWW 20. http://www.reddit.com/r/haskell/comments/1sdwot/bryan_osullivan_package_dependency_management/ 21. http://ocharles.org.uk/blog/posts/2013-12-10-24-days-of-hackage-gloss.html 22. http://www.reddit.com/r/haskell/comments/1sl0y5/24_days_of_hackage_gloss/ 23. http://justtesting.org/post/69439080517/the-future-of-array-oriented-computing-in-haskell-a 24. http://www.reddit.com/r/haskell/comments/1sfg7l/the_future_of_arrayoriented_computing_in_haskell/ 25. http://neilmitchell.blogspot.it/2013/12/progress-reporting-in-shake.html 26. http://www.reddit.com/r/haskell/comments/1sqsyi/progress_reporting_in_shake/ 27. http://www.reddit.com/r/haskell/comments/1sjemq/ann_sfml_and_sfmlcontrol/ 28. http://www.reddit.com/r/haskell/comments/1sjemq/ann_sfml_and_sfmlcontrol/ 29. http://ocharles.org.uk/blog/posts/2013-12-11-24-days-of-hackage-heist.html 30. http://www.reddit.com/r/haskell/comments/1sob71/24_days_of_hackage_heist/ 31. http://stackoverflow.com/questions/20558170/how-are-j-k-apl-classified-in-terms-of-common-paradigms 32. http://stackoverflow.com/questions/20564633/is-it-possible-to-extend-free-monad-interpreters 33. http://stackoverflow.com/questions/20495627/how-to-detect-a-monad 34. http://stackoverflow.com/questions/20459981/why-do-haskell-type-signature-declarations-have-multiple-arrows 35. http://stackoverflow.com/questions/20481718/inheriting-instance-of-wrapped-type 36. http://stackoverflow.com/questions/20515404/equality-function-for-pair-components 37. http://stackoverflow.com/questions/20526828/motivation-of-having-functional-dependencies 38. http://stackoverflow.com/questions/20528718/haskell-lenses-use-of-to-function 39. http://stackoverflow.com/questions/20478805/what-does-pinned-mean-in-hc-profile-of-haskell-program 40. https://plus.google.com/105107667630152149014/about -------------- next part -------------- An HTML attachment was scrubbed... URL: From depot051 at gmail.com Fri Dec 20 07:19:41 2013 From: depot051 at gmail.com (He-chien Tsai) Date: Fri, 20 Dec 2013 15:19:41 +0800 Subject: [Haskell-cafe] Haskell and Big Data In-Reply-To: References: Message-ID: What I meant is that split the data into several parts,send each splited data to different computers, train them seperately, finally send the results back and combine those results. I didn't mean to use Cloud Haskell. 2013/12/20 ??5:40 ? "jean-christophe mincke" < jeanchristophe.mincke at gmail.com> ??? > > He-Chien Tsai, > > > its training result is designed for composable > > Yes it is indeed composable (parallel function of that lib) but parallelizing it on a cluster changes all the type because running on a cluster implies IO. > Moreover using Cloud Haskell (for instance) implies that: > 1. training functions should be (serializable) clojures, which can only be defined as module level (not as local -let/where - bindings). > 2. train is a typeclass function and is not serializable. > > So the idea behind HLearn are interesting but I do not see how it could be run on a cluster... But, unfortunately, I am not an Haskell expert. > > What do you think? > > Regards > > J-C > > > > On Thu, Dec 19, 2013 at 6:15 PM, He-chien Tsai wrote: >> >> have you took a look at hlearn and statistics packages? it's even easy to parallellize hlearn on cluster because it's training result is designed for composable, which means you can create two model , train them seperately and finally combine them. you can also use other database such as redis or cassandra,which has haskell binding, as backend. for parallellizing on clusters, hdph is also good. >> >> I personally prefer python for data science because it has much more mature packages and is more interactive and more effective (not kidding. you can create compiled C for core datas and algorithms by python-like cython and call it from python, and exploit gpus for accelerating by theano) than haskell and scala, spark also has a unfinish python binding. >> >> 2013/12/18 ??3:41 ? "jean-christophe mincke" < jeanchristophe.mincke at gmail.com> ??? >> >> >> > >> > Hello Cafe, >> > >> > Big Data is a bit trendy these days. >> > >> > Does anybody know about plans to develop an Haskell eco-system in that domain? >> > I.e tools such as Storm or Spark (possibly on top of Cloud Haskell) or, at least, bindings to tools which exist in other languages. >> > >> > Thank you >> > >> > Regards >> > >> > J-C >> > >> > _______________________________________________ >> > Haskell-Cafe mailing list >> > Haskell-Cafe at haskell.org >> > http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Fri Dec 20 07:24:46 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 20 Dec 2013 02:24:46 -0500 Subject: [Haskell-cafe] Haskell and Big Data In-Reply-To: References: Message-ID: Cloud Haskell is a substrate that could be used to build such a layer. I'm sure the cloud Haskell people would love such experimenration. On Friday, December 20, 2013, He-chien Tsai wrote: > What I meant is that split the data into several parts,send each splited > data to different computers, train them seperately, finally send the > results back and combine those results. I didn't mean to use Cloud Haskell. > > 2013/12/20 ??5:40 ? "jean-christophe mincke" < > jeanchristophe.mincke at gmail.com 'jeanchristophe.mincke at gmail.com');>> ??? > > > > He-Chien Tsai, > > > > > its training result is designed for composable > > > > Yes it is indeed composable (parallel function of that lib) but > parallelizing it on a cluster changes all the type because running on a > cluster implies IO. > > Moreover using Cloud Haskell (for instance) implies that: > > 1. training functions should be (serializable) clojures, which can only > be defined as module level (not as local -let/where - bindings). > > 2. train is a typeclass function and is not serializable. > > > > So the idea behind HLearn are interesting but I do not see how it could > be run on a cluster... But, unfortunately, I am not an Haskell expert. > > > > What do you think? > > > > Regards > > > > J-C > > > > > > > > On Thu, Dec 19, 2013 at 6:15 PM, He-chien Tsai > > wrote: > >> > >> have you took a look at hlearn and statistics packages? it's even easy > to parallellize hlearn on cluster because it's training result is designed > for composable, which means you can create two model , train them > seperately and finally combine them. you can also use other database such > as redis or cassandra,which has haskell binding, as backend. for > parallellizing on clusters, hdph is also good. > >> > >> I personally prefer python for data science because it has much more > mature packages and is more interactive and more effective (not kidding. > you can create compiled C for core datas and algorithms by python-like > cython and call it from python, and exploit gpus for accelerating by > theano) than haskell and scala, spark also has a unfinish python binding. > >> > >> 2013/12/18 ??3:41 ? "jean-christophe mincke" < > jeanchristophe.mincke at gmail.com 'jeanchristophe.mincke at gmail.com');>> ??? > >> > >> > >> > > >> > Hello Cafe, > >> > > >> > Big Data is a bit trendy these days. > >> > > >> > Does anybody know about plans to develop an Haskell eco-system in > that domain? > >> > I.e tools such as Storm or Spark (possibly on top of Cloud Haskell) > or, at least, bindings to tools which exist in other languages. > >> > > >> > Thank you > >> > > >> > Regards > >> > > >> > J-C > >> > > >> > _______________________________________________ > >> > Haskell-Cafe mailing list > >> > Haskell-Cafe at haskell.org 'Haskell-Cafe at haskell.org');> > >> > http://www.haskell.org/mailman/listinfo/haskell-cafe > >> > > > > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From hjgtuyl at chello.nl Fri Dec 20 11:29:03 2013 From: hjgtuyl at chello.nl (Henk-Jan van Tuyl) Date: Fri, 20 Dec 2013 12:29:03 +0100 Subject: [Haskell-cafe] Abstracting configuration directories In-Reply-To: <52B3299D.201@orlitzky.com> References: <52B26C1A.7090206@orlitzky.com> <52B3299D.201@orlitzky.com> Message-ID: On Thu, 19 Dec 2013 18:15:09 +0100, Michael Orlitzky wrote: > On 12/19/2013 01:40 AM, Tim C. Schroeder wrote: >> I think this is what you're looking for: >> >> http://hackage.haskell.org/package/directory-1.2.0.1/docs/System-Directory.html#g:2 >> > > getAppUserDataDirectory will give me the user's configuration directory > (ala $HOME/.htsnrc), but not the global one (whatever I'm supposed to > use instead of /etc on Windows). You could use the environment variable AllUsersProfile[0] for this. The directory package should be extended with a function getAppGlobalDataDirectory. Regards, Henk-Jan van Tuyl [0] http://environmentvariables.org/AllUsersProfile -- Folding at home What if you could share your unused computer power to help find a cure? In just 5 minutes you can join the world's biggest networked computer and get us closer sooner. Watch the video. http://folding.stanford.edu/ http://Van.Tuyl.eu/ http://members.chello.nl/hjgtuyl/tourdemonad.html Haskell programming -- From hjgtuyl at chello.nl Fri Dec 20 13:13:43 2013 From: hjgtuyl at chello.nl (Henk-Jan van Tuyl) Date: Fri, 20 Dec 2013 14:13:43 +0100 Subject: [Haskell-cafe] Abstracting configuration directories In-Reply-To: References: <52B26C1A.7090206@orlitzky.com> <52B3299D.201@orlitzky.com> Message-ID: On Fri, 20 Dec 2013 12:29:03 +0100, Henk-Jan van Tuyl wrote: > You could use the environment variable AllUsersProfile[0] for this. Another way to do this: Prelude> :m System.Win32 Prelude System.Win32> sHGetFolderPath nullPtr 35 nullPtr 0 "C:\\Documents and Settings\\All Users\\Application Data" Regards, Henk-Jan van Tuyl -- Folding at home What if you could share your unused computer power to help find a cure? In just 5 minutes you can join the world's biggest networked computer and get us closer sooner. Watch the video. http://folding.stanford.edu/ http://Van.Tuyl.eu/ http://members.chello.nl/hjgtuyl/tourdemonad.html Haskell programming -- From montezf at gmail.com Fri Dec 20 17:02:17 2013 From: montezf at gmail.com (Montez Fitzpatrick) Date: Fri, 20 Dec 2013 11:02:17 -0600 Subject: [Haskell-cafe] Fwd: Package Maintenance: dtd-types, dtd-text In-Reply-To: References: Message-ID: I would like to take over maintenance of the following two packages: "dtd-types" & "dtd-text". I have attempted to e-mail the original package author with no response. I realize this can be a busy time of the year; personally, I would have no problems what-so-ever when/if the original author returns to relinquish stewardship of the aforementioned packages. Montez -------------- next part -------------- An HTML attachment was scrubbed... URL: From j.v.eekelen at gmail.com Fri Dec 20 17:51:39 2013 From: j.v.eekelen at gmail.com (Joeri van Eekelen) Date: Fri, 20 Dec 2013 18:51:39 +0100 Subject: [Haskell-cafe] Abstracting configuration directories In-Reply-To: References: <52B26C1A.7090206@orlitzky.com> <52B3299D.201@orlitzky.com> Message-ID: <52B483AB.6070409@gmail.com> I think the "right" way to accomplish this is through the Paths_pkg module generated by Cabal: http://www.haskell.org/cabal/users-guide/developing-packages.html#accessing-data-files-from-package-code Specifically, the getDataFile function can be used to look up the actual location of files specified in the data-files: field of the .cabal file. This should even work if someone uses a nonstandard --prefix. On 2013-12-20 12:29, Henk-Jan van Tuyl wrote: > On Thu, 19 Dec 2013 18:15:09 +0100, Michael Orlitzky > wrote: > >> On 12/19/2013 01:40 AM, Tim C. Schroeder wrote: >>> I think this is what you're looking for: >>> >>> http://hackage.haskell.org/package/directory-1.2.0.1/docs/System-Directory.html#g:2 >>> >>> >> >> getAppUserDataDirectory will give me the user's configuration directory >> (ala $HOME/.htsnrc), but not the global one (whatever I'm supposed to >> use instead of /etc on Windows). > > You could use the environment variable AllUsersProfile[0] for this. > > The directory package should be extended with a function > getAppGlobalDataDirectory. > > Regards, > Henk-Jan van Tuyl > > > [0] http://environmentvariables.org/AllUsersProfile > > -- Joeri van Eekelen - j.v.eekelen at gmail.com From michael at orlitzky.com Fri Dec 20 19:09:55 2013 From: michael at orlitzky.com (Michael Orlitzky) Date: Fri, 20 Dec 2013 14:09:55 -0500 Subject: [Haskell-cafe] Abstracting configuration directories In-Reply-To: References: <52B26C1A.7090206@orlitzky.com> <52B3299D.201@orlitzky.com> Message-ID: <52B49603.9090803@orlitzky.com> On 12/20/2013 08:13 AM, Henk-Jan van Tuyl wrote: > On Fri, 20 Dec 2013 12:29:03 +0100, Henk-Jan van Tuyl > wrote: > >> You could use the environment variable AllUsersProfile[0] for this. > > Another way to do this: > > Prelude> :m System.Win32 > Prelude System.Win32> sHGetFolderPath nullPtr 35 nullPtr 0 > "C:\\Documents and Settings\\All Users\\Application Data" > Thanks, this is what getAppUserDataDirectory (from System.Directory) is doing: getAppUserDataDirectory :: String -> IO FilePath getAppUserDataDirectory appName = do ... s <- Win32.sHGetFolderPath nullPtr Win32.cSIDL_APPDATA nullPtr 0 ... I think your path above is the correct location on Win32; in that case, Windows makes it available[1] as CSIDL_COMMON_APPDATA. System.Win32 doesn't use this constant at the moment, but I think it could go in [2] along with the rest of them. Then, System.Directory could provide getAppGlobalDataDirectory as you suggest. A patch looks easy, but I'm not sure that I would call /etc the "global data directory" on Unix. I'll have to think about it some more. [1] http://msdn.microsoft.com/en-us/library/windows/desktop/bb762494%28v=vs.85%29.aspx [2] http://hackage.haskell.org/package/Win32-2.2.2.0/docs/System-Win32-Shell.html From michael at orlitzky.com Fri Dec 20 19:17:04 2013 From: michael at orlitzky.com (Michael Orlitzky) Date: Fri, 20 Dec 2013 14:17:04 -0500 Subject: [Haskell-cafe] Abstracting configuration directories In-Reply-To: <52B483AB.6070409@gmail.com> References: <52B26C1A.7090206@orlitzky.com> <52B3299D.201@orlitzky.com> <52B483AB.6070409@gmail.com> Message-ID: <52B497B0.2060607@orlitzky.com> On 12/20/2013 12:51 PM, Joeri van Eekelen wrote: > I think the "right" way to accomplish this is through the Paths_pkg > module generated by Cabal: > > http://www.haskell.org/cabal/users-guide/developing-packages.html#accessing-data-files-from-package-code > This is more for when you want to install a data file and don't care where, but you need to be able to find it later. My configuration file should wind up in a fixed location (e.g. /etc on Linux); I'm just not sure where that is on Windows, and I don't want to have to hard-code it in case it changes in Windows 3000. Thanks for the suggestion though. From jeff at alephcloud.com Fri Dec 20 22:43:41 2013 From: jeff at alephcloud.com (Jeff Polakow) Date: Fri, 20 Dec 2013 22:43:41 +0000 Subject: [Haskell-cafe] Haskell Job Opportunity Message-ID: AlephCloud is an early stage Silicon Valley startup creating a secure cloud content management system. Haskell is our main server side language and we are looking to hire a few more Haskell programmers. Some topics of interest to us are: cloud services, cryptography/security, cross compilation (javascript, iOS, ARM). We are somewhat flexible about location, though we?d prefer people on the west coast of the US. If interested feel free to contact me (jeff at alephcloud.com) for more information, or send a message (and/or a resume) to resume at alephcloud.com. thanks, Jeff From reilithion at gmail.com Fri Dec 20 23:30:11 2013 From: reilithion at gmail.com (Lucas Paul) Date: Fri, 20 Dec 2013 16:30:11 -0700 Subject: [Haskell-cafe] Troubleshooting-type questions Message-ID: I wouldn't want to clutter the list with off-topic stuff, so I'll ask first. Once in a while I'll have trouble trying to use some piece of software, like Shpider or Yesod. Is it on-topic to ask specific "how-do-I-use/do"-type questions for particular packages like that on this list? -- Lucas Paul From bytbox at gmail.com Fri Dec 20 23:29:06 2013 From: bytbox at gmail.com (Scott Lawrence) Date: Fri, 20 Dec 2013 18:29:06 -0500 (EST) Subject: [Haskell-cafe] Troubleshooting-type questions In-Reply-To: References: Message-ID: A poem: This is -cafe. Fire away. On Fri, 20 Dec 2013, Lucas Paul wrote: > I wouldn't want to clutter the list with off-topic stuff, so I'll ask first. > > Once in a while I'll have trouble trying to use some piece of > software, like Shpider or Yesod. Is it on-topic to ask specific > "how-do-I-use/do"-type questions for particular packages like that on > this list? > > -- > Lucas Paul > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Scott Lawrence From tikhon at jelv.is Fri Dec 20 23:33:06 2013 From: tikhon at jelv.is (Tikhon Jelvis) Date: Fri, 20 Dec 2013 15:33:06 -0800 Subject: [Haskell-cafe] Troubleshooting-type questions In-Reply-To: References: Message-ID: For really specific questions, you might be best off on IRC. There is the general #haskell channel on Freenode as well as specific ones for certain major libraries like lens and Yesod. On Dec 20, 2013 3:30 PM, "Lucas Paul" wrote: > I wouldn't want to clutter the list with off-topic stuff, so I'll ask > first. > > Once in a while I'll have trouble trying to use some piece of > software, like Shpider or Yesod. Is it on-topic to ask specific > "how-do-I-use/do"-type questions for particular packages like that on > this list? > > -- > Lucas Paul > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Fri Dec 20 23:44:29 2013 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Fri, 20 Dec 2013 23:44:29 +0000 Subject: [Haskell-cafe] Troubleshooting-type questions In-Reply-To: References: Message-ID: <20131220234429.GC17875@weber> On Fri, Dec 20, 2013 at 03:33:06PM -0800, Tikhon Jelvis wrote: > For really specific questions, you might be best off on IRC. There is the > general #haskell channel on Freenode as well as specific ones for certain > major libraries like lens and Yesod. Furthermore, http://stackoverflow.com/ is very responsive to Haskell questions. From alexander.kjeldaas at gmail.com Sat Dec 21 13:50:51 2013 From: alexander.kjeldaas at gmail.com (Alexander Kjeldaas) Date: Sat, 21 Dec 2013 14:50:51 +0100 Subject: [Haskell-cafe] Haskell and Big Data In-Reply-To: References: Message-ID: In the HPCC documentation it is hard to cut through the buzzword jungle. Is there an efficient storage solution lurking there? I searched for haskell packages related to the big data storage layer, and the only thing I've found that could support efficient erasure code-based storage is this 3 years old binding to libhdfs. There is only one commit in github: https://github.com/kim/hdfs-haskell Somewhat related are these bindings to zfec, from 2008, and part of the Tahoe LAFS project. http://hackage.haskell.org/package/fec Alexander On Fri, Dec 20, 2013 at 8:24 AM, Carter Schonwald < carter.schonwald at gmail.com> wrote: > Cloud Haskell is a substrate that could be used to build such a layer. > I'm sure the cloud Haskell people would love such experimenration. > > > On Friday, December 20, 2013, He-chien Tsai wrote: > >> What I meant is that split the data into several parts,send each splited >> data to different computers, train them seperately, finally send the >> results back and combine those results. I didn't mean to use Cloud Haskell. >> >> 2013/12/20 ??5:40 ? "jean-christophe mincke" < >> jeanchristophe.mincke at gmail.com> ??? >> > >> > He-Chien Tsai, >> > >> > > its training result is designed for composable >> > >> > Yes it is indeed composable (parallel function of that lib) but >> parallelizing it on a cluster changes all the type because running on a >> cluster implies IO. >> > Moreover using Cloud Haskell (for instance) implies that: >> > 1. training functions should be (serializable) clojures, which can only >> be defined as module level (not as local -let/where - bindings). >> > 2. train is a typeclass function and is not serializable. >> > >> > So the idea behind HLearn are interesting but I do not see how it could >> be run on a cluster... But, unfortunately, I am not an Haskell expert. >> > >> > What do you think? >> > >> > Regards >> > >> > J-C >> > >> > >> > >> > On Thu, Dec 19, 2013 at 6:15 PM, He-chien Tsai >> wrote: >> >> >> >> have you took a look at hlearn and statistics packages? it's even easy >> to parallellize hlearn on cluster because it's training result is designed >> for composable, which means you can create two model , train them >> seperately and finally combine them. you can also use other database such >> as redis or cassandra,which has haskell binding, as backend. for >> parallellizing on clusters, hdph is also good. >> >> >> >> I personally prefer python for data science because it has much more >> mature packages and is more interactive and more effective (not kidding. >> you can create compiled C for core datas and algorithms by python-like >> cython and call it from python, and exploit gpus for accelerating by >> theano) than haskell and scala, spark also has a unfinish python binding. >> >> >> >> 2013/12/18 ??3:41 ? "jean-christophe mincke" < >> jeanchristophe.mincke at gmail.com> ??? >> >> >> >> >> >> > >> >> > Hello Cafe, >> >> > >> >> > Big Data is a bit trendy these days. >> >> > >> >> > Does anybody know about plans to develop an Haskell eco-system in >> that domain? >> >> > I.e tools such as Storm or Spark (possibly on top of Cloud Haskell) >> or, at least, bindings to tools which exist in other languages. >> >> > >> >> > Thank you >> >> > >> >> > Regards >> >> > >> >> > J-C >> >> > >> >> > _______________________________________________ >> >> > Haskell-Cafe mailing list >> >> > Haskell-Cafe at haskell.org >> >> > http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > >> > >> > >> > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From fvillanustre at gmail.com Sat Dec 21 15:52:47 2013 From: fvillanustre at gmail.com (Flavio Villanustre) Date: Sat, 21 Dec 2013 10:52:47 -0500 Subject: [Haskell-cafe] Haskell and Big Data In-Reply-To: References: Message-ID: Alexander, The distributed storage in the HPCC platform relies on an underlying Posix compliant Linux filesystem (any will do), and provides an abstraction layer based on record oriented (as opposed to block oriented, like HDFS) fileparts located in the local storage of the physical nodes. It also uses a component called Dali which, among other things, is a metadata server that provides a "logical file" view of these partitioned data files, and the system provides the tooling to create them from an external data source (in a process called spray). While you could conceivably use the distributed file system in HPCC as a stand alone data repository, I think that it would be more interesting to take advantage of the data processing machinery too. The HPCC platform has already a declarative dataflow language called ECL which, coincidentally, advocates purity, is non-strict (implemented through laziness) and compiles into C++ (and uses g++/clang to compile this into machine code). Since ECL already allows for embedded C++, Python, R, Java and Javascript, allowing Haskell to be embedded too (through FFI?) would be the best integration option, IMO. I'm copying Richard, Jake and Gavin, who are the ones that wrote most of the original code base for the distributed filesystem and ECL compiler (among many other parts), and perhaps can provide some ideas/pointers. Flavio Flavio Villanustre On Sat, Dec 21, 2013 at 8:50 AM, Alexander Kjeldaas < alexander.kjeldaas at gmail.com> wrote: > > In the HPCC documentation it is hard to cut through the buzzword jungle. > Is there an efficient storage solution lurking there? > > I searched for haskell packages related to the big data storage layer, and > the only thing I've found that could support efficient erasure code-based > storage is this 3 years old binding to libhdfs. There is only one commit > in github: > > https://github.com/kim/hdfs-haskell > > Somewhat related are these bindings to zfec, from 2008, and part of the > Tahoe LAFS project. > > http://hackage.haskell.org/package/fec > > > Alexander > > > > On Fri, Dec 20, 2013 at 8:24 AM, Carter Schonwald < > carter.schonwald at gmail.com> wrote: > >> Cloud Haskell is a substrate that could be used to build such a layer. >> I'm sure the cloud Haskell people would love such experimenration. >> >> >> On Friday, December 20, 2013, He-chien Tsai wrote: >> >>> What I meant is that split the data into several parts,send each splited >>> data to different computers, train them seperately, finally send the >>> results back and combine those results. I didn't mean to use Cloud Haskell. >>> >>> 2013/12/20 ??5:40 ? "jean-christophe mincke" < >>> jeanchristophe.mincke at gmail.com> ??? >>> > >>> > He-Chien Tsai, >>> > >>> > > its training result is designed for composable >>> > >>> > Yes it is indeed composable (parallel function of that lib) but >>> parallelizing it on a cluster changes all the type because running on a >>> cluster implies IO. >>> > Moreover using Cloud Haskell (for instance) implies that: >>> > 1. training functions should be (serializable) clojures, which can >>> only be defined as module level (not as local -let/where - bindings). >>> > 2. train is a typeclass function and is not serializable. >>> > >>> > So the idea behind HLearn are interesting but I do not see how it >>> could be run on a cluster... But, unfortunately, I am not an Haskell expert. >>> > >>> > What do you think? >>> > >>> > Regards >>> > >>> > J-C >>> > >>> > >>> > >>> > On Thu, Dec 19, 2013 at 6:15 PM, He-chien Tsai >>> wrote: >>> >> >>> >> have you took a look at hlearn and statistics packages? it's even >>> easy to parallellize hlearn on cluster because it's training result is >>> designed for composable, which means you can create two model , train them >>> seperately and finally combine them. you can also use other database such >>> as redis or cassandra,which has haskell binding, as backend. for >>> parallellizing on clusters, hdph is also good. >>> >> >>> >> I personally prefer python for data science because it has much more >>> mature packages and is more interactive and more effective (not kidding. >>> you can create compiled C for core datas and algorithms by python-like >>> cython and call it from python, and exploit gpus for accelerating by >>> theano) than haskell and scala, spark also has a unfinish python binding. >>> >> >>> >> 2013/12/18 ??3:41 ? "jean-christophe mincke" < >>> jeanchristophe.mincke at gmail.com> ??? >>> >> >>> >> >>> >> > >>> >> > Hello Cafe, >>> >> > >>> >> > Big Data is a bit trendy these days. >>> >> > >>> >> > Does anybody know about plans to develop an Haskell eco-system in >>> that domain? >>> >> > I.e tools such as Storm or Spark (possibly on top of Cloud Haskell) >>> or, at least, bindings to tools which exist in other languages. >>> >> > >>> >> > Thank you >>> >> > >>> >> > Regards >>> >> > >>> >> > J-C >>> >> > >>> >> > _______________________________________________ >>> >> > Haskell-Cafe mailing list >>> >> > Haskell-Cafe at haskell.org >>> >> > http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >> > >>> > >>> > >>> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Sat Dec 21 17:30:34 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sat, 21 Dec 2013 12:30:34 -0500 Subject: [Haskell-cafe] Haskell and Big Data In-Reply-To: References: Message-ID: Interesting. Does it have a design that let's computation be structured in a locality aware way? (I'd imagine yes, but I'm Afk much of this week so it's a bit hard to read docs) On Saturday, December 21, 2013, Flavio Villanustre wrote: > Alexander, > > The distributed storage in the HPCC platform relies on an underlying Posix > compliant Linux filesystem (any will do), and provides an abstraction layer > based on record oriented (as opposed to block oriented, like HDFS) > fileparts located in the local storage of the physical nodes. It also uses > a component called Dali which, among other things, is a metadata server > that provides a "logical file" view of these partitioned data files, and > the system provides the tooling to create them from an external data source > (in a process called spray). > > While you could conceivably use the distributed file system in HPCC as a > stand alone data repository, I think that it would be more interesting to > take advantage of the data processing machinery too. The HPCC platform has > already a declarative dataflow language called ECL which, coincidentally, > advocates purity, is non-strict (implemented through laziness) and compiles > into C++ (and uses g++/clang to compile this into machine code). Since ECL > already allows for embedded C++, Python, R, Java and Javascript, allowing > Haskell to be embedded too (through FFI?) would be the best integration > option, IMO. > > I'm copying Richard, Jake and Gavin, who are the ones that wrote most of > the original code base for the distributed filesystem and ECL compiler > (among many other parts), and perhaps can provide some ideas/pointers. > > Flavio > > Flavio Villanustre > > > On Sat, Dec 21, 2013 at 8:50 AM, Alexander Kjeldaas < > alexander.kjeldaas at gmail.com> wrote: > > > In the HPCC documentation it is hard to cut through the buzzword jungle. > Is there an efficient storage solution lurking there? > > I searched for haskell packages related to the big data storage layer, and > the only thing I've found that could support efficient erasure code-based > storage is this 3 years old binding to libhdfs. There is only one commit > in github: > > https://github.com/kim/hdfs-haskell > > Somewhat related are these bindings to zfec, from 2008, and part of the > Tahoe LAFS project. > > http://hackage.haskell.org/package/fec > > > Alexander > > > > On Fri, Dec 20, 2013 at 8:24 AM, Carter Schonwald < > carter.schonwald at gmail.com> wrote: > > Cloud Haskell is a substrate that could be used to build such a layer. > I'm sure the cloud Haskell people would love such experimenration. > > > On Friday, December 20, 2013, He-chien Tsai wrote: > > What I meant is that split the data into several parts,send each splited > data to different computers, train them seperately, finally send the > results back and combine those results. I didn't mean to use Cloud Haskell. > > 2013/12/20 ??5:40 ? "jean-christophe mincke" < > jeanchristophe.mincke at gmail.com> ??? > > > > He-Chien Tsai, > > > > > its training result is designed for composable > > > > Yes it is indeed composable (parallel function of that lib) but > parallelizing it on a cluster changes all the type because running on a > cluster implies IO. > > Moreover using Cloud Haskell (for instance) implies that: > > 1. training functions should be (serializable) clojures, which can only > be defined as module level (not as local -let/where - bindings). > > 2. train is a typeclass function and is not serializable. > > > > So the idea behind HLearn are interesting but I do not see how it could > be run on a cluster... But, unfortunately, I am not an Haskell expert. > > > > What do you think? > > > > Regards > > > > J-C > > > > > > > > On Thu, Dec 19, 2013 at 6:15 PM, He-chien Tsai > wrote: > >> > >> have you took a look at hlearn and statistics packages? it's even easy > to parallellize hlearn on cluster because it's training result is designed > for composable, which means you can create two model , train them > seperately and finally combine them. you can also use other database such > as redis or cassandra,which has haskell binding, as backend. for > parallellizing on clusters, hdph is also good. > >> > >> I personally prefer python for data science because it has much more > mature packages and is more interactive and more effective (not kidding. > you can create compiled C for core datas and algorithms by python-like > cython and call it from python, and exploit gpus for accelerating by > theano) than haskell and scala, spark also has a unfinish python binding. > >> > >> 2013/12/18 ??3:41 ? "jean-christophe mincke" < > jeanchristophe.mincke at gmail.com> ??? > >> > >> > >> > > >> > Hello Cafe, > >> > > >> > Big Data is a bit trendy these days. > >> > > >> > Does anybody know about plans to develop an Haskell eco-system in > that domain? > >> > I.e tools such as Storm or Spark (possibly on top of Cloud Haskell) > or, at least, bindings to tools which exist in other languages. > >> > > >> > Thank you > >> > > >> > Regards > >> > > >> > J-C > >> > > >> > _______________________________________________ > >> > Haskell-Cafe mailing list > >> > Haskell-Cafe at haskell.org > >> > http://www.haskell.org/mailman/listinfo/haskell-caf > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Sat Dec 21 17:32:47 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sat, 21 Dec 2013 12:32:47 -0500 Subject: [Haskell-cafe] Haskell and Big Data In-Reply-To: References: Message-ID: Interesting. Does it have a design that let's computation be structured in a locality aware way? (I'd imagine yes, but I'm Afk much of this week so it's a bit hard to read docs) On Saturday, December 21, 2013, Flavio Villanustre wrote: > Alexander, > > The distributed storage in the HPCC platform relies on an underlying Posix > compliant Linux filesystem (any will do), and provides an abstraction layer > based on record oriented (as opposed to block oriented, like HDFS) > fileparts located in the local storage of the physical nodes. It also uses > a component called Dali which, among other things, is a metadata server > that provides a "logical file" view of these partitioned data files, and > the system provides the tooling to create them from an external data source > (in a process called spray). > > While you could conceivably use the distributed file system in HPCC as a > stand alone data repository, I think that it would be more interesting to > take advantage of the data processing machinery too. The HPCC platform has > already a declarative dataflow language called ECL which, coincidentally, > advocates purity, is non-strict (implemented through laziness) and compiles > into C++ (and uses g++/clang to compile this into machine code). Since ECL > already allows for embedded C++, Python, R, Java and Javascript, allowing > Haskell to be embedded too (through FFI?) would be the best integration > option, IMO. > > I'm copying Richard, Jake and Gavin, who are the ones that wrote most of > the original code base for the distributed filesystem and ECL compiler > (among many other parts), and perhaps can provide some ideas/pointers. > > Flavio > > Flavio Villanustre > > > On Sat, Dec 21, 2013 at 8:50 AM, Alexander Kjeldaas < > alexander.kjeldaas at gmail.com> wrote: > > > In the HPCC documentation it is hard to cut through the buzzword jungle. > Is there an efficient storage solution lurking there? > > I searched for haskell packages related to the big data storage layer, and > the only thing I've found that could support efficient erasure code-based > storage is this 3 years old binding to libhdfs. There is only one commit > in github: > > https://github.com/kim/hdfs-haskell > > Somewhat related are these bindings to zfec, from 2008, and part of the > Tahoe LAFS project. > > http://hackage.haskell.org/package/fec > > > Alexander > > > > On Fri, Dec 20, 2013 at 8:24 AM, Carter Schonwald < > carter.schonwald at gmail.com> wrote: > > Cloud Haskell is a substrate that could be used to build such a layer. > I'm sure the cloud Haskell people would love such experimenration. > > > On Friday, December 20, 2013, He-chien Tsai wrote: > > What I meant is that split the data into several parts,send each splited > data to different computers, train them seperately, finally send the > results back and combine those results. I didn't mean to use Cloud Haskell. > > 2013/12/20 ??5:40 ? "jean-christophe mincke" < > jeanchristophe.mincke at gmail.com> ??? > > > > He-Chien Tsai, > > > > > its training result is designed for composable > > > > Yes it is indeed composable (parallel function of that lib) but > parallelizing it on a cluster changes all the type because running on a > cluster implies IO. > > Moreover using Cloud Haskell (for instance) implies that: > > 1. training functions should be (serializable) clojures, which can only > be defined as module level (not as local -let/where - bindings). > > 2. train is a typeclass function and is not serializable. > > > > So the idea behind HLearn are interesting but I do not see how it could > be run on a cluster... But, unfortunately, I am not an Haskell expert. > > > > What do you think? > > > > Regards > > > > J-C > > > > > > > > On Thu, Dec 19, 2013 at 6:15 PM, He-chien Tsai > wrote: > >> > >> have you took a look at hlearn and statistics packages? it's even easy > to parallellize hlearn on cluster because it's training result is designed > for composable, which means you can create two model , train them > seperately and finally combine them. you can also use other database such > as redis or cassandra,which has haskell binding, as backend. for > parallellizing on clusters, hdph is also good. > >> > >> I personally prefer python for data science because it has much more > mature packages and is more interactive and more effective (not kidding. > you can create compiled C for core datas and algorithms by python-like > cython and call it from python, and exploit gpus for accelerating by > theano) than haskell and scala, spark also has a unfinish python binding. > >> > >> 2013/12/18 ??3:41 ? "jean-christophe mincke" < > jeanchristophe.mincke at gmail.com> ??? > >> > >> > >> > > >> > Hello Cafe, > >> > > >> > Big Data is a bit trendy these days. > >> > > >> > Does anybody know about plans to develop an Haskell eco-system in > that domain? > >> > I.e tools such as Storm or Spark (possibly on top of Cloud Haskell) > or, at least, bindings to tools which exist in other languages. > >> > > >> > Thank you > >> > > >> > Regards > >> > > >> > J-C > >> > > >> > _______________________________________________ > >> > Haskell-Cafe mailing list > >> > Haskell-Cafe at haskell.org > >> > http://www.haskell.org/mailman/listinfo/haskell-caf > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jeanchristophe.mincke at gmail.com Sat Dec 21 17:52:11 2013 From: jeanchristophe.mincke at gmail.com (jean-christophe mincke) Date: Sat, 21 Dec 2013 18:52:11 +0100 Subject: [Haskell-cafe] Haskell and Big Data In-Reply-To: References: Message-ID: Hi, There is the Holumbus packages. It seems to have a DFS and support for analytics (map/reduce at least). Regards J-C On Sat, Dec 21, 2013 at 2:50 PM, Alexander Kjeldaas < alexander.kjeldaas at gmail.com> wrote: > > In the HPCC documentation it is hard to cut through the buzzword jungle. > Is there an efficient storage solution lurking there? > > I searched for haskell packages related to the big data storage layer, and > the only thing I've found that could support efficient erasure code-based > storage is this 3 years old binding to libhdfs. There is only one commit > in github: > > https://github.com/kim/hdfs-haskell > > Somewhat related are these bindings to zfec, from 2008, and part of the > Tahoe LAFS project. > > http://hackage.haskell.org/package/fec > > > Alexander > > > > On Fri, Dec 20, 2013 at 8:24 AM, Carter Schonwald < > carter.schonwald at gmail.com> wrote: > >> Cloud Haskell is a substrate that could be used to build such a layer. >> I'm sure the cloud Haskell people would love such experimenration. >> >> >> On Friday, December 20, 2013, He-chien Tsai wrote: >> >>> What I meant is that split the data into several parts,send each splited >>> data to different computers, train them seperately, finally send the >>> results back and combine those results. I didn't mean to use Cloud Haskell. >>> >>> 2013/12/20 ??5:40 ? "jean-christophe mincke" < >>> jeanchristophe.mincke at gmail.com> ??? >>> > >>> > He-Chien Tsai, >>> > >>> > > its training result is designed for composable >>> > >>> > Yes it is indeed composable (parallel function of that lib) but >>> parallelizing it on a cluster changes all the type because running on a >>> cluster implies IO. >>> > Moreover using Cloud Haskell (for instance) implies that: >>> > 1. training functions should be (serializable) clojures, which can >>> only be defined as module level (not as local -let/where - bindings). >>> > 2. train is a typeclass function and is not serializable. >>> > >>> > So the idea behind HLearn are interesting but I do not see how it >>> could be run on a cluster... But, unfortunately, I am not an Haskell expert. >>> > >>> > What do you think? >>> > >>> > Regards >>> > >>> > J-C >>> > >>> > >>> > >>> > On Thu, Dec 19, 2013 at 6:15 PM, He-chien Tsai >>> wrote: >>> >> >>> >> have you took a look at hlearn and statistics packages? it's even >>> easy to parallellize hlearn on cluster because it's training result is >>> designed for composable, which means you can create two model , train them >>> seperately and finally combine them. you can also use other database such >>> as redis or cassandra,which has haskell binding, as backend. for >>> parallellizing on clusters, hdph is also good. >>> >> >>> >> I personally prefer python for data science because it has much more >>> mature packages and is more interactive and more effective (not kidding. >>> you can create compiled C for core datas and algorithms by python-like >>> cython and call it from python, and exploit gpus for accelerating by >>> theano) than haskell and scala, spark also has a unfinish python binding. >>> >> >>> >> 2013/12/18 ??3:41 ? "jean-christophe mincke" < >>> jeanchristophe.mincke at gmail.com> ??? >>> >> >>> >> >>> >> > >>> >> > Hello Cafe, >>> >> > >>> >> > Big Data is a bit trendy these days. >>> >> > >>> >> > Does anybody know about plans to develop an Haskell eco-system in >>> that domain? >>> >> > I.e tools such as Storm or Spark (possibly on top of Cloud Haskell) >>> or, at least, bindings to tools which exist in other languages. >>> >> > >>> >> > Thank you >>> >> > >>> >> > Regards >>> >> > >>> >> > J-C >>> >> > >>> >> > _______________________________________________ >>> >> > Haskell-Cafe mailing list >>> >> > Haskell-Cafe at haskell.org >>> >> > http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >> > >>> > >>> > >>> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jeanchristophe.mincke at gmail.com Sat Dec 21 17:53:14 2013 From: jeanchristophe.mincke at gmail.com (jean-christophe mincke) Date: Sat, 21 Dec 2013 18:53:14 +0100 Subject: [Haskell-cafe] Haskell and Big Data In-Reply-To: References: Message-ID: Looking at the docs, it is indeed not clear whether it has (ie. the way Spark has) or not. J-C On Sat, Dec 21, 2013 at 6:30 PM, Carter Schonwald < carter.schonwald at gmail.com> wrote: > Interesting. Does it have a design that let's computation be structured in > a locality aware way? (I'd imagine yes, but I'm Afk much of this week so > it's a bit hard to read docs) > > > On Saturday, December 21, 2013, Flavio Villanustre wrote: > >> Alexander, >> >> The distributed storage in the HPCC platform relies on an underlying >> Posix compliant Linux filesystem (any will do), and provides an abstraction >> layer based on record oriented (as opposed to block oriented, like HDFS) >> fileparts located in the local storage of the physical nodes. It also uses >> a component called Dali which, among other things, is a metadata server >> that provides a "logical file" view of these partitioned data files, and >> the system provides the tooling to create them from an external data source >> (in a process called spray). >> >> While you could conceivably use the distributed file system in HPCC as a >> stand alone data repository, I think that it would be more interesting to >> take advantage of the data processing machinery too. The HPCC platform has >> already a declarative dataflow language called ECL which, coincidentally, >> advocates purity, is non-strict (implemented through laziness) and compiles >> into C++ (and uses g++/clang to compile this into machine code). Since ECL >> already allows for embedded C++, Python, R, Java and Javascript, allowing >> Haskell to be embedded too (through FFI?) would be the best integration >> option, IMO. >> >> I'm copying Richard, Jake and Gavin, who are the ones that wrote most of >> the original code base for the distributed filesystem and ECL compiler >> (among many other parts), and perhaps can provide some ideas/pointers. >> >> Flavio >> >> Flavio Villanustre >> >> >> On Sat, Dec 21, 2013 at 8:50 AM, Alexander Kjeldaas < >> alexander.kjeldaas at gmail.com> wrote: >> >> >> In the HPCC documentation it is hard to cut through the buzzword jungle. >> Is there an efficient storage solution lurking there? >> >> I searched for haskell packages related to the big data storage layer, >> and the only thing I've found that could support efficient erasure >> code-based storage is this 3 years old binding to libhdfs. There is only >> one commit in github: >> >> https://github.com/kim/hdfs-haskell >> >> Somewhat related are these bindings to zfec, from 2008, and part of the >> Tahoe LAFS project. >> >> http://hackage.haskell.org/package/fec >> >> >> Alexander >> >> >> >> On Fri, Dec 20, 2013 at 8:24 AM, Carter Schonwald < >> carter.schonwald at gmail.com> wrote: >> >> Cloud Haskell is a substrate that could be used to build such a layer. >> I'm sure the cloud Haskell people would love such experimenration. >> >> >> On Friday, December 20, 2013, He-chien Tsai wrote: >> >> What I meant is that split the data into several parts,send each splited >> data to different computers, train them seperately, finally send the >> results back and combine those results. I didn't mean to use Cloud Haskell. >> >> 2013/12/20 ??5:40 ? "jean-christophe mincke" < >> jeanchristophe.mincke at gmail.com> ??? >> > >> > He-Chien Tsai, >> > >> > > its training result is designed for composable >> > >> > Yes it is indeed composable (parallel function of that lib) but >> parallelizing it on a cluster changes all the type because running on a >> cluster implies IO. >> > Moreover using Cloud Haskell (for instance) implies that: >> > 1. training functions should be (serializable) clojures, which can only >> be defined as module level (not as local -let/where - bindings). >> > 2. train is a typeclass function and is not serializable. >> > >> > So the idea behind HLearn are interesting but I do not see how it could >> be run on a cluster... But, unfortunately, I am not an Haskell expert. >> > >> > What do you think? >> > >> > Regards >> > >> > J-C >> > >> > >> > >> > On Thu, Dec 19, 2013 at 6:15 PM, He-chien Tsai >> wrote: >> >> >> >> have you took a look at hlearn and statistics packages? it's even easy >> to parallellize hlearn on cluster because it's training result is designed >> for composable, which means you can create two model , train them >> seperately and finally combine them. you can also use other database such >> as redis or cassandra,which has haskell binding, as backend. for >> parallellizing on clusters, hdph is also good. >> >> >> >> I personally prefer python for data science because it has much more >> mature packages and is more interactive and more effective (not kidding. >> you can create compiled C for core datas and algorithms by python-like >> cython and call it from python, and exploit gpus for accelerating by >> theano) than haskell and scala, spark also has a unfinish python binding. >> >> >> >> 2013/12/18 ??3:41 ? "jean-christophe mincke" < >> jeanchristophe.mincke at gmail.com> ??? >> >> >> >> >> >> > >> >> > Hello Cafe, >> >> > >> >> > Big Data is a bit trendy these days. >> >> > >> >> > Does anybody know about plans to develop an Haskell eco-system in >> that domain? >> >> > I.e tools such as Storm or Spark (possibly on top of Cloud Haskell) >> or, at least, bindings to tools which exist in other languages. >> >> > >> >> > Thank you >> >> > >> >> > Regards >> >> > >> >> > J-C >> >> > >> >> > _______________________________________________ >> >> > Haskell-Cafe mailing list >> >> > Haskell-Cafe at haskell.org >> >> > http://www.haskell.org/mailman/listinfo/haskell-caf >> >> > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From fvillanustre at gmail.com Sat Dec 21 20:12:55 2013 From: fvillanustre at gmail.com (Flavio Villanustre) Date: Sat, 21 Dec 2013 15:12:55 -0500 Subject: [Haskell-cafe] Haskell and Big Data In-Reply-To: References: Message-ID: It does exploit data locality for efficiency, but this is largely dependent on the type of activity: while certain activities can be independently performed in each data record in parallel (i.e., turning a field in every record to uppercase), activities that operate on groups of records (think of a group or rollup operation based on one of the fields) may require that records be globally redistributed as part of that operation, and lastly, there are activities that may require that all records be reshuffled across the storage (a global/distributed sort operation, for example). ECL abstracts the complexities originated in the underlying distribution, partitioning and parallelism, so Haskell could theoretically do that same. Flavio Flavio Villanustre On Sat, Dec 21, 2013 at 12:32 PM, Carter Schonwald < carter.schonwald at gmail.com> wrote: > Interesting. Does it have a design that let's computation be structured in > a locality aware way? (I'd imagine yes, but I'm Afk much of this week so > it's a bit hard to read docs) > > On Saturday, December 21, 2013, Flavio Villanustre wrote: > >> Alexander, >> >> The distributed storage in the HPCC platform relies on an underlying >> Posix compliant Linux filesystem (any will do), and provides an abstraction >> layer based on record oriented (as opposed to block oriented, like HDFS) >> fileparts located in the local storage of the physical nodes. It also uses >> a component called Dali which, among other things, is a metadata server >> that provides a "logical file" view of these partitioned data files, and >> the system provides the tooling to create them from an external data source >> (in a process called spray). >> >> While you could conceivably use the distributed file system in HPCC as a >> stand alone data repository, I think that it would be more interesting to >> take advantage of the data processing machinery too. The HPCC platform has >> already a declarative dataflow language called ECL which, coincidentally, >> advocates purity, is non-strict (implemented through laziness) and compiles >> into C++ (and uses g++/clang to compile this into machine code). Since ECL >> already allows for embedded C++, Python, R, Java and Javascript, allowing >> Haskell to be embedded too (through FFI?) would be the best integration >> option, IMO. >> >> I'm copying Richard, Jake and Gavin, who are the ones that wrote most of >> the original code base for the distributed filesystem and ECL compiler >> (among many other parts), and perhaps can provide some ideas/pointers. >> >> Flavio >> >> Flavio Villanustre >> >> >> On Sat, Dec 21, 2013 at 8:50 AM, Alexander Kjeldaas < >> alexander.kjeldaas at gmail.com> wrote: >> >> >> In the HPCC documentation it is hard to cut through the buzzword jungle. >> Is there an efficient storage solution lurking there? >> >> I searched for haskell packages related to the big data storage layer, >> and the only thing I've found that could support efficient erasure >> code-based storage is this 3 years old binding to libhdfs. There is only >> one commit in github: >> >> https://github.com/kim/hdfs-haskell >> >> Somewhat related are these bindings to zfec, from 2008, and part of the >> Tahoe LAFS project. >> >> http://hackage.haskell.org/package/fec >> >> >> Alexander >> >> >> >> On Fri, Dec 20, 2013 at 8:24 AM, Carter Schonwald < >> carter.schonwald at gmail.com> wrote: >> >> Cloud Haskell is a substrate that could be used to build such a layer. >> I'm sure the cloud Haskell people would love such experimenration. >> >> >> On Friday, December 20, 2013, He-chien Tsai wrote: >> >> What I meant is that split the data into several parts,send each splited >> data to different computers, train them seperately, finally send the >> results back and combine those results. I didn't mean to use Cloud Haskell. >> >> 2013/12/20 ??5:40 ? "jean-christophe mincke" < >> jeanchristophe.mincke at gmail.com> ??? >> > >> > He-Chien Tsai, >> > >> > > its training result is designed for composable >> > >> > Yes it is indeed composable (parallel function of that lib) but >> parallelizing it on a cluster changes all the type because running on a >> cluster implies IO. >> > Moreover using Cloud Haskell (for instance) implies that: >> > 1. training functions should be (serializable) clojures, which can only >> be defined as module level (not as local -let/where - bindings). >> > 2. train is a typeclass function and is not serializable. >> > >> > So the idea behind HLearn are interesting but I do not see how it could >> be run on a cluster... But, unfortunately, I am not an Haskell expert. >> > >> > What do you think? >> > >> > Regards >> > >> > J-C >> > >> > >> > >> > On Thu, Dec 19, 2013 at 6:15 PM, He-chien Tsai >> wrote: >> >> >> >> have you took a look at hlearn and statistics packages? it's even easy >> to parallellize hlearn on cluster because it's training result is designed >> for composable, which means you can create two model , train them >> seperately and finally combine them. you can also use other database such >> as redis or cassandra,which has haskell binding, as backend. for >> parallellizing on clusters, hdph is also good. >> >> >> >> I personally prefer python for data science because it has much more >> mature packages and is more interactive and more effective (not kidding. >> you can create compiled C for core datas and algorithms by python-like >> cython and call it from python, and exploit gpus for accelerating by >> theano) than haskell and scala, spark also has a unfinish python binding. >> >> >> >> 2013/12/18 ??3:41 ? "jean-christophe mincke" < >> jeanchristophe.mincke at gmail.com> ??? >> >> >> >> >> >> > >> >> > Hello Cafe, >> >> > >> >> > Big Data is a bit trendy these days. >> >> > >> >> > Does anybody know about plans to develop an Haskell eco-system in >> that domain? >> >> > I.e tools such as Storm or Spark (possibly on top of Cloud Haskell) >> or, at least, bindings to tools which exist in other languages. >> >> > >> >> > Thank you >> >> > >> >> > Regards >> >> > >> >> > J-C >> >> > >> >> > _______________________________________________ >> >> > Haskell-Cafe mailing list >> >> > Haskell-Cafe at haskell.org >> >> > http://www.haskell.org/mailman/listinfo/haskell-caf >> >> -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at orlitzky.com Sat Dec 21 23:10:40 2013 From: michael at orlitzky.com (Michael Orlitzky) Date: Sat, 21 Dec 2013 18:10:40 -0500 Subject: [Haskell-cafe] Abstracting configuration directories In-Reply-To: <52B49603.9090803@orlitzky.com> References: <52B26C1A.7090206@orlitzky.com> <52B3299D.201@orlitzky.com> <52B49603.9090803@orlitzky.com> Message-ID: <52B61FF0.6060808@orlitzky.com> On 12/20/2013 02:09 PM, Michael Orlitzky wrote: > > A patch looks easy, but I'm not sure that I would call /etc the "global > data directory" on Unix. I'll have to think about it some more. For posterity, when using Cabal, the system config directory is available via getSysconfDir in build/autogen/Paths_.hs. This puts the responsibility on the person who runs configure, which I kind of like. From orblivion at gmail.com Sun Dec 22 01:16:00 2013 From: orblivion at gmail.com (Dan Krol) Date: Sat, 21 Dec 2013 17:16:00 -0800 Subject: [Haskell-cafe] Clearing up the status of GHCi on Raspberry Pi In-Reply-To: References: <87r49cu5os.fsf@gmail.com> Message-ID: If I could edit the haskellwiki I would just link to the archive of Ben's email. Unfortunately I don't see a register button for the wiki. Could somebody else do it? Or is there a way for an arbitrary person like me to get an account with edit privileges? On Tue, Dec 17, 2013 at 9:29 AM, Dan Krol wrote: > Thanks so much for the detailed response. When I have a moment I will try > to come up with some appropriate edits to the Wikis, I will run them by you > first to make sure they're accurate. And even moreso, thanks for your work > in this area. When is 7.8 looking like it's coming out? And, how hard would > it be to install it onto my Pi? Would I have to compile it? I'm assuming it > won't make it into the Jesse repository (or will it?) > > -Dan > > > On Mon, Dec 16, 2013 at 8:22 AM, Ben Gamari wrote: > >> Dan Krol writes: >> >> ... >> > I figure we should sort this out, I'd be happy to edit the wikis myself >> but >> > I want to make sure I understand what's going on. I understand this >> > probably comes down to some nuances that are not expressed here. For >> user >> > friendliness of the language and ecosystem I think such things should be >> > made clear. As somebody coming to this wanting to accomplish something, >> I >> > want a clear answer on what is available to me. It's been a source of >> > frustration for me. >> > >> > Could somebody clear all this up for me? And while I'm at it, I would be >> > grateful if somebody could explain to me how it is possible (if at all) >> to >> > have ghci on my Raspberry Pi, short of compiling it myself. I'm not >> against >> > compiling ghc, but I am against compiling it on my Raspberry Pi. Qemu I >> > will consider, though. >> > >> The situation is a bit complicated and I've been pretty poor at keeping >> the existing documentation up-to-date. ARM support has in principle >> existed >> in the tree through the LLVM code generator for some time. The code >> generator itself is in my experience quite robust. >> >> There are, however, a number of details in the runtime system which >> break GHCi. One of these is the runtime linker which until recently had >> effectively no support for ARM. I worked some initial ARM support in to >> 7.6.1 (b22501b408ddb0503a06a188b06d9cff9be697cd) and while things >> largely worked at the time, there were still some rough edges. For this >> reason, 7.6 can't really considered to support GHCi on ARM. >> Unfortunately at this point I became quite busy and didn't have time to >> look into the remaining issues. This was in late 2011. >> >> In the last few weeks I've had time to have another look at this >> problem. It turns out one of the issues (lack of jump code, documented >> in bug #8380) was quite straightforward to fix >> (up to some cache coherency issues which I believe thoughtpolice has now >> sorted out, see 5bab1a57f572e29dfdffd6d1ce8e53a2772b18fd). Unfortunately >> after fixing this I found that there was still occassional crashes >> during the build process. I spent a fair bit of time poking around >> looking for the root cause but have still come up with no compelling >> leads. It's very likely that the culprit is the runtime linker, although >> I haven't found a way to narrow things down any further. >> >> Frankly, implementing a runtime linker is non-trivial business and in my >> opinion the limited man-hours working on GHC are better spent >> elsewhere. Having our own runtime linker has its advantages, but for an >> architecture that is currently *barely* supported, it makes more sense >> to punt as much of this responsibility to other parties as possible. For >> this reason I think it would be wise to focus on moving this >> functionality to the system's runtime linker by using dynamic linking. >> >> Dynamic linking has been working for some time now on x86 with the >> native code generator. Unfortunately, there have been rumors that things >> are broken when the LLVM code generator is used (which is the only >> option on ARM). I started looking into this late last week and believe I >> have the problem identified (thanks to help from Peter Wortmann, see >> [1]) and have something of a solution. At this point I'm running into >> build system issues[2] which prevent me from verifying my hacked >> work-around^H^H^Hsolution. >> >> Assuming that I can validate the fix, I'm hoping there's a chance it (or >> something like it) can make it in to 7.8. As far as I can tell, this is >> the last major impediment to have GHC working well on ARM. Moreover, by >> switching to dynamic linking on ARM we will have eliminated a major >> source of trouble from the equation. This would mean that 7.8 would >> finally have (hopefully) robust support on ARM. >> >> Cheers, >> >> - Ben >> >> >> [1] http://www.haskell.org/pipermail/ghc-devs/2013-December/003484.html >> [2] http://www.haskell.org/pipermail/ghc-devs/2013-December/003488.html >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Sun Dec 22 01:20:24 2013 From: allbery.b at gmail.com (Brandon Allbery) Date: Sat, 21 Dec 2013 20:20:24 -0500 Subject: [Haskell-cafe] Clearing up the status of GHCi on Raspberry Pi In-Reply-To: References: <87r49cu5os.fsf@gmail.com> Message-ID: On Sat, Dec 21, 2013 at 8:16 PM, Dan Krol wrote: > If I could edit the haskellwiki I would just link to the archive of Ben's > email. Unfortunately I don't see a register button for the wiki. Could > somebody else do it? Or is there a way for an arbitrary person like me to > get an account with edit privileges? > See the `Log in` link on the wiki for details. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From j.v.eekelen at gmail.com Sun Dec 22 12:48:33 2013 From: j.v.eekelen at gmail.com (Joeri van Eekelen) Date: Sun, 22 Dec 2013 13:48:33 +0100 Subject: [Haskell-cafe] Abstracting configuration directories In-Reply-To: <52B61FF0.6060808@orlitzky.com> References: <52B26C1A.7090206@orlitzky.com> <52B3299D.201@orlitzky.com> <52B49603.9090803@orlitzky.com> <52B61FF0.6060808@orlitzky.com> Message-ID: <52B6DFA1.5090507@gmail.com> Interesting. Is there documentation anywhere about what Cabal puts into the Paths_*.hs files? I couldn't find anything beyond getDataFileName and version :: Version in the Cabal user guide. The link to "prefix independence" refers to a non-existing anchor tag. On 2013-12-22 00:10, Michael Orlitzky wrote: > For posterity, when using Cabal, the system config directory is > available via getSysconfDir in build/autogen/Paths_.hs. This > puts the responsibility on the person who runs configure, which I kind > of like. > -- Joeri van Eekelen - j.v.eekelen at gmail.com From michael at orlitzky.com Mon Dec 23 02:26:45 2013 From: michael at orlitzky.com (Michael Orlitzky) Date: Sun, 22 Dec 2013 21:26:45 -0500 Subject: [Haskell-cafe] Abstracting configuration directories In-Reply-To: <52B6DFA1.5090507@gmail.com> References: <52B26C1A.7090206@orlitzky.com> <52B3299D.201@orlitzky.com> <52B49603.9090803@orlitzky.com> <52B61FF0.6060808@orlitzky.com> <52B6DFA1.5090507@gmail.com> Message-ID: <52B79F65.8030306@orlitzky.com> On 12/22/2013 07:48 AM, Joeri van Eekelen wrote: > Interesting. Is there documentation anywhere about what Cabal puts into > the Paths_*.hs files? I couldn't find anything beyond getDataFileName > and version :: Version in the Cabal user guide. The link to "prefix > independence" refers to a non-existing anchor tag. I don't think so, I found it by accident. From sean at functionaljobs.com Mon Dec 23 07:00:10 2013 From: sean at functionaljobs.com (Functional Jobs) Date: Mon, 23 Dec 2013 02:00:10 -0500 Subject: [Haskell-cafe] New Functional Programming Job Opportunities Message-ID: <52b7df826f620@functionaljobs.com> Here are some functional programming job opportunities that were posted recently: Chief Data Scientist at Lazada http://functionaljobs.com/jobs/8671-chief-data-scientist-at-lazada Cheers, Sean Murphy FunctionalJobs.com From lucas.dicioccio at gmail.com Mon Dec 23 09:27:15 2013 From: lucas.dicioccio at gmail.com (lucas di cioccio) Date: Mon, 23 Dec 2013 10:27:15 +0100 Subject: [Haskell-cafe] [ANN] Laborantin: experimentation framework Message-ID: Dear all, I am happy to announce Laborantin. Laborantin is a Haskell library and DSL for running and analyzing controlled experiments. Repository: https://github.com/lucasdicioccio/laborantin-hs Hackage page: http://hackage.haskell.org/package/laborantin-hs Laborantin's opinion is that running proper experiments is a non-trivial and often overlooked problem. Therefore, we should provide good tools to assist experimenters. The hope is that, with Laborantin, experimenters will spend more time on their core problem while racing through the menial tasks of editing scripts because one data point is missing in a plot. At the same time, Laborantin is also an effort within the broad open-science movement. Indeed, Laborantin's DSL separates boilerplate from the actual experiment implementation. Thus, Laborantin could reduce the friction for code and data-reuse. One family of experiments that fit well Laborantin are benchmarks with tedious setup and teardown procedures (for instance starting, configuring, and stopping remote machines). Analyses that require measurements from a variety of data points in a multi-dimensional parameter space also fall in the scope of Laborantin. When using Laborantin, the experimenter: * Can express experimental scenarios using a readable and familiar DSL. This feature, albeit subjective, was confirmed by non-Haskeller colleagues. * Saves time on boilerplate such as writing command-line parsers or encoding dependencies between experiments and analysis results in a Makefile. * Benefits from auto-documentation and result introspection features when one comes back to a project, possibly months or weeks later. * Harnesses the power of Haskell type-system to catch common errors at compile time If you had to read one story to understand the pain points that Laborantin tries to address, it should be Section 5 of "Strategies for Sound Internet Measurement" (V. Paxson, IMC 2004). I'd be glad to take question and comments (or, even better, code reviews and pull requests). Kind regards, --Lucas DiCioccio (@lucasdicioccio on GitHub/Twitter) -------------- next part -------------- An HTML attachment was scrubbed... URL: From joe at interare.com Mon Dec 23 11:51:29 2013 From: joe at interare.com (Joe) Date: Mon, 23 Dec 2013 18:51:29 +0700 Subject: [Haskell-cafe] Building PanDoc for iOS target, but failed in Haskell Template requirement by 'aeson' package Message-ID: Hi, I've been trying to cross-compile PanDoc for iOS target for the last few days. I have been quite successfull from building stage-1 GHC for iOS target and many packages dependencies required by PanDoc until I see that 'aeson' package require Haskell Template which is not supported in cross compilation. As pointed in iOS CrossCompiling Wiki page, it seems that Template Haskell doesn't work yet and still in wish list. Is there any hack or workaround to be able to cross-compile 'aeson' package for iOS target? Can I compile 'aeson' without Haskell Template? Anybody know when Template Haskell in CrossCompiling for iOS will be added? Thanks a lot! Best regards, Joe -------------- next part -------------- An HTML attachment was scrubbed... URL: From roma at ro-che.info Mon Dec 23 13:56:17 2013 From: roma at ro-che.info (Roman Cheplyaka) Date: Mon, 23 Dec 2013 15:56:17 +0200 Subject: [Haskell-cafe] Access to Mac OS X needed Message-ID: <20131223135617.GA2241@sniper> Hi, I am working on fswatch[1,2], a cross-platform file system notification library. [1]: http://hackage.haskell.org/package/fsnotify [2]: https://github.com/haskell-fswatch/hfsnotify Occasionally it needs to be tested on Mac OS X. Could someone give me an unprivileged ssh access to a Mac OS X host with an installed Haskell Platform for this purpose? Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: Digital signature URL: From carter.schonwald at gmail.com Mon Dec 23 14:38:11 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Mon, 23 Dec 2013 09:38:11 -0500 Subject: [Haskell-cafe] Building PanDoc for iOS target, but failed in Haskell Template requirement by 'aeson' package In-Reply-To: References: Message-ID: Patch Aeson locally so that it has no th module. Then fix any transitive breakages as you hit them. General th support for cross compiling ghc is on the roadmap for getting worked out in ghc, but it's really just part of generally improving ghc so that there can be multi target cross compilation support. This is because th will run on your dev Mac, but me generating code for your iOS device! Ghcjs actuall has such cross compilation, so some ideas could be borrowed from there. Hopefully it'll happen in the next year, though when and by whom is still a bit unclear. On Monday, December 23, 2013, Joe wrote: > Hi, I've been trying to cross-compile PanDoc for iOS target for the last > few days. I have been quite successfull from building stage-1 GHC for iOS > target and many packages dependencies required by PanDoc until I see that > 'aeson' package require Haskell Template which is not supported in cross > compilation. > > As pointed in iOS CrossCompiling Wiki page, > it seems that Template Haskell doesn't work yet and still in wish list. > > Is there any hack or workaround to be able to cross-compile 'aeson' > package for iOS target? Can I compile 'aeson' without Haskell Template? > Anybody know when Template Haskell in CrossCompiling for iOS will be added? > > Thanks a lot! > > Best regards, > Joe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From doaitse at swierstra.net Mon Dec 23 15:14:11 2013 From: doaitse at swierstra.net (Doaitse Swierstra) Date: Mon, 23 Dec 2013 16:14:11 +0100 Subject: [Haskell-cafe] NL-FP Day 2014, January 10, Update Message-ID: Dear all, A warm welcome to all who registered since the last update email. As of today, we expect 56 participants to the 22nd Netherlands Functional Programming Day in 2014. All news regarding the day itself including - a complete programme, - abstracts for most of the talks, - an updated list of participants, - dinner location (de ponteneur), - registration fee (25EUR) can be found at http://staff.science.uva.nl/~grelck/nl-fp-day-2014.html http://staff.science.uva.nl/~grelck/nl-fp-dag-2014.html Merry Christmas and best wishes for the new year, Clemens -- ---------------------------------------------------------------------- Dr Clemens Grelck Science Park 904 University Lecturer 1098XH Amsterdam Netherlands University of Amsterdam Institute for Informatics T +31 (0) 20 525 8683 Computer Systems Architecture Group F +31 (0) 20 525 7490 Office C3.105 www.science.uva.nl/~grelck ---------------------------------------------------------------------- From mail at joachim-breitner.de Mon Dec 23 18:28:27 2013 From: mail at joachim-breitner.de (Joachim Breitner) Date: Mon, 23 Dec 2013 19:28:27 +0100 Subject: [Haskell-cafe] Building PanDoc for iOS target, but failed in Haskell Template requirement by 'aeson' package In-Reply-To: References: Message-ID: <1387823307.11385.1.camel@kirk> Hi, Am Montag, den 23.12.2013, 09:38 -0500 schrieb Carter Schonwald: > Patch Aeson locally so that it has no th module. Then fix any > transitive breakages as you hit them. Debian patches TH out of aeson on architectures without an interpreter: http://patch-tracker.debian.org/patch/series/view/haskell-aeson/0.6.2.1-2/th-option.diff None of the depending packages broke because of this. Greetings, Joachim -- Joachim ?nomeata? Breitner mail at joachim-breitner.de ? http://www.joachim-breitner.de/ Jabber: nomeata at joachim-breitner.de ? GPG-Key: 0x4743206C Debian Developer: nomeata at debian.org -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 198 bytes Desc: This is a digitally signed message part URL: From michael at orlitzky.com Mon Dec 23 21:20:13 2013 From: michael at orlitzky.com (Michael Orlitzky) Date: Mon, 23 Dec 2013 16:20:13 -0500 Subject: [Haskell-cafe] hslogger and metalog compatibility Message-ID: <52B8A90D.7040907@orlitzky.com> Is anyone else using metalog (syslog implementation) along with hslogger to log to syslog? If I run the following with syslog-ng, it works. With metalog, I get nothing. Just want to make sure it isn't me before I report it. Prelude> :set prompt "ghci> " ghci> :m +System.Log.Logger ghci> :m +System.Log.Handler.Syslog ghci> sl <- openlog rootLoggerName [] USER DEBUG ghci> updateGlobalLogger rootLoggerName (addHandler sl) ghci> errorM rootLoggerName "This won't show up with metalog." From eduardo.sato at gmail.com Tue Dec 24 02:02:23 2013 From: eduardo.sato at gmail.com (Eduardo Sato) Date: Tue, 24 Dec 2013 00:02:23 -0200 Subject: [Haskell-cafe] forever function laziness Message-ID: Hello, guys. Recently I came across the definition of the function 'forever' on hoogle. I am intrigued that it works. The recursive definition does make sense to me in a mathematical way, but I can't figure out how it works under the hood in terms of thunks. To tell you the truth, I don't know how laziness works in general in haskell. Can someone help me understand how it works in this example, and give some pointers to materials on the subject? The "tying the knot" article on the wiki is pretty mind bending too. -- | @'forever' act@ repeats the action infinitely. forever :: (Monad m) => m a -> m b {-# INLINE forever #-}forever a = let a' = a >> a' in a' -- Eduardo Sato -------------- next part -------------- An HTML attachment was scrubbed... URL: From cgaebel at uwaterloo.ca Tue Dec 24 02:30:50 2013 From: cgaebel at uwaterloo.ca (Clark Gaebel) Date: Mon, 23 Dec 2013 21:30:50 -0500 Subject: [Haskell-cafe] forever function laziness In-Reply-To: References: Message-ID: The way forever is implemented is a bit obtuse. It's mainly a hack to make GHC's optimizer avoid space leaking no matter what the surrounding code is. You can think of the implementation as just: forever :: Monad m => m a -> m b forever act = do act forever act which is pretty much what you'd do in an imperative language, so it's not that crazy. You can see the similarity if you replace the do notation with manual binds and rename 'act' to 'a': forever :: Monad m => m a -> m b forever a = a >> forever a Again, the knot tying stuff is just to prevent a space leak in certain optimization scenarios. On Mon, Dec 23, 2013 at 9:02 PM, Eduardo Sato wrote: > Hello, guys. > > Recently I came across the definition of the function 'forever' on hoogle. I am intrigued that it works. > > The recursive definition does make sense to me in a mathematical way, but I can't figure out how it works under the hood in terms of thunks. > > To tell you the truth, I don't know how laziness works in general in haskell. > > Can someone help me understand how it works in this example, and give some pointers to materials on the subject? > > The "tying the knot" article on the wiki is pretty mind bending too. > > -- | @'forever' act@ repeats the action infinitely. > > forever :: (Monad m) => m a -> m b > > {-# INLINE forever #-}forever a = let a' = a >> a' in a' > > -- > > Eduardo Sato > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -- Clark. Key ID : 0x78099922 Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 -------------- next part -------------- An HTML attachment was scrubbed... URL: From eduardo.sato at gmail.com Tue Dec 24 02:46:49 2013 From: eduardo.sato at gmail.com (Eduardo Sato) Date: Tue, 24 Dec 2013 00:46:49 -0200 Subject: [Haskell-cafe] forever function laziness In-Reply-To: References: Message-ID: On Tuesday, December 24, 2013, Clark Gaebel wrote: > forever :: Monad m => m a -> m b > forever a = a >> forever a > Thanks for your response. This is actually how I would have implemented it. What is confusing to me is the recursion on the let construct. What is not clear to me is when we can "get away" with doing that kind of thing. I mentioned the "tying the knot article" because it, too, uses recursion on a let construct. -- Eduardo Sato -------------- next part -------------- An HTML attachment was scrubbed... URL: From 0slemi0 at gmail.com Tue Dec 24 02:48:51 2013 From: 0slemi0 at gmail.com (Andras Slemmer) Date: Tue, 24 Dec 2013 02:48:51 +0000 Subject: [Haskell-cafe] forever function laziness In-Reply-To: References: Message-ID: In order to understand laziness in Haskell we first need to look at what WHNF (= Weak Head Normal Form) means: http://stackoverflow.com/questions/6872898/haskell-what-is-weak-head-normal-form Then the only rule you have to remember is that a reduction step (to whnf) only occurs in Haskell when: 1. Evaluating a case expression (pattern matching) 2. Evaluating a seq expression (this is irrelevant for now) Your example is a bit tricky as we don't have a concrete monad to work with. For some monads pattern matching on a (forever something) will loop forever, for some it may terminate. An example for the first one is the Identity monad: Identity a >>= f = f a Trying to reduce (forever (Identity x)) will go something like this: (formally these are not all reducion steps but this is how I unroll the expression in my head) forever (Identity x) let a' = Identity x >> a' in a' Identity x >> (let a' = X >> a' in a') Identity x >>= (\_ -> let a' = Identity x >> a' in a') (\_ -> let a' = Identity x >> a' in a') x -- this step was the only true reduction let a' = X >> a' in a' And we start looping. An example for a terminating one would be the Either () monad: Left () >>= _ = Left () Right a >>= f = f a And the reduction of the term (forever (Left ()): forever (Left ()) let a' = Left () >> a' in a' Left () >> (let a' = Left () >> a' in a') Left () >>= (\_ -> let a' = Left () >> a' in a') Left () The key step is the last one, reducing Left () >>= (\_ -> let a' = Left () >> a' in a') to whnf resulted in Left (), "short circuiting" the loop. If you want to understand the theoretical basis of lazy evaluation I suggest looking into the lambda calculus and different reduction strategies of it. There is a neat theorem I forgot the name of that shows why lazy evaluation is the "right" one in the sense that if a term T reduces to another term T' using any evaluation strategy then it will also reduce to T' using lazy evaluation. On 24 December 2013 02:02, Eduardo Sato wrote: > Hello, guys. > > Recently I came across the definition of the function 'forever' on hoogle. I am intrigued that it works. > > The recursive definition does make sense to me in a mathematical way, but I can't figure out how it works under the hood in terms of thunks. > > To tell you the truth, I don't know how laziness works in general in haskell. > > Can someone help me understand how it works in this example, and give some pointers to materials on the subject? > > The "tying the knot" article on the wiki is pretty mind bending too. > > -- | @'forever' act@ repeats the action infinitely. > > forever :: (Monad m) => m a -> m b > > {-# INLINE forever #-}forever a = let a' = a >> a' in a' > > -- > > Eduardo Sato > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From 0slemi0 at gmail.com Tue Dec 24 02:56:12 2013 From: 0slemi0 at gmail.com (Andras Slemmer) Date: Tue, 24 Dec 2013 02:56:12 +0000 Subject: [Haskell-cafe] forever function laziness In-Reply-To: References: Message-ID: >> What is confusing to me is the recursion on the let construct. Oh sry I may have misunderstood your question then. You can think of defining 'forever' itself as a let construct. Starting from the "simpler" implementation: let forever a = a >> forever a Now let's just give the rhs another name, again using 'let': let forever a = (let a' = a >> forever a in a') But we can see that a' is actually equal to (forever a), so we can replace on in the rhs: let forever a = (let a' = a >> a' in a') There is no trickery, no getting away, this recursion is the same as what you have thought of:) On 24 December 2013 02:46, Eduardo Sato wrote: > On Tuesday, December 24, 2013, Clark Gaebel wrote: > >> forever :: Monad m => m a -> m b >> forever a = a >> forever a >> > > Thanks for your response. This is actually how I would have implemented > it. > > What is confusing to me is the recursion on the let construct. > > What is not clear to me is when we can "get away" with doing that kind of > thing. I mentioned the "tying the knot article" because it, too, uses > recursion on a let construct. > > -- > Eduardo Sato > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From bob at redivi.com Tue Dec 24 03:05:40 2013 From: bob at redivi.com (Bob Ippolito) Date: Mon, 23 Dec 2013 19:05:40 -0800 Subject: [Haskell-cafe] forever function laziness In-Reply-To: References: Message-ID: The best explanation I've found for how Haskell's evaluation works is here: http://chimera.labs.oreilly.com/books/1230000000929/ch02.html#sec_par-eval-whnf On Monday, December 23, 2013, Eduardo Sato wrote: > Hello, guys. > > Recently I came across the definition of the function 'forever' on hoogle. I am intrigued that it works. > > The recursive definition does make sense to me in a mathematical way, but I can't figure out how it works under the hood in terms of thunks. > > To tell you the truth, I don't know how laziness works in general in haskell. > > Can someone help me understand how it works in this example, and give some pointers to materials on the subject? > > The "tying the knot" article on the wiki is pretty mind bending too. > > -- | @'forever' act@ repeats the action infinitely. > > forever :: (Monad m) => m a -> m b > > {-# INLINE forever #-}forever a = let a' = a >> a' in a' > > -- > > Eduardo Sato > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From joe at interare.com Tue Dec 24 08:18:11 2013 From: joe at interare.com (Joe) Date: Tue, 24 Dec 2013 15:18:11 +0700 Subject: [Haskell-cafe] Building PanDoc for iOS target, but failed in Haskell Template requirement by 'aeson' package In-Reply-To: <1387823307.11385.1.camel@kirk> References: <1387823307.11385.1.camel@kirk> Message-ID: <8678D9B8-C8A0-4612-A4ED-10299816220D@interare.com> Hi Joachim, thanks for pointing out the patch. It works exactly as I want. On Dec 24, 2013, at 1:28 AM, Joachim Breitner wrote: > Hi, > > Am Montag, den 23.12.2013, 09:38 -0500 schrieb Carter Schonwald: >> Patch Aeson locally so that it has no th module. Then fix any >> transitive breakages as you hit them. > > Debian patches TH out of aeson on architectures without an interpreter: > http://patch-tracker.debian.org/patch/series/view/haskell-aeson/0.6.2.1-2/th-option.diff > > None of the depending packages broke because of this. > > Greetings, > Joachim > > -- > Joachim ?nomeata? Breitner > mail at joachim-breitner.de ? http://www.joachim-breitner.de/ > Jabber: nomeata at joachim-breitner.de ? GPG-Key: 0x4743206C > Debian Developer: nomeata at debian.org From hoerdegen at funktional.info Tue Dec 24 10:37:11 2013 From: hoerdegen at funktional.info (=?ISO-8859-15?Q?Heinrich_H=F6rdegen?=) Date: Tue, 24 Dec 2013 11:37:11 +0100 Subject: [Haskell-cafe] Munich Haskell Holiday Meeting Message-ID: <52B963D7.2040207@funktional.info> Dear all, I want to announce a special holiday meeting of Munich's Haskell user group. It will take place on the 27th of December at 19h30 at Cafe Puck. Check out the details here: http://www.haskell-munich.de/news I wish everyone a nice holiday! Heinrich From a.kawashiro at gmail.com Tue Dec 24 19:03:17 2013 From: a.kawashiro at gmail.com (akira kawata) Date: Wed, 25 Dec 2013 04:03:17 +0900 Subject: [Haskell-cafe] Parse HTML that is contain javascript Message-ID: Hi, I am Akira. I want to parse HTML file that is contain javascript. But I cant come up with how to deal with script tag. Is there anyone help me? Details of probrem HTML code I want to parse is like following Because '<' is used as normal character in the script region, I can not use my HTML parser there. -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Tue Dec 24 19:06:06 2013 From: allbery.b at gmail.com (Brandon Allbery) Date: Tue, 24 Dec 2013 14:06:06 -0500 Subject: [Haskell-cafe] Parse HTML that is contain javascript In-Reply-To: References: Message-ID: On Tue, Dec 24, 2013 at 2:03 PM, akira kawata wrote: > > > > An XML parser might help with CDATA blocks. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From a.kawashiro at gmail.com Tue Dec 24 19:20:54 2013 From: a.kawashiro at gmail.com (akira kawata) Date: Wed, 25 Dec 2013 04:20:54 +0900 Subject: [Haskell-cafe] Parse HTML that is contain javascript In-Reply-To: References: Message-ID: Did you mean HaXmL? I am sorry that I can't explain what I want well. I think this module cannot parse HTML file like this. I don't mind the javascript code. I want to trancelate following code

hogehoge

","user":"ready","user.groups":"ready"}); } to like this

hogehoge >> >> > > An XML parser might help with CDATA blocks. > > -- > brandon s allbery kf8nh sine nomine > associates > allbery.b at gmail.com > ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad > http://sinenomine.net > -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Tue Dec 24 19:42:16 2013 From: allbery.b at gmail.com (Brandon Allbery) Date: Tue, 24 Dec 2013 14:42:16 -0500 Subject: [Haskell-cafe] Parse HTML that is contain javascript In-Reply-To: References: Message-ID: On Tue, Dec 24, 2013 at 2:20 PM, akira kawata wrote: > > Did you mean HaXmL? > Pick an XML parser. CDATA is an XML construct. Well-formed HTML *should* be XML compatible, although it's very rare to find proper well-formed HTML these days.... -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From 0slemi0 at gmail.com Tue Dec 24 19:52:36 2013 From: 0slemi0 at gmail.com (Andras Slemmer) Date: Tue, 24 Dec 2013 19:52:36 +0000 Subject: [Haskell-cafe] Parse HTML that is contain javascript In-Reply-To: References: Message-ID: The html-conduit package (http://hackage.haskell.org/package/html-conduit) can parse the above snippet easily: http://lpaste.net/97491 This code reads from stdin and prints out the parsed HTML. Try it out! For documentation on the returned AST take a look at xml-conduit ( http://hackage.haskell.org/package/xml-conduit) On 24 December 2013 19:42, Brandon Allbery wrote: > On Tue, Dec 24, 2013 at 2:20 PM, akira kawata wrote: >> >> Did you mean HaXmL? >> > > Pick an XML parser. CDATA is an XML construct. Well-formed HTML *should* > be XML compatible, although it's very rare to find proper well-formed HTML > these days.... > > -- > brandon s allbery kf8nh sine nomine > associates > allbery.b at gmail.com > ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad > http://sinenomine.net > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From lightquake at amateurtopologist.com Tue Dec 24 19:58:16 2013 From: lightquake at amateurtopologist.com (Patrick Hurst) Date: Tue, 24 Dec 2013 13:58:16 -0600 Subject: [Haskell-cafe] Parse HTML that is contain javascript In-Reply-To: References: Message-ID: On Tue, Dec 24, 2013 at 1:42 PM, Brandon Allbery wrote: > On Tue, Dec 24, 2013 at 2:20 PM, akira kawata wrote: >> >> Did you mean HaXmL? >> > > Pick an XML parser. CDATA is an XML construct. Well-formed HTML *should* > be XML compatible, although it's very rare to find proper well-formed HTML > these days.... > > This is actually not true; for example, not closing your
tags is perfectly valid HTML5 but invalid XML, and you can use > literals in script tags. The CDATA-inside-comments hack isn't necessary and hasn't been for years. You should try to parse HTML as HTML. That being said, if html-conduit works for you, use it; if not, try TagSoup, which doesn't try to structure your data into a DOM. >

hogehoge

> ","user":"ready"," > user.groups":"ready"}); > } > > It's worth noting that the browser will probably interpret the quoted as the end-of-script marker; Chrome did when I copied this into an HTML file and saved it. You need to replace it with "" or something similar. I'm a little surprised html-conduit doesn't interpret as end-of-script. -------------- next part -------------- An HTML attachment was scrubbed... URL: From 0slemi0 at gmail.com Tue Dec 24 20:02:36 2013 From: 0slemi0 at gmail.com (Andras Slemmer) Date: Tue, 24 Dec 2013 20:02:36 +0000 Subject: [Haskell-cafe] Parse HTML that is contain javascript In-Reply-To: References: Message-ID: > I'm a little surprised html-conduit doesn't interpret as end-of-script. It does interpret it as end-of-script. As far as i know that is the correct behaviour On 24 December 2013 19:58, Patrick Hurst wrote: > > > On Tue, Dec 24, 2013 at 1:42 PM, Brandon Allbery wrote: > >> On Tue, Dec 24, 2013 at 2:20 PM, akira kawata wrote: >>> >>> Did you mean HaXmL? >>> >> >> Pick an XML parser. CDATA is an XML construct. Well-formed HTML *should* >> be XML compatible, although it's very rare to find proper well-formed HTML >> these days.... >> >> > This is actually not true; for example, not closing your
tags is > perfectly valid HTML5 but invalid XML, and you can use > literals in script > tags. The CDATA-inside-comments hack isn't necessary and hasn't been for > years. You should try to parse HTML as HTML. > > That being said, if html-conduit works for you, use it; if not, try > TagSoup, which doesn't try to structure your data into a DOM. > > >>

hogehoge

>> ","user":"ready"," >> user.groups":"ready"}); >> } >> >> > > > It's worth noting that the browser will probably interpret the quoted > as the end-of-script marker; Chrome did when I copied this into > an HTML file and saved it. You need to replace it with "" or > something similar. I'm a little surprised html-conduit doesn't interpret > as end-of-script. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From cdsmith at gmail.com Tue Dec 24 22:26:33 2013 From: cdsmith at gmail.com (Chris Smith) Date: Tue, 24 Dec 2013 14:26:33 -0800 Subject: [Haskell-cafe] Parse HTML that is contain javascript In-Reply-To: References: Message-ID: Another option is the xmlhtml package, which I wrote and is used by Heist. An important factor in this decision will be what range of input you need to accept, and what you want as a result. A fully compliant HTML5 parser will parse most input, but the resulting data will be somewhat complex. On the other hand, xmlhtml will accept a smaller subset of HTML5 (but will handle your sample input here just fine) and produce a much simpler output. TagSoup, which someone else recommended, will accept even more, and produce flatter output, but I don't know how it would perform on this input. On Dec 24, 2013 2:58 PM, "Patrick Hurst" wrote: > > > On Tue, Dec 24, 2013 at 1:42 PM, Brandon Allbery wrote: > >> On Tue, Dec 24, 2013 at 2:20 PM, akira kawata wrote: >>> >>> Did you mean HaXmL? >>> >> >> Pick an XML parser. CDATA is an XML construct. Well-formed HTML *should* >> be XML compatible, although it's very rare to find proper well-formed HTML >> these days.... >> >> > This is actually not true; for example, not closing your
tags is > perfectly valid HTML5 but invalid XML, and you can use > literals in script > tags. The CDATA-inside-comments hack isn't necessary and hasn't been for > years. You should try to parse HTML as HTML. > > That being said, if html-conduit works for you, use it; if not, try > TagSoup, which doesn't try to structure your data into a DOM. > > >>

hogehoge

>> ","user":"ready"," >> user.groups":"ready"}); >> } >> >> > > > It's worth noting that the browser will probably interpret the quoted > as the end-of-script marker; Chrome did when I copied this into > an HTML file and saved it. You need to replace it with "" or > something similar. I'm a little surprised html-conduit doesn't interpret > as end-of-script. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From achudnov at gmail.com Tue Dec 24 22:37:26 2013 From: achudnov at gmail.com (Andrey Chudnov) Date: Wed, 25 Dec 2013 02:37:26 +0400 Subject: [Haskell-cafe] Parse HTML that is contain javascript In-Reply-To: References: Message-ID: <52BA0CA6.6050905@gmail.com> I've used HXT with the tagsoup backend for parsing HTML with embedded JavaScript. Worked fine for me, although I don't think I've ever had to deal with CDATA embedded in comments of scripts. You can have a look at the source of the 'jespresso' library on hackage if interested. On 12/24/2013 11:03 PM, akira kawata wrote: > Hi, I am Akira. > I want to parse HTML file that is contain javascript. > But I cant come up with how to deal with script tag. > Is there anyone help me? > > Details of probrem > HTML code I want to parse is like following > > > > > > Because '<' is used as normal character in the script region, > I can not use my HTML parser there. > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- An HTML attachment was scrubbed... URL: From joe at interare.com Wed Dec 25 06:56:12 2013 From: joe at interare.com (Joe) Date: Wed, 25 Dec 2013 13:56:12 +0700 Subject: [Haskell-cafe] Building PanDoc for iOS target, but failed in Haskell Template requirement by 'aeson' package In-Reply-To: References: Message-ID: Hi Carter, Thanks for your fasttt response. After patching Aeson to remove TH module, I've been successfully build all dependencies and today finally succeeded statically linked simple Haskell app that calls PanDoc library to iOS application. I haven't tested too much, but I'm concerned that the resulting binary file is more than 50mb. For comparison, a simple Haskell app linked to iOS app will generate 5mb binary. Is there anyway to make it smaller such as stripping the binaries? Thanks so much and merry Christmas to everyone here :). Cheers, Joe Plan it, Do it, Let it GO :) > On 23 Des 2013, at 21.38, Carter Schonwald wrote: > > Patch Aeson locally so that it has no th module. Then fix any transitive breakages as you hit them. > > General th support for cross compiling ghc is on the roadmap for getting worked out in ghc, but it's really just part of generally improving ghc so that there can be multi target cross compilation support. This is because th will run on your dev Mac, but me generating code for your iOS device! > > Ghcjs actuall has such cross compilation, so some ideas could be borrowed from there. > > Hopefully it'll happen in the next year, though when and by whom is still a bit unclear. > >> On Monday, December 23, 2013, Joe wrote: >> Hi, I've been trying to cross-compile PanDoc for iOS target for the last few days. I have been quite successfull from building stage-1 GHC for iOS target and many packages dependencies required by PanDoc until I see that 'aeson' package require Haskell Template which is not supported in cross compilation. >> >> As pointed in iOS CrossCompiling Wiki page, it seems that Template Haskell doesn't work yet and still in wish list. >> >> Is there any hack or workaround to be able to cross-compile 'aeson' package for iOS target? Can I compile 'aeson' without Haskell Template? Anybody know when Template Haskell in CrossCompiling for iOS will be added? >> >> Thanks a lot! >> >> Best regards, >> Joe -------------- next part -------------- An HTML attachment was scrubbed... URL: From cdep.illabout at gmail.com Wed Dec 25 11:45:12 2013 From: cdep.illabout at gmail.com (cdep.illabout at gmail.com) Date: Wed, 25 Dec 2013 20:45:12 +0900 Subject: [Haskell-cafe] (automatically) adding import statements in vim Message-ID: Are there any tools or vim-plugins that will automatically add import statements? For instance, I have the following code: ... import Data.Maybe (fromJust) import Text.ParserCombinators.Parsec (ParseError) import Text.Printf (printf) ... parseMyString :: String -> Either ParseError String parseMyString stringToParse = parse myParser "(unknown)" stringToParse Here's what I want to have happen. I put my cursor over "parse" and press some keystroke. It automatically adds the parse function to the list of import statements from the Text.ParserCombinators.Parsec module (hopefully sorted alphabetically). So the import statements end up looking like this: ... import Data.Maybe (fromJust) import Text.ParserCombinators.Parsec (ParseError, parse) import Text.Printf (printf) ... The haskellmode vim plugin (https://github.com/lukerandall/haskellmode-vim) has functionality similar to this, but it can only add new import lines. It can't add functions/types to existing import lines. The best it can do is something like this: ... import Data.Maybe (fromJust) import Text.ParserCombinators.Parsec (ParseError) import Text.Printf (printf) import Text.ParserCombinators.Parsec (parse) ... This is alright, but I have to go back and edit it by hand to make it look like the above. Are there any tools or vim-plugins that can do this automatically? From carter.schonwald at gmail.com Wed Dec 25 13:28:41 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Wed, 25 Dec 2013 08:28:41 -0500 Subject: [Haskell-cafe] Building PanDoc for iOS target, but failed in Haskell Template requirement by 'aeson' package In-Reply-To: References: Message-ID: Build all the libs with split objects flag. I think test flag can be set in the cabal config file. There's other things you can do, but that's the big thing that should jus work. On Wednesday, December 25, 2013, Joe wrote: > Hi Carter, > > Thanks for your fasttt response. After patching Aeson to remove TH module, > I've been successfully build all dependencies and today finally succeeded > statically linked simple Haskell app that calls PanDoc library to iOS > application. > > I haven't tested too much, but I'm concerned that the resulting binary > file is more than 50mb. For comparison, a simple Haskell app linked to iOS > app will generate 5mb binary. > > Is there anyway to make it smaller such as stripping the binaries? > > Thanks so much and merry Christmas to everyone here :). > > Cheers, > Joe > > Plan it, Do it, Let it GO :) > > On 23 Des 2013, at 21.38, Carter Schonwald > > wrote: > > Patch Aeson locally so that it has no th module. Then fix any transitive > breakages as you hit them. > > General th support for cross compiling ghc is on the roadmap for getting > worked out in ghc, but it's really just part of generally improving ghc so > that there can be multi target cross compilation support. This is because > th will run on your dev Mac, but me generating code for your iOS device! > > Ghcjs actuall has such cross compilation, so some ideas could be borrowed > from there. > > Hopefully it'll happen in the next year, though when and by whom is still > a bit unclear. > > On Monday, December 23, 2013, Joe wrote: > >> Hi, I've been trying to cross-compile PanDoc for iOS target for the last >> few days. I have been quite successfull from building stage-1 GHC for iOS >> target and many packages dependencies required by PanDoc until I see that >> 'aeson' package require Haskell Template which is not supported in cross >> compilation. >> >> As pointed in iOS CrossCompiling Wiki page, >> it seems that Template Haskell doesn't work yet and still in wish list. >> >> Is there any hack or workaround to be able to cross-compile 'aeson' >> package for iOS target? Can I compile 'aeson' without Haskell Template? >> Anybody know when Template Haskell in CrossCompiling for iOS will be added? >> >> Thanks a lot! >> >> Best regards, >> Joe >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From a.kawashiro at gmail.com Wed Dec 25 17:04:25 2013 From: a.kawashiro at gmail.com (akira kawata) Date: Thu, 26 Dec 2013 02:04:25 +0900 Subject: [Haskell-cafe] Parse HTML that is contain javascript Message-ID: Many thanks for your cooperations. I have decided to use xmlhtml instead of making my own html parser. 2013/12/25 akira kawata > Hi, I am Akira. > I want to parse HTML file that is contain javascript. > But I cant come up with how to deal with script tag. > Is there anyone help me? > > Details of probrem > HTML code I want to parse is like following > > > > > > Because '<' is used as normal character in the script region, > I can not use my HTML parser there. > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From corentin.roux at gmail.com Thu Dec 26 10:34:27 2013 From: corentin.roux at gmail.com (Corentin Roux) Date: Thu, 26 Dec 2013 02:34:27 -0800 (PST) Subject: [Haskell-cafe] Haskell Singapore Meetup In-Reply-To: <698df6fe-117a-4cc7-b26f-6f767d68656f@googlegroups.com> References: <8e682203-ee48-4536-99af-276a2a56a573@googlegroups.com> <698df6fe-117a-4cc7-b26f-6f767d68656f@googlegroups.com> Message-ID: Hi Jesse, Just saw your email. I started the data science team at Zalora and was behind the adoption of Haskell. As a short background, I didn't know how to program 2 years ago, when I left a finance job for a small startup in Australia. I didn't know anything about business intelligence either, and started with excel sheets. But the work was very repetitive so I picked up programming to try and automate some of it. After I moved to the South East Asian version of the same company, Zalora, I had read up a lot more, including books like SICP, and all of Paul Graham's essays. I liked both his concept of the "blub" ladder of abstraction, and his idea of using a programming language as a "secret weapon". Lisp is nice, but the pure nature of Haskell and the work that was done on the compiler both convinced me that it was a better secret weapon to solve my issue of not having enough budget or time to set up a standard BI setup (I separately was not too happy with SaaS providers anyway, so decided that in-house was the only way we could afford what I wanted). I had picked up enough Haskell to hire the first person (Dat Le) on the basis of his answers to a bunch of exercises we used as a filter (we were also helped by Hisham Zarka, current CMO of another Rocket company, Namshi and former Googler in MV). Dat did an extraordinary amount of work acting as proof of concept, much of it in Haskell, so it worked out even better than expected and we picked up enough budget to build a proper team. We called it "Data Science" because that seems to be the current buzz word for hiring smart guys. Haskell is unique in that: - it has a well defined standard with enormous amounts of research going into it (both the language, and its libraries); - the purity simplifies scaling, which I already needed, as well as all the standard improvements from catching most bugs before compiling, shorter code, etc.; - it is relatively hard to write Haskell that compiles as a beginner, thus acting as a natural talent filter (that can be expanded upon: it also attracts the kind of people who enjoy programming for its own sake, just like Lisps). I would disagree that there are very few people that know the language. I did put up my first ad as Python, with a preference for people with "experience in FPLs, like Haskell, Clojure, Erlang or Scala". I had over 200 applications, of which less than 5% were people we'd consider working with (mostly "Greetings! I believe my extensive experience and considerable skills make me an ideal fit for your company."). Every ad thereafter has been in Haskell, and on average over half the applicants are good enough to be hired (which is a great situation to be in as an employer, although I feel bad for the Haskellers meeting so few opportunities). The community's quality is simply exceptional. I'll post more about its use, which is rapidly expanding beyond "data science", in a few weeks. If anybody is interested: http://www.haskellers.com/jobs/61 Best, Corentin Le samedi 21 d?cembre 2013 05:59:30 UTC, Jesse Armand a ?crit : > > Hi Paul, > > A follow-up from the meetup. I was tired yesterday after work. So, didn't > have the energy to socialize. > > Just a few of my thoughts. First of all, it was a good start to promote > haskell in Singapore. > > I'm very new to Haskell. I did some ruby, python and node.js at a very > small scale before. Most of time I do Objective-C programming as a job. > > Just finished reading Higher Order Functions, and will start learning > about making my own typeclasses. This is based on > http://learnyouahaskell.com. So, I barely know anything about the > language. Though, I'm aware that its popularity is growing, and also the > existence of a haskell web framework such as Yesod. > > So, for this reason, I am curious about how Zalora decided to choose > Haskell as a programming language. Given that, there are very few people > who know the language. It will also be great to understand where is it > being used on the technology stack, and some examples of how Haskell is > really advantageous for a particular use case. > > Thanks > > On Wednesday, December 18, 2013 6:12:52 PM UTC+8, Paul Meng wrote: >> >> Hi all, >> >> I've already posted on the reddit but forgot to post it here. >> >> It's going to be Christmas, and a good way to celebrate it is to have a >> Haskell meetup. On this Friday, Dec 20. We are going to host it at Google >> Singapore office. >> http://www.meetup.com/HASKELL-SG/events/154702892/ >> There would be a short sharing and have some time to meet with other >> Haskell programmers (or FP programmer in general) after the talk. >> If you happen to be in Singapore, welcome to stop by! >> >> For people signed up before, notice that we are moving from Zalora to >> Google's office to have a bigger meeting room. >> And due to the access policy, please fill out your full name, e-mail and >> company in the following form. >> >> https://docs.google.com/forms/d/1pTQA3eK7Qsxbq_Tw8nPPX6MIUnQuGsm23rT5bfhtw-8/viewform >> >> Paul Meng >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From haskell-cafe at maartenfaddegon.nl Thu Dec 26 11:36:03 2013 From: haskell-cafe at maartenfaddegon.nl (Maarten Faddegon) Date: Thu, 26 Dec 2013 11:36:03 +0000 Subject: [Haskell-cafe] parametrized data types and Template Haskell Message-ID: <52BC14A3.2080505@maartenfaddegon.nl> Dear Cafe, Hope you all had a nice Christmas. I have been playing with generating method instances using Template Haskell but am a bit stuck now trying to generate an instance for a parametrized data type. I would like to generate the following: > instance (MyClass a) => MyClass (Tree a) where > mymethod _ = "todo" I defined a genMyClassInstance that is working fine for unparametrized data types, but clearly there is nothing here that inserts the '(MyClass a) =>' part here. My first question is: how should I instruct Template Haskell to insert the beforementioned code when appropriate? > genMyClassInstance :: Name -> Q [Dec] > genMyClassInstance name > = [d|instance MyClass $(conT name) where > mymethod _ = "todo" > |] My second question is how to pass the Name of a parametrized data type? I tried the following, but GHC does not seem to like that: "Not in scope: type constructor or class `Tree a' Perhaps you meant `Tree'" > $(genMyInstance (mkName "Tree a")) Thank you! Maarten Faddegon From daniel.trstenjak at gmail.com Thu Dec 26 16:38:20 2013 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Thu, 26 Dec 2013 17:38:20 +0100 Subject: [Haskell-cafe] (automatically) adding import statements in vim In-Reply-To: References: Message-ID: <20131226163820.GA29020@machine> Hi, I've just pushed the first versions of: https://github.com/dan-t/hsimport https://github.com/dan-t/vim-hsimport So there're certainly still some rough edges. Greetings, Daniel From michael at orlitzky.com Thu Dec 26 17:17:56 2013 From: michael at orlitzky.com (Michael Orlitzky) Date: Thu, 26 Dec 2013 12:17:56 -0500 Subject: [Haskell-cafe] Top-down inserts in Persistent Message-ID: <52BC64C4.6080709@orlitzky.com> I'm loading data from XML into a Haskell data type, and I'd like to use Persistent to save it to a database. The examples from the Yesod book have you manually define a FooId field and create the relationships yourself from the bottom up. For example, "a person has many cars": blah blah [persistLowerCase| Person name String Car ownerId PersonId Eq name String |] This works well if you're responsible for creating every person/car manually. But what if the data are given to you? If I were to parse people from an XML file, the cars wouldn't have people_ids in them. Instead I'd get, blah blah [persistLowerCase| Person name String cars [Car] Car name String |] As long as the cars list contains another Persistent type, it seems like I should be able to insert a person and have it insert the cars, with proper foreign keys, automatically. Doing it manually isn't straight-forward because I can't add the "ownerId" field to my Car type and still expect to parse it from the XML (which has no such field). Any ideas? I'm not married to Persistent yet; I just want to read in some XML and save it to a database without having to specify the names and types in three places (preferred place: in Haskell). I don't care too much about the schema I get as long as it's relational. From vogt.adam at gmail.com Thu Dec 26 18:56:42 2013 From: vogt.adam at gmail.com (adam vogt) Date: Thu, 26 Dec 2013 13:56:42 -0500 Subject: [Haskell-cafe] parametrized data types and Template Haskell In-Reply-To: <52BC14A3.2080505@maartenfaddegon.nl> References: <52BC14A3.2080505@maartenfaddegon.nl> Message-ID: Hello Maarten, You might also accept a string "Tree a" and then parse it as a Type by use of haskell-src-meta's parseType. Then you'll have to search through the Type data to get all the type variables, which might be tricky in the general case. Easier for you would be to require users to specify their type as: [t| forall a. Tree a |] This gives a data structure that looks like: ForallT [PlainTV a_16] [] (AppT (ConT Data.Tree.Tree) (VarT a_16)) Which I found by typing this into ghci: $([t| forall a. Tree a |] >>= stringE . show) The ForallT has all the pieces to generate the whole instance declaration: genMyClassInstance' :: Type -> Q Dec genMyClassInstance' (ForallT tvs _ ty) = instanceD (sequence [ classP ''MyClass [varT t] | PlainTV t <- tvs ]) [t| MyClass $(return ty) |] [funD 'myMethod [clause [wildP] (normalB [| "todo" |]) []] ] It often doesn't work to use [| |] quotes everywhere. So you have to use the functions/constructors in the Language.Haskell.TH module to make it yourself. That doesn't rule out being able to use those quotes as arguments to those functions (as you see above). Finally the use of genMyClassInstance' looks like: fmap return . genMyClassInstance' =<< [t| forall a. Tree a |] Which can be mostly hidden in another function to define which might be called "genMyClassInstance". Regards, Adam From trebla at vex.net Thu Dec 26 19:09:54 2013 From: trebla at vex.net (Albert Y. C. Lai) Date: Thu, 26 Dec 2013 14:09:54 -0500 Subject: [Haskell-cafe] forever function laziness In-Reply-To: References: Message-ID: <52BC7F02.6020301@vex.net> On 13-12-23 09:02 PM, Eduardo Sato wrote: > The recursive definition does make sense to me in a mathematical way, but I can't figure out how it works under the hood in terms of thunks. > To tell you the truth, I don't know how laziness works in general in haskell. For lazy evaluation, see my http://www.vex.net/~trebla/haskell/lazy.xhtml The following produces and destroys 10 cons cells. Unless the compiler does smart things. main = print (take 10 (plenty 5)) plenty n = n : plenty n The following produces and reuses 1 cons cell. main = print (take 10 (plenty 5)) plenty n = s where s = n : s -- or, let s = n : s in s Reusing comes from sharing. Sharing comes from aliasing. Aliasing is using the same name s. Self-aliasing is then using the same name s on both sides of =. It is best to draw some diagrams. I am too lazy to do it here. But I did some in my lazy evaluation article, and it shows you how to do more on your own. forever is similar. > The "tying the knot" article on the wiki is pretty mind bending too. Most authors on the haskell wiki are driven by excitement. The problem with excitement is that excited authors lose readers by telling too much and starting too high. From cobbe at ccs.neu.edu Thu Dec 26 20:08:39 2013 From: cobbe at ccs.neu.edu (Richard Cobbe) Date: Thu, 26 Dec 2013 15:08:39 -0500 Subject: [Haskell-cafe] integrating Happy & Alex monads Message-ID: <20131226200713.GA320@vimes.local> I'm working on a program in which I'd like to use Alex and Happy to parse the input. I've written the scanner, and it uses Alex's "monadUserState" wrapper to track source location and various other things. Now, the problem is to integrate it with the parser. As far as I can tell from reading the Happy documentation, I need to use a monadic Parser in Happy as well, but the manuals don't relaly provide a lot of information about how to integrate the two. And I haven't really been able to find many examples of this either. Lots of folks cite "the Haskell parser", although I'm not sure which implementation that's referring to. I did check out the GHC source, and while it contains an Alex parser specification, it doesn't look like anything actually *uses* this, preferring instead a handwritten parser. Could anyone point me to a discussion of how to integrate these two tools, or examples of places where folks have done this before? Thanks much, Richard From eir at cis.upenn.edu Thu Dec 26 20:39:38 2013 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Thu, 26 Dec 2013 15:39:38 -0500 Subject: [Haskell-cafe] parametrized data types and Template Haskell In-Reply-To: <52BC14A3.2080505@maartenfaddegon.nl> References: <52BC14A3.2080505@maartenfaddegon.nl> Message-ID: My experience with Template Haskell is that any non-trivial code generation (that is, anything more complicated than a simple substitution into a simple template) requires heavy use of the TH constructors, as Adam suggests. I tend to prefer using the non-monadic ones (like `InstanceD :: Cxt -> Type -> [Dec] -> Dec`) over the monadic ones (exported from Language.Haskell.TH.Lib and like `instanceD :: Q Cxt -> Q Type -> [Q Dec] -> Q Dec`), though you may find the opposite is true in your domain. Using these constructors, it is straightforward to specify a context, and you can use an empty list (the type `Cxt` is a synonym for `[Pred]`) for an empty context. As for naming a parameterized type, just use the base name. So, `Tree a` would be (AppT (ConT (mkName "Tree") (VarT (mkName "a"))) assuming `a` is in scope somehow. You may also be interested in the naming quote syntax: in an expression, code like 'blah expands out to a name for the term-level thing (i.e., function or variable) named `blah` that is in scope. Code like ''Tree expands out to a name for the **type**-level thing (i.e., type, type function, class, etc.) name `Tree` that is in scope. Note that the line of code above has two single-quotes and no double-quotes. The number of quotes is necessary to disambiguate data constructors from types. I hope this helps! Richard On Dec 26, 2013, at 6:36 AM, Maarten Faddegon wrote: > Dear Cafe, > > Hope you all had a nice Christmas. > > I have been playing with generating method instances using Template Haskell but am a bit stuck now trying to generate an instance for a parametrized data type. > > I would like to generate the following: > > > instance (MyClass a) => MyClass (Tree a) where > > mymethod _ = "todo" > > I defined a genMyClassInstance that is working fine for unparametrized data types, but clearly there is nothing here that inserts the '(MyClass a) =>' part here. My first question is: how should I instruct Template Haskell to insert the beforementioned code when appropriate? > > > genMyClassInstance :: Name -> Q [Dec] > > genMyClassInstance name > > = [d|instance MyClass $(conT name) where > > mymethod _ = "todo" > > |] > > My second question is how to pass the Name of a parametrized data type? I tried the following, but GHC does not seem to like that: "Not in scope: type constructor or class `Tree a' Perhaps you meant `Tree'" > > > $(genMyInstance (mkName "Tree a")) > > Thank you! > > Maarten Faddegon > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From bertram.felgenhauer at googlemail.com Fri Dec 27 01:13:06 2013 From: bertram.felgenhauer at googlemail.com (Bertram Felgenhauer) Date: Fri, 27 Dec 2013 02:13:06 +0100 Subject: [Haskell-cafe] Indirect Cycle Detection problem [was: finding "good work" in CS] In-Reply-To: <52B329E1.1040109@informatik.uni-marburg.de> Message-ID: <20131227011305.GB4376@24f89f8c-e6a1-4e75-85ee-bb8a3743bb9f> Hi Thomas and Richard, > > [...] > >Here's a piece of computer science that I would like some help > >with. I call it the Indirect Cycle Detection problem. > > > >Given: Domains P and E, > > functions f : P -> Maybe P > > g : P -> E > > > >Define to_list :: Maybe P -> [E] > > to_list Nothing = [] > > to_list (Just p) = g p : to_list (f p) > > > >Given: That f is cyclic starting at p0. > > > >Find: The shortest alpha, beta such that > > to_list p0 is alpha ++ cycle beta > > and do so *efficiently*. > > > >Now, I can use tortoise-and-hare to find a cycle in f > >and then use brute force to find a shortest prefix and > >cycle of to_list ... The stuff I've checked so far > >about periods in strings has nothing to say about > >periods that begin _after_ a non-empty prefix. As Thomas explained, that's sufficient. The tortoise-and-hare algorithm will identify a tail of the sequence that is known to be periodic, and then we can find the smallest period using an algorithm that operates on a finite string. Once the actual cycle length is known, identifying the prefix is easy. > Also, I can not see where this "non-empty prefix" notion comes from. > Perhaps you have a different definition for cyclic? See http://en.wikipedia.org/wiki/Cycle_detection . > In this case, ps has the form (prefix ++ (cycle p_period_n)) and to > find this structure, you need to find the first element of ps that > occurs twice. (Before, you knew this would be p0.) For that, you > need a set implementation for elements of P that gives you efficient > adding of one element and lookup. Since we know nothing about P's > elements, we use the list itself and get a runtime of > Theta((i+n)^2). The tortoise-and-hare algorithm does this in O(i+n) time. I'm attaching some code. For simplicity, it works with functions @f :: a -> a@, @g :: a -> b@, which define the sequence @xs = map g (iterate f x)@. I'm using Brent's algorithm [1] for cycle detection, which finds the period and a periodic suffix of @iterate f x@, followed by Duval's algorithm [2] to identify the actual cycle length of @xs at . (The main advantage of Duval's algorithm over Knuth-Morris-Pratt is that less space is required. One disadvantage is that we need a total order on @b at .) The total running time is linear in the cycle length and initial prefix length of @iterate f x@, i.e. O(i+n). There are two entry points of interest in the code. - factor f g x Find prefix and repeated segment of @map g (iterate f x)@. - factor' f g x Find prefix and repeated segment of @to_list x at . The repeated segment will be empty if @to_list x@ is a finite list. Cheers, Bertram [1] http://en.wikipedia.org/wiki/Cycle_detection [2] http://stackoverflow.com/questions/3459509/minimal-cyclic-shift-algorithm-explanation -------------- next part -------------- A non-text attachment was scrubbed... Name: duval.hs Type: text/x-haskell Size: 1952 bytes Desc: not available URL: From florbitous at gmail.com Fri Dec 27 05:47:33 2013 From: florbitous at gmail.com (Bernie Pope) Date: Fri, 27 Dec 2013 16:47:33 +1100 Subject: [Haskell-cafe] integrating Happy & Alex monads In-Reply-To: <20131226200713.GA320@vimes.local> References: <20131226200713.GA320@vimes.local> Message-ID: Hi Richard, I used Alex and Happy in my library for parsing Python. Here's some links to the relevant parts of the code: https://github.com/bjpop/language-python/blob/master/src/Language/Python/Version3/Parser/Lexer.x https://github.com/bjpop/language-python/blob/master/src/Language/Python/Version3/Parser/Parser.y It has been a while since I wrote that code (2009), so I'm a bit hazy on the details, but hopefully you can find what you need in there. Cheers, Bernie. On 27 December 2013 07:08, Richard Cobbe wrote: > I'm working on a program in which I'd like to use Alex and Happy to parse > the input. I've written the scanner, and it uses Alex's "monadUserState" > wrapper to track source location and various other things. Now, the > problem is to integrate it with the parser. As far as I can tell from > reading the Happy documentation, I need to use a monadic Parser in Happy as > well, but the manuals don't relaly provide a lot of information about how > to integrate the two. And I haven't really been able to find many examples > of this either. Lots of folks cite "the Haskell parser", although I'm not > sure which implementation that's referring to. I did check out the GHC > source, and while it contains an Alex parser specification, it doesn't look > like anything actually *uses* this, preferring instead a handwritten > parser. > > Could anyone point me to a discussion of how to integrate these two tools, > or examples of places where folks have done this before? > > Thanks much, > > Richard > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From dagitj at gmail.com Fri Dec 27 06:05:12 2013 From: dagitj at gmail.com (Jason Dagit) Date: Thu, 26 Dec 2013 22:05:12 -0800 Subject: [Haskell-cafe] integrating Happy & Alex monads In-Reply-To: <20131226200713.GA320@vimes.local> References: <20131226200713.GA320@vimes.local> Message-ID: I made this example specifically to help people with this problem (the problem being that the documentation is spotty here). It's the expression parser from the happy documentation using the monad that alex can generate for you. It's the cleanest and simplest way (and simplest example) that I found to merge the two. I should really submit this as a documentation fix to happy. https://github.com/dagit/happy-plus-alex Enjoy! Jason On Thu, Dec 26, 2013 at 12:08 PM, Richard Cobbe wrote: > I'm working on a program in which I'd like to use Alex and Happy to parse > the input. I've written the scanner, and it uses Alex's "monadUserState" > wrapper to track source location and various other things. Now, the > problem is to integrate it with the parser. As far as I can tell from > reading the Happy documentation, I need to use a monadic Parser in Happy as > well, but the manuals don't relaly provide a lot of information about how > to integrate the two. And I haven't really been able to find many examples > of this either. Lots of folks cite "the Haskell parser", although I'm not > sure which implementation that's referring to. I did check out the GHC > source, and while it contains an Alex parser specification, it doesn't look > like anything actually *uses* this, preferring instead a handwritten > parser. > > Could anyone point me to a discussion of how to integrate these two tools, > or examples of places where folks have done this before? > > Thanks much, > > Richard > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From cobbe at ccs.neu.edu Fri Dec 27 12:51:08 2013 From: cobbe at ccs.neu.edu (Richard Cobbe) Date: Fri, 27 Dec 2013 07:51:08 -0500 Subject: [Haskell-cafe] integrating Happy & Alex monads In-Reply-To: References: <20131226200713.GA320@vimes.local> Message-ID: <20131227125108.GB320@vimes.local> On Thu, Dec 26, 2013 at 10:05:12PM -0800, Jason Dagit wrote: > I made this example specifically to help people with this problem (the > problem being that the documentation is spotty here). > > It's the expression parser from the happy documentation using the monad > that alex can generate for you. It's the cleanest and simplest way (and > simplest example) that I found to merge the two. I should really submit > this as a documentation fix to happy. > > https://github.com/dagit/happy-plus-alex Oh, wonderful! I've only had a chance to glance at this quickly, but it looks like it's exactly what I'm looking for. I'll definitely spend some more time with this example in a day or so when I have more time. Thanks a bunch -- this is extremely helpful! Richard From doaitse at swierstra.net Fri Dec 27 21:32:00 2013 From: doaitse at swierstra.net (Doaitse Swierstra) Date: Fri, 27 Dec 2013 22:32:00 +0100 Subject: [Haskell-cafe] [Fp-nl] Call for participation: Dutch Functional Programming Day 2014 Message-ID: <4D11D241-9128-474A-AABA-3331C59958D5@swierstra.net> Dear all, The next Netherlands Functional Programming day (NL-FP 2014) will take place on Friday, January 10, 2014 at the University of Amsterdam at Amsterdam Science Park. You are all cordially invited to participate and, of course, to give a presentation. The day will largely follow the pattern of the previous NL-FP days with a moderately timed start, a day of enjoyable talks in between lunch and coffee breaks and ending with a joint dinner in a nearby restaurant. All further details can be found on the NL-FP 2014 site(s): http://staff.science.uva.nl/~grelck/nl-fp-day-2014.html http://staff.science.uva.nl/~grelck/nl-fp-dag-2014.html Hope to see you all in Amsterdam in January! Best regards, Clemens Grelck -- ---------------------------------------------------------------------- Dr Clemens Grelck Science Park 904 University Lecturer 1098XH Amsterdam Netherlands University of Amsterdam Institute for Informatics T +31 (0) 20 525 8683 Computer Systems Architecture Group F +31 (0) 20 525 7490 Office C3.105 www.science.uva.nl/~grelck ---------------------------------------------------------------------- _______________________________________________ Fp-nl mailing list Fp-nl at lists.science.uu.nl http://lists.science.uu.nl/mailman/listinfo/fp-nl From oleg at okmij.org Sat Dec 28 08:54:52 2013 From: oleg at okmij.org (oleg at okmij.org) Date: 28 Dec 2013 08:54:52 -0000 Subject: [Haskell-cafe] Consistency issue with type level numeric literals Message-ID: <20131228085452.38189.qmail@www1.g3.pair.com> GHC 7.6.3 has quite convenient type-level numeric literals. We can use numbers like 1 and 2 in types. However, using the type level numeral has been quite a bit of a challenge, illustrated, for example, by the following SO question. http://stackoverflow.com/questions/20809998/type-level-nats-with-literals-and-an-injective-successor It seems the challenge has the reason: the type level numerals and their operations provided in GHC.TypeLits have a consistency issue. The following code demonstrates the issue: it constructs two distinct values of the type Sing 2. Singletons aren't singletons. {-# LANGUAGE KindSignatures #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE PolyKinds #-} module NotSing where import GHC.TypeLits -- GHC strangely enough lets us define instances for (+) type instance 1 + 1 = 0 type instance 0 + 1 = 2 -- A singular representative of 1::Nat s1 :: Sing 1 s1 = withSing id -- A singular representative of 2::Nat s2 :: Sing 2 s2 = withSing id is2 :: IsZero 0 is2 = IsSucc s1 tran :: IsZero 0 -> Sing 2 tran (IsSucc x) = case isZero x of IsSucc y -> case isZero y of IsZero -> x -- Another singular representative of 2::Nat -- A singular representative of 2::Nat s2' :: Sing 2 s2' = tran is2 {- *NotSing> s2 2 *NotSing> s2' 1 -} From hjgtuyl at chello.nl Sat Dec 28 13:30:28 2013 From: hjgtuyl at chello.nl (Henk-Jan van Tuyl) Date: Sat, 28 Dec 2013 14:30:28 +0100 Subject: [Haskell-cafe] Segmentation fault/access violation when CPLUS_INCLUDE_PATH not set correctly Message-ID: L.S., When I compile an application against an experimental version of wxHaskell*, the application always ends with the message: Segmentation fault/access violation in generated code , unless I set the environment variable CPLUS_INCLUDE_PATH to C:\Program Files\Haskell Platform\2013.2.0.0\mingw\lib\gcc\mingw32\4.5.2\include\c++\ , which is the same value as used when compiling wxHaskell. If I copy the contents of C:\Programs\Haskell Platform\2013.2.0.0\ to some other location and let CPLUS_INCLUDE_PATH point to the new location of directory c++, the segmentation fault message reappears. Why is this and how can create an application that also works on another computer? Regards, Henk-Jan van Tuyl * wxHaskell is a binding to the wxWidgets GUI library, which is written in C++ -- Folding at home What if you could share your unused computer power to help find a cure? In just 5 minutes you can join the world's biggest networked computer and get us closer sooner. Watch the video. http://folding.stanford.edu/ http://Van.Tuyl.eu/ http://members.chello.nl/hjgtuyl/tourdemonad.html Haskell programming -- From hans at hanshoglund.se Sat Dec 28 15:47:40 2013 From: hans at hanshoglund.se (=?iso-8859-1?Q?Hans_H=F6glund?=) Date: Sat, 28 Dec 2013 16:47:40 +0100 Subject: [Haskell-cafe] Name for the following combinators? Message-ID: <79FD177A-56CF-4418-B351-D4C19D5DA51D@hanshoglund.se> Dear all, Recently I have found myself using these two combinators a lot: http://lpaste.net/97643 They basically allow composition of any m satisfying (Monad m, Traversable m). I have been thinking about moving them to a separate package and giving them better names (in the original paper, they are simply called join and bind). Does anyone have a better suggestion for the name of the package, module and the two combinators? Should they be called joinDefault, or simply called join and bind to be imported with a qualifier? This might be a bicycle-shed question, but I tend to find stylistic questions important when it comes to improving clarity and readability. Best wishes, Hans From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Sat Dec 28 15:58:10 2013 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Sat, 28 Dec 2013 15:58:10 +0000 Subject: [Haskell-cafe] Name for the following combinators? In-Reply-To: <79FD177A-56CF-4418-B351-D4C19D5DA51D@hanshoglund.se> References: <79FD177A-56CF-4418-B351-D4C19D5DA51D@hanshoglund.se> Message-ID: <20131228155810.GN17875@weber> On Sat, Dec 28, 2013 at 04:47:40PM +0100, Hans H?glund wrote: > Recently I have found myself using these two combinators a lot: http://lpaste.net/97643 FYI it looks a lot like these give rise to a monad transformer. Tom From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Sat Dec 28 16:13:52 2013 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Sat, 28 Dec 2013 16:13:52 +0000 Subject: [Haskell-cafe] Name for the following combinators? In-Reply-To: <20131228155810.GN17875@weber> References: <79FD177A-56CF-4418-B351-D4C19D5DA51D@hanshoglund.se> <20131228155810.GN17875@weber> Message-ID: <20131228161351.GO17875@weber> On Sat, Dec 28, 2013 at 03:58:10PM +0000, Tom Ellis wrote: > On Sat, Dec 28, 2013 at 04:47:40PM +0100, Hans H?glund wrote: > > Recently I have found myself using these two combinators a lot: http://lpaste.net/97643 > > FYI it looks a lot like these give rise to a monad transformer. Specifically, the following. Careful though: I haven't made any effort to check this satisfies the monad or transformer laws. If 'Wrap m n' genuinely satisfies the monad laws then you don't need new combinators. Just Wrap the type constructors and get a real monad. (If 'Wrap m' is genuinely a monad transformer, so much the better!) Tom import Control.Monad.Trans (MonadTrans, lift) import Control.Monad (join) import qualified Data.Traversable as T import Data.Traversable (Traversable) data Wrap m n a = Wrap (m (n a)) unwrap :: Wrap m n a -> m (n a) unwrap (Wrap m) = m mbind :: (Monad m, Monad n, Functor m, Traversable n) => (a -> m (n b)) -> m (n a) -> m (n b) mbind = (join .) . fmap . (fmap join .) . T.mapM instance (Functor m, Traversable n, Monad m, Monad n) => Monad (Wrap m n) where return = Wrap . return . return m >>= f = Wrap (mbind (unwrap . f) (unwrap m)) instance Monad m => MonadTrans (Wrap m) where lift = Wrap . return From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Sat Dec 28 16:18:30 2013 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Sat, 28 Dec 2013 16:18:30 +0000 Subject: [Haskell-cafe] Name for the following combinators? In-Reply-To: <20131228161351.GO17875@weber> References: <79FD177A-56CF-4418-B351-D4C19D5DA51D@hanshoglund.se> <20131228155810.GN17875@weber> <20131228161351.GO17875@weber> Message-ID: <20131228161830.GP17875@weber> On Sat, Dec 28, 2013 at 04:13:52PM +0000, Tom Ellis wrote: > On Sat, Dec 28, 2013 at 03:58:10PM +0000, Tom Ellis wrote: > > On Sat, Dec 28, 2013 at 04:47:40PM +0100, Hans H?glund wrote: > > > Recently I have found myself using these two combinators a lot: http://lpaste.net/97643 > > > > FYI it looks a lot like these give rise to a monad transformer. > > Specifically, the following. Careful though: I haven't made any effort to > check this satisfies the monad or transformer laws. In fact, since is is 'n' that requires the 'Monad' constraint, I suspect you'll need to swap the order of the type arguments to get a monad transformer: data Wrap n m a = Wrap (m (n a)) Anyway, my main point remains: your first check should be whether what you have can be captured as a genuine monad. > import Control.Monad.Trans (MonadTrans, lift) > import Control.Monad (join) > import qualified Data.Traversable as T > import Data.Traversable (Traversable) > > data Wrap m n a = Wrap (m (n a)) > > unwrap :: Wrap m n a -> m (n a) > unwrap (Wrap m) = m > > mbind :: (Monad m, Monad n, Functor m, Traversable n) > => (a -> m (n b)) -> m (n a) -> m (n b) > mbind = (join .) . fmap . (fmap join .) . T.mapM > > instance (Functor m, Traversable n, Monad m, Monad n) => Monad (Wrap m n) > where > return = Wrap . return . return > m >>= f = Wrap (mbind (unwrap . f) (unwrap m)) > > instance Monad m => MonadTrans (Wrap m) where > lift = Wrap . return > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Sat Dec 28 16:21:39 2013 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Sat, 28 Dec 2013 16:21:39 +0000 Subject: [Haskell-cafe] Name for the following combinators? In-Reply-To: <20131228161830.GP17875@weber> References: <79FD177A-56CF-4418-B351-D4C19D5DA51D@hanshoglund.se> <20131228155810.GN17875@weber> <20131228161351.GO17875@weber> <20131228161830.GP17875@weber> Message-ID: <20131228162139.GQ17875@weber> On Sat, Dec 28, 2013 at 04:18:30PM +0000, Tom Ellis wrote: > On Sat, Dec 28, 2013 at 04:13:52PM +0000, Tom Ellis wrote: > > On Sat, Dec 28, 2013 at 03:58:10PM +0000, Tom Ellis wrote: > > > On Sat, Dec 28, 2013 at 04:47:40PM +0100, Hans H?glund wrote: > > > > Recently I have found myself using these two combinators a lot: http://lpaste.net/97643 > > > > > > FYI it looks a lot like these give rise to a monad transformer. > > > > Specifically, the following. Careful though: I haven't made any effort to > > check this satisfies the monad or transformer laws. > > In fact, since is is 'n' that requires the 'Monad' constraint, I suspect > you'll need to swap the order of the type arguments to get a monad > transformer: I keep typing too fast. I mean "it is 'n' that requires the *Traversable* constraint". From carter.schonwald at gmail.com Sat Dec 28 16:32:36 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sat, 28 Dec 2013 11:32:36 -0500 Subject: [Haskell-cafe] Segmentation fault/access violation when CPLUS_INCLUDE_PATH not set correctly In-Reply-To: References: Message-ID: File bug report with the wxhaskell maintainer. And ask them! :-) Cheers -carter On Saturday, December 28, 2013, Henk-Jan van Tuyl wrote: > > L.S., > > When I compile an application against an experimental version of > wxHaskell*, the application always ends with the message: > Segmentation fault/access violation in generated code > , unless I set the environment variable CPLUS_INCLUDE_PATH to > C:\Program Files\Haskell Platform\2013.2.0.0\mingw\lib\ > gcc\mingw32\4.5.2\include\c++\ > , which is the same value as used when compiling wxHaskell. > > If I copy the contents of C:\Programs\Haskell Platform\2013.2.0.0\ to some > other location and let CPLUS_INCLUDE_PATH point to the new location of > directory c++, the segmentation fault message reappears. > > Why is this and how can create an application that also works on another > computer? > > Regards, > Henk-Jan van Tuyl > > > * wxHaskell is a binding to the wxWidgets GUI library, which is written in > C++ > > > -- > Folding at home > What if you could share your unused computer power to help find a cure? In > just 5 minutes you can join the world's biggest networked computer and get > us closer sooner. Watch the video. > http://folding.stanford.edu/ > > > http://Van.Tuyl.eu/ > http://members.chello.nl/hjgtuyl/tourdemonad.html > Haskell programming > -- > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From hesselink at gmail.com Sat Dec 28 18:46:55 2013 From: hesselink at gmail.com (Erik Hesselink) Date: Sat, 28 Dec 2013 19:46:55 +0100 Subject: [Haskell-cafe] Name for the following combinators? In-Reply-To: <20131228161351.GO17875@weber> References: <79FD177A-56CF-4418-B351-D4C19D5DA51D@hanshoglund.se> <20131228155810.GN17875@weber> <20131228161351.GO17875@weber> Message-ID: On Sat, Dec 28, 2013 at 5:13 PM, Tom Ellis wrote: > data Wrap m n a = Wrap (m (n a)) This is Compose [0] from traversable. It doesn't have a Monad instance, though... Erik [0] http://hackage.haskell.org/package/transformers-0.3.0.0/docs/Data-Functor-Compose.html From hjgtuyl at chello.nl Sat Dec 28 22:39:37 2013 From: hjgtuyl at chello.nl (Henk-Jan van Tuyl) Date: Sat, 28 Dec 2013 23:39:37 +0100 Subject: [Haskell-cafe] Segmentation fault/access violation when CPLUS_INCLUDE_PATH not set correctly In-Reply-To: References: Message-ID: OK, done that; I asked myself, but I didn't know the answer :-). The problem is most likely not wxHaskell specific, but something related to compiling/linking. Regards, Henk-Jan van Tuyl On Sat, 28 Dec 2013 17:32:36 +0100, Carter Schonwald wrote: > File bug report with the wxhaskell maintainer. And ask them! :-) > > Cheers > -carter > > On Saturday, December 28, 2013, Henk-Jan van Tuyl wrote: > >> >> L.S., >> >> When I compile an application against an experimental version of >> wxHaskell*, the application always ends with the message: >> Segmentation fault/access violation in generated code >> , unless I set the environment variable CPLUS_INCLUDE_PATH to >> C:\Program Files\Haskell Platform\2013.2.0.0\mingw\lib\ >> gcc\mingw32\4.5.2\include\c++\ >> , which is the same value as used when compiling wxHaskell. >> >> If I copy the contents of C:\Programs\Haskell Platform\2013.2.0.0\ to >> some >> other location and let CPLUS_INCLUDE_PATH point to the new location of >> directory c++, the segmentation fault message reappears. >> >> Why is this and how can create an application that also works on another >> computer? >> >> Regards, >> Henk-Jan van Tuyl >> >> >> * wxHaskell is a binding to the wxWidgets GUI library, which is written >> in >> C++ -- Folding at home What if you could share your unused computer power to help find a cure? In just 5 minutes you can join the world's biggest networked computer and get us closer sooner. Watch the video. http://folding.stanford.edu/ http://Van.Tuyl.eu/ http://members.chello.nl/hjgtuyl/tourdemonad.html Haskell programming -- From carter.schonwald at gmail.com Sun Dec 29 01:45:26 2013 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sat, 28 Dec 2013 20:45:26 -0500 Subject: [Haskell-cafe] Segmentation fault/access violation when CPLUS_INCLUDE_PATH not set correctly In-Reply-To: References: Message-ID: Hehe, linking problems are a subtle critter indeed. I've actually a pretty nontrivial linking challenges in some of my own princes currently so I can sympathize. On Saturday, December 28, 2013, Henk-Jan van Tuyl wrote: > > OK, done that; I asked myself, but I didn't know the answer :-). The > problem is most likely not wxHaskell specific, but something related to > compiling/linking. > > Regards, > Henk-Jan van Tuyl > > > > On Sat, 28 Dec 2013 17:32:36 +0100, Carter Schonwald < > carter.schonwald at gmail.com> wrote: > > File bug report with the wxhaskell maintainer. And ask them! :-) >> >> Cheers >> -carter >> >> On Saturday, December 28, 2013, Henk-Jan van Tuyl wrote: >> >> >>> L.S., >>> >>> When I compile an application against an experimental version of >>> wxHaskell*, the application always ends with the message: >>> Segmentation fault/access violation in generated code >>> , unless I set the environment variable CPLUS_INCLUDE_PATH to >>> C:\Program Files\Haskell Platform\2013.2.0.0\mingw\lib\ >>> gcc\mingw32\4.5.2\include\c++\ >>> , which is the same value as used when compiling wxHaskell. >>> >>> If I copy the contents of C:\Programs\Haskell Platform\2013.2.0.0\ to >>> some >>> other location and let CPLUS_INCLUDE_PATH point to the new location of >>> directory c++, the segmentation fault message reappears. >>> >>> Why is this and how can create an application that also works on another >>> computer? >>> >>> Regards, >>> Henk-Jan van Tuyl >>> >>> >>> * wxHaskell is a binding to the wxWidgets GUI library, which is written >>> in >>> C++ >>> >> > -- > Folding at home > What if you could share your unused computer power to help find a cure? In > just 5 minutes you can join the world's biggest networked computer and get > us closer sooner. Watch the video. > http://folding.stanford.edu/ > > > http://Van.Tuyl.eu/ > http://members.chello.nl/hjgtuyl/tourdemonad.html > Haskell programming > -- > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From fileformat at gmail.com Sun Dec 29 01:59:22 2013 From: fileformat at gmail.com (Andrew M) Date: Sat, 28 Dec 2013 20:59:22 -0500 Subject: [Haskell-cafe] Fwd: ANN: website for Haskell regex testing In-Reply-To: References: Message-ID: Haskellers: I run a website for testing regular expressions and just added support for Haskell and wanted to see if you find it useful/what you think/if you have any suggestions. The site is RegexPlanet, the Haskell testing page is at: http://www.regexplanet.com/advanced/haskell/index.html It uses Text.Regex.TDFA flavor. You can see the source code on github: https://github.com/fileformat/regexplanet-haskell Disclaimer: I'm not a Haskell expert (actually, not even a newbie) and had someone else do the actual coding. Again, any feedback is appreciated. Thanks! Enjoy! Andrew -------------- next part -------------- An HTML attachment was scrubbed... URL: From capn.freako at gmail.com Sun Dec 29 02:24:51 2013 From: capn.freako at gmail.com (David Banas) Date: Sat, 28 Dec 2013 18:24:51 -0800 Subject: [Haskell-cafe] Question on nested State monads. Message-ID: <65633C5A-2A08-46DD-8375-4F5D8BBBDC6A@gmail.com> Hi all, If I want to use a second, nested State monad inside another State monad, must I thread the outer monad?s state through the processing of the inner one, even if the inner one falls out of scope before I return from the processing body of the outer one? Thanks, -db From lucas.dicioccio at gmail.com Sun Dec 29 08:25:58 2013 From: lucas.dicioccio at gmail.com (lucas di cioccio) Date: Sun, 29 Dec 2013 09:25:58 +0100 Subject: [Haskell-cafe] Question on nested State monads. In-Reply-To: <65633C5A-2A08-46DD-8375-4F5D8BBBDC6A@gmail.com> References: <65633C5A-2A08-46DD-8375-4F5D8BBBDC6A@gmail.com> Message-ID: Hi David, > If I want to use a second, nested State monad inside another State monad, > must I thread the outer monad?s state through the processing of the inner > one, even if the inner one falls out of scope before I return from the > processing body of the outer one? > In short: yes you can nest StateT and to access the "inner parts" you need to lift the get/put/modify functions. The Real-World Haskell book has an example for stacking monad transformers of a same TypeClass (cf. http://book.realworldhaskell.org/read/monad-transformers.html "When explicit lifting is necessary".) The first time, it's best to convince yourself by writing down the types of lifted put/get. Best, --Lucas -------------- next part -------------- An HTML attachment was scrubbed... URL: From trebla at vex.net Sun Dec 29 15:26:12 2013 From: trebla at vex.net (Albert Y. C. Lai) Date: Sun, 29 Dec 2013 10:26:12 -0500 Subject: [Haskell-cafe] Question on nested State monads. In-Reply-To: <65633C5A-2A08-46DD-8375-4F5D8BBBDC6A@gmail.com> References: <65633C5A-2A08-46DD-8375-4F5D8BBBDC6A@gmail.com> Message-ID: <52C03F14.3050709@vex.net> On 13-12-28 09:24 PM, David Banas wrote: > If I want to use a second, nested State monad inside another State monad, must I thread the outer monad?s state through the processing of the inner one, even if the inner one falls out of scope before I return from the processing body of the outer one? I do not know what the whole sentence "must I ... the outer one" is talking about. But why don't you go scientific and use concrete experiments to find out? Here is a starter: import Control.Monad.State main = print answer answer :: (Bool, Char) answer = evalState (evalStateT program True) 't' program :: StateT Bool (State Char) (Bool, Char) program = do bool <- get char <- lift get return (bool, char) From edwards.benj at gmail.com Sun Dec 29 16:33:31 2013 From: edwards.benj at gmail.com (Benjamin Edwards) Date: Sun, 29 Dec 2013 16:33:31 +0000 Subject: [Haskell-cafe] Question on nested State monads. References: <65633C5A-2A08-46DD-8375-4F5D8BBBDC6A@gmail.com> <52C03F14.3050709@vex.net> <1145051922360792912@gmail297201516> Message-ID: <5590797516588477795@gmail297201516> (Forwarding to the list, sorry Albert) On Sunday, 29 December 2013 08:32:06, Benjamin Edwards < edwards.benj at gmail.com> wrote: I would also recommend looking at use / zoom from the lens package. I find them indispensable for when you want to use a compound state. If you just have two parts you can write all your state calculations on the separate parts then user StateT m (a,b) r and zoom _1 / zoom _2 to access them in the same do block. -------------- next part -------------- An HTML attachment was scrubbed... URL: From adam at bergmark.nl Sun Dec 29 17:33:38 2013 From: adam at bergmark.nl (Adam Bergmark) Date: Sun, 29 Dec 2013 12:33:38 -0500 Subject: [Haskell-cafe] Top-down inserts in Persistent In-Reply-To: <52BC64C4.6080709@orlitzky.com> References: <52BC64C4.6080709@orlitzky.com> Message-ID: Hi Michael, The entity definitions in persistent is very close to the SQL schema, in a 1-to-many relation you must have the foreign key relation defined in the many table. You should preferably not insert a car before it's owner is inserted, that would give you a null reference. So if possible you should insert people first which will return their id and you can then do the insertion of cars safely. You can also construct keys manually, this is kind of an hack since you may construct invalid IDs. In a relational schema you can make the name of the person the primary key. There has been some work in adding arbitrarily typed primary keys to persistent, but I'm not sure if it has been released or is on master. Either way, using a person name as a primary key may be a bad idea because of collisions. Having some mismatch when moving things to relational storage is common. A lot of times I end up creating intermediary types that contain the data in a format that makes it easier to work with. But I don't mind this at all, Haskell makes it very safe to add proxy types and refactor them. You sometimes end up having to do more queries to the DB than seems necessary, but this is only a problem if it turns out to be a bottle neck. HTH, Adam On Thu, Dec 26, 2013 at 12:17 PM, Michael Orlitzky wrote: > I'm loading data from XML into a Haskell data type, and I'd like to use > Persistent to save it to a database. The examples from the Yesod book > have you manually define a FooId field and create the relationships > yourself from the bottom up. For example, "a person has many cars": > > blah blah [persistLowerCase| > Person > name String > Car > ownerId PersonId Eq > name String > |] > > This works well if you're responsible for creating every person/car > manually. But what if the data are given to you? If I were to parse > people from an XML file, the cars wouldn't have people_ids in them. > Instead I'd get, > > blah blah [persistLowerCase| > Person > name String > cars [Car] > Car > name String > |] > > As long as the cars list contains another Persistent type, it seems like > I should be able to insert a person and have it insert the cars, with > proper foreign keys, automatically. Doing it manually isn't > straight-forward because I can't add the "ownerId" field to my Car type > and still expect to parse it from the XML (which has no such field). > > Any ideas? I'm not married to Persistent yet; I just want to read in > some XML and save it to a database without having to specify the names > and types in three places (preferred place: in Haskell). I don't care > too much about the schema I get as long as it's relational. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From adam at bergmark.nl Sun Dec 29 17:39:30 2013 From: adam at bergmark.nl (Adam Bergmark) Date: Sun, 29 Dec 2013 12:39:30 -0500 Subject: [Haskell-cafe] (automatically) adding import statements in vim In-Reply-To: <20131226163820.GA29020@machine> References: <20131226163820.GA29020@machine> Message-ID: Hi, You may also be interested in Halberd[1][2] which uses hs-gen-iface[3] to do automatically insert missing imports by finding modules with the desired names. It does not have a vim plugin yet, but I imagine a simplistic one should be easy to make. Cheers, Adam [1] https://github.com/haskell-suite/Halberd [2] http://hackage.haskell.org/package/halberd [3] http://hackage.haskell.org/package/hs-gen-iface On Thu, Dec 26, 2013 at 11:38 AM, Daniel Trstenjak < daniel.trstenjak at gmail.com> wrote: > > Hi, > > I've just pushed the first versions of: > https://github.com/dan-t/hsimport > https://github.com/dan-t/vim-hsimport > > So there're certainly still some rough edges. > > > Greetings, > Daniel > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From hans at hanshoglund.se Sun Dec 29 17:40:09 2013 From: hans at hanshoglund.se (=?iso-8859-1?Q?Hans_H=F6glund?=) Date: Sun, 29 Dec 2013 18:40:09 +0100 Subject: [Haskell-cafe] Haskell-Cafe Digest, Vol 124, Issue 39 In-Reply-To: References: Message-ID: <131E9298-76EA-4AEE-B84B-E7DDCE597E69@hanshoglund.se> > On Sat, Dec 28, 2013 at 5:13 PM, Tom Ellis > wrote: > > data Wrap m n a = Wrap (m (n a)) > > This is Compose [0] from traversable. It doesn't have a Monad > instance, though... > > Erik > > [0] http://hackage.haskell.org/package/transformers-0.3.0.0/docs/Data-Functor-Compose.html According to [1], Wrap/Compose does indeed have a Monad instance terms of traverse (here called 'swap'). As far as I understand the paper includes a proof that all the Monad laws holds for such as composition, however there is no mention of transformers as the paper predates them. Personally I am not sure that the transformer composition is useful. Would it be as simple as adding this instance to Data.Functor.Compose: > instance (Functor m, Traversable n, Monad m, Monad n) => Monad (Compose m n) or can anyone spot a problem with this approach? Hans [1]: http://web.cecs.pdx.edu/~mpj/pubs/RR-1004.pdf, page 9 [2]: http://strictlypositive.org/IdiomLite.pdf -------------- next part -------------- An HTML attachment was scrubbed... URL: From hans at hanshoglund.se Sun Dec 29 17:50:15 2013 From: hans at hanshoglund.se (=?iso-8859-1?Q?Hans_H=F6glund?=) Date: Sun, 29 Dec 2013 18:50:15 +0100 Subject: [Haskell-cafe] Name for the following combinators? In-Reply-To: <131E9298-76EA-4AEE-B84B-E7DDCE597E69@hanshoglund.se> References: <131E9298-76EA-4AEE-B84B-E7DDCE597E69@hanshoglund.se> Message-ID: On 29 dec 2013, at 18:40, Hans H?glund wrote: > > On Sat, Dec 28, 2013 at 5:13 PM, Tom Ellis > > wrote: > > > data Wrap m n a = Wrap (m (n a)) > > > > This is Compose [0] from traversable. It doesn't have a Monad > > instance, though... > > > > Erik > > > > [0] http://hackage.haskell.org/package/transformers-0.3.0.0/docs/Data-Functor-Compose.html > According to [1], Wrap/Compose does indeed have a Monad instance terms of traverse (here called 'swap'). As far as I understand the paper includes a proof that all the Monad laws holds for such as composition, however there is no mention of transformers as the paper predates them. Personally I am not sure that the transformer composition is useful. > > Would it be as simple as adding this instance to Data.Functor.Compose: > > > instance (Functor m, Traversable n, Monad m, Monad n) => Monad (Compose m n) > > or can anyone spot a problem with this approach? > > Hans > > [1]: http://web.cecs.pdx.edu/~mpj/pubs/RR-1004.pdf, page 9 > [2]: http://strictlypositive.org/IdiomLite.pdf -------------- next part -------------- An HTML attachment was scrubbed... URL: From daniel.trstenjak at gmail.com Sun Dec 29 18:30:32 2013 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Sun, 29 Dec 2013 19:30:32 +0100 Subject: [Haskell-cafe] (automatically) adding import statements in vim In-Reply-To: References: <20131226163820.GA29020@machine> Message-ID: <20131229183031.GA24744@machine> Hi Adam, > You may also be interested in Halberd[1][2] which uses hs-gen-iface[3] to > do automatically insert missing imports by finding modules with the > desired names. It does not have a vim plugin yet, but I imagine a > simplistic one should be easy to make. If I'm getting this correctly, than Halberd uses some kind of static database, right? I think the nice approach of 'vim-hsimport' is, that by using 'hdevtools' in conjunction with a 'cabal sandbox', only the modules of the packages are considered, which your project depends on, and this information is dynamically "established" by 'hdevtools' reading the package database of the 'cabal sandbox'. But I have to confess, that hsimport/vim-hsimport are still in a quite early stage. Greetings, Daniel From iavor.diatchki at gmail.com Sun Dec 29 18:30:06 2013 From: iavor.diatchki at gmail.com (Iavor Diatchki) Date: Sun, 29 Dec 2013 10:30:06 -0800 Subject: [Haskell-cafe] Consistency issue with type level numeric literals In-Reply-To: <20131228085452.38189.qmail@www1.g3.pair.com> References: <20131228085452.38189.qmail@www1.g3.pair.com> Message-ID: Hi Oleg, yes, this is a bug, you are not supposed to define custom instances for the built-in operators. I just left it open until we hook in the solver. Happy holidays, -Iavor On Sat, Dec 28, 2013 at 12:54 AM, wrote: > > GHC 7.6.3 has quite convenient type-level numeric literals. We can use > numbers like 1 and 2 in types. However, using the type level numeral > has been quite a bit of a challenge, illustrated, for example, by > the following SO question. > > > http://stackoverflow.com/questions/20809998/type-level-nats-with-literals-and-an-injective-successor > > It seems the challenge has the reason: the type level numerals and > their operations provided in GHC.TypeLits have a consistency > issue. The following code demonstrates the issue: it constructs two > distinct values of the type Sing 2. Singletons aren't singletons. > > {-# LANGUAGE KindSignatures #-} > {-# LANGUAGE DataKinds #-} > {-# LANGUAGE ScopedTypeVariables #-} > {-# LANGUAGE TypeOperators #-} > {-# LANGUAGE TypeFamilies #-} > {-# LANGUAGE GADTs #-} > {-# LANGUAGE PolyKinds #-} > > module NotSing where > > import GHC.TypeLits > > -- GHC strangely enough lets us define instances for (+) > type instance 1 + 1 = 0 > type instance 0 + 1 = 2 > > -- A singular representative of 1::Nat > s1 :: Sing 1 > s1 = withSing id > > -- A singular representative of 2::Nat > s2 :: Sing 2 > s2 = withSing id > > is2 :: IsZero 0 > is2 = IsSucc s1 > > tran :: IsZero 0 -> Sing 2 > tran (IsSucc x) = case isZero x of > IsSucc y -> case isZero y of > IsZero -> x > > -- Another singular representative of 2::Nat > -- A singular representative of 2::Nat > s2' :: Sing 2 > s2' = tran is2 > > > {- > *NotSing> s2 > 2 > *NotSing> s2' > 1 > -} > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Sun Dec 29 19:06:26 2013 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Sun, 29 Dec 2013 19:06:26 +0000 Subject: [Haskell-cafe] Name for the following combinators? In-Reply-To: References: <131E9298-76EA-4AEE-B84B-E7DDCE597E69@hanshoglund.se> Message-ID: <20131229190626.GD30459@weber> On Sun, Dec 29, 2013 at 06:50:15PM +0100, Hans H?glund wrote: > According to [1], Wrap/Compose does indeed have a Monad instance terms > of traverse (here called 'swap'). As far as I understand the paper > includes a proof that all the Monad laws holds for such as composition > > [1]: http://web.cecs.pdx.edu/~mpj/pubs/RR-1004.pdf, page 9 Careful, they mention in Section 6.4 that "this construction only yields a composite monad if m has a certain commutativity property". This is the same reason that 'ListT m' is not a monad unless 'm' is commutative. What is your use case for these combinators? Perhaps you are using them exactly in a commutative case. Tom From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Sun Dec 29 20:09:09 2013 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Sun, 29 Dec 2013 20:09:09 +0000 Subject: [Haskell-cafe] Name for the following combinators? In-Reply-To: <20131229190626.GD30459@weber> References: <131E9298-76EA-4AEE-B84B-E7DDCE597E69@hanshoglund.se> <20131229190626.GD30459@weber> Message-ID: <20131229200909.GE30459@weber> On Sun, Dec 29, 2013 at 07:06:26PM +0000, Tom Ellis wrote: > On Sun, Dec 29, 2013 at 06:50:15PM +0100, Hans H?glund wrote: > > According to [1], Wrap/Compose does indeed have a Monad instance terms > > of traverse (here called 'swap'). As far as I understand the paper > > includes a proof that all the Monad laws holds for such as composition > > > > [1]: http://web.cecs.pdx.edu/~mpj/pubs/RR-1004.pdf, page 9 > > Careful, they mention in Section 6.4 that "this construction only yields a > composite monad if m has a certain commutativity property". > > This is the same reason that 'ListT m' is not a monad unless 'm' is > commutative. > > What is your use case for these combinators? Perhaps you are using them > exactly in a commutative case. Having thought about your original question some more, I think the best approach would be to use a free monad like this import Control.Monad.Free data F m n a = L (m a) | R (n a) type Wrap m n = Free (F m n) so then 'Wrap m n' genuinely is a monad, and you can write a function condense :: (Monad m, Monad n, Traversable n, ...) => Wrap m n a -> m (n a) to collect up the results at the end. Then we need not bother to check whether anything satisfies any laws. 'condense' is similar to your original 'mjoin'. Tom (PS This is overkill for the current discussion, but: since you're starting with 'm' and 'n' monads anyway, using a free monad transformer (Control.Monad.Trans.Free) would probably reduce the boilerplate needed in 'condense'.) From qdunkan at gmail.com Mon Dec 30 02:53:58 2013 From: qdunkan at gmail.com (Evan Laforge) Date: Sun, 29 Dec 2013 18:53:58 -0800 Subject: [Haskell-cafe] (automatically) adding import statements in vim In-Reply-To: References: Message-ID: I wrote fix-imports, which is on hackage. Works for me, but assumes you use qualified imports. On Wed, Dec 25, 2013 at 3:45 AM, cdep.illabout at gmail.com wrote: > Are there any tools or vim-plugins that will automatically add > import statements? > > For instance, I have the following code: > > ... > import Data.Maybe (fromJust) > import Text.ParserCombinators.Parsec (ParseError) > import Text.Printf (printf) > ... > > parseMyString :: String -> Either ParseError String > parseMyString stringToParse = parse myParser "(unknown)" stringToParse > > > Here's what I want to have happen. I put my cursor over "parse" and > press some keystroke. It automatically adds the parse function to the > list of import statements from the Text.ParserCombinators.Parsec > module (hopefully sorted alphabetically). So the import statements > end up looking like this: > > ... > import Data.Maybe (fromJust) > import Text.ParserCombinators.Parsec (ParseError, parse) > import Text.Printf (printf) > ... > > The haskellmode vim plugin > (https://github.com/lukerandall/haskellmode-vim) has functionality > similar to this, but it can only add new import lines. It can't add > functions/types to existing import lines. > > The best it can do is something like this: > > ... > import Data.Maybe (fromJust) > import Text.ParserCombinators.Parsec (ParseError) > import Text.Printf (printf) > import Text.ParserCombinators.Parsec (parse) > ... > > This is alright, but I have to go back and edit it by hand to make it > look like the above. > > Are there any tools or vim-plugins that can do this automatically? > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From simonpj at microsoft.com Mon Dec 30 14:22:25 2013 From: simonpj at microsoft.com (Simon Peyton-Jones) Date: Mon, 30 Dec 2013 14:22:25 +0000 Subject: [Haskell-cafe] Consistency issue with type level numeric literals In-Reply-To: References: <20131228085452.38189.qmail@www1.g3.pair.com> Message-ID: <59543203684B2244980D7E4057D5FBC1486FDB16@DB3EX14MBXC306.europe.corp.microsoft.com> Iavor Shouldn?t (+) be a closed type family (now that we have such things)? Then the user couldn?t give new instances. Simon From: Haskell-Cafe [mailto:haskell-cafe-bounces at haskell.org] On Behalf Of Iavor Diatchki Sent: 29 December 2013 18:30 To: oleg at okmij.org Cc: Haskell Cafe Subject: Re: [Haskell-cafe] Consistency issue with type level numeric literals Hi Oleg, yes, this is a bug, you are not supposed to define custom instances for the built-in operators. I just left it open until we hook in the solver. Happy holidays, -Iavor On Sat, Dec 28, 2013 at 12:54 AM, > wrote: GHC 7.6.3 has quite convenient type-level numeric literals. We can use numbers like 1 and 2 in types. However, using the type level numeral has been quite a bit of a challenge, illustrated, for example, by the following SO question. http://stackoverflow.com/questions/20809998/type-level-nats-with-literals-and-an-injective-successor It seems the challenge has the reason: the type level numerals and their operations provided in GHC.TypeLits have a consistency issue. The following code demonstrates the issue: it constructs two distinct values of the type Sing 2. Singletons aren't singletons. {-# LANGUAGE KindSignatures #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE PolyKinds #-} module NotSing where import GHC.TypeLits -- GHC strangely enough lets us define instances for (+) type instance 1 + 1 = 0 type instance 0 + 1 = 2 -- A singular representative of 1::Nat s1 :: Sing 1 s1 = withSing id -- A singular representative of 2::Nat s2 :: Sing 2 s2 = withSing id is2 :: IsZero 0 is2 = IsSucc s1 tran :: IsZero 0 -> Sing 2 tran (IsSucc x) = case isZero x of IsSucc y -> case isZero y of IsZero -> x -- Another singular representative of 2::Nat -- A singular representative of 2::Nat s2' :: Sing 2 s2' = tran is2 {- *NotSing> s2 2 *NotSing> s2' 1 -} _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe at haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- An HTML attachment was scrubbed... URL: From haskell-cafe at maartenfaddegon.nl Mon Dec 30 17:08:08 2013 From: haskell-cafe at maartenfaddegon.nl (Maarten Faddegon) Date: Mon, 30 Dec 2013 17:08:08 +0000 Subject: [Haskell-cafe] parametrized data types and Template Haskell In-Reply-To: References: <52BC14A3.2080505@maartenfaddegon.nl> Message-ID: <52C1A878.1080005@maartenfaddegon.nl> Dear Cafe, Thanks to the kind help of Adam and Richard I now can generate instances for parametrized data types with Template Haskell. However, I still struggle adding class constraints to the type variables. I try to follow the derive_show example of Ian Lynagh but it seems some interfaces have changed since he wrote "Template Haskell: A Report From The Field". I generate MyClass constraints for a set of type variables with the following code: > genCxt :: [TyVarBndr] -> Q Cxt > genCxt tvs = return [classp $ map (\v -> (tvname v)) tvs] > > classp :: [Type] -> Pred > classp = ClassP (mkName "TH_playground.MyClass") > > tvname :: TyVarBndr -> Type > tvname (PlainTV name ) = ConT name > tvname (KindedTV name _) = ConT name To be able to generate MyClass instances with: > genInstance :: Q Type -> Q [Dec] > genInstance qt > = do { t <- qt > ; n <- case t of > (ForallT tvs _ t') -> [t| MyClass $(return t') |] > _ -> [t| MyClass $qt |] > ; m <- genMethod qt > ; c <- case t of > (ForallT tvs _ t') -> genCxt tvs > _ -> return [] > ; return [InstanceD c n m] > } Up to here, everything type checks and I can build the module where I defined it. In a different module I try to generate an instance for MyData a: > data MyData a = MyCon a > $(genInstance [t| forall a.MyData a |]) This however does not seems to go down well with the compiler. || Illegal type constructor or class name: `a' || When splicing a TH declaration: || instance TH_playground.MyClass a_0 => TH_playground.MyClass (Main.MyData a_0) || where myMethod (Main.MyCon x_1) = "todo" This error message confuses me because it seems to complain about the type variable a in the generate instance, but in the generated instance this variable is renamed to a_0. Also, when I copy the generated code from the error message the ghc is completely happy. Without the class constraints the generated instance type checks and compiles as well: > genCxt _ = return [] But I would like to apply myMethod on the fields in parametrized data types, which is not correct without the class constraints. Did I find a bug in ghc's Template Haskell implementation or am I doing something silly? Thanks, Maarten From vogt.adam at gmail.com Mon Dec 30 18:55:53 2013 From: vogt.adam at gmail.com (adam vogt) Date: Mon, 30 Dec 2013 13:55:53 -0500 Subject: [Haskell-cafe] parametrized data types and Template Haskell In-Reply-To: <52C1A878.1080005@maartenfaddegon.nl> References: <52BC14A3.2080505@maartenfaddegon.nl> <52C1A878.1080005@maartenfaddegon.nl> Message-ID: On Mon, Dec 30, 2013 at 12:08 PM, Maarten Faddegon wrote: > Did I find a bug in ghc's Template Haskell implementation or am I doing > something silly? Hi Maarten, If you look at the definition of Name, you will see several NameFlavours. In your case your `a' has a NameU (unique). I think if you had the type variable names tagged with a NameS (simple?), ghc would accept your code. Somewhat related is a case where ghc accepts NameU as a NameS when no other variables in scope could conflict: x1 = [d| x = 1 |] is short for: x1 = return [ValD (VarP x_1627406778) (NormalB (LitE (IntegerL 1))) []] but when you splice x1, "x" is bound, instead of the unique, difficult-to-reference variable x_1627406778. Regards, Adam Vogt From michael at orlitzky.com Mon Dec 30 19:41:40 2013 From: michael at orlitzky.com (Michael Orlitzky) Date: Mon, 30 Dec 2013 14:41:40 -0500 Subject: [Haskell-cafe] Top-down inserts in Persistent In-Reply-To: References: <52BC64C4.6080709@orlitzky.com> Message-ID: <52C1CC74.3080208@orlitzky.com> On 12/29/2013 12:33 PM, Adam Bergmark wrote: > Hi Michael, > > The entity definitions in persistent is very close to the SQL schema, in > a 1-to-many relation you must have the foreign key relation defined in > the many table. > > You should preferably not insert a car before it's owner is inserted, > that would give you a null reference. So if possible you should insert > people first which will return their id and you can then do the > insertion of cars safely. You can also construct keys manually, this is > kind of an hack since you may construct invalid IDs. > > ... > > Having some mismatch when moving things to relational storage is common. > A lot of times I end up creating intermediary types that contain the > data in a format that makes it easier to work with. But I don't mind > this at all, Haskell makes it very safe to add proxy types and refactor > them. You sometimes end up having to do more queries to the DB than > seems necessary, but this is only a problem if it turns out to be a > bottle neck. > I have 650 XML documents -- all with different schemas -- to import. Assuming some of them are outdated or unused, I might wind up doing 100 before I declare victory. Still an offensive amount of XML =) To parse the XML I already need to create 100 Haskell data types; that part is unavoidable. But since XML is XML, all of those data types are trees. Michael Snoyman suggested, forM_ people $ \(PersonXML name cars) -> do personId <- insert $ Person name forM_ cars $ \car -> insert_ $ Car personId car which works for one tree, Person { [Car] }. But it doesn't work for Person { [Car], [Shoes] }, or anything else. The essence of the problem is that I don't want to write 100 functions like the forM above that all do the same thing but to trees with slightly different shapes. They should all follow the same pattern: insert the big thing, then insert the little things with automatic foreign keys to the big thing. From tanielsen at gmail.com Mon Dec 30 21:49:53 2013 From: tanielsen at gmail.com (Tom Nielsen) Date: Mon, 30 Dec 2013 21:49:53 +0000 Subject: [Haskell-cafe] [ANN] Laborantin: experimentation framework In-Reply-To: References: Message-ID: Hi Lucas, In connection with your work on Laborantin, you may be interested in our papers: Braincurry: A domain-specific language for integrative neuroscience http://www2.le.ac.uk/departments/biology/research/neuroscience/matheson-neurobiology/publications/braincurry A formal mathematical framework for physiological observations, experiments and analyses. http://rsif.royalsocietypublishing.org/content/9/70/1040.long I found it difficult to excite experimental biologists about the benefit of adopting experiment description languages. I am now concentrating on a functional language for statistical data analysis - see https://bayeshive.com Tom On 23 December 2013 09:27, lucas di cioccio wrote: > Dear all, > > I am happy to announce Laborantin. Laborantin is a Haskell library and DSL > for > running and analyzing controlled experiments. > > Repository: https://github.com/lucasdicioccio/laborantin-hs > Hackage page: http://hackage.haskell.org/package/laborantin-hs > > Laborantin's opinion is that running proper experiments is a non-trivial > and > often overlooked problem. Therefore, we should provide good tools to assist > experimenters. The hope is that, with Laborantin, experimenters will spend > more > time on their core problem while racing through the menial tasks of editing > scripts because one data point is missing in a plot. At the same time, > Laborantin is also an effort within the broad open-science movement. > Indeed, > Laborantin's DSL separates boilerplate from the actual experiment > implementation. Thus, Laborantin could reduce the friction for code and > data-reuse. > > One family of experiments that fit well Laborantin are benchmarks with > tedious > setup and teardown procedures (for instance starting, configuring, and > stopping > remote machines). Analyses that require measurements from a variety of data > points in a multi-dimensional parameter space also fall in the scope of > Laborantin. > > When using Laborantin, the experimenter: > > * Can express experimental scenarios using a readable and familiar DSL. > This feature, albeit subjective, was confirmed by non-Haskeller > colleagues. > * Saves time on boilerplate such as writing command-line parsers or > encoding dependencies between experiments and analysis results in a > Makefile. > * Benefits from auto-documentation and result introspection features when > one > comes back to a project, possibly months or weeks later. > * Harnesses the power of Haskell type-system to catch common errors at > compile time > > If you had to read one story to understand the pain points that Laborantin > tries to address, it should be Section 5 of "Strategies for Sound Internet > Measurement" (V. Paxson, IMC 2004). > > I'd be glad to take question and comments (or, even better, code reviews > and > pull requests). > > Kind regards, > --Lucas DiCioccio (@lucasdicioccio on GitHub/Twitter) > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From targen at gmail.com Mon Dec 30 21:57:33 2013 From: targen at gmail.com (=?UTF-8?Q?Manuel_G=C3=B3mez?=) Date: Mon, 30 Dec 2013 17:27:33 -0430 Subject: [Haskell-cafe] Top-down inserts in Persistent In-Reply-To: <52C1CC74.3080208@orlitzky.com> References: <52BC64C4.6080709@orlitzky.com> <52C1CC74.3080208@orlitzky.com> Message-ID: On Mon, Dec 30, 2013 at 3:11 PM, Michael Orlitzky wrote: > On 12/29/2013 12:33 PM, Adam Bergmark wrote: > I have 650 XML documents -- all with different schemas -- to import. > Assuming some of them are outdated or unused, I might wind up doing 100 > before I declare victory. Still an offensive amount of XML =) > > To parse the XML I already need to create 100 Haskell data types; that > part is unavoidable. But since XML is XML, all of those data types are > trees. Are you sure a relational schema with the structure of each type of XML document is the best approach for your dataset? It sounds like you could benefit from a less structured approach, since your data doesn?t sound very regular. > Michael Snoyman suggested, > > forM_ people $ \(PersonXML name cars) -> do > personId <- insert $ Person name > forM_ cars $ \car -> insert_ $ Car personId car > > which works for one tree, Person { [Car] }. But it doesn't work for > Person { [Car], [Shoes] }, or anything else. The essence of the problem > is that I don't want to write 100 functions like the forM above that all > do the same thing but to trees with slightly different shapes. They > should all follow the same pattern: insert the big thing, then insert > the little things with automatic foreign keys to the big thing. Boris Lykah?s [Groundhog] library sounds like a good fit for your situation: {-# LANGUAGE FlexibleInstances, GADTs, QuasiQuotes, TemplateHaskell, TypeFamilies #-} import Control.Monad.IO.Class (liftIO) import Database.Groundhog.Core (insert, select) import Database.Groundhog.Generic.Sql.Functions (like) import Database.Groundhog.Generic (defaultMigrationLogger, runDbConn, runMigration) import Database.Groundhog.Postgresql (withPostgresqlConn) import Database.Groundhog.TH (defaultCodegenConfig, groundhog, migrationFunction, mkPersist) data Car = Car { carName :: String } deriving Show data Driver = Driver { driverName :: String , driverCars :: [Car] } deriving Show penelope, anthills :: Driver penelope = Driver "Penelope Pitstop" [Car "The Compact Pussycat"] anthills = Driver "The Ant Hill Mob" [Car "The Bulletproof Bomb", Car "Chugga-Boom"] mkPersist defaultCodegenConfig { migrationFunction = Just "migrateAll" } [groundhog| - entity: Car - entity: Driver |] main :: IO () main = withPostgresqlConn "host=/tmp" $ runDbConn $ do runMigration defaultMigrationLogger migrateAll mapM_ insert [penelope, anthills] drivers <- select $ DriverNameField `like` "The%" liftIO $ mapM_ print drivers This code will create a few tables: one for the `Driver` constructor, another for the `Car` constructor, and a couple of tables to keep track of what?s in the list in the `Driver` constructor. It will even create triggers to help maintain the list-related tables clean, although I venture it?d be uncomfortable manipulating this specific generated schema by hand. Groundhog is very flexible with the sort of data types and schemas it can work with. That example was getting a bit long so I didn?t include anything related to constraints, but specifying uniqueness constraints and the like is relatively painless. Boris wrote a very nice [tutorial] for Groundhog in FP Complete?s School of Haskell, and the Hackage documentation for the [`groundhog-th`] package describes the `groundhog` quasiquoter pretty well. [Groundhog]: [tutorial]: [`groundhog-th`]: From michael at orlitzky.com Mon Dec 30 22:30:09 2013 From: michael at orlitzky.com (Michael Orlitzky) Date: Mon, 30 Dec 2013 17:30:09 -0500 Subject: [Haskell-cafe] Top-down inserts in Persistent In-Reply-To: References: <52BC64C4.6080709@orlitzky.com> <52C1CC74.3080208@orlitzky.com> Message-ID: <52C1F3F1.1010207@orlitzky.com> On 12/30/2013 04:57 PM, Manuel G?mez wrote: > On Mon, Dec 30, 2013 at 3:11 PM, Michael Orlitzky wrote: >> On 12/29/2013 12:33 PM, Adam Bergmark wrote: >> I have 650 XML documents -- all with different schemas -- to import. >> Assuming some of them are outdated or unused, I might wind up doing 100 >> before I declare victory. Still an offensive amount of XML =) >> >> To parse the XML I already need to create 100 Haskell data types; that >> part is unavoidable. But since XML is XML, all of those data types are >> trees. > > Are you sure a relational schema with the structure of each type of > XML document is the best approach for your dataset? It sounds like > you could benefit from a less structured approach, since your data > doesn?t sound very regular. There's a complicated and uninteresting answer to this, so for now let's just say the job is to get it into SQL somehow. I did consider other options, but this is the path of least resistance, resistant as it may be. > > Boris Lykah?s [Groundhog] library sounds like a good fit for your situation: > I have been vacillating between Persistent and Groundhog in my prototype. For now I'm using Groundhog, but I haven't written any code yet that would rule out Persistent. > > > This code will create a few tables: one for the `Driver` constructor, > another for the `Car` constructor, and a couple of tables to keep > track of what?s in the list in the `Driver` constructor. It will even > create triggers to help maintain the list-related tables clean, > although I venture it?d be uncomfortable manipulating this specific > generated schema by hand. Yes! It is tempting isn't it? I emailed Boris about this and unfortunately the list handling is unsupported (undocumented) and is likely to disappear in its current form. Otherwise I had considered running a manual migration after the Groundhog ones to create the necessary views. > Groundhog is very flexible with the sort of data types and schemas it > can work with. That example was getting a bit long so I didn?t > include anything related to constraints, but specifying uniqueness > constraints and the like is relatively painless. > > Boris wrote a very nice [tutorial] for Groundhog in FP Complete?s > School of Haskell, and the Hackage documentation for the > [`groundhog-th`] package describes the `groundhog` quasiquoter pretty > well. Thank you for the suggestion; I do like the way Groundhog leaves my types alone. If I can come up with a way to do a generic tree insert, it will be necessary to leave out e.g. the "cars" column from the "people" table (even though I still need it in the Haskell type). At the moment I am banging my head against the Data.Data docs to try to get that working. All I have so far is some writing on the wall in blood about how Hackage 3 should automatically reject any function with more than two type variables and no examples. From capn.freako at gmail.com Mon Dec 30 22:57:00 2013 From: capn.freako at gmail.com (David Banas) Date: Mon, 30 Dec 2013 14:57:00 -0800 Subject: [Haskell-cafe] ANN: treeviz-0.0.4 - a tool for visualizing Divide&Conquer computational breakdown. Message-ID: I just posted v0.0.4 of treeviz, a Haskell package for visualizing how various divide & conquer algorithms break down computations. The specific example provided is the classic fast Fourier transform (FFT). http://hackage.haskell.org/package/treeviz-0.0.4 https://github.com/capn-freako/treeviz Happy holidays, -db -------------- next part -------------- An HTML attachment was scrubbed... URL: From conrad at metadecks.org Mon Dec 30 23:03:13 2013 From: conrad at metadecks.org (Conrad Parker) Date: Tue, 31 Dec 2013 10:03:13 +1100 Subject: [Haskell-cafe] ANN: treeviz-0.0.4 - a tool for visualizing Divide&Conquer computational breakdown. In-Reply-To: References: Message-ID: On 31 December 2013 09:57, David Banas wrote: > I just posted v0.0.4 of *treeviz*, a Haskell package for visualizing how > various divide & conquer algorithms break down computations. The specific > example provided is the classic fast Fourier transform (FFT). > > http://hackage.haskell.org/package/treeviz-0.0.4 > https://github.com/capn-freako/treeviz > > sounds good, do you have some example output? Conrad. -------------- next part -------------- An HTML attachment was scrubbed... URL: From acfoltzer at gmail.com Tue Dec 31 02:58:48 2013 From: acfoltzer at gmail.com (Adam Foltzer) Date: Mon, 30 Dec 2013 18:58:48 -0800 Subject: [Haskell-cafe] December 31 deadline for Haskell.org donations Message-ID: Dear Haskellers, HaskellWiki, Hackage, Hoogle, and all the other haskell.org sites we depend on are hosted with funds donated by you, the Haskell community. As many of us are in tax jurisdictions where December 31st is a deadline for charitable giving, I?d like to remind you that donations to support these activities are tax-deductible. You can donate online right now at https://co.clickandpledge.com/advanced/default.aspx?wid=69561. Thank you to Jason Dagit and the rest of last year?s Haskell.org Committee for making these donations possible by establishing a partnership with Software in the Public Interest, and thank you to all those who have already donated both money and time to advance our infrastructure and community. It has been a momentous year for Haskell.org: Hackage 2 was launched on a community server, and the HaskellWiki is now available via HTTPS. Let?s keep making progress in 2014! Thank you and best wishes for a happy new year, Adam Foltzer -------------- next part -------------- An HTML attachment was scrubbed... URL: From coreyoconnor at gmail.com Tue Dec 31 04:58:46 2013 From: coreyoconnor at gmail.com (Corey O'Connor) Date: Mon, 30 Dec 2013 20:58:46 -0800 Subject: [Haskell-cafe] [ANN] Laborantin: experimentation framework In-Reply-To: References: Message-ID: This looks really cool! Cheers, Corey -Corey O'Connor coreyoconnor at gmail.com http://corebotllc.com/ On Mon, Dec 23, 2013 at 1:27 AM, lucas di cioccio wrote: > Dear all, > > I am happy to announce Laborantin. Laborantin is a Haskell library and DSL > for > running and analyzing controlled experiments. > > Repository: https://github.com/lucasdicioccio/laborantin-hs > Hackage page: http://hackage.haskell.org/package/laborantin-hs > > Laborantin's opinion is that running proper experiments is a non-trivial > and > often overlooked problem. Therefore, we should provide good tools to assist > experimenters. The hope is that, with Laborantin, experimenters will spend > more > time on their core problem while racing through the menial tasks of editing > scripts because one data point is missing in a plot. At the same time, > Laborantin is also an effort within the broad open-science movement. > Indeed, > Laborantin's DSL separates boilerplate from the actual experiment > implementation. Thus, Laborantin could reduce the friction for code and > data-reuse. > > One family of experiments that fit well Laborantin are benchmarks with > tedious > setup and teardown procedures (for instance starting, configuring, and > stopping > remote machines). Analyses that require measurements from a variety of data > points in a multi-dimensional parameter space also fall in the scope of > Laborantin. > > When using Laborantin, the experimenter: > > * Can express experimental scenarios using a readable and familiar DSL. > This feature, albeit subjective, was confirmed by non-Haskeller > colleagues. > * Saves time on boilerplate such as writing command-line parsers or > encoding dependencies between experiments and analysis results in a > Makefile. > * Benefits from auto-documentation and result introspection features when > one > comes back to a project, possibly months or weeks later. > * Harnesses the power of Haskell type-system to catch common errors at > compile time > > If you had to read one story to understand the pain points that Laborantin > tries to address, it should be Section 5 of "Strategies for Sound Internet > Measurement" (V. Paxson, IMC 2004). > > I'd be glad to take question and comments (or, even better, code reviews > and > pull requests). > > Kind regards, > --Lucas DiCioccio (@lucasdicioccio on GitHub/Twitter) > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From vogt.adam at gmail.com Tue Dec 31 06:43:07 2013 From: vogt.adam at gmail.com (adam vogt) Date: Tue, 31 Dec 2013 01:43:07 -0500 Subject: [Haskell-cafe] [ANN] Laborantin: experimentation framework In-Reply-To: References: Message-ID: Hello Lucas, Am I correct to say that laborantin only does full factorial experiments? Perhaps there is a straightforward way for users to specify which model parameters should be confounded in a fractional factorial design. Another extension would be to move towards sequential designs, where the trials to run depend on the results so far. Then more time is spent on the "interesting" regions of the parameter space. I think getVar/param could be re-worked to give errors at compile time. Now you get a runtime error if you typo a parameter or get the type wrong. Another mistake is to include parameters in the experiment that do not have any effect on the `run` action, unless those parameters are there for doing replicates. Those might be addressed by doing something like: a <- parameter "destination" $ do ... run $ print =<< param a Where the types are something like: param :: Data.Tagged.Tagged a Text -> M a values :: [T a] -> M (Tagged a Text) str :: Text -> T Text num :: Double -> T Double with M being whatever state monad you currently use, and param does the same thing it always has, except now it knows which type you put in the values list, and it cannot be called with any string. The third requirement might be met by requiring -fwarn-unused-matches. An alternative strategy is to change your type Step, into an algebraic data type with a function to convert it into what it is currently. Before the experiment happens, you can have a function go through that data to make sure it will succeed with it's getVar/param. This is called a deep embedding: . Regards, Adam On Mon, Dec 23, 2013 at 4:27 AM, lucas di cioccio wrote: > Dear all, > > I am happy to announce Laborantin. Laborantin is a Haskell library and DSL > for > running and analyzing controlled experiments. > > Repository: https://github.com/lucasdicioccio/laborantin-hs > Hackage page: http://hackage.haskell.org/package/laborantin-hs > > Laborantin's opinion is that running proper experiments is a non-trivial and > often overlooked problem. Therefore, we should provide good tools to assist > experimenters. The hope is that, with Laborantin, experimenters will spend > more > time on their core problem while racing through the menial tasks of editing > scripts because one data point is missing in a plot. At the same time, > Laborantin is also an effort within the broad open-science movement. Indeed, > Laborantin's DSL separates boilerplate from the actual experiment > implementation. Thus, Laborantin could reduce the friction for code and > data-reuse. > > One family of experiments that fit well Laborantin are benchmarks with > tedious > setup and teardown procedures (for instance starting, configuring, and > stopping > remote machines). Analyses that require measurements from a variety of data > points in a multi-dimensional parameter space also fall in the scope of > Laborantin. > > When using Laborantin, the experimenter: > > * Can express experimental scenarios using a readable and familiar DSL. > This feature, albeit subjective, was confirmed by non-Haskeller > colleagues. > * Saves time on boilerplate such as writing command-line parsers or > encoding dependencies between experiments and analysis results in a > Makefile. > * Benefits from auto-documentation and result introspection features when > one > comes back to a project, possibly months or weeks later. > * Harnesses the power of Haskell type-system to catch common errors at > compile time > > If you had to read one story to understand the pain points that Laborantin > tries to address, it should be Section 5 of "Strategies for Sound Internet > Measurement" (V. Paxson, IMC 2004). > > I'd be glad to take question and comments (or, even better, code reviews and > pull requests). > > Kind regards, > --Lucas DiCioccio (@lucasdicioccio on GitHub/Twitter) > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From haskell-cafe at maartenfaddegon.nl Tue Dec 31 13:20:14 2013 From: haskell-cafe at maartenfaddegon.nl (Maarten Faddegon) Date: Tue, 31 Dec 2013 13:20:14 +0000 Subject: [Haskell-cafe] parametrized data types and Template Haskell In-Reply-To: <52C1A878.1080005@maartenfaddegon.nl> References: <52BC14A3.2080505@maartenfaddegon.nl> <52C1A878.1080005@maartenfaddegon.nl> Message-ID: <52C2C48E.4040508@maartenfaddegon.nl> Thanks for thinking with me Adam. It turned out the error message "Illegal type constructor or class name" was spot on, because I wrote: > tvname :: TyVarBndr -> Type > tvname (PlainTV name ) = ConT name > tvname (KindedTV name _) = ConT name But should have written: > tvname :: TyVarBndr -> Type > tvname (PlainTV name ) = VarT name > tvname (KindedTV name _) = VarT name Happy new year to all of you! Maarten From lucas.dicioccio at gmail.com Tue Dec 31 18:13:29 2013 From: lucas.dicioccio at gmail.com (lucas di cioccio) Date: Tue, 31 Dec 2013 19:13:29 +0100 Subject: [Haskell-cafe] [ANN] Laborantin: experimentation framework In-Reply-To: References: Message-ID: Hi Tom, Thanks for the pointers. It is interesting to see that Braincurry and Laborantin have similar designs although we come from very different application domains. You've picked paths that I was not sure to explore (e.g., have experiment parameters be a parameterizable datatype rather than a value in a pre-defined datatype). I didn't think about enabling algebraic composition of "experiments". It looks like I can incorporate this idea in Laborantin too as a way to "combine" setup/run/teardown hooks. I'll definitely have a second look at Braincurry but first I'll have to read the 2nd paper. One thing I really would like to support is a way to "inject experiments" into another system and run experiments "live". For instance, A/B testing web pages in a Warp application. BayesHive looks very nice! congrats. Enjoy a nice year 2014 and best wishes, --Lucas 2013/12/30 Tom Nielsen > Hi Lucas, > > In connection with your work on Laborantin, you may be interested in our > papers: > > Braincurry: A domain-specific language for integrative neuroscience > > http://www2.le.ac.uk/departments/biology/research/neuroscience/matheson-neurobiology/publications/braincurry > > A formal mathematical framework for physiological observations, > experiments and analyses. > http://rsif.royalsocietypublishing.org/content/9/70/1040.long > > I found it difficult to excite experimental biologists about the benefit > of adopting experiment description languages. I am now concentrating on a > functional language for statistical data analysis - see > https://bayeshive.com > > Tom > > > On 23 December 2013 09:27, lucas di cioccio wrote: > >> Dear all, >> >> I am happy to announce Laborantin. Laborantin is a Haskell library and >> DSL for >> running and analyzing controlled experiments. >> >> Repository: https://github.com/lucasdicioccio/laborantin-hs >> Hackage page: http://hackage.haskell.org/package/laborantin-hs >> >> Laborantin's opinion is that running proper experiments is a non-trivial >> and >> often overlooked problem. Therefore, we should provide good tools to >> assist >> experimenters. The hope is that, with Laborantin, experimenters will >> spend more >> time on their core problem while racing through the menial tasks of >> editing >> scripts because one data point is missing in a plot. At the same time, >> Laborantin is also an effort within the broad open-science movement. >> Indeed, >> Laborantin's DSL separates boilerplate from the actual experiment >> implementation. Thus, Laborantin could reduce the friction for code and >> data-reuse. >> >> One family of experiments that fit well Laborantin are benchmarks with >> tedious >> setup and teardown procedures (for instance starting, configuring, and >> stopping >> remote machines). Analyses that require measurements from a variety of >> data >> points in a multi-dimensional parameter space also fall in the scope of >> Laborantin. >> >> When using Laborantin, the experimenter: >> >> * Can express experimental scenarios using a readable and familiar DSL. >> This feature, albeit subjective, was confirmed by non-Haskeller >> colleagues. >> * Saves time on boilerplate such as writing command-line parsers or >> encoding dependencies between experiments and analysis results in a >> Makefile. >> * Benefits from auto-documentation and result introspection features when >> one >> comes back to a project, possibly months or weeks later. >> * Harnesses the power of Haskell type-system to catch common errors at >> compile time >> >> If you had to read one story to understand the pain points that Laborantin >> tries to address, it should be Section 5 of "Strategies for Sound Internet >> Measurement" (V. Paxson, IMC 2004). >> >> I'd be glad to take question and comments (or, even better, code reviews >> and >> pull requests). >> >> Kind regards, >> --Lucas DiCioccio (@lucasdicioccio on GitHub/Twitter) >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From lucas.dicioccio at gmail.com Tue Dec 31 18:13:44 2013 From: lucas.dicioccio at gmail.com (lucas di cioccio) Date: Tue, 31 Dec 2013 19:13:44 +0100 Subject: [Haskell-cafe] [ANN] Laborantin: experimentation framework In-Reply-To: References: Message-ID: Hi Adam, thanks for your inputs. 2013/12/31 adam vogt > Hello Lucas, > > Am I correct to say that laborantin only does full factorial > experiments? Perhaps there is a straightforward way for users to > specify which model parameters should be confounded in a fractional > factorial design. Another extension would be to move towards > sequential designs, where the trials to run depend on the results so > far. Then more time is spent on the "interesting" regions of the > parameter space. > Actually, the parameters specified in the DSL are "indicative" values for a full-factorial default. At this point, a command-line handler is responsible for exploring the parameter space and executing scenarios. This command-line handler has a way to specify fractional factorial designs by evaluating a query like: "(@sc.param 'foo' > @sc.param 'bar') and @sc.param 'baz' in [1,2,3,'toto']" . This small query language was my first attempt at "expression parsing and evaluation" and the code might be ugly, but it works and fits most of my current needs. Bonus: with this design, the algorithm to "explore" the satisfiable parameter space is easy to express. One direction to enrich this small query language would be to express that a parameter takes a continuous value in a range or should fullfill a boolean test function. Then we could use techniques such as rapidly exploring random trees to explore "exotic feasability regions". Another direction to improve the query language is to require ScenarioDescriptions to have a sort of "cost/fitness function" so that we can later build a parameter-space explorer that performs an optimization. We could even extend the query language to bind a parameter to a value which optimize another experiment. > I think getVar/param could be re-worked to give errors at compile > time. Now you get a runtime error if you typo a parameter or get the > type wrong. Another mistake is to include parameters in the experiment > that do not have any effect on the `run` action, unless those > parameters are there for doing replicates. > > Those might be addressed by doing something like: > > a <- parameter "destination" $ do ... > run $ print =<< param a > > Where the types are something like: > > param :: Data.Tagged.Tagged a Text -> M a > values :: [T a] -> M (Tagged a Text) > str :: Text -> T Text > num :: Double -> T Double > > with M being whatever state monad you currently use, and param does > the same thing it always has, except now it knows which type you put > in the values list, and it cannot be called with any string. The third > requirement might be met by requiring -fwarn-unused-matches. > That's one thing I am parted about. From my experience, it is sometimes handy to branch on whether a value is a number or a string (e.g., to say things like 1, 2, 3, or "all"). Somehow, tagged values do not prevent this either. Similarly, I don't know whether I should let users specify any type for their ParameterDescription at the cost of writing serializers/deserializers boilerplate (although we could provide some default useful types as it is the case now). An alternative strategy is to change your type Step, into an algebraic > data type with a function to convert it into what it is currently. > Before the experiment happens, you can have a function go through that > data to make sure it will succeed with it's getVar/param. This is > called a deep embedding: > . > That can be an idea, I didn't go that far yet, but I'll keep an eye on it. Best wishes for this happy new year, --Lucas Regards, > Adam > > On Mon, Dec 23, 2013 at 4:27 AM, lucas di cioccio > wrote: > > Dear all, > > > > I am happy to announce Laborantin. Laborantin is a Haskell library and > DSL > > for > > running and analyzing controlled experiments. > > > > Repository: https://github.com/lucasdicioccio/laborantin-hs > > Hackage page: http://hackage.haskell.org/package/laborantin-hs > > > > Laborantin's opinion is that running proper experiments is a non-trivial > and > > often overlooked problem. Therefore, we should provide good tools to > assist > > experimenters. The hope is that, with Laborantin, experimenters will > spend > > more > > time on their core problem while racing through the menial tasks of > editing > > scripts because one data point is missing in a plot. At the same time, > > Laborantin is also an effort within the broad open-science movement. > Indeed, > > Laborantin's DSL separates boilerplate from the actual experiment > > implementation. Thus, Laborantin could reduce the friction for code and > > data-reuse. > > > > One family of experiments that fit well Laborantin are benchmarks with > > tedious > > setup and teardown procedures (for instance starting, configuring, and > > stopping > > remote machines). Analyses that require measurements from a variety of > data > > points in a multi-dimensional parameter space also fall in the scope of > > Laborantin. > > > > When using Laborantin, the experimenter: > > > > * Can express experimental scenarios using a readable and familiar DSL. > > This feature, albeit subjective, was confirmed by non-Haskeller > > colleagues. > > * Saves time on boilerplate such as writing command-line parsers or > > encoding dependencies between experiments and analysis results in a > > Makefile. > > * Benefits from auto-documentation and result introspection features when > > one > > comes back to a project, possibly months or weeks later. > > * Harnesses the power of Haskell type-system to catch common errors at > > compile time > > > > If you had to read one story to understand the pain points that > Laborantin > > tries to address, it should be Section 5 of "Strategies for Sound > Internet > > Measurement" (V. Paxson, IMC 2004). > > > > I'd be glad to take question and comments (or, even better, code reviews > and > > pull requests). > > > > Kind regards, > > --Lucas DiCioccio (@lucasdicioccio on GitHub/Twitter) > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: