[Haskell-cafe] Big endian vs little endian in Haskell land?

2009-01-21 Thread Galchin, Vasili
Hello,

Are there applications that have to deal with both(!!!) big endian
and little endian on persistent store?? I.e. when marshalling out and
unmarshalling in "endian-ness" has to be considered??

Regards, Vasili
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why monoids will abide...

2009-01-21 Thread Eugene Kirpichov
To my mind, in the map-reduce case you generally need a commutative
monoid. Or, you need an extra infrastructure that mappend's only
results from adjacent machines, or something like that.

2009/1/21 Dan Piponi :
> Another important application of monoids is in parallelisation. In
> map-reduce you want to split the reduce part over multiple processors
> and combine the results back together again. Associativity ensures
> that when you combine the pieces together you get the same result as
> if you did the whole operation on one processor.
>
> Eg. we can rewrite
>
> (((a `mappend` b) `mappend` c) `mappend` d
>
> as
>
> (a `mappend` b) `mappend` (c `mappend` d)
>
> and compute (a `mappend` b) and (c `mappend` d) on separate
> processors. And so on recursively. (The mempty element tells us what
> result we should give if we're reducing an empty array.)
>
> For a large class of problems, parallelising the algorithm consists of
> teasing out the hidden monoid structure so it can be chopped up in
> this way.
> --
> Dan
>
> On Tue, Jan 20, 2009 at 4:27 PM, Don Stewart  wrote:
>> http://apfelmus.nfshost.com/monoid-fingertree.html
>>
>> Thanks Apfelmus for this inspiring contribution!
>> ___
>> 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: tensor product of dynamic-sized bits

2009-01-21 Thread Ahn, Ki Yung
Ahn, Ki Yung 쓴 글:
> 
>> reduce (Bs (x:xs)) | all (x==) xs = x
>> reduce (Rep x@(Rep _)) = x
>> reduce x   = x

I already found a bug. The second equation of reduce
"reduce (Rep x@(Rep _)) = x" is wrong because it flattens
two dimensions into one. The reduce function should be:

> reduce x = x
> reduce (Bs (x:xs)) | all (x==) xs = reduce x
> reduce (Bs xs) = Bs (map reduce xs)
> reduce (Rep O) = O
> reduce (Rep I) = I
> reduce (Rep x) = Rep (reduce x)
> reduce x   = x

This is why I am looking for existing work, because I am
not yet very sure about my code I'm using.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to implement daemon start and stop directives?

2009-01-21 Thread Luke Palmer
On Wed, Jan 21, 2009 at 11:36 PM, Belka  wrote:
>
> Hi!
>
> Could somebody please share some experience on how to implement daemon
> start
> and stop directives. In theory I need something like this:
> 1. "my_daemon start" - starts my app with an infinite loop of serving
> inside.
> 2. "my_daemon stop" - puts in some TVar a value signalizing, that stop is
> given - infinite loop brakes.


You can abstract this pattern:

-- runs its argument in an infinite loop, and returns an action that stops
the loop
daemon :: IO () -> IO (IO ())
daemon action = do
stopvar <- atomically $ newTVar False
let run = do
  stop <- atomically $ readTVar stopvar
  if stop then return () else (action >> run)
forkIO run
return (atomically $ writeTVar stopvar True)

TVars are overkill here, actually, an IORef would be just fine, I think.

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] how to implement daemon start and stop directives?

2009-01-21 Thread Belka

Hi!

Could somebody please share some experience on how to implement daemon start
and stop directives. In theory I need something like this:
1. "my_daemon start" - starts my app with an infinite loop of serving
inside.
2. "my_daemon stop" - puts in some TVar a value signalizing, that stop is
given - infinite loop brakes.
3. ...it on Linux platform.

Thanks in advance!
-- 
View this message in context: 
http://www.nabble.com/how-to-implement-daemon-start-and-stop-directives--tp21598690p21598690.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] tensor product of dynamic-sized bits

2009-01-21 Thread Ahn, Ki Yung
For some reasons, I am trying to write a small Haskell code for tensor
products (See http://en.wikipedia.org/wiki/Tensor_product) of bits,
which can expand or shrink their size and dimension as needed.

Has anyone already done similar or more general work before? If so, I'd
be happy use/consult that and cite the work. Otherwise, I should think
about cleaning up and packaging this as a library. My code is like this
right now:

> data Bits = O -- all 1 bits of any size and dimension
>   | I -- all 0 bits of any size and dimension
>   | Bs [Bits] -- row of bits possibly nested
>   | Rep Bits  -- repeating of bits (e.g. O = Rep O = Bs [O,O])
>   deriving (Eq,Show)

bitwise-and

> O   .& _   = O
> _   .& O   = O
> (Rep O) .& _   = O
> _   .& (Rep O) = O
> (Bs (O:xs)) .& _   | all (O==) xs  = O
> _   .& (Bs (O:xs)) | all (O==) xs  = O
> I   .& y   = y
> x   .& I   = x
> (Rep I) .& y   = y
> x   .& (Rep I) = x
> (Bs (I:xs)) .& y   | all (I==) xs  = y
> x   .& (Bs (I:ys)) | all (I==) ys  = x
> (Bs xs) .& (Bs ys) = reduce $ Bs (zipWith (.&) xs ys)
> (Rep x) .& (Bs ys) = reduce $ Bs (xs .&. ys) where xs=repeat x
> (Bs xs) .& (Rep y) = reduce $ Bs (xs .&. ys) where ys=repeat y
> (Rep x) .& (Rep y) = reduce $ Rep (x .& y)
>
> (.&.) = zipWith (.&)

bitwise-or

> O   .| y   = y
> x   .| O   = x
> (Rep O) .| y   = y
> x   .| (Rep O) = x
> (Bs (O:xs)) .| y   | all (O==) xs  = y
> x   .| (Bs (O:ys)) | all (O==) ys  = x
> I   .| _   = I
> _   .| I   = I
> (Rep I) .| _   = I
> _   .| (Rep I) = I
> (Bs (I:xs)) .| _   | all (I==) xs  = I
> _   .| (Bs (I:ys)) | all (I==) ys  = I
> (Bs xs) .| (Bs ys) = reduce $ Bs (xs .|. ys)
> (Rep x) .| (Bs ys) = reduce $ Bs (xs .|. ys) where xs=repeat x
> (Bs xs) .| (Rep y) = reduce $ Bs (xs .|. ys) where ys=repeat y
> (Rep x) .| (Rep y) = reduce $ Rep (x .| y)
>
> (.|.) = zipWith (.|)

tensor product

> O   .* _   = O
> _   .* O   = O
> (Rep O) .* _   = O
> _   .* (Rep O) = O
> (Bs (O:xs)) .* _   | all (O==) xs  = O
> _   .* (Bs (O:ys)) | all (O==) ys  = O
> I   .* I   = I
> I   .* (Rep y) = I .* y
> (Rep I) .* y   = I .* y
> (Bs (I:xs)) .* y   | all (I==) xs  = I .* y
> I   .* y   = reduce $ Rep y
> x   .* (Rep I) = x .* I
> x   .* (Bs (I:xs)) | all (I==) xs  = x .* I
> x   .* I   = x
> (Bs xs) .* (Bs ys) = reduce $ Bs (xs .*. ys)
> (Bs xs) .* (Rep y) = reduce $
>  Bs (map (reduce . Rep) $ xs .*. [y])
> (Rep x) .* y   = reduce $ Rep (x .* y)
>
> [] .*. _  = []
> (x:xs) .*. ys = (reduce $ Bs [x .* y | y<-ys]) : (xs .*. ys)

reducing  from Bs [O,O,..] to O and from Bs [I,I,..] to I

> reduce (Bs (x:xs)) | all (x==) xs = x
> reduce (Rep x@(Rep _)) = x
> reduce x   = x

Some example run on Hugs:

Main> Bs [I,O]

Bs [I,O]

Main> Bs [I,O] .| Bs [O,Bs [I,I,I,I] .* Bs [I,O,O,O,O]]

Bs [I,Rep (Bs [I,O,O,O,O])]

Main> Bs [I,O] .| Bs [O, Bs [I,I,I,I] .* Bs [I,O,O,O,O]]
   .| Bs [O, Bs [I,O,O,O] .* Bs [I,I,I,I,I]]

Bs [I,Bs [I,Bs [I,O,O,O,O],Bs [I,O,O,O,O],Bs [I,O,O,O,O]]]

Main> Bs [I,O] .| Bs [O, Bs [I,I,I,I] .* Bs [I,O,O,O,O]]
   .| Bs [O, Bs [I,O,O,O] .* Bs [I,I,I,I,I]]
   .| Bs [O, Bs [O,I,I,O] .* Bs [O,I,I,O,O]]

Bs [I,Bs [I,Bs [I,I,I,O,O],Bs [I,I,I,O,O],Bs [I,O,O,O,O]]]

Main> Bs [I,O] .| Bs [O, Bs [I,I,I,I] .* Bs [I,O,O,O,O]]
   .| Bs [O, Bs [I,O,O,O] .* Bs [I,I,I,I,I]]
   .| Bs [O, Bs [O,I,I,O] .* Bs [O,I,I,O,O]]
   .| Bs [O, Bs [O,I,I,I] .* Bs [O,O,O,I,I]]

Bs [I,Bs [I,I,I,Bs [I,O,O,I,I]]]

Main> Bs [I,O] .| Bs [O, Bs [I,I,I,I] .* Bs [I,O,O,O,O]]
   .| Bs [O, Bs [I,O,O,O] .* Bs [I,I,I,I,I]]
   .| Bs [O, Bs [O,I,I,O] .* Bs [O,I,I,O,O]]
   .| Bs [O, Bs [O,I,I,I] .* Bs [O,O,O,I,I]]
   .| Bs [O, Bs [O,O,I,I] .* Bs [O,I,I,O,O]]

I

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 1000 libraries

2009-01-21 Thread wirtwolff

Don Stewart wrote:

We've done it!

http://hackage.haskell.org/cgi-bin/hackage-scripts/stats
274 users have uploaded 3161 versions of 1000 packages. 




Now, onto 10k libraries!

-- Don

  


What about the 1024th package? That should be properly honored as well. ;-)

-- ww
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Improved documentation for Bool

2009-01-21 Thread Richard O'Keefe


On 20 Jan 2009, at 8:33 am, Andrew Coppin wrote:


rocon...@theorem.ca wrote:
I noticed the Bool datatype isn't well documented.  Since Bool is  
not a common English word, I figured it could use some haddock to  
help clarify it for newcomers.


My only problem with it is that it's called Bool, while every other  
programming language on Earth calls it Boolean.



(Or at least, the languages that *have* a name for it...)


Algol 68, C99, C++, C#, Standard ML, OCAML, F#, Clean

all use 'bool', not 'Boolean'.  Of course if you want to go
for historical priority, that'd be Fortran's LOGICAL type...

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GLUT (glutGet undefined reference)

2009-01-21 Thread Kazuya Sakakihara
Check this thread:
http://groups.google.com/group/fa.haskell/browse_thread/thread/1716fa5e5643541e/38373ec65e2537fd?lnk=gst

Kazuya

2009/1/20 Paul Keir :
> Hi all,
>
> I was hoping to introduce my old pal OpenGL
> with my new chum, Haskell. I used cabal to
> install GLUT on my 64-bit Ubuntu machine with
> GHC 6.8.2 (installed via apt-get/synaptic).
>
> I followed the wiki OpenGLTutorial1 until:
> ghc -package GLUT HelloWorld.hs -o HelloWorld
> at which point my screen is filled with errors.
> The errors begin with:
>
> /home/paul/.cabal/lib/GLUT-2.1.1.2/ghc-6.8.2/libHSGLUT-2.1.1.2.a(Begin.o):
> In function `szEn_info':
> (.text+0x26c): undefined reference to `glutGet'
>
> This surprised me a little because I've already
> seen these same errors recently on two separate
> Windows boxes. Somehow I'd got the idea it was
> (on Windows) due to installing from a binary; though
> I guess the story is the same with apt-get. Should
> I look for an apt-get switch to reinstall GHC from
> source instead?
>
> Regards,
> Paul
>
>
> ___
> 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: Does readFile "/proc/mounts" hang for you?

2009-01-21 Thread Thomas DuBuisson
Strace tells me that its doing some crazy IO control:

"""
...
open("/proc/mounts", O_RDONLY|O_NOCTTY|O_NONBLOCK) = 3
fstat(3, {st_mode=S_IFREG|0444, st_size=0, ...}) = 0
ioctl(3, SNDCTL_TMR_TIMEBASE or TCGETS, 0x77470b70) = -1 ENOTTY
(Inappropriate ioctl for device)
select(4, [3], [], NULL, {0, 0})= 0 (Timeout)
select(4, [3], [], NULL, {134, 217727} 
"""

I'm too rusty on any sort of low level work to draw meaning out of
this without work, but...

See that failed ioctl that seems to be completely ignored, right
before hanging in our 'select' call?
And see the select call that says 'wait 134 seconds'?  If you wait it
out you get:

select(4, [3], [], NULL, {134, 217727}

... so its a loop that I doubt you'll exit.

Tom

On Wed, Jan 21, 2009 at 2:43 PM, Krzysztof Skrzętnicki  wrote:
> Same for me:
> Linux tenserwer 2.6.28-ARCH #1 SMP PREEMPT Tue Jan 6 10:26:22 UTC 2009
> i686 AMD Athlon(tm) 64 Processor 3000+ AuthenticAMD GNU/Linux
> The Glorious Glasgow Haskell Compilation System, version 6.10.1
>
> All best
>
> Christopher Skrzętnicki
>
> On Wed, Jan 21, 2009 at 23:27, Ertugrul Soeylemez  wrote:
>> David Fox  wrote:
>>
>>> I posted a bug about this
>>> (http://hackage.haskell.org/trac/ghc/ticket/2971) but its so odd I had
>>> to ask here.  Using ghc 6.10.1, both readFile "/proc/mounts" and
>>> Data.ByteString.Lazy.Char8.readFile "/proc/mounts" hang on an amd64
>>> machine running Linux.  Also, Data.ByteString.readFile "/proc/mounts"
>>> returns the empty string.  Is this behavior present for others?  On
>>> i386?
>>
>> I can confirm this on Athlon64 X2 with GHC 6.10.1 running Linux 2.6.25.
>> Same behavior here.
>>
>>
>> Greets,
>> Ertugrul.
>>
>>
>> --
>> nightmare = unsafePerformIO (getWrongWife >>= sex)
>> http://blog.ertes.de/
>>
>>
>> ___
>> 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Why monoids will abide...

2009-01-21 Thread Lennart Augustsson
You're too late, they already have guru status. :)

On Wed, Jan 21, 2009 at 11:09 PM, Andrzej Jaworski
 wrote:
> Let me also suggest to bestow the official  guru status on Dan Piponi and
> Heinrich Apfelmus:-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Why monoids will abide...

2009-01-21 Thread Andrzej Jaworski

Category Theory should speak for itself and I am so glad you guys have seen the 
beauty of this
approach.

Yes, Mauro you are right: locally small Freyd categories correspond to monoidal 
structure of Arrows,
but the strength in this correspondence is as yet unknown to me. I disagree 
however with your doubts:
Arrows indeed are Monoids! [in the functor category (C^op) x C -> C with st, 
cost, ist.]

I will skip Monoid ubiquity in linguistics and its relevance to concurrency as 
not helpful in
learning Haskell.
(e.g. 
http://www.springerlink.com/content/7281243255312730/?p=4dd8bba881cd4ebe894d3b014f01b1ad&pi=7)

Instead I will issue a guarantee that the time invested in CT will pay also in 
system analysis,
particularly in combination with Haskell type classes, which together might be 
used for describing
real world processes and knowledge. Few have scratched the subject as yet but 
the pay-off is huge.

Let me also suggest to bestow the official  guru status on Dan Piponi and 
Heinrich Apfelmus:-)

Cheers,
-Andrzej

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Does readFile "/proc/mounts" hang for you?

2009-01-21 Thread Krzysztof Skrzętnicki
Same for me:
Linux tenserwer 2.6.28-ARCH #1 SMP PREEMPT Tue Jan 6 10:26:22 UTC 2009
i686 AMD Athlon(tm) 64 Processor 3000+ AuthenticAMD GNU/Linux
The Glorious Glasgow Haskell Compilation System, version 6.10.1

All best

Christopher Skrzętnicki

On Wed, Jan 21, 2009 at 23:27, Ertugrul Soeylemez  wrote:
> David Fox  wrote:
>
>> I posted a bug about this
>> (http://hackage.haskell.org/trac/ghc/ticket/2971) but its so odd I had
>> to ask here.  Using ghc 6.10.1, both readFile "/proc/mounts" and
>> Data.ByteString.Lazy.Char8.readFile "/proc/mounts" hang on an amd64
>> machine running Linux.  Also, Data.ByteString.readFile "/proc/mounts"
>> returns the empty string.  Is this behavior present for others?  On
>> i386?
>
> I can confirm this on Athlon64 X2 with GHC 6.10.1 running Linux 2.6.25.
> Same behavior here.
>
>
> Greets,
> Ertugrul.
>
>
> --
> nightmare = unsafePerformIO (getWrongWife >>= sex)
> http://blog.ertes.de/
>
>
> ___
> 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] Applicative/Monad for Either

2009-01-21 Thread Ryan Ingram
I think it's possible, but not in a very clean way.

First lets look at ap:

> ap mf mx = do
>   f <- mf
>   x <- mx
>   return (f x)

equivalently, desugared:

> ap mf mx = mf >>= \f -> mx >>= \x -> return (f x)

So, it's possible to make a definition of >>= where "ap" works as you like:

>Z (Left e1) >>= f = case f (error "urk") of
>Z (Left e2) -> Z (Left (mappend e1 e2))
>Z (Right _) -> Z (Left e1)
>Z (Right a) >>= f = f a

(Does this definition of >>= break any of the monad laws?  I can't see
where it does, but I haven't proved that it doesn't.)

Now "ap" will reduce how you want, but monadic (non-applicative)
computations like this have a problem:

> throw :: e -> Z e a
> throw e = Z (Left e)
> urk = throw "uhoh" >>= \b -> if b then return "ok" else throw "urk"

In order to determine whether the constructor on the right of >>= is
"Left" or "Right", we need to examine the value from the left of >>=.
But there is no value there; it's _|_.

So I don't think there's a way to make this into a particularily safe
to use monad, if you require the law "(<*>) = ap"

  -- ryan

On Wed, Jan 21, 2009 at 2:03 PM, Tony Morris  wrote:
> -BEGIN PGP SIGNED MESSAGE-
> Hash: SHA1
>
> In the code below, the Applicative instance accumulates on the Left
> constructor using Monoid/mappend.
> Is it possible to write an equivalent Monad such that ap = (<*>) ? I'm
> finding difficulty in proving to myself either way.
>
>
>
>
> import Control.Monad.Instances
> import Control.Applicative
> import Data.Monoid
>
> newtype Z e a = Z {
>  either :: Either e a
> }
>
> instance Functor (Z e) where
>  fmap f (Z e) = Z (f `fmap` e)
>
> instance (Monoid e) => Applicative (Z e) where
>  pure = Z . Right
>  (Z (Left e1)) <*> (Z (Left e2)) = Z (Left (e1 `mappend` e2))
>  (Z (Left e1)) <*> (Z (Right _)) = Z (Left e1)
>  (Z (Right _)) <*> (Z (Left e2)) = Z (Left e2)
>  (Z (Right f)) <*> (Z (Right a)) = Z (Right (f a))
>
> instance (Monoid e) => Monad (Z e) where
>  return = pure
>  (Z e) >>= f = error "todo" -- ?
>
> - --
> Tony Morris
> http://tmorris.net/
>
> S, K and I ought to be enough for anybody.
>
> -BEGIN PGP SIGNATURE-
> Version: GnuPG v1.4.6 (GNU/Linux)
> Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org
>
> iD8DBQFJd5vImnpgrYe6r60RAoUNAJ4jn0GfC6zsP9giPGop1ILExiHrLQCfSoc2
> 0QXf533sWb3HyrL0pQNjMww=
> =R36O
> -END PGP SIGNATURE-
>
> ___
> 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: Does readFile "/proc/mounts" hang for you?

2009-01-21 Thread Ertugrul Soeylemez
David Fox  wrote:

> I posted a bug about this
> (http://hackage.haskell.org/trac/ghc/ticket/2971) but its so odd I had
> to ask here.  Using ghc 6.10.1, both readFile "/proc/mounts" and
> Data.ByteString.Lazy.Char8.readFile "/proc/mounts" hang on an amd64
> machine running Linux.  Also, Data.ByteString.readFile "/proc/mounts"
> returns the empty string.  Is this behavior present for others?  On
> i386?

I can confirm this on Athlon64 X2 with GHC 6.10.1 running Linux 2.6.25.
Same behavior here.


Greets,
Ertugrul.


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://blog.ertes.de/


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Applicative/Monad for Either

2009-01-21 Thread Daniel Fischer
Am Mittwoch, 21. Januar 2009 23:03 schrieb Tony Morris:
> -BEGIN PGP SIGNED MESSAGE-
> Hash: SHA1
>
> In the code below, the Applicative instance accumulates on the Left
> constructor using Monoid/mappend.
> Is it possible to write an equivalent Monad such that ap = (<*>) ? I'm
> finding difficulty in proving to myself either way.
>
>
>
>
> import Control.Monad.Instances
> import Control.Applicative
> import Data.Monoid
>
> newtype Z e a = Z {
>   either :: Either e a
> }
>
> instance Functor (Z e) where
>   fmap f (Z e) = Z (f `fmap` e)
>
> instance (Monoid e) => Applicative (Z e) where
>   pure = Z . Right
>   (Z (Left e1)) <*> (Z (Left e2)) = Z (Left (e1 `mappend` e2))
>   (Z (Left e1)) <*> (Z (Right _)) = Z (Left e1)
>   (Z (Right _)) <*> (Z (Left e2)) = Z (Left e2)
>   (Z (Right f)) <*> (Z (Right a)) = Z (Right (f a))
>
> instance (Monoid e) => Monad (Z e) where
>   return = pure
>   (Z e) >>= f = error "todo" -- ?
>

I think

Z (Left e) >>= f = Z (Left e)
Z (Right a) >>= f = f a

would be the only choice.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Applicative/Monad for Either

2009-01-21 Thread Tony Morris
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

In the code below, the Applicative instance accumulates on the Left
constructor using Monoid/mappend.
Is it possible to write an equivalent Monad such that ap = (<*>) ? I'm
finding difficulty in proving to myself either way.




import Control.Monad.Instances
import Control.Applicative
import Data.Monoid

newtype Z e a = Z {
  either :: Either e a
}

instance Functor (Z e) where
  fmap f (Z e) = Z (f `fmap` e)

instance (Monoid e) => Applicative (Z e) where
  pure = Z . Right
  (Z (Left e1)) <*> (Z (Left e2)) = Z (Left (e1 `mappend` e2))
  (Z (Left e1)) <*> (Z (Right _)) = Z (Left e1)
  (Z (Right _)) <*> (Z (Left e2)) = Z (Left e2)
  (Z (Right f)) <*> (Z (Right a)) = Z (Right (f a))

instance (Monoid e) => Monad (Z e) where
  return = pure
  (Z e) >>= f = error "todo" -- ?

- --
Tony Morris
http://tmorris.net/

S, K and I ought to be enough for anybody.

-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFJd5vImnpgrYe6r60RAoUNAJ4jn0GfC6zsP9giPGop1ILExiHrLQCfSoc2
0QXf533sWb3HyrL0pQNjMww=
=R36O
-END PGP SIGNATURE-

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haddock bug for strict unpacked fields?

2009-01-21 Thread Johan Tibell
On Wed, Jan 21, 2009 at 8:54 PM, David Waern  wrote:
> Perhaps we should not display unbox annotations at all since they are
> an implementation detail, right? We could display one "!" instead,
> indicating that the argument is strict.

Yes. I think that's enough.

Cheers,

Johan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Existencial quantification and polymorphic datatypes (actually, components...)

2009-01-21 Thread Jake McArthur

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Jonathan Cast wrote:
| I think you meant to quote the definition
|
| data SomeNum = forall a. SN a

Quite so. Thanks for clearing that up.

- - Jake
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.9 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iEYEARECAAYFAkl3gr8ACgkQye5hVyvIUKmiDgCfeH8fEn0+iDEMlQwtCHtMXAti
vSoAnAwYibedZTR1YyzrcC0OTspXsjMX
=Vagv
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Existencial quantification and polymorphic datatypes (actually, components...)

2009-01-21 Thread Jonathan Cast
On Wed, 2009-01-21 at 13:38 -0600, Jake McArthur wrote:
> -BEGIN PGP SIGNED MESSAGE-
> Hash: SHA1
> 
> Gleb Alexeyev wrote:
> | Mauricio wrote:
> |
> |> data SomeNum = SN (forall a. a)
> |
> | [...]
> |
> | you cannot do anything to the value you extract
> 
> Maybe. Say you construct (SN x). If you later extract x, you can observe
> that it terminates (using seq, perhaps), assuming that it does
> terminate.

The definition you quoted is equivalent to

data SomeNum where
  SN :: (forall a. a) -> SomeNum

So if I say

  case y of
SN x -> ...

Then in the sequel (...) I can use x at whatever type I want --- it's
polymorphic --- but whatever type I use it at, it cannot terminate.

I think you meant to quote the definition

data SomeNum = forall a. SN a

which is equivalent to

data SomeNum where
  SN :: forall a. a -> SomeNum

in which case if I say

  case y of
SN x -> ...

then x is a perfectly monomorphic value, whose type happens to be a
(fresh) constant distinct from all other types in the program.  So I
can't do anything useful with x, although as you say, it can be forced
with seq.  OTOH, you could do exactly the same thing with a normal
judgment of type (), if you found a use for it.

jcc


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haddock bug for strict unpacked fields?

2009-01-21 Thread David Waern
2009/1/21 Stephan Friedrichs :
> Hi,
>
> using haddock-2.4.1 and this file:
>
>> module Test where
>>
>> data Test
>> = NonStrict Int
>> | Strict !Int
>> | UnpackedStrict {-# UNPACK #-} !Int
>
> The generated documentation looks like this:
>
> data Test
> Constructors
>  NonStrict Int
>  Strict !Int
>  UnpackedStrict !!Int
>
> Note the double '!' in the last constructor. This is not intended
> behaviour, is it?

This is the way GHC pretty prints unboxed types, so I thought Haddock
should follow the same convention. Hmm, perhaps Haddock should have a
chapter about language extensions in its documentation, with a
reference to the GHC documentation. That way the language used is at
least documented. Not sure if it helps in this case though, since "!!"
is probably not documented there.

Perhaps we should not display unbox annotations at all since they are
an implementation detail, right? We could display one "!" instead,
indicating that the argument is strict.

David
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: 1000 libraries

2009-01-21 Thread Ahn, Ki Yung

Don Stewart wrote:

We've done it!


Thanks for the good news.

Maybe it's already getting more important organizing existing uesful set 
of libraries as mata-packages. Are there updates on haskell-platform?


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Existencial quantification and polymorphic datatypes (actually, components...)

2009-01-21 Thread Jake McArthur

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Gleb Alexeyev wrote:
| Mauricio wrote:
|
|> data SomeNum = SN (forall a. a)
|
| [...]
|
| you cannot do anything to the value you extract

Maybe. Say you construct (SN x). If you later extract x, you can observe
that it terminates (using seq, perhaps), assuming that it does
terminate. You still can't really do anything with the value, but you
can at least observe something about its computation. The uses of this
may be obscure (I can't think of any right now), but I wouldn't say they
necessarily don't exist.

- - Jake
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.9 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iEYEARECAAYFAkl3eb8ACgkQye5hVyvIUKnGZgCcDvZKVmqcwjdx97MkPu3I5r3n
KsUAn0IlCTwyCH5h5QTyDPvM1MkX36Hz
=Ocgm
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] haskell-src-meta Package

2009-01-21 Thread Matt Morrow
Hi,

I managed to miss not one, but two separate emails containing patches to
haskell-src meta. My sincere apologies to those who've sent me patches.
I'll be applying them among other improvement to src-meta and will update
the package on hackage in short time (today :).

Matt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] (no subject)

2009-01-21 Thread Matt Morrow
Hi,

I managed to miss not one, but two separate emails containing patches to
haskell-src meta. My sincere apologies to those who've sent me patches.
I'll be applying them among other improvement to src-meta and will update
the package on hackage in short time (today :).

Matt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] 1000 libraries

2009-01-21 Thread Don Stewart
We've done it!

http://hackage.haskell.org/cgi-bin/hackage-scripts/stats
274 users have uploaded 3161 versions of 1000 packages. 

Thanks everyone who has written a library or tool or app and released
it, for making hackage and cabal a success!

This has gone further, perhaps more than anything else, towards making
it possible to use Haskell in industry.

The lucky 1000th package is:

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/threadPool-0.1
threadPool: Runs other programs in the manner of a thread pool

Takes a single, optional argument which is the number of threads
(the default is three). Give it the commands to run, one per line,
through standard input. 

Author  Brian Jaress

Now, onto 10k libraries!

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haddock bug for strict unpacked fields?

2009-01-21 Thread Stephan Friedrichs
Hi,

using haddock-2.4.1 and this file:

> module Test where
>
> data Test
> = NonStrict Int
> | Strict !Int
> | UnpackedStrict {-# UNPACK #-} !Int

The generated documentation looks like this:

data Test
Constructors
  NonStrict Int
  Strict !Int
  UnpackedStrict !!Int

Note the double '!' in the last constructor. This is not intended
behaviour, is it?

//Stephan


-- 

Früher hieß es ja: Ich denke, also bin ich.
Heute weiß man: Es geht auch so.

 - Dieter Nuhr
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] haskell-src-meta Package

2009-01-21 Thread George Giorgidze
Hi,

In my project I needed a function that would parse a string into a
template-haskell AST representing the Haskell expression. To be more
precise I needed a function with the following type signature.

:: String -> Either String Language.Haskell.TH.Syntax.Exp

This kind of function should exist in the implementation of
template-haskell, however it is not exported for public consumption
from template-haskell package.

There is haskell-src-exts package that provides a Haskell expression
parser however it uses its own Exp data type which differs from the
template haskell representation Exp.

After that, I found haskell-src-meta package that provided the
function I needed:

parseExp :: String -> Either String TH.Exp

This function uses parser from  haskell-src-exts package and after
that translates returned Exp representation into the template-haskell
representation of Exp.

So problem has been solved. However, In the light of recent changes
and enhancements in the haskell-src-exts, haskell-src-meta package on
Hackage is broken. I have fixed the broken package and contacted its
author and maintainer (Matt Morrow). However, he did not reply.

I have a number of questions:

Was the use of haskell-src-meta really neccessary, I mean, is there
any other package that provides the functionality of aforementioned
parseExp function?
Can I upload the fixed version of haskell-src-meta package to Hackage
and assume its maintenance while Matt Morrow is silent?
Does anyone know how to contact Matt Morrow? His is not replying on my
emails sent to the email address specified in the package description.
The thing is that I do not want my package to be dependent on a
package that is broken on Hackage.

Cheers, George

-- 
George Giorgidze
http://www.cs.nott.ac.uk/~ggg/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why monoids will abide...

2009-01-21 Thread Dan Piponi
Another important application of monoids is in parallelisation. In
map-reduce you want to split the reduce part over multiple processors
and combine the results back together again. Associativity ensures
that when you combine the pieces together you get the same result as
if you did the whole operation on one processor.

Eg. we can rewrite

(((a `mappend` b) `mappend` c) `mappend` d

as

(a `mappend` b) `mappend` (c `mappend` d)

and compute (a `mappend` b) and (c `mappend` d) on separate
processors. And so on recursively. (The mempty element tells us what
result we should give if we're reducing an empty array.)

For a large class of problems, parallelising the algorithm consists of
teasing out the hidden monoid structure so it can be chopped up in
this way.
--
Dan

On Tue, Jan 20, 2009 at 4:27 PM, Don Stewart  wrote:
> http://apfelmus.nfshost.com/monoid-fingertree.html
>
> Thanks Apfelmus for this inspiring contribution!
> ___
> 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] Does readFile "/proc/mounts" hang for you?

2009-01-21 Thread David Fox
I posted a bug about this (http://hackage.haskell.org/trac/ghc/ticket/2971)
but its so odd I had to ask here.  Using ghc 6.10.1, both readFile
"/proc/mounts" and Data.ByteString.Lazy.Char8.readFile "/proc/mounts" hang
on an amd64 machine running Linux.  Also, Data.ByteString.readFile
"/proc/mounts" returns the empty string.  Is this behavior present for
others?  On i386?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Quite confused by simple transformations on this code not working

2009-01-21 Thread Svein Ove Aas
Or if the specificity of (/\) is important to you, you could define f
at the global scope using that type, not export it, then declare (/\)
as equal to f but with a more restrictive type.

On Wed, Jan 21, 2009 at 5:45 AM, Alexander Dunlap
 wrote:
> Instead of declaring (/\) :: Eq a => Sentence a -> Sentence a ->
> Sentence a, you could say (/\) :: Eq a -> [a] -> [a] -> [a]. Then it
> would work in both places. ([a] -> [a] -> [a] is a more general type
> than [[Term a]] -> [[Term a]] -> [[Term a]], so functions with the
> former type can be used in place of functions of the latter type but
> not vice versa.)
>
> Alex
>
> 2009/1/20 Andrew Wagner :
>> So...there's just no good way to avoid the duplication?
>>
>> On Tue, Jan 20, 2009 at 11:10 PM, wren ng thornton 
>> wrote:
>>>
>>> Andrew Wagner wrote:

 Strange little bit of code:
 http://moonpatio.com:8080/fastcgi/hpaste.fcgi/view?id=829#a829

 If I do any of the following, all of which seem natural to me, it fails
 to
 typecheck:

   1. move f out of the 'where' clause (with or without a type signature)
   2. put the same type signature on f as is on (/\)
   3. replace f with (/\) completely

 What's going on here?
>>>
>>>> :t (nub .) . (++)
>>>(nub .) . (++) :: (Eq a) => [a] -> [a] -> [a]
>>>
>>>> :t foldr (map . (nub .) . (++))
>>>foldr (map . (nub .) . (++)) :: (Eq a) => [[a]] -> [[a]] -> [[a]]
>>>
>>> The type you give to (/\) is more restrictive than the type of the
>>> expression, and f uses the generality of the expression.
>>>
>>> --
>>> Live well,
>>> ~wren
>>> ___
>>> 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 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: Why monoids will abide...

2009-01-21 Thread Mauro J. Jaskelioff
Andrzej Jaworski wrote:
> Monads are monoids in categories of functors C -> C Arrows are monoids
> in subcategories of bifunctors (C^op) x C -> C   Trees are a playing
> ground for functors in general:-)
>
This is the nice thing about category theory! plenty of reuse of concepts :)

The situation for Arrows is a bit more complex. Monoids (C^op) x C -> C
are equivalent to Freyd categories (Heunen and Jacobs, MFPS 2006) , but
Arrows in Haskell are actually indexed-Freyd categories, as explained by
Bob Atkey in "What is a Categorical Model of Arrows?"
(MSFP 2008, http://homepages.inf.ed.ac.uk/ratkey/arrows.pdf)

The realization that monads are monoids would be far more useful in a
language with kind polymorphism.
However, this shouldn't stop us from dreaming...

All the best,

- Mauro

This message has been checked for viruses but the contents of an attachment
may still contain software viruses, which could damage your computer system:
you are advised to perform your own checks. Email communications with the
University of Nottingham may be monitored as permitted by UK legislation.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Type family problem

2009-01-21 Thread Manuel M T Chakravarty

Gleb Alexeyev:

Sjoerd Visscher wrote:

When I try this bit of code:
> class C1 a where
>   type F a :: *
>   x :: F a
>   y :: F a
>   x = y
I get this error:
   Couldn't match expected type `F a1' against inferred type `F a'
   In the expression: y
   In the definition of `x': x = y
I can't figure out what is going on or how I should fix this.


The discussion [1] seems to be related.

[1] http://hackage.haskell.org/trac/ghc-test/ticket/2855


Exactly.  See also the related ticket

  http://hackage.haskell.org/trac/ghc-test/ticket/1897

In short, the signature "F a" is ambiguous (as `a' only occurs as a  
parameter of a synonym family in the signature).  Functions with an  
ambiguous signature are generally unusable (even if the compiler  
accepts the definition initially).


Manuel

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Why monoids will abide...

2009-01-21 Thread David Leimbach
Oh indeed!

On Wed, Jan 21, 2009 at 8:00 AM, Eugene Kirpichov wrote:

> No, I mean monads :) I've never thought of them as of monoids in the
> endofunctor category.
>
> 2009/1/21 David Leimbach :
> > You mean monoids right?  :-)
> >
> > On Wed, Jan 21, 2009 at 1:30 AM, Eugene Kirpichov 
> > wrote:
> >>
> >> Wow. This is a cool point of view on monads, thank you for
> >> enlightening (the arrow stuff is yet too difficult for me to
> >> understand)!
> >>
> >> 2009/1/21 Andrzej Jaworski :
> >> > Monads are monoids in categories of functors C -> C Arrows are monoids
> >> > in
> >> > subcategories of bifunctors (C^op) x C -> C  Trees are a playing
> ground
> >> > for
> >> > functors in general:-)
> >> >
> >> > ___
> >> > 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 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: Why monoids will abide...

2009-01-21 Thread Eugene Kirpichov
No, I mean monads :) I've never thought of them as of monoids in the
endofunctor category.

2009/1/21 David Leimbach :
> You mean monoids right?  :-)
>
> On Wed, Jan 21, 2009 at 1:30 AM, Eugene Kirpichov 
> wrote:
>>
>> Wow. This is a cool point of view on monads, thank you for
>> enlightening (the arrow stuff is yet too difficult for me to
>> understand)!
>>
>> 2009/1/21 Andrzej Jaworski :
>> > Monads are monoids in categories of functors C -> C Arrows are monoids
>> > in
>> > subcategories of bifunctors (C^op) x C -> C  Trees are a playing ground
>> > for
>> > functors in general:-)
>> >
>> > ___
>> > 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 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: Why monoids will abide...

2009-01-21 Thread David Leimbach
You mean monoids right?  :-)

On Wed, Jan 21, 2009 at 1:30 AM, Eugene Kirpichov wrote:

> Wow. This is a cool point of view on monads, thank you for
> enlightening (the arrow stuff is yet too difficult for me to
> understand)!
>
> 2009/1/21 Andrzej Jaworski :
> > Monads are monoids in categories of functors C -> C Arrows are monoids in
> > subcategories of bifunctors (C^op) x C -> C  Trees are a playing ground
> for
> > functors in general:-)
> >
> > ___
> > 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ANN: HTTPbis / HTTP-4000.x package available

2009-01-21 Thread Lennart Augustsson
Yeah, the .pac files are a major pain. :(

On Wed, Jan 21, 2009 at 3:32 PM, ChrisK  wrote:
> Duncan Coutts wrote:
>>
>> Proxy auto-configuration files are JavaScript. It uses more or less the
>> full JavaScript language (ECMA these days), though with a small subset
>> of the standard library.
>
> W T F
>
> So we want a tiny naive javascript interpreter, hopefully in pure Haskell.
>  The dumbest interpreter than can parse and evaluate the language.
>
> An separate program that just translates .pac file to something declarative
> is sorely needed.
>
> --
> Chris
>
> ___
> 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: ANN: HTTPbis / HTTP-4000.x package available

2009-01-21 Thread ChrisK

Duncan Coutts wrote:

Proxy auto-configuration files are JavaScript. It uses more or less the
full JavaScript language (ECMA these days), though with a small subset
of the standard library.


W T F

So we want a tiny naive javascript interpreter, hopefully in pure Haskell.  The 
dumbest interpreter than can parse and evaluate the language.


An separate program that just translates .pac file to something declarative is 
sorely needed.


--
Chris

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Type family problem

2009-01-21 Thread Gleb Alexeyev

Sjoerd Visscher wrote:

When I try this bit of code:

 > class C1 a where
 >   type F a :: *
 >   x :: F a
 >   y :: F a
 >   x = y

I get this error:

Couldn't match expected type `F a1' against inferred type `F a'
In the expression: y
In the definition of `x': x = y

I can't figure out what is going on or how I should fix this.



The discussion [1] seems to be related.

[1] http://hackage.haskell.org/trac/ghc-test/ticket/2855

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Pure Haskell implementation of Float type?

2009-01-21 Thread Ertugrul Soeylemez
"Tim Chevalier"  wrote:

> Is there a pure Haskell implementation of Floats, i.e., one that
> (unlike GHC.Float) doesn't use foreign calls for things like
> isFloatNegativeZero? I don't care about performance; I'm just looking
> for something that doesn't use foreign calls.

You can easily do it yourself:

  data MyFloat m e
= MyFloat m e | MyInfinity Bool | MyNaN

A number x is represented in floating point as x = m * b^e, where m is
called the mantissa, e the exponent and b the base.  For performance
reasons, usually b = 2 is chosen and both m and e are integers with
fixed size.  You'll find it useful to have a 'normalize' function, which
'moves the point', such that the mantissa isn't divisible by b, if
possible.


Greets,
Ertugrul.


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://blog.ertes.de/


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Why monoids will abide...

2009-01-21 Thread Eugene Kirpichov
Wow. This is a cool point of view on monads, thank you for
enlightening (the arrow stuff is yet too difficult for me to
understand)!

2009/1/21 Andrzej Jaworski :
> Monads are monoids in categories of functors C -> C Arrows are monoids in
> subcategories of bifunctors (C^op) x C -> C  Trees are a playing ground for
> functors in general:-)
>
> ___
> 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: How to make code least strict?

2009-01-21 Thread Thomas Davie
Further to all the playing with unamb to get some very cool behaviors,  
you might want to look at Olaf Chitil's paper here:


http://www.cs.kent.ac.uk/pubs/2006/2477/index.html

It outlines a tool for checking if your programs are as non-strict as  
they can be.


Bob

On 21 Jan 2009, at 02:08, Conal Elliott wrote:


Lovely reformulation, Ryan!

I think lub [4] is sufficient typeclass hackery for unambPatterns:

   unambPatterns == lubs == foldr lub undefined

[4] http://conal.net/blog/posts/merging-partial-values

I think performance is okay now, if you have very recent versions of  
unamb *and* GHC head (containing some concurrency bug fixes).  See http://haskell.org/haskellwiki/Unamb 
 .  The GHC fix will take a while to get into common use.


My definitions of zip via (a) 'assuming' & 'unamb' and (b)  
parAnnihilator are badly broken.  For one, the unamb arguments are  
incompatible (since i didn't check for both non-null args in the  
third case).  Also, the types aren't right for parAnnihilator.


I tried out this idea, and it seems to work out very nicely.  See  
the brand-new blog post http://conal.net/blog/posts/lazier-function-definitions-by-merging-partial-values/ 
 .  Blog comments, please!


   - Conal

On Mon, Jan 19, 2009 at 3:01 PM, Ryan Ingram   
wrote:

Actually, I see a nice pattern here for unamb + pattern matching:

> zip xs ys = foldr unamb undefined [p1 xs ys, p2 xs ys, p3 xs ys]  
where

> p1 [] _ = []
> p2 _ [] = []
> p3 (x:xs) (y:ys) = (x,y) : zip xs ys

Basically, split each pattern out into a separate function (which by
definition is _|_ if there is no match), then use unamb to combine
them.

The invariant you need to maintain is that potentially overlapping
pattern matches (p1 and p2, here) must return the same result.

With a little typeclass hackery you could turn this into

> zip = unambPatterns [p1,p2,p3] where {- p1, p2, p3 as above -}

Sadly, I believe the performance of "parallel-or"-style operations is
pretty hideous right now.  Conal?

 -- ryan

On Mon, Jan 19, 2009 at 2:42 PM, Conal Elliott   
wrote:
> I second Ryan's recommendation of using unamb [1,2,3] to give you  
unbiased

> (symmetric) laziness.
>
> The zip definition could also be written as
>
> zip xs@(x:xs') ys@(y:ys') =
>   assuming (xs == []) [] `unamb`
>   assuming (ys == []) [] `unamb`
>   (x,y) : zip xs' ys'
>
> The 'assuming' function yields a value if a condition is true and  
otherwise

> is bottom:
>
> assuming :: Bool -> a -> a
> assuming True  a = a
> assuming False _ = undefined
>
> This zip definition is a special case of the annihilator pattern, so
>
> zip = parAnnihilator (\ (x:xs') (y:ys') -> (x,y) : zip xs'  
ys') []

>
> where 'parAnnihilator' is defined in Data.Unamb (along with other  
goodies)

> as follows:
>
> parAnnihilator :: Eq a => (a -> a -> a) -> a -> (a -> a -> a)
> parAnnihilator op ann x y =
>   assuming (x == ann) ann `unamb`
>   assuming (y == ann) ann `unamb`
>   (x `op` y)
>
> [1] http://haskell.org/haskellwiki/Unamb
> [2]
> 
http://hackage.haskell.org/packages/archive/unamb/latest/doc/html/Data-Unamb.html
> [3] http://conal.net/blog/tag/unamb/
>
>- conal
>
> On Mon, Jan 19, 2009 at 12:27 PM, Ryan Ingram  
 wrote:

>>
>> On Mon, Jan 19, 2009 at 9:10 AM, ChrisK >

>> wrote:
>> > Consider that the order of pattern matching can matter as well,  
the

>> > simplest
>> > common case being zip:
>> >
>> > zip xs [] = []
>> > zip [] ys = []
>> > zip (x:xs) (y:ys) = (x,y) : zip xs ys
>>
>> If you are obsessive about least-strictness and performance isn't a
>> giant concern, this seems like a perfect use for Conal's unamb[1]
>> operator.
>>
>> zipR xs [] = []
>> zipR [] ys = []
>> zipR (x:xs) (y:ys) = (x,y) : zip xs ys
>>
>> zipL [] ys = []
>> zipL xs [] = []
>> zipL (x:xs) (y:ys) = (x,y) : zip xs ys
>>
>> zip xs ys = unamb (zipL xs ys) (zipR xs ys)
>>
>> This runs both zipL and zipR in parallel until one of them gives a
>> result; if neither of them is _|_ they are guaranteed to be  
identical,
>> so we can "unambiguously choose" whichever one gives a result  
first.

>>
>>  -- ryan
>>
>> [1]
>> http://conal.net/blog/posts/functional-concurrency-with-unambiguous-choice/
>> ___

___
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] Employment

2009-01-21 Thread Lionel Barret De Nazaris

That fits with our experience (gamr7).
We got 20 applicants, all of them very good.
L.

Paul Johnson wrote:

Tom Hawkins wrote:

 Such a database would help me counter by boss's
argument that "it's impossible to find and hire Haskell programmers."

  
There was a thread last week where someone asked who would be 
interested in a hypothetical Haskell job.  He got about 20 positive 
responses.  This agrees with the experience of Microsoft Research in 
2006 when they advertised for a third person to help with GHC 
development.   They also had about 20 applicants.


So next time I hear the "you can't get the programmers" line I'm going 
to respond with something like this:


   "If you post an advert for a Haskell developer you will get 20
   applicants.  All of those people will be the kind of developer who
   learns new programming languages to improve their own abilities and
   stretch themselves, because nobody yet learns Haskell just to get a 
job.


   "If you post an advert for a Java developer you will get 200
   applicants.  Most of them will be the kind of developer who learned
   Java because there are lots of Java jobs out there, and as long as
   they know enough to hold down a job then they see no reason to learn
   anything."

Paul.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



--
Best Regards,
lionel Barret de Nazaris,
Gamr7 Founder & CTO
=
Gamr7 : Cities for Games
http://www.gamr7.com




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type families are awesome

2009-01-21 Thread Luke Palmer
2009/1/21 John Ky 
>
> *Main> let x = lookup
> *Main> let y = Fx.Data.Map.lookup
>
> :1:8:
> Ambiguous type variable `ma' in the constraint:
>   `Fx.Data.Map.MapType ma'
> arising from a use of `Fx.Data.Map.lookup' at :1:8-25
> Probable fix: add a type signature that fixes these type variable(s)


I think this is just the monomorphism restriction. Turn it off with
-XNoMonomorphismRestriction, or add a parameter to the binding:

let x k = lookup k

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Type families are awesome

2009-01-21 Thread John Ky
Hi Haskell Cafe,

I'm finding that I really like type families.  For instance, the
GHC.List.lookup and Data.Map.lookup functions annoy me because their names
clash, yet their type are so similar.  With type families, I could define a
more generic lookup function like this:

import Data.Map as MAP
import GHC.List as LIST

class MapType ma where
   type Key ma
   type Item ma
   lookup :: Key ma -> ma -> Maybe (Item ma)

instance (Ord ka) => MapType (MAP.Map ka a) where
   type Key (MAP.Map ka a) = ka
   type Item (MAP.Map ka a) = a
   lookup ka ma = MAP.lookup ka ma

instance (Eq ka) => MapType [(ka, a)] where
   type Key [(ka, a)] = ka
   type Item [(ka, a)] = a
   lookup ka ma = LIST.lookup ka ma

This lookup function works on both "Map ka a" and "[(ka, a)]" types and I no
longer need to qualify my lookup function with the module name.

The downside I suppose is that lookup is no longer a function that can be
manipulated freely:

*Main> let x = lookup
*Main> let y = Fx.Data.Map.lookup

:1:8:
Ambiguous type variable `ma' in the constraint:
  `Fx.Data.Map.MapType ma'
arising from a use of `Fx.Data.Map.lookup' at :1:8-25
Probable fix: add a type signature that fixes these type variable(s)

A shame that.  I had been hoping it would be possible to have a generic
lookup function that could be used in every way the current collection of
various lookup functions can be used.

So much nicer if 'y' above could be bound to the Fx.Data.Map.lookup with the
same type:

*Main> :t Fx.Data.Map.lookup
Fx.Data.Map.lookup :: forall ma.
  (Fx.Data.Map.MapType ma) =>
  Fx.Data.Map.Key ma -> ma -> Maybe (Fx.Data.Map.Item
ma)

And then have the ambiguity resolve later when 'y' is actually used.

-John
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe