diff --git a/src/comp/Backend.hs b/src/comp/Backend.hs index dd231f95..0b23f095 100644 --- a/src/comp/Backend.hs +++ b/src/comp/Backend.hs @@ -4,14 +4,16 @@ module Backend ( backendMatches ) where -import qualified Data.Generics as Generic +import Data.Data +import Data.Typeable + import PPrint import Eval -- =============== data Backend = Bluesim | Verilog - deriving (Eq, Ord, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Ord, Show, Data, Typeable) instance PPrint Backend where pPrint _ _ Bluesim = text "Bluesim" @@ -29,4 +31,3 @@ backendMatches Nothing _ = True backendMatches (Just expected) (Just actual) = (expected == actual) -- =============== - diff --git a/src/comp/CType.hs b/src/comp/CType.hs index 21609e35..dd89f638 100644 --- a/src/comp/CType.hs +++ b/src/comp/CType.hs @@ -55,10 +55,10 @@ module CType( import Prelude hiding ((<>)) #endif +import Data.Data (Data, Typeable) import Data.Char(isDigit, chr) import Data.List(union) import Data.Maybe -import qualified Data.Generics as Generic import Eval import PPrint @@ -83,14 +83,14 @@ data Type = TVar TyVar -- ^ type variable | TAp Type Type -- ^ type-level application | TGen Position Int -- ^ quantified type variable used in type schemes | TDefMonad Position -- ^ not used after CVParserImperative - deriving (Show, Generic.Data, Generic.Typeable) + deriving (Show, Data, Typeable) -- | Representation of a type variable data TyVar = TyVar { tv_name :: Id -- ^ name of the type variable , tv_num :: Int -- ^ number for a generated type variable , tv_kind :: Kind -- ^ kind of the type variable } - deriving (Show, Generic.Data, Generic.Typeable) + deriving (Show, Data, Typeable) -- | Representation of a type constructor @@ -107,7 +107,7 @@ data TyCon = -- | A constructor for a type of value kind | TyStr { tystr_value :: FString -- ^ type-level string value , tystr_pos :: Position -- ^ position of introduction } - deriving (Show, Generic.Data, Generic.Typeable) + deriving (Show, Data, Typeable) data TISort = -- type synonym @@ -119,7 +119,7 @@ data TISort -- primitive abstract type -- e.g. Integer, Bit, Module, etc. | TIabstract - deriving (Eq, Ord, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Ord, Show, Data, Typeable) data StructSubType @@ -133,7 +133,7 @@ data StructSubType , spolywrap_ctor :: Maybe Id -- ^ name of the data constructor , spolywrap_field :: Id -- ^ name of the wrapped field } - deriving (Eq, Ord, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Ord, Show, Data, Typeable) type CType = Type @@ -143,7 +143,7 @@ data Kind = KStar -- ^ kind of a simple value type | KStr -- ^ kind of a simple string type | Kfun Kind Kind -- ^ kind of type constructors (type-level function) | KVar Int -- ^ generated kind variable (used only during kind inference) - deriving (Eq, Ord, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Ord, Show, Data, Typeable) -- Used for providing partial Kind information data PartialKind diff --git a/src/comp/ConTagInfo.hs b/src/comp/ConTagInfo.hs index f97a9002..17af0841 100644 --- a/src/comp/ConTagInfo.hs +++ b/src/comp/ConTagInfo.hs @@ -1,9 +1,10 @@ {-# LANGUAGE DeriveDataTypeable #-} module ConTagInfo(ConTagInfo(..)) where +import Data.Data + import Eval import PPrint -import Data.Generics -- Collects constructor and tag metadata for use in the symbol table and ISyntax. -- e.g., data T = A T1 | B T2 diff --git a/src/comp/FStringCompat.hs b/src/comp/FStringCompat.hs index 6d6e6a57..ab484f6c 100644 --- a/src/comp/FStringCompat.hs +++ b/src/comp/FStringCompat.hs @@ -8,13 +8,13 @@ module FStringCompat(FString, getFString, -- wrapper to make SStrings look like FStrings import Prelude hiding((++)) +import Data.Data + import qualified SpeedyString as S import PPrint(PPrint(..), text) import Util(itos) -import qualified Data.Generics as Generic - -newtype FString = FString S.SString deriving (Eq,Ord,Generic.Data, Generic.Typeable) +newtype FString = FString S.SString deriving (Eq, Ord, Data, Typeable) fromString :: String -> FString fromString = FString . S.fromString diff --git a/src/comp/IExpand.hs b/src/comp/IExpand.hs index 4943376d..aaf95e7a 100644 --- a/src/comp/IExpand.hs +++ b/src/comp/IExpand.hs @@ -17,25 +17,25 @@ module IExpand(iExpand) where import Prelude hiding ((<>)) #endif +import qualified Data.Array as Array +import qualified Data.IntMap as IM +import qualified Data.Map as M +import qualified Data.Set as S +import Data.Char(intToDigit, ord, chr) import Data.List import Data.Maybe import Data.Foldable(foldrM) +import Debug.Trace(traceM) import Numeric(showIntAtBase) -import Data.Char(intToDigit, ord, chr) import Control.Monad(when, foldM, zipWithM, mapAndUnzipM) import Control.Monad.Fix(mfix) ---import Control.Monad.Fix -import Control.Monad.State(State, evalState, liftIO, get, put) -import Data.Graph -import qualified Data.Generics as Generic import System.IO(Handle, BufferMode(..), IOMode(..), stdout, stderr, hSetBuffering, hIsOpen, hIsClosed) import System.FilePath(isRelative) -import qualified Data.Array as Array -import qualified Data.IntMap as IM -import qualified Data.Map as M -import qualified Data.Set as S -import Debug.Trace(traceM) + +import qualified Data.Generics as Generic +import Data.Graph +import Control.Monad.State(State, evalState, liftIO, get, put) import FileIOUtil(openFileCatch, hCloseCatch, hFlushCatch, hGetBufferingCatch, hSetBufferingCatch, hPutStrCatch, hGetLineCatch, diff --git a/src/comp/IExpandUtils.hs b/src/comp/IExpandUtils.hs index 443a40b8..127743a8 100644 --- a/src/comp/IExpandUtils.hs +++ b/src/comp/IExpandUtils.hs @@ -65,6 +65,7 @@ module IExpandUtils( import Control.Monad(when, liftM) import Control.Monad.State(StateT, runStateT, evalStateT, lift, liftIO, gets, get, put, modify) +import Data.Data import Data.IORef import System.IO.Unsafe import Data.List @@ -254,7 +255,7 @@ pTermToIExpr (PSel idx idx_sz es) = -- An expression with an implicit condition. data PExpr = P HPred HExpr - deriving (Eq, Ord, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Ord, Show, Data, Typeable) instance PPrint PExpr where pPrint d prec (P p e) = pPrint d prec (iePrimWhen (iGetType e) (predToIExpr p) e) @@ -385,7 +386,7 @@ data HeapCell = HUnev { hc_hexpr :: HExpr, hc_name :: NameInfo } | HNF { hc_pexpr :: PExpr, hc_wire_set :: HWireSet, hc_name :: NameInfo } | HLoop { hc_name :: NameInfo } - deriving (Show, Eq, Ord, Generic.Data, Generic.Typeable) + deriving (Show, Eq, Ord, Data, Typeable) -- should I drop the predicate for better printing of error messages? heapCellToHExpr :: HeapCell -> HExpr @@ -414,7 +415,7 @@ instance PPrint HeapCell where text "HLoop" <+> pPrint d 0 name newtype HeapData = HeapData (IORef (HeapCell)) - deriving (Generic.Data, Generic.Typeable) + deriving (Data, Typeable) {- instance Eq HeapData where diff --git a/src/comp/IStateLoc.hs b/src/comp/IStateLoc.hs index 94d8563a..28a2da78 100644 --- a/src/comp/IStateLoc.hs +++ b/src/comp/IStateLoc.hs @@ -18,20 +18,21 @@ module IStateLoc ( ,newIStateLocTop ) where +import Data.Char(isAlphaNum) +import Data.Data +import Data.List(isPrefixOf,tails) + +import qualified Data.Map as M + import IType import Id -import qualified Data.Generics as Generic import Eval(Hyper(..)) -import Data.Char(isAlphaNum) - import Position import PreStrings(fsUnderscore,fsElements, fsvElements) import FStringCompat import PPrint import PFPrint(pfpString) import PreStrings(fs_unnamed, fsAddRules, fsLoop, fsBody, fsC) -import qualified Data.Map as M -import Data.List(isPrefixOf,tails) import Error(internalError) import IOUtil(progArgs) import Util(traces) @@ -71,7 +72,7 @@ data IStateLocPathComponent = IStateLocPathComponent { -- Name generation isl_prefix :: NameGenerate, -- currently computed hierarchical prefix isl_loop_suffix :: NameGenerate -- loop indexes to add once a "real" name is found. - } deriving (Eq, Show, Generic.Data, Generic.Typeable) + } deriving (Eq, Show, Data, Typeable) -- --------------------------------------- @@ -124,7 +125,7 @@ mkISLPC inst_id ifc_id ifc_type = islpc data NameGenerate = NameEmpty -- No name so far | NameIndex [Integer] -- loop indexes | Name Id -- a real name - deriving (Eq, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Show, Data, Typeable) -- instance Hyper NameGenerate where diff --git a/src/comp/ISyntax.hs b/src/comp/ISyntax.hs index c8af1ea6..893ad7ec 100644 --- a/src/comp/ISyntax.hs +++ b/src/comp/ISyntax.hs @@ -82,9 +82,10 @@ module ISyntax( import Prelude hiding ((<>)) #endif -import System.IO(Handle) -import qualified Data.Map as M +import Data.Data import Data.List(intercalate) +import qualified Data.Map as M +import System.IO(Handle) import qualified Data.Array as Array import IntLit @@ -112,7 +113,6 @@ import Error(internalError, EMsg, ErrMsg(..)) import PFPrint import IStateLoc(IStateLoc) import IType -import qualified Data.Generics as Generic -- ============================================================ -- IPackage, IModule @@ -134,7 +134,7 @@ data IPackage a -- definition list ipkg_defs :: [IDef a] } - deriving (Eq, Ord, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Ord, Show, Data, Typeable) -- An elaborated module -- * These are created during iExpand for each module to be synthesized @@ -162,7 +162,7 @@ data IModule a -- comments on submodule instantiations imod_instance_comments :: [(Id, [String])] } - deriving (Show, Generic.Data, Generic.Typeable) + deriving (Show, Data, Typeable) getWireInfo :: IModule a -> VWireInfo getWireInfo = imod_external_wires @@ -173,7 +173,7 @@ getWireInfo = imod_external_wires type PortTypeMap = M.Map (Maybe Id) (M.Map VName IType) data IDef a = IDef Id IType (IExpr a) [DefProp] - deriving (Eq, Ord, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Ord, Show, Data, Typeable) data IAbstractInput = -- simple input using one port @@ -184,7 +184,7 @@ data IAbstractInput = IAI_Inout Id Integer -- room to add other types here, like: -- IAI_Struct [(Id, IType)] - deriving (Eq, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Show, Data, Typeable) data IEFace a = IEFace { -- This is either an actual method or a ready signal for another @@ -204,7 +204,7 @@ data IEFace a = IEFace { ief_wireprops :: WireProps, ief_fieldinfo :: VFieldInfo } - deriving (Show, Generic.Data, Generic.Typeable) + deriving (Show, Data, Typeable) -- --------------- @@ -225,7 +225,7 @@ data IStateVar a = IStateVar { isv_resets :: [(Id, IReset a)], -- named resets isv_isloc :: IStateLoc -- instantiation path } - deriving (Show, Generic.Data, Generic.Typeable) + deriving (Show, Data, Typeable) getResetMap :: IStateVar a -> [(Id, IReset a)] getResetMap = isv_resets @@ -266,7 +266,7 @@ data IRule a = -- Instantiation hierarchy irule_state_loc :: IStateLoc } - deriving (Show, Generic.Data, Generic.Typeable) + deriving (Show, Data, Typeable) instance Hyper (IRule a) where hyper (IRule i ps s wp r1 r2 orig isl) y = hyper8 i ps s wp r1 r2 orig isl y @@ -278,7 +278,7 @@ getIRuleStateLoc :: IRule a -> IStateLoc getIRuleStateLoc = irule_state_loc data IRules a = IRules [ISchedulePragma] [IRule a] - deriving (Show, Generic.Data, Generic.Typeable) + deriving (Show, Data, Typeable) instance Hyper (IRules a) where hyper (IRules sps rs) y = hyper2 sps rs y @@ -479,7 +479,7 @@ data IExpr a | ICon Id (IConInfo a) -- IRef is only used during reduction, it refers to a "heap" cell | IRefT IType !Int a -- vanishes after IExpand - deriving (Generic.Data, Generic.Typeable) + deriving (Data, Typeable) instance Show (IExpr a) where show (ILam i t e) = "(ILam " ++ show i ++ " " ++ show t ++ " " ++ show e ++ ")" @@ -569,7 +569,7 @@ data IClock a = IClock { ic_id :: ClockId, -- unique id ic_wires :: IExpr a -- expression for clock wires -- will be ICSel of (ICStateVar) or ICTuple of ICModPorts / ICInt (1) for ungated clocks -- theoretically ICTuple (ICInt (0), ICInt (0)) for noClock, but should not appear - } deriving (Generic.Data, Generic.Typeable) + } deriving (Data, Typeable) -- break recursion of wires so that showing a clock does not loop instance Show (IClock a) where @@ -629,7 +629,7 @@ data IReset a = IReset { ir_id :: ResetId, -- unique id ir_wire :: IExpr a -- expression for reset wire -- currently must be an ICModPort or 0, -- since we do not support reset output - } deriving (Generic.Data, Generic.Typeable) + } deriving (Data, Typeable) -- must break recursion of wire so showing a reset output does not loop instance Show (IReset a) where @@ -675,7 +675,7 @@ data IInout a = IInout { io_clock :: IClock a, -- associated clock (may be noClock) io_reset :: IReset a, -- associated reset (may be noReset) io_wire :: IExpr a -- expression for inout wire - } deriving (Generic.Data, Generic.Typeable) + } deriving (Data, Typeable) instance Show (IInout a) where show (IInout clock reset wire) = @@ -711,7 +711,7 @@ getInoutWire = io_wire -- into application of PrimBuildArray to the element expressions. -- data ArrayCell a = ArrayCell { ac_ptr :: Int, ac_ref :: a } - deriving (Generic.Data, Generic.Typeable) + deriving (Data, Typeable) instance Show (ArrayCell a) where show (ArrayCell i _) = "_" ++ show i @@ -734,7 +734,7 @@ instance Hyper (ILazyArray a) where -- Predicates used for implicit conditions. -- most utility functions in IExpandUtils newtype Pred a = PConj (PSet (PTerm a)) - deriving (Eq, Ord, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Ord, Show, Data, Typeable) instance PPrint (Pred a) where pPrint d p (PConj ps) = pPrint d p (S.toList ps) @@ -754,11 +754,18 @@ type PSet a = S.Set a data PTerm a = PAtom (IExpr a) | PIf (IExpr a) (Pred a) (Pred a) | PSel (IExpr a) Integer [Pred a] - deriving (Eq, Ord, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Ord, Show, Data, Typeable) -- ============================== -- IConInfo +-- FIXME: syb includes an orphan to work around the fact Handle needs a Data +-- instance, so we might as well just keep it ourselves. +instance Data Handle where + toConstr _ = error "toConstr" + gunfold _ _ = error "gunfold" + dataTypeOf _ = mkNoRepType "GHC.IOBase.Handle" + data IConInfo a = -- top level definition -- iconDef has the definition body @@ -854,11 +861,9 @@ data IConInfo a = | ICPosition { iConType :: IType, iPosition :: [Position] } | ICType { iConType :: IType, iType :: IType } | ICPred { iConType :: IType, iPred :: Pred a } - deriving (Show, Generic.Data, Generic.Typeable) + deriving (Show, Data, Typeable) ordC :: IConInfo a -> Int --- XXX This definition would be nice, but it imposes a (Data a) context ---ordC x = Generic.constrIndex (Generic.toConstr x) ordC (ICDef { }) = 0 ordC (ICPrim { }) = 1 ordC (ICForeign { }) = 2 diff --git a/src/comp/IType.hs b/src/comp/IType.hs index 78f15f64..d94a28dc 100644 --- a/src/comp/IType.hs +++ b/src/comp/IType.hs @@ -13,6 +13,7 @@ module IType( #if defined(__GLASGOW_HASKELL__) && (__GLASGOW_HASKELL__ >= 804) import Prelude hiding ((<>)) #endif +import Data.Data import ErrorUtil(internalError) import Id(Id) @@ -26,7 +27,6 @@ import PFPrint import Position(noPosition) import Util(itos) import FStringCompat(FString) -import qualified Data.Generics as Generic -- ============================== -- IKind, IType @@ -36,7 +36,7 @@ data IKind | IKNum | IKStr | IKFun IKind IKind - deriving (Eq, Ord, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Ord, Show, Data, Typeable) data IType = ITForAll Id IKind IType @@ -45,7 +45,7 @@ data IType | ITCon Id IKind TISort | ITNum Integer | ITStr FString - deriving (Show, Generic.Data, Generic.Typeable) + deriving (Show, Data, Typeable) -- -------------------------------- -- Hyper Instances diff --git a/src/comp/Id.hs b/src/comp/Id.hs index f7dec512..8c3ec96e 100644 --- a/src/comp/Id.hs +++ b/src/comp/Id.hs @@ -106,9 +106,9 @@ module Id( ) where import Data.Char(isDigit, digitToInt) +import Data.Data (Data, Typeable) import Data.List import Data.Maybe -import qualified Data.Generics as Generic import qualified Data.Map as Map import Util(headOrErr, lastOrErr, ToString(..)) @@ -161,7 +161,7 @@ data IdProp = IdPCanFire -- used by the BSV parser to keep track of which array types -- were introduced from bracket syntax | IdPParserGenerated - deriving (Eq, Ord, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Ord, Show, Data, Typeable) -- ############################################################################# -- # @@ -172,7 +172,7 @@ data Id = Id { id_pos :: !Position, id_fs :: !FString, id_props :: [IdProp] {- , id_stab :: Int -} } - deriving (Generic.Data,Generic.Typeable) + deriving (Data,Typeable) show_raw_id :: Bool show_raw_id = "-show-raw-id" `elem` progArgs diff --git a/src/comp/IntLit.hs b/src/comp/IntLit.hs index 4b02e937..ee1c1ada 100644 --- a/src/comp/IntLit.hs +++ b/src/comp/IntLit.hs @@ -4,17 +4,18 @@ module IntLit (IntLit(..), showVeriIntLit, showSizedVeriIntLit ) where +import Data.Data + import IntegerUtil(integerFormatPref, integerToString) import PPrint import PVPrint import Eval import ErrorUtil(internalError) -import qualified Data.Generics as Generic data IntLit = IntLit { ilWidth :: Maybe Integer, ilBase :: Integer, ilValue :: Integer } - deriving (Generic.Data, Generic.Typeable) + deriving (Data, Typeable) diff --git a/src/comp/Position.hs b/src/comp/Position.hs index d13f2de0..f9a9bee0 100644 --- a/src/comp/Position.hs +++ b/src/comp/Position.hs @@ -1,8 +1,8 @@ {-# LANGUAGE TypeSynonymInstances, FlexibleInstances, DeriveDataTypeable #-} module Position where +import Data.Data import Data.List(partition) -import qualified Data.Generics as Generic import Eval import PPrint @@ -16,7 +16,7 @@ data Position = Position { pos_line :: !Int, pos_column :: !Int, pos_is_stdlib :: !Bool -} deriving (Generic.Data, Generic.Typeable) +} deriving (Data, Typeable) mkPosition :: FString -> Int -> Int -> Position mkPosition f l c = Position f l c False diff --git a/src/comp/Pragma.hs b/src/comp/Pragma.hs index 9042ba46..759e4d01 100644 --- a/src/comp/Pragma.hs +++ b/src/comp/Pragma.hs @@ -54,10 +54,10 @@ module Pragma( import Prelude hiding ((<>)) #endif +import Data.Data +import Data.List(sort) import qualified Data.Map as M import Data.Maybe(listToMaybe) -import Data.List(sort) -import qualified Data.Generics as Generic import Eval import PPrint @@ -78,7 +78,7 @@ import IdPrint data Pragma = Pproperties Id [PProp]-- module Id and properties associate with | Pnoinline [Id] -- [Id] is a list of functions which should not be inlined - deriving (Eq, Ord, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Ord, Show, Data, Typeable) instance PPrint Pragma where @@ -144,7 +144,7 @@ data PProp | PPinst_hide | PPinst_hide_all | PPdeprecate String - deriving (Show, Eq, Ord, Generic.Data, Generic.Typeable) + deriving (Show, Eq, Ord, Data, Typeable) data PPnm = PPnmOne Id @@ -381,7 +381,7 @@ data RulePragma | RPclockCrossingRule | RPdoc String -- comment to carry through to Verilog | RPhide - deriving (Show, Eq, Ord, Generic.Data, Generic.Typeable) + deriving (Show, Eq, Ord, Data, Typeable) -- used for classic printing of CSyntax -- and by various internal dumps of ISyntax/ASyntax @@ -438,7 +438,7 @@ data SchedulePragma id_t | SPConflictFree [[id_t]] | SPPreempt [id_t] [id_t] | SPSchedule (MethodConflictInfo id_t) - deriving (Show, Eq, Ord, Generic.Data, Generic.Typeable) + deriving (Show, Eq, Ord, Data, Typeable) type CSchedulePragma = SchedulePragma Longname type ISchedulePragma = SchedulePragma Id @@ -709,7 +709,7 @@ data IfcPragma | PIEnSignalName String -- name for the enable signal | PIAlwaysRdy -- ifc or methods tagged as always ready | PIAlwaysEnabled -- ifc or methods tagged as always enabled - deriving (Show, Ord, Eq, Generic.Data, Generic.Typeable) + deriving (Show, Ord, Eq, Data, Typeable) -- type PragmaPair = (Id,String) @@ -893,7 +893,7 @@ data DefProp | DefP_Method Id -- for method predicates | DefP_Instance Id -- for method predicates | DefP_NoCSE -- indicate this def should never be used for CSE - deriving (Eq, Ord, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Ord, Show, Data, Typeable) instance PPrint DefProp where pPrint _d _i = text . show diff --git a/src/comp/Prim.hs b/src/comp/Prim.hs index c1b48345..f4a3f1ee 100644 --- a/src/comp/Prim.hs +++ b/src/comp/Prim.hs @@ -8,7 +8,9 @@ module Prim( PrimResult(..), PrimArg(..) ) where +import Data.Data import Numeric(floatToDigits) + import Eval import PPrint import Id @@ -19,7 +21,6 @@ import RealUtil hiding (log2, log10) import qualified RealUtil as R (log2,log10) import ErrorUtil(internalError) import Error(ErrMsg(..)) -import qualified Data.Generics as Generic data PrimOp = PrimAdd @@ -316,7 +317,7 @@ data PrimOp = | PrimGetParamName -- get the parameter name associated with the function value | PrimEQ3 -- === / Verilog case equality - deriving (Eq, Ord, Show, Enum, Bounded, Generic.Data, Generic.Typeable) + deriving (Eq, Ord, Show, Enum, Bounded, Data, Typeable) -- Just some size, have to be coordinated with Prelude.bs stringSize :: String -> Integer diff --git a/src/comp/SchedInfo.hs b/src/comp/SchedInfo.hs index b2708039..d5917df3 100644 --- a/src/comp/SchedInfo.hs +++ b/src/comp/SchedInfo.hs @@ -19,13 +19,14 @@ module SchedInfo ( #if defined(__GLASGOW_HASKELL__) && (__GLASGOW_HASKELL__ >= 804) import Prelude hiding ((<>)) #endif - +import Data.Data import Data.List(foldl',sortBy) -import PFPrint -import Eval + import qualified Data.Map as M import qualified Data.Set as S -import qualified Data.Generics as Generic + +import PFPrint +import Eval -- ======================================================================== -- SchedInfo @@ -45,7 +46,7 @@ data SchedInfo idtype = SchedInfo { -- methods which allow an unsynchronized clock domain crossing clockCrossingMethods :: [idtype] } - deriving (Show, Ord, Eq, Generic.Data, Generic.Typeable) + deriving (Show, Ord, Eq, Data, Typeable) instance (PPrint idtype, Ord idtype) => PPrint (SchedInfo idtype) where pPrint d p si = @@ -123,7 +124,7 @@ data MethodConflictInfo idtype = sC :: [(idtype, idtype)], sEXT :: [idtype] } - deriving (Show, Ord, Eq, Generic.Data, Generic.Typeable) + deriving (Show, Ord, Eq, Data, Typeable) -- -------------------- diff --git a/src/comp/SpeedyString.hs b/src/comp/SpeedyString.hs index a5ef635e..895fc675 100644 --- a/src/comp/SpeedyString.hs +++ b/src/comp/SpeedyString.hs @@ -3,16 +3,16 @@ module SpeedyString(SString, toString, fromString, (++), concat, filter) where import Prelude hiding((++), concat, filter) import qualified Prelude((++), filter) -import IOMutVar(MutableVar, newVar, readVar, writeVar) +import Data.Data import System.IO.Unsafe(unsafePerformIO) + import qualified Data.IntMap as M --- import qualified NotSoSpeedyString -import ErrorUtil (internalError) -import qualified Data.Generics as Generic +import IOMutVar(MutableVar, newVar, readVar, writeVar) +import ErrorUtil (internalError) data SString = SString !Int -- unique id - deriving (Generic.Data, Generic.Typeable) + deriving (Data, Typeable) instance Eq SString where (SString i) == (SString i') = i == i' diff --git a/src/comp/Undefined.hs b/src/comp/Undefined.hs index 766d72dd..329df5a4 100644 --- a/src/comp/Undefined.hs +++ b/src/comp/Undefined.hs @@ -10,7 +10,7 @@ module Undefined ( undefKindToInteger ) where -import qualified Data.Generics as Generic +import Data.Data import Eval @@ -30,7 +30,7 @@ import Eval -- any other dont-care value that doesn't fit the above kinds. data UndefKind = UNotUsed | UDontCare | UNoMatch - deriving (Eq, Ord, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Ord, Show, Data, Typeable) instance Hyper UndefKind where hyper x y = seq x y diff --git a/src/comp/VModInfo.hs b/src/comp/VModInfo.hs index cf6f5ac3..7bd20198 100644 --- a/src/comp/VModInfo.hs +++ b/src/comp/VModInfo.hs @@ -33,11 +33,11 @@ module VModInfo(VModInfo, mkVModInfo, import Prelude hiding ((<>)) #endif +import Data.Data import Data.List(partition, nub) import Data.Maybe(catMaybes) import qualified Data.Map as M import qualified Data.Set as S -import qualified Data.Generics as Generic import ErrorUtil import Id @@ -54,7 +54,7 @@ import PPrint -- VName newtype VName = VName String - deriving (Show, Ord, Eq, Generic.Data, Generic.Typeable) + deriving (Show, Ord, Eq, Data, Typeable) instance PPrint VName where pPrint _ _ (VName s) = text s @@ -88,7 +88,7 @@ data VeriPortProp = VPreg | VPreset | VPinout | VPunused - deriving (Show, Eq, Ord, Generic.Data, Generic.Typeable) + deriving (Show, Eq, Ord, Data, Typeable) instance Hyper VeriPortProp where hyper x y = x `seq` y @@ -131,7 +131,7 @@ type VMethodConflictInfo = MethodConflictInfo Id -- VPathInfo newtype VPathInfo = VPathInfo [(VName, VName)] - deriving (Show, Ord, Eq, Generic.Data, Generic.Typeable) + deriving (Show, Ord, Eq, Data, Typeable) instance PPrint VPathInfo where pPrint d p (VPathInfo []) = @@ -174,7 +174,7 @@ data VArgInfo = Param VName -- named module parameter | ResetArg Id -- named reset -- named module inout, with associated clock and reset | InoutArg VName (Maybe Id) (Maybe Id) - deriving (Show, Ord, Eq, Generic.Data, Generic.Typeable) + deriving (Show, Ord, Eq, Data, Typeable) isParam :: VArgInfo -> Bool isParam (Param {}) = True @@ -276,7 +276,7 @@ data VFieldInfo = Method { vf_name :: Id, -- method name vf_inout :: VName, vf_clock :: (Maybe Id), -- optional clock vf_reset :: (Maybe Id) } -- optional reset - deriving (Show, Ord, Eq, Generic.Data, Generic.Typeable) + deriving (Show, Ord, Eq, Data, Typeable) instance HasPosition VFieldInfo where getPosition (Method { vf_name = n }) = getPosition n @@ -347,7 +347,7 @@ data VClockInfo = ClockInfo { -- method calls are permitted across sibling relationships -- but *both* gate conditions must be enforced siblingClocks :: [(Id, Id)] } - deriving (Show, Ord, Eq, Generic.Data, Generic.Typeable) + deriving (Show, Ord, Eq, Data, Typeable) -- Gets information needed to construct the signals from an output clock clock. -- If there is no gate port or if the port is outhigh, Nothing is returned. @@ -471,7 +471,7 @@ data VResetInfo = ResetInfo { input_resets :: [ResetInf], output_resets :: [ResetInf] } - deriving(Show, Ord, Eq, Generic.Data, Generic.Typeable) + deriving(Show, Ord, Eq, Data, Typeable) -- Gets info needed to construct the signals from an output reset. -- (Currently the same as getting the port name.) @@ -560,7 +560,7 @@ data VModInfo = VModInfo { vSched :: VSchedInfo, vPath :: VPathInfo } - deriving (Show, Ord, Eq, Generic.Data, Generic.Typeable) + deriving (Show, Ord, Eq, Data, Typeable) mkVModInfo :: VName -> VClockInfo -> VResetInfo -> [VArgInfo] -> [VFieldInfo] -> @@ -645,7 +645,7 @@ data VWireInfo = WireInfo { wClk :: VClockInfo, wRst :: VResetInfo, wArgs :: [VArgInfo] - } deriving (Eq, Show, Generic.Data, Generic.Typeable) + } deriving (Eq, Show, Data, Typeable) instance Hyper VWireInfo where diff --git a/src/comp/Verilog.hs b/src/comp/Verilog.hs index b315264a..6b69b8f8 100644 --- a/src/comp/Verilog.hs +++ b/src/comp/Verilog.hs @@ -48,6 +48,7 @@ module Verilog( import Prelude hiding ((<>)) #endif +import Data.Data (Data, Typeable) import Data.List(nub) import Data.Maybe(fromMaybe) import Eval @@ -60,7 +61,6 @@ import Id import Position import FStringCompat import Data.Char(isDigit, isAlpha) -import qualified Data.Generics as Generic --import Debug.Trace @@ -81,7 +81,7 @@ mkSynthPragma s = text ("// " ++ synthesis_str ++ " " ++ s) -- * a list of import-DPI declarations -- * a comment for the entire file, not for any one module data VProgram = VProgram [VModule] [VDPI] VComment - deriving (Eq, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Show, Data, Typeable) instance Hyper VProgram where hyper x y = (x==x) `seq` y @@ -134,7 +134,7 @@ ppComment cs = -- * The return type -- * The arguments (name, whether it's an input, type) data VDPI = VDPI VId VDPIType [(VId, Bool, VDPIType)] - deriving (Eq, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Show, Data, Typeable) instance PPrint VDPI where pPrint d p (VDPI name ret args) = @@ -155,7 +155,7 @@ data VDPIType = VDT_void | VDT_wide Integer | VDT_string | VDT_poly - deriving (Eq, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Show, Data, Typeable) instance PPrint VDPIType where pPrint _ _ VDT_void = text "void" @@ -179,7 +179,7 @@ data VModule = vm_ports :: [([VArg],VComment)] , vm_body :: [VMItem] } - deriving (Eq, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Show, Data, Typeable) instance PPrint VModule where pPrint d p vmodule = @@ -235,7 +235,7 @@ data VArg | VAInout VId (Maybe VId) (Maybe (Maybe VRange)) | VAOutput VId (Maybe VRange) | VAParameter VId (Maybe VRange) VExpr - deriving (Eq, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Show, Data, Typeable) -- only use this for debugging instance PPrint VArg where @@ -299,7 +299,7 @@ data VMItem -- if no spaces needed, use a list of one list. | VMGroup { vg_translate_off :: Bool, vg_body :: [[VMItem]]} | VMFunction VFunction - deriving (Eq, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Show, Data, Typeable) instance Ord VMItem where -- comments are just attached to other statements, @@ -432,7 +432,7 @@ vGroupWithComment True vmis comment = data VFunction = VFunction VId (Maybe VRange) [VFDecl] VStmt - deriving (Eq, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Show, Data, Typeable) type VFDecl = VVDecl -- not quite right @@ -466,7 +466,7 @@ data VStmt | VTask VId [VExpr] -- calling a verilog system task as a Bluespec foreign function of type Action | VAssert VEventExpr [VExpr] | VZeroDelay -- injecting an explicit (0-tick) delay for synchronization purposes - deriving (Eq, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Show, Data, Typeable) instance PPrint VStmt where @@ -565,7 +565,7 @@ data VLValue = VLId VId | VLConcat [VLValue] | VLSub VLValue VExpr - deriving (Eq, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Show, Data, Typeable) instance Ord VLValue where compare (VLId lid) (VLId rid) = compare lid rid @@ -580,7 +580,7 @@ instance PPrint VLValue where data VCaseArm = VCaseArm [VExpr] VStmt | VDefault VStmt - deriving (Eq, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Show, Data, Typeable) instance PPrint VCaseArm where pPrint d p (VCaseArm es s) = @@ -598,7 +598,7 @@ vSeq ss = VSeq ss data VVDecl = VVDecl VDType (Maybe VRange) [VVar] | VVDWire (Maybe VRange) VVar VExpr - deriving (Eq, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Show, Data, Typeable) instance Ord VVDecl where compare (VVDecl _ _ _) (VVDWire _ _ _) = LT @@ -627,7 +627,7 @@ vVDecl t r v = VVDecl t r [v] data VDType = VDReg | VDWire | VDInput | VDInout | VDOutput -- only for decls - deriving (Eq, Ord, Show, Generic.Data, Generic.Typeable, Enum) + deriving (Eq, Ord, Show, Data, Typeable, Enum) instance PPrint VDType where pPrint d p VDReg = text "reg" @@ -639,7 +639,7 @@ instance PPrint VDType where data VVar = VVar VId | VArray VRange VId - deriving (Eq, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Show, Data, Typeable) instance Ord VVar where compare (VVar lid) (VArray _ rid) = compare lid rid @@ -658,7 +658,7 @@ vvName (VArray _ i) = i -- the VMItem is used for inlined registers data VId = VId String Id (Maybe VMItem) - deriving (Show, Generic.Data, Generic.Typeable) + deriving (Show, Data, Typeable) instance Ord VId where compare (VId s1 _ _) (VId s2 _ _) = compare s1 s2 @@ -701,7 +701,7 @@ data VEventExpr | VEEnegedge VExpr | VEE VExpr | VEEMacro String VExpr - deriving (Eq, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Show, Data, Typeable) instance PPrint VEventExpr where pPrint d p (VEEOr e1 e2) = @@ -733,7 +733,7 @@ data VExpr | VEIf VExpr VExpr VExpr | VEFctCall VId [VExpr] | VEMacro String - deriving (Eq, Ord, Show, Generic.Data, Generic.Typeable) + deriving (Eq, Ord, Show, Data, Typeable) -- vVar :: String -> VExpr -- vVar = VEVar . VId @@ -810,7 +810,7 @@ createVEWConstString width base value = width' = whichWidth base' width data VTri = V0 | V1 | Vx | Vz - deriving (Eq, Ord, Show, Generic.Data, Generic.Typeable, Enum) + deriving (Eq, Ord, Show, Data, Typeable, Enum) instance PPrint VTri where pPrint d p V0 = text "0" @@ -834,7 +834,7 @@ data VOp | VOr | VLAnd -- logical AND and OR | VLOr - deriving (Eq, Ord, Show, Generic.Data, Generic.Typeable, Enum) + deriving (Eq, Ord, Show, Data, Typeable, Enum) instance PPrint VOp where diff --git a/src/comp/Wires.hs b/src/comp/Wires.hs index b2e851a0..79f7c4e3 100644 --- a/src/comp/Wires.hs +++ b/src/comp/Wires.hs @@ -14,19 +14,20 @@ module Wires(ClockId, ClockDomain(..), ResetId, import Prelude hiding ((<>)) #endif +import Data.Data + import Eval import PPrint -import qualified Data.Generics as Generic -- Primitives for describing special wires (e.g. clock and reset) data ClockId = ClockId !Int - deriving (Show, Eq, Ord, Generic.Data, Generic.Typeable) + deriving (Show, Eq, Ord, Data, Typeable) instance Hyper ClockId where hyper (ClockId a) y = hyper a y data ClockDomain = ClockDomain !Int - deriving (Show, Eq, Ord, Generic.Data, Generic.Typeable) + deriving (Show, Eq, Ord, Data, Typeable) instance PPrint ClockDomain where pPrint d p (ClockDomain i) = pPrint d p i @@ -35,7 +36,7 @@ instance Hyper ClockDomain where hyper (ClockDomain a) y = hyper a y data ResetId = ResetId !Int - deriving (Show, Eq, Ord, Generic.Data, Generic.Typeable) + deriving (Show, Eq, Ord, Data, Typeable) instance Hyper ResetId where hyper (ResetId a) y = hyper a y @@ -88,7 +89,7 @@ data WireProps = WireProps { -- clock domain of object, Nothing if object crosse -- more than one implies "unsafe reset crossing" wpResets :: [ResetId] } - deriving(Eq, Ord, Show, Generic.Data, Generic.Typeable) + deriving(Eq, Ord, Show, Data, Typeable) emptyWireProps :: WireProps emptyWireProps = WireProps { wpClockDomain = Nothing, wpResets = [] }