Skip to content
This repository has been archived by the owner on Nov 13, 2024. It is now read-only.

Commit

Permalink
Support ability to change fields of created message #11 (#18)
Browse files Browse the repository at this point in the history
  • Loading branch information
TejasSC authored and chshersh committed Sep 6, 2018
1 parent 6342ea3 commit c2eba0b
Showing 1 changed file with 53 additions and 7 deletions.
60 changes: 53 additions & 7 deletions src/Tui.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiWayIf #-}

module Tui
( setAttr
Expand Down Expand Up @@ -160,35 +161,80 @@ addFVPair = do
completeField :: IO (FieldName, FieldValue)
completeField = do
(fn, fv) <- addFVPair
putStrLn "Change field value? y to keep editing, any other key to continue"
putStrLn "Change this field's value? y to keep editing, any other key to continue"
choice <- getLine
if choice == "y"
then do
(fn2, fv2) <- addFVPair
return (fn2, fv2)
else return (fn, fv)

finishOff :: MsgName -> [(FieldName, FieldValue)] -> [MessageField] -> IO ()
finishOff mn namesVals fields = do
serialize :: MsgName -> [(FieldName, FieldValue)] -> [MessageField] -> IO ()
serialize mn namesVals fields = do
let stringMsg = constructProtoMsg mn namesVals
let msg = Message {messageName = mn, messageFields = fields}
let validationWrong = validateMessage msgSchema msg
if validationWrong == Right ()
then runGhci stringMsg
else print validationWrong

replace :: Int -> a -> [a] -> [a]
replace n arg list = x ++ arg : ys
where
(x,_:ys) = splitAt n list

main :: IO ()
main = do
mn <- addMsgName
(fnA, fvA) <- completeField
let field1 = MessageField {messageFieldName = fnA, messageFieldValue = fvA}
let field1 = (MessageField fnA fvA)
(fnB, fvB) <- completeField
let field2 = MessageField {messageFieldName = fnB, messageFieldValue = fvB}
let field2 = (MessageField fnB fvB)
(fnC, fvC) <- completeField
let field3 = MessageField {messageFieldName = fnC, messageFieldValue = fvC}
let field3 = (MessageField fnC fvC)
let namesVals = [(fnA, fvA)
, (fnB, fvB)
, (fnC, fvC)
, (FN "_unknownFields", FText (Rep []))]
let fields = [field1, field2, field3]
finishOff mn namesVals fields
serialize mn namesVals fields
changeFieldsOrNot mn namesVals fields
where
changeFieldsOrNot :: MsgName
-> [(FieldName, FieldValue)]
-> [MessageField]
-> IO ()
changeFieldsOrNot mn namesVals fields = do
putStrLn "Change any field's value? y for yes, s to serialize, any other key to quit"
choice <- getLine
if choice == "y"
then do
(newFN, newFV) <- completeField
if | newFN == messageFieldName (fields!!0) ->
let (newNamesVals, newFields) = doubleReplace 0 (newFN, newFV) namesVals fields
in changeFieldsOrNot mn newNamesVals newFields
| newFN == messageFieldName (fields!!1) ->
let (newNamesVals, newFields) = doubleReplace 1 (newFN, newFV) namesVals fields
in changeFieldsOrNot mn newNamesVals newFields
| otherwise ->
let (newNamesVals, newFields) = doubleReplace 2 (newFN, newFV) namesVals fields
in changeFieldsOrNot mn newNamesVals newFields
else if choice == "s"
then useTwo serialize changeFieldsOrNot mn namesVals fields
else putStrLn "Ok, see final serialisation above."

doubleReplace :: Int
-> (FieldName, FieldValue)
-> [(FieldName, FieldValue)]
-> [MessageField]
-> ([(FieldName, FieldValue)], [MessageField])
doubleReplace n (newFN, newFV) namesVals fields =
( replace n (newFN, newFV) namesVals
, replace n (MessageField newFN newFV) fields)

useTwo :: (a -> b -> c -> IO ())
-> (a -> b -> c -> IO ())
-> a -> b -> c -> IO ()
useTwo f g a b c = do
f a b c
g a b c

0 comments on commit c2eba0b

Please sign in to comment.