Bitcoin Forum
August 07, 2024, 06:31:57 AM *
News: Latest Bitcoin Core release: 27.1 [Torrent]
 
  Home Help Search Login Register More  
  Show Posts
Pages: [1]
1  Economy / Service Discussion / Re: Analysis of the recent MtGox moves: few very big orders on: August 25, 2013, 07:10:18 PM
Oh, and if anyone's interested and wants to play with it, I can post my script here. But sorry, it's in Haskell.  Wink


Yes, please be so kind and post your scrpt.

OK, here it is:

Code:
{-# LANGUAGE TemplateHaskell #-}

import Control.Applicative
import Data.List
import Data.List.Utils
import Data.Maybe
import Data.Time
import HFlags
import Text.Printf

defineFlag "bigs_only" True "Show only big orders."

data Trade = Trade { _time :: !Int
                   , _price :: !Double
                   , _amount :: !Double
                   } deriving (Eq,Show)

readCSVFile :: FilePath -> IO [Trade]
readCSVFile file = do
  ls <- lines <$> readFile file
  return $ map (\[t,p,a] -> Trade (read t) (read p) (read a)) $
    map (split ",") $ ls

aggPrice :: [Trade] -> (Double,Double)
aggPrice l = (avgPrice, totAmount)
  where
    totAmount = sum $ map _amount l
    avgPrice = (/totAmount) $ sum $ map wprice l
    wprice (Trade _ p a) = p * a

showTime :: Int -> String
showTime s = show $ addUTCTime (fromIntegral s) epoch
  where
    epoch = UTCTime (fromGregorian 1970 01 01) 0

data GTag = LEV | BUY | SELL  deriving (Eq,Show)
data TGroup = Single Trade | Group GTag [Trade]  deriving (Show)

groupTrades :: [Trade] -> [TGroup]
groupTrades [] = []
groupTrades [t] = [Single t]
groupTrades (t1:t2:ts) | withinSecond t1 t2 = go (tag t1 t2) t2 ts [t1]
                       | otherwise = Single t1 : groupTrades (t2:ts)
  where
    withinSecond (Trade t1 _ _) (Trade t2 _ _) = abs (t2 - t1) <= 1
    go t x [] res = [Group t (reverse (x:res))]
    go t x (y:ys) res | withinSecond x y,
                        Just t' <- fitsTag t x y = go t' y ys (x:res)
                      | otherwise = (Group t (reverse (x:res))) : groupTrades (y:ys)

    fitsTag LEV (Trade _ p1 _) (Trade _ p2 _) | p1 == p2 = Just LEV
                                              | p1 < p2  = Just BUY
                                              | otherwise = Just SELL
    fitsTag BUY (Trade _ p1 _) (Trade _ p2 _) | p1 <= p2 = Just BUY
    fitsTag SELL (Trade _ p1 _) (Trade _ p2 _) | p1 >= p2 = Just SELL
    fitsTag _ _ _ = Nothing

    tag t1 t2 = fromJust $ fitsTag LEV t1 t2

combinedTransactions :: [Trade] -> IO ()
combinedTransactions trades = do
  let cts = groupTrades trades


      output :: TGroup -> IO ()
      output (Single (Trade t p a)) = if flags_bigs_only && a < 400
                                      then return ()
                                      else printf "%s: %.2f @ %.2f\n" (showTime t) a p
      output (Group tag ts) = if amount > 400 || not flags_bigs_only
                              then printf "%s:      (%d ts in %ds) %.2f @ %.2f %s (min: %.2f, max: %.2f) big ts: %s\n" stTime count duration amount avgPrice tag minPrice maxPrice bigs
                              else return ()
        where
          ta = head ts
          tz = last ts
          count = length ts
          prices = map _price ts
          stTime = showTime $ _time ta
          duration = _time tz - _time ta
          (avgPrice,amount) = aggPrice ts
          minPrice = minimum prices
          maxPrice = maximum prices
          bigs :: [String]
          bigs = map (printf "%.2f") $ take 4 $ reverse $ sort $ map _amount ts
  mapM_ output cts

main :: IO ()
main = do
  $initHFlags "Analyze bitcoin trades"
  mtgox <- readCSVFile "mtgox.csv"
  combinedTransactions mtgox

It's not very compact or nice, but it works. Smiley

You can download the data for it from: http://bitcoincharts.com/t/trades.csv?symbol=mtgoxUSD&start=$starttime&end=$endtime, specifying proper start and end time. Or you can get the whole history in one file from http://api.bitcoincharts.com/v1/csv/mtgoxUSD.csv
2  Economy / Service Discussion / Re: Analysis of the recent MtGox moves: few very big orders on: August 21, 2013, 07:21:17 PM
Klao,

Have you analyzed the most recent price movements at Gox?  Looks like they fall under the large buy orders from whales category.

Here's the results for today:

2013-08-21 00:04:42 UTC:      (462 ts in 17s) 3471.65 @ 123.29 BUY (min: 122.34, max: 124.45) big ts: ["249.98","199.15","167.00","138.50"]
2013-08-21 01:54:53 UTC:      (78 ts in 4s) 680.50 @ 124.50 BUY (min: 123.49, max: 124.70) big ts: ["166.43","115.05","72.97","43.00"]
2013-08-21 02:50:27 UTC:      (36 ts in 1s) 1088.79 @ 124.90 BUY (min: 124.83, max: 124.91) big ts: ["497.85","300.00","49.75","40.00"]
2013-08-21 03:36:44 UTC:      (129 ts in 6s) 1000.00 @ 121.68 SELL (min: 121.00, max: 123.04) big ts: ["140.54","124.78","112.42","69.60"]
2013-08-21 04:49:13 UTC:      (95 ts in 4s) 490.00 @ 120.40 SELL (min: 120.00, max: 121.00) big ts: ["40.00","40.00","39.00","30.00"]
2013-08-21 13:27:46 UTC:      (94 ts in 4s) 868.91 @ 120.23 SELL (min: 120.00, max: 121.48) big ts: ["100.00","98.00","91.65","83.33"]
2013-08-21 14:38:38 UTC:      (78 ts in 4s) 1000.00 @ 121.71 BUY (min: 120.43, max: 122.50) big ts: ["100.00","100.00","65.94","60.00"]
2013-08-21 14:39:36 UTC:      (146 ts in 6s) 1000.00 @ 123.32 BUY (min: 120.55, max: 123.99) big ts: ["175.51","132.73","90.00","43.12"]
2013-08-21 16:06:39 UTC:      (152 ts in 5s) 1000.00 @ 123.57 BUY (min: 121.01, max: 124.23) big ts: ["133.33","60.00","46.00","40.00"]
2013-08-21 16:07:29 UTC:      (225 ts in 8s) 2404.00 @ 124.75 BUY (min: 123.40, max: 125.00) big ts: ["401.16","173.58","102.18","101.00"]
2013-08-21 18:06:17 UTC:      (108 ts in 4s) 1021.96 @ 124.39 BUY (min: 122.93, max: 124.91) big ts: ["250.00","71.19","60.79","40.00"]
2013-08-21 18:46:40 UTC:      (44 ts in 2s) 444.98 @ 124.21 BUY (min: 123.00, max: 124.90) big ts: ["57.00","50.00","50.00","40.00"]


Again, we have several very obvious exact 1k orders. And a few even bigger. For example, the 2404 BTC one had probably limit price of 125 and exhausted the order book.

Interestingly, today we had more big sells. But still, the buys dominate.
3  Economy / Service Discussion / Re: Analysis of the recent MtGox moves: few very big orders on: August 20, 2013, 11:23:40 PM
Oh, and if anyone's interested and wants to play with it, I can post my script here. But sorry, it's in Haskell.  Wink
4  Economy / Exchanges / Re: MtGox withdrawal delays [Gathering] on: August 20, 2013, 11:05:39 PM
I've posted an analysis about the recent sudden rise above 120 on MtGox here: https://bitcointalk.org/index.php?topic=278643

It might not be directly relevant to the discussion in this thread, but I think it provides very interesting insight into what is happening on MtGox now.

Short summary: The big move of mtgoxUSD on Aug 19th was a result of a very few (about 15) very large (1000-2000 BTC) orders, which were done by a handful (1-4) of individuals. For the full analysis see there!
5  Economy / Service Discussion / Analysis of the recent MtGox moves: few very big orders on: August 20, 2013, 10:58:46 PM
I don't want to speculate about the current situation at MtGox, but I wanted to share a little research about the recent big moves on it. It definitely made me think, and I didn't see this mentioned here before. We did the research together with @errge.

TL;DR: The big move on mtgoxUSD from 112 to 123 on Aug 19th was a result of a very few (about 15) very large (1000-2000 BTC) orders, which were done by a few (1-4) individuals.

http://bitcoincharts.com/charts/mtgoxUSD#rg5zczsg2013-08-18zeg2013-08-20ztgSzm1g10zm2g25zv

Here's how we determined this. MtGox publishes a feed of all transactions and if you look at the beginning of the first move, you see the following:

1376880909,111.999920000000,0.024069000000
1376880915,111.840100000000,0.193640000000
1376880956,111.840200000000,0.097470000000
1376880959,111.840200000000,0.010960000000
1376880984,111.999900000000,4.463718200000
1376880984,112.000000000000,4.945000000000
1376880984,112.699990000000,7.269893300000
1376880984,112.700000000000,0.031112900000
1376880984,112.700000000000,0.099900000000
1376880984,112.700000000000,5.000000000000
1376880984,112.700010000000,102.262969930000
1376880984,112.790170000000,1.330178290000
1376880984,112.992520000000,0.018122130000
1376880984,113.000030000000,1.000000000000
1376880985,113.238050000000,5.517000000000
1376880985,113.240000000000,0.883080180000


There is a transaction every few seconds and then at 1376880984 (= 2013-08-19 02:56:24 UTC) starts a long streak of transactions with an ever increasing price that immediately follow each other.

We made an assumption that this was a big "buy" order and what we see is it "eating its way up through the order book". This looked very plausible, so we wanted to see how big was the order and what was its limit price. So, I wrote a script that looks for streaks like that and aggregates them. This is what we got:

2013-08-19 02:56:24 UTC:      (156 ts in 6s) 2000.00 @ 114.49 BUY (min: 112.00, max: 114.91) big ts: ["102.26","99.59","98.20","97.00"]


Meaning: there were 156 transactions completed in 6 seconds, and if you add up the amounts you get exactly 2000 BTC. This can't be a coincidence! It seems this was indeed one order of size 2000.
(The rest of the line is a weighted average price, the min and max price of the transactions and the amounts of a few biggest transactions within that streak.)

And immediately after that we get another one:
2013-08-19 02:56:31 UTC:      (111 ts in 4s) 1000.00 @ 114.97 BUY (min: 114.12, max: 115.00) big ts: ["100.00","87.22","86.19","84.48"]

Here's the order size was 1000 BTC and it ate through the asks till it got to the rich field @ 115.00 USD/BTC.

Well, without further ado, here's the full list:


2013-08-19 02:56:24 UTC:      (156 ts in 6s) 2000.00 @ 114.49 BUY (min: 112.00, max: 114.91) big ts: ["102.26","99.59","98.20","97.00"]
2013-08-19 02:56:31 UTC:      (111 ts in 4s) 1000.00 @ 114.97 BUY (min: 114.12, max: 115.00) big ts: ["100.00","87.22","86.19","84.48"]
2013-08-19 02:57:32 UTC:      (28 ts in 1s) 1500.00 @ 115.00 BUY (min: 114.70, max: 115.00) big ts: ["1293.75","90.00","43.57","30.72"]
2013-08-19 02:59:40 UTC:      (42 ts in 2s) 1433.72 @ 115.00 BUY (min: 114.70, max: 115.00) big ts: ["946.69","177.43","145.00","24.00"]
2013-08-19 03:10:35 UTC:      (198 ts in 6s) 1000.00 @ 116.48 BUY (min: 116.21, max: 116.95) big ts: ["222.80","117.17","52.76","44.68"]
2013-08-19 03:11:40 UTC:      (250 ts in 9s) 1000.00 @ 117.30 BUY (min: 116.95, max: 117.80) big ts: ["154.00","100.00","79.69","40.00"]
2013-08-19 05:32:01 UTC:      (172 ts in 7s) 1000.00 @ 117.94 BUY (min: 117.20, max: 118.40) big ts: ["112.94","100.00","96.53","78.30"]
2013-08-19 05:32:19 UTC:      (111 ts in 4s) 1000.00 @ 118.68 BUY (min: 118.05, max: 119.00) big ts: ["400.00","110.00","90.50","69.12"]
2013-08-19 05:32:54 UTC:      (91 ts in 4s) 1000.00 @ 119.00 BUY (min: 116.78, max: 119.08) big ts: ["152.13","150.00","147.55","74.95"]
2013-08-19 05:33:05 UTC:      (125 ts in 4s) 814.90 @ 119.38 BUY (min: 119.08, max: 119.73) big ts: ["100.00","99.00","83.62","79.00"]
2013-08-19 05:34:52 UTC:      (198 ts in 9s) 1000.00 @ 119.91 BUY (min: 117.50, max: 120.00) big ts: ["160.00","100.00","78.90","67.00"]
2013-08-19 06:37:50 UTC:      (240 ts in 10s) 1458.41 @ 119.95 BUY (min: 118.95, max: 120.00) big ts: ["100.92","100.00","100.00","59.64"]
2013-08-19 07:47:45 UTC:      (171 ts in 6s) 750.00 @ 121.11 BUY (min: 120.28, max: 121.79) big ts: ["150.00","50.00","39.23","30.78"]
2013-08-19 07:50:58 UTC:      (265 ts in 9s) 1250.00 @ 122.15 BUY (min: 120.38, max: 122.76) big ts: ["148.51","129.95","127.90","90.15"]
2013-08-19 07:52:29 UTC:      (104 ts in 4s) 406.50 @ 122.84 BUY (min: 122.50, max: 123.00) big ts: ["89.33","72.41","52.03","25.87"]
2013-08-19 07:53:36 UTC:      (179 ts in 7s) 837.36 @ 123.12 BUY (min: 122.78, max: 123.56) big ts: ["102.14","67.92","51.42","49.60"]


In most of these the amount is very round, indicating that indeed we found one exact order that was completely filled. For the non-round ones my guess is that they actually emptied the order book up to the given limit price and were not filled immediately. The proof for this is that we can sometimes find follow-up transactions matching in price which if added to the streak produce a round number.

Altogether these giant orders add up to about 17500 BTC, which is a considerable part of transaction volume during that period. And all the upward price movements happened within them.

We don't know whether all these whales are from the same person. But, based on the timing, I would say it's no more than 4 different players. And they moved more than $2M into bitcoins with 16 nice round orders.


Interestingly we found two big sells too (and only two):

2013-08-19 09:56:14 UTC:      (24 ts in 2s) 589.56 @ 120.09 SELL (min: 120.00, max: 122.00) big ts: ["274.83","100.00","60.00","30.00"]
2013-08-19 09:57:26 UTC:      (3 ts in 0s) 659.28 @ 120.00 SELL (min: 120.00, max: 121.89) big ts: ["659.26","0.01","0.01"]

Or, actually, I think this is only one order, because together with the small ones in between them, they add up to exactly 1250.


Thoughs?
6  Other / Beginners & Help / Re: Whitelist Requests (Want out of here?) on: August 20, 2013, 01:27:55 PM
Hi,

I'd like to post the following little research in the "Bitcoin Forum > Economy > Marketplace > Service Discussion". We did this together with @errge, so can you please lift the newbie restriction for me and for him too.



I don't want to speculate about the current situation at MtGox, but I wanted to share a little research about the recent big moves that we did together with @errge. It definitely made me think, and I didn't see this mentioned here before.

TL;DR The move on mtgoxUSD from 112 to 123 on Aug 19th was a result of a very few (about 15) very large (1000-2000 BTC) orders, which were done by a few (1-4) distinct individuals.

http://bitcoincharts.com/charts/mtgoxUSD#rg5zczsg2013-08-18zeg2013-08-20ztgSzm1g10zm2g25zv

Here's how we determined this. MtGox publishes a feed of all transactions and if you look at the beginning of the first move, you see the following:

1376880909,111.999920000000,0.024069000000
1376880915,111.840100000000,0.193640000000
1376880956,111.840200000000,0.097470000000
1376880959,111.840200000000,0.010960000000
1376880984,111.999900000000,4.463718200000
1376880984,112.000000000000,4.945000000000
1376880984,112.699990000000,7.269893300000
1376880984,112.700000000000,0.031112900000
1376880984,112.700000000000,0.099900000000
1376880984,112.700000000000,5.000000000000
1376880984,112.700010000000,102.262969930000
1376880984,112.790170000000,1.330178290000
1376880984,112.992520000000,0.018122130000
1376880984,113.000030000000,1.000000000000
1376880985,113.238050000000,5.517000000000
1376880985,113.240000000000,0.883080180000


There is a transaction every few seconds and then at 1376880984 (= 2013-08-19 02:56:24 UTC) starts a long streak of transactions with an ever increasing price that immediately follow each other.

We made an assumption that this was a big "buy" order and what we see is it "eating its way up through the order book". This looked very plausible, so we wanted to see how big was the order and what was its limit price. So, I wrote a script that looks for streaks like that and aggregates them. This is what we got:

2013-08-19 02:56:24 UTC:      (156 ts in 6s) 2000.00 @ 114.49 BUY (min: 112.00, max: 114.91) big ts: ["102.26","99.59","98.20","97.00"]


Meaning: there were 156 transactions completed in 6 seconds, and if you add up the amounts you get exactly 2000 BTC. This can't be random! It was indeed one order of size 2000.
(The rest of the line is a weighted average price, the min and max price of the transactions and the amounts of a few biggest transactions within that streak.)

And immediately after that we get another one:
2013-08-19 02:56:31 UTC:      (111 ts in 4s) 1000.00 @ 114.97 BUY (min: 114.12, max: 115.00) big ts: ["100.00","87.22","86.19","84.48"]

Here's the order size was 1000 BTC and it ate through the asks till it got to the rich field @ 115.00 USD/BTC.

Well, without further ado, here's the full list:


2013-08-19 02:56:24 UTC:      (156 ts in 6s) 2000.00 @ 114.49 BUY (min: 112.00, max: 114.91) big ts: ["102.26","99.59","98.20","97.00"]
2013-08-19 02:56:31 UTC:      (111 ts in 4s) 1000.00 @ 114.97 BUY (min: 114.12, max: 115.00) big ts: ["100.00","87.22","86.19","84.48"]
2013-08-19 02:57:32 UTC:      (28 ts in 1s) 1500.00 @ 115.00 BUY (min: 114.70, max: 115.00) big ts: ["1293.75","90.00","43.57","30.72"]
2013-08-19 02:59:40 UTC:      (42 ts in 2s) 1433.72 @ 115.00 BUY (min: 114.70, max: 115.00) big ts: ["946.69","177.43","145.00","24.00"]
2013-08-19 03:10:35 UTC:      (198 ts in 6s) 1000.00 @ 116.48 BUY (min: 116.21, max: 116.95) big ts: ["222.80","117.17","52.76","44.68"]
2013-08-19 03:11:40 UTC:      (250 ts in 9s) 1000.00 @ 117.30 BUY (min: 116.95, max: 117.80) big ts: ["154.00","100.00","79.69","40.00"]
2013-08-19 05:32:01 UTC:      (172 ts in 7s) 1000.00 @ 117.94 BUY (min: 117.20, max: 118.40) big ts: ["112.94","100.00","96.53","78.30"]
2013-08-19 05:32:19 UTC:      (111 ts in 4s) 1000.00 @ 118.68 BUY (min: 118.05, max: 119.00) big ts: ["400.00","110.00","90.50","69.12"]
2013-08-19 05:32:54 UTC:      (91 ts in 4s) 1000.00 @ 119.00 BUY (min: 116.78, max: 119.08) big ts: ["152.13","150.00","147.55","74.95"]
2013-08-19 05:33:05 UTC:      (125 ts in 4s) 814.90 @ 119.38 BUY (min: 119.08, max: 119.73) big ts: ["100.00","99.00","83.62","79.00"]
2013-08-19 05:34:52 UTC:      (198 ts in 9s) 1000.00 @ 119.91 BUY (min: 117.50, max: 120.00) big ts: ["160.00","100.00","78.90","67.00"]
2013-08-19 06:37:50 UTC:      (240 ts in 10s) 1458.41 @ 119.95 BUY (min: 118.95, max: 120.00) big ts: ["100.92","100.00","100.00","59.64"]
2013-08-19 07:47:45 UTC:      (171 ts in 6s) 750.00 @ 121.11 BUY (min: 120.28, max: 121.79) big ts: ["150.00","50.00","39.23","30.78"]
2013-08-19 07:50:58 UTC:      (265 ts in 9s) 1250.00 @ 122.15 BUY (min: 120.38, max: 122.76) big ts: ["148.51","129.95","127.90","90.15"]
2013-08-19 07:52:29 UTC:      (104 ts in 4s) 406.50 @ 122.84 BUY (min: 122.50, max: 123.00) big ts: ["89.33","72.41","52.03","25.87"]
2013-08-19 07:53:36 UTC:      (179 ts in 7s) 837.36 @ 123.12 BUY (min: 122.78, max: 123.56) big ts: ["102.14","67.92","51.42","49.60"]


Most of these are very round, indicating that indeed we found one exact order that was completely filled. For the non-round ones my guess is that they actually emptied the order book up to the given limit price and were not filled immediately. The proof for this is that we can sometimes find follow-up transactions matching in price which if are added to the streak give a round number.

Altogether these giant orders add up to about 17500 BTC, which is a considerable part of transaction volume during that period. And all the upward price moves happened within them.

We don't know whether all these whales are from the same person. But, based on the timing, I would say it's no more than 4 different players.

Interestingly we found two big sells too (and only two):

2013-08-19 09:56:14 UTC:      (24 ts in 2s) 589.56 @ 120.09 SELL (min: 120.00, max: 122.00) big ts: ["274.83","100.00","60.00","30.00"]
2013-08-19 09:57:26 UTC:      (3 ts in 0s) 659.28 @ 120.00 SELL (min: 120.00, max: 121.89) big ts: ["659.26","0.01","0.01"]

Or, actually, I think this is only one order, because together with the small ones in between them, they add up to exactly 1250.

Thoughts?
Pages: [1]
Powered by MySQL Powered by PHP Powered by SMF 1.1.19 | SMF © 2006-2009, Simple Machines Valid XHTML 1.0! Valid CSS!