Re: [Haskell-cafe] Data structure

2011-09-01 Thread Ketil Malde
yrazes yra...@gmail.com writes:

 I want to compare data structure between Haskell, Java, Lisp and C. I am
 wondering if I could compare list comprehention in haskell with the vector
 class in Java, macros in common lisp and dynamic arrays in C.

You /can/ compare them, of course, but they are very different
concepts.  I'd classify list comprehensions and macros as control
structures, rather than data structures, for instance.

Wouldn't it be more appropriate to compare Haskell's algebraic data
types with C structs, Java classes, and Lisp S-expressions?

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


[Haskell-cafe] Finger Tree without using Monoid

2011-09-01 Thread Xinyu LIU
Hi,

I was trying to implement MTF (move-to-front) algorithm, However, neither
Array nor List satisfied all aspects.
  Array: Although the random access is O(1), However, move an element to
front takes O(N) in average;
  List: Although move to front is O(1), However, random access takes O(N) in
average;

I dig out the paper [1] and find the Finger Tree solution. There is already
good Finger Tree implementation in Haskell as Data.Sequence [2] based on
[3].

I wrote a simple version based on the original paper, but avoid using Monoid
when augment (or cache) the size of the tree. The idea is to wrap every
element as a leaf of node.
This idea is similar to the Chris Okasaki's binary random access list [4].

As one test case, I tested move to front with Finger Tree.

Here is the code (sorry for a bit long):


module FingerTree where

import Test.QuickCheck

data Node a = Br Int [a] deriving (Show) -- size, branches

data Tree a = Empty
| Lf a
| Tr Int [a] (Tree (Node a)) [a] -- size, front, middle, rear
  deriving (Show)

type FList a = Tree (Node a)

-- Auxiliary functions for calculate size of node and tree

size :: Node a - Int
size (Br s _) = s

sizeL :: [Node a] - Int
sizeL = sum .(map size)

sizeT :: FList a - Int
sizeT Empty = 0
sizeT (Lf a) = size a
sizeT (Tr s _ _ _) = s

-- Auxiliary functions for building and unboxing node(s)

wrap :: a - Node a
wrap x = Br 1 [x]

unwrap :: Node a - a
unwrap (Br 1 [x]) = x

wraps :: [Node a] - Node (Node a)
wraps xs = Br (sizeL xs) xs

unwraps :: Node a - [a]
unwraps (Br _ xs) = xs

-- Helper function for building tree

tree :: [Node a] - FList (Node a) - [Node a] - FList a
tree f Empty [] = foldr cons' Empty f
tree [] Empty r = foldr cons' Empty r
tree [] m r = let (f, m') = uncons' m in tree (unwraps f) m' r
tree f m [] = let (m', r) = unsnoc' m in tree f m' (unwraps r)
tree f m r = Tr (sizeL f + sizeT m + sizeL r) f m r

-- Operations at the front of the sequence

cons :: a - FList a - FList a
cons a t = cons' (wrap a) t

cons' :: (Node a) - FList a - FList a
cons' a Empty = Lf a
cons' a (Lf b) = tree [a] Empty [b]
cons' a (Tr _ [b, c, d, e] m r) = tree [a, b] (cons' (wraps [c, d, e]) m) r
cons' a (Tr _ f m r) = tree (a:f) m r

uncons :: FList a - (a, FList a)
uncons ts = let (t, ts') = uncons' ts in (unwrap t, ts')

uncons' :: FList a - ((Node a), FList a)
uncons' (Lf a) = (a, Empty)
uncons' (Tr _ [a] Empty [b]) = (a, Lf b)
uncons' (Tr _ [a] Empty (r:rs)) = (a, tree [r] Empty rs)
uncons' (Tr _ [a] m r) = (a, tree (unwraps f) m' r) where (f, m') = uncons'
m
uncons' (Tr _ (a:f) m r) = (a, tree f m r)

head' :: FList a - a
head' = fst . uncons

tail' :: FList a - FList a
tail' = snd . uncons

-- Operations at the rear of the sequence

snoc :: FList a - a - FList a
snoc t a = snoc' t (wrap a)

snoc' :: FList a - Node a - FList a
snoc' Empty a = Lf a
snoc' (Lf a) b = tree [a] Empty [b]
snoc' (Tr _ f m [a, b, c, d]) e = tree f (snoc' m (wraps [a, b, c])) [d, e]
snoc' (Tr _ f m r) a = tree f m (r++[a])

unsnoc :: FList a - (FList a, a)
unsnoc ts = let (ts', t) = unsnoc' ts in (ts', unwrap t)

unsnoc' :: FList a - (FList a, (Node a))
unsnoc' (Lf a) = (Empty, a)
unsnoc' (Tr _ [a] Empty [b]) = (Lf a, b)
unsnoc' (Tr _ f@(_:_) Empty [a]) = (tree (init f) Empty [last f], a)
unsnoc' (Tr _ f m [a]) = (tree f m' (unwraps r), a) where (m', r) = unsnoc'
m
unsnoc' (Tr _ f m r) = (tree f m (init r), (last r))

last' :: FList a - a
last' = snd . unsnoc

init' :: FList a - FList a
init' = fst . unsnoc

-- Concatenation

concat' :: FList a - FList a - FList a
concat' t1 t2 = merge t1 [] t2

merge :: FList a - [Node a] - FList a - FList a
merge Empty ts t2 = foldr cons' t2 ts
merge t1 ts Empty = foldl snoc' t1 ts
merge (Lf a) ts t2 = merge Empty (a:ts) t2
merge t1 ts (Lf a) = merge t1 (ts++[a]) Empty
merge (Tr s1 f1 m1 r1) ts (Tr s2 f2 m2 r2) =
Tr (s1 + s2 + (sizeL ts)) f1 (merge m1 (nodes (r1 ++ ts ++ f2)) m2) r2

nodes :: [Node a] - [Node (Node a)]
nodes [a, b] = [wraps [a, b]]
nodes [a, b, c] = [wraps [a, b, c]]
nodes [a, b, c, d] = [wraps [a, b], wraps [c, d]]
nodes (a:b:c:xs) = (wraps [a, b, c]):nodes xs

-- Splitting

splitAt' :: Int - FList a - (FList a, Node a, FList a)
splitAt' _ (Lf x) = (Empty, x, Empty)
splitAt' i (Tr _ f m r)
| i  szf = let (xs, y, ys) = splitNodesAt i f
in ((foldr cons' Empty xs), y, tree ys m r)
| i  szf + szm = let (m1, t, m2) = splitAt' (i-szf) m
  (xs, y, ys) = splitNodesAt (i-szf - sizeT m1)
(unwraps t)
  in (tree f m1 xs, y, tree ys m2 r)
| otherwise = let (xs, y, ys) = splitNodesAt (i-szf -szm) r
  in (tree f m xs, y, foldr cons' Empty ys)
where
  szf = sizeL f
  szm = sizeT m

splitNodesAt :: Int - [Node a] - ([Node a], Node a, [Node a])
splitNodesAt 0 [x] = ([], x, [])
splitNodesAt i (x:xs) | i  size x = ([], x, xs)
  | otherwise = let (xs', y, ys) = splitNodesAt (i-size
x) xs
 

Re: [Haskell-cafe] Data structure

2011-09-01 Thread yrazes
sure!

types are something you can compare and the differences are so clear

but I will probe the code in some programs like bubble sort
(least efficient)

including DataBase (HDBC) and MySql...

This time, my mail is concerning about queuing theory, h... I tough
list are nice concept for this purpose... I wan't so sure about the other
languages.

Julita


On Thu, Sep 1, 2011 at 2:16 AM, Ketil Malde ke...@malde.org wrote:

 yrazes yra...@gmail.com writes:

  I want to compare data structure between Haskell, Java, Lisp and C. I am
  wondering if I could compare list comprehention in haskell with the
 vector
  class in Java, macros in common lisp and dynamic arrays in C.

 You /can/ compare them, of course, but they are very different
 concepts.  I'd classify list comprehensions and macros as control
 structures, rather than data structures, for instance.

 Wouldn't it be more appropriate to compare Haskell's algebraic data
 types with C structs, Java classes, and Lisp S-expressions?

 -k
 --
 If I haven't seen further, it is by standing in the footprints of giants

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


Re: [Haskell-cafe] Finger Tree without using Monoid

2011-09-01 Thread Chris Smith
I'm curious why you wanted a finger tree without the Monoid instance...
if you need a different Monoid instance, you can probably simplify your
code significantly by using a newtype wrapper around Seq rather than
re-implementing it.

-- 
Chris Smith


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


Re: [Haskell-cafe] Pointed, but not Applicative

2011-09-01 Thread Ryan Ingram
On Tue, Aug 30, 2011 at 4:53 PM, Sebastian Fischer fisc...@nii.ac.jpwrote:

 I think the idea of functional lists is that the monoids of 'lists'
 and 'functions on lists' are isomorphic with isomorphisms toFList and
 toList:

toFList [] = id
toFList (xs++ys) = toFList xs . toFList ys

toList id = []
toList (f . g) = toList f ++ toList g


Oh absolutely, but my point (if you will pardon the pun), was that just
given the type

newtype FList a = FL ([a] - [a])
runFList (FL f) = f

and the law

runFList fl as = runFList fl [] ++ as

we can prove that

fmap f fl = FL $ \bs - map f (runFList fl []) ++ bs

is a valid functor instance:

fmap id
(eta expand) = \fl - fmap id fl
(apply fmap) = \fl - FL $ \bs - map id (runFList fl []) ++ bs
(map law) = \fl - FL $ \bs - id (runFList fl []) ++ bs
(apply id) = \fl - FL $ \bs - runFList fl [] ++ bs
(FList law) = \fl - FL $ \bs - runFList fl bs
(eta reduce) = \fl - FL $ runFList fl
(constructor of destructor) = \fl - fl
(unapply id) = \fl - id fl
(eta reduce) = id

We don't need to know that FList is supposed to represent an isomorphism
to/from lists, although you can derive one, as you've shown.  I just wanted
to show that it's a valid functor, but only if you assume an extra law on
the type.  The functor instance depends critically on converting back to a
list which requires that law.

There's no functor instance for this type that doesn't convert back to a
list, which is unfortunate, because you lose the performance benefits of
constant-time append!

  -- ryan
___
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-09-01 Thread Jonas Almström Duregård
Its a bug in haskell-src-meta. I just reported it:

https://github.com/benmachine/haskell-src-meta/issues/8

Regards,
Jonas



On 1 September 2011 03:19, bob zhang bobzhang1...@gmail.com wrote:
 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


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


[Haskell-cafe] ANN: hledger 0.15

2011-09-01 Thread Simon Michael
I'm pleased to announce hledger 0.15! This release includes work by
Trygve Laugstøl, Dmitry Astapov, Clint Adams, Johann Klähn and
myself, and we have added cmdargs and warp to our list of awesome
dependencies. Summary of changes: a modal cli that detects add-ons,
more powerful CSV converting, a much better web interface, a useful
account aliasing feature, more Ledger compatibility, and bugfixes.

hledger is a library and set of user tools for working with
financial data (or anything that can be tracked in a double-entry
accounting ledger.) It is a haskell port and friendly fork of John
Wiegley's Ledger. hledger provides command-line, curses and web
interfaces, and aims to be a reliable, practical tool for daily use.
Given a plain text file describing transactions of money or any
other commodity, it will print the chart of accounts, account
balances, or just the transactions you're interested in.  It can
also help you record new transactions, or convert CSV data from your
bank.

Home: http://hledger.org

IRC: irc://irc.freenode.net/#ledger

Install: cabal update; cabal install hledger
   [hledger-web hledger-vty hledger-chart hledger-interest]

Platform-specific binaries, which are time-consuming to make and
support, are now provided on request to financial donors - a great
way to give back and help pay hosting costs!

Best,
-Simon

Changes in 0.15:

  * hledger's options are now modal, providing better help (using
cmdargs)

  * hledger now lists and runs any hledger-* add-ons found in the
user's path

  * case insensitivity of filter patterns has been fixed

  * parsing: `alias`/`end aliases` directives, for renaming
accounts, are supported, like ledger's but a bit more powerful;
also an `--alias` option for renaming on the fly

  * parsing: the `account` directive now preserves posting type
(normal/virtual/balanced virtual)

  * parsing: the `pop` directive is supported as an alias for `end
tag`, like ledger

  * parsing: `P` (historical price) directives can contain a
(ignored) numeric time zone, like ledger

  * parsing: the leading `!` in directives is now optional and
deprecated, like ledger

  * parsing: entries with a negative amount in the first posting now
infer the correct balancing amount

  * parsing: bad date checking is more accurate

  * balance: collapsing of boring accounts to one line can be
disabled with `--no-elide`

  * balance: fix a wrong precision regression from last release

  * convert: standard input can be converted

  * convert: an alternate rules file can be specified with `--rules`

  * convert: `account2-field` can be used when the CSV file
specifies both accounts

  * convert: `description-field` can have a custom format and
combine multiple CSV fields

  * convert: `in-field` and `out-field` support CSV files that use
two amount columns

  * convert: don't fail when there's no default journal file

  * web: the web interface has been overhauled/cleaned up

  * web: account register views are now transaction-based, like
gnucash etc., and show accurate historical balances when
possible

  * web: simple balance charts are displayed (using flot)

  * web: more expressive and consistent search patterns, using a new
matching engine

  * web: add form uses currently focussed account as default,
redirects to itself, formats status messages better

  * web: sidebar now shows empty/boring accounts too

  * web: now uses warp and a newer yesod

  * api simplifications

  * importable Hledger, Hledger.Web, Hledger.Vty and Hledger.Chart
modules

  * the basic reports are now provided by hledger-lib for easier
reuse

  * new api use examples: `equity.hs`, `uniquify.hs`

  * some old base 3 support has been dropped

  * the old -s flag has been dropped

Stats:

Release contributors: Simon Michael, Trygve Laugstøl, Dmitry Astapov, Clint 
Adams, Johann Klähn

132 days, 314 commits, 18 end-user features and 6 end-user bugfixes since last 
release.

210 unit  functional tests and 55% unit test coverage (hledger, hledger-lib 
packages).

7642 lines of code (all packages).


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