Re: [Haskell-cafe] Fwd: GHC as a library error.

2011-10-18 Thread JP Moresmau
The release notes say: The type of defaultErrorHandler has changed.
In particular, this means that you will normally want to pass it
defaultLogAction instead of defaultDynFlags.
(http://www.haskell.org/ghc/docs/7.2.1/html/users_guide/release-7-2-1.html).
defaultLogAction is in the DynFlags module, reexported by GHC. I
haven't tried it yet, though.
Unfortunately the documentation about using GHC as an API is often not
up to date. Even the API documentation is wrong: for example, the
documentation for the load function talks about a
reportModuleCompilationResult callback that doesn't exist any more,
and the release notes do not explain the changes to the load function
(loadWithLogger gone, etc).
You can look at the projects using the GHC API for inspiration, for
example the Scion library.

JP

On Tue, Oct 18, 2011 at 12:34 AM, Paulo Pocinho poci...@gmail.com wrote:
 Forwarding to Haskell-Cafe:
 I'm trying GHC as a library, as documented in:

 http://www.haskell.org/haskellwiki/GHC/As_a_library
 http://www.haskell.org/ghc/docs/7.2.1/html/users_guide/ghc-as-a-library.html

 However, this code:

 import GHC
 import GHC.Paths ( libdir )
 import DynFlags ( defaultDynFlags )

 main =
    defaultErrorHandler defaultDynFlags $ do
      runGhc (Just libdir) $ do
        dflags - getSessionDynFlags
        setSessionDynFlags dflags
        target - guessTarget test_main.hs Nothing
        setTargets [target]
        load LoadAllTargets


 Produces:

 Couldn't match expected type `Severity'
            with actual type `DynFlags.Settings'
 Expected type: DynFlags.LogAction
  Actual type: DynFlags.Settings - DynFlags
 In the first argument of `defaultErrorHandler', namely
  `defaultDynFlags'
 In the expression: defaultErrorHandler defaultDynFlags


 How can I fix it?

 Note: this was on a fresh install with latest stable GHC installer 7.2.1.

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




-- 
JP Moresmau
http://jpmoresmau.blogspot.com/

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


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-18 Thread Vincent Hanquez

On 10/18/2011 01:30 AM, Conrad Parker wrote:

And I often work with mixed text/binary data (eg. text annotations in
video streams). I'd want the Show/Read instances to be in the form of
a hexdump with char representation alongside (like xxd or od -xc
output). It roundtrips well, so why not? :-)

(slightly out of topic ...)

I often do mixed text/binary too, and i now use the following package:
http://hackage.haskell.org/package/bytedump

The problem with a Show instance is that there's no way to configure some 
aspects of it :-)


--
Vincent

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


Re: [Haskell-cafe] About the ConstraintKinds extension

2011-10-18 Thread Max Bolingbroke
On 18 October 2011 02:17, bob zhang bobzhang1...@gmail.com wrote:
      But I found a problem which I thought would be made better, plz correct
 me if I am wrong

For those who only subscribe to Haskell-Cafe, Bob posted a very
similar thread to ghc-users, which I replied to here with a suggestion
for how we could relax the superclass-cycle check:

http://thread.gmane.org/gmane.comp.lang.haskell.glasgow.user/20828/focus=20829

Max

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


Re: [Haskell-cafe] Waiting on input with `hWaitForInput' or `threadWaitRead'

2011-10-18 Thread Gregory Collins
On Tue, Oct 18, 2011 at 3:18 AM, Jason Dusek jason.du...@gmail.com wrote:
 The lazy bridging code, `lazyBridge', blocks (unsurprisingly)
 and does not allow packets to go back and forth. I think I need
 explicit selects/waits here to get the back and forth traffic.
 Maybe there is a some way to leverage GHC's internal async I/O
 but I'm not sure how to do it.

Maybe: forkIO two threads, one for the read end, one for the write
end? I would use a loop over lazy I/O, also.

G
-- 
Gregory Collins g...@gregorycollins.net

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


Re: [Haskell-cafe] Fwd: GHC as a library error.

2011-10-18 Thread Paulo Pocinho
Thank you for the heads up; didn't know about the Scion library.

Cheers!

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


Re: [Haskell-cafe] Waiting on input with `hWaitForInput' or `threadWaitRead'

2011-10-18 Thread Ertugrul Soeylemez
Jason Dusek jason.du...@gmail.com wrote:

  I don't think you want either of the functions you mentioned.  What
  you probably want instead is to do concurrent programming by
  creating Haskell threads.  A hundred Haskell threads reading from
  Handles are translated to one or more OS threads using whatever
  polling mechanism (select(), poll(), epoll) your operating system
  supports.
 
  I have uploaded a simple concurrent echo server implementation to
  hpaste [1]. It uses one thread for the stdout logger, one thread for
  the server, one thread for each client and finally a main thread
  waiting for you to hit enter to quit the application.
 
  [1] http://hpaste.org/52742 - Concurrent echo server with logger

 I am not sure how to apply the principle you mention to a proxy, which
 must read from and write to both handles in turn (or, ideally, as
 needed).

A proxy server acts a lot like an echo server.  The difference is that
usually before the actual proxying starts you have a negotiation phase,
and instead of echoing back to the same socket, you just write it to a
different one.  Here is an (untested) example:

(clientH, clientHost, clientPort) - accept serverSock
destH - negotiate clientH
doneVar - newEmptyMVar

forkIO (hGetContents clientH = hPutStr destH = putMVar doneVar)
forkIO (hGetContents destH = hPutStr clientH = putMVar doneVar)
replicateM_ 2 (takeMVar doneVar)
mapM_ hClose [clientH, destH]

Of course this code is going to bite you in production for two reasons:
First of all it has no error handling.  If the 'negotiate' function
throws an exception, then nobody will close the client handle.  So view
this is a highly simplified example!

The second reason is that in this lazy I/O framework it is
extraordinarily difficult to write the 'negotiate' function in the first
place, unless you allow yourself to put stuff back into the handle or
process only one byte at a time.  Both options are bad.  A better option
is to use a proper I/O abstraction suitable for protocol processing.
Iteratees [1] come to mind.  They solve this problem elegantly and let
you really just use the parser style destH - negotiate.

My usage of the MVar is actually kind of an abuse.  I just use it to
allow the two forwarder threads to signal their completion.  The main
thread just waits for the two to complete and then closes both handles.
The word abuse is perhaps too strong, because there is essentially
nothing wrong with the approach.  The standard concurrency library
doesn't provide an event primitive, so the more general MVar is often
used for this.

[1] http://www.yesodweb.com/book/enumerator


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/



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


Re: [Haskell-cafe] Waiting on input with `hWaitForInput' or `threadWaitRead'

2011-10-18 Thread Ertugrul Soeylemez
Michael Orlitzky mich...@orlitzky.com wrote:

  I have uploaded a simple concurrent echo server implementation to
  hpaste [1].  It uses one thread for the stdout logger, one thread
  for the server, one thread for each client and finally a main thread
  waiting for you to hit enter to quit the application.
 
  [1] http://hpaste.org/52742 - Concurrent echo server with logger

 This is a good example; you should stick it on the wiki somewhere so
 it isn't lost.

It is a good example for concurrent programming, but not a good example
for server programming.  By putting it into the wiki I would discourage
some programmers from using more suitable I/O abstractions/mechanisms.

Better let's keep it away from the wiki.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/



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


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-18 Thread Christian Maeder

Am 12.10.2011 16:02, schrieb Bas van Dijk:

API DOCS

http://hackage.haskell.org/package/vector-bytestring-0.0.0.0


you could re-export VS.empty, VS.singleton, etc. directly.

Cheers Christian


-- | /O(1)/ The empty 'ByteString'
empty :: ByteString
empty = VS.empty
{-# INLINE empty #-}

-- | /O(1)/ Convert a 'Word8' into a 'ByteString'
singleton :: Word8 - ByteString
singleton = VS.singleton
{-# INLINE [1] singleton #-} -- Inline [1] for intercalate rule

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


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-18 Thread Roel van Dijk
2011/10/18 Christian Maeder christian.mae...@dfki.de:
 you could re-export VS.empty, VS.singleton, etc. directly.

The vector singleton and the vector-bytestring singleton don't have
the same type.

vector:
 singleton :: a - Vector a

vector-bytestring:
 singleton :: Word8 - Vector Word8

By choosing the more general type you risk that a previously correct
program becomes ambiguous. (When migrating from bytestring to
vector-bytestring).

I'm not sure if this will actually occur in practive or that it holds
for all the little functions that you could theoretically re-export
directly. Maybe we create an example program which would fail with the
more general type. Proving the opposite (that the more general type is
always safe) will be more difficult.

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


[Haskell-cafe] hello Haskell

2011-10-18 Thread R J
hey Haskell check it out http://www.fastnews10i.com

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


Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-18 Thread Roel van Dijk
2011/10/18 Roel van Dijk vandijk.r...@gmail.com:
 Maybe we [can] create an example program which would fail with the
 more general type.

Migrating the function foo from bytestring to vector-bytestring
would fail with more general types:

 import Data.ByteString
 foo = print empty
Ok, modules loaded: Test.

With vector:
 import Data.Vector.Storable
 foo = print empty
Ambiguous type variable `a0' in the constraints:
  (Show a0) arising from a use of `print'
at /home/roelvandijk/development/test.hs:5:7-11
  (Storable a0) arising from a use of `empty'
at /home/roelvandijk/development/test.hs:5:13-17
Probable fix: add a type signature that fixes these type variable(s)
In the expression: print empty
In an equation for `foo': foo = print empty
Failed, modules loaded: none.

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


[Haskell-cafe] Working with the code For Typing Haskell In Haskell

2011-10-18 Thread Patrick LeBoutillier
Hi all,

I'm working with the code that accompanies this paper
(http://web.cecs.pdx.edu/~mpj/thih/) and I'm trying to use it
but I can't figure out how to get started. I have the following code
but it is not giving me the expected result:

import TypingHaskellInHaskell

mapt = map :: Forall [Star, Star]
([] :=
 ((TGen 0 `fn` TGen 1) `fn` TAp tList (TGen 0) `fn` TAp
tList (TGen 1)))

idt = id :: Forall [Star]
([] :=
 (TGen 0 `fn` TGen 0))

exprt = Ap (Const mapt) (Const idt)

test = runTI $ tiExpr initialEnv [] exprt


When I execute the test function above in ghci I get:

([],TVar (Tyvar v3 Star)).

I was expecting someting like below for the type part:

TAp tList (TGen 0) `fn` TAp tList (TGen 0)


What I want is the library to compute for me the type of map id.
What is the proper way to achieve this? Has anybody on the list worked
with this code before?

Thanks as lot,

Patrick
-- 
=
Patrick LeBoutillier
Rosemère, Québec, Canada

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


[Haskell-cafe] Comparison Haskell, Java, C and LISP

2011-10-18 Thread yrazes
Hi,

Maybe you remember my case.
I was trying to compare some aspects of these languages.
Well... I found that I can compare reflection, support for generics,
simplicity and safe code.
I just want to ask if you have more information for reflection in Haskell.
I read that there is no enough for dynamics to support complete reflection.
I hope someone can help me this time :)

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


Re: [Haskell-cafe] hello Haskell

2011-10-18 Thread Gregory Collins
On Tue, Oct 18, 2011 at 9:23 AM, R J rj248...@hotmail.com wrote:
 hey Haskell check it out http://www.fastnews10i.com

OK, who has the ban hammer?

G
-- 
Gregory Collins g...@gregorycollins.net

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


Re: [Haskell-cafe] Comparison Haskell, Java, C and LISP

2011-10-18 Thread Stephen Tetley
Haskell has no support for reflection whatsoever.

It can support compile time meta-programming with Template Haskell.

Reflection itself might be antagonistic to functional programming, I
suspect it is at odds with referential transparency. Most of the work
on reflection seemed based around Lisp / Scheme - Christian Queinnec's
reflective interpreter in Lisp in Small Pieces uses an awful lot of
set! 

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


Re: [Haskell-cafe] Waiting on input with `hWaitForInput' or `threadWaitRead'

2011-10-18 Thread Jason Dusek
2011/10/18 Ertugrul Soeylemez e...@ertes.de:
 A proxy server acts a lot like an echo server.  The difference is that
 usually before the actual proxying starts you have a negotiation phase,
 and instead of echoing back to the same socket, you just write it to a
 different one.  Here is an (untested) example:

    (clientH, clientHost, clientPort) - accept serverSock
    destH - negotiate clientH
    doneVar - newEmptyMVar

    forkIO (hGetContents clientH = hPutStr destH = putMVar doneVar)
    forkIO (hGetContents destH = hPutStr clientH = putMVar doneVar)
    replicateM_ 2 (takeMVar doneVar)
    mapM_ hClose [clientH, destH]

This code seems like it says:

  Allow the client to write to the server one time.

  Allow the server to write to the client one time.

  Teardown both sides of the connection.

Am I reading this correctly? This is, indeed, a proxy; but I'm
not sure it could support a wide range of protocols.

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments

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


Re: [Haskell-cafe] Waiting on input with `hWaitForInput' or `threadWaitRead'

2011-10-18 Thread Jason Dusek
2011/10/18 Gregory Collins g...@gregorycollins.net:
 On Tue, Oct 18, 2011 at 3:18 AM, Jason Dusek jason.du...@gmail.com wrote:
  The lazy bridging code, `lazyBridge', blocks (unsurprisingly)
  and does not allow packets to go back and forth. I think I need
  explicit selects/waits here to get the back and forth traffic.
  Maybe there is a some way to leverage GHC's internal async I/O
  but I'm not sure how to do it.

 Maybe: forkIO two threads, one for the read end, one for the write
 end? I would use a loop over lazy I/O, also.

This does work, thanks; the new version of lazyBridge is:


  lazyBridge  ::  Handle - Handle - IO ()
  lazyBridge a b   =  do forkIO (flush a b)
 forkIO (flush b a)
 return ()
   where
flush a b  =  LazyB.hGetContents a = LazyB.hPut b

  -- http://hpaste.org/52814

I am kind of surprised that this works at all, actually.

The strict version has this problem where it lets each socket
takes turns sending and receiving, if you try to send and it's
not your turn, it waits for the other one to send before sending
your data. The lazy version just sends bytes as they become
available, the desired behaviour.

I guess if I wanted to instrument the proxying, to keep a tally
of how much traffic there was (to GC little used connections,
for example), I would need to move up to enumerators?

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments

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


Re: [Haskell-cafe] Waiting on input with `hWaitForInput' or `threadWaitRead'

2011-10-18 Thread Jason Dusek
2011/10/18 Jason Dusek jason.du...@gmail.com:
 2011/10/18 Ertugrul Soeylemez e...@ertes.de:
  A proxy server acts a lot like an echo server.  The difference is that
  usually before the actual proxying starts you have a negotiation phase,
  and instead of echoing back to the same socket, you just write it to a
  different one.  Here is an (untested) example:
 
     (clientH, clientHost, clientPort) - accept serverSock
     destH - negotiate clientH
     doneVar - newEmptyMVar
 
     forkIO (hGetContents clientH = hPutStr destH = putMVar doneVar)
     forkIO (hGetContents destH = hPutStr clientH = putMVar doneVar)
     replicateM_ 2 (takeMVar doneVar)
     mapM_ hClose [clientH, destH]

 This code seems like it says: [...]

After working through Gregory Collins suggestion, above, I see
that I was not reading your code correctly.

--
Jason Dusek
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments

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


Re: [Haskell-cafe] Comparison Haskell, Java, C and LISP

2011-10-18 Thread Nicu Ionita

Am 18.10.2011 18:53, schrieb Stephen Tetley:

Haskell has no support for reflection whatsoever.

It can support compile time meta-programming with Template Haskell.

Reflection itself might be antagonistic to functional programming, I
suspect it is at odds with referential transparency. Most of the work
on reflection seemed based around Lisp / Scheme - Christian Queinnec's
reflective interpreter in Lisp in Small Pieces uses an awful lot of
set! 

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

But is (delimited) continuation not a kind of reflection?
Nicu

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


Re: [Haskell-cafe] subclasses and classes with same type in instance

2011-10-18 Thread Albert Y. C. Lai

On 11-10-16 01:56 PM, Patrick Browne wrote:

I get the same results from Listing 1 and Listing 2 below.


I carefully diff'ed the two listings and found no difference except for 
comments.



-- Listing 1- Subclass
data Shed = Shed

class Building building where
  addressB :: building - Integer
  addressB b = 1

--  subclass, but none in Listing 2
class Building house = House house where
  addressH :: house - Integer
  addressH b = 0

instance Building Shed where
instance House Shed where


-- Listing 2 -- No subclass
data Shed = Shed

class Building building where
  addressB :: building - Integer
  addressB b = 1

-- No subclass
class Building house = House house where
  addressH :: house - Integer
  addressH b = 0

instance Building Shed where
instance House Shed where


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


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 jvl...@hotmail.com
 Subject: Re: [Haskell-cafe] How to implement a digital filter, using
Arrows?
 To: haskell-cafe@haskell.org
 Message-ID: BLU0-
 smtp384394452fd2750fbe3bcfcc6...@phx.gbl
 Content-Type: text/plain; charset=ISO-8859-1; format=flowed



 your function corresponds with Control.Arrow.Transformer.Automaton. If
 you frame your function is such most of your plumbing is taken care of.

Following your advice, I arrived at:

  1 {-# LANGUAGE Arrows, GeneralizedNewtypeDeriving, FlexibleContexts #-}
  2
  3 module Filter (
  4 FilterState
  5   , Filter
  6   , applyFilter
  7   , convT
  8 ) where
  9
 10 import EitherT
 11 import Control.Monad
 12 import Control.Monad.State
 13 import Control.Arrow
 14 import Control.Arrow.Operations
 15 import Control.Arrow.Transformer
 16 import Control.Arrow.Transformer.All
 17 import Data.Stream as DS (fromList, toList)
 18
 19 -- tap weights, `as' and `bs', are being made part of the filter state,
in
 20 -- order to accomodate adaptive filters (i.e. - DFEs).
 21 data FilterState a = FilterState {
 22 as   :: [a] -- transfer function denominator coefficients
 23   , bs   :: [a] -- transfer function numerator coefficients
 24   , taps :: [a] -- current delay tap stored values
 25   }
 26
 27 -- Future proofing the implementation, using the `newtype' trick.
 28 newtype Filter b c = F {
 29 runFilter :: (b, FilterState b) - (c, FilterState b)
 31   }
 32
 33 -- Time domain convolution filter (FIR or IIR),
 34 -- expressed in direct form 2
 35 convT :: (Num b) = Filter b b
 36 convT = F $ \(x, s) -
 37 let wk = (x - sum [a * t | (a, t) - zip (tail $ as s) (taps s)])
 38 newTaps = wk : ((reverse . tail . reverse) $ taps s)
 39 s' = s {taps = newTaps}
 40 y  = sum [b * w | (b, w) - zip (bs s) (wk : (taps s))]
 41 in (y, s')
 42
 43 -- Turn a filter into an Automaton, in order to use the built in
plubming
 44 -- of Arrows to run the filter on an input.
 45 filterAuto :: (ArrowApply a) = Filter b c - FilterState b - Automaton
a (e, b) c
 46 filterAuto f s = Automaton a where
 47 a = proc (e, x) - do
 48 (y, s') - arr (runFilter f) - (x, s)
 49 returnA - (y, filterAuto f s')
 50
 53 applyFilter :: Filter b c - FilterState b - [b] - ([c], FilterState
b)
 54 applyFilter f s =
 55 let a = filterAuto f s
 56 in proc xs - do
 57 ys - runAutomaton a - ((), DS.fromList xs)
 58 s' - (|fetch|)
 59 returnA - (DS.toList ys, s')
 60

which gave me this compile error:

 Filter.hs:58:16:
 Could not deduce (ArrowState (FilterState b) (-))
   from the context ()
   arising from a use of `fetch' at Filter.hs:58:16-20
 Possible fix:
   add (ArrowState (FilterState b) (-)) to the context of
 the type signature for `applyFilter'
   or add an instance declaration for
  (ArrowState (FilterState b) (-))
 In the expression: fetch
 In the expression:
 proc xs - do { ys - runAutomaton a - ((), fromList xs);
 s' - (|fetch |);
 returnA - (toList ys, s') }
 In the expression:
 let a = filterAuto f s
 in
   proc xs - do { ys - runAutomaton a - ((), fromList xs);
   s' - (|fetch |);
    }

So, I made this change:

 51 applyFilter :: *(ArrowState (FilterState b) (-)) =* Filter b c -
FilterState b - [b] -
 52 ([c], FilterState b)

And that compiled. However, when I tried to test my new filter with:

 let s = FilterState [1,0,0] [0.7, 0.2, 0.1] [0, 0, 0]
 applyFilter convT s [1,0,0,0,0]

I got:

 interactive:1:0:
 No instance for (ArrowState (FilterState Double) (-))
   arising from a use of `applyFilter' at interactive:1:0-30
 Possible fix:
   add an instance declaration for
   (ArrowState (FilterState Double) (-))
 In the expression: applyFilter convT s [1, 0, 0, 0, ]
 In the definition of `it': it = applyFilter convT s [1, 0, 0, ]

I thought, maybe, I need to derive from *ArrowState* in my *Filter* type
definition.
So, I tried making this change to the code:

28 newtype Filter b c = F {
29 runFilter :: (b, FilterState b) - (c, FilterState b)
30   } deriving (ArrowState (FilterState x))

but then I was back to no compile:

 Filter.hs:30:14:
 Can't make a derived instance of
   `ArrowState (FilterState x) Filter'
   (even with cunning newtype deriving):
   cannot eta-reduce the representation type enough
 In the newtype declaration for `Filter'

Do you have any advice?

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


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

2011-10-18 Thread Ryan Ingram
Your type stopped being an arrow when the state type started to depend on
the input type:

Filter a b ~= (a, FS a) - (b, FS a)

Filter b c ~= (b, FS b) - (c, FS b)

It's impossible to compose these two functions into a single function of
type Filter a c, because the state type doesn't match.

You need to make the filter state not dependent on the input type:

newtype Filter s a b = F { runFilter :: (a, FilterState s) - (b,
FilterState s) }

You can still create objects with the type
   Filter a a b
which correspond to your old filter type.  But these functions will always
'start' a pipeline.  Which I think is what you want anyways!

  -- ryan


On Tue, Oct 18, 2011 at 2:35 PM, Captain Freako capn.fre...@gmail.comwrote:

 Hi John,
 Thanks for this reply:

 Date: Tue, 18 Oct 2011 14:05:22 +1030
 From: John Lask jvl...@hotmail.com
 Subject: Re: [Haskell-cafe] How to implement a digital filter, using
Arrows?
 To: haskell-cafe@haskell.org
 Message-ID: BLU0-
 smtp384394452fd2750fbe3bcfcc6...@phx.gbl
 Content-Type: text/plain; charset=ISO-8859-1; format=flowed



 your function corresponds with Control.Arrow.Transformer.Automaton. If
 you frame your function is such most of your plumbing is taken care of.

 Following your advice, I arrived at:

   1 {-# LANGUAGE Arrows, GeneralizedNewtypeDeriving, FlexibleContexts #-}
   2
   3 module Filter (
   4 FilterState
   5   , Filter
   6   , applyFilter
   7   , convT
   8 ) where
   9
  10 import EitherT
  11 import Control.Monad
  12 import Control.Monad.State
  13 import Control.Arrow
  14 import Control.Arrow.Operations
  15 import Control.Arrow.Transformer
  16 import Control.Arrow.Transformer.All
  17 import Data.Stream as DS (fromList, toList)
  18
  19 -- tap weights, `as' and `bs', are being made part of the filter state,
 in
  20 -- order to accomodate adaptive filters (i.e. - DFEs).
  21 data FilterState a = FilterState {
  22 as   :: [a] -- transfer function denominator coefficients
  23   , bs   :: [a] -- transfer function numerator coefficients
  24   , taps :: [a] -- current delay tap stored values
  25   }
  26
  27 -- Future proofing the implementation, using the `newtype' trick.
  28 newtype Filter b c = F {
  29 runFilter :: (b, FilterState b) - (c, FilterState b)
  31   }
  32
  33 -- Time domain convolution filter (FIR or IIR),
  34 -- expressed in direct form 2
  35 convT :: (Num b) = Filter b b
  36 convT = F $ \(x, s) -
  37 let wk = (x - sum [a * t | (a, t) - zip (tail $ as s) (taps s)])
  38 newTaps = wk : ((reverse . tail . reverse) $ taps s)
  39 s' = s {taps = newTaps}
  40 y  = sum [b * w | (b, w) - zip (bs s) (wk : (taps s))]
  41 in (y, s')
  42
  43 -- Turn a filter into an Automaton, in order to use the built in
 plubming
  44 -- of Arrows to run the filter on an input.
  45 filterAuto :: (ArrowApply a) = Filter b c - FilterState b -
 Automaton a (e, b) c
  46 filterAuto f s = Automaton a where
  47 a = proc (e, x) - do
  48 (y, s') - arr (runFilter f) - (x, s)
  49 returnA - (y, filterAuto f s')
  50
  53 applyFilter :: Filter b c - FilterState b - [b] - ([c], FilterState
 b)
  54 applyFilter f s =
  55 let a = filterAuto f s
  56 in proc xs - do
  57 ys - runAutomaton a - ((), DS.fromList xs)
  58 s' - (|fetch|)
  59 returnA - (DS.toList ys, s')
  60

 which gave me this compile error:

 Filter.hs:58:16:
 Could not deduce (ArrowState (FilterState b) (-))
   from the context ()
   arising from a use of `fetch' at Filter.hs:58:16-20
 Possible fix:
   add (ArrowState (FilterState b) (-)) to the context of
 the type signature for `applyFilter'
   or add an instance declaration for
  (ArrowState (FilterState b) (-))
 In the expression: fetch
 In the expression:
 proc xs - do { ys - runAutomaton a - ((), fromList xs);
 s' - (|fetch |);
 returnA - (toList ys, s') }
 In the expression:
 let a = filterAuto f s
 in
   proc xs - do { ys - runAutomaton a - ((), fromList xs);
   s' - (|fetch |);
    }

 So, I made this change:

  51 applyFilter :: *(ArrowState (FilterState b) (-)) =* Filter b c -
 FilterState b - [b] -
  52 ([c], FilterState
 b)

 And that compiled. However, when I tried to test my new filter with:

  let s = FilterState [1,0,0] [0.7, 0.2, 0.1] [0, 0, 0]
  applyFilter convT s [1,0,0,0,0]

 I got:

 interactive:1:0:
 No instance for (ArrowState (FilterState Double) (-))
   arising from a use of `applyFilter' at interactive:1:0-30
 Possible fix:
   add an instance declaration for
   (ArrowState (FilterState Double) (-))
 In the expression: applyFilter convT s [1, 0, 0, 0, ]
 In the definition of `it': it = applyFilter convT s [1, 0, 0, ]

 I thought, maybe, I 

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

2011-10-18 Thread John Lask


 {-# LANGUAGE Arrows #-}

This is literate code. It expounds on your initial question and provides
two solutions based either on the StateArrow or Automaton

 module Test where
 import Data.List ( mapAccumL )
 import Control.Arrow
 import Control.Arrow.Operations
 import Control.Arrow.Transformer
 import Control.Arrow.Transformer.State
 import Control.Arrow.Transformer.Automaton

this later formulation corresponds to Control.Arrow.Transformer.State

 data FilterState a = FilterState {
  as   :: [a] -- transfer function denominator coefficients
, bs   :: [a] -- transfer function numerator coefficients
, taps :: [a] -- current delay tap stored values
}


  -- Time domain convolution filter (FIR or IIR),
  -- expressed in direct form 2
 convT =  \(x, s) -
  let wk = (x - sum [a * t | (a, t)- zip (tail $ as s) (taps s)])
  newTaps = wk : ((reverse . tail . reverse) $ taps s)
  s' = s {taps = newTaps}
  y  = sum [b * w | (b, w)- zip (bs s) (wk : (taps s))]
  in (y, s')

we can construct the type of a Filter as a state arrow with state
(FilterState s) and base arrow type of (-)

 type FilterSt s b c = StateArrow (FilterState s) (-) b c

to lift the function convT to a state arrow it would be very
easy if the constructor were exported (ie. ST convT), however it is not. So
we define a custom lift to lift functions of the above type into the arrow

 liftSt :: ((x,FilterState s)-(y,FilterState s)) - FilterSt s x y
 liftSt f = proc x - do
s - fetch - ()
(y,s') - arr f - (x,s)
store - s'
returnA - y

then to fold the arrow over a list of inputs

 runFilterSt :: FilterSt s b c - (FilterState s) - [b] - 
(FilterState s , [c])

 runFilterSt f =  mapAccumL (curry (swap . runState f . swap))
   where
 swap (a,b) = (b,a)


 t1 = let
   s = FilterState [1,0,0] [0.7, 0.2, 0.1] [0, 0, 0]
  in snd $ runFilterSt (liftSt convT) s [1,0,0,0,0]


*Test t1
[0.7,0.2,0.1,0.0,0.0]


except I am not sure you want a state arrow as that propogates the state
through all arrows. eg in a  b, the state modified by a passes to b 
and so on.
This would only be any good if all your filters shared/modified the same 
state.


the initial suggestion was to use an automaton arrow which isolates the 
state

in each arrow.




 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'
returnA - y


runAutomaton is a bit cumbersome, so define a custom run function that
takes a list

 runAuto a [] = []
 runAuto (Automaton f) (x:xs) = let
   (y,a) = f x
   in y:runAuto a xs



 t2 = let
   s = FilterState [1,0,0] [0.7, 0.2, 0.1] [0, 0, 0]
  in runAuto (liftAu convT s) [1,0,0,0,0]



*Test t2
[0.7,0.2,0.1,0.0,0.0]


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


Re: [Haskell-cafe] Comparison Haskell, Java, C and LISP

2011-10-18 Thread yi huang
If i understand correctly, what we called generics is what so called
reflection. It allow you to introspect type structure.
http://haskell.org/ghc/docs/latest/html/libraries/ghc-prim-0.2.0.0/GHC-Generics.html#g:4

On Wed, Oct 19, 2011 at 12:03 AM, yrazes yra...@gmail.com wrote:

 Hi,

 Maybe you remember my case.
 I was trying to compare some aspects of these languages.
 Well... I found that I can compare reflection, support for generics,
 simplicity and safe code.
 I just want to ask if you have more information for reflection in Haskell.
 I read that there is no enough for dynamics to support complete reflection.
 I hope someone can help me this time :)

 Julita

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




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