[Haskell-cafe] signals lib

2007-09-28 Thread brad clawsie
does System.POSIX.Signals bind to OS specific real-time POSIX signal
apis? (i.e., kqueue on freebsd).

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


Re: [Haskell-cafe] signals lib

2007-09-28 Thread Bryan O'Sullivan

brad clawsie wrote:

does System.POSIX.Signals bind to OS specific real-time POSIX signal
apis? (i.e., kqueue on freebsd).


No, just the usual portable signals.

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


Re: [Haskell-cafe] 'data' syntax - a suggestion

2007-09-28 Thread Bas van Dijk
On 9/28/07, ok [EMAIL PROTECTED] wrote:
 Now there's a paper that was mentioned about a month ago in this
 mailing list which basically dealt with that by splitting each type
 into two:  roughly speaking a bit that expresses the recursion and
 a bit that expresses the choice structure.

Would you like to give a link to that paper?


(the following is a bit offtopic)

In the 1995 paper[1]: Bananas in Space: Extending Fold and Unfold to
Exponential Types, Erik Meijer and Graham Hutton showed a interesting
technique:

Your ADT:

data Expr env = Variable (Var env)
  | Constant Int
  | Unary String (Expr env)
  | Binary String (Expr env) (Expr env)

can be written without recursion by using a fixpoint newtype
combinator (not sure if this is the right name for it):

newtype Rec f = In { out :: f (Rec f) }

data Var env = Var env String

data E env e = Variable (Var env)
 | Constant Int
 | Unary String e
 | Binary String e e

type Expr env = Rec (E env)

example = In (Binary + (In (Constant 1)) (In (Constant 2)))

You can see that you don't have to name the recursive 'Expr env'
explicitly. However constructing a 'Expr' is a bit verbose because of
the 'In' newtype constructors.

regards,

Bas van Dijk

[1] http://citeseer.ist.psu.edu/293490.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Dynamic choice of reverse implementation

2007-09-28 Thread Krzysztof Kościuszkiewicz
Fellow Haskellers,

I wanted to experiment a bit with lists and sequences (as in Data.List and
Data.Sequence), and I got stuck. I wanted to dynamically select processing
function depending on cmdline argument:

 main = do
 args - getArgs
 let reversor = case args of
 [sequence] - reverseList
 [list] - reverseSeq
 _ - error bad args
 input - getContents
 let output = reversor $ lines $ input
 mapM_ putStrLn output

In my oppinion reversor would have type

 reversor :: (Foldable f) = [a] - f b

but I couldn't get this to work. I've tried typeclass approach:

 class (Foldable f) = Reversor f where
 reverse' :: [a] - f a
 
 instance Reversor ([]) where
 reverse' = Data.List.reverse
 
 instance Reversor ViewR where
 reverse' = viewr . foldr (|) empty 

 reverseList = reverse' :: (???)
 reverseSeq  = reverse' :: (???)

but now in order to differentiate between reverse' functions I'd
have to provide different type annotations, and then reversor won't
typecheck...

Similar problem surfaced with this try:

 data Proc = SP | LP
 reverseList = reverse' LP
 reverseSeq = reverse' SP

 reverse' :: (Foldable f) = Proc - [a] - f a
 reverse' LP = Data.List.reverse
 reverse' SP = viewr . foldr (|) empty

So now I'm looking for some suggestions how should I approach the
problem...

Regards,
-- 
Krzysztof Kościuszkiewicz
Skype: dr.vee,  Gadu: 111851,  Jabber: [EMAIL PROTECTED]
Mobile IRL: +353851383329,  Mobile PL: +48783303040
Simplicity is the ultimate sophistication -- Leonardo da Vinci
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Dynamic choice of reverse implementation

2007-09-28 Thread Brian Hulley

Krzysztof Kościuszkiewicz wrote:

Fellow Haskellers,

I wanted to experiment a bit with lists and sequences (as in Data.List and
Data.Sequence), and I got stuck. I wanted to dynamically select processing
function depending on cmdline argument:

  

main = do
args - getArgs
let reversor = case args of
[sequence] - reverseList
[list] - reverseSeq
_ - error bad args
input - getContents
let output = reversor $ lines $ input
mapM_ putStrLn output



In my oppinion reversor would have type

  

reversor :: (Foldable f) = [a] - f b



  


No, this is the wrong type. To find the correct type, if you look at the 
type of the input argument in your code it will be the result of 
(lines), so from ghci:


Prelude :t lines
lines :: String - [String]
Prelude

Therefore (reverseor) has type [String] - ???
Now for the output type, you are using (output) as an input to (mapM_ 
putStrLn). (mapM_) takes a list and uses its argument to do something to 
each element of the list. So, since the input to (putStrLn) is (String), 
the input to (mapM_ putStrLn) is ([String]).

Therefore

   reversor :: [String] - [String]

So reverseList is just Data.List.reverse as you've got it (though 
presumably you meant to write [list] - reverseList and not reverseSeq).


For using Data.Sequence to implement reversor, all you need to do is 
first convert [String] to Seq String, reverse the sequence, then convert 
back from Seq String to [String].


Hope this helps,
Brian.



but I couldn't get this to work. I've tried typeclass approach:

  

class (Foldable f) = Reversor f where
reverse' :: [a] - f a

instance Reversor ([]) where
reverse' = Data.List.reverse

instance Reversor ViewR where
reverse' = viewr . foldr (|) empty 


reverseList = reverse' :: (???)
reverseSeq  = reverse' :: (???)



but now in order to differentiate between reverse' functions I'd
have to provide different type annotations, and then reversor won't
typecheck...

Similar problem surfaced with this try:

  

data Proc = SP | LP
reverseList = reverse' LP
reverseSeq = reverse' SP

reverse' :: (Foldable f) = Proc - [a] - f a
reverse' LP = Data.List.reverse
reverse' SP = viewr . foldr (|) empty



So now I'm looking for some suggestions how should I approach the
problem...

Regards,
  

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


Re: [Haskell-cafe] int to bin, bin to int

2007-09-28 Thread Brent Yorgey
On 9/27/07, PR Stanley [EMAIL PROTECTED] wrote:

 Hi
 intToBin :: Int - [Int]
 intToBin 1 = [1]
 intToBin n = (intToBin (n`div`2)) ++ [n `mod` 2]

 binToInt :: [Integer] - Integer
 binToInt [] = 0
 binToInt (x:xs) = (x*2^(length xs)) + (binToInt xs)
 Any comments and/or criticisms on the above definitions would be
 appreciated.
 Thanks , Paul


Others have already given many good suggestions, but I'll add something
specifically about the order of the bits in the result. You have the
generated list of bits in reading order, i.e. high-order bits first.  But
perhaps it would make more sense to have the low-order bits first?  At
least, it would be more efficient that way.  Then you could do

intToBin n = (n `mod` 2) : (intToBin (n `div` 2)

The way you have it now, you will end up with something like [1] ++ [0] ++
[0] ++ [1] ++ ... which ends up inefficiently traversing the list multiple
times.  To undo, just (for example)

binToInt xs = sum $ zipWith (*) xs (iterate (*2) 1).

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


[Haskell-cafe] agda v. haskell

2007-09-28 Thread brad clawsie
dons has been posting some links regarding agda on reddit. fairly
interesting, a quick glance and you think you are reading haskell
code.

does anyone have any insights on the major differences in these
languages?

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


Re: [Haskell-cafe] Dynamic choice of reverse implementation

2007-09-28 Thread Brian Hulley

Brian Hulley wrote:

Krzysztof Kościuszkiewicz wrote:

So the type of mapM_ used in the code is
(Foldable t, Monad m) = (a - m b) - t a - m ()

I'd like to keep the generic Foldable t there when m is specialized 
to IO.

I thought this would allow type of reversor to be specialized to
(Foldable f) = [String] - f String
  ... I'd like to avoid [a] - something - [a]


Yes this type should be fine.


I should have said though that in your code, because one arm of the case 
construct returns Data.List.reverse, the type of reversor is fixed to 
[a] - [a].


The other arm of the case construct could make use of a more general 
function eg


   reverseFoldable :: (Foldable f, Foldable g) = f a - g a

but it would only be used at f == [], g == [].

So in terms of the command line test harness, I think the only way is to 
explicitly choose the foldable you want to try out eg by using 
(Foldable.toList . Seq.reverse . Seq.fromList) etc.


An alternative might be to just write some different implementations of 
reverse functions in a module then load the module into ghci to test 
them out interactively so their types don't get unified with each other.


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


Re: [Haskell-cafe] Packages and how to load them

2007-09-28 Thread Henning Thielemann


On Thu, 27 Sep 2007, bbrown wrote:


If I have a set of haskell code and I create a directory with the source that
has the following imports.

(some_dir/MyLib.hs)
module MyLib where

And then I want to use that set of code at the top level directory, eg:

MyTest.hs

import MyLib

How would I compile with ghc such that it loads the code from some_dir
without it having to have the module as module some_dir.MyLib.  I think
this is a basic packaging question but couldnt figure it out.


If you intend to write a library, you might also want to check Cabal.
  http://www.haskell.org/haskellwiki/How_to_write_a_Haskell_program
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] agda v. haskell

2007-09-28 Thread Dan Doel
On Friday 28 September 2007, brad clawsie wrote:
 dons has been posting some links regarding agda on reddit. fairly
 interesting, a quick glance and you think you are reading haskell
 code.

 does anyone have any insights on the major differences in these
 languages?

I'm not too familiar with Agda, but I believe it's one of the dependently 
typed functional languages/theorem provers that more and more people are 
growing interested in these days. If you want to know what all that sort of 
hype is about, you might want to read Why Dependent Types Matter [1] by the 
Epigram folks, which does a pretty good job explaining what you might want 
them for.

Or, if you want an even shorter explanation, imagine the sort of type-system 
programming that Oleg does, and then imagine languages that attempt to make 
that sort of thing as easy as the ordinary programming you do (or, get it 
closer to there, at least).

-- Dan

[1]: http://e-pig.org/downloads/ydtm.pdf
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Dynamic choice of reverse implementation

2007-09-28 Thread Ross Paterson
On Fri, Sep 28, 2007 at 05:54:23PM +0100, Brian Hulley wrote:
 Yes this type should be fine. To implement reversor though you'd still need 
 to first convert from the concrete list to whatever foldable you're using, 
 before reversing the foldable, or implement something more general eg:

 reversor :: (Foldable f, Foldable g) :: f a - g a

One cannot define such a function, as Foldable provides no way to build
things.  However one can define

reversor :: Traversable f = f a - f a

which returns something of the same shape, but with the contents reversed.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Dynamic choice of reverse implementation

2007-09-28 Thread Krzysztof Kościuszkiewicz
On Fri, Sep 28, 2007 at 04:38:35PM +0100, Brian Hulley wrote:

  In my oppinion reversor would have type
   
  reversor :: (Foldable f) = [a] - f b
 

 No, this is the wrong type. To find the correct type, if you look at the 
 type of the input argument in your code it will be the result of 
 (lines), so from ghci:
 
 Prelude :t lines
 lines :: String - [String]
 Prelude
 
 Therefore (reverseor) has type [String] - ???
 Now for the output type, you are using (output) as an input to (mapM_ 
 putStrLn). (mapM_) takes a list and uses its argument to do something to 
 each element of the list.

True. I forgot to mention imports in my code:

 import Prelude hiding (foldr, foldr1, reverse, mapM_)
 import System.Environment
 import Data.List hiding (foldr, foldr1)
 import Data.Foldable
 import Data.Traversable
 import Data.Sequence

So the type of mapM_ used in the code is
(Foldable t, Monad m) = (a - m b) - t a - m ()

I'd like to keep the generic Foldable t there when m is specialized to IO.
I thought this would allow type of reversor to be specialized to
(Foldable f) = [String] - f String

 For using Data.Sequence to implement reversor, all you need to do is 
 first convert [String] to Seq String, reverse the sequence, then convert 
 back from Seq String to [String].

Yes, probably that's how it works under the hood, but the reason I mentioned
Foldable is that I'd like to avoid [a] - something - [a], but keep the
type of output value from reversor abstract... For no particular reason,
just playing with this idea :)

Regards,
-- 
Krzysztof Kościuszkiewicz
Skype: dr.vee,  Gadu: 111851,  Jabber: [EMAIL PROTECTED]
Mobile IRL: +353851383329,  Mobile PL: +48783303040
Simplicity is the ultimate sophistication -- Leonardo da Vinci
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] agda v. haskell

2007-09-28 Thread Jeff Polakow
Hello,

  Agda is essentially an implementation of a type checker for Martin-Lof 
type theory (i.e. dependent types). 

  It is designed to be used as a proof assistant. Roughly speaking 
propositions are represented as types and a proof of a proposition is a 
well-typed, total and terminating function. Agda has machinery to help you 
fill in cases and generally make proof construction easier.

  Agda is different from Haskell in that Agda has dependent types and 
machinery for interactively constructing the definition of a function at a 
given type.

  Agda is also different from Haskell in that the focus is on the user 
interface and writing the proof/program itself, rather than on executing 
the resulting code (i.e. little work has gone into compiling Agda code).

  I think there have been several projects scattered around on generating 
Haskell from Agda and on importing Haskell code into Agda for formal 
verification.

-Jeff

[EMAIL PROTECTED] wrote on 09/28/2007 11:41:41 AM:

 dons has been posting some links regarding agda on reddit. fairly
 interesting, a quick glance and you think you are reading haskell
 code.
 
 does anyone have any insights on the major differences in these
 languages?
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Dynamic choice of reverse implementation

2007-09-28 Thread Brian Hulley

Krzysztof Kościuszkiewicz wrote:

So the type of mapM_ used in the code is
(Foldable t, Monad m) = (a - m b) - t a - m ()

I'd like to keep the generic Foldable t there when m is specialized to IO.
I thought this would allow type of reversor to be specialized to
(Foldable f) = [String] - f String
  
... I'd like to avoid [a] - something - [a]


Yes this type should be fine. To implement reversor though you'd still 
need to first convert from the concrete list to whatever foldable you're 
using, before reversing the foldable, or implement something more 
general eg:


reversor :: (Foldable f, Foldable g) :: f a - g a

Of course with lazy evaluation + compiler optimizations the lists in [a] 
- something - [a] should be erased at compile time... ;-)


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


Re: [Haskell-cafe] Dynamic choice of reverse implementation

2007-09-28 Thread David Benbennick
On 9/28/07, Ross Paterson [EMAIL PROTECTED] wrote:
 However one can define

 reversor :: Traversable f = f a - f a

 which returns something of the same shape, but with the contents reversed.

How?  Is it possible to define a version of foldl for Traversable?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newb question about map and a list of lists

2007-09-28 Thread Jonathan Cast
On Fri, 2007-09-28 at 11:19 -0700, Chuk Goodin wrote:
 I have a list of lists of pairs of numeric Strings (like this:
 [[2,3],[1,2],[13,14]] etc.) I'd like to change it into a
 list of a list of numbers, but I'm not sure how to go about it. If it
 was just one list, I could use map, but map.map doesn't seem to work.
 Any suggestions, or pointers to a reference online?

map :: (a - b) - [a] - [b], so
map . map :: (a - b) - [[a]] - [[b]]

which is right.  Just be sure to put it in parentheses before you apply
it to anything.  If you need more help, more information on what you did
and what happened would be appreciated.

jcc


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


[Haskell-cafe] Newb question about map and a list of lists

2007-09-28 Thread Chuk Goodin
I have a list of lists of pairs of numeric Strings (like this:
[[2,3],[1,2],[13,14]] etc.) I'd like to change it into a list of
a list of numbers, but I'm not sure how to go about it. If it was just one
list, I could use map, but map.map doesn't seem to work. Any suggestions, or
pointers to a reference online?

thanks in advance,

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


Re: [Haskell-cafe] Dynamic choice of reverse implementation

2007-09-28 Thread Dan Doel
On Friday 28 September 2007, David Benbennick wrote:
 On 9/28/07, Ross Paterson [EMAIL PROTECTED] wrote:
  However one can define
 
  reversor :: Traversable f = f a - f a
 
  which returns something of the same shape, but with the contents
  reversed.

 How?  Is it possible to define a version of foldl for Traversable?

At the very least, you can do this:

{-# LANGUAGE FlexibleContexts #-}

import Prelude hiding (mapM)
import Control.Monad   hiding (mapM)
import Control.Monad.State hiding (mapM)

import Data.Foldable(toList)
import Data.Traversable (mapM, Traversable(..))

reversor :: Traversable t = t a - t a
reversor t = evalState (mapM (const pick) t) (reverse $ toList t)

pick :: MonadState [a] m = m a
pick = do (h:t) - get ; put t ; return h

There may be something nicer out there, though.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newb question about map and a list of lists

2007-09-28 Thread Jules Bean

Chuk Goodin wrote:
I have a list of lists of pairs of numeric Strings (like this: 
[[2,3],[1,2],[13,14]] etc.) I'd like to change it into a 
list of a list of numbers, but I'm not sure how to go about it. If it 
was just one list, I could use map, but map.map doesn't seem to work. 
Any suggestions, or pointers to a reference online?



Your instinct to use map.map is correct.

Just be careful to write:

(map.map) read l

or

map.map $ read l

beware that:

map.map read l

is parsed as map.(map read l)...

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


Re: [Haskell-cafe] Newb question about map and a list of lists

2007-09-28 Thread Bas van Dijk
On 9/28/07, Chuk Goodin [EMAIL PROTECTED] wrote:
 I have a list of lists of pairs of numeric Strings (like this:
 [[2,3],[1,2],[13,14]] etc.) I'd like to change
 it into a list of a list of numbers...

Now that you know (map . map) which Jonathan explained you need to
apply that to a function that converts 'String's to 'Int's.

You can write this function yourself or use hoogle [1] to search for a
function in the standard library that does what you want.

(If you now what type classes are you don't have to read any further)


Hint: the reverse of the function you are looking for is called 'show'
and its type is 'Show a = a - String'.

Why isn't the type of 'show' just 'Int - String'? Well you probably
not only want to convert Ints to Strings but also Floats to Strings,
Doubles to Strings, Foo's to String, Bars to Strings, ... So you want
to have a function called 'show' that is overloaded to work on any
type that can be 'Show'n.

To declare an overloaded function in Haskell you should define a type
class, like this:

class Show a where
  show :: a - String

This declares a class of types called 'Show' for which a function
'show' is defined which converts a value of that type into a 'String'.

Now you should provide actual definitions of 'show' for the types you
want to show. These are called instance declarations:

instance Show Int where
  show n = ... code that actually converts the Int 'n' to a 'String'...

instance Show Float where
  show f = ... code that actually converts the Float 'f' to a 'String'...

Now you can use the function 'show' to convert Ints and Floats to Strings. Nice!

Of course you are looking for the reverse of 'show', good luck searching...

regards,

Bas.


[1] Hoogle, The Haskell API Search Engine: http://haskell.org/hoogle
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newb question about map and a list of lists

2007-09-28 Thread Brent Yorgey
 Just be careful to write:

 (map.map) read l

 or

 map.map $ read l


actually, map . map $ read l does not work, that's the same as (map . map)
(read l), whereas (map . map) read l is the same as ((map . map) read) l.
My guess is that Jules wrote that part while asleep. =)

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


Re: [Haskell-cafe] Opengl and Haskell GLdouble/GLfloat vs. Double/Float

2007-09-28 Thread Jules Bean

bbrown wrote:
I am going to be doing a lot of opengl stuff in haskell and so far one thing 
has irked me.  Why does haskell keep the GLFloat and GL types and not just 
the Haskell types.  


It mirrors the C API in doing so.

I assume that this is because, in principle a system might exist where 
the graphics card (and hence, openGL library) used different-precision 
numbers to the CPU.  Perhaps 32bit card on a 64bit machine gives you 
32bit GLints even though you have 64 bit ints?


I don't know how often (if ever) this happens in practice.

Certainly GLfloat, GLdouble, GLint are members of all the type classes 
you would hope them to be and they are no less convenient to use.


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


Re: [Haskell-cafe] Opengl and Haskell GLdouble/GLfloat vs. Double/Float

2007-09-28 Thread Bas van Dijk
On 9/28/07, Jules Bean [EMAIL PROTECTED] wrote:
 Certainly GLfloat, GLdouble, GLint are members of all the type classes
 you would hope them to be and they are no less convenient to use.

And so, if you need it, you can always coerce between the GL and the
standard Haskell types by using the general coercion functions:
'fromIntegral' and 'realToFrac'.

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


Re: [Haskell-cafe] Dynamic choice of reverse implementation

2007-09-28 Thread Ryan Ingram
Here's the problem:
   In my oppinion reversor would have type
  
reversor :: (Foldable f) = [a] - f a

The type of reversor you state is equivalent to
   forall f a. (Foldable f) = [a] - f a

but reverseList has the type
   forall a. [a] - [a]
and reverseSeq has the type
   forall a. [a] - Seq a

What you mean instead is
   forall a. exists f. (Foldable f) = [a] - f a

but that type isn't directly supported in Haskell.  Instead, you need
to wrap it in an existential constructor:

 {-# LANGUAGE ExistentialQuantification #-}
 module Main where
 import Prelude hiding (foldr, foldr1, reverse, mapM_)
 import System.Environment
 import Data.List hiding (foldr, foldr1)
 import Data.Foldable
 import Data.Traversable
 import Data.Sequence

 data Rev a = forall f. Foldable f = Rev ([a] - f a)

in this case,
Rev :: forall f a. Foldable f = ([a] - f a) - Rev a

Once you have this, the rest of the implementation is pretty simple:

 mkReversor :: [String] - Rev a
 mkReversor [sequence] = Rev reverseSeq
 mkReversor [list] = Rev reverseList
 mkReversor _ = error bad args

 reverseList :: [a] - [a]
 reverseList = Data.List.reverse

 reverseSeq :: [a] - Seq a
 reverseSeq = foldr (|) empty

 main = do
 args - getArgs
 (Rev reversor) - return (mkReversor args)
 input - getContents
 let output = reversor $ lines $ input
 mapM_ putStrLn output

This line is particularily interesting:
(Rev reversor) - return (mkReversor args)

Replacing it with the more obvious
let reversor = mkReversor args
causes the best error message in the history of compilers:
My brain just exploded.
I can't handle pattern bindings for existentially-quantified constructors.

The reason why the - return construct works is because it desugars
differently (and more strictly):

return (mkReversor args) = \r -
case r of
(Rev reversor) - do (rest of do block)
_ - fail Pattern match failure

which binds the type of reversor in a case statement; Simon
Peyton-Jones says it's not obvious how to write a typing rule for
let-bindings.

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


[Haskell-cafe] Newb: List of nodes in a graph - is there a prettier way?

2007-09-28 Thread Torsten Otto

Howdy,

I'm working towards Dijkstra's algorithm here and I have a feeling  
that I could do without the helper function nodesInternal in the  
following code, if I only could figure out how. Any hints would be  
appreciated.


nodes::Graph-[Id] should (and actually does) return a list of all  
nodes in the graph.


Thanks a bunch in advance.
Regards,
Torsten Otto


module Route where

Datatypes for the representation of the graph:

type Id = Int
type Weight = Int
type Edge = (Id,Id)
type Graph = [ (Edge, Weight) ]

graph::Graph
graph =  [ ((0,1),1),
((0,2),3),
((0,4),6),
((1,2),1),
((1,3),3),
((2,0),1),
((2,1),2),
((2,3),1),
((3,0),3),
((3,4),2),
((4,3),1),
((5,2),9)]

data Cost = Finite Weight | Infinity
deriving (Eq, Ord, Show)

type PathCost = (Cost, Id)

Return the number of edges in the graph:

edges :: Graph - Int
edges graph = length graph

Calculate the sum of all weights:

weightTotal::Graph - Weight
weightTotal ((edge, weight):xs)| xs == []   = weight
| otherwise = 
weight + (weightTotal xs)

List all the nodes in the graph:

nodes::Graph - [Id]   
  
nodes graph = nodesInternal [] graph

nodesInternal::[Id]-Graph-[Id]
nodesInternal list (((id1,id2),weight):xs)  
| (elem id1 list)  (elem id2 list)= nodesInternal 
list xs
		| (elem id1 list)  (not (elem id2 list))	= nodesInternal  
(id2:list) xs
		| (not (elem id1 list))  (elem id2 list)	= nodesInternal  
(id1:list) xs
		| (not (elem id1 list))  (not (elem id2 list))	= nodesInternal  
(id1:id2:list) xs

nodesInternal list []   = list

Function for adding costs so that we can make use of Infinity for  
impossible routes:


addCosts::Cost - Cost - Cost
addCosts Infinity Infinity  = Infinity
addCosts Infinity (Finite x)= Infinity
addCosts (Finite x) Infinity= Infinity
addCosts (Finite x) (Finite y) = Finite (x + y)

Return the cost of a given edge:

lookUp::Edge - Graph - Cost
lookUp (id1,id2) (((id1x,id2x),weightx):xs) 
| (id1==id1x  id2==id2x)  = Finite weightx
| xs==[]= Infinity
| otherwise = lookUp (id1,id2) 
xs







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


Re: [Haskell-cafe] Newb: List of nodes in a graph - is there a prettier way?

2007-09-28 Thread Dan Weston

If I haven't mistaken what you're asking for, how about:

  import Data.Set as S
  nodes = foldr (\(a,b) - S.insert a . S.insert b) S.empty

Torsten Otto wrote:

Howdy,

I'm working towards Dijkstra's algorithm here and I have a feeling that 
I could do without the helper function nodesInternal in the following 
code, if I only could figure out how. Any hints would be appreciated.


nodes::Graph-[Id] should (and actually does) return a list of all nodes 
in the graph.


Thanks a bunch in advance.
Regards,
Torsten Otto


 module Route where

Datatypes for the representation of the graph:

 type Id = Int
 type Weight = Int
 type Edge = (Id,Id)
 type Graph = [ (Edge, Weight) ]

 graph::Graph
 graph =  [ ((0,1),1),
 ((0,2),3),
 ((0,4),6),
 ((1,2),1),
 ((1,3),3),
 ((2,0),1),
 ((2,1),2),
 ((2,3),1),
 ((3,0),3),
 ((3,4),2),
 ((4,3),1),
 ((5,2),9)]

 data Cost = Finite Weight | Infinity
 deriving (Eq, Ord, Show)
   
 type PathCost = (Cost, Id)


Return the number of edges in the graph:

 edges :: Graph - Int
 edges graph = length graph

Calculate the sum of all weights:

 weightTotal::Graph - Weight
 weightTotal ((edge, weight):xs)| xs == [] = weight
 | otherwise= weight + (weightTotal 
xs)
   
List all the nodes in the graph:   
   
 nodes::Graph - [Id]   
 nodes graph = nodesInternal [] graph


 nodesInternal::[Id]-Graph-[Id]
 nodesInternal list (((id1,id2),weight):xs)   
 | (elem id1 list)  (elem id2 list)= nodesInternal 
list xs
 | (elem id1 list)  (not (elem id2 list))= nodesInternal 
(id2:list) xs
 | (not (elem id1 list))  (elem id2 list)= nodesInternal 
(id1:list) xs
 | (not (elem id1 list))  (not (elem id2 list))= 
nodesInternal (id1:id2:list) xs

 nodesInternal list []= list

Function for adding costs so that we can make use of Infinity for 
impossible routes:


 addCosts::Cost - Cost - Cost
 addCosts Infinity Infinity= Infinity
 addCosts Infinity (Finite x) = Infinity
 addCosts (Finite x) Infinity= Infinity
 addCosts (Finite x) (Finite y) = Finite (x + y)

Return the cost of a given edge:

 lookUp::Edge - Graph - Cost
 lookUp (id1,id2) (((id1x,id2x),weightx):xs)   
 | (id1==id1x  id2==id2x)= Finite weightx

 | xs==[]= Infinity
 | otherwise= lookUp (id1,id2) xs


   





___
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] Newb: List of nodes in a graph - is there a prettier way?

2007-09-28 Thread Dan Weston

Of course, if you want the result as a list instead of a set:

  nodeList = S.toList . nodes

Dan Weston wrote:

If I haven't mistaken what you're asking for, how about:

  import Data.Set as S
  nodes = foldr (\(a,b) - S.insert a . S.insert b) S.empty

Torsten Otto wrote:

Howdy,

I'm working towards Dijkstra's algorithm here and I have a feeling 
that I could do without the helper function nodesInternal in the 
following code, if I only could figure out how. Any hints would be 
appreciated.


nodes::Graph-[Id] should (and actually does) return a list of all 
nodes in the graph.


Thanks a bunch in advance.
Regards,
Torsten Otto


 module Route where

Datatypes for the representation of the graph:

 type Id = Int
 type Weight = Int
 type Edge = (Id,Id)
 type Graph = [ (Edge, Weight) ]

 graph::Graph
 graph =  [ ((0,1),1),
 ((0,2),3),
 ((0,4),6),
 ((1,2),1),
 ((1,3),3),
 ((2,0),1),
 ((2,1),2),
 ((2,3),1),
 ((3,0),3),
 ((3,4),2),
 ((4,3),1),
 ((5,2),9)]

 data Cost = Finite Weight | Infinity
 deriving (Eq, Ord, Show)
type PathCost = (Cost, Id)

Return the number of edges in the graph:

 edges :: Graph - Int
 edges graph = length graph

Calculate the sum of all weights:

 weightTotal::Graph - Weight
 weightTotal ((edge, weight):xs)| xs == [] = weight
 | otherwise= weight + 
(weightTotal xs)
   List all the nodes in the graph:   
nodes::Graph - 
[Id]nodes graph = nodesInternal [] graph


 nodesInternal::[Id]-Graph-[Id]
 nodesInternal list (((id1,id2),weight):xs)| (elem id1 
list)  (elem id2 list)= nodesInternal list xs
 | (elem id1 list)  (not (elem id2 list))= 
nodesInternal (id2:list) xs
 | (not (elem id1 list))  (elem id2 list)= 
nodesInternal (id1:list) xs
 | (not (elem id1 list))  (not (elem id2 list))= 
nodesInternal (id1:id2:list) xs

 nodesInternal list []= list

Function for adding costs so that we can make use of Infinity for 
impossible routes:


 addCosts::Cost - Cost - Cost
 addCosts Infinity Infinity= Infinity
 addCosts Infinity (Finite x) = Infinity
 addCosts (Finite x) Infinity= Infinity
 addCosts (Finite x) (Finite y) = Finite (x + y)

Return the cost of a given edge:

 lookUp::Edge - Graph - Cost
 lookUp (id1,id2) (((id1x,id2x),weightx):xs)| (id1==id1x 
 id2==id2x)= Finite weightx

 | xs==[]= Infinity
 | otherwise= lookUp (id1,id2) xs


  




___
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] Newb: List of nodes in a graph - is there a prettier way?

2007-09-28 Thread Ryan Ingram
Take a look in Data.List, in particular nub, unzip, and map.

You may also be interested in this function from the Prelude:
fst :: (a,b) - a
fst (a,_) = a

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


[Haskell-cafe] some simple proof exercises

2007-09-28 Thread Tim Newsham

Here are two small problem sets of proofs of Haskell functions.
They are aimed at people who do not have experience writing proofs
and are not necessarily well versed in Haskell.  Feedback is appreciated.

http://www.thenewsh.com/%7Enewsham/formal/problems/set1.html
http://www.thenewsh.com/%7Enewsham/formal/problems/set2.html

Tim Newsham
http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] some simple proof exercises

2007-09-28 Thread Michaeljohn Clement
 http://www.thenewsh.com/%7Enewsham/formal/problems/set1.html

In P2 there is a typo:

 8:  Assume: xs ++ [] = zsindhypothesis
 ^^

I know very little Haskell but the proofs were nonetheless easy enough
to follow.

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


[Haskell-cafe] Yampa question

2007-09-28 Thread Ryan Ingram
I'm deriving an FRP implementation based on the ideas presented in the
Yampa Arcade paper
(http://www.haskell.org/yale/papers/haskell-workshop03/) to improve my
understanding of arrows, but I have a couple of questions.

I'm using the following declaration for SF:

 type DTime = Double
 newtype SF a b = SF { runSF :: DTime - a - (b, SF a b) }

which I make an arrow in the obvious way:

 instance Arrow SF where
 arr f = SF sf where
 sf dt b = (f b, SF sf)
 bc  cd = SF sf where
 sf dt b = (d, bc'  cd') where
 (c, bc') = runSF bc dt b
 (d, cd') = runSF cd dt c
 first bc = SF sf where
 sf dt ~(b,d) = ((c,d), sfFirst bc') where
 (c, bc') = runSF bc dt b

One question I had was about the implementation of first.  Is it
important that the pair match be lazy?  Or is it safe to make it
strict?  What are the advantages and disadvantages of each choice?

My other question had to do with ArrowChoice.

 instance ArrowChoice SF where
 left bc = SF sf where
 sf dt (Right d) = (Right d, left bc)
 sf dt (Left b) = (Left c, left bc') where
 (c, bc') = runSF bc dt b

What happens to the dt in the Right d case?  It seems to be
invisible to the inner signal function.  Is this the right thing to
do?

I have an alternate implementation which does the following:

 sf dt (Right d) = (Right d, left $ addtime dt bc)

 addtime :: DTime - SF a b - SF a b
 addtime add sf = SF sf' where
sf' dt a = runSF sf (dt + add) a

but there's a pretty clear space leak here with repeated Right
calls, and I'm not sure if the inner signal should see the lost time
or not.

Perhaps signal functions shouldn't be an instance of ArrowChoice at all?

Any insights would be appreciated.

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