Re: [Haskell-cafe] Re: Slightly humorous: Headhunters toolbox (example for Germany)

2010-08-17 Thread Lutz Donnerhacke
* Ertugrul Soeylemez wrote:
 Good to know that Saxony-Anhalt is the state in Germany with leading
 interest in Haskell. :-) I would like to know, whether this is due to
 Magdeburg or Halle.

 Saxony-Anhalt is the state in Germany with leading number of Google
 searches regarding Haskell.

And that means, that the two people playing with Haskell at the university
of Halle (located in Saxony-Anhalt) has Internet access an know to use a
search engine.

Lutz, using good old Altavista via 64kbps in Jena, Thuringia.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why Either = Left | Right instead of something like Result = Success | Failure

2010-05-27 Thread Lutz Donnerhacke
* Ionut G. Stan wrote:
 I was just wondering if there's any particular reason for which the two
 constructors of the Either data type are named Left and Right.

Yes. The basic function on this type is either.

either a b (Left  x) = Left  (a x)
either a b (Right x) = Right (b x)

So the names of the constuctors are natural.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Bug with [Double]

2010-05-19 Thread Lutz Donnerhacke
* Ben Millwood wrote:
 Prelude [1,1+2/3..10] :: [Rational]
 [1 % 1,5 % 3,7 % 3,3 % 1,11 % 3,13 % 3,5 % 1,17 % 3,19 % 3,7 % 1,23 %
 3,25 % 3,9 % 1,29 % 3,31 % 3]

 Same result.

 This sounds like a bug to me. The section of the Haskell Report that
 deals with the Enum class mentions Float and Double, not Rational, and
 there's really no sensible reason why Rationals would exhibit this
 behaviour given that they don't have rounding error.

Double is not better:

Prelude [9,9+2/3..10]
[9.0,9.666,10.332]
Prelude [7,9 .. 10]
[7,9]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] (liftM join .) . mapM

2009-12-29 Thread Lutz Donnerhacke
* Tony Morris wrote:
 Can (liftM join .) . mapM be improved?
 (Monad m) = (a - m [b]) - [a] - m [b]

a) liftM concat . mapM  -- list handling . monad handling
b) (sequence .) . map   -- monad handling . list handling

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


Re: [Haskell-cafe] semantics of type synonym

2009-12-29 Thread Lutz Donnerhacke
* pbrowne wrote:
 semantics). I used the following type synonym:

type String = [Char]
type Name = String

String, Name and [Char] are synonyms, which means every expression is
identically to the others. There is no difference besides that String and
Name are type aliases while [Char] is a type construct.

getName :: String - Name
getName n = n

 I checked the types with two tests:
 -- test 1
:t ww
 ww :: [Char]

The type interference system determines that you have an array of
characters, hence a [Char]. All those existing type aliases are suppressed
by the module. Otherwise the list get's very long ...

 -- test 2
:t getName(ww)
 getName(ww) :: Name

From the definition of getName, the compiler knows which type alias is
prefered from the set of equivalent names.

 Obviously I get two different types.

You get two different representations of the same type.

 In the case of the function Haskells type system seems to pick up enough
 information to determine that “ww” is a Name.

Nope. ww is still a [Char] for the compiler. And you do not even check for
the type of ww.

:t snd . (\x - (getName x, x)) $ ww
... :: String

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


Re: [Haskell-cafe] about Haskell code written to be too smart

2009-03-26 Thread Lutz Donnerhacke
* Claus Reinke wrote:
 Continuing our adventures into stylistic and semantic differences:-)

It's good practice to keep a simple minded version of the code and using
quickcheck to try to find differences between the optimized and trivial
version. It's good practice to even check, that the optimized version is
really faster/smaller than the simple one.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] about Haskell code written to be too smart

2009-03-24 Thread Lutz Donnerhacke
* Manlio Perillo wrote:
 But this may be really a question of personal taste or experience.
 What is more natural?

 1) pattern matching
 2) recursion
 or
 1) function composition
 2) high level functions

Composition of library functions is usually much more readable than hand
written recursion, simply because the typical idiom is highlighted instead
of checking yourself, that there is no strange matching against the obvious
case.

Composition of library functions is usually much more efficient and
preferable than hand written recursion, simply because the fine tuned fusion
capabilities.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] type metaphysics

2009-02-02 Thread Lutz Donnerhacke
* Martijn van Steenbergen wrote:
 Int has 2^32 values, just like in Java.

Haskell Report 6.4 (revised):
  The finite-precision integer type Int covers at least
  the range [ - 2^29, 2^29 - 1]. 

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


Re: [Haskell-cafe] Re: tensor product of dynamic-sized bits

2009-01-22 Thread Lutz Donnerhacke
* Ahn, Ki Yung wrote:
 This is why I am looking for existing work, because I am
 not yet very sure about my code I'm using.

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


Re: [Haskell-cafe] Re: sort and lazyness (?)

2008-12-19 Thread Lutz Donnerhacke
* Daniel Kraft wrote:
 Otherwise, how can one handle such amounts in data anyway?
 Only using arrays?

Data.Array or some problem specific data structure.

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


Re: [Haskell-cafe] Bit Field Marshalling

2008-11-07 Thread Lutz Donnerhacke
* Michael D. Adams wrote:
 But as far as I can tell, hsc2hs doesn't support bit
 fields.  On top of that I'm not sure I can make any safe assumptions
 about what order the bit fields are packed (LSB or MSB first).

C standard allows padding and reorder of struct entries in order to match
alignment requirements. The only exeption are bitfields, which must not
reordered and padded. This way bit fields are the only portable way to
define the binary representation in C. Unfortunly the C standard does not
specify any bit order for bit fields, but almost all implementations use
the machine specific bit order, in order to ease access to multiple bits
wide bit field and fill LSB to MSB. But there is no guarantee.

I run into this problem when writing an low level kernel interface in SPARK.
The ABI (binary representation) of the kernel API depends on the C compiler
flags (i.e. #pragma packed). Especially kernels of commericial unicies might
generate this problem, because the developer uses gcc instead of the native
compiler.

The only portable way to get access to C defined structures is involving
a C compiler, either using hsc or a C helper module.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Poor libraries documentation

2008-01-31 Thread Lutz Donnerhacke
* Jonathan Cast wrote:
 On 30 Jan 2008, at 7:19 PM, Anton van Straaten wrote:
  quickCheck $  x - cos (x + 2*pi) == cos x
 Falsifiable, after 2 tests:
 -1.0

 Test.QuickCheck.quickCheck $ \x - abs (cos x - cos (x + 2*pi))  0.1
OK, passed 100 tests.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: cryptographic hash functions in darcs (re: announcing darcs 2.0.0pre3)

2008-01-25 Thread Lutz Donnerhacke
* zooko wrote:
 This makes the choice of SHA-1 for the patch-id-generation function  
 wholly inappropriate.  We already know that SHA-1 doesn't have  
 collision resistance, and there is reason to suspect that in the near  
 future it will turn out that it doesn't have second-pre-image  
 resistance either.

Calm down! The found collisions in SHA-1 require some very specific
environment choices. I doubt darcs will allow those preconditions.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Why functional programming matters

2008-01-24 Thread Lutz Donnerhacke
* Isaac Dupree wrote:
 fewer frustratingly unsolvable bugs down-the-road?

I personally like the refactoring speed. Due to pureness it's easy to
refactor and that's why I can generalize more and more often.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [darcs-devel] [Haskell-cafe] Re: announcing darcs 2.0.0pre3

2008-01-23 Thread Lutz Donnerhacke
* zooko wrote:
 On the one hand, SHA-1 is cryptographically fragile and is deprecated
 for use in applications that require collision-resistance and pre- 
 image resistance.

Such a cryptographically strong requirement is not given in the darcs case.

SHA-1 is still used in almost all existing cryptographic protocols and
secure against the known attacks, because the protocol itself prohibits the
attacking preconditions.

 SHA-2 is the current standard for those applications

It's not known, if SHA-2 will suffer from the same attack principle or not.
If you really consider the current known attacks against SHA-1 as important,
you have to leave the whole family an choose i.e. RIPEMD-160.

 On the other hand, why does darcs need a cryptographically secure
 hash function at all?  Wouldn't MD5 or a sufficiently wide CRC, such
 as the one used in ZFS [2], do just as well?  They would certainly be
 a lot faster to compute.

SHA-1 is the current standard for quick and dirty checksumming an new
applications. Using MD5 or any CRC is only for software acheologists.

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


Re: [Haskell-cafe] Field updates in a state monad

2008-01-10 Thread Lutz Donnerhacke
* Michael Roth wrote:
 Exists there a way to write this cleaner without writing countless
 set_xyz helper functions?

The syntactic sugar for record modifications is simply that: sugar.
You might write your own modifier functions:
  set_bla x y = x { bla = y }
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Show instances for error messages (Was: Refactoring status)

2008-01-07 Thread Lutz Donnerhacke
* Henning Thielemann wrote:
 happen. Paradoxical. It would be interesting if it is possible to tunnel
 Show class dictionaries through to an 'error' like IO is tunneled to
 'trace'.

unsafeShow :: (forall a . Show a = a) - String
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell-cafe reply-to etiquette

2007-12-27 Thread Lutz Donnerhacke
* Justin Bailey wrote:
 When I joined the haskell-cafe mailing list, I was surprised to see
 the reply-to header on each message was set to the sender of a given
 message to the list, rather than the list itself.

That's good practice.

 That seemed counter to other mailing lists I had been subscribed to, but
 I didn't think too much about it.

Please search for Reply-To considered harmful and send this text to the
admins of the other lists. The discussion is older than Google.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: DSL question -- was: New slogan for haskell.org

2007-12-26 Thread Lutz Donnerhacke
* Steve Lihn wrote:
 Thanks for the example. I am particularly amazed GHC is complaining at
 '/', not '+'. The type mismatch occurs (is reported) at much lower
 level. It would be nice if there is a way to bump it up a couple
 levels...

Add type signatures for mu and dont_try_this.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell performance

2007-12-20 Thread Lutz Donnerhacke
* Simon Peyton-Jones wrote:
 Does anyone feel like doing this?  It'd be a great service.  No need to
 know anything much about GHC.

I'd like to do that. For a lecture I'm already generated performance tests
for various sorting algorithms.

It's designed about a function performance :: Size - IO RunsPerSecond.
So with unsafePerformIO it is a good candidate for quickCheck.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell performance

2007-12-20 Thread Lutz Donnerhacke
* Malcolm Wallace wrote:
 Something along these lines already exists - the nobench suite.

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


Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-18 Thread Lutz Donnerhacke
* Tillmann Rendel wrote:
 My conclusion: To make Haskell a better OO language

Haskell is not an OO language and never should be.

 (Since it's not the goal of Haskell to be any OO language at all this
 may not be a problem)

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


Re: [Haskell-cafe] type classes

2007-12-14 Thread Lutz Donnerhacke
* Peter Padawitz wrote:
 I'd like to define several instances of the same type class with the
 same type variable instance. Only method instances differ. How can I do
 this without writing copies of the type class?

Define the type class in a module named MyClass. Define the each instance
in a module named MyInstanceX where X is a version number.

Include only the MyInstanceX module, you currently need.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] St. Petersburg Game

2007-11-27 Thread Lutz Donnerhacke
* [EMAIL PROTECTED] wrote:
 I'm trying to program an implementation of the St. Petersburg game in
 Haskell. There is a coin toss implied, and the random-number generation is
 driving me quite mad. So far, I've tried this:

 import Random

import System.Random  -- time goes on, interfaces change

 increment :: Int - Int
 increment b = b + 1


 main =  dolet b = 0
   let c = randomRIO (1,2)
   until (c == 1)  increment b
   return b

In Haskell you take it the other side around:
  - Given a random number generator
System.Random.newStdGen :: IO StdGen

  - you generate an infinite list of coin flip results
System.Random.randoms  :: (RandomGen g) =  g - [a]
System.Random.randomRs :: (RandomGen g) = (a,a) - g - [a]
  
  - you are interested in the the first elements of a given value
takeWhile :: (a - Bool) - [a] - [a]
  
  - and need to compute the length of this list
length :: [a] - Int
  

To model the result of a coin flip, you need two possible values.
Your choice [1,2] is possible, but the boolean values are much easier.
Let's choose True for number up and False otherwise.

Put it together:

main :: IO ()
main = do
  rnd - newStdGen
  let result = computeResult rnd
  print result

computeResult :: (RandomGen g) = g - Int
computeResult = length . takeWhile not . randoms

Or in short:

main = print . length . takeWhile not . randoms = newStdGen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Learning hierarchy

2007-10-23 Thread Lutz Donnerhacke
Hi,

in order to upload my teaching programms to hackage, I look for an accepted
hierarchy to put the modules into.

My current version is Learning.Donnerhacke.Algorithms.Sort ... etc. pp.
Would such a hierarchy make sense? Is the a hope for inclusion of other
modules?

The main purpose of this moduls in my special case are: Implementation of
the algorithms from Sedgewick's famous book. They are combined with a ver
short program
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Learning hierarchy

2007-10-23 Thread Lutz Donnerhacke
* Lutz Donnerhacke wrote:
 The main purpose of this moduls in my special case are: Implementation of
 the algorithms from Sedgewick's famous book. ...

Sorry, I hit the send button a bit too early.

... They are used with very small main programms containing a FFI inclusion
of a external C object and a main calling Test.QuickCheck between the C
function and the library function (from Learning...).

This way the studends are teached to learn C. The Makefile compiles the C
code to a object file and links it with the main programm to generate test
cases for their work.

A secondary function is exported via FFI to display the used data structures
at the C level in an additional X11 window. This is offered to ease
debugging of their programms.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Lutz Donnerhacke
* Simon Marlow wrote:
 further sub-versions may be added after the x.y, their meaning is
 package-defined.  Ordering on versions is lexicographic, given multiple 
 versions that satisfy a dependency Cabal will pick the latest.

x.y.z should be ordered numerically, if possible.

 As suggested by various people in this thread: we change the convention so 
 that dependencies must specify a single x.y API version, or a range of 
 versions with an upper bound.  Cabal or Hackage can refuse to accept 
 packages that don't follow this convention (perhaps Hackage is a better 
 place to enforce it, and Cabal should just warn, I'm not sure).

Ack. Hackage is a good place to reject.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Is take behaving correctly?

2007-09-13 Thread Lutz Donnerhacke
* Neil Mitchell wrote:
 There are 4 variants of tail:

 tail :: [a] - [a] -- normal
 tailDef :: [a] - [a] - [a] -- returns the first argument on []
 tailMay :: [a] - Maybe [a] -- returns a Nothing
 tailNote :: String - [a] - [a] -- crashes, but with a helpful message
 tailSafe :: [a] - [a] -- returns [] on []

From the logical point of view tailMay is the right one.
It pushes the error handling to the caller programm.

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


Re: [Haskell-cafe] Re: Data.Binary Endianness

2007-09-11 Thread Lutz Donnerhacke
* apfelmus wrote:
 It's not that related, but I just got struck by an obvious idea, namely
 to put the endianness in an extra parameter

data Endianness = Little | Big | Host
putInt32 :: Endianness - Int - Put

Please add the endianess to the state of the monad Put.
  setendianess :: Endianness - Put

And for convinience please add the Network constructor to the type
Endianness. ,-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsing binary data.

2007-08-22 Thread Lutz Donnerhacke
* Tony Finch wrote:
 http://erlang.org/doc/programming_examples/bit_syntax.html#4
 The IP header example in the latter is a brilliant real-world example.

Unfortunly this example does not handle bit and byte order.
Take a look at Ada's representation clauses for such topics.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Slow IO or bad code?

2007-08-09 Thread Lutz Donnerhacke
* Vimal wrote:
 Beginning of CODE
 loop t function
  | t == 1 = do function
  | otherwise = do { function; loop (t - 1) function }

 prod [] [] = 0
 prod (a:as) (b:bs) = a*b + prod as bs

prod = sum . zipWith (*)

 to_int :: [String] - [Integer]
 to_int [] = []
 to_int (x:xs) = (read x) : to_int xs

This is the slow part. Prelude.read ist really slow.

Futhermore use the recusion pattern again:
to_int = map read

 doit = do
   n - getLine
   a - getLine
   b - getLine
   let la = to_int (words a);
   lb = to_int (words b); in
 print (prod la lb)

What is n used for?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Lutz Donnerhacke
* Bulat Ziganshin wrote:
 Hello apfelmus,
 I still think that this syntax extension has profound impact and is a
 bad idea.

 can you please rewrite *p++=*q++ in haskell?

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


Re: [Haskell-cafe] Definition of the Haskell standard library

2007-07-31 Thread Lutz Donnerhacke
* Simon Peyton-Jones wrote:
 Then, in effect, the standard library is all the X packages.  I wonder
 if it'd help to have some descriptions such as those above (better
 worded), and use them?  Cabal already has a stability indication, and
 that might serve, but we'd want to articulate much more clearly what it
 meant.

You need an external indicator, not an indicator from the package author.
It might be interesting to transform the dependency graph of cabalized
packaged at hackage into a ranking indicator.
It's like the Google Pagerank: Same benefit, same illness.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Maintaining the community

2007-07-13 Thread Lutz Donnerhacke
* Malcolm Wallace wrote:
 If anything, Usenet is even worse than mailing lists for volume,
 especially of spam.  Also, very few sites maintain their nntp servers
 adequately these days - e.g.  comp.lang.haskell has never made it to
 where I work.

I beg to differ. Of course, I'm an Usenet admin and involved in Usenet
administration since years.

Saing no Usenet is usually a sign of the famous not invented here
syndrom. I'd sugest to keep the 30+ years experience with large volume
distributed mass communication, instead of throwing good and infrastructure
and user interfaces away.

Wikis, Webformus and a lot of other Web 2.0 hypes are doomed to redo every
mistake which is solved since 20+ years.

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


Re: [Haskell-cafe] Maintaining the community

2007-07-13 Thread Lutz Donnerhacke
* Magnus Therning wrote:
 One obvious solution is to split the list into several, more specialised
 lists.  It's far from obvious, at least to me, how to do that with this
 list though.

Switch to Usenet. The new haskell group will die, if the traffic will not
increase.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Updated urlcheck

2007-06-14 Thread Lutz Donnerhacke
I'm proud to announce an updated version of dons' concurrent urlcheck.

It's a bad and buggy rewrite from scratch. It can check a file of urls or
the consistency of the transitive hull of a website incl. the existance of
the border urls. Futhermore the warnings from TagSoup parsing can be
reported.

Main bugs are memory leaks in conjunction with unnecessary retrieval of
binary files, and missing documentation.
If somebody has enough time in the next weeks: Many thanks in advance.

URL: http://www.iks-jena.de/mitarb/lutz/haskell/urlcheck-0.0.tar.gz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] (pre)compiled Haskell compiler for True64/Alpha

2007-06-06 Thread Lutz Donnerhacke
Does anyone have a haskell compiler for True64 (formerly known as OSF/1) on
Alpha hardware?

I'm currently unable to compile the first bootstrap compiler.
Any hint which compiler should I start with?

I'll send detailed error reports only if I do not succeed in the next hours.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] (pre)compiled Haskell compiler for True64/Alpha

2007-06-06 Thread Lutz Donnerhacke
On Wed, Jun 06, 2007 at 10:00:15PM +1000, Donald Bruce Stewart wrote:
 I think the last ghc I ran on OSF/1 alpha was hmm, 5.04.2?

Yep. I found that, because it was heavily described. There were quite a
number of bugs with 64bit code. This are the same problems I have with nhc
or hugs (sizeof (void*) != sizeof int). Hugs simply crashes while nhc does
not compile (yet).

 You might be able to get a newer one working though. The 6.x series is
 fairly easy to bootstrap (there's alpha/debian for example), so if you
 run into problems, let glasgow-haskell-users@ know.

Thank you. I do not have Linux, so a Debian packet does not help that much.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: wanted: haskell one-liners (in the perl sense of one-liners)

2007-03-20 Thread Lutz Donnerhacke
* Thomas Hartman wrote:
 You contributed

 #12:14  Thunder @pl s - drop (length s - n) s
 #12:14  lambdabot drop = subtract n . length

 But, on second thought, 1) I can't use this as a drop-in replacement
 for the non points free (right term?) version, and 2) I don't really
 understand it.

I did not contribute, but polluted the channel with my own test.

In order to understand this construct you have to switch to the (- a) Monad:

 drop = subtract n . length

==   do x - subtract n . length
drop x

This construct consists of partially applied functions, i.e. functions
waiting for an argument.

If you apply an argument to the whole construct, it is applied to each line
seperatly.

So  drop = subtract n . length $ s becomes:

 let x = subtract n . length $ s
 in  drop x s

==

 let x = length s - n
 in  drop x s

==
 drop (length s - n) s


I did not expect this monadic approach from lambdabot and was somewhat
surprised. I assumed an application of liftM2 drop instead.

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