[Haskell] ANNOUNCE: htags-1.0

2008-11-03 Thread David Sankel
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/htags

htags is a tag file generator to enable extra functionality in editors
like vim. It expands upon hasktags by using a full Haskell 98 parser
and options for recursion.

--
David Sankel
Sankel Software
www.sankelsoftware.com
585 617 4748 (Office)
585 309 2016 (Mobile)
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] ANNOUNCE: rsa-haskell 2.0.1

2007-05-01 Thread David Sankel

RSA-Haskell is a collection of command-line cryptography tools and a
cryptography library written in Haskell. It is intended to be useful
to anyone who wants to secure files or communications or who wants to
incorporate cryptography in their Haskell application.

Download and documentation are available at
http://www.netsuperbrain.com/rsa-haskell.html

In this 2.0.1 release I've added a bunch of documentation and
incorporated an archive with windows binaries for the command line
tools.

Please let me know if you have any questions or comments.

Enjoy!

David

--
David Sankel
Sankel Software
www.sankelsoftware.com
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Re: putStr is not evaluated in the correct order

2006-09-09 Thread David Sankel
On 9/5/06, Bruno Martínez <[EMAIL PROTECTED]> wrote:
C++ avoids this problem 'tieing' cin and cout.  Why can't haskell do thesame?I was thinking the same thing. I'm imagining a situation where processes are communicating to each other using pipes, but cannot think of a concrete case. Do you know if C++ has any way to disable tying std::cin and std::cout?
David
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Read Instances for Data.Map and Data.Set

2005-10-21 Thread David Sankel
On 10/19/05, Georg Martius <[EMAIL PROTECTED]> wrote:
> I was really annoyed by the fact that for Data.Map and Data.Set are no Read
> instances declared, but Show instances are! I believe there should be some
> kind of unwritten rule that in the standart lib the Show and Read instances
> come pairwise and are fully compatible.

If there was this unwritten rule, should there not be other rules
designed to ensure that reads and shows with interacting types are
compatible? For example, I could imagine a type that would read and
show on it's own, but a map of these objects wouldn't read and show
correctly.

I'm not suggesting this, but a possible solution would be to use
parenthesis around every type and disallow a type to show to unmatched
internal parenthesis.

Regards,

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


Re: [Haskell] Should inet_ntoa Be Pure?

2005-05-07 Thread David Sankel
Below is the relevant source code.

David


foreign import ccall unsafe "my_inet_ntoa"
  c_inet_ntoa :: HostAddress -> IO (Ptr CChar)

foreign import CALLCONV unsafe "inet_addr"
  c_inet_addr :: Ptr CChar -> IO HostAddress

-- -
-- Internet address manipulation routines:

inet_addr :: String -> IO HostAddress
inet_addr ipstr = do
   withCString ipstr $ \str -> do
   had <- c_inet_addr str
   if had == -1
then ioError (userError ("inet_addr: Malformed address: " ++ ipstr))
else return had  -- network byte order

inet_ntoa :: HostAddress -> IO String
inet_ntoa haddr = do
  pstr <- c_inet_ntoa haddr
  peekCString pstr


On 5/7/05, Dominic Steinitz <[EMAIL PROTECTED]> wrote:
> Does anyone know why these are in the IO monad? Aren't they pure functions
> converting between dotted-decimal strings and a 32-bit network byte ordered
> binary value?
> 
> Dominic.
> 
> http://www.haskell.org/ghc/docs/latest/html/libraries/network/Network.Socket.html#v%3Ainet_addr
> http://www.haskell.org/ghc/docs/latest/html/libraries/network/Network.Socket.html#v%3Ainet_ntoa
> 
> ___
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Re: 2-D Plots, graphical representation of massive data

2004-08-28 Thread David Sankel
A bit off topic, but a haskell charting/graphic library designer would
be wise to check out the highly successful python equivelant, pychart.

It seems as though a library equivelant in features to pychart is
exactly what the original poster is looking for.

David
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Lists as Arrows

2004-06-05 Thread David Sankel
Hello,

  Forgive me, I have but a fuzzy idea of what Arrows are.  I was thinking it
might be possible to make lists arrows instead of monads.

  This would allow (++) to be one of those special arrow computations.  It
would have some quite nice properties.  For example (++ [a]) could be a O(1)
operation instead of a O(n).  Also, the trivial implementation of a queue
would be O(1) for push and pop operations instead of the more complicated
amortized O(1) implementation.

  Am I missing the point or is what I said above a possibility?

David J. Sankel
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] main::[String]->IO() ?

2004-03-23 Thread David Sankel
--- Steffen Mazanek <[EMAIL PROTECTED]> wrote:
> I think this would simplify everyday-programming a lot. Or are there
> any severe theoretical (semantical) problems (main is running in the IO 
> monad either way)? 

The type signature of main currently is:

main :: IO()

and the new type signature would be

main :: [String] -> IO()

Since type signature declarations for functions are generally considered good
practice, those who use "<- getArgs" would actually need to type two extra
characters.  And those who do not use getArgs typically (which may or may not
be the case in general), would type an extra 14 characters.

One might also consider getProgName and getEnv to be plausible arguments to
main as they are for some variants of c.  However, in this case we are
getting quite excessive with main's arguments.

Aside from the two points made above, the current, no-argument version of
main would support new programming models elegantly.  Future systems
development may lead to better system-program communication.  GUI's, for
instance, might have a special configuration line of communication for window
placement which could be vastly superior to parsing a list of strings.

Although there aren't any theoretical problems with main having an argument,
I think that current practicioners would find it more efficient the way it is
now.

David J. Sankel
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Implicit parameters redux

2004-01-28 Thread David Sankel
Ben,

  Could you explain in an extremely dumbed-down way what this is?  It would
be great if there were examples of

  1)  Some common, simple, and useful code in Haskell.
  2)  Same code using Implicit Parameters with a discussion of how it is
better.

Thanks,

David J. Sankel
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: type classes, superclass of different kind

2003-12-11 Thread David Sankel
--- Robert Will <[EMAIL PROTECTED]> wrote:
-- > Here
-- > is a quesion for the
-- > most creative of thinkers: which is the design
(in
-- > proper Haskell or a
-- > wide-spread extension) possibly include much
-- > intermediate type classes and
-- > other stuff, that comes nearest to my desire?

Hello,

  I've often wondered the same thing.  I've found that
one can simulate several OO paradigms.  Note that
these aren't particularly elegant or simple.


Using Data Constructors:


> data Shape = Rectangle {topLeft :: (Int, Int),
bottomRight :: (Int,Int) } 
>| Circle {center :: (Int,Int), radius ::
Int } 

This allows you have a list of shapes 

> shapeList :: [Shape]
> shapeList = [ Rectangle (-3,3) (0,0), Circle (0,0) 3
]

When you want member functions, you need to specialize
the function for
all the constructors.

> height :: Shape -> Int
> height (Rectangle (a,b) (c,d)) = b - d
> height (Circle _ radius) = 2 * radius

Disadvantages:

1) When a new Shape is needed, one needs to edit the
original Shape source 
file.
2) If a member function is not implemented for a shape
subclass, it will lead
to a run-time error (instead of compile-time).

Advantages:

1) Simple Syntax
2) Allows lists of Shapes
3) Haskell98

Example: GHC's exception types
 
http://www.haskell.org/ghc/docs/latest/html/base/Control.Exception.html


Using Classes


Classes can be used to force a type have specific
functions to act upon it.
>From our previous example:

> class Shape a where
>   height :: a -> Int
>
> data Rectangle = Rectangle {topLeft :: (Int, Int),
bottomRight :: (Int,Int) }
> data Circle = Circle {center :: (Int,Int), radius ::
Int } 
> 
> instance Shape Circle where
>   height (Circle _ radius) = 2 * radius
>
> instance Shape Rectangle where
>   height (Rectangle (a,b) (c,d)) = b - d

In this case, something is a shape if it specifically
has the member 
functions associated with Shapes (height in this
case).

Advantages
1) Simple Syntax
2) Haskell98
3) Allows a user to easily add Shapes without
modifying the original source.
4) If a member function is not implemented for a shape
subclass, it will lead
to a compile-time error.

Disadvantages:
1) Lists of Shapes not allowed

Example: Haskell 98's Num class. 
http://www.haskell.org/ghc/


Classes with Instance holder.


There have been a few proposals of ways to get around
the List of Shapes 
problem with classes.  The Haskell98 ways looks like
this

> data ShapeInstance = ShapeInstance { ci_height ::
Int }

> toShapeInstance :: (Shape a) => a -> ShapeInstance
> toShapeInstance a = ShapeInstance { ci_height =
(height a) }

> instance Shape ShapeInstance where
>   height (ShapeInstance ci_height) = ci_height

So when we want a list of shapes, we can do

> shapeList = [ toShapeInstance (Circle (3,3) 3), 
>   toShapeInstance (Rectangle (-3,3)
(0,0) ) ]

Of course this also has it's disadvantages.  Everytime
a new memeber function is added, it must be noted in
the ShapeInstance declaration, the toShapeInstance
function, and the "instance Shape ShapeInstance"
declaration.

Using a haskell extention, we can get a little better.
 Existentially quantified data constructors gives us
this:

> data ShapeInstance = forall a. Shape a =>
ShapeInstance a
> 
> instance Shape ShapeInstance where
>   height (ShapeInstance a) = height a
>
> shapeList = [ ShapeInstance (Circle (3,3) 3), 
>   ShapeInstance (Rectangle (-3,3) (0,0)
) ]

The benefits of this method are shorter code, and no
need to update the ShapeInstance declaration every
time a new member function is added.


Records extention


A different kind of inheritance can be implemented
with enhanced haskell 
records.  See
http://research.microsoft.com/~simonpj/Haskell/records.html
and
http://citeseer.nj.nec.com/gaster96polymorphic.html
for in depth explinations.  I'm not sure if these have
been impemented or not, but it would work as follows.

The inheritance provided by the above extentions is
more of a data inheritance 
than a functional inheritance. Lets say all shapes
must have a color parameter:

> type Shape = {color :: (Int,Int,Int)}
> type Circle = Shape + { center :: (Int,Int), radius
:: (Int) }
> type Rectangle = Shape + { topLeft :: (Int,Int),
bottomRight :: (Int, Int) }

So now we can reference this color for any shape by
calling .color.

> getColor :: (a <: Shape ) -> a -> (Int,Int,Int)
> getColor a = a.color

I'm not sure how the records extention could be used
with Classes with instance 
holders to provide an even more plentiful OO
environment.

So I'll conclude this email with the observation that
Haskell supports some
OO constructs although not with the most elegance.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Doing weird things with types.

2003-11-06 Thread David Sankel
Hello All,

  I'm trying to create a generic function (*) using
classes.  I've been playing with ghc extensions but
haven't found what I need yet.

class HasTimes a b c where
 (*) :: a -> b -> c

  This doesn't work because it can't figure out what
the return types are for a general expression a*(b*c).
 This kinda makes sense since someone could overload
HasTimes Float Float Int and HasTimes Float Float
Float.

What about:

class HasTimes a b where
 (*) :: a -> b -> c

  This would sort of imply that c is the only possible
result of a (*) for types a and b.  But I'm pretty
sure this functionality hasn't been implemented.

  Why is this important?  I'm trying to reduce
ugliness of code using the following library:

data Matrix = Matrix ((Float,Float),(Float,Float))
data HVec   = HVec Float Float
data VVec   = VVec Float Float

idMatrix = Matrix ((1.0,0.0),(0.0,1.0))

vhVecMult (VVec a b) (HVec c d) = 
  Matrix ((a*c,a*d),(b*c,b*d))

matMult (Matrix ((a,b),(c,d))) (Matrix ((e,f),(g,h)))
=
  Matrix (((a*e+b*g),(a*f+b*h)),((c*e+d*g),(c*f+d*h)))

matVVecMult  (Matrix ((c,d),(e,f))) (VVec a b) =
  VVec (a*c + b*d) (a*e + b*f)

hVecMatMult (HVec a b) (Matrix ((c,d),(e,f))) =
  HVec (c*c+b*e) (a*d+b*f)

vVecMinus (VVec a b) (VVec c d) = VVec (a-c) (b-d)

vVecPlus (VVec a b) (VVec c d) = VVec (a+c) (b+d)


matMinus (Matrix ((a,b),(c,d))) (Matrix ((e,f),(g,h)))
=
  Matrix ((a-e,b-f),(c-g,d-h))

hvVecMult (HVec a b) (VVec c d) = a*c + b*d

scalHVecMult :: Float -> HVec -> HVec
scalHVecMult i (HVec a b ) = HVec (i*a) (i*b)

Thanks,

David J. Sankel

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


[ANNOUNCE] rsa-haskell 2.0.0

2003-06-07 Thread David Sankel
===
rsa-haskell   2.0.0
===

  RSA implementation in Haskell (rsa-haskell) contains
the Simple and Strong
Cryptography program set and Haskell libraries of
several cryptographic 
standards.  

  The libraries include haskell implementations of
SHA1, EME-OAEP, EMSA-PSS, 
MGF, RSAES-OAEP, and RSA-PSS.  These standards
implement signature/verification,
strong cryptography, and hashing.  Also included in
the library is a general
number theory library.

  The Simple and Strong Cryptography program set
contains simple programs for 
encrypting and decrypting files with public key
cryptography as well as
signature verification with public key cryptography.

Changes from 1.2.0 to 2.0.0:


  Added implementation for several standard
cryptographic protocols including
SHA1, EME-OAEP, EMSA-PSS, MGF, RSAES-OAEP, and
RSA-PSS.  Refactored client
code.  Program names are now ssdecrypt, ssencrypt,
sskeygen, sssign, and
ssverify.  Renamed client programs to the Simple and
Strong Cryptography 
program set.  

see 

  http://www.electronconsulting.com/rsa-haskell

for details.

David J. Sankel
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Haskell Networking Example

2003-04-02 Thread David Sankel
Hello All,
  Here is an example of using haskell networking
operations for those interested.  The implementation
is a simple echo server.

echoclient.hs:

module Main( main ) where

import Network
import IO
import Control.Concurrent

main :: IO ()
main =  withSocketsDo $ --For windows compatibility
  do
handle <- connectTo "localhost" (PortNumber 2048)
input <- getContents
sequence_ $ map ( \a -> do 
  hPutStr handle $ a ++ "\n"
  hFlush handle ) $ lines input
hClose handle

echoserver.hs:

module Main( main ) where

import Network
import IO
import Control.Concurrent

main :: IO ()
main = withSocketsDo $ --For windows compatibility
  do
theSocket <- listenOn (PortNumber 2048)
sequence_ $ repeat $ acceptConnectionAndFork
theSocket
  where
acceptConnectionAndFork :: Socket -> IO ()
acceptConnectionAndFork theSocket = do
  connection <- accept theSocket
  let (handle, hostname, portnumber ) = connection
  putStr ("("++ hostname ++ ":" ++ (show
portnumber) ++ "): Open\n" )
  forkIO (echoServer connection)
  return ()

echoServer :: (Handle, String, PortNumber) -> IO ()
echoServer (handle, hostname, portnumber ) = do
  a <- hGetContents handle
  putStr $ foldr (++) "" $ map (\a -> "(" ++ hostname
++ ":" 
  ++ (show portnumber) ++ "): Msg " ++ (show
a) ++ "\n" ) $ lines a
  putStr ("("++ hostname ++ ":" ++ (show portnumber)
++ "): Close\n" )

Makefile:

all: echoclient echoserver

echoclient: echoclient.hs
ghc -package network echoclient.hs -o
echoclient

echoserver: echoserver.hs
ghc -package network echoserver.hs -o
echoserver

clean:
rm *.o *.hi echoclient echoserver

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Interesting Read

2003-02-18 Thread David Sankel
An interesting read:

http://www.paulgraham.com/popular.html

Any thoughts?


David J. Sankel
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Proposal Proposal: haskell-gui addendum to haskell standard

2003-01-22 Thread David Sankel
Hello Everyone,

  I believe that haskell would have great benifit from
a platform independant specification for a graphical
user interface module or set of modules.  I've been
blessed with a lot of time on my hands so I'd be
willing to organize this project if needed.

  Since there are several working haskell gui
libraries out there, I would like this to be a
collaboration project with those who are experienced
in this area.  Input and ideas from users would also
be a part of the collaberation.

  The goal would be a specification much like the
haskell report that could be freely implimented and a
reference impementation.

  This is an informal proposal for a proposal and
would like to get some feedback for the following
ideas. (please reply to [EMAIL PROTECTED])

1.  Platform independance:  The QT widget library is a
stunning example of how platform independance is
achievable without sacraficing speed.  I am not
suggesting that we build haskell-gui off of QT but
might use major components of it as a model. 
Eventually, the library could have three backends; the
Windows API, the X API (or gtk perhaps?), and the Mac
API (the name illudes me at the moment).

2.  Signals support:  Having a signals mechanism is
essential for large gui projects.

3.  Dynamic widgets:  All widgets should have dynamic
size and should have the ability to be resized by the
measurement of their contents or their parents.  This
could be done in a way similar to QT widgets.

4.  GUI GUI builder:  Widgets should be flexible
enough to have the ability to be incorporated in a GUI
GUI builder program, such as QT designer.  The storage
for a GUI builder might be direct Haskell code or some
intermediate format.

5.  OpenGL incorporation:  haskell-gui should have
some sort of OpenGL widget as OpenGL is the most
standardized and multiplatform graphical library
availible.  Perhaps the hgl software could be
incorporated in this aspect of haskell-gui.

6.  Custom Widgets:  It should be easy for one to
create his or her own custom widgets from scratch
using Haskell code or by some modification of the
standard ones.

Please give your feedback and suggestions for this
project proposal proposal.  If there is enough
interest, I'll get this thing started.

Kudos,

David J. Sankel
Head Consultant
Electron Consulting (www.electronconsulting.com)



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: ANNOUNCE: Haskell Wiki resurrected

2002-12-30 Thread David Sankel
--- John Meacham <[EMAIL PROTECTED]> wrote:
> On another note related to providing services to the
> haskell comunity,
> how about a public bugzilla server on
> bugs.haskell.org?
> (http://bugzilla.org) any haskell project which
> wishes to use the public
> bug server could be set up with an entry, it would
> be nice to have a
> central place to report bugs in the various haskell
> systems as well.
> This is not meant to replace whatever established
> project have, but
> rather provide a service to anyone with a haskell
> project who wishes bug
> reporting capability.

I concur on this idea.  This would be very useful.

David J. Sankel
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Interpret haskell within haskell.

2002-12-19 Thread David Sankel
I was wondering if there is any project that aims to
interpret haskell within haskell.

Is it feasable that a program can import a user's .hs
file that has something like:

greeting :: String
greeting = "Something"

port :: Int
port = 32 + 33

And the program can parse and execute the user's
function.

I'm looking for something similar to the eval command
in Python.

Thanks,

David J. Sankel
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: video4linux

2002-12-10 Thread David Sankel
--- Martin Huschenbett <[EMAIL PROTECTED]> wrote:
> Hi all,
> 
> does anybody know how to read a single image from a
> video4linux device under Haskell?
> Thanks for all help,

Hello,

  I think that the easiest way to do this would be to
use the ffi to connect with C code that does this.

David J. Sankel
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



ANNOUNCE: rsa-haskell 1.1.0

2002-11-27 Thread David Sankel
rsa-haskell 1.1.0
=

This is an announcement for a version 1.1.0 of the
rsa-haskell library/tools.

Description:

  rsa-haskell is a haskell implementation of the RSA
algorithm.  It contains simple programs that are
useful for encrypting/decrypting anything that can
be
piped from STDIN/STDOUT.  rsa-haskell also has an
easy-to-use rsa and number theory library.

Changes:

  Added AddZeros and SubZeros programs to fix previous
m>pq errors.  Now
rsa-haskell's test runs without known error.  Huge
speedup in the RSAcrypt
program.  Useage messages now show for all user
errors.  All programs now
support the -h, -?, and --help options.

For more information and download:

  http://www.electronconsulting.com/rsa-haskell/

Please email comments, bugs, etc. to
[EMAIL PROTECTED]


David J. Sankel

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: how to convert IO String to string (Simple answer)

2002-11-24 Thread David Sankel
--- Lu Mudong <[EMAIL PROTECTED]> wrote:
> Thanks a lot for you guys' help.
> 
> I am very new to haskell and tried some methods you
> guys advised, doesn't 
> seem to work, i think i didn't do it properly,
> here's my code and result, 
> hope you can point out what's wrong. thanks!
>

Lots of theory, here's some code:

-- Begin code
module Main()
where

import IO

myReadFile :: String -> IO String
myReadFile filename = readFile filename 

main :: IO ()
main = do
  s <- myReadFile "/etc/fstab"
  let length = doStuffWithNormalString s
  putStr "Length of File :" 
  putStr (show length)
  putStr "\n"


-- For example, count the number of characters
doStuffWithNormalString :: String -> Int
doStuffWithNormalString s = length s;

-- End code

My Explination:
Basically, your program starts in a do loop.  Anything
that returns an IO something needs a <-.  For example

a <- someIOReturnValue

And you can use a as a normal value w/o an IO type.

Anything function that doesn't return the IO type
needs a 

let a = someNormalFunction.

And you can pretty much do what you want after you
know these things.  Oh yea, you can't do IO stuff in a
non IO function.  This is a pretty nasty part of
learning haskell, but once you get used to it, you
might actually like it.

Later,

David J. Sankel
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



ANNOUNCE: rsa-haskell 1.0.0

2002-11-12 Thread David Sankel
rsa-haskell 1.0.0
=

This is an announcement for a version 1.0.0 of the
rsa-haskell library/tools.

Description:

  rsa-haskell is a haskell implementation of the RSA
algorithm.  It contains simple programs that are
useful for encrypting/decrypting anything that can be
piped from STDIN/STDOUT.  rsa-haskell also has an
easy-to-use rsa and number theory library.

For more information and download:

  http://www.electronconsulting.com/rsa-haskell/

Please email comments, bugs, etc. to [EMAIL PROTECTED]


David J. Sankel


__
Do you Yahoo!?
U2 on LAUNCH - Exclusive greatest hits videos
http://launch.yahoo.com/u2
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: finding ....

2002-03-19 Thread David Sankel

--- Pixel <[EMAIL PROTECTED]> wrote:
> Lennart Augustsson <[EMAIL PROTECTED]> writes:
> 
> > > Diego Yanivello wrote:
> > > 
> > > > hi,is there (in Haskell) a function like  
>  existFile :: FilePath ->
> > > > IO (Bool) ? Thanks!
> > 
> > Using such a function is generally a bad idea
> because of race conditions.
> 
> however, real world programs use those tests since
> you don't need to care
> *everytime* about race conditions. (of course using
> this existFile before
> creating a temporary file is wrong, but existFile
> has *many* other
> applications)

Could someone post an example of the creation of a
temporary file where race conditions are important?

Thanks,

David J. Sankel

__
Do You Yahoo!?
Yahoo! Sports - live college hoops coverage
http://sports.yahoo.com/
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Help

2002-02-25 Thread David Sankel

--- "Juan M. Duran" <[EMAIL PROTECTED]> wrote:
> Hi, I'm writting a small parser in Haskell and, when
> it is all done, I get
> the following problem: Type Binding.
> 
> The thing is, I have 3 main functions:
> 1) Read the file, its type is: [Char] ->IO [Char]
> (see InputOutput.hs)
> 2) Parse a string (using words and readDec), its
> type is: Integral a =>
> [Char] -> [a] (see Parse.hs)
> 3) Parse a list of integer, its type is: [Float] ->
> [[Float]]
> (Functions.hs)
> 
> Now the problem is that I cannot run the first
> function, then use its
> results as an input of the second function and,
> finally, its results as
> the input of the third function.
> 
> How can I fix this without modifing all my functions
> because they,
> independly, works fine.
> 

I'm kinda confused with all the spanish and such, but
isn't the solution something like this?

main =
  do
a <- function1
let b = function2 a
let c = function3 a

David J. Sankel





__
Do You Yahoo!?
Yahoo! Sports - Coverage of the 2002 Olympic Games
http://sports.yahoo.com
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell