{-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -O -fplugin Test.Inspection.Plugin #-} module Main (main) where import Test.Inspection import Data.Tagged (Tagged (..), retag) import qualified Data.Type.Nat as N ------------------------------------------------------------------------------- -- InlineInduction ------------------------------------------------------------------------------- -- | This doesn't evaluate compile time. lhsInline :: Int lhsInline = unTagged (N.inlineInduction1 (pure 0) (retag . fmap succ) :: Tagged N.Five Int) -- | This doesn't evaluate compile time. lhsNormal :: Int lhsNormal = unTagged (N.induction1 (pure 0) (retag . fmap succ) :: Tagged N.Five Int) rhs :: Int rhs = 5 inspect $ 'lhsInline === 'rhs inspect $ 'lhsNormal =/= 'rhs ------------------------------------------------------------------------------- -- Main to make GHC happy ------------------------------------------------------------------------------- main :: IO () main = return ()