-- Simple module providing some types used by Translator. These are in a
-- separate module to prevent circular dependencies in Pretty for example.
--
-{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE TemplateHaskell, NoGenerics #-}
module CLasH.Translator.TranslatorTypes where
import qualified Control.Monad.Trans.State as State
deriving instance (Show n, OutputableBndr n) => Show (HsTypes.ConDeclField n)
deriving instance (Show x) => Show (SrcLoc.Located x)
deriving instance (Show x, OutputableBndr x) => Show (HsExpr.StmtLR x x)
-deriving instance (Show x, OutpubableBndr x) => Show (HsExpr.HsTupArg x)
+deriving instance (Show x, OutputableBndr x) => Show (HsExpr.HsTupArg x)
deriving instance (Show x, OutputableBndr x) => Show (HsExpr.HsExpr x)
deriving instance Show (RdrName.RdrName)
deriving instance (Show idL, Show idR, OutputableBndr idL, OutputableBndr idR) => Show (HsBinds.HsBindLR idL idR)