Henning Thielemann wrote:
Anyway, I tried to wrap Prelude lists in a newtype and thus got GHC (still
6.4.1) to invoke my rules instead of the Prelude rules. But I encountered
the following problem: I define something like
nonFusable x y = fusable (aux x y)
where fusion rules are defined for
Achim Schneider writes:
[EMAIL PROTECTED] wrote:
... *what do you want to convey?*
Probably that you have to come up with something more confusing and
powerful than a neural net and then transfer your consciousness into it
to understand yourself and how to program something like you.
Oh m
What kind of code would you write if it would be such monad?
Useless stuff like:
s2 = do
push 11
push 17
count >>= push
binop (+)
binop (*)
pop
Then you should use something like
data Stack a = Stack {run :: [Integer] -> (a,
On Mon, Jan 07, 2008 at 09:40:29PM +, Andrew Coppin wrote:
> Well, I was thinking more of using them for two things. One is for
> speculative work (i.e., doing work which we might need later - but don't
> bother unless there's cores going spare).
For (pure) speculative tasks, try Control.Par
On Mon, 2008-01-07 at 20:26 +, Jon Harrop wrote:
> On Monday 07 January 2008 20:27:17 Peter Verswyvelen wrote:
> > If your compiler (pretty amazing job btw) does whole program optimization,
> > can it remove the dictionary (aka v-table in C/C++ parlance?) overhead of
> > type classes? Because i
Jules Bean schrieb:
> data Stack a b = Stack { run :: [a] -> (b, [a]) }
Thank you, that does the trick.
> The correct types for the other functions are:
>
> push :: a -> Stack a ()
> pop :: Stack a a
> top :: Stack a a
>
> With those clues I think you will be able to write >>= and return more
>
Ben Franksen <[EMAIL PROTECTED]> wrote:
> Spencer Janssen wrote:
> > On Sun, Jan 06, 2008 at 11:30:53AM +, Andrew Coppin wrote:
> >> 1. Is there some way to assign a "priority" to Haskell threads?
> >> (The behaviour I'd like is that high priority threads always run
> >> first, and low priorit
Miguel Mitrofanov schrieb:
> May be you can explain what do you want to do with this "monad"?
Pure educational purpose, just "learning by doing".
> What kind of code would you write if it would be such monad?
Useless stuff like:
s2 = do
push 11
push 17
co
[EMAIL PROTECTED] wrote:
> Albert Y. C. Lai writes:
>
> > Achim Schneider wrote:
> >> There is this story about some military (US afair) training a
> >> neural net to detect tanks in images
> ...
> > 50% accuracy.
>
> > I have some similar stories to tell
> >
> > A. ... students assumed
Spencer Janssen wrote:
> On Sun, Jan 06, 2008 at 11:30:53AM +, Andrew Coppin wrote:
>> 1. Is there some way to assign a "priority" to Haskell threads? (The
>> behaviour I'd like is that high priority threads always run first, and
>> low priority threads potentially never run at all unless there
Albert Y. C. Lai writes:
Achim Schneider wrote:
There is this story about some military (US afair) training a neural
net to detect tanks in images
...
50% accuracy.
I have some similar stories to tell
A. ... students assumed
sin(x+y) = sin(x) + sin(y)
B. ... But that day, that car, it
Achim Schneider wrote:
Erm...
There is this story about some military (US afair) training a neural
net to detect tanks in images, I can't find the link right now.
It worked, with amazing 100% accuracy.
Then they threw another batch of images at the net.
It worked, with devastating 50% accurac
andrewcoppin:
> Spencer Janssen wrote:
> >On Sun, Jan 06, 2008 at 11:30:53AM +, Andrew Coppin wrote:
> >
> >>Just a couple of things I was wondering about...
> >>
> >>1. Is there some way to assign a "priority" to Haskell threads? (The
> >>behaviour I'd like is that high priority threads alw
Peter Verswyvelen wrote:
> Jerzy wrote:
>> The relational syntax of Prolog is more "universal" than the functional
>> notation, since you have logic variables and logical-non-determinism, and
>
> Isn't this just because mathematically, a function *is* a relation, but
> not vice versa? A relation b
Spencer Janssen wrote:
On Sun, Jan 06, 2008 at 11:30:53AM +, Andrew Coppin wrote:
Just a couple of things I was wondering about...
1. Is there some way to assign a "priority" to Haskell threads? (The
behaviour I'd like is that high priority threads always run first, and low
priority th
ANNOUNCEMENT: Build fixed for regex-base, regex-posix, regex-compat, regex-pcre
The changes are mainly to the Cabal build files to support ghc-6.8 and ghc-6.6
simultaneously. They definitely work with cabal version 1.2.3.0 (required for
regex-pcre). The regex-base, regex-posix, and regex-comp
On Mon, Jan 07, 2008 at 09:27:17PM +0100, Peter Verswyvelen wrote:
> If your compiler (pretty amazing job btw) does whole program
> optimization, can it remove the dictionary (aka v-table in C/C++
> parlance?) overhead of type classes? Because if I understand it
> correctly, unless one uses existen
ChrisK wrote:
Could I has one question? What is the purpose of the "stream" function
in the ArrowLoop instance? Is it just to catch an unexpected [] at
runtime?
instance ArrowLoop SF where
loop (SF f) = SF $ \as ->
let (bs,cs) = unzip (f (zip as (stream cs))) in bs
where stre
Could I has one question? What is the purpose of the "stream" function in the
ArrowLoop instance? Is it just to catch an unexpected [] at runtime?
8<
module Main where
import Control.Arrow
import Control.Arrow.Operations
import Control.Arrow.Transformer.Reader
--
-- Standard list/st
On Monday 07 January 2008 20:27:17 Peter Verswyvelen wrote:
> If your compiler (pretty amazing job btw) does whole program optimization,
> can it remove the dictionary (aka v-table in C/C++ parlance?) overhead of
> type classes? Because if I understand it correctly, unless one uses
> existential ty
John Meacham wrote:
> I would like to move jhc to more of a 'link-time-code-generation' model
> though if I understand what you mean, right now jhc does a full
Yes, LTCG is Microsoft's terminology. See
http://msdn.microsoft.com/msdnmag/issues/02/05/Hood
> monolithic compilation which is pretty r
Wow, amazing :)
How long did it take you to write this little nice example? Examples like this
are really welcome. It will take me a while to decipher, but that's the fun of
Haskell, it's an endless learning experience!
Here's a thought: I hardly know Haskell, but I can already write some cod
On Tue, Jan 01, 2008 at 06:44:46PM +0100, Achim Schneider wrote:
> Peter Verswyvelen <[EMAIL PROTECTED]> wrote:
>
> > Another question regarding the backend: a cool feature of the
> > Microsoft Visual C++ (MVC) compiler is its ability to perform "LTCG"
> > (link-time-code-generation), performing
Yes. It's simply impossible. The Stack data type can't be turned
into a monad.
Why not? Surely this is just a variation on the theme of a state
monad?
Because it can't be turned into a functor. You can't, given a
function a -> b, construct a function Stack a -> Stack b. On the
contrast,
> It would seem that there would be three possible outcomes from an
> incremental Get:
> - Failure: some bitstreams are just invalid and no amount of extra
> data will ever fix that
> - Complete [Result]: the last chunk of data has been processed.
> Maybe this should also include the remainder
Derek Elkins <[EMAIL PROTECTED]> wrote:
> On Mon, 2008-01-07 at 18:21 +, Paul Johnson wrote:
> > Miguel Mitrofanov wrote:
> > >
> > > Yes. It's simply impossible. The Stack data type can't be turned
> > > into a monad.
> > Why not? Surely this is just a variation on the theme of a state
> > m
On Mon, 2008-01-07 at 18:21 +, Paul Johnson wrote:
> Miguel Mitrofanov wrote:
> >
> > Yes. It's simply impossible. The Stack data type can't be turned into
> > a monad.
> Why not? Surely this is just a variation on the theme of a state monad?
I somewhat explain in this reply:
http://www.hask
On Mon, 2008-01-07 at 17:24 +0100, Peter Verswyvelen wrote:
> Derek Elkins wrote:
> > Implicit parameters add an extra argument to a function conceptually.
> > What you need is to "add an argument" to "SF" which implicit parameters
> > don't know how to do since SF is just some data structure. One
On Mon, 2008-01-07 at 18:15 +0300, Miguel Mitrofanov wrote:
> > data Stack a = Stack { run :: [a] -> (a, [a]) }
>
> [...skipped...]
>
> > But, I have simply no clue how to fix that. :-(
> > Can anybody give my a hint?
>
> Yes. It's simply impossible. The Stack data type can't be turned into
On Jan 6, 2008 9:13 PM, Bryan O'Sullivan <[EMAIL PROTECTED]> wrote:
> Ooh, nice. We could really do with an incremental version, too, which
> could be spoonfed chunks of bytes, and dole out values as
> deserialisation completes.
>
> Passing back a Left String is in some sense not much of an improv
Miguel Mitrofanov wrote:
Yes. It's simply impossible. The Stack data type can't be turned into
a monad.
Why not? Surely this is just a variation on the theme of a state monad?
Paul.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www
Peter Verswyvelen wrote:
Derek Elkins wrote:
you can
use an equivalent Reader/Environment arrow transformer.
Nice, I did not know that monad yet, thanks!
But can it be combined together with the arrows do/proc syntax? How
would that look like?
Something like this?
8<
module M
On Sun, Jan 06, 2008 at 11:30:53AM +, Andrew Coppin wrote:
> Just a couple of things I was wondering about...
>
> 1. Is there some way to assign a "priority" to Haskell threads? (The
> behaviour I'd like is that high priority threads always run first, and low
> priority threads potentially ne
Derek Elkins wrote:
Implicit parameters add an extra argument to a function conceptually.
What you need is to "add an argument" to "SF" which implicit parameters
don't know how to do since SF is just some data structure. One way to
deal with this is the way you deal with the same problem in Hask
On Mon, 7 Jan 2008, Miguel Mitrofanov wrote:
> > data Stack a = Stack { run :: [a] -> (a, [a]) }
>
> [...skipped...]
>
> > But, I have simply no clue how to fix that. :-(
> > Can anybody give my a hint?
>
> Yes. It's simply impossible. The Stack data type can't be turned into
> a monad.
What
data Stack a = Stack { run :: [a] -> (a, [a]) }
[...skipped...]
But, I have simply no clue how to fix that. :-(
Can anybody give my a hint?
Yes. It's simply impossible. The Stack data type can't be turned into
a monad.
May be you can explain what do you want to do with this "mona
Michael Roth wrote:
Hello list,
while trying to learn the secrets of monads, I decided to write a simply
monand for pure educational purpose. But it turned out that it isn't as
easy as I thought... I circumnavigate quite a number of hurdles but now
I reached a point where I'm at a loss. :-(
Th
On 2008.01.07 07:20:05 -0600, Austin Seipp <[EMAIL PROTECTED]> scribbled 2.6K
characters:
> > I recently tried the latest version of HS-PLUGINS, and it gave an error on
> > Windows. After a bit of Googling it seemed Conal Elliot had the same
> > problem. I reported this problem to the author. This
Michael Roth wrote:
while trying to learn the secrets of monads, I decided to write a simply
monand for pure educational purpose. But it turned out that it isn't as
easy as I thought... I circumnavigate quite a number of hurdles but now
I reached a point where I'm at a loss. :-(
data Sta
The only possible definition of such a function is something like
unsafeShow :: (forall a . Show a => a) -> String
unsafeShow a = show (a :: Bool)
right?
And you'd also need to coerce the argument type in order to use it:
putStrLn $ unsafeShow $ unsafeCoerce True
Right?
Then a nicer de
Cetin Sert wrote:
class Streamable a where
to :: a -> Stream a
The type of to looks wrong for me. a -> Stream a means to takes a single
element into a stream of such elements, but you probably want to convert
between different representations of streams of elements.
toStream :: [a] -> St
Hello list,
while trying to learn the secrets of monads, I decided to write a simply
monand for pure educational purpose. But it turned out that it isn't as
easy as I thought... I circumnavigate quite a number of hurdles but now
I reached a point where I'm at a loss. :-(
The source:
#!
> I recently tried the latest version of HS-PLUGINS, and it gave an error on
> Windows. After a bit of Googling it seemed Conal Elliot had the same
> problem. I reported this problem to the author. This is also (one of) the
> reason why I could not get YI running on Windows.
Currently I believe C
Hi,
I'm new to Haskell programming and have the following problem.
-
(|>) f g = g f
data Stream a where
S :: (s -> Step s a) -> s -> Stream a
data Step s a = Done | Yield a s | Skip a s
toStream :: [a] -> Stream a
toStream ax = S step ax
* Henning Thielemann wrote:
> happen. Paradoxical. It would be interesting if it is possible to tunnel
> Show class dictionaries through to an 'error' like IO is tunneled to
> 'trace'.
unsafeShow :: (forall a . Show a => a) -> String
___
Haskell-Cafe mai
Brian Park wrote:
> Hi,
>
> I was installing various haskell packages from hackage.
>
> When I was installing HaXml, I think it was complaining about
> Text.PrettyPrint.HughesPJ not installed or something. (can't remember
> the specific message and I can't reproduce now...)
HaXml-1.13.2 needs pr
On Thu, 3 Jan 2008, Don Stewart wrote:
> You can, with some caveats, use a single fusion system across data
> structures, and avoid the built in build/foldr system.
>
> I'd start by installing the stream-fusion list library, from hackage,
> which gives you the list api, and a fusion mechanism.
>
On Mon, 7 Jan 2008, Emil Axelsson wrote:
> One approach to programming in Haskell, which I use all the time, is to write
> the type signature before the function body. This means that if I'm trying to
> do
> something strange, I will often be warned by the type checker even before I've
> written
Andrew Coppin wrote:
2. You have to take the data out of an MVar to read it. In other words,
only 1 thread can read an MVar at once [by design]. This isn't truly a
problem in the current case, but it's irritating in principle that I
can't make it so that once the cell is written, multiple threa
One approach to programming in Haskell, which I use all the time, is to write
the type signature before the function body. This means that if I'm trying to do
something strange, I will often be warned by the type checker even before I've
written the strange code.
But I've also been bitten by t
Hello Bob,
Sunday, January 6, 2008, 3:45:42 AM, you wrote:
> You are wrong. Without type signatures some type errors will not be
> caught by the compiler, resulting in erroneous program behaviour.
of course. moreover, the same applies to any type inference. are you
give explicit type signature t
51 matches
Mail list logo