<html><head><style>body{font-family:Helvetica,Arial;font-size:13px}</style></head><body style="word-wrap: break-word; -webkit-nbsp-mode: space; -webkit-line-break: after-white-space; "><div id="bloop_customfont" style="font-family:Helvetica,Arial;font-size:13px; color: rgba(0,0,0,1.0); margin: 0px; line-height: auto;">For transforming the code, have you checked out the uniplate package? It seems like it could fit your problem pretty well.</div> <div id="bloop_sign_1407511443754356736" class="bloop_sign"><br><br><span style="font-family:helvetica,arial;font-size:13px"></span><span></span></div> <br><p style="color:#000;">On 8 August, 2014 at 5:00:19 AM, haskell-cafe-request@haskell.org (<a href="mailto:haskell-cafe-request@haskell.org">haskell-cafe-request@haskell.org</a>) wrote:</p> <blockquote type="cite" class="clean_bq"><span><div><div></div><div>Send Haskell-Cafe mailing list submissions to
<br>      haskell-cafe@haskell.org
<br>
<br>To subscribe or unsubscribe via the World Wide Web, visit
<br>      http://www.haskell.org/mailman/listinfo/haskell-cafe
<br>or, via email, send a message with subject or body 'help' to
<br>      haskell-cafe-request@haskell.org
<br>
<br>You can reach the person managing the list at
<br>      haskell-cafe-owner@haskell.org
<br>
<br>When replying, please edit your Subject line so it is more specific
<br>than "Re: Contents of Haskell-Cafe digest..."
<br>
<br>
<br>Today's Topics:
<br>
<br>   1. Re: Side-by-side pretty printing (J. Waldmann)
<br>   2. Free monad based EDSL for writing LLVM programs. (arrowdodger)
<br>   3. parsec: problem combining lookAhead with many1 (bug?) (silly8888)
<br>   4. Re: parsec: problem combining lookAhead with many1      (bug?)
<br>      (Andreas Reuleaux)
<br>   5. Performance of StateT and best practices for    debugging
<br>      (Kyle Hanson)
<br>   6. [ANN] rtorrent-state 0.1.0.0 (Mateusz Kowalczyk)
<br>   7. Re: Performance of StateT and best practices for        debugging
<br>      (John Lato)
<br>   8. How to improve the zipwith's performance (jun zhang)
<br>   9. Re: Performance of StateT and best practices for        debugging
<br>      (Bardur Arantsson)
<br>  10. Visualising Haskell function execution (Jan Paul Posma)
<br>  11. Re: Performance of StateT and best practices for        debugging
<br>      (John Lato)
<br>
<br>
<br>----------------------------------------------------------------------
<br>
<br>Message: 1
<br>Date: Thu, 7 Aug 2014 12:33:43 +0000 (UTC)
<br>From: J. Waldmann <waldmann@imn.htwk-leipzig.de>
<br>To: haskell-cafe@haskell.org
<br>Subject: Re: [Haskell-cafe] Side-by-side pretty printing
<br>Message-ID: <loom.20140807T142947-462@post.gmane.org>
<br>Content-Type: text/plain; charset=us-ascii
<br>
<br>This is what I use
<br>
<br>http://autolat.imn.htwk-leipzig.de/gitweb/?p=autolib;a=blob;f=todoc/Autolib/ToDoc/Beside.hs;hb=HEAD
<br>
<br>it's of the works-but-looks-ugly-and-is-terribly-inefficient variety
<br>but since it's applied to small Docs only (like, columns of matrices),
<br>I don't really care.
<br>
<br>- J.W.
<br>
<br>
<br>
<br>
<br>------------------------------
<br>
<br>Message: 2
<br>Date: Thu, 7 Aug 2014 18:16:57 +0400
<br>From: arrowdodger <6yearold@gmail.com>
<br>To: haskell-cafe@haskell.org
<br>Subject: [Haskell-cafe] Free monad based EDSL for writing LLVM
<br>      programs.
<br>Message-ID:
<br>      <CALH631=EbZ8aTZi=oPdfsP97J2XrRCTf=DpX+uaZ5m9=0mxXhw@mail.gmail.com>
<br>Content-Type: text/plain; charset="utf-8"
<br>
<br>Hello. I'm new with Haskell and FP, so i wanted someone to give comments on
<br>the package i've made [1]. It's, actually, my first attempt to create
<br>something more or less real, so any feedback would be welcome.
<br>
<br>I've used Free monad to create EDSL that allows writing LLVM IR code.
<br>Afterwards it could be converted into pure AST structure provided by
<br>llvm-general-pure[2] package. Currently, it supports almost every
<br>instruction, but i haven't yet come up with sensible defaults for them.
<br>
<br>Another thing that bugs me is the ability to transform the code in syb way.
<br>I want take a user-supplied function that would pattern-match instruction
<br>and produce another code block and apply this function everywhere in the
<br>code, but still can't get my head around it. I've come up with extF
<br>function, that unlike extM, would resort to wrap instead of return, but
<br>that's all i've managed to do.
<br>
<br>Thanks in advance.
<br>
<br>[1] https://bitbucket.org/arrowdodger/llvm-general-edsl
<br>[2] http://hackage.haskell.org/package/llvm-general-pure
<br>-------------- next part --------------
<br>An HTML attachment was scrubbed...
<br>URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140807/6d973f16/attachment-0001.html>
<br>
<br>------------------------------
<br>
<br>Message: 3
<br>Date: Thu, 7 Aug 2014 15:25:23 +0100
<br>From: silly8888 <silly8888@gmail.com>
<br>To: haskell-cafe@haskell.org
<br>Subject: [Haskell-cafe] parsec: problem combining lookAhead with many1
<br>      (bug?)
<br>Message-ID:
<br>      <CAMmzbfWA9S3YGjJ1iQaa72rKZyuV4psvEP3LsQuDGC3QED-YVw@mail.gmail.com>
<br>Content-Type: text/plain; charset=UTF-8
<br>
<br>Suppose that we have the following parser:
<br>
<br>  p = lookAhead (char 'a') >> char 'b'
<br>
<br>If we use it like so
<br>
<br>  parse p "" "a"
<br>
<br>we get the following error:
<br>
<br>Left (line 1, column 1):
<br>unexpected "a"
<br>expecting "b"
<br>
<br>What happened is that char 'a' succeeded by consuming the 'a' from the
<br>input and then lookAhead rewinded the input stream (as it does on
<br>success). Then, char 'b' tries to parse (again) the first character of
<br>the input and fails. Everything works as expected.
<br>
<br>Now let's slightly modify our parser:
<br>
<br>  p' = lookAhead (many1 $ char 'a') >> char 'b'
<br>
<br>I've only added a many1. I was expecting this parser to give the same
<br>error as the previous one: many1 $ char 'a' will succeed consuming one
<br>'a' and then lookAhead will rewind the input (as it does on success).
<br>Thus when we call char 'b' we are going to be in the beginning of the
<br>input again. Well, that doesn't happen:
<br>
<br>Left (line 1, column 2):
<br>unexpected end of input
<br>expecting "b"
<br>
<br>As you can see, lookAhead did not rewind the input as it was supposed to.
<br>
<br>
<br>------------------------------
<br>
<br>Message: 4
<br>Date: Thu, 07 Aug 2014 17:32:11 +0100
<br>From: Andreas Reuleaux <reuleaux@web.de>
<br>To: silly8888 <silly8888@gmail.com>
<br>Cc: haskell-cafe@haskell.org
<br>Subject: Re: [Haskell-cafe] parsec: problem combining lookAhead with
<br>      many1   (bug?)
<br>Message-ID: <87y4v0z2es.fsf@web.de>
<br>Content-Type: text/plain
<br>
<br>While I haven't tried out your example in parsec, I can at least confirm
<br>that in trifecta it does work that way you expect it, ie. there is no
<br>difference between the error messages in both of your cases:
<br>(parsec's many1 = trifecta's some)
<br>
<br>
<br>Prelude > :m +Text.Trifecta
<br>Prelude Text.Trifecta > :m +Text.Parser.LookAhead
<br>Prelude Text.Trifecta Text.Parser.LookAhead >
<br>...
<br>Prelude Text.Trifecta Text.Parser.LookAhead > parseTest (lookAhead (char 'a') >> char 'b') "a"
<br>...
<br>Loading package reducers-3.10.2.1 ... linking ... done.
<br>Loading package trifecta-1.5.1 ... linking ... done.
<br>(interactive):1:1: error: expected: "b"
<br>a<EOF>  
<br>^       
<br>Prelude Text.Trifecta Text.Parser.LookAhead > parseTest (lookAhead (some $ char 'a') >> char 'b') "a"
<br>(interactive):1:1: error: expected: "b"
<br>a<EOF>  
<br>^       
<br>Prelude Text.Trifecta Text.Parser.LookAhead >  
<br>
<br>
<br>Hope this helps.
<br>
<br>-Andreas
<br>
<br>
<br>
<br>
<br>silly8888 <silly8888@gmail.com> writes:
<br>
<br>> Suppose that we have the following parser:
<br>>
<br>>   p = lookAhead (char 'a') >> char 'b'
<br>>
<br>> If we use it like so
<br>>
<br>>   parse p "" "a"
<br>>
<br>> we get the following error:
<br>>
<br>> Left (line 1, column 1):
<br>> unexpected "a"
<br>> expecting "b"
<br>>
<br>> What happened is that char 'a' succeeded by consuming the 'a' from the
<br>> input and then lookAhead rewinded the input stream (as it does on
<br>> success). Then, char 'b' tries to parse (again) the first character of
<br>> the input and fails. Everything works as expected.
<br>>
<br>> Now let's slightly modify our parser:
<br>>
<br>>   p' = lookAhead (many1 $ char 'a') >> char 'b'
<br>>
<br>> I've only added a many1. I was expecting this parser to give the same
<br>> error as the previous one: many1 $ char 'a' will succeed consuming one
<br>> 'a' and then lookAhead will rewind the input (as it does on success).
<br>> Thus when we call char 'b' we are going to be in the beginning of the
<br>> input again. Well, that doesn't happen:
<br>>
<br>> Left (line 1, column 2):
<br>> unexpected end of input
<br>> expecting "b"
<br>>
<br>> As you can see, lookAhead did not rewind the input as it was supposed to.
<br>> _______________________________________________
<br>> Haskell-Cafe mailing list
<br>> Haskell-Cafe@haskell.org
<br>> http://www.haskell.org/mailman/listinfo/haskell-cafe
<br>
<br>
<br>------------------------------
<br>
<br>Message: 5
<br>Date: Thu, 7 Aug 2014 10:57:47 -0700
<br>From: Kyle Hanson <me@khanson.io>
<br>To: haskell-cafe@haskell.org
<br>Subject: [Haskell-cafe] Performance of StateT and best practices for
<br>      debugging
<br>Message-ID:
<br>      <CAMJUouBqFbSi+ifFsbYdXpba7pPVoP8BkyZxZaUoqLNuHc7VzQ@mail.gmail.com>
<br>Content-Type: text/plain; charset="utf-8"
<br>
<br>Hello,
<br>
<br>I was looking at cleaning up my refactoring a core loop of template
<br>rendering to go from a loop with many parameters
<br>
<br>loop :: RenderConfig -> BlockMap -> InputBucket m -> Builder -> [Pieces] ->
<br>ExceptT StrapError m Builder
<br>
<br>to a looped state monad transformer
<br>
<br>loop :: [Pieces] -> RenderT m Builder
<br>
<br>newtype RenderT m a = RenderT
<br>  { runRenderT :: ExceptT StrapError (StateT (RenderState m) m) a
<br>  } deriving ( Functor, Applicative, Monad, MonadIO )
<br>
<br>data RenderState m = RenderState
<br>  { position     :: SourcePos
<br>  , renderConfig :: RenderConfig
<br>  , blocks       :: BlockMap
<br>  , bucket       :: InputBucket m
<br>  }
<br>
<br>however, there is a big slow down (about 6-10x) using a StateT. I think it
<br>might have something to do with laziness but I am not exactly sure of where
<br>to begin in tracking it down. Swapping out the Lazy State to a Strict State
<br>helps a little (only a 5x slow down)
<br>
<br>You can find some of the processing code here:
<br>
<br>https://github.com/hansonkd/StrappedTemplates/blob/321a88168d54943fc217553c873f188797c0d4f5/src/Text/Strapped/Render.hs#L189
<br>
<br>With my old loop commented out.
<br>
<br>Its messy right now since I am just trying a number of different
<br>approaches. I did some more work factoring out the lifts, trying different
<br>iterations of foldlM and stuff but that didn't have that much of an effect
<br>on performance.
<br>
<br>After profiling I see in the StateT, the report has a lot more CAFs and
<br>garbage collecting.
<br>
<br>Here is the profiling report from my original version w/o StateT
<br>http://lpaste.net/108995
<br>
<br>Slow version with StateT
<br>http://lpaste.net/108997
<br>
<br>Here is the "makeBucket" function that is referenced (it is the same in
<br>both state and nonstate):
<br>
<br>https://github.com/hansonkd/StrappedTemplates/blob/321a88168d54943fc217553c873f188797c0d4f5/examples/big_example.hs#L24
<br>
<br>Looking at stacked overflow and the official docs I have gotten an idea of
<br>what is going on. The heaps generated between them tells me that a lot more
<br>memory is being allocated to lists. These heaps were generated running my
<br>render function against a template with nested loops and a list of elements.
<br>
<br>http://imgur.com/a/2jOIf
<br>
<br>I am hoping that maybe someone could give me a hint at what to look at
<br>next. I've played around with Strictness and refactoring loops to no avail
<br>and now am kind of stuck. Any help would be appreciated.
<br>
<br>--
<br>Kyle Hanson
<br>-------------- next part --------------
<br>An HTML attachment was scrubbed...
<br>URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140807/a82b99f5/attachment-0001.html>
<br>
<br>------------------------------
<br>
<br>Message: 6
<br>Date: Thu, 07 Aug 2014 21:07:02 +0200
<br>From: Mateusz Kowalczyk <fuuzetsu@fuuzetsu.co.uk>
<br>To: haskell-cafe@haskell.org
<br>Subject: [Haskell-cafe] [ANN] rtorrent-state 0.1.0.0
<br>Message-ID: <53E3CE56.6090500@fuuzetsu.co.uk>
<br>Content-Type: text/plain; charset=windows-1252
<br>
<br>Hi,
<br>
<br>rtorrent-state is a library that allows working with rtorrent state
<br>files (SOMEHASH.torrent.rtorrent) placed in your session directory.
<br>
<br>If you're an rtorrent user and ever had to manually muck around with
<br>those files, you should be able to use this library to make your life
<br>easier.
<br>
<br>For example, you can stop all torrents in your session directory with
<br>just: ?overFilesIn "rtorrent/session/dir" stopTorrent?
<br>
<br>The way it works is by parsing the session files, modifying the
<br>resulting data type and serialising it back into the file. I did not do
<br>optimisation but I had no problem with test sample of 100,000 files.
<br>
<br>I need to add IOException handling and maybe extra utility functions but
<br>otherwise I consider the library finished.
<br>
<br>Thanks
<br>--  
<br>Mateusz K.
<br>
<br>
<br>------------------------------
<br>
<br>Message: 7
<br>Date: Thu, 7 Aug 2014 15:39:53 -0700
<br>From: John Lato <jwlato@gmail.com>
<br>To: Kyle Hanson <me@khanson.io>
<br>Cc: haskell-cafe <haskell-cafe@haskell.org>
<br>Subject: Re: [Haskell-cafe] Performance of StateT and best practices
<br>      for     debugging
<br>Message-ID:
<br>      <CAJ727GjPpMn3xMDs=4EmJGG0FpndsBwvq5Zkc97X6yQ-H21KEA@mail.gmail.com>
<br>Content-Type: text/plain; charset="utf-8"
<br>
<br>I haven't looked very closely, but I'm suspicious of this code from
<br>"instance Block Piece"
<br>
<br>  ListLike l -> forM l (\obj -> ...)
<br>                    >>= (return . mconcat)
<br>
<br>The "forM" means that "l" will be traversed once and create an output list,
<br>which will then be mconcat'd together.  The list has to be created because
<br>of the monadic structure imposed by forM, but if the result of the mconcat
<br>isn't demanded right away it will be retained as a thunk that references
<br>the newly-created list.
<br>
<br>I'd suggest that you replace it with something like
<br>
<br>  ListLike l -> foldM (\(!acc) obj -> ... >>= return . mappend acc) mempty l
<br>
<br>Here I've justed added a bang pattern to the accumulator.  If whatever is
<br>being returned has some lazy fields, you may want to change that to use
<br>deepseq instead of a bang pattern.
<br>
<br>Also, "foo >>= return . bar" is often regarded as a bit of a code smell, it
<br>can be replaced with "bar <$> foo" or "bar `liftM` foo", or sometimes
<br>something even simpler depending on circumstances (but IMHO sometimes it's
<br>more clear to just leave it alone).
<br>
<br>The heap profile does look like a space leak.  The line
<br>
<br> <StrappedTemplates-0.1.1.0:Text.Strapped.Render.sat_sc1z>
<br>
<br>is a thunk (you can tell because it's in '<>' brackets), so whatever is
<br>referencing that is not strict enough.  Sometimes another heap profile
<br>report, e.g. "-hc" or maybe "-hy" will give more useful information that
<br>lets you identify what exactly "sat_sc1z" is.  You could also try compiling
<br>with -ddump-stg, which will dump the intermediate STG output which usually
<br>shows those names.  But then you'll probably also need to re-run the
<br>profile, since the names change between compilations.  Also IIRC some of
<br>values aren't named until the cmm phase, but that's harder to map back to
<br>Haskell so if you can identify the code from stg it's simpler.
<br>
<br>If you haven't seen
<br>http://blog.ezyang.com/2011/06/pinpointing-space-leaks-in-big-programs/,
<br>I'd highly recommend it if you need to track down a space leak.
<br>
<br>John L.
<br>
<br>
<br>
<br>On Thu, Aug 7, 2014 at 10:57 AM, Kyle Hanson <me@khanson.io> wrote:
<br>
<br>> Hello,
<br>>
<br>> I was looking at cleaning up my refactoring a core loop of template
<br>> rendering to go from a loop with many parameters
<br>>
<br>> loop :: RenderConfig -> BlockMap -> InputBucket m -> Builder -> [Pieces]
<br>> -> ExceptT StrapError m Builder
<br>>
<br>> to a looped state monad transformer
<br>>
<br>> loop :: [Pieces] -> RenderT m Builder
<br>>
<br>> newtype RenderT m a = RenderT
<br>>   { runRenderT :: ExceptT StrapError (StateT (RenderState m) m) a
<br>>   } deriving ( Functor, Applicative, Monad, MonadIO )
<br>>
<br>> data RenderState m = RenderState
<br>>   { position     :: SourcePos
<br>>   , renderConfig :: RenderConfig
<br>>   , blocks       :: BlockMap
<br>>   , bucket       :: InputBucket m
<br>>   }
<br>>
<br>> however, there is a big slow down (about 6-10x) using a StateT. I think it
<br>> might have something to do with laziness but I am not exactly sure of where
<br>> to begin in tracking it down. Swapping out the Lazy State to a Strict State
<br>> helps a little (only a 5x slow down)
<br>>
<br>> You can find some of the processing code here:
<br>>
<br>>
<br>> https://github.com/hansonkd/StrappedTemplates/blob/321a88168d54943fc217553c873f188797c0d4f5/src/Text/Strapped/Render.hs#L189
<br>>
<br>> With my old loop commented out.
<br>>
<br>> Its messy right now since I am just trying a number of different
<br>> approaches. I did some more work factoring out the lifts, trying different
<br>> iterations of foldlM and stuff but that didn't have that much of an effect
<br>> on performance.
<br>>
<br>> After profiling I see in the StateT, the report has a lot more CAFs and
<br>> garbage collecting.
<br>>
<br>> Here is the profiling report from my original version w/o StateT
<br>> http://lpaste.net/108995
<br>>
<br>> Slow version with StateT
<br>> http://lpaste.net/108997
<br>>
<br>> Here is the "makeBucket" function that is referenced (it is the same in
<br>> both state and nonstate):
<br>>
<br>>
<br>> https://github.com/hansonkd/StrappedTemplates/blob/321a88168d54943fc217553c873f188797c0d4f5/examples/big_example.hs#L24
<br>>
<br>> Looking at stacked overflow and the official docs I have gotten an idea of
<br>> what is going on. The heaps generated between them tells me that a lot more
<br>> memory is being allocated to lists. These heaps were generated running my
<br>> render function against a template with nested loops and a list of elements.
<br>>
<br>> http://imgur.com/a/2jOIf
<br>>
<br>> I am hoping that maybe someone could give me a hint at what to look at
<br>> next. I've played around with Strictness and refactoring loops to no avail
<br>> and now am kind of stuck. Any help would be appreciated.
<br>>
<br>> --
<br>> Kyle Hanson
<br>>
<br>> _______________________________________________
<br>> Haskell-Cafe mailing list
<br>> Haskell-Cafe@haskell.org
<br>> http://www.haskell.org/mailman/listinfo/haskell-cafe
<br>>
<br>>
<br>-------------- next part --------------
<br>An HTML attachment was scrubbed...
<br>URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140807/b4c26366/attachment-0001.html>
<br>
<br>------------------------------
<br>
<br>Message: 8
<br>Date: Fri, 8 Aug 2014 11:24:29 +0800
<br>From: jun zhang <zhangjun.julian@gmail.com>
<br>To: haskell-cafe@haskell.org
<br>Subject: [Haskell-cafe] How to improve the zipwith's performance
<br>Message-ID:
<br>      <CAGjcJLcT0FAmNxFLbdaZZfMFg5aEL1rZDPEWOpRxvsKJsau3ew@mail.gmail.com>
<br>Content-Type: text/plain; charset="utf-8"
<br>
<br>Dear All
<br>
<br>I write a code for Clustering with Data.Clustering.Hierarchical, but it's
<br>slow.
<br>
<br>I use the profiling and change some code, but I don't know why zipwith take
<br>so many time? (even I change list to vector)
<br>
<br>My code is as blow, Any one kindly give me some advices.
<br>======================
<br>main = do
<br>    ....
<br>    let cluster = dendrogram  SingleLinkage vectorList getVectorDistance
<br>    ....
<br>
<br>getExp2 v1 v2 = d*d
<br>    where
<br>        d = v1 - v2
<br>
<br>getExp v1 v2
<br>    | v1 == v2 = 0
<br>    | otherwise = getExp2 v1 v2
<br>
<br>tfoldl  d = DV.foldl1' (+) d
<br>
<br>changeDataType:: Int -> Double
<br>changeDataType d = fromIntegral d
<br>
<br>getVectorDistance::(a,DV.Vector Int)->(a, DV.Vector Int )->Double
<br>getVectorDistance v1 v2 = fromIntegral $ tfoldl dat
<br>    where
<br>        l1 = snd v1
<br>        l2 = snd v2
<br>        dat = DV.zipWith getExp l1 l2
<br>
<br>=======================================
<br>
<br>build with ghc -prof -fprof-auto -rtsopts -O2 log_cluster.hs
<br>
<br>run with  log_cluster.exe +RTS -p
<br>
<br>profiling result is
<br>
<br> log_cluster.exe +RTS -p -RTS
<br>
<br>    total time  =        8.43 secs   (8433 ticks @ 1000 us, 1 processor)
<br>    total alloc = 1,614,252,224 bytes  (excludes profiling overheads)
<br>
<br>COST CENTRE            MODULE  %time %alloc
<br>
<br>getVectorDistance.dat  Main     49.4   37.8
<br>tfoldl                 Main      5.7    0.0
<br>getExp                 Main      4.5    0.0
<br>getExp2                Main      0.5    1.5
<br>-------------- next part --------------
<br>An HTML attachment was scrubbed...
<br>URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140808/d29aa298/attachment-0001.html>
<br>
<br>------------------------------
<br>
<br>Message: 9
<br>Date: Fri, 08 Aug 2014 06:31:49 +0200
<br>From: Bardur Arantsson <spam@scientician.net>
<br>To: haskell-cafe@haskell.org
<br>Subject: Re: [Haskell-cafe] Performance of StateT and best practices
<br>      for     debugging
<br>Message-ID: <ls1jrl$7gp$1@ger.gmane.org>
<br>Content-Type: text/plain; charset=utf-8
<br>
<br>On 2014-08-07 19:57, Kyle Hanson wrote:
<br>> Hello,
<br>>  
<br>> Here is the "makeBucket" function that is referenced (it is the same in
<br>> both state and nonstate):
<br>>  
<br>> https://github.com/hansonkd/StrappedTemplates/blob/321a88168d54943fc217553c873f188797c0d4f5/examples/big_example.hs#L24
<br>>  
<br>
<br>Just a shot in the dark, but I notice that you're using "modify" and not
<br>"modify'" which was added in a recent version of transformers.
<br>
<br>Strict.StateT is not always "strict enough" and you may need to use modify'.
<br>
<br>At any rate, it's worth a shot, I think.
<br>
<br>Regards,
<br>
<br>
<br>
<br>
<br>------------------------------
<br>
<br>Message: 10
<br>Date: Thu, 7 Aug 2014 22:30:25 -0700
<br>From: Jan Paul Posma <me@janpaulposma.nl>
<br>To: haskell-cafe@haskell.org
<br>Subject: [Haskell-cafe] Visualising Haskell function execution
<br>Message-ID:
<br>      <CAPtY9n+6onYBYb=pWP4NRmLq43zY6MGXQMuhmp2HfnUzhuOiyA@mail.gmail.com>
<br>Content-Type: text/plain; charset="utf-8"
<br>
<br>Hey all,
<br>
<br>Last weekend my friend Steve and I did a small project for visualising
<br>Haskell function execution in the browser. It's meant to be used in
<br>education, and uses a tiny custom parser. I figured it could be of interest
<br>for anyone here learning or teaching Haskell:
<br>https://stevekrouse.github.io/hs.js/
<br>
<br>To see it in action, scroll a bit down to the red bordered box, and click
<br>on "map", and then keep clicking on each new line.
<br>
<br>I hope it can be useful to someone.
<br>
<br>Cheers, JP
<br>-------------- next part --------------
<br>An HTML attachment was scrubbed...
<br>URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140807/3c4dabe9/attachment-0001.html>
<br>
<br>------------------------------
<br>
<br>Message: 11
<br>Date: Thu, 7 Aug 2014 23:56:43 -0700
<br>From: John Lato <jwlato@gmail.com>
<br>To: Bardur Arantsson <spam@scientician.net>
<br>Cc: haskell-cafe <haskell-cafe@haskell.org>
<br>Subject: Re: [Haskell-cafe] Performance of StateT and best practices
<br>      for     debugging
<br>Message-ID:
<br>      <CAJ727GipLL12TXfrMBeLJBX2_GdoD0W-CKJd4U1cu48CvnkrBg@mail.gmail.com>
<br>Content-Type: text/plain; charset="utf-8"
<br>
<br>On Thu, Aug 7, 2014 at 9:31 PM, Bardur Arantsson <spam@scientician.net>
<br>wrote:
<br>
<br>> On 2014-08-07 19:57, Kyle Hanson wrote:
<br>> > Hello,
<br>> >
<br>> > Here is the "makeBucket" function that is referenced (it is the same in
<br>> > both state and nonstate):
<br>> >
<br>> >
<br>> https://github.com/hansonkd/StrappedTemplates/blob/321a88168d54943fc217553c873f188797c0d4f5/examples/big_example.hs#L24
<br>> >
<br>>
<br>> Just a shot in the dark, but I notice that you're using "modify" and not
<br>> "modify'" which was added in a recent version of transformers.
<br>>
<br>> Strict.StateT is not always "strict enough" and you may need to use
<br>> modify'.
<br>>
<br>> At any rate, it's worth a shot, I think.
<br>>
<br>
<br>Good point.  I think that even modify' will not be strict enough without
<br>adding strictness to RenderState as well.
<br>
<br>John L.
<br>-------------- next part --------------
<br>An HTML attachment was scrubbed...
<br>URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140807/ce617687/attachment-0001.html>
<br>
<br>------------------------------
<br>
<br>Subject: Digest Footer
<br>
<br>_______________________________________________
<br>Haskell-Cafe mailing list
<br>Haskell-Cafe@haskell.org
<br>http://www.haskell.org/mailman/listinfo/haskell-cafe
<br>
<br>
<br>------------------------------
<br>
<br>End of Haskell-Cafe Digest, Vol 132, Issue 11
<br>*********************************************
<br></div></div></span></blockquote></body></html>