Re: [Haskell-cafe] Proposal: new function for lifting

2013-09-29 Thread Bas van Dijk
On 27 September 2013 21:51, Thiago Negri evoh...@gmail.com wrote:
 Stop lifting, start using shinny operators like this one:

 (^$) :: Monad m = m a - (a - b - c) - m b - m c
 (^$) = flip liftM2

Note that something like this is already provided by the
InfixApplicative library:

http://hackage.haskell.org/package/InfixApplicative
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] reifying typeclasses (resend)

2013-09-15 Thread Bas van Dijk
You can indeed use GADTs to solve this:

{-# LANGUAGE GADTs #-}

data Universe a where
UInt  :: Int  - Universe Int
UChar :: Char - Universe Char

class Universal a where
universe :: a - Universe a

instance Universal Int where
universe = UInt

instance Universal Char where
universe = UChar

argument :: (Universal a) = a - Int
argument x = case universe x of
   UInt  n - n
   UChar c - fromEnum c

result :: (Universal a) = Int - a
result val = x
  where
x = case universe x of
  UInt  _ - val
  UChar _ - toEnum val

On 15 September 2013 09:38, Evan Laforge qdun...@gmail.com wrote:
 [ This is the second time I sent this, the first time it said it was
 awaiting moderation because I'm not subscribed to haskell-cafe, which
 is weird because I thought I was.  Did a bunch of people get
 unsubscribed? ]

 I'm sure this is old-hat to typeclass wizards, but I've managed to get
 pretty far without understanding them too well, so here's a basic
 question.  I haven't seen it phrased this way before though:

 I have a typeclass which is instantiated across a closed set of 3
 types.  It has an ad-hoc set of methods, and I'm not too happy with
 them because being a typeclass forces them to all be defined in one
 place, breaking modularity.  A sum type, of course, wouldn't have that
 problem.  But in other places I want the type-safety that separate
 types provide, and packing everything into a sum type would destroy
 that.  So, expression problem-like, I guess.

 It seems to me like I should be able to replace a typeclass with
 arbitrary methods with just two, to reify the type and back.  This
 seems to work when the typeclass dispatches on an argument, but not on
 a return value.  E.g.:

 {-# LANGUAGE ScopedTypeVariables #-}

 class Taggable a where
 toTagged :: a - Tagged
 toTaggedType :: a - TaggedType
 fromTagged :: Tagged - Maybe a

 m_argument :: a - Int
 m_result :: Int - a

 data Tagged = TInt Int | TChar Char deriving (Show)
 data TaggedType = TypeInt | TypeChar deriving (Show)

 instance Taggable Int where
 toTagged = TInt
 toTaggedType _ = TypeInt
 fromTagged (TInt x) = Just x
 fromTagged _ = Nothing

 m_argument = id
 m_result = id

 instance Taggable Char where
 toTagged = TChar
 toTaggedType _ = TypeChar
 fromTagged (TChar x) = Just x
 fromTagged _ = Nothing

 m_argument = fromEnum
 m_result = toEnum

 argument :: (Taggable a) = a - Int
 argument a = case toTagged a of
 TInt x - x
 TChar c - fromEnum c

 result :: forall a. (Taggable a) = Int - a
 result val = case toTaggedType (undefined :: a) of
 TypeInt - val
 TypeChar - toEnum val


 Say m_argument and m_result are the ad-hoc methods I'd like to get out
 of the typeclass.  I can do that well enough for 'argument', but
 'result' runs into trouble.  One is the ugly undefined trick with
 toTaggedType, but the bigger one is that ghc says 'Could not deduce (a
 ~ Int) from the context (Taggable a)'.  I wasn't really expecting it
 to work, because it would entail a case with multiple types.  As far
 as I know, the only way for that to happen is with GADTs.  But I don't
 see how they could help me here.

 So, perhaps my intuition was wrong.  toTagged and fromTagged methods
 give you the power to go between value and type level, but apparently
 that's not enough power to express what typeclasses give you.  Also it
 seems like there's a fundamental difference between dispatching on
 argument vs dispatching on result.

 Is there a way to more formally understand the extents of what
 typeclasses provide, and what a toTagged fromTagged scheme gives me,
 so I can have a better intuition for how to go between value and type
 levels?

 Also, the toTaggedType thing is pretty ugly.  Not just passing it
 undefined, but how it has to repeat the types.  I don't really see a
 way to get around that though.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: Google co-sponsoring ZuriHac 2013

2013-08-21 Thread Bas van Dijk
Dear Haskellers,

I would like to remind you that the Zurich FP Afternoon (with a
keynote by Simon Marlow) is taking place next week (13:00, Thursday,
29 August) and is directly followed by the ZuriHac 2013 Haskell
Hackathon [1].

There are still some places available at both events -- you're welcome
to register at:

http://bit.ly/ZuriHac2013Reg

Google Switzerland will co-sponsor the FP Afternoon and ZuriHac 2013
together with ETH Zurich and Erudify.

Their sponsorship means we can give each attendee a free t-shirt
(picture on the wikipage [2]) and free food and drinks during the FP
Afternoon.

Google is also offering a quiz during the FP Afternoon with prizes
including a Galaxy S4 mini.

I hope to see you there!

Bas

[1] http://www.haskell.org/haskellwiki/ZuriHac2013
[2] http://www.haskell.org/haskellwiki/ZuriHac2013#News

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-07-10 Thread Bas van Dijk
On 10 July 2013 08:57, Alfredo Di Napoli alfredo.dinap...@gmail.com wrote:

 To make the transition easier I have an experimental library which
 defines a ByteString as a type synonym of a Storable.Vector of Word8
 and provides the same interface as the bytestring package:

 https://github.com/basvandijk/vector-bytestring


 That's interesting Bas. What bothers me about ByteStrings is that they need
 to be pinned inside the heap,
 preventing the GC from collecting them.

Being pinned doesn't prevent an object from being garbage collected.
It just means that the GC won't move the object around so that foreign
code can reliably reference the object while the GC is running:

http://ghc.haskell.org/trac/ghc/wiki/Commentary/Rts/Storage/GC/Pinned

 I assume that working with vector remove the problem, correct?

There wasn't a problem in the first but note that a Storable Vector is
implemented in the same way as a ByteString: a ForeignPtr and a
length*

I hope I have now improved your sleep quality ;-)

Cheers,

Bas

* A ByteString also contains an offset but vector modifies the pointer
in the ForeignPtr instead so we safe an Int there.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Examples of MVars usage

2013-06-12 Thread Bas van Dijk
On 12 June 2013 21:29, Francisco M. Soares Nt.
xfrancisco.soa...@gmail.com wrote:
 I am looking for packages on hackage which use MVars extensively. Those
 which create plenty of MVars

Hi Francisco,

Also take a look at Control.Concurrent.Chan in the base library:

http://hackage.haskell.org/packages/archive/base/latest/doc/html/Control-Concurrent-Chan.html

A big Chan has a lot of MVars inside.

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Hackathon] ANN: ZuriHac 2013 FP Afternoon with keynote by Simon Marlow

2013-06-10 Thread Bas van Dijk
On 10 June 2013 19:38, Roman Cheplyaka r...@ro-che.info wrote:
 Hi Bas,

 When:  Thursday 30 August - Friday 1 September
 Where: Erudify offices, Zurich, Switzerland

 Is this a mistake? 30 August is Friday, 1 September is Sunday.

Oops! You're right, that's embarrassing :-)

Thanks,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Array, Vector, Bytestring

2013-06-05 Thread Bas van Dijk
On 5 June 2013 11:50, Peter Simons sim...@cryp.to wrote:
 I meant to say that there is redundancy in *both*. The libraries
 mentioned in this thread re-implement the same type internally and
 expose APIs to the user that are largely identical.

I agree. I hope that ByteStrings will be replaced by a Storable.Vector
of Word8 at some point in the future.

To make the transition easier I have an experimental library which
defines a ByteString as a type synonym of a Storable.Vector of Word8
and provides the same interface as the bytestring package:

https://github.com/basvandijk/vector-bytestring

It includes a comprehensive benchmark suite which compares it to
bytestring. IIRC some functions are way faster in vector than their
bytestring equivalents and they have the potential to fuse. However
some functions are still way slower so more work has to be done in
vector to beat bytestring completely.

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: new bridge! (prelude-prime)

2013-05-23 Thread Bas van Dijk
On 23 May 2013 11:26, Joachim Breitner m...@joachim-breitner.de wrote:
 So you can get what you want by not
 depending on base, but rather have prelude-prime re-export all modules
 from base plus its own Preldue.

How would you re-export all base's modules from the prelude-prime
package? I didn't know this was already possible.

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: new bridge! (prelude-prime)

2013-05-23 Thread Bas van Dijk
On 23 May 2013 11:54, Joachim Breitner m...@joachim-breitner.de wrote:
 Hi,

 Am Donnerstag, den 23.05.2013, 11:52 +0200 schrieb Bas van Dijk:
 On 23 May 2013 11:26, Joachim Breitner m...@joachim-breitner.de wrote:
  So you can get what you want by not
  depending on base, but rather have prelude-prime re-export all modules
  from base plus its own Preldue.

 How would you re-export all base's modules from the prelude-prime
 package? I didn't know this was already possible.

 manually...

 you create a .hs file for every module in base, which imports the module
 in base (using a package-qualified import), gives it a qualified name
 and puts that name in the export list.

I see. Thanks for the clarification.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Streaming bytes and performance

2013-03-20 Thread Bas van Dijk
On 20 March 2013 11:41, Konstantin Litvinenko to.darkan...@gmail.com wrote:
 On 03/20/2013 11:17 AM, Branimir Maksimovic wrote:

 Are you sure? I use ghc 7.6.2


 Huh, I use 7.4.2, and if 7.6.2 can handle this I will try to switch. Not
 sure how to do that on ubuntu 12.10...

I always install ghcs under my home directory:

wget 
http://www.haskell.org/ghc/dist/7.6.2/ghc-7.6.2-x86_64-unknown-linux.tar.bz2
tar -xf ghc-7.6.2-x86_64-unknown-linux.tar.bz2
cd ghc-7.6.2
configure --prefix=$HOME/ghcs/7.6.2
make install

Then put $HOME/ghcs/7.6.2/bin in front of your $PATH.

You could also use:
hsenv --ghc=ghc-7.6.2-x86_64-unknown-linux.tar.bz2 for this:
http://hackage.haskell.org/package/hsenv

My colleague Jason just made  a nice improvement:
https://github.com/tmhedberg/hsenv/pull/22

which allows you to do:

hsenv --ghc=7.6.2

which will automatically download the right ghc for your platform and
install it in a new fresh environment isolated from the rest of your
system.

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Optimizing performance problems with Aeson rendering large Text arrays

2013-02-01 Thread Bas van Dijk
On Feb 1, 2013 1:15 PM, Oliver Charles ol...@ocharles.org.uk wrote:

 Urgh, the formatting got totally destroyed in sending, I think. If so,
here's a paste of my email as I intended it to be sent:

 http://hpaste.org/81648

 Sorry about that!
 - Ocharles


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

If I make a special case for text based UUIDs in aeson:

data Value = ... | UUID Text | ...

Data.Aeson.Encode.fromValue (UUID s) = singleton ''  fromText s 
singleton ''

Then encoding time improves by 20%.

So a big part of the time is spent encoding the UUID strings.

Bas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] aeson-0.6.1.0 deriveJSON error

2013-01-26 Thread Bas van Dijk
On 26 January 2013 14:47,  j...@stuttard.org wrote:
 ghc doesn't seem to be unifying deriveJSON (String-String)
 parameter with id :: a - a.

It seems you're using aeson HEAD. Note that the deriveJSON from the
released aeson-0.6.1.0 as the type:

  deriveJSON :: (String - String) - Name - Q [Dec]

But in aeson-HEAD it has the following type:

  deriveJSON :: Options - Name - Q [Dec]

Cheers,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] aeson-0.6.1.0 deriveJSON error

2013-01-26 Thread Bas van Dijk
On 26 January 2013 15:20, Bas van Dijk v.dijk@gmail.com wrote:
 But in aeson-HEAD it has the following type:

   deriveJSON :: Options - Name - Q [Dec]

Note that I'm currently working on extending the encoding Options record:

* I added a constructorNameModifier :: String - String which is
applied to constructor names and is handy for lower-casing them for
example.

* I extended the sumEncoding with a ObjectWithSingleField constructor
which causes a constructor to be encoded to an object with a single
field named after the constructor (modified by the
constructorNameModifier) and the value will be the contents of the
constructor.

* I'm also modifying the GHC Generics code to take the encoding
Options into account.

This work is happening in my parameterize-generic-encoding-with-options branch:

https://github.com/basvandijk/aeson/commits/parameterize-generic-encoding-with-options

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How can I avoid buffered reads?

2012-12-09 Thread Bas van Dijk
On 9 December 2012 10:29, Leon Smith leon.p.sm...@gmail.com wrote:
 On Thu, Dec 6, 2012 at 5:23 PM, Brandon Allbery allber...@gmail.com wro\

 Both should be cdevs, not files, so they do not go through the normal
 filesystem I/O pathway in the kernel and should support select()/poll().
 (ls -l, the first character should be c instead of - indicating
 character-mode device nodes.)  If ghc is not detecting that, then *that* is
 indeed an I/O manager issue.


 The issue here is that if you look at the source of fdReadBuf,  you see that
 it's a plain system call without any reference to GHC's (relatively new) IO
 manager.

What if you use threadWaitRead on the fd before you read from it?

http://hackage.haskell.org/packages/archive/base/latest/doc/html/Control-Concurrent.html#v:threadWaitRead

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Portability of Safe Haskell packages

2012-11-23 Thread Bas van Dijk
On 23 November 2012 15:47, Roman Cheplyaka r...@ro-che.info wrote:
 Should it be advised to surround safe annotations with CPP #ifs?
 Or does anyone see a better way out of this contradiction?

I think that would be good advice. Note that even if you're only using
GHC then you still want to use CPP in order to support older GHC
versions which don't support Safe Haskell as in:

http://hackage.haskell.org/packages/archive/usb/1.1.0.4/doc/html/src/System-USB-Internal.html

Arguably, in that example it would be better to move the check for the
availability of Safe Haskell to the cabal file which would define a
CPP pragma SAFE_HASKELL which can be used in source files.

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] I killed performance of my code with Eval and Strategies

2012-11-14 Thread Bas van Dijk
On Nov 14, 2012 10:44 PM, Janek S. fremenz...@poczta.onet.pl wrote:
 calculateSeq :: [Double] - [Double]
 calculateSeq [] = []
 calculateSeq (x:xs) = (sin . sqrt $ x) : xs

Do you really mean to calculate the 'sin . sqrt' of just the head of the
list, or do you mean:

calculateSeq = map (sin . sqrt)   ?

Bas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mtl-2.1 severly broken, cabal needs blacklisting

2012-11-13 Thread Bas van Dijk
On 13 November 2012 17:27, Andreas Abel andreas.a...@ifi.lmu.de wrote:
 This calls for a means of blacklisting broken or malicious packages.

   cabal update

 should also pull a blacklist of packages that will never be selected by
 cabal install (except maybe by explicit user safety overriding).

Maybe we can use the existing preferred-versions file that cabal-install uses:

http://hackage.haskell.org/packages/archive/preferred-versions

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange behavior with listArray

2012-11-12 Thread Bas van Dijk
On 12 November 2012 14:52, Daniel Fischer
daniel.is.fisc...@googlemail.com wrote:
 I see no loop in that, and ghci doesn't either:

Oops you're right of course.

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Taking over ghc-core

2012-11-11 Thread Bas van Dijk
Great!

On 10 November 2012 16:17, Shachaf Ben-Kiki shac...@gmail.com wrote:
 With Don Stewart's blessing
 (https://twitter.com/donsbot/status/267060717843279872), I'll be
 taking over maintainership of ghc-core, which hasn't been updated
 since 2010. I'll release a version with support for GHC 7.6 later
 today.

 Shachaf

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange behavior with listArray

2012-11-11 Thread Bas van Dijk
On 12 November 2012 04:50, Alex Stangl a...@stangl.us wrote:
 I'm stymied trying to figure out why the program below blows up with
 loop when I use f 0

If you replace the a!0 in f by its value 0, f is equivalent to:

f k = if k  0
then f 0
else 0 : f 1

Do you see the loop now?

Maybe you meant f to be:

f k = if k  0
then f (a!k)
else 0 : f 1

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Motion to unify all the string data types

2012-11-11 Thread Bas van Dijk
On 10 November 2012 17:57, Johan Tibell johan.tib...@gmail.com wrote:
 It better communicates intent. A e.g. lazy byte string can be used for two
 separate things:

  * to model a stream of bytes, or
  * to avoid costs due to concatenating strings.

 By using a strict byte string you make it clear that you're not trying to do
 the former (at some potential cost due to the latter). When you want to do
 the former it should be clear to the consumer that he/she better consume the
 string in an incremental manner as to preserve laziness and avoid space
 leaks (by forcing the whole string).

Good advice.

And when you want to do the latter you should use a Builder[1] (or [2]
if you're working with text).

Bas

[1] 
http://hackage.haskell.org/packages/archive/bytestring/0.10.2.0/doc/html/Data-ByteString-Builder.html
[2] 
http://hackage.haskell.org/packages/archive/text/0.11.2.3/doc/html/Data-Text-Lazy-Builder.html

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lazy boxed array and builder?

2012-07-12 Thread Bas van Dijk
On 12 July 2012 15:35, Yves Parès yves.pa...@gmail.com wrote:
 I remember this discussion, lazy vectors would also enable an implementation
 of bytestring and (maybe) text only with unboxed vectors, unifying it all:
 type ByteString = Vector Word8

Yes, I would like to add a lazy storable vector to
vector-bytestring[1] to make the API 100% consistent with bytestring.

Ideally we would have a type like:

data Lazy vector a = Empty | Chuck {-# UNPACK #-} !(vector a) (Lazy vector a)

Unfortunately GHC can't unpack polymorphic fields. The next best thing
is to use a type family which for each type of vector would return its
lazy version (where the vector is unpacked in the cons cell). Then we
would need a class for common operations on those lazy vectors.

Regards,

Bas

[1] http://hackage.haskell.org/package/vector-bytestring
https://github.com/basvandijk/vector-bytestring

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Extending constraints

2012-06-05 Thread Bas van Dijk
Hello,

I have the following program:

--
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE ScopedTypeVariables #-}

import Data.Proxy (Proxy)
import Data.Typeable (Typeable, TypeRep, typeOf)

data ProxyWrapper constraint =
forall a. constraint a = ProxyWrapper (Proxy a)

typeOfInnerProxy :: ProxyWrapper constraint - TypeRep
typeOfInnerProxy (ProxyWrapper p) = typeOfArg p

typeOfArg :: forall t a. Typeable a = t a - TypeRep
typeOfArg _ = typeOf (undefined :: a)
--

Type checking this gives the following expected type error:

ProxyWrapper.hs:12:37:
Could not deduce (Typeable a) arising from a use of `typeOfArg'
from the context (constraint a)
  bound by a pattern with constructor
 ProxyWrapper :: forall (constraint :: * - Constraint) a.
 (constraint a) =
 Proxy a - ProxyWrapper constraint,
   in an equation for `typeOfInnerProxy'

Is there a way to extend the 'constraint' with the 'Typeable'
constraint in the type signature of 'typeOfInnerProxy'?

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Extending constraints

2012-06-05 Thread Bas van Dijk
On 5 June 2012 17:52, Andres Löh and...@well-typed.com wrote:
 Hi Bas.

 I haven't thought about this for long, but ...

 data ProxyWrapper constraint =
    forall a. constraint a = ProxyWrapper (Proxy a)

 I'm assuming adding Typable a in ProxyWrapper is not an option for you?

No, I would rather keep that type as unconstrained as possible.

 So then what about:

 class (c1 a, c2 a) = Ext c1 c2 a
 instance (c1 a, c2 a) = Ext c1 c2 a

 typeOfInnerProxy :: ProxyWrapper (Ext Typeable constraint) - TypeRep
 typeOfInnerProxy (ProxyWrapper p) = typeOfArg p

 This will certainly require all sorts of undecidable instances :) But
 does it work for you?

It works. Thanks a lot!

Cheers,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Extending constraints

2012-06-05 Thread Bas van Dijk
On 5 June 2012 17:57, Bas van Dijk v.dijk@gmail.com wrote:
 It works.

It turns out it doesn't work exactly as I want. Say I have this
ProxyWrapper of Nums:

p :: ProxyWrapper Num
p = ProxyWrapper (Proxy :: Proxy Int)

then the following would give a type error:

oops :: TypeRep
oops = typeOfInnerProxy p

Couldn't match expected type `Ext Typeable constraint0'
with actual type `Num'
Expected type: ProxyWrapper (Ext Typeable constraint0)
  Actual type: ProxyWrapper Num
In the first argument of `typeOfInnerProxy', namely `p'
In the expression: typeOfInnerProxy p

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Extending constraints

2012-06-05 Thread Bas van Dijk
On 5 June 2012 18:46, Gábor Lehel illiss...@gmail.com wrote:
 I must be missing something, but this seems a bit useless to me. You
 have a phantom type parameter on Proxy, and then you're hiding it. So
 when you pattern match on ProxyWrapper you recover the fact that there
 was a type which satisfies the constraint, but you don't know what
 type it was, and neither do you know about any values which are of the
 type. What are you trying to do?

I need a list of types that satisfy a certain constraint. I would like
to have the static guarantee that types that don't satisfy the
constraint can't be put in the list, as in:

nums :: [ProxyWrapper Num]
nums = [ ProxyWrapper (Proxy :: Proxy Int)
   , ProxyWrapper (Proxy :: Proxy Double)
   , ProxyWrapper (Proxy :: Proxy String) -- not allowed
   ]

fracs :: [ProxyWrapper Fractional]
fracs = [ ProxyWrapper (Proxy :: Proxy Double)
, ProxyWrapper (Proxy :: Proxy Float)
, ProxyWrapper (Proxy :: Proxy Int) -- not allowed
]

 That said, if you want to be able to recover a Typeable constraint, I
 don't see any way except for using 'ProxyWrapper (Ext Typeable
 constraint)' as Andres says or putting 'forall a. (constraint a,
 Typeable a)' in the definition of ProxyWrapper.

Indeed, I'm now going for the latter option.

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Parameterize constraints of existentially quantified types

2012-04-21 Thread Bas van Dijk
Hi,

I just found out that with the new ConstraintKinds extension we can
parameterize the constraint of an existentially quantified type:

{-# LANGUAGE KindSignatures, ConstraintKinds, ExistentialQuantification #-}
import GHC.Exts
data Some (c :: * - Constraint) = forall a. c a = Some a

This could be used to define SomeException for example:

import Control.Exception (Exception)
type SomeException = Some Exception

Are there any other use cases?

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Arguments against an hypothetical Data.ByteString.Generic?

2012-03-27 Thread Bas van Dijk
On 27 March 2012 11:00, Yves Parès yves.pa...@gmail.com wrote:
 Hello,

 As vector provides a class generalizing all flavours
 (Data.Vector.Generic.Vector), it occurs to me that the same could be done
 for ByteString. Then, packages based on it would have the choice between
 hardcoded and generic, they wouldn't have to duplicate a module to handle
 both strict and lazy versions, as (with the exception of functions for
 communication with C code) they already provide the same API.
 I would be willing to make it, it's a concern I've had in mind for a long
 time, but as I'm pretty sure the idea isn't new, I would very much like to
 know if and what arguments (related to performance maybe ? I don't know...)
 were raised against that.

It's not entirely what you need but are you aware of my
vector-bytestring library?

http://hackage.haskell.org/package/vector-bytestring

It doesn't (yet) abstract over strict and lazy ByteStrings. But that
would be a nice addition!

In an ideal world we would have a Lazy type family which for each type
of vector would return its lazy version (where the vector is unpacked
in the cons cell). Then we would need your generic API for working
with both lazy and strict vectors.

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Arguments against an hypothetical Data.ByteString.Generic?

2012-03-27 Thread Bas van Dijk
On 27 March 2012 21:46, Yves Parès yves.pa...@gmail.com wrote:
 Yes, thank you to remind me of that, I remember now having seen the project.
 Strict ByteStrings being an alias to Vector Word8 is a good idea (are
 bytestrings are already implemented exactly like
 Data.Vector.Storable.Vector). But in that case we could use the API of
 vector for bytestrings (the bytestring API would be provided only for
 backwards compatibility, right?).

Yes, I hope that one day the bytestring package and the ByteString
type will be deprecated in favor of vector and
Data.Vector.Storable.Vector Word8 respectively. vector-bytestring is
indeed intended as a package which should make the transition easier.

 Does vector-bytestring plans to be the new implementation for bytestrings in
 the end or is it a side-package?

I hope that once we get on par with bytestring's performance we can
replace it (we're almost there!, Yell if you want to see some
benchmark results).

 In an ideal world we would have a Lazy type family which for each type
 of vector would return its lazy version

 What about a type like:

 data Vector v a = Empty | Chuck {-# UNPACK #-} !(v a) (Vector v a)
 ??

If you build with -Wall you'll see the following unfortunate warning:

Warning: Ignoring unusable UNPACK pragma on the
 first argument of `Chunk'

Johan Tibell recently discussed some of his ideas on how to solve this:

http://www.haskell.org/pipermail/glasgow-haskell-users/2012-March/022079.html

But for now we need to make a specialized type for every different
vector type and use an associated type family to abstract over these
different types.

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: generic-deepseq 1.0.0.0

2012-02-23 Thread Bas van Dijk
On 23 February 2012 22:09, Maxime Henrion mhenr...@gmail.com wrote:
 On Sun, 2012-02-19 at 21:06 +0100, Bas van Dijk wrote:
 On 19 February 2012 18:11, Maxime Henrion mhenr...@gmail.com wrote:
  I'm guilty of not having preserved the rnf :: a - ()
  function as the class function though, it's a wrapper around deepseq
  in my code. I just didn't see the point of having a class function with
  such a signature versus having a function just like seq :: a - b -
  b. In retrospect, that might have been a bad idea, and maybe I should
  switch to have an rnf :: a - () class function to make switching even
  easier?

 I'm not sure but maybe a method like rnf :: a - () is easier to optimize.

 Also in my experience (with generics support in aeson and cereal) it's
 a very good idea (performance-wise) to INLINE your methods like I did
 in my previous message. Of course the only way to know for sure is the
 create some (criterion) benchmarks.

 Well I wrote some dumb criterion benchmarks that run deepseq over
 increasingly bigger lists of numbers, and it appears that using rnf as
 the member function of the DeepSeq class indeed makes a _huge_
 difference.

Nice, that's what I expected. Have you checked if adding INLINE
pragma's helps even more? (I guess not since it's already on par with
manual written code, as you mentioned)

BTW I would also recommend making a benchmark for a big sum type.

Some nitpicking:

* In the instance:

instance GDeepSeq U1 where grnf _ = ()

I think it makes sense to pattern match on the U1 constructor, as in:
grnf U1 = ().

I haven't checked if that's necessary but my fear is that assuming:
data Unit = Unit deriving Generic; instance DeepSeq Unit
rnf (⊥ :: Unit) would equal: () while I would expect it to equal ⊥.

* Why do you have the instance:

instance GDeepSeq V1 where grnf _ = ()

The only way to construct values of a void type is using ⊥. And I
would expect that rnf ⊥ = ⊥, not (). I think the best thing is to just
remove the V1 instance.

Cheers,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: generic-deepseq 1.0.0.0

2012-02-19 Thread Bas van Dijk
On 19 February 2012 13:12, Maxime Henrion mhenr...@gmail.com wrote:
 Any suggestions are welcome.

Nice work but it would be nice to have this functionality directly in
the deepseq package as in:

#ifdef GENERICS
{-# LANGUAGE DefaultSignatures, TypeOperators, FlexibleContexts #-}
#endif

class NFData a where
rnf :: a - ()
rnf a = a `seq` ()

#ifdef GENERICS
default rnf :: (Generic a, GNFData (Rep a)) = a - ()
rnf = grnf . from

class GNFData f where
grnf :: f a - ()

instance GNFData U1 where
grnf U1 = ()
{-# INLINE grnf #-}

instance NFData a = GNFData (K1 i a) where
grnf = rnf . unK1
{-# INLINE grnf #-}

instance GNFData f = GNFData (M1 i c f) where
grnf = grnf . unM1
{-# INLINE grnf #-}

instance (GNFData f, GNFData g) = GNFData (f :+: g) where
grnf (L1 x) = grnf x
grnf (R1 x) = grnf x
{-# INLINE grnf #-}

instance (GNFData f, GNFData g) = GNFData (f :*: g) where
grnf (x :*: y) = grnf x `seq` grnf y
{-# INLINE grnf #-}
#endif

Unfortunately this is not possible since the two default
implementations conflict. I see two solutions:

1) Change the DefaultSignatures extension to always give preference to
the default signature. I think giving preference to the default
signature makes sense since it's usually more specific (more
constraint) and thus more correct than the default implementation.

2) Remove the default implementation of rnf. I understand the default
implementation gives some convenience when writing instances for types
that have an all strict representation, as in:

instance NFData Int
instance NFData Word
instance NFData Integer
...

However, I think having the default implementation can mask some bugs as in:
data T = C Int; instance NFData T
which will neither give a compile time error nor warning.

I don't think it's that much more inconvenient to write:

instance NFData Int where rnf = rnf'
instance NFData Word where rnf = rnf'
instance NFData Integer where rnf = rnf'
...
where
rnf' :: a - ()
rnf' a = a `seq` ()

So I would vote for option 2, removing the default rnf implementation.
If I find some time I will turn this into an official proposal.

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: generic-deepseq 1.0.0.0

2012-02-19 Thread Bas van Dijk
On 19 February 2012 18:11, Maxime Henrion mhenr...@gmail.com wrote:
 If you're not dealing with an abstract datatype, you _shouldn't_ have an
 explicit instance, because it would be possible to write an incorrect one,
 while that is impossible if you just derive a generic implementation
 (as long as the generic code is correct, of course).

I agree. I hadn't considered this advantage yet. I guess it's the same
argument for why it's better to automatically derive Data and Typeable
instances using the DeriveDataTypeable extension.

 So, knowing that it would necessarily be backwards incompatible (I
 wasn't intending to hack on GHC :-), and also that, in the end, this is
 not quite the same class as the NFData class from the deepseq package, I
 thought it made more sense to create another package that would be
 mostly compatible with deepseq, but with a different class name so as to
 force people to reevaluate the need for their instances if they have
 some. I'd be interested in knowing what you and others think about that.
 Maybe I'm being overly cautious?

I do think it's better to integrate this into the deepseq package (and
thus removing the default implementation of rnf). Otherwise we end up
with two ways of evaluating values to normal form.

 I'm guilty of not having preserved the rnf :: a - ()
 function as the class function though, it's a wrapper around deepseq
 in my code. I just didn't see the point of having a class function with
 such a signature versus having a function just like seq :: a - b -
 b. In retrospect, that might have been a bad idea, and maybe I should
 switch to have an rnf :: a - () class function to make switching even
 easier?

I'm not sure but maybe a method like rnf :: a - () is easier to optimize.

Also in my experience (with generics support in aeson and cereal) it's
a very good idea (performance-wise) to INLINE your methods like I did
in my previous message. Of course the only way to know for sure is the
create some (criterion) benchmarks.

One last issue: Say I have a type like: data T = C !Int
Currently GHC Generics can't express the strictness annotation. This
means that your deepseq will unnecessarily evaluate the Int (since it
will always be evaluated already). It would be nice if the strictness
information could be added to the K1 type. (José, would it be hard to
add this to GHC.Generics?)

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Serializing UTCTimes

2012-01-21 Thread Bas van Dijk
Thanks Ertugrul and Yitzchak. I failed to notice the Real and
Fractional instances for DiffTime. Thanks very much for pointing me to
it. I dropped the dependency on datetime and implemented your
suggestions.

Bas

On 21 January 2012 22:29, Yitzchak Gale g...@sefer.org wrote:
 Bas van Dijk wrote:
 What's the recommended way for serializing (with the cereal package) an 
 UTCTime?

 Serialize the Day part as an Integer using
 toModifiedJulianDay/ModifiedJulianDay,
 (Note that Day is not a constructor, it's just the name of
 the type.)

 Serialize the DiffTime as a Rational, as Ertugrul said.

 I'm now using the datetime package

 Why? It just obscures the time library.

 But I will have to look at the code of datetime to see if I'm not
 losing precision.

 You are losing precision. If you only care
 about time to the nearest second, you can truncate
 the Rational of the DiffTime (don't round, because
 this may be the last second of a day) and then
 use fromIntegral to deserialize.

 Regards,
 Yitz

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Serializing UTCTimes

2012-01-20 Thread Bas van Dijk
Hello,

What's the recommended way for serializing (with the cereal package) an UTCTime?

It's easy to give Serialize instances for UTCTime and Day:

instance Serialize UTCTime where
get = liftM2 UTCTime get get
put (UTCTime day time) = put day  put time

instance Serialize Day where
get = liftM Day get
put = put . toModifiedJulianDay

However I have no idea how to serialize the DiffTime stored in an UTCTime:

instance Serialize DiffTime where
get = ?
put = ?

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Serializing UTCTimes

2012-01-20 Thread Bas van Dijk
On 20 January 2012 15:03, Bas van Dijk v.dijk@gmail.com wrote:
 What's the recommended way for serializing (with the cereal package) an 
 UTCTime?

I'm now using the datetime package so I can do:

import Data.DateTime (fromSeconds, toSeconds)

instance Serialize UTCTime where
get = fromSeconds $ get
put = put . toSeconds

But I will have to look at the code of datetime to see if I'm not
loosing precision.

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] hackage trac broken

2012-01-15 Thread Bas van Dijk
On 15 January 2012 12:01, Joachim Breitner nome...@debian.org wrote:
 Is this known and will it be fixed?

It was shut down because of massive spamming:

http://www.haskell.org/pipermail/cabal-devel/2012-January/008427.html

I have no idea who's working on it and when it will be up again.

Cheers,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHC 7.4: Expected behavior or bug?

2011-12-27 Thread Bas van Dijk
On 27 December 2011 17:38, Michael Snoyman mich...@snoyman.com wrote:
 Thanks to Mark Wright for pointing this out[1].

 We have the equivalent of the following code in persistent:

 {-# LANGUAGE MultiParamTypeClasses #-}
 data Key backend entity = Key

 class Monad (b m) = Foo b m where
    func :: b m (Key b m)

 This code works fine with GHC 7.0, but I get the following message from GHC 
 7.4:

    Expecting two more arguments to `b'
    In the type `b m (Key b m)'
    In the class declaration for `Foo'

 Is this expected behavior, or a bug? If the former, what would be a
 possible workaround?

 Thanks,
 Michael

 [1] https://github.com/yesodweb/persistent/issues/31

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

I fixed a similar breakage in the hmatrix library:

https://github.com/AlbertoRuiz/hmatrix/commit/a4f38eb196209436f72b938f6355f6e28474bef3

I don't know if it's a bug in GHC, but the workaround is to add an
explicit kind signature:

{-# LANGUAGE KindSignatures, MultiParamTypeClasses #-}
data Key (backend :: * - * - *) entity = Key

class Monad (b m) = Foo b m where
   func :: b m (Key b m)

Cheers,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHC 7.4: Expected behavior or bug?

2011-12-27 Thread Bas van Dijk
On 27 December 2011 17:47, Bas van Dijk v.dijk@gmail.com wrote:
 I fixed a similar breakage in the hmatrix library:

 https://github.com/AlbertoRuiz/hmatrix/commit/a4f38eb196209436f72b938f6355f6e28474bef3

GHC-7.4.1-rc1 also reported another type error in code that was
accepted by GHC = 7.2.2. These were the type errors I got:

[24 of 36] Compiling Numeric.LinearAlgebra.Algorithms (
lib/Numeric/LinearAlgebra/Algorithms.hs,
dist/build/Numeric/LinearAlgebra/Algorithms.o )

lib/Numeric/LinearAlgebra/Algorithms.hs:576:23:
No instance for (RealFrac (RealOf t0))
  arising from a use of `floor'
Possible fix:
  add an instance declaration for (RealFrac (RealOf t0))
In the expression: floor
In the second argument of `($)', namely
  `floor $ logBase 2 $ pnorm Infinity m'
In the expression: max 0 $ floor $ logBase 2 $ pnorm Infinity m

lib/Numeric/LinearAlgebra/Algorithms.hs:576:31:
No instance for (Floating (RealOf t0))
  arising from a use of `logBase'
Possible fix:
  add an instance declaration for (Floating (RealOf t0))
In the expression: logBase 2
In the second argument of `($)', namely
  `logBase 2 $ pnorm Infinity m'
In the second argument of `($)', namely
  `floor $ logBase 2 $ pnorm Infinity m'

lib/Numeric/LinearAlgebra/Algorithms.hs:576:39:
No instance for (Num (RealOf t0))
  arising from the literal `2'
Possible fix: add an instance declaration for (Num (RealOf t0))
In the first argument of `logBase', namely `2'
In the expression: logBase 2
In the second argument of `($)', namely
  `logBase 2 $ pnorm Infinity m'

lib/Numeric/LinearAlgebra/Algorithms.hs:576:43:
No instance for (Normed Matrix t0)
  arising from a use of `pnorm'
Possible fix: add an instance declaration for (Normed Matrix t0)
In the second argument of `($)', namely `pnorm Infinity m'
In the second argument of `($)', namely
  `logBase 2 $ pnorm Infinity m'
In the second argument of `($)', namely
  `floor $ logBase 2 $ pnorm Infinity m'

lib/Numeric/LinearAlgebra/Algorithms.hs:593:19:
No instance for (Container Vector t0)
  arising from a use of `add'
Possible fix: add an instance declaration for (Container Vector t0)
In the expression: add
In an equation for `|+|': |+| = add
In an equation for `expGolub':
expGolub m
  = iterate msq f !! j
  where
  j = max 0 $ floor $ logBase 2 $ pnorm Infinity m
  a = m */ fromIntegral ((2 :: Int) ^ j)
  q = geps eps
  eye = ident (rows m)
  

lib/Numeric/LinearAlgebra/Algorithms.hs:599:1:
Couldn't match type `t0' with `t'
  because type variable `t' would escape its scope
This (rigid, skolem) type variable is bound by
  the type signature for expm :: Field t = Matrix t - Matrix t
The following variables have types that mention t0
  expGolub :: Matrix t0 - Matrix t0
(bound at lib/Numeric/LinearAlgebra/Algorithms.hs:575:1)

Note that RealOf is a type family:

type family RealOf x

type instance RealOf Double = Double
type instance RealOf (Complex Double) = Double

type instance RealOf Float = Float
type instance RealOf (Complex Float) = Float

Adding the following explicit type signature fixed it:

expGolub :: ( Fractional t, Element t, Field t
, Normed Matrix t
, RealFrac (RealOf t)
, Floating (RealOf t)
) = Matrix t - Matrix t

I have no idea if this should be considered a bug.

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell Platform and Windows - where's 2011.4?

2011-12-27 Thread Bas van Dijk
On 27 December 2011 19:13, Steve Horne sh006d3...@blueyonder.co.uk wrote:
 On haskell.org, the 2011.4.0.0 version is shown as the current stable
 release - but the most recent download link is for the 2011.2.0.0 version.

What download link are you referring to? I see that:
http://hackage.haskell.org/platform/windows.html correctly points to
the 2011.4.0.0 release.

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-21 Thread Bas van Dijk
On 16 December 2011 16:26, Yves Parès limestr...@gmail.com wrote:
 1) What about the First type? Do we {-# DEPRECATE #-} it?

 Personnaly, I'm in favor of following the same logic than Int:
 Int itself is not a monoid. You have to be specific: it's either Sum or
 Mult.

 It should be the same for Maybe: we remove its instance of Monoid, and we
 only use First and Last.

The reason you need to be specific with Int is that it's not clear
which semantics (sum or product) you want. The semantics of Maybe are
clear: it's failure-and-prioritized-choice.

Changing the order of the arguments of mappend should be the job of Dual.

If we really want to drop the Monoid instance for Maybe and keep First
and Last and also want to be consistent we should also drop the Monoid
instances of [a], a-b, Endo a and of all the tuples. And instead
define Monoid instance for First [a], Last [a], First (a-b), Last
(a-b), etc. I don't think this is what we want.

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Interruptible threads with IO loops

2011-12-21 Thread Bas van Dijk
On 21 December 2011 09:52, Fedor Gogolev k...@knsd.net wrote:
 I'm trying to get some threads that I can stop and get last
 values that was computed (and that values are IO values, in fact).

I'm not sure it's what you need but you might want to look at:

http://hackage.haskell.org/package/Workflow

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Adding state to a library

2011-12-18 Thread Bas van Dijk
On 18 December 2011 22:26, Kevin Jardine kevinjard...@gmail.com wrote:
 I have a library of functions that all take a config parameter (and usually
 others) and return results in the IO monad.

 It is sometimes useful to drop the config parameter by using a state-like
 monad..

If you're not modifying the configuration, a reader monad transformer
is probably enough:

http://hackage.haskell.org/packages/archive/transformers/0.2.2.0/doc/html/Control-Monad-Trans-Reader.html#t:ReaderT

You probably want to define your own monad transformer for your library:

newtype MyMonad m a = M {unM :: ReaderT Config m a}
  deriving (Functor, Applicative, Monad, MonadTrans, MonadIO)

getConfig :: MyMonad m Config
getConfig = M ask

 I have found that I can wrap all my functions like so:

 withLibrary cfg f = f cfg

This can now be defined as:

withLibrary :: Config - MyMonad m a - m a
withLibrary cfg m = runReaderT (unM m) cfg

 stateF a b c d =
    getConfig = \cfg - liftIO $ withLibrary cfg
    libraryF a b c d

 notice that I need stateF and libraryF lines, each with n parameters.

 Upgrading my library like this is rather tedious.

 I would prefer to just write something like

 stateF = upgrade libraryF

 but I can find no way to define the function upgrade in Haskell.

 This must be a fairly common problem. Is there a simple solution?

What do you mean by upgrading?

Cheers,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-16 Thread Bas van Dijk
On 16 December 2011 05:26, Brent Yorgey byor...@seas.upenn.edu wrote:
 I, for one, would be
 quite in favor of changing the current Monoid (Maybe a) instance to
 correspond to the failure-and-prioritized-choice semantics

So lets do this. Some questions:

1) What about the First type? Do we {-# DEPRECATE #-} it?

2) What about the Last type? It could be deprecated in favor of Dual.

3) Do we need a new type (like the current Maybe) for lifting
semigroups into a Monoid? IMHO we don't since the semigroup package
does a better job with the Option type (like Brent mentioned).

4) How much code will break from this change?

5) Anyone up for proposing this to librar...@haskell.org?

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-16 Thread Bas van Dijk
Attached is a git patch for base which makes the proposed changes.
From 824bdca994b3fcceff21fcb68e1b18f1d4f03bd5 Mon Sep 17 00:00:00 2001
From: Bas van Dijk v.dijk@gmail.com
Date: Fri, 16 Dec 2011 15:16:14 +0100
Subject: [PATCH] Give the Maybe Monoid the expected
 failure-and-prioritized-choice semantics instead of the
 lift-a-semigroup-to-a-monoid semantics. The old semantics
 didn't even achieve the latter since it required a Monoid
 instance on a, rather than a semigroup Also DEPRECATE First
 in favor of Maybe and Last in favor of Dual.

---
 Data/Monoid.hs |   46 --
 1 files changed, 20 insertions(+), 26 deletions(-)

diff --git a/Data/Monoid.hs b/Data/Monoid.hs
index 228e254..d1d9564 100644
--- a/Data/Monoid.hs
+++ b/Data/Monoid.hs
@@ -186,14 +186,14 @@ instance Num a = Monoid (Product a) where
 --
 -- @
 -- findLast :: Foldable t = (a - Bool) - t a - Maybe a
--- findLast pred = getLast . foldMap (\x - if pred x
---then Last (Just x)
---else Last Nothing)
+-- findLast pred = getDual . foldMap (\x - if pred x
+--then Dual (Just x)
+--else Dual Nothing)
 -- @
 --
 -- Much of Data.Map's interface can be implemented with
 -- Data.Map.alter. Some of the rest can be implemented with a new
--- @alterA@ function and either 'First' or 'Last':
+-- @alterA@ function and either 'Maybe' or 'Dual Maybe':
 --
 --  alterA :: (Applicative f, Ord k) =
 --(Maybe a - f (Maybe a)) - k - Map k a - f (Map k a)
@@ -204,28 +204,21 @@ instance Num a = Monoid (Product a) where
 -- insertLookupWithKey :: Ord k = (k - v - v - v) - k - v
 -- - Map k v - (Maybe v, Map k v)
 -- insertLookupWithKey combine key value =
---   Arrow.first getFirst . alterA doChange key
+--   alterA doChange key
 --   where
---   doChange Nothing = (First Nothing, Just value)
---   doChange (Just oldValue) =
--- (First (Just oldValue),
---  Just (combine key value oldValue))
+--   doChange m@Nothing = (m, Just value)
+--   doChange m@(Just oldValue) = (m, Just (combine key value oldValue))
 -- @
 
--- | Lift a semigroup into 'Maybe' forming a 'Monoid' according to
--- http://en.wikipedia.org/wiki/Monoid: \Any semigroup @S@ may be
--- turned into a monoid simply by adjoining an element @e@ not in @S@
--- and defining @e*e = e@ and @e*s = s = s*e@ for all @s ∈ S@.\ Since
--- there is no \Semigroup\ typeclass providing just 'mappend', we
--- use 'Monoid' instead.
-instance Monoid a = Monoid (Maybe a) where
+instance Monoid (Maybe a) where
   mempty = Nothing
-  Nothing `mappend` m = m
-  m `mappend` Nothing = m
-  Just m1 `mappend` Just m2 = Just (m1 `mappend` m2)
-
+  Nothing `mappend` r = r
+  l   `mappend` _ = l
 
 -- | Maybe monoid returning the leftmost non-Nothing value.
+--
+-- /DEPRECATED in favor of 'Maybe'!/
+{-# DEPRECATED First Use Maybe instead #-}
 newtype First a = First { getFirst :: Maybe a }
 #ifndef __HADDOCK__
 deriving (Eq, Ord, Read, Show)
@@ -237,11 +230,13 @@ instance Show a = Show (First a)
 #endif
 
 instance Monoid (First a) where
-mempty = First Nothing
-r@(First (Just _)) `mappend` _ = r
-First Nothing `mappend` r = r
+mempty = First mempty
+First l `mappend` First r = First (l `mappend` r)
 
 -- | Maybe monoid returning the rightmost non-Nothing value.
+--
+-- /DEPRECATED in favor of 'Dual'!/
+{-# DEPRECATED Last Use Dual instead #-}
 newtype Last a = Last { getLast :: Maybe a }
 #ifndef __HADDOCK__
 deriving (Eq, Ord, Read, Show)
@@ -253,9 +248,8 @@ instance Show a = Show (Last a)
 #endif
 
 instance Monoid (Last a) where
-mempty = Last Nothing
-_ `mappend` r@(Last (Just _)) = r
-r `mappend` Last Nothing = r
+mempty = Last mempty
+Last x `mappend` Last y = Last (y `mappend` x)
 
 {-
 {
-- 
1.7.5.4

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] DB vs read/show for persisting large data

2011-12-14 Thread Bas van Dijk
On 14 December 2011 15:22, Claude Heiland-Allen cla...@goto10.org wrote:
 I ran into this very nightmare in one project, and was recommend safecopy
 [0] by someone on the #haskell IRC channel.  I've not (yet) used it but it
 looks very nice!

 [0] http://hackage.haskell.org/package/safecopy

Or better yet, use acid-state which is build on top of safecopy:

http://acid-state.seize.it/

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell functions caller-callee details

2011-12-09 Thread Bas van Dijk
On 9 December 2011 16:41, Shakthi Kannan shakthim...@gmail.com wrote:
 Given a Haskell package is there a way I can get each functions'
 caller-callee details? Are there any existing tools/libraries that can
 help me get this data from the source?

Check out SourceGraph:

http://hackage.haskell.org/package/SourceGraph

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-06 Thread Bas van Dijk
On 6 December 2011 04:03, Joey Hess j...@kitenet.net wrote:
 I'm trying to convert from 0.2 to 0.3, but in way over my head.

 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
 newtype Annex a = Annex { runAnnex :: StateT AnnexState IO a }
        deriving (
                Monad,
                MonadIO,
                -- MonadControlIO
                MonadBaseControl IO
        )

You can use the following:

{-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies, MultiParamTypeClasses #-}

import Control.Applicative
import Control.Monad
import Control.Monad.Base
import Control.Monad.Trans.Class
import Control.Monad.Trans.Control
import Control.Monad.Trans.State
import Control.Monad.IO.Class

newtype Annex a = Annex { runAnnex :: StateT AnnexState IO a }
   deriving (Applicative, Functor, Monad, MonadIO)

data AnnexState = AnnexState

instance MonadBase IO Annex where
liftBase = Annex . liftBase

instance MonadBaseControl IO Annex where
newtype StM Annex a = StAnnex (StM (StateT AnnexState IO) a)
liftBaseWith f = Annex $ liftBaseWith $ \runInIO -
   f $ liftM StAnnex . runInIO . runAnnex

When I have some time I will add some better documentation to monad-control.

Cheers,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-06 Thread Bas van Dijk
On 6 December 2011 09:12, Bas van Dijk v.dijk@gmail.com wrote:
 instance MonadBaseControl IO Annex where
    newtype StM Annex a = StAnnex (StM (StateT AnnexState IO) a)
    liftBaseWith f = Annex $ liftBaseWith $ \runInIO -
                       f $ liftM StAnnex . runInIO . runAnnex

Oops forgot the restoreM method:

   restoreM = Annex . restoreM . unStAnnex

unStAnnex (StAnnex st) = st

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-06 Thread Bas van Dijk
On 6 December 2011 05:06, Michael Snoyman mich...@snoyman.com wrote:
 Maybe this will help[1]. It's using RWST instead of StateT, but it's
 the same idea.

 [1] 
 https://github.com/yesodweb/yesod/commit/7619e4e9dd88c152d1e00b6fea073c3d52dc797f#L0R105

Hi Michael,

Note that you can just reuse the MonadTransControl instance of the
RWST transformer:

instance MonadTransControl (GGWidget master) where
newtype StT (GGWidget master) a =
StWidget {unStWidget :: StT (GWInner master) a}
liftWith f = GWidget $ liftWith $ \run -
   f $ liftM StWidget . run . unGWidget
restoreT = GWidget . restoreT . liftM unStWidget

Cheers,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-06 Thread Bas van Dijk
On 6 December 2011 12:59, Michael Snoyman mich...@snoyman.com wrote:
 On Tue, Dec 6, 2011 at 11:49 AM, Bas van Dijk v.dijk@gmail.com wrote:
 On 6 December 2011 05:06, Michael Snoyman mich...@snoyman.com wrote:
 Maybe this will help[1]. It's using RWST instead of StateT, but it's
 the same idea.

 [1] 
 https://github.com/yesodweb/yesod/commit/7619e4e9dd88c152d1e00b6fea073c3d52dc797f#L0R105

 Hi Michael,

 Note that you can just reuse the MonadTransControl instance of the
 RWST transformer:

 instance MonadTransControl (GGWidget master) where
    newtype StT (GGWidget master) a =
        StWidget {unStWidget :: StT (GWInner master) a}
    liftWith f = GWidget $ liftWith $ \run -
                   f $ liftM StWidget . run . unGWidget
    restoreT = GWidget . restoreT . liftM unStWidget

 Cheers,

 Bas

 Thanks Bas, I was just in the process of converting Widget from being
 a RWS to a Writer, and your code made it much simpler :).

 Michael

Do you think it's useful to have the following two utility functions
for defining a MonadTransControl instance for your own monad
transformer provided that your transformers is defined in terms of
another transformer:

defaultLiftWith ∷ (Monad m, MonadTransControl tInner)
⇒ (tInner m α → t m α)  -- ^ Constructor
→ (∀ β n. t n β → tInner n β)   -- ^ Deconstructor
→ (∀ β. StT tInner β → StT t β) -- ^ State constructor
→ ((Run t → m α) → t m α)
defaultLiftWith con deCon st = \f → con $ liftWith $ \run →
  f $ liftM st ∘ run ∘ deCon

defaultRestoreT ∷ (Monad m, MonadTransControl tInner)
⇒ (tInner m α → t m α)  -- ^ Constructor
→ (StT t α  → StT tInner α) -- ^ State deconstructor
→ (m (StT t α) → t m α)
defaultRestoreT con unSt = con ∘ restoreT ∘ liftM unSt

For example in your case you would use these as follows:

instance MonadTransControl (GGWidget master) where
newtype StT (GGWidget master) a =
StWidget {unStWidget :: StT (GWInner master) a}
liftWith = defaultLiftWith GWidget unGWidget StWidget
restoreT = defaultRestoreT GWidget unStWidget

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-03 Thread Bas van Dijk
On 3 December 2011 10:18, Herbert Valerio Riedel h...@gnu.org wrote:
 btw, how did you manage to get measurements from 2 different versions of
 the same library (monad-control 0.3 and 0.2.0.3) into a single report?

By renaming the old package to monad-control2 and using the
PackageImports extension.

I do wonder why it's not possible to use two different versions of the
same package at the same time.

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-03 Thread Bas van Dijk
On 3 December 2011 00:45, Bas van Dijk v.dijk@gmail.com wrote:
 Note that Peter Simons just discovered that these packages don't build
 with GHC-7.0.4 (https://github.com/basvandijk/monad-control/issues/3).
 I just committed some fixes which enable them to be build on GHC =
 6.12.3. Hopefully I can release these fixes this weekend.

I just released the fixes:

http://hackage.haskell.org/package/monad-control-0.3.0.1
http://hackage.haskell.org/package/lifted-base-0.1.0.1

Cheers,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Weird interaction between literate haskell, ghci and OverloadedStrings

2011-12-03 Thread Bas van Dijk
On 3 December 2011 11:19, Erik de Castro Lopo mle...@mega-nerd.com wrote:
 Joachim Breitner wrote:

 it does not seem to be related to literate haskell, if I copy the code
 from your file into a .hs without the  , ghci still does not activate
 the OverloadedStrings extension when loading the file.

 I hadn't noticed that.

 I’d consider this a bug until the developers explain why this should or
 cannot be different, and suggest you file it as such.

 I agree. I've lodged a bug report here:

    http://hackage.haskell.org/trac/ghc/ticket/5673

I think it's very dangerous if language extensions leak from modules
by default. For example if someone creates a library and needs to use
some unsafe language extensions like:

{-# LANGUAGE UndecidableInstances, OverlappingInstances, IncoherentInstances #-}
module SomeLib where ...

You surely don't want to silently enable these in some unsuspecting client:

module MyFirstHaskellModule where
import SomeLib
...

I can imagine having a pragma for explicitly exporting language extensions:

{-# EXPORT_LANGUAGE OverloadedStrings #-}

Cheers,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-02 Thread Bas van Dijk
Hello,

I just released monad-control-0.3. The package for lifting control
operations (like catch, bracket, mask, alloca, timeout, forkIO,
modifyMVar, etc.) through monad transformers:

http://hackage.haskell.org/package/monad-control-0.3

It has a new and improved API which is:

* easier to understand by explicitly representing the monadic state
using type families.
* 60 times faster than the previous release!
* more general because control operations can now, not only be lifted
from IO, but from any base monad (ST, STM, etc.)

I also released a new package: lifted-base:

http://hackage.haskell.org/package/lifted-base-0.1

It provides lifted versions of functions from the base library.
Currently it exports the following modules:

* Control.Exception.Lifted
* Control.Concurrent.Lifted
* Control.Concurrent.MVar.Lifted
* System.Timeout.Lifted

These are just modules which people have needed in the past. If you
need a lifted version of some function, just ask me to add it or send
me a patch.

Note that Peter Simons just discovered that these packages don't build
with GHC-7.0.4 (https://github.com/basvandijk/monad-control/issues/3).
I just committed some fixes which enable them to be build on GHC =
6.12.3. Hopefully I can release these fixes this weekend.

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: monad-control-0.3

2011-12-02 Thread Bas van Dijk
On 3 December 2011 00:45, Bas van Dijk v.dijk@gmail.com wrote:
 * 60 times faster than the previous release!

Here are some benchmark results that compare the original monad-peel,
the previous monad-control-0.2.0.3 and the new monad-control-0.3:

http://basvandijk.github.com/monad-control.html

Note that the benchmarks use Bryan O'Sullivan's excellent new
criterion-0.6 package.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Documenting strictness properties for Data.Map.Strict

2011-11-18 Thread Bas van Dijk
On 18 November 2011 06:44, Johan Tibell johan.tib...@gmail.com wrote:
 Here are some examples:

    insertWith (+) k undefined m  ==  undefined
    delete undefined m  ==  undefined
    map (\ v - undefined)  ==  undefined
    mapKeys (\ k - undefined)  ==  undefined

 Any ideas for further improvements?

I would use '_|_' instead of 'undefined'.

Then again, this does require the reader to know what '_|_' means. But
note we already use this symbol in the base library.

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A Mascot

2011-11-16 Thread Bas van Dijk
On 16 November 2011 05:18, John Meacham j...@repetae.net wrote:
 Not nearly enough
 attention is paid to the other striking feature, the laziness. The
 'bottom' symbol _|_ should feature prominently. The two most defining
 features of haskell are that it is purely functional and _|_ inhabits
 every type. The combination of which is very powerful.

Is ⊥ the right symbol to express the non-strict evaluation of the
language? Is it true that non-strict evaluation requires that ⊥
inhabits every type? In other words: why can't there exist a
non-strict total language (probably having some form of coinductive
types)?

Cheers,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A Mascot

2011-11-16 Thread Bas van Dijk
On 16 November 2011 11:05, MigMit miguelim...@yandex.ru wrote:
 Maybe it's just me, but I've thought that being non-strict just means that 
 it's possible for a function to produce some value even if it's argument 
 doesn't; in other words, that it's possible to have f (_|_) ≠ (_|_). If 
 there was no such thing as (_|_), what would non-strictness mean?

Thanks, non-strictness is indeed defined using ⊥ like you mentioned.

I think I was confusing non-strict evaluation with coinduction. They
have the same advantages but the latter is less powerful but safer
than the former.

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] deepseq-1.2.0.1 missing Data.Map instance

2011-11-15 Thread Bas van Dijk
On 15 November 2011 23:50, Daniel Fischer
daniel.is.fisc...@googlemail.com wrote:
 The change is already in the latest released
 deepseq version, but will only be in the containers version to be released
 with ghc-7.4.

The change is already in the released containers-0.4.2.0. So the only
thing Henry needs to do is install that version and rebuild his
libraries against that version.

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monad-control rant

2011-11-13 Thread Bas van Dijk
Hi Mikhail,

your type class:

class MonadAbort e μ ⇒ MonadRecover e μ | μ → e where
  recover ∷ μ α → (e → μ α) → μ α

looks a lot like the MonadCatchIO type class from MonadCatchIO-transformers:

class MonadIO m = MonadCatchIO m where
  catch   :: E.Exception e = m a - (e - m a) - m a

I haven't looked at your code in detail but are you sure your
continuation based AIO monad doesn't suffer from the same unexpected
behavior as the ContT monad transformer with regard to catching and
handling exceptions? The API docs of MonadCatchIO-transformers explain
the bug in detail:

http://hackage.haskell.org/packages/archive/MonadCatchIO-transformers/0.2.2.3/doc/html/Control-Monad-CatchIO.html
Regards,

Bas


On 12 November 2011 13:55, Mikhail Vorozhtsov
mikhail.vorozht...@gmail.com wrote:
 On 11/12/2011 07:34 AM, Bas van Dijk wrote:

 Are you going to release a new version of monad-control right away

 Not just yet. I've split `monad-control` into two packages:

 * `monad-control`: just exports `Control.Monad.Trans.Control`. This part
 is finished.
 * `lifted-base`: wraps all modules of the `base` package which export `IO`
 computations and provides
  lifted version instead. For example we have `Control.Exception.Lifted`,
 `Control.Concurrent.Lifted`, etc.

 As you can imagine the latter is a lot of boring work. Fortunately it's
 easy to do so will probably
 not take a lot of time. BTW if by any chance you want to help out, that
 will be much appreciated!

 The repos can be found [here](https://github.com/basvandijk/lifted-base)

 Maybe I should elaborate on why I stopped using monad-control and rolled out
 my own version of lifted Control.Exception in monad-abort-fd package. I'm
 CC-ing the Cafe just in case someone else might be interested in the matter
 of IO lifting.

 Imagine we have a monad for multiprogramming with shared state:

 -- ContT with a little twist. Both the constructor and runAIO
 -- are NOT exported.
 newtype AIO s α =
  AIO { runAIO ∷ ∀ β . (α → IO (Trace s β)) → IO (Trace s β) }

 runAIOs ∷ MonadBase IO μ
        ⇒ s -- The initial state
        → [AIO s α] -- The batch of programs to run.
                    -- If one program exits normally (without using
                    -- aioExit) or throws an exception, the whole batch
                    -- is terminated.
        → μ (s, Maybe (Attempt α)) -- The final state and the result.
                                   -- Nothing means deadlock or that
                                   -- all the programs exited with
                                   -- aioExit.
 runAIOs = liftBase $ mask_ $ ... bloody evaluation ...

 data Trace s α where
  -- Finish the program (without finishing the batch).
  TraceExit ∷ Trace s α
  -- Lift a pure value.
  TraceDone ∷ α → Trace s α
  -- A primitive to execute and the continuation.
  TraceCont ∷ Prim s α → (α → IO (Trace s β)) → Trace s β

 -- Primitive operations
 data Prim s α where
  -- State retrieval/modification
  PrimGet  ∷ Prim s s
  PrimSet  ∷ s → Prim s ()
  -- Scheduling point. The program is suspended until
  -- the specified event occurs.
  PrimEv   ∷ Event e ⇒ e → Prim s (EventResult e)
  -- Scheduling point. The program is suspended until the state
  -- satisfies the predicate.
  PrimCond ∷ (s → Bool) → Prim s ()
  -- Run computation guarded with finalizer.
  PrimFin  ∷ IO (Trace s α) → (Maybe α → AIO s β) → Prim s (α, β)
  -- Run computation guarded with exception handler.
  PrimHand ∷ IO (Trace s α) → (SomeException → AIO s α) → Prim s α

 aioExit ∷ AIO s α
 aioExit = AIO $ const $ return TraceExit

 aioAfter ∷ (s → Bool) → AIO s ()
 aioAfter cond = AIO $ return . TraceCont (PrimCond cond)

 aioAwait ∷ Event e ⇒ e → AIO s (EventResult e)
 aioAwait e = AIO $ return . TraceCont (PrimEv e)

 runAIOs slices the programs at scheduling points and enqueues the individual
 pieces for execution, taking care of saving/restoring the context
 (finalizers and exception handlers).

 The Functor/Applicative/Monad/MonadBase/etc instances are pretty trivial:

 instance Functor (AIO s) where
  fmap f (AIO g) = AIO $ \c → g (c . f)

 instance Applicative (AIO s) where
  pure a = AIO ($ a)
  (*) = ap

 instance Monad (AIO s) where
  return = pure
  AIO g = f = AIO $ \c → g (\a → runAIO (f a) c)

 instance MonadBase IO (AIO s) where
  liftBase io = AIO (io =)

 instance MonadState s (AIO s) where
  get   = AIO $ return . TraceCont PrimGet
  put s = AIO $ return . TraceCont (PrimSet s)

 instance MonadAbort SomeException (AIO s) where
  abort = liftBase . throwIO

 trace ∷ AIO s α → IO (Trace s α)
 trace (AIO g) = g (return . TraceDone)

 instance MonadRecover SomeException (AIO s) where
  recover m h = AIO $ return . TraceCont (PrimHand (trace m) h)

 instance MonadFinally (AIO s) where
  finally' m f = AIO $ return . TraceCont (PrimFin (trace m) f)
  -- finally m = fmap fst . finally' m . const

 -- No async exceptions in AIO
 instance MonadMask () (AIO s) where
  getMaskingState = return ()
  setMaskingState

Re: [Haskell-cafe] [ANN] transformers-base, transformers-abort, monad-abort-fd

2011-11-10 Thread Bas van Dijk
On 10 November 2011 12:58, Mikhail Vorozhtsov
mikhail.vorozht...@gmail.com wrote:
 transformers-base[1] introduces a generalized version of MonadIO, MonadBase
 (BaseM in monadLib terms).

Hi Mikhail, nice packages!

I'm currently giving monad-control a new design and I'm planning to
generalize MonadControlIO to MonadBaseControl. I would like to use
your MonadBase as a super class of MonadBaseControl.

However, your package depends on monad-control to define a similar
class. Of course this prevents monad-control to depend on
transformers-base. Are you willing to drop the monad-control
dependency (and remove Control.Monad.Base.Control)?

I send you a pull request that implements this change.

The pull request also contains a patch that makes some other changes:

* Use CPP macros to abstract the repetitious instances
* Add instances for all base monads in the base library
* Use descriptive variable names: 'm' for monad, 'b' for base monad
* Reversed order of 'b' and 'm' to match BaseM from monadLib

Hopefully you are fine with these changes, otherwise no hard feelings ;-)

Cheers,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [ANN] transformers-base, transformers-abort, monad-abort-fd

2011-11-10 Thread Bas van Dijk
What about base instead of b?

I don't think we should change m since that name is used to denote a
monad in almost any Haskell library I know.

On 10 November 2011 19:07, Colin Adams colinpaulad...@gmail.com wrote:
 And quite rightly too.

 On 10 November 2011 18:02, Felipe Almeida Lessa felipe.le...@gmail.com
 wrote:

 On Thu, Nov 10, 2011 at 2:54 PM, Bas van Dijk v.dijk@gmail.com
 wrote:
  * Use descriptive variable names: 'm' for monad, 'b' for base monad

 It's funny how we, haskellers, find 'm' and 'b' descriptive names.  I
 know many programmers who would cry after seeing this =).

 Cheers,

 --
 Felipe.

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Vector.Unboxed

2011-11-09 Thread Bas van Dijk
On 9 November 2011 10:56, kaffeepause73 kaffeepaus...@yahoo.de wrote:
 Is it possible to create an unboxed vector of unboxed vector ? :

Why do you want to do this?

If you want multi-dimensional unboxed arrays you could try out repa:

http://www.haskell.org/haskellwiki/Numeric_Haskell:_A_Repa_Tutorial

(I believe it uses unboxed Vectors internally).

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Easiest to use NoSQL storage with Haskell?

2011-11-09 Thread Bas van Dijk
On 9 November 2011 11:59, dokondr doko...@gmail.com wrote:
 What  Haskell package to work with NoSQL storage is both mature and easiest
 to use?
 I need persistent storage for simple key/value lists (not complex JSON
 docs).

If your data fits in RAM then acid-state is also an option:

http://hackage.haskell.org/package/acid-state

It's used as the storage library for the new hackage server.

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Easiest to use NoSQL storage with Haskell?

2011-11-09 Thread Bas van Dijk
On 9 November 2011 19:50, dokondr doko...@gmail.com wrote:
 On Wed, Nov 9, 2011 at 8:41 PM, Bas van Dijk v.dijk@gmail.com wrote:

 On 9 November 2011 11:59, dokondr doko...@gmail.com wrote:
  What  Haskell package to work with NoSQL storage is both mature and
  easiest
  to use?
  I need persistent storage for simple key/value lists (not complex JSON
  docs).

 If your data fits in RAM then acid-state is also an option:

 http://hackage.haskell.org/package/acid-state

 It's used as the storage library for the new hackage server.


 I need to share data across processes running both on the same node or
 different nodes. Every process has its own memory space.
 Can acid-state memory be shared between several system processes?


I believe so:

http://hackage.haskell.org/packages/archive/acid-state/0.6.0/doc/html/Data-Acid-Remote.html

but maybe David can tell you more about that.

Cheers,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Vector.Unboxed

2011-11-09 Thread Bas van Dijk
On 9 November 2011 22:33, kaffeepause73 kaffeepaus...@yahoo.de wrote:
 Repa is indeed very Interesting, but I have changing vector length in the
 second dimension and later on only want to generate Data on demand. If I use
 Matrices, I will use loads of space for no reason.

Even if it is possible to create an unboxed vector of unboxed vectors,
if the inner unboxed vectors have variable lengths as you require,
indexing will become O(n) instead of O(1) because you need to traverse
the inner unboxed vectors and check their length to find the desired
index. I'm not sure that's what you want.

 Seems like sticking to Boxed Vector for now is best Choice for me.

Yes your second alternative: a boxed vector of unboxed vectors seems
to do what you want.

 isn't data.vector also providing multidimensional arrays?

I don't think so. All indexing functions get a single Int argument. Of
course it's easy to build a layer on top that adds more dimensions.

 So is Repa just another Version of Data.Vector or is it building another 
 level on top.

The latter, repa provides a layer on top of vector.

Note that you can also convert Vectors to repa Arrays using:

fromVector :: Shape sh = sh - Vector a - Array sh a

I believe its O(1).

 And when to use best which of the two ?

I guess when your vectors are multi-dimensional and you want to
benefit from parallelism you should use repa instead of vector.

Cheers,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is generic information dumpable?

2011-11-04 Thread Bas van Dijk
Thanks José!

Will this make it into ghc-7.4?

Bas

2011/11/4 José Pedro Magalhães j...@cs.uu.nl:
 Hi,
 Now, for the following datatype:
 data X a = X { myX :: a } deriving Generic
 You get the following -ddump-deriv output:
  Derived instances 
 Derived instances:
   instance GHC.Generics.Generic (Temp.X a_adY) where
     GHC.Generics.from (Temp.X g1_aeG)
       = GHC.Generics.M1
           (GHC.Generics.M1 (GHC.Generics.M1 (GHC.Generics.K1 g1_aeG)))
     GHC.Generics.to
       (GHC.Generics.M1 (GHC.Generics.M1 (GHC.Generics.M1 (GHC.Generics.K1
 g1_aeH
       = Temp.X g1_aeH

   instance GHC.Generics.Datatype Temp.D1X where
     GHC.Generics.datatypeName _ = X
     GHC.Generics.moduleName _ = Temp

   instance GHC.Generics.Constructor Temp.C1_0X where
     GHC.Generics.conName _ = X
     GHC.Generics.conIsRecord _ = GHC.Types.True

   instance GHC.Generics.Selector Temp.S1_0_0X where
     GHC.Generics.selName _ = myX

 Generic representation:

   Generated datatypes for meta-information:
     Temp.D1X
     Temp.C1_0X
     Temp.S1_0_0X

   Representation types:
     Temp.Rep_X = GHC.Generics.D1
                    Temp.D1X
                    (GHC.Generics.C1
                       Temp.C1_0X
                       (GHC.Generics.S1 Temp.S1_0_0X (GHC.Generics.Par0
 a_adY)))
 Still not perfect, in that the representation type should really appear as a
 type instance inside the Generic instance, but at least all the important
 information is printed.

 Cheers,
 Pedro

 2011/11/3 Bas van Dijk v.dijk@gmail.com

 2011/11/3 José Pedro Magalhães j...@cs.uu.nl:
  -ddump-deriv will print (most of) it.

 But it doesn't print the most useful piece of information: the
 definition of Rep.

 It would be great if this could be added.

 Currently when I have a type that I want to know the Rep of, say:

 data Foo = Bar Int
         | Boo {hello :: String}
           deriving Generic

 I just convert it to a Rep and show it:

 err = show $ from $ Boo World

 However Reps don't have Show instances so GHC complains:

 No instance for
  (Show (D1 D1Foo (   C1 C1_0Foo (S1 NoSelector (Rec0 Int))
                  :+: C1 C1_1Foo (S1 S1_1_0Foo (Rec0 String))
                  )
         x0
        )
  )
  arising from a use of `show'

 And there you go. This is the only time when I'm happy to see an error
 message :-)

 Bas



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [ANNOUNCE] cereal-0.3.4.0

2011-11-04 Thread Bas van Dijk
On 3 November 2011 16:27, Trevor Elliott tre...@galois.com wrote:
 I'm happy to announce version 0.3.4.0 of the cereal serialization library.

Thanks!

Is your repository public? If so, where can I find it and could it be
listed in the cabal file using something like:

source-repository head
  type: git
  location: http://github.com/.../cereal

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] How to speedup generically parsing sum types?

2011-11-03 Thread Bas van Dijk
Hello,

I recently added default generic implementations of toJSON and
parseJSON to the aeson package. Now I'm optimizing them. Here are some
benchmark results that compare:

* th: toJSON and fromJSON generated by template-haskell. Can be
compared to hand-written code. Should be the fastest of all.

* syb: toJSON and fromJSON from the Data.Aeson.Generic module. Uses
the Data type class.

* generic: my toJSON and fromJSON using GHC Generics.

The benchmark itself can be found here:
https://github.com/basvandijk/aeson/blob/optimizations/benchmarks/AesonCompareAutoInstances.hs

toJSON
==

D/toJSON/th 3.631734 us
D/toJSON/syb32.66679 us
D/toJSON/generic3.371868 us

BigRecord/toJSON/th 8.982990 us
BigRecord/toJSON/syb48.90737 us
BigRecord/toJSON/generic8.971597 us

BigProduct/toJSON/th1.578259 us
BigProduct/toJSON/syb   29.21153 us
BigProduct/toJSON/generic   1.623115 us

BigSum/toJSON/th51.81214 ns
BigSum/toJSON/syb   1.256708 us
BigSum/toJSON/generic   71.32851 ns


fromJSON


D/fromJSON/th   7.017204 us
D/fromJSON/syb  23.46567 us
D/fromJSON/generic  7.968974 us

BigRecord/fromJSON/th   8.513789 us
BigRecord/fromJSON/syb  36.64501 us
BigRecord/fromJSON/generic  10.07809 us

BigProduct/fromJSON/th  2.430677 us
BigProduct/fromJSON/syb 17.97764 us
BigProduct/fromJSON/generic 2.201130 us

BigSum/fromJSON/th  414.8699 ns
BigSum/fromJSON/syb 4.113170 us
BigSum/fromJSON/generic 13.62614 us !!!


As can be seen, in most cases the GHC Generics implementation is much
faster than SYB and just as fast as TH. I'm impressed by how well GHC
optimizes the code!

Unfortunately the last benchmark, generically parsing a big sum type,
is much slower. The code for parsing sums, which can be found here:

https://github.com/basvandijk/aeson/blob/optimizations/Data/Aeson/Types/Internal.hs#L1059

is basically this:


instance (GFromSum a, GFromSum b) = GFromJSON (a :+: b) where
gParseJSON (Object (M.toList - [keyVal])) = gParseSum keyVal
gParseJSON v = typeMismatch sum (:+:) v
{-# INLINE gParseJSON #-}


class GFromSum f where
gParseSum :: Pair - Parser (f a)

instance (GFromSum a, GFromSum b) = GFromSum (a :+: b) where
gParseSum keyVal = (L1 $ gParseSum keyVal) |
   (R1 $ gParseSum keyVal)
{-# INLINE gParseSum #-}

instance (Constructor c, GFromJSON a, ConsFromJSON a) =
GFromSum (C1 c a) where
gParseSum (key, value)
| key == pack (conName (undefined :: t c a p)) =
gParseJSON value
| otherwise = notFound $ unpack key
{-# INLINE gParseSum #-}


notFound :: String - Parser a
notFound key = fail $ The key \ ++ key ++ \ was not found
{-# INLINE notFound #-}


Any idea how to make it faster?

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to speedup generically parsing sum types?

2011-11-03 Thread Bas van Dijk
2011/11/3 José Pedro Magalhães j...@cs.uu.nl:
 - Compile with -O2 and -fno-spec-constr-count (this last one is particularly
 important)

I already compiled with -O2. Adding -fno-spec-constr-count does not
change the results.

 - Add {-# INLINE [1] #-} pragmas to the to/from methods of your Generic
 instances.

I tried:

BigSum/toJSON/generic goes from 70 ns to 52 ns! So inlining 'from' is
an improvement.

Unfortunately BigSum/fromJSON/generic stays at 13 us.

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to speedup generically parsing sum types?

2011-11-03 Thread Bas van Dijk
For those who find this interesting. Here's the code of the BigSum benchmark
with a manual Generic instance with inlined 'from' and 'to':
https://gist.github.com/1336426

José, I was thinking about the following idea. Say GHC generates the
following instance for BigSum:

instance Generic BigSum where
  type Rep BigSum = D1 D1BigSum SumOfBigSum
  ...

type SumOfBigSum =
   (   (   (C1 C1_0BigSum U1
   :+: (C1 C1_1BigSum U1 :+: C1 C1_2BigSum U1)
   )
   :+: (C1 C1_3BigSum U1
   :+: (C1 C1_4BigSum U1 :+: C1 C1_5BigSum U1)
   )
   )
   :+: (   (C1 C1_6BigSum U1
   :+: (C1 C1_7BigSum U1 :+: C1 C1_8BigSum U1)
   )
   :+: (C1 C1_9BigSum  U1
   :+: (C1 C1_10BigSum U1 :+: C1 C1_11BigSum U1)
   )
   )
   )
  :+: (   (   (C1 C1_12BigSum U1
  :+: (C1 C1_13BigSum U1 :+: C1 C1_14BigSum U1)
  )
  :+: (C1 C1_15BigSum U1
  :+: (C1 C1_16BigSum U1 :+: C1 C1_17BigSum U1)
  )
  )
  :+: (   (C1 C1_18BigSum U1
  :+: (C1 C1_19BigSum U1 :+: C1 C1_20BigSum U1)
  )
  :+: (   (C1 C1_21BigSum U1 :+: C1 C1_22BigSum U1)
  :+: (C1 C1_23BigSum U1 :+: C1 C1_24BigSum U1)
  )
  )
  )

It also generates the following function (or method): (I haven't
figured out the correct type yet. A correct version might need to use
type families or functional dependencies)

conPath :: String - Maybe (C1 ? ? ? - SumOfBigSum)
conPath F01 = Just $ L1 . L1 . L1 . L1
conPath F02 = Just $ L1 . L1 . L1 . R1 . L1
conPath F03 = Just $ L1 . L1 . L1 . R1 . R1
conPath F04 = Just $ L1 . L1 . R1 . L1
conPath F05 = Just $ L1 . L1 . R1 . R1 . L1
conPath F06 = Just $ L1 . L1 . R1 . R1 . R1
conPath F07 = Just $ L1 . R1 . L1 . L1
conPath F08 = Just $ L1 . R1 . L1 . R1 . L1
conPath F09 = Just $ L1 . R1 . L1 . R1 . R1
conPath F10 = Just $ L1 . R1 . R1 . L1
conPath F11 = Just $ L1 . R1 . R1 . R1 . L1
conPath F12 = Just $ L1 . R1 . R1 . R1 . R1
conPath F13 = Just $ R1 . L1 . L1 . L1
conPath F14 = Just $ R1 . L1 . L1 . R1 . L1
conPath F15 = Just $ R1 . L1 . L1 . R1 . R1
conPath F16 = Just $ R1 . L1 . R1 . L1
conPath F17 = Just $ R1 . L1 . R1 . R1 . L1
conPath F18 = Just $ R1 . L1 . R1 . R1 . R1
conPath F19 = Just $ R1 . R1 . L1 . L1
conPath F20 = Just $ R1 . R1 . L1 . R1 . L1
conPath F21 = Just $ R1 . R1 . L1 . R1 . R1
conPath F22 = Just $ R1 . R1 . R1 . L1 . L1
conPath F23 = Just $ R1 . R1 . R1 . L1 . R1
conPath F24 = Just $ R1 . R1 . R1 . R1 . L1
conPath F25 = Just $ R1 . R1 . R1 . R1 . R1
conPath _ = Nothing

conPath is given the name of the constructor. If it's a valid name it
will return a function that constructs a SumOfBigSum given the
corresponding constructor. Of course, since the types of the
constructors can vary (not in this case) coming up with a correct
implementation is a challenge.

Using conPath in my gParseJSON is easy:

instance (GFromJSON a, GFromJSON b) = GFromJSON (a :+: b) where
gParseJSON (Object (M.toList - [(key, val)])) =
case conPath key of
  Nothing   - mzero
  Just path - path $ gParseJSON val

gParseJSON v = typeMismatch sum (:+:) v
{-# INLINE gParseJSON #-}

I suspect this to be much more efficient.

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The type class wilderness + Separating instances and implementations into separate packages

2011-11-03 Thread Bas van Dijk
On 3 November 2011 14:56, Ryan Newton rrnew...@gmail.com wrote:
 Aside: The problem with collections is that we don't have the programming
 language means to do this well yet (although soon!). The issue is that we
 want to declare a type class where the context of the methods depends on the
 instance e.g.
 class MapLike m where
     type Ctx :: Context  -- Can't do this today!
     insert Ctx = k - v - m - m
 Java et all cheats in their container hierarchy by doing unsafe casts (i.e.
 they never solved this problem)!

 Ah, interesting.  Is there a proposal to do this?

Even better: it's already implemented by Max Bolingbroke and will be
in ghc-7.4! See:

http://hackage.haskell.org/trac/ghc/wiki/Status/Oct11

So be patient and wait for your Christmas present ;-)

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to speedup generically parsing sum types?

2011-11-03 Thread Bas van Dijk
2011/11/3 Claus Reinke claus.rei...@talk21.com:
 Not that it matters much if you're going with other tools, but your SYB code
 has a long linear chain of type rep comparisons, at every
 level of the recursive traversals. That is partially inherent in the SYB
 design (reducing everything to cast), but could probably be improved?

I'm not an expert on the SYB code. So if you have an idea how to
improve it please file a ticket or even better send a pull request.

Cheers,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to speedup generically parsing sum types?

2011-11-03 Thread Bas van Dijk
On 3 November 2011 17:38, Twan van Laarhoven twa...@gmail.com wrote:
 Perhaps relying on Attoparsec backtracking for picking out the right
 alternative from the sum is the problem. You could try it with Maybe:

Good idea. I implemented and committed it and the
BigSum/fromJSON/generic benchmark goes from 13.6 us to 11.3 us. Still
a lot slower than the 4.1 us of SYB or the 414.9 ns of TH but an
improvement nonetheless.

Thanks for the idea!

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Mailing lists at haskell.org

2011-11-03 Thread Bas van Dijk
On 3 November 2011 23:11, Giovanni Tirloni gtirl...@sysdroid.com wrote:
 Does anyone know what's the procedure to create a new mailing list at
 haskell.org for a forming user group?

community.haskell.org provides MailMan mailing lists:

Cheers,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is generic information dumpable?

2011-11-03 Thread Bas van Dijk
2011/11/3 José Pedro Magalhães j...@cs.uu.nl:
 -ddump-deriv will print (most of) it.

But it doesn't print the most useful piece of information: the
definition of Rep.

It would be great if this could be added.

Currently when I have a type that I want to know the Rep of, say:

data Foo = Bar Int
 | Boo {hello :: String}
   deriving Generic

I just convert it to a Rep and show it:

err = show $ from $ Boo World

However Reps don't have Show instances so GHC complains:

No instance for
  (Show (D1 D1Foo (   C1 C1_0Foo (S1 NoSelector (Rec0 Int))
  :+: C1 C1_1Foo (S1 S1_1_0Foo (Rec0 String))
  )
 x0
)
  )
  arising from a use of `show'

And there you go. This is the only time when I'm happy to see an error
message :-)

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is generic information dumpable?

2011-11-03 Thread Bas van Dijk
2011/11/4 José Pedro Magalhães j...@cs.uu.nl:
 Hi,

 2011/11/3 Bas van Dijk v.dijk@gmail.com

 2011/11/3 José Pedro Magalhães j...@cs.uu.nl:
  -ddump-deriv will print (most of) it.

 But it doesn't print the most useful piece of information: the
 definition of Rep.

 Yes... I am aware of this.


 It would be great if this could be added.

 I'll do it.


 Cheers,
 Pedro




Great, thanks!

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] A catch-all MonadIO instance

2011-10-28 Thread Bas van Dijk
Hello,

Is it unsafe to add the following catch-all MonadIO instance to
transformers' Control.Monad.IO.Class module?

{-# LANGUAGE FlexibleInstances, FlexibleContexts, UndecidableInstances #-}

instance (MonadTrans t, Monad (t m), MonadIO m) = MonadIO (t m) where
liftIO = lift . liftIO

It could get rid of all the similarly looking instances:

instance (MonadIO m) = MonadIO (ReaderT r m) where
liftIO = lift . liftIO
instance (MonadIO m) = MonadIO (StateT s m) where
liftIO = lift . liftIO
instance (Monoid w, MonadIO m) = MonadIO (WriterT w m) where
liftIO = lift . liftIO
...

The reason I ask is that I want to do something similar for
monad-control's MonadControlIO type class. But I'm not sure if I don't
introduce any undecidability in the type-checker.

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A catch-all MonadIO instance

2011-10-28 Thread Bas van Dijk
On 28 October 2011 16:23, Antoine Latter aslat...@gmail.com wrote:
 I would then need OverlappingInstances to declare a MonadIO instance
 for any similar looking instance head (that is `t m`) where 't' was
 not a proper MonadTrans instance, which sounds like a common enough
 things to do.

I actually have never seen a MonadIO instance for a `t m` where 't' is
not a MonadTrans instance.

On 28 October 2011 16:24, Paterson, Ross r.pater...@city.ac.uk wrote:
 It's done that way in transformers to keep the package portable.
 As for doing it elsewhere, although this catch-all instance requires
 UndecidableInstances, I don't think it introduces non-termination.

I understand, portability is important for transformers. For
monad-control it's less of an issue because I already use other
language extensions (incl. RankNTypes).

So I think I go ahead and add a catch-all instance for MonadControlIO
to monad-control.

Thanks for your responses,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A catch-all MonadIO instance

2011-10-28 Thread Bas van Dijk
On 28 October 2011 16:59, Ertugrul Soeylemez e...@ertes.de wrote:
 I'm not sure whether this will work well.  You will get overlapping
 instances, and I don't see a way to hide instances when importing.
 Perhaps the OverlappingInstances extension could help here.

You're right.

I didn't get an overlapping instances error when building transformers
with this change (Note I didn't remove the custom MonadIO instances).

However when *using* liftIO I did get it:

 runReaderT (liftIO $ putStrLn Hello World!) (10 :: Int)

interactive:0:13:
Overlapping instances for MonadIO (ReaderT Int m0)
  arising from a use of `liftIO'
Matching instances:
  instance MonadIO m = MonadIO (ReaderT r m)
-- Defined at Control/Monad/Trans/Reader.hs:128:10-45
  instance (MonadTrans t, Monad (t m), MonadIO m) = MonadIO (t m)
-- Defined at Control/Monad/IO/Class.hs:43:10-64

Enabling the OverlappingInstances extension does fix it. However I
don't want to force users to use it so I keep the custom instances.

Thanks,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: Monad.Reader Issue 19

2011-10-26 Thread Bas van Dijk
On 26 October 2011 21:17, Brent Yorgey byor...@seas.upenn.edu wrote:
 I am pleased to announce that Issue 19 of The Monad.Reader, a special
 issue on parallelism and concurrency, is now available:

Thanks, I always really enjoy The Monad.Reader.

 Issue 19 consists of the following three articles:

  * Mighttpd – a High Performance Web Server in Haskell
    by Kazu Yamamoto

Kazu, really interesting article!

I have one question regarding your use of atomicModifyIORef:

  x - atomicModifyIORef ref (\_ - (tmstr, ()))
  x `seq` return ()

Can't you write that as just: writeIORef ref tmstr? If you're not
using the previous value of the IORef there's no chance of
inconsistency.

I looked in the git repository of mighttpd2 and it seems that in the
FileCache module we can make a similar change by rewriting:

remover :: IORef Cache - IO ()
remover ref = do
threadDelay 1000
_ - atomicModifyIORef ref (\_ - (M.empty, ()))
remover ref

to:

remover :: IORef Cache - IO ()
remover ref = forever $ do
threadDelay 1000
writeIORef ref M.empty

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] runStateT execution times measurement baffling

2011-10-22 Thread Bas van Dijk
On 20 October 2011 22:16, thomas burt thedwa...@gmail.com wrote:
 Perhaps I will try and force `stuffToDo` not to leave any partially
 evaluated thunks behind and compare the cost then.

What happens when you switch to a strict StateT?

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] New rss maintainer

2011-10-22 Thread Bas van Dijk
I released a new rss:

http://hackage.haskell.org//package/rss-3000.2.0

It no longer requires old-time and is tested with the latest versions
of its dependencies.

On 21 October 2011 17:34, Vincent Hanquez t...@snarc.org wrote:
 Perhaps, unless someone step up, it would be nice to move packages that have
 no maintainer anymore into a github organisation (haskell-janitors ?),

Nice idea! However I think we should always strive for having a single
or a limited number of maintainers. Finally when nobody wants to take
over a package we can hand it over to haskell-janitors.

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] New rss maintainer

2011-10-21 Thread Bas van Dijk
On 20 October 2011 21:27, Bas van Dijk v.dijk@gmail.com wrote:
 Otherwise I could take it over. I probably won't make lots of changes
 since I'm a bit swamped at the moment. Just updating it to the latest
 versions.

I've moved the repository over to github:

https://github.com/basvandijk/rss

If nobody steps up as new maintainer I will make a new release this weekend.

Cheers,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] New rss maintainer

2011-10-20 Thread Bas van Dijk
Hello,

I've a small patch[1] that updates the rss package to the latest
versions of its dependencies. (I'm trying to get the new
hackage-server to build on ghc-7.2.1)

However Bjorn Bringert told me he's no longer maintaining the package.
He asked me to ask you if there's already a new maintainer. If not,
does any one want to take over the package? Jeremy, maybe you?

Otherwise I could take it over. I probably won't make lots of changes
since I'm a bit swamped at the moment. Just updating it to the latest
versions.

Regards,

Bas

[1] http://code.haskell.org/~basvandijk/update_rss.dpatch

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lost in generics

2011-10-20 Thread Bas van Dijk
On 20 October 2011 19:12, Rustom Mody rustompm...@gmail.com wrote:
 And of course which are easier and which more difficult to dig into.

If you're looking for an example for the new GHC generic mechanism: I
recently added a generic default implementation to the ToJSON and
FromJSON type classes of the aeson package (not in mainline yet):

class ToJSON a where
toJSON   :: a - Value

default toJSON :: (Generic a, GToJSON (Rep a)) = a - Value
toJSON = gToJSON . from

class FromJSON a where
parseJSON :: Value - Parser a

default parseJSON :: (Generic a, GFromJSON (Rep a)) = Value - Parser a
parseJSON = fmap to . gParseJSON

See:

https://github.com/basvandijk/aeson/blob/newGenerics/Data/Aeson/Types/Internal.hs#L895

It wasn't that difficult to implement. However I did need to use some
advanced type-level tricks to convert to and from records.

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] proper way to generate a random data in criterion

2011-10-19 Thread Bas van Dijk
On 19 October 2011 17:03, Johan Tibell johan.tib...@gmail.com wrote:
 Have a look at:

 https://github.com/tibbe/unordered-containers/blob/master/benchmarks/Benchmarks.hs

I see you use the (evaluate . rnf) composition.

I also used it in:

https://github.com/basvandijk/vector-bytestring/blob/master/bench.hs#L118

and called it:

deepEvaluate :: NFData a = a - IO ()
deepEvaluate = evaluate . rnf

I'm not sure about the name but I think it would be nice if this was
added to Control.DeepSeq.

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-17 Thread Bas van Dijk
On 17 October 2011 10:18, Christian Maeder christian.mae...@dfki.de wrote:
 I think the cleanest solution (just from a theoretical point of view) is to
 use a newtype for your byte strings.

 - it should have the same performance
 - allows to make ByteString really abstract when hiding the newtype
 constructor

But what would a newtype ByteString = ByteString (Vector Word8)
abstract over? What's there to hide? Vectors are already abstract so
users can't mess with their internals.

 - is portable and supplies control over all other instances (not just Show)

What other instances (besides Show) should have different semantics
than those of Vector?

 I'm not sure if one could make really bad thinks to your ByteString by using
 the Vector interface, but one would want to disallow vector operations just
 for compatible with other byte strings.

My idea is that when vector-bytestring is as fast as bytestring, it
can replace it. When that happens it doesn't matter if users use the
vector interface. I would even recommend it over using the bytestring
interface so that bytestring can eventually be deprecated in favor of
vector.

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-17 Thread Bas van Dijk
On 17 October 2011 16:44, Michael Snoyman mich...@snoyman.com wrote:
 On Mon, Oct 17, 2011 at 4:42 PM, Roman Leshchinskiy r...@cse.unsw.edu.au 
 wrote:
 Michael Snoyman wrote:
 On Mon, Oct 17, 2011 at 12:14 PM, Bas van Dijk v.dijk@gmail.com
 wrote:

 My idea is that when vector-bytestring is as fast as bytestring, it
 can replace it. When that happens it doesn't matter if users use the
 vector interface. I would even recommend it over using the bytestring
 interface so that bytestring can eventually be deprecated in favor of
 vector.

 +1. I'm in favor of using the OverlappingInstances/no newtype and
 specialized Show instance. I think that, if there was *ever* a case
 where OverlappingInstances was a good fit, it's this one. We're
 talking about a single module exporting both the base and overlapped
 instance, so which instance gets used should be completely decidable.
 (Unless of course someone defines an orphan instance elsewhere, but
 that's a different issue IMO.) And even in a worst-case-scenario where
 somehow we get the wrong instance, we're only talking about output
 used as a debugging aid, so the damage is minimal.

 So suppose we change the Show and Read instances for Storable vectors of
 Word8 and Char. What happens with unboxed and boxed vectors of these
 types? Should these be changed as well? Should these be changed as well?
 If not, why not?

 I don't have any strong opinion on the matter, but it seems like they
 may as well be changed also. It seems like all the same useful for
 debugging arguments would apply there as well.

 Michael


Yes I think that makes sense. My patch already adds specific Show and
Read instances to all vectors of Chars and Word8s:
http://trac.haskell.org/vector/ticket/64

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-17 Thread Bas van Dijk
On 17 October 2011 13:12, Christian Maeder christian.mae...@dfki.de wrote:
 Am 17.10.2011 12:14, schrieb Bas van Dijk:

 On 17 October 2011 10:18, Christian Maederchristian.mae...@dfki.de
  wrote:

 I think the cleanest solution (just from a theoretical point of view) is
 to
 use a newtype for your byte strings.

 - it should have the same performance
 - allows to make ByteString really abstract when hiding the newtype
 constructor

 But what would a newtype ByteString = ByteString (Vector Word8)
 abstract over? What's there to hide? Vectors are already abstract so
 users can't mess with their internals.

 Maybe some of the functions that start with unsafe?

But to keep compatible with bytestring's Data.ByteString.Unsafe, I
have to export the unsafe functions anyway.

I do think we should provide a Data.Vector.Storable.Safe module which
only exports the safe interface and mark it Trustworthy using the new
Safe Haskell language extensions.

Roman: any reason why only storable vectors are missing a Safe module?
I could add one this evening, if you like?

And should we also export Unsafe modules like how it's done in the base library?

 http://hackage.haskell.org/packages/archive/vector/0.9/doc/html/Data-Vector-Storable.html#t:Vector

 - is portable and supplies control over all other instances (not just
 Show)

 What other instances (besides Show) should have different semantics
 than those of Vector?

 instance Read (and maybe the vector package will evolve further).

 I'm not sure if one could make really bad thinks to your ByteString by
 using
 the Vector interface, but one would want to disallow vector operations
 just
 for compatible with other byte strings.

 My idea is that when vector-bytestring is as fast as bytestring, it
 can replace it. When that happens it doesn't matter if users use the
 vector interface. I would even recommend it over using the bytestring
 interface so that bytestring can eventually be deprecated in favor of
 vector.

 So your package basically supports an unfortunate mix of bytestring and
 vector functions?

No, vector-bytestring exports the same API as bytestring (except for
the Show and Read instances which will hopefully be fixed in a new
vector release).

 How about proposing a better bytestring interface (if it
 should not just be that of vector)?

I'm all for improving the interface but the goal of vector-bytestring
is that it can be used as a drop-in replacement for bytestring without
changing to much code.

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-17 Thread Bas van Dijk
On 17 October 2011 20:15, Yves Parès limestr...@gmail.com wrote:
 It's a good question, I don't think there is something in the vector library
 that can handle chunks of vectors...

Yes I forgot about lazy bytestrings when writing that. Of course
vector-bytestring does provide lazy ByteStrings.

 If both lazy and strict bytestrings are to be generalized, it would at last
 permit to have a single interface to them, thanks to Data.Vector.Generic,
 and no longer two identical interfaces in separate modules, which forces to
 duplicate each code which handles bytestrings so that it can deal with the
 two flavours.

It would be an interesting idea to add a chunking vector adapter to
the vector package.

I guess it will look something like this:

data Chunks v a = Empty | Chunk {-# UNPACK #-} !(v a) (Chunks v a)

foldrChunks :: (v a - b - b) - b - Chunks v a - b
foldrChunks f z = go
  where go Empty= z
go (Chunk c cs) = f c (go cs)
{-# INLINE foldrChunks #-}

foldlChunks :: (b - v a - b) - b - Chunks v a - b
foldlChunks f z = go z
  where go !a Empty= a
go !a (Chunk c cs) = go (f a c) cs
{-# INLINE foldlChunks #-}

Giving it an instance for Data.Vector.Generic.Base.Vector should be
easy right? Anyone up for the job?

Then I can replace my custom lazy ByteStrings with:

type ByteString = Chunks Vector Word8

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-17 Thread Bas van Dijk
On 17 October 2011 18:28, Christian Maeder christian.mae...@dfki.de wrote:
 Am 17.10.2011 17:26, schrieb Bas van Dijk:

 On 17 October 2011 13:12, Christian Maederchristian.mae...@dfki.de
  wrote:

 So your package basically supports an unfortunate mix of bytestring and
 vector functions?

 No, vector-bytestring exports the same API as bytestring (except for
 the Show and Read instances which will hopefully be fixed in a new
 vector release).

 Yes, but Data.Vector.Storable can be simple imported and used in addition.

I consider that an advantage.

 I suppose, the (derived) Data instances (from vector and the original
 bytestrings) break the abstraction. (So you must hope nobody is relying on
 this instance.)

Good point! I will mention that in the documentation of
vector-bytestring. Also code using the ByteString constructor PS has
to be changed because I obviously can't provide an equivalent. However
the documentation of Data.ByteString.Internal (which exports PS) warns
normal users not to use that module:

A module containing semi-public 'ByteString' internals. This exposes the
'ByteString' representation and low level construction functions. As such
all the functions in this module are unsafe. The API is also not stable.

Where possible application should instead use the functions from the normal
public interface modules, such as Data.ByteString.Unsafe. Packages that
extend the ByteString system at a low level will need to use this module.

So I expect not many packages are using the PS constructor directly
which means the pain of switching to vectors will be minimal.

 How about proposing a better bytestring interface (if it
 should not just be that of vector)?

 I'm all for improving the interface but the goal of vector-bytestring
 is that it can be used as a drop-in replacement for bytestring without
 changing to much code.

 Changing back to another drop-in replacement for bytestring will be
 difficult if functions from Data.Vector.Storable have been used.

True, so lets try to make this the final replacement ;-)

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-16 Thread Bas van Dijk
On 16 October 2011 08:51, Stephen Tetley stephen.tet...@gmail.com wrote:
 On 15 October 2011 23:56, Bas van Dijk v.dijk@gmail.com wrote:
 On 15 October 2011 23:17, Ertugrul Soeylemez e...@ertes.de wrote:
 Both instances are valid here, and there is no mechanism to choose one of 
 them.

 There is: OverlappingInstances[1] chooses the most specific instance.
 So in case someVector :: Vector Word8 the instance Show (Vector Word8)
 is chosen because it's the most specific.

 This has the problem of incoherence in multi-module programs - GHC
 might chose different instances for the same type depending on
 compilation order. For a Show instance, this may be acceptable.

But is this a problem when both instances are exported from the same
module and OverlappingInstances is only enabled in that module, as is
the case here?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-15 Thread Bas van Dijk
On 15 October 2011 13:34, Roman Leshchinskiy r...@cse.unsw.edu.au wrote:

 On 15/10/2011, at 12:26, Roman Leshchinskiy wrote:

 On 14/10/2011, at 12:37, Bas van Dijk wrote:

 If there's need for a specific Show instance for Vectors of Word8s we
 can always add one directly to vector. (Roman, what are your thoughts
 on this?)

 Personally, I think that ByteString and especially Vector Word8 aren't 
 strings and shouldn't be treated as such. But I wouldn't be strongly against 
 showing them as strings. However, I *am* strongly against using 
 UndecidableInstances in vector and I don't see how to implement this without 
 using them.

 I meant OverlappingInstances, of course. To clarify, I would still consider 
 it if everybody thinks it's a really good idea.

 Roman




I agree that you shouldn't use ByteStrings or Vectors of Word8s for
Unicode strings. However I can imagine that for quick sessions in ghci
it can be quite handy if they are shown as strings. For example,
currently we have:

 import Network.HTTP.Enumerator
 simpleHttp http://code.haskell.org/~basvandijk/;
Chunk html\nheadtitleBas van
Dijk/title/head\nbody\nh1Bas van Dijk/h1\n\npEmail: a
href=\mailto://v.dijk@gmail.com\;v.dijk@gmail.com/a/p\n\npNick
on IRC: ttbasvandijk/tt/p\n\na
href=\http://www.haskellers.com/user/basvandijk/\;\n  img
src=\http://www.haskellers.com/static/badge.png\; \n   alt=\I'm
a Haskeller\\n   border=\0\\n/a\n\npSee my a
href=\https://github.com/basvandijk\;GitHub/a page for a list of
projects I work on./p\n\n/body\n/html\n Empty

If ByteStrings were not shown as strings this would look like:

Chunk ( fromList
[60,104,116,109,108,62,10,60,104,101,97,100,62,60,116,105,116,108,101,62,66,97,115,32,118,97,110,32,68,105,106,107,60,47,116,105,116,108,101,62,60,47,104,101,97,100,62,10,60,98,111,100,121,62,10,60,104,49,62,66,97,115,32,118,97,110,32,68,105,106,107,60,47,104,49,62,10,10,60,112,62,69,109,97,105,108,58,32,60,97,32,104,114,101,102,61,34,109,97,105,108,116,111,58,47,47,118,46,100,105,106,107,46,98,97,115,64,103,109,97,105,108,46,99,111,109,34,62,118,46,100,105,106,107,46,98,97,115,64,103,109,97,105,108,46,99,111,109,60,47,97,62,60,47,112,62,10,10,60,112,62,78,105,99,107,32,111,110,32,73,82,67,58,32,60,116,116,62,98,97,115,118,97,110,100,105,106,107,60,47,116,116,62,60,47,112,62,10,10,60,97,32,104,114,101,102,61,34,104,116,116,112,58,47,47,119,119,119,46,104,97,115,107,101,108,108,101,114,115,46,99,111,109,47,117,115,101,114,47,98,97,115,118,97,110,100,105,106,107,47,34,62,10,32,32,60,105,109,103,32,115,114,99,61,34,104,116,116,112,58,47,47,119,119,119,46,104,97,115,107,101,108,108,101,114,115,46,99,111,109,47,115,116,97,116,105,99,47,98,97,100,103,101,46,112,110,103,34,32,10,32,32,32,32,32,32,32,97,108,116,61,34,73,39,109,32,97,32,72,97,115,107,101,108,108,101,114,34,10,32,32,32,32,32,32,32,98,111,114,100,101,114,61,34,48,34,62,10,60,47,97,62,10,10,60,112,62,83,101,101,32,109,121,32,60,97,32,104,114,101,102,61,34,104,116,116,112,115,58,47,47,103,105,116,104,117,98,46,99,111,109,47,98,97,115,118,97,110,100,105,106,107,34,62,71,105,116,72,117,98,60,47,97,62,32,112,97,103,101,32,102,111,114,32,97,32,108,105,115,116,32,111,102,32,112,114,111,106,101,99,116,115,32,73,32,119,111,114,107,32,111,110,46,60,47,112,62,10,10,60,47,98,111,100,121,62,10,60,47,104,116,109,108,62,10])
Empty

Personally, I don't work in ghci that often so I don't care that much
if we have or don't have specialized Show instances for Vectors of
Word8s.

So what do other people think about this?

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-15 Thread Bas van Dijk
On 15 October 2011 20:50, Ertugrul Soeylemez e...@ertes.de wrote:
 Roman Leshchinskiy r...@cse.unsw.edu.au wrote:

  Personally, I think that ByteString and especially Vector Word8
  aren't strings and shouldn't be treated as such. But I wouldn't be
  strongly against showing them as strings. However, I *am* strongly
  against using UndecidableInstances in vector and I don't see how to
  implement this without using them.

 I meant OverlappingInstances, of course. To clarify, I would still
 consider it if everybody thinks it's a really good idea.

 My suggestion was to remove the generic Show instance and add only
 specialized instances.  This is more work, but will also yield better
 results.  In particular, it allows specialized string representations
 for other types, too.

What exactly is the problem with using OverlappingInstances to define
specialized Show and Read instances for Vectors with certain element
types (Char, Word8, Bool)?

Am I missing something dangerous here?

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-15 Thread Bas van Dijk
On 15 October 2011 23:17, Ertugrul Soeylemez e...@ertes.de wrote:
 Both instances are valid here, and there is no mechanism to choose one of 
 them.

There is: OverlappingInstances[1] chooses the most specific instance.
So in case someVector :: Vector Word8 the instance Show (Vector Word8)
is chosen because it's the most specific.

Bas

[1] 
http://www.haskell.org/ghc/docs/latest/html/users_guide/type-class-extensions.html#instance-overlap

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-14 Thread Bas van Dijk
On 14 October 2011 12:58, Christian Maeder christian.mae...@dfki.de wrote:
 Would it not be simple to use a newtype for ByteString (rather than a
 synonym)?

My vision for the future of bytestring and vector-bytestring is that
they will be replaced by vector directly. This way users don't have to
think about choosing between bytestring and vector and can go to
vector directly to work with Word8 vectors or interface with foreign
libraries.

This would mean moving some (bytestring only) functions from
vector-bytestring to vector like mapAccumL/R, create, createAndTrim,
etc. and generalizing them from Word8s to any Storable.

So in my vision there's no ByteString type anymore, just Vectors. The
vector-bytestring package is meant to make the transition smoother.

If there's need for a specific Show instance for Vectors of Word8s we
can always add one directly to vector. (Roman, what are your thoughts
on this?)

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Haskell] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-14 Thread Bas van Dijk
On 14 October 2011 14:01, Ertugrul Soeylemez e...@ertes.de wrote:
 Is there any particular reason to prefer storable vectors instead of
 unboxed vectors?  The element type is fixed to Word8 anyway.

To be able to safely interface with foreign libraries.

Note that unboxed vectors are represented as ByteArray#s. These are
unpinned which means that the GC can freely move them through the
heap to defragment your memory. If a foreign library had a pointer to
an unboxed vector and the GC would move the memory to some place else,
your program could crash. Storable vectors use a ForeignPtr instead
which (according how you allocated it) points to pinned memory.

You might like to follow the just created:

http://hackage.haskell.org/trac/ghc/ticket/5556

which proposes the pin# and unpin# primitives for dynamically pinning
and unpinning ByteArray#s. This way, as pumpkin explains it, you don't
have to decide up front whether you want to suffer from memory
fragmentation or to support foreign bindings.

It would be really nice if that could be implemented!

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-14 Thread Bas van Dijk
On 14 October 2011 13:37, Bas van Dijk v.dijk@gmail.com wrote:
 If there's need for a specific Show instance for Vectors of Word8s we
 can always add one directly to vector. (Roman, what are your thoughts
 on this?)

Ok I have proposed and implemented this for vector:

http://trac.haskell.org/vector/ticket/64

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lists concatenation being O(n)

2011-10-14 Thread Bas van Dijk
On 13 October 2011 20:53, Albert Y. C. Lai tre...@vex.net wrote:
 The number of new cons cells created in due course is Θ(length xs).

I was actually surprised by this because I expected: length(xs++ys) to
fuse into one efficient loop which doesn't create cons cells at all.

Unfortunately, I was mistaken since length is defined recursively.

length :: [a] - Int
length l =  len l 0#
  where
len :: [a] - Int# - Int
len [] a# = I# a#
len (_:xs) a# = len xs (a# +# 1#)

However, if we would define it as:

length = foldl' (l _ - l+1) 0

And implemented foldl' using foldr as described here:

http://www.haskell.org/pipermail/libraries/2011-October/016895.html

then fuse = length(xs++ys) where for example xs = replicate 100 1
and ys = replicate 5000 (1::Int) would compile to the following
totally fused core:

fuse :: Int
fuse = case $wxs 100 0 of ww_srS {
 __DEFAULT - I# ww_srS
   }

$wxs :: Int# - Int# - Int#
$wxs = \ (w_srL :: Int#) (ww_srO :: Int#) -
case =# w_srL 1 of _ {
  False - $wxs (-# w_srL 1) (+# ww_srO 1);
  True  - $wxs1_rs8 5000 (+# ww_srO 1)
}

$wxs1_rs8 :: Int# - Int# - Int#
$wxs1_rs8 =
  \ (w_srA :: Int#) (ww_srD :: Int#) -
case =# w_srA 1 of _ {
  False - $wxs1_rs8 (-# w_srA 1) (+# ww_srD 1);
  True  - +# ww_srD 1
}

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


  1   2   3   4   5   >