Re: [Haskell-cafe] ANN: th-desugar simplifies Template Haskell processing

2013-08-31 Thread Sjoerd Visscher
Great package! One question: Do you remove/inline type synonyms? I ask because I just ran into this with some TH code. I'm looking for types that end with -> a, but that fails when type synonyms are involved. Sjoerd On Aug 30, 2013, at 2:08 AM, Richard Eisenberg wrote: > I've just uploaded m

Re: [Haskell-cafe] Constrained Category, Arrow, ArrowChoice, etc?

2013-05-10 Thread Sjoerd Visscher
On May 9, 2013, at 10:36 PM, Conal Elliott wrote: > BTW, have you see the new paper The constrained-monad problem? I want to > investigate whether its techniques can apply to Category & friends for linear > maps and for circuits. Perhaps you’d like to give it a try as well. I got to > linear m

Re: [Haskell-cafe] Constrained Category, Arrow, ArrowChoice, etc?

2013-05-09 Thread Sjoerd Visscher
Hi Conal, > I’ve cloned your gist and tried out an idea to simplify verifying the > required constraints on linear map values. > Lovely use of view patterns! It looks like it is not necessary to store the LM value, all that is needed is to store that VS2 s a b is satisfied. > Am I right in think

Re: [Haskell-cafe] Error compiling transformers-base-0.4.1 (debian 64 bits, ghc-7.4.2)

2013-05-09 Thread Sjoerd Visscher
There's a flag to turn it off, does that work? Try cabal install transformers-base -f-OrphanInstances Sjoerd On May 9, 2013, at 2:47 PM, jean-christophe mincke wrote: > Hello Café > > I am running into problems when installing transformers-base-0.4.1. > > Has anyone an idea about what is g

Re: [Haskell-cafe] Constrained Category, Arrow, ArrowChoice, etc?

2013-05-09 Thread Sjoerd Visscher
Hi Conal, I have a package data-category that should be able to do this. http://hackage.haskell.org/package/data-category I tried implementing your linear map, and this is the result: https://gist.github.com/sjoerdvisscher/5547235 I had to make some changes to your linear map data type, because

[Haskell-cafe] ANN: algebraic-classes, conversions between algebraic classes and F-algebras

2013-04-17 Thread Sjoerd Visscher
age/algebraic-classes And if you have suggestions, issues (the Template Haskell code is far from perfect at the moment) or pull-request, it is also on Github: https://github.com/sjoerdvisscher/algebraic-classes greetings, Sjoerd Visscher ___ Haskell-Cafe

Re: [Haskell-cafe] Sparse records/ADTs

2012-10-27 Thread Sjoerd Visscher
Maybe the vault package works for you? http://hackage.haskell.org/package/vault Sjoerd Visscher On Oct 26, 2012, at 5:17 PM, Jon Fairbairn wrote: > Twan van Laarhoven writes: > >> On 24/10/12 12:08, Jon Fairbairn wrote: >>> >>> Is there a convenient way of

Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-25 Thread Sjoerd Visscher
So, in order not to have to rely on rewrite rules, would it be a good idea to add unpackCString to the IsString class? import GHC.Base (unpackCString#, Addr#) class IsString a where fromString :: String -> a unpackCString :: Addr# -> a unpackCString addr = fromString (unpackCString#

[Haskell-cafe] ANNOUCE: one-liner-0, SYB-like generics with constraint kinds

2012-09-19 Thread Sjoerd Visscher
o learn more, you can find an introductory blog post here: https://github.com/sjoerdvisscher/blog/blob/master/2012/2012-09-06%20constraint-based%20generics.md Some complete examples are here: https://github.com/sjoerdvisscher/one-liner/tree/master/examples Some more generic functions, including generic

Re: [Haskell-cafe] Combining Network Descriptions in Reactive.Banana

2012-06-27 Thread Sjoerd Visscher
e? > >> library :: forall t. NetworkDescription t (Behavior t String) -> IO () > > Regards, > Alexander Foremny > > 2012/6/27 Sjoerd Visscher : >> This should work: >> >>library :: (forall t. NetworkDescription t (Behavior t [Char])) -> IO () >&

Re: [Haskell-cafe] Combining Network Descriptions in Reactive.Banana

2012-06-27 Thread Sjoerd Visscher
f this kind of program is possible with Reactive.Banana at > all. > > [1] https://gist.github.com/3004430 > > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskel

Re: [Haskell-cafe] cabal doens't forget old dependencies

2012-06-27 Thread Sjoerd Visscher
s > > So try "-f-UseExtensions" if you really want that? > > Cheers, > Andres > > > -- > Andres Löh, Haskell Consultant > Well-Typed LLP, http://www.well-typed.com > -- Sjoerd Visscher https://github.com/sjoerdvisscher/blog ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] cabal doens't forget old dependencies

2012-06-27 Thread Sjoerd Visscher
dependency of reactive-banana-0.6.0.0! How can I let cabal forget this dependency? Thanks, -- Sjoerd Visscher https://github.com/sjoerdvisscher/blog ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Have you seen this functor/contrafunctor combo?

2012-06-07 Thread Sjoerd Visscher
th (+) x x]) gives [[1,1,2,3,5,8…], [1,2,4,8,16,32,64…]], and mfix (\x -> [f x, g x, h x]) = [fix f, fix g, fix h]. For a list monad instance I would expect results with a mixture of f, g and h (but that would not be productive). Btw, you've asked this before and you got an interesting re

Re: [Haskell-cafe] Have you seen this functor/contrafunctor combo?

2012-06-06 Thread Sjoerd Visscher
x27; (pure (return a)) > Q' fs <*> Q' as = Q' $ \r -> do > rec > f <- fs (contramap ($ a) r) > a <- as (contramap (f $) r) > return $ f a [1] http://hackage.haskell.org/package/contravariant -- Sjoerd Visscher https://github.com/sjo

Re: [Haskell-cafe] library conflicts and how to resolve them

2012-05-06 Thread Sjoerd Visscher
ething ? Is there a way to force ghc to ignore this ?? > > Thanks > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Sjoerd Visscher https://github.com/sjoerdvisscher/blog __

Re: [Haskell-cafe] ANN: unfoldable-0.4.0

2012-04-28 Thread Sjoerd Visscher
On Apr 28, 2012, at 2:40 AM, wren ng thornton wrote: > On 4/26/12 3:52 PM, Roman Cheplyaka wrote: >> * Tillmann Rendel [2012-04-26 >> 21:34:21+0200] >>> Hi, >>> >>> Sjoerd Visscher wrote: >>>> Just as there's a Foldable class, t

Re: [Haskell-cafe] ANN: unfoldable-0.4.0

2012-04-26 Thread Sjoerd Visscher
checkers could use the same API, but there's a lot more to checking than that. By the way, I uploaded 0.5.0 a few hours ago, which contains a generic arbitrary implementation. greetings, -- Sjoerd Visscher https://github.com/sjoerdvisscher/blog ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] ANN: signed-multiset-0.1

2012-04-25 Thread Sjoerd Visscher
On Apr 26, 2012, at 12:54 AM, Stefan Holdermans wrote: > Sjoerd, > > I am sorry, as I already wrote, I decided to deprecate the package. That's too bad, I really love these kind of data structures. (That's why I keep ranting about it, sorry about that.) > >> [3] defines the union as h(u) = m

[Haskell-cafe] ANN: unfoldable-0.4.0

2012-04-25 Thread Sjoerd Visscher
I am pleased to announce the 5th version of the unfoldable package. (This is the first announcement, you didn't miss anything.) http://hackage.haskell.org/package/unfoldable-0.4.0 Just as there's a Foldable class, there should also be an Unfoldable class. This package provides one: class Unfo

Re: [Haskell-cafe] ANN: signed-multiset-0.1

2012-04-25 Thread Sjoerd Visscher
On Apr 25, 2012, at 11:39 AM, Stefan Holdermans wrote: > The union of two sets is typically defined as the smallest set that is a > superset of both the operands; this definition extends nicely for multisets > and hybrid sets [1,2,3]. [3] differs from [1] and [2] (and your implementation). [3]

Re: [Haskell-cafe] ANN: signed-multiset-0.1

2012-04-23 Thread Sjoerd Visscher
On Apr 23, 2012, at 7:04 PM, Stefan Holdermans wrote: > if this is what people have agreed on to be a sensible semantics for hybrid > sets, I am fine implementing it like this. I have a hard time believing you have implemented the semantics that people have agreed on to be a sensible semantics

Re: [Haskell-cafe] ANN: signed-multiset-0.1

2012-04-23 Thread Sjoerd Visscher
On Apr 23, 2012, at 4:34 PM, Stefan Holdermans wrote: > Sjoerd, > This is not just about map, but it also a problem for the Monoid instance. You are basically adding an extra identity element, 0, to the max monoid, which works but is weird. > >>> Still that's how union is typic

Re: [Haskell-cafe] ANN: signed-multiset-0.1

2012-04-23 Thread Sjoerd Visscher
On Apr 23, 2012, at 3:18 PM, Stefan Holdermans wrote: > Sjoerd, > >> This is not just about map, but it also a problem for the Monoid instance. >> You are basically adding an extra identity element, 0, to the max monoid, >> which works but is weird. > > Still that's how union is typically def

Re: [Haskell-cafe] ANN: signed-multiset-0.1

2012-04-23 Thread Sjoerd Visscher
This is not just about map, but it also a problem for the Monoid instance. You are basically adding an extra identity element, 0, to the max monoid, which works but is weird. You'll have to call norm everywhere to make it work, f.e. you would expect this to work: empty' = insert () $ delete ()

Re: [Haskell-cafe] ANN: signed-multiset-0.1

2012-04-23 Thread Sjoerd Visscher
; > Any groupoid on the multiplicities would do, I guess. > > As I wrote in my answer to Richard, max seems a better choise, as it nicely > generalises mapping on sets. > > Cheers, > > Stefan > ___ > Ha

Re: [Haskell-cafe] for = flip map

2012-03-29 Thread Sjoerd Visscher
issing something. >> >> ___ >> Haskell-Cafe mailing list >> Haskell-Cafe@haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe > > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Sjoerd Visscher https://github.com/sjoerdvisscher/blog ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] haskell platform - mac lion - installation error

2012-03-11 Thread Sjoerd Visscher
afe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Sjoerd Visscher https://github.com/sjoerdvisscher/blog ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Using multiplate to get free variables from a syntax tree

2012-02-26 Thread Sjoerd Visscher
a complicated subject! (Have you tried multirec?) Sjoerd On Feb 26, 2012, at 12:21 AM, Thomas Schilling wrote: > No that's correct. I have to say the multiplate code is incredibly > hard to decipher. > > On 25 February 2012 19:47, Sjoerd Visscher wrote: >

Re: [Haskell-cafe] Using multiplate to get free variables from a syntax tree

2012-02-25 Thread Sjoerd Visscher
. Is that not correct? Sjoerd On Feb 25, 2012, at 7:15 PM, Thomas Schilling wrote: > That will give you the wrong answer for an expression like: > > (let x = 1 in x + y) + x > > Unless you do a renaming pass first, you will end up both with a bound > "x" and a free &

Re: [Haskell-cafe] Using multiplate to get free variables from a syntax tree

2012-02-25 Thread Sjoerd Visscher
) . foldFor expr freeVariablesPlate >>> freeVars $ Let ("x" := Con 42) (Add (EVar "x") (EVar "y")) ["y"] -- Sjoerd Visscher https://github.com/sjoerdvisscher/blog ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] German names for kinds and sorts

2011-11-13 Thread Sjoerd Visscher
What a nice idea! Here's a list: http://www.biblestudytools.com/genesis/1-24-compare.html The German word is indeed Art, the French word is espèce. Sjoerd On Nov 13, 2011, at 9:31 PM, Paul Johnson wrote: > An odd suggestion I know, but take a look at some bibles. The King James > Bible uses

Re: [Haskell-cafe] New rss maintainer

2011-10-22 Thread Sjoerd Visscher
; _______ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Sjoerd Visscher http://w3future.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] The maximum/minimum asymmetry

2011-09-05 Thread Sjoerd Visscher
This way these laws hold for non-empty lists: maximumBy f xs = last (sortBy f xs) minimumBy f xs = head (sortBy f xs) Sjoerd Visscher On Sep 5, 2011, at 6:44 AM, Mario Blažević wrote: >I was recently surprised to discover that the maximum and maximumBy > functions always return the

Re: [Haskell-cafe] Monad for binary tree data structure

2011-07-23 Thread Sjoerd Visscher
t;= f) `mappend` lb) (rb `mappend` (r >>= f)) Let's see if this indeed behaves like the list monad. fromList :: [a] -> Tree a fromList [] = Empty fromList xs = Node a (fromList l) (fromList r) where (l, a:r) = splitAt (length xs `div` 2) xs > toList $ fromList [10,20

Re: [Haskell-cafe] Inconsistent trailing comma in export list and record syntax

2011-07-11 Thread Sjoerd Visscher
? Now you can no longer comment out the first line. -- Sjoerd Visscher ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Proof in Haskell

2010-12-23 Thread Sjoerd Visscher
= x? -- Sjoerd Visscher ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Serialization of (a -> b) and IO a

2010-11-11 Thread Sjoerd Visscher
do that. Being able to serialize functions is just as dangerous as having unsafePerformIO. If you don't use it, you don't have problems. -- Sjoerd Visscher http://w3future.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Serialization of (a -> b) and IO a

2010-11-11 Thread Sjoerd Visscher
On Nov 11, 2010, at 3:36 PM, Dan Doel wrote: > On Thursday 11 November 2010 6:22:06 am Sjoerd Visscher wrote: > >> The reasoning above is used regularly to shoot down some really useful >> functionality. So what would go wrong if we chose to take the practical >> p

Re: [Haskell-cafe] Serialization of (a -> b) and IO a

2010-11-11 Thread Sjoerd Visscher
tationally equal if the type is (Float -> Float), or the speed or memory use might be different. Could it not be that requiring them to be equal could just as well break things? greetings, Sjoerd Visscher ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Am I using type families well?

2010-11-01 Thread Sjoerd Visscher
s > -- -- -- Other cases yet to come... > > > > Well, there is no way I can get it type-check. I think I must be misusing the > type families (I tried with multi-param typeclasses and functional > dependencies, but it ends up to be the same kind of nightmare...). > _

Re: [Haskell-cafe] Scrap your rolls/unrolls

2010-10-23 Thread Sjoerd Visscher
Oct 23, 2010, at 6:07 PM, Max Bolingbroke wrote: > On 23 October 2010 15:32, Sjoerd Visscher wrote: >> A little prettier (the cata detour wasn't needed after all): >> >> data IdThunk a >> type instance Force (IdThunk a) = a > > Yes, this IdThunk is key -

Re: [Haskell-cafe] Scrap your rolls/unrolls

2010-10-23 Thread Sjoerd Visscher
Alg (ListF Int) Int sumAlg Nil = 0 sumAlg (Cons a r) = a + r sumList :: List Int -> Int sumList = fold sumAlg It all works out very well, so this trick seems to be really useful! Sjoerd On Oct 23, 2010, at 4:05 PM, Sjoerd Visscher wrote: > > On Oct 23, 2010, at 1:2

Re: [Haskell-cafe] Scrap your rolls/unrolls

2010-10-23 Thread Sjoerd Visscher
ely the IdThunk does not get in the way when defining algebras: sumAlg :: ListF Int (IdThunk Int) -> Int sumAlg Nil = 0 sumAlg (Cons a r) = a + r greetings, Sjoerd Visscher ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Tree Construction

2010-09-25 Thread Sjoerd Visscher
oc/html/Language-ImProve-Tree.html > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Sjoerd Visscher http://w3future.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Re: Re: Re: Full strict functor by abusing Haskell exceptions

2010-09-18 Thread Sjoerd Visscher
On Sep 17, 2010, at 10:39 PM, Ben Franksen wrote: > What I actually wanted was a mathematical definition, though. Here's a definition of pointed objects: http://ncatlab.org/nlab/show/pointed+object -- Sjoerd Visscher sjo...@w3future.com ___

Re: [Haskell-cafe] Re: Full strict functor by abusing Haskell exceptions

2010-09-16 Thread Sjoerd Visscher
tHask f) = f And indeed we have StrictIncl % (f . g) = StrictIncl % f . StrictIncl % g But StrictIncl can't be a pointed functor, only endofunctors can be pointed. -- Sjoerd Visscher http://w3future.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Re: Equality constraints and RankNTypes - how do I assist type inference

2010-08-21 Thread Sjoerd Visscher
. And is there any way to fix it? > > > _______ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Sjoerd Visscher http://w3future.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Re: ANN: weighted-regexp-0.1.0.0

2010-07-27 Thread Sjoerd Visscher
On Jul 27, 2010, at 7:09 AM, Sebastian Fischer wrote: > I'll add > >noMatch :: RegExp c >noMatch = psym "[]" (const False) Oh, by the way, with noMatch, eps, alt and seq_ RegExp is itself a Semiring, but I'm not sure what that would do. -- Sjo

Re: [Haskell-cafe] Re: ANN: weighted-regexp-0.1.0.0

2010-07-27 Thread Sjoerd Visscher
ne all alternatives that start with the same regexp. Yes, this was what I had at first too, but trying to match this on 8 items takes 2 seconds and 9 items already takes one minute. -- Sjoerd Visscher http://w3future.com ___ Haskell-Cafe mailing list

[Haskell-cafe] Re: ANN: weighted-regexp-0.1.0.0

2010-07-26 Thread Sjoerd Visscher
Hi Sebastian, I enjoyed this paper very much. Writing papers in the style of a play seems to work very well! (although I think you should spice it up more if your want to get it on Broadway) It seems that only shift needs the reg field of the RegW datatype. So you can also replace the reg fiel

Re: [Haskell-cafe] Data types a la carte

2010-07-21 Thread Sjoerd Visscher
to perform some automatic lifting so that app will work > for any combination of ApplicativeF? Can I use Functor class > or should I define my own type-class for this purpose? Is it > possible at all? Yes, it is possible, see the section "automating injections" in t

Re: [Haskell-cafe] More experiments with ATs

2010-07-04 Thread Sjoerd Visscher
> * -> * where BS :: BSFunctor Word8 Word8 instance RFunctor BSFunctor where type F BSFunctor Word8 = B.ByteString BS % f = B.map f -- Sjoerd Visscher ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] More experiments with ATs

2010-07-04 Thread Sjoerd Visscher
lightening names. As functors map both types and functions, the following may be more readable, with TMap mapping types, and fmap mapping functions: > type family TMap f a :: * > class RFunctor f where > fmap :: f a b -> (a -> b) -> f

Re: [Haskell-cafe] More experiments with ATs

2010-07-03 Thread Sjoerd Visscher
sition requires UndecidableInstances, because of the nested type family application. Perhaps one day GHC will be able to tell that this is structural recursion, and therefore not undecidable. This is a variation on what I'm doing in data-category 0.2, which is not done yet, but you can take a look here: http://github.com/sjoerdvisscher/data-category/ greetings, Sjoerd Visscher ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] The mother of all functors/monads/categories

2010-06-27 Thread Sjoerd Visscher
Applicative (Thingy i) where pure x = Thingy $ fmap ($ x) mf <*> mx = Thingy $ runThingy mx . runThingy mf . fmap (.) Not allowing Functor i and adding Yoneda also works. On Jun 27, 2010, at 1:43 PM, Sjoerd Visscher wrote: > Hi Max, > > This is really interesting! > >

Re: [Haskell-cafe] The mother of all functors/monads/categories

2010-06-27 Thread Sjoerd Visscher
class constraints at all is a good requirement. It only makes things more complicated, without providing more insights. I'd say that if class X requires a superclass constraint Y, then the instance of X (D d) is allowed to have the constraint Y d. The above code then stays the same, only with Yoneda removed and constraints added. greetings, -- Sjoerd Visscher http://w3future.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Programming with categories

2010-03-30 Thread Sjoerd Visscher
; > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > _______ > Haskell-C

Re: [Haskell-cafe] Re: ANN: data-category, restricted categories

2010-03-22 Thread Sjoerd Visscher
tegory-extras? > > Regards > > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Sjoerd Visscher http://w3future.com ___

[Haskell-cafe] ANN: data-category, restricted categories

2010-03-22 Thread Sjoerd Visscher
b.com/sjoerdvisscher/data-category greetings, Sjoerd Visscher ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Restricted categories

2010-02-21 Thread Sjoerd Visscher
Ok, I've got product categories working: > {-# LANGUAGE TypeOperators, TypeFamilies, MultiParamTypeClasses, > ScopedTypeVariables, FlexibleContexts, FlexibleInstances, GADTs, RankNTypes, > UndecidableInstances #-} > import Prelude hiding ((.), id, fst, snd) > import qualified Prelude Suitable2

[Haskell-cafe] Restricted categories

2010-02-20 Thread Sjoerd Visscher
Hi all, I want restricted categories, just like the rmonad package provides restricted monads. The ultimate goal is to have a product category: http://en.wikipedia.org/wiki/Product_category > {-# LANGUAGE TypeOperators, TypeFamilies, MultiParamTypeClasses, > FlexibleInstances, FlexibleContexts

Re: [Haskell-cafe] Control.Parallel missing

2009-12-28 Thread Sjoerd Visscher
pile out of the box. Maybe we could > extend this 4th step also with an introduction to Cabal? > > > Mitar > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Sj

Re: [Haskell-cafe] Problem with cabal install zlib

2009-12-20 Thread Sjoerd Visscher
l-m32 ${1+"$@"} "$Iflag" greetings, Sjoerd Visscher On Dec 20, 2009, at 1:31 AM, Duncan Coutts wrote: > On Sat, 2009-12-19 at 09:39 +, Ozgur Akgun wrote: > >> I guess the following part is the problematic part: (But I've no idea >> how to resolv

Re: [Fwd: Re: [Haskell-cafe] Implicit newtype unwrapping]

2009-12-03 Thread Sjoerd Visscher
pping even). Sjoerd On Dec 3, 2009, at 11:47 AM, Holger Siegel wrote: > Am Donnerstag, den 03.12.2009, 01:40 +0100 schrieb Sjoerd Visscher: >> The idea is that there's just enough unwrapping such that you don't >> need to use getDual and appEndo. > > Yes, but what

Re: [Haskell-cafe] Implicit newtype unwrapping

2009-12-03 Thread Sjoerd Visscher
achim-breitner.de | http://www.joachim-breitner.de/ > Debian Developer: nome...@debian.org > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Sjoerd Visscher sjo...@w3future.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Fwd: Re: [Haskell-cafe] Implicit newtype unwrapping]

2009-12-02 Thread Sjoerd Visscher
; > 2) > instance Monoid (Endo a) > instance Monoid b => Monoid (a -> b) > > > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Sjoerd Visscher sjo...@w3future.com

Re: [Haskell-cafe] Re: inversion lists

2009-12-01 Thread Sjoerd Visscher
ink that would clean things up a bit. Keep on going, there's lots of fun ahead! greetings, Sjoerd -- Sjoerd Visscher sjo...@w3future.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Names for properties of operators

2009-11-08 Thread Sjoerd Visscher
and c. There are also symmetrically-typed examples of these operators, but the Set operations are easy and familiar. Thanks, Neil. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-c

Re: [Haskell-cafe] Fair diagonals (code golf)

2009-11-04 Thread Sjoerd Visscher
erge xs [] = xs merge (x:xs) (y:ys) = (x++y) : merge xs ys But my feeling is that this can still be simplified further. Or at least refactored so it is clear what actually is going on! -- Sjoerd Visscher sjo...@w3future.com ___ Haskell-Cafe mail

Re: [Haskell-cafe] Fair diagonals

2009-11-04 Thread Sjoerd Visscher
mport Control.Monad.Levels import Data.FMList (fromList) diagN = bfs . mapM fromList -- Sjoerd Visscher sjo...@w3future.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Fair diagonals

2009-11-04 Thread Sjoerd Visscher
is). * The implementation shows regularity and elegance. Many thanks, Martijn. [1] http://hpaste.org/fastcgi/hpaste.fcgi/view?id=11515 ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://w

Re: [Haskell-cafe] Re: Simple FAST lazy functional primes

2009-11-02 Thread Sjoerd Visscher
On Nov 2, 2009, at 5:11 PM, Will Ness wrote: Sjoerd Visscher w3future.com> writes: Excuse me, 2 doesn't have to be in the list of smaller primes, as we're only generating odd numbers: primes = 2 : 3 : 5 : 7 : sieve [3] (drop 2 primes) sieve qs@(q:_) (p:ps) = [x | x<

Re: [Haskell-cafe] Simple FAST lazy functional primes

2009-11-02 Thread Sjoerd Visscher
On Nov 2, 2009, at 2:07 PM, Sjoerd Visscher wrote: You can remove the "take k" step by passing along the list of primes smaller than p instead of k: primes = 2 : 3 : 5 : 7 : sieve [3, 2] (drop 2 primes) sieve qs@(q:_) (p:ps) = [x | x<-[q*q+2,q*q+4..p*p-2], and [(x`rem`p)/=

Re: [Haskell-cafe] Simple FAST lazy functional primes

2009-11-02 Thread Sjoerd Visscher
f. So I take it to disprove the central premise of the article, and to show that simple lazy functional FAST primes code does in fact exist, and that the PQ optimization - which value of course no-one can dispute - is a far-end optimization. ____

Re: [Haskell-cafe] What *is* a DSL?

2009-10-12 Thread Sjoerd Visscher
ntations. Bob -- The University of Edinburgh is a charitable body, registered in Scotland, with registration number SC005336. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe -

Re: [Haskell-cafe] Don't “accidentallyparalle lize”

2009-09-05 Thread Sjoerd Visscher
guarantee with `seq` is that x `seq` y will be _|_ if x is. -Brent _______ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe -- Sjoerd Visscher sjo...@w3future.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Text.Html introduction

2009-08-18 Thread Sjoerd Visscher
know? I was looking for this page this morning and couldn't find it. Google does have it in its cache either. -- Johan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe -- Sjoe

Re: [Haskell-cafe] cabal version issue

2009-07-18 Thread Sjoerd Visscher
"Cabal-Version: >= 1.2" or equivalent. What is the "Cabal-Version" in the latter? Why I am getting this warning? Thanks, Vasili ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/hask

Re: [Haskell-cafe] Problems with nested Monads

2009-07-15 Thread Sjoerd Visscher
_ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe -- Sjoerd Visscher sjo...@w3future.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] rewrite rules

2009-06-24 Thread Sjoerd Visscher
de with GHC 6.10, and I get two firings of transform/transform. Does that not happen for you? Simon -- Sjoerd Visscher sjo...@w3future.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] rewrite rules

2009-06-24 Thread Sjoerd Visscher
ings of transform/transform. Does that not happen for you? Simon -- Sjoerd Visscher sjo...@w3future.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] rewrite rules

2009-06-22 Thread Sjoerd Visscher
ore the core output becomes manageable. Sjoerd -- ryan On Mon, Jun 22, 2009 at 2:41 AM, Sjoerd Visscher wrote: Hi all, I have a rewrite rule as follows: {-# RULES "transform/transform" forall (f::forall m. Monoid m => (a -> m) -> (b -> m))

[Haskell-cafe] rewrite rules

2009-06-22 Thread Sjoerd Visscher
rm f (transform g l) = transform (g.f) l #-} It fires on this code: print $ transform (. (*2)) (transform (. (+1)) (upto 10)) But it doesn't fire on this code: print $ map (*2) (map (+1) (upto 10))) with map g x = transform (. g) x and with or without {-# INLINE map #-}. Wha

Re: [Haskell-cafe] ANNOUNCE fmlist

2009-06-19 Thread Sjoerd Visscher
f.e. the ChoiceT type from MonadLib, where bfs and idfsBy are variations on runChoiceT. The ChoiceEff part might complicate things a bit though. But I might be missing some essential detail. greetings, -- Sjoerd Visscher sjo...@w3future.com ___

Re: [Haskell-cafe] ANNOUNCE fmlist

2009-06-19 Thread Sjoerd Visscher
On Jun 19, 2009, at 3:35 PM, Sjoerd Visscher wrote: > transform t l = FM $ \f -> unFM l (t f) Unfortunately I couldn't get this code to type-check, so the library doesn't use transform. With some help from Martijn van Steenbergen the type turned out to be: transform :: (

Re: [Haskell-cafe] ANNOUNCE fmlist

2009-06-19 Thread Sjoerd Visscher
e library doesn't use transform. Sjoerd On Jun 18, 2009, at 11:28 AM, Sebastian Fischer wrote: 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

Re: [Haskell-cafe] Confusion on the third monad law when using lambda abstractions

2009-06-18 Thread Sjoerd Visscher
Jake ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe -- Sjoerd Visscher sjo...@w3future.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] ANNOUNCE fmlist

2009-06-18 Thread Sjoerd Visscher
s my first package on Hackage, so any comments are welcome! greetings, Sjoerd Visscher PS. What happened to the traverse encoded containers (see below)? It turns out that it is a bit too generic, and functions like filter were impossible to implement. FMLists still have a Traversable

[Haskell-cafe] traversal transformations

2009-06-14 Thread Sjoerd Visscher
structure. newtype ShowContainer a = ShowContainer { doShowContainer :: String } instance Functor ShowContainer where fmap _ (ShowContainer x) = ShowContainer $ "(" ++ x ++ ")" instance Applicative ShowContainer where pure _ = ShowContainer "()" ShowContainer l <*&g

Re: [Haskell-cafe] Code Golf

2009-04-20 Thread Sjoerd Visscher
This is one with functional lists: diag = foldr1 (zipWith (.) $. id ~> (id:) ~> id) $. map (++ repeat id) ~> takeWhile (not.null.($[])) $. (map.map) (:) ~> ($[]) . mconcat On Apr 20, 2009, at 1:48 PM, Sebastian Fischer wrote: On Apr 18, 2009, at 2:48 AM, Sjoerd Vi

Re: [Haskell-cafe] Code Golf

2009-04-17 Thread Sjoerd Visscher
e grouped. greetings, -- Sjoerd Visscher sjo...@w3future.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] replicateM should be called mreplicate?

2009-04-06 Thread Sjoerd Visscher
; m a -> m [a] Am I missing something or should this have been called mreplicate? greetings, -- Sjoerd Visscher sjo...@w3future.com___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Paper draft: "Denotational design with type class morphisms"

2009-02-19 Thread Sjoerd Visscher
beautiful relations found in the rest of the paper. greetings, Sjoerd Visscher On Feb 19, 2009, at 4:21 AM, Conal Elliott wrote: I have a draft paper some of you might enjoy, called "Denotational design with type class morphisms". Abstract: Type classes provide a mechanism for va

[Haskell-cafe] Type family problem

2009-01-20 Thread Sjoerd Visscher
I can't figure out what is going on or how I should fix this. -- Sjoerd Visscher sjo...@w3future.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Slow Text.JSON parser

2009-01-17 Thread Sjoerd Visscher
sing would be: instance (Monad m, U.UTF8Bytes string index) => Stream (U.UTF8 string) m Char where uncons = return . U.uncons I did not do any performance measuring yet, I was glad I got it working. Any comments on the code is appreciated! greetings, Sjoerd Visscher {-# LANGUAGE Flex

Re: [Haskell-cafe] Slow Text.JSON parser

2009-01-17 Thread Sjoerd Visscher
g to write to get UTF8 JSON parsing would be: instance (Monad m, U.UTF8Bytes string index) => Stream (U.UTF8 string) m Char where uncons = return . U.uncons I did not do any performance measuring yet, I was glad I got it working. Any comments on the code is appreciated! gree

Re: [Haskell-cafe] Slow Text.JSON parser

2009-01-13 Thread Sjoerd Visscher
42 AM, Luke Palmer wrote: On Tue, Jan 13, 2009 at 4:39 PM, Sjoerd Visscher wrote: JSON is a UNICODE format, like any modern format is today. ByteStrings are not going to work. I don't understand this statement. Why can one not make a parser from ByteStrings that can decode UTF-8?

Re: [Haskell-cafe] Slow Text.JSON parser

2009-01-13 Thread Sjoerd Visscher
_ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe -- Sjoerd Visscher sjo...@w3future.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe