Re: [Haskell-cafe] instance Enum Double considered not entirely great?

2011-09-26 Thread Lennart Augustsson
If you do [0.1, 0.2 .. 0.3] it should leave out 0.3.  This is floating point
numbers and if you don't understand them, then don't use them.  The current
behaviour of .. for floating point is totally broken, IMO.

  -- Lennart

On Fri, Sep 23, 2011 at 6:06 AM, Chris Smith cdsm...@gmail.com wrote:

 On Fri, 2011-09-23 at 11:02 +1200, Richard O'Keefe wrote:
  I do think that '..' syntax for Float and Double could be useful,
  but the actual definition is such that, well, words fail me.
  [1.0..3.5] = [1.0,2.0,3.0,4.0]   Why did anyone ever think
  _that_ was a good idea?

 In case you meant that as a question, the reason is this:

Prelude [0.1, 0.2 .. 0.3]
[0.1,0.2,0.30004]

 Because of rounding error, an implementation that meets your proposed
 law would have left out 0.3 from that sequence, when of course it was
 intended to be there.  This is messy for the properties you want to
 state, but it's almost surely the right thing to do in practice.  If the
 list is longer, then the most likely way to get it right is to follow
 the behavior as currently specified.  Of course it's messy, but the
 world is a messy place, especially when it comes to floating point
 arithmetic.

 If you can clear this up with a better explanation of the properties,
 great!  But if you can't, then we ought to reject the kind of thinking
 that would remove useful behavior when it doesn't fit some theoretical
 properties that looked nice until you consider the edge cases.

 --
 Chris



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

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


Re: [Haskell-cafe] instance Enum Double considered not entirely great?

2011-09-26 Thread Lennart Augustsson
I totally agree with you.  Haskell is very broken when it comes to [x..y]
for floating point.
It's an attempt to make it more friendly for naive users, but there is no
way FP can be made friendly.  Any such attempts will fail, so make it usable
for people who understand FP instead.

  -- Lennart

On Mon, Sep 26, 2011 at 10:02 AM, Richard O'Keefe o...@cs.otago.ac.nz wrote:


 On 23/09/2011, at 4:06 PM, Chris Smith wrote:

  On Fri, 2011-09-23 at 11:02 +1200, Richard O'Keefe wrote:
  I do think that '..' syntax for Float and Double could be useful,
  but the actual definition is such that, well, words fail me.
  [1.0..3.5] = [1.0,2.0,3.0,4.0]   Why did anyone ever think
  _that_ was a good idea?
 
  In case you meant that as a question, the reason is this:
 
 Prelude [0.1, 0.2 .. 0.3]
 [0.1,0.2,0.30004]

 That shows why it is a *BAD* idea.
 0.3 comes out as 0.29998890
 so the final value is clearly and unambiguously
 *outside* the requested range.

  Because of rounding error, an implementation that meets your proposed
  law would have left out 0.3 from that sequence, when of course it was
  intended to be there.

 But the output shown does NOT include 0.3 in the sequence.

 0.3 `elem` [0.1, 0.2 .. 0.3]

 is False.

   This is messy for the properties you want to
  state, but it's almost surely the right thing to do in practice.

 I flatly deny that.  I have access to several programming languages
 that offer 'REAL DO', including Fortran, R, and Smalltalk.  They all
 do the same thing; NONE of them overshoots the mark.

 If I *wanted* the range to be enlarged a little bit,
 I would enlarge it myself:  [0.1, 0.2 .. 0.3+0.001] perhaps.

   If the
  list is longer, then the most likely way to get it right is to follow
  the behavior as currently specified.

 I don't see the length of the list as having much relevance; if the
 bug shows up in a list of length 3, it is clearly not likely to be
 any better for longer lists.  This is NOT by any stretch of the
 imagination, it is a BUG.  If you have used REAL DO in almost any other
 programming language, you will be shocked and dismayed by its behaviour
 in Haskell.

 Programming constructs that are implemented to do what would probably
 meant if you were an idiot instead of what you *asked* for are
 dangerous.

  If you can clear this up with a better explanation of the properties,
  great!  But if you can't, then we ought to reject the kind of thinking
  that would remove useful behavior when it doesn't fit some theoretical
  properties that looked nice until you consider the edge cases.

 I don't see any useful behaviour here.
 I see an implausibly motivated bug and while I _have_ written REAL DO
 in the past (because some languages offer only one numeric type), I
 cannot imagine wishing to do so in Haskell, thanks to this bug.  What
 I want now is a compiler option, on by default, to assure me that I am
 *not* using floating point numeration in Haskell.



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

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


Re: [Haskell-cafe] mapM is supralinear?

2011-09-26 Thread Lennart Augustsson
You seem to ignore garbage collection.

On Sat, Sep 24, 2011 at 6:40 AM, Arseniy Alekseyev 
arseniy.alekse...@gmail.com wrote:

  Apparently it doesn't, and it seems to be fixed now.

 Does anyone know what exactly the bug was? Because this seems like a
 serious bug to me. I've run into it myself today and wasn't happy.
 Linear algorithms should work in linear time however much memory they
 allocate (modulo cache thrashing of course). Existence of people
 claiming otherwise surprises me!


 On 22 September 2011 01:05, John Lato jwl...@gmail.com wrote:
  On Wed, Sep 21, 2011 at 1:57 PM, Tim Docker t...@dockerz.net wrote:
 
  On 09/09/2011, at 8:19 PM, John Lato wrote:
 
  Agreed.  Whenever I'd like to use mapM (or any other function for
  which a *M_ is available), I've found the following rules helpful:
 
  1.  If I can guarantee the list is short (~ n=20), go ahead and use
 mapM
  2.  Otherwise use mapM_, foldM_, or foldM if a real reduction is
  possible (i.e. not foldM snocM []).
 
  Step 2 sometimes requires changing my design, but it's always been for
  the better.  `mapM_` tends to require more pipeline composition, so
  it's leveraging the language's strengths.
 
  This thread is really interesting - it relates directly to problems I am
  currently
  having with mapM over large lists (see the thread stack overflow
 pain).
 
  Can you explain what you mean by mapM_ tends to require more pipeline
  composition?
  In what way is it leveraging the language strengths?
 
  Hmm, that is suitably cryptic.  One way to think of it is an inversion
  of control.  Instead of operating on whole collections of things in a
  monad, you specify monadic actions (pipelines) which are applied
  sequentially to each input.
 
  Here's a simple example.  Suppose you have a bunch of data serialized
  to files, and you want to read each file into a data structure, apply
  some process based upon the last file's data, and write out the output
  to new files.  One way to do that would look like:
 
  do
 dats - mapM readMyData files
 let pairs = zip (mempty:dats) dats
 zipWithM_ (\(last, this) fname - writeMyData (update last this)
  fname) pairs newFiles
 
  However, you could also put everything into a single monadic
  operation, like this
 
  do
 foldM_ (\last (infile, outfile) - do
 this - readMyData
 infile
 writeMyData
  (update last this) outfile
 return this
)
mempty
(zip files newFiles)
 
  The first interleaves control (mapM, zipWIthM_) with monadic actions
  (file IO), whereas the second only has one control function (foldM_)
  which completely processes one input.  I say this is more pipeline
  composition because you have to create an entire pipeline from input
  to output, which is then sequentially fed inputs by the control
  function.
 
  I say this leverages Haskell's strengths because it's quite easy to
  compose functions and monadic actions in Haskell.  It also tends to be
  garbage-collector friendly.  I also find it much easier to reason
  about space usage.  You don't need to worry if part of a list is being
  retained, because the full list of data doesn't appear anywhere.  If
  you need to access prior elements they're specified explicitly so you
  know exactly how much data you're holding on to.
 
  My perspective might be warped by my work on iteratees, but I find
  this a very natural approach.
 
  John L.
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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

___
Haskell-Cafe 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 Lennart Augustsson
It probably is portable, but I'd think only GHC has all the necessary
extensions.

On Sun, Jan 23, 2011 at 12:27 PM, Maciej Piechotka uzytkown...@gmail.comwrote:

 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

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


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


Re: [Haskell-cafe] Set monad

2011-01-09 Thread Lennart Augustsson
That looks like it looses the efficiency of the underlying representation.

On Sun, Jan 9, 2011 at 6:45 AM, Sebastian Fischer fisc...@nii.ac.jp wrote:

 On Sun, Jan 9, 2011 at 6:53 AM, Lennart Augustsson lenn...@augustsson.net
  wrote:

 It so happens that you can make a set data type that is a Monad, but it's
 not exactly the best possible sets.

 module SetMonad where

 newtype Set a = Set { unSet :: [a] }


 Here is a version that also does not require restricted monads but works
 with an arbitrary underlying Set data type (e.g. from Data.Set). It uses
 continuations with a Rank2Type.

 import qualified Data.Set as S

 newtype Set a = Set { (-) :: forall b . Ord b = (a - S.Set b) -
 S.Set b }

 instance Monad Set where
   return x = Set ($x)
   a = f  = Set (\k - a - \x - f x - k)

 Only conversion to the underlying Set type requires an Ord constraint.

 getSet :: Ord a = Set a - S.Set a
 getSet a = a - S.singleton

 A `MonadPlus` instance can lift `empty` and `union`.

 instance MonadPlus Set where
   mzero = Set (const S.empty)
   mplus a b = Set (\k - S.union (a - k) (b - k))

 Maybe, Heinrich Apfelmus's operational package [1] can be used to do the
 same without continuations.

 [1]: http://projects.haskell.org/operational/

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


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


Re: [Haskell-cafe] Set monad

2011-01-08 Thread Lennart Augustsson
It so happens that you can make a set data type that is a Monad, but it's
not exactly the best possible sets.

module SetMonad where

newtype Set a = Set { unSet :: [a] }

singleton :: a - Set a
singleton x = Set [x]

unions :: [Set a] - Set a
unions ss = Set $ concatMap unSet ss

member :: (Eq a) = a - Set a - Bool
member x s = x `elem` unSet s

instance Monad Set where
return = singleton
x = f = unions (map f (unSet x))


On Sat, Jan 8, 2011 at 9:28 PM, Peter Padawitz peter.padaw...@udo.eduwrote:

 Hi,

 is there any way to instantiate m in Monad m with a set datatype in order
 to implement the usual powerset monad?

 My straightforward attempt failed because the bind operator of this
 instance requires the Eq constraint on the argument types of m.

 Peter



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

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


Re: [Haskell-cafe] Incorrectly inferring type [t]

2010-12-29 Thread Lennart Augustsson
First, what type would such a function have?
Certainly not [a]-[b], because that type say that it can take a list of any
type and turn it into a list of any other type, e.g.,
[Int]-[Bool].


On Thu, Dec 30, 2010 at 4:05 AM, william murphy will.t.mur...@gmail.comwrote:

 Hi All,

 I've spent a lot of time trying to write a version of concat, which
 concatenates lists of any depth:
 So:
 concat'' [[[1,2],[3,4]],[[5]]]   would return: [1,2,3,4,5]


 The code is:
 concat'' :: [a] - [b]
 concat'' ((y:ys):xs) = (concat'' (y:ys)) ++ (concat'' xs)
 concat'' []  = []
 concat'' (x:xs)  = (x:xs)


 And the inevitable error is:
 test.hs:298:12:
 Couldn't match expected type `a' against inferred type `[t]'
   `a' is a rigid type variable bound by
   the type signature for `concat''' at test.hs:297:13
 In the pattern: y : ys
 In the pattern: (y : ys) : xs
 In the definition of `concat''':
 concat'' ((y : ys) : xs) = (concat'' (y : ys)) ++ (concat'' xs)

 test.hs:300:24:
 Couldn't match expected type `b' against inferred type `[t]'
   `b' is a rigid type variable bound by
   the type signature for `concat''' at test.hs:297:20
 In the first argument of `(:)', namely `x'
 In the expression: (x : xs)
 In the definition of `concat''': concat'' (x : xs) = (x : xs)
 Failed, modules loaded: none.


 Any help or advice would be appreciated.
 Will

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


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


Re: [Haskell-cafe] how to write a loop in haskell way

2010-12-19 Thread Lennart Augustsson
Recursion replaces loops.  If it needs to be monadic or not depends on what
you want to do.

On Sun, Dec 19, 2010 at 10:53 AM, ender crazyen...@gmail.com wrote:

 2010/12/19 Henning Thielemann lemm...@henning-thielemann.de:
 
  On Sun, 19 Dec 2010, ender wrote:
 
   do
   alloca $ \value - do
   poke value (50::Int)
   allocaArray 4 $ \part_stack - do
   alloca $ \part_ptr - do
   poke part_ptr part_stack
   let loop = do
val - peek value
if val == 0 then return () else do
p - peek part_ptr
poke p (val `rem` 1)
poke part_ptr (p `plusPtr` 1)
poke value (val `quot` 1)
loop
   loop
 
  and I really think that's not a haskell way, it's just translate c
  code into haskell code byte by byte
  My question is: how to translate above c code into haskell in haskell
  way
 
  If the count of loop runs does not depend on results of the loop body,
 then
  'mapM' and 'mapM_' applied to the list of increasing pointers are your
  friends. In your case, the loop aborts when 'val' becomes zero. I'm
  certainly thinking too complicated, but you might use MaybeT IO () (e.g.
  from transformers package) and abort 'mapM_' with 'mzero' when 'val'
 becomes
  zero. (MaybeT IO a) is like an IO monad with an early exit (somehow an
  exception) option.
 
 Hi Henning:
   Thanks for your quick reply. So recursive and monad is the proper
 way to simulate loop,right?

 Thanks and BR

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

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


Re: [Haskell-cafe] [URGENT] DNS problems at haskell.org?

2010-12-18 Thread Lennart Augustsson
I bet they did try to contact the owner.  But when the contact email no
longer works nobody will get the messages.

On Sat, Dec 18, 2010 at 3:35 PM, Ketil Malde ke...@malde.org wrote:

 Karel Gardas karel.gar...@centrum.cz writes:

 
 http://www.reddit.com/r/haskell/comments/encrv/whats_happened_to_haskellorg_did_someone_forget/c19guw1

 Quoth dons:

 | The domain name was seized by Network Solutions (it wasn't due to
 | expire until this time next year). The confusion seems to be that
 | while Yale was the nominated owner, it was administered by Galois.

 | We've contacted Network Solutions and resolve their confusion.

 Would it be impertinent to question the wisdom of using a domain
 provider that just breaks a paid-for and working site without contacting
 the owner?  How about contacting another, more professional registrar
 instead of Network Solution?

 http://www.host-shopper.com/web-hosts-reviews.html?sortBy=rating

 -k
 --
 If I haven't seen further, it is by standing in the footprints of giants

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

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


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

2010-12-16 Thread Lennart Augustsson
IO

On Thu, Dec 16, 2010 at 6:03 PM, John Smith volderm...@hotmail.com wrote:

 On 15/12/2010 14:31, Lennart Augustsson wrote:

 Yes, I think there should be a MonadFail distinct from MonadPlus.
 Some types, like IO, are not in MonadPlus, but have a special
 implementation of the fail method.

 Personally, I think fail should just be removed, but that would break
 existing code.
 The fail method was introduced for the wrong reasons (better error
 messages was the excuse).


 Which other monads (other than MonadPlus subclasses) define fail?



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

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


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

2010-12-15 Thread Lennart Augustsson
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.

  -- Lennart

2010/12/15 Tillmann Rendel ren...@informatik.uni-marburg.de

 Hi John,


 John Smith wrote:

 Perhaps pattern match failures in a MonadPlus should bind to mzero - I
 believe that this is what your example and similar wish to achieve.


 You updated the proposal to say:

 a failed pattern match should error in the same way as is does for pure
 code, while in
 MonadPlus, the current behaviour could be maintained with mzero


 Can you be more specific as to how that would interact with polymorphism
 and type inference? What does it mean to be in MonadPlus? How does the
 compiler know?

 For example, what would be the static types and dynamic semantics of the
 following expressions:

  1. \a - do {Just x - return (Just a); return x}

  2. do {Just x - return Nothing; return x}

  3. \a - do {Just x - a; return x}

  4. \a b - do {(x, _) - return (a, b); return x}

  5. \a - do {(x, _) - return a; return x}

Tillmann


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

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


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

2010-12-15 Thread Lennart Augustsson
Yes, I think there should be a MonadFail distinct from MonadPlus.
Some types, like IO, are not in MonadPlus, but have a special implementation
of the fail method.

Personally, I think fail should just be removed, but that would break
existing code.
The fail method was introduced for the wrong reasons (better error messages
was the excuse).

  -- Lennart

On Wed, Dec 15, 2010 at 11:51 AM, John Smith volderm...@hotmail.com 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).



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

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


Re: [Haskell-cafe] Re: Haskell is a scripting language inspired by Python.

2010-11-04 Thread Lennart Augustsson
KRC, Miranda, and LML all predate Haskell and have list comprehensions.

On Thu, Nov 4, 2010 at 3:16 PM, Jonathan Geddes
geddes.jonat...@gmail.com wrote:
 Regardless of which languages got which features for which other
 languages, Haskell is surely NOT a scripting language inspired by
 python...

 Also, it was my understanding that Python got list comprehensions
 straight from Haskell. Unless, of course, some of the pre-Haskells
 also had this feature.

 Haskell: [f x | x - xs, x = 15]
 Python: [f(x) for x in xs if x = 15]

 The Python version reads the way I would speak the Haskell one if I
 were reading code aloud, though I might say such that rather than
 for

 --Jonathan Geddes

 On Thu, Nov 4, 2010 at 6:05 AM, Stephen Tetley stephen.tet...@gmail.com 
 wrote:
 On 4 November 2010 12:03, Stephen Tetley stephen.tet...@gmail.com wrote:
 Python is approximately as old as Python and most likely got
 indentation from ABC.

 Apologies that should read - as old as Haskell

 Obviously IDSWIM - (I _don't_ say what I mean).
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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

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


Re: [Haskell-cafe] Re: Haskell is a scripting language inspired by Python.

2010-11-04 Thread Lennart Augustsson
It happened at various universities around the world.  Look at the
original Haskell committee and you'll get a good idea where.

The smallest Haskell I know of is Gofer/Hugs; it originally ran on a 640k PCs.
Before that languages like SASL and KRC ran on PDP-11 with 64k memory.
None of these had a compiler that was bootstrapped, but I had a simple
functional language that compiled itself and ran in 64K.
The smallest bootstrapped Haskell compiler is NHC which (I think) runs
in a few MB.

  -- Lennart

On Thu, Nov 4, 2010 at 8:54 PM, Andrew Coppin
andrewcop...@btinternet.com wrote:
 Where the heck did all this
 stuff happen?! Can you actually run something like Haskell with mere
 kilobytes of RAM?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What is simplest extension language to implement?

2010-11-02 Thread Lennart Augustsson
I don't understand.  Why don't you use Haskell as the scripting language?

On Tue, Nov 2, 2010 at 7:04 AM, Permjacov Evgeniy permea...@gmail.com wrote:
 Let us think, that we need some scripting language for our pure haskell
 project and configure-compile-run is not a way. In such a case a
 reasonably simple, yet standartized and wide known language should be
 implemented. What such language may be?
  R(4/5/6)RS ?
  EcmaScript ?
  Some other ?
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Re: Mysterious fact

2010-11-02 Thread Lennart Augustsson
Jon, you beat me to it.  I was going to mention Ponder.

But Ponder did have a builtin type, it had the function type built in. :)

  -- Lennart

On Tue, Nov 2, 2010 at 9:47 PM, Jon Fairbairn
jon.fairba...@cl.cam.ac.uk wrote:
 Andrew Coppin andrewcop...@btinternet.com writes:

 The other day, I accidentally came up with this:

 |{-# LANGUAGE RankNTypes #-}

 type  Either  x y=  forall r.  (x -  r) -  (y -  r) -  r

 left :: x -  Either  x y
 left x f g=  f x

 right :: y -  Either  x y
 right y f g=  g y

 |

 This is one example; it seems that just about any algebraic
 type can be encoded this way. I presume that somebody else
 has thought of this before. Does it have a name?

 You could try reading my PhD thesis!
 http://www.cl.cam.ac.uk/techreports/UCAM-CL-TR-75.html
 contains a link to the full text scanned to a pdf. (That -- 1985
 -- was a long time ago. One thing I really regret about it is
 that there should have been a comma between simple and typed
 in the title. I suspect people think simply typed when they
 see it). It isn't hard to read (one of my examiners said it made
 good bed-time reading).

 Anyway, the relevant part is that Ponder was a programming
 language (Stuart Wray even wrote a GUI programme in it) that had
 (in principle) no built-in types, relying on the type system
 being powerful enough to express anything and the optimiser
 being good enough to convert them to something more sensible.
 In practice neither was /quite/ true, but it got quite close.

 --
 Jón Fairbairn                                 jon.fairba...@cl.cam.ac.uk
 http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html  (updated 2010-09-14)

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

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


Re: [Haskell-cafe] who's in charge?

2010-10-28 Thread Lennart Augustsson
It's working just fine.  I've never wanted a mail client library. :)

  -- Lennart

2010/10/27 Günther Schmidt gue.schm...@web.de:
 Dear Malcolm,

 since there is no mail client library even after 10+ years I suggest to
 rethink the approach, because frankly, it's not working.

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

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


Re: [Haskell-cafe] Re-order type

2010-10-10 Thread Lennart Augustsson
You can use Djinn to generate the glue.  Note that in the example you
give there are many possible ways to make the glue just looking at the
types.
Changing the output types of f so they can't be confused with the
input types we get:

Djinn ? compose :: (c1 - a1 - d) - (a- b - c - (b1,c1,a1)) -
(a - b - c - d)
compose :: (c1 - a1 - d) - (a - b - c - (b1, c1, a1)) - a - b - c - d
compose a b c d e =
  case b c d e of
  (_, f, g) - a f g

  -- Lennart

2010/10/9 André Batista Martins andre...@netcabo.pt:
 Hello,
  exists any algorithm  to determine how terms can be changed to safisty the
 type of one function?


 example:

 f:: a- b - c - (b,c,a)

 f1 ::  c - a - d

 In my first function f i want assign  the output c and a for to input
 of function f1.
 I searched for any solution, but i didn't find any anything.

 One clue i have found is minimal edit distance algorithm for 2 strings.
 Perhaps if i convert de output type of f to one string, and de input of
 f1 to another string and then use this algorithm , i will get one dirty
 solution...

 I'm open to any sugestion.

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


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


Re: [Haskell-cafe] Static computation/inlining

2010-10-10 Thread Lennart Augustsson
I would not worry about doing that at runtime.
The only reliable way to make sure it happens at compile time that I
can think of would be some Template Haskell.
(Or some really deep magic with dictionaries.)

  -- Lennart

On Mon, Oct 11, 2010 at 3:51 AM, Alexander Solla a...@2piix.com wrote:
 Hi everybody,
 I'm working on a module that encodes static facts about the real world.
  For now, I'm working on an ISO 3166 compliant list of countries, country
 names, and country codes.  I've run into a bit of an optimization issue.
 There is a static bijective correspondence between countries and their
 codes.  In order to keep one just one large data structure representation
 as Haskell code, I encoded this bijection using a list.  I'm looking to
 write queries against this list, but it is rather tedious.  I figured I
 could make some Data.Maps to handle it for me.


 -- Country and ISOCountryCodes derive (Data, Eq, Ord, Show, Typeable)
 countries_and_iso_country_codes :: [ (Country, ISOCountryCode) ]
 countries_and_iso_country_codes =

         [ ( Afghanistan                           , ISOCountryCode  AF
 AFG    (isoNumericCode 004) )
         , ( AlandIslands                    , ISOCountryCode  AX    ALA
  (isoNumericCode 248) )
         , ( Albania                            , ISOCountryCode  AL    ALB
  (isoNumericCode 008) )
 ...
         , ( Zimbabwe , ISOCountryCode ZW ZWE (isoNumericCode 716) ) ]
 map_country_to_country_code :: Map Country ISOCountryCode
 map_country_to_country_code = fromList countries_and_iso_country_codes
 map_country_code_to_country :: Map ISOCountryCode Country
 map_country_code_to_country = fromList . fmap (\(a,b) - (b, a)) $
 countries_and_iso_country_codes
 Is there anyway to instruct GHC (and maybe other compilers) to compute these
 maps statically? Are GHC and the other compilers smart enough to do it
 automatically? Although the list isn't huge, I would still rather get rid of
 the O(2*n) operation of turning it into maps at run-time. (Especially since
 some later list encodings like these might be enormous) What should I be
 looking into?
 Thanks
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


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


Re: [Haskell-cafe] Desired behaviour of rounding etc.

2010-10-08 Thread Lennart Augustsson
That code is incorrect.  You can't assume that the base for floating
point numbers is 2, that's something you have to check.
(POWER6 and z9 has hardware support for base 10 floating point.)

  -- Lennart

On Fri, Oct 8, 2010 at 2:08 PM, Daniel Fischer daniel.is.fisc...@web.de wrote:
 The methods of the RealFrac class produce garbage when the value lies
 outside the range of the target type, e.g.

 Prelude GHC.Float truncate 1.234e11 :: Int  -- 32-bits
 -1154051584

 and, in the case of truncate, different garbage when the rewrite rule
 fires:

 Prelude GHC.Float double2Int 1.234e11
 -2147483648

 I'm currently working on faster implementations of properFraction,
 truncate, round, ceiling and floor for Float and Double, so I'd like to
 know

 - does it matter at all what garbage is returned in the above case?
 - if it does, what is the desired behaviour (at least for Int, I can't
 cater for all possibilities)?


 On a related note, in my benchmarks,

 truncFloatGen :: Integral a = Float - a
 truncFloatGen = fromInteger . truncFloatInteger

 truncFloatInteger :: Float - Integer
 truncFloatInteger x =
  case decodeFloat x of
    (m,e) | e == 0  - m
          | e  0   -
            let s = -e
            in if m  0
                  then - ((-m) `shiftR` s)
                  else m `shiftR` s
          | otherwise - m `shiftL` e

 is more than twice as fast as GHC.Float.float2Int, the corresponding for
 Double almost twice as fast as double2Int.

 Can anybody confirm that the above is faster than float2Int on other
 machines/architectures?

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

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


Re: [Haskell-cafe] Re: A GHC error message puzzle

2010-08-13 Thread Lennart Augustsson
So it's a bug in the garbage collector.  It's closing a handle that
clearly is still reachable, otherwise this would not have happened.

On Fri, Aug 13, 2010 at 10:53 AM, Simon Marlow marlo...@gmail.com wrote:
 On 12/08/2010 21:59, Yitzchak Gale wrote:

 Wei Hu wrote:

 nonTermination _ = blackhole where blackhole = blackhole

 My original example was actually:

 process :: String -  String
 process = let x = x in x

 Ah yes, that works too.  But other similar versions don't, like this one:

 process :: String -  String
 process _ = let x = x in x

 Hence why I added the tail in my version.

 So what happens is this:

  - the recursive definition causes the main thread to block on itself
   (known as a black hole)

  - the program is deadlocked (no threads to run), so the runtime
   invokes the GC to see if any threads are unreachable

  - the GC finds that
   (a) the main thread is unreachable and blocked on a blackhole, so it
       gets a NonTermination exception
   (b) the Handle is unreachable, so its finalizer is started

  - the finalizer runs first, and closes the Handle

  - the main thread runs next, and the exception handler for writeFile
   tries to close the Handle, which has already been finalized

 Really hClose shouldn't complain about a finalized handle, I'll see if I can
 fix that.

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

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


Re: [Haskell-cafe] Re: Haskell in Industry

2010-08-10 Thread Lennart Augustsson
Rather than high turnover it indicates (in my experience) that it's
difficult to fill positions in finance.
That's one reason they are advertised repeatedly.

On Tue, Aug 10, 2010 at 12:27 PM, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:
 Malcolm Wallace malcolm.wall...@me.com writes:

 It's disproportionate.  95% of the job offerings in functional
 programming are with investment firms.

 I'm not sure that is really true.  You might see more adverts for
 financial jobs, but often those jobs may be advertised multiple times,
 because different headhunters see an opportunity to earn a slice of
 the pie.  By contrast, non-financial FP jobs are likely to be
 advertised only once, or not at all, because candidates are easily
 found.

 It could also indicate high turn-over for investment firm
 jobs... (i.e. people get sick of it).

 --
 Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com
 IvanMiljenovic.wordpress.com
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Re: Haskell in Industry

2010-08-10 Thread Lennart Augustsson
The former.

On Tue, Aug 10, 2010 at 2:59 PM, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:
 Lennart Augustsson lenn...@augustsson.net writes:

 Rather than high turnover it indicates (in my experience) that it's
 difficult to fill positions in finance.
 That's one reason they are advertised repeatedly.

 Because you can't find people that are good enough (in terms of required
 skill sets, etc.) or because no-one wants the job?

 --
 Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com
 IvanMiljenovic.wordpress.com

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


Re: [Haskell-cafe] Re: Haskell in Industry

2010-08-09 Thread Lennart Augustsson
Out of 10 people trained only 2 should do programming anyway. :)

On Fri, Aug 6, 2010 at 4:58 AM, Tom Hawkins tomahawk...@gmail.com wrote:
 Hi Eil,
 Have you had any trouble training people to use Haskell?

 Yes.  I find that out of 10 people I train, only about 2 pick it up
 and run with it.  I'm starting to believe you are either wired for
 functional programming, or you're not.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Haskell in Industry

2010-08-09 Thread Lennart Augustsson
But do you think there would be more Haskell jobs offered (in absolute
terms), if no investment firms offered jobs?
Is there some kind of quota of job offers that gets used up?

There seems to be more job applicants that job offers at the moment,
so I'm not sure what the problem is.

On Mon, Aug 9, 2010 at 6:59 PM, Tom Hawkins tomahawk...@gmail.com wrote:
 It's disproportionate.  95% of the job offerings in functional
 programming are with investment firms.  I believe investment banking
 is important, but does it really need to dominate a large percentage
 of the world's top tier programmers?  Is computing the risk of
 derivative contracts more important than pursuing sustainable energy,
 new drug discovery, improving crop yields, etc.  Some will argue
 investment banking enables all of these things -- and I'm sure many
 people in the industry go to work everyday feeling proud of their
 contributions.  But I just think most of this talent is going in to
 improve the bottom line and little else.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is toRational a method of Real?

2010-08-05 Thread Lennart Augustsson
Yes, for instance to be able to use functions as number.
Or to be able to use constructive real numbers as numbers, since
equality is not computable.

  -- Lennart

On Thu, Aug 5, 2010 at 4:17 AM, Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com wrote:
 On 5 August 2010 10:15, Lennart Augustsson lenn...@augustsson.net wrote:
 You're right.  It's bad to have toRational in Real.  It's also bad to
 have Show and Eq as superclasses to Num.

 I understand why it's bad to have Show as a superclass, but why Eq?
 Because it stops you from using functions as numbers, etc. ?


 --
 Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com
 IvanMiljenovic.wordpress.com

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


Re: [Haskell-cafe] Why is toRational a method of Real?

2010-08-04 Thread Lennart Augustsson
You're right.  It's bad to have toRational in Real.  It's also bad to
have Show and Eq as superclasses to Num.

On Wed, Aug 4, 2010 at 8:30 PM, Omari Norman om...@smileystation.com wrote:
 Why is toRational a method of Real? I thought that real numbers need not
 be rational, such as the square root of two. Wouldn't it make more sense
 to have some sort of Rational typeclass with this method? Thanks.
 --Omari

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

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


Re: [Haskell-cafe] Re: Instances for Set of Functor, Traversable?

2010-07-27 Thread Lennart Augustsson
But that's not really a solution, since it doesn't make a Functor
instance for Set; it makes a Functor' instance for Set.
If you are willing to not be upwards compatible then, yes, there are solutions.

I think the best bet for an upwards compatible solutions is the
associated constraints,
www.cs.kuleuven.be/~toms/Research/papers/constraint_families.pdf

On Tue, Jul 27, 2010 at 10:17 AM,  o...@okmij.org wrote:

 Lennart Augustsson wrote:
 Try to make Set an instance of Functor and you'll see why it isn't.
 It's very annoying.

 And yet the very simple, and old solution works.

        http://okmij.org/ftp/Haskell/types.html#restricted-datatypes

 We just properly generalize Functor, so that all old functors are new
 functors. In addition, many more functors become possible, including
 Set. In general, we can have functors
        fmap' :: (C1 a, C2 b) = (a - b) - f a - f b
 Incidentally, even an Integer may be considered a functor:
 we can define the fmap' operation fitting the above signature, where
 the constraint C1 a is a ~ Integer.

 Although the use of OverlappingInstances is not required, the
 extension leads to the nicest code; all old functors just work.


 {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
 {-# LANGUAGE OverlappingInstances #-}

 module FunctorEx where

 import Control.Monad
 import Data.Set as S

 class Functor' f a b where
    fmap' :: (a - b) - f a - f b

 -- The default instance:
 -- All ordinary Functors are also extended functors

 instance Functor f = Functor' f a b where
    fmap' = fmap

 -- Now define a functor for a set
 instance (Ord a, Ord b) = Functor' S.Set a b where
    fmap' = S.map


 -- Define a degenerate functor, for an integer
 newtype I a = I Integer deriving Show

 instance Functor'  I Integer Integer where
    fmap' f (I x) = I $ f x

 -- tests

 -- Lists as functors
 test_l = fmap' (+10) [1,2,3,4]
 -- [11,12,13,14]

 -- Sets as functors
 test_s = fmap' (\x - x `mod` 3) $ S.fromList [1,2,3,4]
 -- fromList [0,1,2]

 -- Integer as functor
 test_i = fmap' (* (6::Integer)) $ I 7
 -- I 42


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

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


Re: [Haskell-cafe] Instances for Set of Functor, Traversable?

2010-07-26 Thread Lennart Augustsson
Try to make Set an instance of Functor and you'll see why it isn't.
It's very annoying.

On Mon, Jul 26, 2010 at 11:55 PM, Gregory Crosswhite
gcr...@phys.washington.edu wrote:
 Is there a specific reason why Set doesn't have instances for Functor
 and Traversable?  Or have they just not been written yet?  :-)

 Cheers,
 Greg

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

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


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

2010-06-10 Thread Lennart Augustsson
I would not use the continuation monad just for early exit.  Sounds
like the error monad to me.

2010/6/10 Günther Schmidt gue.schm...@web.de:
 Hi everyone,

 I'm about to write a rather lengthy piece of IO code. Depending on the
 results of some of the IO actions I'd like the computation to stop right
 there and then.

 Now I know in general how to write this but I'm wondering if this is one of
 those occasions where I should make use of the Cont monad to make an early
 exit.

 Günther

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

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


Re: [Haskell-cafe] currying combinators

2010-05-28 Thread Lennart Augustsson
Yes, of course you have to trust Djinn to believe its proof.
That's no different from having to trust me if I had done the proof by hand.
Our you would have to trust yourself if you did the proof.

BTW, Djinn does not do an exhaustive search, since there are
infinitely many proofs.
(Even if you just consider cut free proofs there's usually infinitely many.)

On Fri, May 28, 2010 at 8:14 AM, wren ng thornton w...@freegeek.org wrote:
 Lennart Augustsson wrote:

 So what would you consider a proof that there are no total Haskell
 functions of that type?
 Or, using Curry-Howard, a proof that the corresponding logical formula
 is unprovable in intuitionistic logic?


 It depends on what kind of proof I'm looking for. If I'm looking for an
 informal proof to convince myself, then I'd probably trust Djinn. If I'm
 trying to convince others, am deeply skeptical, or want to understand the
 reasoning behind the result, then I'd be looking for a more rigorous proof.
 In general, that rigorous proof would require metatheory (as you say)---
 either my own, or understanding the metatheory behind some tool I'm using to
 develop the proof. For example, I'd only trust Djinn for a rigorous proof
 after fully understanding the algorithms it's using and the metatheory used
 to prove its correctness (and a code inspection, if I didn't trust the
 developers).


 If Djinn correctly implements the decision procedure that have been
 proven to be total (using meta theory), then I would regard Djinn
 saying no as a proof that there is no function of that type.

 So would I. However, that's adding prerequisites for trusting Djinn--- which
 was my original point: that Djinn says there isn't one is not sufficient
 justification for some folks, they'd also want justification for why we
 should believe Djinn actually does exhaust every possibility.

 --
 Live well,
 ~wren
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] currying combinators

2010-05-27 Thread Lennart Augustsson
So what would you consider a proof that there are no total Haskell
functions of that type?
Or, using Curry-Howard, a proof that the corresponding logical formula
is unprovable in intuitionistic logic?
As I understand, in general this can only be proven using meta theory
rather than the logic itself (it could happen that the given formula
implies absurdity, and then we'd know it can't be proven, given that
the logic is consistent).
If Djinn correctly implements the decision procedure that have been
proven to be total (using meta theory), then I would regard Djinn
saying no as a proof that there is no function of that type.

   -- Lennart

On Thu, May 27, 2010 at 7:49 PM, wren ng thornton w...@freegeek.org wrote:
 Dan Doel wrote:

 On Thursday 27 May 2010 3:27:58 am wren ng thornton wrote:

 By parametricty, presumably.

 Actually, I imagine the way he proved it was to use djinn, which uses a
 complete decision procedure for intuitionistic propositional logic. The
 proofs of theorems for that logic correspond to total functions for the
 analogous type. Since djinn is complete, it will either find a total
 function with the right type, or not, in which case there is no such
 function.

 At that point, all you have left to do is show that djinn is in fact
 complete. For that, you can probably look to the paper it's based on:
 Contraction-Free Sequent Calculi for Intuitionistic Logic* (if I'm not
 mistaken) by Roy Dyckhoff.

 Sure, that's another option. But the failure of exhaustive search isn't a
 constructive/intuitionistic technique, so not everyone would accept the
 proof. Djinn is essentially an implementation of reasoning by parametricity,
 IIRC, so it comes down to the same first principles.


 (Sorry, just finished writing a philosophy paper on intuitionism :)

 --
 Live well,
 ~wren
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] currying combinators

2010-05-26 Thread Lennart Augustsson
There are no interesting (i.e. total) functions of that type.

2010/5/25 Yitzchak Gale g...@sefer.org:
 Günther Schmidt wrote:
 http://www.hpaste.org/fastcgi/hpaste.fcgi/view?id=25694
 in which I attempt to develop a currying combinator library.
 I'm stuck at some point and would appreciate any help.

 How about this:

 keep :: ((t - b) - u - b) - ((t1 - t) - b) - (t1 - u) - b

 so then

 nameZip = keep (drop' . drop') names

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

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


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

2010-05-24 Thread Lennart Augustsson
That's totally false.  You don't evaluate 'undefined' before calling 'id'.
(Or if you, it's because you've made a transformation that is valid
because 'id' is strict.)


On Mon, May 24, 2010 at 9:05 AM, Alexander Solla a...@2piix.com wrote:
 Yes, but only because it doesn't work at all.  Consider that calling

 id undefined

 requires evaluating undefined before you can call id.  The program will
 crash before you ever call id.  Of course, the identity function should
 have produced a value that crashed in exactly the same way.  But we never
 got there.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-05-23 Thread Lennart Augustsson
For Bool, I'm not sure, but for, e.g., () it's certainly true.
Take this definition of ==
  () == _  =  True
Using case analysis of just the constructors, ignoring the value
bottom, you can easily prove symmetry.
But '() == undefined' terminates, whereas 'undefined == ()' does not.

Ignore bottom at your own peril.

BTW, the id function works fine on bottom, both from a semantic and
implementation point of view.

  -- Lennart

On Sun, May 23, 2010 at 11:23 AM, Alexander Solla a...@2piix.com wrote:

 On May 23, 2010, at 1:35 AM, Jon Fairbairn wrote:

 It seems to me relevant here, because one of the uses to which
 one might put the symmetry rule is to replace an expression “e1
 == e2” with “e2 == e1”, which can turn a programme that
 terminates into a programme that does not.

 I don't see how that can be (but if you have a counter example, please show
 us).  Even if we extend == to apply to equivalence classes of bottom values,
 we would have to evaluate both e1 and e2 to determine the value of e1 == e2
 or e2 == e1.

 Prelude undefined == True
 *** Exception: Prelude.undefined
 Prelude True == undefined
 *** Exception: Prelude.undefined
 Prelude undefined == undefined
 *** Exception: Prelude.undefined

 That is, if one case is exceptional, so is the other.

 You can't really even quantify over bottoms in Haskell, as a language.  The
 language runtime is able to do some evaluation and sometimes figure out that
 a bottom is undefined.  Sometimes.  But the runtime isn't a part of the
 language.  The runtime is an implementation of the language's interpetation
 function.  Bottoms are equivalent by conceptual fiat (in other words,
 vacuously) since not even the id :: a - a function applies to
 them.___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Clean proof?

2010-05-23 Thread Lennart Augustsson
There is no clean proof of that statement because it is false.
(Consider the argument 'undefined'.)

2010/5/23 R J rj248...@hotmail.com:
 Given the following definition of either, from the prelude:
     either                      :: (a - c, b - c) - Either a b - c
     either (f, g) (Left x)      =  f x
     either (f, g) (Right x)     =  g x
 what's a clean proof that:
     h . either (f, g) = either (h . f, g . h)?
 The only proof I can think of requires the introduction of an anonymous
 function of z, with case analysis on z (Case 1:  z = Left x, Case 2:  z =
 Right y), but the use of anonymous functions and case analysis is ugly, and
 I'm not sure how to tie up the two cases neatly at the end.  For example
 here's the Left case:
       h . either (f, g)
   =    {definition of \}
       \z - (h . either (f, g)) z
   =    {definition of .}
       \z - (h (either (f, g) z)
   =    {definition of either in case z = Left x}
       \z - (h (f x))
   =    {definition of .}
       \z - (h . f) x
   =    {definition of .}
       h . f

 Thanks.
 
 The New Busy is not the too busy. Combine all your e-mail accounts with
 Hotmail. Get busy.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


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


Re: [Haskell-cafe] Clean proof -- correction

2010-05-23 Thread Lennart Augustsson
Actually, I didn't notice the typo.  It's still not a true statement.

(h . either (f, g)) undefined /= (either (h . f, h . g)) undefined

Also, it's not exactly the function either from the Prelude.

  -- Lennart

2010/5/23 R J rj248...@hotmail.com:
 Correction:  the theorem is
     h . either (f, g) = either (h . f, h . g)

 (Thanks to Lennart for pointing out the typo.)
 
 From: rj248...@hotmail.com
 To: haskell-cafe@haskell.org
 Subject: Clean proof?
 Date: Sun, 23 May 2010 15:41:20 +

 Given the following definition of either, from the prelude:
     either                      :: (a - c, b - c) - Either a b - c
     either (f, g) (Left x)      =  f x
     either (f, g) (Right x)     =  g x
 what's a clean proof that:
     h . either (f, g) = either (h . f, g . h)?
 The only proof I can think of requires the introduction of an anonymous
 function of z, with case analysis on z (Case 1:  z = Left x, Case 2:  z =
 Right y), but the use of anonymous functions and case analysis is ugly, and
 I'm not sure how to tie up the two cases neatly at the end.  For example
 here's the Left case:
       h . either (f, g)
   =    {definition of \}
       \z - (h . either (f, g)) z
   =    {definition of .}
       \z - (h (either (f, g) z)
   =    {definition of either in case z = Left x}
       \z - (h (f x))
   =    {definition of .}
       \z - (h . f) x
   =    {definition of .}
       h . f

 Thanks.
 
 The New Busy is not the too busy. Combine all your e-mail accounts with
 Hotmail. Get busy.
 
 The New Busy is not the old busy. Search, chat and e-mail from your inbox.
 Get started.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


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


Re: [Haskell-cafe] ShowList magic

2010-05-17 Thread Lennart Augustsson
Your question is actually deeper than some of the people answering you
seem to realize.
How does ghci decide what to do when you say
  show []
?
The expression [] has type [a], which means it could be a list of any
type 'a', including Char.
Normally, when Haskell can't determine the type in this kind of
context it will complain.
You can try compiling the program
  main = putStrLn (show [])
and you'll see the error message.
But in ghci there is a special defaulting rule that will use the type
() ambiguous types.
So ghci will use the 'Show ()' instance, which uses the default
implementation for showList.

  -- Lennart

On Mon, May 17, 2010 at 4:56 AM, Abby Henríquez Tejera
parad...@gmail.com wrote:
 Hi.

 I'm a Haskell newbie and there's a bit of Haskell code that I don't
 understand how it works. In the prelude, defining the class Show, the
 function showList is implemented twice, one for String and another one
 for other lists:

    showList cs = showChar '' . showl cs
                 where showl        = showChar ''
                       showl ('':cs) = showString \\\ . showl cs
                       showl (c:cs)   = showLitChar c . showl cs

 and



    showList []       = showString []
    showList (x:xs)   = showChar '[' . shows x . showl xs
                        where showl []     = showChar ']'
                              showl (x:xs) = showChar ',' . shows x .
                                             showl xs

 The thing is... how does Haskell «know» which to execute? It works
 even for the blank string:
 Prelude show 
 \\
 Prelude show []
 []

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

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


Re: [Haskell-cafe] Integers v ints

2010-04-03 Thread Lennart Augustsson
The cost factor of Integer vs Int is far, far smaller than the factor
between computable reals vs Double.

On Thu, Apr 1, 2010 at 6:33 PM, Jens Blanck jens.bla...@gmail.com wrote:
 Yes, the cost for computable reals will be an order of magnitude or possibly
 two for well-behaved computations. For not well-behaved problems it will be
 much worse, but it won't return nonsense either. Also consider that the
 difference between Integers and unboxed Ints is also quite big. I'll happily
 to take the hit.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-03-30 Thread Lennart Augustsson
Of course Haskell' should have an empty case.  As soon as empty data
declarations are allowed then empty case must be allowed just by using
common sense.

On Tue, Mar 30, 2010 at 11:03 PM, Ashley Yakeley ash...@semantic.org wrote:
 wagne...@seas.upenn.edu wrote:

 I believe I was claiming that, in the absence of undefined, Nothing and
 Nothing2 *aren't* isomorphic (in the CT sense).

 Well, this is only due to Haskell's difficulty with empty case expressions.
 If that were fixed, they would be isomorphic even without undefined.

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

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


Re: [Haskell-cafe] Where are the haskell elders?

2010-03-29 Thread Lennart Augustsson
What Don said.

2010/3/29 Don Stewart d...@galois.com:
 gue.schmidt:
 Hi all,

 I notice that posts from the Haskell elders are pretty rare now. Only
 every now and then we hear from them.

 How come?

 Because there is too much noise on this list, Günther

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

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


Re: [Haskell-cafe] GHC vs GCC vs JHC

2010-03-28 Thread Lennart Augustsson
Does anything change if you swap the first two rhss?

On Sun, Mar 28, 2010 at 1:28 AM, Roman Leshchinskiy r...@cse.unsw.edu.au 
wrote:
 On 28/03/2010, at 09:47, Lennart Augustsson wrote:

 It's important to switch from mod to rem.  This can be done by a
 simple abstract interpretation.

 Also, changing the definition of rem from

    a `rem` b
     | b == 0                     = divZeroError
     | a == minBound  b == (-1) = overflowError
     | otherwise                  =  a `remInt` b

 to

    a `rem` b
     | b == 0                     = divZeroError
     | b == (-1)  a == minBound = overflowError
     | otherwise                  =  a `remInt` b

 speeds up the GHC version by about 20%. Figuring out why is left as an 
 exercise to the reader :-)

 Roman


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

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


Re: [Haskell-cafe] GHC vs GCC vs JHC

2010-03-27 Thread Lennart Augustsson
It's important to switch from mod to rem.  This can be done by a
simple abstract interpretation.
I'm nore sure if it's jhc or gcc that does this for jhc.

  -- Lennart

On Sat, Mar 27, 2010 at 10:30 PM, Rafael Cunha de Almeida
almeida...@gmail.com wrote:
 John Meacham wrote:
 Here are jhc's timings for the same programs on my machine. gcc and ghc
 both used -O3 and jhc had its full standard optimizations turned on.

 jhc:
 ./hs.out  5.12s user 0.07s system 96% cpu 5.380 total

 gcc:
 ./a.out  5.58s user 0.00s system 97% cpu 5.710 total

 ghc:
 ./try  31.11s user 0.00s system 96% cpu 32.200 total


 As you can see, jhc shines at this example, actually beating gcc -O3. It
 isn't too surprising, this is exactly the sort of haskell code that jhc
 excels at.

 What's the property of that code which makes jhc excels in it? What
 makes ghc perform so poorly in comparison?
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Bytestrings and [Char]

2010-03-22 Thread Lennart Augustsson
Turn on OverloadedStrings and you can pattern match on any type you
like that is in the IsString class.
Which means that Data.Text can use string literals just like regular
strings (but you can't use Char literals in the match).

On Mon, Mar 22, 2010 at 1:15 PM, Ivan Miljenovic
ivan.miljeno...@gmail.com wrote:
 On 23 March 2010 00:10, Johan Tibell johan.tib...@gmail.com wrote:
 A sequence of bytes is not the same thing as a sequence of Unicode
 code points. If you want to replace String by something more efficient
 have a look at Data.Text.

 Though Data.Text still has the disadvantage of not being as nice to
 deal with as String, since you can't pattern match on it, etc.

 Whilst it may degrade performance, treating String as a list of
 characters rather than an array provides you with greater flexibility
 of how to deal with it.

 --
 Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com
 IvanMiljenovic.wordpress.com
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Proper round-trip HughesPJ/Parsec for Doubles?

2010-02-23 Thread Lennart Augustsson
If you use read (reads) and show for the actual conversion it will round trip.
It appears to be non-trivial since most languages and libraries get it wrong. :)

  -- Lennart

On Tue, Feb 23, 2010 at 1:44 PM, Andy Gimblett hask...@gimbo.org.uk wrote:
 Hi all,

 Short version: How can I pretty print and parse values of type Double such
 that those operations are each other's inverse?

 Long version: I'm writing and QuickCheck-testing a parser using the approach
 set out here:

 http://lstephen.wordpress.com/2007/07/29/parsec-parser-testing-with-quickcheck/

 That is, each syntactic category gets a pretty-printer and a parser and an
 Arbitrary instance, and QuickCheck checks that (parse . prettyPrint) == id,
 basically.  Somewhat unsurprisingly, this sometimes fails for floating point
 values (I'm using Doubles).

 Now, I know that floats are in some sense imprecise, and comparing for
 equality is fraught with peril, but it seems that if x==x then it ought to
 be at least _possible_ to arrange matters such that (parse . prettyPrint x)
 == x as well.  At worst, pretty-printing the underlying binary
 representation!?  So my feeling is that my parser could be improved.

 At the moment I'm working around it by defining a type class which checks
 for equality within some margin of error, and using that instead of Eq - but
 it's messier than I'd like, so I wondered if there was something obvious I'm
 missing.

 As hpaste.org seems to be down, I'll attach a code example here instead.

 Thanks!

 -Andy

 --
 Andy Gimblett
 http://gimbo.org.uk/





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


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


Re: [Haskell-cafe] GHC RTS question

2010-02-21 Thread Lennart Augustsson
Supply a fix for the problem, and it will probably get included.
There has probably been little demand for this feature so far.

  -- Lennart

On Sun, Feb 21, 2010 at 10:21 PM, Ben Millwood hask...@benmachine.co.uk wrote:
 On Sun, Feb 21, 2010 at 7:10 PM, Max Bolingbroke
 batterseapo...@hotmail.com wrote:

 You might be able to get somewhere by writing a custom main function
 in C and linking it in. According to
 http://haskell.org/ghc/docs/latest/html/users_guide/options-phases.html
 if a lib specified with the -l option during compilation contains a
 main, that will be used in preference to the one from HSrts.


 I think the neater way of doing this would be to use the FFI, with a
 foreign export declaration making your haskell main available to a
 wrapper C file, which would then initialise the RTS with a
 slightly-modified argc and argv.
 See http://www.haskell.org/ghc/docs/latest/html/users_guide/ffi-ghc.html
 for details on how to do that.

 I also think it's strange, though, that adding RTS hooks is not
 optional. GHC should support some method of disabling them, in my
 opinion.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] haskell-src type inference algorithm?

2010-02-12 Thread Lennart Augustsson
Well, something like such a tool exists, but I can't give it away.

On Fri, Feb 12, 2010 at 12:13 AM, Niklas Broberg
niklas.brob...@gmail.com wrote:
 Anyone know of a type inference utility that can run right on haskell-src
 types? or one that could be easily adapted?

 This is very high on my wish-list for haskell-src-exts, and I'm hoping
 the stuff Lennart will contribute will go a long way towards making it
 feasible. I believe I can safely say that no such tool exists (and if
 it does, why haven't you told me?? ;-)), but if you implement (parts
 of) one yourself I'd be more than interested to see, and incorporate,
 the results.

 Cheers,

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

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


Re: [Haskell-cafe] haskell-src type inference algorithm?

2010-02-11 Thread Lennart Augustsson
To do anything interesting you also to process modules, something
which I hope to contribute soon to haskell-src-exts.


On Thu, Feb 11, 2010 at 6:35 PM, Job Vranish job.vran...@gmail.com wrote:
 Anyone know of a type inference utility that can run right on haskell-src
 types? or one that could be easily adapted?
 I want to be able to pass in an HsExp and get back an HsQualType. It doesn't
 have to be fancy, plain Haskell98 types would do.

 It wouldn't be to hard to make one myself, but I figured there might be one
 floating around already and it'd be a shame to write it twice :)

 Thanks,

 - Job

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


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


Re: [Haskell-cafe] haskell-src type inference algorithm?

2010-02-11 Thread Lennart Augustsson
It does type inference, it's just not engineered to be part of a real compiler.

On Thu, Feb 11, 2010 at 6:41 PM, Stephen Tetley
stephen.tet...@gmail.com wrote:
 http://web.cecs.pdx.edu/~mpj/thih/

 Looks like its a type _checker_ though...


 On 11 February 2010 17:39, Stephen Tetley stephen.tet...@gmail.com wrote:
 Hello Job

 For Haskell 98 would the code from 'Typing Haskell in Haskell' paper suffice?

 A web search should find the code...

 Best wishes

 Stephen

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

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


Re: [Haskell-cafe] Re: could we get a Data instance for Data.Text.Text?

2010-01-23 Thread Lennart Augustsson
 The only safe rule is: if you don't control the class, C, or you don't
 control the type constructor, T, don't make instance C T.

I agree in principle, but in the real world you can't live by this rule.
Example, I want to use Uniplate to traverse the tree built by haskell-src-exts,
Using Data.Data is too slow, so I need to make my own instances.
HSE provides like 50 types that need instances, and it has to be
exactly those types.
Also, Uniplate requires instances of a particular class it has.

I don't own either of these packages.  Including the HSE instances in
Uniplate would just be plain idiotic.
Including the Uniplate instances with HSE would make some sense, but
would make HSE artificially depend on Uniplate for those who don't
want the instances.

So, what's left is to make orphan instances (that I own).  It's not
ideal, but I don't see any alternative to it.

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


Re: [Haskell-cafe] Language simplicity

2010-01-16 Thread Lennart Augustsson
PL/I has keywords, they're just not reserved words.
With as many keywords as PL/I has, there something to say for not
making them reserved. :)

On Wed, Jan 13, 2010 at 11:50 AM, Brandon S. Allbery KF8NH
allb...@ece.cmu.edu wrote:
 On Jan 13, 2010, at 05:45 , Ketil Malde wrote:

 Brandon S. Allbery KF8NH allb...@ece.cmu.edu writes:

 If we're going to go that far, FORTRAN and PL/1 have none.  FORTRAN is
 somewhat infamous for this:

 There's also the option (perhaps this was PL/1?) of writing constructs
 like:  IF THEN THEN IF ELSE THEN etc.  Having few reserved words isn't
 necessarily a benefit.  :-)

 That'd be PL/I, and a prime example of why languages use keywords these days
 (as if FORTRAN weren't enough). :)

 --
 brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
 system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
 electrical and computer engineering, carnegie mellon university    KF8NH



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


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


Re: [Haskell-cafe] How to get a list of constructors for a type?

2009-12-30 Thread Lennart Augustsson
I've put some of Oleg's code on hackage, named polytypeable.

 import Data.PolyTypeable
 main = print [polyTypeOf Nothing, polyTypeOf Just]

This prints
  [Maybe a1,a1 - Maybe a1]

To get a list of the actual constructors you need to derive
Data.Data.Data and use that.

  -- Lennart

On Wed, Dec 30, 2009 at 8:46 PM, Claude Heiland-Allen
claudiusmaxi...@goto10.org wrote:
 Gregory Propf wrote:

 Say I have something like

 data DT a = Foo a | Bar a | Boo a

 I want something like a list of the constructors of DT, perhaps as
 [TypeRep].  I'm using Data.Typeable but can't seem to find what I need in
 there.  Everything there operates over constructors, not types.

 The approach below won't work in general because the constructors may have
 different (argument) types, but for the above:

    [Foo, Bar, Boo] :: [a - DT a]

 And you could manually build a list of constructor types, as a try:

    [typeOf Nothing, typeOf Just] :: [TypeRep]

 which doesn't work, due to polymorphic ambiguity, so you'd have to:

    [typeOf (Nothing :: Maybe Int), typeOf (Just :: Int - Maybe Int)]

 In general, maybe Data.Dynamic is what you need, but I don't think that can
 handle polymorphic values yet either.

 What do you want to do with the list of constructors once you have them?

 Where are they defined?


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

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


Re: [Haskell-cafe] ANNOUNCE: repr-0.3.2

2009-12-24 Thread Lennart Augustsson
Did you consider using the traced package?

2009/12/24 Bas van Dijk v.dijk@gmail.com:
 On Thu, Dec 24, 2009 at 1:00 AM, Andrey Sisoyev
 andrejs.sisoj...@nextmail.ru wrote:
 Where do you make use of it? :)

 A few months ago I was working on 'levmar'[1] a Levenberg-Marquardt
 data fitting library in Haskell. If you want your data fitting to be
 really fast you need to supply a Jacobian of the model function you
 want to fit. A Jacobian describes the partial derivatives of the
 parameters of the model function. I used Conal Elliott's
 vector-space[2] library to automatically derive a Jacobian from the
 model function.

 I was interested in the derivatives vector-space would come up with. A
 derivative however, is just a function so the only thing you can do
 with it is apply it to a value. This then yields a result which is
 usually just a Double. I wasn't really interested in this actual
 numeric result but more in the underlying numeric expressing that
 generated that result.

 So I wrote repr to visualize this numeric expression. However, after I
 wrote repr, the work on levmar stalled a bit and I did not actually
 get around to applying repr to the derivatives. I plan to make a new
 release of levmar in the coming weeks or so and I think I will use
 repr then.

 regards,

 Bas

 [1] http://hackage.haskell.org/package/levmar
 [2] http://hackage.haskell.org/package/vector-space
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Zumkeller numbers

2009-12-08 Thread Lennart Augustsson
And if you use quotRem it's faster (unless you're running on some
exotic hardware like NS32K).

On Tue, Dec 8, 2009 at 10:19 PM, Richard O'Keefe o...@cs.otago.ac.nz wrote:

 On Dec 9, 2009, at 1:15 AM, Daniel Fischer wrote:

 Am Dienstag 08 Dezember 2009 08:44:52 schrieb Ketil Malde:

 Richard O'Keefe o...@cs.otago.ac.nz writes:

 factors n = [m | m - [1..n], mod n m == 0]

  -- saves about 10% time, seems to give the same result:
  factors n = [m | m - [1..n `div` 2], mod n m == 0]++[n]

 Even faster (for large enough n):

 factors n =
   mergeAll [if q == d then [d] else [d, q] | d - [1 .. isqrt n]
                                            , let (q,r) = n `divMod` d, r
 == 0]

 We can improve on that somewhat:

 factors 1 = [1]
 factors n = 1 : candidates 2 4 n [n]
  where candidates d d2 n hi =
          if d2  n then
             let (q,r) = divMod n d in
               if r == 0 then d : candidates (d+1) (d2+d+d+1) n (q:hi)
                         else     candidates (d+1) (d2+d+d+1) n    hi
          else if d2 == n then d:hi else hi

 This never constructs a cons cell it doesn't mean to keep.


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

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


Re: [Haskell-cafe] Optimization with Strings ?

2009-12-03 Thread Lennart Augustsson
Thank you Sir for giving me a good laugh!

On Thu, Dec 3, 2009 at 5:25 PM, John D. Earle johndea...@cox.net wrote:
 Dear Emmanuel Chantréau,

 You may want to look into Objective CAML http://caml.inria.fr/ which is a
 French product as you can see from the Internet address. It is likely better
 suited to the task than Haskell and has a reputation for speed. For those
 who prefer object oriented programming it has facilities for that which may
 ease your transition from C++. The Microsoft F# language is based on
 Objective CAML.

 Haskell has a problem with its type system and is not rigorous. Haskell is
 not a suitable language for proof assistants and so I would advise you to
 stay clear of Haskell. Standard ML was engineered with the needs of proof
 assistants in mind and so you may want to look into Standard ML, but you
 should be very happy with Objective CAML. It has an excellent reputation.
 The Coq proof assistant which is another French product is based on
 Objective CAML.

 If you do decide that Haskell is the way, it will help ease your transition
 to Haskell. There is nothing that says you can't keep your fingers in
 several pies at once.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


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


Re: [Haskell-cafe] Coercing numeric and string constants

2009-11-16 Thread Lennart Augustsson
Try with -XExtendedDefaulingRules.

On Mon, Nov 16, 2009 at 6:33 AM, Mark Lentczner ma...@glyphic.com wrote:
 I'm looking for a good way to handle a library interface that accepts both 
 strings and numbers in particular argument positions:

 Start with the following definitions. I've defined ResourceTree as a class 
 here since the details don't matter.

 data Segment = Key String | Index Int
     deriving (Eq, Show)

 type Path = [Segment]

 class ResourceTree a where
     lookupPath :: Path - a - Maybe String

 What I'm after is to make the following code, representative of intended 
 client usage to work:

 examples :: (ResourceTree a) = a - [Maybe String]
 examples r = [
         r `at` status,
         r `at` 7,
         r `at` part ./ sku,
         r `at` items ./ 2,
         r `at` 7 ./ name,
         r `at` 7 ./ 9
     ]

 The first way I thought to do this was with type classes:

 class    Segmentable a       where { toSegment :: a - Segment }
 instance Segmentable Segment where { toSegment = id }
 instance Segmentable String  where { toSegment = Key }
 instance Segmentable Int     where { toSegment = Index }

 class    Pathable a      where { toPath :: a - Path }
 instance Pathable Path   where { toPath = id }
 instance Pathable String where { toPath s = [ Key s ] }
 instance Pathable Int    where { toPath i = [ Index i ] }

 (./) :: (Segmentable a, Pathable b) = a - b - Path
 a ./ b = toSegment a : toPath  b
 infixr 4 ./

 at :: (ResourceTree a, Pathable b) = a - b - Maybe String
 a `at` b = lookupPath (toPath b) a
 infix 2 `at`

 This works great for all uses in the client code where the type of the 
 numeric arguments are known or otherwise forced to be Int. However, when used 
 with numeric constants (as in the function example above), it fails due to 
 the way that numeric constants are defined in Haskell. For example, the 
 constant 9 in example results in this error:

    Ambiguous type variable `t4' in the constraints:
      `Pathable t4' arising from a use of `./' at Test.hs:48:15-20
      `Num t4' arising from the literal `9' at Test.hs:48:20
    Probable fix: add a type signature that fixes these type variable(s)

 I suppose that even though there is only one type that is both an instance of 
 Num and of Pathable (Int), that can't be deduced with certainty.

 In the client code, one could fix this by typing the constants thus:

 r `at` (7::Int) ./ (9::Int)

 But to me that makes a hash out of the concise syntax I was trying to achieve.

 Also, this code requires both FlexibleInstances and TypeSynonymInstances 
 pragmas (though the later requirement could be worked around.), though I'm 
 lead to understand that those are common enough. I think also that, these are 
 only needed in the library, not the client code.

 The other way I thought to do this is by making Path and Segment instances of 
 Num and IsString:

 instance Num      Segment where { fromInteger = Index . fromInteger }
 instance IsString Segment where { fromString  = Key . fromString }
 instance Num      Path    where { fromInteger i = [ Index $ fromInteger i ] }
 instance IsString Path    where { fromString  s = [ Key $ fromString s ] }

 (./) :: Segment - Path - Path
 a ./ b =  a : b
 infixr 4 ./

 at :: (ResourceTree a) = a - Path - Maybe String
 a `at` b = lookupPath b a
 infix 2 `at`

 This works but has two downsides: 1) Segment and Path are poor instances of 
 Num, eliciting errors for missing methods and resulting in run-time errors 
 should any client code accidentally use them as such. 2) It requires the 
 OverloadedStrings pragma in every client module.

 Any comments on these two approaches would be appreciated, How to improve 
 them? Which is the lesser of two evils?

 On the other hand, I realize that many may object that intended interface 
 isn't very Haskell like. The data object I need to represent (ResourceTree) 
 comes from external input and really does have the strange paths of strings 
 or integers construction, I can't change that. And it is expected that much 
 client code will use constant paths to access and manipulate various parts of 
 such objects, hence the desire for a concise operator set that works with 
 constants. Given that there are actually several operations on ResourceTree 
 involving paths (where the operation requires the whole Path as a single 
 value), any thoughts on a more Haskell like construction?

 Thanks,
        - MtnViewMark


 Mark Lentczner
 http://www.ozonehouse.com/mark/
 m...@glyphic.com



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

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


Re: [Haskell-cafe] Little errors in number calculations

2009-11-15 Thread Lennart Augustsson
Hugs is wrong, as you can easily see by evaluating
   let x = 123.35503 * 10.0 in x == read (show x)
With ghc it comes out as True and with Hugs as False.

  -- Lennart

On Sat, Nov 14, 2009 at 9:00 PM, Abby Henríquez Tejera
parad...@gmail.com wrote:
 Hi.

 I've seen that in GHC sometimes there are little errors in some basic
 number calculations:

 *Prelude 123.35503 * 10.0
 1233.55029

 *Prelude properFraction 123.35503
 (123,0.35502993)

 whereas in Hugs no such errors seem to occur (that I have found, at
 least):

 *Hugs 123.35503 * 10.0
 1233.5503

 (but:)

 *Hugs properFraction 123.35503
 (123,0.3550299)

 I understand that error may (and will) happen in floating point, but
 it surprises me that they do so easily, and, above all, the difference
 between GHC and Hugs. Does someone know why does this difference
 occur?

 (Thanks in advance, by the way :) ).
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] What does the `forall` mean ?

2009-11-14 Thread Lennart Augustsson
Of the two declarations
data Fizzle a = Fizzle (b - (a, b)) a
data Fizzle a = forall b. Fizzle (b - (a, b)) a
only the second one is allowed (with some suitable extension).

Personally I think the first one should be allowed as well, with the
same meaning as the second one.
Some people thought it was to error prone not to have any indication
when an existential type is introduced,
so instead we are now stuck with a somewhat confusing keyword.

  -- Lennart

On Sat, Nov 14, 2009 at 4:55 PM, Mark Lentczner ma...@glyphic.com wrote:
 On Nov 12, 2009, at 2:59 PM, Sean Leather wrote:
   foo :: forall x y. (x - x) - y
   bar :: forall y. (forall x . x - x) - y

 While neither function is seemingly useful, the second says that the 
 higher-order argument must be polymorphic. I see two options:

 AHA! This is the bit of insight I needed! My confusion over forall was I 
 thought that I understood that all Haskell types were as if there was a 
 forall for all free type variables in front of the expression. For example, I 
 think the following are the same:

        fizz :: a - String - [a]
        fizz :: forall a. a - String - [a]

 So why would you need forall? The example Sean explained is that if you want 
 to control the scope of the existential quantification. And you can only 
 push the scope inward, since the outer most scope basically foralls all 
 the free type variables (after type inference, I suppose.)

 I also think I understand that the implicit 'forall' inherent in Haskell 
 falls at different places in various constructs, which also had me confused. 
 For example, while the above two function type declarations are equivalent, 
 these two data declarations aren't:

        data Fizzle a = Fizzle (b - (a, b)) a
        data Fizzle a = forall b. Fizzle (b - (a, b)) a

 This would be because the implicit 'forall' is essentially to the left of the 
 'data Fizzle a' section. I'm guessing that the same holds true for type and 
 newtype constructs.

 Have I got this all correct?

 Would I be correct in thinking: The difference between these two is that the 
 type b can be fixed upon application of amy to the first two arguments 
 (given context), whereas bob applied to two arguments MUST return a function 
 that is applicable to every type.

        amy :: Int - a - b - [Either a b]
        bob :: Int - a - (forall b. b) - [Either a b]

 Thanks for helping me understand...
        - Mark

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

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


Re: [Haskell-cafe] Opinion about JHC

2009-11-13 Thread Lennart Augustsson
Thanks Neil,

That was indeed my point.  Since a compiler is a substantial program I
would have more confidence it a compiler that is self-hosting.
Surely you must have tried?

  -- Lennart

On Fri, Nov 13, 2009 at 8:08 PM, Neil Mitchell ndmitch...@gmail.com wrote:
 Hi John,

 Do you use jhc when you develop jhc?  I.e., does it compile itself.
 For me, this is the litmus test of when a compiler has become usable.
 I mean, if even the developers of a compiler don't use it themselves,
 why should anyone else? :)

 Well, this touches on another issue, and that is that jhc is a native
 cross-compiler. It never behaves differently if compiled by another
 haskell compiler or is compiled on an alternate platform. There is never
 a need to 'bootstrap' it, once you have jhc running anywhere then it is
 as good as it would be if it is running everywhere. So to me,
 self-hosting has never been a big issue as it doesn't provide any direct
 material benefit. My time is better spent implementing more extensions
 or improving the back end.

 I think you might have missed Lennart's point. It's fair to say you do
 a lot of Haskell development work while writing a Haskell compiler. If
 you aren't using your compiler for your development work (in
 particular for your compiler) then anyone trying to use it is likely
 to bump in to problems. It's not that there are technical advantages
 of self-compilation, but it is a good statement of faith from the
 compiler author.

 Anyway, I think the Haskell community needs more compilers, so I wish
 you lots of luck with JHC!

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

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


Re: [Haskell-cafe] Opinion about JHC

2009-11-11 Thread Lennart Augustsson
John,

Do you use jhc when you develop jhc?  I.e., does it compile itself.
For me, this is the litmus test of when a compiler has become usable.
I mean, if even the developers of a compiler don't use it themselves,
why should anyone else? :)

  -- Lennart

On Wed, Nov 11, 2009 at 3:37 AM, John Meacham j...@repetae.net wrote:
 On Tue, Nov 10, 2009 at 07:41:54PM -0800, Philippos Apolinarius wrote:
 I discovered a Haskell compiler that generates very small and fast
 code. In fact, it beats Clean. It has the following properties:

 Excellent. that was my goal ;)

 1 --- One can cross-compile programs easily. For instance, here is how I 
 generated code for Windows:

 jhc --cross -mwin32 genetic.hs -o genetic

 Yup. This was a major goal. compiling for iPhones and embedded arches is
 just as easy assuming you have a gcc toolchain set up. (at least with
 the hacked iPhone SDK.. I have never tried it with the official one)


 2 -- It seems to be quite complete.

 3 -- However, it often compiles a file, but the program fails to run.

 I have the following questions about it:

 1 -- How active is the team who is writing the JHC compiler?

 Hi, I am the main contributor, but others are welcome and several have
 made signifigant contributions. Development tends to be spurty. A lot of
 work will get done in a short amount of time, this generally corresponds
 to when an external contributor gets involved and the back and forth
 helps stimulate patches on my part to complement theirs.

 Although I have not been able to devote a lot of my time to jhc in the
 past, hopefully this will change in the not to distant future and I will
 be able to work on it full time.


 2 -- Is it complete Haskell? The author claims that it is; it compiled
 all programs that I wrote, but that does not mean much, because my
 programs are quite simple.

 It does Haskell 98 and several extensions, which is pretty much what GHC
 does. However, it does not implement the same set of extensions as GHC
 so this causes issues as a lot of people use GHC extensions extensively.

 I plan on supporting all of Haskell' of course, and the popular GHC
 extensions to help compatibility. Not all are implemented.

 3 -- Why the Haskell community almost never talks about JHC?

 Part of it is that I am not very good at advocacy. I don't always
 post announcements on the main haskell lists figuring the interested
 parties are on the jhc list already. I do try to make jhc good, fast,
 and usable, I always hoped someone better at advocacy than me would join
 the project :) In truth, I think the spurty nature of development also
 affects this, the list will be quite for a long time with a flurry of
 development lasting a few weeks occasionally inspiring some discussion
 in the other groups.

 In any case, I am glad you liked what you found! please join the mailing
 list for jhc if you are interested in its development or using it.

        John



 --
 John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Opinion about JHC

2009-11-11 Thread Lennart Augustsson
If by minority platform you mean platforms that are resource starved,
like some embedded systems, then I would have to agree.

  -- Lennart

On Wed, Nov 11, 2009 at 2:12 PM, Donn Cave d...@avvanta.com wrote:
 Quoth Lennart Augustsson lenn...@augustsson.net,

 Do you use jhc when you develop jhc?  I.e., does it compile itself.
 For me, this is the litmus test of when a compiler has become usable.
 I mean, if even the developers of a compiler don't use it themselves,
 why should anyone else? :)

 Though that's exactly backwards for minority platforms, where the
 compilers that compile themselves tend to be no use whatever.

        Donn Cave, d...@avvanta.com

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

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


Re: [Haskell-cafe] pretty printing with comments

2009-10-20 Thread Lennart Augustsson
It's not an easy problem to pretty print (i.e. change indentation) and
preserve the comments.  And always get it right.

On Tue, Oct 20, 2009 at 1:28 PM, Pasqualino Titto Assini
tittoass...@gmail.com wrote:
 Thanks Niklas,

 in fact this produced a source with comments:


 import Language.Haskell.Exts.Annotated

 main = do
  (ParseOk (mod,comments)) - parseFileWithComments defaultParseMode Test.hs
  let pretty = exactPrint mod comments
  writeFile Test_PRETTY.hs pretty



 However:
 - The source code produced was incorrect:


 class Dir d where

 was rewritten as:

 class Dir dwhere{


 And:

 instance Dir Directory where
  localDir (Local f) = return f

 type URL= String


 was rewritten as:


 instance Dir Directory where
  localDir (Local f) = return f

  typeURL= String


 Are these known bugs?


 - Also, the printing is a bit too exact :-), I would like to keep my
 comments AND get the code nicely reformatted.


 Is there a way?

 What people use to keep their haskell source files in tip-top shape?

 Thanks

          titto






 2009/10/20 Niklas Broberg niklas.brob...@gmail.com:
 Hi Pasqualino,

 I am looking at the haskell-src-ext library.

 It can parse files with comments and it can pretty print but, for what
 I can see it cannot do both :-)  (prettyPrint won't work on the
 structure returned by parseFileWithComments).

 What you want is exactPrint, defined in
 Language.Haskell.Exts.Annotated.ExactPrint. :-)

 Cheers,

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

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


Re: [Haskell-cafe] Exponential complexity of type checking (Was: Type-level naturals multiplication)

2009-10-13 Thread Lennart Augustsson
Yes, there are simple H-M examples that are exponential.
x0 = undefined
x1 = (x1,x1)
x2 = (x2,x2)
x3 = (x3,x3)
...

xn will have a type with 2^n type variables so it has size 2^n.

  -- Lennart

On Tue, Oct 13, 2009 at 6:04 PM, Brad Larsen brad.lar...@gmail.com wrote:
 On Tue, Oct 13, 2009 at 3:37 AM, Simon Peyton-Jones
 simo...@microsoft.com wrote:
 |  Is there any way to define type-level multiplication without requiring
 |  undecidable instances?
 |
 | No, not at the moment.  The reasons are explained in the paper Type
 | Checking with Open Type Functions (ICFP'08):
 |
 |    http://www.cse.unsw.edu.au/~chak/papers/tc-tfs.pdf
 |
 | We want to eventually add closed *type families* to the system (ie,
 | families where you can't add new instances in other modules).  For
 | such closed families, we should be able to admit more complex
 | instances without requiring undecidable instances.

 It's also worth noting that while undecidable instances sound scary, but 
 all it means is that the type checker can't prove that type inference will 
 terminate.  We accept this lack-of-guarantee for the programs we *run*, and 
 type inference can (worst case) take exponential time which is not so 
 different from failing to terminate; so risking non-termination in type 
 inference is arguably not so bad.

 Simon


 I have written code that makes heavy use of multi-parameter type
 classes in the ``finally tagless'' tradition, which takes several
 seconds and many megabytes of memory for GHCI to infer its type.
 However, that example is rather complicated, and I am not sure its
 type inference complexity is exponential---it is at least very bad.

 Are there any simple, well-known examples where Haskell type inference
 has exponential complexity?  Or Hindley-Milner type inference, for
 that matter?  (Haskell 98 is not quite Hindley-Milner?)

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

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


Re: [Haskell-cafe] type inference question

2009-10-08 Thread Lennart Augustsson
The reason a gets a single type is the monomorphism restriction (read
the report).
Using NoMonomorphismRestriction your example with a works fine.

On Thu, Oct 8, 2009 at 12:29 PM, Cristiano Paris fr...@theshire.org wrote:
 On Thu, Oct 8, 2009 at 11:04 AM, minh thu not...@gmail.com wrote:
 Hi,

 I'd like to know what are the typing rules used in Haskell (98 is ok).

 Specifically, I'd like to know what makes

 let i = \x - x in (i True, i 1)

 legal, and not

 let a = 1 in (a + (1 :: Int), a + (1.0 :: Float))

 Is it correct that polymorphic functions can be used polymorphically
 (in multiple places) while non-functions receive a monomorphic type ?

 First, 1 IS a constant function so it's in no way special and is a
 value like any other.

 That said, the type of 1 is (Num t) = t, hence polymorphic. But, when
 used in the first element of the tuple, a is assigned a more concrete
 type (Int) which mismatches with the second element of the tuple,
 which is a Float.

 If you swap the tuple, you'll find that the error reported by ghci is
 the very same as before, except that the two types are swapped.

 Is it possible to rewrite the expression so as to work? The answer is
 yes, using existential quantification (and Rank2 polymorphism).

 Here you are:
 {-# LANGUAGE ExistentialQuantification, Rank2Types #-}
 foo :: (forall a. (Num a) = a) - (Int,Float)
 foo = \x - (x + (1 :: Int), x + (1 :: Float))

 Hence:

 foo 1 -- (2,2.0)

 Bye,

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

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


Re: Re[2]: [Haskell-cafe] type inference question

2009-10-08 Thread Lennart Augustsson
Indeed, the types
  foo :: forall a . (Num a) = a - (Int, Float)
and
  foo :: (forall a . (Num a) = a) - (Int, Float)
are quite different.

The first one say, I (foo) can handle any kind of numeric 'a' you (the
caller) can pick. You (the caller) get to choose exactly what type you
give me.

The second one says, I (foo) require you (the caller) to give me an
numeric 'a' that I can use any way I want.  You (the caller) don't get
to choose what type you give me, you have to give me a polymorphic
one.

  -- Lennart

On Thu, Oct 8, 2009 at 5:35 PM, Bulat Ziganshin
bulat.zigans...@gmail.com wrote:
 Hello Cristiano,

 Thursday, October 8, 2009, 7:14:20 PM, you wrote:

 Could you explain why, under NoMonomorphismRestriction, this typechecks:

 let a = 1 in (a + (1 :: Int),a + (1 :: Float))

 while this not:

 foo :: Num a = a - (Int,Float)
 foo k = (k + (1 :: Int), k + (1.0 :: Float))

 i think it's because type is different:

 foo :: (forall a. (Num a) = a) - (Int,Float)

 in first equation it probably inferred correctly



 --
 Best regards,
  Bulat                            mailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Num instances for 2-dimensional types

2009-10-05 Thread Lennart Augustsson
And what is a number?  Are complex numbers numbers?

On Mon, Oct 5, 2009 at 3:12 PM, Miguel Mitrofanov miguelim...@yandex.ru wrote:


 Sönke Hahn wrote:

 I used to implement

    fromInteger n = (r, r) where r = fromInteger n

 , but thinking about it,
    fromInteger n = (fromInteger n, 0)

 seems very reasonable, too.

 Stop pretending something is a number when it's not.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Num instances for 2-dimensional types

2009-10-05 Thread Lennart Augustsson
But complex numbers are just pairs of numbers.  So pairs of numbers
can obviously be numbers then.

On Mon, Oct 5, 2009 at 4:40 PM, Miguel Mitrofanov miguelim...@yandex.ru wrote:
 Lennart Augustsson wrote:

 And what is a number?

 Can't say. You know, it's kinda funny to ask a biologist what it means to be
 alive.

 Are complex numbers numbers?

 Beyond any reasonable doubt. Just like you and me are most certainly alive.

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


Re: [Haskell-cafe] Num instances for 2-dimensional types

2009-10-05 Thread Lennart Augustsson
Everyone agrees that the Haskell numeric hierarchy is flawed, but I've
yet to see a good replacement.

On Mon, Oct 5, 2009 at 4:51 PM, Brad Larsen brad.lar...@gmail.com wrote:
 On Mon, Oct 5, 2009 at 10:36 AM, Miguel Mitrofanov
 miguelim...@yandex.ru wrote:
 [...]
 Of course, it's OK to call anything numbers provided that you stated
 explicitly what exactly you would mean by that. But then you have to drop
 all kind of stuff mathematicians developed for the usual notion of numbers.
 In the same way, you shouldn't use the Num class for your numbers.

 On the other hand, people can (ab)use the Num class as they wish, and it's
 their business until they ask a question about it somewhere outside - which
 makes the business not only theirs.
 [...]

 The Num class has `negate' as part of its definition.  Natural numbers
 are numbers, but I don't believe there is any sensible definition of
 `negate' for them.

 Haskell 98's numeric hierarchy combines many operations which should
 be separate.  As further evidence, every bit of Haskell I have seen
 that does symbolic manipulation of numeric expressions either leaves
 out instances that would make the syntax more convenient, or else
 defines partial instances because certain class functions have no
 sensible definition for symbolic expressions.

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

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


Re: [Haskell-cafe] Num instances for 2-dimensional types

2009-10-05 Thread Lennart Augustsson
Complex numbers are just pairs of numbers, and then the various
operations on them are defined in a specific way.
There may be other ways to define the operations on pairs of numbers
that makes sense too.

You can also view complex numbers as polynomials if you wish.  Or two
element lists of numbers.

My real point is that you shouldn't tell others what they should
regard as numbers and what not.
Being a number is in the eye of the beholder. :)

On Mon, Oct 5, 2009 at 4:55 PM, Miguel Mitrofanov miguelim...@yandex.ru wrote:
 No, they aren't. They are polynomials in one variable i modulo i^2+1.

 Seriously, if you say complex numbers are just pairs of real numbers - you
 have to agree that double numbers (sorry, don't know the exact English
 term), defined by

 (a,b)+(c,d) = (a+c,b+d)
 (a,b)(c,d) = (ac, ad+bc)

 are just pairs of real numbers too. After that, you have two choices: a)
 admit that complex numbers and double numbers are the same - and most
 mathematicians would agree they aren't - or b) admit that the relation be
 the same is not transitive - which is simply bizarre.


 Lennart Augustsson wrote:

 But complex numbers are just pairs of numbers.  So pairs of numbers
 can obviously be numbers then.

 On Mon, Oct 5, 2009 at 4:40 PM, Miguel Mitrofanov miguelim...@yandex.ru
 wrote:

 Lennart Augustsson wrote:

 And what is a number?

 Can't say. You know, it's kinda funny to ask a biologist what it means to
 be
 alive.

 Are complex numbers numbers?

 Beyond any reasonable doubt. Just like you and me are most certainly
 alive.

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


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


Re: [Haskell-cafe] What is a number. (Was: Num instances for 2-dimensional types)

2009-10-05 Thread Lennart Augustsson
OK, just pairs have no arithmetic, but one way of defining
arithmetic is to treat the pairs as complex numbers.  Or as mantissa
and exponent.  Or as something else.  So there's nothing wrong, IMO,
to make pairs an instance of Num if you so desire.  (Though I'd
probably introduce a new type.)

On Mon, Oct 5, 2009 at 6:46 PM, Miguel Mitrofanov miguelim...@yandex.ru wrote:
 Just pairs have no natural arithmetic upon them.

 Exactly my point.

 BTW. the missing term of M.M. is DUAL NUMBERS.

 Remembered this already. Thanks anyway.

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

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


Re: [Haskell-cafe] Re: Is logBase right?

2009-08-27 Thread Lennart Augustsson
Prelude toRational 697.04157958259998
3065621287177675 % 4398046511104
Prelude toRational 697.0415795826
3065621287177675 % 4398046511104

As you can see, both numbers are represented by the same Double.
Haskell prints a Double with the simplest number that converts back to
the same bit pattern.
So there's no keep more decimals, just a matter of string conversion.

  -- Lennart

On Tue, Aug 25, 2009 at 7:11 PM, Ketil Maldeke...@malde.org wrote:
 Steve stevech1...@yahoo.com.au writes:

 Also, I had a problem using floating point in Python where
 round(697.04157958254996, 10)
 gave
 697.04157958259998

 Its been fixed in the latest versions of Python:
 round(697.04157958254996, 10)
 697.0415795825

 ghci roundN 697.04157958254996 10
 697.0415795826

 Is there something special with this number?

  Python 2.6.2 (release26-maint, Apr 19 2009, 01:56:41)
  [GCC 4.3.3] on linux2
  Type help, copyright, credits or license for more information.
   697.04157958259998
  697.04157958259998
   12345.678901234567890
  12345.678901234567

  GHCi, version 6.8.2: http://www.haskell.org/ghc/  :? for help
  Loading package base ... linking ... done.
  Prelude 697.04157958259998
  697.0415795826
  Prelude 12345.678901234567890
  12345.678901234567

 So, Python manages to keep more decimals than GHC for your number, but
 for other numbers, the precision appears to be the same.

 -k
 --
 If I haven't seen further, it is by standing in the footprints of giants
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Re: Is logBase right?

2009-08-25 Thread Lennart Augustsson
I don't really care much one way or the other, but since C (math.h)
provides functions for base 2 and base 10 with some additional
accuracy, I wouldn't mind using them.  For a constant base I'd expect
the extra comparison to be constant folded, so that's ok.  For a
non-constant base there would be a small penalty.

  -- Lennart

On Tue, Aug 25, 2009 at 3:20 PM, Henning
Thielemannlemm...@henning-thielemann.de wrote:

 On Sun, 23 Aug 2009, Lennart Augustsson wrote:

 You're absolutely right.  It would be easy to change logBase to have
 special cases for, say, base 2 and base 10, and call the C library
 functions for those.  In fact, I think it's a worth while change,
 since it's easy and get's better results for some cases.

 I think, the current implementation should left as it is. For fractional
 bases, no one would easily detect such imprecise results and report them as
 problem. So, it seems like people need a logarithm of integers, so they
 should be supplied with a special logarithm function for integers. For the
 other use cases, where 10 as base is one choice amongst a continuous set of
 rational numbers it would not be a problem to give the imprecise result. In
 the general case I would not accept a speed loss due to a check against 2
 and 10 as base.

 In dynamically typed languages like Python this might be different, because
 their users might not care much about types. It may not be important for
 them, whether a number is an integer or a floating point number that is
 accidentally integral. However, Python distinguishes between these two kinds
 of integers, but only dynamically.

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


Re: [Haskell-cafe] Re: Is logBase right?

2009-08-23 Thread Lennart Augustsson
You're absolutely right.  It would be easy to change logBase to have
special cases for, say, base 2 and base 10, and call the C library
functions for those.  In fact, I think it's a worth while change,
since it's easy and get's better results for some cases.

  -- Lennart

On Sun, Aug 23, 2009 at 12:41 PM, Stevestevech1...@yahoo.com.au wrote:
 On Sat, 2009-08-22 at 13:03 -0400, haskell-cafe-requ...@haskell.org
 wrote:
 Message: 10
 Date: Sat, 22 Aug 2009 11:24:21 +0200
 From: Roberto L?pez plasterm...@hotmail.com
 Subject: [Haskell-cafe] Re: Is logBase right?
 To: haskell-cafe@haskell.org
 Message-ID: h6odg8$93...@ger.gmane.org
 Content-Type: text/plain; charset=ISO-8859-1

 If 4.0 / 2.0 was 1.98, it would be ok?

 The real value of log10 1000 is 3 (3.0). It can be represented with
 accuracy
 and it should be.

 You get the accuracy value in Perl, but there is the same problem in
 Python.
 It's a bit discouraging.


 There is *not* the same problem in Python:
 $ python
 Python 2.6.2 (r262:71600, Jul  9 2009, 23:16:53)
 [GCC 4.4.0 20090506 (Red Hat 4.4.0-4)] on linux2
 Type help, copyright, credits or license for more information.
 import math
 math.log10(1000)
 3.0

 Recent work in Python 3 (and Python 2.6) has improved the handling of
 floating point numbers, and addresses exactly the problem that Roberto
 has raised.

 I see no reason why Haskell could not improve its handling of floating
 point numbers by using similar techniques.

 Steve

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

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


Re: [Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-22 Thread Lennart Augustsson
Even if you are only slightly irritated by offset syntax, why are you using it?
{;} works fine.

On Sat, Aug 22, 2009 at 3:51 AM, John D. Ramsdellramsde...@gmail.com wrote:
 Let me put all my cards on the table.  You see, I really am only
 slightly irrigated by offset syntax.  In contrast, I am a strong
 proponent of functional programming for parallel programming.  In my
 opinion, it has to be the new way for multiprocessor machines.  Just
 think about it and if other paradym could possibly work.  We've tried
 many on them.  Many years ago, I wrote SISAl programs.  There were
 many good ideas in SISAL, but it did not catch on.  Perhaps Data
 Parallel Haskell will catch on.  In my opinion, something like it is
 the ``answer.''  Even though the code I submitted is not parallel,
 I've thought about how to make it so.  And isn't thinking parallelism
 iour future?  I think so.

 John

 On Thu, Aug 20, 2009 at 10:04 AM, Jules Beanju...@jellybean.co.uk wrote:
 John D. Ramsdell wrote:

 On Thu, Aug 20, 2009 at 9:08 AM, Jules Beanju...@jellybean.co.uk wrote:

 I don't find layout a problem, with good editor support. I agree it's a
 problem, with poor editor support. That's all I meant.

 Let's put this issue in perspective.  For those few Haskell
 programmers that do find layout irritating, I'm sure we would all
 agree it's but a minor irritation.  The real downside of layout is if
 non-Haskell programmers use it as an excuse to dismiss the language.
 I happen to think that Data Parallel Haskell has great potential  for
 use in high performance computations.  I'd hate to see a bunch of
 Fortraners not try DPH because of Haskell syntax.

 Well that's a reasonable point.

 They can still use the non-layout form if it bothers them that much?

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

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


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-21 Thread Lennart Augustsson
Internally GHC does have to enforce the ordering on IO operations somehow.
If there actually was a RealWorld value being passed around you could
use some version of seq the guarantees sequential evaluation.
But GHC doesn't even pass a RealWorld around, the sequencing is
enforced by different means.

It's uninteresting for this discussion how GHC enforces the sequencing
internally, the important part is that it is part the sequencing is
part of the IO monad semantics and this is what should be used to
guarantee the sequencing of IO operations in a program.

  -- Lennart

On Thu, Aug 20, 2009 at 10:41 PM, Peter Verswyvelenbugf...@gmail.com wrote:
 But how does GHC implement the RealWorld internally? I guess this can't be
 done using standard Haskell stuff? It feels to me that if I would implement
 it, I would need seq again, or a strict field, or some incrementing time
 value that is a strict argument of each of the IO primitives. In any case, I
 would need strictness to control the dependencies no? I might be wrong
 (again) but this is all very interesting ;-)

 On Thu, Aug 20, 2009 at 10:25 PM, David Menendez d...@zednenem.com wrote:

 On Thu, Aug 20, 2009 at 3:43 PM, Peter Verswyvelenbugf...@gmail.com
 wrote:
 
  Also doesn't Haskell's IO system uses a hidden RealWorld type that has
  no
  value but which is passed from between monadics binds in a strict way to
  make the ordering work?

 Haskell only describes how the IO monad behaves. GHC's implementation
 uses a RealWorld type, but other implementations are possible.

 A quick sketch of an alternative implementation,

 data Trace = Done | Get (Char - Trace) | Put Char Trace

 newtype IO a = IO { unIO :: (a - Trace) - Trace }

 instance Monad IO where
    return a = IO (\k - k a)
    m = f = IO (\k - unIO m (\a - unIO (f a) k))

 getChar :: IO Char
 getChar = IO Get

 putChar :: Char - IO ()
 putChar c = IO (\k - Put c (k ()))

 The run-time system is responsible for interpreting the Trace and
 inputting/outputting characters as needed. All of IO can be
 implemented in this manner.

  So IO in Haskell is a horrible hack then? :-) If it
  would be done nicely, in the FRP way, then RealWorld IO would need time
  stamps to get rid of the hack?

 Again, no. GHC's IO type uses the RealWorld value to create data
 dependencies. For example, putChar 'x'  getChar, the getChar depends
 on the RealWorld returned by putChar 'x'.

 This is why it's dangerous to open up GHC's IO type unless you know
 what you're doing. If you aren't careful, you may accidentally
 duplicate or destroy the RealWorld, at which point you risk losing
 purity and referential transparency.

 I suppose you could consider the fact that GHC's IO is implemented
 using impure primitive operations a hack, but the whole point of the
 IO monad is to hide that impurity from the rest of the program.

 --
 Dave Menendez d...@zednenem.com
 http://www.eyrie.org/~zednenem/


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


Re: Re[2]: [Haskell-cafe] Re: Where do I put the seq?

2009-08-21 Thread Lennart Augustsson
You need a lot of magic to make the IO monad efficient.
You don't really want to pass around (and pattern match on) a
RealWorld token, that would be inefficient.


On Fri, Aug 21, 2009 at 11:04 AM, Peter Verswyvelenbugf...@gmail.com wrote:
 IO also seems to use unboxed (hence strict?) tuples

 newtype IO a = IO (State# RealWorld - (# State# RealWorld, a #))

 Not sure if this is just for performance, but if the strictness is required,
 here we have the horrible hack again then (would behave different without
 it?). I guess it works because when applying primitive function likes
 putChar#, these could be considered as fully strict, since putChar# c really
 does force evaluation of c strictly and puts in the screen. This is
 different from the lazy IO situation, where a string is concatenated lazily,
 and put on the screen by the consumer as soon as it's available. Ah I'm
 having troubles to explain myself formally, never mind :)
 Actually RealWorld is not defined in that file, it is defined here, but
 hidden
 file:///C:/app/ghp/doc/libraries/ghc-prim/GHC-Prim.html#t%3ARealWorld
 But I don't understand the comment
 data RealWorld Source
 RealWorld is deeply magical. It is primitive, but it is
 not unlifted (hence ptrArg). We never manipulate values of type RealWorld;
 it's only used in the type system, to parameterise State#.
 Maybe I should reread the papers, but it seems lots of magic is needed to
 get IO right (such as the existential types to make sure different state
 threads are kept separate)
 On Fri, Aug 21, 2009 at 10:52 AM, Bayley, Alistair
 alistair.bay...@invesco.com wrote:

  From: haskell-cafe-boun...@haskell.org
  [mailto:haskell-cafe-boun...@haskell.org] On Behalf Of Bulat Ziganshin
  To: Peter Verswyvelen
 
   But how does GHC implement the RealWorld internally? I guess
 
  look the base library sources for RealWorld

 http://www.haskell.org/ghc/docs/latest/html/libraries/base/src/GHC-IOBas
 e.html#IO
 *
 Confidentiality Note: The information contained in this message,
 and any attachments, may contain confidential and/or privileged
 material. It is intended solely for the person(s) or entity to
 which it is addressed. Any review, retransmission, dissemination,
 or taking of any action in reliance upon this information by
 persons or entities other than the intended recipient(s) is
 prohibited. If you received this in error, please contact the
 sender and delete the material from any computer.
 *



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


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


Re: Re[2]: [Haskell-cafe] Re: Where do I put the seq?

2009-08-21 Thread Lennart Augustsson
The IO in hbc was (is) the old request-response model, on top of which
there was also a continuation layer, as well as the monadic IO (once
that was invented).  It involved a lot more C code handling the
requests than I really liked.

BTW, unsafePerformIO is pretty ugly to implement in the
request-response model.  I take that as a sign that unsafePerformIO is
bad. :)

  -- Lennart

On Fri, Aug 21, 2009 at 3:14 PM, Derek Elkinsderek.a.elk...@gmail.com wrote:
 On Fri, Aug 21, 2009 at 5:04 AM, Lennart
 Augustssonlenn...@augustsson.net wrote:
 On Fri, Aug 21, 2009 at 10:52 AM, Bayley, Alistair
 alistair.bay...@invesco.com wrote:

  From: haskell-cafe-boun...@haskell.org
  [mailto:haskell-cafe-boun...@haskell.org] On Behalf Of Bulat Ziganshin
  To: Peter Verswyvelen
 
   But how does GHC implement the RealWorld internally? I guess
 
  look the base library sources for RealWorld

 http://www.haskell.org/ghc/docs/latest/html/libraries/base/src/GHC-IOBas
 e.html#IO

 On Fri, Aug 21, 2009 at 11:04 AM, Peter Verswyvelenbugf...@gmail.com wrote:
 IO also seems to use unboxed (hence strict?) tuples

 newtype IO a = IO (State# RealWorld - (# State# RealWorld, a #))

 Not sure if this is just for performance, but if the strictness is required,
 here we have the horrible hack again then (would behave different without
 it?). I guess it works because when applying primitive function likes
 putChar#, these could be considered as fully strict, since putChar# c really
 does force evaluation of c strictly and puts in the screen. This is
 different from the lazy IO situation, where a string is concatenated lazily,
 and put on the screen by the consumer as soon as it's available. Ah I'm
 having troubles to explain myself formally, never mind :)
 Actually RealWorld is not defined in that file, it is defined here, but
 hidden
 file:///C:/app/ghp/doc/libraries/ghc-prim/GHC-Prim.html#t%3ARealWorld
 But I don't understand the comment
 data RealWorld Source
 RealWorld is deeply magical. It is primitive, but it is
 not unlifted (hence ptrArg). We never manipulate values of type RealWorld;
 it's only used in the type system, to parameterise State#.
 Maybe I should reread the papers, but it seems lots of magic is needed to
 get IO right (such as the existential types to make sure different state
 threads are kept separate)

 You need a lot of magic to make the IO monad efficient.
 You don't really want to pass around (and pattern match on) a
 RealWorld token, that would be inefficient.

 I've always preferred the continuation based implementation of IO as
 used in Hugs and I believe in HBC.  GHC's handling of it has always
 seemed hack-y to me.  I don't recall any special treatment of IO by
 HBC, though Lennart will definitely be able to verify or deny that.

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


Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Lennart Augustsson
Using seq to control a program's semantics (as in, input-output
behaviour) is a horrible hack.
The seq operation there to control space and time aspects of your program.
(The specification of seq doesn't even say that the first argument is
evaluated before the second one.)
You should use data dependencies to control your program's semantics.

On Thu, Aug 20, 2009 at 4:34 PM, David Leimbachleim...@gmail.com wrote:


 On Thu, Aug 20, 2009 at 2:52 AM, Jules Bean ju...@jellybean.co.uk wrote:

 Peter Verswyvelen wrote:

 Not at all, use it for whatever you want to :-)

 I'm writing this code because I'm preparing to write a bunch of tutorials
 on FRP, and I first wanted to start with simple console based FRP, e.g.
 making a little text adventure game, where the input/choices of the user
 might be parsed ala parsec, using monadic style, applicative style, and
 arrows, and then doing the same with FRP frameworks like


 This is a really bad place to start a FRP tutorial IMO.

 The interface for 'interact' does not make any promises about the relative
 evaluation order of the input list / production order of the output list.

 That's why you are having to play horrible tricks with seq to try to force
 the order to be what you want.

 I don't think this is the basis of a robust system or a sensible tutorial.

 Just my 2c.

 Interesting feedback, but I don't get the reason really.  How is using seq a
 horrible trick?  It's there for strict evaluation when you need it, and in
 this case it was warranted.
 And as far as saying it's not a good basis for a robust system, I'm also not
 sure I agree, but a sensible tutorial, that I could believe as I think
 it's actually quite difficult to explain these topics to people in a way
 they're going to understand right away.
 Could we perhaps bother you to suggest an alternative along with your
 criticism?  It would feel a little more constructive at least (not that I
 think you were being terribly harsh)
 Dave
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


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


Re: [Haskell-cafe] unsafeDestructiveAssign?

2009-08-11 Thread Lennart Augustsson
No, there's no way you can change the value of 'a' after the fact.
Since 'a' is a constant the compiler has most likely inlined it
wherever it has been used, the done constant folding etc.
If you need an updateable variable, you need to tell the compiler,
otherwise it will assume your code is pure.

  -- Lennart

On Tue, Aug 11, 2009 at 5:48 PM, Job Vranishjvran...@gmail.com wrote:
 Does anybody know if there is some unsafe IO function that would let me do
 destructive assignment?
 Something like:

 a = 5
 main = do
   veryUnsafeAndYouShouldNeverEveryCallThisFunction_DestructiveAssign a 8
   print a
 8

 and yes I am in fact insane...

 I'm also looking for a way to make actual copies of data.
 so I could do something like this:

 a = Node 5 [Node 2 [], Node 5 [a]]
 main = do
   b - makeCopy a
   veryUnsafeAndYouShouldNeverEveryCallThisFunction_DestructiveAssign b (Node
 0 [])
   -- 'a' is unchanged

 It would be even more fantastic, if the copy function was lazy.
 I think the traverse function might actually make a copy, but I would be
 happier with something more general (doesn't require membership in
 traversable), and more explicit (was actually designed for making real
 copies).

 Any ideas?

 Thanks,

 - Job



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


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


Re: [Haskell-cafe] generalize RecordPuns and RecordWildCards to work with qualified names?

2009-08-09 Thread Lennart Augustsson
At a minimum I think the error message should be better.

I also think it would be natural to use the DisambiguateRecordFields
for the places where RecordWildcards are used.
I mean, if I change from unqualified import to a qualified one, and
then change all visible names to be qualified I would expect things to
still work.
For RecordPuns I don't have an opinion on what to do.

  -- Lennart

On Sun, Aug 9, 2009 at 9:42 PM, Simon Peyton-Jonessimo...@microsoft.com wrote:
 Oh, now I get it, thanks.  This message concerns design choices for 
 record-syntax-related GHC extensions.  Lennart, pls tune in.  You don’t need 
 to have read the thread to understand this message.

 | I think that Even refers to an example like this:
 |
 | module A where
 |   data A = A { a :: Int }
 |
 | The following works:
 |
 | {-# LANGUAGE NamedFieldPuns #-}
 | module B where
 |   import A
 |   f (A { a }) = a
 |
 | However, if we import A qualified, then punning does not seem to work:
 |
 | {-# LANGUAGE NamedFieldPuns #-}
 | module B where
 |   import qualified A
 |   f (A.A { a }) = a
 |
 | This results in: Not in scope: `a'

 Right.  What is happening is that GHC looks up the first 'a' (the one on the 
 LHS) and finds it not in scope.  If you add -XDisambiguateRecordFields, it 
 works fine.  But admittedly, the error message is unhelpful.  I could improve 
 that.

 Now on to the suggested change:

 | {-# LANGUAGE NamedFieldPuns #-}
 | module B where
 |   import qualified A
 |
 |   f (A.A { A.a }) = a
 |
 | This results in: Qualified variable in pattern: A.a
 |
 | Even is suggesting that instead of reporting an error, in the second
 | case we could use the translation:
 |
 |   f (A.A { A.a }) = a   --   f (A.A { A.a = a })
 |
 | (i.e., when punning occurs with a qualified name, use just the
 | unqualified part of the name in the pattern)

 Yes, that'd be possible.   But it seems debatable -- it doesn't *look* as if 
 the pattern (A.A { A.a }) binds 'a' -- and it seems even less desirable in 
 record construction and update.  To be concrete, would you expect these to 
 work too?

  g a = A.A { A.a }     --    g a = A.A { A.a = a }
  h x a = x { A.a }     --    h x a = a { A.a = a }

 In these cases, I think the abbreviated code looks too confusing.

 With -XDisambiguateRecordFields you could say

  g a = A.A { a }

 which seems better.  (But there's no help for record update, since we don’t 
 know which data constructor is involved.)


 So my current conclusion is: improve the error message, perhaps suggesting 
 the flag -XDismabiguateRecordFields, but don't add the change you suggest.

 Comments?

 Simon


 ___
 Glasgow-haskell-users mailing list
 glasgow-haskell-us...@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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


Re: [Haskell-cafe] Complex numbers and (**)

2009-08-08 Thread Lennart Augustsson
A2: Yes, this seem unfortunate, so perhaps a different definition for
Complex is warranted.
Or maybe the default implementation for (**) should be changed so that
0**x is 0, except if x is 0 (in which case I think it should be
undefined).

  -- Lennart


On Sat, Aug 8, 2009 at 2:55 PM, Paul Sargentpsarge+hask...@gmail.com wrote:
 Hi,

 First post to the cafe, so Hello everybody!.
 Hope this is reasonable subject matter and not too long.

 I've been working on some algorithms that involved taking the n-th root of
 complex numbers. In my code I've implemented this as raising the complex
 number ('z') to 1/n using the (**) operator. Obviously, there are n roots,
 but I only need one of them so this is fine.

 Q1) Have I missed a method that's a little less general than 'raising to a
 Complex'? We have integer powers, but not integer roots?

 All seems to work fine, except I have a little wrapper function to prefer
 real roots of real numbers, until I started seeing NaNs appearing. This
 happened when I tried to take the root of 0+0i. In fact raising 0+0i to any
 power with (**) causes NaNs to appear. (^) and (^^) have no problem,
 assuming the calculation is one that can be represented with those
 operators. Neither is there a problem when the values being raised are not
 in complex form.

 Prelude Data.Complex let xs = [0.0 :+ 0.0, 1.0 :+ 0.0, 2.0 :+ 0.0, 3.0 :+
 0.0]

 Prelude Data.Complex [x ^ 2 | x - xs]
 [0.0 :+ 0.0,1.0 :+ 0.0,4.0 :+ 0.0,9.0 :+ 0.0]

 Prelude Data.Complex [x ^^ 2 | x - xs]
 [0.0 :+ 0.0,1.0 :+ 0.0,4.0 :+ 0.0,9.0 :+ 0.0]

 Prelude Data.Complex [x ** 2 | x - xs]
 [NaN :+ NaN,1.0 :+ 0.0,4.0 :+ 0.0,9.002 :+ 0.0]

 Prelude Data.Complex let xs = [0.0,1.0,2.0,3.0]
 Prelude Data.Complex [x ** 2 | x - xs]
 [0.0,1.0,4.0,9.0]

 Digging deeper I've discovered this is because Complex inherits it's
 definition of (**) as x ** y = exp (log x * y). Well... the log of 0+0i is
 -Inf+0i. Multiply this by a real number in complex form and you end up with
 -Infinity * 0.0 as one of the terms. According to the IEEE floating point
 spec, this is NaN. That NaN propagates through exp, and you end up with NaN
 :+ NaN  as the result.

 Q2) Do people agree this is a bug in the definition of Data.Complex?

 Seems like the thing to do to fix this is have an instance of (**) for
 Data.Complex that special cases (0 :+ 0) ** _ to always return (0 :+ 0). An
 alternative would be to use the underlying non-complex (**) operator for
 arguments with no imaginary parts. One downside is that this would change
 the output of Complex (**) so that raising a real argument to a real power
 always produced a real result (which is actually what I want, but may not be
 what others expect / have got used to)

 Q3) Do people agree with these options? Any opinions? How would I submit a
 patch?

 I did send a mail to the glasgow-haskell-bugs list, but it doesn't appear to
 shown up in the archives, so I assume it didn't make it. It also didn't seem
 quite the right place as this is in the libraries. Apologies if anybody
 reading this is getting deja-vu.

 Paul




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


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


Re: [Haskell-cafe] Re: Simple quirk in behavior of `mod`

2009-08-04 Thread Lennart Augustsson
That how I was taught to round in school, so it doesn't seem at all
unusual to me.

2009/7/23 Matthias Görgens matthias.goerg...@googlemail.com:
 Round-to-even means x.5 gets rounded to x if x is even and x+1 if x is
 odd. This is sometimes known as banker's rounding.

 OK.  That's slightly unusual indeed.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Re: Adding a field to a data record

2009-07-29 Thread Lennart Augustsson
With the RecordWildCard extension you should be able to write

newFoo Old.Foo{..} = New.Foo { .., z=1 }



On Tue, Jul 28, 2009 at 3:47 PM, Henry Laxennadine.and.he...@pobox.com wrote:
 Malcolm Wallace Malcolm.Wallace at cs.york.ac.uk writes:


  and perhaps use emacs to
  query-replace all the Foo1's back to Foo's

 At least this bit can be avoided easily enough, by using
 module qualification during the conversion process.

      module Original (Foo(..)) where
      data Foo = Foo { ... y :: Int } deriving ...

      module New (Foo(..)) where
      data Foo = Foo { ... y, z :: Int } deriving ...

      module Convert where
      import Original as Old
      import New as New
      newFoo :: Old.Foo - New.Foo
      newFoo old{..} = New.Foo { a=a, b=b, ... z=1 }

 Finally rename module New.

 Regards,
      Malcolm


 Thanks Malcolm, yes, that keeps me out of emacs, but the part I would really
 like to avoid is writing the New.Foo { a=a, b=b, ... z=1 } part, where the 
 field
 names are many, long, and varied.  Yes, I could cut and paste, but I'm hoping
 for a better way.  Thanks.
 Best wishes,
 Henry Laxen


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

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


Re: [Haskell-cafe] Slightly off-topic: Lambda calculus

2009-06-21 Thread Lennart Augustsson
As others have pointed out, it is not enough to rename before reduction.
It should be pretty obvious since when you do substitution and copy a
lambda expression into more than once place you will introduce
variables with the same name.  You can keep unique variables by
cloning during substitution, i.e., renaming the bound variables.

  -- Lennart

On Sun, Jun 21, 2009 at 6:53 PM, Andrew
Coppinandrewcop...@btinternet.com wrote:
 OK, so I'm guessing there might be one or two (!) people around here who
 know something about the Lambda calculus.

 I've written a simple interpretter that takes any valid Lambda expression
 and performs as many beta reductions as possible. When the input is first
 received, all the variables are renamed to be unique.

 Question: Does this guarantee that the reduction sequence will never contain
 name collisions?

 I have a sinking feeling that it does not. However, I can find no
 counter-example as yet. If somebody here can provide either a proof or a
 counter-example, that would be helpful.

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

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


Re: [Haskell-cafe] Slightly off-topic: Lambda calculus

2009-06-21 Thread Lennart Augustsson
Actually, keeping all names distinct is not de Bruijn numbering, it's
called the Barendregt convention.

On Sun, Jun 21, 2009 at 7:05 PM, Deniz Dogandeniz.a.m.do...@gmail.com wrote:
 2009/6/21 Andrew Coppin andrewcop...@btinternet.com:
 OK, so I'm guessing there might be one or two (!) people around here who
 know something about the Lambda calculus.

 I've written a simple interpretter that takes any valid Lambda expression
 and performs as many beta reductions as possible. When the input is first
 received, all the variables are renamed to be unique.

 Question: Does this guarantee that the reduction sequence will never contain
 name collisions?

 I have a sinking feeling that it does not. However, I can find no
 counter-example as yet. If somebody here can provide either a proof or a
 counter-example, that would be helpful.

 I'm no expert, but it sounds to me like you're doing the equivalent of
 de Bruijn indexing, which is a method to avoid alpha conversion,
 which is basically what you're worried about. Therefore, I'm guessing
 that there will be no name collisions.

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

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


Re: [Haskell-cafe] unique identity and name shadowing during type inference

2009-06-20 Thread Lennart Augustsson
Use 1.  You'll probably need a monad in the type checker soon or later
anyway, e.g., for handling errors.

On Sat, Jun 20, 2009 at 7:57 PM, Geoffrey Irvingirv...@naml.us wrote:
 Hello,

 I am designing a type inference algorithm for a language with
 arbitrary function overloading.  For various reasons (beyond the scope
 of this email), it's impossible to know the full type of an overloaded
 function, so each function is assigned a unique primitive type and the
 inference algorithm gradually learns more information about the
 primitive.  For example, if we declare an identity function

    f x = x

 the algorithm will create a primitive type F, and record f :: F.  If
 we use the function a few times,

    f 1
    f blah

 the algorithm will infer

    F Int = Int
    F String = String

 My question is: what's the best way to represent these unique
 primitive types in Haskell?  A new type primitive needs to be created
 whenever we process a function declaration.  Nested function
 declarations produce a different primitive each time the parent is
 invoked with different argument types.  These separate primitives can
 escape if local functions are returned, so the inference algorithm
 must be able to keep them separate and learn more about them after
 their parent function is forgotten.

 Here are a few ways I know of:

 1. Thread a uniqueness generator monad through the whole algorithm.
 I'd prefer to avoid this extra plumbing if possible.
 2. Label primitives with the full context of how they were created.
 If function f declares a nested function g, and f is called with Int
 and Char, the primitives for g would be labeled with f Int and f
 Char to keep them separate.  This is similar to lambda lifting.
 3. Scary hacks involving makeStableName and unsafePerformIO.  Some
 sort of context would have to be thrown around here to make sure GHC
 doesn't merge the different makeStableName calls.

 Unfortunately, method (2) is complicated by the fact that variable
 names are not unique even in the internal representation (I'm using
 the trick from [1]), so I'm not sure what the minimal unique context
 would be.

 Does anyone know other methods outside of (1), (2), or (3), or clean
 ways of structuring (2) or (3)?

 Thanks!
 Geoffrey

 [1]: http://www.haskell.org/~simonmar/bib/ghcinliner02_abstract.html
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Obscure weirdness

2009-06-20 Thread Lennart Augustsson
Did you try running it in some debugger, like windbg or VS?

2009/6/20 Andrew Coppin andrewcop...@btinternet.com:
 Marcin Kosiba wrote:

 On Saturday 20 June 2009, Andrew Coppin wrote:


 OK, so here's an interesting problem...

 I've been coding away all day, but now my program is doing something
 slightly weird. For a specific input, it summarily terminates. The
 registered exception handler does not fire. There is no output to stdout
 or stderr indicating what the problem is. It just *stops* half way
 through the printout.

 Weirder: If I run it in GHCi, then GHCi itself terminates. (I didn't
 think you could *do* that!)


 Hi,
        With the information you've provided it's hard to even guess. At
 least take a look at your app's RAM usage -- it just may be that its
 allocating too much memory and the OOM killer is killing it (if you're
 running linux, that is).
        You may also want to try the GHCi debugger [1] to find out where
 the program crashes. The last thing I'd do is blame it on ghc/ghci, but as
 always -- such a possibility exists.


 It's Windows. And while it's possible (indeed even probable) that my code
 has an infinite loop in it somewhere, usually that makes the program slow to
 a crawl and start thrashing the HD as it hits virtual memory. But this
 program just dies. Instantly.

 And I already tried the GHCi debugger. When I run the program, GHCi just
 quits. I suppose if I can track down exactly *where* in the program it's
 dying, I could try single-stepping through it...

 If I was doing something tricky like FFI or unsafe coersions, I'd assume I'd
 got it wrong somewhere. But I'm just doing plain ordinary Haskell stuff -
 traversing trees, pattern matching, etc. I'm a bit perplexed that it can
 fail this way.

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

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


Re: [Haskell-cafe] curious about sum

2009-06-17 Thread Lennart Augustsson
What do you mean by literals are strict?  Strictness is a semantic
property of functions, and while literals can be overloaded to be
functions I don't know what you mean.

On Wed, Jun 17, 2009 at 9:50 PM, Keith Sheppardkeiths...@gmail.com wrote:
 Haskell's numeric literals are strict. You wouldn't want that to
 change right? It seems to me that having sum and product be strict is
 consistent with this.

 -Keith

 On Wed, Jun 17, 2009 at 11:15 AM, Thomas Davietom.da...@gmail.com wrote:

 On 17 Jun 2009, at 13:32, Yitzchak Gale wrote:

 Henk-Jan van Tuyl wrote:

 reverse
 maximum
 minimum

 Oh yes, please fix those also!

 import Prelude.Strict?

 Honestly, these functions are ones that I've *deffinately* used lazy
 versions of, in fact, in the cases of minimum/maximum I've even used ones
 that are super-lazy and parallel using unamb.

 It would be extremely odd to randomly decide most people would want this to
 be strict based on no knowledge of what they're actually doing.  Instead,
 why don't we stand by the fact that haskell is a lazy language, and that the
 functions we get by default are lazy, and then write a strict prelude as I
 suggest above to complement the lazy version.

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




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

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


Re: [Haskell-cafe] curious about sum

2009-06-17 Thread Lennart Augustsson
The creators of Haskell didn't pick any particular representation for numbers.
(Well, literals are kind of Integers.)  You can pick what types you
make instances of Num.
Some of them are lazy, some of them are strict.

On Wed, Jun 17, 2009 at 11:05 PM, Keith Sheppardkeiths...@gmail.com wrote:
 In lambda calculus numbers are just functions and you evaluate them
 just like any other function. Haskell could have chosen the same
 representation for numbers and all evaluation on numbers would be lazy
 (assuming normal order evaluation). I think that would have been the
 Purist Lazy way to go. That is not the way the creators of Haskell
 designed language though... am i missing something?

 On Wed, Jun 17, 2009 at 4:05 PM, Lennart
 Augustssonlenn...@augustsson.net wrote:
 What do you mean by literals are strict?  Strictness is a semantic
 property of functions, and while literals can be overloaded to be
 functions I don't know what you mean.

 On Wed, Jun 17, 2009 at 9:50 PM, Keith Sheppardkeiths...@gmail.com wrote:
 Haskell's numeric literals are strict. You wouldn't want that to
 change right? It seems to me that having sum and product be strict is
 consistent with this.

 -Keith

 On Wed, Jun 17, 2009 at 11:15 AM, Thomas Davietom.da...@gmail.com wrote:

 On 17 Jun 2009, at 13:32, Yitzchak Gale wrote:

 Henk-Jan van Tuyl wrote:

 reverse
 maximum
 minimum

 Oh yes, please fix those also!

 import Prelude.Strict?

 Honestly, these functions are ones that I've *deffinately* used lazy
 versions of, in fact, in the cases of minimum/maximum I've even used ones
 that are super-lazy and parallel using unamb.

 It would be extremely odd to randomly decide most people would want this 
 to
 be strict based on no knowledge of what they're actually doing.  Instead,
 why don't we stand by the fact that haskell is a lazy language, and that 
 the
 functions we get by default are lazy, and then write a strict prelude as I
 suggest above to complement the lazy version.

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




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





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

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


Re: [Haskell-cafe] Performance of functional priority queues

2009-06-15 Thread Lennart Augustsson
A priority queue can't have all operations being O(1), because then
you would be able to sort in O(n) time.  So O(log n) deleteMin and
O(1) for the rest is as good as it gets.

On Mon, Jun 15, 2009 at 10:40 AM, Sebastian
Sylvansebastian.syl...@gmail.com wrote:


 On Mon, Jun 15, 2009 at 4:18 AM, Richard O'Keefe o...@cs.otago.ac.nz wrote:

 There's a current thread in the Erlang mailing list about
 priority queues.  I'm aware of, for example, the Brodal/Okasaki
 paper and the David King paper. I'm also aware of James Cook's
 priority queue package in Hackage, have my own copy of Okasaki's
 book, and have just spent an hour searching the web.

 One of the correspondents in that thread claims that it is
 provably impossible to have an efficient priority queue implementation


 A priority queue based on skewed binomial heaps is asymptotically optimal
 (O(1) for everything except deleteMin which is O(log n)), so if that's what
 he means by efficient then he's most definitely wrong. If he's talking
 about small constant factors then it's harder to understand what he's
 referring to more precisely, and therefore what he means by provably.

 --
 Sebastian Sylvan
 +44(0)7857-300802
 UIN: 44640862

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


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


Re: [Haskell-cafe] Performance of functional priority queues

2009-06-15 Thread Lennart Augustsson
I wasn't contradicting you, just clarifying that this is indeed the
optimal asymtotic complexity.

On Mon, Jun 15, 2009 at 3:43 PM, Sebastian
Sylvansebastian.syl...@gmail.com wrote:
 Is that not what I said?

 On Mon, Jun 15, 2009 at 2:12 PM, Lennart Augustsson lenn...@augustsson.net
 wrote:

 A priority queue can't have all operations being O(1), because then
 you would be able to sort in O(n) time.  So O(log n) deleteMin and
 O(1) for the rest is as good as it gets.

 On Mon, Jun 15, 2009 at 10:40 AM, Sebastian
 Sylvansebastian.syl...@gmail.com wrote:
 
 
  On Mon, Jun 15, 2009 at 4:18 AM, Richard O'Keefe o...@cs.otago.ac.nz
  wrote:
 
  There's a current thread in the Erlang mailing list about
  priority queues.  I'm aware of, for example, the Brodal/Okasaki
  paper and the David King paper. I'm also aware of James Cook's
  priority queue package in Hackage, have my own copy of Okasaki's
  book, and have just spent an hour searching the web.
 
  One of the correspondents in that thread claims that it is
  provably impossible to have an efficient priority queue implementation
 
 
  A priority queue based on skewed binomial heaps is asymptotically
  optimal
  (O(1) for everything except deleteMin which is O(log n)), so if that's
  what
  he means by efficient then he's most definitely wrong. If he's talking
  about small constant factors then it's harder to understand what he's
  referring to more precisely, and therefore what he means by provably.
 
  --
  Sebastian Sylvan
  +44(0)7857-300802
  UIN: 44640862
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 



 --
 Sebastian Sylvan
 +44(0)7857-300802
 UIN: 44640862

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


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


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

2009-05-28 Thread Lennart Augustsson
Here's what I usually use.  As Simon points out, ambiguity is lurking
as soon as you use conditional.  You can avoid it a fundep, but that's
not necessarily what you want either.

-- | Generalization of the 'Bool' type.  Used by the generalized 'Eq' and 'Ord'.
class Boolean bool where
()  :: bool - bool - bool   -- ^Logical conjunction.
(||)  :: bool - bool - bool   -- ^Logical disjunction.
not   :: bool - bool   -- ^Locical negation.
false :: bool   -- ^Truth.
true  :: bool   -- ^Falsity.
fromBool :: Bool - bool-- ^Convert a 'Bool' to the
generalized Boolean type.
fromBool b = if b then true else false

-- | Generalization of the @if@ construct.
class (Boolean bool) = Conditional bool a where
conditional :: bool - a - a - a -- ^Pick the first argument if
the 'Boolean' value is true, otherwise the second argument.

class (Boolean bool) = Eq a bool {- x | a - bool -} where
(==) :: a - a - bool
(/=) :: a - a - bool

x /= y  =  not (x == y)
x == y  =  not (x /= y)


On Thu, May 28, 2009 at 8:14 AM, Simon Peyton-Jones
simo...@microsoft.com wrote:
 You are absolutely right about the tantalising opportunity.  I know that 
 Lennart has thought quite a bit about this very point when designing his 
 Paradise system.  Likewise Conal for Pan.

 One difficulty is, I think, that it's easy to get ambiguity.  Eg
        ifthenelse (a  b) e1 e2
 The (ab) produces a boolean-thing, and ifthenelse consumes it; but which 
 type of boolean?  The Expr type?  Real Bools? Or what?

 If there was a nice design, then GHC's existing -fno-implicit-prelude flag 
 could be extended (again) to desugar if-then-else to the new thing.  But the 
 design is unclear, to me anyway.

 Simon

 | -Original Message-
 | From: haskell-cafe-boun...@haskell.org 
 [mailto:haskell-cafe-boun...@haskell.org] On
 | Behalf Of Sebastiaan Visser
 | Sent: 27 May 2009 13:32
 | To: Haskell Cafe
 | Subject: [Haskell-cafe] Bool as type class to serve EDSLs.
 |
 | Hello,
 |
 | While playing with embedded domain specific languages in Haskell I
 | discovered the Num type class is a really neat tool. Take this simple
 | example embedded language that can embed primitives from the output
 | language and can do function application.
 |
 |  data Expr :: * - * where
 |    Prim :: String - Expr a
 |    App  :: Expr (a - b) - Expr a - Expr b
 |
 | Take these two dummy types to represent things in the output language.
 |
 |  data MyNum
 |  data MyBool
 |
 | Now it is very easy to create an Num instance for this language:
 |
 |  primPlus :: Expr (MyNum - MyNum - MyNum)
 |  primPlus = Prim prim+
 |
 |  instance Num (Epxr MyNum) where
 |    a + b = primPlus `App` a `App` b
 |    fromInteger = Prim . show
 |    ...
 |
 | Which allows you to create very beautiful expression for your language
 | embedded inside Haskell. The Haskell expression `10 * 5 + 2' produces
 | a nice and well typed expression in your embedded domain.
 |
 | But unfortunately, not everyone in the Prelude is as tolerant as the
 | Num instance. Take the Eq and the Ord type classes for example, they
 | require you to deliver real Haskell `Bool's. This makes it impossible
 | make your DSL an instance of these two, because there are no `Bool's
 | only `Expr Bool's.
 |
 | Which brings me to the point that, for the sake of embedding other
 | languages, Haskell's Prelude (or an alternative) can greatly benefit
 | from (at least) a Boolean type class like this:
 |
 | class Boolean a where
 |    ifthenelse :: a - b - b - b         -- Not sure about this
 | representation.
 |    ...
 |
 | And one instance:
 |
 |  instance Boolean (Expr MyBool) where
 |    ifthenelse c a b = Prim if-then-else `App` c `App` a `App` b
 |
 | Now we can change (for example) the Eq type class to this:
 |
 |  class Eq a where
 |    (==) :: Boolean b = a - a - b
 |    (/=) :: Boolean b = a - a - b
 |
 | For which we can give an implementation for our domain:
 |
 |  primEq :: Epxr (a - a - MyBool)
 |  primEq = Prim ==
 |
 |  instance Eq (Expr a) where
 |    a == b = primEq `App` a `App` b
 |
 | And now we get all functionality from the Prelude that is based on Eq
 | (like not, , ||, etc) for free in our domain specific language! Off
 | course there are many, many more examples of things from the standard
 | libraries that can be generalised in order to serve reuse in EDSLs.
 |
 | Anyone already working on such a generalized Prelude? I can imagine
 | much more domains can benefit from this than my example above. Any
 | interesting thoughts or pointers related to this subject?
 |
 | Gr,
 |
 | --
 | Sebastiaan Visser
 |
 | ___
 | Haskell-Cafe mailing list
 | Haskell-Cafe@haskell.org
 | http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Haskell type system and the lambda cube

2009-05-25 Thread Lennart Augustsson
Type checking is decidable for all of the lambda cube, but not type inference.

Haskell 98 is a subset of Fw, Haskell with extensions is an superset of Fw.

  -- Lennart

On Mon, May 25, 2009 at 12:59 PM, Brent Yorgey byor...@seas.upenn.edu wrote:
 On Sun, May 24, 2009 at 10:39:50AM +0200, Petr Pudlak wrote:
 On Sun, May 24, 2009 at 12:18:40PM +0400, Eugene Kirpichov wrote:
  Haskell has terms depending on types (polymorphic terms) and types
  depending on types (type families?), but no dependent types.

 But how about undecidability? I'd say that lambda2 or lambda-omega have
 undecidable type checking,

 I don't think that's true.  Unless I am mistaken, type checking is
 decidable for all the vertices of the lambda cube.

 (BWT, will some future version of Haskell consider including some kind of
 dependent types?)

 I doubt it.  But there is a lot of current research into bringing as
 much of the power of dependent types into the language (e.g. type
 families) without actually bringing in all the headaches of
 full-spectrum dependent types.

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

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


Re: [Haskell-cafe] conflicting variable definitions in pattern

2009-05-15 Thread Lennart Augustsson
In the original language design the Haskell committee considered
allowing multiple occurrences of the same variable in a pattern (with
the suggested equality tests), but it was rejected in favour of
simplicity.

  -- Lennart

On Fri, May 15, 2009 at 11:30 AM, Sittampalam, Ganesh
ganesh.sittampa...@credit-suisse.com wrote:
 Conor McBride wrote:
 On 15 May 2009, at 09:11, Sittampalam, Ganesh wrote:

 but then pattern matching can introduce Eq constraints which some
 might see as a bit odd.

 Doesn't seem that odd to me. Plenty of other language features come
 with constraints attached.

 It's the introduction of a constraint from tweaking a pattern that is
 odd, I think. By way of precedent H98 rejected this kind of idea in
 favour of putting 'fail' into Monad.

 Ganesh

 ===
  Please access the attached hyperlink for an important electronic 
 communications disclaimer:
  http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
  ===

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

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


Re: [Haskell-cafe] conflicting variable definitions in pattern

2009-05-15 Thread Lennart Augustsson
Simplicity of pattern matching semantics, not of implementation (we
all knew how to implement it).
Miranda had non-linear patterns, but nobody really argued for them in Haskell.
If Haskell had them, I'd not argue to have them removed, but nor will
I argue to add them.

  -- Lennart

On Fri, May 15, 2009 at 1:19 PM, Conor McBride
co...@strictlypositive.org wrote:

 On 15 May 2009, at 12:07, Lennart Augustsson wrote:

 In the original language design the Haskell committee considered
 allowing multiple occurrences of the same variable in a pattern (with
 the suggested equality tests), but it was rejected in favour of
 simplicity.

 Simplicity for whom, is the question? My point is
 only that there's no technical horror to the proposal.
 It's just that, given guards, the benefit (in simplicity
 of program comprehension) of nonlinear patterns over
 explicit == is noticeable but hardly spectacular.

 Rumblings about funny termination behaviour, equality
 for functions, and the complexity of unification (which
 isn't the proposal anyway) are wide of the mark. This
 is just an ordinary cost-versus-benefit issue. My guess
 is that if this feature were already in, few would be
 campaigning to remove it. (By all means step up and say
 why!) As it's not in, it has to compete with other
 priorities: I'm mildly positive about nonlinear
 patterns, but there are more important concerns.

 Frankly, the worst consequence I've had from Haskell's
 pattern linearity was just my father's derision. He
 quite naturally complained that his programs had lost
 some of their simplicity.

 All the best

 Conor

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

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


Re: [Haskell-cafe] is value evaluated?

2009-05-09 Thread Lennart Augustsson
But testing for something being evaluated has to be in the IO monad,
or else you're going to break the semantics.

On Fri, May 8, 2009 at 4:14 PM, Don Stewart d...@galois.com wrote:
 Andy Gill has been advocating programmatic access to the 'is evaluated'
 status bit for years now. 'seq' becomes cheaper, and we can write
 operational properties/assertions about strictness.

 -- Don


 jochem:
 Nikhil Patil wrote:
  Hi,
 
  I am curious to know if there is a function in Haskell to find if a
 certain
  value has already been evaluated. The function I need would have the type:
 
  (?!) :: a - Bool

 I will call this function `evaluated', since it is not a binary operator.

 The existence of such a function would violate referential transparency.

 What would the value of
 ( evaluated (fibs !! 100), evaluated (fibs !! 100) )
 be ? Suppose that I first print the `fst' of this tuple, then print the
 101st Fibonacci nummber, and then print the `snd' of this tuple. By lazy
 evaluation, one would expect that this yields

 False
 the 101st Fibonacci number
 True

 but this violates referential transparency.

 Cheers,
 --
 Jochem Berndsen | joc...@functor.nl
 GPG: 0xE6FABFAB
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] A brief note on n_k patterns and Hackage

2009-05-04 Thread Lennart Augustsson
I presume that is a joke, but it's not very funny.

On Mon, May 4, 2009 at 6:48 PM, Richard O'Keefe o...@cs.otago.ac.nz wrote:
 [about n+k in Hackage]
 On 5 May 2009, at 12:23 pm, John Van Enk wrote:

 Which package?

 There are at least two occurrences of n+1 as a pattern.
 If anyone wants to get rid of them, I'd like them to work
 as hard at this as I did...


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

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


Re: [Haskell-cafe] Question about implementing an off-side rule in Parsec 2

2009-04-28 Thread Lennart Augustsson
Implementing exactly Haskell's rule for indentation is incredibly hard.
In fact, no known Haskell compiler gets it right.
But if you make a slightly simpler one, it's easy.  The simple one is
the one based only on indentation.

There are different ways you can do this.

For instance, you can preprocess the token stream from the lexer.
This prprocessor needs a little bit of parsing, e.g., if it encounters
a let token that is not followed by a { token it should insert a
{ and then a corresponding } at the right place (this requires
every token to carry its column number).

You can also integrate it more into the parser.  Make, say, a block
parsing combinator that is called after seeing a let.  If block does
not see a { it will modify the remaining token stream to insert the
} at the right place.  Nested blocks will similarely to their
modifications.

You can also imagine inserting indentation change as a new kind of
token in the token streak and then rewriting the grammar to deal with
this.

Personally, I like option two (the block parsing combinator).  I've
used it several times.

  -- Lennart

On Mon, Apr 27, 2009 at 10:41 PM, Bas van Gijzel neneko...@gmail.com wrote:
 Hello everyone,

 I'm doing a bachelor project focused on comparing parsers. One of the parser
 libraries I'm using is Parsec (2) and I'm going to implement a very small
 subset of haskell with it, with as most important feature the off-side rule
 (indentation based parsing) used in function definitions and possibly in
 where clauses.

 But I'm still a bit stuck on how to implement this cleanly. I tried to
 search for some examples on blogs but I haven't found anything yet. As far
 as I can see the way to go would be using getState and updateState methods
 defined in Parsec.Prim and to use the methods in Parsec.Pos to compare the
 difference in indendation for tokens.

 But I haven't completely wrapped my head around any state monad yet and I
 don't understand Parsec enough yet to see how to use the methods Parsec.Pos
 and state easily. Some examples or pointers to something to read would
 really be helpful.

 Thanks in advance,

 Bas van Gijzel

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


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


Re: [Haskell-cafe] Re: ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release

2009-04-23 Thread Lennart Augustsson
Let me parenthesise and rename
  (n + 1) +++ 1 = n
This defines a function +++, first argument is a n+1 pattern, second
argument is 1.

In the same way,
  (+) + 1 + 1 = (+)
defines a function +, first argument is n+1 (but using (+) as n),
second argument is 1.

On Thu, Apr 23, 2009 at 10:27 AM, Colin Paul Adams
co...@colina.demon.co.uk wrote:
 Lennart == Lennart Augustsson lenn...@augustsson.net writes:

    Lennart Of course, n+k will be missed by Haskell obfuscators.  I
    Lennart mean, what will we do without (+) + 1 + 1 = (+) ?

 I think what would be missed would you be having the opportunity to
 explain to me what it means.

 But as we still have them, go right ahead (please).
 --
 Colin Adams
 Preston Lancashire

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


Re: [Haskell-cafe] Re: ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release

2009-04-23 Thread Lennart Augustsson
On Thu, Apr 23, 2009 at 6:30 AM, Richard O'Keefe o...@cs.otago.ac.nz wrote:
  - a somewhat bogus claim about how much of the library you need to
   know how to use it (of COURSE you need to know about integers in
   order to use an integer operation, what's so bad about that?)
  - the claim that + doesn't mean + (this is really an argument about
   the scope of + and could have been dealt with by ruling that n+k
   is only available when the version of + in scope is the one from
   the Prelude)

What's bogus about that claim?  Then n+k patterns have type (Integral
a) = a, so you need to know about type classes and Integral.

Even if it's listed as a reason, you rest assure that the Haskell'
committee did consider how widespread the use of n+k was before
removing it.  Of course, this can only be an educated guess.

Of course, n+k will be missed by Haskell obfuscators.  I mean, what
will we do without
  (+) + 1 + 1 = (+)
?

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


  1   2   3   4   5   6   >