-- | The data type definition for "Futhark.Analysis.Metrics", factored
-- out to simplify the module import hierarchies when working on the
-- test modules.
module Futhark.Analysis.Metrics.Type (AstMetrics (..)) where

import qualified Data.Map.Strict as M
import Data.Text (Text)
import qualified Data.Text as T

-- | AST metrics are simply a collection from identifiable node names
-- to the number of times that node appears.
newtype AstMetrics = AstMetrics (M.Map Text Int)

instance Show AstMetrics where
  show :: AstMetrics -> String
show (AstMetrics Map Text Int
m) = [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ ((Text, Int) -> String) -> [(Text, Int)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (Text, Int) -> String
forall a. Show a => (Text, a) -> String
metric ([(Text, Int)] -> [String]) -> [(Text, Int)] -> [String]
forall a b. (a -> b) -> a -> b
$ Map Text Int -> [(Text, Int)]
forall k a. Map k a -> [(k, a)]
M.toList Map Text Int
m
    where
      metric :: (Text, a) -> String
metric (Text
k, a
v) = Text -> String
T.unpack Text
k String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
v

instance Read AstMetrics where
  readsPrec :: Int -> ReadS AstMetrics
readsPrec Int
_ String
s =
    [(AstMetrics, String)]
-> ([(Text, Int)] -> [(AstMetrics, String)])
-> Maybe [(Text, Int)]
-> [(AstMetrics, String)]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] [(Text, Int)] -> [(AstMetrics, String)]
success (Maybe [(Text, Int)] -> [(AstMetrics, String)])
-> Maybe [(Text, Int)] -> [(AstMetrics, String)]
forall a b. (a -> b) -> a -> b
$ (String -> Maybe (Text, Int)) -> [String] -> Maybe [(Text, Int)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM String -> Maybe (Text, Int)
forall b. Read b => String -> Maybe (Text, b)
onLine ([String] -> Maybe [(Text, Int)])
-> [String] -> Maybe [(Text, Int)]
forall a b. (a -> b) -> a -> b
$ String -> [String]
lines String
s
    where
      onLine :: String -> Maybe (Text, b)
onLine String
l = case String -> [String]
words String
l of
        [String
k, String
x] | [(b
n, String
"")] <- ReadS b
forall a. Read a => ReadS a
reads String
x -> (Text, b) -> Maybe (Text, b)
forall a. a -> Maybe a
Just (String -> Text
T.pack String
k, b
n)
        [String]
_ -> Maybe (Text, b)
forall a. Maybe a
Nothing
      success :: [(Text, Int)] -> [(AstMetrics, String)]
success [(Text, Int)]
m = [(Map Text Int -> AstMetrics
AstMetrics (Map Text Int -> AstMetrics) -> Map Text Int -> AstMetrics
forall a b. (a -> b) -> a -> b
$ [(Text, Int)] -> Map Text Int
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [(Text, Int)]
m, String
"")]