Re: [Haskell-cafe] partial inheritance

2011-07-19 Thread Maciej Piechotka
On Tue, 2011-07-19 at 10:43 +0200, Yves Parès wrote:
  I haven't followed the thread carefully but why does the bird have
 to be a penguin?
 
 A bird doesn't have to be a penguin :
 
 instance (Penguin b) = Bird b where
  fly = -- fly method for penguins
 
 Says that every Penguin is a Bird.
 But thinking back about it, there is a problem when trying to define
 the method walk, because:
 
 class Penguin p where
walkPenguin :: 
 
 instance (Penguin b) = Bird b where
 fly = .
 walk = walkPenguin
 
 is kind of awful, because walk has to be duplicated. So, not the best
 way to go...

Note to self: don't respond to ml after 2am. I saw instance but read
class.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Maybe use advice

2011-06-06 Thread Maciej Piechotka
On Tue, 2011-06-07 at 04:09 +0800, Lyndon Maydwell wrote:
 (missed including cafe)
 
 f :: [Modification] - Maybe [Modification]
 and
 f _ = Just $ f ...
 are incompatible
 


My bad:

f ... = let cs' = (Rotate (x+x') : fromMaybe cs (f cs))
in fromMaybe cs (f cs)

Or refactoring it:

g l = fromMaybe l (f l)

f (Rotatex   : Rotatex': cs) = g (Rotate (x+x') : g cs)

Regards

 I managed to get the behaviour I'm after with the use of Either, but
 this really is messy:
 
 
 -- Sets of changes
 o (Modifier (Changes [])  i) = Just $ i
 o (Modifier (Changes [c]) i) = Just $ Modifier c i
 o (Modifier (Changes l)   i) = g (f (Left l))
   where
 g (Right l) = Just $ Modifier (Changes l) i
 g (Left  l) = Nothing
 
 f (Left  (Scale x y : Scale x' y' : l)) =
 f $ Right $ Scale (x*x') (y*y') : h (f $ Left l)
 f (Left  (Translate x y : Translate x' y' : l)) =
 f $ Right $ Translate (x+x') (y+y') : h (f $ Left l)
 f (Left  (Rotatex   : Rotatex': l)) =
 f $ Right $ Rotate(x+x'): h (f $ Left l)
 f x = x
 
 h (Left  l) = l
 h (Right l) = l
 
 
 On Tue, Jun 7, 2011 at 3:11 AM, Maciej Marcin Piechotka
 uzytkown...@gmail.com wrote:
  On Mon, 2011-06-06 at 23:38 +0800, Lyndon Maydwell wrote:
  I'm writing an optimisation routine using Uniplate. Unfortunately, a
  sub-function I'm writing is getting caught in an infinite loop because
  it doesn't return Nothing when there are no optimisations left.
 
  I'd like a way to move the last Just into f, but this makes recursion
  very messy. I was wondering if there was a nice way to use something
  like the Monad or Applicative instance to help here.
 
  -- Sets of changes
  o (Modifier (Changes [])  i) = Just $ i
  o (Modifier (Changes [c]) i) = Just $ Modifier c i
  o (Modifier (Changes l)   i) = Just $ Modifier (Changes (f l)) i
where
  f (Scale x y : Scale x' y' : l) = f $ Scale (x*x') (y*y') 
  : f l
  f (Translate x y : Translate x' y' : l) = f $ Translate (x+x') (y+y') 
  : f l
  f (Rotatex   : Rotatex': l) = f $ Rotate(x+x')
  : f l
  f l = l
 
 
  Any ideas?
 
  Something like:
 
  ...
  f (Rotatex   : Rotatex': l)
 = Just $ f (Rotate (x+x') : fromMaybe l (f l))
  f l = Nothing -- As far as I understend
 
  Regards
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 




signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: iteratee-compress 0.2.0.0

2011-04-26 Thread Maciej Piechotka
On Mon, 2011-04-25 at 15:47 +0900, Conrad Parker wrote:
 On 23 April 2011 19:29, Maciej Piechotka uzytkown...@gmail.com wrote:
  Iteratee-compress provides compressing and decompressing enumerators
  including flushing (using John Lato's implementation). Currently only
  gzip and bzip is provided but LZMA is planned.
 
  Changes from previous version:
   - Add BZip support
 
 
 Cool :)
 
 I notice the haddocks on hackage have not been generated; would this
 be due to libbz2-dev missing on the hackage server?
 
 Conrad.

No - you need to wait as it is a batch process. Currently it is
up-to-date.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: iteratee-compress 0.2.0.0

2011-04-23 Thread Maciej Piechotka
Iteratee-compress provides compressing and decompressing enumerators
including flushing (using John Lato's implementation). Currently only
gzip and bzip is provided but LZMA is planned.

Changes from previous version:
 - Add BZip support

Next goals:
 - LZMA support
 - Generic interface for flushing

To think about:
 - Should inner iteratee be able to request flushing

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] There is no null; Maybe/Option types

2011-04-22 Thread Maciej Piechotka
On Fri, 2011-04-22 at 22:11 +0200, Henning Thielemann wrote:
 On Fri, 22 Apr 2011, Maciej Marcin Piechotka wrote:
 
  On Fri, 2011-04-22 at 21:26 +0200, Henning Thielemann wrote:
 
  In idiomatic Haskell you would write
 
  case userList of
  Nothing - Nothing
  Just plainUserList =
 let user = findUser bob plainUserList
 ...
 
  since (userList /= Nothing) requires an Eq instance without need and it
  requires fromJust. Or was there an educational purpose to write it with
  (/= Nothing) ?
 
  Using 'more advanced haskell'
 
  email = getEmail = findUser bob = userList
 
 This is what Christopher Done wrote some lines below the code, that I 
 quoted.

Ups. Sorry - I didn't have all the context.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHC 7.0.2 and haddock

2011-03-05 Thread Maciej Piechotka
On Sun, 2011-03-06 at 02:56 +0100, Daniel Fischer wrote:
 On Sunday 06 March 2011 02:34:58, Maciej Marcin Piechotka wrote:
  Is there any version of haddock that builds with ghc 7.0.2?
 
 The source tarball comes with 2.9.2, that built and works here. While 2.9.2 
 is not on hackage, you could try the darcs version.
 

Ok. Thanks.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] iteratee-compress space leak?

2011-02-20 Thread Maciej Piechotka
On Fri, 2011-02-18 at 17:27 +0300, Michael A Baikov wrote:
 I am trying to play with iteratee making parser for squid log files, but 
 found that my code do not run in constant space when it tries to process 
 compressed log files. So i simplified my code down to this snippet:
 
 import Data.ByteString (ByteString)
 import Data.Iteratee as I
 import Data.Iteratee.Char
 import Data.Iteratee.ZLib
 import System
 
 main = do
 args - getArgs
 let fname = args !! 0
 let blockSize = read $ args !! 1
 
 fileDriver (leak blockSize) fname = print
 
 leak :: Int - Iteratee ByteString IO ()
 leak blockSize = joinIM $ enumInflate GZip defaultDecompressParams chunkedRead
 where
 consChunk :: Iteratee ByteString IO String
 consChunk = (joinI $ I.take blockSize I.length) = return . show
 
 chunkedRead :: Iteratee ByteString IO ()
 chunkedRead = joinI $ convStream consChunk printLines
 
 
 First argument - file name (/var/log/messages.1.gz will do)
 second - size of block to consume input. with low size (10 bytes) of consumed 
 blocks it leaks very fast, with larger blocks (~1) it works almost 
 without leaks.
 
 So. Is it bugs within my code, or iteratee-compress should behave differently?

After looking into problem (or rather onto your code) - the problem have
nothing to do with iteratee-compress I believe. I get similar behaviour
and results when I replace joinIM $ enumInflate GZip
defaultDecompressParams chunkedRead by chunkedRead. (The memory is
smaller but it is due to decompression not iteratee fault).

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] iteratee-compress space leak?

2011-02-18 Thread Maciej Piechotka
On Fri, 2011-02-18 at 17:27 +0300, Michael A Baikov wrote:
 I am trying to play with iteratee making parser for squid log files, but 
 found that my code do not run in constant space when it tries to process 
 compressed log files. So i simplified my code down to this snippet:
 
 import Data.ByteString (ByteString)
 import Data.Iteratee as I
 import Data.Iteratee.Char
 import Data.Iteratee.ZLib
 import System
 
 main = do
 args - getArgs
 let fname = args !! 0
 let blockSize = read $ args !! 1
 
 fileDriver (leak blockSize) fname = print
 
 leak :: Int - Iteratee ByteString IO ()
 leak blockSize = joinIM $ enumInflate GZip defaultDecompressParams chunkedRead
 where
 consChunk :: Iteratee ByteString IO String
 consChunk = (joinI $ I.take blockSize I.length) = return . show
 
 chunkedRead :: Iteratee ByteString IO ()
 chunkedRead = joinI $ convStream consChunk printLines
 
 
 First argument - file name (/var/log/messages.1.gz will do)
 second - size of block to consume input. with low size (10 bytes) of consumed 
 blocks it leaks very fast, with larger blocks (~1) it works almost 
 without leaks.
 
 So. Is it bugs within my code, or iteratee-compress should behave differently?

It may be a bug - I'll look into it. 

Regards

PS. Please CC me and/or just send e-mail to me - I may miss mails to the
cafe list but I won't miss (or rather it by several orders of magnitude
less likely) anything that is sent to me


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: nanoparsec 0.1.1

2011-01-30 Thread Maciej Piechotka
Nanoparsec is currently simply a port of attoparsec on the ListLike (the
abstraction of lists used by iteratee).

It allows to achive in parsing a near-attoparsec levels of speed
(benchmarks from attoparsec library shown a 0.450 ± 0.028 for
attoparsec, 0.479 ± 0.043 for nanoparsec and 1.532 ± 0.084 for parsec 3)
combining the flexibility of stream of parsec 3 with the iterative
approach and speed of attoparsec.

Changes since version 0.1:
 - Lowered conditions on base to allow using GHC 6.12.x (haven't been
tested)
 - Added IsString instance and (.*) (*.) helper functions

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: nanoparsec 0.1.1

2011-01-30 Thread Maciej Piechotka
On Sun, 2011-01-30 at 13:13 -0200, Felipe Almeida Lessa wrote:
 On Sun, Jan 30, 2011 at 1:03 PM, Maciej Piechotka uzytkown...@gmail.com 
 wrote:
  It allows to achive in parsing a near-attoparsec levels of speed
  (benchmarks from attoparsec library shown a 0.450 ± 0.028 for
  attoparsec, 0.479 ± 0.043 for nanoparsec and 1.532 ± 0.084 for parsec 3)
  combining the flexibility of stream of parsec 3 with the iterative
  approach and speed of attoparsec.
 
 Nice!  How does it compare to attoparsec-text performance-wise?


I haven't checked. So far there are specializations for ByteString but
not Text. I would expect similar penalty for it anyway (I'll try to port
tests and report values).

 Although I'm its maintainer, duplicating libraries isn't funny =).
 

Deduplication was a goal of the nanoparsec. Most of the code and
documentation is from attoparsec anyway.

 Cheers,
 

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GPL License of H-Matrix and prelude numeric

2011-01-28 Thread Maciej Piechotka
On Thu, 2011-01-27 at 19:36 -0500, wren ng thornton wrote:
 On 1/27/11 2:21 PM, Maciej Piechotka wrote:
  On Thu, 2011-01-27 at 00:45 -0500, wren ng thornton wrote:
  On 1/26/11 5:51 AM, Maciej Piechotka wrote:
  Some projects (like Linux) remove this clause and I'm not sure how many
  projects are marked on hackage as GPL2 being GPL2-only.
 
  Technically GPLx and GPLy are incompatible for all x and y such that x
  /= y.The problem is that *technically* the phrasing of the viral clause
  prohibits dual licensing, despite the obvious intention.
 
  Could you elaborate? I cannot see any problem why author, having all
  rights, cannot publish code under GPL-2 and MPL. Sure GPL-2 allows
  someone to fork it into single-licence fork.
 
 IANAL, but that is the synopsis that was given to me by and old friend 
 who was. ISTR that the FSF may have a page on the matter too (circa how 
 to upgrade to GPL3 pages), though I'm loo lazy to look for it now.
 
 The problem is in the exact wording of how the viral clause is phrased, 
 which is somewhat at odds with the intention. Basically, if you license 
 your work under GPL2, and someone else wants to use it in a derivative 
 work, then they must distribute the composite work under GPL2. All well 
 and good, since this is the intention of the viral clause. However, 
 copyright law doesn't have any built-in notion of versioning. So if 
 you distribute your work as GPL2 and someone does some derivative work 
 that they want to distribute as GPL3, then technically they must 
 distribute the composite work under the *joint* license (GPL2  GPL3); 
 however, since parts of the GPL3 were specifically written as bugfixes 
 to the GPL2, this means the joint license is inconsistent and so noone 
 can simultaneously adhere to both of them, so the composite work cannot 
 be (non-vacuously) distributed.
 
 Conversely, if your work was distributed as GPL2+ then you are providing 
 a disjunction of licenses for users to choose from. The person making 
 their derivative work would be free to choose the GPL3 (or GPL3+) 
 license(s) for their use of your work, and this is clearly compatible 
 with their own GPL3 (or GPL3+) license, so the composite work can be 
 released under GPL3  GPL3 == GPL3 (or GPL3+  GPL3+ == GPL3+, or 
 GPL3+  GPL3 == GPL3,...)
 
 If you're familiar with linear logic, this is basically the same kind of 
 differentiation between multiplicative and additive conjunction.
 


Sorry - I misunderstood you. Dual licensing corresponds in my mind to ||
not . I.e. program dual-licensed on MPL and GPL-2 is (MPL || GPL-2)
and user can choose to which license he wants to adhere. I believe
similar nomenclature is used on Wikipedia.

The problem you are describing corresponds to compatibility and, of
course, GPL-2 and GPL-3 are not compatible (I believe that GPL-2+ 
GPL-3+ == GPL-3+).

  I'm not sure about the interpretation (and IANAL) but I'm not entirely
  sure if GPLx+ and GPLx-only are compatible at all.
 
 If one project is released under GPL version x (or, at your option, any 
 later version) and the other is released under GPL version x (only), 
 then the composite work can satisfy both by being released under GPL 
 version x (only), since they have the option to choose GPL version x 
 as their license for the first project.
 
 It's only a problem when x-only is not in the range of y+.
 

Sorry - my concerns were unbased. I reread licences and found answer in
point 9 (GPL-2) and 14 (GPL-3). 

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GPL License of H-Matrix and prelude numeric

2011-01-26 Thread Maciej Piechotka
On Tue, 2011-01-25 at 22:21 -0800, John Millikin wrote:
 On Tue, Jan 25, 2011 at 22:14, Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com wrote:
  However, my understanding that this property is then transitive: if
  Foo is GPL, Bar depends on Foo and Baz depends on Bar, then Baz must
  also be released under a GPL-compatible license.
 
 It's not really a must, just a matter of practicality.
 
 If you compile/link together code with incompatible licenses (BSD4 +
 GPL, GPL2-only + GPL3-only) then the resulting binary can't be legally
 distributed for any reason (because doing so would violate at least
 one of the licenses). You can still license the source code however
 you want, and distribute it; the problem is only for binaries.

The text of GPL-2 and GPL-3 at least have note about upgrading so GPL-2
program can be relicensed into GPL-3. ANAL but I think the legal
framework of US makes it relatively safe (status of FSF prevents it from
'being evil').

Some projects (like Linux) remove this clause and I'm not sure how many
projects are marked on hackage as GPL2 being GPL2-only.

Regards

PS. I may be wrong but on the first sight GPLx and GPLx-only seems to be
noncompatible. 


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GPL License of H-Matrix and prelude numeric

2011-01-26 Thread Maciej Piechotka
On Wed, 2011-01-26 at 08:11 +0100, Ketil Malde wrote:
 David Leimbach leim...@gmail.com writes:
 
  BSD3 doesn't really state anything about what it links with, but the
 GPL
  injects itself into the tree of stuff it's linked with via the
 derivative
  works clause.  
 
 I'm not an IP lawyer either (thank God), but merely using a published
 interface does not make it a derivative work.  So IMO there's no
 problem
 with a GPL library making use of a BSD library, nor vice versa - just
 like I can write a BSD program and run it on (GPL'ed) Linux and libc. 

In addition to Chris Smith reply please note that system interfaces (to
which Linux syscalls and libc belongs according to FSF) are explicitly
excluded IIRC.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proposal: Applicative = Monad: Call for consensus

2011-01-25 Thread Maciej Piechotka
On Mon, 2011-01-24 at 20:13 -0800, Ryan Ingram wrote:
 On Fri, Jan 21, 2011 at 7:58 PM, Casey Hawthorne cas...@istar.ca wrote:
  uj supplied this:
 
  About the discussion
  putStrLn (readLn + (5 :: Int))..
 
  I'll write it as the following line,
 
  importing Control.Applicative
  main = (+) readLn (return 3)
 
  They look almost exactly same in my eyes..
 
 You're missing some bits.
 
 main = print = liftM2 (+) readLn (return 3)
 
 Which I assert looks like more line noise than some perl programs I've read. 
 :)
 

Or using idiom brackets (for example from SHE):

main = print = (| readLn + ~3 |)

or

main = (| print (| readLn + ~3 |) @|)

Regards



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proposal: Applicative = Monad: Call for consensus

2011-01-25 Thread Maciej Piechotka
On Tue, 2011-01-25 at 12:17 +0100, Gábor Lehel wrote:
 On Tue, Jan 25, 2011 at 10:20 AM, Ketil Malde ke...@malde.org wrote:
  Erik Hesselink hessel...@gmail.com writes:
 
  importing Control.Applicative
 
  main = print = liftM2 (+) readLn (return 3)
  [...] line noise
 
  Why not just:
 
  main = print . (+3) = readLn
 
  Or using applicative:
 
   print = (+3) $ readLn
 
  ?
 
  (Which separates the printing from the addition.)
 
  -k
 
 IMHO, all these proposed solutions just serve to further illustrate
 the problem. :-)
 

Even SHE?

main = (| print (| readLn + ~5 |) @|)

int main () {
print (%d\n, readLn () + 5);
}

Looks rather similar (except noise of both languages).

 Personally I don't mind having to use explicit combinators to interact
 with monadic values -- forces me to think things through, and all that
 -- but it's true that having automatic lifting would be convenient,
 and look less syntaxy. 

class Debug m where
debug :: Show a = m a - m a

instance Debug (Writer [String]) where
debug x = tell (show x)

instance Debug IO where
debug = print

instance (Show w, Show a) = Show (Writer w) where
-- Yes I'm using old mtl to illustrate the problem
show (Writer (a, w)) = Writer ( ++ show a ++ ,  ++ show w ++ )

main = debug (return (return ())) * return ()

What does it do?

- In case of no lifting it prints Writer ((), [])
- In case of lifting it may mean debug $ return (return ()) which
would not print anything

Regards



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Is SHE (the Strathclyde Haskell Enhancement) portable?

2011-01-23 Thread Maciej Piechotka
It may be strange question but:

 - Is SHE portable (assuming that the compiler have the extensions)?
 - If yes why there is only information how to use it with GHC?

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is SHE (the Strathclyde Haskell Enhancement) portable?

2011-01-23 Thread Maciej Piechotka
On Sun, 2011-01-23 at 18:42 +0100, Lennart Augustsson wrote:
 It probably is portable, but I'd think only GHC has all the necessary
 extensions.

I imagine some parts (idiom brackets) works with minimal amount of
extentions - maybe it would be benefitial to have instructions to run
SHE with other compilers?

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] parsec2 vs. parsec3... again

2011-01-13 Thread Maciej Piechotka
On Wed, 2011-01-12 at 18:15 -0800, Evan Laforge wrote:
 On Mon, Dec 27, 2010 at 6:51 AM, Evan Laforge qdun...@gmail.com
 wrote:
  I've uploaded attoparsec-text and attoparsec-text-enumerator to
  Hackage.  I've written those packages late last week and asked for
 
  Very nice!  I'll download this and try it out.  Attoparsec has a bit
  different combinators than parsec so it'll take some rewriting, but
  it's work I'd have to do anyway to try the bytestring+attoparsec
  approach.
 
 Well, I tried it... and it's still slower!
 
 parsec2, String: (a little faster since last time since I have new
 computer)
 total time  =9.10 secs   (455 ticks @ 20 ms)
 total alloc = 2,295,837,512 bytes  (excludes profiling
 overheads)
 
 attoparsec-text, Data.Text:
 total time  =   14.72 secs   (736 ticks @ 20 ms)
 total alloc = 2,797,672,844 bytes  (excludes profiling
 overheads) 

Sorry for asking but just for reference - what is performance of
nanoparsec on your machine in this test?

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: nanoparsec 0.1

2011-01-10 Thread Maciej Piechotka
On Sun, 2011-01-09 at 16:54 +, Magnus Therning wrote:
 On 09/01/11 00:46, Maciej Piechotka wrote:
  Nanoparsec is currently simply a port of attoparsec on the ListLike (the
  abstraction of lists used by iteratee).
  
  It allows to achive in parsing a near-attoparsec levels of speed
  (benchmarks from attoparsec library shown a 0.450 ± 0.028 for
  attoparsec, 0.479 ± 0.043 for nanoparsec and 1.532 ± 0.084 for parsec 3)
  combining the flexibility of stream of parsec 3 with the iterative
  approach and speed of attoparsec.
 
 It's a bit unfortunate that it requires base 4.3, GHC 7 hasn't made it
 into a lot of distros yet so that causes a lot of extra work when
 wanting to try it out :-(
 
 /M

I'll fix it in next release.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: nanoparsec 0.1

2011-01-08 Thread Maciej Piechotka
Nanoparsec is currently simply a port of attoparsec on the ListLike (the
abstraction of lists used by iteratee).

It allows to achive in parsing a near-attoparsec levels of speed
(benchmarks from attoparsec library shown a 0.450 ± 0.028 for
attoparsec, 0.479 ± 0.043 for nanoparsec and 1.532 ± 0.084 for parsec 3)
combining the flexibility of stream of parsec 3 with the iterative
approach and speed of attoparsec.

Regards 


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] getting last char of String

2011-01-01 Thread Maciej Piechotka
On Sat, 2011-01-01 at 19:27 +1100, Jesse Schalken wrote:
 
 On Sat, Jan 1, 2011 at 8:54 AM, Felipe Almeida Lessa
 felipe.le...@gmail.com wrote:
 On Fri, Dec 31, 2010 at 6:43 PM, aditya siram
 aditya.si...@gmail.com wrote:
  -- untested and won't work on an infinite list
  last :: [a] - a
  last = head . reverse
 
 
 No definition for last works with infinite lists =). 
 
 
 Unless you make the result nullable, of course.
 
 
 maybeLast :: [a] - Maybe a
 
 maybeLast [] = Nothing
 maybeLast [x] = Just x
 maybeLast (_:xs) = maybeLast xs
 

It may or may not be expected but it may also be written as:

maybeLast' [] = Nothing
maybeLast' (x:xs) = Just (fromMaybe x (maybeLast xs))

The main differences are:

maybeLast  (x:_|_) = _|_
maybeLast' (x:_|_) = Just _|_

maybeLast  (fix (x:)) = _|_
maybeLast' (fix (x:)) = Just _|_

Regards



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] getting last char of String

2011-01-01 Thread Maciej Piechotka
On Sat, 2011-01-01 at 19:27 +1100, Jesse Schalken wrote:
 
 On Sat, Jan 1, 2011 at 8:54 AM, Felipe Almeida Lessa
 felipe.le...@gmail.com wrote:
 On Fri, Dec 31, 2010 at 6:43 PM, aditya siram
 aditya.si...@gmail.com wrote:
  -- untested and won't work on an infinite list
  last :: [a] - a
  last = head . reverse
 
 
 No definition for last works with infinite lists =). 
 
 
 Unless you make the result nullable, of course.
 
 
 maybeLast :: [a] - Maybe a
 
 maybeLast [] = Nothing
 maybeLast [x] = Just x
 maybeLast (_:xs) = maybeLast xs
 

It may or may not be expected but it may also be written as:

maybeLast' [] = Nothing
maybeLast' (x:xs) = Just (fromMaybe x (maybeLast xs))

The main differences are:

maybeLast  (x:_|_) = _|_
maybeLast' (x:_|_) = Just _|_

maybeLast  (fix (x:)) = _|_
maybeLast' (fix (x:)) = Just _|_

Regards



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] getting last char of String

2011-01-01 Thread Maciej Piechotka
On Sat, 2011-01-01 at 19:27 +1100, Jesse Schalken wrote:
 
 On Sat, Jan 1, 2011 at 8:54 AM, Felipe Almeida Lessa
 felipe.le...@gmail.com wrote:
 On Fri, Dec 31, 2010 at 6:43 PM, aditya siram
 aditya.si...@gmail.com wrote:
  -- untested and won't work on an infinite list
  last :: [a] - a
  last = head . reverse
 
 
 No definition for last works with infinite lists =). 
 
 
 Unless you make the result nullable, of course.
 
 
 maybeLast :: [a] - Maybe a
 
 maybeLast [] = Nothing
 maybeLast [x] = Just x
 maybeLast (_:xs) = maybeLast xs
 

It may or may not be expected but it may also be written as:

maybeLast' [] = Nothing
maybeLast' (x:xs) = Just (fromMaybe x (maybeLast xs))

The main differences are:

maybeLast  (x:_|_) = _|_
maybeLast' (x:_|_) = Just _|_

maybeLast  (fix (x:)) = _|_
maybeLast' (fix (x:)) = Just _|_

Regards



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] parsec2 vs. parsec3... again

2010-12-24 Thread Maciej Piechotka
On Thu, 2010-12-23 at 18:38 +0200, Michael Snoyman wrote:
 On Thu, Dec 23, 2010 at 6:21 PM, Johan Tibell johan.tib...@gmail.com wrote:
  On Thu, Dec 23, 2010 at 3:03 PM, Felipe Almeida Lessa
  felipe.le...@gmail.com wrote:
  Michael Snoyman wants attoparsec-text as well [1].
 
  [1] http://docs.yesodweb.com/blog/wishlist/
 
  It's on my Christmas wishlist too.
 
  Johan
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
 Since I'm sure everyone is thinking it at this point, I'll just say
 it: we're all hoping Bryan O'Sullivan saves the day again and writes
 this package. He wrote both attoparsec *and* text, so if he writes
 attoparsec-text, it will just be double the awesomeness. So Bryan,
 please do tell: how many beers (or any other consumable) will it take
 to get you to write it? I'll start up the collection fund, and throw
 in a six pack ;).
 
 Michael

I may be wrong but the attoparsec/attoparsec-text would be operating on
the same principles. Maybe using typeclass like Data.ListLike would be
solution?

I'd not quite sure how much would it slow down but it should be
possible.

More as proof of concept reimplementation of string parser (for real
life probably needs INLINE and SPECIALISE):

 import Control.Applicative
 import Control.Monad
 import Data.Monoid
 import Data.ListLike as LL
 
 data Result i r
 = Fail !i [String] String
 | Partial (i - Result i r)
 | Done !i r
 
 newtype Parser i a
 = Parser { runParser :: forall r. S i
  - Failure i   r
  - Success i a r
  - Result  i   r }
 
 type Failure i   r = S i - [String] - String - Result i r
 type Success i a r = S i - a - Result i r
 
 data More = Complete | Incomplete deriving (Eq, Show)
 
 instance Monoid More where
 mempty  = Incomplete
 mappend Complete _= Complete
 mappend _Complete = Complete
 mappend __= Incomplete
 
 data S i = S { input :: !i, _added :: !i, more :: !More }
 
 instance Functor (Parser i) where
 fmap p m = Parser (\st0 f k - runParser m st0 f (\s a - k s (p
a)))
 
 instance Applicative (Parser i) where
 pure x = Parser (\st0 _ ks - ks st0 x)
 (*) = ap
 
 instance Monad (Parser i) where
 return = pure
 m = g
 = Parser (\st0 kf ks - runParser m st0 kf (\s a - runParser
(g a) s kf ks))
 fail err = Parser (\st0 kf _ - kf st0 [] err)
 
 string :: (Eq full, LL.ListLike full item) = full - Parser full full
 string s = takeWith (LL.length s) (== s)
 
 takeWith :: (LL.ListLike full item) = Int - (full - Bool) - Parser
full full
 takeWith n p = do
 ensure n
 s - get
 let (h, t) = LL.splitAt n s
 if p h then put t  return h else fail takeWith
 
 ensure :: (LL.ListLike full item) = Int - Parser full ()
 ensure n
 = Parser $ \st0@(S s0 _a0 _c0) kf ks -
 if LL.length s0 = n
 then ks st0 ()
 else runParser (demandInput  ensure n) st0 kf ks
 
 prompt :: LL.ListLike i ii
= S i - (S i - Result i r) - (S i - Result i r) - Result
i r
 prompt (S s0 a0 _) kf ks
 = Partial $ \s -
 if LL.null s
 then kf $! S s0 a0 Complete
 else ks $! S (s0 `mappend` s) (a0 `mappend` s) Incomplete
 
 demandInput :: (LL.ListLike full item) = Parser full ()
 demandInput
 = Parser $ \st0 kf ks -
 if more st0 == Complete
 then kf st0 [demandInput] not enough bytes
 else prompt st0 (\st - kf st [demandInput] not enough
bytes) (`ks` ())
 
 get :: Parser full full
 get = Parser (\st0 _ ks - ks st0 (input st0))
 
 put :: full - Parser full ()
 put s = Parser (\(S _ a0 c0) _ ks - ks (S s a0 c0) ())



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] (Co/Contra)Functor and Comonad

2010-12-24 Thread Maciej Piechotka
On Fri, 2010-12-24 at 05:36 -0500, Edward Kmett wrote:
 
 +1 for adding Comonads. As an aside, since Haskell doesn't have (nor
 could it have) coexponential objects, there is no 'missing'
 Coapplicative concept that goes with it, so there can be no objection
 on the grounds of lack of symmetry even if the Functor = Applicative
 = Monad proposal goes through.  

There is still potentially useful Copointed/CoPointed:

class [Functor a =] CoPointed a where
copoint :: f a - a

Regards



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] UTF-8 in Haskell.

2010-12-23 Thread Maciej Piechotka
On Thu, 2010-12-23 at 14:15 +0800, Magicloud Magiclouds wrote:
 On Thu, Dec 23, 2010 at 2:01 PM, Mark Lentczner ma...@glyphic.com wrote:
 
  On Dec 22, 2010, at 9:29 PM, Magicloud Magiclouds wrote:
  Thus under all situation (ascii, UTF-8, or even
  UTF-32), my program always send 4 bytes through the network. Is that
  OK?
 
  Generally, no.
 
  Haskell strings are sequences of Unicode characters. Each character has an 
  integral code point value, from 0 to 0x10, but technically, the code 
  point itself is just a number, not a pattern of bits to be exchanged. That 
  is an encoding.
 
  In any protocol you need know the encoding before you exchange characters 
  as bytes or words. In some protocols it is implicit, in others explicit in 
  header or meta data, and in yet others (IRC comes to mind) it is undefined 
  (which makes problems for the user).
 
  The UTF-8 encoding uses a variable number of bytes to represent each 
  character, depending on the code point, not Word32 as you suggested.
 
  Converting from Haskell's String to various encodings can be done with 
  either the text package or utf8-string package.
 
 - Mark
 
 I see. I just realize that, in this case (ssh), I could use CString to
 avoid all problems about encoding.
 

By using CString you may avoid problems by putting them on users.
CString is char * and Foreign marshaling just use ASCII. And as non only
English speaking user of computer programs I ask to have support of
unicode (for example utf-8). Unless you mean only commands, not data, in
which you probably should check details of protocol.

In any case I don't think that CString is correct approach to network
data and you probably should use ByteString in place of CString.

Regards



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Haskell] Functor = Applicative = Monad

2010-12-15 Thread Maciej Piechotka
On Wed, 2010-12-15 at 13:51 +0200, John Smith wrote:
 On 15/12/2010 11:39, Lennart Augustsson wrote:
  Any refutable pattern match in do would force MonadFail (or MonadPlus if 
  you prefer).  So
  1.  (MonadFail m) = a - m a,   \ a - return a
  2.  (MonadFail m) = m a,   mfail ...
  3.  (MonadFail m) = Maybe a - m a,   \ a - case a of Nothing - mfail 
  ...; Just x - return x
  4.  (Monad m) = a - b - m a,   \ a b - return a
  5.  (Monad m) = (a, b) - m a,   \ (a, b) - return a
 
  As far as type inference and desugaring goes, it seems very little would 
  have to be changed in an implementation.
 
 Is there a need for a MonadFail, as distinct from mzero? fail always seems to 
 be defined as error in ordinary monads, 
 and as mzero in MonadPlus (or left at the default error).

Not all types can implement mplus to begin with even if they can have
'zero' type. For example technically Maybe breaks the laws while still
having useful fail:

(guard . even) = (Just 1 | Just 2)
(guard . even) = Just 1
guard (even 1)
guard False
Nothing
/=
Just ()
Nothing | Just ()
guard False | guard True
(guard (even 1)) | (guard (even 2))
((guard . even) = Just 1) | ((guard . even) = Just 2)

Regards



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Rendering of hask in new wiki (MSIE6)

2010-12-15 Thread Maciej Piechotka
On Wed, 2010-12-15 at 09:01 -0500, Dimitry Golubovsky wrote:
 Hi,
 
 In MSIE6, hask tags are rendered like this (from the Monad_Transformers 
 page):
 
 transformers: provides the classes
 MonadTrans
 and
 MonadIO
 , as well as concrete monad transformers such as
 StateT
 
 ... etc.
 
 The Wiki source:
 
 [http://hackage.haskell.org/package/transformers transformers]:
 provides the classes haskMonadTrans/hask and haskMonadIO/hask,
 as well as concrete monad transformers such as haskStateT/hask.
 
 HTML (a small piece of it):
 
 provides the classes div class=inline-codediv dir=ltr
 style=text-align: left;div class=source-haskell
 style=font-family: monospace;MonadTrans/div/div/div
 
 Words MonadTrans, MonadIO, StateT etc are enclosed in hask tags.
 They show up in monospace, each starting a new line. Is this only
 MSIE6, or this is how it is supposed to render?
 
 Thanks.
 
 PS I am not attaching a screenshot to the mailing list; if anyone
 needs to see it I'll send via personal e-mail.
 

In epiphany (webkit) it displays OK. 

You can always test on pages like
http://browsershots.org/http://haskell.org/haskellwiki/Monad_Transformers

In general I'd say that MSIE should be avoided and updated to newer
version like 7 or 8 (according to wikipedia they should be avaible for
Windows XP - or at least they were available when Windows XP was
supported) - IE6 have technology from 2001. I understand however that it
may be outside your control (maybe portable Fx would be solution?)

Regards

PS. BTW - does anyone have statistics on browser share on Haskell site?
According to Wikipedia IE6 have still around 16% market share but I
guess it is lower here.


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Rendering of hask in new wiki (MSIE6)

2010-12-15 Thread Maciej Piechotka
On Wed, 2010-12-15 at 17:56 +, Neil Mitchell wrote:
 Hi
 
  In general I'd say that MSIE should be avoided and updated to newer
  version like 7 or 8 (according to wikipedia they should be avaible for
  Windows XP - or at least they were available when Windows XP was
  supported) - IE6 have technology from 2001. I understand however that it
  may be outside your control (maybe portable Fx would be solution?)
 
 I strongly agree that MSIE 6 should be avoided, but for many company
 networks it's required. The big problem isn't that 16% (or whatever)
 of people use it, it's that while technical people will use a modern
 and powerful browser, many non-technical managers will just use the
 default settings/systems, and it gives a bad impression if when told
 that Haskell is a great tool a manager looks up haskell.org and sees
 a messy splat.
 
 For reference, the new Haddock style also gives various rendering
 issues in IE6. I reported these a while back (to Mark) but never got
 any response.
 
 Thanks, Neil

I cannot speak for anyone but from what I remember supporting MSIE is
neither trivial nor fan. If you happen to use newer version of IE or
even different operating system (if I remember correctly most of Haskell
users use GNU/Linux) then you have bad luck - you have to use other
tools like virtual machines etc. - only to find out that you have not
been visited once by IE 6.

I'm not sure how many changes are going to be commited into haddock
backend/themes but once ported it would need to be maintained. 

Regards



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] dot-ghci files

2010-12-11 Thread Maciej Piechotka
On Thu, 2010-12-09 at 14:01 -0500, Albert Y. C. Lai wrote:
 On 10-12-09 01:57 PM, Claus Reinke wrote:
  Perhaps ghc should also ignore all group-writable *.hs, *.lhs, *.c,
  *.o, *.hi files.
 
  dot-ghci files are *run* if you just start ghci (or ghc -e) in that
  directory
  (even if you don't intend to compile, load, or run any Haskell code).
 
 Haskell developers don't just run ghci. They go ahead to run arbitrary 
 Haskell code too.

On the other hand - code that they likely just seen. On the other
hand .ghci file may not have been even noticed. It makes it much lower
risk.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] dot-ghci files

2010-12-11 Thread Maciej Piechotka
On Thu, 2010-12-09 at 17:01 +1000, Tony Morris wrote:
 I teach haskell quite a lot. I recommend using .ghci files in projects.
 Today I received complaints about the fact that ghci will reject .ghci
 if it is group-writeable. I didn't offer an opinion on the matter. I am
 wondering if these complaints have legitimate grounds i.e. maybe you
 want to have group write on that file for some reason.
 
 I'd appreciate some comments on this issue. Thanks.
 

While I may not understend setting it may be possible to set a
repository in shared directory (like git, svn or darcs) and use
non-group-writable copies to actual work.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: mime-mail 0.1.0

2010-12-09 Thread Maciej Piechotka
On Thu, 2010-12-09 at 11:53 +0200, Michael Snoyman wrote:
 On Thu, Dec 9, 2010 at 11:48 AM, Magnus Therning mag...@therning.org wrote:
  On Wed, Dec 8, 2010 at 19:11, Michael Snoyman mich...@snoyman.com wrote:
  Hi all (again),
 
  I'm happy to announce the second major release of the mime-mail[1]
  package. mime-mail is a package providing support for rendering
  multipart emails. This new release introduces:
 
  Very nice!  Are you working on a parser to accompany the renderer? ;-)
 
  /M
 
 
 I'm not currently, though that is definitely a direction the project
 could expand to. I've already written some multipart-parsing code in
 wai-extra, though that code probably wouldn't help here too much. The
 quoted-printable decoding is simple enough to write, and
 base64-decoding has already been solved. Is this a challenge anyone
 out there wants to undertake?
 
 Michael

Hmm. Probably no. I wanted to write a proper parser for MIME for nntp
package but I gave up in the middle of RFC and concentrated on more
interesting problems.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: mime-mail 0.1.0

2010-12-08 Thread Maciej Piechotka
On Wed, 2010-12-08 at 21:11 +0200, Michael Snoyman wrote:
 Hi all (again),
 
 I'm happy to announce the second major release of the mime-mail[1]
 package. mime-mail is a package providing support for rendering
 multipart emails. This new release introduces:
 
 * A partHeaders record, allowing you to place arbitrary headers on
 individual parts of a message. This is especially useful for ContentID
 * Support for quoted-printable. There are two new Encoding
 constructors added: QuotedPrintableText and QuotedPrintableBinary.
 They differ in how they treat newline characters: the latter outputs
 CRs and LFs in an escaped form, while the former strips all CRs and
 outputs LFs as the ASCII codes for \r\n.
 * Support for encoded-word for header values. This is a completely
 transparent change: now if you use non-ASCII characters in your header
 values, mime-mail will automatically encode appropriately.
 
 Enjoy!
 Michael
 
 [1] http://hackage.haskell.org/package/mime-mail

Sorry I'm asking here (I know it is slightly off-topic) - does anyone
knows package to parse MIME messages operating on ByteString/Text
instead of String (reverse of mime-mail)?

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Hackage have ghc 7.0 false positives builds

2010-12-05 Thread Maciej Piechotka
Hackage seems to hae false positive builds. For example llvm is reported
to have been built with ghc despite problems with cabal (type errors and
after quick'n'dirty fix it has errors).

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Transparent identity instances

2010-11-29 Thread Maciej Piechotka
On Sun, 2010-11-28 at 22:59 +0800, Jafet wrote:
  {-# LANGUAGE TypeSynonymInstances #-}
  type Identity a = a
  instance Applicative Identity where
-- something like
pure a = a
f * a = f a
 
 But GHC does not accept type synonym instances unless they are fully
 applied.
 
 Is it sound for such an instance to exist? If so, how might it be
 defined? 

 data Tag a = Tag

 instance Applicative Tag where
 pure _ = Tag
 Tag * Tag = Tag

 cast :: Tag a - Tag b
 cast Tag = Tag

1. pure id * Tag = Tag

2. I'm too lazy to prove it

3. pure f * pure x = Tag * Tag = Tag = pure (f x)

4. u * pure y = u * Tag = u = Tag * u = pure ($ y) * u

 x = pure undefined
 y = x :: Tag ()

Is y defined?

pure!Tag undefined = Tag
pure!Identity undefined = undefined

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: iteratee-compress 0.1.2

2010-11-28 Thread Maciej Piechotka
Iteratee-compress provides compressing and decompressing enumerators
including flushing. Currently only gzip is provided but at bzip and LZMA
are planned.

This is bug-fixing release

Changes from previous version:
 - Fix infinite loop/segfault bug
 - Fix bug in which part of the output was lost

Next goals:
 - BZip support
 - LZMA support
 - Generic interface for flushing

To think about:
 - Should inner iteratee be able to request flushing?

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: iteratee-compress 0.1.2

2010-11-28 Thread Maciej Piechotka
Iteratee-compress provides compressing and decompressing enumerators
including flushing. Currently only gzip is provided but at bzip and LZMA
are planned.

This is bug-fixing release

Changes from previous version:
 - Fix infinite loop/segfault bug
 - Fix bug in which part of the output was lost
 - Support for iteratee 0.5 and 0.6

Next goals:
 - BZip support
 - LZMA support
 - Generic interface for flushing

To think about:
 - Should inner iteratee be able to request flushing?

Regards



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: iteratee-parsec 0.0.6

2010-11-28 Thread Maciej Piechotka
Iteratee-parsec is a library which allows to have a parsec (3) parser in
Iteratee monad.

It contains 2 implementations:
- John Lato's on public domain. It is based on monoid and design with
short parsers in mind.
- Mine on MIT. It is based on single-linked mutable list. It seems to be
significantly faster for larger parsers - at least in some cases - but
it requires a monad with references (such as for example IO or ST).

The version 0.0.6 uses reference library.

Regards



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: ANNOUNCE: iteratee-compress 0.1.2

2010-11-28 Thread Maciej Piechotka
On Sun, 2010-11-28 at 15:24 +, Maciej Piechotka wrote:
 Iteratee-compress provides compressing and decompressing enumerators
 including flushing. Currently only gzip is provided but at bzip and LZMA
 are planned.
 
 This is bug-fixing release
 
 Changes from previous version:
  - Fix infinite loop/segfault bug
  - Fix bug in which part of the output was lost
  - Support for iteratee 0.5 and 0.6
 
 Next goals:
  - BZip support
  - LZMA support
  - Generic interface for flushing
 
 To think about:
  - Should inner iteratee be able to request flushing?
 
 Regards

I'm sorry for double-posting. I'm not quite sure how did it happend.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: version of findIndex that works with a monadic predicate

2010-11-26 Thread Maciej Piechotka
On Sat, 2010-11-27 at 02:23 +0300, Miguel Mitrofanov wrote:
 findIndexM = (liftM (findIndex id) .) . mapM


Not quite. Compare:

findIndexM (\x - print x  return True) [1,2,3]

or

findIndexM (\x - if x == 2 then Nothing else Just True) [1,2,3]

Possibly better:

findIndexM p = foldr (\(n, y) x -
p y = \b - if b then return $! Just $! n
   else x) (return $! Nothing) .
   zip (map fromIntegral [1..]))

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Re: Reply-To: Header in Mailinglists

2010-11-22 Thread Maciej Piechotka
On Sun, 2010-11-21 at 08:24 +, Malcolm Wallace wrote:
  If the mailing list replaced Reply-To header it would required
  additional effort for responders instead of just pressing reply-to- 
  all.
 
 If the list were to add a Reply-To: header, but only in the case  
 where one was not already present, that would seem to me to be ideal.   
 (None of the internet polemics against Reply-To that I have seen, have  
 considered this modest suggestion.)
 

Except... I don't use Reply-To because it defaults to sender so it will
still be breaking the RFC - in most cases (as most people don't set the
Reply-To header).

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Re: Reply-To: Header in Mailinglists (was: About Fun with type functions example)

2010-11-20 Thread Maciej Piechotka
On Fri, 2010-11-19 at 15:25 +0100, Arnaud Bailly wrote:
 I personnally use most of the time gmail, so I don't have access to a
 Reply-To-List feature (or do I?).
 I usually do Reply-to-all which I think is as I guess most mailers
 remove duplicate mails. Am I right?
 
 Arnaud

As message have the same Message-ID the servers have to (or at least
should - I'm too lazy right now to check the RFC) considered it 'the
same' message (i.e. say - oh. I've already received this message).

I tend to use reply-to-all or reply-to-list if the latter is present.

Regards

PS. Please note that sometimes people do not subscribe to receive
messages. For example I asked a few times on various mailing lists for
help when I was not interested in general discussion on topic asking to
add me to CC.

If the mailing list replaced Reply-To header it would required
additional effort for responders instead of just pressing reply-to-all.




signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Reply-To: Header in Mailinglists (was: About Fun with type functions example)

2010-11-19 Thread Maciej Piechotka
On Fri, 2010-11-19 at 04:55 +0100, Bastian Erdnüß wrote:
 Hi there,
 
 I just put an answer two this in beginn...@haskell.org.  It was not on 
 purpose to move the topic.  It's just that questions I feel I can answer are 
 usually beginner level questions and so I'm not often writing in the cafe 
 itself.
 
 It would make my life a little bit more easy if the mailing lists on 
 haskell.org would add a Reply-To: header automatically to each message 
 containing the address of the mailing list, the message was sent to.  Usually 
 that's the place where others would want to sent the answers to, I would 
 suppose.
 
 Is there a reason that that's not the case?  Am I missing something?  Or am I 
 supposed to install a more cleaver mail client which can do that for me?  Is 
 there one?  Probably written in Haskell ;-)
 
 Cheers,
 Bastian
 
 On

Inserting the Reply-To header is against the RFC (if you like I can find
exact quote). Reply-To is a header marking where *author* of message
wants to receive replies.

There are many reasons why you want to reply privately - for example you
want to say about crossing the rules of netiquette etc., disclose some
information not intended for public view (remote code execution bug)
etc.

You press reply to author button and... oops. it wasn't suppose to go
public.

There is a specialized header meant to specify mailing list which should
and is be used.

Regards

PS. Probably it varies from ML to ML along with top and bottom posting
along with 72-character limit in line.


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Re: typeclass namespace rational?

2010-11-16 Thread Maciej Piechotka
On Tue, 2010-11-16 at 00:55 -0500, Daniel Peebles wrote:
 If I were to guess, I'd say it's because there are two major spaces
 in Haskell, the type level and the value level. They never interact
 directly (their terms are never juxtaposed) so there's not much chance
 for confusion. Typeclass constructors and type constructors do
 however live in the same space. The fact that you propose instance
 String String might be odd to some. It's still unambiguous, but isn't
 necessarily the most clear:
 
 
 (with higher-sorted kind polymorphism, MPTCs, type families, and
 GADTs)
 
 
 instance String String String String String where
   data String String String String String where String :: String
 String String String String
 
 
 :-)

data Buffalo = Buffalo

class Buffalo b where
type familly Buffalo b

instance Buffalo Buffalo where
type familly Buffalo Buffalo = Buffalo

instance Buffalo b = Buffalo (Buffalo b) where
type familly Buffalo (Buffalo b) = b

But:

data Buffalo b = Buffalo b

class Buffalo b where
type familly Buffalo b

-- Is it about Buffalo (type) b being buffalo or result of 
-- Buffalo (type function) being Buffalo?
instance Buffalo b = Buffalo (Buffalo b) where
type familly Buffalo (Buffalo b) = b

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: http://functionalley.eu

2010-11-06 Thread Maciej Piechotka
On Sat, 2010-11-06 at 15:10 +, Alistair Ward wrote:
 I opted to host them there rather than  uploading them to Hackage,
 because they're part of a wider project.

You can upload to hackage packages hosted (like webpage, code repo, bug
tracker...) elsewhere - it similar to Ubuntu (or insert your favourite
distro here) containing packages for KDE while not hosting KDE.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Is let special?

2010-11-03 Thread Maciej Piechotka
On Wed, 2010-11-03 at 18:05 +0100, Petr Pudlak wrote:
  Hi Günther,
 
 from the semantical point of view, you can replace
  let x = e' in e
 by
  (\x - e) e'
 Both should evaluate to the same thing. 

You also need (sometimes) fix function

 let xs = 1:xs in xs 

and

 fix (\xs - 1:xs)

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Decoupling type classes (e.g. Applicative)?

2010-11-03 Thread Maciej Piechotka
On Tue, 2010-11-02 at 21:57 -0400, Brandon S Allbery KF8NH wrote:
 On 10/29/10 09:35 , Dominique Devriese wrote:
  * Only introduce a dependency from type class A to type class B if all
functions in type class B can be implemented in terms of the
functions in type class A or if type class A is empty.
 
 Er?  Eq a = Ord a makes perfect sense in context but violates this law.


x == y = case x `compare` y of EQ - True; _ - False

Or using (==) inside definition:

(==) = ((== EQ) .) . compare

Class A - Ord, B - Eq.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: cabal mystery (#562?)

2010-10-30 Thread Maciej Piechotka
On Thu, 2010-10-28 at 15:33 +0200, Daniel Fischer wrote:
 On Thursday 28 October 2010 15:08:09, Conor McBride wrote:
  Any tips to keep the gremlins at bay gratefully appreciated.
 
 Don't feed after midnight, don't get them wet, I think were the tips.

Don't expose to bright light.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: iteratee-compress 0.1.1

2010-10-24 Thread Maciej Piechotka
Iteratee-compress provides compressing and decompressing enumerators
including flushing. Currently only gzip is provided but at least bzip
is planned.


Changes from previous version:
 - Independent from zlib library (Haskell one, not C)
 - Allow hand-flushing the contents (from outside).
 - Fix potential memory-leak

Next goals:
 - BZip support
 - Generic interface for flushing

To think about:
 - Should inner iteratee be able to request flushing?

Regards

PS. It did change API by removing dependency on zlib but I home such
breakage in 0.1.x will be allowed



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: ANNOUNCE: iteratee-compress 0.1.1

2010-10-24 Thread Maciej Piechotka
On Sun, 2010-10-24 at 15:03 -0400, wren ng thornton wrote:
 On 10/24/10 7:09 AM, Maciej Piechotka wrote:
  Iteratee-compress provides compressing and decompressing enumerators
  including flushing. Currently only gzip is provided but at least bzip
  is planned.
 
  Changes from previous version:
- Independent from zlib library (Haskell one, not C)
- Allow hand-flushing the contents (from outside).
- Fix potential memory-leak
 
  Next goals:
- BZip support
- Generic interface for flushing
 
 Have you thought about adding LZO[1] support? There'd be the usual 
 licensing issues for GPL, but it offers a realtime alternative to gzip 
 (i.e., decompression time is hidden by I/O latency) with comparable 
 compression performance.
 
 
 [1] http://www.oberhumer.com/opensource/lzo/
 

Currently I thought only about bzip2/gzip. Probably .xz support would
follow if any.

LZO, as you said, is on GPL-2. While I have no problems with GPL-2 some
potential users may (Haskell tend to be BSD3 community). Does anyone
knows if conditional compilation solves problem? In my interpretation of
GPL-2 yes but I'm not sure. 

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ANNOUNCE: tls, native TLS/SSL protocol implementation

2010-10-10 Thread Maciej Piechotka
On 10/10/10, Michael Snoyman mich...@snoyman.com wrote:
 On Fri, Oct 8, 2010 at 3:29 PM, Maciej Piechotka uzytkown...@gmail.com
 wrote:

 I had in mind something like:

 import Data.ByteString
 import Data.Iteratee

 clientEnum :: MonadIO m
   = params
   - Enumerator ByteString m a
   - Enumerator ByteString m a
 clientEnum params client = ...

 i.e.

 clientEnum :: MonadIO m
   = params
   - (Iteratee ByteString m a - m (Iteratee ByteString m a))
  -- ^ Client function
   - Iteratee ByteString m a --^ Output
   - m (Iteratee ByteString m a) --^ Input

 Where inner enumerator is simply a client side while 'outer' is a
 outside/server part.

 Regards


 I'm afraid I haven't really looked at iteratee 0.4 enough to
 understand those type signatures completely, but it looks pretty
 similar to the API I have. Am I missing something? And is there a
 reason you can't implement that against the current tls API?

 Michael


Yes as far as I understend. My signature is parametrized both in
client side of protocol as well as native. I.e. in my signature you
don't need to have any Handle but the encrypted output is simply
passed to next iteratee.

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


Re: [Haskell-cafe] Re: ANNOUNCE: tls, native TLS/SSL protocol implementation

2010-10-09 Thread Maciej Piechotka
On Sat, 2010-10-09 at 09:27 +0100, Vincent Hanquez wrote:
 On Fri, Oct 08, 2010 at 12:59:56PM +0100, Maciej Piechotka wrote:
  1. Could also callback in addition to handles be added? 
  Like:
  
  connect' :: (ByteString - IO ()) - IO ByteString - TLSClient IO ()
 
 Would an interface that generate the packet to send and just return them as
 bytes be even better ?
 
 connect' :: TLSClient () ByteString
 
 I'm hoping to have something like that so i can use quickcheck to verify that
 all possible configurations result in a workable connection.
 

I don't think I quite follow. Could you explain?

  2. Does listen corresponds to listen(2)? If yes how to handle STARTTLS
  server-side? If no - please rename it.
 
 it's not doing the same thing as the socket listen(2).
 
 it waits for the handle passed as argument to establish a new TLS session as
 in: listen to the new tls connection.
 
 after reading STARTTLS, you would call listen that would listen for the TLS
 context to be established.
 
 Please suggest something, if you want me to rename it though, as I can't 
 really
 think of a better name.
 

Maybe serverStartTLS? 

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: ANNOUNCE: tls, native TLS/SSL protocol implementation

2010-10-08 Thread Maciej Piechotka
On Wed, 2010-10-06 at 22:26 +0100, Vincent Hanquez wrote:
 Hi haskellers,
 
 I'ld like to announce the tls package [1][2], which is a native implementation
 of the TLS protocol, client and server.  It's currently mostly supporting 
 SSL3,
 TLS1.0 and TLS1.1.  It's got *lots* of rough edges, and a bunch of unsupported
 features, but it's humming along, and at each iteration it's becoming more
 tighly secure and featureful.
 
 I would recommend against using this implementation in a production system 
 just
 yet, or in an aggressive environment either (specially for the server side);
 I don't think it should necessary fail, but it's still an early implementation
 with probable API changes on the way.
 
 [1] http://github.com/vincenthz/hs-tls
 [2] http://hackage.haskell.org/package/tls

1. Could also callback in addition to handles be added? 
Like:

connect' :: (ByteString - IO ()) - IO ByteString - TLSClient IO ()

Why:
 - It allows to wrap it into Enumerators

2. Does listen corresponds to listen(2)? If yes how to handle STARTTLS
server-side? If no - please rename it.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ANNOUNCE: tls, native TLS/SSL protocol implementation

2010-10-08 Thread Maciej Piechotka
On Fri, 2010-10-08 at 15:14 +0200, Michael Snoyman wrote:
 On Fri, Oct 8, 2010 at 1:59 PM, Maciej Piechotka uzytkown...@gmail.com 
 wrote:
  On Wed, 2010-10-06 at 22:26 +0100, Vincent Hanquez wrote:
  Hi haskellers,
 
  I'ld like to announce the tls package [1][2], which is a native 
  implementation
  of the TLS protocol, client and server.  It's currently mostly supporting 
  SSL3,
  TLS1.0 and TLS1.1.  It's got *lots* of rough edges, and a bunch of 
  unsupported
  features, but it's humming along, and at each iteration it's becoming more
  tighly secure and featureful.
 
  I would recommend against using this implementation in a production system 
  just
  yet, or in an aggressive environment either (specially for the server 
  side);
  I don't think it should necessary fail, but it's still an early 
  implementation
  with probable API changes on the way.
 
  [1] http://github.com/vincenthz/hs-tls
  [2] http://hackage.haskell.org/package/tls
 
  1. Could also callback in addition to handles be added?
  Like:
 
  connect' :: (ByteString - IO ()) - IO ByteString - TLSClient IO ()
 
  Why:
   - It allows to wrap it into Enumerators
 
 It's entirely possible to wrap the current interface into
 enumerators/iteratees[1]. That's how http-enumerator works.
 
 Michael
 
 [1] 
 http://github.com/snoyberg/http-enumerator/blob/master/Network/TLS/Client/Enumerator.hs


I had in mind something like:

import Data.ByteString
import Data.Iteratee

clientEnum :: MonadIO m
   = params
   - Enumerator ByteString m a
   - Enumerator ByteString m a
clientEnum params client = ...

i.e.

clientEnum :: MonadIO m
   = params
   - (Iteratee ByteString m a - m (Iteratee ByteString m a))
  -- ^ Client function
   - Iteratee ByteString m a --^ Output
   - m (Iteratee ByteString m a) --^ Input

Where inner enumerator is simply a client side while 'outer' is a
outside/server part.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Coding conventions for Haskell?

2010-09-26 Thread Maciej Piechotka
On Sun, 2010-09-26 at 11:40 +0200, Petr Pudlak wrote:
 Hi Johan,
 
 On Sat, Sep 25, 2010 at 01:44:07PM +0200, Johan Tibell wrote:
 Quite a few people follow my style guide
 
 http://github.com/tibbe/haskell-style-guide/blob/master/haskell-style.md
 
 which codifies the style used in Real World Haskell, bytestring, text,
 and a few other libraries.
 
 Thanks for sharing the link, it's quite helpful. It's just what I was 
 looking for. 
 
 One more thought: Do you also have some recommendations for formatting 
 'let ... in ...' expressions?
 
   Best regards,
   Petr

I use it in following way;

1. For short sharing name (rarely)

let a = b ++ c in (a, a) 

2. Default

let a :: [Int]
a = b ++ c
f :: Int - String
f 0 = 
f x = show x
in map f a

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Coding conventions for Haskell?

2010-09-26 Thread Maciej Piechotka
On Sat, 2010-09-25 at 13:44 +0200, Johan Tibell wrote:
 On Sat, Sep 25, 2010 at 11:24 AM, Petr Pudlak d...@pudlak.name wrote:
  sometimes I have doubts how to structure my Haskell code - where to break
  lines, how much to indent, how to name functions and variables etc. Are
  there any suggested/recommended coding conventions? I searched a bit and I
  found a few articles and discussions:
 
 Quite a few people follow my style guide
 
 http://github.com/tibbe/haskell-style-guide/blob/master/haskell-style.md
 
 which codifies the style used in Real World Haskell, bytestring, text,
 and a few other libraries.
 
 -- Johan

May I ask clarification about formatting (according to your convention)

doSomething :: (a - a - a) - a - a - a
doSomething f x = f y y
  where y = f x x

i.e. single line function+where

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Unified Haskell login

2010-09-20 Thread Maciej Piechotka
On Sun, 2010-09-19 at 17:12 +0200, Michael Snoyman wrote:
 
 Let me respond to this directly since a number of people have brought
 this up:
 
 Due to spam reasons we can't trust the email given via an OpenID
 provider in general. For example, it would be trivial for me to create
 an OpenID provider for myself, set my email address as insert someone
 else's address here and essentially spam them.
 
 By going with a service like Facebook or Google, we know (or at least
 assume) that they do proper email validation, so we could immediately
 accept this value without needing to verify it ourselves.
 
 In other words: Yes, I know there are extensions to OpenID. And no, we
 can't use it to get a verified email address.
 
 Michael 

There are people who for whatever reason don't use Facebook/Google/
And sending verification e-mail costs practically nothing.

Regards

PS. If we have on-site registration it would have unverified e-mail as
well.


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Unified Haskell login

2010-09-18 Thread Maciej Piechotka
On Fri, 2010-09-17 at 08:47 +0200, Michael Snoyman wrote:
 Hi cafe,
 
 Let me preface this by stating that this is purposely a half-baked
 idea, a straw man if you will. I'd like to hear what the community
 thinks about this.
 
 I mentioned yesterday that I was planning on building haskellers.com.
 The first technicality I considered was how login should work. There
 are a few basic ideas:
 
 * Username/password on the site. But who wants to deal with *another* 
 password?
 * OpenID. Fixes the extra password problem, but doesn't give us any
 extra information about the user (email address, etc).

Actually most OpenID providers uses OpenID extension which allows to
query (with user permission) about data such as e-mail address, real
name etc.

 * Facebook/Twitter/Google: We get the users email address, but do we
 *really* want to force users to have one of those accounts?
 

Possibly also:
* FOAF/SSL: Practically not used in wild

I'd give +1 for either common username/password or OpenID.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Ultra-newbie Question

2010-09-18 Thread Maciej Piechotka
On Sat, 2010-09-18 at 03:51 -0400, Christopher Tauss wrote:
 Hello Haskell Community -
  
 I am a professional programmer with 11 years experience, yet I just do
 not seem to be able to get the hang of even simple things in Haskell.
 I am trying to write a function that takes a list and returns the last
 n elements.
  
 There may be a function which I can just call that does that, but I am
 trying to roll my own just to understand the concept.
  
 Let's call the function n_lastn and, given a list  [1,2,3,4,5], I
 would like 
 n_lastn 3 = [3,4,5]
  
 Seems like it would be something like:
  
 n_lastn:: [a]-Int-[a]
 n_lastn 1 (xs) = last(xs)
 n_lastn n (x:xs) = 
  
 The issue is I do not see how you can store the last elements of the
 list.
  
 Thanks in advance.
  
 ctauss

I'll add my $0.03 - unless you are doing it to learn about lists rethink
your approach. Taking k elements from end of n-element list will be O(n)
operation.

For example with appropriate structures (like finger trees) it would
look like O(k) operation.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-09-14 Thread Maciej Piechotka
On Tue, 2010-09-14 at 11:27 +0100, Neil Brown wrote:
 On 13/09/10 17:25, Maciej Piechotka wrote:
  import Control.Exception
  import Foreign
  import Prelude hiding (catch)
 
  data StrictMonad a = StrictMonad a deriving Show
 
  instance Monad StrictMonad where
   return x = unsafePerformIO $ do
   (return $! x) `catch` \(SomeException _) -  return x
   return $! StrictMonad x
   StrictMonad v= f = f v
   
  It seems to be valid IMHO Functor and Monad (I haven't prove it) as long
  as functions terminates.
 
 
 I'm not sure if I'm allowed to use unsafePerformIO in my 
 counter-example, but you used it so why not ;-)
 The first monad law says: return a = k = k a
 
 let k = const (StrictMonad ())
  a = unsafePerformIO launchMissiles
 
 In k a no missiles will be launched, in return a = k, they will be 
 launched.

I guess we enter a grey area - I did use unsafePerformIO but without
side-effects. 

 You can construct a similar example against m = return = 
 m.

Assuming StrictMonad (constructor) is hidden - I don't think so.

 Although, if you changed your definition of bind to:
 
 StrictMonad v = f = return v = f = return
 
 Then as long as return x = return = return x (which it does for you) 
 then you automatically satisfy the first two monad laws!  Which is an 
 interesting way of solving the problem -- haven't checked the third law 
 though.
 

My error.

 Thanks,
 
 Neil.


Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-09-13 Thread Maciej Piechotka
I started experiment with strict functors. I come to:

 import Control.Exception
 import Foreign
 import Prelude hiding (catch)
 
 data StrictMonad a = StrictMonad a deriving Show
 
 instance Functor StrictMonad where
 f `fmap` StrictMonad v = return $ f v
 
 instance Applicative StrictMonad where
 pure = return
 (*) = ap
 
 instance Monad StrictMonad where
 return x = unsafePerformIO $ do
 (return $! x) `catch` \(SomeException _) - return x
 return $! StrictMonad x
 StrictMonad v = f = f v

It seems to be valid IMHO Functor and Monad (I haven't prove it) as long
as functions terminates.

Some time ago there was post stating that there is not possible strict
'interesting' functor - I guess that the above is 'interesting' (and due
to halting problem I guess it is not possible to create strict Functor
which would deal with that problem).

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] ANNOUNCE: reference 0.1

2010-09-07 Thread Maciej Piechotka
On Tue, 2010-09-07 at 02:15 +0200, Bas van Dijk wrote:
 On Mon, Sep 6, 2010 at 11:55 PM, Maciej Piechotka uzytkown...@gmail.com 
 wrote:
  Reference is class which generalizes references and monads they exists
  in. It means that IORef, STRef and others can be accessed by common
  interface.
 
  Currently it is of form:
 
  class Reference r m where
 
  1. There was a proposal to rename the class to MonadRef or
  MonadReference. IMHO it would imply m - r functional dependency and
  therefore disallow the instances for both MVar IO and IORef IO
 
  2. Should the functional dependencies or type famillies be introduced?
  Personally I don't think so as I would like to allow all of the
  following:
 
   - IORef IO
   - MVar IO
   - IORef (ContT IO)
   - MVar (ContT IO)
 
  Any feedback mostly welcome.
 
  Regards
  PS. Darcs repository will be available soon
 
  ___
  Haskell mailing list
  hask...@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell
 
 
 


First I'd like to say sorry for error in cafe mailing list address. The
whole e-mail is included above.

 I've played with a somewhat similar idea:
 
 darcs get http://code.haskell.org/~basvandijk/code/only-read-or-write-vars
 
 API Docs + Hyperlinked source:
 http://code.haskell.org/~basvandijk/code/only-read-or-write-vars/doc/html/only-read-or-write-vars/
 
 This is not released (yet) because I'm unsure about the design.
 
 Especially, I'm unsure whether parameterizing Readable with α is a good idea:
 
 class Readable v m α | v → m where read  v → m α
 
 and whether parameterizing Writable with α and β is a good idea:
 
 class Writable v α m β | v → m where write  v → α → m β
 
 They do allow some some nice instances like:
 
 instance Readable (TMVar α) STM (Maybe α) where
 read = TMVar.tryTakeTMVar
 
 instance Writable (TMVar α) α STM Bool where
 write = TMVar.tryPutTMVar
 
 instance Writable (Chan α) (End α) IO () where
 write t = Chan.unGetChan t  unEnd
 
 -- | Writing @End x@ to a 'Chan' or 'TChan' writes @x@ to the end of
the channel
 -- instead of to the front. Also see 'unGetChan' and 'unGetTChan'.
 newtype End α = End {unEnd  α}
 
 Regards,
 
 Bas
 

I guess they are to some extend like Foldable to FoldableLL and possibly
describing different aspects. Yours seems to be a bit like StateVar[1]
generalized for different monads. Support for ptr  others is additional
bonus.

I wanted clear 1-1 mapping with references - i.e. basic 2 operations
with added third for 'atomic' support. 

For example one of unmentioned law is that:

write r x  read r  ===  write r x  return r -- If it's only thread
write r x  write r y === write r y -- If it's only thread
read r  read r === read r
read r = write r === id -- If it's only thread
read r = const f === f -- If it's only thread?

In fact I guess each on them could be used as RULES as IMHO each case in
which it is not necessary true it is undeterministic anyway.

While Chan is clearly writable and readable it cannot be considered a
reference - it do have it purposes but they are usually different then
references.

To sum up - I would not be willing to use Readable/Writable in place of
Reference but I don't say they don't have their purposes.

PS. I took the liberty of continuing sentence.

[1] http://hackage.haskell.org/package/StateVar-1.0.0.0


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Re: [Haskell] ANNOUNCE: reference 0.1

2010-09-07 Thread Maciej Piechotka
On Tue, 2010-09-07 at 20:36 +0200, Alberto G. Corona wrote:
 Why not to define it for any monad, for example STM (TVars) and
 whatever?

I'm really sorry but I fail to see what does 'it' refers to. reference
0.1 contains at this moment definitions for:

- Reference TVar STM
- Reference IORef IO
- Reference MVar IO
- Reference (STRef s) (ST s)

(http://hackage.haskell.org/packages/archive/reference/0.1/doc/html/Data-Reference.html#t:Reference)

So in fact there is already support for STM/TVar pair.

Regards



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: ANNOUNCE: countable-0.1

2010-09-06 Thread Maciej Piechotka
On Mon, 2010-09-06 at 03:54 -0700, Ashley Yakeley wrote: 
 countable: Countable, Searchable, Finite, Empty classes.
 
class Countable, for countable types
class AtLeastOneCountable, for countable types that have at least one 
 value
class InfiniteCountable, for infinite countable types
class Searchable, for types that can be searched over
class Finite, for finite types
class Empty, for empty types
data Nothing, an empty type
 
 Also includes these orphan instances:
 
instance (Searchable a,Eq b) = Eq (a - b)
instance (Finite a) = Foldable ((-) a)
instance (Finite a) = Traversable ((-) a)
instance (Show a,Finite a,Show b) = Show (a - b)
 
 It turns out Searchable includes some infinite types. Specifically, 
 countable implements this:
 
instance (Countable c,Searchable s) = Searchable (c - s)
 
 using the algorithm described here:
 
 http://math.andrej.com/2007/09/28/seemingly-impossible-functional-programs/
 
 I would welcome improvements.
 
 http://hackage.haskell.org/package/countable-0.1
 cabal install countable
 darcs get http://code.haskell.org/countable/
 
 See also this thread:
 http://thread.gmane.org/gmane.comp.lang.haskell.cafe/73275
 

Hmm.

1. Code formatting is very C#-like. At least for me it is hard to read
the code that way (it IS matter of preference however)

2. countMaybeNext seems to need documentation. If I understand it
correctly:

countMaybeNext Nothing = 'minimalValue'
countMaybeNext (Just x) = x + 1

Wouldn't be split it to:

countNext :: a - Maybe a
initial :: Maybe a

3. 

Regards 


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: overloaded list literals?

2010-09-06 Thread Maciej Piechotka
On Mon, 2010-09-06 at 10:23 +, Johannes Waldmann wrote:
 We have overloaded numerical literals (Num.fromInteger)
 and we can overload string literals (IsString.fromString),
 so how about using list syntax ( [], : )
 for anything list-like (e.g., Data.Sequence)?
 
 Of course some minor details would need to be worked out,
 like what methods should go in the hypothetical class IsList
 (is is Foldable?) and what to do about pattern matching
 (perhaps we don't need it?)
 

Foldable is not necessary a good choice.

Neither ByteString nor Text is Foldable. It would make hard to write
methods like:

checkMagicKey :: ByteString - Bool
checkMagicKey (0x85:0x86:_) = True
checkMagicKey _ = False

or

checkFoo :: Text - Bool
checkFoo Foo = True
checkFoo _ = False


 IIRC there was a time when list comprehension 
 would actually mean monad comprehension 
 (when there was no do notation)
 but that's not what I'm getting at here. Or is it?
 Do we have a Haskell museum of ideas from the past?
 
 
 Best - J.W. 

I guess the laziness and view patterns are sufficient:

checkMagicKey :: ByteString - Bool
checkMagicKey (unpack - 0x85:0x86:_) = True
checkMagicKey _ = False

checkFoo :: Text - Bool
checkFoo (unpack - Foo) = True
checkFoo _ = False

The problems:
 - In teaching list are useful because they are simple. View patterns
are not. Even if view patterns were standard it could be considered too
complicated to teach.
 - They introduce nothing more then is already achievable as it is
possible to write
checkFoo x = case unpack x of
 Foo - ...
 _ - ...  
or
checkFoo x
| unpack x == Foo = ...
| otherwise = ...
 - I may be wrong but they require the recomputation on each call of
unpack


I guess that maybe active patterns should be considered to be imported
from F#. I'm not quite sure about syntax and maybe they are too logic
like.

PS.

data FooBar a = Foo
  | Bar
  deriving Show

class IsString (FooBar Char) where
toString _ = Foo

class IsList FooBar where
toList _ = Bar

show (1234 :: FooBar Char) == ???



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: questions about Arrows

2010-09-01 Thread Maciej Piechotka
On Tue, 2010-08-31 at 20:39 -0700, Ben wrote:
 Hello --
 
 Three related questions, going from most specific to most general :
 
 1 ) Consider the stream processing arrow which computes a running sum,
 with two implementations : first using generic ArrowCircuits (rSum);
 second using Automaton (rSum2) :
 
 module Foo where
 
 import Control.Arrow
 import Control.Arrow.Operations
 import Control.Arrow.Transformer
 import Control.Arrow.Transformer.All
 
 rSum :: ArrowCircuit a = a Int Int
 rSum = proc x - do
   rec out - delay 0 - out + x
   returnA - out
 
 rSum2 = Automaton (f 0)
   where f s n = let s' = s + n
 in (s', Automaton (f s'))
 
 runAuto _ [] = []
 runAuto (Automaton f) (x:xs) =
   let (y, a) = f x
   in y : runAuto a xs
 
 take 10 $ runAuto rSum [1..]
 [0,1,3,6,10,15,21,28,36,45]
 
 take 10 $ runAuto rSum2 [1..]
 [1,3,6,10,15,21,28,36,45,55]
 
 Note that the circuit version starts with the initial value zero.
 
 Is there a way to write rSum2 in the general ArrowCircuit form, or
 using ArrowLoop?
 

rSum2 :: ArrowCircuit a = a Int Int
rSum2 = proc x - do
rec out - delay 0 - out + x
returnA - out + x


 2) Are the ArrowLoop instances for (-), Kleisli Identity, and
 Kleisli ((-) r) all morally equivalent?  (e.g., up to tagging and untagging?)
 

Yes

 3) One can define fix in terms of trace and trace in terms of fix.
 
 trace f x = fst $ fix (\(m, z) - f (x, z))
 fix f = trace (\(x, y) - (f y, f y)) undefined
 
 Does this mean we can translate arbitrary recursive functions into
 ArrowLoop equivalents?
 

Yes. In fact fix is used on functional languages that do not support
recursion to have recursion (or so I heard)

 Best regards, Ben

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: questions about Arrows

2010-09-01 Thread Maciej Piechotka
On Wed, 2010-09-01 at 11:49 -0700, Ben wrote:
 Thanks for the prompt reply.  Some questions / comments below :
 
 On Wed, Sep 1, 2010 at 12:33 AM, Maciej Piechotka uzytkown...@gmail.com 
 wrote:
 
  rSum2 :: ArrowCircuit a = a Int Int
  rSum2 = proc x - do
 rec out - delay 0 - out + x
 returnA - out + x
 
 Wow, that was simple.  I guess I never thought to do this because it
 evaluates (out + x) twice, but one can always write
 
 rSum3 :: ArrowCircuit a = a Int Int
 rSum3 = proc x - do
   rec let next = out + x
   out - delay 0 - next
   returnA - next
 
 I have a follow-up question which I'll ask in a new thread.
 

Possibly it should be written as

rSum4 :: ArrowCircuit a = a Int Int
rSum4 = proc x - do
  rec let !next = out + x
  out - delay 0 - next
  returnA - next

  3) One can define fix in terms of trace and trace in terms of fix.
 
  trace f x = fst $ fix (\(m, z) - f (x, z))
  fix f = trace (\(x, y) - (f y, f y)) undefined
 
  Does this mean we can translate arbitrary recursive functions into
  ArrowLoop equivalents?
 
 
  Yes. In fact fix is used on functional languages that do not support
  recursion to have recursion (or so I heard)
 

Ups. Sorry - my dyslexia came to me and I read recursive instead of
ArrowLoop. My fault

IMHO it is not possible.

 In which case my question is, why is the primitive for Arrows based on
 trace instead of fix?
 

How would you define loop in terms of

fixA :: ArrowLoop a = a b b - a c b
fixA f = loop (second f  arr (\(_, x) - (x, x)))

The only way that comes to my mind is:

loopA :: (ArrowLoop a, ArrowApply a) = a (b, d) (c, d) - a b c
loopA f = proc (x) - do
arr fst  fixA (proc (m, z) - do f - (x, z)) - x

Which requires ArrowApply. So as long as arrow is ArrowLoop and
ArrowApply it is possible.

 Best regards, Ben

Regards



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: iteratee-compress 0.1

2010-08-31 Thread Maciej Piechotka
Iteratee-compress provides compressing and decompressing enumerators.
Currently only gzip is provided but at least bzip is planned.

Additionally more fine-control over stream (i.e. flushing) is planned.


Library currently depends on zlib haskell library only for sharing
parameters data. However no zlib function is called (the needed
functions are not exported) and the symbols it uses from necessity are
deprecated. Would it be better to copy the parameters from zlib and drop
the dependency?

Please note also that the library do not bundle zlib (C) as zlib
(Haskell) do.


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Crypto-API is stabilizing

2010-08-27 Thread Maciej Piechotka
On Mon, 2010-08-23 at 10:05 -0700, Thomas DuBuisson wrote:
 All,
 
 Crypto-API - a unified interface to which I hope hash and cipher
 algorithms will adhere - has recently gotten a reasonable amount of
 polish work.  I continue to welcome all comments!  A blog on its
 current interface is online [1] as are darcs repositories of the
 crypto-api package [2].  Recent changes includes added block cipher
 modes, platform-independent RNG, tests, a simplistic benchmark
 framework, and minor tweaks of the classes.  I've made experimental
 hash, block cipher and stream cipher instances.  Almost no
 optimizations have been made as of yet!
 
 Thanks to everyone for their past comments!  I have made numerous
 changes based on input received.  If you feel I didn't respond
 properly to your suggestion then please ping me again - this is purely
 a spare time effort and things do fall through the cracks.
 
 Cheers,
 Thomas
 
 [1] 
 http://tommd.wordpress.com/2010/08/23/a-haskell-api-for-cryptographic-algorithms/
 [2] http://community.haskell.org/~tommd/crypto/
 
 (If you're wondering why you're BCCed its probably because you worked
 on a crypto-related Haskell package)

I wonder - conceptually compression does not differ much from stream
ciphers - you put some data in and you get some data out.

The only real difference is that the compression does not need to have
any private key [but it can have 'public' as the level of compression
etc.].

Except naming they do not differ much (on the other hand - they do share
subsystem in Linux kernel).

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] FRP - style

2010-08-27 Thread Maciej Piechotka
I wanted to learn something about FRP. I tried to use existing packages
on hackage and write something in OpenGL but I failed - mainly due to
problem of handling single occurrence of event[1].

I tried to write my own library
(https://patch-tag.com/r/uzytkownik/reactive-event/home) and I'd like to
ask if I'm doing it from right direction or do I miss some important
aspects of FRP.

I assume that the events are discrete and the value can change (along
with action) only on event.
For specific class of events there exists 'always' event associated with
time [In practice it would mean that it is executed as fast as
possible].

Regards

[1] In retrospection - I should have rely more on immutable data to pass
around information that I did handled event - but it seems for me an
overkill.


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: ANNOUNCE: hs-cryptohash 0.4

2010-07-02 Thread Maciej Piechotka
On Fri, 2010-07-02 at 20:10 +1000, Ivan Lazar Miljenovic wrote:
 Vincent Hanquez t...@snarc.org writes:
 
  On Fri, Jul 02, 2010 at 12:55:03PM +1000, Ivan Miljenovic wrote:
  On 1 July 2010 17:25, Vincent Hanquez t...@snarc.org wrote:
   The main reason for this library is the lack of incremental api exposed 
   by
   current digest libraries, and filling the void about some missing digest
   algorithms; Also the speed comes as a nice bonus.
  
  Can you explain what you mean by incremental API?
 
  The incremental API is the init/update/finalize functions where you can call
  update as many time as you need, instead of a single function hash where 
  you
  need to hash all your data in one-go.
 
  It's necessary in my case since i receive chunks of data to be hashed from 
  the
  network, and I don't want to carry a buffer of data (with potential security
  issues), until i can hash everything.
 
  The few existing packages that exposes the incremental API, usually do it
  in the IO monad; cryptohash do it purely, creating a new context as it get 
  updated.
  (this has a cost but remains fast globally with the C implementation)
 
  i.e.
  update : ctx - bytestring - IO ()
  becomes:
  update : ctx - bytestring - ctx
 
 So you're using explicit state parsing?  Any particular reason for not
 using the State monad or something like that?
 

Wrapping it into State monad is trivial IMHO but such implementation is
trivial to use for example in foldl.

Also it allows to not jump in both direction if you need to use it
somewhere:

f ctx = do
   l - getLine
   let !ctx = update ctx l
   l - getLine
   let !ctx = update ctx l
   return ctx

vs.
(if it is forall m. StateT ctx m a)

f = execStateT $ do
   l - lift $ getLine
   update l -- Alternativly: update = lift (getLine)
   l - lift $ getLine
   update l

or

f ctx = do
   l - getLine
   let !ctx = execState (update l)
   l - getLine
   let !ctx = execState (update l)
   return ctx

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: specifying package name in ghci import?

2010-06-29 Thread Maciej Piechotka
On Mon, 2010-06-28 at 19:29 -0700, Michael Vanier wrote:
 Hi,
 
 Quick question about ghci: when I do this at the prompt:
 
 ghci :m +Control.Monad.Cont
 
 I get
 
  Ambiguous module name `Control.Monad.Cont':
it was found in multiple packages: mtl-1.1.0.2 monads-fd-0.0.0.1
 
 Is there any way to fix this from within ghci (i.e. not involving 
 mucking with ghc-pkg)?  What I have in mind might be e.g.
 
 ghci :m + mtl Control.Monad.Cont
 
 or something similar.
 
 Thanks,
 
 Mike

% ghci -hide-package monads-fd
ghci import Control.Monad.Cont

or

ghci :set -hide-package mtl
ghci import Control.Monad.Cont

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] TypeFamillies and UndecidableInstances - why?

2010-06-22 Thread Maciej Piechotka
When I tried to do something like:

 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE TypeFamilies #-}
 
 class Test a where
   type TestMonad a :: * - *
   from :: a b - TestMonad a b
   to :: TestMonad a b - a b
 
 data Testable a b = Testable (a b)
 
 instance (Test a, Functor (TestMonad a)) = Functor (Testable a) where
   f `fmap` Testable v = Testable $! (to . fmap f . from) v
 

It asks for adding UndecidableInstances as:

test.hs:11:0:
Constraint is no smaller than the instance head
  in the constraint: Functor (TestMonad a)
(Use -XUndecidableInstances to permit this)
In the instance declaration for `Functor (Testable a)'


What is undecidable? a is bound so TestMonad a should be bound so
Functor (TestMonad a) should be valid.

Is it a bug/missing feature in ghc or do I fail to see something?

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: TypeFamillies and UndecidableInstances - why?

2010-06-22 Thread Maciej Piechotka
On Tue, 2010-06-22 at 21:51 -0400, Brandon S. Allbery KF8NH wrote:
 On Jun 22, 2010, at 21:41 , Maciej Piechotka wrote:
  test.hs:11:0:
 Constraint is no smaller than the instance head
   in the constraint: Functor (TestMonad a)
 (Use -XUndecidableInstances to permit this)
 In the instance declaration for `Functor (Testable a)'
  
  What is undecidable? a is bound so TestMonad a should be bound so
  Functor (TestMonad a) should be valid.
 
 I *think* the point of the error message is that Functor (TestMonad a) is a 
 tautology, so including it doesn't actually constrain the instance (which in 
 GHC-ese is Constraint is no smaller than the instance head).  In short, GHC 
 thinks you're being tricky in a way it can't understand, because otherwise 
 there's no point in including the constraint, so it's telling you that being 
 tricky requires UndecidableInstances.
 

I'm sorry but how Functor (TestMonad a) is a tautology? It cannot be
derived from other constraints (in and outside this class). 

Unless you mean that GHC thinks it is tautology. 

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Re: What is Haskell unsuitable for?

2010-06-19 Thread Maciej Piechotka
On Sat, 2010-06-19 at 03:12 +0200, Henning Thielemann wrote:
 Maciej Piechotka schrieb:
 
  1. Glueing a few highier level, object-oriented libraries if it is just
  glueing.
  
  2. (Currently) AFAIK real-time applications although it is rather
  property of GHC GC then the language itself
 
 In my experience the garbage collector was not the problem in real-time
 applications, but memory leaks that make the garbage collector slow.

The problem is that:
 - GHC GC can run at any moment
 - It is stop-the-world GC
 - There is no upper limit on how long GHC GC will run

I have no experience with real-time applications however.

Regards



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: What is Haskell unsuitable for?

2010-06-16 Thread Maciej Piechotka
On Wed, 2010-06-16 at 10:34 +0200, David Virebayre wrote:
 On Wed, Jun 16, 2010 at 8:00 AM, Michael Snoyman mich...@snoyman.com wrote:
 
  Next you'll say there's no need for anyone to ask whether they prefer
  vi or emacs... ;-)
 
  Of course *real* programmers use ed. It is the standard editor[1].
 
 *Real* programmers use butterfiles [1].
 
 [1] http://xkcd.com/378/
 
 David.

Emacs is also accepted IIRC - M-x butterfly

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: What is Haskell unsuitable for?

2010-06-15 Thread Maciej Piechotka
On Tue, 2010-06-15 at 19:47 -0400, aditya siram wrote:
 Hi all,
 Haskell is a great language and in a lot of ways it still hasn't found
 a niche, but that's part of what is great about it. 
 
 But I wanted to ask people are more experienced with Haskell - what
 kinds of problems is it unsuited for? Have you ever regretted using it
 for something? Meaning if you could write the program over you would
 do it in another language.
 
 thanks ...
 -deech
 

1. Glueing a few highier level, object-oriented libraries if it is just
glueing.

2. (Currently) AFAIK real-time applications although it is rather
property of GHC GC then the language itself

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Reactive and 'real live' problem

2010-06-14 Thread Maciej Piechotka
I tried to experiment with reactive[1] and rewrite NeHe tutorials using
reactive-glut. However I run into problems.

I tried to write first tutorial and exit on escape. However there were 2
problems:

1. Optimized constant functions
2. Continuous behaviour

In reactive the final step is Behaviour which is 'function' from time to
something a. Here a = IO (). The problem is that it is not indifferent
how many time the same IO () was returned (we don't want to write to
file twice etc.).

I tried to workaround it in various ways but all I came up to was to
switch after switch with time + * where * is the difference between
times (unfortunately there is no function which give the next float).

As with every tick everything is executed -- unless everything gets
optimized to constant function.

Am I failing to find proper docs? How solve those problems? If they are
not easily solvable is there any general-purpose FRP library that allows
to use IO inside?

Regards

[1] http://hackage.haskell.org/package/reactive



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Using the ContT monads for early exits of IO ?

2010-06-11 Thread Maciej Piechotka
On Thu, 2010-06-10 at 21:21 +0100, Ben Millwood wrote:
 On Thu, Jun 10, 2010 at 8:57 PM, Maciej Piechotka uzytkown...@gmail.com 
 wrote:
 
  Error monad seems not to be a semantic solution as we exit on success
  not failure.
 
 
 Which is really why the Either monad should not necessarily have Error
 associations :)
 If you forget about the fail method, the Monad (Either e) instance
 doesn't need the e to be an error type.
 
 Alternatively, if even Error is more information than you need, you
 could use MaybeT:
 
 http://hackage.haskell.org/package/MaybeT
 
 which allows you to just stop. Given you're using it with IO it'd be
 easy to write a result to an IORef before terminating the computation,
 so it's of equivalent power, if slightly less convenient.

Over MaybeT I would prefer to simply iterate over list using helper
recursive function.

Either monad (without Error part) seems to be good solution - and it do
not contain too much information.

But the function with ContT IO seemed... nice. Also as it deals with
network I/O speed does not seems to be a great issue.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: How to Show an Operation?

2010-06-10 Thread Maciej Piechotka
On Thu, 2010-06-10 at 19:44 +0200, Martin Drautzburg wrote:
 On Thursday, 10. June 2010 00:08:34 Luke Palmer wrote:
 
  Or just:
 
  apply = val_of
 
  So, to summarize:  if you have something that isn't a function and you
  want to use it like a function, convert it to a function (using
  another function :-P).  That's all.  No syntax magic, just say what
  you're doing.
 
 Thanks Luke
 
 The reason I was asking is the following: suppose I have some code which uses 
 some functions, and what it primarily does with those functions is CALL them 
 in different orders.
 
 Now at a later point in time I decide I need to give names to  those 
 functions 
 because at the end I need to print information about the functions which 
 together solved a certain problem. Think of my problem as In which order do 
 I have to call f,g,h such that (f.g.h) 42 = 42?.
 
 I don't want to change all places where those functions are called 
 into apply style. Therefore I was looking for some idiom like the python 
 __call__() method, which, when present, can turn just about anything into a 
 callable.
 
 I could change the *definition* of my original functions into apply style 
 and the rest of the code would not notice any difference. But that does not 
 really help, because in the end I want to Show something like [g,h,f], but my 
 functions would no longer carry names.
 
 Alternatively I could associate functions with names in some association 
 function, but that function simply has to know to much for my taste.
 
 The thing is, I only need the names at the very end. Throughout the majority 
 of the computation they should stay out of the way.
 
 

data Named a = Named String a

instance Functor Named where
f `fmap` (Named s v) = Named s (f v)

instance Applicative Named where
pure x = Named  x
(Named s f) * (Named t v) = Named (s ++ ( ++ t ++ )) (f v)

instance Eq a = Eq (Named a) where
(Named _ x) == (Named _ y) = x == y

instance Show (Named a) where
show (Named s _) = s

namedPure :: Show a = a - Named a
namedPure x = Named (show x) x

test :: Num a
 = (a - a) - (a - a) - (a - a) - [String]
test f g h = do
[f', g', h'] - permutations [Named f f, Named g g, Named h h]
guard $ namedPure 42 == f' * g' * h' * namedPure 42
return $ show f' ++  .  ++ show g' ++  .  ++ show h'

(code is not tested but it should work)

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Using the ContT monads for early exits of IO ?

2010-06-10 Thread Maciej Piechotka
On Thu, 2010-06-10 at 14:09 -0500, Tim Wawrzynczak wrote:
 Actually, on second thought, Lennart is probably right.  Continuations
 are probably overkill for this situation.
 Since not wanting to continue is probably an 'erroneous condition,'
 you may as well use Error.
 
 Cheers,
  - Tim
 

Technically it can be a success. For example if we get a list of
HostInfo for given hostname we want to connect once instead of many
times. Also the first time might not succeed (it is  entry in IPv4
network).

Error monad seems not to be a semantic solution as we exit on success
not failure.

Regards




signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: GATD and pattern matching

2010-06-09 Thread Maciej Piechotka
On Wed, 2010-06-09 at 22:28 +0200, Dupont Corentin wrote:
 Thanks for your response.
 
 How would you do it? I design this GATD for a game i'm making:
 
  data Obs a where 
  Player :: Obs Integer 
  Turn :: Obs Integer
  Official :: Obs Bool 
  Equ :: Obs a - Obs a - Obs Bool   --woops!!
  Plus :: (Num a) = Obs a - Obs a - Obs a 
  Time :: (Num a) = Obs a - Obs a - Obs a 
  Minus :: (Num a) = Obs a - Obs a - Obs a 
  Konst :: a - Obs a 

Actually woops is here. Make it for example

Const :: (Show a, Eq a, ...) = a - Obs a

  And :: Obs Bool - Obs Bool - Obs Bool 
  Or :: Obs Bool - Obs Bool - Obs Bool
 
 For example I can design an Observable like that:
 
 myObs = Player `Equ` (Konst 1) `And` Official
 
 These Observables will then be processed during gameplay.
 
 I would like to be able to do in ghci:
 
  show myObs
 Player `Equ` (Konst 1) `And` Official
 
 and:
   myObs == myObs
 True
 

Regards



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Re: Re: Difference between div and /

2010-06-07 Thread Maciej Piechotka
On Thu, 2010-06-03 at 06:48 -0700, mo...@deepbondi.net wrote:
 
  On Thu, 3 Jun 2010, Maciej Piechotka wrote:
 
  Hmm. Thanks - however I fail to figure out how to do something like:
 
  generate a random number with normal distribution with average avg and
  standard deviation stdev.
 
  Unfortunately the package is restricted to discrete distributions so far.
 
 Shameless self-advertisement: The random-fu package (whimsically named,
 sorry) implements a modest variety of continuous distributions with what I
 believe to be a user-friendly and flexible interface.
 
 This thread inspired me to finish up and upload the 0.1 release (just
 announced on haskell-cafe as well).  The public interface is slightly
 different from earlier releases and the haddock docs for the new one
 failed to build on hackage, but earlier versions have essentially the same
 end-user interface aside from some changes in the module export lists so
 if you'd like to get an idea of the basic spirit of the system you can
 browse the docs for the earlier releases.  Alternatively, feel free to
 browse the source and steal some of the implementations (many of which
 were, in turn, translated from other sources such as wikipedia or the
 Numerical Recipes book).
 
 Unfortunately, the old documentation is much sparser and terser than the
 new documentation that failed to build, but if nothing else you can
 download and build the docs yourself for the new one.

I build docs anyway ;). I discovered random-fu just before 0.1 release
and it have nice, monadic interface :D

I guess all it lacks is something to 'just' use IO without state etc.
for fast typing in ghci - otherwise is IMHO perfect.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: PDF generation?

2010-06-07 Thread Maciej Piechotka
On Tue, 2010-06-01 at 21:45 +0300, Yitzchak Gale wrote:
 I wrote:
  I have often generated PostScript from Haskell...
  Then you convert the PS to PDF using any of the nice
  utilities around for that
 
 Pierre-Etienne Meunier wrote:
  Isn't there a problem with non-type 1 vectorial fonts being
  rasterized during this conversion ?
 
 No.
 
 PDF is just a simplified, compressed encoding of PostScript.
 Unless there is some special reason to do so, why would
 a conversion utility go to the trouble of rasterizing fonts
 instead of just copying them in?
 
 Perhaps something like ImageMagick might do that; its
 internal format is a raster.
 
 Regards,
 Yitz

PDF is not just simplified, compressed encoding of PostScript. Or at
least - LaTeX have some features PDF-only.

For example PDF can have hyper-links (both to local and external
content). It can be scripted in JavaScript (don't ask me why) and can
have form (OK. So I can fill them and print probably). 

Regards 


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Difference between div and /

2010-06-03 Thread Maciej Piechotka
On Thu, 2010-06-03 at 12:44 +1200, Richard O'Keefe wrote:
 On Jun 3, 2010, at 1:13 AM, Maciej Piechotka wrote:
 
  On Wed, 2010-06-02 at 14:01 +1200, Richard O'Keefe wrote:
  For what applications is it useful to use the same symbol
  for operations obeying (or in the case of floating point
  operations, *approximating* operations obeying) distinct laws?
 
 
 
  If the given operations do share something in common. For example * is
  usually commutative. However you do use it with quaternions (Hamilton
  product). You even write ij = k despite the fact that ji = -k.
 
 I think you just made my point:  Commutativity is NOT one of the  
 standard
 properties that * is EXPECTED to possess. 

I don't think that many people expect * to be not commutative (I'm not
speaking about people who deal with Mathematics - I mean 'average
person' and 'average programmer'). 


 If you look at the Int and Double instance of Random in
 the Random.hs that comes with Hugs, you'll see they use
 different code.  It's not because of any problem with /
 per se but because they need genuinely different algorithms.
 
 

Point taken.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Re: Difference between div and /

2010-06-03 Thread Maciej Piechotka
On Wed, 2010-06-02 at 16:11 +0200, Henning Thielemann wrote:
 Sorry, I missed this post.
 
 
 Maciej Piechotka schrieb:
 
  Well - i tried to write some package dealing with distributions etc. 
  
  If you have something like that:
  
  instance ... = Distribution (Linear a) a where
  rand (Linear f s) g =
  let (gf, gt) = genRange g
  (v, g') = next g
  in (g', f + (fromIntegral v * s) / fromIntegral (gt - gf))
  
  (I haven't check it but IMHO it is right implementation)
  
  Now I have following options:
  
   - Implement per Int/Int8/...
   - Implement IntegerLinear and FractionalLinear separatly
 
 That is, what you need is a general division with rounding. But you
 might more generally want a custom type class with a method that selects
 an element from a set for given parameters gf, gt, v. This way, you
 could also handle distributions on Enumeration types. You certainly you
 do not want, say a division operation on Monday, Tuesday, ..., Sunday,
 but having a probability distribution of weekdays is very reasonable.
 
 Btw. you may want to have a look at:
http://hackage.haskell.org/package/probability

Hmm. Thanks - however I fail to figure out how to do something like:

generate a random number with normal distribution with average avg and
standard deviation stdev.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Difference between div and /

2010-06-02 Thread Maciej Piechotka
On Wed, 2010-06-02 at 14:01 +1200, Richard O'Keefe wrote:
 For what applications is it useful to use the same symbol
 for operations obeying (or in the case of floating point
 operations, *approximating* operations obeying) distinct laws?
 
 

If the given operations do share something in common. For example * is
usually commutative. However you do use it with quaternions (Hamilton
product). You even write ij = k despite the fact that ji = -k.

I gave the code which might have work for both Integral and Fractional
but it is not possible to type it in Haskell. Although I wouldn't mind
something like:

class Num a = Divisable a where
(./.) :: a - a - a

class (Real a, Enum a, Divisable a) = Integral a where
div = (./.)
...

class Divisable a = Fractional a where
(/) = (./.)
...

(/ and div preserve their meaning, ./. is the generalized division)

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Difference between div and /

2010-06-01 Thread Maciej Piechotka
I started to wonder what is the difference between div and / so they are
2 separate symbols.

div:
  Take a Integral divide and round (down)

(/):
  Take a Fractional divide and usually round

In some applications I would like to use any of those but it is not
possible. Is this unification taken into account while reworking numeric
classes?

I.e. why not:

class Num a = Divisable a where
(/) :: a - a - a

class (Real a, Enum a, Divisable a) = Integral a where
quot :: a - a - a
rem :: a - a - a
div = (/)
mod :: a - a - a
x `quotRem` y = (x `quot` y, x `rem y)
x `divMod` y = (x `div` y, x `mod` y)
toInteger :: a - Integer

class Divisable a = Fractional a where
recip = (1/) :: a - a
fromRational :: Rational - a

(Example does not take into account other refactoring)

Regards

PS. Why is Fd/cPid etc. Integral or even Num?
What does (stdin + stderr) `mod` stdout mean (result will be stdin).


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Difference between div and /

2010-06-01 Thread Maciej Piechotka
On Tue, 2010-06-01 at 22:40 +0200, Jonas Almström Duregård wrote:
  One might expect a == (a/b)*b and other common arithmetic formulas to
  hold for division?
 
  Better not if one's using Float or Double.
 
 I figured someone would say that :)
 
 What about this one:
 round (a/b/c) == round (a/(b*c))
 
 Of course this doesn't work on Integers...
 

Hmm. C, Java  co.[1] seems to not have this problem. Also having common
division operator is well - useful.

I don't think it would create much confusion. At least no more than IEEE
standard.

[1] By co I mean Ruby, Python, Perl and others. There are no so many
languages that do recognize the difference.


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Difference between div and /

2010-06-01 Thread Maciej Piechotka
On Tue, 2010-06-01 at 15:20 -0400, Aaron D. Ball wrote:
 
  What does (stdin + stderr) `mod` stdout mean (result will be stdin).
 
 In my GHCi (6.12.1) with System.IO, this fails because Handle is not a
 numeric type.  What implementation are you using? 

Ups. I missed the Handle with Fd. Which does not change point
significantly. 

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Difference between div and /

2010-06-01 Thread Maciej Piechotka
On Tue, 2010-06-01 at 15:29 -0700, Evan Laforge wrote:
  [1] By co I mean Ruby, Python, Perl and others. There are no so many
  languages that do recognize the difference.
 
 % python -Q new
 Python 2.4.6 (#1, Aug  3 2009, 17:05:16)
 [GCC 4.0.1 (Apple Inc. build 5490)] on darwin
 Type help, copyright, credits or license for more information.
 10 / 3
 #- 3.3335
 10 // 3
 #- 3
 
 
 The python guys decided that int/int - int was a mistake, but because
 it's an incompatible change, the removal process has been long (hence
 the -Q flag, or a from __future__ import).  In fact, I think they gave
 up on making it the default before python 3.
 
 I appreciate that haskell has differentiated from the beginning.

Well - i tried to write some package dealing with distributions etc. 

If you have something like that:

instance ... = Distribution (Linear a) a where
rand (Linear f s) g =
let (gf, gt) = genRange g
(v, g') = next g
in (g', f + (fromIntegral v * s) / fromIntegral (gt - gf))

(I haven't check it but IMHO it is right implementation)

Now I have following options:

 - Implement per Int/Int8/...
 - Implement IntegerLinear and FractionalLinear separatly

Neither of choices are IMHO not ideal.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Difference between div and /

2010-06-01 Thread Maciej Piechotka
On Wed, 2010-06-02 at 01:13 +0200, Daniel Fischer wrote:
 On Wednesday 02 June 2010 00:55:08, Maciej Piechotka wrote:
  On Tue, 2010-06-01 at 15:29 -0700, Evan Laforge wrote:
[1] By co I mean Ruby, Python, Perl and others. There are no so many
languages that do recognize the difference.
  
   % python -Q new
   Python 2.4.6 (#1, Aug  3 2009, 17:05:16)
   [GCC 4.0.1 (Apple Inc. build 5490)] on darwin
   Type help, copyright, credits or license for more information.
   10 / 3
   #- 3.3335
   10 // 3
   #- 3
  
  
   The python guys decided that int/int - int was a mistake, but because
   it's an incompatible change, the removal process has been long (hence
   the -Q flag, or a from __future__ import).  In fact, I think they gave
   up on making it the default before python 3.
  
   I appreciate that haskell has differentiated from the beginning.
 
  Well - i tried to write some package dealing with distributions etc.
 
  If you have something like that:
 
  instance ... = Distribution (Linear a) a where
  rand (Linear f s) g =
  let (gf, gt) = genRange g
  (v, g') = next g
  in (g', f + (fromIntegral v * s) / fromIntegral (gt - gf))
 
  (I haven't check it but IMHO it is right implementation)
 
  Now I have following options:
 
   - Implement per Int/Int8/...
   - Implement IntegerLinear and FractionalLinear separatly
 
 - use realToFrac instead of fromIntegral
 (using the logfloat package is probably not a bad idea then)
 

I'm not quire sure how to use it. I would have to either use floor/...
which would make result Integral or left it as it is and having
(Fractional a, Real a) constraint.

 
  Neither of choices are IMHO not ideal.
 
 Methinks that is not what you wanted to say ;)
 

Ups. Sorry - it's rather late and I'm not native speaker (and my native
language do use double negation). Neither of the choices are ideal
IMHO.

 
  Regards
 

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Math questions

2010-05-28 Thread Maciej Piechotka
On Tue, 2010-05-25 at 22:47 +0100, Mujtaba Boori wrote:
 Hello 
 I am try to solve this equation
 
 
 Define a higher order function  that tests whether two functions ,
 both defined on integers , coincide for all integers between 1 and 100
 
 
  how can I solve this ?
 is there any thing in Haskell library to solve this kind ?


Not so beginner answer (but not advanced I guess):

import Control.Applicative

check f g = all (liftA2 (==) f g) [1..100]

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Proof question -- (==) over Bool

2010-05-22 Thread Maciej Piechotka
On Sat, 2010-05-22 at 00:15 +, R J wrote:
 I'm trying to prove that (==) is reflexive, symmetric, and transitive
 over the Bools, given this definition:
 
 
 (==)   :: Bool - Bool - Bool
 x == y =  (x  y) || (not x  not y)
 
 
 My question is:  are the proofs below for reflexivity and symmetricity
 rigorous, and what is the proof of transitivity, which eludes me?
  Thanks.
  
 Theorem (reflexivity):  For all x `elem` Bool, x == x.
 
 
 Proof:
 
 
   x == x
   ={definition of ==}
   (x  x) || (not x  not x)
   ={logic (law of the excluded middle)}
   True
 

I'd add additional step:

x == x = (x  x) || (not x  not x) = x || not x = T
   def  A  A = A   A || not A = T

However it depends on your level - the more advanced you are the more
step you can omit.

 
 Theorem (symmetricity):  For all x, y `elem` Bool, if x == y, then y
 == x.
 
 
 Proof:
 
 
   x == y
   ={definition of ==}
   (x  y) || (not x  not y)
   ={lemma:  () is commutative}
   (y  x) || (not x  not y)
   ={lemma:  () is commutative}
   (y  x) || (not y  not x)
   ={definition of ==}
   y == x
 
 
 Theorem (transitivity):  For all x, y, z `elem` Bool, if x == y, and y
 == z,
 then x == z.
 
 
 Proof: ?
 

For example by cases in Y (assume Y is true and prove it correct and
then assume Y is false and prove it correct. As in logic where there is
law of excluded middle Y have to be true or false it holds). It took
around 7 lines.



Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Type famillies Lifting IO

2010-05-19 Thread Maciej Piechotka
I started playing with type families. I wanted to achieve, for the
beginning, something like:

 import qualified Control.Monad.IO.Class as IOC
 import Control.Monad.Trans.Class
 import Control.Monad.Trans.Cont
 import Data.Functor.Identity

 class (Monad m, Monad (IO' m)) = MonadIO m where
 type IO' m :: * - *
 liftIO :: IO a - IO' m a
 liftM :: m a - IO' m a

It allows to add IO to computation even if computation originally was
'pure'.

First step was easy:

 instance MonadIO Identity where
 type IO' Identity = IO
 liftIO = id
 liftM = return . runIdentity
 
 instance MonadIO IO where
 type IO' IO = IO
 liftIO = id
 liftM = id
 
 instance MonadIO (ST r) where
 type IO' (ST r) = IO
 liftIO = id
 liftM = unsafeSTToIO
 
 --instance IOC.MonadIO m = MonadIO m where
 --type IO' m = m
 --liftIO = IOC.liftIO
 --liftM = id

However I run into problems - this code doesn't want to compile:

 instance MonadIO m = MonadIO (ContT r m) where
 type IO' (ContT r m) = ContT r (IO' m)
 liftIO f = ContT $ \cont - liftIO f = cont
 liftM f = ContT $ \cont - liftM f = cont

Or this:

 instance MonadIO m = MonadIO (ContT r m) where
 type IO' (ContT r m) = ContT r (IO' m)
 liftIO f = lift . liftIO
 liftM f = lift . liftIO

In fact there is strange interfering types of ghci:

ghci :t lift . liftIO
lift . liftIO
  :: (m ~ IO' m1, MonadTrans t, Monad m, MonadIO m1) = IO a - t m a
ghci :t lift . liftIO :: (m ~ IO' m1, MonadTrans t, Monad m, MonadIO
m1) = IO a - t m a

interactive:1:7:
Couldn't match expected type `IO' m' against inferred type `m1'
  `m1' is a rigid type variable bound by
   an expression type signature at interactive:1:18
  NB: `IO'' is a type function, and may not be injective
In the second argument of `(.)', namely `liftIO'
In the expression:
lift . liftIO ::
(m ~ (IO' m1), MonadTrans t, Monad m, MonadIO m1) = IO a -
t m a

What's the problem? I guess I don't understand something basic about
type famillies.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: What makes Haskell difficult as .NET?

2010-05-14 Thread Maciej Piechotka
On Fri, 2010-05-14 at 10:40 -0700, Daryoush Mehrtash wrote:
 In this presentation
 
 http://norfolk.cs.washington.edu/htbin-post/unrestricted/colloq/details.cgi?id=907
 
 the speaker talks about F# on .Net platform.   Early on in the talk he
 says that they did F# because haskell would be hard to make as a .Net
 language.Does anyone know what features of Haskell make it
 difficult as .Net language?
 
 
 
 Daryoush

1. Haskell Class/Type famillies/... are conceptually different then
classes and interfaces.

2. As .Net does not differentiate between IO a and a Haskell cannot feel
completely native (hand-made FFI or everything in IO)

3. .Net does differentiate between variables and functions with 0
arguments.

4. .Net types are not lazy. String is not [Char]. Arrays are used in
many places.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: What makes Haskell difficult as .NET?

2010-05-14 Thread Maciej Piechotka
On Fri, 2010-05-14 at 22:54 -0400, C. McCann wrote:
 On Fri, May 14, 2010 at 8:39 PM, Maciej Piechotka uzytkown...@gmail.com 
 wrote:
  1. Haskell Class/Type famillies/... are conceptually different then
  classes and interfaces.
 
 I believe interfaces would be roughly equivalent to the subset of
 single-parameter type classes such that:
   - All type class methods are functions
   - The first argument of each function is the class's type parameter,
 fully applied to any type parameters it needs
   - The class's type parameter appears nowhere else
 

I'm not sure but also:

- you can write always a new class in Haskell:

class Abc x where
abc :: x - Int

instance Abc Int where abc = id

IIRC .Net interfaces cannot be added outside assembly (I may be wrong).
On the other hand Haskell does not have inheritance.

Generally
Haskell: newtype/data specify data (and type) while classes provides
basic abstract operations on it.
C#/Java/...: Classes specify data AND how to operate on it (including
non-basic operators) and interfaces abstract operations.

- It is not that it can occur once:

class Abc x where
abc :: x - [x]

is roughly:

interface Abcin T {
public IListT abc();
}

- It seems that it is not possible to have default implementations in
interfaces.

  2. As .Net does not differentiate between IO a and a Haskell cannot feel
  completely native (hand-made FFI or everything in IO)
 
 Wouldn't be any worse than using most C bindings in Haskell as is. Or
 using a lot of .NET libraries in F#, to be honest, if you try to write
 functional-idiomatic instead of quasi-imperative code.
 
 Though, considering the near-omnipresent possibility of null
 references, most .NET functions would actually need to return
 something of the form IO (Maybe a).
 

However the problem is that the .Net is suppose to be a single platform
with different syntaxes attacked to it. It does not stop to use F#
operations (without syntax sugar) in C# or VB.

Haskell on .Net would be a foreigner as it is on C. 

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Ideas of a polymorphic Tree in Haskell

2010-05-13 Thread Maciej Piechotka
On Thu, 2010-05-13 at 10:06 -0300, Edgar Z. Alvarenga wrote:
 Hi,
 
 I created a small Genetic Algorithm program, replicating this 
 work (Statistical mechanics of program systems - JP Neirotti, N.
 Caticha, Journal of Physics A  Math and Gen) made in Lisp. When a
 restricted the problem just for one type, the Haskell program worked
 perfectly with much less lines and a lot faster than the Lisp program.
 The problem was when I tried to generalize to polymorphic types. 
 
 I'm using this datatype to represent a program:
 
 data Tree a = Bin (String, (a - a - a)) (Tree a) (Tree a)
 | Un (String, (a - a)) (Tree a)
 | V
 
 And can convert a Tree to a function with:
 
 treeToFunc :: Tree a - a - a
 treeToFunc (Bin f l r) =  (snd f) $ treeToFunc l * treeToFunc r
 treeToFunc (Un f u) = (snd f).(treeToFunc u)
 treeToFunc V = id
 
 I already create another datatype to represent a polymorphic program
 (using GADT or existentials), but doesn't see a way to convert this kind
 of tree to a function. 
 
 Anyone has any idea?
 
 Thanks,
 Edgar

Hmm. What GDAT/existential do you use (for lazy people who do not want
to read paper)? How is it programmed in Lisp?

data Tree a where
Bin :: String - (c - (a, b)) - (a - b - c) - Tree a - Tree b
- Tree c
Un :: String - (a - a) - Tree a
V :: Tree a

treeToFunc :: Tree a - a - a
treeToFunc (Bin _ f g l r) v = let ~(x, y) = f v
   in g (treeToFunc l x) (treeToFunc r y)
treeToFunc (Un _ f)v = f v
treeToFunc V   v = v

Or

data Tree a where
Bin :: String - Tree a - Tree b - Tree (a, b)
Un :: String - (a - a) - Tree a
V :: Tree a

treeToFunc :: Tree a - a - a
treeToFunc (Bin _ l r) (a, b) = (treeToFunc l a, treeToFunc r b)
treeToFunc (Un _ f)v  = f v
treeToFunc V   v  = v

Both compiles but I'm not sure if they are what you want.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: IO (Either a Error) question

2010-05-07 Thread Maciej Piechotka
On Fri, 2010-05-07 at 19:26 -0700, John Meacham wrote:
 On Fri, May 07, 2010 at 08:27:04PM -0400, Dan Doel wrote:
  Personally, I don't really understand why unfailable patterns were canned
  (they don't seem that complicated to me), so I'd vote to bring them back, 
  and
  get rid of fail. But hind sight is 20/20, I suppose (or perhaps there exist
  cogent arguments that I haven't heard).
 
 What counts as unfailable?
 
 (x,y) probably,  but what about
 
 data Foo = Foo x y
 
 If we don't allow it, we add 'magic' to tuples, which is a bad thing, if
 we do allow it, there are some odd consequences.
 
 adding another constructor to Foo will suddenly change the type of do
 notations involving it non locally. said constructor may not even be
 exported from the module defining Foo, its existence being an
 implementation detail.
 
 All in all, it is very hacky one way or another. Much more so than
 having 'fail' in Monad.
 
 John
 

Sorry I'm asking but why:

do Constructor x y z - f
   g x y z

is not compiled into:

f = \(Constructor x y z) - g x y z

Hence using exactly the same way or reporting errors as pure functions?
I.e. why fail !== error[1]

Regards

[1] Well - what came to my mind is something like:

func :: Either a b - Maybe b
func f = do Right x - f
return x

But:
1. It's IMHO vary bad style as it silently fails in cases mentioned
above.
2. It is not obvious knowing rest of Haskell. I expected until now a
pattern failure error.


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Re: Haskell and scripting

2010-05-06 Thread Maciej Piechotka
On Wed, 2010-05-05 at 17:18 -0400, Kyle Murphy wrote:
 Concerning your second point, I think just about any functional
 language isn't going to be simple or quick to learn. It's simply not a
 way of approaching problems that your average person (even your
 average programmer) is used to dealing with. Things like fold and map,
 the work horses of functional programming, are simply too foreign to
 most peoples imperative way of approaching problems.
 
 -R. Kyle Murphy 

Sorry - I wanted to respond to many posts in this thread but I choose
the first post:

1. While doing fold/map may not be what is simple for average programmer
I guess pattern matching/some HL functions can be relatively simple for
others (pureness on the other hand do not). For example average person
thinks Add 1 to each element of list.

Imperative way:

for i = 0 to l.length:
l[i] = l[i] + 1 # WTF? There is no x such that x = x + 1

Functional way:

callOnEvery _ [] = [] 
callOnEvery f (x:xs) = f x:xs -- Built-in function 'map'
  -- Name could be 'better'

add1 x = x + 1

add1ToEachElement xs = callOnEvery add1 xs

Please note that I heard about person who wrote 'awesome game' in .exe
file (definitely _declarative_ style of programming ;) ) and expected it
to run ;) [Although fortunately it was 'hobbiest'].

2. Lisp readability depends much on formatting. While I cannot write
LISP I'm usually able to read it)

(defun hello-world ()
(format t hello, world))

Is a merge between:

def hello_world():
print hello, world

and

void hello_world() {
println(hello, world)
}

Of course you can write obfuscation competition entries in LISP.

3. For the list of universities that first teaches functional
programming - ICL begins with Haskell and from non-imperative languages
Prolog is in the first year curriculum.

Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


  1   2   3   >