{-# OPTIONS_GHC -fno-warn-orphans #-}
module Agda.Benchmarking where
import qualified Control.Exception as E
import Data.IORef
import System.IO.Unsafe
import Agda.Syntax.Concrete.Name (TopLevelModuleName)
import Agda.Syntax.Concrete.Pretty () 
import Agda.Syntax.Abstract.Name
import Agda.Utils.Benchmark (MonadBench(..))
import qualified Agda.Utils.Benchmark as B
import Agda.Utils.Null
import Agda.Utils.Pretty
data Phase
  = Parsing
    
  | Import
    
  | Deserialization
    
  | Scoping
    
  | Typing
    
  | Termination
    
  | Positivity
    
  | Injectivity
    
  | ProjectionLikeness
    
  | Coverage
    
  | Highlighting
    
  | Serialization
    
  | DeadCode
    
  | Graph
    
  | RecCheck
    
  | Reduce
    
  | Level
    
  | Compare
    
  | With
    
  | ModuleName
    
  | Compaction
    
  | BuildInterface
    
  | Sort
    
  | BinaryEncode
    
  | Compress
    
  | OperatorsExpr
    
  | OperatorsPattern
    
  | Free
    
  | OccursCheck
    
  | CheckLHS
    
  | CheckRHS
    
  | TypeSig
    
  | Generalize
    
  | InstanceSearch
    
  | UnifyIndices
    
  | InverseScopeLookup
    
  | TopModule TopLevelModuleName
  | Definition QName
  deriving (Eq, Ord, Show)
instance Pretty Phase where
  pretty (TopModule m)  = pretty m
  pretty (Definition q) = pretty q
  pretty a = text (show a)
type Benchmark = B.Benchmark Phase
type Account   = B.Account Phase
isModuleAccount :: Account -> Bool
isModuleAccount []                = True
isModuleAccount (TopModule{} : _) = True
isModuleAccount _                 = False
isDefAccount :: Account -> Bool
isDefAccount []                 = True
isDefAccount (Definition{} : _) = True
isDefAccount _                  = False
isInternalAccount :: Account -> Bool
isInternalAccount (TopModule{}  : _) = False
isInternalAccount (Definition{} : _) = False
isInternalAccount _                  = True
{-# NOINLINE benchmarks #-}
benchmarks :: IORef Benchmark
benchmarks = unsafePerformIO $ newIORef empty
instance MonadBench Phase IO where
  getBenchmark = readIORef benchmarks
  putBenchmark = writeIORef benchmarks
  finally = E.finally
billToIO :: Account -> IO a -> IO a
billToIO = B.billTo
billToPure :: Account -> a -> a
billToPure acc a = unsafePerformIO $ billToIO acc $ return a