Re: [Haskell-cafe] I/O system brokenness with named pipes

2008-04-11 Thread Donn Cave


On Apr 11, 2008, at 6:15 AM, John Goerzen wrote:

I wonder if we could document this behavior.  I rarely use non- 
blocking I/O
from C, and Haskell hides the fact that it's doing this, so the  
behavior is

non-intuitive.


I have run into this problem, with Network.Socket (socket).  If I  
remember right,
ktrace showed me what was happening.  This isn't my favorite thing  
about Haskell.
Is there even a means provided to set it back to blocking?  I  
couldn't find one,
had to write my own FFI.  It is not news to me that there is an issue  
with the
Haskell thread implementation here, but since any non-native library  
I/O will

similarly be blocking, we have to be able to live with this anyway.


Actually, better yet, I wonder if we could *fix* this behavior.  Most
programs can take a FIFO as arguments in a standard way, and it  
seems to me

that this violates the principle of least surprise.

Unfortunately, since we're talking about open here, we can't use  
select() or
poll().  But I wonder if we couldn't use stat() to determine if  
something is
a named pipe, and if so, enter a loop where we try to open it  
periodically?


I am having a little trouble following this.  Somewhere in the  
thread, the subject
of ReadWrite pipe behavior came up, apparently for whatever reason  
you get
non-blocking I/O this way too.  But as long as you don't do that,  
then all you need
for normal named pipe I/O is to set the file descriptor back to  
blocking ... right?
Is the loop to work around the Haskell non-blocking, or the ReadWrite  
non-blocking?


Donn Cave, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] do construct in wxhaskell

2008-04-11 Thread Jodi-Ann Prince

hi, im working ona project, and im having problem loading some code in 
wxhaskell:
 
 
onOpen :: Frame a -> TextCtrl b -> MenuItem c -> StatusField -> IO ()
onOpen f sw mclose status = do   mbfname <- fileOpenDialog f False True "Open 
image" fileTypes "" ""  case  
(mbfname) of  (Nothing)  -> 
return ()
  (Just (fname)) -> do   
fileContent <- readFile fname
 
set sw [text := fileContent]
 set mclose [enabled := True]   
   set status [text := fname]   
   return ()
 
i keep getting the error : "the last statement in a 'do' construct must be an 
expression."
ive tried rearranging it many times, but i still get the same error. any help 
would be greatly appreciated.
_
Connect to the next generation of MSN Messenger 
http://imagine-msn.com/messenger/launch80/default.aspx?locale=en-us&source=wlmailtagline___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Type families and GADTs in 6.9

2008-04-11 Thread Dan Doel
Hello,

I've been playing around with type families off and on in 6.8, but, what with 
the implementation therein being reportedly incomplete, it's hard to know 
what I'm getting right and wrong, or what should work but doesn't and so on. 
So, I finally decided to take the plunge and install 6.9 (which, perhaps, 
isn't yet safe in that regard either, but, such is life :)). But, when I 
loaded up one of my programs, I got a type error. The subject is inductively 
defined tuples:

-

{-# LANGUAGE GADTs, TypeFamilies, EmptyDataDecls, TypeOperators #-}

data Zero
data Succ n

data Nat n where
  Zero :: Nat Zero
  Succ :: Nat n -> Nat (Succ n)

data FZ
data FS a

data Fin fn n where
  FZ :: Fin FZ (Succ n)
  FS :: Fin fn n -> Fin (FS fn) (Succ n)

f0 = FZ
f1 = FS f0
f2 = FS f1
-- ... etc.

data Nil
data t ::: ts

type family Length ts :: *
type instance Length Nil = Zero
type instance Length (t ::: ts) = Succ (Length ts)

type family Lookup ts fn :: *
type instance Lookup (t ::: ts) FZ = t
type instance Lookup (t ::: ts) (FS fn) = Lookup ts fn

infixr 4 :::

data Tuple ts where
  ZT:: Tuple Nil
  (:::) :: t -> !(Tuple ts) -> Tuple (t ::: ts)

{-
  This type signature gets complained about in 6.8, but it seems like
  a sensible one:
proj :: (Length ts ~ n) => Fin fn n -> Tuple ts -> Lookup ts fn
  Indexing the tuple by its length is also an option (which works).
  In any case, the code doesn't even work with the lenient 6.8 signature:
-}
proj :: Fin fn n -> Tuple ts -> Lookup ts fn
proj FZ  (v ::: vs) = v
proj (FS fn) (v ::: vs) = proj fn vs

-

The overall goal being Haskell-alike tuples with a single projection function 
that works for all of them, without having to use template haskell for 
instance (fst = proj f0, snd = proj f1, etc.). However, proj results in a 
type error:

Occurs check: cannot construct the infinite type:
  t = Lookup (t ::: ts) fn
In the pattern: v ::: vs
In the definition of `proj': proj FZ (v ::: vs) = v

Oddly (to me), if I reverse the clauses, the compiler doesn't complain about 
the FS case, still complaining about FZ. Now, my thought process here is that 
the pattern match against FZ (the value) requires fn to be FZ (the type), 
which should tell the compiler to solve "t ~ Lookup (t ::: ts) FZ" which is, 
of course, the first instance above.

Am I doing something wrong, or have I bumped into as-yet-unimplemented 
functionality?

Thanks for your time and help.
-- Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] more on my ghc package issues

2008-04-11 Thread Galchin, Vasili
Hello,

 I "unregistered" unix-2.3.0.0. Now I cannot rebuild the Unix package.
Please see the below log:


[EMAIL PROTECTED]:~$ ghc-pkg latest unix
unix-2.2.0.0
[EMAIL PROTECTED]:~$ ghc-pkg describe unix
name: unix
version: 2.2.0.0
license: BSD3
copyright:
maintainer: [EMAIL PROTECTED]
stability:
homepage:
package-url:
description: This package gives you access to the set of operating system
 services standardised by POSIX 1003.1b (or the IEEE Portable
 Operating System Interface for Computing Environments -
 IEEE Std. 1003.1).
 .
 The package is not supported under Windows (except under
Cygwin).
category:
author:
exposed: True
exposed-modules: System.Posix System.Posix.DynamicLinker.Module
 System.Posix.DynamicLinker.Prim System.Posix.Directory
 System.Posix.DynamicLinker System.Posix.Env
System.Posix.Error
 System.Posix.Files System.Posix.IO System.Posix.Process
 System.Posix.Process.Internals System.Posix.Resource
 System.Posix.Temp System.Posix.Terminal System.Posix.Time
 System.Posix.Unistd System.Posix.User System.Posix.Signals
 System.Posix.Signals.Exts System.Posix.Semaphore
 System.Posix.SharedMem System.Posix.MQueue
hidden-modules:
import-dirs: /usr/local/lib/unix-2.2.0.0/ghc-6.8.2
library-dirs: /usr/local/lib/unix-2.2.0.0/ghc-6.8.2
hs-libraries: HSunix-2.2.0.0
extra-libraries: util dl
extra-ghci-libraries:
include-dirs: /usr/local/lib/unix-2.2.0.0/ghc-6.8.2/include
includes: HsUnix.h execvpe.h
depends: base-3.0.1.0 directory-1.0.0.0
hugs-options:
cc-options:
ld-options:
framework-dirs:
frameworks:
haddock-interfaces: /usr/local/share/doc/unix-2.2.0.0/html/unix.haddock
haddock-html: /usr/local/share/doc/unix-2.2.0.0/html
[EMAIL PROTECTED]:~$

[EMAIL PROTECTED]:~/FTP/Haskell/unix-2.2.0.0$ runhaskell Setup.hs configure
unknown package: unix-2.3.0.0

In my .cabal file, I have specified the version as 2.2.0.0, 2.3.0.0 and
2.4.0.0 all with the same results: "unknown package: unix-2.3.0.0"


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


Re: [Haskell-cafe] install trouble with SDL on win32+cygwin

2008-04-11 Thread Luke Palmer
2008/4/11 Conal Elliott <[EMAIL PROTECTED]>:
> I'm trying to install the SDL package (on win32+cygwin), and configure isn't
> able to find my SDL.dll, though it's on my PATH.  Any ideas?  - Conal
>
> bash-3.2$ cabal install SDL
> 'SDL-0.5.3' is cached.
>  [1 of 1] Compiling Main ( Setup.lhs, dist\setup/Main.o )
> Linking dist\setup\setup.exe ...
> Configuring SDL-0.5.3...
> checking for sdl-config... no

I currently am not running cygwin, so I could be wrong, but the lack
of sdl-config is a red flag.  Have you installed sdl and sdl-devel (I
think those are the package names) with the cygwin installer yet?

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


Re: [Haskell-cafe] install trouble with SDL on win32+cygwin

2008-04-11 Thread Jake Mcarthur

On Apr 11, 2008, at 8:37 PM, Conal Elliott wrote:

I'm trying to install the SDL package (on win32+cygwin), and  
configure isn't able to find my SDL.dll, though it's on my PATH.   
Any ideas?  - Conal



I think this has been a known (neglected?) issue for quite some time.  
That's why I am not using SDL right now. :(


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


[Haskell-cafe] install trouble with SDL on win32+cygwin

2008-04-11 Thread Conal Elliott
I'm trying to install the SDL package (on win32+cygwin), and configure isn't
able to find my SDL.dll, though it's on my PATH.  Any ideas?  - Conal

bash-3.2$ cabal install SDL
'SDL-0.5.3' is cached.
[1 of 1] Compiling Main ( Setup.lhs, dist\setup/Main.o )
Linking dist\setup\setup.exe ...
Configuring SDL-0.5.3...
checking for sdl-config... no
checking for sdl11-config... no
configure: error: *** SDL not found! Get SDL from www.libsdl.org.
If you already installed it, check it's in the path. If problem remains,
please send a mail to the address that appears in ./configure --version
indicating your platform, the version of configure script and the problem.
cabal.exe: Error: some packages failed to install:
SDL-0.5.3 failed during the configure step. The exception was:
exit: ExitFailure 1
bash-3.2$ which SDL.dll
/cygdrive/c/WINDOWS/system32/SDL.dll
bash-3.2$
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad proof

2008-04-11 Thread Ryan Ingram
I really like Chuan-Kai Lin's Unimo paper; in it he talks about
defining a monad in terms of defining the behavior of its effects:

   http://web.cecs.pdx.edu/~cklin/papers/unimo-143.pdf

Prompt is based on the same idea, with one small difference.  While
it's possible to write observation functions that break the monad laws
with Unimo, it's actually impossible to do so with Prompt.

   
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/MonadPrompt-1.0.0.1

This way you don't have to prove the Monad laws at all, you just write
the code you want and some properties are guaranteed for you.

  -- ryan

On 4/11/08, Rafael C. de Almeida <[EMAIL PROTECTED]> wrote:
> Hello,
>
> I was studying Monads and I was trying to think about new Monads I could
> define. So, a question poped into my mind: how is proof regarding the 3
> Monad laws handled? I know that, aside from testing all the possible values
> (and there can be a lot of them), there's no general way to prove it.
> Nonetheless, I think that it would be insightful to see how people write
> those proofs for their monads -- specially for new user monads. Is there
> some article or some notes on proving that Monads are implemented correctly?
>
> []'s
> Rafael
> ___
> 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] library version problem

2008-04-11 Thread Galchin, Vasili
Right I am just trying to rebuild the unix package. No matter what version
is present in the unix.cabal file,

runhaskell Setup.hs configure

produces an error concerning unix-2.3.0.0


Starting to get really frustrated over this. I just want to build a Unix
package test case .. and now I can't even build the unix package itself.

 ghc-pkg seems to be at the center of this problem because the problem seems
to have to deal with the package database.

1) On Linux(Ubuntu) where is the package database?

2) If ghc-pkg is indeed a Haskell program, how can I get the source to
better understand the problem I am encountering on my own?

On Fri, Apr 11, 2008 at 9:33 AM, Brent Yorgey <[EMAIL PROTECTED]> wrote:

>
>  On Fri, Apr 11, 2008 at 3:11 AM, Ketil Malde <[EMAIL PROTECTED]> wrote:
>
> > "Galchin, Vasili" <[EMAIL PROTECTED]> writes:
> >
> > >> ghci
> > >   :m System.Posix
> > >
> > > I am getting the wrong version of the Unix package. I know this to be
> > true
> > > because I did
> > > ghc-pkg latest unix
> > >
> > > and got unix-2.3.0.0
> > >
> > > I want unix.2.2.0.0 because this version has changes that I made
> >
> > Naturally, you'll get 2.3.0.0, since it has the highest version number!
> >
> > Either rename your modified version to 2.4 (or similar), specify the
> > exact version in your *application's* cabal file, or use
> > "ghc-pkg hide" to hide version 2.3.0.0 from view.
> >
>
> Actually, I'm pretty sure that Cabal does not take the visibility states
> of packages into account when selecting packages to fulfill dependencies, so
> ghc-pkg hide will not actually work.
>
> -Brent
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Longest increasing subsequence

2008-04-11 Thread ChrisK
My late night suggestions were nearly correct.  I have actually written the code 
now.  Once keeping track of indices, and a second time without them:



{-# LANGUAGE BangPatterns #-}
-- By Chris Kuklewicz, copyright 2008, BSD3 license
-- Longest increasing subsequence
-- (see http://en.wikipedia.org/wiki/Longest_increasing_subsequence)
import Data.List (foldl')
import Data.Map (Map)
import qualified Data.Map as M (empty,null,insert,findMin,findMax
   ,splitLookup,deleteMin,delete)

type DList a = [a] -> [a]

lnds :: Ord a => [a] -> [a]
lnds = lnds_decode . lnds_fold

lnds_fold :: Ord a => [a] -> Map a (DList a)
lnds_fold = foldl' process M.empty where
  -- The Map keys, in sorted order, are the input values which
  --   terminate the longest increasing chains of length 1,2,3,…
  process mu x =
case M.splitLookup x mu of
  (_,Just {},_) -> mu -- ignore x when it is already an end of a chain

  (map1,Nothing,map2) | M.null map2 ->
-- insert new maximum element x
if M.null mu
  then M.insert x (x:) mu -- x is very first element
  else let !xs = snd (M.findMax mu)
   in M.insert x (xs . (x:)) mu

  | M.null map1 ->
-- replace minimum element with smaller x
M.insert x (x:) (M.deleteMin mu)

  | otherwise ->
-- replace previous element oldX with slightly smaller x
let !xs = snd (M.findMax map1)
!oldX = fst (M.findMin map2) -- slightly bigger key
!withoutOldX = M.delete oldX mu
in M.insert x (xs . (x:)) withoutOldX

lnds_decode :: Ord a => Map a (DList a) -> [a]
lnds_decode mu | M.null mu = []
   | otherwise = snd (M.findMax mu) []

tests =  [ ['b'..'m'] == (lnds $ ['m'..'s'] ++ ['b'..'g'] ++ ['a'..'c'] ++ 
['h'..'k'] ++ ['h'..'m'] ++ ['d','c'..'a'])
 , "" == lnds ""
 , "a" == lnds "a"
 , "a" == lnds "ba"
 , "ab" == lnds "ab"
 ]


Comparing to wikipedia:
  The X[M[1]],X[M[2]],… sequence is strictly increasing.  These are the ends of 
the current increasing chains of length 1,2,… and they are the keys to the Map 
in my code.


  The values of the map are the subsequences themselves, in DList form. 
Instead of pointing to the index of the previous element I just lookup '!xs' and 
append '(x:)' to that.


Complexity:
  The strictness annotations ensure that the garbage collector can destroy any 
unreachable DList entries.  The space usage is thus O(N) and may be O(1) for 
certain inputs (such as the best case of never-increasing input list).  A 
strictly increasing input list is the worst case for space usage.


The naive time complexity of 'process' for the i'th input value is O(log i). 
This can be double checked by looking at the time complexity of everything I 
import from Data.Map.


Peak performance could be had by
  (1) adding the first element before the foldl' to avoid checking for this 
case in process
  (2a) accessing the internal map structure to optimize the 
splitLookup->delete->insert case into a single operation
  (2b) Using something like a zipper to access the to-be-deleted-and-replaced 
element of the map
The (2a) and (2b) work because we know the changed key will go into the same 
'slot' of the map as the old one.


--
Chris

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


Re: [Haskell-cafe] Monad proof

2008-04-11 Thread Rodrigo Geraldo
Did you see this?

http://okmij.org/ftp/Computation/proving-monad-laws.txt

[]'s


Rodrigo Geraldo Ribeiro.

PhD student - UFMG

On Fri, Apr 11, 2008 at 2:35 PM, Rafael C. de Almeida <[EMAIL PROTECTED]>
wrote:

> Hello,
>
> I was studying Monads and I was trying to think about new Monads I could
>  define. So, a question poped into my mind: how is proof regarding the 3
> Monad laws handled? I know that, aside from testing all the possible values
> (and there can be a lot of them), there's no general way to prove it.
> Nonetheless, I think that it would be insightful to see how people write
> those proofs for their monads -- specially for new user monads. Is there
> some article or some notes on proving that Monads are implemented correctly?
>
> []'s
> Rafael
> ___
> 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] Monad proof

2008-04-11 Thread Rafael C. de Almeida

Hello,

I was studying Monads and I was trying to think about new Monads I could 
 define. So, a question poped into my mind: how is proof regarding the 
3 Monad laws handled? I know that, aside from testing all the possible 
values (and there can be a lot of them), there's no general way to prove 
it. Nonetheless, I think that it would be insightful to see how people 
write those proofs for their monads -- specially for new user monads. Is 
there some article or some notes on proving that Monads are implemented 
correctly?


[]'s
Rafael
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Control.Parallel.Strategies

2008-04-11 Thread Cale Gibbard
Out of interest, have you tried using parListChunk to break the work
into larger pieces? It seems rather unlikely to help with this case as
the parts are already pretty large, but perhaps it's worth a shot.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] library version problem

2008-04-11 Thread Brent Yorgey
On Fri, Apr 11, 2008 at 3:11 AM, Ketil Malde <[EMAIL PROTECTED]> wrote:

> "Galchin, Vasili" <[EMAIL PROTECTED]> writes:
>
> >> ghci
> >   :m System.Posix
> >
> > I am getting the wrong version of the Unix package. I know this to be
> true
> > because I did
> > ghc-pkg latest unix
> >
> > and got unix-2.3.0.0
> >
> > I want unix.2.2.0.0 because this version has changes that I made
>
> Naturally, you'll get 2.3.0.0, since it has the highest version number!
>
> Either rename your modified version to 2.4 (or similar), specify the
> exact version in your *application's* cabal file, or use
> "ghc-pkg hide" to hide version 2.3.0.0 from view.
>

Actually, I'm pretty sure that Cabal does not take the visibility states of
packages into account when selecting packages to fulfill dependencies, so
ghc-pkg hide will not actually work.

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


Re: [Haskell-cafe] Haskell IDE: Someone else interested in enhancingShim ? / How to contact author Benedikt Schmidt ?

2008-04-11 Thread Claus Reinke

Hi Marc,

when i first encountered Shim, i thought it was a nice idea, but
with a lot less emphasis on the vim side than on the emacs side.

also, iirc, Shim uses python's interprocess communication and i
didn't want to ask vim users to install python to get haskell 
functionality. so i found that Shim didn't help me to simplify my

own haskellmode plugins for vim [1]. perhaps all that has
changed, and information just hasn't reached this list yet?

but i like your suggestions, so i thought i'd comment as a 
non-Shim vim haskeller;-)



   :GrepScope regex
   Which greps the whole scope of all used packages by regex.
   Very useful to find all functions taking/ returning some type etc


i have something similar in my .ghci file [2], allowing things
like ':grep Maybe :browse' or ':grep fold :browse'. it might be 
useful to have more direct access to it inside vim, but i'll wait

for user interest on this one.


   :ModulesExporting identifier
   returns all modules exporting identifiers. Can be used to 
   add imports more automatically.


already supported in my haskellmode plugins; used for

|_?|  browse Haddock entry for id under cursor
|_.|  qualify unqualified id under cursor
|_i|  add 'import ()' for id under cursor
|_im| add 'import ' for id under cursor


   Completion:
   camelCaseMatching
   Use pSL to get putStrLn


i like this so much that i've implemented it, too (still testing/modifying,
so it isn't online yet;-)! nice way to navigate/narrow down the huge 
menues of options one can otherwise get from completing short ids.

there are some interesting issues, though:

- i consider upper-case letters anchored at the start of patterns,
   so 'X' will ignore things like 'fromX'

- apart from upper-case letters, i also use '.' for guidance,
   and as anchors, so that 'C.E.t' will get you directly 
   to the 'Control.Exception.t' stuff, ignoring 'C[^.]E' stuff
   (depending on preferences, some might want '_'  for 
guidance, too?)


- i need to enable CamelCase matching only when there are no 
   prefix matches, otherwise it will enlarge the completion options,

   offering unintended choices (and since those extra options
   will not have the same prefix, that prefix will disappear,
   eg if you actually mean 'pSomething', you try 'pS', and
   it will turn into 'p' -with a huge menu- because there are
   things like 'putStr', etc)

- there are now more possible matches and more matching,
   so things get a bit slower..

- i'm having an odd issue that interferes with incrementally
   adding upper-case letters to narrow completion options
   CamelCase style; but hitting  again works,
   so it might be a bug in my code?

but quite useful when it works, so thanks for the suggestion!-)

claus

[1] http://www.cs.kent.ac.uk/~cr3/toolbox/haskell/Vim
[2] http://haskell.cs.yale.edu/haskellwiki/GHCi#Using_.ghci.2C_a_mini-tutorial
   (everyone, please add your own .ghci tips to that wiki page!-)

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


Re: [Haskell-cafe] I/O system brokenness with named pipes

2008-04-11 Thread Brandon S. Allbery KF8NH


On Apr 11, 2008, at 9:08 , John Goerzen wrote:

On Fri April 11 2008 8:02:07 am Brandon S. Allbery KF8NH wrote:

On Apr 11, 2008, at 8:12 , John Goerzen wrote:

OK, I have referred to fifo(7) regarding this point.  It seems I
may need a
loop trying over and over to open the FIFO in write mode.  It also
appears
that ReadWriteMode appearing to work is Linux-specific, and this
behavior is
left undefined in POSIX.


Undefined in POSIX, normal for Unix (and Linux originally promised
only POSIX semantics but was rejiggered some years back to behave
like Unix in this regard, because Unix programs rely on these
semantics and therefore failed on Linux).


Hrm, can you define what OSs you mean when you say "Unix"?


SunOS/Solaris, and in general the descendants of 4.xBSD and AT&T  
System III/V.  Unless this is a different issue from the usual FIFO  
only-works-as-expected-if-both-ends-always-open problem.  That is,  
unless the first opener opens read/write, neither a prospective  
writer nor a prospective reader will be capable of opening it at all;  
depending on OS you will get ENXIO or EPIPE or (in some rare  
implementations) EAGAIN.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] I/O system brokenness with named pipes

2008-04-11 Thread John Goerzen
On Fri April 11 2008 7:53:12 am Brandon S. Allbery KF8NH wrote:
> On Apr 11, 2008, at 6:33 , Don Stewart wrote:
> >> But I can't use writeFile to write data to it.  Worse, it returns:
> >>
> >> *** Exception: /tmp/bakroller.zD0xHj/fifo: openFile: does not exist
> >> (No such device or address)
> >
> > Hmm, I can get this to work, but only if I have another process
> > waiting
> > on the pipe already:
>
> Yep; that's one of the tricky parts of FIFOs.  If you don't have the
> read side *always* open, it behaves very nonintuitively.  (But with
> the read side always open, you will never receive an EOF.)
>
> This has nothing to do with Haskell; it's just the way FIFOs work.

I wonder if we could document this behavior.  I rarely use non-blocking I/O 
from C, and Haskell hides the fact that it's doing this, so the behavior is 
non-intuitive.

Actually, better yet, I wonder if we could *fix* this behavior.  Most 
programs can take a FIFO as arguments in a standard way, and it seems to me 
that this violates the principle of least surprise.  

Unfortunately, since we're talking about open here, we can't use select() or 
poll().  But I wonder if we couldn't use stat() to determine if something is 
a named pipe, and if so, enter a loop where we try to open it periodically?

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


Re: [Haskell-cafe] I/O system brokenness with named pipes

2008-04-11 Thread John Goerzen
On Fri April 11 2008 8:02:07 am Brandon S. Allbery KF8NH wrote:
> On Apr 11, 2008, at 8:12 , John Goerzen wrote:
> > OK, I have referred to fifo(7) regarding this point.  It seems I
> > may need a
> > loop trying over and over to open the FIFO in write mode.  It also
> > appears
> > that ReadWriteMode appearing to work is Linux-specific, and this
> > behavior is
> > left undefined in POSIX.
>
> Undefined in POSIX, normal for Unix (and Linux originally promised
> only POSIX semantics but was rejiggered some years back to behave
> like Unix in this regard, because Unix programs rely on these
> semantics and therefore failed on Linux).

Hrm, can you define what OSs you mean when you say "Unix"?

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


Re: [Haskell-cafe] I/O system brokenness with named pipes

2008-04-11 Thread Brandon S. Allbery KF8NH


On Apr 11, 2008, at 8:12 , John Goerzen wrote:
OK, I have referred to fifo(7) regarding this point.  It seems I  
may need a
loop trying over and over to open the FIFO in write mode.  It also  
appears
that ReadWriteMode appearing to work is Linux-specific, and this  
behavior is

left undefined in POSIX.


Undefined in POSIX, normal for Unix (and Linux originally promised  
only POSIX semantics but was rejiggered some years back to behave  
like Unix in this regard, because Unix programs rely on these  
semantics and therefore failed on Linux).


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] I/O system brokenness with named pipes

2008-04-11 Thread Brandon S. Allbery KF8NH


On Apr 11, 2008, at 6:33 , Don Stewart wrote:


But I can't use writeFile to write data to it.  Worse, it returns:

*** Exception: /tmp/bakroller.zD0xHj/fifo: openFile: does not exist
(No such device or address)

Hmm, I can get this to work, but only if I have another process  
waiting

on the pipe already:


Yep; that's one of the tricky parts of FIFOs.  If you don't have the  
read side *always* open, it behaves very nonintuitively.  (But with  
the read side always open, you will never receive an EOF.)


This has nothing to do with Haskell; it's just the way FIFOs work.

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] I/O system brokenness with named pipes

2008-04-11 Thread John Goerzen
On Friday 11 April 2008 05:39:54 am Duncan Coutts wrote:
> On Thu, 2008-04-10 at 20:34 -0500, John Goerzen wrote:
> > I have created the named pipe from Haskell no problem.
> >
> > But I can't use writeFile to write data to it.  Worse, it returns:
> >
> > *** Exception: /tmp/bakroller.zD0xHj/fifo: openFile: does not exist
> > (No such device or address)
> >
> > What's going on here?  Am I going to have to resort to the
> > System.Posix interface just to be able to write to a named pipe?
>
> Named pipes have broken semantics for non-blocking IO, see google or the
> man pages on named pipes. GHC's standard Handle IO always sets file
> descriptor to non-blocking mode. That's the problem. That's why cat
> works, because it uses blocking IO.

OK, I have referred to fifo(7) regarding this point.  It seems I may need a 
loop trying over and over to open the FIFO in write mode.  It also appears 
that ReadWriteMode appearing to work is Linux-specific, and this behavior is 
left undefined in POSIX.

Does openFd do a non-blocking open?  (Brief testing suggests it does) I'm 
somewhat confused about its semantics, especially since it does not appear 
to correspond directly to open(2).  O_CREAT, for instance, is missing.  

> You would indeed need to use System.Posix to get a FD in blocking mode.
> Then you have to worry a bit about blocking other Haskell thread when
> you block on writing to the pipe.

Fortunately, in this particular case, I'm using forking instead of threading 
so this won't be a problem.

Thanks for the help.

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


Re: [Haskell-cafe] I/O system brokenness with named pipes

2008-04-11 Thread Brandon S. Allbery KF8NH


On Apr 10, 2008, at 21:34 , John Goerzen wrote:

So I have a need to write data to a POSIX named pipe (aka FIFO).  Long
story involving a command that doesn't have an option to read data
from stdin, but can from a named pipe.

I have created the named pipe from Haskell no problem.

But I can't use writeFile to write data to it.  Worse, it returns:

*** Exception: /tmp/bakroller.zD0xHj/fifo: openFile: does not exist
(No such device or address)


The "does not exist" is misleading:  ENXIO ("No such device or  
address"), unless it's being abused by the runtime, indicates  
something's wrong at the kernel level when trying to associate the FIFO.


Using FIFOs properly is actually rather tricky and fidgety.  Can you  
provide the actual code you're using?


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] library version problem

2008-04-11 Thread Leif Frenzel
Hi Vasili,

there is:

http://www.haskell.org/ghc/docs/latest/html/users_guide/packages.html

HTH,
Ciao,
Leif

On Fri, April 11, 2008 4:38 am, Galchin, Vasili wrote:
> Hello,
>
>  Is there better documentation for ghc-pkg than just "help"??
>
> Vasili
>
> On Thu, Apr 10, 2008 at 9:36 PM, Galchin, Vasili <[EMAIL PROTECTED]>
> wrote:
>
>> Hi Philip,
>>
>> Before I got your email, I deregistered unix-2.3.0.0 which made my
>> unix-2.2.0.0 namespace changes visible. However, deregistering seems to
>> made
>> other things worse, e.g. runhaskell Setup.hs configure gives an error
>> message "unknown parameter package: unix-2.3.0.0". Sigh .. how do I get
>> back
>> to where i was in order to do a "hide"?
>>
>> Kind regards, Vasili
>>
>>
>> On Thu, Apr 10, 2008 at 8:22 PM, Philip Weaver <[EMAIL PROTECTED]>
>> wrote:
>>
>> > 2008/4/10 Galchin, Vasili <[EMAIL PROTECTED]>:
>> > > Hello,
>> > >
>> > > I doing work using Linux. The wrong version (for me) of the
>> > unix
>> > > package seems to be visible. I see possibilities to use ghc-pkg to
>> >  suppress
>> > > the unix package that I don't want(2.3.0.0) but that seems
>> dangerious.
>> > > Details are below .  What should I do?
>> >
>> > If you don't want to use it, then it's safe to hide it:
>> >
>> >   ghc-pkg hide unix-2.3.0.0
>> >
>> > You can always unhide it later.
>> >
>> > You can also tell ghc to use a specific version of a package:
>> >
>> >   ghc -package unix-2.2.0.0
>> >
>> > Of course, you'll need to make sure unix-2.2.0.0 is registered with
>> > ghc-pkg.
>> >
>> > >
>> > > Regards, vasili
>> > >
>> > >
>> > >
>> > > When I do:
>> > >
>> > > > ghci
>> > >   :m System.Posix
>> > >
>> > > I am getting the wrong version of the Unix package. I know this to
>> be
>> > true
>> > > because I did
>> > > ghc-pkg latest unix
>> > >
>> > > and got unix-2.3.0.0
>> > >
>> > > I want unix.2.2.0.0 because this version has changes that I made to
>> > the unix
>> > > package.  libHSunix-2.2.0.0.a is installed under
>> > > /usr/local/lib/unix-2.2.0.0/ghc-6.8.2 I did a "nm -a
>> > libHSunix-2.2.0.0.a"
>> > > and found symbols that I added.
>> > >
>> > > ___
>> > >  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
>


-- 
Leif Frenzel
http://leiffrenzel.de
http://cohatoe.blogspot.com

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


Re: [Haskell-cafe] Control.Parallel.Strategies

2008-04-11 Thread Sebastian Sylvan
On Fri, Apr 11, 2008 at 10:43 AM, Don Stewart <[EMAIL PROTECTED]> wrote:

> sebastian.sylvan:
> >On Wed, Apr 9, 2008 at 10:58 PM, Justin Bailey <[EMAIL PROTECTED]
> >
> >wrote:
> >
> >  On Wed, Apr 9, 2008 at 2:25 PM, Sebastian Sylvan
> >  <[EMAIL PROTECTED]> wrote:
> >  > Nope!
> >  >
> >  > This is GHC 6.8.2 btw, downloaded the binary from the web site,
> so
> >  it's
> >  > nothing strange.
> >
> >  On my hyper-threaded CPU, your original code works fine. With -N2,
> I
> >  see 100% CPU. With N1, only 50%. I am also using GHC [3]6.8.2.
> >  Justin
> >
> >Hmm, that's curious. I compile with "ghc --make -threaded partest.hs
> -o
> >par.exe", and then run it with "par.exe +RTS -N2 -RTS". Am I making
> some
> >silly configuration error?
> >Are you running this on windows?
> >
>
> I think its always worth using -O or -O2 too, for what its worth.
>
Yes I've tried both, neither helped.



-- 
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] library version problem

2008-04-11 Thread Ketil Malde
Ketil Malde <[EMAIL PROTECTED]> writes:

> Either rename your modified version to 2.4 (or similar), specify the
> exact version in your *application's* cabal file, 

..or you could compile your application specifying the package
explicitly, using "-package unix-2.2.0.0" (and all the other packages,
normally supplied by Cabal or ghc --make).

> or use "ghc-pkg hide" to hide version 2.3.0.0 from view.

-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/listinfo/haskell-cafe


Re: [Haskell-cafe] I/O system brokenness with named pipes

2008-04-11 Thread Duncan Coutts

On Thu, 2008-04-10 at 20:34 -0500, John Goerzen wrote:

> I have created the named pipe from Haskell no problem.
> 
> But I can't use writeFile to write data to it.  Worse, it returns:
> 
> *** Exception: /tmp/bakroller.zD0xHj/fifo: openFile: does not exist
> (No such device or address)

> What's going on here?  Am I going to have to resort to the
> System.Posix interface just to be able to write to a named pipe?

Named pipes have broken semantics for non-blocking IO, see google or the
man pages on named pipes. GHC's standard Handle IO always sets file
descriptor to non-blocking mode. That's the problem. That's why cat
works, because it uses blocking IO.

You would indeed need to use System.Posix to get a FD in blocking mode.
Then you have to worry a bit about blocking other Haskell thread when
you block on writing to the pipe.

Duncan

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


Re: [Haskell-cafe] I/O system brokenness with named pipes

2008-04-11 Thread Don Stewart
jgoerzen:
> So I have a need to write data to a POSIX named pipe (aka FIFO).  Long
> story involving a command that doesn't have an option to read data
> from stdin, but can from a named pipe.
> 
> I have created the named pipe from Haskell no problem.
> 
> But I can't use writeFile to write data to it.  Worse, it returns:
> 
> *** Exception: /tmp/bakroller.zD0xHj/fifo: openFile: does not exist
> (No such device or address)
> 
> which is completely false, as it *does* exist, and I can cat to it as
> expected.  The call should block until everything is read on the
> remote end.
> 
> I thought maybe writeFile is being weird, so I tried:
> 
> openFile "/tmp/bakroller.zD0xHj/fifo" WriteMode

Hmm, I can get this to work, but only if I have another process waiting
on the pipe already:

$ mkfifo /tmp/pipe
$ tail -f /tmp/pipe $ ghc -e 'writeFile "/tmp/pipe" "test"'
testtesttesttest^C

However, if I don't have 'tail' waiting on the pipe, it fails.

> There is no logical reason I can see for this behavior.  In fact,
> something must be going to *extra* effort to avoid writing to a named
> pipe, and I can't work out why.  Named pipes are a standard, useful
> part of a system and shouldn't be ignored like this.
> 
> Interestingly, readFile works fine on a named pipe.
> 
> What's going on here?  Am I going to have to resort to the
> System.Posix interface just to be able to write to a named pipe?

Something fishy.

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


Re: [Haskell-cafe] Control.Parallel.Strategies

2008-04-11 Thread Don Stewart
sebastian.sylvan:
>On Wed, Apr 9, 2008 at 10:58 PM, Justin Bailey <[EMAIL PROTECTED]>
>wrote:
> 
>  On Wed, Apr 9, 2008 at 2:25 PM, Sebastian Sylvan
>  <[EMAIL PROTECTED]> wrote:
>  > Nope!
>  >
>  > This is GHC 6.8.2 btw, downloaded the binary from the web site, so
>  it's
>  > nothing strange.
> 
>  On my hyper-threaded CPU, your original code works fine. With -N2, I
>  see 100% CPU. With N1, only 50%. I am also using GHC [3]6.8.2.
>  Justin
> 
>Hmm, that's curious. I compile with "ghc --make -threaded partest.hs -o
>par.exe", and then run it with "par.exe +RTS -N2 -RTS". Am I making some
>silly configuration error?
>Are you running this on windows?
> 

I think its always worth using -O or -O2 too, for what its worth.

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


[Haskell-cafe] Re: type families and type signatures

2008-04-11 Thread apfelmus

Tom Schrijvers wrote:

apfelmus wrote:

However, I have this feeling that

 bar :: forall a . Id a -> String

with a type family  Id  *is* parametric in the sense that no matter 
what  a is, the result always has to be the same. Intuitively, that's 
because we may not "pattern match on the branch" of a definition like


 type instance Id String = ..
 type instance Id Int= ..
 ..


But in a degenerate case there could be just this one instance:

type instance Id x = GADT x

which then reduces this example to the GADT case of which you said that 
is was "clearly parametric".


Manuel M T Chakravarty wrote:

type instance Id [a] = GADT a



Oh right, just setting the instance to a GADT makes it non-parametric. 
Still, it's not the type family that is the problem, but "parametricity" 
is not the right word for that. What I want to say is that although the 
type signature


  bar :: forall a . Id a ~ b => b -> String

looks ambiguous, it is not. A trivial example of "seeming" ambiguity 
would be  (foo :: forall a . Int) . Here, parametricity tells us that 
this is not ambiguous.


The proper formulation is probably: a value  f :: forall a . t  is 
/unambiguous/ iff any choices  a1, a2  for  a  that yield the same 
static type necessarily also yield the same dynamic value


 t[a1/a] = t[a2/a]  -- types are equal
  =>  f @ a1 = f @ a2   -- values are equal

In the case of  bar , this would mean that anything not injective like

  type instance Id Int  = Int
  type instance Id Char = Int

would not change the dynamic semantics of  bar  at all, i.e.  (bar @ Int 
:: Int -> String) = (bar @ Char :: Int -> String).


I believe that this is indeed the case for  bar  and for type synonym 
families in general. (Not so for type classes, of course.)



Regards
apfelmus

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


Re: [Haskell-cafe] type families and type signatures

2008-04-11 Thread Martin Sulzmann

Lennart Augustsson wrote:
On Wed, Apr 9, 2008 at 8:53 AM, Martin Sulzmann 
<[EMAIL PROTECTED] > wrote:



Lennart, you said

(It's also pretty easy to fix the problem.)


What do you mean? Easy to fix the type checker, or easy to fix the
program by inserting annotations
to guide the type checker?

Martin

 
I'm referring to the situation where the type inferred by the type 
checker is illegal for me to put into the program.
In our example we can fix this in two ways, by making foo' illegal 
even when it has no signature, or making foo' legal even when it has a 
signature.


To make it illegal:  If foo' has no type signature, infer a type for 
foo', insert this type as a signature and type check again.  If this 
fails, foo' is illegal.


To make it legal: If foo' with a type signature doesn't type check, 
try to infer a type without a signature.  If this succeeds then check 
that the type that was inferred is alpha-convertible to the original 
signature.  If it is, accept foo'; the signature doesn't add any 
information.


Either of these two option would be much preferable to the current 
(broken) situation where the inferred signature is illegal.


I understand now what you meant. See my earlier reply to Claus' email.

Regarding your request to take into account alpha-convertibility when 
checking signatures.

We know that in GHC the check

(forall a, b. Foo a b => a) <= (forall a, c. Foo a c => a)(**)

fails cause when testing the constraint/formula derived from the above 
subsumption check


 forall a, b. Foo a b implies exists c. Foo a c

GHC simply drops the exists c bit and clearly

  Foo a b does NOT imply Foo a c

We need to choose c to be equal to b. I call this process "matching" but 
it's of course

a form of alpha-conversion.
(We convince GHC to accept such signatures but encoding System F style
type application via redundant type proxy arguments)

The point I want to make is that in Chameleon I've implemented a 
subsumption check
which takes into account matching. Therefore, (**) is checkable in 
Chameleon.
BUT matching can be fairly expensive, exponential in the worst case, for 
example

consider cases such as Foo x_i x_i+1
So maybe there's good reason why GHC's subsumption check doesn't take 
into account matching.


The slightly odd thing is that GHC uses a "pessimistic" subsumption 
check (no matching) in combination

with an "optimistic" ambiguity check (see my earlier message on this topic).
I'd say it's better to be pessimistic/pessimistic and 
optimistic/optimistic, maybe this could be

a compiler switch?

Martin

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


Re: [Haskell-cafe] library version problem

2008-04-11 Thread Ketil Malde
"Galchin, Vasili" <[EMAIL PROTECTED]> writes:

>> ghci
>   :m System.Posix
>
> I am getting the wrong version of the Unix package. I know this to be true
> because I did
> ghc-pkg latest unix
>
> and got unix-2.3.0.0
>
> I want unix.2.2.0.0 because this version has changes that I made

Naturally, you'll get 2.3.0.0, since it has the highest version number!

Either rename your modified version to 2.4 (or similar), specify the
exact version in your *application's* cabal file, or use
"ghc-pkg hide" to hide version 2.3.0.0 from view.

-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/listinfo/haskell-cafe


Re: [Haskell-cafe] library version problem

2008-04-11 Thread Galchin, Vasili
I am reading currently ..
http://www.haskell.org/ghc/docs/latest/html/users_guide/packages.html#installed-pkg-info

1) Is ghc-pkg intended to be run by most Haskell developers or should
ghc-pkg be run by "higher level" tools like Cabal??

2) my package database appears to be somewhat comprised after I unregistered
unix-2.3.0.0. I can no longer build the unix package via "runhaskell". ??

Kind regards, Vasili

On Thu, Apr 10, 2008 at 9:39 PM, Galchin, Vasili <[EMAIL PROTECTED]>
wrote:

> e.g. with "register" what is filename .. a path? Is this path to the .a
> (archive) file on Unix systems?
>
> On Thu, Apr 10, 2008 at 9:38 PM, Galchin, Vasili <[EMAIL PROTECTED]>
> wrote:
>
> > Hello,
> >
> >  Is there better documentation for ghc-pkg than just "help"??
> >
> > Vasili
> >
> >
> > On Thu, Apr 10, 2008 at 9:36 PM, Galchin, Vasili <[EMAIL PROTECTED]>
> > wrote:
> >
> > > Hi Philip,
> > >
> > > Before I got your email, I deregistered unix-2.3.0.0 which made my
> > > unix-2.2.0.0 namespace changes visible. However, deregistering seems to 
> > > made
> > > other things worse, e.g. runhaskell Setup.hs configure gives an error
> > > message "unknown parameter package: unix-2.3.0.0". Sigh .. how do I get 
> > > back
> > > to where i was in order to do a "hide"?
> > >
> > > Kind regards, Vasili
> > >
> > >
> > > On Thu, Apr 10, 2008 at 8:22 PM, Philip Weaver <
> > > [EMAIL PROTECTED]> wrote:
> > >
> > > > 2008/4/10 Galchin, Vasili <[EMAIL PROTECTED]>:
> > > > > Hello,
> > > > >
> > > > > I doing work using Linux. The wrong version (for me) of
> > > > the unix
> > > > > package seems to be visible. I see possibilities to use ghc-pkg to
> > > >  suppress
> > > > > the unix package that I don't want(2.3.0.0) but that seems
> > > > dangerious.
> > > > > Details are below .  What should I do?
> > > >
> > > > If you don't want to use it, then it's safe to hide it:
> > > >
> > > >   ghc-pkg hide unix-2.3.0.0
> > > >
> > > > You can always unhide it later.
> > > >
> > > > You can also tell ghc to use a specific version of a package:
> > > >
> > > >   ghc -package unix-2.2.0.0
> > > >
> > > > Of course, you'll need to make sure unix-2.2.0.0 is registered with
> > > > ghc-pkg.
> > > >
> > > > >
> > > > > Regards, vasili
> > > > >
> > > > >
> > > > >
> > > > > When I do:
> > > > >
> > > > > > ghci
> > > > >   :m System.Posix
> > > > >
> > > > > I am getting the wrong version of the Unix package. I know this to
> > > > be true
> > > > > because I did
> > > > > ghc-pkg latest unix
> > > > >
> > > > > and got unix-2.3.0.0
> > > > >
> > > > > I want unix.2.2.0.0 because this version has changes that I made
> > > > to the unix
> > > > > package.  libHSunix-2.2.0.0.a is installed under
> > > > > /usr/local/lib/unix-2.2.0.0/ghc-6.8.2 I did a "nm -a
> > > > libHSunix-2.2.0.0.a"
> > > > > and found symbols that I added.
> > > > >
> > > > > ___
> > > > >  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] type families and type signatures

2008-04-11 Thread Manuel M T Chakravarty

Lennart Augustsson:
On Thu, Apr 10, 2008 at 4:20 AM, Manuel M T Chakravarty <[EMAIL PROTECTED] 
> wrote:

Lennart Augustsson:

On Wed, Apr 9, 2008 at 8:53 AM, Martin Sulzmann <[EMAIL PROTECTED] 
> wrote:


Lennart, you said

(It's also pretty easy to fix the problem.)

What do you mean? Easy to fix the type checker, or easy to fix the  
program by inserting annotations

to guide the type checker?

Martin

I'm referring to the situation where the type inferred by the type  
checker is illegal for me to put into the program.
In our example we can fix this in two ways, by making foo' illegal  
even when it has no signature, or making foo' legal even when it has  
a signature.


To make it illegal:  If foo' has no type signature, infer a type for  
foo', insert this type as a signature and type check again.  If this  
fails, foo' is illegal.


That would be possible, but it means we have to do this for all  
bindings in a program (also all lets bindings etc).


Of course, but I'd rather the compiler did it than I.  It's not that  
hard, btw.  If the whole module type checks, insert all signatures  
and type check again.


Sure.  I did not argue against this.  I think it would be a reasonable  
way forward.


Manuel

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


Re: [Haskell-cafe] type families and type signatures

2008-04-11 Thread Manuel M T Chakravarty

Lennart Augustsson:
In the current GHC there are even definitions that are perfecty  
usable, that cannot be given the type signature that that was  
inferred.


That's bad, I agree.

At work we have the warning for missing signatures enabled, and we  
turn warnings into errors.  We have to disbale this for certain  
definitions, because you cannot give them a signature.  I find that  
broken.


Definitely.  Can you give an example?

Manuel

On Thu, Apr 10, 2008 at 5:52 AM, Manuel M T Chakravarty <[EMAIL PROTECTED] 
> wrote:

Lennart Augustsson:

Let's look at this example from a higher level.

Haskell is a language which allows you to write type signatures for  
functions, and even encourages you to do it.
Sometimes you even have to do it.  Any language feature that stops  
me from writing a type signature is in my opinion broken.
TFs as implemented in currently implemented ghc stops me from  
writing type signatures.  They are thus, in my opinion, broken.


The problem of ambiguity is not at all restricted to TFs.  In fact,  
you need neither TFs nor FDs to get the exact same behaviour.  You  
don't even need MPTCs:


{-# LANGUAGE FlexibleContexts #-}
module Ambiguity where

class C a

bar :: C (a, b) => b -> b
bar = id

bar' :: C (a, b) => b -> b
bar' = bar



This gives us

/Users/chak/Code/haskell/Ambiguity.hs:10:7:
  Could not deduce (C (a, b)) from the context (C (a1, b))
arising from a use of `bar'
 at /Users/chak/Code/haskell/Ambiguity.hs:10:7-9
  Possible fix:
add (C (a, b)) to the context of the type signature for `bar''
or add an instance declaration for (C (a, b))
  In the expression: bar
  In the definition of `bar'': bar' = bar


So, we have this problem as soon as we have flexible contexts and/or  
MPTCs, independent of TFs and FDs.


Manuel


___
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] type families and type signatures

2008-04-11 Thread Manuel M T Chakravarty

Lennart Augustsson:


On Thu, Apr 10, 2008 at 4:20 AM, Manuel M T Chakravarty <[EMAIL PROTECTED] 
> wrote:

the five signatures

 forall a. S a
 forall b. S b
 forall a b. S (a, b)
 Int
 S Int

By alpha-convertible I mean the usual thing from lambda calculus,  
they are identical modulo the names of bound variables.

So only the first two are alpha-convertible to each other.

If you involve any kind of reduction the equivalence test is no  
longer trivial.


All I'm asking for really, is to be able to paste in the type that  
was inferred as the signature, without the compiler complaining.


I think a trivial, purely syntactic test, such as the one proposed,  
would generate at least as much puzzlement as the current situation  
does.  It would mean, you could not have String in your signature if  
the inferred signature has [Char].  I don't think that this is a  
solution at all.


Manuel

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


[Haskell-cafe] http: Network.Browser leaks TCP connections

2008-04-11 Thread Daniel McAllansmith
I've looked into this further and I believe the leaked connections are due to 
Network.Browser, this is a separate issue from that identified by Paul Brown.

The BrowserState in Network.Browser has a connection pool of up to five 
connections.  When a sixth is opened the oldest connection is closed.  This 
looks to be the only time that a connection is closed.
BrowserState's internals are not exported so there is no way for a user to 
close them.

The net effect for HXT is that every time readDocument is called, using native 
http, a single TCP connection is leaked.

I've attached a patch against the darcs version of http that cures my test 
programs leak.

Cheers
Daniel

New patches:

[Make browse close pooled connections to prevent them leaking.
'Daniel McAllansmith <[EMAIL PROTECTED]>'**20080411025515
 The closing of the connections needs to be made exception safe.  Should try to
 close every connection before breaking out with an exception.  Currently an
 exception may allow connections to leak.
] {
hunk ./Network/Browser.hs 656
-browse act = do x <- lift act defaultBrowserState
-return (snd x)
+browse act = do (bs, x) <- lift act defaultBrowserState
+closePooledConnections bs
+return x
hunk ./Network/Browser.hs 675
+-- |
+-- Close all connections that are in bs' connection pool.
+-- This should have some sort of exception handling, soldier on until
+-- all the connections have been closed.  Not sure about portability
+-- issues.
+closePooledConnections :: BrowserState -> IO ()
+closePooledConnections = mapM_ close . bsConnectionPool
+
}

Context:

[Bump version number to 3001.1.0. Incremented minor number since the patch from Eric Mertens extends the API.
[EMAIL PROTECTED] 
[Export getRequestHead and processRequest, add support for custom RequestMethods
Eric Mertens <[EMAIL PROTECTED]>**20080305190759] 
[Include uriQuery in request line.
[EMAIL PROTECTED] 
[Send abs_path as Request-URI to comply with HTTP 1.1 spec.
'Daniel McAllansmith <[EMAIL PROTECTED]>'**20080128053024
 RFC2616 Section 5.1.2 specifies that abs_path MUST be used to identify a resource on a origin server or gateway, not absoluteURI which is for use with proxies.
 
 Change Request's Show instance to use /path/to/resource rather than
 http://server/path/to/resource.
] 
[Bump version to 3001.0.4
[EMAIL PROTECTED] 
[Expose Network.HTTP.Headers in cabal file
Eric Mertens <[EMAIL PROTECTED]>**20071212220235
 
 Failure to do this breaks :browse functionality in GHCi
 as well as makes these useful functions unavailable
] 
[Resolved conflicts in Network.Stream.
[EMAIL PROTECTED] 
[Resolve conflict in HTTP.cabal.
[EMAIL PROTECTED] 
[Split Header functionality into Network.HTTP.Headers module.
[EMAIL PROTECTED] 
[Added files to .cabal file, made deps explicit in Network.TCP module.
[EMAIL PROTECTED] 
[Refactored Network.Stream.
[EMAIL PROTECTED] 
[Made more deps explicit.
[EMAIL PROTECTED] 
[Made dependencies explicit in import statements.
[EMAIL PROTECTED] 
[Bumped version number to 3001.0.3.
[EMAIL PROTECTED] 
[Change myrecv to allow a 0 length. Suggested by Eric Mertens.
[EMAIL PROTECTED]
 On Wed, 2007-08-15 at 23:25 +0200, Bjorn Bringert wrote:
 Why doesn't the existing code work? Does recv fail when given 0?
 
 On Nov 30, 2007, at 23:36 , Eric Mertens wrote:
 Yes, recv can not cope with an argument of 0
 
 http://darcs.haskell.org/packages/network/Network/Socket.hsc
 
 recv :: Socket -> Int -> IO String
 recv sock l = recvLen sock l >>= \ (s,_) -> return s
 
 recvLen :: Socket -> Int -> IO (String, Int)
 recvLen sock@(MkSocket s _family _stype _protocol status) nbytes 
  | nbytes <= 0 = ioError (mkInvalidRecvArgError "Network.Socket.recv")
 
] 
[Set version number to 3001.0.2.
[EMAIL PROTECTED] 
[Change version to 3001.0.1.
[EMAIL PROTECTED] 
[Don't treat any chunk size starting with '0' as a 0 chunk size.
[EMAIL PROTECTED]
 Radosław Grzanka reported that Network.HTTP can't get http://www.podshow.com/feeds/gbtv.xml, see http://article.gmane.org/gmane.comp.lang.haskell.cafe/31783
 
 This turned out to be a bug in how Network.HTTP handled Chunked Transfer Encoding. The web server sent the chunk size as "4000" (according to RFC 2616 this can be non-empty sequence of hex digits). However, Network.HTTP treated any chunk size starting with '0' as a chunk size of 0, which indicates the end of the chunked encoding. 
] 
[TAG 3001.0.0
Duncan Coutts <[EMAIL PROTECTED]>**20071021133823] 
Patch bundle hash:
2606de184a3abe46c8095959a11a2f60575ceada
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] library version problem

2008-04-11 Thread Galchin, Vasili
e.g. with "register" what is filename .. a path? Is this path to the .a
(archive) file on Unix systems?

On Thu, Apr 10, 2008 at 9:38 PM, Galchin, Vasili <[EMAIL PROTECTED]>
wrote:

> Hello,
>
>  Is there better documentation for ghc-pkg than just "help"??
>
> Vasili
>
>
> On Thu, Apr 10, 2008 at 9:36 PM, Galchin, Vasili <[EMAIL PROTECTED]>
> wrote:
>
> > Hi Philip,
> >
> > Before I got your email, I deregistered unix-2.3.0.0 which made my
> > unix-2.2.0.0 namespace changes visible. However, deregistering seems to made
> > other things worse, e.g. runhaskell Setup.hs configure gives an error
> > message "unknown parameter package: unix-2.3.0.0". Sigh .. how do I get back
> > to where i was in order to do a "hide"?
> >
> > Kind regards, Vasili
> >
> >
> > On Thu, Apr 10, 2008 at 8:22 PM, Philip Weaver <[EMAIL PROTECTED]>
> > wrote:
> >
> > > 2008/4/10 Galchin, Vasili <[EMAIL PROTECTED]>:
> > > > Hello,
> > > >
> > > > I doing work using Linux. The wrong version (for me) of the
> > > unix
> > > > package seems to be visible. I see possibilities to use ghc-pkg to
> > >  suppress
> > > > the unix package that I don't want(2.3.0.0) but that seems
> > > dangerious.
> > > > Details are below .  What should I do?
> > >
> > > If you don't want to use it, then it's safe to hide it:
> > >
> > >   ghc-pkg hide unix-2.3.0.0
> > >
> > > You can always unhide it later.
> > >
> > > You can also tell ghc to use a specific version of a package:
> > >
> > >   ghc -package unix-2.2.0.0
> > >
> > > Of course, you'll need to make sure unix-2.2.0.0 is registered with
> > > ghc-pkg.
> > >
> > > >
> > > > Regards, vasili
> > > >
> > > >
> > > >
> > > > When I do:
> > > >
> > > > > ghci
> > > >   :m System.Posix
> > > >
> > > > I am getting the wrong version of the Unix package. I know this to
> > > be true
> > > > because I did
> > > > ghc-pkg latest unix
> > > >
> > > > and got unix-2.3.0.0
> > > >
> > > > I want unix.2.2.0.0 because this version has changes that I made to
> > > the unix
> > > > package.  libHSunix-2.2.0.0.a is installed under
> > > > /usr/local/lib/unix-2.2.0.0/ghc-6.8.2 I did a "nm -a
> > > libHSunix-2.2.0.0.a"
> > > > and found symbols that I added.
> > > >
> > > > ___
> > > >  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] library version problem

2008-04-11 Thread Galchin, Vasili
Hello,

 Is there better documentation for ghc-pkg than just "help"??

Vasili

On Thu, Apr 10, 2008 at 9:36 PM, Galchin, Vasili <[EMAIL PROTECTED]>
wrote:

> Hi Philip,
>
> Before I got your email, I deregistered unix-2.3.0.0 which made my
> unix-2.2.0.0 namespace changes visible. However, deregistering seems to made
> other things worse, e.g. runhaskell Setup.hs configure gives an error
> message "unknown parameter package: unix-2.3.0.0". Sigh .. how do I get back
> to where i was in order to do a "hide"?
>
> Kind regards, Vasili
>
>
> On Thu, Apr 10, 2008 at 8:22 PM, Philip Weaver <[EMAIL PROTECTED]>
> wrote:
>
> > 2008/4/10 Galchin, Vasili <[EMAIL PROTECTED]>:
> > > Hello,
> > >
> > > I doing work using Linux. The wrong version (for me) of the
> > unix
> > > package seems to be visible. I see possibilities to use ghc-pkg to
> >  suppress
> > > the unix package that I don't want(2.3.0.0) but that seems dangerious.
> > > Details are below .  What should I do?
> >
> > If you don't want to use it, then it's safe to hide it:
> >
> >   ghc-pkg hide unix-2.3.0.0
> >
> > You can always unhide it later.
> >
> > You can also tell ghc to use a specific version of a package:
> >
> >   ghc -package unix-2.2.0.0
> >
> > Of course, you'll need to make sure unix-2.2.0.0 is registered with
> > ghc-pkg.
> >
> > >
> > > Regards, vasili
> > >
> > >
> > >
> > > When I do:
> > >
> > > > ghci
> > >   :m System.Posix
> > >
> > > I am getting the wrong version of the Unix package. I know this to be
> > true
> > > because I did
> > > ghc-pkg latest unix
> > >
> > > and got unix-2.3.0.0
> > >
> > > I want unix.2.2.0.0 because this version has changes that I made to
> > the unix
> > > package.  libHSunix-2.2.0.0.a is installed under
> > > /usr/local/lib/unix-2.2.0.0/ghc-6.8.2 I did a "nm -a
> > libHSunix-2.2.0.0.a"
> > > and found symbols that I added.
> > >
> > > ___
> > >  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] library version problem

2008-04-11 Thread Galchin, Vasili
Hi Philip,

Before I got your email, I deregistered unix-2.3.0.0 which made my
unix-2.2.0.0 namespace changes visible. However, deregistering seems to made
other things worse, e.g. runhaskell Setup.hs configure gives an error
message "unknown parameter package: unix-2.3.0.0". Sigh .. how do I get back
to where i was in order to do a "hide"?

Kind regards, Vasili

On Thu, Apr 10, 2008 at 8:22 PM, Philip Weaver <[EMAIL PROTECTED]>
wrote:

> 2008/4/10 Galchin, Vasili <[EMAIL PROTECTED]>:
> > Hello,
> >
> > I doing work using Linux. The wrong version (for me) of the unix
> > package seems to be visible. I see possibilities to use ghc-pkg to
>  suppress
> > the unix package that I don't want(2.3.0.0) but that seems dangerious.
> > Details are below .  What should I do?
>
> If you don't want to use it, then it's safe to hide it:
>
>   ghc-pkg hide unix-2.3.0.0
>
> You can always unhide it later.
>
> You can also tell ghc to use a specific version of a package:
>
>   ghc -package unix-2.2.0.0
>
> Of course, you'll need to make sure unix-2.2.0.0 is registered with
> ghc-pkg.
>
> >
> > Regards, vasili
> >
> >
> >
> > When I do:
> >
> > > ghci
> >   :m System.Posix
> >
> > I am getting the wrong version of the Unix package. I know this to be
> true
> > because I did
> > ghc-pkg latest unix
> >
> > and got unix-2.3.0.0
> >
> > I want unix.2.2.0.0 because this version has changes that I made to the
> unix
> > package.  libHSunix-2.2.0.0.a is installed under
> > /usr/local/lib/unix-2.2.0.0/ghc-6.8.2 I did a "nm -a
> libHSunix-2.2.0.0.a"
> > and found symbols that I added.
> >
> > ___
> >  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] I/O system brokenness with named pipes

2008-04-11 Thread John Goerzen
So I have a need to write data to a POSIX named pipe (aka FIFO).  Long
story involving a command that doesn't have an option to read data
from stdin, but can from a named pipe.

I have created the named pipe from Haskell no problem.

But I can't use writeFile to write data to it.  Worse, it returns:

*** Exception: /tmp/bakroller.zD0xHj/fifo: openFile: does not exist
(No such device or address)

which is completely false, as it *does* exist, and I can cat to it as
expected.  The call should block until everything is read on the
remote end.

I thought maybe writeFile is being weird, so I tried:

openFile "/tmp/bakroller.zD0xHj/fifo" WriteMode

Same thing.

There is no logical reason I can see for this behavior.  In fact,
something must be going to *extra* effort to avoid writing to a named
pipe, and I can't work out why.  Named pipes are a standard, useful
part of a system and shouldn't be ignored like this.

Interestingly, readFile works fine on a named pipe.

What's going on here?  Am I going to have to resort to the
System.Posix interface just to be able to write to a named pipe?

-- John

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


Re: [Haskell-cafe] Fighting the monad stack, MonadIO

2008-04-11 Thread Ryan Ingram
On 4/10/08, Adam Smyczek <[EMAIL PROTECTED]> wrote:
> If yes, is this a general concept/pattern
> how to hide functionality of a underlying monad,
> in this case hide IO entirely?

Yes, that's correct, although with IO you can't hide it entirely;
eventually you need a way to actually run the computation, and if
that's built on IO there's no way to do that without at least a way to
get -back- to the IO Monad.

On the other hand, you can use this to encapsulate "sandboxed" computations:

> module Console (Console, execConsole, consoleGetLine, consolePutLine)
> where

> newtype Console a = MkConsole { execConsole :: IO a }
>   deriving (Monad, Functor)

> consoleGetLine :: Console String
> consoleGetLine = MkConsole getLine

> consolePutLine :: String -> Console ()
> consolePutLine = MkConsole . putStrLn

MkConsole is a private constructor not exported from this module, so
the only way to construct one is via the operations we provide and the
monad/functor operations.  So we can prove that these operations never
do any network access, or file I/O, or weird pointer access.

Of course, with unsafeCoerce# and/or unsafePerformIO, client code can
break either/both of these claims:

> runConsole :: Console a -> a
> runConsole = unsafePerformIO . execConsole

> instance MonadIO Console where
>liftIO = unsafeCoerce#
>-- works because newtype is guaranteed not to change
>-- the runtime representation

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


Re: [Haskell-cafe] Fighting the monad stack, MonadIO

2008-04-11 Thread Derek Elkins
On Thu, 2008-04-10 at 11:53 -0700, Adam Smyczek wrote:
> Thanks a lot for all explanations!
> 
> It looks like 'ioAction' is the key to the solution
> and if the Browser module did not provide/expose
> this function, no IO actions could be run inside
> the BrowserAction monad?
> 
> If yes, is this a general concept/pattern
> how to hide functionality of a underlying monad,
> in this case hide IO entirely?

Yes, only there is nothing particular to monads.  This would be just
utilizing a standard abstract data type.

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


Re: [Haskell-cafe] Longest increasing subsequence

2008-04-11 Thread Ariel J. Birnbaum
>   liss = maximumBy length . filter ascending . concat . map inits . tails
Of course my solution is braindamaged since I skipped this bit of the 
definition: [quote]Note that subsequence we are searching for is not 
necessarily contiguous[/quote]. Like the article says, without this detail 
the problem is quite trivial =P
Replace
concat . map inits . tails
with
foldr (\x xss -> xss ++ map (x:) xss) [[]] 

for a correct (yet even more inefficient) solution.
I'd blame the mistake on the late hour, but it was even later when I 
noticed... *shame*
-- 
Ariel J. Birnbaum
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ghc

2008-04-11 Thread Cetin Sert
moving a binary compiled on a 32-bit machine running Linux to a 64-bit one,
would that necessitate recompilation on the target machine or
cross-compilation or can 64-bit Linux run 32-bit binaries?

2008/4/11 Jake Mcarthur <[EMAIL PROTECTED]>:

> On Apr 10, 2008, at 1:20 PM, Brent Yorgey wrote:
>
>  This is true for any compiler that produces native binaries (as opposed
> > to certain languages which require a virtual machine...)
> >
>
> Unless, of course, it results in a dynamically linked binary, which I'm
> pretty sure GHC doesn't support at all anyway (unless that has changed?).
>
> — Jake
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Longest increasing subsequence

2008-04-11 Thread ChrisK
It is late, but I was not sleepy enough, so here is my first translation of the 
algorithm to a functional approach...



{- Quote wikipedia: http://en.wikipedia.org/wiki/Longest_increasing_subsequence

 L = 0
 M[0] = 0
 for i = 1, 2, ... n:
binary search for the largest j ≤ L such that X[M[j]] < X[i] (or set j = 0 
if no such value exists)

P[i] = M[j]
if j == L or X[i] < X[M[j+1]]:
   M[j+1] = i
   L = max(L, j+1)
-}

{-
X[i] defined for i = 1,2,3…
So X[0] is not defined.
Now, rethink '0' as Nothing, and 1≤j≤L since X[M[0]] is also undefined.

Not that after the binary search that one the three conditions holds:

X[i] ≤ X[M[1]]
  "The same or a new minimum value"
  P[i] is created and set to Nothing
  If X[i] < X[M[1]] then M[1] is changed to i

X[M[j]] < X[i] ≤ X[M[j+1]] for some jWikipedia is too loose.  X[M[1]], X[M[2]], …, X[M[L]] is not "nondecreasing", 
but must be strictly increasing.  This is really sloppy of wikipedia.


The P[i] are just a stack, create a linked list going in and pull
apart on way out, will by O(N).

If you do not separately track the min and max values, then the
algorithm works like this:

Make a map mu from the set of X[M[j]] to M[j], starting empty.
Make a P as a list of Maybe Int, starting as [].
Note that "size mu" will always by L, and starts off as 0.
For i=1,2,3…:
 do a Data.Map.splitLookup using pivot X[i] to get (map1,m,map2) and find which
 of the three cases we are in:
  If there is a null map2 then third case:
If empty mu then prepend Nothing to P.
  else get "M[L]" from "snd (snd (findMax mu))", prepend Just "M[L]" to P.
Create new my by inserting key X[i] with value i to mu.
  If there is a null map1 then first case (Note that mu cannot be empty):
Prepend Nothing to P
get min from "fst (findMin mu)"
If X[i] < min then make new mu from replacing key X[i] with value i
   with (Data.Map.updateMin).
  Otherwise this is the middle case and map1 and map2 are both non-empty.
Get "M[j]" from (snd (findMax map1)) and prepend Just "M[j]" to P.
If 'm' is (Just {}) then "X[i] < X[M[j+1]]" and do not change mu
  else change mu to Data.Map.adjust key X[i] with value i on mu

Also: keep track of the length of P, which is ultimate N, where 1≤i≤N.

Each operation in the loop with index i is order "log (i-1)"

Note that the "j" is never explicitly tracked.  It is implicit in the order of 
the keys of the map "mu".


Once you are done, you have a maximum subsequence length of (size mu),
and the stack P is just the P[i]'s in reverse order.  You can get the
last index i of the longest subsequence from (snd (findMax mu)) and
backtrack to get the other i's by carefully popping the stack P (in a
single traversal) and keeping only the indices you need until you
reach a Nothing.

-}

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


Re: [Haskell-cafe] Longest increasing subsequence

2008-04-11 Thread ajb

G'day all.

Quoting Matt Amos <[EMAIL PROTECTED]>:


http://en.wikipedia.org/wiki/Longest_increasing_subsequence

The most efficient algorithm relies on destructive updates, so a
simple translation doesn't seem possible.


Given that it's based on binary search, you might like to try using a
binary search tree.

You may or may not have discovered that the quadratic algorithm has a
more-or-less direct translation into Haskell using lazy arrays.  Did you
have a go at implementing that first?

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


Re: [Haskell-cafe] ghc

2008-04-11 Thread Jake Mcarthur

On Apr 10, 2008, at 1:20 PM, Brent Yorgey wrote:

This is true for any compiler that produces native binaries (as  
opposed to certain languages which require a virtual machine...)


Unless, of course, it results in a dynamically linked binary, which  
I'm pretty sure GHC doesn't support at all anyway (unless that has  
changed?).


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


[Haskell-cafe] Re: ghc

2008-04-11 Thread Braden Shepherdson

Cetin Sert wrote:

Hi,

Is GHC required to be installed on the target OS I compile Haskell 
binaries for in order for these binaries to run? I need a quick answer 
on that!


By the way there is no computer in the 4 or so networks I have online 
access to on which ghc is not installed, which might be a sign people 
like haskell here in Heidelberg/Mannheim, Germany.


Best Regards,
Cetin Sert




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


No, GHC is not required. Compiling on the same OS and architecture will 
produce an executable that can be sent standalone to users.


If it uses any external libraries (GTK, for example) then these 
libraries will need to be installed as well. Generally it is not necessary.



Braden Shepherdson
shepheb

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