On 17/03/2009, at 1:13 PM, Jonathan Cast wrote:
[Totally OT tangent: How did operational semantics come to get its
noun?
The more I think about it, the more it seems like a precís of the
implementation, rather than a truly semantic part of a language
specification.]
I haven't followed the w
a...@spamcop.net wrote:
G'day all.
Quoting wren ng thornton :
> Most of the (particular) problems OO design patterns solve are
> non-issues in Haskell because the language is more expressive.
...and vice versa. Some of the "design patterns" that we use in
Haskell, for example, are to overcome
On Mon, 16 Mar 2009, Matthew Donadio wrote:
Thy polynomial and matrix libraries weren't really developed to be stand
alone libraries. I was developing some DSP libraries that required
polynomial and matrix math, so I implemented what I needed so I could test
the DSP. Both libraries work for
On Tue, 2009-03-17 at 01:16 +, Claus Reinke wrote:
> >> > > "exception handling" which allows to "catch" programming errors.
> >> > And which I have a sneaking suspicion actually *is* `unsafe'. Or, at
> >> > least, incapable of being given a compositional, continuous semantics.
> >> "A semanti
>
> Why not:
>
> data Value = forall a . Typeable a => V a
>
> type STValue s = STRef Value
>
This should be:
type STValue s = STRef s Value
Antoine
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-
On Mon, Mar 16, 2009 at 8:08 PM, Michael Vanier wrote:
> Ryan,
>
> So, if I understand you correctly, my only option is to use an IORef instead
> of an STRef? What I'm trying to do is implement a mutable box type as part
> of a dynamically-typed language I'm implementing in Haskell (which is main
> > "exception handling" which allows to "catch" programming errors.
> And which I have a sneaking suspicion actually *is* `unsafe'. Or, at
> least, incapable of being given a compositional, continuous semantics.
"A semantics for imprecise exceptions"
http://research.microsoft.com/en-us/um/people
Ryan,
So, if I understand you correctly, my only option is to use an IORef
instead of an STRef? What I'm trying to do is implement a mutable box
type as part of a dynamically-typed language I'm implementing in Haskell
(which is mainly an exercise to improve my Haskell programming; mission
ac
Having the state be an instance of Typeable breaks the purity
guarantees of runST; a reference could escape runST:
let v = runST (V `liftM` newSTRef 0)
in runST (readSTRef $ fromJust $ getValue v)
Keep in mind that the state actually used by runST is "RealWorld";
runST is just a pretty name f
Hi,
I'm having a problem using Typeable with STRefs. Basically, I want to
store STRefs (among other things) in a universal type. STRef is an
instance of Typeable2, which means that STRef s a is Typeable if s and a
are both Typeable. The problem is that the state type s is opaque and I
can
Eric Kow writes:
> We hope to raise another $5000 to pay for a summer project ($4000)
Nitpick: "summer" is hemispherist.
--
Trent W. Buck, Pedant
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-c
Hi.
For my Netflix Prize project I have implemented two reusable modules.
The first module implements a random shuffle on immutable lists.
It uses http://okmij.org/ftp/Haskell/perfect-shuffle.txt, with an
additional "wrapper" function, having a more friendly interface.
The second module implem
On Mon, 2009-03-16 at 22:01 +, Duncan Coutts wrote:
> On Mon, 2009-03-16 at 14:17 -0700, Jonathan Cast wrote:
> > On Mon, 2009-03-16 at 22:12 +0100, Henning Thielemann wrote:
> > > On Sun, 15 Mar 2009, Claus Reinke wrote:
> > >
> > > > import Data.IORef
> > > > import Control.Exception
> > > >
2009/3/16 Duane Johnson
> Looks great!
> By any chance, is the mesh loading functionality separate from the texture
> loading?
>
Yes, it is completly separated from material, it only refers to material's
name.
You can define the material writing a nice human readable script:
http://www.ogre3d.org
On Mon, Mar 16, 2009 at 9:50 PM, Henning Thielemann <
lemm...@henning-thielemann.de> wrote:
> Polynomial arithmetic is also contained in
>
> http://hackage.haskell.org/packages/archive/numeric-prelude/0.0.5/doc/html/MathObj-Polynomial.html
> http://darcs.haskell.org/htam/src/Polynomial.hs
Nice
On Mon, 2009-03-16 at 14:17 -0700, Jonathan Cast wrote:
> On Mon, 2009-03-16 at 22:12 +0100, Henning Thielemann wrote:
> > On Sun, 15 Mar 2009, Claus Reinke wrote:
> >
> > > import Data.IORef
> > > import Control.Exception
> > >
> > > main = do
> > > r <- newIORef 0
> > > let v = undefined
> >
Oh yes, we will :-)
On Mon, Mar 16, 2009 at 10:45 PM, Roel van Dijk wrote:
> This is really nice! I will be looking forward to the preview version.
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/has
2009/3/16 Csaba Hruska :
> Hi!
>
> I've created a wiki page for my project.
> Currently only some text and screenshot are available.
> Additional documentation and source code are coming soon.. :)
>
> http://www.haskell.org/haskellwiki/LambdaCubeEngine
>
> Cheers,
> Csaba Hruska
>
> ___
2009/3/16 Peter Verswyvelen :
> The DSP package on Hackage seems to contain complex polynomial functions.
> It seems these functions are completely independent of the other DSP
> functions, so this package could be split of?
I would be interested in a separate package that deals with
polynomials.
I'm just getting to know this community, and I have to say, I am very
impressed by this. Congrats to everyone for making the world a better
place :)
-- Duane Johnson
On Mar 16, 2009, at 6:09 AM, Eric Kow wrote:
Dear darcs users and Haskellers,
I wanted to thank you all for your contribut
On Mon, 2009-03-16 at 22:12 +0100, Henning Thielemann wrote:
> On Sun, 15 Mar 2009, Claus Reinke wrote:
>
> > import Data.IORef
> > import Control.Exception
> >
> > main = do
> > r <- newIORef 0
> > let v = undefined
> > handle (\(ErrorCall _)->print "hi">>return 42) $ case f v of
> > 0
On Sun, 15 Mar 2009, Claus Reinke wrote:
import Data.IORef
import Control.Exception
main = do
r <- newIORef 0
let v = undefined
handle (\(ErrorCall _)->print "hi">>return 42) $ case f v of
0 -> return 0
n -> return (n - 1)
y <- readIORef r
print y
I don't see what this has
On Sun, 15 Mar 2009, Ryan Ingram wrote:
unsafeInterleaveIO allows embedding side effects into a pure
computation. This means you can potentially observe if some pure
value has been evaluated or not; the result of your code could change
depending how lazy/strict it is, which is very hard to pr
On Mon, 16 Mar 2009, Peter Verswyvelen wrote:
The DSP package on Hackage seems to contain complex polynomial functions.
It seems these functions are completely independent of the other DSP functions,
so this
package could be split of?
The matrix stuff is also independent. If you split off th
Don Stewart wrote:
tphyahoo:
Is there something like subRegex... something like =~ s/.../.../ in
perl... for haskell pcre Regexen?
I mean, subRegex from Text.Regex of course:
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/regex-compat
Thanks for any advice,
Basically, we should h
On Mon, Mar 16, 2009 at 9:26 AM, Arie Peterson wrote:
>
> It is indeed unfortunate that mtl:State is a different type from
> transformers:State, but that is not biting me right now.
>
If the type problem does ever become an issue, could the MTL use the
types from the transformers package?
Antoin
Thanks, that was extremely helpful.
My bad for being so sloppy reading the documentation so sloppily -- I
somehow glossed over the bit that backreferences worked as one would
expect.
To atone for this,
http://patch-tag.com/repo/haskell-learning/browse/regexStuff/pcreReplace.hs
shows successful =
Hi!
I've created a wiki page for my project.
Currently only some text and screenshot are available.
Additional documentation and source code are coming soon.. :)
http://www.haskell.org/haskellwiki/LambdaCubeEngine
Cheers,
Csaba Hruska
___
Haskell-Cafe
On Monday 16 March 2009 2:11:10 pm Ryan Ingram wrote:
> However, I disagree with your description of what "unsafe" should be
> used for. "unsafe" calls out the need for the programmer to prove
> that what they are doing is safe semantically, instead of the compiler
> providing those proofs for you
Don Stewart ha scritto:
manlio_perillo:
Don Stewart ha scritto:
I've just finished a post (and quick tool) for graphing the complete
module namespace of Haskell, taken from the core libraries and all of
Hackage.
It's quite large:
http://donsbot.wordpress.com/2009/03/16/visualising-the-h
On Mon, Mar 16, 2009 at 7:55 AM, Jake McArthur wrote:
> I think it depends on what we want to take "unsafe" to mean. In my
> opinion, the word "unsafe" should really only be used in cases where
> using the function can case an otherwise well-typed program to not be
> well-typed. I'm pretty sure I
manlio_perillo:
> Don Stewart ha scritto:
>> I've just finished a post (and quick tool) for graphing the complete
>> module namespace of Haskell, taken from the core libraries and all of
>> Hackage.
>>
>> It's quite large:
>>
>> http://donsbot.wordpress.com/2009/03/16/visualising-the-haskell-u
Don Stewart ha scritto:
I've just finished a post (and quick tool) for graphing the complete
module namespace of Haskell, taken from the core libraries and all of
Hackage.
It's quite large:
http://donsbot.wordpress.com/2009/03/16/visualising-the-haskell-universe/
Just a note: isn't it t
>
>
> On Mon, 16 Mar 2009 08:05:37 -0700 Don Stewart wrote :
> Subject: [Haskell-cafe] Visualising the Hierarchical Namespace
>
> I've just finished a post (and quick tool) for graphing the complete
> module namespace of Haskell, taken from the core libraries and all of
> Hackage.
>
> It's quite l
Hi Mark,
What's the definition of foldr in terms of map? As far as I was aware,
its not possible.
And as it happens, map is (or is sometimes) defined in term of foldr
:-) While you can use mutual recursion, you can't define a in terms of
b and b in terms of a unless one of them actually does some
Hi,
I’ve noticed that it’s possible to define map as foldr and foldr as a map.
Would this be sensible to define both in terms of each other in the Prelude?
i.e mutually recursive?
Cheers,
Mark
No virus found in this outgoing message.
Checked by AVG.
Version: 7.5.557 / Virus Databa
The DSP package on Hackage seems to contain complex polynomial functions.
It seems these functions are completely independent of the other DSP
functions, so this package could be split of?
Also, polynomials form a vector space, so could be made an instance of
VectorSpace class?
___
That's why I just asked on IRC for them :-) Also wrote most of a
Hieroglyph script last night to replace the graph of daily uploads on
Hackage. Will send it out tonight or tomorrow.
On Mon, Mar 16, 2009 at 11:17 AM, Don Stewart wrote:
> My secret hope is that Jeff will take the .dot files and do
Beautiful; I especially like the "neato" rendering. There's just something
about the concentric circles radiating out from certain modules that just
looks so...well, cool. Nice work!
-John
On Mon, Mar 16, 2009 at 11:05 AM, Don Stewart wrote:
> I've just finished a post (and quick tool) for grap
My secret hope is that Jeff will take the .dot files and doing
something very cool with them
jefferson.r.heard:
> Very impressive looking, Don.
>
> -- Jeff
>
> On Mon, Mar 16, 2009 at 11:14 AM, Don Stewart wrote:
> > Oh, barely any time (maybe 30-60 seconds). It's "just" a 10k node graph
>
Very impressive looking, Don.
-- Jeff
On Mon, Mar 16, 2009 at 11:14 AM, Don Stewart wrote:
> Oh, barely any time (maybe 30-60 seconds). It's "just" a 10k node graph with
> a 50k edges. :)
>
> vanenkj:
>> How long did the haskell universe graphs take to render?
>>
>> On Mon, Mar 16, 2009 at 11:0
Oh, barely any time (maybe 30-60 seconds). It's "just" a 10k node graph with a
50k edges. :)
vanenkj:
> How long did the haskell universe graphs take to render?
>
> On Mon, Mar 16, 2009 at 11:05 AM, Don Stewart wrote:
>
> I've just finished a post (and quick tool) for graphing the complete
How long did the haskell universe graphs take to render?
On Mon, Mar 16, 2009 at 11:05 AM, Don Stewart wrote:
> I've just finished a post (and quick tool) for graphing the complete
> module namespace of Haskell, taken from the core libraries and all of
> Hackage.
>
> It's quite large:
>
>
> http
I've just finished a post (and quick tool) for graphing the complete
module namespace of Haskell, taken from the core libraries and all of
Hackage.
It's quite large:
http://donsbot.wordpress.com/2009/03/16/visualising-the-haskell-universe/
___
Hask
Am Samstag, 14. März 2009 23:33 schrieben Sie:
> On Fri, 13 Mar 2009, Wolfgang Jeltsch wrote:
> > Class instances should satisfy certain laws. (Although these laws are
> > often not stated explicitely, they are assumed to hold by users of the
> > class and they should hold to make the instance sens
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
Yusaku Hashimoto wrote:
| I was studying about what unsafeInterleaveIO is.I understood
| unsafeInterleaveIO takes an IO action, and delays it. But I couldn't
| find any reason why unsafeInterleaveIO is unsafe.
I think it depends on what we want to ta
On Sat, 14 Mar 2009 02:14:53 +0100 (CET), Henning Thielemann
wrote:
> I think 'transformers' exports Control.Monad.Trans.State. This should not
> conflict with MTL. However, MTL's State type is different from
> transformer's one. Is that your problem?
No. The immediate problem is, that a modul
On 2009 Mar 16, at 8:48, Yusaku Hashimoto wrote:
On 2009/03/16, at 10:04, wren ng thornton wrote:
Moreover, let's have two pure implementations, f and g, of the same
mathematical function. Even if f and g are close enough to
correctly give the same output for inputs with _|_ in them, we may
On 2009 Mar 16, at 6:53, Vimal wrote:
Is there a packet analysis framework in Haskell? The framework should
abstract away the features of packet analysis in the form of a library
that people can use and write extensions to perform computation on the
packets flowing through the network.
The onl
R J wrote:
> The following theorem is obviously true, but how is it proved (most cleanly
> and simply)
> in Haskell?
>
> Theorem: (nondecreasing xs) => nondecreasing (insert x xs), where:
>
>nondecreasing :: (Ord a) => [a] -> Bool
>nondecreasing []= True
>
Thomas Hartman wrote:
testPcre = ( subRegex (mkRegex "(?
quoting from the man page for regcomp:
REG_NEWLINE Compile for newline-sensitive matching. By default, newline is a
completely ordinary character with
no special meaning in either REs or strings. With this flag,
`[^'
Thomas Hartman wrote:
testPcre = ( subRegex (mkRegex "(?
quoting from the man page for regcomp:
REG_NEWLINE Compile for newline-sensitive matching. By default, newline is a
completely ordinary character with
no special meaning in either REs or strings. With this flag,
`[^'
Hi,
On 2009/03/16, at 10:04, wren ng thornton wrote:
> next r = do n <- readIORef r
> writeIORef r (n+1)
> return n
Now, if I use unsafeInterleaveIO:
> main = do r <- newIORef 0
> x <- do a <- unsafeInterleaveIO (next r)
>b <- unsafeInter
Dear darcs users and Haskellers,
I wanted to thank you all for your contributions to our first darcs
fundraising drive. We've done it! We managed to raise $1000, over two
weeks with contributions from 22 donors. This means that we will able
to help our programmers travel to the darcs hacking sp
Vimal wrote:
> The above are some of the features which I believe are necessary for
> packet analysis (or, analytics maybe?). There could be more. I was
> wondering if Haskell would be a good language to achieve these things.
> I had a brief idea and started writing an application in C and I
> re
Hi all,
Is there a packet analysis framework in Haskell? The framework should
abstract away the features of packet analysis in the form of a library
that people can use and write extensions to perform computation on the
packets flowing through the network.
What are the "features" of packet analys
* Ryan Ingram [2009-03-14 11:36:33-0700]
> For the second case you might be able to come up with a commutative
> hash-combiner function for && and ||.
What a beautiful idea! I wish I thought of it myself.
> For the lambda-term situation, I can think of a couple ways to hash
> that give what you
On Monday 16 March 2009 06:40:12 Alexander Dunlap wrote:
> Hi all,
>
> I have noticed that in both Data.Binary and Data.Text (which is still
> experimental, but still), the "decode" functions can be undefined
> (i.e. bottom) if they encounter malformed input.
>
> What is the preferred way to use th
I am pleased to announce that a new issue of The Monad.Reader is now
available:
http://www.haskell.org/haskellwiki/The_Monad.Reader
The Monad.Reader is a quarterly magazine about functional programming.
Issue 13 consists of the following four articles:
* Stephen Hicks
Rapid Prototyp
I've set both limits to 20MiB, and switched off MediaWiki's warning.
I've uploaded Wouter's file to [[Image:TMR-Issue13.pdf]].
Fantastic! Thanks for all your help,
Wouter
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org
Okay, many thanks. That's exactly I need (I hope :-) ).
Cheers,
Martin
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
2009/3/14 Gü?nther Schmidt :
> Hi,
>
> can someone please point me to error handling examples with takusen?
>
> I try to run a piece of code with takusen but just get the very sparse
> "Database.InternalEnumerator.DBException
Hello Günther,
We use dynamic exceptions in Takusen, which is why you d
Hi Martin,
> Only to avoid misunderstandings, you only use the ghc-api to get the AST
> of a CoreModule which you translate into your own data structure (VHDL).
That's correct.
> At this point, you don't use type information, right?
I use some typing information, but that's mostly hidden away. In
Wouter Swierstra wrote:
I can't manage to upload files to the Haskell wiki. I've tried different
browsers, different internet connections, different machines, different
operating systems, and different user accounts - all without success. Is
this a new anti-spam measure?
This is slightly anno
Matthijs Kooijman wrote:
> I've been working on parsing core in the past few months. For an example, look
> here:
>
> http://git.stderr.nl/gitweb?p=matthijs/projects/fhdl.git;a=blob;f=Translator.hs;h=8072f85925ad1238
>
> The loadModule and findBind functions are interesting. As for iterating th
65 matches
Mail list logo