Hello,
I recently became the owner a USB gadget that tracks movement via GPS
and also tracks heart rate (it's a training device for athletes).
This device comes with software that is windows only and...doesn't
like up to it's potential (to put it politely). Being a programmer
type and someone th
Hi Chris!
On Aug 24, 2006, at 7:28 PM, Chris Kuklewicz wrote:
class Ref m r | m->r where
newRef
readRef
writeRef
instance Ref IO IORef
writeRef r x = writeIORef r $! x
instance (Ref m r) => Ref (WriterT m) r where
writeRef = lift . writeRef
and so on...
The code snippet above l
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 combin
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 mor
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 ::
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, Th
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
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 worl
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
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 rathe
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 ref
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)
>
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
h
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 Lo
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 oft
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
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)
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 (J
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)
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
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
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
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.
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,
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 di
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
> = T
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
27 matches
Mail list logo