Re: [Haskell-cafe] Re: Resending: MissingH: profiler support?

2007-01-12 Thread Gregory Wright


Hi John,

On Jan 12, 2007, at 10:25 AM, John Goerzen wrote:


On Fri, Jan 12, 2007 at 08:10:47AM -0500, Gregory Wright wrote:

-- John


Does MissingH's cabal file have a line

Ghc-Prof-Options:   -prof -auto-all


No, it doesn't.  None of my Cabal files do.  Could anyone confirm if
this fixes it?


The rhs of the option is added to compiler command line when the
--enable-library-profiling option is included to configure.  Without
this,
the --enable-library-profiling switch doesn't do anything.   
(Arguably a

bug that cabal silently does nothing instead of reporting an error.)


I'd argue that Cabal should make this a default.  It seems silly to  
have
to add this boilerplate code to every cabal file out there just to  
have

a sensible default.



Actually, for some reason my brain missed that your were talking about
a library, not an application.  As lemmih said, --enable-executable- 
profiling
will make you a profiling library.  If you are building an app  
however, unless
you include a "Ghc-Prof-Options" something like the above, or add  
cost center
annotations yourself, you just get a profile that tells you that Main  
took 100% of

the time.

Best,
Greg


Thanks for the info.

-- John
___
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] Re: Resending: MissingH: profiler support?

2007-01-12 Thread Gregory Wright


Hi John,

On Jan 11, 2007, at 8:06 PM, John Goerzen wrote:


On 2007-01-11, Chris Eidhof <[EMAIL PROTECTED]> wrote:

Hey,

does anyone know about this? Resending as I got no replies (yet) ;)


Just for the record, I have no idea; I've never really used profiling
and couldn't figure out how to make it work in general (at least  
not in

a short amount of time).

Are you sure your problem is restricted to MissingH?  I can't think of
anything special about it that would throw off profiling.

-- John


Does MissingH's cabal file have a line

Ghc-Prof-Options:   -prof -auto-all

?

The rhs of the option is added to compiler command line when the
--enable-library-profiling option is included to configure.  Without  
this,

the --enable-library-profiling switch doesn't do anything.  (Arguably a
bug that cabal silently does nothing instead of reporting an error.)

Best Wishes,
Greg


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


Re: [Haskell-cafe] UDP client/server

2007-01-11 Thread Gregory Wright


Hi John,

On Jan 11, 2007, at 10:35 AM, Gregory Wright wrote:



Hi John,

On Jan 11, 2007, at 1:58 AM, John Ky wrote:


Hello,

Does anyone know where I can find a simple UDP client/server  
written in Haskell?


Something along the lines of an echo server would do.

Thanks

-John



Try:






For testing, you need only use

gregory-wrights-powerbook-g4-17> nc -ul -p 9900 127.0.0.1

and whatever you type should be echoed.  My original description
of how to test:


On my OS X/ppc 10.4.8 system, the above builds with ghc 6.6 and if  
I open one

terminal with

gregory-wrights-powerbook-g4-17> nc -u 127.0.0.1 9900

and another with

gregory-wrights-powerbook-g4-17> nc -ul -p 9900 127.0.0.1

whatever I type into the first terminal appears on the second.  You  
may have to
consult your documentation for the options to your version of nc  
(or netcat,

if you use that instead).


is wrong.  (It will copy from one terminal to the other when the  
daemon is not present.)


Best,
Greg

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


Re: [Haskell-cafe] UDP client/server

2007-01-11 Thread Gregory Wright


Hi John,

On Jan 11, 2007, at 1:58 AM, John Ky wrote:


Hello,

Does anyone know where I can find a simple UDP client/server  
written in Haskell?


Something along the lines of an echo server would do.

Thanks

-John



Try:

--
-- UDPEchoServer.hs: Exactly what the name says, a datagram echo server.
--


module Main (main) where

import Network.Socket
import System.Posix.Directory
import System.Posix.Files
import System.Posix.IO
import System.Posix.Process
import System.Exit


echoPort = 9900
maxline = 1500

--
-- The daemon infrastructure
--

main :: IO ()
main = do
  pid <- forkProcess child
  exitImmediately ExitSuccess


child :: IO ()
child = do
  -- Set up the working directory, mask and standard i/o
  -- for a daemon process (these will be inherited by
  -- the forked process):

  changeWorkingDirectory "/"
  setFileCreationMask 0

  mapM_ closeFd [stdInput, stdOutput, stdError]
  nullFd <- openFd "/dev/null" ReadWrite Nothing  
defaultFileFlags

  mapM_ (dupTo nullFd) [stdInput, stdOutput, stdError]

  closeFd nullFd

  createSession -- This child becomes a process and session
-- group leader. This prevents the child of
-- this process (the daemon) from
-- ever getting a controlling terminal.
  pid' <- forkProcess echoserver

  exitImmediately ExitSuccess

--
-- The echo server daemon
--

echoserver :: IO ()
echoserver = do
  withSocketsDo $ do
  sock <- socket AF_INET Datagram 0
  bindSocket sock (SockAddrInet echoPort iNADDR_ANY)
  socketEcho sock


socketEcho :: Socket -> IO ()
socketEcho sock = do
  (mesg, recv_count, client) <- recvFrom sock maxline
  send_count <- sendTo sock mesg client
  socketEcho sock



 
---



On my OS X/ppc 10.4.8 system, the above builds with ghc 6.6 and if I  
open one

terminal with

gregory-wrights-powerbook-g4-17> nc -u 127.0.0.1 9900

and another with

gregory-wrights-powerbook-g4-17> nc -ul -p 9900 127.0.0.1

whatever I type into the first terminal appears on the second.  You  
may have to
consult your documentation for the options to your version of nc (or  
netcat,

if you use that instead).

I was also able to see that the server returned packets using hping3.

Needless to say, the above is just an example, and is by no means  
bulletproof.
I think I adapted it from something I found on the old wiki and  
updated it

to work with the current libraries.

Best Wishes,
Greg




 
___

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


Re: [Haskell-cafe] Error building Edison 1.2.0.1

2006-10-19 Thread Gregory Wright


On Oct 18, 2006, at 8:47 AM, Robert Dockins wrote:



On Oct 17, 2006, at 1:46 PM, Gregory Wright wrote:



On Oct 17, 2006, at 1:07 PM, Robert Dockins wrote:



On Oct 17, 2006, at 12:55 PM, Gregory Wright wrote:



Hi Rob,

I've built Edison 1.2.0.1 using ghc-6.6.  (I'm testing the  
macports,

formerly darwinports, packages for the new 6.6 release.)

The build goes fine, but the ./Setup register fails claiming  
that the directory
/opt/local/lib/EdisonAPI-1.2/ghc-6.6/include does not exist.  I  
can make the
directory by hand, and the registration works.  I have an ugly  
workaround,
but I wanted to check with you that this is really a cabal bug.   
Installation

using ghc-6.4.2 on OS X/ppc worked just fine for me.

Best Wishes,
Greg



I'm not doing anything unusual with the cabal scripts (that I'm  
aware of!), so I expect this is a cabal or GHC bug.


BTW, could you run the test suite if you get a moment?  Every  
data point helps.





Hi Rob,

OK, it looks like cabal has gone slightly broken again. :-(



Any idea what the problem is?  Or why other people aren't yelling  
about it?  Is it only the "register" command that is broken?




I don't know what the problem is yet.  It only affects the "register"  
command, which I suspect is

lightly tested.

It may be moot, since I have discovered more infelicities when using  
cabal and macports together.
Macports allows an applications tree to be uninstalled and  
reinstalled.  Uninstallation is done
by removing the installed file; reinstallation is done by unpacking  
them from a tarball.  The
problem here is that the Setup script is not preserved after the  
initial build, so unregistering

and reregistering don't work.

The workaround will likely be to run the ghc-pkg commands directly,  
rather than using
setup.  The cabal folks might want to think about saving setup  
scripts somewhere, so that

"unregister" could be run even if the original build tree were deleted.

I could just unarchive the whole library or application and rebuild  
the setup script, but that

doesn't seem very attractive either.

Best Wishes,
Greg





Here's the test data:

OS X 10.4.8/ppc
PowerBook G4, 1.5 GHz, 1 GB ram
	ghc-6.6, cabal 1.1.6 as distributed with ghc-6.6, built using  
macports


test output:

Welcome to Darwin!
crossroads-able> cd ~/Desktop/edison-1.2.0.1-source/test/
crossroads-able> ./dist/build/testSuite/testSuite
Cases: 1728  Tried: 1728  Errors: 0  Failures: 0
crossroads-able>



Excellent.  That's what I like to see.  Thanks!



Everything looks good but for the package registration.

I should add that I find the Edison package wonderfully easy
to work with.  It has really helped me out while writing simulation
of the custom communication system for a customer.  Many thanks
to you, Rob, and Chris Okasaki for this fine software!

Best Wishes,
Greg



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



___
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] Error building Edison 1.2.0.1

2006-10-17 Thread Gregory Wright


On Oct 17, 2006, at 1:07 PM, Robert Dockins wrote:



On Oct 17, 2006, at 12:55 PM, Gregory Wright wrote:



Hi Rob,

I've built Edison 1.2.0.1 using ghc-6.6.  (I'm testing the macports,
formerly darwinports, packages for the new 6.6 release.)

The build goes fine, but the ./Setup register fails claiming that  
the directory
/opt/local/lib/EdisonAPI-1.2/ghc-6.6/include does not exist.  I  
can make the
directory by hand, and the registration works.  I have an ugly  
workaround,
but I wanted to check with you that this is really a cabal bug.   
Installation

using ghc-6.4.2 on OS X/ppc worked just fine for me.

Best Wishes,
Greg



I'm not doing anything unusual with the cabal scripts (that I'm  
aware of!), so I expect this is a cabal or GHC bug.


BTW, could you run the test suite if you get a moment?  Every data  
point helps.





Hi Rob,

OK, it looks like cabal has gone slightly broken again. :-(

Here's the test data:

OS X 10.4.8/ppc
PowerBook G4, 1.5 GHz, 1 GB ram
ghc-6.6, cabal 1.1.6 as distributed with ghc-6.6, built using macports

test output:

Welcome to Darwin!
crossroads-able> cd ~/Desktop/edison-1.2.0.1-source/test/
crossroads-able> ./dist/build/testSuite/testSuite
Cases: 1728  Tried: 1728  Errors: 0  Failures: 0
crossroads-able>


Everything looks good but for the package registration.

I should add that I find the Edison package wonderfully easy
to work with.  It has really helped me out while writing simulation
of the custom communication system for a customer.  Many thanks
to you, Rob, and Chris Okasaki for this fine software!

Best Wishes,
Greg



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG


___
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] Error building Edison 1.2.0.1

2006-10-17 Thread Gregory Wright


Hi Rob,

I've built Edison 1.2.0.1 using ghc-6.6.  (I'm testing the macports,
formerly darwinports, packages for the new 6.6 release.)

The build goes fine, but the ./Setup register fails claiming that the  
directory
/opt/local/lib/EdisonAPI-1.2/ghc-6.6/include does not exist.  I can  
make the
directory by hand, and the registration works.  I have an ugly  
workaround,
but I wanted to check with you that this is really a cabal bug.   
Installation

using ghc-6.4.2 on OS X/ppc worked just fine for me.

Best Wishes,
Greg

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


Re: Re[2]: [Haskell-cafe] style question: Writer monad or unsafeIOToST?

2006-08-25 Thread Gregory Wright


Hi Bulat,

On Aug 25, 2006, at 3:36 AM, Bulat Ziganshin wrote:


Hello Gregory,

Friday, August 25, 2006, 3:08:09 AM, you wrote:


Some performance data:  using unsafeIOToST to write log messages
directly to the output, the simulation does 10^7 state updates in
about 45 seconds
on my 1.5 GHz ppc G4.  Using LogT, with a list of strings as the  
monoid,

it takes about 7 minutes to do the same, and the system swaps heavily
during the last few minutes.  Not surprising, given that the mappend
operation is not very efficient for the list monoid.


are you sure that you know how monads are implemented? IO/ST monads
just organize order of execution, without any penalty comparing
to imperative languages. but other monads and all monad transformers
add their data to the tuple passed between monad operations. and this
makes their execution significantly slower. you can read more about  
this
in http://sigfpe.blogspot.com/2006/08/you-could-have-invented- 
monads-and.html




No doubt my understanding of the underlying implementation could
be improved.  I will read the reference. Thank you.



about multi-threading - you can (and should!) use ghc's internal
concurrency with forkIO. it is a perfect way - with minimal overhead
and ability to use any Haskell features in each thread without
fighting against multi-threading implementation



I will give this a try when I get to that stage in the project.

Best Wishes,
Greg


--
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
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] style question: Writer monad or unsafeIOToST?

2006-08-24 Thread Gregory Wright


Hi Chris!


On Aug 24, 2006, at 7:28 PM, Chris Kuklewicz wrote:


class Ref m r | m->r where
  newRef
  readRef
  writeRef

instance Ref IO IORef
  writeRef r x = writeIORef r $! x

instance (Ref m r) => Ref (WriterT m) r where
  writeRef = lift . writeRef

and so on...


The code snippet above looks like a very good idea.  The monad
dependent operations combined with "lift" seem more complicated
than necessary.  "lift" in particular often seems like plumbing that
should not be necessary.
Best Wishes,
Greg


Well, lift is the common plumbing that lets you build writeRef and  
liftIO.  So it is an intermediate invention.  In fact it is the  
only thing in MonadTrans:


class MonadTrans (t::(* -> *) -> * -> *) where
  lift :: forall (m::* -> *) a. Monad m => m a -> t m a
-- Imported from Control.Monad.Trans


You are supposed to make higher level shorthand and abstractions  
from it.


But it helps to learn how the plumbing works.


I have no objection to good plumbing (I have some in my house).
I just usually like it to be out of sight in the wall or under the  
floor.


Which does lead to a mess in the case of leaks ;-)

Metaphorically,
Greg


___
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] style question: Writer monad or unsafeIOToST?

2006-08-24 Thread Gregory Wright


Hi Bulat!

On Aug 24, 2006, at 1:17 PM, Bulat Ziganshin wrote:


Hello Gregory,

Thursday, August 24, 2006, 7:29:47 PM, you wrote:


it seems that unsafeIOToST is safe in this case, in the sense that


why you are stuck to ST monad? isn't it better to use just IO monad?



The IO monad may be more appropriate.  The simulation evolved out
of a different (and simpler) simulate for a 6502 microcontroller which
used the ST monad.  I had thought at the time that there may be multiple
threads in the full simulation, so using state threads seemed a good
idea at the time.  (The full simulation may still need multiple threads;
I don't know yet.)

As it stands, the code I had written was almost correct.  I needed a
lazy version of the WriterT monad to make it work.  Chris Kuklewicz
pointed this out to me. The toy model now works with both the lazy  
WriterT

(called LogT here) and the unsafe* operation.

Some performance data:  using unsafeIOToST to write log messages
directly to the output, the simulation does 10^7 state updates in  
about 45 seconds

on my 1.5 GHz ppc G4.  Using LogT, with a list of strings as the monoid,
it takes about 7 minutes to do the same, and the system swaps heavily
during the last few minutes.  Not surprising, given that the mappend
operation is not very efficient for the list monoid.

Is there a simple monoid structure I could use instead of a list to  
generate
the log string incrementally?  I don't care if the order of the  
output is

reversed.


and about total style - again, you can use my lib or write this
yourself so that all you reference operations will work independent on
Monad used and you can freely experiment with different monads without
rewriting whole code:

class Ref m r | m->r where
  newRef
  readRef
  writeRef

instance Ref IO IORef
  writeRef r x = writeIORef r $! x

instance (Ref m r) => Ref (WriterT m) r where
  writeRef = lift . writeRef

and so on...



The code snippet above looks like a very good idea.  The monad
dependent operations combined with "lift" seem more complicated
than necessary.  "lift" in particular often seems like plumbing that
should not be necessary.

Best Wishes,
Greg




ps to Brian: it is why i was so interested in your idea. writing
monad-independent code, including code that can be applied to any
monad lifted from ST or IO, looks for me very promising idea, somewhat
that will be widely used in future


--
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
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: Re[2]: [Haskell-cafe] stack overflow when using ST monad

2006-08-24 Thread Gregory Wright


Hi Bulat!

On Aug 24, 2006, at 1:07 PM, Bulat Ziganshin wrote:


Hello Brian,

Thursday, August 24, 2006, 4:16:41 PM, you wrote:

I would make all the fields strict here, to be sure that no  
lazyness can

creep about unseen eg:



 data Tag s = Tag {
 tagID :: !Int,
 state :: !(STRef s TagState),
 count :: !(STRef s Integer)
   }


perhaps better:

  data Tag s = Tag {
  tagID :: !Int,
  state :: STRef s !TagState,
  count :: STRef s !Integer
}

although i don't even sure that this will compile (in this case we can
request it as wishful feature). in theory, this should allow to omit
'$!' from writeRef calls



Alas, at the moment the last gives (in ghc-6.4.2),

Unexpected strictness annotation: !TagState
In the data type declaration for `Tag'
Failed, modules loaded: none.
Prelude>



also, one can implement strict write operations:

writeRef r x = writeSTRef r $! x

or use my unboxed references (but not with Integer) -
http://haskell.org/haskellwiki/Library/ArrayRef



I will look at this. Thanks!

Best Wishes,
Greg



--
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
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] style question: Writer monad or unsafeIOToST?

2006-08-24 Thread Gregory Wright

Hi Chris,

Thank you.  That is exactly what I needed to know.

It's good to know that I'm not totally crazy and that with the
lazier LogT the code can run as it was written.  It seems
as if a request should be made for a Writer.Lazy as well as
the existing Writer.Strict.  (The latter could well be the default,
just as with the ST monad.)  A good idea?

Virtual beer to you sir!

-Greg

On Aug 24, 2006, at 1:05 PM, Chris Kuklewicz wrote:


The problem with WriterT is it is too strict.

See http://www.mail-archive.com/haskell@haskell.org/msg16088.html

The fix is adding ~ to the patterns inside the definition of (>>=):

~(a,w)  <- runLogT m
~(b,w') <- runLogT (k a)

A lazy version of WriterT, called LogT:


{-# OPTIONS_GHC -fglasgow-exts #-}
module Main where
import Control.Monad.ST.Lazy
import Data.STRef.Lazy
import Control.Monad.Writer
import Control.Monad.Identity
import Control.Monad.Fix
import Control.Monad.Trans
import Control.Monad.Reader
import Maybe
import Debug.Trace
type LogMonoid = [String] -> [String]
loopLT :: Int -> LogT [String] Identity [Int]
loopLT 0 = trace "end of loopLT" (return [0])
loopLT x = do
  let msg = "loopLT now "++ show x
  tell [msg]
  liftM (x:) (loopLT (pred x))
newtype LogT w m a = LogT { runLogT :: m (a, w) }
instance (Monad m) => Functor (LogT w m) where
fmap f m = LogT $ do
(a, w) <- runLogT m
return (f a, w)
instance (Monoid w, Monad m) => Monad (LogT w m) where
return a = LogT $ return (a, mempty)
m >>= k  = LogT $ do
~(a,w)  <- runLogT m
~(b,w') <- runLogT (k a)
return (b, w `mappend` w')
fail msg = LogT $ fail msg
instance (Monoid w, MonadPlus m) => MonadPlus (LogT w m) where
mzero   = LogT mzero
m `mplus` n = LogT $ runLogT m `mplus` runLogT n
instance (Monoid w, MonadFix m) => MonadFix (LogT w m) where
mfix m = LogT $ mfix $ \ ~(a, _) -> runLogT (m a)
instance (Monoid w, Monad m) => MonadWriter w (LogT w m) where
tell   w = LogT $ return ((), w)
listen m = LogT $ do
(a, w) <- runLogT m
return ((a, w), w)
pass   m = LogT $ do
((a, f), w) <- runLogT m
return (a, f w)
instance (Monoid w) => MonadTrans (LogT w) where
lift m = LogT $ do
a <- m
return (a, mempty)
instance (Monoid w, MonadIO m) => MonadIO (LogT w m) where
liftIO = lift . liftIO
-- This instance needs -fallow-undecidable-instances, because --  
it does not satisfy the coverage condition
instance (Monoid w, MonadReader r m) => MonadReader r (LogT w m)  
where

ask   = lift ask
local f m = LogT $ local f (runLogT m)
execLogT :: Monad m => LogT w m a -> m w
execLogT m = do
(_, w) <- runLogT m
return w
mapLogT :: (m (a, w) -> n (b, w')) -> LogT w m a -> LogT w' n b
mapLogT f m = LogT $ f (runLogT m)
main :: IO ()
main = do
  let logLT = runIdentity (execLogT (loopLT 100))
  print (head logLT)
  print (last logLT)


The output is

 ./maindemo
"loopLT now 100"
end of loopLT
"loopLT now 1"

Just as we want.




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


[Haskell-cafe] style question: Writer monad or unsafeIOToST?

2006-08-24 Thread Gregory Wright


Hi,

Thanks to the responses earlier from the list, the core of my simulator
now happy processes tens of millions of state updates without running
out of stack.

The goal of the simulator is to produce a log of tag states, which  
can be
analyzed to find statistics of how often the sensor tags in a  
particular state.
(In the toy model below there is no external signal, so the log isn't  
very
interesting yet.)  For the moment, I am using the "big stick"  
approach of
unsafeIOToST to write log messages.  Since the only outputs of the  
program
are the log messages, and invocations of "step" are ordered by the ST  
monad,
it seems that unsafeIOToST is safe in this case, in the sense that  
the outputs

will all be ordered the same as the actual state updates.

I've tested the program test1.hs below and it quite fast (runs in  
just under 10 s,

or about 10^6 state updates per second).

I've considered using a WriterT monad to wrap the ST monad to produce
a log.  The problem with this seems to be ensuring that the log output
is generated lazily so it can be incrementally output. A somewhat broken
sketch is the program test2.hs below.  I used a function from  
[String] -> [String]
as the monoid to avoid the O(n^2) inefficiency of appending to a  
list, but

my implementation of this may well be faulty.

To my eye, the Writer monad should be a better way, since it  
encapsulates
the logging process, separating it from other I/O that the program  
may do.

On the other hand, I don't see an easy way to ensure that the log output
is generated lazily so that it can be output incrementally.  I think  
that the
main issue is that until_ is building up a list of log strings, but  
that these
aren't passed to the putStrLn until after the completion of the whole  
runTag

function.  ATM, running test2 gives a stack overflow.

Could someone point out how the Writer monad could be adapted to this,
or tell me that,  "Real programmers just use unsafe* and get on with  
it" ?


Best,
greg


 
--


test1.hs, the big stick (unsafeIOToST):

--
-- test1.hs, state updating with logging via unsafeIOToST.
--


module Main where


import Control.Monad.ST
import Data.STRef
import Maybe


data TagState = Syncing | Listening | Sleeping
deriving (Eq, Show)


-- A structure with internal state:
--
data Tag s = Tag {
tagID :: ! Int,
state :: ! (STRef s TagState),
count :: ! (STRef s Integer)
}


data FrozenTag = FrozenTag {
ft_tagID :: Int,
ft_state :: TagState,
ft_count :: Integer
} deriving Show



-- Repeat a computation until it returns Nothing:
--
until_ :: Monad m => m (Maybe a) -> m ()
until_ action = do
result <- action
if isNothing result
   then return ()
   else until_ action


-- Here is a toy stateful computation:
--
runTag :: ST s (FrozenTag)
runTag = do
tag <- initialize
until_ (step tag)
freezeTag tag


initialize :: ST s (Tag s)
initialize = do
init_count <- newSTRef 100
init_state <- newSTRef Syncing

return (Tag { tagID = 1,
  state = init_state,
  count = init_count })


step :: Tag s -> ST s (Maybe Integer)
step t = do
c <- readSTRef (count t)
s <- readSTRef (state t)
writeSTRef (count t) $! (c - 1)
writeSTRef (state t) $! (nextState s)
unsafeIOToST $! putStrLn ("next state is " ++ show s)
if (c <= 0) then return Nothing else return (Just c)


nextState :: TagState -> TagState
nextState s = case s of
Syncing   -> Listening
Listening -> Sleeping
Sleeping  -> Syncing


freezeTag :: Tag s -> ST s (FrozenTag)
freezeTag t = do
frozen_count <- readSTRef (count t)
frozen_state <- readSTRef (state t)

return (FrozenTag { ft_tagID = tagID t,
ft_count = frozen_count,
ft_state = frozen_state })


main :: IO ()
main = do
print $ runST (runTag)






 
-


test2.hs: stacked WriterT and ST monads:

--
-- test2.hs, state updating with logging via the WriterT monad.
--


module Main where


import Control.Monad.ST
import Control.Monad.Writer
import Data.STRef
import Maybe


data TagState = Syncing | Listening | Sleeping
deriving (Eq, Show)


-- A type for combined logging and state transformation:
--
type LogMonoid = [String] -> [String]
type LogST s a = WriterT LogMonoid (ST s) a


-- A structure with internal state:
--
data Tag s = Tag {
tagID :: ! Int,
state :: ! (STRef s TagState),
count :: ! (STRef s Integer)
}


data FrozenTag = FrozenTag {
ft_tagID :: Int,
ft_state :: TagState,
ft_count :: Integer
} deriving Sho

Re: [Haskell-cafe] stack overflow when using ST monad

2006-08-24 Thread Gregory Wright


Hi Udo,

On Aug 24, 2006, at 7:22 AM, Udo Stenzel wrote:


Hi Gregory,

Gregory Wright wrote:

step :: Tag s -> ST s (Maybe Integer)
step t = do
c <- readSTRef (count t)
s <- readSTRef (state t)
writeSTRef (count t) (c - 1)
writeSTRef (state t) (nextState s)
if (c <= 0) then return Nothing else return (Just c)


just looking at the program, this seems to be the problem: writeSTRef
does not force the evaluation of the stored value.  So after repeated
calculation, you end up storing not the current counter and state, but
something like (nextState (...(nextState (nextState initState))...)).
The counter is evaluated for the conditional at the end, so it doesn't
exhibit this problem.  Your computation runs to its end, then that
deeply nested expression is evaluated and exhausts the control stack.
Try this instead:


writeSTRef (state t) $! nextState s


If TagState is a more complicated data type, you may also need strict
fields in there.

[This comes up so often, shouldn't there be an FAQ about it  
somewhere?  It
could even offer a guideline along the lines of "Whenever you  
repeatedly

update some value, chances are that you want to force strict
evaluation."]



I agree this should be a FAQ.  Perhaps I should write it up for the
performance section of the wiki?  Looking back I see my mental error
was that I thought I was doing what you and everyone else correctly
suggested:

writeSTRef (state t) $! nextState s

but what I actually typed was

writeSTRef (state t) (nextState $! s)

which of course doesn't help.  Another telling example
of the fact that coffee is not an entirely adequate substitute for
sleep.

Best,
Greg



Udo.
___
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] stack overflow when using ST monad

2006-08-24 Thread Gregory Wright


Hi Bulat,

On Aug 24, 2006, at 7:52 AM, Bulat Ziganshin wrote:


Hello Gregory,

Thursday, August 24, 2006, 2:29:15 PM, you wrote:


step t = do
 c <- readSTRef (count t)
 s <- readSTRef (state t)
 writeSTRef (count t) (c - 1)
 writeSTRef (state t) (nextState s)
 if (c <= 0) then return Nothing else return (Just c)


as Chris said, you are write unevaluated chunks.

add $! to evaluate values before writing:

  writeSTRef (count t) $! (c - 1)
  writeSTRef (state t) $! (nextState s)



That fixed it exactly.  Thank you Bulat and Chris!

Best Wishes,
Greg



--
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


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


[Haskell-cafe] stack overflow when using ST monad

2006-08-24 Thread Gregory Wright


Hi,

I have a program, abstracted from a larger application that I am
writing for a customer, that persistently overflows its stack.  The
program is a simulation of the communication protocol of a
sensor tag.  The code is below.

The program mimics a hardware state machine.  In the example
below, the internal state is just a counter and a another register
that holds what is called the tag's "state": Syncing, Listening or
Sleeping.  The simulation just advances the tags internal
state until the counter reaches zero.  (In the real application, there
are external inputs that can change the state, but that's not needed
to see the problem.)

The simulation crashes, running out of stack space after only about
40 cycles on my machine  (OS X 10.4.7 ppc).  Both hugs and
ghci show it:

hugs -98 Test2.hs

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

Type :? for help
Main> main

ERROR - Garbage collection fails to reclaim sufficient space
Main>

and ghci:

Prelude> :load "/Users/gwright/src/haskell/simulator/test2.hs"
Compiling Main ( /Users/gwright/src/haskell/simulator/ 
test2.hs, interpreted )

Ok, modules loaded: Main.
*Main> main
FrozenTag {ft_tagID = 1, ft_state = *** Exception: stack overflow
*Main>


Searches through old mailing lists warn me that it can be hard to tell
if evaluation is truly tail recursive, and I saw a discussion of this  
in the

context of "monadic loops", but I never saw a solution.  Perhaps
in my sleep deprived condition I am missing the obvious, but any
help would be appreciated.

Best,
Greg



--
-- Test the state transformer calculation.
--
-- 21 August 2006
--


module Main where


import Control.Monad.ST
import Control.Monad.Writer
import Data.STRef
import Maybe


data TagState = Syncing | Listening | Sleeping
deriving (Eq, Show)


-- A structure with internal state:
--
data Tag s = Tag {
tagID :: Int,
state :: STRef s TagState,
count :: STRef s Integer
}


data FrozenTag = FrozenTag {
ft_tagID :: Int,
ft_state :: TagState,
ft_count :: Integer
} deriving Show



-- Repeat a computation until it returns Nothing:
--
until_ :: Monad m => m (Maybe a) -> m ()
until_ action = do
result <- action
if isNothing result
   then return ()
   else until_ action


-- Here is a toy stateful computation:
--
runTag :: ST s (FrozenTag)
runTag = do
tag <- initialize
until_ (step tag)
freezeTag tag


initialize :: ST s (Tag s)
initialize = do
init_count <- newSTRef 100
init_state <- newSTRef Syncing

return (Tag { tagID = 1,
  state = init_state,
  count = init_count })


step :: Tag s -> ST s (Maybe Integer)
step t = do
c <- readSTRef (count t)
s <- readSTRef (state t)
writeSTRef (count t) (c - 1)
writeSTRef (state t) (nextState s)
if (c <= 0) then return Nothing else return (Just c)


nextState :: TagState -> TagState
nextState s = case s of
Syncing   -> Listening
Listening -> Sleeping
Sleeping  -> Syncing


freezeTag :: Tag s -> ST s (FrozenTag)
freezeTag t = do
frozen_count <- readSTRef (count t)
frozen_state <- readSTRef (state t)

return (FrozenTag { ft_tagID = tagID t,
ft_count = frozen_count,
ft_state = frozen_state })


main :: IO ()
main = do
putStrLn (show (runST runTag))

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


Re: [Haskell-cafe] Porting GHC to OSX86?

2006-03-22 Thread Gregory Wright


Hi,

DP will support the i386 build as soon as Wolfgang makes his
changes available.  As I understand, from earlier messages on one
of the ghc* lists, this is almost done for the pre-6.6 branch, but not
yet backported to the 6.4.x branch.

Also, DP uses a binary bootstrap compiler to build ghc, rather than
starting from the .hc files.  I've been meaning to try it, but I can't
promise any schedule as work and life have distracted me from
code recently.

Best Wishes,
Greg

(darwinports ghc maintainer)


On Mar 22, 2006, at 6:16 AM, Deling Ren wrote:


It's not supported on i386 platform yet :(

On Mar 22, 2006, at 12:34 AM, Thomas Davie wrote:



On Mar 21, 2006, at 8:09 PM, Deling Ren wrote:


Hi there,

Has anyone made any attempt to port GHC to Mac OS X on x86?  
Wolfgang Thaller’s binary package runs over Rosetta but slow (not  
surprising). It can not be used to compile a native version  
either (I got some errors related to machine registers).


I tried to do a bootstrap but can't find the ".HC" files  
mentioned in the manual. They don't seem to be on the download  
page of GHC. Any ideas?


Why not use darwin ports to build it?

Bob


___
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] Must be a FAQ - Can't make install Hugs98-Nov2003 on MacOSX 10.3.8

2005-02-25 Thread Gregory Wright
Hi,
The hugs98-20041101 snapshot builds without trouble on OS X 10.3.8.
(It's the one I use in darwinports for hugs98-devel).  Our standard DP 
hugs98
is still the Nov2002 version, since I was never able to get the Nov2003 
release
to build properly.

(If your not familiar with darwinports, see 
http://darwinports.opendarwin.org.
It is in some ways similar to fink, but is intended to be a more 
flexible building/
packaging infrastructure.)

If you do decide to set up darwinports on your system, you can build the
20041101 snapshot from source by typing
sudo port install hugs98-devel
Remember to add the darwinports binary directory (/opt/local/bin by 
default)
to your path.

If you want to watch the progress of the build, use
sudo port -dv install hugs98-devel
(the -dv option gives you verbose debugging, and will let you see all
of the output from the build).
Best Wishes,
Greg

On Feb 25, 2005, at 4:56 PM, Sven Panne wrote:
Arthur Baars wrote:
See the hugs-bugs archive:
http://www.mail-archive.com/hugs-bugs@haskell.org/msg02815.html
Malcolm Wallace wrote:
The configure script is (wrongly) determining that the MacOS X C
compiler does not support Floats/Doubles.  Ideally, the autoconf 
magic
which determined this setting should be fixed, [...]
Hmmm, I'm not sure if the autoconf magic has been fixed. Does it work 
with Hugs from
CVS HEAD? If not, could somebody please send a patch for it or at 
least a log + all
involved config.logs? I don't have access to a Mac...

Cheers,
   S.
___
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] File path programme

2005-01-27 Thread Gregory Wright
Hello,
On Jan 27, 2005, at 10:46 AM, Krasimir Angelov wrote:
Hello Guys,
Let me propose another solution which is simpler (at least from my
point of view)and will not break the existing. When I designed the API
of the original System.FilePath library I looked at OS.Path modules
from Python and ML. They both uses plain string to keep the file path
but does precise parsing/printing of the path when it is manipulated.
I haven't ever heard of any language that uses special FilePath type
instead of plain string. I don't want to do any parsing/printing each
time when I need to open file or create directory. In most cases the
file path is passed as string from the outside world to the
application and if we have special FilePath then we need each time to
parse it. What I propose is the following:
Actually, Common Lisp specifies a special data type to handle logical
filepaths, which are distinct from file path strings.  Having had to 
debug
common lisp code that uses this (written by other people) I've observed
that this attempt to do the "Right Thing" almost certainly has caused
more trouble than it has solved.

While an abstract filepath isolates you from having to deal with the
syntax of file paths on different systems, it does not provide an 
abstract
view of the filesystem hierarchy.  These differ greatly, even among
unix-like systems.  Handling differences in the file system hierarchy
inevitably results in a lot of system specific code, for any program 
that
has to use files scattered across a system.


 - Keep the existing System.IO API the same. openFile, createDirectory
... will take the file path as string.
 - Introduce two new modules System.Posix.FilePath and
System.Win32.FilePath. Each of them will provide functions for
parsing/printing of paths to/from some platform specific type:
PosixFilePath and Win32FilePath. As you can see from Robert Dockins
examples, these types can be completely different.
 - Introduce third module System.FilePath which will do some basic
operations of path through parsing/printing. The API of this module
can be similar to this which I wrote but its implementation can be
more accurate if it works on some ADT instead of string. The module
will use #ifdef in order to import the right from the above two
modules.
 In most cases we do only simple manipulations on path and I don't
think it is required and easy to explicitly parse/print the path only
in order to change its extension. I prefer to invoke changeFileExt and
don't care how the function will do its job. If someone would like to
perform any more complicated operations on file path he can import the
system specific module and use PosixFilePath or Win32FilePath. This is
basically the way in which OS.Path is implemented in ML.

Your proposal above for a lightweight solution seems the right way
to go.  If there is really a need for a higher layer it could be built 
upon
something like you suggest.

One thing that the library shouldn't exclude is the manipulation
of non-native file paths.  For example, I on my unix system I may want
to generate a win32 file path as part of some code that will be executed
on Windows machine.  The underlying os-specific modules should always
be available, even if there is a module for file path manipulations 
specific
to the host-OS. (If I understand correctly, this is what you've proposed
with the System.FilePath.)


The type class solution doesn't work very well. As Simon said it may
require to have #ifdef-s in some places in order to choice the right
type. Another disadvantage is that this will complicate some data
types. Example:
data FilePath a => MyFileInfo a = MyFileInfo { path :: a; size :: 
Integer }

I don't want to add extra type parameters here only in order to
specify the right FilePath type.
Cheers,
 Krasimir
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] problem building hmake on Mac OS X

2004-12-02 Thread Gregory Wright
Hi Steve,
I see that Malcolm Wallace has already answered your question,
but you might be interested in some of the other haskell tools
for OS X supported under darwinports. See 
http://darwinports.opendarwin.org

hmake is supported, as well as a the new haskell-mode for emacs
and a bunch of other stuff (e.g. alex, happy, hat, buddha, haskelldb).
I support most of the tools, so feel free to ask questions.
Best Wishes,
Greg
On Dec 2, 2004, at 5:05 AM, Steven Elkins wrote:
Hello everyone,
I'm trying to build hmake on version 10.3.6 of Mac OS, having
installed the ghc 6.2.2 dmg I found on haskell.org, but I'm
encountering the following problem:
Steven-Elkins-Computer:~/haskell/hmake-3.09 sge$ make
cd src/hmake;  make HC=ghc all config
/Users/sge/haskell/hmake-3.09/lib/powerpc-Darwin7/config:9: ***
missing separator.  Stop.
make: *** [targets/powerpc-Darwin7/hmake-ghc] Error 2
Here's lib/powerpc-Darwin7/config:
Steven-Elkins-Computer:~/haskell/hmake-3.09 sge$ cat
lib/powerpc-Darwin7/config
BUILDWITH=ghc
BUILDOPTS=""
INSTALLVER="3.09 (2004-11-13)"
INSTALLINFO="config: powerpc-Darwin7/ by
[EMAIL PROTECTED] on Thu Dec  2 04:43:46 EST 2004"
BUILDBASEDIR=/Users/sge/haskell/hmake-3.09/targets
READLINE="-DUSE_READLINE=1 -lreadline"
EXE=
GHCSYM=#pragma GCC set_debug_pwd "/Users/sge/haskell/hmake-3.09"
602
TRUE=/usr/bin/true
In case Gmail wraps this, line 9 has the oracular '602'.
Finally, here's the ./configure output:
Steven-Elkins-Computer:~/haskell/hmake-3.09 sge$ ./configure 
--prefix=/usr/local
Configuring for hmake... [ 3.09 (2004-11-13) ]

Looking for already-installed Haskell compilers:
  Looking for hbc...   (not found)
  Note: LMLDIR/HBCDIR variables must be set to enable detection of hbc.
  Looking for ghc...   found 6.2.2
  Looking for nhc98... (not found)
I am guessing that you want to use ghc to build hmake.
  Now I'm creating targets/powerpc-Darwin7/hmake3.config for your 
installation.
Done.

   Configuration report for hmake.
(You can re-run configure to change settings before proceeding.)
You wish (eventually) to install the following components in these 
locations:
(Installation directories are not created/checked at this stage.)
Final install root:   /usr/local
hmake binaries:   /usr/local/lib/hmake/powerpc-Darwin7
Scripts:  /usr/local/bin
Man pages:/usr/local/man/man1

Now we check/create your build directories:
Config directory:  targets/powerpc-Darwin7
Build directory root:
/Users/sge/haskell/hmake-3.09/targets (exists)
Object files build in:
/Users/sge/haskell/hmake-3.09/targets/powerpc-Darwin7 (exists)
Executables and libs:
/Users/sge/haskell/hmake-3.09/lib/powerpc-Darwin7 (created)
I have guessed you will build hmake with:   ghc
Testing for the curses library: -lncurses (detected)
Testing for the readline library:   -lreadline (detected)
Executables need .exe suffix?   no  (detected)
Found /usr/bin/true not /bin/true
Adding Makefile config script to
/Users/sge/haskell/hmake-3.09/lib/powerpc-Darwin7...
Adding build scripts for hmake, hmake-config, and hi to
/Users/sge/haskell/hmake-3.09/script...
Updating targets/powerpc-Darwin7/hmake3.config...
Saving current configuration in targets/powerpc-Darwin7/config.cache
Done.
Steven-Elkins-Computer:~/haskell/hmake-3.09 sge$
Thanks,
Steve
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHC and OS X (10.4)

2004-09-02 Thread Gregory Wright
Hi Tom,
You might try building ghc using darwinports 
(darwinports.opendarwin.org).
It works under both Jaguar and Panther. I maintain the port, and would 
be
interested in your experience on 10.4-beta.  (The darwinports version 
doesn't
use /Library/Frameworks, instead it keeps everything in a unix-style 
lib/
hierarchy.)

The downside is that it takes a few hours to build.
Best Wishes,
Greg Wright
On Sep 2, 2004, at 5:06 PM, Tom Davie wrote:
Hi,
  I've been attempting to use GHC on a beta copy of Mac OS X 10.4,
I've been attmepting to use the panther version of the install
package, but have hit a problem with tinkering with it - I get the
following error when I attempt to run ghc:
Verenia:~/Documents/Development/XBridgeAI tatd100$ ghc
dyld: Library not found: 
HaskellSupport.framework/Versions/A/HaskellSupport
  Referenced from: /usr/local/lib/ghc-6.2.1/ghc-6.2.1
  Reason: file not found
Trace/BPT trap

The framework is present in /Library/Frameworks, and
/Library/Frameworks is in dyld's framework search path.
Any Mac/Haskell gurus able to help I would much appreciate it.
Thanks
Tom Davie
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] x11 libs

2004-06-17 Thread Gregory Wright
Hi Matt,
Just for reference, you need the X11 SDK from Apple's developer
site, in addition to the usual X11 binaries.  Sometimes people download
only the latter and discover they can't compile programs that use X11.
Let me know if you have trouble with the darwinports installed GHC,
since I maintain that.
Best Wishes,
Greg
Gregory Wright
Antiope Associates LLC
[EMAIL PROTECTED]

On Jun 17, 2004, at 3:28 AM, Matthew Roberts wrote:
Sorry
I have found it now.  I was a bit quick on the email trigger.  NOw to
install it.
Matt
On Thu, 17 Jun 2004, Matthew Roberts wrote:
I have ghc installed on OSX 10.3 via darwin ports.  I have no X11 
libs and
I can't find anywhere on the web to get them.

Can anyone help me out?
Cheers,
Matt
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] C Bindings?

2004-04-13 Thread Gregory Wright
Hi,

The Foreign Function Interface (FFI) is your friend for these tasks:

http://www.cse.unsw.edu.au/~chak/haskell/ffi/

On the haskell.org web page, under "libraries and tools" there are 
links to
a number of tools to help you connect your C & haskell programs.
The GreenCard and c->haskell tools seem to be used by a number
of people.

Alastair Reid's Guide to Haskell's Foreign Function Interface,

http://www.reid-consulting-uk.ltd.uk/docs/ffi.html

is a good place to start. It has some comparison of the various tools.

Best Wishes,
Greg
On Apr 13, 2004, at 12:56 PM, Russ Lewis wrote:

Does Haskell have some mechanism that allows it to link to C, or other 
imperative languages?

I know, you could use the IO Monad to do it...using stdin and stdout 
as pipes to any other program.  But is there a way to link Haskell 
into a C program?

Thanks again for the help for a newbie...
   Russ
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Producing fortran/C code with haskell?

2004-01-30 Thread Gregory Wright
On Jan 30, 2004, at 1:32 PM, Vincenzo aka Nick Name wrote:

I seem to recall a discussion, don't know if it was here or on
comp.lang.functional, where somebody said he uses haskell to generate
fortran code.
That fascinated me a lot, because that would mean being able to 
generate
a program already specialized for a specific input, by first reading
input in haskell and then producing code (fortran, but could be C
either) - and because I guess it can add static safety exploiting
haskell types. Since we already have that nice syntax for monads those
programs should be readable, too.

Where could I find information on such topics, or existing libraries to
generate programs with haskell? Is somebody willing to share what (s)he
already did?
V.

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

You might try looking at http://www.fftw.org. They use an Objective 
Caml program
to generate optimized C fourier transforms for various machine 
architectures.

Best Wishes,
Greg


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


Re: [Haskell-cafe] Interpreting fields in a buffer

2004-01-26 Thread Gregory Wright
Mikael,

Thanks, that's very helpful and seems to be just the sort of
thing I'm looking for.
Greg

On Jan 26, 2004, at 6:05 PM, Mikael Brockman wrote:
You'll probably want to take a look at Erlang's so called ``bit 
syntax''
at http://www.erlang.se/euc/00/bit_syntax.html.  It's very nifty, and
I'd love to see it (or something equally convenient) as a Haskell
extension.

Hugs and kisses,
Mikael Brockman
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Interpreting fields in a buffer

2004-01-26 Thread Gregory Wright


Hi Dominic,

First, thanks to everyone for their help.

RIght now, I'm leaning toward Dominic's solution of a collection
of helper functions, but I have the feeling that we should be generating
them automatically. After all, given a buffer that consists of packed,
fixed width fields, if we specify a name and width of the field, making
the helper functions should be straightforward. (I understand the
network byte order issues. Since I won't always have to examine each
field, I wasn't going to convert all fields to host byte order, rather 
only
convert the ones I needed to examine.)

It's a little strange that we seem to have to use template haskell or
some other preprocessor to do this. Rather like using a sledgehammer
to crack a walnut.
I'll try to come up with something of general use. I'm very interested 
to
see Tom's (de)serialization framework. As long as this problem is going
to require TH, we may as well solve more than one problem.

And now I let you return to your discussion of the tab character ;-)

Best Wishes,
Greg


On Jan 26, 2004, at 11:13 AM, Dominic Steinitz wrote:

Gregory,

I don't know if this helps but I ended creating functions like the ones
below (I didn't need to use the C structures because the IP definition 
is
language independent). I'm sure there are better ways and I didn't 
test the
throughput but I was able to develop a Haskell version of ping and
traceroute (both multi-threaded). It would be nice if there were a 
library
so that we didn't end up re-inventing the wheel.

Dominic.

ipHeaderLength :: String -> Int
ipHeaderLength s = (fromIntegral (ord (s !! 0)) .&. 0x0f) * 4
ipTTL :: String -> Int
ipTTL s = fromIntegral (ord (s !! 8))
ipProtocol :: String -> IPProto
ipProtocol s = toEnum (ord (s !! 9))
ipDestAddr :: String -> HostAddress
ipDestAddr s = fromIntegral (ord (s !! 16)) `shiftL` 24 +
   fromIntegral (ord (s !! 17)) `shiftL` 16 +
   fromIntegral (ord (s !! 18)) `shiftL` 8 +
   fromIntegral (ord (s !! 19))
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Interpreting fields in a buffer

2004-01-25 Thread Gregory Wright
Hi,

I have a question related to a program I'm writing. I have to handle IP 
packets,
which will be read into a buffer. What is the best haskell idiom for 
getting access
to the fields in the buffer?

The IP header has a number of fixed format fields. In C, I would define 
a struct,
then cast the pointer to the beginning of the buffer to a pointer to 
the struct. I would then be
able to access each field in the header as  -> 
.

Is there a way in haskell to declare the format of the header, then 
access the
components of the buffer as elements of those types? I'm only going to 
do read
access on the buffer (an unboxed array). Most fields won't be examined 
but I can't
tell in advance which ones will have to be looked at.

I've not seen an example of this kind and was wondering if this was
especially awkward.
Thanks.

Best Wishes,
Greg
Gregory Wright
Antiope Associates LLC
18 Clay Street
Fair Haven, New Jersey 07704
[EMAIL PROTECTED]

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


Re: OT - Book on Programming

2003-09-03 Thread Gregory Wright
On Tuesday, September 2, 2003, at 07:54 PM, Matthew Donadio wrote:
They have several people in the company who understand the mechanics of
programming, but don't really understand the concepts.  I am looking 
for
a book to recommend to them.  I would really like to find a book that
just discusses programming, and avoids any one particular language.  It
would have to cover the common imperative controls, as well as basic
data structures.

In my previous company, I recommended Thomas Standish's
_Data Structure Techniques_. It's out of print, but easily (and 
inexpensively)
available at Amazon. I like the original 1980 edition; his later
_Data Structure Techniques in Java_ is too closely tied to the
Java language.

It covers the usual data structures (lists, trees, strings, etc.) using
pseudocode algorithms. It's at the right level for someone who has
gotten the hang of programming at the level of compiling and
debugging simple programs and is ready to move onto something
more complicated.
Best Wishes,

Greg

Gregory Wright
Antiope Associates
18 Clay Street
Fair Haven, New Jersey 07704
USA
[EMAIL PROTECTED]

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


Re: Pointers in Haskell??

2001-12-07 Thread Gregory Wright


This book is already on-line at

http://research.microsoft.com/Users/simonpj/Papers/student.ps.gz

(It was noted on the "Books and Tutorials" link from haskell.org, which
is usually the best place to start looking for something Haskell.)

Best Wishes,
Greg


On Fri, 2001-12-07 at 12:57, Yoann Padioleau wrote:
> Jan Kort <[EMAIL PROTECTED]> writes:
> 
> > 
> > Simon Peyton-Jones. The implementation of functional
> > programming languages. Prentice-Hall, 1987
> 
> is this book could be made available online ? cos on amazon it seems
> out of print.
> 
> 
> > 
> >   Jan
> > 
> > ___
> > Haskell-Cafe mailing list
> > [EMAIL PROTECTED]
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> > 
> 
> -- 
>   Yoann  Padioleau,  INSA de Rennes, France,
> Opinions expressed here are only mine. Je n'écris qu'à titre personnel.
> **   Get Free. Be Smart.  Simply use Linux and Free Software.   **
> 
> ___________
> Haskell-Cafe mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell-cafe
-- 

Gregory Wright
Chief Technical Officer
PacketStorm Communications, Inc.
20 Meridian Road
Eatontown, New Jersey 07724

1 732 544-2434 ext. 206
1 732 544-2437 [fax]
[EMAIL PROTECTED]



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