From jeffbrown.the at gmail.com Tue Dec 1 02:18:29 2015 From: jeffbrown.the at gmail.com (Jeffrey Brown) Date: Mon, 30 Nov 2015 18:18:29 -0800 Subject: [Haskell-cafe] Monadic function fails as Nothing in Maybe context but as Exception in Either context. In-Reply-To: References: <39EA7BFC-BD56-482F-8747-380B0C0BD9AC@iki.fi> Message-ID: Oleg's suggestion works! I just had to add these two lines in order to use it: {-# LANGUAGE FlexibleContexts #-} import Control.Monad.Except -- mtl library Thanks, everybody! On Mon, Nov 30, 2015 at 2:38 PM, Oleg Grenrus wrote: > > On 01 Dec 2015, at 00:34, Oleg Grenrus wrote: > > Hi, Jeffrey > > in short: `fail` of `Either e` throws an exception (i.e. is not overriden, > default implementation is `fail s = error s`) [1, 2] > > For `Maybe`, fail is defined as `fail _ = Nothing`; which is good default. > [3] > > You probably want to use for example `throwError from `mtl` package [4]: > > > I haven?t still tested it, but less wrong context is `MonadError String m`: > > gelemM :: (MonadError String m) => MyGraph -> Node -> m () > gelemM g n = if gelem n g -- FGL's gelem function returns > then return () -- True if the node is in the > graph > else throwError "Node not in Graph" -- False otherwise > > > [1] > https://hackage.haskell.org/package/base-4.8.1.0/docs/src/Data.Either.html#line-137 > [2] > https://hackage.haskell.org/package/base-4.8.1.0/docs/src/GHC.Base.html#Monad > [3] > https://hackage.haskell.org/package/base-4.8.1.0/docs/src/GHC.Base.html#line-642 > [4] > http://hackage.haskell.org/package/mtl-2.2.1/docs/Control-Monad-Except.html#v:throwError > > - Oleg > > On 01 Dec 2015, at 00:25, Jeffrey Brown wrote: > > I've written a monadic function which in a Maybe context produces a > Nothing when it fails (as intended), but in an Either context produces an > Exception rather than a Left. > > Here's a tiny demonstration. "tinyGraph" below has one Node, 0, with the > label "dog". If I try to change the label at Node 0 to "cat", it works. If > I try to change the label at Node 1 to "cat", it fails, because Node 1 is > not in the graph. > > type MyGraph = Gr String String > > tinyGraph = mkGraph [(0, "dog")] [] :: MyGraph > > maybeSucceed = replaceStringAtNodeM tinyGraph 0 "cat" :: Maybe MyGraph > -- == Just (mkGraph [(0,"cat")] []) > maybeFail = replaceStringAtNodeM tinyGraph 1 "cat" :: Maybe MyGraph > -- == Nothing > > eitherSucceed = replaceStringAtNodeM tinyGraph 0 "cat" :: Either > String MyGraph > -- == Right (mkGraph [(0,"cat")] []) > eitherFail = replaceStringAtNodeM tinyGraph 1 "cat" :: Either String > MyGraph > -- *** Exception: Node not in Graph > > Here's the code: > > import Data.Graph.Inductive -- FGL, the Functional Graph Library > > gelemM :: (Monad m) => MyGraph -> Node -> m () > gelemM g n = if gelem n g -- FGL's gelem function returns > then return () -- True if the node is in the graph > else fail "Node not in Graph" -- False otherwise > > replaceStringAtNode :: MyGraph -> Node -> String -> MyGraph > replaceStringAtNode g n e = let (Just (a,b,c,d),g') = match n g > in (a,b,e,d) & g' > > replaceStringAtNodeM :: (Monad m) => MyGraph -> Node -> String -> m > MyGraph > replaceStringAtNodeM g n s = do > gelemM g n > return $ replaceStringAtNode g n s > -- if evaluated, the pattern match in replaceStringAtNode must > succeed, > -- because gelemM catches the case where n is not in the graph > > [1] > https://github.com/JeffreyBenjaminBrown/digraphs-with-text/blob/master/test/monad_fail_problems.hs > > > -- > Jeffrey Benjamin Brown > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > -- Jeffrey Benjamin Brown -------------- next part -------------- An HTML attachment was scrubbed... URL: From mike at barrucadu.co.uk Tue Dec 1 05:57:09 2015 From: mike at barrucadu.co.uk (Michael Walker) Date: Tue, 1 Dec 2015 05:57:09 +0000 Subject: [Haskell-cafe] [ANN] dejafu-0.2.0.0: Overloadable primitives for testable, potentially non-deterministic, concurrency. Message-ID: <20151201055709.3f07ee25@barrucadu.co.uk> Hi cafe, I am happy to announce a new release of D?j? Fu, my library for testing concurrent Haskell programs! Things have advanced significantly since the paper I presented at the Haskell Symposium this year, both in terms of performance and functionality. Git: https://github.com/barrucadu/dejafu Hackage: https://hackage.haskell.org/package/dejafu-0.2.0.0 ## What is it? D?j? Fu is a library for developing and testing concurrent Haskell programs, it provides a typeclass-abstraction over GHC's regular concurrency API, allowing the concrete implementation to be swapped out. Why do we need this? Well, concurrency is really hard to get right. Empirical studies have found that many real-world concurrency bugs can be exhibited with small test cases using as few as two threads: so it?s not just big concurrent programs that are hard, small ones are too. We as programmers just don?t seem to have a very good intuition for traditional threads-and-shared-memory-style concurrency. The typical approach to testing concurrent programs is to just run them lots of times, but that doesn?t provide any hard coverage guarantees, and then we need to wonder: how many runs do we need? Fortunately, there has been a lot of research into testing concurrency in the past several years. Systematic concurrency testing is an approach where the source of nondeterminism, the actual scheduler, is swapped out for one under the control of the testing framework. This allows possible schedules to be systematically explored, giving real coverage guarantees for our tests. This is a library implementing systematic concurrency testing. It provides two typeclasses, MonadConc to abstract over much of Control.Concurrent and related modules, and MonadSTM, to similarly abstract over Control.Monad.STM. For examples, see the test suite and the async-dejafu source: - https://github.com/barrucadu/dejafu/tree/master/dejafu-tests - https://github.com/barrucadu/dejafu/tree/master/async-dejafu If you want to read more: - Recent technical report: http://misc.barrucadu.co.uk/pub/dejafu-techreport.pdf - Haskell Symposium paper about version 0.1.0.0: http://www.barrucadu.co.uk/publications/dejafu-hs15.pdf - A slew of things on my blog: http://www.barrucadu.co.uk/posts.html ## Changelog New stuff: - Relaxed memory: CRefs now behave just like IORefs, and testing can use one of three different memory models: sequential consistency, total store order (the default), and partial store order. - Support for 'yield'. - Integration with HUnit and tasty: https://hackage.haskell.org/package/hunit-dejafu https://hackage.haskell.org/package/tasty-dejafu - Version of the async library reimplemented to use MonadConc: https://hackage.haskell.org/package/async-dejafu - Fair bounding: which allows yield-based constructs like spinlocks to be tested without causing infinitely-long executions. - Length bounding: which allows for potentially non-terminating computations to be tested. Improvements: - Now uses partial-order reduction to cut down on the number of schedules to try, which is a *huge* improvement over just pre-emption bounding, which is what 0.1.0.0 did. - The 'autocheck' function has prettier output. ## How to use it: If you?re not making use of any IO in your code other than for concurrency, the transition to using MonadConc and MonadSTM will probably just be a textual substitution: - IO is replaced with MonadConc m => m - STM with MonadSTM m => m - *IORef with *CRef - *MVar with *CVar - *TVar with *CTVar - Most other things have the same name, and so can be replaced by just swapping imports around. If you are using other IO, you will need a gentle sprinkling of MonadIO and liftIO in your code as well. ## Is this really just a drop-in replacement for IO/STM? That?s the idea, yes. More specifically, the IO instance of MonadConc and the STM instance of MonadSTM just use the regular IO and STM functions, and so should have no noticeable change in behaviour. There are some differences which can lead to incorrect results when testing, but which should not affect code when used in an IO or STM context. Specifically: Control.Monad.Conc.Class.getNumCapabilities can lie to encourage more concurrency when testing; and Control.Exception.catch can catch exceptions from pure code, but Control.Monad.Conc.Class.catch can?t (except for the IO instance). -- Michael Walker (http://www.barrucadu.co.uk) -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 473 bytes Desc: OpenPGP digital signature URL: From gracjanpolak at gmail.com Tue Dec 1 09:02:56 2015 From: gracjanpolak at gmail.com (Gracjan Polak) Date: Tue, 1 Dec 2015 10:02:56 +0100 Subject: [Haskell-cafe] Month in Haskell Mode November 2015 Message-ID: Welcome Haskell Mode users, Haskell Mode progress report for November 2015 (online version ). For previous issue see October 2015 . Go to Reddit discussion . What is Haskell Mode? Haskell Mode is an umbrella project for multiple Emacs tools for efficient Haskell development. Haskell Mode is an open source project developed by a group of volunteers. For more information see https://github.com/haskell/haskell-mode. Important developments The bug that everybody was waiting for was fixed! No more 'Illegal token' in indentation. Rejoice! Coming release In the beginning of December we plan to tag new stable release of haskell-mode with current state of the repo (plus possible bugfixes). Competitive projects Haskell editor landscape is growing and there are compelling propositions all over the place: - Atom IDE-Haskell - Haskell Vim IDE - Leksah - Haskell IDE in Haskell - Haskell for Mac There is an idea turning into reality that there should be a common infrastructure powering all of the above. It is brewing in Haskell IDE Engine repo. Cruft removal, reminder Last month we declared that we plan to remove some cruft. Note that SCC functions got salvaged and now they are fully functional part of haskell-mode! Killing list for December: - Remove haskell-bot.el - Remove horizontal whitespace based smart indentation mode haskell-simple-indent - Remove Unicode input method - Remove haskell-checkers.el Current project focus Current project focus is to lower entry barrier for newcomers by defining bite-sized tasks. Get 50 'well-defined-tasks' done as by the metric: https://github.com/haskell/haskell-mode/issues?q=is%3Aissue+label%3Awell-defined-task+is%3Aclosed A 'well-defined-task' is a category of tasks that have the field cleared for them, questions already sorted out and detailed information how to get them done. So you can just sit, search for 'well-defined-task' label and enjoy the coding! The point is to lower the entry barrier for new users, new issue reporters and advanced programmers but Emacs lisp beginners to contribute to the project. Current status: 14 well-defined-tasks closed plus 13 more open . If only you can help with reaching our targets please do so! Issues closed in November - Repl hanging #447 - On opening a file, haskell-doc opens several files defined in import section #742 - Indentation has been spoiled #782 - Refactor load-or-reload #807 - Make import sorting/aligning optional #914 - Remove possibility of 'Illegal token' from haskell-indentation #962 - Can't edit a buffer while resolving merge conflict because Invalid Token error. #969 - C pragma and Illegal token: else #970 - Please do not make haskell-mode non-useful without ghc-mod #974 - haskell-process-load-file: cabal test-suite wants to inject deps into library #979 - Parsing failure with type-level lists #982 - Stop blocking me from typing my code #985 - haskell-process-do-type truncates types too aggressively #988 - Code duplication between haskell-process-do-type, haskell-process-insert-type #989 - Issues trying to use local version of a package in a layer #993 - Emacs haskell-mode: how to send PART of file to repl? #1002 - haskell-process-load-file error (wrong-type-argument number-or-marker-p nil) when code has an error #1004 Pull requests merged in November - Add haskell-font-lock-tests.el. #957 - [Doc] Add stack related configuration for compilation #971 - Extract hoogle/hayoo code into haskell-hoogle.el and tidy up #973 - Move some docs from wiki to manual #976 - Don't spuriously modify tags-table-list's global value #978 - Add an additional trigger for pragma suggestions #983 - Add hayoo choice as part of hoogle url. #984 - Clean up SCC code #986 - Truncate multi-line messages less aggressively #990 - Spelling #991 - Use haskell-process-load-file, not -load-or-reload #992 - Add RET, TAB and BACKTAB tests #994 - Add case for haskell-debug-parse-module regex to parse #995 - Remove duplicate filename in Makefile #996 - Remove haskell-indentation-parse-error #997 - Fix markup typo in README.md #999 - Remove haskell-indentation-parse-error, fixup #1001 - Do not sort imports twice #1003 Contributors active in November Cody Goodman, Daniel Bergey, Gabor Greif, Gracjan Polak, Moritz Kiefer, Sibi Prabakaran, Steve Purcell, Thien-Thi Nguyen Contributing Haskell Mode needs volunteers like any other open source project. For more information see: https://github.com/haskell/haskell-mode/wiki Also drop by our IRC channel: #haskell-emacs at irc.freenode.net. Thanks! -------------- next part -------------- An HTML attachment was scrubbed... URL: From chpatrick at gmail.com Tue Dec 1 12:03:12 2015 From: chpatrick at gmail.com (Patrick Chilton) Date: Tue, 1 Dec 2015 12:03:12 +0000 Subject: [Haskell-cafe] [ANN] clang-pure-0.1.0.0: Pure C++ code analysis Message-ID: Hi everyone, I've been working on a pure binding to libclang that lets you easily analyze any code that the Clang compiler understands. Github: https://github.com/chpatrick/clang-pure Hackage: http://hackage.haskell.org/package/clang-pure Haddock: http://chpatrick.github.io/clang-pure/ libclang documentation: http://clang.llvm.org/doxygen/group__CINDEX.html A short example that prints out the type of every function in a header file (very useful for binding generation): main = do idx <- createIndex tu <- parseTranslationUnit idx "foo.h" [] let root = translationUnitCursor tu funDecs = root ^.. cosmosOf cursorChildrenF . filtered (\c -> cursorKind c == FunctionDecl) . folding (\c -> fmap (\t -> ( cursorSpelling c, typeSpelling t )) (cursorType c)) for_ funDecs $ \(f, t) -> putStrLn $ BS.unpack f ++ " :: " ++ BS.unpack t Or to find the number of gotos: gotoCount = lengthOf (cosmosOf cursorChildrenF . filtered (\c -> cursorKind c == GotoStmt)) root (This uses lens, but the library itself only has one optional lens-style function). Please refer to libclang's good documentation for an explanation of the functions. The only thing to keep in mind is that functions clang_foo are renamed to just foo, functions clang_getBar are renamed to just bar, and types CXBaz are renamed to just Baz in the Haskell bindings. Under the hood, a reference counting system ensures that the C objects are freed at the right time and in the right order, which allows the public API to be simple and pure. The bindings are not yet complete, so if you find something missing please make an issue or better yet send a pull request. :) Patrick -------------- next part -------------- An HTML attachment was scrubbed... URL: From jeffbrown.the at gmail.com Tue Dec 1 18:44:11 2015 From: jeffbrown.the at gmail.com (Jeffrey Brown) Date: Tue, 1 Dec 2015 10:44:11 -0800 Subject: [Haskell-cafe] Monadic function fails as Nothing in Maybe context but as Exception in Either context. In-Reply-To: References: <39EA7BFC-BD56-482F-8747-380B0C0BD9AC@iki.fi> Message-ID: I spoke too soon; I'm seeing the same problem with MonadError. Prelude> :set -XFlexibleContexts Prelude> import Control.Monad.Except Prelude Control.Monad.Except> let f = (fail "be Left!" :: (MonadError String m) => m ()) Loading package transformers-0.4.2.0 ... linking ... done. Loading package mtl-2.2.1 ... linking ... done. Prelude Control.Monad.Except> f :: Either String () *** Exception: be Left! Prelude Control.Monad.Except> On Mon, Nov 30, 2015 at 6:18 PM, Jeffrey Brown wrote: > Oleg's suggestion works! I just had to add these two lines in order to use > it: > > {-# LANGUAGE FlexibleContexts #-} > import Control.Monad.Except -- mtl library > > Thanks, everybody! > > On Mon, Nov 30, 2015 at 2:38 PM, Oleg Grenrus wrote: > >> >> On 01 Dec 2015, at 00:34, Oleg Grenrus wrote: >> >> Hi, Jeffrey >> >> in short: `fail` of `Either e` throws an exception (i.e. is not >> overriden, default implementation is `fail s = error s`) [1, 2] >> >> For `Maybe`, fail is defined as `fail _ = Nothing`; which is good >> default. [3] >> >> You probably want to use for example `throwError from `mtl` package [4]: >> >> >> I haven?t still tested it, but less wrong context is `MonadError String >> m`: >> >> gelemM :: (MonadError String m) => MyGraph -> Node -> m () >> gelemM g n = if gelem n g -- FGL's gelem function returns >> then return () -- True if the node is in the >> graph >> else throwError "Node not in Graph" -- False otherwise >> >> >> [1] >> https://hackage.haskell.org/package/base-4.8.1.0/docs/src/Data.Either.html#line-137 >> [2] >> https://hackage.haskell.org/package/base-4.8.1.0/docs/src/GHC.Base.html#Monad >> [3] >> https://hackage.haskell.org/package/base-4.8.1.0/docs/src/GHC.Base.html#line-642 >> [4] >> http://hackage.haskell.org/package/mtl-2.2.1/docs/Control-Monad-Except.html#v:throwError >> >> - Oleg >> >> On 01 Dec 2015, at 00:25, Jeffrey Brown wrote: >> >> I've written a monadic function which in a Maybe context produces a >> Nothing when it fails (as intended), but in an Either context produces an >> Exception rather than a Left. >> >> Here's a tiny demonstration. "tinyGraph" below has one Node, 0, with the >> label "dog". If I try to change the label at Node 0 to "cat", it works. If >> I try to change the label at Node 1 to "cat", it fails, because Node 1 is >> not in the graph. >> >> type MyGraph = Gr String String >> >> tinyGraph = mkGraph [(0, "dog")] [] :: MyGraph >> >> maybeSucceed = replaceStringAtNodeM tinyGraph 0 "cat" :: Maybe MyGraph >> -- == Just (mkGraph [(0,"cat")] []) >> maybeFail = replaceStringAtNodeM tinyGraph 1 "cat" :: Maybe MyGraph >> -- == Nothing >> >> eitherSucceed = replaceStringAtNodeM tinyGraph 0 "cat" :: Either >> String MyGraph >> -- == Right (mkGraph [(0,"cat")] []) >> eitherFail = replaceStringAtNodeM tinyGraph 1 "cat" :: Either String >> MyGraph >> -- *** Exception: Node not in Graph >> >> Here's the code: >> >> import Data.Graph.Inductive -- FGL, the Functional Graph Library >> >> gelemM :: (Monad m) => MyGraph -> Node -> m () >> gelemM g n = if gelem n g -- FGL's gelem function returns >> then return () -- True if the node is in the graph >> else fail "Node not in Graph" -- False otherwise >> >> replaceStringAtNode :: MyGraph -> Node -> String -> MyGraph >> replaceStringAtNode g n e = let (Just (a,b,c,d),g') = match n g >> in (a,b,e,d) & g' >> >> replaceStringAtNodeM :: (Monad m) => MyGraph -> Node -> String -> m >> MyGraph >> replaceStringAtNodeM g n s = do >> gelemM g n >> return $ replaceStringAtNode g n s >> -- if evaluated, the pattern match in replaceStringAtNode must >> succeed, >> -- because gelemM catches the case where n is not in the graph >> >> [1] >> https://github.com/JeffreyBenjaminBrown/digraphs-with-text/blob/master/test/monad_fail_problems.hs >> >> >> -- >> Jeffrey Benjamin Brown >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> >> >> > > > -- > Jeffrey Benjamin Brown > -- Jeffrey Benjamin Brown -------------- next part -------------- An HTML attachment was scrubbed... URL: From oleg.grenrus at iki.fi Tue Dec 1 18:46:03 2015 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Tue, 1 Dec 2015 20:46:03 +0200 Subject: [Haskell-cafe] Monadic function fails as Nothing in Maybe context but as Exception in Either context. In-Reply-To: References: <39EA7BFC-BD56-482F-8747-380B0C0BD9AC@iki.fi> Message-ID: <9B9DE023-B355-4B64-860D-19BEA3EB3E53@iki.fi> Use `throwError`, not `fail`. :) Forget `fail`. Luckily we are taking it out of `Monad`. - Oleg > On 01 Dec 2015, at 20:44, Jeffrey Brown wrote: > > I spoke too soon; I'm seeing the same problem with MonadError. > > Prelude> :set -XFlexibleContexts > Prelude> import Control.Monad.Except > Prelude Control.Monad.Except> let f = (fail "be Left!" :: (MonadError String m) => m ()) > Loading package transformers-0.4.2.0 ... linking ... done. > Loading package mtl-2.2.1 ... linking ... done. > Prelude Control.Monad.Except> f :: Either String () > *** Exception: be Left! > Prelude Control.Monad.Except> > > > > On Mon, Nov 30, 2015 at 6:18 PM, Jeffrey Brown > wrote: > Oleg's suggestion works! I just had to add these two lines in order to use it: > > {-# LANGUAGE FlexibleContexts #-} > import Control.Monad.Except -- mtl library > > Thanks, everybody! > > On Mon, Nov 30, 2015 at 2:38 PM, Oleg Grenrus > wrote: > >> On 01 Dec 2015, at 00:34, Oleg Grenrus > wrote: >> >> Hi, Jeffrey >> >> in short: `fail` of `Either e` throws an exception (i.e. is not overriden, default implementation is `fail s = error s`) [1, 2] >> >> For `Maybe`, fail is defined as `fail _ = Nothing`; which is good default. [3] >> >> You probably want to use for example `throwError from `mtl` package [4]: >> > > I haven?t still tested it, but less wrong context is `MonadError String m`: > > gelemM :: (MonadError String m) => MyGraph -> Node -> m () > gelemM g n = if gelem n g -- FGL's gelem function returns > then return () -- True if the node is in the graph > else throwError "Node not in Graph" -- False otherwise >> >> [1] https://hackage.haskell.org/package/base-4.8.1.0/docs/src/Data.Either.html#line-137 >> [2] https://hackage.haskell.org/package/base-4.8.1.0/docs/src/GHC.Base.html#Monad >> [3] https://hackage.haskell.org/package/base-4.8.1.0/docs/src/GHC.Base.html#line-642 >> [4] http://hackage.haskell.org/package/mtl-2.2.1/docs/Control-Monad-Except.html#v:throwError >> >> - Oleg >> >>> On 01 Dec 2015, at 00:25, Jeffrey Brown > wrote: >>> >>> I've written a monadic function which in a Maybe context produces a Nothing when it fails (as intended), but in an Either context produces an Exception rather than a Left. >>> >>> Here's a tiny demonstration. "tinyGraph" below has one Node, 0, with the label "dog". If I try to change the label at Node 0 to "cat", it works. If I try to change the label at Node 1 to "cat", it fails, because Node 1 is not in the graph. >>> >>> type MyGraph = Gr String String >>> >>> tinyGraph = mkGraph [(0, "dog")] [] :: MyGraph >>> >>> maybeSucceed = replaceStringAtNodeM tinyGraph 0 "cat" :: Maybe MyGraph >>> -- == Just (mkGraph [(0,"cat")] []) >>> maybeFail = replaceStringAtNodeM tinyGraph 1 "cat" :: Maybe MyGraph >>> -- == Nothing >>> >>> eitherSucceed = replaceStringAtNodeM tinyGraph 0 "cat" :: Either String MyGraph >>> -- == Right (mkGraph [(0,"cat")] []) >>> eitherFail = replaceStringAtNodeM tinyGraph 1 "cat" :: Either String MyGraph >>> -- *** Exception: Node not in Graph >>> >>> Here's the code: >>> >>> import Data.Graph.Inductive -- FGL, the Functional Graph Library >>> >>> gelemM :: (Monad m) => MyGraph -> Node -> m () >>> gelemM g n = if gelem n g -- FGL's gelem function returns >>> then return () -- True if the node is in the graph >>> else fail "Node not in Graph" -- False otherwise >>> >>> replaceStringAtNode :: MyGraph -> Node -> String -> MyGraph >>> replaceStringAtNode g n e = let (Just (a,b,c,d),g') = match n g >>> in (a,b,e,d) & g' >>> >>> replaceStringAtNodeM :: (Monad m) => MyGraph -> Node -> String -> m MyGraph >>> replaceStringAtNodeM g n s = do >>> gelemM g n >>> return $ replaceStringAtNode g n s >>> -- if evaluated, the pattern match in replaceStringAtNode must succeed, >>> -- because gelemM catches the case where n is not in the graph >>> >>> [1] https://github.com/JeffreyBenjaminBrown/digraphs-with-text/blob/master/test/monad_fail_problems.hs >>> >>> >>> -- >>> Jeffrey Benjamin Brown >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > > > -- > Jeffrey Benjamin Brown > > > > -- > Jeffrey Benjamin Brown -------------- next part -------------- An HTML attachment was scrubbed... URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 842 bytes Desc: Message signed with OpenPGP using GPGMail URL: From jeffbrown.the at gmail.com Tue Dec 1 18:48:38 2015 From: jeffbrown.the at gmail.com (Jeffrey Brown) Date: Tue, 1 Dec 2015 10:48:38 -0800 Subject: [Haskell-cafe] Monadic function fails as Nothing in Maybe context but as Exception in Either context. In-Reply-To: <9B9DE023-B355-4B64-860D-19BEA3EB3E53@iki.fi> References: <39EA7BFC-BD56-482F-8747-380B0C0BD9AC@iki.fi> <9B9DE023-B355-4B64-860D-19BEA3EB3E53@iki.fi> Message-ID: Right! That's what I was doing when I got it to work and then I forgot. I will correct the habit. Sorry for the annoyance! On Tue, Dec 1, 2015 at 10:46 AM, Oleg Grenrus wrote: > Use `throwError`, not `fail`. :) > > Forget `fail`. Luckily we are taking it out of `Monad`. > > - Oleg > > > On 01 Dec 2015, at 20:44, Jeffrey Brown wrote: > > I spoke too soon; I'm seeing the same problem with MonadError. > > Prelude> :set -XFlexibleContexts > Prelude> import Control.Monad.Except > Prelude Control.Monad.Except> let f = (fail "be Left!" :: (MonadError > String m) => m ()) > Loading package transformers-0.4.2.0 ... linking ... done. > Loading package mtl-2.2.1 ... linking ... done. > Prelude Control.Monad.Except> f :: Either String () > *** Exception: be Left! > Prelude Control.Monad.Except> > > > > On Mon, Nov 30, 2015 at 6:18 PM, Jeffrey Brown > wrote: > >> Oleg's suggestion works! I just had to add these two lines in order to >> use it: >> >> {-# LANGUAGE FlexibleContexts #-} >> import Control.Monad.Except -- mtl library >> >> Thanks, everybody! >> >> On Mon, Nov 30, 2015 at 2:38 PM, Oleg Grenrus >> wrote: >> >>> >>> On 01 Dec 2015, at 00:34, Oleg Grenrus wrote: >>> >>> Hi, Jeffrey >>> >>> in short: `fail` of `Either e` throws an exception (i.e. is not >>> overriden, default implementation is `fail s = error s`) [1, 2] >>> >>> For `Maybe`, fail is defined as `fail _ = Nothing`; which is good >>> default. [3] >>> >>> You probably want to use for example `throwError from `mtl` package [4]: >>> >>> >>> I haven?t still tested it, but less wrong context is `MonadError String >>> m`: >>> >>> gelemM :: (MonadError String m) => MyGraph -> Node -> m () >>> gelemM g n = if gelem n g -- FGL's gelem function returns >>> then return () -- True if the node is in >>> the graph >>> else throwError "Node not in Graph" -- False otherwise >>> >>> >>> [1] >>> https://hackage.haskell.org/package/base-4.8.1.0/docs/src/Data.Either.html#line-137 >>> [2] >>> https://hackage.haskell.org/package/base-4.8.1.0/docs/src/GHC.Base.html#Monad >>> [3] >>> https://hackage.haskell.org/package/base-4.8.1.0/docs/src/GHC.Base.html#line-642 >>> [4] >>> http://hackage.haskell.org/package/mtl-2.2.1/docs/Control-Monad-Except.html#v:throwError >>> >>> - Oleg >>> >>> On 01 Dec 2015, at 00:25, Jeffrey Brown wrote: >>> >>> I've written a monadic function which in a Maybe context produces a >>> Nothing when it fails (as intended), but in an Either context produces an >>> Exception rather than a Left. >>> >>> Here's a tiny demonstration. "tinyGraph" below has one Node, 0, with the >>> label "dog". If I try to change the label at Node 0 to "cat", it works. If >>> I try to change the label at Node 1 to "cat", it fails, because Node 1 is >>> not in the graph. >>> >>> type MyGraph = Gr String String >>> >>> tinyGraph = mkGraph [(0, "dog")] [] :: MyGraph >>> >>> maybeSucceed = replaceStringAtNodeM tinyGraph 0 "cat" :: Maybe >>> MyGraph >>> -- == Just (mkGraph [(0,"cat")] []) >>> maybeFail = replaceStringAtNodeM tinyGraph 1 "cat" :: Maybe MyGraph >>> -- == Nothing >>> >>> eitherSucceed = replaceStringAtNodeM tinyGraph 0 "cat" :: Either >>> String MyGraph >>> -- == Right (mkGraph [(0,"cat")] []) >>> eitherFail = replaceStringAtNodeM tinyGraph 1 "cat" :: Either String >>> MyGraph >>> -- *** Exception: Node not in Graph >>> >>> Here's the code: >>> >>> import Data.Graph.Inductive -- FGL, the Functional Graph Library >>> >>> gelemM :: (Monad m) => MyGraph -> Node -> m () >>> gelemM g n = if gelem n g -- FGL's gelem function returns >>> then return () -- True if the node is in the graph >>> else fail "Node not in Graph" -- False otherwise >>> >>> replaceStringAtNode :: MyGraph -> Node -> String -> MyGraph >>> replaceStringAtNode g n e = let (Just (a,b,c,d),g') = match n g >>> in (a,b,e,d) & g' >>> >>> replaceStringAtNodeM :: (Monad m) => MyGraph -> Node -> String -> m >>> MyGraph >>> replaceStringAtNodeM g n s = do >>> gelemM g n >>> return $ replaceStringAtNode g n s >>> -- if evaluated, the pattern match in replaceStringAtNode must >>> succeed, >>> -- because gelemM catches the case where n is not in the graph >>> >>> [1] >>> https://github.com/JeffreyBenjaminBrown/digraphs-with-text/blob/master/test/monad_fail_problems.hs >>> >>> >>> -- >>> Jeffrey Benjamin Brown >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> >>> >>> >> >> >> -- >> Jeffrey Benjamin Brown >> > > > > -- > Jeffrey Benjamin Brown > > > -- Jeffrey Benjamin Brown -------------- next part -------------- An HTML attachment was scrubbed... URL: From will.yager at gmail.com Tue Dec 1 20:34:57 2015 From: will.yager at gmail.com (William Yager) Date: Tue, 1 Dec 2015 14:34:57 -0600 Subject: [Haskell-cafe] Monadic function fails as Nothing in Maybe context but as Exception in Either context. In-Reply-To: References: <39EA7BFC-BD56-482F-8747-380B0C0BD9AC@iki.fi> Message-ID: Shouldn't that be "throwError", not "fail"? --Will On Tue, Dec 1, 2015 at 12:44 PM, Jeffrey Brown wrote: > I spoke too soon; I'm seeing the same problem with MonadError. > > Prelude> :set -XFlexibleContexts > Prelude> import Control.Monad.Except > Prelude Control.Monad.Except> let f = (fail "be Left!" :: (MonadError > String m) => m ()) > Loading package transformers-0.4.2.0 ... linking ... done. > Loading package mtl-2.2.1 ... linking ... done. > Prelude Control.Monad.Except> f :: Either String () > *** Exception: be Left! > Prelude Control.Monad.Except> > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From will.yager at gmail.com Tue Dec 1 20:35:32 2015 From: will.yager at gmail.com (William Yager) Date: Tue, 1 Dec 2015 14:35:32 -0600 Subject: [Haskell-cafe] Monadic function fails as Nothing in Maybe context but as Exception in Either context. In-Reply-To: References: <39EA7BFC-BD56-482F-8747-380B0C0BD9AC@iki.fi> Message-ID: Oops, disregard that. Other responses didn't show up for some reason. On Tue, Dec 1, 2015 at 2:34 PM, William Yager wrote: > Shouldn't that be "throwError", not "fail"? > > --Will > > On Tue, Dec 1, 2015 at 12:44 PM, Jeffrey Brown > wrote: > >> I spoke too soon; I'm seeing the same problem with MonadError. >> >> Prelude> :set -XFlexibleContexts >> Prelude> import Control.Monad.Except >> Prelude Control.Monad.Except> let f = (fail "be Left!" :: (MonadError >> String m) => m ()) >> Loading package transformers-0.4.2.0 ... linking ... done. >> Loading package mtl-2.2.1 ... linking ... done. >> Prelude Control.Monad.Except> f :: Either String () >> *** Exception: be Left! >> Prelude Control.Monad.Except> >> >> >> -------------- next part -------------- An HTML attachment was scrubbed... URL: From gershomb at gmail.com Wed Dec 2 04:34:41 2015 From: gershomb at gmail.com (Gershom B) Date: Tue, 1 Dec 2015 23:34:41 -0500 Subject: [Haskell-cafe] A new case for the pointed functor class In-Reply-To: References: Message-ID: On November 29, 2015 at 11:23:24 PM, roconnor at theorem.ca (roconnor at theorem.ca) wrote: > > class Functor f => StrongSum f where? > ? ? distRight :: Either a (f b) -> f (Either a b)? > > -- Natural laws: > -- distRight . right . fmap f = fmap (right f) . distRight > -- distRight . left f = fmap (left f) . distRight > -- > -- Other laws: > -- 1. either absurd (fmap Right) = distRight :: Either Void (f a) -> f (Either Void a) > -- 2. fmap assocL . distRight . right distRight . assocR = distRight :: Either (Either > a b) (f c) -> f (Either (Either a b) c) > -- where > -- assocL :: Either a (Either b c) -> Either (Either a b) c > -- assocL (Left a) = Left (Left a) > -- assocL (Right (Left a)) = Left (Right a) > -- assocL (Right (Right a)) = Right a > -- assocR :: Either (Either a b) c -> Either a (Either b c) > -- assocR (Left (Left a)) = Left a > -- assocR (Left (Right a)) = Right (Left a) > -- assocR (Right a) = Right (Right a) This is very interesting, but I?m not exactly convinced. This is what I?ve worked out thus far: Here is a pretty minimal instance of StrongSum that fails the laws: data WithInt a = WithInt Int a deriving Show instance Functor WithInt where ? ?fmap f (WithInt no x) = WithInt no (f x) instance StrongSum WithInt where ? ? distRight (Left x) = WithInt 42 (Left x) ? ? distRight (Right (WithInt no x)) = WithInt (no + 1) (Right x) From this it becomes clear why StrongSum requires laws and fmap does not. Consider the induced Pointed instance from: pure = fmap (id ||| absurd) . distRight . Left? This completely ignores the Right case, which is where all the potential for an ?unlawful? StrongSum resides. ( i.e., in this case: distVoidRight1 = either absurd (fmap Right) distVoidRight2 = distRight distVoidRight1 (Right (WithInt 12 ?hi?)) = WithInt 12 (Right ?hi?) distVoidRight2 (Right (WithInt 12 ?hi?)) = WithInt 13 (Right ?hi?) ) In the induced StrongSum from Pointed case, the Right instance is given definitively by ?fmap Right?. The laws, as far as I can tell, just require that ?distRight . Right == fmap Right? which is what is freely generated by inducing StrongSum from Pointed. So this at core leaves us with a class with additional structure, which has Pointed as a subclass, which is a familiar story. Except here there is a twist ? we?ve added some extra laws to that class such that it corresponds precisely to the instance we can freely generate from Functor and Pointed. So posit we had a class Apply as in?https://hackage.haskell.org/package/semigroupoids-5.0.0.4/docs/Data-Functor-Apply.html#t:Apply? but did not yet have Pointed. Now we can play the same game (well, almost ? there are a few more subtleties here). A lawful Applicative could be generated by Apply and Pointed*, and every Applicative gives rise to Pointed. But if that doesn?t motivate Pointed, why should this? :-) Cheers, Gershom *The subtlety being in particular that not every Apply/Pointed combination directly gives rise to a proper Applicative. From alan.zimm at gmail.com Wed Dec 2 08:34:41 2015 From: alan.zimm at gmail.com (Alan & Kim Zimmerman) Date: Wed, 2 Dec 2015 10:34:41 +0200 Subject: [Haskell-cafe] Month (and a bit) in haskell-ide-engine November 2015 Message-ID: Welcome Haskell IDE Engine (future) users, Haskell IDE Engine progress report for November 2015. What is Haskell IDE Engine? Not an IDE. It is a common point to join together the effort of integrating tools into an IDE and the effort of writing tools for an IDE, by providing an API in the middle that each of these parties can work from and to. Important developments The first commit to this project took place on 22 October. In a little over a month we have had 290 commits, 116 PRs, and 114 issues. We have 14 contributors, 16 forks, 155 stars and 36 watchers. So it is safe to say we are actively working on the project. At this point we have an initial implementation of the architecture, which allows for different front end transport implementations to interface with the IDE. The current supported transports are JSON over stdio and JSON over HTTP. The architecture allows for other data encodings or interface protocols, so long as the hie side can read and write to TChans. We have a PluginDescriptor type which captures information about a given plugin, which is loaded into the main dispatcher in a namespace per plugin. The commands exposed by a plugin can run in synchronous or async mode, if they are long running, or must coordinate with backend infrastructure. The initial plugins under development provide access to - ghc-mod - HaRe - base plugin, allowing plugin introspection - example plugin A ghci-ng plugin is on hold pending the Remote GHCi work Simon Marlow is doing. We have initial integrations to emacs, and to leksah. Current project focus The current project focus is on getting our collective heads straight on what actually needs to be done, and to provide working integrations to at least 2 IDEs to get a better feel for what is needed. Both of these are well in hand, and if anyone would like to join in the discussion happens via the github issue tracker and docs section of the project, as well as IRC at #haskell-ide-engine on freenode. Issues closed in November - Do plugins the same way as GHC #1 - Use Idris's protocol? #3 - What would the smallest useful haskell-ide look like #4 - Loose comments from editor (emacs) perspective #5 - Name of project module hierarchy root question #9 - Proposition: setup the same label and milestones system as in stack repo #22 - The command "./travis_long stack +RTS -N2 -RTS build --test --pedantic" exited with 1 #28 - Travis build should be deterministic #30 - HIE should start web server only on demand #31 - Make all ToJSON instances clearly visible #32 - make jsonHttpListener only start via a CLI flag #33 - Add the balance of commands to the HaRe plugin #36 - Extend the dispatcher to validate commands before calling worker #37 - Decide on package name for the plugin API / plugin packages #39 - Remove Context from IdeRequest #40 - Consume invalid input #43 - Encourage stateless programming style #45 - Worker function parameter passing #54 - Bring in async processing #67 - Define Emacs menu #68 - Add references to hsimport, hlint-refactor, haskdogs, etc. #84 - struggling with ghci-ng #86 - Different behavior between launch stack exec hie and hie directly #87 - PluginDescriptor should not be serialisable #92 - Add user visible info to PluginDescriptor #98 - Consider switching back to aeson-generated json serialization? #109 Pull requests merged in November - Fix badges #15 - Add argon to Tools #17 - (RFC) [list of tools] add more tools, add links, add short descriptions, group tools #18 - fixed typo #21 - [RFC] New readme for the project #23 - Fix spelling of ?supersede? in README #24 - Fix minor typos #26 - Add Emacs process communication layer #27 - Improve wire protocol #34 - Handwrite ToJSON instances, fix #32 #35 - Introduce cmdFileExtensions for the CommandDescriptor #41 - Make web interface optional and port configurable #42 - Remove Context, simplifying IdeRequest #44 - Implement testing framework for Emacs (plus some fixes) #46 - Remove state cwd #47 - Dispatcher validation #51 - Improve console #53 - Error structure with code #55 - Use a GADT parametrized by param type, fixes #54 #56 - Ghcmod commands #57 - Expect json input separated by STX, fix #43 #59 - fixed typo ParamDescription #60 - Add the rest of the commands to HaRe plugin #62 - Short cut sleeping when result is available #63 - Typed responses #64 - Enrich plugins call #65 - Implement STX #69 - Fall back to emacs if there is no emacs24 binary #70 - Async dispatch #72 - Remove invalid input even if not handled #73 - Handle end-of-file #74 - Properly handle STX delimited message #75 - [WIP] Initial stab at hie-mode #76 - Rename sub-packages to be hie-* #77 - added fast-tags #80 - Simplify json #85 - Support commands that only require a context #88 - Add plugin name to commandDetail response #90 - Ghc mod dir #91 - PluginDescriptor no longer serialisable. #93 - Adapt elisp to plugins response changes #94 - Json enhancements #96 - Use hierarchical menus instead of a flat one #97 - Create elisp functions for all commands #99 - Rename haskell-ide-engine to hie #100 - Update irc channel for travis #101 - Insert dash between plugin and command name #102 - Use dash.el #103 - nicer parameters and command return type #105 - Install dash.el for tests and require it #106 - docs: mention apply-refact, hsimport, haskdogs #110 - add ShortName and Overview to PluginDescriptor #111 - Extract the first type of a type info response #113 Contributors active in November Aaron Wolf, Alan Zimmerman, Daniel Bergey, Daniel Gr?ber, Gracjan Polak, JP Moresmau, Jochen G?rtler, Joe Hillenbrand, Justin Wood, Michael Sloan, Moritz Kiefer, Rory O?Kane, R?mi Vion, jpmoresmau Thanks A special thanks to Gracjan Polak for running his report scripts on this repo. Contributing Haskell IDE Engine needs volunteers like any other open source project. For more information see: https://github.com/haskell/haskell-ide-engine Also drop by our IRC channel: #haskell-ide-engine at irc.freenode.net. Thanks! Alan -------------- next part -------------- An HTML attachment was scrubbed... URL: From agentm at themactionfaction.com Wed Dec 2 17:51:44 2015 From: agentm at themactionfaction.com (A.M.) Date: Wed, 2 Dec 2015 12:51:44 -0500 Subject: [Haskell-cafe] [ANNOUNCE] Haskell DBMS: Project:M36 Message-ID: <565F2FB0.5010507@themactionfaction.com> Hello, Project:M36 is an open-source, relational algebra engine database management system written in Haskell. When used as a backend with other Haskell frameworks such as yesod, Project:M36 completes a fully-Haskell application stack. https://github.com/agentm/project-m36 Project:M36 adheres strongly to the relational algebra principles laid out by Chris Date in his books and, thus, includes a TutorialD interactive interpreter for learning about the relational algebra. Thus, Project:M36 does not suffer from the typical type-system impedance mismatch or SQL inconsistencies common in ORMs. Of particular interest to Haskellers is the existentially-quantified value type which allows any Haskell data type adhering to a set of basic typeclasses to be used directly as a database value. This feature includes creating database functions to operate directly on these values. In addition, the transaction model is similar to git: instead of continually contending for the "latest committed" state, the DBMS maintains a transaction graph which allows for branching and time travel to past commits. Naturally, through the use of immutable data structures, Project:M36 opens the door for parallelization of every query. Project:M36 includes two native Haskell interfacing libraries: a) a driver for the "persistent" library and b) a client library which allows direct access to the relational algebra DSLs. Thanks for looking at Project:M36! Best regards, Team Project:M36 -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: OpenPGP digital signature URL: From agentm at themactionfaction.com Wed Dec 2 17:51:43 2015 From: agentm at themactionfaction.com (A.M.) Date: Wed, 2 Dec 2015 12:51:43 -0500 Subject: [Haskell-cafe] [ANNOUNCE] Haskell DBMS: Project:M36 Message-ID: <565F2FAF.1090807@themactionfaction.com> Hello, Project:M36 is an open-source, relational algebra engine database management system written in Haskell. When used as a backend with other Haskell frameworks such as yesod, Project:M36 completes a fully-Haskell application stack. https://github.com/agentm/project-m36 Project:M36 adheres strongly to the relational algebra principles laid out by Chris Date in his books and, thus, includes a TutorialD interactive interpreter for learning about the relational algebra. Thus, Project:M36 does not suffer from the typical type-system impedance mismatch or SQL inconsistencies common in ORMs. Of particular interest to Haskellers is the existentially-quantified value type which allows any Haskell data type adhering to a set of basic typeclasses to be used directly as a database value. This feature includes creating database functions to operate directly on these values. In addition, the transaction model is similar to git: instead of continually contending for the "latest committed" state, the DBMS maintains a transaction graph which allows for branching and time travel to past commits. Naturally, through the use of immutable data structures, Project:M36 opens the door for parallelization of every query. Project:M36 includes two native Haskell interfacing libraries: a) a driver for the "persistent" library and b) a client library which allows direct access to the relational algebra DSLs. Thanks for looking at Project:M36! Best regards, Team Project:M36 -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: OpenPGP digital signature URL: From heraldhoi at gmail.com Wed Dec 2 18:38:30 2015 From: heraldhoi at gmail.com (Geraldus) Date: Wed, 02 Dec 2015 18:38:30 +0000 Subject: [Haskell-cafe] [ANNOUNCE] Haskell DBMS: Project:M36 In-Reply-To: <565F2FAF.1090807@themactionfaction.com> References: <565F2FAF.1090807@themactionfaction.com> Message-ID: Sounds very exciting! ??, 2 ???. 2015 ?. ? 22:52, A.M. : > Hello, > > Project:M36 is an open-source, relational algebra engine database > management system written in Haskell. When used as a backend with other > Haskell frameworks such as yesod, Project:M36 completes a fully-Haskell > application stack. > > https://github.com/agentm/project-m36 > > Project:M36 adheres strongly to the relational algebra principles laid > out by Chris Date in his books and, thus, includes a TutorialD > interactive interpreter for learning about the relational algebra. Thus, > Project:M36 does not suffer from the typical type-system impedance > mismatch or SQL inconsistencies common in ORMs. > > Of particular interest to Haskellers is the existentially-quantified > value type which allows any Haskell data type adhering to a set of basic > typeclasses to be used directly as a database value. This feature > includes creating database functions to operate directly on these values. > > In addition, the transaction model is similar to git: instead of > continually contending for the "latest committed" state, the DBMS > maintains a transaction graph which allows for branching and time travel > to past commits. > > Naturally, through the use of immutable data structures, Project:M36 > opens the door for parallelization of every query. > > Project:M36 includes two native Haskell interfacing libraries: a) a > driver for the "persistent" library and b) a client library which allows > direct access to the relational algebra DSLs. > > Thanks for looking at Project:M36! > > Best regards, > Team Project:M36 > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From achudnov at gmail.com Wed Dec 2 19:37:11 2015 From: achudnov at gmail.com (Andrey Chudnov) Date: Wed, 2 Dec 2015 14:37:11 -0500 Subject: [Haskell-cafe] [ANNOUNCE] Haskell DBMS: Project:M36 In-Reply-To: <565F2FAF.1090807@themactionfaction.com> References: <565F2FAF.1090807@themactionfaction.com> Message-ID: <565F4867.2020104@gmail.com> Interesting. I wonder how it compares to IxSet (https://hackage.haskell.org/package/ixset) and ACID-State (https://hackage.haskell.org/package/acid-state). Could you comment? On 12/02/2015 12:51 PM, A.M. wrote: > Hello, > > Project:M36 is an open-source, relational algebra engine database > management system written in Haskell. When used as a backend with other > Haskell frameworks such as yesod, Project:M36 completes a fully-Haskell > application stack. > > https://github.com/agentm/project-m36 > > Project:M36 adheres strongly to the relational algebra principles laid > out by Chris Date in his books and, thus, includes a TutorialD > interactive interpreter for learning about the relational algebra. Thus, > Project:M36 does not suffer from the typical type-system impedance > mismatch or SQL inconsistencies common in ORMs. > > Of particular interest to Haskellers is the existentially-quantified > value type which allows any Haskell data type adhering to a set of basic > typeclasses to be used directly as a database value. This feature > includes creating database functions to operate directly on these values. > > In addition, the transaction model is similar to git: instead of > continually contending for the "latest committed" state, the DBMS > maintains a transaction graph which allows for branching and time travel > to past commits. > > Naturally, through the use of immutable data structures, Project:M36 > opens the door for parallelization of every query. > > Project:M36 includes two native Haskell interfacing libraries: a) a > driver for the "persistent" library and b) a client library which allows > direct access to the relational algebra DSLs. > > Thanks for looking at Project:M36! > > Best regards, > Team Project:M36 > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe -------------- next part -------------- An HTML attachment was scrubbed... URL: From agentm at themactionfaction.com Wed Dec 2 19:56:44 2015 From: agentm at themactionfaction.com (A.M.) Date: Wed, 2 Dec 2015 14:56:44 -0500 Subject: [Haskell-cafe] [ANNOUNCE] Haskell DBMS: Project:M36 In-Reply-To: <565F4867.2020104@gmail.com> References: <565F2FAF.1090807@themactionfaction.com> <565F4867.2020104@gmail.com> Message-ID: <565F4CFC.9020200@themactionfaction.com> On 12/02/2015 02:37 PM, Andrey Chudnov wrote: > Interesting. I wonder how it compares to IxSet > (https://hackage.haskell.org/package/ixset) and ACID-State > (https://hackage.haskell.org/package/acid-state). Could you comment? Hi Andrey, Project:M36 is a complete relational algebra engine with multiple front-ends, optional filesystem persistence, and transactional semantics. Therefore, it is more akin to SQL DBMSs. More specifically, IxSet does not support relational join, relational group, persistence, aggregations, schema changes, or transactions. Acid-state is effectively a structure graph serializer and therefore has no provisions for schema changes, querying, or any relational algebra operators. Project:M36 can be used as a foundational component of the "Out of the Tarpit" architecture, while the other packages cannot. http://shaffner.us/cs/papers/tarpit.pdf Cheers, M -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: OpenPGP digital signature URL: From hjgtuyl at chello.nl Thu Dec 3 15:44:08 2015 From: hjgtuyl at chello.nl (Henk-Jan van Tuyl) Date: Thu, 03 Dec 2015 16:44:08 +0100 Subject: [Haskell-cafe] [ANNOUNCE] An Argh! interpreter in wxHaskell Message-ID: L.S., I just updated and cabalized arghwxhaskell (which I found on SourceForge) and put it on Hackage. arghwxhaskell is an interpreter for the Argh! programming language in wxHaskell. Argh! is an esoteric programming language created by Sascha Wilde. Wiki page: https://wiki.haskell.org/Argh! Package address: https://hackage.haskell.org/package/arghwxhaskell Regards, Henk-Jan van Tuyl -- Folding at home What if you could share your unused computer power to help find a cure? In just 5 minutes you can join the world's biggest networked computer and get us closer sooner. Watch the video. http://folding.stanford.edu/ http://Van.Tuyl.eu/ http://members.chello.nl/hjgtuyl/tourdemonad.html Haskell programming -- From olshanskydr at gmail.com Thu Dec 3 16:16:53 2015 From: olshanskydr at gmail.com (Dmitry Olshansky) Date: Thu, 3 Dec 2015 19:16:53 +0300 Subject: [Haskell-cafe] Yet Another Named Record Message-ID: Hello, cafe! I made a small library https://github.com/odr/pers. It is my attempt for Named Record problem. There is no TH, just TF, Symbols and so on. With this library one can now: * Construct record sequentially (record is balanced tuple-based tree): type T = "a":>Int +> "b":>String +> "c":>Maybe Int rec = V 5 +> V "b" +> V (Just 3) :: T * Get Lens' for fields or record (group of fields) with O(k*log n) access: lb = fieldLens (Proxy :: "b":>String) :: Lens' T String lca = recLens :: Lens' T ("c:>Maybe Int +> "a":>Int) Note that recLens is Projection! * Lift all fields into Functor: type LT = Lifted Maybe T -- LT == "a":>Maybe Int +> "b":>Maybe String +> "c":>Maybe (Maybe Int) If all fields has Default instances, record has it also. It is the case for Lifted Maybe T. * Convert from and to Map of fields (using PersistField and PersistValue from persistent package) m = M.fromList [ (someSymbolVal "a", toPersistValue 1) , (someSymbolVal "b", toPersistValue "xx") -- value for "c" is optional ] recEither = mapToRec (Proxy :: Proxy T) m :: Either [SomeSymbol] T m' = fmap toMap recEither I wonder: - Are there similar attempts? - Is it interesting? I suppose it could be used as basis for Persistent (instead of TH). Is it? Other application? - What other features you want to add here? Best regards, Dmitry Olshansky -------------- next part -------------- An HTML attachment was scrubbed... URL: From murilo.winter at gmail.com Thu Dec 3 22:16:07 2015 From: murilo.winter at gmail.com (Murilo Winter) Date: Thu, 3 Dec 2015 22:16:07 +0000 Subject: [Haskell-cafe] Creating an instance of the Show Typeclass for a datatype Message-ID: Hello, As part of my exercise, I have to create an instance of the show typeclass for a given data type defined as: 1. *type *stat *= (*String*, Int)* *If* it was a data type, like: 1. data TrafficLight = Red | Yellow | Green It would be as simple as doing: 1. instance Show TrafficLight where 2. show Red = "Red light" 3. show Yellow = "Yellow light" 4. show Green = "Green light" However, I do not know how to declare the instance for a type, and then how to access its elements (String and Int). This is what I have so far, which does not work: 1. instance Show Stat where 2. show stat(a,b) = a instance Show Stat where show stat(a b) = b (imagine, for example, I desire to write" the value of "String" is "Int"). Thanks, -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Thu Dec 3 22:23:10 2015 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Thu, 3 Dec 2015 22:23:10 +0000 Subject: [Haskell-cafe] Creating an instance of the Show Typeclass for a datatype In-Reply-To: References: Message-ID: <20151203222310.GI9779@weber> On Thu, Dec 03, 2015 at 10:16:07PM +0000, Murilo Winter wrote: > As part of my exercise, I have to create an instance of the show typeclass > for a given data type defined as: > > 1. *type *stat *= (*String*, Int)* That's not a new datatype, that's a type synonym. > *If* it was a data type, like: > > 1. data TrafficLight = Red | Yellow | Green > > > It would be as simple as doing: > > 1. instance Show TrafficLight where > 2. show Red = "Red light" > 3. show Yellow = "Yellow light" > 4. show Green = "Green light" > > > However, I do not know how to declare the instance for a type, and then how > to access its elements (String and Int). > > This is what I have so far, which does not work: > > 1. instance Show Stat where > 2. show stat(a,b) = a > > instance Show Stat where > show stat(a b) = b You probably want something like data Stat = Stat String Int instance Show Stat where show (Stat s _) = s By why not just use data Stat = Stat String Int deriving Show instead? Tom From ncrashed at gmail.com Thu Dec 3 22:23:32 2015 From: ncrashed at gmail.com (NCrashed .) Date: Fri, 4 Dec 2015 01:23:32 +0300 Subject: [Haskell-cafe] Creating an instance of the Show Typeclass for a datatype In-Reply-To: References: Message-ID: Hi, instance Show Stat where show (a, b) = "the value of " ++ a ++ " is " ++ show b I pretty sure you need also enable TypeSynonymInstances extension. One way to do it is to add "{-# LANGUAGE TypeSynonymInstances #-}" just at the beginning of your module. Best wishes 2015-12-04 1:16 GMT+03:00 Murilo Winter : > Hello, > > As part of my exercise, I have to create an instance of the show typeclass > for a given data type defined as: > > 1. *type *stat *= (*String*, Int)* > > *If* it was a data type, like: > > 1. data TrafficLight = Red | Yellow | Green > > > It would be as simple as doing: > > 1. instance Show TrafficLight where > 2. show Red = "Red light" > 3. show Yellow = "Yellow light" > 4. show Green = "Green light" > > > However, I do not know how to declare the instance for a type, and then > how to access its elements (String and Int). > > This is what I have so far, which does not work: > > 1. instance Show Stat where > 2. show stat(a,b) = a > > instance Show Stat where > show stat(a b) = b > > (imagine, for example, I desire to write" the value of "String" is "Int"). > > Thanks, > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jo at durchholz.org Fri Dec 4 07:49:43 2015 From: jo at durchholz.org (Joachim Durchholz) Date: Fri, 4 Dec 2015 08:49:43 +0100 Subject: [Haskell-cafe] Reasoning about performance Message-ID: <56614597.8080607@durchholz.org> Hi all, is there an easy-to read introductory paper on reasoning about performance in Haskell? Stuff like big-Oh space and time complexity of a function. What I'm mostly after is how to organize complexity reasoning given non-strict evaluation. In that situation, a function's complexity depends on what subexpressions of the parameters have already been evaluated, so you get rather complicated conditional formulae, and you also need to somehow express what parts of a passed-in parameter may get evaluated under what conditions. Is there even a good notation for that kind of stuff? Is there advice on how to organize the code to make performance formulae manageable? Example: Performance of length xs Turns out it is the number of items in xs, plus whatever you need to evaluate the list spine, as far as the list spine elements have not yet been evaluated (but you do not need to evaluate the list items). I have no idea how to even write that down. What notation to use so one can formally reason about it. Any pointers? Regards, Jo From sumit.sahrawat.apm13 at iitbhu.ac.in Fri Dec 4 08:01:16 2015 From: sumit.sahrawat.apm13 at iitbhu.ac.in (Sumit Sahrawat, Maths & Computing, IIT (BHU)) Date: Fri, 4 Dec 2015 13:31:16 +0530 Subject: [Haskell-cafe] Reasoning about performance In-Reply-To: <56614597.8080607@durchholz.org> References: <56614597.8080607@durchholz.org> Message-ID: If you're comfortable with imperative data structures, then you can go for Okasaki's book: http://www.amazon.com/Purely-Functional-Structures-Chris-Okasaki/dp/0521663504 Which developed from his Ph.D thesis available here: http://www.cs.cmu.edu/~rwh/theses/okasaki.pdf People say both are very similar in their contents, but I can't say for sure. I've read the first two chapters and found them to be enlightening. On 4 December 2015 at 13:19, Joachim Durchholz wrote: > Hi all, > > is there an easy-to read introductory paper on reasoning about performance > in Haskell? > Stuff like big-Oh space and time complexity of a function. > > What I'm mostly after is how to organize complexity reasoning given > non-strict evaluation. In that situation, a function's complexity depends > on what subexpressions of the parameters have already been evaluated, so > you get rather complicated conditional formulae, and you also need to > somehow express what parts of a passed-in parameter may get evaluated under > what conditions. > Is there even a good notation for that kind of stuff? Is there advice on > how to organize the code to make performance formulae manageable? > > Example: Performance of > length xs > Turns out it is the number of items in xs, plus whatever you need to > evaluate the list spine, as far as the list spine elements have not yet > been evaluated (but you do not need to evaluate the list items). > I have no idea how to even write that down. What notation to use so one > can formally reason about it. > > Any pointers? > > Regards, > Jo > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -- Regards Sumit Sahrawat -------------- next part -------------- An HTML attachment was scrubbed... URL: From jo at durchholz.org Fri Dec 4 08:35:38 2015 From: jo at durchholz.org (Joachim Durchholz) Date: Fri, 4 Dec 2015 09:35:38 +0100 Subject: [Haskell-cafe] Reasoning about performance In-Reply-To: References: <56614597.8080607@durchholz.org> Message-ID: <5661505A.9010908@durchholz.org> Am 04.12.2015 um 09:01 schrieb Sumit Sahrawat, Maths & Computing, IIT (BHU): > If you're comfortable with imperative data structures, then you can go for > Okasaki's book: > http://www.amazon.com/Purely-Functional-Structures-Chris-Okasaki/dp/0521663504 > Which developed from his Ph.D thesis available here: > http://www.cs.cmu.edu/~rwh/theses/okasaki.pdf > > People say both are very similar in their contents, but I can't say for > sure. I've read the first two chapters and found them to be enlightening. I read the book, Okasaki is very enlightening but does not talk about how to deal with partially preevaluated data structures. Regards, Jo From frantisek.kocun at gmail.com Fri Dec 4 22:02:37 2015 From: frantisek.kocun at gmail.com (frantisek kocun) Date: Fri, 4 Dec 2015 17:02:37 -0500 Subject: [Haskell-cafe] Eq macro which matches anything Message-ID: Hi guys, I'm doing Write yourself Scheme tutorial. And for testing it would be cool to have some kind of macro. -- My data type with Eq derived data LispError = NumArgs Integer [LispVal] | TypeMismatch String LispVal | Parser ParseError | BadSpecialForm String LispVal | NotFunction String String | UnboundVar String String | Default String deriving (Eq) -- I can call == NumArgs 1 [] == NumArgs 1 [] -- but sometimes I want to do (I know I can implement my own Eq, but I want to use both forms) NumArgs 1 [] == NumArgs 1 _ where I omit second parameter. I think derived Eq where it matches all the args is fine I just need to do macro which will get whateverType by compiler and always return True in Equality check. Do you think it is possible to do? I use Mockito library in java but java is OO, so completely different beast. Thank you -------------- next part -------------- An HTML attachment was scrubbed... URL: From manny at fpcomplete.com Fri Dec 4 23:57:10 2015 From: manny at fpcomplete.com (Emanuel Borsboom) Date: Fri, 04 Dec 2015 23:57:10 +0000 Subject: [Haskell-cafe] ANN: stack-0.1.10.0 Message-ID: Release notes: - The Stack home page is now at haskellstack.org, which shows the documentation rendered by readthedocs.org. Note: this has necessitated some changes to the links in the documentation?s markdown source code, so please check the links on the website before submitting a PR to fix them. - The locations of the Ubuntu and Debian package repositories have changed to have correct URL semantics according to Debian?s guidelines #1378 . The old locations will continue to work for some months, but we suggest that you adjust your /etc/apt/sources.list.d/fpco.list to the new location to avoid future disruption. - openSUSE and SUSE Linux Enterprise packages are now available, thanks to @mimi1vx . Note: there will be some lag before these pick up new versions, as they are based on Stackage LTS. Major changes: - Support for building inside a Nix-shell providing system dependencies #1285 - Add optional GPG signing on stack upload --sign or with stack sig sign ... Other enhancements: - Print latest applicable version of packages on conflicts #508 - Support for packages located in Mercurial repositories #1397 - Only run benchmarks specified as build targets #1412 - Support git-style executable fall-through (stack something executes stack-something if present) #1433 - GHCi now loads intermediate dependencies #584 - --work-dir option for overriding .stack-work #1178 - Support detailed-0.9 tests #1429 - Docker: improved POSIX signal proxying to containers #547 Bug fixes: - Show absolute paths in error messages in multi-package builds #1348 - Docker-built binaries and libraries in different path #911 #1367 - Docker: --resolver argument didn?t effect selected image tag - GHCi: Spaces in filepaths caused module loading issues #1401 - GHCi: cpp-options in cabal files weren?t used #1419 - Benchmarks couldn?t be run independently of eachother #1412 - Send output of building setup to stderr #1410 ? -------------- next part -------------- An HTML attachment was scrubbed... URL: From defigueiredo at ucdavis.edu Sat Dec 5 01:01:17 2015 From: defigueiredo at ucdavis.edu (Dimitri DeFigueiredo) Date: Fri, 4 Dec 2015 22:01:17 -0300 Subject: [Haskell-cafe] Reasoning about performance In-Reply-To: <5661505A.9010908@durchholz.org> References: <56614597.8080607@durchholz.org> <5661505A.9010908@durchholz.org> Message-ID: <5662375D.1000805@ucdavis.edu> Indeed. I find laziness and the non-composable nature of space complexity in Haskell to be a much harder beast to deal with than immutability. There is an *excellent* introduction to the basics of lazy evaluation in Graham Hutton's book /Programming in Haskell/ (chapter 12), but I don't know of any good references beyond that basic level. Let us know if you find some! Dimitri On 12/4/15 5:35 AM, Joachim Durchholz wrote: > Am 04.12.2015 um 09:01 schrieb Sumit Sahrawat, Maths & Computing, IIT > (BHU): >> If you're comfortable with imperative data structures, then you can >> go for >> Okasaki's book: >> http://www.amazon.com/Purely-Functional-Structures-Chris-Okasaki/dp/0521663504 >> >> Which developed from his Ph.D thesis available here: >> http://www.cs.cmu.edu/~rwh/theses/okasaki.pdf >> >> People say both are very similar in their contents, but I can't say for >> sure. I've read the first two chapters and found them to be >> enlightening. > > I read the book, Okasaki is very enlightening but does not talk about > how to deal with partially preevaluated data structures. > > Regards, > Jo > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe -------------- next part -------------- An HTML attachment was scrubbed... URL: From ivan.miljenovic at gmail.com Sat Dec 5 01:46:06 2015 From: ivan.miljenovic at gmail.com (Ivan Lazar Miljenovic) Date: Sat, 5 Dec 2015 12:46:06 +1100 Subject: [Haskell-cafe] Eq macro which matches anything In-Reply-To: References: Message-ID: On 5 December 2015 at 09:02, frantisek kocun wrote: > Hi guys, > > I'm doing Write yourself Scheme tutorial. And for testing it would be cool > to have some kind of macro. > > -- My data type with Eq derived > data LispError = NumArgs Integer [LispVal] > | TypeMismatch String LispVal > | Parser ParseError > | BadSpecialForm String LispVal > | NotFunction String String > | UnboundVar String String > | Default String > deriving (Eq) > > -- I can call == > NumArgs 1 [] == NumArgs 1 [] > > -- but sometimes I want to do (I know I can implement my own Eq, but I want > to use both forms) > NumArgs 1 [] == NumArgs 1 _ > > where I omit second parameter. I think derived Eq where it matches all the > args is fine I just need to do macro which will get whateverType by compiler > and always return True in Equality check. Do you think it is possible to do? > I use Mockito library in java but java is OO, so completely different beast. > > Thank you You could always define a new function: eqError :: LispError -> LispError -> Bool eqError (NumArgs n1 _) (NumArgs n2 _) = n1 == n2 eqError TypeMisMatch{} TypeMismatch{} = True -- etc. > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -- Ivan Lazar Miljenovic Ivan.Miljenovic at gmail.com http://IvanMiljenovic.wordpress.com From heraldhoi at gmail.com Sat Dec 5 07:50:04 2015 From: heraldhoi at gmail.com (Geraldus) Date: Sat, 05 Dec 2015 07:50:04 +0000 Subject: [Haskell-cafe] ANN: stack-0.1.10.0 In-Reply-To: References: Message-ID: Thank you! It's nice to see new homepage and pretty documentation! ??, 5 ???. 2015 ?. ? 4:57, Emanuel Borsboom : > Release notes: > > - The Stack home page is now at haskellstack.org, which shows the > documentation rendered by readthedocs.org. Note: this has necessitated > some changes to the links in the documentation?s markdown source code, so > please check the links on the website before submitting a PR to fix them. > - The locations of the Ubuntu > > and Debian > > package repositories have changed to have correct URL semantics according > to Debian?s guidelines #1378 > . The old > locations will continue to work for some months, but we suggest that you > adjust your /etc/apt/sources.list.d/fpco.list to the new location to > avoid future disruption. > - openSUSE and SUSE Linux Enterprise > > packages are now available, thanks to @mimi1vx > . Note: there will be some lag before > these pick up new versions, as they are based on Stackage LTS. > > Major changes: > > - Support for building inside a Nix-shell providing system > dependencies #1285 > > - Add optional GPG signing on stack upload --sign or with stack sig > sign ... > > Other enhancements: > > - Print latest applicable version of packages on conflicts #508 > > - Support for packages located in Mercurial repositories #1397 > > - Only run benchmarks specified as build targets #1412 > > - Support git-style executable fall-through (stack something executes > stack-something if present) #1433 > > - GHCi now loads intermediate dependencies #584 > > - --work-dir option for overriding .stack-work #1178 > > - Support detailed-0.9 tests #1429 > > - Docker: improved POSIX signal proxying to containers #547 > > > Bug fixes: > > - Show absolute paths in error messages in multi-package builds #1348 > > - Docker-built binaries and libraries in different path #911 > #1367 > > - Docker: --resolver argument didn?t effect selected image tag > - GHCi: Spaces in filepaths caused module loading issues #1401 > > - GHCi: cpp-options in cabal files weren?t used #1419 > > - Benchmarks couldn?t be run independently of eachother #1412 > > - Send output of building setup to stderr #1410 > > > ? > > -- > You received this message because you are subscribed to the Google Groups > "haskell-stack" group. > To unsubscribe from this group and stop receiving emails from it, send an > email to haskell-stack+unsubscribe at googlegroups.com. > To post to this group, send email to haskell-stack at googlegroups.com. > To view this discussion on the web visit > https://groups.google.com/d/msgid/haskell-stack/CACGj5vLb32C9kBxXjSYN1nP8Vc77wgo2MDoFRShoHscYgYKqZg%40mail.gmail.com > > . > For more options, visit https://groups.google.com/d/optout. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From sumit.sahrawat.apm13 at iitbhu.ac.in Sat Dec 5 11:05:53 2015 From: sumit.sahrawat.apm13 at iitbhu.ac.in (Sumit Sahrawat, Maths & Computing, IIT (BHU)) Date: Sat, 5 Dec 2015 16:35:53 +0530 Subject: [Haskell-cafe] Reasoning about performance In-Reply-To: <5662375D.1000805@ucdavis.edu> References: <56614597.8080607@durchholz.org> <5661505A.9010908@durchholz.org> <5662375D.1000805@ucdavis.edu> Message-ID: For lazy evaluation, this is the best resource I've found: https://hackhands.com/guide-lazy-evaluation-haskell On 5 December 2015 at 06:31, Dimitri DeFigueiredo wrote: > Indeed. I find laziness and the non-composable nature of space complexity > in Haskell to be a much harder beast to deal with than immutability. > > There is an *excellent* introduction to the basics of lazy evaluation in > Graham Hutton's book *Programming in Haskell* (chapter 12), but I don't > know of any good references beyond that basic level. Let us know if you > find some! > > Dimitri > > On 12/4/15 5:35 AM, Joachim Durchholz wrote: > > Am 04.12.2015 um 09:01 schrieb Sumit Sahrawat, Maths & Computing, IIT > (BHU): > > If you're comfortable with imperative data structures, then you can go for > Okasaki's book: > > http://www.amazon.com/Purely-Functional-Structures-Chris-Okasaki/dp/0521663504 > Which developed from his Ph.D thesis available here: > http://www.cs.cmu.edu/~rwh/theses/okasaki.pdf > > People say both are very similar in their contents, but I can't say for > sure. I've read the first two chapters and found them to be enlightening. > > > I read the book, Okasaki is very enlightening but does not talk about how > to deal with partially preevaluated data structures. > > Regards, > Jo > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > -- Regards Sumit Sahrawat -------------- next part -------------- An HTML attachment was scrubbed... URL: From jo at durchholz.org Sat Dec 5 12:18:54 2015 From: jo at durchholz.org (Joachim Durchholz) Date: Sat, 5 Dec 2015 13:18:54 +0100 Subject: [Haskell-cafe] Reasoning about performance In-Reply-To: <5662375D.1000805@ucdavis.edu> References: <56614597.8080607@durchholz.org> <5661505A.9010908@durchholz.org> <5662375D.1000805@ucdavis.edu> Message-ID: <5662D62E.6000506@durchholz.org> Am 05.12.2015 um 02:01 schrieb Dimitri DeFigueiredo: > Indeed. I find laziness and the non-composable nature of space > complexity in Haskell to be a much harder beast to deal with than > immutability. I can imagine. Immutability can be dealt with by applying a few principles in the key points, and everything will work out; space complexity is riddled with exceptions. OTOH space and time complexity are non-composable (well, not trivially composable anyway) even in a strict language. As software grows larger, people start doing all kinds of deferred evaluation strategies, and the problems crop up - with the added complication that the software is already so large that the root cause of some complexity problem is hidden behind lots of tiny details. So, I currently believe that Haskell is just showcasing the problem early. This is worth something, but I guess not for that majority of programmers who're doing business logic for websites, or for those just learning to code in Haskell and tripping over space complexity. > There is an *excellent* introduction to the basics of lazy evaluation in > Graham Hutton's book /Programming in Haskell/ (chapter 12), but I don't > know of any good references beyond that basic level. Let us know if you > find some! Sumit gave a link to backhands.com which has turned out to be pretty deep and accessible. Unfortunately, that link still does not offer a systematic approach to keeping tabs about complexity. So... the main question is still open. I hope somebody can shed insight about how to attack this. What do people do if they find their Haskell code to perform badly - do they all resort to ad-hockery, or is there a systematic approach that will either give insight what to change where? Even an approach that may fail is better than just ad hoc I think, as long as it succeeds often enough to be useful. Regards, Jo From apfelmus at quantentunnel.de Sat Dec 5 14:15:40 2015 From: apfelmus at quantentunnel.de (Heinrich Apfelmus) Date: Sat, 05 Dec 2015 15:15:40 +0100 Subject: [Haskell-cafe] Reasoning about performance In-Reply-To: <56614597.8080607@durchholz.org> References: <56614597.8080607@durchholz.org> Message-ID: Dear Joachim, you probably already know the basics of lazy evaluation, but to fix conventions, allow me to plug a tutorial of mine: https://hackhands.com/guide-lazy-evaluation-haskell/ As you mentioned, reasoning about time usage is not entirely straightforward, since expressions may be evaluated partially. Chris Okasaki's thesis/book does treat this problem in chapter 6, in order to clarify what amortization means in a language with persistent data structures, and why lazy evaluation is very useful for that. The main idea is that to each constructor of a data structure, we assign a cost, which is a number of "debits". Whenever we evaluate a constructor to WHNF, we have to pay the number of debits assigned to it. Then, the debits that we have paid so far will always be an upper bound on the time that we have spent evaluating the expression so far. For instance, the `length` function creates an integer whose assigned number of debits is twice the sum of the debits of each constructor in the input list. For more details, see also http://apfelmus.nfshost.com/articles/debit-method.html Ultimately, the point of the debit method is to reflect the time needed for evaluation of an expression (a notion from operational semantics) in the value that this expression represents (a notion from denotational semantics). Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com Joachim Durchholz wrote: > Hi all, > > is there an easy-to read introductory paper on reasoning about > performance in Haskell? > Stuff like big-Oh space and time complexity of a function. > > What I'm mostly after is how to organize complexity reasoning given > non-strict evaluation. In that situation, a function's complexity > depends on what subexpressions of the parameters have already been > evaluated, so you get rather complicated conditional formulae, and you > also need to somehow express what parts of a passed-in parameter may get > evaluated under what conditions. > Is there even a good notation for that kind of stuff? Is there advice on > how to organize the code to make performance formulae manageable? > > Example: Performance of > length xs > Turns out it is the number of items in xs, plus whatever you need to > evaluate the list spine, as far as the list spine elements have not yet > been evaluated (but you do not need to evaluate the list items). > I have no idea how to even write that down. What notation to use so one > can formally reason about it. > > Any pointers? > > Regards, > Jo From capn.freako at gmail.com Sat Dec 5 16:28:31 2015 From: capn.freako at gmail.com (David Banas) Date: Sat, 5 Dec 2015 08:28:31 -0800 Subject: [Haskell-cafe] -Wall in IHaskell notebooks? Message-ID: Does anyone know how to turn on ?-Wall? in a IHaskell notebook? From sumit.sahrawat.apm13 at iitbhu.ac.in Sat Dec 5 16:33:28 2015 From: sumit.sahrawat.apm13 at iitbhu.ac.in (Sumit Sahrawat, Maths & Computing, IIT (BHU)) Date: Sat, 5 Dec 2015 22:03:28 +0530 Subject: [Haskell-cafe] -Wall in IHaskell notebooks? In-Reply-To: References: Message-ID: Try :? On 5 December 2015 at 21:58, David Banas wrote: > Does anyone know how to turn on ?-Wall? in a IHaskell notebook? > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -- Regards Sumit Sahrawat -------------- next part -------------- An HTML attachment was scrubbed... URL: From sumit.sahrawat.apm13 at iitbhu.ac.in Sat Dec 5 16:54:37 2015 From: sumit.sahrawat.apm13 at iitbhu.ac.in (Sumit Sahrawat, Maths & Computing, IIT (BHU)) Date: Sat, 5 Dec 2015 22:24:37 +0530 Subject: [Haskell-cafe] -Wall in IHaskell notebooks? In-Reply-To: References: Message-ID: Using `:set -Wall` also has some issues, I've added them to the issue report on github: https://github.com/gibiansky/IHaskell/issues/610 We would need to conceal warnings from specific regions of code for it to work as expected. On 5 December 2015 at 22:03, Sumit Sahrawat, Maths & Computing, IIT (BHU) < sumit.sahrawat.apm13 at iitbhu.ac.in> wrote: > Try :? > > On 5 December 2015 at 21:58, David Banas wrote: > >> Does anyone know how to turn on ?-Wall? in a IHaskell notebook? >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> > > > > -- > Regards > > Sumit Sahrawat > -- Regards Sumit Sahrawat -------------- next part -------------- An HTML attachment was scrubbed... URL: From omari at smileystation.com Sat Dec 5 17:54:31 2015 From: omari at smileystation.com (Omari Norman) Date: Sat, 5 Dec 2015 12:54:31 -0500 Subject: [Haskell-cafe] Announcing Pinchot - builds data types and Earley grammars for context-free grammars Message-ID: I have just uploaded to Hackage the Pinchot library: https://hackage.haskell.org/package/pinchot I also have a pull request to get it into Stackage so hopefully it should be there in a few days as well. Pinchot provides a simple monadic language that you use to describe a context-free grammar. Using this language you build a value that represents your grammar. Then, using this value and Template Haskell, you can automatically generate a complete set of data types that correspond to the rules in your context-free grammar. You also use Template Haskell to generate an Earley grammar for your language, using the Haskell Earley library: https://hackage.haskell.org/package/Earley Unlike parsers such as Parsec and Happy, Earley parses all context-free grammars, regardless of the amount of necessary look-ahead or the presence of left recursion. Earley does not, however, parse context-sensitive grammars. Pinchot is documented and comes with several examples. It passes several simple tests but it has not yet been used in anger. I wrote Pinchot because I was excited to see Earley when it was released. Finally we had a parser that would simply parse context-free grammars. Give a grammar, get a parser. Parsec and its ilk, on the other hand, are libraries allowing you to write a recursive-descent parser by hand. That's useful, but if you know you have a context-free grammar it's easier to use a tool tailored to that. So when using Earley I found myself writing the data types and then writing the Earley grammar specification. This was a rote process ripe for automation. -------------- next part -------------- An HTML attachment was scrubbed... URL: From b at chreekat.net Sat Dec 5 18:49:58 2015 From: b at chreekat.net (Bryan Richter) Date: Sat, 5 Dec 2015 10:49:58 -0800 Subject: [Haskell-cafe] Eq macro which matches anything In-Reply-To: References: Message-ID: On Fri, Dec 4, 2015 at 2:02 PM, frantisek kocun wrote: > -- (I know I can implement my own Eq, but I want to use both forms) The two computations are very different. Since the type of a value determines which "Eq" computation to run, it is not advisable to try to get two different computations to work for the same type. What you can do instead is use a newtype: -- | A variant that ignores the LispVal in NumArgs for Eq newtype LispErrorI = LispErrorI LispError instance Eq LispErrorI where (LispErrorI (NumArgs n _)) == (LispErrorI (NumArgs n' _)) = n == n' (LispErrorI e) == (LispErrorI e') = e == e' Anytime you want to compare two LispError:s using the second computation, you can wrap / unwrap the values in the newtype. It creates some extra syntax noise, but it makes the intent very clear, and there's no runtime cost. -------------- next part -------------- An HTML attachment was scrubbed... URL: From capn.freako at gmail.com Sat Dec 5 20:18:03 2015 From: capn.freako at gmail.com (David Banas) Date: Sat, 5 Dec 2015 12:18:03 -0800 Subject: [Haskell-cafe] -Wall in IHaskell notebooks? In-Reply-To: References: Message-ID: <2450457A-B190-4A14-9453-FDADF2C3F24F@gmail.com> Hi Sumit, Thanks for your reply! I tried putting ?:set -Wall? near the top of my first code cell (immediately after all my {-# LANGUAGE ? #-} pragmas), but that hasn?t resulted in any extra output, compared to what I was seeing before. Do I need to enable something else, in order to have ?:set -Wall? take effect? Thanks, -db On Dec 5, 2015, at 8:54 AM, Sumit Sahrawat, Maths & Computing, IIT (BHU) wrote: > Using `:set -Wall` also has some issues, I've added them to the issue report on github: https://github.com/gibiansky/IHaskell/issues/610 > > We would need to conceal warnings from specific regions of code for it to work as expected. > > On 5 December 2015 at 22:03, Sumit Sahrawat, Maths & Computing, IIT (BHU) wrote: > Try :? > > On 5 December 2015 at 21:58, David Banas wrote: > Does anyone know how to turn on ?-Wall? in a IHaskell notebook? > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > > -- > Regards > > Sumit Sahrawat > > > > -- > Regards > > Sumit Sahrawat -------------- next part -------------- An HTML attachment was scrubbed... URL: From sumit.sahrawat.apm13 at iitbhu.ac.in Sat Dec 5 20:27:19 2015 From: sumit.sahrawat.apm13 at iitbhu.ac.in (Sumit Sahrawat, Maths & Computing, IIT (BHU)) Date: Sun, 6 Dec 2015 01:57:19 +0530 Subject: [Haskell-cafe] -Wall in IHaskell notebooks? In-Reply-To: <2450457A-B190-4A14-9453-FDADF2C3F24F@gmail.com> References: <2450457A-B190-4A14-9453-FDADF2C3F24F@gmail.com> Message-ID: Hi David, When I tried it, I put it in an empty cell containing just the `:set -Wall` command. I think it is intended to be usable freely in a cell, so you might have landed on a bug. Also, I'm assuming that you're familiar with the notebook interface, and you executed the cell after making the edit. If not, take a look at the interface intro tour in the toolbar above: Help > User Interface Tour. I'll experiment and update the issue report with what I find. On 6 December 2015 at 01:48, David Banas wrote: > Hi Sumit, > > Thanks for your reply! > > I tried putting ?:set -Wall? near the top of my first code cell > (immediately after all my {-# LANGUAGE ? #-} pragmas), but that hasn?t > resulted in any extra output, compared to what I was seeing before. Do I > need to enable something else, in order to have ?:set -Wall? take effect? > > Thanks, > -db > > On Dec 5, 2015, at 8:54 AM, Sumit Sahrawat, Maths & Computing, IIT (BHU) < > sumit.sahrawat.apm13 at iitbhu.ac.in> wrote: > > Using `:set -Wall` also has some issues, I've added them to the issue > report on github: https://github.com/gibiansky/IHaskell/issues/610 > > We would need to conceal warnings from specific regions of code for it to > work as expected. > > On 5 December 2015 at 22:03, Sumit Sahrawat, Maths & Computing, IIT (BHU) > wrote: > >> Try :? >> >> On 5 December 2015 at 21:58, David Banas wrote: >> >>> Does anyone know how to turn on ?-Wall? in a IHaskell notebook? >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> >> >> >> >> -- >> Regards >> >> Sumit Sahrawat >> > > > > -- > Regards > > Sumit Sahrawat > > > -- Regards Sumit Sahrawat -------------- next part -------------- An HTML attachment was scrubbed... URL: From capn.freako at gmail.com Sat Dec 5 20:43:31 2015 From: capn.freako at gmail.com (David Banas) Date: Sat, 5 Dec 2015 12:43:31 -0800 Subject: [Haskell-cafe] -Wall in IHaskell notebooks? In-Reply-To: References: <2450457A-B190-4A14-9453-FDADF2C3F24F@gmail.com> Message-ID: <145C46E3-25AE-42FC-9B0C-BC6BC520AAA5@gmail.com> So, I just: Put ?:set -Wall? in the first code cell in my notebook, and all by itself. Saved my notebook. Restarted my kernel. Selected ?Run all? from the Cell menu. No change in the output from any of my code cells. -db On Dec 5, 2015, at 12:27 PM, Sumit Sahrawat, Maths & Computing, IIT (BHU) wrote: > Hi David, > > When I tried it, I put it in an empty cell containing just the `:set -Wall` command. I think it is intended to be usable freely in a cell, so you might have landed on a bug. > Also, I'm assuming that you're familiar with the notebook interface, and you executed the cell after making the edit. If not, take a look at the interface intro tour in the toolbar above: Help > User Interface Tour. > > I'll experiment and update the issue report with what I find. > > On 6 December 2015 at 01:48, David Banas wrote: > Hi Sumit, > > Thanks for your reply! > > I tried putting ?:set -Wall? near the top of my first code cell (immediately after all my {-# LANGUAGE ? #-} pragmas), but that hasn?t resulted in any extra output, compared to what I was seeing before. Do I need to enable something else, in order to have ?:set -Wall? take effect? > > Thanks, > -db > > On Dec 5, 2015, at 8:54 AM, Sumit Sahrawat, Maths & Computing, IIT (BHU) wrote: > >> Using `:set -Wall` also has some issues, I've added them to the issue report on github: https://github.com/gibiansky/IHaskell/issues/610 >> >> We would need to conceal warnings from specific regions of code for it to work as expected. >> >> On 5 December 2015 at 22:03, Sumit Sahrawat, Maths & Computing, IIT (BHU) wrote: >> Try :? >> >> On 5 December 2015 at 21:58, David Banas wrote: >> Does anyone know how to turn on ?-Wall? in a IHaskell notebook? >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> >> >> >> -- >> Regards >> >> Sumit Sahrawat >> >> >> >> -- >> Regards >> >> Sumit Sahrawat > > > > > -- > Regards > > Sumit Sahrawat -------------- next part -------------- An HTML attachment was scrubbed... URL: From sumit.sahrawat.apm13 at iitbhu.ac.in Sat Dec 5 21:25:52 2015 From: sumit.sahrawat.apm13 at iitbhu.ac.in (Sumit Sahrawat, Maths & Computing, IIT (BHU)) Date: Sun, 6 Dec 2015 02:55:52 +0530 Subject: [Haskell-cafe] -Wall in IHaskell notebooks? In-Reply-To: <145C46E3-25AE-42FC-9B0C-BC6BC520AAA5@gmail.com> References: <2450457A-B190-4A14-9453-FDADF2C3F24F@gmail.com> <145C46E3-25AE-42FC-9B0C-BC6BC520AAA5@gmail.com> Message-ID: I added some details to the issue report on GitHub. It turns out that the issue of warnings not showing was discovered before, but got lost somewhere. On 6 December 2015 at 02:13, David Banas wrote: > So, I just: > > 1. Put ?:set -Wall? in the first code cell in my notebook, and all by > itself. > 2. Saved my notebook. > 3. Restarted my kernel. > 4. Selected ?Run all? from the Cell menu. > > No change in the output from any of my code cells. > > -db > > On Dec 5, 2015, at 12:27 PM, Sumit Sahrawat, Maths & Computing, IIT (BHU) < > sumit.sahrawat.apm13 at iitbhu.ac.in> wrote: > > Hi David, > > When I tried it, I put it in an empty cell containing just the `:set > -Wall` command. I think it is intended to be usable freely in a cell, so > you might have landed on a bug. > Also, I'm assuming that you're familiar with the notebook interface, and > you executed the cell after making the edit. If not, take a look at the > interface intro tour in the toolbar above: Help > User Interface Tour. > > I'll experiment and update the issue report with what I find. > > On 6 December 2015 at 01:48, David Banas wrote: > >> Hi Sumit, >> >> Thanks for your reply! >> >> I tried putting ?:set -Wall? near the top of my first code cell >> (immediately after all my {-# LANGUAGE ? #-} pragmas), but that hasn?t >> resulted in any extra output, compared to what I was seeing before. Do I >> need to enable something else, in order to have ?:set -Wall? take effect? >> >> Thanks, >> -db >> >> On Dec 5, 2015, at 8:54 AM, Sumit Sahrawat, Maths & Computing, IIT (BHU) < >> sumit.sahrawat.apm13 at iitbhu.ac.in> wrote: >> >> Using `:set -Wall` also has some issues, I've added them to the issue >> report on github: https://github.com/gibiansky/IHaskell/issues/610 >> >> We would need to conceal warnings from specific regions of code for it to >> work as expected. >> >> On 5 December 2015 at 22:03, Sumit Sahrawat, Maths & Computing, IIT (BHU) >> wrote: >> >>> Try :? >>> >>> On 5 December 2015 at 21:58, David Banas wrote: >>> >>>> Does anyone know how to turn on ?-Wall? in a IHaskell notebook? >>>> >>>> _______________________________________________ >>>> Haskell-Cafe mailing list >>>> Haskell-Cafe at haskell.org >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>>> >>> >>> >>> >>> -- >>> Regards >>> >>> Sumit Sahrawat >>> >> >> >> >> -- >> Regards >> >> Sumit Sahrawat >> >> >> > > > -- > Regards > > Sumit Sahrawat > > > -- Regards Sumit Sahrawat -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Sun Dec 6 02:58:25 2015 From: david.feuer at gmail.com (David Feuer) Date: Sat, 5 Dec 2015 21:58:25 -0500 Subject: [Haskell-cafe] Type family weirdness Message-ID: If I have {-# LANGUAGE PolyKinds, TypeFamilies #-} import Data.Type.Coercion type family X :: k and I want coercionXX :: Coercion X X, the obvious thing, coercionXX = Coercion, doesn't work: Couldn't match representation of type ?X? with that of ?X? NB: ?X? is a type function, and may not be injective Relevant role signatures: type role X nominal Relevant bindings include coercionXX :: Coercion X X (bound at Fold.hs:167:1) In the expression: Coercion In an equation for ?coercionXX?: coercionXX = Coercion However, if I write coercionXX = x where x = Coercion, that does work! What gives? From icfp.publicity at googlemail.com Sun Dec 6 03:40:24 2015 From: icfp.publicity at googlemail.com (Lindsey Kuper) Date: Sun, 06 Dec 2015 03:40:24 +0000 Subject: [Haskell-cafe] ICFP 2016 Call for Papers Message-ID: <94eb2c07edda382971052632808f@google.com>                               ICFP 2016 The 21st ACM SIGPLAN International Conference on Functional Programming                http://conf.researchr.org/home/icfp-2016                            Call for Papers Important dates --------------- Submissions due:    Wednesday, March 16 2016, 15:00 (UTC)                     https://icfp2016.hotcrp.com                     (in preparation as of December 1) Author response:    Monday, 2 May, 2016, 15:00 (UTC) -                     Thursday, 5 May, 2016, 15:00 (UTC) Notification:       Friday, 20 May, 2016 Final copy due:     TBA Early registration: TBA Conference:         Tuesday, 20 September -                     Thursday, 22 September, 2016 Scope ----- ICFP 2016 seeks original papers on the art and science of functional programming. Submissions are invited on all topics from principles to practice, from foundations to features, and from abstraction to application. The scope includes all languages that encourage functional programming, including both purely applicative and imperative languages, as well as languages with objects, concurrency, or parallelism. Topics of interest include (but are not limited to): - Language Design: concurrency, parallelism, and distribution;   modules; components and composition; metaprogramming; type systems;   interoperability; domain-specific languages; and relations to   imperative, object-oriented, or logic programming. - Implementation: abstract machines; virtual machines; interpretation;   compilation; compile-time and run-time optimization; garbage   collection and memory management; multi-threading; exploiting   parallel hardware; interfaces to foreign functions, services,   components, or low-level machine resources. - Software-Development Techniques: algorithms and data structures;   design patterns; specification; verification; validation; proof   assistants; debugging; testing; tracing; profiling. - Foundations: formal semantics; lambda calculus; rewriting; type   theory; monads; continuations; control; state; effects; program   verification; dependent types. - Analysis and Transformation: control-flow; data-flow; abstract   interpretation; partial evaluation; program calculation. - Applications: symbolic computing; formal-methods tools; artificial   intelligence; systems programming; distributed-systems and web   programming; hardware design; databases; XML processing; scientific   and numerical computing; graphical user interfaces; multimedia and   3D graphics programming; scripting; system administration; security. - Education: teaching introductory programming; parallel programming;   mathematical proof; algebra. - Functional Pearls: elegant, instructive, and fun essays on   functional programming. - Experience Reports: short papers that provide evidence that   functional programming really works or describe obstacles that have   kept it from working. If you are concerned about the appropriateness of some topic, do not hesitate to contact the program chair. Abbreviated instructions for authors ------------------------------------ - By Wednesday, March 16 2016, 15:00 (UTC), submit a full paper of at   most 12 pages (6 pages for an Experience Report), in standard   SIGPLAN conference format, including figures but ***excluding   bibliography***. The deadlines will be strictly enforced and papers exceeding the page limits will be summarily rejected. ***ICFP 2016 will employ a lightweight double-blind reviewing process.*** To facilitate this, submitted papers must adhere to two rules:  1. ***author names and institutions must be omitted***, and  2. ***references to authors' own related work should be in the third     person*** (e.g., not "We build on our previous work ..." but     rather "We build on the work of ..."). The purpose of this process is to help the PC and external reviewers come to an initial judgement about the paper without bias, not to make it impossible for them to discover the authors if they were to try. Nothing should be done in the name of anonymity that weakens the submission or makes the job of reviewing the paper more difficult (e.g., important background references should not be omitted or anonymized). In addition, authors should feel free to disseminate their ideas or draft versions of their paper as they normally would. For instance, authors may post drafts of their papers on the web or give talks on their research ideas. We have put together a document answering frequently asked questions that should address many common concerns: http://conf.researchr.org/track/icfp-2016/icfp-2016-papers#Submission-and-Reviewing-FAQ - Authors have the option to attach supplementary material to a   submission, on the understanding that reviewers may choose not to   look at it. The material should be uploaded at submission time, as a   single pdf or a tarball, not via a URL. This supplementary material   may or may not be anonymized; if not anonymized, it will only be   revealed to reviewers after they have submitted their review of your   paper and learned your identity. - Each submission must adhere to SIGPLAN's republication policy, as   explained on the web at:   http://www.sigplan.org/Resources/Policies/Republication - Authors of resubmitted (but previously rejected) papers have the   option to attach an annotated copy of the reviews of their previous   submission(s), explaining how they have addressed these previous   reviews in the present submission. If a reviewer identifies   him/herself as a reviewer of this previous submission and wishes to   see how his/her comments have been addressed, the program chair will   communicate to this reviewer the annotated copy of his/her previous   review. Otherwise, no reviewer will read the annotated copies of the   previous reviews. Overall, a submission will be evaluated according to its relevance, correctness, significance, originality, and clarity. It should explain its contributions in both general and technical terms, clearly identifying what has been accomplished, explaining why it is significant, and comparing it with previous work. The technical content should be accessible to a broad audience. Functional Pearls and Experience Reports are separate categories of papers that need not report original research results and must be marked as such at the time of submission. Detailed guidelines on both categories are given below. Presentations will be videotaped and released online if the presenter consents. The proceedings will be freely available for download from the ACM Digital Library from at least one week before the start of the conference until two weeks after the conference. Formatting: Submissions must be in PDF format printable in black and white on US Letter sized paper and interpretable by Ghostscript. Papers must adhere to the standard SIGPLAN conference format: two columns, nine-point font on a ten-point baseline, with columns 20pc (3.33in) wide and 54pc (9in) tall, with a column gutter of 2pc (0.33in). A suitable document template for LaTeX is available at http://www.sigplan.org/Resources/Author/ Submission: Submissions will be accepted at https://icfp2016.hotcrp.com (in preparation as of December 1). Improved versions of a paper may be submitted at any point before the submission deadline using the same web interface. Author response: Authors will have a 72-hour period, starting at 15:00 UTC on Monday, 2 May, 2016, to read reviews and respond to them. ACM Author-Izer is a unique service that enables ACM authors to generate and post links on either their home page or institutional repository for visitors to download the definitive version of their articles from the ACM Digital Library at no charge. Downloads through Author-Izer links are captured in official ACM statistics, improving the accuracy of usage and impact measurements. Consistently linking the definitive version of ACM article should reduce user confusion over article versioning. After your article has been published and assigned to your ACM Author Profile page, please visit http://www.acm.org/publications/acm-author-izer-service to learn how to create your links for free downloads from the ACM DL. Publication date: The official publication date of accepted papers is the date the proceedings are made available in the ACM Digital Library. This date may be up to two weeks prior to the first day of the conference. The official publication date affects the deadline for any patent filings related to published work. Special categories of papers ---------------------------- In addition to research papers, ICFP solicits two kinds of papers that do not require original research contributions: Functional Pearls, which are full papers, and Experience Reports, which are limited to six pages. Authors submitting such papers may wish to consider the following advice. Functional Pearls ================= A Functional Pearl is an elegant essay about something related to functional programming. Examples include, but are not limited to: - a new and thought-provoking way of looking at an old idea - an instructive example of program calculation or proof - a nifty presentation of an old or new data structure - an interesting application of functional programming techniques - a novel use or exposition of functional programming in the classroom While pearls often demonstrate an idea through the development of a short program, there is no requirement or expectation that they do so. Thus, they encompass the notions of theoretical and educational pearls. Functional Pearls are valued as highly and judged as rigorously as ordinary papers, but using somewhat different criteria. In particular, a pearl is not required to report original research, but, it should be concise, instructive, and entertaining. Your pearl is likely to be rejected if your readers get bored, if the material gets too complicated, if too much specialized knowledge is needed, or if the writing is inelegant. The key to writing a good pearl is polishing. A submission you wish to have treated as a pearl must be marked as such on the submission web page, and should contain the words ``Functional Pearl'' somewhere in its title or subtitle. These steps will alert reviewers to use the appropriate evaluation criteria. Pearls will be combined with ordinary papers, however, for the purpose of computing the conference's acceptance rate. Experience Reports ================== The purpose of an Experience Report is to help create a body of published, refereed, citable evidence that functional programming really works -- or to describe what obstacles prevent it from working. Possible topics for an Experience Report include, but are not limited to: - insights gained from real-world projects using functional   programming - comparison of functional programming with conventional programming   in the context of an industrial project or a university curriculum - project-management, business, or legal issues encountered when using   functional programming in a real-world project - curricular issues encountered when using functional programming in   education - real-world constraints that created special challenges for an   implementation of a functional language or for functional   programming in general An Experience Report is distinguished from a normal ICFP paper by its title, by its length, and by the criteria used to evaluate it. - Both in the proceedings and in any citations, the title of each   accepted Experience Report must begin with the words ``Experience   Report'' followed by a colon. The acceptance rate for Experience   Reports will be computed and reported separately from the rate for   ordinary papers. - An Experience Report is at most six pages long. Each accepted   Experience Report will be presented at the conference, but depending   on the number of Experience Reports and regular papers accepted,   authors of Experience reports may be asked to give shorter talks. - Because the purpose of Experience Reports is to enable our community   to accumulate a body of evidence about the efficacy of functional   programming, an acceptable Experience Report need not add to the   body of knowledge of the functional-programming community by   presenting novel results or conclusions. It is sufficient if the   Report states a clear thesis and provides supporting evidence. The   thesis must be relevant to ICFP, but it need not be novel. The program committee will accept or reject Experience Reports based on whether they judge the evidence to be convincing. Anecdotal evidence will be acceptable provided it is well argued and the author explains what efforts were made to gather as much evidence as possible. Typically, more convincing evidence is obtained from papers which show how functional programming was used than from papers which only say that functional programming was used. The most convincing evidence often includes comparisons of situations before and after the introduction or discontinuation of functional programming. Evidence drawn from a single person's experience may be sufficient, but more weight will be given to evidence drawn from the experience of groups of people. An Experience Report should be short and to the point: make a claim about how well functional programming worked on your project and why, and produce evidence to substantiate your claim. If functional programming worked for you in the same ways it has worked for others, you need only to summarize the results?the main part of your paper should discuss how well it worked and in what context. Most readers will not want to know all the details of your project and its implementation, but please characterize your project and its context well enough so that readers can judge to what degree your experience is relevant to their own projects. Be especially careful to highlight any unusual aspects of your project. Also keep in mind that specifics about your project are more valuable than generalities about functional programming; for example, it is more valuable to say that your team delivered its software a month ahead of schedule than it is to say that functional programming made your team more productive. If your paper not only describes experience but also presents new technical results, or if your experience refutes cherished beliefs of the functional-programming community, you may be better off submitting it as a full paper, which will be judged by the usual criteria of novelty, originality, and relevance. If you are unsure in which category to submit, the program chair will be happy to help you decide. Organizers ---------- General Co-Chairs: Jacques Garrigue (Nagoya University) Gabriele Keller (University of New South Wales) Program Chair: Eijiro Sumii (Tohoku University) Program Committee: Koen Claessen (Chalmers University of Technology) Joshua Dunfield (University of British Columbia, Canada) Matthew Fluet (Rochester Institute of Technology) Nate Foster (Cornell University) Dan Grossman (University of Washington, USA) Jurriaan Hage (Utrecht University) Roman Leshchinskiy (Standard Chartered Bank) Keisuke Nakano (The University of Electro-Communications) Aleksandar Nanevski (IMDEA Software Institute) Scott Owens (University of Kent) Sungwoo Park (Pohang University of Science and Technology) Amr Sabry (Indiana University) Tom Schrijvers (KU Leuven) Olin Shivers (Northeastern University) Walid Taha (Halmstad University) Dimitrios Vytiniotis (Microsoft Research, Cambridge) David Walker (Princeton University) Nobuko Yoshida (Imperial College London, UK) External Review Committee to be announced. -------------- next part -------------- An HTML attachment was scrubbed... URL: From eir at cis.upenn.edu Sun Dec 6 04:51:22 2015 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Sat, 5 Dec 2015 23:51:22 -0500 Subject: [Haskell-cafe] Type family weirdness In-Reply-To: References: Message-ID: <919C1831-3575-4443-A92B-A3D673791FB2@cis.upenn.edu> Looks like a bug. I think the `coercionXX = Coercion` should work. Richard On Dec 5, 2015, at 9:58 PM, David Feuer wrote: > If I have > > {-# LANGUAGE PolyKinds, TypeFamilies #-} > import Data.Type.Coercion > > type family X :: k > > and I want > > coercionXX :: Coercion X X, > > the obvious thing, > > coercionXX = Coercion, > > doesn't work: > > Couldn't match representation of type ?X? with that of ?X? > NB: ?X? is a type function, and may not be injective > Relevant role signatures: type role X nominal > Relevant bindings include > coercionXX :: Coercion X X (bound at Fold.hs:167:1) > In the expression: Coercion > In an equation for ?coercionXX?: coercionXX = Coercion > > However, if I write > > coercionXX = x where x = Coercion, > > that does work! What gives? > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > From david.feuer at gmail.com Sun Dec 6 05:14:12 2015 From: david.feuer at gmail.com (David Feuer) Date: Sun, 6 Dec 2015 00:14:12 -0500 Subject: [Haskell-cafe] Type family weirdness In-Reply-To: <919C1831-3575-4443-A92B-A3D673791FB2@cis.upenn.edu> References: <919C1831-3575-4443-A92B-A3D673791FB2@cis.upenn.edu> Message-ID: In case this helps any, coercionXX = c where c :: x ~ X => Coercion x x c = Coercion works too (with or without a top-level type signature), but coercionXX = c where c :: Coercion X X c = Coercion gives the same error as before. On Sat, Dec 5, 2015 at 11:51 PM, Richard Eisenberg wrote: > Looks like a bug. I think the `coercionXX = Coercion` should work. > > Richard > > On Dec 5, 2015, at 9:58 PM, David Feuer wrote: > >> If I have >> >> {-# LANGUAGE PolyKinds, TypeFamilies #-} >> import Data.Type.Coercion >> >> type family X :: k >> >> and I want >> >> coercionXX :: Coercion X X, >> >> the obvious thing, >> >> coercionXX = Coercion, >> >> doesn't work: >> >> Couldn't match representation of type ?X? with that of ?X? >> NB: ?X? is a type function, and may not be injective >> Relevant role signatures: type role X nominal >> Relevant bindings include >> coercionXX :: Coercion X X (bound at Fold.hs:167:1) >> In the expression: Coercion >> In an equation for ?coercionXX?: coercionXX = Coercion >> >> However, if I write >> >> coercionXX = x where x = Coercion, >> >> that does work! What gives? >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> > From hjgtuyl at chello.nl Sun Dec 6 17:19:15 2015 From: hjgtuyl at chello.nl (Henk-Jan van Tuyl) Date: Sun, 06 Dec 2015 18:19:15 +0100 Subject: [Haskell-cafe] [Haskell-beginners] DOOM rewritten in the Haskell programming language. In-Reply-To: <451608938.16111539.1449415275423.JavaMail.yahoo@mail.yahoo.com> References: <451608938.16111539.1449415275423.JavaMail.yahoo.ref@mail.yahoo.com> <451608938.16111539.1449415275423.JavaMail.yahoo@mail.yahoo.com> Message-ID: On Sun, 06 Dec 2015 16:21:15 +0100, David Blubaugh wrote: > TO ALL, > Hello My name is David Allen Blubaugh. I am currently considering > starting a kick-starter project in redeveloping the DOOM source code > with the Haskell Programming language using the power of > functional-oriented programming...... > I know that John Carmack was interested in the Haskell programming > language and had even recreated wolfenstein 3D using the Haskell > programming language. Does anybody have a copy of John Carmack's > recreation of wolfenstein 3D using haskell ??? Also would anybody enjoy > working with this project ??? What benefits would DOOM have enjoyed had > ID software created the DOOM source code in 1993 with Haskell or some > other functional-oriented programming language instead of C/assembly > programming languages ??? Thanks, > David Allen BlubaughElectrical EngineerATR Associate I don't know about his source code, but the Games page[0] lists: - hadoom A clone of Doom, using reactive-banana, GTK, and the "diagrams" library. https://github.com/ocharles/hadoom - Frag A 3D first person shooting game https://wiki.haskell.org/Frag These might be helpful. Advantages, when developing software in Haskell, are faster development with fewer bugs. Disadvantages are: the compiled programs are slower then when written in C and the garbage collection of a Haskell program (when compiled with GHC) might sometimes cause delays in screen updates. Regards, Henk-Jan van Tuyl [0] https://wiki.haskell.org/Games -- Folding at home What if you could share your unused computer power to help find a cure? In just 5 minutes you can join the world's biggest networked computer and get us closer sooner. Watch the video. http://folding.stanford.edu/ http://Van.Tuyl.eu/ http://members.chello.nl/hjgtuyl/tourdemonad.html Haskell programming -- From benl at ouroborus.net Sun Dec 6 23:30:18 2015 From: benl at ouroborus.net (Ben Lippmeier) Date: Mon, 7 Dec 2015 10:30:18 +1100 Subject: [Haskell-cafe] [Haskell] [Haskell-beginners] DOOM rewritten in the Haskell programming language. In-Reply-To: References: <451608938.16111539.1449415275423.JavaMail.yahoo.ref@mail.yahoo.com> <451608938.16111539.1449415275423.JavaMail.yahoo@mail.yahoo.com> Message-ID: <81A3A565-A015-4A1D-B924-4C1DD12A27AE@ouroborus.net> > On 7 Dec 2015, at 4:19 am, Henk-Jan van Tuyl wrote: > > On Sun, 06 Dec 2015 16:21:15 +0100, David Blubaugh wrote: > >> TO ALL, Hello My name is David Allen Blubaugh. I am currently considering starting a kick-starter project in redeveloping the DOOM source code with the Haskell Programming language using the power of functional-oriented programming...... >> I know that John Carmack was interested in the Haskell programming language and had even recreated wolfenstein 3D using the Haskell programming language. Does anybody have a copy of John Carmack's recreation of wolfenstein 3D using haskell ??? Also would anybody enjoy working with this project ??? What benefits would DOOM have enjoyed had ID software created the DOOM source code in 1993 with Haskell or some other functional-oriented programming language instead of C/assembly programming languages ??? Thanks, >> David Allen BlubaughElectrical EngineerATR Associate > LambdaCube 3D Quake level renderer: https://lambdacube3d.wordpress.com/2012/09/08/some-eye-candy/ Ben. -------------- next part -------------- An HTML attachment was scrubbed... URL: From icfp.publicity at googlemail.com Mon Dec 7 08:48:06 2015 From: icfp.publicity at googlemail.com (Lindsey Kuper) Date: Mon, 7 Dec 2015 00:48:06 -0800 Subject: [Haskell-cafe] ICFP 2016 Call for Papers In-Reply-To: <94eb2c07edda382971052632808f@google.com> References: <94eb2c07edda382971052632808f@google.com> Message-ID: [My apologies for the garbled text in a previous version of this email. -- Lindsey] ICFP 2016 The 21st ACM SIGPLAN International Conference on Functional Programming http://conf.researchr.org/home/icfp-2016 Call for Papers Important dates --------------- Submissions due: Wednesday, March 16 2016, 15:00 (UTC) https://icfp2016.hotcrp.com (in preparation as of December 1) Author response: Monday, 2 May, 2016, 15:00 (UTC) - Thursday, 5 May, 2016, 15:00 (UTC) Notification: Friday, 20 May, 2016 Final copy due: TBA Early registration: TBA Conference: Tuesday, 20 September - Thursday, 22 September, 2016 Scope ----- ICFP 2016 seeks original papers on the art and science of functional programming. Submissions are invited on all topics from principles to practice, from foundations to features, and from abstraction to application. The scope includes all languages that encourage functional programming, including both purely applicative and imperative languages, as well as languages with objects, concurrency, or parallelism. Topics of interest include (but are not limited to): - Language Design: concurrency, parallelism, and distribution; modules; components and composition; metaprogramming; type systems; interoperability; domain-specific languages; and relations to imperative, object-oriented, or logic programming. - Implementation: abstract machines; virtual machines; interpretation; compilation; compile-time and run-time optimization; garbage collection and memory management; multi-threading; exploiting parallel hardware; interfaces to foreign functions, services, components, or low-level machine resources. - Software-Development Techniques: algorithms and data structures; design patterns; specification; verification; validation; proof assistants; debugging; testing; tracing; profiling. - Foundations: formal semantics; lambda calculus; rewriting; type theory; monads; continuations; control; state; effects; program verification; dependent types. - Analysis and Transformation: control-flow; data-flow; abstract interpretation; partial evaluation; program calculation. - Applications: symbolic computing; formal-methods tools; artificial intelligence; systems programming; distributed-systems and web programming; hardware design; databases; XML processing; scientific and numerical computing; graphical user interfaces; multimedia and 3D graphics programming; scripting; system administration; security. - Education: teaching introductory programming; parallel programming; mathematical proof; algebra. - Functional Pearls: elegant, instructive, and fun essays on functional programming. - Experience Reports: short papers that provide evidence that functional programming really works or describe obstacles that have kept it from working. If you are concerned about the appropriateness of some topic, do not hesitate to contact the program chair. Abbreviated instructions for authors ------------------------------------ - By Wednesday, March 16 2016, 15:00 (UTC), submit a full paper of at most 12 pages (6 pages for an Experience Report), in standard SIGPLAN conference format, including figures but ***excluding bibliography***. The deadlines will be strictly enforced and papers exceeding the page limits will be summarily rejected. ***ICFP 2016 will employ a lightweight double-blind reviewing process.*** To facilitate this, submitted papers must adhere to two rules: 1. ***author names and institutions must be omitted***, and 2. ***references to authors' own related work should be in the third person*** (e.g., not "We build on our previous work ..." but rather "We build on the work of ..."). The purpose of this process is to help the PC and external reviewers come to an initial judgement about the paper without bias, not to make it impossible for them to discover the authors if they were to try. Nothing should be done in the name of anonymity that weakens the submission or makes the job of reviewing the paper more difficult (e.g., important background references should not be omitted or anonymized). In addition, authors should feel free to disseminate their ideas or draft versions of their paper as they normally would. For instance, authors may post drafts of their papers on the web or give talks on their research ideas. We have put together a document answering frequently asked questions that should address many common concerns: http://conf.researchr.org/track/icfp-2016/icfp-2016-papers#Submission-and-Reviewing-FAQ - Authors have the option to attach supplementary material to a submission, on the understanding that reviewers may choose not to look at it. The material should be uploaded at submission time, as a single pdf or a tarball, not via a URL. This supplementary material may or may not be anonymized; if not anonymized, it will only be revealed to reviewers after they have submitted their review of your paper and learned your identity. - Each submission must adhere to SIGPLAN's republication policy, as explained on the web at: http://www.sigplan.org/Resources/Policies/Republication - Authors of resubmitted (but previously rejected) papers have the option to attach an annotated copy of the reviews of their previous submission(s), explaining how they have addressed these previous reviews in the present submission. If a reviewer identifies him/herself as a reviewer of this previous submission and wishes to see how his/her comments have been addressed, the program chair will communicate to this reviewer the annotated copy of his/her previous review. Otherwise, no reviewer will read the annotated copies of the previous reviews. Overall, a submission will be evaluated according to its relevance, correctness, significance, originality, and clarity. It should explain its contributions in both general and technical terms, clearly identifying what has been accomplished, explaining why it is significant, and comparing it with previous work. The technical content should be accessible to a broad audience. Functional Pearls and Experience Reports are separate categories of papers that need not report original research results and must be marked as such at the time of submission. Detailed guidelines on both categories are given below. Presentations will be videotaped and released online if the presenter consents. The proceedings will be freely available for download from the ACM Digital Library from at least one week before the start of the conference until two weeks after the conference. Formatting: Submissions must be in PDF format printable in black and white on US Letter sized paper and interpretable by Ghostscript. Papers must adhere to the standard SIGPLAN conference format: two columns, nine-point font on a ten-point baseline, with columns 20pc (3.33in) wide and 54pc (9in) tall, with a column gutter of 2pc (0.33in). A suitable document template for LaTeX is available at http://www.sigplan.org/Resources/Author/ Submission: Submissions will be accepted at https://icfp2016.hotcrp.com (in preparation as of December 1). Improved versions of a paper may be submitted at any point before the submission deadline using the same web interface. Author response: Authors will have a 72-hour period, starting at 15:00 UTC on Monday, 2 May, 2016, to read reviews and respond to them. ACM Author-Izer is a unique service that enables ACM authors to generate and post links on either their home page or institutional repository for visitors to download the definitive version of their articles from the ACM Digital Library at no charge. Downloads through Author-Izer links are captured in official ACM statistics, improving the accuracy of usage and impact measurements. Consistently linking the definitive version of ACM article should reduce user confusion over article versioning. After your article has been published and assigned to your ACM Author Profile page, please visit http://www.acm.org/publications/acm-author-izer-service to learn how to create your links for free downloads from the ACM DL. Publication date: The official publication date of accepted papers is the date the proceedings are made available in the ACM Digital Library. This date may be up to two weeks prior to the first day of the conference. The official publication date affects the deadline for any patent filings related to published work. Special categories of papers ---------------------------- In addition to research papers, ICFP solicits two kinds of papers that do not require original research contributions: Functional Pearls, which are full papers, and Experience Reports, which are limited to six pages. Authors submitting such papers may wish to consider the following advice. Functional Pearls ================= A Functional Pearl is an elegant essay about something related to functional programming. Examples include, but are not limited to: - a new and thought-provoking way of looking at an old idea - an instructive example of program calculation or proof - a nifty presentation of an old or new data structure - an interesting application of functional programming techniques - a novel use or exposition of functional programming in the classroom While pearls often demonstrate an idea through the development of a short program, there is no requirement or expectation that they do so. Thus, they encompass the notions of theoretical and educational pearls. Functional Pearls are valued as highly and judged as rigorously as ordinary papers, but using somewhat different criteria. In particular, a pearl is not required to report original research, but, it should be concise, instructive, and entertaining. Your pearl is likely to be rejected if your readers get bored, if the material gets too complicated, if too much specialized knowledge is needed, or if the writing is inelegant. The key to writing a good pearl is polishing. A submission you wish to have treated as a pearl must be marked as such on the submission web page, and should contain the words ``Functional Pearl'' somewhere in its title or subtitle. These steps will alert reviewers to use the appropriate evaluation criteria. Pearls will be combined with ordinary papers, however, for the purpose of computing the conference's acceptance rate. Experience Reports ================== The purpose of an Experience Report is to help create a body of published, refereed, citable evidence that functional programming really works -- or to describe what obstacles prevent it from working. Possible topics for an Experience Report include, but are not limited to: - insights gained from real-world projects using functional programming - comparison of functional programming with conventional programming in the context of an industrial project or a university curriculum - project-management, business, or legal issues encountered when using functional programming in a real-world project - curricular issues encountered when using functional programming in education - real-world constraints that created special challenges for an implementation of a functional language or for functional programming in general An Experience Report is distinguished from a normal ICFP paper by its title, by its length, and by the criteria used to evaluate it. - Both in the proceedings and in any citations, the title of each accepted Experience Report must begin with the words ``Experience Report'' followed by a colon. The acceptance rate for Experience Reports will be computed and reported separately from the rate for ordinary papers. - An Experience Report is at most six pages long. Each accepted Experience Report will be presented at the conference, but depending on the number of Experience Reports and regular papers accepted, authors of Experience reports may be asked to give shorter talks. - Because the purpose of Experience Reports is to enable our community to accumulate a body of evidence about the efficacy of functional programming, an acceptable Experience Report need not add to the body of knowledge of the functional-programming community by presenting novel results or conclusions. It is sufficient if the Report states a clear thesis and provides supporting evidence. The thesis must be relevant to ICFP, but it need not be novel. The program committee will accept or reject Experience Reports based on whether they judge the evidence to be convincing. Anecdotal evidence will be acceptable provided it is well argued and the author explains what efforts were made to gather as much evidence as possible. Typically, more convincing evidence is obtained from papers which show how functional programming was used than from papers which only say that functional programming was used. The most convincing evidence often includes comparisons of situations before and after the introduction or discontinuation of functional programming. Evidence drawn from a single person's experience may be sufficient, but more weight will be given to evidence drawn from the experience of groups of people. An Experience Report should be short and to the point: make a claim about how well functional programming worked on your project and why, and produce evidence to substantiate your claim. If functional programming worked for you in the same ways it has worked for others, you need only to summarize the results?the main part of your paper should discuss how well it worked and in what context. Most readers will not want to know all the details of your project and its implementation, but please characterize your project and its context well enough so that readers can judge to what degree your experience is relevant to their own projects. Be especially careful to highlight any unusual aspects of your project. Also keep in mind that specifics about your project are more valuable than generalities about functional programming; for example, it is more valuable to say that your team delivered its software a month ahead of schedule than it is to say that functional programming made your team more productive. If your paper not only describes experience but also presents new technical results, or if your experience refutes cherished beliefs of the functional-programming community, you may be better off submitting it as a full paper, which will be judged by the usual criteria of novelty, originality, and relevance. If you are unsure in which category to submit, the program chair will be happy to help you decide. Organizers ---------- General Co-Chairs: Jacques Garrigue (Nagoya University) Gabriele Keller (University of New South Wales) Program Chair: Eijiro Sumii (Tohoku University) Program Committee: Koen Claessen (Chalmers University of Technology) Joshua Dunfield (University of British Columbia, Canada) Matthew Fluet (Rochester Institute of Technology) Nate Foster (Cornell University) Dan Grossman (University of Washington, USA) Jurriaan Hage (Utrecht University) Roman Leshchinskiy (Standard Chartered Bank) Keisuke Nakano (The University of Electro-Communications) Aleksandar Nanevski (IMDEA Software Institute) Scott Owens (University of Kent) Sungwoo Park (Pohang University of Science and Technology) Amr Sabry (Indiana University) Tom Schrijvers (KU Leuven) Olin Shivers (Northeastern University) Walid Taha (Halmstad University) Dimitrios Vytiniotis (Microsoft Research, Cambridge) David Walker (Princeton University) Nobuko Yoshida (Imperial College London, UK) External Review Committee to be announced. From csaba.hruska at gmail.com Mon Dec 7 09:49:04 2015 From: csaba.hruska at gmail.com (Csaba Hruska) Date: Mon, 7 Dec 2015 10:49:04 +0100 Subject: [Haskell-cafe] [Haskell] [Haskell-beginners] DOOM rewritten in the Haskell programming language. In-Reply-To: <81A3A565-A015-4A1D-B924-4C1DD12A27AE@ouroborus.net> References: <451608938.16111539.1449415275423.JavaMail.yahoo.ref@mail.yahoo.com> <451608938.16111539.1449415275423.JavaMail.yahoo@mail.yahoo.com> <81A3A565-A015-4A1D-B924-4C1DD12A27AE@ouroborus.net> Message-ID: Here is the Quake 3 renderer code (pure function run on GPU) for: - LambdaCube 3D : https://github.com/csabahruska/quake3 - GPipe2 : https://github.com/csabahruska/gpipe-quake3 Both must work with cabal install. Csaba On Mon, Dec 7, 2015 at 12:30 AM, Ben Lippmeier wrote: > > On 7 Dec 2015, at 4:19 am, Henk-Jan van Tuyl wrote: > > On Sun, 06 Dec 2015 16:21:15 +0100, David Blubaugh < > davidblubaugh2000 at yahoo.com> wrote: > > TO ALL, Hello My name is David Allen Blubaugh. I am currently > considering starting a kick-starter project in redeveloping the DOOM source > code with the Haskell Programming language using the power of > functional-oriented programming...... > I know that John Carmack was interested in the Haskell programming > language and had even recreated wolfenstein 3D using the Haskell > programming language. Does anybody have a copy of John Carmack's recreation > of wolfenstein 3D using haskell ??? Also would anybody enjoy working with > this project ??? What benefits would DOOM have enjoyed had ID software > created the DOOM source code in 1993 with Haskell or some other > functional-oriented programming language instead of C/assembly programming > languages ??? Thanks, > David Allen BlubaughElectrical EngineerATR Associate > > > > LambdaCube 3D Quake level renderer: > > https://lambdacube3d.wordpress.com/2012/09/08/some-eye-candy/ > > > Ben. > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ollie at ocharles.org.uk Mon Dec 7 10:49:48 2015 From: ollie at ocharles.org.uk (Oliver Charles) Date: Mon, 07 Dec 2015 10:49:48 +0000 Subject: [Haskell-cafe] [Haskell-beginners] DOOM rewritten in the Haskell programming language. In-Reply-To: References: <451608938.16111539.1449415275423.JavaMail.yahoo.ref@mail.yahoo.com> <451608938.16111539.1449415275423.JavaMail.yahoo@mail.yahoo.com> Message-ID: On Sun, Dec 6, 2015 at 5:19 PM Henk-Jan van Tuyl wrote: > On Sun, 06 Dec 2015 16:21:15 +0100, David Blubaugh > wrote: > > > TO ALL, > > Hello My name is David Allen Blubaugh. I am currently considering > > starting a kick-starter project in redeveloping the DOOM source code > > with the Haskell Programming language using the power of > > functional-oriented programming...... > > I know that John Carmack was interested in the Haskell programming > > language and had even recreated wolfenstein 3D using the Haskell > > programming language. Does anybody have a copy of John Carmack's > > recreation of wolfenstein 3D using haskell ??? Also would anybody enjoy > > working with this project ??? What benefits would DOOM have enjoyed had > > ID software created the DOOM source code in 1993 with Haskell or some > > other functional-oriented programming language instead of C/assembly > > programming languages ??? Thanks, > > David Allen BlubaughElectrical EngineerATR Associate > > I don't know about his source code, but the Games page[0] lists: > - hadoom > A clone of Doom, using reactive-banana, GTK, and the "diagrams" > library. > https://github.com/ocharles/hadoom Possibly worth noting that hadoom is not a source-port of Doom - it's inspired by Doom's approach to level editing (2.5D), but beyond that there isn't much cross over. For example, I use full triangulation for rendering via OpenGL, rather than building my own rendering engine. The level format is also different from WAD. Ollie -------------- next part -------------- An HTML attachment was scrubbed... URL: From alexander at plaimi.net Mon Dec 7 10:54:45 2015 From: alexander at plaimi.net (Alexander Berntsen) Date: Mon, 7 Dec 2015 11:54:45 +0100 Subject: [Haskell-cafe] [Haskell-beginners] DOOM rewritten in the Haskell programming language. In-Reply-To: <451608938.16111539.1449415275423.JavaMail.yahoo@mail.yahoo.com> References: <451608938.16111539.1449415275423.JavaMail.yahoo.ref@mail.yahoo.com> <451608938.16111539.1449415275423.JavaMail.yahoo@mail.yahoo.com> Message-ID: <56656575.8090109@plaimi.net> -----BEGIN PGP SIGNED MESSAGE----- Hash: SHA512 David, I think it would be more valuable to make a DOOM-like game than to remake DOOM. Especially if you are going to aim for funding. The free software community has had this problem for years, where we point to remakes of old games as evidence to viability. It isn't. Nobody will be swayed by Haskell DOOM. (Although I would, personally, think it interesting.) Good luck with your project. - -- Alexander alexander at plaimi.net https://secure.plaimi.net/~alexander -----BEGIN PGP SIGNATURE----- Version: GnuPG v2 iQIcBAEBCgAGBQJWZWV0AAoJENQqWdRUGk8B0bMQAKu/4hBeS7Iz23IMIatrc5Jd hkWm/bG8FRCtiLyETiH9NtUL5RPtmS+s3+o05h6fZZ1VFFfzucygsmOTw27kWApc ZpZiypv22y7uJsrbyxFgXVp2w6vfp6rrdA+vRSOUp/dmJ+vnn7jVeGUInnlAKX50 WAsEUPx0q4IhGnF/2O3kBuKw/baGvp2kne2IjrgdAJ5qptVEvVoAEpIG3WveTnlP LQMBwTLrB+TkdTIZWTYUT/e8MYZorU5x6LN+GtKuO28PEEG0jS2IgfNeUnzZjalF p37Av84UCiIhTQD3LV6Eq1sQThQMVMm/S+qkqZrNL3I/+TbS3Ztf6q7u7zDRCsnr vum2JR0f9vtGfpd5j3hGVXjQTd0jU3uFdY1kHM0ISGTSKYrOGYs4qsCL/VxPubo8 Lh7YfCltXY+LQkz/Q2FElcd9eM9xYWSOBhPhiudXZ3f+PnkBNRwH03eWk/LHgmhB MByAdf2WCAU4DK7xpJKkCVsyOlsC17t8CtKDIfnt/RkPUr8108i6KOh6zvDR94Du lJyQWuCbL7FFb7uXVO7cKTeWJFejd/K5GrQBTBpVEy3xA15c8Kj+9ALWrdJAlion ktS85eEcp/3IzrNpPby8lhjJvujwzbzny+a9Jdn8ZcybBwpF3+IRSARnb7lJ4Yba Ca972BfXJnFZXiYARfov =mGnp -----END PGP SIGNATURE----- From sumit.sahrawat.apm13 at iitbhu.ac.in Mon Dec 7 11:04:56 2015 From: sumit.sahrawat.apm13 at iitbhu.ac.in (Sumit Sahrawat, Maths & Computing, IIT (BHU)) Date: Mon, 7 Dec 2015 16:34:56 +0530 Subject: [Haskell-cafe] [Haskell-beginners] DOOM rewritten in the Haskell programming language. In-Reply-To: <56656575.8090109@plaimi.net> References: <451608938.16111539.1449415275423.JavaMail.yahoo.ref@mail.yahoo.com> <451608938.16111539.1449415275423.JavaMail.yahoo@mail.yahoo.com> <56656575.8090109@plaimi.net> Message-ID: I'm interested in game development, and would be willing to learn and contribute if the project kicks off. Just showing my support, good luck with the project. On 7 December 2015 at 16:24, Alexander Berntsen wrote: > -----BEGIN PGP SIGNED MESSAGE----- > Hash: SHA512 > > David, > > I think it would be more valuable to make a DOOM-like game than to > remake DOOM. Especially if you are going to aim for funding. The free > software community has had this problem for years, where we point to > remakes of old games as evidence to viability. It isn't. Nobody will > be swayed by Haskell DOOM. (Although I would, personally, think it > interesting.) > > Good luck with your project. > - -- > Alexander > alexander at plaimi.net > https://secure.plaimi.net/~alexander > -----BEGIN PGP SIGNATURE----- > Version: GnuPG v2 > > iQIcBAEBCgAGBQJWZWV0AAoJENQqWdRUGk8B0bMQAKu/4hBeS7Iz23IMIatrc5Jd > hkWm/bG8FRCtiLyETiH9NtUL5RPtmS+s3+o05h6fZZ1VFFfzucygsmOTw27kWApc > ZpZiypv22y7uJsrbyxFgXVp2w6vfp6rrdA+vRSOUp/dmJ+vnn7jVeGUInnlAKX50 > WAsEUPx0q4IhGnF/2O3kBuKw/baGvp2kne2IjrgdAJ5qptVEvVoAEpIG3WveTnlP > LQMBwTLrB+TkdTIZWTYUT/e8MYZorU5x6LN+GtKuO28PEEG0jS2IgfNeUnzZjalF > p37Av84UCiIhTQD3LV6Eq1sQThQMVMm/S+qkqZrNL3I/+TbS3Ztf6q7u7zDRCsnr > vum2JR0f9vtGfpd5j3hGVXjQTd0jU3uFdY1kHM0ISGTSKYrOGYs4qsCL/VxPubo8 > Lh7YfCltXY+LQkz/Q2FElcd9eM9xYWSOBhPhiudXZ3f+PnkBNRwH03eWk/LHgmhB > MByAdf2WCAU4DK7xpJKkCVsyOlsC17t8CtKDIfnt/RkPUr8108i6KOh6zvDR94Du > lJyQWuCbL7FFb7uXVO7cKTeWJFejd/K5GrQBTBpVEy3xA15c8Kj+9ALWrdJAlion > ktS85eEcp/3IzrNpPby8lhjJvujwzbzny+a9Jdn8ZcybBwpF3+IRSARnb7lJ4Yba > Ca972BfXJnFZXiYARfov > =mGnp > -----END PGP SIGNATURE----- > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > -- Regards Sumit Sahrawat -------------- next part -------------- An HTML attachment was scrubbed... URL: From sean at functionaljobs.com Mon Dec 7 17:00:02 2015 From: sean at functionaljobs.com (Functional Jobs) Date: Mon, 7 Dec 2015 12:00:02 -0500 Subject: [Haskell-cafe] New Functional Programming Job Opportunities Message-ID: <5665bb5892065@functionaljobs.com> Here are some functional programming job opportunities that were posted recently: Haskell Engineer at Wagon https://functionaljobs.com/jobs/8868-haskell-engineer-at-wagon Cheers, Sean Murphy FunctionalJobs.com From plredmond at gmail.com Mon Dec 7 18:30:23 2015 From: plredmond at gmail.com (Patrick Redmond) Date: Mon, 7 Dec 2015 10:30:23 -0800 Subject: [Haskell-cafe] [Haskell] [Haskell-beginners] DOOM rewritten in the Haskell programming language. In-Reply-To: References: <451608938.16111539.1449415275423.JavaMail.yahoo.ref@mail.yahoo.com> <451608938.16111539.1449415275423.JavaMail.yahoo@mail.yahoo.com> <56656575.8090109@plaimi.net> Message-ID: I'd also like to show support and participate in building this out if work is needed. Contact me when/if that happens! On Monday, December 7, 2015, Sumit Sahrawat, Maths & Computing, IIT (BHU) < sumit.sahrawat.apm13 at iitbhu.ac.in> wrote: > I'm interested in game development, and would be willing to learn and > contribute if the project kicks off. > > Just showing my support, good luck with the project. > > On 7 December 2015 at 16:24, Alexander Berntsen > wrote: > >> -----BEGIN PGP SIGNED MESSAGE----- >> Hash: SHA512 >> >> David, >> >> I think it would be more valuable to make a DOOM-like game than to >> remake DOOM. Especially if you are going to aim for funding. The free >> software community has had this problem for years, where we point to >> remakes of old games as evidence to viability. It isn't. Nobody will >> be swayed by Haskell DOOM. (Although I would, personally, think it >> interesting.) >> >> Good luck with your project. >> - -- >> Alexander >> alexander at plaimi.net >> >> https://secure.plaimi.net/~alexander >> -----BEGIN PGP SIGNATURE----- >> Version: GnuPG v2 >> >> iQIcBAEBCgAGBQJWZWV0AAoJENQqWdRUGk8B0bMQAKu/4hBeS7Iz23IMIatrc5Jd >> hkWm/bG8FRCtiLyETiH9NtUL5RPtmS+s3+o05h6fZZ1VFFfzucygsmOTw27kWApc >> ZpZiypv22y7uJsrbyxFgXVp2w6vfp6rrdA+vRSOUp/dmJ+vnn7jVeGUInnlAKX50 >> WAsEUPx0q4IhGnF/2O3kBuKw/baGvp2kne2IjrgdAJ5qptVEvVoAEpIG3WveTnlP >> LQMBwTLrB+TkdTIZWTYUT/e8MYZorU5x6LN+GtKuO28PEEG0jS2IgfNeUnzZjalF >> p37Av84UCiIhTQD3LV6Eq1sQThQMVMm/S+qkqZrNL3I/+TbS3Ztf6q7u7zDRCsnr >> vum2JR0f9vtGfpd5j3hGVXjQTd0jU3uFdY1kHM0ISGTSKYrOGYs4qsCL/VxPubo8 >> Lh7YfCltXY+LQkz/Q2FElcd9eM9xYWSOBhPhiudXZ3f+PnkBNRwH03eWk/LHgmhB >> MByAdf2WCAU4DK7xpJKkCVsyOlsC17t8CtKDIfnt/RkPUr8108i6KOh6zvDR94Du >> lJyQWuCbL7FFb7uXVO7cKTeWJFejd/K5GrQBTBpVEy3xA15c8Kj+9ALWrdJAlion >> ktS85eEcp/3IzrNpPby8lhjJvujwzbzny+a9Jdn8ZcybBwpF3+IRSARnb7lJ4Yba >> Ca972BfXJnFZXiYARfov >> =mGnp >> -----END PGP SIGNATURE----- >> _______________________________________________ >> Beginners mailing list >> Beginners at haskell.org >> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >> > > > > -- > Regards > > Sumit Sahrawat > -------------- next part -------------- An HTML attachment was scrubbed... URL: From lemming at henning-thielemann.de Mon Dec 7 18:34:03 2015 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Mon, 7 Dec 2015 19:34:03 +0100 (CET) Subject: [Haskell-cafe] [Haskell] [Haskell-beginners] DOOM rewritten in the Haskell programming language. In-Reply-To: References: <451608938.16111539.1449415275423.JavaMail.yahoo.ref@mail.yahoo.com> <451608938.16111539.1449415275423.JavaMail.yahoo@mail.yahoo.com> <56656575.8090109@plaimi.net> Message-ID: On Mon, 7 Dec 2015, Patrick Redmond wrote: > I'd also like to show support and participate in building this out if work is needed. Contact me when/if that happens! haskell at haskell.org is an announcement list. Please continue discussion in haskell-cafe etc. From aeyakovenko at gmail.com Mon Dec 7 23:53:08 2015 From: aeyakovenko at gmail.com (Anatoly Yakovenko) Date: Mon, 07 Dec 2015 23:53:08 +0000 Subject: [Haskell-cafe] haddoc "modules on this system" index Message-ID: I have a bunch of dead links in file:///Users/anatolyy/Library/Haskell/share/doc/index.html like this one: file:///Users/anatolyy/Library/Haskell/ghc-7.8.3-x86_64/lib/blaze-builder-0.4.0.1/doc/html/Blaze-ByteString-Builder.html which should really be this one: file:///Users/anatolyy/Library/Haskell/ghc-7.10.1-x86_64/lib/blaze-builder-0.4.0.1/doc/html/Blaze-ByteString-Builder.html is there a way to regenerate the index from the currently installed docs? Anatoly -------------- next part -------------- An HTML attachment was scrubbed... URL: From trebla at vex.net Tue Dec 8 00:48:04 2015 From: trebla at vex.net (Albert Y. C. Lai) Date: Mon, 7 Dec 2015 19:48:04 -0500 Subject: [Haskell-cafe] haddoc "modules on this system" index In-Reply-To: References: Message-ID: <566628C4.6080200@vex.net> On 2015-12-07 06:53 PM, Anatoly Yakovenko wrote: > I have a bunch of dead links in > > file:///Users/anatolyy/Library/Haskell/share/doc/index.html > is there a way to regenerate the index from the currently installed docs? The index is rebuilt whenever you "cabal install --user --enable-documentation" some library. (--user is the default. --enable-documentation can be permanently set in $HOME/.cabal/config, is it the same path on Mac?) I made a dummy library package so I can reinstall it to force-refresh the index whenever I feel like to. From aeyakovenko at gmail.com Tue Dec 8 04:57:31 2015 From: aeyakovenko at gmail.com (Anatoly Yakovenko) Date: Tue, 08 Dec 2015 04:57:31 +0000 Subject: [Haskell-cafe] haddoc "modules on this system" index In-Reply-To: <566628C4.6080200@vex.net> References: <566628C4.6080200@vex.net> Message-ID: i have this: documentation: True So I tried running cabal install on a dummy package, and i got this: $ cabal install Resolving dependencies... Configuring dummy-0.0... Building dummy-0.0... Installed dummy-0.0 Updating documentation index /Users/anatolyy/Library/Haskell/share/doc/x86_64-osx-ghc-7.10.1/index.html so it updated the wrong index file, but even that one has dead links: file:///Users/anatolyy/Library/Haskell/share/doc/x86_64-osx-ghc-7.10.1/Blaze-ByteString-Builder.html doesn't exit $ find ~/Library -name Blaze-ByteString-Builder.html /Users/anatolyy/Library/Haskell/ghc-7.10.1-x86_64/lib/blaze-builder-0.4.0.1/doc/html/Blaze-ByteString-Builder.html On Mon, Dec 7, 2015 at 4:48 PM Albert Y. C. Lai wrote: > On 2015-12-07 06:53 PM, Anatoly Yakovenko wrote: > > I have a bunch of dead links in > > > > file:///Users/anatolyy/Library/Haskell/share/doc/index.html > > > is there a way to regenerate the index from the currently installed docs? > > The index is rebuilt whenever you "cabal install --user > --enable-documentation" some library. (--user is the default. > --enable-documentation can be permanently set in $HOME/.cabal/config, is > it the same path on Mac?) > > I made a dummy library package so I can reinstall it to force-refresh > the index whenever I feel like to. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at schmong.org Tue Dec 8 14:53:04 2015 From: michael at schmong.org (Michael Litchard) Date: Tue, 8 Dec 2015 06:53:04 -0800 Subject: [Haskell-cafe] setting up property tests Message-ID: I've got a little project, based off of fizzbuzz, that I would like to write property tests for using either QuickCheck or SmallCheck. Could someone have a look at https://github.com/mlitchard/fizzbuzzfib/blob/master/src/FizzBuzz.hs and help me sort out how to write property tests? -------------- next part -------------- An HTML attachment was scrubbed... URL: From monkleyon at googlemail.com Wed Dec 9 05:09:21 2015 From: monkleyon at googlemail.com (martin) Date: Wed, 9 Dec 2015 06:09:21 +0100 Subject: [Haskell-cafe] Applicative banana brackets Message-ID: <5667B781.7020103@gmail.com> Hi, while learning about all the type classes and their relationships I came across something I found weird. If I understand it correctly, banana brackets where originally developed for Applicatives. The intent was to enable us to write something like (| (\a b c -> a + b + c), [3], [1,2], [5,0,7] |) and have it translated to liftA3 (\a b c -> a + b + c) [3] [1,2] [5,0,7] or alternatively, to allow us to write something like (| (pure $ \a b c -> a + b + c), [3], [1,2], [5,0,7] |) and have it translated directly to pure (\a b c -> a + b + c) <*> [3] <*> [1,2] <*> [5,0,7] A variant of banana brackets is implemented in ghc, but only for Arrows as part of -XArrowSyntax. Arrows are just the intersection of Applicative and Category, so this implementation seems to be a specialization. What's worse, I don't think -XRebindableSyntax extends to banana brackets. But why? Is it hard to have the notation work with both? (After all, the relationship between Arrows and Applicatives is not easily expressed in Haskell.) Was the demand for (Applicative) bananas not big enough? Is it just a relic? And more to the point: I have not looked at the ghc code base at all yet, but it's on my bucket list to hack on it one day. Right now, a generalization of banana brackets seems like a simple enough low pressure first project, but I fear that it might break code or that there is some pitfall I'm not seeing. Can anybody shed a bit of light on this? Thanks and cheers, Martin L. P.S.: If the list receives this mail several times, I apologize. The list management tool seems to be confused by gmail vs. googlemail. That's what you get for using non-Haskell software. ;) From johannes.waldmann at htwk-leipzig.de Wed Dec 9 09:23:22 2015 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Wed, 09 Dec 2015 10:23:22 +0100 Subject: [Haskell-cafe] parsing and printing - applicative style? Message-ID: <5667F30A.5050603@htwk-leipzig.de> Dear Cafe, what is the current state of the art (and notation) in writing combined parser/printers? (as in Rendel/Ostermann ICFP 2010, http://lambda-the-ultimate.org/node/4191 ) >From the paper I get the impression that this is, or could be, a nice showcase for Applicative and Alternative. Indeed, if parsing a text in a (programming) language is separated from semantics, then the parsing should be applicative? You don't need ">>=" since you do not compute a semantical value on the left, but just the AST, which is syntax only. But then Section 3.2 shows that Printer cannot be Applicative. Indeed, the version of "pure" in the paper (see class "Syntax delta" in Section 3.4) has type "Eq a => a -> delta a", and that's different from the Applicative that we know. But one of the many "categorial" packages on hackage can express this, meanwhile? What is the meta-search-procedure to find it? - J.W. From ben at well-typed.com Wed Dec 9 12:17:24 2015 From: ben at well-typed.com (Ben Gamari) Date: Wed, 09 Dec 2015 13:17:24 +0100 Subject: [Haskell-cafe] [ANNOUNCE] Glasgow Haskell Compiler version 7.10.3 Message-ID: <874mfrlstn.fsf@smart-cactus.org> Hello everyone, We are pleased to announce the release of GHC 7.10.3: https://downloads.haskell.org/~ghc/7.10.3/ There can be found source tarballs and binary distributions for 64-bit and 32-bit modern Linux (GMP 5.0 or later), CentOS (GMP 4.0), Windows, and 64-bit Mac OS X platforms. These binaries and tarballs have an accompanying SHA256SUMS file signed by my GPG key id (0x97DB64AD). Significant fixes in release include changes to the simplifier's treatment of rules, the handling of Mac OS X frameworks, and support for response files to work around the restrictive command line length limit on Windows. As always, a full accounting of the changes present in this release can be found in the release notes [1]. The previous release, 7.10.2, was well-behaved save a couple notable bugs; while we have merged a good number of bug fixes in 7.10.3 they were were largely low risk and so we expect that this release should be similiarly stable. A notable exception is the upgrade of the Windows compiler toolchain to GCC 5.2. Typically we would refrain from making such large changes in a point release but Windows users have been long suffering at the hand of the old toolchain (e.g. lack of response file support, #8596, and lack of SEH support). We expect that this change should fix far more than breaks. Unfortunately, due to some oversights in the release process there are two source tarballs for this release. The first, ghc-7.10.3-src.tar.{bz2,xz}, does not include the release notes in the users guide. This is fixed in the second patchlevel release, ghc-7.10.3a-src.tar.{bz2,xz}. It is recommended that users wanting a source release use the ghc-7.10.3a-src tarballs. GHC 7.10.3 will very likely be the last release in the GHC 7 series. In the coming weeks we will be beginning the release process for GHC 8.0, which will include a number of exciting features including the merger of kinds with types, injective type families, imporved DWARF debugging information, applicative-do syntax, a Strict language extension synonyms mechanism, and more. See the GHC 8.0.1 status page for details [2]. Happy compiling! Cheers, - Ben [1] http://downloads.haskell.org/~ghc/7.10.3/docs/html/users_guide//release-7-10-3.html [2] https://ghc.haskell.org/trac/ghc/wiki/Status/GHC-8.0.1 -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From tikhon at jelv.is Wed Dec 9 16:36:56 2015 From: tikhon at jelv.is (Tikhon Jelvis) Date: Wed, 9 Dec 2015 08:36:56 -0800 Subject: [Haskell-cafe] Applicative banana brackets In-Reply-To: <5667B781.7020103@gmail.com> References: <5667B781.7020103@gmail.com> Message-ID: I don't know how the arrow syntax works, but you can get banana brackets for applicatives with a preprocessor?the Strathclyde Haskell Enhancement (SHE)[1]. You can install it from cabal and enable it with {-# OPTIONS _GHC -F -pgmF she #-} after which it just works (including, if I recall correctly, ghci). Personally, playing around with it convinced me that banana brackets aren't quite as nice in practice as they look. They still make *certain* expressions nicer (especially simple ones involving operators), but either don't make a difference or actually make the code *less* readable in more complicated cases. Of course, those more complicated cases end up being the most common, so in a small project I only found something like two applicative expressions where it helped (out of at least 20). A particular problem I had is that, by necessity, $ works differently inside banana brackets than normally. This is the only thing that makes sense, of course, but it doesn't jell well with how I intuitively use $ as more or less syntax for limiting nested parentheses. I don't want to discourage you too much. They might work better for you than they did for me. But you should definitely play around with them, preferably on a real project, before you sink any time in trying to implement them in GHC. You might like them but don't be surprised if you don't. Also, they'd be somewhat redundant with ApplicativeDo. The syntax is different enough that both can be useful, but it's something to keep in mind. At the very least, the ApplicativeDo extension is a good place to start looking to understand how to desugar to applicative operators in GHC. On Tue, Dec 8, 2015 at 9:09 PM, martin wrote: > Hi, > > while learning about all the type classes and their relationships I came > across something I found weird. > If I understand it correctly, banana brackets where originally developed > for Applicatives. The intent was to enable us to write something like > > (| (\a b c -> a + b + c), [3], [1,2], [5,0,7] |) > > and have it translated to > > liftA3 (\a b c -> a + b + c) [3] [1,2] [5,0,7] > > or alternatively, to allow us to write something like > > (| (pure $ \a b c -> a + b + c), [3], [1,2], [5,0,7] |) > > and have it translated directly to > > pure (\a b c -> a + b + c) <*> [3] <*> [1,2] <*> [5,0,7] > > A variant of banana brackets is implemented in ghc, but only for Arrows > as part of -XArrowSyntax. Arrows are just the intersection of > Applicative and Category, so this implementation seems to be a > specialization. What's worse, I don't think -XRebindableSyntax extends > to banana brackets. > But why? Is it hard to have the notation work with both? (After all, the > relationship between Arrows and Applicatives is not easily expressed in > Haskell.) Was the demand for (Applicative) bananas not big enough? Is it > just a relic? > And more to the point: I have not looked at the ghc code base at all > yet, but it's on my bucket list to hack on it one day. Right now, a > generalization of banana brackets seems like a simple enough low > pressure first project, but I fear that it might break code or that > there is some pitfall I'm not seeing. > > Can anybody shed a bit of light on this? > > Thanks and cheers, > Martin L. > > P.S.: If the list receives this mail several times, I apologize. The > list management tool seems to be confused by gmail vs. googlemail. > That's what you get for using non-Haskell software. ;) > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From gershomb at gmail.com Wed Dec 9 17:10:06 2015 From: gershomb at gmail.com (Gershom B) Date: Wed, 9 Dec 2015 12:10:06 -0500 Subject: [Haskell-cafe] ANNOUNCE: Haskell Platform 7.10.3 Message-ID: Haskellers, we are pleased to announce the release of Haskell Platform 7.10.3 * * get it here: https://www.haskell.org/platform/ * * Highlights include: - GHC 7.10.3 - Major version bumps to - HUnit - OpenGL - OpenGLRaw - syb - Minor version bumps to - Cabal - case-insensitive - fgl - GLUT - GLURaw - primitive Full package and version list: https://www.haskell.org/platform/contents.html GHC release notes can be found at: http://downloads.haskell.org/~ghc/7.10.3/docs/html/users_guide/release-7-10-3.html This is the first release in which I've taken over as release manager. Thanks to Erik Rantapaa, Ben Gamari, Randy Polen and Jason Dagit for various platform related work; thanks to Oleg Grenrus and John Wiegley for additional testing; and thanks of course to Mark Lentczner for developing the new streamlined HP build process that has made things so much easier for all of us. * Windows Notes * The Haskell Platform on Windows now provides the MSys2 tools. These tools are needed when installing packages that use conf-tools (generally rare). These tools are not automatically placed onto the PATH in order avoid troubles due to MSys2 tools which have the same name as a standard Windows tool (e.g., echo, find, dir). * Future Plans * As per the November 13 email on "Haskell Platform Plans" (https://mail.haskell.org/pipermail/haskell-cafe/2015-November/122171.html) this is a modest release for ghc, and also a modest release for the platform, to put a capstone on the 7.10 series. Coming with the 8.0 platform we'll have lots of the exciting stuff that has been long promised, including a minimal distro without extra packages, a bundled stack binary, and a much-improved experience for installing build-type: configure packages (such as network) on Windows. Issues can be reported on the github tracker: https://github.com/haskell/haskell-platform/issues * Known Issues * As the platform builds were done from the tarballs lacking 7.10.3 release notes, those notes will not be present in the installed users' guides. However, they are available online, as in the link given above. Happy Haskelling, Gershom Bazerman, Haskell Platform release manager From ivan.miljenovic at gmail.com Wed Dec 9 20:16:04 2015 From: ivan.miljenovic at gmail.com (Ivan Lazar Miljenovic) Date: Thu, 10 Dec 2015 07:16:04 +1100 Subject: [Haskell-cafe] [ANNOUNCE] Glasgow Haskell Compiler version 7.10.3 In-Reply-To: <874mfrlstn.fsf@smart-cactus.org> References: <874mfrlstn.fsf@smart-cactus.org> Message-ID: On 9 December 2015 at 23:17, Ben Gamari wrote: > > Hello everyone, > > We are pleased to announce the release of GHC 7.10.3: > > https://downloads.haskell.org/~ghc/7.10.3/ > > There can be found source tarballs and binary distributions for 64-bit and 32-bit > modern Linux (GMP 5.0 or later), CentOS (GMP 4.0), Windows, and 64-bit > Mac OS X platforms. These binaries and tarballs have an accompanying > SHA256SUMS file signed by my GPG key id (0x97DB64AD). Significant > fixes in release include changes to the simplifier's treatment of > rules, the handling of Mac OS X frameworks, and support for response > files to work around the restrictive command line length limit on > Windows. As always, a full accounting of the changes present in this > release can be found in the release notes [1]. > > The previous release, 7.10.2, was well-behaved save a couple notable > bugs; while we have merged a good number of bug fixes in 7.10.3 they > were were largely low risk and so we expect that this release should be > similiarly stable. > > A notable exception is the upgrade of the Windows compiler toolchain to > GCC 5.2. Typically we would refrain from making such large changes in a > point release but Windows users have been long suffering at the hand of > the old toolchain (e.g. lack of response file support, #8596, and lack > of SEH support). We expect that this change should fix far more than > breaks. > > Unfortunately, due to some oversights in the release process there are > two source tarballs for this release. The first, > ghc-7.10.3-src.tar.{bz2,xz}, does not include the release notes in the > users guide. This is fixed in the second patchlevel release, > ghc-7.10.3a-src.tar.{bz2,xz}. It is recommended that users wanting a > source release use the ghc-7.10.3a-src tarballs. > > GHC 7.10.3 will very likely be the last release in the GHC 7 series. In > the coming weeks we will be beginning the release process for GHC 8.0, > which will include a number of exciting features including the merger of > kinds with types, injective type families, imporved DWARF debugging > information, applicative-do syntax, a Strict language extension synonyms > mechanism, and more. See the GHC 8.0.1 status page for details [2]. > > Happy compiling! > > Cheers, > > - Ben > > > [1] http://downloads.haskell.org/~ghc/7.10.3/docs/html/users_guide//release-7-10-3.html The links to Trac issues in that page seem to redirect to the same page. > [2] https://ghc.haskell.org/trac/ghc/wiki/Status/GHC-8.0.1 > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -- Ivan Lazar Miljenovic Ivan.Miljenovic at gmail.com http://IvanMiljenovic.wordpress.com From ben at well-typed.com Wed Dec 9 20:23:49 2015 From: ben at well-typed.com (Ben Gamari) Date: Wed, 09 Dec 2015 21:23:49 +0100 Subject: [Haskell-cafe] [ANNOUNCE] Glasgow Haskell Compiler version 7.10.3 In-Reply-To: References: <874mfrlstn.fsf@smart-cactus.org> Message-ID: <87zixjid62.fsf@smart-cactus.org> Ivan Lazar Miljenovic writes: > On 9 December 2015 at 23:17, Ben Gamari wrote: >> >> >> [1] http://downloads.haskell.org/~ghc/7.10.3/docs/html/users_guide//release-7-10-3.html > > The links to Trac issues in that page seem to redirect to the same page. > Indeed, I'm trying to work out what went wrong here. I am quite looking forward to being able to drop DocBook in 8.0. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Wed Dec 9 21:20:30 2015 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Wed, 9 Dec 2015 21:20:30 +0000 Subject: [Haskell-cafe] Applicative banana brackets In-Reply-To: <5667B781.7020103@gmail.com> References: <5667B781.7020103@gmail.com> Message-ID: <20151209212030.GA27389@weber> On Wed, Dec 09, 2015 at 06:09:21AM +0100, martin wrote: > while learning about all the type classes and their relationships I came > across something I found weird. > If I understand it correctly, banana brackets where originally developed > for Applicatives. The intent was to enable us to write something like > > (| (\a b c -> a + b + c), [3], [1,2], [5,0,7] |) > > and have it translated to > > liftA3 (\a b c -> a + b + c) [3] [1,2] [5,0,7] > > or alternatively, to allow us to write something like > > (| (pure $ \a b c -> a + b + c), [3], [1,2], [5,0,7] |) > > and have it translated directly to > > pure (\a b c -> a + b + c) <*> [3] <*> [1,2] <*> [5,0,7] > > A variant of banana brackets is implemented in ghc, but only for Arrows > as part of -XArrowSyntax. I don't think Arrow banana brackets are related to these Applicative (or "Idiom") brackets. Tom From lemming at henning-thielemann.de Wed Dec 9 21:25:23 2015 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Wed, 9 Dec 2015 22:25:23 +0100 (CET) Subject: [Haskell-cafe] [Haskell] ANNOUNCE: Haskell Platform 7.10.3 In-Reply-To: References: Message-ID: On Wed, 9 Dec 2015, Gershom B wrote: > GHC release notes can be found at: > http://downloads.haskell.org/~ghc/7.10.3/docs/html/users_guide/release-7-10-3.html The links in the Release Notes all refer to the Release Notes themselves. I remember that there was a similar problem in former Release Notes. From magnus at therning.org Wed Dec 9 21:46:58 2015 From: magnus at therning.org (Magnus Therning) Date: Wed, 09 Dec 2015 22:46:58 +0100 Subject: [Haskell-cafe] [ANNOUNCE] Glasgow Haskell Compiler version 7.10.3 In-Reply-To: <874mfrlstn.fsf@smart-cactus.org> References: <874mfrlstn.fsf@smart-cactus.org> Message-ID: <87h9jruwfh.fsf@therning.org> Ben Gamari writes: > Hello everyone, > > We are pleased to announce the release of GHC 7.10.3: > > https://downloads.haskell.org/~ghc/7.10.3/ > > Unfortunately, due to some oversights in the release process there are > two source tarballs for this release. The first, > ghc-7.10.3-src.tar.{bz2,xz}, does not include the release notes in the > users guide. This is fixed in the second patchlevel release, > ghc-7.10.3a-src.tar.{bz2,xz}. It is recommended that users wanting a > source release use the ghc-7.10.3a-src tarballs. I don't see any ghc-7.10.3a-src.tar.{bz2,xz} there. Also, https://downloads.haskell.org/~ghc/7.10-latest/ seems to still point to 7.10.2. /M -- Magnus Therning OpenPGP: 0xAB4DFBA4 email: magnus at therning.org jabber: magnus at therning.org twitter: magthe http://therning.org/magnus If voting could really change things it would be illegal. -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 162 bytes Desc: not available URL: From richard.lewis at gold.ac.uk Thu Dec 10 01:31:23 2015 From: richard.lewis at gold.ac.uk (Richard Lewis) Date: Thu, 10 Dec 2015 01:31:23 +0000 Subject: [Haskell-cafe] Audio search library; and debugging help! Message-ID: <85vb876qdw.wl-richard.lewis@gold.ac.uk> Hi there, For a little while I've been working on an audio search library. It wraps over a C++ library written by some of my colleagues. It's nearing the state where someone other than me might actually be able to use it. So this message is partly an annoucement: I'd be very interested to hear if anyone has a go at installing it and running the "tests". But this message is also a request for help, because I'm actually stuck with a bug. I've created a fork of the above repo here: which includes an extra commit which adds quite a few tracing statements. So if anyone feels up to trying to help me with my bug, then this would be the repo to use. The bug goes something like this: One of the features I need to implement is so-called "query rotation". The library implements audio feature searching. For some kinds of multi-dimensional audio features, it's useful to execute queries with them repeatedly moving the values between the dimensions each time to get a kind of exhaustive search. As a specific example (and for those who know a little music theory), there's a feature known as chroma which gives a measure of the signal energy in each of the 12 pitch classes for each window in the audio. If you search with a vector of chroma features, you will only find results that are at exactly the same pitch. But if you shift the chroma search vector around 11 times, you can effectively search for the query vector in every transposition (that's "transposition" as in to transpose in music theory). Anyway, I've tried to capture this in the library by allowing a call to the Sound.Audio.Database.Query.query function to include a QueryTransformer, which is essentially a function which takes a query and returns a new query. And then one instance of this is the function S.A.D.Query.mkSequenceQueryWithRotation which uses another helper function, S.A.D.Query.mkSequenceQueryMutateDatum. This function takes a Ptr to a query, and scribbles over the memory to replace its contents with an altered query vector: the result of some mutation function. Now, what originally alerted me to there being anything wrong with this was that, when I execute a rotated query, I'm getting exactly the same results as for a non-rotated query. As I started investigating, the first thing I found was that the altered feature vectors were not being altered in the way I expected. If I printed them and traced the path of a single value, it wasn't moving step-wise between the bins, but instead jumping around between them randomly. I eventually put in enough putStrLn and trace calls to find that, I think, each time the query is transformed, instead of doing just one transformation, it does as many transformations as times it has iterated: i.e., first iteration it does one transformation, second iteration it does two transformations, and so on. The recursive (sort of iterative?) query transformation is implemented in S.A.D.Query.queryWithTransformPtr. But I'm now at a loss to say whether there's anything actually wrong with this function. So, I think this is the end of my message. I appreciate that this is a very specific problem. I know it's normally helpful to try and abstract a problem into something in terms of Foos and Bars, but I'm not sure I can do this here. As a result, it would be a significant undertaking for anyone to try and help out. So I would be even more grateful than usual if anyone could! (And that's not really meant as a grovelling plea, it's actually more of a warning: you probably shouldn't try and help me.) Thanks, Richard -- -=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-= Richard Lewis Computing, Goldsmiths' College t: +44 (0)20 7078 5203 @: lewisrichard http://www.transforming-musicology.org/ 905C D796 12CD 4C6E CBFB 69DA EFCE DCDF 71D7 D455 -=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-= From juhpetersen at gmail.com Thu Dec 10 04:13:43 2015 From: juhpetersen at gmail.com (Jens Petersen) Date: Thu, 10 Dec 2015 13:13:43 +0900 Subject: [Haskell-cafe] [ANNOUNCE] Glasgow Haskell Compiler version 7.10.3 In-Reply-To: <874mfrlstn.fsf@smart-cactus.org> References: <874mfrlstn.fsf@smart-cactus.org> Message-ID: On 9 December 2015 at 21:17, Ben Gamari wrote: > We are pleased to announce the release of GHC 7.10.3 Awesome, thank you! I have build it for Fedora and RHEL/CentOS in my Fedora Copr repo: https://copr.fedoraproject.org/coprs/petersen/ghc-7.10.3 The repos also include cabal-install. Cheers, Jens From jo at durchholz.org Thu Dec 10 07:01:10 2015 From: jo at durchholz.org (Joachim Durchholz) Date: Thu, 10 Dec 2015 08:01:10 +0100 Subject: [Haskell-cafe] [ANNOUNCE] Glasgow Haskell Compiler version 7.10.3 In-Reply-To: <87zixjid62.fsf@smart-cactus.org> References: <874mfrlstn.fsf@smart-cactus.org> <87zixjid62.fsf@smart-cactus.org> Message-ID: <56692336.4010701@durchholz.org> Am 09.12.2015 um 21:23 schrieb Ben Gamari: > I am quite looking forward to being able to drop DocBook in 8.0. What's going to be the replacement? Just curious, because I need to decide on a publishing toolchain for my own project. Regards, Jo From voldermort at hotmail.com Thu Dec 10 07:55:31 2015 From: voldermort at hotmail.com (Jeremy) Date: Thu, 10 Dec 2015 00:55:31 -0700 (MST) Subject: [Haskell-cafe] [ANNOUNCE] Glasgow Haskell Compiler version 7.10.3 In-Reply-To: <56692336.4010701@durchholz.org> References: <874mfrlstn.fsf@smart-cactus.org> <87zixjid62.fsf@smart-cactus.org> <56692336.4010701@durchholz.org> Message-ID: <1449734131686-5823995.post@n5.nabble.com> https://www.haskell.org/ghc/download still lists 7.10.3 as the current release. -- View this message in context: http://haskell.1045720.n5.nabble.com/ANNOUNCE-Glasgow-Haskell-Compiler-version-7-10-3-tp5823927p5823995.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com. From trupill at gmail.com Thu Dec 10 07:55:47 2015 From: trupill at gmail.com (Alejandro Serrano Mena) Date: Thu, 10 Dec 2015 08:55:47 +0100 Subject: [Haskell-cafe] Looking for maintainers for emacs-haskell-tutorial Message-ID: Dear Haskell-Caf?, Some time ago, and as part of my Google Summer of Code project, I wrote a tutorial about setting up Emacs to work with Haskell [ https://github.com/serras/emacs-haskell-tutorial/blob/master/tutorial.md]. The tutorial is now a bit outdated and several issues are pending solution [ https://github.com/serras/emacs-haskell-tutorial/issues]. However, due to other (young, crying) obligations I don't have the time needed to maintain the tutorial anymore, all by myself. Thus, I would like to ask whether somebody is willing to maintain the tutorial up-to-date, and take care of the issues. Or simply, whether somebody is willing to help in doing so. Regards, Alejandro -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben at well-typed.com Thu Dec 10 08:26:52 2015 From: ben at well-typed.com (Ben Gamari) Date: Thu, 10 Dec 2015 09:26:52 +0100 Subject: [Haskell-cafe] [ANNOUNCE] Glasgow Haskell Compiler version 7.10.3 In-Reply-To: <56692336.4010701@durchholz.org> References: <874mfrlstn.fsf@smart-cactus.org> <87zixjid62.fsf@smart-cactus.org> <56692336.4010701@durchholz.org> Message-ID: <87vb86iu9f.fsf@smart-cactus.org> Joachim Durchholz writes: > Am 09.12.2015 um 21:23 schrieb Ben Gamari: >> I am quite looking forward to being able to drop DocBook in 8.0. > > What's going to be the replacement? > Just curious, because I need to decide on a publishing toolchain for my > own project. > We have moved the users guide to ReStructuredText, which is built with Sphinx. I'm quite pleased with how the transition has gone. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From jo at durchholz.org Thu Dec 10 08:50:46 2015 From: jo at durchholz.org (Joachim Durchholz) Date: Thu, 10 Dec 2015 09:50:46 +0100 Subject: [Haskell-cafe] [ANNOUNCE] Glasgow Haskell Compiler version 7.10.3 In-Reply-To: <87vb86iu9f.fsf@smart-cactus.org> References: <874mfrlstn.fsf@smart-cactus.org> <87zixjid62.fsf@smart-cactus.org> <56692336.4010701@durchholz.org> <87vb86iu9f.fsf@smart-cactus.org> Message-ID: <56693CE6.5030100@durchholz.org> Am 10.12.2015 um 09:26 schrieb Ben Gamari: > We have moved the users guide to ReStructuredText, which is built with > Sphinx. I'm quite pleased with how the transition has gone. Heh. I can imagine; Sphinx seems to be the doc toolchain tool du jour, I was just curious about the reasons and how the differences work out. Regards, Jo From oleg at okmij.org Thu Dec 10 09:39:06 2015 From: oleg at okmij.org (Oleg) Date: Thu, 10 Dec 2015 18:39:06 +0900 Subject: [Haskell-cafe] FLOPS 2016: Call for Participation and Posters/Demos Message-ID: <20151210093906.GA1715@Magus.sf-private> FLOPS 2016: 13th International Symposium on Functional and Logic Programming March 4-6, 2016, Kochi, Japan http://www.info.kochi-tech.ac.jp/FLOPS2016/ Call for Participation and Posters/Demos Registration will be open on Monday, Dec 21, 2015. Early registration deadline is Monday, Feb 8, 2016. Poster/Demo abstract submission deadline is Monday, Jan 11, 2016. FLOPS aims to bring together practitioners, researchers and implementers of the declarative programming, to discuss mutually interesting results and common problems: theoretical advances, their implementations in language systems and tools, and applications of these systems in practice. The scope includes all aspects of the design, semantics, theory, applications, implementations, and teaching of declarative programming. FLOPS specifically aims to promote cross-fertilization between theory and practice and among different styles of declarative programming. In addition to the presentations of regular research papers, the FLOPS program includes tutorials, as well as the poster/demo session for demonstrating the tools and systems described during the talks and for presenting works-in-progress and getting the feedback. FLOPS has established a Best Paper award. The winner will be announced at the symposium. CALLS FOR POSTERS AND DEMONSTRATIONS If you wish to present a poster at FLOPS, please send the plain text abstract by e-mail to -- by January 11, 2016. The abstract should include the title, the names of the authors and their affiliation, along with enough details to judge its scope and relevance. We will announce the accepted submissions on January 25, 2016. The format of the poster will be announced at that time. Important Dates * Submission due: January 11, 2016 (Monday), any time zone * Notification: January 25, 2016 (Monday) INVITED TALKS Kazunori UEDA (Waseda University) The exciting time and hard-won lessons of the Fifth Generation Computer Project Atze Dijkstra (Utrecht University) UHC: Coping with Compiler Complexity TUTORIALS Andreas Abel, on Agda Atze Dijkstra, on Attribute Grammars Neng-Fa Zhou, on programming in Picat ACCEPTED PAPERS Ki Yung Ahn and Andrea Vezzosi. Executable Relational Specifications of Polymorphic Type Systems using Prolog Markus Triska. The Boolean Constraint Solver of SWI-Prolog: System Description Peng Fu, Ekaterina Komendantskaya, Tom Schrijvers and Andrew Pond. Proof Relevant Corecursive Resolution Jay McCarthy, Burke Fetscher, Max New and Robert Bruce Findler. A Coq Library For Internal Verification of Running-Times Akimasa Morihata. Incremental Computing with Abstract Data Structures Wouter Swierstra and Joao Alpuim. >From proposition to program: embedding the refinement calculus in Coq Andre Van Delft and Anatoliy Kmetyuk. Declarative Programming with Algebra Ian Mackie and Shinya Sato. An interaction net encoding of Godel's System T Arthur Blot, Pierre-Evariste Dagand and Julia Lawall. >From Sets to Bits in Coq Jeremy Yallop, David Sheets and Anil Madhavapeddy. Declarative foreign function binding through generic programming Praveen Narayanan, Jacques Carette, Wren Romano, Chung-Chieh Shan and Robert Zinkov. Probabilistic inference by program transformation in Hakaru: System description Francisco Javier Lopez-Fraguas, Manuel Montenegro and Juan Rodriguez-Hortala. Polymorphic Types in Erlang Function Specifications Remy Haemmerle, Pedro Lopez-Garcia, Umer Liqat, Maximiliano Klemen, John Gallagher and Manuel V. Hermenegildo. A Transformational Approach to Parametric Accumulated-cost Static Profiling Taus Brock-Nannestad. Space-efficient Planar Acyclicity Constraints: A Declarative Pearl From ben at smart-cactus.org Thu Dec 10 09:51:24 2015 From: ben at smart-cactus.org (Ben Gamari) Date: Thu, 10 Dec 2015 10:51:24 +0100 Subject: [Haskell-cafe] [ANNOUNCE] Glasgow Haskell Compiler version 7.10.3 In-Reply-To: <56693CE6.5030100@durchholz.org> References: <874mfrlstn.fsf@smart-cactus.org> <87zixjid62.fsf@smart-cactus.org> <56692336.4010701@durchholz.org> <87vb86iu9f.fsf@smart-cactus.org> <56693CE6.5030100@durchholz.org> Message-ID: <87r3iuiqcj.fsf@smart-cactus.org> Joachim Durchholz writes: > Am 10.12.2015 um 09:26 schrieb Ben Gamari: >> We have moved the users guide to ReStructuredText, which is built with >> Sphinx. I'm quite pleased with how the transition has gone. > > Heh. I can imagine; Sphinx seems to be the doc toolchain tool du jour, I > was just curious about the reasons and how the differences work out. > I wrote up a brief description of the motivations and the options we evaluated on the Wiki [1]. In short, I found there weren't too many options which had flexible enough markup, could scale to something the size of the Users Guide, and didn't impose onerous dependencies. Ultimately the two realistic options were asciidoc and ReST. While an initial poll of ghc-devs found a slight preference for asciidoc, my preliminary attempts to port the users guide quickly encountered resistance from asciidoc's syntax. In short, asciidoc constructs just don't compose very well: while all lightweight markup languages have their limitations, I found that I ran into asciidoc's very quickly, particularly when nesting block items (e.g. a code block inside a list item). Due to how asciidoc's continuation syntax works I found that the local structure of the document would have wide-spread effects on how the rest of the document would need to be marked-up. After seeing asciidoc fail so badly, I was reluctant to even try ReST, assuming it would meet a similar fate. Thankfully I decided to try running a couple chapters through Pandoc and was pleasantly surprised by the output. While Pandoc's output wasn't perfect (e.g. there is no support of index terms), it was obvious that ReST was capable of conveniently representing most of the document and did not exhibit the same syntactic papercuts I saw with Asciidoc. In the end I was able to modify Pandoc to mechanically produce reasonable ReST output for the majority of the user's guide. ReST does have its limitations however and we ended up sacrificing in some areas in the name of more readable markup. Most notably, inline objects cannot be nested in ReST. This means that constructions like, :module +|- *mod1 ... *modn become impossible to express. In the end I settled for an approximation representing tags with ? ? symbols. Anyways, on the whole I think the trade-off was well worthwhile. The syntax is substantially more readable, the output is more appealing, and the tooling is orders of magnitude better. Cheers, - Ben [1] https://ghc.haskell.org/trac/ghc/wiki/UsersGuide/MoveFromDocBook -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From jo at durchholz.org Thu Dec 10 10:05:45 2015 From: jo at durchholz.org (Joachim Durchholz) Date: Thu, 10 Dec 2015 11:05:45 +0100 Subject: [Haskell-cafe] [ANNOUNCE] Glasgow Haskell Compiler version 7.10.3 In-Reply-To: <87r3iuiqcj.fsf@smart-cactus.org> References: <874mfrlstn.fsf@smart-cactus.org> <87zixjid62.fsf@smart-cactus.org> <56692336.4010701@durchholz.org> <87vb86iu9f.fsf@smart-cactus.org> <56693CE6.5030100@durchholz.org> <87r3iuiqcj.fsf@smart-cactus.org> Message-ID: <56694E79.1020105@durchholz.org> Am 10.12.2015 um 10:51 schrieb Ben Gamari: > [1] https://ghc.haskell.org/trac/ghc/wiki/UsersGuide/MoveFromDocBook Aaah... thanks, that was exactly what I was interested in. Regards, Jo From k-bx at k-bx.com Thu Dec 10 12:59:38 2015 From: k-bx at k-bx.com (Kostiantyn Rybnikov) Date: Thu, 10 Dec 2015 14:59:38 +0200 Subject: [Haskell-cafe] setting up property tests In-Reply-To: References: Message-ID: Hi. Are you struggling with getting a setup itself or with examples of test-cases which would test your code well? If former -- I suggest looking at framework called "tasty". Its readme has full working example of both quick- and smallcheck. Cheers. 8 ????. 2015 4:53 ?? "Michael Litchard" ????: > I've got a little project, based off of fizzbuzz, that I would like to > write > property tests for using either QuickCheck or SmallCheck. > Could someone have a look at > https://github.com/mlitchard/fizzbuzzfib/blob/master/src/FizzBuzz.hs and > help me sort out how to write property tests? > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From sumit.sahrawat.apm13 at iitbhu.ac.in Thu Dec 10 16:00:59 2015 From: sumit.sahrawat.apm13 at iitbhu.ac.in (Sumit Sahrawat, Maths & Computing, IIT (BHU)) Date: Thu, 10 Dec 2015 21:30:59 +0530 Subject: [Haskell-cafe] Looking for maintainers for emacs-haskell-tutorial In-Reply-To: References: Message-ID: I shall take a look at this. On 10 December 2015 at 13:25, Alejandro Serrano Mena wrote: > Dear Haskell-Caf?, > Some time ago, and as part of my Google Summer of Code project, I wrote a > tutorial about setting up Emacs to work with Haskell [ > https://github.com/serras/emacs-haskell-tutorial/blob/master/tutorial.md]. > The tutorial is now a bit outdated and several issues are pending solution > [https://github.com/serras/emacs-haskell-tutorial/issues]. However, due > to other (young, crying) obligations I don't have the time needed to > maintain the tutorial anymore, all by myself. > Thus, I would like to ask whether somebody is willing to maintain the > tutorial up-to-date, and take care of the issues. Or simply, whether > somebody is willing to help in doing so. > > Regards, > Alejandro > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > -- Regards Sumit Sahrawat -------------- next part -------------- An HTML attachment was scrubbed... URL: From guillaumh at gmail.com Thu Dec 10 18:48:48 2015 From: guillaumh at gmail.com (Guillaume Hoffmann) Date: Thu, 10 Dec 2015 15:48:48 -0300 Subject: [Haskell-cafe] Darcs Hacking Sprint #10 (January 15th-17th, Seville) Message-ID: Dear Hackers I'm glad to announce that the 10th Darcs Sprint that will be in Seville, on January 15-17 at the ETS de Ingenier?a Inform?tica, Universidad de Sevilla. Please check the details at: http://darcs.net/Sprints/2016-01 Here are three things to know 1. Everybody is welcome to join us. We'd love to have you, whatever your Haskell or Darcs hacking experience. Also, if you've got a wacky idea for the future of version control, or a cool use for the Darcs library, you should join us too :-) 2. Please let us know if you're attending: * add your name to http://wiki.darcs.net/Sprints/2016-01 * send me (privately) your full name and some official identification number for access to the university on Saturday and Sunday. 3. We can reimburse travel costs (within reason!). Let us know if you'd like a reimbursement, and save your receipts. Many thanks to everybody who participated in our fundraising drives or who gave money on the side. Thanks also to the Software Freedom Conservancy for making fundraising and reimbursements so painless! If you can't join us in person, but you'd like to cheer us on, say hello at http://darcs.net/Donations ! see you in one month! Guillaume From heraldhoi at gmail.com Thu Dec 10 21:56:12 2015 From: heraldhoi at gmail.com (Geraldus) Date: Thu, 10 Dec 2015 21:56:12 +0000 Subject: [Haskell-cafe] [ANNOUNCE] Glasgow Haskell Compiler version 7.10.3 In-Reply-To: <56694E79.1020105@durchholz.org> References: <874mfrlstn.fsf@smart-cactus.org> <87zixjid62.fsf@smart-cactus.org> <56692336.4010701@durchholz.org> <87vb86iu9f.fsf@smart-cactus.org> <56693CE6.5030100@durchholz.org> <87r3iuiqcj.fsf@smart-cactus.org> <56694E79.1020105@durchholz.org> Message-ID: In case this will be helpfull for someone here [1] is my Docker file for building GHC-7.10.3 on Debian Wheezy from sources, also here is the image itself [2]. Note, Docker Hub shows that image size is 1Gb, however running `docker images` locally shows me 6.354 GB. I tried to make some cleanup but my docker skills are quite weak, so I will be happy if anyone can teach me how to reduce image size. Regards! [1]: https://github.com/geraldus/docker-debian-wheezy-haskell-src [2]: https://hub.docker.com/r/geraldus/wheezy-haskell-src -------------- next part -------------- An HTML attachment was scrubbed... URL: From ss.nedunuri at gmail.com Fri Dec 11 00:12:30 2015 From: ss.nedunuri at gmail.com (s nedunuri) Date: Thu, 10 Dec 2015 18:12:30 -0600 Subject: [Haskell-cafe] Problem running the ping example from "Parallel and Concurrent Programming in Haskell" Message-ID: hello I am trying out the examples in Chapter 14 of the book, and was able to install and build the parconc-examples package fine. However when I try running the (very first example) ping program I get the following error: ping.exe: bind: failed (Cannot assign requested address (WSAEADDRNOTAVAIL)) It appears that the failure is in the main function: distribMain (\_ -> master) Main.__remoteTable Any ideas? thanks PS I am running Haskell Platform 7.10.2-a on Windows 7 From atzeus at gmail.com Fri Dec 11 10:43:32 2015 From: atzeus at gmail.com (Atze van der Ploeg) Date: Fri, 11 Dec 2015 11:43:32 +0100 Subject: [Haskell-cafe] Problem running the ping example from "Parallel and Concurrent Programming in Haskell" In-Reply-To: References: Message-ID: Sounds like the requested port is already taken. Try changing the port number On Dec 11, 2015 1:15 AM, "s nedunuri" wrote: > hello I am trying out the examples in Chapter 14 of the book, and was able > to install and build the parconc-examples package fine. However when I try > running the (very first example) ping program I get the following error: > > ping.exe: bind: failed (Cannot assign requested address (WSAEADDRNOTAVAIL)) > > It appears that the failure is in the main function: > distribMain (\_ -> master) Main.__remoteTable > > Any ideas? > > thanks > PS I am running Haskell Platform 7.10.2-a on Windows 7 > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From richard.lewis at gold.ac.uk Fri Dec 11 12:05:13 2015 From: richard.lewis at gold.ac.uk (Richard Lewis) Date: Fri, 11 Dec 2015 12:05:13 +0000 Subject: [Haskell-cafe] Audio search library; and debugging help! In-Reply-To: <85vb876qdw.wl-richard.lewis@gold.ac.uk> References: <85vb876qdw.wl-richard.lewis@gold.ac.uk> Message-ID: <85zixhxkau.wl-richard.lewis@gold.ac.uk> On Thu, 10 Dec 2015 01:31:23 +0000, Richard Lewis wrote: > So, I think this is the end of my message. I appreciate that this is a > very specific problem. I know it's normally helpful to try and > abstract a problem into something in terms of Foos and Bars, but I'm > not sure I can do this here. As a result, it would be a significant > undertaking for anyone to try and help out. So I would be even more > grateful than usual if anyone could! (And that's not really meant as a > grovelling plea, it's actually more of a warning: you probably > shouldn't try and help me.) On the suggestion of #haskell, here is the output of a recent run of the debugging version of this code: (with apologies for the Wagner!) Richard -- -=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-= Richard Lewis Computing, Goldsmiths' College t: +44 (0)20 7078 5203 @: lewisrichard http://www.transforming-musicology.org/ 905C D796 12CD 4C6E CBFB 69DA EFCE DCDF 71D7 D455 -=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-= From haskell at dshevchenko.biz Fri Dec 11 17:48:09 2015 From: haskell at dshevchenko.biz (Denis Shevchenko) Date: Fri, 11 Dec 2015 21:48:09 +0400 Subject: [Haskell-cafe] webdriver and click via executeJS In-Reply-To: References: <874mfrlstn.fsf@smart-cactus.org> <87zixjid62.fsf@smart-cactus.org> <56692336.4010701@durchholz.org> <87vb86iu9f.fsf@smart-cactus.org> <56693CE6.5030100@durchholz.org> <87r3iuiqcj.fsf@smart-cactus.org> <56694E79.1020105@durchholz.org> Message-ID: <566B0C59.4090900@dshevchenko.biz> Hi there! I use `webdriver` package for test automation with PhantomJS. And I need to click some button, but not with a `click` function, but with a native JS. I see a special function for such a task, `executeJS`, in the module `Test.WebDriver.Commands`. So this is my code: ... button <- findElement . ById $ "clearCart" info <- elemInfo button executeJS [JSArg info] "arguments[0].click();" ... But I got a runtime error: BadJSON "when expecting a (), encountered Null instead" How can I fix it? - Denis -------------- next part -------------- An HTML attachment was scrubbed... URL: From wuzzeb at gmail.com Fri Dec 11 18:37:18 2015 From: wuzzeb at gmail.com (John Lenz) Date: Fri, 11 Dec 2015 12:37:18 -0600 Subject: [Haskell-cafe] webdriver and click via executeJS In-Reply-To: <566B0C59.4090900@dshevchenko.biz> References: <874mfrlstn.fsf@smart-cactus.org> <87zixjid62.fsf@smart-cactus.org> <56692336.4010701@durchholz.org> <87vb86iu9f.fsf@smart-cactus.org> <56693CE6.5030100@durchholz.org> <87r3iuiqcj.fsf@smart-cactus.org> <56694E79.1020105@durchholz.org> <566B0C59.4090900@dshevchenko.biz> Message-ID: I have this problem all the time and it is pretty anoying. The problem is in parsing the return value. The javascript is returning null but the executeJS is returning `()`. The aeson instance for `()` does not parse null. What I do is something like someOper :: WD () ret <- executeJS [...] "...] maybe (return ()) return ret -- parse value from executeJS as Maybe () On Fri, Dec 11, 2015 at 11:48 AM, Denis Shevchenko wrote: > Hi there! > > I use `webdriver` package for test automation with PhantomJS. And I need > to click some button, but not with a `click` function, but with a native > JS. I see a special function for such a task, `executeJS`, in the module > `Test.WebDriver.Commands`. So this is my code: > > ... > button <- findElement . ById $ "clearCart" > info <- elemInfo button > executeJS [JSArg info] "arguments[0].click();" > ... > > But I got a runtime error: > > BadJSON "when expecting a (), encountered Null instead" > > How can I fix it? > > - Denis > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ss.nedunuri at gmail.com Fri Dec 11 20:07:17 2015 From: ss.nedunuri at gmail.com (s nedunuri) Date: Fri, 11 Dec 2015 14:07:17 -0600 Subject: [Haskell-cafe] Problem running the ping example from "Parallel and Concurrent Programming in Haskell" In-Reply-To: References: Message-ID: Ok sure, but any ide what to change it to? Its currently set to 44444 in DistribUtils.hs (a utility module that comes with the code) and I tried various numbers in Windows preferred range from 49152 upwards, and 0 but to no avail. thanks On 12/11/2015 4:43 AM, Atze van der Ploeg wrote: > Sounds like the requested port is already taken. Try changing the port > number > > On Dec 11, 2015 1:15 AM, "s nedunuri" > wrote: > > hello I am trying out the examples in Chapter 14 of the book, and > was able to install and build the parconc-examples package fine. > However when I try running the (very first example) ping program I > get the following error: > > ping.exe: bind: failed (Cannot assign requested address > (WSAEADDRNOTAVAIL)) > > It appears that the failure is in the main function: > distribMain (\_ -> master) Main.__remoteTable > > Any ideas? > > thanks > PS I am running Haskell Platform 7.10.2-a on Windows 7 > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > From dagitj at gmail.com Fri Dec 11 23:49:31 2015 From: dagitj at gmail.com (Jason Dagit) Date: Fri, 11 Dec 2015 15:49:31 -0800 Subject: [Haskell-cafe] [ANNOUNCE] Glasgow Haskell Compiler version 7.10.3 In-Reply-To: References: <874mfrlstn.fsf@smart-cactus.org> <87zixjid62.fsf@smart-cactus.org> <56692336.4010701@durchholz.org> <87vb86iu9f.fsf@smart-cactus.org> <56693CE6.5030100@durchholz.org> <87r3iuiqcj.fsf@smart-cactus.org> <56694E79.1020105@durchholz.org> Message-ID: On Thu, Dec 10, 2015 at 1:56 PM, Geraldus wrote: > > In case this will be helpfull for someone here [1] is my Docker > file for building GHC-7.10.3 on Debian Wheezy from sources, also > here is the image itself [2]. Note, Docker Hub shows that image > size is 1Gb, however running `docker images` locally shows me > 6.354 GB. I tried to make some cleanup but my docker skills are > quite weak, so I will be happy if anyone can teach me how to > reduce image size. > For the Haskell Platform I did the build on Debian Jessie using docker. I haven't tried to share the images, but I worked from these notes: https://github.com/haskell/haskell-platform/blob/master/notes/building-ghc-docker That was the first time I ever used docker. Perhaps in the future we can combine efforts to reduce duplication? I've been trying to figure out if we can use this setup to cross compile a 32bit build as well, but it seems like 32bit containers are not supported. I think for a cross compile that true 32bit support is unnecessary so I'm not quite ready to give up on the idea. Thanks, Jason -------------- next part -------------- An HTML attachment was scrubbed... URL: From dct25-561bs at mythic-beasts.com Sat Dec 12 11:02:32 2015 From: dct25-561bs at mythic-beasts.com (David Turner) Date: Sat, 12 Dec 2015 11:02:32 +0000 Subject: [Haskell-cafe] ANNOUNCE: alarmclock-0.2.0.8: wake up at a certain time In-Reply-To: References: Message-ID: Hi all, A very belated announcement of a little library for efficiently waking up at a certain time. I've found this useful for things like timeouts, scheduling retries, cache expiry and so on. Not a lot to say, really, it does what it says on the tin! http://hackage.haskell.org/package/alarmclock Comments and feature requests are most welcome. Cheers, David -------------- next part -------------- An HTML attachment was scrubbed... URL: From dct25-561bs at mythic-beasts.com Sat Dec 12 11:12:56 2015 From: dct25-561bs at mythic-beasts.com (David Turner) Date: Sat, 12 Dec 2015 11:12:56 +0000 Subject: [Haskell-cafe] ANNOUNCE: bank-holidays-england: Calculation of bank holidays in England and Wales In-Reply-To: References: Message-ID: Hi all, A very belated announcement of a little library that implements the frankly daft rules for calculating the dates of bank holidays in England and Wales. With apologies to the Welsh for the abbreviated package name, and to the Scots for not including yours too. http://hackage.haskell.org/package/bank-holidays-england Comments and feature requests are most welcome. Cheers, David -------------- next part -------------- An HTML attachment was scrubbed... URL: From tkoster at gmail.com Sun Dec 13 01:34:11 2015 From: tkoster at gmail.com (Thomas Koster) Date: Sun, 13 Dec 2015 12:34:11 +1100 Subject: [Haskell-cafe] Problem running the ping example from "Parallel and Concurrent Programming in Haskell" In-Reply-To: References: Message-ID: On Dec 11, 2015 1:15 AM, "s nedunuri" wrote: > hello I am trying out the examples in Chapter 14 of the book, and was able > to install and build the parconc-examples package fine. However when I try > running the (very first example) ping program I get the following error: > > ping.exe: bind: failed (Cannot assign requested address > (WSAEADDRNOTAVAIL)) On 11 December 2015 at 21:43, Atze van der Ploeg wrote: > Sounds like the requested port is already taken. Try changing the port > number Atze, I think you're thinking of WSAEADDRINUSE. S, the error sounds like the program is trying to bind a socket to a non-existent or invalid address or port. If the program gets its configuration for these things from command line arguments, config files or environment variables, I would check there first. -- Thomas Koster From martin.drautzburg at web.de Sun Dec 13 20:15:59 2015 From: martin.drautzburg at web.de (martin) Date: Sun, 13 Dec 2015 21:15:59 +0100 Subject: [Haskell-cafe] Need ideas how to model the lack of something Message-ID: <566DD1FF.3090700@web.de> Hello all, here is a problem where I did not manage to find a suitable abstraction. The main idea goes like this: a List (and many other containers) can be seen as something containing "stuff". There is a function (:) that unconditionally adds an element to the container and returns a new container Now suppose the container has the possiblility to refuse having another element added to it, e.g. because it has only limited "space". In that case the corresponding function would have a signature of insert :: a -> C a -> Maybe (C a). If an item can successfully be added, then the returned container will be less space avaiable. I'd like stuff and space to be symmetrical (maybe there lies the first flaw, because I can enumerate the elements, but I cannot enumerate the space). A symmetry like electrones and holes. I started like this data C a = C { insert :: a -> Maybe (C a), remove :: Maybe (a, C a) } but I could not implement anything sensible on top of this. I'd be happy to hear any comments on this, including loud thinking and random ramblings. From sumit.sahrawat.apm13 at iitbhu.ac.in Sun Dec 13 20:49:11 2015 From: sumit.sahrawat.apm13 at iitbhu.ac.in (Sumit Sahrawat, Maths & Computing, IIT (BHU)) Date: Mon, 14 Dec 2015 02:19:11 +0530 Subject: [Haskell-cafe] Need ideas how to model the lack of something In-Reply-To: <566DD1FF.3090700@web.de> References: <566DD1FF.3090700@web.de> Message-ID: You can implement a structure which hides a max length and a length inside it, whose record accessors are not exported. Also, rather than thinking of insert and remove as operations *inside* the structure, think of them separately. Define just the data structure first, and then define the operations afterwards. This separates the interface and implementation, allowing you to change the structure without changing the API. On 14 December 2015 at 01:45, martin wrote: > Hello all, > > here is a problem where I did not manage to find a suitable abstraction. > The main idea goes like this: > > a List (and many other containers) can be seen as something containing > "stuff". There is a function (:) that > unconditionally adds an element to the container and returns a new > container > > Now suppose the container has the possiblility to refuse having another > element added to it, e.g. because it has only > limited "space". In that case the corresponding function would have a > signature of insert :: a -> C a -> Maybe (C a). If > an item can successfully be added, then the returned container will be > less space avaiable. > > I'd like stuff and space to be symmetrical (maybe there lies the first > flaw, because I can enumerate the elements, but I > cannot enumerate the space). A symmetry like electrones and holes. > > I started like this > > data C a = C { > insert :: a -> Maybe (C a), > remove :: Maybe (a, C a) > } > > but I could not implement anything sensible on top of this. > > I'd be happy to hear any comments on this, including loud thinking and > random ramblings. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -- Sumit Sahrawat, Junior - Mathematics and Computing, Indian Institute of Technology - BHU, Varanasi, India -------------- next part -------------- An HTML attachment was scrubbed... URL: From roma at ro-che.info Sun Dec 13 21:36:08 2015 From: roma at ro-che.info (Roman Cheplyaka) Date: Sun, 13 Dec 2015 23:36:08 +0200 Subject: [Haskell-cafe] Need ideas how to model the lack of something In-Reply-To: <566DD1FF.3090700@web.de> References: <566DD1FF.3090700@web.de> Message-ID: <566DE4C8.2020309@ro-che.info> You may want to specify: 1. whether you want the symmetry to be present in the API, the internal representation, or both 2. what exactly your C type is lacking. It looks like a valid model of what you described, even if somewhat object-oriented one. You may also be interested in combinatorial species. That theory specifically considers functorial shapes containing a specific number of holes and/or elements. I think Brent Yorgey has some articles and/or code relating species to Haskell. On 12/13/2015 10:15 PM, martin wrote: > Hello all, > > here is a problem where I did not manage to find a suitable abstraction. The main idea goes like this: > > a List (and many other containers) can be seen as something containing "stuff". There is a function (:) that > unconditionally adds an element to the container and returns a new container > > Now suppose the container has the possiblility to refuse having another element added to it, e.g. because it has only > limited "space". In that case the corresponding function would have a signature of insert :: a -> C a -> Maybe (C a). If > an item can successfully be added, then the returned container will be less space avaiable. > > I'd like stuff and space to be symmetrical (maybe there lies the first flaw, because I can enumerate the elements, but I > cannot enumerate the space). A symmetry like electrones and holes. > > I started like this > > data C a = C { > insert :: a -> Maybe (C a), > remove :: Maybe (a, C a) > } > > but I could not implement anything sensible on top of this. > > I'd be happy to hear any comments on this, including loud thinking and random ramblings. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > . > -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: OpenPGP digital signature URL: From plredmond at gmail.com Sun Dec 13 22:57:09 2015 From: plredmond at gmail.com (Patrick Redmond) Date: Sun, 13 Dec 2015 14:57:09 -0800 Subject: [Haskell-cafe] Need ideas how to model the lack of something In-Reply-To: <566DE4C8.2020309@ro-che.info> References: <566DD1FF.3090700@web.de> <566DE4C8.2020309@ro-che.info> Message-ID: I think you're off to a good start with this insert signature: insert :: a -> C a -> Maybe (C a) "Insert element `a` into structure `C a` and return a new structure if the insertion was successful." It looks like you're following the lead of some common haskell data structures (eg, containers:Data.Set.insert ). What does this lack? --- If you want the container to be implicit in the arguments (albeit, explicit in the return value), then your second formulation works: data C a = C { insert :: a -> Maybe (C a), remove :: Maybe (a, C a) } To implement this you could make a constructor that has an internal data structure, and then constructs a `C` by closing over the internal structure. In this way, your `C` is really just an API and you'll have an internal implementation of insert & remove that take the internal structure as an explicit argument. That's a bunch of extra work for a minor convenience, so I'd recommend starting with the version that takes an explicit argument (first in this email). On Sun, Dec 13, 2015 at 1:36 PM, Roman Cheplyaka wrote: > You may want to specify: > > 1. whether you want the symmetry to be present in the API, the internal > representation, or both > 2. what exactly your C type is lacking. It looks like a valid model of > what you described, even if somewhat object-oriented one. > > You may also be interested in combinatorial species. That theory > specifically considers functorial shapes containing a specific number of > holes and/or elements. I think Brent Yorgey has some articles and/or > code relating species to Haskell. > > On 12/13/2015 10:15 PM, martin wrote: > > Hello all, > > > > here is a problem where I did not manage to find a suitable abstraction. > The main idea goes like this: > > > > a List (and many other containers) can be seen as something containing > "stuff". There is a function (:) that > > unconditionally adds an element to the container and returns a new > container > > > > Now suppose the container has the possiblility to refuse having another > element added to it, e.g. because it has only > > limited "space". In that case the corresponding function would have a > signature of insert :: a -> C a -> Maybe (C a). If > > an item can successfully be added, then the returned container will be > less space avaiable. > > > > I'd like stuff and space to be symmetrical (maybe there lies the first > flaw, because I can enumerate the elements, but I > > cannot enumerate the space). A symmetry like electrones and holes. > > > > I started like this > > > > data C a = C { > > insert :: a -> Maybe (C a), > > remove :: Maybe (a, C a) > > } > > > > but I could not implement anything sensible on top of this. > > > > I'd be happy to hear any comments on this, including loud thinking and > random ramblings. > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > . > > > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ky3 at atamo.com Mon Dec 14 00:28:53 2015 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Mon, 14 Dec 2015 07:28:53 +0700 Subject: [Haskell-cafe] Need ideas how to model the lack of something In-Reply-To: <566DD1FF.3090700@web.de> References: <566DD1FF.3090700@web.de> Message-ID: On Mon, Dec 14, 2015 at 3:15 AM, martin wrote: > I started like this > > data C a = C { > insert :: a -> Maybe (C a), > remove :: Maybe (a, C a) > } > > but I could not implement anything sensible on top of this. > And the reason you're stuck implementing anything sensible on top of this is because you've written an OOP-style specification of a data structure. You might want to review how Haskell declares data types. -- Kim-Ee -------------- next part -------------- An HTML attachment was scrubbed... URL: From jo at durchholz.org Mon Dec 14 06:28:49 2015 From: jo at durchholz.org (Joachim Durchholz) Date: Mon, 14 Dec 2015 07:28:49 +0100 Subject: [Haskell-cafe] Need ideas how to model the lack of something In-Reply-To: References: <566DD1FF.3090700@web.de> Message-ID: <566E61A1.9070500@durchholz.org> Am 14.12.2015 um 01:28 schrieb Kim-Ee Yeoh: > On Mon, Dec 14, 2015 at 3:15 AM, martin wrote: > >> I started like this >> >> data C a = C { >> insert :: a -> Maybe (C a), >> remove :: Maybe (a, C a) >> } >> >> but I could not implement anything sensible on top of this. >> > > And the reason you're stuck implementing anything sensible on top of this > is because you've written an OOP-style specification of a data structure. Mmm... this is the second time this has been raised. What's the problem with OOP style? Something specific with Haskell, something about OOP in general, something else? Regards, Jo From martin.drautzburg at web.de Mon Dec 14 07:03:26 2015 From: martin.drautzburg at web.de (martin) Date: Mon, 14 Dec 2015 08:03:26 +0100 Subject: [Haskell-cafe] Need ideas how to model the lack of something In-Reply-To: References: <566DD1FF.3090700@web.de> <566DE4C8.2020309@ro-che.info> Message-ID: <566E69BE.1020800@web.de> Am 12/13/2015 um 11:57 PM schrieb Patrick Redmond: > I think you're off to a good start with this insert signature: > > insert :: a -> C a -> Maybe (C a) > "Insert element `a` into structure `C a` and return a new structure if the insertion was successful." This way I'd have to be explicit about what C really is, don't I? Data.Set certainly has a very explicit data structure under the hood. I was hoping to express the idea of "something that can be inserted to and removed from" without specifying how the data is actually stored. But maybe that's a bad point to start from. At least this is where the trouble started when I tried to implement something on top of it. I just didn't have enough "flesh" to work with. From plredmond at gmail.com Mon Dec 14 07:21:07 2015 From: plredmond at gmail.com (Patrick Redmond) Date: Sun, 13 Dec 2015 23:21:07 -0800 Subject: [Haskell-cafe] Need ideas how to model the lack of something In-Reply-To: <566E69BE.1020800@web.de> References: <566DD1FF.3090700@web.de> <566DE4C8.2020309@ro-che.info> <566E69BE.1020800@web.de> Message-ID: Replies inline. On Sunday, December 13, 2015, martin wrote: > Am 12/13/2015 um 11:57 PM schrieb Patrick Redmond: > > I think you're off to a good start with this insert signature: > > > > insert :: a -> C a -> Maybe (C a) > > "Insert element `a` into structure `C a` and return a new structure if > the insertion was successful." > > This way I'd have to be explicit about what C really is, don't I? Data.Set > certainly has a very explicit data structure > under the hood. I was hoping to express the idea of "something that can be > inserted to and removed from" without > specifying how the data is actually stored. Use a typeclass. But maybe that's a bad point to start from. At least this is where the > trouble started when I tried to implement > something on top of it. I just didn't have enough "flesh" to work with. Yes, you will have to write a concrete implementation anyway, so start with that. Make an explicit data structure, with concretely typed functions to manipulate it. When you have two of these explicit implementations, make a typeclass and provide two instances - one which delegates to each of the implementations. -------------- next part -------------- An HTML attachment was scrubbed... URL: From dennis.raddle at gmail.com Mon Dec 14 10:39:35 2015 From: dennis.raddle at gmail.com (Dennis Raddle) Date: Mon, 14 Dec 2015 02:39:35 -0800 Subject: [Haskell-cafe] a problem I can't solve simply Message-ID: I have a problem that doesn't seem hard to state but I can't seem to solve without a bunch of complex code. This relates to my musical score playback. In using it to play music, I don't always want to play back the entire source musical document, but rather play a range of measures. So I might give a command to my app like "play 1-3" which means play measures 1 through 3. There is a time saving feature, which is that I can type "play 10" which means start the playback at measure 10 and continue until the first occurrence of two empty measures. This is a common use case. So I have to write a function that takes a start measure and computes the end measure by scanning for two empty measures. Let's say for simplicity's sake that we'll forget about "measures" and just say that notes have a start time and end time, which will be integers. type Note = (Int,Int) A musical score can have several individual staves (notes for individual instruments), so it will look like this: type Staff = [Note] type Score = [Staff] I need to write a function as follows computeEndMsr :: Int -> Score -> Int computeEndMsr beginMsr score = ... Some examples: Here's a score with just one staff, to give you an idea. score1 = [ [(1,3), (2,4), (7,10)] ] -- In the following case a two-unit gap is found at units 5 and 6. computeEndMsr 1 score1 = 4 computeEndMsr 5 score1 = should throw an error indicating that a gap was found immediately and no actual notes were included -- In the following case, the maximum unit of any note is 10, so that is what is computed computeEndMsr 6 score1 = 10 -- This case illustrates how it's okay if the computed end measure is equal to the begin msr computeEndMsr 10 score1 = 10 computeEndMsr 11 score1 = should throw an error indicating that the given begin msr is past the end of any note in the score This example has only one staff, but a score can have multiple staves. Also the timing and duration of notes can overlap, either on one staff or across multiple staves. -------------- next part -------------- An HTML attachment was scrubbed... URL: From atze at uu.nl Mon Dec 14 10:58:05 2015 From: atze at uu.nl (Atze Dijkstra) Date: Mon, 14 Dec 2015 11:58:05 +0100 Subject: [Haskell-cafe] [NL-FP 2016] Final CFP: Dutch Functional Programming Day 2016 Message-ID: [My apologies for multiple received copies of the same message] Final Call for Participation: Dear all, The next Dutch Functional Programming day (NL-FP 2016) will be held on Friday, January 8, 2016 at the Utrecht University, The Netherlands. The program of the day now is online (see the below webpage). At the end of the day we will have a joint dinner. Besides the program, on the web page http://foswiki.cs.uu.nl/foswiki/NlFpDay2016/WebHome for the day you?ll also find the registration, which is by letting me know via email (with a subject header that begins with [NL-FP 2016]) whether you want to (1) participate, (2) join dinner, also see the webpage for additional details. There is still room for a demo or poster during lunch/break time. If you intend to participate, please let me know before the end of this year because we like to know how many people we can expect. Hope to meet you all in Utrecht at the next FP Day! Best regards, - Atze - Atze Dijkstra, Department of Information and Computing Sciences. /|\ Utrecht University, PO Box 80089, 3508 TB Utrecht, Netherlands. / | \ Tel.: +31-30-2534118/1454 | WWW : http://www.cs.uu.nl/~atze . /--| \ Fax : +31-30-2513971 .... | Email: atze at uu.nl ............... / |___\ -------------- next part -------------- An HTML attachment was scrubbed... URL: From dennis.raddle at gmail.com Mon Dec 14 11:15:34 2015 From: dennis.raddle at gmail.com (Dennis Raddle) Date: Mon, 14 Dec 2015 03:15:34 -0800 Subject: [Haskell-cafe] a problem I can't solve simply In-Reply-To: References: Message-ID: Ooops I meant to post this to the beginner's list. I'll wait to see if someone here responds, then repost it on the beginner's list. -------------- next part -------------- An HTML attachment was scrubbed... URL: From monkleyon at googlemail.com Mon Dec 14 13:53:30 2015 From: monkleyon at googlemail.com (martin) Date: Mon, 14 Dec 2015 14:53:30 +0100 Subject: [Haskell-cafe] Applicative banana brackets In-Reply-To: References: <5667B781.7020103@gmail.com> Message-ID: <566EC9DA.7080000@gmail.com> > I don't know how the arrow syntax works, but you can get banana brackets > for applicatives with a preprocessor?the Strathclyde Haskell Enhancement > (SHE)[1]. [...] I hadn't looked into preprocessors yet, but that sounds like a great idea. Thanks! > Personally, playing around with it convinced me that banana brackets aren't > quite as nice in practice as they look. [...] Of course, those more complicated cases end up being the > most common. [...] I only played around with arrow brackets yet, but that sounds familiar. They can make your code really beautiful - but only rarely. I'm currently trying to convert some of my overcomplicated arrow structures to simpler applicative ones, which is one of my motivations here. But if it's of so little use, and with liftAn's already there... > A particular problem I had is that, by necessity, $ works differently > inside banana brackets than normally. [...] That sounds like it might not have been a problem for me yet because the natural composition of arrows is through (>>>) anyway. Interesting. > I don't want to discourage you too much. Don't worry. There are always things to play around with and projects to try. It was just that I thought I might have found something far simpler that what I usually come up with, and thus something I could actually finish and share some day. ;) > Also, they'd be somewhat redundant with ApplicativeDo. Yet another thing I hadn't thought of. I'm not a huge fan of do-notation and arrow-notation myself. They are useful, but can be overly verbose and distracting. So maybe I'll get more use out of brackets? Only one way to find out... Anyway, thanks for all the great information. These are definitely things I'll consider! >> Hi, >> >> while learning about all the type classes and their relationships I came >> across something I found weird. >> If I understand it correctly, banana brackets where originally developed >> for Applicatives. The intent was to enable us to write something like >> >> (| (\a b c -> a + b + c), [3], [1,2], [5,0,7] |) >> >> and have it translated to >> >> liftA3 (\a b c -> a + b + c) [3] [1,2] [5,0,7] >> >> or alternatively, to allow us to write something like >> >> (| (pure $ \a b c -> a + b + c), [3], [1,2], [5,0,7] |) >> >> and have it translated directly to >> >> pure (\a b c -> a + b + c) <*> [3] <*> [1,2] <*> [5,0,7] >> >> A variant of banana brackets is implemented in ghc, but only for Arrows >> as part of -XArrowSyntax. Arrows are just the intersection of >> Applicative and Category, so this implementation seems to be a >> specialization. What's worse, I don't think -XRebindableSyntax extends >> to banana brackets. >> But why? Is it hard to have the notation work with both? (After all, the >> relationship between Arrows and Applicatives is not easily expressed in >> Haskell.) Was the demand for (Applicative) bananas not big enough? Is it >> just a relic? >> And more to the point: I have not looked at the ghc code base at all >> yet, but it's on my bucket list to hack on it one day. Right now, a >> generalization of banana brackets seems like a simple enough low >> pressure first project, but I fear that it might break code or that >> there is some pitfall I'm not seeing. >> >> Can anybody shed a bit of light on this? >> >> Thanks and cheers, >> Martin L. >> >> P.S.: If the list receives this mail several times, I apologize. The >> list management tool seems to be confused by gmail vs. googlemail. >> That's what you get for using non-Haskell software. ;) >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> From doaitse at swierstra.net Mon Dec 14 14:16:02 2015 From: doaitse at swierstra.net (S. Doaitse Swierstra) Date: Mon, 14 Dec 2015 15:16:02 +0100 Subject: [Haskell-cafe] Applicative banana brackets In-Reply-To: <566EC9DA.7080000@gmail.com> References: <5667B781.7020103@gmail.com> <566EC9DA.7080000@gmail.com> Message-ID: In the Idioms module of uu-parsinglib: https://hackage.haskell.org/package/uu-parsinglib-2.9.1/docs/Text-ParserCombinators-UU-Idioms.html I show how you can achieve what you want without any preprocessors. The idea is to overload based on the type of the operand: {-# LANGUAGE RankNTypes, MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, UndecidableInstances, FlexibleContexts, CPP #-} module Idiomatic where -- | The `Ii` is to be pronounced as @stop@ data Ii = Ii -- | The function `iI` is to be pronounced as @start@ iI ::Idiomatic (a -> a) g => g iI = idiomatic (pure id) class Idiomatic f g | g -> f where idiomatic :: [f] -> g instance Idiomatic x (Ii -> [x]) where idiomatic ix Ii = ix instance Idiomatic f g => Idiomatic (a -> f) ([a] -> g) where idiomatic isf is = idiomatic (isf <*> is) instance Idiomatic f g => Idiomatic ((a -> b) -> f) ((a -> b) -> g) where idiomatic isf f = idiomatic (isf <*> (pure f)) t :: [Int] t = iI (\ a b c -> a + b +c) [3] [1,2] [5,0,7] Ii So you get: *Idiomatic> show t "[9,4,11,10,5,12]" *Idiomatic> > On 14 Dec 2015, at 14:53 , martin wrote: > >> I don't know how the arrow syntax works, but you can get banana brackets >> for applicatives with a preprocessor?the Strathclyde Haskell Enhancement >> (SHE)[1]. [...] > I hadn't looked into preprocessors yet, but that sounds like a great > idea. Thanks! >> Personally, playing around with it convinced me that banana brackets aren't >> quite as nice in practice as they look. [...] Of course, those more complicated cases end up being the >> most common. [...] > I only played around with arrow brackets yet, but that sounds familiar. > They can make your code really beautiful - but only rarely. I'm > currently trying to convert some of my overcomplicated arrow structures > to simpler applicative ones, which is one of my motivations here. But if > it's of so little use, and with liftAn's already there... >> A particular problem I had is that, by necessity, $ works differently >> inside banana brackets than normally. [...] > That sounds like it might not have been a problem for me yet because the > natural composition of arrows is through (>>>) anyway. Interesting. >> I don't want to discourage you too much. > Don't worry. There are always things to play around with and projects to > try. It was just that I thought I might have found something far simpler > that what I usually come up with, and thus something I could actually > finish and share some day. ;) >> Also, they'd be somewhat redundant with ApplicativeDo. > Yet another thing I hadn't thought of. I'm not a huge fan of do-notation > and arrow-notation myself. They are useful, but can be overly verbose > and distracting. So maybe I'll get more use out of brackets? Only one > way to find out... > > Anyway, thanks for all the great information. These are definitely > things I'll consider! > >>> Hi, >>> >>> while learning about all the type classes and their relationships I came >>> across something I found weird. >>> If I understand it correctly, banana brackets where originally developed >>> for Applicatives. The intent was to enable us to write something like >>> >>> (| (\a b c -> a + b + c), [3], [1,2], [5,0,7] |) >>> >>> and have it translated to >>> >>> liftA3 (\a b c -> a + b + c) [3] [1,2] [5,0,7] >>> >>> or alternatively, to allow us to write something like >>> >>> (| (pure $ \a b c -> a + b + c), [3], [1,2], [5,0,7] |) >>> >>> and have it translated directly to >>> >>> pure (\a b c -> a + b + c) <*> [3] <*> [1,2] <*> [5,0,7] >>> >>> A variant of banana brackets is implemented in ghc, but only for Arrows >>> as part of -XArrowSyntax. Arrows are just the intersection of >>> Applicative and Category, so this implementation seems to be a >>> specialization. What's worse, I don't think -XRebindableSyntax extends >>> to banana brackets. >>> But why? Is it hard to have the notation work with both? (After all, the >>> relationship between Arrows and Applicatives is not easily expressed in >>> Haskell.) Was the demand for (Applicative) bananas not big enough? Is it >>> just a relic? >>> And more to the point: I have not looked at the ghc code base at all >>> yet, but it's on my bucket list to hack on it one day. Right now, a >>> generalization of banana brackets seems like a simple enough low >>> pressure first project, but I fear that it might break code or that >>> there is some pitfall I'm not seeing. >>> >>> Can anybody shed a bit of light on this? >>> >>> Thanks and cheers, >>> Martin L. >>> >>> P.S.: If the list receives this mail several times, I apologize. The >>> list management tool seems to be confused by gmail vs. googlemail. >>> That's what you get for using non-Haskell software. ;) >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe From monkleyon at googlemail.com Mon Dec 14 14:38:34 2015 From: monkleyon at googlemail.com (martin) Date: Mon, 14 Dec 2015 15:38:34 +0100 Subject: [Haskell-cafe] Applicative banana brackets In-Reply-To: <20151209212030.GA27389@weber> References: <5667B781.7020103@gmail.com> <20151209212030.GA27389@weber> Message-ID: <566ED46A.6050808@gmail.com> On 2015-12-09 22:20, Tom Ellis wrote: >> while learning about all the type classes and their relationships I came >> across something I found weird. >> If I understand it correctly, banana brackets where originally developed >> for Applicatives. The intent was to enable us to write something like > I don't think Arrow banana brackets are related to these Applicative (or > "Idiom") brackets. Let me try to convince you. ;) Actually I have no idea if there is a historical relationship, but there is definitely a semantic one. Consider this: 1) An alternative definition of Applicative is as a monoidal, with the operation comma :: f a -> f b -> f (a,b) "comma" is connected with (<*>) through the Functor superclass. It's typically named (**), but I'll use a prefix version. 2) Every arrow a b c is an applicative (a b) c, because comma = (&&&). Conversely, every applicative that is polymorphic over some "internal" variable is automatically an arrow, through (&&&) = comma. 3) Let's rename (&&&) to "andA". It's trivial to think of "comma" and "andA" as the special versions "comma2" and "andA2" of more general forms commaN and andAn for all natural numbers n. The equivalence of both functions extends naturally for all n. (N.B.: comma0/andA0 and comma1/andA1 are very interesting functions and one of the reasons I left out all the stuff from Pointed/CoPointed/Unit. The other reason is simplification.) 4) An idiom bracket (| f x1 x2 ... xn |) translates very roughly to liftA (uncurryN f) (commaN x1 x2 ... xn) while a banana bracket (| f x1 x2 ... xn |) translates very roughly to liftA' (uncurryN f) (andAn x1 x2 ... xn) And as commaN and andAn are equivalent, the relation should be obvious now. Of course that's a very very rough sketch without any proofs, without looking at the wrappers, and with slightly modified semantics in the first argument. Still, I'm convinced both are (almost) the same. But then I might be overlooking something important... From ky3 at atamo.com Mon Dec 14 14:53:42 2015 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Mon, 14 Dec 2015 21:53:42 +0700 Subject: [Haskell-cafe] Applicative banana brackets In-Reply-To: <566ED46A.6050808@gmail.com> References: <5667B781.7020103@gmail.com> <20151209212030.GA27389@weber> <566ED46A.6050808@gmail.com> Message-ID: On Mon, Dec 14, 2015 at 9:38 PM, martin wrote: 2) Every arrow a b c is an applicative (a b) c, because comma = (&&&). > Conversely, every applicative that is polymorphic over some "internal" > variable is automatically an arrow, through (&&&) = comma. > Where is the proof that (a b) is a Functor? Recall that the class method arr -- the closest kin to fmap -- has the type: (b -> c) -> a b c. -- Kim-Ee -------------- next part -------------- An HTML attachment was scrubbed... URL: From monkleyon at googlemail.com Mon Dec 14 14:53:49 2015 From: monkleyon at googlemail.com (martin) Date: Mon, 14 Dec 2015 15:53:49 +0100 Subject: [Haskell-cafe] Applicative banana brackets In-Reply-To: References: <5667B781.7020103@gmail.com> <566EC9DA.7080000@gmail.com> Message-ID: <566ED7FD.1010406@gmail.com> That's... just brilliant! I think I'll sneak back to the beginners' play room now... On 2015-12-14 15:16, S. Doaitse Swierstra wrote: > In the Idioms module of uu-parsinglib: > > https://hackage.haskell.org/package/uu-parsinglib-2.9.1/docs/Text-ParserCombinators-UU-Idioms.html > > I show how you can achieve what you want without any preprocessors. The idea is to overload based on the type of the operand: > > {-# LANGUAGE RankNTypes, > MultiParamTypeClasses, > FunctionalDependencies, > FlexibleInstances, > UndecidableInstances, > FlexibleContexts, > CPP #-} > > module Idiomatic where > > -- | The `Ii` is to be pronounced as @stop@ > data Ii = Ii > > -- | The function `iI` is to be pronounced as @start@ > iI ::Idiomatic (a -> a) g => g > iI = idiomatic (pure id) > > class Idiomatic f g | g -> f where > idiomatic :: [f] -> g > > instance Idiomatic x (Ii -> [x]) where > idiomatic ix Ii = ix > > > instance Idiomatic f g => Idiomatic (a -> f) ([a] -> g) where > idiomatic isf is = idiomatic (isf <*> is) > > instance Idiomatic f g => Idiomatic ((a -> b) -> f) ((a -> b) -> g) where > idiomatic isf f = idiomatic (isf <*> (pure f)) > > t :: [Int] > t = iI (\ a b c -> a + b +c) [3] [1,2] [5,0,7] Ii > > So you get: > > *Idiomatic> show t > "[9,4,11,10,5,12]" > *Idiomatic> > > > > > >> On 14 Dec 2015, at 14:53 , martin wrote: >> >>> I don't know how the arrow syntax works, but you can get banana brackets >>> for applicatives with a preprocessor?the Strathclyde Haskell Enhancement >>> (SHE)[1]. [...] >> I hadn't looked into preprocessors yet, but that sounds like a great >> idea. Thanks! >>> Personally, playing around with it convinced me that banana brackets aren't >>> quite as nice in practice as they look. [...] Of course, those more complicated cases end up being the >>> most common. [...] >> I only played around with arrow brackets yet, but that sounds familiar. >> They can make your code really beautiful - but only rarely. I'm >> currently trying to convert some of my overcomplicated arrow structures >> to simpler applicative ones, which is one of my motivations here. But if >> it's of so little use, and with liftAn's already there... >>> A particular problem I had is that, by necessity, $ works differently >>> inside banana brackets than normally. [...] >> That sounds like it might not have been a problem for me yet because the >> natural composition of arrows is through (>>>) anyway. Interesting. >>> I don't want to discourage you too much. >> Don't worry. There are always things to play around with and projects to >> try. It was just that I thought I might have found something far simpler >> that what I usually come up with, and thus something I could actually >> finish and share some day. ;) >>> Also, they'd be somewhat redundant with ApplicativeDo. >> Yet another thing I hadn't thought of. I'm not a huge fan of do-notation >> and arrow-notation myself. They are useful, but can be overly verbose >> and distracting. So maybe I'll get more use out of brackets? Only one >> way to find out... >> >> Anyway, thanks for all the great information. These are definitely >> things I'll consider! >> >>>> Hi, >>>> >>>> while learning about all the type classes and their relationships I came >>>> across something I found weird. >>>> If I understand it correctly, banana brackets where originally developed >>>> for Applicatives. The intent was to enable us to write something like >>>> >>>> (| (\a b c -> a + b + c), [3], [1,2], [5,0,7] |) >>>> >>>> and have it translated to >>>> >>>> liftA3 (\a b c -> a + b + c) [3] [1,2] [5,0,7] >>>> >>>> or alternatively, to allow us to write something like >>>> >>>> (| (pure $ \a b c -> a + b + c), [3], [1,2], [5,0,7] |) >>>> >>>> and have it translated directly to >>>> >>>> pure (\a b c -> a + b + c) <*> [3] <*> [1,2] <*> [5,0,7] >>>> >>>> A variant of banana brackets is implemented in ghc, but only for Arrows >>>> as part of -XArrowSyntax. Arrows are just the intersection of >>>> Applicative and Category, so this implementation seems to be a >>>> specialization. What's worse, I don't think -XRebindableSyntax extends >>>> to banana brackets. >>>> But why? Is it hard to have the notation work with both? (After all, the >>>> relationship between Arrows and Applicatives is not easily expressed in >>>> Haskell.) Was the demand for (Applicative) bananas not big enough? Is it >>>> just a relic? >>>> And more to the point: I have not looked at the ghc code base at all >>>> yet, but it's on my bucket list to hack on it one day. Right now, a >>>> generalization of banana brackets seems like a simple enough low >>>> pressure first project, but I fear that it might break code or that >>>> there is some pitfall I'm not seeing. >>>> >>>> Can anybody shed a bit of light on this? >>>> >>>> Thanks and cheers, >>>> Martin L. >>>> >>>> P.S.: If the list receives this mail several times, I apologize. The >>>> list management tool seems to be confused by gmail vs. googlemail. >>>> That's what you get for using non-Haskell software. ;) >>>> _______________________________________________ >>>> Haskell-Cafe mailing list >>>> Haskell-Cafe at haskell.org >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>>> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe From hesselink at gmail.com Mon Dec 14 15:10:34 2015 From: hesselink at gmail.com (Erik Hesselink) Date: Mon, 14 Dec 2015 16:10:34 +0100 Subject: [Haskell-cafe] Applicative banana brackets In-Reply-To: References: <5667B781.7020103@gmail.com> <20151209212030.GA27389@weber> <566ED46A.6050808@gmail.com> Message-ID: Every Arrow is a Functor through: fmapA :: Arrow arr => (a -> b) -> arr i a -> arr i b fmapA f a = arr f . a Right? Erik On 14 December 2015 at 15:53, Kim-Ee Yeoh wrote: > On Mon, Dec 14, 2015 at 9:38 PM, martin wrote: > >> 2) Every arrow a b c is an applicative (a b) c, because comma = (&&&). >> Conversely, every applicative that is polymorphic over some "internal" >> variable is automatically an arrow, through (&&&) = comma. > > > Where is the proof that (a b) is a Functor? > > Recall that the class method arr -- the closest kin to fmap -- has the type: > > (b -> c) -> a b c. > > -- Kim-Ee > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > From ky3 at atamo.com Mon Dec 14 15:41:43 2015 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Mon, 14 Dec 2015 22:41:43 +0700 Subject: [Haskell-cafe] Applicative banana brackets In-Reply-To: References: <5667B781.7020103@gmail.com> <20151209212030.GA27389@weber> <566ED46A.6050808@gmail.com> Message-ID: On Mon, Dec 14, 2015 at 10:10 PM, Erik Hesselink wrote: Every Arrow is a Functor through: > > fmapA :: Arrow arr => (a -> b) -> arr i a -> arr i b > fmapA f a = arr f . a > > Right? > That's one of the missing holes in Martin's claim. In cases like this, it would help to avoid any risk that the usual abuse of language brings. So an arrow is not a functor but it does give rise to one. More precisely, there would be an instance Arrow a => Functor (a b). -- Kim-Ee -------------- next part -------------- An HTML attachment was scrubbed... URL: From monkleyon at googlemail.com Mon Dec 14 16:18:10 2015 From: monkleyon at googlemail.com (martin) Date: Mon, 14 Dec 2015 17:18:10 +0100 Subject: [Haskell-cafe] Applicative banana brackets In-Reply-To: References: <5667B781.7020103@gmail.com> <20151209212030.GA27389@weber> <566ED46A.6050808@gmail.com> Message-ID: <566EEBC2.6070705@gmail.com> Yes, I know, my sketch is like a swiss cheese. Also, I apologize for my abuse of language. My excuse is that my training did not involve the precise terms used in English proofs. (It's not my first language, after all.) Indeed it did not even expand to proofs in this area at all. The only language I know how to express proofs in unambiguously is Haskell itself - but I haven't found a way to express the relationships here. Most importantly: instance (forall b.Applicative (a b)) => Arrow a where ... That's not idiomatic, and I haven't found any idiomatic way to express that relationship yet. As a result (and to keep the sketch short), my goal was more on the level of transporting intuition. So, to quell your hunger for proofs, here's a proof that fmapA is indeed a suitable definition for fmap: # Definition fmapA f = \a -> a >>> arr f -- equivalent through currying and the definition of (>>>) # fmap id == id fmapA id = \a -> a >>> arr id -- definition of fmapA = \a -> a >>> id -- Arrow law = \a -> id . a -- definition of (>>>) = \a -> a -- definition of id = id -- definition of id # fmap (f . g) == (fmap f) . (fmap g) fmapA (f . g) = \a -> a >>> arr (f . g) -- definition of fmapA = \a -> a >>> arr (g >>> f) -- definition of (>>>) = \a -> a >>> (arr g >>> arr f) -- Arrow law = \a -> (a >>> arr g) >>> arr f -- Category law = \a -> (fmapA g a) >>> arr f -- definition of fmapA = \a -> fmapA f (fmapA g a) -- definition of fmapA = \a -> (fmapA f) . (fmapA g) a -- definition of (.) = (fmapA f) . (fmapA g) -- currying And here's the blog post that initially convinced me of the relationship between Arrows and Applicatives: http://just-bottom.blogspot.de/2010/04/programming-with-effects-story-so-far.html The alternative definition of Applicative as Monoidal can be found in the Typeclassopedia: https://wiki.haskell.org/Typeclassopedia#Alternative_formulation There are still holes to be filled, but these are more or less all the pieces of the puzzle I have so far. On 2015-12-14 16:41, Kim-Ee Yeoh wrote: > On Mon, Dec 14, 2015 at 10:10 PM, Erik Hesselink > wrote: > > Every Arrow is a Functor through: >> fmapA :: Arrow arr => (a -> b) -> arr i a -> arr i b >> fmapA f a = arr f . a >> >> Right? >> > That's one of the missing holes in Martin's claim. > > In cases like this, it would help to avoid any risk that the usual abuse of > language brings. So an arrow is not a functor but it does give rise to one. > More precisely, there would be an instance Arrow a => Functor (a b). > > -- Kim-Ee > From ky3 at atamo.com Mon Dec 14 17:23:10 2015 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Tue, 15 Dec 2015 00:23:10 +0700 Subject: [Haskell-cafe] Applicative banana brackets In-Reply-To: <566EEBC2.6070705@gmail.com> References: <5667B781.7020103@gmail.com> <20151209212030.GA27389@weber> <566ED46A.6050808@gmail.com> <566EEBC2.6070705@gmail.com> Message-ID: On Mon, Dec 14, 2015 at 11:18 PM, martin wrote: Yes, I know, my sketch is like a swiss cheese. That's fine in many places. But extraordinary claims -- like applicative and arrow brackets being the same -- demand extraordinary evidence. Also, I apologize for my abuse of language. (Actually that wasn't directed at anyone in particular. I'd really like to get to the bottom of this, and abuse of language is like drilling with a blunt bit.) > My excuse is that my training did not involve the precise terms used in > English proofs. (It's not my first language, after all.) A smart man once wrote that Fate has imposed upon my writing the yoke of a foreign tongue that was not sung at my cradle. That makes two of us. (See what I wrote about "missing holes"? There was a hole. Erik filled it. No-one misses it.) Indeed it did not even expand to proofs in this area at all. The > only language I know how to express proofs in unambiguously is Haskell > itself - but I haven't found a way to express the relationships here. > Most importantly: > > instance (forall b.Applicative (a b)) => Arrow a where ... > You're referring to http://just-bottom.blogspot.de/2010/04/programming-with-effects-story-so-far.html ? Superclassing Applicative over Arrow appears off. > That's not idiomatic, and I haven't found any idiomatic way to express > that relationship yet. > As a result (and to keep the sketch short), my goal was more on the > level of transporting intuition. > > So, to quell your hunger for proofs, here's a proof that fmapA is indeed > a suitable definition for fmap: > Or we could just cite "instance Arrow a => Applicative (WrappedArrow a b)" in https://hackage.haskell.org/package/base-4.8.1.0/docs/Control-Applicative.html Make no mistake: The goal here isn't pedantry. We retrace the steps (1) to (4) with a fine-toothed comb to understand the claimed equivalence of brackets. -- Kim-Ee > # Definition > fmapA f = \a -> a >>> arr f -- equivalent through currying and the > definition of (>>>) > > # fmap id == id > fmapA id = \a -> a >>> arr id -- definition of fmapA > = \a -> a >>> id -- Arrow law > = \a -> id . a -- definition of (>>>) > = \a -> a -- definition of id > = id -- definition of id > > # fmap (f . g) == (fmap f) . (fmap g) > fmapA (f . g) = \a -> a >>> arr (f . g) -- definition of fmapA > = \a -> a >>> arr (g >>> f) -- definition of (>>>) > = \a -> a >>> (arr g >>> arr f) -- Arrow law > = \a -> (a >>> arr g) >>> arr f -- Category law > = \a -> (fmapA g a) >>> arr f -- definition of fmapA > = \a -> fmapA f (fmapA g a) -- definition of fmapA > = \a -> (fmapA f) . (fmapA g) a -- definition of (.) > = (fmapA f) . (fmapA g) -- currying > > And here's the blog post that initially convinced me of the relationship > between Arrows and Applicatives: > > http://just-bottom.blogspot.de/2010/04/programming-with-effects-story-so-far.html > > The alternative definition of Applicative as Monoidal can be found in > the Typeclassopedia: > https://wiki.haskell.org/Typeclassopedia#Alternative_formulation > > There are still holes to be filled, but these are more or less all the > pieces of the puzzle I have so far. > > On 2015-12-14 16:41, Kim-Ee Yeoh wrote: > > On Mon, Dec 14, 2015 at 10:10 PM, Erik Hesselink > > wrote: > > > > Every Arrow is a Functor through: > >> fmapA :: Arrow arr => (a -> b) -> arr i a -> arr i b > >> fmapA f a = arr f . a > >> > >> Right? > >> > > That's one of the missing holes in Martin's claim. > > > > In cases like this, it would help to avoid any risk that the usual abuse > of > > language brings. So an arrow is not a functor but it does give rise to > one. > > More precisely, there would be an instance Arrow a => Functor (a b). > > > > -- Kim-Ee > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From itz at buug.org Mon Dec 14 19:42:23 2015 From: itz at buug.org (Ian Zimmerman) Date: Mon, 14 Dec 2015 11:42:23 -0800 Subject: [Haskell-cafe] Tongues [Was: Applicative banana brackets] In-Reply-To: References: <5667B781.7020103@gmail.com> <20151209212030.GA27389@weber> <566ED46A.6050808@gmail.com> <566EEBC2.6070705@gmail.com> Message-ID: <20151214193850.4795.1462A36E@ahiker.mooo.com> On 2015-12-15 00:23 +0700, Kim-Ee Yeoh wrote: > A smart man once wrote that Fate has imposed upon my writing the yoke of a > foreign tongue that was not sung at my cradle. Hermann Weyl? https://en.wikipedia.org/wiki/Hermann_Weyl -- Please *no* private copies of mailing list or newsgroup messages. Rule 420: All persons more than eight miles high to leave the court. From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Mon Dec 14 20:21:26 2015 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Mon, 14 Dec 2015 20:21:26 +0000 Subject: [Haskell-cafe] Applicative banana brackets In-Reply-To: <566ED46A.6050808@gmail.com> References: <5667B781.7020103@gmail.com> <20151209212030.GA27389@weber> <566ED46A.6050808@gmail.com> Message-ID: <20151214202126.GJ29838@weber> On Mon, Dec 14, 2015 at 03:38:34PM +0100, martin wrote: > On 2015-12-09 22:20, Tom Ellis wrote: > >> while learning about all the type classes and their relationships I came > >> across something I found weird. > >> If I understand it correctly, banana brackets where originally developed > >> for Applicatives. The intent was to enable us to write something like > > > I don't think Arrow banana brackets are related to these Applicative (or > > "Idiom") brackets. > > Let me try to convince you. ;) OK :) > Actually I have no idea if there is a historical relationship, but there > is definitely a semantic one. Consider this: 1) - 3), all agreed. > 4) An idiom bracket (| f x1 x2 ... xn |) translates very roughly to > liftA (uncurryN f) (commaN x1 x2 ... xn) > while a banana bracket (| f x1 x2 ... xn |) translates very roughly to > liftA' (uncurryN f) (andAn x1 x2 ... xn) But in an Applicative or Idiom bracket expression of the form (| f x1 ... xn |), f is a pure function. In the Applicative banana bracket, the expression that is in f's position is *not* pure, instead it's an operator on arrows. In the GHC users' guide we have https://downloads.haskell.org/~ghc/7.2.2/docs/html/users_guide/arrow-notation.html untilA :: ArrowChoice a => a e () -> a e Bool -> a e () ... ... (|untilA (increment -< x+y) (within 0.5 -< x)|) untilA is manifestly not a pure function. So, I don't think these brackets are the same thing. I may have been wrong to say they are not related, but I can't see that there's as close a correspondence as you are trying to make out. Tom From qdunkan at gmail.com Mon Dec 14 20:28:39 2015 From: qdunkan at gmail.com (Evan Laforge) Date: Mon, 14 Dec 2015 12:28:39 -0800 Subject: [Haskell-cafe] a problem I can't solve simply In-Reply-To: References: Message-ID: You have separate streams of overlapping events, so if you merge them into one stream your life will be easier: mergeOn key = Data.List.Ordered.mergeBy (Data.Ord.comparing key) computeEndMsr begin = findEnd begin . skip . mergeOn fst where -- drop until the begin measure skip = dropWhile ((= measureOf (snd note) + 2 = Just (measureOf snd note) | otherwise = Nothing You'll need 'measureOf :: Time -> MeasureNumber', which means you can only have a single global time signature that never changes. All untested of course, but I think this should have at least some hints in it. Data.List.Ordered is from data-ordlist, which is generally useful. You also have an unstated precondition, which is that Staff is in time order, which is useful but a hassle to maintain. I myself would be open to advice on how to maintain a ordered invariant :) In my own program (which is also for music), I keep an Ordered flag, and map operations are categorized by whether they maintain or could destroy the order. Well, that's the plan at least. On Mon, Dec 14, 2015 at 2:39 AM, Dennis Raddle wrote: > I have a problem that doesn't seem hard to state but I can't seem to solve > without a bunch of complex code. > > This relates to my musical score playback. In using it to play music, I > don't always want to play back the entire source musical document, but > rather play a range of measures. So I might give a command to my app like > "play 1-3" which means play measures 1 through 3. > > There is a time saving feature, which is that I can type "play 10" which > means start the playback at measure 10 and continue until the first > occurrence of two empty measures. This is a common use case. > > So I have to write a function that takes a start measure and computes the > end measure by scanning for two empty measures. > > Let's say for simplicity's sake that we'll forget about "measures" and just > say that notes have a start time and end time, which will be integers. > > type Note = (Int,Int) > > A musical score can have several individual staves (notes for individual > instruments), so it will look like this: > > type Staff = [Note] > > type Score = [Staff] > > I need to write a function as follows > > computeEndMsr :: Int -> Score -> Int > computeEndMsr beginMsr score = ... > > Some examples: > > Here's a score with just one staff, to give you an idea. > > score1 = [ [(1,3), (2,4), (7,10)] ] > > -- In the following case a two-unit gap is found at units 5 and 6. > computeEndMsr 1 score1 = 4 > > computeEndMsr 5 score1 = should throw an error indicating that a gap was > found immediately and no actual notes were included > > -- In the following case, the maximum unit of any note is 10, so that is > what is computed > computeEndMsr 6 score1 = 10 > > -- This case illustrates how it's okay if the computed end measure is equal > to the begin msr > computeEndMsr 10 score1 = 10 > > computeEndMsr 11 score1 = should throw an error indicating that the given > begin msr is past the end of any note in the score > > This example has only one staff, but a score can have multiple staves. Also > the timing and duration of notes can overlap, either on one staff or across > multiple staves. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > From johannes.waldmann at htwk-leipzig.de Mon Dec 14 22:30:52 2015 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Mon, 14 Dec 2015 23:30:52 +0100 Subject: [Haskell-cafe] sum $ map f xs ... ghc-7.10 performance regression? Message-ID: <566F431C.8090502@htwk-leipzig.de> Is there a difference between "sum $ map f xs" and "sum $! map f xs"? I would think no, since "$!" just evaluates the argument to WHNF, so it would evaluate just the first cons of the list. This little program main = print $ sum $ map bitcount [0, 4 .. 2^24-1 ] bitcount :: Int -> Int bitcount x = if x > 0 then let (d,m) = divMod x 2 in bitcount d + m else 0 runs in 1.6 seconds when compiled with -O2 on ghc-7.6.3, ghc-7.8.4, but takes 3.2 seconds on ghc-7.10.[1-3]. Why? when I change the main function (note: $ => $!) to main = print $ sum $! map bitcount [0, 4 .. 2^24-1 ] and compile with 7.10.[1-3], then it also runs in 1.6 seconds. (I can write a bug report but I want to check whether I am missing something obvious) - J.W. From lists at qseep.net Mon Dec 14 23:34:21 2015 From: lists at qseep.net (Lyle Kopnicky) Date: Mon, 14 Dec 2015 15:34:21 -0800 Subject: [Haskell-cafe] Trouble installing ghc on CentOS 6 Message-ID: Hi folks, I'm trying to install the 64-bit generic Linux distribution of ghc-7.10.3 on CentOS 6, as a non-privileged user in my home dir. I've unpacked the files, and I ran ./configure, but it told me it couldn't find libgmp.so.3. I searched for and found that library on the system. Looking at the help for ./configure, I saw the --with-gmp-libraries option, so I tried again with that, but it still can't seem to find the file: $ ./configure --prefix=/home/kopnicky/ghc --with-gmp-libraries=/usr/lib64 checking for path to top of build tree... utils/ghc-pwd/dist-install/build/tmp/ghc-pwd: error while loading shared libraries: libgmp.so.3: cannot open shared object file: No such file or directory configure: error: cannot determine current directory Strange, because that library is definitely there in /usr/lib64. Any thoughts on what I can try next? Thanks, Lyle -------------- next part -------------- An HTML attachment was scrubbed... URL: From anselm.scholl at tu-harburg.de Tue Dec 15 00:20:16 2015 From: anselm.scholl at tu-harburg.de (Jonas Scholl) Date: Tue, 15 Dec 2015 01:20:16 +0100 Subject: [Haskell-cafe] sum $ map f xs ... ghc-7.10 performance regression? In-Reply-To: <566F431C.8090502@htwk-leipzig.de> References: <566F431C.8090502@htwk-leipzig.de> Message-ID: <566F5CC0.3000109@tu-harburg.de> -----BEGIN PGP SIGNED MESSAGE----- Hash: SHA256 If you look at the memory usage, the version without the bang actually contains a space leak, so that's the source of the longer runtime. I hope you do not mind some core from ghc ; ) With the bang, we have the following main loop: - -- strict acculumator function over a list, good (worker from sum) Rec { $wgo :: [Int] -> Int# -> Int# $wgo = \ (w :: [Int]) (ww :: Int#) -> case w of _ { [] -> ww; : y ys -> case y of _ { I# y1 -> $wgo ys (+# ww y1) } } end Rec } - -- builds a list, lazy (i.e. no space leak) main3 :: Int -> [Int] -> [Int] main3 = \ (x :: Int) (ys :: [Int]) -> : (bitcount x) ys main2 :: String main2 = case $w$s^ main5 main4 of ww { __DEFAULT -> -- calculate 2^24 case efdtIntUpFB main3 ([]) 0 4 (-# ww 1) of vx { __DEFAULT -> -- loop function, desugared from [a, b..c] case $wgo vx 0 of ww1 { __DEFAULT -> -- sum up the list case $wshowSignedInt 0 ww1 ([]) of _ { (# ww5, ww6 #) -> -- only shows the result, not important : ww5 ww6 } } } } So we build a lazy list with bitcount applied to all arguments. All the stuff is boxed for some reason, so we allocate some stuff, just to throw it away, but it is never held on for long, so our memory usage never gets past 1MB (and thus GC stays cheap). This list is then deconstructed by $wgo again, forcing one element at the time and accumulated into a Int#. Without the bang, the main loops looks something like this: - -- This is interesting. The first argument seems to be the number from the list and the third is our accumulator while the second seems to start as the identity function (from main2 second case). main4 :: Int -> (Int -> Int) -> Int -> Int main4 = \ (x :: Int) (ys :: Int -> Int) (tpl :: Int) -> ys (case tpl of _ { I# x1 -> case x of _ { I# ww1 -> case $wbitcount ww1 of ww2 { __DEFAULT -> I# (+# x1 ww2) } } }) main2 :: String main2 = case $w$s^ main6 main5 of ww { __DEFAULT -> -- calculate 2^24 case efdtIntUpFB main4 (id) 0 4 (-# ww 1) main3 of _ { I# ww3 -> -- loop function, desugared from [a, b..c], but instead of building a list we do something like a difference-list, but with ints (note that we now have 7 arguments instead of 6) case $wshowSignedInt 0 ww3 ([]) of _ { (# ww5, ww6 #) -> -- only shows the result, not important : ww5 ww6 } } } efdtIntUpFB seems to be something like this: efdtIntUpFB :: (Int -> acc -> acc) -> acc -> Int# -> Int# -> Int# -> acc efdtIntUpFB f acc x step max = if x > max then acc else f x (efdtIntUpFB f acc (x + step) step max) (Actual implementation: http://hackage.haskell.org/package/base-4.8.1.0/docs/src/GHC.Enum.html#efdtIntUpFB) But acc now resoves to Int -> Int. So if we exand this, we get: main4 0 (main4 4 (main4 8 ... (main4 ... id) ...))) And main4 builds a closure and applies this to ys. Then we enter ys, which is again main4, building a closure and apply this to ys, which is again main4, which builds a closure and finally applies this to id (after 2^22 closures or something like that). So we leak a few hundered MB (423 on my machine) which we have to copy every time we do a (full) GC. On my machine 0.5 sec are spend on full GC, another 0.5 on a few more minor GCs and 1 sec actually computing, which is somewhat similar to your results. So, that much about the space leak. The reason for the difference seems to manifest itself after the first float-out pass, somehow the simplifier rebuilds the expression differently... but right now I do not see what exactly is happening there and why. My first though was a different set of rules from the list fusion stuff fires, but at least the names and order of the rule firings are exactly the same... But the more I think about it, the more I think this is a bug. The following program leaks a similar amount of space: main = print bar bar :: Int bar = sum $ map (\x -> x) [1,2..2^24-1] There is a special rule for map id, so we avoid it, a function doing actual work (like bitcount) would yield the same result. Using [1..2^24-1] yields an efficient program, so something with the combination of sum, map and enumFromThenTo seems to be broken. So yes, I would argue that you indeed did hit a bug. On 12/14/2015 11:30 PM, Johannes Waldmann wrote: > Is there a difference between "sum $ map f xs" and "sum $! map f xs"? > > I would think no, since "$!" just evaluates the argument to WHNF, > so it would evaluate just the first cons of the list. > > > This little program > > main = print $ sum $ map bitcount [0, 4 .. 2^24-1 ] > > bitcount :: Int -> Int > bitcount x = > if x > 0 then let (d,m) = divMod x 2 in bitcount d + m else 0 > > runs in 1.6 seconds when compiled with -O2 > on ghc-7.6.3, ghc-7.8.4, > > but takes 3.2 seconds on ghc-7.10.[1-3]. Why? > > > when I change the main function (note: $ => $!) to > > main = print $ sum $! map bitcount [0, 4 .. 2^24-1 ] > > and compile with 7.10.[1-3], then it also runs in 1.6 seconds. > > > (I can write a bug report but I want to check > whether I am missing something obvious) > > > - J.W. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe -----BEGIN PGP SIGNATURE----- Version: GnuPG v2 iQEcBAEBCAAGBQJWb1y3AAoJEM0PYZBmfhoBqNAH/1QNNvZ84We9b0RUtb6w5gNt 6u9yzw5DxMBsxdHgEWlbc7vXOLpeCXaPhLMKYVFnNDHwwx4c+CPWZd44YUCZtLOd Xi9sCAHMJX5vDxfhFgCzwBP39KsMr+Euhde+thIBjlAmM/IKJLC1h1tjtoYUOMle W9AMzIoVetHSWA5MqgX+LjpNiMifTnXNy+6yx8aytCtRKo2hiGs9tWSzCE58a8XM EY3cFSzbqy1IHsq9xwycjfpTvpUt1Ga8jjmhwilhjdREIYwWmc6qT2vAiAGf4nPn gx9SoMIlAmgbcV/xMSUha2YZ5QzG9deYTIZ7SYLfcaTev1/QMKmONgHX4uWTRFU= =rHVH -----END PGP SIGNATURE----- From tkoster at gmail.com Tue Dec 15 00:40:03 2015 From: tkoster at gmail.com (Thomas Koster) Date: Tue, 15 Dec 2015 11:40:03 +1100 Subject: [Haskell-cafe] Need ideas how to model the lack of something In-Reply-To: <566E61A1.9070500@durchholz.org> References: <566DD1FF.3090700@web.de> <566E61A1.9070500@durchholz.org> Message-ID: On Mon, Dec 14, 2015 at 3:15 AM, martin wrote: > I started like this > > data C a = C { > insert :: a -> Maybe (C a), > remove :: Maybe (a, C a) > } > > but I could not implement anything sensible on top of this. Am 14.12.2015 um 01:28 schrieb Kim-Ee Yeoh: > And the reason you're stuck implementing anything sensible on top of this > is because you've written an OOP-style specification of a data structure. On 14 December 2015 at 17:28, Joachim Durchholz wrote: > Mmm... this is the second time this has been raised. > What's the problem with OOP style? Something specific with Haskell, > something about OOP in general, something else? Nothing nefarious: Object-oriented style in Haskell is wordy and unnatural for no other reason than that Haskell is a functional programming language and not an object-oriented language. Haskell is not a multi-paradigm language like Scala. -- Thomas Koster From rf at rufflewind.com Tue Dec 15 05:21:42 2015 From: rf at rufflewind.com (Phil Ruffwind) Date: Tue, 15 Dec 2015 00:21:42 -0500 Subject: [Haskell-cafe] sum $ map f xs ... ghc-7.10 performance regression? In-Reply-To: <566F5CC0.3000109@tu-harburg.de> References: <566F431C.8090502@htwk-leipzig.de> <566F5CC0.3000109@tu-harburg.de> Message-ID: sum for lists is implemented using foldl rather than foldl' so I suspect that's the origin of the issue. Somehow, ($!) seems to give GHC enough of a hint so as to optimize smarter thereby avoiding the thunk build-up. I don't know how this occurs though. From tkoster at gmail.com Tue Dec 15 06:15:53 2015 From: tkoster at gmail.com (Thomas Koster) Date: Tue, 15 Dec 2015 17:15:53 +1100 Subject: [Haskell-cafe] sum $ map f xs ... ghc-7.10 performance regression? In-Reply-To: References: <566F431C.8090502@htwk-leipzig.de> <566F5CC0.3000109@tu-harburg.de> Message-ID: On 15 December 2015 at 09:30, Johannes Waldmann wrote: > Is there a difference between "sum $ map f xs" and "sum $! map f xs"? > > I would think no, since "$!" just evaluates the argument to WHNF, > so it would evaluate just the first cons of the list. > > This little program > > main = print $ sum $ map bitcount [0, 4 .. 2^24-1 ] > > bitcount :: Int -> Int > bitcount x = > if x > 0 then let (d,m) = divMod x 2 in bitcount d + m else 0 > > runs in 1.6 seconds when compiled with -O2 > on ghc-7.6.3, ghc-7.8.4, > > but takes 3.2 seconds on ghc-7.10.[1-3]. Why? > > when I change the main function (note: $ => $!) to > > main = print $ sum $! map bitcount [0, 4 .. 2^24-1 ] > > and compile with 7.10.[1-3], then it also runs in 1.6 seconds. On 15 December 2015 at 11:20, Jonas Scholl wrote: > The reason for the difference seems > to manifest itself after the first float-out pass, somehow the > simplifier rebuilds the expression differently... but right now I do not > see what exactly is happening there and why. My first though was a > different set of rules from the list fusion stuff fires, but at least > the names and order of the rule firings are exactly the same... But the > more I think about it, the more I think this is a bug. On 15 December 2015 at 16:21, Phil Ruffwind wrote: > sum for lists is implemented using foldl rather than foldl' so I > suspect that's the origin of the issue. Somehow, ($!) seems to give > GHC enough of a hint so as to optimize smarter thereby avoiding the > thunk build-up. I don't know how this occurs though. Phil, I think that was true in 7.8, but if I'm reading the haddocks correctly, Data.List.sum = Data.Foldable.sum in 7.10, and Data.Foldable.sum uses foldMap/foldr. I don't have 7.8 handy at the moment, but the 7.8 base probably would have used the definition now in GHC.OldList, which uses foldl as you say. The switch from foldl to foldr might be a factor in the list fusion issue hinted by Jonas. Since foldl is almost always used incorrectly by beginners (right?), I wouldn't be surprised if the reason the space leak is magically eliminated in 7.8 is because of beginner-friendly rewrite rules and strictness analyses targeted at foldl. -- Thomas Koster From jo at durchholz.org Tue Dec 15 07:33:53 2015 From: jo at durchholz.org (Joachim Durchholz) Date: Tue, 15 Dec 2015 08:33:53 +0100 Subject: [Haskell-cafe] Need ideas how to model the lack of something In-Reply-To: References: <566DD1FF.3090700@web.de> <566E61A1.9070500@durchholz.org> Message-ID: <566FC261.50302@durchholz.org> Am 15.12.2015 um 01:40 schrieb Thomas Koster: > On Mon, Dec 14, 2015 at 3:15 AM, martin wrote: >> I started like this >> >> data C a = C { >> insert :: a -> Maybe (C a), >> remove :: Maybe (a, C a) >> } >> >> but I could not implement anything sensible on top of this. > > Am 14.12.2015 um 01:28 schrieb Kim-Ee Yeoh: >> And the reason you're stuck implementing anything sensible on top of this >> is because you've written an OOP-style specification of a data structure. > > On 14 December 2015 at 17:28, Joachim Durchholz wrote: >> Mmm... this is the second time this has been raised. >> What's the problem with OOP style? Something specific with Haskell, >> something about OOP in general, something else? > > Nothing nefarious: Object-oriented style in Haskell is wordy and > unnatural for no other reason than that Haskell is a functional > programming language and not an object-oriented language. I see Kim-Ee Yeoh stating that Martin is stuck without a way forward due to using OO style, which seems more serious than just "wordy and unnatural". Or am I misreading his words, and that "OO-style" reference was just descriptive rather than presenting the base cause of Martin's problems? Regards, Jo P.S.: I'm not trying to criticize anything, just trying to understand what the issue is. Is there a webpage like "Haskell for OO-warped minds" that explains how to transition one's idioms? I have a good grasp of Haskell in-the-small, but I haven't had an opportunity to learn the larger-scale issues, so I'm probably just being dense and would like to change that. From carlo at carlo-hamalainen.net Tue Dec 15 08:02:05 2015 From: carlo at carlo-hamalainen.net (Carlo Hamalainen) Date: Tue, 15 Dec 2015 16:02:05 +0800 Subject: [Haskell-cafe] Need ideas how to model the lack of something In-Reply-To: <566FC261.50302@durchholz.org> References: <566DD1FF.3090700@web.de> <566E61A1.9070500@durchholz.org> <566FC261.50302@durchholz.org> Message-ID: <566FC8FD.4040400@carlo-hamalainen.net> On 15/12/2015 15:33, Joachim Durchholz wrote: > I see Kim-Ee Yeoh stating that Martin is stuck without a way forward > due to using OO style, which seems more serious than just "wordy and > unnatural". > Or am I misreading his words, and that "OO-style" reference was just > descriptive rather than presenting the base cause of Martin's problems? The OP originally wrote an insert function with this type: insert :: a -> Maybe (C a) which sort of looks like an insert function from an OO language where the self object is implicit. In functional style it should be insert :: a -> C a -> Maybe (C a) Another way: it's impossible to implement insert :: a -> Maybe (C a) insert a = ??? because there is no 'C a' to modify. -- Carlo Hamalainen http://carlo-hamalainen.net From dedgrant at gmail.com Tue Dec 15 08:06:13 2015 From: dedgrant at gmail.com (Darren Grant) Date: Tue, 15 Dec 2015 19:06:13 +1100 Subject: [Haskell-cafe] Need ideas how to model the lack of something In-Reply-To: <566FC8FD.4040400@carlo-hamalainen.net> References: <566DD1FF.3090700@web.de> <566E61A1.9070500@durchholz.org> <566FC261.50302@durchholz.org> <566FC8FD.4040400@carlo-hamalainen.net> Message-ID: 'insert' is a record accessor, so there is an implied (C a). Cheers, D On Dec 15, 2015 00:02, "Carlo Hamalainen" wrote: > On 15/12/2015 15:33, Joachim Durchholz wrote: > > I see Kim-Ee Yeoh stating that Martin is stuck without a way forward > > due to using OO style, which seems more serious than just "wordy and > > unnatural". > > Or am I misreading his words, and that "OO-style" reference was just > > descriptive rather than presenting the base cause of Martin's problems? > > The OP originally wrote an insert function with this type: > > insert :: a -> Maybe (C a) > > which sort of looks like an insert function from an OO language where > the self object is implicit. In functional style it should be > > insert :: a -> C a -> Maybe (C a) > > Another way: it's impossible to implement > > insert :: a -> Maybe (C a) > insert a = ??? > > because there is no 'C a' to modify. > > -- > Carlo Hamalainen > http://carlo-hamalainen.net > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From rf at rufflewind.com Tue Dec 15 08:11:27 2015 From: rf at rufflewind.com (Phil Ruffwind) Date: Tue, 15 Dec 2015 03:11:27 -0500 Subject: [Haskell-cafe] sum $ map f xs ... ghc-7.10 performance regression? In-Reply-To: References: <566F431C.8090502@htwk-leipzig.de> <566F5CC0.3000109@tu-harburg.de> Message-ID: On Tue, Dec 15, 2015 at 1:15 AM, Thomas Koster wrote: > Phil, I think that was true in 7.8, but if I'm reading the haddocks > correctly, Data.List.sum = Data.Foldable.sum in 7.10, and > Data.Foldable.sum uses foldMap/foldr. According to the source code for base-4.8 (GHC 7.10), sum is specialized to GHC.List.sum for lists. https://hackage.haskell.org/package/base-4.8.1.0/docs/src/Data.Foldable.html#Foldable From johannes.waldmann at htwk-leipzig.de Tue Dec 15 08:47:18 2015 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Tue, 15 Dec 2015 09:47:18 +0100 Subject: [Haskell-cafe] sum $ map f xs ... ghc-7.10 performance regression? In-Reply-To: References: <566F431C.8090502@htwk-leipzig.de> <566F5CC0.3000109@tu-harburg.de> Message-ID: <566FD396.3030706@htwk-leipzig.de> cross-reference: https://ghc.haskell.org/trac/ghc/ticket/11226 From johannes.waldmann at htwk-leipzig.de Tue Dec 15 08:53:59 2015 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Tue, 15 Dec 2015 09:53:59 +0100 Subject: [Haskell-cafe] Hyperlinked source - was: Re: sum $ map f xs ... ghc-7.10 performance regression? In-Reply-To: References: <566F431C.8090502@htwk-leipzig.de> <566F5CC0.3000109@tu-harburg.de> Message-ID: <566FD527.50902@htwk-leipzig.de> > According to the source code [...] > https://hackage.haskell.org/package/base-4.8.1.0/docs/src/Data.Foldable.html#Foldable Ah - source code is hyperlinked! Finally! I want that! How does this work? - J.W. From martin.drautzburg at web.de Tue Dec 15 09:25:41 2015 From: martin.drautzburg at web.de (martin) Date: Tue, 15 Dec 2015 10:25:41 +0100 Subject: [Haskell-cafe] Need ideas how to model the lack of something In-Reply-To: <566FC261.50302@durchholz.org> References: <566DD1FF.3090700@web.de> <566E61A1.9070500@durchholz.org> <566FC261.50302@durchholz.org> Message-ID: <566FDC95.2030000@web.de> Am 12/15/2015 um 08:33 AM schrieb Joachim Durchholz: >> On 14 December 2015 at 17:28, Joachim Durchholz wrote: >>> Mmm... this is the second time this has been raised. >>> What's the problem with OOP style? Something specific with Haskell, >>> something about OOP in general, something else? > > P.S.: I'm not trying to criticize anything, just trying to understand what the issue is. > Is there a webpage like "Haskell for OO-warped minds" that explains how to transition one's idioms? I have a good grasp > of Haskell in-the-small, but I haven't had an opportunity to learn the larger-scale issues, so I'm probably just being > dense and would like to change that. I'd be interested in that "Haskell for OO-warped minds" too. As for my specific question, here's what I believe I've learned. Abstract classes or interfaces are commonplace in the OO world. But even there you have to provide a concrete implementation eventually. While you can program in a similar style in haskell by using typeclasses, haskellers tend to start with a concrete implementation and then use typeclasses to express commonalities of concrete implementations. While some data types, particularly those which wrap functions (the simplest of which is probably the state monad), look like they are providing an abstract interface to a computation, they are actually concrete things. Or take the List data type: it is not just something you can prepend an element to, express an empty list and split it into head and tail, but really a concrete thing, which allows implementing these operations. You could implement these three operations (:, head, tail) and the constant [] on top of other data structures, but this would not make them a List. Some time ago I asked the question, whether you have a choice between using a newtype/data or a typeclass and if so which is the preferred approach. The answer was yes, these two concepts can occasionally replace each other and "short answer: use data". This was one reason why I didn't even try to use a typeclass in my problem here. Now I believe that I misread "short answer: use data" as using the "data" keyword. What it really meant is: "be concrete". From johannes.waldmann at htwk-leipzig.de Tue Dec 15 13:58:18 2015 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Tue, 15 Dec 2015 14:58:18 +0100 Subject: [Haskell-cafe] Trouble installing ghc on CentOS 6 Message-ID: <56701C7A.8000007@htwk-leipzig.de> I think that "--with-gmp-libraries" states the location of libgmp that the installed ghc will use when linking programs. Your error indicates that a .so file referenced from the executable (contained in the binary package) "utils/ghc-pwd/dist-install/build/tmp/ghc-pwd" could not be resolved. $ ldd utils/ghc-pwd/dist-install/build/tmp/ghc-pwd if it says ... libgmp.so.3 => not found then set LD_LIBRARY_PATH or check values in /etc/ld.so.conf and run /sbin/ldconfig - J.W. From david.feuer at gmail.com Tue Dec 15 19:20:24 2015 From: david.feuer at gmail.com (David Feuer) Date: Tue, 15 Dec 2015 14:20:24 -0500 Subject: [Haskell-cafe] Does Backwards admit a Monad instance? Message-ID: In particular, I'm thinking about instance MonadFix m => Monad (Backwards m) where m >>= f = Backwards $ do fin <- forwards (f int) int <- forwards m return fin It looks to me like this should be valid, and compatible with the Applicative instance, but maybe I'm missing something. -------------- next part -------------- An HTML attachment was scrubbed... URL: From heraldhoi at gmail.com Tue Dec 15 19:26:11 2015 From: heraldhoi at gmail.com (Geraldus) Date: Tue, 15 Dec 2015 19:26:11 +0000 Subject: [Haskell-cafe] Hyperlinked source - was: Re: sum $ map f xs ... ghc-7.10 performance regression? In-Reply-To: <566FD527.50902@htwk-leipzig.de> References: <566F431C.8090502@htwk-leipzig.de> <566F5CC0.3000109@tu-harburg.de> <566FD527.50902@htwk-leipzig.de> Message-ID: Amazing! (: ??, 15 ???. 2015 ?. ? 13:55, Johannes Waldmann < johannes.waldmann at htwk-leipzig.de>: > > > According to the source code [...] > > > https://hackage.haskell.org/package/base-4.8.1.0/docs/src/Data.Foldable.html#Foldable > > Ah - source code is hyperlinked! Finally! > I want that! How does this work? > > - J.W. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From lists at qseep.net Tue Dec 15 21:13:33 2015 From: lists at qseep.net (Lyle Kopnicky) Date: Tue, 15 Dec 2015 13:13:33 -0800 Subject: [Haskell-cafe] Trouble installing ghc on CentOS 6 In-Reply-To: <56701C7A.8000007@htwk-leipzig.de> References: <56701C7A.8000007@htwk-leipzig.de> Message-ID: Thanks! The whole problem was that I had accidentally downloaded the 32-bit version, when I meant to get the 64-bit version. It works without any extra flags beyond --prefix. On Tue, Dec 15, 2015 at 5:58 AM, Johannes Waldmann < johannes.waldmann at htwk-leipzig.de> wrote: > I think that "--with-gmp-libraries" > states the location of libgmp that the installed ghc > will use when linking programs. > > Your error indicates that a .so file referenced > from the executable (contained in the binary package) > "utils/ghc-pwd/dist-install/build/tmp/ghc-pwd" > could not be resolved. > > $ ldd utils/ghc-pwd/dist-install/build/tmp/ghc-pwd > > if it says ... libgmp.so.3 => not found > then set LD_LIBRARY_PATH > or check values in /etc/ld.so.conf and run /sbin/ldconfig > > - J.W. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Tue Dec 15 22:43:14 2015 From: david.feuer at gmail.com (David Feuer) Date: Tue, 15 Dec 2015 17:43:14 -0500 Subject: [Haskell-cafe] Does Backwards admit a Monad instance? In-Reply-To: References: Message-ID: I realized this does not quite satisfy the law pure x >>= f = f x In particular, pure () >>= (\() -> m) :: Backwards m is a divergent computation whenever m is a "strict" monad. Things seem somewhat nicer when m is "lazy", but there could be further problems I've overlooked. On Tue, Dec 15, 2015 at 2:20 PM, David Feuer wrote: > In particular, I'm thinking about > > instance MonadFix m => Monad (Backwards m) where > m >>= f = Backwards $ > do > fin <- forwards (f int) > int <- forwards m > return fin > > It looks to me like this should be valid, and compatible with the > Applicative instance, but maybe I'm missing something. From tkoster at gmail.com Tue Dec 15 23:06:48 2015 From: tkoster at gmail.com (Thomas Koster) Date: Wed, 16 Dec 2015 10:06:48 +1100 Subject: [Haskell-cafe] sum $ map f xs ... ghc-7.10 performance regression? In-Reply-To: References: <566F431C.8090502@htwk-leipzig.de> <566F5CC0.3000109@tu-harburg.de> Message-ID: On Tue, Dec 15, 2015 at 1:15 AM, Thomas Koster wrote: > Phil, I think that was true in 7.8, but if I'm reading the haddocks > correctly, Data.List.sum = Data.Foldable.sum in 7.10, and > Data.Foldable.sum uses foldMap/foldr. On 15 December 2015 at 19:11, Phil Ruffwind wrote: > According to the source code for base-4.8 (GHC 7.10), sum is > specialized to GHC.List.sum for lists. > > https://hackage.haskell.org/package/base-4.8.1.0/docs/src/Data.Foldable.html#Foldable My mistake. I didn't read past this: class Foldable t where foldMap f = foldr (mappend . f) mempty sum = getSum #. foldMap Sum instance Foldable [] where foldr = List.foldr -- Thomas Koster From tkoster at gmail.com Tue Dec 15 23:24:05 2015 From: tkoster at gmail.com (Thomas Koster) Date: Wed, 16 Dec 2015 10:24:05 +1100 Subject: [Haskell-cafe] Need ideas how to model the lack of something In-Reply-To: <566FC261.50302@durchholz.org> References: <566DD1FF.3090700@web.de> <566E61A1.9070500@durchholz.org> <566FC261.50302@durchholz.org> Message-ID: On Mon, Dec 14, 2015 at 3:15 AM, martin wrote: > I started like this > > data C a = C { > insert :: a -> Maybe (C a), > remove :: Maybe (a, C a) > } > > but I could not implement anything sensible on top of this. Am 14.12.2015 um 01:28 schrieb Kim-Ee Yeoh: > And the reason you're stuck implementing anything sensible on top of this > is because you've written an OOP-style specification of a data structure. On 14 December 2015 at 17:28, Joachim Durchholz wrote: > Mmm... this is the second time this has been raised. > What's the problem with OOP style? Something specific with Haskell, > something about OOP in general, something else? On 15 December 2015 at 11:40, Thomas Koster wrote: > Nothing nefarious: Object-oriented style in Haskell is wordy and > unnatural for no other reason than that Haskell is a functional > programming language and not an object-oriented language. Haskell is > not a multi-paradigm language like Scala. On 15/12/2015 15:33, Joachim Durchholz wrote: > I see Kim-Ee Yeoh stating that Martin is stuck without a way forward > due to using OO style, which seems more serious than just "wordy and > unnatural". > Or am I misreading his words, and that "OO-style" reference was just > descriptive rather than presenting the base cause of Martin's problems? Sorry, my answer was specifically to your question: "What's the problem with OOP style [in Haskell]?" It doesn't help Martin. -- Thomas Koster From capn.freako at gmail.com Wed Dec 16 13:08:33 2015 From: capn.freako at gmail.com (David Banas) Date: Wed, 16 Dec 2015 05:08:33 -0800 Subject: [Haskell-cafe] IHaskell trouble, after upgrading to Haskell Platform 7.10.3? Message-ID: Hi all, Are there any other IHaskell users out there, who are having trouble re-installing IHaskell, after upgrading to Haskell Platform 7.10.3? I?m getting this, at the tail end of the actual ihaskell build: [24 of 25] Compiling IHaskell.Eval.Info ( src/IHaskell/Eval/Info.hs, dist/build/IHaskell/Eval/Info.o ) [25 of 25] Compiling IHaskell.Publish ( src/IHaskell/Publish.hs, dist/build/IHaskell/Publish.o ) In-place registering ihaskell-0.8.3.0... Preprocessing executable 'ihaskell' for ihaskell-0.8.3.0... main/Main.hs:29:18: Could not find module ?Data.String.Here? It is a member of the hidden package ?here-1.2.7 at here_63mTmLx8Sz20TyEJBVCnnC?. Perhaps you need to add ?here? to the build-depends in your .cabal file. Use -v to see a list of the files searched for. Updating documentation index /Users/dbanas/Library/Haskell/share/doc/x86_64-osx-ghc-7.10.3/index.html cabal: Error: some packages failed to install: ihaskell-0.8.3.0 failed during the building phase. The exception was: ExitFailure 1 Thanks, and Happy Holidays! -db -------------- next part -------------- An HTML attachment was scrubbed... URL: From adam at bergmark.nl Wed Dec 16 13:30:43 2015 From: adam at bergmark.nl (Adam Bergmark) Date: Wed, 16 Dec 2015 14:30:43 +0100 Subject: [Haskell-cafe] IHaskell trouble, after upgrading to Haskell Platform 7.10.3? In-Reply-To: References: Message-ID: It looks like that version of ihaskell is broken, the dependency is missing in the cabal file. Could it be that you are trying to install a later version than you had compiled on <7.10.3? The maintainer will probably be interested in hearing about this. HTH, Adam On Wed, Dec 16, 2015 at 2:08 PM, David Banas wrote: > Hi all, > > Are there any other IHaskell users out there, who are having trouble > re-installing IHaskell, after upgrading to Haskell Platform 7.10.3? > I?m getting this, at the tail end of the actual ihaskell build: > > [24 of 25] Compiling IHaskell.Eval.Info ( src/IHaskell/Eval/Info.hs, > dist/build/IHaskell/Eval/Info.o ) > [25 of 25] Compiling IHaskell.Publish ( src/IHaskell/Publish.hs, > dist/build/IHaskell/Publish.o ) > In-place registering ihaskell-0.8.3.0... > Preprocessing executable 'ihaskell' for ihaskell-0.8.3.0... > > main/Main.hs:29:18: > Could not find module ?Data.String.Here? > It is a member of the hidden package > ?here-1.2.7 at here_63mTmLx8Sz20TyEJBVCnnC?. > Perhaps you need to add ?here? to the build-depends in your .cabal > file. > Use -v to see a list of the files searched for. > Updating documentation index > /Users/dbanas/Library/Haskell/share/doc/x86_64-osx-ghc-7.10.3/index.html > cabal: Error: some packages failed to install: > ihaskell-0.8.3.0 failed during the building phase. The exception was: > ExitFailure 1 > > Thanks, and Happy Holidays! > -db > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From johannes.waldmann at htwk-leipzig.de Wed Dec 16 13:55:40 2015 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Wed, 16 Dec 2015 14:55:40 +0100 Subject: [Haskell-cafe] Hyperlinked source docs Message-ID: <56716D5C.5040308@htwk-leipzig.de> As I said, I admire hyperlinked sources in the new "base" documentation https://hackage.haskell.org/package/base-4.8.1.0/docs/ and I want to know how I can produce such documents. What is the magic haddock/hscolour invocation? (I actually use standalone-haddock.) On hackage, not every package gets the special treatment? (In fact, only "base" does?) - J.W. From adam at bergmark.nl Wed Dec 16 14:00:20 2015 From: adam at bergmark.nl (Adam Bergmark) Date: Wed, 16 Dec 2015 15:00:20 +0100 Subject: [Haskell-cafe] Hyperlinked source docs In-Reply-To: <56716D5C.5040308@htwk-leipzig.de> References: <56716D5C.5040308@htwk-leipzig.de> Message-ID: I think the hyperlinked docs for base were uploaded manually. Hackage is probably still using an earlier version of haddock. Can't help with how to use it though unfortunately. - Adam On Wed, Dec 16, 2015 at 2:55 PM, Johannes Waldmann < johannes.waldmann at htwk-leipzig.de> wrote: > As I said, I admire hyperlinked sources > in the new "base" documentation > https://hackage.haskell.org/package/base-4.8.1.0/docs/ > > and I want to know how I can produce such documents. > What is the magic haddock/hscolour invocation? > (I actually use standalone-haddock.) > > On hackage, not every package gets the special treatment? > (In fact, only "base" does?) > > - J.W. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From spacestation at venussociety.org Wed Dec 16 14:11:33 2015 From: spacestation at venussociety.org (spacestation at venussociety.org) Date: Wed, 16 Dec 2015 14:11:33 +0000 (GMT) Subject: [Haskell-cafe] Parallel Haskell on RPi2 Message-ID: <899752240.71288.00c4b038-5bfd-4914-829e-f81b45e74c50.open-xchange@webmail.123-reg.co.uk> Hello to everone, Did anybody manage to install parconc-examples on a Raspberry Pi2 without the use of --force-reinstalls. As it would break to many packages on my end.I tried it the way describe from Simon Marlow s book "Parallel and concurrent programming in haskell". Or is there any option within cabal to seperate between new,new version and reinstall packages listed with pi at opencvrpi2:~/parconc-examples-master$ cabal install --only-dependencies I m using ghc 7.4.1 Thanks for any feedback Gottfried F. Zojer -------------- next part -------------- An HTML attachment was scrubbed... URL: From matthewtpickering at gmail.com Wed Dec 16 14:19:02 2015 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Wed, 16 Dec 2015 14:19:02 +0000 Subject: [Haskell-cafe] Hyperlinked source docs In-Reply-To: <56716D5C.5040308@htwk-leipzig.de> References: <56716D5C.5040308@htwk-leipzig.de> Message-ID: Here is how: 1. Build haddock from source (https://github.com/haskell/haddock) 2. cabal haddock --haddock-options="--hyperlinked-source" (if the new version is in your path, otherwise use --with-haddock=) 3. Manually upload the docs using a script (like this https://github.com/ekmett/lens/blob/master/scripts/hackage-docs.sh) Matt On Wed, Dec 16, 2015 at 1:55 PM, Johannes Waldmann wrote: > As I said, I admire hyperlinked sources > in the new "base" documentation > https://hackage.haskell.org/package/base-4.8.1.0/docs/ > > and I want to know how I can produce such documents. > What is the magic haddock/hscolour invocation? > (I actually use standalone-haddock.) > > On hackage, not every package gets the special treatment? > (In fact, only "base" does?) > > - J.W. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe From defigueiredo at ucdavis.edu Wed Dec 16 14:55:09 2015 From: defigueiredo at ucdavis.edu (Dimitri DeFigueiredo) Date: Wed, 16 Dec 2015 12:55:09 -0200 Subject: [Haskell-cafe] Hyperlinked source docs In-Reply-To: References: <56716D5C.5040308@htwk-leipzig.de> Message-ID: <56717B4D.20901@ucdavis.edu> This is indeed beautiful. Thank you for the information on how to do it! :-) Dimitri On 12/16/15 12:19 PM, Matthew Pickering wrote: > Here is how: > > 1. Build haddock from source (https://github.com/haskell/haddock) > 2. cabal haddock --haddock-options="--hyperlinked-source" (if the new > version is in your path, otherwise use --with-haddock=) > 3. Manually upload the docs using a script (like this > https://github.com/ekmett/lens/blob/master/scripts/hackage-docs.sh) > > Matt > > On Wed, Dec 16, 2015 at 1:55 PM, Johannes Waldmann > wrote: >> As I said, I admire hyperlinked sources >> in the new "base" documentation >> https://hackage.haskell.org/package/base-4.8.1.0/docs/ >> >> and I want to know how I can produce such documents. >> What is the magic haddock/hscolour invocation? >> (I actually use standalone-haddock.) >> >> On hackage, not every package gets the special treatment? >> (In fact, only "base" does?) >> >> - J.W. >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe From capn.freako at gmail.com Wed Dec 16 15:31:55 2015 From: capn.freako at gmail.com (David Banas) Date: Wed, 16 Dec 2015 07:31:55 -0800 Subject: [Haskell-cafe] IHaskell trouble, after upgrading to Haskell Platform 7.10.3? In-Reply-To: References: Message-ID: <6F55BE8B-BF22-4402-807B-96BDE4C469ED@gmail.com> Thanks, Adam. Following the suggestion in the error message, this worked for me: Davids-MacBook-Air-2:IHaskell dbanas$ git diff ihaskell.cabal diff --git a/ihaskell.cabal b/ihaskell.cabal index fb53441..9562240 100644 --- a/ihaskell.cabal +++ b/ihaskell.cabal @@ -147,7 +147,8 @@ executable ihaskell strict >=0.3, unix >= 2.6, directory -any, - ipython-kernel >=0.7 + ipython-kernel >=0.7, + here -any if flag(binPkgDb) build-depends: bin-package-db Davids-MacBook-Air-2:IHaskell dbanas$ -db On Dec 16, 2015, at 5:30 AM, Adam Bergmark wrote: > It looks like that version of ihaskell is broken, the dependency is missing in the cabal file. Could it be that you are trying to install a later version than you had compiled on <7.10.3? > > The maintainer will probably be interested in hearing about this. > > HTH, > Adam > > > On Wed, Dec 16, 2015 at 2:08 PM, David Banas wrote: > Hi all, > > Are there any other IHaskell users out there, who are having trouble re-installing IHaskell, after upgrading to Haskell Platform 7.10.3? > I?m getting this, at the tail end of the actual ihaskell build: > > [24 of 25] Compiling IHaskell.Eval.Info ( src/IHaskell/Eval/Info.hs, dist/build/IHaskell/Eval/Info.o ) > [25 of 25] Compiling IHaskell.Publish ( src/IHaskell/Publish.hs, dist/build/IHaskell/Publish.o ) > In-place registering ihaskell-0.8.3.0... > Preprocessing executable 'ihaskell' for ihaskell-0.8.3.0... > > main/Main.hs:29:18: > Could not find module ?Data.String.Here? > It is a member of the hidden package ?here-1.2.7 at here_63mTmLx8Sz20TyEJBVCnnC?. > Perhaps you need to add ?here? to the build-depends in your .cabal file. > Use -v to see a list of the files searched for. > Updating documentation index > /Users/dbanas/Library/Haskell/share/doc/x86_64-osx-ghc-7.10.3/index.html > cabal: Error: some packages failed to install: > ihaskell-0.8.3.0 failed during the building phase. The exception was: > ExitFailure 1 > > Thanks, and Happy Holidays! > -db > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From corentin.dupont at gmail.com Wed Dec 16 15:47:12 2015 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Wed, 16 Dec 2015 16:47:12 +0100 Subject: [Haskell-cafe] Hyperlinked source docs In-Reply-To: References: <56716D5C.5040308@htwk-leipzig.de> Message-ID: That's really great! That's a long awaited feature on my side. Do you plan to upload this version of haddock on hackage? On Wed, Dec 16, 2015 at 3:19 PM, Matthew Pickering < matthewtpickering at gmail.com> wrote: > Here is how: > > 1. Build haddock from source (https://github.com/haskell/haddock) > 2. cabal haddock --haddock-options="--hyperlinked-source" (if the new > version is in your path, otherwise use --with-haddock=) > 3. Manually upload the docs using a script (like this > https://github.com/ekmett/lens/blob/master/scripts/hackage-docs.sh) > > Matt > > On Wed, Dec 16, 2015 at 1:55 PM, Johannes Waldmann > wrote: > > As I said, I admire hyperlinked sources > > in the new "base" documentation > > https://hackage.haskell.org/package/base-4.8.1.0/docs/ > > > > and I want to know how I can produce such documents. > > What is the magic haddock/hscolour invocation? > > (I actually use standalone-haddock.) > > > > On hackage, not every package gets the special treatment? > > (In fact, only "base" does?) > > > > - J.W. > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From valentino.picotti at gmail.com Thu Dec 17 15:02:31 2015 From: valentino.picotti at gmail.com (Valentino Picotti) Date: Thu, 17 Dec 2015 16:02:31 +0100 Subject: [Haskell-cafe] Haskell safe ccalls Message-ID: <48F5B0F3-1AF6-461A-98B3-FDD7391202BE@gmail.com> Hi everybody, I?m new on this list and have a newbie question about Haskell FFI and safe calls. I have written the following lines of C code that rely on the RTS: Condition* init_cond(){ Condition* c = malloc(sizeof(Condition)); initCondition(c); return c; } Mutex* init_mutex(){ Mutex* m = malloc(sizeof(Mutex)); initMutex(m); return m; } void wait_condition(Condition* condition, Mutex* mutex) { ACQUIRE_LOCK(mutex); if(!waitCondition(condition, mutex)){ fprintf(stderr, "A: Wait failed!"); }; RELEASE_LOCK(mutex); } And the Haskell program is written as follow: data Condition = Condition data Mutex = Mutex foreign import ccall "init_cond" init_cond :: IO (Ptr Condition) foreign import ccall "init_mutex" init_mutex :: IO (Ptr Mutex) foreign import ccall "wait_condition" wait_condition:: Ptr Condition -> Ptr Mutex -> IO () main :: IO () main = do c <- init_cond m <- init_mutex wait_condition c m putStrLn ?Hello!? The behaviour that i want from my application is the same as the following C program: int main(int argc, char** argv){ pthread_cond_t c = PTHREAD_COND_INITIALIZER; pthread_mutex_t m; pthread_mutex_init(&m, 0); pthread_mutex_lock(&m); pthread_cond_wait(&c, &m); printf(?I didn?t block!\n"); pthread_mutex_unlock(&m); return 0; } What I expect is that the program doesn?t reach the putStrLn line, but it prints ?Hello!? and terminates with exit code 0. I can?t figure out what?s going on under the hood. Can someone explain me what i?m missing? (I?m familiar with Capabilities, Tasks, Haskell threads) Thanks, Valentino P. From rendel at informatik.uni-tuebingen.de Thu Dec 17 16:13:40 2015 From: rendel at informatik.uni-tuebingen.de (Tillmann Rendel) Date: Thu, 17 Dec 2015 17:13:40 +0100 Subject: [Haskell-cafe] Need ideas how to model the lack of something In-Reply-To: <566DD1FF.3090700@web.de> References: <566DD1FF.3090700@web.de> Message-ID: <5672DF34.20409@informatik.uni-tuebingen.de> Hi, martin wrote: > I started like this > > data C a = C { > insert :: a -> Maybe (C a), > remove :: Maybe (a, C a) > } > > but I could not implement anything sensible on top of this. Looks reasonable to me. What do you want to implement on top of it? For starters, here are three values of this type: stack :: From jeffbrown.the at gmail.com Thu Dec 17 23:45:54 2015 From: jeffbrown.the at gmail.com (Jeffrey Brown) Date: Thu, 17 Dec 2015 15:45:54 -0800 Subject: [Haskell-cafe] Canned routines for the first say thousand digits of pi, e, sqrt 2, etc? Message-ID: Do there exist libraries for finding the first thousand or so digits of irrational numbers? In base 12? I searhed all the "Numeric" and "Numerical" packages on Hackage and found nothing appropriate. I did figure out how to change the base of a number: https://github.com/JeffreyBenjaminBrown/play/blob/master/digits/chBase.hs but that method appears limited to numbers only a dozen or so digits long. My motivation is this video, in which James Zamerski puts the first couple hundred digits of pi to music. I've listened to it maybe 15 times in two days. https://www.youtube.com/watch?v=AOaR4NS7ObI It makes me want to try playing the first few hundred digits of other irrational numbers on the piano and try to harmonize them. -- Jeffrey Benjamin Brown -------------- next part -------------- An HTML attachment was scrubbed... URL: From jerzy.karczmarczuk at unicaen.fr Fri Dec 18 00:28:05 2015 From: jerzy.karczmarczuk at unicaen.fr (Jerzy Karczmarczuk) Date: Fri, 18 Dec 2015 01:28:05 +0100 Subject: [Haskell-cafe] Canned routines for the first say thousand digits of pi, e, sqrt 2, etc? In-Reply-To: References: Message-ID: <56735315.4080503@unicaen.fr> Le 18/12/2015 00:45, Jeffrey Brown badly needs : > the first thousand or so digits of irrational numbers? In base 12? Well, I wonder why not in base 314159? It would be much more Mystical, and making Music out of it would not be more lousy than in any other base. Anyway... Conversion from one base to another of an integer is a simple student exercise. But of a fraction, perhaps infinite, requires more work. I did it some centuries ago, if you want some co-recursive fun, find my Braga School participant delirium: "The most Unreliable Technique in the World to Compute Pi", still somewhere among my files ( https://karczmarczuk.users.greyc.fr/arpap/lazypi.pdf ). I never thought I would recommend it to anybody... Now, I would not call my exercice a "canned routine"... Jerzy Karczmarczuk /Caen [don't pronounce it "canned", please!], France/ From noonslists at gmail.com Fri Dec 18 02:48:31 2015 From: noonslists at gmail.com (Noon Silk) Date: Fri, 18 Dec 2015 13:48:31 +1100 Subject: [Haskell-cafe] haskell GIS projects Message-ID: Hello Cafe, Is anyone using any nice modern GIS libraries in Haskell? Say for opening various geographic file formats, and doing geometric queries, etc? Searching often leads me to TerraHS: https://wiki.haskell.org/TerraHS but it's pretty out of date. Is there some cool library I'm missing? -- Noon Silk, ? "Every morning when I wake up, I experience an exquisite joy ? the joy of being this signature." -------------- next part -------------- An HTML attachment was scrubbed... URL: From hahn at geoinfo.tuwien.ac.at Fri Dec 18 07:25:14 2015 From: hahn at geoinfo.tuwien.ac.at (=?UTF-8?Q?J=c3=bcrgen_Hahn?=) Date: Fri, 18 Dec 2015 08:25:14 +0100 Subject: [Haskell-cafe] haskell GIS projects In-Reply-To: References: Message-ID: <5673B4DA.7040102@geoinfo.tuwien.ac.at> Dear Noon Silk, there are some GIS packages available at hackage: Processing shapefiles: http://hackage.haskell.org/package/shapefile Conversions from GPS to UKGrid Coordinates: http://hackage.haskell.org/package/geo-uk Three libraries for geocoding using different services: Google: http://hackage.haskell.org/package/geocode-google http://hackage.haskell.org/package/geo-resolver OpenStreetMap: http://hackage.haskell.org/package/reverse-geocoding OpenCage: http://hackage.haskell.org/package/GeocoderOpenCage As far as I know geometric queries are not yet implemented in Haskell. J?rgen Hahn On 12/18/2015 03:48 AM, Noon Silk wrote: > Hello Cafe, > > Is anyone using any nice modern GIS libraries in Haskell? Say for > opening various geographic file formats, and doing geometric queries, etc? > > Searching often leads me to TerraHS: > https://wiki.haskell.org/TerraHS but it's pretty out of date. > > Is there some cool library I'm missing? > > -- > Noon Silk, ? > > "Every morning when I wake up, I experience an exquisite joy ? the joy > of being this signature." > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe -------------- next part -------------- An HTML attachment was scrubbed... URL: From epsilonhalbe at gmail.com Fri Dec 18 08:35:14 2015 From: epsilonhalbe at gmail.com (Martin Heuschober) Date: Fri, 18 Dec 2015 09:35:14 +0100 Subject: [Haskell-cafe] Canned routines for the first say thousand digits of pi, e, sqrt 2, etc? In-Reply-To: <56735315.4080503@unicaen.fr> References: <56735315.4080503@unicaen.fr> Message-ID: you could also use pre-calculated results from files found for example in http://www.subidiom.com/pi/ or http://www.wolframalpha.com/input/?i=N%5Bpi%2C1000%5D and then do a base conversion. Cheers ?/2 2015-12-18 1:28 GMT+01:00 Jerzy Karczmarczuk : > > Le 18/12/2015 00:45, Jeffrey Brown badly needs : > >> the first thousand or so digits of irrational numbers? In base 12? >> > > Well, I wonder why not in base 314159? It would be much more Mystical, and > making Music out of it would not be more lousy than in any other base. > Anyway... > > Conversion from one base to another of an integer is a simple student > exercise. But of a fraction, perhaps infinite, requires more work. I did it > some centuries ago, if you want some co-recursive fun, find my Braga > School participant delirium: "The most Unreliable Technique in the World to > Compute Pi", still somewhere among my files ( > https://karczmarczuk.users.greyc.fr/arpap/lazypi.pdf ). I never thought > I would recommend it to anybody... > > Now, I would not call my exercice a "canned routine"... > > Jerzy Karczmarczuk > /Caen [don't pronounce it "canned", please!], France/ > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From dct25-561bs at mythic-beasts.com Fri Dec 18 09:40:15 2015 From: dct25-561bs at mythic-beasts.com (David Turner) Date: Fri, 18 Dec 2015 09:40:15 +0000 Subject: [Haskell-cafe] Preventing sharing Message-ID: I have been playing around with this definition of fib with a colleague: fib n = fibs !! n where fibs = 0 : 1 : zipWith (+) fibs (tail fibs) My initial expectation was that this should take linear time and constant space, but this proved not to be the case: it leaks (a linear amount of) space. We fixed this by replacing (!!) with a version that is strict in the head of its first argument, effectively forcing the list to be strict as far as is needed. With that fix we could quite happily do { print $ fib 1000000 } and all was well, so I tried to write a Criterion benchmark to show that the time taken was linear in n. And the space leak reappeared! Looking at the core, I think what had happened was that GHC had spotted that the inner definition of fibs didn't depend on n and floated it out to the top level so it could be shared between calls. Normally a good move, but in this case it's a disaster as it's much quicker to recalculate the list as needed than to keep it around for next time, for sufficiently large values of n. Now I'm a bit stuck: how do you prevent this from happening? Obviously here we could just implement fibs differently, but as a more general question, how would you prevent unwanted sharing from taking place? Cheers, David -------------- next part -------------- An HTML attachment was scrubbed... URL: From anton.kholomiov at gmail.com Fri Dec 18 11:22:46 2015 From: anton.kholomiov at gmail.com (Anton Kholomiov) Date: Fri, 18 Dec 2015 14:22:46 +0300 Subject: [Haskell-cafe] wondering on Haskell kickstarter project: VST plugin / mobile synthesizer Message-ID: I'm wondering if it's good idea to make crowd-founding project for a synthesizer written in Haskell. What's your opinion? Would you like to support such a project? I've made a prototype: https://github.com/anton-k/tiny-synth It's a desktop synthesizer, a collection of instruments. About 150 instruments written in Haskell. It works with midi keyboard. You can try it out with USB-midi device. The UI is written with Python and audio engine is written with Haskell. I use my library csound-expression to generate the code for Csound. The Csound is an audio programming language it can be used as C library. There are bindings to many languages and it can work on Android / iOS. Right now I've made a prototype for desktop. The big plan is to create VST/AU/Lv2 plugins and mobile versions for Android and iOS. [1] https://github.com/anton-k/tiny-synth [2] http://hackage.haskell.org/package/csound-expression [3] https://github.com/spell-music/csound-expression Cheers, Anton -------------- next part -------------- An HTML attachment was scrubbed... URL: From olf at aatal-apotheke.de Fri Dec 18 12:31:33 2015 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Fri, 18 Dec 2015 13:31:33 +0100 Subject: [Haskell-cafe] Canned routines for the first say thousand digits of pi, e, sqrt 2, etc? Message-ID: <054CD8F1-D067-4335-B917-99E959632D99@aatal-apotheke.de> As it happens, I am just studying a presentation [1] Martin Escardo gave to students at the University of Birmingham. It contains Haskell code for exact real number computation. Among other things, there is a function that computes a signed digit representation of pi/32. It computes several thousand digits in a few seconds. I did not try it yet, but many irrational numbers are fixed points of simple arithmetical expressions. For example, the golden ratio is the fixed point of \x -> 1+1/x. Infinite streams of digits should be a type where such a fixed point is computable. Or you could use a sufficiently precise rational approximation and convert that do decimal in the usual way. import Data.Ratio import Data.List (iterate) -- one step of Heron's algorithm for sqrt(a) heron :: (Fractional a) => a -> a -> a heron a x = (x+a/x)/2 -- infinite stream of approximations to sqrt(a) approx :: (Fractional a) => a -> [a] approx a = iterate (heron a) 1 -- Find an interval with rational end-points -- for a signed-digit real number type SDReal = [Int] -- use digits [-1,0,1] interval :: Int -> SDReal -> (Rational,Rational) interval precision x = let f = foldr (\d g -> (a d).g) id (take precision x)) a d = \x -> ((fromIntegral d)+x)/2 in (f(-1),f(1)) Cheers, Olaf [1] www.cs.bham.ac.uk/~mhe/.talks/phdopen2013/realreals.lhs From mail at joachim-breitner.de Fri Dec 18 14:36:40 2015 From: mail at joachim-breitner.de (Joachim Breitner) Date: Fri, 18 Dec 2015 15:36:40 +0100 Subject: [Haskell-cafe] Preventing sharing In-Reply-To: References: Message-ID: <1450449400.1546.13.camel@joachim-breitner.de> Hi, Am Freitag, den 18.12.2015, 09:40 +0000 schrieb David Turner: > Now I'm a bit stuck: how do you prevent this from happening? > Obviously here we could just implement fibs differently, but as a > more general question, how would you prevent unwanted sharing from > taking place? floating out (and, relatedly, CSE) is tricky to get a good grip on, and I wish there were good and easy solutions. This also comes up with things like "zip xs [0..]" and gets in the way of applying rules. Note that in your example, depending on the use case, maybe the programmer did want to share the fibs list. So it is not clear that the compiler can always do the right thing. You can pass?-fno-full-laziness to GHC (and you can do that with a per- module pragma), this might work in your case, but you better check. Another trick is to add an argument to fibs, e.g. the initial starting values fib n = fibs 0 1 !! n ? where ? ?fibs a b = go where go = a : b : zipWith (+) go (tail go) ? ?{-# NOINLINE fibs #-} The noinline pragma might be required as otherwise GHC will simplify the code again to your origin form, and then share the go with a and be specialized to 0 and 1. Again, check the core if it indeed does what you want. Both approaches are unsatisfying. Greetings, Joachim -- Joachim ?nomeata? Breitner mail at joachim-breitner.de ? http://www.joachim-breitner.de/ Jabber: nomeata at joachim-breitner.de ? GPG-Key: 0xF0FBF51F Debian Developer: nomeata at debian.org -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: This is a digitally signed message part URL: From dct25-561bs at mythic-beasts.com Fri Dec 18 18:43:10 2015 From: dct25-561bs at mythic-beasts.com (David Turner) Date: Fri, 18 Dec 2015 18:43:10 +0000 Subject: [Haskell-cafe] Preventing sharing In-Reply-To: <1450449400.1546.13.camel@joachim-breitner.de> References: <1450449400.1546.13.camel@joachim-breitner.de> Message-ID: Hi, Well at least I hadn't overlooked something obvious! Some combination of dummy arguments, NOINLINE and -fno-full-laziness did indeed prevent it from sharing but this definitely seemed unsatisfactory. Particularly that -fno-full-laziness applies to the whole module which feels a bit heavyweight. How feasible would it be to add another pragma like NOINLINE that prevented exactly this? Is it actually important? This is a toy example of course and I've not come across this kind of problem in any real code - has anyone else? Cheers, David On 18 December 2015 at 14:36, Joachim Breitner wrote: > Hi, > > Am Freitag, den 18.12.2015, 09:40 +0000 schrieb David Turner: > > Now I'm a bit stuck: how do you prevent this from happening? > > Obviously here we could just implement fibs differently, but as a > > more general question, how would you prevent unwanted sharing from > > taking place? > > floating out (and, relatedly, CSE) is tricky to get a good grip on, and > I wish there were good and easy solutions. This also comes up with > things like "zip xs [0..]" and gets in the way of applying rules. > > Note that in your example, depending on the use case, maybe the > programmer did want to share the fibs list. So it is not clear that the > compiler can always do the right thing. > > You can pass -fno-full-laziness to GHC (and you can do that with a per- > module pragma), this might work in your case, but you better check. > > Another trick is to add an argument to fibs, e.g. the initial starting > values > > fib n = fibs 0 1 !! n > where > fibs a b = go where go = a : b : zipWith (+) go (tail go) > {-# NOINLINE fibs #-} > > The noinline pragma might be required as otherwise GHC will simplify > the code again to your origin form, and then share the go with a and be > specialized to 0 and 1. Again, check the core if it indeed does what > you want. > > Both approaches are unsatisfying. > > > Greetings, > Joachim > > -- > Joachim ?nomeata? Breitner > mail at joachim-breitner.de ? http://www.joachim-breitner.de/ > Jabber: nomeata at joachim-breitner.de ? GPG-Key: 0xF0FBF51F > Debian Developer: nomeata at debian.org > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Fri Dec 18 18:53:49 2015 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Fri, 18 Dec 2015 18:53:49 +0000 Subject: [Haskell-cafe] Preventing sharing In-Reply-To: References: <1450449400.1546.13.camel@joachim-breitner.de> Message-ID: <20151218185349.GW9624@weber> On Fri, Dec 18, 2015 at 06:43:10PM +0000, David Turner wrote: > Some combination of dummy arguments, NOINLINE and -fno-full-laziness did > indeed prevent it from sharing but this definitely seemed unsatisfactory. > Particularly that -fno-full-laziness applies to the whole module which > feels a bit heavyweight. I would be very surprised if -fno-full-laziness did not fix the issue on its own. Do you have a simple example which I can reproduce myself that shows that it doesn't? Tom From jeffbrown.the at gmail.com Fri Dec 18 20:20:54 2015 From: jeffbrown.the at gmail.com (Jeffrey Brown) Date: Fri, 18 Dec 2015 12:20:54 -0800 Subject: [Haskell-cafe] Canned routines for the first say thousand digits of pi, e, sqrt 2, etc? In-Reply-To: <054CD8F1-D067-4335-B917-99E959632D99@aatal-apotheke.de> References: <054CD8F1-D067-4335-B917-99E959632D99@aatal-apotheke.de> Message-ID: Thanks everybody! It turns out WolframAlpha will do the computation for me. (It won't let me copy the digits, so I have to transcribe them by hand, but given how much time I'm spending reviewing the notes anyway, that is a small part of the overall labor cost.) On Fri, Dec 18, 2015 at 4:31 AM, Olaf Klinke wrote: > As it happens, I am just studying a presentation [1] Martin Escardo gave > to students at the University of Birmingham. It contains Haskell code for > exact real number computation. Among other things, there is a function that > computes a signed digit representation of pi/32. It computes several > thousand digits in a few seconds. > I did not try it yet, but many irrational numbers are fixed points of > simple arithmetical expressions. For example, the golden ratio is the fixed > point of \x -> 1+1/x. Infinite streams of digits should be a type where > such a fixed point is computable. Or you could use a sufficiently precise > rational approximation and convert that do decimal in the usual way. > > import Data.Ratio > import Data.List (iterate) > > -- one step of Heron's algorithm for sqrt(a) > heron :: (Fractional a) => a -> a -> a > heron a x = (x+a/x)/2 > > -- infinite stream of approximations to sqrt(a) > approx :: (Fractional a) => a -> [a] > approx a = iterate (heron a) 1 > > -- Find an interval with rational end-points > -- for a signed-digit real number > type SDReal = [Int] -- use digits [-1,0,1] > interval :: Int -> SDReal -> (Rational,Rational) > interval precision x = let > f = foldr (\d g -> (a d).g) id (take precision x)) > a d = \x -> ((fromIntegral d)+x)/2 > in (f(-1),f(1)) > > Cheers, > Olaf > > [1] www.cs.bham.ac.uk/~mhe/.talks/phdopen2013/realreals.lhs -- Jeffrey Benjamin Brown -------------- next part -------------- An HTML attachment was scrubbed... URL: From douglas.mcclean at gmail.com Fri Dec 18 20:36:04 2015 From: douglas.mcclean at gmail.com (Douglas McClean) Date: Fri, 18 Dec 2015 15:36:04 -0500 Subject: [Haskell-cafe] Storable types with zero size Message-ID: Can the sizeOf a Storable type be 0? As far as I can see the documentation doesn't say. I wouldn't expect there to be a problem, but there also isn't an instance Storable (), which I was expecting to see. If so, should its alignment be 1 or 0? -Doug McClean -------------- next part -------------- An HTML attachment was scrubbed... URL: From will.yager at gmail.com Fri Dec 18 21:30:12 2015 From: will.yager at gmail.com (William Yager) Date: Fri, 18 Dec 2015 15:30:12 -0600 Subject: [Haskell-cafe] Canned routines for the first say thousand digits of pi, e, sqrt 2, etc? In-Reply-To: References: <054CD8F1-D067-4335-B917-99E959632D99@aatal-apotheke.de> Message-ID: A trick I use when I need lots of digits is to calculate the number using a series expansion. If you calculate it using e.g. Rational, you can then get arbitrary precision and print an arbitrary number of digits. Here are a few examples. I've calculated both e and pi, accurate to 1000 digits. It takes about 2.3 seconds to run on my laptop. https://gist.github.com/wyager/33dcc26d1e867c462808 It's also very easy to adapt to non-decimal bases. Will On Fri, Dec 18, 2015 at 2:20 PM, Jeffrey Brown wrote: > Thanks everybody! It turns out WolframAlpha will do the computation > for > me. (It won't let me copy the digits, so I have to transcribe them by hand, > but given how much time I'm spending reviewing the notes anyway, that is a > small part of the overall labor cost.) > > On Fri, Dec 18, 2015 at 4:31 AM, Olaf Klinke > wrote: > >> As it happens, I am just studying a presentation [1] Martin Escardo gave >> to students at the University of Birmingham. It contains Haskell code for >> exact real number computation. Among other things, there is a function that >> computes a signed digit representation of pi/32. It computes several >> thousand digits in a few seconds. >> I did not try it yet, but many irrational numbers are fixed points of >> simple arithmetical expressions. For example, the golden ratio is the fixed >> point of \x -> 1+1/x. Infinite streams of digits should be a type where >> such a fixed point is computable. Or you could use a sufficiently precise >> rational approximation and convert that do decimal in the usual way. >> >> import Data.Ratio >> import Data.List (iterate) >> >> -- one step of Heron's algorithm for sqrt(a) >> heron :: (Fractional a) => a -> a -> a >> heron a x = (x+a/x)/2 >> >> -- infinite stream of approximations to sqrt(a) >> approx :: (Fractional a) => a -> [a] >> approx a = iterate (heron a) 1 >> >> -- Find an interval with rational end-points >> -- for a signed-digit real number >> type SDReal = [Int] -- use digits [-1,0,1] >> interval :: Int -> SDReal -> (Rational,Rational) >> interval precision x = let >> f = foldr (\d g -> (a d).g) id (take precision x)) >> a d = \x -> ((fromIntegral d)+x)/2 >> in (f(-1),f(1)) >> >> Cheers, >> Olaf >> >> [1] www.cs.bham.ac.uk/~mhe/.talks/phdopen2013/realreals.lhs > > > > > -- > Jeffrey Benjamin Brown > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ss.nedunuri at gmail.com Fri Dec 18 23:00:08 2015 From: ss.nedunuri at gmail.com (s nedunuri) Date: Fri, 18 Dec 2015 17:00:08 -0600 Subject: [Haskell-cafe] documentation of Haskell's hierarchical libraries Message-ID: I am wondering where I might be able to get a reasonably complete documentation of Haskell's libraries. I was using the documentation at https://downloads.haskell.org/~ghc/latest/docs/html/libraries/ but I noticed that it was missing hash tables, which are located in Data.HashTable. I am not sure what other modules might be missing from there. Is there some place where everything (up to some release) is documented? thanks PS the documentation bundled with the Haskell Platform (7.10.2-a) is even worse as its missing large sections of what you find at the online documentation From adam at bergmark.nl Fri Dec 18 23:10:31 2015 From: adam at bergmark.nl (Adam Bergmark) Date: Sat, 19 Dec 2015 00:10:31 +0100 Subject: [Haskell-cafe] documentation of Haskell's hierarchical libraries In-Reply-To: References: Message-ID: Data.HashTable isn't missing, it was removed in base 4.7 (GHC 7.8). Have you looked at the documentation on hackage.haskell.org? I imagine that's where the majority of people read documentation, there's little reason to restrict yourself to the packages shipped with GHC or haskell platform. - Adam On Sat, Dec 19, 2015 at 12:00 AM, s nedunuri wrote: > I am wondering where I might be able to get a reasonably complete > documentation of Haskell's libraries. I was using the documentation at > https://downloads.haskell.org/~ghc/latest/docs/html/libraries/ but I > noticed that it was missing hash tables, which are located in > Data.HashTable. I am not sure what other modules might be missing from > there. Is there some place where everything (up to some release) is > documented? > > thanks > > PS the documentation bundled with the Haskell Platform (7.10.2-a) is even > worse as its missing large sections of what you find at the online > documentation > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From vieira.ufpi at gmail.com Sat Dec 19 13:45:24 2015 From: vieira.ufpi at gmail.com (vieira.ufpi at gmail.com) Date: Sat, 19 Dec 2015 13:45:24 +0000 Subject: [Haskell-cafe] =?utf-8?q?Clausula_where?= Message-ID: <56756326.c6d10d0a.ace6c.ffffeb19@mx.google.com> I?m using GHCi in a Haskell version 7.10.2 and using this fragmente of coding: data ArvBinA t = Folha t | No Int (ArvBinA t) (ArvBinA t) deriving (Eq, Ord, Show) arvbina = No 4 (No 2 (Folha 14) (Folha 09)) (No 2 (Folha 19) (Folha 51)) tamArvBinA :: ArvBinA t -> Int tamArvBinA (Folha x) = 1 tamArvBinA (No n xt yt) = n rotula :: ArvBinA t -> ArvBinA t -> ArvBinA t rotula ae ad = No n ae ad where n = (tamArvBinA ae) + (tamArvBinA ad) listoArvBinA :: (Eq t) => [t] -> ArvBinA t listoArvBinA xs |m == 0 = Folha (head xs) |otherwise = rotula (listoArvBinA xse) (listoArvBinA xsd) where m = (length xs) `div` 2 (xse, xsd) = (take m xs, drop m xs) After compiling there is this message: parse error on input ?=?. There is someone that he/she can help me? I think that?is na error by clause where and the offside rule, or so, but I?m not right of this. Thanks in advance for some help Francisco Vieira Enviado do Email do Windows -------------- next part -------------- An HTML attachment was scrubbed... URL: From imantc at gmail.com Sat Dec 19 14:18:28 2015 From: imantc at gmail.com (Imants Cekusins) Date: Sat, 19 Dec 2015 15:18:28 +0100 Subject: [Haskell-cafe] Clausula where In-Reply-To: <56756326.c6d10d0a.ace6c.ffffeb19@mx.google.com> References: <56756326.c6d10d0a.ace6c.ffffeb19@mx.google.com> Message-ID: Hello, try changing this: rotula ae ad = No n ae ad where n = (tamArvBinA ae) + (tamArvBinA ad) to rotula ae ad = No n ae ad where n = (tamArvBinA ae) + (tamArvBinA ad) From dct25-561bs at mythic-beasts.com Sat Dec 19 14:31:00 2015 From: dct25-561bs at mythic-beasts.com (David Turner) Date: Sat, 19 Dec 2015 14:31:00 +0000 Subject: [Haskell-cafe] Preventing sharing In-Reply-To: <20151218185349.GW9624@weber> References: <1450449400.1546.13.camel@joachim-breitner.de> <20151218185349.GW9624@weber> Message-ID: You're right, I think. I wasn't being very scientific with my investigation. Though as mentioned, -fno-full-laziness seems like a bit of a sledgehammer. On 18 Dec 2015 18:54, "Tom Ellis" < tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk> wrote: > On Fri, Dec 18, 2015 at 06:43:10PM +0000, David Turner wrote: > > Some combination of dummy arguments, NOINLINE and -fno-full-laziness did > > indeed prevent it from sharing but this definitely seemed unsatisfactory. > > Particularly that -fno-full-laziness applies to the whole module which > > feels a bit heavyweight. > > I would be very surprised if -fno-full-laziness did not fix the issue on > its > own. Do you have a simple example which I can reproduce myself that shows > that it doesn't? > > Tom > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Sat Dec 19 15:01:10 2015 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sat, 19 Dec 2015 10:01:10 -0500 Subject: [Haskell-cafe] Storable types with zero size In-Reply-To: References: Message-ID: 1 byte alignment might be tricky. When talking about storable, its helpful to keep in mind that it's meant to facilitate c interop, and ask what the corresponds with unit in c land, and I think the answer is 0 bits :) On Friday, December 18, 2015, Douglas McClean wrote: > Can the sizeOf a Storable type be 0? > > As far as I can see the documentation doesn't say. I wouldn't expect there > to be a problem, but there also isn't an instance Storable (), which I was > expecting to see. > > If so, should its alignment be 1 or 0? > > > -Doug McClean > -------------- next part -------------- An HTML attachment was scrubbed... URL: From adam at bergmark.nl Sat Dec 19 16:25:37 2015 From: adam at bergmark.nl (Adam Bergmark) Date: Sat, 19 Dec 2015 17:25:37 +0100 Subject: [Haskell-cafe] Stackage update and plans for LTS Haskell 4 Message-ID: Hi caf?, This is an update on Stackage moving to GHC 7.10.3 and towards LTS Haskell 4. I especially encourage maintainers with packages on stackage to read the post since some packages have been disabled in the process. http://andnam.tumblr.com/post/135510474243/stackage-update-and-plans-for-lts-haskell-4 All the best, Adam Discussion on Reddit: https://www.reddit.com/r/haskell/comments/3xh5uq/stackage_update_and_plans_for_lts_haskell_4/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From douglas.mcclean at gmail.com Sat Dec 19 17:04:27 2015 From: douglas.mcclean at gmail.com (Douglas McClean) Date: Sat, 19 Dec 2015 12:04:27 -0500 Subject: [Haskell-cafe] Storable types with zero size In-Reply-To: References: Message-ID: My thinking was that an address p is valid for a type a iff p `mod` (alignment (undefined :: a)) == 0 and that, at least in most languages, x mod 0 is undefined. In contrast, anything mod 1 is 0. On Dec 19, 2015 10:01 AM, "Carter Schonwald" wrote: > 1 byte alignment might be tricky. > > When talking about storable, its helpful to keep in mind that it's meant > to facilitate c interop, and ask what the corresponds with unit in c land, > and I think the answer is 0 bits :) > > > > On Friday, December 18, 2015, Douglas McClean > wrote: > >> Can the sizeOf a Storable type be 0? >> >> As far as I can see the documentation doesn't say. I wouldn't expect >> there to be a problem, but there also isn't an instance Storable (), which >> I was expecting to see. >> >> If so, should its alignment be 1 or 0? >> >> >> -Doug McClean >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From trebla at vex.net Sat Dec 19 17:14:21 2015 From: trebla at vex.net (Albert Y. C. Lai) Date: Sat, 19 Dec 2015 12:14:21 -0500 Subject: [Haskell-cafe] Clausula where In-Reply-To: <56756326.c6d10d0a.ace6c.ffffeb19@mx.google.com> References: <56756326.c6d10d0a.ace6c.ffffeb19@mx.google.com> Message-ID: <5675906D.9020409@vex.net> On 2015-12-19 08:45 AM, vieira.ufpi at gmail.com wrote: > where m = (length xs) `div` 2 > (xse, xsd) = (take m xs, > drop m xs) These two lines are misaligned. Proof: paste them to an honest pastebin such as lpaste.net to see: http://lpaste.net/147461 -------------- next part -------------- An HTML attachment was scrubbed... URL: From keydana at gmx.de Sat Dec 19 18:09:20 2015 From: keydana at gmx.de (Sigrid Keydana) Date: Sat, 19 Dec 2015 19:09:20 +0100 Subject: [Haskell-cafe] No instance of ... error with Statistics.Sample.Histogram Message-ID: An HTML attachment was scrubbed... URL: From imantc at gmail.com Sat Dec 19 18:31:40 2015 From: imantc at gmail.com (Imants Cekusins) Date: Sat, 19 Dec 2015 19:31:40 +0100 Subject: [Haskell-cafe] No instance of ... error with Statistics.Sample.Histogram In-Reply-To: References: Message-ID: let numBuckets = 3::Int ? -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Sat Dec 19 20:04:10 2015 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sat, 19 Dec 2015 15:04:10 -0500 Subject: [Haskell-cafe] Storable types with zero size In-Reply-To: References: Message-ID: Ohhhh. I see. I guess the funny bit is that the size of a strictly evaluated unit type should be zero. So size zero is what I was thinking about. On Saturday, December 19, 2015, Douglas McClean wrote: > My thinking was that an address p is valid for a type a iff p `mod` > (alignment (undefined :: a)) == 0 and that, at least in most languages, x > mod 0 is undefined. In contrast, anything mod 1 is 0. > On Dec 19, 2015 10:01 AM, "Carter Schonwald" > wrote: > >> 1 byte alignment might be tricky. >> >> When talking about storable, its helpful to keep in mind that it's meant >> to facilitate c interop, and ask what the corresponds with unit in c land, >> and I think the answer is 0 bits :) >> >> >> >> On Friday, December 18, 2015, Douglas McClean > > wrote: >> >>> Can the sizeOf a Storable type be 0? >>> >>> As far as I can see the documentation doesn't say. I wouldn't expect >>> there to be a problem, but there also isn't an instance Storable (), which >>> I was expecting to see. >>> >>> If so, should its alignment be 1 or 0? >>> >>> >>> -Doug McClean >>> >> -------------- next part -------------- An HTML attachment was scrubbed... URL: From vieira.ufpi at gmail.com Sun Dec 20 00:40:04 2015 From: vieira.ufpi at gmail.com (Francisco Vieira de Souza) Date: Sat, 19 Dec 2015 22:40:04 -0200 Subject: [Haskell-cafe] Clausula where In-Reply-To: <5675906D.9020409@vex.net> References: <56756326.c6d10d0a.ace6c.ffffeb19@mx.google.com> <5675906D.9020409@vex.net> Message-ID: If it is right, what should I do to correct the problem? Thanks in advance Vieira 2015-12-19 15:14 GMT-02:00 Albert Y. C. Lai : > On 2015-12-19 08:45 AM, vieira.ufpi at gmail.com wrote: > > where m = (length xs) `div` 2 > (xse, xsd) = (take m xs, drop m > xs) > > > These two lines are misaligned. Proof: paste them to an honest pastebin > such as lpaste.net to see: http://lpaste.net/147461 > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > -- "Embora ningu?m possa voltar atr?s e fazer um novo come?o, qualquer um pode come?ar agora e fazer um novo fim". (Chico Xavier) -------------- next part -------------- An HTML attachment was scrubbed... URL: From keydana at gmx.de Sun Dec 20 07:15:27 2015 From: keydana at gmx.de (Sigrid Keydana) Date: Sun, 20 Dec 2015 08:15:27 +0100 Subject: [Haskell-cafe] No instance of ... error with Statistics.Sample.Histogram In-Reply-To: References: , Message-ID: An HTML attachment was scrubbed... URL: From imantc at gmail.com Sun Dec 20 08:25:21 2015 From: imantc at gmail.com (Imants Cekusins) Date: Sun, 20 Dec 2015 09:25:21 +0100 Subject: [Haskell-cafe] Clausula where In-Reply-To: References: <56756326.c6d10d0a.ace6c.ffffeb19@mx.google.com> <5675906D.9020409@vex.net> Message-ID: > what should I do to correct the problem? try to align "m" and "(xse,xsd)": indent "(" to the same number of spaces as "m" where m = (length xs) `div` 2 (xse, xsd) = (take m xs, drop m xs) indents are important. Also check if you use tab character. It is safer to use spaces. From imz at altlinux.org Sun Dec 20 15:32:46 2015 From: imz at altlinux.org (Ivan Zakharyaschev) Date: Sun, 20 Dec 2015 18:32:46 +0300 (MSK) Subject: [Haskell-cafe] Q: language-c upstream repo Message-ID: Hello! I've been interested in hacking language-c library a bit for my needs. (If it turns out useful and successful, I'll tell about it.) And I've cloned the repo listed at https://hackage.haskell.org/package/language-c-0.4.7 , namely: http://code.haskell.org/language-c Apart from my special hacks, I've also fixed some typos and so on. But then I discovered that if I want to publish them on hub.darcs.net , I need a darcs-2 repo, and the initial one which I used for cloning is a darcs-1 repo. I could do the conversion to darcs-2, but I read that it is not reproducible: run several times on the same set of patches it will give different results. As I've discovered also a language-c repo at hub.darcs.net which looks like an upstream repo: http://hub.darcs.net/visq/language-c , I'm in doubt whether I should continue making my patches against the darcs-1 repo which is said to be upstream at hackage or against http://hub.darcs.net/visq/language-c whichis not officially declared as the upstream but looks more fresh. ..if I want to be able to send some of my patches upstream. Best regards, Ivan From qdunkan at gmail.com Sun Dec 20 18:41:05 2015 From: qdunkan at gmail.com (Evan Laforge) Date: Sun, 20 Dec 2015 10:41:05 -0800 Subject: [Haskell-cafe] wondering on Haskell kickstarter project: VST plugin / mobile synthesizer In-Reply-To: References: Message-ID: It sounds hard to get enough interest for significant funding, because it's a niche of a niche. And, at least if I am anything to go by, the niche is occupied by especially iconoclastic sorts. For instance, even though I'm very much interested in that kind of thing, and would like to do something myself, I would only do it for the the purpose of using something better than MIDI, because there are already tons of MIDI using VSTs out there. Doing something different would give an opportunity to easily support things that are awkward in MIDI, and offline incremental rendering would allow expensive synthesis and unlimited polyphony. Also it would be nice to have a programmable sampler which is not as hilariously terrible as kontakt. So I wouldn't really be personally interested, unless it had some unique gimmick that made it more interesting than all the existing VSTs, or if perhaps it were about establishing low level libraries that would make it easier to do what I'm interested in. In fact your existing work with csound-sampler is already somewhat along those lines since it makes all the csound stuff available with a nice haskell frontend. But even then... though I wish you luck and I do support the general idea of more of this kind of thing happening, software development is really expensive. It seems to me pretty much the only way it can work is for an interested individual to do on their own for free. Either that, or an established product with aiming at the most mainstream possible market, e.g. ardour. And even then it will likely struggle. On Fri, Dec 18, 2015 at 3:22 AM, Anton Kholomiov wrote: > I'm wondering if it's good idea to make crowd-founding project > for a synthesizer written in Haskell. What's your opinion? > Would you like to support such a project? > > I've made a prototype: > > https://github.com/anton-k/tiny-synth > > It's a desktop synthesizer, a collection of instruments. About 150 > instruments > written in Haskell. It works with midi keyboard. You can try it out with > USB-midi device. > > The UI is written with Python and audio engine is > written with Haskell. I use my library csound-expression to > generate the code for Csound. The Csound is an audio programming language > it can be used as C library. There are bindings to many languages and it > can work on Android / iOS. > > Right now I've made a prototype for desktop. The big plan is to > create VST/AU/Lv2 plugins and mobile versions for Android and iOS. > > [1] https://github.com/anton-k/tiny-synth > [2] http://hackage.haskell.org/package/csound-expression > [3] https://github.com/spell-music/csound-expression > > Cheers, > Anton > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > From noonslists at gmail.com Mon Dec 21 01:01:54 2015 From: noonslists at gmail.com (Noon Silk) Date: Mon, 21 Dec 2015 12:01:54 +1100 Subject: [Haskell-cafe] NoMonomorphismRestriction forces odd situation when using contexts Message-ID: Hello, Consider the following program: ------------------------------------------------------------------- -- bar.hs {-# LANGUAGE NoMonomorphismRestriction #-} data Status = Foo | Bar data Rec m a = Rec { get :: m a , status :: Status } defRec :: (Monad m) => Rec m a defRec = undefined myRec :: (Monad m) => Rec m a myRec = Rec x y where Rec x y = defRec ------------------------------------------------------------------- It doesn't compile (under GHC 7.10.2), the error is: bar.hs:16:7: No instance for (Monad t0) The type variable ?t0? is ambiguous When checking that ?y? has the inferred type y :: Status Probable cause: the inferred type is ambiguous In an equation for ?myRec?: myRec = Rec x y where Rec x y = defRec Failed, modules loaded: none. If you remove the language extension, it does. Keeping the NoMonomorphismRestriction, it can be forced to typecheck by putting in a "dummy" type that satifies the constraint when obtaining the field `status` (that doesn't depend on `m`. ------------------------------------------------------------------- -- bar.hs {-# LANGUAGE NoMonomorphismRestriction #-} data Status = Foo | Bar data Rec m a = Rec { get :: m a , status :: Status } defRec :: (Monad m) => Rec m a defRec = undefined myRec :: (Monad m) => Rec m a myRec = Rec x y where s :: Rec Maybe a -> Status s = status x = get defRec -- y = s defRec ------------------------------------------------------------------- So, what's going on here? Is this a feature of this extension? It seems like the ability to destructure and then recombine is pretty fundamental, and it shouldn't break in the way that it does. (I.e. it's kinda crazy to have to put in a dummy type satisfying the constraint; is there some way to pass down the error -- Noon Silk, ? https://silky.github.io/ "Every morning when I wake up, I experience an exquisite joy ? the joy of being this signature." -------------- next part -------------- An HTML attachment was scrubbed... URL: From imz at altlinux.org Mon Dec 21 09:43:52 2015 From: imz at altlinux.org (Ivan Zakharyaschev) Date: Mon, 21 Dec 2015 12:43:52 +0300 (MSK) Subject: [Haskell-cafe] Q: language-c upstream repo In-Reply-To: References: Message-ID: On Sun, 20 Dec 2015, Ivan Zakharyaschev wrote: > And I've cloned the repo listed at > https://hackage.haskell.org/package/language-c-0.4.7 , namely: > http://code.haskell.org/language-c > But then I discovered that if I want to publish them on hub.darcs.net , I > need a darcs-2 repo, and the initial one which I used for cloning is a > darcs-1 repo. > > I could do the conversion to darcs-2, but I read that it is not reproducible: > run several times on the same set of patches it will give different results. Ganesh Sittampalam re-assured me at http://stackoverflow.com/a/34385874/94687 that it is not always so bad, and gave advices that I still try to go through the conversion and pushing my changes to a clone of the other upstream darcs-2 repo: > As I've discovered also a language-c repo at hub.darcs.net which looks like > an upstream repo: http://hub.darcs.net/visq/language-c , I'm in doubt whether Unfortunately, it didn't go smoothly -- when pushing the converted repo, darcs "couldn't commute" some tag patches, and it seems it refused to do anything further: ~/TOOLS/prog/language-c.darcs-2 $ darcs push ../language-c_hub/ HINT: if you want to change the default remote repository to /home/imz/TOOLS/prog/language-c_hub, quit now and issue the same command with the --set-default flag. darcs: bug at src/Darcs/Patch/Depends.hs:327 compiled May 26 2015 04:16:45 Failed to commute common patches: patch 71a1a541365ab8de9a874c21681f07b97bc1669b Author: benedikt.huber at gmail.com Date: Tue Aug 16 20:19:10 MSK 2011 tagged 0.4.1 patch f711caf67e93818e50033b7453e503ac23f26441 Author: benedikt.huber at gmail.com Date: Wed Feb 24 10:19:43 MSK 2010 * old tag: darcs_apply_bug patch c400ff96bc04d011ad9ab89966a104965f4b3548 Author: benedikt.huber at gmail.com Date: Thu Aug 21 16:32:18 MSD 2008 tagged 0.3.1 patch 4ab2c817f54dbd8f06a1350cb9a4abf28e25ddeb Author: benedikt.huber at gmail.com Date: Tue Aug 12 20:34:05 MSD 2008 * old tag: 0.3 patch c64f7c2830d166da91fa0d20b8a6877babe6d580 Author: benedikt.huber at gmail.com Date: Tue Jun 3 12:45:36 MSD 2008 * old tag: 0.1 See http://wiki.darcs.net/BugTracker/Reporting for help on bug reporting. ~/TOOLS/prog/language-c.darcs-2 $ For now, I'm still in doubt what would be a simple way to transfer the several last patches to a darcs-2 fork. Perhaps, there is some kind of a known problem with converted tags in darcs? Best regards, Ivan From anton.kholomiov at gmail.com Mon Dec 21 10:03:23 2015 From: anton.kholomiov at gmail.com (Anton Kholomiov) Date: Mon, 21 Dec 2015 13:03:23 +0300 Subject: [Haskell-cafe] wondering on Haskell kickstarter project: VST plugin / mobile synthesizer In-Reply-To: References: Message-ID: @Evan Thanks for detailed and sincere reply. I can see your points. That VST/mobiles market is very crowded business and it's really hard to compete with super giants especially when you don't provide any significant change or creative opportunity in the app. So I think this project is going to be more a prove of the concept and example that it's really possible to create real-time audio with Haskell and wrap it in non-Haskell UI. Hope I would manage to do the mobile version of it too some days. I would really like to add non equal temeprament scales, I feel that it can make a difference to the mood of the music. Maybe it's better to look in the direction of media installations. The Python has many cool libraries for non-trivial user interaction like computer vision. It would be great to stream this data in Haskell generated synthesizer. Maybe something can be created in this area. Anton 2015-12-20 21:41 GMT+03:00 Evan Laforge : > It sounds hard to get enough interest for significant funding, because > it's a niche of a niche. And, at least if I am anything to go by, the > niche is occupied by especially iconoclastic sorts. For instance, > even though I'm very much interested in that kind of thing, and would > like to do something myself, I would only do it for the the purpose of > using something better than MIDI, because there are already tons of > MIDI using VSTs out there. Doing something different would give an > opportunity to easily support things that are awkward in MIDI, and > offline incremental rendering would allow expensive synthesis and > unlimited polyphony. Also it would be nice to have a programmable > sampler which is not as hilariously terrible as kontakt. > > So I wouldn't really be personally interested, unless it had some > unique gimmick that made it more interesting than all the existing > VSTs, or if perhaps it were about establishing low level libraries > that would make it easier to do what I'm interested in. In fact your > existing work with csound-sampler is already somewhat along those > lines since it makes all the csound stuff available with a nice > haskell frontend. > > But even then... though I wish you luck and I do support the general > idea of more of this kind of thing happening, software development is > really expensive. It seems to me pretty much the only way it can work > is for an interested individual to do on their own for free. Either > that, or an established product with aiming at the most mainstream > possible market, e.g. ardour. And even then it will likely struggle. > > On Fri, Dec 18, 2015 at 3:22 AM, Anton Kholomiov > wrote: > > I'm wondering if it's good idea to make crowd-founding project > > for a synthesizer written in Haskell. What's your opinion? > > Would you like to support such a project? > > > > I've made a prototype: > > > > https://github.com/anton-k/tiny-synth > > > > It's a desktop synthesizer, a collection of instruments. About 150 > > instruments > > written in Haskell. It works with midi keyboard. You can try it out with > > USB-midi device. > > > > The UI is written with Python and audio engine is > > written with Haskell. I use my library csound-expression to > > generate the code for Csound. The Csound is an audio programming language > > it can be used as C library. There are bindings to many languages and it > > can work on Android / iOS. > > > > Right now I've made a prototype for desktop. The big plan is to > > create VST/AU/Lv2 plugins and mobile versions for Android and iOS. > > > > [1] https://github.com/anton-k/tiny-synth > > [2] http://hackage.haskell.org/package/csound-expression > > [3] https://github.com/spell-music/csound-expression > > > > Cheers, > > Anton > > > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From imz at altlinux.org Mon Dec 21 10:12:46 2015 From: imz at altlinux.org (Ivan Zakharyaschev) Date: Mon, 21 Dec 2015 13:12:46 +0300 (MSK) Subject: [Haskell-cafe] Q: language-c upstream repo In-Reply-To: References: Message-ID: On Mon, 21 Dec 2015, Ivan Zakharyaschev wrote: > Ganesh Sittampalam re-assured me at http://stackoverflow.com/a/34385874/94687 > that it is not always so bad, and gave advices that I still try to go through > the conversion and pushing my changes to a clone of the other upstream > darcs-2 repo: > Unfortunately, it didn't go smoothly -- when pushing the converted repo, > darcs "couldn't commute" some tag patches, and it seems it refused to do > anything further: > For now, I'm still in doubt what would be a simple way to transfer the > several last patches to a darcs-2 fork. > > Perhaps, there is some kind of a known problem with converted tags in darcs? It looks like a bug in the darcs conversion in my case, because my darcs-2 result of the conversion lacks some tags, which are present in the darcs-1 source (and also in the hub darcs-2 repo). It's strange that the conversion once done for hub didn't have this problem. ~/TOOLS/prog/language-c.darcs-2 $ darcs show tags imz_init_typos-fixed 0.4.1 0.3.1 $ cd ../language-c ~/TOOLS/prog/language-c $ darcs show tags imz_init_typos-fixed 0.4.1 darcs_apply_bug 0.3.1 0.3 0.1 ~/TOOLS/prog/language-c_hub $ darcs show tags 0.4.1 darcs_apply_bug 0.3.1 0.3 0.1 The conversion was done like this (with some warnings/error messages): ~/TOOLS/prog $ darcs convert darcs-2 language-c language-c.darcs-2 WARNING: the repository produced by this command is not understood by Darcs 1.x, and patches cannot be exchanged between repositories in darcs-1 and darcs-2 formats. Furthermore, repositories created by different invocations of this command SHOULD NOT exchange patches. Please confirm that you have read and understood the above by typing `I understand the consequences of my action': I understand the consequences of my action lossy conversion: merger 0.0 ( merger 0.0 ( hunk ./src/Language/C/Data/Position.hs 115 +-- | advance to the next row +incRow :: Position -> Position +incRow (Position o f r c) = Position o f (r + 1) c +incRow p = p hunk ./src/Language/C/Data/Position.hs 115 +{-# INLINE adjustPos #-} +-- | adjust position: change file and line number, reseting column to 1. This is usually +-- used for #LINE pragmas. The absolute offset is not changed - this can be done +-- by @adjustPos newFile line . incPos (length pragma)@. +adjustPos :: FilePath -> Int -> Position -> Position +adjustPos fname row (Position offs _ _ _) = Position offs fname row 1 +adjustPos _ _ p = p ) hunk ./src/Language/C/Data/Position.hs 115 --- | advance to the next row +-- | advance to the next row, this does not reset the column. use +-- @retPos@ if that's what you want to do. ) Finished converting. Best regards, Ivan From oleg at okmij.org Mon Dec 21 11:17:10 2015 From: oleg at okmij.org (Oleg) Date: Mon, 21 Dec 2015 20:17:10 +0900 Subject: [Haskell-cafe] Preventing sharing Message-ID: <20151221111710.GA2407@Magus.sf-private> The old article Preventing memoization in (AI) search problems http://okmij.org/ftp/Haskell/index.html#memo-off deals with the problem, explaining the trick to deliberately confuse GHC so that it won't perform memoization (sharing). Yes, I know how bad this confusing of GHC sounds: which is part of my argument that lazy evaluation by default was a mistake. From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Mon Dec 21 11:25:08 2015 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Mon, 21 Dec 2015 11:25:08 +0000 Subject: [Haskell-cafe] Preventing sharing In-Reply-To: <20151221111710.GA2407@Magus.sf-private> References: <20151221111710.GA2407@Magus.sf-private> Message-ID: <20151221112508.GA21065@weber> On Mon, Dec 21, 2015 at 08:17:10PM +0900, Oleg wrote: > The old article > Preventing memoization in (AI) search problems > http://okmij.org/ftp/Haskell/index.html#memo-off > > deals with the problem, explaining the trick to deliberately confuse > GHC so that it won't perform memoization (sharing). Yes, I know how > bad this confusing of GHC sounds: which is part of my argument that > lazy evaluation by default was a mistake. Hi Oleg, As I explained here https://mail.haskell.org/pipermail/haskell-cafe/2013-February/106673.html -fno-full-laziness fixes the space leak issue in your iterative deepening example. This isn't a problem with laziness. It's a problem with performing a time optimization which is a space pessimization. In the absence of the "optimization" there is no problem. Tom From oleg at okmij.org Mon Dec 21 11:55:05 2015 From: oleg at okmij.org (Oleg) Date: Mon, 21 Dec 2015 20:55:05 +0900 Subject: [Haskell-cafe] Preventing sharing Message-ID: <20151221115505.GA2585@Magus.sf-private> > -fno-full-laziness fixes the space leak issue in your iterative deepening > example. Yes, and I think it has been mentioned that the flag is a blunt weapon as it affects the whole module... > This isn't a problem with laziness. It's a problem with performing a time > optimization which is a space pessimization. In the absence of the > "optimization" there is no problem. How come it isn't the problem with laziness?! Recall, that pure call-by-name calculus is observationally undistinguishable from the call-by-need (i.e., lazy) calculus. The only reason to have laziness is to avoid recomputations of argument computations should an argument be used more than once -- at the cost of taking memory to store the result of the first evaluation. Thus "performing a time optimization which is a space pessimization" is exactly what laziness is all about -- as the article mentioned earlier argued. Laziness isn't an absolute good -- it is a time-space trade-off, which is not always beneficial. From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Mon Dec 21 12:33:48 2015 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Mon, 21 Dec 2015 12:33:48 +0000 Subject: [Haskell-cafe] Preventing sharing In-Reply-To: <20151221115505.GA2585@Magus.sf-private> References: <20151221115505.GA2585@Magus.sf-private> Message-ID: <20151221123348.GB21065@weber> On Mon, Dec 21, 2015 at 08:55:05PM +0900, Oleg wrote: > > -fno-full-laziness fixes the space leak issue in your iterative deepening > > example. > Yes, and I think it has been mentioned that the flag is a blunt weapon > as it affects the whole module... Agreed. > > This isn't a problem with laziness. It's a problem with performing a time > > optimization which is a space pessimization. In the absence of the > > "optimization" there is no problem. > > How come it isn't the problem with laziness?! Recall, that pure > call-by-name calculus is observationally undistinguishable from the > call-by-need (i.e., lazy) calculus. The only reason to have laziness > is to avoid recomputations of argument computations should an argument > be used more than once -- at the cost of taking memory to store the > result of the first evaluation. Thus "performing a time optimization > which is a space pessimization" is exactly what laziness is all about > -- as the article mentioned earlier argued. Laziness isn't an absolute > good -- it is a time-space trade-off, which is not always beneficial. I don't agree at all. To my mind you are assigning blame to the wrong thing. The operational semantics of f () = let x = in ... are perfectly clear. x is reallocated each time, and is free to be released between calls to f. It's only when an "optimization" rewrites this to x = f () = ... that there is a space leak. Exactly the same applies if the language is strict. Tom From hjgtuyl at chello.nl Mon Dec 21 15:50:38 2015 From: hjgtuyl at chello.nl (Henk-Jan van Tuyl) Date: Mon, 21 Dec 2015 16:50:38 +0100 Subject: [Haskell-cafe] Preventing sharing In-Reply-To: <20151221115505.GA2585@Magus.sf-private> References: <20151221115505.GA2585@Magus.sf-private> Message-ID: On Mon, 21 Dec 2015 12:55:05 +0100, Oleg wrote: : > The only reason to have laziness > is to avoid recomputations of argument computations should an argument > be used more than once -- at the cost of taking memory to store the > result of the first evaluation. Thus "performing a time optimization > which is a space pessimization" is exactly what laziness is all about > -- as the article mentioned earlier argued. Laziness isn't an absolute > good -- it is a time-space trade-off, which is not always beneficial. In paper "Why Functional Programming Matters"[0], John Hughes shows how lazy functional programming can be used for better modularity. A more precise title for the paper would be "Why Lazy Functional Programming Matters". Regards, Henk-Jan van Tuyl [0] http://www.cse.chalmers.se/~rjmh/Papers/whyfp.pdf -- Folding at home What if you could share your unused computer power to help find a cure? In just 5 minutes you can join the world's biggest networked computer and get us closer sooner. Watch the video. http://folding.stanford.edu/ http://Van.Tuyl.eu/ http://members.chello.nl/hjgtuyl/tourdemonad.html Haskell programming -- From ky3 at atamo.com Mon Dec 21 16:05:28 2015 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Mon, 21 Dec 2015 23:05:28 +0700 Subject: [Haskell-cafe] Preventing sharing In-Reply-To: References: <20151221115505.GA2585@Magus.sf-private> Message-ID: On Mon, Dec 21, 2015 at 10:50 PM, Henk-Jan van Tuyl wrote: In paper "Why Functional Programming Matters"[0], John Hughes shows how > lazy functional programming can be used for better modularity. A more > precise title for the paper would be "Why Lazy Functional Programming > Matters". This is Oleg. He's perfectly aware of the paper. The point he's making is not that laziness is bad, but that it shouldn't be the default. And if you note the recent work on -XStrict, there are good arguments about bolting laziness on top of strictness and not doing a nasty -- and thus necessarily heroic -- shoehorn in the reverse direction. See: https://www.reddit.com/r/programming/comments/3sux1d/strict_haskell_xstrict_has_landed/ However, the record remains that Oleg has offered little by way of elegant bolting. His lazy programs based on a strict language tend to be cluttered with lazy and force functions that uglify previously elegant code. His arguments would persuade many more folks if, for instance, he could offer lazy-over-strict translations of Doug McIlroy's power serious one-liners with no loss in elegance: http://www.cs.dartmouth.edu/~doug/powser.html -- Kim-Ee -------------- next part -------------- An HTML attachment was scrubbed... URL: From ky3 at atamo.com Mon Dec 21 16:16:32 2015 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Mon, 21 Dec 2015 23:16:32 +0700 Subject: [Haskell-cafe] Preventing sharing In-Reply-To: References: <20151221115505.GA2585@Magus.sf-private> Message-ID: > His lazy programs based on a strict language tend to be cluttered with > lazy and force functions that uglify previously elegant code. * I think the pair of functions are called "delay" and "force", I forget the precise names. -- Kim-Ee -------------- next part -------------- An HTML attachment was scrubbed... URL: From aovieth at gmail.com Mon Dec 21 16:23:51 2015 From: aovieth at gmail.com (Alexander Vieth) Date: Mon, 21 Dec 2015 11:23:51 -0500 Subject: [Haskell-cafe] Imported rewrite rules are ignored Message-ID: Hi caf?, I observe that rewrite rules from imported modules are ignored by GHC. Given these two files, one module and one executable, the problem can be demonstrated by switching between `rewrite_me` and `rewrite_me_local`. If the rule fires, the program should run cleanly, as the `error` term should be rewritten to `()`. The imported function rewrite_me is not rewritten; but the same thing, rewrite_me_local, defined in the same program, will be rewritten. File RuleModule.hs module RuleModule where {-# NOINLINE rewrite_me #-} rewrite_me :: () -> () rewrite_me = error "Should rewrite" {-# RULES "rewrite_me" forall input . rewrite_me input = () #-} File Rule.hs import RuleModule {-# NOINLINE rewrite_me_local #-} rewrite_me_local :: () -> () rewrite_me_local = error "Should rewrite" {-# RULES "rewrite_local" forall input . rewrite_me_local input = () #-} -- Replace with rewrite_me_local and it's all good. main = case rewrite_me () of () -> return () This is GHC 7.10.2. I compile using -O -fenable-rewrite-rules. Using -dverbose-core2core, the "Desugar (after optimization)" section shows no rules when using rewrite_me, but shows the rule rewrite_local when using the local variant. Maybe this is expected, but I thought it important to mention. Thanks for any advice, Alex -------------- next part -------------- An HTML attachment was scrubbed... URL: From sean at functionaljobs.com Mon Dec 21 17:00:02 2015 From: sean at functionaljobs.com (Functional Jobs) Date: Mon, 21 Dec 2015 12:00:02 -0500 Subject: [Haskell-cafe] New Functional Programming Job Opportunities Message-ID: <5678304c9209a@functionaljobs.com> Here are some functional programming job opportunities that were posted recently: Software Engineer (Scala/Play/Scala.js/React) at AdAgility https://functionaljobs.com/jobs/8871-software-engineer-scala-play-scalajs-react-at-adagility Cheers, Sean Murphy FunctionalJobs.com From jan.stolarek at p.lodz.pl Mon Dec 21 17:52:34 2015 From: jan.stolarek at p.lodz.pl (Jan Stolarek) Date: Mon, 21 Dec 2015 18:52:34 +0100 Subject: [Haskell-cafe] RFC: explicit support for GADTs in Template Haskell Message-ID: <201512211852.34425.jan.stolarek@p.lodz.pl> GHC Users, I am working on adding proper support for GADTs in Template Haskell. By proper I mean that GADTs data constructors will no longer be encoded using H98 data constructors, but will be represented explicity. GADTs allow to declare several constructors with the same signature: data T where MkT1, MkT2 :: T The question is whether to represent such constructors in TH syntax as: (1) GadtC [Name] [StrictType] Name [Type] -- or: (2) GadtC Name [StrictType] Name [Type] Note the difference in first field. (1) is closer to the original syntax, as it stores the list of all names in a single declaration, as was originally written in the source code. (2) requires to have a separate `GadtC` for each constructor even if constructors were declared together, as in the example above. I would like to hear from TH users which of these two representations you prefer. At the moment I have implemented (1) as it directly represents source syntax. The downside of (1) is that information whether several data constructors were declared together is not recoverable during reification, and so reifying T will yield: data T where MkT1 :: T MkT2 :: T Janek --- Politechnika ??dzka Lodz University of Technology Tre?? tej wiadomo?ci zawiera informacje przeznaczone tylko dla adresata. Je?eli nie jeste?cie Pa?stwo jej adresatem, b?d? otrzymali?cie j? przez pomy?k? prosimy o powiadomienie o tym nadawcy oraz trwa?e jej usuni?cie. This email contains information intended solely for the use of the individual to whom it is addressed. If you are not the intended recipient or if you have received this message in error, please notify the sender and delete it from your system. From johannes.waldmann at htwk-leipzig.de Mon Dec 21 17:56:33 2015 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Mon, 21 Dec 2015 18:56:33 +0100 Subject: [Haskell-cafe] Imported rewrite rules are ignored Message-ID: <56783D51.5050401@htwk-leipzig.de> Well, ghc --show-iface RuleModule.hi does show the rule: rewrite_me :: () -> () {- Strictness: b, Inline: NOINLINE -} "rewrite_me" [ALWAYS] forall input :: () rewrite_me input = () From johannes.waldmann at htwk-leipzig.de Mon Dec 21 18:21:05 2015 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Mon, 21 Dec 2015 19:21:05 +0100 Subject: [Haskell-cafe] Imported rewrite rules are ignored Message-ID: <56784311.2010100@htwk-leipzig.de> Forgot to say: I confirm your observation for ghc-7.* and I checked that the imported rule *does* fire with ghc-6.10.4. From roma at ro-che.info Mon Dec 21 18:30:22 2015 From: roma at ro-che.info (Roman Cheplyaka) Date: Mon, 21 Dec 2015 20:30:22 +0200 Subject: [Haskell-cafe] RFC: explicit support for GADTs in Template Haskell In-Reply-To: <201512211852.34425.jan.stolarek@p.lodz.pl> References: <201512211852.34425.jan.stolarek@p.lodz.pl> Message-ID: <5678453E.9080106@ro-che.info> Hi Janek, Shouldn't it be represented the same way as in GHC's own AST? Especially regarding a recent thread about unifying the two (IIRC). On 12/21/2015 07:52 PM, Jan Stolarek wrote: > GHC Users, > > I am working on adding proper support for GADTs in Template Haskell. By proper I mean that GADTs > data constructors will no longer be encoded using H98 data constructors, but will be represented > explicity. > > GADTs allow to declare several constructors with the same signature: > > data T where > MkT1, MkT2 :: T > > The question is whether to represent such constructors in TH syntax as: > > (1) GadtC [Name] [StrictType] Name [Type] -- or: > (2) GadtC Name [StrictType] Name [Type] > > Note the difference in first field. (1) is closer to the original syntax, as it stores the list of > all names in a single declaration, as was originally written in the source code. (2) requires to > have a separate `GadtC` for each constructor even if constructors were declared together, as in > the example above. > > I would like to hear from TH users which of these two representations you prefer. At the moment I > have implemented (1) as it directly represents source syntax. The downside of (1) is that > information whether several data constructors were declared together is not recoverable during > reification, and so reifying T will yield: > > data T where > MkT1 :: T > MkT2 :: T > > Janek > > --- > Politechnika ??dzka > Lodz University of Technology > > Tre?? tej wiadomo?ci zawiera informacje przeznaczone tylko dla adresata. > Je?eli nie jeste?cie Pa?stwo jej adresatem, b?d? otrzymali?cie j? przez pomy?k? > prosimy o powiadomienie o tym nadawcy oraz trwa?e jej usuni?cie. > > This email contains information intended solely for the use of the individual to whom it is addressed. > If you are not the intended recipient or if you have received this message in error, > please notify the sender and delete it from your system. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: OpenPGP digital signature URL: From will.yager at gmail.com Mon Dec 21 19:11:17 2015 From: will.yager at gmail.com (Will Yager) Date: Mon, 21 Dec 2015 13:11:17 -0600 Subject: [Haskell-cafe] More disciplined alternative to rewrite rules? Message-ID: <0B2F6AB2-58BC-4156-88A8-236699393F50@gmail.com> Has there been any discussion of replacing rewrite rules with a more disciplined and robust system? Some problems I've noticed with rewrite rules are: A) It's highly syntactic. It isn't really capable of encapsulating intent; it just does restrictively simple term manipulation. B) As a result, many performance-oriented modules seem to have an ungainly number of rewrite rules so as to cover every likely case. C) There are many cases where rewrite rules fail to work as intended, either because the module author missed a rewrite case or because the rewrite fails to fire for some reason. Perhaps a good approach would be to implement a rewrite system in a domain more amenable to simplification rules. For example, there has been a great deal of (quite successful) work on circuit simplification in the form of operations on graphs. Haskell is quite amenable to graph representations, so this approach might work for Haskell as well. -Will From johannes.waldmann at htwk-leipzig.de Mon Dec 21 19:34:12 2015 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Mon, 21 Dec 2015 20:34:12 +0100 Subject: [Haskell-cafe] More disciplined alternative to rewrite rules? Message-ID: <56785434.8060203@htwk-leipzig.de> What graph(s) do you want to rewrite? How would this help with respect to A, B, and C? The program is a term (tree), the runtime data structure (heap) is a graph - you want rewriting at run-time then? But the purpose is to move work from run-time to compile-time. - J.W. From will.yager at gmail.com Mon Dec 21 19:47:56 2015 From: will.yager at gmail.com (Will Yager) Date: Mon, 21 Dec 2015 13:47:56 -0600 Subject: [Haskell-cafe] More disciplined alternative to rewrite rules? In-Reply-To: <56785434.8060203@htwk-leipzig.de> References: <56785434.8060203@htwk-leipzig.de> Message-ID: This would be a static rewrite system, of course. Are you familiar with any of the Haskell to hardware compilation projects? It turns out that it is quite sensible to interpret Haskell programs as graphs or circuits. When you say "The program is a term (tree)", you are suffering from the same conceptual limitation as the existing rewrite system. The syntactic representation of the program is the most natural to humans, but it is perhaps not the best for simplification. I simply suggested graphs as a representation suited for optimization because there is a great deal of research in this domain (for VLSI software) and I know Haskell programs are well suited to graph representation. There are, I suspect, other domains conducive to optimization that Haskell programs could also be converted to. -Will > On Dec 21, 2015, at 13:34, Johannes Waldmann wrote: > > What graph(s) do you want to rewrite? > How would this help with respect to A, B, and C? > > The program is a term (tree), the runtime data structure > (heap) is a graph - you want rewriting at run-time then? > But the purpose is to move work from run-time to compile-time. > > - J.W. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe From johannes.waldmann at htwk-leipzig.de Mon Dec 21 20:44:42 2015 From: johannes.waldmann at htwk-leipzig.de (Johannes Waldmann) Date: Mon, 21 Dec 2015 21:44:42 +0100 Subject: [Haskell-cafe] More disciplined alternative to rewrite rules? In-Reply-To: References: <56785434.8060203@htwk-leipzig.de> Message-ID: <567864BA.40706@htwk-leipzig.de> > The syntactic representation of the program is the most natural to humans, > but it is perhaps not the best for simplification. Maybe so. Please give examples. We use graphs (instead of trees) to express sharing. Do you see sharing (or the lack of expressibility for it) as a problem with GHC rules currently? - J.W. From qdunkan at gmail.com Mon Dec 21 21:24:16 2015 From: qdunkan at gmail.com (Evan Laforge) Date: Mon, 21 Dec 2015 13:24:16 -0800 Subject: [Haskell-cafe] wondering on Haskell kickstarter project: VST plugin / mobile synthesizer In-Reply-To: References: Message-ID: On Mon, Dec 21, 2015 at 2:03 AM, Anton Kholomiov wrote: > @Evan > > Thanks for detailed and sincere reply. I can see your points. > That VST/mobiles market is very crowded business and it's really > hard to compete with super giants especially when you > don't provide any significant change or creative opportunity > in the app. > > So I think this project is going to be more a prove of the > concept and example that it's really possible to create > real-time audio with Haskell and wrap it in non-Haskell UI. > Hope I would manage to do the mobile version of it too some days. > I would really like to add non equal temeprament scales, I feel > that it can make a difference to the mood of the music. This is a basic requirement for me, because most of the music I'm interested in doesn't use equal temperament. MIDI makes it really inconvenient though, which is one reason why if I did my own synthesizer it wouldn't use MIDI. Supporting multiple MIDI channels is about as convenient as MIDI can get, but very few VSTs do even that. But computers are fast and loading say 8 copies of the same VST actually works, though it's aesthetically unappealing. Actually, it only works for cheap synthesis like FM... so maybe it doesn't work that great. As far as I can tell, if you're using MIDI there is no satisfactory answer. Some synthesizers can load scala files too, which more complicated and not as flexible, but it can sidestep the multiple VST hassle. Of course it's static so it only works for instruments like percussion that are not pitch continuous. Even though there is a crowded market of giants, from my perspective they all have fundamental holes in their functionality, but it works for them because they aim at a market not interested in those things. > Maybe it's better to look in the direction of media installations. > The Python has many cool libraries for non-trivial user interaction > like computer vision. It would be great to stream this data > in Haskell generated synthesizer. Maybe something can be created in this > area. Indeed, it does sound interesting. Ultimately it's whatever is interesting enough to you that doing it would be its own reward. I did a little experimentation with interactive musical toys in python back in college, and it was kind of neat... though ultimately didn't pursue it any further. With a powerful language like haskell and access down to the low level synthesis you could express more complicated kinds of control. From jan.stolarek at p.lodz.pl Mon Dec 21 22:00:09 2015 From: jan.stolarek at p.lodz.pl (Jan Stolarek) Date: Mon, 21 Dec 2015 23:00:09 +0100 Subject: [Haskell-cafe] RFC: explicit support for GADTs in Template Haskell In-Reply-To: <5678453E.9080106@ro-che.info> References: <201512211852.34425.jan.stolarek@p.lodz.pl> <5678453E.9080106@ro-che.info> Message-ID: <201512212300.09651.jan.stolarek@p.lodz.pl> > Shouldn't it be represented the same way as in GHC's own AST? My personal opinion is that it should. But I wanted to hear what others have to say. If there is a strong bias towards option (2) I will re-consider my design decision. Janek > Especially > regarding a recent thread about unifying the two (IIRC). > > On 12/21/2015 07:52 PM, Jan Stolarek wrote: > > GHC Users, > > > > I am working on adding proper support for GADTs in Template Haskell. By > > proper I mean that GADTs data constructors will no longer be encoded > > using H98 data constructors, but will be represented explicity. > > > > GADTs allow to declare several constructors with the same signature: > > > > data T where > > MkT1, MkT2 :: T > > > > The question is whether to represent such constructors in TH syntax as: > > > > (1) GadtC [Name] [StrictType] Name [Type] -- or: > > (2) GadtC Name [StrictType] Name [Type] > > > > Note the difference in first field. (1) is closer to the original syntax, > > as it stores the list of all names in a single declaration, as was > > originally written in the source code. (2) requires to have a separate > > `GadtC` for each constructor even if constructors were declared together, > > as in the example above. > > > > I would like to hear from TH users which of these two representations you > > prefer. At the moment I have implemented (1) as it directly represents > > source syntax. The downside of (1) is that information whether several > > data constructors were declared together is not recoverable during > > reification, and so reifying T will yield: > > > > data T where > > MkT1 :: T > > MkT2 :: T > > > > Janek > > > > --- > > Politechnika ??dzka > > Lodz University of Technology > > > > Tre?? tej wiadomo?ci zawiera informacje przeznaczone tylko dla adresata. > > Je?eli nie jeste?cie Pa?stwo jej adresatem, b?d? otrzymali?cie j? przez > > pomy?k? prosimy o powiadomienie o tym nadawcy oraz trwa?e jej usuni?cie. > > > > This email contains information intended solely for the use of the > > individual to whom it is addressed. If you are not the intended recipient > > or if you have received this message in error, please notify the sender > > and delete it from your system. > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe --- Politechnika ??dzka Lodz University of Technology Tre?? tej wiadomo?ci zawiera informacje przeznaczone tylko dla adresata. Je?eli nie jeste?cie Pa?stwo jej adresatem, b?d? otrzymali?cie j? przez pomy?k? prosimy o powiadomienie o tym nadawcy oraz trwa?e jej usuni?cie. This email contains information intended solely for the use of the individual to whom it is addressed. If you are not the intended recipient or if you have received this message in error, please notify the sender and delete it from your system. From trebla at vex.net Mon Dec 21 22:07:56 2015 From: trebla at vex.net (Albert Y. C. Lai) Date: Mon, 21 Dec 2015 17:07:56 -0500 Subject: [Haskell-cafe] Preventing sharing In-Reply-To: References: <20151221115505.GA2585@Magus.sf-private> Message-ID: <5678783C.1030907@vex.net> I have a cunning plan. Default to call-by-name. From amos.robinson at gmail.com Mon Dec 21 23:40:57 2015 From: amos.robinson at gmail.com (Amos Robinson) Date: Mon, 21 Dec 2015 23:40:57 +0000 Subject: [Haskell-cafe] More disciplined alternative to rewrite rules? In-Reply-To: <567864BA.40706@htwk-leipzig.de> References: <56785434.8060203@htwk-leipzig.de> <567864BA.40706@htwk-leipzig.de> Message-ID: Hi, Some kind of graph rewriting on the term is a promising idea, but I have no idea how that would look. I would like to hear more. I have an example where sharing is a barrier to shortcut fusion. In Stream fusion combinators like map, filter and so on are implemented as converting from list to streams, a stream transformer, then back to a list: map f = unstream . map_s f . stream Then the rewrite rule removes superfluous conversion: {-# RULES stream . unstream = id #-} So if you have map.map, this gets fused away: map f . map g = (inline map) unstream . map_s f . stream . unstream . map_s g . stream = (rewrite rule) unstream . map_s f . map_s g . stream However, this doesn't work once you introduce sharing: let ys = map f xs in (map g ys, map h ys) = (inline map) let ys = unstream (map_s f (stream xs)) in (unstream (map g (stream ys)), unstream (map h (stream ys))) here, we cannot inline substitute "ys" into both use sites as it would duplicate work, so the rewrite rules have no way of firing. GHC has another pragma called "CONLIKE", which declares a particular function to be "cheap enough" to duplicate if duplication would cause a rule to fire. Data.Vector doesn't seem to use this in its stream fusion implementation, and I'm not sure why. It may solve this case, but I'm not sure it solves all cases On Tue, 22 Dec 2015 at 07:44 Johannes Waldmann < johannes.waldmann at htwk-leipzig.de> wrote: > > > The syntactic representation of the program is the most natural to > humans, > > but it is perhaps not the best for simplification. > > Maybe so. Please give examples. > > We use graphs (instead of trees) to express sharing. > Do you see sharing (or the lack of expressibility for it) > as a problem with GHC rules currently? > > - J.W. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From erkokl at gmail.com Tue Dec 22 08:43:46 2015 From: erkokl at gmail.com (Levent Erkok) Date: Tue, 22 Dec 2015 00:43:46 -0800 Subject: [Haskell-cafe] [ANNOUNCE] sbvPlugin: Run SMT solvers over Haskell "theorems" Message-ID: Hello all, I'm happy to announce the first public release of sbvPlugin, a new GHC-core plugin based on the SBV library: http://hackage.haskell.org/package/sbvPlugin The plugin can be used to prove (or refute!) theorems in your Haskell code, using the SBV library as its backend. Here's a most simple example: {-# OPTIONS_GHC -fplugin=Data.SBV.Plugin #-} module Test where import Data.SBV.Plugin {-# ANN test theorem #-} test :: Integer -> Integer -> Bool test x y = x + y >= x - y When compiled (or loaded into ghci), you'll see that the plugin will attempt to prove the given theorem, and will produce a counter-example since it is not valid! (This assumes, you've installed an SBV-supported SMT solver. Z3 from Microsoft is a good choice: http://github.com/Z3Prover/z3) The plugin is still in its early days and the examples are rather sparse. But see the following for one worked out instance: (Thanks to Anthony Cowley for the original idea.) http://hackage.haskell.org/package/sbvPlugin/docs/Data-SBV-Plugin-Examples-MicroController.html The sbvPlugin takes advantage of the SBV library ( http://hackage.haskell.org/package/sbv) to directly reason about Haskell programs at GHC's core level. However, the plugin is *not* a replacement for SBV. It only exposes a few features of SBV directly at the Haskell level; which hopefully makes it useful and more friendly than SBV; but it is neither intended nor possible for it to replace the SBV library itself. In particular, the plugin is limited to certain types (mostly numeric), and a few composite ones (lists and tuples.) If the plugin does not "understand" a Haskell type/expression, it'll use a technique called "uninterpretation" to black-box it. In those cases, the counter-examples produced might be bogus, though proofs will still be valid. Note that any definitions that are outside of the module being compiled will also go uninterpreted, including all the Prelude functions. The plugin is still in its early days, and there are a number of rough edges. Any feedback is most welcome! Happy hacking, -Levent. -------------- next part -------------- An HTML attachment was scrubbed... URL: From imz at altlinux.org Tue Dec 22 08:56:04 2015 From: imz at altlinux.org (Ivan Zakharyaschev) Date: Tue, 22 Dec 2015 11:56:04 +0300 (MSK) Subject: [Haskell-cafe] Q: language-c upstream repo (fwd) Message-ID: ---------- Forwarded message ---------- Date: Tue, 22 Dec 2015 05:59:17 +0000 From: Benedikt Huber To: Ivan Zakharyaschev , haskell-cafe at haskell.org Subject: Re: Q: language-c upstream repo Hi Ivan, the hub.darcs.net repository is a mirror of http://code.haskell.org/language-c (the official upstream) that was created to simplify contributing. Conversion to darcs-2 was not straightforward IIRC, and the update of the repository did not work out.That's why code.haskell.org is still darcs-1. Best, Benedikt Ivan Zakharyaschev schrieb am So., 20. Dez. 2015 um 16:32?Uhr: Hello! I've been interested in hacking language-c library a bit for my needs. (If it turns out useful and successful, I'll tell about it.) And I've cloned the repo listed at https://hackage.haskell.org/package/language-c-0.4.7 , namely: http://code.haskell.org/language-c Apart from my special hacks, I've also fixed some typos and so on. But then I discovered that if I want to publish them on hub.darcs.net , I need a darcs-2 repo, and the initial one which I used for cloning is a darcs-1 repo. I could do the conversion to darcs-2, but I read that it is not reproducible: run several times on the same set of patches it will give different results. As I've discovered also a language-c repo at hub.darcs.net which looks like an upstream repo: http://hub.darcs.net/visq/language-c , I'm in doubt whether I should continue making my patches against the darcs-1 repo which is said to be upstream at hackage or against http://hub.darcs.net/visq/language-c whichis not officially declared as the upstream but looks more fresh. ..if I want to be able to send some of my patches upstream. Best regards, Ivan From Andrew.Butterfield at scss.tcd.ie Tue Dec 22 09:09:19 2015 From: Andrew.Butterfield at scss.tcd.ie (Andrew Butterfield) Date: Tue, 22 Dec 2015 09:09:19 +0000 Subject: [Haskell-cafe] Data.Map docs missing on hackage Message-ID: Is there a problem on hackage ?- when I try to look up Data.Map (via Hoogle) I get an error: ------------------- Not Found There is no documentation for containers-0.5.7.1. See https://hackage.haskell.org/package/containers/docs/Data-Map.html for the latest version. ---------------- Going to that link gives the exact same error Andrew Butterfield School of Computer Science & Statistics Trinity College Dublin 2, Ireland From yom at artyom.me Tue Dec 22 09:13:20 2015 From: yom at artyom.me (Artyom) Date: Tue, 22 Dec 2015 12:13:20 +0300 Subject: [Haskell-cafe] Data.Map docs missing on hackage In-Reply-To: References: Message-ID: <56791430.7010309@artyom.me> The latest version of containers has been uploaded very recently and Hackage hasn't built the docs yet. Try looking at https://hackage.haskell.org/package/containers-0.5.7.0/docs/Data-Map.html. The error message is unfortunate, I agree. Hackage could be a bit more clever about that. On 12/22/2015 12:09 PM, Andrew Butterfield wrote: > Is there a problem on hackage ?- when I try to look up Data.Map (via Hoogle) I get an error: > > ------------------- > Not Found > There is no documentation for containers-0.5.7.1. See https://hackage.haskell.org/package/containers/docs/Data-Map.html for the latest version. > ---------------- > > Going to that link gives the exact same error > > > Andrew Butterfield > School of Computer Science & Statistics > Trinity College > Dublin 2, Ireland > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe From ollie at ocharles.org.uk Tue Dec 22 09:38:41 2015 From: ollie at ocharles.org.uk (Oliver Charles) Date: Tue, 22 Dec 2015 09:38:41 +0000 Subject: [Haskell-cafe] Data.Map docs missing on hackage In-Reply-To: <56791430.7010309@artyom.me> References: <56791430.7010309@artyom.me> Message-ID: This is happening far too often imo, I think it might worth considering having `cabal upload` upload documentation at the same time. On Tue, Dec 22, 2015 at 9:13 AM Artyom wrote: > The latest version of containers has been uploaded very recently and > Hackage hasn't built the docs yet. Try looking at > https://hackage.haskell.org/package/containers-0.5.7.0/docs/Data-Map.html. > > The error message is unfortunate, I agree. Hackage could be a bit more > clever about that. > > On 12/22/2015 12:09 PM, Andrew Butterfield wrote: > > Is there a problem on hackage ?- when I try to look up Data.Map (via > Hoogle) I get an error: > > > > ------------------- > > Not Found > > There is no documentation for containers-0.5.7.1. See > https://hackage.haskell.org/package/containers/docs/Data-Map.html for the > latest version. > > ---------------- > > > > Going to that link gives the exact same error > > > > > > Andrew Butterfield > > School of Computer Science & Statistics > > Trinity College > > Dublin 2, Ireland > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From imz at altlinux.org Tue Dec 22 09:59:27 2015 From: imz at altlinux.org (Ivan Zakharyaschev) Date: Tue, 22 Dec 2015 12:59:27 +0300 (MSK) Subject: [Haskell-cafe] Q: language-c upstream repo (fwd) In-Reply-To: References: Message-ID: Hi, Benedikt! Thanks for your reply clarifying these things. > ---------- Forwarded message ---------- > Date: Tue, 22 Dec 2015 05:59:17 +0000 > From: Benedikt Huber > the hub.darcs.net repository is a mirror of > http://code.haskell.org/language-c (the official upstream) that was created > to simplify contributing. > Conversion to darcs-2 was not straightforward IIRC, and the update of the > repository did not work out.That's why code.haskell.org is still darcs-1. To be able to push to hub.darcs.net, I've done the conversion with "darcs convert darcs-2" with the help of the advices from darcs developers -- after a "darcs optimize reorder", and the resulting darcs-2 repo had no problems with pushing to (a clone of) your darcs-2 repo at hub.darcs.net. (Although one thing that still appears strange to me is that some tags were lost in my result of the conversion, but not in your darcs-2 repo. I've described all this in the previous messages in this thread.) Anyway, now, this darcs-2 mirror of the upstream code.haskell.org darcs-1 repo is at http://hub.darcs.net/imz/language-c_hackage It is "compatible" with your darcs-2 repo at hub.darcs.net, and compared to it has 2 extra patches. These are the last two changes in the "official upstream" darcs-1 repo (they are from December 2014). > Ivan Zakharyaschev schrieb am So., 20. Dez. 2015 um > 16:32?Uhr: > I've been interested in hacking language-c library a bit for my needs. > (If > it turns out useful and successful, I'll tell about it.) > > And I've cloned the repo listed at > https://hackage.haskell.org/package/language-c-0.4.7 , namely: > http://code.haskell.org/language-c > > Apart from my special hacks, I've also fixed some typos and so on. > > But then I discovered that if I want to publish them on hub.darcs.net > , I > need a darcs-2 repo, and the initial one which I used for cloning is > a darcs-1 repo. > > I could do the conversion to darcs-2, but I read that it is not > reproducible: run several times on the same set of patches it will > give > different results. > > As I've discovered also a language-c repo at hub.darcs.net which looks > like an upstream repo: http://hub.darcs.net/visq/language-c , I'm in > doubt > whether I should continue making my patches against the darcs-1 repo > which > is said to be upstream at hackage or against > http://hub.darcs.net/visq/language-c whichis not officially declared > as > the upstream but looks more fresh. > > ..if I want to be able to send some of my patches upstream. Best regards, Ivan From imantc at gmail.com Tue Dec 22 10:02:39 2015 From: imantc at gmail.com (Imants Cekusins) Date: Tue, 22 Dec 2015 11:02:39 +0100 Subject: [Haskell-cafe] Data.Map docs missing on hackage In-Reply-To: References: <56791430.7010309@artyom.me> Message-ID: > upload documentation at the same time .. or even redirect to a previous existing version.. -------------- next part -------------- An HTML attachment was scrubbed... URL: From fa-ml at ariis.it Tue Dec 22 10:14:50 2015 From: fa-ml at ariis.it (Francesco Ariis) Date: Tue, 22 Dec 2015 11:14:50 +0100 Subject: [Haskell-cafe] Data.Map docs missing on hackage In-Reply-To: References: <56791430.7010309@artyom.me> Message-ID: <20151222101450.GA2049@casa.casa> On Tue, Dec 22, 2015 at 11:02:39AM +0100, Imants Cekusins wrote: > > upload documentation at the same time > > .. or even redirect to a previous existing version.. That would be a bit risky though (99% better than no documentation, to be fair). From imantc at gmail.com Tue Dec 22 11:01:34 2015 From: imantc at gmail.com (Imants Cekusins) Date: Tue, 22 Dec 2015 12:01:34 +0100 Subject: [Haskell-cafe] Data.Map docs missing on hackage In-Reply-To: <20151222101450.GA2049@casa.casa> References: <56791430.7010309@artyom.me> <20151222101450.GA2049@casa.casa> Message-ID: > That would be a bit risky frequent readers of Data.Map docs (like me) would most likely prefer out-of-date docs over blank page. It takes time and effort to make this change so I'll patiently wait for the new docs. From fa-ml at ariis.it Tue Dec 22 11:55:18 2015 From: fa-ml at ariis.it (Francesco Ariis) Date: Tue, 22 Dec 2015 12:55:18 +0100 Subject: [Haskell-cafe] Data.Map docs missing on hackage In-Reply-To: References: <56791430.7010309@artyom.me> <20151222101450.GA2049@casa.casa> Message-ID: <20151222115518.GA3761@casa.casa> On Tue, Dec 22, 2015 at 12:01:34PM +0100, Imants Cekusins wrote: > > That would be a bit risky > > frequent readers of Data.Map docs (like me) would most likely prefer > out-of-date docs over blank page. > > It takes time and effort to make this change so I'll patiently wait > for the new docs. One thing that I found helpful is having /offline/ documentation! Modify the appropriate line in ~/.cabal/config and then create an alias alias ghdoc='lynx ~/.cabal/share/doc/i386-linux-ghc-7.10.2/index.html' Voil?, no more missing-documentation blues (or offline blues). Hoogle works offline too, I am pretty happy with the setup. From oleg at okmij.org Tue Dec 22 12:24:37 2015 From: oleg at okmij.org (Oleg) Date: Tue, 22 Dec 2015 21:24:37 +0900 Subject: [Haskell-cafe] Preventing sharing In-Reply-To: <20151221123348.GB21065@weber> Message-ID: <20151222122437.GA1845@Magus.sf-private> > > Thus "performing a time optimization > > which is a space pessimization" is exactly what laziness is all about > > -- as the article mentioned earlier argued. Laziness isn't an absolute > > good -- it is a time-space trade-off, which is not always beneficial. > > I don't agree at all. To my mind you are assigning blame to the wrong > thing. The operational semantics of > > f () = let x = in ... > > are perfectly clear. x is reallocated each time, and is free to be released > between calls to f. It's only when an "optimization" rewrites this to > > x = > > f () = ... > > that there is a space leak. Exactly the same applies if the language is > strict. Let us take a step back. The article on my web page noted the great difficulty of writing AI search program in Haskell because the search tree is evaluated lazily: whenever a node is evaluated, its result is memoized for further use. That is precisely the wrong thing to do for such problems. Again, this problem is precisely of lazy evaluation (as defined in the book below). The obvious way to avoid memoization was to introduce thunks -- which didn't work. The article then developed a more involved solution. Yes, -no-full-laziness would have worked just as well. However, the solution in the article works on the case-by-case basis whereas -no-full-laziness affects the whole compilation unit. It is for that reason that I pointed out the article in this discussion. Let us turn to the problem of the "optimization" that we are discussing. Does it have anything to do with laziness? Yes, it does. Please see Chap 15 of the excellent book http://research.microsoft.com/en-us/um/people/simonpj/papers/slpj-book-1987/ which explains the full laziness. Once I mention the book I must point out Chap 23 of the book (near the end). It should be the required read. The introduction to the section contains the following emphasized statement (emphasized by the author, Simon Peyton Jones): A major weakness of functional languages is the difficulty of reasoning about their space and time behavior. The last paragraph of the introduction says ``No good solutions are yet known to most of these problems.'' This is true even today. Sec 23.3 ``Space behavior'' is the excellent collection of the problems with lazy evaluation and full laziness. The book was published in 1987. The problems are still with us. From imantc at gmail.com Tue Dec 22 12:26:25 2015 From: imantc at gmail.com (Imants Cekusins) Date: Tue, 22 Dec 2015 13:26:25 +0100 Subject: [Haskell-cafe] Data.Map docs missing on hackage In-Reply-To: <20151222115518.GA3761@casa.casa> References: <56791430.7010309@artyom.me> <20151222101450.GA2049@casa.casa> <20151222115518.GA3761@casa.casa> Message-ID: > offline/ documentation very helpful tip, Francesco! Mille grazie! the ~/.cabal/config entry is: documentation: True if you use cabal sandbox, the relative (from sandbox root) path to index.html is: .cabal-sandbox/share/doc/$arch-$os-$compiler/index.html From oleg at okmij.org Tue Dec 22 12:31:56 2015 From: oleg at okmij.org (Oleg) Date: Tue, 22 Dec 2015 21:31:56 +0900 Subject: [Haskell-cafe] Preventing sharing In-Reply-To: Message-ID: <20151222123156.GA1886@Magus.sf-private> Henk-Jan van Tuyl wrote: > In paper "Why Functional Programming Matters"[0], John Hughes shows how > lazy functional programming can be used for better modularity. A more > precise title for the paper would be "Why Lazy Functional Programming > Matters". The first paragraph of our paper (published 3 years ago) http://okmij.org/ftp/ftp/continuations/PPYield/index.html#introduction is as follows Lazy evaluation is regarded as one of the main reasons why functional programming matters \cite{hughes:matters-cj}. Lazy evaluation lets us write \emph{producers} and \emph{consumers} separately, whereas the two are inextricably intertwined in a call-by-value language. This separation allows a modular style of programming, in which a variety of producers, consumers, and transformers can readily be ``plugged together.'' Lazy evaluation is also an elegant implementation of a form of coroutines, suspending and resuming computations based on the demand for values, giving us memory-efficient, incremental computation `for free' \cite{McIlroy:1999:PSP:968592.968597,Bird:1984:UCP,AG-embed}. But do read the next paragraph and the rest of the paper, and other articles on the web site http://okmij.org/ftp/continuations/PPYield/index.html Our conclusion is that the modularity benefit of lazy evaluation can be held without lazy evaluation, gaining the predictability of the space and time behavior. From takenobu.hs at gmail.com Tue Dec 22 13:03:28 2015 From: takenobu.hs at gmail.com (Takenobu Tani) Date: Tue, 22 Dec 2015 22:03:28 +0900 Subject: [Haskell-cafe] Lazy evaluation illustrated for Haskell divers Message-ID: Dear cafe, I'm studying and enjoying for Haskell. I'm drawing some illustrations about lazy evaluation in Haskell. Of course, I know a lot of pretty good documents. My document is one of the starter-kits to them. Here is: Lazy evaluation illustrated for Haskellers http://takenobu-hs.github.io/downloads/haskell_lazy_evaluation.pdf https://github.com/takenobu-hs/lazy_evaluation If there are misunderstandings, please teach me. I'll correct them. I apology if my responses is late. This is my night work (fun) =) I wish you a happy new year. Enjoy, lazy!, Takenobu -------------- next part -------------- An HTML attachment was scrubbed... URL: From jo at durchholz.org Tue Dec 22 17:31:08 2015 From: jo at durchholz.org (Joachim Durchholz) Date: Tue, 22 Dec 2015 18:31:08 +0100 Subject: [Haskell-cafe] Preventing sharing In-Reply-To: <20151222123156.GA1886@Magus.sf-private> References: <20151222123156.GA1886@Magus.sf-private> Message-ID: <567988DC.2070406@durchholz.org> Am 22.12.2015 um 13:31 schrieb Oleg: > > But do read the next paragraph and the rest of the paper, and other > articles on the web site > http://okmij.org/ftp/continuations/PPYield/index.html I have to say I almost stopped reading at "worst in lazy evaluation: its incompatibility with effects". Incompatibility with side effects is a good thing, so that's not "worst", and there are frameworks for doing effects (most notably IO), so there goes "incompatibility". > Our conclusion is that the modularity benefit of lazy evaluation can > be held without lazy evaluation, gaining the predictability of the > space and time behavior. I just skimmed the paper, so correct me if I'm wrong. It seems to show how one can transform a specific class of lazy functions into generators. This seems to miss the point of laziness. Having lazy evaluation means that when writing a function, you don't know (and don't care) how much of the returned data structure is ever explored, that's the caller's decision. This means you do not ever transform your code as a generator, because you don't need to. As I said, I didn't do more than a quick scan, and I might be in error thinking it's a transformation just for a specific class of lazy functions. More importantly, I might have missed some essential point about how this isn't really a transformation, or that one does not need to transform the code to get a transformer out. So... please correct the omissions :-) Regards, Jo From ky3 at atamo.com Tue Dec 22 18:01:29 2015 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Wed, 23 Dec 2015 01:01:29 +0700 Subject: [Haskell-cafe] Preventing sharing In-Reply-To: <20151222122437.GA1845@Magus.sf-private> References: <20151221123348.GB21065@weber> <20151222122437.GA1845@Magus.sf-private> Message-ID: On Tue, Dec 22, 2015 at 7:24 PM, Oleg wrote: Let us take a step back. The article on my web page noted the great > difficulty of writing AI search program in Haskell because the search > tree is evaluated lazily: whenever a node is evaluated, its result is > memoized for further use. That is precisely the wrong thing to do for > such problems. Again, this problem is precisely of lazy evaluation (as > defined in the book below). The obvious way to avoid memoization was > to introduce thunks -- which didn't work. The article then developed a > more involved solution. Yes, -no-full-laziness would have worked just > as well. However, the solution in the article works on the > case-by-case basis whereas -no-full-laziness affects the whole > compilation unit. It is for that reason that I pointed out the article > in this discussion. Dear Oleg: First you paint with a wide brush that laziness is "precisely the wrong thing to do for such problems." Then you implicitly acknowledge that there are different levels of laziness, namely that non-full-laziness is less lazy than full laziness. Call them laziness Levels 1 and 2, respectively Finally, you cite your local solution as an improvement to the blunt one of throttling the whole module to mere laziness Level 1. Therefore, the clever Level 1 localization is an improvement only if laziness Level 2 is useful in other parts of the module, yes? How can laziness be so bad, as the shrillness of your emails convey, if a laziness Level /2/ -- never mind Level 1 -- is actually useful elsewhere in your code? Notwithstanding your eagerness to warn of the pitfalls of laziness, your true position on laziness is undoubtedly nuanced in a manner that befits your discernment and decades of programming experience. Unfortunately, here you don't express that nuance clearly, and we are left in the dark. -- Kim-Ee -------------- next part -------------- An HTML attachment was scrubbed... URL: From gombocarti at gmail.com Tue Dec 22 20:28:33 2015 From: gombocarti at gmail.com (=?UTF-8?B?QXJ0w7pyIFBvw7Ny?=) Date: Tue, 22 Dec 2015 21:28:33 +0100 Subject: [Haskell-cafe] wiki account creation Message-ID: <5679B271.8040506@gmail.com> Hello, I would like to create a new wiki account. The automatic account creation has been disabled, and requests should be sent to domain at haskell.org. However, my email has been returned as undelivered. Could someone help with the account creation? Art?r From trebla at vex.net Tue Dec 22 20:57:14 2015 From: trebla at vex.net (Albert Y. C. Lai) Date: Tue, 22 Dec 2015 15:57:14 -0500 Subject: [Haskell-cafe] NoMonomorphismRestriction forces odd situation when using contexts In-Reply-To: References: Message-ID: <5679B92A.6090609@vex.net> On 2015-12-20 08:01 PM, Noon Silk wrote: > {-# LANGUAGE NoMonomorphismRestriction #-} > > data Status = Foo | Bar > > data Rec m a = Rec { > get :: m a > , status :: Status > } > > defRec :: (Monad m) => Rec m a > defRec = undefined > > myRec :: (Monad m) => Rec m a > myRec = Rec x y > where > Rec x y = defRec Why this is an ambiguous-type error is a really long story. But a factor is analogous to "show . read". Another factor is that since you turn off the monomorphism restriction, there is a type generalization step, and the generalizing of y's type is separate from the generalization of x's type. I have found this solution, it works by connecting types to suppress the generalize step: {-# LANGUAGE NoMonomorphismRestriction, ScopedTypeVariables #-} ... myRec :: forall m a. (Monad m) => Rec m a myRec = Rec x y where Rec x y = defRec :: Rec m a From noonslists at gmail.com Tue Dec 22 21:43:36 2015 From: noonslists at gmail.com (Noon Silk) Date: Wed, 23 Dec 2015 08:43:36 +1100 Subject: [Haskell-cafe] NoMonomorphismRestriction forces odd situation when using contexts In-Reply-To: <5679B92A.6090609@vex.net> References: <5679B92A.6090609@vex.net> Message-ID: Hi Albert, Thanks for your response (and sorry about my earlier email missing some content at the end; I rushed out to lunch as I was sending this). Your solution works fine. It's better than the option I've listed. On Wed, Dec 23, 2015 at 7:57 AM, Albert Y. C. Lai wrote: > On 2015-12-20 08:01 PM, Noon Silk wrote: > >> {-# LANGUAGE NoMonomorphismRestriction #-} >> >> data Status = Foo | Bar >> >> data Rec m a = Rec { >> get :: m a >> , status :: Status >> } >> >> defRec :: (Monad m) => Rec m a >> defRec = undefined >> >> myRec :: (Monad m) => Rec m a >> myRec = Rec x y >> where >> Rec x y = defRec >> > > Why this is an ambiguous-type error is a really long story. But a factor > is analogous to "show . read". Another factor is that since you turn off > the monomorphism restriction, there is a type generalization step, and the > generalizing of y's type is separate from the generalization of x's type. > > I have found this solution, it works by connecting types to suppress the > generalize step: > > {-# LANGUAGE NoMonomorphismRestriction, ScopedTypeVariables #-} > ... > myRec :: forall m a. (Monad m) => Rec m a > myRec = Rec x y > where > Rec x y = defRec :: Rec m a > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -- Noon Silk, ? https://sites.google.com/site/noonsilk/ "Every morning when I wake up, I experience an exquisite joy ? the joy of being this signature." -------------- next part -------------- An HTML attachment was scrubbed... URL: From rf at rufflewind.com Wed Dec 23 01:11:56 2015 From: rf at rufflewind.com (Phil Ruffwind) Date: Tue, 22 Dec 2015 20:11:56 -0500 Subject: [Haskell-cafe] NoMonomorphismRestriction forces odd situation when using contexts In-Reply-To: References: <5679B92A.6090609@vex.net> Message-ID: You can avoid this problem by using a case-expression, which remains monomorphic: myRec = case defRec of Rec x y -> Rec x y From wren at community.haskell.org Wed Dec 23 03:00:05 2015 From: wren at community.haskell.org (wren romano) Date: Tue, 22 Dec 2015 22:00:05 -0500 Subject: [Haskell-cafe] Preventing sharing In-Reply-To: <567988DC.2070406@durchholz.org> References: <20151222123156.GA1886@Magus.sf-private> <567988DC.2070406@durchholz.org> Message-ID: On Tue, Dec 22, 2015 at 12:31 PM, Joachim Durchholz wrote: > It seems to show how one can transform a specific class of lazy functions > into generators. > This seems to miss the point of laziness. Having lazy evaluation means that > when writing a function, you don't know (and don't care) how much of the > returned data structure is ever explored, that's the caller's decision. This > means you do not ever transform your code as a generator, because you don't > need to. To play the celestial advocate: the ability to not care about strictness/laziness when writing a function is precisely what causes it to be hard to reason about the space/time costs of that function. Yes, it's nice to be able to abstract over evaluation semantics, but that abstraction does not come for free. Where the balance between cost and benefit tilts is, imo, less important than realizing the nature of the tradeoff. For, there is no single optimum; the objective function for "good programming" must weight many different concerns, and those weights necessarily differ by context and goal. -- Live well, ~wren From gershomb at gmail.com Wed Dec 23 03:11:39 2015 From: gershomb at gmail.com (Gershom B) Date: Tue, 22 Dec 2015 22:11:39 -0500 Subject: [Haskell-cafe] wiki account creation In-Reply-To: <5679B271.8040506@gmail.com> References: <5679B271.8040506@gmail.com> Message-ID: Apologies for the confusion. The text reads: ? ? "wiki-account-request" (at the domain haskell dot org)? So the part in quotes is the part that precedes the at sign in the proper email address for account creation ? I?m sure this modest attempt to foil spambots doesn?t amount to much, but there you go. Cheers, Gershom On December 22, 2015 at 3:28:43 PM, Art?r Po?r (gombocarti at gmail.com) wrote: > Hello, > > I would like to create a new wiki account. The automatic account > creation has been disabled, and requests should be sent to > domain at haskell.org. However, my email has been returned as undelivered. > > Could someone help with the account creation? > > Art?r > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > From jo at durchholz.org Wed Dec 23 03:59:59 2015 From: jo at durchholz.org (Joachim Durchholz) Date: Wed, 23 Dec 2015 04:59:59 +0100 Subject: [Haskell-cafe] Preventing sharing In-Reply-To: References: <20151222123156.GA1886@Magus.sf-private> <567988DC.2070406@durchholz.org> Message-ID: <567A1C3F.6070307@durchholz.org> Am 23.12.2015 um 04:00 schrieb wren romano: > To play the celestial advocate: the ability to not care about > strictness/laziness when writing a function is precisely what causes > it to be hard to reason about the space/time costs of that function. Sure. I'm not disputing well-known facts, I'm just wondering that the paper highlights just the problems and does not put them into proportion to the advantages. From hon.lianhung at gmail.com Wed Dec 23 15:51:32 2015 From: hon.lianhung at gmail.com (Lian Hung Hon) Date: Wed, 23 Dec 2015 23:51:32 +0800 Subject: [Haskell-cafe] Installation instructions for ghc 7-10-3 on Windows Message-ID: Dear Haskellers, How can I install just ghc on Windows? Especially with regards to the network package? Before this I used minghc, but the github page says its now dead. Sincerely, Hon -------------- next part -------------- An HTML attachment was scrubbed... URL: From adam at bergmark.nl Wed Dec 23 15:54:21 2015 From: adam at bergmark.nl (Adam Bergmark) Date: Wed, 23 Dec 2015 16:54:21 +0100 Subject: [Haskell-cafe] Installation instructions for ghc 7-10-3 on Windows In-Reply-To: References: Message-ID: In short, use stack. Detailed here: http://neilmitchell.blogspot.nl/2015/12/minghc-is-dead-long-live-stack.html - Adam On Wed, Dec 23, 2015 at 4:51 PM, Lian Hung Hon wrote: > Dear Haskellers, > > How can I install just ghc on Windows? Especially with regards to the > network package? Before this I used minghc, but the github page says its > now dead. > > Sincerely, > Hon > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From hon.lianhung at gmail.com Wed Dec 23 16:06:23 2015 From: hon.lianhung at gmail.com (Lian Hung Hon) Date: Thu, 24 Dec 2015 00:06:23 +0800 Subject: [Haskell-cafe] Installation instructions for ghc 7-10-3 on Windows In-Reply-To: References: Message-ID: There is no way to use haskell on Windows without stack? On 23 Dec 2015 23:54, "Adam Bergmark" wrote: > In short, use stack. Detailed here: > http://neilmitchell.blogspot.nl/2015/12/minghc-is-dead-long-live-stack.html > > - Adam > > > On Wed, Dec 23, 2015 at 4:51 PM, Lian Hung Hon > wrote: > >> Dear Haskellers, >> >> How can I install just ghc on Windows? Especially with regards to the >> network package? Before this I used minghc, but the github page says its >> now dead. >> >> Sincerely, >> Hon >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mantkiew at gsd.uwaterloo.ca Wed Dec 23 16:22:59 2015 From: mantkiew at gsd.uwaterloo.ca (mantkiew at gsd.uwaterloo.ca) Date: Wed, 23 Dec 2015 11:22:59 -0500 Subject: [Haskell-cafe] Installation instructions for ghc 7-10-3 on Windows In-Reply-To: References: Message-ID: <20151223162259.5443663.51797.15011@gsd.uwaterloo.ca> There is. Just manually install MSYS2, ghc, and cabal. Set up the paths and that's it. Stack does all that for you.? ?Micha?? ? Original Message ? From: Lian Hung Hon Sent: Wednesday, December 23, 2015 11:06 AM To: Adam Bergmark Cc: haskell-cafe Subject: Re: [Haskell-cafe] Installation instructions for ghc 7-10-3 on Windows There is no way to use haskell on Windows without stack? On 23 Dec 2015 23:54, "Adam Bergmark" wrote: In short, use stack. Detailed here: http://neilmitchell.blogspot.nl/2015/12/minghc-is-dead-long-live-stack.html - Adam On Wed, Dec 23, 2015 at 4:51 PM, Lian Hung Hon wrote: Dear Haskellers, How can I install just ghc on Windows? Especially with regards to the network package? Before this I used minghc, but the github page says its now dead. Sincerely, Hon _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe at haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe From fr33domlover at riseup.net Wed Dec 23 22:13:34 2015 From: fr33domlover at riseup.net (fr33domlover) Date: Thu, 24 Dec 2015 00:13:34 +0200 Subject: [Haskell-cafe] Formatting strict Text Message-ID: Hello, I have code which uses Text.Printf.printf with String. Now I'm moving the code to use strict Text everywhere (I picked strict since all my strings are very short, mostly less than 400 chars). What should I use instead of printf now? One solution I found is the text-format package, which seems to simply split a Text on occurences of "{}" and insert values there. Are there other simple and efficient options? All I need is to append Text values and sometimes Ints too, so it's enough to have (1) efficient append and concat (2) A function that is :: Int -> Text Why is strict Text not a Monoid instance? And Builder has no `toStrictText` function? There is a function to convert Int to Builder and a Buildable instance for Int, but for a simple Int->Text it seems I'm left with an ugly `T.pack . show`. Suggestions / advice / comments on this? Thanks in advance :) fr33 -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 801 bytes Desc: not available URL: From adam at bergmark.nl Wed Dec 23 23:56:31 2015 From: adam at bergmark.nl (Adam Bergmark) Date: Thu, 24 Dec 2015 00:56:31 +0100 Subject: [Haskell-cafe] Formatting strict Text In-Reply-To: <20151223221135.5443DBCE6E@haskell.org> References: <20151223221135.5443DBCE6E@haskell.org> Message-ID: Data.Text definitely has a Monoid instance, it's defined in Data.Text. - Adam On Wed, Dec 23, 2015 at 11:13 PM, fr33domlover wrote: > Hello, > > I have code which uses Text.Printf.printf with String. Now I'm moving the > code > to use strict Text everywhere (I picked strict since all my strings are > very > short, mostly less than 400 chars). What should I use instead of printf > now? > > One solution I found is the text-format package, which seems to simply > split a > Text on occurences of "{}" and insert values there. Are there other simple > and > efficient options? All I need is to append Text values and sometimes Ints > too, > so it's enough to have > > (1) efficient append and concat > (2) A function that is :: Int -> Text > > Why is strict Text not a Monoid instance? And Builder has no `toStrictText` > function? There is a function to convert Int to Builder and a Buildable > instance for Int, but for a simple Int->Text it seems I'm left with an ugly > `T.pack . show`. > > > Suggestions / advice / comments on this? > > Thanks in advance :) > > fr33 > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From fr33domlover at riseup.net Thu Dec 24 00:13:05 2015 From: fr33domlover at riseup.net (fr33domlover) Date: Thu, 24 Dec 2015 02:13:05 +0200 Subject: [Haskell-cafe] Formatting strict Text In-Reply-To: References: <20151223221135.5443DBCE6E@haskell.org> Message-ID: On Thu, 24 Dec 2015 00:56:31 +0100 Adam Bergmark wrote: > Data.Text definitely has a Monoid instance, it's defined in Data.Text. > > - Adam > > Hmmm weird, it seems to have it indeed, but when I open the Hackage haddock pages for Data.Text it doesn't list the instances for the Text type. It does list then for any previus version of the 'text' package. Is that a haddock bug? -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 801 bytes Desc: not available URL: From fr33domlover at riseup.net Thu Dec 24 00:43:41 2015 From: fr33domlover at riseup.net (fr33domlover) Date: Thu, 24 Dec 2015 02:43:41 +0200 Subject: [Haskell-cafe] Formatting strict Text In-Reply-To: <20151223221133.9F32ABCCD8@haskell.org> References: <20151223221133.9F32ABCCD8@haskell.org> Message-ID: On Thu, 24 Dec 2015 00:13:34 +0200 fr33domlover wrote: > Hello, > > I have code which uses Text.Printf.printf with String. Now I'm moving the code > to use strict Text everywhere (I picked strict since all my strings are very > short, mostly less than 400 chars). What should I use instead of printf now? > > One solution I found is the text-format package, which seems to simply split a > Text on occurences of "{}" and insert values there. Are there other simple and > efficient options? All I need is to append Text values and sometimes Ints too, > so it's enough to have > > (1) efficient append and concat > (2) A function that is :: Int -> Text > > Why is strict Text not a Monoid instance? And Builder has no `toStrictText` > function? There is a function to convert Int to Builder and a Buildable > instance for Int, but for a simple Int->Text it seems I'm left with an ugly > `T.pack . show`. > > > Suggestions / advice / comments on this? > > Thanks in advance :) > > fr33 Since Text does have a Monoid instance after all, another question: The docs say 'append' is subject to fusion, but it isn't said about 'concat'. When I need to append several texts together, does it matter whether I just use <> between then or I 'concat' a list of them? Any one of them recommended / more efficient? I don't have any performance issues in my program, I just want to create good habits now and not get used to bad ones :P --fr33 -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 801 bytes Desc: not available URL: From gershomb at gmail.com Thu Dec 24 01:58:46 2015 From: gershomb at gmail.com (Gershom B) Date: Wed, 23 Dec 2015 20:58:46 -0500 Subject: [Haskell-cafe] Installation instructions for ghc 7-10-3 on Windows In-Reply-To: <20151223162259.5443663.51797.15011@gsd.uwaterloo.ca> References: <20151223162259.5443663.51797.15011@gsd.uwaterloo.ca> Message-ID: You can also just install the Haskell Platform on Windows. It works just fine! And it comes with a prebuilt network package too. These days, it also comes with MSYS2. However, it does not yet come with a ?path switcher? script as MinGHC did. So if you want to _reinstall_ network or the like, you need to first add the appropriate msys directories to your path for the duration of the build. These days, as far as I?m concerned, the only obstacle to using the platform on windows is if you _really_ don?t want any platform packages installed in your global package repo. And with the next release of the platform, that won?t be an issue either... Cheers, Gershom On December 23, 2015 at 11:23:09 AM, mantkiew at gsd.uwaterloo.ca (mantkiew at gsd.uwaterloo.ca) wrote: > There is. Just manually install MSYS2, ghc, and cabal. Set up the paths and that's it. > Stack does all that for you. > > ?Micha? > > Original Message > From: Lian Hung Hon > Sent: Wednesday, December 23, 2015 11:06 AM > To: Adam Bergmark > Cc: haskell-cafe > Subject: Re: [Haskell-cafe] Installation instructions for ghc 7-10-3 on Windows > > There is no way to use haskell on Windows without stack? > > On 23 Dec 2015 23:54, "Adam Bergmark" wrote: > In short, use stack. Detailed here: http://neilmitchell.blogspot.nl/2015/12/minghc-is-dead-long-live-stack.html > > - Adam > > > On Wed, Dec 23, 2015 at 4:51 PM, Lian Hung Hon wrote: > Dear Haskellers, > > How can I install just ghc on Windows? Especially with regards to the network package? > Before this I used minghc, but the github page says its now dead. > > Sincerely, > Hon > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Thu Dec 24 10:50:03 2015 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Thu, 24 Dec 2015 10:50:03 +0000 Subject: [Haskell-cafe] Preventing sharing In-Reply-To: <20151222122437.GA1845@Magus.sf-private> References: <20151221123348.GB21065@weber> <20151222122437.GA1845@Magus.sf-private> Message-ID: <20151224105003.GK23901@weber> On Tue, Dec 22, 2015 at 09:24:37PM +0900, Oleg wrote: > Once I mention the book I must point out Chap 23 of the book (near the > end). It should be the required read. The introduction to the section > contains the following emphasized statement (emphasized by the author, > Simon Peyton Jones): > > A major weakness of functional languages is the difficulty > of reasoning about their space and time behavior. Let me start by saying that I, too, am very skeptical of the value of lazy-evaluation-by-default. However, regardless of my support for your conclusion, I don't agree with your line of reasoning in this case. > Let us take a step back. The article on my web page noted the great > difficulty of writing AI search program in Haskell because the search > tree is evaluated lazily: whenever a node is evaluated, its result is > memoized for further use. That is precisely the wrong thing to do for > such problems. Again, this problem is precisely of lazy evaluation (as > defined in the book below).The obvious way to avoid memoization was > to introduce thunks -- which didn't work. The article then developed a > more involved solution. Yes, -no-full-laziness would have worked just > as well. However, the solution in the article works on the > case-by-case basis whereas -no-full-laziness affects the whole > compilation unit. It is for that reason that I pointed out the article > in this discussion. > > Let us turn to the problem of the "optimization" that we are > discussing. Does it have anything to do with laziness? Yes, it > does. Please see Chap 15 of the excellent book > > http://research.microsoft.com/en-us/um/people/simonpj/papers/slpj-book-1987/ > > which explains the full laziness. In order to demonstrate that the problem you are describing is unique to lazy-by-default languages, you need to explain why it does not occur in strict-by-default languages. The motivating example in the excellent book is that in the program f = g 4 g x y = y + (sqrt x) (f 1) + (f 2) the (sqrt 4) expression is evaluated twice. Thus the "full laziness transformation" (the name is misleading!) rewrites the program to (essentially) f = g 4 g x = let sqrtx = sqrt x in \y = y + sqrtx (f 1) + (f 2) To prove your point you now need to explain why 1. the full laziness transformation (again: misleading name!) is required in lazy-by-default languages 2. the full laziness transformation (don't be misled by the name) is not required in strict-by-default languages Personally I can't see why either 1 or 2 is true. Can you help me out? Or could you answer an essentially equivalent question? * If Haskell had never had the full laziness transformation (very misleading name!) you would not have seen the space leak in your iterative deepening implementation. We would have gained some predictability in space usage. But what would have been lost? My answer to the question is "we would have lost pretty much nothing". Anyone who wants the full laziness transformation (poor name) can implement it herself. What's your answer? Tom From hon.lianhung at gmail.com Thu Dec 24 13:28:57 2015 From: hon.lianhung at gmail.com (Lian Hung Hon) Date: Thu, 24 Dec 2015 21:28:57 +0800 Subject: [Haskell-cafe] Installation instructions for ghc 7-10-3 on Windows In-Reply-To: References: <20151223162259.5443663.51797.15011@gsd.uwaterloo.ca> Message-ID: Gee, thanks everyone for the feedback. Stack will do for now, I didn't realise I can run ghci from outside a project directory using stack exec ghci. The platform is quite large, and I'm on a costly metered network connection. Cheers, Hon On 24 Dec 2015 09:59, "Gershom B" wrote: > You can also just install the Haskell Platform on Windows. It works just > fine! And it comes with a prebuilt network package too. > > These days, it also comes with MSYS2. However, it does not yet come with a > ?path switcher? script as MinGHC did. So if you want to _reinstall_ network > or the like, you need to first add the appropriate msys directories to your > path for the duration of the build. > > These days, as far as I?m concerned, the only obstacle to using the > platform on windows is if you _really_ don?t want any platform packages > installed in your global package repo. And with the next release of the > platform, that won?t be an issue either... > > Cheers, > Gershom > > > On December 23, 2015 at 11:23:09 AM, mantkiew at gsd.uwaterloo.ca ( > mantkiew at gsd.uwaterloo.ca) wrote: > > There is. Just manually install MSYS2, ghc, and cabal. Set up the paths > and that's it. > > Stack does all that for you. > > > > ?Micha? > > > > Original Message > > From: Lian Hung Hon > > Sent: Wednesday, December 23, 2015 11:06 AM > > To: Adam Bergmark > > Cc: haskell-cafe > > Subject: Re: [Haskell-cafe] Installation instructions for ghc 7-10-3 on > Windows > > > > There is no way to use haskell on Windows without stack? > > > > On 23 Dec 2015 23:54, "Adam Bergmark" wrote: > > In short, use stack. Detailed here: > http://neilmitchell.blogspot.nl/2015/12/minghc-is-dead-long-live-stack.html > > > > - Adam > > > > > > On Wed, Dec 23, 2015 at 4:51 PM, Lian Hung Hon wrote: > > Dear Haskellers, > > > > How can I install just ghc on Windows? Especially with regards to the > network package? > > Before this I used minghc, but the github page says its now dead. > > > > Sincerely, > > Hon > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From artella.coding at googlemail.com Thu Dec 24 14:56:34 2015 From: artella.coding at googlemail.com (Artella Coding) Date: Thu, 24 Dec 2015 14:56:34 +0000 Subject: [Haskell-cafe] Installation instructions for ghc 7-10-3 on Windows In-Reply-To: References: Message-ID: Instructions to install with msys can be found here : https://wiki.haskell.org/Windows On Wed, Dec 23, 2015 at 4:06 PM, Lian Hung Hon wrote: > There is no way to use haskell on Windows without stack? > On 23 Dec 2015 23:54, "Adam Bergmark" wrote: > >> In short, use stack. Detailed here: >> http://neilmitchell.blogspot.nl/2015/12/minghc-is-dead-long-live-stack.html >> >> - Adam >> >> >> On Wed, Dec 23, 2015 at 4:51 PM, Lian Hung Hon >> wrote: >> >>> Dear Haskellers, >>> >>> How can I install just ghc on Windows? Especially with regards to the >>> network package? Before this I used minghc, but the github page says its >>> now dead. >>> >>> Sincerely, >>> Hon >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> >>> >> > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From manny at fpcomplete.com Thu Dec 24 15:10:53 2015 From: manny at fpcomplete.com (Emanuel Borsboom) Date: Thu, 24 Dec 2015 15:10:53 +0000 Subject: [Haskell-cafe] Installation instructions for ghc 7-10-3 on Windows In-Reply-To: References: <20151223162259.5443663.51797.15011@gsd.uwaterloo.ca> Message-ID: On Thu, Dec 24, 2015 at 5:29 AM Lian Hung Hon hon.lianhung at gmail.com wrote: Gee, thanks everyone for the feedback. Stack will do for now, I didn't > realise I can run ghci from outside a project directory using stack exec > ghci. The platform is quite large, and I'm on a costly metered network > connection. > You can also use ?plain? ghc/ghci by adding, e.g., %LOCALAPPDATA%\Programs\stack\i386-windows\ghc-7.10.3\bin to your PATH after running stack setup. ? -------------- next part -------------- An HTML attachment was scrubbed... URL: From mark.fine at gmail.com Thu Dec 24 21:07:37 2015 From: mark.fine at gmail.com (Mark Fine) Date: Thu, 24 Dec 2015 16:07:37 -0500 Subject: [Haskell-cafe] Formatting strict Text In-Reply-To: <20151223221135.20542BCE4F@haskell.org> References: <20151223221135.20542BCE4F@haskell.org> Message-ID: I've been using Formatting recently. Mark On Wed, Dec 23, 2015 at 5:13 PM, fr33domlover wrote: > Hello, > > I have code which uses Text.Printf.printf with String. Now I'm moving the > code > to use strict Text everywhere (I picked strict since all my strings are > very > short, mostly less than 400 chars). What should I use instead of printf > now? > > One solution I found is the text-format package, which seems to simply > split a > Text on occurences of "{}" and insert values there. Are there other simple > and > efficient options? All I need is to append Text values and sometimes Ints > too, > so it's enough to have > > (1) efficient append and concat > (2) A function that is :: Int -> Text > > Why is strict Text not a Monoid instance? And Builder has no `toStrictText` > function? There is a function to convert Int to Builder and a Buildable > instance for Int, but for a simple Int->Text it seems I'm left with an ugly > `T.pack . show`. > > > Suggestions / advice / comments on this? > > Thanks in advance :) > > fr33 > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From manny at fpcomplete.com Thu Dec 24 23:53:44 2015 From: manny at fpcomplete.com (Emanuel Borsboom) Date: Thu, 24 Dec 2015 23:53:44 +0000 Subject: [Haskell-cafe] ANN: stack-1.0.0 Message-ID: A Christmas present: we?re calling this version 1.0! This is a minor enhancement and bug fix release, but since Stackage LTS 4 is about to be cut we thought it was time to give Stack a version number that reflects its readiness for production use. Enhancements: - Added flag --profile flag: passed with stack build, it will enable profiling, and for --bench and --test it will generate a profiling report by passing +RTS -p to the executable(s). Great for using like stack build --bench --profile (remember that enabling profile will slow down your benchmarks by >4x). Run stack build --bench again to disable the profiling and get proper speeds - Added flag --trace flag: just like --profile, it enables profiling, but instead of generating a report for --bench and --test, prints out a stack trace on exception. Great for using like stack build --test --trace - Nix: all options can be overriden on command line #1483 - Nix: build environments (shells) are now pure by default. - Make verbosity silent by default in script interpreter mode #1472 - Show a message when resetting git commit fails #1453 - Improve Unicode handling in project/package names #1337 - Fix ambiguity between a stack command and a filename to execute (prefer stack subcommands) #1471 - Support multi line interpreter directive comments #1394 - Handle space separated pids in ghc-pkg dump (for GHC HEAD) #1509 - Add ghci ?no-package-hiding option #1517 - stack new can download templates from URL #1466 Bug fixes: - Nix: stack exec options are passed properly to the stack sub process #1538 - Nix: specifying a shell-file works in any current working directory #1547 - Nix: use --resolver argument - Docker: fix missing image message and ??docker-auto-pull? - No HTML escaping for ?stack new? template params #1475 - Set permissions for generated .ghci script #1480 - Restrict commands allowed in interpreter mode #1504 - stack ghci doesn?t see preprocessed files for executables #1347 - All test suites run even when only one is requested #1550 - Edge cases in broken templates give odd errors #1535 - Fix test coverage bug on windows ? -------------- next part -------------- An HTML attachment was scrubbed... URL: From aeroboy94 at gmail.com Fri Dec 25 12:54:20 2015 From: aeroboy94 at gmail.com (Arian van Putten) Date: Fri, 25 Dec 2015 13:54:20 +0100 Subject: [Haskell-cafe] ANN: stack-1.0.0 In-Reply-To: References: Message-ID: That is great news! I'm happy to see stack hit the 1.0 so soon Though it's totally symbolic, it gives Stack a really healthy appearance. All the best, merry christmas and a happy new year! Arian On Fri, Dec 25, 2015 at 12:53 AM, Emanuel Borsboom wrote: > A Christmas present: we?re calling this version 1.0! This is a minor > enhancement and bug fix release, but since Stackage LTS 4 is about to be > cut we thought it was time to give Stack a version number that reflects its > readiness for production use. > > Enhancements: > > - Added flag --profile flag: passed with stack build, it will enable > profiling, and for --bench and --test it will generate a profiling > report by passing +RTS -p to the executable(s). Great for using like stack > build --bench --profile (remember that enabling profile will slow down > your benchmarks by >4x). Run stack build --bench again to disable the > profiling and get proper speeds > - Added flag --trace flag: just like --profile, it enables profiling, > but instead of generating a report for --bench and --test, prints out > a stack trace on exception. Great for using like stack build --test > --trace > - Nix: all options can be overriden on command line #1483 > > - Nix: build environments (shells) are now pure by default. > - Make verbosity silent by default in script interpreter mode #1472 > > - Show a message when resetting git commit fails #1453 > > - Improve Unicode handling in project/package names #1337 > > - Fix ambiguity between a stack command and a filename to execute > (prefer stack subcommands) #1471 > > - Support multi line interpreter directive comments #1394 > > - Handle space separated pids in ghc-pkg dump (for GHC HEAD) #1509 > > - Add ghci ?no-package-hiding option #1517 > > - stack new can download templates from URL #1466 > > > Bug fixes: > > - Nix: stack exec options are passed properly to the stack sub process > #1538 > - Nix: specifying a shell-file works in any current working directory > #1547 > - Nix: use --resolver argument > - Docker: fix missing image message and ??docker-auto-pull? > - No HTML escaping for ?stack new? template params #1475 > > - Set permissions for generated .ghci script #1480 > > - Restrict commands allowed in interpreter mode #1504 > > - stack ghci doesn?t see preprocessed files for executables #1347 > > - All test suites run even when only one is requested #1550 > > - Edge cases in broken templates give odd errors #1535 > > - Fix test coverage bug on windows > > ? > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > -- Groetjes, Arian -------------- next part -------------- An HTML attachment was scrubbed... URL: From oleg at okmij.org Fri Dec 25 15:26:30 2015 From: oleg at okmij.org (Oleg) Date: Sat, 26 Dec 2015 00:26:30 +0900 Subject: [Haskell-cafe] Preventing sharing In-Reply-To: Message-ID: <20151225152630.GA2041@Magus.sf-private> Kim-Ee Yeoh wrote: > However, the record remains that Oleg has offered little by way of elegant > bolting. His lazy programs based on a strict language tend to be cluttered > with lazy and force functions that uglify previously elegant code. > > His arguments would persuade many more folks if, for instance, he could > offer lazy-over-strict translations of Doug McIlroy's power serious > one-liners with no loss in elegance: > > http://www.cs.dartmouth.edu/~doug/powser.html I wanted to write about ordinary and (inappropriately named, to some) full laziness and about how much elegance is in the eye of the beholder and difficult to evaluate, and about many other things. The quoted paragraph gave a much better topic: a concrete and easy to evaluate challenge: can we re-write Doug McIlroy's code in a strict language without ever using lazy and force or thunks everywhere -- basically maintaining the same structure of the code. I took the challenge and re-wrote the powser code in OCaml, a strict language. Haskell and OCaml differ in many respects, not just in the order of evaluation. OCaml is in general a little bit more verbose. Also, it does not have overloading. That's why you see not just + but also +. (for float addition) and +% (which I define for infinite series addition). Here are several examples: Haskell: series f = f : repeat 0 OCaml: let series f = I.cons f I.repeat 0. Things prefixed with I are library functions (just as repeat in Doug McIlroy's code is a library function). Haskell (using the tying-the-knot trick!) This is probably the most complex code (f:ft) / (g:gt) = qs where qs = f/g : series(1/g)*(ft-qs*gt) OCaml: let ( /% ) fs gs = let (f,ft) = I.decon fs and (g,gt) = I.decon gs in I.fix @@ I.cons (f /. g) (fun qs -> series (1. /. g) *% (ft -% qs *% gt)) Integration in Haskell: int fs = 0 : zipWith (/) fs [1..] and OCaml: let integ = I.cons 0. (fun fs -> I.zip_with (/.) fs (iota 1.)) Tangent as a polynomial in Haskell: tans = revert(int(1/(1:0:1))) and OCaml let tans = revert @@ integ (int 1 /% from_list [1.;0.;1.]) It seems the OCaml code (executed in the bytecode interpreter) is a bit faster than Haskell (in ghci). The complete code is available for inspection at http://okmij.org/ftp/ML/powser.ml There is no lazy/force in sight. Lazy/force could be used to implement the infinite stream data type (what has been prefixed with I) but no user of the stream library needs to know how exactly it is implemented. In particular, all McIlroy's code is written without any use of lazy/force. His code in OCaml has essentially the same structure as Haskell code, considering the syntactic differences between the two languages. The point is that well-chosen combinators are far more important than strict/lazy evaluation differences. If a language is expressive enough to support mini-languages (embedded DSLs), we can write infinite series and other DSL code without much trouble. Strict evaluation is not an obstacle to infinite data structures, on demand evaluation, etc. Once we can define a DSL, we can make it follow any evaluation strategy we want. Regarding the elegance, I can't help but quote a paragraph from Doug McIlroy's powser's page: Extensions to handle polynomials make a practical package, doubled in size, not as pretty, but much faster and capable of feats like pascal. To see the dramatic speedup, try a bigger test like take 20 tans. Note "not as pretty, but much faster". I'm afraid I'll have to significantly delay commenting on other points raised in this discussion: I have several deadlines coming up. From imz at altlinux.org Fri Dec 25 16:38:37 2015 From: imz at altlinux.org (Ivan Zakharyaschev) Date: Fri, 25 Dec 2015 19:38:37 +0300 (MSK) Subject: [Haskell-cafe] PATCHES: language-c minor fixes In-Reply-To: References: Message-ID: Hi, On Sun, 20 Dec 2015, Ivan Zakharyaschev wrote: > I've been interested in hacking language-c library a bit for my needs. (If it > turns out useful and successful, I'll tell about it.) > > And I've cloned the repo listed at > https://hackage.haskell.org/package/language-c-0.4.7 , namely: > http://code.haskell.org/language-c > > Apart from my special hacks, I've also fixed some typos and so on. I've pushed my minor fixes to the code of language-c to http://hub.darcs.net/imz/language-c_fixes and http://hub.darcs.net/imz/language-c_cleanup (which is a superset of the former). And will push more if I have more minor fixes. So, if someone is interested, please pull them. As for the problems with the conversion from darcs-1 to darcs-2, they were overcome with the help of darcs maintainers in the darcs-users mailing list, and now I do the changes in the darcs-1 clone of the repo pointed at by Hackage, covert to darcs-2 then, and push to hub.darcs.net. (http://hub.darcs.net/imz/language-c_hackage holds the result of the conversion of the upstream darcs-1 repo. visq's darcs-2 repo is 2 patches behind.) > But then I discovered that if I want to publish them on hub.darcs.net , I > need a darcs-2 repo, and the initial one which I used for cloning is a > darcs-1 repo. > > I could do the conversion to darcs-2, but I read that it is not reproducible: > run several times on the same set of patches it will give different results. > > As I've discovered also a language-c repo at hub.darcs.net which looks like > an upstream repo: http://hub.darcs.net/visq/language-c , I'm in doubt whether > I should continue making my patches against the darcs-1 repo which is said to > be upstream at hackage or against http://hub.darcs.net/visq/language-c > whichis not officially declared as the upstream but looks more fresh. > > ..if I want to be able to send some of my patches upstream. Best regards, Ivan From mwnx at gmx.com Sat Dec 26 21:32:39 2015 From: mwnx at gmx.com (mwnx) Date: Sat, 26 Dec 2015 22:32:39 +0100 Subject: [Haskell-cafe] [ANN] Flashy-Haskell: Advanced Haskell syntax for Vim Message-ID: <20151226213239.GA9873@debian> In case anyone is interested, I just published a syntax extension I use for vim. It adds on to the default "haskell.vim" syntax file and enables some more advanced colouring. Here's the link to the github page, with visual examples: https://github.com/mwnx/flashy-haskell I rewrote the whole thing before publishing so there might be quite a few bugs due to a lack of real world testing, but I'll strive to fix any reported bugs rapidly. It also doesn't seek to completely and perfectly interpret Haskell's syntax. As a result, some of the more unusual syntactic constructs might not benefit from the extra colouring. -- mwnx GPG: AEC9 554B 07BD F60D 75A3 AF6A 44E8 E4D4 0312 C726 From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Mon Dec 28 12:42:32 2015 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Mon, 28 Dec 2015 12:42:32 +0000 Subject: [Haskell-cafe] Preventing sharing In-Reply-To: <20151225152630.GA2041@Magus.sf-private> References: <20151225152630.GA2041@Magus.sf-private> Message-ID: <20151228124232.GU23901@weber> On Sat, Dec 26, 2015 at 12:26:30AM +0900, Oleg wrote: > Kim-Ee Yeoh wrote: > > However, the record remains that Oleg has offered little by way of elegant > > bolting. His lazy programs based on a strict language tend to be cluttered > > with lazy and force functions that uglify previously elegant code. > > > > His arguments would persuade many more folks if, for instance, he could > > offer lazy-over-strict translations of Doug McIlroy's power serious > > one-liners with no loss in elegance: > > > > http://www.cs.dartmouth.edu/~doug/powser.html > [...] > can we re-write Doug McIlroy's code in a strict language without ever > using lazy and force or thunks everywhere -- basically maintaining the > same structure of the code. > > I took the challenge and re-wrote the powser code in OCaml, a strict > language. [...] > There is no lazy/force in sight. Lazy/force could be used to implement > the infinite stream data type (what has been prefixed with I) but no > user of the stream library needs to know how exactly it is > implemented. In particular, all McIlroy's code is written without any > use of lazy/force. His code in OCaml has essentially the same > structure as Haskell code, considering the syntactic differences > between the two languages. [...] > The point is that well-chosen combinators are far more important than > strict/lazy evaluation differences. Thanks for that, Oleg. I am very much in agreement with you that we can have access to laziness within strict languages with no less elegance than we have access to IO in pure languages. Tom From dct25-561bs at mythic-beasts.com Tue Dec 29 09:55:07 2015 From: dct25-561bs at mythic-beasts.com (David Turner) Date: Tue, 29 Dec 2015 09:55:07 +0000 Subject: [Haskell-cafe] Make this code more idiomatic? Message-ID: Hi, I'd like to use the Control.Parallel.Strategies machinery to evaluate parts of a big record-based data structure in the background. The following code is the sort of thing that I've ended up with - it makes a spark that forces the actuals field of a user object, in the sense that it forces all of the elements to WHNF. (At least, that's what I hope it's doing!) updateActuals user = runEval $ do newActuals <- rparWith (evalTraversable rseq) $ calculateActuals user return user { actuals = newActuals } However, I'm concerned that runEval is marked as "for Strategy programmers" and that I should be using some collection of combinators instead of dropping down to this level. But I just can't work out how to combine the available combinators to do the same thing. In particular, all the articles I've found about this seem to end up adding `using` something to the end of one key line of code to achieve near-perfect parallelisation, but now that I come to do it myself I'm stuck! I think I'm looking for something like: updateActuals user = user { actuals = newActuals } `using` ... Can anyone help me fill in the blank there? Many thanks, David -------------- next part -------------- An HTML attachment was scrubbed... URL: From dct25-561bs at mythic-beasts.com Tue Dec 29 10:32:21 2015 From: dct25-561bs at mythic-beasts.com (David Turner) Date: Tue, 29 Dec 2015 10:32:21 +0000 Subject: [Haskell-cafe] Make this code more idiomatic? In-Reply-To: References: Message-ID: As soon as I sent this, I think I hit on the answer. There's no getting away from having to write a strategy like this: evalActualsWith :: Strategy [ActualShift] -> Strategy User evalActualsWith strat user = do actuals' <- strat $ actuals user return $ user { actuals = actuals' } But once I've written that it's a simple case of the following: parActuals :: Strategy User parActuals = evalActualsWith $ rparWith $ evalTraversable rseq updateActuals :: User -> User updateActuals user = users { actuals = newActuals } `using` parActuals where ... I think that's the same thing, right? Cheers, On 29 December 2015 at 09:55, David Turner wrote: > Hi, > > I'd like to use the Control.Parallel.Strategies machinery to evaluate > parts of a big record-based data structure in the background. The following > code is the sort of thing that I've ended up with - it makes a spark that > forces the actuals field of a user object, in the sense that it forces > all of the elements to WHNF. (At least, that's what I hope it's doing!) > > updateActuals user = runEval $ do > newActuals <- rparWith (evalTraversable rseq) > $ calculateActuals user > return user { actuals = newActuals } > > However, I'm concerned that runEval is marked as "for Strategy > programmers" and that I should be using some collection of combinators > instead of dropping down to this level. But I just can't work out how to > combine the available combinators to do the same thing. In particular, all > the articles I've found about this seem to end up adding `using` > something to the end of one key line of code to achieve near-perfect > parallelisation, but now that I come to do it myself I'm stuck! I think I'm > looking for something like: > > updateActuals user = user { actuals = newActuals } `using` ... > > Can anyone help me fill in the blank there? > > Many thanks, > > David > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From r.klomp at students.uu.nl Wed Dec 30 11:54:57 2015 From: r.klomp at students.uu.nl (Rick Klomp) Date: Wed, 30 Dec 2015 12:54:57 +0100 Subject: [Haskell-cafe] I need repositories that contain commited erroneous code Message-ID: Hi Haskell community, For my master thesis project I need change logs that I can use to derive what changes have been made to fix certain compilation errors. Unfortunately so for me, good repository etiquette is to never commit erroneous code. However, there are bound to be plenty of repos where this etiquette isn't/hasn't been followed (in non-main branches). My question to you is if you currently know or at some point in the near future (new data will be useful until somewhere early summer 2016) come to know of repos that fit the description, could you point me to them? Much appreciated! Or if you are willing to share a personal project with me (where obviously this repo etiquette is much less significant), then that would be immensely helpful to me! I promise to only use the metadata (but you'll have to believe me on my word). Thanks in advance for your help. Best regards, Rick Klomp -------------- next part -------------- An HTML attachment was scrubbed... URL: From alan.zimm at gmail.com Wed Dec 30 12:01:36 2015 From: alan.zimm at gmail.com (Alan & Kim Zimmerman) Date: Wed, 30 Dec 2015 14:01:36 +0200 Subject: [Haskell-cafe] I need repositories that contain commited erroneous code In-Reply-To: References: Message-ID: Perhaps look at Travis records for branches transitioning from failed build to fixed ones Alan On 30 Dec 2015 13:55, "Rick Klomp" wrote: > Hi Haskell community, > > For my master thesis project I need change logs that I can use to derive > what changes have been made to fix certain compilation errors. > > Unfortunately so for me, good repository etiquette is to never commit > erroneous code. However, there are bound to be plenty of repos where this > etiquette isn't/hasn't been followed (in non-main branches). > > My question to you is if you currently know or at some point in the near > future (new data will be useful until somewhere early summer 2016) come to > know of repos that fit the description, could you point me to them? Much > appreciated! > > Or if you are willing to share a personal project with me (where obviously > this repo etiquette is much less significant), then that would be immensely > helpful to me! I promise to only use the metadata (but you'll have to > believe me on my word). > > Thanks in advance for your help. > Best regards, > Rick Klomp > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From hjgtuyl at chello.nl Wed Dec 30 13:23:22 2015 From: hjgtuyl at chello.nl (Henk-Jan van Tuyl) Date: Wed, 30 Dec 2015 14:23:22 +0100 Subject: [Haskell-cafe] ANN: wxInstall Achelanne and wxHaskell 0.92.2.0 Message-ID: L.S., I am happy to announce a new version of wxHaskell: 0.92.2.0 and new installation packages for wxHaskell on Windows: wxInstall Achelanne 0.1 (32 bit and 64 bit) Changes in wxHaskell since 0.92.1: - Solved warnings for wxcore, wxdirect, wxc - Added support for Pickerctrl, Hyperlinkctrl and some Streams in wxc and wxcore - Solved several bugs - Added some image Functions in wxc and wxcore - Added enumerateFonts function in wxcore - Updated wxBITMAP_TYPE_ constants - Adapted to GHC 7.10.3 Thanks to everyone who contributed! wxInstall Achelanne[0] is created because GHC 7.10.3 for Windows is accompanied with a newer GCC: 5.2.0. A detailed description can be found at the wxHaskell-for-Windows homepage[1]. What is wxHaskell? ------------------ wxHaskell[2] is a portable and native GUI library for Haskell. The goal of the project is to provide an industrial strength GUI library for Haskell, but without the burden of developing (and maintaining) one ourselves. wxHaskell is therefore built on top of wxWidgets ? a comprehensive C++ library that is portable across all major GUI platforms; including GTK, Windows, X11, and MacOS X. Furthermore, it is a mature library (in development since 1992) that supports a wide range of widgets with the native look-and-feel. Links ----- See the homepage of wxHaskell for more information: https://wiki.haskell.org/WxHaskell The packages are: - wxc https://hackage.haskell.org/package/wxc - wxdirect https://hackage.haskell.org/package/wxdirect - wxcore https://hackage.haskell.org/package/wxcore - wx https://hackage.haskell.org/package/wx Regards, Henk-Jan van Tuyl [0] http://sourceforge.net/projects/wxhaskell/files/wxInstall/ [1] https://wiki.haskell.org/WxHaskell/Windows#Installing_the_easy_way [2] https://wiki.haskell.org/WxHaskell -- Folding at home What if you could share your unused computer power to help find a cure? In just 5 minutes you can join the world's biggest networked computer and get us closer sooner. Watch the video. http://folding.stanford.edu/ http://Van.Tuyl.eu/ http://members.chello.nl/hjgtuyl/tourdemonad.html Haskell programming -- From dct25-561bs at mythic-beasts.com Wed Dec 30 22:18:00 2015 From: dct25-561bs at mythic-beasts.com (David Turner) Date: Wed, 30 Dec 2015 22:18:00 +0000 Subject: [Haskell-cafe] Make this code more idiomatic? In-Reply-To: References: Message-ID: On 29 December 2015 at 10:32, David Turner wrote: > As soon as I sent this, I think I hit on the answer. There's no getting > away from having to write a strategy like this: > > evalActualsWith :: Strategy [ActualShift] -> Strategy User > evalActualsWith strat user = do > actuals' <- strat $ actuals user > return $ user { actuals = actuals' } > Hang on, isn't evalActualsWith just the lens for the actuals field with a slightly more specialised type? That's pretty cool. Cheers, David -------------- next part -------------- An HTML attachment was scrubbed... URL: From capn.freako at gmail.com Thu Dec 31 01:15:35 2015 From: capn.freako at gmail.com (David Banas) Date: Wed, 30 Dec 2015 17:15:35 -0800 Subject: [Haskell-cafe] Question on nested fmaps. Message-ID: Is this true, in general?: fmap h (fmap g f) == fmap (h . g) f Is there a simple proof? Thanks, -db -------------- next part -------------- An HTML attachment was scrubbed... URL: From adam at bergmark.nl Thu Dec 31 01:27:05 2015 From: adam at bergmark.nl (Adam Bergmark) Date: Thu, 31 Dec 2015 02:27:05 +0100 Subject: [Haskell-cafe] Question on nested fmaps. In-Reply-To: References: Message-ID: This is one of the functor laws, the other one being `fmap id = id'. If it doesn't hold your type *should* not have a Functor instance, but the compiler doesn't verify this for you. HTH, Adam On Thu, Dec 31, 2015 at 2:15 AM, David Banas wrote: > Is this true, in general?: > > fmap h (fmap g f) == fmap (h . g) f > > > Is there a simple proof? > > Thanks, > -db > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From amindfv at gmail.com Thu Dec 31 02:38:43 2015 From: amindfv at gmail.com (amindfv at gmail.com) Date: Wed, 30 Dec 2015 21:38:43 -0500 Subject: [Haskell-cafe] Naming inner elements Message-ID: I've looked all around but haven't found a nice syntax for this -- anyone have suggestions?: What I'd like to do is assign toplevel variable names to inner elements of a structure. Pseudocode for what I'd like to do is: things = [ foo@"thing1" , bar@"thing2" ] The major difference from just `foo = "thing1" ; things = [foo, ...` is that it's much more visually clear which values are in `things` (imagine I create a `baz` but forget to add it to `things`). The best I've found (which is not at all ideal) is to say e.g.: things@ [ foo , bar , baz ] = ["thing1", "thing2", "thing3"] But of course, for starters, I run off the page very quickly. I don't see anything in the usual places (e.g. the Haskell Report), but has anyone come across this and found an elegant solution? Thanks! Tom From peter.padawitz at udo.edu Thu Dec 31 03:03:02 2015 From: peter.padawitz at udo.edu (Peter Padawitz) Date: Thu, 31 Dec 2015 04:03:02 +0100 Subject: [Haskell-cafe] costate Message-ID: When is cobinding in the costate/funarg/incontext comonad (c -> a,c) (see papers by Kieburtz, Uustalu, Vene, Orchard, Mycroft, ?) preferable to (better-known) currying? f <<= (g,x) is equivalent to (curry f g,x) ! HNY, Peter -------------- next part -------------- An HTML attachment was scrubbed... URL: From targen at gmail.com Thu Dec 31 03:16:57 2015 From: targen at gmail.com (=?UTF-8?Q?Manuel_G=C3=B3mez?=) Date: Wed, 30 Dec 2015 22:46:57 -0430 Subject: [Haskell-cafe] Naming inner elements In-Reply-To: References: Message-ID: On Dec 30, 2015 10:05 PM, wrote: > The major difference from just `foo = "thing1" ; things = [foo, ...` is that it's much more visually clear which values are in `things` (imagine I create a `baz` but forget to add it to `things`). The best I've found is to use `where` profusely: ``` things = [ foo , bar , baz ] where foo = _ bar = _ baz = _ ``` If you forget to define `baz` but include it in the list, you get an error for a name not bound, and if you define it but forget to include it in the list, you get an error with `-Wall -Werror` for an unused binding. Now, if you want some of them at the top level, you do this ugly thing: ``` ( foo, bar, things ) = ( foo, bar, things ) where things = [ foo , bar , baz ] foo = _ bar = _ baz = _ ``` Just don't get the order wrong on the tuples for things with the same types. Welp! It's a bit less awful if you always want all the items in e. g. a list exported to the top level, as in your example, but this is a bit more general. It's still awful, but using tuples instead of list patterns allows you heterogeneous toplevel exports and more structures than just lists. You could also define a record: ``` {-# LANGUAGE RecordWildCards #-} data R = R { foo :: {- something -} , bar :: {- something else -} , things :: {- stuff -} } R {..} = R {..} where foo = _ bar = _ baz = _ things = [ foo , bar , baz ] ``` This costs you explicit type signatures in the record declaration, but `-Wall` would ask for those on toplevel bindings anyway. I don't think this could be solved easily with syntax; consider ``` things x = foo@(x, x + 1) ``` `foo` can't be made toplevel easily. -------------- next part -------------- An HTML attachment was scrubbed... URL: From roma at ro-che.info Thu Dec 31 08:13:11 2015 From: roma at ro-che.info (Roman Cheplyaka) Date: Thu, 31 Dec 2015 10:13:11 +0200 Subject: [Haskell-cafe] Question on nested fmaps. In-Reply-To: References: Message-ID: <5684E397.9010102@ro-che.info> This law implies from fmap id = id, see https://www.fpcomplete.com/user/edwardk/snippets/fmap On 12/31/2015 03:27 AM, Adam Bergmark wrote: > This is one of the functor laws, the other one being `fmap id = id'. If > it doesn't hold your type *should* not have a Functor instance, but the > compiler doesn't verify this for you. > > HTH, > Adam > > On Thu, Dec 31, 2015 at 2:15 AM, David Banas > wrote: > > Is this true, in general?: > > fmap h (fmap g f) == fmap (h . g) f > > > Is there a simple proof? > > Thanks, > -db > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: OpenPGP digital signature URL: