[Haskell-cafe] Missing Functor instances in GHC 7?

2010-12-09 Thread Sebastian Fischer
Hello, according to http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Monad.html Control.Monad exports 20 Functor instance declarations in base-4.3.0.0. However: bash# ghc-pkg list | grep base base-4.3.0.0 bash# ghci --version The Glorious Glasgow Haskell

Re: [Haskell-cafe] Missing Functor instances in GHC 7?

2010-12-09 Thread Sebastian Fischer
Hi Antoine, On Thu, 2010-12-09 at 23:20 -0600, Antoine Latter wrote: Are there any particular ones you're running into problems with? Yes, I cannot find the instance for ((-) r). Even if I import Control.Monad Control.Monad.Reader Control.Applicative Data.Functor

Re: [Haskell-cafe] Missing Functor instances in GHC 7?

2010-12-09 Thread Sebastian Fischer
On Fri, 2010-12-10 at 14:35 +0900, Sebastian Fischer wrote: Yes, I cannot find the Functor instance for ((-) r). As the Applicative instance for ((-) r) depends on the Functor instance I only needed to go through the imports of Control.Applicative to find that the Functor instance of ((-) r

Re: [Haskell-cafe] Missing Functor instances in GHC 7?

2010-12-10 Thread Sebastian Fischer
On Fri, 2010-12-10 at 08:33 +, Simon Peyton-Jones wrote: If there's a consensus that the behaviour is wrong, or at least unexpected, would you like to make a reproducible test case and file a ticket? I took Erik's mail as indicator that the behaviour of GHCi is inconsistent and

Re: [Haskell-cafe] Set monad

2011-01-08 Thread Sebastian Fischer
On Sun, Jan 9, 2011 at 6:53 AM, Lennart Augustsson lenn...@augustsson.netwrote: It so happens that you can make a set data type that is a Monad, but it's not exactly the best possible sets. module SetMonad where newtype Set a = Set { unSet :: [a] } Here is a version that also does not

Re: [Haskell-cafe] Set monad

2011-01-12 Thread Sebastian Fischer
On Sun, Jan 9, 2011 at 10:11 PM, Lennart Augustsson lenn...@augustsson.netwrote: That looks like it looses the efficiency of the underlying representation. Yes, I don't think one can retain that cleanly without using restricted monads to exclude things like liftM ($42) (mplus (return

Re: [Haskell-cafe] A question about monad laws

2011-01-18 Thread Sebastian Fischer
Hi Kashyap, Could someone please help me get a better understanding of the necessity of monads complying with these laws? Maybe it helps to write them in do-notation. Once written like this, it becomes clear(er?) that do-notation would be much less intuitive if the laws would not hold: Left

Re: [Haskell-cafe] Are constructors strict?

2011-01-21 Thread Sebastian Fischer
sorry, forgot to cc cafe. On Fri, Jan 21, 2011 at 7:12 PM, Sebastian Fischer fisc...@nii.ac.jpwrote: Hi Daryoush, On Fri, Jan 21, 2011 at 6:18 AM, Daryoush Mehrtash dmehrt...@gmail.comwrote: I am having hard time understanding the following paragraph in Purely functional Lazy non

Re: [Haskell-cafe] Are constructors strict?

2011-01-22 Thread Sebastian Fischer
Hi Daryoush, On Fri, Jan 21, 2011 at 7:52 PM, Daryoush Mehrtash dmehrt...@gmail.comwrote: loop = MonadPlus m = m Bool loop = loop If we apply Just to loop as follows test2 :: MonadPlus m = m (Maybe Bool) test2 = loop = return . Just the evaluation of test2 does not terminate

[Haskell-cafe] parsing exercise

2011-01-22 Thread Sebastian Fischer
Hello, I need a function and wonder whether I can copy some existing code so I don't have to write it myself. It should split a string into a list of strings: splitAtTopLevelCommas :: String - [String] I need something similar to `splitOn ,` from the Text package with the property

Re: [Haskell-cafe] parsing exercise

2011-01-23 Thread Sebastian Fischer
On Sun, Jan 23, 2011 at 4:31 PM, Chung-chieh Shan ccs...@post.harvard.eduwrote: Maybe Text.Show.Pretty.parseValue in the pretty-show package can help? That's what I was looking for, thanks! On Sun, Jan 23, 2011 at 5:23 PM, Stephen Tetley stephen.tet...@gmail.com wrote: I don't think you

Re: [Haskell-cafe] Code Golf

2009-04-20 Thread Sebastian Fischer
On Apr 18, 2009, at 2:48 AM, Sjoerd Visscher wrote: using Matt Hellige's pointless fun http://matt.immute.net/content/pointless-fun diag = foldr1 (zipWith (++) $. id ~ ([]:) ~ id) $. map (++ repeat []) ~ takeWhile (not.null) $. (map.map) (:[]) ~ concat pretty! Those seem to be

Re: [Haskell-cafe] traversing a tree using monad.cont

2009-05-07 Thread Sebastian Fischer
On Sun, May 3, 2009 at 2:40 PM, Ryan Ingram ryani.s...@gmail.com wrote: There's a great exposition of using something much like Cont to get success and failure for free here: http://www-ps.informatik.uni-kiel.de/~sebf/haskell/barefaced-pilferage-of-monadic-bind.lhs.html On May 4, 2009, at

Re: [Haskell-cafe] Visualizing Typed Functions

2009-05-07 Thread Sebastian Fischer
I've never really seen a satisfactory visual scheme for clearly representing higher order functions I saw a visual scheme for this purpose at FDPE'08. It uses an alternating colouring scheme, representing arguments as holes: a hole in a black thing is white and a hole in a white thing is

Re: [Haskell-cafe] generic filter through MonadPlus

2009-05-22 Thread Sebastian Fischer
On May 22, 2009, at 4:13 AM, Jason Dusek wrote: I'd like to know what folks think about the use of `MonadPlus` in this case. The |guard| function is almost |filter|: import Control.Monad ( MonadPlus, guard ) filter :: MonadPlus m = (a - Bool) - m a - m a filter p m = do a - m

[Haskell-cafe] Re: Purely logical programming language

2009-05-27 Thread Sebastian Fischer
On May 27, 2009, at 1:01 AM, Ahn, Ki Yung wrote: By the way, did Curry solved the problem of how to deal with IO and backtracking issues? (where and where not should IO happen kind of a thing) Curry uses the IO monad to specify where IO actions may happen. Non- determinism is not

Re: [Haskell-cafe] Bool as type class to serve EDSLs.

2009-06-01 Thread Sebastian Fischer
On Jun 1, 2009, at 12:17 AM, Henning Thielemann wrote: On Thu, 28 May 2009, Bulat Ziganshin wrote: i use another approach which imho is somewhat closer to interpretation of logical operations in dynamic languages (lua, ruby, perl): [...] The absence of such interpretations and thus the

Re: [Haskell-cafe] Bool as type class to serve EDSLs.

2009-06-01 Thread Sebastian Fischer
Do you argue that overloading logical operations like this in Haskell sacrifices type safety? Could programs go wrong [1] that use such abstractions? If I understand your point correctly, you are suggesting that such programs are still type safe. My asking was really meant as a question to

Re: [Haskell-cafe] containers dependency on base

2009-06-04 Thread Sebastian Fischer
On Jun 4, 2009, at 6:38 PM, Louis Wasserman wrote: I have been unable to compile the stable version of containers-0.2.0.1, having to add the constraint base=4.0.0.0. Can anybody else duplicate this problem? I could also not compile containers-0.2.0.1 and as a workaround added the

Re: [Haskell-cafe] ANNOUNCE: StrictBench 0.1 - Benchmarking code through strict evaluation

2009-06-08 Thread Sebastian Fischer
On Jun 8, 2009, at 2:56 PM, Martijn van Steenbergen wrote: Is there no way to force repeated evaluation of a pure value? I'm really curious about this too. could it be done by wrapping the computation in a function which is repeatedly called and compiling with -fno-full-laziness to

[Haskell-cafe] purely functional lazy non-deterministic programming

2009-06-08 Thread Sebastian Fischer
[crosspost from Haskell-libraries and Curry mailing list] Dear Haskell and Curry programmers, there is now a Haskell library that supports lazy functional-logic programming in Haskell. It is available from http://sebfisch.github.com/explicit-sharing and can be obtained from Hackage

[Haskell-cafe] Re: [Haskell] ANN: haskell-src-exts 1.0.0 rc1 (aka 0.5.2)

2009-06-17 Thread Sebastian Fischer
On Jun 17, 2009, at 12:43 AM, Niklas Broberg wrote: Testing it is really easy, four simple steps: cabal install haskell-src-exts [...] ghci [...] Prelude :m Language.Haskell.Exts Prelude Language.Haskell.Exts parseFile YourFileHere.(l)hs This script may even simplify testing of large

Re: [Haskell-cafe] Re: [Haskell] ANN: haskell-src-exts 1.0.0 rc1 (aka 0.5.2)

2009-06-17 Thread Sebastian Fischer
On Jun 17, 2009, at 1:00 PM, Niklas Broberg wrote: Thanks a lot, very useful! I'll add that to the darcs repository if you don't mind. :-) feel free! Here is a cleaned-up and updated version that can also read from stdin: #! /usr/bin/env runhaskell import Language.Haskell.Exts import

Re: [Haskell-cafe] ANNOUNCE fmlist

2009-06-18 Thread Sebastian Fischer
On Jun 18, 2009, at 9:57 AM, Sjoerd Visscher wrote: I am pleased to announce the first release of Data.FMList, lists represented by their foldMap function: [...] http://hackage.haskell.org/package/fmlist-0.1 cool! Just for fun: a derivation translating between different formulations of

Re: [Haskell-cafe] ANNOUNCE fmlist

2009-06-19 Thread Sebastian Fischer
On Jun 18, 2009, at 9:57 AM, Sjoerd Visscher wrote: This is my first package on Hackage, so any comments are welcome! It is not only pleasingly elegant but also quite useful: Your Monad and MonadPlus instances lead me to an interesting observation. Various strategies for non-deterministic

Re: [Haskell-cafe] Nested tests [Code walking off the right edge of the screen]

2009-06-21 Thread Sebastian Fischer
On Jun 21, 2009, at 11:52 AM, Andrew Coppin wrote: In a similar vein: d1x - doesDirectoryExist d1 if d1x then do f1x - doesFileExist (d1 / f1) if f1x then do d2x - doesDirectoryExist d2 if d2x then do f2x - doesFileExist (d2 / f2) if

Re: [Haskell-cafe] ANNOUNCE fmlist

2009-06-22 Thread Sebastian Fischer
On Jun 19, 2009, at 7:12 PM, Sjoerd Visscher wrote: I see you did performance tests. How does your current version compare to f.e. one based on DiffLists? The current versions (0.4) of bfs and idfs based on FMList (0.5) use the same amount of memory and are about 10-15% slower than

Re: [Haskell-cafe] Pattern matching does not work like this?

2009-07-16 Thread Sebastian Fischer
On Jul 15, 2009, at 2:30 PM, Hans Aberg wrote: If ++ could be pattern matched, what should have been the result of let (x++y)=[1,2,3] in (x,y)? It will branch. In terms of unification, you get a list of substitutions. f :: [a] - ([a],[a]) f (x ++ y) = (x,y) For an argument s, any pair

Re: [Haskell-cafe] powerSet = filterM (const [True, False]) ... is this obfuscated haskell?

2009-07-28 Thread Sebastian Fischer
The M is the list, i.e. nondeterminism monad. For each element in the list, there is one return value where it appears (True), and one where it does not (False). This discussion made Curry [1] programmers realise the beauty of non- determinism and lead to interesting reformulations of

Re: [Haskell-cafe] powerSet = filterM (const [True, False]) ... is this obfuscated haskell?

2009-07-28 Thread Sebastian Fischer
On Jul 28, 2009, at 11:06 AM, Sittampalam, Ganesh wrote: perms = sortByM (const [True,False]) This doesn't seem right, since the comparison function is inconsistent I was also wary about this point, e.g. QuickSort depends on transitivity. and moreover the results will depend on the

Re: [Haskell-cafe] Keeping an indexed collection of values?

2009-08-19 Thread Sebastian Fischer
On Aug 18, 2009, at 9:19 PM, Job Vranish wrote: data IndexedCollection a = IndexedCollection { nextKey:: Int, availableKeys :: [Int], items:: (IntMap Int a) } deriving (Show) emptyIndexedCollection :: IndexedCollection a emptyIndexedCollection =

Re: [Haskell-cafe] Re: Keeping an indexed collection of values?

2009-08-21 Thread Sebastian Fischer
On Aug 21, 2009, at 5:11 PM, Job Vranish wrote: I also added an extra phantom type parameter to the collection (and key) so that I can prevent keys from being used on different collections even if they hold elements of the same type. I have the impression that this requires explicit type

Re: [Haskell-cafe] Is there already an abstraction for this?

2008-09-22 Thread Sebastian Fischer
Hi Jeremy, There are some approaches that support such generic transformations. The simplest is probably Uniplate by Neil Mitchell: http://www-users.cs.york.ac.uk/~ndm/uniplate/ The function 'rewrite' is what you are looking for. If you change the definition of 'identity' to:

[Haskell-cafe] FunDeps vs. Associated Types

2008-12-05 Thread Sebastian Fischer
Dear Haskellers, I have a question regarding the correspondence between functional dependencies and associated types. {-# LANGUAGE TypeFamilies, FlexibleInstances, MultiParamTypeClasses, FunctionalDependencies #-} With associated types, we can

[Haskell-cafe] ANN: incremental-sat-solver

2009-01-28 Thread Sebastian Fischer
Simple, Incremental SAT Solving as a Library This Haskell library provides an implementation of the Davis-Putnam- Logemann-Loveland algorithm (cf. http://en.wikipedia.org/wiki/DPLL_algorithm ) for the boolean satisfiability problem. It not only

Re: [Haskell-cafe] ANN: incremental-sat-solver

2009-01-29 Thread Sebastian Fischer
Unlike 'sat' and 'sat-micro-hs' it is a library, and unlike 'libsat' it provides an interface for incremental solving. Funsat is also a library. By saying 'libsat' I actually meant 'funsat' ;) I have considered using it instead of writing 'incremental-sat-solver'. But after looking at

[Haskell-cafe] experience with SmallCheck

2009-01-30 Thread Sebastian Fischer
Today I played with SmallCheck. Interested in what happened when I tried to find a small unsatisfiable boolean formula that is not easily detected as such? Watch my attempts: http://www-ps.informatik.uni-kiel.de/~sebf/haskell/unsatisfiable-formula-that-needs-guessing-to-fail.lhs.html

Re: [Haskell-cafe] Natural Numbers: Best implementation?

2009-03-13 Thread Sebastian Fischer
Hi Mark, On Mar 13, 2009, at 3:54 AM, Mark Spezzano wrote: I was wondering what the best way to implement Natural number would be. Is there a package which already does this? there are two packages on Hackage that implement natural numbers using algebraic datatypes: 'numbers' has a module

Re: [Haskell-cafe] ANNOUNCE: vacuum-cairo: a cairo frontend to vacuum for live Haskell data visualization

2009-03-31 Thread Sebastian Fischer
On Mar 31, 2009, at 7:40 AM, Don Stewart wrote: I am pleased to announce the release of vacuum-cairo, a Haskell library for interactive rendering and display of values on the GHC heap using Matt Morrow's vacuum library. Awesome! I want to try this. I have problems though installing it on

Re: [Haskell-cafe] ANNOUNCE: vacuum-cairo: a cairo frontend to vacuum for live Haskell data visualization

2009-03-31 Thread Sebastian Fischer
On Mar 31, 2009, at 7:15 PM, Brandon S. Allbery KF8NH wrote: cabal: cannot configure vacuum-cairo-0.3.1. It requires svgcairo -any There is no available version of svgcairo that satisfies -any This is looking for the Haskell svgcairo package, in other words the Haskell binding for the

Re: [Haskell-cafe] ANNOUNCE: vacuum-cairo: a cairo frontend to vacuum for live Haskell data visualization

2009-04-01 Thread Sebastian Fischer
On Apr 1, 2009, at 4:02 AM, Brandon S. Allbery KF8NH wrote: Yes, if the libsvg-cairo library is found when you run configure for gtk2hs, it will be built. The version of libsvg-cairo that I have installed from MacPorts does not seem to work together with the native GTK+ framework for

[Haskell-cafe] Code Golf

2009-04-15 Thread Sebastian Fischer
Fancy some Codegolf? I wrote the following function for list diagonalization: diag l = foldr (.) id ((sel l . flip sel) ((:[]).(:))) [] where sel = foldr (\a b c - id : mrg (a c) (b c)) (const []) . map (flip id) mrg [] ys = ys mrg xs [] = xs mrg (x:xs) (y:ys)

Re: [Haskell-cafe] Code Golf

2009-04-15 Thread Sebastian Fischer
Prelude let diag = concat . diags where diags ((x:xs):xss) = [x] : zipWith (:) xs (diags xss) this has a different semantics on finite lists, so I should add a test case: *Main diag [[1,2,3],[4,5,6],[7,8,9]] [1,2,4,3,5,7,6,8,9] Your version yields [1,2,4,3,5,7]. Actually, there are a

Re: [Haskell-cafe] Code Golf

2009-04-15 Thread Sebastian Fischer
diag [[1,2,3],[4],[5,6,7]] What it should be? *Main diag [[1,2,3],[4],[5,6,7]] [1,2,4,3,5,6,7] it's basically just skipping holes: 1 2 3 4 5 6 7 ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] ANN: level-monad-0.3

2009-04-15 Thread Sebastian Fischer
I am pleased to announce version 0.3 of the package level-monad. This package implements breadth-first search directly as an instance of MonadPlus (without using an intermediate tree representation). In version 0.3 I have added a MonadPlus instance for iterative deepening inspired by

Re: [Haskell-cafe] Code Golf

2009-04-16 Thread Sebastian Fischer
ghci let diag = foldr (curry (prod mappend fst snd . uncurry (coprod mappend (splitAt 2) (splitAt 1 [] nice :) thanks to the comments of Martijn and Jan we can replace prod and coprod by liftA2 and fancy dots: let diag = foldr (curry (liftA2 mappend fst snd.uncurry (((flip.).

Re: [Haskell-cafe] Looking for the fastest Haskell primes algorithm

2009-04-16 Thread Sebastian Fischer
On Apr 15, 2009, at 5:27 PM, Adrian Neumann wrote: I've just uploaded a package with some functions I had lying around. http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Numbers This package seems to be missing the source file Data/Numbers/ Primes.hs so I couldn't compare it to

[Haskell-cafe] [Announce] primes

2009-04-16 Thread Sebastian Fischer
I am pleased to announce the package 'primes' that implements lazy wheel sieves for efficient, purely functional generation of prime numbers in Haskell. Following the current discussion about primes in Haskell, I packaged up an implementation inspired by the papers Lazy wheel sieves and

[Haskell-cafe] Re: [Announce] primes

2009-04-16 Thread Sebastian Fischer
I have just finished benchmarking all the implementations provided in http://www.cs.hmc.edu/~oneill/code/haskell-primes.zip (the zip file linked to from the Haskell wiki article on primes). NaurPrimes.hs is by far the fastest version, and at least 2 or 3 times faster than your current

Re: [Haskell-cafe] RE: [Announce] primes

2009-04-17 Thread Sebastian Fischer
Oh, I just remembered, I'm using ghci. I'll bet that's why I'm so slow. I also did, but after installing the package using cabal. IIRC, cabal compiles with -O2 by default. But if you downloaded the tarball and then loaded the module in ghci without installing it, this is probably the

Re: [Haskell-cafe] MonadPeelIO instance for monad transformers on top of forall

2011-02-04 Thread Sebastian Fischer
Hi Max, data M a = M { unM :: forall m. MonadPeelIO m = Reader.ReaderT () m a } It seems clear that there should be a MonadPeelIO instance for M, but I can't for the life of me figure it out. Have you (or the big brains on Haskell-Cafe, who are CCed) come across this before? Is there an

Re: [Haskell-cafe] Concurrency best practices?

2011-02-05 Thread Sebastian Fischer
Hi Wren, maybe Twilight STM is for you: http://hackage.haskell.org/package/twilight-stm Sebastian On Sat, Feb 5, 2011 at 6:46 PM, wren ng thornton w...@freegeek.org wrote: So I'm working on a project that uses STM to run a lot of things in parallel without the headaches of locks. So far it's

Re: [Haskell-cafe] Proving correctness

2011-02-11 Thread Sebastian Fischer
I've come across this a few times - In Haskell, once can prove the correctness of the code - Is this true? One way to prove the correctness of a program is to calculate it from its specification. If the specification is also a Haskell program, equational reasoning can be used to transform a

Re: [Haskell-cafe] upgrading mtl1 to mtl2

2011-02-16 Thread Sebastian Fischer
On Thu, Feb 17, 2011 at 11:32 AM, Evan Laforge qdun...@gmail.com wrote: Or will there just be massive signature rewriting in the wake of mtl2? I must admit I still don't understand your exact problem. Could you help me with an example where using mtl2 requires an additional (Functor m)

Re: [Haskell-cafe] upgrading mtl1 to mtl2

2011-02-17 Thread Sebastian Fischer
On Thu, Feb 17, 2011 at 4:57 PM, Max Bolingbroke batterseapo...@hotmail.com wrote: I think the problem is that the mtl1 Functor instances looked like: instance Monad m = Functor (ReaderT e m) where fmap = ... But the mtl2/transformers instances look like: instance Functor f = Functor

Re: [Haskell-cafe] Where to put a library

2011-03-02 Thread Sebastian Fischer
Hi Richard, On Thu, Mar 3, 2011 at 1:46 AM, Richard Senington sc06...@leeds.ac.ukwrote: The file parsers are designed to process files coming out of the TSPLIB and SATLIB repositories. [...] Since these are all related I was going to try to put them together into a single library and post

[Haskell-cafe] efficient parallel foldMap for lists/sequences

2011-04-01 Thread Sebastian Fischer
Hello Haskellers, in parallel programs it is a common pattern to accumulate a list of results in parallel using an associative operator. This can be seen as a simple form of the map-reduce pattern where each element of the list is mapped into a monoid before combining the results using `mconcat`.

Re: [Haskell-cafe] Programming Chalenges: The 3n+1 problem

2011-04-14 Thread Sebastian Fischer
Hi Dimitri, When asking how to implement cache in Haskell I was hopping that there exists some solution without using Data.Array, more functional approach, if I may say so  ... Steven's second solution is purely functional. It uses so-called tries to cache results instead of mutable arrays.

Re: [Haskell-cafe] Programming Chalenges: The 3n+1 problem

2011-04-15 Thread Sebastian Fischer
On Thu, Apr 14, 2011 at 8:02 PM, Luke Palmer lrpal...@gmail.com wrote: For this problem, it is too slow to memoize everything; you have to use a bounded memo table. That's why I use a combinator-based memo approach as opposed to the type-directed approach used in eg. MemoTrie. The memo table

Re: [Haskell-cafe] For Euler 25; What is the first term in the Fibonacci sequence to contain 1000 digits?; the following seems to work.

2011-05-19 Thread Sebastian Fischer
On Thu, May 19, 2011 at 7:29 PM, KC kc1...@gmail.com wrote: For Euler 25; What is the first term in the Fibonacci sequence to contain 1000 digits?; the following seems to work. -- For number of digits being 5 or more. fibNdigits :: Int - Int fibNdigits nDigits = floor (((fromIntegral

[Haskell-cafe] Student Internships for Parallel Haskell Programming at NII, Tokyo

2011-05-30 Thread Sebastian Fischer
As part of my research fellowship at the National Institute of Informatics in Tokyo, I announce the availability of student internships for up to three months between July and September 2011. Qualified applicants are enrolled in a Masters or Phd program, have a firm grasp of the Haskell

Re: [Haskell-cafe] Subcategories on Hackage

2011-06-04 Thread Sebastian Fischer
http://www.shirky.com/writings/ontology_overrated.html On Sat, Jun 4, 2011 at 10:02 AM, Tillmann Vogt tillmann.v...@rwth-aachen.de wrote: Hi, There are some categories on Hackage that have become so large that it is hard to find something, i.e. Data(414 packages) and Graphics (191). Thats

Re: [Haskell-cafe] For class Monoid; better names than mempty mappend might have been: mid (mident) mbinop

2011-07-24 Thread Sebastian Fischer
because list is a (the?) free monoid. Yes, all free monoids are isomorphic (to lists). Sebastian ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Properties for Foldable

2011-07-29 Thread Sebastian Fischer
 http://www.cs.ox.ac.uk/jeremy.gibbons/publications/iterator.pdf Interesting. However I don't understand why the instance in Section 5.5 is not already forbidden by the purity law traverse pure = pure and a 'no duplication' constraint would be necessary. For example: traverse Id

Re: [Haskell-cafe] Properties for Foldable

2011-07-29 Thread Sebastian Fischer
What am I missing? I suspect you missed the use of const Doh! I completely overlooked that it's about duplication of *effects*. Thanks, Sebastian ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] strictness properties of monoidal folds

2011-08-01 Thread Sebastian Fischer
Hello Cafe, left- and rightwards folds come in strict and lazy variants foldl/fold' and foldr/foldr' which makes sense because strict versions sometimes use less stack space while lazy versions support infinite data. For example, head (foldr (:) [] [1..]) returns in an instant while

Re: [Haskell-cafe] weird type signature in Arrow Notation

2011-08-04 Thread Sebastian Fischer
here is a reduced program that still segfaults: {-# LANGUAGE Arrows #-} import Control.Arrow main :: IO () main = print segfault segfault :: [()] segfault = anythingYouWant () anythingYouWant :: a anythingYouWant = testB False (const ()) () testB :: ArrowChoice arrow = bool - arrow ()

Re: [Haskell-cafe] weird type signature in Arrow Notation

2011-08-04 Thread Sebastian Fischer
I created a ticket with a slightly further simplified program: http://hackage.haskell.org/trac/ghc/ticket/5380 On Fri, Aug 5, 2011 at 10:10 AM, Sebastian Fischer fisc...@nii.ac.jpwrote: here is a reduced program that still segfaults: {-# LANGUAGE Arrows #-} import Control.Arrow main :: IO

Re: [Haskell-cafe] ANNOUNCE: yap-0.0 - yet another prelude

2011-08-11 Thread Sebastian Fischer
[switched to Cafe] On Wed, Aug 10, 2011 at 11:46 PM, Henning Thielemann lemm...@henning-thielemann.de wrote: On Wed, 10 Aug 2011, Paterson, Ross wrote: Yet another restructuring of the Prelude numeric classes on algebraic lines, proposed for a revision of the Haskell Prelude:

Re: [Haskell-cafe] Building ? using kleene closure {not haskell specific}

2011-08-12 Thread Sebastian Fischer
I can easily understand how + can be built but am having trouble with building ? (zero or one). If there is a regular expression e for the empty word, one can define ? as a? = e | a If there is a regular expression o that never matches one can define e as e = o* If there are

Re: [Haskell-cafe] strictness properties of monoidal folds

2011-08-14 Thread Sebastian Fischer
Hello Alexey, sorry for my slow response. On Thu, Aug 4, 2011 at 7:10 AM, Alexey Khudyakov alexey.sklad...@gmail.comwrote: On 02.08.2011 08:16, Sebastian Fischer wrote: Data.Foldable also provides the monoidal fold function foldMap. It is left unspecified whether the elements

Re: [Haskell-cafe] ANNOUNCE: TKYProf

2011-08-16 Thread Sebastian Fischer
I'm glad to announce the alpha release of TKYProf. This looks useful, thanks! I'll try it out and let you know if I have problems. Installing with GHC 7.2, I needed to relax some upper bounds in cabal files of dependencies (maintainers CC'ed). - email-validate and ranges specify base 4.4

Re: [Haskell-cafe] a minor bug (memory leak) in ListLike package

2011-08-23 Thread Sebastian Fischer
On Wed, Aug 24, 2011 at 10:47 AM, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote: On 24 August 2011 11:10, bob zhang bobzhang1...@gmail.com wrote: Hi, John, there is a space leak problem in ListLike typeclass, in the method genericLength calclen !accum cl = calclen accum cl = I

Re: [Haskell-cafe] a minor bug (memory leak) in ListLike package

2011-08-26 Thread Sebastian Fischer
On Wed, Aug 24, 2011 at 3:47 PM, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote: I was just trying to remember some of the tricks Daniel Peebles (aka {co}pumpkin) used to do in #haskell with Data.List.genericLength. I've never really used ListLike, but was just trying to guess why the

Re: [Haskell-cafe] Pointed, but not Applicative

2011-08-28 Thread Sebastian Fischer
On Sun, Aug 28, 2011 at 12:41 AM, Sönke Hahn sh...@cs.tu-berlin.de wrote: I was wondering which type could be an instance of Pointed, but not of Applicative. But I can't think of one. Any ideas? Functional lists: type FList a = [a] - [a] they have a Monoid instance for empty and append,

Re: [Haskell-cafe] Pointed, but not Applicative

2011-08-28 Thread Sebastian Fischer
On Mon, Aug 29, 2011 at 12:24 PM, Maciej Marcin Piechotka uzytkown...@gmail.com wrote: instance Functor FList where    f `fmap` FList g = ...? Yes, Functor is also one of the classes that can only be implemented by converting to ordinary lists (I think). So FList could only be made an

Re: [Haskell-cafe] Pointed, but not Applicative

2011-08-30 Thread Sebastian Fischer
On Wed, Aug 31, 2011 at 6:13 AM, Ryan Ingram ryani.s...@gmail.com wrote: technically it violates 'fmap id' == 'id' [...] If you add this FList law, though, you're OK: runFList fl as = runFList fl [] ++ as I think the idea of functional lists is that the monoids of 'lists' and 'functions on

Re: [Haskell-cafe] Pointed, but not Applicative

2011-08-30 Thread Sebastian Fischer
   toFList [] = id    toFList (xs++ys) = toFList xs . toFList ys    toList id = []    toList (f . g) = toList f ++ toList g These laws do not *define* the isomorphisms because their behavior on singletons is not fixed. Combining them with laws using a 'point' function for functional lists

Re: [Haskell-cafe] Smarter do notation

2011-09-04 Thread Sebastian Fischer
On Sun, Sep 4, 2011 at 11:34 AM, Daniel Peebles pumpkin...@gmail.com wrote: I was wondering what people thought of a smarter do notation. I'd support it (for both do notation and monad comprehensions) once Applicative is a superclass of Monad. To me it looks light a slight complication for an

Re: [Haskell-cafe] Smarter do notation

2011-09-04 Thread Sebastian Fischer
These are important questions. I think there is a trade-off between supporting many cases and having a simple desugaring. We should find a sweet-spot where the desugaring is reasonably simple and covers most idiomatic cases. So I guess it's possible to detect the pattern: do x1 - foo1; ...;

Re: [Haskell-cafe] Smarter do notation

2011-09-05 Thread Sebastian Fischer
Hi Max, thanks for you proposal! Using the Applicative methods to optimise do desugaring is still possible, it's just not that easy to have that weaken the generated constraint from Monad to Applicative since only degenerate programs like this one won't use a Monad method: Is this still

Re: [Haskell-cafe] Smarter do notation

2011-09-05 Thread Sebastian Fischer
, 2011 at 5:37 PM, Sebastian Fischer fisc...@nii.ac.jp wrote: Hi Max, thanks for you proposal! Using the Applicative methods to optimise do desugaring is still possible, it's just not that easy to have that weaken the generated constraint from Monad to Applicative since only degenerate programs

Re: [Haskell-cafe] Smarter do notation

2011-09-05 Thread Sebastian Fischer
On Mon, Sep 5, 2011 at 10:19 PM, Thomas Schilling nomin...@googlemail.comwrote: a = \p - f $ b -- 'free p' and 'free b' disjoint -- ((\p - f) $ a) * b Will there also be an optimisation for some sort of simple patterns? I.e., where we could rewrite this to: liftA2 (\pa pb - f ...) a

Re: [Haskell-cafe] extending and reusing cmdargs option specs ?

2011-09-12 Thread Sebastian Fischer
Hi Simon, while it is not possible to reuse the definitions of common fields themselves, their *descriptions* need to be given only once. Not sure if you are already sharing descriptions or if it helps you saving a few more lines. See

Re: [Haskell-cafe] extending and reusing cmdargs option specs ?

2011-09-13 Thread Sebastian Fischer
Hi Simon, On Tue, Sep 13, 2011 at 12:13 AM, Simon Michael si...@joyful.com wrote: Is that because of = auto ? I'm not sure. The feature was added in version 0.2 and is described in issue 333: http://code.google.com/p/ndmitchell/issues/detail?id=333 The description does not mention = auto.

Re: [Haskell-cafe] [Alternative] summary of my understanding so far

2011-12-18 Thread Sebastian Fischer
On Thu, Dec 15, 2011 at 9:13 AM, Gregory Crosswhite gcrosswh...@gmail.comwrote: To quote Ross Paterson's proposals: instance Alternative [] where ... some [] = [] some (x:xs) = repeat (repeat x) many [] = [[]] many (x:xs) = repeat (repeat x) Isn't this instance

Re: [Haskell-cafe] Reifying case expressions [was: Re: On stream processing, and a new release of timeplot coming]

2011-12-26 Thread Sebastian Fischer
On Sun, Dec 25, 2011 at 11:25 AM, Heinrich Apfelmus apfel...@quantentunnel.de wrote: Your StreamSummary type has a really nice interpretation: it's a reification of case expressions [on lists]. nice observation! For instance, consider the following simple function from lists to

Re: [Haskell-cafe] Reifying case expressions [was: Re: On stream processing, and a new release of timeplot coming]

2011-12-26 Thread Sebastian Fischer
2011/12/26 Eugene Kirpichov ekirpic...@gmail.com Whoa. Sebastian, you're my hero — I've been struggling with defining Arrow for ListTransformer for a substantial time without success, and here you got it, dramatically simpler than I thought it could be done (I was using explicit queues).

Re: [Haskell-cafe] Reifying case expressions [was: Re: On stream processing, and a new release of timeplot coming]

2011-12-27 Thread Sebastian Fischer
On Tue, Dec 27, 2011 at 5:35 AM, Eugene Kirpichov ekirpic...@gmail.comwrote: I wonder if now this datatype of yours is isomorphic to StreamSummary b r - StreamSummary a r. Not sure what you mean here. StreamSummary seems to be the same as ListConsumer but I don't see how functions from

[Haskell-cafe] space-efficient, composable list transformers [was: Re: Reifying case expressions [was: Re: On stream processing, and a new release of timeplot coming]]

2011-12-28 Thread Sebastian Fischer
Hello Heinrich, On Tue, Dec 27, 2011 at 1:09 PM, Heinrich Apfelmus apfel...@quantentunnel.de wrote: Sebastian Fischer wrote: all functions defined in terms of `ListTo` and `interpret` are spine strict - they return a result only after consuming all input list constructors. Indeed

Re: [Haskell-cafe] Avoiding parametric function binding

2012-01-01 Thread Sebastian Fischer
On Sat, Dec 31, 2011 at 4:09 PM, Kevin Quick qu...@sparq.org wrote: onVarElem :: forall a . (Show a) = (Maybe a - String) - Var - String onVarElem f (V1 x) = f x onVarElem f (V2 x) = f x main = putStrLn . onVarElem elemStr $ test This is probably a better design, but still fails for the

Re: [Haskell-cafe] Monads, do and strictness

2012-01-22 Thread Sebastian Fischer
On Sat, Jan 21, 2012 at 8:09 PM, David Barbour dmbarb...@gmail.com wrote: In any case, I think the monad identity concept messed up. The property:   return x = f = f x Logically only has meaning when `=` applies to values in the domain. `undefined` is not a value in the domain. We can

Re: [Haskell-cafe] Monads, do and strictness

2012-01-23 Thread Sebastian Fischer
On Sun, Jan 22, 2012 at 5:25 PM, David Barbour dmbarb...@gmail.com wrote: The laws for monads only apply to actual values and combinators of the monad algebra You seem to argue that, even in a lazy language like Haskell, equational laws should be considered only for values, as if they where

Re: [Haskell-cafe] Monad laws in presence of bottoms

2012-02-20 Thread Sebastian Fischer
On Mon, Feb 20, 2012 at 7:42 PM, Roman Cheplyaka r...@ro-che.info wrote: Is there any other interpretation in which the Reader monad obeys the laws? If selective strictness (the seq combinator) would exclude function types, the difference between undefined and \_ - undefined could not

[Haskell-cafe] [Snap] Argument Substitution in Heist Templates with Splices

2012-09-20 Thread Sebastian Fischer
Hello, the following program demonstrates that arguments in Heist templates are sometimes not substituted in presence of splices: {-# LANGUAGE OverloadedStrings #-} import Blaze.ByteString.Builder (toByteString) import qualified Data.ByteString.Char8as BS import

Re: [Haskell-cafe] [Snap] Argument Substitution in Heist Templates with Splices

2012-09-23 Thread Sebastian Fischer
tag. This avoids the infinite recursion and will work the way you want without needing stopRecursion. On Thu, Sep 20, 2012 at 3:00 PM, Sebastian Fischer m...@sebfisch.de wrote: Hello, the following program demonstrates that arguments in Heist templates are sometimes not substituted

Re: [Haskell-cafe] foldr (.) id

2012-10-29 Thread Sebastian Fischer
(.)/compose is consistent with (+)/sum, (*)/product, ()/and, etc. (to) compose is a verb. composition would be consistent with sum and product. and doesn't fit, though. Sebastian ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

<    1   2