Re: [Haskell-cafe] Lifted Spine View

2011-11-21 Thread bob zhang
Thanks,  I don't see the footnote, but that works. :-)

On Mon, Nov 21, 2011 at 5:15 AM, Andres Löh andres.l...@googlemail.comwrote:

 Hi there.

 I tried to follow the program of the paper Scrap your boilerpolate
  Revolutions. Unfortunately,
  I found the program in the section lifted spine view does not compile in
 my
  GHC, could anybody
   point out where I am wrong? Many Thanks
 
  My code is posted here http://hpaste.org/54357

 You have to flip the two fields of (:-), i.e., the type has to be
 first and the annotated term has to be second. This is because pattern
 matching on GADTs and refinement is implicitly left-to-right in GHC.
 The paper presents it the other way round and remarks on the flipped
 order in a footnote near the beginning.

 Cheers,
  Andres




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


[Haskell-cafe] Lifted Spine View

2011-11-20 Thread bob zhang
Hi, all
I tried to follow the program of the paper Scrap your boilerpolate
Revolutions. Unfortunately,
I found the program in the section lifted spine view does not compile in
my GHC, could anybody
point out where I am wrong? Many Thanks

My code is posted herehttp://hpaste.org/54357

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


[Haskell-cafe] About the ConstraintKinds extension

2011-10-17 Thread bob zhang
Hi cafe,
 I have played quite a bit with the ConstraintKinds extension, pretty
cool.
 But I found a problem which I thought would be made better, plz correct
me if I am wrong

 take a contrived example,
 class C B = B a where
 here B :: * - Constraint,  I think this definition is reasonable,
since B does not appears in the
 first position of the context.

 Previously, we require acyclic class declarations since we don't have
ConstraintKinds extension
 but now since type class could be abstracted, I think the definition
above should be ok.

 the ghc-manual cited the program below is valid
class C a where {

op :: D b = a - b - b
  }


class C a = D a where { ... }

I think there are no reasons to reject
class C B = B where (and this style is pretty useful in some cases)
...
B :: * - Constraint
C :: (*-Constraint) - Constraint

Any comments are welcome


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


[Haskell-cafe] Is it a bug in haskell-src-meta package?

2011-08-31 Thread bob zhang
Hi, all

parseExp (,) 3 4  =

Right (AppE (AppE (ConE GHC.Unit.(,)) (LitE (IntegerL 3))) (LitE
(IntegerL 4)))

where's GHC.Unit.(,) ?

Many thanks

best, bob

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


Re: [Haskell-cafe] Is it a bug in haskell-src-meta package?

2011-08-31 Thread bob zhang

于 11-8-31 下午10:01, Ivan Lazar Miljenovic 写道:

On 1 September 2011 11:19, bob zhangbobzhang1...@gmail.com  wrote:

Hi, all

parseExp (,) 3 4  =

Right (AppE (AppE (ConE GHC.Unit.(,)) (LitE (IntegerL 3))) (LitE
(IntegerL 4)))

where's GHC.Unit.(,) ?

GHC.Unit (like all GHC.* modules) is an internal module used by GHC to
implement base, containers, etc.  The actual definitions of tuples in
the Prelude come from Data.Unit, which for GHC are just re-exported
from GHC.Unit: 
http://haskell.org/ghc/docs/latest/html/libraries/base/src/Data-Tuple.html


Thanks for your quick-reply.
I tried this does not work.(simplified) in quasiquoter.

import Control.Arrow
import Control.Applicative
import Prelude hiding ((.), id)
import Control.Monad
import Control.Category
import Data.Derive.All
import Data.DeriveTH
import Test.QuickCheck

import Language.Haskell.TH.Quote
import Language.Haskell.TH.Syntax

import Language.Haskell.TH.Lib
import Language.Haskell.Meta

hs = QuasiQuoter { quoteExp = either fail return . parseExp }
 top-level---
[hs| (,) 3 4 |] will not compile
do you know how to fix it ?

Thank you !
Best, bob


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


Re: [Haskell-cafe] Is it a bug in haskell-src-meta package?

2011-08-31 Thread bob zhang

于 11-8-31 下午10:01, Ivan Lazar Miljenovic 写道:

On 1 September 2011 11:19, bob zhangbobzhang1...@gmail.com  wrote:

Hi, all

parseExp (,) 3 4  =

Right (AppE (AppE (ConE GHC.Unit.(,)) (LitE (IntegerL 3))) (LitE
(IntegerL 4)))

where's GHC.Unit.(,) ?

GHC.Unit (like all GHC.* modules) is an internal module used by GHC to
implement base, containers, etc.  The actual definitions of tuples in
the Prelude come from Data.Unit, which for GHC are just re-exported
from GHC.Unit: 
http://haskell.org/ghc/docs/latest/html/libraries/base/src/Data-Tuple.html


Hi, I tried
   ghc-pkg find-module GHC.Unit -- ghc-prim-0.2.0
:browse GHC.Unit
data () = ()

could not find the function (,) exposed,  thanks



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


Re: [Haskell-cafe] Is it a bug in haskell-src-meta package?

2011-08-31 Thread bob zhang

于 11-8-31 下午10:35, Ivan Lazar Miljenovic 写道:

May I ask though why you're trying to use (,) as an explicit
constructor in a quasi-quotation?

Thanks for your reply. I just  generated some code
this way, and it does not work.

this style is common in applicative functor, right?

Best, bob

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


Re: [Haskell-cafe] How to make callCC more dynamic

2011-08-26 Thread bob zhang
Thank you, there is also a nice link here :-)
http://stackoverflow.com/questions/7178919/how-to-make-callcc-more-dynamic
and for this type,
ContT {runContT :: forall r1 . (forall r2 . a- m r2) - m r1}
callCC can be defined, however, you can not run it, and reset couldn't
type check
于 11-8-25 上午1:53, o...@okmij.org 写道:
 bob zhang wrote:
 I thought the right type for ContT should be
 newtype ContT m a = ContT {runContT :: forall r. (a- m r) - m r}
 and
 other control operators
 shift :: Monad m = (forall r . (a- ContT m r) - ContT m r) - ContT m a
 reset :: Monad m = ContT m a - ContT m a
 callCC :: ((a- (forall r . ContT m r)) - ContT m a) - ContT m a
 unfortunately, I can not make callCC type check, and don't know how to
 do it.
 Precisely that problem was discussed in  
   http://okmij.org/ftp/continuations/undelimited.html#proper-contM

 Your ContT is CPS1 in the above article. The article shows why you
 cannot write callCC with the above type of ContT. The article talks
 about other types. BTW, if you faithfully defined the monad for
 undelimited control than shift/reset cannot be expressed. Undelimited
 continuations are strictly less expressible than delimited ones. The
 above page gives the pointers to the papers with the proof.




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


[Haskell-cafe] How to make callCC more dynamic

2011-08-24 Thread bob zhang
Hi, all
I thought the right type for ContT should be
newtype ContT m a = ContT {runContT :: forall r. (a- m r) - m r}
and
other control operators
shift :: Monad m = (forall r . (a- ContT m r) - ContT m r) - ContT m a
reset :: Monad m = ContT m a - ContT m a
callCC :: ((a- (forall r . ContT m r)) - ContT m a) - ContT m a

unfortunately, I can not make callCC type check, and don't know how to
do it.
I managed to make shift, reset type check

reset :: Monad m = ContT m a - ContT m a
reset e = ContT $ \ k - runContT e return = k

shift :: Monad m = (forall r . (a- ContT m r) - ContT m r) - ContT m a
shift e = ContT $ \ (k :: a - m r) -
runContT ((e $ \ v - ContT $ \c - k v = c) :: ContT m r) return

but still, I cann't use shift, reset in recursive jumpings like this?

newtype H r m = H (H r m - ContT m r)
unH (H x) = x
test = flip runContT return $ reset $ do
jump - shift (\f - f (H f))
lift . print $ hello
unH jump jump

Have anyone tried this before?
Best, bob

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


Re: [Haskell-cafe] How to make callCC more dynamic

2011-08-24 Thread bob zhang
Hi Jason, thanks for your reply.
  I was curious that we could bring really continuations into haskell, the
traditional callCC brings a lot of unnecessary
type restrictions

On Wed, Aug 24, 2011 at 12:45 PM, Jason Dagit dag...@gmail.com wrote:

 On Wed, Aug 24, 2011 at 9:19 AM, bob zhang bobzhang1...@gmail.com wrote:
  Hi, all
  I thought the right type for ContT should be
  newtype ContT m a = ContT {runContT :: forall r. (a- m r) - m r}
  and
  other control operators
  shift :: Monad m = (forall r . (a- ContT m r) - ContT m r) - ContT m
 a
  reset :: Monad m = ContT m a - ContT m a
  callCC :: ((a- (forall r . ContT m r)) - ContT m a) - ContT m a
 
  unfortunately, I can not make callCC type check, and don't know how to
  do it.
  I managed to make shift, reset type check

 Correct me if I'm wrong, but you're wanting to implement the delimited
 form of continuations?

 If so, you might take a look at this and the associated papers:
 http://hackage.haskell.org/package/CC-delcont

 Jason




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


[Haskell-cafe] a minor bug (memory leak) in ListLike package

2011-08-23 Thread bob zhang
Hi, John, there is a space leak problem in ListLike typeclass,
in the method genericLength
calclen !accum cl =
calclen accum cl =
--- thank you for your nice library
btw, is there any way to derive ListLike interface automatically?
for such type :
newtype List a = List {[a]}
Best,bob

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


Re: [Haskell-cafe] a minor bug (memory leak) in ListLike package

2011-08-23 Thread bob zhang
Hi,
  I think 3  genericLength [1..] should fail, that laziness is not we
want.
  I can not derive ListLike  instance using GHC extensions, can you provide
a working example?
  Thanks
On Tue, Aug 23, 2011 at 9:47 PM, Ivan Lazar Miljenovic 
ivan.miljeno...@gmail.com wrote:

 On 24 August 2011 11:10, bob zhang bobzhang1...@gmail.com wrote:
  Hi, John, there is a space leak problem in ListLike typeclass,
  in the method genericLength
  calclen !accum cl =
  calclen accum cl =

 I _think_ this may cause problems with some data types (e.g.

 http://hackage.haskell.org/packages/archive/numbers/2009.8.9/doc/html/Data-Number-Natural.html
 ) that require the extra laziness (that is, you can do things like ` 3
  genericLength [1..] ' and have it return True).

  --- thank you for your nice library
  btw, is there any way to derive ListLike interface automatically?
  for such type :
  newtype List a = List {[a]}

 GeneralizedNewtypeDeriving can do that.

 --
 Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com
 IvanMiljenovic.wordpress.com




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


[Haskell-cafe] Need help Very strange space behavior

2011-08-21 Thread bob zhang
Hi all,
 I thought that Cont Monad is just equivalent to CPS Transformation, so
if I have
a monadic sum, if I run in Identity Monad, it will suck due to
stackoverflow, and if
I run it in Cont Monad, it will okay due to tail recursion. So I write a
simple program
to verify my idea. But to my surprise, the result is unreasonable due to my
limited knowledge.
All programs are compiled ghc --make Test.hs -o test  ./test
  Thank you in advance, the clearer the better!! (I am really confused)
in the comments, suck means stackoverflow.

sum0 n = if n==0  then  0  else n + sum0 (n-1)
sum1 n = if  n==0  then return 0 else sum1 (n-1) = \ v -  seq v (return
(n+v))

sum2 n k = if n == 0 then k 0 else sum2 n (\v - k (n +
v))

sum3 n k = if n == 0 then k 0 else sum3 n (\ !v - k (n +
v))

sum4 n k = if n == 0 then k 0 else sum4 n (\ v - seq v ( k (n +
v)))

sum5 n = if  n==0  then return 0 else sum5 (n-1) = \ v -   (return
(n+v))

-- main = print (sum0 300)
--  suck  reasonable

-- main = print (flip runCont id (sum1 300))
-- rock 180M memory reasonable, but I am not clear why seq needed here,
since its continuation is not applied until n goes to 0

-- main = print (flip runCont id (sum5 300))
-- suck -- why?

-- main = print (flip runCont (const 0) (sum1 300))
-- rock 130M memory   -- reasonable

-- main = print (flip runCont (const 0) (sum5 300))
-- rock 118M memory   -- reasonable

-- main = print (sum2 300 (const 0))
-- a lot of memory (more than 1G)   -- I thought sum2 is equivalent to sum5
(when sum5 is in Cont Monad), why?

-- main = print (sum3 300 (const 0))
-- a lot of memory -- I thought sum3 is equivalent to sum1(Cont Monad), why?


-- main = print (runIdentity  (sum1 300))
-- suck -- exactly what I want

-- main = print (sum3 300 id)
-- a lot of memory -- equivalent to sum1 why?

-- main = print (sum4 300 id) -
- a lot of memory  -- equivalent to sum1 why?

-- main = print (sum [1 .. 300]) -- suck -- src sum = foldl (+)
0
-- reasonable
-- main = print (foldl' (+) 0 [1 .. 300]) -- rock 1.5M
memory
-- reasonable


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


[Haskell-cafe] weird type signature in Arrow Notation

2011-08-02 Thread bob zhang
hi, all
testB :: (ArrowChoice t1, Num a1, Num a) = (a - a1 - t2) - t1 a t3
- t1 a1 t3 - t1 (a, a1) t
testB f g h = proc (x,y) - do
if (f x y)then g - x + 1 else h - y + 2

it's very strange that the type of _f_ is (a-a1-t2) which I thought
should be a - a1 - Bool,

btw, is there any way to get the output of preprocessing using -XArrow
extensions,

Thanks a lot
best, bob


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


[Haskell-cafe] deriving ListLike instance

2011-07-25 Thread bob zhang
Hi, all,
newtype Stream a = Stream [a]

I wanna derive ListLike [a] a automatically, but did not find a solution,
I tried
deriving instance ListLile (Stream a) a -- does not work

Thank you.

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


Re: [Haskell-cafe] deriving ListLike instance

2011-07-25 Thread bob zhang

Thanks. I know we can only derive built-in classes.
Since Stream is just a newtype  and
ListLike [a] a  is an instance, so I hope ListLike (Stream a) a would 
work given extensions.


Unforturnately, newtype derivation requires the _last_ type variable to 
be newtype


Thank you
于 11-7-25 下午6:14, Ivan Lazar Miljenovic 写道:

On 26 July 2011 04:30, bob zhangbobzhang1...@gmail.com  wrote:

Hi, all,
newtype Stream a = Stream [a]

I wanna derive ListLike [a] a automatically, but did not find a solution,
I tried
deriving instance ListLile (Stream a) a -- does not work

You can only derive certain in-built classes (Eq, Ord, Show, etc.) and
- with extensions - some other classes (e.g. Functor).  You _cannot_
derive ListLike.  That said, it may be possible to extend either
derive [1] or DrIFT [2] to be able to generate these instances for
you.

[1]: http://hackage.haskell.org/package/derive
[2]: http://hackage.haskell.org/package/DrIFT-cabalized




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


[Haskell-cafe] Reactive Programming in Machine Learning

2011-07-22 Thread bob zhang
Hi all,
I am doing a survey on combining Functional Reactive Programming and
Machine Learning. Has anyone did relevant research on this topic?
Any discussion or link is appreciable.
Best,bob

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


Re: [Haskell-cafe] Reactive Programming in Machine Learning

2011-07-22 Thread bob zhang

Thank your for kind help :-)
于 11-7-22 下午3:28, Edward Amsden 写道:

I did a survey of functional reactive programming, though there's no
reference to machine learning:

http://blog.edwardamsden.com/2011/05/survey-of-functional-reactive.html

On Fri, Jul 22, 2011 at 2:30 PM, bob zhangbobzhang1...@gmail.com  wrote:

Hi all,
I am doing a survey on combining Functional Reactive Programming and
Machine Learning. Has anyone did relevant research on this topic?
Any discussion or link is appreciable.
Best,bob

___
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] derive + quickCheck

2011-07-19 Thread bob zhang

Hi,
   thank you .
   I read your souce, I found the depth is only 2, right?
  like data A = [A]|String, any easy way to control the maximum_depth 
of generated data?


Regards,bob
于 11-7-17 下午8:13, Ivan Lazar Miljenovic 写道:

On 17 July 2011 23:42, bob zhangbobzhang1...@gmail.com  wrote:

Hi, all,
I found derive + quickCheck very useful but I came across some problems.
I used derive to derive instance of Arbitrary immeditaely, but sometimes the
sample is non-terminating, which I mean the result is very very big.

[snip]

data JValue = JString String
| JNumber Double
| JBool Bool
| JNull
| JObject [(String, JValue)] --
| JArray [JValue] --
deriving (Eq,Ord,Show)
$(derive makeArbitrary ''JValue)

Your JValue type is recursive; as such I highly suggest you manually
create the Arbitrary instances for it (e.g. a helper function with a
Bool parameter to indicate whether or not to create recursive calls;
see how I do it in
http://code.haskell.org/graphviz/Data/GraphViz/Testing/Instances/Canonical.hs
where the DotStatements type can have DotSubGraph values, which in
turn have DotStatements).




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


[Haskell-cafe] derive + quickCheck

2011-07-17 Thread bob zhang
Hi, all,
I found derive + quickCheck very useful but I came across some problems.
I used derive to derive instance of Arbitrary immeditaely, but sometimes the
sample is non-terminating, which I mean the result is very very big.
I used
samples - take 10 $ sample' in ghci to test the result,
it's non-terminating..
another problem is that $(derive makeArbitrary ''JValue) uses reify, so
I can not see the generated code,
any better way to have a look at the generated code in ghci?
my sample code
{-# LANGUAGE
FlexibleInstances
,MultiParamTypeClasses
,GeneralizedNewtypeDeriving
,FunctionalDependencies
,TypeSynonymInstances
,TemplateHaskell
#-}

module JsonParse where
import Text.ParserCombinators.Parsec
import Text.Parsec.String()
import Control.Applicative hiding ( (|) , many, optional )
import Control.Monad
import Test.QuickCheck -- unGen, sample
-- import Language

import Data.DeriveTH
import Data.Binary
import Data.Derive.Arbitrary
import Language.Haskell.TH
import Language.Haskell.TH.Syntax

data JValue = JString String
| JNumber Double
| JBool Bool
| JNull
| JObject [(String, JValue)] --
| JArray [JValue] --
deriving (Eq,Ord,Show)
$(derive makeArbitrary ''JValue)



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