[Haskell-cafe] (Un)termination of overloading resolution
[EMAIL PROTECTED] writes: > > Martin Sulzmann wrote: > > > Let's consider the general case (which I didn't describe in my earlier > > email). > > In case we have an n-ary type function T (or (n+1)-ary type class > > constraint T) the conditions says for each > > > > type T t1 ... tn = t > > > > (or rule T t1 ... tn x ==> t) > > > > then rank(ti) > rank(t) for each i=1,..,n > > ... > > > Sorry, I left out the precise definition of the rank function > > in my previous email. Here's the formal definition. > > > > rank(x) is some positive number for variable x > > > > rank(F t1 ... tn) = 1 + rank t1 + ... + rank tn > > > > where F is an n-ary type constructor. > > > > rank (f t) = rank f + rank t > > > > f is a functor variable > > Yes, I was wondering what rank means exactly. But now I do > have a problem with the criterion itself. The following simple and > quite common code > > > newtype MyIOState a = MyIOState (Int -> IO (a,Int)) > > > > instance Monad MyIOState where > > return x = MyIOState (\s -> return (x,s)) > > > > instance MonadState Int MyIOState where > > put x = MyIOState (\s -> return ((),x)) > > > becomes illegal then? Indeed, the class |MonadState s m| has a > functional dependency |m -> s|. In our case, > m = MyIOState, rank MyIOState = 1 > s = Intrank Int = 1 > and so rank(m) > rank(s) is violated, right? > > The additional conditions I propose are only necesssary once we break the Bound Variable Condition. Recall: The Bound Variable Condition (BV Condition) says: for each instance C => TC ts we have that fv(C) subsetof fv(ts) (the same applies to (super)class declarations which I leave out here). The above MonadState instance does NOT break the BV Condition. Hence, everything's fine here, the FD-CHR results guarantee that type inference is sound, complete and decidable. Though, your earlier example breaks the BV Condition. > class Foo m a where > foo :: m b -> a -> Bool > > instance Foo m () where > foo _ _ = True > > instance (E m a b, Foo m b) => Foo m (a->()) where > foo m f = undefined > > class E m a b | m a -> b where > tr :: m c -> a -> b > instance E m (() -> ()) (m ()) In the second instance, variable b appears only in the context but not in the instance head. But variable b is "captured" by the constraint E m a b where m and a appear in the instance head and we have that class E m a b | m a -> b. We say that this instance satisfies the Weak Coverage Condition. The problem is that Weak Coverage does not guarantee termination. See this and the earlier examples we have discussed so far. To obtain termination, I propose to impose stronger conditions on improvement rules (see above). My guess is that thus we obtain termination. If we can guarantee termination, we know that Weak Coverage guarantees confluence. Hence, we can restore sound, complete and decidable type inference. > BTW, the above definition of the rank is still incomplete: it doesn't say > what rank(F t1 ... tm) is where F is an n-ary type constructor and > m < n. Hopefully, the rank of an incomplete type application is bounded > (otherwise, I have a non-termination example in mind). If the rank is > bounded, then the problem with defining an instance of MonadState > persists. For example, I may wish for a more complex state (which is > realistic): > > > newtype MyIOState a = MyIOState (Int -> IO (a,(Int,String,Bool))) > > instance MonadState (Int,String,Bool) MyIOState > > Now, the rank of the state is 4... > The simple solution might be for any n-ary type constructor F rank(F t1 ... tm) = 1 + rank t1 + ... + rank tm where m<=n This might be too naive, I don't know. I haven't thought about the case where we need to compute the rank of a type constructor. Though, the style of termination proof I'm using dates back to Prolog which we know is untyped. Hence, there might not be any problem after all? Martin ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] (Un)termination of overloading resolution
Martin Sulzmann wrote: > Let's consider the general case (which I didn't describe in my earlier > email). > In case we have an n-ary type function T (or (n+1)-ary type class > constraint T) the conditions says for each > > type T t1 ... tn = t > > (or rule T t1 ... tn x ==> t) > > then rank(ti) > rank(t) for each i=1,..,n ... > Sorry, I left out the precise definition of the rank function > in my previous email. Here's the formal definition. > > rank(x) is some positive number for variable x > > rank(F t1 ... tn) = 1 + rank t1 + ... + rank tn > > where F is an n-ary type constructor. > > rank (f t) = rank f + rank t > > f is a functor variable Yes, I was wondering what rank means exactly. But now I do have a problem with the criterion itself. The following simple and quite common code > newtype MyIOState a = MyIOState (Int -> IO (a,Int)) > > instance Monad MyIOState where > return x = MyIOState (\s -> return (x,s)) > > instance MonadState Int MyIOState where > put x = MyIOState (\s -> return ((),x)) becomes illegal then? Indeed, the class |MonadState s m| has a functional dependency |m -> s|. In our case, m = MyIOState, rank MyIOState = 1 s = Intrank Int = 1 and so rank(m) > rank(s) is violated, right? BTW, the above definition of the rank is still incomplete: it doesn't say what rank(F t1 ... tm) is where F is an n-ary type constructor and m < n. Hopefully, the rank of an incomplete type application is bounded (otherwise, I have a non-termination example in mind). If the rank is bounded, then the problem with defining an instance of MonadState persists. For example, I may wish for a more complex state (which is realistic): > newtype MyIOState a = MyIOState (Int -> IO (a,(Int,String,Bool))) > instance MonadState (Int,String,Bool) MyIOState Now, the rank of the state is 4... ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] (Un)termination of overloading resolution
[EMAIL PROTECTED] writes: > > > Let's consider the general case (which I didn't describe in my earlier > > email). > > > > In case we have an n-ary type function T (or (n+1)-ary type class > > constraint T) the conditions says for each > > > > type T t1 ... tn = t > > > > (or rule T t1 ... tn x ==> t) > > > > then rank(ti) > rank(t) for each i=1,..,n > > I didn't know what condition you meant for the general form. But the > condition above is not sufficient either, as a trivial modification of the > example shows. The only modification is > > instance E ((->) (m ())) (() -> ()) (m ()) where > > and > test = foo (undefined::((() -> ()) -> ()) -> ()) (\f -> (f ()) :: ()) > > Now we have t1 = ((->) (m ())) : two constructors, one variable > t2 = () -> (): three constructors > t = m (): one constructor, one variable > > and yet GHC 6.4.1 loops in the typechecking phase as before. rank (() ->()) > rank (m ()) does NOT hold. Sorry, I left out the precise definition of the rank function in my previous email. Here's the formal definition. rank(x) is some positive number for variable x rank(F t1 ... tn) = 1 + rank t1 + ... + rank tn where F is an n-ary type constructor. rank (f t) = rank f + rank t f is a functor variable Hence, rank (()->()) = 3 rank (m ()) = rank m + 1 We cannot verify that 3 > rank m + 1. So, I still claim my conjecture is correct. Martin P. S. Oleg, can you next time please provide more details why type inference does not terminate. This will help others to follow our discussion. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] (Un)termination of overloading resolution
> Let's consider the general case (which I didn't describe in my earlier > email). > > In case we have an n-ary type function T (or (n+1)-ary type class > constraint T) the conditions says for each > > type T t1 ... tn = t > > (or rule T t1 ... tn x ==> t) > > then rank(ti) > rank(t) for each i=1,..,n I didn't know what condition you meant for the general form. But the condition above is not sufficient either, as a trivial modification of the example shows. The only modification is instance E ((->) (m ())) (() -> ()) (m ()) where and test = foo (undefined::((() -> ()) -> ()) -> ()) (\f -> (f ()) :: ()) Now we have t1 = ((->) (m ())) : two constructors, one variable t2 = () -> (): three constructors t = m (): one constructor, one variable and yet GHC 6.4.1 loops in the typechecking phase as before. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] (Un)termination of overloading resolution
This is not a counter-example to my conjecture. Let's consider the general case (which I didn't describe in my earlier email). In case we have an n-ary type function T (or (n+1)-ary type class constraint T) the conditions says for each type T t1 ... tn = t (or rule T t1 ... tn x ==> t) then rank(ti) > rank(t) for each i=1,..,n Your example violates this condition > class E m a b | m a -> b > instance E m (() -> ()) (m ()) The improvement rule says: rule E m (() -> ()) x ==> x=(m ()) but rank m < rank (m ()) Your example shows that the condition rank(t1)+...+rank(tn) > rank(t) is not sufficient (but that's not a surprise). Program text > test = foo (\f -> (f ()) :: ()) (\f -> (f ()) :: ()) gives rise to Foo ((->) (() -> ())) ((() -> ()) -> ()) via > instance (E m a b, Foo m b) => Foo m (a->()) where this constraint reduces to E ((->) (() -> ())) (()->()) x Foo ((->) (() -> ())) x the above improvement yields x = (((->) (() -> ( () this leads to Foo ((->) (() -> ())) ->) (() -> ( ()) and so on (the second component is increasing). So, I'll stick to my claim. I don't think I have time at the moment to work out the details of my claim/proof sketch. But if somebody is interested. The following is a good reference how to attack the problem: @inproceedings{thom-term, author = "T. Fr{\"u}hwirth", title = "Proving Termination of Constraint Solver Programs", booktitle = "Proc.\ of New Trends in Constraints: Joint {ERCIM/Compulog} Net Workshop", volume = "1865", series = "LNAI", publisher = "Springer-Verlag", year = "2000" } Martin [EMAIL PROTECTED] writes: > > Martin Sulzmann wrote: > > > - The type functions are obviously terminating, e.g. > > type T [a] = [[a]] clearly terminates. > > - It's the devious interaction between instances/superclasss > > and type function which causes the type class program > > not to terminate. > > > > Is there a possible fix? Here's a guess. > > For each type definition in the AT case > > > > type T t1 = t2 > > > > (or improvement rule in the FD case > > > > rule T1 t1 a ==> a=t2 > > > > we demand that the number of constructors in t2 > > is strictly smaller than the in t1 > > (plus some of the other usual definitions). > > I'm afraid that may still be insufficient, as the following > counter-example shows. It causes GHC 6.4.1 to loop in the typechecking > phase. I haven't checked the latest GHC. The example corresponds to a > type function (realized as a class E with functional dependencies) in > the context of an instance. The function in question is > > class E m a b | m a -> b > instance E m (() -> ()) (m ()) > > We see that the result of the function, "m ()" is smaller (in the > number of constructors) that the functions' arguments, "m" and > "() -> ()" together. Plus any type variable free in the result is also > free in at least one of the arguments. And yet it loops. > > > > {-# OPTIONS -fglasgow-exts #-} > -- Note the absence of the flag -fallow-undecidable-instances > > module F where > > class Foo m a where > foo :: m b -> a -> Bool > > instance Foo m () where > foo _ _ = True > > instance (E m a b, Foo m b) => Foo m (a->()) where > foo m f = undefined > > class E m a b | m a -> b where > tr :: m c -> a -> b > > -- There is only one instance of the class with functional dependencies > instance E m (() -> ()) (m ()) where > tr x = undefined > > -- GHC(i) loops > > test = foo (\f -> (f ()) :: ()) (\f -> (f ()) :: ()) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] (Un)termination of overloading resolution
Martin Sulzmann wrote: > - The type functions are obviously terminating, e.g. > type T [a] = [[a]] clearly terminates. > - It's the devious interaction between instances/superclasss > and type function which causes the type class program > not to terminate. > > Is there a possible fix? Here's a guess. > For each type definition in the AT case > > type T t1 = t2 > > (or improvement rule in the FD case > > rule T1 t1 a ==> a=t2 > > we demand that the number of constructors in t2 > is strictly smaller than the in t1 > (plus some of the other usual definitions). I'm afraid that may still be insufficient, as the following counter-example shows. It causes GHC 6.4.1 to loop in the typechecking phase. I haven't checked the latest GHC. The example corresponds to a type function (realized as a class E with functional dependencies) in the context of an instance. The function in question is class E m a b | m a -> b instance E m (() -> ()) (m ()) We see that the result of the function, "m ()" is smaller (in the number of constructors) that the functions' arguments, "m" and "() -> ()" together. Plus any type variable free in the result is also free in at least one of the arguments. And yet it loops. {-# OPTIONS -fglasgow-exts #-} -- Note the absence of the flag -fallow-undecidable-instances module F where class Foo m a where foo :: m b -> a -> Bool instance Foo m () where foo _ _ = True instance (E m a b, Foo m b) => Foo m (a->()) where foo m f = undefined class E m a b | m a -> b where tr :: m c -> a -> b -- There is only one instance of the class with functional dependencies instance E m (() -> ()) (m ()) where tr x = undefined -- GHC(i) loops test = foo (\f -> (f ()) :: ()) (\f -> (f ()) :: ()) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Constructor classes implementation
sean.seefried: > >> > >I still don't see clearly. So you've implemented the type inference > >algorithm from Jones' paper, good. But is there any significance or > >gain, apart from it being a nice and interesting exercise? > > No. Nor did I state that there was. There's a reason I posted this > to Haskell-cafe and not Haskell. I just thought the code might be > useful for other people who were similarly trying to understand how > constructor classes are implemented. The only other code I found > (that wasn't inside a compiler) was that associated with the "Typing > Haskell in Haskell" paper. The nice thing about the algorithm in "A > system of constructor classes: ..." is that it is small and to-the- > point. Seems like useful code to me. The more the merrier :) -- Don ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: standard poll/select interface
On Tue, 21 Feb 2006, John Meacham wrote: > Yeah, this is why I have held off on a specific design until we get a > better idea of what the new IO library will look like. I am thinking it > will have to involve some abstract event source type with primitive > routines for creating this type from things like handles,fds, or > anything else we might want to wait on. so it is system-extendable in > that sense in that implementations can just provide new event source > creation primitives. > > The other advantage of this sort of thing is that you would want things > like the X11 library to be able to provide an event source for when an > X11 event is ready to be read so you can seamlessly integrate your X11 > loop into your main one. > > The X11 library would create such an event source from the underlying > socket but just return the abstract event source so the implementation > can change (perhaps when using a shared memory based system like D11 for > instance) without affecting how the user uses the library in a portable > way. Could an application reasonably choose between several dispatching systems? For example, I'm working on a Macintosh here, where instead of X11 Apple provides its NextStep based GUI with its own apparently fairly well defined event system. I don't know that system very well, but a MacOS Haskell GUI application would probably want to look in that direction for event integration. Meanwhile, I might want to work with kqueue, on the same platform, because it supports filesystem events along with the usual select stuff. Donn Cave, [EMAIL PROTECTED] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] typesafe non-local returns in the IO monad
On Tue, Feb 21, 2006 at 01:07:51PM -, Simon Peyton-Jones wrote: > I'm not sure this works. Consider this > > newContinuation (\k -> return (callContinuation k)) ... > > The partial application (callContinuation k) has no 's' in its type, and so > can go anywhere. Ah, you are right. silly me, I thought I had come up with something clever.. I don't see any good way to fix this in the IO monad proper off the top of my head.. I think I will still provide the primitives in jhc for now but put a big caveat in the docs since they might still be useful to use internally in some safe library (and you can already shoot yourself in the IO monad). but I am much less happy about them. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Constructor classes implementation
Thank you for taking the time to look through the code. 1. printGamma [] would print an unmotivated " }", as witnessed by typeInf [] term14. 2. the case unify (ConT c) (AppT t1 t2) is missing. and unifying a tyvar with itself fails. That probably doesn't occur in the inference-algorithm, but still... And that case is in the paper, so I should have implemented it. I have now. 3. too many shadowed bindings, this is always dangerous, I believe 4. I'm not sure, the datatypes are appropriate; as far as I know, expressions have a type and not a kind, which is what the use of the same Var type for Type and Exp entails. Thank you. This was a glaring mistake in the code and it has been fixed. Type variables are the only ones that have kinds now. I have used your definition of fv_gamma too. and that led to an error: in generalise, we are interested in the free constructor-variables in the environment, not the term-variables, hence -- Free variables in ... -- ... schemes fv_scheme :: Scheme -> [Var] fv_scheme (Scheme vs ps ty) = nub (fv_preds ps ++ fv ty) \\ vs -- ... environments fv_gamma :: Gamma -> [Var] fv_gamma gamma = nub (concatMap (fv_scheme . snd) gamma) and not fv_gamma gamma = nub (map fst gamma) I have only just glimpsed at Jones' paper, so I don't yet see, what this type inference algorithm (quite nice, btw) has to do with constructor classes. If I still don't after reading it, I'll come back to ask. I still don't see clearly. So you've implemented the type inference algorithm from Jones' paper, good. But is there any significance or gain, apart from it being a nice and interesting exercise? No. Nor did I state that there was. There's a reason I posted this to Haskell-cafe and not Haskell. I just thought the code might be useful for other people who were similarly trying to understand how constructor classes are implemented. The only other code I found (that wasn't inside a compiler) was that associated with the "Typing Haskell in Haskell" paper. The nice thing about the algorithm in "A system of constructor classes: ..." is that it is small and to-the- point. Cheers, Sean ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: standard poll/select interface
On Tue, Feb 21, 2006 at 01:15:48PM +, Simon Marlow wrote: > I agree that a generic select/poll interface would be nice. If it was > in terms of Handles though, that's not useful for implementing the I/O > library. If it was in terms of FDs, that's not portable - we'd need a > separate one for Windows. How would you design it? Yeah, this is why I have held off on a specific design until we get a better idea of what the new IO library will look like. I am thinking it will have to involve some abstract event source type with primitive routines for creating this type from things like handles,fds, or anything else we might want to wait on. so it is system-extendable in that sense in that implementations can just provide new event source creation primitives. The other advantage of this sort of thing is that you would want things like the X11 library to be able to provide an event source for when an X11 event is ready to be read so you can seamlessly integrate your X11 loop into your main one. The X11 library would create such an event source from the underlying socket but just return the abstract event source so the implementation can change (perhaps when using a shared memory based system like D11 for instance) without affecting how the user uses the library in a portable way. I will try to come up with something concrete for us to look at that we can modify as the rest of the IO library congeals. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Constructor classes implementation
Am Montag, 20. Februar 2006 13:35 schrieb Daniel Fischer: > > > > Cheers, > > > > Sean > > > > p.s. If you find any bugs, please let me know. > > Re bugs: > > 1. printGamma [] would print an unmotivated " }", as witnessed by > typeInf [] term14. > > 2. the case > unify (ConT c) (AppT t1 t2) > is missing. > and unifying a tyvar with itself fails. That probably doesn't occur in the inference-algorithm, but still... > 3. too many shadowed bindings, this is always dangerous, I believe > > 4. I'm not sure, the datatypes are appropriate; as far as I know, > expressions have a type and not a kind, which is what the use of the same > Var type for Type and Exp entails. and that led to an error: in generalise, we are interested in the free constructor-variables in the environment, not the term-variables, hence -- Free variables in ... -- ... schemes fv_scheme :: Scheme -> [Var] fv_scheme (Scheme vs ps ty) = nub (fv_preds ps ++ fv ty) \\ vs -- ... environments fv_gamma :: Gamma -> [Var] fv_gamma gamma = nub (concatMap (fv_scheme . snd) gamma) and not fv_gamma gamma = nub (map fst gamma) > > I have only just glimpsed at Jones' paper, so I don't yet see, what this > type inference algorithm (quite nice, btw) has to do with constructor > classes. If I still don't after reading it, I'll come back to ask. > I still don't see clearly. So you've implemented the type inference algorithm from Jones' paper, good. But is there any significance or gain, apart from it being a nice and interesting exercise? Cheers, Daniel -- "In My Egotistical Opinion, most people's C programs should be indented six feet downward and covered with dirt." -- Blair P. Houghton ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Streams: the extensible I/O library
Am Dienstag, 21. Februar 2006 13:06 schrieb Simon Marlow: > If we get class synonyms (see Haskell' proposal) this will get easier. This raises two questions in me: 1. Is this the thing, John Meacham proposed some time ago? 2. What is the URL of the respective Haskell' proposal? > [...] Best wishes, Wolfgang ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Hashtable woes
Simon Marlow wrote: > Brian Sniffen wrote: >> On 2/10/06, Ketil Malde <[EMAIL PROTECTED]> wrote: >> >> >>> Hmm...perhaps it is worth it, then? The benchmark may specify "hash >>> table", but I think it is fair to interpret it as "associative data >>> structure" - after all, people are using "associative arrays" that >>> (presumably) don't guarantee a hash table underneath, and it can be >>> argued that Data.Map is the canonical way to achieve that in Haskell. >> >> >> Based on this advice, I wrote a k-nucleotide entry using the rough >> structure of the OCaml entry, but with the manual IO from Chris and >> Don's "Haskell #2" entry. It runs in under 4 seconds on my machine, >> more than ten times the speed of the fastest Data.HashTable entry. > > I haven't been following this too closely, but could someone provide me > with (or point me to) the badly performing Data.HashTable example, so we > can measure our improvements? > > Cheers, > Simon >From the shooutout itself: http://shootout.alioth.debian.org/gp4/benchmark.php?test=knucleotide&lang=ghc&id=3 and http://shootout.alioth.debian.org/gp4/benchmark.php?test=knucleotide&lang=ghc&id=2 (I forget the exact different between them) >From the wiki (the Current Entry): http://haskell.org/hawiki/KnucleotideEntry#head-dfcdad61d34153143175bb9f8237d87fe0813092 ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: getChar + System.Cmd.system + threads causes hangups
On Tue, 21 Feb 2006, Simon Marlow wrote: ... > The reason for the deadlock is because getChar is holding a lock on > stdin, and System.Cmd.system needs to access the stdin Handle in order > to know which file descriptor to dup as stdin in the child process (the > stdin Handle isn't always FD 0, because of hDuplicateTo). I was puzzled by this; from a quick review of the source, it seems that this is because system calls runProcessPosix, which has optional arguments for (stdin, stdout, stderr) for the child process, and when value is Nothing the parent's stdin etc. are used instead. That last part doesn't seem right to me, so if it's awkward to implement, I hope you will consider the possibility that no one needs it. The default value for fd 0 should be fd 0. A process that intends to change the default input stream on this level where the same stream should be inherited by children, can open or dup another file onto fd 0. Conversely, if a program contrives to change stdin to something besides fd 0, I would have assumed the intent was to avoid any affect on child processes. Donn Cave, [EMAIL PROTECTED] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: getChar + System.Cmd.system + threads causes hangups
Einar Karttunen wrote: Hello Using system or any variant of it from System.Process seems broken in multithreaded environments. This example will fail with and without -threaded. When run the program will print "hello: start" and then freeze. After pressing enter (the first getChar) System.Cmd.system will complete, but without that it will freeze for all eternity. What is the best way to fix this? I could use System.Posix, but that would lose windows portablity which is needed. import Control.Concurrent import System.Cmd main = do forkIO (threadDelay 10 >> hello) getChar getChar hello = do putStrLn "hello: start" system "echo hello world!" putStrLn "hello: done" The reason for the deadlock is because getChar is holding a lock on stdin, and System.Cmd.system needs to access the stdin Handle in order to know which file descriptor to dup as stdin in the child process (the stdin Handle isn't always FD 0, because of hDuplicateTo). Maybe getChar shouldn't hold the lock while it is waiting. I was vaguely aware of this when I wrote System.IO, but couldn't see an easy way to implement it, so currently all operations that block in I/O hold the Handle lock while they block. Mostly this isn't a problem, but it does mean that things like hClose will block if there's another thread blocked in hGetChar on the same Handle (maybe you want it to cause the hGetChar to immediately fail instead). One way to work around it in this case is to hDuplicate the standard Handles, and call runProcess passing your duplicate Handles. I've just checked; this works fine. import GHC.Handle (hDuplicate) main = do i <- hDuplicate stdin o <- hDuplicate stdout e <- hDuplicate stderr forkIO (threadDelay 10 >> hello i o e) getChar getChar hello i o e = do putStrLn "hello: start" p <- runProcess "echo" ["hello world!"] Nothing Nothing (Just i) (Just o) (Just e) waitForProcess p putStrLn "hello: done" Cheers, Simon ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: standard poll/select interface
Bulat Ziganshin wrote: SM> I don't think async I/O is a stream transformer, fitting it into the SM> stream hierarchy seems artificial to me. yes, it is possible - what i'm trying to implement everything as tranformer, independent of real necessity. i really thinks that idea of transformers fit every need in extending functionality it is a list of my reasons to implement this as transformer: 1) there is no "common FD" interface. Well, there's the unix package. In theory, System.IO should layer on top of System.Posix or System.Win32, depending on the platform. In practice we extract the important bits of System.Posix and put them in the base package to avoid circular dependencies. The current implementation could use some cleaning up here (eg. FD vs. Fd). on the other side, reasons for your proposal, as i see: 1) if FD will incorporate async i/o support, the System.FD library will become much more useful - anyone using low-level fd* functions will get async i/o support for free but there is another defeciency in the System.FD library - it doesn't include support for the files>4Gb Yes it does! and files with unicode filenames under Windows. Under Windows I believe we should be using a Win32-specific substrate on which to build the I/O library. it seems natural to include this support in fd* too. now let's see. you are proposing to include in fd* implementation support for files, sockets, various async i/o methods and what's not all. are you not think that this library will become a successor of Handle library, implementing all possible fucntionality and don't giving 3rd-party libraries chances to change anything partially? Not at all - I'm just suggesting that there should be an API to FD-based I/O, and that concurrency-safety can be layered on top of this, providing exactly the same API but with concurrency-safety built in. i think that you mix two things - readNonBlockingFD call that can fill buffer only partially and readAsync call that use some I/O manager to perform other Haskell threads while data are read Why do you want to expose readAsync at all? well, i agree that should be two GetBuf variants in the Stream interface - greedy and non-greedy. say, vGetBuf and vGetBufNonBlocking. vPutBuf also need two variants? then, may be LineBuffering and BlockBuffering should use vGetBufNonBlocking and vGetBuf, respectively? but i don't know anything about implementation. is the difference between readNonBlockingFD and readFD calls only in the O_NONBLOCK mode of file handle, or different functions are used? what for Windows? for sockets? how this interacts with the async i/o? Never mind about this - just assume readNonBlockingFD as your lowest-level primitive, and we can provide an implementation of readNonBlockingFD that uses select/poll/whatever underneath. I imagine we'll stop using O_NONBLOCK. The Windows version will look different at this level, because we should be using Win32 native I/O, i.e HANDLE instead of FD, but it will have a primitive similar to readNonBlockingFD, also concurrency-safe. Cheers, SImon ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: standard poll/select interface
John Meacham wrote: On Fri, Feb 10, 2006 at 12:26:30PM +, Simon Marlow wrote: in fact, I think this should be the basic API, since you can implement readFD in terms of it. (readNonBlockingFD always reads at least one byte, blocking until some data is available). This is used to partially fill an input buffer with the available data, for example. this is the behavior of standard file descriptors. not non-blocking ones. We should definitly not guarentee reads fill an input buffer fully at least for the lowest level calls, that is the job for the layers on top of it. You're right - I was slightly confused there. O_NONBLOCK isn't necessary to implement readNonBlockingFD. One problem here is that in order to implement readNonBlockingFD on Unix you have to put the FD into O_NONBLOCK mode, which due to misdesign of the Unix API affects other users of the same file descriptor, including other programs. GHC suffers from this problem. non blocking ones will return immediatly if no data is available rather than make sure they return at least one byte. In any case, the correct solution in the circumstances is to provide a select/poll/epoll/devpoll interface. It is nicer than setting NON_BLOCKING and more efficient. This is largely orthogonal to the Streams design though. I think the reason we set O_NONBLOCK is so that we don't have to test with select() before reading, we can just call read(). If you don't use O_NONBLOCK, you need two system calls to read/write instead of one. This probably isn't a big deal, given that we're buffering anyway. I agree that a generic select/poll interface would be nice. If it was in terms of Handles though, that's not useful for implementing the I/O library. If it was in terms of FDs, that's not portable - we'd need a separate one for Windows. How would you design it? Cheers, Simon ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
RE: [Haskell-cafe] typesafe non-local returns in the IO monad
I'm not sure this works. Consider this newContinuation (\k -> return (callContinuation k)) ... The partial application (callContinuation k) has no 's' in its type, and so can go anywhere. Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of John | Meacham | Sent: 21 February 2006 12:40 | To: haskell-cafe@haskell.org | Subject: [Haskell-cafe] typesafe non-local returns in the IO monad | | Although I am sure I am not the first to discover this, I thought it was | a neat application of the runST trick. Safe non-local returns for | the IO monad. What I mean by safe is that it is impossible to return to | a context that no longer exists. the api is simple: | | > module System.IO.Continuation(IOCont(),newContinuation,callContinuation) where | > | > data IOCont s a = | > | > newContinuation :: (forall s . IOCont s a -> IO b) -> (a -> IO b) -> IO b | > newContinuation act cc = ... | > | > callContinuation :: IOCont s a -> a -> IO b | > callContinuation cont x = ... | | newContinuation runs its first argument passing a fresh jumppoint into | it, if it is jumped to then the argument is passed to the second | argument of newContinuation. | | the universal quantification means that the continuation is unable to | escape the action so you know its context is still available on the | stack. | | in jhc these are just implemented as straight FFI calls to setjmp(2) and | longjmp(2) and an IORef. | | I feel using the term 'continuation' is something of a misnomer as true | continuations would allow jumping between multiple stacks I would think | but am unsure what a good name for this is then. Is there a fully | typesafe interface for 'true' IO continuations for some definition of | 'true'? hmm | | John | | -- | John Meacham - ⑆repetae.net⑆john⑈ | ___ | 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: Emulating bash pipe/ process lib
Bulat Ziganshin wrote: Friday, February 10, 2006, 2:53:25 PM, you wrote: i'm not very interested to do something fascinating in this area. it seems that it is enough to do 1) non-blocking read of the entire buffer on input 2) flush buffer at each '\n' at output that should be enough to implement LineBuffering for everyone except purists? and for the NoBuffering the same except for flushing after each output operation? Yes, exactly. This is almost what GHC's System.IO currently does, except that for NoBuffering we have a fixed buffer size of 1 byte. It would be safe to have a larger buffer size for NoBuffering read handles, but I didn't recognise that when I wrote it. Cheers, Simon ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] typesafe non-local returns in the IO monad
Although I am sure I am not the first to discover this, I thought it was a neat application of the runST trick. Safe non-local returns for the IO monad. What I mean by safe is that it is impossible to return to a context that no longer exists. the api is simple: > module System.IO.Continuation(IOCont(),newContinuation,callContinuation) where > > data IOCont s a = > > newContinuation :: (forall s . IOCont s a -> IO b) -> (a -> IO b) -> IO b > newContinuation act cc = ... > > callContinuation :: IOCont s a -> a -> IO b > callContinuation cont x = ... newContinuation runs its first argument passing a fresh jumppoint into it, if it is jumped to then the argument is passed to the second argument of newContinuation. the universal quantification means that the continuation is unable to escape the action so you know its context is still available on the stack. in jhc these are just implemented as straight FFI calls to setjmp(2) and longjmp(2) and an IORef. I feel using the term 'continuation' is something of a misnomer as true continuations would allow jumping between multiple stacks I would think but am unsure what a good name for this is then. Is there a fully typesafe interface for 'true' IO continuations for some definition of 'true'? hmm John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: Hashtable woes
Brian Sniffen wrote: On 2/10/06, Ketil Malde <[EMAIL PROTECTED]> wrote: Hmm...perhaps it is worth it, then? The benchmark may specify "hash table", but I think it is fair to interpret it as "associative data structure" - after all, people are using "associative arrays" that (presumably) don't guarantee a hash table underneath, and it can be argued that Data.Map is the canonical way to achieve that in Haskell. Based on this advice, I wrote a k-nucleotide entry using the rough structure of the OCaml entry, but with the manual IO from Chris and Don's "Haskell #2" entry. It runs in under 4 seconds on my machine, more than ten times the speed of the fastest Data.HashTable entry. I haven't been following this too closely, but could someone provide me with (or point me to) the badly performing Data.HashTable example, so we can measure our improvements? Cheers, Simon ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: Streams: the extensible I/O library
Bulat Ziganshin wrote: Wednesday, February 08, 2006, 2:58:30 PM, you wrote: SM> I would prefer to see more type structure, rather than putting SM> everything in the Stream class. You have classes ByteStream, SM> BlockStream etc, but these are just renamings of the Stream class. There SM> are many compositions that are illegal, but we don't find out until SM> runtime; it would make a lot more sense to me to expose this structure SM> in the type system. i initially used normal splitted classes (vGetBuf was in BlockStream) and so on, but come accross problems with the type classes system and decided to simplify the design. now i feel himself more confident with the classes, feel that i know source of my previous problems and therefore slowly migrate back to the splitted classes design. the library as published is just on the half of this way. but i know some limitations. that is the one problem: data BinHandle = forall h . (Stream IO h) => BinH h One possibility is something like this: data BinHandle = forall h . (Stream IO h, Typeable h) => BinH h then you can recover the original stream type (by guessing what it is). Or there are other solutions - adding an extra field to BinH, or separating the BinH constructor into two, one with a MemoryStream and one without. What's interesting is that you're saying you really want dynamic typing here - you don't want to distinguish different types of BinHandle, instead you want the saveToFile operation to fail at runtime if the wrong kind of stream is used. It's slightly strange to use dynamic typing here when the rest of the library would be using static typing, so it might be worthwhile considering static typing solutions instead: don't use an existential here, just add h as a parameter of BinHandle. This does mean you have to add Stream predicates a lot of places, though. Someday (soon, I hope), GHC will let you say data BinHandle h where BinH :: Stream IO h => BinH h but it doesn't work right now (or at least, it doesn't do what you want). moreover, splitting the Streams interface will require from the library users to give more classes in defining context for their functions, like the: process :: (Stream IO h, Seekable IO h, Buffered h) => h -> IO () that is not so good, especially if adding new interfaces means slowdown of calls to this function you can combine multiple classes with a dummy superclass. If we get class synonyms (see Haskell' proposal) this will get easier. Performance of the example above might actually be better than having a single Stream class, depending on how much dictionary *building* needs to happen. In your library, every time an overloaded Stream function is called, it must be passed a dictionary for Stream, which is a tuple with 20+ elements. These dictionaries will probably be built at runtime, because of the superclass structure (the compiler usually won't be able to predict what layering of stream transformers will be used, and hence what dictionaries will be needed). You can provide some specialisations to help - SPECIALISE INSTANCE should be useful here. The point is that the performance implications aren't obvious, it depends a lot on how much sharing of dictionaries happens. SM> Also I'd like to see separate SM> input/output streams for even more type safety, and I believe SM> simplicity, it will be great! but it is very uneasy and even seems impossible: 1) this will prevent dividing streams into the MemoryStream/BlockStream/ByteStream, what i like you consider as more important. it is impossible to say what InputStream BlockStream implements only vGetBuf, while OutputStream BlockStream implements only vPutBuf operation I don't think so - you just have InputByteStream/OutputByteStream classes, and similarly for the others. 2) such division will require to implement 2 or 3 (+ReadWrite) times more Stream types than now. Say, instead of FD we will get InputFD and OutputFD, instead of CharEncoding transformer - two transformers and so on. most of the functionality in Input and Ouput variants will be repeated (because this functionality don't depend on input/output mode) and in addition to the current large lists of passed calls like the: vIsEOF(WithEncoding h _) = vIsEOFh vMkIOError(WithEncoding h _) = vMkIOErrorh vReady(WithEncoding h _) = vReadyh vIsReadable (WithEncoding h _) = vIsReadable h we will get the same lists in 2 or 3 repetitions!!! the common operations should be members of a separate superclass. I have in mind a structure like this: class Stream h where streamEOF :: h -> IO Bool streamReady :: h -> IO Bool streamClose :: h -> IO () class InputByteStream h where streamGet :: h -> IO Word8 ... class InputBlockStream h where streamGetBuf :: h -> Int -> Ptr Word8 -> IO Int ... class InputMemoryStream h where streamGetMem :: h -> IO (Ptr Word8) ... there's no dupli
Re: [Haskell-cafe] Re: Associated Type Synonyms question
Claus Reinke writes: > The main argument for ATS is that the extra parameter for the > functionally dependend type disappears, but as you say, that > should be codeable in FDs. I say should be, because that does > not seem to be the case at the moment. > > My approach for trying the encoding was slightly different from > your's, but also ran into trouble with implementations. > > First, I think you need a per-class association, so your T a b > would be specific to C. Second, I'd use a superclass context > to model the necessity of providing an associated type, and > instance contexts to model the provision of such a type. No > big difference, but it seems closer to the intension of ATS: > associated types translate into type association constraints. > > (a lot like calling an auxiliary function with empty accumulator, > to hide the extra parameter from the external interface) > > > Example > > > > -- ATS > > class C a where > > type T a > > m :: a->T a > > instance C Int where > > type T Int = Int > > m _ = 1 > > -- alternative FD encoding attempt > > class CT a b | a -> b > instance CT Int Int > > class CT a b => C a where > m :: a-> b > > instance CT Int b => C Int where > m _ = 1::b > Hm, I haven't thought about this. Two comments. You use scoped variables in class declarations. Are they available in ghc? How do you encode? --AT instance C a => C [a] where type T [a] = [T a] m xs = map m xs Via the following I guess? instance CT a b => CT a [b] instance C a => C [a] where m xs = map m xs It seems your solution won't suffer from the problem I face. See below. > > -- FD encoding > > class T a b | a->b > > instance T Int Int > > > > class C a where > > m :: T a b => a->b > > > > instance C Int where > > m _ = 1 > > > > -- general recipe: > > -- encode type functions T a via type relations T a b > > -- replace T a via fresh b under the constraint C a b > My AT encoding won't work with ghc/hugs because the class declaration of C demands that the output type b is univeral. Though, in the declaration instance C Int we return an Int. Hence, the above cannot be translated to System F. Things would be different if we'd translate to an untyped back-end. > referring to the associated type seems slightly awkward > in these encodings, so the special syntax for ATS would > still be useful, but I agree that an encoding into FDs should > be possible. > > > The FD program won't type check under ghc but this > > doesn't mean that it's not a legal FD program. > > glad to hear you say that. but is there a consistent version > of FDs that allows these things - and if not, is that for lack > of trying or because it is known not to work? > The FD framework in "Understanding FDs via CHRs" clearly subsumes ATs (based on my brute-force encoding). My previous email showed that type inference for FDs and ATs can be equally tricky. Though, why ATs? Well, ATs are still *very useful* because they help to structure programs (they avoid redundant parameters). On the other hand, FDs provide the user with the convenience of 'automatic' improvement. Let's do a little test. Who can translate the following FD program to AT? zip2 :: [a]->[b]->[(a,b)] zip2 (a:as) (b:bs) = (a,b) : (zip2 as bs) zip2 _ _ = [] class Zip a b c | c -> a, c -> b where mzip :: [a] -> [b] -> c instance Zip a b [(a,b)] where mzip = zip2 instance Zip (a,b) c e => Zip a b ([c]->e) where mzip as bs cs = mzip (zip2 as bs) cs Martin ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe