Re: [Haskell-cafe] RE: ANN: System.FilePath 0.9

2006-07-17 Thread David Roundy
On Mon, Jul 17, 2006 at 03:07:51AM +0100, Neil Mitchell wrote:
 Hi Brian,
 
 I kind of expect that a Haskell library for file paths will use the
  type system to ensure some useful properties about the paths.

 I am specificially concentrating on type FilePath = String, because
 that is how it is defined by Haskell 98. And consequently that's how
 it works with readFile/writeFile/appendFile etc.
 
 Perhaps a far better solution to this would not be to hack these kind
 of guarantees in at the filepath level, but have a restricted IO monad
 that only lets you perform operations inside certain directories, or
 only lets you read/write files. I know that both House and Halfs use
 these techniques. Without too much effort Yhc (for example) could be
 modified to perform restricted IO operations (only on certain
 directories etc).

 You seem to want to distinguish between relative, relative down only
 and absolute paths. By putting this in the filepath, and having
 different types for each, you pretty much guarantee that all standard
 functions will operate on all 3 types of path, so you don't gain any
 security that way, since mistakes will still slip through. How about
 adding something like restrictFilePaths :: FilePath - IO () which
 will restrict the area that can be played with to that beneath the
 given FilePath?

Darcs also does something similar (typeclasses for control of IO
actions), and this is certainly the way to go.  However, I also agree
that type distinctions between paths would be nice.  My preference has
long been that the FilePath should be a class rather than a type.
Then one could have single IO functions that accept restricted and
unrestricted file paths, and other ones that accept only restricted
file paths, so you could get compile-time checking that your safe
chroot monad won't die at runtime.
-- 
David Roundy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Unix gurus, help me please

2006-07-17 Thread Bulat Ziganshin
Hello gurus :)

i got message about problems compiling Streams 0.2.1 library on Unix systems:

- I include file io.h, but this particular system has sys/io.h
instead. I think that i should solve this problem by including
HsBase.h which should include proper io.h on any system supported.
One more question is whether this HsBase.h will be available on non-GHC
platforms, including Hugs, yhc, jhc?



- Michael Stone (which reported all these problems) suggests to use

#!/usr/bin/env runhaskell

instead of 

#!/usr/bin/runhaskell

at the start of Setup.hs file. Is that really better?



- mingw supports _commit operation which (as i guess) saves to disk
buffers of given file. Is that true that regular unixes has fsync
function to perform the same action? (and what the hell MS don't
use the same name??)


-- 
Best regards,
 Bulat  mailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Unix gurus, help me please

2006-07-17 Thread Duncan Coutts
On Mon, 2006-07-17 at 18:04 +0400, Bulat Ziganshin wrote:
 Hello gurus :)
 
 i got message about problems compiling Streams 0.2.1 library on Unix systems:
 
 - I include file io.h, but this particular system has sys/io.h

Are you sure you need sys/io.h? What are you using from it? As far as I
can see it doesn't define anything that you might want to use, just
functions for reading and writing bytes from/to the non-portable unix io
ports feature (aka /dev/port).

Duncan

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


Re: [Haskell-cafe] Unix gurus, help me please

2006-07-17 Thread Eugene Crosser
Bulat Ziganshin wrote:

 - I include file io.h, but this particular system has sys/io.h
 instead.

Just out of the blue: could it be that you rather need fcntl.h?
It's the place where open() and friends are defined.  Maybe(?) windows
have them in io.h...

 - mingw supports _commit operation which (as i guess) saves to disk
 buffers of given file. Is that true that regular unixes has fsync
 function to perform the same action? (and what the hell MS don't
 use the same name??)

Not all unixes (unii?) have fsync() syscall, but most of them do.  And
all modern ones, I guess.  If your platform does not have fsync(), it is
recommended to fallback to sync().

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


Re: [Haskell-cafe] Compiling ghc for using STM

2006-07-17 Thread Bulat Ziganshin
Hello Asfand,

Monday, July 17, 2006, 7:31:23 PM, you wrote:

 I finally got my spiffy dual-core processor (an Opteron 165 no-less)
 and want to learn STM, since I think it and haskell are the future of
 concurrent programming.

 How do I compile Haskell to be able learn STM on it, using proper
 threading?  I know there's a parallel haskell flag, but I read
 somewhere about it running on top of some special server that lets it
 work in parallel threads or something.

you should compile with -threaded flag which allows to preempt
threads created in your program with forkIO/forkOS

if you want to really use 2 processors, you should use ghc 6.5, which
is still in beta stage. ghc 6.4 executes all the Haskell code on one
processor (to be exact, at each moment there is only one program
thread executing Haskell code)

look at 
http://www.cse.unsw.edu.au/~chak/haskell/ghc/comm/rts-libs/multi-thread.html
which describes 6.4 situation

http://research.microsoft.com/Users/simonpj/papers/marktoberdorf/marktoberdorf.ps.gz
contains Concurrency chapter what says more about concurrency in GHC

You can find more information about concurrency and STM at the
http://haskell.org/haskellwiki/GHC/Concurrency page


ps: are you one of Iranian hackers cheating A-bomb? ;)

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Unix gurus, help me please

2006-07-17 Thread Lennart Augustsson


On Jul 17, 2006, at 10:04 , Bulat Ziganshin wrote:



#!/usr/bin/env runhaskell

instead of

#!/usr/bin/runhaskell

at the start of Setup.hs file. Is that really better?


Yes, much better.  I think it's crazy to have runhaskell installed  
in /usr/bin.  It should be somewhere in your path, but not  
necessarily in /usr/bin.


-- Lennart

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


Re[2]: [Haskell-cafe] Unix gurus, help me please

2006-07-17 Thread Bulat Ziganshin
Hello Duncan,

Monday, July 17, 2006, 6:18:49 PM, you wrote:

 - I include file io.h, but this particular system has sys/io.h

 Are you sure you need sys/io.h? What are you using from it? As far as I
 can see it doesn't define anything that you might want to use, just
 functions for reading and writing bytes from/to the non-portable unix io
 ports feature (aka /dev/port).

yes, only this _commit really. and how should i import this fsync
instead of _commit so that this import will work on all unix platforms
(supported by ghc and other compilers)?

is the following enough:

foreign import ccall unsafe unistd.h fsync
   c_commit :: CInt - IO CInt

? or it's better to import it using HsBase.h?


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: Re[2]: [Haskell-cafe] Unix gurus, help me please

2006-07-17 Thread Duncan Coutts
On Mon, 2006-07-17 at 19:59 +0400, Bulat Ziganshin wrote:
 Hello Duncan,
 
 Monday, July 17, 2006, 6:18:49 PM, you wrote:
 
  - I include file io.h, but this particular system has sys/io.h
 
  Are you sure you need sys/io.h? What are you using from it? As far as I
  can see it doesn't define anything that you might want to use, just
  functions for reading and writing bytes from/to the non-portable unix io
  ports feature (aka /dev/port).
 
 yes, only this _commit really. and how should i import this fsync
 instead of _commit so that this import will work on all unix platforms
 (supported by ghc and other compilers)?
 
 is the following enough:
 
 foreign import ccall unsafe unistd.h fsync
c_commit :: CInt - IO CInt

I think that should do. It's defined in POSIX.1b so you should be able
to rely on it being defined in that header file on all POSIX systems.

 ? or it's better to import it using HsBase.h?

Well that's GHC-only as far as I know.

Duncan

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


Re: [Haskell-cafe] Compiling ghc for using STM

2006-07-17 Thread Duncan Coutts
On Mon, 2006-07-17 at 18:29 +0100, Asfand Yar Qazi wrote:
 On 7/17/06, Bulat Ziganshin [EMAIL PROTECTED] wrote:
 
  if you want to really use 2 processors, you should use ghc 6.5, which
  is still in beta stage. ghc 6.4 executes all the Haskell code on one
  processor (to be exact, at each moment there is only one program
  thread executing Haskell code)
 
 I should have explained: I've already got ghc trunk successfully
 compiled.  I just need to turn on native threading or whatever its
 called so I can learn STM'ism (and no, I can't make do with in-process
 threads - I didn't pay 230 GBP for a dual-core processor to have one
 in the background processing cron jobs :-)
 
 So, as soon as I figure out how to compile ghc 6.5 beta, and how to
 include parallelisation support, I'm set :-)

I believe that the smp flavour of the RTS is now built by default and so
all you need to do is use it when linking a program:

ghc-6.5 -smp Foo.hs -o foo

Then when running the program you can tell the RTS how many OS threads
to use:

./foo +RTS -N2 -RTS


Duncan

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


Re: [Haskell-cafe] process simulation in functional style

2006-07-17 Thread Jared Updike

Also, I found that the textbook The Haskell School of Expression by
Paul Hudak is a good introduction (particularly, if I remember
correctly, the second half of the book) to functional reactive
programming in Haskell.

 Jared.

On 7/16/06, Nicolas Frisby [EMAIL PROTECTED] wrote:

You might discover helpful techniques by searching for these
terms/projects/papers:

- functional reactive programming (e.g. Yampa project)
- resumption monad (e.g. Cheap but Functional Threads)
- concurrent Haskell extensions
- or even comonads (e.g. Essence of Dataflow)

The activation energy to be invested in each technique is likely
considerable, but that's the fun part, right?

Hope that helps,
Nick

On 7/16/06, Alexander Vodomerov [EMAIL PROTECTED] wrote:
   Hello!

 I'm writing a program that simulates multiple processes. The processes may
 send/receive messages, do some work, or sleep for some amount of time.

 I have seen that many such things can be expressed in Haskell in very
 elegant manner using it functional or lazy properties. For example,
 client/server interaction may be expressed via inifinite lists as shown
 in Gentle Introduction to Haskell. Another way of process simulation
 is describied in http://citeseer.ist.psu.edu/harcourt95extensible.html,
 where simple and concise CCS interperter is constructed.

 I've tried to apply the idea of infinite lists or CCS-style processes,
 but fail. The main reason is that:

 1) messages are asynchronous (it may be received and handled while
 process are sleeping, without waking them)
 2) in some cases received message may wake up process
 3) all activity in system is ordered by time
 4) there are 2 process and during simulations new processes may be
 created

 I've no idea how to implement 1, 2 in CCS interpeter.
 The approach of infinite lists seems to have problems with 3, 4.

 Have somebody any ideas how this can be solved in simple and concise way?

 With best regards,
 Alexander.

 PS. Currently I have some code (see below), but it is VERY UGLY. The
 main drawback is that is very imperative. It employs notion of Global
 state.  It doesn't use features of Haskell and can be rewritten in ML
 or C++ without changes. Another flaws is that it is very unextensible,
 and all processes must have the same state.

 -- example code

 latency = 0.001

 type Message = String
 type MsgM = WriterT [(Int, Message)] IO  -- process may send messages

 -- process states

 next id = (id + 1) `mod` 3

 type State = (Int, Int, Double) -- proc. number, counter, interval

 do_step :: State - MsgM (Double, State) --- do something and then sleep
 do_step (id, cnt, delay) = do
   tell [(next id, ping  ++ show id ++  cnt  ++ show cnt)]
   return (delay, (id, cnt + 1, delay))

 handle_message :: Message - State - MsgM State
 handle_message msg (id, cnt, delay) = do
 -- liftIO $ putStrLn $ show id ++  received  msg  ++ msg
 if msg !! 0 == 'p' then tell [(next id, reply  ++ show id ++  to  ++ 
msg)] else return ()
 return (id, cnt, delay)

 -- global event queue

 data Event = MsgRecv Message | Work deriving Show
 type EventQueue = [(Double, Int, Event)]

 compare_event (t1, n1, e1) (t2, n2, e2) = compare t1 t2

 type EventM = WriterT EventQueue IO

 queue_event :: Int - Event - Double - EventM ()
 queue_event dest ev time = tell [(time, dest, ev)]

 type FullState = Map.Map Int State

 handle_event :: Int - Double - Event - FullState - EventM FullState
 handle_event procnum time ev fullstate  = do
 let localstate = (fullstate Map.! procnum)
 case ev of
   MsgRecv msg - do
   (nstate, messages) - lift $ runWriterT (handle_message msg 
localstate)
   sequence_ $ map (\(dst, msg) - queue_event dst (MsgRecv msg) 
(time + latency)) messages
   return $ Map.insert procnum nstate fullstate
   Work - do
   ((pause, nstate), messages) - lift $ runWriterT (do_step 
localstate)
   sequence_ $ map (\(dst, msg) - queue_event dst (MsgRecv msg) 
(time + latency)) messages
   queue_event procnum Work (time + pause)
   return $ Map.insert procnum nstate fullstate

 run_queue :: FullState - EventQueue - IO ()
 run_queue st eventqueue =
 case eventqueue of
   [] - return ()
   (time, dest, ev) : rest - do
   putStrLn $ processing event  ++ (showFFloat (Just 3) time)  ++  
at procnum  ++ show dest ++++ show ev
   (nst, nev) - runWriterT (handle_event dest time ev st)
   let nqueue = foldl (\res - \e - insertBy 
compare_event e res) rest nev
   run_queue nst nqueue

 init_state = Map.fromList [(0, (0, 0, 0.3)), (1, (1, 0, 0.4)), (2, (2, 0, 
0.5))]

 main = run_queue init_state [(0, 0, Work), (0, 1, Work)]

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

___

Re: [Haskell-cafe] RE: ANN: System.FilePath 0.9

2006-07-17 Thread Brian Smith
Hi Neil,On 7/17/06, Neil Mitchell [EMAIL PROTECTED] wrote:
Hi Brian,You sent this email just to me, and not to the list. If you indendedto send to the list then feel free to forward my bits on to the list. I know that FilePath is defined by Haskell '98 as a String and so it cannot
 be changed. So, perhaps a new type or class should be created for this library (hereafter GoodPath, although I am not suggesting that is the best name).The problem is people will have to marshal their data into this
GoodPath, and marshal it out again. When people can shortcut thatmarshalling, as the current readFile/writeFile definitions ensure theycan, they will. At that point you loose all safety because people will
abuse it.I disagree. It would be trivial to create a new module that exported new definitions of file IO actions that operated on GoodPath instead of FilePath, transparently delegating to the original readFile/writeFile/etc. until they could be removed in the future. This would also support the SuperFilePath idea you mentioned. 
Another thing I thought of would be a canonicalPath IO action (canonicalPath :: FilePath - IO FilePath) that returns a FilePath that implements case-preserving-case-insensitive matching. For example, if there is a file named Hello 
There.txt in C:\, then(canonicalPath c:\hello there.txt ) would give C:\Hello There.txt).I think that the xxxDrive functions should only be exported from System.FilePath.Windows and no 
System.FilePath since it is unclear as to how they should be used effectively by cross-platform software.- Brian
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] RE: ANN: System.FilePath 0.9

2006-07-17 Thread Neil Mitchell

Hi


I disagree. It would be trivial to create a new module that exported new
definitions of file IO actions that operated on GoodPath instead of
FilePath, transparently delegating to the original readFile/writeFile/etc.
until they could be removed in the future. This would also support the
SuperFilePath idea you mentioned.

Yes it would, but because readFile etc. are in the prelude its not
easy to not have them included. If someone was to write a
System.SuperFilePath module and an IO.SuperFilePath module that would
be great! I have considered it myself, but unfortunately don't have
enough time, at the moment.

The advantage of moving to FilePath now is that its entirely
non-breaking for anything, and once we have SuperFilePath, it makes it
easier to migrate because (hopefully!) there will be less functions
proding directly at FilePath's as strings.


Another thing I thought of would be a canonicalPath IO action
(canonicalPath :: FilePath - IO FilePath) that returns a FilePath that
implements case-preserving-case-insensitive matching. For
example, if there is a file named Hello There.txt in C:\, then
(canonicalPath c:\hello there.txt ) would give C:\Hello There.txt).

Yes, thats a really good idea - and in fact when I wrote a FilePath
module for Visual Basic (a long long time ago), I had such a function
in it. I will make sure I add that tomorrow.


I think that the xxxDrive functions should only be exported from
System.FilePath.Windows and no System.FilePath since it is unclear as to how
they should be used effectively by cross-platform software.

I would say they shouldn't be used at all, but it is true that
Posix.setDrive c: is a bit poorly defined. I will think this idea
over, maybe the drive functions shouldn't be exported under either the
general one or under the Posix, but it breaks a nice symetry that the
library has...

I have added a wiki page discussing System.FilePath,
http://haskell.org/haskellwiki/FilePath, which is more a personal todo
list, but if people want to summarise/propose things then feel free :)

Thanks

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


[Haskell-cafe] announce: (preliminary) dbus haskell bindings

2006-07-17 Thread Evan Martin

D-Bus is a message bus system, a simple way for applications to talk
to one another. [1]
It's particularly popular on free software desktops (Gnome, KDE).
HDBus wraps the DBus APIs so your Haskell code can broadcast messages
and make calls to services.  For example, on my recent Ubuntu system,
these bindings are sufficient to pop up balloon-tip-style
notifications via a daemon I wasn't previously aware of.

Very preliminary code, so please let me know if you find it useful.
(Also, I don't know where it's appropriate to announce this, so please
direct me to other mailing lists.)

Home page: http://neugierig.org/software/hdbus/
Haddock: http://neugierig.org/software/hdbus/doc/
Repository browser:
http://neugierig.org/software/darcs/browse/?r=hdbus;a=summary

[1] http://www.freedesktop.org/wiki/Software/dbus
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Gtk2hs-devel] announce: (preliminary) dbus haskell bindings

2006-07-17 Thread Duncan Coutts
That's great Evan!

I had actually been hoping that we'd get a student to do D-Bus bindings
for a Google Summer of Code project. Sadly we didn't get quite enough
places assigned for a D-Bus project to make it into our list.

I would be happy to include D-Bus bindings with Gtk2Hs as it's generally
been our intention to increase our coverage of the Gnome platform (while
of course preserving cross-platform support for the cross-platform
components like Gtk+, glade etc).

I've not looked carefully at the API yet but one suggestion I'd make
would be to put it under the System namespace, ie System.DBus

I see you're binding to the low level C API, I figured that'd be the
best approach.

Duncan

On Tue, 2006-07-18 at 09:04 +0900, Evan Martin wrote:
 D-Bus is a message bus system, a simple way for applications to talk
 to one another. [1]
 It's particularly popular on free software desktops (Gnome, KDE).
 HDBus wraps the DBus APIs so your Haskell code can broadcast messages
 and make calls to services.  For example, on my recent Ubuntu system,
 these bindings are sufficient to pop up balloon-tip-style
 notifications via a daemon I wasn't previously aware of.
 
 Very preliminary code, so please let me know if you find it useful.
 (Also, I don't know where it's appropriate to announce this, so please
 direct me to other mailing lists.)
 
 Home page: http://neugierig.org/software/hdbus/
 Haddock: http://neugierig.org/software/hdbus/doc/
 Repository browser:
 http://neugierig.org/software/darcs/browse/?r=hdbus;a=summary
 
 [1] http://www.freedesktop.org/wiki/Software/dbus
 
 -
 Take Surveys. Earn Cash. Influence the Future of IT
 Join SourceForge.net's Techsay panel and you'll get the chance to share your
 opinions on IT  business topics through brief surveys -- and earn cash
 http://www.techsay.com/default.php?page=join.phpp=sourceforgeCID=DEVDEV
 ___
 Gtk2hs-devel mailing list
 [EMAIL PROTECTED]
 https://lists.sourceforge.net/lists/listinfo/gtk2hs-devel

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


[Haskell-cafe] Re: Type-Level Naturals Like Prolog?

2006-07-17 Thread Jared Warren

Thank you to everyone for the responses. I guess what I should have
clarified is that I know how Peano numbers are *normally* encoded in
the type language (I am very familiar with the HList library), but I
would like to know why the type language appears to require data
structures to do so while [Idealised] Prolog has none.

Niklas Broberg helpfully corrected my Prolog:


That is not a valid encoding of peano numbers in prolog, so I think
that's where your problems stem from. :-)

% defining natural numbers
natural(zero).
natural(s(X)) :- natural(X).

% translate to integers
toInt(zero, 0).
toInt(s(X), N) :- toInt(X, Y), N is Y + 1.


Thank you. I can now more precisely state that what I'm trying to
figure out is: what is 's', a predicate or a data structure? If it's a
predicate, where are its instances? If not, what is the difference
between the type language and Prolog such that the type language
requires data structures?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Type-Level Naturals Like Prolog?

2006-07-17 Thread Donald Bruce Stewart
jawarren:
 Thank you to everyone for the responses. I guess what I should have
 clarified is that I know how Peano numbers are *normally* encoded in
 the type language (I am very familiar with the HList library), but I
 would like to know why the type language appears to require data
 structures to do so while [Idealised] Prolog has none.
 
 Niklas Broberg helpfully corrected my Prolog:
 
 That is not a valid encoding of peano numbers in prolog, so I think
 that's where your problems stem from. :-)
 
 % defining natural numbers
 natural(zero).
 natural(s(X)) :- natural(X).
 
 % translate to integers
 toInt(zero, 0).
 toInt(s(X), N) :- toInt(X, Y), N is Y + 1.
 
 Thank you. I can now more precisely state that what I'm trying to
 figure out is: what is 's', a predicate or a data structure? If it's a
 predicate, where are its instances? If not, what is the difference
 between the type language and Prolog such that the type language
 requires data structures?

It shouldn't actually require new data structures, just new types (with
no inhabiting values).

such as,
data Zero
data Succ a

So there are no values of this type (other than bottom).
That is, you can just see 'data' here as a way of producing new types to
play with in the type checker.

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