Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Pablo Nogueira
Hasn't Ryan raised an interesting point, though?

Bottom is used to denote non-termination and run-time errors. Are they
the same thing? To me, they're not. A non-terminating program has
different behaviour from a failing program.

When it comes to strictness, the concept is defined in a particular
semantic context, typically an applicative structure:

  [[ f x ]] = App [[f]] [[x]]

Function f is strict if App [[f]] _|_ = _|_

Yet, that definition is pinned down in a semantics where what  _|_
models is clearly defined.

I don't see why one could not provide a more detailed semantics where
certain kinds of run-time errors are distinguished from bottom.
Actually, this already happens. Type systems are there to capture many
program properties statically. Some properties that can't be captured
statically are captured dynamically: the compiler introduces run-time
tests. Checking for non-termination is undecidable, but putting
run-time checks for certain errors is not.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Haskell Digest, Vol 52, Issue 1

2007-12-05 Thread Simon Marlow

Taral wrote:

On 12/4/07, Simon Marlow [EMAIL PROTECTED] wrote:

  do
 x - newIVar
 let y = readIVar x
 writeIVar x 3
 print y

(I wrote the let to better illustrate the problem, of course you can inline
y if you want).  Now suppose the compiler decided to evaluate y before the
writeIVar.  What's to prevent it doing that?


Look at the translation:

newIVar = (\x - let y = readIVar x in writeIVar x 3  print y)

y can't be floated out because it depends on x.


y doesn't need to be floated out, just evaluated eagerly.

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


Re: [Haskell-cafe] Array copying

2007-12-05 Thread Andrew Coppin

Jules Bean wrote:

Andrew Coppin wrote:

Andrew Coppin wrote:
copy :: Word32 - IOUArray Word32 Bool - Word32 - IO (IOUArray 
Word32 Bool)

copy p grid size = do
 let size' = size * p
 grid' - newArray (1,size') False

 mapM_
   (\n - do
 b - readArray grid n
 if b
   then mapM_ (\x - writeArray grid' (n + size*x) True) [0..p-1]
   else return ()
   )
   [1..size]

 return grid'


Actually, thinking about this... for most kinds of arrays (whether 
boxed or unboxed, mutable or immutable) there's probably a more 
efficient way to copy the data then this. Maybe we should add 
something to the various array APIs to allow efficient copying of 
arrays / large chunks of arrays?


Ideally we'd have the compiler generate optimal code anyway, then you 
wouldn't need such things.


So, let's hope those compiler/optimiser guys keep working hard!


True - but copyArray x y is surely a lot clearer than some longwinded 
mapM thing, no? ;-)


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


[Haskell-cafe] SingHaskell slides

2007-12-05 Thread Martin Sulzmann

Slides (in pdf) are now available online:
http://taichi.ddns.comp.nus.edu.sg/taichiwiki/SingHaskell2007
http://www.comp.nus.edu.sg/~sulzmann/singhaskell07/index.html

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


Re: [Haskell-cafe] unification would give infinite type

2007-12-05 Thread Emil Axelsson
You usually don't need to worry about it. Just keep in mind that if you happen 
to get a strange type error concerning an (overloaded) function *without type 
signature*, it sometimes helps to add a signature.


/ Emil



On 2007-12-04 15:52, Rafael wrote:

I don't know about monomorphis restriction

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


Re: [Haskell-cafe] Re: Why is this strict in its arguments?

2007-12-05 Thread Luke Palmer
On Dec 5, 2007 12:16 AM, Aaron Denney [EMAIL PROTECTED] wrote:
  we (the FPSIG group) defined:
  data BTree a = Leaf a
   | Branch (BTree a) a (BTree a)

 Totally avoiding your question, but I'm curious as to why you
 deliberately exclude empty trees.

 Come to think of it, how can you represent a tree with two elements?

Indeed, this tree is only capable of representing odd numbers of
elements, which can be shown by straightforward induction.

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


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Andrew Coppin

Roberto Zunino wrote:

Neil Mitchell wrote:
  

is there any automated
way to know when a function is strict in its arguments?
  

Yes, strictness analysis is a very well studied subject -



...and is undecidable, in general. ;-)
  


*thinks*

Conjecture #1: All nontrivial properties of a computer program are 
undecidable in general.


*thinks more*

Conjecture #2: Conjecture #1 is undecidable...

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


Re: [Haskell-cafe] a positive challenge for the Haskell effort .....

2007-12-05 Thread Andrew Coppin

Galchin Vasili wrote:
http://code.enthought.com/enthon/ .. how do Haskell libraries/packages 
stack up against this challenge?


I suspect this question is rather nontrivial to answer.

There's a library to do X. Well, yes, but is it any good? (Does it have 
a nice API? Is it flexible? Is it reliable and bug-free? Is it 
efficient? etc.) Cateloging this information for both sides and then 
making a meaningful comparison would probably require a small grant, 9 
months and a team of consultants.


Anybody feel like giving me a small grant BTW? :-D

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


Re: [Haskell-cafe] Re: Why is this strict in its arguments?

2007-12-05 Thread Benja Fallenstein
Hi Paolo,

On Dec 5, 2007 2:09 PM, Paulo J. Matos [EMAIL PROTECTED] wrote:
 I'm glad that my initial post generated such an interesting discussion
 but I'm still not understanding why the first version of findAllPath
 seems to be computing the whole list even when I just request the
 head, while the second one doesn't.

Because the function starts its work with

if isNothing lfpaths  isNothing rtpaths
then Nothing
else ...

which forces the evaluation of 'lfpaths' and 'rtpaths' to see whether
they are Just or Nothing, which recursively forces the evaluation of
findAllPath for the whole tree.

Hope this helps,
- Benja
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Andrew Coppin

Tillmann Rendel wrote:

Andrew Coppin wrote:

*thinks*

Conjecture #1: All nontrivial properties of a computer program are 
undecidable in general.


That is the well-known Rice's theorem.


Wait - Rice's *theorem*? So Rice *proved* this?

OMG, I was *right* about something! :-D


Conjecture #2: Conjecture #1 is undecidable...

*thinks more*

But the question wether a nontrivial property of a computer program is 
decidable is *not* a property of computer programs itself.


Indeed no. And, in fact, if Rice's theorem has been proved, then clearly 
it *is* decidable. And has been decided.


I was merely noting that questions of the form is X decidable? are 
usually undecidable. (It's as if God himself wants to tease us...)


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


[Haskell-cafe] Re: Why is this strict in its arguments?

2007-12-05 Thread Paulo J. Matos
I'm glad that my initial post generated such an interesting discussion
but I'm still not understanding why the first version of findAllPath
seems to be computing the whole list even when I just request the
head, while the second one doesn't. I thought that this was
denominated by findAllPath is strict in its arguments but it seems
that I haven't used the right terminology to explain what I really
wanted to understand.

-- 
Paulo Jorge Matos - pocm at soton.ac.uk
http://www.personal.soton.ac.uk/pocm
PhD Student @ ECS
University of Southampton, UK
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Clean Dynamics and serializing code to disk

2007-12-05 Thread John van Groningen
[EMAIL PROTECTED] wrote:

Hey everyone; recently I've been toying around with various methods of writing 
a shell and reading the academic literature on such things. The best prior art 
on the subject seems to be the ESTHER shell (see 
http://citeseer.ist.psu.edu/689593.html, 
http://citeseer.ist.psu.edu/744494.html, 
ftp://ftp.cs.kun.nl/pub/Clean/papers/2003/vWeA2003-Esther.pdf).

Now, ESTHER is a really cool looking shell, but it has two main problems for 
me:
1) Source doesn't seem to be available anywhere online
...

The source code of ESTHER is include with Clean 2.2 in the directory
Libraries/Hilde of the windows 32 bit binary zip and the sources zip and tar.

Kind regards,

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


[Haskell-cafe] Re: Why is this strict in its arguments? (Jules Bean)

2007-12-05 Thread John Lato
Wow, thanks.  I had a similar function (long if/then/else chain,
fromJust) that I haven't been happy with, but couldn't see how to
improve it.  Now I have a much better idea for how to fix that
function.
Thanks again,
John Lato

 the general pattern is : replace isNothing with a case match on Nothing,
 replace fromJust with a case match on Just, don't be afraid to case two
 expressions at once.

 Hope someone finds that useful,

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


Re: [Haskell-cafe] Re: Why is this strict in its arguments?

2007-12-05 Thread Benja Fallenstein
On Dec 5, 2007 5:40 PM, Paulo J. Matos [EMAIL PROTECTED] wrote:
 Oh, but lfpaths is not nothing so that means that isNothing rtpaths
 shouldn't be evaluated, right?

You're right, and I was stupid not to think about that case. Since
Luke already gave an in-depth analysis I'll be quiet now :-)

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


Re: [Haskell-cafe] Clean Dynamics and serializing code to disk

2007-12-05 Thread Sterling Clover
In an email to the HAppS listt today, alexj described that HAppS-State
provides a way to serialize function calls for replay either on-restart or
on other replicated boxes. (which actually helped me to understand somewhat
what's going on behind all its TemplateHaskell magic. This is somewhat more
constrained than perhaps you're looking for, given that A) it requires
TemplateHaskell and B) it requires that the functions operate only on other
replicated boxes but it might be a place to start looking?

--S

On Dec 5, 2007 9:56 AM, John van Groningen [EMAIL PROTECTED] wrote:

 [EMAIL PROTECTED] wrote:

 Hey everyone; recently I've been toying around with various methods of
 writing a shell and reading the academic literature on such things. The best
 prior art on the subject seems to be the ESTHER shell (see 
 http://citeseer.ist.psu.edu/689593.html, 
 http://citeseer.ist.psu.edu/744494.html, 
 ftp://ftp.cs.kun.nl/pub/Clean/papers/2003/vWeA2003-Esther.pdf).
 
 Now, ESTHER is a really cool looking shell, but it has two main problems
 for me:
 1) Source doesn't seem to be available anywhere online
 ...

 The source code of ESTHER is include with Clean 2.2 in the directory
 Libraries/Hilde of the windows 32 bit binary zip and the sources zip and
 tar.

 Kind regards,

 John van Groningen
 ___
 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] Why is this strict in its arguments?

2007-12-05 Thread Paulo J. Matos
On Dec 5, 2007 1:51 PM, Luke Palmer [EMAIL PROTECTED] wrote:

 On Dec 4, 2007 9:41 PM, Paulo J. Matos [EMAIL PROTECTED] wrote:
  Hello all,
 
  As you might have possibly read in some previous blog posts:
  http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=10
  http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=11
 
  we (the FPSIG group) defined:
  data BTree a = Leaf a
 | Branch (BTree a) a (BTree a)
 
  and a function that returns a list of all the paths (which are lists
  of node values) where each path element makes the predicate true.
  findAllPath :: (a - Bool) - (BTree a) - Maybe [[a]]
  findAllPath pred (Leaf l) | pred l = Just [[l]]
| otherwise = Nothing
  findAllPath pred (Branch lf r rt) | pred r = let lfpaths = findAllPath pred 
  lf
   rtpaths = findAllPath pred 
  rt
   in
 if isNothing lfpaths 
  isNothing rtpaths
 then Nothing
 else
 if isNothing lfpaths
 then Just (map (r:)
  $ fromJust rtpaths)
 else
 if isNothing rtpaths
 then Just (map
  (r:) $ fromJust lfpaths)
 else Just (map
  (r:) $ fromJust rtpaths ++ fromJust lfpaths)
| otherwise = Nothing

 I don't think this evaluates the whole tree every time, but it
 certainly evaluates more than it needs to.  It has to do with an extra
 check.  Here's a very operational description:

 First note that if findAllPath returns Nothing, then it has evaluated
 the tree down to the contour where all the preds are false.  Let's
 suppose that this is the best possible case, where there is a path
 down the left side of the tree with no backtracking where all nodes
 are true.

 findAllPath pred (Leaf l) = Just [[l]]

 Now:

 if isNothing lfpaths  ...   -- false already, lfpaths is a Just, go
 to else branch
 else if isNothing lfpaths ... -- false again, go to else branch
 else if isNothing rtpaths ...

 To check this, you have to evaluate rtpaths down to its false contour
 before you can proceed.  You didn't need to do this.  Instead, writing
 the last else as:

 else Just (map (r:) $ fromJust lfpaths ++ fromMaybe [] rtpaths)

 Will get you behavior -- I think -- equivalent to the original.
 Except for that it will return paths in leftmost order rather than
 rightmost.  But changing the order of some of those checks will get
 you back the original rightmost behavior and lazy semantics.  Left as
 an exercise for the OP :-)


Oh, ok! :)

I think I got it now!
Thank you!

Cheers,

Paulo Matos

 Luke

  Later on we noticed that this could be simply written as:
  findAllPath :: (a - Bool) - (BTree a) - [[a]]
findAllPath pred = g where
g (Leaf l) | pred l = [[l]]
g (Branch lf r rt) | pred r = map (r:) $ (findAllPath pred
  lf) ++ (findAllPath pred rt)
g _  = []
 
  without even using maybe. However, 2 questions remained:
  1 - why is the first version strict in its arguments?
  2 - if it really is strict in its arguments, is there any automated
  way to know when a function is strict in its arguments?
 
  Cheers,
 
  --
  Paulo Jorge Matos - pocm at soton.ac.uk
  http://www.personal.soton.ac.uk/pocm
  PhD Student @ ECS
  University of Southampton, UK

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






-- 
Paulo Jorge Matos - pocm at soton.ac.uk
http://www.personal.soton.ac.uk/pocm
PhD Student @ ECS
University of Southampton, UK
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ghc overlapping instances

2007-12-05 Thread Steffen Mazanek
Hi,

Stefan and Isaac, thx for providing quick advice.

@Stefan: Unfortunately I have to use a list.
@Isaac: I do not get it. Could you please provide a short example of your
approach?

The question still remains. Which arguments do I have ghc to start with to
get the same behavior than hugs with -98 +o (here it works).

I provide my example for testing purposes:

module Test where
import Test.QuickCheck
import Monad(liftM,liftM2)

type Program = [Stmt]
data Stmt = Text | IfElse Program Program | While Program deriving (Eq,
Show)

instance Arbitrary [Stmt] where
  arbitrary = sized genProg
instance Arbitrary Stmt where
  arbitrary = sized genStmt

genStmt::Int-Gen Stmt
genStmt 0 = return Text
genStmt 1 = return Text
genStmt 2 = oneof [return Text, return (While [Text])]
genStmt n | n2 = oneof ([return Text,
  liftM While (genProg (n-1))]++
 [liftM2 IfElse (genProg k) (genProg
(n-k-1))|k-[1..n-2]])

genProg::Int-Gen Program
genProg 0 = return []
genProg 1 = return [Text]
genProg n | n1 = oneof ((liftM (\x-[x]) (genStmt n)):[liftM2 (:) (genStmt
k) (genProg (n-k))|k-[1..n-1]])

prop_ConstructParse progr = True
  where types = progr::Program

main = mapM_ (\(s,a) - putStrLn s  a) [(flowchart construct and parse,
test prop_ConstructParse)]


2007/12/4, Stefan O'Rear [EMAIL PROTECTED]:

 On Tue, Dec 04, 2007 at 03:36:20PM +0100, Steffen Mazanek wrote:
  Hello,
 
  I want to quickcheck a property on a datatype representing
  programs (=[Stmt]) and need to define a specific instance
 
  instance Arbitrary [Stmt]
 
  (mainly to restrict the size of the list).
 
  In quickcheck an instance Arbitrary of lists is already defined.
  Which parameters do I have to give ghc such that it accepts
  such an instance? In hugs -98 +o is enough. I have
  tried -XOverlappingInstances, -XFlexibleInstances and also
  -XIncoherentInstances, however I still got an overlapping
  instances error for this declaration.

 You shouldn't use lists if you need to have special instance behavior -
 lists are for perfectly ordinary sequences of things.  If a program is
 just a bunch of unrelated statements, then use [], otherwise use a
 custom (new)type.

 Stefan

 -BEGIN PGP SIGNATURE-
 Version: GnuPG v1.4.6 (GNU/Linux)

 iD8DBQFHVcxTFBz7OZ2P+dIRAmtMAJ9xcL0xhG9u+QaIFXwhEEq177ePEgCfUfOf
 dlDMHAN8ldq2qZ7ctOFkNb4=
 =hxkS
 -END PGP SIGNATURE-




-- 
Dipl.-Inform. Steffen Mazanek
Institut für Softwaretechnologie
Fakultät Informatik

Universität der Bundeswehr München
85577 Neubiberg

Tel: +49 (0)89 6004-2505
Fax: +49 (0)89 6004-4447

E-Mail: [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ghc overlapping instances

2007-12-05 Thread Isaac Dupree

Steffen Mazanek wrote:

Hi,

Stefan and Isaac, thx for providing quick advice.

@Stefan: Unfortunately I have to use a list.
@Isaac: I do not get it. Could you please provide a short example of your
approach?

The question still remains. Which arguments do I have ghc to start with to
get the same behavior than hugs with -98 +o (here it works).

I provide my example for testing purposes:

module Test where
import Test.QuickCheck
import Monad(liftM,liftM2)

type Program = [Stmt]
data Stmt = Text | IfElse Program Program | While Program deriving (Eq,
Show)

instance Arbitrary [Stmt] where
  arbitrary = sized genProg
instance Arbitrary Stmt where
  arbitrary = sized genStmt

genStmt::Int-Gen Stmt
genStmt 0 = return Text
genStmt 1 = return Text
genStmt 2 = oneof [return Text, return (While [Text])]
genStmt n | n2 = oneof ([return Text,
  liftM While (genProg (n-1))]++
 [liftM2 IfElse (genProg k) (genProg
(n-k-1))|k-[1..n-2]])

genProg::Int-Gen Program
genProg 0 = return []
genProg 1 = return [Text]
genProg n | n1 = oneof ((liftM (\x-[x]) (genStmt n)):[liftM2 (:) (genStmt
k) (genProg (n-k))|k-[1..n-1]])

prop_ConstructParse progr = True
  where types = progr::Program

main = mapM_ (\(s,a) - putStrLn s  a) [(flowchart construct and parse,
test prop_ConstructParse)]


is prop_ConstructParse the only thing that breaks when you remove the 
instance Arbitrary [Stmt] where arbitrary = sized genProg, or have I 
missed something?  If that's all, try this (untested) :


prop_ConstructParse = forAll (sized genProg) (\progr - True)

and similarly for other properties.

Or, you _can_ use a newtype for quickcheck-only, something like this:

newtype P = P { unP :: Program }
instance Show P where show = show . unP
instance Arbitrary P where arbitrary = sized genProg . unP
prop_ConstructParse (P progr) = True


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


[Haskell-cafe] distinguish functions from non-functions in a class/instances

2007-12-05 Thread Philipp N.

Hello,

i'm trying to wrap functions (a - b - ... - z) of any arity to functions
of type ([String] - y), where list of strings replaces the typed arguments.

one attempt looks like this (here written with type families, you can
replace it by functional dependencies or what ever):

type family Res x
type instance Res x = x
type instance Res (x-y) = Res y

class Nary x where
nary :: x - [String] - Res x

instance Nary x where
nary x [] = x

instance Nary (x-y) where
nary f (x:xs) = nary (f $ read x) xs

i hope you can get the idea.
the problem is, that you cannot distinguish type (x-y) from z, so these
instances are overlapping.
the odd thing is. you can get this to work, if you have a terminating type
as result type (for example (IO x)). then you can work with all types (IO
x), (a - IO x), (a - b - IO x), ...

but i don't want this delimiter IO! any ideas?

greetings
  Philipp N.

-- 
View this message in context: 
http://www.nabble.com/distinguish-functions-from-non-functions-in-a-class-instances-tf4952209.html#a14180315
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] Re: Why is this strict in its arguments?

2007-12-05 Thread Paulo J. Matos
On Dec 5, 2007 1:43 PM, Benja Fallenstein [EMAIL PROTECTED] wrote:
 Hi Paolo,

 On Dec 5, 2007 2:09 PM, Paulo J. Matos [EMAIL PROTECTED] wrote:
  I'm glad that my initial post generated such an interesting discussion
  but I'm still not understanding why the first version of findAllPath
  seems to be computing the whole list even when I just request the
  head, while the second one doesn't.

 Because the function starts its work with

 if isNothing lfpaths  isNothing rtpaths
 then Nothing
 else ...

 which forces the evaluation of 'lfpaths' and 'rtpaths' to see whether
 they are Just or Nothing, which recursively forces the evaluation of
 findAllPath for the whole tree.


Oh, but lfpaths is not nothing so that means that isNothing rtpaths
shouldn't be evaluated, right?

 Hope this helps,
 - Benja






-- 
Paulo Jorge Matos - pocm at soton.ac.uk
http://www.personal.soton.ac.uk/pocm
PhD Student @ ECS
University of Southampton, UK
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] distinguish functions from non-functions in a class/instances

2007-12-05 Thread Brandon S. Allbery KF8NH


On Dec 5, 2007, at 16:00 , Philipp N. wrote:

the odd thing is. you can get this to work, if you have a  
terminating type
as result type (for example (IO x)). then you can work with all  
types (IO

x), (a - IO x), (a - b - IO x), ...

but i don't want this delimiter IO! any ideas?


Use ST instead?  (just tossing ideas in the wind...)

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Looking for largest power of 2 = Integer

2007-12-05 Thread Spencer Janssen
On Tuesday 04 December 2007 15:47:19 David Benbennick wrote:
 On Dec 4, 2007 11:51 AM, Don Stewart [EMAIL PROTECTED] wrote:
  Awesome. We can use this in Data.Bits, if you've got some QuickChecks
  for it.

 Hear hear.  But is there any way to just make the compiler use
 fastTestBit in place of testBit :: (Bits a) = a - Int - Bool when a
 = Integer?  (That is, without having to introduce a new function to
 the public interface of Data.Bits.)  Some kind of SPECIALIZE pragma,
 perhaps?

 I've attached a program with two QuickCheck properties.  Unfortunately
 they fail on negative Integers.  I can't figure out why.

No fancy specialization is needed.  Since testBit is part of the Bits class,
simply 'testBit = fastTestBit' in the instance for Integer.


Cheers,
Spencer Janssen

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


Re: [Haskell-cafe] distinguish functions from non-functions in a class/instances

2007-12-05 Thread Ryan Ingram
No, that doesn't work; it's close, but not quite.  liftM doesn't have the
right type signature.

liftM :: Monad m = (a - r) - (m a1 - m r)

What would work is if you could define a function
liftLast :: Monad m = (a0 - a1 - ... - aN - r) - (a0 - a1 - ... -
aN - m r)

then

nary' f = runIdentity . nary (liftLast f)

  -- ryan


On 12/5/07, Dan Weston [EMAIL PROTECTED] wrote:

 Wouldn't any isomorphism do (like the Identity monad)? How about

 nary' f = runIdentity . nary (liftM f) . return


 Brandon S. Allbery KF8NH wrote:
 
  On Dec 5, 2007, at 16:00 , Philipp N. wrote:
 
  the odd thing is. you can get this to work, if you have a terminating
  type
  as result type (for example (IO x)). then you can work with all types
 (IO
  x), (a - IO x), (a - b - IO x), ...
 
  but i don't want this delimiter IO! any ideas?
 
  Use ST instead?  (just tossing ideas in the wind...)
 


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

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


Re: [Haskell-cafe] Clean Dynamics and serializing code to disk

2007-12-05 Thread Jed Brown
On  5 Dec 2007, [EMAIL PROTECTED] wrote:

 Since from my Lisp days I know that code is data, it strikes me that
 one could probably somehow smuggle Haskell expressions via this route
 although I am not sure this is a good way to go or even how one would
 do it (to turn, say, a list of the chosen ADT back into real
 functions, you need the 'eval' function, but apparently eval can only
 produce functions of the same type - so you'd need to either create as
 many adts and instances as there are varieties of type signatures in
 Haskell '98 and the libraries, I guess, or somehow encode in a lambda
 calculus). Is that a route worth pursuing?

I too am interested in serializing functions, but for a different
purpose: distributed computing without emulating global shared memory
like GdH.  The hard part, as I understand it, is tracking down all the
references in a function.  Once they are identified, we can wrap the
whole thing up (sort of lambda lifting at runtime) and send that.  I
believe this is what the GUM runtime does internally.  I am unaware of a
way to get at this information without modification of the runtime.

If the function we want to serialize is available at compile time, the
compiler should be able to do the lambda lifting and give us a binary
object that we can serialize.  I don't know if this is possible now or
if it would need a compiler modification.

Perhaps the Mobile Haskell approach is a good idea---serializing
byte-code generated by GHCi.  In one paper, they reference new functions

  packV :: a - IO CString
  unpackV :: CString - IO a

although I'm skeptical of these type signatures.  At least, they are
only valid for byte-code, so they don't tell the whole story.  This
byte-code is dynamically linked on the receiving end so the same
libraries must be compiled there, but compiled code is never serialized.
From the article:

  Packing, or serializing, arbitrary graph structures is not a trivial
  task and care must be taken to preserve sharing and cycles.  As in
  GpH, GdH and Eden, packing is done breadth-first, closure by closure
  and when the closure is packed its address is recorded in a temporary
  table that is checked for each new closure to be packed to preserve
  sharing and cycles.  We proceed packing until every reachable graph
  has been serialised.

As long as the real work takes place in compiled code, sending the
byte-code might not be a bad idea and it has the added benefit of being
platform-independent.  However, I haven't been able to find specifics
about the implementation of packV/unpackV, and I would think the runtime
is better positioned to do this analysis itself.

Perhaps someone on this list who knows a thing or two about the
internals can offer some insight.  :-)

Jed


pgpE0YVIASYXb.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Luke Palmer
On Dec 5, 2007 11:56 AM, Andrew Coppin [EMAIL PROTECTED] wrote:
 I was merely noting that questions of the form is X decidable? are
 usually undecidable. (It's as if God himself wants to tease us...)

I take issue with your definition of usually then.

Whenever X is decidable is undecidable, 'X is decidable' is decidable' is
decidable, namely false.  So there are at least as many decidable sentences
of the form X is decidable as there are undecidable ones.

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


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Derek Elkins
On Wed, 2007-12-05 at 10:01 +0100, Pablo Nogueira wrote:
 Hasn't Ryan raised an interesting point, though?
 
 Bottom is used to denote non-termination and run-time errors. Are they
 the same thing? 

Up to observational equality, yes.

 To me, they're not. A non-terminating program has
 different behaviour from a failing program.
 
 When it comes to strictness, the concept is defined in a particular
 semantic context, typically an applicative structure:
 
   [[ f x ]] = App [[f]] [[x]]
 
 Function f is strict if App [[f]] _|_ = _|_
 
 Yet, that definition is pinned down in a semantics where what  _|_
 models is clearly defined.
 
 I don't see why one could not provide a more detailed semantics where
 certain kinds of run-time errors are distinguished from bottom.

When there is reason to, that is exactly what is done.  The domain grows
from 1+V to 1+V+E.  However, when run-time errors can be observed you
start having to provide answers to undesirable questions:  what is the
behavior of error foo + error bar?  Another person has pointed you
to the imprecise exceptions paper that gives one well thought out answer
for this in the context of Haskell.

 Actually, this already happens. Type systems are there to capture many
 program properties statically. Some properties that can't be captured
 statically are captured dynamically: the compiler introduces run-time
 tests. Checking for non-termination is undecidable, but putting
 run-time checks for certain errors is not.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


[Haskell-cafe] Re: [Haskell] IVar

2007-12-05 Thread Jan-Willem Maessen


On Dec 5, 2007, at 3:58 AM, Simon Marlow wrote:


Jan-Willem Maessen wrote:


Consider this:

do
  x - newIVar
  let y = readIVar x
  writeIVar x 3
  print y

(I wrote the let to better illustrate the problem, of course you  
can inline y if you want).  Now suppose the compiler decided to  
evaluate y before the writeIVar.  What's to prevent it doing  
that?  Nothing in the Haskell spec, only implementation convention.
Nope, semantics.  If we have a cyclic dependency, we have to  
respect it---it's just like thunk evaluation order in that respect.


Ah, so I was thinking of the following readIVar:

readIVar = unsafePerformIO . readIVarIO

But clearly there's a better one.  Fair enough.


Hmm, so unsafePerformIO doesn't deal with any operation that blocks?   
I'm wondering about related sorts of examples now, as well:


do
  x - newIVar
  y - unsafeInterleaveIO (readIVarIO x)
  writeIVar x 3
  print y

Or the equivalent things to the above with MVars.

-Jan




Cheers,
Simon



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


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Luke Palmer
On Dec 5, 2007 12:30 PM, Andrew Coppin [EMAIL PROTECTED] wrote:

 Luke Palmer wrote:
  On Dec 5, 2007 11:56 AM, Andrew Coppin [EMAIL PROTECTED] wrote:
 
  I was merely noting that questions of the form is X decidable? are
  usually undecidable. (It's as if God himself wants to tease us...)
 
 
  I take issue with your definition of usually then.
 
  Whenever X is decidable is undecidable, 'X is decidable' is decidable' is
  decidable, namely false.  So there are at least as many decidable sentences
  of the form X is decidable as there are undecidable ones.
 

 Ouch... my head hurts.

 OK, well how about I rephrase it as most 'interesting' questions about
 decidability tend to be undecidable and we call it quits? ;-)

Nah, I was just performing a slight-of-hand on you.  Basically by
saying X is decidable
is undecidable, you were implying you could prove it.   Which you
usually can't.  Well,
rather, which you usually don't know if you can...

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


[Haskell-cafe] Re: [Haskell] IVar

2007-12-05 Thread Simon Marlow

Jan-Willem Maessen wrote:


Consider this:

do
   x - newIVar
   let y = readIVar x
   writeIVar x 3
   print y

(I wrote the let to better illustrate the problem, of course you can 
inline y if you want).  Now suppose the compiler decided to evaluate y 
before the writeIVar.  What's to prevent it doing that?  Nothing in 
the Haskell spec, only implementation convention.


Nope, semantics.  If we have a cyclic dependency, we have to respect 
it---it's just like thunk evaluation order in that respect.


Ah, so I was thinking of the following readIVar:

 readIVar = unsafePerformIO . readIVarIO

But clearly there's a better one.  Fair enough.

Cheers,
Simon

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


Re: [Haskell-cafe] distinguish functions from non-functions in a class/instances

2007-12-05 Thread Dan Weston

Wouldn't any isomorphism do (like the Identity monad)? How about

nary' f = runIdentity . nary (liftM f) . return


Brandon S. Allbery KF8NH wrote:


On Dec 5, 2007, at 16:00 , Philipp N. wrote:

the odd thing is. you can get this to work, if you have a terminating 
type

as result type (for example (IO x)). then you can work with all types (IO
x), (a - IO x), (a - b - IO x), ...

but i don't want this delimiter IO! any ideas?


Use ST instead?  (just tossing ideas in the wind...)




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


Re: [Haskell-cafe] Parsing unstructured data

2007-12-05 Thread Olivier Boudry
On Nov 29, 2007 5:31 AM, Reinier Lamers [EMAIL PROTECTED] wrote:

 Especially in the fuzzy cases like this one, NLP often turns to machine
 learning models. One could try to train a hidden Markov model or support
 vector machines to label parts of the string as name, street,
 number, city, etc. These techniques work very well for part of
 speech tagging in natural language, and this seems similar. However, you
 need a manually annotated set of examples to train the models. If you
 really have a big load of data and it seems like a good solution, you
 could use an off-the-shelf part-of-speech tagger like SVMTool
 (http://www.lsi.upc.edu/~nlp/SVMTool/http://www.lsi.upc.edu/%7Enlp/SVMTool/)
 to do it.

 Reinier


Hi Reinier,

Thanks for the link to SVMTool. I don't have the basis to understand most of
the NLP articles I found and get stuck on the first NLP's slang words. For
me using an existing tool will be easier than build a new one. I'm currently
looking at the tool's documentation and it looks quite promising. It seems
to be very generic and highly reusable.

Cheers,

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


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Andrew Coppin

Luke Palmer wrote:

On Dec 5, 2007 11:56 AM, Andrew Coppin [EMAIL PROTECTED] wrote:
  

I was merely noting that questions of the form is X decidable? are
usually undecidable. (It's as if God himself wants to tease us...)



I take issue with your definition of usually then.

Whenever X is decidable is undecidable, 'X is decidable' is decidable' is
decidable, namely false.  So there are at least as many decidable sentences
of the form X is decidable as there are undecidable ones.
  


Ouch... my head hurts.

OK, well how about I rephrase it as most 'interesting' questions about 
decidability tend to be undecidable and we call it quits? ;-)


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


Re: [Haskell-cafe] type class question

2007-12-05 Thread Brent Yorgey
On Dec 3, 2007 7:43 AM, Peter Padawitz [EMAIL PROTECTED] wrote:

  What is wrong here? ghci tries (and fails) to deduce certain types for
 the comp functions that I did not expect.

 type Block   = [Command]
 data Command = Skip | Assign String IntE | Cond BoolE Block Block |
Loop BoolE Block
 data IntE= IntE Int | Var String | Sub IntE IntE | Sum [IntE] | Prod
 [IntE]
 data BoolE   = BoolE Bool | Greater IntE IntE | Not BoolE

 class Java block command intE boolE
where block_ :: [command] - block
  skip :: command
  assign :: String - intE - command
  cond :: boolE - block - block - command
  loop :: boolE - block - command
  intE_ :: Int - intE
  var :: String - intE
  sub :: intE - intE - intE
  sum_ :: [intE] - intE
  prod :: [intE] - intE
  boolE_ :: Bool - boolE
  greater :: intE - intE - boolE
  not_ :: boolE - boolE

  compBlock :: Block - block
  compBlock = block_ . map compCommand

  compCommand :: Command - command
  compCommand Skip   = skip
  compCommand (Assign x e)   = assign x (compIntE e)
  compCommand (Cond be c c') = cond (compBoolE be) (compCommand c)
   (compCommand c')
  compCommand (Loop be c)= loop (compBoolE be) (compCommand
 c)-}

  compIntE :: IntE - intE
  compIntE (IntE i)   = intE_ i
  compIntE (Var x)= var x
  compIntE (Sub e e') = sub (compIntE e) (compIntE e')
  compIntE (Sum es)   = sum_ (map compIntE es)
  compIntE (Prod es)  = prod (map compIntE es)

  compBoolE :: BoolE - boolE
  compBoolE (BoolE b)  = boolE_ b
  compBoolE (Greater e e') = greater (compIntE e) (compIntE e')
  compBoolE (Not be)   = not_ (compBoolE be)


Well, first of all, the definition of compCommand should use calls to
compBlock, not recursive calls to compCommand.  But that's not the main
source of your problems.

What exactly are you trying to accomplish?  And why do you need a type
class?

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


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Johan Tibell
On Dec 5, 2007 11:44 AM, Jules Bean [EMAIL PROTECTED] wrote:
 the general pattern is : replace isNothing with a case match on Nothing,
 replace fromJust with a case match on Just, don't be afraid to case two
 expressions at once.

That's a nice little insight. I'll remember that.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Jules Bean

Paulo J. Matos wrote:

Hello all,


Hi.



findAllPath :: (a - Bool) - (BTree a) - Maybe [[a]]
findAllPath pred (Leaf l) | pred l = Just [[l]]
  | otherwise = Nothing
findAllPath pred (Branch lf r rt) | pred r = let lfpaths = findAllPath pred lf
 rtpaths = findAllPath pred rt
 in
   if isNothing lfpaths 
isNothing rtpaths
   then Nothing
   else
   if isNothing lfpaths
   then Just (map (r:)
$ fromJust rtpaths)
   else
   if isNothing rtpaths
   then Just (map
(r:) $ fromJust lfpaths)
   else Just (map
(r:) $ fromJust rtpaths ++ fromJust lfpaths)
  | otherwise = Nothing


Ignoring the fact that you found a better way to write this entirely, a 
style point.


Use of isNothing and fromJust and a cascade of ifs is generally a poor 
sign, much better to use case:


findAllPath pred (Branch lf r rt)
| pred r =
case (findAllPath pred lf,findAllPath pred rt) of
  (Nothing,Nothing)   - Nothing
  (Nothing,Just rtpaths)  - Just (map (r:) rtpaths)
  (Just lfpaths,Nothing)  - Just (map (r:) lfpaths)
  (Just lfpaths,Just rtpaths) - Just (map (r:) $ rtpaths ++ 
lfpaths)

| otherwise = Nothing

the general pattern is : replace isNothing with a case match on Nothing, 
replace fromJust with a case match on Just, don't be afraid to case two 
expressions at once.


Hope someone finds that useful,

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


RE: [Haskell-cafe] building HUnit and other packages on Windows cygwin...

2007-12-05 Thread Bayley, Alistair
 From: [EMAIL PROTECTED] 
 [mailto:[EMAIL PROTECTED] On Behalf Of Galchin Vasili
 
 I believe that HUnit has absolutely not other package 
 dependencies. When I do a runhaskell Setup.hs build, I get 
 the following error message: gcc: installation problem, cannot 
 exec `cc1': No such file or directory. I am not sure what 
 cc1 is? A pass/phase of the gnu gcc compiler? 

Which version of ghc is it? There's a bug with ghc-6.8.1 and Cabal,
where you need to put gcc-lib in your path. It looks like that solution
might help you here, but I don't know what the cause of the problem is.

Yes, cc1 is the gnu c compiler, which is bundled with ghc in the gcc-lib
folder.

Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Paulo J. Matos
On Dec 4, 2007 10:00 PM, Neil Mitchell [EMAIL PROTECTED] wrote:
 Hi

  findAllPath :: (a - Bool) - (BTree a) - [[a]]
findAllPath pred = g where
g (Leaf l) | pred l = [[l]]
g (Branch lf r rt) | pred r = map (r:) $ (findAllPath pred
  lf) ++ (findAllPath pred rt)
g _  = []
 
  without even using maybe. However, 2 questions remained:
  1 - why is the first version strict in its arguments?

 Because in all call paths findAllPath will call g with its second
 argument. g will always evaluate (by pattern matching on) its value
 argument.


Wait! You're analyzing my second function and you're saying that it is
strict in its arguments?
Gee, that's bad. I questioned about the first one. The second seems to
be definitely lazy because I can use it on such big trees like I
showed. How come I can do this computation if like you said the
function is strict?

  2 - if it really is strict in its arguments, is there any automated
  way to know when a function is strict in its arguments?

 Yes, strictness analysis is a very well studied subject -
 http://haskell.org/haskellwiki/Research_papers/Compilation#Strictness
 . Essentially, an argument is strict if passing _|_ for that value
 results in _|_. So to take your example, evaluating:

 findAllPath a _|_
 g _|_
 _|_

 Since g tests what value _|_ has, we get bottom.

 Thanks

 Neil






-- 
Paulo Jorge Matos - pocm at soton.ac.uk
http://www.personal.soton.ac.uk/pocm
PhD Student @ ECS
University of Southampton, UK
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: type class question

2007-12-05 Thread Ben Franksen
Brent Yorgey wrote:
 Well, first of all, the definition of compCommand should use calls to
 compBlock, not recursive calls to compCommand.  But that's not the main
 source of your problems.
 
 What exactly are you trying to accomplish?  And why do you need a type
 class?

Whatever the code is supposed to accomplish, there is something strange
going on with the type checking. I have managed to reduce the code (while
keeping the type error message) thus

data Command = Skip

class Java block command where
  block_ :: [command] - block

  compBlock :: [Command] - block
  --compBlock = block_ . map compCommand

  compCommand :: Command - command

This compiles ok. But when I ask ghci for the type of the body of the
default definition of compBlock I get

*Main :t block_ . map compCommand
block_ . map compCommand :: forall block block1 command.
(Java block command, Java block1 command) =
[Command] - block

and if I remove the comment from the default definition of compBlock I get

Could not deduce (Java block command1)
  from the context (Java block command)
  arising from use of `block_' at Bla.hs:7:14-19
Possible fix:
  add (Java block command1)
  to the class or instance method `compBlock'
In the first argument of `(.)', namely `block_'
In the expression: block_ . (map compCommand)
In the definition of `compBlock':
compBlock = block_ . (map compCommand)

It would be nice if someone could explain (in language that can be
understood by non-type-system-experts) why ghc(i) deduces these
strange 'duplicated' contexts.

Cheers
Ben

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


Re: [Haskell-cafe] Re: type class question

2007-12-05 Thread Felipe Lessa
On Dec 5, 2007 10:38 PM, Ben Franksen [EMAIL PROTECTED] wrote:
 data Command = Skip

 class Java block command where
   block_ :: [command] - block

   compBlock :: [Command] - block
   --compBlock = block_ . map compCommand

   compCommand :: Command - command

My guess is that nothing's guaranteeing the calls from block_ and
compCommand to be using the same 'command' type as the class head. For
example, having

 instance Java B C1
 instance Java B C2

you can have both

 compBlock = (block_ :: [C1] - B) . map (compCommand :: Command - C1)
 compBlock = (block_ :: [C2] - B) . map (compCommand :: Command - C2)

Also, there's another problem: from compCommand you can't know the
type of block (as it's not appearing in the signature). The modified
version below typechecks:

 data Command = Skip

 class Java block command | command - block where
  block_ :: [command] - block

  compBlock :: [Command] - block
  compBlock = block_ . map (compCommand :: Command - command)

  compCommand :: Command - command

(Note that (compCommand :: Command - command) actually is restricting
to a monomorphic type.)

So, this seems to me to be a problem with multi-parameter type classes
when you prune the types (on compBlock and on compCommand one of the
types of the class head is missing).

I'm not a wizard on this subject, please anybody correct me if I'm mistaken =).

Cheers,

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


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Tillmann Rendel

Andrew Coppin wrote:

*thinks*

Conjecture #1: All nontrivial properties of a computer program are 
undecidable in general.


That is the well-known Rice's theorem.

(A very handy one in exams about theoretical computer science, since you 
can smash so many questions with follows from Rice).



*thinks more*

Conjecture #2: Conjecture #1 is undecidable...


But the question wether a nontrivial property of a computer program is 
decidable is *not* a property of computer programs itself. (it is a 
property of properties of computer programs instead). Rice's theorem 
doesn't apply to Rice's theorem.


(Thats the problem with smashing everything with Rice's theorem: it may 
be not applicable).


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


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Paulo J. Matos
On Dec 5, 2007 10:44 AM, Jules Bean [EMAIL PROTECTED] wrote:
 Paulo J. Matos wrote:
  Hello all,

 Hi.


  findAllPath :: (a - Bool) - (BTree a) - Maybe [[a]]
  findAllPath pred (Leaf l) | pred l = Just [[l]]
| otherwise = Nothing
  findAllPath pred (Branch lf r rt) | pred r = let lfpaths = findAllPath pred 
  lf
   rtpaths = findAllPath pred 
  rt
   in
 if isNothing lfpaths 
  isNothing rtpaths
 then Nothing
 else
 if isNothing lfpaths
 then Just (map (r:)
  $ fromJust rtpaths)
 else
 if isNothing rtpaths
 then Just (map
  (r:) $ fromJust lfpaths)
 else Just (map
  (r:) $ fromJust rtpaths ++ fromJust lfpaths)
| otherwise = Nothing

 Ignoring the fact that you found a better way to write this entirely, a
 style point.

 Use of isNothing and fromJust and a cascade of ifs is generally a poor
 sign, much better to use case:

 findAllPath pred (Branch lf r rt)
  | pred r =
  case (findAllPath pred lf,findAllPath pred rt) of
(Nothing,Nothing)   - Nothing
(Nothing,Just rtpaths)  - Just (map (r:) rtpaths)
(Just lfpaths,Nothing)  - Just (map (r:) lfpaths)
(Just lfpaths,Just rtpaths) - Just (map (r:) $ rtpaths ++
 lfpaths)
  | otherwise = Nothing

 the general pattern is : replace isNothing with a case match on Nothing,
 replace fromJust with a case match on Just, don't be afraid to case two
 expressions at once.

 Hope someone finds that useful,


Thanks, Although I think that the general thread diverged from my
initial question, here it is again, why is this terrible function (I
know it is ugly) evaluating all of the resulting list when I just
request the head? (at seems from my experiments that's what it seems
to be doing).

BTW, I thought that the problem of  evaluating all of the resulting
list when I just request the head  was related to argument strictness
but from the other mails, I think I was wrong. :)

 Jules






-- 
Paulo Jorge Matos - pocm at soton.ac.uk
http://www.personal.soton.ac.uk/pocm
PhD Student @ ECS
University of Southampton, UK
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Why is this strict in its arguments?

2007-12-05 Thread Paulo J. Matos
On Dec 5, 2007 12:16 AM, Aaron Denney [EMAIL PROTECTED] wrote:
 On 2007-12-04, Paulo J. Matos [EMAIL PROTECTED] wrote:
  Hello all,
 
  As you might have possibly read in some previous blog posts:
  http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=10
  http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=11
 
  we (the FPSIG group) defined:
  data BTree a = Leaf a
 | Branch (BTree a) a (BTree a)

 Totally avoiding your question, but I'm curious as to why you
 deliberately exclude empty trees.

 Come to think of it, how can you represent a tree with two elements?


Good question. I think we were just trying to define a tree in the
meeting and everyone agreed on this representation.

 Wouldn't

  data BTree a = Empty
   | Branch (BTree a) a (BTree a)

 be better?


Possibly :) I think that at the time nobody really cared about empty
trees! But for a really application we would have had to define them
probably. Now thinking about it, it seems like defining lists without
Null, strange, isn't it?

 --
 Aaron Denney
 --


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






-- 
Paulo Jorge Matos - pocm at soton.ac.uk
http://www.personal.soton.ac.uk/pocm
PhD Student @ ECS
University of Southampton, UK
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: type class question

2007-12-05 Thread Ryan Ingram
On 12/5/07, Ben Franksen [EMAIL PROTECTED] wrote:

 data Command = Skip

 class Java block command where
 block_ :: [command] - block

 compBlock :: [Command] - block
 --compBlock = block_ . map compCommand

 compCommand :: Command - command

 This compiles ok. But when I ask ghci for the type of the body of the
 default definition of compBlock I get

 *Main :t block_ . map compCommand
 block_ . map compCommand :: forall block block1 command.
 (Java block command, Java block1 command) =
 [Command] - block


Lets look at the type of compCommand.

compCommand :: Java block command = Command - command

The block type is not used at all in this declaration, but the block type
can influence which implementation compCommand is chosen.  This means that
it's actually almost impossible to ever call this function, as given a type
for  command there could be multiple implementations of Java block
command for different block types, and there's no way to ever determine
which function to call unless the instance declaration admits any type.

{-# OPTIONS_GHC -fglasgow-exts #-}
module BrokenTypeClass where

class Broken a b where
broken :: String - b

{-
instance Broken Bool String where
broken = id

instance Broken String String where
broken = reverse
-} -- which instance of broken do you choose in test below?

instance Broken a String where
broken = id

test :: String
test = broken hello
You would have to use functional dependencies or associated types to
eliminate this error.  Alternatively, you can add a dummy argument of type
block and pass undefined :: BlockType in to help choose the instance
declaration.

Still, I agree with Brent here; whenever I have written code like this I
soon realize that I didn't need a typeclass in the first place, and I would
have been better off not using them; they're not like OO classes.

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


Re: [Haskell-cafe] foild function for expressions

2007-12-05 Thread Pablo Nogueira
I believe the exercise is about understanding folds.

There are two references that are related to the exercise:

  A tutorial on the universality and expressiveness of fold, by Graham Hutton.
  Dealing with large bananas, by Ralf Lammel, etc.

The last paper motivates well the need to gather all the function
parameters to the fold (ie, the algebra) in a separate record
structure.

I don't think being told what to write will help you understand what
is going on, which is simpler than it seems.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Graph theory analysis of Haskell code

2007-12-05 Thread Ivan Miljenovic
On 06/12/2007, Tim Chevalier [EMAIL PROTECTED] wrote:
 This is very well-trodden ground, but if you familiarize yourself with
 the literature on the subject, then who knows, you may discover
 something new. And you can take pleasure in knowing that you've
 already independently conceived of an idea that lots of smart people
 have seen fit to put a lot of time into :-)

\o/ Yay! :p
-- 
Ivan Lazar Miljenovic
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Graph theory analysis of Haskell code

2007-12-05 Thread Ivan Miljenovic
This isn't strictly Haskell related, but anyway.

Next year I will be doing my honours in mathematics.  One possible
topic for my thesis that I've thought of - and my supervisor is quite
enthused about - is to use graph theory to analyse various textual
sources, starting with source code but leaving the framework open
enough to be able to extend it to other sources (e.g. email address
books).

How I envisage it happening is that a parser would be used to find all
functions in the given code, treat these as nodes in the graph and
then use directed edges to indicate which functions call other
functions.  This resultant graph can then be analysed in various ways
suitable to the context (e.g. find that a library module can be split
into two since there are two completely separate trees present in the
graph that don't interact at all, or if a function is only ever called
by one other function then it can be subsumed into it).

So, here is the question I ask of all of you: is this feasible?  Do
you know if anything like this has ever been attempted before?  I know
there are some other usages of graph theory related to source code
(e.g. McCabes complexity metric [1]), but I couldn't seem to find
anything related to what I'm proposing.  I intend to code this up in
Haskell (possibly using FGL: I know of it, but haven't really looked
at it) and use Haskell as my primary target for analysis, so in a
sense the resultant graph could be seen as a Haskell equivalent to
UML.


[1] http://en.wikipedia.org/wiki/Cyclomatic_complexity

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


Re: [Haskell-cafe] Graph theory analysis of Haskell code

2007-12-05 Thread Tim Chevalier
On 12/5/07, Ivan Miljenovic [EMAIL PROTECTED] wrote:
 How I envisage it happening is that a parser would be used to find all
 functions in the given code, treat these as nodes in the graph and
 then use directed edges to indicate which functions call other
 functions.

aka a call graph. This is called control flow analysis and the
classic paper on it is Olin Shivers' dissertation, Control Flow
Analysis of Higher Order Languages
(http://repository.readscheme.org/ftp/papers/shivers-diss.ps.gz ).

 This resultant graph can then be analysed in various ways
 suitable to the context (e.g. find that a library module can be split
 into two since there are two completely separate trees present in the
 graph that don't interact at all, or if a function is only ever called
 by one other function then it can be subsumed into it).


One example of an analysis like this is done by GHC's inliner. See the
paper Secrets of the Glasgow Haskell Compiler Inliner by Peyton
Jones and Marlow
(http://research.microsoft.com/~simonpj/Papers/inlining/).


 So, here is the question I ask of all of you: is this feasible?  Do
 you know if anything like this has ever been attempted before?  I know
 there are some other usages of graph theory related to source code
 (e.g. McCabes complexity metric [1]), but I couldn't seem to find
 anything related to what I'm proposing.  I intend to code this up in
 Haskell (possibly using FGL: I know of it, but haven't really looked
 at it) and use Haskell as my primary target for analysis, so in a
 sense the resultant graph could be seen as a Haskell equivalent to
 UML.


This is very well-trodden ground, but if you familiarize yourself with
the literature on the subject, then who knows, you may discover
something new. And you can take pleasure in knowing that you've
already independently conceived of an idea that lots of smart people
have seen fit to put a lot of time into :-)

Cheers,
Tim

-- 
Tim Chevalier * catamorphism.org * Often in error, never in doubt
It's true I don't want to join the Army or turn lathes in precision
parts factories, I'm nearsighted and psychopathic anyway.  America I'm
putting my queer shoulder to the wheel.  -- Allen Ginsberg
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Janis Voigtlaender

See

http://doi.acm.org/10.1145/301631.301637

and

http://dx.doi.org/10.1016/S1571-0661(05)80288-9


Pablo Nogueira wrote:

Hasn't Ryan raised an interesting point, though?

Bottom is used to denote non-termination and run-time errors. Are they
the same thing? To me, they're not. A non-terminating program has
different behaviour from a failing program.

When it comes to strictness, the concept is defined in a particular
semantic context, typically an applicative structure:

  [[ f x ]] = App [[f]] [[x]]

Function f is strict if App [[f]] _|_ = _|_

Yet, that definition is pinned down in a semantics where what  _|_
models is clearly defined.

I don't see why one could not provide a more detailed semantics where
certain kinds of run-time errors are distinguished from bottom.
Actually, this already happens. Type systems are there to capture many
program properties statically. Some properties that can't be captured
statically are captured dynamically: the compiler introduces run-time
tests. Checking for non-termination is undecidable, but putting
run-time checks for certain errors is not.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



--
Dr. Janis Voigtlaender
http://wwwtcs.inf.tu-dresden.de/~voigt/
mailto:[EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-12-05 Thread Albert Y. C. Lai

Combinators get my code done, tralalalala, laughing out loud!
Quickcheck locates all of my bugs, tralalalala, laughing out loud!
Fusion laws make my code run fast, tralala, lalala, lololol!
Folks, I'm so done, Merry Christmas, tralalalala, laughing out loud!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Clean Dynamics and serializing code to disk

2007-12-05 Thread gwern0
On 2007.12.05 15:56:49 +0100, John van Groningen [EMAIL PROTECTED] scribbled 
0.7K characters:
 [EMAIL PROTECTED] wrote:

 Hey everyone; recently I've been toying around with various methods of 
 writing a shell and reading the academic literature on such things. The best 
 prior art on the subject seems to be the ESTHER shell (see 
 http://citeseer.ist.psu.edu/689593.html, 
 http://citeseer.ist.psu.edu/744494.html, 
 ftp://ftp.cs.kun.nl/pub/Clean/papers/2003/vWeA2003-Esther.pdf).
 
 Now, ESTHER is a really cool looking shell, but it has two main problems for 
 me:
 1) Source doesn't seem to be available anywhere online
 ...

 The source code of ESTHER is include with Clean 2.2 in the directory
 Libraries/Hilde of the windows 32 bit binary zip and the sources zip and tar.

 Kind regards,

 John van Groningen

Thanks for the information! I had no idea it'd be included with the Clean 
compiler package, but it's there alright. Interesting reading, too.

--
gwern


pgpBNEbAkyLnB.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] matching

2007-12-05 Thread Ryan Bloor
hi
 
I have a matching problem... I am wanting to identify whether or not a string 
is an opening substring of another (ignoring leading spaces). I have this:
word is a single word and str is a string.
 
match :: String - String - (Bool, String)match word str   | 
if removeSpace str `elem` (removeSpace word) ++ rest = (True, rest) 
 | otherwise == (False,str)  where rest = str
 
Any help?
 
Ryan  
 
 
_
The next generation of MSN Hotmail has arrived - Windows Live Hotmail
http://www.newhotmail.co.uk___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] matching

2007-12-05 Thread Luke Palmer
Just remove that if.  What comes after | is already a conditional.

Luke

On Dec 6, 2007 7:03 AM, Ryan Bloor [EMAIL PROTECTED] wrote:

 hi

  I have a matching problem... I am wanting to identify whether or not a
 string is an opening substring of another (ignoring leading spaces). I have
 this:
  word is a single word and str is a string.

  match :: String - String - (Bool, String)
 match word str
   | if removeSpace str `elem` (removeSpace word) ++ rest =
 (True, rest)
   | otherwise == (False,str)
   where rest = str

  Any help?

  Ryan




 
 Can you guess the film? Search Charades!
 ___
 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] matching

2007-12-05 Thread Luke Palmer
Oops, not quite.  otherwise == should be otherwise =.  Looks like
you already go this from the first one, but guard syntax looks like:

defn
  | cond1 = ...
  | cond2 = ...
  | ...
  | otherwise = ...

(otherwise is not actually necessary; it is just a synonym for True)

Luke

On Dec 6, 2007 7:09 AM, Luke Palmer [EMAIL PROTECTED] wrote:
 Just remove that if.  What comes after | is already a conditional.

 Luke


 On Dec 6, 2007 7:03 AM, Ryan Bloor [EMAIL PROTECTED] wrote:
 
  hi
 
   I have a matching problem... I am wanting to identify whether or not a
  string is an opening substring of another (ignoring leading spaces). I have
  this:
   word is a single word and str is a string.
 
   match :: String - String - (Bool, String)
  match word str
| if removeSpace str `elem` (removeSpace word) ++ rest =
  (True, rest)
| otherwise == (False,str)
where rest = str
 
   Any help?
 
   Ryan
 
 
 
 
  
  Can you guess the film? Search Charades!
  ___
  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