Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Fraser Wilson
On Tue, Jan 12, 2010 at 11:26 PM, Daniel Fischer
daniel.is.fisc...@web.dewrote:

 Okay, 'as' is easy. But can you find a situation where 'qualified' or
 'hiding' would be natural choices for an identifier? I'd love to see those
 in some code :)


module LordsOfMidnight.Character(Character) where

data Character = C { name :: String,
 location :: (Int,Int),
 facing   :: Direction,
 hour :: Int,
 energy   :: Int,
 fear :: Int,
 riders   :: Int,
 soldiers :: Int,
 hiding   :: Bool
   }
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Martin Coxall

On 12 Jan 2010, at 21:25, Andrew Coppin wrote:

 OK people, it's random statistics time!
 
 Haskell '98 apparently features 25 reserved words. (Not counting forall and 
 mdo and so on, which AFAIK are not in Haskell '98.) So how does that 
 compare to other languages?
 
 C: 32
 C++: 62
 Borland Turbo Pascal: ~50 [without the OOP extensions added later]
 Eiffel: 59
 VB: The source I checked listed in excess of 120 reserved words, but I'm 
 dubious as to how reserved they really are. (Is CInt really reserved? I 
 doubt it!) It also depends wildly on which of the bazillion VB dialects you 
 mean.
 Java: 50
 JavaScript: 36
 Smalltalk: 0

There are six singleton pseudo-variables that act as reserved words: 
true,false, nil, self, super and thisContext.

 Lisp: AFAIK, there are no truly reserved words in Lisp, only predefined 
 functions. (??)

All Lisps have special forms which are evaluated uniquely and differently 
from function application and are therefore reserved words by another name. For 
example, Clojure has def, if, do, let, var, quote, fn, loop, recur, throw, try, 
monitor-enter, monitor-exit, dot, new and set!.

 Python: 31
 Ruby: 38
 Tcl: Same analysis as for Lisp I believe.

COBOL: Over 400 (!)

 
 As you can see, this conclusively proves... something.

Generally speaking, the most widely used languages seem to be near the upper 
end of the range.

I don't think it really tells you that much. Possibly that a little superficial 
complexity through syntactic sugar can make your language a lot more 
human-friendly, but that it's possible to go too far and end up like C++.

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


Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Martin Coxall

On 12 Jan 2010, at 22:22, Andrew Coppin wrote:

 Niklas Broberg wrote:
 Haskell '98 apparently features 25 reserved words. (Not counting forall
 and mdo and so on, which AFAIK are not in Haskell '98.)

 
 21 actually. case, class, data, default, deriving, do, else, if,
 import, in, infix, infixl, infixr, instance, let, module, newtype, of,
 then, type, where. There's also three special words that can still be
 used as identifiers, so aren't reserved: as, qualified, hiding.
  
 
 OK. Well the list I saw was for Haskell plus extensions, and I visually 
 filtered out the inapplicable stuff. Apparently I missed something.
 
 Also, the number varies depending on whether you consider reversed words or 
 keywords, 

Aye, there's a subtle distinction between keywords and reserved words, but I 
think for the purposes of this discussion, they're the same thing.

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


Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Marc Weber
 As you can see, this conclusively proves... something.

What about brainfuck? 8 different signs are used.
- http://de.wikipedia.org/wiki/Brainfuck#cite_note-0

The first link points to a page saying there is an interpreter 98 bytes
in size..

What does this prove? :-)

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


[Haskell-cafe] Re: FASTER primes

2010-01-13 Thread Heinrich Apfelmus
Daniel Fischer wrote:
 Heinrich Apfelmus wrote:

 It is exactly because these troubles that I'm advocating the original
 VIP data structure that buries the dorks (that name is awesome :D) deep
 inside the structure. :)

In fact, your transformation that fixes the space leaks pretty much
emulates the behavior of the old

   data People a = VIP a (People a) | Dorks [a]

structure. This becomes apparent if we put the last two arguments of
spMerge  back into a pair:

   mergeSP (P a b) ~(P c d) =
  let P bc m = spMerge b (P c d) in P (a ++ bc) m
  where
  spMerge b  (P [] d)   = P [] (merge b d)
  spMerge xs@(x:xt) cd@(P (y:yt) d) = case compare x y of
LT - celebrate x (spMerge xt cd  )
EQ - celebrate x (spMerge xt (P yt d))
GT - celebrate y (spMerge xs (P yt d))

In particular, forcing  dorks (mergeSP ...)  also forces the complete
VIP list.

I wonder whether it's really the liveness of  pair  in

  mergeSP (a,b) pair
 = let sm = spMerge b (fst pair)
   in (a ++ fst sm, merge (snd sm) (snd pair))

that is responsible for the space leak, for chances are that Sparud's
technique applies and  pair  is properly disposed of. Rather, it could
be that we need the stronger property that forcing the second component
will evaluate the first to NF.


 In any case, it appears to me that the lazy pattern match in  mergeSP
 is actually unnecessary! This is because  mergeSP  returns a pair
 constructor immediately, so infinite nesting works even when the second
 argument is demanded. [...]

 No, loop. For the reason you stated below.
 In
 
 tfold f (a:b:c:xs) = (a `f` (b `f` c)) `f` smartfold f xs
 
 , it must compute smartfold f xs too early to match it against P c d. The 
 compiler can't see that smartfold mergeSP always returns a P [well, it 
 might return _|_, mightn't it?].

Oops, silly me! Mea culpa, of course  mergeSP a (mergeSP b (mergeSP c
..))) or any infinite nesting is not going to work with a strict
pattern. _ _


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] QuickCheck: test passes in GHCi, fails when compiled

2010-01-13 Thread Lauri Pesonen
I provided a Java solution to a problem of returning the first digit
of an integer on StackOverflow and someone wondered if there were any
floating point point problems with the solution, so I though I'd
implement the algorithm in Haskell and run QuickCheck on it.
Everything works fine on GHCi, but if I compile the code and run the
test, it fails with -1000, 1000, -100. Any ideas why?

In any case it seems that the commenter was right and there are some
subtle problems with my solution. I'd just like to know more
details...

import Data.Char
import Test.QuickCheck

-- my solution
getFirstDigit :: Int - Int
getFirstDigit 0 = 0
getFirstDigit x = let x' = abs x
  digits = (floor $ logBase 10 $ fromIntegral x')
  in x' `div` (floor $ 10 ** (fromIntegral digits))

-- two reference implementation that agree with each other
getFirstDigitRef1 :: Int - Int
getFirstDigitRef1 x = digitToInt $ head $ show $ abs x

getFirstDigitRef2 :: Int - Int
getFirstDigitRef2 x | x  0 = getFirstDigitRef2 (-x)
| x  10 = x
| otherwise = getFirstDigitRef2 $ x `div` 10

myTest x = getFirstDigit x == getFirstDigitRef1 x
--myTest x = getFirstDigitRef2 x == getFirstDigitRef1 x

myCheck n = check (defaultConfig { configMaxTest = n }) myTest

main = myCheck 10

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


Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Ketil Malde
sylvain sylvain.na...@googlemail.com writes:

 Let me order your list:

 Smalltalk: 0  
 Lisp: 0
 Tcl: 0

If you count reserved tokens, I guess Lisp reserves parentheses and
whitespace? 

 Haskell: 21 *
 Python: 31
 C: 32 *
 JavaScript: 36
 Ruby: 38
 ---
 Borland Turbo Pascal: ~50
 Java: 53
 Eiffel: 59
 C++: 62

 Interestingly enough, interpreted languages tend to need less keywords,
 which support my observation above. 

I can't help but notice that the top three are untyped (all right,
dynamically typed) languages.  Static typing seems to require at least
a few reserved words (does it make sense to redefine 'data' or 'type' in
Haskell?)

 But if you really wanted to compare apples to apples you would, for
 instance, add GHC pragmas and magic things like `par` to the mix. I
 wonder if the picture would change much?

Looking for a minimal subset that everything else can be implemented in
terms of?  Still, having 'par' as a user redefinable token lets you
replace it with your own implementation (par = seq, for instance :-).
So I think there's a benefit, even if it is normally implemented using
magic.

-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


Re: [Haskell-cafe] How to fulfill the code-reuse destiny of OOP?

2010-01-13 Thread Peter Verswyvelen
On Sun, Nov 1, 2009 at 2:57 AM, Gregory Collins g...@gregorycollins.netwrote:

 Doing OO-style programming in Haskell is difficult and unnatural, it's
 true (although technically speaking it is possible). That said, nobody's
 yet to present a convincing argument to me why Java gets a free pass for
 lacking closures and typeclasses.


I might be wrong, but doesn't Java's concepts of inner classes and
interfaces together with adapter classes can be used to replace closures and
typeclasses in a way?

An inner class allows you to implicitly capture the parent object
(environment), just like a closure does in a sense.

Interfaces group together methods, like type classes do.

Although I'm actually a C# fanboy for doing industrial programming, I
think the Java designers did an excellent job, finding a good balance in
language features, ease of use and readability, and although C# does offer
closures and many more FP constructs, I really miss the above Java
constructs.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to fulfill the code-reuse destiny of OOP?

2010-01-13 Thread Martin Coxall

On 13 Jan 2010, at 09:51, Peter Verswyvelen wrote:

 On Sun, Nov 1, 2009 at 2:57 AM, Gregory Collins g...@gregorycollins.net 
 wrote:
 Doing OO-style programming in Haskell is difficult and unnatural, it's
 true (although technically speaking it is possible). That said, nobody's
 yet to present a convincing argument to me why Java gets a free pass for
 lacking closures and typeclasses.
 
 I might be wrong, but doesn't Java's concepts of inner classes and interfaces 
 together with adapter classes can be used to replace closures and typeclasses 
 in a way?

Inner classes are not a semantic replacement for closures, even if you discount 
horrific syntax. Inner classes do not close over their lexical environment.

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


[Haskell-cafe] Type Inference for Overloading without Restrictions

2010-01-13 Thread Peter Verswyvelen
A while ago, someone provided me a link to the paper Type Inference
for Overloading without Restrictions
http://www.dcc.ufmg.br/~camarao/ct-flops99.ps.gz

Although I don't understand everything in this paper, I wander what
people's opinions are about this regarding a future Haskell language
revision or extension?

Would a feature like this be preferable over typeclasses? Would it be
practical to implement? Are people working on this?

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


RE: [Haskell-cafe] How to fulfill the code-reuse destiny of OOP?

2010-01-13 Thread Sittampalam, Ganesh
The problem with interfaces as a replacement for type classes is that
they only provide dispatch based on the specific type of the first
argument (i.e. the receiver).
 
Type classes allow you to dispatch based on return type, and on the
instantiations of generic parameters. Neither of these things is
reasonably possible with interfaces.
 
For example you can't directly implement the Read type class with
interfaces. Neither can you implement a function of type [a] - ...
where the dispatch is based on the instantiation of a - even if you can
add an interface to the [] generic type, you might not have a concrete
object of type a to dispatch from if the empty list is passed as an
argument.
 



From: haskell-cafe-boun...@haskell.org
[mailto:haskell-cafe-boun...@haskell.org] On Behalf Of Peter Verswyvelen
Sent: 13 January 2010 09:52
To: Gregory Collins
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] How to fulfill the code-reuse destiny of
OOP?


On Sun, Nov 1, 2009 at 2:57 AM, Gregory Collins
g...@gregorycollins.net wrote:


Doing OO-style programming in Haskell is difficult and
unnatural, it's
true (although technically speaking it is possible). That said,
nobody's
yet to present a convincing argument to me why Java gets a free
pass for
lacking closures and typeclasses.



I might be wrong, but doesn't Java's concepts of inner classes and
interfaces together with adapter classes can be used to replace closures
and typeclasses in a way?

An inner class allows you to implicitly capture the parent object
(environment), just like a closure does in a sense.

Interfaces group together methods, like type classes do. 

Although I'm actually a C# fanboy for doing industrial programming, I
think the Java designers did an excellent job, finding a good balance in
language features, ease of use and readability, and although C# does
offer closures and many more FP constructs, I really miss the above Java
constructs.



=== 
 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] Re: QuickCheck: test passes in GHCi, fails when compiled

2010-01-13 Thread Lauri Pesonen
2010/1/13 Lauri Pesonen lauri.peso...@iki.fi:
 I provided a Java solution to a problem of returning the first digit
 of an integer on StackOverflow and someone wondered if there were any
 floating point point problems with the solution, so I though I'd
 implement the algorithm in Haskell and run QuickCheck on it.
 Everything works fine on GHCi, but if I compile the code and run the
 test, it fails with -1000, 1000, -100. Any ideas why?

 In any case it seems that the commenter was right and there are some
 subtle problems with my solution. I'd just like to know more
 details...

Ok, I've figured out why the compiled version fails the check:

main = putStrLn $ show $ logBase 10 1000

when compiled returns 2.9996 on my system (WinXp 32-bit)
which then gets truncated to 2.

So it seems that there's a precision difference between the compiled
and the interpreted code.

'logBase 10 999' on the other hand produces exactly the same value in
both cases.

I expect this to be a known issue with floats. Sorry for the noise.

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


Re: [Haskell-cafe] How to fulfill the code-reuse destiny of OOP?

2010-01-13 Thread Sebastian Fischer


On Jan 13, 2010, at 11:00 AM, Sittampalam, Ganesh wrote:

Type classes allow you to dispatch based on return type, and on the  
instantiations of generic parameters. Neither of these things is  
reasonably possible with interfaces.


There is recent work that generalises the capabilities of interfaces  
in Java:



http://www.informatik.uni-freiburg.de/~wehr/publications/WehrLammelThiemann2007.html

http://www.informatik.uni-freiburg.de/~wehr/publications/WehrThiemann2009.html
http://www.informatik.uni-freiburg.de/~wehr/publications/Wehr2009.html

Seeing type-class features in Java disguise highlights the differences  
between the two concepts that you mention.


Sebastian


--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



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


Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Brandon S. Allbery KF8NH

On Jan 13, 2010, at 03:49 , Martin Coxall wrote:

COBOL: Over 400 (!)



If we're going to go that far, FORTRAN and PL/1 have none.  FORTRAN is  
somewhat infamous for this:  DO 10 I = 1, 400 is a loop start, DO  
10 I = 1. 400 (note typo, . for ,) parses as the assignment  
DO10I = 1.400.  (This is often cited as the cause of the failure of  
Mariner 1, but that's an urban legend.  See http://catless.ncl.ac.uk/Risks/9.54.html#subj1.1 
 for discussion, including the possible origin of this UL.)


--
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 universityKF8NH




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


Re: [Haskell-cafe] How to fulfill the code-reuse destiny of OOP?

2010-01-13 Thread Peter Verswyvelen
Yes that is true, but often in Haskell I had to use type annotations
when the dispatch is based on the return type, so it also has some
tradeoffs.

Don't get me wrong, I see the advantages of Haskell's type classes and
closures, and I love these. But in Java - if you stay close to OO, and
don't try to do FP - you can accomplish a lot, albeit with a lot of
boilerplate. IMO, it's not because you have less lines of code in
Haskell, that the code becomes more readable per se. I'm not a Java
expert, but I have no troubles at all reading Java code, even though
that code is typically twice as long as similar C# code, and maybe ten
times as long as Haskell or ML code (at least if the side effects are
kept local enough, which is good practice in OO anyway). But after
many years of playing with Haskell, I still fail to read and
understand a lot of Haskell code (maybe because it is written by
people with a much higher IQ than mine I guess)

On Wed, Jan 13, 2010 at 11:00 AM, Sittampalam, Ganesh
ganesh.sittampa...@credit-suisse.com wrote:
 The problem with interfaces as a replacement for type classes is that they
 only provide dispatch based on the specific type of the first argument (i.e.
 the receiver).

 Type classes allow you to dispatch based on return type, and on the
 instantiations of generic parameters. Neither of these things is reasonably
 possible with interfaces.

 For example you can't directly implement the Read type class with
 interfaces. Neither can you implement a function of type [a] - ... where
 the dispatch is based on the instantiation of a - even if you can add an
 interface to the [] generic type, you might not have a concrete object of
 type a to dispatch from if the empty list is passed as an argument.

 
 From: haskell-cafe-boun...@haskell.org
 [mailto:haskell-cafe-boun...@haskell.org] On Behalf Of Peter Verswyvelen
 Sent: 13 January 2010 09:52
 To: Gregory Collins
 Cc: haskell-cafe@haskell.org
 Subject: Re: [Haskell-cafe] How to fulfill the code-reuse destiny of OOP?

 On Sun, Nov 1, 2009 at 2:57 AM, Gregory Collins g...@gregorycollins.net
 wrote:

 Doing OO-style programming in Haskell is difficult and unnatural, it's
 true (although technically speaking it is possible). That said, nobody's
 yet to present a convincing argument to me why Java gets a free pass for
 lacking closures and typeclasses.

 I might be wrong, but doesn't Java's concepts of inner classes and
 interfaces together with adapter classes can be used to replace closures and
 typeclasses in a way?
 An inner class allows you to implicitly capture the parent object
 (environment), just like a closure does in a sense.
 Interfaces group together methods, like type classes do.
 Although I'm actually a C# fanboy for doing industrial programming, I
 think the Java designers did an excellent job, finding a good balance in
 language features, ease of use and readability, and although C# does offer
 closures and many more FP constructs, I really miss the above Java
 constructs.


 ==
 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


Re: [Haskell-cafe] Re: QuickCheck: test passes in GHCi, fails when compiled

2010-01-13 Thread Brandon S. Allbery KF8NH

On Jan 13, 2010, at 05:07 , Lauri Pesonen wrote:

I expect this to be a known issue with floats. Sorry for the noise.



Yep.  There's a faction that wants Float and Double to not be in the  
Eq typeclass, because floating point calculations can never reliably  
be compared for equality.  (There are some infinite precision float  
packages out there, but transcendentals will still get you in trouble  
even if repeating decimals don't.)


--
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 universityKF8NH




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


Re: [Haskell-cafe] FFI, C/C++ and undefined references

2010-01-13 Thread Malcolm Wallace
But when I try to compile it (after having successfully compiled the  
C code

with g++), I get:

$ ghc --make Main.hs


You are not telling ghc to link against the C/C++ code,  e.g.
ghc --make Main.hs srilm.o

Regards,
Malcolm

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


Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Ketil Malde
Fraser Wilson blancoli...@gmail.com writes:

 module LordsOfMidnight.Character(Character) where

 data Character = C { name :: String,
  location :: (Int,Int),
  facing   :: Direction,
  hour :: Int,
  energy   :: Int,
  fear :: Int,
  riders   :: Int,
  soldiers :: Int,
  hiding   :: Bool
}

Daniel Fisher thinks again...

(With apologies for the rather obscure reference.)

-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


Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Ketil Malde
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.  :-)

-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


Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Brandon S. Allbery KF8NH

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 universityKF8NH




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


Re: [Haskell-cafe] wildcards for type variables?

2010-01-13 Thread David Virebayre
On Wed, Jan 13, 2010 at 12:29 AM, Evan Laforge qdun...@gmail.com wrote:
 Occasionally I have a function with an unused argument, whose type I
 don't want to restrict.  Thus:

 f :: _unused - A - B
 f _ a = b

I probably misunderstood the problem, why not f:: a - A - B

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


Re: [Haskell-cafe] wildcards for type variables?

2010-01-13 Thread Brandon S. Allbery KF8NH

On Jan 13, 2010, at 05:54 , David Virebayre wrote:
On Wed, Jan 13, 2010 at 12:29 AM, Evan Laforge qdun...@gmail.com  
wrote:

Occasionally I have a function with an unused argument, whose type I
don't want to restrict.  Thus:

f :: _unused - A - B
f _ a = b


I probably misunderstood the problem, why not f:: a - A - B



He's looking for the self-documentation aspect of this argument is  
completely irrelevant.  Neither rolling a random unused type variable  
nor foralling it (my first idea) really accomplishes that.


--
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 universityKF8NH




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


Re: [Haskell-cafe] FFI, C/C++ and undefined references

2010-01-13 Thread Bulat Ziganshin
Hello DNM,

Wednesday, January 13, 2010, 8:57:45 AM, you wrote:

 Note: I'm relatively new to Haskell, and my knowledge of C and C++ is
 basically pretty
 minimal -- I can read, modify and compile C/C++ programs (usually).

1. you use too much unsafePerformIO. since you need newCString, i
suggest you to declare C functions as returning IO a so your code
will be

unsafePerformIO$ do
  withCString str $ \c_str - do
  c_function c_str ...

2. if your function returns Ptr a - then hold in haskell types this Ptr a.
no need to convert it back and forth to ForeignPtr

3. why c_dlm is FunPtr in your definition? it should be

foreign import ccall srilm.h deleteLM
c_dlm :: Ptr Ngram - IO ()

4. i don't looked in your code but if C functions defines
*modifiable* datastructure - you should use it at Haskell side via
imperatiove functions, i.e. those with return type IO a. using
unsafePerformIO in this case will lead to Haskell compiler will
consider this datatype as permanent and reorder operations on the will

so,

 data NGModel = NGModel {ng :: !(Ptr Ngram)}

 foreign import ccall srilm.h bldLM
 c_blm :: CInt - CString - IO (Ptr Ngram)

 foreign import ccall srilm.h deleteLM
 c_dlm :: Ptr Ngram - IO ()

 foreign import ccall srilm.h getSeqProb 
 c_ngramProb :: Ptr Ngram - CString - CUInt - CUInt - IO CFloat

 scoreSequence :: NGModel - Int - [String] - IO Float
 scoreSequence ngram order seq = do
   withCString (unwords seq) $ \stringSeq - do
   sc - c_ngramProb (ng ngram) stringSeq (fromIntegral order) 
 (fromIntegral $ length seq)
   return (realToFrac sc)

and so on



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Re: FASTER primes

2010-01-13 Thread Daniel Fischer
Am Mittwoch 13 Januar 2010 10:43:42 schrieb Heinrich Apfelmus:
 I wonder whether it's really the liveness of  pair  in

   mergeSP (a,b) pair
      = let sm = spMerge b (fst pair)
        in (a ++ fst sm, merge (snd sm) (snd pair))

 that is responsible for the space leak, for chances are that Sparud's
 technique applies and  pair  is properly disposed of. Rather, it could
 be that we need the stronger property that forcing the second component
 will evaluate the first to NF.

I think that is responsible. At least that's how I understand the core:

mergeSP (a,b) ~(c,d) = (a ++ bc, merge b' d)
   where
  (bc, b') = spMerge b c
  spMerge ...
--
OldMerge.$wmergeSP :: [GHC.Types.Int]
  - [GHC.Types.Int]
  - ([GHC.Types.Int], [GHC.Types.Int])
  - (# [GHC.Types.Int], [GHC.Types.Int] #)
GblId
[Arity 3
 Str: DmdType LLL]
OldMerge.$wmergeSP =
  \ (ww_sny :: [GHC.Types.Int])
(ww1_snz :: [GHC.Types.Int])
(w_snB :: ([GHC.Types.Int], [GHC.Types.Int])) -
let {
  ds_so7 [ALWAYS Just D(SS)] :: ([GHC.Types.Int], [GHC.Types.Int])
  LclId
  [Str: DmdType]
  ds_so7 =
case w_snB of _ { (c_adj, _) -
case OldMerge.$wspMerge ww1_snz c_adj
of _ { (# ww3_snH, ww4_snI #) -
(ww3_snH, ww4_snI)
}
} } in
(# GHC.Base.++
 @ GHC.Types.Int
 ww_sny
 (case ds_so7 of _ { (bc_ajQ, _) - bc_ajQ }),
   case ds_so7 of _ { (_, b'_ajS) -
   case w_snB of _ { (_, d_adk) - OldMerge.merge b'_ajS d_adk }

-- Here, in the second component of the result,
-- we reference the entire pair to get the dorks

   } #)

OldMerge.mergeSP :: ([GHC.Types.Int], [GHC.Types.Int])
- ([GHC.Types.Int], [GHC.Types.Int])
- ([GHC.Types.Int], [GHC.Types.Int])
GblId
[Arity 2
 Worker OldMerge.$wmergeSP
 Str: DmdType U(LL)Lm]
OldMerge.mergeSP =
  __inline_me (\ (w_snw :: ([GHC.Types.Int], [GHC.Types.Int]))
 (w1_snB :: ([GHC.Types.Int], [GHC.Types.Int])) -
 case w_snw of _ { (ww_sny, ww1_snz) -
 case OldMerge.$wmergeSP ww_sny ww1_snz w1_snB
 of _ { (# ww3_snN, ww4_snO #) -
 (ww3_snN, ww4_snO)
 }
 })
--

vs.

mergeSP (a,b) ~(c,d) = (a ++ bc, m)
   where
  (bc,m) = spMerge b c d
  spMerge ...
--
NewMerge.$wmergeSP :: [GHC.Types.Int]
  - [GHC.Types.Int]
  - ([GHC.Types.Int], [GHC.Types.Int])
  - (# [GHC.Types.Int], [GHC.Types.Int] #)
GblId
[Arity 3
 Str: DmdType LLL]
NewMerge.$wmergeSP =
  \ (ww_snB :: [GHC.Types.Int])
(ww1_snC :: [GHC.Types.Int])
(w_snE :: ([GHC.Types.Int], [GHC.Types.Int])) -
let {
  ds_soa [ALWAYS Just D(SS)] :: ([GHC.Types.Int], [GHC.Types.Int])
  LclId
  [Str: DmdType]
  ds_soa =
case w_snE of _ { (c_adj, d_adk) -

  -- There's no reference to the pair after this

case NewMerge.$wspMerge ww1_snC c_adj d_adk
of _ { (# ww3_snK, ww4_snL #) -
(ww3_snK, ww4_snL)
}
} } in
(# GHC.Base.++
 @ GHC.Types.Int
 ww_snB
 (case ds_soa of _ { (bc_ajT, _) - bc_ajT }),
   case ds_soa of _ { (_, b'_ajV) - b'_ajV } #)

NewMerge.mergeSP :: ([GHC.Types.Int], [GHC.Types.Int])
- ([GHC.Types.Int], [GHC.Types.Int])
- ([GHC.Types.Int], [GHC.Types.Int])
GblId
[Arity 2
 Worker NewMerge.$wmergeSP
 Str: DmdType U(LL)Lm]
NewMerge.mergeSP =
  __inline_me (\ (w_snz :: ([GHC.Types.Int], [GHC.Types.Int]))
 (w1_snE :: ([GHC.Types.Int], [GHC.Types.Int])) -
 case w_snz of _ { (ww_snB, ww1_snC) -
 case NewMerge.$wmergeSP ww_snB ww1_snC w1_snE
 of _ { (# ww3_snQ, ww4_snR #) -
 (ww3_snQ, ww4_snR)
 }
 })
--
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] wildcards for type variables?

2010-01-13 Thread Antoine Latter
On Wed, Jan 13, 2010 at 4:59 AM, Brandon S. Allbery KF8NH
allb...@ece.cmu.edu wrote:
 On Jan 13, 2010, at 05:54 , David Virebayre wrote:

 On Wed, Jan 13, 2010 at 12:29 AM, Evan Laforge qdun...@gmail.com wrote:

 Occasionally I have a function with an unused argument, whose type I
 don't want to restrict.  Thus:

 f :: _unused - A - B
 f _ a = b

 I probably misunderstood the problem, why not f:: a - A - B


 He's looking for the self-documentation aspect of this argument is
 completely irrelevant.  Neither rolling a random unused type variable nor
 foralling it (my first idea) really accomplishes that.


Isn't that what we have here? a function of type (a - A - B) cannot
use the first argument in any meaningful way.

But once you start throwing in higher ranked types you might have to
think a bit to come to that conclusion.

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


Re: [Haskell-cafe] How to fulfill the code-reuse destiny of OOP?

2010-01-13 Thread Gregory Collins
Peter Verswyvelen bugf...@gmail.com writes:

 On Sun, Nov 1, 2009 at 2:57 AM, Gregory Collins g...@gregorycollins.net 
 wrote:

 Doing OO-style programming in Haskell is difficult and unnatural,
 it's true (although technically speaking it is possible). That
 said, nobody's yet to present a convincing argument to me why Java
 gets a free pass for lacking closures and typeclasses.

 I might be wrong, but doesn't Java's concepts of inner classes and
 interfaces together with adapter classes can be used to replace
 closures and typeclasses in a way?

Maybe, in the same sense that a lawnmower engine strapped to a
skateboard is a replacement for a car: it takes you ten times as long to
get to your destination and you're cold and wet when you get there.

G
-- 
Gregory Collins g...@gregorycollins.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] wildcards for type variables?

2010-01-13 Thread Sebastian Fischer


On Jan 13, 2010, at 2:16 PM, Antoine Latter wrote:


He's looking for the self-documentation aspect of this argument is
completely irrelevant.  Neither rolling a random unused type  
variable nor

foralling it (my first idea) really accomplishes that.



Isn't that what we have here? a function of type (a - A - B) cannot
use the first argument in any meaningful way.


I think, he wants to document that the type variable 'a' is not used  
in the *type*.


Just like you can document that the second argument of 'const' is  
unused by using a wildcard. You can write


const x _ = x

instead of

const x y = x

and it would be nice to write 'const's type as

a - _ - a

rather than

a - b - a

Sebastian

--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



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


[Haskell-cafe] what is *hack*?

2010-01-13 Thread Günther Schmidt

Hi,

References to a Hack. module came in the responses to my posts on HTML-GUIs.

What is Hack then?


Günther


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


Re: [Haskell-cafe] what is *hack*?

2010-01-13 Thread John Van Enk
http://hackage.haskell.org/package/hack

2010/1/13 Günther Schmidt gue.schm...@web.de

 Hi,

 References to a Hack. module came in the responses to my posts on
 HTML-GUIs.

 What is Hack then?


 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] what is *hack*?

2010-01-13 Thread Günther Schmidt

Hi John,

thanks, I should have mentioned that I had found it on hackage, I just 
don't understand what it *is* or what it's supposed to be for.


Günther


Am 13.01.10 14:46, schrieb John Van Enk:

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

2010/1/13 Günther Schmidt gue.schm...@web.de mailto:gue.schm...@web.de

Hi,

References to a Hack. module came in the responses to my posts on
HTML-GUIs.

What is Hack then?


Günther


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org mailto: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 *hack*?

2010-01-13 Thread John Van Enk
This may help more: http://wiki.github.com/nfjinjing/hack

The Hack project is based off of a project known as Rack for ruby. I'm
fairly sure the documentation you can find on Rack will help you understand
what Hack does.

2010/1/13 Günther Schmidt gue.schm...@web.de

  Hi John,

 thanks, I should have mentioned that I had found it on hackage, I just
 don't understand what it *is* or what it's supposed to be for.

 Günther


 Am 13.01.10 14:46, schrieb John Van Enk:

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

 2010/1/13 Günther Schmidt gue.schm...@web.de

 Hi,

 References to a Hack. module came in the responses to my posts on
 HTML-GUIs.

 What is Hack then?


 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] what is *hack*?

2010-01-13 Thread Magnus Therning
2010/1/13 John Van Enk vane...@gmail.com:
 This may help more: http://wiki.github.com/nfjinjing/hack

 The Hack project is based off of a project known as Rack for ruby. I'm
 fairly sure the documentation you can find on Rack will help you understand
 what Hack does.

Not knowing what Rack is myself I found this, and assume that's the
Ruby project you refer to: http://rack.rubyforge.org/

/M

-- 
Magnus Therning(OpenPGP: 0xAB4DFBA4)
magnus@therning.org  Jabber: magnus@therning.org
http://therning.org/magnus identi.ca|twitter: magthe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Xhtml?

2010-01-13 Thread Günther Schmidt

Hi,

apologies upfront. As time presses I decided to post questions 
immediately as soon as I run into dead-ends.


I just don't want to give the impression that I'm not willing to do my 
homework.


I'm trying to find documentation on Xhtml, the site on hackage refers to 
http://www.cse.ogi.edu/~andy/html/intro.htm for an introduction to the 
library, the link is dead.


I managed to locate Andy Gill's current homepage 
(http://www.cse.ogi.edu/~andy/html/intro.htm) but there is no mention of 
his html combinatory library.


Does anyone else know where an introduction to this library can be 
retrieved from?


Günther


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


[Haskell-cafe] Re: Xhtml?

2010-01-13 Thread Günther Schmidt

Am 13.01.10 15:31, schrieb Günther Schmidt:

Hi,

apologies upfront. As time presses I decided to post questions
immediately as soon as I run into dead-ends.

I just don't want to give the impression that I'm not willing to do my
homework.

I'm trying to find documentation on Xhtml, the site on hackage refers to
http://www.cse.ogi.edu/~andy/html/intro.htm for an introduction to the
library, the link is dead.

I managed to locate Andy Gill's current homepage
(http://www.cse.ogi.edu/~andy/html/intro.htm) but there is no mention of
his html combinatory library.



sry, I meant this site here: http://www.ittc.ku.edu/~andygill/index.php


Does anyone else know where an introduction to this library can be
retrieved from?

Günther




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


[Haskell-cafe] Web application interface

2010-01-13 Thread Michael Snoyman
Hi,

I recently read (again) the wiki page on a web application interface[1] for
Haskell. It seems like this basically works out to Hack[2], but using an
enumerator instead of lazy bytestring in the response type. Is anyone
working on implementing this? If not, I would like to create the package,
though I wouldn't mind some community input on some design decisions:

* Hack has been fairly well-tested in the past year and I think it provides
the features that people want. Therefore, I would want to model the
Environment variable for WAI from Hack. I *could* just import Hack in WAI
and use the exact same Environment data type. Thoughts?

* If using a different data type for Environment, should I replace the
String parts with ByteStrings? On the one hand, ByteStrings are the
correct data type since the HTTP protocol does not specify a character
encoding; on the other hand, Strings are easier to deal with.

* It's simple to write a function to convert between a lazy bytestring and
an enumerator, meaning it would be very easy to write conversion functions
between Hack and WAI applications. This would make it simpler for people to
use either backend.

If someone else is already working on WAI, please let me know, I don't want
to have duplicate implementations. The idea here is to consolidate, not
split the community. I have a few Hack handlers (simpleserver, cgi, fastcgi)
that I would happily convert to WAI handlers as well.

Michael

[1] http://www.haskell.org/haskellwiki/WebApplicationInterface
[2] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/hack
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] what is *hack*?

2010-01-13 Thread Michael Snoyman
Günther,

Hack is a layer between a web application and a web server. It allows you to
write a web application once and have it communicate with the server in
different ways simply by swapping the handler. For example, I have
applications that I test on my local system using hack-handler-simpleserver
and then deploy onto an Apache server using either hack-handler-cgi or
hack-handler-fastcgi.

Michael

2010/1/13 Günther Schmidt gue.schm...@web.de

  Hi John,

 thanks, I should have mentioned that I had found it on hackage, I just
 don't understand what it *is* or what it's supposed to be for.

 Günther


 Am 13.01.10 14:46, schrieb John Van Enk:

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

 2010/1/13 Günther Schmidt gue.schm...@web.de

 Hi,

 References to a Hack. module came in the responses to my posts on
 HTML-GUIs.

 What is Hack then?


 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


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


Re: [Haskell-cafe] Re: Xhtml?

2010-01-13 Thread minh thu
2010/1/13 Günther Schmidt gue.schm...@web.de:
 Am 13.01.10 15:31, schrieb Günther Schmidt:

 Hi,

 apologies upfront. As time presses I decided to post questions
 immediately as soon as I run into dead-ends.

 I just don't want to give the impression that I'm not willing to do my
 homework.

 I'm trying to find documentation on Xhtml, the site on hackage refers to
 http://www.cse.ogi.edu/~andy/html/intro.htm for an introduction to the
 library, the link is dead.

 I managed to locate Andy Gill's current homepage
 (http://www.cse.ogi.edu/~andy/html/intro.htm) but there is no mention of
 his html combinatory library.


 sry, I meant this site here: http://www.ittc.ku.edu/~andygill/index.php

 Does anyone else know where an introduction to this library can be
 retrieved from?

 Günther

Hi,

By Xhtml, do you mean the xhtml package on hackage [1] ?

Maybe to get you started:

$ ghci
Prelude :m + Text.XHtml.Strict
Prelude Text.XHtml.Strict putStrLn . prettyHtmlFragment $ p (primHtml
hello) ! [theclass foo]
p class=foo
   hello
/p

The idea is to create values of type Html, e.g. primHtml, combine them
to make bigger document, e.g. with p or (+++), possibly with some
attributes, e.g. with (!), then eventually render the final Html
value, e.g. with prettyHtmlFragment.

Try it in ghci!

HTH, cheers
Thu



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


[Haskell-cafe] Re: ssh ports for monk and nun?

2010-01-13 Thread Stefan Monnier
 Trying to get ssh working via putty from behind my company firewall.

My recommendation is to get access to an outside machine where you run
an OpenVPN server on port 80 or 443.  This will solve it once and for
all.
But first, please complain loudly and repeatedly about the firewall
being closed to port 22.


Stefan

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


Re: [Haskell-cafe] How to fulfill the code-reuse destiny of OOP?

2010-01-13 Thread Robert Greayer
On Wed, Jan 13, 2010 at 4:56 AM, Martin Coxall pseudo.m...@me.com wrote:

 On 13 Jan 2010, at 09:51, Peter Verswyvelen wrote:

 On Sun, Nov 1, 2009 at 2:57 AM, Gregory Collins g...@gregorycollins.net
 wrote:

 Doing OO-style programming in Haskell is difficult and unnatural, it's
 true (although technically speaking it is possible). That said, nobody's
 yet to present a convincing argument to me why Java gets a free pass for
 lacking closures and typeclasses.

 I might be wrong, but doesn't Java's concepts of inner classes and
 interfaces together with adapter classes can be used to replace closures and
 typeclasses in a way?

 Inner classes are not a semantic replacement for closures, even if you
 discount horrific syntax. Inner classes do not close over their lexical
 environment.
 Martin

Anonymous classes in Java close over their lexical environment (can
refer to variables in that lexical environment, with values bound at
the time of instance construction) with the caveat that only local
variables/parameters marked as 'final' may be referred to.  Aside from
the horrible syntax, this is the key distinction between them, and,
say, Ruby closures.  Referring to mutable variables from inside a
closure has its drawbacks, making the horrible syntax the biggest
stumbling block to using them IMHO (other than runtime overhead, which
I believe is also an issue).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] wildcards for type variables?

2010-01-13 Thread Evan Laforge
 Isn't that what we have here? a function of type (a - A - B) cannot
 use the first argument in any meaningful way.

 I think, he wants to document that the type variable 'a' is not used in the
 *type*.

Yeah, that's the idea, sorry if I wasn't clear.

In the case of const, I might write

const :: a - _b - a

To document that 'b' intentionally appears only once, but this is only
my convention and I've never seen anyone else use it.  In the case of
'const' it's pretty obvious and unnecessary, but in a longer signature
it might help a bit, especially if you are using phantom types and
some functions intentionally ignore type arguments.

I haven't used them before, but in the presence of scoped type
variables, wouldn't have a reader have to go look for internal
definitions to reassure himself that the type is in fact ignored
entirely?

It's not a big issue, but it seemed like a nice symmetry with pattern
matching syntax.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Name overloading

2010-01-13 Thread Cristiano Paris
Hi,

these days I'm thinking about name scoping in Haskell and a question
built up silently but steadily in my mind.

Many times I see code like this:

data Foo = { fooBar :: Int, fooSay :: String, fooClose :: String }

which reminds me of Ye Olde Times of C where you prepend the
structure name (or an abbreviation) to the structure's fields so as to
avoid clashes with other (possibly included) structures (here Haskell
qualified imports don't help as they just let you cut down the size of
the prefix which is still present though and is module-scoped anyway).

One of the most appreciated (at least by me) features of OOP languages
like C++, Java, Python and co. is the possibility to name instance
methods the same in different classes and have the compiler resolve to
the correct implementation (at least indirectly through a virtual
table when inheritance is in place) simply looking at the type of the
variable which - is applied to. The most fulgid example of this is
the open method, which is likely to be present in lots of classes.

Now, in Haskell we have type inference, which is The Good Thing as
it allows to validate your program at compile time. Hence, the idea
coming up to my mind is that type inference actually forbids a
type-directed resolution of names as in C++ or Java.

Is this correct?

Think about this piece of code:

data DB = { open :: DBHandle }
data FS = { open :: File }

foo x = open x

or, worse:

foo x = open (open x)

if the result of the first open application should typecheck with
the second. Notice that, in my understanding, adding a signature
doesn't help as the type checker must guarantee that foo code
complies with its signature, which is actually impossible if open is
left undetermined in its type.

Thank you for any comment.

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


Re: [Haskell-cafe] Name overloading

2010-01-13 Thread Bulat Ziganshin
Hello Cristiano,

Wednesday, January 13, 2010, 9:43:06 PM, you wrote:

 coming up to my mind is that type inference actually forbids a
 type-directed resolution of names as in C++ or Java.

you are right. we either have ad-hoc polymorphism like in C++ where
type of id selected based on type of arguments, like in

int open(char *s)
int open(int i)

or two-way type inference where each id has just one type. otherwise,
having both overloaded ids and two-way inference, we will got
polynomial raise of complexity of type inferencing. ie. imagine some

f = a . b . c . d

where a,b,c,d have multiple possible types

there is backdorr to this mechanism - you can define foo inside of
class. moreover, you can use this to overload struct fields:

class HasFoo a b where
  foo :: a - b

data X = {fooX :: Int}
data Y = {fooY :: Char}

instance HasFoo X Int  where foo=fooX
instance HasFoo Y Char where foo=fooY

although error messages may be not ideal ;)




-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Name overloading

2010-01-13 Thread John Millikin
The usual suggestion I see for this sort of thing is to create a
typeclass for the operations you care about[1][2]. For example:

---
class HasOpen a where
  open :: a - Handle

data DB
data FS

openDB :: DB - Handle
openFS :: FS - Handle

instance DB HasOpen where open = openDB
instance FS HasOpen where open = openFS
---

Of course, this doesn't allow you to have functions share the same
name if they have different signatures, as in your (open :: FS -
File) example. To be honest, I think the C / Haskell approach of
unambiguously-identified functions is clearly superior to the C++ / C#
/ Java class as namespace idiom, which has caused me no end of
grief.

Dynamic languages such as Python and Ruby, of course, can return
anything from anywhere. This is nice in some cases, but having used
both extensively I think (static typing+inference) is a better
solution than dynamic typing.

 Now, in Haskell we have type inference, which is The Good Thing as
 it allows to validate your program at compile time. Hence, the idea
 coming up to my mind is that type inference actually forbids a
 type-directed resolution of names as in C++ or Java.

 Is this correct?

Type inference and static typing are separate; inference makes static
typing usable, but static typing makes compile-type correctness
verification easier. And it's not inference making your goal
impossible, but the fact that Haskell (like C) does not support
arbitrary overloading.

[1] http://www.mail-archive.com/haskell-cafe@haskell.org/msg64844.html
[2] 
http://stackoverflow.com/questions/1897306/haskell-record-syntax-and-type-classes
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Name overloading

2010-01-13 Thread Bulat Ziganshin
Hello John,

Wednesday, January 13, 2010, 10:08:08 PM, you wrote:

 Of course, this doesn't allow you to have functions share the same
 name if they have different signatures

class Open a where
  open :: a

instance Open (Int - String) where ...
instance Open (String - Int) where ...

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Name overloading

2010-01-13 Thread Edward Kmett
Well, you can get part of the way there, by using a class associated type

class HasOpen a where
   type Open a :: *
   open :: a - Open a

This lets you use type inference in one direction, without requiring that
every result be a member of a data family. On the other hand, type inference
just became directional, like in C#. you can't use the type of Open a to
infer the type a because you've lost injectivity.

You'd need a data type family to guarantee injectivity and determine a from
the context of Open a, and that yields an ugly mess. Since each container
would have to yield a distinct value type and interoperability goes out the
window.

On the other hand, the mixture of fixed type slots and type family slots
gets you a pretty good compromise. You typically know the type of the
structs whose members you are asking for.

-Edward Kmett


On Wed, Jan 13, 2010 at 2:08 PM, John Millikin jmilli...@gmail.com wrote:

 The usual suggestion I see for this sort of thing is to create a
 typeclass for the operations you care about[1][2]. For example:


 ---
 class HasOpen a where
  open :: a - Handle

 data DB
 data FS

 openDB :: DB - Handle
 openFS :: FS - Handle

 instance DB HasOpen where open = openDB
 instance FS HasOpen where open = openFS

 ---

 Of course, this doesn't allow you to have functions share the same
 name if they have different signatures, as in your (open :: FS -
 File) example. To be honest, I think the C / Haskell approach of
 unambiguously-identified functions is clearly superior to the C++ / C#
 / Java class as namespace idiom, which has caused me no end of
 grief.

 Dynamic languages such as Python and Ruby, of course, can return
 anything from anywhere. This is nice in some cases, but having used
 both extensively I think (static typing+inference) is a better
 solution than dynamic typing.

  Now, in Haskell we have type inference, which is The Good Thing as
  it allows to validate your program at compile time. Hence, the idea
  coming up to my mind is that type inference actually forbids a
  type-directed resolution of names as in C++ or Java.
 
  Is this correct?

 Type inference and static typing are separate; inference makes static
 typing usable, but static typing makes compile-type correctness
 verification easier. And it's not inference making your goal
 impossible, but the fact that Haskell (like C) does not support
 arbitrary overloading.

 [1] http://www.mail-archive.com/haskell-cafe@haskell.org/msg64844.html
 [2]
 http://stackoverflow.com/questions/1897306/haskell-record-syntax-and-type-classes
 ___
 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] Name overloading

2010-01-13 Thread Edward Kmett

 On Wed, Jan 13, 2010 at 2:14 PM, Bulat Ziganshin 
 bulat.zigans...@gmail.com wrote:

 class Open a where
  open :: a

 instance Open (Int - String) where ...
 instance Open (String - Int) where ...


The problem with this approach is that you'll need to supply type
annotations with basically every use of open, which is even more verbose
than prepending the type name.

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


Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Andrew Coppin

Colin Paul Adams wrote:

Andrew It's weird that us Haskell people complain about there
Andrew being only 26 letters in the alphabet

Which alphabet?
You have plenty of choice in Unicode.
  


Er... I was under the impression that Haskell source code uses the ASCII 
character set, not Unicode.


(And even if that's not the case, I've yet to find a way to type in the 
Unicode characters which are hypothetically possible.)


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


Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Andrew Coppin

Marc Weber wrote:

As you can see, this conclusively proves... something.



What about brainfuck? 8 different signs are used.
- http://de.wikipedia.org/wiki/Brainfuck#cite_note-0

The first link points to a page saying there is an interpreter 98 bytes
in size..

What does this prove? :-)
  


Exhibit A: The Iota calculus.

It has one value (the Iota function), and one operator (function 
application). It is Turing-complete.


I have literally *no idea* how big an interpretter would be...

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


Re: [Haskell-cafe] Name overloading

2010-01-13 Thread Evan Laforge
 Now, in Haskell we have type inference, which is The Good Thing as
 it allows to validate your program at compile time. Hence, the idea
 coming up to my mind is that type inference actually forbids a
 type-directed resolution of names as in C++ or Java.

 Is this correct?

There is a proposed extension which is not implemented but was
discussed on the list a while back, maybe you'd find this interesting:

http://hackage.haskell.org/trac/haskell-prime/wiki/TypeDirectedNameResolution

Search back in the archives for TDNR and you should turn up some threads.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Brandon S. Allbery KF8NH

On Jan 13, 2010, at 14:25 , Andrew Coppin wrote:

Colin Paul Adams wrote:

   Andrew It's weird that us Haskell people complain about there
   Andrew being only 26 letters in the alphabet

Which alphabet?
You have plenty of choice in Unicode.


Er... I was under the impression that Haskell source code uses the  
ASCII character set, not Unicode.


The Report would beg to differ with you; see section 2.1.  Haskell  
uses the Unicode [11] character set. However, source programs are  
currently biased toward the ASCII character set used in earlier  
versions of Haskell .  (Currently at the time being 1998.  Unicode  
is more prevalent these days.)


(And even if that's not the case, I've yet to find a way to type in  
the Unicode characters which are hypothetically possible.)



That's a problem with your editor/development environment.

--
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 universityKF8NH




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


Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Andrew Coppin

Brandon S. Allbery KF8NH wrote:

On Jan 12, 2010, at 17:12 , Niklas Broberg wrote:
Haskell '98 apparently features 25 reserved words. (Not counting 
forall

and mdo and so on, which AFAIK are not in Haskell '98.)


21 actually. case, class, data, default, deriving, do, else, if,
import, in, infix, infixl, infixr, instance, let, module, newtype, of,
then, type, where. There's also three special words that can still be
used as identifiers, so aren't reserved: as, qualified, hiding.



Are we counting the FFI annex (foreign)?



Strictly, wasn't that added *after* the Haskell 98 report was written? 
I.e., if you wanted to be ultra-technical about it, it's not part of the 
original Haskell '98?


At any rate, no I didn't count the FFI. (Since I almost never use it.)

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


Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Brandon S. Allbery KF8NH

On Jan 13, 2010, at 14:29 , Andrew Coppin wrote:

Brandon S. Allbery KF8NH wrote:

On Jan 12, 2010, at 17:12 , Niklas Broberg wrote:
Haskell '98 apparently features 25 reserved words. (Not counting  
forall

and mdo and so on, which AFAIK are not in Haskell '98.)


21 actually. case, class, data, default, deriving, do, else, if,
import, in, infix, infixl, infixr, instance, let, module, newtype,  
of,
then, type, where. There's also three special words that can still  
be

used as identifiers, so aren't reserved: as, qualified, hiding.


Are we counting the FFI annex (foreign)?


Strictly, wasn't that added *after* the Haskell 98 report was  
written? I.e., if you wanted to be ultra-technical about it, it's  
not part of the original Haskell '98?



That would be the import of annex, yes.  It was not part of the  
original standard, but is considered part of the working Haskell '98  
standard.


--
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 universityKF8NH




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


Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Andrew Coppin

sylvain wrote:

Le mardi 12 janvier 2010 à 21:25 +, Andrew Coppin a écrit :

Hi Andrew,

  

As you can see, this conclusively proves... something.



What, exactly?
  


Not a lot. As you so elegantly point out, the number of keywords in a 
language is a fairly crude measurement of how complex the language is or 
is not. On the other hand, like lines of code, it's something that's 
easy to measure. ;-)


Other such ways include taking the size of a gzip of a typical block of 
source code, like the Shootout does. This doesn't really prove anything 
though, because any benchmark can be implemented in more than one way. 
You could also try using how many pages it takes to explain the syntax 
of the language - but that also depends on how you explain it. 
Simplicity is really in the eye of the beholder, after all...



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


[Haskell-cafe] What is the difference between Strachey diff from Scott Semantic Domain?

2010-01-13 Thread Daryoush Mehrtash
On Stack overflow page Conal Elliot  says:

 Beware that denotational semantics has two parts, from its two founders
 Christopher Strachey and Dana Scott: the easier  more useful Strachey part
 and the harder and less useful (for design) Scott part.


http://stackoverflow.com/questions/1028250/what-is-functional-reactive-programming



Any more information on how the Scott version is different from Starchey?



On Tue, Jan 12, 2010 at 3:24 PM, Raoul Duke rao...@gmail.com wrote:

 http://lambda-the-ultimate.org/node/1665#comment-55086


http://perlustration.blogspot.com/

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


Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Andrew Coppin

Brandon S. Allbery KF8NH wrote:

On Jan 13, 2010, at 14:29 , Andrew Coppin wrote:

Brandon S. Allbery KF8NH wrote:

Are we counting the FFI annex (foreign)?


Strictly, wasn't that added *after* the Haskell 98 report was 
written? I.e., if you wanted to be ultra-technical about it, it's not 
part of the original Haskell '98?



That would be the import of annex, yes.  It was not part of the 
original standard, but is considered part of the working Haskell '98 
standard.


Of course, you could always use Haskell 2010. It exists now, apparently...

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


Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Andrew Coppin

Brandon S. Allbery KF8NH wrote:

On Jan 13, 2010, at 14:25 , Andrew Coppin wrote:

Colin Paul Adams wrote:

   Andrew It's weird that us Haskell people complain about there
   Andrew being only 26 letters in the alphabet

Which alphabet?
You have plenty of choice in Unicode.


Er... I was under the impression that Haskell source code uses the 
ASCII character set, not Unicode.


The Report would beg to differ with you; see section 2.1.  Haskell 
uses the Unicode [11] character set. However, source programs are 
currently biased toward the ASCII character set used in earlier 
versions of Haskell .  (Currently at the time being 1998.  Unicode 
is more prevalent these days.)


So... how would GHC tell which of the hundreds of millions of possible 
character encodings is in use?


(And even if that's not the case, I've yet to find a way to type in 
the Unicode characters which are hypothetically possible.)


That's a problem with your editor/development environment.


Or rather, the problem with every computer system known to man?

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


Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Miguel Mitrofanov


On 13 Jan 2010, at 22:25, Andrew Coppin wrote:


Colin Paul Adams wrote:

   Andrew It's weird that us Haskell people complain about there
   Andrew being only 26 letters in the alphabet

Which alphabet?
You have plenty of choice in Unicode.



Er... I was under the impression that Haskell source code uses the  
ASCII character set, not Unicode.


(And even if that's not the case, I've yet to find a way to type in  
the Unicode characters which are hypothetically possible.)


module Main where
import Prelude hiding (putStrLn)
import System.IO.UTF8
main = let é = Andrew Coppin снова оказался неправ
   ç = что_то_там where что_то_там = undefined
   in putStrLn é

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


Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Sebastian Sylvan
On Wed, Jan 13, 2010 at 12:55 AM, Eduard Sergeev
eduard.serg...@gmail.comwrote:



 Andrew Coppin wrote:
 
  OK people, it's random statistics time!

 OK, my version of meaningless statistics:

 C++ (ISO/IEC 14882:1998(E)): 325 pages (712 including standard libraries)
 C# (ECMA-334): 505 pages (language only)
 Java: 450 pages (language only?)
 Scala (2.7): 125 pages (157 including standard library)
 Eiffel (ECMA-367): 160 pages (language only)
 ANSI SQL-92: 685 pages (language only)
 Haskell-98: 77 pages (247 including Prelude)
 Erlang (4.7.3) 162 pages (251 including builtin functions)
 Scheme (R5RS): 17 pages (45 including standard procedures)


Oberon: 16 pages, including table of contents and Appendix (containing EBNF
grammar).


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


Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Brandon S. Allbery KF8NH

On Jan 13, 2010, at 14:42 , Andrew Coppin wrote:

Brandon S. Allbery KF8NH wrote:

On Jan 13, 2010, at 14:25 , Andrew Coppin wrote:

Colin Paul Adams wrote:

  Andrew It's weird that us Haskell people complain about there
  Andrew being only 26 letters in the alphabet

Which alphabet?
You have plenty of choice in Unicode.


Er... I was under the impression that Haskell source code uses the  
ASCII character set, not Unicode.


The Report would beg to differ with you; see section 2.1.  Haskell  
uses the Unicode [11] character set. However, source programs are  
currently biased toward the ASCII character set used in earlier  
versions of Haskell .  (Currently at the time being 1998.   
Unicode is more prevalent these days.)


So... how would GHC tell which of the hundreds of millions of  
possible character encodings is in use?


That's left to the compiler implementation.  I'm not spotting an  
official statement in the GHC manual, but in practice GHC uses UTF-8.   
(It might support Windows standard UTF-16 as well; if do, it probably  
requires the first character of the source file to be a UTF-16 byte  
order mark.)


(And even if that's not the case, I've yet to find a way to type  
in the Unicode characters which are hypothetically possible.)


That's a problem with your editor/development environment.


Or rather, the problem with every computer system known to man?



s/man/you/

The existence of -XUnicodeSyntax ( http://www.haskell.org/ghc/docs/latest/html/users_guide/syntax-extns.html#unicode-syntax 
 ) suggests that at least some other GHC users don't have your problem.


--
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 universityKF8NH




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


Re: [Haskell-cafe] wildcards for type variables?

2010-01-13 Thread Sebastian Fischer


On Jan 13, 2010, at 6:54 PM, Evan Laforge wrote:


It's not a big issue, but it seemed like a nice symmetry with pattern
matching syntax.


And I don't think it's a weird idea. The Haskell dialect Curry [1]  
supports this syntax. Maybe the hurdle for Haskell is the competition  
with more complex, conflicting proposals like [2].


Sebastian

[1] http://curry-language.org
[2] http://hackage.haskell.org/trac/haskell-prime/wiki/PartialTypeSigs

--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



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


Re: [Haskell-cafe] Re: what is *hack*?

2010-01-13 Thread Pasqualino Titto Assini
Hi Michael,

what is your experience with hack? Do you have any problem moving your
apps from one server/env to another?

Regards,

 titto

2010/1/13 Günther Schmidt gue.schm...@web.de:
 Hi Michael,

 on first impression this seems like a good idea then.

 Günther



 Am 13.01.10 15:48, schrieb Michael Snoyman:

 Günther,

 Hack is a layer between a web application and a web server. It allows
 you to write a web application once and have it communicate with the
 server in different ways simply by swapping the handler. For example, I
 have applications that I test on my local system using
 hack-handler-simpleserver and then deploy onto an Apache server using
 either hack-handler-cgi or hack-handler-fastcgi.

 Michael



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




-- 
Pasqualino Titto Assini, Ph.D.
http://quicquid.org/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Tom Tobin
On Wed, Jan 13, 2010 at 1:28 PM, Brandon S. Allbery KF8NH
allb...@ece.cmu.edu wrote:
 On Jan 13, 2010, at 14:25 , Andrew Coppin wrote:
 (And even if that's not the case, I've yet to find a way to type in the
 Unicode characters which are hypothetically possible.)

 That's a problem with your editor/development environment.

It's not just one's editor (I use emacs, and it's actually not that
hard to type a decent subset of interesting Unicode characters in
emacs with the tex input mode), but readability.  The ASCII characters
are universal and easily recognized (assuming you have a decent
monochrome font); having to notice potentially significant differences
involving diacritics alone (not to mention all the various
mathematical symbols) in identifiers would drive me mad.  It's the
same reason we try to limit lines of code to ~80 characters — our
editors are *capable* of more, sure, but are we?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: what is *hack*?

2010-01-13 Thread Alberto G. Corona
rack (and hack)  permits also to concatenate applications (request handlers)
one in top of the other. with interesting combinations (filters,
encriptation layers, applications as such). It seems that this is the reason
for its name. At first sight it seems too little code to make something
useful, but it´s fine.

2010/1/13 Pasqualino Titto Assini tittoass...@gmail.com

 Hi Michael,

 what is your experience with hack? Do you have any problem moving your
 apps from one server/env to another?

 Regards,

 titto

 2010/1/13 Günther Schmidt gue.schm...@web.de:
  Hi Michael,
 
  on first impression this seems like a good idea then.
 
  Günther
 
 
 
  Am 13.01.10 15:48, schrieb Michael Snoyman:
 
  Günther,
 
  Hack is a layer between a web application and a web server. It allows
  you to write a web application once and have it communicate with the
  server in different ways simply by swapping the handler. For example, I
  have applications that I test on my local system using
  hack-handler-simpleserver and then deploy onto an Apache server using
  either hack-handler-cgi or hack-handler-fastcgi.
 
  Michael
 
 
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 



 --
 Pasqualino Titto Assini, Ph.D.
 http://quicquid.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] Re: what is *hack*?

2010-01-13 Thread Michael Snoyman
Titto,

I've had no problems with hack. The only things to keep in mind are outside
the scope of hack such as:

* Persistence. Clearly you need to optimize your application different for
CGI run (load up only what you need right now) versus long-running processes
like FastCGI (load data only once).
* URL schemes. A lot of people assume that your web app with be served from
the root of the domain. When using my simpleserver testing, that *is* the
case. However, I deploy apps in subdirectories of my domain (
http://www.snoyman.com/photos/, http://www.snoyman.com/wordify/, etc), so I
need to keep this in mind.

My only two quips about hack itself is:

* Versioning scheme. I wish (and have requested) that Hack would follow the
Package Versioning Policy so that I could easily check for breaking changes.
As is, I simply have to declare the exact version number of Hack I want to
work with to guarantee my apps aren't broken in the future.
* More serious issue is that it returns the response as a lazy bytestring.
It's not really fair to call this a quip, since I fully supported this
approach; nonetheless, using an enumerator for this would probably be more
efficient for certain use cases.

I just a few hours ago sent off an e-mail about bringing into fruition the
Web Application Interface for Haskell, which I would envision as Hack with
these two quips addressed. Theoretically, it would also allow easy
collaboration with Hack.

Michael

On Wed, Jan 13, 2010 at 10:33 PM, Pasqualino Titto Assini 
tittoass...@gmail.com wrote:

 Hi Michael,

 what is your experience with hack? Do you have any problem moving your
 apps from one server/env to another?

 Regards,

 titto

 2010/1/13 Günther Schmidt gue.schm...@web.de:
  Hi Michael,
 
  on first impression this seems like a good idea then.
 
  Günther
 
 
 
  Am 13.01.10 15:48, schrieb Michael Snoyman:
 
  Günther,
 
  Hack is a layer between a web application and a web server. It allows
  you to write a web application once and have it communicate with the
  server in different ways simply by swapping the handler. For example, I
  have applications that I test on my local system using
  hack-handler-simpleserver and then deploy onto an Apache server using
  either hack-handler-cgi or hack-handler-fastcgi.
 
  Michael
 
 
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 



 --
 Pasqualino Titto Assini, Ph.D.
 http://quicquid.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] ghc -e

2010-01-13 Thread Henning Thielemann


On Wed, 6 Jan 2010, Gwern Branwen wrote:


On Wed, Jan 6, 2010 at 7:23 PM, Tony Morris tonymor...@gmail.com wrote:

ghc -e import Control.Monad; forM [[1,2,3]] reverse


As of 6.10.2, the bug whereby the GHC API lets you use functions from
anywhere just by naming them (Java-style) has not been fixed:

$ ghc -e Control.Monad.forM [[1,2,3]] reverse
package flags have changed, resetting and loading new packages...


Why is this a bug? This is the intended behaviour in GHCi and you can 
include and exclude packages with -package and -hide-package options, 
respectively.

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


Re: [Haskell-cafe] Re: looking for origin of quote on preprocessors and language design

2010-01-13 Thread Henning Thielemann

Maciej Piechotka schrieb:


Not quite. While I agree that the *frequent* need for a preprocessor
shows omissions in (the design of) a language. it is not necessary the
case. Preprocessor may be useful if:

- there is a new beatyful feature in newer version of compiler but you
still want to have backward compatibility.
- there are compiler or platform dependant elements. For example if you
write a driver in Haskell you may want to share code as much as possible
but you need to know 1) the size of registers and 2) the platform you're
writing as Windows have quite different API then Linux or BSD.
- You need to enable/disable features at build-time. It is not frequent
at closed-source system but it is frequent on OpenSource systems. For
example I might need to have minimal program for embedded system but
with full feature set it likly conquer the desktops
  
Many of these problems are solved by preprocessor intervention in C/C++, 
but there is often no need to do so. You could also write system 
dependent modules, where the right module for your system is included by 
the build system. I hope the build system does not count as a 
preprocessor. In Haskell it is however still no fun to support multiple 
versions of the base libraries, not to speak of different compilers - 
and their set of libraries.


Unfortunately, the original question is still not answered.

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


[Haskell-cafe] Re: status of wash?

2010-01-13 Thread Günther Schmidt

Hi,

well I followed klondykes advise and followed through with the examples 
on the
http://www.haskell.org/haskellwiki/Practical_web_programming_in_Haskell 
site.


The authors did point out at the very beginning that the approach shown 
was not very sophisticated and I'd agree with that :) .


Of what I *read* about WASH that is more like what I had in mind, state 
of the art sort of thing. How come it's discontinued or not maintained? 
It pretty much looks like Seaside just in Haskell.


As I said this is by judging from what I *read*, I haven't actually used 
it yet.


Is this technique continued in some other project maybe?

Günther


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


Re: [Haskell-cafe] Re: looking for origin of quote on preprocessors and language design

2010-01-13 Thread Maciej Piechotka
On Wed, 2010-01-13 at 22:42 +0100, Henning Thielemann wrote:
 Maciej Piechotka schrieb:
 
  Not quite. While I agree that the *frequent* need for a preprocessor
  shows omissions in (the design of) a language. it is not necessary the
  case. Preprocessor may be useful if:
 
  - there is a new beatyful feature in newer version of compiler but you
  still want to have backward compatibility.
  - there are compiler or platform dependant elements. For example if you
  write a driver in Haskell you may want to share code as much as possible
  but you need to know 1) the size of registers and 2) the platform you're
  writing as Windows have quite different API then Linux or BSD.
  - You need to enable/disable features at build-time. It is not frequent
  at closed-source system but it is frequent on OpenSource systems. For
  example I might need to have minimal program for embedded system but
  with full feature set it likly conquer the desktops

 Many of these problems are solved by preprocessor intervention in C/C++, 
 but there is often no need to do so. You could also write system 
 dependent modules, where the right module for your system is included by 
 the build system. I hope the build system does not count as a 
 preprocessor. In Haskell it is however still no fun to support multiple 
 versions of the base libraries, not to speak of different compilers - 
 and their set of libraries.
 
 Unfortunately, the original question is still not answered.
 

Hmm. May I ask how to do for example something depending on POSIX or
WinAPI? I am sorry but I cannot see how any of the above problems could
be solved.

Regards


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


Re: [Haskell-cafe] looking for origin of quote on preprocessors and language design

2010-01-13 Thread John Millikin
Haskell doesn't *need* preprocessors, but they sure make a lot of
things easier. There are three I use regularly (c2hs, cpphs, noweb),
and each serves a purpose which isn't directly supported by plain
Haskell:

c2hs -- Supports generating foreign function imports and wrappers
based on C header files. This is simpler and less prone to
cross-platform type errors than writing the declarations in Haskell,
which generally requires a cpp-style #if..#else..#endif preprocessor
anyway.

cpphs -- The C preprocessor, adapted to Haskell syntax. I'd like to
replace my uses of it with Template Haskell, but TH's limitation that
its splices can't be defined in the same file make it (for my
purposes) essentially useless. cpphs is text-based, which means you
can glue together pretty much anything and let the compiler verify
that it type-checks.

noweb -- True literate programming (as opposed to .lhs verbose
commenting), which allows sections of the source code to be
re-arranged arbitrarily. I suppose it's possible in theory for a
language to support this without a preprocessing step, but (to my
knowledge) not even LISP derivatives do/can.

On Thu, Jan 7, 2010 at 04:32, Johannes Waldmann
waldm...@imn.htwk-leipzig.de wrote:
 Dear all,

 It's not exactly Haskell-specific, but ...
 I am trying to track down the origin of the proverb

 the existence (or: need for) a preprocessor
 shows omissions in (the design of) a language.


 I like to think that in Haskell, we don't need
 preprocessors since we can manipulate programs
 programmatically, because they are data.

 In other words, a preprocessor realizes higher order
 functions, and you only need this if your base language
 is first-order.

 Yes, that's vastly simplified, and it does not cover
 all cases, what about generic programming
 (but this can be done via Data.Data)
 and alex/happy (but we have parsec) etc etc.

 Best regards, J.W.


 ___
 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 fulfill the code-reuse destiny of OOP?

2010-01-13 Thread Martin Coxall
 
 
 Anonymous classes in Java close over their lexical environment (can
 refer to variables in that lexical environment, with values bound at
 the time of instance construction) with the caveat that only local
 variables/parameters marked as 'final' may be referred to.  Aside from
 the horrible syntax, this is the key distinction between them, and,
 say, Ruby closures.  Referring to mutable variables from inside a
 closure has its drawbacks, making the horrible syntax the biggest
 stumbling block to using them IMHO (other than runtime overhead, which
 I believe is also an issue).


Yes, this. Which makes them basically unusable where you might want proper 
closures.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Web application interface

2010-01-13 Thread Jinjing Wang
The hyena backend is essentially just a translator between hack and
wai, i failed to finished it since I can't understand iteratee
(seriously) and eventually got distracted  ...

What hyena tries to solve can't be realized in hack, so there's not
too much reason for a backend anyway.

Hyena is especially tuned for streaming and that's exactly what hack
can't do (in practice).

http://github.com/nfjinjing/hack-handler-hyena


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


Re: [Haskell-cafe] space leaks and optimizations

2010-01-13 Thread Ryan Ingram
On Sat, Jan 9, 2010 at 2:23 AM, Alexei Kitaev kit...@iqi.caltech.edu wrote:
 Reading the discussion related to your blog, I
 realized that strict State is different in that it does not actually
 force the state. But forcing can be achieved by wrapping all actions
 with the following function:

 sState :: (s - (a,s)) - State s a
 sState f = State $ \s - case f s of
                             (a,s') - s' `seq` (a,s')

 I hope that somebody will answer my other questions about the
 operational semantics and optimizations.

Hi Alexei, you have a ton of great points but I wanted to discuss an
issue with this one.

It's unusual that this is what you want either; since it only reduces
the state to WHNF.  For example, if your state is a string, this only
evaluates enough to know whether or not the string is empty at each
step, and you can still get into trouble with code like this:

   put (xxx ++ some_bad_computation)

which leave bottoms inside of your state which won't show up until later.

Several attempts to solve this problem exist, but the most commonly
used one is the rnf strategy from Control.Parallel.Strategies, which
uses a typeclass to allow each type to specify how to evaluate itself
completely.

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


Re: [Haskell-cafe] FFI, C/C++ and undefined references

2010-01-13 Thread DNM

Bulat,

Some very good suggestions.  I will try to appease Ceiling Cat and
reduce my (perhaps gratuitous) use of unsafePerformIO.  I'm going to
have to use it somewhere, since I want referentially transparent code
(and I try to avoid the IO monad when possible, anyway).

 2. if your function returns Ptr a - then hold in haskell types this Ptr a.
 no need to convert it back and forth to ForeignPtr
Yes, I thought of doing this, but then thought it was better to use a
so-called
managed foreign pointer via newForeignPtr.  I thought this was the best
way to have a foreign pointer that the Haskell garbage collector would eat
up when
it was no longer in use.  I could be wrong.  I convert from a ForeignPtr to
a Ptr, 
because the FFI code wasn't compiling at all (nevermind the missing C/C++
reference 
problem), as apparently a ForeignPtr isn't the sort of thing that an
imported foreign 
function can take as an argument (or so said GHC). I just assumed that the 
back-and-forth between Ptr and ForeignPtr would be compiled away by GHC.  
I could be wrong, though. If performance starts to suffer, I'll manage the
Ptr memory 
in my code directly.

 4. i don't looked in your code but if C functions defines
 *modifiable* datastructure - you should use it at Haskell side via
 imperatiove functions, i.e. those with return type IO a. using
 unsafePerformIO in this case will lead to Haskell compiler will
 consider this datatype as permanent and reorder operations on the will

Good point.  I would do this if I planned to train or update the language
model 
from within Haskell, but, as it stands, I just want to train it once (at the
command line, 
using the built-in mechanisms of SRILM) and then read in the ARPA-formatted
language 
model file for use in Haskell.

 3. why c_dlm is FunPtr in your definition? it should be
 
 foreign import ccall srilm.h deleteLM
c_dlm :: Ptr Ngram - IO ()
No reason.  Just because I don't know what I'm doing yet.
Thanks for the correction.

Thanks for the help, Bulat.  Much appreciated.

Best,
Dennis
-- 
View this message in context: 
http://old.nabble.com/FFI%2C-C-C%2B%2B-and-undefined-references-tp27139612p27156139.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] FFI, C/C++ and undefined references

2010-01-13 Thread DNM

Malcolm,

I saw this suggestion somewhere else.  Unfortunately, it didn't help either.
I still get the undefined reference errors.  I did eventually get ghc to
compile
Main.hs by putting the -c and -cpp flags after --make Main.hs.

Then it produces a Main.o file which (even with +x permissions on my Linux
box) will not run. I just get the message cannot run binary file, or some
such 
message.

No explanation given.

Any ideas?

Best,
Dennis


Malcolm Wallace wrote:
 
 But when I try to compile it (after having successfully compiled the  
 C code
 with g++), I get:

 $ ghc --make Main.hs
 
 You are not telling ghc to link against the C/C++ code,  e.g.
  ghc --make Main.hs srilm.o
 
 Regards,
  Malcolm
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

-- 
View this message in context: 
http://old.nabble.com/FFI%2C-C-C%2B%2B-and-undefined-references-tp27139612p27156254.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] FFI, C/C++ and undefined references

2010-01-13 Thread DNM

Sorry.  In my haste to paste in the .c file, I left out all the include
statements.  I do have #include srilm.h there (which to my non-
C/C++ mind seems stupid -- why the hell would you need to import 
the header file for the code that it's a header *for*?)

Still no dice.

Thanks for your time, though.  Sorry to waste it.

--D.N.

-- 
View this message in context: 
http://old.nabble.com/FFI%2C-C-C%2B%2B-and-undefined-references-tp27139612p27156267.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] FFI, C/C++ and undefined references

2010-01-13 Thread Brandon S. Allbery KF8NH

On Jan 13, 2010, at 23:28 , DNM wrote:
Sorry.  In my haste to paste in the .c file, I left out all the  
include

statements.  I do have #include srilm.h there (which to my non-
C/C++ mind seems stupid -- why the hell would you need to import
the header file for the code that it's a header *for*?)



Really, the only reason in this case is that there is no equivalent  
for `extern C' that you can apply to a function definition, only to  
a declaration.  The rationale is that everything that works with the  
function, including its definition, needs to see that declaration, so  
rather than repeat it in the definition you #include the declaration.


In GHC, this is the kind of thing that lands in the .hi file; the  
tradeoff is you need to have up to date .hi files for everything that  
needs to see that information, which can lead to dependency loops.   
GHC has a .hs-boot hack to work around this.  No free lunch


--
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 universityKF8NH




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


Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Colin Paul Adams
 Tom == Tom Tobin korp...@korpios.com writes:

Tom readability.  The ASCII characters are universal and easily
Tom recognized

No they are not.
My wife is Chinese. When she was learning pinyin as a child, she asked
her father for help with some homework. He replied that he didn't
understand them.
-- 
Colin Adams
Preston Lancashire
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Strategies

2010-01-13 Thread Alexei Kitaev
Dear Ryan,

Thanks a lot for your support and for pointing out a problem with my
approach to forcing the state. I was aware of this issue but I didn't
know there was a standard solution. It is indeed very natural to let
each type specify how to evaluate itself. I will try this technique on
the nearest occasion.

Incidentally, the link to Control.Parallel.Strategies from the latest
GHC User Guide is broken...

--Alexei

Ryan Ingram wrote:
 On Sat, Jan 9, 2010 at 2:23 AM, Alexei Kitaev kit...@iqi.caltech.edu wrote:
 Reading the discussion related to your blog, I
 realized that strict State is different in that it does not actually
 force the state. But forcing can be achieved by wrapping all actions
 with the following function:

 sState :: (s - (a,s)) - State s a
 sState f = State $ \s - case f s of
 (a,s') - s' `seq` (a,s')

 I hope that somebody will answer my other questions about the
 operational semantics and optimizations.
 
 Hi Alexei, you have a ton of great points but I wanted to discuss an
 issue with this one.
 
 It's unusual that this is what you want either; since it only reduces
 the state to WHNF.  For example, if your state is a string, this only
 evaluates enough to know whether or not the string is empty at each
 step, and you can still get into trouble with code like this:
 
put (xxx ++ some_bad_computation)
 
 which leave bottoms inside of your state which won't show up until later.
 
 Several attempts to solve this problem exist, but the most commonly
 used one is the rnf strategy from Control.Parallel.Strategies, which
 uses a typeclass to allow each type to specify how to evaluate itself
 completely.
 
   -- ryan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: FASTER primes

2010-01-13 Thread Will Ness
Daniel Fischer daniel.is.fischer at web.de writes:

 
 Am Mittwoch 13 Januar 2010 10:43:42 schrieb Heinrich Apfelmus:
  I wonder whether it's really the liveness of  pair  in
 
    mergeSP (a,b) pair
       = let sm = spMerge b (fst pair)
         in (a ++ fst sm, merge (snd sm) (snd pair))
 
  that is responsible for the space leak, for chances are that Sparud's
  technique applies and  pair  is properly disposed of. Rather, it could
  be that we need the stronger property that forcing the second component
  will evaluate the first to NF.
 
 I think that is responsible. At least that's how I understand the core:
 
 mergeSP (a,b) ~(c,d) = (a ++ bc, merge b' d)
where
   (bc, b') = spMerge b c
   spMerge ...



That is equivalent to

  first (a++) . second (`merge`d) $ spMerge b c

and Daniel's fix is equivalent to

  first (a++) $ spMerge b c d


Now, when compiler sees the first variant, it probably treats spMerge as 
opaque. I.e. although in reality spMerge only contributes to the 
first channel while it is progressively instantiated, and (`merge`d) will 
only be called upon when spMerge's final clause is reached, that is (most 
likely) not known to the compiler at this stage. When looking at just the first 
expression itself, it has to assume that spMerge may contribute to both 
channels (parts of a pair) while working, and so can't know _when_ /d/ will get 
called upon to contribute to the data, as it is consumed finally at access.

So /d/ is gotten hold of prematurely, _before_ going into spMerge.

The second variant passes the responsibility for actually accessing its inputs 
to spMerge itself, and _it_ is clear about needing /d/ only in the very end.

Just a theory. :) 

Does that make sense? 




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


Re[2]: [Haskell-cafe] FFI, C/C++ and undefined references

2010-01-13 Thread Bulat Ziganshin
Hello DNM,

Thursday, January 14, 2010, 7:07:43 AM, you wrote:

 Yes, I thought of doing this, but then thought it was better to use a
 so-called managed foreign pointer via newForeignPtr.

i recommend to use Ptr and switch to ForeignPtr only when you will
study how to use it. overall, unsafe* functions are really unsafe, and
using them without learning will lead to mysterious problems. it's
like painting with eyes closed

 Good point.  I would do this if I planned to train or update the language
 model 
 from within Haskell, but, as it stands, I just want to train it once (at the
 command line, 
 using the built-in mechanisms of SRILM) and then read in the ARPA-formatted
 language 
 model file for use in Haskell.

you may add problems by using unsafePerformIO. i recommend you to
learn first how to manage FFI without it, make program work, and only
then try to use it. eat elephant in small pieces!

look into http://haskell.org/haskellwiki/IO_inside


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re[2]: [Haskell-cafe] FFI, C/C++ and undefined references

2010-01-13 Thread Bulat Ziganshin
Hello Brandon,

Thursday, January 14, 2010, 7:40:45 AM, you wrote:
 Really, the only reason in this case is that there is no equivalent
 for `extern C' that you can apply to a function definition, only to
 a declaration

it works with GCC:

extern C int c_szOpenArchive (TABI_ELEMENT* params)
{

}

-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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