module EVM.Flatten (flatten) where
import EVM.Dapp (DappInfo, dappSources, regexMatches)
import EVM.Solidity (sourceAsts)
import EVM.Demand (demand)
import Control.Lens (preview, view, universe)
import Data.Aeson (Value (String))
import Data.Aeson.Lens (key, _String, _Array, _Integer)
import qualified Data.Graph.Inductive.Graph as Fgl
import qualified Data.Graph.Inductive.PatriciaTree as Fgl
import qualified Data.Graph.Inductive.Query.BFS as Fgl
import qualified Data.Graph.Inductive.Query.DFS as Fgl
import Data.SemVer (SemVerRange, parseSemVerRange)
import qualified Data.SemVer as SemVer
import Control.Monad (forM)
import Data.ByteString (ByteString)
import Data.Foldable (foldl', toList)
import Data.List (sort, nub, (\\))
import Data.Map (Map, (!), (!?))
import Data.Maybe (mapMaybe, isJust, catMaybes, fromMaybe)
import Data.Text (Text, unpack, pack, intercalate)
import Data.Text.Encoding (encodeUtf8, decodeUtf8)
import Text.Read (readMaybe)
import qualified Data.Map as Map
import qualified Data.Text as Text
import qualified Data.ByteString as BS
type FileGraph = Fgl.Gr Text ()
getAttribute :: Text -> Value -> Maybe Value
getAttribute :: Text -> Value -> Maybe Value
getAttribute Text
s Value
v = case Getting (First Value) Value Value -> Value -> Maybe Value
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview (Text -> Traversal' Value Value
forall t. AsValue t => Text -> Traversal' t Value
key Text
"attributes" Getting (First Value) Value Value
-> Getting (First Value) Value Value
-> Getting (First Value) Value Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Traversal' Value Value
forall t. AsValue t => Text -> Traversal' t Value
key Text
s) Value
v of
Maybe Value
Nothing -> Getting (First Value) Value Value -> Value -> Maybe Value
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview (Text -> Traversal' Value Value
forall t. AsValue t => Text -> Traversal' t Value
key Text
s) Value
v
Just Value
r -> Value -> Maybe Value
forall a. a -> Maybe a
Just Value
r
importsFrom :: Value -> [Text]
importsFrom :: Value -> [Text]
importsFrom Value
ast =
let
allNodes :: [Value]
allNodes :: [Value]
allNodes = Value -> [Value]
forall a. Plated a => a -> [a]
universe Value
ast
resolveImport :: Value -> Maybe Text
resolveImport :: Value -> Maybe Text
resolveImport Value
node =
case Getting (First Value) Value Value -> Value -> Maybe Value
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview (Text -> Traversal' Value Value
forall t. AsValue t => Text -> Traversal' t Value
key Text
"nodeType") Value
node of
Just (String Text
"ImportDirective") -> Getting Text Value Text -> Value -> Text
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Text Value Text
forall t. AsPrimitive t => Prism' t Text
_String (Value -> Text) -> Maybe Value -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Value -> Maybe Value
getAttribute Text
"absolutePath" Value
node
Maybe Value
_ ->
case Getting (First Value) Value Value -> Value -> Maybe Value
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview (Text -> Traversal' Value Value
forall t. AsValue t => Text -> Traversal' t Value
key Text
"name") Value
node of
Just (String Text
"ImportDirective") ->
Getting Text Value Text -> Value -> Text
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Text Value Text
forall t. AsPrimitive t => Prism' t Text
_String (Value -> Text) -> Maybe Value -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Value -> Maybe Value
getAttribute Text
"absolutePath" Value
node
Maybe Value
_ ->
Maybe Text
forall a. Maybe a
Nothing
in (Value -> Maybe Text) -> [Value] -> [Text]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Value -> Maybe Text
resolveImport [Value]
allNodes
flatten :: DappInfo -> Text -> IO ()
flatten :: DappInfo -> Text -> IO ()
flatten DappInfo
dapp Text
target = do
let
graph :: FileGraph
graph :: FileGraph
graph = [LNode Text] -> [LEdge ()] -> FileGraph
forall (gr :: * -> * -> *) a b.
Graph gr =>
[LNode a] -> [LEdge b] -> gr a b
Fgl.mkGraph [LNode Text]
nodes [LEdge ()]
edges
nodes :: [(Int, Text)]
nodes :: [LNode Text]
nodes = [Int] -> [Text] -> [LNode Text]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1..] (Map Text Value -> [Text]
forall k a. Map k a -> [k]
Map.keys Map Text Value
asts)
edges :: [LEdge ()]
edges =
[ (Map Text Int
indices Map Text Int -> Text -> Int
forall k a. Ord k => Map k a -> k -> a
! Text
s, Map Text Int
indices Map Text Int -> Text -> Int
forall k a. Ord k => Map k a -> k -> a
! Text
t, ())
| (Text
s, Value
v) <- Map Text Value -> [(Text, Value)]
forall k a. Map k a -> [(k, a)]
Map.toList Map Text Value
asts
, Text
t <- Value -> [Text]
importsFrom Value
v ]
indices :: Map Text Int
indices :: Map Text Int
indices = [(Text, Int)] -> Map Text Int
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Text
v, Int
k) | (Int
k, Text
v) <- [LNode Text]
nodes]
asts :: Map Text Value
asts :: Map Text Value
asts = Getting (Map Text Value) DappInfo (Map Text Value)
-> DappInfo -> Map Text Value
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ((SourceCache -> Const (Map Text Value) SourceCache)
-> DappInfo -> Const (Map Text Value) DappInfo
Lens' DappInfo SourceCache
dappSources ((SourceCache -> Const (Map Text Value) SourceCache)
-> DappInfo -> Const (Map Text Value) DappInfo)
-> ((Map Text Value -> Const (Map Text Value) (Map Text Value))
-> SourceCache -> Const (Map Text Value) SourceCache)
-> Getting (Map Text Value) DappInfo (Map Text Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Map Text Value -> Const (Map Text Value) (Map Text Value))
-> SourceCache -> Const (Map Text Value) SourceCache
Lens' SourceCache (Map Text Value)
sourceAsts) DappInfo
dapp
topScopeIds :: [Integer]
topScopeIds :: [Integer]
topScopeIds = [[Integer]] -> [Integer]
forall a. Monoid a => [a] -> a
mconcat ([[Integer]] -> [Integer]) -> [[Integer]] -> [Integer]
forall a b. (a -> b) -> a -> b
$ (Value -> [Integer]) -> [Value] -> [[Integer]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Value -> [Integer]
f ([Value] -> [[Integer]]) -> [Value] -> [[Integer]]
forall a b. (a -> b) -> a -> b
$ Map Text Value -> [Value]
forall k a. Map k a -> [a]
Map.elems Map Text Value
asts
where
id' :: Value -> Maybe Integer
id' = Getting (First Integer) Value Integer -> Value -> Maybe Integer
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview (Text -> Traversal' Value Value
forall t. AsValue t => Text -> Traversal' t Value
key Text
"id" ((Value -> Const (First Integer) Value)
-> Value -> Const (First Integer) Value)
-> Getting (First Integer) Value Integer
-> Getting (First Integer) Value Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting (First Integer) Value Integer
forall t. AsNumber t => Prism' t Integer
_Integer)
f :: Value -> [Integer]
f Value
ast =
[ String -> Maybe Integer -> Integer
forall a. String -> Maybe a -> a
fromJust' String
"no id for SourceUnit" (Maybe Integer -> Integer) -> Maybe Integer -> Integer
forall a b. (a -> b) -> a -> b
$ Value -> Maybe Integer
id' Value
node
| Value
node <- Value -> [Value]
forall a. Plated a => a -> [a]
universe Value
ast
, Text -> Value -> Bool
nodeIs Text
"SourceUnit" Value
node
]
contractsAndStructsToRename :: Map Integer Text
contractsAndStructsToRename :: Map Integer Text
contractsAndStructsToRename =
[(Integer, Text)] -> Map Integer Text
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
([(Integer, Text)] -> Map Integer Text)
-> [(Integer, Text)] -> Map Integer Text
forall a b. (a -> b) -> a -> b
$ [(Integer, Text)] -> [(Integer, Text)]
indexed [ (Integer, Text)
x | (Integer, Text)
x <- [(Integer, Text)]
xs, ((Integer, Text) -> Text
forall a b. (a, b) -> b
snd (Integer, Text)
x) Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
xs' ]
where
xs :: [(Integer, Text)]
xs = (Value -> [(Integer, Text)]) -> [Value] -> [(Integer, Text)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Value -> [(Integer, Text)]
f ([Value] -> [(Integer, Text)]) -> [Value] -> [(Integer, Text)]
forall a b. (a -> b) -> a -> b
$ Map Text Value -> [Value]
forall k a. Map k a -> [a]
Map.elems Map Text Value
asts
xs' :: [Text]
xs' = [Text] -> [Text]
forall a. Eq a => [a] -> [a]
repeated ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ ((Integer, Text) -> Text) -> [(Integer, Text)] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Integer, Text) -> Text
forall a b. (a, b) -> b
snd [(Integer, Text)]
xs
scope :: Value -> Maybe Integer
scope Value
x = Text -> Value -> Maybe Value
getAttribute Text
"scope" Value
x Maybe Value -> (Value -> Maybe Integer) -> Maybe Integer
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Getting (First Integer) Value Integer -> Value -> Maybe Integer
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview Getting (First Integer) Value Integer
forall t. AsNumber t => Prism' t Integer
_Integer
name :: Value -> Maybe Text
name Value
x = Text -> Value -> Maybe Value
getAttribute Text
"name" Value
x Maybe Value -> (Value -> Maybe Text) -> Maybe Text
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Getting (First Text) Value Text -> Value -> Maybe Text
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview Getting (First Text) Value Text
forall t. AsPrimitive t => Prism' t Text
_String
id' :: Value -> Maybe Integer
id' = Getting (First Integer) Value Integer -> Value -> Maybe Integer
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview (Text -> Traversal' Value Value
forall t. AsValue t => Text -> Traversal' t Value
key Text
"id" ((Value -> Const (First Integer) Value)
-> Value -> Const (First Integer) Value)
-> Getting (First Integer) Value Integer
-> Getting (First Integer) Value Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting (First Integer) Value Integer
forall t. AsNumber t => Prism' t Integer
_Integer)
p :: Value -> Bool
p Value
x = (Text -> Value -> Bool
nodeIs Text
"ContractDefinition" Value
x Bool -> Bool -> Bool
|| Text -> Value -> Bool
nodeIs Text
"StructDefinition" Value
x)
Bool -> Bool -> Bool
&& (String -> Maybe Integer -> Integer
forall a. String -> Maybe a -> a
fromJust' String
"no contract/struct scope" (Maybe Integer -> Integer) -> Maybe Integer -> Integer
forall a b. (a -> b) -> a -> b
$ Value -> Maybe Integer
scope Value
x) Integer -> [Integer] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Integer]
topScopeIds
f :: Value -> [(Integer, Text)]
f Value
ast =
[ ( String -> Maybe Integer -> Integer
forall a. String -> Maybe a -> a
fromJust' String
"no id for top scoped contract or struct" (Maybe Integer -> Integer) -> Maybe Integer -> Integer
forall a b. (a -> b) -> a -> b
$ Value -> Maybe Integer
id' Value
node
, String -> Maybe Text -> Text
forall a. String -> Maybe a -> a
fromJust' String
"no id for top scoped contract or struct" (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ Value -> Maybe Text
name Value
node
)
| Value
node <- Value -> [Value]
forall a. Plated a => a -> [a]
universe Value
ast
, Value -> Bool
p Value
node
]
contractStructs :: [(Integer, (Integer, Text))]
contractStructs :: [(Integer, (Integer, Text))]
contractStructs = [[(Integer, (Integer, Text))]] -> [(Integer, (Integer, Text))]
forall a. Monoid a => [a] -> a
mconcat ([[(Integer, (Integer, Text))]] -> [(Integer, (Integer, Text))])
-> [[(Integer, (Integer, Text))]] -> [(Integer, (Integer, Text))]
forall a b. (a -> b) -> a -> b
$ (Value -> [(Integer, (Integer, Text))])
-> [Value] -> [[(Integer, (Integer, Text))]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Value -> [(Integer, (Integer, Text))]
f ([Value] -> [[(Integer, (Integer, Text))]])
-> [Value] -> [[(Integer, (Integer, Text))]]
forall a b. (a -> b) -> a -> b
$ Map Text Value -> [Value]
forall k a. Map k a -> [a]
Map.elems Map Text Value
asts
where
scope :: Value -> Maybe Integer
scope Value
x = Text -> Value -> Maybe Value
getAttribute Text
"scope" Value
x Maybe Value -> (Value -> Maybe Integer) -> Maybe Integer
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Getting (First Integer) Value Integer -> Value -> Maybe Integer
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview Getting (First Integer) Value Integer
forall t. AsNumber t => Prism' t Integer
_Integer
cname :: Value -> Maybe Text
cname Value
x = Text -> Value -> Maybe Value
getAttribute Text
"canonicalName" Value
x Maybe Value -> (Value -> Maybe Text) -> Maybe Text
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Getting (First Text) Value Text -> Value -> Maybe Text
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview Getting (First Text) Value Text
forall t. AsPrimitive t => Prism' t Text
_String
id' :: Value -> Maybe Integer
id' = Getting (First Integer) Value Integer -> Value -> Maybe Integer
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview (Text -> Traversal' Value Value
forall t. AsValue t => Text -> Traversal' t Value
key Text
"id" ((Value -> Const (First Integer) Value)
-> Value -> Const (First Integer) Value)
-> Getting (First Integer) Value Integer
-> Getting (First Integer) Value Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting (First Integer) Value Integer
forall t. AsNumber t => Prism' t Integer
_Integer)
p :: Value -> Bool
p Value
x = (Text -> Value -> Bool
nodeIs Text
"StructDefinition" Value
x)
Bool -> Bool -> Bool
&& (String -> Maybe Integer -> Integer
forall a. String -> Maybe a -> a
fromJust' String
"nested struct" (Maybe Integer -> Integer) -> Maybe Integer -> Integer
forall a b. (a -> b) -> a -> b
$ Value -> Maybe Integer
scope Value
x) Integer -> Map Integer Text -> Bool
forall k a. Ord k => k -> Map k a -> Bool
`Map.member` Map Integer Text
contractsAndStructsToRename
f :: Value -> [(Integer, (Integer, Text))]
f Value
ast =
[ let
id'' :: Integer
id'' = String -> Maybe Integer -> Integer
forall a. String -> Maybe a -> a
fromJust' String
"no id for nested struct" (Maybe Integer -> Integer) -> Maybe Integer -> Integer
forall a b. (a -> b) -> a -> b
$ Value -> Maybe Integer
id' Value
node
cname' :: Text
cname' = String -> Maybe Text -> Text
forall a. String -> Maybe a -> a
fromJust'
(String
"no canonical name of nested struct with id:" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
id'') (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ Value -> Maybe Text
cname Value
node
ref :: Integer
ref = String -> Maybe Integer -> Integer
forall a. String -> Maybe a -> a
fromJust'
(String
"no scope of nested struct with id:" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
id'') (Maybe Integer -> Integer) -> Maybe Integer -> Integer
forall a b. (a -> b) -> a -> b
$ Value -> Maybe Integer
scope Value
node
in
(Integer
id'', (Integer
ref, Text
cname'))
| Value
node <- Value -> [Value]
forall a. Plated a => a -> [a]
universe Value
ast
, Value -> Bool
p Value
node
]
case Text -> Map Text Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Text
target Map Text Int
indices of
Maybe Int
Nothing ->
String -> IO ()
forall a. HasCallStack => String -> a
error String
"didn't find contract AST"
Just Int
root -> do
let
subgraph :: Fgl.Gr Text ()
subgraph :: FileGraph
subgraph = [Int] -> FileGraph -> FileGraph
forall (gr :: * -> * -> *) a b.
DynGraph gr =>
[Int] -> gr a b -> gr a b
Fgl.subgraph (Int -> FileGraph -> [Int]
forall (gr :: * -> * -> *) a b. Graph gr => Int -> gr a b -> [Int]
Fgl.bfs Int
root FileGraph
graph) FileGraph
graph
ordered :: [Text]
ordered :: [Text]
ordered = [Text] -> [Text]
forall a. [a] -> [a]
reverse (FileGraph -> [Text]
forall (gr :: * -> * -> *) a b. Graph gr => gr a b -> [a]
Fgl.topsort' FileGraph
subgraph)
pragma :: Text
pragma :: Text
pragma = [Value] -> Text
maximalPragma (Map Text Value -> [Value]
forall k a. Map k a -> [a]
Map.elems ((Text -> Value -> Bool) -> Map Text Value -> Map Text Value
forall k a. (k -> a -> Bool) -> Map k a -> Map k a
Map.filterWithKey (\Text
k Value
_ -> Text
k Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
ordered) Map Text Value
asts))
license :: Text
license :: Text
license = [Value] -> Text
joinLicenses (Map Text Value -> [Value]
forall k a. Map k a -> [a]
Map.elems ((Text -> Value -> Bool) -> Map Text Value -> Map Text Value
forall k a. (k -> a -> Bool) -> Map k a -> Map k a
Map.filterWithKey (\Text
k Value
_ -> Text
k Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
ordered) Map Text Value
asts))
[ByteString]
sources <-
[Text] -> (Text -> IO ByteString) -> IO [ByteString]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [Text]
ordered ((Text -> IO ByteString) -> IO [ByteString])
-> (Text -> IO ByteString) -> IO [ByteString]
forall a b. (a -> b) -> a -> b
$ \Text
path -> do
ByteString
src <- String -> IO ByteString
BS.readFile (Text -> String
unpack Text
path)
ByteString -> IO ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> IO ByteString) -> ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$ [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat
[ ByteString
"////// ", Text -> ByteString
encodeUtf8 Text
path, ByteString
"\n"
, (ByteString, Int) -> ByteString
forall a b. (a, b) -> a
fst
(Map Integer Text
-> [(Integer, (Integer, Text))]
-> (ByteString, Int)
-> Value
-> (ByteString, Int)
prefixContractAst
Map Integer Text
contractsAndStructsToRename
[(Integer, (Integer, Text))]
contractStructs
((ByteString, Int) -> Value -> (ByteString, Int)
stripImportsAndPragmas (ByteString -> (ByteString, Int)
stripLicense ByteString
src) (Map Text Value
asts Map Text Value -> Text -> Value
forall k a. Ord k => Map k a -> k -> a
! Text
path))
(Map Text Value
asts Map Text Value -> Text -> Value
forall k a. Ord k => Map k a -> k -> a
! Text
path))
, ByteString
"\n"
]
Text -> IO ()
forall (m :: * -> *) a. (MonadIO m, NFData a) => a -> m ()
demand Text
target; Text -> IO ()
forall (m :: * -> *) a. (MonadIO m, NFData a) => a -> m ()
demand Text
pragma; [ByteString] -> IO ()
forall (m :: * -> *) a. (MonadIO m, NFData a) => a -> m ()
demand [ByteString]
sources
String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"// hevm: flattened sources of " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Text -> String
unpack Text
target
String -> IO ()
putStrLn (Text -> String
unpack Text
license)
String -> IO ()
putStrLn (Text -> String
unpack Text
pragma)
ByteString -> IO ()
BS.putStr ([ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat [ByteString]
sources)
joinLicenses :: [Value] -> Text
joinLicenses :: [Value] -> Text
joinLicenses [Value]
asts =
case [Text] -> [Text]
forall a. Eq a => [a] -> [a]
nub ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ (Value -> Maybe Text) -> [Value] -> [Text]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (\Value
ast -> Text -> Value -> Maybe Value
getAttribute Text
"license" Value
ast Maybe Value -> (Value -> Maybe Text) -> Maybe Text
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Getting (First Text) Value Text -> Value -> Maybe Text
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview Getting (First Text) Value Text
forall t. AsPrimitive t => Prism' t Text
_String) [Value]
asts of
[] -> Text
""
[Text]
x -> Text
"// SPDX-License-Identifier: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
intercalate Text
" AND " [Text]
x
maximalPragma :: [Value] -> Text
maximalPragma :: [Value] -> Text
maximalPragma [Value]
asts = (
case (Value -> Maybe SemVerRange) -> [Value] -> [SemVerRange]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Value -> Maybe SemVerRange
versions [Value]
asts of
[] -> Text
""
[SemVerRange]
xs ->
Text
"pragma solidity "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
pack (SemVerRange -> String
forall a. Show a => a -> String
show ([SemVerRange] -> SemVerRange
rangeIntersection [SemVerRange]
xs))
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
";\n"
)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (
[Text] -> Text
forall a. Monoid a => [a] -> a
mconcat ([Text] -> Text) -> ([Value] -> [Text]) -> [Value] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> [Text]
forall a. Eq a => [a] -> [a]
nub ([Text] -> [Text]) -> ([Value] -> [Text]) -> [Value] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> [Text]
forall a. Ord a => [a] -> [a]
sort ([Text] -> [Text]) -> ([Value] -> [Text]) -> [Value] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Value -> Text) -> [Value] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Value
ast ->
[Text] -> Text
forall a. Monoid a => [a] -> a
mconcat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ ([Value] -> Text) -> [[Value]] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
(\[Value]
xs -> Text
"pragma "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
intercalate Text
" " [Text
x | String Text
x <- [Value]
xs]
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
";\n")
(Value -> [[Value]]
otherPragmas Value
ast)
)
) [Value]
asts
where
isVersionPragma :: [Value] -> Bool
isVersionPragma :: [Value] -> Bool
isVersionPragma (String Text
"solidity" : [Value]
_) = Bool
True
isVersionPragma [Value]
_ = Bool
False
pragmaComponents :: Value -> [[Value]]
pragmaComponents :: Value -> [[Value]]
pragmaComponents Value
ast = [[Value]]
components
where
ps :: [Value]
ps :: [Value]
ps = (Value -> Bool) -> [Value] -> [Value]
forall a. (a -> Bool) -> [a] -> [a]
filter (Text -> Value -> Bool
nodeIs Text
"PragmaDirective") (Value -> [Value]
forall a. Plated a => a -> [a]
universe Value
ast)
components :: [[Value]]
components :: [[Value]]
components = [Maybe [Value]] -> [[Value]]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe [Value]] -> [[Value]]) -> [Maybe [Value]] -> [[Value]]
forall a b. (a -> b) -> a -> b
$
(Value -> Maybe [Value]) -> [Value] -> [Maybe [Value]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
(((Vector Value -> [Value]) -> Maybe (Vector Value) -> Maybe [Value]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Vector Value -> [Value]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) (Maybe (Vector Value) -> Maybe [Value])
-> (Value -> Maybe (Vector Value)) -> Value -> Maybe [Value]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\Value
x -> Text -> Value -> Maybe Value
getAttribute Text
"literals" Value
x Maybe Value
-> (Value -> Maybe (Vector Value)) -> Maybe (Vector Value)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Getting (First (Vector Value)) Value (Vector Value)
-> Value -> Maybe (Vector Value)
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview Getting (First (Vector Value)) Value (Vector Value)
forall t. AsValue t => Prism' t (Vector Value)
_Array))
[Value]
ps
rangeIntersection :: [SemVerRange] -> SemVerRange
rangeIntersection :: [SemVerRange] -> SemVerRange
rangeIntersection = (SemVerRange -> SemVerRange -> SemVerRange)
-> [SemVerRange] -> SemVerRange
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldr1 SemVerRange -> SemVerRange -> SemVerRange
SemVer.And ([SemVerRange] -> SemVerRange)
-> ([SemVerRange] -> [SemVerRange]) -> [SemVerRange] -> SemVerRange
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [SemVerRange] -> [SemVerRange]
forall a. Eq a => [a] -> [a]
nub ([SemVerRange] -> [SemVerRange])
-> ([SemVerRange] -> [SemVerRange])
-> [SemVerRange]
-> [SemVerRange]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [SemVerRange] -> [SemVerRange]
forall a. Ord a => [a] -> [a]
sort
versions :: Value -> Maybe SemVerRange
versions :: Value -> Maybe SemVerRange
versions Value
ast = ([Value] -> SemVerRange) -> Maybe [Value] -> Maybe SemVerRange
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Value] -> SemVerRange
grok Maybe [Value]
components
where
components :: Maybe [Value]
components :: Maybe [Value]
components =
case ([Value] -> Bool) -> [[Value]] -> [[Value]]
forall a. (a -> Bool) -> [a] -> [a]
filter [Value] -> Bool
isVersionPragma (Value -> [[Value]]
pragmaComponents Value
ast) of
[Value
_:[Value]
xs] -> [Value] -> Maybe [Value]
forall a. a -> Maybe a
Just [Value]
xs
[] -> Maybe [Value]
forall a. Maybe a
Nothing
[[Value]]
x -> String -> Maybe [Value]
forall a. HasCallStack => String -> a
error (String -> Maybe [Value]) -> String -> Maybe [Value]
forall a b. (a -> b) -> a -> b
$ String
"multiple version pragmas" String -> String -> String
forall a. [a] -> [a] -> [a]
++ [[Value]] -> String
forall a. Show a => a -> String
show [[Value]]
x
grok :: [Value] -> SemVerRange
grok :: [Value] -> SemVerRange
grok [Value]
xs =
let
rangeText :: Text
rangeText = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [Text
x | String Text
x <- [Value]
xs]
in
case Text -> Either ParseError SemVerRange
parseSemVerRange Text
rangeText of
Right SemVerRange
r -> SemVerRange
r
Left ParseError
_ ->
String -> SemVerRange
forall a. HasCallStack => String -> a
error (String
"failed to parse SemVer range " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
rangeText)
otherPragmas :: Value -> [[Value]]
otherPragmas :: Value -> [[Value]]
otherPragmas = (([Value] -> Bool) -> [[Value]] -> [[Value]]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> ([Value] -> Bool) -> [Value] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Value] -> Bool
isVersionPragma)) ([[Value]] -> [[Value]])
-> (Value -> [[Value]]) -> Value -> [[Value]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> [[Value]]
pragmaComponents
nodeIs :: Text -> Value -> Bool
nodeIs :: Text -> Value -> Bool
nodeIs Text
t Value
x = Bool
isSourceNode Bool -> Bool -> Bool
&& Bool
hasRightName
where
isSourceNode :: Bool
isSourceNode =
Maybe Value -> Bool
forall a. Maybe a -> Bool
isJust (Getting (First Value) Value Value -> Value -> Maybe Value
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview (Text -> Traversal' Value Value
forall t. AsValue t => Text -> Traversal' t Value
key Text
"src") Value
x)
hasRightName :: Bool
hasRightName =
Text -> Maybe Text
forall a. a -> Maybe a
Just Text
t Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== Getting (First Text) Value Text -> Value -> Maybe Text
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview (Text -> Traversal' Value Value
forall t. AsValue t => Text -> Traversal' t Value
key Text
"name" ((Value -> Const (First Text) Value)
-> Value -> Const (First Text) Value)
-> Getting (First Text) Value Text
-> Getting (First Text) Value Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting (First Text) Value Text
forall t. AsPrimitive t => Prism' t Text
_String) Value
x
Bool -> Bool -> Bool
|| Text -> Maybe Text
forall a. a -> Maybe a
Just Text
t Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== Getting (First Text) Value Text -> Value -> Maybe Text
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview (Text -> Traversal' Value Value
forall t. AsValue t => Text -> Traversal' t Value
key Text
"nodeType" ((Value -> Const (First Text) Value)
-> Value -> Const (First Text) Value)
-> Getting (First Text) Value Text
-> Getting (First Text) Value Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting (First Text) Value Text
forall t. AsPrimitive t => Prism' t Text
_String) Value
x
stripLicense :: ByteString -> (ByteString, Int)
stripLicense :: ByteString -> (ByteString, Int)
stripLicense ByteString
bs =
(Text -> ByteString
encodeUtf8 (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
Text.unlines ([Text]
lines' [Text] -> [Text] -> [Text]
forall a. Eq a => [a] -> [a] -> [a]
\\ [Text]
licenseLines), - [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum (((Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+) (Int -> Int) -> (Text -> Int) -> Text -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Int
Text.length) (Text -> Int) -> [Text] -> [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Text]
licenseLines))
where lines' :: [Text]
lines' = Text -> [Text]
Text.lines (Text -> [Text]) -> Text -> [Text]
forall a b. (a -> b) -> a -> b
$ ByteString -> Text
decodeUtf8 ByteString
bs
licenseLines :: [Text]
licenseLines = (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
filter (Text -> Text -> Bool
regexMatches Text
"SPDX-License-Identifier") [Text]
lines'
stripImportsAndPragmas :: (ByteString, Int) -> Value -> (ByteString, Int)
stripImportsAndPragmas :: (ByteString, Int) -> Value -> (ByteString, Int)
stripImportsAndPragmas (ByteString, Int)
bso Value
ast = (ByteString, Int) -> Value -> (Value -> Bool) -> (ByteString, Int)
stripAstNodes (ByteString, Int)
bso Value
ast Value -> Bool
p
where
p :: Value -> Bool
p Value
x = Text -> Value -> Bool
nodeIs Text
"ImportDirective" Value
x Bool -> Bool -> Bool
|| Text -> Value -> Bool
nodeIs Text
"PragmaDirective" Value
x
stripAstNodes :: (ByteString, Int)-> Value -> (Value -> Bool) -> (ByteString, Int)
stripAstNodes :: (ByteString, Int) -> Value -> (Value -> Bool) -> (ByteString, Int)
stripAstNodes (ByteString, Int)
bso Value
ast Value -> Bool
p =
[(Int, Int)] -> (ByteString, Int)
cutRanges [Value -> (Int, Int)
sourceRange Value
node | Value
node <- Value -> [Value]
forall a. Plated a => a -> [a]
universe Value
ast, Value -> Bool
p Value
node]
where
cutRanges :: [(Int, Int)] -> (ByteString, Int)
cutRanges :: [(Int, Int)] -> (ByteString, Int)
cutRanges ([(Int, Int)] -> [(Int, Int)]
forall a. Ord a => [a] -> [a]
sort -> [(Int, Int)]
rs) = ((ByteString, Int) -> (Int, Int) -> (ByteString, Int))
-> (ByteString, Int) -> [(Int, Int)] -> (ByteString, Int)
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (ByteString, Int) -> (Int, Int) -> (ByteString, Int)
f (ByteString, Int)
bso [(Int, Int)]
rs
where
f :: (ByteString, Int) -> (Int, Int) -> (ByteString, Int)
f (ByteString
bs', Int
n) (Int
i, Int
j) =
( ByteString -> Int -> Int -> ByteString
cut ByteString
bs' (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n) (Int
j Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n)
, Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (String
"/* */" :: String))
cut :: ByteString -> Int -> Int -> ByteString
cut :: ByteString -> Int -> Int -> ByteString
cut ByteString
x Int
i Int
j =
let (ByteString
a, ByteString
b) = Int -> ByteString -> (ByteString, ByteString)
BS.splitAt Int
i ByteString
x
in ByteString
a ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
"/* " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Int -> ByteString -> ByteString
BS.take (Int
j Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
i) ByteString
b ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" */" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Int -> ByteString -> ByteString
BS.drop (Int
j Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
i) ByteString
b
readAs :: Read a => Text -> Maybe a
readAs :: Text -> Maybe a
readAs = String -> Maybe a
forall a. Read a => String -> Maybe a
readMaybe (String -> Maybe a) -> (Text -> String) -> Text -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
Text.unpack
prefixContractAst :: Map Integer Text -> [(Integer, (Integer, Text))] -> (ByteString, Int) -> Value -> (ByteString, Int)
prefixContractAst :: Map Integer Text
-> [(Integer, (Integer, Text))]
-> (ByteString, Int)
-> Value
-> (ByteString, Int)
prefixContractAst Map Integer Text
castr [(Integer, (Integer, Text))]
cs (ByteString, Int)
bso Value
ast = (ByteString, Int)
prefixAstNodes
where
bs :: ByteString
bs = (ByteString, Int) -> ByteString
forall a b. (a, b) -> a
fst (ByteString, Int)
bso
refDec :: Value -> Maybe Integer
refDec Value
x = Text -> Value -> Maybe Value
getAttribute Text
"referencedDeclaration" Value
x Maybe Value -> (Value -> Maybe Integer) -> Maybe Integer
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Getting (First Integer) Value Integer -> Value -> Maybe Integer
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview Getting (First Integer) Value Integer
forall t. AsNumber t => Prism' t Integer
_Integer
name :: Value -> Maybe Text
name Value
x = Text -> Value -> Maybe Value
getAttribute Text
"name" Value
x Maybe Value -> (Value -> Maybe Text) -> Maybe Text
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Getting (First Text) Value Text -> Value -> Maybe Text
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview Getting (First Text) Value Text
forall t. AsPrimitive t => Prism' t Text
_String
id' :: Value -> Maybe Integer
id' = Getting (First Integer) Value Integer -> Value -> Maybe Integer
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview (Text -> Traversal' Value Value
forall t. AsValue t => Text -> Traversal' t Value
key Text
"id" ((Value -> Const (First Integer) Value)
-> Value -> Const (First Integer) Value)
-> Getting (First Integer) Value Integer
-> Getting (First Integer) Value Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting (First Integer) Value Integer
forall t. AsNumber t => Prism' t Integer
_Integer)
p :: Value -> Bool
p Value
x = (Text -> Value -> Bool
nodeIs Text
"ContractDefinition" Value
x Bool -> Bool -> Bool
|| Text -> Value -> Bool
nodeIs Text
"StructDefinition" Value
x)
Bool -> Bool -> Bool
&& (String -> Maybe Integer -> Integer
forall a. String -> Maybe a -> a
fromJust' String
"id of any" (Maybe Integer -> Integer) -> Maybe Integer -> Integer
forall a b. (a -> b) -> a -> b
$ Value -> Maybe Integer
id' Value
x) Integer -> Map Integer Text -> Bool
forall k a. Ord k => k -> Map k a -> Bool
`Map.member` Map Integer Text
castr
p' :: Value -> Bool
p' Value
x =
(Text -> Value -> Bool
nodeIs Text
"Identifier" Value
x Bool -> Bool -> Bool
|| Text -> Value -> Bool
nodeIs Text
"UserDefinedTypeName" Value
x)
Bool -> Bool -> Bool
&& (Maybe Integer -> Bool
forall a. Maybe a -> Bool
isJust (Maybe Integer -> Bool) -> Maybe Integer -> Bool
forall a b. (a -> b) -> a -> b
$ Value -> Maybe Integer
refDec Value
x) Bool -> Bool -> Bool
&& (String -> Maybe Integer -> Integer
forall a. String -> Maybe a -> a
fromJust' String
"refDec of ident/userdef" (Maybe Integer -> Integer) -> Maybe Integer -> Integer
forall a b. (a -> b) -> a -> b
$ Value -> Maybe Integer
refDec Value
x) Integer -> Map Integer Text -> Bool
forall k a. Ord k => k -> Map k a -> Bool
`Map.member` Map Integer Text
castr
p'' :: Value -> Bool
p'' Value
x =
(Text -> Value -> Bool
nodeIs Text
"Identifier" Value
x Bool -> Bool -> Bool
|| Text -> Value -> Bool
nodeIs Text
"UserDefinedTypeName" Value
x)
Bool -> Bool -> Bool
&& (Maybe Text -> Bool
forall a. Maybe a -> Bool
isJust (Maybe Text -> Bool) -> Maybe Text -> Bool
forall a b. (a -> b) -> a -> b
$ Value -> Maybe Text
name Value
x)
Bool -> Bool -> Bool
&& (
let
refs :: [Integer]
refs = ((Integer, (Integer, Text)) -> Integer)
-> [(Integer, (Integer, Text))] -> [Integer]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Integer, (Integer, Text)) -> Integer
forall a b. (a, b) -> a
fst [(Integer, (Integer, Text))]
cs
i :: Integer
i = String -> Maybe Integer -> Integer
forall a. String -> Maybe a -> a
fromJust' String
"no id for ident/userdef" (Maybe Integer -> Integer) -> Maybe Integer -> Integer
forall a b. (a -> b) -> a -> b
$ Value -> Maybe Integer
id' Value
x
ref :: Integer
ref = String -> Maybe Integer -> Integer
forall a. String -> Maybe a -> a
fromJust' (String
"no refDec for ident/userdef: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
i) (Maybe Integer -> Integer) -> Maybe Integer -> Integer
forall a b. (a -> b) -> a -> b
$ Value -> Maybe Integer
refDec Value
x
n :: Text
n = String -> Maybe Text -> Text
forall a. String -> Maybe a -> a
fromJust' (String
"no name for ident/userdef: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
i) (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ Value -> Maybe Text
name Value
x
cn :: (Integer, Text)
cn = String -> Maybe (Integer, Text) -> (Integer, Text)
forall a. String -> Maybe a -> a
fromJust'
(String
"no match for lookup in nested structs: "
String -> String -> String
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
i
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" -> "
String -> String -> String
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
ref
) (Maybe (Integer, Text) -> (Integer, Text))
-> Maybe (Integer, Text) -> (Integer, Text)
forall a b. (a -> b) -> a -> b
$ Integer -> [(Integer, (Integer, Text))] -> Maybe (Integer, Text)
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Integer
ref [(Integer, (Integer, Text))]
cs
in
Integer
ref Integer -> [Integer] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Integer]
refs Bool -> Bool -> Bool
&& Text
n Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== (Integer, Text) -> Text
forall a b. (a, b) -> b
snd (Integer, Text)
cn
)
p''' :: Value -> Bool
p''' Value
x = Value -> Bool
p Value
x Bool -> Bool -> Bool
|| Value -> Bool
p' Value
x Bool -> Bool -> Bool
|| Value -> Bool
p'' Value
x
prefixAstNodes :: (ByteString, Int)
prefixAstNodes :: (ByteString, Int)
prefixAstNodes =
[(Int, Integer)] -> (ByteString, Int)
cutRanges [Value -> (Int, Integer)
sourceId Value
node | Value
node <- Value -> [Value]
forall a. Plated a => a -> [a]
universe Value
ast, Value -> Bool
p''' Value
node]
sourceId :: Value -> (Int, Integer)
sourceId :: Value -> (Int, Integer)
sourceId Value
v =
if (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Value -> Bool
p Value
v Bool -> Bool -> Bool
|| Value -> Bool
p' Value
v) Bool -> Bool -> Bool
&& Value -> Bool
p'' Value
v then (
let
ref :: Integer
ref = String -> Maybe Integer -> Integer
forall a. String -> Maybe a -> a
fromJust' String
"refDec of nested struct ref" (Maybe Integer -> Integer) -> Maybe Integer -> Integer
forall a b. (a -> b) -> a -> b
$ Value -> Maybe Integer
refDec Value
v
cn :: (Integer, Text)
cn = String -> Maybe (Integer, Text) -> (Integer, Text)
forall a. String -> Maybe a -> a
fromJust' String
"no match for lookup in nested structs" (Maybe (Integer, Text) -> (Integer, Text))
-> Maybe (Integer, Text) -> (Integer, Text)
forall a b. (a -> b) -> a -> b
$ Integer -> [(Integer, (Integer, Text))] -> Maybe (Integer, Text)
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Integer
ref [(Integer, (Integer, Text))]
cs
in
(Int
end, (Integer, Text) -> Integer
forall a b. (a, b) -> a
fst (Integer, Text)
cn)
) else
String -> Maybe (Int, Integer) -> (Int, Integer)
forall a. String -> Maybe a -> a
fromJust' String
"internal error: no id found for contract reference" Maybe (Int, Integer)
x
where
(Int
start, Int
end) = Value -> (Int, Int)
sourceRange Value
v
f :: Text -> Maybe (Int, Integer)
f :: Text -> Maybe (Int, Integer)
f Text
t | Text
t Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"ContractDefinition", Text
"StructDefinition"] =
let
name' :: ByteString
name' = Text -> ByteString
encodeUtf8 (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> Text
forall a. String -> Maybe a -> a
fromJust' String
"no name for contract/struct" (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ Value -> Maybe Text
name Value
v
bs' :: ByteString
bs' = (ByteString, ByteString) -> ByteString
forall a b. (a, b) -> b
snd ((ByteString, ByteString) -> ByteString)
-> (ByteString, ByteString) -> ByteString
forall a b. (a -> b) -> a -> b
$ Int -> ByteString -> (ByteString, ByteString)
BS.splitAt (Int
start Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (ByteString, Int) -> Int
forall a b. (a, b) -> b
snd (ByteString, Int)
bso) ByteString
bs
pos :: Int
pos = Int
start
Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (ByteString -> Int
BS.length (ByteString -> Int) -> ByteString -> Int
forall a b. (a -> b) -> a -> b
$ (ByteString, ByteString) -> ByteString
forall a b. (a, b) -> a
fst ((ByteString, ByteString) -> ByteString)
-> (ByteString, ByteString) -> ByteString
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString -> (ByteString, ByteString)
BS.breakSubstring ByteString
name' ByteString
bs')
Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (ByteString -> Int
BS.length ByteString
name')
in
(Integer -> (Int, Integer))
-> Maybe Integer -> Maybe (Int, Integer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((,) Int
pos) (Maybe Integer -> Maybe (Int, Integer))
-> Maybe Integer -> Maybe (Int, Integer)
forall a b. (a -> b) -> a -> b
$ Value -> Maybe Integer
id' Value
v
| Text
t Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"UserDefinedTypeName", Text
"Identifier"] =
(Integer -> (Int, Integer))
-> Maybe Integer -> Maybe (Int, Integer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((,) Int
end) (Maybe Integer -> Maybe (Int, Integer))
-> Maybe Integer -> Maybe (Int, Integer)
forall a b. (a -> b) -> a -> b
$ Value -> Maybe Integer
refDec Value
v
| Bool
otherwise =
String -> Maybe (Int, Integer)
forall a. HasCallStack => String -> a
error (String -> Maybe (Int, Integer)) -> String -> Maybe (Int, Integer)
forall a b. (a -> b) -> a -> b
$ String
"internal error: not a contract reference: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
t
x :: Maybe (Int, Integer)
x :: Maybe (Int, Integer)
x = case Getting (First Text) Value Text -> Value -> Maybe Text
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview (Text -> Traversal' Value Value
forall t. AsValue t => Text -> Traversal' t Value
key Text
"nodeType" ((Value -> Const (First Text) Value)
-> Value -> Const (First Text) Value)
-> Getting (First Text) Value Text
-> Getting (First Text) Value Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting (First Text) Value Text
forall t. AsPrimitive t => Prism' t Text
_String) Value
v of
Just Text
t -> Text -> Maybe (Int, Integer)
f Text
t
Maybe Text
Nothing -> case Getting (First Text) Value Text -> Value -> Maybe Text
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview (Text -> Traversal' Value Value
forall t. AsValue t => Text -> Traversal' t Value
key Text
"name" ((Value -> Const (First Text) Value)
-> Value -> Const (First Text) Value)
-> Getting (First Text) Value Text
-> Getting (First Text) Value Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting (First Text) Value Text
forall t. AsPrimitive t => Prism' t Text
_String) Value
v of
Just Text
t -> Text -> Maybe (Int, Integer)
f Text
t
Maybe Text
Nothing ->
String -> Maybe (Int, Integer)
forall a. HasCallStack => String -> a
error String
"internal error: not a contract reference"
cutRanges :: [(Int, Integer)] -> (ByteString, Int)
cutRanges :: [(Int, Integer)] -> (ByteString, Int)
cutRanges ([(Int, Integer)] -> [(Int, Integer)]
forall a. Ord a => [a] -> [a]
sort -> [(Int, Integer)]
rs) = ((ByteString, Int) -> (Int, Integer) -> (ByteString, Int))
-> (ByteString, Int) -> [(Int, Integer)] -> (ByteString, Int)
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (ByteString, Int) -> (Int, Integer) -> (ByteString, Int)
f (ByteString, Int)
bso [(Int, Integer)]
rs
where
f :: (ByteString, Int) -> (Int, Integer) -> (ByteString, Int)
f (ByteString
bs', Int
n) (Int
i, Integer
t) =
let
t' :: Text
t' = Text
"_" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (Map Integer Text
castr Map Integer Text -> Integer -> Text
forall k a. Ord k => Map k a -> k -> a
! Integer
t)
in
( Text -> ByteString -> Int -> ByteString
prefix Text
t' ByteString
bs' (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n)
, Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Text -> Int
Text.length Text
t' )
prefix :: Text -> ByteString -> Int -> ByteString
prefix :: Text -> ByteString -> Int -> ByteString
prefix Text
t ByteString
x Int
i =
let (ByteString
a, ByteString
b) = Int -> ByteString -> (ByteString, ByteString)
BS.splitAt Int
i ByteString
x
in ByteString
a ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Text -> ByteString
encodeUtf8 Text
t ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
b
sourceRange :: Value -> (Int, Int)
sourceRange :: Value -> (Int, Int)
sourceRange Value
v =
case Getting (First Text) Value Text -> Value -> Maybe Text
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview (Text -> Traversal' Value Value
forall t. AsValue t => Text -> Traversal' t Value
key Text
"src" ((Value -> Const (First Text) Value)
-> Value -> Const (First Text) Value)
-> Getting (First Text) Value Text
-> Getting (First Text) Value Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting (First Text) Value Text
forall t. AsPrimitive t => Prism' t Text
_String) Value
v of
Just (Text -> Text -> [Text]
Text.splitOn Text
":" -> [Text -> Maybe Int
forall a. Read a => Text -> Maybe a
readAs -> Just Int
i, Text -> Maybe Int
forall a. Read a => Text -> Maybe a
readAs -> Just Int
n, Text
_]) ->
(Int
i, Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n)
Maybe Text
_ ->
String -> (Int, Int)
forall a. HasCallStack => String -> a
error String
"internal error: no source position for AST node"
fromJust' :: String -> Maybe a -> a
fromJust' :: String -> Maybe a -> a
fromJust' String
msg = \case
Just a
x -> a
x
Maybe a
Nothing -> String -> a
forall a. HasCallStack => String -> a
error String
msg
repeated :: Eq a => [a] -> [a]
repeated :: [a] -> [a]
repeated = (([a], [a]) -> [a]) -> ([a] -> ([a], [a])) -> [a] -> [a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([a], [a]) -> [a]
forall a b. (a, b) -> a
fst (([a] -> ([a], [a])) -> [a] -> [a])
-> ([a] -> ([a], [a])) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ (([a], [a]) -> a -> ([a], [a])) -> ([a], [a]) -> [a] -> ([a], [a])
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' ([a], [a]) -> a -> ([a], [a])
forall a. Eq a => ([a], [a]) -> a -> ([a], [a])
f ([], [])
where
f :: ([a], [a]) -> a -> ([a], [a])
f ([a]
acc, [a]
seen) a
x =
( if (a
x a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [a]
seen) Bool -> Bool -> Bool
&& (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ a
x a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [a]
acc)
then a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
acc
else [a]
acc
, a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
seen
)
indexed :: [(Integer, Text)] -> [(Integer, Text)]
indexed :: [(Integer, Text)] -> [(Integer, Text)]
indexed = ([(Integer, Text)], Map Text Integer) -> [(Integer, Text)]
forall a b. (a, b) -> a
fst (([(Integer, Text)], Map Text Integer) -> [(Integer, Text)])
-> ([(Integer, Text)] -> ([(Integer, Text)], Map Text Integer))
-> [(Integer, Text)]
-> [(Integer, Text)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (([(Integer, Text)], Map Text Integer)
-> (Integer, Text) -> ([(Integer, Text)], Map Text Integer))
-> ([(Integer, Text)], Map Text Integer)
-> [(Integer, Text)]
-> ([(Integer, Text)], Map Text Integer)
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' ([(Integer, Text)], Map Text Integer)
-> (Integer, Text) -> ([(Integer, Text)], Map Text Integer)
forall a k a.
(Num a, Ord k, Show a) =>
([(a, Text)], Map k a) -> (a, k) -> ([(a, Text)], Map k a)
f ([], Map Text Integer
forall k a. Map k a
Map.empty)
where
f :: ([(a, Text)], Map k a) -> (a, k) -> ([(a, Text)], Map k a)
f ([(a, Text)]
acc, Map k a
seen) (a
id', k
n) =
let
count :: a
count = (a -> Maybe a -> a
forall a. a -> Maybe a -> a
fromMaybe a
0 (Maybe a -> a) -> Maybe a -> a
forall a b. (a -> b) -> a -> b
$ Map k a
seen Map k a -> k -> Maybe a
forall k a. Ord k => Map k a -> k -> Maybe a
!? k
n) a -> a -> a
forall a. Num a => a -> a -> a
+ a
1
in
((a
id', String -> Text
pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ a -> String
forall a. Show a => a -> String
show a
count) (a, Text) -> [(a, Text)] -> [(a, Text)]
forall a. a -> [a] -> [a]
: [(a, Text)]
acc, k -> a -> Map k a -> Map k a
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert k
n a
count Map k a
seen)