[Haskell-cafe] Question on proper use of Data.IORef

2012-06-22 Thread Captain Freako
Hi experts, I fear I don't understand how to properly use *Data.IORef*. I wrote the following code: 1 -- Testing Data.IORef 2 module Main where 3 4 import Data.IORef 5 6 bump :: IORef Int -> IO() 7 bump theRef = do 8 tmp <- readIORef theRef 9 let tmp2 = tmp + 1 10

Re: [Haskell-cafe] Question on proper use of Data.IORef

2012-06-22 Thread Captain Freako
hat structure, which is being passed back to me, by the higher level C function that is calling me?* Thanks, all! -db On Fri, Jun 22, 2012 at 8:43 AM, Max Rabkin wrote: > On Fri, Jun 22, 2012 at 5:30 PM, Captain Freako > wrote: > > 12 main = do > > 13 let theValue = 1 >

[Haskell-cafe] Request for optimizing help.

2012-06-24 Thread Captain Freako
Does anyone have any advice for optimizing the code, below? Currently, the profiling results look like this: COST CENTREMODULE %time %alloc runFilter Filter90.9 41.0 convT Filter 9.1

[Haskell-cafe] Getting a segmentation fault when starting/stopping the RTS, from C, several times.

2012-07-10 Thread Captain Freako
Hi experts, Should I expect the following C code to run to completion, or am I trying to do something that was never intended? Thanks, -db C code: 1 #include 2 #include 3 #include "HsFFI.h" 4 5 int main() 6 { 7 int argc = 1, i; 8 char* argv[] = {"ghcDll", NULL}; // arg

[Haskell-cafe] Request for help with shared object link failure, involving relocation and -fPIC.

2013-04-24 Thread Captain Freako
Can anyone help me solve this link failure? ghc -o libami.so -shared -package parsec -lHSrts -lm -lffi -lrt AMIParse.o AMIModel.o ami_model.o ExmplUsrModel.o Filter.o /usr/bin/ld: /usr/lib/ghc-7.4.2/libHSrts.a(RtsAPI.o): relocation R_X86_64_32S against `ghczmprim_GHCziTypes_Czh_con_info' can not b

[Haskell-cafe] Why the `-ghc7.4.2' suffix on *.SO base names?

2013-04-25 Thread Captain Freako
In trying to compile a 2 year old, previously working project on a new machine with a fresh Haskell Platform installation, I bumped into this: ghc -o libami.so -shared -package parsec -lHSrts -lm -lffi -lrt AMIParse.o AMIModel.o ami_model.o ExmplUsrModel.o Filter.o /usr/bin/ld: /usr/lib/ghc-7.4.2/

[Haskell-cafe] Request for help: Recompile of ghc producing "...-ghc7.4.2.so"s, which break project builds.

2013-04-27 Thread Captain Freako
Recently, I had to recompile ghc, in order to get the "-dyn" versions of the standard libraries installed. (The standard Ubuntu 12.10 64-bit Linux distribution doesn't include them in its "haskell-platform" package, and you can't upgrade "base" using the normal "cabal iinstall" approach, from what

Re: [Haskell-cafe] Undefined symbol error coming from shared, dynamic library.

2011-09-08 Thread Captain Freako
So, did the problem go away after you updated those packages ? On Sep 8, 2011 2:36 AM, "Sergiy Nazarenko" wrote: > Hi David! > > I've got same problem. As I see that happens before I've updated > following packages. I needed it because I compile ghc702. > mtl > transformers > regex-base > regex-co

Re: [Haskell-cafe] Undefined symbol error coming from shared, dynamic library.

2011-09-11 Thread Captain Freako
Sergiy, Tom, Thanks for your replies. Sergiy, I was able to get this working without having to recompile my installed Haskell libraries. Tom, you were correct; I needed to explicitly link against the Haskell run-time system, as well as a few other things: I changed my ghc link options from this

Re: [Haskell-cafe] Undefined symbol error coming from shared, dynamic library.

2011-09-14 Thread Captain Freako
static library to solve my problem. And I'm > looking for how to build static library, but no luck. > > Cheers, > Sergiy > > On 11 September 2011 17:56, Captain Freako wrote: > > Sergiy, Tom, > > > > Thanks for your replies. > > > > Sergiy

[Haskell-cafe] poles/residues -> FIR tap weights ?

2011-09-21 Thread Captain Freako
Anyone know of a Haskell package containing a function for converting a list of pole/residue pairs into FIR filter tap weights? Thanks, -db ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Question on definition of `parse' function in Parsec library.

2011-10-08 Thread Captain Freako
Hi all, In this definition from the Parsec library: parse :: (Stream s Identity t) => Parsec s () a -> SourceName -> s -> Either ParseError aparse p = runP p () what's the significance of `Identity t'? (`t' isn't used anywhere.) Thanks, -db ___ H

[Haskell-cafe] Trouble using State Monad.

2011-10-08 Thread Captain Freako
Hi all, I'm trying to use the State Monad to help implement a digital filter: 17 newtype Filter e a = F { 18 runFilter :: a -> EitherT e (State FilterState) a 19 } deriving (Monad, MonadState FilterState) but I'm getting these compiler errors: Filter.hs:19:14: Can't make a derived

Re: [Haskell-cafe] Trouble using State Monad.

2011-10-09 Thread Captain Freako
. Thanks, -db On Sat, Oct 8, 2011 at 5:27 PM, David Barbour wrote: > > > On Sat, Oct 8, 2011 at 4:28 PM, Captain Freako wrote: > >> >> 17 newtype Filter e a = F { >> * 18 runFilter :: EitherT e (State FilterState) a >> ** * 19 } deriving (Monad, Mon

[Haskell-cafe] Arrow based re-definition of `StateT' included in `Control.Arrow.'?

2011-10-11 Thread Captain Freako
Hi all, Is the Arrow-based re-definition of `StateT' included somewhere in the `Control.Arrow.' stack, or do you put the code into your program explicitly? Thanks, -db ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman

[Haskell-cafe] Question, re: using Automaton

2011-10-15 Thread Captain Freako
Hi all, In this excerpt from the Automatonpage: runAutomaton :: (ArrowLoopCa,

[Haskell-cafe] How to wrap a StateArrow in an Automaton?

2011-10-16 Thread Captain Freako
HI all, How do you wrap a StateArrow in an Automaton? Thanks, -db ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Question on `runState'

2011-10-17 Thread Captain Freako
In this excerpt from the `StateArrow' page: runState :: Arrowa => StateArrows a *e*

[Haskell-cafe] How to implement a digital filter, using Arrows?

2011-10-17 Thread Captain Freako
Hi all, If I have a pure function, which maps `(input, initialState)' to `(output, nextState)', what's the most succinct way of constructing a digital filter from this function, using Arrows? Thanks, -db ___ Haskell-Cafe mailing list Haskell-Cafe@haskel

Re: [Haskell-cafe] How to implement a digital filter, using Arrows?

2011-10-18 Thread Captain Freako
Hi John, Thanks for this reply: > Date: Tue, 18 Oct 2011 14:05:22 +1030 > From: John Lask > Subject: Re: [Haskell-cafe] How to implement a digital filter, using >Arrows? > To: haskell-cafe@haskell.org > Message-ID: smtp384394452fd2750fbe3bcfcc6...@phx.gbl> > Content-Type: text/plain; cha

Re: [Haskell-cafe] How to implement a digital filter, using Arrows?

2011-10-19 Thread Captain Freako
John Lask wrote: >This is literate code. It expounds on your initial question and provides >two solutions based either on the StateArrow or Automaton >(Remainder omitted.) John, Thanks so much for your help! I'm going to study your example code and try to understand how the Automaton implici

Re: [Haskell-cafe] How to implement a digital filter, using Arrows?

2011-10-19 Thread Captain Freako
m `runAuto'? Thanks, -db On Wed, Oct 19, 2011 at 3:02 PM, John Lask wrote: > On 20/10/2011 5:11 AM, Captain Freako wrote: > > for your use case then, the StateArrow seems more appropriate as it provides > you with the final state. Ofcourse the Automaton arrow could also be used:

Re: [Haskell-cafe] How to implement a digital filter, using Arrows?

2011-10-19 Thread Captain Freako
; On 20/10/2011 5:11 AM, Captain Freako wrote: > > for your use case then, the StateArrow seems more appropriate as it provides > you with the final state. Ofcourse the Automaton arrow could also be used: > >> liftAu' f s0 = proc x -> do >>    rec (y,s') <- arr

Re: [Haskell-cafe] How to implement a digital filter, using Arrows?

2011-10-20 Thread Captain Freako
Hi David, I was referring to the `f' in the `runAuto' function, not the `liftAu' function. -db On Wed, Oct 19, 2011 at 8:53 PM, David Barbour wrote: > On Wed, Oct 19, 2011 at 8:07 PM, Captain Freako > wrote: >> >> One more question on the `runAuto' code

[Haskell-cafe] List archives searchable?

2011-10-25 Thread Captain Freako
Are the archives of this list searchable? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Really impossible to reinstall `base' using cabal?

2011-10-25 Thread Captain Freako
In response to this: dbanas@dbanas-eeepc:~$ cabal install arrows Resolving dependencies... Configuring lazysmallcheck-0.6... Preprocessing library lazysmallcheck-0.6... Building lazysmallcheck-0.6... [1 of 1] Compiling Test.LazySmallCheck ( Test/LazySmallCheck.hs, dist/build/Test/LazySmallCheck.o

Re: [Haskell-cafe] Really impossible to reinstall `base' using cabal?

2011-10-25 Thread Captain Freako
ons of the `base' package libraries installed, if not via a `cabal install'? Thanks, -db On Tue, Oct 25, 2011 at 1:45 PM, Daniel Fischer wrote: > On Tuesday 25 October 2011, 22:32:23, Captain Freako wrote: >> dbanas@dbanas-eeepc:~$ cabal install base >> >> and got

Re: [Haskell-cafe] Really impossible to reinstall `base' using cabal?

2011-10-27 Thread Captain Freako
Thanks, Daniel. That was it. On Tue, Oct 25, 2011 at 5:15 PM, Daniel Fischer wrote: > On Wednesday 26 October 2011, 02:00:49, Captain Freako wrote: >> So, do you have any advice for me, with regard to solving this issue: >> >> Implicit import declaration: >>    Cou

[Haskell-cafe] Trouble defining `instance Arrow SF'

2011-10-27 Thread Captain Freako
In trying to follow along with `Programming with Arrows' by John Hughes, I'm entering the following code: 1 -- Taken from `Programming with Arrows'. 2 3 module SF where 4 5 import Control.Arrow 6 7 newtype SF a b = SF {runSF :: [a] -> [b]} 8 9 instance Arrow SF where 10 arr

Re: [Haskell-cafe] Trouble defining `instance Arrow SF'

2011-10-27 Thread Captain Freako
es loaded: none. Any thoughts? Thanks, -db On Thu, Oct 27, 2011 at 8:29 AM, David Barbour wrote: > > On Thu, Oct 27, 2011 at 5:55 AM, Captain Freako > wrote: >> >> SF.hs:11:10: `>>>' is not a (visible) method of class `Arrow' >> Failed, modules load

Re: [Haskell-cafe] How to implement digital filters using Arrows

2011-10-31 Thread Captain Freako
Hi John, Thanks for all your help. I've been studying your suggested code: > type FilterAu b c = Automaton (->) b c > liftAu :: ((x,FilterState s)->(y,FilterState s)) -> FilterState s -> FilterAu x y > liftAu f s0 = proc x -> do >rec (y,s') <- arr f -< (x,s) >s <- delay s0 -< s'

[Haskell-cafe] Figures 6 and 7 from `Programming with Arrows'?

2011-10-31 Thread Captain Freako
Does anyone have figures 6 and 7, as well as the intervening unnumbered figure, from `Programming with Arrows'? Thanks, -db ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] How to implement digital filters using Arrows

2011-11-01 Thread Captain Freako
On Mon, Oct 31, 2011 at 3:19 PM, John Lask wrote: > On 1/11/2011 1:35 AM, Captain Freako wrote: > > you need to study ArrowLoop and understand that. Thanks, John. I'm working my way through Hughes' suggested exercise in `Programming with Arrows', to wit: "The r

Re: [Haskell-cafe] How to implement digital filters using Arrows

2011-11-01 Thread Captain Freako
: Stopped at SF.hs:23:13-42 _result :: [a] = _ [SF.hs:23:13-42] *SF> : Stopped at SF.hs:23:30-42 _result :: [a] = _ x :: a = _ xs :: [a] = _ [SF.hs:23:30-42] *SF> : (Pattern repeats.) Do you have any advice? Thanks, -db On Mon, Oct 31, 2011 at 3:19 PM, John Lask wrote: > On 1/11/2