[Haskell-cafe] Re: Closest analog to popen()

2005-04-13 Thread Peter Simons
Dimitry Golubovsky writes:

  Does there exist any analog of popen in the standard Haskell libraries?

Maybe System.Process.runInteractiveCommand is what you need?

http://haskell.org/ghc/docs/latest/html/libraries/base/System.Process.html

Peter



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


Re: [Haskell-cafe] Binary file r/w example

2005-04-13 Thread Cale Gibbard
Ptr is defined in the FFI, which is documented here: 
http://www.cse.unsw.edu.au/~chak/haskell/ffi/
and also in the GHC documentation:
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Foreign.Ptr.html

I haven't done much binary IO, so I'll let someone else handle that,
but there are some libraries for doing binary IO in Haskell linked
from here:
http://www.haskell.org/hawiki/BinaryIo

 - Cale

On 4/13/05, Bo Herlin [EMAIL PROTECTED] wrote:
 Yes, I am, and the IOExtension module IS one of my problems.
 The other problem is that I am interested in this Ptr thing, and I
 havent seen any examples in using it, and is seems like Ptr is not in
 any of my Haskell-books or in any of the tutorials that I have found.
 
 Henning Thielemann wrote:
 
  On Wed, 13 Apr 2005, Bo Herlin wrote:
 
  Hi, does anyone have a small but complete example on how to read a
  (portion of) a binary file, like r/w the header of a Midi-file?
 
  It seems like readBinaryFile (ans writeBinaryFile) is deprecated and I
  should use hGetBuf (and hPutBuf), but what is this Ptr thing?
 
  How would I implement readBinaryFile using hGetBuf?
 
 
 
  Are you aware of Haskore (www.haskell.org/haskore and
  cvs.haskell.org/darcs/haskore) which provides a MidiFile reader and
  writer? It has no good solution for reading and writing binary files,
  but uses a platform dependent IOExtension module. :-(
 
 ___
 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] Installing and running QuickCheck

2005-04-13 Thread adam
Hi Daniel,

Yes, importing Data.Char worked, but revealed other problems.  Now I get the
following.

ERROR C:\Program Files\Hugs98\libraries\QuickCheck.hs:161 - Undefined variable
 fromInt
Monad

This, however, I have seen before, and it has to do with different versions of
Prelude, where fromInt was removed and fromInteger put in.  From hugs-bugs, we
find that we need to just change fromInt to fromInteger on the appropriate
line.

http://www.haskell.org/pipermail/hugs-bugs/2005-January/001537.html


So, starting with line 160 of QuickCheck.hs should read:

instance Arbitrary Integer where
  arbitrary = sized $ \n - choose (-fromIntegral n,fromIntegral n)
  coarbitrary n = variant (fromInteger (if n = 0 then 2*n else 2*(-n) + 1))

And with these two changes, QuickCheck compiles.  Now I have to see how it
works.

Thanks,
Adam

Quoting Daniel Fischer [EMAIL PROTECTED]:

 Hm,

 no instance Arbitrary Char is provided in the QuickCheck modules that came
 with my hugs or ghc. Probably the author just forgot to import Data.Char. Try
 inserting that in QuickCheck.hs.

 Hope that works,
 Daniel


This message was sent using IMP, the Internet Messaging Program.

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


[Haskell-cafe] [Q] A typing problem

2005-04-13 Thread Didier Verna

Hi !

I'm trying to write a function that combines folding and mapping. This
function would take two arguments (a folding function and a mapping function),
and would return a function of one argument (a list of 'a''s) returning a 'a'.

The idea is to write something like sumsquare = foldmap (+) square

Here's what I write:

foldmap :: (c - c - c) - (c - c) - (c - c - c)
foldmap f m = foldr1 f (map m)

But this gives a typing error:

ERROR src/ssq4.hs:2 - Type error in application
*** Expression : foldr1 f (map m)
*** Term   : map m
*** Type   : [b] - [b]
*** Does not match : [a]


What can I do to get what I want ?

Thanks.

--
Didier Verna, [EMAIL PROTECTED], http://www.lrde.epita.fr/~didier

EPITA / LRDE, 14-16 rue Voltaire   Tel.+33 (1) 44 08 01 85
94276 Le Kremlin-Bicêtre, France   Fax.+33 (1) 53 14 59 22   [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Q] A typing problem

2005-04-13 Thread Henning Thielemann
On Wed, 13 Apr 2005, Didier Verna wrote:
I'm trying to write a function that combines folding and mapping. This
function would take two arguments (a folding function and a mapping function),
and would return a function of one argument (a list of 'a''s) returning a 'a'.
The idea is to write something like sumsquare = foldmap (+) square
Here's what I write:
foldmap :: (c - c - c) - (c - c) - (c - c - c)
foldmap f m = foldr1 f (map m)

Do you mean
foldmap :: (b - b - b) - (a - b) - [a] - b
foldmap f m = foldr1 f . map m
?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] foldr1 min [(maxBound::Int)%1,1 % 2]

2005-04-13 Thread Bo Herlin
Hi
How come
 foldr1 min [(maxBound::Int) % 1,1 % 2]
2147483647 % 1
but
 foldr1 min [2147483647 % 1,1 % 2]
1 % 2
Why???
/Bo Herlin
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] foldr1 min [(maxBound::Int)%1,1 % 2]

2005-04-13 Thread Henning Thielemann
On Wed, 13 Apr 2005, Bo Herlin wrote:
Hi
How come
foldr1 min [(maxBound::Int) % 1,1 % 2]
2147483647 % 1
I guess that
  foldr1 min == minimum
but
foldr1 min [2147483647 % 1,1 % 2]
1 % 2
Why???
The first one certainly causes an overflow with machine word Ints whereas 
2147483647 is an Integer and thus all other numbers are interpreted as 
Integers.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] foldr1 min [(maxBound::Int)%1,1 % 2]

2005-04-13 Thread Cale Gibbard
Hmm...
let a = (maxBound :: Int)%1 in 1  a  a  1/2 
 == True

From the Ord instance for Ratio a
(x:%y)   (x':%y')  =  x * y'   x' * y

So the comparison for 1  a looks like
1 * 1  (maxBound :: Int) * 1
which is true.
And the comparison for a  1/2 looks like
(maxBound :: Int) * 2  1 * 1
== -2  1
which is again true!

If you want well-behaved rationals, I suppose you have to use Ratio Integer.

Hope this helps,
 - Cale

On 4/13/05, Bo Herlin [EMAIL PROTECTED] wrote:
 Hi
 
 How come
 
   foldr1 min [(maxBound::Int) % 1,1 % 2]
 2147483647 % 1
 
 but
 
   foldr1 min [2147483647 % 1,1 % 2]
 1 % 2
 
 Why???
 
 /Bo Herlin
 ___
 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] [Q] A typing problem

2005-04-13 Thread Claus Reinke
I'm trying to write a function that combines folding and mapping

a map is a fold:)

idList = foldr (:) []
map f = foldr ((:) . f) []

 foldmap :: (b - b - b) - (a - b) - [a] - b
 foldmap f m = foldr1 f . map m

alternatively, and dealing with empty lists as well

foldmap op n f = foldr (op . f) n

cheers,
claus


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


[Haskell-cafe] Passing Constructors as arguments

2005-04-13 Thread Ralph Hodgson




I am learning Haskell and have set a small exercise for myself on a
frames and slots program. 
Would appreciate some help on how to pass constructors of data
structures as arguments to a function. 

Thanks,

-- Ralph
__

A
Frames test


 module Frames

 where


Define frame slots:


 type FirstName = String -- first name

 type LastName = String -- last name

 type Organization = String

 type Email = String

 type WorkPhone = String

 type CellPhone = String

 type TelephoneNumber = String


Define slots for a contact


 data ContactProperty = FN FirstName

 | LN LastName

 | OR Organization

 | EM Email

 | WP TelephoneNumber

 | MP TelephoneNumber

 deriving (Show, Eq)


 data Contact = Contact [ContactProperty]

 deriving (Show, Eq)


 type Contacts = [ Contact]


Now I need a way to extract properties from the frame. Start by testing
pattern matching

without using parameters. Then I need to find out how to pass a
constructor as a parameter.


 getProperty:: [ContactProperty] - FirstName

 getProperty ((FN fn):_) = fn

 getProperty (_:xs) = getProperty xs

 getProperty [] = "unknown"


 firstName:: Contact - FirstName

 firstName (Contact cpl) = getProperty cpl



Define Contacts


 c1::Contacts

 c1 =

 [ ( Contact [(FN "Ralph"),(LN "Hodgson"),(OR "TopQuadrant"),(EM "[EMAIL PROTECTED]")]),

 ( Contact [(FN "Mills"),(LN "Davis"),(EM "[EMAIL PROTECTED]")])]


Tests


 t1=firstName $ head c1 -- should be "Ralph"

 t2=firstName $ last c1 -- should be "Mills"

___











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


Re: [Haskell-cafe] foldr1 min [(maxBound::Int)%1,1 % 2]

2005-04-13 Thread Bo Herlin
Hmm, too simple :-P   ...Thanks
Henning Thielemann wrote:
On Wed, 13 Apr 2005, Bo Herlin wrote:
Hi
How come
foldr1 min [(maxBound::Int) % 1,1 % 2]
2147483647 % 1

I guess that
  foldr1 min == minimum
but
foldr1 min [2147483647 % 1,1 % 2]
1 % 2
Why???

The first one certainly causes an overflow with machine word Ints 
whereas 2147483647 is an Integer and thus all other numbers are 
interpreted as Integers.

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


Re: [Haskell-cafe] foldr1 min [(maxBound::Int)%1,1 % 2]

2005-04-13 Thread Bo Herlin
Yep, got it, Thanks!
Cale Gibbard wrote:
Hmm...
let a = (maxBound :: Int)%1 in 1  a  a  1/2 
 == True

From the Ord instance for Ratio a
(x:%y)   (x':%y')  =  x * y'   x' * y
So the comparison for 1  a looks like
1 * 1  (maxBound :: Int) * 1
which is true.
And the comparison for a  1/2 looks like
(maxBound :: Int) * 2  1 * 1
== -2  1
which is again true!
If you want well-behaved rationals, I suppose you have to use Ratio Integer.
Hope this helps,
 - Cale
On 4/13/05, Bo Herlin [EMAIL PROTECTED] wrote:
Hi
How come
 foldr1 min [(maxBound::Int) % 1,1 % 2]
2147483647 % 1
but
 foldr1 min [2147483647 % 1,1 % 2]
1 % 2
Why???
/Bo Herlin
___
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] Passing Constructors as arguments

2005-04-13 Thread Daniel Fischer
Am Mittwoch, 13. April 2005 15:43 schrieb Ralph Hodgson:
 I am learning Haskell and have set a small exercise for myself on a
 frames and slots program.
 Would appreciate some help on how to pass constructors of data
 structures as arguments to a function.

 Thanks,

 -- Ralph
snip
 Now I need a way to extract properties from the frame. Start by testing
 pattern matching
 without using parameters. Then I need to find out how to pass a
 constructor as a parameter.

Your code works fine. 
I'm not sure, what your problem is.
Given type-correctness, data constructors can be passed as arguments to 
functions like any other function. Probably that's not your question, 
however. 
As a wild guess, maybe you should use labelled records,

data Contact = Contact
 { firstName :: FirstName
 , lastName :: LastName
 , ...
 }

and you have your selector-functions.

And it's possible to define partial contacts as

me = Contact{firstName=Daniel, lastName=Fischer}

-- just don't ask for my phone-number or anything else which is undefined.

If I'm far off, state your problem more precisely.

   getProperty:: [ContactProperty] - FirstName
   getProperty ((FN fn):_) = fn
   getProperty (_:xs)  = getProperty xs
   getProperty  [] = unknown
  
   firstName:: Contact - FirstName
   firstName (Contact cpl) = getProperty cpl

Cheers,
Daniel

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


Re: [Haskell-cafe] [Q] A typing problem

2005-04-13 Thread Didier Verna
Henning Thielemann [EMAIL PROTECTED] wrote:

 Do you mean

 foldmap :: (b - b - b) - (a - b) - [a] - b
 foldmap f m = foldr1 f . map m

But of course ! Thanks :-)

-- 
Didier Verna, [EMAIL PROTECTED], http://www.lrde.epita.fr/~didier

EPITA / LRDE, 14-16 rue Voltaire   Tel.+33 (1) 44 08 01 85
94276 Le Kremlin-Bicêtre, France   Fax.+33 (1) 53 14 59 22   [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Passing Constructors as arguments

2005-04-13 Thread Pierre Barbier de Reuille
I don't really understand what you want to achieve : constructors are 
functions, thus first class objects ...

I suppose you want a destructor, ie a function extracting the first name 
from a property for example. You may want to have a look there :

http://haskell.org/hawiki/DecoratingStructures
Pierre
Ralph Hodgson a écrit :
I am learning Haskell and have set a small exercise for myself on a 
frames and slots program.
Would appreciate some help on how to pass constructors of data 
structures as arguments to a function.

Thanks,
-- Ralph
__
A Frames test
  module Frames
  where
Define frame slots:
  type FirstName = String -- first name
  type LastName= String   -- last name
  type Organization = String
  type Email = String
  type WorkPhone = String
  type CellPhone = String
  type TelephoneNumber = String
Define slots for a contact
  data ContactProperty = FN FirstName
| LN LastName
| OR Organization
| EM Email
| WP TelephoneNumber
| MP TelephoneNumber
  deriving (Show, Eq)
  data Contact = Contact [ContactProperty]
  deriving (Show, Eq)
  type Contacts = [ Contact]
Now I need a way to extract properties from the frame. Start by testing 
pattern matching
without using parameters. Then I need to find out how to pass a 
constructor as a parameter.

  getProperty:: [ContactProperty] - FirstName
  getProperty ((FN fn):_) = fn
  getProperty (_:xs)  = getProperty xs
  getProperty  [] = unknown
  firstName:: Contact - FirstNamen
  firstName (Contact cpl) = getProperty cpl
Define Contacts
  c1::Contacts
  c1 =
   [ ( Contact  [(FN Ralph),(LN Hodgson),(OR TopQuadrant),(EM 
[EMAIL PROTECTED])]),
 ( Contact  [(FN Mills),(LN Davis),(EM [EMAIL PROTECTED])])]

Tests
  t1=firstName $ head c1 -- should be Ralph
  t2=firstName $ last c1 -- should be Mills
___




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
--
Pierre Barbier de Reuille
INRA - UMR Cirad/Inra/Cnrs/Univ.MontpellierII AMAP
Botanique et Bio-informatique de l'Architecture des Plantes
TA40/PSII, Boulevard de la Lironde
34398 MONTPELLIER CEDEX 5, France
tel   : (33) 4 67 61 65 77fax   : (33) 4 67 61 56 68
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Passing Constructors as arguments

2005-04-13 Thread Ralph Hodgson
Thanks for your help Daniel - I am clarifying my message
Daniel Fischer wrote:
Am Mittwoch, 13. April 2005 15:43 schrieb Ralph Hodgson:
 

I am learning Haskell and have set a small exercise for myself on a
frames and slots program.
Would appreciate some help on how to pass constructors of data
structures as arguments to a function.
Thanks,
-- Ralph
   

snip
 

Now I need a way to extract properties from the frame. Start by testing
pattern matching
without using parameters. Then I need to find out how to pass a
constructor as a parameter.
   

Your code works fine. 
I'm not sure, what your problem is.
Given type-correctness, data constructors can be passed as arguments to 
functions like any other function. Probably that's not your question, 
however. 
 

I would like to see an example of passing constructors as arguments. I 
am still getting familiar with constructs like:

 getProperty ( a - b) - [ContactProperty] - b
I am not sure how to test the Constructor passed as the argument. Do I 
say the following:

 getProperty c ((c v:_) = v
 getProperty c ((_:xs) = getProperty c xs
..
I have tried doing this but GHC gives me parse errors. There is  Haskell 
syntax that I don't know yet that I need to learn.

As a wild guess, maybe you should use labelled records,
data Contact = Contact
{ firstName :: FirstName
, lastName :: LastName
, ...
}
and you have your selector-functions.
 

thanks - very useful
And it's possible to define partial contacts as
me = Contact{firstName=Daniel, lastName=Fischer}
-- just don't ask for my phone-number or anything else which is undefined.
If I'm far off, state your problem more precisely.
 

 getProperty:: [ContactProperty] - FirstName
 getProperty ((FN fn):_) = fn
 getProperty (_:xs)  = getProperty xs
 getProperty  [] = unknown

 firstName:: Contact - FirstName
 firstName (Contact cpl) = getProperty cpl
   

Cheers,
Daniel
 

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


Re: [Haskell-cafe] Passing Constructors as arguments

2005-04-13 Thread Daniel Fischer
Am Mittwoch, 13. April 2005 17:14 schrieben Sie:
 Thanks for your help Daniel - I am clarifying my message

 I would like to see an example of passing constructors as arguments. I

 am still getting familiar with constructs like:
   getProperty ( a - b) - [ContactProperty] - b

 I am not sure how to test the Constructor passed as the argument. Do I

This isn't an argument, by the way, it's a parameter.

 say the following:
   getProperty c ((c v:_) = v
   getProperty c ((_:xs) = getProperty c xs

You can't do it thus, a variable-pattern like c may only appear once in a 
function definition and c v isn't a legal pattern, so may not appear on the 
lhs of the definition. Neither may an incompletely applied constructor:

Hugs mode: Restart with command line option +98 for Haskell 98 mode

ERROR ./Ini.hs:29 - Constructor Left must have exactly 1 argument in 
pattern

The offending line is

humm Left = LT

You can achieve your goal with dummy values:

getProperty c@(FN d) (x:xs) = case x of
  FN fn - fn
   _   - getProperty c xs
getProperty c@(LN d) (x:xs) = case x of
   LN ln - ln
   _   - getProperty c xs
...

and then call 

getProperty (FN undefined) list.

This isn't very nice, though. I'd rather do it (if labelled records aren't the 
thing to do) using Maybe types:

firstName :: ContactProperty - Maybe FirstName
firstName (FN fn) = Just fn
firstName _ = Nothing

and so on, then (this depends on all properties being represented by a String, 
if different types were involved, it'd be more complicated)

getProperty :: (ContactProperty - Maybe String) - [ContactProperty]
 - String
getProperty f xs = case catMaybes $ map f xs of
  [] - unknown
  (p:ps) - p

However, this isn't nice either.



 ..

 I have tried doing this but GHC gives me parse errors. There is  Haskell
 syntax that I don't know yet that I need to learn.

Quite natural, I strongly recommend reading the 'Gentle Introduction to 
Haskell' and every now and then looking whether you already know enough 
Haskell to profit by reading the report. The sections on pattern matching 
have valuable information on the problem at hand.

 As a wild guess, maybe you should use labelled records,
 
 data Contact = Contact
  { firstName :: FirstName
  , lastName :: LastName
  , ...
  }
 
 and you have your selector-functions.

 thanks - very useful

Nice to read that :-)

Cheers,
Daniel

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


Re: [Haskell-cafe] Re: Closest analog to popen()

2005-04-13 Thread Dimitry Golubovsky
Peter Simons wrote:
Dimitry Golubovsky writes:
  Does there exist any analog of popen in the standard Haskell libraries?
Maybe System.Process.runInteractiveCommand is what you need?
http://haskell.org/ghc/docs/latest/html/libraries/base/System.Process.html
Is this available only in 6.4? In 6.2.2 I've got only 
System.Posix.Process, and this is just binding to Unix functions dealing 
with processes.

Thanks for pointing me out.
Dimitry Golubovsky
Middletown, CT

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