Skip to content

Commit

Permalink
expose decodeJsonSelection to allow downstream users to decode output…
Browse files Browse the repository at this point in the history
… selection specs
  • Loading branch information
iostat committed Sep 16, 2019
1 parent 2788dda commit 83d201b
Show file tree
Hide file tree
Showing 3 changed files with 28 additions and 24 deletions.
7 changes: 6 additions & 1 deletion src/Language/Solidity/Compiler/Types.purs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,8 @@ module Language.Solidity.Compiler.Types
import Language.Solidity.Compiler.Types.Common ( ContractMapped
, FileMapped
) as Common
import Language.Solidity.Compiler.Types.Input ( Remapping(..)
import Language.Solidity.Compiler.Types.Input ( class IsSelection
, Remapping(..)
, CompilerSettings(..)
, OptimizerDetails(..)
, YulOptimizerDetails(..)
Expand All @@ -27,6 +28,10 @@ import Language.Solidity.Compiler.Types.Input ( Remapping(..)
, Source(..)
, Sources(..)
, CompilerInput(..)
, decodeJsonSelection
, encodeJsonSelection
, fromSelection
, toSelection
) as Input
import Language.Solidity.Compiler.Types.Output ( ErrorType(..)
, ErrorSeverity(..)
Expand Down
2 changes: 1 addition & 1 deletion src/Language/Solidity/Compiler/Types/Input.purs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ import Data.Maybe (Maybe)
import Data.Newtype (class Newtype)
import Foreign.Object as FO
import Network.Ethereum.Types (HexString)
import Language.Solidity.Compiler.Types.Settings (CompilerSettings(..), ContractLevelSelection(..), EvmBytecodeOutput(..), EvmOutputSelection(..), EvmVersion(..), EwasmOutputSelection(..), FileLevelSelection(..), Libraries(..), Library(..), MetadataSettings(..), OptimizerDetails(..), OptimizerSettings(..), OutputSelection(..), OutputSelections(..), Remapping(..), YulOptimizerDetails(..))
import Language.Solidity.Compiler.Types.Settings (class IsSelection, CompilerSettings(..), ContractLevelSelection(..), EvmBytecodeOutput(..), EvmOutputSelection(..), EvmVersion(..), EwasmOutputSelection(..), FileLevelSelection(..), Libraries(..), Library(..), MetadataSettings(..), OptimizerDetails(..), OptimizerSettings(..), OutputSelection(..), OutputSelections(..), Remapping(..), YulOptimizerDetails(..), decodeJsonSelection, encodeJsonSelection, fromSelection, toSelection)

--------------------------------------------------
--- "language" field of input
Expand Down
43 changes: 21 additions & 22 deletions src/Language/Solidity/Compiler/Types/Settings.purs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
module Language.Solidity.Compiler.Types.Settings
( Remapping(..)
( class IsSelection
, Remapping(..)
, CompilerSettings(..)
, OptimizerDetails(..)
, YulOptimizerDetails(..)
Expand All @@ -15,6 +16,10 @@ module Language.Solidity.Compiler.Types.Settings
, ContractLevelSelection(..)
, OutputSelection(..)
, OutputSelections(..)
, decodeJsonSelection
, encodeJsonSelection
, fromSelection
, toSelection
) where

import Prelude
Expand All @@ -23,10 +28,9 @@ import Data.Argonaut (class DecodeJson, class EncodeJson, Json, decodeJson, enco
import Data.Argonaut as A
import Data.Array (nub, null, uncons)
import Data.Either (Either(..), note)
import Data.Maybe (Maybe(..), maybe)
import Data.Newtype (class Newtype, un)
import Data.Maybe (Maybe(..), fromMaybe)
import Data.String (Pattern(..), joinWith, split)
import Data.Traversable (sequence)
import Data.Traversable (for, traverse)
import Data.Tuple (Tuple(..))
import Foreign.Object as FO
import Language.Solidity.Compiler.Types.Common (ContractMapped, FileMapped, flattenOptionalArray)
Expand Down Expand Up @@ -224,20 +228,15 @@ class IsSelection a where
toSelection :: a -> Array String
fromSelection :: Array String -> Maybe a

newtype JsonSelection a = JsonSelection a
derive instance newtypeJsonSelection :: Newtype (JsonSelection a) _
derive newtype instance eqJsonSelection :: Eq a => Eq (JsonSelection a)
derive newtype instance ordJsonSelection :: Ord a => Ord (JsonSelection a)
decodeJsonSelection :: forall a. IsSelection a => Json -> Either String a
decodeJsonSelection j = do
s <- decodeJson j
let splits = split (Pattern ".") s
sels = fromSelection splits
note ("Unknown output selection \"" <> s <> "\"") sels

instance decodeJsonSelection :: IsSelection a => DecodeJson (JsonSelection a) where
decodeJson j = do
s <- decodeJson j
let splits = split (Pattern ".") s
sels = fromSelection splits
note ("Unknown output selection " <> s) (JsonSelection <$> sels)

instance encodeJsonSelection :: IsSelection a => EncodeJson (JsonSelection a) where
encodeJson = fromString <<< joinWith "." <<< toSelection <<< un JsonSelection
encodeJsonSelection :: forall a. IsSelection a => a -> Json
encodeJsonSelection = fromString <<< joinWith "." <<< toSelection

mapFromSelectionNullable :: forall a b. IsSelection a => (Maybe a -> b) -> Array String -> Maybe b
mapFromSelectionNullable f [] = Just (f Nothing)
Expand Down Expand Up @@ -365,15 +364,15 @@ derive instance ordOutputSelection :: Ord OutputSelection
instance decodeJsonOutputSelection :: DecodeJson OutputSelection where
decodeJson j = do
(o :: FO.Object Json) <- decodeJson j
let Tuple fileJ contractJ = maybe (Tuple jsonEmptyArray o) identity $ FO.pop "" o
file <- (map $ un JsonSelection) <$> decodeJson fileJ
contract <- sequence $ (map (map (un JsonSelection)) <<< decodeJson) <$> contractJ
let Tuple fileJ contractJ = fromMaybe (Tuple jsonEmptyArray o) $ FO.pop "" o
file <- traverse decodeJsonSelection =<< decodeJson fileJ
contract <- for contractJ $ (traverse decodeJsonSelection <=< decodeJson)
pure $ OutputSelection { file, contract }

instance encodeJsonOutputSelection :: EncodeJson OutputSelection where
encodeJson (OutputSelection { file, contract }) =
let fileLevelJson = nub $ (encodeJson <<< JsonSelection) <$> file
contractLevelJson = (nub <<< map (encodeJson <<< JsonSelection)) <$> contract
let fileLevelJson = nub $ encodeJsonSelection <$> file
contractLevelJson = (nub <<< map encodeJsonSelection) <$> contract
allSels = FO.insert "" fileLevelJson contractLevelJson
nonEmptySelections = FO.filter (not <<< null) allSels
in encodeJson nonEmptySelections
Expand Down

0 comments on commit 83d201b

Please sign in to comment.