On Tue, Jul 28, 2009 at 6:32 PM, Fernan Bolando wrote:
> 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 ad
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 yea
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
What would this do with
instance Num a => Num [a]
in scope?
On Tue, Jul 28, 2009 at 3:51 PM, Eduard Sergeev 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
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 b
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 LineBufferin
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
--
竹密岂妨流水过
山高哪阻野云飞
__
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 i
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 Ad
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 fol
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. behav
> "Ryan" == Ryan Ingram 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 <-
On Tue, Jul 28, 2009 at 6:47 AM, Sebastian
Fischer 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
On Tue, Jul 28, 2009 at 1:41 AM, Heinrich
Apfelmus 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
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 t
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é
To: CK Kas
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 retr
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
On Tue, Jul 28, 2009 at 7:47 AM, Henry Laxen wrote:
> Malcolm Wallace 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 proces
Malcolm Wallace 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
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 :
> I tried updating to ghc-6.10.4 and have exactly the same error.
> Also ghc doesn't seem t
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
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)
N
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)
>
> li
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 or
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 sor
On Tue, Jul 28, 2009 at 3:04 PM, CK Kashyap 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 simplif
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]
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 Kashyap wrote:
> Hi Everyone,
> I managed to write up the line drawing function using the fo
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)
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
> 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 e
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 Eijkel wrote:
Is it possible, to reach the (shadowed) values in any way?
I'm not sure about this, but . . .
Another
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://w
> 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
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 comm
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 ab
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,
> b
(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 n
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 n
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 exa
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
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,
43 matches
Mail list logo