11module Statebox.Console where
22
33import Prelude
4+ import Data.Array (cons , filter )
45import Data.Either (either )
56import Data.Generic.Rep
67import Data.Lens
@@ -20,7 +21,6 @@ import Halogen.HTML.Events (onClick, onValueInput)
2021import Halogen.Query.HalogenM (HalogenM )
2122
2223import Statebox.Console.DAO as DAO
23- import View.Model (Project (..), ProjectId )
2424
2525import Stripe as Stripe
2626
@@ -29,18 +29,44 @@ import Debug.Trace (spy)
2929-- TODO
3030fakeCustomerId = " TODO"
3131
32+ type ApiKey = { hex :: Hex , name :: String }
33+ type RootId = String -- TODO get from stbx-core
34+ type TxHash = Hex -- TODO get from stbx-core
35+ type Hex = String -- TODO get from stbx-core
36+
37+ -- ------------------------------------------------------------------------------
38+
39+ -- | projects are collections of root-transactions and are used to manage the public keys associated to those.
40+ type Project =
41+ { name :: String
42+ , rootTransactions :: Array TxHash
43+ }
44+
45+ type ProjectId = String
46+
47+ -- ------------------------------------------------------------------------------
48+
49+ type TxPubInfo =
50+ { name :: String -- TODO seems redundant if we have the hash
51+ , message :: String -- TODO seems redundant if we have the hash
52+ , hash :: TxHash
53+ , key :: Unit -- TODO is this the key of a genesis tx?
54+ }
55+
3256-- ------------------------------------------------------------------------------
3357
3458type State =
35- { route :: Route
36- , customer :: Maybe Stripe.Customer
37- , paymentMethods :: Array Stripe.PaymentMethod
38- , subscriptions :: Array Stripe.Subscription
39- , plans :: Array Stripe.PlanWithExpandedProduct
40- , accounts :: Array { invoices :: Array Stripe.Invoice
41- }
42- , status :: AppStatus
43- , projects :: Map ProjectId Project
59+ { route :: Route
60+ , customer :: Maybe Stripe.Customer
61+ , paymentMethods :: Array Stripe.PaymentMethod
62+ , subscriptions :: Array Stripe.Subscription
63+ , plans :: Array Stripe.PlanWithExpandedProduct
64+ , accounts :: Array { invoices :: Array Stripe.Invoice
65+ }
66+ , projects :: Map ProjectId Project
67+ , apiKeys :: Array ApiKey
68+ , rootTransactions :: Array TxHash
69+ , status :: AppStatus
4470 }
4571
4672_accounts = prop (SProxy :: SProxy " accounts" )
@@ -53,8 +79,9 @@ data Route
5379 | Projects
5480 | ProjectR ProjectId
5581 | APIKeys
82+ | RootTx
5683 | Invoices Stripe.CustomerId
57- | Account
84+ | Account Stripe.CustomerId
5885 | Subscription
5986 | Plan
6087
@@ -77,6 +104,15 @@ type Input = State
77104
78105data Action
79106 = SelectRoute Route
107+
108+ | CreateRootTx
109+ | PublishRootTx TxPubInfo
110+
111+ | CreateApiKey
112+ | DeprecateApiKey ApiKey
113+ | AssociateApiKeyWithProject ApiKey ProjectId
114+ | AssociateApiKeyWithRoot ApiKey RootId
115+
80116 | FetchStuff
81117
82118data Query a
@@ -100,12 +136,41 @@ handleQuery = case _ of
100136 handleAction x
101137 pure (Just next)
102138
139+ -- NavigateTo newRoute next -> do
140+ -- H.modify_ $ \state -> state -- { route = newRoute }
141+ -- pure (Just next)
142+
103143handleAction :: ∀ m . MonadAff m => Action -> HalogenM State Action ChildSlots Void m Unit
104144handleAction = case _ of
105145
146+ -- NavigateTo newRoute ->
147+ -- H.modify_ $ \state -> state { route = newRoute }
148+
106149 SelectRoute newRoute -> do
107150 H .modify_ \state -> state { route = newRoute }
108151
152+ CreateRootTx -> do
153+ H .modify_ $ _ { status = ErrorStatus " Create root transaction." }
154+
155+ PublishRootTx txPubInfo -> do
156+ H .modify_ $ \state -> state { status = ErrorStatus " Publish root transaction."
157+ , rootTransactions = txPubInfo.hash `cons` state.rootTransactions
158+ }
159+
160+ CreateApiKey -> do
161+ H .modify_ $ _ { status = ErrorStatus " Create API key." }
162+
163+ AssociateApiKeyWithProject apiKey projectId -> do
164+ H .modify_ $ _ { status = ErrorStatus $ " Associate API Key '" <> apiKey.name <> " ' (hex: " <> apiKey.hex <> " ) with project " <> projectId <> " ." }
165+
166+ AssociateApiKeyWithRoot apiKey rootTxId -> do
167+ H .modify_ $ _ { status = ErrorStatus $ " Associate API Key '" <> apiKey.name <> " ' (hex: " <> apiKey.hex <> " ) with root transaction " <> rootTxId <> " ." }
168+
169+ DeprecateApiKey apiKey -> do
170+ H .modify_ $ \state -> state { status = ErrorStatus $ " Successfully deprecated API key '" <> apiKey.name <> " '."
171+ , apiKeys = filter (\k -> k /= apiKey) state.apiKeys
172+ }
173+
109174 FetchStuff -> do
110175 H .liftEffect $ log " handling action FetchStuff..."
111176
@@ -161,7 +226,6 @@ navMenuHtml state =
161226 div []
162227 [ button [ onClick \e -> Just $ SelectRoute $ Home ] [ text " Home" ]
163228 , button [ onClick \e -> Just $ SelectRoute $ Projects ] [ text " Projects" ]
164- , button [ onClick \e -> Just $ SelectRoute $ Account ] [ text " Billing Accounts" ]
165229 , button [ onClick \e -> Just $ SelectRoute $ APIKeys ] [ text " API Keys" ]
166230 , button [ onClick \e -> Just $ SelectRoute $ Invoices fakeCustomerId ] [ text " Invoices" ]
167231 , button [ onClick \e -> Just $ SelectRoute $ Subscription ] [ text " Subscriptions" ]
@@ -173,28 +237,64 @@ contentHtml state = case state.route of
173237 Home ->
174238 div []
175239 [ h2 [] [ text " Statebox Cloud Admin Console" ]
176- , text " Welcome!"
240+
241+ , h3 [] [ text " Projects" ]
242+ , ul [] $ Map .toUnfoldable state.projects <#> (\(projectId /\ project) ->
243+ li [] [ button [ onClick \e -> Just $ SelectRoute $ ProjectR projectId ] [ text project.name ] ])
244+
245+ , h3 [] [ text " Billing accounts" ]
246+ , ul [] $ customers <#> \customer ->
247+ li [] [ button [ onClick \e -> Just $ SelectRoute $ Account customer.id ] [ text $ fold customer.name ]
248+ , text $ fold customer.description
249+ ]
250+
251+ , h3 [] [ text " API keys" ]
252+ , ul [] $ state.apiKeys <#> \key -> li [] [ p [] [ text key.name ]
253+ , p [] [ text key.hex ]
254+ ]
177255 ]
256+ where
257+ -- TODO in reality we should have multiple customers
258+ customers :: Array Stripe.Customer
259+ customers = maybe [] (\c -> [c]) state.customer
178260 Projects ->
179261 div [] $
180262 [ h2 [] [ text " Projects" ]
181263 , div [] $ Map .toUnfoldable state.projects <#>
182264 (\(projectId /\ project) -> button [ onClick \e -> Just $ SelectRoute $ ProjectR projectId ] [ text project.name ])
183265 ]
266+ ProjectR projectId ->
267+ projectMaybe # maybe (text $ " project " <> projectId <> " not found." ) (\project ->
268+ div []
269+ [ h2 [] [ text $ " Project " <> show projectId ]
270+ , h3 [] [ text $ " API keys" ]
271+ , h3 [] [ text $ " Roots" ]
272+ , ul [] (project.rootTransactions <#> \txHash -> li [] [ text txHash ])
273+ , p [] [ button [ onClick \e -> Just $ SelectRoute $ RootTx ] [ text " Create new root tx" ] ]
274+ ]
275+ )
276+ where
277+ projectMaybe = Map .lookup projectId state.projects
184278 APIKeys ->
185279 div [] $
186280 [ h2 [] [ text " API keys" ]
187- , p [] [ text " * Create" ]
188- , p [] [ text " * Deprecate" ]
281+ , p [] [ button [ onClick \e -> Just $ CreateApiKey ] [ text " Create new API key" ] ]
282+ , ul [] $ state.apiKeys <#> \key -> li [] [ p [] [ text key.name ]
283+ , p [] [ text key.hex ]
284+ , p [] [ button [ onClick \e -> Just $ DeprecateApiKey key ] [ text " Deprecate" ] ]
285+ ]
189286 , p [] [ text " * Assign to a root" ]
190287 ]
191- ProjectR projectId ->
288+ RootTx ->
192289 div []
193- [ h2 [] [ text $ " Project " <> show projectId ]
194- , h3 [] [ text $ " API keys" ]
195- , h3 [] [ text $ " Roots" ]
290+ [ h2 [] [ text " Create root transaction" ]
291+ , p [] [ text " name" ]
292+ , p [] [ text " message" ]
293+ , p [] [ text " hash" ]
294+ , p [] [ text " valid key [key 1] (add)" ]
295+ , p [] [ button [ onClick \e -> Just $ PublishRootTx { name: " Example tx" , message: " Hi there!" , hash: " CAF3CAF3" , key: unit } ] [ text " Publish" ] ]
196296 ]
197- Account ->
297+ Account customerId ->
198298 div []
199299 [ h2 [] [ text " Customer" ]
200300 , div [] (maybe [] (pure <<< customerHtml) state.customer)
0 commit comments