[Haskell-cafe] question on traversing syntax tree

2006-08-24 Thread Xiong Yingfei
I am writing a compiler using Haskell. After the compiler parses program, the 
program is stored into an syntax tree stucture defined blew:

..
data Exp 
  = Plus Exp Term 
  | Minus Exp Term 
  | Term Term
  deriving Show

data Term 
  = Times Term Factor 
  | Div Term Factor 
  | Factor Factor
  deriving Show
..

This is just part of the definition. The full tree contains much more 
definition than this. Now I want to adjust the syntax-tree. However, I don't 
need to adjust all the data types, but a small subset of the syntax tree. e.g. 
I might adjust the Times data like the following, but not modify the rest of 
the syntax tree:
transformTerm (Times t f) = Times t (FactorInt 100)

However, in order to apply the modification like this, I have to write a series 
of function to traverse the tree until I get to the Term data type. e.g. I have 
to define:
transformExp (Plus e t) = Plus (transformExp e) (transformTerm t)
transformExp (Minus e t) = Minus (transformExp e)(transformTerm t)
transformTerm (Term t) = ...

This is tedious and error-prone. I want to know if there some means in Haskell 
to write a single generic function to traverse the syntax tree and only stop 
on the Term data type. Can anyone tell me something about it? Thanks a lot.

--
Xiong, Yingfei (熊英飞)
Ph.D. Student
Institute of Software
School of Electronics Engineering and Computer Science
Peking University
Beijing, 100871, PRC.
Web: http://xiong.yingfei.googlepages.com___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] question on traversing syntax tree

2006-08-24 Thread Donald Bruce Stewart
xiongyf04:
 I am writing a compiler using Haskell. After the compiler parses program, the 
 program is stored into an syntax tree stucture defined blew:
 
 ..
 data Exp 
   = Plus Exp Term 
   | Minus Exp Term 
   | Term Term
   deriving Show
 
 data Term 
   = Times Term Factor 
   | Div Term Factor 
   | Factor Factor
   deriving Show
 ..
 
 This is just part of the definition. The full tree contains much more 
 definition than this. Now I want to adjust the syntax-tree. However, I don't 
 need to adjust all the data types, but a small subset of the syntax tree. 
 e.g. I might adjust the Times data like the following, but not modify the 
 rest of the syntax tree:
 transformTerm (Times t f) = Times t (FactorInt 100)
 
 However, in order to apply the modification like this, I have to write a 
 series of function to traverse the tree until I get to the Term data type. 
 e.g. I have to define:
 transformExp (Plus e t) = Plus (transformExp e) (transformTerm t)
 transformExp (Minus e t) = Minus (transformExp e)(transformTerm t)
 transformTerm (Term t) = ...
 
 This is tedious and error-prone. I want to know if there some means in 
 Haskell to write a single generic function to traverse the syntax tree and 
 only stop on the Term data type. Can anyone tell me something about it? 
 Thanks a lot.
 

The Scrap Your Boilerplate series covers this, as does several other
works on generics in Haskell. Here's a good place to start:

http://www.cs.vu.nl/boilerplate/

also,
http://www.informatik.uni-bonn.de/~loeh/SYB0.html
http://www.informatik.uni-bonn.de/~loeh/SYB1.html

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


Re: [Haskell-cafe] implementing a csv reader

2006-08-24 Thread Henning Thielemann

On Wed, 23 Aug 2006, Robert Dockins wrote:

 
 On Aug 23, 2006, at 3:37 PM, Henk-Jan van Tuyl wrote:
 
  
  L.S.,
  
  Reading and writing a comma seperated datafile doesn't have to be that
  complicated; the following is an easy way to read a CSV file into a list of
  tuples and display the list on screen:
 
 For every complex problem, there is a solution which is simple, neat, and
 wrong.  -- HL Mencken
 
 
 Although it seems straightforward at first, CSV suffers from text escaping
 complexities, just as does every other general purpose plain-text encoding.
 Most notably, a newline embedded inside double quotes does not end a record.

I also think that quotes within quotes are represented by  rather than
\ in CSV.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] stack overflow when using ST monad

2006-08-24 Thread Gregory Wright


Hi,

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

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

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

hugs -98 Test2.hs

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

Type :? for help
Main main

ERROR - Garbage collection fails to reclaim sufficient space
Main

and ghci:

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

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


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

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

Best,
Greg



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


module Main where


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


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


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


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



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


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


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

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


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


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


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

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


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

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


[Haskell-cafe] wiki page Arrays updated

2006-08-24 Thread Bulat Ziganshin
Hello Haskell-Cafe,

i've added a lot of low-level information to the Arrays wiki page.
new material starts from note about GHC 6.6 in
http://haskell.org/haskellwiki/Modern_array_libraries#StorableArray_.28module_Data.Array.Storable.29

there are several details, however, which makes it imperfect. first,
as usual, is my awkward English. please correct my language misuse. in
particular, i don't know how to better name the page itself, meaning
modern library which implements many array types

second is that it will be great to add examples demonstrating each
discussed concept: casting, freezing, unsafe indexing, [::]. we also
still don't have examples for unboxed and diff arrays

third is that i'm not 100% sure that information about GHC internals i
provided is correct. can someone with a good knowledge of RTS internals
check it, including
http://haskell.org/haskellwiki/Modern_array_libraries#Welcome_to_machine:_Array.23.2C_MutableArray.23.2C_ByteArray.23.2C_MutableByteArray.23.2C_pinned_and_moveable_byte_arrays
and next section plus abovementioned link with information about
StorableArray in GHC 6.6?

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

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


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

2006-08-24 Thread Chris Kuklewicz
The write*Ref functions, like many write into data structure have the common 
problem of being much lazier than you want.  The nextState calls form a lazy 
thunk.  In fact it tries form 10^6 nested thunks to call nextState.  So you have 
to use something like seq to reduce the laziness:




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


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


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

2006-08-24 Thread Bulat Ziganshin
Hello Gregory,

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

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

as Chris said, you are write unevaluated chunks.

add $! to evaluate values before writing:

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

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


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

2006-08-24 Thread Brian Hulley

Gregory Wright wrote:

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


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


I would make all the fields strict here, to be sure that no lazyness can 
creep about unseen eg:


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

  -- ditto for FrozenTag

(And use (writeSTRef ref $! value) as others have suggested)

Regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


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

2006-08-24 Thread Gregory Wright


Hi Bulat,

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


Hello Gregory,

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


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


as Chris said, you are write unevaluated chunks.

add $! to evaluate values before writing:

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



That fixed it exactly.  Thank you Bulat and Chris!

Best Wishes,
Greg



--
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


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


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

2006-08-24 Thread Udo Stenzel
Hi Gregory,

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

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

 writeSTRef (state t) $! nextState s

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

[This comes up so often, shouldn't there be an FAQ about it somewhere?  It
could even offer a guideline along the lines of Whenever you repeatedly
update some value, chances are that you want to force strict
evaluation.]


Udo.


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


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

2006-08-24 Thread Gregory Wright


Hi Udo,

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


Hi Gregory,

Gregory Wright wrote:

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


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


writeSTRef (state t) $! nextState s


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

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

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



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

writeSTRef (state t) $! nextState s

but what I actually typed was

writeSTRef (state t) (nextState $! s)

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

Best,
Greg



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


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


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

2006-08-24 Thread Gregory Wright


Hi,

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

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

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

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

or about 10^6 state updates per second).

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

my implementation of this may well be faulty.

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

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

function.  ATM, running test2 gives a stack overflow.

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


Best,
greg


 
--


test1.hs, the big stick (unsafeIOToST):

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


module Main where


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


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


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


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



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


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


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

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


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


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


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

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


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






 
-


test2.hs: stacked WriterT and ST monads:

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


module Main where


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


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


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


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


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



-- Repeat a 

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

2006-08-24 Thread Chris Kuklewicz

Gregory Wright wrote:


Hi,

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

The goal of the simulator is to produce a log of tag states, which can be
analyzed to find statistics of how often the sensor tags in a particular 
state.

(In the toy model below there is no external signal, so the log isn't very
interesting yet.)  For the moment, I am using the big stick approach of
unsafeIOToST to write log messages.  Since the only outputs of the program
are the log messages, and invocations of step are ordered by the ST 
monad,
it seems that unsafeIOToST is safe in this case, in the sense that the 
outputs

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

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

or about 10^6 state updates per second).

I've considered using a WriterT monad to wrap the ST monad to produce
a log.  The problem with this seems to be ensuring that the log output
is generated lazily so it can be incrementally output. A somewhat broken
sketch is the program test2.hs below.  I used a function from [String] 
- [String]

as the monoid to avoid the O(n^2) inefficiency of appending to a list, but
my implementation of this may well be faulty.



(Writer [String] [Int]) can produce the log lazily.  (WriterT [String] Identity 
[Int]) cannot produce the log lazily.  But (Identity [Int]) can produce its 
output lazily.  Using ST.Lazy and Either instead of WriterT, I can get the 
streaming behavior.  But I have to use a continuation passing style

module Main where

import Control.Monad.ST.Lazy
import Data.STRef.Lazy
import Control.Monad.Writer
import Control.Monad.Identity
import Maybe
import Debug.Trace

type LogMonoid = [String] - [String]

loop :: Int - Writer [String] [Int]
loop 0 = trace end of loop (return [0])
loop x = do
  let msg = loop now ++ show x
  tell [msg]
  liftM (x:) (loop (pred x))

loop' :: Int - WriterT [String] Identity [Int]
loop' 0 = trace end of loop' (return [0])
loop' x = do
  let msg = loop' now ++ show x
  tell [msg]
  liftM (x:) (loop' (pred x))

loopI :: Int - Identity [Int]
loopI 0 = trace end of loopI (return [0])
loopI x = liftM (x:) (loopI (pred x))

loopM :: Int - WriterT LogMonoid Identity [Int]
loopM 0 = trace end of loopM (return [0])
loopM x = do
  let msg = loopM now ++ show x
  tell (msg:)
  liftM (x:) (loopM (pred x))

loopST :: Int - ST s [Either String Int]
loopST init = do
  ref - newSTRef init
  let loop = do
x - readSTRef ref
writeSTRef ref $! (pred x)
let msg = Left (loopST now ++ show x)
cont = if x==0
 then trace end of loopST (return [Right 0])
 else loop
liftM (msg :) cont
  loop


loopST2 :: Int - ST s [Either String Int]
loopST2 init = do
  ref - newSTRef init
  let loop = do
x - readSTRef ref
writeSTRef ref $! (pred x)
let msg = Left (loopST now ++ show x)
cont = if x==0
 then trace end of loopST (return [Right 0])
 else loop
rest - cont
return (msg : rest)
  loop

main :: IO ()
main = do
  let log = execWriter (loop 100)
  print (head log)
  print (last log)
  let log' = runIdentity (execWriterT (loop' 100))
  print (head log')
  print (last log')
  let logI = runIdentity (loopI 100)
  print (head logI)
  print (last logI)
  let logMf = runIdentity (execWriterT (loopM 100))
  logM = logMf []
  print (head logM)
  print (last logM)
  let logst = runST (loopST 100)
  print (head logst)
  print (last logst)
  let logst2 = runST (loopST2 100)
  print (head logst2)
  print (last logst2)



Edited output is

$ ./maindemo
loop now 100
end of loop
loop now 1

end of loop'
loop' now 100
loop' now 1

100
end of loopI
0

end of loopM
loopM now 100
loopM now 1

Left loopST now 100
end of loopST
Right 0

Left loopST now 100
end of loopST
Right 0

From the above the WriterT in loop' and loopM are not lazy but the other 
examples are.



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


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

2006-08-24 Thread Chris Kuklewicz

The problem with WriterT is it is too strict.

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

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

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

A lazy version of WriterT, called LogT:


{-# OPTIONS_GHC -fglasgow-exts #-}
module Main where

import Control.Monad.ST.Lazy
import Data.STRef.Lazy
import Control.Monad.Writer
import Control.Monad.Identity
import Control.Monad.Fix
import Control.Monad.Trans
import Control.Monad.Reader
import Maybe
import Debug.Trace

type LogMonoid = [String] - [String]

loopLT :: Int - LogT [String] Identity [Int]
loopLT 0 = trace end of loopLT (return [0])
loopLT x = do
  let msg = loopLT now ++ show x
  tell [msg]
  liftM (x:) (loopLT (pred x))

newtype LogT w m a = LogT { runLogT :: m (a, w) }


instance (Monad m) = Functor (LogT w m) where
fmap f m = LogT $ do
(a, w) - runLogT m
return (f a, w)

instance (Monoid w, Monad m) = Monad (LogT w m) where
return a = LogT $ return (a, mempty)
m = k  = LogT $ do
~(a,w)  - runLogT m
~(b,w') - runLogT (k a)
return (b, w `mappend` w')
fail msg = LogT $ fail msg

instance (Monoid w, MonadPlus m) = MonadPlus (LogT w m) where
mzero   = LogT mzero
m `mplus` n = LogT $ runLogT m `mplus` runLogT n

instance (Monoid w, MonadFix m) = MonadFix (LogT w m) where
mfix m = LogT $ mfix $ \ ~(a, _) - runLogT (m a)

instance (Monoid w, Monad m) = MonadWriter w (LogT w m) where
tell   w = LogT $ return ((), w)
listen m = LogT $ do
(a, w) - runLogT m
return ((a, w), w)
pass   m = LogT $ do
((a, f), w) - runLogT m
return (a, f w)

instance (Monoid w) = MonadTrans (LogT w) where
lift m = LogT $ do
a - m
return (a, mempty)

instance (Monoid w, MonadIO m) = MonadIO (LogT w m) where
liftIO = lift . liftIO

-- This instance needs -fallow-undecidable-instances, because 
-- it does not satisfy the coverage condition

instance (Monoid w, MonadReader r m) = MonadReader r (LogT w m) where
ask   = lift ask
local f m = LogT $ local f (runLogT m)


execLogT :: Monad m = LogT w m a - m w
execLogT m = do
(_, w) - runLogT m
return w

mapLogT :: (m (a, w) - n (b, w')) - LogT w m a - LogT w' n b
mapLogT f m = LogT $ f (runLogT m)


main :: IO ()
main = do
  let logLT = runIdentity (execLogT (loopLT 100))
  print (head logLT)
  print (last logLT)


The output is

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

Just as we want.


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


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

2006-08-24 Thread Chris Kuklewicz
So using LogT instead of WriterT, and changing from Control.Monad.ST to 
Control.Monad.ST.Lazy I can make you code work as you wanted:



{-# OPTIONS_GHC -fglasgow-exts #-}
module Main where

import Control.Monad.ST.Lazy
import Data.STRef.Lazy
import Maybe
import Debug.Trace
-- LogT, copied from 
http://darcs.haskell.org/packages/mtl/Control/Monad/Writer.hs
import Control.Monad.Writer
import Control.Monad.Reader
import Control.Monad.Fix
import Control.Monad.Trans

newtype LogT w m a = LogT { runLogT :: m (a, w) }


instance (Monad m) = Functor (LogT w m) where
fmap f m = LogT $ do
(a, w) - runLogT m
return (f a, w)

instance (Monoid w, Monad m) = Monad (LogT w m) where
return a = LogT $ return (a, mempty)
m = k  = LogT $ do
~(a,w)  - runLogT m
~(b,w') - runLogT (k a)
return (b, w `mappend` w')
fail msg = LogT $ fail msg

instance (Monoid w, MonadPlus m) = MonadPlus (LogT w m) where
mzero   = LogT mzero
m `mplus` n = LogT $ runLogT m `mplus` runLogT n

instance (Monoid w, MonadFix m) = MonadFix (LogT w m) where
mfix m = LogT $ mfix $ \ ~(a, _) - runLogT (m a)

instance (Monoid w, Monad m) = MonadWriter w (LogT w m) where
tell   w = LogT $ return ((), w)
listen m = LogT $ do
(a, w) - runLogT m
return ((a, w), w)
pass   m = LogT $ do
((a, f), w) - runLogT m
return (a, f w)

instance (Monoid w) = MonadTrans (LogT w) where
lift m = LogT $ do
a - m
return (a, mempty)

instance (Monoid w, MonadIO m) = MonadIO (LogT w m) where
liftIO = lift . liftIO

instance (Monoid w, MonadReader r m) = MonadReader r (LogT w m) where
ask   = lift ask
local f m = LogT $ local f (runLogT m)


execLogT :: Monad m = LogT w m a - m w
execLogT m = do
(_, w) - runLogT m
return w

mapLogT :: (m (a, w) - n (b, w')) - LogT w m a - LogT w' n b
mapLogT f m = LogT $ f (runLogT m)

-- End of LogT


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


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


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


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



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


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


initialize :: LogST s (Tag s)
initialize = do
init_count - lift $ newSTRef 100
init_state - lift $ newSTRef Syncing

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


step :: Tag s - LogST s (Maybe Integer)
step t = do
c - lift $ readSTRef (count t)
s - lift $ readSTRef (state t)
lift $ writeSTRef (count t) $! (c - 1)
lift $ writeSTRef (state t) $! (nextState s)
tell ((next state is  ++ show s) : )
if (c = 0) then return Nothing else return (Just c)


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


freezeTag :: Tag s - LogST s (FrozenTag)
freezeTag t = do
frozen_count - lift $ readSTRef (count t)
frozen_state - lift $ readSTRef (state t)

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


main :: IO ()
main = do
let (t, l) = runST (runLogT runTag)
log = l []
putStrLn (show . head $ log)
putStrLn (show . last $ log)


output is

$ ./main2
next state is Syncing
until_ is finished
next state is Listening

with a very long delay after the first line of output and before the second.


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


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

2006-08-24 Thread Bulat Ziganshin
Hello Brian,

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

 I would make all the fields strict here, to be sure that no lazyness can
 creep about unseen eg:

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

perhaps better:

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

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

also, one can implement strict write operations:

writeRef r x = writeSTRef r $! x

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


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


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

2006-08-24 Thread Bulat Ziganshin
Hello Gregory,

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

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

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

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

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

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

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

and so on...

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


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


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

2006-08-24 Thread Bulat Ziganshin
Hello Gregory,

Thursday, August 24, 2006, 4:43:57 PM, you wrote:

 I agree this should be a FAQ.

we already have something like this on performance/strictness
wikipage. although adding your example of misusing $! may be helpful -
peoples are always better learned on (good and bad) examples rather on
bare theory

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

 writeSTRef (state t) $! nextState s

 but what I actually typed was

 writeSTRef (state t) (nextState $! s)

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


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] monads once again: a newbie perspective

2006-08-24 Thread Andrea Rossato
Hello!

I' m new to Haskell and try to find my way through types and monads.
I tried the yet Another Haskell Tutorial, very useful for types, but
almost unreadable for monads (that's my perspective!).
Then I discovered that wonderful paper by Wadler (Monads for
functional programming).
So I started translating it for someone who can be scared of
something with an abstract and footnotes coming from a professor.

I started writing it in order to clarify to myself this difficult
topic. I think I'm now grasping the concept of monads. 
I thought that someone else could find my writings useful.

It could become a page on the wiki. But before posting there I would
like to have your opinion. Perhaps this is just something unreadable.

Let me know.
Andrea
An evaluation of Philip Wadler's Monads for functional programming
(avail. from http://homepages.inf.ed.ac.uk/wadler/topics/monads.html)


Let's start with something simple: suppose we want to implement a new
programming language. We just finished with Abelson and Sussman's
Structure and Interpretation of Computer Programs
[http://swiss.csail.mit.edu/classes/6.001/abelson-sussman-lectures/]
and we want to test what we have learned.

Our programming language will be very simple: it will just compute the
sum operation.
So we have just one primitive operation (Add) that takes to constants
and calculates their sum
For instance, something like:
(Add (Con 5) (Con 6))
should yeld:
11

We will implement our language with the help of a data type
constructor such as:

 module MyMonads where
 data Term = Con Int
  | Add Term Term
deriving (Show)

After that we build our interpreter:

 eval :: Term - Int
 eval (Con a) = a
 eval (Add a b) = eval a + eval b

That's it. Just an example:

*MyMonads eval (Add (Con 5) (Con 6))
11

Very very simple. The evaluator checks if its argument is a Cons: if
it is it just returns it.
If it's not a Cons, but it is a Term, it evaluates the right one and
sums the result with the result of the evaluation of the second term.

Now, that's fine, but we'd like to add some features, like providing
some output, to show how the computation was carried out.
Well, but Haskell is a pure functional language, with no side effects,
we were told.
Now we seem to be wanting to create a side effect of the computation,
its output, and be able to stare at it...
If we had some global variable to store the out that would be
simple...
But we can create the output and carry it along the computation,
concatenating it with the old one, and present it at the end of the
evaluation together with the evaluation of the expression!
Simple and neat!

 type MOut a = (a, Output)
 type Output = String
 
 formatLine :: Term - Int - Output
 formatLine t a = eval ( ++ show t ++ ) =  ++ show a ++  -  
   
 
 evalO :: Term - MOut Int
 evalO (Con a) = (a, formatLine (Con a) a)
 evalO (Add t u) = ((a + b),(x ++ y ++ formatLine (Add t u) (a + b)))
 where (a, x) = evalO t
   (b, y) = evalO u


Now we have what we want. But we had to change our evaluator quite a
bit. First we added a function, that takes a Term (of the expression
to be evaluated), an Int (the result of the evaluation) and gives back
an output of type Output (that is a synonymous of String). 

The evaluator changed quite a lot! Now it has a different type: it
takes a Term data type and produces a new type, we called MOut, that
is actually a pair of a variable type a (an Int in our evaluator) and
a type Output, a string.
So our evaluator, now, will take a Term (the type of the expressions
in our new programming language) and will produce a pair, composed of
the result of the evaluation (an Int) and the Output, a string.

So far so good. But what's happening inside the evaluator?
The first part will just return a pair with the number evaluated and
the output formatted by formatLine. 
The second part does something more complicated: it returns a pair
composed by 
1. the result of the evaluation of the right Term summed to the result
of the evaluation of the second Term
2. the output: the concatenation of the output produced by the
evaluation of the right Term, the output produced by the evaluation of
the left Term (each this evaluation returns a pair with the number and
the output), and the formatted output of the evaluation.

Let's try it:
*MyMonads evalO (Add (Con 5) (Con 6))
(11,eval (Con 5) = 5 - eval (Con 6) = 6 - eval (Add (Con 5) (Con 6)) = 11 - 
)
*MyMonads

It works! Let's put the output this way:
eval (Con 5) = 5 - 
eval (Con 6) = 6 - 
eval (Add (Con 5) (Con 6)) = 11 -

Great! We are able to produce a side effect of our evaluation and
present it at the end of the computation, after all.

Let's have a closer look at this expression:
evalO (Add t u) = ((a + b),(x ++ y ++ formatLine (Add t u) (a + b)))
 where (a, x) = evalO t
   (b, y) = evalO u

Why all that? The problem is that we need a and b to calculate their
sum, 

Re: [Haskell-cafe] monads once again: a newbie perspective

2006-08-24 Thread Neil Mitchell

Hi,


It could become a page on the wiki. But before posting there I would
like to have your opinion. Perhaps this is just something unreadable.


Just shove it on the wiki regardless. If its useless then no one will
read it. If its a bit unreadable, then people will fix it. If its
useful the world will benefit. Any outcome is a good outcome!

Once its on the wiki I'll give it a read, since it looks promising,
but its a bit hard to read in teletype font as displayed by my
browser.

Thanks

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


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

2006-08-24 Thread Gregory Wright

Hi Chris,

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

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

Virtual beer to you sir!

-Greg

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


The problem with WriterT is it is too strict.

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

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

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

A lazy version of WriterT, called LogT:


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

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


The output is

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

Just as we want.




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


Re: [Haskell-cafe] Fran - Functional Reactive Animation

2006-08-24 Thread Paul Hudak
Actually Pan (and Pan#) are NOT the same as Fran -- quite a bit 
different, in fact.  You may have to email Conal Elliott for a working 
version of Fran, OR you could look at my simplified version (which I 
call FAL, for Functional Animation Language) described in Chapter 15 
of my textbook, The Haskell School of Expression.  You can get a working 
version of FAL by downloading the source code from www.haskell.org/soe, 
although I should warn that the graphics lib on which it depends no 
longer works on all platforms and with all compilers.


Another option is to look at Yampa (www.haskell.org/yampa) which when 
combined with a suitable graphics back-end is essentially an arrowized 
version of Fran.  I would recommend this route if you want to avoid 
space-leak problems that are inherent with pure Fran.


Let me know if you have any problems.

   -Paul


Jared Updike wrote:


I think this works:

 http://haskell.org/edsl/pansharp.html

 Jared.

On 8/23/06, HIGGINS Neil (ENERGEX) [EMAIL PROTECTED] wrote:



Fran is a Haskell library (or embedded language) for interactive
animations with 2D and 3D graphics and sound. See
http://www.conal.net/fran/ and
http://research.microsoft.com/research/downloads/download.aspx?FUID=c9eff407-ce59-4a2a-90cb-de099a9bacbd 



I would like to use Fran as a rapid prototyping environment for 
animations,

but it appears to be broken under WinHugs.

I'm looking for someone with much better Haskell prowess than myself who
might be able resurrect Fran under WinHugs. Unfortunately I can only 
offer

my gratitude in return.

It's a long shot, I know.

Kind regards,
Neil Higgins
Snr Strategic Planning Engineer
ENERGEX
Em: [EMAIL PROTECTED]
Ph:  3407 4800
Fx:  3407 4832




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


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

2006-08-24 Thread Gregory Wright


Hi Bulat!

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


Hello Brian,

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

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

creep about unseen eg:



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


perhaps better:

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

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



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

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



also, one can implement strict write operations:

writeRef r x = writeSTRef r $! x

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



I will look at this. Thanks!

Best Wishes,
Greg



--
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


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


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

2006-08-24 Thread Gregory Wright


Hi Bulat!

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


Hello Gregory,

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


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


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



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

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

(called LogT here) and the unsafe* operation.

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

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

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

reversed.


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

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

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

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

and so on...



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

Best Wishes,
Greg




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


--
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


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


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

2006-08-24 Thread Chris Kuklewicz

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

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

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

and so on...



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

Best Wishes,
Greg



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


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


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

But it helps to learn how the plumbing works.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe