Re: [Haskell-cafe] Conditional properties in QuickCheck alter test data generation?
Thanks. That took care of the problem with quickCheck, but now I have another problem: verboseCheck has disappeared! It doesn't seem to exist anymore in QuickCheck 2. I've looked over all the documentation I can find, but I can't any mention of this change. What replaces the functionality of verboseCheck in QuickCheck 2? On Dec 18, 2008, at 1:09 PM, Thomas Schilling wrote: This bug appears to be fixed in QuickCheck 2. However, for some reason cabal-install by default only installs 1.2. You have to explicitly ask for the newer version: $ cabal install QuickCheck-2.1.0.1 -- Push the envelope. Watch it bend. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] RWH book club
Matt Podwysocki set up a Real World Haskell book club, http://groups.google.com/group/real-world-haskell-book-club (a mailing list on google groups), with already some 200 members discussing typical new user Haskell questions. Feel free to join if you like talking about Haskell, or teaching new users. -- Don ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Detecting system endianness
On Thu, 2008-12-18 at 22:35 -0500, wren ng thornton wrote: > In a similar vein, is there already a function available to give the > size of Word in bytes? Or should I write the usual Ptr conversion tricks > to figure it out? How about this: (`div` 8) $ ceiling $ logBase 2 $ fromIntegral (maxBound :: Word) Could write an integral log_2 function to make it nicer :) - George signature.asc Description: This is a digitally signed message part ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Detecting system endianness
Foreign.Storable.sizeOf wren: > In a similar vein, is there already a function available to give the > size of Word in bytes? Or should I write the usual Ptr conversion tricks > to figure it out? > > > > Holger Siegel wrote: > >On Thursday 18 December 2008 13:40:47 Ryan Ingram wrote: > >>Actually, this is probably safer: > >> > >>import Foreign.Marshal.Alloc > >>import Foreign.Ptr > >>import Foreign.Storable > >>import Data.Word > >>import System.IO.Unsafe > >> > >>endianCheck = unsafePerformIO $ alloca $ \p -> poke p (0x01020304 :: > >>Word32) >> peek (castPtr p :: Ptr Word8) > >> > >>littleEndian = endianCheck == 4 > >>bigEndian = endianCheck == 1 > >> > >> -- ryan > > > > > >Using modules Data.Binary, Data.Binary.Put and Data.Word, you can define > > > > littleEndian = (decode $ runPut $ putWord16host 42 :: Word8) == 42 > > > >Under the hood, it also uses peek and poke, but it looks a bit more > >functional. > > > -- > Live well, > ~wren > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Detecting system endianness
In a similar vein, is there already a function available to give the size of Word in bytes? Or should I write the usual Ptr conversion tricks to figure it out? Holger Siegel wrote: On Thursday 18 December 2008 13:40:47 Ryan Ingram wrote: Actually, this is probably safer: import Foreign.Marshal.Alloc import Foreign.Ptr import Foreign.Storable import Data.Word import System.IO.Unsafe endianCheck = unsafePerformIO $ alloca $ \p -> poke p (0x01020304 :: Word32) >> peek (castPtr p :: Ptr Word8) littleEndian = endianCheck == 4 bigEndian = endianCheck == 1 -- ryan Using modules Data.Binary, Data.Binary.Put and Data.Word, you can define littleEndian = (decode $ runPut $ putWord16host 42 :: Word8) == 42 Under the hood, it also uses peek and poke, but it looks a bit more functional. -- Live well, ~wren ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] lengthOP rewrite rules
Luke Palmer wrote: This does not answer your question, but you can solve this problem without rewrite rules by having length return a lazy natural: data Nat = Zero | Succ Nat And defining lazy comparison operators on it. And if you want to go that route, then see Data.List.Extras.LazyLength from list-extras[1]. Peano integers are quite inefficient, but this library does the same transform efficiently. [1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/list-extras Of course you cannot replace usages of Prelude.length. But I am really not in favor of rules which change semantics, even if they only make things less strict. My argument is the following. I may come to rely on such nonstrictness as in: bad xs = (length xs > 10, length xs > 20) bad [1..] will return (True,True). However, if I do an obviously semantics-preserving refactor: bad xs = (l > 10, l > 20) where l = length xs My semantics are not preserved: bad [1..] = (_|_, _|_) (if/unless the compiler is clever, in which case my semantics depend on the compiler's cleverness which is even worse) Data.List.Extras.LazyLength does have rewrite rules to apply the lazy versions in place of Prelude.length where it can. My justification is two-fold. First is that for finite lists the semantics are identical but the memory behavior is strictly better. Second is that for non-finite lists the termination behavior is strictly better. It's true that refactoring can disable either point, and that can alter semantics in the latter case. Since the module is explicit about having these rules, I would say that users should remain aware of the fact that they're taking advantage of them or they should use the explicit lengthBound or lengthCompare functions instead. -- Live well, ~wren ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Yampa vs. Reactive
Hi Tony, Reactive so far has focused mainly on events and functions of time (behaviors/signals), while Yampa on transformations between signals. I'm in the process of building a higher-level interface with some semantic similarity to the arrow/Yampa style. See recent posts at http://conal.net/blog to get some flavor of where I'm going. The post "Why classic FRP does not fit interactive behavior" in particular mentions part of my motivation for doing something different from both classic FRP and Yampa. - Conal 2008/12/16 Tony Hannan > Hello, > > Can someone describe the advantages and disadvantages of the Yampa library > versus the Reactive library for functional reactive programming, or point me > to a link. > > Thanks, > Tony > > P.S. It is hard to google for Yampa and Reactive together because > "reactive" as in "function reactive programming" always appears with Yampa > > > ___ > 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
intimidating terminology (was: Re: [Haskell-cafe] Time for a new logo?)
quoth Andrew Coppin: quoth Tristan Seligmann: > quoth Andrew Coppin: > > Sure, there are many concepts in Haskell which just aren't found > > anywhere else. But monads? Catamorphisms? Coroutines? Couldn't we > > think up some less intimidating terminology? > > The problem is that "less intimidating" terminology generally seems to > mean inaccurate or misleading terminology. I'm not sure I agree with that. Sure, simplifying things *can* make them less precise. But I don't believe it is always necessarily so. And I think we could try a little bit harder here. (Nothing too radical, just some small changes.) Consider the humble catamorphism (and anamorphism). Can you think of any simple, descriptive, non-ambiguous name for this pattern other than the technical name? An oft used name is "fold" (and "unfold") which is simple, possibly descriptive, but certainly ambiguous. For example: the fold/unfold names are used as jargon for optimization ---in compilers for logic languages and query planning for databases--- for inlining functions and then 'outlining' parts after doing some reorganization. There are other technical uses which are just as different. The problem with simple terms for jargon is that they're all taken. When we take everyday terms like "fold", "set", "list", "tree", "category", "type", "kind", "sort", "variety", "domain", "group", et cetera and reappropriate them for technical use there are two problems. The first is that all of the simple everyday terms have already been appropriated time and again, so using it will often be ambiguous. The second is that the technical meaning often does not expressly match the daily meaning, which in turn means that these terms will often be confusing or used casually in a way that confuses the daily and technical meanings. It's all well and good for terminology to be non-intimidating, but for technical terminology I think there must be a high premium on correctness as well. Reappropriating terms which have fallen into disuse for their original meanings (e.g. monad) or which are taken or invented from languages the audience is unlikely to be familiar with (e.g. catamorphism) ensures that we don't have to worry about baggage associated with those words. This is good because it means there won't be conflicts of meaning, but it's bad because it means the audience can't intuit an approximate meaning. Pedantic as I am wont to be, I think the benefit outweighs the detriment, but YMMV. -- Live well, ~wren ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Fwd: [Haskell-cafe] Haskell as a religion
On Thu, Dec 18, 2008 at 4:15 PM, Henning Thielemann wrote: > In C/C++ referential transparent functions code can be declared by > appending a 'const' to the prototype, right? For one thing, some fields in a const C++ object can be explicitly set mutable. mutable is sometimes used in C++ a similar way to unsafePerformIO in Haskell. You have something that uses mutability in its internals but that mutability shouldn't be observable to the caller. In both cases you have no means of actually ensuring that the mutability is actually unobservable. -- Dan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] When using functional dependencies to combine...
Am Freitag, 19. Dezember 2008 02:20 schrieb Daniel Fischer: > For SucParser, > get :: StateT [s] [] [s]. > To wrap it in WithUnit, it would need type > StateT [s] [] (([s],()),[s]) Oops, that should be StateT [s] [] ([s],()), of course. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] When using functional dependencies to combine...
Am Freitag, 19. Dezember 2008 00:17 schrieb Martijn van Steenbergen: > Good evening everyone, > > My program reads: > > module Boom where > > > > import Control.Monad.State > > > > type SucParser s = StateT [s] [] > > > > newtype WithUnit s a = WithUnit (SucParser s (a, ())) > > > > foo :: SucParser s [s] > > foo = get > > > > bar :: WithUnit s [s] > > bar = WithUnit get > > The compiler complains: > > Boom.hs:13:0: > Couldn't match expected type `([s], ())' > against inferred type `[s]' > When using functional dependencies to combine >MonadState s (StateT s m), > arising from the instance declaration at >MonadState ([s], ()) (StateT [s] []), > arising from a use of `get' at Boom.hs:13:15-17 > When generalising the type(s) for `bar' > > I'm wondering if I'm making a silly mistake or if there's something less > trivial going on here. Could someone please explain the error and give a > hint on how to fix it? class MonadState s m | m -> s where get :: m s ... For SucParser, get :: StateT [s] [] [s]. To wrap it in WithUnit, it would need type StateT [s] [] (([s],()),[s]) Easy fix: bar :: WithUnit s [s] bar = WithUnit $ do s <- get return (s,()) Better define liftUnit :: SucParser s a -> WithUnit s a liftUnit m = WithUnit $ do a <- m return (a,()) and bar = liftUnit get Or make WithUnit more general (working with arbitrary monads) and give it a MonadTrans instance. > > Thanks much. :-) > > Martijn. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Yampa vs. Reactive
Hi Tom, > I'm not sure why mapping the function is not satisfactory -- It would > create a new Behavior, who's internals contain only the two elements > from the list -- that would expose to the garbage collector that the > second element has no reference from this behavior any more, and thus > the whole behavior could be collected. We must be talking at cross purposes here: there is no way that deleting the *output* from one of the behaviours from a list of outputs would cause the underlying behavior whose output no longer is observed to be garbage collected. After all, that list of three numbers is just a normal value: why should removing one of its elements, so to speak, affect the producer of the list? But if we have a list of running behaviors or signals, and that list is changed, then yes, of course we get the desired behavior (this is what Yampa does). So maybe that's what you mean? > That's a yes. My first answer to how to implement the resetting > counter would be someting along the lines of this, but I'm not certain > it's dead right: > > e = (1+) <$ mouseClick > e' = (const 0) <$ > b = accumB 0 (e `mappend` e') > > i.e. b is the behavior got by adding 1 every time the mouse click > event occurs, but resetting to 0 whenever occurs. Hmm. Looks somewhat complicated to me. Anyway, it doesn't really answer the fundamental question: how does one start a behavior/signal function at a particular point in time? I consider the fact that Yampa, through supporting both signals and signal functions, provides simple yet flexible answers to the question when a signal function starts to be one of its key strengths over Classical FRP and maybe then also over Reactive. Best, /Henrik -- Henrik Nilsson School of Computer Science The University of Nottingham n...@cs.nott.ac.uk This message has been checked for viruses but the contents of an attachment may still contain software viruses, which could damage your computer system: you are advised to perform your own checks. Email communications with the University of Nottingham may be monitored as permitted by UK legislation. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Conditional properties in QuickCheck alter test data generation?
On Thu, 2008-12-18 at 16:13 -0800, Max Rabkin wrote: > On Thu, Dec 18, 2008 at 3:55 PM, Duncan Coutts > wrote: > > However QuickCheck seems to be a case where > > people now expect to use QC-2, but old packages that don't specify a > > version typically only work with QC-1.x. > > Can't we just fix those .cabal files? We can certainly ask maintainers to specify the QC dependency properly when they next upload. We do not yet have a mechanism to update .cabal file dependencies on hackage after a package has been uploaded, though we have been pondering adding such a facility for a while. Duncan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Fwd: [Haskell-cafe] Haskell as a religion
Henning Thielemann wrote: Alberto G. Corona schrieb: But many features need other features. For example, the option to use referential transparency will be common in future languages for multicore programming purposes. This creates the problem of separating side-effect-free code from side-effect code. In C/C++ referential transparent functions code can be declared by appending a 'const' to the prototype, right? not quite. GCC allows __attribute__((__const__)) or __attribute__((__pure__)), to declare that, though (one of them allows reading global variables, the other doesn't, I forget which). In C and C++ per standard, "const" can only be applied to types, e.g. function arguments (including C++'s implicit *this, via funny location of "const"). Maybe C99 made up an additional way to use it, as it introduced "restrict", I forget -Isaac ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: Detecting system endianness
I actually don't need a pure function, IO is OK. I'll try something in these lines. It doesn't build yet, with an error message I'll probably take a few months to understand: Couldn't match expected type `forall a. (Storable a) => a -> IO a' against inferred type `a -> IO a' Thanks, Maurício - import Control.Monad ; import Foreign ; import Foreign.C ; type CUInt16 = CUShort ; type CUInt8 = CChar ; littleEndianToHost,hostToLittleEndian :: forall a. (Storable a ) => a -> IO a ; (littleEndianToHost,hostToLittleEndian) = (f,f) where { f :: forall a. ( Storable a ) => a -> IO a ; f a = with ( 0x0102 :: CUInt16 ) $ \p -> do { firstByte <- peek ( castPtr p :: Ptr CUInt8 ) ; littleEndian <- return $ firstByte == 0x02 ; halfSize <- return $ div ( alignment a ) 2; reverse <- with a $ \val -> zipWithM (swapByte (castPtr val :: Ptr CUInt8)) [0..halfSize-1] [halfSize..2*halfSize-1] >> peek val ; return $ if littleEndian then a else reverse ; } ; swapByte p n1 n2 = do { v1 <- peekElemOff p n1 ; v2 <- peekElemOff p n2 ; pokeElemOff p n1 v2 ; pokeElemOff p n2 v1 } >> return () } - On Thursday 18 December 2008 13:40:47 Ryan Ingram wrote: Actually, this is probably safer: import Foreign.Marshal.Alloc import Foreign.Ptr import Foreign.Storable import Data.Word import System.IO.Unsafe endianCheck = unsafePerformIO $ alloca $ \p -> poke p (0x01020304 :: Word32) >> peek (castPtr p :: Ptr Word8) littleEndian = endianCheck == 4 bigEndian = endianCheck == 1 (...) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Haskell, successing crossplatform API standart
On 18 Dec 2008, at 7:41 pm, Belka wrote: Oh, but JSON doesn't seem to support tree-structured data... Sure it does. In Haskell terms, data JSON = JSON_Number Double -- not entirely clear, actually | JSON_String String -- Unicode | JSON_Array [JSON] -- order matters | JSON_Object [(String,JSON)] -- Unicode keys, order no matter It supports trees well enough that encoding XML as JSON is trivial. To a first approximation, data XML = XML_CData String | XML_Element String [(String,String)] [XML] So, xml_to_json (XML_CData s) = JSON_String s xml_to_json (XML_Elment name atts children) = JSON_Object [("n", JSON_String name), ("a", JSON_Object [(k,JSON_STRING v) | (k,v) <- atts]), ("c", JSON_Array (map xml_to_json children))] One can handle the other aspects of XML, I just couldn't be bothered. Converting JSON that represents XML to XML is straightforward. Of course the converse is true too. json_to_xml (JSON_Number x) = XML_Element "n" [] XML_CData (show x) json_to_xml (JSON_String s) = XML_Element "s" [] XML_CData s json_to_xml (JSON_Array a) = XML_Element "a" [] map json_to_xml a json_to_xml (JSON_Object o) = XML_Element "o" [] [XML_Element "e" [("k",k)] (json_to_xml v) | (k,v) <- o] Again, converting XML that represents JSON to JSON is straightward, I just don't need to show it to make the point. Also obviously, you might as well use Lisp s-expressions. If you have a choice between XML and JSON, it may be worth remembering that JSON is *far* easier to parse. I would expect a JSON parser to be faster, and more importantly, I would expect it to be more reliable. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Fwd: [Haskell-cafe] Haskell as a religion
On Thu, Dec 18, 2008 at 4:15 PM, Henning Thielemann wrote: > Extrapolating the habit of programmers from the past to the future, I > predict that Haskell can only become a mainstream language once there is > a cleaner, simpler, safer and more powerful programming language than > Haskell. And so, finally, we find the fatal flaw in trying to create the ultimate programming language. --Max ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Conditional properties in QuickCheck alter test data generation?
On Thu, Dec 18, 2008 at 3:55 PM, Duncan Coutts wrote: > However QuickCheck seems to be a case where > people now expect to use QC-2, but old packages that don't specify a > version typically only work with QC-1.x. Can't we just fix those .cabal files? --Max ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Fwd: [Haskell-cafe] Haskell as a religion
Alberto G. Corona schrieb: > But many features need other features. For example, the option to use > referential transparency will be common in future languages for > multicore programming purposes. This creates the problem of separating > side-effect-free code from side-effect code. In C/C++ referential transparent functions code can be declared by appending a 'const' to the prototype, right? > I think that once the average programmer start to use one or two of > these features, he will feel a bit frustrated if its language don´t have > all the others, specially if he know haskell. Probably, he will use > haskell for fun. This is the best way for the takeover of the industry, > because this has been so historically. Extrapolating the habit of programmers from the past to the future, I predict that Haskell can only become a mainstream language once there is a cleaner, simpler, safer and more powerful programming language than Haskell. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Conditional properties in QuickCheck alter test data generation?
On Thu, 2008-12-18 at 20:09 +, Thomas Schilling wrote: > This bug appears to be fixed in QuickCheck 2. However, for some > reason cabal-install by default only installs 1.2. You have to > explicitly ask for the newer version: > > $ cabal install QuickCheck-2.1.0.1 Or more generally: $ cabal install 'quickcheck >= 2' so you don't have to know exactly which version. I'm not quite sure what to do about these cases where we've added a global preference to keep old packages working but where it conflicts with the principle of least surprise. We don't necessarily want to just ignore the preference when the user asks for it on the command line because that prevents maintainers using it to allow stable and experimental versions of a package to be on hackage simultaneously. However QuickCheck seems to be a case where people now expect to use QC-2, but old packages that don't specify a version typically only work with QC-1.x. Duncan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] When using functional dependencies to combine...
Good evening everyone, My program reads: module Boom where import Control.Monad.State type SucParser s = StateT [s] [] newtype WithUnit s a = WithUnit (SucParser s (a, ())) foo :: SucParser s [s] foo = get bar :: WithUnit s [s] bar = WithUnit get The compiler complains: Boom.hs:13:0: Couldn't match expected type `([s], ())' against inferred type `[s]' When using functional dependencies to combine MonadState s (StateT s m), arising from the instance declaration at MonadState ([s], ()) (StateT [s] []), arising from a use of `get' at Boom.hs:13:15-17 When generalising the type(s) for `bar' I'm wondering if I'm making a silly mistake or if there's something less trivial going on here. Could someone please explain the error and give a hint on how to fix it? Thanks much. :-) Martijn. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: ANN: Thingie-0.80
Make that version 0.81 -- added in a module that exports all the other modules except BasicUIState. On Thu, Dec 18, 2008 at 5:12 PM, Jeff Heard wrote: > I need a better name for this, but I have software, so I shall release > it with a dumb name. Thingie has just been uploaded to hackage. It > is a library for creating 2D visualizations in a purely functional > manner. It supports static visualizations and animation, and like > most vis libraries, can probably do games as well as simple viz > graphics. The backend uses Cairo for rendering, but I'm looking to > port it to OpenGL/GLUT for systems where Gtk/Cairo is hard to get > working (i.e. OS/X). The idea is that you create a graph of objects > or function that return objects and the library renders them for you > in 2D. > > Right now, there's one thing I would like to add to the system above > all other things: The interactive system has the concept of a tracked > program state that is threaded through the graph. This state is > defined by a UIState class, and any state (which is a record object) > must be an instance of UIState and provide the system with a certain > number of getters and setters for basic bits of state. I would like > to use Template Haskell to help create/derive these structures. Does > anyone on the list want to help with that? > > Here are two examples. Each draws a smiley face, and the interactive > one tracks your mouse with a little red ball. > First the non-interactive: > > module Main where > > import Graphics.Rendering.Thingie.Primitives > import Graphics.Rendering.Thingie.Cairo > import qualified Graphics.Rendering.Cairo as Cairo > > smiley = Context [FillRGBA 0 0 0 0, Operator Cairo.OperatorClear] $ > Group [Draw rectangleFilled{ topleft=Point2D 0 0, > width=200, height=200 } > ,Context [FillRGBA 1 1 0 1, OutlineRGBA 0 0 0 > 1, Translate 100 100, Operator Cairo.OperatorOver] $ >Group [Draw arc{ radius=100, filled=True } > ,Context [FillRGBA 0 0 0 1] $ > Group [Draw arc{ > center=Point2D (-33) (-33), radius=10, filled=True } > ,Draw arc{ > center=Point2D 33 (-33), radius=10, filled=True } > ,Draw arc{ > angle1=degrees 30, angle2=degrees 150, radius=70 }]]] > > main = renderObjectToPNG "smiley.png" 200 200 smiley > > > - > > Now the interactive: > > > import Graphics.Rendering.Thingie.Interactive > import Graphics.Rendering.Thingie.BasicUIState > import Graphics.Rendering.Thingie.Cairo > import Graphics.Rendering.Thingie.Primitives > > import qualified Graphics.Rendering.Cairo as Cairo > > smiley = Context [FillRGBA 0 0 0 0, Operator Cairo.OperatorClear] $ > Group [Draw rectangleFilled{ topleft=Point2D 0 0, > width=200, height=200 } > ,Context [FillRGBA 1 1 0 1, OutlineRGBA 0 0 0 > 1, Translate 100 100, Operator Cairo.OperatorOver] $ >Group [Draw arc{ radius=100, filled=True } > ,Context [FillRGBA 0 0 0 1] $ > Group [Draw arc{ > center=Point2D (-33) (-33), radius=10, filled=True } > ,Draw arc{ > center=Point2D 33 (-33), radius=10, filled=True } > ,Draw arc{ > angle1=degrees 30, angle2=degrees 150, radius=70 }]]] > > undercursor uistate = Context [FillRGBA 1 0 0 1] $ > Draw arcFilled{ center=mousePosition > uistate, radius=5 } > > scene = [StaticElement smiley (Rect2D 0 0 0 0) >,UnboundedElement undercursor] > > main = simpleMotionSensitiveGui defaultBasicUIState scene "smiley face" > ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] ANN: Thingie-0.80
I need a better name for this, but I have software, so I shall release it with a dumb name. Thingie has just been uploaded to hackage. It is a library for creating 2D visualizations in a purely functional manner. It supports static visualizations and animation, and like most vis libraries, can probably do games as well as simple viz graphics. The backend uses Cairo for rendering, but I'm looking to port it to OpenGL/GLUT for systems where Gtk/Cairo is hard to get working (i.e. OS/X). The idea is that you create a graph of objects or function that return objects and the library renders them for you in 2D. Right now, there's one thing I would like to add to the system above all other things: The interactive system has the concept of a tracked program state that is threaded through the graph. This state is defined by a UIState class, and any state (which is a record object) must be an instance of UIState and provide the system with a certain number of getters and setters for basic bits of state. I would like to use Template Haskell to help create/derive these structures. Does anyone on the list want to help with that? Here are two examples. Each draws a smiley face, and the interactive one tracks your mouse with a little red ball. First the non-interactive: module Main where import Graphics.Rendering.Thingie.Primitives import Graphics.Rendering.Thingie.Cairo import qualified Graphics.Rendering.Cairo as Cairo smiley = Context [FillRGBA 0 0 0 0, Operator Cairo.OperatorClear] $ Group [Draw rectangleFilled{ topleft=Point2D 0 0, width=200, height=200 } ,Context [FillRGBA 1 1 0 1, OutlineRGBA 0 0 0 1, Translate 100 100, Operator Cairo.OperatorOver] $ Group [Draw arc{ radius=100, filled=True } ,Context [FillRGBA 0 0 0 1] $ Group [Draw arc{ center=Point2D (-33) (-33), radius=10, filled=True } ,Draw arc{ center=Point2D 33 (-33), radius=10, filled=True } ,Draw arc{ angle1=degrees 30, angle2=degrees 150, radius=70 }]]] main = renderObjectToPNG "smiley.png" 200 200 smiley - Now the interactive: import Graphics.Rendering.Thingie.Interactive import Graphics.Rendering.Thingie.BasicUIState import Graphics.Rendering.Thingie.Cairo import Graphics.Rendering.Thingie.Primitives import qualified Graphics.Rendering.Cairo as Cairo smiley = Context [FillRGBA 0 0 0 0, Operator Cairo.OperatorClear] $ Group [Draw rectangleFilled{ topleft=Point2D 0 0, width=200, height=200 } ,Context [FillRGBA 1 1 0 1, OutlineRGBA 0 0 0 1, Translate 100 100, Operator Cairo.OperatorOver] $ Group [Draw arc{ radius=100, filled=True } ,Context [FillRGBA 0 0 0 1] $ Group [Draw arc{ center=Point2D (-33) (-33), radius=10, filled=True } ,Draw arc{ center=Point2D 33 (-33), radius=10, filled=True } ,Draw arc{ angle1=degrees 30, angle2=degrees 150, radius=70 }]]] undercursor uistate = Context [FillRGBA 1 0 0 1] $ Draw arcFilled{ center=mousePosition uistate, radius=5 } scene = [StaticElement smiley (Rect2D 0 0 0 0) ,UnboundedElement undercursor] main = simpleMotionSensitiveGui defaultBasicUIState scene "smiley face" ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: [reactive] problem with unamb -- doesn't kill enough threads
(I'm broadening the discussion to include haskell-cafe.) Andy -- What do you mean by "handling all thread forking locally"? - Conal On Thu, Dec 18, 2008 at 1:57 PM, Andy Gill wrote: > Conal, et. al, > I was looking for exactly this about 6~9 months ago. I got the suggestion > to pose it as a challenge > to the community by Duncan Coutts. What you need is thread groups, where > for a ThreadId, you can send a signal > to all its children, even missing generations if needed. > > I know of no way to fix this at the Haskell level without handling > all thread forking locally. > > Perhaps a ICFP paper about the pending implementation :-) but I'm not sure > about the research content here. > > Again, there is something deep about values with lifetimes. > > Andy Gill > > > On Dec 18, 2008, at 3:43 PM, Conal Elliott wrote: > > I realized in the shower this morning that there's a serious flaw in my > unamb implementation as described in > http://conal.net/blog/posts/functional-concurrency-with-unambiguous-choice. > I'm looking for ideas for fixing the flaw. Here's the code for racing > computations: > > race :: IO a -> IO a -> IO a > a `race` b = do v <- newEmptyMVar > ta <- forkPut a v > tb <- forkPut b v > x <- takeMVar v > killThread ta > killThread tb > return x > > forkPut :: IO a -> MVar a -> IO ThreadId > forkPut act v = forkIO ((act >>= putMVar v) `catch` uhandler `catch` > bhandler) > where >uhandler (ErrorCall "Prelude.undefined") = return () >uhandler err = throw err >bhandler BlockedOnDeadMVar = return () > > The problem is that each of the threads ta and tb may have spawned other > threads, directly or indirectly. When I kill them, they don't get a chance > to kill their sub-threads. > > Perhaps I want some form of garbage collection of threads, perhaps akin to > Henry Baker's paper "The Incremental Garbage Collection of Processes". As > with memory GC, dropping one consumer would sometimes result is cascading > de-allocations. That cascade is missing from my implementation. > > Or maybe there's a simple and dependable manual solution, enhancing the > method above. > > Any ideas? > >- Conal > > > ___ > Reactive mailing list > react...@haskell.org > http://www.haskell.org/mailman/listinfo/reactive > > > ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Thread scheduling and GHC.Conc
jacobrfoell: > using ghc v6.8.2 > Problem: > I am creating a program that forks two other lightweight threads. One > of the forked threads seems to be stuck or dead after running > successfully for a non-trivial amount of time. I am receiving no > error messages. > Questions: > What is the best way to diagnose this problem? (perhaps a ghc upgrade to > a version that includes processStatus?) > Does the runtime system ensure that no thread will starve for processor > time? > > My initial diagnosis: > by looking at log files that this program produces, it seems that the > thread in question is failing while receiving a response from a server. > Here is a simplified exerpt: > h <- connectTo server port > appendFile file "Connection Established\n" > hPutStr h httpRequestString > hFlush h > reply <- hGetContents h > appendFile file reply > If I look at the tail of file that is created, I see something similar > to this: > ... > Connection Established > here is the response... > Connection Established > Answers to my questions and/or any advice would be appreciated. thanks > ___ Could you tell us more about how you compiled the program? Did you use the -threaded flag? Does your program do blocking foreign IO? -- Don ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Thread scheduling and GHC.Conc
using ghc v6.8.2 Problem: I am creating a program that forks two other lightweight threads. One of the forked threads seems to be stuck or dead after running successfully for a non-trivial amount of time. I am receiving no error messages. Questions: What is the best way to diagnose this problem? (perhaps a ghc upgrade to a version that includes processStatus?) Does the runtime system ensure that no thread will starve for processor time? My initial diagnosis: by looking at log files that this program produces, it seems that the thread in question is failing while receiving a response from a server. Here is a simplified exerpt: h <- connectTo server port appendFile file "Connection Established\n" hPutStr h httpRequestString hFlush h reply <- hGetContents h appendFile file reply If I look at the tail of file that is created, I see something similar to this: ... Connection Established here is the response... Connection Established Answers to my questions and/or any advice would be appreciated. thanks ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Conditional properties in QuickCheck alter test data generation?
On Thu, Dec 18, 2008 at 3:09 PM, Thomas Schilling wrote: > This bug appears to be fixed in QuickCheck 2. However, for some > reason cabal-install by default only installs 1.2. You have to > explicitly ask for the newer version: > > $ cabal install QuickCheck-2.1.0.1 cabal-install only installs 1.2 because QC 2 breaks a lot of packages (different function names, no coarbitrary, etc. IIRC). -- gwern ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Conditional properties in QuickCheck alter test data generation?
This bug appears to be fixed in QuickCheck 2. However, for some reason cabal-install by default only installs 1.2. You have to explicitly ask for the newer version: $ cabal install QuickCheck-2.1.0.1 -- Push the envelope. Watch it bend. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Yampa vs. Reactive
Hi Henrik, On 18 Dec 2008, at 19:06, Henrik Nilsson wrote: Hi Tom, > I don't think this is really true. Behaviors and Events do not reveal > in their type definitions any relation to any system that they may or > may not exist in. OK. So how does e.g. mousePoint :: Behavior Point get at the mouse input? unsafePerformIO? I.e. it is conceptually a global signal? main = adapter doSomeStuff -- Note here that different adapters provide different "UI"s. adapter :: (Behavior UI -> Behavior SomethingFixedThatYouKnowHowToInterpret) -> IO () adapter f = set up the system behaviors, pass them into f, grab the outputs, and do the "something" to render. doSomeStuff :: Behavior UI -> Behavior SomethingFixedThatYouKnowHowToInterpret > I'm not sure I understand you clearly. If I wish to apply a constant > function to a signal, can I not just use fmap? The question is why I would want to (conceptually). I'm just saying I find it good and useful to be able to easily mix static values and computations and signals and computations on signals. Yep, I can see that, I think we need to agree to disagree on this front, I would prefer to use fmap, or <$>, while you prefer arrow syntax. > You would certainly need to ask Conal on this point, but I have no > reason to suspect that b' = [1,2,3,4,5] `stepper` listE [(1,[])] would > not deallocate the first list once it had taken its step. It's not the lists that concern me, nor getting rid of a collection of behaviors all at once. The problem is if we ant to run a collection of behaviors in parallel, all potentially accumulating internal state, how do we add/delete individual behaviors to/from that collection, without "disturbing" the others? For the sake of argument, say we have the following list of behaviours: [integral time, integral (2 * time), integral (3 * time)] We turn them into a single behavior with a list output in order to run them. After one second the output is thus [1,2,3] Now, we want to delete the second behavior, but continue to run the other two, so that the output at time 2 is [2,6] Simply mapping postprocessing that just drops the second element from the output isn't a satisfactory solution. I'm not sure why mapping the function is not satisfactory -- It would create a new Behavior, who's internals contain only the two elements from the list -- that would expose to the garbage collector that the second element has no reference from this behavior any more, and thus the whole behavior could be collected. > Yes, we really do get a shared n -- without doing that we certainly > would see a large space/time leak. Interesting, although I don't see why not sharing would imply a space/time leak: if the behavior is simply restarted, there is no catchup computation to do, nor any old input to hang onto, so there is neither a time nor a space-leak? Anyway, let's explore this example a bit further. Suppose "lbp" is the signal of left button presses, and that we can count them by "count lbp" Then the question is if let n :: Behavior Int n = count lbp in n `until` -=> n means the same as (count lbp) `until` -=> (count lbp) If no, then Reactive is not referentially transparent, as we manifestly cannot reason equationally. If yes, the question is how to express a counting that starts over after the switch (which sometimes is what is needed). That's a yes. My first answer to how to implement the resetting counter would be someting along the lines of this, but I'm not certain it's dead right: e = (1+) <$ mouseClick e' = (const 0) <$ b = accumB 0 (e `mappend` e') i.e. b is the behavior got by adding 1 every time the mouse click event occurs, but resetting to 0 whenever occurs. > Yep, such Behaviors are seperated in Reactive only by the method you > create them with. I may use the `stepper` function to create a > behavior that increases in steps based on an event occurring, or I may > use fmap over time to create a continuously varying Behavior. But the question was not about events vs continuous signals. The question is, what is a behavior conceptually, and when is it started? E.g. in the example above, at what point do the various instances of "count lbp" start counting? Or are the various instances of "count lbp" actually only one? They are indeed, only 1. Or if you prefer, are beahviours really signals, that conceptually start running all at once at a common time 0 when the system starts? The answers regarding input behaviors like mousePosition, that "n is shared", and the need to do catchup computations all seem to indicate this. But if so, that leaves open an important question on expressivity, examplified by how to start counting from the time of a switch above, and makes if virtually impossible to avoid time and space leaks in general, at least in an embedded setting. After all, something like "count lbp" can be compiled int
Re: [Haskell-cafe] Coroutines
Robin Green wrote: In my opinion, in Haskell, you don't need coroutines because you have lazy evaluation. You example below is simply an example of a heterogenous list being read. The simplest way to implement a heterogenous list in Haskell is to use a tuple. Or you could use the HList package. Not quite. The consumer, useSimple, is an example of a heterogenous list being read. The producer, simple, is an example of producing a heterogenous list, value by value, on demand. You don't get that from HList for free. The difference between coroutines and lazy evaluation is that in the latter the consumer has full control. Producer supplies all the thunks, consumer picks which thunk to evaluate. Of course the producer could return a pair of first value and the rest of the computation, but then any control structure can be encoded using continuations. The question is one of notational convenience. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Coroutines
Another implementation of coroutines is in the Streaming Component Combinators on Hackage (http://hackage.haskell.org/cgi-bin/hackage-scripts/package/scc). In this version, a coroutine is a monad transformer that can be laid over any monad, including Id and IO. Furthermore, you can have an arbitrary number of inputs/output channels but they are restricted to communicating a single value type. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Yampa vs. Reactive
Hi Tom, > I don't think this is really true. Behaviors and Events do not reveal > in their type definitions any relation to any system that they may or > may not exist in. OK. So how does e.g. mousePoint :: Behavior Point get at the mouse input? unsafePerformIO? I.e. it is conceptually a global signal? > I'm not sure I understand you clearly. If I wish to apply a constant > function to a signal, can I not just use fmap? The question is why I would want to (conceptually). I'm just saying I find it good and useful to be able to easily mix static values and computations and signals and computations on signals. > You would certainly need to ask Conal on this point, but I have no > reason to suspect that b' = [1,2,3,4,5] `stepper` listE [(1,[])] would > not deallocate the first list once it had taken its step. It's not the lists that concern me, nor getting rid of a collection of behaviors all at once. The problem is if we ant to run a collection of behaviors in parallel, all potentially accumulating internal state, how do we add/delete individual behaviors to/from that collection, without "disturbing" the others? For the sake of argument, say we have the following list of behaviours: [integral time, integral (2 * time), integral (3 * time)] We turn them into a single behavior with a list output in order to run them. After one second the output is thus [1,2,3] Now, we want to delete the second behavior, but continue to run the other two, so that the output at time 2 is [2,6] Simply mapping postprocessing that just drops the second element from the output isn't a satisfactory solution. > > let > > n :: Behavior Int > >n = > > in > > n `until` -=> n > > > > I'm not sure I got the syntax right. But the idea is that we > > output the number of left mouse button clicks, and then at some > > point, we switch to a behavior that again output the number of left > > mouse button clicks, notionally the "same" one "n". > > > > The question is, after the switch, do we observe a count that > > continues from where the old one left off, i.e. is there a > > single *shared* instance of "n" that is merely being *observed* > > from within the two "branches" of the switch, or is the counting > > behavior "n" restarted (from 0) after the switch? > > Yes, we really do get a shared n -- without doing that we certainly > would see a large space/time leak. Interesting, although I don't see why not sharing would imply a space/time leak: if the behavior is simply restarted, there is no catchup computation to do, nor any old input to hang onto, so there is neither a time nor a space-leak? Anyway, let's explore this example a bit further. Suppose "lbp" is the signal of left button presses, and that we can count them by "count lbp" Then the question is if let n :: Behavior Int n = count lbp in n `until` -=> n means the same as (count lbp) `until` -=> (count lbp) If no, then Reactive is not referentially transparent, as we manifestly cannot reason equationally. If yes, the question is how to express a counting that starts over after the switch (which sometimes is what is needed). > Yep, such Behaviors are seperated in Reactive only by the method you > create them with. I may use the `stepper` function to create a > behavior that increases in steps based on an event occurring, or I may > use fmap over time to create a continuously varying Behavior. But the question was not about events vs continuous signals. The question is, what is a behavior conceptually, and when is it started? E.g. in the example above, at what point do the various instances of "count lbp" start counting? Or are the various instances of "count lbp" actually only one? Or if you prefer, are beahviours really signals, that conceptually start running all at once at a common time 0 when the system starts? The answers regarding input behaviors like mousePosition, that "n is shared", and the need to do catchup computations all seem to indicate this. But if so, that leaves open an important question on expressivity, examplified by how to start counting from the time of a switch above, and makes if virtually impossible to avoid time and space leaks in general, at least in an embedded setting. After all, something like "count lbp" can be compiled into a function that potentially may be invoked at some point. And as long as this possibility exists, the system needs to hang on to the entire history of mouse clicks so that they can be coounted at some future point if necessary. These are all questions that go back to classical FRP, which we didn't find any good answers to back then, and which also were part of the motivation for moving to AFRP/Yampa. If Reactive has come up with better answers, that would be very exciting indeed! Best, /Henrik -- Henrik Nilsson School of Computer Science The University of Nottingham n...@cs.nott.ac.uk This message has been checked fo
Re[4]: [Haskell-cafe] Coroutines
Hello Brandon, Thursday, December 18, 2008, 7:05:05 PM, you wrote: >> ruby doesn't support coroutines, but only iterators (where control >> moved from caller to callee). usually control is on the caller side, >> and coroutines gives control to both (or many) sides > Right, and you don't normally do iterators in Haskell; you do map/fmap. iterators are not cycles :) they allow to return value without returning control -- Best regards, Bulatmailto:bulat.zigans...@gmail.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Coroutines
Andrew was recently asking about co-routines. A couple of years ago, I was in much the same position as him; although I am pretty sure I had heard the term before, it seemed like a mysterious idea with no practical use. Besides the point that people have already made that lazy evaluation gives you similar control as coroutines, I wanted to point out how simple it is to implement coroutines. Here's a simple implementation that ddarius made on IRC a few months back off-the-cuff. I kept it around on codepad because its cool: http://codepad.org/GwtS6wMj -- ryan Tim Newsham http://www.thenewsh.com/~newsham/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] gtk2hs question - derive SettingsWindow from Window
On Fri, 2008-12-12 at 21:03 +0100, Cetin Sert wrote: > Hi all, > > For a network manager of sorts I'm working on, I want to derive a > SettingsWindowClass from the WindowClass present in Gtk2Hs: > > I want (the) instance(s) of the SettingsWindowClass to have a field to > store connection settings: > > 1) Is it safe to do it like this? You've missed out the unsafe bit where you make SettingsWindow an instance of class WindowClass. That bit will not work because the upcast function is not a proper Haskell function just is just a pointer cast. Currently the assumption is that each gtk2hs type is backed by a C type held in a ForeignPtr. We should generalise that to allow subclasses defined in Haskell. > class WindowClass self ⇒ SettingsWindowClass self where > settingsWindowGetSettings :: self → IO [ConnectionSetting] > settingsWindowSetSettings :: self → [ConnectionSetting] → IO () > > newtype SettingsWindow = SettingsWindow (Window,[ConnectionSetting]) So you can use this newtype, you just can't make it an instance of WindowClass. > mkSettingsWindow = SettingsWindow > unSettingsWindow (SettingsWindow o) = o > > settingsWindowNew :: IO SettingsWindow > settingsWindowNew = do > win ← windowNew > return $ mkSettingsWindow (win,[]) > > 2) Is this a common practice in gtk2hs usage? Making records of widgets is pretty common. > 3) And will GC properly free the memory allocated for the Window > object? How is this ensured, do ForeignPtr's always call delete on the > underlying C ptr when they get garbage collected? Right, exactly. Duncan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Haskell, successing crossplatform API standart
> Oh, but JSON doesn't seem to support tree-structured data... { "value" : 5, "left" : { "value" : 3, "left" : null, "right" : null }, "right" : { "value" : 8, "left" : null, "right" : null } } JSON *is* tree structured data. /jve On Thu, Dec 18, 2008 at 1:41 AM, Belka wrote: > > Thanks for the info! > > > These days, however, web services seem to be moving towards a RESTful > model with a JSON layer and there are plenty of JSON libraries on > hackage, which you could just throw over the fastCGI bindings. > > Oh, but JSON doesn't seem to support tree-structured data... This might > turn > into hell, when highly demanded in big infrastructures with complex > communications. That's why I guess my choise will be XML. Don't know any > good alternative with total support on every platform. > -- > View this message in context: > http://www.nabble.com/Haskell%2C-successing-crossplatform-API-standart-tp20742743p21067779.html > Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com. > > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Yampa vs. Reactive
Hi Henrik, On 18 Dec 2008, at 14:26, Henrik Nilsson wrote: Hi Tom, > I'll have an attempt at addressing the questions, although I freely > admit that I'm not as "into" Reactive as Conal is yet, so he may come > and correct me in a minute. > [...] > Reactive has explicitly parameterized inputs. In your robot example I > would expect something along the lines of > > data RobotInputs = > RI {lightSensor :: Behavior Colour; > bumbSwitch :: Event ()} -- A couple of example robot sensors > > robotBehavior :: RobotInputs -> Behavior Robot > robotBehavior sensors = a behovior that combines the light sensor and > the bumb switch to stay in the light, but not keep driving into > things. This looks exactly like Classical FRP. And if it is like Classical FRP behind the scenes, it nicely exemplifies the problem. In Classical FRP, Behavior is actually what I would call a signal function. When started (switched into), they map the system input signal from that point in time to a signal of some particular type. So, the record RobotInputs is just a record of lifted projection functions that selects some particular parts of the overall system input. Behind the scenes, all Behaviors are connected to the one and only system input. I don't think this is really true. Behaviors and Events do not reveal in their type definitions any relation to any system that they may or may not exist in. A Behavior can exist wether or not it is being run by a particular legacy adapter (a piece of code to adapt it to work as expected on a legacy, imperative computer). I can define an Event e = (+1) <$ atTimes [0,10..] and use it as a Haskell construct without needing any system at all to run it within. Similarly I can define a Behavior b = accumB 0 e that depends on this event, completely independant of any system, or definition of what basic events and behaviors I get to interact with it. > data UIInputs = UI {mousePoint :: Behavior Point; mouseClick :: Event > (); ...} > > world :: UIInputs -> Behavior World > world = interpret mouse and produce a world with barriers, robots and > lights in it Fine, of course, assuming that all behaviours share the same kind of system input, in this case UI input. But what if I want my reactive library to interface to different kinds of systems? The robot code should clearly work regardless of whether we are running it on a real hardware platform, or in a simulated setting where the system input comes form the GUI. In Classical FRP, this was not easily possible, because all combinators at some level need to refer to some particular system input type which is hardwired into the definitions. There are no hardwired definitions of what inputs I'm allowed to use or not use. If I would like my reactive program to run on a "legacy" robot which uses imperative IO, then I may write a legacy adapter around it to take those IO actions and translate them into Events and Behaviors that I can use. One such legacy adapter exists, called reactive-glut, which ties glut's IO actions into reactive events one can use. I could easily imagine several others, for example one that interacts with robot hardware and presents the record above to the behaviors it's adapting, or another still which works much like the "interact" function, but instead of taking a String -> String, takes an Event Char -> Event Char. Had Haskell had ML-style parameterized modules, that would likely have offered a solution: the libraries could have been parameterized on the system input, and then one could obtain say robot code for running on real hardware or in a simulated setting by simply applying the robot module to the right kind of system input. An alternative is to parameterize the behaviour type explicitly on the system input type: Behavior sysinput a This design eventually evolved into Arrowized FRP and Yampa. So, from your examples, it is not clear to what extent Reactive as addressed this point. Just writing functions that maps behaviours to behaviours does not say very much. On a more philosophical note, I always found it a bit odd that if I wanted to write a function that mapped a signal of, say, type "a", which we can think of as type Signal a = Time -> a to another signal, of type "b" say, in Classical FRP, I'd have to write a function of type Behavior a -> Behavior b which really is a function of type (Signal SystemInput -> Signal a) -> (Signal SystemInput -> Signal b) I find this unsatisfying, as my mapping from a signal of type a to a signal of type b is completely independent from the system input (or the function wouldn't have a polymorphic type). Yes, certainly that would be unsatisfactory. But I don't agree about the type of the function -- this really is a (Time -> a) -> (Time -> a). It may be though that the argument (Time -> a) is a system input from our legacy adapter, or an internal part of our program.
Re: [Haskell-cafe] Haskell as a religion
On 2008 Dec 18, at 11:47, Paul Moore wrote: 2008/12/18 Brandon S. Allbery KF8NH : On 2008 Dec 18, at 9:13, John Goerzen wrote: Some ideas in Haskell are easy to integrate into other languages: see list comprehensions in Python. I don't see Perl picking up pervasive laziness anytime soon, nor Python compile-time type inference. I think perl6 is specced with pervasive laziness, although I'm not sure it's actually implemented anywhere. I assumed it was implemented lazily, so that when you use it somewhere, the Perl 6 developers implement that part of the feature :-) Lot of truth to that at the moment :) -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu 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] Haskell as a religion
2008/12/18 Brandon S. Allbery KF8NH : > On 2008 Dec 18, at 9:13, John Goerzen wrote: >> >> Some ideas in Haskell are easy to integrate into other languages: see >> list comprehensions in Python. I don't see Perl picking up pervasive >> laziness anytime soon, nor Python compile-time type inference. > > I think perl6 is specced with pervasive laziness, although I'm not sure it's > actually implemented anywhere. I assumed it was implemented lazily, so that when you use it somewhere, the Perl 6 developers implement that part of the feature :-) Paul. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Haskell as a religion
On Thu, 18 Dec 2008 11:27:14 -0500, Brandon S. Allbery KF8NH wrote: > On 2008 Dec 18, at 9:13, John Goerzen wrote: >> Some ideas in Haskell are easy to integrate into other languages: see >> list comprehensions in Python. I don't see Perl picking up pervasive >> laziness anytime soon, nor Python compile-time type inference. > > I think perl6 is specced with pervasive laziness, although I'm not > sure it's actually implemented anywhere. I'm not sure about pervasive, but I read somewhere that Perl 6's lists are head-strict, tail-lazy by default... Regards, Brad Larsen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Haskell as a religion
On 2008 Dec 18, at 9:13, John Goerzen wrote: Some ideas in Haskell are easy to integrate into other languages: see list comprehensions in Python. I don't see Perl picking up pervasive laziness anytime soon, nor Python compile-time type inference. I think perl6 is specced with pervasive laziness, although I'm not sure it's actually implemented anywhere. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu electrical and computer engineering, carnegie mellon universityKF8NH ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Re[2]: [Haskell-cafe] Coroutines
On 2008 Dec 18, at 5:47, Bulat Ziganshin wrote: ruby doesn't support coroutines, but only iterators (where control moved from caller to callee). usually control is on the caller side, and coroutines gives control to both (or many) sides Right, and you don't normally do iterators in Haskell; you do map/fmap. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu electrical and computer engineering, carnegie mellon universityKF8NH ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Fwd: [Haskell-cafe] Haskell as a religion
But many features need other features. For example, the option to use referential transparency will be common in future languages for multicore programming purposes. This creates the problem of separating side-effect-free code from side-effect code. For this purpose, a strong type system at compile time is needed, which indeed need automatic type inference or, else, the user will be too busy with the details. The type inference open the door for experimenting with complex data types. class types is a logical step after that. Monads are the best option for many problems once the programmer have all te above. higuer order functions are being taken seriously in other languages. this goes to the need of currying and lists. optional lazyness and tail recursion is the most elegant option for expressing lists managing code. Will all the above, explicit loops will be avoided by the programmer, this will end up in mode declarative programming style. I think that once the average programmer start to use one or two of these features, he will feel a bit frustrated if its language don´t have all the others, specially if he know haskell. Probably, he will use haskell for fun. This is the best way for the takeover of the industry, because this has been so historically. 2008/12/18 John Goerzen Andrew Coppin wrote: > > Don Stewart wrote: > >> I think of Haskell more as a revolutionary movement > > > > LOL! Longest revolution EVER, eh? I mean, how long ago was its dogma > > first codified? ;-) > > Lisp has been around for how long now? Measured in decades. We don't > even have our version of a Symbolics machine yet! > > > Basically, Haskell will never be popular, but its coolest ideas will be > > stolen by everybody else and passed off as their own. :-( > > Well, in a sense, if that happens, we would have won, right? We'd have > created a situation where "paradigm shift" would mean more than just a > buzzword on some CEO's presentation slide ;-) > > In another sense, isn't this what Haskell was explicitly created to do? > (Combine ideas from a bunch of similar languages into one standard one) > > Some ideas in Haskell are easy to integrate into other languages: see > list comprehensions in Python. I don't see Perl picking up pervasive > laziness anytime soon, nor Python compile-time type inference. > > -- 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: [Haskell] possible bug in pretty-1.0.1.0
On Thu, 2008-12-18 at 13:27 +, Neil Mitchell wrote: > Hi Duncan, > > > I'd just like to advertise the fact that as of Cabal-1.6 you can put a > > bug-reports field in your .cabal file and it will be displayed by > > hackage. > > Fantastic. Is it backwards compatible? i.e. if I add such a field, > will Cabal-1.2 give warnings/errors? It should give warnings but not errors. Unfortunately for the source repo stuff that uses a new section which the old parser did not handle quite so gracefully. Duncan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Haskell as a religion
as some german right-hegelian thinkers of the beginning of the 20th century noticed, the hegelian system is missing what we call 'action'. the whole system can be described as a timeless and closed set of invariant relations between parts of the world, which can also be seen as gods thinking. this critique is similar to the marxist turn of the hegelian philosophy. now, thinking of an timeless set of invariant relations, that should be extended by some concept of action, reminds me of haskell's monads. so I would say, haskell is not a revolutionary movement itself, its just a (or: THE) vehicle of the revolutionary progress that started 200 years ago (some might say, 2000 years ago). it's the place where the 'spirit of the world' comes to itself in these days... just kidding. daniel Jonathan Cast schrieb: On Tue, 2008-12-16 at 20:38 +, Andrew Coppin wrote: Don Stewart wrote: I think of Haskell more as a revolutionary movement LOL! Longest revolution EVER, eh? No. Das Kapital publication 1867. Russian Revolution 1917. FTW. jcc ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-caf ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Haskell as a religion
Andrew Coppin wrote: > Don Stewart wrote: >> I think of Haskell more as a revolutionary movement > > LOL! Longest revolution EVER, eh? I mean, how long ago was its dogma > first codified? ;-) Lisp has been around for how long now? Measured in decades. We don't even have our version of a Symbolics machine yet! > Basically, Haskell will never be popular, but its coolest ideas will be > stolen by everybody else and passed off as their own. :-( Well, in a sense, if that happens, we would have won, right? We'd have created a situation where "paradigm shift" would mean more than just a buzzword on some CEO's presentation slide ;-) In another sense, isn't this what Haskell was explicitly created to do? (Combine ideas from a bunch of similar languages into one standard one) Some ideas in Haskell are easy to integrate into other languages: see list comprehensions in Python. I don't see Perl picking up pervasive laziness anytime soon, nor Python compile-time type inference. -- John ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Yampa vs. Reactive
Hi Tom, > I'll have an attempt at addressing the questions, although I freely > admit that I'm not as "into" Reactive as Conal is yet, so he may come > and correct me in a minute. > [...] > Reactive has explicitly parameterized inputs. In your robot example I > would expect something along the lines of > > data RobotInputs = > RI {lightSensor :: Behavior Colour; > bumbSwitch :: Event ()} -- A couple of example robot sensors > > robotBehavior :: RobotInputs -> Behavior Robot > robotBehavior sensors = a behovior that combines the light sensor and > the bumb switch to stay in the light, but not keep driving into > things. This looks exactly like Classical FRP. And if it is like Classical FRP behind the scenes, it nicely exemplifies the problem. In Classical FRP, Behavior is actually what I would call a signal function. When started (switched into), they map the system input signal from that point in time to a signal of some particular type. So, the record RobotInputs is just a record of lifted projection functions that selects some particular parts of the overall system input. Behind the scenes, all Behaviors are connected to the one and only system input. > data UIInputs = UI {mousePoint :: Behavior Point; mouseClick :: Event > (); ...} > > world :: UIInputs -> Behavior World > world = interpret mouse and produce a world with barriers, robots and > lights in it Fine, of course, assuming that all behaviours share the same kind of system input, in this case UI input. But what if I want my reactive library to interface to different kinds of systems? The robot code should clearly work regardless of whether we are running it on a real hardware platform, or in a simulated setting where the system input comes form the GUI. In Classical FRP, this was not easily possible, because all combinators at some level need to refer to some particular system input type which is hardwired into the definitions. Had Haskell had ML-style parameterized modules, that would likely have offered a solution: the libraries could have been parameterized on the system input, and then one could obtain say robot code for running on real hardware or in a simulated setting by simply applying the robot module to the right kind of system input. An alternative is to parameterize the behaviour type explicitly on the system input type: Behavior sysinput a This design eventually evolved into Arrowized FRP and Yampa. So, from your examples, it is not clear to what extent Reactive as addressed this point. Just writing functions that maps behaviours to behaviours does not say very much. On a more philosophical note, I always found it a bit odd that if I wanted to write a function that mapped a signal of, say, type "a", which we can think of as type Signal a = Time -> a to another signal, of type "b" say, in Classical FRP, I'd have to write a function of type Behavior a -> Behavior b which really is a function of type (Signal SystemInput -> Signal a) -> (Signal SystemInput -> Signal b) I find this unsatisfying, as my mapping from a signal of type a to a signal of type b is completely independent from the system input (or the function wouldn't have a polymorphic type). > > * A clear separation between signals, signal functions, and ordinary > > functions and values, yet the ability to easily integrate all > > kinds of computations. > > I agree and disagree here (that'll be the matter of taste creeping > in). I agree that in Reactive you often spend a lot of keystrokes > lifting pure values into either an Event or a Behavior. Having said > that I'd argue that Yampa requires us to do this too -- it merely > enforces the style in which we do it (we must do it with arrows). Yes, there is lifting in Yampa, but the arrow syntax mostly does it for the programmer, which in practice (in my experience) translates to a lot less effort, and, in my opinion, leads to clearer code as it is easy to maintain a distinction between signals and static values. After all, why should I want to live a constant to a signal, if all I'm going to do with it is to apply one and the same function to it over and over? (I'm not worried about efficiency here, that can be fixed: it's a philosophical point.) Also, form practical experience when programming with Classical FRP, we often lifted entire libraries we wanted to use to avoid having to write explicit lifts all the time. Tedious, but OK, doable. However, quite often we then discovered that actually, we needed the unlifted version of the library too, leading to name clashes and thus extra noise to do the need to disambiguate, be it by qualified input or naming the lifted versions differently. Not a show stopper by any means, but a tedious extra level of concerns. The arrow framework offer clear guidance in this case which translates to convenient coding practice: just use whatever library you need and let the arrow syntax take care of liftings where necessary. >
[Haskell-cafe] Re: [Haskell] possible bug in pretty-1.0.1.0
Hi Duncan, > I'd just like to advertise the fact that as of Cabal-1.6 you can put a > bug-reports field in your .cabal file and it will be displayed by > hackage. Fantastic. Is it backwards compatible? i.e. if I add such a field, will Cabal-1.2 give warnings/errors? Thanks Neil ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Detecting system endianness
On Thursday 18 December 2008 13:40:47 Ryan Ingram wrote: > Actually, this is probably safer: > > import Foreign.Marshal.Alloc > import Foreign.Ptr > import Foreign.Storable > import Data.Word > import System.IO.Unsafe > > endianCheck = unsafePerformIO $ alloca $ \p -> poke p (0x01020304 :: > Word32) >> peek (castPtr p :: Ptr Word8) > > littleEndian = endianCheck == 4 > bigEndian = endianCheck == 1 > > -- ryan > > On Thu, Dec 18, 2008 at 4:33 AM, Ryan Ingram wrote: > > I think something like this might work: > > > > Prelude GHC.Exts GHC.Word> let W64# x = 0x10002 in W32# > > (unsafeCoerce# x) 2 > > > > You should get 1 for big-endian and 2 for little-endian. > > > > (Disclaimer: not particularily well-tested.) Using modules Data.Binary, Data.Binary.Put and Data.Word, you can define littleEndian = (decode $ runPut $ putWord16host 42 :: Word8) == 42 Under the hood, it also uses peek and poke, but it looks a bit more functional. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: [Haskell] possible bug in pretty-1.0.1.0
On Mon, 2008-12-15 at 08:17 -0800, John MacFarlane wrote: > I noticed a difference in how "hang" works between pretty-1.0.0.0 and > pretty-1.0.1.0. I think it's a bug. If this isn't the right place to > report it, please let me know where I should. (Maintainer is listed > as librar...@haskell.org, but that is a closed mailing list. Perhaps > Cabal should include a report-bugs-at field?) I'd just like to advertise the fact that as of Cabal-1.6 you can put a bug-reports field in your .cabal file and it will be displayed by hackage. We would like to encourage all package authors to use this. It can be a mailto: url to a maintainer or mailing list or it can be a http: url to a bug tracker website. (Cabal-1.6 also supports specifying darcs/git/whatever repos) Duncan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Functional MetaPost in 5 Steps
I have the same problem with FuncMP. I've also replaced the "generate" function by a custom "toMPFile" as you suggested, but mpost still generates only an empty white sheet. I've used the simple example posted in the first message of this thread. The generated .mp file is also relatively simple (see attachment http://www.nabble.com/file/p21070707/Test.mp Test.mp ) The only problem is the line "input FuncMP", which produces additional code in the ps file and causes the white page. If you remove this line everything is fine again and you can see the text "blah". Here's the additional code FuncMP produces in the .ps file: - /xdvi$run where {pop errordict begin /undefined {} bind def end} if /fmp1 /fmp1 def /fmp8 /fmp8 def /fmp24 /fmp24 def /bitline1 {gsave pop dup scale dup length 8 mul 1 true currentpoint translate [66.6 0 0 66.6 0 0] 4 index imagemask pop grestore} bind def /bitline8 {gsave pop dup scale dup length 1 8 currentpoint translate [2.8 0 0 2.8 0 0] 4 index image pop grestore} bind def /bitline24 {gsave pop dup scale dup length 3 idiv 1 8 currentpoint translate [2.77 0 0 2.77 0 0] 4 index false 3 colorimage pop grestore} bind def /XDVIfshow {findfont exch scalefont setfont show} bind def /DVIPSfshow {exch gsave 72 TeXDict /Resolution get div -72 TeXDict /VResolution get div scale 1 DVImag div dup scale get cvx exec show grestore} bind def /fshowText {/xdvi$run where {pop XDVIfshow} {DVIPSfshow} ifelse} def /fshow { exch dup /fmp1 eq {bitline1} {dup /fmp8 eq {bitline8} {dup /fmp24 eq {bitline24} {fshowText} ifelse} ifelse} ifelse} def - You can also fix the .ps file by removing the "/fshow ..." part from the file and the text "blah" will appear in your ghostscript viewer. Well, this is my first test with FuncMP and that's why I'm asking this silly question now: Is the "fshow" function really necessary or can I remove it from every generated .ps file without problems? :) Or you know another solution? Does your generated .ps files also contain this code? If no, what version of FuncMP do you use? -- View this message in context: http://www.nabble.com/Functional-MetaPost-in-5-Steps-tp20144360p21070707.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Detecting system endianness
Actually, this is probably safer: import Foreign.Marshal.Alloc import Foreign.Ptr import Foreign.Storable import Data.Word import System.IO.Unsafe endianCheck = unsafePerformIO $ alloca $ \p -> poke p (0x01020304 :: Word32) >> peek (castPtr p :: Ptr Word8) littleEndian = endianCheck == 4 bigEndian = endianCheck == 1 -- ryan On Thu, Dec 18, 2008 at 4:33 AM, Ryan Ingram wrote: > I think something like this might work: > > Prelude GHC.Exts GHC.Word> let W64# x = 0x10002 in W32# (unsafeCoerce# x) > 2 > > You should get 1 for big-endian and 2 for little-endian. > > (Disclaimer: not particularily well-tested.) > > -- ryan > > On Thu, Dec 18, 2008 at 3:27 AM, Mauricio wrote: >> Hi, >> >> Is there some way I can check the endianness >> of the machine my haskell code is running in? >> >> Thanks, >> Maurício >> >> ___ >> 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] Detecting system endianness
I think something like this might work: Prelude GHC.Exts GHC.Word> let W64# x = 0x10002 in W32# (unsafeCoerce# x) 2 You should get 1 for big-endian and 2 for little-endian. (Disclaimer: not particularily well-tested.) -- ryan On Thu, Dec 18, 2008 at 3:27 AM, Mauricio wrote: > Hi, > > Is there some way I can check the endianness > of the machine my haskell code is running in? > > Thanks, > Maurício > > ___ > 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] Coroutines
On Thu, Dec 18, 2008 at 3:01 AM, Robin Green wrote: > In my opinion, in Haskell, you don't need coroutines because you have > lazy evaluation. That's a fair criticism. Lazy evaluation basically gives you a coroutine embedded in any data structure. But sometimes making implicit things explicit aids understanding! Especially when there can be communication in both directions; that is, the data structure can be somewhat dependent on the code doing the evaluation. In addition, I think coroutines under effectful monads are still potentially useful. It would not be too hard to extend this library to allow effectful computations to communicate. At the very least I can easily imagine a version of InSession that supports lifting from IO into coroutines. > You example below is simply an example of a heterogenous list being > read. The simplest way to implement a heterogenous list in Haskell is > to use a tuple. Or you could use the HList package. Actually, the result of "runSession simple" is isomorphic to a tuple/heterogeneous list: > data instance InSession (a :!: r) v = W a (InSession r v) > newtype instance InSession Eps v = Eps v runSession simple :: InSession (String :!: Int :!: (Int -> Int) :!: Eps) () => W "hello" $ W 1 $ W (+1) $ Eps () Similarily, useSimple evaluates to a function of three arguments: > newtype instance InSession (a :?: r) v = R (a -> InSession r v) runSession useSimple => R $ \string -> R $ \int -> R $ \func -> Eps (string ++ show (int * 4) ++ show (func 10)) There are three pieces to this package: 1) A monad-like structure that gives nice syntax for the construction of InSession values. 2) A data family that gives a representation of these values as different functors. This is similar to using the TypeCompose library [1] and the (,) a and (->) a Functor instances [2]. That is, in some way (a :!: r) represents ((,) a) . r. (.) here represents function composition at the *type* level. This allows composition of functors: (a :!: b :?: c :!: Eps) == (a,) . (b ->) . (c,) . Id == \v -> (a, b -> (c,v)) where again, the lambda is at the type level, and (a,) means a section at the type level similar to (5 <=) at the value level. (As an aside, my thanks to Simon Peyton-Jones for suggesting this representation of sessions using type families.) 3) A "duality" type family and connector which shows which functors can be connected to which other functors. This is similar to the "zap" operation in Category-extras [3]. I wrote the library initially to play around with (1); Indexed monads are an interesting topic and I don't think they are well covered outside of the dense material by Oleg & friends. I definitely understand them much better after writing it! (2) and (3) are there to give some structure to the exercise. The other goal was to give a machine-checkable proof of the semantics of session types described in Jesse Tov's paper [4]. In the paper, sessions are represented by effectful computations, which run in parallel and communicate over *untyped* channels, using unsafeCoerce. The paper contains a proof that this is indeed safe, but it seemed worthwhile to encode the proof in the Haskell type system, allowing the possibility to remove unsafeCoerce. -- ryan [1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/TypeCompose-0.6.3 [2] http://haskell.org/ghc/docs/latest/html/libraries/base/Control-Monad-Instances.html [3] http://comonad.com/reader/2008/zapping-strong-adjunctions/ [4] http://www.ccs.neu.edu/home/tov/pubs/session08.html ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Detecting system endianness
Hi, Is there some way I can check the endianness of the machine my haskell code is running in? Thanks, Maurício ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Coroutines
In my opinion, in Haskell, you don't need coroutines because you have lazy evaluation. You example below is simply an example of a heterogenous list being read. The simplest way to implement a heterogenous list in Haskell is to use a tuple. Or you could use the HList package. -- Robin On Thu, 18 Dec 2008 02:26:26 -0800 "Ryan Ingram" wrote: > On Thu, Dec 18, 2008 at 2:00 AM, Nicolas Pouillard > wrote: > > I don't see why one would need session types, channels... to > > express that. I maybe need a more complicated coroutines (ruby) > > example that would require using this system. > > OK, how would you type these routines in Haskell? > > def simple > yield "hello" > yield 1 > yield (lambda { |x| x + 1 }) > end > > def useSimple > state = 0 > result = nil > simple { |x| > if (state == 0) then result = x > else if (state == 1) then result += (x * 4).toString > else if (state == 2) then result += x.call(10).toString > state = state + 1 > } > result > end > > I know it's a bit contrived, but you get the idea. > > In Haskell using Control.Coroutine: > > simple :: forall rest. Session (String :!: Int :!: (Int -> Int) :!: > rest) rest () > simple = do > put "hello" > put 1 > put (\x -> x + 1) > > useSimple :: forall rest. Session (String :?: Int :?: (Int -> Int) :?: > rest) rest String > useSimple = do > string <- get > int <- get > func <- get > return (string ++ show (int * 4) ++ show (func 10)) > > result :: String > result = snd $ connects simple useSimple > -- result = "hello411" > ___ > 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[2]: [Haskell-cafe] Coroutines
Hello Miguel, Thursday, December 18, 2008, 1:42:21 PM, you wrote: ruby doesn't support coroutines, but only iterators (where control moved from caller to callee). usually control is on the caller side, and coroutines gives control to both (or many) sides coroutines are easily emulated in IO monad using multithreading, and i think that are easily emulated both in Ruby and Haskell using callCC > First thing I've tried when learning Ruby was something like that: > > def a >yield {puts 1} > end > a {yield} > > It didn't work. Can Coroutine.hs do something like that? > On 18 Dec 2008, at 13:26, Ryan Ingram wrote: >> On Thu, Dec 18, 2008 at 2:00 AM, Nicolas Pouillard >> wrote: >>> I don't see why one would need session types, channels... to >>> express that. >>> I maybe need a more complicated coroutines (ruby) example that >>> would require >>> using this system. >> >> OK, how would you type these routines in Haskell? >> >> def simple >>yield "hello" >>yield 1 >>yield (lambda { |x| x + 1 }) >> end >> >> def useSimple >>state = 0 >>result = nil >>simple { |x| >>if (state == 0) then result = x >>else if (state == 1) then result += (x * 4).toString >>else if (state == 2) then result += x.call(10).toString >>state = state + 1 >>} >>result >> end >> >> I know it's a bit contrived, but you get the idea. >> >> In Haskell using Control.Coroutine: >> >> simple :: forall rest. Session (String :!: Int :!: (Int -> Int) :!: >> rest) rest () >> simple = do >>put "hello" >>put 1 >>put (\x -> x + 1) >> >> useSimple :: forall rest. Session (String :?: Int :?: (Int -> Int) :?: >> rest) rest String >> useSimple = do >>string <- get >>int <- get >>func <- get >>return (string ++ show (int * 4) ++ show (func 10)) >> >> result :: String >> result = snd $ connects simple useSimple >> -- result = "hello411" >> ___ >> 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 -- Best regards, Bulatmailto:bulat.zigans...@gmail.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Coroutines
First thing I've tried when learning Ruby was something like that: def a yield {puts 1} end a {yield} It didn't work. Can Coroutine.hs do something like that? On 18 Dec 2008, at 13:26, Ryan Ingram wrote: On Thu, Dec 18, 2008 at 2:00 AM, Nicolas Pouillard wrote: I don't see why one would need session types, channels... to express that. I maybe need a more complicated coroutines (ruby) example that would require using this system. OK, how would you type these routines in Haskell? def simple yield "hello" yield 1 yield (lambda { |x| x + 1 }) end def useSimple state = 0 result = nil simple { |x| if (state == 0) then result = x else if (state == 1) then result += (x * 4).toString else if (state == 2) then result += x.call(10).toString state = state + 1 } result end I know it's a bit contrived, but you get the idea. In Haskell using Control.Coroutine: simple :: forall rest. Session (String :!: Int :!: (Int -> Int) :!: rest) rest () simple = do put "hello" put 1 put (\x -> x + 1) useSimple :: forall rest. Session (String :?: Int :?: (Int -> Int) :?: rest) rest String useSimple = do string <- get int <- get func <- get return (string ++ show (int * 4) ++ show (func 10)) result :: String result = snd $ connects simple useSimple -- result = "hello411" ___ 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] Coroutines
On Thu, Dec 18, 2008 at 2:00 AM, Nicolas Pouillard wrote: > I don't see why one would need session types, channels... to express that. > I maybe need a more complicated coroutines (ruby) example that would require > using this system. OK, how would you type these routines in Haskell? def simple yield "hello" yield 1 yield (lambda { |x| x + 1 }) end def useSimple state = 0 result = nil simple { |x| if (state == 0) then result = x else if (state == 1) then result += (x * 4).toString else if (state == 2) then result += x.call(10).toString state = state + 1 } result end I know it's a bit contrived, but you get the idea. In Haskell using Control.Coroutine: simple :: forall rest. Session (String :!: Int :!: (Int -> Int) :!: rest) rest () simple = do put "hello" put 1 put (\x -> x + 1) useSimple :: forall rest. Session (String :?: Int :?: (Int -> Int) :?: rest) rest String useSimple = do string <- get int <- get func <- get return (string ++ show (int * 4) ++ show (func 10)) result :: String result = snd $ connects simple useSimple -- result = "hello411" ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: excessive usage of CPU by threadDelay in GHCi
Jeremy Shaw wrote: I have the following simple program: import Control.Concurrent main = threadDelay (10^6) >> main If I run it in GHCi it requires 2-5% of my CPU. If i compile it, it takes 0% of my CPU. It does not matter if I compile -O0, -O2, -threaded, it always uses 0% (which is good). Is it expected that threadDelay should be really expensive in GHCi? Am I doing something wrong? Or should I file a bug? Please file a bug. It could be that the idle time GC is running repeatedly rather than just once, or something like that. Cheers, Simon ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] lengthOP rewrite rules
2008/12/18 Luke Palmer : > On Thu, Dec 18, 2008 at 1:53 AM, Cetin Sert wrote: >> >> Hi, >> >> I tested the following, why does the rewrite rules not fire when using >> tuples also in testRewrite2, testRewriteReverse2? > >> testRewrite2 :: a → (Bool,Bool) >> testRewrite2 x = (pf,pi) >> where >> f = replicate 2000 x >> i = repeat x >> lf = length f >> li = length i >> pf = lf > 300 >> pi = li > 300 >> > > Why would you expect it to? The compiler is free to inline lf and li to > discover that the rule applies, but it is also free not to. Applying all > applicable rules while maintaining the ability to abstract is undecidable > (big surprise). Thus the dependency on compiler cleverness I mentioned... I'm agreeing with Luke here. It's possible that the compiler decided to inline f and i, and length, and determined that lf == 2000 and li == _|_ Or it could have decided not to inline at all. Or some other possibility. If you specify {-# INLINE lf #-}, do the results change? I suspect they might. -- ryan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Coroutines
Andrew was recently asking about co-routines. A couple of years ago, I was in much the same position as him; although I am pretty sure I had heard the term before, it seemed like a mysterious idea with no practical use. Then I learned Ruby. Ruby makes extensive use of coroutines; it's not uncommon to have three or more coroutines executing cooperatively, made simple by how easy it is to pass blocks of code around in that language. The entire collection iteration system in Ruby is based on coroutines; if an object implements "each", it can be iterated over: [1, 2, 3].each { |x| print x } Implementing "each" for a container is generally simple; you just write a loop and call "yield" def each [1 .. length].each { |index| yield self[index] } end It surprised me how simple and powerful this concept was; code that previously was incredibly ugly to write became simple. I think this abstraction is one of the big reasons for Ruby's current success. At the Haskell Symposium this year, Jesse Tov gave a talk about Session Types in Haskell, and it struck me that they are ideal for implementing coroutines in a type-safe manner. Here you can write pure functions that represent a communicating routines, and guarantee that the communication completes successfully (assuming the routines terminate, of course). Consider these two values: f1 :: Int -> (Char, ()) f2 :: (Int, Char -> String) You can see a natural way to connect them, using the duality of (a, _) and (a -> _): connect_f1f2 :: ((), String) connect_f1f2 = let (arg1, k2) = f2 (arg2, result1) = f1 arg1 result2 = k2 arg2 in (result1, result2) I implemented this idea, along with a nice syntax for these coroutines, in http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Coroutine-0.1.0.0: f1 :: InSession (Int :?: Char :!: Eps) () f1 = runSession $ do x <- get put (head $ show x) return () f2 :: InSession (Int :!: Char :?: Eps) String f2 = runSession $ do put 6 result <- get return ("the answer is " ++ [result]) (Caveat: while this uses the do-notation, it's not *exactly* a monad; it's something more general than that. See Control.Monad.Indexed for the details. Thanks to the GHC team for NoImplicitPrelude!) You can then add choice, looping constructs, etc., to allow increasingly complicated protocols: peer1 :: InSession ((Int :?: Int :!: Eps) :?* Eps) Int -- read an Int, then write an Int, any number of times we are told to do so -- then return an Int peer2 :: InSession ((Int :!: Int :?: Eps) :!* Eps) [Int] -- write an Int, then read an Int, any number of times we want -- then return a list of Ints. The neat thing about this library is that the communication is completely pure! No side effects required! ghci> :t connect peer1 peer2 connect peer1 peer2 :: (Int, [Int]) -- ryan On Wed, Dec 17, 2008 at 6:54 PM, Richard O'Keefe wrote: > On 18 Dec 2008, at 11:26 am, Andrew Coppin wrote: >>> >>> (Also, "coroutines"? Seriously? That's hardly an obscure term in >>> programming circles.) >>> >> >> Well now, I'm curios. I've been writing computer programs since I was 9 >> years old. I hold a diploma *and* an honours degree in computer science. And >> I have never even *heard* of a coroutine. To this day I still don't know >> what it means. I rather suspect I'm not the only "programmer" on earth who >> finds themselves in this position. ;-) > > Shame on you for not reading Knuth's > "The Art of Computer Programming", Volume 1, "Fundamental Algorithms". > The then available three volumes of TAOCP > "were named among the best twelve physical-science monographs > of the century by American Scientist" "at the end of 1999". > (Fasicles 0, 2, 3, and 4 of volume 4 are now available, and > parts of fasicle 1 are on-line. Hooray hooray!) > > Quoting the first two paragraphs of the Wikipedia entry: > "In computer science, coroutines are program components that generalize > subroutines to allow multiple entry points for suspending and resuming of > execution at certain locations. Coroutines are well-suited for implementing > more familiar program components such as cooperative tasks, iterators, > infinite lists and pipes. > The term "coroutine" was originated by Melvin Conway in his seminal 1963 > paper.[1]" > > So "coroutine" has been standard hacker-type programming terminology > since 1963. I was able to use coroutines in Burroughs Extended Algol > (designed in the mid to late 60s), Simula 67, and Interlisp-D (80s). > Current languages supporting them include (thanks, Wikipedia) Lua, > Limbo, JavaScript, Python, and Ruby. Since anything with continuations > can do coroutines, we add Scheme and SML/NJ. Sather's iterators may be > a more familiar form of coroutine. You will commonly find something > like a "yield e" statement that reports the value of e to the caller > without actually returning, and "resume c" that resumes a coroutine > to get the next value. > > > _
Re: [Haskell-cafe] How to choose an arbitrary Arbitrary?
On Wed, Dec 17, 2008 at 11:05 PM, Ryan Ingram wrote: > ...It's possible to extend this idea and generate an "arbitrary arbitrary"... Thanks for your thorough answer. I like the SomeArbitrary idea. I see it's easy to also sample[1] SomeArbitrary. You do need to add a 'Show' constraint to the existential 'a' in SomeArbitrary. samplesSomeArbitrary :: IO () samplesSomeArbitrary = mapM_ f =<< sample' arbitrary where f (SomeArbitrary a) = sample (arbitrary `asTypeOf` gen a) where gen :: a -> Gen a gen _ = undefined Thanks, Bas [1] sample: http://hackage.haskell.org/packages/archive/QuickCheck/2.1.0.1/doc/html/Test-QuickCheck.html#v%3Asample ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] lengthOP rewrite rules
On Thu, Dec 18, 2008 at 1:53 AM, Cetin Sert wrote: > > Hi, > > I tested the following, why does the rewrite rules not fire when using tuples also in testRewrite2, testRewriteReverse2? testRewrite2 :: a → (Bool,Bool) > testRewrite2 x = (pf,pi) > where > f = replicate 2000 x > i = repeat x > lf = length f > li = length i > pf = lf > 300 > pi = li > 300 > > Why would you expect it to? The compiler is free to inline lf and li to discover that the rule applies, but it is also free not to. Applying all applicable rules while maintaining the ability to abstract is undecidable (big surprise). Thus the dependency on compiler cleverness I mentioned... There might be something you can do with rule ordering, make sure it happens after the inlining phase, but I don't know how to do that offhand. Luke ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] lengthOP rewrite rules
oh, btw I am using GHC 6.10.1 (on Linux x86_64) 2008/12/18 Cetin Sert > Hi, > > I tested the following, why does the rewrite rules not fire when using > tuples also in testRewrite2, testRewriteReverse2? compiling: rm *.o; ghc > -fglasgow-exts -ddump-simpl-stats -O9 --make rules.hs > > module Main where > > main :: IO () > main = do > print $ test0 > print $ test2 0 > print $ testRewrite 0 > print $ testRewriteReverse 0 > print $ testRewrite20 > print $ testRewriteReverse2 0 > > test :: a → Bool > test x = pi > where > f = replicate 2000 x > i = repeat x > pf = lenGT f 300 > pi = lenGT i 300 > > test2 :: a → (Bool,Bool) > test2 x = (pf,pi) > where > f = replicate 2000 x > i = repeat x > pf = lenGT f 300 > pi = lenGT i 300 > > testRewrite :: a → Bool > testRewrite x = pi > where > f = replicate 2000 x > i = repeat x > lf = length f > li = length i > pf = lf > 300 > pi = li > 300 > > testRewriteReverse :: a → Bool > testRewriteReverse x = pi > where > f = replicate 2000 x > i = repeat x > lf = length f > li = length i > pf = 300 <= lf > pi = 300 <= li > > testRewrite2 :: a → (Bool,Bool) > testRewrite2 x = (pf,pi) > where > f = replicate 2000 x > i = repeat x > lf = length f > li = length i > pf = lf > 300 > pi = li > 300 > > testRewriteReverse2 :: a → (Bool,Bool) > testRewriteReverse2 x = (pf,pi) > where > f = replicate 2000 x > i = repeat x > lf = length f > li = length i > pf = 300 <= lf > pi = 300 <= li > > > lengthOP :: (Num a, Ord a) ⇒ Bool → (a → a → Bool) → [b] → a → Bool > lengthOP v (⊜) [] n = 0 ⊜ n > lengthOP v (⊜) xxs n = co xxs 0 > where > co (_:xs) c | n > c = co xs (c+1) > | otherwise = v > co [] c = c ⊜ n > > lenEQ = lengthOP False (==) > lenLT = lengthOP False (<) > lenLE = lengthOP False (<=) > lenGT = lengthOP True (>) > lenGE = lengthOP True (>=) > > {-# RULES > -- | length > "lenEQ_LHS" forall xs n. (length xs) == n = lenEQ xs n > "lenLT_LHS" forall xs n. (length xs) < n = lenLT xs n > "lenLE_LHS" forall xs n. (length xs) <= n = lenLE xs n > "lenGT_LHS" forall xs n. (length xs) > n = lenGT xs n > "lenGE_LHS" forall xs n. (length xs) >= n = lenGE xs n > > "lenEQ_RHS" forall xs n. n == (length xs) = lenEQ xs n > "lenLT_RHS" forall xs n. n < (length xs) = lenGE xs n > "lenLE_RHS" forall xs n. n <= (length xs) = lenGT xs n > "lenGT_RHS" forall xs n. n > (length xs) = lenLE xs n > "lenGE_RHS" forall xs n. n >= (length xs) = lenLT xs n > #-} > > Best Regards, > Cetin Sert > > 2008/12/18 Luke Palmer > >> This does not answer your question, but you can solve this problem without >> rewrite rules by having length return a lazy natural: >> >> >>data Nat = Zero | Succ Nat >> >> And defining lazy comparison operators on it. >> >> Of course you cannot replace usages of Prelude.length. But I am really >> not in favor of rules which change semantics, even if they only make things >> less strict. My argument is the following. I may come to rely on such >> nonstrictness as in: >> >> bad xs = (length xs > 10, length xs > 20) >> >> bad [1..] will return (True,True). However, if I do an obviously >> semantics-preserving refactor: >> >> bad xs = (l > 10, l > 20) >> where >> l = length xs >> >> My semantics are not preserved: bad [1..] = (_|_, _|_) (if/unless the >> compiler is clever, in which case my semantics depend on the compiler's >> cleverness which is even worse) >> >> Luke >> >> 2008/12/18 Cetin Sert >> >>> Hi *^o^*, >>> >>> With the following rewrite rules: >>> >>> lengthOP :: (Num a, Ord a) ⇒ Bool → (a → a → Bool) → [b] → a → Bool >>> lengthOP v (⊜) [] n = 0 ⊜ n >>> lengthOP v (⊜) xxs n = co xxs 0 >>> where >>> co [] c = c ⊜ n >>> co (_:xs) c | n > c = co xs (c+1) >>> | otherwise = v >>> >>> lenEQ = lengthOP False (==) >>> lenLT = lengthOP False (<) >>> lenLE = lengthOP False (<=) >>> lenGT = lengthOP True (>) >>> lenGE = lengthOP True (>=) >>> >>> {-# RULES >>> -- | length >>> "lenEQ_LHS" forall xs n. (length xs) == n = lenEQ xs n >>> "lenLT_LHS" forall xs n. (length xs) < n = lenLT xs n >>> "lenLE_LHS" forall xs n. (length xs) <= n = lenLE xs n >>> "lenGT_LHS" forall xs n. (length xs) > n = lenGT xs n >>> "lenGE_LHS" forall xs n. (length xs) >= n = lenGE xs n >>> >>> "lenEQ_RHS" forall xs n. n == (length xs) = lenEQ xs n >>> "lenLT_RHS" forall xs n. n < (length xs) = lenGE xs n >>> "lenLE_RHS" forall xs n. n <= (length xs) = lenGT xs n >>> "lenGT_RHS" forall xs n. n > (length xs) = lenLE xs n >>> "lenGE_RHS" forall xs n. n >= (length xs) = lenLT xs n >>> >>> -- | genericLength >>> "glenEQ_LHS" forall xs n. (genericLength xs) == n = lenEQ xs n >>> "glenLT_LHS" forall xs n. (genericLength xs) < n = lenLT xs n >>> "glen
Re: [Haskell-cafe] Re: Time for a new logo?
Hi >> Might be interesting to try angling the ends of the stems to look >> something more like the guillemot in [1]. I might try this in Gimp but >> I'm no designer :P > > If you're on Linux or similar, I recommend Inkscape for this kind of > thing. If you're on Windows, Inkscape also works well for most graphics tasks (unless you bought a copy of Xara X, in which case use that unless you want SVG output) Thanks Neil ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Time for a new logo?
George Pollard writes: > Might be interesting to try angling the ends of the stems to look > something more like the guillemot in [1]. I might try this in Gimp but > I'm no designer :P If you're on Linux or similar, I recommend Inkscape for this kind of thing. -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] lengthOP rewrite rules
Hi, I tested the following, why does the rewrite rules not fire when using tuples also in testRewrite2, testRewriteReverse2? compiling: rm *.o; ghc -fglasgow-exts -ddump-simpl-stats -O9 --make rules.hs module Main where main :: IO () main = do print $ test0 print $ test2 0 print $ testRewrite 0 print $ testRewriteReverse 0 print $ testRewrite20 print $ testRewriteReverse2 0 test :: a → Bool test x = pi where f = replicate 2000 x i = repeat x pf = lenGT f 300 pi = lenGT i 300 test2 :: a → (Bool,Bool) test2 x = (pf,pi) where f = replicate 2000 x i = repeat x pf = lenGT f 300 pi = lenGT i 300 testRewrite :: a → Bool testRewrite x = pi where f = replicate 2000 x i = repeat x lf = length f li = length i pf = lf > 300 pi = li > 300 testRewriteReverse :: a → Bool testRewriteReverse x = pi where f = replicate 2000 x i = repeat x lf = length f li = length i pf = 300 <= lf pi = 300 <= li testRewrite2 :: a → (Bool,Bool) testRewrite2 x = (pf,pi) where f = replicate 2000 x i = repeat x lf = length f li = length i pf = lf > 300 pi = li > 300 testRewriteReverse2 :: a → (Bool,Bool) testRewriteReverse2 x = (pf,pi) where f = replicate 2000 x i = repeat x lf = length f li = length i pf = 300 <= lf pi = 300 <= li lengthOP :: (Num a, Ord a) ⇒ Bool → (a → a → Bool) → [b] → a → Bool lengthOP v (⊜) [] n = 0 ⊜ n lengthOP v (⊜) xxs n = co xxs 0 where co (_:xs) c | n > c = co xs (c+1) | otherwise = v co [] c = c ⊜ n lenEQ = lengthOP False (==) lenLT = lengthOP False (<) lenLE = lengthOP False (<=) lenGT = lengthOP True (>) lenGE = lengthOP True (>=) {-# RULES -- | length "lenEQ_LHS" forall xs n. (length xs) == n = lenEQ xs n "lenLT_LHS" forall xs n. (length xs) < n = lenLT xs n "lenLE_LHS" forall xs n. (length xs) <= n = lenLE xs n "lenGT_LHS" forall xs n. (length xs) > n = lenGT xs n "lenGE_LHS" forall xs n. (length xs) >= n = lenGE xs n "lenEQ_RHS" forall xs n. n == (length xs) = lenEQ xs n "lenLT_RHS" forall xs n. n < (length xs) = lenGE xs n "lenLE_RHS" forall xs n. n <= (length xs) = lenGT xs n "lenGT_RHS" forall xs n. n > (length xs) = lenLE xs n "lenGE_RHS" forall xs n. n >= (length xs) = lenLT xs n #-} Best Regards, Cetin Sert 2008/12/18 Luke Palmer > This does not answer your question, but you can solve this problem without > rewrite rules by having length return a lazy natural: > >data Nat = Zero | Succ Nat > > And defining lazy comparison operators on it. > > Of course you cannot replace usages of Prelude.length. But I am really not > in favor of rules which change semantics, even if they only make things less > strict. My argument is the following. I may come to rely on such > nonstrictness as in: > > bad xs = (length xs > 10, length xs > 20) > > bad [1..] will return (True,True). However, if I do an obviously > semantics-preserving refactor: > > bad xs = (l > 10, l > 20) > where > l = length xs > > My semantics are not preserved: bad [1..] = (_|_, _|_) (if/unless the > compiler is clever, in which case my semantics depend on the compiler's > cleverness which is even worse) > > Luke > > 2008/12/18 Cetin Sert > >> Hi *^o^*, >> >> With the following rewrite rules: >> >> lengthOP :: (Num a, Ord a) ⇒ Bool → (a → a → Bool) → [b] → a → Bool >> lengthOP v (⊜) [] n = 0 ⊜ n >> lengthOP v (⊜) xxs n = co xxs 0 >> where >> co [] c = c ⊜ n >> co (_:xs) c | n > c = co xs (c+1) >> | otherwise = v >> >> lenEQ = lengthOP False (==) >> lenLT = lengthOP False (<) >> lenLE = lengthOP False (<=) >> lenGT = lengthOP True (>) >> lenGE = lengthOP True (>=) >> >> {-# RULES >> -- | length >> "lenEQ_LHS" forall xs n. (length xs) == n = lenEQ xs n >> "lenLT_LHS" forall xs n. (length xs) < n = lenLT xs n >> "lenLE_LHS" forall xs n. (length xs) <= n = lenLE xs n >> "lenGT_LHS" forall xs n. (length xs) > n = lenGT xs n >> "lenGE_LHS" forall xs n. (length xs) >= n = lenGE xs n >> >> "lenEQ_RHS" forall xs n. n == (length xs) = lenEQ xs n >> "lenLT_RHS" forall xs n. n < (length xs) = lenGE xs n >> "lenLE_RHS" forall xs n. n <= (length xs) = lenGT xs n >> "lenGT_RHS" forall xs n. n > (length xs) = lenLE xs n >> "lenGE_RHS" forall xs n. n >= (length xs) = lenLT xs n >> >> -- | genericLength >> "glenEQ_LHS" forall xs n. (genericLength xs) == n = lenEQ xs n >> "glenLT_LHS" forall xs n. (genericLength xs) < n = lenLT xs n >> "glenLE_LHS" forall xs n. (genericLength xs) <= n = lenLE xs n >> "glenGT_LHS" forall xs n. (genericLength xs) > n = lenGT xs n >> "glenGE_LHS" forall xs n. (genericLength xs) >= n = lenGE xs n >> >> "glenEQ_RHS" forall xs n. n == (genericLength xs) = lenEQ xs n >> "glenLT_RHS" forall xs n. n < (genericLength xs) = lenGE xs n >> "glenLE_
Re: [Haskell-cafe] lengthOP rewrite rules
This does not answer your question, but you can solve this problem without rewrite rules by having length return a lazy natural: data Nat = Zero | Succ Nat And defining lazy comparison operators on it. Of course you cannot replace usages of Prelude.length. But I am really not in favor of rules which change semantics, even if they only make things less strict. My argument is the following. I may come to rely on such nonstrictness as in: bad xs = (length xs > 10, length xs > 20) bad [1..] will return (True,True). However, if I do an obviously semantics-preserving refactor: bad xs = (l > 10, l > 20) where l = length xs My semantics are not preserved: bad [1..] = (_|_, _|_) (if/unless the compiler is clever, in which case my semantics depend on the compiler's cleverness which is even worse) Luke 2008/12/18 Cetin Sert > Hi *^o^*, > > With the following rewrite rules: > > lengthOP :: (Num a, Ord a) ⇒ Bool → (a → a → Bool) → [b] → a → Bool > lengthOP v (⊜) [] n = 0 ⊜ n > lengthOP v (⊜) xxs n = co xxs 0 > where > co [] c = c ⊜ n > co (_:xs) c | n > c = co xs (c+1) > | otherwise = v > > lenEQ = lengthOP False (==) > lenLT = lengthOP False (<) > lenLE = lengthOP False (<=) > lenGT = lengthOP True (>) > lenGE = lengthOP True (>=) > > {-# RULES > -- | length > "lenEQ_LHS" forall xs n. (length xs) == n = lenEQ xs n > "lenLT_LHS" forall xs n. (length xs) < n = lenLT xs n > "lenLE_LHS" forall xs n. (length xs) <= n = lenLE xs n > "lenGT_LHS" forall xs n. (length xs) > n = lenGT xs n > "lenGE_LHS" forall xs n. (length xs) >= n = lenGE xs n > > "lenEQ_RHS" forall xs n. n == (length xs) = lenEQ xs n > "lenLT_RHS" forall xs n. n < (length xs) = lenGE xs n > "lenLE_RHS" forall xs n. n <= (length xs) = lenGT xs n > "lenGT_RHS" forall xs n. n > (length xs) = lenLE xs n > "lenGE_RHS" forall xs n. n >= (length xs) = lenLT xs n > > -- | genericLength > "glenEQ_LHS" forall xs n. (genericLength xs) == n = lenEQ xs n > "glenLT_LHS" forall xs n. (genericLength xs) < n = lenLT xs n > "glenLE_LHS" forall xs n. (genericLength xs) <= n = lenLE xs n > "glenGT_LHS" forall xs n. (genericLength xs) > n = lenGT xs n > "glenGE_LHS" forall xs n. (genericLength xs) >= n = lenGE xs n > > "glenEQ_RHS" forall xs n. n == (genericLength xs) = lenEQ xs n > "glenLT_RHS" forall xs n. n < (genericLength xs) = lenGE xs n > "glenLE_RHS" forall xs n. n <= (genericLength xs) = lenGT xs n > "glenGT_RHS" forall xs n. n > (genericLength xs) = lenLE xs n > "glenGE_RHS" forall xs n. n >= (genericLength xs) = lenLT xs n > #-} > > 1) Is there a way to tell where 'length' is mentioned, what is meant is for > example 'Prelude.length' or any length that works on lists? > 2) How can I avoid the following error messages? > > module Main where > import Data.List > main :: IO Int > print $ length (repeat 0) > 200 > print $ 200 < length (repeat 0) > print $ genericLength (repeat 0) > 200 -- error > print $ 200 < genericLength (repeat 0) -- error > return 0 > > : > Could not deduce (Ord i) from the context (Eq i, Num i) > arising from a use of `lenEQ' at > Possible fix: add (Ord i) to the context of the RULE "glenEQ_LHS" > In the expression: lenEQ xs n > When checking the transformation rule "glenEQ_LHS" > > : > Could not deduce (Ord a) from the context (Eq a, Num a) > arising from a use of `lenEQ' at > Possible fix: add (Ord a) to the context of the RULE "glenEQ_RHS" > In the expression: lenEQ xs n > When checking the transformation rule "glenEQ_RHS" > > 3) What speaks for/against broad usage of such rewrite rules involving list > lengths? > > Best Regards, > Cetin Sert > > ___ > 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