> From: Jan-Willem Maessen
> Sent: Wed, March 23, 2011 8:43:14 PM
>
> Hi all -
>
> I've been trying to construct a class declaration with an associated
> type synonym, but I'd like to constrain that type to belong to a
> particular class.
>
> Consider the following class:
>
> class Monoid
Welcome to issue 174 of the HWN, a newsletter covering developments in the
[1]Haskell community. This release covers the week of March 13-19.
You can find the HTML version at: http://bit.ly/hLu36R
Announcements
JP Moresmau [2]announced a new release of EclipseFP with support for ghc
Hi all -
I've been trying to construct a class declaration with an associated
type synonym, but I'd like to constrain that type to belong to a
particular class.
Consider the following class:
class Monoid m => Constructs c m | c -> m where
construct :: m -> c
This captures the idea that the co
On Mar 23, 2011, at 6:57 PM, Henning Thielemann wrote:
James Cook schrieb:
Those are both options, as is to simply restart findRoot if it
returns
a 'Left' vaule. I personally would incline toward a custom driver
function (findRoot). I should probably add one to the library that
accepts a
On 24 March 2011 01:22, Bas van Dijk wrote:
> The given IO computation can then be something like: unsafeIOToSTM $ newTVar
> e.
Oops I meant: unsafeSTMToIO $ newTVar e
where
unsafeSTMToIO :: STM a -> IO a
unsafeSTMToIO (STM m) = IO m
___
Haskell-Caf
On 23 March 2011 21:07, Ketil Malde wrote:
> Shouldn't it be possible to create an array in a loop with only constant
> memory overhead?
I think it should. Maybe we need something like this:
unsafeArrayM :: Ix i => (i, i) -> Int -> IO e -> IO (Array i e)
unsafeArrayM (l,u) n@(I# n#) (IO f) = IO
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1
On 3/18/11 00:43 , Conal Elliott wrote:
> Speaking of which, for a while now I've been interested in designs of
> make-like systems that have precise & simple (denotational) semantics with
> pleasant properties. What Peter Landin called "denotative" (a
I think that would be the case ...I would have to think. Should reflexive
and transitive operations I think on the finite graph (possibly with
equations).
Vasili
On Wed, Mar 23, 2011 at 5:26 PM, Luke Palmer wrote:
> On Wed, Mar 23, 2011 at 3:58 PM, Vasili I. Galchin
> wrote:
> > Hello,
> >
> >
James Cook schrieb:
> Those are both options, as is to simply restart findRoot if it returns
> a 'Left' vaule. I personally would incline toward a custom driver
> function (findRoot). I should probably add one to the library that
> accepts a step limit and/or one that just iterates until conver
On Wed, Mar 23, 2011 at 3:58 PM, Vasili I. Galchin wrote:
> Hello,
>
> Does there exist Haskell to generate a finite free category from a
> finite multipath graph with loops?
AKA the transitive closure of a graph?
Luke
___
Haskell-Cafe mailing lis
Hello,
Does there exist Haskell to generate a finite free category from a
finite multipath graph with loops?
Thank you,
Vasilki
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Bas van Dijk writes:
> Maybe it's not really a bug:
Any idea why it works in GHCI?
-k
--
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/l
Latest from hackage: 2.2.3.2
On Wednesday, March 23, 2011 01:58:52 PM you wrote:
> On 03/23/2011 06:43 AM, Gershom Bazerman wrote:
> >> I've run into that bug too. I'm pretty sure its an issue with
> >> hdbc-odbc, but haven't wanted to patch it without testing it across a
> >> few other configurat
On 03/23/2011 06:43 AM, Gershom Bazerman wrote:
I've run into that bug too. I'm pretty sure its an issue with
hdbc-odbc, but haven't wanted to patch it without testing it across a
few other configurations, which I haven't had time/found
straightforward to do.
I should add, for those interested,
Thanks a lot for all assistance and help. I'm now as well finally running
GHC 7.0.2.
I spent some time documenting all the steps I made here:
http://klevstul.posterous.com/haskell-ghc-702-on-centos-55
Cheers,
Frode
[k]
___
Haskell-Cafe mailing list
Has
Bas van Dijk writes:
> sequence ms = foldr k (return []) ms
> where
> k m m' = do
> x <- m
> xs <- m'
> return (x:xs)
Isn't this really a strictness problem with the STM monad? If I
understand correctly, this forces xs before x can be examined. Something
to be
I fixed the bug in the newArray method of a TArray:
http://hackage.haskell.org/trac/ghc/ticket/5042
Bas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On 23 March 2011 18:42, Bas van Dijk wrote:
> On 23 March 2011 17:19, Jake McArthur wrote:
>> On 03/23/2011 10:34 AM, Ketil Malde wrote:
>>>
>>> It works (calling the same function) from GHCi, but breaks when
>>> compiled. Also when compiling with -O0.
>>
>> Confirmed for GHC 7.0.2. Works fine i
On 23 March 2011 17:19, Jake McArthur wrote:
> On 03/23/2011 10:34 AM, Ketil Malde wrote:
>>
>> It works (calling the same function) from GHCi, but breaks when
>> compiled. Also when compiling with -O0.
>
> Confirmed for GHC 7.0.2. Works fine in GHCi, but compiling it (in my case,
> with -O) and
On 03/23/2011 10:34 AM, Ketil Malde wrote:
It works (calling the same function) from GHCi, but breaks when
compiled. Also when compiling with -O0.
Confirmed for GHC 7.0.2. Works fine in GHCi, but compiling it (in my
case, with -O) and running the executable causes a stack overflow unless
I r
Bas van Dijk writes:
Thanks to you and Felipe for trying this out.
>> omap <- atomically $ (newArray_ (0,n-1) :: STM (TArray Int Int))
> I can't reproduce this with ghci-7.0.2 (base-4.3.1.0, array-0.3.0.2
> and stm-2.2.0.1).
It works (calling the same function) from GHCi, but breaks when
comp
To all undergrads on this list:
Are you a student looking for an internship? Do you want to work with
Haskell in the south of France? My company, Amadeus, is able to offer
an internship on the subject of property-based testing of XML schema
based web service APIs. The project goal is to write an X
On Wed, Mar 23, 2011 at 2:22 PM, Bas van Dijk wrote:
> On 23 March 2011 13:35, Ketil Malde wrote:
>> I'm seeing some weirdness here. My code does this:
>>
>> omap <- atomically $ (newArray_ (0,n-1) :: STM (TArray Int Int))
>>
>> This gives a stack overflow when n is one million.
>
> I can't r
On 23 March 2011 13:35, Ketil Malde wrote:
> I'm seeing some weirdness here. My code does this:
>
> omap <- atomically $ (newArray_ (0,n-1) :: STM (TArray Int Int))
>
> This gives a stack overflow when n is one million.
I can't reproduce this with ghci-7.0.2 (base-4.3.1.0, array-0.3.0.2
and s
Hi,
I'm seeing some weirdness here. My code does this:
omap <- atomically $ (newArray_ (0,n-1) :: STM (TArray Int Int))
This gives a stack overflow when n is one million. The equivalent code
in the ST monad doesn't show this behavior, and works as expected.
I'm not sure what is going on
On 23 March 2011 10:28, C K Kashyap wrote:
> I am not able to ascertain if what you are saying is consistent with
> http://www.haskell.org/haskellwiki/Embedded_domain_specific_language
> Regards,
> Kashyap
Well - I'm not sure if the description of a shallow embedding on that
page is particular
On 22 March 2011 15:49, Jason Dagit wrote:
>> This seems to consistently give about a 0.4s improvement, which isn't
>> nothing but isn't a particularly interesting chunck of 8s (actually
>> it's 8.4s -> 8s). Setting it to 256M doesn't make any difference.
>
> You should use criterion to make sure
> I've run into that bug too. I'm pretty sure its an issue with hdbc-odbc, but
> haven't wanted to patch it without testing it across a few other
> configurations, which I haven't had time/found straightforward to do.
I should add, for those interested, where I think the bug is. In the bindCol
frode k writes:
> The command should be "-with-gcc".
Ah, thanks, missed that, I guess.
> Implicit import declaration:
> Could not find module `Prelude':
> Perhaps you haven't installed the profiling libraries for package
> `base'?
> Use -v to see a list of the files searched for
On Mar 23, 2011, at 4:01 AM, vagif.ve...@gmail.com wrote:
> I have a weird problem ?
> When preparing sql statements with ? placeholders, hdbc-odbc adds a space to
> a
> string value at the end.
>
> run conn "update sometable set somefield = ? where id = ?" [SqlString "bla",
> toSql 10]
>
> D
hello,
i'm a bit lost here so i hope s.o. can help me here:
seems i have a problem in my code when compiled with ghc-7.0.2:
what i try to do:
serverside:
-listen on a socket and reply to requests
client-side:
-send a request to that server
-wait for a response (with a timeout)
any ideas on how i
On Mon, Mar 21, 2011 at 5:57 PM, Ketil Malde wrote:
> I got gcc44 (RHEL package) installed, but the suggested (by ./configure
> --help) "./configure CC=gcc44" doesn't seem to do anything, this seems
> to be a documentation bug.
>
The command should be "-with-gcc". I've used the following command
>
> A shallow embedding would typically use just functions - a famous
> example is Paul Hudak's "region server". A deep embedding would build
> syntax - represented with data types - and interpret the syntax or
> compile the syntax for another use (so called "off-shoring" e.g. Conal
> Elliott's Pan
I now also fixed the examples on the website [1] to work with version 0.1.3.0
of CLaSH :-)
-- Christiaan
[1] http://clash.ewi.utwente.nl
On Mar 22, 2011, at 6:43 PM, Christiaan Baaij wrote:
> Hello,
>
> I am pleased to announce an incremental update to CLaSH, version 0.1.3.0.
>
> CLaSH can t
A shallow embedding would typically use just functions - a famous
example is Paul Hudak's "region server". A deep embedding would build
syntax - represented with data types - and interpret the syntax or
compile the syntax for another use (so called "off-shoring" e.g. Conal
Elliott's Pan).
I have a weird problem ?
When preparing sql statements with ? placeholders, hdbc-odbc adds a space to a
string value at the end.
run conn "update sometable set somefield = ? where id = ?" [SqlString "bla",
toSql 10]
Database: Ms Sql Server 2005.
Driver: FreeTds on linux
Please help!
Regards,
36 matches
Mail list logo