Skip to content

Commit

Permalink
uom: fix byteToGigabyte conversion
Browse files Browse the repository at this point in the history
  • Loading branch information
tranma committed Feb 27, 2015
1 parent 8628018 commit cc83655
Show file tree
Hide file tree
Showing 4 changed files with 11 additions and 13 deletions.
2 changes: 0 additions & 2 deletions lib/Borel.hs
Original file line number Diff line number Diff line change
Expand Up @@ -124,8 +124,6 @@ query = do
( params ^. paramBorelConfig . allInstances)
( params ^. paramMetrics)

liftIO $ debugM "borel" "start a query"

P.enumerate
[ (fst result, mkItem sd result)
| metrics <- Select $ P.each grouped
Expand Down
4 changes: 2 additions & 2 deletions lib/Borel/Chevalier.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,6 @@ import Vaultaire.Types

import Borel.Types

import Debug.Trace

-- | Use Chevalier to find origin, address, sourcedict that contains data relevant
-- to this OpenStack tenancy.
Expand Down Expand Up @@ -91,7 +90,8 @@ searchP
-> Producer (Address, SourceDict) m ()
searchP ctx uri org req = do
x <- lift $ search ctx uri org req
trace ("chev addrs=" ++ show (map fst x)) $ P.each x
liftIO $ debugM "borel" ("addresses=" <> show (map fst x))
P.each x

-- this doesn't stream because chevalier doesn't
search
Expand Down
16 changes: 8 additions & 8 deletions lib/Borel/Marquise.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,25 +16,25 @@ module Borel.Marquise

where

import Control.Monad
import Control.Lens
import Control.Monad
import Data.Monoid
import Network.URI
import Pipes.Safe

import Pipes

import qualified Pipes.Safe as P
import Pipes.Safe as P
import System.Log.Logger
import qualified System.ZMQ4 as Z
import qualified System.ZMQ4 as Z

-- friends
import qualified Marquise.Client as M
import qualified Marquise.Client as M
import Vaultaire.Types

-- family
import Borel.Types


import qualified Pipes.Prelude as P

-- | Use Marquise to fetch raw data points.
--
marquise :: (MonadIO m, MonadSafe m)
Expand Down Expand Up @@ -87,4 +87,4 @@ runMarquiseReader
runMarquiseReader ctx (show -> uri) f
= P.bracket (liftIO $ Z.socket ctx Z.Dealer) (liftIO . Z.close) $ \sock ->
P.bracket (liftIO $ Z.connect sock uri) (const $ return ())$ \_ ->
f (M.SocketState sock uri)
f (M.SocketState sock uri)
2 changes: 1 addition & 1 deletion lib/Borel/Types/UOM.hs
Original file line number Diff line number Diff line change
Expand Up @@ -184,7 +184,7 @@ nanosecToSec (u, v)
byteToGigabyte :: (UOM, Word64) -> (UOM, Word64)
byteToGigabyte (u, v)
= let new = mapUOM f u
in (new, tryConvert byte gigabyte v)
in (new, tryConvert byte new v)
where f p b | UOM p b == byte = gigabyte
| otherwise = UOM p b

Expand Down

0 comments on commit cc83655

Please sign in to comment.