Re: [Haskell-cafe] Newbie question about Read strings in a line of File

2005-07-26 Thread Cale Gibbard
Here's how I wrote it:

- beginning of file
import IO

-- turn a line of the text file into a pair consisting of
-- the message triple and the message string
-- slight bug: will contract multiple spaces in the message string
-- This could be rewritten to avoid this problem, but couldn't make as
much use of
-- existing prelude functions to do the work.
readMessage :: String -> ((Integer, Integer, Integer), String)
readMessage line = let (lang:typ:idx:msgWds) = words line
   msg = unwords msgWds
   in ((read lang, read typ, read idx),msg)

-- An IO action which gets a list of such pairs given a filename.
readMessagesFile filename = do hdl <- openFile filename ReadMode
   cs <- hGetContents hdl
   return $ map readMessage (lines cs)

-- An IO action which gets a lookup function for the message codes
given a filename.
getMessageLookup :: String -> IO ((Integer, Integer, Integer) -> Maybe String)
getMessageLookup filename = do msgs <- readMessagesFile filename
   return (flip lookup msgs)
- end of file

You can then test this in GHCi with something like
msgLookup <- getMessageLookup "messages.txt"
msgLookup (1,1,1)
which should result in:
Just "Error message 1"

The values are wrapped in the "Just" constructor, and typed in the
Maybe monad, since the lookup might fail, in which case the msgLookup
will return the value "Nothing". Also note that this is somewhat
inefficient for very large numbers of messages, (lookup will be linear
in the number of messages in the worst case.) To get better
performance, a Map (see Data.Map) could be constructed, and the
lookups done on that, resulting in logarithmic time performance. The
interface would remain the same.

Hope this helps,
 - Cale

On 26/07/05, Huong Nguyen <[EMAIL PROTECTED]> wrote:
> Hello everybody,
> 
> Now I am writing a module to handles messages of a system. The
> messages are stored in a file. The content of each line of the file
> likes this:
> 
>1001  001   Error message 1
>1001  002   Error message 2
>1002  001   Warning message 1
> 
> in which: The first word is the language Code (e.g: 1 is English, 2 is
> French), the second is type of messages (e.g: 001 is error message,
> 002 is warning message,etc), the third is the index number of
> messages, and the last is the message. I need to read 3 first words of
> each line and assign them to 3 variables. After that, I need to show
> the error message based on the tuple of those 3 first variable, e.g:
> errMsg("1","001","001") = "Error message 1"
> 
> At first, I tried to read only one first line of the file as follows:
> 
> import Prelude
> import List
> import Char
> import IO
> 
> main = do hdl <- openFile "message.txt" ReadMode
>msgLine <-hGetLine hdl
> --stdMsg: cut space at the begining of the line.
>let stdMsg = dropWhile(not.isSpace) msgLine
> -Assign langCode with the first word of the line.
>let langCode = takeWhile(not.isSpace) stdMsg
> 
> However, after that, I do not know how to read second element, third
> element of the line. And how to read continuous next line after first?
> 
> Please help me. Thanks a lot.
> ___
> 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] ForeignPtrs with liveness dependencies

2005-07-26 Thread Einar Karttunen
"Simon Marlow" <[EMAIL PROTECTED]> writes:
> No, unfortunately not.  You have foo's finalizer which refers to bar via
> a touchForeignPtr.  If both foo and bar are unreachable (references from
> finalizers don't count), then both foo and bar's finalizers will be
> started together, and may run in any order.

I didn't realize the "references from finalizers don't count" rule.
What would happen if the finalizer of foo would resurrect bar after 
bar's finalizer has been run?

> So touchForeignPtr does only one thing: it expresses the precise
> relationship "bar is alive if foo is alive".  If both are not alive,
> then both finalizers can run, in any order.

So reference counting the objects is the solution?

> I realise this is very subtle.  By all means suggest improvements to the
> docs.

Mentioning that references from finalizers don't count could help
someone not to repeat my mistakes.

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


[Haskell-cafe] Newbie question about Read strings in a line of File

2005-07-26 Thread Huong Nguyen
Hello everybody,

Now I am writing a module to handles messages of a system. The
messages are stored in a file. The content of each line of the file
likes this:

   1001  001   Error message 1
   1001  002   Error message 2
   1002  001   Warning message 1

in which: The first word is the language Code (e.g: 1 is English, 2 is
French), the second is type of messages (e.g: 001 is error message,
002 is warning message,etc), the third is the index number of
messages, and the last is the message. I need to read 3 first words of
each line and assign them to 3 variables. After that, I need to show
the error message based on the tuple of those 3 first variable, e.g:
errMsg("1","001","001") = "Error message 1"

At first, I tried to read only one first line of the file as follows:

import Prelude
import List
import Char
import IO

main = do hdl <- openFile "message.txt" ReadMode
   msgLine <-hGetLine hdl
--stdMsg: cut space at the begining of the line.
   let stdMsg = dropWhile(not.isSpace) msgLine
-Assign langCode with the first word of the line.
   let langCode = takeWhile(not.isSpace) stdMsg

However, after that, I do not know how to read second element, third
element of the line. And how to read continuous next line after first?

Please help me. Thanks a lot.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Data-types in dynamically loaded hs-plugins

2005-07-26 Thread Thomas Sutton

Hi all,

I'm [trying to] develop a system that uses plug-ins to implement a  
"black-box" ADT, that is a data-type and a few typeclass instances  
for it. I want my system (a theorem prover) to be able to work with  
any of these plug-ins (which define a logic and operations on its  
formulae) but have been having trouble.


I've had a go at using forall's, and at adding a type variable  
(constrained to the appropriate class) to the interface of the plug- 
in, but I haven't been able to get it to work and have run out of ideas.


Is it possible to define data-types in a module loaded at run-time  
with hs-plugins and have values pass out of the plug-in (though only  
being used by functions within it)? Can someone point me in the right  
direction?


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


RE: [Haskell-cafe] ForeignPtrs with liveness dependencies

2005-07-26 Thread Simon Marlow
On 26 July 2005 14:15, Einar Karttunen wrote:

> "Simon Marlow" <[EMAIL PROTECTED]> writes:
>>> Now the association becomes
>>> associate (Foo _ ref) bar =
>>>   atomicModifyIORef ref (\lst -> (touchForeignPtr bar : lst, ()))
>> 
>> Isn't that equivalent to using addForeignPtrFinalizer?  I don't think
>> this fixes anything: the finalizer for bar can still run before the
>> finalizer for foo.
> 
> foo has a single finalizer which is defined like:
> 
> fooFinalizer cfoo ref = do cdeleteFoo cfoo
>vs <- readIORef ref
>mapM_ (\c -> c) vs

the last line is equivalent to "sequence_ vs", FWIW.

> and foo is created like
> 
> createFoo ptr = do ref <- newIORef []
>fp <- newForeigPtr ptr (fooFinalizer ptr ref)
>return (Foo fp ref)
> 
> As the finalizer of foo references the IORef which contains
> the list of actions containing the "touchForeignPtr bar"
> the finalizer of foo is run first. The finalizer to bar
> should be able to run only when the touchForeignPtr has been
> executed in the mapM_ which only happens after foo
> has been cleaned up - if I understand things correctly.

No, unfortunately not.  You have foo's finalizer which refers to bar via
a touchForeignPtr.  If both foo and bar are unreachable (references from
finalizers don't count), then both foo and bar's finalizers will be
started together, and may run in any order.

So touchForeignPtr does only one thing: it expresses the precise
relationship "bar is alive if foo is alive".  If both are not alive,
then both finalizers can run, in any order.

I realise this is very subtle.  By all means suggest improvements to the
docs.

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


Re: [Haskell-cafe] ForeignPtrs with liveness dependencies

2005-07-26 Thread Einar Karttunen
"Simon Marlow" <[EMAIL PROTECTED]> writes:
>> Now the association becomes
>> associate (Foo _ ref) bar =
>>   atomicModifyIORef ref (\lst -> (touchForeignPtr bar : lst, ()))
>
> Isn't that equivalent to using addForeignPtrFinalizer?  I don't think
> this fixes anything: the finalizer for bar can still run before the
> finalizer for foo.

foo has a single finalizer which is defined like:

fooFinalizer cfoo ref = do cdeleteFoo cfoo
   vs <- readIORef ref
   mapM_ (\c -> c) vs

and foo is created like

createFoo ptr = do ref <- newIORef []
   fp <- newForeigPtr ptr (fooFinalizer ptr ref)
   return (Foo fp ref)

As the finalizer of foo references the IORef which contains
the list of actions containing the "touchForeignPtr bar"
the finalizer of foo is run first. The finalizer to bar
should be able to run only when the touchForeignPtr has been 
executed in the mapM_ which only happens after foo 
has been cleaned up - if I understand things correctly.

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


RE: [Haskell-cafe] FFI and callbacks

2005-07-26 Thread Simon Marlow
On 26 July 2005 11:32, Sebastian Sylvan wrote:

> On 7/26/05, Simon Marlow <[EMAIL PROTECTED]> wrote:
>> On 25 July 2005 22:41, Sebastian Sylvan wrote:
>>> Well how about not touching the "bound threads" design at all, but
>>> modifying the lightweigh threads design to also include "forkIOHere"
>>> (or something) which would produce a lightweight thread which is
>>> always run in the "main" OS thread.
>> 
>> This is what Duncan was angling for, I think.  My point is that this
>> requires the implementation to support lightweight threads, which is
>> something we intentionally avoided in the bound threads design.
> 
> No it doesn't. If they don't support lightweight threads, they won't
> have the forkIOHere function available.
> I.e. leave it out of the bound threads design and just implement it as
> a feature in the GHC lightweight threads system.

I think you misunderstand me.  I'm merely pointing out that the fact
that it would be a GHC-specific feature is a drawback.  (not that any
other compilers have bound threads either, but still).

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


Re: [Haskell-cafe] FFI and callbacks

2005-07-26 Thread Sebastian Sylvan
On 7/26/05, Simon Marlow <[EMAIL PROTECTED]> wrote:
> On 25 July 2005 22:41, Sebastian Sylvan wrote:
> 
> > On 7/25/05, Simon Marlow <[EMAIL PROTECTED]> wrote:
> >> On 23 July 2005 03:38, Duncan Coutts wrote:
> >>
> >>> The problem then as John noted is that the main loop of these
> >>> toolkits block and so the other Haskell threads would not get a
> >>> chance to schedule. So the challenge is to give the Haskell threads
> >>> a chance to schedule.
> >>
> >> [ good description of the multi-threaded GUI problem deleted ]
> >>
> >> Thanks for describing the problem in detail, I understand it better
> >> now. I think it comes down to this conflict:
> >>
> >>  - you want to take advantage of the fact that GHC has lightweight
> >>"green" threads in order to do multithreading within a single OS
> >> thread, but
> >>
> >>  - our "bound threads" design does not require the implementation
> >>to support lightweight threads, and hence doesn't let the
> >>programmer take advantage of them.
> >
> > Well how about not touching the "bound threads" design at all, but
> > modifying the lightweigh threads design to also include "forkIOHere"
> > (or something) which would produce a lightweight thread which is
> > always run in the "main" OS thread.
> 
> This is what Duncan was angling for, I think.  My point is that this
> requires the implementation to support lightweight threads, which is
> something we intentionally avoided in the bound threads design.
 
No it doesn't. If they don't support lightweight threads, they won't
have the forkIOHere function available.
I.e. leave it out of the bound threads design and just implement it as
a feature in the GHC lightweight threads system.

/S

-- 
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] ForeignPtrs with liveness dependencies

2005-07-26 Thread Simon Marlow
On 26 July 2005 11:26, Einar Karttunen wrote:

> "Simon Marlow" <[EMAIL PROTECTED]> writes:
>> You might be able to find more information on this in the mailing
>> list archives.  It's true that touchForeignPtr isn't enough to
>> enforce an ordering on the running of finalizers, but it *can* be
>> used to express a liveness relationship between one ForeignPtr and
>> another (ForeignPtr A is alive if ForeignPtr B is alive).  This
>> should be enough if you're dealing with pointer relationships
>> between memory objects, for example, where it doesn't matter which
>> one gets freed first when they're both unreferenced.
> 
> The order of the cleanup functions is significant in this case,
> so that does not unfortunately help.
> 
>> If you really do need ordering, maybe it would be possible to use
>> reference counting in your case?
> 
> I ended up using the following design, which seems to work fine:
> data Foo = Foo (ForeignPtr Foo) (IORef [IO ()])
> Each ForeignPtr Foo has a single finalizer which first calls the
> C-side cleanup function for Foo and then executes all the IO-actions
> inside the IORef.
> 
> Now the association becomes
> associate (Foo _ ref) bar =
>   atomicModifyIORef ref (\lst -> (touchForeignPtr bar : lst, ()))

Isn't that equivalent to using addForeignPtrFinalizer?  I don't think
this fixes anything: the finalizer for bar can still run before the
finalizer for foo.

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


Re: [Haskell-cafe] ForeignPtrs with liveness dependencies

2005-07-26 Thread Einar Karttunen
"Simon Marlow" <[EMAIL PROTECTED]> writes:
> You might be able to find more information on this in the mailing list
> archives.  It's true that touchForeignPtr isn't enough to enforce an
> ordering on the running of finalizers, but it *can* be used to express a
> liveness relationship between one ForeignPtr and another (ForeignPtr A
> is alive if ForeignPtr B is alive).  This should be enough if you're
> dealing with pointer relationships between memory objects, for example,
> where it doesn't matter which one gets freed first when they're both
> unreferenced.

The order of the cleanup functions is significant in this case,
so that does not unfortunately help.

> If you really do need ordering, maybe it would be possible to use
> reference counting in your case?

I ended up using the following design, which seems to work fine:
data Foo = Foo (ForeignPtr Foo) (IORef [IO ()])
Each ForeignPtr Foo has a single finalizer which first calls the C-side
cleanup function for Foo and then executes all the IO-actions inside the 
IORef. 

Now the association becomes
associate (Foo _ ref) bar = 
  atomicModifyIORef ref (\lst -> (touchForeignPtr bar : lst, ()))

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


RE: [Haskell-cafe] FFI and callbacks

2005-07-26 Thread Simon Marlow
On 25 July 2005 22:41, Sebastian Sylvan wrote:

> On 7/25/05, Simon Marlow <[EMAIL PROTECTED]> wrote:
>> On 23 July 2005 03:38, Duncan Coutts wrote:
>> 
>>> The problem then as John noted is that the main loop of these
>>> toolkits block and so the other Haskell threads would not get a
>>> chance to schedule. So the challenge is to give the Haskell threads
>>> a chance to schedule.
>> 
>> [ good description of the multi-threaded GUI problem deleted ]
>> 
>> Thanks for describing the problem in detail, I understand it better
>> now. I think it comes down to this conflict:
>> 
>>  - you want to take advantage of the fact that GHC has lightweight
>>"green" threads in order to do multithreading within a single OS 
>> thread, but 
>> 
>>  - our "bound threads" design does not require the implementation
>>to support lightweight threads, and hence doesn't let the
>>programmer take advantage of them.
> 
> Well how about not touching the "bound threads" design at all, but
> modifying the lightweigh threads design to also include "forkIOHere"
> (or something) which would produce a lightweight thread which is
> always run in the "main" OS thread.

This is what Duncan was angling for, I think.  My point is that this
requires the implementation to support lightweight threads, which is
something we intentionally avoided in the bound threads design.

While I don't doubt that we could implement some way to fork another
thread bound to the same OS thread as the parent, I'm worried that this
would add yet more complexity to GHC's scheduler, so I think we should
fully explore other possibilities first.

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


RE: [Haskell-cafe] ForeignPtrs with liveness dependencies

2005-07-26 Thread Simon Marlow
On 25 July 2005 14:44, Einar Karttunen wrote:

> What is the correct way to express liveness dependencies for
> ForeignPtrs? I am wrapping a C library and need a way to keep
> ForeignPtrs alive until the finalizer for an another ForeignPtr
> has been executed.
> 
> Basically I have two types, ForeignPtr A and ForeignPtr B and a
> function associate :: ForeignPtr A -> ForeignPtr B -> IO (). I want
> to keep all of the ForeignPtr Bs associated with a given ForeignPtr A
> alive until its finalizer has been run. The relationship is M:N -
> each ForeignPtr A may be associated with multiple ForeignPtr B and
> each ForeignPtr B may be associated with multiple ForeignPtr A.
> 
> GHC documentation tells that touchForeignPtr is not enough as it makes
> no guarantees about when the finalizers are run. If it helps the
> finalizers are C functions which neither block nor perform callbacks
> into Haskell.

You might be able to find more information on this in the mailing list
archives.  It's true that touchForeignPtr isn't enough to enforce an
ordering on the running of finalizers, but it *can* be used to express a
liveness relationship between one ForeignPtr and another (ForeignPtr A
is alive if ForeignPtr B is alive).  This should be enough if you're
dealing with pointer relationships between memory objects, for example,
where it doesn't matter which one gets freed first when they're both
unreferenced.

If you really do need ordering, maybe it would be possible to use
reference counting in your case?

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


RE: [Haskell-cafe] building Ghc with msvc ?

2005-07-26 Thread Simon Marlow
On 23 July 2005 22:52, Duncan Coutts wrote:

> On Sat, 2005-07-23 at 22:49 +0200, Jan Scott wrote:
>> Hi,
>> 
>> Has anyone ever tried to build Ghc with Microsofts c compiler (msvc)
>> ? 
> 
> GHC relies quite heavily on gcc. GHC's C code backend uses a number of
> GNU C extensions I believe.
> 
> I think it would be a great deal of work to make it use msvc. And
> there's no need since the mingw gcc works just fine on windows and is
> binary compatible with msvc (if one uses the appropriate gcc options).

I'd like to make the native code generator produce code in Intel syntax
so it would be possible to use the MS binutils as an alterntiave to the
GNU tools (the MS tools are available for free).  Playing nicely with
native Windows debuggers would be useful for debugging mixed
Haskell/foreign language apps, I've had no end of trouble trying to use
gdb for this.

I believe the C parts of the RTS has been (is?) compilable with MSVC.
The non-C parts of the RTS still need ghc -fvia-C (ie. gcc), but if I
ever get around to adding support for loops in the native code generator
we could drop that dependency too.  I seriously doubt that we'd add
support to the mangler for the Intel asm syntax, but generating Intel
asm with the NCG is a distinct possibility.

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