Skip to content

Commit

Permalink
More stuff removed for repo separation.
Browse files Browse the repository at this point in the history
  • Loading branch information
graninas committed Dec 4, 2018
1 parent 15acc84 commit 6293f6d
Show file tree
Hide file tree
Showing 21 changed files with 17 additions and 690 deletions.
15 changes: 9 additions & 6 deletions app/Enecuum/Main.hs
Original file line number Diff line number Diff line change
@@ -1,17 +1,20 @@
module Main where

import App.GenConfigs (genConfigs)
import App.Initialize (initialize)
import Enecuum.Config (withConfig)
import Enecuum.Assets.GenConfigs (genConfigs)
import Enecuum.Assets.Initialization (initialize)
import Enecuum.Config (withConfig)
import Enecuum.Prelude

defaultConfig :: IsString a => a
defaultConfig = "configs/config.json"
help :: IO ()
help = putStrLn @Text $ "Please, specify node config:"
<> "\n\n$ enq-node-haskell singlenode configs/tst_graph_node_transmitter.json"
<> "\n\nOr generate default configs (they will be placed to ./configs/default):"
<> "\n\n$ enq-node-haskell generate-configs"

main :: IO ()
main = do
args <- getArgs
case args of
["singlenode", configFile] -> withConfig configFile initialize
["generate-configs"] -> genConfigs
_ -> withConfig defaultConfig initialize
_ -> help
17 changes: 0 additions & 17 deletions configs/TestClient.json

This file was deleted.

17 changes: 0 additions & 17 deletions configs/TestServer.json

This file was deleted.

File renamed without changes.
18 changes: 0 additions & 18 deletions configs/tst_real_pow.json

This file was deleted.

1 change: 0 additions & 1 deletion package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -89,7 +89,6 @@ dependencies:
- validation
- silently
- uuid
- gd
- resourcet
- triplesec
- yaml
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Enecuum.Assets.Nodes.ConfigParsing where
module Enecuum.Assets.ConfigParsing where

import Data.Yaml (ParseException, prettyPrintParseException)
import qualified Enecuum.Assets.TstScenarios as Tst
Expand All @@ -19,15 +19,11 @@ runParser (Right _) = pure $ Right 1
parseConfig :: LByteString -> IO ()
parseConfig configSrc = do
let runners =
[ runParser $ Cfg.tryParseConfig @Tst.TestClient configSrc
, runParser $ Cfg.tryParseConfig @Tst.TestServer configSrc

, runParser $ Cfg.tryParseConfig @Tst.ClientNode configSrc
[ runParser $ Cfg.tryParseConfig @Tst.ClientNode configSrc

, runParser $ Cfg.tryParseConfig @Tst.TstGraphNode configSrc
, runParser $ Cfg.tryParseConfig @Tst.TstGenPoWNode configSrc
, runParser $ Cfg.tryParseConfig @Tst.TstGenPoANode configSrc
, runParser $ Cfg.tryParseConfig @Tst.TstRealPoWNode configSrc
]

results <- sequence runners
Expand Down
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeInType #-}

module App.GenConfigs where
module Enecuum.Assets.GenConfigs where

import Data.Aeson.Encode.Pretty (encodePretty)
import qualified Data.ByteString.Lazy as B
Expand Down
Original file line number Diff line number Diff line change
@@ -1,11 +1,11 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeInType #-}

module App.Initialize where
module Enecuum.Assets.Initialization where

import qualified Data.Map as M
import qualified Enecuum.Assets.Nodes.Address as A
import Enecuum.Assets.Nodes.ConfigParsing (parseConfig)
import Enecuum.Assets.ConfigParsing (parseConfig)
import Enecuum.Assets.System.Directory (clientStory)
import qualified Enecuum.Assets.TstScenarios as Tst
import qualified Enecuum.Config as Cfg
Expand Down Expand Up @@ -85,15 +85,11 @@ initialize configSrc = do

-- Don't forget to update the list in ConfigParsing!
let runners =
[ runNode' $ Cfg.dispatchScenario @Tst.TestClient configSrc
, runNode' $ Cfg.dispatchScenario @Tst.TestServer configSrc

, runNode' $ Cfg.dispatchScenario @Tst.ClientNode configSrc
[ runNode' $ Cfg.dispatchScenario @Tst.ClientNode configSrc

, runNode' $ Cfg.dispatchScenario @Tst.TstGraphNode configSrc
, runNode' $ Cfg.dispatchScenario @Tst.TstGenPoWNode configSrc
, runNode' $ Cfg.dispatchScenario @Tst.TstGenPoANode configSrc
, runNode' $ Cfg.dispatchScenario @Tst.TstRealPoWNode configSrc
]
sequence_ runners

Expand Down
30 changes: 0 additions & 30 deletions src/Enecuum/Assets/Nodes/Address.hs
Original file line number Diff line number Diff line change
Expand Up @@ -52,36 +52,6 @@ clientPorts = makeNodePorts1000 5010
clientAddress :: NodeAddress
clientAddress = makeAddressByPorts clientPorts

-- Routing nodes

-- boot node = [0 .. 9]
routingBootNodePorts :: NodePorts
routingBootNodePorts = makeNodePorts1000 5000

routingBootNodeAddress :: NodeAddress
routingBootNodeAddress = makeAddressByPorts routingBootNodePorts

-- pow = [20 .. 49]
routingGenPoWNodePorts :: NodePorts
routingGenPoWNodePorts = makeNodePorts1000 5020

routingGenPoWNodeAddress :: NodeAddress
routingGenPoWNodeAddress = makeAddressByPorts routingGenPoWNodePorts

-- graph node = [50 .. 199]
routingGraphNodePorts :: NodePorts
routingGraphNodePorts = makeNodePorts1000 5050

routingGraphNodeAddress :: NodeAddress
routingGraphNodeAddress = makeAddressByPorts routingGraphNodePorts

-- poa = [200 .. 999]
routingGenPoANodePorts :: NodePorts
routingGenPoANodePorts = makeNodePorts1000 5200

routingGenPoANodeAddress :: NodeAddress
routingGenPoANodeAddress = makeAddressByPorts routingGenPoANodePorts

-- Test nodes
tstGenPoANodePorts :: NodePorts
tstGenPoANodePorts = makeNodePorts1000 5200
Expand Down
30 changes: 0 additions & 30 deletions src/Enecuum/Assets/Nodes/Client.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,8 +26,6 @@ import Enecuum.Framework.Domain.Error
import qualified Enecuum.Framework.Lens as Lens
import qualified Enecuum.Language as L
import Enecuum.Prelude hiding (map, unpack)
import Enecuum.Research.RouteDrawing
import Graphics.GD.Extra

data ClientNode = ClientNode
deriving (Show, Generic)
Expand Down Expand Up @@ -63,7 +61,6 @@ data GetBlock = GetBlock D.StringHash D.Address deriving R
data Protocol = UDP | TCP | RPC deriving (Show, Eq, Ord, Read)
data SendTo = SendTo Address D.PortNumber deriving Read
data Address = Address D.Host D.PortNumber deriving Read
newtype DrawMap = DrawMap D.PortNumber deriving Read

data GenerateBlocksPacket = GenerateBlocksPacket
{ blocks :: D.BlockNumber
Expand Down Expand Up @@ -187,33 +184,6 @@ getBlock (GetBlock hash address) = do
Right (D.MBlockContent block) -> "Microblock is " <> show block
Left requestError -> "Error: " <> requestError

-- | Build connection map.
cardAssembly
:: Map D.StringHash [D.StringHash]
-> Set.Set D.NodeAddress
-> Set.Set D.NodeAddress
-> L.NodeL (Map D.StringHash [D.StringHash])
cardAssembly accum passed nexts
| Set.null nexts = pure accum
| otherwise = do
-- take the address of who will ask the next contact
let currentAddress = Set.elemAt 0 nexts
connects <- fromRight [] <$>
L.makeRpcRequest (A.getRpcAddress currentAddress) M.ConnectMapRequest

-- add the address to the list of the passed
let newPassed :: Set.Set D.NodeAddress
newPassed = Set.insert currentAddress passed

-- add received addresses to the queue and remove from it those that have already visited
let newNexts :: Set.Set D.NodeAddress
newNexts = (nexts `union` Set.fromList connects) \\ newPassed

-- add to the accumulator addresses for the passed address
let newAccum :: Map.Map D.StringHash [D.StringHash]
newAccum = Map.insert (currentAddress ^. Lens.nodeId) ((^. Lens.nodeId) <$> connects) accum
cardAssembly newAccum newPassed newNexts

createNodeId :: M.CreateNodeId -> L.NodeL Text
createNodeId (M.CreateNodeId password) = do
createKeyPair NodeId $ User (Manual password)
Expand Down
27 changes: 0 additions & 27 deletions src/Enecuum/Assets/Nodes/Messages.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,33 +16,6 @@ data SuccessMsg = SuccessMsg
newtype IsDead = IsDead StringHash
deriving (Show, Eq, Generic, ToJSON, FromJSON)


data GetNodeType = GetNodeType
deriving (Show, Eq, Generic, ToJSON, FromJSON)

data NodeType = TypeGraphNode | TypeBN | TypePoA | TypePoW
deriving (Show, Eq, Generic, ToJSON, FromJSON)

-- | BN, NN nodes
data Hello = Hello StringHash D.Address
deriving (Show, Eq, Generic, ToJSON, FromJSON)

data ConnectMapRequest = ConnectMapRequest
deriving (Show, Eq, Generic, ToJSON, FromJSON)

-- | BN node
data ConnectRequest = ConnectRequest StringHash Word64
deriving (Show, Eq, Generic, ToJSON, FromJSON)

newtype PreviousForMe = PreviousForMe StringHash
deriving (Show, Eq, Generic, ToJSON, FromJSON)

newtype NextForMe = NextForMe StringHash
deriving (Show, Eq, Generic, ToJSON, FromJSON)

data GetRoutingMessages = GetRoutingMessages
deriving (Show, Eq, Generic, ToJSON, FromJSON)

-- | Network messages
data Ping = Ping
deriving (Show, Eq, Generic, ToJSON, FromJSON)
Expand Down
58 changes: 0 additions & 58 deletions src/Enecuum/Assets/Nodes/TestClient.hs

This file was deleted.

46 changes: 0 additions & 46 deletions src/Enecuum/Assets/Nodes/TestServer.hs

This file was deleted.

Loading

0 comments on commit 6293f6d

Please sign in to comment.