Re: [Haskell-cafe] Interfacing real-time stocks data API

2013-10-09 Thread Alexey Uimanov
Yes, the trading system, or code generator. It depends on what would be
easier to implement. But firstly I need a simulator and history data
crawler what I am working on.


2013/10/9 Miro Karpis 

> Hi Alexey,
> thank you for response. You wrote that you are developing package for
> testing trading systems. Are you planning to also build a trading system?
>
> Regards,
> Miro
>
>
> On Wed, Oct 9, 2013 at 10:28 AM, Alexey Uimanov wrote:
>
>> I did not find such a library, but I am interested in Haskell trading
>> automation too.
>>
>> BTW, I am developing package for testing trading systems, it can just
>> download historical data from some free russian stock services for now.
>>
>> https://github.com/s9gf4ult/hadan
>>
>> If you interested we could join forces.
>>
>>
>> 2013/10/9 Miro Karpis 
>>
>>> Please, did/does anybody tried to interface with Haskell some real-time
>>> stocks data API? If yes, please which one? So far I came down to
>>> ActveTick,...
>>>
>>> thanks,
>>> m.
>>>
>>> ___
>>> 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] Interfacing real-time stocks data API

2013-10-09 Thread Alexey Uimanov
I did not find such a library, but I am interested in Haskell trading
automation too.

BTW, I am developing package for testing trading systems, it can just
download historical data from some free russian stock services for now.

https://github.com/s9gf4ult/hadan

If you interested we could join forces.


2013/10/9 Miro Karpis 

> Please, did/does anybody tried to interface with Haskell some real-time
> stocks data API? If yes, please which one? So far I came down to
> ActveTick,...
>
> thanks,
> m.
>
> ___
> 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] Lifting IO actions into Applicatives

2013-10-01 Thread Alexey Uimanov
Maybe this is needed new typeclass ApplicativeTrans?


2013/10/1 Michael Snoyman 

> I'm wondering if anyone's run into this problem before, and if there's a
> common solution.
>
> In Yesod, we have applicative forms (based originally on formlets). These
> forms are instances of Applicative, but not of Monad. Let's consider a
> situation where we want to get some user input to fill out a blog post
> datatype, which includes the current time:
>
> data Blog = Blog Title UTCTime Contents
>
> myBlogForm :: Form Blog
> myBlogForm = Blog <$> titleForm <*> something <*> contentsForm
>
>  The question is: what goes in something? Its type has to be:
>
> something :: Form UTCTime
>
> Ideally, I'd call getCurrentTime. The question is: how do I lift that into
> a Form? Since Form is only an Applicative, not a Monad, I can't create a
> MonadIO instance. However, Form is in fact built on top of IO[1]. And it's
> possible to create a MonadTrans instance for Form, since it's entirely
> possible to lift actions from the underlying functor/monad into Form. So
> something can be written as:
>
> something = lift $ liftIO getCurrentTime
>
> This works, but is unintuitive. One solution would be to have an
> ApplicativeIO typeclass and then use liftIOA. My questions here are:
>
> 1. Has anyone else run into this issue?
> 2. Is there an existing solution out there?
>
> Michael
>
> [1] Full crazy definition is at:
> http://haddocks.fpcomplete.com/fp/7.4.2/20130922-179/yesod-form/Yesod-Form-Types.html#t:AForm
>
> ___
> 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] ANNOUNCE: HDBI-1.1.1 and friends

2013-09-11 Thread Alexey Uimanov
Hello, haskellers!

I am glad to announce new tested version of HDBI-1.1.1 (Haskell Database
Independent interface). Now it becomes much more databae-independent than
before because of SQlite3 driver in addition to PostrgreSQL driver.

What changed from version 1.0.0:

1. removed `affectedRows` from `Statement`: sqlite does not support this
feature directly. You can still use this feature of PostgreSQL with
function `pgAffectedRows`

2. fixed default implementation of `executeMany`: perform reset after
execute, statement will be in New state after `executeMany`.

3. "stm" is now a dependency

4. DriverUtils: ChildList implemented with STM, `closeAllChildren` now wait
for all child statement finalizers and reduced the probability of blocking.

5. Tests improved.

6. Common tests moved to separate package
http://hackage.haskell.org/package/hdbi-tests

HDBI available on Hackage
http://hackage.haskell.org/package/hdbi
http://hackage.haskell.org/package/hdbi-postgresql
http://hackage.haskell.org/package/hdbi-sqlite


Here is github:
https://github.com/s9gf4ult/hdbi
https://github.com/s9gf4ult/hdbi-postgresql
https://github.com/s9gf4ult/hdbi-sqlite
https://github.com/s9gf4ult/hdbi-tests
https://github.com/s9gf4ult/hdbi-svc

Look at the issues list https://github.com/s9gf4ult/hdbi/issues?state=open
Your issues and comments are welcome.
Pull requests and contribution are welcome as well.

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


[Haskell-cafe] Freeing dependent resources

2013-08-13 Thread Alexey Uimanov
Hello, Haskellers.

I am working on HDBI and I faced with the problem.

There is an error when I close SQlite database, "unable to close due to
unfinalized statements or unfinished backups".
This problems occurs when there is some not finalized statements related to
this database.

So, I must protect the user from this error and garantee the finalisation
of all the statements BEFORE the disconnection from
the database.

There is naive implementation of weak child list inherited from HDBC

https://github.com/s9gf4ult/hdbi/blob/master/Database/HDBI/DriverUtils.hs

Here you can see that ChildList is just MVar to list of weak pointers.
Every time when the statement is created the new weak pointer prepended to
this list.
Every time when statement becomes not reachable the weak pointer becomes
empty and it's finalizer is scheduled to execute in parralel thread.
The finalizer finishes the statement, so if finalizer is executed the
statement is finished.
Before the actual call of disconnection the 'disconnect' method performs
'closeAllChildren'.
Call of 'closeAllChildren' performs finishing of just not empty weak
pointers, because the finishing of not reachable statements is imposible.

You can see the implementation here

https://github.com/s9gf4ult/hdbi-sqlite/blob/master/Database/HDBI/SQlite/Implementation.hs#L80
https://github.com/s9gf4ult/hdbi-sqlite/blob/master/Database/HDBI/SQlite/Implementation.hs#L117

and here is the simplest code which cause an error

{-# LANGUAGE
  OverloadedStrings
  #-}

module Main where

import System.Mem
import Database.HDBI.SQlite
import Database.HDBI

perf c = do
  runRaw c "create table integers (val)"
  s <- prepare c "select * from integers"
  return ()

main = do
  c <- connectSqlite3 ":memory:"
  perf c
  performGC
  disconnect c

If you remove 'performGC' error not occurs, because the weak pointer in
ChildList is still not empty and
'finish' is performed in 'closeAllChildren'.

The problem occures when the statement becomes not reachable and weak
pointer becomes empty,
but finalizer is not performed yet, because the finalizer performed in
parralel thread according to
https://www.google.ru/url?sa=t&rct=j&q=&esrc=s&source=web&cd=1&cad=rja&ved=0CC8QFjAA&url=http%3A%2F%2Fcommunity.haskell.org%2F~simonmar%2Fpapers%2Fweak.pdf&ei=vRALUvrELaaS4ASH_oCQCw&usg=AFQjCNEWQtRfh5ei7J_Qd-VDVMq0ied0KQ&sig2=nsvzz4FXB_4dWp75CU6gzg

The naive solution is to make 'closeAllChildren' to wait until all
finalizers is completely performed. But how ?
Maybe you have the better solution to garantee that all statements are
finished before the database disconnecting ?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: hdbi-1.0.0 and hdbi-postgresql-1.0.0

2013-07-31 Thread Alexey Uimanov
The rationale is that the low-level database interface accepts parameters
directly instead of
inserting them inside the query manually (like HoleyMonoid would do).
Postgresql-simple
also does parameter substitution on haskell side. This is not safe and may
cause to
http://en.wikipedia.org/wiki/SQL_injection because of not properly done
backquoting. Low-level
database interface knows better how to work with parameters, so the driver
must pass them to it instead
of parameters substitution.

hdbi-postgresql just replace "?" to "$1" sequence properly parsing and
ignoring question marks inside the doublequoted identifiers, quoted
literals and even dollar quoted literals  4.1.2.2. Dollar-Quoted String
Constants<http://www.postgresql.org/docs/8.2/static/sql-syntax-lexical.html>


2013/7/31 Tom Ellis 

> On Wed, Jul 31, 2013 at 09:45:50AM +0600, Alexey Uimanov wrote:
> > Hello, haskellers. This is the first release of HDBI (Haskell Database
> > Independent interface).
>
> Hi, thanks for this Alexey.  It's great that there is continued development
> of this really important infrustructure for Haskell.
>
> I have a question about variable interpolation, that is, using "?"
> parameter
> placeholders in the query strings, as documented here:
>
>
> http://hackage.haskell.org/packages/archive/hdbi/1.0.0/doc/html/Database-HDBI.html
>
> I know postgresql-simple does this, and presumably database access
> libraries
> in other languages do this too.
>
> What is the rationale for this when in Haskell we have safer methods of
> interpolation at our disposal (for example HoleyMonoid)?  Is it simply a
> matter of using the most familiar interface, or is there a deeper reason
> this is necessary?
>
> Thanks,
>
> Tom
>
>
> ___
> 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] ANNOUNCE: hdbi-1.0.0 and hdbi-postgresql-1.0.0

2013-07-31 Thread Alexey Uimanov
>
> Regard parameterized SQL: It might be worth using named parameters (e.g.
> ":foo" and ":bar" or something like that) rather than "?" as
> placeholders in SQL/prepared SQL. This will make it slightly more
> flexible if you need to provide different SQL strings for different
> databases, but want to reuse the code which does the actual running of
> the SQL. It's also more flexible if you need to repeat parameters -- the
> latter is typical with PostgreSQL if you want to emulate
> "update-or-insert" in a single SQL statement
>

Named parameters might be more flexible, but it is need to think hard about
how to implement this.
If you are using named parameters you need to pass not just list [SqlValue]
as parameters,
but Map Text SqlValue or something. So named parameters will not be
compatible with unnamed and will need
separate query parser.


> Regarding migrations: If you haven't already, please have a look at
> Liquibase (http://www.liquibase.org/documentation/index.html) before
> attempting to implement migrations. The most important attributes of
> Liquibase are:
>

What I am trying to implement is not a new migration system, but just the
common interface for
simple schema actions, here is my in-mind draft:

newtype TableName = TableName Text

data TableDescription = TableDescription
{tableName :: TableName
,tableFields :: [FieldDescription]
}

class (Connection con) => Introspect con where
  getTableNames:: con -> IO [TableName]
  describeTable :: con -> TableName -> IO TableDescription
  getIndexes :: con -> [IndexDescription]

class (Connection con) => SchemaChange con where
  createTable :: con -> TableDescription -> IO ()
  dropTable :: con -> TableName -> IO ()
  addColumn :: con -> TableName -> FieldDescription -> IO ()
  ...

This typeclasses must provide database-independent schema introspection and
changing.
Migration system can be anything you want.

I also have the idea do not throw the exceptions in IO but return  (Either
SqlError a) from
all the Connection and Statement methods for safe data processing. What do
you think about ?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: hdbi-1.0.0 and hdbi-postgresql-1.0.0

2013-07-30 Thread Alexey Uimanov
Hello, haskellers. This is the first release of HDBI (Haskell Database
Independent interface). It is the fork of HDBC.
HDBI has some improvements in design, it also has better testing and
performance (mainly because of using Text instead of String anywhere).
HDBI designed to be more flexible and correct database interface.

You can find out more information in the documentation.
http://hackage.haskell.org/package/hdbi
http://hackage.haskell.org/package/hdbi-postgresql

I am planning to implement MySql and Sqlite drivers as well

https://github.com/s9gf4ult/hdbi
https://github.com/s9gf4ult/hdbi-postgresql
Issues and pull requests are welcome, as well as collaboration.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Database conectivity in Haskell. HDBC-3 or something.

2013-07-15 Thread Alexey Uimanov
Hello, haskellers.

I has made some rework of HDBC,
if you are interested follow the link
http://s9gf4ult.github.io/hdbc/Database-HDBC.html

So, why did I made this ? Because I did not found good enough (inside and
outside) common interface
for database connectivity. What I mean is flexible and simple interface,
supporting arbitrary precision values
and providing convenient and minimalistic interface for just query
execution.

In ''roadmap'' in the documentation you can see, that I think, that Haskell
must have such interface which must
become the conveient base for other high-level interfaces, such as
Persistent and HaskellDB. Other languages, like
Python goes this way, so why we must not ?

I dont know will this patches accepted to main HDBC repository or not. I
will fork HDBC under another name
if necessary.

The patches are:
https://github.com/s9gf4ult/hdbc
https://github.com/s9gf4ult/hdbc-postgresql
There is just PostgreSQL driver for now, but I plan to write some other
drivers as well.
Any help and pull requests are welcome.

My question is: what do you think about all of this? Do you think this is
good idea or this is not necessary
for now? I just want to notify the community about this and maybe find
support.

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


[Haskell-cafe] Help me with space leaks

2012-09-25 Thread Alexey Uimanov
Hello. I am trying to write some thing in haskell and i need fast
storage to store and select this things from storage.
https://github.com/s9gf4ult/projs/tree/master/haskell/teststorage

I am writing simple testing package to determine my needs and select
the fastest storage and i have encountered problems.

Firstly i decided to check out postgresql-simple, but when i am doing
"executeMany" i see space leaks, here is the picture
http://bayimg.com/NAdjHAaeA
http://bayimg.com/NADjKAAea
I dont fully understand what is happening here, but i belive this is
because of lazy consuming of "executeMany" or something. So things im
trying to insert do not calculate one by one, but this is creating
many thunks for calculate them.

I would understand how to narrow the cause of this problem and create
more strict function "executeMany" which would work in constant space
(or space of data).

Here the insertMany from postgresql-simple

executeMany :: (ToRow q) => Connection -> Query -> [q] -> IO Int64
executeMany _ _ [] = return 0
executeMany conn q qs = do
  result <- exec conn =<< formatMany conn q qs
  finishExecute conn q result

And this is not looks like a problem case go to formatMany

formatMany :: (ToRow q) => Connection -> Query -> [q] -> IO ByteString
formatMany _ q [] = fmtError "no rows supplied" q []
formatMany conn q@(Query template) qs = do
  case parseTemplate template of
Just (before, qbits, after) -> do
  bs <- mapM (buildQuery conn q qbits . toRow) qs
  return . toByteString . mconcat $ fromByteString before :
intersperse (fromChar ',') bs ++
[fromByteString after]
Nothing -> fmtError "syntax error in multi-row template" q []

Here bs is the map of bs and must stay lazy evaluated
and here we see mconcat which must be strict i think, and if i am
right so problem must disapear whan i replace it with strict mconcat

mconcat' :: (Monod a) => [a] -> a
mconcat' [] = mempty
mconcat' (x:xs) = x `seq` (mappend x $ mconcat' xs)

but it doesnt.
I assume i must write the same for "deepseq" to realy calculate each
parameter up to value. But if so, this must touch several projects
such as blaze and maybe bytestring because of the need to make NFData instances.
How to solve this problem right - way ? Maybe haskell have elegant
solution for this ?

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