Re: [Haskell-cafe] ghci identifier listing question
On Mon, Jul 27, 2009 at 6:37 PM, Daniel van den Eijkeld...@gmx.net wrote: Is it possible, to reach the (shadowed) values in any way? I'm not sure about this, but . . . Another question: Is it possible to show only those identifiers that are defined during the interactive session? I only can list all identifiers which start with a given prefix, but I would like to know if GHCi can show me all identifiers defined in a given module or in the current session (by pressing Tab or alike). Yes, this will list the current bindings: :show bindings Jeff Wheeler ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
RE: [Haskell-cafe] Proposal: TypeDirectedNameResolution
Cale Gibbard wrote: There was a great related idea on #haskell the other day: Make explicit qualification unnecessary whenever there is a *unique* choice of module qualifications from those imported which would make the expression typecheck. Ambiguities would still need to be qualified, but I feel that this would eliminate 99% of all ugly qualified names from code. It would be especially good in the case of infix operators, which as far as I know, nobody actually enjoys qualifying explicitly. [...] What do people think of this idea? Personally, it really annoys me whenever I'm forced to give explicit module qualifications, and I think this would really help. It would also subsume the DisambiguateRecordFields extension rather handily. I think this idea would severely damage compositionality. One example of this is that it would make it substantially less likely that subexpressions could be abstracted into a separate declaration without giving a type signature to fix the type of the new declaration. Ganesh === Please access the attached hyperlink for an important electronic communications disclaimer: http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html === ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] A Question of Restriction
Would you be so kind as to elaborate? Sure. I'll just sketch how to deal the example in your e-mail. If you want to use recursive data types (like Lists or Trees), you'll need to use the Expr data type from the paper. Instead of defining: data Foo = One | Two | Three | Four Define the following data types: data One = One data Two = Two data Three = Three data Four = Four You can define the following data type to assemble the pieces: infixr 6 :+: data (a :+: b) = Inl a | Inr b So, for example you could define: type Odd = One :+: Three type Even = Two :+: Four type Foo = One :+: Two :+: Three :+: Four To define functions modularly, it's a good idea to use Haskell's clasess to do some of the boring work for you. Here's another example: class ToNumber a where toNumber :: a - Int instance ToNumber One where toNumber One = 1 (and similar instances for Two, Three, and Four) The key instance, however, is the following: instance (ToNumber a, ToNumber b) = ToNumber (a :+: b) where toNumber (Inl a) = toNumber a toNumber (Inr b) = toNumber b This instance explains how to build instances for Odd, Even, and Foo from the instances for One, Two, Three, and Four. An example ghci sessions might look like: *Main let x = Inl One :: Odd *Main toNumber x 1 *Main let y = Inr (Inr (Inl Three) :: Foo *Main toNumber y 3 Of course, writing all these injections (Inr (Inr (Inl ...))) gets dull quite quickly. The () class in the paper explains how to avoid this. I hope this gives you a better idea of how you might go about solving your problem. All the best, Wouter ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] A Question of Restriction
Brian Troutwine wrote: Hello Wouter. I've had a go at the paper linked and perused other references found with Google. Unfortunately, such sophisticated use of the type system is pretty far out of my normal problem domain and I can't see how to apply the techniques presented to my motivating example. Would you be so kind as to elaborate? data Foo = One | Two | Three | Four data Odd = One | Three data Even = Two | Four == {- data Fix f = Fix { unFix :: f (Fix f) } data (:+:) f g x = Inl (f x) | Inr (g x) ... -} data One r = One data Two r = Two data Three r = Three data Four r = Four instance Functor One where fmap _ One = One instance Functor Two where fmap _ Two = Two instance Functor Three where fmap _ Three = Three instance Functor Four where fmap _ Four = Four type Foo = Fix (One :+: Two :+: Three :+: Four) type Odd = Fix (One :+: Three) type Even = Fix (Two :+: Four) If your original types were actually recursive, then the unfixed functors should use their r parameter in place of the recursive call, e.g. data List a = Nil | Cons a (List a) == data List a r = Nil | Cons a r Also, if you know a certain collection of component types must always occur together, then you can flatten parts of the coproduct and use normal unions as well. E.g. data Odd r = One | Three data Two r = Two data Four r = Four type Foo= Fix (Odd :+: Two :+: Four) -- Live well, ~wren ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Proposal: TypeDirectedNameResolution
Sittampalam, Ganesh wrote: ... it would make it substantially less likely that subexpressions could be abstracted into a separate declaration without giving a type signature to fix the type of the new declaration. OK, then give a type signature to fix the type of (really, to document) the new declaration. I can't understand why declarative programmers insist they should be able to omit (type) declarations ... Best, J.W. signature.asc Description: OpenPGP digital signature ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
RE: [Haskell-cafe] Proposal: TypeDirectedNameResolution
(To be clear, this about Cale's proposal, not simonpj's one) Johannes Waldmann wrote: Sittampalam, Ganesh wrote: ... it would make it substantially less likely that subexpressions could be abstracted into a separate declaration without giving a type signature to fix the type of the new declaration. OK, then give a type signature to fix the type of (really, to document) the new declaration. I can't understand why declarative programmers insist they should be able to omit (type) declarations ... I find type inference a valuable feature. Generally at some point I annotate top-level declarations, but while developing it's nice not to have to worry about it. Having to annotate every single declaration would be painful. Ganesh === Please access the attached hyperlink for an important electronic communications disclaimer: http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html === ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: Proposal: TypeDirectedNameResolution
Cale Gibbard wrote: There was a great related idea on #haskell the other day: Make explicit qualification unnecessary whenever there is a *unique* choice of module qualifications from those imported which would make the expression typecheck. Ambiguities would still need to be qualified, but I feel that this would eliminate 99% of all ugly qualified names from code. It would be especially good in the case of infix operators, which as far as I know, nobody actually enjoys qualifying explicitly. [...] What do people think of this idea? Personally, it really annoys me whenever I'm forced to give explicit module qualifications, and I think this would really help. It would also subsume the DisambiguateRecordFields extension rather handily. While I do agree that qualified names are annoying at times, I think that type directed name disambiguation is a Pandora's box. Furthermore, we already have a mechanism for type based disambiguation, namely good old type classes. For instance, the qualifications required when importing Data.Map are actually a sign that we are lacking proper container type classes à la Edison. There are other possible language extension that may make qualification easier, Pascal's with statement comes to mind. http://freepascal.decenturl.com/with-statement-pascal In Haskell, this would work something like this: histogram xs = with Data.Map foldl' f empty xs where f m x = case lookup m x where Just k - insertWith x (+1) m Nothing - insert x 1 m In the scope of with , ambiguous qualifications default to Data.Map . Regards, apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] lifting restrictions on defining instances
Tillmann Rendel wrote: wren ng thornton wrote: [1] In System F the capital-lambda binder is used for the term-level abstraction of passing type representations. So for example we have, id :: forall a. a - a id = /\a. \(x::a). x Thus, the forall keyword is serving as the type-level abstraction. Perhaps this is suboptimal syntax, but it is the standard. We could, of course, have both a term-level /\ and a type-level /\ where the latter is the type of the former (since the namespaces are separate) though that's also dubious. Capital-pi is the canonical type-level abstraction, though that evokes the idea of dependent types which are much more complex. What do you mean by type-level abstraction here? I mean an abstraction, as in a lambda-abstraction (aka a lambda-expression), at the type level. In a language with type functions and polymorphism, we need three different lambda binders: (1) abstraction over terms in terms (to construct functions) (2) abstraction over types in terms (to construct polymorphic values) (3) abstraction over types in types (to construct type functions) I think only (2) should be written as upper-case lambdas, while (1) and (3) should both be written as lower-case lambdas. Since (1) and (3) belong to different syntactic categories, they can not be confused, and we can reuse the lower-case lambda at the type-level. I'm sure that's fine. I was merely pointing out precedent. The syntax of #3 could also be conflated with the syntax of #2, for the same reason: they are in different syntactic categories. I pointed this out because the capital-lambda was the syntax others in the thread were using. Also, it makes sense to me to have #2 and #3 (abstraction over types in _) paired together, rather than #1 and #3 (abstraction over X in X). Pairing #2/#3 also gives term/type symmetry as we have for other built-ins like [], (,), and - (though the symmetry is imperfect for -). Furthermore, we need three function types / kinds to describe the three lambdas one level higher: (4) the type of functions (5) the type of polymorphic values (6) the kind of type functions In ghc, we already have forall for (5), and arrows for (4) and (6). I would say that (3) is the type-level abstraction, not (5). I'm not sure I follow what you mean. Given the relationship between /\ and forall as demonstrated in the definition of id above, I don't see such a difference between #3 and #5. That is, given the need for #2 the need for #5 follows; from there #3 follows by extending the wording of #5. (Though #6 is desirable from a theoretical perspective I'm not sure whether the language needs to be able to express it. There's much else at the kind-layer we cannot express.) In other words, just because forall is the type of /\ doesn't mean that that's all it is. All of these are effectively identical: -- Just a type-level lambda five :: (forall a. a) Int five = 5 -- Making the term-level match the type exactly five :: (forall a. a) Int five = (/\a. 5::a) @Int -- Hiding a CAF behind a constant type -- (somewhat like how numeric constants really work) five :: Int five = (/\a. 5::a) @Int -- Boring five :: Int five = 5 -- Live well, ~wren ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] powerSet = filterM (const [True, False]) ... is this obfuscated haskell?
The M is the list, i.e. nondeterminism monad. For each element in the list, there is one return value where it appears (True), and one where it does not (False). This discussion made Curry [1] programmers realise the beauty of non- determinism and lead to interesting reformulations of common list functions [2]. Here are some of them translated to Haskell: inits = takeWhileM (const [True,False]) tails = dropWhileM (const [True,False]) perms = sortByM (const [True,False]) Only that Hoogle does not know any of these monadic helper functions. Cheers, Sebastian [1]: http://www.curry-language.org/ [2]: unfortunately not yet in the mailing list archive (http://www.informatik.uni-kiel.de/~mh/curry/listarchive/ Thread title: beautiful non-determinism) -- Underestimating the novelty of the future is a time-honored tradition. (D.G.) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
RE: [Haskell-cafe] powerSet = filterM (const [True, False]) ... is this obfuscated haskell?
perms = sortByM (const [True,False]) This doesn't seem right, since the comparison function is inconsistent and moreover the results will depend on the sorting algorithm chosen. Ganesh === Please access the attached hyperlink for an important electronic communications disclaimer: http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html === ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] powerSet = filterM (const [True, False]) ... is this obfuscated haskell?
On Tue, Jul 28, 2009 at 10:58:53AM +0200, Sebastian Fischer wrote: tails = dropWhileM (const [True,False]) Actually this should be tails = dropWhileM (const [False, True]) -- Felipe. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] ghci identifier listing question
Ah, thats great! And it shows the values (or part of if), too. Very nice. Thank you, Daniel Jeff Wheeler schrieb: On Mon, Jul 27, 2009 at 6:37 PM, Daniel van den Eijkeld...@gmx.net wrote: Is it possible, to reach the (shadowed) values in any way? I'm not sure about this, but . . . Another question: Is it possible to show only those identifiers that are defined during the interactive session? I only can list all identifiers which start with a given prefix, but I would like to know if GHCi can show me all identifiers defined in a given module or in the current session (by pressing Tab or alike). Yes, this will list the current bindings: :show bindings Jeff Wheeler ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Proposal: TypeDirectedNameResolution
There are other possible language extension that may make qualification easier, Pascal's with statement comes to mind. http://freepascal.decenturl.com/with-statement-pascal In Haskell, this would work something like this: histogram xs = with Data.Map foldl' f empty xs where f m x = case lookup m x where Just k - insertWith x (+1) m I like both that and TDNR. It would be cool that at least one of them gets accepted in Haskell prime. David. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] lifting restrictions on defining instances
wren ng thornton wrote: Thus, the forall keyword is serving as the type-level abstraction. What do you mean by type-level abstraction here? I mean an abstraction, as in a lambda-abstraction (aka a lambda-expression), at the type level. [...] I'm not sure I follow what you mean. I mean that the forall keyword is *not* serving as the type-level abstraction. There is a difference between abstraction (as in lambda abstraction) and the type of abstractions (as in function types). In pure type systems, we have two different binders for these different features: - lower-case lambda for abstraction (on all levels) - upper-case Pi for the type of abstractions (on all levels) I find it highly confusing to say that forall denotes type-level abstraction, because it does not denote abstraction at all. It rather denotes the type of an abstraction, namely in Haskell, the type of abstracting over types in terms. In other words, the following is not legal Haskell, and not how forall works in any polymorphic lambda calculus: -- Just a type-level lambda five :: (forall a. a) Int five = 5 -- Making the term-level match the type exactly five :: (forall a. a) Int five = (/\a. 5::a) @Int Note that (forall a . a) has kind *, so (forall a . a) Int is not even well-kinded, as ghci correctly determines: ghci -XRankNTypes :k (forall a. a) (forall a. a) :: * :k (forall a . a) Int interactive:1:0: Kind error: `forall a. a' is applied to too many type arguments About syntax: (1) abstraction over terms in terms (to construct functions) (2) abstraction over types in terms (to construct polymorphic values) (3) abstraction over types in types (to construct type functions) The syntax of #3 could also be conflated with the syntax of #2, for the same reason: they are in different syntactic categories. I pointed this out because the capital-lambda was the syntax others in the thread were using. Also, it makes sense to me to have #2 and #3 (abstraction over types in _) paired together, rather than #1 and #3 (abstraction over X in X). Pairing #2/#3 also gives term/type symmetry as we have for other built-ins like [], (,), and - (though the symmetry is imperfect for -). I agree that this makes as much sense as my view. However, I still argue that the existing type/kind symmetry for - should be reflected in a term/type symmetry for \. We already have: id x = x type Id x = x :t id id :: a - a :k Id Id :: * - * And I think anonymous type-level abstraction should look like this: id' = \x - x type Id' = \x - x :t id' id' :: a - a :k Id' Id' :: * - * I would use the upper-case lambda for kind-polymorphism on the type level. type Id'' = /\k - \t :: k - t :k Id'' :: forall k . k - k :k Id'' [*] :: * - * :k Id'' [*] Int = Int :k Id'' [forall k . k - k] Id'' [*] Int = Int Tillmann ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Need feedback on my Haskell code
Hi Everyone, I managed to write up the line drawing function using the following links - http://www.cs.helsinki.fi/group/goa/mallinnus/lines/bresenh.html http://rosettacode.org/wiki/Bresenham%27s_line_algorithm#Haskell line :: Point - Point - [Point] line (xa,ya) (xb,yb) = line' (x1,y1) (x2,y2) deltax deltay ystep isSteep 0 where isSteep = abs (yb - ya) abs (xb - xa) (xa',ya',xb',yb') = if isSteep then (ya,xa,yb,xb) else (xa,ya,xb,yb) (x1,y1,x2,y2) = if xa' xb' then (xb',yb',xa',ya') else (xa',ya',xb',yb') deltax = x2 - x1 deltay = abs (y2 - y1) ystep = if y1 y2 then 1 else -1 line' :: Point - Point - Integer - Integer - Integer - Bool - Integer - [Point] line' (x1,y1) (x2,y2) deltax deltay ystep isSteep error = if x1 == x2 then if isSteep then [(y1,x1)] else [(x1,y1)] else if isSteep then [(y1,x1)] ++ line' (newX,newY) (x2,y2) deltax deltay ystep isSteep newError else [(x1,y1)] ++ line' (newX,newY) (x2,y2) deltax deltay ystep isSteep newError where newX = x1 + 1 tempError = error + deltay (newY, newError) = if (2*tempError) = deltax then (y1+ystep,tempError-deltax) else (y1,tempError) Can someone please provide feedback on this? In terms of, how do I get more Haskell'ism into it. Regards, Kashyap ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Need feedback on my Haskell code
Hi Kashyap, My first suggestion would be to run HLint over the code (http://community.haskell.org/~ndm/hlint) - that will spot a few easy simplifications. Thanks Neil On Tue, Jul 28, 2009 at 2:04 PM, CK Kashyapck_kash...@yahoo.com wrote: Hi Everyone, I managed to write up the line drawing function using the following links - http://www.cs.helsinki.fi/group/goa/mallinnus/lines/bresenh.html http://rosettacode.org/wiki/Bresenham%27s_line_algorithm#Haskell line :: Point - Point - [Point] line (xa,ya) (xb,yb) = line' (x1,y1) (x2,y2) deltax deltay ystep isSteep 0 where isSteep = abs (yb - ya) abs (xb - xa) (xa',ya',xb',yb') = if isSteep then (ya,xa,yb,xb) else (xa,ya,xb,yb) (x1,y1,x2,y2) = if xa' xb' then (xb',yb',xa',ya') else (xa',ya',xb',yb') deltax = x2 - x1 deltay = abs (y2 - y1) ystep = if y1 y2 then 1 else -1 line' :: Point - Point - Integer - Integer - Integer - Bool - Integer - [Point] line' (x1,y1) (x2,y2) deltax deltay ystep isSteep error = if x1 == x2 then if isSteep then [(y1,x1)] else [(x1,y1)] else if isSteep then [(y1,x1)] ++ line' (newX,newY) (x2,y2) deltax deltay ystep isSteep newError else [(x1,y1)] ++ line' (newX,newY) (x2,y2) deltax deltay ystep isSteep newError where newX = x1 + 1 tempError = error + deltay (newY, newError) = if (2*tempError) = deltax then (y1+ystep,tempError-deltax) else (y1,tempError) Can someone please provide feedback on this? In terms of, how do I get more Haskell'ism into it. Regards, Kashyap ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Need feedback on my Haskell code
Thanks Neil, That helped. Now the code looks better - I still feel a little bad about the way I repeat calls to line' though - I was thinking of using a partially applied function with (newX,newY) as the last parameter - but that'll make the code less readable. line :: Point - Point - [Point] line (xa,ya) (xb,yb) = line' (x1,y1) (x2,y2) deltax deltay ystep isSteep 0 where isSteep = abs (yb - ya) abs (xb - xa) (xa',ya',xb',yb') = if isSteep then (ya,xa,yb,xb) else (xa,ya,xb,yb) (x1,y1,x2,y2) = if xa' xb' then (xb',yb',xa',ya') else (xa',ya',xb',yb') deltax = x2 - x1 deltay = abs (y2 - y1) ystep = if y1 y2 then 1 else -1 line' (x1, y1) (x2, y2) deltax deltay ystep isSteep error | x1 == x2 = if isSteep then [(y1, x1)] else [(x1, y1)] | isSteep = (y1, x1) : line' (newX, newY) (x2, y2) deltax deltay ystep isSteep newError | otherwise = (x1, y1) : line' (newX, newY) (x2, y2) deltax deltay ystep isSteep newError where newX = x1 + 1 tempError = error + deltay (newY, newError) = if (2 * tempError) = deltax then (y1 + ystep, tempError - deltax) else (y1, tempError) Regards, Kashyap From: Neil Mitchell ndmitch...@gmail.com To: CK Kashyap ck_kash...@yahoo.com Cc: haskell-cafe@haskell.org Sent: Tuesday, July 28, 2009 6:44:58 PM Subject: Re: [Haskell-cafe] Need feedback on my Haskell code Hi Kashyap, My first suggestion would be to run HLint over the code (http://community.haskell.org/~ndm/hlint) - that will spot a few easy simplifications. Thanks Neil On Tue, Jul 28, 2009 at 2:04 PM, CK Kashyapck_kash...@yahoo.com wrote: Hi Everyone, I managed to write up the line drawing function using the following links - http://www.cs.helsinki.fi/group/goa/mallinnus/lines/bresenh.html http://rosettacode.org/wiki/Bresenham%27s_line_algorithm#Haskell line :: Point - Point - [Point] line (xa,ya) (xb,yb) = line' (x1,y1) (x2,y2) deltax deltay ystep isSteep 0 where isSteep = abs (yb - ya) abs (xb - xa) (xa',ya',xb',yb') = if isSteep then (ya,xa,yb,xb) else (xa,ya,xb,yb) (x1,y1,x2,y2) = if xa' xb' then (xb',yb',xa',ya') else (xa',ya',xb',yb') deltax = x2 - x1 deltay = abs (y2 - y1) ystep = if y1 y2 then 1 else -1 line' :: Point - Point - Integer - Integer - Integer - Bool - Integer - [Point] line' (x1,y1) (x2,y2) deltax deltay ystep isSteep error = if x1 == x2 then if isSteep then [(y1,x1)] else [(x1,y1)] else if isSteep then [(y1,x1)] ++ line' (newX,newY) (x2,y2) deltax deltay ystep isSteep newError else [(x1,y1)] ++ line' (newX,newY) (x2,y2) deltax deltay ystep isSteep newError where newX = x1 + 1 tempError = error + deltay (newY, newError) = if (2*tempError) = deltax then (y1+ystep,tempError-deltax) else (y1,tempError) Can someone please provide feedback on this? In terms of, how do I get more Haskell'ism into it. Regards, Kashyap ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Need feedback on my Haskell code
On Tue, Jul 28, 2009 at 3:04 PM, CK Kashyapck_kash...@yahoo.com wrote: Hi Everyone, I managed to write up the line drawing function using the following links - http://www.cs.helsinki.fi/group/goa/mallinnus/lines/bresenh.html http://rosettacode.org/wiki/Bresenham%27s_line_algorithm#Haskell I tried to simplify your function a little bit : line :: Point - Point - [Point] line pa@(xa,ya) pb@(xb,yb) = map maySwitch . unfoldr go $ (x1,y1,0) where steep = abs (yb - ya) abs (xb - xa) maySwitch = if steep then (\(x,y) - (y,x)) else id [(x1,y1),(x2,y2)] = sort [maySwitch pa, maySwitch pb] deltax = x2 - x1 deltay = abs (y2 - y1) ystep = if y1 y2 then 1 else -1 go (xTemp, yTemp, error) | xTemp x2 = Nothing | otherwise = Just ((xTemp, yTemp), (xTemp + 1, newY, newError)) where tempError = error + deltay (newY, newError) = if (2*tempError) = deltax then (yTemp+ystep,tempError-deltax) else (yTemp,tempError) I think it will be a bit better, tell me what you think ? -- Jedaï ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] powerSet = filterM (const [True, False]) ... is this obfuscated haskell?
On Jul 28, 2009, at 11:06 AM, Sittampalam, Ganesh wrote: perms = sortByM (const [True,False]) This doesn't seem right, since the comparison function is inconsistent I was also wary about this point, e.g. QuickSort depends on transitivity. and moreover the results will depend on the sorting algorithm chosen. Is it only that different sorting algorithms enumerate all permutations in different orders or is there a sorting algorithm, such that the above definition does not enumerate all permutations? Here is some shirt-sleeved reasoning: Every sorting algorithm :: [Int] - [Int] that actually sorts can describe every possible permutation (if there is a permutation that cannot be realised by the sorting algorithm then there is an input list that cannot be sorted). Hence, if this sorting algorithm is `sortBy p` for some predicate p then there are possible decisions of p to produce every possible permutation. If p makes *every* decision non- deterministically then certainly the specific decisions necessary for any specific permutation are also made. Hence, perm as defined above can yield a list that contains all permutations of the input (at least once) regardless of the sorting algorithm. Where is the hitch? Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
RE: [Haskell-cafe] powerSet = filterM (const [True, False]) ... is this obfuscated haskell?
Sebastian Fischer wrote: On Jul 28, 2009, at 11:06 AM, Sittampalam, Ganesh wrote: perms = sortByM (const [True,False]) and moreover the results will depend on the sorting algorithm chosen. Is it only that different sorting algorithms enumerate all permutations in different orders or is there a sorting algorithm, such that the above definition does not enumerate all permutations? [..] Hence, perm as defined above can yield a list that contains all permutations of the input (at least once) regardless of the sorting algorithm. Where is the hitch? The at least once bit - unless your non-determinism is based on set rather than bag semantics, it's wrong to duplicate results. Ganesh === Please access the attached hyperlink for an important electronic communications disclaimer: http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html === ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Need feedback on my Haskell code
Small tips: - Use swap and avoid those if's. - [a] ++ b is the same as a : b. - Factor out the first point that is always there. - Factor out line' arguments that don't change with the recursion. Untested: swap :: Bool - (a,a) - (a,a) swap False = id swap True = \(x,y) - (y,x) line :: Point - Point - [Point] line (xa,ya) (xb,yb) = line' p1 p2 deltax deltay ystep isSteep 0 where isSteep = abs (yb - ya) abs (xb - xa) (p1,p2) = let a = swap isSteep (xa,ya) b = swap isSteep (xb,yb) in swap (fst a fst b) (a, b) ((x1,y1),(x2,y2)) = (p1,p2) deltax = x2 - x1 deltay = abs (y2 - y1) ystep = if y1 y2 then 1 else -1 line' :: Point - Point - Integer - Integer - Integer - Bool - Integer - [Point] line' p1 (x2,_) deltax deltay ystep isSteep = go p1 where go (x1,y1) error = swap isSteep (x1,y1) : rest where rest = if x1 == x2 then [] else go (newX,newY) newError newX = x1 + 1 tempError = error + deltay (newY, newError) = if (2*tempError) = deltax then (y1+ystep,tempError-deltax) else (y1,tempError) But now that we got here, you may inline line' and avoid swap isSteep. I've also changed some names to more pleasant one (for me, at least :). Untested as well: swap :: Bool - (a,a) - (a,a) swap False = id swap True = \(x,y) - (y,x) line :: Point - Point - [Point] line (xa,ya) (xb,yb) = go (x1,y1) 0 where ((x1,y1),(x2,y2)) = let a = adjust (xa,ya) b = adjust (xb,yb) in swap (fst a fst b) (a, b) adjust = swap $ abs (yb - ya) abs (xb - xa) deltax = x2 - x1 deltay = abs (y2 - y1) ystep = if y1 y2 then 1 else -1 go (x,y) error = let error' = error + deltay (yd,ed) = if 2*tempError = deltax then (ystep,deltax) else (0,0) in adjust (x,y) : if x == x2 then [] else go (x+1,y+yd) (error' - ed) HTH, -- Felipe. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Adding a field to a data record
Dear Group, It seems to me this should be easy, but I can't quite figure out how to do it without a lot of typing. Here is the question: Suppose you have a data type like: Data Foo = Foo { a :: Int, b :: Int, ... many other fields ... y :: Int } deriving (Eq, Read, Show, Typeable, Data) Now I would like to add a field z :: Int to the end of Foo. If I have a ton of data out on disk, which I wrote with, say writeFile a.data (show foo) -- where foo is a [Foo] say 1000 long, I would like to get a new a.data file which has a new z::Int field. So far the only way I can think of is to make a new Data Foo1, which includes the z::Int, read in a.data as a list of Foo, write a function like: fooTofoo1 :: Foo - Foo1 fooTofoo1 xx = Foo1 {a = a xx, ... y = y xx, z = 1} then write the file back out, and perhaps use emacs to query-replace all the Foo1's back to Foo's, add the z::Int field back into Foo, and read it back. Please tell me there is a better way. Thanks in advance. Best wishes, Henry Laxen PS: I have read syb1, and syb2 a couple of times now, but so far haven't been able to connect it with this kind of problem. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Adding a field to a data record
and perhaps use emacs to query-replace all the Foo1's back to Foo's At least this bit can be avoided easily enough, by using module qualification during the conversion process. module Original (Foo(..)) where data Foo = Foo { ... y :: Int } deriving ... module New (Foo(..)) where data Foo = Foo { ... y, z :: Int } deriving ... module Convert where import Original as Old import New as New newFoo :: Old.Foo - New.Foo newFoo old{..} = New.Foo { a=a, b=b, ... z=1 } Finally rename module New. Regards, Malcolm ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: cabal: : openFile: does not exist (No such file or directory)
did you verify parsec-2.1.0.1 exports Text.Parsec.Language ? This might be a parsec 2 versus parsec 3 issue ghc-pkg describe parsec-2.1.0.1 should tell you the answer to that. 2009/7/27 Job Vranish jvran...@gmail.com: I tried updating to ghc-6.10.4 and have exactly the same error. Also ghc doesn't seem to be able to find any of the haskell platform packages, even though it ghc-pkg finds them just fine. For example (trimmed for brevity): ghc-pkg list /usr/local/lib/ghc-6.10.4/./package.conf: Cabal-1.6.0.3, ... parsec-2.1.0.1, pretty-1.0.1.0, process-1.0.1.1, random-1.0.0.1, ... ghci -v readModel.hs GHCi, version 6.10.4: http://www.haskell.org/ghc/ :? for help Glasgow Haskell Compiler, Version 6.10.4, for Haskell 98, stage 2 booted by GHC version 6.8.2 Using package config file: /usr/local/lib/ghc-6.10.4/./package.conf ... readModel.hs:9:7: Could not find module `Text.Parsec.Language': locations searched: Text/Parsec/Language.hs Text/Parsec/Language.lhs Failed, modules loaded: none. ... ghc-pkg finds parsec, but ghci can't find it. And if I do a cabal -v3 update I get a: cabal: 3: openFile: does not exist (No such file or directory) Anybody figured it out? - Job Vranish On Fri, Jul 17, 2009 at 11:17 AM, Thomas Hartman tphya...@gmail.com wrote: cabal -v3 update will give you a more verbose version of what is going wrong. cabal --help regrettably, cabal --help doesn't tell you this but there is always the man page I suppose. 2009/7/16 Tony Hannan tonyhann...@gmail.com: Hello, I'm on Ubuntu 8.10. I installed ghc 6.10.4 (from binary package: ghc-6.10.4-i386-unknown-linux-n.tar.bz2). I installed haskell-platform-2009.2.0.1 (from source package: haskell-platform-2009.2.0.1.tar.gz). It contains cabal-install-0.6.2. Then when I run cabal update, I get the following error: cabal: : openFile: does not exist (No such file or directory) Any ideas? Thanks, Tony ___ Libraries mailing list librar...@haskell.org http://www.haskell.org/mailman/listinfo/libraries ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: Adding a field to a data record
Malcolm Wallace Malcolm.Wallace at cs.york.ac.uk writes: and perhaps use emacs to query-replace all the Foo1's back to Foo's At least this bit can be avoided easily enough, by using module qualification during the conversion process. module Original (Foo(..)) where data Foo = Foo { ... y :: Int } deriving ... module New (Foo(..)) where data Foo = Foo { ... y, z :: Int } deriving ... module Convert where import Original as Old import New as New newFoo :: Old.Foo - New.Foo newFoo old{..} = New.Foo { a=a, b=b, ... z=1 } Finally rename module New. Regards, Malcolm Thanks Malcolm, yes, that keeps me out of emacs, but the part I would really like to avoid is writing the New.Foo { a=a, b=b, ... z=1 } part, where the field names are many, long, and varied. Yes, I could cut and paste, but I'm hoping for a better way. Thanks. Best wishes, Henry Laxen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Adding a field to a data record
On Tue, Jul 28, 2009 at 7:47 AM, Henry Laxen nadine.and.he...@pobox.comwrote: Malcolm Wallace Malcolm.Wallace at cs.york.ac.uk writes: and perhaps use emacs to query-replace all the Foo1's back to Foo's At least this bit can be avoided easily enough, by using module qualification during the conversion process. module Original (Foo(..)) where data Foo = Foo { ... y :: Int } deriving ... module New (Foo(..)) where data Foo = Foo { ... y, z :: Int } deriving ... module Convert where import Original as Old import New as New newFoo :: Old.Foo - New.Foo newFoo old{..} = New.Foo { a=a, b=b, ... z=1 } Finally rename module New. Regards, Malcolm Thanks Malcolm, yes, that keeps me out of emacs, but the part I would really like to avoid is writing the New.Foo { a=a, b=b, ... z=1 } part, where the field names are many, long, and varied. Yes, I could cut and paste, but I'm hoping for a better way. Thanks. I guess you could define: type UpgradeFoo = (Foo, Int) And then write the conversion code as a zip. upgradeFoo foos = zip foos [1..] instance Show UpgradeFoo where ... And then use the module trick to switch the code around? Jason ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: Adding a field to a data record
Suppose you have a data type like: Data Foo = Foo { a :: Int, b :: Int, ... many other fields ... y :: Int } deriving (Eq, Read, Show, Typeable, Data) Now I would like to add a field z :: Int to the end of Foo. If I have a ton of data out on disk, which I wrote with, say writeFile a.data (show foo) -- where foo is a [Foo] say 1000 long, I would like to get a new a.data file which has a new z::Int field. This seems to depend on what you want to accomplish. Is your goal just to rewrite this whole file? If it is, the idea of just adding a field to Foo would be enough. You could then add that 'z' field in your file using 'sed' (or, as you said, emacs) and then read it back. In general, however, if you want to deal with this kind of translation of text to data, what you really want is to take some time to learn something like Parsec. http://www.haskell.org/ghc/docs/latest/html/libraries/parsec/Text-ParserCombinators-Parsec.html So far the only way I can think of is to make a new Data Foo1, which includes the z::Int, read in a.data as a list of Foo, write a function like: fooTofoo1 :: Foo - Foo1 fooTofoo1 xx = Foo1 {a = a xx, ... y = y xx, z = 1} Note that this would not work exactly like that. 'a' is a field of Foo, and that means it's a function like a :: Foo - Int So, you can't use it as a field of Foo1, as that would imply a :: Foo1 - Int Best, Maurício ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Adding a field to a data record
the part I would really like to avoid is writing the New.Foo { a=a, b=b, ... z=1 } part, where the field names are many, long, and varied. OK, here is another hack-ish trick, since I notice your data is stored on disk as text, using show. I assume you are using something like Read to retrieve it. Well, how about using a real parser instead? The parser during conversion can be slightly more lax, automatically adding in the extra field. For instance, using polyparse's Text.Parse, and DrIFT to derive the appropriate Parse instance for your datatype: module Foo where data Foo = Foo { a :: Int , b :: Bool , c :: Maybe Foo } {-! derive : Parse !-} DrIFT gives you this instance: {-* Generated by DrIFT : Look, but Don't Touch. *-} instance Parse Foo where parse = constructors [ ( Foo , return Foo `discard` isWord { `apply` field a `discard` isWord , `apply` field b `discard` isWord , `apply` field c `discard` isWord } ) ] Let's say the field 'b' is new, and your existing data does not have it. So just take the parser generated by DrIFT and make a small modification: {-* Generated by DrIFT but modified by hand for conversion purposes *-} instance Parse Foo where parse = constructors [ ( Foo , return Foo `discard` isWord { `apply` field a `apply` return True -- this field does not yet exist in data `discard` isWord , `apply` field c `discard` isWord } ) ] Then do the obvious thing: parse the old data, immediately write it out again, and then throw away the modified parser in favour of the pure generated one. Regards, Malcolm ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Need feedback on my Haskell code
Thank you very much Jedai ... this looks much more concise and does not contain the repetitions that I had. I'd need to go over it more to understand it better. I'll ping you if I have any questions about this. Regards, Kashyap From: Chaddaï Fouché chaddai.fou...@gmail.com To: CK Kashyap ck_kash...@yahoo.com Cc: haskell-cafe@haskell.org Sent: Tuesday, July 28, 2009 7:10:38 PM Subject: Re: [Haskell-cafe] Need feedback on my Haskell code On Tue, Jul 28, 2009 at 3:04 PM, CK Kashyapck_kash...@yahoo.com wrote: Hi Everyone, I managed to write up the line drawing function using the following links - http://www.cs.helsinki.fi/group/goa/mallinnus/lines/bresenh.html http://rosettacode.org/wiki/Bresenham%27s_line_algorithm#Haskell I tried to simplify your function a little bit : line :: Point - Point - [Point] line pa@(xa,ya) pb@(xb,yb) = map maySwitch . unfoldr go $ (x1,y1,0) where steep = abs (yb - ya) abs (xb - xa) maySwitch = if steep then (\(x,y) - (y,x)) else id [(x1,y1),(x2,y2)] = sort [maySwitch pa, maySwitch pb] deltax = x2 - x1 deltay = abs (y2 - y1) ystep = if y1 y2 then 1 else -1 go (xTemp, yTemp, error) | xTemp x2 = Nothing | otherwise = Just ((xTemp, yTemp), (xTemp + 1, newY, newError)) where tempError = error + deltay (newY, newError) = if (2*tempError) = deltax then (yTemp+ystep,tempError-deltax) else (yTemp,tempError) I think it will be a bit better, tell me what you think ? -- Jedaï ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Adding a field to a data record
Hello, you may also find the package pretty-show (http://hackage.haskell.org/package/pretty-show) useful. It contains code to convert automatically derived instances of Show into an explicit data structure, which you can then manipulate (e.g., by adding the extra field), and then render back to text. -Iavor On Tue, Jul 28, 2009 at 6:07 PM, Malcolm Wallacemalcolm.wall...@cs.york.ac.uk wrote: the part I would really like to avoid is writing the New.Foo { a=a, b=b, ... z=1 } part, where the field names are many, long, and varied. OK, here is another hack-ish trick, since I notice your data is stored on disk as text, using show. I assume you are using something like Read to retrieve it. Well, how about using a real parser instead? The parser during conversion can be slightly more lax, automatically adding in the extra field. For instance, using polyparse's Text.Parse, and DrIFT to derive the appropriate Parse instance for your datatype: module Foo where data Foo = Foo { a :: Int , b :: Bool , c :: Maybe Foo } {-! derive : Parse !-} DrIFT gives you this instance: {-* Generated by DrIFT : Look, but Don't Touch. *-} instance Parse Foo where parse = constructors [ ( Foo , return Foo `discard` isWord { `apply` field a `discard` isWord , `apply` field b `discard` isWord , `apply` field c `discard` isWord } ) ] Let's say the field 'b' is new, and your existing data does not have it. So just take the parser generated by DrIFT and make a small modification: {-* Generated by DrIFT but modified by hand for conversion purposes *-} instance Parse Foo where parse = constructors [ ( Foo , return Foo `discard` isWord { `apply` field a `apply` return True -- this field does not yet exist in data `discard` isWord , `apply` field c `discard` isWord } ) ] Then do the obvious thing: parse the old data, immediately write it out again, and then throw away the modified parser in favour of the pure generated one. Regards, Malcolm ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Proposal: TypeDirectedNameResolution
On Tue, Jul 28, 2009 at 1:41 AM, Heinrich Apfelmusapfel...@quantentunnel.de wrote: While I do agree that qualified names are annoying at times, I think that type directed name disambiguation is a Pandora's box. I see where you are going, but I'm not sure I agree. Let me give an example from another language with this kind of resolution: C++. From a purely practical point of view, function overloading in C++ does what I want almost all the time. And when it doesn't do what I want, it's always been immediately obvious, and it's a sign that my design is flawed. But those cases where it does what I want have been incredibly useful. Furthermore, we already have a mechanism for type based disambiguation, namely good old type classes. For instance, the qualifications required when importing Data.Map are actually a sign that we are lacking proper container type classes à la Edison. Perhaps. I think containers is a great example of why you want TDNR. Many containers have *almost* the same interface, but not quite. After all, if the interface was the same, you would just find the most efficient container for that interface and call it a day. So unless you want to go the direction of putting every single container-related function in its own typeclass, I don't think you'll be able to come up with one container interface to rule them all. To be fair, I'm not against the idea of putting each function in its own typeclass. For work along these lines, see the many better numeric hierarchy attempts. But I'd also need support for class aliases or something similar so that defining common subsets of those classes would work easily. Along those lines, what about being able to elide class names when they can be unambiguously determined from the functions defined? instance _ [] where fmap = map pure x = [x] fs * xs = [ f x | f - fs, x - xs ] return x = [x] m = f = concatMap f m This would define Functor, Applicative, and Monad for []. -- ryan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] powerSet = filterM (const [True, False]) ... is this obfuscated haskell?
On Tue, Jul 28, 2009 at 6:47 AM, Sebastian Fischers...@informatik.uni-kiel.de wrote: perms = sortByM (const [True,False]) Hence, perm as defined above can yield a list that contains all permutations of the input (at least once) regardless of the sorting algorithm. Where is the hitch? The algorithm might diverge when given a non-transitive comparison operator. On Spore we had a bug where a NaN got into a list of floats we were sorting and our quicksort corrupted the heap because isn't transitive on lists with NaNs. -- ryan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Proposal: TypeDirectedNameResolution
Ryan == Ryan Ingram ryani.s...@gmail.com writes: Ryan Along those lines, what about being able to elide class Ryan names when they can be unambiguously determined from the Ryan functions defined? Ryan instance _ [] where fmap = map pure x = [x] fs * xs = [ f Ryan x | f - fs, x - xs ] return x = [x] m = f = concatMap f Ryan m Ryan This would define Functor, Applicative, and Monad for []. What happens if I define a class Foo with a method named fmap? If this were in scope then Functor would no longer be defined for []. Could this situation cause a problem? -- Colin Adams Preston Lancashire ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Deepest polymorphic functor
I was wondering if it is possible to somehow change deep f_map from http://okmij.org/ftp/Haskell/deepest-functor.lhs article in a such a way that it would work not only for monotypes like in the provided example: test1 = f_map (+1) [[[1::Int,2,3]]] But for polymorphic types as well (e.g. behaves like simple map) so the following line would compile as well: test1 = f_map (+1) [[[1,2,3]]] ? -- View this message in context: http://www.nabble.com/Deepest-polymorphic-functor-tp24709303p24709303.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] lifting restrictions on defining instances
Tillmann Rendel wrote: wren ng thornton wrote: Thus, the forall keyword is serving as the type-level abstraction. What do you mean by type-level abstraction here? I mean an abstraction, as in a lambda-abstraction (aka a lambda-expression), at the type level. [...] I'm not sure I follow what you mean. I mean that the forall keyword is *not* serving as the type-level abstraction. There is a difference between abstraction (as in lambda abstraction) and the type of abstractions (as in function types). In pure type systems, we have two different binders for these different features: - lower-case lambda for abstraction (on all levels) - upper-case Pi for the type of abstractions (on all levels) I find it highly confusing to say that forall denotes type-level abstraction, because it does not denote abstraction at all. It rather denotes the type of an abstraction, namely in Haskell, the type of abstracting over types in terms. I view these as different sides of the same coin. There are two different senses of the forall keyword. There's the implicit Rank-1 quantifier, and then there's the Rank-N quantifier for polymorphic components. Your intuition is relying on the latter, whereas mine is relying on the former. The difference is similar to the difference between morphisms vs exponential objects in CCCs. We often find it convenient to elide the conversions between them, but they are in fact quite different. And if, at the term layer, functions can be silently lifted to/lowered from closures, then why not also at the type layer? While it is important to keep the ideas distinct, in practice we've found great utility in conflating the two faces of the coin. Why can't the type of abstractions be an abstraction of types? This is not currently the case in GHC, as you point out, but that does not demonstrate that the idea is unsound. This distributive transformation is used routinely in Conal Elliott's typeclass morphisms[1], Ralf Hinze's polyidiomatic lambda calculus[2], in HOAS (if you squint), and many other places where poly*ism spans multiple layers of the tower of interpretation. The symmetry between forall and /\ in System F is simply too great to write off without investigation. In any case, I think this discussion has veered far afield from the intent of my original footnote, which was simply to point out that the capital-lambda binder already has a canonical usage in System F (so we should not co-op it for type abstractions, without express intention). I have little invested in the current discussion, and the Cafe list doesn't really seem like the best venue to pursue it. If you have references you think would enlighten me, I'd happily pursue them. Otherwise, I think the best color for the bikeshed is purple :) [1] http://conal.net/blog/tag/type-class-morphism/ [2] http://www.comlab.ox.ac.uk/ralf.hinze/WG2.8//26/slides/ralf.pdf -- Live well, ~wren ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Proposal: TypeDirectedNameResolution
On Jul 29, 2009, at 5:05 AM, Ryan Ingram wrote: I see where you are going, but I'm not sure I agree. Let me give an example from another language with this kind of resolution: C++. Right. That settles it: TDNR is a bad idea. Half fun and full earnest. I'm a fan of overloading as done in Ada, but the way C++ does it has always struck me as a mix of under-useful and over-complex, and my experience with it in practice has not been that marvellous. (C++ has far too many types that are _sort of_ compatible, but only sort of.) Interestingly, I've found that when I've thought I've wanted overloading in Haskell, what I've _really_ wanted is typeclasses, because they give me - far more confidence that my code is correct - far more _leverage_; typeful programming is amazing. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Proposal: TypeDirectedNameResolution
On Tuesday 28 July 2009 8:27:53 pm Richard O'Keefe wrote: Right. That settles it: TDNR is a bad idea. Half fun and full earnest. I'm a fan of overloading as done in Ada, but the way C++ does it has always struck me as a mix of under-useful and over-complex, and my experience with it in practice has not been that marvellous. (C++ has far too many types that are _sort of_ compatible, but only sort of.) Amusingly enough, one of the major items going into C++0x was concepts, which are an effort to add type class-alike restrictions to C++'s current completely ad-hoc overloading. They were only recently dropped due to disagreements about certain details (I think I read that people couldn't agree whether programmers should be forced to declare the analogue of class instances, or whether the compiler should figure it out, but I haven't paid close attention, so that may be inaccurate). -- Dan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] runProcess does not care about hSetBuffering?
Hi, Code like: (or_, ow_) - createPipe or - fdToHandle or_ ow - fdToHandle ow_ hSetBuffering ow LineBuffering hSetBuffering or LineBuffering h - runProcess cmd [] Nothing Nothing Nothing (Just ow) Nothing In the cmd process, the ow is not LineBuffering -- 竹密岂妨流水过 山高哪阻野云飞 ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] runProcess does not care about hSetBuffering?
On Jul 28, 2009, at 21:14 , Magicloud Magiclouds wrote: (or_, ow_) - createPipe or - fdToHandle or_ ow - fdToHandle ow_ hSetBuffering ow LineBuffering hSetBuffering or LineBuffering h - runProcess cmd [] Nothing Nothing Nothing (Just ow) Nothing In the cmd process, the ow is not LineBuffering Buffering is not an attribute of a filehandle, but of the I/O library. There is no way for you to tell cmd how you want it to buffer, unless it has an option to do so (cat -u, tcpdump -l, etc.), although you can hint by using a pty instead of a pipe: many programs will switch to line buffering in that case, some will go unbuffered; usually, a pipe, FIFO, or ordinary file will be block buffered. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu electrical and computer engineering, carnegie mellon universityKF8NH PGP.sig Description: This is a digitally signed message part ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Hugs used in circuit simulations code
Hi all thanks to everyone that reviewed my code. The good news 1. I happy to say that it has become useful enough for me to use it in some matlab type caluculations. includes transient and dc op 2. The simple pivtoing code I added into the DSP Lu appears to be useable for this application. The bad news 1. If you dont use some strategy in simplifying circuits and use the simulator only, it would take a considerable amount of time to converge. A simple 10x10 non linear matrix will take 13 minutes. In a high-end circuit simulator this would have taken less than a second. What is everybodies expereience in speed difference between C and interpreted haskell? I am hoping to achieve at least 10x an equivalent C code. So if a 10x10 matrix takes 1 second for C I want it to take 10seconds for hugs. regards fernan -- http://www.fernski.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Deepest polymorphic functor
What would this do with instance Num a = Num [a] in scope? On Tue, Jul 28, 2009 at 3:51 PM, Eduard Sergeeveduard.serg...@gmail.com wrote: I was wondering if it is possible to somehow change deep f_map from http://okmij.org/ftp/Haskell/deepest-functor.lhs article in a such a way that it would work not only for monotypes like in the provided example: test1 = f_map (+1) [[[1::Int,2,3]]] But for polymorphic types as well (e.g. behaves like simple map) so the following line would compile as well: test1 = f_map (+1) [[[1,2,3]]] ? -- View this message in context: http://www.nabble.com/Deepest-polymorphic-functor-tp24709303p24709303.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Hugs used in circuit simulations code
Am Mittwoch 29 Juli 2009 03:32:20 schrieb Fernan Bolando: What is everybodies expereience in speed difference between C and interpreted haskell? That depends on what you do, unsurprisingly. But usually it's huge. A factor of several hundred is not uncommon, but 10-100 is the normal range (in my limited experience, I almost always compile). I am hoping to achieve at least 10x an equivalent C code. Then you should definitely *not* run interpreted code, but compile it. With compiled code, I usually have a factor of less than 10, mostly 2-4, sometimes even better. But some things take longer in Haskell. So if a 10x10 matrix takes 1 second for C I want it to take 10seconds for hugs. Execution speed is not one of hugs' strongest points, so I'd be surprised. I recommend you get a GHC. regards fernan Cheers, Daniel ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Hugs used in circuit simulations code
daniel.is.fischer: Am Mittwoch 29 Juli 2009 03:32:20 schrieb Fernan Bolando: What is everybodies expereience in speed difference between C and interpreted haskell? Why are you using hugs? Hugs is slower than GHCi, which is around 30x slower on average than GHC, (measured a couple of years ago). Please use ghc -O2 if you care about performance! -- Don ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Hugs used in circuit simulations code
On Tue, Jul 28, 2009 at 6:32 PM, Fernan Bolando fernanbola...@mailc.netwrote: Hi all thanks to everyone that reviewed my code. The good news 1. I happy to say that it has become useful enough for me to use it in some matlab type caluculations. includes transient and dc op 2. The simple pivtoing code I added into the DSP Lu appears to be useable for this application. The bad news 1. If you dont use some strategy in simplifying circuits and use the simulator only, it would take a considerable amount of time to converge. A simple 10x10 non linear matrix will take 13 minutes. In a high-end circuit simulator this would have taken less than a second. What is everybodies expereience in speed difference between C and interpreted haskell? I am hoping to achieve at least 10x an equivalent C code. So if a 10x10 matrix takes 1 second for C I want it to take 10seconds for hugs. Use GHC's profiler. Figure out why and where the code is slow and then you can do something about it: http://book.realworldhaskell.org/read/profiling-and-optimization.html Jason ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe