[Haskell-cafe] A yet another question about subtyping and heterogeneous collections

2012-10-18 Thread oleg

First of all, MigMit has probably suggested the parameterization of
Like by the constraint, something like the following:

data Like ctx = forall a. (ctx a, Typeable a) => Like a

instance ALike (Like ALike) where
   toA (Like x) = toA x

instance CLike (Like CLike) where
   toC (Like x) = toC x

get_mono :: Typeable b => [Like ALike] -> [b]
get_mono = catMaybes . map ((\(Like x) -> cast x))

lst_a :: [Like ALike]
lst_a = [Like a1, Like b1, Like c1, Like d1]

lst_c :: [Like CLike]
lst_c = [Like c1, Like d1]

t1 = map print_a lst_a
t2 = map print_a lst_c

(The rest of the code is the same as in your first message). 
You need the flag ConstraintKinds. 

Second, all your examples so far used structural subtyping (objects
with the same fields have the same type) rather than nominal
subtyping of C++ (distinct classes have distinct types even if they
have the same fields; the subtyping must be declared in the class
declaration). For the structural subtyping, upcasts and downcasts can
be done mostly automatically. See the OOHaskell paper or the code

http://code.haskell.org/OOHaskell
(see the files in the samples directory).



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


[Haskell-cafe] acid-state audit trail

2012-10-18 Thread Richard Wallace
Hey all,

I've been looking at acid-state as a possible storage backend for an
application.  It looks like it fits my needs pretty damn well, but one
thing that I'm curious about is if it is possible to get a list of
"update events".  You can obviously query for the current state, but
it's not immediately apparent if you can see the history of your
values state.  This is useful in some things, like providing audit
trails and debugging.  As well as being able to re-create state in a
different form.

I was also curious if the createCheckpoint function eliminates the
state history or does it just create a snapshot, it's not apparent
from the docs.

Thanks,
Rich

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


Re: [Haskell-cafe] A yet another question about subtyping and heterogeneous collections

2012-10-18 Thread AntC
Roman Cheplyaka  ro-che.info> writes:

> 
> * Dmitry Vyal  gmail.com> [2012-10-18 17:31:13+0400]
> > On 10/18/2012 03:20 PM, MigMit wrote:
> > >Why do you need "ALike x", "BLike x" etc.? Why not just "Like u x"?
> > >
> > 
> > Hmm, looks like a nice idea. I tried it, unfortunately I can't cope
> > with compiler error messages:
> > 
> > tst.hs:32:15:
> > Context reduction stack overflow; size = 201
> > Use -fcontext-stack=N to increase stack size to N
> >   Upcast a b
> > In the first argument of `(.)', namely `(upcast :: b -> a)'
> > In the expression: (upcast :: b -> a) . (upcast :: c -> b)
> > In the expression: (upcast :: b -> a) . (upcast :: c -> b) $ x
> 
> > instance (Upcast a b, Upcast b c) => Upcast a c where
> >   upcast = (upcast :: b -> a) . (upcast :: c -> b)
> 
> This is the offending instance. Remember, GHC only looks at the instance
> head ("Upcast a c" here) when it decides which instance to use.
> 
> Roman
> 
Hi Dmitry, looks like you've got the classic (show . read) difficulty. In 
your "Upcast a c" instance, the compiler is trying to figure out the type of b.

You might think there's only one 'chain' to get from (say) type A to type D -- 
that is via Upcast A B to Upcast B C to Upcast C D; but there's also an 
instance Upcast x x -- which means there could be any number of Upcast A A, 
Upcast B B, etc links in the chain.

(And this doesn't count all the other possible instances that might be defined 
in other modules -- for all the compiler knows at that point.)

The modern way to handle this is using type functions (aka type families aka 
associated types), but I'm not sure how that would apply here. (And, for the 
record, the old-fashioned way would use functional dependencies, as per the 
Heterogenous Collections paper aka 'HList's).

AntC




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


Re: [Haskell-cafe] Getting PID of a child process

2012-10-18 Thread Donn Cave
Quoth Jason Dusek ,

> Using `System.Process.runInteractiveProcess', I can start a process
> and get a handle to it:
> 
>   runInteractiveProcess
>:: FilePath
>-> [String]
>-> Maybe FilePath
>-> Maybe [(String, String)]
>-> IO (Handle, Handle, Handle, ProcessHandle)
> 
> For diagnostic purposes, I'd like to print the PID of the
> process attached to this handle -- how best to do that?


There's a good chance this isn't the best way, but it seems to work:


import System.Process
import System.Process.Internals (ProcessHandle__(..), PHANDLE, 
withProcessHandle)

-- for use with withProcessHandle
getPID :: ProcessHandle__ -> IO (ProcessHandle__, Maybe PHANDLE)
getPID h@(OpenHandle t) = return (h, Just t)
getPID h@(ClosedHandle t) = return (h, Nothing)

main = do
(h0, h1, h2, hp) <- runInteractiveProcess "/bin/date" [] Nothing Nothing
mp <- withProcessHandle hp $ getPID
print mp

Seems like more scaffolding than this application really ought to require.

Donn



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


[Haskell-cafe] ANNOUNCE: apphointments - A simple functional calendar

2012-10-18 Thread Steffen Schuldenzucker


Dear Café,

I just wrote myself a small (~ 200 LOC) calendar application today.

https://bitbucket.org/rainmaker/apphointments

Comments/Patches welcome.

From the readme:

apphointments - A simple functional calendar


This is a "UI = Code" calendar application: You create an event by writing
code that defines it.
To see what's up next, you create a "report", i.e. a summary of the 
events in

a certain time range such as 'thisWeek'. This is done by haskell functions
again from GHCi or ghc -e.

See example.hs.

Using just haskell instead of our own language or GUI allows great 
flexibility

in both defining events and generating reports. See e.g. the 'lecture'
combinator from Apphointments.Util.

Status
--

Works for me, but has no features yet.
See TODO.

Credits
---

Created by Steffen Schuldenzucker 


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


Re: [Haskell-cafe] Getting PID of a child process

2012-10-18 Thread Gwern Branwen
On Thu, Oct 18, 2012 at 5:03 PM, Jason Dusek  wrote:
> For diagnostic purposes, I'd like to print the PID of the
> process attached to this handle -- how best to do that?

In Mueval when I wanted the PID (so I could later send sigkills), I did this:

  hdl <- runProcess "mueval-core" args Nothing Nothing Nothing
Nothing Nothing
  _ <- forkIO $ do
 threadDelay (7 * 70)
 status <- getProcessExitCode hdl
 case status of
 Nothing -> do terminateProcess hdl
   _ <- withProcessHandle hdl (\x
-> case x of

OpenHandle pid -> signalProcess 9 pid >> return (undefined, undefined)

_ -> return (undefined,undefined))
   exitWith (ExitFailure 1)
 Just a -> exitWith a
  stat <- waitForProcess hdl
  exitWith stat

The key is the poorly documented withProcessHandle ::
System.Process.Internals.ProcessHandle -> (ProcessHandle__ -> IO
(ProcessHandle__, a)) -> IO a

The implementation:

data ProcessHandle__ = OpenHandle PHANDLE | ClosedHandle ExitCode
type PHANDLE = CPid

Well, my code seems to work, anyway...

-- 
gwern
http://www.gwern.net

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


[Haskell-cafe] Getting PID of a child process

2012-10-18 Thread Jason Dusek
Hi All,

Using `System.Process.runInteractiveProcess', I can start a process
and get a handle to it:

  runInteractiveProcess
   :: FilePath
   -> [String]
   -> Maybe FilePath
   -> Maybe [(String, String)]
   -> IO (Handle, Handle, Handle, ProcessHandle)

For diagnostic purposes, I'd like to print the PID of the
process attached to this handle -- how best to do that?

--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B

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


Re: [Haskell-cafe] How to correctly benchmark code with Criterion?

2012-10-18 Thread Thomas Schilling
On 18 October 2012 13:15, Janek S.  wrote:
>> Something like this might work, not sure what the canonical way is.
>> (...)
>
> This is basically the same as the answer I was given on SO. My concerns about 
> this solutions are:
> - rnf requires its parameter to belong to NFData type class. This is not the 
> case for some data
> structures like Repa arrays.

For unboxed arrays of primitive types WHNF = NF.  That is, once the
array is constructed all its elements will be in WHNF.

> - evaluate only evaluates its argument to WHNF - is this enough? If I have a 
> tuple containing two
> lists won't this only evaluate the tuple construtor and leave the lists as 
> thunks? This is
> actually the case in my code.

That is why you use "rnf" from the NFData type class. You use
"evaluate" to kick-start rnf which then goes ahead and evaluates
everything (assuming the NFData instance has been defined correctly.)

>
> As I said previously, it seems that Criterion somehow evaluates the data so 
> that time needed for
> its creation is not included in the benchmark. I modified my dataBuild 
> function to look lik this:
>
> dataBuild gen = unsafePerformIO $ do
> let x = (take 6 $ randoms gen, take 2048 $ randoms gen)
> delayThread 100
> return x
>
> When I ran the benchmark, criterion estimated the time needed to complete it 
> to over 100 seconds
> (which means that delayThread worked and was used as a basis for estimation), 
> but the benchamrk
> was finished much faster and there was no difference in the final result 
> comparing to the normal
> dataBuild function. This suggests that once data was created and used for 
> estimation, the
> dataBuild function was not used again. The main question is: is this 
> observation correct? In this
> question on SO:
> http://stackoverflow.com/questions/6637968/how-to-use-criterion-to-measure-performance-of-haskell-programs
> one of the aswers says that there is no automatic memoization, while it looks 
> that in fact the
> values of dataBuild are memoized. I have a feeling that I am misunderstanding 
> something.

If you bind an expression to a variable and then reuse that variable,
the expression is only evaluated once. That is, in "let x = expr in
..." the expression is only evaluated once. However, if you have "f y
= let x = expr in ..." then the expression is evaluated once per
function call.



>
>> I don't know if you have already read them,
>> but Tibell's slides on High Performance Haskell are pretty good:
>>
>> http://www.slideshare.net/tibbe/highperformance-haskell
>>
>> There is a section at the end where he runs several tests using Criterion.
> I skimmed the slides and slide 59 seems to show that my concerns regarding 
> WHNF might be true.

It's usually safe if you benchmark a function. However, you most
likely want the result to be in normal form.  The "nf" does this for
you. So, if your benchmark function has type "f :: X -> ([Double],
Double)", your benchmark will be:

  bench "f" (nf f input)

The first run will evaluate the input (and discard the runtime) and
all subsequent runs will evaluate the result to normal form. For repa
you can use deepSeqArray [1] if your array is not unboxed:

  bench "f'" (whnf (deepSeqArray . f) input)

[1]: 
http://hackage.haskell.org/packages/archive/repa/3.2.2.2/doc/html/Data-Array-Repa.html#v:deepSeqArray

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


Re: [Haskell-cafe] How to correctly benchmark code with Criterion?

2012-10-18 Thread Thomas Schilling
Yes, Criterion always discards the time of the first evaluation.

On 18 October 2012 15:06, Janek S.  wrote:
>> So the evaluation will be included in the benchmark, but if "bench" is
>> doing enough trials it will be statistical noise.
> When I intentionally delayed my dataBuild function (using delayThread 
> 100) the estimated time
> of benchmark was incorrect, but when I got the final results all runs were 
> below 50ms, which
> means that initial run that took 1 second was discarded. So it seems to me 
> that the first
> evaluation is discarded. Would be good if someone could definitely confirm 
> that.
>
> Janek
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



-- 
Push the envelope. Watch it bend.

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


Re: [Haskell-cafe] Teaching Haskell @ MOOCs like Coursera or Udacity

2012-10-18 Thread Thiago Negri
+1

2012/10/18 niket :
> I would love to see Haskell growing on such new platforms!

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


[Haskell-cafe] Teaching Haskell @ MOOCs like Coursera or Udacity

2012-10-18 Thread niket
I am a novice in Haskell but I would love to see the gurus out here
teaching Haskell on MOOCs like Coursera or Udacity.

Dr Martin Odersky is doing it for Scala here:
https://www.coursera.org/course/progfun

I would love to see Haskell growing on such new platforms!

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


Re: [Haskell-cafe] A yet another question about subtyping and heterogeneous collections

2012-10-18 Thread Roman Cheplyaka
* Dmitry Vyal  [2012-10-18 17:31:13+0400]
> On 10/18/2012 03:20 PM, MigMit wrote:
> >Why do you need "ALike x", "BLike x" etc.? Why not just "Like u x"?
> >
> 
> Hmm, looks like a nice idea. I tried it, unfortunately I can't cope
> with compiler error messages:
> 
> tst.hs:32:15:
> Context reduction stack overflow; size = 201
> Use -fcontext-stack=N to increase stack size to N
>   Upcast a b
> In the first argument of `(.)', namely `(upcast :: b -> a)'
> In the expression: (upcast :: b -> a) . (upcast :: c -> b)
> In the expression: (upcast :: b -> a) . (upcast :: c -> b) $ x

> instance (Upcast a b, Upcast b c) => Upcast a c where
>   upcast = (upcast :: b -> a) . (upcast :: c -> b)

This is the offending instance. Remember, GHC only looks at the instance
head ("Upcast a c" here) when it decides which instance to use.

Roman

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


Re: [Haskell-cafe] How to correctly benchmark code with Criterion?

2012-10-18 Thread Antoine Latter
On Thu, Oct 18, 2012 at 9:06 AM, Janek S.  wrote:
>> So the evaluation will be included in the benchmark, but if "bench" is
>> doing enough trials it will be statistical noise.
>
> When I intentionally delayed my dataBuild function (using delayThread 
> 100) the estimated time
> of benchmark was incorrect, but when I got the final results all runs were 
> below 50ms, which
> means that initial run that took 1 second was discarded. So it seems to me 
> that the first
> evaluation is discarded. Would be good if someone could definitely confirm 
> that.
>

You could email Bryan, the author of criterion.

> Janek

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


Re: [Haskell-cafe] How to correctly benchmark code with Criterion?

2012-10-18 Thread Janek S.
> So the evaluation will be included in the benchmark, but if "bench" is
> doing enough trials it will be statistical noise.
When I intentionally delayed my dataBuild function (using delayThread 100) 
the estimated time 
of benchmark was incorrect, but when I got the final results all runs were 
below 50ms, which 
means that initial run that took 1 second was discarded. So it seems to me that 
the first 
evaluation is discarded. Would be good if someone could definitely confirm that.

Janek

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


Re: [Haskell-cafe] How to correctly benchmark code with Criterion?

2012-10-18 Thread Antoine Latter
On Thu, Oct 18, 2012 at 4:23 AM, Janek S.  wrote:
> Dear list,
>
> during past few days I spent a lot of time trying to figure out how to write 
> Criterion benchmarks,
> so that results don't get skewed by lazy evaluation. I want to benchmark 
> different versions of an
> algorithm doing numerical computations on a vector. For that I need to create 
> an input vector
> containing a few thousand elements. I decided to create random data, but that 
> really doesn't
> matter - I could have as well use infinite lists instead of random ones.
>
> My problem is that I am not certain if I am creating my benchmark correctly. 
> I wrote a function
> that creates data like this:
>
> dataBuild :: RandomGen g => g -> ([Double], [Double])
> dataBuild gen = (take 6 $ randoms gen, take 2048 $ randoms gen)
>
> And I create benchmark like this:
>
> bench "Lists" $ nf L.benchThisFunction (L.dataBuild gen)
>

The argument value will be evaluated by the first run of the
bench-mark, and then laziness will keep the value around for the next
few hundred runs that the "bench" function performs.

So the evaluation will be included in the benchmark, but if "bench" is
doing enough trials it will be statistical noise.

Antoine

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


Re: [Haskell-cafe] A yet another question about subtyping and heterogeneous collections

2012-10-18 Thread Dmitry Vyal

On 10/18/2012 03:20 PM, MigMit wrote:

Why do you need "ALike x", "BLike x" etc.? Why not just "Like u x"?



Hmm, looks like a nice idea. I tried it, unfortunately I can't cope with 
compiler error messages:


tst.hs:32:15:
Context reduction stack overflow; size = 201
Use -fcontext-stack=N to increase stack size to N
  Upcast a b
In the first argument of `(.)', namely `(upcast :: b -> a)'
In the expression: (upcast :: b -> a) . (upcast :: c -> b)
In the expression: (upcast :: b -> a) . (upcast :: c -> b) $ x


{-# LANGUAGE FlexibleInstances, UndecidableInstances, 
OverlappingInstances, ExistentialQuantification, DeriveDataTypeable, 
MultiParamTypeClasses, FlexibleContexts,

IncoherentInstances #-}

import Data.Typeable
import Data.Maybe

data A = A {a_x :: Int} deriving (Show, Typeable)
data B = B {b_x :: Int, b_a :: A} deriving (Show, Typeable)
data C = C {c_z :: Int, c_b :: B} deriving (Show, Typeable)
data D = D {d_w :: Int, d_c :: C, d_a :: A} deriving (Show, Typeable)

class Upcast c x where
  upcast :: x -> c

instance Upcast x x where
  upcast = id

instance Upcast A B where upcast = b_a
instance Upcast B C where upcast = c_b
instance Upcast C D where upcast = d_c

instance (Upcast a b, Upcast b c) => Upcast a c where
  upcast = (upcast :: b -> a) . (upcast :: c -> b)

a1 = A 1
b1 = B 2 (A 2)
c1 = C 3 b1
d1 = D 4 c1 (A 10)

print_a :: Upcast A x => x -> String
print_a v = "A = " ++ show (a_x $ upcast v)

sum_a :: (Upcast A x, Upcast A y) => x -> y -> String
sum_a v1 v2 = "A1 = " ++ show (a_x $ upcast v1) ++ " A2 = " ++ show (a_x 
$ upcast v2)



data LikeA = forall a. (Upcast A a, Typeable a) => LikeA a

--instance Upcast a LikeA where
--  upcast (LikeA x) = upcast x

lst_a = [LikeA a1, LikeA b1, LikeA c1, LikeA d1]

get_mono :: Typeable b => [LikeA] -> [b]
get_mono = catMaybes . map ((\(LikeA x) -> cast x))

data LikeC = forall c. (Upcast C c, Typeable c) => LikeC c

--instance Upcast C LikeC where
--  upcast (LikeC x) = upcast x

lst_c = [LikeC c1, LikeC d1]

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


Re: [Haskell-cafe] How to correctly benchmark code with Criterion?

2012-10-18 Thread Janek S.
> Something like this might work, not sure what the canonical way is.
> (...)

This is basically the same as the answer I was given on SO. My concerns about 
this solutions are:
- rnf requires its parameter to belong to NFData type class. This is not the 
case for some data 
structures like Repa arrays.
- evaluate only evaluates its argument to WHNF - is this enough? If I have a 
tuple containing two 
lists won't this only evaluate the tuple construtor and leave the lists as 
thunks? This is 
actually the case in my code.

As I said previously, it seems that Criterion somehow evaluates the data so 
that time needed for 
its creation is not included in the benchmark. I modified my dataBuild function 
to look lik this:

dataBuild gen = unsafePerformIO $ do
let x = (take 6 $ randoms gen, take 2048 $ randoms gen)
delayThread 100
return x

When I ran the benchmark, criterion estimated the time needed to complete it to 
over 100 seconds 
(which means that delayThread worked and was used as a basis for estimation), 
but the benchamrk 
was finished much faster and there was no difference in the final result 
comparing to the normal 
dataBuild function. This suggests that once data was created and used for 
estimation, the 
dataBuild function was not used again. The main question is: is this 
observation correct? In this 
question on SO: 
http://stackoverflow.com/questions/6637968/how-to-use-criterion-to-measure-performance-of-haskell-programs
 
one of the aswers says that there is no automatic memoization, while it looks 
that in fact the 
values of dataBuild are memoized. I have a feeling that I am misunderstanding 
something.

> I don't know if you have already read them,
> but Tibell's slides on High Performance Haskell are pretty good:
>
> http://www.slideshare.net/tibbe/highperformance-haskell
>
> There is a section at the end where he runs several tests using Criterion.
I skimmed the slides and slide 59 seems to show that my concerns regarding WHNF 
might be true.

Janek

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


Re: [Haskell-cafe] A yet another question about subtyping and heterogeneous collections

2012-10-18 Thread MigMit
Why do you need "ALike x", "BLike x" etc.? Why not just "Like u x"?

Отправлено с iPhone

Oct 18, 2012, в 14:36, Dmitry Vyal  написал(а):

> Hello list!
> 
> I've been experimenting with emulating subtyping and heterogeneous 
> collections in Haskell. I need this to parse a binary representation of 
> objects of a class hierarchy in C++ program.
> 
> So far I implemented upcasting using a chain of type classes and now I'm 
> playing with heterogeneous lists. For future purposes It would be ideal to be 
> able to have something like these functions:
> upcast_list :: [LikeC] -> [LikeA]
> downcast_list :: [LikeA] -> [LikeC]
> 
> First one only replaces the existential wrapper leaving the actual value 
> intact, and the second one also filters the list, passing the elements with 
> specific enough type.
> 
> I can implement this particular functions, but what's about a more general 
> one? Something like cast_list :: [a] -> [b], where a and b are existential 
> types from one hierarchy. Something like LikeA and LikeC in my example.
> 
> Is my approach feasible? Is there a better one? Am I missing something 
> obvious?
> Any relevant advices are welcome.
> 
> The example code follows:
> 
> {-# LANGUAGE FlexibleInstances, UndecidableInstances, OverlappingInstances, 
> ExistentialQuantification, DeriveDataTypeable #-}
> 
> import Data.Typeable
> import Data.Maybe
> 
> data A = A {a_x :: Int} deriving (Show, Typeable)
> data B = B {b_x :: Int, b_a :: A} deriving (Show, Typeable)
> data C = C {c_z :: Int, c_b :: B} deriving (Show, Typeable)
> data D = D {d_w :: Int, d_c :: C, d_a :: A} deriving (Show, Typeable)
> 
> class ALike x where toA :: x -> A
> class BLike x where toB :: x -> B
> class CLike x where toC :: x -> C
> class DLike x where toD :: x -> D
> 
> instance ALike A where toA = id
> instance BLike B where toB = id
> instance CLike C where toC = id
> instance DLike D where toD = id
> 
> instance ALike B where toA = b_a
> instance BLike C where toB = c_b
> instance CLike D where toC = d_c
> 
> instance (BLike x) => (ALike x) where
>  toA = (toA :: B -> A) . toB
> instance CLike x => BLike x where
>  toB = toB . toC
> 
> a1 = A 1
> b1 = B 2 (A 2)
> c1 = C 3 b1
> d1 = D 4 c1 (A 10)
> 
> print_a :: ALike x => x -> String
> print_a v = "A = " ++ show (a_x $ toA v)
> 
> sum_a :: (ALike x, ALike y) => x -> y -> String
> sum_a v1 v2 = "A1 = " ++ show (a_x $ toA v1) ++ " A2 = " ++ show (a_x $ toA 
> v2)
> 
> 
> data LikeA = forall a. (ALike a, Typeable a) => LikeA a
> 
> instance ALike LikeA where
>  toA (LikeA x) = toA x
> 
> get_mono :: Typeable b => [LikeA] -> [b]
> get_mono = catMaybes . map ((\(LikeA x) -> cast x))
> 
> data LikeC = forall c. (CLike c, Typeable c) => LikeC c
> 
> instance CLike LikeC where
>  toC (LikeC x) = toC x
> 
> lst_a = [LikeA a1, LikeA b1, LikeA c1, LikeA d1]
> lst_c = [LikeC c1, LikeC d1]
> 
> ___
> 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


[Haskell-cafe] A yet another question about subtyping and heterogeneous collections

2012-10-18 Thread Dmitry Vyal

Hello list!

I've been experimenting with emulating subtyping and heterogeneous 
collections in Haskell. I need this to parse a binary representation of 
objects of a class hierarchy in C++ program.


So far I implemented upcasting using a chain of type classes and now I'm 
playing with heterogeneous lists. For future purposes It would be ideal 
to be able to have something like these functions:

upcast_list :: [LikeC] -> [LikeA]
downcast_list :: [LikeA] -> [LikeC]

First one only replaces the existential wrapper leaving the actual value 
intact, and the second one also filters the list, passing the elements 
with specific enough type.


I can implement this particular functions, but what's about a more 
general one? Something like cast_list :: [a] -> [b], where a and b are 
existential types from one hierarchy. Something like LikeA and LikeC in 
my example.


Is my approach feasible? Is there a better one? Am I missing something 
obvious?

Any relevant advices are welcome.

The example code follows:

{-# LANGUAGE FlexibleInstances, UndecidableInstances, 
OverlappingInstances, ExistentialQuantification, DeriveDataTypeable #-}


import Data.Typeable
import Data.Maybe

data A = A {a_x :: Int} deriving (Show, Typeable)
data B = B {b_x :: Int, b_a :: A} deriving (Show, Typeable)
data C = C {c_z :: Int, c_b :: B} deriving (Show, Typeable)
data D = D {d_w :: Int, d_c :: C, d_a :: A} deriving (Show, Typeable)

class ALike x where toA :: x -> A
class BLike x where toB :: x -> B
class CLike x where toC :: x -> C
class DLike x where toD :: x -> D

instance ALike A where toA = id
instance BLike B where toB = id
instance CLike C where toC = id
instance DLike D where toD = id

instance ALike B where toA = b_a
instance BLike C where toB = c_b
instance CLike D where toC = d_c

instance (BLike x) => (ALike x) where
  toA = (toA :: B -> A) . toB
instance CLike x => BLike x where
  toB = toB . toC

a1 = A 1
b1 = B 2 (A 2)
c1 = C 3 b1
d1 = D 4 c1 (A 10)

print_a :: ALike x => x -> String
print_a v = "A = " ++ show (a_x $ toA v)

sum_a :: (ALike x, ALike y) => x -> y -> String
sum_a v1 v2 = "A1 = " ++ show (a_x $ toA v1) ++ " A2 = " ++ show (a_x $ 
toA v2)



data LikeA = forall a. (ALike a, Typeable a) => LikeA a

instance ALike LikeA where
  toA (LikeA x) = toA x

get_mono :: Typeable b => [LikeA] -> [b]
get_mono = catMaybes . map ((\(LikeA x) -> cast x))

data LikeC = forall c. (CLike c, Typeable c) => LikeC c

instance CLike LikeC where
  toC (LikeC x) = toC x

lst_a = [LikeA a1, LikeA b1, LikeA c1, LikeA d1]
lst_c = [LikeC c1, LikeC d1]

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


[Haskell-cafe] Fwd: hdbc parametrized select

2012-10-18 Thread Wilfried van Asten
This was not sent to the cafe since I used the wrong from address.

-- Forwarded message --
From: Asten, W.G.G. van (Wilfried, Student M-CSC)

Date: Thu, Oct 18, 2012 at 12:27 PM
Subject: Re: [Haskell-cafe] hdbc parametrized select
To: s9gf4...@gmail.com
Cc: haskell-cafe@haskell.org


To my knowledge you can combine execute and the fetch functions like this:

find conn id =
  do
stmt <- prepare conn "SELECT * FROM table WHERE id = ? LIMIT 1"
excute stmt [id]
row <- fetchRow stmt

On Thu, Oct 18, 2012 at 10:51 AM,   wrote:
> does hdbc have parametrized selects ?
> There is execute
> execute :: Statement -> [SqlValue] -> IO Integer
> and some other functions which get list of parameters but return IO Integer or
> IO ()
> and there is other couple of functions
> fetchRow :: Statement -> IO (Maybe [SqlValue])
> which return values of select but do not get parameters
>
> How can i execute parametrized select with hdbc ?
>
> ___
> 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] How to correctly benchmark code with Criterion?

2012-10-18 Thread Alfredo Di Napoli
I don't know if you have already read them,
but Tibell's slides on High Performance Haskell are pretty good:

http://www.slideshare.net/tibbe/highperformance-haskell

There is a section at the end where he runs several tests using Criterion.

HTH,
A.

On 18 October 2012 11:45, Claude Heiland-Allen  wrote:

> Hi Janek,
>
>
> On 18/10/12 10:23, Janek S. wrote:
>
>> during past few days I spent a lot of time trying to figure out how to
>> write Criterion benchmarks,
>> so that results don't get skewed by lazy evaluation. I want to benchmark
>> different versions of an
>> algorithm doing numerical computations on a vector. For that I need to
>> create an input vector
>> containing a few thousand elements. I decided to create random data, but
>> that really doesn't
>> matter - I could have as well use infinite lists instead of random ones.
>>
>
> [snip]
>
>
>  The question is how to generate data so that its evaluation won't be
>> included in the benchmark.
>>
>
> Something like this might work, not sure what the canonical way is.
>
> ---8<---
> main = do
>   ...
>   let input = L.dataBuild gen
>   evaluate (rnf input)
>   defaultMain
>  ...
>  bench "Lists" $ nf L.benchThisFunction input
>  ...
> ---8<---
>
> I did use something like this in practice here:
>
> https://gitorious.org/bitwise/**bitwise/blobs/master/extra/**
> benchmark.hs#line155
>
> Thanks,
>
>
> Claude
> --
> http://mathr.co.uk
>
>
> __**_
> 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] How to correctly benchmark code with Criterion?

2012-10-18 Thread Claude Heiland-Allen

Hi Janek,

On 18/10/12 10:23, Janek S. wrote:

during past few days I spent a lot of time trying to figure out how to write 
Criterion benchmarks,
so that results don't get skewed by lazy evaluation. I want to benchmark 
different versions of an
algorithm doing numerical computations on a vector. For that I need to create 
an input vector
containing a few thousand elements. I decided to create random data, but that 
really doesn't
matter - I could have as well use infinite lists instead of random ones.


[snip]


The question is how to generate data so that its evaluation won't be included 
in the benchmark.


Something like this might work, not sure what the canonical way is.

---8<---
main = do
  ...
  let input = L.dataBuild gen
  evaluate (rnf input)
  defaultMain
 ...
 bench "Lists" $ nf L.benchThisFunction input
 ...
---8<---

I did use something like this in practice here:

https://gitorious.org/bitwise/bitwise/blobs/master/extra/benchmark.hs#line155

Thanks,


Claude
--
http://mathr.co.uk

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


[Haskell-cafe] How to correctly benchmark code with Criterion?

2012-10-18 Thread Janek S.
Dear list,

during past few days I spent a lot of time trying to figure out how to write 
Criterion benchmarks, 
so that results don't get skewed by lazy evaluation. I want to benchmark 
different versions of an 
algorithm doing numerical computations on a vector. For that I need to create 
an input vector 
containing a few thousand elements. I decided to create random data, but that 
really doesn't 
matter - I could have as well use infinite lists instead of random ones.

My problem is that I am not certain if I am creating my benchmark correctly. I 
wrote a function 
that creates data like this:

dataBuild :: RandomGen g => g -> ([Double], [Double])
dataBuild gen = (take 6 $ randoms gen, take 2048 $ randoms gen)

And I create benchmark like this:

bench "Lists" $ nf L.benchThisFunction (L.dataBuild gen)

The question is how to generate data so that its evaluation won't be included 
in the benchmark. I 
already asked this question on StackOverflow ( 
http://stackoverflow.com/questions/12896235/how-to-create-data-for-criterion-benchmarks#comment17466915_12896235
 ) 
and got answer to use evaluate + force. After spending one day on  testing this 
approach I came 
to conclusion that doing this does not seem to influence results of a benchmark 
in any way (I did 
stuf like unsagePerformIO + delayThread). On the other hand I looked into 
sources of criterion 
and I see that the benchmark code is run like this: evaluate (rnf (f x))
I am a Haskell newbie and perhaps don't interpret this correctly, but to me it 
looks as though 
criterion did not evaluate the possibly non-evaluated parameter x before 
running the benchmark, 
but instead evaluates the final result. Can someone provide an explanation on 
how this exactly 
works and how should I write my benchmarks so that results are correct?

Janek

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


Re: [Haskell-cafe] tplot (out of memory)

2012-10-18 Thread malcolm.wallace
Did you ever solve this?  I have a similar message ( user error (out of memory) ) arising from a different app (not tplot) that uses the Haskell Chart library (and cairo underneath).  On some linux machines, it crashes, on others it works fine.  I can find no environment differences between the machines.  The app does not use a lot of memory, and the machine is not running out of physical or swap. Regards,
MalcolmOn 04 Sep, 2012,at 04:01 PM, Eugene Kirpichov  wrote:Hi Manish,  Please provide the input file, I'll debug this.  On Mon, Sep 3, 2012 at 1:06 PM, Manish Trivedi  wrote: > Hi, > > I am running into a weird out of memory issue. While running timeplot over > an input file having ~800 rows. From below provided info, seems like machine > has enough ram (1849MB). > Please let me know if anyone has pointers. > > # free -m > total used free shared buffers cached > Mem: 3825 1975 1849 0 13 71 > -/+ buffers/cache: 1891 1934 > Swap: 4031 111 3920 > > #time tplot -o out.png -or 1024x768 -k 'CurrentPerHour' 'lines' -k > 'RequiredPerHour' 'lines' -if adgroup_delivery_chart.input -tf 'date > %Y-%m-%d %H:%M:%OS' > > tplot: user error (out of memory) > > real 0m0.026s > user 0m0.018s > sys 0m0.008s > > -Manish > > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe >--  Eugene Kirpichov http://www.linkedin.com/in/eugenekirpichov  ___ 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


[Haskell-cafe] hdbc parametrized select

2012-10-18 Thread s9gf4ult
does hdbc have parametrized selects ? 
There is execute
execute :: Statement -> [SqlValue] -> IO Integer
and some other functions which get list of parameters but return IO Integer or 
IO ()
and there is other couple of functions
fetchRow :: Statement -> IO (Maybe [SqlValue])
which return values of select but do not get parameters

How can i execute parametrized select with hdbc ?

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