Skip to content

Commit

Permalink
Merge branch 'feature/i1-add-name-for-each-marionettes-performers'
Browse files Browse the repository at this point in the history
  • Loading branch information
Cj-bc committed Aug 24, 2022
2 parents b6728f1 + a67d759 commit 6baf585
Show file tree
Hide file tree
Showing 4 changed files with 36 additions and 9 deletions.
24 changes: 21 additions & 3 deletions src/VMCMixer/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ import Lens.Micro ((%~), _1, _2)

data HostName = IPAddress Int Int Int Int
| DomainName T.Text
| Localhost
| Localhost deriving (Eq)

instance Show HostName where
show (IPAddress x y z w) = mconcat [show x, ".", show y, ".", show z, ".", show w]
Expand All @@ -48,10 +48,28 @@ parsePort :: String -> Either String Int
parsePort s = eitherResult $ parse validPortNumber (T.pack s) `feed` ""

performer :: Parser Performer
performer = Performer . fromInteger . toInteger <$> validPortNumber
performer = do
name <- option Nothing (try nameField)
port <- validPortNumber
return $ Performer port name
where
nameField = do
name <- takeTill (== ',')
char ','
skipSpace
return $ Just name

marionette :: Parser Marionette
marionette = uncurry Marionette . (_2%~(fromInteger . toInteger)) <$> addressWithPort
marionette = do
name <- option Nothing (try nameField)
(addr, port) <- addressWithPort
return $ Marionette addr port name
where
nameField = do
name <- takeTill (== ',')
char ','
skipSpace
return $ Just name

-- | Int parser with port number range validation.
--
Expand Down
2 changes: 2 additions & 0 deletions src/VMCMixer/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,10 +22,12 @@ import Network.Socket (PortNumber)
import Lens.Micro.TH (makeLenses)

data Performer = Performer { _performerPort :: Int
, _performerName :: Maybe Text
} deriving (Show, Eq)
makeLenses ''Performer

data Marionette = Marionette { _marionetteAddress :: String
, _marionettePort :: Int
, _marionetteName :: Maybe Text
} deriving (Show, Eq)
makeLenses ''Marionette
9 changes: 5 additions & 4 deletions src/VMCMixer/UI/Brick.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ vmc-mixer is distributed in the hope that it will be useful, but WITHOUT ANY WAR
You should have received a copy of the GNU General Public License along with vmc-mixer. If not, see <https://www.gnu.org/licenses/>.
-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell, OverloadedStrings #-}
module VMCMixer.UI.Brick where

import Brick
Expand All @@ -39,7 +39,7 @@ import Network.Socket (Socket)
import VMCMixer.UI.Brick.Attr
import VMCMixer.UI.Brick.Event
import VMCMixer.Parser (parsePerformer)
import VMCMixer.Types (Performer, Marionette, performerPort)
import VMCMixer.Types (Performer, Marionette, performerPort, performerName)

data Name = InputStreams | NewAddrEditor deriving (Ord, Eq, Show)

Expand All @@ -52,8 +52,9 @@ data AppState = AppState { _inputStreams :: List Name Performer
makeLenses ''AppState

renderAddrInfo :: Bool -> Performer -> Widget Name
renderAddrInfo isFocused = str . show . view performerPort
where
renderAddrInfo isFocused performer = hBox [txt . maybe "" id $ view performerName performer
, str $ " (" ++ (show $ view performerPort performer) ++ ")"
]

-- | Draw 'Widget' in border, but with focus-aware attribute
--
Expand Down
10 changes: 8 additions & 2 deletions test/VMCMixer/ParserSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -71,8 +71,14 @@ spec = do

describe "performer" $ do
it "should accept 'NAME, PORT_NUMBER' format" $
performer `tryParse` (T.pack "foo, 300") == Just (Performer 300 (T.pack "foo"))
performer `tryParse` (T.pack "foo, 300") == Just (Performer 300 (Just $ T.pack "foo"))

it "should accept 'PORT_NUMBER' format" $
performer `tryParse` (T.pack "300") == Just (Performer 300 Nothing)

describe "marionette" $ do
it "should accept 'NAME, ADDRESS:PORT_NUMBER' format" $
marionette `tryParse` (T.pack "foo, foobar.org:300") == Just (Marionette "foobar.org" 300 (T.pack "foo"))
marionette `tryParse` (T.pack "foo, foobar.org:300") == Just (Marionette "foobar.org" 300 (Just $ T.pack "foo"))

it "should accept 'ADDRESS:PORT_NUMBER' format" $
marionette `tryParse` (T.pack "foobar.org:300") == Just (Marionette "foobar.org" 300 Nothing)

0 comments on commit 6baf585

Please sign in to comment.