[Haskell-cafe] Re: Control.Exceptions and MonadIO

2006-04-23 Thread Robert Dockins
On Sunday 23 April 2006 02:19 pm, you wrote:

[snip some discussion]

> Perhaps something like:
>
> class MonadIO m => MonadIOE m where
>  catch :: m a-> (Exception -> m a) -> m a
>  throw
>  catchDyn
>  throwDyn
>  -- etc
>
> instance MonadIOE m => StateT s m where ...
> instance MonadIOE m => ReaderT r m where ...
>
> blockIO :: IO a -> IO a
>
> class MonadIO m => MonadIOB m where
>  getUnliftIO :: m (m a -> IO a)
>  block :: m a -> m a
>  block x = do
> unliftIO <- getUnliftIO
> liftIO (blockIO (unliftIO x))
>
>  unblock :: m a -> m a
>  bracket_ :: m a -> m b -> m c -> m c
>  -- etc
>
> instance MonadIOB m => ReaderT r m where ...
>
> and then we could just get rid of all the other exception handling
> functions scattered all over the code base eg Prelude.catch etc.
>
> StateT s can be an instance of MonadIOE but not of MonadIOB because
> although it is sometimes fine to discard state changes when an exception
> arises, it is not ok to discard the state changes inside a block (or
> unblock, bracket_ etc).
>
> Does the above look like a good way of organising things?

I think the basic distinction is good; the added ability to "project" out the 
IO monad seems to be the important point (although I wonder if the other 
methods need to be in the class?).  

It seems to me, however, that the devil is in the details for something like 
this.  It's hard to know if the whole thing hangs together without an 
implementation.

> (I don't know whether MonadIOB would require MonadIOE or not since I
> haven't tried to implement all these functions yet - if it did I would use
> the name MonadIOEB instead)
> I'm about to make an attempt along these lines myself since I can't go
> further in my own work without a proper exception api that doesn't drag
> everything down to concrete IO (unless someone else has already done this?)

> Also, would it be worth modifying
> http://hackage.haskell.org/trac/haskell-prime/ticket/110 to include
> something like this (someone more knowledgeable than me would have to do
> it)?

Well, I created the ticket without much in the way of details -- feel free to 
add a concrete proposal.  I suppose we can take up discussion on the 
haskell-prime list when discussion is opened on topics besides concurrency 
and the class system.

> Regards, Brian.

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


Re: [Haskell-cafe] Current situation regarding global IORefs

2006-04-21 Thread Robert Dockins


On Apr 21, 2006, at 1:27 PM, Brian Hulley wrote:


Robert Dockins wrote:

On Apr 21, 2006, at 10:34 AM, Brian Hulley wrote:

Robert Dockins wrote:

On Apr 21, 2006, at 9:56 AM, Brian Hulley wrote:


Hi -
I've run into the global mutable state problem described in  
http://

[snip]

There is only one GUI for the application and only one control in
it can have the keyboard focus so it seems natural to use global
state here


I'd suggest you consider not making those assumptions... they are the
kinds of assumptions that can make later code reuse and maintenance
more difficult than it should be.  (Obviously, if code reuse/
maintenance is a low priority then it doesn't matter).


, but I suppose I could also look into using a state monad. The
advantage (perhaps also disadvantage ;-) ) of global state is that
it allows me to easily convert all my old C++ singleton classes to
Haskell modules...



Ahhh... the singleton pattern.  There is a debate among OO theorists
about whether the singleton pattern is actually a good idea.  I tend
to side with those who say that it is Just Wrong. [snip]


Thanks for the comments. I've now changed everything so that  
controls use a ManagerM monad which wraps up the state instead of  
using the IO monad so there are no longer any global variables. It  
wasn't as difficult as I had thought and as you say it makes  
everything much more scalable, although at the expense of having to  
use liftIO in various places.


This is true, and mildly irritating.  One additional (very  
unfortunate) point is that higher-order IO monad combinators will not  
work on your monad, eg, the ones in Control.Exception.  I hope H'  
will generalize the types to (use MonadIO)  these combinators to make  
this sort of thing easier, because I think this is a great way to  
structure programs.  *makes mental note to create a ticket for this*   
Sometimes I also think it would be nice if all the standard lib  
functions with IO types would instead take arbitrary MonadIO types,  
so you could avoid having to write down liftIO all the time



I've defined my state monad by:

data MState = MState {keyboard:: !Maybe Control} -- etc - other  
state here also

type ManagerM a = StateT MState IO a

and everything works ok. However if I try to use a newtype instead  
of a type (to completely hide the representation) eg


newtype ManagerM a = ManagerM (StateT MState IO a) deriving (Monad,  
MonadIO, MonadState)


it won't compile.


Are you compiling with -fglasgow-exts?  You're relying on generalized  
newtype deriving, which is a GHC extension.


http://www.haskell.org/ghc/docs/latest/html/users_guide/type- 
extensions.html#newtype-deriving


If that's not it, what's the error you are getting?

Does this mean it is not possible to wrap combined monads in a  
newtype? I notice that the examples in tutorials I've looked at  
tend to always just use type instead of newtype.


I usually use a newtype myself; but then I usually roll my own monads  
instead of using monad transformers (not a value judgement, just habit).


Another point is that I'm not sure what is the "proper" way to  
represent the state itself ie should each component of the state be  
a separate IORef to avoid having to copy the whole state each time  
or is it better practice to just use an immutable record as I've  
done above?


I usually use immutable records as you have done; it somehow "feels  
better".  Unfortunately, going this way exposes you to the clunkiness  
of Haskell's record system.  If all your record components are  
declared with a bang, you may be able to coerce the compiler to unbox  
the record (-funbox-strict-fields, I think), which would prevent  
copying altogether.  Immutable records are also a little nicer to the  
garbage collector.  However, I've never actually tried to measure the  
performance difference.


If you're going to use a record of IORefs, you should probably go  
with ReaderT instead.



Thanks, Brian.



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


Re: [Haskell-cafe] Current situation regarding global IORefs

2006-04-21 Thread Robert Dockins

On Apr 21, 2006, at 10:34 AM, Brian Hulley wrote:

Robert Dockins wrote:

On Apr 21, 2006, at 9:56 AM, Brian Hulley wrote:


Hi -
I've run into the global mutable state problem described in http://
www.haskell.org/hawiki/GlobalMutableState
Since the page was last edited in March last year, I'm wondering if
there have been any developments or further thoughts on how to
safely create top level IORefs since they are absolutely essential
for the library I'm writing.

For my library, which implements a GUI, I have a Manager module
which keeps track of which control currently has the keyboard focus
etc, and I don't want to have to pass round the state of the
manager to every control since this would be monstrously
inconvenient and a total waste of space/time, so at the moment I'm
reduced to:

module Manager where
keyboard :: IORef (Maybe Control)
{-# NOINLINE keyboard #-}
keyboard = unsafePerformIO $ newIORef Nothing

The problem is that I don't know if this is guaranteed to be
completely safe for all Haskell compilers or even for all future
versions of ghc (?)


RE: the technique itself, you should also compile the module with -
fno-cse.


Thanks



RE: the design, Isn't that bit of state local to a dialog/window/
control group or something?  I understand that top level state is a
problem in general that needs some sort of solution, but I'm not sure
it's the right hammer here


There is only one GUI for the application and only one control in  
it can have the keyboard focus so it seems natural to use global  
state here


I'd suggest you consider not making those assumptions... they are the  
kinds of assumptions that can make later code reuse and maintenance  
more difficult than it should be.  (Obviously, if code reuse/ 
maintenance is a low priority then it doesn't matter).


, but I suppose I could also look into using a state monad. The  
advantage (perhaps also disadvantage ;-) ) of global state is that  
it allows me to easily convert all my old C++ singleton classes to  
Haskell modules...



Ahhh... the singleton pattern.  There is a debate among OO theorists  
about whether the singleton pattern is actually a good idea.  I tend  
to side with those who say that it is Just Wrong.  The reality is  
that "singletons" are only unique within some scope (OS process, VM,  
sandbox, whatever).  "Global" state is similar; it is always bounded  
by _something_.  I think its always better to make the boundaries  
explicit and aligned with the problem domain rather than implicit,  
because the implicit boundaries sometimes/often don't do what you  
want.  As soon as you have an even slightly unusual execution  
environment, your assumptions can be violated (eg, within Java  
application containers *shudder*).  I have to imagine using, eg, HS  
plugins with modules containing top-level state could cause all sorts  
of havoc.




As far as I know, the only recent developments in this area are a
rumor from the Simons that they are working on some sort of thread-
local state which (under some sets of design decisions) can fill the
needs of top level state.  If you press them, they might be willing
to give some details about this.


I was kind of hoping that there would just be a safe, simple way to  
create a top level monomorphic IORef without having to use a pragma  
etc.


I don't think that exists currently.


Thanks, Brian.



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


Re: [Haskell-cafe] Current situation regarding global IORefs

2006-04-21 Thread Robert Dockins


On Apr 21, 2006, at 9:56 AM, Brian Hulley wrote:


Hi -
I've run into the global mutable state problem described in http:// 
www.haskell.org/hawiki/GlobalMutableState
Since the page was last edited in March last year, I'm wondering if  
there have been any developments or further thoughts on how to  
safely create top level IORefs since they are absolutely essential  
for the library I'm writing.


For my library, which implements a GUI, I have a Manager module  
which keeps track of which control currently has the keyboard focus  
etc, and I don't want to have to pass round the state of the  
manager to every control since this would be monstrously  
inconvenient and a total waste of space/time, so at the moment I'm  
reduced to:


module Manager where
keyboard :: IORef (Maybe Control)
{-# NOINLINE keyboard #-}
keyboard = unsafePerformIO $ newIORef Nothing

The problem is that I don't know if this is guaranteed to be  
completely safe for all Haskell compilers or even for all future  
versions of ghc (?)


RE: the technique itself, you should also compile the module with - 
fno-cse.


RE: the design, Isn't that bit of state local to a dialog/window/ 
control group or something?  I understand that top level state is a  
problem in general that needs some sort of solution, but I'm not sure  
it's the right hammer here


As far as I know, the only recent developments in this area are a  
rumor from the Simons that they are working on some sort of thread- 
local state which (under some sets of design decisions) can fill the  
needs of top level state.  If you press them, they might be willing  
to give some details about this.



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


Re: [Haskell-cafe] Advice needed on best way to simulate an STL vector

2006-04-19 Thread Robert Dockins


On Apr 19, 2006, at 3:06 PM, Brian Hulley wrote:

Thanks. I might try this if I don't have any luck with finger trees  
(from Udo's post), or if they seem too heavy for the simple thing  
I'm planning to use them for (implementing the text buffer for an  
edit control which needs a mutable array of lines where each line  
contains a mutable array of character info). I don't need non-Int  
indices so your data type for Vector would be fine.


In that case, you may be interested in this paper, which discusses a  
data structure specifically designed for strings called 'ropes':


http://www.cs.ubc.ca/local/reading/proceedings/spe91-95/spe/vol25/ 
issue12/spe986.pdf



I'm not aware of a Haskell implementation of ropes, but there may  
well be one floating around.  Actually, I'd be kind of surprised if  
someone hasn't implemented this already (does YI use ropes?); it  
seems like such a great fit for Haskell.





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


Re: [Haskell-cafe] Ambiguous types for collection keys

2006-04-12 Thread Robert Dockins


On Apr 12, 2006, at 4:09 PM, Scott Weeks wrote:



Or carry an instance in along with a type parameter, using  
existentials or GADT.


Brandon Moore


Do you know of an example that would apply to my situation?

I think I neglected to state part of my problem. I am storing the  
root nodes of btree indexes in a heterogeneous list using Typeable.  
When they come out of the list they need to be unwrapped


I think this will clarify my situation because I've been doing a  
poor job of explaining:


import Data.Dynamic

data Foo a = FVal a
 deriving (Show, Typeable)

type FooStr = Foo String
type FooInt = Foo Integer

main = do
  fooType <- getLine
  fooVal  <- getLine
  let foo   = toDyn (FVal fooVal)
  fs= [foo]
  (f:_) = fs
  Just dynFoo = fromDynamic f
  dostuff dynFoo



dostuff :: (Show a) => Foo a -> IO ()
dostuff (FVal x) = print x


This fails with:

 Ambiguous type variable `a' in the constraints:
  `Typeable a'
	arising from use of `fromDynamic' at /Users/weeksie/workspace/ 
haskell/Main.hs:243:20-30

  `Show a'
	arising from use of `dostuff' at /Users/weeksie/workspace/haskell/ 
Main.hs:247:2-8
Probable fix: add a type signature that fixes these type  
variable(s)



However, changing main:

main = do
  fooType <- getLine
  fooVal  <- getLine
  let foo   = toDyn (FVal fooVal)
  fs= [foo]
  (f:_) = fs
  Just dynFoo = fromDynamic f
  if fooType == "str"
 then dostuff (dynFoo::FooStr)
 else dostuff (dynFoo::FooInt)



You are trying to assign two distinct types to dynFoo; that's a no- 
no.  You need to move the usage of the polymorphic function out of  
the let so that the use at each distinct type doesn't get unified.



{-# OPTIONS -fglasgow-exts #-}
import Data.Dynamic

data Foo a = FVal a
 deriving (Show, Typeable)

type FooStr = Foo String
type FooInt = Foo Integer

main = do
  fooType <- getLine
  fooVal  <- getLine
  let foo   = toDyn (FVal fooVal)
  fs= [foo]
  (f:_) = fs
  if fooType == "str"
 then dostuff (fromDyn f undefined :: Foo String)
 else dostuff (fromDyn f undefined :: Foo Int)


dostuff :: (Show a) => Foo a -> IO ()
dostuff (FVal x) = print x



BTW, this little example always stuffs a string into the FVal, so  
trying to get anything else out will fail.




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


Re: [Haskell-cafe] Ambiguous types for collection keys

2006-04-12 Thread Robert Dockins


On Apr 12, 2006, at 3:18 PM, Scott Weeks wrote:






Well, if you get an "ambiguous type variable" error, you probably (I
think) need to add some type annotations. For example:

class Foo a where
  foo :: a
  bar :: a -> String

Evaluating bar foo will result in an error, but bar (foo :: Integer)
will work just fine.



The problem is that I get  an incoming value which is a key of some  
sort. There's no way of knowing what type that value is supposed to  
be until I compare it with the schema from the above example. where  
I _am_ adding type annotations.


coerceIndex f (Schema _ SInt SPtr _) (r,hdl,o,hdr) = f  
(r::IdxInt,hdl,o,hdr)
coerceIndex f (Schema _ SStr SPtr _) (r,hdl,o,hdr) = f  
(r::IdxPS,hdl,o,hdr)



When I try to add type annotations I get a complaint from the  
typechecker that says (In the case of the above example) Expected  
type: Integer, Inferred Type: PackedString.


Is the alternative to write different "select" methods for each key  
type (selectInt, selectPS, ...)? God I hope not, that would be a  
bit scary.



I'm not 100% sure I understand your use case, but I think you might  
be able to crack this by using Data.Dynamic:


http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data- 
Dynamic.html





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


Re: [Haskell-cafe] Counting bits: Sanity Check

2006-04-12 Thread Robert Dockins


On Apr 11, 2006, at 10:09 AM, David F. Place wrote:


Hi All,

Since it seems that real applications need more than just  union,  
intersection, difference and complement to be fast to make EnumSet  
useful, I've been looking into the less naive approaches to the  
other things.   In particular, size seems to find itself in the  
inner loop.   I've made a comparison of various approaches to bit  
counting.  It seems I was too hasty to declare Bulat's suggestion  
of table lookup (table,table32) the winner.  It seems Robert's  
suggestion of Kernighan's (kern) method is faster.


I also implemented the method described in pages 187-188 of  
Software Optimization Guide for AMD Athlon™ 64 and Opteron™  
Processors. (ones32)  It's slower on my powerbook, but may be the  
winner on 64bit processors.  Here are the results:


[Marcel:~/devl/EnumSet] david% time ./bits 200 300 ones32
21
1.788u 0.136s 0:03.30 57.8% 0+0k 0+0io 0pf+0w
[Marcel:~/devl/EnumSet] david% time ./bits 200 300 table
21
2.404u 0.164s 0:04.96 51.6% 0+0k 0+1io 0pf+0w
[Marcel:~/devl/EnumSet] david% time ./bits 200 300 table32
21
2.067u 0.140s 0:04.27 51.5% 0+0k 0+0io 0pf+0w
[Marcel:~/devl/EnumSet] david% time ./bits 200 300 kern
21
1.729u 0.137s 0:03.25 56.9% 0+0k 0+1io 0pf+0w

If you'd like to give it a whirl on your fancy modern computers,  
here's the code:




ghc -O3 -optc-O3 -o bits BitTwiddle.hs



I get similar results on my machine (PPC powerbook).  'ones32'   
barely edges out 'kern' and 'table' and 'table32' come in behind.


Average 'user' time over three runs:

ones32:  0.540s
kern: 0.545s
table: 0.730s
table32: 0.632s




Of course, if I've done something lame-brained and skewed the  
results, please let me know.


Cheers, David



David F. Place
mailto:[EMAIL PROTECTED]

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



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


Re: [Haskell-cafe] Understanding allocation behavior

2006-04-10 Thread Robert Dockins


On Apr 8, 2006, at 9:30 PM, Daniel Fischer wrote:


Hum,
oddly, these actually slow things down.
While the new size brought the sudoku17 time from ~570s down to ~490s,
the new findMinIndex/findMaxIndex increased the time to ~515s,  
although hardly

used.
Why?


Hard to say.  I'd expect that if the bit twiddly parts get turned  
directly into the corresponding opcodes, it would help (but that's  
not certain).  It's possible that GHC munges things somewhere in the  
pipe and accidently unoptimizes; its possible that strictness isn't  
correctly discovered in 'msb'.  Or, it could be that whatever  
(probably superscalar) chip you're running does a better job with the  
loop (although that's hard to believe...), or its some sort of cache  
effect... or who knows.


You'd probably have to study the core and/or disassembly to figure  
out exactly what's happened.  I suppose its possible that the change  
had some bizarre ripple effect that somehow suppressed a helpful  
optimization in some other part of the program.  At this point it  
sort of becomes black magic, and I must confess I'm no magician.  Its  
disappointing that those lovely, inscrutable algorithms don't help,  
though ;-)


Rob Dockins


Cheers,
Daniel

Am Sonntag, 9. April 2006 00:54 schrieb Robert Dockins:

On Apr 8, 2006, at 1:58 PM, David F. Place wrote:

Thanks Bulat and Robert.  I implemented Bulat's idea as the
following.  It tests faster than Roberts.  I use Robert's to
compute the table.  The performance seems satisfactory now.

size :: Set a -> Int
size (Set w) = countBits w
where
  countBits w

  | w == 0 = 0
  | otherwise = countBits (w `shiftR` 8) + bitsTable! 
(w .&. 0xFF)


bitsTable :: Array Word Int
bitsTable = array (0,255) $ [(i,bitcount i) | i <- [0..255]]

bitcount :: Word -> Int
bitcount 0 = 0
bitcount x = 1 + bitcount (x .&. (x-1))


There's a couple of other nice bit-twiddily things you can do:

countBits :: Word -> Int
countBits w

| w == 0 = 0
| otherwise = countBits (w `shiftR` 8) + bitsTable!(w .&. 0xFF)

bitsTable :: Array Word Int
bitsTable = array (0,255) $ [(i,bitcount i) | i <- [0..255]]

bitcount :: Word -> Int
bitcount 0 = 0
bitcount x = 1 + bitcount (x .&. (x-1))

lsb :: Word -> Int
lsb x = countBits ((x-1) .&. (complement x))

-- stolen from http://aggregate.org/MAGIC/
msb :: Word -> Int
msb x0 = let
  x1 = x0 .|. (x0 `shiftR` 1)
  x2 = x1 .|. (x1 `shiftR` 2)
  x3 = x2 .|. (x2 `shiftR` 4)
  x4 = x3 .|. (x3 `shiftR` 8)
  x5 = x4 .|. (x4 `shiftR` 16)
  in countBits x5 - 1


findMinIndex :: Word -> Int
findMinIndex 0 =
 error "EnumSet.findMin: empty set has no minimal element"
findMinIndex w = lsb w

findMaxIndex :: Word -> Int
findMaxIndex 0 =
 error "EnumSet.findMax: empty set has no maximal element"
findMaxIndex w = msb w



Which should make all access to the greatest or least element O(1).
I guess, come to think of it, all operations on EnumSet are O(1) by
virtue of the set size being upper-bounded.  At any rate this turns
recursion into unboxable straight-line code and I think it does less
allocations.



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


--

"In My Egotistical Opinion, most people's C programs should be
indented six feet downward and covered with dirt."
-- Blair P. Houghton





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


Re: Re[2]: [Haskell-cafe] Understanding allocation behavior

2006-04-08 Thread Robert Dockins


On Apr 8, 2006, at 1:58 PM, David F. Place wrote:

Thanks Bulat and Robert.  I implemented Bulat's idea as the  
following.  It tests faster than Roberts.  I use Robert's to  
compute the table.  The performance seems satisfactory now.


size :: Set a -> Int
size (Set w) = countBits w
where
  countBits w
  | w == 0 = 0
  | otherwise = countBits (w `shiftR` 8) + bitsTable!(w .&.  
0xFF)


bitsTable :: Array Word Int
bitsTable = array (0,255) $ [(i,bitcount i) | i <- [0..255]]

bitcount :: Word -> Int
bitcount 0 = 0
bitcount x = 1 + bitcount (x .&. (x-1))


There's a couple of other nice bit-twiddily things you can do:

countBits :: Word -> Int
countBits w
   | w == 0 = 0
   | otherwise = countBits (w `shiftR` 8) + bitsTable!(w .&. 0xFF)

bitsTable :: Array Word Int
bitsTable = array (0,255) $ [(i,bitcount i) | i <- [0..255]]

bitcount :: Word -> Int
bitcount 0 = 0
bitcount x = 1 + bitcount (x .&. (x-1))

lsb :: Word -> Int
lsb x = countBits ((x-1) .&. (complement x))

-- stolen from http://aggregate.org/MAGIC/
msb :: Word -> Int
msb x0 = let
 x1 = x0 .|. (x0 `shiftR` 1)
 x2 = x1 .|. (x1 `shiftR` 2)
 x3 = x2 .|. (x2 `shiftR` 4)
 x4 = x3 .|. (x3 `shiftR` 8)
 x5 = x4 .|. (x4 `shiftR` 16)
 in countBits x5 - 1


findMinIndex :: Word -> Int
findMinIndex 0 =
error "EnumSet.findMin: empty set has no minimal element"
findMinIndex w = lsb w

findMaxIndex :: Word -> Int
findMaxIndex 0 =
error "EnumSet.findMax: empty set has no maximal element"
findMaxIndex w = msb w



Which should make all access to the greatest or least element O(1).   
I guess, come to think of it, all operations on EnumSet are O(1) by  
virtue of the set size being upper-bounded.  At any rate this turns  
recursion into unboxable straight-line code and I think it does less  
allocations.




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


Re: Re[2]: [Haskell-cafe] Understanding allocation behavior

2006-04-08 Thread Robert Dockins


On Apr 8, 2006, at 4:24 AM, Bulat Ziganshin wrote:


Hello Daniel,

Saturday, April 8, 2006, 4:21:14 AM, you wrote:

Unless I overlooked something, I use foldBits only via size  
(though that's

used a lot).


size of set? there is much faster method - use a table

[0..255] -> number of bits in this number seen as set


Or:

bitcount :: Word -> Int
bitcount 0 = 0
bitcount x = 1 + bitcount (x .&. (x-1))

-- | /O(1)/. The number of elements in the set.
size :: Set a -> Int
size (Set w) = bitcount w

Taking a look at the generated core (with -O2) , bitcount gets  
unboxed the way I'd expect, so this might do the trick.




then we split Word to the bytes and count total size of set
by adding number of bits set in each byte

foldBits can be made faster (may be) by adding strict annotations:

foldBits :: Bits c => (a -> Int -> a) -> a -> c -> a
foldbits _ z bs | z `seq` bs `seq` False  = undefined

foldBits' :: Bits c => (a -> Int -> a) -> Int -> c -> a -> a
foldbits' _ i bs z | i `seq` bs `seq` z `seq` False  = undefined

moreover, GHC don't inline recursive functions! so foldbits' is out of
luck and it seems that GHC generates polymorphic version that is of
course very-very slow. what you can do?

1. use SPECIALIZE pragma. this allow to make faster version at least
for typical cases (a=c=Int, for example)

2. use recursion on the internal foldbits' function. may be this will
help to inline and therefore specialize each call to foldbits'. it's
better to ask Simon Marlow about this

--
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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




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


Re: [Haskell-cafe] Justification for Ord inheriting from Eq?

2006-04-07 Thread Robert Dockins


On Apr 7, 2006, at 9:43 AM, Jacques Carette wrote:

Robert Dockins wrote:
The behaviour of NaN actually makes perfect sense when you  
realise that
it is Not a Number.  Things that are not numbers are incomparable  
with

things that are.

Yes, NaN can be of type Float.  But it's not a Float.


If you take that tack, then you have to concede that the type  
system isn't doing what it should (keeping me from having  
something not-a-float where I expect a float).  Any way you slice  
it, its an unfortunate situation.


I'd personally rather that any operation generating NaN raises an  
exception, a la divide by 0 at Int.  I think (although I'm not  
sure) that the floating point infinities play nice wrt equality  
and ordering, so getting rid of NaN would restore at least _some_  
semblance of proper algebraic behavior to the floating point  
representations.  (And the FFI already has CFloat/CDouble, so you  
should use those when you really need to actually do something  
with NaN generated by external code, and CFloat/CDobule should not  
be members of Eq and Ord).


Or at the very least, attempting to compare NaN using (==) or (<)  
and friends should raise an exception, rather than just returning  
broken results.


Rob Dockins


The IEEE 754 standard explicitly specifies that complete  
implementations can have either or both 'signalling' NaNs and  
'quiet' NaNs.  It appears that current Haskell implementations have  
chosen to go with quiet NaNs, which is very surprising indeed, as  
that does go "against" the type system.  Signalling NaNs are more  
consistent with the rest of Haskell's semantics.


However, it is also important to note that IEEE 754 also mandates  
'trap handlers' for signalling NaNs, so that implementors may  
choose (even at run-time, on a per-instance basis) what to do with  
any given occurence of NaN.  In particular, it is possible to  
resume the computation with a _value_ being substituted in for that  
NaN.  These 'trap handlers' are also in there for division-by-zero,  
so that one may _choose_ to return either infinity or raise an  
actual exception.


If one reads the standard (IEEE 754) carefully enough, it is  
possible to 'pick' an implementation of it which actually fits in  
with Haskell fairly well.  Yes, the standard is explicitly written  
to have *choices* in it for implementors.  The current  
implementation is generally standard-compliant, but does not seem  
to 'pick' a path of least-resistance wrt the rest of Haskell.


Is this an H' worthy item?


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


Re: [Haskell-cafe] Justification for Ord inheriting from Eq?

2006-04-07 Thread Robert Dockins


On Apr 7, 2006, at 1:36 AM, [EMAIL PROTECTED] wrote:


G'day all.

Quoting Robert Dockins <[EMAIL PROTECTED]>:

Eww! Be careful how far you depend on properties of  
typeclasses, and make

sure you document it when you do.


The behaviour of NaN actually makes perfect sense when you realise  
that

it is Not a Number.  Things that are not numbers are incomparable with
things that are.

Yes, NaN can be of type Float.  But it's not a Float.


If you take that tack, then you have to concede that the type system  
isn't doing what it should (keeping me from having something not-a- 
float where I expect a float).  Any way you slice it, its an  
unfortunate situation.


I'd personally rather that any operation generating NaN raises an  
exception, a la divide by 0 at Int.  I think (although I'm not sure)  
that the floating point infinities play nice wrt equality and  
ordering, so getting rid of NaN would restore at least _some_  
semblance of proper algebraic behavior to the floating point  
representations.  (And the FFI already has CFloat/CDouble, so you  
should use those when you really need to actually do something with  
NaN generated by external code, and CFloat/CDobule should not be  
members of Eq and Ord).


Or at the very least, attempting to compare NaN using (==) or (<) and  
friends should raise an exception, rather than just returning broken  
results.




Cheers,
Andrew Bromage



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


Re: [Haskell-cafe] Justification for Ord inheriting from Eq?

2006-04-06 Thread Robert Dockins
On Thursday 06 April 2006 06:44 pm, John Meacham wrote:
> On Thu, Apr 06, 2006 at 10:52:52PM +0100, Brian Hulley wrote:

[snip a question about Eq and Ord classes]

> well, there are a few reasons you would want to use inheritance in
> haskell, some good, some bad.
>
> 1. one really does logically derive from the other, Eq and Ord are like
> this, the rules of Eq says it must be an equivalance relation and that
> Ord defines a total order over that equivalance relation. this is a good
> thing, as it lets you write code that depends on these properties.



Many of you probably know this already, but for those who might not know:

Prelude> let x = read "NaN" :: Float
Prelude> x == x
False
Prelude> x == 0
False
Prelude> 0 < x
False
Prelude> x < 0
False

Eww! Be careful how far you depend on properties of typeclasses, and make 
sure you document it when you do.





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


Re: [Haskell-cafe] Re: [Haskell] What's up with this Haskell runtime error message:

2006-04-06 Thread Robert Dockins


On Apr 6, 2006, at 11:25 AM, Michael Goodrich wrote:

Thanks so much for your help. I should have made clear that I was  
aware that the definitions were mutually dependent.  What I was  
hoping was that Haskell could solve this for me without my having  
to resort to effectively finessing any sequencing considerations.


Perhaps I am really asking it to do too much.

This I thought might be reasonable since one is supposed to be  
achieving a sequence-less style of programming.  But this would  
seem to be a counter example where  I will be essentially forced to  
implement a sequential processing semantic in a language  
environment which ostensibly would deny me such (for my own good I  
understand).


Thoughts?


[snip a bunch of code]

I'm not an expert, but I'll take a crack at this.  What you seem to  
want is a numeric fixpoint, wherein each variable in the mutually  
recursive set of equations is assigned a value that causes all  
equations to hold.  This is called a fixpoint because it represents a  
point where the function in n-space generated by the n equations maps  
to itself.


The notion of a fixpoint usually found in functional programming  
languages is a little different -- it is specifically the "least  
fixed point".  Now, I'm getting a little out of my depth here, but I  
think that the Kleene fixpoint theorem tells us that the least  
fixpoint of the kind of function in the previous paragraph must be  
bottom - ie, non-termination (which, GHC can sometimes detect, in  
which case it prints the <> error you saw).  You can't use the  
least fixpoint mechanism that the programming language gives you to  
calculate the those kind of numeric fixpoints, because the least  
fixpoint is completely uninteresting and not what you want.


In haskell, the standard techinque for this kind of thing is to  
calculate an "infinite" list of successive approximations to the  
answer and choosing an element from the list according to some  
criteria (usually absolute or relative convergence of successive  
elements).  You can easily build such a list with 'Data.List.iterate'.


This should work for all attractive fixpoints of the function when  
given an appropriate initial approximation (modulo floating point  
rounding errors, as always).




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


Re: [Haskell-cafe] What's up with this Haskell runtime error message:

2006-04-05 Thread Robert Dockins
On Wednesday 05 April 2006 04:51 pm, Michael Goodrich wrote:
> Oops, I just realized that you gave me the answer, namely that it won't
> find fixed points of numeric sets of equations.
>
> Pity, that would really have made Haskell useful for this kind of
> scientific computing.

See section 4 of:

http://www.cs.chalmers.se/~rjmh/Papers/whyfp.html


See also:
http://www.haskell.org/haskellwiki/Libraries_and_tools/Mathematics
http://users.info.unicaen.fr/~karczma/arpap/


> On 4/5/06, Brandon Moore <[EMAIL PROTECTED]> wrote:
> > Michael Goodrich wrote:
> > > Looks like my calulation involves a self referential set of
> > > definitions.
> > >
> > > Is Haskell not able to deal with a self referential set of definitions?
> > >
> > >  I was frankly hoing it would since otherwise there is then  the
> > > specter of sequence, i.e. that I have to finesse the order in which
> > > things are calculated so as to avoid it.
> > >
> > > Thoughts?
> >
> > Lazy evaluation is great with self-referential definitions, but id
> > doesn't do so well with ill-founded definitions. It also won't find
> > fixpoints of numeric equations. Here are some examples, and then some
> > explanation.
> >
> > Things that work:
> >
> > {- for interactive use in ghci -}
> > let ones = 1:ones
> > --infinite list of ones
> > let counting = 1:map (+1) counting
> > -- infinite list counting up from one
> > let fibs = 1:1:zipWith (+) fibs (tail fibs)
> > --fibbonacci numbers
> >
> > {- A larger program.
> > turns references by name into direct references
> > Try on a cyclic graph, like
> > buildGraph [("a",["b"]),("b",["a"])]
> >   -}
> > import Data.List
> > import Data.Map as Map
> >
> > data Node = Node String [Node]
> > type NodeDesc = (String, [String])
> >
> > buildNode :: Map String Node -> NodeDesc -> Node
> > buildNode env (name,outlinks) =
> >Node name (concat [Map.lookup other finalBinds | other <- outlinks])
> >
> > buildGraph :: [(String,[String])] -> [Node]
> > buildGraph descs = nodes
> >where (finalBinds, nodes) = mapAccumR buildExtend Map.empty descs
> >  buildExtend binds desc@(name,_) =
> >  let node = buildNode finalBinds desc
> >   in (Map.insert name node binds, node)
> >
> >
> > Things that will not work:
> >
> > let x = x
> > -- no information on how to define x
> >
> > let x = 2*x + 1
> > -- this is not treated algebraically
> >
> > let broke = 1:zipWith (+) broke (tail broke)
> > -- the second element depends on itself
> >
> >
> > Recursive definitions in Haskell can be explained by
> > saying that they find the least-defined fixedpoint of the equations.
> > Every type in Haskell has all the usual values you would have in a
> > strict language, plus an undefined value which corresponds to a
> > nonterminating computation. Also, there are values where subterms
> > of different types are undefined values of that type rather.
> >
> > For example, with pairs of numbers there are these posibilites
> >(x,y)
> >   / \
> > (_|_,x)   (x,|_|)
> >   \ /
> >  (_|_,_|_)
> >
> > _|_
> > where x and y represent any defined number, and _|_ is "undefined",
> > or a non-terminating computation. A value on any line is
> > considered more defined than values on lower lines. Any value which can
> > be obtained from another by replacing subterms with _|_ is less defined,
> > if neither can be made from the other that way than neither is more
> > defined that the other.
> >
> >
> > Think of a definition like x = f x. That will make x the least-defined
> > value which is a fixedpoint of f. For example, numeric operations are
> > (generally) strict, so _|_ * x = _|_, _|_ + x = _|_, and
> > _|_ is a fixedpoint of \x -> 2*x + 1.
> >
> > for broke, consider the function f = \l -> 1:(zipWith (+) l (tail l))
> > f (x:_|_) = 1:zipWith (+) (1:_|_) (tail (1:_|_))
> >= 1:zipWith (+) (1:_|_) _|_
> >= 1:_|_
> > so 1:_|_ is a fixedpoint. It's also the least fixedpoint, because
> > _|_:_|_ is not a fixedpoint, and
> > f _|_ = 1:, so _|_ is not a fixedpoint either. If I try that
> > definition of broke, ghci prints "[1" and hangs, indicating that the
> > rest of the list is undefined.
> >
> > If multiple definitions are involved, think of a function on a tuple of
> > all the definitions:
> >
> > x = y
> > y = 1:x
> >
> > corresponds to the least fixedpoint of (\(x,y) -> (y,1:x))
> >
> > The recursiveness in the graph example is more tedious to analyze like
> > this, but it works out the same way - whatever value of "finalBinds" is
> > fed into the recursive equation, you get out a map built by taking the
> > empty map and adding a binding for each node name. Chase it around a few
> > more times, and you'll get some detail about the nodes.
> >
> > Also, posting code really helps if you want specific advice. Thanks to
> > the hard work of compiler writers, the error message are usually precise
> > enough for a message like this to describe the possibilit

Re: [Haskell-cafe] "show" for functional types

2006-04-05 Thread Robert Dockins


On Apr 5, 2006, at 12:42 PM, Josef Svenningsson wrote:


Sorry to barge in in the middle of your discussion here..


Hey, if we wanted a private conversation, we'd take it off-list. :-)


On 4/5/06, Robert Dockins <[EMAIL PROTECTED]> wrote:

There is a fair bit of disagreement about what referential
transparency means.  I found the following link after googling around
a bit; it seems to address some of these issues.

http://www.cs.indiana.edu/~sabry/papers/purelyFunctional.ps


Do you have any reference to the fact that there is any diagreement
about the term? I know it has been used sloppily at times but I think
it is pretty well defined. See section 4 of the following paper:
http://www.dina.kvl.dk/~sestoft/papers/SondergaardSestoft1990.pdf


http://en.wikipedia.org/wiki/Referential_transparency
http://lambda-the-ultimate.org/node/1237

It may be that experts have a well defined notion of what it means,  
but I think that non-experts (ie, most people) have a pretty vague  
idea of exactly what it means.




Readers digest:
First we need a denotational semantics and a corresponding equality
which I call '='. A language is then referentially transparent if for
all expressions e,e1 and e2, if e1 = e2 then e[x:=e1] = e[x:=e2].
Here e[x:=e'] denotes substitution where the variable x is replaced
with e' in the expression e.

So it's a standard substitutivity property. The only problem here is
that Haskell has a pretty hairy denotational semantics and I don't
think anyone has spelled it out in detail.


I think that may be the main problem, at least in this context.  We  
can take a nice lovely definition of rt, as above, but its  
meaningless without a good semantic model.  So we're forced to  
approximate and hand-wave, which is where the disagreement comes in.



The thing which I think
comes closest is the following paper which investigates the
denotational implications of have seq as a primitive:
http://www.crab.rutgers.edu/~pjohann/seqFinal.pdf

Cheers,

/Josef


Thanks for these paper links; I'll be reading them as soon as I find  
a few moments.


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


Re: [Haskell-cafe] "show" for functional types

2006-04-05 Thread Robert Dockins


On Apr 5, 2006, at 10:49 AM, Brian Hulley wrote:


Robert Dockins wrote:

On Apr 1, 2006, at 3:23 PM, Brian Hulley wrote:

[snip]
" For particular types T1 and T2, if (f (x::T1))::T2 === g x for
all x in T1 then f :: T1->T2 and g ::T1->T2 can be freely
substituted since the context T1->T2 cannot tell them apart."


Having thought about this a bit more, I realize that this statement
is also too strong.  In the lambda calculus, extensionality is
equivalent to the validity of eta-conversion (Plotkin, Call-by-value,
Call-by-name and the lambda calculus, 1975).  However, in Haskell,
eta-conversion is not valid (ie, meaning-preserving).  Observe:

f, g :: a -> b
f = undefined
g = \x -> undefined x

forall x::a, f x === g x === _|_.  However, 'seq' can tell them  
apart.


seq f 'a' === _|_
seq g 'a' === 'a'

So f and g are not replaceable in all term contexts (in particular,
not in 'seq' contexts).


I should not have used functions, since in any case for full  
generality rt is about allowing equivalent expressions to be  
substituted eg as in:


"For a particular type T, if f::T === g then f::T and g::T can be  
freely substituted since the context T cannot tell them apart"


This of course begs the question of how === is defined and so  
perhaps is not that useful.


I had in mind "has the same denotational semantics", but the notation  
is a little sloppy.


On the other hand, you could turn the definition around and say that  
=== means two expression which can be freely substituted.  To prove  
properties about ===, you then need to have a very precise definition  
of the semantics of the programming language.  Unfortunately, I don't  
think Haskell's semantics are developed to quite that point.


If === must be defined extensionally then not all contexts in  
Haskell are referentially transparent since seq is referentially  
opaque, but this would render the whole notion of referential  
transparency useless for Haskell since there would be no way for a  
user of a library function to know whether or not the argument  
context(s) are transparent or opaque. At the moment I can't think  
of a non-extensional definition for === but there must be one  
around somewhere so that equational reasoning can be used.


There is a fair bit of disagreement about what referential  
transparency means.  I found the following link after googling around  
a bit; it seems to address some of these issues.


http://www.cs.indiana.edu/~sabry/papers/purelyFunctional.ps



Regards, Brian.



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


Re: [Haskell-cafe] "show" for functional types

2006-04-04 Thread Robert Dockins


On Apr 1, 2006, at 3:23 PM, Brian Hulley wrote:


Robert Dockins wrote:

[snip]
From an earlier post:


Now since f and g compute the same results for the same inputs,
anywhere in a program that you can use f you could just replace f
by g and the observable behaviour of the program would be
completely unaffected. This is what referential transparency means.


My essential claim is that the above statement is in error (but in a
fairly subtle way).


Ok I see now! :-) I was confusing the concept of referential  
transparency with a kind of global code equivalence, so the rest of  
my argument is irrelevant. Thus I should have said:


" For particular types T1 and T2, if (f (x::T1))::T2 === g x for  
all x in T1 then f :: T1->T2 and g ::T1->T2 can be freely  
substituted since the context T1->T2 cannot tell them apart."


Having thought about this a bit more, I realize that this statement  
is also too strong.  In the lambda calculus, extensionality is  
equivalent to the validity of eta-conversion (Plotkin, Call-by-value,  
Call-by-name and the lambda calculus, 1975).  However, in Haskell,  
eta-conversion is not valid (ie, meaning-preserving).  Observe:


f, g :: a -> b
f = undefined
g = \x -> undefined x

forall x::a, f x === g x === _|_.  However, 'seq' can tell them apart.

seq f 'a' === _|_
seq g 'a' === 'a'

So f and g are not replaceable in all term contexts (in particular,  
not in 'seq' contexts).



As I understand it, it is exactly this issue that causes some to want  
'seq' to be a class member from which functions are specifically  
excluded.




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


Re: [Haskell-cafe] "show" for functional types

2006-04-01 Thread Robert Dockins
[snip]

> No, it doesn't, because that wasn't my argument. Consider:
>
> f :: C a => a->a
> g :: C a => a->a
>
> Now if we can define just one instance of C, eg T1 where f (x::T1) \= g
> (x::T1), then we can tell f and g apart for all instances of C, even when
> there is another instance of C, eg T2, for which f (x::T2) == g (x::T2).
> Thus we can't just interchange the uses of f and g in the program because
> we can always use values of T1 to distinguish between uses of f :: T2 -> T2
> and g :: T2 -> T2.

> If f (x::T1) == g (x::T1) then nothing has been demonstrated, as you
> rightly point out, because there could be another instance of of C eg T3
> for which f (x::T3) \= g(x::T3).

I agree to this point.

> It is the inequality that is the key to 
> breaking referential transparency, because the discovery of an inequality
> implies different code.

Here is where you make the jump that I don't follow.  You appear to be 
claiming that the AbsNum module coerces a Haskell compiler into breaking 
referential integrity by allowing you to discover a difference between the
following two functions:

f :: (Num a) => a -> a
f x = x + 2

and

g :: (Num a) => a -> a
g x = x + 1 + 1


From an earlier post:

> > Now since f and g compute the same results for the same inputs,  
> > anywhere in a program that you can use f you could just replace f  
> > by g and the observable behaviour of the program would be  
> > completely unaffected. This is what referential transparency means.

My essential claim is that the above statement is in error (but in a fairly 
subtle way).  It is only true when f and g are instantiated at appropriate 
types.  This is what I meant by saying that overloading was muddying the 
waters.  The original post did not have a type signature, so one _could_ 
assume that MR forced defaulting to Integer (the MR is evil, _evil_ I say), 
which would then make the statement true _in that context_.  However the post 
with the AbsNum code instantiates f and g at a different type with different 
properties, and the equality does not hold.

> Interesting! Referential transparency (as I understand it) has indeed been 
> violated. Perhaps the interaction of GADTs and type classes was not 
> sufficiently studied before being introduced to the language.

I believe your reasoning is correct, but you are using a false supposition.


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


Re: [Haskell-cafe] "show" for functional types

2006-04-01 Thread Robert Dockins
On Saturday 01 April 2006 11:53 am, Brian Hulley wrote:
> Claus Reinke wrote:
> > the usual way to achieve this uses the overloading of Nums in Haskell:
> > when you write '1' or '1+2', the meaning of those expressions depends
> > on their types. in particular, the example above uses 'T Double', not
> > just 'Double'.
>
> However there is nothing in the functions themselves that restricts their
> use to just T Double. Thus the functions can be compared for equality by
> supplying an argument of type T Double but used elsewhere in the program
> with args of type (plain) Double eg:

Overloaded functions instantiated at different types are not (in general) the 
same function.  If you mentally do the dictionary-translation, you'll see 
why.

In particular for f, g :: XYZ a => a -> b, and types n m such that (XYZ n) and 
(XYZ m),

f :: (n -> b) === g :: (n -> b)

does *not* imply

f :: (m -> b) === g :: (m -> b)


That is where your argument falls down.


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


Re: [Haskell-cafe] "show" for functional types

2006-04-01 Thread Robert Dockins
On Saturday 01 April 2006 07:50 am, Brian Hulley wrote:
> Greg Buchholz wrote:
> >Hmm.  It must be a little more complicated than that, right?  Since
> > after all you can print out *some* functions.  That's what section 5
> > of _Fun with Phantom Types_ is about.  Here's a slightly different
> > example, using the AbsNum module from...
> >
> > http://www.haskell.org/hawiki/ShortExamples_2fSymbolDifferentiation
> >
> >> import AbsNum
> >>
> >> f x = x + 2
> >> g x = x + 1 + 1
> >>
> >> y :: T Double
> >> y = Var "y"
> >>
> >> main = do print (f y)
> >>   print (g y)
> >
> > ...which results in...
> >
> >   *Main> main
> >   (Var "y")+(Const (2.0))
> >   (Var "y")+(Const (1.0))+(Const (1.0))
> >
> > ...is this competely unrelated?
>
> Interesting! Referential transparency (as I understand it) has indeed been
> violated. Perhaps the interaction of GADTs and type classes was not
> sufficiently studied before being introduced to the language.

No, it hasn't -- the waters have just been muddied by overloading (+).  You 
have reasoned that (x + 2) is extensionally equivalent to (x + 1 + 1) because 
this is true for integers.  However, (+) has been mapped to a type 
constructor for which this property doesn't hold (aside: all sorts of useful 
algebraic properties like this also don't hold for floating point 
representations).  So, you've 'show'ed two distinct values and gotten two 
distinct results -- no suprise.

The general problem (as I see it) is that Haskell programers would like to 
identify programs up to extensionality, but a general 'show' on functions 
means that you (and the compiler) can only reason up to intensional (ie, 
syntactic) equality.  That's a problem, of course, because the Haskell 
standard doesn't provide a syntactic interpretation of runtime functional 
values.  Such a thing would be needed for runtime reflection on functional 
values (which is essentially what show would do).

It might be possible, but it would surely mean one would have to be very 
careful what the compiler would be allowed to do, and the standard would have 
to be very precise about the meaning of functions.  Actually, there are all 
kinds of cool things one could do with full runtime reflection; I wonder if 
anyone has persued the interaction of extensionality/intensionality, runtime 
reflection and referential integrity?


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


Re: [Haskell-cafe] Code Review: Sudoku solver

2006-03-22 Thread Robert Dockins


On Mar 22, 2006, at 2:16 PM, David F. Place wrote:


Hi All,

I really appreciate all the help I received when I asked you to  
critique my PrefixMap module a few weeks ago.  I think I am making  
good progress in correcting the "lisp" in my Haskell programming.   
I'll be very grateful to anyone who can take a glance at the  
attached short program and say if any unidiomatic usages pop out.



sudoku :: Sudoku -> IO ()
sudoku s = ((mapM_ putStrLn) . (check s) . (take 1) . solveSudoku) s



check puzzle [] = [showSudoku puzzle,"No solutions."]
check puzzle [solution]
  | solution `solves` puzzle =
  ["Puzzle:",showSudoku puzzle,"Solution:",showSudoku  
solution]

  | otherwise = ["Program Error.  Incorrect Solution!"]



That '(check s) . (take 1)' bit looks a little odd to me.  I would  
simply have written 'check' to match like:


check puzzle [] = 
check puzzle (solution : _ ) = 


Also, I like to put off doing IO as long as possible, so I'd probably  
have 'sodoku' return a String or [String] and move the putStr into  
main.  Its an easy way to make your code more reusable.


Also, your parser is pretty hackish (but I suspect you knew that  
already).



FYI, solveSudoku has a bug; if you enter an invalid puzzle it will  
return non-solutions.



It solves sudoku puzzles.  (What pleasure do people get by doing  
these in their heads?!?)


I have no idea.


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


Re: [Haskell-cafe] Returning a list element?

2006-03-20 Thread Robert Dockins


On Mar 20, 2006, at 5:15 PM, Neil Rutland wrote:

Hi there,

thank you all for your help with regards to the integer addition  
question that i asked yesterday it was very good in clarifying my  
ideas. However i would now like to ask for your expert help once  
again.


Basically i have a list of 16 tuples of 12 elements each, each  
tuple representing a train station - the tuple takes the form


station = [string, int, int, bool, bool, bool, bool, bool, bool,  
boo, bool, bool]
I think you'll be better off defining an enumerated type for your  
rail lines and then having each station contain a list of the lines  
to which it connects rather than trying to wrangle that huge tuple of  
booleans.  Something like:


data RailLine
  = Bakerloo | British | Central 

type Station = (String,Int,Float,[RailLine])

victoriaLine :: [Station]
victoriaLine = [("Walthamstow Central", 1, 0, [British]), ... ]


Or, better:

type Station = (String,(Int,Float,[RailLine]))

because now you can use the standard list function 'lookup'.


Or, better still, use Data.Map:

http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-Map.html


Basically i have a list called victoria line which is a list of 16  
stations. What i want to do is access an element of the list so i  
can check and output the value that it holds. I'll include all my  
code below so you can see what i mean more as well as the attempt  
that i have made to do just that - its the bit called bakerloo!


import Prelude

type Element0 = String
type Element1 = Int
type Element2 = Float
type Element3 = Bool
type Element4 = Bool
type Element5 = Bool
type Element6 = Bool
type Element7 = Bool
type Element8 = Bool
type Element9 = Bool
type Element10 = Bool
type Element11 = Bool


This all is pretty unnecessary -- as a rule of thumb, introduce a  
type alias when it makes it easier to read or maintain the resulting  
code.  I don't think these help.


type Station = [ (Element0, Element1, Element2, Element3, Element4,  
Element5, Element6, Element7, Element8, Element9, Element10,  
Element11) ]


victoriaLine :: Station

victoriaLine = [ ("Walthamstow Central", 1, 0, False, True, False,  
False, False, False, False, False, False),
  ("BlackHorse Road", 2, 3.0, False, True, False, False,  
False, False, False, False, False),
  ("Tottenham Hale", 3, 3.3, False, True, False, False,  
False, False, False, False, False),
   ("Seven Sisters", 4, 3, False, True, False, False, False,  
False, False, False, False),
  ("Finsbury Park", 5, 4.0, False, True, False, False,  
False, False, False, False, True),
   ("Highbury and islington", 6, 4.0, False, True, False,  
False, False, False, False, False, False),
  ("Kings Corss And St Pancras", 7, 3.3, False, True,  
False, True, False, False, True, True, True),
  ("Euston", 8, 1.3, False, True, False, False, False,  
False, False, True, False),
   ("Warren Street", 9, 2.0, False, False, False,  
False, False, False, False, True, False),
  ("Oxford Circus", 10, 1.45, True, False, True, False,  
False, False, False, False, False),
  ("Green Park", 11, 2.0, False, False, False, False,  
False, True, False, False, True),
  ("Victoria", 12, 2.3, False, True, False, False,  
True, True, False, False, False),
  ("Pimlico", 13, 1.0, False, False, False, False,  
False, False, False, False, False),
   ("Vauxhall", 14, 1.45, False, True, False, False,  
False, False, False, False, False),
  ("Stockwell", 15, 1.3, False, False, False, False,  
False, False, False, True, False),
  ("Brixton", 16, 2.0, False, True, False, False,  
False, False, False, False, False) ]



mainMenu :: IO()
mainMenu = do
  putStr"\n"
  putStr"Welcome To the Victoria Line Timetable System\n"
  putStr"Please Make A Choice from those Listed Below\n\n"
  putStr"Detail Station Information = stationMenu\n"
  putStr"For All Stations that link to the Bakerloo Line = Bakerloo\n"
  putStr"For All Stations that link to British Rail Services =  
British\n"

  putStr"For All Stations that link to the Central Line = Central\n"
  putStr"For All Stations that link to the Circle Line = Circle\n"
  putStr"For All Stations that link to the District Line = District\n"
  putStr"For All Stations that link to the Jubilee Line = Jubilee\n"
  putStr"For All Stations that link to the Metropolitan Line =  
Metropolitan\n"

  putStr"For All Stations that link to the Northern Line = Northern\n"
  putStr"For All Stations that link to the Piccadilly Line =  
Piccadilly\n"

  return()


FYI, putStrLn will automatically insert a newline for you, and the  
final 'return ()' is unnecessary.  My favorite idiom for this kind of  
thing is:


mainMenu = putStr $ unlines
  [ "line 1"
  , "line 2"
  , "line 3"
  ]

I think it's easier to read.


stationMenu::IO()
stationMenu = do
  putStr"\n"
  putStr"Please Select The station You are

Re: [Haskell-cafe] Lists of Lists

2006-03-08 Thread Robert Dockins


On Mar 8, 2006, at 2:27 PM, zell_ffhut wrote:
Could you explain what the function does.. I can't seem to peice it  
together.


It takes three things 1) a function 2) an index and 3) a list.  It  
finds the nth element of the list, applies the function to it and  
then returns a new list containing the new element in the same  
position.  It dies with an error message if you index past the end of  
the list.


e.g.

updateList (\x -> x + 10) 3 [0,1,2,3,4,5] == [0,1,2,13,4,5]


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


Re: [Haskell-cafe] Lists of Lists

2006-03-08 Thread Robert Dockins


On Mar 8, 2006, at 1:29 PM, zell_ffhut wrote:

Im afraid im baffled again!

Im now trying to add a char to a string of strings (eg - ["434233434"
"444929192" "909313434"]

Im sure i can use my previous function to help me achive this, but  
i can't

seem to get it workinging


charToGrid :: Char -> Position -> Grid -> Grid
charToGrid c (row,col) g = concat g (changeValue c(row*9 + col))


Im not sure i should be using concat, as i have to return a grid as  
it was

given, just with the added char.


As before, the idea is to create a new list with the changes you  
want, only now you have a list "two levels deep".  So the first thing  
to do is to pick out the sublist (row) you want to "change" and  
create a new changed sublist (row), and then rebuild your grid.  Try  
this, it may get you started:


updateList :: (a -> a) -> Int -> [a] -> [a]
updateList f i l = begin ++ (f x : end)
  where (begin, x : end) = splitAt i l


BTW, lists aren't very good for these kinds of manipulations.  If you  
really need an indexable, mutable data structure, try one of  
Data.Array.*



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


Re: [Haskell-cafe] Dropping trailing nulls from a list of list

2006-03-08 Thread Robert Dockins
On Mar 8, 2006, at 12:08 PM, [EMAIL PROTECTED] wrote:Today, I reviewed a function I wrote a few months ago.  The function, dropTrailNulls, takes a list of lists and drops trailing null lists.  For instance:  *Main> dropTrailNulls [[1],[2,3],[],[]] [[1],[2,3]]  My original implementation was terrible.  It was recursive, overly bulky, and difficult to understand.  It embarrasses me.  I won't post it here.  Today, it occurred to me this would do the trick:  dropTrailNulls list = reverse (dropWhile null (reverse list))  The problem is 20 years of experience writing efficient imperative programs says to me, "You don't drop things off the end of a structure by reversing the structure, dropping stuff from the beginning, then reversing again."  I suspect this imperative bias prevented me from coming up with the simple solution when I first wrote my function.  On the other hand, it is conceivable to me that my new implementation may actually be relatively efficient since Haskell uses lazy evaluation, and Haskell lists are constructed from the tail to the beginning. Only if the list is spine strict (AND the compiler knows this AND it decides to strictify the call).  Lazy evaluation actually builds lists from the front, unfolding thunks as they are demanded.I'm sure there are many problems that are encountered in Haskell where it is necessary to operate on the end of a list.  So, I'm wondering if the idiom, reverse, operate, then reverse is something I should add to my toolbox.  Or, is there a more efficient idiom for addressing these problems?Use a data structure which allows efficient access to the end of a sequence.  (shameless plug)  Check out Edison, it has a couple that would serve; I hope to prepare an updated release pretty soon. (http://www.eecs.tufts.edu/~rdocki01/edison.html)As to lists in particular...While I suppose its _possible_ that (reverse . dropWhile p . reverse) will be fused into something more efficient, I don't think you can count on it (any core wizards care to contradict me?).  You might be able to do something more efficient with foldr.  Humm, lets see...dropTailNulls = snd . foldr f (True,[])f x (allNulls,y)  | null x && allNulls = (True, [])  | otherwise          = (False, x : y)That seems to work.  Dunno if it's any more efficient though; it is certainly less beautiful.Rob DockinsSpeak 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


Re: [Haskell-cafe] Comparing programs

2006-03-06 Thread Robert Dockins


On Mar 6, 2006, at 1:05 PM, Harry Chesley wrote:

This is more of an algorithm question than a language question, but  
any insights would be much appreciated.


The problem is to input a series of programs and find previous  
occurrences of the same algorithm.


The programs consist of a set of input parameters (a, b, c, ...),  
and a set of side-effect-free functions (f, g, h, ...). Since the  
functions are side-effect-free, they can be reordered without  
changing the algorithm ("f(a), g(b)" is the same as "g(b), f(a)").  
Subsequent calls of the same function with the same parameters have  
no effect ("f(a), f(a)" is the same as "f(a)"); in fact, you can  
assume duplicates have been removed in earlier processing.


But here's the thing that makes it hard (at least for me): two  
programs are considered the same if they can be made to match by  
rearranging the order of the input parameters. I.e., "f(a), g(b)"  
is the same as "f(b), g(a)". Although parameters can be reordered,  
they cannot be substituted ("f(a), g(b)" is _not_ the same as "f 
(a), g(a)").


Example: "f(a), g(b), h(a, b)" is the same as "f(b), g(a), h(b, a)"  
but _not_ the same as "f(a), g(b), h(b, a)".


I need a way to compare the input programs, and preferably to order  
them.
In Haskell terms, given the programs are represented by a type  
Prog, I want Prog to be a member of class Ord, letting me use tools  
like Data.Map to look up information about previous instances.


One thing you could try is to develop a "canonical representation",  
ie, an exemplar from the equivalence class which can be calculated  
from any member of that class.  You could define a lexicographical  
order for variables and define the canonical representation such that  
the first occurrence of each variable occurs in lexicographical  
order.  Then you define an ordering based on the canonical  
representation.  If your representation of programs is simple enough,  
you can probably just use the derived Ord instance and just make sure  
to always use the canonical representation.


I can do a brute-force compare by trying all the parameter  
permutations, but that only gives me Eq, not Ord, and seems  
terribly inelegant as well.



It's hard to be more specific without more details about the language  
and the problem.  Your comments make it sound like you are dealing  
with an imperative language, but it's hard to tell.  In some cases,  
language analysis is easier if you do a dataflow analysis first and  
then do your manipulations on the resulting graphs; you might try  
taking that tack.



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


Re: [Haskell-cafe] PrefixMap: code review request

2006-02-27 Thread Robert Dockins


On Feb 27, 2006, at 2:30 PM, David F.Place wrote:


Hi,

I'm a newish Haskell hacker with way too much experience hacking  
Lisp.At first, I found my Haskell code looking very lisp-y.   I  
think my code is becoming more idiomatic haskell.  I would be very  
grateful to anyone who would take a glance at the code below and  
point out any un-idiomatic usages that jump out.  It's a small  
module from a program which looks for palindromes in a list of  
words.  Thanks very much.


[snip]


partList :: Ord k => [([k],v)]->[k]->[(k,[([k],v)])]
partList pairs alphabet = reverse . fst $ foldl' f ([],pairs) alphabet
where f (result,pairs) l = (result',rest)
  where (part,rest) = span ((==l) . head . fst) pairs
result' = if null part
 then result
 else (l,part):result


I don't think I've ever seen nested "where"s before ;-)  I'd probably  
avoid that; it's really hard to read.  If your function is  
sufficiently complicated that it needs its own "where" clause, you  
should probably just promote it to the top level.  If it is truly  
internal, you can avoid exporting it with the module export list.


[snip]

> searchMap :: Ord k => (v -> vv) -> [k] -> PrefixMap k v -> [vv]

Humm... double "v" seems like a pretty poor choice for a type  
variable name.


[snip]


Just a couple of general comments:

-- you don't seem to like horizontal whitespace much.  I know, I  
know, whitespace placement can be a highly personal thing, but I find  
most haskellers usually use a bit more horizontal whitespace,  
particularly in function signatures.  The arrow is almost always  
written with surrounding spaces.  I personally like space after  
commas in tuples and lists.  Several of your list comprehensions  
would also be easier to read with a bit of whitespace.  I also tend  
to like '=' signs lined up in a column for lets, pattern function  
definitions and wheres.


-- Nested tuple and lists types are pretty hard to read.  In your  
code [([k],v)] appears a lot.  Consider defining a type alias for it.




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


Re: [Haskell-cafe] haskell programming guidelines

2006-02-20 Thread Robert Dockins


On Feb 20, 2006, at 2:26 PM, Henning Thielemann wrote:

On Mon, 20 Feb 2006, Robert Dockins wrote:

I personally disagree with your preference for custom datatypes  
with a value representing failure to lifting types with Maybe.


I understood that part of the guidelines as a pleading for Maybe.


Humm.  Well clearly I read it the opposite way.  I suppose that means  
that whatever technique is being recommended should be put forth with  
more clarity ;-)




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


Re: [Haskell-cafe] haskell programming guidelines

2006-02-20 Thread Robert Dockins


On Feb 20, 2006, at 12:48 PM, Christian Maeder wrote:

Hi,

haskell admits many programming styles and I find it important that  
several developers of a prject agree on a certain style to ease  
code review.


I've set up guidelines (still as plain text) for our (hets) project in

http://www.informatik.uni-bremen.de/agbkb/forschung/formal_methods/ 
CoFI/hets/src-distribution/versions/HetCATS/docs/Programming- 
Guidelines.txt


These were inspired by C programming guidelines, http://haskell.org/ 
hawiki/ThingsToAvoid and the problems I came across myself.


It like to get comments or proposals for our or other haskell  
grogramming guidelines.


I personally disagree with your preference for custom datatypes with  
a value representing failure to lifting types with Maybe.  I tend to  
like using the Maybe monad for composing large partial functions from  
smaller ones, but your suggestion makes that impossible.  Also, if  
you bake in your failure case into your datatype, you can't use the  
type system to differentiate explicitly partial functions (which use  
Maybe X), from ones that are not expected to be partial (which just  
use X).  Final point, using Maybe gives you an easy route to go to  
"Either String X" or some other richer monad to represent failure.




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


Re: [Haskell-cafe] Overlapping instance problem

2006-02-13 Thread Robert Dockins
On Feb 13, 2006, at 2:26 PM, [EMAIL PROTECTED] wrote:Hi,  I've posted a couple messages to the Haskell Cafe in the last few months.  I'm new to Haskell.  But, I've set out to implement my own vectors, matrices, complex numbers, etc.  One goal I have, is to overload operators to work with my new types.  The pursuit of this goal, has pushed me to learn a lot about the Haskell type system. When I get stuck from time-to-time, the kind folks on this list have pointed me in the right direction.  I'm stuck now.  One thing I want to avoid is adding new multiplication operators to handle multiplication of dissimilar types.  For instance, I'd like to be able to have an _expression_ like k * m where k is a Double and m is a Matrix.  This doesn't work with the prelude's (*) operator because the prelude's (*) has signature:  (*) :: (Num a) => a -> a -> a.  To get around this, I wrote my own versions of a Multiply class that allows dissimilar types to be multiplied.  You can see my Multiply class in the module at the end of this Email. [snip error message]I don't understand how m1 * m2 can match the scalar multiplication instances.  For instance, the scalar * matrix instance has signature:  instance (Multiply a b c, Num a, Num b, Num c)                                 => Multiply a (Matrix b) (Matrix c) where  m1 in my _expression_ would correspond to the 'a' type variable.  But, 'a' is constrained to be a Num.  However, I never made my Matrix type an instance of Num.  Is there a work around for this?  In my first implementation, I did not have the Num constraints in the matrix Multiply instances.  I added the Num constraints specifically, to remove the ambiguity of the overlapping instance.  Why didn't this work?I'm pretty sure this is due to a misfeature of the way class class instance selection works.  Essentially, the typechecker IGNORES the instance context (everything before the =>) when looking for matches, and it only checks the context after it has irrevocably selected an instance.  Thus, rather than backtracking and trying to find another instance, the typechecker just gives you errors about unsatisfied constraints or overlapping instance errors.  Often this isn't what you want (as in this case).To be fair, doing better than this (in general) seems pretty difficult.  The typechecker sometimes needs to have more information than it can currently gather.  I think the following extension proposal might address this problem (if its ever implemented...)http://www.haskell.org/pipermail/haskell-prime/2006-February/000423.htmlAs of now, the typechecker can't be absolutely certain that 'Matrix' isn't (and will never be) an instance of 'Num'.  Just because you haven't make it a member of 'Num' doesn't mean someone else couldn't!  For it to do what you want, the typechecker needs to be able to prove that, given any legal collection of instances, the instance declarations in question will not overlap.  It can't to that.As to workarounds... that becomes more difficult.  Essentially you need to replace the bare type variable 'a' in your instance declarations with something that can guide the typechecker to select the 'correct' instance.  Two options come to mind:1) create a 'newtype' for scalars.  Now you have to wrap and unwrap your scalars, which is a bit of a pain, but it is a fully general solution.  Judicious use of newtype deriving may eliminate some of this pain.2) Create separate 'Multiply' instances for each type of scalar you want to use.  Eliminates the ugly wrapping/unwrapping, but limits the types of scalars you can use.Rob DockinsSpeak 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


Re: [Haskell-cafe] question about type lambda and decidability of typechecking

2006-02-10 Thread Robert Dockins

For the record, a little more digging turned up this

http://portal.acm.org/citation.cfm?id=583852.581496

which answers most of my questions.


On Feb 10, 2006, at 2:02 PM, Robert Dockins wrote:


OK.  I've been doing a little thinking about type lambda in Haskell.

Now, I understand the prevailing wisdom is that adding type lambda  
and/or partially applied type synonyms to the haskell type system  
would make type checking/inference undecidable.  The reason given  
is that higher-order unification is undecidable.


I have to admit that I don't fully understand this reason.  Setting  
aside typeclasses for now, it seems to me that type expressions  
together with the kind system are just the simply-typed lambda  
calculus with unit, which is well known to be strong normalizing.   
So any type with kind * has a normal form with (by definition) no  
internal redexes.  I think this is sufficient to guarantee that all  
type lambdas are removed.  Now you can proceed using first-order  
unification, which is decidable.  Of course, all valid expressions  
have kind * (ignoring unboxing and other trickiness for now).


So where have I gone wrong?  Do typeclasses complicate the matter?   
Or have I missed something more basic?



Thanks,
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




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] question about type lambda and decidability of typechecking

2006-02-10 Thread Robert Dockins

OK.  I've been doing a little thinking about type lambda in Haskell.

Now, I understand the prevailing wisdom is that adding type lambda  
and/or partially applied type synonyms to the haskell type system  
would make type checking/inference undecidable.  The reason given is  
that higher-order unification is undecidable.


I have to admit that I don't fully understand this reason.  Setting  
aside typeclasses for now, it seems to me that type expressions  
together with the kind system are just the simply-typed lambda  
calculus with unit, which is well known to be strong normalizing.  So  
any type with kind * has a normal form with (by definition) no  
internal redexes.  I think this is sufficient to guarantee that all  
type lambdas are removed.  Now you can proceed using first-order  
unification, which is decidable.  Of course, all valid expressions  
have kind * (ignoring unboxing and other trickiness for now).


So where have I gone wrong?  Do typeclasses complicate the matter?   
Or have I missed something more basic?



Thanks,
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


Re: [Haskell-cafe] Combinatory logic interpreter?

2006-02-10 Thread Robert Dockins

On Feb 10, 2006, at 11:09 AM, Colin Paul Adams wrote:
Is there any Haskell code around that can interpret combinatory  
logic expressions?


Humm.  That's kind of a broad question.  I've written a shell for  
interpreting the pure untyped lambda calculus which has definitions  
for Turner's Combinators.  You can get the darcs repo here:


http://www.eecs.tufts.edu/~rdocki01/lambda/

you will also need

http://www.eecs.tufts.edu/~rdocki01/shell/
http://www.eecs.tufts.edu/~rdocki01/shell-readline/


Or... you can play with it on the haskell IRC channel by using the  
'@lam' lambdabot command.



Its hard to know if this will meet your needs without knowing more.   
What are you trying to do?



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] Re: Re[2]: Tuple-like constructors

2006-02-08 Thread Robert Dockins


[Moved to cafe; time to stop bothering the Haskell' committee...]

On Feb 8, 2006, at 1:19 PM, Malcolm Wallace wrote:

Robert Dockins <[EMAIL PROTECTED]> writes:


instance (Bin a,Bin b,Bin c,Bin d) => Bin (a,b,c,d)

See the problem?  Sooner or later (probably sooner) I'll get tired of
typing.  I have to write down an 'instance' declaration for each
value of n.  Clearly this can't generalize to all n.


There has been a suggestion that the 'deriving' mechanism be de- 
coupled

from the datatype declaration.  Together with a generic default
definition, that means you could write something like

deriving Bin for ()

and hence not need to write the tedious instance header yourself,
since the compiler can easily infer it.


Humm.  That is nice, and it would help keep my fingers from cramping,  
but it doesn't solve the root objection.  Consider machine-generated  
code using largish tuples.  Should the generated code include the  
'deriving' clause?  If no, someone from outside has to supply it.  If  
yes, I have to deal with overlapping instance from other generated  
code.  If maybe, I have to know when to generate it and when not.   
Solvable? yes, but kind of ugly.  Acceptable? probably.



Now, (speculatively combining a whole host of language extensions) if  
I could write down:


deriving Bin for (_::*)

Which would mean "derive (as necessary) Bin for all types at kind *  
where the suitable preconditions can be found/derived" I'd be  
completely happy.




Humph.  That's more or less adding an axiom schema to the constraint  
solving system of the typehecker which could be realized at link-time  
via C++ style template thingies or at compile-time by whole-program  
analysis.  I am simultaneously appalled by and attracted to this  
idea.




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


Re: [Haskell-cafe] extending bang proposal Re: strict Haskell dialect

2006-02-06 Thread Robert Dockins


On Feb 6, 2006, at 9:19 AM, Bulat Ziganshin wrote:


Hello Ketil,

Monday, February 06, 2006, 4:06:35 PM, you wrote:


foo :: !Int -> !Int


KM> (Is the second ! actually meaningful?)

yes! it means that the function is strict in its result - i.e.  
can't return
undefined value when strict arguments are given. this sort of  
knowledge

should help a compiler to "propagate" strictness and figure out the
parts of program that can be compiled as strict code. really, i think
ghc is able to figure functions with strict result just like it is  
able to

figure strict function arguments

KM> Personally, I think is much nicer than sprinkling seq's around,  
and
KM> generally sufficient.  However, there could perhaps be  
disambiguities?


btw, it's just implemented in the GHC HEAD



Actually, I think strict _patterns_ are implemented.  You are talking  
about strict _type annotations_, which is rather different.


As I understand it, strict patterns are just sugar for putting 'seq'  
in the right places.


There has been some work dealing with folding strictness and totality  
information into types systems; I find the resulting type systems  
pretty ugly, and I think they'd be pretty hard to bolt onto an HM base.



Robert 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


Re: [Haskell-cafe] Re: Haskell code for this example of flow control

2006-02-03 Thread Robert Dockins


On Feb 3, 2006, at 11:28 AM, MaurĂ­cio wrote:

Kurt Hutchinson wrote:

On 2/2/06, MaurĂ­cio <[EMAIL PROTECTED]> wrote:
  I understand those examples, but I really would like to know  
how to
do that with monads. I would like to ask the same question, but  
now with

this code:

double a = 1000;
double b = 0;
while (a != b) {
a /= 2;
cout << a; // Prints a
cin << b; // User gives a number, stored in b
};

An idiomatic approach:
example :: Double -> Double -> IO ()
example a b
| a == b= return ()
| otherwise = do
let a' = a / 2
print a'
b' <- readLn
example a' b'
main = example 1000 0


  Thanks! Robert's, Chris' and yours examples solved many of my  
questions. I understand I can insert modifications in IORefs (as  
used by Robert and Chris) inside the loop above:


| otherwise = do
 let a' = a / 2
 ...
 modifyIORef some_ioref some_function
 ...
 example a' b'

  I wonder if I could write a generic while based on your example:

while :: (a -> IO a) -> (a -> Bool) -> IO ()

  I'll probably learn something trying that.


FYI, here's a thread from a few months back about monad control  
structures; it may also provide some enlightenment.



http://www.haskell.org/pipermail/haskell-cafe/2005-October/011890.html



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


Re: [Haskell-cafe] Re: Haskell code for this example of flow control

2006-02-02 Thread Robert Dockins
I think you're looking for IORef http://www.haskell.org/ghc/docs/ 
latest/html/libraries/base/Data-IORef.html


Something like this (untested) should do what you want:

example :: IO ()
example = do { ref <- newIORef 1000; loop ref }
 where loop ref = do
   x <- readIORef ref
   print x
   when (x>1) (writeIORef ref (x/2) >> loop ref)


On Feb 2, 2006, at 10:57 AM, MaurĂ­cio wrote:


Donald Bruce Stewart wrote:

briqueabraque:

 Hi,

 I would like to know what options I have in Haskell to do  
something similar to this C++ code:


double a = 1000;
while (a>1) a/=2;

 I'm able to do that with lists, but I would like to know how to  
do that with monads and variables with state.

You'll get good code using a normal recusive loop:
main = print (loop 1000)
where
loop a | a <= 1= a| otherwise  
= loop (a/2)

All such control structures may be implemented using recursion.
-- Don


  I understand those examples, but I really would like to know how  
to do that with monads. I would like to ask the same question, but  
now with this code:


double a = 1000;
double b = 0;
while (a != b) {
a /= 2;
cout << a; // Prints a
cin << b; // User gives a number, stored in b
};

  Best,
  MaurĂ­cio


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




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] library(s) for numeric constant folding?

2006-01-29 Thread Robert Dockins
Does anyone know of a good library or libraries which will allow me  
to perform arithmetic operations on


  1) binary integers (signed and unsigned) of various fixed sizes?
  2) IEEE 754 floating point numbers (single and double precision).

Pure Haskell is preferable, but I'll make do with C bindings.  I need  
to do constant folding for integral and floating point types for a  
compiler front-end, and I'm hoping that I don't have to write this  
stuff myself


Why not just use Float and Double for 2) you ask?  Because I need to  
to EXACTLY IEEE 754 computation, and the Haskell report is pretty  
dodgy about what implementations are required to provide.


Thanks



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


Re: [Haskell-cafe] How to redirect a handle within a thread (GHC 6.4.1 runtime)?

2006-01-18 Thread Robert Dockins


On Jan 18, 2006, at 2:59 PM, Benjamin Franksen wrote:


On Wednesday 18 January 2006 19:01, Dimitry Golubovsky wrote:

Is it possible to redirect a Handle (say stdout) somewhere only
within a running thread (started with forkIO) not touching the same
handle for the main and other threads?

I have a lot of code written with putStr(Ln) which was used in a
program acting as a filter, i. e. stdout was redirected by the
invoking shell. Now I want to run this code within a thread in other
program, but output must go to a file (or a pipe, or anywhere else a
file descriptor may be opened for). So fdToHandle is not good because
I need to modify the `stdout' only for that thread, not to create a
new Handle. Rewriting the code is not a convenient way (but will be
done if nothing else helps) because then I will need to pass that
handle around.


Isn't this _the_ real-world example perfectly matching Robert Dockins'
'threadlocal' proposal?


Yes, actually.  This is precisely the use case that got me thinking  
about threadlocal storage in the first place.  I'm working on Shellac  
(http://www.mail-archive.com/haskell@haskell.org/msg17871.html) and  
it turns out that redirecting the standard output handle for a  
specific thread would be really nice.  The obvious alternative is to  
pass in a function of type (String -> IO ()) and pass it around, and  
make sure to use it instead of putStr and friends.  The non-obvious  
alternative is some unsafePerformIO hackery, as just posted.  Either  
way, its ugly.


[snip]


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


Re: [Haskell-cafe] Yet another top-level IO proposal

2006-01-17 Thread Robert Dockins
> Hello,
>
> Well it seems like you haven't started another flame war (yet :-).

Indeed; I am a little surprised to hear the silence.

> I'm afraid I haven't properly understood your proposal, because I
> don't have much time right now. It seems to be a bit like George
> Russels proposal (aka "execution contexts").

Somewhat.  However, execution contexts don't have the initializer concept.

> Personally I have never felt the need for thread local state, but
> I have often needed to use the unsafePerformIO hack to create
> *unique state* for API's that are both sane from a users point of
> view and are also invulnerable to accidental or malicious state
> "spoofing". So thread local state isn't really what I want (it's
> a sure way to guarantee that spoofing will occur :-)
>
> You seem to indicate that this is still possible with your scheme,
> but I'm not sure of the details.

If you declare a thread-local in a module but don't export it, then you have 
exclusive control over what happens to that thread-local.  You set the 
initializer and no one else can touch it.  If you set an initializer that 
copies parent values and never write to the cell, you effectively have a 
variable that is set exactly once at program start.

The only way to alter this from outside the module is to use the "clearBank" 
primitive, which resets all thread-locals to empty.  It may be that this 
primitive is too dangerous to include.

On the other hand, I'm not convinced that absolutely unique state is that 
great.  Suppose I want to run multiple copies of my Haskell OS in an emulator 
so I can test the TCP/IP stack I just wrote? I'll need some way to keep the 
"unique" state for each OS separate.

> Maybe you should put all this 
> on the wiki page. I'd like to see how/if you could implement
> the hypothetical device driver API I put there, or even just
> use the "oneShot" function or similar at the top level.

I've attached a hypothetical implementation in the proposed syntax.

> Regards
> --
> Adrian Hey

Robert Dockins
module FictionalDevice
( device1
, device2
, DeviceHandle
, initDevice
, someDeviceAction
)

import Control.Concurrent
import Control.Concurrent.MVar

type BaseAddress = ...

data DeviceState = 
  DeviceState 
  { isFirstAccess :: Bool
  , baseAddress   :: BaseAddress
  , ...
  }

initialDeviceState :: BaseAddress -> DeviceState
initialDeviceState addr = DeviceState
  { isFirstAccess = True
  , baseAddress   = addr
  , ...
  }

device1baseAddresss :: BaseAddress
device1baseAddress = ...

device2baseAddresss :: BaseAddress
device2baseAddress = ...

threadlocal device1state (MVar DeviceState)
   (initTL (newMVarTL (initialDeviceState device1baseAddress)))

threadlocal device2state (MVar DeviceState)
   (initTL (newMVarTL (initialDeviceState device2baseAddress)))

newtype DeviceHandle = DH (TLRef (MVar DeviceState))

device1 = DH device1state
device2 = DH device2state

doInitDevice :: BaseAddress -> IO ()
doInitDevice addr = ...

initDevice :: DeviceHandle -> IO ()
initDevice (DH ref) = do
  stMvar <- readThreadLocal ref
  modifyMVar_ stMVar (\st -> do
when (isFirstAccess st) (doInitDevice (baseAddress st))
return st{ isFirstAccess = False })
  
someDeviceAction :: DeviceHandle -> IO ()
someDeviceAdction h@(DH ref) = do
  initDevice h
  ...___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Yet another top-level IO proposal

2006-01-16 Thread Robert Dockins

Fellow haskellers,

I have a proposal I would like to enter into the eternal top-level IO  
debate.  The proposal
involves a minor language extension and some runtime support for  
thread local reference cells.
I believe it has the potential to meet many of the needs of those  
requesting top level IO.


My apologies for this rather lengthy message, but given the  
volatility of discussion on this matter
in the past, it seemed best to lay out my thoughts as precisely as  
possible at the beginning.


So without further ado, the proposal.


The language extension:

-- Add a new keyword 'threadlocal' and a top level declaration with  
the syntax


  threadlocal   expression>


-- The declaration consists of three parts 1) the name of the  
reference cell 2) the type of

data stored in the cell and 3) an initializer action.
-- The name of the cell declared with 'threadlocal' shares the  
function namespace and introduces
a CAF with the type 'TLRef a', where 'a' stands for the type  
given in the declaration.
-- The initializer action must be an expression with type 'TL a',  
where 'a' stands for the
the type given in the 'threadlocal' declaration, and 'TL' is the  
thread-local initialization

monad (a little like the ACIO monad, more on this below).

The semantics:

-- Each thread in a program (the main thread and threads sparked from  
forkIO and forkOS) has a "bank"
of thread local variables.  Writes to and reads from a thread- 
local cell are only written to/read

from the bank of the thread performing the write/read.
-- For any given bank, a thread-local cell may be "empty" (which  
means it holds no value) or "full"

with a value of its declared type.
-- There is a phantom bank of thread-local values belonging to no  
thread in which the value of all
thread-local cells is "empty".  This represents the state of  
thread local variables before program

start.
-- Whenever a thread is sparked (including the main thread) and  
before it begins executing, its
thread-local variables are initialized.  For each declared  
thread-local variable (in the transitive
closure of imported modules), the declared initilzation action  
is run and the generated value initializes
the thread-local cell for that thread.  The initializer actions  
are run in an unspecified order.
-- The primitives of the TL are strictly limited and include only  
actions which have no observable
side effects (a proposed list of primitives is listed below).  A  
TL action may read from (but NOT write
to) thread-local cells in the bank of the sparking thread (the  
bank of the thread calling forkIO, or the

special phantom bank for the main thread).
-- Any exceptions generated during a thread-local initilization  
action are propigated to the thread
which called forkIO/forkOS or, in the case of the main thread,  
directly to the runtime system just

as though an uncaught exception bubbled off the main thread.
-- New IO primitives are added to read from, write to and clear (set  
to empty) thread-local variables.



Advantages:

This proposal seems to hit most of the use cases that I recall having  
seen (including the very important
allocate-a-top-level-concurrency-variable use case) and seems to  
provide a nice way to reinterpret some
of the "magic" currently in the standard libraries.  In addition,  
this proposal does not suffer from the
module loading order problem that some previous proposals have;  
because thread local initializer actions
depend only on the "previous" bank of values, the order in which they  
are run makes very little difference
(only for the primitives that read clock time or some such).  The  
value of a thread-local cell is always well-defined,
even before the main thread starts. Values in a thread-local have a  
well defined lifetime that is tied to the owning
thread.  I think that efficient implementation is possible (maybe we  
can play some copy-on-write games?).


I especially like that variables are only as "global" as desired for  
any given task; if a library writer
uses thread-locals for some manner of shared "global" state, later  
users are always able to write programs
that use more than one instance of the "global" state without needing  
to alter the library.


Disadvantages:

Requires a language extension (but I don't know of a serious  
alternate proposal that doesn't).  Requires
non-trivial runtime system support.  Not sure what effect this has on  
garbage collection. Adds overhead to
thread creation (this could perhaps be mitigated by introducing new  
primitives that distinguish heavyweight
threads with their own thread-local banks from lightweight threads,  
which do not have separate thread-local banks).
Its a bit complicated.  You can shoot yourself in the foot (true of  
most of the other proposals).



Some representative use cases:

-- Implicit parameter style use case:
  You want to provide a default value that you 

Re: [Haskell-cafe] Splitting a string into chunks

2006-01-13 Thread Robert Dockins


On Jan 13, 2006, at 4:35 PM, Jon Fairbairn wrote:


On 2006-01-13 at 13:32PST Jared Updike wrote:

That works except it loses single newline characters.

let s = "1234\n5678\n\nabcdefghijklmnopq\n\n,,.,.,."
Prelude> blocks s
["12345678","abcdefghijklmnopq",",,.,.,."]


Also the argument to groupBy ought to be some sort of
equivalence relation.


Humm, still not reflexive.  You need xor.


blocks = map unlines
 . filter (all $ not . null)
 . groupBy (\a b -> not (null b|| null a))
 . lines

... but that suffers from the somewhat questionable
properties of lines and unlines.

-- JĂłn Fairbairn  Jon.Fairbairn at  
cl.cam.ac.uk



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


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


Re: [Haskell-cafe] Is there a notion for identity?

2006-01-09 Thread Robert Dockins
On Monday 09 January 2006 04:09 am, Tim Walkenhorst wrote:
> Thanks for all infos.
>
> I'll apply that Ref-datatype from the "observable sharing" paper
> to my problem and see where this brings me. I'm also looking
> into the solution Paul Hudak presented in the
> "Detecting Cycles in Datastructures" thread in october.
>
> > For the problem at hand (involving the STLC), you will not be able to
> > type omega because omega is a non-normalizing closed term and STLC has
> > the strong normalization property.  You will have to move to a more
> > expressive calculus to type omega.
>
> I guess the infinite omega-"type" I'm using is not a type in
> the same way as infinity is not a number. You cannot reach it
> by structural induction.

Right.  This is something that seems to cause confusion for people 
occasionally.  I myself didn't understand this subtle point until I did some 
work with the with the proof assistant Coq which differentiates between 
inductive and coinductive definitions.  Haskell datatypes are actually 
coinductive, which are are related to sets of objects created by a maximal 
fixpoint (rather than the more usual least fixpoint).  This means that 
Haskell datatypes admit more values than their inductive cousins, and can 
cause unintuitive results like this where you can create things that 
"shouldn't exist" according to the literature, like a type for omega in STLC.

> Therefore the strong normalization 
> property will not work for infinite types (or none-types if
> you prefer). I admit that allowing infinite types basically
> means moving to a more expressive calculus. Probably the
> best thing is to introduce the recursion operator mu explicitly
> and avoid the cyclic structures.

That would be my recommendation.  Cyclic datastructures bend my mind and tend 
to be hard to work with; I personally try to avoid them except for a few 
idiomatic uses involving lists.

> I just thought it would 
> be interesting to play around with infinite stuctures in this
> context.
>
> Thanks again,
> Tim
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is there a notion for identity?

2006-01-08 Thread Robert Dockins
On Sunday 08 January 2006 06:43 am, Tim Walkenhorst wrote:
> {- Disclaimer: I'm rather new to Haskell and completely new to this board.
>  I may not use the correct terminology in all cases, but I hope my
>  intention becomes clear when you have a look at the code-snippets. -}
>
> Hey ho,
>
> Is there any way two find out whether two variables refer to the
> same cell? That is I'm looking for a notion of identity (compareable
> to == in Java) as opposed to equality (== in Haskell).

Another poster has already replied with a link to a long answer.  The short 
answer is "no, not really".

An attempted rationale:

The semantics of such an "identity" operator are unclear.  The operator could 
be a test for leibenz equality (ie, structural equality, ie replaceability in 
all contexts), but such an operator cannot be decidable (proof due to 
Church), so that wouldn't help in your situation anyway.  The general 
usefulness of such an operator is debatable.

We could instead provide an implementation-dependent operation that tests for 
identical heap location, but such an operator would give different results 
with different Haskell implementations and would be sensitive to 
optimizations.  That would either be a horribly broken operator or (to fix 
the brokeness) greatly constrain the avaliable optimizations and 
implementation strategies.



For the problem at hand (involving the STLC), you will not be able to type 
omega because omega is a non-normalizing closed term and STLC has the strong 
normalization property.  You will have to move to a more expressive calculus 
to type omega.


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


Re: [Haskell-cafe] How to read this syntax?

2005-12-29 Thread Robert Dockins


On Dec 29, 2005, at 11:26 AM, David F. Place wrote:


Hi,

I am trying to read _Arrows, Robots, and Functional Reactive  
Programming_ by Hudak, et al.


http://www.haskell.org/yampa/AFPLectureNotes.pdf

In section 2.1 there are a number of equations of the form:

g’ :: SF A C
g’ = arr g
= arr f1 >>> arr f2

and

i’ :: SF (A,C) (B,D)
i’ = arr i
   = arr (f1 . fst) &&& arr (f2 . snd)
   = (arr fst >>> arr f1) &&& (arr snd >>> arr f2)

I can't find any reference to the syntax where the function left  
hand side is just  "space."  I'd greatly appreciate any insight.




I'm pretty sure the extra lines are assertions of equality.  That is,  
they are other ways of defining the same function.  That isn't legal  
Haskell syntax as written.


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


Re: [Haskell-cafe] Shared/Exclusive Locks

2005-12-28 Thread Robert Dockins


On Dec 28, 2005, at 1:38 PM, Tomasz Zielonka wrote:


On Wed, Dec 28, 2005 at 05:28:28PM +, Chris Kuklewicz wrote:

But STM, wrapped in small pieces, makes for interesting IO commands
(untested):



waitForZero :: (Num a, Ord a) => (TVar a) -> IO ()
waitForZero tv = atomically $ do
  v <- readTVar tv
  when (v>0) retry


This function is rather useless in IO - you will get race conditions.
That's what you get for leaving the STM wonderland ;-)


Actually, I think it works in the particular instance given of  
constructing read-write locks because the call to waitForZero is  
guarded by a mutex.  But it would certainly be easy to introduce a  
race condition using constructs like this.  Given the alternatives  
{use STM fully, use STM some, don't use STM}, I would have a hard  
time justifying the "use STM some" alternative (at least for new  
programs).  If you are OK with introducing a dependency on STM, why  
not go whole hog?



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


Re: [Haskell-cafe] Shared/Exclusive Locks

2005-12-28 Thread Robert Dockins


On Dec 28, 2005, at 11:14 AM, Chris Kuklewicz wrote:


John Goerzen wrote:

Hello,

I have the need for a locking object that can provide shared and
exclusive locks in much the same manner as the POSIX flock()  
function.


A thread that acquires an exclusive lock has a guarantee that no  
other

thread holds any locks.

A thread that acquires a shared lock has a guarantee that no other
thread holds an exclusive lock, though any number of other threads  
hold

shared locks.

My intuition tells me that this could be implemented in terms of  
an MVar

somehow.  (At least, I've used MVars for simple locks for quite some
time.)  But I can't quite figure out how.  Any ideas?

Thanks,

-- John


STM or IO ?

You need a count of shared locks "S", *Var Word32.

To increase the count "S", you need to hold a mutex "E", *Var ().
So (take mutex "E" >> increment "S" >> release "E") is the the  
combined

operation.

To decrease the count "S", you do not need to hold a mutex.  
(decrement "S").


By grabbing the mutex "E" and waiting for "S" to go to zero, you have
acquired exclusive control.  When you are done just release "E".

--
Chris


This seems fine for STM because you can just retry until count is 0,  
but I don't know of a good way to wait for an MVar to have a  
particular value (I assume busy-wait isn't what you have in mind).   
You'll probably need an additional MVar that exclusive lockers "take"  
to let them block.  Then you need to be sure that this MVar is filled  
when count goes to 0 and empty when count goes above zero.



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


Re: [Haskell-cafe] Prime numbers

2005-12-20 Thread Robert Dockins


-divides a b = (mod a b == 0)
+divides a b = (mod b a == 0)


On Dec 20, 2005, at 11:09 AM, Daniel Carrera wrote:


John Peterson wrote:

Add a type signature:
prime :: Integer -> Bool
It's defaulting to Int and you're getting overflows


Thanks. Hmm... it's still not working.

Btw, I mis-reported the problem. The offending number is 38466629,  
which is /not/ prime but the sample program reports as prime.


38466629 = 31 * 1240859

The offending program is:
--//--
prime :: Integer -> Bool
prime n = not (factors 2 n)

factors :: Integer -> Integer -> Bool
factors m n | m == n = False
| m < n  = divides m n || factors (m+1) n

divides :: Integer -> Integer -> Bool
divides a b = (mod a b == 0)
--//--

The math behind the program seems correct... :(

Cheers,
Daniel.



--
 /\/`) http://oooauthors.org
/\/_/  http://opendocumentfellowship.org
   /\/_/
   \/_/I am not over-weight, I am under-tall.
   /
___
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: Bringing Erlang to Haskell

2005-12-13 Thread Robert Dockins

BTW, there has already been some work in this area.

http://www-i2.informatik.rwth-aachen.de/~stolz/dhs/
http://www.informatik.uni-kiel.de/~fhu/PUBLICATIONS/1999/ifl.html


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


Re: [Haskell-cafe] Tail-call optimization

2005-12-11 Thread Robert Dockins
On Sunday 11 December 2005 06:54 pm, Joel Reymont wrote:
> Thank you Andrew! Does it have any effect on performance? Is there a
> speed up of any sort from not passing parameters?

Shooting from the hip here, but I doubt it -- AFAIK it all gets lambda-lifted 
in the compiler anyway.

> On Dec 11, 2005, at 11:50 PM, [EMAIL PROTECTED] wrote:
> > Good, but even better is this:
> >
> > writeLoop :: (Event a -> IO ()) -> Handle -> (SSL, BIO, BIO) -> IO ()
> > writeLoop post h ssl
> >   = loop
> >   where
> > loop = do handle (\e -> post $ NetworkError e) $
> > do cmd <- read h ssl
> >post $! Cmd $! cmd
> >   loop
> >
> > Avoiding parameter passing can make your code a lot easier to read.
>
> --
> http://wagerlabs.com/
>
>
>
>
>
> ___
> 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] Can't Haskell catch upwith Clean's uniqueness typing?

2005-12-06 Thread Robert Dockins
On Tuesday 06 December 2005 04:00 pm, [EMAIL PROTECTED] wrote:
> From: "Shae Matijs Erisson - [EMAIL PROTECTED]"
> Sent: Tuesday, December 06, 2005 6:16 PM
>
> > [EMAIL PROTECTED] writes:
> > > being occupied with learning both languages, I'm getting curious if
> > > Haskell couldn't achieve most of the performance gains resulting from
> > > uniqueness typing in Clean by *automatically* determining the reference
> > > count of arguments wherever possible and subsequently allowing them to
> > > be physically replaced immediately by (the corresponding part of) the
> > > function's result. Are there any principal obstacles, or *could* this
> > > be done, or *is* this even done already, e. g. in ghc?
> >
> > Maybe you're describing speculative evaluation?
> >
> > Optimistic Evaluation: An Adaptive Evaluation Strategy for Non-Strict
> > Programs http://citeseer.ist.psu.edu/ennals03optimistic.html
> > --
>
> Thanks for the pointer - I have heard a little about optimistic evaluation
> already, but don't know much of the details (yet). Anyway, from what I
> know, I think it's a different thing.
>
> In Clean, you can (and often are required to) assign uniqueness attributes
> to some parts of a function's type signature. The extended type checker
> ensures that none of those parts is referred to more than once during a
> single run of the program. Based on this guarantee, a function does not
> have to allocate new memory at all to store a unique result but can
> overwrite the unique arguments in place.
>
> Apparently, the uniqueness assignments have to comply with very tight laws
> - getting a program through the Clean type checker can be tough, once it
> reports an uniqueness coercion error. I suppose, no explicit uniqueness
> attributing is going to be implemented in Haskell, anyway.
>
> My question is - and this might better suit to Haskell -, can't uniqueness
> be inferred (and exploited) automatically in many cases?

Yes, probably.  There is a technique called sharing analysis that attempts to 
determine when a datastructure is only referenced once (ie, NOT shared).  If 
you can prove a datastructure node is not shared then you can reuse it 
destructively.

Here is a paper on the technique.  It's written for lisp cons cells, but one 
might be able to generalize the technique to ADT.  I don't know where to find 
a free copy.

http://portal.acm.org/citation.cfm?id=99375


There has also been some similar work done along these lines for Mercury (a 
logic programming language).

http://www.cs.mu.oz.au/research/mercury/information/papers.html

Search for papers with the word "reuse" in the title.  I'm not very familiar 
with this work, so I don't know how applicable this might be.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monads as control structures?

2005-10-27 Thread Robert Dockins


On Oct 27, 2005, at 11:54 AM, Creighton Hogg wrote:


Hi,
so I'm a newbie getting used to Haskell.  I'm writing some
simple things like genetic algorithms in it for practice,
and I keep coming across something that really bugs me:
are there any standard libraries that allow you to
do imperative style for or while loops using monads to keep
track of state?

I know there's things like "until", but honestly that's not
quite what I'm looking for.

I just think there should be a simple way to say "execute
this block of code 10 times" without having to wrap it up in
recursion.

Haskell seems to me to be a very powerful language, and it
looks like it should be possible to define control
structures such as for loops using monads.


One way is to create a list of the actions you want to execute, and  
then use one of the sequence family of functions.
The actions can share state with an IORef or STRef or whatever.   
Another option is to use a fold with >>= to allow
actions to pass their results directly to the next action.  This  
works even in "stateless" monads like the list monad.


Some examples using sequence:


forMonad :: Monad m => a -> (a -> Bool) -> (a -> a) -> (a -> m ()) ->  
m ()
forMonad init cond inc f = sequence_ $ map f $ takeWhile cond $  
iterate inc init


xTimes :: Monad m => Int -> (Int -> m ()) -> m ()
xTimes x f = sequence_ $ map f [0..(x-1)]

main = do { forMonad 0 (<10) (+1) (putStrLn . show); xTimes 10 (\_ ->  
putStrLn "hi") }


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


Re: [Haskell-cafe] Haskell scripting system (please help me simplify the design)

2005-10-27 Thread Robert Dockins
On Oct 27, 2005, at 11:01 AM, Joel Reymont wrote:Folks,With lots of help from #haskell and haskell-cafe I came up with the following setup. It's working fine but requires quite a bit of boilerplate code. Could you please help me simplify it?I apologize for the very long message and will describe any parts that are unclear. Please ask away. This is my first Haskell code, written over the course of 3 weeks (1 week to learn Haskell) so I'm bound to get some things wrong or unoptimal. Still, I'm quite amazed that I have been able to get this to work and to work correctly in such a short time span.Welcome to Haskell!The system is basically a scripting engine to test a poker server that lets you write simple scripts. I went out of my way to enable QA techs to use as little Haskell as possible, thus I'm treating all poker commands/packets as a list of properties.What I found is that I'm writing a lot of boiler-plate code to handle the convertion of property values into "storables". I think this dovetails into the recent GADT discussion. I wonder if my design and interaction between Packet, Convertible, Prop and Attr can be simplified.[snip]My concern is mostly with a lot of similar boilerplate code required for casting, specially in very alike cases like the following:data Pot = Pot [Prop] deriving (Eq, Show, Typeable)data BaseTableState = BaseTableState [Prop] deriving (Eq, Show, Typeable)instance Packet Pot where    unstuff xs = case props                 of Just props -> (Just $ Pot props, xs')                    Nothing -> (Nothing, xs)        where (props, xs') = unstuffprops xs potProps <<< this is the only difference    stuff (Pot a) = stuffprops a    size (Pot a) = sizeprops ainstance Convertible [Prop] Pot where    convert_AB a = Pot $ mergeprops a potProps    convert_BA (Pot b) = binstance Packet BaseTableState where    unstuff xs = case props                 of Just props -> (Just $ BaseTableState props, xs')                    Nothing -> (Nothing, xs)        where (props, xs') = unstuffprops xs baseTableStateProps    stuff (BaseTableState a) = stuffprops a    size (BaseTableState a) = sizeprops ainstance Convertible [Prop] BaseTableState where    convert_AB a = BaseTableState $ mergeprops a baseTableStateProps    convert_BA (BaseTableState b) = bNotice that the differences are only in the list of properties required for conversion. I'm wondering if this can be simplified somehow.You could consider creating a monad for the "unstuff" part of the operation that would hide dealing with the FastString, the tupling and the case analysis on Maybe.Your code might then look like:class (Eq a) => Packet a where   unstuff :: Unstuff a   stuff :: a -> P.FastString   size :: a -> Intinstance Packet BaseTableState where  unstuff = unstuffprops baseTableStateProps >>= return . BaseTableState  sutff (BaseTableState a) = stuffprops a  size (BaseTableState a) = sizeprops a where Unstuff is the type constructor for your monad.If you end up doing a lot of instances like this, the monad could well be a win;  it also gives you the opportunity to add error reporting during the parse if you want.As a side note, I see you are doing a bunch of operations on lists of properties.  If performance is an issue, you might want to consider using Data.Map or similar.  If your properties lists can get big, mergeprops looks like a potential problem (   O( n*(n+m) ) each time it's called   ).___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec, state and/of my cluelessness

2005-10-17 Thread robert dockins


[snip]


Now comes the tricky part for me. Since the control can have three different
types of children I use a helper that parses the body of the control using other
parsers, collecting their results in three lists:

ctrlBodyParser :: CharParser ([Value], [Property], [Control]) 
 ([Value], [Property], [Control])

ctrlBodyParser =
do { c <- ctrlParser -- parse child control
   ; (vs, ps, cs) <- getState
   ; setState (vs, ps, (c : cs))
   ; ctrlBodyParser
   }
<|>


 [snip some alternatives]


<|>
do { getState } -- we're finished, return children



I think you might do better to make it tail-recursive (sort of) by 
passing intermediate lists as parameters to ctrlBodyParser rather than 
using state.  Parsec state (if I recall correctly) needs to have the 
same type throughout the parse, but here you really just want a bit of 
help accumulating some results in a section of the parse tree.  Try this:


ctrlBodyParser :: Parser ([Value],[Property],[Control])
ctrlBodyParser = ctrlBodyParser0 [] [] []

ctrlBodyParser0 :: [Value] -> [Property] -> [Control] ->
Parser ([Value],[Property],[Control])
ctrlBodyParser0 vs ps cs =
do { c <- ctrlParser; ctrlBodyBodyParser0 vs ps (c : cs) }
<|>
 etc
<|>
do { return (vs,ps,cs) }


Be aware that your lists will come out in the reverse order that they 
apper in the text.


You can also use a single labeled record instead of the three list 
parameters and a tuple.


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


Re: [Haskell-cafe] Newbie question on Haskell type

2005-10-14 Thread robert dockins
So this is essentially a parsing problem.  You want a user to be able 
input a string and have it interpreted as an appropriate data value.  I 
think you may want to look at the Parsec library 
(http://www.cs.uu.nl/~daan/parsec.html).  I don't think the direction 
you are heading will get the results you want.



As to typeable, the basic types are mostly all members of Typeable.  You 
can find a pretty good list here:


http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data.Typeable.html#t%3ATypeable

Additionally, GHC can create Typeable instances automaticly for user 
defined datatypes; just add a deriving Typeable clause.


data SomeType = C1 | C2 deriving (Show,Eq,Typeable)

The restriction is that all types which appear in constructors must also 
be in Typeable.


I believe the DrIFT preprocessor can also create Typeable instances if 
you are not using GHC.


Huong Nguyen wrote:

Hello,

Thanks for your solution.

My main purpose is that I want to input a value and check whether this 
value is belong to some specific types or not. These types can be some 
popular types (such as: String, Char, Int, etc) or some more complex 
data structures defined by user. Thus, at first, I try with type String 
(even with that simple type, I still face difficulty ;-))


I want to ask you which types can be used with Data.Typeable. I read for 
over 15 minutes but it is still not clear with me.
For some other complex data types defined by user, what I should do to 
use Data.Typeable ?


Thank you very much.

On 10/13/05, *robert dockins* <[EMAIL PROTECTED] 
<mailto:[EMAIL PROTECTED]>> wrote:


In GHC you can do this:

 > import Data.Typeable

 > isString :: (Typeable a) => a -> Bool
 > isString x = typeOf x == typeOf (undefined::String)

Why do you want this?  It's not the kind of operation one does very
often in Haskell.


Huong Nguyen wrote:

 > Hi all,
 >
 > I want to write a small functionto test whether an input is a
String or
 > not. For example,
 >
 > isString::(Show a) =>a ->Bool
 > This function will return True if the input is a string and
return False
 > if not
 >
 > Any of you have idea about that? Thanks in advance
 >
 >
 >


 >
 > ___
 > Haskell-Cafe mailing list
 > Haskell-Cafe@haskell.org <mailto: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] Newbie question on Haskell type

2005-10-13 Thread robert dockins

In GHC you can do this:

> import Data.Typeable

> isString :: (Typeable a) => a -> Bool
> isString x = typeOf x == typeOf (undefined::String)

Why do you want this?  It's not the kind of operation one does very 
often in Haskell.



Huong Nguyen wrote:


Hi all,
 
I want to write a small functionto test whether an input is a String or 
not. For example,
 
isString::(Show a) =>a ->Bool
This function will return True if the input is a string and return False 
if not
 
Any of you have idea about that? Thanks in advance





___
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] Typing problems with basic arithmetic - help!

2005-09-23 Thread robert dockins
For the version with type signatures, you are trying to divide integers 
using the (/) function.  This function expects values in the class 
Fractional, and Integer isn't a member.  Replace with div, which does 
integer division.


pnorep days n = (numeratorex days n) `div` (denominatorex days n)


Marcin Tustin wrote:

I'm trying to do some basic arithmetic code (in fact it calculates the 
probability of a birthday clash given year length and group size), and GHC and 
Hugs are both not liking the code:

[EMAIL PROTECTED] ~]$ ghci burthday.hs
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 6.4, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base-1.0 ... linking ... done.
Compiling Main ( burthday.hs, interpreted )

burthday.hs:14:37:
No instance for (Fractional Integer)
  arising from use of `/' at burthday.hs:14:37
Probable fix: add an instance declaration for (Fractional Integer)
In the definition of `pnorep':
pnorep days n = (numeratorex days n) / (denominatorex days n)
Failed, modules loaded: none.
Prelude> :reload
Compiling Main ( burthday.hs, interpreted )
Ok, modules loaded: Main.
*Main> pnorep 365 30

:1:0:
Ambiguous type variable `a' in the constraints:
  `Fractional a' arising from use of `pnorep' at :1:0-5
  `Integral a' arising from use of `pnorep' at :1:0-5
Probable fix: add a type signature that fixes these type variable(s)
*Main> 


The first time is with the type annotations, the second without:

import Ratio
import Numeric

numeratorex days n = (numdays days n) - (subtractex days n) -- :: Rational 
numdays days n = days * n

--numdays :: Integer -> Integer -> Integer
subtractex days n = (days * (days - 1)) / 2 --:: Rational
denominatorex days n = (days^n) 
-- denominatorex :: Integer -> Integer -> Integer

pnorep days n = (numeratorex days n) / (denominatorex days n)

Help!

Thanks!
___
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] Growing Trees

2005-09-22 Thread robert dockins
It sounds like you are porting an algorithm which does destructive 
updates on this tree.  If so, you can use the ST (or IO) monad and use 
STRef (IORef).


data Tree a
  = TreeRoot { stuff:: STRef a
 , children :: STRef [Tree]
 }
 .

you would get at the data like so:

doStuff node = do
s <- readSTRef (sutff node)
children <- readSTRef (children node)
.
writeSTRef (children node) newChildren



This is probably the most direct translation from a destructive update 
setting.


As you said, having the upward pointers causes the entire tree to be 
recomputed when you make a change.  If you want to move to a pure data 
structure with good sharing properties you will need to remove the 
upward pointers, at which point you have a pretty basic rose tree.  (I 
suppose you could remove the downward pointers instead, but you'd have a 
very strange kind of tree; really, it would be a collection of lists 
with a common tail element).


You might consider:

http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data.Tree.html


Without knowing what you are doing with this tree its hard to be more 
specific.



Tom Hawkins wrote:

I'm porting an ML program to Haskell, but am having difficulty with 
particular data structure: a tree where each node has references to the 
children as well as the parent...


data Tree a
  = TreeRoot { stuff:: a
 , children :: [Tree]
 }
  | TreeNode { stuff:: a
 , parent   :: Tree
 , children :: [Tree]
 }

But because of these bidirectional links, every time I add a node I must 
reconstructing the entire tree.  There is also the add coding complexity 
of threading the tree through various functions to simulate state.


What are my [monadic] options?

-Tom
___
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] Trapped by the Monads

2005-09-20 Thread robert dockins


Mark Carter wrote:
I'm puzzling out how to get a Bool from am IO Bool. I know I'm not 
supposed to, but I don't see any way around my predicament.


The basic setup is: I have an edit box, and a panel. If you click the 
LMB on the panel when the edit box is checked, this means you want to 
move a graphical object around the panel. If it is unchecked, then 
clicking the LMB means you want to add a graphical object.


The relevant bits I've managed to put together so far are:

mainFrame = do -- main application frame
   streams <- varCreate []
  ...
   cbEdit <- checkBox p1 [text := "Edit Mode",  on command ::=  onCbEdit 
textlog] -- p1 is the panel, ignore textlog

   let isEditing =  get cbEdit checked -- returns type IO Bool
   windowOnMouse p False {- no motion events -} (onMouse p streams  
isEditing)

  ...
 where
   onMouse w streams isEditChecked mouse  = case mouse of
   MouseLeftDown pt mods  ->
   if isEditChecked then
   findStream w streams pt
   else
   addStream w streams pt
   other  -> skipCurrentEvent  -- 
unprocessed event: send up the window chain


   where
-- define findStream and addStream

The problem is that isEditChecked is of type IO Bool, not Bool. I 
presume that I should actually be taking a different (non-imperative) 
approach, and I'm wondering if anyone could suggest what that approach 
should be? Many apologies for being a clueless n00b.


Well, your onMouse function is acutally in the IO monad, so you can just 
use the do notation.  You can also get rid of the case, like so:


 onMouse w streams isEditChecked (MouseLeftDown pt mods) =
  do ec <- isEditChecked
 if ec then ... else ...

 onMouse _ _ _ _ = skipCurrentEvent

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


Re: [Haskell-cafe] Eq Type Class: Overloading (==)

2005-09-18 Thread Robert Dockins
On Sunday 18 September 2005 07:59 am, Tom Hawkins wrote:
> Aaron Denney wrote:
> > On 2005-09-17, Jason Dagit <[EMAIL PROTECTED]> wrote:
> >>A link to supertyping can be found here:
> >>http://repetae.net/john/recent/out/supertyping.html
> >>
> >>After reading that, I wonder why it's not implemented.
> >
> > Not enough people calling for it.
> >
> >>It seems like a wonderfully useful idea.
> >
> > It is.  It would be terribly useful for those trying to prototype a
> > new Prelude, and clean up the mathematical structures.
>
> I like the idea of supertyping, but wouldn't that only allow you to
> alter identifiers that were already classified?  What about functions in
> the Prelude that don't belong to a type class?
>
> For instance, I have a datatype that needs an append-like operation, yet
> it appears (++) is reserved only for lists.
>
> I recently switched to Haskell from OCaml because I thought type classes
> may solve one of my problems.  I'm building an embedded language, which
> has a lot of the basic operations.  In OCaml I was forced to invent all
> sort of obscure operator names for the embedded language so as not to
> collide with the standard library.
>
> But with Haskell's Num class, I have been able to reuse (+), (-), and
> (*).  However, (==) and (++) are still sticking points.  My general
> impression of Haskell is good, though it seems you're somewhat locked-in
> by how the upper levels of the class hierarchy are defined in the
> Prelude, or when the Prelude does not type class generic operator names
> such as (++).
>
> Again, I just stared programming Haskell.  Please let me know if I'm
> missing something.

One possible solution for DSLs is to import the Prelude qualified, or with a 
hiding clause.  That allows you to redefine most of the symbols in the 
Prelude, but still use the Prelude ones if needed.  (==) is still a little 
special because the Prelude (==) is used for some desugaring steps.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Updating the Haskell Standard

2005-07-25 Thread robert dockins


John Goerzen wrote:

There was a brief discussion on #haskell today about the Haskell
standard.  I'd like to get opinions from more people, and ask if there
is any effort being done in this direction presently.

I think an updated standard is overdue.  I find it difficult anymore to
write any but the most trivial of programs using pure Haskell 98.


[snip]

This is perhaps a minor point, but if a serious new standardization 
effort were to emerge, I would like to see the formal semantics of 
Haskell firmed up a little.  The Haskell 98 report does a pretty good 
job, but it fails to specify an explicit abstract term language for the 
Haskell kernel, and doesn't (in my opinion) do a satisfactory job of 
supplying formal semantics for the IO monad (this one's tough; perhaps 
via a transform to the pi-calculus?).  It obviously doesn't even touch 
the semantics of extensions like implicit parameters, multi-parameter 
typeclasses (straightforward, but...), existential types or the STM monad.


A serious effort in this area might allow practical interoperability 
between pluggable Haskell frontends (parsing, typechecking, desugaring, 
template expansion) and backends (optimization, code gen, linking) which 
interface via something that looks a lot like external core, as well as 
making Haskell more amenable to formal verification.


Robert Dockins

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


Re: [Haskell-cafe] How to variables

2005-07-19 Thread robert dockins

Some people may suggest that you to create top-level IORefs using
unsafePerformIO, but I don't recommend that for this situation.



Well I can't imagine which particular people you have in mind :-)

But, as a vocal advocate of sound support for top level mutable
state, I would just like to go on record as saying I certainly
would not advocate it for this problem.

But then again, I wouldn't advocate the use of explicit "entire
program state" record passing either :-)


Fair enough.  The main reason I suggested it is a fairly painless way to 
emulate global variables within a main control loop, which was the OPs 
stated goal.  ("it's important to implement it in as most imperative 
form as possible...")


I would personally attempt to adopt a more functional way of approaching 
the problem (Arrows and whatnot), but those are still pretty murky waters.


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


Re: [Haskell-cafe] How to variables

2005-07-18 Thread robert dockins

I'm doing a 3D simulation. Now I need something like variables in
imperative languages. My mainLoop check for new events and renders
scene.



Then you want IORef.
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data.IORef.html



Consider, however, that this kind of construct can be done without
mutable variables. (warning, made-up code ahead)


main = loop 0 0 0 -- initial values
where loop loop_num xpos ypos =
   do e <- pollEvent
  let xpos' = 
  ypos' = 
  someActionInvolvingPosition xpos' ypos'
  when breakCondition (return ())
  loop (loop_num+1) xpos' ypos'




I saw it. The problem is, I need an amount of 100*X of mutable variables
to implement the system (camera position, rotation, aceleration, ...,
position and deformetion infomations for every object, ..., renderer
situations [like temprary fading and other efects], ... and more)


Then you probably want a big labeled record,

data ProgramState =
  ProgramState { var1 :: IORef Int
   , var2 :: IORef Int
   , var3 :: IORef Int
   , objects :: IORef [Object]
   , etc }

with a big nasty init function that calls newIORef a bunch of times with 
the initial values.  Then you just pass around your ProgramState value.


initProgramState :: IO ProgramState
initProgramState =
do ref1 <- newIORef 0
   ref2 <- newIORef 12345
   ref3 <- newIORef 
   .
   return ProgramState { var1 = ref1, var2 =  ref2, var3 =  ref3, ... }

main = ps <- initProgramState
   mainLoop ps

This has the nice property that you can add new fields to your record 
without having to change the signature of dozens of functions.


Of course, you can alternately just create a big labeled record of pure 
values, and stick the whole thing in an IORef, or use recursive argument 
passing trick and skip the IORefs altogether.  I'm not sure I'm 
competent to give a breakdown of the advantages and disadvantages of 
each method, although I am personally inclined toward avoiding IORefs.


Some people may suggest that you to create top-level IORefs using 
unsafePerformIO, but I don't recommend that for this situation.


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


Re: [Haskell-cafe] How to variables

2005-07-18 Thread robert dockins



yin wrote:

Hello all!

I'm doing a 3D simulation. Now I need something like variables in
imperative languages. My mainLoop check for new events and renders
scene. To use input for controling camera position I need variables. An
equivalent code in C:

  void main_loop() {
int loop_num = 0;
bool run = 1;
SDLEvent e;

while(run) {
  while(SDL_PollEvent(&e)) {
  if(e.type == SDL_KeyDown) {
   if(... == SDLK_Left)
camera_pos_x--;
  } else if ...
  ...
  }

 drawScene();

  loop_num++;

}
  }

How to implement camera_pos_x, y and z as variables, which chage values
in run? This is only simplified example, but it's important to implement
it in as most imperative form as possible.


Then you want IORef. 
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data.IORef.html



Consider, however, that this kind of construct can be done without 
mutable variables. (warning, made-up code ahead)



main = loop 0 0 0 -- initial values
 where loop loop_num xpos ypos =
do e <- pollEvent
   let xpos' = 
   ypos' = 
   someActionInvolvingPosition xpos' ypos'
   when breakCondition (return ())
   loop (loop_num+1) xpos' ypos'


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


Re: [Haskell-cafe] How to variables

2005-07-18 Thread robert dockins

I'm doing a 3D simulation. Now I need something like variables in
imperative languages. My mainLoop check for new events and renders
scene.


Then you want IORef.
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data.IORef.html



I saw it. The problem is, I need an amount of 100*X of mutable variables
to implement the system (camera position, rotation, aceleration, ...,
position and deformetion infomations for every object, ..., renderer
situations [like temprary fading and other efects], ... and more)


Then you probably want a big labeled record, 



Uhm... and what if I write some runtines in plain C, then bind them to
Haskell and and use then as in OOP:

[snip]


Is this apoarch safe enougth, what do you think?


If you do it carefully.  But why?  It sounds like you are planning to 
write a transliteration of the code you would write in C, without 
leveraging the advantages of Haskell.  Which brings us to the critical 
question; what properties of Haskell cause you to want to develop your 
program using it?  The answer to that question should direct your design 
choices.


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


Re: [Haskell-cafe] How to variables

2005-07-18 Thread robert dockins



Uhm... and what if I write some runtines in plain C, then bind them to
Haskell and and use then as in OOP:


[snip]



Is this apoarch safe enougth, what do you think?



If you do it carefully.  But why?  It sounds like you are planning to
write a transliteration of the code you would write in C, without
leveraging the advantages of Haskell.  Which brings us to the critical
question; what properties of Haskell cause you to want to develop your
program using it?  The answer to that question should direct your
design choices.



A 3D engine aproach is a bit problematic (I can't describe it correctly
in English... I'm a slovak...). Behind polygons, textures, HUD GUI and
efects are mathematic functions, methods to solve problems, physics,
data representations, heuristic algoritms, "unkown time living meta
data", skripting language and sometimes expert systems, like simplified
neuron networks. Behind these is memory handling, loops, heavy algorithm
optimaliations and bugs.



I need to write functions fast and efective. Math, heuristic, metadata
and expert systems are better in haskell. If I could use haskel from C,
I would do it. The problem are optimalizations, which are a critical
change in algorithm. Other (and me too) won't understand my concepts.
The speed and usability of Haskell is a good argument to use and learn it.


I can buy that.

Well, one can actually call into Haskell from C.  It is less commonly 
done, but very possible.  Skim through the FFI addendum; you can export 
static functions (foreign export) or arbitrary thunks (with the 
confusingly named foreign import "wrapper").  If you are real 
adventurous, you can tie directly into the GHC API from the C side as 
well (although I'm not sure I can seriously recommend this method).


Having said that, if you feel that Haskell has sufficient advantages to 
warrant its use, I don't think you lose much by writing your main loops 
etc. in Haskell as well, and I would recommend you go with the labeled 
record technique to contain your program state.



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


Re: [Haskell-cafe] Can't explain this error

2005-07-11 Thread robert dockins



Thanks for your reply,
i just simply removed the first line and it works, but i dont understand 
why 1/x is not Float.


It depends on the type of 'x'.  If 'x' is a Float, (1/x) will be a 
Float.   If 'x' is a Double, (1/x) will be a Double.  If 'x' is an 
Integer (1/x) will not typecheck because (/) is only defined for 
Fractional arguments, and Integer is not an element of Fractional.  In 
your case, you had constrained 'x' to be an Integer, so it requires a 
cast to perform the division and get a Float.


Removing the type signature allows the compiler to assign a more general 
type to 'x', and so it typechecks.


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


Re: [Haskell-cafe] Can't explain this error

2005-07-11 Thread robert dockins
You are trying to divide by an Integer and get a Float.  Haskell doesn't 
do automatic numeric conversion, so you have to do the casts manually.


Prelude> let sumHam n = sum [ 1 / (fromIntegral x) | x <- [1..n] ]
Prelude> sumHam 5
2.283


Dinh Tien Tuan Anh wrote:


 could anyone tell me what i did wrong with this please

sumHam :: Integer -> Float
sumHam n = sum [1/x | x<-[1..n]]

Error: type error in explicitly typed binding
 Term: sumHam
 Type:  Integer -> Integer
 Does not match : Integer -> Float




it only works if i remove the first line. Tried changing Float by Double 
and still not working


Pls help
Cheers

_
Be the first to hear what's new at MSN - sign up to our free 
newsletters! http://www.msn.co.uk/newsletters


___
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: ANNOUNCE: GHC survey results

2005-06-28 Thread robert dockins

you are completely skipped the point that these is just for C++
programmers wanting to program in Haskell and aimed to give them
faster learning path and easy to use instruments



Not to forget to make learning easier for programmers of Perl, Ruby,
Python, Rexx, Tcl, APL, C#, Java, Bash, Fortran, Pascal and so on by
adding their most beloved features from their currently most beloved
language ...


Please insert  or  tags when making statements 
like this so we can know if you are joking or not ;)



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


Re: [Haskell-cafe] Compiling an extremely large Haskell file (in GHC)

2005-06-27 Thread robert dockins


Arjun Guha wrote:

I have an extremely large source file of about 11 MB.  It's the all-pairs 
shortest paths data for a map of the Hyde Park area of Chicago (no real 
reason, really).  I generated information in Scheme and printed the result to 
a Haskell source file as a list.  I then edited the file to initialized an 
array with the data.


GHC, with a 200MB stack, took up 1 hour and 1.3 GB of memory before getting 
killed by the system.  How would I compile something of this size?  I need to 
have the array of all-pairs shortest paths pre-computed.  Any suggestions?


Don't do that. ;)

Seriously though, you would probably have better luck parsing a data 
file at runtime rather than trying to compile it in.  It might even be 
that the "read" implementation for lists will be sufficent for what you 
want.


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


Re: [Haskell-cafe] Why distinct tyvars in instance declarations?

2005-06-27 Thread robert dockins

but GHC complains:


   Illegal instance declaration for `Foo (Either b b)'
   (The instance type must be of form (T a b c)
where T is not a synonym, and a,b,c are distinct type variables)
   In the instance declaration for `Foo (Either b b)'



unless I'm totally mistaken, your problem isn't the distinction thingy, but 
rather an error like supplying an Int for where you need (Int -> Int -> Int). 
That is, you're trying make (Either String String) an instance of Foo, 
(Either String String) already being a fully constructed type; Foo, on the 
other hand, seems to require a type constructor that is yet to parameterize 
over three more types (e.g. StateT).


I think that you are mistaken.  The OP listed:

> class Foo a
> instance Foo (Either b b)

Without further information, Haskell compilers will assume that the 
type(s) in a class declaration has/have kind * (Report section 4.6). 
Either b b does have kind *, so that's not the problem.


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


Re: [Haskell-cafe] Annotating calculations

2005-06-15 Thread robert dockins

Here is an idea I slammed out.  Maybe it will help you.

The basic idea is to create two types -- one which supports annotations 
and one which ignores them.  Only write your calculations once, with 
annotations.  Uses typeclasses to ignore the annotations when you don't 
want them.


Rene de Visser wrote:


Hello,

I have a somewhat complicated calculation programmed in Haskell.
This calculation is coded without using monads.

I want to also produce a report describing the details of this 
calculation for each particular set of inputs.
e.g. Number of hours worked = 100. Gross pay per hour = 50. Total gross 
= 100 * 50 = 500.

etc.
But about 20 times more complicated than the above.

Naturally I need to write functions to produce the above 
description/report as it should be well presented. Only showing the 
important parts of the calculation in a sensible order.


But I am wondering how to combine the generation of the report with the 
calculation together.


I think if I add the report generating functions into the calculation 
functions, it will make them twice as messy, and they are already 
complicated enough.


On the other hand replicating the calculation source code twice, once 
without reporting and once without seems bad.


Any suggestions on how to handle this?

Rene.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
> {-# OPTIONS -fglasgow-exts #-}
>
> data Annotation a
>   = TotalGrossCalc a a a
>   | SumCalculation [a] a
>   | SomeCalculation a
>   | AbsCalc a
>   | SignumCalc a
>  deriving Show
 
 add a different Show instance here for meaningful reporting
 
> class (Show a,Num a,Num x) => Annotatable a x | a -> x where
> mkAnnotatible :: x -> a
> annotate :: a -> Annotation a -> a
>
> newtype Num a => JustCalc a = JustCalc a deriving (Eq,Num)
> data AnnotateCalc a = AnnotateCalc a [Annotation (AnnotateCalc a)]

ignore annotations for JustCalc

> instance Num a => Annotatable (JustCalc a) a where 
>mkAnnotatible x = JustCalc x
>annotate x _ = x

keep hold of them for AnnotateCalc

> instance Num a => Annotatable (AnnotateCalc a) a where
> mkAnnotatible x = AnnotateCalc x []
> annotate (AnnotateCalc x messages) msg = AnnotateCalc x (msg:messages)

some boilerplate...

> instance Eq a => Eq (AnnotateCalc a) where
>   (AnnotateCalc x _ ) == (AnnotateCalc y _ ) = x == y
>
> instance Num a => Num (AnnotateCalc a) where
> (AnnotateCalc x x_msg) + (AnnotateCalc y y_msg) =
>   AnnotateCalc (x+y) (x_msg++y_msg)
> (AnnotateCalc x x_msg) * (AnnotateCalc y y_msg) =
>   AnnotateCalc (x*y) (x_msg++y_msg)
> fromInteger x = (AnnotateCalc (fromInteger x) []) 
> abs z@(AnnotateCalc x x_msg) = 
>   AnnotateCalc (abs x) ((AbsCalc z):x_msg)
> signum z@(AnnotateCalc x x_msg) =
>   AnnotateCalc (signum x) ((SignumCalc z):x_msg)

> instance Show a => Show (AnnotateCalc a) where
>  show (AnnotateCalc x _ ) = show x
>
> instance (Show a,Num a) => Show (JustCalc a) where
>  show (JustCalc x) = show x

now some calculations

> sumOfHours :: Annotatable a x => [a] -> a
> sumOfHours xs = annotate result (SumCalculation xs result)
>where result = sum xs

> grossTotal :: Annotatable a x => a -> a -> a
> grossTotal hoursWorked payRate = annotate result (TotalGrossCalc hoursWorked 
> payRate result)
>   where result = hoursWorked * payRate

> someCalculation :: Annotatable a x => [a] -> a -> a
> someCalculation hrs rate = annotate result (SomeCalculation result)
>   where result = grossTotal (sumOfHours hrs) rate
>
> printAnnotations (AnnotateCalc _ annotations) = sequence $ map (putStrLn . 
> show) (reverse annotations)
>
> sample :: Annotatable a x => a
> sample = someCalculation (map mkAnnotatible [12,34,23,31]) (mkAnnotatible 50)
>
> main = do let sample1 = sample :: JustCalc Integer
>   sample2 = sample :: AnnotateCalc Integer
>   putStrLn $ show sample1
>   putStrLn $ show sample2
>   printAnnotations sample2
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trivial question... solve_qe

2005-06-15 Thread robert dockins


> So, in a word: I need a tutorial for dummies

I don't know of any tutorials like you have described.  Perhaps someone 
else does?



Now, my current problem is: my program for solving quadratic equation
won't compile...


You left out some 'Just' constructors.




import System

solve_qe :: Maybe (Double, Double, Double) -> Maybe (Double, Double)
solve_qe Nothing = Nothing
--solve_qe (a, b, c)
solve_qe (Just (a, b, c))
| d >= 0 = Just ((-b + (sqrt d)) / (2 * a), (-b - (sqrt d)) / (2 * a))
| otherwise = Nothing
where d = b^2 - 4*a*c

evalArgs :: [String] -> Maybe (Double, Double, Double)
--evalArgs (a:b:c:[]) = (read a, read b, read c)
evalArgs (a:b:c:[]) = Just (read a, read b, read c)
evalArgs _ = Nothing

main = do
args <- getArgs
print (solve_qe (evalArgs args))

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


Re: [Haskell-cafe] Generic types

2005-06-13 Thread robert dockins


I'm writing a small unit library to excercise my barely existing 
Haskell skills.
However I can't figure out how to make Haskell accept any type 
of a specific class.


[snip]

What you want is a technique called "existential types".  The wiki page 
is here: http://haskell.org/hawiki/ExistentialTypes


The problem with existentials is that they are pretty picky about how 
you use them; I'm pretty sure you can't create a labeled record 
containing existentials (because the accessor functions aren't allowed 
to exist).  You have to pattern match to get at the encapsulated value.
Also, once you have done the pattern match on the "UnitValue," you can 
only use polymorphic functions on the pattern variables.


The following does what I think you want.


{-# OPTIONS -fglasgow-exts  #-}

class Unit u where
shortName :: u -> String

data Meter = Meter

instance Unit Meter where
shortName u = "m"

data UnitValue = forall u n. (Unit u,Num n) => UnitValue u n

main = let x = UnitValue Meter 10
   in case x of
UnitValue unit magnitude -> putStrLn $ (show 
magnitude)++(shortName unit)



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


Re: [Haskell-cafe] A reference manual for the Haskell monad > functions

2005-06-09 Thread robert dockins


Frank-Andre Riess wrote:
>>L.S.,
>>
>>I have written a reference manual for the most common Haskell monad
>>functions, in the
>>style of "A Tour of the Haskell Prelude". It can be found at:
>>http://members.chello.nl/hjgtuyl/tourdemonad.html
>>
>>
>>Known bug:
>>Not all keywords in the "See also" sections, that could be links, are
>>links.
> 
> 
> Nice :)
> 
> Reading over it once, I noticed that you confused the types of (>>) and (>>=).
> Didn't see any other mistake, though.

I'd just like to note that this tutorial includes a statement of the
MonadPlus laws, which are subject to some disagreement.  In particular
the 'mzero is a right zero for (>>=)' law is much disputed, and is
included in this tutorial as a law.  This wiki page summarizes the
current state of (dis)agreement:

http://haskell.org/hawiki/MonadPlus




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


Re: [Haskell-cafe] About ($)

2005-06-02 Thread robert dockins

Hello there,

name's Frank-Andre Riess. Nice to meet you m(_ _)m


Welcome.


So, well, my first question on this list is admittedly somewhat simple, but I
managed to delay it long enough and now I think I should ask about it: Does
($) have any relevance at all except for being a somewhat handier version of
parentheses?


That's mostly how it is used (although some will say that it is a 
terrible idea), but one can also do some pretty neat tricks with it as a 
higher-order function.  Eg,


zipWith ($)

Is a function which takes a list of functions and a list of arguments 
and applies the functions pairwise with the arguments.  In addition, 
because of the way the zip* functions work, you can create an infinite 
cycle of functions to apply to some arguments as in:


zipWith ($) (cycle [sin,cos]) [1..5]

which is equivalent to:

[sin 1,cos 2,sin 3,cos 4,sin 5]


I'm sure there are other more esoteric things, but this is about as 
complex as I try to go to avoid severe headaches :)


Robert Dockins

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


Re: [Haskell-cafe] Question about classes from a Haskell newbie.

2005-05-24 Thread robert dockins



 However, I didn't understand the syntax of the class declaration.

Lemmih wrote:
 > import Complex
 >
 > class ConvertibleToComplex a b | a -> b where
 >toComplex :: RealFloat b => a -> Complex b

I've looked at several sources to try to understand this declaration.  I 
can't find any examples where a class declaration takes two type 
variables or uses the pipe symbol.  One of the sources I used was 
_Haskell 98 Language and Libraries The Revised Report_.  I'm not an 
expert at BNF notation, but the definitions for topdecl, tycls, and 
tyvar in the grammar seems to exclude Lemmih's declaration.


If someone could point me to some sources that explain this notation, 
I'd be very grateful.


This is a multi-parameter typeclass (with functional dependencies), 
which is not a part of Haskell 98, so its no surprise that you didn't 
find it in the Report.  The Muli-parameter part is pretty easy to 
understand: the type class simply introduces more than one type 
variable.  Functional dependencies let you say which types should 
determine which other types.  Here are some pages on these ideas:


http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html#multi-param-type-classes
http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html#functional-dependencies
http://haskell.org/hawiki/FunDeps

In this particular instance, what the class definition means is that 
'ConvertaibleToComplex' is a class which relates two types 'a' and 'b' 
AND the type 'a' uniquely determines the type 'b'.



Hope that helps,
Robert Dockins

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


Re: [Haskell-cafe] APIs

2005-05-24 Thread robert dockins



> One of the best bad example is the use of boolean as arguments.

Oh, yes.  That's a pet peeve of mine.  About 99% of boolean arguments
should be meaningful two-valued enumerated types.  It's literally a
one-liner to create such an enumerated type, so there's no excuse.



The documentation effect and type safety provided by two-valued 
enumerated types is indeed much greater. But one needs a conversion from 
Bool to the enumeration if one wants to pass the result of a logic 
operation to the function. What about records with named fields, 
especially if more options are needed?


data CreateDirectoryOptions = Cons {createParents :: Bool}

createDirectory (Cons {createParents = True}) "dir"


Hu I think I like this.  Something like the following allows a 
simple way to make the call site concise and provide defaults at the 
same time.  Additional plus -- adding options requires no call-site code 
changes.



---

import Control.Monad

-- provide "opts" which should be a labeled record
-- of default options
class FunctionOptions a where opts :: a

-- alias for readability when you don't want to change
-- the default options
defaults = opts

-- create a datatype for each function which needs some flags
data CreateDirectoryOptions
   = CreateDirectoryOptions
{ createParents :: Bool
, barFlag :: Bool
, andNow :: Bool
, aWholeBunch :: Bool
, ofOther :: Bool
, seldomEverUsed :: Bool
, esotericOptions :: Bool
}

-- set the flag defaults
instance FunctionOptions CreateDirectoryOptions
  where opts =
  CreateDirectoryOptions
  { createParents = False
  , barFlag = True
  , andNow = True
  , aWholeBunch = True
  , ofOther = False
  , seldomEverUsed = True
  , esotericOptions = False
  }

createDirectory :: CreateDirectoryOptions -> FilePath -> IO ()
createDirectory o path =
do when (createParents o) (putStrLn "creating parents")
   when (barFlag o) (putStrLn "bar flag true")
   putStrLn ("creating "++path)
   return ()

-- readable AND typesafe :-)
main = do createDirectory opts{ createParents = True } "foo"
  createDirectory defaults "baz"

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


Re: [Haskell-cafe] Bit fiddling

2005-05-17 Thread robert dockins
If you want C compatibility, you need
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data.Array.Storable.html
which is similar.  You then use the "withStorableArray" to call out to 
your C functions.

Florian Weimer wrote:
* robert dockins:

Probably you have seen this already, but I thought I'd mention it on the 
off-chance you missed it:

http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data.Bits.html
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data.Word.html
Probably you'll want to think about an IOUArray of Word8, or something 
similar.

IOUArray looks indeed interesting, thanks.  How can I pass such
objects (in particular of type IOUArray Int Word8) to a C routine,
preferably as a void */size_t combination?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Bit fiddling

2005-05-17 Thread robert dockins
Probably you have seen this already, but I thought I'd mention it on the 
off-chance you missed it:

http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data.Bits.html
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data.Word.html
Probably you'll want to think about an IOUArray of Word8, or something 
similar.

Its unclear to me exactly what you mean by "bit fiddling", but perhaps 
this addresses your question.

Florian Weimer wrote:
I'm toying a bit with Haskell and wondering what's the best way to
implement bit fiddling.  Most of my applications involve serializing
and deserializing small blobs (IP packets, for instance), and after
browsing the GHC library documentation, I'm not sure which appraoch I
should use.  That's why I'd appreciate pointers to sample code.
Portability beyond GHC is not required.  It's not necessary to update
blobs, only to parse them, and serialize new ones.  And in the
beginning, I'd like to write the boilerplate manually. 8-)
___
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] supplying some of the arguments to a function

2005-05-06 Thread robert dockins
Mark Goldman wrote:
> if I had a function f that took x y and z in that order, is there some
> way that I can supply y and z and get back a function that takes x?
> This question comes about after talking with a prof about currying and
> wether it buys you anything.
>
> -mdg
let f = (\x y z -> ()) :: Bool -> Char -> Int -> ()
:t (\x -> f x 'a' 0)
 (\x -> f x 'a' 0) :: Bool -> ()
If you don't like lambdas you can do the same thing with combinators 
(eg, flip, (.), const, etc)

:t (flip . flip f) 'a' 0
 (flip . flip f) 'a' 0 :: Bool -> ()
Mostly, one should just try to write functions so that they take their 
parameters in the most convenient order for partial application.

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


Re: [Haskell-cafe] Re: Haskell vs OCaml

2005-05-04 Thread robert dockins

That leaves one aspect of Haskell vs Ocaml I don't yet understand.
What are the advantages of lazy evaluation?
I'd recommend this paper (once again):
http://www.md.chalmers.se/~rjmh/Papers/whyfp.html
One of the main points of the paper is that lazy evaluation enables a 
new way of modularizing code.

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


Re: [Haskell-cafe] How to join two lists of lists?

2005-05-03 Thread robert dockins
> Hi all!
> I'm trying to join to lists of lists. The problem is, i would like to
> get a new list of lists of tuples and not list of tuples of lists (that
> what zip makes).
>
> list1 = [[1,2],[3,4],[5,6]]
> list2 = [[a,b],[c,d],[e,f]]
>
> desiredlist = [[(1,a),(2,b)],[(3,c),(4,d)],[(5,e),(6,f)]]
Prelude> let list1 = [[1,2],[3,4],[5,6]]
Prelude> let list2 = [['a','b'],['c','d'],['e','f']]
Prelude> zipWith (zip) list1 list2
[[(1,'a'),(2,'b')],[(3,'c'),(4,'d')],[(5,'e'),(6,'f')]]
Why do you want to do this?

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


Re: [Haskell-cafe] Where do you use Haskell?

2005-05-03 Thread robert dockins
Hi all,
Again, I'm the new guy slowly learning this "fuctional programming" 
thing. :-)
[snip]
So, I'm tempted to conclude that FP is only applicable to situations 
where user interaction is a small part of the program. For example, for 
simulations.

Now, I'm sure I'm not the first person to have this train of thought. 
And I'm sure there is a good answer why I'm wrong. :-) I'm eager to hear 
what that might be.
You might want to check this out:
http://www.md.chalmers.se/~rjmh/Papers/whyfp.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Clarification on proof section of HS: The Craft of FP

2005-05-02 Thread robert dockins
Well, yes, but I'd argue that ordinary (transfinite) mathematical
induction will work just fine here. It's just that the set we're doing
mathematical induction over is one larger (in the ordinal sense) than
usual. Let S = N union {w}, where N is the usual set of naturals and w
is an additional new element. Adopt the usual well-ordering <= on N,
and extend it to a new well-ordering by defining x <= w for every x.
Assign finite completely defined lists their usual lengths, and every
_|_ terminated or infinite list, length w.
So every infinite object has a special length denoted "w".  I assume we 
wish to make the following statements about "w"

w = w
~(w < w)
Without which "=" and "<" fail to have their intended meaning.
Suppose that if the statement P(x) holds for every x < y then it holds
for y as well. Then P(y) holds by mathematical induction.
Then this induction hypothesis cannot apply to infinite lists.  Suppose
xs is infinite.  Then we assign it length "w".  Now, (x:xs) is also 
infinite, and has length "w".  But, ~(w < w), so we cannot conclude that 
P(x:xs) given P(xs).

One simply cannot reason based on the "size" of an infinite object in 
this way.  You require a form of structural reasoning, and that means 
coinduction.

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


Re: [Haskell-cafe] Clarification on proof section of HS: The Craft of FP

2005-05-02 Thread robert dockins
Well, I also omited the word "countable". I figure it's understood
since computers only deal with finite data. And given an infinite
list, any finite "head" of it would meet the criteria, so the
distinction is moot. Unless Haskell has some neat property I am not
aware of :-)
Due to lazyness, we can have infinite lists (and other infinite structures) 
in
Haskell (of course, in finite time, only a finite portion of those can be
evaluated), e.g.
ns = [1 .. ] :: [Integer]
is an infinite list which is often used.
And now consider the property P that there exists a natural number n so that
the list l has length n.
Obviously P holds for all finite lists, but not for the infinite list ns.
This property clearly violates the assumption for mathematical
induction that if P(x) is true for all x < y, then P(y) is true.
The problem here is that the haskell [] type is not actually an 
inductive type, but a coinductive type (which means one can construct 
infinite objects of that type).  The proof tools available to work with 
coinductive types differ somewhat from the tools used on inductive 
types.  In "Craft of FP", the author works with scheme, which has eager 
evaluation and thus cannot construct objects with coinductive type: thus 
the usual, familiar induction principles just work.  Haskell has lazy 
evaluation which allows the construction and manipulation of 
coinductive-typed objects.

Short story: when working with finite objects, regular induction works. 
 When working with infinite objects, be careful and read up on coinduction.

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


Re: [Haskell-cafe] Ambiguous type signature in class declaration

2005-04-27 Thread robert dockins
See:
http://haskell.org/hawiki/FunDeps
 > class CRank a b where
 >   rank :: a -> b -> Maybe Integer -- Nothing means b is out of range 
or badly constructed
 >   unrank :: a -> Integer -> Maybe b -- Nothing means rank is out of 
range
 >   count :: a -> Maybe Integer -- Nothing means infinity

[snip]
but all i get is
ERROR "./Cafe.lhs":8 - Ambiguous type signature in class declaration
*** ambiguous type : CRank a b => a -> Maybe Integer
*** assigned to: count
Any suggestions anyone?

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


Re: [Haskell-cafe] Using catch and errors

2005-04-22 Thread robert dockins

Now I have one problem (Well 2 really but the second one is just me not
having programmed in haskell for so long that I forgot). getLine is used for
the sole purpous of stopping the program and allowing the user to read the
error message before the window closes but error does not allow me to do
that and aparently using a lambda function (As shown below) does not work
(It gives error upon compilation
 when ((length keyno /= 1) && (keyno /= "1") && (keyno /= "0")) (\_ ->
putStrLn "Please input either 0 or 1 as key number"
getLine
exitWith ExitSuccess)
So is there anyway to fix that?
You need a "do" not a lambda ( or use >> )
when (stuff) (do putStrLn "blah"
 getLine
 exitWith ExitSuccess)
or
when (stuff) (putStrLn "blah" >> getLine >> exitWith ExitSuccess)
The second error is that apparenlty (keyno /= "1") and (keyno /= "0") do not
work, but I suspect that, like Java, one can't compare strings using = sign
or am I wrong?
No, that should work.  Haskell equality is not at all like Java 
equality.  In java, '=' basicaly means pointer equality.  I am not aware 
of a way to even make that comparison in Haskell (in general).  Haskell 
'=' behaves a lot more like equals() in Java.

Remove the length test and I think your condition will do what you expect.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Using catch and errors

2005-04-22 Thread robert dockins

No, that should work.  Haskell equality is not at all like Java
equality.  In java, '=' basicaly means pointer equality.  I am not aware
of a way to even make that comparison in Haskell (in general).  Haskell
'=' behaves a lot more like equals() in Java.
Of course, you mean Haskell '==', as Haskell '=' is declared equality,
which is somewhat like '=' in mathematics.
D'oh!  Indeed.  I mean '==' for Java as well.  Java '=' is variable 
assignment.

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


Re: [Haskell-cafe] a newbie's question

2005-04-21 Thread robert dockins
Hi,
I'm beginning to study Haskell, For the following
a = [1,2,3]
b = "there"
do x <- a
  y <- b
 return (x , y)
Winhugs cannot run it. Gives
 Syntax error in input (unexpected backslash (
lambda))
Your problem is that you're using monads to grab the contents of a  and 
b, while a and b are not monadic... 
They *are* actually monadic, just perhaps not the monad the OP expects. 
 This code should compile and produce the cartesian product of the 
numbers {1, 2, 3} and the characters {t,h,e,r,e}.  I'm not sure what 
would cause the given error -- it may be a layout problem (the indention 
is wrong but it might just be the mailer).

   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 6.2.2, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.
Loading package base ... linking ... done.
Prelude> let a = [1,2,3]
Prelude> let b = "there"
Prelude> do { x <- a; y <- b; return (x,y) }
[(1,'t'),(1,'h'),(1,'e'),(1,'r'),(1,'e'),(2,'t'),(2,'h'),(2,'e'),(2,'r'),(2,'e')
,(3,'t'),(3,'h'),(3,'e'),(3,'r'),(3,'e')]
Prelude>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] interesting IO oriented code

2005-03-17 Thread robert dockins

2) It is performant (mostly).  At least it outperforms other Haskell IO 
methods I have tried.  My 'wc' is about twice as fast as the current 
shootout version in informal tests (the shootout code is included in the 
repo).  My md5 can sum somewhere between 2-4Mb/Sec on my hardware.

You know that http://www.bagley.org/~doug/shootout/ is frozen, don't you?
For a current version look at http://shootout.alioth.debian.org/
The current version is fast but ugly. There was some comitee work on
Haskell mailing lists to make it prettier, but it didn't make to the
shootout yet.
Thanks, I do have an old version; it wasn't on bagley.org, but I'm not 
sure exactly where I found it.  I'll compare against the newest version 
when I get home.

The reason I compared to the shootout program was to get a sense of how 
well the API I was developing stacked up against hand-optimized haskell. 
   So, even getting pretty close is a win as far as I'm concerned.

(... quick google ...) I just found Ian's md5 implementation.  I'll 
compare to that as well when I get a chance.

> BTW, do we care about such benchmarks? I am going to have some spare
> time and I could work on Haskell solutions a bit, but I'm not sure
> it's worth the hassle.
I think they are interesting as an indication of where haskell and GHC 
in particular are weak.  If the techniques developed for optimizing 
shootout scripts can drive better optimizations or new, better 
libraries, I think that's worthwhile.  OTOH, nobody asks if perl golf 
(for example) is worthwhile, they just do it for kicks (as far as I can 
tell).

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


[Haskell-cafe] interesting IO oriented code

2005-03-17 Thread robert dockins
I while back following the most recent discussion about filepaths and IO 
generally, I decided to pick up the torch and try my hand at a solution 
that delt with all the issues.  My conception of the problem can be 
found here:

http://www.haskell.org//pipermail/haskell-cafe/2005-January/008955.html
However, I quickly got sidetracked by the character encoding issue, and 
sequential IO operations generally.  I have come up with some code that 
I think is interesting, not least of which because it is somewhat 
performant.  In the spirit of 'release early, release often' I am now 
making it available.

I ended up developing a sequential IO API and a couple of test cases to 
drive it.  I currently have a simple word count and a md5 
implementation.  There is a darcs repo at:

http://www.eecs.tufts.edu/~rdocki01/filepath/
The code relies on multi-parameter typeclasses, fundeps and unboxed 
tuples, so its GHC only.

The good news:
1) The API is semi-manageable.  It is based around Producer, Transformer 
and Consumer functors (at least I think they can be called functors; I'm 
not real knowledgeable here).  I think that with a little more work (and 
the input of people more experienced at this stuff than I) it could be 
sugared into a pretty usable API.

2) It is performant (mostly).  At least it outperforms other Haskell IO 
methods I have tried.  My 'wc' is about twice as fast as the current 
shootout version in informal tests (the shootout code is included in the 
repo).  My md5 can sum somewhere between 2-4Mb/Sec on my hardware.

3) Very importantly, the code appears to have reliable constant-space 
behavior.

4) We are not artificially forced into the IO or ST monads for 
performance reasons.  Explicit state passing is used where necessary, 
which seems to have the added benefit of helping the compiler to find 
good optimizations (pure speculation).

The bad news:
1) Mostly performant is still not great.  My wc takes about 6 times as 
long as the C version on my machine, and md5 takes about about 80 times 
as long.  (interestingly, the C md5sum takes about 1/5 of the time as C 
wc!).  However, it is within an order of magnitude of a java 
implementation of md5 (using the standard digest classes).

2) The performance is pretty fragile.  Small changes can cause large 
performance hits for no easily discernible reason.  This probably 
relates to the way particular optimizations do or don't get applied. 
The situation is hugely complicated by the typeclass-heavy API, I am sure.

3) The stream-observer paradigm is a somewhat difficult programming 
environment.


My next step is to try some actual character encoding implementations 
(the original purpose after all) and see how that goes.  I'd also like 
to try gzip and gunzip transformer layers.

Any ideas for improvements (including patches!) are welcome.
Robert Dockins

PS the code currently includes a number of vestigial remnants of false 
starts, and is generally kind of ugly; you are warned.

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


Re: [Haskell-cafe] Parser problem continued

2005-03-15 Thread robert dockins

expr :: Parser Int
expr = do t <- term
  do symbol "+"
 e <- expr
 return e
  return (t + e)
   +++ return t<- 
't' is not in scope at the arrow.  t only exists inside the
do block, and your code parses like this
( do t <-  return (t+e) ) +++ ( return t )
perhaps like this:
expr = do t <- term
  (do symbol "+"
  e <- expr
  return (t+e)
  )
  +++
  (return t)
although I think you may also want a 'try' before the first alternative.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: File path programme

2005-01-31 Thread robert dockins

Well, there is a sort-of canonic version for every path; on
most Unix systems the function realpath(3) will find it.
Here is the BUGS listing from 'man realpath' on my system:
Never use this function. It is broken by design since it is impossible 
to determine a suitable size for the output  buffer. According  to 
POSIX  a  buffer  of size PATH_MAX suffices, but PATH_MAX need not be a 
defined constant, and may have to be obtained using pathconf().  And 
asking pathconf() does not really help, since on the one hand POSIX 
warns that  the  result of  pathconf()  may  be huge and unsuitable for 
mallocing memory. And on the other hand pathconf() may return -1 to 
signify that PATH_MAX is not bounded.

> My interpretation is that two paths are equivalent iff they
> point to the same target.
You might do better (on *nix) to check if two paths terminate in the 
same filesystem and then see if the inode numbers match (with some stat 
variant).  Even that may break down for networked filesystems or FAT 
wrappers or other things that may lie about the inode number.

You could also unravel the path manually, but that seems error-prone and 
unportable.

This strikes me as yet another case of a simple-seeming operation that 
simply cannot be implemented correctly on file names.

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


Re: [Haskell-cafe] Re: File path programme

2005-01-31 Thread robert dockins
I have been ruminating on the various responses my attempted file path 
implementation has generated.  I have a design beginning to form in the 
back of my head which attempts to address the file path problem as I lay 
out below. Before I develop it any further, are there any important 
considerations I am missing?

Here is my conception of the file name problem:
1) File names are abstract entities.  There are a number of ways one 
might concretely represent a filename. Among these ways are:

  a) A contiguous sequence of octets in memory
   (C style string on most modern hardware)
  b) A sequence of unicode codepoints
   (Haskell style string)
  c) Algebraic datatypes supporting path manipulations
   (yet to be developed)
2) We would like these three representations to be isomorphic. 
Unfortunately, this cannot be.  In particular, there are major issues 
with the translations between the (a) and (b) forms given above.  One 
could imagine that translations issues involving the (c) form are also 
possible.

3) Translations between (a) and (b) must be parameterized by a character 
encoding.  Translations to and from (c) will require some manner of 
description of the path syntax, which differs by OS.

4) In practice, the vast majority of file paths are portable between the 
various forms; the forms are "nearly" isomorphic, with corner cases 
being fairly rare.

5) Translations between the various forms cost compute cycles and 
memory, and are not necessarily bijective.  Therefore, translations 
should occur _only_ if absolutely necessary.  In particular, if a file 
name passes through a program as a black box (it is not examined or 
manipulated) it should undergo no transformation.

6) Different OSes handle file names differently.  These differences 
should be accounted for, transparently where possible.  These 
differences, however, should be exposed to developers for whom the 
difference matter.

7) Using simple file names should be easy.  We don't want developers to 
have to worry too much about character encodings, path separators, and 
generally bizarre path syntax just to open files.  The complexities of 
correct file name handling should be hidden from the casual programmer. 
However, developers interested in serious 
portability/internationalization should be able to get down into the 
muck if they need to.


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


Re: [Haskell-cafe] File path programme

2005-01-28 Thread robert dockins
I don't pretend to fully understand various unicode standard but it
seems to me that these problems are deeper than file path library. The
equation (decode . encode)
/= id seems confusing for me. Can you give me an example when this
happen? 
I am pretty sure that ISO 2022 encoded strings can have multiple ways to 
express the same unicode glyphs.  This means that any sensible relation 
between IS0 2022 strings and unicode strings maps more than one ISO 2022 
string onto the same unicode string.  The inverse is therefore not a 
function.  To make it a function one of the possibly several encodings 
of the unicode string will have to be chosen.  So you have a ISO 2022 
string A which is decoded to a unicode string U.  We reencode U to an 
ISO 2022 string B.  It may be that A /= B.  That is the problem.

The various UTF encodings do not have this particular problem; if a UTF 
string is valid, then it is a unique representation of a unicode string.
However, decoding is still a partial function and can fail.

A discussion about this problem floated around on this list several 
months ago.

> What can we do when the file name is passed as command line
> argument to program? We need to convert String to FilePath after all.
Then we can parse the unicode and hope that nothing bad happens; the 
majority of the time, we will be OK.  Or we can make the RTS allow 
access to the raw bytes of the program arguments, env variables, etc, 
and actually do the right thing.

___
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 robert dockins

Even simple manipulations break in the presence of encoding issues, or 
even just of unusual paths.  What is the extension of "\\.\TAPE0" ?  Its 
not "\TAPE0".  BTW this is a valid path on Windows 2000 upwards.  If you 
don't care about corner cases, then you have no worries.  It would be 
nice to have correct handling for all valid paths on each supported OS 
though.
Urk.  This is a terrible example, sorry.  Still, the point is that 
unusual paths can break simple seeming string manipulations.

___
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 robert dockins
 - Keep the existing System.IO API the same. openFile, createDirectory
... will take the file path as string.
The problem is that "string" means different things in haskell and in C.
A C "string" is really just a contiguous sequence of octets in memory. 
A haskell string has a particular interpretation, that of a list of 
unicode characters.  Depending on how strings come into and leave the 
haskell world, there may OR MAY NOT be a one-to-one mapping between C 
strings and haskell strings, if non-trivial character encodings are 
involved (they will be eventually).  Decoding may fail (no haskell 
representation for that string), or it might be that (deocde . encode) 
/= id, which is also bad (file name returned from a directory listing 
gives file not found error).  The sad truth is that FilePath = String is 
BROKEN.  FilePath = [Word8] would at least preserve filenames as they 
move across the boundaries of the haskell world, but then simple 
questions like "does this file have a .gz ending" become difficult 
(because they depend on the encoding).  We need something else.  Maybe 
ADTs aren't it, but String certainly isn't.  I don't think "mostly 
works, if you only use ASCII" is good enough for something as basic as 
file IO.

 In most cases we do only simple manipulations on path 
Even simple manipulations break in the presence of encoding issues, or 
even just of unusual paths.  What is the extension of "\\.\TAPE0" ?  Its 
not "\TAPE0".  BTW this is a valid path on Windows 2000 upwards.  If you 
don't care about corner cases, then you have no worries.  It would be 
nice to have correct handling for all valid paths on each supported OS 
though.

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


<    1   2   3   >