Re: [Haskell-cafe] How to give unique name/id to nodes outside any monad ?

2009-01-08 Thread Timothy Goddard
On Thu, 08 Jan 2009 21:28:27 minh thu wrote:
> Hi,
>
> I'd like to process some kind of graph data structure,
> say something like
>
> data DS = A [DS] | B DS DS | C.

Graphs in funtional languages aren't usually represented in this sort of 
manner. Trees are fine to represent like that as they're acyclic and have 
exactly one parent for each node but for graphs it's much more difficult. Say 
that you have a graph with directed connections like this:

0 -> 1
1 -> 2
2 -> 3
1 -> 3
3 -> 4

Now you want to alter node 4. Node 3 has to be updated to point to the new 
version of 4, node 1 has to be changed to point to the new version of 3, node 
2 has to be changed to point to the new version of node 3, then node 1 has to 
be changed again to point to the new version of 2, then finally 0 can be 
changed to point to the new version of 1 and returned.

There is no simple way using this representation to handle that double-update 
to node 1, or to handle disconnected or cyclic graphs. Updates are extremely 
difficult since Haskell data structures are not mutable and have no concept 
of identity. The approach of treating nodes as structures with pointers to 
each other cannot be cleanly and efficiently implemented in an immutable 
fashion. It only really makes sense in a stateful, imperative context.

An approach that suits functional languages better is to store a flat 
structure listing the edges leaving each node. This, I believe, is the 
approach taken by Haskell's main graph library, FGL 
(http://hackage.haskell.org/cgi-bin/hackage-scripts/package/fgl). You would 
now have something like:

data MyNode nv = MyNode {nodeId::Int, nodeValue::nv}

data MyEdge ev = MyEdge {edgeDestination::Int, edgeValue::ev}

data MyGraph nv ev = MyGraph {
maxNode :: Int,
nodes :: (Map Int nv),
edges :: (Map Int [MyEdge ev])}

emptyGraph :: MyGraph nv ev
emptyGraph = MyGraph 0 (Data.Map.empty) (Data.Map.empty)

getNode :: MyGraph nv ev -> Int -> Maybe (MyNode nv)
getNode g id = ((nodes g) `lookup` id) >>= (\v -> MyNode id v)

getEdgesLeaving :: MyGraph nv ev -> Int -> [MyEdge ev]
getEdgesLeaving g id = fromMaybe [] ((edges g) `lookup` id)

addNode :: nv -> MyGraph nv ev -> (Int, MyGraph nv ev)
addNode val g = (maxNode newGraph, newGraph)
where
newNodeId = (maxNode g) + 1
newGraph = MyGraph newNodeId (insert newNodeId val (nodes g)) 
(edges g)

... and so on. (This is all totally untested - use at your own peril.)

Each node in the graph has a unique identifying number, issued in sequence 
using maxNode as a counter. This makes identifying cycles easy. The nodes map 
contains the value for each node based on its id. The edges map contains a 
list of links from each node to others in the graph. Finding links entering a 
node is quite expensive - if you need to do this often then maintaining a 
second list of edges entering each node would speed it up.

Each node and each edge can have a custom data structure attached. New nodes 
and edges can be added without having to modify references elsewhere, nodes 
have a distinct identity given by the associated Int and the graph is 
immutable - operations on it produce modified copies.

Cheers,

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


Re: [Haskell-cafe] Spine-lazy "multiqueue"

2008-10-21 Thread Timothy Goddard
On Wed, 22 Oct 2008 11:54:50 Luke Palmer wrote:
> On Tue, Oct 21, 2008 at 3:02 PM, Justin Bailey <[EMAIL PROTECTED]> wrote:
> > On Tue, Oct 21, 2008 at 11:43 AM, Luke Palmer <[EMAIL PROTECTED]> wrote:
> >> Hi, I need a rather strange data structure, and I can't find any
> >> existing implementations or think of a way to implement it.  It's a
> >> "multiqueue", basically a map of queues.  The trick is that it should
> >> be lazy in its spine and still support efficient access.  For example,
> >> the following should hold:
> >
> > This doesn't answer your question, but how is a Map of queues not
> > "spine-lazy"? I'm mostly looking to understand that term.
>
> Well, first, my question was highly malformed.  I actually just want a
> spine lazy map of lists; queues were not what I wanted.
>
> Data.Map is strict in its keys, meaning rougly that you cannot store
> infinitely many keys in a map.  So:
>
>   foldr (\x x -> Map.insert x x) Map.empty [0..]  =  _|_
>
> I.e. if you take this map that maps every natural to itself and try to
> do anything with it, you will get an infinite loop (or stack overflow,
> or whatever).
>
> On the other hand, the "map" type [(k,v)] *is* spine lazy, because, for
> example:
>
>   lookup 42 [ (x,x) | x <- [0..] ]  = Just 42
>
> It's just not very efficient.  I'm basically looking for a version of
> the above which has a logarithmic lookup time.
>
> The best I've come up with so far is a binary search tree where the
> most recently inserted thing is at the root.  It's not balanced,
> because balancing would make it strict (as far as I can tell).  So
> it's only logarithmic time sometimes.
>
> Luke
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

You might possibly be able to get a logarithmic lookup time for keys known to 
be present while preserving some laziness (don't ask me how) but to say a key 
does not exist in the map you would have to somehow check them all, which 
with an infinite list of keys will never complete.

You're unlikely to get a free lunch with infinite maps - infinite items means 
infinite depth to any tree structure and there are few other nice 
alternatives.

You could simply add your own laziness - have a special map which consumes a 
list of (key, value) pairs and where reading the map also returns another map 
evaluated enough to answer the immediate query. Reading an already discovered 
key will take logarithmic time while reading an undiscovered key will take as 
long as it takes to find it in the list (for a nonexistent key, until memory 
runs out).

You could also work carefully with mutable references inside the map to make 
it appear pure from the outside. It could still present a referentially 
transparent interface since it is only evaluating itself further, not 
changing what it actually contains. You would have to make sure this worked 
properly though.

With that map you could perform updates as normal. Reading a value from the 
input list that already exists in the map would just do nothing.

I was interested enough to give this a try. Source is attached. It's 
incomplete - if you finish it please send me the result. Otherwise, use as 
you like.

Cheers,

Tim
module InfiniteMap
  (
InfiniteMap,
fromList,
(!)
  )
  where

import System.IO.Unsafe
import Data.IORef
import qualified Data.Map as M

data InfiniteMap k v = InfiniteMap {imRef :: IORef ((M.Map k v), [(k, v)])}

fromList :: Ord k => [(k, v)] -> InfiniteMap k v
fromList l = InfiniteMap (unsafePerformIO $ newIORef (M.empty, l))

fillMapUntil :: (Ord k, Eq k) => k -> (M.Map k v, [(k, v)]) -> (M.Map k v, [(k, 
v)])
fillMapUntil tk (m, []) = (m, [])
fillMapUntil tk (m, ((k, v):xs))
  | tk == k = (filledMap, xs)
  | otherwise = fillMapUntil tk (filledMap, xs)
  where
filledMap = M.insertWith' (\a _ -> a) k v m

(!) :: Ord k => InfiniteMap k v -> k -> v
m ! k = if k `M.member` cmap then (M.!) cmap k else (if k `M.member` newMap 
then (M.!) newMap k else error "Key not in map")
  where
cmap = fst $ unsafePerformIO $ readIORef $ imRef m
newMap = unsafePerformIO $ do
  (nm, nl) <- atomicModifyIORef (imRef m) (\a -> let res = fillMapUntil k a 
in (res, res))
  return nm

insert :: Ord k => k -> v -> InfiniteMap k v -> InfiniteMap k v
insert k v m = InfiniteMap $ unsafePerformIO $ newIORef (M.insert k v cmap, 
clist)
  where
(cmap, clist) = unsafePerformIO $ readIORef $ imRef m

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


Re: [Haskell-cafe] monadic parser with Happy and Alex

2008-10-07 Thread Timothy Goddard
On Sun, 05 Oct 2008 04:05:51 Manlio Perillo wrote:
> Hi.
>
> I have completed a draft of a CSS lexer, using Alex.
> http://hg.mperillo.ath.cx/haskell/webtools/file/tip/src/CSS/Lexer.x
>
> The lexer use the posn wrapper.
>
> Now I'm starting to write the parser with Happy, however for the final
> product I would like to:
> 1) Be able to do I/O in the lexer, for stylesheets inclusion
> (@import rule)
> 2) be able to keep state in the parser (or lexer?), for character
> transcoding (@charset rule)
>
>
> This should be possible with Happy (and there are some example), however
>   I don't find examples that make use of a lexer written with Alex.
>
> Should I write a lexer using only the Alex basic interface (without
> wrappers)?
>
>
>
> Thanks   Manlio Perillo
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Manlio,

You may be better off separating the parsing from the import process. You 
would first parse it in to internal data structures (including an option for 
import) then go through that and replace import statements with the parsed 
content of those files. Producing a list which is then consumed by an IO 
procedure is almost exactly equivalent to threading IO through the entire 
parser and is a lot tidier, more flexible and should be easier to maintain.

Cheers,

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


Re: [Haskell-cafe] System.Process

2008-09-29 Thread Timothy Goddard
On Tue, 30 Sep 2008 08:49:44 Andrew Coppin wrote:
> Before anybody remarks that "words" will do this, consider the "echo" 
command, which treats whitespace meaningfully.)

[EMAIL PROTECTED]:~/$ echo foo  barbaz
foo bar baz

Echo doesn't receive special treatment. It joins its arguments with spaces.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Red-Blue Stack

2008-09-29 Thread Timothy Goddard
There was a bug in there with popping the non-head colour off the stack. 
Updated code, please test thoroughly:

module RBStack where

data RBColour = Red | Blue
  deriving (Show, Eq)

data RBStack a =  RBStack {
  headColour :: RBColour,
  stackElems :: [[a]]
}
  deriving (Show, Eq)

otherCol :: RBColour -> RBColour
otherCol Red = Blue
otherCol Blue = Red

empty :: RBStack a
empty = RBStack Red []

push :: RBColour -> a -> RBStack a -> RBStack a
push col val stack
  | null (stackElems stack) = RBStack col [[val]]
  | headColour stack == col = RBStack col ((val:e):es)
  | otherwise = RBStack col ([val]:e:es)
  where
(e:es) = stackElems stack

popColour :: RBColour -> RBStack a -> (Maybe a, RBStack a)
popColour col stack
  | null (stackElems stack) = (Nothing, stack)
  | headColour stack == col = (Just (head e), if null (tail e)
  then (RBStack (otherCol col) es)
  else (RBStack col ((tail e):es)))
  | otherwise = if null es
  then (Nothing, stack)
  else let (f:fs) = es in (Just (head f), if null (tail f)
then (if null fs then (RBStack (otherCol col) [e]) else (RBStack 
(otherCol col) ((e ++ (head fs)):(tail fs
else RBStack (otherCol col) (e:(tail f):fs))
  where
(e:es) = stackElems stack

pop :: RBStack a -> (Maybe (RBColour, a), RBStack a)
pop stack
  | null (stackElems stack) = (Nothing, stack)
  | otherwise = (Just (col, head e), if null (tail e) then (RBStack (otherCol 
col) es) else (RBStack col ((tail e):es)))
  where
(e:es) = stackElems stack
col = headColour stack

peek :: RBStack a -> Maybe (RBColour, a)
peek = fst . pop
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Red-Blue Stack

2008-09-29 Thread Timothy Goddard
It won't be O(1) but this is how I would do it. It uses alternating lists of 
red and blue elements. It has to access at most three elements from this list 
for any one operation so as long as we don't have huge blocks of red or blue 
elements performance should be quite good.

The worst case I can think of is if we have an extremely large number of one 
colour followed by a single element of the other then pop that single element 
off the stack. This would require two lists (before and after the single 
element) to be combined with ++, taking time linear to the size of the first 
list.

Anyway, here's some code:

module RBStack
  where

data RBColour = Red | Blue
  deriving (Show, Eq)

data RBStack a =  RBStack {
  headColour :: RBColour,
  stackElems :: [[a]]
}
  deriving (Show, Eq)

otherCol :: RBColour -> RBColour
otherCol Red = Blue
otherCol Blue = Red

empty :: RBStack a
empty = RBStack Red []

push :: RBColour -> a -> RBStack a -> RBStack a
push col val stack
  | null (stackElems stack) = RBStack col [[val]]
  | headColour stack == col = RBStack col ((val:e):es)
  | otherwise = RBStack col ([val]:e:es)
  where
(e:es) = stackElems stack

popColour :: RBColour -> RBStack a -> (Maybe a, RBStack a)
popColour col stack
  | null (stackElems stack) = (Nothing, stack)
  | headColour stack == col = (Just (head e), if null (tail e)
  then (RBStack (otherCol col) es)
  else (RBStack col ((tail e):es)))
  | otherwise = if null es
  then (Nothing, empty)
  else let (f:fs) = es in (Just (head f), if null (tail f)
then (if null fs then (RBStack (otherCol col) [e]) else (RBStack 
(otherCol col) ((e ++ (head fs)):(tail fs
else RBStack (otherCol col) (e:(tail f):fs))
  where
(e:es) = stackElems stack

pop :: RBStack a -> (Maybe (RBColour, a), RBStack a)
pop stack
  | null (stackElems stack) = (Nothing, stack)
  | otherwise = (Just (col, head e), if null (tail e) then (RBStack (otherCol 
col) es) else (RBStack col ((tail e):es)))
  where
(e:es) = stackElems stack
col = headColour stack

peek :: RBStack a -> Maybe (RBColour, a)
peek = fst . pop
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Can you do everything without shared-memory concurrency?

2008-09-08 Thread Timothy Goddard
On Tue, 09 Sep 2008 07:33:24 Bruce Eckel wrote:
> I know that both Haskell and Erlang only allow separated memory spaces
> with message passing between processes, and they seem to be able to
> solve a large range of problems -- but are there problems that they
> cannot solve? I recently listened to an interview with Simon
> Peyton-Jones where he seemed to suggest that this newsgroup might be a
> helpful place to answer such questions. Thanks for any insights -- it
> would be especially useful if I can point to some kind of proof one
> way or another.

In Haskell it is  simply irrelevant whether parts of the structures being 
passed between threads are shared or not because the structures are 
immutable. We keep our code side-effect free and as a result it is incredibly 
easy to make parallel. This is so solid that we can also add implicit 
threading to the code with simple annotations such as 'par' and 'seq'.

Having said this, it is possible to generate structures which are mutable and 
only accessible in the IO monad. As a general rule, IO code using shared 
memory has the same threading issues as in any other language while pure code 
is guaranteed safe. Haskell is capable of working with both models, but 
mutable data structures are deliberately restricted in their use and are rare 
in practice.

A great deal of parallelism can be added to pure code without any risk. I 
can't assist with mathematical proofs, but can't think of any reason why 
shared, manipulable memory would be absolutely necessary. In the worst case, 
all operations on the data structure can be converted to messages to a 
central thread which manages that structure and serialises access. Any 
procedure call can become an asynchronous pair of request, response messages. 

I am not a mathematician, I can't prove it, but I can't think of circumstances 
where I would need to put mutable references in a data structure except where 
the language and compiler can't handle immutable structures efficiently.

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


Re: [Haskell-cafe] Is it usual to read a Maybe (IORef a) ?

2008-09-03 Thread Timothy Goddard
It looks like this code isn't really in fitting with normal Haskell idioms. 
Emulating C in Haskell will only give you a harder way of writing C. Don't 
think about emulating a potentially null pointer with Maybe (IORef a) and 
passing this to a function to read content unless you also want to implement 
the function "segfault :: IO ()".

You really need to ask yourself whether it makes sense to read a NULL / 
Nothing field. In C this would cause a segfault. The idea in Haskell is that 
you don't allow invalid values to be passed in to a function at all. Each 
function should be pure and accept only sensible inputs, allowing you to 
analyse what each function does in isolation from the rest of the program.

In Haskell, functions should use the type system to only accept arguments 
which make sense. The caller should handle the possibility that a function it 
calls returns nothing, not expect every other callee to do so. The Maybe 
monad helps with this for many cases:

lookupEmployee :: Integer -> Maybe Employee
lookupPassportNo :: Employee -> PassportNo
lookupMarriageCertificate :: PassportNo -> Maybe MarriageCert
getPassportNumbers :: MarriageCert -> (PassportNo, PassportNo)
getNameFromPassport :: PassportNo -> Maybe String

lookupSpouse :: Integer -> Maybe String
lookupSpouse employee_no = do
employee <- lookupEmployee employee_no
let passport = lookupPassportNo employee
cert <- lookupMarriageCertificate
let (p1, p2) = getPassportNumbers cert
let partner = if p1 == passport then p2 else p1
getNameFromPassport partner

In this example, if any lookup which can fail does, the result is Nothing. 
Each lookup function can assume that a valid argument is present, though some 
types of lookup may still give no result. The caller chooses how to account 
for this inability to find a match, in this case by itself having no result.

The thing I'm more concerned about here is the use of IORefs inside data 
structures at all. A data structure containing IORefs is mutable and can only 
be manipulated in the IO monad, which defeats the point of Haskell. There is 
a use case for using mutable structures for some resource-intensive 
operations, but even then it's often trading short-term speed for long term 
difficulties. If you think immutable structures imply poor performance, take 
a look at projects such as uvector and Data Parallel Haskell - immutable data 
structures which beat the hell out traditional, C-like techniques.

If you must use IORefs, consider only using them to hold the whole structure, 
which is modified by normal, pure functions. If you don't think you can make 
do with this, you're probably still thinking about the program in an 
imperative manner. You will probably be better off either rethinking how 
you're doing things or, if you cannot translate the concepts to a functional 
form, using an imperative language.

Good luck,

Tim

On Wed, 03 Sep 2008 22:09:38 minh thu wrote:
> Hi,
>
> I'd like to write a data structure to be used inside the IO monad.
> The structure has some handles of type Maybe (IORef a),
> i.e. IORef are pointers and the Maybe is like null pointers.
>
> So I came up with the following functions :
>
> readHandle :: Maybe (IORef a) -> IO (Maybe a)
> readField :: (a -> b) -> Maybe (IORef a) -> IO (Maybe b)
>
> readHandle Nothing  = do
>   return Nothing
> readHandle (Just r) = do
>   v <- readIORef r
>   return $ Just v
>
> readField f h = do
>   m <- readHandle h
>   return $ fmap f m
>
> Is it something usual ?
> Are there any related functions in the standard libraries ?
>
> Thanks,
> Thu
> ___
> 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