Re: [Haskell-cafe] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread Ryan Ingram
It depends what you mean by "faster"; more efficient (runtime) or less
typing (programmer time!)

For the former, you have basically the best implementation there is;
you are basically encoding the continuation of (++) into the
accumulating list of arguments to evs.  You might want to consider
difference lists to simplify the definition, however; the performance
should be comparable:

newtype DList a = DL ([a] -> [a])

dlToList :: DList a -> [a]
dlToList (DL l) = l []

dlSingleton :: a -> DList a
dlSingleton = DL . (:)

dlConcat :: DList a -> DList a -> DList a
dlConcat (DL l1) (DL l2) = DL (l1 . l2)

varsDL :: Prp a -> DList a
varsDL (Var a) = dlSingleton a
varsDL (Not a) = varsDL a
varsDL (Or a b) = varsDL a `dlConcat` varsDL b
-- etc.

If you want less typing, consider some form of generics programming
such as using "Scrap your Boilerplate"; see
http://www.cs.vu.nl/boilerplate/

data Prp a = ... deriving (Eq, Show, Data, Typeable)

-- note that this gives the wrong result for Prp Bool because of Cns.
-- this is fixable, see http://www.cs.vu.nl/boilerplate/testsuite/foldTree.hs
varsGeneric :: forall a. Typeable a => Prp a -> [a]
varsGeneric = listify (\x -> case (x :: a) of _ -> True)

  -- ryan

On 2/20/08, Cetin Sert <[EMAIL PROTECTED]> wrote:
> -- proposition
> data Prp a = Var a
>| Not (Prp a)
>| Or  (Prp a) (Prp a)
>| And (Prp a) (Prp a)
>| Imp (Prp a) (Prp a)
>| Xor (Prp a) (Prp a)
>| Eqv (Prp a) (Prp a)
>| Cns Bool
>deriving (Show, Eq)
>
> -- Here are to variable extraction methods
>
> -- variable extraction reference imp.
> -- Graham Hutton: Programming in Haskell, 107
> vars_ :: Prp a → [a]
> vars_ (Cns _)   = []
> vars_ (Var x)   = [x]
> vars_ (Not p)   = vars_ p
> vars_ (Or  p q) = vars_ p ++ vars_ q
> vars_ (And p q) = vars_ p ++ vars_ q
> vars_ (Imp p q) = vars_ p ++ vars_ q
> vars_ (Xor p q) = vars_ p ++ vars_ q
> vars_ (Eqv p q) = vars_ p ++ vars_ q
>
> -- variable extraction new * this is faster
> vars :: Prp a → [a]
> vars p = evs [p]
>   where
> evs []   = []
> evs (Cns _  :ps) = []
> evs (Var x  :ps) = x:evs ps
> evs (Not p  :ps) = evs (p:ps)
> evs (Or  p q:ps) = evs (p:q:ps)
> evs (And p q:ps) = evs (p:q:ps)
> evs (Imp p q:ps) = evs (p:q:ps)
> evs (Xor p q:ps) = evs (p:q:ps)
> evs (Eqv p q:ps) = evs (p:q:ps)
>
> -- for  : Not (Imp (Or (Var 'p') (Var 'q')) (Var p))
> -- vars_: ['p','q','p']
> -- vars : ['p','q','p']
>
> -- order and the fact that 'p' appears twice being irrelevant:
> -- is there an even faster way to do this?
> --
> -- Cetin Sert
> -- www.corsis.de
>
> ___
> 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] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread ajb

G'day all.

Quoting Cetin Sert <[EMAIL PROTECTED]>:


-- proposition
data Prp a = Var a
   | Not (Prp a)
   | Or  (Prp a) (Prp a)
   | And (Prp a) (Prp a)
   | Imp (Prp a) (Prp a)
   | Xor (Prp a) (Prp a)
   | Eqv (Prp a) (Prp a)
   | Cns Bool
   deriving (Show, Eq)


This is probably the fastest:

vars :: Prp a -> [a]
vars p = vars' p []
  where
vars' (Var a) = (a:)
vars' (Not p) = vars' p
vars' (Or l r) = vars' l . vars' r
{- etc -}
vars' (Cns _) = id

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


Re: [Haskell-cafe] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread Cetin Sert
plong 0 = Var 0
plong n | even n= Or  (Var n) (plong (n-1))
| otherwise = And (Var n) (plong (n-1))

main = do print ((length ∘ vars) (plong 1000))
real0m3.290s
user0m3.152s
sys 0m0.020s

main = do print ((length ∘ vars_) (plong 1000))
real0m3.732s
user0m3.680s
sys 0m0.024s

-- vrsn=varsBromage
main = do print ((length ∘ vrsn) (plong 1000))
real0m4.164s
user0m4.128s
sys 0m0.008s

ghc -fglasgow-exts -O2
ghc 6.8.2

@Andrew:
It is astonishing to see that your version actually performs the worst (at
least on my machine). By looking at your code I had also thought that yours
would be the fastest in terms of runtime performance, it was also exactly
what I tried but failed to get to here on my own. Maybe future ghc versions
will change this in favour of your version.

I would like to have someone test it on another machine though:

fetch: svn co https://okitsune.svn.sourceforge.net/svnroot/okitsune .
build: ghc -fglasgow-exts -O2 Common.hs Propositions.hs Test.hs
testS: time ./a.out sert
testH: time ./a.out hutton
testB: time ./a.out bromage

Best regards,
Cetin Sert.

On 21/02/2008, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote:
>
> G'day all.
>
>
> Quoting Cetin Sert <[EMAIL PROTECTED]>:
>
> > -- proposition
> > data Prp a = Var a
> >| Not (Prp a)
> >| Or  (Prp a) (Prp a)
> >| And (Prp a) (Prp a)
> >| Imp (Prp a) (Prp a)
> >| Xor (Prp a) (Prp a)
> >| Eqv (Prp a) (Prp a)
> >| Cns Bool
> >deriving (Show, Eq)
>
>
> This is probably the fastest:
>
> vars :: Prp a -> [a]
> vars p = vars' p []
>where
>  vars' (Var a) = (a:)
>
>  vars' (Not p) = vars' p
>
>  vars' (Or l r) = vars' l . vars' r
>  {- etc -}
>  vars' (Cns _) = id
>
> Cheers,
> Andrew Bromage
>
> ___
> 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] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread Derek Elkins
On Thu, 2008-02-21 at 05:10 +0100, Cetin Sert wrote:
> plong 0 = Var 0
> plong n | even n= Or  (Var n) (plong (n-1))
> | otherwise = And (Var n) (plong (n-1))

compare the times again but with plong as follows:
plong 0 = Var 0
plong n | even n = Or (plong (n-1)) (Var n)
| otherwise = And (plong (n-1)) (Var n)

>  
> 
> main = do print ((length ∘ vars) (plong 1000))
> real0m3.290s
> user0m3.152s
> sys 0m0.020s
> 
> main = do print ((length ∘ vars_) (plong 1000))
> real0m3.732s
> user0m3.680s
> sys 0m0.024s
> 
> -- vrsn=varsBromage
> main = do print ((length ∘ vrsn) (plong 1000))
> real0m4.164s
> user0m4.128s
> sys 0m0.008s
> 
> ghc -fglasgow-exts -O2
> ghc 6.8.2
> 
> @Andrew:
> It is astonishing to see that your version actually performs the worst
> (at least on my machine). By looking at your code I had also thought
> that yours would be the fastest in terms of runtime performance, it
> was also exactly what I tried but failed to get to here on my own.
> Maybe future ghc versions will change this in favour of your version.
> 
> I would like to have someone test it on another machine though:
> 
> fetch: svn co https://okitsune.svn.sourceforge.net/svnroot/okitsune .
> build: ghc -fglasgow-exts -O2 Common.hs Propositions.hs Test.hs
> testS: time ./a.out sert
> testH: time ./a.out hutton
> testB: time ./a.out bromage
> 
> 
> Best regards,
> Cetin Sert.
> 
> On 21/02/2008, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote:
> G'day all.
> 
> 
> Quoting Cetin Sert <[EMAIL PROTECTED]>:
> 
> > -- proposition
> > data Prp a = Var a
> >| Not (Prp a)
> >| Or  (Prp a) (Prp a)
> >| And (Prp a) (Prp a)
> >| Imp (Prp a) (Prp a)
> >| Xor (Prp a) (Prp a)
> >| Eqv (Prp a) (Prp a)
> >| Cns Bool
> >deriving (Show, Eq)
> 
> 
> This is probably the fastest:
> 
> vars :: Prp a -> [a]
> vars p = vars' p []
>where
>  vars' (Var a) = (a:)
> 
>  vars' (Not p) = vars' p
> 
>  vars' (Or l r) = vars' l . vars' r
>  {- etc -}
>  vars' (Cns _) = id
> 
> Cheers,
> Andrew Bromage
> 
> ___
> 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread ajb

G'day all.

Quoting Cetin Sert <[EMAIL PROTECTED]>:


It is astonishing to see that your version actually performs the worst (at
least on my machine).


On your example, I'm not surprised:


plong 0 = Var 0
plong n | even n= Or  (Var n) (plong (n-1))
| otherwise = And (Var n) (plong (n-1))


This is effectively a singly linked list.  I would expect my (well, I
didn't invent it) to work better on something that didn't have this
unique structure, such as:

test 0 = Var 0
test n | even n= Or  (Var n) (test (n-1))
   | otherwise = And (test (n-1)) (Var n)

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


Re: [Haskell-cafe] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread Cetin Sert
[EMAIL PROTECTED]:~/workspace/Haskell-1/bin$ time ./theResult sert
101

real0m1.384s
user0m1.148s
sys 0m0.112s

[EMAIL PROTECTED]:~/workspace/Haskell-1/bin$ time ./theResult bromage
101

real0m2.240s
user0m1.972s
sys 0m0.176s

[EMAIL PROTECTED]:~/workspace/Haskell-1/bin$ time ./theResult bromage
1001

real0m59.875s
user0m58.080s
sys 0m1.656s

[EMAIL PROTECTED]:~/workspace/Haskell-1/bin$ time ./theResult sert
1001

real0m32.043s
user0m30.930s
sys 0m0.992s


Hutton seems to fail miserably in both lengths here o_O

I was not aware of the effect of structures on performance.
Thanks for reminding me!

Best Regards,
Cetin Sert

On 21/02/2008, Derek Elkins <[EMAIL PROTECTED]> wrote:
>
> On Thu, 2008-02-21 at 05:10 +0100, Cetin Sert wrote:
> > plong 0 = Var 0
> > plong n | even n= Or  (Var n) (plong (n-1))
> > | otherwise = And (Var n) (plong (n-1))
>
>
> compare the times again but with plong as follows:
> plong 0 = Var 0
> plong n | even n = Or (plong (n-1)) (Var n)
> | otherwise = And (plong (n-1)) (Var n)
>
>
> >
> >
> > main = do print ((length ∘ vars) (plong 1000))
> > real0m3.290s
> > user0m3.152s
> > sys 0m0.020s
> >
> > main = do print ((length ∘ vars_) (plong 1000))
> > real0m3.732s
> > user0m3.680s
> > sys 0m0.024s
> >
> > -- vrsn=varsBromage
> > main = do print ((length ∘ vrsn) (plong 1000))
> > real0m4.164s
> > user0m4.128s
> > sys 0m0.008s
> >
> > ghc -fglasgow-exts -O2
> > ghc 6.8.2
> >
> > @Andrew:
> > It is astonishing to see that your version actually performs the worst
> > (at least on my machine). By looking at your code I had also thought
> > that yours would be the fastest in terms of runtime performance, it
> > was also exactly what I tried but failed to get to here on my own.
> > Maybe future ghc versions will change this in favour of your version.
> >
> > I would like to have someone test it on another machine though:
> >
> > fetch: svn co https://okitsune.svn.sourceforge.net/svnroot/okitsune .
> > build: ghc -fglasgow-exts -O2 Common.hs Propositions.hs Test.hs
> > testS: time ./a.out sert
> > testH: time ./a.out hutton
> > testB: time ./a.out bromage
> >
> >
> > Best regards,
> > Cetin Sert.
> >
> > On 21/02/2008, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote:
> > G'day all.
> >
> >
> > Quoting Cetin Sert <[EMAIL PROTECTED]>:
> >
> > > -- proposition
> > > data Prp a = Var a
> > >| Not (Prp a)
> > >| Or  (Prp a) (Prp a)
> > >| And (Prp a) (Prp a)
> > >| Imp (Prp a) (Prp a)
> > >| Xor (Prp a) (Prp a)
> > >| Eqv (Prp a) (Prp a)
> > >| Cns Bool
> > >deriving (Show, Eq)
> >
> >
> > This is probably the fastest:
> >
> > vars :: Prp a -> [a]
> > vars p = vars' p []
> >where
> >  vars' (Var a) = (a:)
> >
> >  vars' (Not p) = vars' p
> >
> >  vars' (Or l r) = vars' l . vars' r
> >  {- etc -}
> >  vars' (Cns _) = id
> >
> > Cheers,
> > Andrew Bromage
> >
> > ___
> > 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread Cetin Sert
> I would expect my (well, I didn't invent it) to work better on something
that didn't have this unique structure, such as:
> test 0 = Var 0
> test n | even n= Or  (Var n) (test (n-1))
>   | otherwise = And (test (n-1)) (Var n)

for some reason this still does not perform as well as it should o__O
I think function composition might somehow be the bottleneck behind this.

--with
plong 0 = Var 0
plong n | even n= Or  (Var n) (plong (n-1))
| otherwise = And (plong (n-1)) (Var n)

--and n = 100

[EMAIL PROTECTED]:~/workspace/Haskell-1/bin$ time ./theResult sert
101

real0m0.692s
user0m0.624s
sys 0m0.040s

[EMAIL PROTECTED]:~/workspace/Haskell-1/bin$ time ./theResult sert
101

real0m0.696s
user0m0.644s
sys 0m0.036s

[EMAIL PROTECTED]:~/workspace/Haskell-1/bin$ time ./theResult sert
101

real0m0.840s
user0m0.744s
sys 0m0.052s

[EMAIL PROTECTED]:~/workspace/Haskell-1/bin$ time ./theResult bromage
101

real0m1.561s
user0m1.360s
sys 0m0.100s

[EMAIL PROTECTED]:~/workspace/Haskell-1/bin$ time ./theResult bromage
101

real0m1.692s
user0m1.392s
sys 0m0.136s

[EMAIL PROTECTED]:~/workspace/Haskell-1/bin$ time ./theResult bromage
101

real0m1.959s
user0m1.580s
sys 0m0.116s

Best Regards,
Cetin Sert

On 21/02/2008, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote:
>
> G'day all.
>
> Quoting Cetin Sert <[EMAIL PROTECTED]>:
>
>
> > It is astonishing to see that your version actually performs the worst
> (at
> > least on my machine).
>
>
> On your example, I'm not surprised:
>
>
> > plong 0 = Var 0
> > plong n | even n= Or  (Var n) (plong (n-1))
> > | otherwise = And (Var n) (plong (n-1))
>
>
> This is effectively a singly linked list.  I would expect my (well, I
> didn't invent it) to work better on something that didn't have this
> unique structure, such as:
>
> test 0 = Var 0
> test n | even n= Or  (Var n) (test (n-1))
> | otherwise = And (test (n-1)) (Var n)
>
>
> Cheers,
> Andrew Bromage
> ___
> 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