-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | The GHC API -- -- GHC's functionality can be useful for more things than just compiling -- Haskell programs. Important use cases are programs that analyse (and -- perhaps transform) Haskell code. Others include loading Haskell code -- dynamically in a GHCi-like manner. For this reason, a lot of GHC's -- functionality is made available through this package. @package ghc @version 7.0.3 module ParserCoreUtils data ParseResult a OkP :: a -> ParseResult a FailP :: String -> ParseResult a type P a = String -> Int -> ParseResult a thenP :: P a -> (a -> P b) -> P b returnP :: a -> P a failP :: String -> P a getCoreModuleName :: FilePath -> IO String data Token TKmodule :: Token TKdata :: Token TKnewtype :: Token TKforall :: Token TKrec :: Token TKlet :: Token TKin :: Token TKcase :: Token TKof :: Token TKcast :: Token TKnote :: Token TKexternal :: Token TKlocal :: Token TKwild :: Token TKoparen :: Token TKcparen :: Token TKobrace :: Token TKcbrace :: Token TKhash :: Token TKeq :: Token TKcolon :: Token TKcoloncolon :: Token TKcoloneqcolon :: Token TKstar :: Token TKrarrow :: Token TKlambda :: Token TKat :: Token TKdot :: Token TKquestion :: Token TKsemicolon :: Token TKname :: String -> Token TKcname :: String -> Token TKinteger :: Integer -> Token TKrational :: Rational -> Token TKstring :: String -> Token TKchar :: Char -> Token TKEOF :: Token module FastMutInt data FastMutInt newFastMutInt :: IO FastMutInt readFastMutInt :: FastMutInt -> IO Int writeFastMutInt :: FastMutInt -> Int -> IO () data FastMutPtr newFastMutPtr :: IO FastMutPtr readFastMutPtr :: FastMutPtr -> IO (Ptr a) writeFastMutPtr :: FastMutPtr -> Ptr a -> IO () module Encoding utf8DecodeChar# :: Addr# -> (# Char#, Addr# #) utf8PrevChar :: Ptr Word8 -> IO (Ptr Word8) utf8CharStart :: Ptr Word8 -> IO (Ptr Word8) utf8DecodeChar :: Ptr Word8 -> (Char, Ptr Word8) utf8DecodeString :: Ptr Word8 -> Int -> IO [Char] utf8EncodeChar :: Char -> Ptr Word8 -> IO (Ptr Word8) utf8EncodeString :: Ptr Word8 -> String -> IO () utf8EncodedLength :: String -> Int countUTF8Chars :: Ptr Word8 -> Int -> IO Int zEncodeString :: UserString -> EncodedString zDecodeString :: EncodedString -> UserString module ExternalCore data Module Module :: Mname -> [Tdef] -> [Vdefg] -> Module data Tdef Data :: (Qual Tcon) -> [Tbind] -> [Cdef] -> Tdef Newtype :: (Qual Tcon) -> (Qual Tcon) -> [Tbind] -> Ty -> Tdef data Cdef Constr :: (Qual Dcon) -> [Tbind] -> [Ty] -> Cdef GadtConstr :: (Qual Dcon) -> Ty -> Cdef data Vdefg Rec :: [Vdef] -> Vdefg Nonrec :: Vdef -> Vdefg type Vdef = (Bool, Qual Var, Ty, Exp) data Exp Var :: (Qual Var) -> Exp Dcon :: (Qual Dcon) -> Exp Lit :: Lit -> Exp App :: Exp -> Exp -> Exp Appt :: Exp -> Ty -> Exp Lam :: Bind -> Exp -> Exp Let :: Vdefg -> Exp -> Exp Case :: Exp -> Vbind -> Ty -> [Alt] -> Exp Cast :: Exp -> Ty -> Exp Note :: String -> Exp -> Exp External :: String -> String -> Ty -> Exp DynExternal :: String -> Ty -> Exp Label :: String -> Exp data Bind Vb :: Vbind -> Bind Tb :: Tbind -> Bind data Alt Acon :: (Qual Dcon) -> [Tbind] -> [Vbind] -> Exp -> Alt Alit :: Lit -> Exp -> Alt Adefault :: Exp -> Alt type Vbind = (Var, Ty) type Tbind = (Tvar, Kind) data Ty Tvar :: Tvar -> Ty Tcon :: (Qual Tcon) -> Ty Tapp :: Ty -> Ty -> Ty Tforall :: Tbind -> Ty -> Ty TransCoercion :: Ty -> Ty -> Ty SymCoercion :: Ty -> Ty UnsafeCoercion :: Ty -> Ty -> Ty InstCoercion :: Ty -> Ty -> Ty LeftCoercion :: Ty -> Ty RightCoercion :: Ty -> Ty data Kind Klifted :: Kind Kunlifted :: Kind Kunboxed :: Kind Kopen :: Kind Karrow :: Kind -> Kind -> Kind Keq :: Ty -> Ty -> Kind data Lit Lint :: Integer -> Ty -> Lit Lrational :: Rational -> Ty -> Lit Lchar :: Char -> Ty -> Lit Lstring :: String -> Ty -> Lit type Mname = Id type Var = Id type Tvar = Id type Tcon = Id type Dcon = Id type Qual t = (Mname, t) type Id = String primMname :: Mname tcArrow :: Qual Tcon module Dataflow -- | Solve the fixed-point of a dataflow problem. -- -- Complexity: O(N+H*E) calls to the update function where: N = number of -- nodes, E = number of edges, H = maximum height of the lattice for any -- particular node. -- -- Sketch for proof of complexity: Note that the state is threaded -- through the entire execution. Also note that the height of the latice -- at any particular node is the number of times update can -- return non-Nothing for a particular node. Every call (except for the -- top level one) must be caused by a non-Nothing result and each -- non-Nothing result causes as many calls as it has out-going edges. -- Thus any particular node, n, may cause in total at most H*out(n) -- further calls. When summed over all nodes, that is H*E. The N term of -- the complexity is from the initial call when update will be -- passed Nothing. fixedpoint :: (node -> [node]) -> (node -> Maybe node -> s -> Maybe s) -> [node] -> s -> s module CmmTx data ChangeFlag NoChange :: ChangeFlag SomeChange :: ChangeFlag type Tx a = a -> TxRes a data TxRes a TxRes :: ChangeFlag -> a -> TxRes a seqTx :: Tx a -> Tx a -> Tx a iterateTx :: Tx a -> Tx a runTx :: Tx a -> a -> a aTx :: a -> TxRes a noTx :: a -> TxRes a replaceTx :: a -> TxRes b -> TxRes a txVal :: TxRes a -> a txHasChanged :: TxRes a -> Bool plusTx :: (a -> b -> c) -> TxRes a -> TxRes b -> TxRes c mapTx :: Tx a -> Tx [a] orChange :: ChangeFlag -> ChangeFlag -> ChangeFlag instance Monad TxRes instance Functor TxRes -- | GHC LLVM Mangler -- -- This script processes the assembly produced by LLVM, rearranging the -- code so that an info table appears before its corresponding function. -- We also use it to fix up the stack alignment, which needs to be 16 -- byte aligned but always ends up off by 4 bytes because GHC sets it to -- the wrong starting value in the RTS. -- -- We only need this for Mac OS X, other targets don't use it. module LlvmMangler -- | Read in assembly file and process llvmFixupAsm :: FilePath -> FilePath -> IO () module Maybes data MaybeErr err val Succeeded :: val -> MaybeErr err val Failed :: err -> MaybeErr err val failME :: err -> MaybeErr err val isSuccess :: MaybeErr err val -> Bool fmapM_maybe :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b) orElse :: Maybe a -> a -> a mapCatMaybes :: (a -> Maybe b) -> [a] -> [b] -- | Collects a list of Justs into a single Just, -- returning Nothing if there are any Nothings. allMaybes :: [Maybe a] -> Maybe [a] firstJust :: Maybe a -> Maybe a -> Maybe a -- | Takes a list of Maybes and returns the first Just if -- there is one, or Nothing otherwise. firstJusts :: [Maybe a] -> Maybe a expectJust :: String -> Maybe a -> a maybeToBool :: Maybe a -> Bool newtype MaybeT m a MaybeT :: m (Maybe a) -> MaybeT m a runMaybeT :: MaybeT m a -> m (Maybe a) instance Monad (MaybeErr err) instance Monad m => Monad (MaybeT m) instance Functor m => Functor (MaybeT m) module FiniteMap insertList :: Ord key => [(key, elt)] -> Map key elt -> Map key elt insertListWith :: Ord key => (elt -> elt -> elt) -> [(key, elt)] -> Map key elt -> Map key elt deleteList :: Ord key => [key] -> Map key elt -> Map key elt foldRight :: (elt -> a -> a) -> a -> Map key elt -> a foldRightWithKey :: (key -> elt -> a -> a) -> a -> Map key elt -> a module SPARC.Cond -- | Branch condition codes. data Cond ALWAYS :: Cond EQQ :: Cond GE :: Cond GEU :: Cond GTT :: Cond GU :: Cond LE :: Cond LEU :: Cond LTT :: Cond LU :: Cond NE :: Cond NEG :: Cond NEVER :: Cond POS :: Cond VC :: Cond VS :: Cond condUnsigned :: Cond -> Bool condToSigned :: Cond -> Cond condToUnsigned :: Cond -> Cond instance Eq Cond module OrdList data OrdList a nilOL :: OrdList a isNilOL :: OrdList a -> Bool unitOL :: a -> OrdList a appOL :: OrdList a -> OrdList a -> OrdList a consOL :: a -> OrdList a -> OrdList a snocOL :: OrdList a -> a -> OrdList a concatOL :: [OrdList a] -> OrdList a mapOL :: (a -> b) -> OrdList a -> OrdList b fromOL :: OrdList a -> [a] toOL :: [a] -> OrdList a foldrOL :: (a -> b -> b) -> b -> OrdList a -> b foldlOL :: (b -> a -> b) -> b -> OrdList a -> b instance Functor OrdList module X86.Cond data Cond ALWAYS :: Cond EQQ :: Cond GE :: Cond GEU :: Cond GTT :: Cond GU :: Cond LE :: Cond LEU :: Cond LTT :: Cond LU :: Cond NE :: Cond NEG :: Cond POS :: Cond CARRY :: Cond OFLO :: Cond PARITY :: Cond NOTPARITY :: Cond condUnsigned :: Cond -> Bool condToSigned :: Cond -> Cond condToUnsigned :: Cond -> Cond instance Eq Cond module Constants oFFSET_StgRegTable_rR1 :: Int oFFSET_StgRegTable_rR2 :: Int oFFSET_StgRegTable_rR3 :: Int oFFSET_StgRegTable_rR4 :: Int oFFSET_StgRegTable_rR5 :: Int oFFSET_StgRegTable_rR6 :: Int oFFSET_StgRegTable_rR7 :: Int oFFSET_StgRegTable_rR8 :: Int oFFSET_StgRegTable_rR9 :: Int oFFSET_StgRegTable_rR10 :: Int oFFSET_StgRegTable_rF1 :: Int oFFSET_StgRegTable_rF2 :: Int oFFSET_StgRegTable_rF3 :: Int oFFSET_StgRegTable_rF4 :: Int oFFSET_StgRegTable_rD1 :: Int oFFSET_StgRegTable_rD2 :: Int oFFSET_StgRegTable_rL1 :: Int oFFSET_StgRegTable_rSp :: Int oFFSET_StgRegTable_rSpLim :: Int oFFSET_StgRegTable_rHp :: Int oFFSET_StgRegTable_rHpLim :: Int oFFSET_StgRegTable_rCurrentTSO :: Int oFFSET_StgRegTable_rCurrentNursery :: Int oFFSET_StgRegTable_rHpAlloc :: Int oFFSET_StgRegTable_rRet :: Int oFFSET_StgRegTable_rNursery :: Int oFFSET_stgEagerBlackholeInfo :: Int oFFSET_stgGCEnter1 :: Int oFFSET_stgGCFun :: Int oFFSET_Capability_r :: Int oFFSET_Capability_lock :: Int oFFSET_Capability_mut_lists :: Int oFFSET_Capability_context_switch :: Int oFFSET_Capability_sparks :: Int oFFSET_bdescr_start :: Int oFFSET_bdescr_free :: Int oFFSET_bdescr_blocks :: Int oFFSET_bdescr_gen_no :: Int oFFSET_bdescr_link :: Int sIZEOF_generation :: Int oFFSET_generation_mut_list :: Int oFFSET_generation_n_new_large_blocks :: Int sIZEOF_CostCentreStack :: Int oFFSET_CostCentreStack_ccsID :: Int oFFSET_CostCentreStack_mem_alloc :: Int oFFSET_CostCentreStack_scc_count :: Int oFFSET_CostCentreStack_prevStack :: Int oFFSET_CostCentre_ccID :: Int oFFSET_CostCentre_link :: Int oFFSET_StgHeader_info :: Int oFFSET_StgHeader_ccs :: Int oFFSET_StgHeader_ldvw :: Int sIZEOF_StgSMPThunkHeader :: Int oFFSET_StgClosure_payload :: Int oFFSET_StgEntCounter_allocs :: Int oFFSET_StgEntCounter_registeredp :: Int oFFSET_StgEntCounter_link :: Int oFFSET_StgEntCounter_entry_count :: Int sIZEOF_StgUpdateFrame_NoHdr :: Int sIZEOF_StgCatchFrame_NoHdr :: Int sIZEOF_StgStopFrame_NoHdr :: Int sIZEOF_StgMutArrPtrs_NoHdr :: Int oFFSET_StgMutArrPtrs_ptrs :: Int oFFSET_StgMutArrPtrs_size :: Int sIZEOF_StgArrWords_NoHdr :: Int oFFSET_StgArrWords_bytes :: Int oFFSET_StgArrWords_payload :: Int oFFSET_StgTSO__link :: Int oFFSET_StgTSO_global_link :: Int oFFSET_StgTSO_what_next :: Int oFFSET_StgTSO_why_blocked :: Int oFFSET_StgTSO_block_info :: Int oFFSET_StgTSO_blocked_exceptions :: Int oFFSET_StgTSO_id :: Int oFFSET_StgTSO_cap :: Int oFFSET_StgTSO_saved_errno :: Int oFFSET_StgTSO_trec :: Int oFFSET_StgTSO_flags :: Int oFFSET_StgTSO_dirty :: Int oFFSET_StgTSO_bq :: Int oFFSET_StgTSO_CCCS :: Int oFFSET_StgTSO_sp :: Int oFFSET_StgTSO_stack :: Int oFFSET_StgTSO_stack_size :: Int sIZEOF_StgTSOProfInfo :: Int oFFSET_StgUpdateFrame_updatee :: Int oFFSET_StgCatchFrame_handler :: Int oFFSET_StgCatchFrame_exceptions_blocked :: Int sIZEOF_StgPAP_NoHdr :: Int oFFSET_StgPAP_n_args :: Int oFFSET_StgPAP_fun :: Int oFFSET_StgPAP_arity :: Int oFFSET_StgPAP_payload :: Int sIZEOF_StgAP_NoThunkHdr :: Int sIZEOF_StgAP_NoHdr :: Int oFFSET_StgAP_n_args :: Int oFFSET_StgAP_fun :: Int oFFSET_StgAP_payload :: Int sIZEOF_StgAP_STACK_NoThunkHdr :: Int sIZEOF_StgAP_STACK_NoHdr :: Int oFFSET_StgAP_STACK_size :: Int oFFSET_StgAP_STACK_fun :: Int oFFSET_StgAP_STACK_payload :: Int sIZEOF_StgSelector_NoThunkHdr :: Int sIZEOF_StgSelector_NoHdr :: Int oFFSET_StgInd_indirectee :: Int sIZEOF_StgMutVar_NoHdr :: Int oFFSET_StgMutVar_var :: Int sIZEOF_StgAtomicallyFrame_NoHdr :: Int oFFSET_StgAtomicallyFrame_code :: Int oFFSET_StgAtomicallyFrame_next_invariant_to_check :: Int oFFSET_StgAtomicallyFrame_result :: Int oFFSET_StgInvariantCheckQueue_invariant :: Int oFFSET_StgInvariantCheckQueue_my_execution :: Int oFFSET_StgInvariantCheckQueue_next_queue_entry :: Int oFFSET_StgAtomicInvariant_code :: Int oFFSET_StgTRecHeader_enclosing_trec :: Int sIZEOF_StgCatchSTMFrame_NoHdr :: Int oFFSET_StgCatchSTMFrame_handler :: Int oFFSET_StgCatchSTMFrame_code :: Int sIZEOF_StgCatchRetryFrame_NoHdr :: Int oFFSET_StgCatchRetryFrame_running_alt_code :: Int oFFSET_StgCatchRetryFrame_first_code :: Int oFFSET_StgCatchRetryFrame_alt_code :: Int oFFSET_StgTVarWatchQueue_closure :: Int oFFSET_StgTVarWatchQueue_next_queue_entry :: Int oFFSET_StgTVarWatchQueue_prev_queue_entry :: Int oFFSET_StgTVar_current_value :: Int sIZEOF_StgWeak_NoHdr :: Int oFFSET_StgWeak_link :: Int oFFSET_StgWeak_key :: Int oFFSET_StgWeak_value :: Int oFFSET_StgWeak_finalizer :: Int oFFSET_StgWeak_cfinalizer :: Int sIZEOF_StgDeadWeak_NoHdr :: Int oFFSET_StgDeadWeak_link :: Int sIZEOF_StgMVar_NoHdr :: Int oFFSET_StgMVar_head :: Int oFFSET_StgMVar_tail :: Int oFFSET_StgMVar_value :: Int sIZEOF_StgMVarTSOQueue_NoHdr :: Int oFFSET_StgMVarTSOQueue_link :: Int oFFSET_StgMVarTSOQueue_tso :: Int sIZEOF_StgBCO_NoHdr :: Int oFFSET_StgBCO_instrs :: Int oFFSET_StgBCO_literals :: Int oFFSET_StgBCO_ptrs :: Int oFFSET_StgBCO_arity :: Int oFFSET_StgBCO_size :: Int oFFSET_StgBCO_bitmap :: Int sIZEOF_StgStableName_NoHdr :: Int oFFSET_StgStableName_sn :: Int sIZEOF_StgBlockingQueue_NoHdr :: Int oFFSET_StgBlockingQueue_bh :: Int oFFSET_StgBlockingQueue_owner :: Int oFFSET_StgBlockingQueue_queue :: Int oFFSET_StgBlockingQueue_link :: Int sIZEOF_MessageBlackHole_NoHdr :: Int oFFSET_MessageBlackHole_link :: Int oFFSET_MessageBlackHole_tso :: Int oFFSET_MessageBlackHole_bh :: Int oFFSET_RtsFlags_ProfFlags_showCCSOnException :: Int oFFSET_RtsFlags_DebugFlags_apply :: Int oFFSET_RtsFlags_DebugFlags_sanity :: Int oFFSET_RtsFlags_DebugFlags_weak :: Int oFFSET_RtsFlags_GcFlags_initialStkSize :: Int oFFSET_RtsFlags_MiscFlags_tickInterval :: Int sIZEOF_StgFunInfoExtraFwd :: Int oFFSET_StgFunInfoExtraFwd_slow_apply :: Int oFFSET_StgFunInfoExtraFwd_fun_type :: Int oFFSET_StgFunInfoExtraFwd_arity :: Int oFFSET_StgFunInfoExtraFwd_bitmap :: Int sIZEOF_StgFunInfoExtraRev :: Int oFFSET_StgFunInfoExtraRev_slow_apply_offset :: Int oFFSET_StgFunInfoExtraRev_fun_type :: Int oFFSET_StgFunInfoExtraRev_arity :: Int oFFSET_StgFunInfoExtraRev_bitmap :: Int oFFSET_StgLargeBitmap_size :: Int oFFSET_StgLargeBitmap_bitmap :: Int sIZEOF_snEntry :: Int oFFSET_snEntry_sn_obj :: Int oFFSET_snEntry_addr :: Int mAX_TUPLE_SIZE :: Int mAX_CONTEXT_REDUCTION_DEPTH :: Int mAX_SPEC_THUNK_SIZE :: Int mAX_SPEC_FUN_SIZE :: Int mAX_SPEC_CONSTR_SIZE :: Int mAX_SPEC_SELECTEE_SIZE :: Int mAX_SPEC_AP_SIZE :: Int mIN_PAYLOAD_SIZE :: Int mAX_INTLIKE :: Int mIN_INTLIKE :: Int mAX_CHARLIKE :: Int mIN_CHARLIKE :: Int mUT_ARR_PTRS_CARD_BITS :: Int mAX_Vanilla_REG :: Int mAX_Float_REG :: Int mAX_Double_REG :: Int mAX_Long_REG :: Int mAX_Real_Vanilla_REG :: Int mAX_Real_Float_REG :: Int mAX_Real_Double_REG :: Int mAX_Real_Long_REG :: Int sTD_HDR_SIZE :: Int pROF_HDR_SIZE :: Int dOUBLE_SIZE :: Int wORD64_SIZE :: Int iNT64_SIZE :: Int rESERVED_C_STACK_BYTES :: Int rESERVED_STACK_WORDS :: Int aP_STACK_SPLIM :: Int wORD_SIZE :: Int wORD_SIZE_IN_BITS :: Int type TargetInt = Int64 type TargetWord = Word64 tARGET_MAX_INT :: Integer tARGET_MAX_WORD :: Integer tARGET_MIN_INT :: Integer tARGET_MAX_CHAR :: Int tAG_BITS :: Int tAG_MASK :: Int mAX_PTR_TAG :: Int cINT_SIZE :: Int bLOCK_SIZE :: Int bLOCK_SIZE_W :: Int bLOCKS_PER_MBLOCK :: Int bITMAP_BITS_SHIFT :: Int module BreakArray data BreakArray BA :: (MutableByteArray# RealWorld) -> BreakArray newBreakArray :: Int -> IO BreakArray getBreak :: BreakArray -> Int -> IO (Maybe Word) setBreakOn :: BreakArray -> Int -> IO Bool setBreakOff :: BreakArray -> Int -> IO Bool showBreakArray :: BreakArray -> IO () module FastBool type FastBool = Int# fastBool :: Bool -> FastBool isFastTrue :: FastBool -> Bool fastOr :: FastBool -> FastBool -> FastBool fastAnd :: FastBool -> FastBool -> FastBool module Alpha.CodeGen module Alpha.Instr module Alpha.RegInfo module Alpha.Regs -- | Fast integers, characters and pointer types for use in many parts of -- GHC module FastTypes type FastInt = Int# _ILIT :: Int -> FastInt iBox :: FastInt -> Int iUnbox :: Int -> FastInt (+#) :: Int# -> Int# -> Int# (-#) :: Int# -> Int# -> Int# (*#) :: Int# -> Int# -> Int# quotFastInt :: FastInt -> FastInt -> FastInt negateFastInt :: FastInt -> FastInt (==#) :: Int# -> Int# -> Bool (/=#) :: Int# -> Int# -> Bool (<#) :: Int# -> Int# -> Bool (<=#) :: Int# -> Int# -> Bool (>=#) :: Int# -> Int# -> Bool (>#) :: Int# -> Int# -> Bool minFastInt :: FastInt -> FastInt -> FastInt maxFastInt :: FastInt -> FastInt -> FastInt shiftLFastInt :: FastInt -> FastInt -> FastInt shiftR_FastInt :: FastInt -> FastInt -> FastInt shiftRLFastInt :: FastInt -> FastInt -> FastInt shiftRAFastInt :: FastInt -> FastInt -> FastInt bitAndFastInt :: FastInt -> FastInt -> FastInt bitOrFastInt :: FastInt -> FastInt -> FastInt type FastChar = Char# _CLIT :: Char -> FastChar cBox :: FastChar -> Char cUnbox :: Char -> FastChar fastOrd :: FastChar -> FastInt fastChr :: FastInt -> FastChar eqFastChar :: FastChar -> FastChar -> Bool type FastPtr a = Addr# pBox :: FastPtr a -> Ptr a pUnbox :: Ptr a -> FastPtr a castFastPtr :: FastPtr a -> FastPtr b module FastFunctions unsafeChr :: Int -> Char inlinePerformIO :: IO a -> a unsafeDupableInterleaveIO :: IO a -> IO a indexWord8OffFastPtr :: FastPtr Word8 -> FastInt -> Word8 indexWord8OffFastPtrAsFastChar :: FastPtr Word8 -> FastInt -> FastChar indexWord8OffFastPtrAsFastInt :: FastPtr Word8 -> FastInt -> FastInt global :: a -> Global a type Global a = IORef a module Config cBuildPlatform :: String cHostPlatform :: String cTargetPlatform :: String cProjectName :: String cProjectVersion :: String cProjectVersionInt :: String cProjectPatchLevel :: String cBooterVersion :: String cStage :: String cCcOpts :: [String] cGccLinkerOpts :: [String] cLdLinkerOpts :: [String] cIntegerLibrary :: String cSplitObjs :: String cGhcWithInterpreter :: String cGhcWithNativeCodeGen :: String cGhcWithLlvmCodeGen :: String cGhcWithSMP :: String cGhcRTSWays :: String cGhcUnregisterised :: String cGhcEnableTablesNextToCode :: String cLeadingUnderscore :: String cRAWCPP_FLAGS :: String cGCC :: String cMKDLL :: String cLdIsGNULd :: String cLD_X :: String cGHC_DRIVER_DIR :: String cGHC_TOUCHY_PGM :: String cGHC_TOUCHY_DIR :: String cGHC_UNLIT_PGM :: String cGHC_UNLIT_DIR :: String cGHC_MANGLER_PGM :: String cGHC_MANGLER_DIR :: String cGHC_SPLIT_PGM :: String cGHC_SPLIT_DIR :: String cGHC_SYSMAN_PGM :: String cGHC_SYSMAN_DIR :: String cGHC_PERL :: String cDEFAULT_TMPDIR :: String cRelocatableBuild :: Bool cLibFFI :: Bool module Exception catchIO :: IO a -> (IOException -> IO a) -> IO a handleIO :: (IOException -> IO a) -> IO a -> IO a tryIO :: IO a -> IO (Either IOException a) -- | A monad that can catch exceptions. A minimal definition requires a -- definition of gcatch. -- -- Implementations on top of IO should implement gblock and -- gunblock to eventually call the primitives block and -- unblock respectively. These are used for implementations that -- support asynchronous exceptions. The default implementations of -- gbracket and gfinally use gblock and -- gunblock thus rarely require overriding. class Monad m => ExceptionMonad m gcatch :: (ExceptionMonad m, Exception e) => m a -> (e -> m a) -> m a gmask :: ExceptionMonad m => ((m a -> m a) -> m b) -> m b gbracket :: ExceptionMonad m => m a -> (a -> m b) -> (a -> m c) -> m c gfinally :: ExceptionMonad m => m a -> m b -> m a gblock :: ExceptionMonad m => m a -> m a gunblock :: ExceptionMonad m => m a -> m a gtry :: (ExceptionMonad m, Exception e) => m a -> m (Either e a) -- | Generalised version of handle, allowing an arbitrary exception -- handling monad instead of just IO. ghandle :: (ExceptionMonad m, Exception e) => (e -> m a) -> m a -> m a -- | Always executes the first argument. If this throws an exception the -- second argument is executed and the exception is raised again. gonException :: ExceptionMonad m => m a -> m b -> m a instance ExceptionMonad IO module Panic -- | GHC's own exception type error messages all take the form: -- --
--   location: error
--   
-- -- If the location is on the command line, or in GHC itself, then -- location=ghc. All of the error types below correspond to -- a location of ghc, except for ProgramError (where the -- string is assumed to contain a location already, so we don't print -- one). data GhcException PhaseFailed :: String -> ExitCode -> GhcException -- | Some other fatal signal (SIGHUP,SIGTERM) Signal :: Int -> GhcException -- | Prints the short usage msg after the error UsageError :: String -> GhcException -- | A problem with the command line arguments, but don't print usage. CmdLineError :: String -> GhcException -- | The impossible happened. Panic :: String -> GhcException -- | The user tickled something that's known not to work yet, but we're not -- counting it as a bug. Sorry :: String -> GhcException -- | An installation problem. InstallationError :: String -> GhcException -- | An error in the user's code, probably. ProgramError :: String -> GhcException -- | Append a description of the given exception to this string. showGhcException :: GhcException -> String -> String throwGhcException :: GhcException -> a handleGhcException :: ExceptionMonad m => (GhcException -> m a) -> m a -> m a -- | Alias for throwGhcException ghcError :: GhcException -> a -- | The name of this GHC. progName :: String pgmError :: String -> a panic :: String -> a -- | Panics and asserts. sorry :: String -> a -- | Panic while pretending to return an unboxed int. You can't use the -- regular panic functions in expressions producing unboxed ints because -- they have the wrong kind. panicFastInt :: String -> FastInt -- | Throw an failed assertion exception for a given filename and line -- number. assertPanic :: String -> Int -> a -- | When called, trace outputs the string in its first argument, -- before returning the second argument as its result. The trace -- function is not referentially transparent, and should only be used for -- debugging, or for monitoring execution. Some implementations of -- trace may decorate the string that's output to indicate that -- you're tracing. The function is implemented on top of -- putTraceMsg. trace :: String -> a -> a -- | Any type that you wish to throw or catch as an exception must be an -- instance of the Exception class. The simplest case is a new -- exception type directly below the root: -- --
--   data MyException = ThisException | ThatException
--       deriving (Show, Typeable)
--   
--   instance Exception MyException
--   
-- -- The default method definitions in the Exception class do what -- we need in this case. You can now throw and catch -- ThisException and ThatException as exceptions: -- --
--   *Main> throw ThisException catch e -> putStrLn ("Caught " ++ show (e :: MyException))
--   Caught ThisException
--   
-- -- In more complicated examples, you may wish to define a whole hierarchy -- of exceptions: -- --
--   ---------------------------------------------------------------------
--   -- Make the root exception type for all the exceptions in a compiler
--   
--   data SomeCompilerException = forall e . Exception e => SomeCompilerException e
--       deriving Typeable
--   
--   instance Show SomeCompilerException where
--       show (SomeCompilerException e) = show e
--   
--   instance Exception SomeCompilerException
--   
--   compilerExceptionToException :: Exception e => e -> SomeException
--   compilerExceptionToException = toException . SomeCompilerException
--   
--   compilerExceptionFromException :: Exception e => SomeException -> Maybe e
--   compilerExceptionFromException x = do
--       SomeCompilerException a <- fromException x
--       cast a
--   
--   ---------------------------------------------------------------------
--   -- Make a subhierarchy for exceptions in the frontend of the compiler
--   
--   data SomeFrontendException = forall e . Exception e => SomeFrontendException e
--       deriving Typeable
--   
--   instance Show SomeFrontendException where
--       show (SomeFrontendException e) = show e
--   
--   instance Exception SomeFrontendException where
--       toException = compilerExceptionToException
--       fromException = compilerExceptionFromException
--   
--   frontendExceptionToException :: Exception e => e -> SomeException
--   frontendExceptionToException = toException . SomeFrontendException
--   
--   frontendExceptionFromException :: Exception e => SomeException -> Maybe e
--   frontendExceptionFromException x = do
--       SomeFrontendException a <- fromException x
--       cast a
--   
--   ---------------------------------------------------------------------
--   -- Make an exception type for a particular frontend compiler exception
--   
--   data MismatchedParentheses = MismatchedParentheses
--       deriving (Typeable, Show)
--   
--   instance Exception MismatchedParentheses where
--       toException   = frontendExceptionToException
--       fromException = frontendExceptionFromException
--   
-- -- We can now catch a MismatchedParentheses exception as -- MismatchedParentheses, SomeFrontendException or -- SomeCompilerException, but not other types, e.g. -- IOException: -- --
--   *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses))
--   Caught MismatchedParentheses
--   *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException))
--   Caught MismatchedParentheses
--   *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException))
--   Caught MismatchedParentheses
--   *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: IOException))
--   *** Exception: MismatchedParentheses
--   
class (Typeable e, Show e) => Exception e toException :: Exception e => e -> SomeException fromException :: Exception e => SomeException -> Maybe e -- | Show an exception as a string. showException :: Exception e => e -> String -- | Similar to catch, but returns an Either result which is -- (Right a) if no exception of type e was -- raised, or (Left ex) if an exception of type -- e was raised and its value is ex. If any other type -- of exception is raised than it will be propogated up to the next -- enclosing exception handler. -- --
--   try a = catch (Right `liftM` a) (return . Left)
--   
-- -- Note that System.IO.Error also exports a function called -- System.IO.Error.try with a similar type to -- Control.Exception.try, except that it catches only the IO and -- user families of exceptions (as required by the Haskell 98 IO -- module). try :: Exception e => IO a -> IO (Either e a) -- | Like try, but pass through UserInterrupt and Panic exceptions. Used -- when we want soft failures when reading interface files, for example. -- TODO: I'm not entirely sure if this is catching what we really want to -- catch tryMost :: IO a -> IO (Either SomeException a) -- | throwTo raises an arbitrary exception in the target thread (GHC -- only). -- -- throwTo does not return until the exception has been raised in -- the target thread. The calling thread can thus be certain that the -- target thread has received the exception. This is a useful property to -- know when dealing with race conditions: eg. if there are two threads -- that can kill each other, it is guaranteed that only one of the -- threads will get to kill the other. -- -- Whatever work the target thread was doing when the exception was -- raised is not lost: the computation is suspended until required by -- another thread. -- -- If the target thread is currently making a foreign call, then the -- exception will not be raised (and hence throwTo will not -- return) until the call has completed. This is the case regardless of -- whether the call is inside a mask or not. -- -- Important note: the behaviour of throwTo differs from that -- described in the paper "Asynchronous exceptions in Haskell" -- (http://research.microsoft.com/~simonpj/Papers/asynch-exns.htm). -- In the paper, throwTo is non-blocking; but the library -- implementation adopts a more synchronous design in which -- throwTo does not return until the exception is received by the -- target thread. The trade-off is discussed in Section 9 of the paper. -- Like any blocking operation, throwTo is therefore interruptible -- (see Section 5.3 of the paper). Unlike other interruptible operations, -- however, throwTo is always interruptible, even if it -- does not actually block. -- -- There is no guarantee that the exception will be delivered promptly, -- although the runtime will endeavour to ensure that arbitrary delays -- don't occur. In GHC, an exception can only be raised when a thread -- reaches a safe point, where a safe point is where memory -- allocation occurs. Some loops do not perform any memory allocation -- inside the loop and therefore cannot be interrupted by a -- throwTo. -- -- Blocked throwTo is fair: if multiple threads are trying to -- throw an exception to the same target thread, they will succeed in -- FIFO order. throwTo :: Exception e => ThreadId -> e -> IO () -- | Install standard signal handlers for catching ^C, which just throw an -- exception in the target thread. The current target thread is the -- thread at the head of the list in the MVar passed to -- installSignalHandlers. installSignalHandlers :: IO () interruptTargetThread :: MVar [ThreadId] instance Eq GhcException instance Typeable GhcException instance Show GhcException instance Exception GhcException -- | Highly random utility functions module Util ghciSupported :: Bool debugIsOn :: Bool ghciTablesNextToCode :: Bool isDynamicGhcLib :: Bool isWindowsHost :: Bool isWindowsTarget :: Bool isDarwinTarget :: Bool zipEqual :: String -> [a] -> [b] -> [(a, b)] zipWithEqual :: String -> (a -> b -> c) -> [a] -> [b] -> [c] zipWith3Equal :: String -> (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] zipWith4Equal :: String -> (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e] -- | zipLazy is a kind of zip that is lazy in the second list -- (observe the ~) zipLazy :: [a] -> [b] -> [(a, b)] -- | stretchZipWith p z f xs ys stretches ys by inserting -- z in the places where p returns True stretchZipWith :: (a -> Bool) -> b -> (a -> b -> c) -> [a] -> [b] -> [c] unzipWith :: (a -> b -> c) -> [(a, b)] -> [c] mapFst :: (a -> c) -> [(a, b)] -> [(c, b)] mapSnd :: (b -> c) -> [(a, b)] -> [(a, c)] mapAndUnzip :: (a -> (b, c)) -> [a] -> ([b], [c]) mapAndUnzip3 :: (a -> (b, c, d)) -> [a] -> ([b], [c], [d]) nOfThem :: Int -> a -> [a] -- | Like filter, only it reverses the sense of the test filterOut :: (a -> Bool) -> [a] -> [a] -- | Uses a function to determine which of two output lists an input -- element should join partitionWith :: (a -> Either b c) -> [a] -> ([b], [c]) -- | Teases a list of Eithers apart into two lists splitEithers :: [Either a b] -> ([a], [b]) -- | A strict version of foldl1 foldl1' :: (a -> a -> a) -> [a] -> a foldl2 :: (acc -> a -> b -> acc) -> acc -> [a] -> [b] -> acc count :: (a -> Bool) -> [a] -> Int all2 :: (a -> b -> Bool) -> [a] -> [b] -> Bool -- |
--   (lengthExceeds xs n) = (length xs > n)
--   
lengthExceeds :: [a] -> Int -> Bool lengthIs :: [a] -> Int -> Bool lengthAtLeast :: [a] -> Int -> Bool listLengthCmp :: [a] -> Int -> Ordering -- | atLength atLen atEnd ls n unravels list ls to -- position n. Precisely: -- --
--   atLength atLenPred atEndPred ls n
--    | n < 0         = atLenPred n
--    | length ls < n = atEndPred (n - length ls)
--    | otherwise     = atLenPred (drop n ls)
--   
atLength :: ([a] -> b) -> (Int -> b) -> [a] -> Int -> b equalLength :: [a] -> [b] -> Bool compareLength :: [a] -> [b] -> Ordering isSingleton :: [a] -> Bool only :: [a] -> a singleton :: a -> [a] notNull :: [a] -> Bool snocView :: [a] -> Maybe ([a], a) isIn :: Eq a => String -> a -> [a] -> Bool isn'tIn :: Eq a => String -> a -> [a] -> Bool fstOf3 :: (a, b, c) -> a sndOf3 :: (a, b, c) -> b thirdOf3 :: (a, b, c) -> c takeList :: [b] -> [a] -> [a] dropList :: [b] -> [a] -> [a] splitAtList :: [b] -> [a] -> ([a], [a]) split :: Char -> String -> [String] dropTail :: Int -> [a] -> [a] -- | Compose a function with itself n times. (nth rather than twice) nTimes :: Int -> (a -> a) -> (a -> a) sortLe :: (a -> a -> Bool) -> [a] -> [a] sortWith :: Ord b => (a -> b) -> [a] -> [a] on :: (a -> a -> c) -> (b -> a) -> b -> b -> c isEqual :: Ordering -> Bool eqListBy :: (a -> a -> Bool) -> [a] -> [a] -> Bool thenCmp :: Ordering -> Ordering -> Ordering cmpList :: (a -> a -> Ordering) -> [a] -> [a] -> Ordering removeSpaces :: String -> String -- | Search for possible matches to the users input in the given list, -- returning a small number of ranked results fuzzyMatch :: String -> [String] -> [String] transitiveClosure :: (a -> [a]) -> (a -> a -> Bool) -> [a] -> [a] seqList :: [a] -> b -> b looksLikeModuleName :: String -> Bool getCmd :: String -> Either String (String, String) toCmdArgs :: String -> Either String (String, [String]) toArgs :: String -> Either String [String] readRational :: String -> Rational createDirectoryHierarchy :: FilePath -> IO () doesDirNameExist :: FilePath -> IO Bool modificationTimeIfExists :: FilePath -> IO (Maybe ClockTime) global :: a -> IORef a consIORef :: IORef [a] -> a -> IO () globalMVar :: a -> MVar a globalEmptyMVar :: MVar a type Suffix = String splitLongestPrefix :: String -> (Char -> Bool) -> (String, String) escapeSpaces :: String -> String -- | The function splits the given string to substrings using the -- searchPathSeparator. parseSearchPath :: String -> [FilePath] data Direction Forwards :: Direction Backwards :: Direction reslash :: Direction -> FilePath -> FilePath abstractConstr :: String -> Constr abstractDataType :: String -> DataType -- | Constructs a non-representation for a non-presentable type mkNoRepType :: String -> DataType -- | There are two principal string types used internally by GHC: -- -- FastString: * A compact, hash-consed, representation of -- character strings. * Comparison is O(1), and you can get a -- Unique.Unique from them. * Generated by fsLit. * Turn -- into Outputable.SDoc with Outputable.ftext. -- -- LitString: * Just a wrapper for the Addr# of a C -- string (Ptr CChar). * Practically no operations. * Outputing -- them is fast. * Generated by sLit. * Turn into -- Outputable.SDoc with Outputable.ptext -- -- Use LitString unless you want the facilities of -- FastString. module FastString -- | A FastString is an array of bytes, hashed to support fast O(1) -- comparison. It is also associated with a character encoding, so that -- we know how to convert a FastString to the local encoding, or -- to the Z-encoding used by the compiler internally. -- -- FastStrings support a memoized conversion to the Z-encoding via -- zEncodeFS. data FastString FastString :: {-# UNPACK #-} !Int -> {-# UNPACK #-} !Int -> {-# UNPACK #-} !Int -> {-# UNPACK #-} !ForeignPtr Word8 -> FSEncoding -> FastString uniq :: FastString -> {-# UNPACK #-} !Int n_bytes :: FastString -> {-# UNPACK #-} !Int n_chars :: FastString -> {-# UNPACK #-} !Int buf :: FastString -> {-# UNPACK #-} !ForeignPtr Word8 enc :: FastString -> FSEncoding fsLit :: String -> FastString -- | Creates a UTF-8 encoded FastString from a String mkFastString :: String -> FastString mkFastStringBytes :: Ptr Word8 -> Int -> FastString -- | Creates a FastString from a UTF-8 encoded [Word8] mkFastStringByteList :: [Word8] -> FastString -- | Create a FastString from an existing ForeignPtr; the -- difference between this and mkFastStringBytes is that we don't -- have to copy the bytes if the string is new to the table. mkFastStringForeignPtr :: Ptr Word8 -> ForeignPtr Word8 -> Int -> IO FastString mkFastString# :: Addr# -> FastString -- | Creates a Z-encoded FastString from a String mkZFastString :: String -> FastString mkZFastStringBytes :: Ptr Word8 -> Int -> FastString -- | Unpacks and decodes the FastString unpackFS :: FastString -> String bytesFS :: FastString -> [Word8] -- | Returns True if the FastString is Z-encoded isZEncoded :: FastString -> Bool -- | Returns a Z-encoded version of a FastString. This might be the -- original, if it was already Z-encoded. The first time this function is -- applied to a particular FastString, the results are memoized. zEncodeFS :: FastString -> FastString uniqueOfFS :: FastString -> FastInt -- | Returns the length of the FastString in characters lengthFS :: FastString -> Int -- | Returns True if the FastString is empty nullFS :: FastString -> Bool appendFS :: FastString -> FastString -> FastString headFS :: FastString -> Char tailFS :: FastString -> FastString concatFS :: [FastString] -> FastString consFS :: Char -> FastString -> FastString nilFS :: FastString -- | Outputs a FastString with no decoding at all, that is, -- you get the actual bytes in the FastString written to the -- Handle. hPutFS :: Handle -> FastString -> IO () getFastStringTable :: IO [[FastString]] -- | Returns True if this FastString is not Z-encoded but -- already has a Z-encoding cached (used in producing stats). hasZEncoding :: FastString -> Bool type LitString = Ptr Word8 sLit :: String -> LitString mkLitString# :: Addr# -> LitString mkLitString :: String -> LitString unpackLitString :: LitString -> String lengthLS :: LitString -> Int instance Typeable FastString instance Data FastString instance Show FastString instance Ord FastString instance Eq FastString module BufWrite data BufHandle BufHandle :: {-# UNPACK #-} !Ptr Word8 -> {-# UNPACK #-} !FastMutInt -> Handle -> BufHandle newBufHandle :: Handle -> IO BufHandle bPutChar :: BufHandle -> Char -> IO () bPutStr :: BufHandle -> String -> IO () bPutFS :: BufHandle -> FastString -> IO () bPutLitString :: BufHandle -> LitString -> FastInt -> IO () bFlush :: BufHandle -> IO () module Pretty data Doc data Mode PageMode :: Mode ZigZagMode :: Mode LeftMode :: Mode OneLineMode :: Mode data TextDetails Chr :: {-# UNPACK #-} !Char -> TextDetails Str :: String -> TextDetails PStr :: FastString -> TextDetails LStr :: {-# UNPACK #-} !LitString -> FastInt -> TextDetails empty :: Doc isEmpty :: Doc -> Bool nest :: Int -> Doc -> Doc char :: Char -> Doc text :: String -> Doc ftext :: FastString -> Doc ptext :: LitString -> Doc int :: Int -> Doc integer :: Integer -> Doc float :: Float -> Doc double :: Double -> Doc rational :: Rational -> Doc parens :: Doc -> Doc brackets :: Doc -> Doc braces :: Doc -> Doc quotes :: Doc -> Doc doubleQuotes :: Doc -> Doc semi :: Doc comma :: Doc colon :: Doc space :: Doc equals :: Doc lparen :: Doc rparen :: Doc lbrack :: Doc rbrack :: Doc lbrace :: Doc rbrace :: Doc cparen :: Bool -> Doc -> Doc (<>) :: Doc -> Doc -> Doc (<+>) :: Doc -> Doc -> Doc hcat :: [Doc] -> Doc hsep :: [Doc] -> Doc ($$) :: Doc -> Doc -> Doc ($+$) :: Doc -> Doc -> Doc vcat :: [Doc] -> Doc sep :: [Doc] -> Doc cat :: [Doc] -> Doc fsep :: [Doc] -> Doc fcat :: [Doc] -> Doc hang :: Doc -> Int -> Doc -> Doc punctuate :: Doc -> [Doc] -> [Doc] render :: Doc -> String fullRender :: Mode -> Int -> Float -> (TextDetails -> a -> a) -> a -> Doc -> a printDoc :: Mode -> Handle -> Doc -> IO () showDocWith :: Mode -> Doc -> String bufLeftRender :: BufHandle -> Doc -> IO () instance Show Doc module PprExternalCore instance Show Lit instance Show Kind instance Show Ty instance Show Alt instance Show Exp instance Show Vdefg instance Show Cdef instance Show Tdef instance Show Module module StringBuffer -- | A StringBuffer is an internal pointer to a sized chunk of bytes. The -- bytes are intended to be *immutable*. There are pure operations to -- read the contents of a StringBuffer. -- -- A StringBuffer may have a finalizer, depending on how it was obtained. data StringBuffer StringBuffer :: {-# UNPACK #-} !ForeignPtr Word8 -> {-# UNPACK #-} !Int -> {-# UNPACK #-} !Int -> StringBuffer buf :: StringBuffer -> {-# UNPACK #-} !ForeignPtr Word8 len :: StringBuffer -> {-# UNPACK #-} !Int cur :: StringBuffer -> {-# UNPACK #-} !Int hGetStringBuffer :: FilePath -> IO StringBuffer hGetStringBufferBlock :: Handle -> Int -> IO StringBuffer appendStringBuffers :: StringBuffer -> StringBuffer -> IO StringBuffer stringToStringBuffer :: String -> IO StringBuffer nextChar :: StringBuffer -> (Char, StringBuffer) currentChar :: StringBuffer -> Char prevChar :: StringBuffer -> Char -> Char atEnd :: StringBuffer -> Bool stepOn :: StringBuffer -> StringBuffer offsetBytes :: Int -> StringBuffer -> StringBuffer byteDiff :: StringBuffer -> StringBuffer -> Int lexemeToString :: StringBuffer -> Int -> String lexemeToFastString :: StringBuffer -> Int -> FastString -- | XXX assumes ASCII digits only (by using byteOff) parseUnsignedInteger :: StringBuffer -> Int -> Integer -> (Char -> Int) -> Integer instance Show StringBuffer module StaticFlags staticFlags :: [String] initStaticOpts :: IO () data WayName WayThreaded :: WayName WayDebug :: WayName WayProf :: WayName WayEventLog :: WayName WayPar :: WayName WayGran :: WayName WayNDP :: WayName WayDyn :: WayName data Way Way :: WayName -> String -> Bool -> String -> [String] -> Way wayName :: Way -> WayName wayTag :: Way -> String wayRTSOnly :: Way -> Bool wayDesc :: Way -> String wayOpts :: Way -> [String] v_Ways :: IORef ([Way]) isRTSWay :: WayName -> Bool mkBuildTag :: [Way] -> String opt_PprUserLength :: Int opt_SuppressUniques :: Bool opt_SuppressCoercions :: Bool opt_SuppressModulePrefixes :: Bool opt_PprStyle_Debug :: Bool opt_TraceLevel :: Int opt_NoDebugOutput :: Bool opt_SccProfilingOn :: Bool opt_Hpc :: Bool opt_DictsStrict :: Bool opt_IrrefutableTuples :: Bool opt_Parallel :: Bool opt_DsMultiTyVar :: Bool opt_NoStateHack :: Bool opt_SimpleListLiterals :: Bool opt_CprOff :: Bool opt_SimplNoPreInlining :: Bool opt_SimplExcessPrecision :: Bool opt_MaxWorkerArgs :: Int opt_UF_CreationThreshold :: Int opt_UF_UseThreshold :: Int opt_UF_FunAppDiscount :: Int opt_UF_DictDiscount :: Int opt_UF_KeenessFactor :: Float opt_UF_DearOp :: Int opt_Fuel :: Int opt_PIC :: Bool opt_Static :: Bool opt_IgnoreDotGhci :: Bool opt_ErrorSpans :: Bool opt_GranMacros :: Bool opt_HiVersion :: Integer opt_HistorySize :: Int opt_OmitBlackHoling :: Bool opt_Unregisterised :: Bool v_Ld_inputs :: IORef ([String]) tablesNextToCode :: Bool opt_StubDeadValues :: Bool opt_Ticky :: Bool addOpt :: String -> IO () removeOpt :: String -> IO () addWay :: WayName -> IO () getWayFlags :: IO [String] v_opt_C_ready :: IORef (Bool) instance Eq WayName instance Ord WayName -- | This module defines classes and functions for pretty-printing. It also -- exports a number of helpful debugging and other utilities such as -- trace and panic. -- -- The interface to this module is very similar to the standard Hughes-PJ -- pretty printing module, except that it exports a number of additional -- functions that are rarely used, and works over the SDoc type. module Outputable -- | Class designating that some type has an SDoc representation class Outputable a ppr :: Outputable a => a -> SDoc -- | When we print a binder, we often want to print its type too. The -- OutputableBndr class encapsulates this idea. class Outputable a => OutputableBndr a pprBndr :: OutputableBndr a => BindingSite -> a -> SDoc type SDoc = PprStyle -> Doc docToSDoc :: Doc -> SDoc -- | Returns the seperated concatenation of the pretty printed things. interppSP :: Outputable a => [a] -> SDoc -- | Returns the comma-seperated concatenation of the pretty printed -- things. interpp'SP :: Outputable a => [a] -> SDoc -- | Returns the comma-seperated concatenation of the quoted pretty printed -- things. -- --
--   [x,y,z]  ==>  `x', `y', `z'
--   
pprQuotedList :: Outputable a => [a] -> SDoc pprWithCommas :: (a -> SDoc) -> [a] -> SDoc quotedListWithOr :: [SDoc] -> SDoc empty :: SDoc -- | Indent SDoc some specified amount nest :: Int -> SDoc -> SDoc char :: Char -> SDoc text :: String -> SDoc ftext :: FastString -> SDoc ptext :: LitString -> SDoc int :: Int -> SDoc integer :: Integer -> SDoc float :: Float -> SDoc double :: Double -> SDoc rational :: Rational -> SDoc parens :: SDoc -> SDoc cparen :: Bool -> SDoc -> SDoc brackets :: SDoc -> SDoc braces :: SDoc -> SDoc quotes :: SDoc -> SDoc doubleQuotes :: SDoc -> SDoc angleBrackets :: SDoc -> SDoc semi :: SDoc comma :: SDoc colon :: SDoc dcolon :: SDoc space :: SDoc equals :: SDoc dot :: SDoc arrow :: SDoc darrow :: SDoc lparen :: SDoc rparen :: SDoc lbrack :: SDoc rbrack :: SDoc lbrace :: SDoc rbrace :: SDoc underscore :: SDoc blankLine :: SDoc -- | Join two SDoc together horizontally without a gap (<>) :: SDoc -> SDoc -> SDoc -- | Join two SDoc together horizontally with a gap between them (<+>) :: SDoc -> SDoc -> SDoc -- | Concatenate SDoc horizontally hcat :: [SDoc] -> SDoc -- | Concatenate SDoc horizontally with a space between each one hsep :: [SDoc] -> SDoc -- | Join two SDoc together vertically; if there is no vertical -- overlap it dovetails the two onto one line ($$) :: SDoc -> SDoc -> SDoc -- | Join two SDoc together vertically ($+$) :: SDoc -> SDoc -> SDoc -- | Concatenate SDoc vertically with dovetailing vcat :: [SDoc] -> SDoc -- | Separate: is either like hsep or like vcat, depending on -- what fits sep :: [SDoc] -> SDoc -- | Catenate: is either like hcat or like vcat, depending on -- what fits cat :: [SDoc] -> SDoc -- | A paragraph-fill combinator. It's much like sep, only it keeps fitting -- things on one line until it can't fit any more. fsep :: [SDoc] -> SDoc -- | This behaves like fsep, but it uses <> for -- horizontal conposition rather than <+> fcat :: [SDoc] -> SDoc hang :: SDoc -> Int -> SDoc -> SDoc punctuate :: SDoc -> [SDoc] -> [SDoc] ppWhen :: Bool -> SDoc -> SDoc ppUnless :: Bool -> SDoc -> SDoc -- | Converts an integer to a verbal index: -- --
--   speakNth 1 = text "first"
--   speakNth 5 = text "fifth"
--   speakNth 21 = text "21st"
--   
speakNth :: Int -> SDoc -- | Converts a strictly positive integer into a number of times: -- --
--   speakNTimes 1 = text "once"
--   speakNTimes 2 = text "twice"
--   speakNTimes 4 = text "4 times"
--   
speakNTimes :: Int -> SDoc -- | Converts an integer to a verbal multiplicity: -- --
--   speakN 0 = text "none"
--   speakN 5 = text "five"
--   speakN 10 = text "10"
--   
speakN :: Int -> SDoc -- | Converts an integer and object description to a statement about the -- multiplicity of those objects: -- --
--   speakNOf 0 (text "melon") = text "no melons"
--   speakNOf 1 (text "melon") = text "one melon"
--   speakNOf 3 (text "melon") = text "three melons"
--   
speakNOf :: Int -> SDoc -> SDoc -- | Determines the pluralisation suffix appropriate for the length of a -- list: -- --
--   plural [] = char 's'
--   plural ["Hello"] = empty
--   plural ["Hello", "World"] = char 's'
--   
plural :: [a] -> SDoc printSDoc :: SDoc -> PprStyle -> IO () printErrs :: Doc -> IO () printOutput :: Doc -> IO () hPrintDump :: Handle -> SDoc -> IO () printDump :: SDoc -> IO () printForC :: Handle -> SDoc -> IO () printForAsm :: Handle -> SDoc -> IO () printForUser :: Handle -> PrintUnqualified -> SDoc -> IO () printForUserPartWay :: Handle -> Int -> PrintUnqualified -> SDoc -> IO () pprCode :: CodeStyle -> SDoc -> SDoc mkCodeStyle :: CodeStyle -> PprStyle showSDoc :: SDoc -> String showSDocOneLine :: SDoc -> String showSDocForUser :: PrintUnqualified -> SDoc -> String showSDocDebug :: SDoc -> String showSDocDump :: SDoc -> String showSDocDumpOneLine :: SDoc -> String showPpr :: Outputable a => a -> String showSDocUnqual :: SDoc -> String showsPrecSDoc :: Int -> SDoc -> ShowS pprInfixVar :: Bool -> SDoc -> SDoc pprPrefixVar :: Bool -> SDoc -> SDoc -- | Special combinator for showing character literals. pprHsChar :: Char -> SDoc -- | Special combinator for showing string literals. pprHsString :: FastString -> SDoc pprHsInfix :: Outputable name => name -> SDoc pprHsVar :: Outputable name => name -> SDoc pprFastFilePath :: FastString -> SDoc -- | BindingSite is used to tell the thing that prints binder what -- language construct is binding the identifier. This can be used to -- decide how much info to print. data BindingSite LambdaBind :: BindingSite CaseBind :: BindingSite LetBind :: BindingSite data PprStyle data CodeStyle CStyle :: CodeStyle AsmStyle :: CodeStyle type PrintUnqualified = (QueryQualifyName, QueryQualifyModule) alwaysQualify :: PrintUnqualified neverQualify :: PrintUnqualified data QualifyName NameUnqual :: QualifyName NameQual :: ModuleName -> QualifyName NameNotInScope1 :: QualifyName NameNotInScope2 :: QualifyName getPprStyle :: (PprStyle -> SDoc) -> SDoc withPprStyle :: PprStyle -> SDoc -> SDoc withPprStyleDoc :: PprStyle -> SDoc -> Doc pprDeeper :: SDoc -> SDoc pprDeeperList :: ([SDoc] -> SDoc) -> [SDoc] -> SDoc pprSetDepth :: Depth -> SDoc -> SDoc codeStyle :: PprStyle -> Bool userStyle :: PprStyle -> Bool debugStyle :: PprStyle -> Bool dumpStyle :: PprStyle -> Bool asmStyle :: PprStyle -> Bool ifPprDebug :: SDoc -> SDoc qualName :: PprStyle -> QueryQualifyName qualModule :: PprStyle -> QueryQualifyModule -- | Style for printing error messages mkErrStyle :: PrintUnqualified -> PprStyle defaultErrStyle :: PprStyle defaultDumpStyle :: PprStyle defaultUserStyle :: PprStyle mkUserStyle :: PrintUnqualified -> Depth -> PprStyle cmdlineParserStyle :: PprStyle data Depth AllTheWay :: Depth PartWay :: Int -> Depth -- | Throw an exception saying bug in GHC pprPanic :: String -> SDoc -> a -- | Throw an exceptio saying this isn't finished yet pprSorry :: String -> SDoc -> a -- | Panic with an assertation failure, recording the given file and line -- number. Should typically be accessed with the ASSERT family of macros assertPprPanic :: String -> Int -> SDoc -> a -- | Specialization of pprPanic that can be safely used with FastInt pprPanicFastInt :: String -> SDoc -> FastInt -- | Throw an exception saying bug in pgm being compiled (used for -- unusual program errors) pprPgmError :: String -> SDoc -> a -- | If debug output is on, show some SDoc on the screen pprTrace :: String -> SDoc -> a -> a -- | Just warn about an assertion failure, recording the given file and -- line number. Should typically be accessed with the WARN macros warnPprTrace :: Bool -> String -> Int -> SDoc -> a -> a -- | When called, trace outputs the string in its first argument, -- before returning the second argument as its result. The trace -- function is not referentially transparent, and should only be used for -- debugging, or for monitoring execution. Some implementations of -- trace may decorate the string that's output to indicate that -- you're tracing. The function is implemented on top of -- putTraceMsg. trace :: String -> a -> a pgmError :: String -> a panic :: String -> a -- | Panics and asserts. sorry :: String -> a -- | Panic while pretending to return an unboxed int. You can't use the -- regular panic functions in expressions producing unboxed ints because -- they have the wrong kind. panicFastInt :: String -> FastInt -- | Throw an failed assertion exception for a given filename and line -- number. assertPanic :: String -> Int -> a instance (Outputable key, Outputable elt) => Outputable (Map key elt) instance Outputable FastString instance (Outputable a, Outputable b, Outputable c, Outputable d, Outputable e) => Outputable (a, b, c, d, e) instance (Outputable a, Outputable b, Outputable c, Outputable d) => Outputable (a, b, c, d) instance (Outputable a, Outputable b, Outputable c) => Outputable (a, b, c) instance (Outputable a, Outputable b) => Outputable (Either a b) instance Outputable a => Outputable (Maybe a) instance (Outputable a, Outputable b) => Outputable (a, b) instance Outputable a => Outputable [a] instance Outputable () instance Outputable Word instance Outputable Word32 instance Outputable Word16 instance Outputable Int instance Outputable Bool module BasicTypes type Version = Int bumpVersion :: Version -> Version initialVersion :: Version type Arity = Int data FunctionOrData IsFunction :: FunctionOrData IsData :: FunctionOrData data WarningTxt WarningTxt :: [FastString] -> WarningTxt DeprecatedTxt :: [FastString] -> WarningTxt data Fixity Fixity :: Int -> FixityDirection -> Fixity data FixityDirection InfixL :: FixityDirection InfixR :: FixityDirection InfixN :: FixityDirection defaultFixity :: Fixity maxPrecedence :: Int negateFixity :: Fixity funTyFixity :: Fixity compareFixity :: Fixity -> Fixity -> (Bool, Bool) newtype IPName name IPName :: name -> IPName name ipNameName :: IPName name -> name mapIPName :: (a -> b) -> IPName a -> IPName b data RecFlag Recursive :: RecFlag NonRecursive :: RecFlag isRec :: RecFlag -> Bool isNonRec :: RecFlag -> Bool boolToRecFlag :: Bool -> RecFlag type RuleName = FastString data TopLevelFlag TopLevel :: TopLevelFlag NotTopLevel :: TopLevelFlag isTopLevel :: TopLevelFlag -> Bool isNotTopLevel :: TopLevelFlag -> Bool data OverlapFlag NoOverlap :: OverlapFlag OverlapOk :: OverlapFlag Incoherent :: OverlapFlag data Boxity Boxed :: Boxity Unboxed :: Boxity isBoxed :: Boxity -> Bool data TupCon TupCon :: Boxity -> Arity -> TupCon tupleParens :: Boxity -> SDoc -> SDoc -- | Identifier occurrence information data OccInfo -- | There are many occurrences, or unknown occurences NoOccInfo :: OccInfo -- | Marks unused variables. Sometimes useful for lambda and case-bound -- variables. IAmDead :: OccInfo -- | Occurs exactly once, not inside a rule OneOcc :: !InsideLam -> !OneBranch -> !InterestingCxt -> OccInfo -- | This identifier breaks a loop of mutually recursive functions. The -- field marks whether it is only a loop breaker due to a reference in a -- rule IAmALoopBreaker :: !RulesOnly -> OccInfo seqOccInfo :: OccInfo -> () zapFragileOcc :: OccInfo -> OccInfo isOneOcc :: OccInfo -> Bool isDeadOcc :: OccInfo -> Bool isLoopBreaker :: OccInfo -> Bool isNonRuleLoopBreaker :: OccInfo -> Bool isNoOcc :: OccInfo -> Bool nonRuleLoopBreaker :: OccInfo type InsideLam = Bool insideLam :: InsideLam notInsideLam :: InsideLam type OneBranch = Bool oneBranch :: OneBranch notOneBranch :: OneBranch type InterestingCxt = Bool data EP a EP :: a -> a -> EP a fromEP :: EP a -> a toEP :: EP a -> a data HsBang HsNoBang :: HsBang HsStrict :: HsBang HsUnpack :: HsBang HsUnpackFailed :: HsBang isBanged :: HsBang -> Bool isMarkedUnboxed :: HsBang -> Bool data StrictnessMark MarkedStrict :: StrictnessMark NotMarkedStrict :: StrictnessMark isMarkedStrict :: StrictnessMark -> Bool data DefMethSpec NoDM :: DefMethSpec VanillaDM :: DefMethSpec GenericDM :: DefMethSpec data CompilerPhase Phase :: PhaseNum -> CompilerPhase InitialPhase :: CompilerPhase type PhaseNum = Int data Activation NeverActive :: Activation AlwaysActive :: Activation ActiveBefore :: PhaseNum -> Activation ActiveAfter :: PhaseNum -> Activation isActive :: CompilerPhase -> Activation -> Bool isActiveIn :: PhaseNum -> Activation -> Bool isNeverActive :: Activation -> Bool isAlwaysActive :: Activation -> Bool isEarlyActive :: Activation -> Bool data RuleMatchInfo ConLike :: RuleMatchInfo FunLike :: RuleMatchInfo isConLike :: RuleMatchInfo -> Bool isFunLike :: RuleMatchInfo -> Bool data InlineSpec Inline :: InlineSpec Inlinable :: InlineSpec NoInline :: InlineSpec EmptyInlineSpec :: InlineSpec data InlinePragma InlinePragma :: InlineSpec -> Maybe Arity -> Activation -> RuleMatchInfo -> InlinePragma inl_inline :: InlinePragma -> InlineSpec inl_sat :: InlinePragma -> Maybe Arity inl_act :: InlinePragma -> Activation inl_rule :: InlinePragma -> RuleMatchInfo defaultInlinePragma :: InlinePragma alwaysInlinePragma :: InlinePragma neverInlinePragma :: InlinePragma dfunInlinePragma :: InlinePragma isDefaultInlinePragma :: InlinePragma -> Bool isInlinePragma :: InlinePragma -> Bool isInlinablePragma :: InlinePragma -> Bool isAnyInlinePragma :: InlinePragma -> Bool inlinePragmaSpec :: InlinePragma -> InlineSpec inlinePragmaSat :: InlinePragma -> Maybe Arity inlinePragmaActivation :: InlinePragma -> Activation inlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfo setInlinePragmaActivation :: InlinePragma -> Activation -> InlinePragma setInlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfo -> InlinePragma data SuccessFlag Succeeded :: SuccessFlag Failed :: SuccessFlag succeeded :: SuccessFlag -> Bool failed :: SuccessFlag -> Bool successIf :: Bool -> SuccessFlag instance Typeable FunctionOrData instance Typeable WarningTxt instance Typeable1 IPName instance Typeable FixityDirection instance Typeable Fixity instance Typeable Boxity instance Typeable RecFlag instance Typeable HsBang instance Typeable Activation instance Typeable RuleMatchInfo instance Typeable InlineSpec instance Typeable InlinePragma instance Eq FunctionOrData instance Ord FunctionOrData instance Data FunctionOrData instance Eq WarningTxt instance Data WarningTxt instance Eq name => Eq (IPName name) instance Ord name => Ord (IPName name) instance Data name => Data (IPName name) instance Eq FixityDirection instance Data FixityDirection instance Data Fixity instance Eq Boxity instance Data Boxity instance Eq RecFlag instance Data RecFlag instance Eq OverlapFlag instance Eq HsBang instance Data HsBang instance Eq Activation instance Data Activation instance Eq RuleMatchInfo instance Data RuleMatchInfo instance Show RuleMatchInfo instance Eq InlineSpec instance Data InlineSpec instance Show InlineSpec instance Eq InlinePragma instance Data InlinePragma instance Outputable InlinePragma instance Outputable InlineSpec instance Outputable RuleMatchInfo instance Outputable Activation instance Outputable CompilerPhase instance Outputable SuccessFlag instance Outputable DefMethSpec instance Outputable StrictnessMark instance Outputable HsBang instance Show OccInfo instance Outputable OccInfo instance Eq TupCon instance Outputable OverlapFlag instance Outputable RecFlag instance Outputable TopLevelFlag instance Outputable FixityDirection instance Eq Fixity instance Outputable Fixity instance Outputable name => Outputable (IPName name) instance Outputable WarningTxt instance Outputable FunctionOrData module Unique -- | The type of unique identifiers that are used in many places in GHC for -- fast ordering and equality tests. You should generate these with the -- functions from the UniqSupply module data Unique -- | Class of things that we can obtain a Unique from class Uniquable a getUnique :: Uniquable a => a -> Unique hasKey :: Uniquable a => a -> Unique -> Bool pprUnique :: Unique -> SDoc mkUniqueGrimily :: Int -> Unique getKey :: Unique -> Int getKeyFastInt :: Unique -> FastInt incrUnique :: Unique -> Unique deriveUnique :: Unique -> Int -> Unique newTagUnique :: Unique -> Char -> Unique initTyVarUnique :: Unique isTupleKey :: Unique -> Bool mkAlphaTyVarUnique :: Int -> Unique mkPrimOpIdUnique :: Int -> Unique mkTupleTyConUnique :: Boxity -> Int -> Unique mkTupleDataConUnique :: Boxity -> Int -> Unique mkPreludeMiscIdUnique :: Int -> Unique mkPreludeDataConUnique :: Int -> Unique mkPreludeTyConUnique :: Int -> Unique mkPreludeClassUnique :: Int -> Unique mkPArrDataConUnique :: Int -> Unique mkVarOccUnique :: FastString -> Unique mkDataOccUnique :: FastString -> Unique mkTvOccUnique :: FastString -> Unique mkTcOccUnique :: FastString -> Unique mkRegSingleUnique :: Int -> Unique mkRegPairUnique :: Int -> Unique mkRegClassUnique :: Int -> Unique mkRegSubUnique :: Int -> Unique mkBuiltinUnique :: Int -> Unique mkPseudoUniqueC :: Int -> Unique mkPseudoUniqueD :: Int -> Unique mkPseudoUniqueE :: Int -> Unique mkPseudoUniqueH :: Int -> Unique instance Show Unique instance Outputable Unique instance Uniquable Unique instance Ord Unique instance Eq Unique instance Uniquable Int instance Uniquable FastString -- | An architecture independent description of a register's class. module RegClass -- | The class of a register. Used in the register allocator. We treat all -- registers in a class as being interchangable. data RegClass RcInteger :: RegClass RcFloat :: RegClass RcDouble :: RegClass RcDoubleSSE :: RegClass instance Eq RegClass instance Outputable RegClass instance Uniquable RegClass -- | An architecture independent description of a register. This needs to -- stay architecture independent because it is used by NCGMonad and the -- register allocators, which are shared by all architectures. module Reg -- | An identifier for a primitive real machine register. type RegNo = Int -- | A register, either virtual or real data Reg RegVirtual :: !VirtualReg -> Reg RegReal :: !RealReg -> Reg regPair :: RegNo -> RegNo -> Reg regSingle :: RegNo -> Reg isRealReg :: Reg -> Bool takeRealReg :: Reg -> Maybe RealReg isVirtualReg :: Reg -> Bool takeVirtualReg :: Reg -> Maybe VirtualReg data VirtualReg VirtualRegI :: {-# UNPACK #-} !Unique -> VirtualReg VirtualRegHi :: {-# UNPACK #-} !Unique -> VirtualReg VirtualRegF :: {-# UNPACK #-} !Unique -> VirtualReg VirtualRegD :: {-# UNPACK #-} !Unique -> VirtualReg VirtualRegSSE :: {-# UNPACK #-} !Unique -> VirtualReg renameVirtualReg :: Unique -> VirtualReg -> VirtualReg classOfVirtualReg :: VirtualReg -> RegClass getHiVirtualRegFromLo :: VirtualReg -> VirtualReg getHiVRegFromLo :: Reg -> Reg -- | RealRegs are machine regs which are available for allocation, in the -- usual way. We know what class they are, because that's part of the -- processor's architecture. -- -- RealRegPairs are pairs of real registers that are allocated together -- to hold a larger value, such as with Double regs on SPARC. data RealReg RealRegSingle :: {-# UNPACK #-} !RegNo -> RealReg RealRegPair :: {-# UNPACK #-} !RegNo -> {-# UNPACK #-} !RegNo -> RealReg regNosOfRealReg :: RealReg -> [RegNo] realRegsAlias :: RealReg -> RealReg -> Bool -- | The patch function supplied by the allocator maps VirtualReg to -- RealReg regs, but sometimes we want to apply it to plain old Reg. liftPatchFnToRegReg :: (VirtualReg -> RealReg) -> (Reg -> Reg) instance Eq VirtualReg instance Show VirtualReg instance Ord VirtualReg instance Eq RealReg instance Show RealReg instance Ord RealReg instance Eq Reg instance Ord Reg instance Outputable Reg instance Uniquable Reg instance Outputable RealReg instance Uniquable RealReg instance Outputable VirtualReg instance Uniquable VirtualReg module UniqFM data UniqFM ele emptyUFM :: UniqFM elt unitUFM :: Uniquable key => key -> elt -> UniqFM elt unitDirectlyUFM :: Unique -> elt -> UniqFM elt listToUFM :: Uniquable key => [(key, elt)] -> UniqFM elt listToUFM_Directly :: [(Unique, elt)] -> UniqFM elt listToUFM_C :: Uniquable key => (elt -> elt -> elt) -> [(key, elt)] -> UniqFM elt addToUFM :: Uniquable key => UniqFM elt -> key -> elt -> UniqFM elt addToUFM_C :: Uniquable key => (elt -> elt -> elt) -> UniqFM elt -> key -> elt -> UniqFM elt addToUFM_Acc :: Uniquable key => (elt -> elts -> elts) -> (elt -> elts) -> UniqFM elts -> key -> elt -> UniqFM elts addListToUFM :: Uniquable key => UniqFM elt -> [(key, elt)] -> UniqFM elt addListToUFM_C :: Uniquable key => (elt -> elt -> elt) -> UniqFM elt -> [(key, elt)] -> UniqFM elt addToUFM_Directly :: UniqFM elt -> Unique -> elt -> UniqFM elt addListToUFM_Directly :: UniqFM elt -> [(Unique, elt)] -> UniqFM elt delFromUFM :: Uniquable key => UniqFM elt -> key -> UniqFM elt delFromUFM_Directly :: UniqFM elt -> Unique -> UniqFM elt delListFromUFM :: Uniquable key => UniqFM elt -> [key] -> UniqFM elt plusUFM :: UniqFM elt -> UniqFM elt -> UniqFM elt plusUFM_C :: (elt -> elt -> elt) -> UniqFM elt -> UniqFM elt -> UniqFM elt minusUFM :: UniqFM elt1 -> UniqFM elt2 -> UniqFM elt1 intersectUFM :: UniqFM elt -> UniqFM elt -> UniqFM elt intersectUFM_C :: (elt1 -> elt2 -> elt3) -> UniqFM elt1 -> UniqFM elt2 -> UniqFM elt3 foldUFM :: (elt -> a -> a) -> a -> UniqFM elt -> a foldUFM_Directly :: (Unique -> elt -> a -> a) -> a -> UniqFM elt -> a mapUFM :: (elt1 -> elt2) -> UniqFM elt1 -> UniqFM elt2 elemUFM :: Uniquable key => key -> UniqFM elt -> Bool elemUFM_Directly :: Unique -> UniqFM elt -> Bool filterUFM :: (elt -> Bool) -> UniqFM elt -> UniqFM elt filterUFM_Directly :: (Unique -> elt -> Bool) -> UniqFM elt -> UniqFM elt sizeUFM :: UniqFM elt -> Int isNullUFM :: UniqFM elt -> Bool lookupUFM :: Uniquable key => UniqFM elt -> key -> Maybe elt lookupUFM_Directly :: UniqFM elt -> Unique -> Maybe elt lookupWithDefaultUFM :: Uniquable key => UniqFM elt -> elt -> key -> elt lookupWithDefaultUFM_Directly :: UniqFM elt -> elt -> Unique -> elt eltsUFM :: UniqFM elt -> [elt] keysUFM :: UniqFM elt -> [Unique] splitUFM :: Uniquable key => UniqFM elt -> key -> (UniqFM elt, Maybe elt, UniqFM elt) ufmToList :: UniqFM elt -> [(Unique, elt)] instance Outputable a => Outputable (UniqFM a) module UniqSet type UniqSet a = UniqFM a emptyUniqSet :: UniqSet a unitUniqSet :: Uniquable a => a -> UniqSet a mkUniqSet :: Uniquable a => [a] -> UniqSet a addOneToUniqSet :: Uniquable a => UniqSet a -> a -> UniqSet a addOneToUniqSet_C :: Uniquable a => (a -> a -> a) -> UniqSet a -> a -> UniqSet a addListToUniqSet :: Uniquable a => UniqSet a -> [a] -> UniqSet a delOneFromUniqSet :: Uniquable a => UniqSet a -> a -> UniqSet a delOneFromUniqSet_Directly :: Uniquable a => UniqSet a -> Unique -> UniqSet a delListFromUniqSet :: Uniquable a => UniqSet a -> [a] -> UniqSet a unionUniqSets :: UniqSet a -> UniqSet a -> UniqSet a unionManyUniqSets :: [UniqSet a] -> UniqSet a minusUniqSet :: UniqSet a -> UniqSet a -> UniqSet a intersectUniqSets :: UniqSet a -> UniqSet a -> UniqSet a foldUniqSet :: (a -> b -> b) -> b -> UniqSet a -> b mapUniqSet :: (a -> b) -> UniqSet a -> UniqSet b elementOfUniqSet :: Uniquable a => a -> UniqSet a -> Bool elemUniqSet_Directly :: Unique -> UniqSet a -> Bool filterUniqSet :: (a -> Bool) -> UniqSet a -> UniqSet a sizeUniqSet :: UniqSet a -> Int isEmptyUniqSet :: UniqSet a -> Bool lookupUniqSet :: Uniquable a => UniqSet a -> a -> Maybe a uniqSetToList :: UniqSet a -> [a] -- | Types for the general graph colorer. module GraphBase -- | A fn to check if a node is trivially colorable For graphs who's color -- classes are disjoint then a node is 'trivially colorable' when it has -- less neighbors and exclusions than available colors for that node. -- -- For graph's who's color classes overlap, ie some colors alias other -- colors, then this can be a bit more tricky. There is a general way to -- calculate this, but it's likely be too slow for use in the code. The -- coloring algorithm takes a canned function which can be optimised by -- the user to be specific to the specific graph being colored. -- -- for details, see A Generalised Algorithm for Graph-Coloring -- Register Allocation Smith, Ramsey, Holloway - PLDI 2004. type Triv k cls color = cls -> UniqSet k -> UniqSet color -> Bool -- | The Interference graph. There used to be more fields, but they were -- turfed out in a previous revision. maybe we'll want more later.. data Graph k cls color Graph :: UniqFM (Node k cls color) -> Graph k cls color -- | All active nodes in the graph. graphMap :: Graph k cls color -> UniqFM (Node k cls color) -- | An empty graph. initGraph :: Graph k cls color -- | Modify the finite map holding the nodes in the graph. graphMapModify :: (UniqFM (Node k cls color) -> UniqFM (Node k cls color)) -> Graph k cls color -> Graph k cls color -- | Graph nodes. Represents a thing that can conflict with another thing. -- For the register allocater the nodes represent registers. data Node k cls color Node :: k -> cls -> Maybe color -> UniqSet k -> UniqSet color -> [color] -> UniqSet k -> Node k cls color -- | A unique identifier for this node. nodeId :: Node k cls color -> k -- | The class of this node, determines the set of colors that can be used. nodeClass :: Node k cls color -> cls -- | The color of this node, if any. nodeColor :: Node k cls color -> Maybe color -- | Neighbors which must be colored differently to this node. nodeConflicts :: Node k cls color -> UniqSet k -- | Colors that cannot be used by this node. nodeExclusions :: Node k cls color -> UniqSet color -- | Colors that this node would prefer to be, in decending order. nodePreference :: Node k cls color -> [color] -- | Neighbors that this node would like to be colored the same as. nodeCoalesce :: Node k cls color -> UniqSet k -- | An empty node. newNode :: k -> cls -> Node k cls color module RegAlloc.Graph.TrivColorable trivColorable :: (RegClass -> VirtualReg -> FastInt) -> (RegClass -> RealReg -> FastInt) -> Triv VirtualReg RegClass RealReg -- | Utils for calculating general worst, bound, squeese and free, -- functions. -- -- as per: A Generalized Algorithm for Graph-Coloring Register -- Allocation Michael Smith, Normal Ramsey, Glenn Holloway. PLDI 2004 -- -- These general versions are not used in GHC proper because they are too -- slow. Instead, hand written optimised versions are provided for each -- architecture in MachRegs*.hs -- -- This code is here because we can test the architecture specific code -- against it. module RegAlloc.Graph.ArchBase data RegClass ClassG32 :: RegClass ClassG16 :: RegClass ClassG8 :: RegClass ClassF64 :: RegClass -- | A register of some class data Reg Reg :: RegClass -> Int -> Reg RegSub :: RegSub -> Reg -> Reg -- | A subcomponent of another register data RegSub SubL16 :: RegSub SubL8 :: RegSub SubL8H :: RegSub -- | Worst case displacement -- -- a node N of classN has some number of neighbors, all of which are from -- classC. -- -- (worst neighbors classN classC) is the maximum number of potential -- colors for N that can be lost by coloring its neighbors. worst :: (RegClass -> UniqSet Reg) -> (Reg -> UniqSet Reg) -> Int -> RegClass -> RegClass -> Int -- | For a node N of classN and neighbors of classesC (bound classN -- classesC) is the maximum number of potential colors for N that can be -- lost by coloring its neighbors. bound :: (RegClass -> UniqSet Reg) -> (Reg -> UniqSet Reg) -> RegClass -> [RegClass] -> Int -- | The total squeese on a particular node with a list of neighbors. -- -- A version of this should be constructed for each particular -- architecture, possibly including uses of bound, so that alised -- registers don't get counted twice, as per the paper. squeese :: (RegClass -> UniqSet Reg) -> (Reg -> UniqSet Reg) -> RegClass -> [(Int, RegClass)] -> Int instance Show RegClass instance Eq RegClass instance Enum RegClass instance Show RegSub instance Enum RegSub instance Ord RegSub instance Eq RegSub instance Show Reg instance Eq Reg instance Uniquable Reg -- | A description of the register set of the X86. This isn't used directly -- in GHC proper. -- -- See RegArchBase.hs for the reference. See MachRegs.hs for the actual -- trivColorable function used in GHC. module RegAlloc.Graph.ArchX86 -- | Determine the class of a register classOfReg :: Reg -> RegClass -- | Determine all the regs that make up a certain class. regsOfClass :: RegClass -> UniqSet Reg -- | Determine the common name of a reg returns Nothing if this reg is not -- part of the machine. regName :: Reg -> Maybe String -- | Which regs alias what other regs regAlias :: Reg -> UniqSet Reg -- | Optimised versions of RegColorBase.{worst, squeese} specific to x86 worst :: Int -> RegClass -> RegClass -> Int squeese :: RegClass -> [(Int, RegClass)] -> Int -- | This module contains types that relate to the positions of things in -- source files, and allow tagging of those things with locations module SrcLoc -- | Represents a single point within a file data SrcLoc mkSrcLoc :: FastString -> Int -> Int -> SrcLoc -- | Creates a bad SrcLoc that has no detailed information -- about its location mkGeneralSrcLoc :: FastString -> SrcLoc noSrcLoc :: SrcLoc -- | Built-in bad SrcLoc values for particular locations generatedSrcLoc :: SrcLoc interactiveSrcLoc :: SrcLoc -- | Move the SrcLoc down by one line if the character is a newline, -- to the next 8-char tabstop if it is a tab, and across by one character -- in any other case advanceSrcLoc :: SrcLoc -> Char -> SrcLoc -- | Gives the filename of the SrcLoc if it is available, otherwise -- returns a dummy value srcLocFile :: SrcLoc -> FastString -- | Raises an error when used on a bad SrcLoc srcLocLine :: SrcLoc -> Int -- | Raises an error when used on a bad SrcLoc srcLocCol :: SrcLoc -> Int -- | Pretty prints information about the SrcSpan in the style -- defined at ... pprDefnLoc :: SrcSpan -> SDoc -- | Good SrcLocs have precise information about their -- location isGoodSrcLoc :: SrcLoc -> Bool -- | A SrcSpan delimits a portion of a text file. It could be represented -- by a pair of (line,column) coordinates, but in fact we optimise -- slightly by using more compact representations for single-line and -- zero-length spans, both of which are quite common. -- -- The end position is defined to be the column after the end of -- the span. That is, a span of (1,1)-(1,2) is one character long, and a -- span of (1,1)-(1,1) is zero characters long. data SrcSpan -- | Create a bad SrcSpan that has not location information mkGeneralSrcSpan :: FastString -> SrcSpan -- | Create a SrcSpan between two points in a file mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan noSrcSpan :: SrcSpan -- | Built-in bad SrcSpans for common sources of location -- uncertainty wiredInSrcSpan :: SrcSpan -- | Create a SrcSpan corresponding to a single point srcLocSpan :: SrcLoc -> SrcSpan -- | Combines two SrcSpan into one that spans at least all the -- characters within both spans. Assumes the file part is the same -- in both inputs combineSrcSpans :: SrcSpan -> SrcSpan -> SrcSpan -- | Returns the location at the start of the SrcSpan or a -- bad SrcSpan if that is unavailable srcSpanStart :: SrcSpan -> SrcLoc -- | Returns the location at the end of the SrcSpan or a bad -- SrcSpan if that is unavailable srcSpanEnd :: SrcSpan -> SrcLoc -- | Obtains the filename for a SrcSpan if it is good srcSpanFileName_maybe :: SrcSpan -> Maybe FastString srcSpanFile :: SrcSpan -> FastString -- | Raises an error when used on a bad SrcSpan srcSpanStartLine :: SrcSpan -> Int -- | Raises an error when used on a bad SrcSpan srcSpanEndLine :: SrcSpan -> Int -- | Raises an error when used on a bad SrcSpan srcSpanStartCol :: SrcSpan -> Int -- | Raises an error when used on a bad SrcSpan srcSpanEndCol :: SrcSpan -> Int -- | Test if a SrcSpan is good, i.e. has precise location -- information isGoodSrcSpan :: SrcSpan -> Bool -- | True if the span is known to straddle only one line. For bad -- SrcSpan, it returns False isOneLineSpan :: SrcSpan -> Bool -- | We attach SrcSpans to lots of things, so let's have a datatype for it. data Located e L :: SrcSpan -> e -> Located e noLoc :: e -> Located e mkGeneralLocated :: String -> e -> Located e getLoc :: Located e -> SrcSpan unLoc :: Located e -> e -- | Tests whether the two located things are equal eqLocated :: Eq a => Located a -> Located a -> Bool -- | Tests the ordering of the two located things cmpLocated :: Ord a => Located a -> Located a -> Ordering combineLocs :: Located a -> Located b -> SrcSpan -- | Combine locations from two Located things and add them to a -- third thing addCLoc :: Located a -> Located b -> c -> Located c leftmost_smallest :: SrcSpan -> SrcSpan -> Ordering -- | Alternative strategies for ordering SrcSpans leftmost_largest :: SrcSpan -> SrcSpan -> Ordering rightmost :: SrcSpan -> SrcSpan -> Ordering -- | Determines whether a span encloses a given line and column index spans :: SrcSpan -> (Int, Int) -> Bool -- | Determines whether a span is enclosed by another one isSubspanOf :: SrcSpan -> SrcSpan -> Bool instance Typeable1 Located instance Eq SrcSpan instance Eq e => Eq (Located e) instance Ord e => Ord (Located e) instance Data e => Data (Located e) instance Outputable e => Outputable (Located e) instance Functor Located instance Outputable SrcSpan instance Ord SrcSpan instance Data SrcSpan instance Typeable SrcSpan instance Outputable SrcLoc instance Ord SrcLoc instance Eq SrcLoc -- | Utilities related to Monad and Applicative classes Mostly for -- backwards compatability. module MonadUtils -- | A functor with application. -- -- Instances should satisfy the following laws: -- -- -- -- The Functor instance should satisfy -- --
--   fmap f x = pure f <*> x
--   
-- -- If f is also a Monad, define pure = -- return and (<*>) = ap. -- -- Minimal complete definition: pure and <*>. class Functor f => Applicative f :: (* -> *) pure :: Applicative f => a -> f a (<*>) :: Applicative f => f (a -> b) -> f a -> f b (*>) :: Applicative f => f a -> f b -> f b (<*) :: Applicative f => f a -> f b -> f a -- | An infix synonym for fmap. (<$>) :: Functor f => (a -> b) -> f a -> f b -- | Monads having fixed points with a 'knot-tying' semantics. Instances of -- MonadFix should satisfy the following laws: -- -- -- -- This class is used in the translation of the recursive do -- notation supported by GHC and Hugs. class Monad m => MonadFix m :: (* -> *) mfix :: MonadFix m => (a -> m a) -> m a class Monad m => MonadIO m liftIO :: MonadIO m => IO a -> m a data ID a runID :: ID a -> a -- | Lift an IO operation with 1 argument into another monad liftIO1 :: MonadIO m => (a -> IO b) -> a -> m b -- | Lift an IO operation with 2 arguments into another monad liftIO2 :: MonadIO m => (a -> b -> IO c) -> a -> b -> m c -- | Lift an IO operation with 3 arguments into another monad liftIO3 :: MonadIO m => (a -> b -> c -> IO d) -> a -> b -> c -> m d -- | Lift an IO operation with 4 arguments into another monad liftIO4 :: MonadIO m => (a -> b -> c -> d -> IO e) -> a -> b -> c -> d -> m e zipWith3M :: Monad m => (a -> b -> c -> m d) -> [a] -> [b] -> [c] -> m [d] -- | The mapAndUnzipM function maps its first argument over a list, -- returning the result as a pair of lists. This function is mainly used -- with complicated data structures or a state-transforming monad. mapAndUnzipM :: Monad m => (a -> m (b, c)) -> [a] -> m ([b], [c]) -- | mapAndUnzipM for triples mapAndUnzip3M :: Monad m => (a -> m (b, c, d)) -> [a] -> m ([b], [c], [d]) mapAndUnzip4M :: Monad m => (a -> m (b, c, d, e)) -> [a] -> m ([b], [c], [d], [e]) -- | Monadic version of mapAccumL mapAccumLM :: Monad m => (acc -> x -> m (acc, y)) -> acc -> [x] -> m (acc, [y]) -- | Monadic version of mapSnd mapSndM :: Monad m => (b -> m c) -> [(a, b)] -> m [(a, c)] -- | Monadic version of concatMap concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b] -- | Monadic version of mapMaybe mapMaybeM :: Monad m => (a -> m (Maybe b)) -> [a] -> m [b] -- | Monadic version of fmap fmapMaybeM :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b) -- | Monadic version of fmap fmapEitherM :: Monad m => (a -> m b) -> (c -> m d) -> Either a c -> m (Either b d) -- | Monadic version of any, aborts the computation at the first -- True value anyM :: Monad m => (a -> m Bool) -> [a] -> m Bool -- | Monad version of all, aborts the computation at the first -- False value allM :: Monad m => (a -> m Bool) -> [a] -> m Bool -- | Monadic version of foldl foldlM :: Monad m => (a -> b -> m a) -> a -> [b] -> m a -- | Monadic version of foldl that discards its result foldlM_ :: Monad m => (a -> b -> m a) -> a -> [b] -> m () -- | Monadic version of foldr foldrM :: Monad m => (b -> a -> m a) -> a -> [b] -> m a -- | Monadic version of fmap specialised for Maybe maybeMapM :: Monad m => (a -> m b) -> (Maybe a -> m (Maybe b)) instance MonadIO IO instance Monad ID module State newtype State s a State :: (s -> (# a, s #)) -> State s a runState' :: State s a -> s -> (# a, s #) get :: State s s gets :: (s -> a) -> State s a put :: s -> State s () modify :: (s -> s) -> State s () evalState :: State s a -> s -> a execState :: State s a -> s -> s runState :: State s a -> s -> (a, s) -- | Monadic version of mapAccumL mapAccumLM :: Monad m => (acc -> x -> m (acc, y)) -> acc -> [x] -> m (acc, [y]) instance Monad (State s) instance Applicative (State s) instance Functor (State s) module UniqSupply -- | A value of type UniqSupply is unique, and it can supply -- one distinct Unique. Also, from the supply, one can also -- manufacture an arbitrary number of further UniqueSupply -- values, which will be distinct from the first and from all others. data UniqSupply -- | Obtain the Unique from this particular UniqSupply uniqFromSupply :: UniqSupply -> Unique -- | Obtain an infinite list of Unique that can be generated by -- constant splitting of the supply uniqsFromSupply :: UniqSupply -> [Unique] -- | Create a unique supply out of thin air. The character given must be -- distinct from those of all calls to this function in the compiler for -- the values generated to be truly unique. mkSplitUniqSupply :: Char -> IO UniqSupply -- | Build two UniqSupply from a single one, each of which can -- supply its own Unique. splitUniqSupply :: UniqSupply -> (UniqSupply, UniqSupply) -- | Create an infinite list of UniqSupply from a single one listSplitUniqSupply :: UniqSupply -> [UniqSupply] -- | A monad which just gives the ability to obtain Uniques data UniqSM result -- | A monad for generating unique identifiers class Monad m => MonadUnique m getUniqueSupplyM :: MonadUnique m => m UniqSupply getUniqueM :: MonadUnique m => m Unique getUniquesM :: MonadUnique m => m [Unique] -- | Run the UniqSM action, returning the final UniqSupply initUs :: UniqSupply -> UniqSM a -> (a, UniqSupply) -- | Run the UniqSM action, discarding the final UniqSupply initUs_ :: UniqSupply -> UniqSM a -> a lazyThenUs :: UniqSM a -> (a -> UniqSM b) -> UniqSM b lazyMapUs :: (a -> UniqSM b) -> [a] -> UniqSM [b] getUniqueUs :: UniqSM Unique getUs :: UniqSM UniqSupply returnUs :: a -> UniqSM a thenUs :: UniqSM a -> (a -> UniqSM b) -> UniqSM b mapUs :: (a -> UniqSM b) -> [a] -> UniqSM [b] instance MonadUnique UniqSM instance MonadFix UniqSM instance Applicative UniqSM instance Functor UniqSM instance Monad UniqSM module Digraph data Graph node graphFromVerticesAndAdjacency :: Ord key => [(node, key)] -> [(key, key)] -> Graph (node, key) graphFromEdgedVertices :: Ord key => [(node, key, [key])] -> Graph (node, key, [key]) data SCC vertex AcyclicSCC :: vertex -> SCC vertex CyclicSCC :: [vertex] -> SCC vertex flattenSCC :: SCC a -> [a] flattenSCCs :: [SCC a] -> [a] stronglyConnCompG :: Graph node -> [SCC node] topologicalSortG :: Graph node -> [node] verticesG :: Graph node -> [node] edgesG :: Graph node -> [Edge node] hasVertexG :: Graph node -> node -> Bool reachableG :: Graph node -> node -> [node] transposeG :: Graph node -> Graph node outdegreeG :: Graph node -> node -> Maybe Int indegreeG :: Graph node -> node -> Maybe Int vertexGroupsG :: Graph node -> [[node]] emptyG :: Graph node -> Bool componentsG :: Graph node -> [[node]] stronglyConnCompFromEdgedVertices :: Ord key => [(node, key, [key])] -> [SCC node] stronglyConnCompFromEdgedVerticesR :: Ord key => [(node, key, [key])] -> [SCC (node, key, [key])] tabulate :: Bounds -> [Vertex] -> Table Int preArr :: Bounds -> Forest Vertex -> Table Int components :: IntGraph -> Forest Vertex undirected :: IntGraph -> IntGraph back :: IntGraph -> Table Int -> IntGraph cross :: IntGraph -> Table Int -> Table Int -> IntGraph forward :: IntGraph -> IntGraph -> Table Int -> IntGraph path :: IntGraph -> Vertex -> Vertex -> Bool bcc :: IntGraph -> Forest [Vertex] do_label :: IntGraph -> Table Int -> Tree Vertex -> Tree (Vertex, Int, Int) bicomps :: Tree (Vertex, Int, Int) -> Forest [Vertex] collect :: Tree (Vertex, Int, Int) -> (Int, Tree [Vertex]) instance Show a => Show (Forest a) instance Show a => Show (Tree a) instance Outputable node => Outputable (Edge node) instance Outputable node => Outputable (Graph node) instance Outputable a => Outputable (SCC a) instance Functor SCC module Bag data Bag a emptyBag :: Bag a unitBag :: a -> Bag a unionBags :: Bag a -> Bag a -> Bag a unionManyBags :: [Bag a] -> Bag a mapBag :: (a -> b) -> Bag a -> Bag b elemBag :: Eq a => a -> Bag a -> Bool lengthBag :: Bag a -> Int filterBag :: (a -> Bool) -> Bag a -> Bag a partitionBag :: (a -> Bool) -> Bag a -> (Bag a, Bag a) partitionBagWith :: (a -> Either b c) -> Bag a -> (Bag b, Bag c) concatBag :: Bag (Bag a) -> Bag a foldBag :: (r -> r -> r) -> (a -> r) -> r -> Bag a -> r foldrBag :: (a -> r -> r) -> r -> Bag a -> r foldlBag :: (r -> a -> r) -> r -> Bag a -> r isEmptyBag :: Bag a -> Bool isSingletonBag :: Bag a -> Bool consBag :: a -> Bag a -> Bag a snocBag :: Bag a -> a -> Bag a anyBag :: (a -> Bool) -> Bag a -> Bool listToBag :: [a] -> Bag a bagToList :: Bag a -> [a] foldlBagM :: Monad m => (b -> a -> m b) -> b -> Bag a -> m b mapBagM :: Monad m => (a -> m b) -> Bag a -> m (Bag b) mapBagM_ :: Monad m => (a -> m b) -> Bag a -> m () flatMapBagM :: Monad m => (a -> m (Bag b)) -> Bag a -> m (Bag b) flatMapBagPairM :: Monad m => (a -> m (Bag b, Bag c)) -> Bag a -> m (Bag b, Bag c) mapAndUnzipBagM :: Monad m => (a -> m (b, c)) -> Bag a -> m (Bag b, Bag c) mapAccumBagLM :: Monad m => (acc -> x -> m (acc, y)) -> acc -> Bag x -> m (acc, Bag y) instance Data a => Data (Bag a) instance Typeable1 Bag instance Outputable a => Outputable (Bag a) module ByteCodeFFI moan64 :: String -> SDoc -> a module DriverPhases data HscSource HsSrcFile :: HscSource HsBootFile :: HscSource ExtCoreFile :: HscSource isHsBoot :: HscSource -> Bool hscSourceString :: HscSource -> String data Phase Unlit :: HscSource -> Phase Cpp :: HscSource -> Phase HsPp :: HscSource -> Phase Hsc :: HscSource -> Phase Ccpp :: Phase Cc :: Phase HCc :: Phase Mangle :: Phase SplitMangle :: Phase SplitAs :: Phase As :: Phase LlvmOpt :: Phase LlvmLlc :: Phase LlvmMangle :: Phase CmmCpp :: Phase Cmm :: Phase StopLn :: Phase happensBefore :: Phase -> Phase -> Bool eqPhase :: Phase -> Phase -> Bool anyHsc :: Phase isStopLn :: Phase -> Bool startPhase :: String -> Phase phaseInputExt :: Phase -> String isHaskellishSuffix :: String -> Bool isHaskellSrcSuffix :: String -> Bool isObjectSuffix :: String -> Bool isCishSuffix :: String -> Bool isExtCoreSuffix :: String -> Bool isDynLibSuffix :: String -> Bool isHaskellUserSrcSuffix :: String -> Bool isSourceSuffix :: String -> Bool isHaskellishFilename :: FilePath -> Bool isHaskellSrcFilename :: FilePath -> Bool isObjectFilename :: FilePath -> Bool isCishFilename :: FilePath -> Bool isExtCoreFilename :: FilePath -> Bool isDynLibFilename :: FilePath -> Bool isHaskellUserSrcFilename :: FilePath -> Bool isSourceFilename :: FilePath -> Bool instance Eq HscSource instance Ord HscSource instance Show HscSource instance Eq Phase instance Show Phase instance Outputable Phase module ListSetOps unionLists :: Eq a => [a] -> [a] -> [a] minusList :: Eq a => [a] -> [a] -> [a] insertList :: Eq a => a -> [a] -> [a] type Assoc a b = [(a, b)] assoc :: Eq a => String -> Assoc a b -> a -> b assocMaybe :: Eq a => Assoc a b -> a -> Maybe b assocUsing :: (a -> a -> Bool) -> String -> Assoc a b -> a -> b assocDefault :: Eq a => b -> Assoc a b -> a -> b assocDefaultUsing :: (a -> a -> Bool) -> b -> Assoc a b -> a -> b emptyAssoc :: Assoc a b unitAssoc :: a -> b -> Assoc a b mapAssoc :: (b -> c) -> Assoc a b -> Assoc a c plusAssoc_C :: Eq a => (b -> b -> b) -> Assoc a b -> Assoc a b -> Assoc a b extendAssoc_C :: Eq a => (b -> b -> b) -> Assoc a b -> (a, b) -> Assoc a b mkLookupFun :: (key -> key -> Bool) -> [(key, val)] -> key -> Maybe val findInList :: (a -> Bool) -> [a] -> Maybe a assocElts :: Assoc a b -> [(a, b)] hasNoDups :: Eq a => [a] -> Bool runs :: (a -> a -> Bool) -> [a] -> [[a]] removeDups :: (a -> a -> Ordering) -> [a] -> ([a], [[a]]) findDupsEq :: (a -> a -> Bool) -> [a] -> [[a]] equivClasses :: (a -> a -> Ordering) -> [a] -> [[a]] equivClassesByUniq :: (a -> Unique) -> [a] -> [[a]] module StackPlacements data SlotSet allStackSlots :: SlotSet data SlotClass SlotClass32 :: SlotClass SlotClass64 :: SlotClass SlotClass128 :: SlotClass slotClassBits :: SlotClass -> Int stackSlot32 :: SlotClass -- | Only supported slot classes stackSlot64 :: SlotClass stackSlot128 :: SlotClass allSlotClasses :: [SlotClass] getStackSlot :: SlotClass -> SlotSet -> (StackPlacement, SlotSet) extendSlotSet :: SlotSet -> StackPlacement -> SlotSet deleteFromSlotSet :: StackPlacement -> SlotSet -> SlotSet elemSlotSet :: StackPlacement -> SlotSet -> Bool chooseSlot :: SlotClass -> [StackPlacement] -> SlotSet -> Maybe (StackPlacement, SlotSet) data StackPlacement FullSlot :: SlotClass -> Int -> StackPlacement YoungHalf :: StackPlacement -> StackPlacement OldHalf :: StackPlacement -> StackPlacement instance Eq SlotClass instance Eq StackPlacement instance Outputable SlotSet instance Outputable StackPlacement instance Outputable SlotClass instance Uniquable SlotClass -- | Basic operations on graphs. module GraphOps -- | Add a node to the graph, linking up its edges addNode :: Uniquable k => k -> Node k cls color -> Graph k cls color -> Graph k cls color -- | Delete a node and all its edges from the graph. delNode :: (Uniquable k, Outputable k) => k -> Graph k cls color -> Maybe (Graph k cls color) -- | Get a node from the graph, throwing an error if it's not there getNode :: Uniquable k => Graph k cls color -> k -> Node k cls color -- | Lookup a node from the graph. lookupNode :: Uniquable k => Graph k cls color -> k -> Maybe (Node k cls color) -- | Modify a node in the graph. returns Nothing if the node isn't present. modNode :: Uniquable k => (Node k cls color -> Node k cls color) -> k -> Graph k cls color -> Maybe (Graph k cls color) -- | Get the size of the graph, O(n) size :: Uniquable k => Graph k cls color -> Int -- | Union two graphs together. union :: Uniquable k => Graph k cls color -> Graph k cls color -> Graph k cls color -- | Add a conflict between nodes to the graph, creating the nodes -- required. Conflicts are virtual regs which need to be colored -- differently. addConflict :: Uniquable k => (k, cls) -> (k, cls) -> Graph k cls color -> Graph k cls color -- | Delete a conflict edge. k1 -> k2 returns Nothing if the node isn't -- in the graph delConflict :: Uniquable k => k -> k -> Graph k cls color -> Maybe (Graph k cls color) -- | Add some conflicts to the graph, creating nodes if required. All the -- nodes in the set are taken to conflict with each other. addConflicts :: Uniquable k => UniqSet k -> (k -> cls) -> Graph k cls color -> Graph k cls color -- | Add a coalescence edge to the graph, creating nodes if requried. It is -- considered adventageous to assign the same color to nodes in a -- coalesence. addCoalesce :: Uniquable k => (k, cls) -> (k, cls) -> Graph k cls color -> Graph k cls color -- | Delete a coalescence edge (k1 -> k2) from the graph. delCoalesce :: Uniquable k => k -> k -> Graph k cls color -> Maybe (Graph k cls color) -- | Add an exclusion to the graph, creating nodes if required. These are -- extra colors that the node cannot use. addExclusion :: (Uniquable k, Uniquable color) => k -> (k -> cls) -> color -> Graph k cls color -> Graph k cls color addExclusions :: (Uniquable k, Uniquable color) => k -> (k -> cls) -> [color] -> Graph k cls color -> Graph k cls color -- | Add a color preference to the graph, creating nodes if required. The -- most recently added preference is the most prefered. The algorithm -- tries to assign a node it's prefered color if possible. addPreference :: Uniquable k => (k, cls) -> color -> Graph k cls color -> Graph k cls color -- | Coalesce this pair of nodes unconditionally / agressively. The -- resulting node is the one with the least key. -- -- returns: Just the pair of keys if the nodes were coalesced the second -- element of the pair being the least one -- -- Nothing if either of the nodes weren't in the graph coalesceNodes :: (Uniquable k, Ord k, Eq cls, Outputable k) => Bool -> Triv k cls color -> Graph k cls color -> (k, k) -> (Graph k cls color, Maybe (k, k)) -- | Do agressive coalescing on this graph. returns the new graph and the -- list of pairs of nodes that got coaleced together. for each pair, the -- resulting node will have the least key and be second in the pair. coalesceGraph :: (Uniquable k, Ord k, Eq cls, Outputable k) => Bool -> Triv k cls color -> Graph k cls color -> (Graph k cls color, [(k, k)]) -- | Freeze a node This is for the iterative coalescer. By freezing a node -- we give up on ever coalescing it. Move all its coalesce edges into the -- frozen set - and update back edges from other nodes. freezeNode :: Uniquable k => k -> Graph k cls color -> Graph k cls color -- | Freeze one node in the graph This if for the iterative coalescer. Look -- for a move related node of low degree and freeze it. -- -- We probably don't need to scan the whole graph looking for the node of -- absolute lowest degree. Just sample the first few and choose the one -- with the lowest degree out of those. Also, we don't make any -- distinction between conflicts of different classes.. this is just a -- heuristic, after all. -- -- IDEA: freezing a node might free it up for Simplify.. would be good to -- check for triv right here, and add it to a worklist if known -- triv/non-move nodes. freezeOneInGraph :: (Uniquable k, Outputable k) => Graph k cls color -> (Graph k cls color, Bool) -- | Freeze all the nodes in the graph for debugging the iterative -- allocator. freezeAllInGraph :: (Uniquable k, Outputable k) => Graph k cls color -> Graph k cls color -- | Find all the nodes in the graph that meet some criteria scanGraph :: Uniquable k => (Node k cls color -> Bool) -> Graph k cls color -> [Node k cls color] -- | Set the color of a certain node setColor :: Uniquable k => k -> color -> Graph k cls color -> Graph k cls color -- | validate the internal structure of a graph all its edges should point -- to valid nodes If they don't then throw an error validateGraph :: (Uniquable k, Outputable k, Eq color) => SDoc -> Bool -> Graph k cls color -> Graph k cls color -- | Slurp out a map of how many nodes had a certain number of conflict -- neighbours slurpNodeConflictCount :: Uniquable k => Graph k cls color -> UniqFM (Int, Int) module HsDoc newtype HsDocString HsDocString :: FastString -> HsDocString type LHsDocString = Located HsDocString ppr_mbDoc :: Maybe LHsDocString -> SDoc instance Typeable HsDocString instance Eq HsDocString instance Show HsDocString instance Data HsDocString instance Outputable HsDocString module Fingerprint data Fingerprint Fingerprint :: {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> Fingerprint fingerprint0 :: Fingerprint readHexFingerprint :: String -> Fingerprint fingerprintData :: Ptr Word8 -> Int -> IO Fingerprint instance Eq Fingerprint instance Ord Fingerprint instance Outputable Fingerprint -- | Pretty printing of graphs. module GraphPpr -- | Pretty print a graph in a somewhat human readable format. dumpGraph :: (Outputable k, Outputable cls, Outputable color) => Graph k cls color -> SDoc -- | Pretty print a graph in graphviz .dot format. Conflicts get solid -- edges. Coalescences get dashed edges. dotGraph :: (Uniquable k, Outputable k, Outputable cls, Outputable color) => (color -> SDoc) -> Triv k cls color -> Graph k cls color -> SDoc -- | Graph Coloring. This is a generic graph coloring library, abstracted -- over the type of the node keys, nodes and colors. module GraphColor -- | Try to color a graph with this set of colors. Uses Chaitin's algorithm -- to color the graph. The graph is scanned for nodes which are deamed -- 'trivially colorable'. These nodes are pushed onto a stack and removed -- from the graph. Once this process is complete the graph can be colored -- by removing nodes from the stack (ie in reverse order) and assigning -- them colors different to their neighbors. colorGraph :: (Uniquable k, Uniquable cls, Uniquable color, Eq color, Eq cls, Ord k, Outputable k, Outputable cls, Outputable color) => Bool -> Int -> UniqFM (UniqSet color) -> Triv k cls color -> (Graph k cls color -> k) -> Graph k cls color -> (Graph k cls color, UniqSet k, UniqFM k) module PPC.Cond data Cond ALWAYS :: Cond EQQ :: Cond GE :: Cond GEU :: Cond GTT :: Cond GU :: Cond LE :: Cond LEU :: Cond LTT :: Cond LU :: Cond NE :: Cond condNegate :: Cond -> Cond condUnsigned :: Cond -> Bool condToSigned :: Cond -> Cond condToUnsigned :: Cond -> Cond instance Eq Cond -- | Bits and pieces on the bottom of the module dependency tree. Also -- import the required constants, so we know what we're using. -- -- In the interests of cross-compilation, we want to free ourselves from -- the autoconf generated modules like main/Constants module SPARC.Base wordLength :: Int wordLengthInBits :: Int spillAreaLength :: Int -- | We need 8 bytes because our largest registers are 64 bit. spillSlotSize :: Int -- | We (allegedly) put the first six C-call arguments in registers; where -- do we start putting the rest of them? extraStackArgsHere :: Int -- | Check whether an offset is representable with 13 bits. fits13Bits :: Integral a => a -> Bool -- | Check whether an integer will fit in 32 bits. A CmmInt is intended to -- be truncated to the appropriate number of bits, so here we truncate it -- to Int64. This is important because e.g. -1 as a CmmInt might be -- either -1 or 18446744073709551615. is32BitInteger :: Integer -> Bool -- | Sadness. largeOffsetError :: Integral a => a -> b module ObjLink initObjLinker :: IO () loadDLL :: String -> IO (Maybe String) loadArchive :: String -> IO () loadObj :: String -> IO () unloadObj :: String -> IO () insertSymbol :: String -> String -> Ptr a -> IO () lookupSymbol :: String -> IO (Maybe (Ptr a)) resolveObjs :: IO SuccessFlag module Ctype is_ident :: Char -> Bool is_symbol :: Char -> Bool is_any :: Char -> Bool is_space :: Char -> Bool is_lower :: Char -> Bool is_upper :: Char -> Bool is_digit :: Char -> Bool is_alphanum :: Char -> Bool is_decdigit :: Char -> Bool is_hexdigit :: Char -> Bool is_octdigit :: Char -> Bool hexDigit :: Char -> Int octDecDigit :: Char -> Int module CmdLineParser processArgs :: Monad m => [Flag m] -> [Located String] -> m ([Located String], [Located String], [Located String]) data OptKind m NoArg :: (EwM m ()) -> OptKind m HasArg :: (String -> EwM m ()) -> OptKind m SepArg :: (String -> EwM m ()) -> OptKind m Prefix :: (String -> EwM m ()) -> OptKind m OptPrefix :: (String -> EwM m ()) -> OptKind m OptIntSuffix :: (Maybe Int -> EwM m ()) -> OptKind m IntSuffix :: (Int -> EwM m ()) -> OptKind m PassFlag :: (String -> EwM m ()) -> OptKind m AnySuffix :: (String -> EwM m ()) -> OptKind m PrefixPred :: (String -> Bool) -> (String -> EwM m ()) -> OptKind m AnySuffixPred :: (String -> Bool) -> (String -> EwM m ()) -> OptKind m newtype CmdLineP s a CmdLineP :: (s -> (a, s)) -> CmdLineP s a runCmdLine :: CmdLineP s a -> s -> (a, s) getCmdLineState :: CmdLineP s s putCmdLineState :: s -> CmdLineP s () data Flag m Flag :: String -> OptKind m -> Flag m flagName :: Flag m -> String flagOptKind :: Flag m -> OptKind m errorsToGhcException :: [Located String] -> GhcException data EwM m a addErr :: Monad m => String -> EwM m () addWarn :: Monad m => String -> EwM m () getArg :: Monad m => EwM m String liftEwM :: Monad m => m a -> EwM m a deprecate :: Monad m => String -> EwM m () instance Monad (CmdLineP s) instance Monad m => Monad (EwM m) module StaticFlagParser -- | Parses GHC's static flags from a list of command line arguments. -- -- These flags are static in the sense that they can be set only once and -- they are global, meaning that they affect every instance of GHC -- running; multiple GHC threads will use the same flags. -- -- This function must be called before any session is started, i.e., -- before the first call to GHC.withGhc. -- -- Static flags are more of a hack and are static for more or less -- historical reasons. In the long run, most static flags should -- eventually become dynamic flags. -- -- XXX: can we add an auto-generated list of static flags here? parseStaticFlags :: [Located String] -> IO ([Located String], [Located String]) module LexCore isNameChar :: Char -> Bool isKeywordChar :: Char -> Bool lexer :: (Token -> P a) -> P a lexChar :: (Token -> String -> Int -> ParseResult a) -> String -> Int -> ParseResult a lexString :: String -> (Token -> [Char] -> Int -> ParseResult a) -> String -> Int -> ParseResult a isHexEscape :: String -> Bool hexToChar :: Char -> Char -> Char lexNum :: (Token -> String -> a) -> String -> a lexName :: (a -> String -> b) -> (String -> a) -> String -> b lexKeyword :: (Token -> [Char] -> Int -> ParseResult a) -> String -> Int -> ParseResult a module Interval data Interval mkInterval :: Int -> Width -> Interval intervalToInfinityFrom :: Int -> Interval integersInInterval :: Interval -> [Int] data DisjointIntervalSet emptyIntervalSet :: DisjointIntervalSet extendIntervalSet :: DisjointIntervalSet -> Interval -> DisjointIntervalSet deleteFromIntervalSet :: DisjointIntervalSet -> Interval -> DisjointIntervalSet subIntervals :: DisjointIntervalSet -> Width -> [Interval] module IOEnv data IOEnv env a failM :: IOEnv env a failWithM :: String -> IOEnv env a data IOEnvFailure IOEnvFailure :: IOEnvFailure getEnv :: IOEnv env env -- | Perform a computation with a different environment setEnv :: env' -> IOEnv env' a -> IOEnv env a -- | Perform a computation with an altered environment updEnv :: (env -> env') -> IOEnv env' a -> IOEnv env a runIOEnv :: env -> IOEnv env a -> IO a unsafeInterleaveM :: IOEnv env a -> IOEnv env a tryM :: IOEnv env r -> IOEnv env (Either IOEnvFailure r) tryAllM :: IOEnv env r -> IOEnv env (Either SomeException r) tryMostM :: IOEnv env r -> IOEnv env (Either SomeException r) fixM :: (a -> IOEnv env a) -> IOEnv env a -- | A mutable variable in the IO monad data IORef a :: * -> * newMutVar :: a -> IOEnv env (IORef a) readMutVar :: IORef a -> IOEnv env a writeMutVar :: IORef a -> a -> IOEnv env () updMutVar :: IORef a -> (a -> a) -> IOEnv env () -- | Atomically update the reference. Does not force the evaluation of the -- new variable contents. For strict update, use atomicUpdMutVar'. atomicUpdMutVar :: IORef a -> (a -> (a, b)) -> IOEnv env b -- | Strict variant of atomicUpdMutVar. atomicUpdMutVar' :: IORef a -> (a -> (a, b)) -> IOEnv env b instance Typeable IOEnvFailure instance MonadIO (IOEnv env) instance MonadPlus IO => MonadPlus (IOEnv env) instance Exception IOEnvFailure instance Show IOEnvFailure instance Functor (IOEnv m) instance Applicative (IOEnv m) instance Monad (IOEnv m) module Binary data Bin a class Binary a put_ :: Binary a => BinHandle -> a -> IO () put :: Binary a => BinHandle -> a -> IO (Bin a) get :: Binary a => BinHandle -> IO a data BinHandle openBinIO :: Handle -> IO BinHandle openBinIO_ :: Handle -> IO BinHandle openBinMem :: Int -> IO BinHandle seekBin :: BinHandle -> Bin a -> IO () seekBy :: BinHandle -> Int -> IO () tellBin :: BinHandle -> IO (Bin a) castBin :: Bin a -> Bin b writeBinMem :: BinHandle -> FilePath -> IO () readBinMem :: FilePath -> IO BinHandle fingerprintBinMem :: BinHandle -> IO Fingerprint isEOFBin :: BinHandle -> IO Bool putAt :: Binary a => BinHandle -> Bin a -> a -> IO () getAt :: Binary a => BinHandle -> Bin a -> IO a putByte :: BinHandle -> Word8 -> IO () getByte :: BinHandle -> IO Word8 lazyGet :: Binary a => BinHandle -> IO a lazyPut :: Binary a => BinHandle -> a -> IO () data ByteArray BA :: ByteArray# -> ByteArray getByteArray :: BinHandle -> Int -> IO ByteArray putByteArray :: BinHandle -> ByteArray# -> Int# -> IO () data UserData UserData :: Dictionary -> SymbolTable -> (BinHandle -> Name -> IO ()) -> (BinHandle -> FastString -> IO ()) -> UserData ud_dict :: UserData -> Dictionary ud_symtab :: UserData -> SymbolTable ud_put_name :: UserData -> BinHandle -> Name -> IO () ud_put_fs :: UserData -> BinHandle -> FastString -> IO () getUserData :: BinHandle -> UserData setUserData :: BinHandle -> UserData -> BinHandle newReadState :: Dictionary -> IO UserData newWriteState :: (BinHandle -> Name -> IO ()) -> (BinHandle -> FastString -> IO ()) -> IO UserData putDictionary :: BinHandle -> Int -> UniqFM (Int, FastString) -> IO () getDictionary :: BinHandle -> IO Dictionary putFS :: BinHandle -> FastString -> IO () instance Eq (Bin a) instance Ord (Bin a) instance Show (Bin a) instance Bounded (Bin a) instance Binary FunctionOrData instance Binary Fingerprint instance Binary FastString instance Binary TypeRep instance Binary TyCon instance Binary (Bin a) instance (Integral a, Binary a) => Binary (Ratio a) instance Binary Integer instance (Binary a, Binary b) => Binary (Either a b) instance Binary a => Binary (Maybe a) instance (Binary a, Binary b, Binary c, Binary d) => Binary (a, b, c, d) instance (Binary a, Binary b, Binary c) => Binary (a, b, c) instance (Binary a, Binary b) => Binary (a, b) instance Binary a => Binary [a] instance Binary Int instance Binary Char instance Binary Bool instance Binary () instance Binary Int64 instance Binary Int32 instance Binary Int16 instance Binary Int8 instance Binary Word64 instance Binary Word32 instance Binary Word16 instance Binary Word8 -- | GHC uses several kinds of name internally: -- -- module OccName data NameSpace tcName :: NameSpace clsName :: NameSpace tcClsName :: NameSpace dataName :: NameSpace varName :: NameSpace tvName :: NameSpace srcDataName :: NameSpace pprNameSpace :: NameSpace -> SDoc pprNonVarNameSpace :: NameSpace -> SDoc pprNameSpaceBrief :: NameSpace -> SDoc data OccName pprOccName :: OccName -> SDoc mkOccName :: NameSpace -> String -> OccName mkOccNameFS :: NameSpace -> FastString -> OccName mkVarOcc :: String -> OccName mkVarOccFS :: FastString -> OccName mkDataOcc :: String -> OccName mkDataOccFS :: FastString -> OccName mkTyVarOcc :: String -> OccName mkTyVarOccFS :: FastString -> OccName mkTcOcc :: String -> OccName mkTcOccFS :: FastString -> OccName mkClsOcc :: String -> OccName mkClsOccFS :: FastString -> OccName mkDFunOcc :: String -> Bool -> OccSet -> OccName mkTupleOcc :: NameSpace -> Boxity -> Arity -> OccName setOccNameSpace :: NameSpace -> OccName -> OccName isDerivedOccName :: OccName -> Bool mkDataConWrapperOcc :: OccName -> OccName mkWorkerOcc :: OccName -> OccName mkDefaultMethodOcc :: OccName -> OccName mkDerivedTyConOcc :: OccName -> OccName mkNewTyCoOcc :: OccName -> OccName mkClassOpAuxOcc :: OccName -> OccName mkCon2TagOcc :: OccName -> OccName mkTag2ConOcc :: OccName -> OccName mkMaxTagOcc :: OccName -> OccName mkClassTyConOcc :: OccName -> OccName mkClassDataConOcc :: OccName -> OccName mkDictOcc :: OccName -> OccName mkIPOcc :: OccName -> OccName mkSpecOcc :: OccName -> OccName mkForeignExportOcc :: OccName -> OccName mkGenOcc1 :: OccName -> OccName mkGenOcc2 :: OccName -> OccName mkDataTOcc :: OccName -> OccName mkDataCOcc :: OccName -> OccName mkDataConWorkerOcc :: OccName -> OccName mkSuperDictSelOcc :: Int -> OccName -> OccName mkLocalOcc :: Unique -> OccName -> OccName mkMethodOcc :: OccName -> OccName -- | Derive a name for the representation type constructor of a -- data/newtype instance. mkInstTyTcOcc :: String -> OccSet -> OccName mkInstTyCoOcc :: OccName -> OccName mkEqPredCoOcc :: OccName -> OccName mkVectOcc :: OccName -> OccName mkVectTyConOcc :: OccName -> OccName mkVectDataConOcc :: OccName -> OccName mkVectIsoOcc :: OccName -> OccName mkPDataTyConOcc :: OccName -> OccName mkPDataDataConOcc :: OccName -> OccName mkPReprTyConOcc :: OccName -> OccName mkPADFunOcc :: OccName -> OccName occNameFS :: OccName -> FastString occNameString :: OccName -> String occNameSpace :: OccName -> NameSpace isVarOcc :: OccName -> Bool isTvOcc :: OccName -> Bool isTcOcc :: OccName -> Bool isDataOcc :: OccName -> Bool -- | Test if the OccName is a data constructor that starts with a -- symbol (e.g. :, or []) isDataSymOcc :: OccName -> Bool -- | Test if the OccName is that for any operator (whether it is a -- data constructor or variable or whatever) isSymOcc :: OccName -> Bool -- | Value OccNamess are those that are either in the -- variable or data constructor namespaces isValOcc :: OccName -> Bool -- | Wrap parens around an operator parenSymOcc :: OccName -> SDoc -> SDoc -- | Haskell 98 encourages compilers to suppress warnings about unsed names -- in a pattern if they start with _: this implements that test startsWithUnderscore :: OccName -> Bool isTcClsNameSpace :: NameSpace -> Bool isTvNameSpace :: NameSpace -> Bool isDataConNameSpace :: NameSpace -> Bool isVarNameSpace :: NameSpace -> Bool isValNameSpace :: NameSpace -> Bool isTupleOcc_maybe :: OccName -> Maybe (NameSpace, Boxity, Arity) data OccEnv a emptyOccEnv :: OccEnv a unitOccEnv :: OccName -> a -> OccEnv a extendOccEnv :: OccEnv a -> OccName -> a -> OccEnv a mapOccEnv :: (a -> b) -> OccEnv a -> OccEnv b lookupOccEnv :: OccEnv a -> OccName -> Maybe a mkOccEnv :: [(OccName, a)] -> OccEnv a mkOccEnv_C :: (a -> a -> a) -> [(OccName, a)] -> OccEnv a extendOccEnvList :: OccEnv a -> [(OccName, a)] -> OccEnv a elemOccEnv :: OccName -> OccEnv a -> Bool occEnvElts :: OccEnv a -> [a] foldOccEnv :: (a -> b -> b) -> b -> OccEnv a -> b plusOccEnv :: OccEnv a -> OccEnv a -> OccEnv a plusOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccEnv a -> OccEnv a extendOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccName -> a -> OccEnv a extendOccEnv_Acc :: (a -> b -> b) -> (a -> b) -> OccEnv b -> OccName -> a -> OccEnv b filterOccEnv :: (elt -> Bool) -> OccEnv elt -> OccEnv elt delListFromOccEnv :: OccEnv a -> [OccName] -> OccEnv a delFromOccEnv :: OccEnv a -> OccName -> OccEnv a type OccSet = UniqSet OccName emptyOccSet :: OccSet unitOccSet :: OccName -> OccSet mkOccSet :: [OccName] -> OccSet extendOccSet :: OccSet -> OccName -> OccSet extendOccSetList :: OccSet -> [OccName] -> OccSet unionOccSets :: OccSet -> OccSet -> OccSet unionManyOccSets :: [OccSet] -> OccSet minusOccSet :: OccSet -> OccSet -> OccSet elemOccSet :: OccName -> OccSet -> Bool occSetElts :: OccSet -> [OccName] foldOccSet :: (OccName -> b -> b) -> b -> OccSet -> b isEmptyOccSet :: OccSet -> Bool intersectOccSet :: OccSet -> OccSet -> OccSet intersectsOccSet :: OccSet -> OccSet -> Bool type TidyOccEnv = OccEnv Int emptyTidyOccEnv :: TidyOccEnv tidyOccName :: TidyOccEnv -> OccName -> (TidyOccEnv, OccName) initTidyOccEnv :: [OccName] -> TidyOccEnv isLexCon :: FastString -> Bool isLexVar :: FastString -> Bool isLexId :: FastString -> Bool isLexSym :: FastString -> Bool isLexConId :: FastString -> Bool isLexConSym :: FastString -> Bool isLexVarId :: FastString -> Bool isLexVarSym :: FastString -> Bool startsVarSym :: Char -> Bool startsVarId :: Char -> Bool startsConSym :: Char -> Bool startsConId :: Char -> Bool instance Eq NameSpace instance Ord NameSpace instance Binary OccName instance Binary NameSpace instance Outputable a => Outputable (OccEnv a) instance Uniquable OccName instance Outputable OccName instance Data OccName instance Typeable OccName instance Ord OccName instance Eq OccName module Module -- | A ModuleName is essentially a simple string, e.g. Data.List. data ModuleName pprModuleName :: ModuleName -> SDoc moduleNameFS :: ModuleName -> FastString moduleNameString :: ModuleName -> String -- | Returns the string version of the module name, with dots replaced by -- slashes moduleNameSlashes :: ModuleName -> String mkModuleName :: String -> ModuleName mkModuleNameFS :: FastString -> ModuleName -- | Compares module names lexically, rather than by their Uniques stableModuleNameCmp :: ModuleName -> ModuleName -> Ordering -- | Essentially just a string identifying a package, including the -- version: e.g. parsec-1.0 data PackageId fsToPackageId :: FastString -> PackageId packageIdFS :: PackageId -> FastString stringToPackageId :: String -> PackageId packageIdString :: PackageId -> String -- | Compares package ids lexically, rather than by their Uniques stablePackageIdCmp :: PackageId -> PackageId -> Ordering primPackageId :: PackageId integerPackageId :: PackageId basePackageId :: PackageId rtsPackageId :: PackageId thPackageId :: PackageId dphSeqPackageId :: PackageId dphParPackageId :: PackageId mainPackageId :: PackageId -- | A Module is a pair of a PackageId and a ModuleName. data Module modulePackageId :: Module -> PackageId moduleName :: Module -> ModuleName pprModule :: Module -> SDoc mkModule :: PackageId -> ModuleName -> Module -- | This gives a stable ordering, as opposed to the Ord instance which -- gives an ordering based on the Uniques of the components, which -- may not be stable from run to run of the compiler. stableModuleCmp :: Module -> Module -> Ordering -- | Where a module lives on the file system: the actual locations of the -- .hs, .hi and .o files, if we have them data ModLocation ModLocation :: Maybe FilePath -> FilePath -> FilePath -> ModLocation ml_hs_file :: ModLocation -> Maybe FilePath ml_hi_file :: ModLocation -> FilePath ml_obj_file :: ModLocation -> FilePath -- | Add the -boot suffix to .hs, .hi and .o files addBootSuffix :: FilePath -> FilePath -- | Add the -boot suffix if the Bool argument is -- True addBootSuffix_maybe :: Bool -> FilePath -> FilePath -- | Add the -boot suffix to all file paths associated with the -- module addBootSuffixLocn :: ModLocation -> ModLocation -- | This is the package Id for the current program. It is the default -- package Id if you don't specify a package name. We don't add this -- prefix to symbol names, since there can be only one main package per -- program. -- -- A map keyed off of Modules data ModuleEnv elt elemModuleEnv :: Module -> ModuleEnv a -> Bool extendModuleEnv :: ModuleEnv a -> Module -> a -> ModuleEnv a extendModuleEnvList :: ModuleEnv a -> [(Module, a)] -> ModuleEnv a extendModuleEnvList_C :: (a -> a -> a) -> ModuleEnv a -> [(Module, a)] -> ModuleEnv a plusModuleEnv_C :: (a -> a -> a) -> ModuleEnv a -> ModuleEnv a -> ModuleEnv a delModuleEnvList :: ModuleEnv a -> [Module] -> ModuleEnv a delModuleEnv :: ModuleEnv a -> Module -> ModuleEnv a plusModuleEnv :: ModuleEnv a -> ModuleEnv a -> ModuleEnv a lookupModuleEnv :: ModuleEnv a -> Module -> Maybe a lookupWithDefaultModuleEnv :: ModuleEnv a -> a -> Module -> a mapModuleEnv :: (a -> b) -> ModuleEnv a -> ModuleEnv b mkModuleEnv :: [(Module, a)] -> ModuleEnv a emptyModuleEnv :: ModuleEnv a moduleEnvKeys :: ModuleEnv a -> [Module] moduleEnvElts :: ModuleEnv a -> [a] moduleEnvToList :: ModuleEnv a -> [(Module, a)] unitModuleEnv :: Module -> a -> ModuleEnv a isEmptyModuleEnv :: ModuleEnv a -> Bool foldModuleEnv :: (a -> b -> b) -> b -> ModuleEnv a -> b extendModuleEnvWith :: (a -> a -> a) -> ModuleEnv a -> Module -> a -> ModuleEnv a filterModuleEnv :: (Module -> a -> Bool) -> ModuleEnv a -> ModuleEnv a -- | A map keyed off of ModuleNames (actually, their Uniques) type ModuleNameEnv elt = UniqFM elt -- | A set of Modules type ModuleSet = Map Module () emptyModuleSet :: ModuleSet mkModuleSet :: [Module] -> ModuleSet moduleSetElts :: ModuleSet -> [Module] extendModuleSet :: ModuleSet -> Module -> ModuleSet elemModuleSet :: Module -> ModuleSet -> Bool instance Show ModLocation instance Eq PackageId instance Eq Module instance Ord Module instance Binary PackageId instance Outputable PackageId instance Data PackageId instance Typeable PackageId instance Ord PackageId instance Uniquable PackageId instance Data Module instance Typeable Module instance Binary Module instance Outputable Module instance Uniquable Module instance Data ModuleName instance Typeable ModuleName instance Binary ModuleName instance Outputable ModuleName instance Ord ModuleName instance Eq ModuleName instance Uniquable ModuleName instance Outputable ModLocation -- | Package configuration information: essentially the interface to Cabal, -- with some utilities module PackageConfig -- | Turn a Cabal PackageIdentifier into a GHC PackageId mkPackageId :: PackageIdentifier -> PackageId -- | Get the GHC PackageId right out of a Cabalish -- PackageConfig packageConfigId :: PackageConfig -> PackageId type PackageConfig = InstalledPackageInfo_ ModuleName data InstalledPackageInfo_ m :: * -> * InstalledPackageInfo :: InstalledPackageId -> PackageId -> License -> String -> String -> String -> String -> String -> String -> String -> String -> Bool -> [m] -> [m] -> [FilePath] -> [FilePath] -> [String] -> [String] -> [String] -> [FilePath] -> [String] -> [InstalledPackageId] -> [String] -> [String] -> [String] -> [FilePath] -> [String] -> [FilePath] -> [FilePath] -> InstalledPackageInfo_ m installedPackageId :: InstalledPackageInfo_ m -> InstalledPackageId sourcePackageId :: InstalledPackageInfo_ m -> PackageId license :: InstalledPackageInfo_ m -> License copyright :: InstalledPackageInfo_ m -> String maintainer :: InstalledPackageInfo_ m -> String author :: InstalledPackageInfo_ m -> String stability :: InstalledPackageInfo_ m -> String homepage :: InstalledPackageInfo_ m -> String pkgUrl :: InstalledPackageInfo_ m -> String description :: InstalledPackageInfo_ m -> String category :: InstalledPackageInfo_ m -> String exposed :: InstalledPackageInfo_ m -> Bool exposedModules :: InstalledPackageInfo_ m -> [m] hiddenModules :: InstalledPackageInfo_ m -> [m] importDirs :: InstalledPackageInfo_ m -> [FilePath] libraryDirs :: InstalledPackageInfo_ m -> [FilePath] hsLibraries :: InstalledPackageInfo_ m -> [String] extraLibraries :: InstalledPackageInfo_ m -> [String] extraGHCiLibraries :: InstalledPackageInfo_ m -> [String] includeDirs :: InstalledPackageInfo_ m -> [FilePath] includes :: InstalledPackageInfo_ m -> [String] depends :: InstalledPackageInfo_ m -> [InstalledPackageId] hugsOptions :: InstalledPackageInfo_ m -> [String] ccOptions :: InstalledPackageInfo_ m -> [String] ldOptions :: InstalledPackageInfo_ m -> [String] frameworkDirs :: InstalledPackageInfo_ m -> [FilePath] frameworks :: InstalledPackageInfo_ m -> [String] haddockInterfaces :: InstalledPackageInfo_ m -> [FilePath] haddockHTMLs :: InstalledPackageInfo_ m -> [FilePath] display :: Text a => a -> String -- | A Version represents the version of a software entity. -- -- An instance of Eq is provided, which implements exact equality -- modulo reordering of the tags in the versionTags field. -- -- An instance of Ord is also provided, which gives lexicographic -- ordering on the versionBranch fields (i.e. 2.1 > 2.0, 1.2.3 -- > 1.2.2, etc.). This is expected to be sufficient for many uses, -- but note that you may need to use a more specific ordering for your -- versioning scheme. For example, some versioning schemes may include -- pre-releases which have tags "pre1", "pre2", and so -- on, and these would need to be taken into account when determining -- ordering. In some cases, date ordering may be more appropriate, so the -- application would have to look for date tags in the -- versionTags field and compare those. The bottom line is, don't -- always assume that compare and other Ord operations are -- the right thing for every Version. -- -- Similarly, concrete representations of versions may differ. One -- possible concrete representation is provided (see showVersion -- and parseVersion), but depending on the application a different -- concrete representation may be more appropriate. data Version :: * Version :: [Int] -> [String] -> Version -- | The numeric branch for this version. This reflects the fact that most -- software versions are tree-structured; there is a main trunk which is -- tagged with versions at various points (1,2,3...), and the first -- branch off the trunk after version 3 is 3.1, the second branch off the -- trunk after version 3 is 3.2, and so on. The tree can be branched -- arbitrarily, just by adding more digits. -- -- We represent the branch as a list of Int, so version 3.2.1 -- becomes [3,2,1]. Lexicographic ordering (i.e. the default instance of -- Ord for [Int]) gives the natural ordering of branches. versionBranch :: Version -> [Int] -- | A version can be tagged with an arbitrary list of strings. The -- interpretation of the list of tags is entirely dependent on the entity -- that this version applies to. versionTags :: Version -> [String] -- | The name and version of a package. data PackageIdentifier :: * PackageIdentifier :: PackageName -> Version -> PackageIdentifier -- | The name of this package, eg. foo pkgName :: PackageIdentifier -> PackageName -- | the version of this package, eg 1.2 pkgVersion :: PackageIdentifier -> Version defaultPackageConfig :: PackageConfig -- | Turn a PackageConfig, which contains GHC ModuleNames -- into a Cabal specific InstalledPackageInfo which contains Cabal -- ModuleNames packageConfigToInstalledPackageInfo :: PackageConfig -> InstalledPackageInfo -- | Turn an InstalledPackageInfo, which contains Cabal -- ModuleNames into a GHC specific PackageConfig which -- contains GHC ModuleNames installedPackageInfoToPackageConfig :: InstalledPackageInfo_ String -> PackageConfig module HsImpExp type LImportDecl name = Located (ImportDecl name) -- | A single Haskell import declaration. data ImportDecl name ImportDecl :: Located ModuleName -> Maybe FastString -> Bool -> Bool -> Maybe ModuleName -> Maybe (Bool, [LIE name]) -> ImportDecl name -- | Module name. ideclName :: ImportDecl name -> Located ModuleName -- | Package qualifier. ideclPkgQual :: ImportDecl name -> Maybe FastString -- | True = {--} import ideclSource :: ImportDecl name -> Bool -- | True => qualified ideclQualified :: ImportDecl name -> Bool -- | as Module ideclAs :: ImportDecl name -> Maybe ModuleName -- | (True => hiding, names) ideclHiding :: ImportDecl name -> Maybe (Bool, [LIE name]) type LIE name = Located (IE name) -- | Imported or exported entity. data IE name IEVar :: name -> IE name -- | Class/Type (can't tell) IEThingAbs :: name -> IE name -- | ClassType plus all methodsconstructors IEThingAll :: name -> IE name -- | ClassType plus some methodsconstructors IEThingWith :: name -> [name] -> IE name -- | (Export Only) IEModuleContents :: ModuleName -> IE name -- | Doc section heading IEGroup :: Int -> HsDocString -> IE name -- | Some documentation IEDoc :: HsDocString -> IE name -- | Reference to named doc IEDocNamed :: String -> IE name ieName :: IE name -> name ieNames :: IE a -> [a] instance Typeable1 IE instance Typeable1 ImportDecl instance Data name => Data (IE name) instance Data name => Data (ImportDecl name) instance Outputable name => Outputable (IE name) instance Outputable name => Outputable (ImportDecl name) -- | Modules that contain builtin functions used by the vectoriser. module Vectorise.Builtins.Modules -- | Ids of the modules that contain our DPH builtins. data Modules Modules :: Module -> Module -> Module -> Module -> Module -> Module -> Module -> Module -> Module -> Module -> Module -> Module -> Module -> Modules dph_PArray :: Modules -> Module dph_Repr :: Modules -> Module dph_Closure :: Modules -> Module dph_Unboxed :: Modules -> Module dph_Instances :: Modules -> Module dph_Combinators :: Modules -> Module dph_Scalar :: Modules -> Module dph_Prelude_PArr :: Modules -> Module dph_Prelude_Int :: Modules -> Module dph_Prelude_Word8 :: Modules -> Module dph_Prelude_Double :: Modules -> Module dph_Prelude_Bool :: Modules -> Module dph_Prelude_Tuple :: Modules -> Module -- | The locations of builtins in the current DPH library. dph_Modules :: PackageId -> Modules -- | Project out ids of modules that contain orphan instances that we need -- to load. dph_Orphans :: [Modules -> Module] module ForeignCall newtype ForeignCall CCall :: CCallSpec -> ForeignCall data Safety PlaySafe :: Bool -> Safety PlayRisky :: Safety playSafe :: Safety -> Bool data CExportSpec CExportStatic :: CLabelString -> CCallConv -> CExportSpec type CLabelString = FastString isCLabelString :: CLabelString -> Bool pprCLabelString :: CLabelString -> SDoc data CCallSpec CCallSpec :: CCallTarget -> CCallConv -> Safety -> CCallSpec -- | How to call a particular function in C-land. data CCallTarget StaticTarget :: CLabelString -> (Maybe PackageId) -> CCallTarget DynamicTarget :: CCallTarget isDynamicTarget :: CCallTarget -> Bool data CCallConv CCallConv :: CCallConv StdCallConv :: CCallConv CmmCallConv :: CCallConv PrimCallConv :: CCallConv defaultCCallConv :: CCallConv ccallConvToInt :: CCallConv -> Int ccallConvAttribute :: CCallConv -> String instance Typeable Safety instance Typeable CCallConv instance Typeable CCallTarget instance Typeable CExportSpec instance Eq Safety instance Show Safety instance Data Safety instance Eq CCallConv instance Data CCallConv instance Eq CCallTarget instance Data CCallTarget instance Eq CCallSpec instance Eq ForeignCall instance Data CExportSpec instance Binary CCallConv instance Binary CCallTarget instance Binary CCallSpec instance Binary CExportSpec instance Binary Safety instance Binary ForeignCall instance Outputable CCallSpec instance Outputable CExportSpec instance Outputable CCallConv instance Outputable Safety instance Outputable ForeignCall module Serialized -- | Represents a serialized value of a particular type. Attempts can be -- made to deserialize it at certain types data Serialized -- | Force the contents of the Serialized value so weknow it doesn't -- contain any bottoms seqSerialized :: Serialized -> () -- | Put a Typeable value that we are able to actually turn into bytes into -- a Serialized value ready for deserialization later toSerialized :: Typeable a => (a -> [Word8]) -> a -> Serialized -- | If the Serialized value contains something of the given type, -- then use the specified deserializer to return Just that. -- Otherwise return Nothing. fromSerialized :: Typeable a => ([Word8] -> a) -> Serialized -> Maybe a -- | Use a Data instance to implement a serialization scheme dual to -- that of deserializeWithData serializeWithData :: Data a => a -> [Word8] -- | Use a Data instance to implement a deserialization scheme dual -- to that of serializeWithData deserializeWithData :: Data a => [Word8] -> a instance Binary Serialized instance Outputable Serialized -- | GHC uses several kinds of name internally: -- -- -- -- Names are one of: -- -- module Name -- | A unique, unambigious name for something, containing information about -- where that thing originated. data Name -- | BuiltInSyntax is for things like (:), [] and tuples, -- which have special syntactic forms. They aren't in scope as such. data BuiltInSyntax BuiltInSyntax :: BuiltInSyntax UserSyntax :: BuiltInSyntax -- | Create a name which is (for now at least) local to the current module -- and hence does not need a Module to disambiguate it from other -- Names mkInternalName :: Unique -> OccName -> SrcSpan -> Name -- | Create a name brought into being by the compiler mkSystemName :: Unique -> OccName -> Name mkDerivedInternalName :: (OccName -> OccName) -> Unique -> Name -> Name mkSystemVarName :: Unique -> FastString -> Name mkSysTvName :: Unique -> FastString -> Name -- | Make a name for a foreign call mkFCallName :: Unique -> String -> Name -- | Make the name of an implicit parameter mkIPName :: Unique -> OccName -> Name mkTickBoxOpName :: Unique -> String -> Name -- | Create a name which definitely originates in the given module mkExternalName :: Unique -> Module -> OccName -> SrcSpan -> Name -- | Create a name which is actually defined by the compiler itself mkWiredInName :: Module -> OccName -> Unique -> TyThing -> BuiltInSyntax -> Name nameUnique :: Name -> Unique setNameUnique :: Name -> Unique -> Name nameOccName :: Name -> OccName nameModule :: Name -> Module nameModule_maybe :: Name -> Maybe Module tidyNameOcc :: Name -> OccName -> Name hashName :: Name -> Int -- | Make the Name into an internal name, regardless of what it was -- to begin with localiseName :: Name -> Name nameSrcLoc :: Name -> SrcLoc nameSrcSpan :: Name -> SrcSpan pprNameLoc :: Name -> SDoc isSystemName :: Name -> Bool isInternalName :: Name -> Bool isExternalName :: Name -> Bool isTyVarName :: Name -> Bool isTyConName :: Name -> Bool isDataConName :: Name -> Bool isValName :: Name -> Bool isVarName :: Name -> Bool isWiredInName :: Name -> Bool isBuiltInSyntax :: Name -> Bool wiredInNameTyThing_maybe :: Name -> Maybe TyThing nameIsLocalOrFrom :: Module -> Name -> Bool -- | A class allowing convenient access to the Name of various -- datatypes class NamedThing a getOccName :: NamedThing a => a -> OccName getName :: NamedThing a => a -> Name getSrcLoc :: NamedThing a => a -> SrcLoc getSrcSpan :: NamedThing a => a -> SrcSpan getOccString :: NamedThing a => a -> String pprInfixName :: (Outputable a, NamedThing a) => a -> SDoc pprPrefixName :: (Outputable a, NamedThing a) => a -> SDoc pprModulePrefix :: PprStyle -> Module -> OccName -> SDoc instance OutputableBndr Name instance Outputable Name instance Binary Name instance Data Name instance Typeable Name instance NamedThing Name instance Uniquable Name instance Ord Name instance Eq Name -- | GHC uses several kinds of name internally: -- -- -- -- Global Ids and Vars are those that are imported or -- correspond to a data constructor, primitive operation, or record -- selectors. Local Ids and Vars are those bound within an -- expression (e.g. by a lambda) or at the top level of the module being -- compiled. module Var -- | Essentially a typed Name, that may also contain some additional -- information about the Var and it's use sites. data Var type TyVar = Var type CoVar = TyVar type Id = Var type DictId = EvId type DFunId = Id type EvVar = Var type EvId = Id type IpId = EvId varName :: Var -> Name varUnique :: Var -> Unique varType :: Var -> Kind setVarName :: Var -> Name -> Var setVarUnique :: Var -> Unique -> Var setVarType :: Id -> Type -> Id mkGlobalVar :: IdDetails -> Name -> Type -> IdInfo -> Id mkLocalVar :: IdDetails -> Name -> Type -> IdInfo -> Id -- | Exported Vars will not be removed as dead code mkExportedLocalVar :: IdDetails -> Name -> Type -> IdInfo -> Id idInfo :: Id -> IdInfo idDetails :: Id -> IdDetails lazySetIdInfo :: Id -> IdInfo -> Var setIdDetails :: Id -> IdDetails -> Id -- | If it's a local, make it global globaliseId :: Id -> Id -- | Exports the given local Id. Can also be called on global -- Ids, such as data constructors and class operations, which are -- born as global Ids and automatically exported setIdExported :: Id -> Id -- | We can only do this to LocalIds setIdNotExported :: Id -> Id isCoVar :: Var -> Bool isId :: Var -> Bool isTyCoVar :: Var -> Bool isTyVar :: Var -> Bool isTcTyVar :: Var -> Bool -- | isLocalVar returns True for type variables as well as -- local Ids These are the variables that we need to pay attention -- to when finding free variables, or doing dependency analysis. isLocalVar :: Var -> Bool isLocalId :: Var -> Bool isGlobalId :: Var -> Bool -- | isExportedIdVar means "don't throw this away" isExportedId :: Var -> Bool -- | mustHaveLocalBinding returns True of Ids and -- TyVars that must have a binding in this module. The converse is -- not quite right: there are some global Ids that must have -- bindings, such as record selectors. But that doesn't matter, because -- it's only used for assertions mustHaveLocalBinding :: Var -> Bool mkTyVar :: Name -> Kind -> TyVar mkTcTyVar :: Name -> Kind -> TcTyVarDetails -> TyVar -- | Create a type variable that is never referred to, so its unique -- doesn't matter mkWildCoVar :: Kind -> TyVar tyVarName :: TyVar -> Name tyVarKind :: TyVar -> Kind tcTyVarDetails :: TyVar -> TcTyVarDetails setTcTyVarDetails :: TyVar -> TcTyVarDetails -> TyVar setTyVarName :: TyVar -> Name -> TyVar setTyVarUnique :: TyVar -> Unique -> TyVar setTyVarKind :: TyVar -> Kind -> TyVar mkCoVar :: Name -> Kind -> CoVar coVarName :: CoVar -> Name setCoVarUnique :: CoVar -> Unique -> CoVar setCoVarName :: CoVar -> Name -> CoVar instance Data Var instance Typeable Var instance Ord Var instance Eq Var instance Uniquable Var instance NamedThing Var instance Show Var instance Outputable Var module VarSet type VarSet = UniqSet Var type IdSet = UniqSet Id type TyVarSet = UniqSet TyVar emptyVarSet :: VarSet unitVarSet :: Var -> VarSet mkVarSet :: [Var] -> VarSet extendVarSet :: VarSet -> Var -> VarSet extendVarSetList :: VarSet -> [Var] -> VarSet extendVarSet_C :: (Var -> Var -> Var) -> VarSet -> Var -> VarSet elemVarSet :: Var -> VarSet -> Bool varSetElems :: VarSet -> [Var] subVarSet :: VarSet -> VarSet -> Bool unionVarSet :: VarSet -> VarSet -> VarSet unionVarSets :: [VarSet] -> VarSet intersectVarSet :: VarSet -> VarSet -> VarSet intersectsVarSet :: VarSet -> VarSet -> Bool disjointVarSet :: VarSet -> VarSet -> Bool isEmptyVarSet :: VarSet -> Bool delVarSet :: VarSet -> Var -> VarSet delVarSetList :: VarSet -> [Var] -> VarSet delVarSetByKey :: VarSet -> Unique -> VarSet minusVarSet :: VarSet -> VarSet -> VarSet foldVarSet :: (Var -> a -> a) -> a -> VarSet -> a filterVarSet :: (Var -> Bool) -> VarSet -> VarSet fixVarSet :: (VarSet -> VarSet) -> VarSet -> VarSet lookupVarSet :: VarSet -> Var -> Maybe Var mapVarSet :: (Var -> Var) -> VarSet -> VarSet sizeVarSet :: VarSet -> Int seqVarSet :: VarSet -> () elemVarSetByKey :: Unique -> VarSet -> Bool module VarEnv type VarEnv elt = UniqFM elt type IdEnv elt = VarEnv elt type TyVarEnv elt = VarEnv elt emptyVarEnv :: VarEnv a unitVarEnv :: Var -> a -> VarEnv a mkVarEnv :: [(Var, a)] -> VarEnv a elemVarEnv :: Var -> VarEnv a -> Bool varEnvElts :: VarEnv a -> [a] varEnvKeys :: VarEnv a -> [Unique] extendVarEnv :: VarEnv a -> Var -> a -> VarEnv a extendVarEnv_C :: (a -> a -> a) -> VarEnv a -> Var -> a -> VarEnv a extendVarEnv_Acc :: (a -> b -> b) -> (a -> b) -> VarEnv b -> Var -> a -> VarEnv b extendVarEnvList :: VarEnv a -> [(Var, a)] -> VarEnv a plusVarEnv :: VarEnv a -> VarEnv a -> VarEnv a plusVarEnv_C :: (a -> a -> a) -> VarEnv a -> VarEnv a -> VarEnv a delVarEnvList :: VarEnv a -> [Var] -> VarEnv a delVarEnv :: VarEnv a -> Var -> VarEnv a minusVarEnv :: VarEnv a -> VarEnv a -> VarEnv a intersectsVarEnv :: VarEnv a -> VarEnv a -> Bool lookupVarEnv :: VarEnv a -> Var -> Maybe a lookupVarEnv_NF :: VarEnv a -> Var -> a lookupWithDefaultVarEnv :: VarEnv a -> a -> Var -> a mapVarEnv :: (a -> b) -> VarEnv a -> VarEnv b zipVarEnv :: [Var] -> [a] -> VarEnv a modifyVarEnv :: (a -> a) -> VarEnv a -> Var -> VarEnv a modifyVarEnv_Directly :: (a -> a) -> UniqFM a -> Unique -> UniqFM a isEmptyVarEnv :: VarEnv a -> Bool foldVarEnv :: (a -> b -> b) -> b -> VarEnv a -> b elemVarEnvByKey :: Unique -> VarEnv a -> Bool lookupVarEnv_Directly :: VarEnv a -> Unique -> Maybe a filterVarEnv_Directly :: (Unique -> a -> Bool) -> VarEnv a -> VarEnv a restrictVarEnv :: VarEnv a -> VarSet -> VarEnv a -- | A set of variables that are in scope at some point data InScopeSet emptyInScopeSet :: InScopeSet mkInScopeSet :: VarEnv Var -> InScopeSet delInScopeSet :: InScopeSet -> Var -> InScopeSet extendInScopeSet :: InScopeSet -> Var -> InScopeSet extendInScopeSetList :: InScopeSet -> [Var] -> InScopeSet extendInScopeSetSet :: InScopeSet -> VarEnv Var -> InScopeSet getInScopeVars :: InScopeSet -> VarEnv Var -- | Look up a variable the InScopeSet. This lets you map from the -- variable's identity (unique) to its full value. lookupInScope :: InScopeSet -> Var -> Maybe Var lookupInScope_Directly :: InScopeSet -> Unique -> Maybe Var unionInScope :: InScopeSet -> InScopeSet -> InScopeSet elemInScopeSet :: Var -> InScopeSet -> Bool -- | uniqAway in_scope v finds a unique that is not used in the -- in-scope set, and gives that to v. uniqAway :: InScopeSet -> Var -> Var -- | When we are comparing (or matching) types or terms, we are faced with -- "going under" corresponding binders. E.g. when comparing: -- --
--   \x. e1	~   \y. e2
--   
-- -- Basically we want to rename [x -> y] or -- [y -> x], but there are lots of things we must be -- careful of. In particular, x might be free in e2, or -- y in e1. So the idea is that we come up with a fresh binder -- that is free in neither, and rename x and y -- respectively. That means we must maintain: -- --
    --
  1. A renaming for the left-hand expression
  2. --
  3. A renaming for the right-hand expressions
  4. --
  5. An in-scope set
  6. --
-- -- Furthermore, when matching, we want to be able to have an 'occurs -- check', to prevent: -- --
--   \x. f   ~   \y. y
--   
-- -- matching with [f -> y]. So for each expression we -- want to know that set of locally-bound variables. That is precisely -- the domain of the mappings 1. and 2., but we must ensure that we -- always extend the mappings as we go in. -- -- All of this information is bundled up in the RnEnv2 data RnEnv2 mkRnEnv2 :: InScopeSet -> RnEnv2 -- | rnBndr2 env bL bR goes under a binder bL in the Left -- term, and binder bR in the Right term. It finds a new binder, -- new_b, and returns an environment mapping bL -> -- new_b and bR -> new_b rnBndr2 :: RnEnv2 -> Var -> Var -> RnEnv2 -- | Applies rnBndr2 to several variables: the two variable lists -- must be of equal length rnBndrs2 :: RnEnv2 -> [Var] -> [Var] -> RnEnv2 -- | Look up the renaming of an occurrence in the left or right term rnOccL :: RnEnv2 -> Var -> Var rnOccR :: RnEnv2 -> Var -> Var -- | Tells whether a variable is locally bound inRnEnvL :: RnEnv2 -> Var -> Bool inRnEnvR :: RnEnv2 -> Var -> Bool -- | Similar to rnBndr2 but used when there's a binder on the left -- side only. rnBndrL :: RnEnv2 -> Var -> (RnEnv2, Var) -- | Similar to rnBndr2 but used when there's a binder on the right -- side only. rnBndrR :: RnEnv2 -> Var -> (RnEnv2, Var) -- | Wipe the left or right side renaming nukeRnEnvL :: RnEnv2 -> RnEnv2 nukeRnEnvR :: RnEnv2 -> RnEnv2 addRnInScopeSet :: RnEnv2 -> VarEnv Var -> RnEnv2 -- | Similar to rnBndrL but used for eta expansion See Note [Eta -- expansion] rnEtaL :: RnEnv2 -> Var -> (RnEnv2, Var) -- | Similar to rnBndr2 but used for eta expansion See Note [Eta -- expansion] rnEtaR :: RnEnv2 -> Var -> (RnEnv2, Var) rnInScope :: Var -> RnEnv2 -> Bool rnInScopeSet :: RnEnv2 -> InScopeSet lookupRnInScope :: RnEnv2 -> Var -> Var -- | When tidying up print names, we keep a mapping of in-scope occ-names -- (the TidyOccEnv) and a Var-to-Var of the current renamings type TidyEnv = (TidyOccEnv, VarEnv Var) emptyTidyEnv :: TidyEnv instance Outputable InScopeSet module Demand data Demand Top :: Demand Abs :: Demand Call :: Demand -> Demand Eval :: Demands -> Demand Defer :: Demands -> Demand Box :: Demand -> Demand Bot :: Demand topDmd :: Demand lazyDmd :: Demand seqDmd :: Demand evalDmd :: Demand errDmd :: Demand isStrictDmd :: Demand -> Bool isTop :: Demand -> Bool isAbsent :: Demand -> Bool seqDemand :: Demand -> () data DmdType DmdType :: DmdEnv -> [Demand] -> DmdResult -> DmdType topDmdType :: DmdType botDmdType :: DmdType mkDmdType :: DmdEnv -> [Demand] -> DmdResult -> DmdType mkTopDmdType :: [Demand] -> DmdResult -> DmdType dmdTypeDepth :: DmdType -> Arity seqDmdType :: DmdType -> () type DmdEnv = VarEnv Demand emptyDmdEnv :: VarEnv Demand data DmdResult TopRes :: DmdResult RetCPR :: DmdResult BotRes :: DmdResult retCPR :: DmdResult isBotRes :: DmdResult -> Bool returnsCPR :: DmdResult -> Bool resTypeArgDmd :: DmdResult -> Demand data Demands Poly :: Demand -> Demands Prod :: [Demand] -> Demands mapDmds :: (Demand -> Demand) -> Demands -> Demands zipWithDmds :: (Demand -> Demand -> Demand) -> Demands -> Demands -> Demands allTop :: Demands -> Bool seqDemands :: Demands -> () newtype StrictSig StrictSig :: DmdType -> StrictSig mkStrictSig :: DmdType -> StrictSig topSig :: StrictSig botSig :: StrictSig cprSig :: StrictSig isTopSig :: StrictSig -> Bool splitStrictSig :: StrictSig -> ([Demand], DmdResult) increaseStrictSigArity :: Int -> StrictSig -> StrictSig pprIfaceStrictSig :: StrictSig -> SDoc appIsBottom :: StrictSig -> Int -> Bool isBottomingSig :: StrictSig -> Bool seqStrictSig :: StrictSig -> () instance Eq Demands instance Eq Demand instance Eq DmdResult instance Show DmdResult instance Eq StrictSig instance Show StrictSig instance Outputable StrictSig instance Outputable DmdResult instance Outputable DmdType instance Eq DmdType instance Outputable Demands instance Outputable Demand module Class data Class type ClassOpItem = (Id, DefMeth) data DefMeth NoDefMeth :: DefMeth DefMeth :: Name -> DefMeth GenDefMeth :: DefMeth -- | Convert a DefMethSpec to a DefMeth, which discards the -- name field in the DefMeth constructor of the DefMeth. defMethSpecOfDefMeth :: DefMeth -> DefMethSpec type FunDep a = ([a], [a]) pprFundeps :: Outputable a => [FunDep a] -> SDoc pprFunDep :: Outputable a => FunDep a -> SDoc mkClass :: Name -> [TyVar] -> [([TyVar], [TyVar])] -> [PredType] -> Int -> [Id] -> [TyCon] -> [ClassOpItem] -> TyCon -> Class classTyVars :: Class -> [TyVar] classArity :: Class -> Arity classSCNEqs :: Class -> Int classKey :: Class -> Unique className :: Class -> Name classATs :: Class -> [TyCon] classTyCon :: Class -> TyCon classMethods :: Class -> [Id] classOpItems :: Class -> [ClassOpItem] classBigSig :: Class -> ([TyVar], [PredType], [Id], [ClassOpItem]) classExtraBigSig :: Class -> ([TyVar], [FunDep TyVar], [PredType], [Id], [TyCon], [ClassOpItem]) classTvsFds :: Class -> ([TyVar], [FunDep TyVar]) classSCTheta :: Class -> [PredType] classAllSelIds :: Class -> [Id] classSCSelId :: Class -> Int -> Id instance Eq DefMeth instance Data Class instance Typeable Class instance Outputable DefMeth instance Show Class instance Outputable Class instance NamedThing Class instance Uniquable Class instance Ord Class instance Eq Class module NameEnv type NameEnv a = UniqFM a mkNameEnv :: [(Name, a)] -> NameEnv a emptyNameEnv :: NameEnv a unitNameEnv :: Name -> a -> NameEnv a nameEnvElts :: NameEnv a -> [a] nameEnvUniqueElts :: NameEnv a -> [(Unique, a)] extendNameEnv_C :: (a -> a -> a) -> NameEnv a -> Name -> a -> NameEnv a extendNameEnv_Acc :: (a -> b -> b) -> (a -> b) -> NameEnv b -> Name -> a -> NameEnv b extendNameEnv :: NameEnv a -> Name -> a -> NameEnv a extendNameEnvList :: NameEnv a -> [(Name, a)] -> NameEnv a extendNameEnvList_C :: (a -> a -> a) -> NameEnv a -> [(Name, a)] -> NameEnv a foldNameEnv :: (a -> b -> b) -> b -> NameEnv a -> b filterNameEnv :: (elt -> Bool) -> NameEnv elt -> NameEnv elt plusNameEnv :: NameEnv a -> NameEnv a -> NameEnv a plusNameEnv_C :: (a -> a -> a) -> NameEnv a -> NameEnv a -> NameEnv a lookupNameEnv :: NameEnv a -> Name -> Maybe a lookupNameEnv_NF :: NameEnv a -> Name -> a delFromNameEnv :: NameEnv a -> Name -> NameEnv a delListFromNameEnv :: NameEnv a -> [Name] -> NameEnv a elemNameEnv :: Name -> NameEnv a -> Bool mapNameEnv :: (elt1 -> elt2) -> NameEnv elt1 -> NameEnv elt2 -- | GHC uses several kinds of name internally: -- -- module RdrName -- | Do not use the data constructors of RdrName directly: prefer the -- family of functions that creates them, such as mkRdrUnqual data RdrName -- | Used for ordinary, unqualified occurrences, e.g. x, -- y or Foo. Create such a RdrName with -- mkRdrUnqual Unqual :: OccName -> RdrName -- | A qualified name written by the user in source code. The module -- isn't necessarily the module where the thing is defined; just the one -- from which it is imported. Examples are Bar.x, Bar.y -- or Bar.Foo. Create such a RdrName with -- mkRdrQual Qual :: ModuleName -> OccName -> RdrName -- | An original name; the module is the defining module. This is -- used when GHC generates code that will be fed into the renamer (e.g. -- from deriving clauses), but where we want to say "Use Prelude.map -- dammit". One of these can be created with mkOrig Orig :: Module -> OccName -> RdrName -- | We know exactly the Name. This is used: -- --
    --
  1. When the parser parses built-in syntax like [] and -- (,), but wants a RdrName from it
  2. --
  3. By Template Haskell, when TH has generated a unique name
  4. --
-- -- Such a RdrName can be created by using getRdrName on a -- Name Exact :: Name -> RdrName mkRdrUnqual :: OccName -> RdrName mkRdrQual :: ModuleName -> OccName -> RdrName mkUnqual :: NameSpace -> FastString -> RdrName mkVarUnqual :: FastString -> RdrName -- | Make a qualified RdrName in the given namespace and where the -- ModuleName and the OccName are taken from the first and -- second elements of the tuple respectively mkQual :: NameSpace -> (FastString, FastString) -> RdrName mkOrig :: Module -> OccName -> RdrName nameRdrName :: Name -> RdrName getRdrName :: NamedThing thing => thing -> RdrName rdrNameOcc :: RdrName -> OccName rdrNameSpace :: RdrName -> NameSpace -- | This rather gruesome function is used mainly by the parser. When -- parsing: -- --
--   data T a = T | T1 Int
--   
-- -- we parse the data constructors as types because of parser -- ambiguities, so then we need to change the type constr to a -- data constr -- -- The exact-name case can occur when parsing: -- --
--   data [] a = [] | a : [a]
--   
-- -- For the exact-name case we return an original name. setRdrNameSpace :: RdrName -> NameSpace -> RdrName isRdrDataCon :: RdrName -> Bool isRdrTyVar :: RdrName -> Bool isRdrTc :: RdrName -> Bool isQual :: RdrName -> Bool isQual_maybe :: RdrName -> Maybe (ModuleName, OccName) isUnqual :: RdrName -> Bool isOrig :: RdrName -> Bool isOrig_maybe :: RdrName -> Maybe (Module, OccName) isExact :: RdrName -> Bool isExact_maybe :: RdrName -> Maybe Name isSrcRdrName :: RdrName -> Bool showRdrName :: RdrName -> String -- | This environment is used to store local bindings (let, -- where, lambda, case). It is keyed by OccName, -- because we never use it for qualified names type LocalRdrEnv = OccEnv Name emptyLocalRdrEnv :: LocalRdrEnv extendLocalRdrEnv :: LocalRdrEnv -> Name -> LocalRdrEnv extendLocalRdrEnvList :: LocalRdrEnv -> [Name] -> LocalRdrEnv lookupLocalRdrEnv :: LocalRdrEnv -> RdrName -> Maybe Name lookupLocalRdrOcc :: LocalRdrEnv -> OccName -> Maybe Name elemLocalRdrEnv :: RdrName -> LocalRdrEnv -> Bool -- | Keyed by OccName; when looking up a qualified name we look up -- the OccName part, and then check the Provenance to see -- if the appropriate qualification is valid. This saves routinely -- doubling the size of the env by adding both qualified and unqualified -- names to the domain. -- -- The list in the codomain is required because there may be name clashes -- These only get reported on lookup, not on construction -- -- INVARIANT: All the members of the list have distinct gre_name -- fields; that is, no duplicate Names -- -- INVARIANT: Imported provenance => Name is an ExternalName However -- LocalDefs can have an InternalName. This happens only when -- type-checking a [d| ... |] Template Haskell quotation; see this note -- in RnNames Note [Top-level Names in Template Haskell decl quotes] type GlobalRdrEnv = OccEnv [GlobalRdrElt] emptyGlobalRdrEnv :: GlobalRdrEnv mkGlobalRdrEnv :: [GlobalRdrElt] -> GlobalRdrEnv plusGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrEnv -> GlobalRdrEnv lookupGlobalRdrEnv :: GlobalRdrEnv -> OccName -> [GlobalRdrElt] extendGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrElt -> GlobalRdrEnv pprGlobalRdrEnv :: GlobalRdrEnv -> SDoc globalRdrEnvElts :: GlobalRdrEnv -> [GlobalRdrElt] lookupGRE_RdrName :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt] lookupGRE_Name :: GlobalRdrEnv -> Name -> [GlobalRdrElt] getGRE_NameQualifier_maybes :: GlobalRdrEnv -> Name -> [Maybe [ModuleName]] -- | Apply a transformation function to the GREs for these OccNames transformGREs :: (GlobalRdrElt -> GlobalRdrElt) -> [OccName] -> GlobalRdrEnv -> GlobalRdrEnv -- | For each OccName, see if there are multiple local definitions -- for it. If so, remove all but one (to suppress subsequent error -- messages) and return a list of the duplicate bindings findLocalDupsRdrEnv :: GlobalRdrEnv -> [OccName] -> (GlobalRdrEnv, [[Name]]) -- | Take a list of GREs which have the right OccName Pick those GREs that -- are suitable for this RdrName And for those, keep only only the -- Provenances that are suitable -- -- Consider: -- --
--   module A ( f ) where
--   import qualified Foo( f )
--   import Baz( f )
--   f = undefined
--   
-- -- Let's suppose that Foo.f and Baz.f are the same -- entity really. The export of f is ambiguous because it's in -- scope from the local def and the import. The lookup of Unqual -- f should return a GRE for the locally-defined f, and a -- GRE for the imported f, with a single provenance, -- namely the one for Baz(f). pickGREs :: RdrName -> [GlobalRdrElt] -> [GlobalRdrElt] -- | An element of the GlobalRdrEnv data GlobalRdrElt GRE :: Name -> Parent -> Provenance -> GlobalRdrElt gre_name :: GlobalRdrElt -> Name gre_par :: GlobalRdrElt -> Parent -- | Why it's in scope gre_prov :: GlobalRdrElt -> Provenance isLocalGRE :: GlobalRdrElt -> Bool -- | Test if an unqualifed version of this thing would be in scope unQualOK :: GlobalRdrElt -> Bool -- | Is in scope qualified with the given module? qualSpecOK :: ModuleName -> ImportSpec -> Bool -- | Is in scope unqualified? unQualSpecOK :: ImportSpec -> Bool -- | The Provenance of something says how it came to be in scope. -- It's quite elaborate so that we can give accurate unused-name -- warnings. data Provenance -- | The thing was defined locally LocalDef :: Provenance -- | The thing was imported. -- -- INVARIANT: the list of ImportSpec is non-empty Imported :: [ImportSpec] -> Provenance -- | Print out the place where the name was imported pprNameProvenance :: GlobalRdrElt -> SDoc -- | The children of a Name are the things that are abbreviated by the -- .. notation in export lists. Specifically: TyCon Children are * -- data constructors * record field ids Class Children are * class -- operations Each child has the parent thing as its Parent data Parent NoParent :: Parent ParentIs :: Name -> Parent data ImportSpec ImpSpec :: ImpDeclSpec -> ImpItemSpec -> ImportSpec is_decl :: ImportSpec -> ImpDeclSpec is_item :: ImportSpec -> ImpItemSpec -- | Describes a particular import declaration and is shared among all the -- Provenances for that decl data ImpDeclSpec ImpDeclSpec :: ModuleName -> ModuleName -> Bool -> SrcSpan -> ImpDeclSpec -- | Module imported, e.g. import Muggle Note the Muggle -- may well not be the defining module for this thing! is_mod :: ImpDeclSpec -> ModuleName -- | Import alias, e.g. from as M (or Muggle if there is -- no as clause) is_as :: ImpDeclSpec -> ModuleName -- | Was this import qualified? is_qual :: ImpDeclSpec -> Bool -- | The location of the entire import declaration is_dloc :: ImpDeclSpec -> SrcSpan -- | Describes import info a particular Name data ImpItemSpec -- | The import had no import list, or had a hiding list ImpAll :: ImpItemSpec -- | The import had an import list. The is_explicit field is -- True iff the thing was named explicitly in the import -- specs rather than being imported as part of a ... group. -- Consider: -- --
--   import C( T(..) )
--   
-- -- Here the constructors of T are not named explicitly; only -- T is named explicitly. ImpSome :: Bool -> SrcSpan -> ImpItemSpec is_explicit :: ImpItemSpec -> Bool is_iloc :: ImpItemSpec -> SrcSpan importSpecLoc :: ImportSpec -> SrcSpan importSpecModule :: ImportSpec -> ModuleName isExplicitItem :: ImpItemSpec -> Bool instance Typeable RdrName instance Data RdrName instance Eq Parent instance Eq ImportSpec instance Ord ImportSpec instance Outputable ImportSpec instance Ord ImpItemSpec instance Ord ImpDeclSpec instance Ord Provenance instance Eq ImpItemSpec instance Eq ImpDeclSpec instance Eq Provenance instance Outputable GlobalRdrElt instance Outputable Parent instance Ord RdrName instance Eq RdrName instance OutputableBndr RdrName instance Outputable RdrName module PrelNames -- | The type of unique identifiers that are used in many places in GHC for -- fast ordering and equality tests. You should generate these with the -- functions from the UniqSupply module data Unique -- | Class of things that we can obtain a Unique from class Uniquable a getUnique :: Uniquable a => a -> Unique hasKey :: Uniquable a => a -> Unique -> Bool itName :: Unique -> Name mkUnboundName :: RdrName -> Name isUnboundName :: Name -> Bool basicKnownKeyNames :: [Name] genericTyConNames :: [Name] pRELUDE :: Module gHC_TYPES :: Module gHC_BOOL :: Module gHC_UNIT :: Module gHC_ORDERING :: Module gHC_GENERICS :: Module gHC_MAGIC :: Module gHC_CLASSES :: Module gHC_BASE :: Module gHC_ENUM :: Module gHC_SHOW :: Module gHC_READ :: Module gHC_NUM :: Module gHC_INTEGER :: Module gHC_INTEGER_TYPE :: Module gHC_LIST :: Module gHC_PARR :: Module gHC_TUPLE :: Module dATA_TUPLE :: Module dATA_EITHER :: Module dATA_STRING :: Module dATA_FOLDABLE :: Module dATA_TRAVERSABLE :: Module gHC_PACK :: Module gHC_CONC :: Module gHC_IO :: Module gHC_IO_Exception :: Module gHC_ST :: Module gHC_ARR :: Module gHC_STABLE :: Module gHC_ADDR :: Module gHC_PTR :: Module gHC_ERR :: Module gHC_REAL :: Module gHC_FLOAT :: Module gHC_TOP_HANDLER :: Module sYSTEM_IO :: Module dYNAMIC :: Module tYPEABLE :: Module gENERICS :: Module dOTNET :: Module rEAD_PREC :: Module lEX :: Module gHC_INT :: Module gHC_WORD :: Module mONAD :: Module mONAD_FIX :: Module aRROW :: Module cONTROL_APPLICATIVE :: Module gHC_DESUGAR :: Module rANDOM :: Module gHC_EXTS :: Module cONTROL_EXCEPTION_BASE :: Module gHC_PRIM :: Module rOOT_MAIN :: Module mAIN :: Module iNTERACTIVE :: Module mAIN_NAME :: ModuleName pRELUDE_NAME :: ModuleName mkPrimModule :: FastString -> Module mkIntegerModule :: FastString -> Module mkBaseModule :: FastString -> Module mkBaseModule_ :: ModuleName -> Module mkMainModule :: FastString -> Module mkMainModule_ :: ModuleName -> Module mkTupleModule :: Boxity -> Arity -> Module main_RDR_Unqual :: RdrName dot_tv_RDR :: RdrName forall_tv_RDR :: RdrName ge_RDR :: RdrName ne_RDR :: RdrName le_RDR :: RdrName lt_RDR :: RdrName gt_RDR :: RdrName compare_RDR :: RdrName ltTag_RDR :: RdrName eqTag_RDR :: RdrName gtTag_RDR :: RdrName eq_RDR :: RdrName numClass_RDR :: RdrName ordClass_RDR :: RdrName enumClass_RDR :: RdrName monadClass_RDR :: RdrName eqClass_RDR :: RdrName append_RDR :: RdrName map_RDR :: RdrName build_RDR :: RdrName returnM_RDR :: RdrName bindM_RDR :: RdrName failM_RDR :: RdrName foldr_RDR :: RdrName right_RDR :: RdrName left_RDR :: RdrName toEnum_RDR :: RdrName fromEnum_RDR :: RdrName enumFromTo_RDR :: RdrName enumFromThen_RDR :: RdrName enumFromThenTo_RDR :: RdrName enumFrom_RDR :: RdrName plusInteger_RDR :: RdrName timesInteger_RDR :: RdrName ratioDataCon_RDR :: RdrName ioDataCon_RDR :: RdrName unpackCString_RDR :: RdrName unpackCStringFoldr_RDR :: RdrName unpackCStringUtf8_RDR :: RdrName eqString_RDR :: RdrName wordDataCon_RDR :: RdrName newStablePtr_RDR :: RdrName returnIO_RDR :: RdrName bindIO_RDR :: RdrName fromRational_RDR :: RdrName minus_RDR :: RdrName times_RDR :: RdrName plus_RDR :: RdrName fromInteger_RDR :: RdrName fromString_RDR :: RdrName compose_RDR :: RdrName getTag_RDR :: RdrName succ_RDR :: RdrName pred_RDR :: RdrName minBound_RDR :: RdrName maxBound_RDR :: RdrName and_RDR :: RdrName range_RDR :: RdrName inRange_RDR :: RdrName index_RDR :: RdrName unsafeIndex_RDR :: RdrName unsafeRangeSize_RDR :: RdrName not_RDR :: RdrName readListDefault_RDR :: RdrName readListPrec_RDR :: RdrName readListPrecDefault_RDR :: RdrName readPrec_RDR :: RdrName parens_RDR :: RdrName choose_RDR :: RdrName lexP_RDR :: RdrName readList_RDR :: RdrName ident_RDR :: RdrName symbol_RDR :: RdrName punc_RDR :: RdrName alt_RDR :: RdrName reset_RDR :: RdrName prec_RDR :: RdrName step_RDR :: RdrName showList___RDR :: RdrName showsPrec_RDR :: RdrName showString_RDR :: RdrName showSpace_RDR :: RdrName showParen_RDR :: RdrName showList_RDR :: RdrName mkTypeRep_RDR :: RdrName mkTyConRep_RDR :: RdrName typeOf_RDR :: RdrName undefined_RDR :: RdrName inlDataCon_RDR :: RdrName inrDataCon_RDR :: RdrName genUnitDataCon_RDR :: RdrName crossDataCon_RDR :: RdrName pure_RDR :: RdrName ap_RDR :: RdrName foldable_foldr_RDR :: RdrName traverse_RDR :: RdrName fmap_RDR :: RdrName tcQual_RDR :: Module -> FastString -> RdrName clsQual_RDR :: Module -> FastString -> RdrName dataQual_RDR :: Module -> FastString -> RdrName varQual_RDR :: Module -> FastString -> RdrName runMainIOName :: Name orderingTyConName :: Name leftDataConName :: Name rightDataConName :: Name eitherTyConName :: Name plusTyConName :: Name genUnitTyConName :: Name crossTyConName :: Name unpackCStringAppendName :: Name unpackCStringFoldrName :: Name unpackCStringUtf8Name :: Name eqStringName :: Name stringTyConName :: Name unpackCStringName :: Name inlineIdName :: Name eqName :: Name ordClassName :: Name geName :: Name functorClassName :: Name eqClassName :: Name thenMName :: Name bindMName :: Name returnMName :: Name failMName :: Name monadClassName :: Name foldableClassName :: Name traversableClassName :: Name applicativeClassName :: Name groupWithName :: Name otherwiseIdName :: Name foldrName :: Name buildName :: Name augmentName :: Name mapName :: Name appendName :: Name assertName :: Name breakpointName :: Name breakpointCondName :: Name breakpointAutoName :: Name dollarName :: Name opaqueTyConName :: Name fromStringName :: Name breakpointJumpName :: Name breakpointCondJumpName :: Name breakpointAutoJumpName :: Name sndName :: Name fstName :: Name fromIntegerName :: Name minusName :: Name negateName :: Name plusIntegerName :: Name timesIntegerName :: Name integerTyConName :: Name smallIntegerName :: Name numClassName :: Name ratioTyConName :: Name ratioDataConName :: Name realClassName :: Name integralClassName :: Name realFracClassName :: Name fractionalClassName :: Name fromRationalName :: Name rationalTyConName :: Name realFloatClassName :: Name floatingClassName :: Name ixClassName :: Name typeable1ClassName :: Name typeable2ClassName :: Name typeable3ClassName :: Name typeable4ClassName :: Name typeable5ClassName :: Name typeable6ClassName :: Name typeable7ClassName :: Name typeableClassName :: Name typeableClassNames :: [Name] dataClassName :: Name assertErrorName :: Name enumFromName :: Name enumFromToName :: Name enumFromThenName :: Name enumFromThenToName :: Name boundedClassName :: Name enumClassName :: Name filterName :: Name zipName :: Name concatName :: Name showClassName :: Name readClassName :: Name enumFromThenToPName :: Name nullPName :: Name lengthPName :: Name singletonPName :: Name replicatePName :: Name mapPName :: Name filterPName :: Name zipPName :: Name crossMapPName :: Name indexPName :: Name toPName :: Name emptyPName :: Name appPName :: Name enumFromToPName :: Name ioDataConName :: Name thenIOName :: Name bindIOName :: Name returnIOName :: Name failIOName :: Name ioTyConName :: Name printName :: Name int16TyConName :: Name int32TyConName :: Name int64TyConName :: Name int8TyConName :: Name word16TyConName :: Name word32TyConName :: Name word64TyConName :: Name wordTyConName :: Name wordDataConName :: Name word8TyConName :: Name funPtrTyConName :: Name ptrTyConName :: Name newStablePtrName :: Name stablePtrTyConName :: Name runSTRepName :: Name mfixName :: Name monadFixClassName :: Name composeAName :: Name firstAName :: Name appAName :: Name choiceAName :: Name loopAName :: Name arrAName :: Name toAnnotationWrapperName :: Name randomClassName :: Name randomGenClassName :: Name isStringClassName :: Name monadPlusClassName :: Name objectTyConName :: Name marshalObjectName :: Name marshalStringName :: Name unmarshalStringName :: Name checkDotnetResName :: Name unmarshalObjectName :: Name tcQual :: Module -> FastString -> Unique -> Name clsQual :: Module -> FastString -> Unique -> Name varQual :: Module -> FastString -> Unique -> Name mk_known_key_name :: NameSpace -> Module -> FastString -> Unique -> Name conName :: Module -> FastString -> Unique -> Name methName :: Module -> FastString -> Unique -> Name enumClassKey :: Unique eqClassKey :: Unique floatingClassKey :: Unique fractionalClassKey :: Unique integralClassKey :: Unique monadClassKey :: Unique dataClassKey :: Unique functorClassKey :: Unique numClassKey :: Unique ordClassKey :: Unique readClassKey :: Unique realClassKey :: Unique realFloatClassKey :: Unique realFracClassKey :: Unique showClassKey :: Unique ixClassKey :: Unique boundedClassKey :: Unique typeable1ClassKey :: Unique typeable2ClassKey :: Unique typeable3ClassKey :: Unique typeable4ClassKey :: Unique typeable5ClassKey :: Unique typeable6ClassKey :: Unique typeable7ClassKey :: Unique typeableClassKey :: Unique monadFixClassKey :: Unique randomClassKey :: Unique randomGenClassKey :: Unique monadPlusClassKey :: Unique isStringClassKey :: Unique foldableClassKey :: Unique traversableClassKey :: Unique applicativeClassKey :: Unique arrayPrimTyConKey :: Unique boolTyConKey :: Unique byteArrayPrimTyConKey :: Unique charPrimTyConKey :: Unique charTyConKey :: Unique doublePrimTyConKey :: Unique doubleTyConKey :: Unique floatPrimTyConKey :: Unique floatTyConKey :: Unique funTyConKey :: Unique intPrimTyConKey :: Unique intTyConKey :: Unique int8TyConKey :: Unique int16TyConKey :: Unique int32PrimTyConKey :: Unique int32TyConKey :: Unique int64PrimTyConKey :: Unique int64TyConKey :: Unique integerTyConKey :: Unique listTyConKey :: Unique foreignObjPrimTyConKey :: Unique weakPrimTyConKey :: Unique mutableArrayPrimTyConKey :: Unique mutableByteArrayPrimTyConKey :: Unique orderingTyConKey :: Unique mVarPrimTyConKey :: Unique ratioTyConKey :: Unique rationalTyConKey :: Unique realWorldTyConKey :: Unique stablePtrPrimTyConKey :: Unique stablePtrTyConKey :: Unique anyTyConKey :: Unique addrPrimTyConKey :: Unique stableNamePrimTyConKey :: Unique stableNameTyConKey :: Unique mutVarPrimTyConKey :: Unique ioTyConKey :: Unique wordPrimTyConKey :: Unique wordTyConKey :: Unique word8TyConKey :: Unique word16TyConKey :: Unique word32PrimTyConKey :: Unique word32TyConKey :: Unique word64PrimTyConKey :: Unique word64TyConKey :: Unique liftedConKey :: Unique unliftedConKey :: Unique anyBoxConKey :: Unique kindConKey :: Unique boxityConKey :: Unique typeConKey :: Unique threadIdPrimTyConKey :: Unique bcoPrimTyConKey :: Unique ptrTyConKey :: Unique funPtrTyConKey :: Unique tVarPrimTyConKey :: Unique statePrimTyConKey :: Unique plusTyConKey :: Unique genUnitTyConKey :: Unique crossTyConKey :: Unique parrTyConKey :: Unique objectTyConKey :: Unique eitherTyConKey :: Unique coSuperKindTyConKey :: Unique tySuperKindTyConKey :: Unique openTypeKindTyConKey :: Unique unliftedTypeKindTyConKey :: Unique ubxTupleKindTyConKey :: Unique argTypeKindTyConKey :: Unique liftedTypeKindTyConKey :: Unique transCoercionTyConKey :: Unique leftCoercionTyConKey :: Unique rightCoercionTyConKey :: Unique instCoercionTyConKey :: Unique unsafeCoercionTyConKey :: Unique csel1CoercionTyConKey :: Unique csel2CoercionTyConKey :: Unique cselRCoercionTyConKey :: Unique symCoercionTyConKey :: Unique unknown1TyConKey :: Unique unknown2TyConKey :: Unique unknown3TyConKey :: Unique opaqueTyConKey :: Unique unknownTyConKey :: Unique stringTyConKey :: Unique unitTyConKey :: Unique consDataConKey :: Unique doubleDataConKey :: Unique falseDataConKey :: Unique floatDataConKey :: Unique intDataConKey :: Unique nilDataConKey :: Unique ratioDataConKey :: Unique stableNameDataConKey :: Unique trueDataConKey :: Unique wordDataConKey :: Unique ioDataConKey :: Unique integerDataConKey :: Unique charDataConKey :: Unique inlDataConKey :: Unique inrDataConKey :: Unique genUnitDataConKey :: Unique crossDataConKey :: Unique parrDataConKey :: Unique rightDataConKey :: Unique leftDataConKey :: Unique augmentIdKey :: Unique appendIdKey :: Unique buildIdKey :: Unique errorIdKey :: Unique foldlIdKey :: Unique foldrIdKey :: Unique recSelErrorIdKey :: Unique integerMinusOneIdKey :: Unique integerPlusOneIdKey :: Unique integerPlusTwoIdKey :: Unique integerZeroIdKey :: Unique int2IntegerIdKey :: Unique seqIdKey :: Unique irrefutPatErrorIdKey :: Unique eqStringIdKey :: Unique noMethodBindingErrorIdKey :: Unique nonExhaustiveGuardsErrorIdKey :: Unique runtimeErrorIdKey :: Unique parErrorIdKey :: Unique parIdKey :: Unique patErrorIdKey :: Unique realWorldPrimIdKey :: Unique recConErrorIdKey :: Unique recUpdErrorIdKey :: Unique traceIdKey :: Unique unpackCStringUtf8IdKey :: Unique unpackCStringAppendIdKey :: Unique unpackCStringFoldrIdKey :: Unique unpackCStringIdKey :: Unique absentErrorIdKey :: Unique concatIdKey :: Unique filterIdKey :: Unique zipIdKey :: Unique bindIOIdKey :: Unique returnIOIdKey :: Unique deRefStablePtrIdKey :: Unique newStablePtrIdKey :: Unique smallIntegerIdKey :: Unique plusIntegerIdKey :: Unique timesIntegerIdKey :: Unique printIdKey :: Unique failIOIdKey :: Unique nullAddrIdKey :: Unique voidArgIdKey :: Unique fstIdKey :: Unique sndIdKey :: Unique otherwiseIdKey :: Unique assertIdKey :: Unique runSTRepIdKey :: Unique unsafeCoerceIdKey :: Unique runMainKey :: Unique rootMainKey :: Unique lazyIdKey :: Unique assertErrorIdKey :: Unique thenIOIdKey :: Unique breakpointCondIdKey :: Unique breakpointAutoIdKey :: Unique breakpointJumpIdKey :: Unique breakpointCondJumpIdKey :: Unique breakpointAutoJumpIdKey :: Unique breakpointIdKey :: Unique inlineIdKey :: Unique groupWithIdKey :: Unique dollarIdKey :: Unique mapIdKey :: Unique nullPIdKey :: Unique lengthPIdKey :: Unique replicatePIdKey :: Unique mapPIdKey :: Unique filterPIdKey :: Unique zipPIdKey :: Unique crossMapPIdKey :: Unique indexPIdKey :: Unique toPIdKey :: Unique enumFromToPIdKey :: Unique enumFromThenToPIdKey :: Unique emptyPIdKey :: Unique appPIdKey :: Unique singletonPIdKey :: Unique marshalObjectIdKey :: Unique marshalStringIdKey :: Unique unmarshalStringIdKey :: Unique checkDotnetResNameIdKey :: Unique unmarshalObjectIdKey :: Unique unboundKey :: Unique minusClassOpKey :: Unique fromRationalClassOpKey :: Unique enumFromClassOpKey :: Unique enumFromThenClassOpKey :: Unique enumFromToClassOpKey :: Unique enumFromThenToClassOpKey :: Unique eqClassOpKey :: Unique geClassOpKey :: Unique negateClassOpKey :: Unique failMClassOpKey :: Unique bindMClassOpKey :: Unique thenMClassOpKey :: Unique returnMClassOpKey :: Unique fromIntegerClassOpKey :: Unique mfixIdKey :: Unique composeAIdKey :: Unique firstAIdKey :: Unique appAIdKey :: Unique choiceAIdKey :: Unique loopAIdKey :: Unique arrAIdKey :: Unique fromStringClassOpKey :: Unique toAnnotationWrapperIdKey :: Unique numericTyKeys :: [Unique] kindKeys :: [Unique] numericClassKeys :: [Unique] fractionalClassKeys :: [Unique] needsDataDeclCtxtClassKeys :: [Unique] standardClassKeys :: [Unique] derivableClassKeys :: [Unique] -- | Mapping of prelude functions to vectorised versions. Functions like -- filterP currently have a working but naive version in GHC.PArr During -- vectorisation we replace these by calls to filterPA, which are defined -- in dph-common Data.Array.Parallel.Lifted.Combinators -- -- As renamer only sees the GHC.PArr functions, if you want to add a new -- function to the vectoriser there has to be a definition for it in -- GHC.PArr, even though it will never be used at runtime. module Vectorise.Builtins.Prelude preludeVars :: Modules -> [(Module, FastString, Module, FastString)] preludeScalars :: Modules -> [(Module, FastString)] module NameSet type NameSet = UniqSet Name emptyNameSet :: NameSet unitNameSet :: Name -> NameSet mkNameSet :: [Name] -> NameSet unionNameSets :: NameSet -> NameSet -> NameSet unionManyNameSets :: [NameSet] -> NameSet minusNameSet :: NameSet -> NameSet -> NameSet elemNameSet :: Name -> NameSet -> Bool nameSetToList :: NameSet -> [Name] addOneToNameSet :: NameSet -> Name -> NameSet addListToNameSet :: NameSet -> [Name] -> NameSet delFromNameSet :: NameSet -> Name -> NameSet delListFromNameSet :: NameSet -> [Name] -> NameSet isEmptyNameSet :: NameSet -> Bool foldNameSet :: (Name -> b -> b) -> b -> NameSet -> b filterNameSet :: (Name -> Bool) -> NameSet -> NameSet -- | True if there is a non-empty intersection. s1 -- intersectsNameSet s2 doesn't compute s2 if -- s1 is empty intersectsNameSet :: NameSet -> NameSet -> Bool intersectNameSet :: NameSet -> NameSet -> NameSet type FreeVars = NameSet isEmptyFVs :: NameSet -> Bool emptyFVs :: FreeVars plusFVs :: [FreeVars] -> FreeVars plusFV :: FreeVars -> FreeVars -> FreeVars mkFVs :: [Name] -> FreeVars addOneFV :: FreeVars -> Name -> FreeVars unitFV :: Name -> FreeVars delFV :: Name -> FreeVars -> FreeVars delFVs :: [Name] -> FreeVars -> FreeVars -- | A set of names that are defined somewhere type Defs = NameSet -- | A set of names that are used somewhere type Uses = NameSet -- | (Just ds, us) => The use of any member of the ds -- implies that all the us are used too. Also, us may -- mention ds. -- -- Nothing => Nothing is defined in this group, but -- nevertheless all the uses are essential. Used for instance -- declarations, for example type DefUse = (Maybe Defs, Uses) -- | A number of DefUses in dependency order: earlier Defs -- scope over later Uses In a single (def, use) pair, the defs -- also scope over the uses type DefUses = [DefUse] emptyDUs :: DefUses usesOnly :: Uses -> DefUses mkDUs :: [(Defs, Uses)] -> DefUses plusDU :: DefUses -> DefUses -> DefUses -- | Given some DefUses and some Uses, find all the uses, -- transitively. The result is a superset of the input Uses; and -- includes things defined in the input DefUses (but only if they -- are used) findUses :: DefUses -> Uses -> Uses duDefs :: DefUses -> Defs -- | Collect all Uses, regardless of whether the group is itself -- used, but remove Defs on the way duUses :: DefUses -> Uses -- | Just like allUses, but Defs are not eliminated from the -- Uses returned allUses :: DefUses -> Uses instance Data NameSet instance Typeable NameSet module Annotations -- | Represents an annotation after it has been sufficiently desugared from -- it's initial form of HsDecls.AnnDecl data Annotation Annotation :: CoreAnnTarget -> Serialized -> Annotation -- | The target of the annotation ann_target :: Annotation -> CoreAnnTarget -- | Serialized version of the annotation that allows recovery of -- its value or can be persisted to an interface file ann_value :: Annotation -> Serialized -- | An annotation target data AnnTarget name -- | We are annotating something with a name: a type or identifier NamedTarget :: name -> AnnTarget name -- | We are annotating a particular module ModuleTarget :: Module -> AnnTarget name -- | The kind of annotation target found in the middle end of the compiler type CoreAnnTarget = AnnTarget Name getAnnTargetName_maybe :: AnnTarget name -> Maybe name -- | A collection of annotations data AnnEnv mkAnnEnv :: [Annotation] -> AnnEnv extendAnnEnvList :: AnnEnv -> [Annotation] -> AnnEnv plusAnnEnv :: AnnEnv -> AnnEnv -> AnnEnv emptyAnnEnv :: AnnEnv -- | Find the annotations attached to the given target as Typeable -- values of your choice. If no deserializer is specified, only transient -- annotations will be returned. findAnns :: Typeable a => ([Word8] -> a) -> AnnEnv -> CoreAnnTarget -> [a] -- | Deserialize all annotations of a given type. This happens lazily, that -- is no deserialization will take place until the [a] is actually -- demanded and the [a] can also be empty (the UniqFM is not filtered). deserializeAnns :: Typeable a => ([Word8] -> a) -> AnnEnv -> UniqFM [a] instance Outputable Annotation instance Outputable name => Outputable (AnnTarget name) instance Uniquable name => Uniquable (AnnTarget name) instance Functor AnnTarget module TyCon -- | TyCons represent type constructors. Type constructors are introduced -- by things such as: -- -- 1) Data declarations: data Foo = ... creates the Foo -- type constructor of kind * -- -- 2) Type synonyms: type Foo = ... creates the Foo -- type constructor -- -- 3) Newtypes: newtype Foo a = MkFoo ... creates the -- Foo type constructor of kind * -> * -- -- 4) Class declarations: class Foo where creates the -- Foo type constructor of kind * -- -- 5) Type coercions! This is because we represent a coercion from -- t1 to t2 as a Type, where that type has kind -- t1 ~ t2. See Coercion for more on this -- -- This data type also encodes a number of primitive, built in type -- constructors such as those for function and tuple types. data TyCon -- | Names of the fields in an algebraic record type type FieldLabel = Name -- | Represents right-hand-sides of TyCons for algebraic types data AlgTyConRhs -- | Says that we know nothing about this data type, except that it's -- represented by a pointer. Used when we export a data type abstractly -- into an .hi file. AbstractTyCon :: AlgTyConRhs -- | Represents an open type family without a fixed right hand side. -- Additional instances can appear at any time. -- -- These are introduced by either a top level declaration: -- --
--   data T a :: *
--   
-- -- Or an associated data type declaration, within a class declaration: -- --
--   class C a b where
--     data T b :: *
--   
DataFamilyTyCon :: AlgTyConRhs -- | Information about those TyCons derived from a data -- declaration. This includes data types with no constructors at all. DataTyCon :: [DataCon] -> Bool -> AlgTyConRhs -- | The data type constructors; can be empty if the user declares the type -- to have no constructors -- -- INVARIANT: Kept in order of increasing DataCon tag (see the tag -- assignment in DataCon.mkDataCon) data_cons :: AlgTyConRhs -> [DataCon] -- | Cached value: is this an enumeration type? See Note [Enumeration -- types] is_enum :: AlgTyConRhs -> Bool -- | Information about those TyCons derived from a newtype -- declaration NewTyCon :: DataCon -> Type -> ([TyVar], Type) -> Maybe TyCon -> AlgTyConRhs -- | The unique constructor for the newtype. It has no -- existentials data_con :: AlgTyConRhs -> DataCon -- | Cached value: the argument type of the constructor, which is just the -- representation type of the TyCon (remember that -- newtypes do not exist at runtime so need a different -- representation type). -- -- The free TyVars of this type are the tyConTyVars from -- the corresponding TyCon nt_rhs :: AlgTyConRhs -> Type -- | Same as the nt_rhs, but this time eta-reduced. Hence the list -- of TyVars in this field may be shorter than the declared arity -- of the TyCon. nt_etad_rhs :: AlgTyConRhs -> ([TyVar], Type) -- | A TyCon (which is always a CoTyCon) that can have a -- Coercion extracted from it to create the newtype -- from the representation Type. -- -- This field is optional for non-recursive newtypes only. nt_co :: AlgTyConRhs -> Maybe TyCon -- | Extract those DataCons that we are able to learn about. Note -- that visibility in this sense does not correspond to visibility in the -- context of any particular user program! -- -- Both type classes as well as family instances imply implicit type -- constructors. These implicit type constructors refer to their parent -- structure (ie, the class or family from which they derive) using a -- type of the following form. We use TyConParent for both -- algebraic and synonym types, but the variant ClassTyCon will -- only be used by algebraic TyCons. visibleDataCons :: AlgTyConRhs -> [DataCon] data TyConParent -- | An ordinary type constructor has no parent. NoParentTyCon :: TyConParent -- | Type constructors representing a class dictionary. ClassTyCon :: Class -> TyConParent -- | An *associated* type of a class. AssocFamilyTyCon :: Class -> TyConParent -- | Type constructors representing an instance of a type family. -- Parameters: -- -- 1) The type family in question -- -- 2) Instance types; free variables are the tyConTyVars of the -- current TyCon (not the family one). INVARIANT: the number of -- types matches the arity of the family TyCon -- -- 3) A CoTyCon identifying the representation type with the type -- instance family FamInstTyCon :: TyCon -> [Type] -> TyCon -> TyConParent isNoParent :: TyConParent -> Bool -- | Information pertaining to the expansion of a type synonym -- (type) data SynTyConRhs -- | An ordinary type synonyn. SynonymTyCon :: Type -> SynTyConRhs -- | A type synonym family e.g. type family F x y :: * -> * SynFamilyTyCon :: SynTyConRhs data CoTyConDesc CoSym :: CoTyConDesc CoTrans :: CoTyConDesc CoLeft :: CoTyConDesc CoRight :: CoTyConDesc CoCsel1 :: CoTyConDesc CoCsel2 :: CoTyConDesc CoCselR :: CoTyConDesc CoInst :: CoTyConDesc CoAxiom :: [TyVar] -> Type -> Type -> CoTyConDesc co_ax_tvs :: CoTyConDesc -> [TyVar] co_ax_lhs :: CoTyConDesc -> Type co_ax_rhs :: CoTyConDesc -> Type CoUnsafe :: CoTyConDesc -- | This is the making of an algebraic TyCon. Notably, you have to -- pass in the generic (in the -XGenerics sense) information about the -- type constructor - you can get hold of it easily (see Generics module) mkAlgTyCon :: Name -> Kind -> [TyVar] -> [PredType] -> AlgTyConRhs -> TyConParent -> RecFlag -> Bool -> Bool -> TyCon -- | Simpler specialization of mkAlgTyCon for classes mkClassTyCon :: Name -> Kind -> [TyVar] -> AlgTyConRhs -> Class -> RecFlag -> TyCon -- | Given the name of the function type constructor and it's kind, create -- the corresponding TyCon. It is reccomended to use -- TypeRep.funTyCon if you want this functionality mkFunTyCon :: Name -> Kind -> TyCon -- | Create an unlifted primitive TyCon, such as Int# mkPrimTyCon :: Name -> Kind -> Arity -> PrimRep -> TyCon -- | Kind constructors mkKindTyCon :: Name -> Kind -> TyCon -- | Create a lifted primitive TyCon such as RealWorld mkLiftedPrimTyCon :: Name -> Kind -> Arity -> PrimRep -> TyCon -- | Foreign-imported (.NET) type constructors are represented as -- primitive, but lifted, TyCons for now. They are lifted -- because the Haskell type T representing the (foreign) .NET -- type T is actually implemented (in ILX) as a -- thunkT mkTupleTyCon :: Name -> Kind -> Arity -> [TyVar] -> DataCon -> Boxity -> Bool -> TyCon -- | Create a type synonym TyCon mkSynTyCon :: Name -> Kind -> [TyVar] -> SynTyConRhs -> TyConParent -> TyCon -- | Create a super-kind TyCon mkSuperKindTyCon :: Name -> TyCon -- | Create a coercion TyCon mkCoercionTyCon :: Name -> Arity -> CoTyConDesc -> TyCon mkForeignTyCon :: Name -> Maybe FastString -> Kind -> Arity -> TyCon mkAnyTyCon :: Name -> Kind -> TyCon -- | Returns True if the supplied TyCon resulted from -- either a data or newtype declaration isAlgTyCon :: TyCon -> Bool -- | Is this TyCon that for a class instance? isClassTyCon :: TyCon -> Bool -- | Is this TyCon that for a family instance, be that for a synonym -- or an algebraic family instance? isFamInstTyCon :: TyCon -> Bool isFunTyCon :: TyCon -> Bool -- | Does this TyCon represent something that cannot be defined in -- Haskell? isPrimTyCon :: TyCon -> Bool -- | Does this TyCon represent a tuple? -- -- NB: when compiling Data.Tuple, the tycons won't reply -- True to isTupleTyCon, becuase they are built as -- AlgTyCons. However they get spat into the interface file as -- tuple tycons, so I don't think it matters. isTupleTyCon :: TyCon -> Bool -- | Is this the TyCon for an unboxed tuple? isUnboxedTupleTyCon :: TyCon -> Bool -- | Is this the TyCon for a boxed tuple? isBoxedTupleTyCon :: TyCon -> Bool -- | A product TyCon must both: -- --
    --
  1. Have one constructor
  2. --
  3. Not be existential
  4. --
-- -- However other than this there are few restrictions: they may be -- data or newtype TyCons of any boxity and may -- even be recursive. -- -- Is this a TyCon representing a type synonym (type)? isSynTyCon :: TyCon -> Bool -- | Is this a synonym TyCon that can have no further instances -- appear? isClosedSynTyCon :: TyCon -> Bool -- | Is this a super-kind TyCon? isSuperKindTyCon :: TyCon -> Bool isDecomposableTyCon :: TyCon -> Bool -- | Is this a TyCon that represents a coercion? isCoercionTyCon :: TyCon -> Bool -- | Attempt to pull a TyCon apart into the arity and -- coKindFun of a coercion TyCon. Returns -- Nothing if the TyCon is not of the appropriate kind isCoercionTyCon_maybe :: TyCon -> Maybe (Arity, CoTyConDesc) -- | Is this the TyCon of a foreign-imported type constructor? isForeignTyCon :: TyCon -> Bool -- | Is this an AnyTyCon? isAnyTyCon :: TyCon -> Bool tyConHasKind :: TyCon -> Bool -- | Injective TyCons can be decomposed, so that T ty1 ~ T ty2 => -- ty1 ~ ty2 isInjectiveTyCon :: TyCon -> Bool -- | Returns True for data types that are definitely -- represented by heap-allocated constructors. These are scrutinised by -- Core-level case expressions, and they get info tables -- allocated for them. -- -- Generally, the function will be true for all data types and -- false for newtypes, unboxed tuples and type family -- TyCons. But it is not guarenteed to return True in all -- cases that it could. -- -- NB: for a data type family, only the instance TyCons get -- an info table. The family declaration TyCon does not isDataTyCon :: TyCon -> Bool isProductTyCon :: TyCon -> Bool -- | Is this an algebraic TyCon which is just an enumeration of -- values? isEnumerationTyCon :: TyCon -> Bool -- | Is this TyCon that for a newtype isNewTyCon :: TyCon -> Bool -- | Test if the TyCon is algebraic but abstract (invisible data -- constructors) isAbstractTyCon :: TyCon -> Bool -- | Is this a TyCon, synonym or otherwise, that may have further -- instances appear? isFamilyTyCon :: TyCon -> Bool -- | Is this a synonym TyCon that can have may have further -- instances appear? isSynFamilyTyCon :: TyCon -> Bool -- | Is this a synonym TyCon that can have may have further -- instances appear? isDataFamilyTyCon :: TyCon -> Bool -- | Is this TyCon unlifted (i.e. cannot contain bottom)? Note that -- this can only be true for primitive and unboxed-tuple TyCons isUnLiftedTyCon :: TyCon -> Bool -- | Is this an algebraic TyCon declared with the GADT syntax? isGadtSyntaxTyCon :: TyCon -> Bool -- | Are we able to extract informationa TyVar to class argument -- list mappping from a given TyCon? isTyConAssoc :: TyCon -> Bool -- | Is this a recursive TyCon? isRecursiveTyCon :: TyCon -> Bool -- | Did this TyCon originate from type-checking a .h*-boot file? isHiBootTyCon :: TyCon -> Bool -- | Identifies implicit tycons that, in particular, do not go into -- interface files (because they are implicitly reconstructed when the -- interface is read). -- -- Note that: -- -- isImplicitTyCon :: TyCon -> Bool -- | Does this TyCon have any generic to/from functions available? -- See also hasGenerics tyConHasGenerics :: TyCon -> Bool tyConName :: TyCon -> Name tyConKind :: TyCon -> Kind tyConUnique :: TyCon -> Unique tyConTyVars :: TyCon -> [TyVar] -- | As tyConDataCons_maybe, but returns the empty list of -- constructors if no constructors could be found tyConDataCons :: TyCon -> [DataCon] -- | Determine the DataCons originating from the given TyCon, -- if the TyCon is the sort that can have any constructors (note: -- this does not include abstract algebraic types) tyConDataCons_maybe :: TyCon -> Maybe [DataCon] -- | If the given TyCon has a single data constructor, i.e. -- it is a data type with one alternative, a tuple type or a -- newtype then that constructor is returned. If the -- TyCon has more than one constructor, or represents a primitive -- or function type constructor then Nothing is returned. In any -- other case, the function panics tyConSingleDataCon_maybe :: TyCon -> Maybe DataCon -- | Determine the number of value constructors a TyCon has. Panics -- if the TyCon is not algebraic or a tuple tyConFamilySize :: TyCon -> Int -- | Find the "stupid theta" of the TyCon. A "stupid theta" is the -- context to the left of an algebraic type declaration, e.g. Eq -- a in the declaration data Eq a => T a ... tyConStupidTheta :: TyCon -> [PredType] tyConArity :: TyCon -> Arity tyConParent :: TyCon -> TyConParent -- | If this TyCon is that for a class instance, return the class it -- is for. Otherwise returns Nothing tyConClass_maybe :: TyCon -> Maybe Class -- | If this TyCon is that of a family instance, return the family -- in question and the instance types. Otherwise, return Nothing tyConFamInst_maybe :: TyCon -> Maybe (TyCon, [Type]) -- | If this TyCon is that of a family instance, return a -- TyCon which represents a coercion identifying the -- representation type with the type instance family. Otherwise, return -- Nothing tyConFamilyCoercion_maybe :: TyCon -> Maybe TyCon tyConFamInstSig_maybe :: TyCon -> Maybe (TyCon, [Type], TyCon) -- | Extract the TyVars bound by a type synonym and the -- corresponding (unsubstituted) right hand side. If the given -- TyCon is not a type synonym, panics synTyConDefn :: TyCon -> ([TyVar], Type) -- | Extract the information pertaining to the right hand side of a type -- synonym (type) declaration. Panics if the given TyCon -- is not a type synonym synTyConRhs :: TyCon -> SynTyConRhs -- | Find the expansion of the type synonym represented by the given -- TyCon. The free variables of this type will typically include -- those TyVars bound by the TyCon. Panics if the -- TyCon is not that of a type synonym synTyConType :: TyCon -> Type -- | Just e for foreign-imported types, holds the name of the -- imported thing tyConExtName :: TyCon -> Maybe FastString -- | Extract an AlgTyConRhs with information about data constructors -- from an algebraic or tuple TyCon. Panics for any other sort of -- TyCon algTyConRhs :: TyCon -> AlgTyConRhs -- | Extract the bound type variables and type expansion of a type synonym -- TyCon. Panics if the TyCon is not a synonym newTyConRhs :: TyCon -> ([TyVar], Type) -- | Extract the bound type variables and type expansion of an -- eta-contracted type synonym TyCon. Panics if the TyCon -- is not a synonym newTyConEtadRhs :: TyCon -> ([TyVar], Type) -- | Take a TyCon apart into the TyVars it scopes over, the -- Type it expands into, and (possibly) a coercion from the -- representation type to the newtype. Returns Nothing -- if this is not possible. unwrapNewTyCon_maybe :: TyCon -> Maybe ([TyVar], Type, Maybe TyCon) -- | Extract the boxity of the given TyCon, if it is a -- TupleTyCon. Panics otherwise tupleTyConBoxity :: TyCon -> Boxity -- | Used to create the view the typechecker has on TyCons. -- We expand (closed) synonyms only, cf. coreExpandTyCon_maybe -- -- Used to create the view Core has on TyCons. We expand -- not only closed synonyms like tcExpandTyCon_maybe, but also -- non-recursive newtypes tcExpandTyCon_maybe :: TyCon -> [Type] -> Maybe ([(TyVar, Type)], Type, [Type]) coreExpandTyCon_maybe :: TyCon -> [Type] -> Maybe ([(TyVar, Type)], Type, [Type]) -- | Make an algebraic TyCon abstract. Panics if the supplied -- TyCon is not algebraic makeTyConAbstract :: TyCon -> TyCon -- | Extracts the newtype coercion from such a TyCon, which -- can be used to construct something with the newtypes type -- from its representation type (right hand side). If the supplied -- TyCon is not a newtype, returns Nothing newTyConCo_maybe :: TyCon -> Maybe TyCon -- | A PrimRep is an abstraction of a type. It contains information -- that the code generator needs in order to pass arguments, return -- results, and store values of this type. data PrimRep VoidRep :: PrimRep PtrRep :: PrimRep -- | Signed, word-sized value IntRep :: PrimRep -- | Unsigned, word-sized value WordRep :: PrimRep -- | Signed, 64 bit value (with 32-bit words only) Int64Rep :: PrimRep -- | Unsigned, 64 bit value (with 32-bit words only) Word64Rep :: PrimRep -- | A pointer, but not to a Haskell value (use PtrRep) AddrRep :: PrimRep FloatRep :: PrimRep DoubleRep :: PrimRep -- | Find the primitive representation of a TyCon tyConPrimRep :: TyCon -> PrimRep -- | Find the size of a PrimRep, in words primRepSizeW :: PrimRep -> Int instance Eq PrimRep instance Show PrimRep instance Data TyCon instance Typeable TyCon instance NamedThing TyCon instance Outputable TyCon instance Outputable CoTyConDesc instance Uniquable TyCon instance Ord TyCon instance Eq TyCon instance Outputable PrimRep -- | Main functions for manipulating types and type-related things module Type -- | A typecheckable-thing, essentially anything that has a name data TyThing AnId :: Id -> TyThing ADataCon :: DataCon -> TyThing ATyCon :: TyCon -> TyThing AClass :: Class -> TyThing -- | The key representation of types within the compiler data Type -- | A type of the form PredTy p represents a value whose type is -- the Haskell predicate p, where a predicate is what occurs -- before the => in a Haskell type. It can be expanded into -- its representation, but: -- -- -- -- Consider these examples: -- --
--   f :: (Eq a) => a -> Int
--   g :: (?x :: Int -> Int) => a -> Int
--   h :: (r\l) => {r} => {l::Int | r}
--   
-- -- Here the Eq a and ?x :: Int -> Int and -- rl are all called "predicates" data PredType -- | Class predicate e.g. Eq a ClassP :: Class -> [Type] -> PredType -- | Implicit parameter e.g. ?x :: Int IParam :: (IPName Name) -> Type -> PredType -- | Equality predicate e.g ty1 ~ ty2 EqPred :: Type -> Type -> PredType -- | A collection of PredTypes type ThetaType = [PredType] mkTyVarTy :: TyVar -> Type mkTyVarTys :: [TyVar] -> [Type] -- | Attempts to obtain the type variable underlying a Type, and -- panics with the given message if this is not a type variable type. See -- also getTyVar_maybe getTyVar :: String -> Type -> TyVar -- | Attempts to obtain the type variable underlying a Type getTyVar_maybe :: Type -> Maybe TyVar -- | Applies a type to another, as in e.g. k a mkAppTy :: Type -> Type -> Type mkAppTys :: Type -> [Type] -> Type -- | Attempts to take a type application apart, as in -- splitAppTy_maybe, and panics if this is not possible splitAppTy :: Type -> (Type, Type) -- | Recursively splits a type as far as is possible, leaving a residual -- type being applied to and the type arguments applied to it. Never -- fails, even if that means returning an empty list of type -- applications. splitAppTys :: Type -> (Type, [Type]) -- | Attempt to take a type application apart, whether it is a function, -- type constructor, or plain type application. Note that type family -- applications are NEVER unsaturated by this! splitAppTy_maybe :: Type -> Maybe (Type, Type) -- | Does the AppTy split as in splitAppTy_maybe, but assumes that -- any Core view stuff is already done repSplitAppTy_maybe :: Type -> Maybe (Type, Type) -- | Creates a function type from the given argument and result type mkFunTy :: Type -> Type -> Type mkFunTys :: [Type] -> Type -> Type -- | Attempts to extract the argument and result types from a type, and -- panics if that is not possible. See also splitFunTy_maybe splitFunTy :: Type -> (Type, Type) -- | Attempts to extract the argument and result types from a type splitFunTy_maybe :: Type -> Maybe (Type, Type) splitFunTys :: Type -> ([Type], Type) -- | Split off exactly the given number argument types, and panics if that -- is not possible splitFunTysN :: Int -> Type -> ([Type], Type) -- | Extract the function result type and panic if that is not possible funResultTy :: Type -> Type -- | Extract the function argument type and panic if that is not possible funArgTy :: Type -> Type -- | Splits off argument types from the given type and associating them -- with the things in the input list from left to right. The final result -- type is returned, along with the resulting pairs of objects and types, -- albeit with the list of pairs in reverse order. Panics if there are -- not enough argument types for the input list. zipFunTys :: Outputable a => [a] -> Type -> ([(a, Type)], Type) -- | A key function: builds a TyConApp or FunTy as -- apppropriate to its arguments. Applies its arguments to the -- constructor from left to right mkTyConApp :: TyCon -> [Type] -> Type -- | Create the plain type constructor type which has been applied to no -- type arguments at all. mkTyConTy :: TyCon -> Type -- | The same as fst . splitTyConApp tyConAppTyCon :: Type -> TyCon -- | The same as snd . splitTyConApp tyConAppArgs :: Type -> [Type] -- | Attempts to tease a type apart into a type constructor and the -- application of a number of arguments to that constructor splitTyConApp_maybe :: Type -> Maybe (TyCon, [Type]) -- | Attempts to tease a type apart into a type constructor and the -- application of a number of arguments to that constructor. Panics if -- that is not possible. See also splitTyConApp_maybe splitTyConApp :: Type -> (TyCon, [Type]) mkForAllTy :: TyVar -> Type -> Type -- | Wraps foralls over the type using the provided TyVars from left -- to right mkForAllTys :: [TyVar] -> Type -> Type -- | Attempts to take a forall type apart, returning the bound type -- variable and the remainder of the type splitForAllTy_maybe :: Type -> Maybe (TyVar, Type) -- | Attempts to take a forall type apart, returning all the immediate such -- bound type variables and the remainder of the type. Always suceeds, -- even if that means returning an empty list of TyVars splitForAllTys :: Type -> ([TyVar], Type) -- | Instantiate a forall type with one or more type arguments. Used when -- we have a polymorphic function applied to type args: -- --
--   f t1 t2
--   
-- -- We use applyTys type-of-f [t1,t2] to compute the type of the -- expression. Panics if no application is possible. applyTy :: Type -> Type -> Type -- | This function is interesting because: -- --
    --
  1. The function may have more for-alls than there are args
  2. --
  3. Less obviously, it may have fewer for-alls
  4. --
-- -- For case 2. think of: -- --
--   applyTys (forall a.a) [forall b.b, Int]
--   
-- -- This really can happen, via dressing up polymorphic types with newtype -- clothing. Here's an example: -- --
--   newtype R = R (forall a. a->a)
--   foo = case undefined :: R of
--              R f -> f ()
--   
applyTys :: Type -> [Type] -> Type applyTysD :: SDoc -> Type -> [Type] -> Type isForAllTy :: Type -> Bool -- | Equivalent to snd . splitForAllTys dropForAlls :: Type -> Type -- | Unwrap one layer of newtype on a type constructor and its -- arguments, using an eta-reduced version of the newtype if -- possible newTyConInstRhs :: TyCon -> [Type] -> Type carefullySplitNewType_maybe :: [TyCon] -> TyCon -> [Type] -> Maybe ([TyCon], Type) -- | Finds type family instances occuring in a type after expanding -- synonyms. tyFamInsts :: Type -> [(TyCon, [Type])] -- | Finds type family instances occuring in a predicate type after -- expanding synonyms. predFamInsts :: PredType -> [(TyCon, [Type])] mkPredTy :: PredType -> Type mkPredTys :: ThetaType -> [Type] -- | Given a family instance TyCon and its arg types, return the -- corresponding family type. E.g: -- --
--   data family T a
--   data instance T (Maybe b) = MkT b
--   
-- -- Where the instance tycon is :RTL, so: -- --
--   mkFamilyTyConApp :RTL Int  =  T (Maybe Int)
--   
mkFamilyTyConApp :: TyCon -> [Type] -> Type isEqPred :: PredType -> Bool coVarPred :: CoVar -> PredType funTyCon :: TyCon isTyVarTy :: Type -> Bool isFunTy :: Type -> Bool isDictTy :: Type -> Bool -- | See Type#type_classification for what an unlifted type is isUnLiftedType :: Type -> Bool isUnboxedTupleType :: Type -> Bool -- | See Type#type_classification for what an algebraic type is. -- Should only be applied to types, as opposed to e.g. partially -- saturated type constructors isAlgType :: Type -> Bool -- | See Type#type_classification for what an algebraic type is. -- Should only be applied to types, as opposed to e.g. partially -- saturated type constructors. Closed type constructors are those with a -- fixed right hand side, as opposed to e.g. associated types isClosedAlgType :: Type -> Bool -- | Returns true of types that are opaque to Haskell. Most of these are -- unlifted, but now that we interact with .NET, we may have primtive -- (foreign-imported) types that are lifted isPrimitiveType :: Type -> Bool -- | Computes whether an argument (or let right hand side) should be -- computed strictly or lazily, based only on its type. Works just like -- isUnLiftedType, except that it has a special case for -- dictionaries (i.e. does not work purely on representation types) isStrictType :: Type -> Bool -- | We may be strict in dictionary types, but only if it has more than one -- component. -- -- (Being strict in a single-component dictionary risks poking the -- dictionary component, which is wrong.) isStrictPred :: PredType -> Bool -- | The key type representing kinds in the compiler. Invariant: a kind is -- always in one of these forms: -- --
--   FunTy k1 k2
--   TyConApp PrimTyCon [...]
--   TyVar kv   -- (during inference only)
--   ForAll ... -- (for top-level coercions)
--   
type Kind = Type type SimpleKind = Kind type KindVar = TyVar liftedTypeKind :: Kind -- | See Type#kind_subtyping for details of the distinction between -- these Kinds unliftedTypeKind :: Kind openTypeKind :: Kind argTypeKind :: Kind ubxTupleKind :: Kind tySuperKind :: SuperKind coSuperKind :: SuperKind liftedTypeKindTyCon :: TyCon openTypeKindTyCon :: TyCon unliftedTypeKindTyCon :: TyCon argTypeKindTyCon :: TyCon ubxTupleKindTyCon :: TyCon -- | NB: for type synonyms tyVarsOfType does not expand the synonym tyVarsOfType :: Type -> TyVarSet tyVarsOfTypes :: [Type] -> TyVarSet tyVarsOfPred :: PredType -> TyVarSet tyVarsOfTheta :: ThetaType -> TyVarSet -- | Expand out all type synonyms. Actually, it'd suffice to expand out -- just the ones that discard type variables (e.g. type Funny a = Int) -- But we don't know which those are currently, so we just expand all. expandTypeSynonyms :: Type -> Type -- | Type equality test for Core types (i.e. ignores predicate-types, -- synonyms etc.) coreEqType :: Type -> Type -> Bool coreEqType2 :: RnEnv2 -> Type -> Type -> Bool -- | Type equality on source types. Does not look through newtypes -- or PredTypes, but it does look through type synonyms. tcEqType :: Type -> Type -> Bool tcEqTypes :: [Type] -> [Type] -> Bool -- | Type ordering on source types. Does not look through newtypes -- or PredTypes, but it does look through type synonyms. tcCmpType :: Type -> Type -> Ordering tcCmpTypes :: [Type] -> [Type] -> Ordering tcEqPred :: PredType -> PredType -> Bool tcEqPredX :: RnEnv2 -> PredType -> PredType -> Bool tcCmpPred :: PredType -> PredType -> Ordering tcEqTypeX :: RnEnv2 -> Type -> Type -> Bool -- | Checks whether the second argument is a subterm of the first. (We -- don't care about binders, as we are only interested in syntactic -- subterms.) tcPartOfType :: Type -> Type -> Bool tcPartOfPred :: Type -> PredType -> Bool seqType :: Type -> () seqTypes :: [Type] -> () -- | In Core, we "look through" non-recursive newtypes and -- PredTypes: this function tries to obtain a different view of -- the supplied type given this -- -- Strips off the top layer only of a type to give its underlying -- representation type. Returns Nothing if there is nothing to look -- through. -- -- In the case of newtypes, it returns one of: -- -- 1) A vanilla TyConApp (recursive newtype, or non-saturated) -- -- 2) The newtype representation (otherwise), meaning the type written in -- the RHS of the newtype declaration, which may itself be a newtype -- -- For example, with: -- --
--   newtype R = MkR S
--   newtype S = MkS T
--   newtype T = MkT (T -> T)
--   
-- -- expandNewTcApp on: -- -- coreView :: Type -> Maybe Type -- | Similar to coreView, but for the type checker, which just looks -- through synonyms tcView :: Type -> Maybe Type -- | Similar to coreView or tcView, but works on Kinds kindView :: Kind -> Maybe Kind -- | Looks through: -- --
    --
  1. For-alls 2. Synonyms 3. Predicates 4. All newtypes, including -- recursive ones, but not newtype families
  2. --
-- -- It's useful in the back end of the compiler. repType :: Type -> Type -- | A PrimRep is an abstraction of a type. It contains information -- that the code generator needs in order to pass arguments, return -- results, and store values of this type. data PrimRep VoidRep :: PrimRep PtrRep :: PrimRep -- | Signed, word-sized value IntRep :: PrimRep -- | Unsigned, word-sized value WordRep :: PrimRep -- | Signed, 64 bit value (with 32-bit words only) Int64Rep :: PrimRep -- | Unsigned, 64 bit value (with 32-bit words only) Word64Rep :: PrimRep -- | A pointer, but not to a Haskell value (use PtrRep) AddrRep :: PrimRep FloatRep :: PrimRep DoubleRep :: PrimRep -- | Discovers the primitive representation of a more abstract Type typePrimRep :: Type -> PrimRep -- | Convert a PredType to its representation type. However, it -- unwraps only the outermost level; for example, the result might be a -- newtype application predTypeRep :: PredType -> Type -- | A substitition of Types for TyVars type TvSubstEnv = TyVarEnv Type -- | Type substitution -- -- The following invariants must hold of a TvSubst: -- --
    --
  1. The in-scope set is needed only to guide the generation of -- fresh uniques
  2. --
  3. In particular, the kind of the type variables in the -- in-scope set is not relevant
  4. --
  5. The substition is only applied ONCE! This is because in general -- such application will not reached a fixed point.
  6. --
data TvSubst TvSubst :: InScopeSet -> TvSubstEnv -> TvSubst emptyTvSubstEnv :: TvSubstEnv emptyTvSubst :: TvSubst mkTvSubst :: InScopeSet -> TvSubstEnv -> TvSubst -- | Generates the in-scope set for the TvSubst from the types in -- the incoming environment, hence open mkOpenTvSubst :: TvSubstEnv -> TvSubst -- | Generates the in-scope set for the TvSubst from the types in -- the incoming environment, hence open zipOpenTvSubst :: [TyVar] -> [Type] -> TvSubst zipTopTvSubst :: [TyVar] -> [Type] -> TvSubst -- | Called when doing top-level substitutions. Here we expect that the -- free vars of the range of the substitution will be empty. mkTopTvSubst :: [(TyVar, Type)] -> TvSubst notElemTvSubst :: TyVar -> TvSubst -> Bool getTvSubstEnv :: TvSubst -> TvSubstEnv setTvSubstEnv :: TvSubst -> TvSubstEnv -> TvSubst zapTvSubstEnv :: TvSubst -> TvSubst getTvInScope :: TvSubst -> InScopeSet extendTvInScope :: TvSubst -> Var -> TvSubst extendTvInScopeList :: TvSubst -> [Var] -> TvSubst extendTvSubst :: TvSubst -> TyVar -> Type -> TvSubst extendTvSubstList :: TvSubst -> [TyVar] -> [Type] -> TvSubst isInScope :: Var -> TvSubst -> Bool -- | (compose env1 env2)(x) is env1(env2(x)); i.e. apply -- env2 then env1. It assumes that both are idempotent. -- Typically, env1 is the refinement to a base substitution -- env2 composeTvSubst :: InScopeSet -> TvSubstEnv -> TvSubstEnv -> TvSubstEnv zipTyEnv :: [TyVar] -> [Type] -> TvSubstEnv isEmptyTvSubst :: TvSubst -> Bool unionTvSubst :: TvSubst -> TvSubst -> TvSubst -- | Substitute within a Type substTy :: TvSubst -> Type -> Type -- | Substitute within several Types substTys :: TvSubst -> [Type] -> [Type] -- | Type substitution making use of an TvSubst that is assumed to -- be open, see zipOpenTvSubst substTyWith :: [TyVar] -> [Type] -> Type -> Type -- | Type substitution making use of an TvSubst that is assumed to -- be open, see zipOpenTvSubst substTysWith :: [TyVar] -> [Type] -> [Type] -> [Type] -- | Substitute within a ThetaType substTheta :: TvSubst -> ThetaType -> ThetaType -- | Substitute within a PredType substPred :: TvSubst -> PredType -> PredType substTyVar :: TvSubst -> TyVar -> Type substTyVars :: TvSubst -> [TyVar] -> [Type] substTyVarBndr :: TvSubst -> TyVar -> (TvSubst, TyVar) -- | Remove any nested binders mentioning the TyVars in the -- TyVarSet deShadowTy :: TyVarSet -> Type -> Type lookupTyVar :: TvSubst -> TyVar -> Maybe Type pprType :: Type -> SDoc pprParendType :: Type -> SDoc pprTypeApp :: NamedThing a => a -> [Type] -> SDoc pprTyThingCategory :: TyThing -> SDoc pprTyThing :: TyThing -> SDoc pprForAll :: [TyVar] -> SDoc pprPred :: PredType -> SDoc pprEqPred :: (Type, Type) -> SDoc pprTheta :: ThetaType -> SDoc pprThetaArrow :: ThetaType -> SDoc pprClassPred :: Class -> [Type] -> SDoc pprKind :: Kind -> SDoc pprParendKind :: Kind -> SDoc -- | Pretty prints a TyCon, using the family instance in case of a -- representation tycon. For example: -- --
--   data T [a] = ...
--   
-- -- In that case we want to print T [a], where T is the -- family TyCon pprSourceTyCon :: TyCon -> SDoc instance Outputable TvSubst instance Ord PredType instance Eq PredType module HsTypes data HsType name HsForAllTy :: HsExplicitFlag -> [LHsTyVarBndr name] -> (LHsContext name) -> (LHsType name) -> HsType name HsTyVar :: name -> HsType name HsAppTy :: (LHsType name) -> (LHsType name) -> HsType name HsFunTy :: (LHsType name) -> (LHsType name) -> HsType name HsListTy :: (LHsType name) -> HsType name HsPArrTy :: (LHsType name) -> HsType name HsTupleTy :: Boxity -> [LHsType name] -> HsType name HsOpTy :: (LHsType name) -> (Located name) -> (LHsType name) -> HsType name HsParTy :: (LHsType name) -> HsType name HsNumTy :: Integer -> HsType name HsPredTy :: (HsPred name) -> HsType name HsKindSig :: (LHsType name) -> Kind -> HsType name HsQuasiQuoteTy :: (HsQuasiQuote name) -> HsType name HsSpliceTy :: (HsSplice name) -> FreeVars -> PostTcKind -> HsType name HsDocTy :: (LHsType name) -> LHsDocString -> HsType name HsBangTy :: HsBang -> (LHsType name) -> HsType name HsRecTy :: [ConDeclField name] -> HsType name HsCoreTy :: Type -> HsType name type LHsType name = Located (HsType name) data HsTyVarBndr name UserTyVar :: name -> PostTcKind -> HsTyVarBndr name KindedTyVar :: name -> Kind -> HsTyVarBndr name type LHsTyVarBndr name = Located (HsTyVarBndr name) data HsExplicitFlag Explicit :: HsExplicitFlag Implicit :: HsExplicitFlag type HsContext name = [LHsPred name] type LHsContext name = Located (HsContext name) data HsPred name HsClassP :: name -> [LHsType name] -> HsPred name HsEqualP :: (LHsType name) -> (LHsType name) -> HsPred name HsIParam :: (IPName name) -> (LHsType name) -> HsPred name type LHsPred name = Located (HsPred name) data HsQuasiQuote id HsQuasiQuote :: id -> SrcSpan -> FastString -> HsQuasiQuote id type LBangType name = Located (BangType name) type BangType name = HsType name data HsBang HsNoBang :: HsBang HsStrict :: HsBang HsUnpack :: HsBang HsUnpackFailed :: HsBang getBangType :: LHsType a -> LHsType a getBangStrictness :: LHsType a -> HsBang data ConDeclField name ConDeclField :: Located name -> LBangType name -> Maybe LHsDocString -> ConDeclField name cd_fld_name :: ConDeclField name -> Located name cd_fld_type :: ConDeclField name -> LBangType name cd_fld_doc :: ConDeclField name -> Maybe LHsDocString pprConDeclFields :: OutputableBndr name => [ConDeclField name] -> SDoc mkExplicitHsForAllTy :: [LHsTyVarBndr name] -> LHsContext name -> LHsType name -> HsType name mkImplicitHsForAllTy :: LHsContext name -> LHsType name -> HsType name hsExplicitTvs :: LHsType name -> [name] hsTyVarName :: HsTyVarBndr name -> name hsTyVarNames :: [HsTyVarBndr name] -> [name] replaceTyVarName :: HsTyVarBndr name1 -> name2 -> HsTyVarBndr name2 hsTyVarKind :: HsTyVarBndr name -> Kind hsTyVarNameKind :: HsTyVarBndr name -> (name, Kind) hsLTyVarName :: LHsTyVarBndr name -> name hsLTyVarNames :: [LHsTyVarBndr name] -> [name] hsLTyVarLocName :: LHsTyVarBndr name -> Located name hsLTyVarLocNames :: [LHsTyVarBndr name] -> [Located name] splitHsInstDeclTy :: OutputableBndr name => HsType name -> ([LHsTyVarBndr name], HsContext name, name, [LHsType name]) splitHsFunType :: LHsType name -> ([LHsType name], LHsType name) type PostTcType = Type placeHolderType :: PostTcType type PostTcKind = Kind placeHolderKind :: PostTcKind pprParendHsType :: OutputableBndr name => HsType name -> SDoc pprHsForAll :: OutputableBndr name => HsExplicitFlag -> [LHsTyVarBndr name] -> LHsContext name -> SDoc pprHsContext :: OutputableBndr name => HsContext name -> SDoc ppr_hs_context :: OutputableBndr name => HsContext name -> SDoc instance Typeable1 HsQuasiQuote instance Typeable HsExplicitFlag instance Typeable1 HsTyVarBndr instance Typeable1 HsType instance Typeable1 ConDeclField instance Typeable1 HsPred instance Data id => Data (HsQuasiQuote id) instance Data HsExplicitFlag instance Data name => Data (HsTyVarBndr name) instance Data name => Data (HsType name) instance Data name => Data (ConDeclField name) instance Data name => Data (HsPred name) instance OutputableBndr name => Outputable (HsPred name) instance Outputable name => Outputable (HsTyVarBndr name) instance OutputableBndr name => Outputable (HsType name) instance OutputableBndr id => Outputable (HsQuasiQuote id) module HsLit data HsLit HsChar :: Char -> HsLit HsCharPrim :: Char -> HsLit HsString :: FastString -> HsLit HsStringPrim :: FastString -> HsLit HsInt :: Integer -> HsLit HsIntPrim :: Integer -> HsLit HsWordPrim :: Integer -> HsLit HsInteger :: Integer -> Type -> HsLit HsRat :: Rational -> Type -> HsLit HsFloatPrim :: Rational -> HsLit HsDoublePrim :: Rational -> HsLit data HsOverLit id OverLit :: OverLitVal -> Bool -> SyntaxExpr id -> PostTcType -> HsOverLit id ol_val :: HsOverLit id -> OverLitVal ol_rebindable :: HsOverLit id -> Bool ol_witness :: HsOverLit id -> SyntaxExpr id ol_type :: HsOverLit id -> PostTcType data OverLitVal HsIntegral :: !Integer -> OverLitVal HsFractional :: !Rational -> OverLitVal HsIsString :: !FastString -> OverLitVal overLitType :: HsOverLit a -> Type instance Typeable HsLit instance Typeable OverLitVal instance Typeable1 HsOverLit instance Data HsLit instance Data OverLitVal instance Data id => Data (HsOverLit id) instance Outputable OverLitVal instance OutputableBndr id => Outputable (HsOverLit id) instance Outputable HsLit instance Ord OverLitVal instance Ord (HsOverLit id) instance Eq OverLitVal instance Eq (HsOverLit id) instance Eq HsLit module LibFFI type ForeignCallToken = C_ffi_cif prepForeignCall :: CCallConv -> [PrimRep] -> PrimRep -> IO (Ptr ForeignCallToken) -- | Module for (a) type kinds and (b) type coercions, as used in System -- FC. See CoreSyn.Expr for more on System FC and how coercions -- fit into it. -- -- Coercions are represented as types, and their kinds tell what types -- the coercion works on. The coercion kind constructor is a special -- TyCon that must always be saturated, like so: -- --
--   typeKind (symCoercion type) :: TyConApp CoTyCon{...} [type, type]
--   
module Coercion -- | A Coercion represents a Type something should be coerced -- to. type Coercion = Type -- | The key type representing kinds in the compiler. Invariant: a kind is -- always in one of these forms: -- --
--   FunTy k1 k2
--   TyConApp PrimTyCon [...]
--   TyVar kv   -- (during inference only)
--   ForAll ... -- (for top-level coercions)
--   
type Kind = Type typeKind :: Type -> Kind -- | Essentially funResultTy on kinds kindFunResult :: Kind -> Kind kindAppResult :: Kind -> [arg] -> Kind -- | Find the result Kind of a type synonym, after applying it to -- its arity number of type variables Actually this function -- works fine on data types too, but they'd always return *, so we -- never need to ask synTyConResKind :: TyCon -> Kind -- | Essentially splitFunTys on kinds splitKindFunTys :: Kind -> ([Kind], Kind) -- | Essentially splitFunTysN on kinds splitKindFunTysN :: Int -> Kind -> ([Kind], Kind) splitKindFunTy_maybe :: Kind -> Maybe (Kind, Kind) isLiftedTypeKind :: Kind -> Bool isUnliftedTypeKind :: Kind -> Bool -- | See Type#kind_subtyping for details of the distinction between -- these Kinds isOpenTypeKind :: Kind -> Bool isUbxTupleKind :: Kind -> Bool isArgTypeKind :: Kind -> Bool -- | Is this a kind (i.e. a type-of-types)? isKind :: Kind -> Bool isTySuperKind :: SuperKind -> Bool isCoSuperKind :: SuperKind -> Bool -- | Is this a super-kind (i.e. a type-of-kinds)? isSuperKind :: Type -> Bool isCoercionKind :: Kind -> Bool -- | Given two kinds k1 and k2, creates the Kind -- k1 -> k2 mkArrowKind :: Kind -> Kind -> Kind -- | Iterated application of mkArrowKind mkArrowKinds :: [Kind] -> Kind -> Kind -- | True of any sub-kind of ArgTypeKind isSubArgTypeKind :: Kind -> Bool -- | True of any sub-kind of OpenTypeKind (i.e. anything except arrow) isSubOpenTypeKind :: Kind -> Bool -- | k1 `isSubKind` k2 checks that k1 <: k2 isSubKind :: Kind -> Kind -> Bool -- | Used when generalising: default kind ? and ?? to *. See -- Type#kind_subtyping for more information on what that means defaultKind :: Kind -> Kind eqKind :: Kind -> Kind -> Bool -- | kc1 `isSubKindCon` kc2 checks that kc1 <: -- kc2 isSubKindCon :: TyCon -> TyCon -> Bool -- | Makes a CoercionKind from two types: the types whose equality -- is proven by the relevant Coercion mkCoKind :: Type -> Type -> CoercionKind -- | (mkCoPredTy s t r) produces the type: (s~t) => r mkCoPredTy :: Type -> Type -> Type -> Type coVarKind :: CoVar -> (Type, Type) coVarKind_maybe :: CoVar -> Maybe (Type, Type) -- | If it is the case that -- --
--   c :: (t1 ~ t2)
--   
-- -- i.e. the kind of c is a CoercionKind relating -- t1 and t2, then coercionKind c = (t1, t2). coercionKind :: Coercion -> (Type, Type) -- | Apply coercionKind to multiple Coercions coercionKinds :: [Coercion] -> ([Type], [Type]) isIdentityCoercion :: Coercion -> Bool isEqPred :: PredType -> Bool -- | Creates a type equality predicate mkEqPred :: (Type, Type) -> PredType -- | Splits apart a type equality predicate, if the supplied -- PredType is one. Panics otherwise getEqPredTys :: PredType -> (Type, Type) -- | Tests whether a type is just a type equality predicate isEqPredTy :: Type -> Bool -- | Make a coercion from the specified coercion TyCon and the -- Type arguments to that coercion. Try to use the -- mk*Coercion family of functions instead of using this -- function if possible mkCoercion :: TyCon -> [Type] -> Coercion -- | Create a symmetric version of the given Coercion that asserts -- equality between the same types but in the other direction, so -- a kind of t1 ~ t2 becomes the kind t2 ~ t1. mkSymCoercion :: Coercion -> Coercion -- | Create a new Coercion by exploiting transitivity on the two -- given Coercions. mkTransCoercion :: Coercion -> Coercion -> Coercion -- | From an application Coercion build a Coercion that -- asserts the equality of the functions on either side of the -- type equality. So if c has kind f x ~ g y then: -- --
--   mkLeftCoercion c :: f ~ g
--   
mkLeftCoercion :: Coercion -> Coercion -- | From an application Coercion build a Coercion that -- asserts the equality of the arguments on either side of the -- type equality. So if c has kind f x ~ g y then: -- --
--   mkLeftCoercion c :: x ~ y
--   
mkRightCoercion :: Coercion -> Coercion -- | Instantiates a Coercion with a Type argument. If -- possible, it immediately performs the resulting beta-reduction, -- otherwise it creates a suspended instantiation. mkInstCoercion :: Coercion -> Type -> Coercion -- | Apply a Coercion to another Coercion, which is -- presumably a Coercion constructor of some kind mkAppCoercion :: Coercion -> Coercion -> Coercion -- | Apply a type constructor to a list of coercions. mkTyConCoercion :: TyCon -> [Coercion] -> Coercion -- | Make a function Coercion between two other Coercions mkFunCoercion :: Coercion -> Coercion -> Coercion -- | Make a Coercion which binds a variable within an inner -- Coercion mkForAllCoercion :: Var -> Coercion -> Coercion -- | As mkInstCoercion, but instantiates the coercion with a number -- of type arguments, left-to-right mkInstsCoercion :: Coercion -> [Type] -> Coercion -- | Manufacture a coercion from this air. Needless to say, this is not -- usually safe, but it is used when we know we are dealing with bottom, -- which is one case in which it is safe. This is also used implement the -- unsafeCoerce# primitive. Optimise by pushing down through -- type constructors mkUnsafeCoercion :: Type -> Type -> Coercion -- | Create a coercion suitable for the given TyCon. The Name -- should be that of a new coercion TyCon, the TyVars the -- arguments expected by the newtype and the type the -- appropriate right hand side of the newtype, with the free -- variables a subset of those TyVars. mkNewTypeCoercion :: Name -> TyCon -> [TyVar] -> Type -> TyCon -- | Create a coercion identifying a data, newtype or -- type representation type and its family instance. It has the -- form Co tvs :: F ts ~ R tvs, where Co is the -- coercion tycon built here, F the family tycon and R -- the (derived) representation tycon. mkFamInstCoercion :: Name -> [TyVar] -> TyCon -> [Type] -> TyCon -> TyCon -- | Applies multiple Coercions to another Coercion, from -- left to right. See also mkAppCoercion mkAppsCoercion :: Coercion -> [Coercion] -> Coercion mkCsel1Coercion :: Coercion -> Coercion mkCsel2Coercion :: Coercion -> Coercion mkCselRCoercion :: Coercion -> Coercion mkClassPPredCo :: Class -> [Coercion] -> Coercion mkIParamPredCo :: (IPName Name) -> Coercion -> Coercion mkEqPredCo :: Coercion -> Coercion -> Coercion mkCoVarCoercion :: CoVar -> Coercion mkCoPredCo :: Coercion -> Coercion -> Coercion -> Coercion unsafeCoercionTyCon :: TyCon symCoercionTyCon :: TyCon -- | Coercion type constructors: avoid using these directly and instead use -- the mk*Coercion and split*Coercion family of -- functions if possible. -- -- Each coercion TyCon is built with the special CoercionTyCon record and -- carries its own kinding rule. Such CoercionTyCons must be fully -- applied by any TyConApp in which they are applied, however they may -- also be over applied (see example above) and the kinding function must -- deal with this. transCoercionTyCon :: TyCon leftCoercionTyCon :: TyCon rightCoercionTyCon :: TyCon instCoercionTyCon :: TyCon csel1CoercionTyCon :: TyCon csel2CoercionTyCon :: TyCon cselRCoercionTyCon :: TyCon decompLR_maybe :: (Type, Type) -> Maybe ((Type, Type), (Type, Type)) decompCsel_maybe :: (Type, Type) -> Maybe ((Type, Type), (Type, Type), (Type, Type)) decompInst_maybe :: (Type, Type) -> Maybe ((TyVar, TyVar), (Type, Type)) splitCoPredTy_maybe :: Type -> Maybe (Type, Type, Type) -- | Sometimes we want to look through a newtype and get its -- associated coercion. This function only strips *one layer* of -- newtype off, so the caller will usually call itself -- recursively. Furthermore, this function should only be applied to -- types of kind *, hence the newtype is always saturated. If -- co : ty ~ ty' then: -- --
--   splitNewTypeRepCo_maybe ty = Just (ty', co)
--   
-- -- The function returns Nothing for non-newtypes or -- fully-transparent newtypes. splitNewTypeRepCo_maybe :: Type -> Maybe (Type, Coercion) -- | If co :: T ts ~ rep_ty then: -- --
--   instNewTyCon_maybe T ts = Just (rep_ty, co)
--   
instNewTyCon_maybe :: TyCon -> [Type] -> Maybe (Type, CoercionI) -- | This breaks a Coercion with CoercionKind T A B C ~ T -- D E F into a list of Coercions of kinds A ~ D, -- B ~ E and E ~ F. Hence: -- --
--   decomposeCo 3 c = [right (left (left c)), right (left c), right c]
--   
decomposeCo :: Arity -> Coercion -> [Coercion] -- | Determines syntactic equality of coercions coreEqCoercion :: Coercion -> Coercion -> Bool coreEqCoercion2 :: RnEnv2 -> Coercion -> Coercion -> Bool -- | CoercionI represents a lifted ordinary Coercion, -- in that it can represent either one of: -- --
    --
  1. A proper Coercion
  2. --
  3. The identity coercion
  4. --
data CoercionI IdCo :: Type -> CoercionI ACo :: Coercion -> CoercionI isIdentityCoI :: CoercionI -> Bool -- | Smart constructor for sym on CoercionI, see also -- mkSymCoercion mkSymCoI :: CoercionI -> CoercionI -- | Smart constructor for trans on CoercionI, see also -- mkTransCoercion mkTransCoI :: CoercionI -> CoercionI -> CoercionI -- | Smart constructor for type constructor application on -- CoercionI, see also mkAppCoercion mkTyConAppCoI :: TyCon -> [CoercionI] -> CoercionI -- | Smart constructor for honest-to-god Coercion application on -- CoercionI, see also mkAppCoercion mkAppTyCoI :: CoercionI -> CoercionI -> CoercionI mkFunTyCoI :: CoercionI -> CoercionI -> CoercionI -- | Smart constructor for quantified Coercions on CoercionI, -- see also mkForAllCoercion mkForAllTyCoI :: TyVar -> CoercionI -> CoercionI -- | Return either the Coercion contained within the -- CoercionI or the given Type if the CoercionI is -- the identity Coercion fromCoI :: CoercionI -> Type -- | Smart constructor for class Coercions on CoercionI. -- Satisfies: -- --
--   mkClassPPredCoI cls tys cois :: PredTy (cls tys) ~ PredTy (cls (tys `cast` cois))
--   
mkClassPPredCoI :: Class -> [CoercionI] -> CoercionI -- | Smart constructor for implicit parameter Coercions on -- CoercionI. Similar to mkClassPPredCoI mkIParamPredCoI :: (IPName Name) -> CoercionI -> CoercionI -- | Smart constructor for type equality Coercions on -- CoercionI. Similar to mkClassPPredCoI mkEqPredCoI :: CoercionI -> CoercionI -> CoercionI mkCoPredCoI :: CoercionI -> CoercionI -> CoercionI -> CoercionI instance Outputable CoercionI module DataCon -- | A data constructor data DataCon -- | Contains the Ids of the data constructor functions data DataConIds DCIds :: (Maybe Id) -> Id -> DataConIds -- | Type of the tags associated with each constructor possibility type ConTag = Int -- | Build a new data constructor mkDataCon :: Name -> Bool -> [HsBang] -> [FieldLabel] -> [TyVar] -> [TyVar] -> [(TyVar, Type)] -> ThetaType -> [Type] -> Type -> TyCon -> ThetaType -> DataConIds -> DataCon -- | Tags are allocated from here for real constructors fIRST_TAG :: ConTag -- | The representation type of the data constructor, i.e. the sort type -- that will represent values of this type at runtime dataConRepType :: DataCon -> Type -- | The "signature" of the DataCon returns, in order: -- -- 1) The result of dataConAllTyVars, -- -- 2) All the ThetaTypes relating to the DataCon (coercion, -- dictionary, implicit parameter - whatever) -- -- 3) The type arguments to the constructor -- -- 4) The original result type of the DataCon dataConSig :: DataCon -> ([TyVar], ThetaType, [Type], Type) -- | The "full signature" of the DataCon returns, in order: -- -- 1) The result of dataConUnivTyVars -- -- 2) The result of dataConExTyVars -- -- 3) The result of dataConEqSpec -- -- 4) The result of dataConDictTheta -- -- 5) The original argument types to the DataCon (i.e. before any -- change of the representation of the type) -- -- 6) The original result type of the DataCon dataConFullSig :: DataCon -> ([TyVar], [TyVar], [(TyVar, Type)], ThetaType, ThetaType, [Type], Type) -- | The Name of the DataCon, giving it a unique, rooted -- identification dataConName :: DataCon -> Name -- | The string package:module.name identifying a constructor, -- which is attached to its info table and used by the GHCi debugger and -- the heap profiler dataConIdentity :: DataCon -> [Word8] -- | The tag used for ordering DataCons dataConTag :: DataCon -> ConTag -- | The type constructor that we are building via this data constructor dataConTyCon :: DataCon -> TyCon -- | The original type constructor used in the definition of this data -- constructor. In case of a data family instance, that will be the -- family type constructor. dataConOrigTyCon :: DataCon -> TyCon -- | The user-declared type of the data constructor in the nice-to-read -- form: -- --
--   T :: forall a b. a -> b -> T [a]
--   
-- -- rather than: -- --
--   T :: forall a c. forall b. (c~[a]) => a -> b -> T c
--   
-- -- NB: If the constructor is part of a data instance, the result type -- mentions the family tycon, not the internal one. dataConUserType :: DataCon -> Type -- | The universally-quantified type variables of the constructor dataConUnivTyVars :: DataCon -> [TyVar] -- | The existentially-quantified type variables of the constructor dataConExTyVars :: DataCon -> [TyVar] -- | Both the universal and existentiatial type variables of the -- constructor dataConAllTyVars :: DataCon -> [TyVar] -- | Equalities derived from the result type of the data constructor, as -- written by the programmer in any GADT declaration dataConEqSpec :: DataCon -> [(TyVar, Type)] eqSpecPreds :: [(TyVar, Type)] -> ThetaType -- | The equational constraints on the data constructor type dataConEqTheta :: DataCon -> ThetaType -- | The type class and implicit parameter contsraints on the data -- constructor type dataConDictTheta :: DataCon -> ThetaType -- | The "stupid theta" of the DataCon, such as data Eq a -- in: -- --
--   data Eq a => T a = ...
--   
dataConStupidTheta :: DataCon -> ThetaType -- | Finds the instantiated types of the arguments required to construct a -- DataCon representation NB: these INCLUDE any dictionary args -- but EXCLUDE the data-declaration context, which is discarded It's all -- post-flattening etc; this is a representation type dataConInstArgTys :: DataCon -> [Type] -> [Type] -- | Returns the argument types of the wrapper, excluding all dictionary -- arguments and without substituting for any type variables dataConOrigArgTys :: DataCon -> [Type] dataConOrigResTy :: DataCon -> Type -- | Returns just the instantiated value argument types of a -- DataCon, (excluding dictionary args) dataConInstOrigArgTys :: DataCon -> [Type] -> [Type] -- | Returns the arg types of the worker, including all dictionaries, after -- any flattening has been done and without substituting for any type -- variables dataConRepArgTys :: DataCon -> [Type] -- | The labels for the fields of this particular DataCon dataConFieldLabels :: DataCon -> [FieldLabel] -- | Extract the type for any given labelled field of the DataCon dataConFieldType :: DataCon -> FieldLabel -> Type -- | The strictness markings decided on by the compiler. Does not include -- those for existential dictionaries. The list is in one-to-one -- correspondence with the arity of the DataCon dataConStrictMarks :: DataCon -> [HsBang] -- | Strictness of existential arguments only dataConExStricts :: DataCon -> [HsBang] -- | Source-level arity of the data constructor dataConSourceArity :: DataCon -> Arity -- | Gives the number of actual fields in the representation of the -- data constructor. This may be more than appear in the source code; the -- extra ones are the existentially quantified dictionaries dataConRepArity :: DataCon -> Int -- | Should the DataCon be presented infix? dataConIsInfix :: DataCon -> Bool -- | Get the Id of the DataCon worker: a function that is the -- actual constructor and has no top level binding in the program. -- The type may be different from the obvious one written in the source -- program. Panics if there is no such Id for this DataCon dataConWorkId :: DataCon -> Id -- | Returns an Id which looks like the Haskell-source constructor by using -- the wrapper if it exists (see dataConWrapId_maybe) and failing -- over to the worker (see dataConWorkId) dataConWrapId :: DataCon -> Id -- | Get the Id of the DataCon wrapper: a function that wraps the -- actual constructor so it has the type visible in the source -- program: c.f. dataConWorkId. Returns Nothing if there is no -- wrapper, which occurs for an algebraic data constructor and also for a -- newtype (whose constructor is inlined compulsorily) dataConWrapId_maybe :: DataCon -> Maybe Id -- | Find all the Ids implicitly brought into scope by the data -- constructor. Currently, the union of the dataConWorkId and the -- dataConWrapId dataConImplicitIds :: DataCon -> [Id] -- | Give the demands on the arguments of a Core constructor application -- (Con dc args) dataConRepStrictness :: DataCon -> [StrictnessMark] -- | Return whether there are any argument types for this DataCons -- original source type isNullarySrcDataCon :: DataCon -> Bool -- | Return whether there are any argument types for this DataCons -- runtime representation type isNullaryRepDataCon :: DataCon -> Bool isTupleCon :: DataCon -> Bool isUnboxedTupleCon :: DataCon -> Bool -- | Vanilla DataCons are those that are nice boring Haskell 98 -- constructors isVanillaDataCon :: DataCon -> Bool classDataCon :: Class -> DataCon -- | Extract the type constructor, type argument, data constructor and it's -- representation argument types from a type if it is a product -- type. -- -- Precisely, we return Just for any type that is all of: -- -- -- -- Whether the type is a data type or a newtype splitProductType_maybe :: Type -> Maybe (TyCon, [Type], DataCon, [Type]) -- | As splitProductType_maybe, but panics if the Type is not -- a product type splitProductType :: String -> Type -> (TyCon, [Type], DataCon, [Type]) -- | As deepSplitProductType_maybe, but panics if the Type is -- not a product type deepSplitProductType :: String -> Type -> (TyCon, [Type], DataCon, [Type]) -- | As splitProductType_maybe, but in turn instantiates the -- TyCon returned and hence recursively tries to unpack it as far -- as it able to deepSplitProductType_maybe :: Type -> Maybe (TyCon, [Type], DataCon, [Type]) instance Data DataCon instance Typeable DataCon instance Show DataCon instance Outputable DataCon instance NamedThing DataCon instance Uniquable DataCon instance Ord DataCon instance Eq DataCon module Vectorise.Type.Classify type TyConGroup = ([TyCon], UniqSet TyCon) -- | Split the given tycons into two sets depending on whether they have to -- be converted (first list) or not (second list). The first argument -- contains information about the conversion status of external tycons: -- -- classifyTyCons :: UniqFM Bool -> [TyConGroup] -> ([TyCon], [TyCon]) -- | Compute mutually recursive groups of tycons in topological order tyConGroups :: [TyCon] -> [TyConGroup] -- | This module defines TyCons that can't be expressed in Haskell. They -- are all, therefore, wired-in TyCons. C.f module TysWiredIn module TysPrim alphaTyVars :: [TyVar] betaTyVars :: [TyVar] alphaTyVar :: TyVar betaTyVar :: TyVar gammaTyVar :: TyVar deltaTyVar :: TyVar alphaTy :: Type betaTy :: Type gammaTy :: Type deltaTy :: Type openAlphaTy :: Type openBetaTy :: Type openAlphaTyVar :: TyVar openBetaTyVar :: TyVar openAlphaTyVars :: [TyVar] argAlphaTy :: Type argAlphaTyVar :: TyVar argBetaTy :: Type argBetaTyVar :: TyVar primTyCons :: [TyCon] charPrimTyCon :: TyCon charPrimTy :: Type intPrimTyCon :: TyCon intPrimTy :: Type wordPrimTyCon :: TyCon wordPrimTy :: Type addrPrimTyCon :: TyCon addrPrimTy :: Type floatPrimTyCon :: TyCon floatPrimTy :: Type doublePrimTyCon :: TyCon doublePrimTy :: Type statePrimTyCon :: TyCon mkStatePrimTy :: Type -> Type realWorldTyCon :: TyCon realWorldTy :: Type realWorldStatePrimTy :: Type arrayPrimTyCon :: TyCon mkArrayPrimTy :: Type -> Type byteArrayPrimTyCon :: TyCon byteArrayPrimTy :: Type mutableArrayPrimTyCon :: TyCon mkMutableArrayPrimTy :: Type -> Type -> Type mutableByteArrayPrimTyCon :: TyCon mkMutableByteArrayPrimTy :: Type -> Type mutVarPrimTyCon :: TyCon mkMutVarPrimTy :: Type -> Type -> Type mVarPrimTyCon :: TyCon mkMVarPrimTy :: Type -> Type -> Type tVarPrimTyCon :: TyCon mkTVarPrimTy :: Type -> Type -> Type stablePtrPrimTyCon :: TyCon mkStablePtrPrimTy :: Type -> Type stableNamePrimTyCon :: TyCon mkStableNamePrimTy :: Type -> Type bcoPrimTyCon :: TyCon bcoPrimTy :: Type weakPrimTyCon :: TyCon mkWeakPrimTy :: Type -> Type threadIdPrimTyCon :: TyCon threadIdPrimTy :: Type int32PrimTyCon :: TyCon int32PrimTy :: Type word32PrimTyCon :: TyCon word32PrimTy :: Type int64PrimTyCon :: TyCon int64PrimTy :: Type word64PrimTyCon :: TyCon word64PrimTy :: Type anyTyCon :: TyCon anyTyConOfKind :: Kind -> TyCon anyTypeOfKind :: Kind -> Type -- | This module is about types that can be defined in Haskell, but which -- must be wired into the compiler nonetheless. C.f module TysPrim module TysWiredIn wiredInTyCons :: [TyCon] boolTy :: Type boolTyCon :: TyCon boolTyCon_RDR :: RdrName boolTyConName :: Name trueDataCon :: DataCon trueDataConId :: Id true_RDR :: RdrName falseDataCon :: DataCon falseDataConId :: Id false_RDR :: RdrName charTyCon :: TyCon charDataCon :: DataCon charTyCon_RDR :: RdrName charTy :: Type stringTy :: Type charTyConName :: Name doubleTyCon :: TyCon doubleDataCon :: DataCon doubleTy :: Type doubleTyConName :: Name floatTyCon :: TyCon floatDataCon :: DataCon floatTy :: Type floatTyConName :: Name intTyCon :: TyCon intDataCon :: DataCon intTyCon_RDR :: RdrName intDataCon_RDR :: RdrName intTyConName :: Name intTy :: Type wordTyCon :: TyCon wordDataCon :: DataCon wordTyConName :: Name wordTy :: Type listTyCon :: TyCon nilDataCon :: DataCon consDataCon :: DataCon listTyCon_RDR :: RdrName consDataCon_RDR :: RdrName listTyConName :: Name mkListTy :: Type -> Type mkTupleTy :: Boxity -> [Type] -> Type -- | Build the type of a small tuple that holds the specified type of thing mkBoxedTupleTy :: [Type] -> Type tupleTyCon :: Boxity -> Arity -> TyCon tupleCon :: Boxity -> Arity -> DataCon unitTyCon :: TyCon unitDataCon :: DataCon unitDataConId :: Id pairTyCon :: TyCon unboxedSingletonTyCon :: TyCon unboxedSingletonDataCon :: DataCon unboxedPairTyCon :: TyCon unboxedPairDataCon :: DataCon unitTy :: Type -- | Construct a type representing the application of the parallel array -- constructor mkPArrTy :: Type -> Type -- | Represents the type constructor of parallel arrays -- -- -- -- NB: Although the constructor is given here, it will not be accessible -- in user code as it is not in the environment of any compiled module -- except PrelPArr. parrTyCon :: TyCon -- | Fake array constructors -- -- parrFakeCon :: Arity -> DataCon -- | Check whether a type constructor is the constructor for parallel -- arrays isPArrTyCon :: TyCon -> Bool -- | Checks whether a data constructor is a fake constructor for parallel -- arrays isPArrFakeCon :: DataCon -> Bool parrTyCon_RDR :: RdrName parrTyConName :: Name module Literal -- | So-called Literals are one of: -- -- data Literal -- | Char# - at least 31 bits. Create with mkMachChar MachChar :: Char -> Literal -- | A string-literal: stored and emitted UTF-8 encoded, we'll arrange to -- decode it at runtime. Also emitted with a '\0' terminator. -- Create with mkMachString MachStr :: FastString -> Literal -- | The NULL pointer, the only pointer value that can be -- represented as a Literal. Create with nullAddrLit MachNullAddr :: Literal -- | Int# - at least WORD_SIZE_IN_BITS bits. Create with -- mkMachInt MachInt :: Integer -> Literal -- | Int64# - at least 64 bits. Create with mkMachInt64 MachInt64 :: Integer -> Literal -- | Word# - at least WORD_SIZE_IN_BITS bits. Create with -- mkMachWord MachWord :: Integer -> Literal -- | Word64# - at least 64 bits. Create with mkMachWord64 MachWord64 :: Integer -> Literal -- | Float#. Create with mkMachFloat MachFloat :: Rational -> Literal -- | Double#. Create with mkMachDouble MachDouble :: Rational -> Literal -- | A label literal. Parameters: -- -- 1) The name of the symbol mentioned in the declaration -- -- 2) The size (in bytes) of the arguments the label expects. Only -- applicable with stdcall labels. Just x => -- <x> will be appended to label name when emitting -- assembly. MachLabel :: FastString -> (Maybe Int) -> FunctionOrData -> Literal -- | Creates a Literal of type Int# mkMachInt :: Integer -> Literal -- | Creates a Literal of type Word# mkMachWord :: Integer -> Literal -- | Creates a Literal of type Int64# mkMachInt64 :: Integer -> Literal -- | Creates a Literal of type Word64# mkMachWord64 :: Integer -> Literal -- | Creates a Literal of type Float# mkMachFloat :: Rational -> Literal -- | Creates a Literal of type Double# mkMachDouble :: Rational -> Literal -- | Creates a Literal of type Char# mkMachChar :: Char -> Literal -- | Creates a Literal of type Addr#, which is appropriate -- for passing to e.g. some of the "error" functions in GHC.Err such as -- GHC.Err.runtimeError mkMachString :: String -> Literal -- | Find the Haskell Type the literal occupies literalType :: Literal -> Type hashLiteral :: Literal -> Int absentLiteralOf :: TyCon -> Maybe Literal -- | True if code space does not go bad if we duplicate this literal -- Currently we treat it just like litIsTrivial litIsDupable :: Literal -> Bool -- | True if there is absolutely no penalty to duplicating the literal. -- False principally of strings litIsTrivial :: Literal -> Bool inIntRange :: Integer -> Bool inWordRange :: Integer -> Bool tARGET_MAX_INT :: Integer inCharRange :: Char -> Bool -- | Tests whether the literal represents a zero of whatever type it is isZeroLit :: Literal -> Bool litFitsInChar :: Literal -> Bool word2IntLit :: Literal -> Literal int2WordLit :: Literal -> Literal narrow8IntLit :: Literal -> Literal narrow16IntLit :: Literal -> Literal narrow32IntLit :: Literal -> Literal narrow8WordLit :: Literal -> Literal narrow16WordLit :: Literal -> Literal narrow32WordLit :: Literal -> Literal char2IntLit :: Literal -> Literal int2CharLit :: Literal -> Literal float2IntLit :: Literal -> Literal int2FloatLit :: Literal -> Literal double2IntLit :: Literal -> Literal int2DoubleLit :: Literal -> Literal nullAddrLit :: Literal float2DoubleLit :: Literal -> Literal double2FloatLit :: Literal -> Literal instance Typeable Literal instance Data Literal instance Ord Literal instance Eq Literal instance Show Literal instance Outputable Literal instance Binary Literal module PrimOp data PrimOp CharGtOp :: PrimOp CharGeOp :: PrimOp CharEqOp :: PrimOp CharNeOp :: PrimOp CharLtOp :: PrimOp CharLeOp :: PrimOp OrdOp :: PrimOp IntAddOp :: PrimOp IntSubOp :: PrimOp IntMulOp :: PrimOp IntMulMayOfloOp :: PrimOp IntQuotOp :: PrimOp IntRemOp :: PrimOp IntNegOp :: PrimOp IntAddCOp :: PrimOp IntSubCOp :: PrimOp IntGtOp :: PrimOp IntGeOp :: PrimOp IntEqOp :: PrimOp IntNeOp :: PrimOp IntLtOp :: PrimOp IntLeOp :: PrimOp ChrOp :: PrimOp Int2WordOp :: PrimOp Int2FloatOp :: PrimOp Int2DoubleOp :: PrimOp ISllOp :: PrimOp ISraOp :: PrimOp ISrlOp :: PrimOp WordAddOp :: PrimOp WordSubOp :: PrimOp WordMulOp :: PrimOp WordQuotOp :: PrimOp WordRemOp :: PrimOp AndOp :: PrimOp OrOp :: PrimOp XorOp :: PrimOp NotOp :: PrimOp SllOp :: PrimOp SrlOp :: PrimOp Word2IntOp :: PrimOp WordGtOp :: PrimOp WordGeOp :: PrimOp WordEqOp :: PrimOp WordNeOp :: PrimOp WordLtOp :: PrimOp WordLeOp :: PrimOp Narrow8IntOp :: PrimOp Narrow16IntOp :: PrimOp Narrow32IntOp :: PrimOp Narrow8WordOp :: PrimOp Narrow16WordOp :: PrimOp Narrow32WordOp :: PrimOp DoubleGtOp :: PrimOp DoubleGeOp :: PrimOp DoubleEqOp :: PrimOp DoubleNeOp :: PrimOp DoubleLtOp :: PrimOp DoubleLeOp :: PrimOp DoubleAddOp :: PrimOp DoubleSubOp :: PrimOp DoubleMulOp :: PrimOp DoubleDivOp :: PrimOp DoubleNegOp :: PrimOp Double2IntOp :: PrimOp Double2FloatOp :: PrimOp DoubleExpOp :: PrimOp DoubleLogOp :: PrimOp DoubleSqrtOp :: PrimOp DoubleSinOp :: PrimOp DoubleCosOp :: PrimOp DoubleTanOp :: PrimOp DoubleAsinOp :: PrimOp DoubleAcosOp :: PrimOp DoubleAtanOp :: PrimOp DoubleSinhOp :: PrimOp DoubleCoshOp :: PrimOp DoubleTanhOp :: PrimOp DoublePowerOp :: PrimOp DoubleDecode_2IntOp :: PrimOp FloatGtOp :: PrimOp FloatGeOp :: PrimOp FloatEqOp :: PrimOp FloatNeOp :: PrimOp FloatLtOp :: PrimOp FloatLeOp :: PrimOp FloatAddOp :: PrimOp FloatSubOp :: PrimOp FloatMulOp :: PrimOp FloatDivOp :: PrimOp FloatNegOp :: PrimOp Float2IntOp :: PrimOp FloatExpOp :: PrimOp FloatLogOp :: PrimOp FloatSqrtOp :: PrimOp FloatSinOp :: PrimOp FloatCosOp :: PrimOp FloatTanOp :: PrimOp FloatAsinOp :: PrimOp FloatAcosOp :: PrimOp FloatAtanOp :: PrimOp FloatSinhOp :: PrimOp FloatCoshOp :: PrimOp FloatTanhOp :: PrimOp FloatPowerOp :: PrimOp Float2DoubleOp :: PrimOp FloatDecode_IntOp :: PrimOp NewArrayOp :: PrimOp SameMutableArrayOp :: PrimOp ReadArrayOp :: PrimOp WriteArrayOp :: PrimOp IndexArrayOp :: PrimOp UnsafeFreezeArrayOp :: PrimOp UnsafeThawArrayOp :: PrimOp NewByteArrayOp_Char :: PrimOp NewPinnedByteArrayOp_Char :: PrimOp NewAlignedPinnedByteArrayOp_Char :: PrimOp ByteArrayContents_Char :: PrimOp SameMutableByteArrayOp :: PrimOp UnsafeFreezeByteArrayOp :: PrimOp SizeofByteArrayOp :: PrimOp SizeofMutableByteArrayOp :: PrimOp IndexByteArrayOp_Char :: PrimOp IndexByteArrayOp_WideChar :: PrimOp IndexByteArrayOp_Int :: PrimOp IndexByteArrayOp_Word :: PrimOp IndexByteArrayOp_Addr :: PrimOp IndexByteArrayOp_Float :: PrimOp IndexByteArrayOp_Double :: PrimOp IndexByteArrayOp_StablePtr :: PrimOp IndexByteArrayOp_Int8 :: PrimOp IndexByteArrayOp_Int16 :: PrimOp IndexByteArrayOp_Int32 :: PrimOp IndexByteArrayOp_Int64 :: PrimOp IndexByteArrayOp_Word8 :: PrimOp IndexByteArrayOp_Word16 :: PrimOp IndexByteArrayOp_Word32 :: PrimOp IndexByteArrayOp_Word64 :: PrimOp ReadByteArrayOp_Char :: PrimOp ReadByteArrayOp_WideChar :: PrimOp ReadByteArrayOp_Int :: PrimOp ReadByteArrayOp_Word :: PrimOp ReadByteArrayOp_Addr :: PrimOp ReadByteArrayOp_Float :: PrimOp ReadByteArrayOp_Double :: PrimOp ReadByteArrayOp_StablePtr :: PrimOp ReadByteArrayOp_Int8 :: PrimOp ReadByteArrayOp_Int16 :: PrimOp ReadByteArrayOp_Int32 :: PrimOp ReadByteArrayOp_Int64 :: PrimOp ReadByteArrayOp_Word8 :: PrimOp ReadByteArrayOp_Word16 :: PrimOp ReadByteArrayOp_Word32 :: PrimOp ReadByteArrayOp_Word64 :: PrimOp WriteByteArrayOp_Char :: PrimOp WriteByteArrayOp_WideChar :: PrimOp WriteByteArrayOp_Int :: PrimOp WriteByteArrayOp_Word :: PrimOp WriteByteArrayOp_Addr :: PrimOp WriteByteArrayOp_Float :: PrimOp WriteByteArrayOp_Double :: PrimOp WriteByteArrayOp_StablePtr :: PrimOp WriteByteArrayOp_Int8 :: PrimOp WriteByteArrayOp_Int16 :: PrimOp WriteByteArrayOp_Int32 :: PrimOp WriteByteArrayOp_Int64 :: PrimOp WriteByteArrayOp_Word8 :: PrimOp WriteByteArrayOp_Word16 :: PrimOp WriteByteArrayOp_Word32 :: PrimOp WriteByteArrayOp_Word64 :: PrimOp AddrAddOp :: PrimOp AddrSubOp :: PrimOp AddrRemOp :: PrimOp Addr2IntOp :: PrimOp Int2AddrOp :: PrimOp AddrGtOp :: PrimOp AddrGeOp :: PrimOp AddrEqOp :: PrimOp AddrNeOp :: PrimOp AddrLtOp :: PrimOp AddrLeOp :: PrimOp IndexOffAddrOp_Char :: PrimOp IndexOffAddrOp_WideChar :: PrimOp IndexOffAddrOp_Int :: PrimOp IndexOffAddrOp_Word :: PrimOp IndexOffAddrOp_Addr :: PrimOp IndexOffAddrOp_Float :: PrimOp IndexOffAddrOp_Double :: PrimOp IndexOffAddrOp_StablePtr :: PrimOp IndexOffAddrOp_Int8 :: PrimOp IndexOffAddrOp_Int16 :: PrimOp IndexOffAddrOp_Int32 :: PrimOp IndexOffAddrOp_Int64 :: PrimOp IndexOffAddrOp_Word8 :: PrimOp IndexOffAddrOp_Word16 :: PrimOp IndexOffAddrOp_Word32 :: PrimOp IndexOffAddrOp_Word64 :: PrimOp ReadOffAddrOp_Char :: PrimOp ReadOffAddrOp_WideChar :: PrimOp ReadOffAddrOp_Int :: PrimOp ReadOffAddrOp_Word :: PrimOp ReadOffAddrOp_Addr :: PrimOp ReadOffAddrOp_Float :: PrimOp ReadOffAddrOp_Double :: PrimOp ReadOffAddrOp_StablePtr :: PrimOp ReadOffAddrOp_Int8 :: PrimOp ReadOffAddrOp_Int16 :: PrimOp ReadOffAddrOp_Int32 :: PrimOp ReadOffAddrOp_Int64 :: PrimOp ReadOffAddrOp_Word8 :: PrimOp ReadOffAddrOp_Word16 :: PrimOp ReadOffAddrOp_Word32 :: PrimOp ReadOffAddrOp_Word64 :: PrimOp WriteOffAddrOp_Char :: PrimOp WriteOffAddrOp_WideChar :: PrimOp WriteOffAddrOp_Int :: PrimOp WriteOffAddrOp_Word :: PrimOp WriteOffAddrOp_Addr :: PrimOp WriteOffAddrOp_Float :: PrimOp WriteOffAddrOp_Double :: PrimOp WriteOffAddrOp_StablePtr :: PrimOp WriteOffAddrOp_Int8 :: PrimOp WriteOffAddrOp_Int16 :: PrimOp WriteOffAddrOp_Int32 :: PrimOp WriteOffAddrOp_Int64 :: PrimOp WriteOffAddrOp_Word8 :: PrimOp WriteOffAddrOp_Word16 :: PrimOp WriteOffAddrOp_Word32 :: PrimOp WriteOffAddrOp_Word64 :: PrimOp NewMutVarOp :: PrimOp ReadMutVarOp :: PrimOp WriteMutVarOp :: PrimOp SameMutVarOp :: PrimOp AtomicModifyMutVarOp :: PrimOp CatchOp :: PrimOp RaiseOp :: PrimOp RaiseIOOp :: PrimOp MaskAsyncExceptionsOp :: PrimOp MaskUninterruptibleOp :: PrimOp UnmaskAsyncExceptionsOp :: PrimOp MaskStatus :: PrimOp AtomicallyOp :: PrimOp RetryOp :: PrimOp CatchRetryOp :: PrimOp CatchSTMOp :: PrimOp Check :: PrimOp NewTVarOp :: PrimOp ReadTVarOp :: PrimOp ReadTVarIOOp :: PrimOp WriteTVarOp :: PrimOp SameTVarOp :: PrimOp NewMVarOp :: PrimOp TakeMVarOp :: PrimOp TryTakeMVarOp :: PrimOp PutMVarOp :: PrimOp TryPutMVarOp :: PrimOp SameMVarOp :: PrimOp IsEmptyMVarOp :: PrimOp DelayOp :: PrimOp WaitReadOp :: PrimOp WaitWriteOp :: PrimOp ForkOp :: PrimOp ForkOnOp :: PrimOp KillThreadOp :: PrimOp YieldOp :: PrimOp MyThreadIdOp :: PrimOp LabelThreadOp :: PrimOp IsCurrentThreadBoundOp :: PrimOp NoDuplicateOp :: PrimOp ThreadStatusOp :: PrimOp MkWeakOp :: PrimOp MkWeakForeignEnvOp :: PrimOp DeRefWeakOp :: PrimOp FinalizeWeakOp :: PrimOp TouchOp :: PrimOp MakeStablePtrOp :: PrimOp DeRefStablePtrOp :: PrimOp EqStablePtrOp :: PrimOp MakeStableNameOp :: PrimOp EqStableNameOp :: PrimOp StableNameToIntOp :: PrimOp ReallyUnsafePtrEqualityOp :: PrimOp ParOp :: PrimOp GetSparkOp :: PrimOp NumSparks :: PrimOp ParGlobalOp :: PrimOp ParLocalOp :: PrimOp ParAtOp :: PrimOp ParAtAbsOp :: PrimOp ParAtRelOp :: PrimOp ParAtForNowOp :: PrimOp DataToTagOp :: PrimOp TagToEnumOp :: PrimOp AddrToHValueOp :: PrimOp MkApUpd0_Op :: PrimOp NewBCOOp :: PrimOp UnpackClosureOp :: PrimOp GetApStackValOp :: PrimOp TraceCcsOp :: PrimOp TraceEventOp :: PrimOp allThePrimOps :: [PrimOp] primOpType :: PrimOp -> Type primOpSig :: PrimOp -> ([TyVar], [Type], Type, Arity, StrictSig) primOpTag :: PrimOp -> Int maxPrimOpTag :: Int primOpOcc :: PrimOp -> OccName tagToEnumKey :: Unique primOpOutOfLine :: PrimOp -> Bool primOpNeedsWrapper :: PrimOp -> Bool primOpOkForSpeculation :: PrimOp -> Bool primOpIsCheap :: PrimOp -> Bool primOpIsDupable :: PrimOp -> Bool getPrimOpResultInfo :: PrimOp -> PrimOpResultInfo data PrimOpResultInfo ReturnsPrim :: PrimRep -> PrimOpResultInfo ReturnsAlg :: TyCon -> PrimOpResultInfo data PrimCall PrimCall :: CLabelString -> PackageId -> PrimCall instance Outputable PrimCall instance Show PrimOp instance Outputable PrimOp instance Ord PrimOp instance Eq PrimOp module CostCentre data CostCentre NoCostCentre :: CostCentre NormalCC :: CcName -> Module -> IsDupdCC -> IsCafCC -> CostCentre cc_name :: CostCentre -> CcName cc_mod :: CostCentre -> Module cc_is_dupd :: CostCentre -> IsDupdCC cc_is_caf :: CostCentre -> IsCafCC AllCafsCC :: Module -> CostCentre cc_mod :: CostCentre -> Module type CcName = FastString data IsDupdCC OriginalCC :: IsDupdCC DupdCC :: IsDupdCC data IsCafCC CafCC :: IsCafCC NotCafCC :: IsCafCC data CostCentreStack type CollectedCCs = ([CostCentre], [CostCentre], [CostCentreStack]) noCCS :: CostCentreStack subsumedCCS :: CostCentreStack currentCCS :: CostCentreStack overheadCCS :: CostCentreStack dontCareCCS :: CostCentreStack noCostCentre :: CostCentre noCCAttached :: CostCentre -> Bool noCCSAttached :: CostCentreStack -> Bool isCurrentCCS :: CostCentreStack -> Bool isSubsumedCCS :: CostCentreStack -> Bool currentOrSubsumedCCS :: CostCentreStack -> Bool isDerivedFromCurrentCCS :: CostCentreStack -> Bool maybeSingletonCCS :: CostCentreStack -> Maybe CostCentre decomposeCCS :: CostCentreStack -> ([CostCentre], CostCentreStack) pushCCisNop :: CostCentre -> CostCentreStack -> Bool mkUserCC :: FastString -> Module -> CostCentre mkAutoCC :: Id -> Module -> IsCafCC -> CostCentre mkAllCafsCC :: Module -> CostCentre mkSingletonCCS :: CostCentre -> CostCentreStack dupifyCC :: CostCentre -> CostCentre pushCCOnCCS :: CostCentre -> CostCentreStack -> CostCentreStack isCafCCS :: CostCentreStack -> Bool isCafCC :: CostCentre -> Bool isSccCountCostCentre :: CostCentre -> Bool sccAbleCostCentre :: CostCentre -> Bool ccFromThisModule :: CostCentre -> Module -> Bool pprCostCentreCore :: CostCentre -> SDoc costCentreUserName :: CostCentre -> String cmpCostCentre :: CostCentre -> CostCentre -> Ordering instance Typeable IsDupdCC instance Typeable IsCafCC instance Typeable CostCentre instance Data IsDupdCC instance Data IsCafCC instance Data CostCentre instance Eq CostCentreStack instance Ord CostCentreStack instance Outputable CostCentre instance Outputable CostCentreStack instance Ord CostCentre instance Eq CostCentre -- | CoreSyn holds all the main data types for use by for the Glasgow -- Haskell Compiler midsection module CoreSyn -- | This is the data type that represents GHCs core intermediate language. -- Currently GHC uses System FC -- http://research.microsoft.com/~simonpj/papers/ext-f/ for this -- purpose, which is closely related to the simpler and better known -- System F http://en.wikipedia.org/wiki/System_F. -- -- We get from Haskell source to this Core language in a number of -- stages: -- --
    --
  1. The source code is parsed into an abstract syntax tree, which is -- represented by the data type HsExpr.HsExpr with the names -- being RdrName.RdrNames
  2. --
  3. This syntax tree is renamed, which attaches a -- Unique.Unique to every RdrName.RdrName (yielding a -- Name) to disambiguate identifiers which are lexically -- identical. For example, this program:
  4. --
-- --
--   f x = let f x = x + 1
--         in f (x - 2)
--   
-- -- Would be renamed by having Uniques attached so it looked -- something like this: -- --
--   f_1 x_2 = let f_3 x_4 = x_4 + 1
--             in f_3 (x_2 - 2)
--   
-- --
    --
  1. The resulting syntax tree undergoes type checking (which also -- deals with instantiating type class arguments) to yield a -- HsExpr.HsExpr type that has Id.Id as it's -- names.
  2. --
  3. Finally the syntax tree is desugared from the expressive -- HsExpr.HsExpr type into this Expr type, which has far -- fewer constructors and hence is easier to perform optimization, -- analysis and code generation on.
  4. --
-- -- The type parameter b is for the type of binders in the -- expression tree. data Expr b -- | Variables Var :: Id -> Expr b -- | Primitive literals Lit :: Literal -> Expr b -- | Applications: note that the argument may be a Type. -- -- See CoreSyn#let_app_invariant for another invariant App :: (Expr b) -> (Arg b) -> Expr b -- | Lambda abstraction Lam :: b -> (Expr b) -> Expr b -- | Recursive and non recursive lets. Operationally this -- corresponds to allocating a thunk for the things bound and then -- executing the sub-expression. -- -- -- The right hand sides of all top-level and recursive lets -- must be of lifted type (see Type#type_classification for -- the meaning of lifted vs. unlifted). -- -- The right hand side of of a non-recursive Let _and_ the -- argument of an App, may be of unlifted type, but only if -- the expression is ok-for-speculation. This means that the let can be -- floated around without difficulty. For example, this is OK: -- --
--   y::Int# = x +# 1#
--   
-- -- But this is not, as it may affect termination if the expression is -- floated out: -- --
--   y::Int# = fac 4#
--   
-- -- In this situation you should use case rather than a -- let. The function CoreUtils.needsCaseBinding can -- help you determine which to generate, or alternatively use -- MkCore.mkCoreLet rather than this constructor directly, which -- will generate a case if necessary -- -- We allow a non-recursive let to bind a type variable, thus: -- --
--   Let (NonRec tv (Type ty)) body
--   
-- -- This can be very convenient for postponing type substitutions until -- the next run of the simplifier. -- -- At the moment, the rest of the compiler only deals with type-let in a -- Let expression, rather than at top level. We may want to revist this -- choice. Let :: (Bind b) -> (Expr b) -> Expr b -- | Case split. Operationally this corresponds to evaluating the scrutinee -- (expression examined) to weak head normal form and then examining at -- most one level of resulting constructor (i.e. you cannot do nested -- pattern matching directly with this). -- -- The binder gets bound to the value of the scrutinee, and the -- Type must be that of all the case alternatives -- -- This is one of the more complicated elements of the Core language, and -- comes with a number of restrictions: -- -- The DEFAULT case alternative must be first in the list, if it -- occurs at all. -- -- The remaining cases are in order of increasing tag (for -- DataAlts) or lit (for LitAlts). This makes finding -- the relevant constructor easy, and makes comparison easier too. -- -- The list of alternatives must be exhaustive. An exhaustive case -- does not necessarily mention all constructors: -- --
--        data Foo = Red | Green | Blue
--   ... case x of 
--        Red   -> True
--        other -> f (case x of 
--                        Green -> ...
--                        Blue  -> ... ) ...
--   
-- -- The inner case does not need a Red alternative, because -- x can't be Red at that program point. Case :: (Expr b) -> b -> Type -> [Alt b] -> Expr b -- | Cast an expression to a particular type. This is used to implement -- newtypes (a newtype constructor or destructor just -- becomes a Cast in Core) and GADTs. Cast :: (Expr b) -> Coercion -> Expr b -- | Notes. These allow general information to be added to expressions in -- the syntax tree Note :: Note -> (Expr b) -> Expr b -- | A type: this should only show up at the top level of an Arg Type :: Type -> Expr b -- | A case split alternative. Consists of the constructor leading to the -- alternative, the variables bound from the constructor, and the -- expression to be executed given that binding. The default alternative -- is (DEFAULT, [], rhs) type Alt b = (AltCon, [b], Expr b) -- | Binding, used for top level bindings in a module and local bindings in -- a let. data Bind b NonRec :: b -> (Expr b) -> Bind b Rec :: [(b, Expr b)] -> Bind b -- | A case alternative constructor (i.e. pattern match) data AltCon -- | A plain data constructor: case e of { Foo x -> ... }. -- Invariant: the DataCon is always from a data type, and -- never from a newtype DataAlt :: DataCon -> AltCon -- | A literal: case e of { 1 -> ... } LitAlt :: Literal -> AltCon -- | Trivial alternative: case e of { _ -> ... } DEFAULT :: AltCon -- | Type synonym for expressions that occur in function argument -- positions. Only Arg should contain a Type at top level, -- general Expr should not type Arg b = Expr b -- | Allows attaching extra information to points in expressions rather -- than e.g. identifiers. data Note -- | A cost centre annotation for profiling SCC :: CostCentre -> Note -- | A generic core annotation, propagated but not used by GHC CoreNote :: String -> Note -- | Expressions where binders are CoreBndrs type CoreExpr = Expr CoreBndr -- | Case alternatives where binders are CoreBndrs type CoreAlt = Alt CoreBndr -- | Binding groups where binders are CoreBndrs type CoreBind = Bind CoreBndr -- | Argument expressions where binders are CoreBndrs type CoreArg = Arg CoreBndr -- | The common case for the type of binders and variables when we are -- manipulating the Core language within GHC type CoreBndr = Var type TaggedExpr t = Expr (TaggedBndr t) type TaggedAlt t = Alt (TaggedBndr t) type TaggedBind t = Bind (TaggedBndr t) type TaggedArg t = Arg (TaggedBndr t) -- | Binders are tagged with a t data TaggedBndr t TB :: CoreBndr -> t -> TaggedBndr t -- | Bind all supplied binding groups over an expression in a nested let -- expression. Prefer to use CoreUtils.mkCoreLets if possible mkLets :: [Bind b] -> Expr b -> Expr b -- | Bind all supplied binders over an expression in a nested lambda -- expression. Prefer to use CoreUtils.mkCoreLams if possible mkLams :: [b] -> Expr b -> Expr b -- | Apply a list of argument expressions to a function expression in a -- nested fashion. Prefer to use CoreUtils.mkCoreApps if -- possible mkApps :: Expr b -> [Arg b] -> Expr b -- | Apply a list of type argument expressions to a function expression in -- a nested fashion mkTyApps :: Expr b -> [Type] -> Expr b -- | Apply a list of type or value variables to a function expression in a -- nested fashion mkVarApps :: Expr b -> [Var] -> Expr b -- | Create a machine integer literal expression of type Int# from -- an Integer. If you want an expression of type Int -- use MkCore.mkIntExpr mkIntLit :: Integer -> Expr b -- | Create a machine integer literal expression of type Int# from -- an Int. If you want an expression of type Int use -- MkCore.mkIntExpr mkIntLitInt :: Int -> Expr b -- | Create a machine word literal expression of type Word# from -- an Integer. If you want an expression of type Word -- use MkCore.mkWordExpr mkWordLit :: Integer -> Expr b -- | Create a machine word literal expression of type Word# from a -- Word. If you want an expression of type Word use -- MkCore.mkWordExpr mkWordLitWord :: Word -> Expr b -- | Create a machine character literal expression of type Char#. -- If you want an expression of type Char use -- MkCore.mkCharExpr mkCharLit :: Char -> Expr b -- | Create a machine string literal expression of type Addr#. If -- you want an expression of type String use -- MkCore.mkStringExpr mkStringLit :: String -> Expr b -- | Create a machine single precision literal expression of type -- Float# from a Rational. If you want an expression of -- type Float use MkCore.mkFloatExpr mkFloatLit :: Rational -> Expr b -- | Create a machine single precision literal expression of type -- Float# from a Float. If you want an expression of -- type Float use MkCore.mkFloatExpr mkFloatLitFloat :: Float -> Expr b -- | Create a machine double precision literal expression of type -- Double# from a Rational. If you want an expression -- of type Double use MkCore.mkDoubleExpr mkDoubleLit :: Rational -> Expr b -- | Create a machine double precision literal expression of type -- Double# from a Double. If you want an expression of -- type Double use MkCore.mkDoubleExpr mkDoubleLitDouble :: Double -> Expr b -- | Apply a list of argument expressions to a data constructor in a nested -- fashion. Prefer to use MkCore.mkCoreConApps if possible mkConApp :: DataCon -> [Arg b] -> Expr b -- | Create a binding group where a type variable is bound to a type. Per -- CoreSyn#type_let, this can only be used to bind something in a -- non-recursive let expression mkTyBind :: TyVar -> Type -> CoreBind -- | Convert a binder into either a Var or Type Expr -- appropriately varToCoreExpr :: CoreBndr -> Expr b varsToCoreExprs :: [CoreBndr] -> [Expr b] isTyCoVar :: Var -> Bool isId :: Var -> Bool -- | Compares AltCons within a single list of alternatives cmpAltCon :: AltCon -> AltCon -> Ordering cmpAlt :: Alt b -> Alt b -> Ordering ltAlt :: Alt b -> Alt b -> Bool -- | Extract every variable by this group bindersOf :: Bind b -> [b] -- | bindersOf applied to a list of binding groups bindersOfBinds :: [Bind b] -> [b] rhssOfBind :: Bind b -> [Expr b] rhssOfAlts :: [Alt b] -> [Expr b] -- | We often want to strip off leading lambdas before getting down to -- business. This function is your friend. collectBinders :: Expr b -> ([b], Expr b) -- | Collect as many type bindings as possible from the front of a nested -- lambda collectTyBinders :: CoreExpr -> ([TyVar], CoreExpr) -- | Collect as many value bindings as possible from the front of a nested -- lambda collectValBinders :: CoreExpr -> ([Id], CoreExpr) -- | Collect type binders from the front of the lambda first, then follow -- up by collecting as many value bindings as possible from the resulting -- stripped expression collectTyAndValBinders :: CoreExpr -> ([TyVar], [Id], CoreExpr) -- | Takes a nested application expression and returns the the function -- being applied and the arguments to which it is applied collectArgs :: Expr b -> (Expr b, [Arg b]) -- | Gets the cost centre enclosing an expression, if any. It looks inside -- lambdas because (scc "foo" \x.e) = \x. scc "foo" e coreExprCc :: Expr b -> CostCentre -- | Collapse all the bindings in the supplied groups into a single list of -- lhs/rhs pairs suitable for binding in a Rec binding group flattenBinds :: [Bind b] -> [(b, Expr b)] -- | Returns False iff the expression is a Type expression -- at its top level isValArg :: Expr b -> Bool -- | Returns True iff the expression is a Type expression -- at its top level isTypeArg :: Expr b -> Bool -- | The number of argument expressions that are values rather than types -- at their top level valArgCount :: [Arg b] -> Int -- | The number of binders that bind values rather than types valBndrCount :: [CoreBndr] -> Int -- | Will this argument expression exist at runtime? isRuntimeArg :: CoreExpr -> Bool -- | Will this variable exist at runtime? isRuntimeVar :: Var -> Bool notSccNote :: Note -> Bool -- | Records the unfolding of an identifier, which is approximately -- the form the identifier would have if we substituted its definition in -- for the identifier. This type should be treated as abstract everywhere -- except in CoreUnfold data Unfolding -- | We have no information about the unfolding NoUnfolding :: Unfolding -- | It ain't one of these constructors. OtherCon xs also -- indicates that something has been evaluated and hence there's no point -- in re-evaluating it. OtherCon [] is used even for -- non-data-type values to indicated evaluated-ness. Notably: -- --
--   data C = C !(Int -> Int)
--   case x of { C f -> ... }
--   
-- -- Here, f gets an OtherCon [] unfolding. OtherCon :: [AltCon] -> Unfolding DFunUnfolding :: Arity -> DataCon -> [DFunArg CoreExpr] -> Unfolding -- | An unfolding with redundant cached information. Parameters: -- -- uf_tmpl: Template used to perform unfolding; NB: Occurrence info is -- guaranteed correct: see Note [OccInfo in unfoldings and rules] -- -- uf_is_top: Is this a top level binding? -- -- uf_is_value: exprIsHNF template (cached); it is ok to discard -- a seq on this variable -- -- uf_is_cheap: Does this waste only a little work if we expand it inside -- an inlining? Basically this is a cached version of -- exprIsCheap -- -- uf_guidance: Tells us about the size of the unfolding template CoreUnfolding :: CoreExpr -> UnfoldingSource -> Bool -> Arity -> Bool -> Bool -> Bool -> Bool -> UnfoldingGuidance -> Unfolding uf_tmpl :: Unfolding -> CoreExpr uf_src :: Unfolding -> UnfoldingSource uf_is_top :: Unfolding -> Bool uf_arity :: Unfolding -> Arity uf_is_value :: Unfolding -> Bool uf_is_conlike :: Unfolding -> Bool uf_is_cheap :: Unfolding -> Bool uf_expandable :: Unfolding -> Bool uf_guidance :: Unfolding -> UnfoldingGuidance -- | UnfoldingGuidance says when unfolding should take place data UnfoldingGuidance UnfWhen :: Bool -> Bool -> UnfoldingGuidance ug_unsat_ok :: UnfoldingGuidance -> Bool ug_boring_ok :: UnfoldingGuidance -> Bool UnfIfGoodArgs :: [Int] -> Int -> Int -> UnfoldingGuidance ug_args :: UnfoldingGuidance -> [Int] ug_size :: UnfoldingGuidance -> Int ug_res :: UnfoldingGuidance -> Int UnfNever :: UnfoldingGuidance data UnfoldingSource InlineRhs :: UnfoldingSource InlineStable :: UnfoldingSource InlineCompulsory :: UnfoldingSource InlineWrapper :: Id -> UnfoldingSource data DFunArg e DFunPolyArg :: e -> DFunArg e DFunConstArg :: e -> DFunArg e DFunLamArg :: Int -> DFunArg e dfunArgExprs :: [DFunArg e] -> [e] -- | There is no known Unfolding noUnfolding :: Unfolding -- | This unfolding marks the associated thing as being evaluated evaldUnfolding :: Unfolding mkOtherCon :: [AltCon] -> Unfolding unSaturatedOk :: Bool needSaturated :: Bool boringCxtOk :: Bool boringCxtNotOk :: Bool -- | Retrieves the template of an unfolding: panics if none is known unfoldingTemplate :: Unfolding -> CoreExpr setUnfoldingTemplate :: Unfolding -> CoreExpr -> Unfolding expandUnfolding_maybe :: Unfolding -> Maybe CoreExpr -- | Retrieves the template of an unfolding if possible maybeUnfoldingTemplate :: Unfolding -> Maybe CoreExpr -- | The constructors that the unfolding could never be: returns -- [] if no information is available otherCons :: Unfolding -> [AltCon] unfoldingArity :: Unfolding -> Arity -- | Determines if it is certainly the case that the unfolding will yield a -- value (something in HNF): returns False if unsure isValueUnfolding :: Unfolding -> Bool -- | Determines if it possibly the case that the unfolding will yield a -- value. Unlike isValueUnfolding it returns True for -- OtherCon isEvaldUnfolding :: Unfolding -> Bool -- | Is the thing we will unfold into certainly cheap? isCheapUnfolding :: Unfolding -> Bool isExpandableUnfolding :: Unfolding -> Bool -- | True if the unfolding is a constructor application, the -- application of a CONLIKE function or OtherCon isConLikeUnfolding :: Unfolding -> Bool isCompulsoryUnfolding :: Unfolding -> Bool isStableUnfolding :: Unfolding -> Bool isStableCoreUnfolding_maybe :: Unfolding -> Maybe UnfoldingSource isClosedUnfolding :: Unfolding -> Bool -- | Only returns False if there is no unfolding information available at -- all hasSomeUnfolding :: Unfolding -> Bool canUnfold :: Unfolding -> Bool neverUnfoldGuidance :: UnfoldingGuidance -> Bool isStableSource :: UnfoldingSource -> Bool seqExpr :: CoreExpr -> () seqExprs :: [CoreExpr] -> () seqUnfolding :: Unfolding -> () -- | Annotated core: allows annotation at every node in the tree type AnnExpr bndr annot = (annot, AnnExpr' bndr annot) -- | A clone of the Expr type but allowing annotation at every tree -- node data AnnExpr' bndr annot AnnVar :: Id -> AnnExpr' bndr annot AnnLit :: Literal -> AnnExpr' bndr annot AnnLam :: bndr -> (AnnExpr bndr annot) -> AnnExpr' bndr annot AnnApp :: (AnnExpr bndr annot) -> (AnnExpr bndr annot) -> AnnExpr' bndr annot AnnCase :: (AnnExpr bndr annot) -> bndr -> Type -> [AnnAlt bndr annot] -> AnnExpr' bndr annot AnnLet :: (AnnBind bndr annot) -> (AnnExpr bndr annot) -> AnnExpr' bndr annot AnnCast :: (AnnExpr bndr annot) -> Coercion -> AnnExpr' bndr annot AnnNote :: Note -> (AnnExpr bndr annot) -> AnnExpr' bndr annot AnnType :: Type -> AnnExpr' bndr annot -- | A clone of the Bind type but allowing annotation at every tree -- node data AnnBind bndr annot AnnNonRec :: bndr -> (AnnExpr bndr annot) -> AnnBind bndr annot AnnRec :: [(bndr, AnnExpr bndr annot)] -> AnnBind bndr annot -- | A clone of the Alt type but allowing annotation at every tree -- node type AnnAlt bndr annot = (AltCon, [bndr], AnnExpr bndr annot) -- | Takes a nested application expression and returns the the function -- being applied and the arguments to which it is applied collectAnnArgs :: AnnExpr b a -> (AnnExpr b a, [AnnExpr b a]) deAnnotate :: AnnExpr bndr annot -> Expr bndr deAnnotate' :: AnnExpr' bndr annot -> Expr bndr deAnnAlt :: AnnAlt bndr annot -> Alt bndr -- | As collectBinders but for AnnExpr rather than -- Expr collectAnnBndrs :: AnnExpr bndr annot -> ([bndr], AnnExpr bndr annot) -- | A CoreRule is: -- -- data CoreRule Rule :: RuleName -> Activation -> Name -> [Maybe Name] -> [CoreBndr] -> [CoreExpr] -> CoreExpr -> Bool -> Bool -> CoreRule -- | Name of the rule, for communication with the user ru_name :: CoreRule -> RuleName -- | When the rule is active ru_act :: CoreRule -> Activation -- | Name of the Id.Id at the head of this rule ru_fn :: CoreRule -> Name -- | Name at the head of each argument to the left hand side ru_rough :: CoreRule -> [Maybe Name] -- | Variables quantified over ru_bndrs :: CoreRule -> [CoreBndr] -- | Left hand side arguments ru_args :: CoreRule -> [CoreExpr] -- | Right hand side of the rule Occurrence info is guaranteed correct See -- Note [OccInfo in unfoldings and rules] ru_rhs :: CoreRule -> CoreExpr -- | True = this rule is auto-generated False -- = generated at the users behest Main effect: reporting of -- orphan-hood ru_auto :: CoreRule -> Bool -- | True iff the fn at the head of the rule is defined in the -- same module as the rule and is not an implicit Id (like a -- record selector, class operation, or data constructor) ru_local :: CoreRule -> Bool -- | Built-in rules are used for constant folding and suchlike. They have -- no free variables. BuiltinRule :: RuleName -> Name -> Int -> (IdUnfoldingFun -> [CoreExpr] -> Maybe CoreExpr) -> CoreRule -- | Name of the rule, for communication with the user ru_name :: CoreRule -> RuleName -- | Name of the Id.Id at the head of this rule ru_fn :: CoreRule -> Name -- | Number of arguments that ru_try consumes, if it fires, -- including type arguments ru_nargs :: CoreRule -> Int -- | This function does the rewrite. It given too many arguments, it simply -- discards them; the returned CoreExpr is just the rewrite of -- ru_fn applied to the first ru_nargs args ru_try :: CoreRule -> IdUnfoldingFun -> [CoreExpr] -> Maybe CoreExpr type RuleName = FastString type IdUnfoldingFun = Id -> Unfolding seqRules :: [CoreRule] -> () -- | The number of arguments the ru_fn must be applied to before the -- rule can match on it ruleArity :: CoreRule -> Int ruleName :: CoreRule -> RuleName -- | The Name of the Id.Id at the head of the rule left -- hand side ruleIdName :: CoreRule -> Name ruleActivation :: CoreRule -> Activation -- | Set the Name of the Id.Id at the head of the rule left -- hand side setRuleIdName :: Name -> CoreRule -> CoreRule isBuiltinRule :: CoreRule -> Bool isLocalRule :: CoreRule -> Bool instance Typeable AltCon instance Typeable Note instance Typeable1 Expr instance Typeable1 Bind instance Eq AltCon instance Ord AltCon instance Data AltCon instance Data Note instance Data b => Data (Expr b) instance Data b => Data (Bind b) instance Outputable b => OutputableBndr (TaggedBndr b) instance Outputable b => Outputable (TaggedBndr b) instance Show AltCon instance Outputable AltCon instance Functor DFunArg module IdInfo -- | The IdDetails of an Id give stable, and necessary, -- information about the Id. data IdDetails VanillaId :: IdDetails -- | The Id for a record selector RecSelId :: TyCon -> Bool -> IdDetails -- | For a data type family, this is the instance TyCon not -- the family TyCon sel_tycon :: IdDetails -> TyCon sel_naughty :: IdDetails -> Bool -- | The Id is for a data constructor worker DataConWorkId :: DataCon -> IdDetails -- | The Id is for a data constructor wrapper DataConWrapId :: DataCon -> IdDetails -- | The Id is an superclass selector or class operation of a -- class ClassOpId :: Class -> IdDetails -- | The Id is for a primitive operator PrimOpId :: PrimOp -> IdDetails -- | The Id is for a foreign call FCallId :: ForeignCall -> IdDetails -- | The Id is for a HPC tick box (both traditional and binary) TickBoxOpId :: TickBoxOp -> IdDetails -- | A dictionary function. Int = the number of silent arguments to -- the dfun e.g. class D a => C a where ... instance C a => C [a] -- has is_silent = 1, because the dfun has type dfun :: (D a, C a) => -- C [a] See the DFun Superclass Invariant in TcInstDcls -- -- Bool = True = the class has only one method, so may be -- implemented with a newtype, so it might be bad to be strict on this -- dictionary DFunId :: Int -> Bool -> IdDetails pprIdDetails :: IdDetails -> SDoc -- | An IdInfo gives optional information about an -- Id. If present it never lies, but it may not be present, in -- which case there is always a conservative assumption which can be -- made. -- -- Two Ids may have different info even though they have the -- same Unique (and are hence the same Id); for -- example, one might lack the properties attached to the other. -- -- The IdInfo gives information about the value, or definition, of -- the Id. It does not contain information about the -- Id's usage, except for demandInfo and -- lbvarInfo. data IdInfo -- | Basic IdInfo that carries no useful information whatsoever vanillaIdInfo :: IdInfo -- | More informative IdInfo we can use when we know the Id -- has no CAF references noCafIdInfo :: IdInfo -- | Just evaluate the IdInfo to WHNF seqIdInfo :: IdInfo -> () -- | Evaluate all the fields of the IdInfo that are generally -- demanded by the compiler megaSeqIdInfo :: IdInfo -> () -- | This is used to remove information on lambda binders that we have -- setup as part of a lambda group, assuming they will be applied all at -- once, but turn out to be part of an unsaturated lambda as in e.g: -- --
--   (\x1. \x2. e) arg1
--   
zapLamInfo :: IdInfo -> Maybe IdInfo -- | Remove demand info on the IdInfo if it is present, otherwise -- return Nothing zapDemandInfo :: IdInfo -> Maybe IdInfo -- | Zap info that depends on free variables zapFragileInfo :: IdInfo -> Maybe IdInfo -- | An ArityInfo of n tells us that partial application of -- this Id to up to n-1 value arguments does -- essentially no work. -- -- That is not necessarily the same as saying that it has n -- leading lambdas, because coerces may get in the way. -- -- The arity might increase later in the compilation process, if an extra -- lambda floats up to the binding site. type ArityInfo = Arity -- | It is always safe to assume that an Id has an arity of 0 unknownArity :: Arity -- | Id arity arityInfo :: IdInfo -> ArityInfo setArityInfo :: IdInfo -> ArityInfo -> IdInfo ppArityInfo :: Int -> SDoc -- | Id strictness information. Reason for Maybe: the DmdAnal phase needs -- to know whether this is the first visit, so it can assign botSig. -- Other customers want topSig. So Nothing is good. strictnessInfo :: IdInfo -> Maybe StrictSig setStrictnessInfo :: IdInfo -> Maybe StrictSig -> IdInfo -- | Id demand information. Similarly we want to know if there's no known -- demand yet, for when we are looking for CPR info demandInfo :: IdInfo -> Maybe Demand setDemandInfo :: IdInfo -> Maybe Demand -> IdInfo pprStrictness :: Maybe StrictSig -> SDoc -- | The Ids unfolding unfoldingInfo :: IdInfo -> Unfolding setUnfoldingInfo :: IdInfo -> Unfolding -> IdInfo setUnfoldingInfoLazily :: IdInfo -> Unfolding -> IdInfo -- | Tells when the inlining is active. When it is active the thing may be -- inlined, depending on how big it is. -- -- If there was an INLINE pragma, then as a separate matter, the -- RHS will have been made to look small with a Core inline Note -- -- The default InlinePragInfo is AlwaysActive, so the info -- serves entirely as a way to inhibit inlining until we want it type InlinePragInfo = InlinePragma -- | Any inline pragma atached to the Id inlinePragInfo :: IdInfo -> InlinePragma setInlinePragInfo :: IdInfo -> InlinePragma -> IdInfo -- | Identifier occurrence information data OccInfo -- | There are many occurrences, or unknown occurences NoOccInfo :: OccInfo -- | Marks unused variables. Sometimes useful for lambda and case-bound -- variables. IAmDead :: OccInfo -- | Occurs exactly once, not inside a rule OneOcc :: !InsideLam -> !OneBranch -> !InterestingCxt -> OccInfo -- | This identifier breaks a loop of mutually recursive functions. The -- field marks whether it is only a loop breaker due to a reference in a -- rule IAmALoopBreaker :: !RulesOnly -> OccInfo isDeadOcc :: OccInfo -> Bool isLoopBreaker :: OccInfo -> Bool -- | How the Id occurs in the program occInfo :: IdInfo -> OccInfo setOccInfo :: IdInfo -> OccInfo -> IdInfo type InsideLam = Bool type OneBranch = Bool insideLam :: InsideLam notInsideLam :: InsideLam oneBranch :: OneBranch notOneBranch :: OneBranch -- | Records the specializations of this Id that we know about in -- the form of rewrite CoreRules that target them data SpecInfo SpecInfo :: [CoreRule] -> VarSet -> SpecInfo isEmptySpecInfo :: SpecInfo -> Bool -- | Retrieve the locally-defined free variables of both the left and right -- hand sides of the specialization rules specInfoFreeVars :: SpecInfo -> VarSet specInfoRules :: SpecInfo -> [CoreRule] seqSpecInfo :: SpecInfo -> () -- | Change the name of the function the rule is keyed on on all of the -- CoreRules setSpecInfoHead :: Name -> SpecInfo -> SpecInfo -- | Specialisations of the Ids function which exist See Note -- [Specialisations and RULES in IdInfo] specInfo :: IdInfo -> SpecInfo setSpecInfo :: IdInfo -> SpecInfo -> IdInfo -- | Records whether an Id makes Constant Applicative Form -- references data CafInfo -- | Indicates that the Id is for either: -- --
    --
  1. A function or static constructor that refers to one or more CAFs, -- or
  2. --
  3. A real live CAF
  4. --
MayHaveCafRefs :: CafInfo -- | A function or static constructor that refers to no CAFs. NoCafRefs :: CafInfo ppCafInfo :: CafInfo -> SDoc mayHaveCafRefs :: CafInfo -> Bool -- | Id CAF info cafInfo :: IdInfo -> CafInfo setCafInfo :: IdInfo -> CafInfo -> IdInfo -- | If the Id is a lambda-bound variable then it may have -- lambda-bound variable info. Sometimes we know whether the lambda -- binding this variable is a "one-shot" lambda; that is, whether it is -- applied at most once. -- -- This information may be useful in optimisation, as computations may -- safely be floated inside such a lambda without risk of duplicating -- work. data LBVarInfo -- | No information NoLBVarInfo :: LBVarInfo -- | The lambda is applied at most once). IsOneShotLambda :: LBVarInfo -- | It is always safe to assume that an Id has no lambda-bound -- variable information noLBVarInfo :: LBVarInfo hasNoLBVarInfo :: LBVarInfo -> Bool -- | Info about a lambda-bound variable, if the Id is one lbvarInfo :: IdInfo -> LBVarInfo setLBVarInfo :: IdInfo -> LBVarInfo -> IdInfo -- | Tick box for Hpc-style coverage data TickBoxOp TickBox :: Module -> {-# UNPACK #-} !TickBoxId -> TickBoxOp type TickBoxId = Int instance Eq CafInfo instance Ord CafInfo instance Outputable TickBoxOp instance Show LBVarInfo instance Outputable LBVarInfo instance Outputable CafInfo instance Outputable IdDetails -- | GHC uses several kinds of name internally: -- -- module Id type Id = Var type DictId = EvId -- | For an explanation of global vs. local Ids, see -- Var#globalvslocal mkGlobalId :: IdDetails -> Name -> Type -> IdInfo -> Id -- | Make a global Id without any extra information at all mkVanillaGlobal :: Name -> Type -> Id -- | Make a global Id with no global information but some generic -- IdInfo mkVanillaGlobalWithInfo :: Name -> Type -> IdInfo -> Id -- | For an explanation of global vs. local Ids, see -- Var#globalvslocal mkLocalId :: Name -> Type -> Id mkLocalIdWithInfo :: Name -> Type -> IdInfo -> Id -- | Create a local Id that is marked as exported. This prevents -- things attached to it from being removed as dead code. mkExportedLocalId :: Name -> Type -> Id -- | Create a system local Id. These are local Ids (see -- Var#globalvslocal) that are created by the compiler out of thin -- air mkSysLocal :: FastString -> Unique -> Type -> Id mkSysLocalM :: MonadUnique m => FastString -> Type -> m Id -- | Create a user local Id. These are local Ids (see -- Var#globalvslocal) with a name and location that the user might -- recognize mkUserLocal :: OccName -> Unique -> Type -> SrcSpan -> Id mkUserLocalM :: MonadUnique m => OccName -> Type -> SrcSpan -> m Id -- | Create a template local for a series of types mkTemplateLocals :: [Type] -> [Id] -- | Create a template local for a series of type, but start from a -- specified template local mkTemplateLocalsNum :: Int -> [Type] -> [Id] -- | Create a template local: a family of system local Ids in -- bijection with Ints, typically used in unfoldings mkTemplateLocal :: Int -> Type -> Id -- | Workers get local names. CoreTidy will externalise these if -- necessary mkWorkerId :: Unique -> Id -> Type -> Id mkWiredInIdName :: Module -> FastString -> Unique -> Id -> Name idName :: Id -> Name idType :: Id -> Kind idUnique :: Id -> Unique idInfo :: Id -> IdInfo idDetails :: Id -> IdDetails isId :: Var -> Bool idPrimRep :: Id -> PrimRep -- | If the Id is that for a record selector, extract the -- sel_tycon and label. Panic otherwise recordSelectorFieldLabel :: Id -> (TyCon, FieldLabel) setIdName :: Id -> Name -> Id setIdUnique :: Id -> Unique -> Id -- | Not only does this set the Id Type, it also evaluates -- the type to try and reduce space usage setIdType :: Id -> Type -> Id setIdExported :: Id -> Id setIdNotExported :: Id -> Id -- | If it's a local, make it global globaliseId :: Id -> Id localiseId :: Id -> Id setIdInfo :: Id -> IdInfo -> Id lazySetIdInfo :: Id -> IdInfo -> Id modifyIdInfo :: (IdInfo -> IdInfo) -> Id -> Id maybeModifyIdInfo :: Maybe IdInfo -> Id -> Id zapLamIdInfo :: Id -> Id zapDemandIdInfo :: Id -> Id zapFragileIdInfo :: Id -> Id transferPolyIdInfo :: Id -> [Var] -> Id -> Id -- | isImplicitId tells whether an Ids info is implied by -- other declarations, so we don't need to put its signature in an -- interface file, even if it's mentioned in some other interface -- unfolding. isImplicitId :: Id -> Bool isDeadBinder :: Id -> Bool isDictId :: Id -> Bool -- | This predicate says whether the Id has a strict demand placed -- on it or has a type such that it can always be evaluated strictly -- (e.g., an unlifted type, but see the comment for isStrictType). -- We need to check separately whether the Id has a so-called -- "strict type" because if the demand for the given id hasn't -- been computed yet but id has a strict type, we still want -- isStrictId id to be True. isStrictId :: Id -> Bool -- | isExportedIdVar means "don't throw this away" isExportedId :: Var -> Bool isLocalId :: Var -> Bool isGlobalId :: Var -> Bool isRecordSelector :: Id -> Bool isNaughtyRecordSelector :: Id -> Bool isClassOpId_maybe :: Id -> Maybe Class isDFunId :: Id -> Bool dfunNSilent :: Id -> Int isPrimOpId :: Id -> Bool isPrimOpId_maybe :: Id -> Maybe PrimOp isFCallId :: Id -> Bool isFCallId_maybe :: Id -> Maybe ForeignCall isDataConWorkId :: Id -> Bool isDataConWorkId_maybe :: Id -> Maybe DataCon isDataConId_maybe :: Id -> Maybe DataCon -- | Get from either the worker or the wrapper Id to the -- DataCon. Currently used only in the desugarer. -- -- INVARIANT: idDataCon (dataConWrapId d) = d: remember, -- dataConWrapId can return either the wrapper or the worker idDataCon :: Id -> DataCon isConLikeId :: Id -> Bool -- | Returns true if an application to n args would diverge isBottomingId :: Id -> Bool idIsFrom :: Module -> Id -> Bool isTickBoxOp :: Id -> Bool isTickBoxOp_maybe :: Id -> Maybe TickBoxOp -- | Returns True of an Id which may not have a binding, -- even though it is defined in this module. hasNoBinding :: Id -> Bool idInlinePragma :: Id -> InlinePragma setInlinePragma :: Id -> InlinePragma -> Id modifyInlinePragma :: Id -> (InlinePragma -> InlinePragma) -> Id idInlineActivation :: Id -> Activation setInlineActivation :: Id -> Activation -> Id idRuleMatchInfo :: Id -> RuleMatchInfo -- | Returns whether the lambda associated with the Id is certainly -- applied at most once OR we are applying the "state hack" which makes -- it appear as if theis is the case for lambdas used in IO. You -- should prefer using this over isOneShotLambda isOneShotBndr :: Id -> Bool -- | Returns whether the lambda associated with the Id is certainly -- applied at most once. You probably want to use isOneShotBndr -- instead isOneShotLambda :: Id -> Bool -- | Should we apply the state hack to values of this Type? isStateHackType :: Type -> Bool setOneShotLambda :: Id -> Id clearOneShotLambda :: Id -> Id idArity :: Id -> Arity idDemandInfo :: Id -> Demand idDemandInfo_maybe :: Id -> Maybe Demand idStrictness :: Id -> StrictSig idStrictness_maybe :: Id -> Maybe StrictSig idUnfolding :: Id -> Unfolding realIdUnfolding :: Id -> Unfolding idSpecialisation :: Id -> SpecInfo idCoreRules :: Id -> [CoreRule] idHasRules :: Id -> Bool idCafInfo :: Id -> CafInfo idLBVarInfo :: Id -> LBVarInfo idOccInfo :: Id -> OccInfo setIdUnfoldingLazily :: Id -> Unfolding -> Id setIdUnfolding :: Id -> Unfolding -> Id setIdArity :: Id -> Arity -> Id setIdDemandInfo :: Id -> Demand -> Id setIdStrictness :: Id -> StrictSig -> Id zapIdStrictness :: Id -> Id setIdSpecialisation :: Id -> SpecInfo -> Id setIdCafInfo :: Id -> CafInfo -> Id setIdOccInfo :: Id -> OccInfo -> Id zapIdOccInfo :: Id -> Id -- | Builtin types and functions used by the vectoriser. These are all -- defined in the DPH package. module Vectorise.Builtins.Base mAX_DPH_PROD :: Int mAX_DPH_SUM :: Int mAX_DPH_COMBINE :: Int mAX_DPH_SCALAR_ARGS :: Int -- | Holds the names of the builtin types and functions used by the -- vectoriser. data Builtins Builtins :: Modules -> TyCon -> DataCon -> TyCon -> TyCon -> DataCon -> TyCon -> TyCon -> DataCon -> Var -> Var -> Var -> Array Int Var -> Class -> TyCon -> Var -> Var -> Var -> Var -> Array Int Var -> TyCon -> TyCon -> Array Int TyCon -> Var -> Var -> Var -> Var -> Array Int Type -> Array Int CoreExpr -> Array Int CoreExpr -> Array Int CoreExpr -> Array (Int, Int) CoreExpr -> Array Int Var -> Var -> Builtins dphModules :: Builtins -> Modules -- | PArray parrayTyCon :: Builtins -> TyCon -- | PArray parrayDataCon :: Builtins -> DataCon -- | PData pdataTyCon :: Builtins -> TyCon -- | PA paTyCon :: Builtins -> TyCon -- | PA paDataCon :: Builtins -> DataCon -- | PRepr preprTyCon :: Builtins -> TyCon -- | PR prTyCon :: Builtins -> TyCon -- | PR prDataCon :: Builtins -> DataCon -- | replicatePD replicatePDVar :: Builtins -> Var -- | emptyPD emptyPDVar :: Builtins -> Var -- | packByTagPD packByTagPDVar :: Builtins -> Var -- | combinePD combinePDVars :: Builtins -> Array Int Var -- | Scalar scalarClass :: Builtins -> Class -- | :-> closureTyCon :: Builtins -> TyCon -- | closure closureVar :: Builtins -> Var -- | $: applyVar :: Builtins -> Var -- | liftedClosure liftedClosureVar :: Builtins -> Var -- | liftedApply liftedApplyVar :: Builtins -> Var -- | closure1 .. closure2 closureCtrFuns :: Builtins -> Array Int Var -- | Void voidTyCon :: Builtins -> TyCon -- | Wrap wrapTyCon :: Builtins -> TyCon -- | Sum2 .. Sum3 sumTyCons :: Builtins -> Array Int TyCon -- | void voidVar :: Builtins -> Var -- | pvoid pvoidVar :: Builtins -> Var -- | fromVoid fromVoidVar :: Builtins -> Var -- | punit punitVar :: Builtins -> Var -- | Sel2 selTys :: Builtins -> Array Int Type -- | replicate2 selReplicates :: Builtins -> Array Int CoreExpr -- | pick2 selPicks :: Builtins -> Array Int CoreExpr -- | tagsSel2 selTagss :: Builtins -> Array Int CoreExpr -- | elementsSel2_0 .. elementsSel_2_1 selEls :: Builtins -> Array (Int, Int) CoreExpr -- | map, zipWith, zipWith3 scalarZips :: Builtins -> Array Int Var -- | lc liftingContext :: Builtins -> Var -- | Get an element from one of the arrays of contained by a -- Builtins. If the indexed thing is not in the array then panic. indexBuiltin :: (Ix i, Outputable i) => String -> (Builtins -> Array i a) -> i -> Builtins -> a selTy :: Int -> Builtins -> Type selReplicate :: Int -> Builtins -> CoreExpr selPick :: Int -> Builtins -> CoreExpr selTags :: Int -> Builtins -> CoreExpr selElements :: Int -> Int -> Builtins -> CoreExpr sumTyCon :: Int -> Builtins -> TyCon prodTyCon :: Int -> Builtins -> TyCon prodDataCon :: Int -> Builtins -> DataCon combinePDVar :: Int -> Builtins -> Var scalarZip :: Int -> Builtins -> Var closureCtrFun :: Int -> Builtins -> Var -- | Simple vectorised constructors and projections. module Vectorise.Vect -- | Contains the vectorised and lifted versions of some thing. type Vect a = (a, a) type VVar = Vect Var type VExpr = Vect CoreExpr type VBind = Vect CoreBind -- | Get the vectorised version of a thing. vectorised :: Vect a -> a -- | Get the lifted version of a thing. lifted :: Vect a -> a -- | Apply some function to both the vectorised and lifted versions of a -- thing. mapVect :: (a -> b) -> Vect a -> Vect b -- | Get the type of a vectorised variable. vVarType :: VVar -> Type -- | Make a vectorised non-recursive binding. vNonRec :: VVar -> VExpr -> VBind -- | Make a vectorised recursive binding. vRec :: [VVar] -> [VExpr] -> VBind -- | Wrap a vectorised variable as a vectorised expression. vVar :: VVar -> VExpr -- | Wrap a vectorised type as a vectorised expression. vType :: Type -> VExpr -- | Make a vectorised note. vNote :: Note -> VExpr -> VExpr -- | Make a vectorised let expresion. vLet :: VBind -> VExpr -> VExpr -- | Make a vectorised lambda abstraction. The lifted version also binds -- the lifting context. vLams :: Var -> [VVar] -> VExpr -> VExpr -- | Like vLams but the lifted version doesn't bind the lifting -- context. vLamsWithoutLC :: [VVar] -> VExpr -> VExpr -- | Apply some argument variables to an expression. The lifted version is -- also applied to the variable of the lifting context. vVarApps :: Var -> VExpr -> [VVar] -> VExpr vCaseDEFAULT :: VExpr -> VVar -> Type -> Type -> VExpr -> VExpr module PprCore pprCoreExpr :: OutputableBndr b => Expr b -> SDoc pprParendExpr :: OutputableBndr b => Expr b -> SDoc pprCoreBinding :: OutputableBndr b => Bind b -> SDoc pprCoreBindings :: OutputableBndr b => [Bind b] -> SDoc pprCoreAlt :: OutputableBndr a => (AltCon, [a], Expr a) -> SDoc pprRules :: [CoreRule] -> SDoc instance Outputable CoreRule instance Outputable e => Outputable (DFunArg e) instance Outputable Unfolding instance Outputable UnfoldingSource instance Outputable UnfoldingGuidance instance OutputableBndr Var instance OutputableBndr b => Outputable (Expr b) instance OutputableBndr b => Outputable (Bind b) module HsBinds type HsLocalBinds id = HsLocalBindsLR id id data HsLocalBindsLR idL idR HsValBinds :: (HsValBindsLR idL idR) -> HsLocalBindsLR idL idR HsIPBinds :: (HsIPBinds idR) -> HsLocalBindsLR idL idR EmptyLocalBinds :: HsLocalBindsLR idL idR type HsValBinds id = HsValBindsLR id id data HsValBindsLR idL idR ValBindsIn :: (LHsBindsLR idL idR) -> [LSig idR] -> HsValBindsLR idL idR ValBindsOut :: [(RecFlag, LHsBinds idL)] -> [LSig Name] -> HsValBindsLR idL idR type LHsBinds id = Bag (LHsBind id) type LHsBind id = Located (HsBind id) type HsBind id = HsBindLR id id type LHsBindLR idL idR = Located (HsBindLR idL idR) type LHsBindsLR idL idR = Bag (LHsBindLR idL idR) data HsBindLR idL idR -- | FunBind is used for both functions f x = e and variables -- f = x -> e -- -- Reason 1: Special case for type inference: see -- TcBinds.tcMonoBinds. -- -- Reason 2: Instance decls can only have FunBinds, which is convenient. -- If you change this, you'll need to change e.g. rnMethodBinds -- -- But note that the form f :: a->a = ... parses as a pattern -- binding, just like (f :: a -> a) = ... FunBind :: Located idL -> Bool -> MatchGroup idR -> HsWrapper -> NameSet -> Maybe (Int, [Id]) -> HsBindLR idL idR fun_id :: HsBindLR idL idR -> Located idL -- | True => infix declaration fun_infix :: HsBindLR idL idR -> Bool -- | The payload fun_matches :: HsBindLR idL idR -> MatchGroup idR -- | Coercion from the type of the MatchGroup to the type of the Id. -- Example: f :: Int -> forall a. a -> a f x y = y Then -- the MatchGroup will have type (Int -> a' -> a') (with a free -- type variable a'). The coercion will take a CoreExpr of this type and -- convert it to a CoreExpr of type Int -> forall a'. a' -> a' -- Notice that the coercion captures the free a'. fun_co_fn :: HsBindLR idL idR -> HsWrapper -- | After the renamer, this contains a superset of the Names of the other -- binders in this binding group that are free in the RHS of the defn -- Before renaming, and after typechecking, the field is unused; it's -- just an error thunk bind_fvs :: HsBindLR idL idR -> NameSet -- | This is the (optional) module-local tick number. fun_tick :: HsBindLR idL idR -> Maybe (Int, [Id]) PatBind :: LPat idL -> GRHSs idR -> PostTcType -> NameSet -> HsBindLR idL idR pat_lhs :: HsBindLR idL idR -> LPat idL pat_rhs :: HsBindLR idL idR -> GRHSs idR pat_rhs_ty :: HsBindLR idL idR -> PostTcType -- | After the renamer, this contains a superset of the Names of the other -- binders in this binding group that are free in the RHS of the defn -- Before renaming, and after typechecking, the field is unused; it's -- just an error thunk bind_fvs :: HsBindLR idL idR -> NameSet VarBind :: idL -> LHsExpr idR -> Bool -> HsBindLR idL idR var_id :: HsBindLR idL idR -> idL var_rhs :: HsBindLR idL idR -> LHsExpr idR var_inline :: HsBindLR idL idR -> Bool AbsBinds :: [TyVar] -> [EvVar] -> [([TyVar], idL, idL, TcSpecPrags)] -> TcEvBinds -> LHsBinds idL -> HsBindLR idL idR abs_tvs :: HsBindLR idL idR -> [TyVar] abs_ev_vars :: HsBindLR idL idR -> [EvVar] abs_exports :: HsBindLR idL idR -> [([TyVar], idL, idL, TcSpecPrags)] abs_ev_binds :: HsBindLR idL idR -> TcEvBinds abs_binds :: HsBindLR idL idR -> LHsBinds idL placeHolderNames :: NameSet pprValBindsForUser :: (OutputableBndr idL, OutputableBndr idR, OutputableBndr id2) => LHsBindsLR idL idR -> [LSig id2] -> SDoc pprLHsBinds :: (OutputableBndr idL, OutputableBndr idR) => LHsBindsLR idL idR -> SDoc emptyLocalBinds :: HsLocalBindsLR a b isEmptyLocalBinds :: HsLocalBindsLR a b -> Bool isEmptyValBinds :: HsValBindsLR a b -> Bool emptyValBindsOut :: HsValBindsLR a b emptyValBindsIn :: HsValBindsLR a b emptyLHsBinds :: LHsBindsLR idL idR isEmptyLHsBinds :: LHsBindsLR idL idR -> Bool plusHsValBinds :: HsValBinds a -> HsValBinds a -> HsValBinds a getTypeSigNames :: HsValBinds a -> NameSet ppr_monobind :: (OutputableBndr idL, OutputableBndr idR) => HsBindLR idL idR -> SDoc pprTicks :: SDoc -> SDoc -> SDoc data HsIPBinds id IPBinds :: [LIPBind id] -> TcEvBinds -> HsIPBinds id isEmptyIPBinds :: HsIPBinds id -> Bool type LIPBind id = Located (IPBind id) -- | Implicit parameter bindings. data IPBind id IPBind :: (IPName id) -> (LHsExpr id) -> IPBind id data HsWrapper WpHole :: HsWrapper WpCompose :: HsWrapper -> HsWrapper -> HsWrapper WpCast :: Coercion -> HsWrapper WpEvLam :: EvVar -> HsWrapper WpEvApp :: EvTerm -> HsWrapper WpTyLam :: TyVar -> HsWrapper WpTyApp :: Type -> HsWrapper WpLet :: TcEvBinds -> HsWrapper data TcEvBinds TcEvBinds :: EvBindsVar -> TcEvBinds EvBinds :: (Bag EvBind) -> TcEvBinds data EvBindsVar EvBindsVar :: (IORef EvBindMap) -> Unique -> EvBindsVar type EvBindMap = VarEnv EvBind emptyEvBindMap :: EvBindMap extendEvBinds :: EvBindMap -> EvVar -> EvTerm -> EvBindMap lookupEvBind :: EvBindMap -> EvVar -> Maybe EvBind evBindMapBinds :: EvBindMap -> Bag EvBind data EvBind EvBind :: EvVar -> EvTerm -> EvBind data EvTerm EvId :: EvId -> EvTerm EvCoercion :: Coercion -> EvTerm EvCast :: EvVar -> Coercion -> EvTerm EvDFunApp :: DFunId -> [Type] -> [EvVar] -> EvTerm EvSuperClass :: DictId -> Int -> EvTerm evVarTerm :: EvVar -> EvTerm emptyTcEvBinds :: TcEvBinds isEmptyTcEvBinds :: TcEvBinds -> Bool (<.>) :: HsWrapper -> HsWrapper -> HsWrapper mkWpTyApps :: [Type] -> HsWrapper mkWpEvApps :: [EvTerm] -> HsWrapper mkWpEvVarApps :: [EvVar] -> HsWrapper mkWpTyLams :: [TyVar] -> HsWrapper mkWpLams :: [Var] -> HsWrapper mkWpLet :: TcEvBinds -> HsWrapper mk_co_lam_fn :: (a -> HsWrapper) -> [a] -> HsWrapper mk_co_app_fn :: (a -> HsWrapper) -> [a] -> HsWrapper idHsWrapper :: HsWrapper isIdHsWrapper :: HsWrapper -> Bool pprHsWrapper :: SDoc -> HsWrapper -> SDoc type LSig name = Located (Sig name) data Sig name TypeSig :: (Located name) -> (LHsType name) -> Sig name IdSig :: Id -> Sig name FixSig :: (FixitySig name) -> Sig name InlineSig :: (Located name) -> InlinePragma -> Sig name SpecSig :: (Located name) -> (LHsType name) -> InlinePragma -> Sig name SpecInstSig :: (LHsType name) -> Sig name type LFixitySig name = Located (FixitySig name) data FixitySig name FixitySig :: (Located name) -> Fixity -> FixitySig name data TcSpecPrags IsDefaultMethod :: TcSpecPrags SpecPrags :: [LTcSpecPrag] -> TcSpecPrags type LTcSpecPrag = Located TcSpecPrag data TcSpecPrag SpecPrag :: Id -> HsWrapper -> InlinePragma -> TcSpecPrag noSpecPrags :: TcSpecPrags hasSpecPrags :: TcSpecPrags -> Bool isDefaultMethod :: TcSpecPrags -> Bool okBindSig :: Sig a -> Bool okHsBootSig :: Sig a -> Bool okClsDclSig :: Sig a -> Bool okInstDclSig :: Sig a -> Bool sigForThisGroup :: NameSet -> LSig Name -> Bool sigName :: LSig name -> Maybe name sigNameNoLoc :: Sig name -> Maybe name isFixityLSig :: LSig name -> Bool isVanillaLSig :: LSig name -> Bool isTypeLSig :: LSig name -> Bool isSpecLSig :: LSig name -> Bool isSpecInstLSig :: LSig name -> Bool isPragLSig :: LSig name -> Bool isInlineLSig :: LSig name -> Bool hsSigDoc :: Sig name -> SDoc eqHsSig :: Eq a => LSig a -> LSig a -> Bool ppr_sig :: OutputableBndr name => Sig name -> SDoc pragBrackets :: SDoc -> SDoc pprVarSig :: Outputable id => id -> SDoc -> SDoc pprSpec :: Outputable id => id -> SDoc -> InlinePragma -> SDoc pprTcSpecPrags :: TcSpecPrags -> SDoc instance Typeable1 IPBind instance Typeable EvTerm instance Typeable TcEvBinds instance Typeable1 HsIPBinds instance Typeable HsWrapper instance Typeable1 FixitySig instance Typeable1 Sig instance Typeable TcSpecPrag instance Typeable TcSpecPrags instance Typeable2 HsBindLR instance Typeable2 HsValBindsLR instance Typeable2 HsLocalBindsLR instance Data id => Data (IPBind id) instance Data EvTerm instance Data id => Data (HsIPBinds id) instance Data HsWrapper instance Data name => Data (FixitySig name) instance Data name => Data (Sig name) instance Data TcSpecPrag instance Data TcSpecPrags instance (Data idL, Data idR) => Data (HsBindLR idL idR) instance (Data idL, Data idR) => Data (HsValBindsLR idL idR) instance (Data idL, Data idR) => Data (HsLocalBindsLR idL idR) instance Outputable TcSpecPrag instance Outputable name => Outputable (FixitySig name) instance OutputableBndr name => Outputable (Sig name) instance Outputable EvTerm instance Outputable EvBind instance Outputable EvBindsVar instance Outputable TcEvBinds instance Outputable HsWrapper instance Data TcEvBinds instance OutputableBndr id => Outputable (IPBind id) instance OutputableBndr id => Outputable (HsIPBinds id) instance (OutputableBndr idL, OutputableBndr idR) => Outputable (HsBindLR idL idR) instance (OutputableBndr idL, OutputableBndr idR) => Outputable (HsValBindsLR idL idR) instance (OutputableBndr idL, OutputableBndr idR) => Outputable (HsLocalBindsLR idL idR) module HsPat data Pat id WildPat :: PostTcType -> Pat id VarPat :: id -> Pat id VarPatOut :: id -> TcEvBinds -> Pat id LazyPat :: (LPat id) -> Pat id AsPat :: (Located id) -> (LPat id) -> Pat id ParPat :: (LPat id) -> Pat id BangPat :: (LPat id) -> Pat id ListPat :: [LPat id] -> PostTcType -> Pat id TuplePat :: [LPat id] -> Boxity -> PostTcType -> Pat id PArrPat :: [LPat id] -> PostTcType -> Pat id ConPatIn :: (Located id) -> (HsConPatDetails id) -> Pat id ConPatOut :: Located DataCon -> [TyVar] -> [EvVar] -> TcEvBinds -> HsConPatDetails id -> Type -> Pat id pat_con :: Pat id -> Located DataCon pat_tvs :: Pat id -> [TyVar] pat_dicts :: Pat id -> [EvVar] pat_binds :: Pat id -> TcEvBinds pat_args :: Pat id -> HsConPatDetails id pat_ty :: Pat id -> Type ViewPat :: (LHsExpr id) -> (LPat id) -> PostTcType -> Pat id QuasiQuotePat :: (HsQuasiQuote id) -> Pat id LitPat :: HsLit -> Pat id NPat :: (HsOverLit id) -> (Maybe (SyntaxExpr id)) -> (SyntaxExpr id) -> Pat id NPlusKPat :: (Located id) -> (HsOverLit id) -> (SyntaxExpr id) -> (SyntaxExpr id) -> Pat id TypePat :: (LHsType id) -> Pat id SigPatIn :: (LPat id) -> (LHsType id) -> Pat id SigPatOut :: (LPat id) -> Type -> Pat id CoPat :: HsWrapper -> (Pat id) -> Type -> Pat id type InPat id = LPat id type OutPat id = LPat id type LPat id = Located (Pat id) data HsConDetails arg rec PrefixCon :: [arg] -> HsConDetails arg rec RecCon :: rec -> HsConDetails arg rec InfixCon :: arg -> arg -> HsConDetails arg rec type HsConPatDetails id = HsConDetails (LPat id) (HsRecFields id (LPat id)) hsConPatArgs :: HsConPatDetails id -> [LPat id] data HsRecFields id arg HsRecFields :: [HsRecField id arg] -> Maybe Int -> HsRecFields id arg rec_flds :: HsRecFields id arg -> [HsRecField id arg] rec_dotdot :: HsRecFields id arg -> Maybe Int data HsRecField id arg HsRecField :: Located id -> arg -> Bool -> HsRecField id arg hsRecFieldId :: HsRecField id arg -> Located id hsRecFieldArg :: HsRecField id arg -> arg hsRecPun :: HsRecField id arg -> Bool hsRecFields :: HsRecFields id arg -> [id] mkPrefixConPat :: DataCon -> [OutPat id] -> Type -> OutPat id mkCharLitPat :: Char -> OutPat id mkNilPat :: Type -> OutPat id isBangHsBind :: HsBind id -> Bool isBangLPat :: LPat id -> Bool hsPatNeedsParens :: Pat a -> Bool isIrrefutableHsPat :: OutputableBndr id => LPat id -> Bool pprParendLPat :: OutputableBndr name => LPat name -> SDoc instance Typeable2 HsConDetails instance Typeable2 HsRecField instance Typeable2 HsRecFields instance Typeable1 Pat instance (Data arg, Data rec) => Data (HsConDetails arg rec) instance (Data id, Data arg) => Data (HsRecField id arg) instance (Data id, Data arg) => Data (HsRecFields id arg) instance Data id => Data (Pat id) instance (OutputableBndr id, Outputable arg) => Outputable (HsRecField id arg) instance (OutputableBndr id, Outputable arg) => Outputable (HsRecFields id arg) instance OutputableBndr name => Outputable (Pat name) -- | Abstract syntax of global declarations. -- -- Definitions for: TyDecl and ConDecl, -- ClassDecl, InstDecl, DefaultDecl and -- ForeignDecl. module HsDecls -- | A Haskell Declaration data HsDecl id -- | A type or class declaration. TyClD :: (TyClDecl id) -> HsDecl id -- | An instance declaration. InstD :: (InstDecl id) -> HsDecl id DerivD :: (DerivDecl id) -> HsDecl id ValD :: (HsBind id) -> HsDecl id SigD :: (Sig id) -> HsDecl id DefD :: (DefaultDecl id) -> HsDecl id ForD :: (ForeignDecl id) -> HsDecl id WarningD :: (WarnDecl id) -> HsDecl id AnnD :: (AnnDecl id) -> HsDecl id RuleD :: (RuleDecl id) -> HsDecl id SpliceD :: (SpliceDecl id) -> HsDecl id DocD :: (DocDecl) -> HsDecl id QuasiQuoteD :: (HsQuasiQuote id) -> HsDecl id type LHsDecl id = Located (HsDecl id) -- | A type or class declaration. data TyClDecl name ForeignType :: Located name -> Maybe FastString -> TyClDecl name tcdLName :: TyClDecl name -> Located name tcdExtName :: TyClDecl name -> Maybe FastString -- |
--   type/data family T :: *->*
--   
TyFamily :: FamilyFlavour -> Located name -> [LHsTyVarBndr name] -> Maybe Kind -> TyClDecl name tcdFlavour :: TyClDecl name -> FamilyFlavour tcdLName :: TyClDecl name -> Located name tcdTyVars :: TyClDecl name -> [LHsTyVarBndr name] tcdKind :: TyClDecl name -> Maybe Kind -- | Declares a data type or newtype, giving its construcors -- data/newtype T a = constrs data/newtype instance T [a] = -- constrs TyData :: NewOrData -> LHsContext name -> Located name -> [LHsTyVarBndr name] -> Maybe [LHsType name] -> Maybe Kind -> [LConDecl name] -> Maybe [LHsType name] -> TyClDecl name tcdND :: TyClDecl name -> NewOrData -- | Context tcdCtxt :: TyClDecl name -> LHsContext name tcdLName :: TyClDecl name -> Located name tcdTyVars :: TyClDecl name -> [LHsTyVarBndr name] -- | Type patterns. -- -- Just [t1..tn] for data instance T t1..tn = ... in -- this case tcdTyVars = fv( tcdTyPats ). Nothing for -- everything else. tcdTyPats :: TyClDecl name -> Maybe [LHsType name] -- | Optional kind signature. -- -- (Just k) for a GADT-style data, or data -- instance decl with explicit kind sig tcdKindSig :: TyClDecl name -> Maybe Kind -- | Data constructors -- -- For data T a = T1 | T2 a the LConDecls all have -- ResTyH98. For data T a where { T1 :: T a } the -- LConDecls all have ResTyGADT. tcdCons :: TyClDecl name -> [LConDecl name] -- | Derivings; Nothing => not specified, Just [] -- => derive exactly what is asked -- -- These types must be of form forall ab. C ty1 ty2 -- Typically the foralls and ty args are empty, but they are non-empty -- for the newtype-deriving case tcdDerivs :: TyClDecl name -> Maybe [LHsType name] TySynonym :: Located name -> [LHsTyVarBndr name] -> Maybe [LHsType name] -> LHsType name -> TyClDecl name tcdLName :: TyClDecl name -> Located name tcdTyVars :: TyClDecl name -> [LHsTyVarBndr name] -- | Type patterns. -- -- Just [t1..tn] for data instance T t1..tn = ... in -- this case tcdTyVars = fv( tcdTyPats ). Nothing for -- everything else. tcdTyPats :: TyClDecl name -> Maybe [LHsType name] -- | synonym expansion tcdSynRhs :: TyClDecl name -> LHsType name ClassDecl :: LHsContext name -> Located name -> [LHsTyVarBndr name] -> [Located (FunDep name)] -> [LSig name] -> LHsBinds name -> [LTyClDecl name] -> [LDocDecl] -> TyClDecl name -- | Context tcdCtxt :: TyClDecl name -> LHsContext name tcdLName :: TyClDecl name -> Located name tcdTyVars :: TyClDecl name -> [LHsTyVarBndr name] -- | Functional deps tcdFDs :: TyClDecl name -> [Located (FunDep name)] -- | Methods' signatures tcdSigs :: TyClDecl name -> [LSig name] -- | Default methods tcdMeths :: TyClDecl name -> LHsBinds name -- | Associated types; ie only TyFamily and TySynonym; the -- latter for defaults tcdATs :: TyClDecl name -> [LTyClDecl name] -- | Haddock docs tcdDocs :: TyClDecl name -> [LDocDecl] type LTyClDecl name = Located (TyClDecl name) -- | type class isClassDecl :: TyClDecl name -> Bool -- | vanilla Haskell type synonym (ie, not a type instance) isSynDecl :: TyClDecl name -> Bool -- | True = argument is a data/newtype or -- data/newtype instance declaration. isDataDecl :: TyClDecl name -> Bool -- | type or type instance declaration isTypeDecl :: TyClDecl name -> Bool -- | type family declaration isFamilyDecl :: TyClDecl name -> Bool -- | family instance (types, newtypes, and data types) isFamInstDecl :: TyClDecl name -> Bool tcdName :: TyClDecl name -> name tyClDeclTyVars :: TyClDecl name -> [LHsTyVarBndr name] countTyClDecls :: [TyClDecl name] -> (Int, Int, Int, Int, Int, Int) data InstDecl name InstDecl :: (LHsType name) -> (LHsBinds name) -> [LSig name] -> [LTyClDecl name] -> InstDecl name type LInstDecl name = Located (InstDecl name) data NewOrData -- |
--   newtype Blah ...
--   
NewType :: NewOrData -- |
--   data Blah ...
--   
DataType :: NewOrData data FamilyFlavour -- |
--   type family ...
--   
TypeFamily :: FamilyFlavour -- |
--   data family ...
--   
DataFamily :: FamilyFlavour instDeclATs :: [LInstDecl name] -> [LTyClDecl name] data DerivDecl name DerivDecl :: (LHsType name) -> DerivDecl name type LDerivDecl name = Located (DerivDecl name) data RuleDecl name HsRule :: RuleName -> Activation -> [RuleBndr name] -> (Located (HsExpr name)) -> NameSet -> (Located (HsExpr name)) -> NameSet -> RuleDecl name type LRuleDecl name = Located (RuleDecl name) data RuleBndr name RuleBndr :: (Located name) -> RuleBndr name RuleBndrSig :: (Located name) -> (LHsType name) -> RuleBndr name collectRuleBndrSigTys :: [RuleBndr name] -> [LHsType name] data DefaultDecl name DefaultDecl :: [LHsType name] -> DefaultDecl name type LDefaultDecl name = Located (DefaultDecl name) data SpliceDecl id SpliceDecl :: (Located (HsExpr id)) -> HsExplicitFlag -> SpliceDecl id data ForeignDecl name ForeignImport :: (Located name) -> (LHsType name) -> ForeignImport -> ForeignDecl name ForeignExport :: (Located name) -> (LHsType name) -> ForeignExport -> ForeignDecl name type LForeignDecl name = Located (ForeignDecl name) data ForeignImport CImport :: CCallConv -> Safety -> FastString -> CImportSpec -> ForeignImport data ForeignExport CExport :: CExportSpec -> ForeignExport data CImportSpec CLabel :: CLabelString -> CImportSpec CFunction :: CCallTarget -> CImportSpec CWrapper :: CImportSpec data ConDecl name ConDecl :: Located name -> HsExplicitFlag -> [LHsTyVarBndr name] -> LHsContext name -> HsConDeclDetails name -> ResType name -> Maybe LHsDocString -> Bool -> ConDecl name -- | Constructor name. This is used for the DataCon itself, and for the -- user-callable wrapper Id. con_name :: ConDecl name -> Located name -- | Is there an user-written forall? (cf. HsForAllTy) con_explicit :: ConDecl name -> HsExplicitFlag -- | Type variables. Depending on con_res this describes the -- follewing entities -- -- con_qvars :: ConDecl name -> [LHsTyVarBndr name] -- | The context. This does not include the "stupid theta" which -- lives only in the TyData decl. con_cxt :: ConDecl name -> LHsContext name -- | The main payload con_details :: ConDecl name -> HsConDeclDetails name -- | Result type of the constructor con_res :: ConDecl name -> ResType name -- | A possible Haddock comment. con_doc :: ConDecl name -> Maybe LHsDocString -- | TEMPORARY field; True = user has employed now-deprecated syntax -- for GADT-style record decl C { blah } :: T a b Remove this when we no -- longer parse this stuff, and hence do not need to report decprecated -- use con_old_rec :: ConDecl name -> Bool type LConDecl name = Located (ConDecl name) data ResType name ResTyH98 :: ResType name ResTyGADT :: (LHsType name) -> ResType name type HsConDeclDetails name = HsConDetails (LBangType name) [ConDeclField name] hsConDeclArgTys :: HsConDeclDetails name -> [LBangType name] data DocDecl DocCommentNext :: HsDocString -> DocDecl DocCommentPrev :: HsDocString -> DocDecl DocCommentNamed :: String -> HsDocString -> DocDecl DocGroup :: Int -> HsDocString -> DocDecl type LDocDecl = Located (DocDecl) docDeclDoc :: DocDecl -> HsDocString data WarnDecl name Warning :: name -> WarningTxt -> WarnDecl name type LWarnDecl name = Located (WarnDecl name) data AnnDecl name HsAnnotation :: (AnnProvenance name) -> (Located (HsExpr name)) -> AnnDecl name type LAnnDecl name = Located (AnnDecl name) data AnnProvenance name ValueAnnProvenance :: name -> AnnProvenance name TypeAnnProvenance :: name -> AnnProvenance name ModuleAnnProvenance :: AnnProvenance name annProvenanceName_maybe :: AnnProvenance name -> Maybe name modifyAnnProvenanceNameM :: Monad m => (before -> m after) -> AnnProvenance before -> m (AnnProvenance after) -- | A HsDecl is categorised into a HsGroup before being fed -- to the renamer. data HsGroup id HsGroup :: HsValBinds id -> [[LTyClDecl id]] -> [LInstDecl id] -> [LDerivDecl id] -> [LFixitySig id] -> [LDefaultDecl id] -> [LForeignDecl id] -> [LWarnDecl id] -> [LAnnDecl id] -> [LRuleDecl id] -> [LDocDecl] -> HsGroup id hs_valds :: HsGroup id -> HsValBinds id hs_tyclds :: HsGroup id -> [[LTyClDecl id]] hs_instds :: HsGroup id -> [LInstDecl id] hs_derivds :: HsGroup id -> [LDerivDecl id] hs_fixds :: HsGroup id -> [LFixitySig id] hs_defds :: HsGroup id -> [LDefaultDecl id] hs_fords :: HsGroup id -> [LForeignDecl id] hs_warnds :: HsGroup id -> [LWarnDecl id] hs_annds :: HsGroup id -> [LAnnDecl id] hs_ruleds :: HsGroup id -> [LRuleDecl id] hs_docs :: HsGroup id -> [LDocDecl] emptyRdrGroup :: HsGroup a emptyRnGroup :: HsGroup a appendGroups :: HsGroup a -> HsGroup a -> HsGroup a instance Typeable1 SpliceDecl instance Typeable NewOrData instance Typeable FamilyFlavour instance Typeable1 ResType instance Typeable1 ConDecl instance Typeable1 DerivDecl instance Typeable1 DefaultDecl instance Typeable CImportSpec instance Typeable ForeignImport instance Typeable ForeignExport instance Typeable1 ForeignDecl instance Typeable1 RuleBndr instance Typeable1 RuleDecl instance Typeable DocDecl instance Typeable1 TyClDecl instance Typeable1 InstDecl instance Typeable1 WarnDecl instance Typeable1 AnnProvenance instance Typeable1 AnnDecl instance Typeable1 HsGroup instance Typeable1 HsDecl instance Data id => Data (SpliceDecl id) instance Eq NewOrData instance Data NewOrData instance Data FamilyFlavour instance Data name => Data (ResType name) instance Data name => Data (ConDecl name) instance Data name => Data (DerivDecl name) instance Data name => Data (DefaultDecl name) instance Data CImportSpec instance Data ForeignImport instance Data ForeignExport instance Data name => Data (ForeignDecl name) instance Data name => Data (RuleBndr name) instance Data name => Data (RuleDecl name) instance Data DocDecl instance Data name => Data (TyClDecl name) instance Data name => Data (InstDecl name) instance Data name => Data (WarnDecl name) instance Data name => Data (AnnProvenance name) instance Data name => Data (AnnDecl name) instance Data id => Data (HsGroup id) instance Data id => Data (HsDecl id) instance OutputableBndr name => Outputable (AnnDecl name) instance OutputableBndr name => Outputable (WarnDecl name) instance Outputable DocDecl instance OutputableBndr name => Outputable (RuleBndr name) instance OutputableBndr name => Outputable (RuleDecl name) instance Outputable ForeignExport instance Outputable ForeignImport instance OutputableBndr name => Outputable (ForeignDecl name) instance OutputableBndr name => Outputable (DefaultDecl name) instance OutputableBndr name => Outputable (DerivDecl name) instance OutputableBndr name => Outputable (InstDecl name) instance OutputableBndr name => Outputable (ConDecl name) instance OutputableBndr name => Outputable (ResType name) instance Outputable NewOrData instance OutputableBndr name => Outputable (TyClDecl name) instance OutputableBndr name => Outputable (SpliceDecl name) instance OutputableBndr name => Outputable (HsGroup name) instance OutputableBndr name => Outputable (HsDecl name) -- | Abstract Haskell syntax for expressions. module HsExpr type LHsExpr id = Located (HsExpr id) -- | PostTcExpr is an evidence expression attached to the syntax tree by -- the type checker (c.f. postTcType). type PostTcExpr = HsExpr Id -- | We use a PostTcTable where there are a bunch of pieces of evidence, -- more than is convenient to keep individually. type PostTcTable = [(Name, PostTcExpr)] noPostTcExpr :: PostTcExpr noPostTcTable :: PostTcTable -- | SyntaxExpr is like PostTcExpr, but it's filled in a little -- earlier, by the renamer. It's used for rebindable syntax. -- -- E.g. (>>=) is filled in before the renamer by the -- appropriate Name for (>>=), and then -- instantiated by the type checker with its type args etc type SyntaxExpr id = HsExpr id noSyntaxExpr :: SyntaxExpr id -- | Currently used only for CmdTop (sigh) -- -- type SyntaxTable id = [(Name, SyntaxExpr id)] noSyntaxTable :: SyntaxTable id -- | A Haskell expression. data HsExpr id -- | variable HsVar :: id -> HsExpr id -- | implicit parameter HsIPVar :: (IPName id) -> HsExpr id -- | Overloaded literals HsOverLit :: (HsOverLit id) -> HsExpr id -- | Simple (non-overloaded) literals HsLit :: HsLit -> HsExpr id HsLam :: (MatchGroup id) -> HsExpr id HsApp :: (LHsExpr id) -> (LHsExpr id) -> HsExpr id OpApp :: (LHsExpr id) -> (LHsExpr id) -> Fixity -> (LHsExpr id) -> HsExpr id NegApp :: (LHsExpr id) -> (SyntaxExpr id) -> HsExpr id HsPar :: (LHsExpr id) -> HsExpr id SectionL :: (LHsExpr id) -> (LHsExpr id) -> HsExpr id SectionR :: (LHsExpr id) -> (LHsExpr id) -> HsExpr id ExplicitTuple :: [HsTupArg id] -> Boxity -> HsExpr id HsCase :: (LHsExpr id) -> (MatchGroup id) -> HsExpr id HsIf :: (Maybe (SyntaxExpr id)) -> (LHsExpr id) -> (LHsExpr id) -> (LHsExpr id) -> HsExpr id HsLet :: (HsLocalBinds id) -> (LHsExpr id) -> HsExpr id HsDo :: (HsStmtContext Name) -> [LStmt id] -> (LHsExpr id) -> PostTcType -> HsExpr id ExplicitList :: PostTcType -> [LHsExpr id] -> HsExpr id ExplicitPArr :: PostTcType -> [LHsExpr id] -> HsExpr id RecordCon :: (Located id) -> PostTcExpr -> (HsRecordBinds id) -> HsExpr id RecordUpd :: (LHsExpr id) -> (HsRecordBinds id) -> [DataCon] -> [PostTcType] -> [PostTcType] -> HsExpr id ExprWithTySig :: (LHsExpr id) -> (LHsType id) -> HsExpr id ExprWithTySigOut :: (LHsExpr id) -> (LHsType Name) -> HsExpr id ArithSeq :: PostTcExpr -> (ArithSeqInfo id) -> HsExpr id PArrSeq :: PostTcExpr -> (ArithSeqInfo id) -> HsExpr id HsSCC :: FastString -> (LHsExpr id) -> HsExpr id HsCoreAnn :: FastString -> (LHsExpr id) -> HsExpr id HsBracket :: (HsBracket id) -> HsExpr id HsBracketOut :: (HsBracket Name) -> [PendingSplice] -> HsExpr id HsSpliceE :: (HsSplice id) -> HsExpr id HsQuasiQuoteE :: (HsQuasiQuote id) -> HsExpr id HsProc :: (LPat id) -> (LHsCmdTop id) -> HsExpr id HsArrApp :: (LHsExpr id) -> (LHsExpr id) -> PostTcType -> HsArrAppType -> Bool -> HsExpr id HsArrForm :: (LHsExpr id) -> (Maybe Fixity) -> [LHsCmdTop id] -> HsExpr id HsTick :: Int -> [id] -> (LHsExpr id) -> HsExpr id HsBinTick :: Int -> Int -> (LHsExpr id) -> HsExpr id HsTickPragma :: (FastString, (Int, Int), (Int, Int)) -> (LHsExpr id) -> HsExpr id EWildPat :: HsExpr id EAsPat :: (Located id) -> (LHsExpr id) -> HsExpr id EViewPat :: (LHsExpr id) -> (LHsExpr id) -> HsExpr id ELazyPat :: (LHsExpr id) -> HsExpr id HsType :: (LHsType id) -> HsExpr id HsWrap :: HsWrapper -> (HsExpr id) -> HsExpr id data HsTupArg id Present :: (LHsExpr id) -> HsTupArg id Missing :: PostTcType -> HsTupArg id tupArgPresent :: HsTupArg id -> Bool type PendingSplice = (Name, LHsExpr Id) pprLExpr :: OutputableBndr id => LHsExpr id -> SDoc pprExpr :: OutputableBndr id => HsExpr id -> SDoc isQuietHsExpr :: HsExpr id -> Bool pprBinds :: (OutputableBndr idL, OutputableBndr idR) => HsLocalBindsLR idL idR -> SDoc ppr_lexpr :: OutputableBndr id => LHsExpr id -> SDoc ppr_expr :: OutputableBndr id => HsExpr id -> SDoc pprCmdArg :: OutputableBndr id => HsCmdTop id -> SDoc pa_brackets :: SDoc -> SDoc pprDebugParendExpr :: OutputableBndr id => LHsExpr id -> SDoc pprParendExpr :: OutputableBndr id => LHsExpr id -> SDoc isAtomicHsExpr :: HsExpr id -> Bool type HsCmd id = HsExpr id type LHsCmd id = LHsExpr id data HsArrAppType HsHigherOrderApp :: HsArrAppType HsFirstOrderApp :: HsArrAppType type LHsCmdTop id = Located (HsCmdTop id) data HsCmdTop id HsCmdTop :: (LHsCmd id) -> [PostTcType] -> PostTcType -> (SyntaxTable id) -> HsCmdTop id type HsRecordBinds id = HsRecFields id (LHsExpr id) data MatchGroup id MatchGroup :: [LMatch id] -> PostTcType -> MatchGroup id type LMatch id = Located (Match id) data Match id Match :: [LPat id] -> (Maybe (LHsType id)) -> (GRHSs id) -> Match id isEmptyMatchGroup :: MatchGroup id -> Bool matchGroupArity :: MatchGroup id -> Arity hsLMatchPats :: LMatch id -> [LPat id] -- | GRHSs are used both for pattern bindings and for Matches data GRHSs id GRHSs :: [LGRHS id] -> (HsLocalBinds id) -> GRHSs id -- | Guarded RHSs grhssGRHSs :: GRHSs id -> [LGRHS id] -- | The where clause grhssLocalBinds :: GRHSs id -> (HsLocalBinds id) type LGRHS id = Located (GRHS id) -- | Guarded Right Hand Side. data GRHS id GRHS :: [LStmt id] -> (LHsExpr id) -> GRHS id pprMatches :: (OutputableBndr idL, OutputableBndr idR) => HsMatchContext idL -> MatchGroup idR -> SDoc pprFunBind :: (OutputableBndr idL, OutputableBndr idR) => idL -> Bool -> MatchGroup idR -> SDoc pprPatBind :: (OutputableBndr bndr, OutputableBndr id) => LPat bndr -> GRHSs id -> SDoc pprMatch :: (OutputableBndr idL, OutputableBndr idR) => HsMatchContext idL -> Match idR -> SDoc pprGRHSs :: (OutputableBndr idL, OutputableBndr idR) => HsMatchContext idL -> GRHSs idR -> SDoc pprGRHS :: (OutputableBndr idL, OutputableBndr idR) => HsMatchContext idL -> GRHS idR -> SDoc pp_rhs :: OutputableBndr idR => HsMatchContext idL -> LHsExpr idR -> SDoc type LStmt id = Located (StmtLR id id) type LStmtLR idL idR = Located (StmtLR idL idR) type Stmt id = StmtLR id id data StmtLR idL idR BindStmt :: (LPat idL) -> (LHsExpr idR) -> (SyntaxExpr idR) -> (SyntaxExpr idR) -> StmtLR idL idR ExprStmt :: (LHsExpr idR) -> (SyntaxExpr idR) -> PostTcType -> StmtLR idL idR LetStmt :: (HsLocalBindsLR idL idR) -> StmtLR idL idR ParStmt :: [([LStmt idL], [idR])] -> StmtLR idL idR TransformStmt :: [LStmt idL] -> [idR] -> (LHsExpr idR) -> (Maybe (LHsExpr idR)) -> StmtLR idL idR GroupStmt :: [LStmt idL] -> [(idR, idR)] -> (Maybe (LHsExpr idR)) -> (Either (LHsExpr idR) (SyntaxExpr idR)) -> StmtLR idL idR RecStmt :: [LStmtLR idL idR] -> [idR] -> [idR] -> SyntaxExpr idR -> SyntaxExpr idR -> SyntaxExpr idR -> [PostTcExpr] -> TcEvBinds -> StmtLR idL idR recS_stmts :: StmtLR idL idR -> [LStmtLR idL idR] recS_later_ids :: StmtLR idL idR -> [idR] recS_rec_ids :: StmtLR idL idR -> [idR] recS_bind_fn :: StmtLR idL idR -> SyntaxExpr idR recS_ret_fn :: StmtLR idL idR -> SyntaxExpr idR recS_mfix_fn :: StmtLR idL idR -> SyntaxExpr idR recS_rec_rets :: StmtLR idL idR -> [PostTcExpr] recS_dicts :: StmtLR idL idR -> TcEvBinds pprStmt :: (OutputableBndr idL, OutputableBndr idR) => (StmtLR idL idR) -> SDoc pprTransformStmt :: OutputableBndr id => [id] -> LHsExpr id -> Maybe (LHsExpr id) -> SDoc pprGroupStmt :: OutputableBndr id => Maybe (LHsExpr id) -> Either (LHsExpr id) (SyntaxExpr is) -> SDoc pprBy :: OutputableBndr id => Maybe (LHsExpr id) -> SDoc pprDo :: OutputableBndr id => HsStmtContext any -> [LStmt id] -> LHsExpr id -> SDoc ppr_do_stmts :: OutputableBndr id => [LStmt id] -> LHsExpr id -> SDoc ppr_lc_stmts :: OutputableBndr id => [LStmt id] -> [SDoc] pprComp :: OutputableBndr id => [LStmt id] -> LHsExpr id -> SDoc data HsSplice id HsSplice :: id -> (LHsExpr id) -> HsSplice id pprSplice :: OutputableBndr id => HsSplice id -> SDoc data HsBracket id ExpBr :: (LHsExpr id) -> HsBracket id PatBr :: (LPat id) -> HsBracket id DecBrL :: [LHsDecl id] -> HsBracket id DecBrG :: (HsGroup id) -> HsBracket id TypBr :: (LHsType id) -> HsBracket id VarBr :: id -> HsBracket id pprHsBracket :: OutputableBndr id => HsBracket id -> SDoc thBrackets :: SDoc -> SDoc -> SDoc data ArithSeqInfo id From :: (LHsExpr id) -> ArithSeqInfo id FromThen :: (LHsExpr id) -> (LHsExpr id) -> ArithSeqInfo id FromTo :: (LHsExpr id) -> (LHsExpr id) -> ArithSeqInfo id FromThenTo :: (LHsExpr id) -> (LHsExpr id) -> (LHsExpr id) -> ArithSeqInfo id pp_dotdot :: SDoc data HsMatchContext id FunRhs :: id -> Bool -> HsMatchContext id LambdaExpr :: HsMatchContext id CaseAlt :: HsMatchContext id ProcExpr :: HsMatchContext id PatBindRhs :: HsMatchContext id RecUpd :: HsMatchContext id StmtCtxt :: (HsStmtContext id) -> HsMatchContext id ThPatQuote :: HsMatchContext id data HsStmtContext id ListComp :: HsStmtContext id DoExpr :: HsStmtContext id GhciStmt :: HsStmtContext id MDoExpr :: PostTcTable -> HsStmtContext id PArrComp :: HsStmtContext id PatGuard :: (HsMatchContext id) -> HsStmtContext id ParStmtCtxt :: (HsStmtContext id) -> HsStmtContext id TransformStmtCtxt :: (HsStmtContext id) -> HsStmtContext id isDoExpr :: HsStmtContext id -> Bool isListCompExpr :: HsStmtContext id -> Bool matchSeparator :: HsMatchContext id -> SDoc pprMatchContext :: Outputable id => HsMatchContext id -> SDoc pprMatchContextNoun :: Outputable id => HsMatchContext id -> SDoc pprStmtContext :: Outputable id => HsStmtContext id -> SDoc matchContextErrString :: Outputable id => HsMatchContext id -> SDoc pprMatchInCtxt :: (OutputableBndr idL, OutputableBndr idR) => HsMatchContext idL -> Match idR -> SDoc pprStmtInCtxt :: (OutputableBndr idL, OutputableBndr idR) => HsStmtContext idL -> StmtLR idL idR -> SDoc instance Typeable HsArrAppType instance Typeable1 HsExpr instance Typeable1 MatchGroup instance Typeable1 Match instance Typeable1 GRHSs instance Typeable1 GRHS instance Typeable2 StmtLR instance Typeable1 HsSplice instance Typeable1 HsStmtContext instance Typeable1 HsMatchContext instance Typeable1 ArithSeqInfo instance Typeable1 HsBracket instance Typeable1 HsCmdTop instance Typeable1 HsTupArg instance Data HsArrAppType instance Data id => Data (HsExpr id) instance Data id => Data (MatchGroup id) instance Data id => Data (Match id) instance Data id => Data (GRHSs id) instance Data id => Data (GRHS id) instance (Data idL, Data idR) => Data (StmtLR idL idR) instance Data id => Data (HsSplice id) instance Data id => Data (HsStmtContext id) instance Data id => Data (HsMatchContext id) instance Data id => Data (ArithSeqInfo id) instance Data id => Data (HsBracket id) instance Data id => Data (HsCmdTop id) instance Data id => Data (HsTupArg id) instance OutputableBndr id => Outputable (ArithSeqInfo id) instance OutputableBndr id => Outputable (HsBracket id) instance OutputableBndr id => Outputable (HsSplice id) instance (OutputableBndr idL, OutputableBndr idR) => Outputable (StmtLR idL idR) instance OutputableBndr id => Outputable (HsCmdTop id) instance OutputableBndr id => Outputable (HsExpr id) module HsUtils mkHsPar :: LHsExpr id -> LHsExpr id mkHsApp :: LHsExpr name -> LHsExpr name -> LHsExpr name mkHsConApp :: DataCon -> [Type] -> [HsExpr Id] -> LHsExpr Id mkSimpleHsAlt :: LPat id -> LHsExpr id -> LMatch id mkSimpleMatch :: [LPat id] -> LHsExpr id -> LMatch id unguardedGRHSs :: LHsExpr id -> GRHSs id unguardedRHS :: LHsExpr id -> [LGRHS id] mkMatchGroup :: [LMatch id] -> MatchGroup id mkMatch :: [LPat id] -> LHsExpr id -> HsLocalBinds id -> LMatch id mkHsLam :: [LPat id] -> LHsExpr id -> LHsExpr id mkHsIf :: LHsExpr id -> LHsExpr id -> LHsExpr id -> HsExpr id mkHsWrap :: HsWrapper -> HsExpr id -> HsExpr id mkLHsWrap :: HsWrapper -> LHsExpr id -> LHsExpr id mkHsWrapCoI :: CoercionI -> HsExpr id -> HsExpr id mkLHsWrapCoI :: CoercionI -> LHsExpr id -> LHsExpr id coiToHsWrapper :: CoercionI -> HsWrapper mkHsDictLet :: TcEvBinds -> LHsExpr Id -> LHsExpr Id mkHsOpApp :: LHsExpr id -> id -> LHsExpr id -> HsExpr id mkHsDo :: HsStmtContext Name -> [LStmt id] -> LHsExpr id -> HsExpr id mkHsWrapPat :: HsWrapper -> Pat id -> Type -> Pat id mkHsWrapPatCoI :: CoercionI -> Pat id -> Type -> Pat id nlHsTyApp :: name -> [Type] -> LHsExpr name nlHsVar :: id -> LHsExpr id nlHsLit :: HsLit -> LHsExpr id nlHsApp :: LHsExpr id -> LHsExpr id -> LHsExpr id nlHsApps :: id -> [LHsExpr id] -> LHsExpr id nlHsIntLit :: Integer -> LHsExpr id nlHsVarApps :: id -> [id] -> LHsExpr id nlHsDo :: HsStmtContext Name -> [LStmt id] -> LHsExpr id -> LHsExpr id nlHsOpApp :: LHsExpr id -> id -> LHsExpr id -> LHsExpr id nlHsLam :: LMatch id -> LHsExpr id nlHsPar :: LHsExpr id -> LHsExpr id nlHsIf :: LHsExpr id -> LHsExpr id -> LHsExpr id -> LHsExpr id nlHsCase :: LHsExpr id -> [LMatch id] -> LHsExpr id nlList :: [LHsExpr id] -> LHsExpr id mkLHsTupleExpr :: [LHsExpr a] -> LHsExpr a mkLHsVarTuple :: [a] -> LHsExpr a missingTupArg :: HsTupArg a mkFunBind :: Located id -> [LMatch id] -> HsBind id mkVarBind :: id -> LHsExpr id -> LHsBind id mkHsVarBind :: SrcSpan -> id -> LHsExpr id -> LHsBind id mk_easy_FunBind :: SrcSpan -> id -> [LPat id] -> LHsExpr id -> LHsBind id mkHsIntegral :: Integer -> PostTcType -> HsOverLit id mkHsFractional :: Rational -> PostTcType -> HsOverLit id mkHsIsString :: FastString -> PostTcType -> HsOverLit id mkHsString :: String -> HsLit mkNPat :: HsOverLit id -> Maybe (SyntaxExpr id) -> Pat id mkNPlusKPat :: Located id -> HsOverLit id -> Pat id nlVarPat :: id -> LPat id nlLitPat :: HsLit -> LPat id nlConVarPat :: id -> [id] -> LPat id nlConPat :: id -> [LPat id] -> LPat id nlInfixConPat :: id -> LPat id -> LPat id -> LPat id nlNullaryConPat :: id -> LPat id nlWildConPat :: DataCon -> LPat RdrName nlWildPat :: LPat id nlTuplePat :: [LPat id] -> Boxity -> LPat id mkHsAppTy :: LHsType name -> LHsType name -> LHsType name userHsTyVarBndrs :: [Located name] -> [Located (HsTyVarBndr name)] nlHsAppTy :: LHsType name -> LHsType name -> LHsType name nlHsTyVar :: name -> LHsType name nlHsFunTy :: LHsType name -> LHsType name -> LHsType name nlHsTyConApp :: name -> [LHsType name] -> LHsType name mkTransformStmt :: [LStmt idL] -> LHsExpr idR -> StmtLR idL idR mkTransformByStmt :: [LStmt idL] -> LHsExpr idR -> LHsExpr idR -> StmtLR idL idR mkExprStmt :: LHsExpr idR -> StmtLR idL idR mkBindStmt :: LPat idL -> LHsExpr idR -> StmtLR idL idR mkGroupUsingStmt :: [LStmt idL] -> LHsExpr idR -> StmtLR idL idR mkGroupByStmt :: [LStmt idL] -> LHsExpr idR -> StmtLR idL idR mkGroupByUsingStmt :: [LStmt idL] -> LHsExpr idR -> LHsExpr idR -> StmtLR idL idR emptyRecStmt :: StmtLR idL idR mkRecStmt :: [LStmtLR idL idR] -> StmtLR idL idR unqualSplice :: RdrName mkHsSpliceTy :: LHsExpr RdrName -> HsType RdrName mkHsSplice :: LHsExpr RdrName -> HsSplice RdrName mkHsQuasiQuote :: RdrName -> SrcSpan -> FastString -> HsQuasiQuote RdrName unqualQuasiQuote :: RdrName noRebindableInfo :: Bool collectLocalBinders :: HsLocalBindsLR idL idR -> [idL] collectHsValBinders :: HsValBindsLR idL idR -> [idL] collectHsBindListBinders :: [LHsBindLR idL idR] -> [idL] collectHsBindsBinders :: LHsBindsLR idL idR -> [idL] collectHsBindBinders :: HsBindLR idL idR -> [idL] collectMethodBinders :: LHsBindsLR RdrName idR -> [Located RdrName] collectPatBinders :: LPat a -> [a] collectPatsBinders :: [LPat a] -> [a] collectLStmtsBinders :: [LStmtLR idL idR] -> [idL] collectStmtsBinders :: [StmtLR idL idR] -> [idL] collectLStmtBinders :: LStmtLR idL idR -> [idL] collectStmtBinders :: StmtLR idL idR -> [idL] collectSigTysFromPats :: [InPat name] -> [LHsType name] collectSigTysFromPat :: InPat name -> [LHsType name] -- | Returns all the binding names of the decl, along with their -- SrcLocs. The first one is guaranteed to be the name of the decl. For -- record fields mentioned in multiple constructors, the SrcLoc will be -- from the first occurence. We use the equality to filter out duplicate -- field names hsTyClDeclBinders :: Eq name => Located (TyClDecl name) -> [Located name] hsTyClDeclsBinders :: [[LTyClDecl Name]] -> [Located (InstDecl Name)] -> [Name] hsForeignDeclsBinders :: [LForeignDecl Name] -> [Name] hsGroupBinders :: HsGroup Name -> [Name] module IfaceType type IfExtName = Name type IfLclName = FastString data IfaceType IfaceTyVar :: IfLclName -> IfaceType IfaceAppTy :: IfaceType -> IfaceType -> IfaceType IfaceForAllTy :: IfaceTvBndr -> IfaceType -> IfaceType IfacePredTy :: IfacePredType -> IfaceType IfaceTyConApp :: IfaceTyCon -> [IfaceType] -> IfaceType IfaceFunTy :: IfaceType -> IfaceType -> IfaceType type IfaceKind = IfaceType data IfacePredType IfaceClassP :: IfExtName -> [IfaceType] -> IfacePredType IfaceIParam :: (IPName OccName) -> IfaceType -> IfacePredType IfaceEqPred :: IfaceType -> IfaceType -> IfacePredType data IfaceTyCon IfaceTc :: IfExtName -> IfaceTyCon IfaceIntTc :: IfaceTyCon IfaceBoolTc :: IfaceTyCon IfaceCharTc :: IfaceTyCon IfaceListTc :: IfaceTyCon IfacePArrTc :: IfaceTyCon IfaceTupTc :: Boxity -> Arity -> IfaceTyCon IfaceAnyTc :: IfaceKind -> IfaceTyCon IfaceLiftedTypeKindTc :: IfaceTyCon IfaceOpenTypeKindTc :: IfaceTyCon IfaceUnliftedTypeKindTc :: IfaceTyCon IfaceUbxTupleKindTc :: IfaceTyCon IfaceArgTypeKindTc :: IfaceTyCon type IfaceContext = [IfacePredType] data IfaceBndr IfaceIdBndr :: {-# UNPACK #-} !IfaceIdBndr -> IfaceBndr IfaceTvBndr :: {-# UNPACK #-} !IfaceTvBndr -> IfaceBndr type IfaceTvBndr = (IfLclName, IfaceKind) type IfaceIdBndr = (IfLclName, IfaceType) type IfaceCoercion = IfaceType ifaceTyConName :: IfaceTyCon -> IfExtName toIfaceType :: Type -> IfaceType toIfacePred :: PredType -> IfacePredType toIfaceContext :: ThetaType -> IfaceContext toIfaceBndr :: Var -> IfaceBndr toIfaceIdBndr :: Id -> (IfLclName, IfaceType) toIfaceTvBndrs :: [TyVar] -> [(IfLclName, IfaceType)] toIfaceTyCon :: TyCon -> IfaceTyCon toIfaceTyCon_name :: Name -> IfaceTyCon pprIfaceType :: IfaceType -> SDoc pprParendIfaceType :: IfaceType -> SDoc pprIfaceContext :: IfaceContext -> SDoc pprIfaceIdBndr :: (IfLclName, IfaceType) -> SDoc pprIfaceTvBndr :: IfaceTvBndr -> SDoc pprIfaceTvBndrs :: [IfaceTvBndr] -> SDoc pprIfaceBndrs :: [IfaceBndr] -> SDoc tOP_PREC :: Int tYCON_PREC :: Int noParens :: SDoc -> SDoc maybeParen :: Int -> Int -> SDoc -> SDoc pprIfaceForAllPart :: [IfaceTvBndr] -> IfaceContext -> SDoc -> SDoc instance Outputable IfaceTyCon instance Outputable IfacePredType instance Outputable IfaceType instance Outputable IfaceBndr module IfaceSyn data IfaceDecl IfaceId :: OccName -> IfaceType -> IfaceIdDetails -> IfaceIdInfo -> IfaceDecl ifName :: IfaceDecl -> OccName ifType :: IfaceDecl -> IfaceType ifIdDetails :: IfaceDecl -> IfaceIdDetails ifIdInfo :: IfaceDecl -> IfaceIdInfo IfaceData :: OccName -> [IfaceTvBndr] -> IfaceContext -> IfaceConDecls -> RecFlag -> Bool -> Bool -> Maybe (IfaceTyCon, [IfaceType]) -> IfaceDecl ifName :: IfaceDecl -> OccName ifTyVars :: IfaceDecl -> [IfaceTvBndr] ifCtxt :: IfaceDecl -> IfaceContext ifCons :: IfaceDecl -> IfaceConDecls ifRec :: IfaceDecl -> RecFlag ifGadtSyntax :: IfaceDecl -> Bool ifGeneric :: IfaceDecl -> Bool ifFamInst :: IfaceDecl -> Maybe (IfaceTyCon, [IfaceType]) IfaceSyn :: OccName -> [IfaceTvBndr] -> IfaceKind -> Maybe IfaceType -> Maybe (IfaceTyCon, [IfaceType]) -> IfaceDecl ifName :: IfaceDecl -> OccName ifTyVars :: IfaceDecl -> [IfaceTvBndr] ifSynKind :: IfaceDecl -> IfaceKind ifSynRhs :: IfaceDecl -> Maybe IfaceType ifFamInst :: IfaceDecl -> Maybe (IfaceTyCon, [IfaceType]) IfaceClass :: IfaceContext -> OccName -> [IfaceTvBndr] -> [FunDep FastString] -> [IfaceDecl] -> [IfaceClassOp] -> RecFlag -> IfaceDecl ifCtxt :: IfaceDecl -> IfaceContext ifName :: IfaceDecl -> OccName ifTyVars :: IfaceDecl -> [IfaceTvBndr] ifFDs :: IfaceDecl -> [FunDep FastString] ifATs :: IfaceDecl -> [IfaceDecl] ifSigs :: IfaceDecl -> [IfaceClassOp] ifRec :: IfaceDecl -> RecFlag IfaceForeign :: OccName -> Maybe FastString -> IfaceDecl ifName :: IfaceDecl -> OccName ifExtName :: IfaceDecl -> Maybe FastString data IfaceClassOp IfaceClassOp :: OccName -> DefMethSpec -> IfaceType -> IfaceClassOp data IfaceConDecl IfCon :: OccName -> Bool -> Bool -> [IfaceTvBndr] -> [IfaceTvBndr] -> [(OccName, IfaceType)] -> IfaceContext -> [IfaceType] -> [OccName] -> [HsBang] -> IfaceConDecl ifConOcc :: IfaceConDecl -> OccName ifConWrapper :: IfaceConDecl -> Bool ifConInfix :: IfaceConDecl -> Bool ifConUnivTvs :: IfaceConDecl -> [IfaceTvBndr] ifConExTvs :: IfaceConDecl -> [IfaceTvBndr] ifConEqSpec :: IfaceConDecl -> [(OccName, IfaceType)] ifConCtxt :: IfaceConDecl -> IfaceContext ifConArgTys :: IfaceConDecl -> [IfaceType] ifConFields :: IfaceConDecl -> [OccName] ifConStricts :: IfaceConDecl -> [HsBang] data IfaceConDecls IfAbstractTyCon :: IfaceConDecls IfOpenDataTyCon :: IfaceConDecls IfDataTyCon :: [IfaceConDecl] -> IfaceConDecls IfNewTyCon :: IfaceConDecl -> IfaceConDecls data IfaceExpr IfaceLcl :: IfLclName -> IfaceExpr IfaceExt :: IfExtName -> IfaceExpr IfaceType :: IfaceType -> IfaceExpr IfaceTuple :: Boxity -> [IfaceExpr] -> IfaceExpr IfaceLam :: IfaceBndr -> IfaceExpr -> IfaceExpr IfaceApp :: IfaceExpr -> IfaceExpr -> IfaceExpr IfaceCase :: IfaceExpr -> IfLclName -> IfaceType -> [IfaceAlt] -> IfaceExpr IfaceLet :: IfaceBinding -> IfaceExpr -> IfaceExpr IfaceNote :: IfaceNote -> IfaceExpr -> IfaceExpr IfaceCast :: IfaceExpr -> IfaceCoercion -> IfaceExpr IfaceLit :: Literal -> IfaceExpr IfaceFCall :: ForeignCall -> IfaceType -> IfaceExpr IfaceTick :: Module -> Int -> IfaceExpr type IfaceAlt = (IfaceConAlt, [IfLclName], IfaceExpr) data IfaceNote IfaceSCC :: CostCentre -> IfaceNote IfaceCoreNote :: String -> IfaceNote data IfaceLetBndr IfLetBndr :: IfLclName -> IfaceType -> IfaceIdInfo -> IfaceLetBndr data IfaceBinding IfaceNonRec :: IfaceLetBndr -> IfaceExpr -> IfaceBinding IfaceRec :: [(IfaceLetBndr, IfaceExpr)] -> IfaceBinding data IfaceConAlt IfaceDefault :: IfaceConAlt IfaceDataAlt :: IfExtName -> IfaceConAlt IfaceTupleAlt :: Boxity -> IfaceConAlt IfaceLitAlt :: Literal -> IfaceConAlt data IfaceIdInfo NoInfo :: IfaceIdInfo HasInfo :: [IfaceInfoItem] -> IfaceIdInfo data IfaceIdDetails IfVanillaId :: IfaceIdDetails IfRecSelId :: IfaceTyCon -> Bool -> IfaceIdDetails IfDFunId :: Int -> IfaceIdDetails data IfaceUnfolding IfCoreUnfold :: Bool -> IfaceExpr -> IfaceUnfolding IfCompulsory :: IfaceExpr -> IfaceUnfolding IfInlineRule :: Arity -> Bool -> Bool -> IfaceExpr -> IfaceUnfolding IfExtWrapper :: Arity -> IfExtName -> IfaceUnfolding IfLclWrapper :: Arity -> IfLclName -> IfaceUnfolding IfDFunUnfold :: [DFunArg IfaceExpr] -> IfaceUnfolding data IfaceInfoItem HsArity :: Arity -> IfaceInfoItem HsStrictness :: StrictSig -> IfaceInfoItem HsInline :: InlinePragma -> IfaceInfoItem HsUnfold :: Bool -> IfaceUnfolding -> IfaceInfoItem HsNoCafRefs :: IfaceInfoItem data IfaceRule IfaceRule :: RuleName -> Activation -> [IfaceBndr] -> IfExtName -> [IfaceExpr] -> IfaceExpr -> Bool -> Maybe OccName -> IfaceRule ifRuleName :: IfaceRule -> RuleName ifActivation :: IfaceRule -> Activation ifRuleBndrs :: IfaceRule -> [IfaceBndr] ifRuleHead :: IfaceRule -> IfExtName ifRuleArgs :: IfaceRule -> [IfaceExpr] ifRuleRhs :: IfaceRule -> IfaceExpr ifRuleAuto :: IfaceRule -> Bool ifRuleOrph :: IfaceRule -> Maybe OccName data IfaceAnnotation IfaceAnnotation :: IfaceAnnTarget -> Serialized -> IfaceAnnotation ifAnnotatedTarget :: IfaceAnnotation -> IfaceAnnTarget ifAnnotatedValue :: IfaceAnnotation -> Serialized type IfaceAnnTarget = AnnTarget OccName data IfaceInst IfaceInst :: IfExtName -> [Maybe IfaceTyCon] -> IfExtName -> OverlapFlag -> Maybe OccName -> IfaceInst ifInstCls :: IfaceInst -> IfExtName ifInstTys :: IfaceInst -> [Maybe IfaceTyCon] ifDFun :: IfaceInst -> IfExtName ifOFlag :: IfaceInst -> OverlapFlag ifInstOrph :: IfaceInst -> Maybe OccName data IfaceFamInst IfaceFamInst :: IfExtName -> [Maybe IfaceTyCon] -> IfaceTyCon -> IfaceFamInst ifFamInstFam :: IfaceFamInst -> IfExtName ifFamInstTys :: IfaceFamInst -> [Maybe IfaceTyCon] ifFamInstTyCon :: IfaceFamInst -> IfaceTyCon ifaceDeclSubBndrs :: IfaceDecl -> [OccName] visibleIfConDecls :: IfaceConDecls -> [IfaceConDecl] freeNamesIfDecl :: IfaceDecl -> NameSet freeNamesIfRule :: IfaceRule -> NameSet pprIfaceExpr :: (SDoc -> SDoc) -> IfaceExpr -> SDoc pprIfaceDeclHead :: IfaceContext -> OccName -> [IfaceTvBndr] -> SDoc instance Outputable IfaceUnfolding instance Outputable IfaceInfoItem instance Outputable IfaceIdInfo instance Outputable IfaceIdDetails instance Outputable IfaceConAlt instance Outputable IfaceNote instance Outputable IfaceExpr instance Outputable IfaceFamInst instance Outputable IfaceInst instance Outputable IfaceRule instance Outputable IfaceClassOp instance Outputable IfaceDecl module HsSyn data Fixity -- | All we actually declare here is the top-level structure for a module. data HsModule name HsModule :: Maybe (Located ModuleName) -> Maybe [LIE name] -> [LImportDecl name] -> [LHsDecl name] -> Maybe WarningTxt -> Maybe LHsDocString -> HsModule name -- | Nothing: "module X where" is omitted (in which case the next -- field is Nothing too) hsmodName :: HsModule name -> Maybe (Located ModuleName) -- | Export list -- -- hsmodExports :: HsModule name -> Maybe [LIE name] -- | We snaffle interesting stuff out of the imported interfaces early on, -- adding that info to TyDecls/etc; so this list is often empty, -- downstream. hsmodImports :: HsModule name -> [LImportDecl name] -- | Type, class, value, and interface signature decls hsmodDecls :: HsModule name -> [LHsDecl name] -- | reason/explanation for warning/deprecation of this module hsmodDeprecMessage :: HsModule name -> Maybe WarningTxt -- | Haddock module info and description, unparsed hsmodHaddockModHeader :: HsModule name -> Maybe LHsDocString data HsExtCore name HsExtCore :: Module -> [TyClDecl name] -> [IfaceBinding] -> HsExtCore name instance Typeable1 HsModule instance Data name => Data (HsModule name) instance OutputableBndr name => Outputable (HsModule name) instance Outputable Char module HscStats ppSourceStats :: Bool -> Located (HsModule RdrName) -> SDoc module HaddockUtils addFieldDoc :: ConDeclField a -> Maybe LHsDocString -> ConDeclField a addFieldDocs :: [ConDeclField a] -> Maybe LHsDocString -> [ConDeclField a] addConDoc :: LConDecl a -> Maybe LHsDocString -> LConDecl a addConDocs :: [LConDecl a] -> Maybe LHsDocString -> [LConDecl a] addConDocFirst :: [LConDecl a] -> Maybe LHsDocString -> [LConDecl a] module RnHsSyn charTyCon_name :: Name listTyCon_name :: Name parrTyCon_name :: Name tupleTyCon_name :: Boxity -> Int -> Name extractHsTyVars :: LHsType Name -> NameSet extractHsTyNames :: LHsType Name -> NameSet extractHsTyNames_s :: [LHsType Name] -> NameSet extractFunDepNames :: FunDep Name -> NameSet extractHsCtxtTyNames :: LHsContext Name -> NameSet extractHsPredTyNames :: HsPred Name -> NameSet hsSigsFVs :: [LSig Name] -> FreeVars hsSigFVs :: Sig Name -> FreeVars conDeclFVs :: LConDecl Name -> FreeVars bangTyFVs :: LHsType Name -> FreeVars maybeGenericMatch :: LMatch Name -> Maybe (HsType Name, LMatch Name) -- | A description of the platform we're compiling for. Used by the native -- code generator. In the future, this module should be the only one that -- references the evil #defines for each TARGET_ARCH and TARGET_OS module Platform -- | Contains enough information for the native code generator to emit code -- for this platform. data Platform Platform :: Arch -> OS -> Platform platformArch :: Platform -> Arch platformOS :: Platform -> OS -- | Architectures that the native code generator knows about. TODO: It -- might be nice to extend these constructors with information about what -- instruction set extensions an architecture might support. data Arch ArchAlpha :: Arch ArchX86 :: Arch ArchX86_64 :: Arch ArchPPC :: Arch ArchPPC_64 :: Arch ArchSPARC :: Arch -- | Operating systems that the native code generator knows about. Having -- OSUnknown should produce a sensible default, but no promises. data OS OSUnknown :: OS OSLinux :: OS OSDarwin :: OS OSSolaris2 :: OS OSMinGW32 :: OS OSFreeBSD :: OS OSOpenBSD :: OS -- | This is the target platform as far as the #ifdefs are concerned. These -- are set in includes/ghcplatform.h by the autoconf scripts defaultTargetPlatform :: Platform -- | This predicates tells us whether the OS supports ELF-like shared -- libraries. osElfTarget :: OS -> Bool instance Show Arch instance Eq Arch instance Show OS instance Eq OS -- | Dynamic flags -- -- (c) The University of Glasgow 2005 module DynFlags -- | Enumerates the simple on-or-off dynamic flags data DynFlag Opt_D_dump_cmm :: DynFlag Opt_D_dump_cmmz :: DynFlag Opt_D_dump_cmmz_pretty :: DynFlag Opt_D_dump_cps_cmm :: DynFlag Opt_D_dump_cvt_cmm :: DynFlag Opt_D_dump_asm :: DynFlag Opt_D_dump_asm_native :: DynFlag Opt_D_dump_asm_liveness :: DynFlag Opt_D_dump_asm_coalesce :: DynFlag Opt_D_dump_asm_regalloc :: DynFlag Opt_D_dump_asm_regalloc_stages :: DynFlag Opt_D_dump_asm_conflicts :: DynFlag Opt_D_dump_asm_stats :: DynFlag Opt_D_dump_asm_expanded :: DynFlag Opt_D_dump_llvm :: DynFlag Opt_D_dump_cpranal :: DynFlag Opt_D_dump_deriv :: DynFlag Opt_D_dump_ds :: DynFlag Opt_D_dump_flatC :: DynFlag Opt_D_dump_foreign :: DynFlag Opt_D_dump_inlinings :: DynFlag Opt_D_dump_rule_firings :: DynFlag Opt_D_dump_occur_anal :: DynFlag Opt_D_dump_parsed :: DynFlag Opt_D_dump_rn :: DynFlag Opt_D_dump_simpl :: DynFlag Opt_D_dump_simpl_iterations :: DynFlag Opt_D_dump_simpl_phases :: DynFlag Opt_D_dump_spec :: DynFlag Opt_D_dump_prep :: DynFlag Opt_D_dump_stg :: DynFlag Opt_D_dump_stranal :: DynFlag Opt_D_dump_tc :: DynFlag Opt_D_dump_types :: DynFlag Opt_D_dump_rules :: DynFlag Opt_D_dump_cse :: DynFlag Opt_D_dump_worker_wrapper :: DynFlag Opt_D_dump_rn_trace :: DynFlag Opt_D_dump_rn_stats :: DynFlag Opt_D_dump_opt_cmm :: DynFlag Opt_D_dump_simpl_stats :: DynFlag Opt_D_dump_cs_trace :: DynFlag Opt_D_dump_tc_trace :: DynFlag Opt_D_dump_if_trace :: DynFlag Opt_D_dump_splices :: DynFlag Opt_D_dump_BCOs :: DynFlag Opt_D_dump_vect :: DynFlag Opt_D_dump_hpc :: DynFlag Opt_D_dump_rtti :: DynFlag Opt_D_source_stats :: DynFlag Opt_D_verbose_core2core :: DynFlag Opt_D_verbose_stg2stg :: DynFlag Opt_D_dump_hi :: DynFlag Opt_D_dump_hi_diffs :: DynFlag Opt_D_dump_minimal_imports :: DynFlag Opt_D_dump_mod_cycles :: DynFlag Opt_D_dump_view_pattern_commoning :: DynFlag Opt_D_faststring_stats :: DynFlag -- | Append dump output to files instead of stdout. Opt_DumpToFile :: DynFlag Opt_D_no_debug_output :: DynFlag Opt_DoCoreLinting :: DynFlag Opt_DoStgLinting :: DynFlag Opt_DoCmmLinting :: DynFlag Opt_DoAsmLinting :: DynFlag Opt_WarnIsError :: DynFlag Opt_WarnDuplicateExports :: DynFlag Opt_WarnHiShadows :: DynFlag Opt_WarnImplicitPrelude :: DynFlag Opt_WarnIncompletePatterns :: DynFlag Opt_WarnIncompletePatternsRecUpd :: DynFlag Opt_WarnMissingFields :: DynFlag Opt_WarnMissingImportList :: DynFlag Opt_WarnMissingMethods :: DynFlag Opt_WarnMissingSigs :: DynFlag Opt_WarnMissingLocalSigs :: DynFlag Opt_WarnNameShadowing :: DynFlag Opt_WarnOverlappingPatterns :: DynFlag Opt_WarnTypeDefaults :: DynFlag Opt_WarnMonomorphism :: DynFlag Opt_WarnUnusedBinds :: DynFlag Opt_WarnUnusedImports :: DynFlag Opt_WarnUnusedMatches :: DynFlag Opt_WarnWarningsDeprecations :: DynFlag Opt_WarnDeprecatedFlags :: DynFlag Opt_WarnDodgyExports :: DynFlag Opt_WarnDodgyImports :: DynFlag Opt_WarnOrphans :: DynFlag Opt_WarnAutoOrphans :: DynFlag Opt_WarnTabs :: DynFlag Opt_WarnUnrecognisedPragmas :: DynFlag Opt_WarnDodgyForeignImports :: DynFlag Opt_WarnLazyUnliftedBindings :: DynFlag Opt_WarnUnusedDoBind :: DynFlag Opt_WarnWrongDoBind :: DynFlag Opt_WarnAlternativeLayoutRuleTransitional :: DynFlag Opt_PrintExplicitForalls :: DynFlag Opt_Strictness :: DynFlag Opt_FullLaziness :: DynFlag Opt_FloatIn :: DynFlag Opt_Specialise :: DynFlag Opt_StaticArgumentTransformation :: DynFlag Opt_CSE :: DynFlag Opt_LiberateCase :: DynFlag Opt_SpecConstr :: DynFlag Opt_DoLambdaEtaExpansion :: DynFlag Opt_IgnoreAsserts :: DynFlag Opt_DoEtaReduction :: DynFlag Opt_CaseMerge :: DynFlag Opt_UnboxStrictFields :: DynFlag Opt_MethodSharing :: DynFlag Opt_DictsCheap :: DynFlag Opt_EnableRewriteRules :: DynFlag Opt_Vectorise :: DynFlag Opt_RegsGraph :: DynFlag Opt_RegsIterative :: DynFlag Opt_IgnoreInterfacePragmas :: DynFlag Opt_OmitInterfacePragmas :: DynFlag Opt_ExposeAllUnfoldings :: DynFlag Opt_AutoSccsOnAllToplevs :: DynFlag Opt_AutoSccsOnExportedToplevs :: DynFlag Opt_AutoSccsOnIndividualCafs :: DynFlag Opt_Pp :: DynFlag Opt_ForceRecomp :: DynFlag Opt_DryRun :: DynFlag Opt_DoAsmMangling :: DynFlag Opt_ExcessPrecision :: DynFlag Opt_EagerBlackHoling :: DynFlag Opt_ReadUserPackageConf :: DynFlag Opt_NoHsMain :: DynFlag Opt_SplitObjs :: DynFlag Opt_StgStats :: DynFlag Opt_HideAllPackages :: DynFlag Opt_PrintBindResult :: DynFlag Opt_Haddock :: DynFlag Opt_HaddockOptions :: DynFlag Opt_Hpc_No_Auto :: DynFlag Opt_BreakOnException :: DynFlag Opt_BreakOnError :: DynFlag Opt_PrintEvldWithShow :: DynFlag Opt_PrintBindContents :: DynFlag Opt_GenManifest :: DynFlag Opt_EmbedManifest :: DynFlag Opt_EmitExternalCore :: DynFlag Opt_SharedImplib :: DynFlag Opt_BuildingCabalPackage :: DynFlag Opt_SSE2 :: DynFlag Opt_GhciSandbox :: DynFlag Opt_RunCPS :: DynFlag Opt_RunCPSZ :: DynFlag Opt_ConvertToZipCfgAndBack :: DynFlag Opt_AutoLinkPackages :: DynFlag Opt_ImplicitImportQualified :: DynFlag Opt_TryNewCodeGen :: DynFlag Opt_KeepHiDiffs :: DynFlag Opt_KeepHcFiles :: DynFlag Opt_KeepSFiles :: DynFlag Opt_KeepRawSFiles :: DynFlag Opt_KeepTmpFiles :: DynFlag Opt_KeepRawTokenStream :: DynFlag Opt_KeepLlvmFiles :: DynFlag data ExtensionFlag Opt_Cpp :: ExtensionFlag Opt_OverlappingInstances :: ExtensionFlag Opt_UndecidableInstances :: ExtensionFlag Opt_IncoherentInstances :: ExtensionFlag Opt_MonomorphismRestriction :: ExtensionFlag Opt_MonoPatBinds :: ExtensionFlag Opt_MonoLocalBinds :: ExtensionFlag Opt_RelaxedPolyRec :: ExtensionFlag Opt_ExtendedDefaultRules :: ExtensionFlag Opt_ForeignFunctionInterface :: ExtensionFlag Opt_UnliftedFFITypes :: ExtensionFlag Opt_GHCForeignImportPrim :: ExtensionFlag Opt_PArr :: ExtensionFlag Opt_Arrows :: ExtensionFlag Opt_TemplateHaskell :: ExtensionFlag Opt_QuasiQuotes :: ExtensionFlag Opt_ImplicitParams :: ExtensionFlag Opt_Generics :: ExtensionFlag Opt_ImplicitPrelude :: ExtensionFlag Opt_ScopedTypeVariables :: ExtensionFlag Opt_UnboxedTuples :: ExtensionFlag Opt_BangPatterns :: ExtensionFlag Opt_TypeFamilies :: ExtensionFlag Opt_OverloadedStrings :: ExtensionFlag Opt_DisambiguateRecordFields :: ExtensionFlag Opt_RecordWildCards :: ExtensionFlag Opt_RecordPuns :: ExtensionFlag Opt_ViewPatterns :: ExtensionFlag Opt_GADTs :: ExtensionFlag Opt_NPlusKPatterns :: ExtensionFlag Opt_DoAndIfThenElse :: ExtensionFlag Opt_RebindableSyntax :: ExtensionFlag Opt_StandaloneDeriving :: ExtensionFlag Opt_DeriveDataTypeable :: ExtensionFlag Opt_DeriveFunctor :: ExtensionFlag Opt_DeriveTraversable :: ExtensionFlag Opt_DeriveFoldable :: ExtensionFlag Opt_TypeSynonymInstances :: ExtensionFlag Opt_FlexibleContexts :: ExtensionFlag Opt_FlexibleInstances :: ExtensionFlag Opt_ConstrainedClassMethods :: ExtensionFlag Opt_MultiParamTypeClasses :: ExtensionFlag Opt_FunctionalDependencies :: ExtensionFlag Opt_UnicodeSyntax :: ExtensionFlag Opt_PolymorphicComponents :: ExtensionFlag Opt_ExistentialQuantification :: ExtensionFlag Opt_MagicHash :: ExtensionFlag Opt_EmptyDataDecls :: ExtensionFlag Opt_KindSignatures :: ExtensionFlag Opt_ParallelListComp :: ExtensionFlag Opt_TransformListComp :: ExtensionFlag Opt_GeneralizedNewtypeDeriving :: ExtensionFlag Opt_RecursiveDo :: ExtensionFlag Opt_DoRec :: ExtensionFlag Opt_PostfixOperators :: ExtensionFlag Opt_TupleSections :: ExtensionFlag Opt_PatternGuards :: ExtensionFlag Opt_LiberalTypeSynonyms :: ExtensionFlag Opt_Rank2Types :: ExtensionFlag Opt_RankNTypes :: ExtensionFlag Opt_ImpredicativeTypes :: ExtensionFlag Opt_TypeOperators :: ExtensionFlag Opt_PackageImports :: ExtensionFlag Opt_NewQualifiedOperators :: ExtensionFlag Opt_ExplicitForAll :: ExtensionFlag Opt_AlternativeLayoutRule :: ExtensionFlag Opt_AlternativeLayoutRuleTransitional :: ExtensionFlag Opt_DatatypeContexts :: ExtensionFlag glasgowExtsFlags :: [ExtensionFlag] -- | Test whether a DynFlag is set dopt :: DynFlag -> DynFlags -> Bool -- | Set a DynFlag dopt_set :: DynFlags -> DynFlag -> DynFlags -- | Unset a DynFlag dopt_unset :: DynFlags -> DynFlag -> DynFlags -- | Test whether a ExtensionFlag is set xopt :: ExtensionFlag -> DynFlags -> Bool -- | Set a ExtensionFlag xopt_set :: DynFlags -> ExtensionFlag -> DynFlags -- | Unset a ExtensionFlag xopt_unset :: DynFlags -> ExtensionFlag -> DynFlags -- | Contains not only a collection of DynFlags but also a plethora -- of information relating to the compilation of a single file or GHC -- session data DynFlags DynFlags :: GhcMode -> GhcLink -> HscTarget -> String -> String -> Int -> Int -> Int -> Int -> Maybe String -> Maybe String -> [Int] -> Maybe Int -> Maybe Int -> Maybe Int -> Maybe Int -> Platform -> Int -> [String] -> [FilePath] -> Module -> Maybe String -> Int -> DPHBackend -> PackageId -> [Way] -> String -> String -> Maybe (String, Int) -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> String -> String -> String -> Maybe String -> Maybe String -> DynLibLoader -> Maybe FilePath -> Maybe FilePath -> [String] -> [String] -> [String] -> [String] -> String -> FilePath -> FilePath -> Maybe String -> RtsOptsEnabled -> String -> [String] -> [String] -> [String] -> [String] -> [String] -> [String] -> [String] -> [String] -> [String] -> [String] -> String -> (String, [Option]) -> String -> (String, [Option]) -> (String, [Option]) -> (String, [Option]) -> (String, [Option]) -> (String, [Option]) -> (String, [Option]) -> String -> String -> String -> (String, [Option]) -> (String, [Option]) -> FilePath -> Bool -> [ModuleName] -> [String] -> [FilePath] -> FilePath -> FilePath -> [PackageFlag] -> Maybe [PackageConfig] -> PackageState -> IORef [FilePath] -> IORef (Map FilePath FilePath) -> [DynFlag] -> Maybe Language -> [OnOff ExtensionFlag] -> [ExtensionFlag] -> (Severity -> SrcSpan -> PprStyle -> Message -> IO ()) -> Maybe String -> DynFlags ghcMode :: DynFlags -> GhcMode ghcLink :: DynFlags -> GhcLink hscTarget :: DynFlags -> HscTarget -- | Name of the output file hscOutName :: DynFlags -> String -- | Name of the .hcr output file extCoreName :: DynFlags -> String -- | Verbosity level: see Note [Verbosity levels] verbosity :: DynFlags -> Int -- | Optimisation level optLevel :: DynFlags -> Int -- | Number of simplifier phases simplPhases :: DynFlags -> Int -- | Max simplifier iterations maxSimplIterations :: DynFlags -> Int shouldDumpSimplPhase :: DynFlags -> Maybe String ruleCheck :: DynFlags -> Maybe String -- | Additional demand analysis strictnessBefore :: DynFlags -> [Int] -- | Threshold for SpecConstr specConstrThreshold :: DynFlags -> Maybe Int -- | Max number of specialisations for any one function specConstrCount :: DynFlags -> Maybe Int -- | Threshold for LiberateCase liberateCaseThreshold :: DynFlags -> Maybe Int -- | Arg count for lambda floating See CoreMonad.FloatOutSwitches floatLamArgs :: DynFlags -> Maybe Int -- | The platform we're compiling for. Used by the NCG. targetPlatform :: DynFlags -> Platform stolen_x86_regs :: DynFlags -> Int -- |
--   -#includes
--   
cmdlineHcIncludes :: DynFlags -> [String] importPaths :: DynFlags -> [FilePath] mainModIs :: DynFlags -> Module mainFunIs :: DynFlags -> Maybe String -- | Typechecker context stack depth ctxtStkDepth :: DynFlags -> Int dphBackend :: DynFlags -> DPHBackend -- | name of package currently being compiled thisPackage :: DynFlags -> PackageId -- | Way flags from the command line ways :: DynFlags -> [Way] -- | The global "way" (e.g. "p" for prof) buildTag :: DynFlags -> String -- | The RTS "way" rtsBuildTag :: DynFlags -> String splitInfo :: DynFlags -> Maybe (String, Int) objectDir :: DynFlags -> Maybe String dylibInstallName :: DynFlags -> Maybe String hiDir :: DynFlags -> Maybe String stubDir :: DynFlags -> Maybe String objectSuf :: DynFlags -> String hcSuf :: DynFlags -> String hiSuf :: DynFlags -> String outputFile :: DynFlags -> Maybe String outputHi :: DynFlags -> Maybe String dynLibLoader :: DynFlags -> DynLibLoader -- | This is set by DriverPipeline.runPipeline based on where its -- output is going. dumpPrefix :: DynFlags -> Maybe FilePath -- | Override the dumpPrefix set by -- DriverPipeline.runPipeline. Set by -- -ddump-file-prefix dumpPrefixForce :: DynFlags -> Maybe FilePath includePaths :: DynFlags -> [String] libraryPaths :: DynFlags -> [String] frameworkPaths :: DynFlags -> [String] cmdlineFrameworks :: DynFlags -> [String] tmpDir :: DynFlags -> String ghcUsagePath :: DynFlags -> FilePath ghciUsagePath :: DynFlags -> FilePath rtsOpts :: DynFlags -> Maybe String rtsOptsEnabled :: DynFlags -> RtsOptsEnabled -- | Path to store the .mix files hpcDir :: DynFlags -> String opt_L :: DynFlags -> [String] opt_P :: DynFlags -> [String] opt_F :: DynFlags -> [String] opt_c :: DynFlags -> [String] opt_m :: DynFlags -> [String] opt_a :: DynFlags -> [String] opt_l :: DynFlags -> [String] opt_windres :: DynFlags -> [String] opt_lo :: DynFlags -> [String] opt_lc :: DynFlags -> [String] pgm_L :: DynFlags -> String pgm_P :: DynFlags -> (String, [Option]) pgm_F :: DynFlags -> String pgm_c :: DynFlags -> (String, [Option]) pgm_m :: DynFlags -> (String, [Option]) pgm_s :: DynFlags -> (String, [Option]) pgm_a :: DynFlags -> (String, [Option]) pgm_l :: DynFlags -> (String, [Option]) pgm_dll :: DynFlags -> (String, [Option]) pgm_T :: DynFlags -> String pgm_sysman :: DynFlags -> String pgm_windres :: DynFlags -> String pgm_lo :: DynFlags -> (String, [Option]) pgm_lc :: DynFlags -> (String, [Option]) depMakefile :: DynFlags -> FilePath depIncludePkgDeps :: DynFlags -> Bool depExcludeMods :: DynFlags -> [ModuleName] depSuffixes :: DynFlags -> [String] extraPkgConfs :: DynFlags -> [FilePath] topDir :: DynFlags -> FilePath -- | The -package-conf flags given on the command line, in the -- order they appeared. systemPackageConfig :: DynFlags -> FilePath -- | The -package and -hide-package flags from the -- command-line packageFlags :: DynFlags -> [PackageFlag] pkgDatabase :: DynFlags -> Maybe [PackageConfig] pkgState :: DynFlags -> PackageState filesToClean :: DynFlags -> IORef [FilePath] dirsToClean :: DynFlags -> IORef (Map FilePath FilePath) flags :: DynFlags -> [DynFlag] language :: DynFlags -> Maybe Language extensions :: DynFlags -> [OnOff ExtensionFlag] extensionFlags :: DynFlags -> [ExtensionFlag] -- | Message output action: use ErrUtils instead of this if you can log_action :: DynFlags -> Severity -> SrcSpan -> PprStyle -> Message -> IO () haddockOptions :: DynFlags -> Maybe String data RtsOptsEnabled RtsOptsNone :: RtsOptsEnabled RtsOptsSafeOnly :: RtsOptsEnabled RtsOptsAll :: RtsOptsEnabled -- | The target code type of the compilation (if any). -- -- Whenever you change the target, also make sure to set ghcLink -- to something sensible. -- -- HscNothing can be used to avoid generating any output, however, -- note that: -- -- data HscTarget -- | Generate C code. HscC :: HscTarget -- | Generate assembly using the native code generator. HscAsm :: HscTarget -- | Generate assembly using the llvm code generator. HscLlvm :: HscTarget -- | Generate Java bytecode. HscJava :: HscTarget -- | Generate bytecode. (Requires LinkInMemory) HscInterpreted :: HscTarget -- | Don't generate any code. See notes above. HscNothing :: HscTarget -- | Will this target result in an object file on the disk? isObjectTarget :: HscTarget -> Bool -- | The HscTarget value corresponding to the default way to create -- object files on the current platform. defaultObjectTarget :: HscTarget -- | The GhcMode tells us whether we're doing multi-module -- compilation (controlled via the GHC API) or one-shot -- (single-module) compilation. This makes a difference primarily to the -- Finder: in one-shot mode we look for interface files for -- imported modules, but in multi-module mode we look for source files in -- order to check whether they need to be recompiled. data GhcMode -- | --make, GHCi, etc. CompManager :: GhcMode -- |
--   ghc -c Foo.hs
--   
OneShot :: GhcMode -- | ghc -M, see Finder for why we need this MkDepend :: GhcMode isOneShot :: GhcMode -> Bool -- | What to do in the link step, if there is one. data GhcLink -- | Don't link at all NoLink :: GhcLink -- | Link object code into a binary LinkBinary :: GhcLink -- | Use the in-memory dynamic linker (works for both bytecode and object -- code). LinkInMemory :: GhcLink -- | Link objects into a dynamic lib (DLL on Windows, DSO on ELF platforms) LinkDynLib :: GhcLink isNoLink :: GhcLink -> Bool data PackageFlag ExposePackage :: String -> PackageFlag ExposePackageId :: String -> PackageFlag HidePackage :: String -> PackageFlag IgnorePackage :: String -> PackageFlag -- | When invoking external tools as part of the compilation pipeline, we -- pass these a sequence of options on the command-line. Rather than just -- using a list of Strings, we use a type that allows us to distinguish -- between filepaths and 'other stuff'. The reason for this is that this -- type gives us a handle on transforming filenames, and filenames only, -- to whatever format they're expected to be on a particular platform. data Option FileOption :: String -> String -> Option Option :: String -> Option showOpt :: Option -> String data DynLibLoader Deployable :: DynLibLoader SystemDependent :: DynLibLoader -- | These -f<blah> flags can all be reversed with -- -fno-<blah> fFlags :: [FlagSpec DynFlag] -- | These -f<blah> flags can all be reversed with -- -fno-<blah> fLangFlags :: [FlagSpec ExtensionFlag] -- | These -Xblah flags can all be reversed with -XNoblah xFlags :: [FlagSpec ExtensionFlag] dphPackage :: DynFlags -> PackageId wayNames :: DynFlags -> [WayName] -- | The normal DynFlags. Note that they is not suitable for use in -- this form and must be fully initialized by GHC.newSession -- first. defaultDynFlags :: DynFlags -- | Used by GHC.newSession to partially initialize a new -- DynFlags value initDynFlags :: DynFlags -> IO DynFlags -- | Retrieve the options corresponding to a particular opt_* -- field in the correct order getOpts :: DynFlags -> (DynFlags -> [a]) -> [a] -- | Gets the verbosity flag for the current verbosity level. This is fed -- to other tools, so GHC-specific verbosity flags like -- -ddump-most are not included getVerbFlag :: DynFlags -> String -- | Sets the DynFlags to be appropriate to the optimisation level updOptLevel :: Int -> DynFlags -> DynFlags setTmpDir :: FilePath -> DynFlags -> DynFlags setPackageName :: String -> DynFlags -> DynFlags doingTickyProfiling :: DynFlags -> Bool -- | Parse dynamic flags from a list of command line arguments. Returns the -- the parsed DynFlags, the left-over arguments, and a list of -- warnings. Throws a UsageError if errors occurred during parsing -- (such as unknown flags or missing arguments). parseDynamicFlags :: Monad m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Located String]) -- | Like parseDynamicFlags but does not allow the package flags -- (-package, -hide-package, -ignore-package, -hide-all-packages, -- -package-conf). parseDynamicNoPackageFlags :: Monad m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Located String]) allFlags :: [String] supportedLanguagesAndExtensions :: [String] machdepCCOpts :: DynFlags -> ([String], [String]) picCCOpts :: DynFlags -> [String] data StgToDo StgDoMassageForProfiling :: StgToDo D_stg_stats :: StgToDo getStgToDo :: DynFlags -> [StgToDo] data Printable String :: String -> Printable FromDynFlags :: (DynFlags -> String) -> Printable compilerInfo :: [(String, Printable)] rtsIsProfiled :: Bool instance Eq DynFlag instance Show DynFlag instance Eq ExtensionFlag instance Show ExtensionFlag instance Eq HscTarget instance Show HscTarget instance Eq GhcMode instance Eq GhcLink instance Show GhcLink instance Eq PackageFlag instance Eq DynLibLoader instance Eq DPHBackend instance Ord DPHBackend instance Enum DPHBackend instance Show DPHBackend instance Outputable GhcMode module ErrUtils type Message = SDoc mkLocMessage :: SrcSpan -> Message -> Message printError :: SrcSpan -> Message -> IO () pprMessageBag :: Bag Message -> SDoc data Severity SevOutput :: Severity SevInfo :: Severity SevWarning :: Severity SevError :: Severity SevFatal :: Severity data ErrMsg type WarnMsg = ErrMsg type ErrorMessages = Bag ErrMsg type WarningMessages = Bag WarnMsg errMsgSpans :: ErrMsg -> [SrcSpan] errMsgContext :: ErrMsg -> PrintUnqualified errMsgShortDoc :: ErrMsg -> Message errMsgExtraInfo :: ErrMsg -> Message type Messages = (Bag WarnMsg, Bag ErrMsg) errorsFound :: DynFlags -> Messages -> Bool emptyMessages :: Messages mkErrMsg :: SrcSpan -> PrintUnqualified -> Message -> ErrMsg mkPlainErrMsg :: SrcSpan -> Message -> ErrMsg mkLongErrMsg :: SrcSpan -> PrintUnqualified -> Message -> Message -> ErrMsg mkWarnMsg :: SrcSpan -> PrintUnqualified -> Message -> WarnMsg mkPlainWarnMsg :: SrcSpan -> Message -> ErrMsg printErrorsAndWarnings :: DynFlags -> Messages -> IO () printBagOfErrors :: DynFlags -> Bag ErrMsg -> IO () printBagOfWarnings :: DynFlags -> Bag ErrMsg -> IO () warnIsErrorMsg :: ErrMsg mkLongWarnMsg :: SrcSpan -> PrintUnqualified -> Message -> Message -> ErrMsg ghcExit :: DynFlags -> Int -> IO () doIfSet :: Bool -> IO () -> IO () doIfSet_dyn :: DynFlags -> DynFlag -> IO () -> IO () dumpIfSet :: Bool -> String -> SDoc -> IO () dumpIfSet_dyn :: DynFlags -> DynFlag -> String -> SDoc -> IO () dumpIfSet_dyn_or :: DynFlags -> [DynFlag] -> String -> SDoc -> IO () mkDumpDoc :: String -> SDoc -> SDoc -- | Write out a dump. If --dump-to-file is set then this goes to a file. -- otherwise emit to stdout. dumpSDoc :: DynFlags -> DynFlag -> String -> SDoc -> IO () putMsg :: DynFlags -> Message -> IO () putMsgWith :: DynFlags -> PrintUnqualified -> Message -> IO () errorMsg :: DynFlags -> Message -> IO () fatalErrorMsg :: DynFlags -> Message -> IO () compilationProgressMsg :: DynFlags -> String -> IO () showPass :: DynFlags -> String -> IO () debugTraceMsg :: DynFlags -> Int -> Message -> IO () instance Show ErrMsg module Unify tcMatchTy :: TyVarSet -> Type -> Type -> Maybe TvSubst tcMatchTys :: TyVarSet -> [Type] -> [Type] -> Maybe TvSubst tcMatchTyX :: TyVarSet -> TvSubst -> Type -> Type -> Maybe TvSubst ruleMatchTyX :: MatchEnv -> TvSubstEnv -> Type -> Type -> Maybe TvSubstEnv tcMatchPreds :: [TyVar] -> [PredType] -> [PredType] -> Maybe TvSubstEnv data MatchEnv ME :: VarSet -> RnEnv2 -> MatchEnv me_tmpls :: MatchEnv -> VarSet me_env :: MatchEnv -> RnEnv2 dataConCannotMatch :: [Type] -> DataCon -> Bool tcUnifyTys :: (TyVar -> BindFlag) -> [Type] -> [Type] -> Maybe TvSubst data BindFlag BindMe :: BindFlag Skolem :: BindFlag niFixTvSubst :: TvSubstEnv -> TvSubst niSubstTvSet :: TvSubstEnv -> TyVarSet -> TyVarSet instance Monad UM module OptCoercion -- | optCoercion applies a substitution to a coercion, *and* optimises it -- to reduce its size optCoercion :: TvSubst -> Coercion -> NormalCo module TcType type TcType = Type type TcSigmaType = TcType type TcRhoType = TcType type TcTauType = TcType type TcPredType = PredType type TcThetaType = ThetaType type TcTyVar = TyVar type TcTyVarSet = TyVarSet type TcKind = Kind type TcCoVar = CoVar data UserTypeCtxt FunSigCtxt :: Name -> UserTypeCtxt ExprSigCtxt :: UserTypeCtxt ConArgCtxt :: Name -> UserTypeCtxt TySynCtxt :: Name -> UserTypeCtxt GenPatCtxt :: UserTypeCtxt LamPatSigCtxt :: UserTypeCtxt BindPatSigCtxt :: UserTypeCtxt ResSigCtxt :: UserTypeCtxt ForSigCtxt :: Name -> UserTypeCtxt DefaultDeclCtxt :: UserTypeCtxt SpecInstCtxt :: UserTypeCtxt ThBrackCtxt :: UserTypeCtxt GenSigCtxt :: UserTypeCtxt pprUserTypeCtxt :: UserTypeCtxt -> SDoc data TcTyVarDetails SkolemTv :: Bool -> TcTyVarDetails RuntimeUnk :: TcTyVarDetails FlatSkol :: TcType -> TcTyVarDetails MetaTv :: MetaInfo -> (IORef MetaDetails) -> TcTyVarDetails pprTcTyVarDetails :: TcTyVarDetails -> SDoc vanillaSkolemTv :: TcTyVarDetails superSkolemTv :: TcTyVarDetails data MetaDetails Flexi :: MetaDetails Indirect :: TcType -> MetaDetails data MetaInfo TauTv :: MetaInfo SigTv :: Name -> MetaInfo TcsTv :: MetaInfo isImmutableTyVar :: TyVar -> Bool isSkolemTyVar :: TcTyVar -> Bool isMetaTyVar :: TcTyVar -> Bool isMetaTyVarTy :: TcType -> Bool isSigTyVar :: Var -> Bool isOverlappableTyVar :: TcTyVar -> Bool isTyConableTyVar :: TcTyVar -> Bool metaTvRef :: TyVar -> IORef MetaDetails isFlexi :: MetaDetails -> Bool isIndirect :: MetaDetails -> Bool isRuntimeUnkSkol :: TyVar -> Bool mkPhiTy :: [PredType] -> Type -> Type mkSigmaTy :: [TyVar] -> [PredType] -> Type -> Type -- | Similar to coreView, but for the type checker, which just looks -- through synonyms tcView :: Type -> Maybe Type tcSplitForAllTys :: Type -> ([TyVar], Type) tcSplitPhiTy :: Type -> (ThetaType, Type) tcSplitPredFunTy_maybe :: Type -> Maybe (PredType, Type) tcSplitFunTy_maybe :: Type -> Maybe (Type, Type) tcSplitFunTys :: Type -> ([Type], Type) tcFunArgTy :: Type -> Type tcFunResultTy :: Type -> Type tcSplitFunTysN :: TcRhoType -> Arity -> ([TcSigmaType], TcSigmaType) tcSplitTyConApp :: Type -> (TyCon, [Type]) tcSplitTyConApp_maybe :: Type -> Maybe (TyCon, [Type]) tcTyConAppTyCon :: Type -> TyCon tcTyConAppArgs :: Type -> [Type] tcSplitAppTy_maybe :: Type -> Maybe (Type, Type) tcSplitAppTy :: Type -> (Type, Type) tcSplitAppTys :: Type -> (Type, [Type]) -- | Does the AppTy split as in splitAppTy_maybe, but assumes that -- any Core view stuff is already done repSplitAppTy_maybe :: Type -> Maybe (Type, Type) tcInstHeadTyNotSynonym :: Type -> Bool tcInstHeadTyAppAllTyVars :: Type -> Bool tcGetTyVar_maybe :: Type -> Maybe TyVar tcGetTyVar :: String -> Type -> TyVar tcSplitSigmaTy :: Type -> ([TyVar], ThetaType, Type) tcDeepSplitSigmaTy_maybe :: TcSigmaType -> Maybe ([TcType], [TyVar], ThetaType, TcSigmaType) -- | Type equality on source types. Does not look through newtypes -- or PredTypes, but it does look through type synonyms. tcEqType :: Type -> Type -> Bool tcEqTypes :: [Type] -> [Type] -> Bool tcEqPred :: PredType -> PredType -> Bool -- | Type ordering on source types. Does not look through newtypes -- or PredTypes, but it does look through type synonyms. tcCmpType :: Type -> Type -> Ordering tcCmpTypes :: [Type] -> [Type] -> Ordering tcCmpPred :: PredType -> PredType -> Ordering tcEqTypeX :: RnEnv2 -> Type -> Type -> Bool eqKind :: Kind -> Kind -> Bool isSigmaTy :: Type -> Bool isOverloadedTy :: Type -> Bool isDoubleTy :: Type -> Bool isFloatTy :: Type -> Bool isIntTy :: Type -> Bool isWordTy :: Type -> Bool isStringTy :: Type -> Bool isIntegerTy :: Type -> Bool isBoolTy :: Type -> Bool isUnitTy :: Type -> Bool isCharTy :: Type -> Bool isTauTy :: Type -> Bool isTauTyCon :: TyCon -> Bool tcIsTyVarTy :: Type -> Bool tcIsForAllTy :: Type -> Bool isSynFamilyTyConApp :: TcTauType -> Bool deNoteType :: Type -> Type orphNamesOfType :: Type -> NameSet orphNamesOfDFunHead :: Type -> NameSet getDFunTyKey :: Type -> OccName getClassPredTys_maybe :: PredType -> Maybe (Class, [Type]) getClassPredTys :: PredType -> (Class, [Type]) isClassPred :: PredType -> Bool isTyVarClassPred :: PredType -> Bool isEqPred :: PredType -> Bool mkClassPred :: Class -> [Type] -> PredType mkIPPred :: IPName Name -> Type -> PredType tcSplitPredTy_maybe :: Type -> Maybe PredType mkDictTy :: Class -> [Type] -> Type evVarPred :: EvVar -> PredType isPredTy :: Type -> Bool isDictTy :: Type -> Bool isDictLikeTy :: Type -> Bool tcSplitDFunTy :: Type -> ([TyVar], Class, [Type]) tcSplitDFunHead :: Type -> (Class, [Type]) predTyUnique :: PredType -> Unique isIPPred :: PredType -> Bool mkMinimalBySCs :: [PredType] -> [PredType] transSuperClasses :: Class -> [Type] -> [PredType] immSuperClasses :: Class -> [Type] -> [PredType] tidyType :: TidyEnv -> Type -> Type tidyTypes :: TidyEnv -> [Type] -> [Type] -- | Grabs the free type variables, tidies them and then uses -- tidyType to work over the type itself tidyOpenType :: TidyEnv -> Type -> (TidyEnv, Type) tidyOpenTypes :: TidyEnv -> [Type] -> (TidyEnv, [Type]) -- | This tidies up a type for printing in an error message, or in an -- interface file. -- -- It doesn't change the uniques at all, just the print names. tidyTyVarBndr :: TidyEnv -> TyVar -> (TidyEnv, TyVar) -- | Add the free TyVars to the env in tidy form, so that we can -- tidy the type they are free in tidyFreeTyVars :: TidyEnv -> TyVarSet -> TidyEnv -- | Treat a new TyVar as a binder, and give it a fresh tidy name -- using the environment if one has not already been allocated. See also -- tidyTyVarBndr tidyOpenTyVar :: TidyEnv -> TyVar -> (TidyEnv, TyVar) tidyOpenTyVars :: TidyEnv -> [TyVar] -> (TidyEnv, [TyVar]) -- | Calls tidyType on a top-level type (i.e. with an empty tidying -- environment) tidyTopType :: Type -> Type tidyPred :: TidyEnv -> PredType -> PredType tidyKind :: TidyEnv -> Kind -> (TidyEnv, Kind) isFFIArgumentTy :: DynFlags -> Safety -> Type -> Bool isFFIImportResultTy :: DynFlags -> Type -> Bool isFFIExportResultTy :: Type -> Bool isFFIExternalTy :: Type -> Bool isFFIDynArgumentTy :: Type -> Bool isFFIDynResultTy :: Type -> Bool isFFIPrimArgumentTy :: DynFlags -> Type -> Bool isFFIPrimResultTy :: DynFlags -> Type -> Bool isFFILabelTy :: Type -> Bool isFFIDotnetTy :: DynFlags -> Type -> Bool isFFIDotnetObjTy :: Type -> Bool isFFITy :: Type -> Bool isFunPtrTy :: Type -> Bool tcSplitIOType_maybe :: Type -> Maybe (TyCon, Type, CoercionI) typeKind :: Type -> Kind -- | The key type representing kinds in the compiler. Invariant: a kind is -- always in one of these forms: -- --
--   FunTy k1 k2
--   TyConApp PrimTyCon [...]
--   TyVar kv   -- (during inference only)
--   ForAll ... -- (for top-level coercions)
--   
type Kind = Type -- | See Type#kind_subtyping for details of the distinction between -- these Kinds unliftedTypeKind :: Kind liftedTypeKind :: Kind argTypeKind :: Kind openTypeKind :: Kind -- | Given two kinds k1 and k2, creates the Kind -- k1 -> k2 mkArrowKind :: Kind -> Kind -> Kind -- | Iterated application of mkArrowKind mkArrowKinds :: [Kind] -> Kind -> Kind isLiftedTypeKind :: Kind -> Bool isUnliftedTypeKind :: Kind -> Bool -- | True of any sub-kind of OpenTypeKind (i.e. anything except arrow) isSubOpenTypeKind :: Kind -> Bool -- | True of any sub-kind of ArgTypeKind isSubArgTypeKind :: Kind -> Bool -- | k1 `isSubKind` k2 checks that k1 <: k2 isSubKind :: Kind -> Kind -> Bool -- | Essentially splitFunTys on kinds splitKindFunTys :: Kind -> ([Kind], Kind) -- | Used when generalising: default kind ? and ?? to *. See -- Type#kind_subtyping for more information on what that means defaultKind :: Kind -> Kind kindVarRef :: KindVar -> IORef MetaDetails mkKindVar :: Unique -> IORef MetaDetails -> KindVar -- | The key representation of types within the compiler data Type -- | A type of the form PredTy p represents a value whose type is -- the Haskell predicate p, where a predicate is what occurs -- before the => in a Haskell type. It can be expanded into -- its representation, but: -- -- -- -- Consider these examples: -- --
--   f :: (Eq a) => a -> Int
--   g :: (?x :: Int -> Int) => a -> Int
--   h :: (r\l) => {r} => {l::Int | r}
--   
-- -- Here the Eq a and ?x :: Int -> Int and -- rl are all called "predicates" data PredType -- | Class predicate e.g. Eq a ClassP :: Class -> [Type] -> PredType -- | Implicit parameter e.g. ?x :: Int IParam :: (IPName Name) -> Type -> PredType -- | Equality predicate e.g ty1 ~ ty2 EqPred :: Type -> Type -> PredType -- | A collection of PredTypes type ThetaType = [PredType] mkForAllTy :: TyVar -> Type -> Type -- | Wraps foralls over the type using the provided TyVars from left -- to right mkForAllTys :: [TyVar] -> Type -> Type -- | Creates a function type from the given argument and result type mkFunTy :: Type -> Type -> Type mkFunTys :: [Type] -> Type -> Type -- | Splits off argument types from the given type and associating them -- with the things in the input list from left to right. The final result -- type is returned, along with the resulting pairs of objects and types, -- albeit with the list of pairs in reverse order. Panics if there are -- not enough argument types for the input list. zipFunTys :: Outputable a => [a] -> Type -> ([(a, Type)], Type) -- | A key function: builds a TyConApp or FunTy as -- apppropriate to its arguments. Applies its arguments to the -- constructor from left to right mkTyConApp :: TyCon -> [Type] -> Type -- | Applies a type to another, as in e.g. k a mkAppTy :: Type -> Type -> Type mkAppTys :: Type -> [Type] -> Type -- | Instantiate a forall type with one or more type arguments. Used when -- we have a polymorphic function applied to type args: -- --
--   f t1 t2
--   
-- -- We use applyTys type-of-f [t1,t2] to compute the type of the -- expression. Panics if no application is possible. applyTy :: Type -> Type -> Type -- | This function is interesting because: -- --
    --
  1. The function may have more for-alls than there are args
  2. --
  3. Less obviously, it may have fewer for-alls
  4. --
-- -- For case 2. think of: -- --
--   applyTys (forall a.a) [forall b.b, Int]
--   
-- -- This really can happen, via dressing up polymorphic types with newtype -- clothing. Here's an example: -- --
--   newtype R = R (forall a. a->a)
--   foo = case undefined :: R of
--              R f -> f ()
--   
applyTys :: Type -> [Type] -> Type mkTyVarTy :: TyVar -> Type mkTyVarTys :: [TyVar] -> [Type] -- | Create the plain type constructor type which has been applied to no -- type arguments at all. mkTyConTy :: TyCon -> Type mkPredTy :: PredType -> Type mkPredTys :: ThetaType -> [Type] -- | Type substitution -- -- The following invariants must hold of a TvSubst: -- --
    --
  1. The in-scope set is needed only to guide the generation of -- fresh uniques
  2. --
  3. In particular, the kind of the type variables in the -- in-scope set is not relevant
  4. --
  5. The substition is only applied ONCE! This is because in general -- such application will not reached a fixed point.
  6. --
data TvSubst TvSubst :: InScopeSet -> TvSubstEnv -> TvSubst -- | A substitition of Types for TyVars type TvSubstEnv = TyVarEnv Type emptyTvSubst :: TvSubst substEqSpec :: TvSubst -> [(TyVar, Type)] -> [(TcType, TcType)] -- | Generates the in-scope set for the TvSubst from the types in -- the incoming environment, hence open mkOpenTvSubst :: TvSubstEnv -> TvSubst -- | Generates the in-scope set for the TvSubst from the types in -- the incoming environment, hence open zipOpenTvSubst :: [TyVar] -> [Type] -> TvSubst zipTopTvSubst :: [TyVar] -> [Type] -> TvSubst -- | Called when doing top-level substitutions. Here we expect that the -- free vars of the range of the substitution will be empty. mkTopTvSubst :: [(TyVar, Type)] -> TvSubst notElemTvSubst :: TyVar -> TvSubst -> Bool unionTvSubst :: TvSubst -> TvSubst -> TvSubst getTvSubstEnv :: TvSubst -> TvSubstEnv setTvSubstEnv :: TvSubst -> TvSubstEnv -> TvSubst getTvInScope :: TvSubst -> InScopeSet extendTvInScope :: TvSubst -> Var -> TvSubst lookupTyVar :: TvSubst -> TyVar -> Maybe Type extendTvSubst :: TvSubst -> TyVar -> Type -> TvSubst extendTvSubstList :: TvSubst -> [TyVar] -> [Type] -> TvSubst isInScope :: Var -> TvSubst -> Bool mkTvSubst :: InScopeSet -> TvSubstEnv -> TvSubst zipTyEnv :: [TyVar] -> [Type] -> TvSubstEnv -- | Substitute within a Type substTy :: TvSubst -> Type -> Type -- | Substitute within several Types substTys :: TvSubst -> [Type] -> [Type] -- | Type substitution making use of an TvSubst that is assumed to -- be open, see zipOpenTvSubst substTyWith :: [TyVar] -> [Type] -> Type -> Type -- | Substitute within a ThetaType substTheta :: TvSubst -> ThetaType -> ThetaType substTyVar :: TvSubst -> TyVar -> Type substTyVars :: TvSubst -> [TyVar] -> [Type] substTyVarBndr :: TvSubst -> TyVar -> (TvSubst, TyVar) -- | See Type#type_classification for what an unlifted type is isUnLiftedType :: Type -> Bool isUnboxedTupleType :: Type -> Bool -- | Returns true of types that are opaque to Haskell. Most of these are -- unlifted, but now that we interact with .NET, we may have primtive -- (foreign-imported) types that are lifted isPrimitiveType :: Type -> Bool -- | NB: for type synonyms tyVarsOfType does not expand the synonym tyVarsOfType :: Type -> TyVarSet tyVarsOfTypes :: [Type] -> TyVarSet tyVarsOfPred :: PredType -> TyVarSet tyVarsOfTheta :: ThetaType -> TyVarSet tcTyVarsOfType :: Type -> TcTyVarSet tcTyVarsOfTypes :: [Type] -> TyVarSet tcTyVarsOfPred :: PredType -> TyVarSet exactTyVarsOfType :: TcType -> TyVarSet exactTyVarsOfTypes :: [TcType] -> TyVarSet pprKind :: Kind -> SDoc pprParendKind :: Kind -> SDoc pprType :: Type -> SDoc pprParendType :: Type -> SDoc pprTypeApp :: NamedThing a => a -> [Type] -> SDoc pprTyThingCategory :: TyThing -> SDoc pprPred :: PredType -> SDoc pprTheta :: ThetaType -> SDoc pprThetaArrow :: ThetaType -> SDoc pprClassPred :: Class -> [Type] -> SDoc instance Outputable MetaDetails module Generics canDoGenerics :: [DataCon] -> Bool mkTyConGenericBinds :: TyCon -> LHsBinds RdrName mkGenericRhs :: Id -> TyVar -> TyCon -> LHsExpr RdrName validGenericInstanceType :: Type -> Bool validGenericMethodType :: Type -> Bool -- | Commonly useful utilites for manipulating the Core language module CoreUtils -- | Wraps the given expression in the cost centre unless in a way that -- maximises their utility to the user mkSCC :: CostCentre -> Expr b -> Expr b -- | Wrap the given expression in the coercion safely, coalescing nested -- coercions mkCoerce :: Coercion -> CoreExpr -> CoreExpr -- | Wrap the given expression in the coercion, dropping identity coercions -- and coalescing nested coercions mkCoerceI :: CoercionI -> CoreExpr -> CoreExpr -- | bindNonRec x r b produces either: -- --
--   let x = r in b
--   
-- -- or: -- --
--   case r of x { _DEFAULT_ -> b }
--   
-- -- depending on whether we have to use a case or let -- binding for the expression (see needsCaseBinding). It's used by -- the desugarer to avoid building bindings that give Core Lint a heart -- attack, although actually the simplifier deals with them perfectly -- well. See also MkCore.mkCoreLet bindNonRec :: Id -> CoreExpr -> CoreExpr -> CoreExpr -- | Tests whether we have to use a case rather than let -- binding for this expression as per the invariants of CoreExpr: -- see CoreSyn#let_app_invariant needsCaseBinding :: Type -> CoreExpr -> Bool -- | This guy constructs the value that the scrutinee must have given that -- you are in one particular branch of a case mkAltExpr :: AltCon -> [CoreBndr] -> [Type] -> CoreExpr -- | Makes a (->) type or a forall type, depending on whether -- it is given a type variable or a term variable. mkPiType :: EvVar -> Type -> Type -- | mkPiType for multiple type or value arguments mkPiTypes :: [EvVar] -> Type -> Type -- | Extract the default case alternative findDefault :: [CoreAlt] -> ([CoreAlt], Maybe CoreExpr) -- | Find the case alternative corresponding to a particular constructor: -- panics if no such constructor exists findAlt :: AltCon -> [CoreAlt] -> Maybe CoreAlt isDefaultAlt :: CoreAlt -> Bool -- | Merge alternatives preserving order; alternatives in the first -- argument shadow ones in the second mergeAlts :: [CoreAlt] -> [CoreAlt] -> [CoreAlt] -- | Given: -- --
--   case (C a b x y) of
--          C b x y -> ...
--   
-- -- We want to drop the leading type argument of the scrutinee leaving the -- arguments to match agains the pattern trimConArgs :: AltCon -> [CoreArg] -> [CoreArg] -- | Recover the type of a well-typed Core expression. Fails when applied -- to the actual Type expression as it cannot really be said to -- have a type exprType :: CoreExpr -> Type -- | Returns the type of the alternatives right hand side coreAltType :: CoreAlt -> Type -- | Returns the type of the first alternative, which should be the same as -- for all alternatives coreAltsType :: [CoreAlt] -> Type exprIsDupable :: CoreExpr -> Bool exprIsTrivial :: CoreExpr -> Bool exprIsCheap :: CoreExpr -> Bool exprIsExpandable :: CoreExpr -> Bool exprIsCheap' :: CheapAppFun -> CoreExpr -> Bool type CheapAppFun = Id -> Int -> Bool -- | exprIsHNF returns true for expressions that are certainly -- already evaluated to head normal form. This is used to -- decide whether it's ok to change: -- --
--   case x of _ -> e
--   
-- -- into: -- --
--   e
--   
-- -- and to decide whether it's safe to discard a seq. -- -- So, it does not treat variables as evaluated, unless they say -- they are. However, it does treat partial applications and -- constructor applications as values, even if their arguments are -- non-trivial, provided the argument type is lifted. For example, both -- of these are values: -- --
--   (:) (f x) (map f xs)
--   map (...redex...)
--   
-- -- because seq on such things completes immediately. -- -- For unlifted argument types, we have to be careful: -- --
--   C (f x :: Int#)
--   
-- -- Suppose f x diverges; then C (f x) is not a value. -- However this can't happen: see CoreSyn#let_app_invariant. This -- invariant states that arguments of unboxed type must be -- ok-for-speculation (or trivial). exprIsHNF :: CoreExpr -> Bool -- | exprOkForSpeculation returns True of an expression that is: -- -- -- -- Precisely, it returns True iff: -- -- -- -- Note that if exprIsHNF e, then exprOkForSpecuation -- e. As an example of the considerations in this test, consider: -- --
--   let x = case y# +# 1# of { r# -> I# r# }
--   in E
--   
-- -- being translated to: -- --
--   case y# +# 1# of { r# -> 
--      let x = I# r#
--      in E 
--   }
--   
-- -- We can only do this if the y + 1 is ok for speculation: it -- has no side effects, and can't diverge or raise an exception. exprOkForSpeculation :: CoreExpr -> Bool -- | Returns True of expressions that are too big to be compared -- by cheapEqExpr exprIsBig :: Expr b -> Bool -- | Similar to exprIsHNF but includes CONLIKE functions as well as -- data constructors. Conlike arguments are considered interesting by the -- inliner. exprIsConLike :: CoreExpr -> Bool -- | This function is called only on *top-level* right-hand sides. Returns -- True if the RHS can be allocated statically in the output, -- with no thunks involved at all. rhsIsStatic :: (Name -> Bool) -> CoreExpr -> Bool isCheapApp :: CheapAppFun isExpandableApp :: CheapAppFun coreBindsSize :: [CoreBind] -> Int -- | A measure of the size of the expressions, strictly greater than 0 It -- also forces the expression pretty drastically as a side effect exprSize :: CoreExpr -> Int -- | Two expressions that hash to the same Int may be equal (but -- may not be) Two expressions that hash to the different Ints are -- definitely unequal. -- -- The emphasis is on a crude, fast hash, rather than on high precision. -- -- But unequal here means "not identical"; two alpha-equivalent -- expressions may hash to the different Ints. -- -- We must be careful that \x.x and \y.y map to the -- same hash code, (at least if we want the above invariant to be true). hashExpr :: CoreExpr -> Int -- | A cheap equality test which bales out fast! If it returns -- True the arguments are definitely equal, otherwise, they may -- or may not be equal. -- -- See also exprIsBig cheapEqExpr :: Expr b -> Expr b -> Bool eqExpr :: InScopeSet -> CoreExpr -> CoreExpr -> Bool -- | Compares expressions for equality, modulo alpha. Does not look -- through newtypes or predicate types Used in rule matching, and also -- CSE eqExprX :: IdUnfoldingFun -> RnEnv2 -> CoreExpr -> CoreExpr -> Bool tryEtaReduce :: [Var] -> CoreExpr -> Maybe CoreExpr -- | A more efficient version of applyTypeToArg when we have several -- arguments. The first argument is just for debugging, and gives some -- context applyTypeToArgs :: CoreExpr -> Type -> [CoreExpr] -> Type -- | Determines the type resulting from applying an expression to a -- function with the given type applyTypeToArg :: Type -> CoreExpr -> Type dataConOrigInstPat :: [Unique] -> DataCon -> [Type] -> ([TyVar], [CoVar], [Id]) dataConRepInstPat :: [Unique] -> DataCon -> [Type] -> ([TyVar], [CoVar], [Id]) dataConRepFSInstPat :: [FastString] -> [Unique] -> DataCon -> [Type] -> ([TyVar], [CoVar], [Id]) module CSE cseProgram :: [CoreBind] -> [CoreBind] module SAT doStaticArgs :: UniqSupply -> [CoreBind] -> [CoreBind] module InstEnv type DFunId = Id data OverlapFlag NoOverlap :: OverlapFlag OverlapOk :: OverlapFlag Incoherent :: OverlapFlag data Instance Instance :: Name -> [Maybe Name] -> TyVarSet -> [Type] -> DFunId -> OverlapFlag -> Instance is_cls :: Instance -> Name is_tcs :: Instance -> [Maybe Name] is_tvs :: Instance -> TyVarSet is_tys :: Instance -> [Type] is_dfun :: Instance -> DFunId is_flag :: Instance -> OverlapFlag pprInstance :: Instance -> SDoc pprInstanceHdr :: Instance -> SDoc pprInstances :: [Instance] -> SDoc instanceHead :: Instance -> ([TyVar], ThetaType, Class, [Type]) mkLocalInstance :: DFunId -> OverlapFlag -> Instance mkImportedInstance :: Name -> [Maybe Name] -> DFunId -> OverlapFlag -> Instance instanceDFunId :: Instance -> DFunId setInstanceDFunId :: Instance -> DFunId -> Instance instanceRoughTcs :: Instance -> [Maybe Name] type InstEnv = UniqFM ClsInstEnv emptyInstEnv :: InstEnv extendInstEnv :: InstEnv -> Instance -> InstEnv extendInstEnvList :: InstEnv -> [Instance] -> InstEnv lookupInstEnv :: (InstEnv, InstEnv) -> Class -> [Type] -> ([InstMatch], [Instance]) instEnvElts :: InstEnv -> [Instance] classInstances :: (InstEnv, InstEnv) -> Class -> [Instance] instanceBindFun :: TyVar -> BindFlag instanceCantMatch :: [Maybe Name] -> [Maybe Name] -> Bool roughMatchTcs :: [Type] -> [Maybe Name] instance Outputable ClsInstEnv instance Outputable Instance instance NamedThing Instance module FamInstEnv data FamInst FamInst :: Name -> [Maybe Name] -> TyVarSet -> [Type] -> TyCon -> FamInst fi_fam :: FamInst -> Name fi_tcs :: FamInst -> [Maybe Name] fi_tvs :: FamInst -> TyVarSet fi_tys :: FamInst -> [Type] fi_tycon :: FamInst -> TyCon famInstTyCon :: FamInst -> TyCon famInstTyVars :: FamInst -> TyVarSet pprFamInst :: FamInst -> SDoc pprFamInstHdr :: FamInst -> SDoc pprFamInsts :: [FamInst] -> SDoc famInstHead :: FamInst -> ([TyVar], TyCon, [Type]) mkLocalFamInst :: TyCon -> FamInst mkImportedFamInst :: Name -> [Maybe Name] -> TyCon -> FamInst type FamInstEnvs = (FamInstEnv, FamInstEnv) type FamInstEnv = UniqFM FamilyInstEnv emptyFamInstEnv :: FamInstEnv emptyFamInstEnvs :: (FamInstEnv, FamInstEnv) extendFamInstEnv :: FamInstEnv -> FamInst -> FamInstEnv extendFamInstEnvList :: FamInstEnv -> [FamInst] -> FamInstEnv famInstEnvElts :: FamInstEnv -> [FamInst] familyInstances :: (FamInstEnv, FamInstEnv) -> TyCon -> [FamInst] lookupFamInstEnv :: FamInstEnvs -> TyCon -> [Type] -> [FamInstMatch] lookupFamInstEnvConflicts :: FamInstEnvs -> FamInst -> [TyVar] -> [FamInstMatch] topNormaliseType :: FamInstEnvs -> Type -> Maybe (Coercion, Type) instance Outputable FamilyInstEnv instance Outputable FamInst instance NamedThing FamInst -- | A module concerned with finding the free variables of an expression. module CoreFVs -- | Find all locally-defined free Ids or type variables in an expression exprFreeVars :: CoreExpr -> VarSet -- | Find all locally-defined free Ids in an expression exprFreeIds :: CoreExpr -> IdSet -- | Find all locally-defined free Ids or type variables in several -- expressions exprsFreeVars :: [CoreExpr] -> VarSet -- | Find all locally defined free Ids in a binding group bindFreeVars :: CoreBind -> VarSet -- | Predicate on possible free variables: returns True iff the -- variable is interesting type InterestingVarFun = Var -> Bool -- | Finds free variables in an expression selected by a predicate exprSomeFreeVars :: InterestingVarFun -> CoreExpr -> VarSet -- | Finds free variables in several expressions selected by a predicate exprsSomeFreeVars :: InterestingVarFun -> [CoreExpr] -> VarSet varTypeTyVars :: Var -> TyVarSet varTypeTcTyVars :: Var -> TyVarSet idUnfoldingVars :: Id -> VarSet idFreeVars :: Id -> VarSet idRuleAndUnfoldingVars :: Id -> VarSet idRuleVars :: Id -> VarSet idRuleRhsVars :: (Activation -> Bool) -> Id -> VarSet stableUnfoldingVars :: Unfolding -> VarSet -- | Those variables free in the right hand side of a rule ruleRhsFreeVars :: CoreRule -> VarSet -- | Those variables free in the right hand side of several rules rulesFreeVars :: [CoreRule] -> VarSet -- | ruleLhsOrphNames is used when deciding whether a rule is an orphan. In -- particular, suppose that T is defined in this module; we want to avoid -- declaring that a rule like: -- --
--   fromIntegral T = fromIntegral_T
--   
-- -- is an orphan. Of course it isn't, and declaring it an orphan would -- make the whole module an orphan module, which is bad. ruleLhsOrphNames :: CoreRule -> NameSet -- | This finds all locally-defined free Ids on the left hand side of a -- rule ruleLhsFreeIds :: CoreRule -> VarSet -- | Every node in an expression annotated with its (non-global) free -- variables, both Ids and TyVars type CoreExprWithFVs = AnnExpr Id VarSet -- | Every node in a binding group annotated with its (non-global) free -- variables, both Ids and TyVars type CoreBindWithFVs = AnnBind Id VarSet -- | Annotate a CoreExpr with its (non-global) free type and value -- variables at every tree node freeVars :: CoreExpr -> CoreExprWithFVs -- | Inverse function to freeVars freeVarsOf :: CoreExprWithFVs -> IdSet module CoreLint lintCoreBindings :: [CoreBind] -> (Bag Message, Bag Message) lintUnfolding :: SrcLoc -> [Var] -> CoreExpr -> Maybe Message instance Monad LintM module OccurAnal occurAnalysePgm :: Maybe (Activation -> Bool) -> [CoreRule] -> [CoreBind] -> [CoreBind] occurAnalyseExpr :: CoreExpr -> CoreExpr instance Outputable OccEncl module FloatIn floatInwards :: [CoreBind] -> [CoreBind] module FunDeps data FDEq FDEq :: Int -> Type -> Type -> FDEq fd_pos :: FDEq -> Int fd_ty_left :: FDEq -> Type fd_ty_right :: FDEq -> Type data Equation FDEqn :: TyVarSet -> [FDEq] -> Pred_Loc -> Pred_Loc -> Equation fd_qtvs :: Equation -> TyVarSet fd_eqs :: Equation -> [FDEq] fd_pred1 :: Equation -> Pred_Loc fd_pred2 :: Equation -> Pred_Loc pprEquation :: Equation -> SDoc oclose :: [PredType] -> TyVarSet -> TyVarSet improveFromInstEnv :: (InstEnv, InstEnv) -> Pred_Loc -> [Equation] improveFromAnother :: Pred_Loc -> Pred_Loc -> [Equation] checkInstCoverage :: Class -> [Type] -> Bool checkFunDeps :: (InstEnv, InstEnv) -> Instance -> Maybe [Instance] pprFundeps :: Outputable a => [FunDep a] -> SDoc -- | Package manipulation module Packages -- | A PackageConfigMap maps a PackageId to a PackageConfig type PackageConfigMap = UniqFM PackageConfig emptyPackageConfigMap :: PackageConfigMap -- | Find the package we know about with the given id (e.g. "foo-1.0"), if -- any lookupPackage :: PackageConfigMap -> PackageId -> Maybe PackageConfig extendPackageConfigMap :: PackageConfigMap -> [PackageConfig] -> PackageConfigMap -- | Show package info on console, if verbosity is >= 3 dumpPackages :: DynFlags -> IO () -- | Package state is all stored in DynFlags, including the details -- of all packages, which packages are exposed, and which modules they -- provide. -- -- The package state is computed by initPackages, and kept in -- DynFlags. -- -- data PackageState PackageState :: PackageConfigMap -> [PackageId] -> UniqFM [(PackageConfig, Bool)] -> InstalledPackageIdMap -> PackageState pkgIdMap :: PackageState -> PackageConfigMap preloadPackages :: PackageState -> [PackageId] moduleToPkgConfAll :: PackageState -> UniqFM [(PackageConfig, Bool)] installedPackageIdMap :: PackageState -> InstalledPackageIdMap -- | Call this after DynFlags.parseDynFlags. It reads the package -- configuration files, and sets up various internal tables of package -- information, according to the package-related flags on the -- command-line (-package, -hide-package etc.) -- -- Returns a list of packages to link in if we're doing dynamic linking. -- This list contains the packages that the user explicitly mentioned -- with -package flags. -- -- initPackages can be called again subsequently after updating -- the packageFlags field of the DynFlags, and it will -- update the pkgState in DynFlags and return a list of -- packages to link in. initPackages :: DynFlags -> IO (DynFlags, [PackageId]) -- | Looks up the package with the given id in the package state, panicing -- if it is not found getPackageDetails :: PackageState -> PackageId -> PackageConfig -- | Takes a Module, and if the module is in a package returns -- (pkgconf, exposed) where pkgconf is the PackageConfig for -- that package, and exposed is True if the package exposes the -- module. lookupModuleInAllPackages :: DynFlags -> ModuleName -> [(PackageConfig, Bool)] -- | Find all the include directories in these and the preload packages getPackageIncludePath :: DynFlags -> [PackageId] -> IO [String] -- | Find all the library paths in these and the preload packages getPackageLibraryPath :: DynFlags -> [PackageId] -> IO [String] -- | Find all the link options in these and the preload packages getPackageLinkOpts :: DynFlags -> [PackageId] -> IO [String] -- | Find all the C-compiler options in these and the preload packages getPackageExtraCcOpts :: DynFlags -> [PackageId] -> IO [String] -- | Find all the package framework paths in these and the preload packages getPackageFrameworkPath :: DynFlags -> [PackageId] -> IO [String] -- | Find all the package frameworks in these and the preload packages getPackageFrameworks :: DynFlags -> [PackageId] -> IO [String] -- | Find all the PackageConfig in both the preload packages from -- DynFlags and corresponding to the list of PackageConfigs getPreloadPackagesAnd :: DynFlags -> [PackageId] -> IO [PackageConfig] collectIncludeDirs :: [PackageConfig] -> [FilePath] collectLibraryPaths :: [PackageConfig] -> [FilePath] collectLinkOpts :: DynFlags -> [PackageConfig] -> [String] packageHsLibs :: DynFlags -> PackageConfig -> [String] -- | Will the Name come from a dynamically linked library? isDllName :: PackageId -> Name -> Bool module CLabel data CLabel -- | Record where a foreign label is stored. data ForeignLabelSource -- | Label is in a named package ForeignLabelInPackage :: PackageId -> ForeignLabelSource -- | Label is in some external, system package that doesn't also contain -- compiled Haskell code, and is not associated with any .hi files. We -- don't have to worry about Haskell code being inlined from external -- packages. It is safe to treat the RTS package as external. ForeignLabelInExternalPackage :: ForeignLabelSource -- | Label is in the package currenly being compiled. This is only used for -- creating hacky tmp labels during code generation. Don't use it in any -- code that might be inlined across a package boundary (ie, core code) -- else the information will be wrong relative to the destination module. ForeignLabelInThisPackage :: ForeignLabelSource -- | For debugging problems with the CLabel representation. We can't make a -- Show instance for CLabel because lots of its components don't have -- instances. The regular Outputable instance only shows the label name, -- and not its other info. pprDebugCLabel :: CLabel -> SDoc mkClosureLabel :: Name -> CafInfo -> CLabel mkSRTLabel :: Name -> CafInfo -> CLabel mkInfoTableLabel :: Name -> CafInfo -> CLabel mkEntryLabel :: Name -> CafInfo -> CLabel mkSlowEntryLabel :: Name -> CafInfo -> CLabel mkConEntryLabel :: Name -> CafInfo -> CLabel mkStaticConEntryLabel :: Name -> CafInfo -> CLabel mkRednCountsLabel :: Name -> CafInfo -> CLabel mkConInfoTableLabel :: Name -> CafInfo -> CLabel mkStaticInfoTableLabel :: Name -> CafInfo -> CLabel mkLargeSRTLabel :: Unique -> CLabel mkApEntryLabel :: Bool -> Int -> CLabel mkApInfoTableLabel :: Bool -> Int -> CLabel mkClosureTableLabel :: Name -> CafInfo -> CLabel mkLocalClosureLabel :: Name -> CafInfo -> CLabel mkLocalInfoTableLabel :: Name -> CafInfo -> CLabel mkLocalEntryLabel :: Name -> CafInfo -> CLabel mkLocalConEntryLabel :: CafInfo -> Name -> CLabel mkLocalStaticConEntryLabel :: CafInfo -> Name -> CLabel mkLocalConInfoTableLabel :: CafInfo -> Name -> CLabel mkLocalStaticInfoTableLabel :: CafInfo -> Name -> CLabel mkLocalClosureTableLabel :: Name -> CafInfo -> CLabel mkReturnPtLabel :: Unique -> CLabel mkReturnInfoLabel :: Unique -> CLabel mkAltLabel :: Unique -> ConTag -> CLabel mkDefaultLabel :: Unique -> CLabel mkBitmapLabel :: Unique -> CLabel mkStringLitLabel :: Unique -> CLabel mkAsmTempLabel :: Uniquable a => a -> CLabel mkModuleInitLabel :: Module -> String -> CLabel mkPlainModuleInitLabel :: Module -> CLabel mkModuleInitTableLabel :: Module -> CLabel mkSplitMarkerLabel :: CLabel mkDirty_MUT_VAR_Label :: CLabel mkUpdInfoLabel :: CLabel mkBHUpdInfoLabel :: CLabel mkIndStaticInfoLabel :: CLabel mkMainCapabilityLabel :: CLabel mkMAP_FROZEN_infoLabel :: CLabel mkMAP_DIRTY_infoLabel :: CLabel mkEMPTY_MVAR_infoLabel :: CLabel mkTopTickyCtrLabel :: CLabel mkCAFBlackHoleInfoTableLabel :: CLabel mkRtsPrimOpLabel :: PrimOp -> CLabel mkRtsSlowTickyCtrLabel :: String -> CLabel moduleRegdLabel :: CLabel moduleRegTableLabel :: Module -> CLabel mkSelectorInfoLabel :: Bool -> Int -> CLabel mkSelectorEntryLabel :: Bool -> Int -> CLabel mkCmmInfoLabel :: PackageId -> FastString -> CLabel mkCmmEntryLabel :: PackageId -> FastString -> CLabel mkCmmRetInfoLabel :: PackageId -> FastString -> CLabel mkCmmRetLabel :: PackageId -> FastString -> CLabel mkCmmCodeLabel :: PackageId -> FastString -> CLabel mkCmmDataLabel :: PackageId -> FastString -> CLabel mkCmmGcPtrLabel :: PackageId -> FastString -> CLabel mkRtsApFastLabel :: FastString -> CLabel mkPrimCallLabel :: PrimCall -> CLabel -- | Make a foreign label mkForeignLabel :: FastString -> Maybe Int -> ForeignLabelSource -> FunctionOrData -> CLabel -- | Update the label size field in a ForeignLabel addLabelSize :: CLabel -> Int -> CLabel -- | Get the label size field from a ForeignLabel foreignLabelStdcallInfo :: CLabel -> Maybe Int mkCCLabel :: CostCentre -> CLabel mkCCSLabel :: CostCentreStack -> CLabel data DynamicLinkerLabelInfo CodeStub :: DynamicLinkerLabelInfo SymbolPtr :: DynamicLinkerLabelInfo GotSymbolPtr :: DynamicLinkerLabelInfo GotSymbolOffset :: DynamicLinkerLabelInfo mkDynamicLinkerLabel :: DynamicLinkerLabelInfo -> CLabel -> CLabel dynamicLinkerLabelInfo :: CLabel -> Maybe (DynamicLinkerLabelInfo, CLabel) mkPicBaseLabel :: CLabel mkDeadStripPreventer :: CLabel -> CLabel mkHpcTicksLabel :: Module -> CLabel mkHpcModuleNameLabel :: CLabel hasCAF :: CLabel -> Bool infoLblToEntryLbl :: CLabel -> CLabel entryLblToInfoLbl :: CLabel -> CLabel cvtToClosureLbl :: CLabel -> CLabel cvtToSRTLbl :: CLabel -> CLabel needsCDecl :: CLabel -> Bool -- | Check whether a label is a local temporary for native code generation isAsmTemp :: CLabel -> Bool -- | If a label is a local temporary used for native code generation then -- return just its unique, otherwise nothing. maybeAsmTemp :: CLabel -> Maybe Unique -- | Is a CLabel visible outside this object file or not? From the point of -- view of the code generator, a name is externally visible if it has to -- be declared as exported in the .o file's symbol table; that is, made -- non-static. externallyVisibleCLabel :: CLabel -> Bool -- | Check whether a label corresponds to a C function that has a prototype -- in a system header somehere, or is built-in to the C compiler. For -- these labels we abovoid generating our own C prototypes. isMathFun :: CLabel -> Bool isCFunctionLabel :: CLabel -> Bool isGcPtrLabel :: CLabel -> Bool labelDynamic :: PackageId -> CLabel -> Bool pprCLabel :: CLabel -> SDoc instance Eq ForeignLabelSource instance Ord ForeignLabelSource instance Eq IdLabelInfo instance Ord IdLabelInfo instance Eq CaseLabelInfo instance Ord CaseLabelInfo instance Eq RtsLabelInfo instance Ord RtsLabelInfo instance Eq CmmLabelInfo instance Ord CmmLabelInfo instance Eq DynamicLinkerLabelInfo instance Ord DynamicLinkerLabelInfo instance Eq CLabel instance Ord CLabel instance Outputable ForeignLabelSource instance Outputable CLabel module BlockId data BlockId BlockId :: Unique -> BlockId mkBlockId :: Unique -> BlockId data BlockEnv a emptyBlockEnv :: BlockEnv a elemBlockEnv :: BlockEnv a -> BlockId -> Bool lookupBlockEnv :: BlockEnv a -> BlockId -> Maybe a extendBlockEnv :: BlockEnv a -> BlockId -> a -> BlockEnv a mkBlockEnv :: [(BlockId, a)] -> BlockEnv a mapBlockEnv :: (a -> b) -> BlockEnv a -> BlockEnv b eltsBlockEnv :: BlockEnv elt -> [elt] plusBlockEnv :: BlockEnv elt -> BlockEnv elt -> BlockEnv elt delFromBlockEnv :: BlockEnv elt -> BlockId -> BlockEnv elt blockEnvToList :: BlockEnv elt -> [(BlockId, elt)] lookupWithDefaultBEnv :: BlockEnv a -> a -> BlockId -> a isNullBEnv :: BlockEnv a -> Bool sizeBEnv :: BlockEnv a -> Int foldBlockEnv :: (BlockId -> a -> b -> b) -> b -> BlockEnv a -> b foldBlockEnv' :: (a -> b -> b) -> b -> BlockEnv a -> b addToBEnv_Acc :: (elt -> elts -> elts) -> (elt -> elts) -> BlockEnv elts -> BlockId -> elt -> BlockEnv elts data BlockSet emptyBlockSet :: BlockSet unitBlockSet :: BlockId -> BlockSet isEmptyBlockSet :: BlockSet -> Bool elemBlockSet :: BlockId -> BlockSet -> Bool extendBlockSet :: BlockSet -> BlockId -> BlockSet sizeBlockSet :: BlockSet -> Int unionBlockSets :: BlockSet -> BlockSet -> BlockSet removeBlockSet :: BlockSet -> BlockId -> BlockSet mkBlockSet :: [BlockId] -> BlockSet blockSetToList :: BlockSet -> [BlockId] foldBlockSet :: (BlockId -> b -> b) -> b -> BlockSet -> b blockLbl :: BlockId -> CLabel infoTblLbl :: BlockId -> CLabel retPtLbl :: BlockId -> CLabel instance Eq BlockId instance Ord BlockId instance Outputable BlockSet instance Outputable a => Outputable (BlockEnv a) instance Outputable BlockId instance Show BlockId instance Uniquable BlockId module CmmExpr data CmmType b8 :: CmmType b16 :: CmmType b32 :: CmmType b64 :: CmmType f32 :: CmmType f64 :: CmmType bWord :: CmmType bHalfWord :: CmmType gcWord :: CmmType cInt :: CmmType cLong :: CmmType cmmBits :: Width -> CmmType cmmFloat :: Width -> CmmType typeWidth :: CmmType -> Width cmmEqType :: CmmType -> CmmType -> Bool cmmEqType_ignoring_ptrhood :: CmmType -> CmmType -> Bool isFloatType :: CmmType -> Bool isGcPtrType :: CmmType -> Bool isWord32 :: CmmType -> Bool isWord64 :: CmmType -> Bool isFloat64 :: CmmType -> Bool isFloat32 :: CmmType -> Bool data Width W8 :: Width W16 :: Width W32 :: Width W64 :: Width W80 :: Width W128 :: Width widthInBits :: Width -> Int widthInBytes :: Width -> Int widthInLog :: Width -> Int widthFromBytes :: Int -> Width wordWidth :: Width halfWordWidth :: Width cIntWidth :: Width cLongWidth :: Width narrowU :: Width -> Integer -> Integer narrowS :: Width -> Integer -> Integer data CmmExpr CmmLit :: CmmLit -> CmmExpr CmmLoad :: CmmExpr -> CmmType -> CmmExpr CmmReg :: CmmReg -> CmmExpr CmmMachOp :: MachOp -> [CmmExpr] -> CmmExpr CmmStackSlot :: Area -> Int -> CmmExpr CmmRegOff :: CmmReg -> Int -> CmmExpr cmmExprType :: CmmExpr -> CmmType cmmExprWidth :: CmmExpr -> Width maybeInvertCmmExpr :: CmmExpr -> Maybe CmmExpr data CmmReg CmmLocal :: LocalReg -> CmmReg CmmGlobal :: GlobalReg -> CmmReg cmmRegType :: CmmReg -> CmmType data CmmLit CmmInt :: Integer -> Width -> CmmLit CmmFloat :: Rational -> Width -> CmmLit CmmLabel :: CLabel -> CmmLit CmmLabelOff :: CLabel -> Int -> CmmLit CmmLabelDiffOff :: CLabel -> CLabel -> Int -> CmmLit CmmBlock :: BlockId -> CmmLit CmmHighStackMark :: CmmLit cmmLitType :: CmmLit -> CmmType data LocalReg -- | Parameters: 1. Identifier 2. Type LocalReg :: !Unique -> CmmType -> LocalReg localRegType :: LocalReg -> CmmType data GlobalReg VanillaReg :: {-# UNPACK #-} !Int -> VGcPtr -> GlobalReg FloatReg :: {-# UNPACK #-} !Int -> GlobalReg DoubleReg :: {-# UNPACK #-} !Int -> GlobalReg LongReg :: {-# UNPACK #-} !Int -> GlobalReg Sp :: GlobalReg SpLim :: GlobalReg Hp :: GlobalReg HpLim :: GlobalReg CurrentTSO :: GlobalReg CurrentNursery :: GlobalReg HpAlloc :: GlobalReg EagerBlackholeInfo :: GlobalReg GCEnter1 :: GlobalReg GCFun :: GlobalReg BaseReg :: GlobalReg PicBaseReg :: GlobalReg globalRegType :: GlobalReg -> CmmType spReg :: CmmReg hpReg :: CmmReg spLimReg :: CmmReg nodeReg :: CmmReg node :: GlobalReg data VGcPtr VGcPtr :: VGcPtr VNonGcPtr :: VGcPtr vgcFlag :: CmmType -> VGcPtr class DefinerOfLocalRegs a foldRegsDefd :: DefinerOfLocalRegs a => (b -> LocalReg -> b) -> b -> a -> b class UserOfLocalRegs a foldRegsUsed :: UserOfLocalRegs a => (b -> LocalReg -> b) -> b -> a -> b filterRegsUsed :: UserOfLocalRegs e => (LocalReg -> Bool) -> e -> RegSet class DefinerOfSlots a foldSlotsDefd :: DefinerOfSlots a => (b -> SubArea -> b) -> b -> a -> b class UserOfSlots a foldSlotsUsed :: UserOfSlots a => (b -> SubArea -> b) -> b -> a -> b -- | Sets of local registers type RegSet = UniqSet LocalReg emptyRegSet :: RegSet elemRegSet :: LocalReg -> RegSet -> Bool extendRegSet :: RegSet -> LocalReg -> RegSet deleteFromRegSet :: RegSet -> LocalReg -> RegSet mkRegSet :: [LocalReg] -> RegSet plusRegSet :: RegSet -> RegSet -> RegSet minusRegSet :: RegSet -> RegSet -> RegSet timesRegSet :: RegSet -> RegSet -> RegSet regUsedIn :: CmmReg -> CmmExpr -> Bool -- | A stack area is either the stack slot where a variable is spilled or -- the stack space where function arguments and results are passed. data Area RegSlot :: LocalReg -> Area CallArea :: AreaId -> Area data AreaId Old :: AreaId Young :: BlockId -> AreaId type SubArea = (Area, Int, Int) type SubAreaSet = Map Area [SubArea] type AreaMap = Map Area Int isStackSlotOf :: CmmExpr -> LocalReg -> Bool -- | Machine-level primops; ones which we can reasonably delegate to the -- native code generators to handle. Basically contains C's primops and -- no others. -- -- Nomenclature: all ops indicate width and signedness, where -- appropriate. Widths: 8/16/32/64 means the given size, obviously. Nat -- means the operation works on STG word sized objects. Signedness: S -- means signed, U means unsigned. For operations where signedness is -- irrelevant or makes no difference (for example integer add), the -- signedness component is omitted. -- -- An exception: NatP is a ptr-typed native word. From the point of view -- of the native code generators this distinction is irrelevant, but the -- C code generator sometimes needs this info to emit the right casts. data MachOp MO_Add :: Width -> MachOp MO_Sub :: Width -> MachOp MO_Eq :: Width -> MachOp MO_Ne :: Width -> MachOp MO_Mul :: Width -> MachOp MO_S_MulMayOflo :: Width -> MachOp MO_S_Quot :: Width -> MachOp MO_S_Rem :: Width -> MachOp MO_S_Neg :: Width -> MachOp MO_U_MulMayOflo :: Width -> MachOp MO_U_Quot :: Width -> MachOp MO_U_Rem :: Width -> MachOp MO_S_Ge :: Width -> MachOp MO_S_Le :: Width -> MachOp MO_S_Gt :: Width -> MachOp MO_S_Lt :: Width -> MachOp MO_U_Ge :: Width -> MachOp MO_U_Le :: Width -> MachOp MO_U_Gt :: Width -> MachOp MO_U_Lt :: Width -> MachOp MO_F_Add :: Width -> MachOp MO_F_Sub :: Width -> MachOp MO_F_Neg :: Width -> MachOp MO_F_Mul :: Width -> MachOp MO_F_Quot :: Width -> MachOp MO_F_Eq :: Width -> MachOp MO_F_Ne :: Width -> MachOp MO_F_Ge :: Width -> MachOp MO_F_Le :: Width -> MachOp MO_F_Gt :: Width -> MachOp MO_F_Lt :: Width -> MachOp MO_And :: Width -> MachOp MO_Or :: Width -> MachOp MO_Xor :: Width -> MachOp MO_Not :: Width -> MachOp MO_Shl :: Width -> MachOp MO_U_Shr :: Width -> MachOp MO_S_Shr :: Width -> MachOp MO_SF_Conv :: Width -> Width -> MachOp MO_FS_Conv :: Width -> Width -> MachOp MO_SS_Conv :: Width -> Width -> MachOp MO_UU_Conv :: Width -> Width -> MachOp MO_FF_Conv :: Width -> Width -> MachOp pprMachOp :: MachOp -> SDoc -- | Returns True if the MachOp has commutable arguments. This is -- used in the platform-independent Cmm optimisations. -- -- If in doubt, return False. This generates worse code on the -- native routes, but is otherwise harmless. isCommutableMachOp :: MachOp -> Bool -- | Returns True if the MachOp is associative (i.e. (x+y)+z == -- x+(y+z)) This is used in the platform-independent Cmm -- optimisations. -- -- If in doubt, return False. This generates worse code on the -- native routes, but is otherwise harmless. isAssociativeMachOp :: MachOp -> Bool -- | Returns True if the MachOp is a comparison. -- -- If in doubt, return False. This generates worse code on the native -- routes, but is otherwise harmless. isComparisonMachOp :: MachOp -> Bool -- | Returns the MachRep of the result of a MachOp. machOpResultType :: MachOp -> [CmmType] -> CmmType -- | This function is used for debugging only: we can check whether an -- application of a MachOp is type-correct by checking that the -- MachReps of its arguments are the same as the MachOp expects. This is -- used when linting a CmmExpr. machOpArgReps :: MachOp -> [Width] maybeInvertComparison :: MachOp -> Maybe MachOp mo_wordAdd :: MachOp mo_wordSub :: MachOp mo_wordEq :: MachOp mo_wordNe :: MachOp mo_wordMul :: MachOp mo_wordSQuot :: MachOp mo_wordSRem :: MachOp mo_wordSNeg :: MachOp mo_wordUQuot :: MachOp mo_wordURem :: MachOp mo_wordSGe :: MachOp mo_wordSLe :: MachOp mo_wordSGt :: MachOp mo_wordSLt :: MachOp mo_wordUGe :: MachOp mo_wordULe :: MachOp mo_wordUGt :: MachOp mo_wordULt :: MachOp mo_wordAnd :: MachOp mo_wordOr :: MachOp mo_wordXor :: MachOp mo_wordNot :: MachOp mo_wordShl :: MachOp mo_wordSShr :: MachOp mo_wordUShr :: MachOp mo_u_8To32 :: MachOp mo_s_8To32 :: MachOp mo_u_16To32 :: MachOp mo_s_16To32 :: MachOp mo_u_8ToWord :: MachOp mo_s_8ToWord :: MachOp mo_u_16ToWord :: MachOp mo_s_16ToWord :: MachOp mo_u_32ToWord :: MachOp mo_s_32ToWord :: MachOp mo_32To8 :: MachOp mo_32To16 :: MachOp mo_WordTo8 :: MachOp mo_WordTo16 :: MachOp mo_WordTo32 :: MachOp instance Eq AreaId instance Ord AreaId instance Eq VGcPtr instance Show VGcPtr instance Show GlobalReg instance Eq CmmCat instance Eq Width instance Ord Width instance Show Width instance Eq Area instance Ord Area instance Eq CmmReg instance Ord CmmReg instance Eq CmmLit instance Eq MachOp instance Show MachOp instance Outputable Width instance Outputable CmmCat instance Outputable CmmType instance Ord GlobalReg instance Eq GlobalReg instance UserOfSlots a => UserOfSlots [a] instance UserOfSlots CmmExpr instance DefinerOfLocalRegs a => DefinerOfLocalRegs (Maybe a) instance DefinerOfLocalRegs a => DefinerOfLocalRegs [a] instance UserOfLocalRegs a => UserOfLocalRegs [a] instance UserOfLocalRegs CmmExpr instance UserOfLocalRegs RegSet instance DefinerOfLocalRegs LocalReg instance UserOfLocalRegs LocalReg instance DefinerOfLocalRegs CmmReg instance UserOfLocalRegs CmmReg instance Uniquable LocalReg instance Ord LocalReg instance Eq LocalReg instance Eq CmmExpr -- | Nasty #ifdefery that generates the definitions for freeReg and -- globalRegMaybe from the information in includes/MachRegs.h. -- -- If the current TARGET_ARCH isn't sparc then these functions will be -- wrong. module SPARC.RegPlate freeReg :: RegNo -> FastBool globalRegMaybe :: GlobalReg -> Maybe RealReg module SMRep type StgWord = Word64 type StgHalfWord = Word32 hALF_WORD_SIZE :: ByteOff hALF_WORD_SIZE_IN_BITS :: Int type WordOff = Int type ByteOff = Int data CgRep VoidArg :: CgRep PtrArg :: CgRep NonPtrArg :: CgRep LongArg :: CgRep FloatArg :: CgRep DoubleArg :: CgRep nonVoidArg :: CgRep -> Bool argMachRep :: CgRep -> CmmType primRepToCgRep :: PrimRep -> CgRep isFollowableArg :: CgRep -> Bool isVoidArg :: CgRep -> Bool isFloatingArg :: CgRep -> Bool is64BitArg :: CgRep -> Bool separateByPtrFollowness :: [(CgRep, a)] -> ([(CgRep, a)], [(CgRep, a)]) cgRepSizeW :: CgRep -> ByteOff cgRepSizeB :: CgRep -> ByteOff retAddrSizeW :: WordOff typeCgRep :: Type -> CgRep idCgRep :: Id -> CgRep tyConCgRep :: TyCon -> CgRep data SMRep GenericRep :: Bool -> !Int -> !Int -> ClosureType -> SMRep BlackHoleRep :: SMRep data ClosureType Constr :: ClosureType ConstrNoCaf :: ClosureType Fun :: ClosureType Thunk :: ClosureType ThunkSelector :: ClosureType isStaticRep :: SMRep -> Bool fixedHdrSize :: WordOff arrWordsHdrSize :: ByteOff arrPtrsHdrSize :: ByteOff profHdrSize :: WordOff thunkHdrSize :: WordOff smRepClosureType :: SMRep -> Maybe ClosureType smRepClosureTypeInt :: SMRep -> StgHalfWord rET_SMALL :: StgHalfWord rET_BIG :: StgHalfWord instance Eq CgRep instance Outputable CgRep module Bitmap -- | A bitmap represented by a sequence of StgWords on the -- target architecture. These are used for bitmaps in info tables -- and other generated code which need to be emitted as sequences of -- StgWords. type Bitmap = [StgWord] -- | Make a bitmap from a sequence of bits mkBitmap :: [Bool] -> Bitmap -- | Make a bitmap where the slots specified are the ones in the -- bitmap. eg. [0,1,3], size 4 ==> 0xb. -- -- The list of Ints must be already sorted. intsToBitmap :: Int -> [Int] -> Bitmap -- | Make a bitmap where the slots specified are the zeros in the -- bitmap. eg. [0,1,3], size 4 ==> 0x4 (we leave any bits -- outside the size as zero, just to make the bitmap easier to read). -- -- The list of Ints must be already sorted. intsToReverseBitmap :: Int -> [Int] -> Bitmap -- | Magic number, must agree with BITMAP_BITS_SHIFT in -- InfoTables.h. Some kinds of bitmap pack a size/bitmap into a single -- word if possible, or fall back to an external pointer when the bitmap -- is too large. This value represents the largest size of bitmap that -- can be packed into a single word. mAX_SMALL_BITMAP_SIZE :: Int seqBitmap :: Bitmap -> a -> a module StgSyn data GenStgArg occ StgVarArg :: occ -> GenStgArg occ StgLitArg :: Literal -> GenStgArg occ StgTypeArg :: Type -> GenStgArg occ type GenStgLiveVars occ = UniqSet occ data GenStgBinding bndr occ StgNonRec :: bndr -> (GenStgRhs bndr occ) -> GenStgBinding bndr occ StgRec :: [(bndr, GenStgRhs bndr occ)] -> GenStgBinding bndr occ data GenStgExpr bndr occ StgApp :: occ -> [GenStgArg occ] -> GenStgExpr bndr occ StgLit :: Literal -> GenStgExpr bndr occ StgConApp :: DataCon -> [GenStgArg occ] -> GenStgExpr bndr occ StgOpApp :: StgOp -> [GenStgArg occ] -> Type -> GenStgExpr bndr occ StgLam :: Type -> [bndr] -> StgExpr -> GenStgExpr bndr occ StgCase :: (GenStgExpr bndr occ) -> (GenStgLiveVars occ) -> (GenStgLiveVars occ) -> bndr -> SRT -> AltType -> [GenStgAlt bndr occ] -> GenStgExpr bndr occ StgLet :: (GenStgBinding bndr occ) -> (GenStgExpr bndr occ) -> GenStgExpr bndr occ StgLetNoEscape :: (GenStgLiveVars occ) -> (GenStgLiveVars occ) -> (GenStgBinding bndr occ) -> (GenStgExpr bndr occ) -> GenStgExpr bndr occ StgSCC :: CostCentre -> (GenStgExpr bndr occ) -> GenStgExpr bndr occ StgTick :: Module -> Int -> (GenStgExpr bndr occ) -> GenStgExpr bndr occ data GenStgRhs bndr occ StgRhsClosure :: CostCentreStack -> StgBinderInfo -> [occ] -> !UpdateFlag -> SRT -> [bndr] -> (GenStgExpr bndr occ) -> GenStgRhs bndr occ StgRhsCon :: CostCentreStack -> DataCon -> [GenStgArg occ] -> GenStgRhs bndr occ type GenStgAlt bndr occ = (AltCon, [bndr], [Bool], GenStgExpr bndr occ) data AltType PolyAlt :: AltType UbxTupAlt :: TyCon -> AltType AlgAlt :: TyCon -> AltType PrimAlt :: TyCon -> AltType data UpdateFlag ReEntrant :: UpdateFlag Updatable :: UpdateFlag SingleEntry :: UpdateFlag isUpdatable :: UpdateFlag -> Bool data StgBinderInfo noBinderInfo :: StgBinderInfo stgSatOcc :: StgBinderInfo stgUnsatOcc :: StgBinderInfo satCallsOnly :: StgBinderInfo -> Bool combineStgBinderInfo :: StgBinderInfo -> StgBinderInfo -> StgBinderInfo type StgArg = GenStgArg Id type StgLiveVars = GenStgLiveVars Id type StgBinding = GenStgBinding Id Id type StgExpr = GenStgExpr Id Id type StgRhs = GenStgRhs Id Id type StgAlt = GenStgAlt Id Id data StgOp StgPrimOp :: PrimOp -> StgOp StgPrimCallOp :: PrimCall -> StgOp StgFCallOp :: ForeignCall -> Unique -> StgOp data SRT NoSRT :: SRT SRTEntries :: IdSet -> SRT SRT :: !Int -> !Int -> !Bitmap -> SRT stgBindHasCafRefs :: GenStgBinding bndr Id -> Bool stgArgHasCafRefs :: GenStgArg Id -> Bool stgRhsArity :: StgRhs -> Int isDllConApp :: PackageId -> DataCon -> [StgArg] -> Bool isStgTypeArg :: StgArg -> Bool stgArgType :: StgArg -> Type pprStgBinding :: StgBinding -> SDoc pprStgBindings :: [StgBinding] -> SDoc pprStgBindingsWithSRTs :: [(StgBinding, [(Id, [Id])])] -> SDoc instance Outputable AltType instance (Outputable bndr, Outputable bdee, Ord bdee) => Outputable (GenStgRhs bndr bdee) instance (Outputable bndr, Outputable bdee, Ord bdee) => Outputable (GenStgExpr bndr bdee) instance (Outputable bndr, Outputable bdee, Ord bdee) => Outputable (GenStgBinding bndr bdee) instance Outputable bdee => Outputable (GenStgArg bdee) instance Outputable UpdateFlag module StgLint lintStgBindings :: String -> [StgBinding] -> [StgBinding] instance Monad LintM module StgStats showStgStats :: [StgBinding] -> String instance Eq CounterType instance Ord CounterType module SRT computeSRTs :: [StgBinding] -> [(StgBinding, [(Id, [Id])])] module PprBase asmSDoc :: SDoc -> Doc pprCLabel_asm :: CLabel -> Doc castFloatToWord8Array :: STUArray s Int Float -> ST s (STUArray s Int Word8) castDoubleToWord8Array :: STUArray s Int Double -> ST s (STUArray s Int Word8) floatToBytes :: Float -> [Int] doubleToBytes :: Double -> [Int] -- | The LLVM Type System. module Llvm.Types -- | A global mutable variable. Maybe defined or external type LMGlobal = (LlvmVar, Maybe LlvmStatic) -- | A String in LLVM type LMString = FastString -- | A type alias type LlvmAlias = (LMString, LlvmType) -- | Llvm Types data LlvmType -- | An integer with a given width in bits. LMInt :: Int -> LlvmType -- | 32 bit floating point LMFloat :: LlvmType -- | 64 bit floating point LMDouble :: LlvmType -- | 80 bit (x86 only) floating point LMFloat80 :: LlvmType -- | 128 bit floating point LMFloat128 :: LlvmType -- | A pointer to a LlvmType LMPointer :: LlvmType -> LlvmType -- | An array of LlvmType LMArray :: Int -> LlvmType -> LlvmType -- | A LlvmVar can represent a label (address) LMLabel :: LlvmType -- | Void type LMVoid :: LlvmType -- | Structure type LMStruct :: [LlvmType] -> LlvmType -- | A type alias LMAlias :: LlvmAlias -> LlvmType -- | Function type, used to create pointers to functions LMFunction :: LlvmFunctionDecl -> LlvmType -- | An LLVM section definition. If Nothing then let LLVM decide the -- section type LMSection = Maybe LMString type LMAlign = Maybe Int type LMConst = Bool -- | Llvm Variables data LlvmVar -- | Variables with a global scope. LMGlobalVar :: LMString -> LlvmType -> LlvmLinkageType -> LMSection -> LMAlign -> LMConst -> LlvmVar -- | Variables local to a function or parameters. LMLocalVar :: Unique -> LlvmType -> LlvmVar -- | Named local variables. Sometimes we need to be able to explicitly name -- variables (e.g for function arguments). LMNLocalVar :: LMString -> LlvmType -> LlvmVar -- | A constant variable LMLitVar :: LlvmLit -> LlvmVar -- | Llvm Literal Data. -- -- These can be used inline in expressions. data LlvmLit -- | Refers to an integer constant (i64 42). LMIntLit :: Integer -> LlvmType -> LlvmLit -- | Floating point literal LMFloatLit :: Double -> LlvmType -> LlvmLit -- | Literal NULL, only applicable to pointer types LMNullLit :: LlvmType -> LlvmLit -- | Undefined value, random bit pattern. Useful for optimisations. LMUndefLit :: LlvmType -> LlvmLit -- | Llvm Static Data. -- -- These represent the possible global level variables and constants. data LlvmStatic -- | A comment in a static section LMComment :: LMString -> LlvmStatic -- | A static variant of a literal value LMStaticLit :: LlvmLit -> LlvmStatic -- | For uninitialised data LMUninitType :: LlvmType -> LlvmStatic -- | Defines a static LMString LMStaticStr :: LMString -> LlvmType -> LlvmStatic -- | A static array LMStaticArray :: [LlvmStatic] -> LlvmType -> LlvmStatic -- | A static structure type LMStaticStruc :: [LlvmStatic] -> LlvmType -> LlvmStatic -- | A pointer to other data LMStaticPointer :: LlvmVar -> LlvmStatic -- | Pointer to Pointer conversion LMBitc :: LlvmStatic -> LlvmType -> LlvmStatic -- | Pointer to Integer conversion LMPtoI :: LlvmStatic -> LlvmType -> LlvmStatic -- | Constant addition operation LMAdd :: LlvmStatic -> LlvmStatic -> LlvmStatic -- | Constant subtraction operation LMSub :: LlvmStatic -> LlvmStatic -> LlvmStatic -- | Concatenate an array together, separated by commas commaCat :: Show a => [a] -> String -- | Concatenate an array together, separated by commas spaceCat :: Show a => [a] -> String -- | Return the variable name or value of the LlvmVar in Llvm IR -- textual representation (e.g. @x, %y or 42). getName :: LlvmVar -> String -- | Return the variable name or value of the LlvmVar in a plain -- textual representation (e.g. x, y or 42). getPlainName :: LlvmVar -> String -- | Print a literal value. No type. getLit :: LlvmLit -> String -- | Return the LlvmType of the LlvmVar getVarType :: LlvmVar -> LlvmType -- | Return the LlvmType of a LlvmLit getLitType :: LlvmLit -> LlvmType -- | Return the LlvmType of the LlvmStatic getStatType :: LlvmStatic -> LlvmType -- | Return the LlvmType of the LMGlobal getGlobalType :: LMGlobal -> LlvmType -- | Return the LlvmVar part of a LMGlobal getGlobalVar :: LMGlobal -> LlvmVar -- | Return the LlvmLinkageType for a LlvmVar getLink :: LlvmVar -> LlvmLinkageType -- | Add a pointer indirection to the supplied type. LMLabel and -- LMVoid cannot be lifted. pLift :: LlvmType -> LlvmType -- | Lower a variable of LMPointer type. pVarLift :: LlvmVar -> LlvmVar -- | Remove the pointer indirection of the supplied type. Only -- LMPointer constructors can be lowered. pLower :: LlvmType -> LlvmType -- | Lower a variable of LMPointer type. pVarLower :: LlvmVar -> LlvmVar -- | Test if the given LlvmType is an integer isInt :: LlvmType -> Bool -- | Test if the given LlvmType is a floating point type isFloat :: LlvmType -> Bool -- | Test if the given LlvmType is an LMPointer construct isPointer :: LlvmType -> Bool -- | Test if a LlvmVar is global. isGlobal :: LlvmVar -> Bool -- | Width in bits of an LlvmType, returns 0 if not applicable llvmWidthInBits :: LlvmType -> Int i64 :: LlvmType i32 :: LlvmType i16 :: LlvmType i8 :: LlvmType i1 :: LlvmType i8Ptr :: LlvmType i128 :: LlvmType -- | The target architectures word size llvmWordPtr :: LlvmType llvmWord :: LlvmType -- | An LLVM Function data LlvmFunctionDecl LlvmFunctionDecl :: LMString -> LlvmLinkageType -> LlvmCallConvention -> LlvmType -> LlvmParameterListType -> [LlvmParameter] -> LMAlign -> LlvmFunctionDecl -- | Unique identifier of the function decName :: LlvmFunctionDecl -> LMString -- | LinkageType of the function funcLinkage :: LlvmFunctionDecl -> LlvmLinkageType -- | The calling convention of the function funcCc :: LlvmFunctionDecl -> LlvmCallConvention -- | Type of the returned value decReturnType :: LlvmFunctionDecl -> LlvmType -- | Indicates if this function uses varargs decVarargs :: LlvmFunctionDecl -> LlvmParameterListType -- | Parameter types and attributes decParams :: LlvmFunctionDecl -> [LlvmParameter] -- | Function align value, must be power of 2 funcAlign :: LlvmFunctionDecl -> LMAlign type LlvmFunctionDecls = [LlvmFunctionDecl] type LlvmParameter = (LlvmType, [LlvmParamAttr]) -- | LLVM Parameter Attributes. -- -- Parameter attributes are used to communicate additional information -- about the result or parameters of a function data LlvmParamAttr -- | This indicates to the code generator that the parameter or return -- value should be zero-extended to a 32-bit value by the caller (for a -- parameter) or the callee (for a return value). ZeroExt :: LlvmParamAttr -- | This indicates to the code generator that the parameter or return -- value should be sign-extended to a 32-bit value by the caller (for a -- parameter) or the callee (for a return value). SignExt :: LlvmParamAttr -- | This indicates that this parameter or return value should be treated -- in a special target-dependent fashion during while emitting code for a -- function call or return (usually, by putting it in a register as -- opposed to memory). InReg :: LlvmParamAttr -- | This indicates that the pointer parameter should really be passed by -- value to the function. ByVal :: LlvmParamAttr -- | This indicates that the pointer parameter specifies the address of a -- structure that is the return value of the function in the source -- program. SRet :: LlvmParamAttr -- | This indicates that the pointer does not alias any global or any other -- parameter. NoAlias :: LlvmParamAttr -- | This indicates that the callee does not make any copies of the pointer -- that outlive the callee itself NoCapture :: LlvmParamAttr -- | This indicates that the pointer parameter can be excised using the -- trampoline intrinsics. Nest :: LlvmParamAttr -- | Llvm Function Attributes. -- -- Function attributes are set to communicate additional information -- about a function. Function attributes are considered to be part of the -- function, not of the function type, so functions with different -- parameter attributes can have the same function type. Functions can -- have multiple attributes. -- -- Descriptions taken from -- http://llvm.org/docs/LangRef.html#fnattrs data LlvmFuncAttr -- | This attribute indicates that the inliner should attempt to inline -- this function into callers whenever possible, ignoring any active -- inlining size threshold for this caller. AlwaysInline :: LlvmFuncAttr -- | This attribute indicates that the source code contained a hint that -- inlining this function is desirable (such as the "inline" keyword in -- C/C++). It is just a hint; it imposes no requirements on the inliner. InlineHint :: LlvmFuncAttr -- | This attribute indicates that the inliner should never inline this -- function in any situation. This attribute may not be used together -- with the alwaysinline attribute. NoInline :: LlvmFuncAttr -- | This attribute suggests that optimization passes and code generator -- passes make choices that keep the code size of this function low, and -- otherwise do optimizations specifically to reduce code size. OptSize :: LlvmFuncAttr -- | This function attribute indicates that the function never returns -- normally. This produces undefined behavior at runtime if the function -- ever does dynamically return. NoReturn :: LlvmFuncAttr -- | This function attribute indicates that the function never returns with -- an unwind or exceptional control flow. If the function does unwind, -- its runtime behavior is undefined. NoUnwind :: LlvmFuncAttr -- | This attribute indicates that the function computes its result (or -- decides to unwind an exception) based strictly on its arguments, -- without dereferencing any pointer arguments or otherwise accessing any -- mutable state (e.g. memory, control registers, etc) visible to caller -- functions. It does not write through any pointer arguments (including -- byval arguments) and never changes any state visible to callers. This -- means that it cannot unwind exceptions by calling the C++ exception -- throwing methods, but could use the unwind instruction. ReadNone :: LlvmFuncAttr -- | This attribute indicates that the function does not write through any -- pointer arguments (including byval arguments) or otherwise modify any -- state (e.g. memory, control registers, etc) visible to caller -- functions. It may dereference pointer arguments and read state that -- may be set in the caller. A readonly function always returns the same -- value (or unwinds an exception identically) when called with the same -- set of arguments and global state. It cannot unwind an exception by -- calling the C++ exception throwing methods, but may use the unwind -- instruction. ReadOnly :: LlvmFuncAttr -- | This attribute indicates that the function should emit a stack -- smashing protector. It is in the form of a "canary"a random value -- placed on the stack before the local variables that's checked upon -- return from the function to see if it has been overwritten. A -- heuristic is used to determine if a function needs stack protectors or -- not. -- -- If a function that has an ssp attribute is inlined into a function -- that doesn't have an ssp attribute, then the resulting function will -- have an ssp attribute. Ssp :: LlvmFuncAttr -- | This attribute indicates that the function should always emit a stack -- smashing protector. This overrides the ssp function attribute. -- -- If a function that has an sspreq attribute is inlined into a function -- that doesn't have an sspreq attribute or which has an ssp attribute, -- then the resulting function will have an sspreq attribute. SspReq :: LlvmFuncAttr -- | This attribute indicates that the code generator should not use a red -- zone, even if the target-specific ABI normally permits it. NoRedZone :: LlvmFuncAttr -- | This attributes disables implicit floating point instructions. NoImplicitFloat :: LlvmFuncAttr -- | This attribute disables prologue / epilogue emission for the function. -- This can have very system-specific consequences. Naked :: LlvmFuncAttr -- | Different types to call a function. data LlvmCallType -- | Normal call, allocate a new stack frame. StdCall :: LlvmCallType -- | Tail call, perform the call in the current stack frame. TailCall :: LlvmCallType -- | Different calling conventions a function can use. data LlvmCallConvention -- | The C calling convention. This calling convention (the default if no -- other calling convention is specified) matches the target C calling -- conventions. This calling convention supports varargs function calls -- and tolerates some mismatch in the declared prototype and implemented -- declaration of the function (as does normal C). CC_Ccc :: LlvmCallConvention -- | This calling convention attempts to make calls as fast as possible -- (e.g. by passing things in registers). This calling convention allows -- the target to use whatever tricks it wants to produce fast code for -- the target, without having to conform to an externally specified ABI -- (Application Binary Interface). Implementations of this convention -- should allow arbitrary tail call optimization to be supported. This -- calling convention does not support varargs and requires the prototype -- of al callees to exactly match the prototype of the function -- definition. CC_Fastcc :: LlvmCallConvention -- | This calling convention attempts to make code in the caller as -- efficient as possible under the assumption that the call is not -- commonly executed. As such, these calls often preserve all registers -- so that the call does not break any live ranges in the caller side. -- This calling convention does not support varargs and requires the -- prototype of all callees to exactly match the prototype of the -- function definition. CC_Coldcc :: LlvmCallConvention -- | Any calling convention may be specified by number, allowing -- target-specific calling conventions to be used. Target specific -- calling conventions start at 64. CC_Ncc :: Int -> LlvmCallConvention -- | X86 Specific StdCall convention. LLVM includes a specific alias -- for it rather than just using CC_Ncc. CC_X86_Stdcc :: LlvmCallConvention -- | Functions can have a fixed amount of parameters, or a variable amount. data LlvmParameterListType FixedArgs :: LlvmParameterListType VarArgs :: LlvmParameterListType -- | Linkage type of a symbol. -- -- The description of the constructors is copied from the Llvm Assembly -- Language Reference Manual -- http://www.llvm.org/docs/LangRef.html#linkage, because they -- correspond to the Llvm linkage types. data LlvmLinkageType -- | Global values with internal linkage are only directly accessible by -- objects in the current module. In particular, linking code into a -- module with an internal global value may cause the internal to be -- renamed as necessary to avoid collisions. Because the symbol is -- internal to the module, all references can be updated. This -- corresponds to the notion of the static keyword in C. Internal :: LlvmLinkageType -- | Globals with linkonce linkage are merged with other globals -- of the same name when linkage occurs. This is typically used to -- implement inline functions, templates, or other code which must be -- generated in each translation unit that uses it. Unreferenced linkonce -- globals are allowed to be discarded. LinkOnce :: LlvmLinkageType -- | weak linkage is exactly the same as linkonce linkage, except -- that unreferenced weak globals may not be discarded. This is used for -- globals that may be emitted in multiple translation units, but that -- are not guaranteed to be emitted into every translation unit that uses -- them. One example of this are common globals in C, such as int -- X; at global scope. Weak :: LlvmLinkageType -- | appending linkage may only be applied to global variables of -- pointer to array type. When two global variables with appending -- linkage are linked together, the two global arrays are appended -- together. This is the Llvm, typesafe, equivalent of having the system -- linker append together sections with identical names when .o -- files are linked. Appending :: LlvmLinkageType -- | The semantics of this linkage follow the ELF model: the symbol is weak -- until linked, if not linked, the symbol becomes null instead of being -- an undefined reference. ExternWeak :: LlvmLinkageType -- | The symbol participates in linkage and can be used to resolve external -- symbol references. ExternallyVisible :: LlvmLinkageType -- | Alias for ExternallyVisible but with explicit textual form in -- LLVM assembly. External :: LlvmLinkageType -- | Llvm binary operators machine operations. data LlvmMachOp -- | add two integer, floating point or vector values. LM_MO_Add :: LlvmMachOp -- | subtract two ... LM_MO_Sub :: LlvmMachOp -- | multiply .. LM_MO_Mul :: LlvmMachOp -- | unsigned integer or vector division. LM_MO_UDiv :: LlvmMachOp -- | signed integer .. LM_MO_SDiv :: LlvmMachOp -- | unsigned integer or vector remainder (mod) LM_MO_URem :: LlvmMachOp -- | signed ... LM_MO_SRem :: LlvmMachOp -- | add two floating point or vector values. LM_MO_FAdd :: LlvmMachOp -- | subtract two ... LM_MO_FSub :: LlvmMachOp -- | multiply ... LM_MO_FMul :: LlvmMachOp -- | divide ... LM_MO_FDiv :: LlvmMachOp -- | remainder ... LM_MO_FRem :: LlvmMachOp -- | Left shift LM_MO_Shl :: LlvmMachOp -- | Logical shift right Shift right, filling with zero LM_MO_LShr :: LlvmMachOp -- | Arithmetic shift right The most significant bits of the result will be -- equal to the sign bit of the left operand. LM_MO_AShr :: LlvmMachOp -- | AND bitwise logical operation. LM_MO_And :: LlvmMachOp -- | OR bitwise logical operation. LM_MO_Or :: LlvmMachOp -- | XOR bitwise logical operation. LM_MO_Xor :: LlvmMachOp -- | Llvm compare operations. data LlvmCmpOp -- | Equal (Signed and Unsigned) LM_CMP_Eq :: LlvmCmpOp -- | Not equal (Signed and Unsigned) LM_CMP_Ne :: LlvmCmpOp -- | Unsigned greater than LM_CMP_Ugt :: LlvmCmpOp -- | Unsigned greater than or equal LM_CMP_Uge :: LlvmCmpOp -- | Unsigned less than LM_CMP_Ult :: LlvmCmpOp -- | Unsigned less than or equal LM_CMP_Ule :: LlvmCmpOp -- | Signed greater than LM_CMP_Sgt :: LlvmCmpOp -- | Signed greater than or equal LM_CMP_Sge :: LlvmCmpOp -- | Signed less than LM_CMP_Slt :: LlvmCmpOp -- | Signed less than or equal LM_CMP_Sle :: LlvmCmpOp -- | Float equal LM_CMP_Feq :: LlvmCmpOp -- | Float not equal LM_CMP_Fne :: LlvmCmpOp -- | Float greater than LM_CMP_Fgt :: LlvmCmpOp -- | Float greater than or equal LM_CMP_Fge :: LlvmCmpOp -- | Float less than LM_CMP_Flt :: LlvmCmpOp -- | Float less than or equal LM_CMP_Fle :: LlvmCmpOp -- | Llvm cast operations. data LlvmCastOp -- | Integer truncate LM_Trunc :: LlvmCastOp -- | Integer extend (zero fill) LM_Zext :: LlvmCastOp -- | Integer extend (sign fill) LM_Sext :: LlvmCastOp -- | Float truncate LM_Fptrunc :: LlvmCastOp -- | Float extend LM_Fpext :: LlvmCastOp -- | Float to unsigned Integer LM_Fptoui :: LlvmCastOp -- | Float to signed Integer LM_Fptosi :: LlvmCastOp -- | Unsigned Integer to Float LM_Uitofp :: LlvmCastOp -- | Signed Int to Float LM_Sitofp :: LlvmCastOp -- | Pointer to Integer LM_Ptrtoint :: LlvmCastOp -- | Integer to Pointer LM_Inttoptr :: LlvmCastOp -- | Cast between types where no bit manipulation is needed LM_Bitcast :: LlvmCastOp -- | Convert a Haskell Double to an LLVM hex encoded floating point form. -- In Llvm float literals can be printed in a big-endian hexadecimal -- format, regardless of underlying architecture. dToStr :: Double -> String -- | Convert a Haskell Float to an LLVM hex encoded floating point form. -- LLVM uses the same encoding for both floats and doubles (16 digit hex -- string) but floats must have the last half all zeroes so it can fit -- into a float size type. fToStr :: Float -> String -- | Reverse or leave byte data alone to fix endianness on this target. fixEndian :: [a] -> [a] instance Eq LlvmParamAttr instance Eq LlvmFuncAttr instance Eq LlvmCallType instance Show LlvmCallType instance Eq LlvmCallConvention instance Eq LlvmParameterListType instance Show LlvmParameterListType instance Eq LlvmLinkageType instance Eq LlvmFunctionDecl instance Eq LlvmType instance Eq LlvmLit instance Eq LlvmVar instance Eq LlvmMachOp instance Eq LlvmCmpOp instance Eq LlvmCastOp instance Show LlvmCastOp instance Show LlvmCmpOp instance Show LlvmMachOp instance Show LlvmLinkageType instance Show LlvmCallConvention instance Show LlvmFuncAttr instance Show LlvmParamAttr instance Show LlvmFunctionDecl instance Show LlvmStatic instance Show LlvmLit instance Show LlvmVar instance Show LlvmType -- | The LLVM abstract syntax. module Llvm.AbsSyn -- | Block labels type LlvmBlockId = Unique -- | A block of LLVM code. data LlvmBlock LlvmBlock :: LlvmBlockId -> [LlvmStatement] -> LlvmBlock -- | The code label for this block blockLabel :: LlvmBlock -> LlvmBlockId -- | A list of LlvmStatement's representing the code for this block. This -- list must end with a control flow statement. blockStmts :: LlvmBlock -> [LlvmStatement] type LlvmBlocks = [LlvmBlock] -- | An LLVM Module. This is a top level container in LLVM. data LlvmModule LlvmModule :: [LMString] -> [LlvmAlias] -> [LMGlobal] -> LlvmFunctionDecls -> LlvmFunctions -> LlvmModule -- | Comments to include at the start of the module. modComments :: LlvmModule -> [LMString] -- | LLVM Alias type definitions. modAliases :: LlvmModule -> [LlvmAlias] -- | Global variables to include in the module. modGlobals :: LlvmModule -> [LMGlobal] -- | LLVM Functions used in this module but defined in other modules. modFwdDecls :: LlvmModule -> LlvmFunctionDecls -- | LLVM Functions defined in this module. modFuncs :: LlvmModule -> LlvmFunctions -- | An LLVM Function data LlvmFunction LlvmFunction :: LlvmFunctionDecl -> [LMString] -> [LlvmFuncAttr] -> LMSection -> LlvmBlocks -> LlvmFunction -- | The signature of this declared function. funcDecl :: LlvmFunction -> LlvmFunctionDecl -- | The functions arguments funcArgs :: LlvmFunction -> [LMString] -- | The function attributes. funcAttrs :: LlvmFunction -> [LlvmFuncAttr] -- | The section to put the function into, funcSect :: LlvmFunction -> LMSection -- | The body of the functions. funcBody :: LlvmFunction -> LlvmBlocks type LlvmFunctions = [LlvmFunction] -- | Llvm Statements data LlvmStatement -- | Assign an expression to an variable: * dest: Variable to assign to * -- source: Source expression Assignment :: LlvmVar -> LlvmExpression -> LlvmStatement -- | Always branch to the target label Branch :: LlvmVar -> LlvmStatement -- | Branch to label targetTrue if cond is true otherwise to label -- targetFalse * cond: condition that will be tested, must be of type i1 -- * targetTrue: label to branch to if cond is true * targetFalse: label -- to branch to if cond is false BranchIf :: LlvmVar -> LlvmVar -> LlvmVar -> LlvmStatement -- | Comment Plain comment. Comment :: [LMString] -> LlvmStatement -- | Set a label on this position. * name: Identifier of this label, unique -- for this module MkLabel :: LlvmBlockId -> LlvmStatement -- | Store variable value in pointer ptr. If value is of type t then ptr -- must be of type t*. * value: Variable/Constant to store. * ptr: -- Location to store the value in Store :: LlvmVar -> LlvmVar -> LlvmStatement -- | Mutliway branch * scrutinee: Variable or constant which must be of -- integer type that is determines which arm is chosen. * def: The -- default label if there is no match in target. * target: A list of -- (value,label) where the value is an integer constant and label the -- corresponding label to jump to if the scrutinee matches the value. Switch :: LlvmVar -> LlvmVar -> [(LlvmVar, LlvmVar)] -> LlvmStatement -- | Return a result. * result: The variable or constant to return Return :: (Maybe LlvmVar) -> LlvmStatement -- | An instruction for the optimizer that the code following is not -- reachable Unreachable :: LlvmStatement -- | Raise an expression to a statement (if don't want result or want to -- use Llvm unnamed values. Expr :: LlvmExpression -> LlvmStatement -- | Llvm Expressions data LlvmExpression -- | Allocate amount * sizeof(tp) bytes on the stack * tp: LlvmType to -- reserve room for * amount: The nr of tp's which must be allocated Alloca :: LlvmType -> Int -> LlvmExpression -- | Perform the machine operator op on the operands left and right * op: -- operator * left: left operand * right: right operand LlvmOp :: LlvmMachOp -> LlvmVar -> LlvmVar -> LlvmExpression -- | Perform a compare operation on the operands left and right * op: -- operator * left: left operand * right: right operand Compare :: LlvmCmpOp -> LlvmVar -> LlvmVar -> LlvmExpression -- | Allocate amount * sizeof(tp) bytes on the heap * tp: LlvmType to -- reserve room for * amount: The nr of tp's which must be allocated Malloc :: LlvmType -> Int -> LlvmExpression -- | Load the value at location ptr Load :: LlvmVar -> LlvmExpression -- | Navigate in an structure, selecting elements * inbound: Is the pointer -- inbounds? (computed pointer doesn't overflow) * ptr: Location of the -- structure * indexes: A list of indexes to select the correct value. GetElemPtr :: Bool -> LlvmVar -> [LlvmVar] -> LlvmExpression -- | Cast the variable from to the to type. This is an abstraction of three -- cast operators in Llvm, inttoptr, prttoint and bitcast. * cast: Cast -- type * from: Variable to cast * to: type to cast to Cast :: LlvmCastOp -> LlvmVar -> LlvmType -> LlvmExpression -- | Call a function. The result is the value of the expression. * -- tailJumps: CallType to signal if the function should be tail called * -- fnptrval: An LLVM value containing a pointer to a function to be -- invoked. Can be indirect. Should be LMFunction type. * args: Concrete -- arguments for the parameters * attrs: A list of function attributes -- for the call. Only NoReturn, NoUnwind, ReadOnly and ReadNone are valid -- here. Call :: LlvmCallType -> LlvmVar -> [LlvmVar] -> [LlvmFuncAttr] -> LlvmExpression -- | Merge variables from different basic blocks which are predecessors of -- this basic block in a new variable of type tp. * tp: type of the -- merged variable, must match the types of the predecessor variables. * -- precessors: A list of variables and the basic block that they -- originate from. Phi :: LlvmType -> [(LlvmVar, LlvmVar)] -> LlvmExpression -- | Inline assembly expression. Syntax is very similar to the style used -- by GCC. * assembly: Actual inline assembly code. * contraints: Operand -- constraints. * return ty: Return type of function. * vars: Any -- variables involved in the assembly code. * sideeffect: Does the -- expression have side effects not visible from the constraints list. * -- alignstack: Should the stack be conservatively aligned before this -- expression is executed. Asm :: LMString -> LMString -> LlvmType -> [LlvmVar] -> Bool -> Bool -> LlvmExpression instance Show LlvmExpression instance Eq LlvmExpression instance Show LlvmStatement instance Eq LlvmStatement -- | Pretty print LLVM IR Code. module Llvm.PpLlvm -- | Print out a whole LLVM module. ppLlvmModule :: LlvmModule -> Doc -- | Print out a multi-line comment, can be inside a function or on its own ppLlvmComments :: [LMString] -> Doc -- | Print out a comment, can be inside a function or on its own ppLlvmComment :: LMString -> Doc -- | Print out a list of global mutable variable definitions ppLlvmGlobals :: [LMGlobal] -> Doc -- | Print out a global mutable variable definition ppLlvmGlobal :: LMGlobal -> Doc -- | Print out an LLVM type alias. ppLlvmAlias :: LlvmAlias -> Doc -- | Print out a list of LLVM type aliases. ppLlvmAliases :: [LlvmAlias] -> Doc -- | Print out a list of function declaration. ppLlvmFunctionDecls :: LlvmFunctionDecls -> Doc -- | Print out a function declaration. Declarations define the function -- type but don't define the actual body of the function. ppLlvmFunctionDecl :: LlvmFunctionDecl -> Doc -- | Print out a list of function definitions. ppLlvmFunctions :: LlvmFunctions -> Doc -- | Print out a function definition. ppLlvmFunction :: LlvmFunction -> Doc -- | Convert SDoc to Doc llvmSDoc :: SDoc -> Doc -- | This module supplies bindings to generate Llvm IR from Haskell -- (http://www.llvm.org/docs/LangRef.html). -- -- Note: this module is developed in a demand driven way. It is no -- complete LLVM binding library in Haskell, but enough to generate code -- for GHC. -- -- This code is derived from code taken from the Essential Haskell -- Compiler (EHC) project (http://www.cs.uu.nl/wiki/Ehc/WebHome). module Llvm -- | An LLVM Module. This is a top level container in LLVM. data LlvmModule LlvmModule :: [LMString] -> [LlvmAlias] -> [LMGlobal] -> LlvmFunctionDecls -> LlvmFunctions -> LlvmModule -- | Comments to include at the start of the module. modComments :: LlvmModule -> [LMString] -- | LLVM Alias type definitions. modAliases :: LlvmModule -> [LlvmAlias] -- | Global variables to include in the module. modGlobals :: LlvmModule -> [LMGlobal] -- | LLVM Functions used in this module but defined in other modules. modFwdDecls :: LlvmModule -> LlvmFunctionDecls -- | LLVM Functions defined in this module. modFuncs :: LlvmModule -> LlvmFunctions -- | An LLVM Function data LlvmFunction LlvmFunction :: LlvmFunctionDecl -> [LMString] -> [LlvmFuncAttr] -> LMSection -> LlvmBlocks -> LlvmFunction -- | The signature of this declared function. funcDecl :: LlvmFunction -> LlvmFunctionDecl -- | The functions arguments funcArgs :: LlvmFunction -> [LMString] -- | The function attributes. funcAttrs :: LlvmFunction -> [LlvmFuncAttr] -- | The section to put the function into, funcSect :: LlvmFunction -> LMSection -- | The body of the functions. funcBody :: LlvmFunction -> LlvmBlocks -- | An LLVM Function data LlvmFunctionDecl LlvmFunctionDecl :: LMString -> LlvmLinkageType -> LlvmCallConvention -> LlvmType -> LlvmParameterListType -> [LlvmParameter] -> LMAlign -> LlvmFunctionDecl -- | Unique identifier of the function decName :: LlvmFunctionDecl -> LMString -- | LinkageType of the function funcLinkage :: LlvmFunctionDecl -> LlvmLinkageType -- | The calling convention of the function funcCc :: LlvmFunctionDecl -> LlvmCallConvention -- | Type of the returned value decReturnType :: LlvmFunctionDecl -> LlvmType -- | Indicates if this function uses varargs decVarargs :: LlvmFunctionDecl -> LlvmParameterListType -- | Parameter types and attributes decParams :: LlvmFunctionDecl -> [LlvmParameter] -- | Function align value, must be power of 2 funcAlign :: LlvmFunctionDecl -> LMAlign type LlvmFunctions = [LlvmFunction] type LlvmFunctionDecls = [LlvmFunctionDecl] -- | Llvm Statements data LlvmStatement -- | Assign an expression to an variable: * dest: Variable to assign to * -- source: Source expression Assignment :: LlvmVar -> LlvmExpression -> LlvmStatement -- | Always branch to the target label Branch :: LlvmVar -> LlvmStatement -- | Branch to label targetTrue if cond is true otherwise to label -- targetFalse * cond: condition that will be tested, must be of type i1 -- * targetTrue: label to branch to if cond is true * targetFalse: label -- to branch to if cond is false BranchIf :: LlvmVar -> LlvmVar -> LlvmVar -> LlvmStatement -- | Comment Plain comment. Comment :: [LMString] -> LlvmStatement -- | Set a label on this position. * name: Identifier of this label, unique -- for this module MkLabel :: LlvmBlockId -> LlvmStatement -- | Store variable value in pointer ptr. If value is of type t then ptr -- must be of type t*. * value: Variable/Constant to store. * ptr: -- Location to store the value in Store :: LlvmVar -> LlvmVar -> LlvmStatement -- | Mutliway branch * scrutinee: Variable or constant which must be of -- integer type that is determines which arm is chosen. * def: The -- default label if there is no match in target. * target: A list of -- (value,label) where the value is an integer constant and label the -- corresponding label to jump to if the scrutinee matches the value. Switch :: LlvmVar -> LlvmVar -> [(LlvmVar, LlvmVar)] -> LlvmStatement -- | Return a result. * result: The variable or constant to return Return :: (Maybe LlvmVar) -> LlvmStatement -- | An instruction for the optimizer that the code following is not -- reachable Unreachable :: LlvmStatement -- | Raise an expression to a statement (if don't want result or want to -- use Llvm unnamed values. Expr :: LlvmExpression -> LlvmStatement -- | Llvm Expressions data LlvmExpression -- | Allocate amount * sizeof(tp) bytes on the stack * tp: LlvmType to -- reserve room for * amount: The nr of tp's which must be allocated Alloca :: LlvmType -> Int -> LlvmExpression -- | Perform the machine operator op on the operands left and right * op: -- operator * left: left operand * right: right operand LlvmOp :: LlvmMachOp -> LlvmVar -> LlvmVar -> LlvmExpression -- | Perform a compare operation on the operands left and right * op: -- operator * left: left operand * right: right operand Compare :: LlvmCmpOp -> LlvmVar -> LlvmVar -> LlvmExpression -- | Allocate amount * sizeof(tp) bytes on the heap * tp: LlvmType to -- reserve room for * amount: The nr of tp's which must be allocated Malloc :: LlvmType -> Int -> LlvmExpression -- | Load the value at location ptr Load :: LlvmVar -> LlvmExpression -- | Navigate in an structure, selecting elements * inbound: Is the pointer -- inbounds? (computed pointer doesn't overflow) * ptr: Location of the -- structure * indexes: A list of indexes to select the correct value. GetElemPtr :: Bool -> LlvmVar -> [LlvmVar] -> LlvmExpression -- | Cast the variable from to the to type. This is an abstraction of three -- cast operators in Llvm, inttoptr, prttoint and bitcast. * cast: Cast -- type * from: Variable to cast * to: type to cast to Cast :: LlvmCastOp -> LlvmVar -> LlvmType -> LlvmExpression -- | Call a function. The result is the value of the expression. * -- tailJumps: CallType to signal if the function should be tail called * -- fnptrval: An LLVM value containing a pointer to a function to be -- invoked. Can be indirect. Should be LMFunction type. * args: Concrete -- arguments for the parameters * attrs: A list of function attributes -- for the call. Only NoReturn, NoUnwind, ReadOnly and ReadNone are valid -- here. Call :: LlvmCallType -> LlvmVar -> [LlvmVar] -> [LlvmFuncAttr] -> LlvmExpression -- | Merge variables from different basic blocks which are predecessors of -- this basic block in a new variable of type tp. * tp: type of the -- merged variable, must match the types of the predecessor variables. * -- precessors: A list of variables and the basic block that they -- originate from. Phi :: LlvmType -> [(LlvmVar, LlvmVar)] -> LlvmExpression -- | Inline assembly expression. Syntax is very similar to the style used -- by GCC. * assembly: Actual inline assembly code. * contraints: Operand -- constraints. * return ty: Return type of function. * vars: Any -- variables involved in the assembly code. * sideeffect: Does the -- expression have side effects not visible from the constraints list. * -- alignstack: Should the stack be conservatively aligned before this -- expression is executed. Asm :: LMString -> LMString -> LlvmType -> [LlvmVar] -> Bool -> Bool -> LlvmExpression type LlvmBlocks = [LlvmBlock] -- | A block of LLVM code. data LlvmBlock LlvmBlock :: LlvmBlockId -> [LlvmStatement] -> LlvmBlock -- | The code label for this block blockLabel :: LlvmBlock -> LlvmBlockId -- | A list of LlvmStatement's representing the code for this block. This -- list must end with a control flow statement. blockStmts :: LlvmBlock -> [LlvmStatement] -- | Block labels type LlvmBlockId = Unique -- | LLVM Parameter Attributes. -- -- Parameter attributes are used to communicate additional information -- about the result or parameters of a function data LlvmParamAttr -- | This indicates to the code generator that the parameter or return -- value should be zero-extended to a 32-bit value by the caller (for a -- parameter) or the callee (for a return value). ZeroExt :: LlvmParamAttr -- | This indicates to the code generator that the parameter or return -- value should be sign-extended to a 32-bit value by the caller (for a -- parameter) or the callee (for a return value). SignExt :: LlvmParamAttr -- | This indicates that this parameter or return value should be treated -- in a special target-dependent fashion during while emitting code for a -- function call or return (usually, by putting it in a register as -- opposed to memory). InReg :: LlvmParamAttr -- | This indicates that the pointer parameter should really be passed by -- value to the function. ByVal :: LlvmParamAttr -- | This indicates that the pointer parameter specifies the address of a -- structure that is the return value of the function in the source -- program. SRet :: LlvmParamAttr -- | This indicates that the pointer does not alias any global or any other -- parameter. NoAlias :: LlvmParamAttr -- | This indicates that the callee does not make any copies of the pointer -- that outlive the callee itself NoCapture :: LlvmParamAttr -- | This indicates that the pointer parameter can be excised using the -- trampoline intrinsics. Nest :: LlvmParamAttr type LlvmParameter = (LlvmType, [LlvmParamAttr]) -- | Different calling conventions a function can use. data LlvmCallConvention -- | The C calling convention. This calling convention (the default if no -- other calling convention is specified) matches the target C calling -- conventions. This calling convention supports varargs function calls -- and tolerates some mismatch in the declared prototype and implemented -- declaration of the function (as does normal C). CC_Ccc :: LlvmCallConvention -- | This calling convention attempts to make calls as fast as possible -- (e.g. by passing things in registers). This calling convention allows -- the target to use whatever tricks it wants to produce fast code for -- the target, without having to conform to an externally specified ABI -- (Application Binary Interface). Implementations of this convention -- should allow arbitrary tail call optimization to be supported. This -- calling convention does not support varargs and requires the prototype -- of al callees to exactly match the prototype of the function -- definition. CC_Fastcc :: LlvmCallConvention -- | This calling convention attempts to make code in the caller as -- efficient as possible under the assumption that the call is not -- commonly executed. As such, these calls often preserve all registers -- so that the call does not break any live ranges in the caller side. -- This calling convention does not support varargs and requires the -- prototype of all callees to exactly match the prototype of the -- function definition. CC_Coldcc :: LlvmCallConvention -- | Any calling convention may be specified by number, allowing -- target-specific calling conventions to be used. Target specific -- calling conventions start at 64. CC_Ncc :: Int -> LlvmCallConvention -- | X86 Specific StdCall convention. LLVM includes a specific alias -- for it rather than just using CC_Ncc. CC_X86_Stdcc :: LlvmCallConvention -- | Different types to call a function. data LlvmCallType -- | Normal call, allocate a new stack frame. StdCall :: LlvmCallType -- | Tail call, perform the call in the current stack frame. TailCall :: LlvmCallType -- | Functions can have a fixed amount of parameters, or a variable amount. data LlvmParameterListType FixedArgs :: LlvmParameterListType VarArgs :: LlvmParameterListType -- | Linkage type of a symbol. -- -- The description of the constructors is copied from the Llvm Assembly -- Language Reference Manual -- http://www.llvm.org/docs/LangRef.html#linkage, because they -- correspond to the Llvm linkage types. data LlvmLinkageType -- | Global values with internal linkage are only directly accessible by -- objects in the current module. In particular, linking code into a -- module with an internal global value may cause the internal to be -- renamed as necessary to avoid collisions. Because the symbol is -- internal to the module, all references can be updated. This -- corresponds to the notion of the static keyword in C. Internal :: LlvmLinkageType -- | Globals with linkonce linkage are merged with other globals -- of the same name when linkage occurs. This is typically used to -- implement inline functions, templates, or other code which must be -- generated in each translation unit that uses it. Unreferenced linkonce -- globals are allowed to be discarded. LinkOnce :: LlvmLinkageType -- | weak linkage is exactly the same as linkonce linkage, except -- that unreferenced weak globals may not be discarded. This is used for -- globals that may be emitted in multiple translation units, but that -- are not guaranteed to be emitted into every translation unit that uses -- them. One example of this are common globals in C, such as int -- X; at global scope. Weak :: LlvmLinkageType -- | appending linkage may only be applied to global variables of -- pointer to array type. When two global variables with appending -- linkage are linked together, the two global arrays are appended -- together. This is the Llvm, typesafe, equivalent of having the system -- linker append together sections with identical names when .o -- files are linked. Appending :: LlvmLinkageType -- | The semantics of this linkage follow the ELF model: the symbol is weak -- until linked, if not linked, the symbol becomes null instead of being -- an undefined reference. ExternWeak :: LlvmLinkageType -- | The symbol participates in linkage and can be used to resolve external -- symbol references. ExternallyVisible :: LlvmLinkageType -- | Alias for ExternallyVisible but with explicit textual form in -- LLVM assembly. External :: LlvmLinkageType -- | Llvm Function Attributes. -- -- Function attributes are set to communicate additional information -- about a function. Function attributes are considered to be part of the -- function, not of the function type, so functions with different -- parameter attributes can have the same function type. Functions can -- have multiple attributes. -- -- Descriptions taken from -- http://llvm.org/docs/LangRef.html#fnattrs data LlvmFuncAttr -- | This attribute indicates that the inliner should attempt to inline -- this function into callers whenever possible, ignoring any active -- inlining size threshold for this caller. AlwaysInline :: LlvmFuncAttr -- | This attribute indicates that the source code contained a hint that -- inlining this function is desirable (such as the "inline" keyword in -- C/C++). It is just a hint; it imposes no requirements on the inliner. InlineHint :: LlvmFuncAttr -- | This attribute indicates that the inliner should never inline this -- function in any situation. This attribute may not be used together -- with the alwaysinline attribute. NoInline :: LlvmFuncAttr -- | This attribute suggests that optimization passes and code generator -- passes make choices that keep the code size of this function low, and -- otherwise do optimizations specifically to reduce code size. OptSize :: LlvmFuncAttr -- | This function attribute indicates that the function never returns -- normally. This produces undefined behavior at runtime if the function -- ever does dynamically return. NoReturn :: LlvmFuncAttr -- | This function attribute indicates that the function never returns with -- an unwind or exceptional control flow. If the function does unwind, -- its runtime behavior is undefined. NoUnwind :: LlvmFuncAttr -- | This attribute indicates that the function computes its result (or -- decides to unwind an exception) based strictly on its arguments, -- without dereferencing any pointer arguments or otherwise accessing any -- mutable state (e.g. memory, control registers, etc) visible to caller -- functions. It does not write through any pointer arguments (including -- byval arguments) and never changes any state visible to callers. This -- means that it cannot unwind exceptions by calling the C++ exception -- throwing methods, but could use the unwind instruction. ReadNone :: LlvmFuncAttr -- | This attribute indicates that the function does not write through any -- pointer arguments (including byval arguments) or otherwise modify any -- state (e.g. memory, control registers, etc) visible to caller -- functions. It may dereference pointer arguments and read state that -- may be set in the caller. A readonly function always returns the same -- value (or unwinds an exception identically) when called with the same -- set of arguments and global state. It cannot unwind an exception by -- calling the C++ exception throwing methods, but may use the unwind -- instruction. ReadOnly :: LlvmFuncAttr -- | This attribute indicates that the function should emit a stack -- smashing protector. It is in the form of a "canary"a random value -- placed on the stack before the local variables that's checked upon -- return from the function to see if it has been overwritten. A -- heuristic is used to determine if a function needs stack protectors or -- not. -- -- If a function that has an ssp attribute is inlined into a function -- that doesn't have an ssp attribute, then the resulting function will -- have an ssp attribute. Ssp :: LlvmFuncAttr -- | This attribute indicates that the function should always emit a stack -- smashing protector. This overrides the ssp function attribute. -- -- If a function that has an sspreq attribute is inlined into a function -- that doesn't have an sspreq attribute or which has an ssp attribute, -- then the resulting function will have an sspreq attribute. SspReq :: LlvmFuncAttr -- | This attribute indicates that the code generator should not use a red -- zone, even if the target-specific ABI normally permits it. NoRedZone :: LlvmFuncAttr -- | This attributes disables implicit floating point instructions. NoImplicitFloat :: LlvmFuncAttr -- | This attribute disables prologue / epilogue emission for the function. -- This can have very system-specific consequences. Naked :: LlvmFuncAttr -- | Llvm compare operations. data LlvmCmpOp -- | Equal (Signed and Unsigned) LM_CMP_Eq :: LlvmCmpOp -- | Not equal (Signed and Unsigned) LM_CMP_Ne :: LlvmCmpOp -- | Unsigned greater than LM_CMP_Ugt :: LlvmCmpOp -- | Unsigned greater than or equal LM_CMP_Uge :: LlvmCmpOp -- | Unsigned less than LM_CMP_Ult :: LlvmCmpOp -- | Unsigned less than or equal LM_CMP_Ule :: LlvmCmpOp -- | Signed greater than LM_CMP_Sgt :: LlvmCmpOp -- | Signed greater than or equal LM_CMP_Sge :: LlvmCmpOp -- | Signed less than LM_CMP_Slt :: LlvmCmpOp -- | Signed less than or equal LM_CMP_Sle :: LlvmCmpOp -- | Float equal LM_CMP_Feq :: LlvmCmpOp -- | Float not equal LM_CMP_Fne :: LlvmCmpOp -- | Float greater than LM_CMP_Fgt :: LlvmCmpOp -- | Float greater than or equal LM_CMP_Fge :: LlvmCmpOp -- | Float less than LM_CMP_Flt :: LlvmCmpOp -- | Float less than or equal LM_CMP_Fle :: LlvmCmpOp -- | Llvm binary operators machine operations. data LlvmMachOp -- | add two integer, floating point or vector values. LM_MO_Add :: LlvmMachOp -- | subtract two ... LM_MO_Sub :: LlvmMachOp -- | multiply .. LM_MO_Mul :: LlvmMachOp -- | unsigned integer or vector division. LM_MO_UDiv :: LlvmMachOp -- | signed integer .. LM_MO_SDiv :: LlvmMachOp -- | unsigned integer or vector remainder (mod) LM_MO_URem :: LlvmMachOp -- | signed ... LM_MO_SRem :: LlvmMachOp -- | add two floating point or vector values. LM_MO_FAdd :: LlvmMachOp -- | subtract two ... LM_MO_FSub :: LlvmMachOp -- | multiply ... LM_MO_FMul :: LlvmMachOp -- | divide ... LM_MO_FDiv :: LlvmMachOp -- | remainder ... LM_MO_FRem :: LlvmMachOp -- | Left shift LM_MO_Shl :: LlvmMachOp -- | Logical shift right Shift right, filling with zero LM_MO_LShr :: LlvmMachOp -- | Arithmetic shift right The most significant bits of the result will be -- equal to the sign bit of the left operand. LM_MO_AShr :: LlvmMachOp -- | AND bitwise logical operation. LM_MO_And :: LlvmMachOp -- | OR bitwise logical operation. LM_MO_Or :: LlvmMachOp -- | XOR bitwise logical operation. LM_MO_Xor :: LlvmMachOp -- | Llvm cast operations. data LlvmCastOp -- | Integer truncate LM_Trunc :: LlvmCastOp -- | Integer extend (zero fill) LM_Zext :: LlvmCastOp -- | Integer extend (sign fill) LM_Sext :: LlvmCastOp -- | Float truncate LM_Fptrunc :: LlvmCastOp -- | Float extend LM_Fpext :: LlvmCastOp -- | Float to unsigned Integer LM_Fptoui :: LlvmCastOp -- | Float to signed Integer LM_Fptosi :: LlvmCastOp -- | Unsigned Integer to Float LM_Uitofp :: LlvmCastOp -- | Signed Int to Float LM_Sitofp :: LlvmCastOp -- | Pointer to Integer LM_Ptrtoint :: LlvmCastOp -- | Integer to Pointer LM_Inttoptr :: LlvmCastOp -- | Cast between types where no bit manipulation is needed LM_Bitcast :: LlvmCastOp -- | Llvm Variables data LlvmVar -- | Variables with a global scope. LMGlobalVar :: LMString -> LlvmType -> LlvmLinkageType -> LMSection -> LMAlign -> LMConst -> LlvmVar -- | Variables local to a function or parameters. LMLocalVar :: Unique -> LlvmType -> LlvmVar -- | Named local variables. Sometimes we need to be able to explicitly name -- variables (e.g for function arguments). LMNLocalVar :: LMString -> LlvmType -> LlvmVar -- | A constant variable LMLitVar :: LlvmLit -> LlvmVar -- | Llvm Static Data. -- -- These represent the possible global level variables and constants. data LlvmStatic -- | A comment in a static section LMComment :: LMString -> LlvmStatic -- | A static variant of a literal value LMStaticLit :: LlvmLit -> LlvmStatic -- | For uninitialised data LMUninitType :: LlvmType -> LlvmStatic -- | Defines a static LMString LMStaticStr :: LMString -> LlvmType -> LlvmStatic -- | A static array LMStaticArray :: [LlvmStatic] -> LlvmType -> LlvmStatic -- | A static structure type LMStaticStruc :: [LlvmStatic] -> LlvmType -> LlvmStatic -- | A pointer to other data LMStaticPointer :: LlvmVar -> LlvmStatic -- | Pointer to Pointer conversion LMBitc :: LlvmStatic -> LlvmType -> LlvmStatic -- | Pointer to Integer conversion LMPtoI :: LlvmStatic -> LlvmType -> LlvmStatic -- | Constant addition operation LMAdd :: LlvmStatic -> LlvmStatic -> LlvmStatic -- | Constant subtraction operation LMSub :: LlvmStatic -> LlvmStatic -> LlvmStatic -- | Llvm Literal Data. -- -- These can be used inline in expressions. data LlvmLit -- | Refers to an integer constant (i64 42). LMIntLit :: Integer -> LlvmType -> LlvmLit -- | Floating point literal LMFloatLit :: Double -> LlvmType -> LlvmLit -- | Literal NULL, only applicable to pointer types LMNullLit :: LlvmType -> LlvmLit -- | Undefined value, random bit pattern. Useful for optimisations. LMUndefLit :: LlvmType -> LlvmLit -- | Llvm Types data LlvmType -- | An integer with a given width in bits. LMInt :: Int -> LlvmType -- | 32 bit floating point LMFloat :: LlvmType -- | 64 bit floating point LMDouble :: LlvmType -- | 80 bit (x86 only) floating point LMFloat80 :: LlvmType -- | 128 bit floating point LMFloat128 :: LlvmType -- | A pointer to a LlvmType LMPointer :: LlvmType -> LlvmType -- | An array of LlvmType LMArray :: Int -> LlvmType -> LlvmType -- | A LlvmVar can represent a label (address) LMLabel :: LlvmType -- | Void type LMVoid :: LlvmType -- | Structure type LMStruct :: [LlvmType] -> LlvmType -- | A type alias LMAlias :: LlvmAlias -> LlvmType -- | Function type, used to create pointers to functions LMFunction :: LlvmFunctionDecl -> LlvmType -- | A type alias type LlvmAlias = (LMString, LlvmType) -- | A global mutable variable. Maybe defined or external type LMGlobal = (LlvmVar, Maybe LlvmStatic) -- | A String in LLVM type LMString = FastString -- | An LLVM section definition. If Nothing then let LLVM decide the -- section type LMSection = Maybe LMString type LMAlign = Maybe Int i64 :: LlvmType i32 :: LlvmType i16 :: LlvmType i8 :: LlvmType i1 :: LlvmType i8Ptr :: LlvmType llvmWord :: LlvmType -- | The target architectures word size llvmWordPtr :: LlvmType -- | Test if a LlvmVar is global. isGlobal :: LlvmVar -> Bool -- | Return the LlvmType of a LlvmLit getLitType :: LlvmLit -> LlvmType -- | Print a literal value. No type. getLit :: LlvmLit -> String -- | Return the variable name or value of the LlvmVar in Llvm IR -- textual representation (e.g. @x, %y or 42). getName :: LlvmVar -> String -- | Return the variable name or value of the LlvmVar in a plain -- textual representation (e.g. x, y or 42). getPlainName :: LlvmVar -> String -- | Return the LlvmType of the LlvmVar getVarType :: LlvmVar -> LlvmType -- | Return the LlvmLinkageType for a LlvmVar getLink :: LlvmVar -> LlvmLinkageType -- | Return the LlvmType of the LlvmStatic getStatType :: LlvmStatic -> LlvmType -- | Return the LlvmVar part of a LMGlobal getGlobalVar :: LMGlobal -> LlvmVar -- | Return the LlvmType of the LMGlobal getGlobalType :: LMGlobal -> LlvmType -- | Lower a variable of LMPointer type. pVarLift :: LlvmVar -> LlvmVar -- | Lower a variable of LMPointer type. pVarLower :: LlvmVar -> LlvmVar -- | Add a pointer indirection to the supplied type. LMLabel and -- LMVoid cannot be lifted. pLift :: LlvmType -> LlvmType -- | Remove the pointer indirection of the supplied type. Only -- LMPointer constructors can be lowered. pLower :: LlvmType -> LlvmType -- | Test if the given LlvmType is an integer isInt :: LlvmType -> Bool -- | Test if the given LlvmType is a floating point type isFloat :: LlvmType -> Bool -- | Test if the given LlvmType is an LMPointer construct isPointer :: LlvmType -> Bool -- | Width in bits of an LlvmType, returns 0 if not applicable llvmWidthInBits :: LlvmType -> Int -- | Print out a whole LLVM module. ppLlvmModule :: LlvmModule -> Doc -- | Print out a multi-line comment, can be inside a function or on its own ppLlvmComments :: [LMString] -> Doc -- | Print out a comment, can be inside a function or on its own ppLlvmComment :: LMString -> Doc -- | Print out a list of global mutable variable definitions ppLlvmGlobals :: [LMGlobal] -> Doc -- | Print out a global mutable variable definition ppLlvmGlobal :: LMGlobal -> Doc -- | Print out a list of function declaration. ppLlvmFunctionDecls :: LlvmFunctionDecls -> Doc -- | Print out a function declaration. Declarations define the function -- type but don't define the actual body of the function. ppLlvmFunctionDecl :: LlvmFunctionDecl -> Doc -- | Print out a list of function definitions. ppLlvmFunctions :: LlvmFunctions -> Doc -- | Print out a function definition. ppLlvmFunction :: LlvmFunction -> Doc -- | Print out an LLVM type alias. ppLlvmAlias :: LlvmAlias -> Doc -- | Print out a list of LLVM type aliases. ppLlvmAliases :: [LlvmAlias] -> Doc -- | Convert SDoc to Doc llvmSDoc :: SDoc -> Doc -- | Deal with Cmm registers module LlvmCodeGen.Regs -- | Get the LlvmVar function argument storing the real register lmGlobalRegArg :: GlobalReg -> LlvmVar -- | Get the LlvmVar function variable storing the real register lmGlobalRegVar :: GlobalReg -> LlvmVar module ClosureInfo data ClosureInfo ClosureInfo :: !Name -> !LambdaFormInfo -> !SMRep -> !C_SRT -> !Type -> !String -> ClosureInfo closureName :: ClosureInfo -> !Name closureLFInfo :: ClosureInfo -> !LambdaFormInfo closureSMRep :: ClosureInfo -> !SMRep closureSRT :: ClosureInfo -> !C_SRT closureType :: ClosureInfo -> !Type closureDescr :: ClosureInfo -> !String ConInfo :: !DataCon -> !SMRep -> ClosureInfo closureCon :: ClosureInfo -> !DataCon closureSMRep :: ClosureInfo -> !SMRep data LambdaFormInfo LFReEntrant :: TopLevelFlag -> !Int -> !Bool -> ArgDescr -> LambdaFormInfo LFCon :: DataCon -> LambdaFormInfo LFThunk :: TopLevelFlag -> !Bool -> !Bool -> StandardFormInfo -> !Bool -> LambdaFormInfo LFUnknown :: !Bool -> LambdaFormInfo LFLetNoEscape :: !Int -> LambdaFormInfo LFBlackHole :: CLabel -> LambdaFormInfo data StandardFormInfo NonStandardThunk :: StandardFormInfo SelectorThunk :: WordOff -> StandardFormInfo ApThunk :: Int -> StandardFormInfo data SMRep data ArgDescr ArgSpec :: !StgHalfWord -> ArgDescr ArgGen :: Liveness -> ArgDescr data Liveness SmallLiveness :: StgWord -> Liveness BigLiveness :: CLabel -> Liveness data C_SRT NoC_SRT :: C_SRT C_SRT :: !CLabel -> !WordOff -> !StgHalfWord -> C_SRT needsSRT :: C_SRT -> Bool mkLFThunk :: Type -> TopLevelFlag -> [Var] -> UpdateFlag -> LambdaFormInfo mkLFReEntrant :: TopLevelFlag -> [Id] -> [Id] -> ArgDescr -> LambdaFormInfo mkConLFInfo :: DataCon -> LambdaFormInfo mkSelectorLFInfo :: Id -> WordOff -> Bool -> LambdaFormInfo mkApLFInfo :: Id -> UpdateFlag -> Int -> LambdaFormInfo mkLFImported :: Id -> LambdaFormInfo mkLFArgument :: Id -> LambdaFormInfo mkLFLetNoEscape :: Int -> LambdaFormInfo mkClosureInfo :: Bool -> Id -> LambdaFormInfo -> Int -> Int -> C_SRT -> String -> ClosureInfo mkConInfo :: Bool -> DataCon -> Int -> Int -> ClosureInfo maybeIsLFCon :: LambdaFormInfo -> Maybe DataCon closureSize :: ClosureInfo -> WordOff closureNonHdrSize :: ClosureInfo -> WordOff closureGoodStuffSize :: ClosureInfo -> WordOff closurePtrsSize :: ClosureInfo -> WordOff slopSize :: ClosureInfo -> WordOff infoTableLabelFromCI :: ClosureInfo -> CafInfo -> CLabel closureLabelFromCI :: ClosureInfo -> CafInfo -> CLabel isLFThunk :: LambdaFormInfo -> Bool closureUpdReqd :: ClosureInfo -> Bool closureNeedsUpdSpace :: ClosureInfo -> Bool closureIsThunk :: ClosureInfo -> Bool closureSingleEntry :: ClosureInfo -> Bool closureReEntrant :: ClosureInfo -> Bool isConstrClosure_maybe :: ClosureInfo -> Maybe DataCon closureFunInfo :: ClosureInfo -> Maybe (Int, ArgDescr) isStandardFormThunk :: LambdaFormInfo -> Bool isKnownFun :: LambdaFormInfo -> Bool funTag :: ClosureInfo -> Int funTagLFInfo :: LambdaFormInfo -> Int tagForArity :: Int -> Maybe Int enterIdLabel :: Name -> CafInfo -> CLabel enterLocalIdLabel :: Name -> CafInfo -> CLabel enterReturnPtLabel :: Unique -> CLabel nodeMustPointToIt :: LambdaFormInfo -> Bool data CallMethod EnterIt :: CallMethod JumpToIt :: CLabel -> CallMethod ReturnIt :: CallMethod ReturnCon :: DataCon -> CallMethod SlowCall :: CallMethod DirectEntry :: CLabel -> Int -> CallMethod getCallMethod :: DynFlags -> Name -> CafInfo -> LambdaFormInfo -> Int -> CallMethod blackHoleOnEntry :: DynFlags -> ClosureInfo -> Bool staticClosureRequired :: Name -> StgBinderInfo -> LambdaFormInfo -> Bool getClosureType :: Bool -> WordOff -> LambdaFormInfo -> ClosureType isToplevClosure :: ClosureInfo -> Bool closureValDescr :: ClosureInfo -> String closureTypeDescr :: ClosureInfo -> String isStaticClosure :: ClosureInfo -> Bool cafBlackHoleClosureInfo :: ClosureInfo -> ClosureInfo staticClosureNeedsLink :: ClosureInfo -> Bool instance Eq C_SRT instance Outputable C_SRT module Cmm newtype GenCmm d h g Cmm :: [GenCmmTop d h g] -> GenCmm d h g -- | Cmm with the info table as a data type type Cmm = GenCmm CmmStatic CmmInfo (ListGraph CmmStmt) -- | Cmm with the info tables converted to a list of CmmStatic type RawCmm = GenCmm CmmStatic [CmmStatic] (ListGraph CmmStmt) -- | A top-level chunk, abstracted over the type of the contents of the -- basic blocks (Cmm or instructions are the likely instantiations). data GenCmmTop d h g CmmProc :: h -> CLabel -> CmmFormals -> g -> GenCmmTop d h g CmmData :: Section -> [d] -> GenCmmTop d h g type CmmTop = GenCmmTop CmmStatic CmmInfo (ListGraph CmmStmt) type RawCmmTop = GenCmmTop CmmStatic [CmmStatic] (ListGraph CmmStmt) -- | A control-flow graph represented as a list of extended basic blocks. newtype ListGraph i -- | Code, may be empty. The first block is the entry point. The order is -- otherwise initially unimportant, but at some point the code gen will -- fix the order. ListGraph :: [GenBasicBlock i] -> ListGraph i cmmMapGraph :: (g -> g') -> GenCmm d h g -> GenCmm d h g' cmmTopMapGraph :: (g -> g') -> GenCmmTop d h g -> GenCmmTop d h g' cmmMapGraphM :: Monad m => (String -> g -> m g') -> GenCmm d h g -> m (GenCmm d h g') cmmTopMapGraphM :: Monad m => (String -> g -> m g') -> GenCmmTop d h g -> m (GenCmmTop d h g') data CmmInfo CmmInfo :: (Maybe BlockId) -> (Maybe UpdateFrame) -> CmmInfoTable -> CmmInfo -- | A frame that is to be pushed before entry to the function. Used to -- handle update frames. data UpdateFrame UpdateFrame :: CmmExpr -> [CmmExpr] -> UpdateFrame data CmmInfoTable CmmInfoTable :: HasStaticClosure -> ProfilingInfo -> ClosureTypeTag -> ClosureTypeInfo -> CmmInfoTable CmmNonInfoTable :: CmmInfoTable type HasStaticClosure = Bool data ClosureTypeInfo ConstrInfo :: ClosureLayout -> ConstrTag -> ConstrDescription -> ClosureTypeInfo FunInfo :: ClosureLayout -> C_SRT -> FunArity -> ArgDescr -> SlowEntry -> ClosureTypeInfo ThunkInfo :: ClosureLayout -> C_SRT -> ClosureTypeInfo ThunkSelectorInfo :: SelectorOffset -> C_SRT -> ClosureTypeInfo ContInfo :: [Maybe LocalReg] -> C_SRT -> ClosureTypeInfo type ConstrDescription = CmmLit data ProfilingInfo ProfilingInfo :: CmmLit -> CmmLit -> ProfilingInfo type ClosureTypeTag = StgHalfWord data GenBasicBlock i BasicBlock :: BlockId -> [i] -> GenBasicBlock i type CmmBasicBlock = GenBasicBlock CmmStmt blockId :: GenBasicBlock i -> BlockId blockStmts :: GenBasicBlock i -> [i] mapBlockStmts :: (i -> i') -> GenBasicBlock i -> GenBasicBlock i' data CmmReturnInfo CmmMayReturn :: CmmReturnInfo CmmNeverReturns :: CmmReturnInfo data CmmStmt CmmNop :: CmmStmt CmmComment :: FastString -> CmmStmt CmmAssign :: CmmReg -> CmmExpr -> CmmStmt CmmStore :: CmmExpr -> CmmExpr -> CmmStmt CmmCall :: CmmCallTarget -> HintedCmmFormals -> HintedCmmActuals -> CmmSafety -> CmmReturnInfo -> CmmStmt CmmBranch :: BlockId -> CmmStmt CmmCondBranch :: CmmExpr -> BlockId -> CmmStmt CmmSwitch :: CmmExpr -> [Maybe BlockId] -> CmmStmt CmmJump :: CmmExpr -> HintedCmmActuals -> CmmStmt CmmReturn :: HintedCmmActuals -> CmmStmt type CmmActual = CmmExpr type CmmActuals = [CmmActual] type CmmFormal = LocalReg type CmmFormals = [CmmFormal] type HintedCmmFormal = CmmHinted CmmFormal type HintedCmmFormals = [HintedCmmFormal] type HintedCmmActual = CmmHinted CmmActual type HintedCmmActuals = [HintedCmmActual] data CmmSafety CmmUnsafe :: CmmSafety CmmSafe :: C_SRT -> CmmSafety data CmmCallTarget CmmCallee :: CmmExpr -> CCallConv -> CmmCallTarget CmmPrim :: CallishMachOp -> CmmCallTarget data CallishMachOp MO_F64_Pwr :: CallishMachOp MO_F64_Sin :: CallishMachOp MO_F64_Cos :: CallishMachOp MO_F64_Tan :: CallishMachOp MO_F64_Sinh :: CallishMachOp MO_F64_Cosh :: CallishMachOp MO_F64_Tanh :: CallishMachOp MO_F64_Asin :: CallishMachOp MO_F64_Acos :: CallishMachOp MO_F64_Atan :: CallishMachOp MO_F64_Log :: CallishMachOp MO_F64_Exp :: CallishMachOp MO_F64_Sqrt :: CallishMachOp MO_F32_Pwr :: CallishMachOp MO_F32_Sin :: CallishMachOp MO_F32_Cos :: CallishMachOp MO_F32_Tan :: CallishMachOp MO_F32_Sinh :: CallishMachOp MO_F32_Cosh :: CallishMachOp MO_F32_Tanh :: CallishMachOp MO_F32_Asin :: CallishMachOp MO_F32_Acos :: CallishMachOp MO_F32_Atan :: CallishMachOp MO_F32_Log :: CallishMachOp MO_F32_Exp :: CallishMachOp MO_F32_Sqrt :: CallishMachOp MO_WriteBarrier :: CallishMachOp MO_Touch :: CallishMachOp pprCallishMachOp :: CallishMachOp -> SDoc data ForeignHint NoHint :: ForeignHint AddrHint :: ForeignHint SignedHint :: ForeignHint data CmmHinted a CmmHinted :: a -> ForeignHint -> CmmHinted a hintlessCmm :: CmmHinted a -> a cmmHint :: CmmHinted a -> ForeignHint data CmmStatic CmmStaticLit :: CmmLit -> CmmStatic CmmUninitialised :: Int -> CmmStatic CmmAlign :: Int -> CmmStatic CmmDataLabel :: CLabel -> CmmStatic CmmString :: [Word8] -> CmmStatic data Section Text :: Section Data :: Section ReadOnlyData :: Section RelocatableReadOnlyData :: Section UninitialisedData :: Section ReadOnlyData16 :: Section OtherSection :: String -> Section instance Eq CmmReturnInfo instance Eq ForeignHint instance Eq a => Eq (CmmHinted a) instance Eq CallishMachOp instance Show CallishMachOp instance Eq CmmCallTarget instance DefinerOfLocalRegs a => DefinerOfLocalRegs (CmmHinted a) instance UserOfSlots a => UserOfSlots (CmmHinted a) instance UserOfLocalRegs a => UserOfLocalRegs (CmmHinted a) instance UserOfSlots CmmCallTarget instance UserOfLocalRegs CmmCallTarget instance UserOfLocalRegs CmmStmt instance UserOfLocalRegs i => UserOfLocalRegs (GenBasicBlock i) -- | Sizes on this architecture A Size is a combination of width and class -- -- TODO: Rename this to Format instead of Size to reflect -- the fact that it represents floating point vs integer. -- -- TODO: Signed vs unsigned? -- -- TODO: This module is currenly shared by all architectures because -- NCGMonad need to know about it to make a VReg. It would be better to -- have architecture specific formats, and do the overloading properly. -- eg SPARC doesn't care about FF80. module Size data Size II8 :: Size II16 :: Size II32 :: Size II64 :: Size FF32 :: Size FF64 :: Size FF80 :: Size -- | Get the integer size of this width. intSize :: Width -> Size -- | Get the float size of this width. floatSize :: Width -> Size -- | Check if a size represents a floating point value. isFloatSize :: Size -> Bool -- | Convert a Cmm type to a Size. cmmTypeSize :: CmmType -> Size -- | Get the Width of a Size. sizeToWidth :: Size -> Width instance Show Size instance Eq Size module X86.Regs -- | regSqueeze_class reg Calculuate the maximum number of register colors -- that could be denied to a node of this class due to having this reg as -- a neighbour. virtualRegSqueeze :: RegClass -> VirtualReg -> FastInt realRegSqueeze :: RegClass -> RealReg -> FastInt data Imm ImmInt :: Int -> Imm ImmInteger :: Integer -> Imm ImmCLbl :: CLabel -> Imm ImmLit :: Doc -> Imm ImmIndex :: CLabel -> Int -> Imm ImmFloat :: Rational -> Imm ImmDouble :: Rational -> Imm ImmConstantSum :: Imm -> Imm -> Imm ImmConstantDiff :: Imm -> Imm -> Imm strImmLit :: String -> Imm litToImm :: CmmLit -> Imm data AddrMode AddrBaseIndex :: EABase -> EAIndex -> Displacement -> AddrMode ImmAddr :: Imm -> Int -> AddrMode addrOffset :: AddrMode -> Int -> Maybe AddrMode spRel :: Int -> AddrMode argRegs :: RegNo -> [Reg] allArgRegs :: [Reg] callClobberedRegs :: [Reg] -- | The complete set of machine registers. allMachRegNos :: [RegNo] -- | Take the class of a register. classOfRealReg :: RealReg -> RegClass -- | Get the name of the register with this number. showReg :: RegNo -> String data EABase EABaseNone :: EABase EABaseReg :: Reg -> EABase EABaseRip :: EABase data EAIndex EAIndexNone :: EAIndex EAIndex :: Reg -> Int -> EAIndex addrModeRegs :: AddrMode -> [Reg] eax :: Reg ebx :: Reg ecx :: Reg edx :: Reg esi :: Reg edi :: Reg ebp :: Reg esp :: Reg fake0 :: Reg fake1 :: Reg fake2 :: Reg fake3 :: Reg fake4 :: Reg fake5 :: Reg firstfake :: RegNo rax :: Reg rbx :: Reg rcx :: Reg rdx :: Reg rsi :: Reg rdi :: Reg rbp :: Reg rsp :: Reg r8 :: Reg r9 :: Reg r10 :: Reg r11 :: Reg r12 :: Reg r13 :: Reg r14 :: Reg r15 :: Reg xmm0 :: Reg xmm1 :: Reg xmm2 :: Reg xmm3 :: Reg xmm4 :: Reg xmm5 :: Reg xmm6 :: Reg xmm7 :: Reg xmm8 :: Reg xmm9 :: Reg xmm10 :: Reg xmm11 :: Reg xmm12 :: Reg xmm13 :: Reg xmm14 :: Reg xmm15 :: Reg xmm :: RegNo -> Reg ripRel :: Displacement -> AddrMode allFPArgRegs :: [Reg] freeReg :: RegNo -> FastBool globalRegMaybe :: GlobalReg -> Maybe RealReg -- | these are the regs which we cannot assume stay alive over a C call. allocatableRegs :: [RealReg] module X86.RegInfo mkVirtualReg :: Unique -> Size -> VirtualReg regDotColor :: RealReg -> SDoc -- | Hard wired things related to registers. This is module is preventing -- the native code generator being able to emit code for non-host -- architectures. -- -- TODO: Do a better job of the overloading, and eliminate this module. -- We'd probably do better with a Register type class, and hook this to -- Instruction somehow. -- -- TODO: We should also make arch specific versions of -- RegAlloc.Graph.TrivColorable module TargetReg targetVirtualRegSqueeze :: RegClass -> VirtualReg -> FastInt targetRealRegSqueeze :: RegClass -> RealReg -> FastInt targetClassOfRealReg :: RealReg -> RegClass targetMkVirtualReg :: Unique -> Size -> VirtualReg targetWordSize :: Size targetRegDotColor :: RealReg -> SDoc targetClassOfReg :: Reg -> RegClass module NCGMonad data NatM_State NatM_State :: UniqSupply -> Int -> [(CLabel)] -> Maybe Reg -> DynFlags -> NatM_State natm_us :: NatM_State -> UniqSupply natm_delta :: NatM_State -> Int natm_imports :: NatM_State -> [(CLabel)] natm_pic :: NatM_State -> Maybe Reg natm_dflags :: NatM_State -> DynFlags mkNatM_State :: UniqSupply -> Int -> DynFlags -> NatM_State data NatM result initNat :: NatM_State -> NatM a -> (a, NatM_State) addImportNat :: CLabel -> NatM () getUniqueNat :: NatM Unique mapAccumLNat :: (acc -> x -> NatM (acc, y)) -> acc -> [x] -> NatM (acc, [y]) setDeltaNat :: Int -> NatM () getDeltaNat :: NatM Int getBlockIdNat :: NatM BlockId getNewLabelNat :: NatM CLabel getNewRegNat :: Size -> NatM Reg getNewRegPairNat :: Size -> NatM (Reg, Reg) getPicBaseMaybeNat :: NatM (Maybe Reg) getPicBaseNat :: Size -> NatM Reg getDynFlagsNat :: NatM DynFlags instance Monad NatM -- | Free regs map for i386 and x86_64 module RegAlloc.Linear.X86.FreeRegs type FreeRegs = Word64 noFreeRegs :: FreeRegs releaseReg :: RealReg -> FreeRegs -> FreeRegs initFreeRegs :: FreeRegs getFreeRegs :: RegClass -> FreeRegs -> [RealReg] allocateReg :: RealReg -> FreeRegs -> FreeRegs module Instruction -- | Holds a list of source and destination registers used by a particular -- instruction. -- -- Machine registers that are pre-allocated to stgRegs are filtered out, -- because they are uninteresting from a register allocation standpoint. -- (We wouldn't want them to end up on the free list!) -- -- As far as we are concerned, the fixed registers simply don't exist -- (for allocation purposes, anyway). data RegUsage RU :: [Reg] -> [Reg] -> RegUsage -- | No regs read or written to. noUsage :: RegUsage type NatCmm instr = GenCmm CmmStatic [CmmStatic] (ListGraph instr) type NatCmmTop instr = GenCmmTop CmmStatic [CmmStatic] (ListGraph instr) type NatBasicBlock instr = GenBasicBlock instr -- | Common things that we can do with instructions, on all architectures. -- These are used by the shared parts of the native code generator, -- specifically the register allocators. class Instruction instr regUsageOfInstr :: Instruction instr => instr -> RegUsage patchRegsOfInstr :: Instruction instr => instr -> (Reg -> Reg) -> instr isJumpishInstr :: Instruction instr => instr -> Bool jumpDestsOfInstr :: Instruction instr => instr -> [BlockId] patchJumpInstr :: Instruction instr => instr -> (BlockId -> BlockId) -> instr mkSpillInstr :: Instruction instr => Reg -> Int -> Int -> instr mkLoadInstr :: Instruction instr => Reg -> Int -> Int -> instr takeDeltaInstr :: Instruction instr => instr -> Maybe Int isMetaInstr :: Instruction instr => instr -> Bool mkRegRegMoveInstr :: Instruction instr => Reg -> Reg -> instr takeRegRegMoveInstr :: Instruction instr => instr -> Maybe (Reg, Reg) mkJumpInstr :: Instruction instr => BlockId -> [instr] module X86.Instr archWordSize :: Size data Instr COMMENT :: FastString -> Instr LDATA :: Section -> [CmmStatic] -> Instr NEWBLOCK :: BlockId -> Instr DELTA :: Int -> Instr MOV :: Size -> Operand -> Operand -> Instr MOVZxL :: Size -> Operand -> Operand -> Instr MOVSxL :: Size -> Operand -> Operand -> Instr LEA :: Size -> Operand -> Operand -> Instr ADD :: Size -> Operand -> Operand -> Instr ADC :: Size -> Operand -> Operand -> Instr SUB :: Size -> Operand -> Operand -> Instr MUL :: Size -> Operand -> Operand -> Instr IMUL :: Size -> Operand -> Operand -> Instr IMUL2 :: Size -> Operand -> Instr DIV :: Size -> Operand -> Instr IDIV :: Size -> Operand -> Instr AND :: Size -> Operand -> Operand -> Instr OR :: Size -> Operand -> Operand -> Instr XOR :: Size -> Operand -> Operand -> Instr NOT :: Size -> Operand -> Instr NEGI :: Size -> Operand -> Instr SHL :: Size -> Operand -> Operand -> Instr SAR :: Size -> Operand -> Operand -> Instr SHR :: Size -> Operand -> Operand -> Instr BT :: Size -> Imm -> Operand -> Instr NOP :: Instr GMOV :: Reg -> Reg -> Instr GLD :: Size -> AddrMode -> Reg -> Instr GST :: Size -> Reg -> AddrMode -> Instr GLDZ :: Reg -> Instr GLD1 :: Reg -> Instr GFTOI :: Reg -> Reg -> Instr GDTOI :: Reg -> Reg -> Instr GITOF :: Reg -> Reg -> Instr GITOD :: Reg -> Reg -> Instr GADD :: Size -> Reg -> Reg -> Reg -> Instr GDIV :: Size -> Reg -> Reg -> Reg -> Instr GSUB :: Size -> Reg -> Reg -> Reg -> Instr GMUL :: Size -> Reg -> Reg -> Reg -> Instr GCMP :: Cond -> Reg -> Reg -> Instr GABS :: Size -> Reg -> Reg -> Instr GNEG :: Size -> Reg -> Reg -> Instr GSQRT :: Size -> Reg -> Reg -> Instr GSIN :: Size -> CLabel -> CLabel -> Reg -> Reg -> Instr GCOS :: Size -> CLabel -> CLabel -> Reg -> Reg -> Instr GTAN :: Size -> CLabel -> CLabel -> Reg -> Reg -> Instr GFREE :: Instr CVTSS2SD :: Reg -> Reg -> Instr CVTSD2SS :: Reg -> Reg -> Instr CVTTSS2SIQ :: Size -> Operand -> Reg -> Instr CVTTSD2SIQ :: Size -> Operand -> Reg -> Instr CVTSI2SS :: Size -> Operand -> Reg -> Instr CVTSI2SD :: Size -> Operand -> Reg -> Instr FDIV :: Size -> Operand -> Operand -> Instr SQRT :: Size -> Operand -> Reg -> Instr TEST :: Size -> Operand -> Operand -> Instr CMP :: Size -> Operand -> Operand -> Instr SETCC :: Cond -> Operand -> Instr PUSH :: Size -> Operand -> Instr POP :: Size -> Operand -> Instr JMP :: Operand -> Instr JXX :: Cond -> BlockId -> Instr JXX_GBL :: Cond -> Imm -> Instr JMP_TBL :: Operand -> [BlockId] -> Instr CALL :: (Either Imm Reg) -> [Reg] -> Instr CLTD :: Size -> Instr FETCHGOT :: Reg -> Instr FETCHPC :: Reg -> Instr data Operand OpReg :: Reg -> Operand OpImm :: Imm -> Operand OpAddr :: AddrMode -> Operand x86_regUsageOfInstr :: Instr -> RegUsage interesting :: Reg -> Bool x86_patchRegsOfInstr :: Instr -> (Reg -> Reg) -> Instr x86_isJumpishInstr :: Instr -> Bool x86_jumpDestsOfInstr :: Instr -> [BlockId] x86_patchJumpInstr :: Instr -> (BlockId -> BlockId) -> Instr -- | Make a spill instruction. x86_mkSpillInstr :: Reg -> Int -> Int -> Instr -- | Make a spill reload instruction. x86_mkLoadInstr :: Reg -> Int -> Int -> Instr spillSlotSize :: Int maxSpillSlots :: Int spillSlotToOffset :: Int -> Int -- | See if this instruction is telling us the current C stack delta x86_takeDeltaInstr :: Instr -> Maybe Int x86_isMetaInstr :: Instr -> Bool -- | Make a reg-reg move instruction. On SPARC v8 there are no instructions -- to move directly between floating point and integer regs. If we need -- to do that then we have to go via memory. x86_mkRegRegMoveInstr :: Reg -> Reg -> Instr -- | Check whether an instruction represents a reg-reg move. The register -- allocator attempts to eliminate reg->reg moves whenever it can, by -- assigning the src and dest temporaries to the same real register. x86_takeRegRegMoveInstr :: Instr -> Maybe (Reg, Reg) -- | Make an unconditional branch instruction. x86_mkJumpInstr :: BlockId -> [Instr] i386_insert_ffrees :: [GenBasicBlock Instr] -> [GenBasicBlock Instr] is_G_instr :: Instr -> Bool data JumpDest DestBlockId :: BlockId -> JumpDest DestImm :: Imm -> JumpDest canShortcut :: Instr -> Maybe JumpDest shortcutJump :: (BlockId -> Maybe JumpDest) -> Instr -> Instr shortcutStatic :: (BlockId -> Maybe JumpDest) -> CmmStatic -> CmmStatic shortBlockId :: (BlockId -> Maybe JumpDest) -> UniqSet Unique -> BlockId -> CLabel instance Instruction Instr module RegAlloc.Linear.FreeRegs type FreeRegs = Word64 noFreeRegs :: FreeRegs releaseReg :: RealReg -> FreeRegs -> FreeRegs initFreeRegs :: FreeRegs getFreeRegs :: RegClass -> FreeRegs -> [RealReg] allocateReg :: RealReg -> FreeRegs -> FreeRegs maxSpillSlots :: Int -- | The assignment of virtual registers to stack slots module RegAlloc.Linear.StackMap -- | Identifier for a stack slot. type StackSlot = Int data StackMap StackMap :: [StackSlot] -> UniqFM StackSlot -> StackMap -- | The slots that are still available to be allocated. stackMapFreeSlots :: StackMap -> [StackSlot] -- | Assignment of vregs to stack slots. stackMapAssignment :: StackMap -> UniqFM StackSlot -- | An empty stack map, with all slots available. emptyStackMap :: StackMap -- | If this vreg unique already has a stack assignment then return the -- slot number, otherwise allocate a new slot, and update the map. getStackSlotFor :: StackMap -> Unique -> (StackMap, Int) module X86.Ppr pprNatCmmTop :: NatCmmTop Instr -> Doc pprBasicBlock :: NatBasicBlock Instr -> Doc pprSectionHeader :: Section -> Doc pprData :: CmmStatic -> Doc pprInstr :: Instr -> Doc pprUserReg :: Reg -> Doc pprSize :: Size -> Doc pprImm :: Imm -> Doc pprDataItem :: CmmLit -> Doc instance Outputable Instr module PPC.Regs -- | regSqueeze_class reg Calculuate the maximum number of register colors -- that could be denied to a node of this class due to having this reg as -- a neighbour. virtualRegSqueeze :: RegClass -> VirtualReg -> FastInt realRegSqueeze :: RegClass -> RealReg -> FastInt mkVirtualReg :: Unique -> Size -> VirtualReg regDotColor :: RealReg -> SDoc data Imm ImmInt :: Int -> Imm ImmInteger :: Integer -> Imm ImmCLbl :: CLabel -> Imm ImmLit :: Doc -> Imm ImmIndex :: CLabel -> Int -> Imm ImmFloat :: Rational -> Imm ImmDouble :: Rational -> Imm ImmConstantSum :: Imm -> Imm -> Imm ImmConstantDiff :: Imm -> Imm -> Imm LO :: Imm -> Imm HI :: Imm -> Imm HA :: Imm -> Imm strImmLit :: String -> Imm litToImm :: CmmLit -> Imm data AddrMode AddrRegReg :: Reg -> Reg -> AddrMode AddrRegImm :: Reg -> Imm -> AddrMode addrOffset :: AddrMode -> Int -> Maybe AddrMode spRel :: Int -> AddrMode argRegs :: RegNo -> [Reg] allArgRegs :: [Reg] callClobberedRegs :: [Reg] allMachRegNos :: [RegNo] classOfRealReg :: RealReg -> RegClass showReg :: RegNo -> String allFPArgRegs :: [Reg] fits16Bits :: Integral a => a -> Bool makeImmediate :: Integral a => Width -> Bool -> a -> Maybe Imm fReg :: Int -> RegNo sp :: Reg r3 :: Reg r4 :: Reg r27 :: Reg r28 :: Reg f1 :: Reg f20 :: Reg f21 :: Reg freeReg :: RegNo -> FastBool globalRegMaybe :: GlobalReg -> Maybe Reg allocatableRegs :: [RealReg] module PPC.Instr archWordSize :: Size data RI RIReg :: Reg -> RI RIImm :: Imm -> RI data Instr COMMENT :: FastString -> Instr LDATA :: Section -> [CmmStatic] -> Instr NEWBLOCK :: BlockId -> Instr DELTA :: Int -> Instr LD :: Size -> Reg -> AddrMode -> Instr LA :: Size -> Reg -> AddrMode -> Instr ST :: Size -> Reg -> AddrMode -> Instr STU :: Size -> Reg -> AddrMode -> Instr LIS :: Reg -> Imm -> Instr LI :: Reg -> Imm -> Instr MR :: Reg -> Reg -> Instr CMP :: Size -> Reg -> RI -> Instr CMPL :: Size -> Reg -> RI -> Instr BCC :: Cond -> BlockId -> Instr BCCFAR :: Cond -> BlockId -> Instr JMP :: CLabel -> Instr MTCTR :: Reg -> Instr BCTR :: [BlockId] -> Instr BL :: CLabel -> [Reg] -> Instr BCTRL :: [Reg] -> Instr ADD :: Reg -> Reg -> RI -> Instr ADDC :: Reg -> Reg -> Reg -> Instr ADDE :: Reg -> Reg -> Reg -> Instr ADDIS :: Reg -> Reg -> Imm -> Instr SUBF :: Reg -> Reg -> Reg -> Instr MULLW :: Reg -> Reg -> RI -> Instr DIVW :: Reg -> Reg -> Reg -> Instr DIVWU :: Reg -> Reg -> Reg -> Instr MULLW_MayOflo :: Reg -> Reg -> Reg -> Instr AND :: Reg -> Reg -> RI -> Instr OR :: Reg -> Reg -> RI -> Instr XOR :: Reg -> Reg -> RI -> Instr XORIS :: Reg -> Reg -> Imm -> Instr EXTS :: Size -> Reg -> Reg -> Instr NEG :: Reg -> Reg -> Instr NOT :: Reg -> Reg -> Instr SLW :: Reg -> Reg -> RI -> Instr SRW :: Reg -> Reg -> RI -> Instr SRAW :: Reg -> Reg -> RI -> Instr RLWINM :: Reg -> Reg -> Int -> Int -> Int -> Instr FADD :: Size -> Reg -> Reg -> Reg -> Instr FSUB :: Size -> Reg -> Reg -> Reg -> Instr FMUL :: Size -> Reg -> Reg -> Reg -> Instr FDIV :: Size -> Reg -> Reg -> Reg -> Instr FNEG :: Reg -> Reg -> Instr FCMP :: Reg -> Reg -> Instr FCTIWZ :: Reg -> Reg -> Instr FRSP :: Reg -> Reg -> Instr CRNOR :: Int -> Int -> Int -> Instr MFCR :: Reg -> Instr MFLR :: Reg -> Instr FETCHPC :: Reg -> Instr LWSYNC :: Instr maxSpillSlots :: Int instance Instruction Instr module PIC cmmMakeDynamicReference :: Monad m => DynFlags -> (CLabel -> m ()) -> ReferenceKind -> CLabel -> m CmmExpr data ReferenceKind DataReference :: ReferenceKind CallReference :: ReferenceKind JumpReference :: ReferenceKind needImportedSymbols :: Arch -> OS -> Bool pprImportedSymbol :: Arch -> OS -> CLabel -> Doc pprGotDeclaration :: Arch -> OS -> Doc initializePicBase_ppc :: Arch -> OS -> Reg -> [NatCmmTop Instr] -> NatM [NatCmmTop Instr] initializePicBase_x86 :: Arch -> OS -> Reg -> [NatCmmTop Instr] -> NatM [NatCmmTop Instr] instance Eq ReferenceKind -- | Free regs map for PowerPC module RegAlloc.Linear.PPC.FreeRegs data FreeRegs FreeRegs :: !Word32 -> !Word32 -> FreeRegs noFreeRegs :: FreeRegs releaseReg :: RealReg -> FreeRegs -> FreeRegs initFreeRegs :: FreeRegs getFreeRegs :: RegClass -> FreeRegs -> [RealReg] allocateReg :: RealReg -> FreeRegs -> FreeRegs instance Show FreeRegs module CmmLive -- | The variables live on entry to a block type CmmLive = UniqSet LocalReg -- | A mapping from block labels to the variables live on entry type BlockEntryLiveness = BlockEnv CmmLive -- | Calculated liveness info for a list of CmmBasicBlock cmmLiveness :: [CmmBasicBlock] -> BlockEntryLiveness cmmFormalsToLiveLocals :: HintedCmmFormals -> [LocalReg] module PPC.RegInfo data JumpDest DestBlockId :: BlockId -> JumpDest canShortcut :: Instr -> Maybe JumpDest shortcutJump :: (BlockId -> Maybe JumpDest) -> Instr -> Instr shortcutStatic :: (BlockId -> Maybe JumpDest) -> CmmStatic -> CmmStatic module PPC.Ppr pprNatCmmTop :: NatCmmTop Instr -> Doc pprBasicBlock :: NatBasicBlock Instr -> Doc pprSectionHeader :: Section -> Doc pprData :: CmmStatic -> Doc pprInstr :: Instr -> Doc pprUserReg :: Reg -> Doc pprSize :: Size -> Doc pprImm :: Imm -> Doc pprDataItem :: CmmLit -> Doc instance Outputable Instr module SPARC.Imm -- | An immediate value. Not all of these are directly representable by the -- machine. Things like ImmLit are slurped out and put in a data segment -- instead. data Imm ImmInt :: Int -> Imm ImmInteger :: Integer -> Imm ImmCLbl :: CLabel -> Imm ImmLit :: Doc -> Imm ImmIndex :: CLabel -> Int -> Imm ImmFloat :: Rational -> Imm ImmDouble :: Rational -> Imm ImmConstantSum :: Imm -> Imm -> Imm ImmConstantDiff :: Imm -> Imm -> Imm LO :: Imm -> Imm HI :: Imm -> Imm -- | Create a ImmLit containing this string. strImmLit :: String -> Imm -- | Convert a CmmLit to an Imm. Narrow to the width: a CmmInt might be out -- of range, but we assume that ImmInteger only contains in-range values. -- A signed value should be fine here. litToImm :: CmmLit -> Imm module SPARC.AddrMode -- | Represents a memory address in an instruction. Being a RISC machine, -- the SPARC addressing modes are very regular. data AddrMode AddrRegReg :: Reg -> Reg -> AddrMode AddrRegImm :: Reg -> Imm -> AddrMode -- | Add an integer offset to the address in an AddrMode. addrOffset :: AddrMode -> Int -> Maybe AddrMode module CmmUtils type CmmStmts = OrdList CmmStmt noStmts :: CmmStmts oneStmt :: CmmStmt -> CmmStmts mkStmts :: [CmmStmt] -> CmmStmts plusStmts :: CmmStmts -> CmmStmts -> CmmStmts stmtList :: CmmStmts -> [CmmStmt] isNopStmt :: CmmStmt -> Bool primRepCmmType :: PrimRep -> CmmType primRepForeignHint :: PrimRep -> ForeignHint typeCmmType :: Type -> CmmType typeForeignHint :: Type -> ForeignHint isTrivialCmmExpr :: CmmExpr -> Bool hasNoGlobalRegs :: CmmExpr -> Bool cmmRegOff :: CmmReg -> Int -> CmmExpr cmmLabelOff :: CLabel -> Int -> CmmLit cmmOffset :: CmmExpr -> Int -> CmmExpr cmmOffsetLit :: CmmLit -> Int -> CmmLit -- | Useful for creating an index into an array, with a staticaly known -- offset. The type is the element type; used for making the multiplier cmmIndex :: Width -> CmmExpr -> Int -> CmmExpr cmmOffsetExpr :: CmmExpr -> CmmExpr -> CmmExpr -- | Useful for creating an index into an array, with an unknown offset. cmmIndexExpr :: Width -> CmmExpr -> CmmExpr -> CmmExpr cmmLoadIndex :: CmmType -> CmmExpr -> Int -> CmmExpr mkIntCLit :: Int -> CmmLit zeroCLit :: CmmLit mkLblExpr :: CLabel -> CmmExpr maybeAssignTemp :: [Unique] -> CmmExpr -> ([Unique], [CmmStmt], CmmExpr) loadArgsIntoTemps :: [Unique] -> HintedCmmActuals -> ([Unique], [CmmStmt], HintedCmmActuals) module CmmOpt cmmMiniInline :: [CmmBasicBlock] -> [CmmBasicBlock] cmmMachOpFold :: MachOp -> [CmmExpr] -> CmmExpr cmmLoopifyForC :: RawCmmTop -> RawCmmTop module PprCmm writeCmms :: Handle -> [Cmm] -> IO () pprCmms :: (Outputable info, Outputable g) => [GenCmm CmmStatic info g] -> SDoc pprCmm :: (Outputable d, Outputable info, Outputable g) => GenCmm d info g -> SDoc pprStmt :: CmmStmt -> SDoc pprExpr :: CmmExpr -> SDoc pprSection :: Section -> SDoc pprStatic :: CmmStatic -> SDoc pprLit :: CmmLit -> SDoc instance Outputable a => Outputable (CmmHinted a) instance Outputable ForeignHint instance Outputable CmmSafety instance Outputable CmmInfo instance Outputable CmmStatic instance Outputable GlobalReg instance Outputable Area instance Outputable LocalReg instance Outputable CmmLit instance Outputable CmmReg instance Outputable CmmExpr instance Outputable CmmStmt instance Outputable instr => Outputable (GenBasicBlock instr) instance Outputable instr => Outputable (ListGraph instr) instance (Outputable d, Outputable info, Outputable i) => Outputable (GenCmmTop d info i) instance (Outputable d, Outputable info, Outputable g) => Outputable (GenCmm d info g) module X86.CodeGen cmmTopCodeGen :: DynFlags -> RawCmmTop -> NatM [NatCmmTop Instr] -- | InstrBlocks are the insn sequences generated by the insn -- selectors. They are really trees of insns to facilitate fast -- appending, where a left-to-right traversal yields the insns in the -- correct order. type InstrBlock = OrdList Instr module RegAlloc.Liveness type RegSet = UniqSet Reg type RegMap a = UniqFM a emptyRegMap :: UniqFM a type BlockMap a = BlockEnv a emptyBlockMap :: BlockEnv a -- | A top level thing which carries liveness information. type LiveCmmTop instr = GenCmmTop CmmStatic LiveInfo [SCC (LiveBasicBlock instr)] -- | The register allocator also wants to use SPILL/RELOAD meta -- instructions, so we'll keep those here. data InstrSR instr -- | A real machine instruction Instr :: instr -> InstrSR instr -- | spill this reg to a stack slot SPILL :: Reg -> Int -> InstrSR instr -- | reload this reg from a stack slot RELOAD :: Int -> Reg -> InstrSR instr -- | An instruction with liveness information. data LiveInstr instr LiveInstr :: (InstrSR instr) -> (Maybe Liveness) -> LiveInstr instr -- | Liveness information. The regs which die are ones which are no longer -- live in the *next* instruction in this sequence. (NB. if the -- instruction is a jump, these registers might still be live at the jump -- target(s) - you have to check the liveness at the destination block to -- find out). data Liveness -- | registers that died because they were clobbered by something. Liveness :: RegSet -> RegSet -> RegSet -> Liveness -- | registers born in this instruction (written to for first time). liveBorn :: Liveness -> RegSet -- | registers that died because they were read for the last time. liveDieRead :: Liveness -> RegSet liveDieWrite :: Liveness -> RegSet -- | Stash regs live on entry to each basic block in the info part of the -- cmm code. data LiveInfo LiveInfo :: [CmmStatic] -> (Maybe BlockId) -> (Maybe (BlockMap RegSet)) -> (Map BlockId (Set Int)) -> LiveInfo -- | A basic block with liveness information. type LiveBasicBlock instr = GenBasicBlock (LiveInstr instr) -- | map a function across all the basic blocks in this code mapBlockTop :: (LiveBasicBlock instr -> LiveBasicBlock instr) -> LiveCmmTop instr -> LiveCmmTop instr -- | map a function across all the basic blocks in this code (monadic -- version) mapBlockTopM :: Monad m => (LiveBasicBlock instr -> m (LiveBasicBlock instr)) -> LiveCmmTop instr -> m (LiveCmmTop instr) mapSCCM :: Monad m => (a -> m b) -> SCC a -> m (SCC b) mapGenBlockTop :: (GenBasicBlock i -> GenBasicBlock i) -> (GenCmmTop d h (ListGraph i) -> GenCmmTop d h (ListGraph i)) -- | map a function across all the basic blocks in this code (monadic -- version) mapGenBlockTopM :: Monad m => (GenBasicBlock i -> m (GenBasicBlock i)) -> (GenCmmTop d h (ListGraph i) -> m (GenCmmTop d h (ListGraph i))) -- | Strip away liveness information, yielding NatCmmTop stripLive :: (Outputable instr, Instruction instr) => LiveCmmTop instr -> NatCmmTop instr -- | Strip away liveness information from a basic block, and make real -- spill instructions out of SPILL, RELOAD pseudos along the way. stripLiveBlock :: Instruction instr => LiveBasicBlock instr -> NatBasicBlock instr -- | Slurp out the list of register conflicts and reg-reg moves from this -- top level thing. Slurping of conflicts and moves is wrapped up -- together so we don't have to make two passes over the same code when -- we want to build the graph. slurpConflicts :: Instruction instr => LiveCmmTop instr -> (Bag (UniqSet Reg), Bag (Reg, Reg)) -- | For spill/reloads -- -- SPILL v1, slot1 ... RELOAD slot1, v2 -- -- If we can arrange that v1 and v2 are allocated to the same hreg it's -- more likely the spill/reload instrs can be cleaned and replaced by a -- nop reg-reg move. slurpReloadCoalesce :: Instruction instr => LiveCmmTop instr -> Bag (Reg, Reg) -- | Erase Delta instructions. eraseDeltasLive :: Instruction instr => LiveCmmTop instr -> LiveCmmTop instr -- | Patch the registers in this code according to this register mapping. -- also erase reg -> reg moves when the reg is the same. also erase -- reg -> reg moves when the destination dies in this instr. patchEraseLive :: Instruction instr => (Reg -> Reg) -> LiveCmmTop instr -> LiveCmmTop instr -- | Patch registers in this LiveInstr, including the liveness information. patchRegsLiveInstr :: Instruction instr => (Reg -> Reg) -> LiveInstr instr -> LiveInstr instr -- | If we've compute liveness info for this code already we have to -- reverse the SCCs in each top to get them back to the right order so we -- can do it again. reverseBlocksInTops :: LiveCmmTop instr -> LiveCmmTop instr regLiveness :: (Outputable instr, Instruction instr) => LiveCmmTop instr -> UniqSM (LiveCmmTop instr) -- | Convert a NatCmmTop to a LiveCmmTop, with empty liveness information natCmmTopToLive :: Instruction instr => NatCmmTop instr -> LiveCmmTop instr instance Outputable LiveInfo instance Outputable instr => Outputable (LiveInstr instr) instance Outputable instr => Outputable (InstrSR instr) instance Instruction instr => Instruction (InstrSR instr) -- | Register coalescing. module RegAlloc.Graph.Coalesce -- | Do register coalescing on this top level thing For Reg -> Reg -- moves, if the first reg dies at the same time the second reg is born -- then the mov only serves to join live ranges. The two regs can be -- renamed to be the same and the move instruction safely erased. regCoalesce :: Instruction instr => [LiveCmmTop instr] -> UniqSM [LiveCmmTop instr] -- | Slurp out mov instructions that only serve to join live ranges. During -- a mov, if the source reg dies and the destiation reg is born then we -- can rename the two regs to the same thing and eliminate the move. slurpJoinMovs :: Instruction instr => LiveCmmTop instr -> Bag (Reg, Reg) -- | When there aren't enough registers to hold all the vregs we have to -- spill some of those vregs to slots on the stack. This module is used -- modify the code to use those slots. module RegAlloc.Graph.Spill -- | Spill all these virtual regs to stack slots. -- -- TODO: See if we can split some of the live ranges instead of just -- globally spilling the virtual reg. This might make the spill cleaner's -- job easier. -- -- TODO: On CISCy x86 and x86_64 we don't nessesarally have to add a mov -- instruction when making spills. If an instr is using a spilled virtual -- we may be able to address the spill slot directly. regSpill :: Instruction instr => [LiveCmmTop instr] -> UniqSet Int -> UniqSet VirtualReg -> UniqSM ([LiveCmmTop instr], UniqSet Int, SpillStats) data SpillStats SpillStats :: UniqFM (Reg, Int, Int) -> SpillStats spillStoreLoad :: SpillStats -> UniqFM (Reg, Int, Int) accSpillSL :: (Num t3, Num t2) => (t1, t2, t3) -> (t, t2, t3) -> (t1, t2, t3) instance Outputable SpillStats -- | Clean out unneeded spill/reload instrs -- -- -- -- B1: B2: ... ... RELOAD SLOT(0), %r1 RELOAD SLOT(0), %r1 ... A ... ... -- B ... jump B3 jump B3 -- -- B3: ... C ... RELOAD SLOT(0), %r1 ... -- -- the plan: So long as %r1 hasn't been written to in A, B or C then we -- don't need the reload in B3. -- -- What we really care about here is that on the entry to B3, %r1 will -- always have the same value that is in SLOT(0) (ie, %r1 is _valid_) -- -- This also works if the reloads in B1/B2 were spills instead, because -- spilling %r1 to a slot makes that slot have the same value as %r1. module RegAlloc.Graph.SpillClean -- | Clean out unneeded spill/reloads from this top level thing. cleanSpills :: Instruction instr => LiveCmmTop instr -> LiveCmmTop instr instance Outputable Store instance Uniquable Store module RegAlloc.Graph.SpillCost type SpillCostRecord = (VirtualReg, Int, Int, Int) plusSpillCostRecord :: SpillCostRecord -> SpillCostRecord -> SpillCostRecord -- | Show a spill cost record, including the degree from the graph and -- final calulated spill cos pprSpillCostRecord :: (VirtualReg -> RegClass) -> (Reg -> SDoc) -> Graph VirtualReg RegClass RealReg -> SpillCostRecord -> SDoc type SpillCostInfo = UniqFM SpillCostRecord zeroSpillCostInfo :: SpillCostInfo -- | Add two spillCostInfos plusSpillCostInfo :: SpillCostInfo -> SpillCostInfo -> SpillCostInfo -- | Slurp out information used for determining spill costs for each vreg, -- the number of times it was written to, read from, and the number of -- instructions it was live on entry to (lifetime) slurpSpillCostInfo :: (Outputable instr, Instruction instr) => LiveCmmTop instr -> SpillCostInfo -- | Choose a node to spill from this graph chooseSpill :: SpillCostInfo -> Graph VirtualReg RegClass RealReg -> VirtualReg lifeMapFromSpillCostInfo :: SpillCostInfo -> UniqFM (VirtualReg, Int) -- | Carries interesting info for debugging / profiling of the graph -- coloring register allocator. module RegAlloc.Graph.Stats data RegAllocStats instr -- | information to help choose which regs to spill RegAllocStatsStart :: [LiveCmmTop instr] -> Graph VirtualReg RegClass RealReg -> SpillCostInfo -> RegAllocStats instr -- | initial code, with liveness raLiveCmm :: RegAllocStats instr -> [LiveCmmTop instr] -- | the initial, uncolored graph raGraph :: RegAllocStats instr -> Graph VirtualReg RegClass RealReg raSpillCosts :: RegAllocStats instr -> SpillCostInfo -- | code with spill instructions added RegAllocStatsSpill :: [LiveCmmTop instr] -> Graph VirtualReg RegClass RealReg -> UniqFM VirtualReg -> SpillStats -> SpillCostInfo -> [LiveCmmTop instr] -> RegAllocStats instr -- | the code we tried to allocate registers for raCode :: RegAllocStats instr -> [LiveCmmTop instr] -- | the initial, uncolored graph raGraph :: RegAllocStats instr -> Graph VirtualReg RegClass RealReg -- | the regs that were coaleced raCoalesced :: RegAllocStats instr -> UniqFM VirtualReg -- | spiller stats raSpillStats :: RegAllocStats instr -> SpillStats raSpillCosts :: RegAllocStats instr -> SpillCostInfo raSpilled :: RegAllocStats instr -> [LiveCmmTop instr] -- | spill/reload/reg-reg moves present in this code RegAllocStatsColored :: [LiveCmmTop instr] -> Graph VirtualReg RegClass RealReg -> Graph VirtualReg RegClass RealReg -> UniqFM VirtualReg -> [LiveCmmTop instr] -> [LiveCmmTop instr] -> [LiveCmmTop instr] -> [NatCmmTop instr] -> (Int, Int, Int) -> RegAllocStats instr -- | the code we tried to allocate registers for raCode :: RegAllocStats instr -> [LiveCmmTop instr] -- | the initial, uncolored graph raGraph :: RegAllocStats instr -> Graph VirtualReg RegClass RealReg -- | the coalesced and colored graph raGraphColored :: RegAllocStats instr -> Graph VirtualReg RegClass RealReg -- | the regs that were coaleced raCoalesced :: RegAllocStats instr -> UniqFM VirtualReg -- | code with coalescings applied raCodeCoalesced :: RegAllocStats instr -> [LiveCmmTop instr] -- | code with vregs replaced by hregs raPatched :: RegAllocStats instr -> [LiveCmmTop instr] -- | code with unneeded spill/reloads cleaned out raSpillClean :: RegAllocStats instr -> [LiveCmmTop instr] -- | final code raFinal :: RegAllocStats instr -> [NatCmmTop instr] raSRMs :: RegAllocStats instr -> (Int, Int, Int) -- | Do all the different analysis on this list of RegAllocStats pprStats :: [RegAllocStats instr] -> Graph VirtualReg RegClass RealReg -> SDoc -- | Dump a table of how many spill loads / stores were inserted for each -- vreg. pprStatsSpills :: [RegAllocStats instr] -> SDoc -- | Dump a table of how long vregs tend to live for in the initial code. pprStatsLifetimes :: [RegAllocStats instr] -> SDoc -- | Dump a table of how many conflicts vregs tend to have in the initial -- code. pprStatsConflict :: [RegAllocStats instr] -> SDoc -- | For every vreg, dump it's how many conflicts it has and its lifetime -- good for making a scatter plot. pprStatsLifeConflict :: [RegAllocStats instr] -> Graph VirtualReg RegClass RealReg -> SDoc -- | Count spillreloadreg-reg moves. Lets us see how well the -- register allocator has done. countSRMs :: Instruction instr => LiveCmmTop instr -> (Int, Int, Int) addSRM :: (Num t1, Num t2, Num t) => (t, t1, t2) -> (t, t1, t2) -> (t, t1, t2) instance Outputable instr => Outputable (RegAllocStats instr) -- | Graph coloring register allocator. -- -- TODO: The colors in graphviz graphs for x86_64 and ppc could be nicer. module RegAlloc.Graph.Main -- | The top level of the graph coloring register allocator. regAlloc :: (Outputable instr, Instruction instr) => DynFlags -> UniqFM (UniqSet RealReg) -> UniqSet Int -> [LiveCmmTop instr] -> UniqSM ([NatCmmTop instr], [RegAllocStats instr]) -- | Put common type definitions here to break recursive module -- dependencies. module RegAlloc.Linear.Base -- | Used to store the register assignment on entry to a basic block. We -- use this to handle join points, where multiple branch instructions -- target a particular label. We have to insert fixup code to make the -- register assignments from the different sources match up. type BlockAssignment = BlockMap (FreeRegs, RegMap Loc) -- | Where a vreg is currently stored A temporary can be marked as living -- in both a register and memory (InBoth), for example if it was recently -- loaded from a spill location. This makes it cheap to spill (no save -- instruction required), but we have to be careful to turn this into -- InReg if the value in the register is changed. data Loc -- | vreg is in a register InReg :: !RealReg -> Loc -- | vreg is held in a stack slot InMem :: {-# UNPACK #-} !StackSlot -> Loc -- | vreg is held in both a register and a stack slot InBoth :: !RealReg -> {-# UNPACK #-} !StackSlot -> Loc -- | Get the reg numbers stored in this Loc. regsOfLoc :: Loc -> [RealReg] -- | Reasons why instructions might be inserted by the spiller. Used when -- generating stats for -ddrop-asm-stats. data SpillReason -- | vreg was spilled to a slot so we could use its current hreg for -- another vreg SpillAlloc :: !Unique -> SpillReason -- | vreg was moved because its hreg was clobbered SpillClobber :: !Unique -> SpillReason -- | vreg was loaded from a spill slot SpillLoad :: !Unique -> SpillReason -- | reg-reg move inserted during join to targets SpillJoinRR :: !Unique -> SpillReason -- | reg-mem move inserted during join to targets SpillJoinRM :: !Unique -> SpillReason -- | Used to carry interesting stats out of the register allocator. data RegAllocStats RegAllocStats :: UniqFM [Int] -> RegAllocStats ra_spillInstrs :: RegAllocStats -> UniqFM [Int] -- | The register alloctor state data RA_State RA_State :: BlockAssignment -> {-# UNPACK #-} !FreeRegs -> RegMap Loc -> Int -> StackMap -> UniqSupply -> [SpillReason] -> RA_State -- | the current mapping from basic blocks to the register assignments at -- the beginning of that block. ra_blockassig :: RA_State -> BlockAssignment -- | free machine registers ra_freeregs :: RA_State -> {-# UNPACK #-} !FreeRegs -- | assignment of temps to locations ra_assig :: RA_State -> RegMap Loc -- | current stack delta ra_delta :: RA_State -> Int -- | free stack slots for spilling ra_stack :: RA_State -> StackMap -- | unique supply for generating names for join point fixup blocks. ra_us :: RA_State -> UniqSupply -- | Record why things were spilled, for -ddrop-asm-stats. Just keep a list -- here instead of a map of regs -> reasons. We don't want to slow -- down the allocator if we're not going to emit the stats. ra_spills :: RA_State -> [SpillReason] -- | The register allocator monad type. newtype RegM a RegM :: (RA_State -> (# RA_State, a #)) -> RegM a unReg :: RegM a -> RA_State -> (# RA_State, a #) instance Eq Loc instance Show Loc instance Ord Loc instance Outputable Loc module RegAlloc.Linear.Stats -- | Build a map of how many times each reg was alloced, clobbered, loaded -- etc. binSpillReasons :: [SpillReason] -> UniqFM [Int] -- | Count reg-reg moves remaining in this code. countRegRegMovesNat :: Instruction instr => NatCmmTop instr -> Int -- | Pretty print some RegAllocStats pprStats :: Instruction instr => [NatCmmTop instr] -> [RegAllocStats] -> SDoc -- | State monad for the linear register allocator. module RegAlloc.Linear.State -- | The register alloctor state data RA_State RA_State :: BlockAssignment -> {-# UNPACK #-} !FreeRegs -> RegMap Loc -> Int -> StackMap -> UniqSupply -> [SpillReason] -> RA_State -- | the current mapping from basic blocks to the register assignments at -- the beginning of that block. ra_blockassig :: RA_State -> BlockAssignment -- | free machine registers ra_freeregs :: RA_State -> {-# UNPACK #-} !FreeRegs -- | assignment of temps to locations ra_assig :: RA_State -> RegMap Loc -- | current stack delta ra_delta :: RA_State -> Int -- | free stack slots for spilling ra_stack :: RA_State -> StackMap -- | unique supply for generating names for join point fixup blocks. ra_us :: RA_State -> UniqSupply -- | Record why things were spilled, for -ddrop-asm-stats. Just keep a list -- here instead of a map of regs -> reasons. We don't want to slow -- down the allocator if we're not going to emit the stats. ra_spills :: RA_State -> [SpillReason] -- | The register allocator monad type. data RegM a -- | Run a computation in the RegM register allocator monad. runR :: BlockAssignment -> FreeRegs -> RegMap Loc -> StackMap -> UniqSupply -> RegM a -> (BlockAssignment, StackMap, RegAllocStats, a) spillR :: Instruction instr => Reg -> Unique -> RegM (instr, Int) loadR :: Instruction instr => Reg -> Int -> RegM instr getFreeRegsR :: RegM FreeRegs setFreeRegsR :: FreeRegs -> RegM () getAssigR :: RegM (RegMap Loc) setAssigR :: RegMap Loc -> RegM () getBlockAssigR :: RegM BlockAssignment setBlockAssigR :: BlockAssignment -> RegM () setDeltaR :: Int -> RegM () getDeltaR :: RegM Int getUniqueR :: RegM Unique -- | Record that a spill instruction was inserted, for profiling. recordSpill :: SpillReason -> RegM () instance Monad RegM -- | Handles joining of a jump instruction to its targets. module RegAlloc.Linear.JoinToTargets -- | For a jump instruction at the end of a block, generate fixup code so -- its vregs are in the correct regs for its destination. joinToTargets :: Instruction instr => BlockMap RegSet -> BlockId -> instr -> RegM ([NatBasicBlock instr], instr) module RegAlloc.Linear.Main regAlloc :: (Outputable instr, Instruction instr) => LiveCmmTop instr -> UniqSM (NatCmmTop instr, Maybe RegAllocStats) module SPARC.Regs -- | Get the standard name for the register with this number. showReg :: RegNo -> String -- | regSqueeze_class reg Calculuate the maximum number of register colors -- that could be denied to a node of this class due to having this reg as -- a neighbour. virtualRegSqueeze :: RegClass -> VirtualReg -> FastInt realRegSqueeze :: RegClass -> RealReg -> FastInt classOfRealReg :: RealReg -> RegClass -- | All the allocatable registers in the machine, including register -- pairs. allRealRegs :: [RealReg] gReg :: Int -> RegNo iReg :: Int -> RegNo -- | Get the regno for this sort of reg lReg :: Int -> RegNo oReg :: Int -> RegNo fReg :: Int -> RegNo fp :: Reg sp :: Reg g0 :: Reg -- | Some specific regs used by the code generator. g1 :: Reg g2 :: Reg o0 :: Reg o1 :: Reg f0 :: Reg f1 :: Reg f6 :: Reg f8 :: Reg f22 :: Reg f26 :: Reg f27 :: Reg -- | Produce the second-half-of-a-double register given the first half. -- -- All the regs that the register allocator can allocate to, with the the -- fixed use regs removed. allocatableRegs :: [RealReg] -- | The registers to place arguments for function calls, for some number -- of arguments. argRegs :: RegNo -> [Reg] -- | All all the regs that could possibly be returned by argRegs allArgRegs :: [Reg] callClobberedRegs :: [Reg] -- | Make a virtual reg with this size. mkVirtualReg :: Unique -> Size -> VirtualReg regDotColor :: RealReg -> SDoc module SPARC.Stack -- | Get an AddrMode relative to the address in sp. This gives us a stack -- relative addressing mode for volatile temporaries and for excess call -- arguments. spRel :: Int -> AddrMode -- | Get an address relative to the frame pointer. This doesn't work work -- for offsets greater than 13 bits; we just hope for the best fpRel :: Int -> AddrMode -- | Convert a spill slot number to a *byte* offset, with no sign. spillSlotToOffset :: Int -> Int -- | The maximum number of spill slots available on the C stack. If we use -- up all of the slots, then we're screwed. -- -- Why do we reserve 64 bytes, instead of using the whole thing?? -- BL -- 20090215 maxSpillSlots :: Int module SPARC.Instr -- | Register or immediate data RI RIReg :: Reg -> RI RIImm :: Imm -> RI -- | Check if a RI represents a zero value. - a literal zero - register -- %g0, which is always zero. riZero :: RI -> Bool -- | Calculate the effective address which would be used by the -- corresponding fpRel sequence. fpRelEA :: Int -> Reg -> Instr -- | Code to shift the stack pointer by n words. moveSp :: Int -> Instr -- | An instruction that will cause the one after it never to be exectuted isUnconditionalJump :: Instr -> Bool -- | SPARC instruction set. Not complete. This is only the ones we need. data Instr COMMENT :: FastString -> Instr LDATA :: Section -> [CmmStatic] -> Instr NEWBLOCK :: BlockId -> Instr DELTA :: Int -> Instr LD :: Size -> AddrMode -> Reg -> Instr ST :: Size -> Reg -> AddrMode -> Instr ADD :: Bool -> Bool -> Reg -> RI -> Reg -> Instr SUB :: Bool -> Bool -> Reg -> RI -> Reg -> Instr UMUL :: Bool -> Reg -> RI -> Reg -> Instr SMUL :: Bool -> Reg -> RI -> Reg -> Instr UDIV :: Bool -> Reg -> RI -> Reg -> Instr SDIV :: Bool -> Reg -> RI -> Reg -> Instr RDY :: Reg -> Instr WRY :: Reg -> Reg -> Instr AND :: Bool -> Reg -> RI -> Reg -> Instr ANDN :: Bool -> Reg -> RI -> Reg -> Instr OR :: Bool -> Reg -> RI -> Reg -> Instr ORN :: Bool -> Reg -> RI -> Reg -> Instr XOR :: Bool -> Reg -> RI -> Reg -> Instr XNOR :: Bool -> Reg -> RI -> Reg -> Instr SLL :: Reg -> RI -> Reg -> Instr SRL :: Reg -> RI -> Reg -> Instr SRA :: Reg -> RI -> Reg -> Instr SETHI :: Imm -> Reg -> Instr NOP :: Instr FABS :: Size -> Reg -> Reg -> Instr FADD :: Size -> Reg -> Reg -> Reg -> Instr FCMP :: Bool -> Size -> Reg -> Reg -> Instr FDIV :: Size -> Reg -> Reg -> Reg -> Instr FMOV :: Size -> Reg -> Reg -> Instr FMUL :: Size -> Reg -> Reg -> Reg -> Instr FNEG :: Size -> Reg -> Reg -> Instr FSQRT :: Size -> Reg -> Reg -> Instr FSUB :: Size -> Reg -> Reg -> Reg -> Instr FxTOy :: Size -> Size -> Reg -> Reg -> Instr BI :: Cond -> Bool -> BlockId -> Instr BF :: Cond -> Bool -> BlockId -> Instr JMP :: AddrMode -> Instr JMP_TBL :: AddrMode -> [BlockId] -> Instr CALL :: (Either Imm Reg) -> Int -> Bool -> Instr -- | The maximum number of spill slots available on the C stack. If we use -- up all of the slots, then we're screwed. -- -- Why do we reserve 64 bytes, instead of using the whole thing?? -- BL -- 20090215 maxSpillSlots :: Int instance Instruction Instr module SPARC.ShortcutJump data JumpDest DestBlockId :: BlockId -> JumpDest DestImm :: Imm -> JumpDest canShortcut :: Instr -> Maybe JumpDest shortcutJump :: (BlockId -> Maybe JumpDest) -> Instr -> Instr shortcutStatic :: (BlockId -> Maybe JumpDest) -> CmmStatic -> CmmStatic shortBlockId :: (BlockId -> Maybe JumpDest) -> BlockId -> CLabel module SPARC.Ppr pprNatCmmTop :: NatCmmTop Instr -> Doc pprBasicBlock :: NatBasicBlock Instr -> Doc -- | Pretty print a section / segment header. On SPARC all the data -- sections must be at least 8 byte aligned incase we store doubles in -- them. pprSectionHeader :: Section -> Doc pprData :: CmmStatic -> Doc -- | Pretty print an instruction. pprInstr :: Instr -> Doc -- | Pretty print a register. This is an alias of pprReg for legacy -- reasons, should remove it. pprUserReg :: Reg -> Doc -- | Pretty print a size for an instruction suffix. pprSize :: Size -> Doc -- | Pretty print an immediate value. pprImm :: Imm -> Doc -- | Pretty print a data item. pprDataItem :: CmmLit -> Doc instance Outputable Instr -- | Expand out synthetic instructions into single machine instrs. module SPARC.CodeGen.Expand -- | Expand out synthetic instructions in this top level thing expandTop :: NatCmmTop Instr -> NatCmmTop Instr -- | One ounce of sanity checking is worth 10000000000000000 ounces of -- staring blindly at assembly code trying to find the problem.. module SPARC.CodeGen.Sanity -- | Enforce intra-block invariants. checkBlock :: CmmBasicBlock -> NatBasicBlock Instr -> NatBasicBlock Instr module SPARC.CodeGen.Base -- | InstrBlocks are the insn sequences generated by the insn -- selectors. They are really trees of insns to facilitate fast -- appending, where a left-to-right traversal yields the insns in the -- correct order. type InstrBlock = OrdList Instr -- | Condition codes passed up the tree. data CondCode CondCode :: Bool -> Cond -> InstrBlock -> CondCode -- | a.k.a Register64 Reg is the lower 32-bit temporary which -- contains the result. Use getHiVRegFromLo to find the other VRegUnique. -- -- Rules of this simplified insn selection game are therefore that the -- returned Reg may be modified data ChildCode64 ChildCode64 :: InstrBlock -> Reg -> ChildCode64 -- | Holds code that references a memory address. data Amode Amode :: AddrMode -> InstrBlock -> Amode -- | Code to produce a result into a register. If the result must go in a -- specific register, it comes out as Fixed. Otherwise, the parent can -- decide which register to put it in. data Register Fixed :: Size -> Reg -> InstrBlock -> Register Any :: Size -> (Reg -> InstrBlock) -> Register -- | Change the size field in a Register. setSizeOfRegister :: Register -> Size -> Register -- | Grab the Reg for a CmmReg getRegisterReg :: CmmReg -> Reg mangleIndexTree :: CmmExpr -> CmmExpr module SPARC.CodeGen.Amode -- | Generate code to reference a memory address. getAmode :: CmmExpr -> NatM Amode module SPARC.CodeGen.CondCode getCondCode :: CmmExpr -> NatM CondCode condIntCode :: Cond -> CmmExpr -> CmmExpr -> NatM CondCode condFltCode :: Cond -> CmmExpr -> CmmExpr -> NatM CondCode -- | Evaluation of 64 bit values on 32 bit platforms. module SPARC.CodeGen.Gen64 -- | Code to assign a 64 bit value to memory. assignMem_I64Code :: CmmExpr -> CmmExpr -> NatM InstrBlock -- | Code to assign a 64 bit value to a register. assignReg_I64Code :: CmmReg -> CmmExpr -> NatM InstrBlock -- | Get the value of an expression into a 64 bit register. iselExpr64 :: CmmExpr -> NatM ChildCode64 -- | Evaluation of 32 bit values. module SPARC.CodeGen.Gen32 -- | The dual to getAnyReg: compute an expression into a register, but we -- don't mind which one it is. getSomeReg :: CmmExpr -> NatM (Reg, InstrBlock) -- | Make code to evaluate a 32 bit expression. getRegister :: CmmExpr -> NatM Register -- | Generating C calls module SPARC.CodeGen.CCall genCCall :: CmmCallTarget -> HintedCmmFormals -> HintedCmmActuals -> NatM InstrBlock module SPARC.CodeGen -- | Top level code generation cmmTopCodeGen :: DynFlags -> RawCmmTop -> NatM [NatCmmTop Instr] -- | InstrBlocks are the insn sequences generated by the insn -- selectors. They are really trees of insns to facilitate fast -- appending, where a left-to-right traversal yields the insns in the -- correct order. type InstrBlock = OrdList Instr -- | Free regs map for SPARC module RegAlloc.Linear.SPARC.FreeRegs data FreeRegs FreeRegs :: !Word32 -> !Word32 -> !Word32 -> FreeRegs -- | A reg map where no regs are free to be allocated. noFreeRegs :: FreeRegs -- | The initial set of free regs. initFreeRegs :: FreeRegs -- | Get all the free registers of this class. getFreeRegs :: RegClass -> FreeRegs -> [RealReg] -- | Grab a register. allocateReg :: RealReg -> FreeRegs -> FreeRegs -- | Release a register from allocation. The register liveness information -- says that most regs die after a C call, but we still don't want to -- allocate to some of them. releaseReg :: RealReg -> FreeRegs -> FreeRegs bitMask :: Int -> Word32 showFreeRegs :: FreeRegs -> String instance Show FreeRegs module ZipCfg data Graph m l Graph :: (ZTail m l) -> (BlockEnv (Block m l)) -> Graph m l g_entry :: Graph m l -> (ZTail m l) g_blocks :: Graph m l -> (BlockEnv (Block m l)) data LGraph m l LGraph :: BlockId -> BlockEnv (Block m l) -> LGraph m l lg_entry :: LGraph m l -> BlockId lg_blocks :: LGraph m l -> BlockEnv (Block m l) data FGraph m l FGraph :: BlockId -> ZBlock m l -> BlockEnv (Block m l) -> FGraph m l fg_entry :: FGraph m l -> BlockId fg_focus :: FGraph m l -> ZBlock m l fg_others :: FGraph m l -> BlockEnv (Block m l) -- | Blocks and flow graphs; see Note [Kinds of graphs] data Block m l Block :: BlockId -> ZTail m l -> Block m l bid :: Block m l -> BlockId tail :: Block m l -> ZTail m l -- | And now the zipper. The focus is between the head and tail. We cannot -- ever focus on an inter-block edge. data ZBlock m l ZBlock :: (ZHead m) -> (ZTail m l) -> ZBlock m l data ZHead m ZFirst :: BlockId -> ZHead m ZHead :: (ZHead m) -> m -> ZHead m data ZTail m l ZLast :: (ZLast l) -> ZTail m l ZTail :: m -> (ZTail m l) -> ZTail m l -- | A basic block is a first node, followed by zero or more -- middle nodes, followed by a last node. data ZLast l LastExit :: ZLast l LastOther :: l -> ZLast l -- | insertBlock should not be used to replace an existing -- block but only to insert a new one insertBlock :: Block m l -> BlockEnv (Block m l) -> BlockEnv (Block m l) -- | We can't make a graph out of just any old 'last node' type. A last -- node has to be able to find its successors, and we need to be able to -- create and identify unconditional branches. We put these capabilities -- in a type class. Moreover, the property of having successors is also -- shared by Blocks and ZTails, so it is useful to have -- that property in a type class of its own. class HavingSuccessors b succs :: HavingSuccessors b => b -> [BlockId] fold_succs :: HavingSuccessors b => (BlockId -> a -> a) -> b -> a -> a class HavingSuccessors l => LastNode l mkBranchNode :: LastNode l => BlockId -> l isBranchNode :: LastNode l => l -> Bool branchNodeTarget :: LastNode l => l -> BlockId blockId :: Block m l -> BlockId zip :: ZBlock m l -> Block m l unzip :: Block m l -> ZBlock m l last :: ZBlock m l -> ZLast l goto_end :: ZBlock m l -> (ZHead m, ZLast l) -- | Take a head and tail and go to beginning or end. The asymmetry in the -- types and names is a bit unfortunate, but 'Block m l' is effectively -- '(BlockId, ZTail m l)' and is accepted in many more places. zipht :: ZHead m -> ZTail m l -> Block m l tailOfLast :: l -> ZTail m l splice_tail :: Graph m l -> ZTail m l -> Graph m l -- | We can splice a single-entry, single-exit LGraph onto a head or a -- tail. For a head, we have a head h followed by a LGraph -- g. The entry node of g gets joined to h, -- forming the entry into the new LGraph. The exit of g becomes -- the new head. For both arguments and results, the order of values is -- the order of control flow: before splicing, the head flows into the -- LGraph; after splicing, the LGraph flows into the head. Splicing a -- tail is the dual operation. (In order to maintain the -- order-means-control-flow convention, the orders are reversed.) -- -- For example, assume head = [L: x:=0] grph = (M, [M: stuff, -- blocks, N: y:=x; LastExit]) tail = [return (y,x)] -- -- Then splice_head head grph = ((L, [L: x:=0; goto M, M: stuff, -- blocks]) , N: y:=x) -- -- Then splice_tail grph tail = ( stuff , (???, [blocks, N: -- y:=x; return (y,x)]) splice_head :: ZHead m -> LGraph m l -> (LGraph m l, ZHead m) splice_head_only' :: ZHead m -> Graph m l -> LGraph m l splice_head' :: ZHead m -> Graph m l -> (BlockEnv (Block m l), ZHead m) -- | A safe operation -- -- Conversion to and from the environment form is convenient. For layout -- or dataflow, however, one will want to use postorder_dfs in -- order to get the blocks in an order that relates to the control flow -- in the procedure. of_block_list :: BlockId -> [Block m l] -> LGraph m l to_block_list :: LGraph m l -> [Block m l] -- | Conversion from LGraph to Graph graphOfLGraph :: LastNode l => LGraph m l -> Graph m l map_blocks :: (Block m l -> Block m' l') -> LGraph m l -> LGraph m' l' map_one_block :: (BlockId -> BlockId) -> (m -> m') -> (l -> l') -> Block m l -> Block m' l' map_nodes :: (BlockId -> BlockId) -> (m -> m') -> (l -> l') -> LGraph m l -> LGraph m' l' mapM_blocks :: Monad mm => (Block m l -> mm (Block m' l')) -> LGraph m l -> mm (LGraph m' l') -- | Traversal: postorder_dfs returns a list of blocks reachable -- from the entry node. This list has the following property: -- -- Say a back reference exists if one of a block's control-flow -- successors precedes it in the output list -- -- Then there are as few back references as possible -- -- The output is suitable for use in a forward dataflow problem. For a -- backward problem, simply reverse the list. (postorder_dfs is -- sufficiently tricky to implement that one doesn't want to try and -- maintain both forward and backward versions.) postorder_dfs :: LastNode l => LGraph m l -> [Block m l] postorder_dfs_from :: (HavingSuccessors b, LastNode l) => BlockEnv (Block m l) -> b -> [Block m l] -- | This is the most important traversal over this data structure. It -- drops unreachable code and puts blocks in an order that is good for -- solving forward dataflow problems quickly. The reverse order is good -- for solving backward dataflow problems quickly. The forward order is -- also reasonably good for emitting instructions, except that it will -- not usually exploit Forrest Baskett's trick of eliminating the -- unconditional branch from a loop. For that you would need a more -- serious analysis, probably based on dominators, to identify loop -- headers. -- -- The ubiquity of postorder_dfs is one reason for the ubiquity of -- the LGraph representation, when for most purposes the plain -- Graph representation is more mathematically elegant (but -- results in more complicated code). -- -- Here's an easy way to go wrong! Consider A -> [B,C] B -> D -- C -> D Then ordinary dfs would give [A,B,D,C] which has a -- back ref from C to D. Better to get [A,B,C,D] postorder_dfs_from_except :: (HavingSuccessors b, LastNode l) => BlockEnv (Block m l) -> b -> BlockSet -> [Block m l] -- | For layout, we fold over pairs of 'Block m l' and 'Maybe BlockId' in -- layout order. The 'Maybe BlockId', if present, identifies the block -- that will be the layout successor of the current block. This may be -- useful to help an emitter omit the final goto of a block that -- flows directly to its layout successor. -- -- For example: fold_layout f z [ L1:B1, L2:B2, L3:B3 ] = z $ f -- (L1:B1) (Just L2) $ f (L2:B2) (Just L3) $ f (L3:B3) -- Nothing where a $ f = f a fold_layout :: LastNode l => (Block m l -> Maybe BlockId -> a -> a) -> a -> LGraph m l -> a -- | We can also fold over blocks in an unspecified order. The -- ZipCfgExtras module provides a monadic version, which we -- haven't needed (else it would be here). fold_blocks :: (Block m l -> a -> a) -> a -> LGraph m l -> a -- | Fold from first to last fold_fwd_block :: (BlockId -> a -> a) -> (m -> a -> a) -> (ZLast l -> a -> a) -> Block m l -> a -> a -- | These translation functions are speculative. I hope eventually they -- will be used in the native-code back ends ---NR translate :: Monad tm => (m -> tm (LGraph m' l')) -> (l -> tm (LGraph m' l')) -> (LGraph m l -> tm (LGraph m' l')) pprLgraph :: (Outputable m, Outputable l, LastNode l) => LGraph m l -> SDoc pprGraph :: (Outputable m, Outputable l, LastNode l) => Graph m l -> SDoc entry :: LGraph m l -> FGraph m l instance Outputable l => Outputable (ZLast l) instance (Outputable m, Outputable l, LastNode l) => Outputable (Block m l) instance (Outputable m, Outputable l, LastNode l) => Outputable (LGraph m l) instance (Outputable m, Outputable l, LastNode l) => Outputable (Graph m l) instance (Outputable m, Outputable l) => Outputable (ZTail m l) instance LastNode l => HavingSuccessors (ZTail m l) instance LastNode l => HavingSuccessors (Block m l) instance LastNode l => HavingSuccessors (ZBlock m l) instance LastNode l => LastNode (ZLast l) instance HavingSuccessors l => HavingSuccessors (ZLast l) instance UserOfLocalRegs a => UserOfLocalRegs (ZLast a) module MkZipCfg data AGraph m l (<*>) :: AGraph m l -> AGraph m l -> AGraph m l catAGraphs :: [AGraph m l] -> AGraph m l -- | The string argument to freshBlockId was originally helpful in -- debugging the Quick C-- compiler, so I have kept it here even though -- at present it is thrown away at this spot---there's no reason a -- BlockId couldn't one day carry a string. freshBlockId :: MonadUnique m => String -> m BlockId -- | A graph is built up by splicing together graphs each containing a -- single node (where a label is considered a first node. The -- empty graph is a left and right unit for splicing. All of the AGraph -- constructors (even complex ones like mkIfThenElse, as well as -- the splicing operation *, are constant-time operations. emptyAGraph :: AGraph m l -- | This function provides access to fresh labels without requiring -- clients to be programmed monadically. withFreshLabel :: String -> (BlockId -> AGraph m l) -> AGraph m l withUnique :: (Unique -> AGraph m l) -> AGraph m l mkMiddle :: m -> AGraph m l mkMiddles :: [m] -> AGraph m l mkLast :: (Outputable m, Outputable l, LastNode l) => l -> AGraph m l mkZTail :: (Outputable m, Outputable l, LastNode l) => ZTail m l -> AGraph m l mkBranch :: (Outputable m, Outputable l, LastNode l) => BlockId -> AGraph m l mkLabel :: LastNode l => BlockId -> AGraph m l -- | For the structured control-flow constructs, a condition is represented -- as a function that takes as arguments the labels to goto on truth or -- falsehood. -- -- mkIfThenElse mk_cond then else = (mk_cond L1 L2) * L1: then -- * goto J * L2: else * goto J * J: -- -- where L1, L2, J are fresh mkIfThenElse :: (Outputable m, Outputable l, LastNode l) => (BlockId -> BlockId -> AGraph m l) -> AGraph m l -> AGraph m l -> AGraph m l mkWhileDo :: (Outputable m, Outputable l, LastNode l) => (BlockId -> BlockId -> AGraph m l) -> AGraph m l -> AGraph m l -- | The argument is an AGraph that has an empty entry sequence and no exit -- sequence. The result is a new AGraph that has an empty entry sequence -- connected to an empty exit sequence, with the original graph sitting -- to the side out-of-line. -- -- Example: mkMiddle (x = 3) * outOfLine (mkLabel L * -- ...stuff...) * mkMiddle (y = x) Control will flow directly from -- x=3 to y=x; the block starting with L is on the side. -- -- N.B. algebraically forall g g' : g * outOfLine g' == outOfLine -- g' * g outOfLine :: (LastNode l, Outputable m, Outputable l) => AGraph m l -> AGraph m l -- | The functions below build Graphs directly; for convenience, they are -- included here with the rest of the constructor functions. emptyGraph :: Graph m l graphOfMiddles :: [m] -> Graph m l graphOfZTail :: ZTail m l -> Graph m l lgraphOfAGraph :: AGraph m l -> UniqSM (LGraph m l) -- | Converting an abstract graph to a concrete form is expensive: the cost -- is linear in the number of nodes in the answer, plus N log N in the -- number of basic blocks. The conversion is also monadic because it may -- require the allocation of fresh, unique labels. graphOfAGraph :: AGraph m l -> UniqSM (Graph m l) labelAGraph :: BlockId -> AGraph m l -> UniqSM (LGraph m l) pprAGraph :: (Outputable m, LastNode l, Outputable l) => AGraph m l -> UniqSM SDoc module CmmZipUtil -- | Compute the predecessors of each reachable block zipPreds :: LastNode l => LGraph m l -> BlockEnv BlockSet -- | Tell if a graph gives a block a unique predecessor. For efficiency, -- this function is designed to be partially applied. givesUniquePredecessorTo :: LastNode l => LGraph m l -> BlockId -> Bool -- | Optimisation fuel is used to control the amount of work the optimiser -- does. -- -- Every optimisation step consumes a certain amount of fuel and stops -- when it runs out of fuel. This can be used e.g. to debug optimiser -- bugs: Run the optimiser with varying amount of fuel to find out the -- exact number of steps where a bug is introduced in the output. module OptimizationFuel data OptimizationFuel canRewriteWithFuel :: OptimizationFuel -> Bool maybeRewriteWithFuel :: OptimizationFuel -> Maybe a -> Maybe a oneLessFuel :: OptimizationFuel -> OptimizationFuel data OptFuelState initOptFuelState :: IO OptFuelState tankFilledTo :: Int -> OptimizationFuel diffFuel :: OptimizationFuel -> OptimizationFuel -> Int type FuelConsumer a = OptimizationFuel -> (a, OptimizationFuel) class Monad m => FuelUsingMonad m fuelRemaining :: FuelUsingMonad m => m OptimizationFuel fuelDecrement :: FuelUsingMonad m => String -> OptimizationFuel -> OptimizationFuel -> m () fuelDec1 :: FuelUsingMonad m => m () fuelExhausted :: FuelUsingMonad m => m Bool lastFuelPass :: FuelUsingMonad m => m String data FuelState runFuelIO :: OptFuelState -> FuelMonad a -> IO a fuelConsumingPass :: String -> FuelConsumer a -> FuelMonad a data FuelMonad a liftUniq :: UniqSM x -> FuelMonad x lGraphOfGraph :: Graph m l -> FuelMonad (LGraph m l) instance Show OptimizationFuel instance FuelUsingMonad FuelMonad instance MonadUnique FuelMonad instance Monad FuelMonad module DFMonad data DataflowLattice a DataflowLattice :: String -> a -> (a -> a -> TxRes a) -> Bool -> DataflowLattice a fact_name :: DataflowLattice a -> String fact_bot :: DataflowLattice a -> a -- | compute join of two args; something changed iff join is greater than -- 2nd arg fact_add_to :: DataflowLattice a -> a -> a -> TxRes a fact_do_logging :: DataflowLattice a -> Bool class DataflowAnalysis m markFactsUnchanged :: DataflowAnalysis m => m f () factsStatus :: DataflowAnalysis m => m f ChangeFlag subAnalysis :: DataflowAnalysis m => m f a -> m f a getFact :: DataflowAnalysis m => BlockId -> m f f setFact :: (DataflowAnalysis m, Outputable f) => BlockId -> f -> m f () getExitFact :: DataflowAnalysis m => m f f setExitFact :: (DataflowAnalysis m, Outputable f) => f -> m f () checkFactMatch :: (DataflowAnalysis m, Outputable f) => BlockId -> f -> m f () botFact :: DataflowAnalysis m => m f f forgetFact :: DataflowAnalysis m => BlockId -> m f () addLastOutFact :: DataflowAnalysis m => (BlockId, f) -> m f () bareLastOutFacts :: DataflowAnalysis m => m f [(BlockId, f)] forgetLastOutFacts :: DataflowAnalysis m => m f () getAllFacts :: DataflowAnalysis m => m f (BlockEnv f) setAllFacts :: DataflowAnalysis m => BlockEnv f -> m f () factsEnv :: (DataflowAnalysis m, Monad (m f)) => m f (BlockId -> f) type DFM fact a = DFM' FuelMonad fact a runDFM :: Monad m => DataflowLattice f -> DFM' m f a -> m a liftToDFM :: FuelMonad x -> DFM f x markGraphRewritten :: Monad m => DFM' m f () graphWasRewritten :: DFM f ChangeFlag instance MonadUnique (DFM' FuelMonad f) instance FuelUsingMonad (DFM' FuelMonad f) instance Monad m => Monad (DFM' m f) instance Monad m => DataflowAnalysis (DFM' m) module ZipDataflow class (Outputable m, Outputable l, LastNode l, Outputable (LGraph m l)) => DebugNodes m l data RewritingDepth RewriteShallow :: RewritingDepth RewriteDeep :: RewritingDepth newtype LastOutFacts a -- | These are facts flowing out of a last node to the node's successors. -- They are either to be set (if they pertain to the graph currently -- under analysis) or propagated out of a sub-analysis LastOutFacts :: [(BlockId, a)] -> LastOutFacts a zdfSolveFrom :: (DataflowSolverDirection transfers fixedpt, DebugNodes m l, Outputable a) => BlockEnv a -> PassName -> DataflowLattice a -> transfers m l a -> a -> Graph m l -> FuelMonad (fixedpt m l a ()) zdfRewriteFrom :: (DataflowDirection transfers fixedpt rewrites, DebugNodes m l, Outputable a) => RewritingDepth -> BlockEnv a -> PassName -> DataflowLattice a -> transfers m l a -> rewrites m l a -> a -> Graph m l -> FuelMonad (fixedpt m l a (Graph m l)) zdfSolveFromL :: (DataflowSolverDirection transfers fixedpt, DebugNodes m l, Outputable a) => BlockEnv a -> PassName -> DataflowLattice a -> transfers m l a -> a -> LGraph m l -> FuelMonad (fixedpt m l a ()) -- | For a forward transfer, you're given the fact on a node's inedge and -- you compute the fact on the outedge. Because a last node may have -- multiple outedges, each pointing to a labelled block, so instead of a -- fact it produces a list of (BlockId, fact) pairs. data ForwardTransfers middle last a ForwardTransfers :: (BlockId -> a -> a) -> (middle -> a -> a) -> (last -> a -> LastOutFacts a) -> (a -> a) -> ForwardTransfers middle last a ft_first_out :: ForwardTransfers middle last a -> BlockId -> a -> a ft_middle_out :: ForwardTransfers middle last a -> middle -> a -> a ft_last_outs :: ForwardTransfers middle last a -> last -> a -> LastOutFacts a ft_exit_out :: ForwardTransfers middle last a -> a -> a -- | For a backward transfer, you're given the fact on a node's outedge and -- you compute the fact on the inedge. Facts have type a. A last -- node may have multiple outedges, each pointing to a labelled block, so -- instead of a fact it is given a mapping from BlockId to fact. data BackwardTransfers middle last a BackwardTransfers :: (BlockId -> a -> a) -> (middle -> a -> a) -> (last -> (BlockId -> a) -> a) -> BackwardTransfers middle last a bt_first_in :: BackwardTransfers middle last a -> BlockId -> a -> a bt_middle_in :: BackwardTransfers middle last a -> middle -> a -> a bt_last_in :: BackwardTransfers middle last a -> last -> (BlockId -> a) -> a -- | A forward rewrite takes the same inputs as a forward transfer, but -- instead of producing a fact, it produces a replacement graph or -- Nothing. data ForwardRewrites middle last a ForwardRewrites :: (BlockId -> a -> Maybe (AGraph middle last)) -> (middle -> a -> Maybe (AGraph middle last)) -> (last -> a -> Maybe (AGraph middle last)) -> (a -> Maybe (AGraph middle last)) -> ForwardRewrites middle last a fr_first :: ForwardRewrites middle last a -> BlockId -> a -> Maybe (AGraph middle last) fr_middle :: ForwardRewrites middle last a -> middle -> a -> Maybe (AGraph middle last) fr_last :: ForwardRewrites middle last a -> last -> a -> Maybe (AGraph middle last) fr_exit :: ForwardRewrites middle last a -> a -> Maybe (AGraph middle last) -- | A backward rewrite takes the same inputs as a backward transfer, but -- instead of producing a fact, it produces a replacement graph or -- Nothing. data BackwardRewrites middle last a BackwardRewrites :: (BlockId -> a -> Maybe (AGraph middle last)) -> (middle -> a -> Maybe (AGraph middle last)) -> (last -> (BlockId -> a) -> Maybe (AGraph middle last)) -> Maybe (AGraph middle last) -> BackwardRewrites middle last a br_first :: BackwardRewrites middle last a -> BlockId -> a -> Maybe (AGraph middle last) br_middle :: BackwardRewrites middle last a -> middle -> a -> Maybe (AGraph middle last) br_last :: BackwardRewrites middle last a -> last -> (BlockId -> a) -> Maybe (AGraph middle last) br_exit :: BackwardRewrites middle last a -> Maybe (AGraph middle last) -- | A forward problem needs the common fields, plus the facts on the -- outedges. data ForwardFixedPoint m l fact a -- | The common fixed point is sufficient for a backward problem. type BackwardFixedPoint = CommonFixedPoint zdfFpFacts :: FixedPoint fp => fp m l fact a -> BlockEnv fact zdfFpOutputFact :: FixedPoint fp => fp m l fact a -> fact zdfGraphChanged :: FixedPoint fp => fp m l fact a -> ChangeFlag zdfDecoratedGraph :: FixedPoint fp => fp m l fact a -> Graph (fact, m) (fact, l) zdfFpContents :: FixedPoint fp => fp m l fact a -> a zdfFpLastOuts :: ForwardFixedPoint m l fact a -> LastOutFacts fact zdfBRewriteFromL :: (DebugNodes m l, Outputable a) => RewritingDepth -> BlockEnv a -> PassName -> DataflowLattice a -> BackwardTransfers m l a -> BackwardRewrites m l a -> a -> LGraph m l -> FuelMonad (BackwardFixedPoint m l a (LGraph m l)) zdfFRewriteFromL :: (DebugNodes m l, Outputable a) => RewritingDepth -> BlockEnv a -> PassName -> DataflowLattice a -> ForwardTransfers m l a -> ForwardRewrites m l a -> a -> LGraph m l -> FuelMonad (ForwardFixedPoint m l a (LGraph m l)) instance FixedPoint ForwardFixedPoint instance FixedPoint CommonFixedPoint instance DataflowDirection BackwardTransfers BackwardFixedPoint BackwardRewrites instance DataflowDirection ForwardTransfers ForwardFixedPoint ForwardRewrites instance DataflowSolverDirection BackwardTransfers BackwardFixedPoint instance DataflowSolverDirection ForwardTransfers ForwardFixedPoint module ZipCfgExtras module ZipCfgCmmRep type CmmZ = GenCmm CmmStatic CmmInfo (CmmStackInfo, CmmGraph) type CmmTopZ = GenCmmTop CmmStatic CmmInfo (CmmStackInfo, CmmGraph) type CmmGraph = LGraph Middle Last type CmmBlock = Block Middle Last type CmmAGraph = AGraph Middle Last data Middle MidComment :: FastString -> Middle MidAssign :: CmmReg -> CmmExpr -> Middle MidStore :: CmmExpr -> CmmExpr -> Middle MidForeignCall :: ForeignSafety -> MidCallTarget -> CmmFormals -> CmmActuals -> Middle data Last LastBranch :: BlockId -> Last LastCondBranch :: CmmExpr -> BlockId -> BlockId -> Last cml_pred :: Last -> CmmExpr cml_true :: Last -> BlockId cml_false :: Last -> BlockId LastSwitch :: CmmExpr -> [Maybe BlockId] -> Last LastCall :: CmmExpr -> Maybe BlockId -> ByteOff -> ByteOff -> Maybe ByteOff -> Last cml_target :: Last -> CmmExpr cml_cont :: Last -> Maybe BlockId cml_args :: Last -> ByteOff cml_ret_args :: Last -> ByteOff cml_ret_off :: Last -> Maybe ByteOff data MidCallTarget ForeignTarget :: CmmExpr -> ForeignConvention -> MidCallTarget PrimTarget :: CallishMachOp -> MidCallTarget type UpdFrameOffset = ByteOff data Convention NativeDirectCall :: Convention NativeNodeCall :: Convention NativeReturn :: Convention Slow :: Convention GC :: Convention PrimOpCall :: Convention PrimOpReturn :: Convention Foreign :: ForeignConvention -> Convention Private :: Convention data ForeignConvention ForeignConvention :: CCallConv -> [ForeignHint] -> [ForeignHint] -> ForeignConvention data ForeignSafety Unsafe :: ForeignSafety Safe :: BlockId -> UpdFrameOffset -> ForeignSafety data ValueDirection Arguments :: ValueDirection Results :: ValueDirection data ForeignHint NoHint :: ForeignHint AddrHint :: ForeignHint SignedHint :: ForeignHint type CmmBackwardFixedPoint a = BackwardFixedPoint Middle Last a () type CmmForwardFixedPoint a = ForwardFixedPoint Middle Last a () pprHinted :: Outputable a => CmmHinted a -> SDoc insertBetween :: MonadUnique m => CmmBlock -> [Middle] -> BlockId -> m (CmmBlock, [CmmBlock]) mapExpMiddle :: (CmmExpr -> CmmExpr) -> Middle -> Middle mapExpLast :: (CmmExpr -> CmmExpr) -> Last -> Last mapExpDeepMiddle :: (CmmExpr -> CmmExpr) -> Middle -> Middle mapExpDeepLast :: (CmmExpr -> CmmExpr) -> Last -> Last foldExpMiddle :: (CmmExpr -> z -> z) -> Middle -> z -> z foldExpLast :: (CmmExpr -> z -> z) -> Last -> z -> z foldExpDeepMiddle :: (CmmExpr -> z -> z) -> Middle -> z -> z foldExpDeepLast :: (CmmExpr -> z -> z) -> Last -> z -> z joinOuts :: DataflowLattice a -> (BlockId -> a) -> Last -> a instance Eq ForeignConvention instance Eq Convention instance Eq MidCallTarget instance Eq ForeignSafety instance Eq Middle instance Eq ValueDirection instance DebugNodes Middle Last instance Outputable ValueDirection instance Outputable ForeignConvention instance Outputable Convention instance Outputable Last instance Outputable Middle instance DefinerOfSlots l => DefinerOfSlots (ZLast l) instance DefinerOfSlots Last instance DefinerOfSlots Middle instance UserOfSlots l => UserOfSlots (ZLast l) instance UserOfSlots Last instance UserOfSlots Middle instance DefinerOfLocalRegs Last instance DefinerOfLocalRegs Middle instance UserOfLocalRegs Last instance UserOfSlots a => UserOfSlots (Maybe a) instance UserOfLocalRegs a => UserOfLocalRegs (Maybe a) instance UserOfSlots MidCallTarget instance UserOfLocalRegs MidCallTarget instance UserOfLocalRegs Middle instance LastNode Last instance HavingSuccessors Last module CmmCallConv data ParamLocation a RegisterParam :: GlobalReg -> ParamLocation a StackParam :: a -> ParamLocation a type ArgumentFormat a b = [(a, ParamLocation b)] assignArguments :: (a -> CmmType) -> [a] -> ArgumentFormat a WordOff -- | JD: For the new stack story, I want arguments passed on the stack to -- manifest as positive offsets in a CallArea, not negative offsets from -- the stack pointer. Also, I want byte offsets, not word offsets. assignArgumentsPos :: Outputable a => Convention -> (a -> CmmType) -> [a] -> ArgumentFormat a ByteOff argumentsSize :: (a -> CmmType) -> [a] -> WordOff instance Outputable a => Outputable (ParamLocation a) module MkZipCfgCmm mkNop :: CmmAGraph mkAssign :: CmmReg -> CmmExpr -> CmmAGraph mkStore :: CmmExpr -> CmmExpr -> CmmAGraph mkCall :: CmmExpr -> (Convention, Convention) -> CmmFormals -> CmmActuals -> UpdFrameOffset -> CmmAGraph mkCmmCall :: CmmExpr -> CmmFormals -> CmmActuals -> UpdFrameOffset -> CmmAGraph mkSafeCall :: MidCallTarget -> CmmFormals -> CmmActuals -> UpdFrameOffset -> CmmAGraph mkUnsafeCall :: MidCallTarget -> CmmFormals -> CmmActuals -> CmmAGraph mkFinalCall :: CmmExpr -> CCallConv -> CmmActuals -> UpdFrameOffset -> CmmAGraph mkJump :: CmmExpr -> CmmActuals -> UpdFrameOffset -> CmmAGraph mkForeignJump :: Convention -> CmmExpr -> CmmActuals -> UpdFrameOffset -> CmmAGraph mkJumpGC :: CmmExpr -> CmmActuals -> UpdFrameOffset -> CmmAGraph mkCbranch :: CmmExpr -> BlockId -> BlockId -> CmmAGraph mkSwitch :: CmmExpr -> [Maybe BlockId] -> CmmAGraph mkReturn :: CmmExpr -> CmmActuals -> UpdFrameOffset -> CmmAGraph mkReturnSimple :: CmmActuals -> UpdFrameOffset -> CmmAGraph mkComment :: FastString -> CmmAGraph copyInOflow :: Convention -> Area -> CmmFormals -> (Int, CmmAGraph) copyInSlot :: Convention -> CmmFormals -> CmmAGraph copyOutOflow :: Convention -> Transfer -> Area -> CmmActuals -> UpdFrameOffset -> (Int, [Middle]) copyOutSlot :: Convention -> [LocalReg] -> [Middle] mkEntry :: BlockId -> Convention -> CmmFormals -> (Int, CmmAGraph) mkCmmIfThenElse :: CmmExpr -> CmmAGraph -> CmmAGraph -> CmmAGraph mkCmmIfThen :: CmmExpr -> CmmAGraph -> CmmAGraph mkCmmWhileDo :: CmmExpr -> CmmAGraph -> CmmAGraph (<*>) :: AGraph m l -> AGraph m l -> AGraph m l catAGraphs :: [AGraph m l] -> AGraph m l mkLabel :: LastNode l => BlockId -> AGraph m l mkBranch :: (Outputable m, Outputable l, LastNode l) => BlockId -> AGraph m l -- | A graph is built up by splicing together graphs each containing a -- single node (where a label is considered a first node. The -- empty graph is a left and right unit for splicing. All of the AGraph -- constructors (even complex ones like mkIfThenElse, as well as -- the splicing operation *, are constant-time operations. emptyAGraph :: AGraph m l -- | This function provides access to fresh labels without requiring -- clients to be programmed monadically. withFreshLabel :: String -> (BlockId -> AGraph m l) -> AGraph m l withUnique :: (Unique -> AGraph m l) -> AGraph m l -- | The argument is an AGraph that has an empty entry sequence and no exit -- sequence. The result is a new AGraph that has an empty entry sequence -- connected to an empty exit sequence, with the original graph sitting -- to the side out-of-line. -- -- Example: mkMiddle (x = 3) * outOfLine (mkLabel L * -- ...stuff...) * mkMiddle (y = x) Control will flow directly from -- x=3 to y=x; the block starting with L is on the side. -- -- N.B. algebraically forall g g' : g * outOfLine g' == outOfLine -- g' * g outOfLine :: (LastNode l, Outputable m, Outputable l) => AGraph m l -> AGraph m l lgraphOfAGraph :: AGraph m l -> UniqSM (LGraph m l) -- | Converting an abstract graph to a concrete form is expensive: the cost -- is linear in the number of nodes in the answer, plus N log N in the -- number of basic blocks. The conversion is also monadic because it may -- require the allocation of fresh, unique labels. graphOfAGraph :: AGraph m l -> UniqSM (Graph m l) labelAGraph :: BlockId -> AGraph m l -> UniqSM (LGraph m l) type CmmZ = GenCmm CmmStatic CmmInfo (CmmStackInfo, CmmGraph) type CmmTopZ = GenCmmTop CmmStatic CmmInfo (CmmStackInfo, CmmGraph) type CmmGraph = LGraph Middle Last type CmmBlock = Block Middle Last type CmmAGraph = AGraph Middle Last type CmmStackInfo = (ByteOff, Maybe ByteOff) data Middle data Last data Convention NativeDirectCall :: Convention NativeNodeCall :: Convention NativeReturn :: Convention Slow :: Convention GC :: Convention PrimOpCall :: Convention PrimOpReturn :: Convention Foreign :: ForeignConvention -> Convention Private :: Convention data ForeignConvention ForeignConvention :: CCallConv -> [ForeignHint] -> [ForeignHint] -> ForeignConvention data MidCallTarget ForeignTarget :: CmmExpr -> ForeignConvention -> MidCallTarget PrimTarget :: CallishMachOp -> MidCallTarget data Transfer Call :: Transfer Jump :: Transfer Ret :: Transfer stackStubExpr :: Width -> CmmExpr pprAGraph :: (Outputable m, LastNode l, Outputable l) => AGraph m l -> UniqSM SDoc instance Eq Transfer module CmmCommonBlockElimZ elimCommonBlocks :: CmmGraph -> CmmGraph module PprCmmZ -- | The purpose of this function is to print a Cmm zipper graph as if -- it were a Cmm program. The objective is dodgy, so it's -- unsurprising parts of the code are dodgy as well. pprCmmGraphLikeCmm :: CmmGraph -> SDoc module CmmContFlowOpt runCmmOpts :: Tx g -> Tx (GenCmm d h g) cmmCfgOpts :: Tx (ListGraph CmmStmt) cmmCfgOptsZ :: Tx (a, CmmGraph) branchChainElimZ :: Tx CmmGraph removeUnreachableBlocksZ :: Tx CmmGraph predMap :: LastNode l => LGraph m l -> BlockEnv BlockSet replaceLabelsZ :: BlockEnv BlockId -> CmmGraph -> CmmGraph replaceBranches :: BlockEnv BlockId -> CmmGraph -> CmmGraph runCmmContFlowOptsZs :: [CmmZ] -> [CmmZ] module CmmCvt cmmToZgraph :: GenCmm d h (ListGraph CmmStmt) -> UniqSM (GenCmm d h (CmmStackInfo, CmmGraph)) cmmOfZgraph :: GenCmm d h (CmmStackInfo, CmmGraph) -> GenCmm d h (ListGraph CmmStmt) module CmmLiveZ -- | The variables live on entry to a block type CmmLive = RegSet -- | Calculated liveness info for a CmmGraph cmmLivenessZ :: CmmGraph -> FuelMonad BlockEntryLiveness -- | The dataflow lattice liveLattice :: DataflowLattice CmmLive middleLiveness :: Middle -> CmmLive -> CmmLive -- | On entry to the procedure, there had better not be any LocalReg's -- live-in. noLiveOnEntry :: BlockId -> CmmLive -> a -> a module CmmSpillReload data DualLive DualLive :: RegSet -> RegSet -> DualLive on_stack :: DualLive -> RegSet in_regs :: DualLive -> RegSet dualLiveLattice :: DataflowLattice DualLive dualLiveTransfers :: BlockId -> BlockSet -> BackwardTransfers Middle Last DualLive dualLiveness :: BlockSet -> LGraph Middle Last -> FuelMonad (BlockEnv DualLive) dualLivenessWithInsertion :: BlockSet -> (LGraph Middle Last) -> FuelMonad (LGraph Middle Last) availRegsLattice :: DataflowLattice AvailRegs cmmAvailableReloads :: LGraph Middle Last -> FuelMonad (BlockEnv AvailRegs) insertLateReloads :: (LGraph Middle Last) -> FuelMonad (LGraph Middle Last) removeDeadAssignmentsAndReloads :: BlockSet -> (LGraph Middle Last) -> FuelMonad (LGraph Middle Last) instance Outputable AvailRegs instance Outputable DualLive module StackColor fold_edge_facts_b :: LastNode l => (DualLive -> a -> a) -> BackwardTransfers m l DualLive -> LGraph m l -> (BlockId -> DualLive) -> a -> a foldConflicts :: (RegSet -> a -> a) -> a -> LGraph Middle Last -> FuelMonad a type IGraph = Graph LocalReg SlotClass StackPlacement type ClassCount = [(SlotClass, Int)] buildIGraphAndCounts :: LGraph Middle Last -> FuelMonad (IGraph, ClassCount) -- | Add some conflict edges to the graph. Conflicts between virtual and -- real regs are recorded as exclusions. graphAddConflictSet :: RegSet -> IGraph -> IGraph slotClass :: LocalReg -> SlotClass -- | number of placements available is from class and all larger classes mkSizeOf :: ClassCount -> (SlotClass -> Int) module CmmLint cmmLint :: (Outputable d, Outputable h) => GenCmm d h (ListGraph CmmStmt) -> Maybe SDoc cmmLintTop :: (Outputable d, Outputable h) => GenCmmTop d h (ListGraph CmmStmt) -> Maybe SDoc instance Monad CmmLint module StgCmmClosure data SMRep type DynTag = Int tagForCon :: DataCon -> DynTag isSmallFamily :: Int -> Bool type ConTagZ = Int dataConTagZ :: DataCon -> ConTagZ data ArgDescr ArgSpec :: !StgHalfWord -> ArgDescr ArgGen :: Liveness -> ArgDescr data Liveness SmallLiveness :: StgWord -> Liveness BigLiveness :: CLabel -> Liveness data C_SRT NoC_SRT :: C_SRT C_SRT :: !CLabel -> !WordOff -> !StgHalfWord -> C_SRT needsSRT :: C_SRT -> Bool isVoidRep :: PrimRep -> Bool isGcPtrRep :: PrimRep -> Bool addIdReps :: [Id] -> [(PrimRep, Id)] addArgReps :: [StgArg] -> [(PrimRep, StgArg)] argPrimRep :: StgArg -> PrimRep data LambdaFormInfo data StandardFormInfo mkLFThunk :: Type -> TopLevelFlag -> [Id] -> UpdateFlag -> LambdaFormInfo mkLFReEntrant :: TopLevelFlag -> [Id] -> [Id] -> ArgDescr -> LambdaFormInfo mkConLFInfo :: DataCon -> LambdaFormInfo mkSelectorLFInfo :: Id -> Int -> Bool -> LambdaFormInfo mkApLFInfo :: Id -> UpdateFlag -> Arity -> LambdaFormInfo mkLFImported :: Id -> LambdaFormInfo mkLFArgument :: Id -> LambdaFormInfo mkLFLetNoEscape :: LambdaFormInfo lfDynTag :: LambdaFormInfo -> DynTag data ClosureInfo mkClosureInfo :: Bool -> Id -> LambdaFormInfo -> Int -> Int -> C_SRT -> String -> ClosureInfo mkConInfo :: Bool -> DataCon -> Int -> Int -> ClosureInfo maybeIsLFCon :: LambdaFormInfo -> Maybe DataCon closureSize :: ClosureInfo -> WordOff closureNonHdrSize :: ClosureInfo -> WordOff closureGoodStuffSize :: ClosureInfo -> WordOff closurePtrsSize :: ClosureInfo -> WordOff slopSize :: ClosureInfo -> WordOff closureName :: ClosureInfo -> Name infoTableLabelFromCI :: ClosureInfo -> CLabel closureLabelFromCI :: ClosureInfo -> CLabel closureTypeInfo :: ClosureInfo -> ((ConstrDescription -> ClosureTypeInfo) -> DataCon -> CLabel -> a) -> (ClosureTypeInfo -> a) -> a closureLFInfo :: ClosureInfo -> LambdaFormInfo isLFThunk :: LambdaFormInfo -> Bool closureSMRep :: ClosureInfo -> SMRep closureUpdReqd :: ClosureInfo -> Bool closureNeedsUpdSpace :: ClosureInfo -> Bool closureIsThunk :: ClosureInfo -> Bool closureSingleEntry :: ClosureInfo -> Bool closureReEntrant :: ClosureInfo -> Bool isConstrClosure_maybe :: ClosureInfo -> Maybe DataCon closureFunInfo :: ClosureInfo -> Maybe (Int, ArgDescr) isStandardFormThunk :: LambdaFormInfo -> Bool isKnownFun :: LambdaFormInfo -> Bool funTag :: ClosureInfo -> DynTag tagForArity :: Int -> DynTag enterIdLabel :: Name -> CafInfo -> CLabel enterLocalIdLabel :: Name -> CafInfo -> CLabel nodeMustPointToIt :: LambdaFormInfo -> Bool data CallMethod EnterIt :: CallMethod JumpToIt :: CallMethod ReturnIt :: CallMethod SlowCall :: CallMethod DirectEntry :: CLabel -> Int -> CallMethod getCallMethod :: DynFlags -> Name -> CafInfo -> LambdaFormInfo -> Int -> CallMethod blackHoleOnEntry :: DynFlags -> ClosureInfo -> Bool getClosureType :: Bool -> WordOff -> LambdaFormInfo -> ClosureType isToplevClosure :: ClosureInfo -> Bool closureValDescr :: ClosureInfo -> String closureTypeDescr :: ClosureInfo -> String isStaticClosure :: ClosureInfo -> Bool cafBlackHoleClosureInfo :: ClosureInfo -> ClosureInfo staticClosureNeedsLink :: ClosureInfo -> Bool clHasCafRefs :: ClosureInfo -> CafInfo module Lexer data Token ITas :: Token ITcase :: Token ITclass :: Token ITdata :: Token ITdefault :: Token ITderiving :: Token ITdo :: Token ITelse :: Token IThiding :: Token ITif :: Token ITimport :: Token ITin :: Token ITinfix :: Token ITinfixl :: Token ITinfixr :: Token ITinstance :: Token ITlet :: Token ITmodule :: Token ITnewtype :: Token ITof :: Token ITqualified :: Token ITthen :: Token ITtype :: Token ITwhere :: Token ITscc :: Token ITforall :: Token ITforeign :: Token ITexport :: Token ITlabel :: Token ITdynamic :: Token ITsafe :: Token ITthreadsafe :: Token ITunsafe :: Token ITstdcallconv :: Token ITccallconv :: Token ITprimcallconv :: Token ITmdo :: Token ITfamily :: Token ITgroup :: Token ITby :: Token ITusing :: Token ITinline_prag :: InlineSpec -> RuleMatchInfo -> Token ITspec_prag :: Token ITspec_inline_prag :: Bool -> Token ITsource_prag :: Token ITrules_prag :: Token ITwarning_prag :: Token ITdeprecated_prag :: Token ITline_prag :: Token ITscc_prag :: Token ITgenerated_prag :: Token ITcore_prag :: Token ITunpack_prag :: Token ITann_prag :: Token ITclose_prag :: Token IToptions_prag :: String -> Token ITinclude_prag :: String -> Token ITlanguage_prag :: Token ITdotdot :: Token ITcolon :: Token ITdcolon :: Token ITequal :: Token ITlam :: Token ITvbar :: Token ITlarrow :: Token ITrarrow :: Token ITat :: Token ITtilde :: Token ITdarrow :: Token ITminus :: Token ITbang :: Token ITstar :: Token ITdot :: Token ITbiglam :: Token ITocurly :: Token ITccurly :: Token ITocurlybar :: Token ITccurlybar :: Token -- | }, for type applications ITvocurly :: Token ITvccurly :: Token ITobrack :: Token ITopabrack :: Token ITcpabrack :: Token ITcbrack :: Token IToparen :: Token ITcparen :: Token IToubxparen :: Token ITcubxparen :: Token ITsemi :: Token ITcomma :: Token ITunderscore :: Token ITbackquote :: Token ITvarid :: FastString -> Token ITconid :: FastString -> Token ITvarsym :: FastString -> Token ITconsym :: FastString -> Token ITqvarid :: (FastString, FastString) -> Token ITqconid :: (FastString, FastString) -> Token ITqvarsym :: (FastString, FastString) -> Token ITqconsym :: (FastString, FastString) -> Token ITprefixqvarsym :: (FastString, FastString) -> Token ITprefixqconsym :: (FastString, FastString) -> Token ITdupipvarid :: FastString -> Token ITchar :: Char -> Token ITstring :: FastString -> Token ITinteger :: Integer -> Token ITrational :: Rational -> Token ITprimchar :: Char -> Token ITprimstring :: FastString -> Token ITprimint :: Integer -> Token ITprimword :: Integer -> Token ITprimfloat :: Rational -> Token ITprimdouble :: Rational -> Token ITopenExpQuote :: Token ITopenPatQuote :: Token ITopenDecQuote :: Token ITopenTypQuote :: Token ITcloseQuote :: Token ITidEscape :: FastString -> Token ITparenEscape :: Token ITvarQuote :: Token ITtyQuote :: Token ITquasiQuote :: (FastString, FastString, SrcSpan) -> Token ITproc :: Token ITrec :: Token IToparenbar :: Token ITcparenbar :: Token ITlarrowtail :: Token ITrarrowtail :: Token ITLarrowtail :: Token ITRarrowtail :: Token ITunknown :: String -> Token ITeof :: Token ITdocCommentNext :: String -> Token ITdocCommentPrev :: String -> Token ITdocCommentNamed :: String -> Token ITdocSection :: Int -> String -> Token ITdocOptions :: String -> Token ITdocOptionsOld :: String -> Token ITlineComment :: String -> Token ITblockComment :: String -> Token lexer :: (Located Token -> P a) -> P a pragState :: DynFlags -> StringBuffer -> SrcLoc -> PState mkPState :: DynFlags -> StringBuffer -> SrcLoc -> PState data PState PState :: StringBuffer -> DynFlags -> Messages -> SrcSpan -> !Int -> SrcLoc -> !Int -> [LayoutContext] -> [Int] -> [Located Token] -> Maybe (Located Token) -> SrcSpan -> [ALRContext] -> Maybe ALRLayout -> Bool -> PState buffer :: PState -> StringBuffer dflags :: PState -> DynFlags messages :: PState -> Messages last_loc :: PState -> SrcSpan last_len :: PState -> !Int loc :: PState -> SrcLoc extsBitmap :: PState -> !Int context :: PState -> [LayoutContext] lex_state :: PState -> [Int] alr_pending_implicit_tokens :: PState -> [Located Token] alr_next_token :: PState -> Maybe (Located Token) alr_last_loc :: PState -> SrcSpan alr_context :: PState -> [ALRContext] alr_expecting_ocurly :: PState -> Maybe ALRLayout alr_justClosedExplicitLetBlock :: PState -> Bool newtype P a P :: (PState -> ParseResult a) -> P a unP :: P a -> PState -> ParseResult a data ParseResult a POk :: PState -> a -> ParseResult a PFailed :: SrcSpan -> Message -> ParseResult a getSrcLoc :: P SrcLoc getPState :: P PState getDynFlags :: P DynFlags withThisPackage :: (PackageId -> a) -> P a failLocMsgP :: SrcLoc -> SrcLoc -> String -> P a failSpanMsgP :: SrcSpan -> SDoc -> P a srcParseFail :: P a getMessages :: PState -> Messages popContext :: P () pushCurrentContext :: P () setLastToken :: SrcSpan -> Int -> P () setSrcLoc :: SrcLoc -> P () getLexState :: P Int popLexState :: P Int pushLexState :: Int -> P () extension :: (Int -> Bool) -> P Bool bangPatEnabled :: Int -> Bool datatypeContextsEnabled :: Int -> Bool addWarning :: DynFlag -> SrcSpan -> SDoc -> P () lexTokenStream :: StringBuffer -> SrcLoc -> DynFlags -> ParseResult [Located Token] instance Show LayoutContext instance Monad P module RdrHsSyn extractHsTyRdrTyVars :: LHsType RdrName -> [Located RdrName] extractHsRhoRdrTyVars :: LHsContext RdrName -> LHsType RdrName -> [Located RdrName] extractGenericPatTyVars :: LHsBinds RdrName -> [Located RdrName] mkHsOpApp :: LHsExpr id -> id -> LHsExpr id -> HsExpr id mkHsIntegral :: Integer -> PostTcType -> HsOverLit id mkHsFractional :: Rational -> PostTcType -> HsOverLit id mkHsIsString :: FastString -> PostTcType -> HsOverLit id mkHsDo :: HsStmtContext Name -> [LStmt id] -> LHsExpr id -> HsExpr id mkHsSplice :: LHsExpr RdrName -> HsSplice RdrName mkTopSpliceDecl :: LHsExpr RdrName -> HsDecl RdrName mkClassDecl :: SrcSpan -> Located (Maybe (LHsContext RdrName), LHsType RdrName) -> Located [Located (FunDep RdrName)] -> Located (OrdList (LHsDecl RdrName)) -> P (LTyClDecl RdrName) mkTyData :: SrcSpan -> NewOrData -> Bool -> Located (Maybe (LHsContext RdrName), LHsType RdrName) -> Maybe Kind -> [LConDecl RdrName] -> Maybe [LHsType RdrName] -> P (LTyClDecl RdrName) mkTyFamily :: SrcSpan -> FamilyFlavour -> LHsType RdrName -> Maybe Kind -> P (LTyClDecl RdrName) mkTySynonym :: SrcSpan -> Bool -> LHsType RdrName -> LHsType RdrName -> P (LTyClDecl RdrName) splitCon :: LHsType RdrName -> P (Located RdrName, HsConDeclDetails RdrName) mkInlinePragma :: (InlineSpec, RuleMatchInfo) -> Maybe Activation -> InlinePragma mkRecConstrOrUpdate :: LHsExpr RdrName -> SrcSpan -> ([HsRecField RdrName (LHsExpr RdrName)], Bool) -> P (HsExpr RdrName) cvBindGroup :: OrdList (LHsDecl RdrName) -> HsValBinds RdrName cvBindsAndSigs :: OrdList (LHsDecl RdrName) -> (Bag (LHsBind RdrName), [LSig RdrName], [LTyClDecl RdrName], [LDocDecl]) cvTopDecls :: OrdList (LHsDecl RdrName) -> [LHsDecl RdrName] placeHolderPunRhs :: LHsExpr RdrName mkImport :: CCallConv -> Safety -> (Located FastString, Located RdrName, LHsType RdrName) -> P (HsDecl RdrName) parseCImport :: CCallConv -> Safety -> FastString -> String -> Maybe ForeignImport mkExport :: CCallConv -> (Located FastString, Located RdrName, LHsType RdrName) -> P (HsDecl RdrName) mkExtName :: RdrName -> CLabelString mkGadtDecl :: [Located RdrName] -> LHsType RdrName -> [ConDecl RdrName] mkSimpleConDecl :: Located RdrName -> [LHsTyVarBndr RdrName] -> LHsContext RdrName -> HsConDeclDetails RdrName -> ConDecl RdrName mkDeprecatedGadtRecordDecl :: SrcSpan -> Located RdrName -> [ConDeclField RdrName] -> LHsType RdrName -> P (LConDecl RdrName) checkPrecP :: Located Int -> P Int checkContext :: LHsType RdrName -> P (LHsContext RdrName) checkPred :: LHsType RdrName -> P (LHsPred RdrName) checkTyVars :: [LHsType RdrName] -> P [LHsTyVarBndr RdrName] checkKindSigs :: [LTyClDecl RdrName] -> P () checkInstType :: LHsType RdrName -> P (LHsType RdrName) checkPattern :: LHsExpr RdrName -> P (LPat RdrName) bang_RDR :: RdrName checkPatterns :: [LHsExpr RdrName] -> P [LPat RdrName] checkDo :: SrcSpan -> [LStmt RdrName] -> P ([LStmt RdrName], LHsExpr RdrName) checkMDo :: SrcSpan -> [LStmt RdrName] -> P ([LStmt RdrName], LHsExpr RdrName) checkValDef :: LHsExpr RdrName -> Maybe (LHsType RdrName) -> Located (GRHSs RdrName) -> P (HsBind RdrName) checkValSig :: LHsExpr RdrName -> LHsType RdrName -> P (Sig RdrName) checkDoAndIfThenElse :: LHsExpr RdrName -> Bool -> LHsExpr RdrName -> Bool -> LHsExpr RdrName -> P () parseError :: SrcSpan -> String -> P a parseErrorSDoc :: SrcSpan -> SDoc -> P a module Convert convertToHsExpr :: SrcSpan -> Exp -> Either Message (LHsExpr RdrName) convertToPat :: SrcSpan -> Pat -> Either Message (LPat RdrName) convertToHsDecls :: SrcSpan -> [Dec] -> Either Message [LHsDecl RdrName] convertToHsType :: SrcSpan -> Type -> Either Message (LHsType RdrName) convertToHsPred :: SrcSpan -> Pred -> Either Message (LHsPred RdrName) thRdrNameGuesses :: Name -> [RdrName] instance Monad CvtM module ParserCore parseCore :: P (HsExtCore RdrName) module CmmLex data CmmToken CmmT_SpecChar :: Char -> CmmToken CmmT_DotDot :: CmmToken CmmT_DoubleColon :: CmmToken CmmT_Shr :: CmmToken CmmT_Shl :: CmmToken CmmT_Ge :: CmmToken CmmT_Le :: CmmToken CmmT_Eq :: CmmToken CmmT_Ne :: CmmToken CmmT_BoolAnd :: CmmToken CmmT_BoolOr :: CmmToken CmmT_CLOSURE :: CmmToken CmmT_INFO_TABLE :: CmmToken CmmT_INFO_TABLE_RET :: CmmToken CmmT_INFO_TABLE_FUN :: CmmToken CmmT_INFO_TABLE_CONSTR :: CmmToken CmmT_INFO_TABLE_SELECTOR :: CmmToken CmmT_else :: CmmToken CmmT_export :: CmmToken CmmT_section :: CmmToken CmmT_align :: CmmToken CmmT_goto :: CmmToken CmmT_if :: CmmToken CmmT_jump :: CmmToken CmmT_foreign :: CmmToken CmmT_never :: CmmToken CmmT_prim :: CmmToken CmmT_return :: CmmToken CmmT_returns :: CmmToken CmmT_import :: CmmToken CmmT_switch :: CmmToken CmmT_case :: CmmToken CmmT_default :: CmmToken CmmT_bits8 :: CmmToken CmmT_bits16 :: CmmToken CmmT_bits32 :: CmmToken CmmT_bits64 :: CmmToken CmmT_float32 :: CmmToken CmmT_float64 :: CmmToken CmmT_gcptr :: CmmToken CmmT_GlobalReg :: GlobalReg -> CmmToken CmmT_Name :: FastString -> CmmToken CmmT_String :: String -> CmmToken CmmT_Int :: Integer -> CmmToken CmmT_Float :: Rational -> CmmToken CmmT_EOF :: CmmToken cmmlex :: (Located CmmToken -> P a) -> P a module CgMonad type Code = FCode () data FCode a initC :: DynFlags -> Module -> FCode a -> IO a thenC :: Code -> FCode a -> FCode a thenFC :: FCode a -> (a -> FCode c) -> FCode c listCs :: [Code] -> Code listFCs :: [FCode a] -> FCode [a] mapCs :: (a -> Code) -> [a] -> Code mapFCs :: (a -> FCode b) -> [a] -> FCode [b] returnFC :: a -> FCode a fixC :: (a -> FCode a) -> FCode a fixC_ :: (a -> FCode a) -> FCode () checkedAbsC :: CmmStmt -> Code stmtC :: CmmStmt -> Code stmtsC :: [CmmStmt] -> Code labelC :: BlockId -> Code emitStmts :: CmmStmts -> Code nopC :: Code whenC :: Bool -> Code -> Code newLabelC :: FCode BlockId newUnique :: FCode Unique newUniqSupply :: FCode UniqSupply type CgStmts = OrdList CgStmt emitCgStmts :: CgStmts -> Code forkCgStmts :: CgStmts -> FCode BlockId cgStmtsToBlocks :: CgStmts -> FCode [CmmBasicBlock] getCgStmts' :: FCode a -> FCode (a, CgStmts) getCgStmts :: FCode a -> FCode CgStmts noCgStmts :: CgStmts oneCgStmt :: CmmStmt -> CgStmts consCgStmt :: CmmStmt -> CgStmts -> CgStmts getCmm :: Code -> FCode Cmm emitData :: Section -> [CmmStatic] -> Code emitProc :: CmmInfo -> CLabel -> CmmFormals -> [CmmBasicBlock] -> Code emitSimpleProc :: CLabel -> Code -> Code forkLabelledCode :: Code -> FCode BlockId forkClosureBody :: Code -> Code forkStatics :: FCode a -> FCode a forkAlts :: [FCode a] -> FCode [a] forkEval :: EndOfBlockInfo -> Code -> FCode Sequel -> FCode EndOfBlockInfo forkEvalHelp :: EndOfBlockInfo -> Code -> FCode a -> FCode (VirtualSpOffset, a) forkProc :: Code -> FCode CgStmts codeOnly :: Code -> Code type SemiTaggingStuff = Maybe ([(ConTagZ, CmmLit)], CmmLit) type ConTagZ = Int data EndOfBlockInfo EndOfBlockInfo :: VirtualSpOffset -> Sequel -> EndOfBlockInfo setEndOfBlockInfo :: EndOfBlockInfo -> Code -> Code getEndOfBlockInfo :: FCode EndOfBlockInfo setSRT :: SRT -> FCode a -> FCode a getSRT :: FCode SRT setSRTLabel :: CLabel -> FCode a -> FCode a getSRTLabel :: FCode CLabel setTickyCtrLabel :: CLabel -> Code -> Code getTickyCtrLabel :: FCode CLabel data StackUsage StackUsage :: VirtualSpOffset -> VirtualSpOffset -> [VirtualSpOffset] -> VirtualSpOffset -> VirtualSpOffset -> StackUsage virtSp :: StackUsage -> VirtualSpOffset frameSp :: StackUsage -> VirtualSpOffset freeStk :: StackUsage -> [VirtualSpOffset] realSp :: StackUsage -> VirtualSpOffset hwSp :: StackUsage -> VirtualSpOffset data HeapUsage HeapUsage :: VirtualHpOffset -> VirtualHpOffset -> HeapUsage virtHp :: HeapUsage -> VirtualHpOffset realHp :: HeapUsage -> VirtualHpOffset type VirtualSpOffset = WordOff type VirtualHpOffset = WordOff initStkUsage :: StackUsage initHpUsage :: HeapUsage getHpUsage :: FCode HeapUsage setHpUsage :: HeapUsage -> Code heapHWM :: HeapUsage -> VirtualHpOffset getModuleName :: FCode Module data Sequel OnStack :: Sequel CaseAlts :: CLabel -> SemiTaggingStuff -> Id -> Sequel getState :: FCode CgState setState :: CgState -> FCode () getInfoDown :: FCode CgInfoDownwards getDynFlags :: FCode DynFlags getThisPackage :: FCode PackageId getStkUsage :: FCode StackUsage setStkUsage :: StackUsage -> Code getBinds :: FCode CgBindings setBinds :: CgBindings -> FCode () getStaticBinds :: FCode CgBindings data CgInfoDownwards MkCgInfoDown :: DynFlags -> Module -> CgBindings -> CLabel -> SRT -> CLabel -> EndOfBlockInfo -> CgInfoDownwards cgd_dflags :: CgInfoDownwards -> DynFlags cgd_mod :: CgInfoDownwards -> Module cgd_statics :: CgInfoDownwards -> CgBindings cgd_srt_lbl :: CgInfoDownwards -> CLabel cgd_srt :: CgInfoDownwards -> SRT cgd_ticky :: CgInfoDownwards -> CLabel cgd_eob :: CgInfoDownwards -> EndOfBlockInfo data CgState MkCgState :: OrdList CgStmt -> OrdList CmmTop -> CgBindings -> StackUsage -> HeapUsage -> UniqSupply -> CgState cgs_stmts :: CgState -> OrdList CgStmt cgs_tops :: CgState -> OrdList CmmTop cgs_binds :: CgState -> CgBindings cgs_stk_usg :: CgState -> StackUsage cgs_hp_usg :: CgState -> HeapUsage cgs_uniqs :: CgState -> UniqSupply instance Monad FCode module CgUtils addIdReps :: [Id] -> [(CgRep, Id)] cgLit :: Literal -> FCode CmmLit emitDataLits :: CLabel -> [CmmLit] -> Code mkDataLits :: CLabel -> [CmmLit] -> GenCmmTop CmmStatic info graph emitRODataLits :: String -> CLabel -> [CmmLit] -> Code mkRODataLits :: CLabel -> [CmmLit] -> GenCmmTop CmmStatic info graph emitIf :: CmmExpr -> Code -> Code emitIfThenElse :: CmmExpr -> Code -> Code -> Code -- | Emit code to call a Cmm function. emitRtsCall :: PackageId -> FastString -> [CmmHinted CmmExpr] -> Bool -> Code emitRtsCallWithVols :: PackageId -> FastString -> [CmmHinted CmmExpr] -> [GlobalReg] -> Bool -> Code emitRtsCallWithResult :: LocalReg -> ForeignHint -> PackageId -> FastString -> [CmmHinted CmmExpr] -> Bool -> Code assignTemp :: CmmExpr -> FCode CmmExpr newTemp :: CmmType -> FCode LocalReg emitSimultaneously :: CmmStmts -> Code emitSwitch :: CmmExpr -> [(ConTagZ, CgStmts)] -> Maybe CgStmts -> ConTagZ -> ConTagZ -> Code emitLitSwitch :: CmmExpr -> [(Literal, CgStmts)] -> CgStmts -> Code tagToClosure :: TyCon -> CmmExpr -> CmmExpr -- | Returns True if this global register is stored in a -- caller-saves machine register. callerSaves :: GlobalReg -> Bool callerSaveVolatileRegs :: Maybe [GlobalReg] -> ([CmmStmt], [CmmStmt]) -- | We map STG registers onto appropriate CmmExprs. Either they map to -- real machine registers or stored as offsets from BaseReg. Given a -- GlobalReg, get_GlobalReg_addr always produces the register table -- address for it. get_GlobalReg_addr :: GlobalReg -> CmmExpr -- | Here is where the STG register map is defined for each target arch. -- The order matters (for the llvm backend anyway)! We must make sure to -- maintain the order here with the order used in the LLVM calling -- conventions. Note that also, this isn't all registers, just the ones -- that are currently possbily mapped to real registers. activeStgRegs :: [GlobalReg] -- | Fixup global registers so that they assign to locations within the -- RegTable if they aren't pinned for the current target. fixStgRegisters :: RawCmmTop -> RawCmmTop cmmAndWord :: CmmExpr -> CmmExpr -> CmmExpr cmmOrWord :: CmmExpr -> CmmExpr -> CmmExpr cmmNegate :: CmmExpr -> CmmExpr cmmEqWord :: CmmExpr -> CmmExpr -> CmmExpr cmmNeWord :: CmmExpr -> CmmExpr -> CmmExpr cmmUGtWord :: CmmExpr -> CmmExpr -> CmmExpr cmmOffsetExprW :: CmmExpr -> CmmExpr -> CmmExpr cmmOffsetExprB :: CmmExpr -> CmmExpr -> CmmExpr cmmRegOffW :: CmmReg -> WordOff -> CmmExpr cmmRegOffB :: CmmReg -> ByteOff -> CmmExpr cmmLabelOffW :: CLabel -> WordOff -> CmmLit cmmLabelOffB :: CLabel -> ByteOff -> CmmLit cmmOffsetW :: CmmExpr -> WordOff -> CmmExpr cmmOffsetB :: CmmExpr -> ByteOff -> CmmExpr cmmOffsetLitW :: CmmLit -> WordOff -> CmmLit cmmOffsetLitB :: CmmLit -> ByteOff -> CmmLit cmmLoadIndexW :: CmmExpr -> Int -> CmmType -> CmmExpr cmmConstrTag :: CmmExpr -> CmmExpr cmmConstrTag1 :: CmmExpr -> CmmExpr tagForCon :: DataCon -> ConTagZ tagCons :: DataCon -> CmmExpr -> CmmExpr isSmallFamily :: Int -> Bool cmmUntag :: CmmExpr -> CmmExpr cmmIsTagged :: CmmExpr -> CmmExpr cmmGetTag :: CmmExpr -> CmmExpr addToMem :: Width -> CmmExpr -> Int -> CmmStmt addToMemE :: Width -> CmmExpr -> CmmExpr -> CmmStmt mkWordCLit :: StgWord -> CmmLit mkStringCLit :: String -> FCode CmmLit mkByteStringCLit :: [Word8] -> FCode CmmLit packHalfWordsCLit :: (Integral a, Integral b) => a -> b -> CmmLit blankWord :: CmmStatic getSRTInfo :: FCode C_SRT clHasCafRefs :: ClosureInfo -> CafInfo module AsmCodeGen nativeCodeGen :: DynFlags -> Handle -> UniqSupply -> [RawCmm] -> IO () instance Monad CmmOptM -- | Base LLVM Code Generation module -- -- Contains functions useful through out the code generator. module LlvmCodeGen.Base type LlvmCmmTop = GenCmmTop LlvmData [CmmStatic] (ListGraph LlvmStatement) type LlvmBasicBlock = GenBasicBlock LlvmStatement -- | Unresolved code. Of the form: (data label, data type, unresolved data) type LlvmUnresData = (CLabel, Section, LlvmType, [UnresStatic]) -- | Top level LLVM Data (globals and type aliases) type LlvmData = ([LMGlobal], [LlvmType]) -- | An unresolved Label. -- -- Labels are unresolved when we haven't yet determined if they are -- defined in the module we are currently compiling, or an external one. type UnresLabel = CmmLit type UnresStatic = Either UnresLabel LlvmStatic type LlvmEnv = (LlvmEnvMap, LlvmEnvMap) -- | Get initial Llvm environment. initLlvmEnv :: LlvmEnv -- | Clear variables from the environment. clearVars :: LlvmEnv -> LlvmEnv varLookup :: Uniquable key => key -> LlvmEnv -> Maybe LlvmType varInsert :: Uniquable key => key -> LlvmType -> LlvmEnv -> LlvmEnv -- | Lookup functions in the environment. funLookup :: Uniquable key => key -> LlvmEnv -> Maybe LlvmType -- | Insert functions into the environment. funInsert :: Uniquable key => key -> LlvmType -> LlvmEnv -> LlvmEnv -- | Translate a basic CmmType to an LlvmType. cmmToLlvmType :: CmmType -> LlvmType -- | Translate a Cmm Float Width to a LlvmType. widthToLlvmFloat :: Width -> LlvmType -- | Translate a Cmm Bit Width to a LlvmType. widthToLlvmInt :: Width -> LlvmType -- | Llvm Function type for Cmm function llvmFunTy :: LlvmType -- | Llvm Function signature llvmFunSig :: CLabel -> LlvmLinkageType -> LlvmFunctionDecl -- | Llvm standard fun attributes llvmStdFunAttrs :: [LlvmFuncAttr] -- | Alignment to use for functions llvmFunAlign :: LMAlign -- | Alignment to use for into tables llvmInfAlign :: LMAlign -- | Pointer width llvmPtrBits :: Int -- | Create a Haskell function in LLVM. mkLlvmFunc :: CLabel -> LlvmLinkageType -> LMSection -> LlvmBlocks -> LlvmFunction -- | Convert a list of types to a list of function parameters (each with no -- parameter attributes) tysToParams :: [LlvmType] -> [LlvmParameter] -- | Pretty print a CLabel. strCLabel_llvm :: CLabel -> LMString -- | Create an external definition for a CLabel defined in another -- module. genCmmLabelRef :: CLabel -> LMGlobal -- | As above (genCmmLabelRef) but taking a LMString, not -- CLabel. genStringLabelRef :: LMString -> LMGlobal -- | Handle conversion of CmmData to LLVM code. module LlvmCodeGen.Data -- | Pass a CmmStatic section to an equivalent Llvm code. Can't complete -- this completely though as we need to pass all CmmStatic sections -- before all references can be resolved. This last step is done by -- resolveLlvmData. genLlvmData :: (Section, [CmmStatic]) -> LlvmUnresData resolveLlvmDatas :: LlvmEnv -> [LlvmUnresData] -> [LlvmData] -> (LlvmEnv, [LlvmData]) -- | Fix up CLabel references now that we should have passed all CmmData. resolveLlvmData :: LlvmEnv -> LlvmUnresData -> (LlvmEnv, LlvmData) -- | Pretty print helpers for the LLVM Code generator. module LlvmCodeGen.Ppr -- | Header code for LLVM modules pprLlvmHeader :: Doc -- | Pretty print LLVM code pprLlvmCmmTop :: LlvmEnv -> Int -> LlvmCmmTop -> (Doc, [LlvmVar]) -- | Pretty print LLVM data code pprLlvmData :: LlvmData -> Doc -- | The section we are putting info tables and their entry code into infoSection :: String -- | We generate labels for info tables by converting them to the same -- label as for the entry code but adding this string as a suffix. iTableSuf :: String -- | Handle conversion of CmmProc to LLVM code. module LlvmCodeGen.CodeGen -- | Top-level of the LLVM proc Code generator genLlvmProc :: LlvmEnv -> RawCmmTop -> UniqSM (LlvmEnv, [LlvmCmmTop]) -- | This is the top-level module in the LLVM code generator. module LlvmCodeGen -- | Top-level of the LLVM Code generator llvmCodeGen :: DynFlags -> Handle -> UniqSupply -> [RawCmm] -> IO () -- | Read in assembly file and process llvmFixupAsm :: FilePath -> FilePath -> IO () module CmmBrokenBlock -- | Similar to a CmmBlock with a little extra information to help -- the CPS analysis. data BrokenBlock BrokenBlock :: BlockId -> BlockEntryInfo -> [CmmStmt] -> [BlockId] -> FinalStmt -> BrokenBlock -- | The block's label like a CmmBasicBlock brokenBlockId :: BrokenBlock -> BlockId -- | Ways this block can be entered brokenBlockEntry :: BrokenBlock -> BlockEntryInfo -- | Body like a CmmBasicBlock (but without the last statement) brokenBlockStmts :: BrokenBlock -> [CmmStmt] -- | Blocks that this block could branch to either by conditional branches -- or via the last statement brokenBlockTargets :: BrokenBlock -> [BlockId] -- | The final statement of the block brokenBlockExit :: BrokenBlock -> FinalStmt -- | How a block could be entered See Note [An example of CPS conversion] data BlockEntryInfo -- | Block is the beginning of a function, parameters are: 1. Function -- header info 2. The function name 3. Aguments to function Only the -- formal parameters are live FunctionEntry :: CmmInfo -> CLabel -> CmmFormals -> BlockEntryInfo -- | Return point of a function call, parameters are: 1. return values -- (argument to continuation) 2. SRT for the continuation's info table 3. -- True = GC block so ignore stack size Live variables, other than -- the return values, are on the stack ContinuationEntry :: CmmFormals -> C_SRT -> Bool -> BlockEntryInfo -- | Any other kind of block. Only entered due to control flow. ControlEntry :: BlockEntryInfo -- | Final statement in a BlokenBlock. Constructors and arguments -- match those in Cmm, but are restricted to branches, returns, -- jumps, calls and switches data FinalStmt -- | Same as CmmBranch. Target must be a ControlEntry FinalBranch :: BlockId -> FinalStmt -- | Same as CmmReturn. Parameter is the return values. FinalReturn :: HintedCmmActuals -> FinalStmt -- | Same as CmmJump. Parameters: 1. The function to call, 2. -- Arguments of the call FinalJump :: CmmExpr -> HintedCmmActuals -> FinalStmt -- | Same as CmmCallee followed by CmmGoto. Parameters: 1. -- Target of the CmmGoto (must be a ContinuationEntry) 2. -- The function to call 3. Results from call (redundant with -- ContinuationEntry) 4. Arguments to call 5. SRT for the continuation's -- info table 6. Does the function return? 7. True = GC block so -- ignore stack size FinalCall :: BlockId -> CmmCallTarget -> HintedCmmFormals -> HintedCmmActuals -> C_SRT -> CmmReturnInfo -> Bool -> FinalStmt -- | Same as a CmmSwitch. Paremeters: 1. Scrutinee (zero based) 2. -- Targets FinalSwitch :: CmmExpr -> [Maybe BlockId] -> FinalStmt -- | Takes a CmmBasicBlock and breaks it up into a list of -- BrokenBlock by splitting on each CmmCall in the -- CmmBasicBlock. breakBlock :: [BlockId] -> [Unique] -> CmmBasicBlock -> BlockEntryInfo -> ([(BlockId, ContFormat)], [BrokenBlock]) -- | Convert from a BrokenBlock back to an equivalent CmmBasicBlock Needed -- by liveness analysis cmmBlockFromBrokenBlock :: BrokenBlock -> CmmBasicBlock -- | Build a mapping so we can lookup a BrokenBlock by its -- BlockId blocksToBlockEnv :: [BrokenBlock] -> BlockEnv BrokenBlock adaptBlockToFormat :: [(BlockId, ContFormat)] -> Unique -> BrokenBlock -> [BrokenBlock] selectContinuations :: [(BlockId, ContFormat)] -> [(BlockId, ContFormat)] data ContFormat makeContinuationEntries :: [(BlockId, ContFormat)] -> BrokenBlock -> BrokenBlock instance Eq ContFormat module CmmProcPoint calculateProcPoints :: [BrokenBlock] -> UniqSet BlockId module CgProf mkCCostCentre :: CostCentre -> CmmLit mkCCostCentreStack :: CostCentreStack -> CmmLit dynProfHdr :: CmmExpr -> [CmmExpr] -- | Record the allocation of a closure. The CmmExpr is the cost centre -- stack to which to attribute the allocation. profDynAlloc :: ClosureInfo -> CmmExpr -> Code -- | Record the allocation of a closure (size is given by a CmmExpr) The -- size must be in words, because the allocation counter in a CCS counts -- in words. profAlloc :: CmmExpr -> CmmExpr -> Code staticProfHdr :: CostCentreStack -> [CmmLit] initUpdFrameProf :: CmmExpr -> Code enterCostCentre :: ClosureInfo -> CostCentreStack -> StgExpr -> Code enterCostCentrePAP :: CmmExpr -> Code enterCostCentreThunk :: CmmExpr -> Code chooseDynCostCentres :: CostCentreStack -> [Id] -> StgExpr -> FCode (CmmExpr, CmmExpr) costCentreFrom :: CmmExpr -> CmmExpr curCCS :: CmmExpr curCCSAddr :: CmmExpr emitCostCentreDecl :: CostCentre -> Code emitCostCentreStackDecl :: CostCentreStack -> Code emitRegisterCC :: CostCentre -> Code emitRegisterCCS :: CostCentreStack -> Code emitSetCCC :: CostCentre -> Code emitCCS :: CostCentreStack -> FCode CmmExpr ldvEnter :: CmmExpr -> Code ldvEnterClosure :: ClosureInfo -> Code ldvRecordCreate :: CmmExpr -> Code -- | Our extended FCode monad. module CgExtCode -- | Does a computation in the FCode monad, with a current environment and -- a list of local declarations. Returns the resulting list of -- declarations. newtype ExtFCode a EC :: (Env -> Decls -> FCode (Decls, a)) -> ExtFCode a unEC :: ExtFCode a -> Env -> Decls -> FCode (Decls, a) type ExtCode = ExtFCode () -- | The environment contains variable definitions or blockids. data Named -- | Holds CmmLit(CmmLabel ..) which gives the label type, eg, RtsLabel, -- ForeignLabel, CmmLabel etc. Var :: CmmExpr -> Named -- | A function name from this package Fun :: PackageId -> Named -- | A blockid of some code or data. Label :: BlockId -> Named -- | An environment of named things. type Env = UniqFM Named -- | Takes the variable decarations and imports from the monad and makes an -- environment, which is looped back into the computation. In this way, -- we can have embedded declarations that scope over the whole procedure, -- and imports that scope over the entire module. Discards the local -- declaration contained within decl' loopDecls :: ExtFCode a -> ExtFCode a -- | Get the current environment from the monad. getEnv :: ExtFCode Env -- | Create a fresh local variable of a given type. newLocal :: CmmType -> FastString -> ExtFCode LocalReg -- | Allocate a fresh label. newLabel :: FastString -> ExtFCode BlockId -- | Add add a local function to the environment. newFunctionName :: FastString -> PackageId -> ExtCode -- | Add an imported foreign label to the list of local declarations. If -- this is done at the start of the module the declaration will scope -- over the whole module. newImport :: (FastString, CLabel) -> ExtFCode () -- | Lookup the BlockId bound to the label with this name. If one hasn't -- been bound yet, create a fresh one based on the Unique of the name. lookupLabel :: FastString -> ExtFCode BlockId -- | Lookup the location of a named variable. Unknown names are treated as -- if they had been 'import'ed from the runtime system. This saves us a -- lot of bother in the RTS sources, at the expense of deferring some -- errors to link time. lookupName :: FastString -> ExtFCode CmmExpr -- | Lift an FCode computation into the ExtFCode monad code :: FCode a -> ExtFCode a code2 :: (FCode (Decls, b) -> FCode ((Decls, b), c)) -> ExtFCode b -> ExtFCode c -- | Do nothing in the ExtFCode monad. nopEC :: ExtFCode () -- | Accumulate a CmmStmt into the monad state. stmtEC :: CmmStmt -> ExtFCode () -- | Accumulate some CmmStmts into the monad state. stmtsEC :: [CmmStmt] -> ExtFCode () -- | Get the generated statements out of the monad state. getCgStmtsEC :: ExtFCode a -> ExtFCode CgStmts -- | Get the generated statements, and the return value out of the monad -- state. getCgStmtsEC' :: ExtFCode a -> ExtFCode (a, CgStmts) -- | Emit a chunk of code outside the instruction stream, and return its -- block id. forkLabelledCodeEC :: ExtFCode a -> ExtFCode BlockId instance Monad ExtFCode module CgStackery spRel :: VirtualSpOffset -> VirtualSpOffset -> WordOff getVirtSp :: FCode VirtualSpOffset getRealSp :: FCode VirtualSpOffset setRealSp :: VirtualSpOffset -> Code setRealAndVirtualSp :: VirtualSpOffset -> Code getSpRelOffset :: VirtualSpOffset -> FCode CmmExpr allocPrimStack :: CgRep -> FCode VirtualSpOffset allocStackTop :: WordOff -> FCode () deAllocStackTop :: WordOff -> FCode () adjustStackHW :: VirtualSpOffset -> Code getFinalStackHW :: (VirtualSpOffset -> Code) -> Code setStackFrame :: VirtualSpOffset -> Code getStackFrame :: FCode VirtualSpOffset mkVirtStkOffsets :: VirtualSpOffset -> [(CgRep, a)] -> (VirtualSpOffset, [(a, VirtualSpOffset)]) -- | mkStkAmodes is a higher-level version of -- mkVirtStkOffsets. It starts from the tail-call locations. It -- returns a single list of addressing modes for the stack locations, and -- therefore is in the monad. It doesn't adjust the high water -- mark. mkStkAmodes :: VirtualSpOffset -> [(CgRep, CmmExpr)] -> FCode (VirtualSpOffset, CmmStmts) freeStackSlots :: [VirtualSpOffset] -> Code pushUpdateFrame :: CmmExpr -> Code -> Code pushBHUpdateFrame :: CmmExpr -> Code -> Code emitPushUpdateFrame :: CmmExpr -> CmmExpr -> Code module CgCallConv mkArgDescr :: Name -> [Id] -> FCode ArgDescr argDescrType :: ArgDescr -> StgHalfWord isBigLiveness :: Liveness -> Bool mkRegLiveness :: [(Id, GlobalReg)] -> Int -> Int -> StgWord smallLiveness :: Int -> StgWord -> Liveness mkLivenessCLit :: Liveness -> CmmLit assignCallRegs :: [(CgRep, a)] -> ([(a, GlobalReg)], [(CgRep, a)]) assignReturnRegs :: [(CgRep, a)] -> ([(a, GlobalReg)], [(CgRep, a)]) assignPrimOpCallRegs :: [(CgRep, a)] -> ([(a, GlobalReg)], [(CgRep, a)]) constructSlowCall :: [(CgRep, CmmExpr)] -> (CLabel, [(CgRep, CmmExpr)], [(CgRep, CmmExpr)]) -- | slowArgs takes a list of function arguments and prepares them -- for pushing on the stack for extra arguments to a function -- which requires fewer arguments than we currently have. slowArgs :: [(CgRep, CmmExpr)] -> [(CgRep, CmmExpr)] slowCallPattern :: [CgRep] -> (FastString, Int) dataReturnConvPrim :: CgRep -> CmmReg getSequelAmode :: FCode CmmExpr module CgParallel staticGranHdr :: [CmmLit] staticParHdr :: [CmmLit] granFetchAndReschedule :: [(Id, GlobalReg)] -> Bool -> Code granYield :: [(Id, GlobalReg)] -> Bool -> Code doGranAllocate :: CmmExpr -> Code module CgTicky emitTickyCounter :: ClosureInfo -> [Id] -> Int -> Code tickyDynAlloc :: ClosureInfo -> Code tickyAllocHeap :: VirtualHpOffset -> Code tickyAllocPrim :: CmmExpr -> CmmExpr -> CmmExpr -> Code tickyAllocThunk :: CmmExpr -> CmmExpr -> Code tickyAllocPAP :: CmmExpr -> CmmExpr -> Code tickyPushUpdateFrame :: Code tickyUpdateFrameOmitted :: Code tickyEnterDynCon :: Code tickyEnterStaticCon :: Code tickyEnterViaNode :: Code tickyEnterFun :: ClosureInfo -> Code tickyEnterThunk :: ClosureInfo -> Code tickyUpdateBhCaf :: ClosureInfo -> Code tickyBlackHole :: Bool -> Code tickyUnboxedTupleReturn :: Int -> Code tickyVectoredReturn :: Int -> Code tickyReturnOldCon :: Arity -> Code tickyReturnNewCon :: Arity -> Code tickyKnownCallTooFewArgs :: Code tickyKnownCallExact :: Code tickyKnownCallExtraArgs :: Code tickyUnknownCall :: Code tickySlowCallPat :: [CgRep] -> Code staticTickyHdr :: [CmmLit] module CgHeapery initHeapUsage :: (VirtualHpOffset -> Code) -> Code getVirtHp :: FCode VirtualHpOffset setVirtHp :: VirtualHpOffset -> Code setRealHp :: VirtualHpOffset -> Code getHpRelOffset :: VirtualHpOffset -> FCode CmmExpr hpRel :: VirtualHpOffset -> VirtualHpOffset -> WordOff funEntryChecks :: ClosureInfo -> CmmStmts -> Code -> Code thunkEntryChecks :: ClosureInfo -> Code -> Code altHeapCheck :: AltType -> Code -> Code unbxTupleHeapCheck :: [(Id, GlobalReg)] -> WordOff -> WordOff -> CmmStmts -> Code -> Code hpChkGen :: CmmExpr -> CmmExpr -> CmmExpr -> Code hpChkNodePointsAssignSp0 :: CmmExpr -> CmmExpr -> Code stkChkGen :: CmmExpr -> CmmExpr -> CmmExpr -> Code stkChkNodePoints :: CmmExpr -> Code layOutDynConstr :: DataCon -> [(CgRep, a)] -> (ClosureInfo, [(a, VirtualHpOffset)]) layOutStaticConstr :: DataCon -> [(CgRep, a)] -> (ClosureInfo, [(a, VirtualHpOffset)]) mkVirtHeapOffsets :: Bool -> [(CgRep, a)] -> (WordOff, WordOff, [(a, VirtualHpOffset)]) mkStaticClosureFields :: ClosureInfo -> CostCentreStack -> Bool -> [CmmLit] -> [CmmLit] mkStaticClosure :: CLabel -> CostCentreStack -> [CmmLit] -> [CmmLit] -> [CmmLit] -> [CmmLit] -> [CmmLit] allocDynClosure :: ClosureInfo -> CmmExpr -> CmmExpr -> [(CmmExpr, VirtualHpOffset)] -> FCode VirtualHpOffset emitSetDynHdr :: CmmExpr -> CmmExpr -> CmmExpr -> Code module ByteCodeItbls type ItblEnv = NameEnv (Name, ItblPtr) newtype ItblPtr ItblPtr :: (Ptr ()) -> ItblPtr itblCode :: ItblPtr -> Ptr () mkITbls :: [TyCon] -> IO ItblEnv data StgInfoTable StgInfoTable :: HalfWord -> HalfWord -> HalfWord -> HalfWord -> [ItblCode] -> StgInfoTable ptrs :: StgInfoTable -> HalfWord nptrs :: StgInfoTable -> HalfWord tipe :: StgInfoTable -> HalfWord srtlen :: StgInfoTable -> HalfWord code :: StgInfoTable -> [ItblCode] instance Show ItblPtr instance Monad m => MonadT (State s) m instance Monad m => Monad (State s m) instance Storable StgInfoTable instance Storable StgConInfoTable module ByteCodeInstr data BCInstr STKCHECK :: Word -> BCInstr PUSH_L :: !Word16 -> BCInstr PUSH_LL :: !Word16 -> !Word16 -> BCInstr PUSH_LLL :: !Word16 -> !Word16 -> !Word16 -> BCInstr PUSH_G :: Name -> BCInstr PUSH_PRIMOP :: PrimOp -> BCInstr PUSH_BCO :: (ProtoBCO Name) -> BCInstr PUSH_ALTS :: (ProtoBCO Name) -> BCInstr PUSH_ALTS_UNLIFTED :: (ProtoBCO Name) -> CgRep -> BCInstr PUSH_UBX :: (Either Literal (Ptr ())) -> Word16 -> BCInstr PUSH_APPLY_N :: BCInstr PUSH_APPLY_V :: BCInstr PUSH_APPLY_F :: BCInstr PUSH_APPLY_D :: BCInstr PUSH_APPLY_L :: BCInstr PUSH_APPLY_P :: BCInstr PUSH_APPLY_PP :: BCInstr PUSH_APPLY_PPP :: BCInstr PUSH_APPLY_PPPP :: BCInstr PUSH_APPLY_PPPPP :: BCInstr PUSH_APPLY_PPPPPP :: BCInstr SLIDE :: Word16 -> Word16 -> BCInstr ALLOC_AP :: !Word16 -> BCInstr ALLOC_AP_NOUPD :: !Word16 -> BCInstr ALLOC_PAP :: !Word16 -> !Word16 -> BCInstr MKAP :: !Word16 -> !Word16 -> BCInstr MKPAP :: !Word16 -> !Word16 -> BCInstr UNPACK :: !Word16 -> BCInstr PACK :: DataCon -> !Word16 -> BCInstr LABEL :: LocalLabel -> BCInstr TESTLT_I :: Int -> LocalLabel -> BCInstr TESTEQ_I :: Int -> LocalLabel -> BCInstr TESTLT_W :: Word -> LocalLabel -> BCInstr TESTEQ_W :: Word -> LocalLabel -> BCInstr TESTLT_F :: Float -> LocalLabel -> BCInstr TESTEQ_F :: Float -> LocalLabel -> BCInstr TESTLT_D :: Double -> LocalLabel -> BCInstr TESTEQ_D :: Double -> LocalLabel -> BCInstr TESTLT_P :: Word16 -> LocalLabel -> BCInstr TESTEQ_P :: Word16 -> LocalLabel -> BCInstr CASEFAIL :: BCInstr JMP :: LocalLabel -> BCInstr CCALL :: Word16 -> (Ptr ()) -> BCInstr SWIZZLE :: Word16 -> Word16 -> BCInstr ENTER :: BCInstr RETURN :: BCInstr RETURN_UBX :: CgRep -> BCInstr BRK_FUN :: (MutableByteArray# RealWorld) -> Word16 -> BreakInfo -> BCInstr data ProtoBCO a ProtoBCO :: a -> [BCInstr] -> [StgWord] -> Word16 -> Int -> Either [AnnAlt Id VarSet] (AnnExpr Id VarSet) -> [Either ItblPtr (Ptr ())] -> ProtoBCO a protoBCOName :: ProtoBCO a -> a protoBCOInstrs :: ProtoBCO a -> [BCInstr] protoBCOBitmap :: ProtoBCO a -> [StgWord] protoBCOBitmapSize :: ProtoBCO a -> Word16 protoBCOArity :: ProtoBCO a -> Int protoBCOExpr :: ProtoBCO a -> Either [AnnAlt Id VarSet] (AnnExpr Id VarSet) protoBCOPtrs :: ProtoBCO a -> [Either ItblPtr (Ptr ())] bciStackUse :: BCInstr -> Word data BreakInfo BreakInfo :: Module -> {-# UNPACK #-} !Int -> [(Id, Word16)] -> Type -> BreakInfo breakInfo_module :: BreakInfo -> Module breakInfo_number :: BreakInfo -> {-# UNPACK #-} !Int breakInfo_vars :: BreakInfo -> [(Id, Word16)] breakInfo_resty :: BreakInfo -> Type instance Outputable BCInstr instance Outputable a => Outputable (ProtoBCO a) instance Outputable BreakInfo module ByteCodeAsm assembleBCOs :: [ProtoBCO Name] -> [TyCon] -> IO CompiledByteCode assembleBCO :: ProtoBCO Name -> IO UnlinkedBCO data CompiledByteCode ByteCode :: [UnlinkedBCO] -> ItblEnv -> CompiledByteCode data UnlinkedBCO UnlinkedBCO :: Name -> Int -> ByteArray# -> ByteArray# -> (SizedSeq BCONPtr) -> (SizedSeq BCOPtr) -> UnlinkedBCO unlinkedBCOName :: UnlinkedBCO -> Name unlinkedBCOArity :: UnlinkedBCO -> Int unlinkedBCOInstrs :: UnlinkedBCO -> ByteArray# unlinkedBCOBitmap :: UnlinkedBCO -> ByteArray# unlinkedBCOLits :: UnlinkedBCO -> (SizedSeq BCONPtr) unlinkedBCOPtrs :: UnlinkedBCO -> (SizedSeq BCOPtr) data BCOPtr BCOPtrName :: Name -> BCOPtr BCOPtrPrimOp :: PrimOp -> BCOPtr BCOPtrBCO :: UnlinkedBCO -> BCOPtr BCOPtrBreakInfo :: BreakInfo -> BCOPtr BCOPtrArray :: (MutableByteArray# RealWorld) -> BCOPtr data BCONPtr BCONPtrWord :: Word -> BCONPtr BCONPtrLbl :: FastString -> BCONPtr BCONPtrItbl :: Name -> BCONPtr -- | Finds external references. Remember to remove the names defined by -- this group of BCOs themselves bcoFreeNames :: UnlinkedBCO -> NameSet data SizedSeq a sizeSS :: SizedSeq a -> Word ssElts :: SizedSeq a -> [a] iNTERP_STACK_CHECK_THRESH :: Int instance Outputable UnlinkedBCO instance Outputable CompiledByteCode module ByteCodeLink data HValue type ClosureEnv = NameEnv (Name, HValue) emptyClosureEnv :: NameEnv a extendClosureEnv :: ClosureEnv -> [(Name, HValue)] -> ClosureEnv linkBCO :: ItblEnv -> ClosureEnv -> UnlinkedBCO -> IO HValue lookupStaticPtr :: FastString -> IO (Ptr ()) lookupName :: ClosureEnv -> Name -> IO HValue lookupIE :: ItblEnv -> Name -> IO (Ptr a) instance MArray IOArray e IO module CgBindery type CgBindings = IdEnv CgIdInfo data CgIdInfo data StableLoc data VolatileLoc cgIdInfoId :: CgIdInfo -> Id cgIdInfoArgRep :: CgIdInfo -> CgRep cgIdInfoLF :: CgIdInfo -> LambdaFormInfo stableIdInfo :: Id -> CmmExpr -> LambdaFormInfo -> CgIdInfo heapIdInfo :: Id -> VirtualHpOffset -> LambdaFormInfo -> CgIdInfo taggedStableIdInfo :: Id -> CmmExpr -> LambdaFormInfo -> DataCon -> CgIdInfo taggedHeapIdInfo :: Id -> VirtualHpOffset -> LambdaFormInfo -> DataCon -> CgIdInfo letNoEscapeIdInfo :: Id -> VirtualSpOffset -> LambdaFormInfo -> CgIdInfo idInfoToAmode :: CgIdInfo -> FCode CmmExpr addBindC :: Id -> CgIdInfo -> Code addBindsC :: [(Id, CgIdInfo)] -> Code nukeVolatileBinds :: CgBindings -> CgBindings nukeDeadBindings :: StgLiveVars -> Code getLiveStackSlots :: FCode [VirtualSpOffset] getLiveStackBindings :: FCode [(VirtualSpOffset, CgIdInfo)] bindArgsToStack :: [(Id, VirtualSpOffset)] -> Code rebindToStack :: Id -> VirtualSpOffset -> Code bindNewToNode :: Id -> VirtualHpOffset -> LambdaFormInfo -> Code bindNewToUntagNode :: Id -> VirtualHpOffset -> LambdaFormInfo -> Int -> Code bindNewToReg :: Id -> CmmReg -> LambdaFormInfo -> Code bindArgsToRegs :: [(Id, GlobalReg)] -> Code bindNewToTemp :: Id -> FCode LocalReg getArgAmode :: StgArg -> FCode (CgRep, CmmExpr) getArgAmodes :: [StgArg] -> FCode [(CgRep, CmmExpr)] getCgIdInfo :: Id -> FCode CgIdInfo getCAddrModeIfVolatile :: Id -> FCode (Maybe CmmExpr) getVolatileRegs :: StgLiveVars -> FCode [GlobalReg] maybeLetNoEscape :: CgIdInfo -> Maybe VirtualSpOffset instance Outputable StableLoc instance Outputable VolatileLoc instance Outputable CgIdInfo module CgInfoTbls emitClosureCodeAndInfoTable :: ClosureInfo -> CmmFormals -> CgStmts -> Code emitInfoTableAndCode :: CLabel -> CmmInfo -> CmmFormals -> [CmmBasicBlock] -> Code dataConTagZ :: DataCon -> ConTagZ emitReturnTarget :: Name -> CgStmts -> FCode CLabel emitAlgReturnTarget :: Name -> [(ConTagZ, CgStmts)] -> Maybe CgStmts -> Int -> FCode (CLabel, SemiTaggingStuff) emitReturnInstr :: Code stdInfoTableSizeB :: ByteOff entryCode :: CmmExpr -> CmmExpr closureInfoPtr :: CmmExpr -> CmmExpr getConstrTag :: CmmExpr -> CmmExpr cmmGetClosureType :: CmmExpr -> CmmExpr infoTable :: CmmExpr -> CmmExpr infoTableClosureType :: CmmExpr -> CmmExpr infoTablePtrs :: CmmExpr -> CmmExpr infoTableNonPtrs :: CmmExpr -> CmmExpr funInfoTable :: CmmExpr -> CmmExpr makeRelativeRefTo :: CLabel -> CmmLit -> CmmLit module CmmInfo emptyContInfoTable :: CmmInfo cmmToRawCmm :: [Cmm] -> IO [RawCmm] mkInfoTable :: Unique -> CmmTop -> [RawCmmTop] mkBareInfoTable :: CLabel -> Unique -> CmmInfoTable -> [CmmTopZ] module CmmProcPointZ type ProcPointSet = BlockSet data Status ReachedBy :: ProcPointSet -> Status ProcPoint :: Status callProcPoints :: CmmGraph -> ProcPointSet minimalProcPointSet :: ProcPointSet -> CmmGraph -> FuelMonad ProcPointSet -- | Function optimize_calls chooses protocols only for those proc -- points that are relevant to the optimization explained above. The -- others are assigned by add_unassigned, which is not yet clever. addProcPointProtocols :: ProcPointSet -> ProcPointSet -> CmmGraph -> FuelMonad CmmGraph splitAtProcPoints :: CLabel -> ProcPointSet -> ProcPointSet -> BlockEnv Status -> CmmTopZ -> FuelMonad [CmmTopZ] procPointAnalysis :: ProcPointSet -> CmmGraph -> FuelMonad (BlockEnv Status) instance Eq Protocol instance Outputable Protocol instance Outputable Status module CmmStackLayout type SlotEnv = BlockEnv SubAreaSet liveSlotAnal :: LGraph Middle Last -> FuelMonad SlotEnv liveSlotTransfers :: BackwardTransfers Middle Last SubAreaSet removeLiveSlotDefs :: (DefinerOfSlots s, UserOfSlots s) => SubAreaSet -> s -> SubAreaSet -- | Greedy stack layout. Compute liveness, build the interference graph, -- and allocate slots for the areas. We visit each basic block in a -- (generally) forward order. layout :: ProcPointSet -> SlotEnv -> ByteOff -> LGraph Middle Last -> AreaMap manifestSP :: AreaMap -> ByteOff -> LGraph Middle Last -> FuelMonad (LGraph Middle Last) igraph :: Ord x => IGraphBuilder x -> SlotEnv -> LGraph Middle Last -> IGraph x areaBuilder :: IGraphBuilder Area stubSlotsOnDeath :: (LGraph Middle Last) -> FuelMonad (LGraph Middle Last) module CmmCPSGen continuationToProc :: (WordOff, WordOff, [(CLabel, ContinuationFormat)]) -> CmmReg -> [[[Unique]]] -> Continuation CmmInfo -> CmmTop data Continuation info Continuation :: info -> CLabel -> CmmFormals -> Bool -> [BrokenBlock] -> Continuation info continuationLabel :: Continuation (Either C_SRT CmmInfo) -> CLabel data ContinuationFormat ContinuationFormat :: CmmFormals -> Maybe CLabel -> WordOff -> [Maybe LocalReg] -> ContinuationFormat continuation_formals :: ContinuationFormat -> CmmFormals continuation_label :: ContinuationFormat -> Maybe CLabel continuation_frame_size :: ContinuationFormat -> WordOff continuation_stack :: ContinuationFormat -> [Maybe LocalReg] module CmmCPS -- | Top level driver for the CPS pass cmmCPS :: DynFlags -> [Cmm] -> IO [Cmm] module CgForeignCall cgForeignCall :: HintedCmmFormals -> ForeignCall -> [StgArg] -> StgLiveVars -> Code emitForeignCall :: HintedCmmFormals -> ForeignCall -> [CmmHinted CmmExpr] -> StgLiveVars -> Code emitForeignCall' :: Safety -> HintedCmmFormals -> CmmCallTarget -> [CmmHinted CmmExpr] -> Maybe [GlobalReg] -> C_SRT -> CmmReturnInfo -> Code shimForeignCallArg :: StgArg -> CmmExpr -> CmmExpr emitSaveThreadState :: Code emitLoadThreadState :: Code emitCloseNursery :: Code emitOpenNursery :: Code module CgPrimOp cgPrimOp :: CmmFormals -> PrimOp -> [StgArg] -> StgLiveVars -> Code module CgTailCall cgTailCall :: Id -> [StgArg] -> Code performTailCall :: CgIdInfo -> [(CgRep, CmmExpr)] -> CmmStmts -> Code performReturn :: Code -> Code performPrimReturn :: CgRep -> CmmExpr -> Code returnUnboxedTuple :: [(CgRep, CmmExpr)] -> Code ccallReturnUnboxedTuple :: [(CgRep, CmmExpr)] -> Code -> Code pushUnboxedTuple :: VirtualSpOffset -> [(CgRep, CmmExpr)] -> FCode (VirtualSpOffset, CmmStmts) tailCallPrimOp :: PrimOp -> [StgArg] -> Code tailCallPrimCall :: PrimCall -> [StgArg] -> Code pushReturnAddress :: EndOfBlockInfo -> Code module CgClosure cgTopRhsClosure :: Id -> CostCentreStack -> StgBinderInfo -> UpdateFlag -> [Id] -> StgExpr -> FCode (Id, CgIdInfo) cgStdRhsClosure :: Id -> CostCentreStack -> StgBinderInfo -> [Id] -> [Id] -> StgExpr -> LambdaFormInfo -> [StgArg] -> FCode (Id, CgIdInfo) cgRhsClosure :: Id -> CostCentreStack -> StgBinderInfo -> [Id] -> UpdateFlag -> [Id] -> StgExpr -> FCode (Id, CgIdInfo) emitBlackHoleCode :: Bool -> Code module CmmParse parseCmmFile :: DynFlags -> FilePath -> IO (Messages, Maybe Cmm) module PprC writeCs :: DynFlags -> Handle -> [RawCmm] -> IO () pprStringInCStyle :: [Word8] -> SDoc instance Monad TE module StgCmmMonad data FCode a initC :: DynFlags -> Module -> FCode a -> IO a thenC :: FCode () -> FCode a -> FCode a thenFC :: FCode a -> (a -> FCode c) -> FCode c listCs :: [FCode ()] -> FCode () listFCs :: [FCode a] -> FCode [a] mapCs :: (a -> FCode ()) -> [a] -> FCode () mapFCs :: (a -> FCode b) -> [a] -> FCode [b] returnFC :: a -> FCode a fixC :: (a -> FCode a) -> FCode a fixC_ :: (a -> FCode a) -> FCode () nopC :: FCode () whenC :: Bool -> FCode () -> FCode () newUnique :: FCode Unique newUniqSupply :: FCode UniqSupply emit :: CmmAGraph -> FCode () emitData :: Section -> [CmmStatic] -> FCode () emitProc :: CmmInfo -> CLabel -> CmmFormals -> CmmAGraph -> FCode () emitProcWithConvention :: Convention -> CmmInfo -> CLabel -> CmmFormals -> CmmAGraph -> FCode () emitSimpleProc :: CLabel -> CmmAGraph -> FCode () getCmm :: FCode () -> FCode CmmZ cgStmtsToBlocks :: CmmAGraph -> FCode CmmGraph getCodeR :: FCode a -> FCode (a, CmmAGraph) getCode :: FCode a -> FCode CmmAGraph getHeapUsage :: (VirtualHpOffset -> FCode a) -> FCode a forkClosureBody :: FCode () -> FCode () forkStatics :: FCode a -> FCode a forkAlts :: [FCode a] -> FCode [a] forkProc :: FCode a -> FCode a codeOnly :: FCode () -> FCode () type ConTagZ = Int data Sequel Return :: Bool -> Sequel AssignTo :: [LocalReg] -> Bool -> Sequel withSequel :: Sequel -> FCode () -> FCode () getSequel :: FCode Sequel setSRTLabel :: CLabel -> FCode a -> FCode a getSRTLabel :: FCode CLabel setTickyCtrLabel :: CLabel -> FCode () -> FCode () getTickyCtrLabel :: FCode CLabel withUpdFrameOff :: UpdFrameOffset -> FCode () -> FCode () getUpdFrameOff :: FCode UpdFrameOffset initUpdFrameOff :: UpdFrameOffset data HeapUsage HeapUsage :: VirtualHpOffset -> VirtualHpOffset -> HeapUsage virtHp :: HeapUsage -> VirtualHpOffset realHp :: HeapUsage -> VirtualHpOffset type VirtualHpOffset = WordOff initHpUsage :: HeapUsage getHpUsage :: FCode HeapUsage setHpUsage :: HeapUsage -> FCode () heapHWM :: HeapUsage -> VirtualHpOffset setVirtHp :: VirtualHpOffset -> FCode () getVirtHp :: FCode VirtualHpOffset setRealHp :: VirtualHpOffset -> FCode () getModuleName :: FCode Module getState :: FCode CgState setState :: CgState -> FCode () getInfoDown :: FCode CgInfoDownwards getDynFlags :: FCode DynFlags getThisPackage :: FCode PackageId data CgIdInfo CgIdInfo :: Id -> LambdaFormInfo -> CgLoc -> PrimRep -> {-# UNPACK #-} !DynTag -> CgIdInfo cg_id :: CgIdInfo -> Id cg_lf :: CgIdInfo -> LambdaFormInfo cg_loc :: CgIdInfo -> CgLoc cg_rep :: CgIdInfo -> PrimRep cg_tag :: CgIdInfo -> {-# UNPACK #-} !DynTag data CgLoc CmmLoc :: CmmExpr -> CgLoc LneLoc :: BlockId -> [LocalReg] -> CgLoc getBinds :: FCode CgBindings setBinds :: CgBindings -> FCode () getStaticBinds :: FCode CgBindings data CgInfoDownwards MkCgInfoDown :: DynFlags -> Module -> CgBindings -> CLabel -> UpdFrameOffset -> CLabel -> Sequel -> CgInfoDownwards cgd_dflags :: CgInfoDownwards -> DynFlags cgd_mod :: CgInfoDownwards -> Module cgd_statics :: CgInfoDownwards -> CgBindings cgd_srt_lbl :: CgInfoDownwards -> CLabel cgd_updfr_off :: CgInfoDownwards -> UpdFrameOffset cgd_ticky :: CgInfoDownwards -> CLabel cgd_sequel :: CgInfoDownwards -> Sequel data CgState MkCgState :: CmmAGraph -> OrdList CmmTopZ -> CgBindings -> HeapUsage -> UniqSupply -> CgState cgs_stmts :: CgState -> CmmAGraph cgs_tops :: CgState -> OrdList CmmTopZ cgs_binds :: CgState -> CgBindings cgs_hp_usg :: CgState -> HeapUsage cgs_uniqs :: CgState -> UniqSupply instance Show Sequel instance Outputable CgLoc instance Outputable CgIdInfo instance Monad FCode module StgCmmUtils cgLit :: Literal -> FCode CmmLit mkSimpleLit :: Literal -> CmmLit emitDataLits :: CLabel -> [CmmLit] -> FCode () mkDataLits :: CLabel -> [CmmLit] -> GenCmmTop CmmStatic info stmt emitRODataLits :: CLabel -> [CmmLit] -> FCode () mkRODataLits :: CLabel -> [CmmLit] -> GenCmmTop CmmStatic info stmt emitRtsCall :: PackageId -> FastString -> [(CmmExpr, ForeignHint)] -> Bool -> FCode () emitRtsCallWithVols :: PackageId -> FastString -> [(CmmExpr, ForeignHint)] -> [GlobalReg] -> Bool -> FCode () emitRtsCallWithResult :: LocalReg -> ForeignHint -> PackageId -> FastString -> [(CmmExpr, ForeignHint)] -> Bool -> FCode () assignTemp :: CmmExpr -> FCode LocalReg newTemp :: CmmType -> FCode LocalReg withTemp :: CmmType -> (LocalReg -> CmmAGraph) -> CmmAGraph newUnboxedTupleRegs :: Type -> FCode ([LocalReg], [ForeignHint]) mkMultiAssign :: [LocalReg] -> [CmmExpr] -> CmmAGraph mkCmmSwitch :: Bool -> CmmExpr -> [(ConTagZ, CmmAGraph)] -> Maybe CmmAGraph -> ConTagZ -> ConTagZ -> CmmAGraph mkCmmLitSwitch :: CmmExpr -> [(Literal, CmmAGraph)] -> CmmAGraph -> CmmAGraph emitSwitch :: CmmExpr -> [(ConTagZ, CmmAGraph)] -> Maybe CmmAGraph -> ConTagZ -> ConTagZ -> FCode () tagToClosure :: TyCon -> CmmExpr -> CmmExpr mkTaggedObjectLoad :: LocalReg -> LocalReg -> WordOff -> DynTag -> CmmAGraph callerSaveVolatileRegs :: (CmmAGraph, CmmAGraph) get_GlobalReg_addr :: GlobalReg -> CmmExpr cmmAndWord :: CmmExpr -> CmmExpr -> CmmExpr cmmOrWord :: CmmExpr -> CmmExpr -> CmmExpr cmmNegate :: CmmExpr -> CmmExpr cmmEqWord :: CmmExpr -> CmmExpr -> CmmExpr cmmNeWord :: CmmExpr -> CmmExpr -> CmmExpr cmmUGtWord :: CmmExpr -> CmmExpr -> CmmExpr cmmOffsetExprW :: CmmExpr -> CmmExpr -> CmmExpr cmmOffsetExprB :: CmmExpr -> CmmExpr -> CmmExpr cmmRegOffW :: CmmReg -> WordOff -> CmmExpr cmmRegOffB :: CmmReg -> ByteOff -> CmmExpr cmmLabelOffW :: CLabel -> WordOff -> CmmLit cmmLabelOffB :: CLabel -> ByteOff -> CmmLit cmmOffsetW :: CmmExpr -> WordOff -> CmmExpr cmmOffsetB :: CmmExpr -> ByteOff -> CmmExpr cmmOffsetLitW :: CmmLit -> WordOff -> CmmLit cmmOffsetLitB :: CmmLit -> ByteOff -> CmmLit cmmLoadIndexW :: CmmExpr -> Int -> CmmType -> CmmExpr cmmConstrTag :: CmmExpr -> CmmExpr cmmConstrTag1 :: CmmExpr -> CmmExpr cmmUntag :: CmmExpr -> CmmExpr cmmIsTagged :: CmmExpr -> CmmExpr cmmGetTag :: CmmExpr -> CmmExpr addToMem :: CmmType -> CmmExpr -> Int -> CmmAGraph addToMemE :: CmmType -> CmmExpr -> CmmExpr -> CmmAGraph addToMemLbl :: CmmType -> CLabel -> Int -> CmmAGraph mkWordCLit :: StgWord -> CmmLit mkStringCLit :: String -> FCode CmmLit mkByteStringCLit :: [Word8] -> FCode CmmLit packHalfWordsCLit :: (Integral a, Integral b) => a -> b -> CmmLit blankWord :: CmmStatic getSRTInfo :: SRT -> FCode C_SRT clHasCafRefs :: ClosureInfo -> CafInfo srt_escape :: StgHalfWord module StgCmmProf initCostCentres :: CollectedCCs -> FCode CmmAGraph ccType :: CmmType ccsType :: CmmType mkCCostCentre :: CostCentre -> CmmLit mkCCostCentreStack :: CostCentreStack -> CmmLit dynProfHdr :: CmmExpr -> [CmmExpr] -- | Record the allocation of a closure. The CmmExpr is the cost centre -- stack to which to attribute the allocation. profDynAlloc :: ClosureInfo -> CmmExpr -> FCode () -- | Record the allocation of a closure (size is given by a CmmExpr) The -- size must be in words, because the allocation counter in a CCS counts -- in words. profAlloc :: CmmExpr -> CmmExpr -> FCode () staticProfHdr :: CostCentreStack -> [CmmLit] initUpdFrameProf :: CmmExpr -> FCode () enterCostCentre :: ClosureInfo -> CostCentreStack -> StgExpr -> FCode () enterCostCentrePAP :: CmmExpr -> FCode () enterCostCentreThunk :: CmmExpr -> FCode () chooseDynCostCentres :: CostCentreStack -> [Id] -> StgExpr -> FCode (CmmExpr, CmmExpr) costCentreFrom :: CmmExpr -> CmmExpr curCCS :: CmmExpr curCCSAddr :: CmmExpr emitSetCCC :: CostCentre -> FCode () emitCCS :: CostCentreStack -> FCode CmmExpr saveCurrentCostCentre :: FCode (Maybe LocalReg) restoreCurrentCostCentre :: Maybe LocalReg -> FCode () ldvEnter :: CmmExpr -> FCode () ldvEnterClosure :: ClosureInfo -> FCode () ldvRecordCreate :: CmmExpr -> FCode () module StgCmmEnv data CgIdInfo cgIdInfoId :: CgIdInfo -> Id cgIdInfoLF :: CgIdInfo -> LambdaFormInfo litIdInfo :: Id -> LambdaFormInfo -> CmmLit -> CgIdInfo lneIdInfo :: Id -> [LocalReg] -> CgIdInfo regIdInfo :: Id -> LambdaFormInfo -> LocalReg -> CgIdInfo idInfoToAmode :: CgIdInfo -> CmmExpr newtype NonVoid a NonVoid :: a -> NonVoid a isVoidId :: Id -> Bool nonVoidIds :: [Id] -> [NonVoid Id] addBindC :: Id -> CgIdInfo -> FCode () addBindsC :: [CgIdInfo] -> FCode () bindArgsToRegs :: [NonVoid Id] -> FCode [LocalReg] bindToReg :: NonVoid Id -> LambdaFormInfo -> FCode LocalReg rebindToReg :: NonVoid Id -> FCode LocalReg bindArgToReg :: NonVoid Id -> FCode LocalReg idToReg :: NonVoid Id -> LocalReg getArgAmode :: NonVoid StgArg -> FCode CmmExpr getNonVoidArgAmodes :: [StgArg] -> FCode [CmmExpr] getCgIdInfo :: Id -> FCode CgIdInfo maybeLetNoEscape :: CgIdInfo -> Maybe (BlockId, [LocalReg]) instance Eq a => Eq (NonVoid a) instance Show a => Show (NonVoid a) instance Outputable a => Outputable (NonVoid a) module StgCmmForeign cgForeignCall :: [LocalReg] -> [ForeignHint] -> ForeignCall -> [StgArg] -> FCode () loadThreadState :: LocalReg -> CmmAGraph saveThreadState :: CmmAGraph emitPrimCall :: CmmFormals -> CallishMachOp -> CmmActuals -> FCode () emitCCall :: [(CmmFormal, ForeignHint)] -> CmmExpr -> [(CmmActual, ForeignHint)] -> FCode () emitSaveThreadState :: BlockId -> FCode () emitLoadThreadState :: LocalReg -> FCode () emitOpenNursery :: FCode () module CmmBuildInfoTables type CAFSet = Map CLabel () type CAFEnv = BlockEnv CAFSet data CmmTopForInfoTables NoInfoTable :: CmmTopZ -> CmmTopForInfoTables ProcInfoTable :: CmmTopZ -> BlockSet -> CmmTopForInfoTables FloatingInfoTable :: CmmInfo -> BlockId -> UpdFrameOffset -> CmmTopForInfoTables cafAnal :: LGraph Middle Last -> FuelMonad CAFEnv localCAFInfo :: CAFEnv -> CmmTopZ -> Maybe (CLabel, CAFSet) mkTopCAFInfo :: [(CLabel, CAFSet)] -> Map CLabel CAFSet setInfoTableSRT :: Map CLabel CAFSet -> TopSRT -> (CAFSet, CmmTopForInfoTables) -> FuelMonad (TopSRT, [CmmTopForInfoTables]) setInfoTableStackMap :: SlotEnv -> AreaMap -> CmmTopForInfoTables -> CmmTopForInfoTables data TopSRT emptySRT :: MonadUnique m => m TopSRT srtToData :: TopSRT -> CmmZ bundleCAFs :: CAFEnv -> CmmTopForInfoTables -> (CAFSet, CmmTopForInfoTables) finishInfoTables :: CmmTopForInfoTables -> IO [CmmTopZ] lowerSafeForeignCalls :: [[CmmTopForInfoTables]] -> CmmTopZ -> FuelMonad [[CmmTopForInfoTables]] cafTransfers :: BackwardTransfers Middle Last CAFSet liveSlotTransfers :: BackwardTransfers Middle Last SubAreaSet extendEnvWithSafeForeignCalls :: BackwardTransfers Middle Last a -> BlockEnv a -> CmmGraph -> BlockEnv a extendEnvsForSafeForeignCalls :: CAFEnv -> SlotEnv -> CmmGraph -> (CAFEnv, SlotEnv) instance Outputable CmmTopForInfoTables instance Outputable TopSRT module StgCmmGran staticGranHdr :: [CmmLit] staticParHdr :: [CmmLit] granThunk :: Bool -> FCode () granYield :: [LocalReg] -> Bool -> FCode () doGranAllocate :: VirtualHpOffset -> FCode () module StgCmmTicky emitTickyCounter :: ClosureInfo -> [Id] -> FCode () tickyDynAlloc :: ClosureInfo -> FCode () tickyAllocHeap :: VirtualHpOffset -> FCode () tickyAllocPrim :: CmmExpr -> CmmExpr -> CmmExpr -> FCode () tickyAllocThunk :: CmmExpr -> CmmExpr -> FCode () tickyAllocPAP :: CmmExpr -> CmmExpr -> FCode () tickySlowCall :: LambdaFormInfo -> [StgArg] -> FCode () tickyDirectCall :: Arity -> [StgArg] -> FCode () tickyPushUpdateFrame :: FCode () tickyUpdateFrameOmitted :: FCode () tickyEnterDynCon :: FCode () tickyEnterStaticCon :: FCode () tickyEnterViaNode :: FCode () tickyEnterFun :: ClosureInfo -> FCode () tickyEnterThunk :: ClosureInfo -> FCode () tickyUpdateBhCaf :: ClosureInfo -> FCode () tickyBlackHole :: Bool -> FCode () tickyUnboxedTupleReturn :: Int -> FCode () tickyVectoredReturn :: Int -> FCode () tickyReturnOldCon :: Arity -> FCode () tickyReturnNewCon :: Arity -> FCode () tickyKnownCallTooFewArgs :: FCode () tickyKnownCallExact :: FCode () tickyKnownCallExtraArgs :: FCode () tickyUnknownCall :: FCode () tickySlowCallPat :: [PrimRep] -> FCode () staticTickyHdr :: [CmmLit] module StgCmmLayout mkArgDescr :: Name -> [Id] -> FCode ArgDescr emitCall :: (Convention, Convention) -> CmmExpr -> [CmmExpr] -> FCode () emitReturn :: [CmmExpr] -> FCode () emitClosureProcAndInfoTable :: Bool -> Id -> ClosureInfo -> [NonVoid Id] -> ((LocalReg, [LocalReg]) -> FCode ()) -> FCode () emitClosureAndInfoTable :: ClosureInfo -> Convention -> [LocalReg] -> FCode () -> FCode () slowCall :: CmmExpr -> [StgArg] -> FCode () directCall :: CLabel -> Arity -> [StgArg] -> FCode () mkVirtHeapOffsets :: Bool -> [(PrimRep, a)] -> (WordOff, WordOff, [(NonVoid a, VirtualHpOffset)]) getHpRelOffset :: VirtualHpOffset -> FCode CmmExpr hpRel :: VirtualHpOffset -> VirtualHpOffset -> WordOff stdInfoTableSizeB :: ByteOff entryCode :: CmmExpr -> CmmExpr closureInfoPtr :: CmmExpr -> CmmExpr getConstrTag :: CmmExpr -> CmmExpr cmmGetClosureType :: CmmExpr -> CmmExpr infoTable :: CmmExpr -> CmmExpr infoTableClosureType :: CmmExpr -> CmmExpr infoTablePtrs :: CmmExpr -> CmmExpr infoTableNonPtrs :: CmmExpr -> CmmExpr funInfoTable :: CmmExpr -> CmmExpr makeRelativeRefTo :: CLabel -> CmmLit -> CmmLit instance Outputable LRep module StgCmmPrim cgOpApp :: StgOp -> [StgArg] -> Type -> FCode () module StgCmmHeap getVirtHp :: FCode VirtualHpOffset setVirtHp :: VirtualHpOffset -> FCode () setRealHp :: VirtualHpOffset -> FCode () getHpRelOffset :: VirtualHpOffset -> FCode CmmExpr hpRel :: VirtualHpOffset -> VirtualHpOffset -> WordOff entryHeapCheck :: Maybe LocalReg -> Int -> [LocalReg] -> FCode () -> FCode () altHeapCheck :: [LocalReg] -> FCode a -> FCode a layOutDynConstr :: DataCon -> [(PrimRep, a)] -> (ClosureInfo, [(NonVoid a, VirtualHpOffset)]) layOutStaticConstr :: DataCon -> [(PrimRep, a)] -> (ClosureInfo, [(NonVoid a, VirtualHpOffset)]) mkVirtHeapOffsets :: Bool -> [(PrimRep, a)] -> (WordOff, WordOff, [(NonVoid a, VirtualHpOffset)]) mkStaticClosureFields :: ClosureInfo -> CostCentreStack -> Bool -> [CmmLit] -> [CmmLit] mkStaticClosure :: CLabel -> CostCentreStack -> [CmmLit] -> [CmmLit] -> [CmmLit] -> [CmmLit] -> [CmmLit] allocDynClosure :: ClosureInfo -> CmmExpr -> CmmExpr -> [(NonVoid StgArg, VirtualHpOffset)] -> FCode (LocalReg, CmmAGraph) emitSetDynHdr :: CmmExpr -> CmmExpr -> CmmExpr -> FCode () module CoreSubst -- | A substitution environment, containing both Id and TyVar -- substitutions. -- -- Some invariants apply to how you use the substitution: -- --
    --
  1. The in-scope set contains at least those Ids and -- TyVars that will be in scope after applying the -- substitution to a term. Precisely, the in-scope set must be a superset -- of the free vars of the substitution range that might possibly clash -- with locally-bound variables in the thing being substituted in.
  2. --
  3. You may apply the substitution only once
  4. --
-- -- There are various ways of setting up the in-scope set such that the -- first of these invariants hold: -- -- data Subst -- | A substitition of Types for TyVars type TvSubstEnv = TyVarEnv Type -- | An environment for substituting for Ids type IdSubstEnv = IdEnv CoreExpr -- | A set of variables that are in scope at some point data InScopeSet -- | De-shadowing the program is sometimes a useful pre-pass. It can be -- done simply by running over the bindings with an empty substitution, -- becuase substitution returns a result that has no-shadowing -- guaranteed. -- -- (Actually, within a single type there might still be shadowing, -- because substTy is a no-op for the empty substitution, but -- that's probably OK.) -- -- deShadowBinds :: [CoreBind] -> [CoreBind] -- | Substitutes for the Ids within the WorkerInfo given -- the new function Id substSpec :: Subst -> Id -> SpecInfo -> SpecInfo substRulesForImportedIds :: Subst -> [CoreRule] -> [CoreRule] -- | See substTy substTy :: Subst -> Type -> Type substExpr :: SDoc -> Subst -> CoreExpr -> CoreExpr -- | Apply a substititon to an entire CoreExpr. Rememeber, you may -- only apply the substitution once: see -- CoreSubst#apply_once -- -- Do *not* attempt to short-cut in the case of an empty substitution! -- See Note [Extending the Subst] substExprSC :: SDoc -> Subst -> CoreExpr -> CoreExpr substBind :: Subst -> CoreBind -> (Subst, CoreBind) -- | Apply a substititon to an entire CoreBind, additionally -- returning an updated Subst that should be used by subsequent -- substitutons. substBindSC :: Subst -> CoreBind -> (Subst, CoreBind) substUnfolding :: Subst -> Unfolding -> Unfolding -- | Substitutes for the Ids within an unfolding substUnfoldingSC :: Subst -> Unfolding -> Unfolding substUnfoldingSource :: Subst -> UnfoldingSource -> UnfoldingSource -- | Find the substitution for an Id in the Subst lookupIdSubst :: SDoc -> Subst -> Id -> CoreExpr -- | Find the substitution for a TyVar in the Subst lookupTvSubst :: Subst -> TyVar -> Type substIdOcc :: Subst -> Id -> Id emptySubst :: Subst mkEmptySubst :: InScopeSet -> Subst mkSubst :: InScopeSet -> TvSubstEnv -> IdSubstEnv -> Subst -- | Simultaneously substitute for a bunch of variables No left-right -- shadowing ie the substitution for (x y. e) a1 a2 so neither x nor y -- scope over a1 a2 mkOpenSubst :: InScopeSet -> [(Var, CoreArg)] -> Subst -- | Find the in-scope set: see CoreSubst#in_scope_invariant substInScope :: Subst -> InScopeSet isEmptySubst :: Subst -> Bool -- | Add a substitution for an Id to the Subst: you must -- ensure that the in-scope set is such that the -- CoreSubst#in_scope_invariant is true after extending the -- substitution like this extendIdSubst :: Subst -> Id -> CoreExpr -> Subst -- | Adds multiple Id substitutions to the Subst: see also -- extendIdSubst extendIdSubstList :: Subst -> [(Id, CoreExpr)] -> Subst -- | Add a substitution for a TyVar to the Subst: you must -- ensure that the in-scope set is such that the -- CoreSubst#in_scope_invariant is true after extending the -- substitution like this extendTvSubst :: Subst -> TyVar -> Type -> Subst -- | Adds multiple TyVar substitutions to the Subst: see also -- extendTvSubst extendTvSubstList :: Subst -> [(TyVar, Type)] -> Subst -- | Add a substitution for a TyVar or Id as appropriate to -- the Var being added. See also extendIdSubst and -- extendTvSubst extendSubst :: Subst -> Var -> CoreArg -> Subst -- | Add a substitution for a TyVar or Id as appropriate to -- all the Vars being added. See also extendSubst extendSubstList :: Subst -> [(Var, CoreArg)] -> Subst -- | Remove all substitutions for Ids and Vars that might -- have been built up while preserving the in-scope set zapSubstEnv :: Subst -> Subst -- | Add the Var to the in-scope set, but do not remove any existing -- substitutions for it addInScopeSet :: Subst -> VarSet -> Subst -- | Add the Var to the in-scope set: as a side effect, and remove -- any existing substitutions for it extendInScope :: Subst -> Var -> Subst -- | Add the Vars to the in-scope set: see also extendInScope extendInScopeList :: Subst -> [Var] -> Subst -- | Optimized version of extendInScopeList that can be used if you -- are certain all the things being added are Ids and hence none -- are TyVars extendInScopeIds :: Subst -> [Id] -> Subst isInScope :: Var -> Subst -> Bool setInScope :: Subst -> InScopeSet -> Subst delBndr :: Subst -> Var -> Subst delBndrs :: Subst -> [Var] -> Subst -- | Substitutes a Var for another one according to the Subst -- given, returning the result and an updated Subst that should be -- used by subsequent substitutons. IdInfo is preserved by this -- process, although it is substituted into appropriately. substBndr :: Subst -> Var -> (Subst, Var) -- | Applies substBndr to a number of Vars, accumulating a -- new Subst left-to-right substBndrs :: Subst -> [Var] -> (Subst, [Var]) -- | Substitute in a mutually recursive group of Ids substRecBndrs :: Subst -> [Id] -> (Subst, [Id]) -- | Very similar to substBndr, but it always allocates a new -- Unique for each variable in its output. It substitutes the -- IdInfo though. cloneIdBndr :: Subst -> UniqSupply -> Id -> (Subst, Id) -- | Applies cloneIdBndr to a number of Ids, accumulating a -- final substitution from left to right cloneIdBndrs :: Subst -> UniqSupply -> [Id] -> (Subst, [Id]) -- | Clone a mutually recursive group of Ids cloneRecIdBndrs :: Subst -> UniqSupply -> [Id] -> (Subst, [Id]) simpleOptPgm :: DynFlags -> [CoreBind] -> [CoreRule] -> IO ([CoreBind], [CoreRule]) simpleOptExpr :: CoreExpr -> CoreExpr simpleOptExprWith :: Subst -> InExpr -> OutExpr instance Outputable Subst -- | Arit and eta expansion module CoreArity -- | manifestArity sees how many leading value lambdas there are manifestArity :: CoreExpr -> Arity -- | An approximate, fast, version of exprEtaExpandArity exprArity :: CoreExpr -> Arity exprBotStrictness_maybe :: CoreExpr -> Maybe (Arity, StrictSig) exprEtaExpandArity :: CheapFun -> CoreExpr -> Arity type CheapFun = CoreExpr -> Maybe Type -> Bool -- | etaExpand n us e ty returns an expression with the same -- meaning as e, but with arity n. -- -- Given: -- --
--   e' = etaExpand n us e ty
--   
-- -- We should have that: -- --
--   ty = exprType e = exprType e'
--   
etaExpand :: Arity -> CoreExpr -> CoreExpr instance Outputable EtaInfo module CoreUnfold -- | Records the unfolding of an identifier, which is approximately -- the form the identifier would have if we substituted its definition in -- for the identifier. This type should be treated as abstract everywhere -- except in CoreUnfold data Unfolding -- | UnfoldingGuidance says when unfolding should take place data UnfoldingGuidance -- | There is no known Unfolding noUnfolding :: Unfolding mkImplicitUnfolding :: CoreExpr -> Unfolding mkUnfolding :: UnfoldingSource -> Bool -> Bool -> CoreExpr -> Unfolding mkCoreUnfolding :: UnfoldingSource -> Bool -> CoreExpr -> Arity -> UnfoldingGuidance -> Unfolding mkTopUnfolding :: Bool -> CoreExpr -> Unfolding mkSimpleUnfolding :: CoreExpr -> Unfolding mkInlineUnfolding :: Maybe Arity -> CoreExpr -> Unfolding mkInlinableUnfolding :: CoreExpr -> Unfolding mkWwInlineRule :: Id -> CoreExpr -> Arity -> Unfolding mkCompulsoryUnfolding :: CoreExpr -> Unfolding mkDFunUnfolding :: Type -> [DFunArg CoreExpr] -> Unfolding interestingArg :: CoreExpr -> ArgSummary data ArgSummary TrivArg :: ArgSummary NonTrivArg :: ArgSummary ValueArg :: ArgSummary couldBeSmallEnoughToInline :: Int -> CoreExpr -> Bool certainlyWillInline :: Unfolding -> Bool smallEnoughToInline :: Unfolding -> Bool callSiteInline :: DynFlags -> Id -> Bool -> Bool -> [ArgSummary] -> CallCtxt -> Maybe CoreExpr data CallCtxt BoringCtxt :: CallCtxt ArgCtxt :: Bool -> CallCtxt ValAppCtxt :: CallCtxt CaseCtxt :: CallCtxt -- | Returns Just (dc, [t1..tk], [x1..xn]) if the argument -- expression is a *saturated* constructor application of the form dc -- t1..tk x1 .. xn, where t1..tk are the *universally-qantified* -- type args of dc exprIsConApp_maybe :: IdUnfoldingFun -> CoreExpr -> Maybe (DataCon, [Type], [CoreExpr]) instance Outputable CallCtxt instance Outputable ArgSummary instance Outputable ExprSize module CoreTidy tidyExpr :: TidyEnv -> CoreExpr -> CoreExpr tidyVarOcc :: TidyEnv -> Var -> Var tidyRule :: TidyEnv -> CoreRule -> CoreRule tidyRules :: TidyEnv -> [CoreRule] -> [CoreRule] tidyUnfolding :: TidyEnv -> Unfolding -> Unfolding -> Unfolding -- | Functions for collecting together and applying rewrite rules to a -- module. The CoreRule datatype itself is declared elsewhere. module Rules -- | Gathers a collection of CoreRules. Maps (the name of) an -- Id to its rules type RuleBase = NameEnv [CoreRule] emptyRuleBase :: RuleBase mkRuleBase :: [CoreRule] -> RuleBase extendRuleBaseList :: RuleBase -> [CoreRule] -> RuleBase unionRuleBase :: RuleBase -> RuleBase -> RuleBase pprRuleBase :: RuleBase -> SDoc -- | Report partial matches for rules beginning with the specified string -- for the purposes of error reporting ruleCheckProgram :: CompilerPhase -> String -> RuleBase -> [CoreBind] -> SDoc -- | Make a SpecInfo containing a number of CoreRules, -- suitable for putting into an IdInfo mkSpecInfo :: [CoreRule] -> SpecInfo extendSpecInfo :: SpecInfo -> [CoreRule] -> SpecInfo addSpecInfo :: SpecInfo -> SpecInfo -> SpecInfo addIdSpecialisations :: Id -> [CoreRule] -> Id -- | Gather all the rules for locally bound identifiers from the supplied -- bindings rulesOfBinds :: [CoreBind] -> [CoreRule] getRules :: RuleBase -> Id -> [CoreRule] pprRulesForUser :: [CoreRule] -> SDoc -- | The main rule matching function. Attempts to apply all (active) -- supplied rules to this instance of an application in a given context, -- returning the rule applied and the resulting expression if successful. lookupRule :: (Activation -> Bool) -> IdUnfoldingFun -> InScopeSet -> Id -> [CoreExpr] -> [CoreRule] -> Maybe (CoreRule, CoreExpr) -- | Used to make CoreRule for an Id defined in the module -- being compiled. See also CoreRule mkRule :: Bool -> Bool -> RuleName -> Activation -> Name -> [CoreBndr] -> [CoreExpr] -> CoreExpr -> CoreRule -- | Find the "top" free names of several expressions. Such names are -- either: -- --
    --
  1. The function finally being applied to in an application chain (if -- that name is a GlobalId: see Var#globalvslocal), or
  2. --
  3. The TyCon if the expression is a Type
  4. --
-- -- This is used for the fast-match-check for rules; if the top names -- don't match, the rest can't roughTopNames :: [CoreExpr] -> [Maybe Name] -- | Types for the per-module compiler module HscTypes -- | A minimal implementation of a GhcMonad. If you need a custom -- monad, e.g., to maintain additional state consider wrapping this monad -- or using GhcT. newtype Ghc a Ghc :: (Session -> IO a) -> Ghc a unGhc :: Ghc a -> Session -> IO a -- | A monad transformer to add GHC specific features to another monad. -- -- Note that the wrapped monad must support IO and handling of -- exceptions. newtype GhcT m a GhcT :: (Session -> m a) -> GhcT m a unGhcT :: GhcT m a -> Session -> m a liftGhcT :: Monad m => m a -> GhcT m a -- | A monad that has all the features needed by GHC API calls. -- -- In short, a GHC monad -- -- -- -- If you do not use Ghc or GhcT, make sure to call -- GHC.initGhcMonad before any call to the GHC API functions can -- occur. class (Functor m, MonadIO m, WarnLogMonad m, ExceptionMonad m) => GhcMonad m getSession :: GhcMonad m => m HscEnv setSession :: GhcMonad m => HscEnv -> m () -- | A monad that allows logging of warnings. class Monad m => WarnLogMonad m setWarnings :: WarnLogMonad m => WarningMessages -> m () getWarnings :: WarnLogMonad m => m WarningMessages liftIO :: MonadIO m => IO a -> m a -- | Lift an IO action returning errors messages into a GhcMonad. -- -- In order to reduce dependencies to other parts of the compiler, -- functions outside the main parts of GHC return warnings and -- errors as a parameter and signal success via by wrapping the result in -- a Maybe type. This function logs the returned warnings and -- propagates errors as exceptions (of type SourceError). -- -- This function assumes the following invariants: -- --
    --
  1. If the second result indicates success (is of the form 'Just x'), -- there must be no error messages in the first result.
  2. --
  3. If there are no error messages, but the second result indicates -- failure there should be warnings in the first result. That is, if the -- action failed, it must have been due to the warnings (i.e., -- -Werror).
  4. --
ioMsgMaybe :: GhcMonad m => IO (Messages, Maybe a) -> m a -- | Lift a non-failing IO action into a GhcMonad. -- -- Like ioMsgMaybe, but assumes that the action will never return -- any error messages. ioMsg :: GhcMonad m => IO (Messages, a) -> m a logWarnings :: WarnLogMonad m => WarningMessages -> m () -- | Clear the log of Warnings. clearWarnings :: WarnLogMonad m => m () -- | Returns true if there were any warnings. hasWarnings :: WarnLogMonad m => m Bool -- | A source error is an error that is caused by one or more errors in the -- source code. A SourceError is thrown by many functions in the -- compilation pipeline. Inside GHC these errors are merely printed via -- log_action, but API clients may treat them differently, for -- example, insert them into a list box. If you want the default -- behaviour, use the idiom: -- --
--   handleSourceError printExceptionAndWarnings $ do
--     ... api calls that may fail ...
--   
-- -- The SourceErrors error messages can be accessed via -- srcErrorMessages. This list may be empty if the compiler failed -- due to -Werror (Opt_WarnIsError). -- -- See printExceptionAndWarnings for more information on what to -- take care of when writing a custom error handler. data SourceError -- | XXX: what exactly is an API error? data GhcApiError mkSrcErr :: ErrorMessages -> SourceError srcErrorMessages :: SourceError -> ErrorMessages mkApiErr :: SDoc -> GhcApiError throwOneError :: MonadIO m => ErrMsg -> m ab -- | Perform the given action and call the exception handler if the action -- throws a SourceError. See SourceError for more -- information. handleSourceError :: ExceptionMonad m => (SourceError -> m a) -> m a -> m a -- | Reflect a computation in the Ghc monad into the IO -- monad. -- -- You can use this to call functions returning an action in the -- Ghc monad inside an IO action. This is needed for some -- (too restrictive) callback arguments of some library functions: -- --
--   libFunc :: String -> (Int -> IO a) -> IO a
--   ghcFunc :: Int -> Ghc a
--   
--   ghcFuncUsingLibFunc :: String -> Ghc a -> Ghc a
--   ghcFuncUsingLibFunc str =
--     reifyGhc $ \s ->
--       libFunc $ \i -> do
--         reflectGhc (ghcFunc i) s
--   
reflectGhc :: Ghc a -> Session -> IO a reifyGhc :: (Session -> IO a) -> Ghc a handleFlagWarnings :: GhcMonad m => DynFlags -> [Located String] -> m () -- | The Session is a handle to the complete state of a compilation -- session. A compilation session consists of a set of modules -- constituting the current program or library, the context for -- interactive evaluation, and various caches. data Session Session :: !IORef HscEnv -> !IORef WarningMessages -> Session -- | Call the argument with the current session. withSession :: GhcMonad m => (HscEnv -> m a) -> m a -- | Set the current session to the result of applying the current session -- to the argument. modifySession :: GhcMonad m => (HscEnv -> HscEnv) -> m () -- | Call an action with a temporarily modified Session. withTempSession :: GhcMonad m => (HscEnv -> HscEnv) -> m a -> m a -- | Hscenv is like Session, except that some of the fields are -- immutable. An HscEnv is used to compile a single module from plain -- Haskell source code (after preprocessing) to either C, assembly or -- C--. Things like the module graph don't change during a single -- compilation. -- -- Historical note: "hsc" used to be the name of the compiler binary, -- when there was a separate driver and compiler. To compile a single -- module, the driver would invoke hsc on the source code... so nowadays -- we think of hsc as the layer of the compiler that deals with compiling -- a single module. data HscEnv HscEnv :: DynFlags -> GhcApiCallbacks -> [Target] -> ModuleGraph -> InteractiveContext -> HomePackageTable -> {-# UNPACK #-} !IORef ExternalPackageState -> {-# UNPACK #-} !IORef NameCache -> {-# UNPACK #-} !IORef FinderCache -> {-# UNPACK #-} !IORef ModLocationCache -> OptFuelState -> Maybe (Module, IORef TypeEnv) -> HscEnv -- | The dynamic flag settings hsc_dflags :: HscEnv -> DynFlags -- | Callbacks for the GHC API. hsc_callbacks :: HscEnv -> GhcApiCallbacks -- | The targets (or roots) of the current session hsc_targets :: HscEnv -> [Target] -- | The module graph of the current session hsc_mod_graph :: HscEnv -> ModuleGraph -- | The context for evaluating interactive statements hsc_IC :: HscEnv -> InteractiveContext -- | The home package table describes already-compiled home-package -- modules, excluding the module we are compiling right now. (In -- one-shot mode the current module is the only home-package module, so -- hsc_HPT is empty. All other modules count as "external-package" -- modules. However, even in GHCi mode, hi-boot interfaces are -- demand-loaded into the external-package table.) -- -- hsc_HPT is not mutable because we only demand-load external -- packages; the home package is eagerly loaded, module by module, by the -- compilation manager. -- -- The HPT may contain modules compiled earlier by --make but -- not actually below the current module in the dependency graph. hsc_HPT :: HscEnv -> HomePackageTable -- | Information about the currently loaded external packages. This is -- mutable because packages will be demand-loaded during a compilation -- run as required. hsc_EPS :: HscEnv -> {-# UNPACK #-} !IORef ExternalPackageState -- | As with hsc_EPS, this is side-effected by compiling to reflect -- sucking in interface files. They cache the state of external interface -- files, in effect. hsc_NC :: HscEnv -> {-# UNPACK #-} !IORef NameCache -- | The cached result of performing finding in the file system hsc_FC :: HscEnv -> {-# UNPACK #-} !IORef FinderCache -- | This caches the location of modules, so we don't have to search the -- filesystem multiple times. See also hsc_FC. hsc_MLC :: HscEnv -> {-# UNPACK #-} !IORef ModLocationCache -- | Settings to control the use of "optimization fuel": by limiting the -- number of transformations, we can use binary search to help find -- compiler bugs. hsc_OptFuel :: HscEnv -> OptFuelState -- | Used for one-shot compilation only, to initialise the -- IfGblEnv. See TcRnTypes.tcg_type_env_var for -- TcRunTypes.TcGblEnv hsc_type_env_var :: HscEnv -> Maybe (Module, IORef TypeEnv) hscEPS :: HscEnv -> IO ExternalPackageState -- | The FinderCache maps home module names to the result of -- searching for that module. It records the results of searching for -- modules along the search path. On :load, we flush the entire -- contents of this cache. -- -- Although the FinderCache range is FindResult for -- convenience , in fact it will only ever contain Found or -- NotFound entries. type FinderCache = ModuleNameEnv FindResult -- | The result of searching for an imported module. data FindResult -- | The module was found Found :: ModLocation -> Module -> FindResult -- | The requested package was not found NoPackage :: PackageId -> FindResult -- | _Error_: both in multiple packages FoundMultiple :: [PackageId] -> FindResult -- | The module was not found, including either * the specified places were -- searched * the package that this module should have been in * list of -- packages in which the module was hidden, * list of hidden packages -- containing this module NotFound :: [FilePath] -> (Maybe PackageId) -> [PackageId] -> [PackageId] -> FindResult -- | The module was not found in this package NotFoundInPackage :: PackageId -> FindResult -- | Cache that remembers where we found a particular module. Contains both -- home modules and package modules. On :load, only home modules -- are purged from this cache. type ModLocationCache = ModuleEnv ModLocation -- | A compilation target. -- -- A target may be supplied with the actual text of the module. If so, -- use this instead of the file contents (this is for use in an IDE where -- the file hasn't been saved by the user yet). data Target Target :: TargetId -> Bool -> Maybe (StringBuffer, ClockTime) -> Target -- | module or filename targetId :: Target -> TargetId -- | object code allowed? targetAllowObjCode :: Target -> Bool -- | in-memory text buffer? targetContents :: Target -> Maybe (StringBuffer, ClockTime) data TargetId -- | A module name: search for the file TargetModule :: ModuleName -> TargetId -- | A filename: preprocess & parse it to find the module name. If -- specified, the Phase indicates how to compile this file (which phase -- to start from). Nothing indicates the starting phase should be -- determined from the suffix of the filename. TargetFile :: FilePath -> (Maybe Phase) -> TargetId pprTarget :: Target -> SDoc pprTargetId :: TargetId -> SDoc -- | A ModuleGraph contains all the nodes from the home package (only). -- There will be a node for each source module, plus a node for each -- hi-boot module. -- -- The graph is not necessarily stored in topologically-sorted order. Use -- GHC.topSortModuleGraph and Digraph.flattenSCC to -- achieve this. type ModuleGraph = [ModSummary] emptyMG :: ModuleGraph -- | These functions are called in various places of the GHC API. -- -- API clients can override any of these callbacks to change GHC's -- default behaviour. data GhcApiCallbacks GhcApiCallbacks :: (forall m. GhcMonad m => ModSummary -> Maybe SourceError -> m ()) -> GhcApiCallbacks -- | Called by load after the compilating of each module. -- -- The default implementation simply prints all warnings and errors to -- stderr. Don't forget to call clearWarnings when -- implementing your own call. -- -- The first argument is the module that was compiled. -- -- The second argument is Nothing if no errors occured, but -- there may have been warnings. If it is Just err at least one -- error has occured. If srcErrorMessages is empty, compilation -- failed due to -Werror. reportModuleCompilationResult :: GhcApiCallbacks -> forall m. GhcMonad m => ModSummary -> Maybe SourceError -> m () -- | Temporarily modify the callbacks. After the action is executed all -- callbacks are reset (not, however, any other modifications to the -- session state.) withLocalCallbacks :: GhcMonad m => (GhcApiCallbacks -> GhcApiCallbacks) -> m a -> m a -- | The ModDetails is essentially a cache for information in the -- ModIface for home modules only. Information relating to -- packages will be loaded into global environments in -- ExternalPackageState. data ModDetails ModDetails :: [AvailInfo] -> !TypeEnv -> ![Instance] -> ![FamInst] -> ![CoreRule] -> ![Annotation] -> !VectInfo -> ModDetails md_exports :: ModDetails -> [AvailInfo] -- | Local type environment for this particular module md_types :: ModDetails -> !TypeEnv -- | DFunIds for the instances in this module md_insts :: ModDetails -> ![Instance] md_fam_insts :: ModDetails -> ![FamInst] -- | Domain may include Ids from other modules md_rules :: ModDetails -> ![CoreRule] -- | Annotations present in this module: currently they only annotate -- things also declared in this module md_anns :: ModDetails -> ![Annotation] -- | Module vectorisation information md_vect_info :: ModDetails -> !VectInfo emptyModDetails :: ModDetails -- | A ModGuts is carried through the compiler, accumulating stuff as it -- goes There is only one ModGuts at any time, the one for the module -- being compiled right now. Once it is compiled, a ModIface and -- ModDetails are extracted and the ModGuts is dicarded. data ModGuts ModGuts :: !Module -> IsBootInterface -> ![AvailInfo] -> !Dependencies -> !ImportedMods -> !NameSet -> !GlobalRdrEnv -> !FixityEnv -> !TypeEnv -> ![Instance] -> ![FamInst] -> ![CoreRule] -> ![CoreBind] -> !ForeignStubs -> !Warnings -> [Annotation] -> !HpcInfo -> !ModBreaks -> !VectInfo -> InstEnv -> FamInstEnv -> ModGuts -- | Module being compiled mg_module :: ModGuts -> !Module -- | Whether it's an hs-boot module mg_boot :: ModGuts -> IsBootInterface -- | What it exports mg_exports :: ModGuts -> ![AvailInfo] -- | What it depends on, directly or otherwise mg_deps :: ModGuts -> !Dependencies -- | Directly-imported modules; used to generate initialisation code mg_dir_imps :: ModGuts -> !ImportedMods -- | What the module needed (used in MkIface.mkIface) mg_used_names :: ModGuts -> !NameSet -- | Top-level lexical environment mg_rdr_env :: ModGuts -> !GlobalRdrEnv -- | Fixities declared in this module TODO: I'm unconvinced this is -- actually used anywhere mg_fix_env :: ModGuts -> !FixityEnv -- | Types declared in this module mg_types :: ModGuts -> !TypeEnv -- | Class instances declared in this module mg_insts :: ModGuts -> ![Instance] -- | Family instances declared in this module mg_fam_insts :: ModGuts -> ![FamInst] -- | Before the core pipeline starts, contains See Note [Overall plumbing -- for rules] in Rules.lhs mg_rules :: ModGuts -> ![CoreRule] -- | Bindings for this module mg_binds :: ModGuts -> ![CoreBind] -- | Foreign exports declared in this module mg_foreign :: ModGuts -> !ForeignStubs -- | Warnings declared in the module mg_warns :: ModGuts -> !Warnings -- | Annotations declared in this module mg_anns :: ModGuts -> [Annotation] -- | Coverage tick boxes in the module mg_hpc_info :: ModGuts -> !HpcInfo -- | Breakpoints for the module mg_modBreaks :: ModGuts -> !ModBreaks -- | Pool of vectorised declarations in the module mg_vect_info :: ModGuts -> !VectInfo -- | Class instance environment from home-package modules (including -- this one); c.f. tcg_inst_env mg_inst_env :: ModGuts -> InstEnv -- | Type-family instance enviroment for home-package modules -- (including this one); c.f. tcg_fam_inst_env mg_fam_inst_env :: ModGuts -> FamInstEnv -- | A CoreModule consists of just the fields of a ModGuts that are -- needed for the GHC.compileToCoreModule interface. data CoreModule CoreModule :: !Module -> !TypeEnv -> [CoreBind] -> ![Module] -> CoreModule -- | Module name cm_module :: CoreModule -> !Module -- | Type environment for types declared in this module cm_types :: CoreModule -> !TypeEnv -- | Declarations cm_binds :: CoreModule -> [CoreBind] -- | Imports cm_imports :: CoreModule -> ![Module] -- | A restricted form of ModGuts for code generation purposes data CgGuts CgGuts :: !Module -> [TyCon] -> [CoreBind] -> ![Module] -> !ForeignStubs -> ![PackageId] -> !HpcInfo -> !ModBreaks -> CgGuts -- | Module being compiled cg_module :: CgGuts -> !Module -- | Algebraic data types (including ones that started life as classes); -- generate constructors and info tables. Includes newtypes, just for the -- benefit of External Core cg_tycons :: CgGuts -> [TyCon] -- | The tidied main bindings, including previously-implicit bindings for -- record and class selectors, and data construtor wrappers. But *not* -- data constructor workers; reason: we we regard them as part of the -- code-gen of tycons cg_binds :: CgGuts -> [CoreBind] -- | Directly-imported modules; used to generate initialisation code cg_dir_imps :: CgGuts -> ![Module] -- | Foreign export stubs cg_foreign :: CgGuts -> !ForeignStubs -- | Dependent packages, used to generate #includes for C code gen cg_dep_pkgs :: CgGuts -> ![PackageId] -- | Program coverage tick box information cg_hpc_info :: CgGuts -> !HpcInfo -- | Module breakpoints cg_modBreaks :: CgGuts -> !ModBreaks -- | Foreign export stubs data ForeignStubs -- | We don't have any stubs NoStubs :: ForeignStubs -- | There are some stubs. Parameters: -- -- 1) Header file prototypes for foreign exported functions -- -- 2) C stubs to use when calling foreign exported functions ForeignStubs :: SDoc -> SDoc -> ForeignStubs -- | Records the modules directly imported by a module for extracting e.g. -- usage information type ImportedMods = ModuleEnv [(ModuleName, Bool, SrcSpan)] -- | A single node in a 'ModuleGraph. The nodes of the module graph are one -- of: -- -- data ModSummary ModSummary :: Module -> HscSource -> ModLocation -> ClockTime -> Maybe ClockTime -> [Located (ImportDecl RdrName)] -> [Located (ImportDecl RdrName)] -> FilePath -> DynFlags -> Maybe StringBuffer -> ModSummary -- | Identity of the module ms_mod :: ModSummary -> Module -- | The module source either plain Haskell, hs-boot or external core ms_hsc_src :: ModSummary -> HscSource -- | Location of the various files belonging to the module ms_location :: ModSummary -> ModLocation -- | Timestamp of source file ms_hs_date :: ModSummary -> ClockTime -- | Timestamp of object, if we have one ms_obj_date :: ModSummary -> Maybe ClockTime -- | Source imports of the module ms_srcimps :: ModSummary -> [Located (ImportDecl RdrName)] -- | Non-source imports of the module ms_imps :: ModSummary -> [Located (ImportDecl RdrName)] -- | Filename of preprocessed source file ms_hspp_file :: ModSummary -> FilePath -- | Cached flags from OPTIONS, INCLUDE and -- LANGUAGE pragmas in the modules source code ms_hspp_opts :: ModSummary -> DynFlags -- | The actual preprocessed source, if we have it ms_hspp_buf :: ModSummary -> Maybe StringBuffer ms_mod_name :: ModSummary -> ModuleName showModMsg :: HscTarget -> Bool -> ModSummary -> String -- | Did this ModSummary originate from a hs-boot file? isBootSummary :: ModSummary -> Bool msHsFilePath :: ModSummary -> FilePath msHiFilePath :: ModSummary -> FilePath msObjFilePath :: ModSummary -> FilePath data HscSource HsSrcFile :: HscSource HsBootFile :: HscSource ExtCoreFile :: HscSource isHsBoot :: HscSource -> Bool hscSourceString :: HscSource -> String -- | Helps us find information about modules in the home package type HomePackageTable = ModuleNameEnv HomeModInfo -- | Information about modules in the package being compiled data HomeModInfo HomeModInfo :: !ModIface -> !ModDetails -> !Maybe Linkable -> HomeModInfo -- | The basic loaded interface file: every loaded module has one of these, -- even if it is imported from another package hm_iface :: HomeModInfo -> !ModIface -- | Extra information that has been created from the ModIface for -- the module, typically during typechecking hm_details :: HomeModInfo -> !ModDetails -- | The actual artifact we would like to link to access things in this -- module. -- -- hm_linkable might be Nothing: -- --
    --
  1. If this is an .hs-boot module
  2. --
  3. Temporarily during compilation if we pruned away the old linkable -- because it was out of date.
  4. --
-- -- After a complete compilation (GHC.load), all -- hm_linkable fields in the HomePackageTable will be -- Just. -- -- When re-linking a module (HscMain.HscNoRecomp), we construct -- the HomeModInfo by building a new ModDetails from the -- old ModIface (only). hm_linkable :: HomeModInfo -> !Maybe Linkable emptyHomePackageTable :: HomePackageTable -- | Find all the instance declarations (of classes and families) that are -- in modules imported by this one, directly or indirectly, and are in -- the Home Package Table. This ensures that we don't see instances from -- modules --make compiled before this one, but which are not -- below this one. hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([Instance], [FamInst]) -- | Get rules from modules "below" this one (in the dependency sense) hptRules :: HscEnv -> [(ModuleName, IsBootInterface)] -> [CoreRule] -- | Get the combined VectInfo of all modules in the home package table. In -- contrast to instances and rules, we don't care whether the modules are -- "below" us in the dependency sense. The VectInfo of those modules not -- "below" us does not affect the compilation of the current module. hptVectInfo :: HscEnv -> VectInfo -- | Information about other packages that we have slurped in by reading -- their interface files data ExternalPackageState EPS :: !ModuleNameEnv (ModuleName, IsBootInterface) -> !PackageIfaceTable -> !PackageTypeEnv -> !PackageInstEnv -> !PackageFamInstEnv -> !PackageRuleBase -> !PackageVectInfo -> !PackageAnnEnv -> !ModuleEnv FamInstEnv -> !EpsStats -> ExternalPackageState -- | In OneShot mode (only), home-package modules accumulate in the -- external package state, and are sucked in lazily. For these home-pkg -- modules (only) we need to record which are boot modules. We set this -- field after loading all the explicitly-imported interfaces, but before -- doing anything else -- -- The ModuleName part is not necessary, but it's useful for debug -- prints, and it's convenient because this field comes direct from -- TcRnTypes.imp_dep_mods eps_is_boot :: ExternalPackageState -> !ModuleNameEnv (ModuleName, IsBootInterface) -- | The ModIfaces for modules in external packages whose interfaces -- we have opened. The declarations in these interface files are held in -- the eps_decls, eps_inst_env, eps_fam_inst_env -- and eps_rules fields of this record, not in the -- mi_decls fields of the interface we have sucked in. -- -- What is in the PIT is: -- -- eps_PIT :: ExternalPackageState -> !PackageIfaceTable -- | Result of typechecking all the external package interface files we -- have sucked in. The domain of the mapping is external-package modules eps_PTE :: ExternalPackageState -> !PackageTypeEnv -- | The total InstEnv accumulated from all the external-package -- modules eps_inst_env :: ExternalPackageState -> !PackageInstEnv -- | The total FamInstEnv accumulated from all the external-package -- modules eps_fam_inst_env :: ExternalPackageState -> !PackageFamInstEnv -- | The total RuleEnv accumulated from all the external-package -- modules eps_rule_base :: ExternalPackageState -> !PackageRuleBase -- | The total VectInfo accumulated from all the external-package -- modules eps_vect_info :: ExternalPackageState -> !PackageVectInfo -- | The total AnnEnv accumulated from all the external-package -- modules eps_ann_env :: ExternalPackageState -> !PackageAnnEnv -- | The family instances accumulated from external packages, keyed off the -- module that declared them eps_mod_fam_inst_env :: ExternalPackageState -> !ModuleEnv FamInstEnv -- | Stastics about what was loaded from external packages eps_stats :: ExternalPackageState -> !EpsStats -- | Accumulated statistics about what we are putting into the -- ExternalPackageState. "In" means stuff that is just read -- from interface files, "Out" means actually sucked in and type-checked data EpsStats EpsStats :: !Int -> !Int -> !Int -> !Int -> !Int -> !Int -> !Int -> EpsStats n_ifaces_in :: EpsStats -> !Int n_decls_in :: EpsStats -> !Int n_decls_out :: EpsStats -> !Int n_rules_in :: EpsStats -> !Int n_rules_out :: EpsStats -> !Int n_insts_in :: EpsStats -> !Int n_insts_out :: EpsStats -> !Int -- | Add stats for one newly-read interface addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats type PackageTypeEnv = TypeEnv -- | Helps us find information about modules in the imported packages type PackageIfaceTable = ModuleEnv ModIface emptyPackageIfaceTable :: PackageIfaceTable -- | Find the ModIface for a Module, searching in both the -- loaded home and external package module information lookupIfaceByModule :: DynFlags -> HomePackageTable -> PackageIfaceTable -> Module -> Maybe ModIface emptyModIface :: Module -> ModIface type PackageInstEnv = InstEnv type PackageRuleBase = RuleBase -- | Deal with gathering annotations in from all possible places and -- combining them into a single AnnEnv prepareAnnotations :: HscEnv -> Maybe ModGuts -> IO AnnEnv -- | Interactive context, recording information relevant to GHCi data InteractiveContext InteractiveContext :: [Module] -> [(Module, Maybe (ImportDecl RdrName))] -> GlobalRdrEnv -> [Id] -> [Resume] -> Maybe FilePath -> InteractiveContext -- | The context includes the top-level scope of these modules ic_toplev_scope :: InteractiveContext -> [Module] -- | The context includes just the exported parts of these modules ic_exports :: InteractiveContext -> [(Module, Maybe (ImportDecl RdrName))] -- | The contexts' cached GlobalRdrEnv, built from -- ic_toplev_scope and ic_exports ic_rn_gbl_env :: InteractiveContext -> GlobalRdrEnv -- | Names bound during interaction with the user. Later Ids shadow earlier -- ones with the same OccName Expressions are typed with these Ids in the -- envt For runtime-debugging, these Ids may have free TcTyVars of -- RuntimUnkSkol flavour, but no free TyVars (because the typechecker -- doesn't expect that) ic_tmp_ids :: InteractiveContext -> [Id] -- | The stack of breakpoint contexts ic_resume :: InteractiveContext -> [Resume] ic_cwd :: InteractiveContext -> Maybe FilePath emptyInteractiveContext :: InteractiveContext icPrintUnqual :: DynFlags -> InteractiveContext -> PrintUnqualified extendInteractiveContext :: InteractiveContext -> [Id] -> InteractiveContext substInteractiveContext :: InteractiveContext -> TvSubst -> InteractiveContext -- | Creates some functions that work out the best ways to format names for -- the user according to a set of heuristics mkPrintUnqualified :: DynFlags -> GlobalRdrEnv -> PrintUnqualified pprModulePrefix :: PprStyle -> Module -> OccName -> SDoc -- | A ModIface plus a ModDetails summarises everything we -- know about a compiled module. The ModIface is the stuff -- *before* linking, and can be written out to an interface file. The -- 'ModDetails is after linking and can be completely recovered from just -- the ModIface. -- -- When we read an interface file, we also construct a ModIface -- from it, except that we explicitly make the mi_decls and a few -- other fields empty; as when reading we consolidate the declarations -- etc. into a number of indexed maps and environments in the -- ExternalPackageState. data ModIface ModIface :: !Module -> !Fingerprint -> !Fingerprint -> !WhetherHasOrphans -> !WhetherHasFamInst -> !IsBootInterface -> Dependencies -> [Usage] -> ![IfaceExport] -> !Fingerprint -> [(OccName, Fixity)] -> Warnings -> [IfaceAnnotation] -> [(Fingerprint, IfaceDecl)] -> !Maybe GlobalRdrEnv -> [IfaceInst] -> [IfaceFamInst] -> [IfaceRule] -> !Fingerprint -> !IfaceVectInfo -> (Name -> Maybe WarningTxt) -> (OccName -> Fixity) -> (OccName -> Maybe (OccName, Fingerprint)) -> !AnyHpcUsage -> ModIface -- | Name of the module we are for mi_module :: ModIface -> !Module -- | Hash of the whole interface mi_iface_hash :: ModIface -> !Fingerprint -- | Hash of the ABI only mi_mod_hash :: ModIface -> !Fingerprint -- | Whether this module has orphans mi_orphan :: ModIface -> !WhetherHasOrphans -- | Whether this module has family instances mi_finsts :: ModIface -> !WhetherHasFamInst -- | Read from an hi-boot file? mi_boot :: ModIface -> !IsBootInterface -- | The dependencies of the module. This is consulted for -- directly-imported modules, but not for anything else (hence lazy) mi_deps :: ModIface -> Dependencies -- | Usages; kept sorted so that it's easy to decide whether to write a new -- iface file (changing usages doesn't affect the hash of this module) mi_usages :: ModIface -> [Usage] -- | Records the modules that are the declaration points for things -- exported by this module, and the OccNames of those things mi_exports :: ModIface -> ![IfaceExport] -- | Hash of export list mi_exp_hash :: ModIface -> !Fingerprint -- | Fixities mi_fixities :: ModIface -> [(OccName, Fixity)] -- | Warnings mi_warns :: ModIface -> Warnings -- | Annotations mi_anns :: ModIface -> [IfaceAnnotation] -- | Sorted type, variable, class etc. declarations mi_decls :: ModIface -> [(Fingerprint, IfaceDecl)] -- | Binds all the things defined at the top level in the original -- source code for this module. which is NOT the same as mi_exports, -- nor mi_decls (which may contains declarations for things not actually -- defined by the user). Used for GHCi and for inspecting the contents of -- modules via the GHC API only. -- -- (We need the source file to figure out the top-level environment, if -- we didn't compile this module from source then this field contains -- Nothing). -- -- Strictly speaking this field should live in the HomeModInfo, -- but that leads to more plumbing. mi_globals :: ModIface -> !Maybe GlobalRdrEnv -- | Sorted class instance mi_insts :: ModIface -> [IfaceInst] -- | Sorted family instances mi_fam_insts :: ModIface -> [IfaceFamInst] -- | Sorted rules mi_rules :: ModIface -> [IfaceRule] -- | Hash for orphan rules and class and family instances combined mi_orphan_hash :: ModIface -> !Fingerprint -- | Vectorisation information mi_vect_info :: ModIface -> !IfaceVectInfo -- | Cached lookup for mi_warns mi_warn_fn :: ModIface -> Name -> Maybe WarningTxt -- | Cached lookup for mi_fixities mi_fix_fn :: ModIface -> OccName -> Fixity -- | Cached lookup for mi_decls. The Nothing in -- mi_hash_fn means that the thing isn't in decls. It's useful to -- know that when seeing if we are up to date wrt. the old interface. The -- OccName is the parent of the name, if it has one. mi_hash_fn :: ModIface -> OccName -> Maybe (OccName, Fingerprint) -- | True if this program uses Hpc at any point in the program. mi_hpc :: ModIface -> !AnyHpcUsage -- | Constructs the cache for the mi_warn_fn field of a -- ModIface mkIfaceWarnCache :: Warnings -> Name -> Maybe WarningTxt -- | Constructs cache for the mi_hash_fn field of a ModIface mkIfaceHashCache :: [(Fingerprint, IfaceDecl)] -> (OccName -> Maybe (OccName, Fingerprint)) -- | Creates cached lookup for the mi_fix_fn field of -- ModIface mkIfaceFixCache :: [(OccName, Fixity)] -> OccName -> Fixity emptyIfaceWarnCache :: Name -> Maybe WarningTxt -- | Fixity environment mapping names to their fixities type FixityEnv = NameEnv FixItem -- | Fixity information for an Name. We keep the OccName in the -- range so that we can generate an interface from it data FixItem FixItem :: OccName -> Fixity -> FixItem lookupFixity :: FixityEnv -> Name -> Fixity emptyFixityEnv :: FixityEnv -- | A typecheckable-thing, essentially anything that has a name data TyThing AnId :: Id -> TyThing ADataCon :: DataCon -> TyThing ATyCon :: TyCon -> TyThing AClass :: Class -> TyThing -- | Get the Class from a TyThing if it is a class thing. -- Panics otherwise tyThingClass :: TyThing -> Class -- | Get the TyCon from a TyThing if it is a type constructor -- thing. Panics otherwise tyThingTyCon :: TyThing -> TyCon -- | Get the DataCon from a TyThing if it is a data -- constructor thing. Panics otherwise tyThingDataCon :: TyThing -> DataCon -- | Get the Id from a TyThing if it is a id *or* data -- constructor thing. Panics otherwise tyThingId :: TyThing -> Id -- | Determine the TyThings brought into scope by another -- TyThing other than itself. For example, Id's don't have -- any implicit TyThings as they just bring themselves into scope, but -- classes bring their dictionary datatype, type constructor and some -- selector functions into scope, just for a start! implicitTyThings :: TyThing -> [TyThing] -- | Returns True if there should be no interface-file declaration -- for this thing on its own: either it is built-in, or it is part of -- some other declaration, or it is generated implicitly by some other -- declaration. isImplicitTyThing :: TyThing -> Bool -- | A map from Names to TyThings, constructed by -- typechecking local declarations or interface files type TypeEnv = NameEnv TyThing -- | Find the TyThing for the given Name by using all the -- resources at our disposal: the compiled modules in the -- HomePackageTable and the compiled modules in other packages -- that live in PackageTypeEnv. Note that this does NOT look up -- the TyThing in the module being compiled: you have to do that -- yourself, if desired lookupType :: DynFlags -> HomePackageTable -> PackageTypeEnv -> Name -> Maybe TyThing -- | As lookupType, but with a marginally easier-to-use interface if -- you have a HscEnv lookupTypeHscEnv :: HscEnv -> Name -> IO (Maybe TyThing) mkTypeEnv :: [TyThing] -> TypeEnv emptyTypeEnv :: TypeEnv extendTypeEnv :: TypeEnv -> TyThing -> TypeEnv extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv lookupTypeEnv :: TypeEnv -> Name -> Maybe TyThing typeEnvElts :: TypeEnv -> [TyThing] typeEnvClasses :: TypeEnv -> [Class] typeEnvTyCons :: TypeEnv -> [TyCon] typeEnvIds :: TypeEnv -> [Id] typeEnvDataCons :: TypeEnv -> [DataCon] -- | Class that abstracts out the common ability of the monads in GHC to -- lookup a TyThing in the monadic environment by Name. -- Provides a number of related convenience functions for accessing -- particular kinds of TyThing class Monad m => MonadThings m lookupThing :: MonadThings m => Name -> m TyThing lookupId :: MonadThings m => Name -> m Id lookupDataCon :: MonadThings m => Name -> m DataCon lookupTyCon :: MonadThings m => Name -> m TyCon lookupClass :: MonadThings m => Name -> m Class -- | Records whether a module has orphans. An "orphan" is one of: -- -- type WhetherHasOrphans = Bool -- | Did this module originate from a *-boot file? type IsBootInterface = Bool -- | Records modules that we depend on by making a direct import from data Usage -- | Module from another package UsagePackageModule :: Module -> Fingerprint -> Usage -- | External package module depended on usg_mod :: Usage -> Module usg_mod_hash :: Usage -> Fingerprint -- | Module from the current package UsageHomeModule :: ModuleName -> Fingerprint -> [(OccName, Fingerprint)] -> Maybe Fingerprint -> Usage -- | Name of the module usg_mod_name :: Usage -> ModuleName usg_mod_hash :: Usage -> Fingerprint -- | Entities we depend on, sorted by occurrence name and fingerprinted. -- NB: usages are for parent names only, e.g. type constructors but not -- the associated data constructors. usg_entities :: Usage -> [(OccName, Fingerprint)] -- | Fingerprint for the export list we used to depend on this module, if -- we depend on the export list usg_exports :: Usage -> Maybe Fingerprint -- | Dependency information about modules and packages below this one in -- the import hierarchy. -- -- Invariant: the dependencies of a module M never includes -- M. -- -- Invariant: none of the lists contain duplicates. data Dependencies Deps :: [(ModuleName, IsBootInterface)] -> [PackageId] -> [Module] -> [Module] -> Dependencies -- | Home-package module dependencies dep_mods :: Dependencies -> [(ModuleName, IsBootInterface)] -- | External package dependencies dep_pkgs :: Dependencies -> [PackageId] -- | Orphan modules (whether home or external pkg), *not* including family -- instance orphans as they are anyway included in dep_finsts dep_orphs :: Dependencies -> [Module] -- | Modules that contain family instances (whether the instances are from -- the home or an external package) dep_finsts :: Dependencies -> [Module] noDependencies :: Dependencies -- | The NameCache makes sure that there is just one Unique assigned for -- each original name; i.e. (module-name, occ-name) pair and provides -- something of a lookup mechanism for those names. data NameCache NameCache :: UniqSupply -> OrigNameCache -> OrigIParamCache -> NameCache -- | Supply of uniques nsUniqs :: NameCache -> UniqSupply -- | Ensures that one original name gets one unique nsNames :: NameCache -> OrigNameCache -- | Ensures that one implicit parameter name gets one unique nsIPs :: NameCache -> OrigIParamCache -- | Per-module cache of original OccNames given Names type OrigNameCache = ModuleEnv (OccEnv Name) -- | Module-local cache of implicit parameter OccNames given -- Names type OrigIParamCache = Map (IPName OccName) (IPName Name) -- | A collection of AvailInfo - several things that are "available" type Avails = [AvailInfo] availsToNameSet :: [AvailInfo] -> NameSet availsToNameEnv :: [AvailInfo] -> NameEnv AvailInfo -- | Just the main name made available, i.e. not the available pieces of -- type or class brought into scope by the GenAvailInfo availName :: GenAvailInfo name -> name -- | All names made available by the availability information availNames :: GenAvailInfo name -> [name] -- | Records what things are available, i.e. in scope data GenAvailInfo name -- | An ordinary identifier in scope Avail :: name -> GenAvailInfo name -- | A type or class in scope. Parameters: -- -- 1) The name of the type or class -- -- 2) The available pieces of type or class. NB: If the type or class is -- itself to be in scope, it must be in this list. Thus, typically: -- AvailTC Eq [Eq, ==, /=] AvailTC :: name -> [name] -> GenAvailInfo name -- | Named things that are available type AvailInfo = GenAvailInfo Name -- | RdrNamed things that are available type RdrAvailInfo = GenAvailInfo OccName -- | The original names declared of a certain module that are exported type IfaceExport = (Module, [GenAvailInfo OccName]) -- | Warning information for a module data Warnings -- | Nothing deprecated NoWarnings :: Warnings -- | Whole module deprecated WarnAll :: WarningTxt -> Warnings -- | Some specific things deprecated WarnSome :: [(OccName, WarningTxt)] -> Warnings data WarningTxt WarningTxt :: [FastString] -> WarningTxt DeprecatedTxt :: [FastString] -> WarningTxt plusWarns :: Warnings -> Warnings -> Warnings -- | Information we can use to dynamically link modules into the compiler data Linkable LM :: ClockTime -> Module -> [Unlinked] -> Linkable -- | Time at which this linkable was built (i.e. when the bytecodes were -- produced, or the mod date on the files) linkableTime :: Linkable -> ClockTime -- | The linkable module itself linkableModule :: Linkable -> Module -- | Those files and chunks of code we have yet to link. -- -- INVARIANT: A valid linkable always has at least one Unlinked -- item. If this list is empty, the Linkable represents a fake linkable, -- which is generated in HscNothing mode to avoid recompiling modules. -- -- XXX: Do items get removed from this list when they get linked? linkableUnlinked :: Linkable -> [Unlinked] isObjectLinkable :: Linkable -> Bool -- | Objects which have yet to be linked by the compiler data Unlinked -- | An object file (.o) DotO :: FilePath -> Unlinked -- | Static archive file (.a) DotA :: FilePath -> Unlinked -- | Dynamically linked library file (.so, .dll, .dylib) DotDLL :: FilePath -> Unlinked -- | A byte-code object, lives only in memory BCOs :: CompiledByteCode -> ModBreaks -> Unlinked data CompiledByteCode -- | Is this an actual file on disk we can link in somehow? isObject :: Unlinked -> Bool -- | Retrieve the filename of the linkable if possible. Panic if it is a -- byte-code object nameOfObject :: Unlinked -> FilePath -- | Is this a bytecode linkable with no file on disk? isInterpretable :: Unlinked -> Bool -- | Retrieve the compiled byte-code if possible. Panic if it is a -- file-based linkable byteCodeOfObject :: Unlinked -> CompiledByteCode -- | Information about a modules use of Haskell Program Coverage data HpcInfo HpcInfo :: Int -> Int -> HpcInfo hpcInfoTickCount :: HpcInfo -> Int hpcInfoHash :: HpcInfo -> Int NoHpcInfo :: AnyHpcUsage -> HpcInfo -- | Is hpc used anywhere on the module *tree*? hpcUsed :: HpcInfo -> AnyHpcUsage emptyHpcInfo :: AnyHpcUsage -> HpcInfo -- | Find out if HPC is used by this module or any of the modules it -- depends upon isHpcUsed :: HpcInfo -> AnyHpcUsage -- | This is used to signal if one of my imports used HPC instrumentation -- even if there is no module-local HPC usage type AnyHpcUsage = Bool -- | All the information about the breakpoints for a given module data ModBreaks ModBreaks :: BreakArray -> !Array BreakIndex SrcSpan -> !Array BreakIndex [OccName] -> ModBreaks -- | The array of flags, one per breakpoint, indicating which breakpoints -- are enabled. modBreaks_flags :: ModBreaks -> BreakArray -- | An array giving the source span of each breakpoint. modBreaks_locs :: ModBreaks -> !Array BreakIndex SrcSpan -- | An array giving the names of the free variables at each breakpoint. modBreaks_vars :: ModBreaks -> !Array BreakIndex [OccName] -- | Breakpoint index type BreakIndex = Int emptyModBreaks :: ModBreaks -- | Vectorisation information for ModGuts, ModDetails and -- ExternalPackageState. data VectInfo VectInfo :: VarEnv (Var, Var) -> NameEnv (TyCon, TyCon) -> NameEnv (DataCon, DataCon) -> NameEnv (TyCon, Var) -> NameEnv (TyCon, Var) -> VectInfo -- | (f, f_v) keyed on f vectInfoVar :: VectInfo -> VarEnv (Var, Var) -- | (T, T_v) keyed on T vectInfoTyCon :: VectInfo -> NameEnv (TyCon, TyCon) -- | (C, C_v) keyed on C vectInfoDataCon :: VectInfo -> NameEnv (DataCon, DataCon) -- | (T_v, paT) keyed on T_v vectInfoPADFun :: VectInfo -> NameEnv (TyCon, Var) -- | (T, isoT) keyed on T vectInfoIso :: VectInfo -> NameEnv (TyCon, Var) -- | Vectorisation information for ModIface: a slightly less -- low-level view data IfaceVectInfo IfaceVectInfo :: [Name] -> [Name] -> [Name] -> IfaceVectInfo -- | All variables in here have a vectorised variant ifaceVectInfoVar :: IfaceVectInfo -> [Name] -- | All TyCons in here have a vectorised variant; the name of the -- vectorised variant and those of its data constructors are determined -- by OccName.mkVectTyConOcc and -- OccName.mkVectDataConOcc; the names of the isomorphisms are -- determined by OccName.mkVectIsoOcc ifaceVectInfoTyCon :: IfaceVectInfo -> [Name] -- | The vectorised form of all the TyCons in here coincides with -- the unconverted form; the name of the isomorphisms is determined by -- OccName.mkVectIsoOcc ifaceVectInfoTyConReuse :: IfaceVectInfo -> [Name] noVectInfo :: VectInfo plusVectInfo :: VectInfo -> VectInfo -> VectInfo noIfaceVectInfo :: IfaceVectInfo instance Eq TargetId instance Eq Warnings instance Eq name => Eq (GenAvailInfo name) instance Eq Dependencies instance Eq Usage instance Outputable Unlinked instance Outputable Linkable instance Outputable ModSummary instance Outputable FixItem instance Outputable n => Outputable (GenAvailInfo n) instance Outputable CoreModule instance Outputable TargetId instance Outputable Target instance (Functor m, ExceptionMonad m, MonadIO m) => GhcMonad (GhcT m) instance MonadIO m => WarnLogMonad (GhcT m) instance ExceptionMonad m => ExceptionMonad (GhcT m) instance MonadIO m => MonadIO (GhcT m) instance Monad m => Monad (GhcT m) instance Functor m => Functor (GhcT m) instance GhcMonad Ghc instance WarnLogMonad Ghc instance ExceptionMonad Ghc instance MonadIO Ghc instance Monad Ghc instance Functor Ghc instance Exception GhcApiError instance Typeable GhcApiError instance Show GhcApiError instance Exception SourceError instance Typeable SourceError instance Show SourceError module Parser parseModule :: P (Located (HsModule RdrName)) parseStmt :: P (Maybe (LStmt RdrName)) parseIdentifier :: P (Located RdrName) parseType :: P (LHsType RdrName) parseHeader :: P (Located (HsModule RdrName)) -- | Handy functions for creating much Core syntax module MkCore -- | Bind a binding group over an expression, using a let or -- case as appropriate (see CoreSyn#let_app_invariant) mkCoreLet :: CoreBind -> CoreExpr -> CoreExpr -- | Bind a list of binding groups over an expression. The leftmost binding -- group becomes the outermost group in the resulting expression mkCoreLets :: [CoreBind] -> CoreExpr -> CoreExpr -- | Construct an expression which represents the application of one -- expression to the other mkCoreApp :: CoreExpr -> CoreExpr -> CoreExpr -- | Construct an expression which represents the application of a number -- of expressions to another. The leftmost expression in the list is -- applied first mkCoreApps :: CoreExpr -> [CoreExpr] -> CoreExpr -- | Construct an expression which represents the application of a number -- of expressions to that of a data constructor expression. The leftmost -- expression in the list is applied first mkCoreConApps :: DataCon -> [CoreExpr] -> CoreExpr -- | Create a lambda where the given expression has a number of variables -- bound over it. The leftmost binder is that bound by the outermost -- lambda in the result mkCoreLams :: [CoreBndr] -> CoreExpr -> CoreExpr mkWildCase :: CoreExpr -> Type -> Type -> [CoreAlt] -> CoreExpr mkIfThenElse :: CoreExpr -> CoreExpr -> CoreExpr -> CoreExpr -- | Make a wildcard binder. This is typically used when you need a -- binder that you expect to use only at a *binding* site. Do not use it -- at occurrence sites because it has a single, fixed unique, and it's -- very easy to get into difficulties with shadowing. That's why it is -- used so little. mkWildValBinder :: Type -> Id mkWildEvBinder :: PredType -> EvVar -- | Create a CoreExpr which will evaluate to the a Word -- with the given value mkWordExpr :: Integer -> CoreExpr -- | Create a CoreExpr which will evaluate to the given -- Word mkWordExprWord :: Word -> CoreExpr -- | Create a CoreExpr which will evaluate to the given Int mkIntExpr :: Integer -> CoreExpr -- | Create a CoreExpr which will evaluate to the given Int mkIntExprInt :: Int -> CoreExpr -- | Create a CoreExpr which will evaluate to the given -- Integer mkIntegerExpr :: MonadThings m => Integer -> m CoreExpr -- | Create a CoreExpr which will evaluate to the given -- Float mkFloatExpr :: Float -> CoreExpr -- | Create a CoreExpr which will evaluate to the given -- Double mkDoubleExpr :: Double -> CoreExpr -- | Create a CoreExpr which will evaluate to the given -- Char mkCharExpr :: Char -> CoreExpr -- | Create a CoreExpr which will evaluate to the given -- String mkStringExpr :: MonadThings m => String -> m CoreExpr -- | Create a CoreExpr which will evaluate to a string morally -- equivalent to the given FastString mkStringExprFS :: MonadThings m => FastString -> m CoreExpr -- | Lifts a "small" constructor into a "big" constructor by recursive -- decompositon mkChunkified :: ([a] -> a) -> [a] -> a -- | Build a small tuple holding the specified variables mkCoreVarTup :: [Id] -> CoreExpr -- | Bulid the type of a small tuple that holds the specified variables mkCoreVarTupTy :: [Id] -> Type -- | Build a small tuple holding the specified expressions mkCoreTup :: [CoreExpr] -> CoreExpr -- | Build a big tuple holding the specified variables mkBigCoreVarTup :: [Id] -> CoreExpr -- | Build the type of a big tuple that holds the specified variables mkBigCoreVarTupTy :: [Id] -> Type -- | Build a big tuple holding the specified expressions mkBigCoreTup :: [CoreExpr] -> CoreExpr -- | Build the type of a big tuple that holds the specified type of thing mkBigCoreTupTy :: [Type] -> Type -- | Like mkTupleSelector but for tuples that are guaranteed never -- to be "big". -- --
--   mkSmallTupleSelector [x] x v e = [| e |]
--   mkSmallTupleSelector [x,y,z] x v e = [| case e of v { (x,y,z) -> x } |]
--   
mkSmallTupleSelector :: [Id] -> Id -> Id -> CoreExpr -> CoreExpr -- | As mkTupleCase, but for a tuple that is small enough to be -- guaranteed not to need nesting. mkSmallTupleCase :: [Id] -> CoreExpr -> Id -> CoreExpr -> CoreExpr -- | Builds a selector which scrutises the given expression and extracts -- the one name from the list given. If you want the no-shadowing rule to -- apply, the caller is responsible for making sure that none of these -- names are in scope. -- -- If there is just one Id in the tuple, then the selector is just -- the identity. -- -- If necessary, we pattern match on a "big" tuple. mkTupleSelector :: [Id] -> Id -> Id -> CoreExpr -> CoreExpr -- | A generalization of mkTupleSelector, allowing the body of the -- case to be an arbitrary expression. -- -- To avoid shadowing, we use uniques to invent new variables. -- -- If necessary we pattern match on a "big" tuple. mkTupleCase :: UniqSupply -> [Id] -> CoreExpr -> Id -> CoreExpr -> CoreExpr -- | Makes a list [] for lists of the specified type mkNilExpr :: Type -> CoreExpr -- | Makes a list (:) for lists of the specified type mkConsExpr :: Type -> CoreExpr -> CoreExpr -> CoreExpr -- | Make a list containing the given expressions, where the list has the -- given type mkListExpr :: Type -> [CoreExpr] -> CoreExpr -- | Make a fully applied foldr expression mkFoldrExpr :: MonadThings m => Type -> Type -> CoreExpr -> CoreExpr -> CoreExpr -> m CoreExpr -- | Make a build expression applied to a locally-bound worker -- function mkBuildExpr :: (MonadThings m, MonadUnique m) => Type -> ((Id, Type) -> (Id, Type) -> m CoreExpr) -> m CoreExpr mkRuntimeErrorApp :: Id -> Type -> String -> CoreExpr mkImpossibleExpr :: Type -> CoreExpr errorIds :: [Id] rEC_CON_ERROR_ID :: Id iRREFUT_PAT_ERROR_ID :: Id rUNTIME_ERROR_ID :: Id nON_EXHAUSTIVE_GUARDS_ERROR_ID :: Id nO_METHOD_BINDING_ERROR_ID :: Id pAT_ERROR_ID :: Id eRROR_ID :: Id rEC_SEL_ERROR_ID :: Id aBSENT_ERROR_ID :: Id module PrelRules primOpRules :: PrimOp -> Name -> [CoreRule] builtinRules :: [CoreRule] module Finder flushFinderCaches :: HscEnv -> IO () -- | The result of searching for an imported module. data FindResult -- | The module was found Found :: ModLocation -> Module -> FindResult -- | The requested package was not found NoPackage :: PackageId -> FindResult -- | _Error_: both in multiple packages FoundMultiple :: [PackageId] -> FindResult -- | The module was not found, including either * the specified places were -- searched * the package that this module should have been in * list of -- packages in which the module was hidden, * list of hidden packages -- containing this module NotFound :: [FilePath] -> (Maybe PackageId) -> [PackageId] -> [PackageId] -> FindResult -- | The module was not found in this package NotFoundInPackage :: PackageId -> FindResult -- | Locate a module that was imported by the user. We have the module's -- name, and possibly a package name. Without a package name, this -- function will use the search path and the known exposed packages to -- find the module, if a package is specified then only that package is -- searched for the module. findImportedModule :: HscEnv -> ModuleName -> Maybe FastString -> IO FindResult -- | Locate a specific Module. The purpose of this function is to -- create a ModLocation for a given Module, that is to find -- out where the files associated with this module live. It is used when -- reading the interface for a module mentioned by another interface, for -- example (a system import). findExactModule :: HscEnv -> Module -> IO FindResult -- | Search for a module in the home package only. findHomeModule :: HscEnv -> ModuleName -> IO FindResult findExposedPackageModule :: HscEnv -> ModuleName -> Maybe FastString -> IO FindResult mkHomeModLocation :: DynFlags -> ModuleName -> FilePath -> IO ModLocation mkHomeModLocation2 :: DynFlags -> ModuleName -> FilePath -> String -> IO ModLocation mkHiOnlyModLocation :: DynFlags -> Suffix -> FilePath -> String -> IO ModLocation addHomeModuleToFinder :: HscEnv -> ModuleName -> ModLocation -> IO Module uncacheModule :: HscEnv -> ModuleName -> IO () mkStubPaths :: DynFlags -> ModuleName -> ModLocation -> (FilePath, FilePath, FilePath) findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable) findObjectLinkable :: Module -> FilePath -> ClockTime -> IO Linkable cannotFindModule :: DynFlags -> ModuleName -> FindResult -> SDoc cannotFindInterface :: DynFlags -> ModuleName -> FindResult -> SDoc module CmmCPSZ -- | Top level driver for the CPS pass protoCmmCPSZ :: HscEnv -> (TopSRT, [CmmZ]) -> CmmZ -> IO (TopSRT, [CmmZ]) module CgHpc cgTickBox :: Module -> Int -> Code initHpc :: Module -> HpcInfo -> Code hpcTable :: Module -> HpcInfo -> Code module StgCmmHpc initHpc :: Module -> HpcInfo -> FCode CmmAGraph mkTickBox :: Module -> Int -> CmmAGraph module TcRnTypes type TcRnIf a b c = IOEnv (Env a b) c type TcRn a = TcRnIf TcGblEnv TcLclEnv a type TcM a = TcRn a type RnM a = TcRn a type IfM lcl a = TcRnIf IfGblEnv lcl a type IfL a = IfM IfLclEnv a type IfG a = IfM () a type TcRef a = IORef a data Env gbl lcl Env :: HscEnv -> {-# UNPACK #-} !IORef UniqSupply -> gbl -> lcl -> Env gbl lcl env_top :: Env gbl lcl -> HscEnv env_us :: Env gbl lcl -> {-# UNPACK #-} !IORef UniqSupply env_gbl :: Env gbl lcl -> gbl env_lcl :: Env gbl lcl -> lcl data TcGblEnv TcGblEnv :: Module -> HscSource -> GlobalRdrEnv -> Maybe [Type] -> FixityEnv -> RecFieldEnv -> TypeEnv -> TcRef TypeEnv -> InstEnv -> FamInstEnv -> [AvailInfo] -> ImportAvails -> DefUses -> TcRef NameSet -> TcRef Bool -> TcRef OccSet -> Maybe [Located (IE Name)] -> [LImportDecl Name] -> TcRef (Set RdrName) -> Maybe (HsGroup Name) -> Bag EvBind -> LHsBinds Id -> NameSet -> [LTcSpecPrag] -> Warnings -> [Annotation] -> [Instance] -> [FamInst] -> [LRuleDecl Id] -> [LForeignDecl Id] -> Maybe LHsDocString -> AnyHpcUsage -> Maybe Name -> TcGblEnv -- | Module being compiled tcg_mod :: TcGblEnv -> Module -- | What kind of module (regular Haskell, hs-boot, ext-core) tcg_src :: TcGblEnv -> HscSource -- | Top level envt; used during renaming tcg_rdr_env :: TcGblEnv -> GlobalRdrEnv -- | Types used for defaulting. Nothing => no default -- decl tcg_default :: TcGblEnv -> Maybe [Type] -- | Just for things in this module tcg_fix_env :: TcGblEnv -> FixityEnv -- | Just for things in this module tcg_field_env :: TcGblEnv -> RecFieldEnv -- | Global type env for the module we are compiling now. All TyCons and -- Classes (for this module) end up in here right away, along with their -- derived constructors, selectors. -- -- (Ids defined in this module start in the local envt, though they move -- to the global envt during zonking) tcg_type_env :: TcGblEnv -> TypeEnv tcg_type_env_var :: TcGblEnv -> TcRef TypeEnv -- | Instance envt for home-package modules; Includes the dfuns in -- tcg_insts tcg_inst_env :: TcGblEnv -> InstEnv -- | Ditto for family instances tcg_fam_inst_env :: TcGblEnv -> FamInstEnv -- | What is exported tcg_exports :: TcGblEnv -> [AvailInfo] -- | Information about what was imported from where, including things bound -- in this module. tcg_imports :: TcGblEnv -> ImportAvails -- | What is defined in this module and what is used. The latter is used to -- generate -- -- (a) version tracking; no need to recompile if these things have not -- changed version stamp -- -- (b) unused-import info tcg_dus :: TcGblEnv -> DefUses -- | Locally-defined top-level names to keep alive. -- -- Keep alive means give them an Exported flag, so that the -- simplifier does not discard them as dead code, and so that they are -- exposed in the interface file (but not to export to the user). -- -- Some things, like dict-fun Ids and default-method Ids are born -- with the Exported flag on, for exactly the above reason, but some we -- only discover as we go. Specifically: -- -- tcg_keep :: TcGblEnv -> TcRef NameSet -- | True = Template Haskell syntax used. -- -- We need this so that we can generate a dependency on the Template -- Haskell package, becuase the desugarer is going to emit loads of -- references to TH symbols. The reference is implicit rather than -- explicit, so we have to zap a mutable variable. tcg_th_used :: TcGblEnv -> TcRef Bool -- | Allows us to choose unique DFun names. tcg_dfun_n :: TcGblEnv -> TcRef OccSet tcg_rn_exports :: TcGblEnv -> Maybe [Located (IE Name)] tcg_rn_imports :: TcGblEnv -> [LImportDecl Name] tcg_used_rdrnames :: TcGblEnv -> TcRef (Set RdrName) -- | Renamed decls, maybe. Nothing = Don't retain renamed -- decls. tcg_rn_decls :: TcGblEnv -> Maybe (HsGroup Name) tcg_ev_binds :: TcGblEnv -> Bag EvBind tcg_binds :: TcGblEnv -> LHsBinds Id tcg_sigs :: TcGblEnv -> NameSet tcg_imp_specs :: TcGblEnv -> [LTcSpecPrag] tcg_warns :: TcGblEnv -> Warnings tcg_anns :: TcGblEnv -> [Annotation] tcg_insts :: TcGblEnv -> [Instance] tcg_fam_insts :: TcGblEnv -> [FamInst] tcg_rules :: TcGblEnv -> [LRuleDecl Id] tcg_fords :: TcGblEnv -> [LForeignDecl Id] -- | Maybe Haddock header docs tcg_doc_hdr :: TcGblEnv -> Maybe LHsDocString -- | True if any part of the prog uses hpc instrumentation. tcg_hpc :: TcGblEnv -> AnyHpcUsage -- | The Name of the main function, if this module is the main module. tcg_main :: TcGblEnv -> Maybe Name data TcLclEnv TcLclEnv :: SrcSpan -> [ErrCtxt] -> TcRef Messages -> ThStage -> ArrowCtxt -> LocalRdrEnv -> TcTypeEnv -> TcRef TcTyVarSet -> TcRef WantedConstraints -> TcRef Unique -> Unique -> TcLclEnv tcl_loc :: TcLclEnv -> SrcSpan tcl_ctxt :: TcLclEnv -> [ErrCtxt] tcl_errs :: TcLclEnv -> TcRef Messages tcl_th_ctxt :: TcLclEnv -> ThStage tcl_arrow_ctxt :: TcLclEnv -> ArrowCtxt tcl_rdr :: TcLclEnv -> LocalRdrEnv tcl_env :: TcLclEnv -> TcTypeEnv tcl_tyvars :: TcLclEnv -> TcRef TcTyVarSet tcl_lie :: TcLclEnv -> TcRef WantedConstraints tcl_meta :: TcLclEnv -> TcRef Unique tcl_untch :: TcLclEnv -> Unique data IfGblEnv IfGblEnv :: Maybe (Module, IfG TypeEnv) -> IfGblEnv if_rec_types :: IfGblEnv -> Maybe (Module, IfG TypeEnv) data IfLclEnv IfLclEnv :: Module -> SDoc -> UniqFM TyVar -> UniqFM Id -> IfLclEnv if_mod :: IfLclEnv -> Module if_loc :: IfLclEnv -> SDoc if_tv_env :: IfLclEnv -> UniqFM TyVar if_id_env :: IfLclEnv -> UniqFM Id type ErrCtxt = (Bool, TidyEnv -> TcM (TidyEnv, Message)) data RecFieldEnv RecFields :: (NameEnv [Name]) -> NameSet -> RecFieldEnv -- | ImportAvails summarises what was imported from where, -- irrespective of whether the imported things are actually used or not. -- It is used: -- -- data ImportAvails ImportAvails :: ModuleEnv [(ModuleName, Bool, SrcSpan)] -> ModuleNameEnv (ModuleName, IsBootInterface) -> [PackageId] -> [Module] -> [Module] -> ImportAvails -- | Domain is all directly-imported modules The ModuleName is what -- the module was imported as, e.g. in import Foo as Bar it is -- Bar. -- -- The Bool means: -- -- -- -- Used -- -- (a) to help construct the usage information in the interface file; if -- we import somethign we need to recompile if the export version changes -- -- (b) to specify what child modules to initialise -- -- We need a full ModuleEnv rather than a ModuleNameEnv here, because we -- might be importing modules of the same name from different packages. -- (currently not the case, but might be in the future). imp_mods :: ImportAvails -> ModuleEnv [(ModuleName, Bool, SrcSpan)] -- | Home-package modules needed by the module being compiled -- -- It doesn't matter whether any of these dependencies are actually -- used when compiling the module; they are listed if they are -- below it at all. For example, suppose M imports A which imports X. -- Then compiling M might not need to consult X.hi, but X is still listed -- in M's dependencies. imp_dep_mods :: ImportAvails -> ModuleNameEnv (ModuleName, IsBootInterface) -- | Packages needed by the module being compiled, whether directly, or via -- other modules in this package, or via modules imported from other -- packages. imp_dep_pkgs :: ImportAvails -> [PackageId] -- | Orphan modules below us in the import tree (and maybe including us for -- imported modules) imp_orphs :: ImportAvails -> [Module] -- | Family instance modules below us in the import tree (and maybe -- including us for imported modules) imp_finsts :: ImportAvails -> [Module] emptyImportAvails :: ImportAvails plusImportAvails :: ImportAvails -> ImportAvails -> ImportAvails data WhereFrom ImportByUser :: IsBootInterface -> WhereFrom ImportBySystem :: WhereFrom mkModDeps :: [(ModuleName, IsBootInterface)] -> ModuleNameEnv (ModuleName, IsBootInterface) type TcTypeEnv = NameEnv TcTyThing data TcTyThing AGlobal :: TyThing -> TcTyThing ATcId :: TcId -> ThLevel -> TcTyThing tct_id :: TcTyThing -> TcId tct_level :: TcTyThing -> ThLevel ATyVar :: Name -> TcType -> TcTyThing AThing :: TcKind -> TcTyThing pprTcTyThingCategory :: TcTyThing -> SDoc data ThStage Splice :: ThStage Comp :: ThStage Brack :: ThStage -> (TcRef [PendingSplice]) -> (TcRef WantedConstraints) -> ThStage topStage :: ThStage topAnnStage :: ThStage topSpliceStage :: ThStage type ThLevel = Int impLevel :: ThLevel outerLevel :: ThLevel thLevel :: ThStage -> ThLevel data ArrowCtxt NoArrowCtxt :: ArrowCtxt newArrowScope :: TcM a -> TcM a escapeArrowScope :: TcM a -> TcM a data Untouchables NoUntouchables :: Untouchables TouchableRange :: Unique -> Unique -> Untouchables inTouchableRange :: Untouchables -> TcTyVar -> Bool isNoUntouchables :: Untouchables -> Bool data WantedConstraints WC :: Bag WantedEvVar -> Bag Implication -> Bag FlavoredEvVar -> WantedConstraints wc_flat :: WantedConstraints -> Bag WantedEvVar wc_impl :: WantedConstraints -> Bag Implication wc_insol :: WantedConstraints -> Bag FlavoredEvVar insolubleWC :: WantedConstraints -> Bool emptyWC :: WantedConstraints isEmptyWC :: WantedConstraints -> Bool andWC :: WantedConstraints -> WantedConstraints -> WantedConstraints addFlats :: WantedConstraints -> Bag WantedEvVar -> WantedConstraints addImplics :: WantedConstraints -> Bag Implication -> WantedConstraints mkFlatWC :: Bag WantedEvVar -> WantedConstraints data EvVarX a EvVarX :: EvVar -> a -> EvVarX a mkEvVarX :: EvVar -> a -> EvVarX a evVarOf :: EvVarX a -> EvVar evVarX :: EvVarX a -> a evVarOfPred :: EvVarX a -> PredType type WantedEvVar = EvVarX WantedLoc wantedToFlavored :: WantedEvVar -> FlavoredEvVar keepWanted :: Bag FlavoredEvVar -> Bag WantedEvVar data Implication Implic :: Untouchables -> TcTypeEnv -> TcTyVarSet -> [EvVar] -> GivenLoc -> WantedConstraints -> Bool -> EvBindsVar -> Implication ic_untch :: Implication -> Untouchables ic_env :: Implication -> TcTypeEnv ic_skols :: Implication -> TcTyVarSet ic_given :: Implication -> [EvVar] ic_loc :: Implication -> GivenLoc ic_wanted :: Implication -> WantedConstraints ic_insol :: Implication -> Bool ic_binds :: Implication -> EvBindsVar data CtLoc orig CtLoc :: orig -> SrcSpan -> [ErrCtxt] -> CtLoc orig ctLocSpan :: CtLoc o -> SrcSpan ctLocOrigin :: CtLoc o -> o setCtLocOrigin :: CtLoc o -> o' -> CtLoc o' data CtOrigin OccurrenceOf :: Name -> CtOrigin AppOrigin :: CtOrigin SpecPragOrigin :: Name -> CtOrigin TypeEqOrigin :: EqOrigin -> CtOrigin IPOccOrigin :: (IPName Name) -> CtOrigin LiteralOrigin :: (HsOverLit Name) -> CtOrigin NegateOrigin :: CtOrigin ArithSeqOrigin :: (ArithSeqInfo Name) -> CtOrigin PArrSeqOrigin :: (ArithSeqInfo Name) -> CtOrigin SectionOrigin :: CtOrigin TupleOrigin :: CtOrigin ExprSigOrigin :: CtOrigin PatSigOrigin :: CtOrigin PatOrigin :: CtOrigin RecordUpdOrigin :: CtOrigin ViewPatOrigin :: CtOrigin ScOrigin :: CtOrigin DerivOrigin :: CtOrigin StandAloneDerivOrigin :: CtOrigin DefaultOrigin :: CtOrigin DoOrigin :: CtOrigin IfOrigin :: CtOrigin ProcOrigin :: CtOrigin AnnOrigin :: CtOrigin FunDepOrigin :: CtOrigin data EqOrigin UnifyOrigin :: TcType -> TcType -> EqOrigin uo_actual :: EqOrigin -> TcType uo_expected :: EqOrigin -> TcType type WantedLoc = CtLoc CtOrigin type GivenLoc = CtLoc SkolemInfo pushErrCtxt :: orig -> ErrCtxt -> CtLoc orig -> CtLoc orig data SkolemInfo SigSkol :: UserTypeCtxt -> Type -> SkolemInfo ClsSkol :: Class -> SkolemInfo InstSkol :: SkolemInfo DataSkol :: SkolemInfo FamInstSkol :: SkolemInfo PatSkol :: DataCon -> (HsMatchContext Name) -> SkolemInfo ArrowSkol :: SkolemInfo IPSkol :: [IPName Name] -> SkolemInfo RuleSkol :: RuleName -> SkolemInfo InferSkol :: [(Name, TcType)] -> SkolemInfo RuntimeUnkSkol :: SkolemInfo BracketSkol :: SkolemInfo UnkSkol :: SkolemInfo data CtFlavor Given :: GivenLoc -> CtFlavor Derived :: WantedLoc -> CtFlavor Wanted :: WantedLoc -> CtFlavor pprFlavorArising :: CtFlavor -> SDoc isWanted :: CtFlavor -> Bool isGiven :: CtFlavor -> Bool isDerived :: CtFlavor -> Bool type FlavoredEvVar = EvVarX CtFlavor pprEvVarTheta :: [EvVar] -> SDoc pprWantedEvVar :: WantedEvVar -> SDoc pprWantedsWithLocs :: WantedConstraints -> SDoc pprEvVars :: [EvVar] -> SDoc pprEvVarWithType :: EvVar -> SDoc pprArising :: CtOrigin -> SDoc pprArisingAt :: Outputable o => CtLoc o -> SDoc type TcId = Id type TcIdSet = IdSet data TcTyVarBind TcTyVarBind :: TcTyVar -> TcType -> TcTyVarBind type TcTyVarBinds = Bag TcTyVarBind instance Outputable EqOrigin instance Outputable CtOrigin instance Outputable SkolemInfo instance Outputable CtFlavor instance Outputable (EvVarX a) instance Outputable Implication instance Outputable Untouchables instance Outputable WantedConstraints instance Outputable WhereFrom instance Outputable TcTyThing instance Outputable ThStage instance Outputable TcTyVarBind module TcRnMonad initTc :: HscEnv -> HscSource -> Bool -> Module -> TcM r -> IO (Messages, Maybe r) initTcPrintErrors :: HscEnv -> Module -> TcM r -> IO (Messages, Maybe r) initTcRnIf :: Char -> HscEnv -> gbl -> lcl -> TcRnIf gbl lcl a -> IO a getTopEnv :: TcRnIf gbl lcl HscEnv getGblEnv :: TcRnIf gbl lcl gbl updGblEnv :: (gbl -> gbl) -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a setGblEnv :: gbl -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a getLclEnv :: TcRnIf gbl lcl lcl updLclEnv :: (lcl -> lcl) -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a setLclEnv :: lcl' -> TcRnIf gbl lcl' a -> TcRnIf gbl lcl a getEnvs :: TcRnIf gbl lcl (gbl, lcl) setEnvs :: (gbl', lcl') -> TcRnIf gbl' lcl' a -> TcRnIf gbl lcl a getDOpts :: TcRnIf gbl lcl DynFlags xoptM :: ExtensionFlag -> TcRnIf gbl lcl Bool doptM :: DynFlag -> TcRnIf gbl lcl Bool setOptM :: ExtensionFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a unsetOptM :: DynFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a -- | Do it flag is true ifDOptM :: DynFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () ifXOptM :: ExtensionFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () getGhcMode :: TcRnIf gbl lcl GhcMode getEpsVar :: TcRnIf gbl lcl (TcRef ExternalPackageState) getEps :: TcRnIf gbl lcl ExternalPackageState -- | Update the external package state. Returns the second result of the -- modifier function. -- -- This is an atomic operation and forces evaluation of the modified EPS -- in order to avoid space leaks. updateEps :: (ExternalPackageState -> (ExternalPackageState, a)) -> TcRnIf gbl lcl a -- | Update the external package state. -- -- This is an atomic operation and forces evaluation of the modified EPS -- in order to avoid space leaks. updateEps_ :: (ExternalPackageState -> ExternalPackageState) -> TcRnIf gbl lcl () getHpt :: TcRnIf gbl lcl HomePackageTable getEpsAndHpt :: TcRnIf gbl lcl (ExternalPackageState, HomePackageTable) newMetaUnique :: TcM Unique newUnique :: TcRnIf gbl lcl Unique newUniqueSupply :: TcRnIf gbl lcl UniqSupply newLocalName :: Name -> TcRnIf gbl lcl Name newSysLocalIds :: FastString -> [TcType] -> TcRnIf gbl lcl [TcId] newTcRef :: a -> TcRnIf gbl lcl (TcRef a) readTcRef :: TcRef a -> TcRnIf gbl lcl a writeTcRef :: TcRef a -> a -> TcRnIf gbl lcl () updTcRef :: TcRef a -> (a -> a) -> TcRnIf gbl lcl () traceTc :: String -> SDoc -> TcRn () traceTcN :: Int -> String -> SDoc -> TcRn () traceSplice :: SDoc -> TcRn () traceRn :: SDoc -> TcRn () traceHiDiffs :: SDoc -> TcRnIf m n () traceIf :: SDoc -> TcRnIf m n () traceOptIf :: DynFlag -> SDoc -> TcRnIf m n () traceOptTcRn :: DynFlag -> SDoc -> TcRn () dumpTcRn :: SDoc -> TcRn () debugDumpTcRn :: SDoc -> TcRn () dumpOptTcRn :: DynFlag -> SDoc -> TcRn () getModule :: TcRn Module setModule :: Module -> TcRn a -> TcRn a tcIsHsBoot :: TcRn Bool getGlobalRdrEnv :: TcRn GlobalRdrEnv getRdrEnvs :: TcRn (GlobalRdrEnv, LocalRdrEnv) getImports :: TcRn ImportAvails getFixityEnv :: TcRn FixityEnv extendFixityEnv :: [(Name, FixItem)] -> RnM a -> RnM a getRecFieldEnv :: TcRn RecFieldEnv getDeclaredDefaultTys :: TcRn (Maybe [Type]) getSrcSpanM :: TcRn SrcSpan setSrcSpan :: SrcSpan -> TcRn a -> TcRn a addLocM :: (a -> TcM b) -> Located a -> TcM b wrapLocM :: (a -> TcM b) -> Located a -> TcM (Located b) wrapLocFstM :: (a -> TcM (b, c)) -> Located a -> TcM (Located b, c) wrapLocSndM :: (a -> TcM (b, c)) -> Located a -> TcM (b, Located c) getErrsVar :: TcRn (TcRef Messages) setErrsVar :: TcRef Messages -> TcRn a -> TcRn a addErr :: Message -> TcRn () failWith :: Message -> TcRn a addErrAt :: SrcSpan -> Message -> TcRn () addErrs :: [(SrcSpan, Message)] -> TcRn () addWarn :: Message -> TcRn () addWarnAt :: SrcSpan -> Message -> TcRn () checkErr :: Bool -> Message -> TcRn () warnIf :: Bool -> Message -> TcRn () addMessages :: Messages -> TcRn () discardWarnings :: TcRn a -> TcRn a addReport :: Message -> Message -> TcRn () addReportAt :: SrcSpan -> Message -> Message -> TcRn () addLongErrAt :: SrcSpan -> Message -> Message -> TcRn () dumpDerivingInfo :: SDoc -> TcM () try_m :: TcRn r -> TcRn (Either IOEnvFailure r) recoverM :: TcRn r -> TcRn r -> TcRn r mapAndRecoverM :: (a -> TcRn b) -> [a] -> TcRn [b] tryTc :: TcRn a -> TcRn (Messages, Maybe a) tryTcErrs :: TcRn a -> TcRn (Messages, Maybe a) tryTcLIE :: TcM a -> TcM (Messages, Maybe a) tryTcLIE_ :: TcM r -> TcM r -> TcM r checkNoErrs :: TcM r -> TcM r ifErrsM :: TcRn r -> TcRn r -> TcRn r failIfErrsM :: TcRn () getErrCtxt :: TcM [ErrCtxt] setErrCtxt :: [ErrCtxt] -> TcM a -> TcM a addErrCtxt :: Message -> TcM a -> TcM a addErrCtxtM :: (TidyEnv -> TcM (TidyEnv, Message)) -> TcM a -> TcM a addLandmarkErrCtxt :: Message -> TcM a -> TcM a updCtxt :: ([ErrCtxt] -> [ErrCtxt]) -> TcM a -> TcM a maybeAddErrCtxt :: Maybe Message -> TcM a -> TcM a popErrCtxt :: TcM a -> TcM a getCtLoc :: orig -> TcM (CtLoc orig) setCtLoc :: CtLoc orig -> TcM a -> TcM a addErrTc :: Message -> TcM () addErrsTc :: [Message] -> TcM () addErrTcM :: (TidyEnv, Message) -> TcM () failWithTc :: Message -> TcM a failWithTcM :: (TidyEnv, Message) -> TcM a checkTc :: Bool -> Message -> TcM () addWarnTc :: Message -> TcM () addWarnTcM :: (TidyEnv, Message) -> TcM () warnTc :: Bool -> Message -> TcM () tcInitTidyEnv :: TcM TidyEnv add_err_tcm :: TidyEnv -> Message -> SrcSpan -> [ErrCtxt] -> TcM () mkErrInfo :: TidyEnv -> [ErrCtxt] -> TcM SDoc mAX_CONTEXTS :: Int debugTc :: TcM () -> TcM () newTcEvBinds :: TcM EvBindsVar extendTcEvBinds :: TcEvBinds -> EvVar -> EvTerm -> TcM TcEvBinds addTcEvBind :: EvBindsVar -> EvVar -> EvTerm -> TcM () chooseUniqueOccTc :: (OccSet -> OccName) -> TcM OccName getConstraintVar :: TcM (TcRef WantedConstraints) setConstraintVar :: TcRef WantedConstraints -> TcM a -> TcM a emitConstraints :: WantedConstraints -> TcM () emitFlat :: WantedEvVar -> TcM () emitFlats :: Bag WantedEvVar -> TcM () emitImplication :: Implication -> TcM () emitImplications :: Bag Implication -> TcM () captureConstraints :: TcM a -> TcM (a, WantedConstraints) captureUntouchables :: TcM a -> TcM (a, Untouchables) isUntouchable :: TcTyVar -> TcM Bool getLclTypeEnv :: TcM (NameEnv TcTyThing) setLclTypeEnv :: TcLclEnv -> TcM a -> TcM a recordThUse :: TcM () keepAliveTc :: Id -> TcM () keepAliveSetTc :: NameSet -> TcM () getStage :: TcM ThStage setStage :: ThStage -> TcM a -> TcM a getLocalRdrEnv :: RnM LocalRdrEnv setLocalRdrEnv :: LocalRdrEnv -> RnM a -> RnM a mkIfLclEnv :: Module -> SDoc -> IfLclEnv initIfaceTcRn :: IfG a -> TcRn a initIfaceExtCore :: IfL a -> TcRn a initIfaceCheck :: HscEnv -> IfG a -> IO a initIfaceTc :: ModIface -> (TcRef TypeEnv -> IfL a) -> TcRnIf gbl lcl a initIfaceRules :: HscEnv -> ModGuts -> IfG a -> IO a initIfaceLcl :: Module -> SDoc -> IfL a -> IfM lcl a getIfModule :: IfL Module failIfM :: Message -> IfL a forkM_maybe :: SDoc -> IfL a -> IfL (Maybe a) forkM :: SDoc -> IfL a -> IfL a instance MonadUnique (IOEnv (Env gbl lcl)) module TcMType type TcTyVar = TyVar type TcKind = Kind type TcType = Type type TcTauType = TcType type TcThetaType = ThetaType type TcTyVarSet = TyVarSet newFlexiTyVar :: Kind -> TcM TcTyVar newFlexiTyVarTy :: Kind -> TcM TcType newFlexiTyVarTys :: Int -> Kind -> TcM [TcType] newKindVar :: TcM TcKind newKindVars :: Int -> TcM [TcKind] mkTcTyVarName :: Unique -> FastString -> Name newMetaTyVar :: MetaInfo -> Kind -> TcM TcTyVar readMetaTyVar :: TyVar -> TcM MetaDetails writeMetaTyVar :: TcTyVar -> TcType -> TcM () writeMetaTyVarRef :: TcTyVar -> TcRef MetaDetails -> TcType -> TcM () isFilledMetaTyVar :: TyVar -> TcM Bool isFlexiMetaTyVar :: TyVar -> TcM Bool newEvVar :: TcPredType -> TcM EvVar newCoVar :: TcType -> TcType -> TcM CoVar newEvVars :: TcThetaType -> TcM [EvVar] writeWantedCoVar :: CoVar -> Coercion -> TcM () readWantedCoVar :: CoVar -> TcM MetaDetails newIP :: IPName Name -> TcType -> TcM IpId newDict :: Class -> [TcType] -> TcM DictId newSilentGiven :: PredType -> TcM EvVar isSilentEvVar :: EvVar -> Bool newWantedEvVar :: TcPredType -> TcM EvVar newWantedEvVars :: TcThetaType -> TcM [EvVar] newTcEvBinds :: TcM EvBindsVar addTcEvBind :: EvBindsVar -> EvVar -> EvTerm -> TcM () tcInstTyVar :: TyVar -> TcM TcTyVar tcInstTyVars :: [TyVar] -> TcM ([TcTyVar], [TcType], TvSubst) tcInstSigTyVars :: [TyVar] -> TcM [TcTyVar] tcInstType :: ([TyVar] -> TcM [TcTyVar]) -> TcType -> TcM ([TcTyVar], TcThetaType, TcType) instMetaTyVar :: MetaInfo -> TyVar -> TcM TcTyVar tcInstSkolTyVars :: [TyVar] -> TcM [TcTyVar] tcInstSuperSkolTyVars :: [TyVar] -> TcM [TcTyVar] tcInstSkolTyVar :: Bool -> TyVar -> TcM TcTyVar tcInstSkolType :: TcType -> TcM ([TcTyVar], TcThetaType, TcType) tcSkolDFunType :: Type -> TcM ([TcTyVar], TcThetaType, TcType) tcSuperSkolTyVars :: [TyVar] -> [TcTyVar] data Rank data UserTypeCtxt FunSigCtxt :: Name -> UserTypeCtxt ExprSigCtxt :: UserTypeCtxt ConArgCtxt :: Name -> UserTypeCtxt TySynCtxt :: Name -> UserTypeCtxt GenPatCtxt :: UserTypeCtxt LamPatSigCtxt :: UserTypeCtxt BindPatSigCtxt :: UserTypeCtxt ResSigCtxt :: UserTypeCtxt ForSigCtxt :: Name -> UserTypeCtxt DefaultDeclCtxt :: UserTypeCtxt SpecInstCtxt :: UserTypeCtxt ThBrackCtxt :: UserTypeCtxt GenSigCtxt :: UserTypeCtxt checkValidType :: UserTypeCtxt -> Type -> TcM () checkValidMonoType :: Type -> TcM () data SourceTyCtxt ClassSCCtxt :: Name -> SourceTyCtxt SigmaCtxt :: SourceTyCtxt DataTyCtxt :: Name -> SourceTyCtxt TypeCtxt :: SourceTyCtxt InstThetaCtxt :: SourceTyCtxt checkValidTheta :: SourceTyCtxt -> ThetaType -> TcM () checkValidInstance :: LHsType Name -> [TyVar] -> ThetaType -> Class -> [TcType] -> TcM () checkValidTypeInst :: [Type] -> Type -> TcM () checkTyFamFreeness :: Type -> TcM () arityErr :: Outputable a => String -> a -> Int -> Int -> SDoc growPredTyVars :: TcPredType -> TyVarSet -> TyVarSet growThetaTyVars :: TcThetaType -> TyVarSet -> TyVarSet validDerivPred :: PredType -> Bool zonkType :: (TcTyVar -> TcM Type) -> TcType -> TcM Type mkZonkTcTyVar :: (TcTyVar -> TcM Type) -> TcTyVar -> TcM TcType zonkTcPredType :: TcPredType -> TcM TcPredType zonkTcTypeCarefully :: TcType -> TcM TcType skolemiseUnboundMetaTyVar :: TcTyVar -> TcTyVarDetails -> TcM TyVar zonkTcTyVar :: TcTyVar -> TcM TcType zonkTcTyVars :: [TcTyVar] -> TcM [TcType] zonkTcTyVarsAndFV :: TcTyVarSet -> TcM TcTyVarSet zonkSigTyVar :: TcTyVar -> TcM TcTyVar zonkQuantifiedTyVar :: TcTyVar -> TcM TcTyVar zonkQuantifiedTyVars :: [TcTyVar] -> TcM [TcTyVar] zonkTcType :: TcType -> TcM TcType zonkTcTypes :: [TcType] -> TcM [TcType] zonkTcThetaType :: TcThetaType -> TcM TcThetaType zonkTcKindToKind :: TcKind -> TcM Kind zonkTcKind :: TcKind -> TcM TcKind zonkImplication :: Implication -> TcM Implication zonkEvVar :: EvVar -> TcM EvVar zonkWantedEvVar :: WantedEvVar -> TcM WantedEvVar zonkFlavoredEvVar :: FlavoredEvVar -> TcM FlavoredEvVar zonkWC :: WantedConstraints -> TcM WantedConstraints zonkWantedEvVars :: Bag WantedEvVar -> TcM (Bag WantedEvVar) zonkTcTypeAndSubst :: TvSubst -> TcType -> TcM TcType tcGetGlobalTyVars :: TcM TcTyVarSet readKindVar :: KindVar -> TcM (MetaDetails) writeKindVar :: KindVar -> TcKind -> TcM () module TcHsSyn mkHsConApp :: DataCon -> [Type] -> [HsExpr Id] -> LHsExpr Id mkHsDictLet :: TcEvBinds -> LHsExpr Id -> LHsExpr Id mkHsApp :: LHsExpr name -> LHsExpr name -> LHsExpr name hsLitType :: HsLit -> TcType hsLPatType :: OutPat Id -> Type hsPatType :: Pat Id -> Type mkHsAppTy :: LHsType name -> LHsType name -> LHsType name mkSimpleHsAlt :: LPat id -> LHsExpr id -> LMatch id nlHsIntLit :: Integer -> LHsExpr id shortCutLit :: OverLitVal -> TcType -> Maybe (HsExpr TcId) hsOverLitName :: OverLitVal -> Name type TcId = Id type TcIdSet = IdSet zonkTopDecls :: Bag EvBind -> LHsBinds TcId -> NameSet -> [LRuleDecl TcId] -> [LTcSpecPrag] -> [LForeignDecl TcId] -> TcM ([Id], Bag EvBind, Bag (LHsBind Id), [LForeignDecl Id], [LTcSpecPrag], [LRuleDecl Id]) zonkTopExpr :: HsExpr TcId -> TcM (HsExpr Id) zonkTopLExpr :: LHsExpr TcId -> TcM (LHsExpr Id) zonkId :: TcId -> TcM TcId zonkTopBndrs :: [TcId] -> TcM [Id] module RnHsDoc rnHsDoc :: HsDocString -> RnM HsDocString rnLHsDoc :: LHsDocString -> RnM LHsDocString rnMbLHsDoc :: Maybe LHsDocString -> RnM (Maybe LHsDocString) module FamInst checkFamInstConsistency :: [Module] -> [Module] -> TcM () tcExtendLocalFamInstEnv :: [FamInst] -> TcM a -> TcM a tcGetFamInstEnvs :: TcM (FamInstEnv, FamInstEnv) instance Ord ModulePair instance Eq ModulePair module TcTyDecls calcRecFlags :: ModDetails -> [TyThing] -> (Name -> RecFlag) calcClassCycles :: [LTyClDecl Name] -> [[LTyClDecl Name]] calcSynCycles :: [LTyClDecl Name] -> [SCC (LTyClDecl Name)] module Vectorise.Env -- | Indicates what scope something (a variable) is in. data Scope a b Global :: a -> Scope a b Local :: b -> Scope a b -- | The local environment. data LocalEnv LocalEnv :: VarEnv (Var, Var) -> [TyVar] -> VarEnv CoreExpr -> FastString -> LocalEnv local_vars :: LocalEnv -> VarEnv (Var, Var) local_tyvars :: LocalEnv -> [TyVar] local_tyvar_pa :: LocalEnv -> VarEnv CoreExpr local_bind_name :: LocalEnv -> FastString -- | Create an empty local environment. emptyLocalEnv :: LocalEnv -- | The global environment. These are things the exist at top-level. data GlobalEnv GlobalEnv :: VarEnv Var -> VarSet -> VarEnv (Var, Var) -> NameEnv TyCon -> NameEnv DataCon -> NameEnv Var -> NameEnv Var -> NameEnv TyCon -> (InstEnv, InstEnv) -> FamInstEnvs -> [(Var, CoreExpr)] -> GlobalEnv -- | Mapping from global variables to their vectorised versions. global_vars :: GlobalEnv -> VarEnv Var -- | Purely scalar variables. Code which mentions only these variables -- doesn't have to be lifted. global_scalars :: GlobalEnv -> VarSet -- | Exported variables which have a vectorised version. global_exported_vars :: GlobalEnv -> VarEnv (Var, Var) -- | Mapping from TyCons to their vectorised versions. TyCons which do not -- have to be vectorised are mapped to themselves. global_tycons :: GlobalEnv -> NameEnv TyCon -- | Mapping from DataCons to their vectorised versions. global_datacons :: GlobalEnv -> NameEnv DataCon -- | Mapping from TyCons to their PA dfuns. global_pa_funs :: GlobalEnv -> NameEnv Var -- | Mapping from TyCons to their PR dfuns. global_pr_funs :: GlobalEnv -> NameEnv Var -- | Mapping from unboxed TyCons to their boxed versions. global_boxed_tycons :: GlobalEnv -> NameEnv TyCon -- | External package inst-env & home-package inst-env for class -- instances. global_inst_env :: GlobalEnv -> (InstEnv, InstEnv) -- | External package inst-env & home-package inst-env for family -- instances. global_fam_inst_env :: GlobalEnv -> FamInstEnvs -- | Hoisted bindings. global_bindings :: GlobalEnv -> [(Var, CoreExpr)] -- | Create an initial global environment initGlobalEnv :: VectInfo -> (InstEnv, InstEnv) -> FamInstEnvs -> GlobalEnv -- | Extend the list of global variables in an environment. extendImportedVarsEnv :: [(Var, Var)] -> GlobalEnv -> GlobalEnv -- | Extend the set of scalar variables in an environment. extendScalars :: [Var] -> GlobalEnv -> GlobalEnv -- | Set the list of type family instances in an environment. setFamInstEnv :: FamInstEnv -> GlobalEnv -> GlobalEnv -- | Extend the list of type constructors in an environment. extendTyConsEnv :: [(Name, TyCon)] -> GlobalEnv -> GlobalEnv -- | Extend the list of data constructors in an environment. extendDataConsEnv :: [(Name, DataCon)] -> GlobalEnv -> GlobalEnv -- | Extend the list of PA functions in an environment. extendPAFunsEnv :: [(Name, Var)] -> GlobalEnv -> GlobalEnv -- | Set the list of PR functions in an environment. setPRFunsEnv :: [(Name, Var)] -> GlobalEnv -> GlobalEnv -- | Set the list of boxed type constructor in an environment. setBoxedTyConsEnv :: [(Name, TyCon)] -> GlobalEnv -> GlobalEnv -- | TODO: What is this for? updVectInfo :: GlobalEnv -> TypeEnv -> VectInfo -> VectInfo module MkId mkDictFunId :: Name -> [TyVar] -> ThetaType -> Class -> [Type] -> Id mkDictFunTy :: [TyVar] -> ThetaType -> Class -> [Type] -> (Int, Type) mkDefaultMethodId :: Id -> Name -> Id mkDictSelId :: Bool -> Name -> Class -> Id mkDataConIds :: Name -> Name -> DataCon -> DataConIds mkPrimOpId :: PrimOp -> Id mkFCallId :: Unique -> ForeignCall -> Type -> Id mkTickBoxOpId :: Unique -> Module -> TickBoxId -> Id mkBreakPointOpId :: Unique -> Module -> TickBoxId -> Id mkReboxingAlt :: [Unique] -> DataCon -> [Var] -> CoreExpr -> CoreAlt wrapNewTypeBody :: TyCon -> [Type] -> CoreExpr -> CoreExpr unwrapNewTypeBody :: TyCon -> [Type] -> CoreExpr -> CoreExpr wrapFamInstBody :: TyCon -> [Type] -> CoreExpr -> CoreExpr unwrapFamInstScrut :: TyCon -> [Type] -> CoreExpr -> CoreExpr mkUnpackCase :: Id -> CoreExpr -> [Id] -> DataCon -> CoreExpr -> CoreExpr mkProductBox :: [Id] -> Type -> CoreExpr wiredInIds :: [Id] ghcPrimIds :: [Id] unsafeCoerceName :: Name unsafeCoerceId :: Id realWorldPrimId :: Id voidArgId :: Id nullAddrId :: Id seqId :: Id lazyId :: Id lazyIdKey :: Unique module ByteCodeGen data UnlinkedBCO byteCodeGen :: DynFlags -> [CoreBind] -> [TyCon] -> ModBreaks -> IO CompiledByteCode coreExprToBCOs :: DynFlags -> CoreExpr -> IO UnlinkedBCO instance Monad BcM instance Outputable Discr instance Outputable TickInfo module IfaceEnv newGlobalBinder :: Module -> OccName -> SrcSpan -> TcRnIf a b Name newIPName :: IPName OccName -> TcRnIf m n (IPName Name) newImplicitBinder :: Name -> (OccName -> OccName) -> TcRnIf m n Name lookupIfaceTop :: OccName -> IfL Name lookupOrig :: Module -> OccName -> TcRnIf a b Name lookupOrigNameCache :: OrigNameCache -> Module -> OccName -> Maybe Name extendNameCache :: OrigNameCache -> Module -> OccName -> Name -> OrigNameCache newIfaceName :: OccName -> IfL Name newIfaceNames :: [OccName] -> IfL [Name] extendIfaceIdEnv :: [Id] -> IfL a -> IfL a extendIfaceTyVarEnv :: [TyVar] -> IfL a -> IfL a tcIfaceLclId :: FastString -> IfL Id tcIfaceTyVar :: FastString -> IfL TyVar lookupIfaceTyVar :: FastString -> IfL (Maybe TyVar) tcIfaceTick :: Module -> Int -> IfL Id ifaceExportNames :: [IfaceExport] -> TcRnIf gbl lcl [AvailInfo] allocateGlobalBinder :: NameCache -> Module -> OccName -> SrcSpan -> (NameCache, Name) initNameCache :: UniqSupply -> [Name] -> NameCache getNameCache :: TcRnIf a b NameCache -- | Return a function to atomically update the name cache. mkNameCacheUpdater :: TcRnIf a b (NameCacheUpdater c) -- | A function that atomically updates the name cache given a modifier -- function. The second result of the modifier function will be the -- result of the IO action. type NameCacheUpdater c = (NameCache -> (NameCache, c)) -> IO c module PrelInfo wiredInIds :: [Id] ghcPrimIds :: [Id] primOpRules :: PrimOp -> Name -> [CoreRule] builtinRules :: [CoreRule] ghcPrimExports :: [RdrAvailInfo] wiredInThings :: [TyThing] basicKnownKeyNames :: [Name] primOpId :: PrimOp -> Id maybeCharLikeCon :: DataCon -> Bool maybeIntLikeCon :: DataCon -> Bool isNumericClass :: Class -> Bool isStandardClass :: Class -> Bool module CgCon cgTopRhsCon :: Id -> DataCon -> [StgArg] -> FCode (Id, CgIdInfo) buildDynCon :: Id -> CostCentreStack -> DataCon -> [(CgRep, CmmExpr)] -> FCode CgIdInfo bindConArgs :: DataCon -> [Id] -> Code bindUnboxedTupleComponents :: [Id] -> FCode ([(Id, GlobalReg)], WordOff, WordOff, VirtualSpOffset) cgReturnDataCon :: DataCon -> [(CgRep, CmmExpr)] -> Code cgTyCon :: TyCon -> FCode [Cmm] module CgCase cgCase :: StgExpr -> StgLiveVars -> StgLiveVars -> Id -> AltType -> [StgAlt] -> Code saveVolatileVarsAndRegs :: StgLiveVars -> FCode (CmmStmts, EndOfBlockInfo, Maybe VirtualSpOffset) restoreCurrentCostCentre :: Maybe VirtualSpOffset -> Bool -> Code module CgLetNoEscape cgLetNoEscapeClosure :: Id -> CostCentreStack -> StgBinderInfo -> StgLiveVars -> EndOfBlockInfo -> Maybe VirtualSpOffset -> RecFlag -> [Id] -> StgExpr -> FCode (Id, CgIdInfo) module CgExpr cgExpr :: StgExpr -> Code module CodeGen codeGen :: DynFlags -> Module -> [TyCon] -> [Module] -> CollectedCCs -> [(StgBinding, [(Id, [Id])])] -> HpcInfo -> IO [Cmm] module StgCmmCon cgTopRhsCon :: Id -> DataCon -> [StgArg] -> FCode CgIdInfo buildDynCon :: Id -> CostCentreStack -> DataCon -> [StgArg] -> FCode (CgIdInfo, CmmAGraph) bindConArgs :: AltCon -> LocalReg -> [Id] -> FCode [LocalReg] module StgCmmExpr cgExpr :: StgExpr -> FCode () module StgCmmBind cgTopRhsClosure :: Id -> CostCentreStack -> StgBinderInfo -> UpdateFlag -> SRT -> [Id] -> StgExpr -> FCode CgIdInfo cgBind :: StgBinding -> FCode () emitBlackHoleCode :: Bool -> FCode () pushUpdateFrame :: [CmmExpr] -> FCode () -> FCode () module StgCmm codeGen :: DynFlags -> Module -> [TyCon] -> [Module] -> CollectedCCs -> [(StgBinding, [(Id, [Id])])] -> HpcInfo -> IO [CmmZ] module TcGenDeriv type DerivAuxBinds = [DerivAuxBind] isDupAux :: DerivAuxBind -> DerivAuxBind -> Bool gen_Bounded_binds :: SrcSpan -> TyCon -> (LHsBinds RdrName, DerivAuxBinds) gen_Enum_binds :: SrcSpan -> TyCon -> (LHsBinds RdrName, DerivAuxBinds) gen_Eq_binds :: SrcSpan -> TyCon -> (LHsBinds RdrName, DerivAuxBinds) gen_Ix_binds :: SrcSpan -> TyCon -> (LHsBinds RdrName, DerivAuxBinds) gen_Ord_binds :: SrcSpan -> TyCon -> (LHsBinds RdrName, DerivAuxBinds) gen_Read_binds :: FixityEnv -> SrcSpan -> TyCon -> (LHsBinds RdrName, DerivAuxBinds) gen_Show_binds :: FixityEnv -> SrcSpan -> TyCon -> (LHsBinds RdrName, DerivAuxBinds) gen_Data_binds :: SrcSpan -> TyCon -> (LHsBinds RdrName, DerivAuxBinds) gen_Typeable_binds :: SrcSpan -> TyCon -> LHsBinds RdrName gen_Functor_binds :: SrcSpan -> TyCon -> (LHsBinds RdrName, DerivAuxBinds) data FFoldType a FT :: a -> a -> a -> (a -> a -> a) -> (Boxity -> [a] -> a) -> (Type -> a -> a) -> a -> (TcTyVar -> a -> a) -> FFoldType a ft_triv :: FFoldType a -> a ft_var :: FFoldType a -> a ft_co_var :: FFoldType a -> a ft_fun :: FFoldType a -> a -> a -> a ft_tup :: FFoldType a -> Boxity -> [a] -> a ft_ty_app :: FFoldType a -> Type -> a -> a ft_bad_app :: FFoldType a -> a ft_forall :: FFoldType a -> TcTyVar -> a -> a functorLikeTraverse :: TyVar -> FFoldType a -> Type -> a deepSubtypesContaining :: TyVar -> Type -> [TcType] foldDataConArgs :: FFoldType a -> DataCon -> [a] gen_Foldable_binds :: SrcSpan -> TyCon -> (LHsBinds RdrName, DerivAuxBinds) gen_Traversable_binds :: SrcSpan -> TyCon -> (LHsBinds RdrName, DerivAuxBinds) genAuxBind :: SrcSpan -> DerivAuxBind -> (LHsBind RdrName, LSig RdrName) module BuildTyCl buildSynTyCon :: Name -> [TyVar] -> SynTyConRhs -> Kind -> TyConParent -> Maybe (TyCon, [Type]) -> TcRnIf m n TyCon buildAlgTyCon :: Name -> [TyVar] -> ThetaType -> AlgTyConRhs -> RecFlag -> Bool -> Bool -> TyConParent -> Maybe (TyCon, [Type]) -> TcRnIf m n TyCon buildDataCon :: Name -> Bool -> [HsBang] -> [Name] -> [TyVar] -> [TyVar] -> [(TyVar, Type)] -> ThetaType -> [Type] -> Type -> TyCon -> TcRnIf m n DataCon type TcMethInfo = (Name, DefMethSpec, Type) buildClass :: Bool -> Name -> [TyVar] -> ThetaType -> [FunDep TyVar] -> [TyThing] -> [TcMethInfo] -> RecFlag -> TcRnIf m n Class mkAbstractTyConRhs :: AlgTyConRhs -- | Monadic because it makes a Name for the coercion TyCon We pass the -- Name of the parent TyCon, as well as the TyCon itself, because the -- latter is part of a knot, whereas the former is not. mkNewTyConRhs :: Name -> TyCon -> DataCon -> TcRnIf m n AlgTyConRhs mkDataTyConRhs :: [DataCon] -> AlgTyConRhs module WwLib mkWwBodies :: Type -> [Demand] -> DmdResult -> [Bool] -> UniqSM ([Demand], Id -> CoreExpr, CoreExpr -> CoreExpr) mkWWstr :: [Var] -> UniqSM ([Var], CoreExpr -> CoreExpr, CoreExpr -> CoreExpr) mkWorkerArgs :: [Var] -> Type -> ([Var], [Var]) module WorkWrap wwTopBinds :: UniqSupply -> [CoreBind] -> [CoreBind] mkWrapper :: Type -> StrictSig -> UniqSM (Id -> CoreExpr) module CoreToStg coreToStg :: PackageId -> [CoreBind] -> IO [StgBinding] coreExprToStg :: CoreExpr -> StgExpr instance MonadFix LneM instance Monad LneM module MkExternalCore emitExternalCore :: DynFlags -> CgGuts -> IO () instance Monad CoreM module Coverage addCoverageTicksToBinds :: DynFlags -> Module -> ModLocation -> [TyCon] -> LHsBinds Id -> IO (LHsBinds Id, HpcInfo, ModBreaks) instance Monad TM module BinIface writeBinIface :: DynFlags -> FilePath -> ModIface -> IO () readBinIface :: CheckHiWay -> TraceBinIFaceReading -> FilePath -> TcRnIf a b ModIface data CheckHiWay CheckHiWay :: CheckHiWay IgnoreHiWay :: CheckHiWay data TraceBinIFaceReading TraceBinIFaceReading :: TraceBinIFaceReading QuietBinIFaceReading :: TraceBinIFaceReading instance Eq CheckHiWay instance Eq TraceBinIFaceReading instance Binary IfaceVectInfo instance Binary name => Binary (AnnTarget name) instance Binary IfaceAnnotation instance Binary IfaceRule instance Binary IfaceClassOp instance Binary IfaceConDecl instance Binary IfaceConDecls instance Binary OverlapFlag instance Binary IfaceFamInst instance Binary IfaceInst instance Binary IfaceDecl instance Binary IfaceNote instance Binary (DFunArg IfaceExpr) instance Binary IfaceUnfolding instance Binary IfaceInfoItem instance Binary IfaceIdInfo instance Binary IfaceIdDetails instance Binary IfaceBinding instance Binary IfaceConAlt instance Binary IfaceExpr instance Binary IfacePredType instance Binary IfaceTyCon instance Binary IfaceType instance Binary IfaceLetBndr instance Binary IfaceBndr instance Binary CostCentre instance Binary IsDupdCC instance Binary IsCafCC instance Binary StrictSig instance Binary DmdResult instance Binary Demands instance Binary Demand instance Binary DmdType instance Binary name => Binary (IPName name) instance Binary Fixity instance Binary FixityDirection instance Binary DefMethSpec instance Binary RecFlag instance Binary TupCon instance Binary Boxity instance Binary HsBang instance Binary InlineSpec instance Binary InlinePragma instance Binary RuleMatchInfo instance Binary Activation instance Binary WarningTxt instance Binary Warnings instance Binary Usage instance Binary name => Binary (GenAvailInfo name) instance Binary Dependencies instance Binary ModIface module LoadIface loadInterface :: SDoc -> Module -> WhereFrom -> IfM lcl (MaybeErr Message ModIface) -- | Loads the interface for a given Name. loadInterfaceForName :: SDoc -> Name -> TcRn ModIface -- | An IfM function to load the home interface for a wired-in -- thing, so that we're sure that we see its instance declarations and -- rules See Note [Loading instances for wired-in things] in TcIface loadWiredInHomeIface :: Name -> IfM lcl () -- | Load the interface corresponding to an import directive in -- source code. On a failure, fail in the monad with an error message. loadSrcInterface :: SDoc -> ModuleName -> IsBootInterface -> Maybe FastString -> RnM ModIface -- | Loads a system interface and throws an exception if it fails loadSysInterface :: SDoc -> Module -> IfM lcl ModIface -- | Loads a user interface and throws an exception if it fails. The first -- parameter indicates whether we should import the boot variant of the -- module loadUserInterface :: Bool -> SDoc -> Module -> IfM lcl ModIface -- | Load interfaces for a collection of orphan modules. loadOrphanModules :: [Module] -> Bool -> TcM () findAndReadIface :: SDoc -> Module -> IsBootInterface -> TcRnIf gbl lcl (MaybeErr Message (ModIface, FilePath)) readIface :: Module -> FilePath -> IsBootInterface -> TcRnIf gbl lcl (MaybeErr Message ModIface) loadDecls :: Bool -> [(Fingerprint, IfaceDecl)] -> IfL [(Name, TyThing)] initExternalPackageState :: ExternalPackageState ifaceStats :: ExternalPackageState -> SDoc pprModIface :: ModIface -> SDoc -- | Read binary interface, and print it out showIface :: HscEnv -> FilePath -> IO () instance Outputable Warnings module TcIface tcImportDecl :: Name -> TcM TyThing checkWiredInTyCon :: TyCon -> TcM () tcHiBootIface :: HscSource -> Module -> TcRn ModDetails typecheckIface :: ModIface -> TcRnIf gbl lcl ModDetails tcIfaceDecl :: Bool -> IfaceDecl -> IfL TyThing tcIfaceInst :: IfaceInst -> IfL Instance tcIfaceFamInst :: IfaceFamInst -> IfL FamInst tcIfaceRules :: Bool -> [IfaceRule] -> IfL [CoreRule] tcIfaceVectInfo :: Module -> TypeEnv -> IfaceVectInfo -> IfL VectInfo tcIfaceAnnotations :: [IfaceAnnotation] -> IfL [Annotation] tcIfaceGlobal :: Name -> IfL TyThing tcExtCoreBindings :: [IfaceBinding] -> IfL [CoreBind] module DsMonad type DsM result = TcRnIf DsGblEnv DsLclEnv result -- | mapM f is equivalent to sequence . -- map f. mapM :: Monad m => (a -> m b) -> [a] -> m [b] -- | The mapAndUnzipM function maps its first argument over a list, -- returning the result as a pair of lists. This function is mainly used -- with complicated data structures or a state-transforming monad. mapAndUnzipM :: Monad m => (a -> m (b, c)) -> [a] -> m ([b], [c]) initDs :: HscEnv -> Module -> GlobalRdrEnv -> TypeEnv -> DsM a -> IO (Messages, Maybe a) initDsTc :: DsM a -> TcM a fixDs :: (a -> DsM a) -> DsM a -- | Monadic version of foldl foldlM :: Monad m => (a -> b -> m a) -> a -> [b] -> m a -- | Monadic version of foldr foldrM :: Monad m => (b -> a -> m a) -> a -> [b] -> m a -- | Do it flag is true ifDOptM :: DynFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () unsetOptM :: DynFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a -- | A functor with application. -- -- Instances should satisfy the following laws: -- -- -- -- The Functor instance should satisfy -- --
--   fmap f x = pure f <*> x
--   
-- -- If f is also a Monad, define pure = -- return and (<*>) = ap. -- -- Minimal complete definition: pure and <*>. class Functor f => Applicative f :: (* -> *) pure :: Applicative f => a -> f a (<*>) :: Applicative f => f (a -> b) -> f a -> f b (*>) :: Applicative f => f a -> f b -> f b (<*) :: Applicative f => f a -> f b -> f a -- | An infix synonym for fmap. (<$>) :: Functor f => (a -> b) -> f a -> f b newLocalName :: Name -> TcRnIf gbl lcl Name duplicateLocalDs :: Id -> DsM Id newSysLocalDs :: Type -> DsM Id newSysLocalsDs :: [Type] -> DsM [Id] newUniqueId :: Id -> Type -> DsM Id newFailLocalDs :: Type -> DsM Id newPredVarDs :: PredType -> DsM Var getSrcSpanDs :: DsM SrcSpan putSrcSpanDs :: SrcSpan -> DsM a -> DsM a getModuleDs :: DsM Module newUnique :: TcRnIf gbl lcl Unique -- | A value of type UniqSupply is unique, and it can supply -- one distinct Unique. Also, from the supply, one can also -- manufacture an arbitrary number of further UniqueSupply -- values, which will be distinct from the first and from all others. data UniqSupply newUniqueSupply :: TcRnIf gbl lcl UniqSupply getDOptsDs :: DsM DynFlags getGhcModeDs :: DsM GhcMode doptDs :: DynFlag -> TcRnIf gbl lcl Bool dsLookupGlobal :: Name -> DsM TyThing dsLookupGlobalId :: Name -> DsM Id dsLookupTyCon :: Name -> DsM TyCon dsLookupDataCon :: Name -> DsM DataCon dsLookupClass :: Name -> DsM Class type DsMetaEnv = NameEnv DsMetaVal data DsMetaVal Bound :: Id -> DsMetaVal Splice :: (HsExpr Id) -> DsMetaVal dsLookupMetaEnv :: Name -> DsM (Maybe DsMetaVal) dsExtendMetaEnv :: DsMetaEnv -> DsM a -> DsM a dsLoadModule :: SDoc -> Module -> DsM () type DsWarning = (SrcSpan, SDoc) warnDs :: SDoc -> DsM () failWithDs :: SDoc -> DsM a data DsMatchContext DsMatchContext :: (HsMatchContext Name) -> SrcSpan -> DsMatchContext data EquationInfo EqnInfo :: [Pat Id] -> MatchResult -> EquationInfo eqn_pats :: EquationInfo -> [Pat Id] eqn_rhs :: EquationInfo -> MatchResult data MatchResult MatchResult :: CanItFail -> (CoreExpr -> DsM CoreExpr) -> MatchResult type DsWrapper = CoreExpr -> CoreExpr idDsWrapper :: DsWrapper data CanItFail CanFail :: CanItFail CantFail :: CanItFail orFail :: CanItFail -> CanItFail -> CanItFail instance MonadThings (IOEnv (Env DsGblEnv DsLclEnv)) instance Outputable EquationInfo -- | Utility functions for constructing Core syntax, principally for -- desugaring module DsUtils data EquationInfo EqnInfo :: [Pat Id] -> MatchResult -> EquationInfo eqn_pats :: EquationInfo -> [Pat Id] eqn_rhs :: EquationInfo -> MatchResult firstPat :: EquationInfo -> Pat Id shiftEqns :: [EquationInfo] -> [EquationInfo] data MatchResult MatchResult :: CanItFail -> (CoreExpr -> DsM CoreExpr) -> MatchResult data CanItFail CanFail :: CanItFail CantFail :: CanItFail cantFailMatchResult :: CoreExpr -> MatchResult alwaysFailMatchResult :: MatchResult extractMatchResult :: MatchResult -> CoreExpr -> DsM CoreExpr combineMatchResults :: MatchResult -> MatchResult -> MatchResult adjustMatchResult :: DsWrapper -> MatchResult -> MatchResult adjustMatchResultDs :: (CoreExpr -> DsM CoreExpr) -> MatchResult -> MatchResult mkCoLetMatchResult :: CoreBind -> MatchResult -> MatchResult mkViewMatchResult :: Id -> CoreExpr -> Id -> MatchResult -> MatchResult mkGuardedMatchResult :: CoreExpr -> MatchResult -> MatchResult matchCanFail :: MatchResult -> Bool mkEvalMatchResult :: Id -> Type -> MatchResult -> MatchResult mkCoPrimCaseMatchResult :: Id -> Type -> [(Literal, MatchResult)] -> MatchResult mkCoAlgCaseMatchResult :: Id -> Type -> [(DataCon, [CoreBndr], MatchResult)] -> MatchResult wrapBind :: Var -> Var -> CoreExpr -> CoreExpr wrapBinds :: [(Var, Var)] -> CoreExpr -> CoreExpr mkErrorAppDs :: Id -> Type -> SDoc -> DsM CoreExpr mkCoreAppDs :: CoreExpr -> CoreExpr -> CoreExpr mkCoreAppsDs :: CoreExpr -> [CoreExpr] -> CoreExpr seqVar :: Var -> CoreExpr -> CoreExpr mkLHsVarPatTup :: [Id] -> LPat Id mkLHsPatTup :: [LPat Id] -> LPat Id mkVanillaTuplePat :: [OutPat Id] -> Boxity -> Pat Id mkBigLHsVarTup :: [Id] -> LHsExpr Id mkBigLHsTup :: [LHsExpr Id] -> LHsExpr Id mkBigLHsVarPatTup :: [Id] -> LPat Id mkBigLHsPatTup :: [LPat Id] -> LPat Id mkSelectorBinds :: LPat Id -> CoreExpr -> DsM [(Id, CoreExpr)] dsSyntaxTable :: SyntaxTable Id -> DsM ([CoreBind], [(Name, Id)]) lookupEvidence :: [(Name, Id)] -> Name -> Id selectSimpleMatchVarL :: LPat Id -> DsM Id selectMatchVars :: [Pat Id] -> DsM [Id] selectMatchVar :: Pat Id -> DsM Id mkTickBox :: Int -> [Id] -> CoreExpr -> DsM CoreExpr mkOptTickBox :: Maybe (Int, [Id]) -> CoreExpr -> DsM CoreExpr mkBinaryTickBox :: Int -> Int -> CoreExpr -> DsM CoreExpr module MatchLit dsLit :: HsLit -> DsM CoreExpr dsOverLit :: HsOverLit Id -> DsM CoreExpr hsLitKey :: HsLit -> Literal hsOverLitKey :: OutputableBndr a => HsOverLit a -> Bool -> Literal tidyLitPat :: HsLit -> Pat Id tidyNPat :: HsOverLit Id -> Maybe (SyntaxExpr Id) -> SyntaxExpr Id -> Pat Id matchLiterals :: [Id] -> Type -> [[EquationInfo]] -> DsM MatchResult matchNPlusKPats :: [Id] -> Type -> [EquationInfo] -> DsM MatchResult matchNPats :: [Id] -> Type -> [EquationInfo] -> DsM MatchResult module DsMeta dsBracket :: HsBracket Name -> [PendingSplice] -> DsM CoreExpr templateHaskellNames :: [Name] qTyConName :: Name nameTyConName :: Name liftName :: Name liftStringName :: Name expQTyConName :: Name patQTyConName :: Name decQTyConName :: Name decsQTyConName :: Name typeQTyConName :: Name decTyConName :: Name typeTyConName :: Name mkNameG_dName :: Name mkNameG_vName :: Name mkNameG_tcName :: Name quoteExpName :: Name quotePatName :: Name quoteDecName :: Name quoteTypeName :: Name module Check check :: [EquationInfo] -> ([ExhaustivePat], [EquationInfo]) type ExhaustivePat = ([WarningPat], [(Name, [HsLit])]) module DsGRHSs dsGuarded :: GRHSs Id -> Type -> DsM CoreExpr dsGRHSs :: HsMatchContext Name -> [Pat Id] -> GRHSs Id -> Type -> DsM MatchResult module DsBinds dsTopLHsBinds :: AutoScc -> LHsBinds Id -> DsM (OrdList (Id, CoreExpr)) dsLHsBinds :: LHsBinds Id -> DsM [(Id, CoreExpr)] decomposeRuleLhs :: [Var] -> CoreExpr -> Either SDoc ([Var], Id, [CoreExpr]) dsSpec :: Maybe CoreExpr -> Located TcSpecPrag -> DsM (Maybe (OrdList (Id, CoreExpr), CoreRule)) dsHsWrapper :: HsWrapper -> DsM (CoreExpr -> CoreExpr) dsTcEvBinds :: TcEvBinds -> DsM [DsEvBind] dsEvBinds :: Bag EvBind -> DsM [DsEvBind] wrapDsEvBinds :: [DsEvBind] -> CoreExpr -> CoreExpr data DsEvBind LetEvBind :: CoreBind -> DsEvBind CaseEvBind :: DictId -> AltCon -> [CoreBndr] -> DsEvBind data AutoScc NoSccs :: AutoScc AddSccs :: Module -> (Id -> Bool) -> AutoScc module DsCCall dsCCall :: CLabelString -> [CoreExpr] -> Safety -> Type -> DsM CoreExpr mkFCall :: Unique -> ForeignCall -> [CoreExpr] -> Type -> CoreExpr unboxArg :: CoreExpr -> DsM (CoreExpr, CoreExpr -> CoreExpr) boxResult :: Type -> DsM (Type, CoreExpr -> CoreExpr) resultWrapper :: Type -> DsM (Maybe Type, CoreExpr -> CoreExpr) module DsForeign dsForeigns :: [LForeignDecl Id] -> DsM (ForeignStubs, OrdList Binding) module MatchCon matchConFamily :: [Id] -> Type -> [[EquationInfo]] -> DsM MatchResult module Match match :: [Id] -> Type -> [EquationInfo] -> DsM MatchResult matchEquations :: HsMatchContext Name -> [Id] -> [EquationInfo] -> Type -> DsM CoreExpr matchWrapper :: HsMatchContext Name -> MatchGroup Id -> DsM ([Id], CoreExpr) matchSimply :: CoreExpr -> HsMatchContext Name -> LPat Id -> CoreExpr -> CoreExpr -> DsM CoreExpr matchSinglePat :: CoreExpr -> HsMatchContext Name -> LPat Id -> Type -> MatchResult -> DsM MatchResult module DsArrows dsProcExpr :: LPat Id -> LHsCmdTop Id -> DsM CoreExpr module DsListComp dsListComp :: [LStmt Id] -> LHsExpr Id -> Type -> DsM CoreExpr dsPArrComp :: [Stmt Id] -> LHsExpr Id -> Type -> DsM CoreExpr module DsExpr dsExpr :: HsExpr Id -> DsM CoreExpr dsLExpr :: LHsExpr Id -> DsM CoreExpr dsLocalBinds :: HsLocalBinds Id -> CoreExpr -> DsM CoreExpr dsValBinds :: HsValBinds Id -> CoreExpr -> DsM CoreExpr dsLit :: HsLit -> DsM CoreExpr module Vectorise.Builtins.Initialise -- | Create the initial map of builtin types and functions. initBuiltins :: PackageId -> DsM Builtins -- | Get the mapping of names in the Prelude to names in the DPH library. initBuiltinVars :: Builtins -> DsM [(Var, Var)] -- | Get a list of names to TyCons in the mock prelude. initBuiltinTyCons :: Builtins -> DsM [(Name, TyCon)] -- | Get a list of names to DataCons in the mock prelude. initBuiltinDataCons :: Builtins -> [(Name, DataCon)] -- | Get the names of all buildin instance functions for the PA class. initBuiltinPAs :: Builtins -> (InstEnv, InstEnv) -> DsM [(Name, Var)] -- | Get the names of all builtin instance functions for the PR class. initBuiltinPRs :: Builtins -> (InstEnv, InstEnv) -> DsM [(Name, Var)] -- | Get a list of boxed TyCons in the mock prelude. This is Int -- only. initBuiltinBoxedTyCons :: Builtins -> DsM [(Name, TyCon)] -- | Get a list of all scalar functions in the mock prelude. initBuiltinScalars :: Builtins -> DsM [Var] -- | Builtin types and functions used by the vectoriser. The source program -- uses functions from GHC.PArr, which the vectoriser rewrites to use -- equivalent vectorised versions in the DPH backend packages. -- -- The Builtins structure holds the name of all the things in the -- DPH packages we will need. We can get specific things using the -- selectors, which print a civilized panic message if the specified -- thing cannot be found. module Vectorise.Builtins -- | Holds the names of the builtin types and functions used by the -- vectoriser. data Builtins Builtins :: Modules -> TyCon -> DataCon -> TyCon -> TyCon -> DataCon -> TyCon -> TyCon -> DataCon -> Var -> Var -> Var -> Array Int Var -> Class -> TyCon -> Var -> Var -> Var -> Var -> Array Int Var -> TyCon -> TyCon -> Array Int TyCon -> Var -> Var -> Var -> Var -> Array Int Type -> Array Int CoreExpr -> Array Int CoreExpr -> Array Int CoreExpr -> Array (Int, Int) CoreExpr -> Array Int Var -> Var -> Builtins dphModules :: Builtins -> Modules -- | PArray parrayTyCon :: Builtins -> TyCon -- | PArray parrayDataCon :: Builtins -> DataCon -- | PData pdataTyCon :: Builtins -> TyCon -- | PA paTyCon :: Builtins -> TyCon -- | PA paDataCon :: Builtins -> DataCon -- | PRepr preprTyCon :: Builtins -> TyCon -- | PR prTyCon :: Builtins -> TyCon -- | PR prDataCon :: Builtins -> DataCon -- | replicatePD replicatePDVar :: Builtins -> Var -- | emptyPD emptyPDVar :: Builtins -> Var -- | packByTagPD packByTagPDVar :: Builtins -> Var -- | combinePD combinePDVars :: Builtins -> Array Int Var -- | Scalar scalarClass :: Builtins -> Class -- | :-> closureTyCon :: Builtins -> TyCon -- | closure closureVar :: Builtins -> Var -- | $: applyVar :: Builtins -> Var -- | liftedClosure liftedClosureVar :: Builtins -> Var -- | liftedApply liftedApplyVar :: Builtins -> Var -- | closure1 .. closure2 closureCtrFuns :: Builtins -> Array Int Var -- | Void voidTyCon :: Builtins -> TyCon -- | Wrap wrapTyCon :: Builtins -> TyCon -- | Sum2 .. Sum3 sumTyCons :: Builtins -> Array Int TyCon -- | void voidVar :: Builtins -> Var -- | pvoid pvoidVar :: Builtins -> Var -- | fromVoid fromVoidVar :: Builtins -> Var -- | punit punitVar :: Builtins -> Var -- | Sel2 selTys :: Builtins -> Array Int Type -- | replicate2 selReplicates :: Builtins -> Array Int CoreExpr -- | pick2 selPicks :: Builtins -> Array Int CoreExpr -- | tagsSel2 selTagss :: Builtins -> Array Int CoreExpr -- | elementsSel2_0 .. elementsSel_2_1 selEls :: Builtins -> Array (Int, Int) CoreExpr -- | map, zipWith, zipWith3 scalarZips :: Builtins -> Array Int Var -- | lc liftingContext :: Builtins -> Var -- | Get an element from one of the arrays of contained by a -- Builtins. If the indexed thing is not in the array then panic. indexBuiltin :: (Ix i, Outputable i) => String -> (Builtins -> Array i a) -> i -> Builtins -> a selTy :: Int -> Builtins -> Type selReplicate :: Int -> Builtins -> CoreExpr selPick :: Int -> Builtins -> CoreExpr selTags :: Int -> Builtins -> CoreExpr selElements :: Int -> Int -> Builtins -> CoreExpr sumTyCon :: Int -> Builtins -> TyCon prodTyCon :: Int -> Builtins -> TyCon prodDataCon :: Int -> Builtins -> DataCon combinePDVar :: Int -> Builtins -> Var scalarZip :: Int -> Builtins -> Var closureCtrFun :: Int -> Builtins -> Var -- | Create the initial map of builtin types and functions. initBuiltins :: PackageId -> DsM Builtins -- | Get the mapping of names in the Prelude to names in the DPH library. initBuiltinVars :: Builtins -> DsM [(Var, Var)] -- | Get a list of names to TyCons in the mock prelude. initBuiltinTyCons :: Builtins -> DsM [(Name, TyCon)] -- | Get a list of names to DataCons in the mock prelude. initBuiltinDataCons :: Builtins -> [(Name, DataCon)] -- | Get the names of all buildin instance functions for the PA class. initBuiltinPAs :: Builtins -> (InstEnv, InstEnv) -> DsM [(Name, Var)] -- | Get the names of all builtin instance functions for the PR class. initBuiltinPRs :: Builtins -> (InstEnv, InstEnv) -> DsM [(Name, Var)] -- | Get a list of boxed TyCons in the mock prelude. This is Int -- only. initBuiltinBoxedTyCons :: Builtins -> DsM [(Name, TyCon)] -- | Get a list of all scalar functions in the mock prelude. initBuiltinScalars :: Builtins -> DsM [Var] -- | Lookup a method function given its name and instance type. primMethod :: TyCon -> String -> Builtins -> DsM (Maybe Var) -- | Lookup the representation type we use for PArrays that contain a given -- element type. primPArray :: TyCon -> Builtins -> DsM (Maybe TyCon) -- | The Vectorisation monad. module Vectorise.Monad.Base -- | Vectorisation can either succeed with new envionment and a value, or -- return with failure. data VResult a Yes :: GlobalEnv -> LocalEnv -> a -> VResult a No :: VResult a newtype VM a VM :: (Builtins -> GlobalEnv -> LocalEnv -> DsM (VResult a)) -> VM a runVM :: VM a -> Builtins -> GlobalEnv -> LocalEnv -> DsM (VResult a) -- | Lift a desugaring computation into the vectorisation monad. liftDs :: DsM a -> VM a -- | Throw a pgmError saying we can't vectorise something. cantVectorise :: String -> SDoc -> a -- | Like fromJust, but pgmError on Nothing. maybeCantVectorise :: String -> SDoc -> Maybe a -> a -- | Like maybeCantVectorise but in a Monad. maybeCantVectoriseM :: Monad m => String -> SDoc -> m (Maybe a) -> m a -- | Return some result saying we've failed. noV :: VM a -- | Like traceNoV but also emit some trace message to stderr. traceNoV :: String -> SDoc -> VM a -- | If True then carry on, otherwise fail. ensureV :: Bool -> VM () -- | Like ensureV but if we fail then emit some trace message to -- stderr. traceEnsureV :: String -> SDoc -> Bool -> VM () -- | If True then return the first argument, otherwise fail. onlyIfV :: Bool -> VM a -> VM a -- | Try some vectorisation computaton. If it succeeds then return -- Just the result, otherwise return Nothing. tryV :: VM a -> VM (Maybe a) -- | If Just then return the value, otherwise fail. maybeV :: VM (Maybe a) -> VM a -- | Like maybeV but emit a message to stderr if we fail. traceMaybeV :: String -> SDoc -> VM (Maybe a) -> VM a -- | Try the first computation, if it succeeds then take the returned -- value, if it fails then run the second computation instead. orElseV :: VM a -> VM a -> VM a -- | Fixpoint in the vectorisation monad. fixV :: (a -> VM a) -> VM a instance Monad VM module Vectorise.Monad.Local -- | Project something from the local environment. readLEnv :: (LocalEnv -> a) -> VM a -- | Set the local environment. setLEnv :: LocalEnv -> VM () -- | Update the enviroment using the provided function. updLEnv :: (LocalEnv -> LocalEnv) -> VM () -- | Perform a computation in its own local environment. This does not -- alter the environment of the current state. localV :: VM a -> VM a -- | Perform a computation in an empty local environment. closedV :: VM a -> VM a -- | Get the name of the local binding currently being vectorised. getBindName :: VM FastString -- | Run a vectorisation computation in a local environment, with this id -- set as the current binding. inBind :: Id -> VM a -> VM a -- | Lookup a PA tyvars from the local environment. lookupTyVarPA :: Var -> VM (Maybe CoreExpr) -- | Add a tyvar to the local environment. defLocalTyVar :: TyVar -> VM () -- | Add mapping between a tyvar and pa dictionary to the local -- environment. defLocalTyVarWithPA :: TyVar -> CoreExpr -> VM () -- | Get the set of tyvars from the local environment. localTyVars :: VM [TyVar] module Vectorise.Monad.Global -- | Project something from the global environment. readGEnv :: (GlobalEnv -> a) -> VM a -- | Set the value of the global environment. setGEnv :: GlobalEnv -> VM () -- | Update the global environment using the provided function. updGEnv :: (GlobalEnv -> GlobalEnv) -> VM () -- | Add a mapping between a global var and its vectorised version to the -- state. defGlobalVar :: Var -> Var -> VM () -- | Get the set of global scalar variables. globalScalars :: VM VarSet -- | Lookup the vectorised version of a TyCon from the global -- environment. lookupTyCon :: TyCon -> VM (Maybe TyCon) -- | Lookup the vectorised version of a boxed TyCon from the global -- environment. lookupBoxedTyCon :: TyCon -> VM (Maybe TyCon) -- | Add a mapping between plain and vectorised TyCons to the global -- environment. defTyCon :: TyCon -> TyCon -> VM () -- | Lookup the vectorised version of a DataCon from the global -- environment. lookupDataCon :: DataCon -> VM (Maybe DataCon) -- | Add the mapping between plain and vectorised DataCons to the -- global environment. defDataCon :: DataCon -> DataCon -> VM () -- | Lookup a PA TyCon from the global environment. lookupTyConPA :: TyCon -> VM (Maybe Var) -- | Add a mapping between a PA TyCon and is vectorised version to the -- global environment. defTyConPA :: TyCon -> Var -> VM () -- | Add several mapping between PA TyCons and their vectorised versions to -- the global environment. defTyConPAs :: [(TyCon, Var)] -> VM () lookupTyConPR :: TyCon -> VM (Maybe Var) module Vectorise.Monad.InstEnv lookupInst :: Class -> [Type] -> VM (DFunId, [Type]) lookupFamInst :: TyCon -> [Type] -> VM (TyCon, [Type]) -- | Computations in the vectorisation monad concerned with naming and -- fresh variable generation. module Vectorise.Monad.Naming -- | Clone a name, using the provide function to transform its -- OccName. cloneName :: (OccName -> OccName) -> Name -> VM Name -- | Clone an Id, using the provided function to transform its -- OccName. cloneId :: (OccName -> OccName) -> Id -> Type -> VM Id -- | Make a fresh instance of this var, with a new unique. cloneVar :: Var -> VM Var -- | Make a fresh exported variable with the given type. newExportedVar :: OccName -> Type -> VM Var -- | Make a fresh local variable with the given type. The variable's name -- is formed using the given string as the prefix. newLocalVar :: FastString -> Type -> VM Var -- | Make several fresh local varaiables with the given types. The -- variable's names are formed using the given string as the prefix. newLocalVars :: FastString -> [Type] -> VM [Var] -- | Make a new local dummy variable. newDummyVar :: Type -> VM Var -- | Make a fresh type variable with the given kind. The variable's name is -- formed using the given string as the prefix. newTyVar :: FastString -> Kind -> VM Var module Vectorise.Monad -- | Run a vectorisation computation. initV :: PackageId -> HscEnv -> ModGuts -> VectInfo -> VM a -> IO (Maybe (VectInfo, a)) -- | Lift a desugaring computation using the Builtins into the -- vectorisation monad. liftBuiltinDs :: (Builtins -> DsM a) -> VM a -- | Project something from the set of builtins. builtin :: (Builtins -> a) -> VM a -- | Lift a function using the Builtins into the vectorisation -- monad. builtins :: (a -> Builtins -> b) -> VM (a -> b) -- | Lookup the vectorised and/or lifted versions of this variable. If it's -- in the global environment we get the vectorised version. If it's in -- the local environment we get both the vectorised and lifted version. lookupVar :: Var -> VM (Scope Var (Var, Var)) maybeCantVectoriseVarM :: Monad m => Var -> m (Maybe Var) -> m Var dumpVar :: Var -> a lookupPrimPArray :: TyCon -> VM (Maybe TyCon) lookupPrimMethod :: TyCon -> String -> VM (Maybe Var) module Vectorise.Utils.Base voidType :: VM Type newLocalVVar :: FastString -> Type -> VM VVar mkDataConTagLit :: DataCon -> Literal mkDataConTag :: DataCon -> CoreExpr dataConTagZ :: DataCon -> Int mkBuiltinTyConApp :: (Builtins -> TyCon) -> [Type] -> VM Type mkBuiltinTyConApps :: (Builtins -> TyCon) -> [Type] -> Type -> VM Type mkWrapType :: Type -> VM Type mkClosureTypes :: [Type] -> Type -> VM Type mkPReprType :: Type -> VM Type mkPArrayType :: Type -> VM Type splitPrimTyCon :: Type -> Maybe TyCon mkPArray :: Type -> CoreExpr -> CoreExpr -> VM CoreExpr mkPDataType :: Type -> VM Type mkBuiltinCo :: (Builtins -> TyCon) -> VM Coercion mkVScrut :: VExpr -> VM (CoreExpr, CoreExpr, TyCon, [Type]) pdataReprTyCon :: Type -> VM (TyCon, [Type]) pdataReprDataCon :: Type -> VM (DataCon, [Type]) module Vectorise.Utils.PADict mkPADictType :: Type -> VM Type paDictArgType :: TyVar -> VM (Maybe Type) -- | Get the PA dictionary for some type, or Nothing if there isn't -- one. paDictOfType :: Type -> VM (Maybe CoreExpr) paDFunType :: TyCon -> VM Type paDFunApply :: CoreExpr -> [Type] -> VM CoreExpr paMethod :: (Builtins -> Var) -> String -> Type -> VM CoreExpr module Vectorise.Utils.Poly polyAbstract :: [TyVar] -> ([Var] -> VM a) -> VM a polyApply :: CoreExpr -> [Type] -> VM CoreExpr polyVApply :: VExpr -> [Type] -> VM VExpr polyArity :: [TyVar] -> VM Int module Vectorise.Utils.Hoisting -- | Records whether we should inline a particular binding. data Inline Inline :: Arity -> Inline DontInline :: Inline -- | Add to the arity contained within an Inline, if any. addInlineArity :: Inline -> Int -> Inline -- | Says to always inline a binding. inlineMe :: Inline hoistBinding :: Var -> CoreExpr -> VM () hoistExpr :: FastString -> CoreExpr -> Inline -> VM Var hoistVExpr :: VExpr -> Inline -> VM VVar hoistPolyVExpr :: [TyVar] -> Inline -> VM VExpr -> VM VExpr takeHoisted :: VM [(Var, CoreExpr)] -- | Utils concerning closure construction and application. module Vectorise.Utils.Closure -- | Make a closure. mkClosure :: Type -> Type -> Type -> VExpr -> VExpr -> VM VExpr -- | Make a closure application. mkClosureApp :: Type -> Type -> VExpr -> VExpr -> VM VExpr buildClosure :: [TyVar] -> [VVar] -> Type -> Type -> VM VExpr -> VM VExpr buildClosures :: [TyVar] -> [VVar] -> [Type] -> Type -> VM VExpr -> VM VExpr buildEnv :: [VVar] -> VM (Type, VExpr, VExpr -> VExpr -> VExpr) module Vectorise.Utils.PRDict prDFunOfTyCon :: TyCon -> VM CoreExpr prDictOfType :: Type -> VM CoreExpr prDictOfTyApp :: Type -> [Type] -> VM CoreExpr prDFunApply :: CoreExpr -> [Type] -> VM CoreExpr wrapPR :: Type -> VM CoreExpr module Vectorise.Utils collectAnnTypeArgs :: AnnExpr b ann -> (AnnExpr b ann, [Type]) collectAnnTypeBinders :: AnnExpr Var ann -> ([Var], AnnExpr Var ann) collectAnnValBinders :: AnnExpr Var ann -> ([Var], AnnExpr Var ann) isAnnTypeArg :: AnnExpr b ann -> Bool replicatePD :: CoreExpr -> CoreExpr -> VM CoreExpr emptyPD :: Type -> VM CoreExpr packByTagPD :: Type -> CoreExpr -> CoreExpr -> CoreExpr -> CoreExpr -> VM CoreExpr combinePD :: Type -> CoreExpr -> CoreExpr -> [CoreExpr] -> VM CoreExpr -- | Like replicatePD but use the lifting context in the vectoriser -- state. liftPD :: CoreExpr -> VM CoreExpr zipScalars :: [Type] -> Type -> VM CoreExpr scalarClosure :: [Type] -> Type -> CoreExpr -> CoreExpr -> VM CoreExpr -- | Make a fresh local variable with the given type. The variable's name -- is formed using the given string as the prefix. newLocalVar :: FastString -> Type -> VM Var -- | Representation of Algebraic Data Types. module Vectorise.Type.Repr data CompRepr Keep :: Type -> CoreExpr -> CompRepr Wrap :: Type -> CompRepr data ProdRepr EmptyProd :: ProdRepr UnaryProd :: CompRepr -> ProdRepr Prod :: TyCon -> TyCon -> [Type] -> [CompRepr] -> ProdRepr repr_tup_tc :: ProdRepr -> TyCon repr_ptup_tc :: ProdRepr -> TyCon repr_comp_tys :: ProdRepr -> [Type] repr_comps :: ProdRepr -> [CompRepr] data ConRepr ConRepr :: DataCon -> ProdRepr -> ConRepr data SumRepr EmptySum :: SumRepr UnarySum :: ConRepr -> SumRepr Sum :: TyCon -> TyCon -> Type -> [Type] -> [ConRepr] -> SumRepr repr_sum_tc :: SumRepr -> TyCon repr_psum_tc :: SumRepr -> TyCon repr_sel_ty :: SumRepr -> Type repr_con_tys :: SumRepr -> [Type] repr_cons :: SumRepr -> [ConRepr] tyConRepr :: TyCon -> VM SumRepr sumReprType :: SumRepr -> VM Type conReprType :: ConRepr -> VM Type prodReprType :: ProdRepr -> VM Type compReprType :: CompRepr -> VM Type compOrigType :: CompRepr -> Type module Vectorise.Type.PData buildPDataTyCon :: TyCon -> TyCon -> SumRepr -> VM TyCon module Vectorise.Type.PRepr buildPReprTyCon :: TyCon -> TyCon -> SumRepr -> VM TyCon buildToPRepr :: TyCon -> TyCon -> TyCon -> SumRepr -> VM CoreExpr buildFromPRepr :: TyCon -> TyCon -> TyCon -> SumRepr -> VM CoreExpr buildToArrPRepr :: TyCon -> TyCon -> TyCon -> SumRepr -> VM CoreExpr buildFromArrPRepr :: TyCon -> TyCon -> TyCon -> SumRepr -> VM CoreExpr module Vectorise.Type.PRDict buildPRDict :: TyCon -> TyCon -> TyCon -> SumRepr -> VM CoreExpr module Vectorise.Type.PADict -- | Build the PA dictionary for some type and hoist it to top level. The -- PA dictionary holds fns that convert values to and from their -- vectorised representations. buildPADict :: TyCon -> TyCon -> TyCon -> SumRepr -> VM Var module Vectorise.Type.Type -- | Vectorise a type constructor. vectTyCon :: TyCon -> VM TyCon -- | Produce the vectorised and lifted versions of a type. vectAndLiftType :: Type -> VM (Type, Type) -- | Vectorise a type. vectType :: Type -> VM Type module Vectorise.Type.TyConDecl -- | Vectorise some (possibly recursively defined) type constructors. vectTyConDecls :: [TyCon] -> VM [TyCon] module Vectorise.Type.Env -- | Vectorise a type environment. The type environment contains all the -- type things defined in a module. vectTypeEnv :: TypeEnv -> VM (TypeEnv, [FamInst], [(Var, CoreExpr)]) module Vectorise.Convert -- | Build an expression that calls the vectorised version of some function -- from a Closure. -- -- For example (x :: Double) -> (y :: Double) -> ($v_foo $: x) -- $: y -- -- We use the type of the original binding to work out how many outer -- lambdas to add. fromVect :: Type -> CoreExpr -> VM CoreExpr -- | Vectorise variables and literals. module Vectorise.Var -- | Vectorise a binder variable, along with its attached type. vectBndr :: Var -> VM VVar -- | Vectorise a binder variable, along with its attached type, but give -- the result a new name. vectBndrNew :: Var -> FastString -> VM VVar -- | Vectorise a binder then run a computation with that binder in scope. vectBndrIn :: Var -> VM a -> VM (VVar, a) -- | Vectorise a binder, give it a new name, then run a computation with -- that binder in scope. vectBndrNewIn :: Var -> FastString -> VM a -> VM (VVar, a) -- | Vectorise some binders, then run a computation with them in scope. vectBndrsIn :: [Var] -> VM a -> VM ([VVar], a) -- | Vectorise a variable, producing the vectorised and lifted versions. vectVar :: Var -> VM VExpr -- | Like vectVar but also add type applications to the variables. vectPolyVar :: Var -> [Type] -> VM VExpr -- | Lifted literals are created by replicating them We use the the integer -- context in the VM state for the number of elements in the -- output array. vectLiteral :: Literal -> VM VExpr -- | Vectorisation of expressions. module Vectorise.Exp -- | Vectorise a polymorphic expression. vectPolyExpr :: Bool -> CoreExprWithFVs -> VM (Inline, VExpr) module TcEnv -- | A typecheckable-thing, essentially anything that has a name data TyThing AnId :: Id -> TyThing ADataCon :: DataCon -> TyThing ATyCon :: TyCon -> TyThing AClass :: Class -> TyThing data TcTyThing AGlobal :: TyThing -> TcTyThing ATcId :: TcId -> ThLevel -> TcTyThing tct_id :: TcTyThing -> TcId tct_level :: TcTyThing -> ThLevel ATyVar :: Name -> TcType -> TcTyThing AThing :: TcKind -> TcTyThing type TcId = Id data InstInfo a InstInfo :: Instance -> InstBindings a -> InstInfo a iSpec :: InstInfo a -> Instance iBinds :: InstInfo a -> InstBindings a iDFunId :: InstInfo a -> DFunId pprInstInfo :: InstInfo a -> SDoc pprInstInfoDetails :: OutputableBndr a => InstInfo a -> SDoc simpleInstInfoClsTy :: InstInfo a -> (Class, Type) simpleInstInfoTy :: InstInfo a -> Type simpleInstInfoTyCon :: InstInfo a -> TyCon data InstBindings a VanillaInst :: (LHsBinds a) -> [LSig a] -> Bool -> InstBindings a NewTypeDerived :: CoercionI -> TyCon -> InstBindings a tcExtendGlobalEnv :: [TyThing] -> TcM r -> TcM r setGlobalTypeEnv :: TcGblEnv -> TypeEnv -> TcM TcGblEnv tcExtendGlobalValEnv :: [Id] -> TcM a -> TcM a tcLookupLocatedGlobal :: Located Name -> TcM TyThing tcLookupGlobal :: Name -> TcM TyThing tcLookupField :: Name -> TcM Id tcLookupTyCon :: Name -> TcM TyCon tcLookupClass :: Name -> TcM Class tcLookupDataCon :: Name -> TcM DataCon tcLookupLocatedGlobalId :: Located Name -> TcM Id tcLookupLocatedTyCon :: Located Name -> TcM TyCon tcLookupLocatedClass :: Located Name -> TcM Class tcLookupFamInst :: TyCon -> [Type] -> TcM (Maybe (TyCon, [Type])) tcLookupDataFamInst :: TyCon -> [Type] -> TcM (TyCon, [Type]) tcExtendKindEnv :: [(Name, TcKind)] -> TcM r -> TcM r tcExtendKindEnvTvs :: [LHsTyVarBndr Name] -> ([LHsTyVarBndr Name] -> TcM r) -> TcM r tcExtendTyVarEnv :: [TyVar] -> TcM r -> TcM r tcExtendTyVarEnv2 :: [(Name, TcType)] -> TcM r -> TcM r tcExtendGhciEnv :: [TcId] -> TcM a -> TcM a tcExtendIdEnv :: [TcId] -> TcM a -> TcM a tcExtendIdEnv1 :: Name -> TcId -> TcM a -> TcM a tcExtendIdEnv2 :: [(Name, TcId)] -> TcM a -> TcM a tcLookup :: Name -> TcM TcTyThing tcLookupLocated :: Located Name -> TcM TcTyThing tcLookupLocalIds :: [Name] -> TcM [TcId] tcLookupId :: Name -> TcM Id tcLookupTyVar :: Name -> TcM TcTyVar getScopedTyVarBinds :: TcM [(Name, TcType)] getInLocalScope :: TcM (Name -> Bool) wrongThingErr :: String -> TcTyThing -> Name -> TcM a pprBinders :: [Name] -> SDoc tcExtendRecEnv :: [(Name, TyThing)] -> TcM r -> TcM r tcExtendRules :: [LRuleDecl Id] -> TcM a -> TcM a tcGetDefaultTys :: Bool -> TcM ([Type], (Bool, Bool)) tcGetGlobalTyVars :: TcM TcTyVarSet checkWellStaged :: SDoc -> ThLevel -> ThLevel -> TcM () tcMetaTy :: Name -> TcM Type thLevel :: ThStage -> ThLevel topIdLvl :: Id -> ThLevel thTopLevelId :: Id -> Bool thRnBrack :: ThStage isBrackStage :: ThStage -> Bool newLocalName :: Name -> TcRnIf gbl lcl Name newDFunName :: Class -> [Type] -> SrcSpan -> TcM Name newFamInstTyConName :: Name -> [Type] -> SrcSpan -> TcM Name mkStableIdFromString :: String -> Type -> SrcSpan -> (OccName -> OccName) -> TcM TcId mkStableIdFromName :: Name -> Type -> SrcSpan -> (OccName -> OccName) -> TcM TcId instance MonadThings (IOEnv (Env TcGblEnv TcLclEnv)) module RnEnv newTopSrcBinder :: Located RdrName -> RnM Name lookupFamInstDeclBndr :: GlobalRdrEnv -> Located RdrName -> RnM Name lookupLocatedTopBndrRn :: Located RdrName -> RnM (Located Name) lookupTopBndrRn :: RdrName -> RnM Name lookupLocatedOccRn :: Located RdrName -> RnM (Located Name) lookupOccRn :: RdrName -> RnM Name lookupLocatedGlobalOccRn :: Located RdrName -> RnM (Located Name) lookupGlobalOccRn :: RdrName -> RnM Name lookupGlobalOccRn_maybe :: RdrName -> RnM (Maybe Name) lookupLocalDataTcNames :: NameSet -> SDoc -> RdrName -> RnM [Name] lookupSigOccRn :: Maybe NameSet -> Sig RdrName -> Located RdrName -> RnM (Located Name) lookupFixityRn :: Name -> RnM Fixity lookupTyFixityRn :: Located Name -> RnM Fixity lookupInstDeclBndr :: Name -> RdrName -> RnM Name lookupSubBndr :: Parent -> SDoc -> RdrName -> RnM Name lookupConstructorFields :: Name -> RnM [Name] lookupSyntaxName :: Name -> RnM (SyntaxExpr Name, FreeVars) lookupSyntaxTable :: [Name] -> RnM (SyntaxTable Name, FreeVars) lookupGreRn :: RdrName -> RnM GlobalRdrElt lookupGreLocalRn :: RdrName -> RnM (Maybe GlobalRdrElt) lookupGreRn_maybe :: RdrName -> RnM (Maybe GlobalRdrElt) getLookupOccRn :: RnM (Name -> Maybe Name) addUsedRdrNames :: [RdrName] -> RnM () newLocalBndrRn :: Located RdrName -> RnM Name newLocalBndrsRn :: [Located RdrName] -> RnM [Name] newIPNameRn :: IPName RdrName -> TcRnIf m n (IPName Name) bindLocalName :: Name -> RnM a -> RnM a bindLocalNames :: [Name] -> RnM a -> RnM a bindLocalNamesFV :: [Name] -> RnM (a, FreeVars) -> RnM (a, FreeVars) type MiniFixityEnv = FastStringEnv (Located Fixity) emptyFsEnv :: FastStringEnv a extendFsEnv :: FastStringEnv a -> FastString -> a -> FastStringEnv a lookupFsEnv :: FastStringEnv a -> FastString -> Maybe a addLocalFixities :: MiniFixityEnv -> [Name] -> RnM a -> RnM a bindLocatedLocalsFV :: [Located RdrName] -> ([Name] -> RnM (a, FreeVars)) -> RnM (a, FreeVars) bindLocatedLocalsRn :: [Located RdrName] -> ([Name] -> RnM a) -> RnM a bindSigTyVarsFV :: [Name] -> RnM (a, FreeVars) -> RnM (a, FreeVars) bindPatSigTyVars :: [LHsType RdrName] -> ([Name] -> RnM a) -> RnM a bindPatSigTyVarsFV :: [LHsType RdrName] -> RnM (a, FreeVars) -> RnM (a, FreeVars) bindTyVarsRn :: [LHsTyVarBndr RdrName] -> ([LHsTyVarBndr Name] -> RnM a) -> RnM a bindTyVarsFV :: [LHsTyVarBndr RdrName] -> ([LHsTyVarBndr Name] -> RnM (a, FreeVars)) -> RnM (a, FreeVars) extendTyVarEnvFVRn :: [Name] -> RnM (a, FreeVars) -> RnM (a, FreeVars) checkDupRdrNames :: [Located RdrName] -> RnM () checkDupAndShadowedRdrNames :: [Located RdrName] -> RnM () checkDupNames :: [Name] -> RnM () checkDupAndShadowedNames :: (GlobalRdrEnv, LocalRdrEnv) -> [Name] -> RnM () addFvRn :: FreeVars -> RnM (thing, FreeVars) -> RnM (thing, FreeVars) mapFvRn :: (a -> RnM (b, FreeVars)) -> [a] -> RnM ([b], FreeVars) mapMaybeFvRn :: (a -> RnM (b, FreeVars)) -> Maybe a -> RnM (Maybe b, FreeVars) mapFvRnCPS :: (a -> (b -> RnM c) -> RnM c) -> [a] -> ([b] -> RnM c) -> RnM c warnUnusedMatches :: [Name] -> FreeVars -> RnM () warnUnusedTopBinds :: [GlobalRdrElt] -> RnM () warnUnusedLocalBinds :: [Name] -> FreeVars -> RnM () dataTcOccs :: RdrName -> [RdrName] unknownNameErr :: RdrName -> SDoc kindSigErr :: Outputable a => a -> SDoc perhapsForallMsg :: SDoc module RnTypes rnHsType :: SDoc -> HsType RdrName -> RnM (HsType Name) rnLHsType :: SDoc -> LHsType RdrName -> RnM (LHsType Name) rnLHsTypes :: SDoc -> [LHsType RdrName] -> IOEnv (Env TcGblEnv TcLclEnv) [LHsType Name] rnContext :: SDoc -> LHsContext RdrName -> RnM (LHsContext Name) rnHsSigType :: SDoc -> LHsType RdrName -> RnM (LHsType Name) rnHsTypeFVs :: SDoc -> LHsType RdrName -> RnM (LHsType Name, FreeVars) rnConDeclFields :: SDoc -> [ConDeclField RdrName] -> RnM [ConDeclField Name] rnLPred :: SDoc -> LHsPred RdrName -> RnM (LHsPred Name) mkOpAppRn :: LHsExpr Name -> LHsExpr Name -> Fixity -> LHsExpr Name -> RnM (HsExpr Name) mkNegAppRn :: LHsExpr id -> SyntaxExpr id -> RnM (HsExpr id) mkOpFormRn :: LHsCmdTop Name -> LHsExpr Name -> Fixity -> LHsCmdTop Name -> RnM (HsCmd Name) mkConOpPatRn :: Located Name -> Fixity -> LPat Name -> LPat Name -> RnM (Pat Name) checkPrecMatch :: Name -> MatchGroup Name -> RnM () checkSectionPrec :: FixityDirection -> HsExpr RdrName -> LHsExpr Name -> LHsExpr Name -> RnM () rnSplice :: HsSplice RdrName -> RnM (HsSplice Name, FreeVars) checkTH :: Outputable a => a -> String -> RnM () module Inst deeplySkolemise :: TcSigmaType -> TcM (HsWrapper, [TyVar], [EvVar], TcRhoType) deeplyInstantiate :: CtOrigin -> TcSigmaType -> TcM (HsWrapper, TcRhoType) instCall :: CtOrigin -> [TcType] -> TcThetaType -> TcM HsWrapper instStupidTheta :: CtOrigin -> TcThetaType -> TcM () emitWanted :: CtOrigin -> TcPredType -> TcM EvVar emitWanteds :: CtOrigin -> TcThetaType -> TcM [EvVar] newOverloadedLit :: CtOrigin -> HsOverLit Name -> TcRhoType -> TcM (HsOverLit TcId) mkOverLit :: OverLitVal -> TcM HsLit tcGetInstEnvs :: TcM (InstEnv, InstEnv) getOverlapFlag :: TcM OverlapFlag tcExtendLocalInstEnv :: [Instance] -> TcM a -> TcM a instCallConstraints :: CtOrigin -> TcThetaType -> TcM HsWrapper newMethodFromName :: CtOrigin -> Name -> TcRhoType -> TcM (HsExpr TcId) tcSyntaxName :: CtOrigin -> TcType -> (Name, HsExpr Name) -> TcM (Name, HsExpr TcId) hasEqualities :: [EvVar] -> Bool unitImplication :: Implication -> Bag Implication tyVarsOfWC :: WantedConstraints -> TyVarSet tyVarsOfBag :: (a -> TyVarSet) -> Bag a -> TyVarSet tyVarsOfEvVarXs :: Bag (EvVarX a) -> TyVarSet tyVarsOfEvVarX :: EvVarX a -> TyVarSet tyVarsOfEvVar :: EvVar -> TyVarSet tyVarsOfEvVars :: [EvVar] -> TyVarSet tyVarsOfImplication :: Implication -> TyVarSet tidyWantedEvVar :: TidyEnv -> WantedEvVar -> WantedEvVar tidyWantedEvVars :: TidyEnv -> Bag WantedEvVar -> Bag WantedEvVar tidyWC :: TidyEnv -> WantedConstraints -> WantedConstraints tidyEvVar :: TidyEnv -> EvVar -> EvVar tidyImplication :: TidyEnv -> Implication -> Implication tidyFlavoredEvVar :: TidyEnv -> FlavoredEvVar -> FlavoredEvVar substWantedEvVar :: TvSubst -> WantedEvVar -> WantedEvVar substWantedEvVars :: TvSubst -> Bag WantedEvVar -> Bag WantedEvVar substFlavoredEvVar :: TvSubst -> FlavoredEvVar -> FlavoredEvVar substEvVar :: TvSubst -> EvVar -> EvVar substImplication :: TvSubst -> Implication -> Implication module CoreMonad data CoreToDo CoreDoSimplify :: Int -> SimplifierMode -> CoreToDo CoreDoFloatInwards :: CoreToDo CoreDoFloatOutwards :: FloatOutSwitches -> CoreToDo CoreLiberateCase :: CoreToDo CoreDoPrintCore :: CoreToDo CoreDoStaticArgs :: CoreToDo CoreDoStrictness :: CoreToDo CoreDoWorkerWrapper :: CoreToDo CoreDoSpecialising :: CoreToDo CoreDoSpecConstr :: CoreToDo CoreDoGlomBinds :: CoreToDo CoreCSE :: CoreToDo CoreDoRuleCheck :: CompilerPhase -> String -> CoreToDo CoreDoVectorisation :: PackageId -> CoreToDo CoreDoNothing :: CoreToDo CoreDoPasses :: [CoreToDo] -> CoreToDo CoreDesugar :: CoreToDo CoreTidy :: CoreToDo CorePrep :: CoreToDo data SimplifierMode SimplMode :: [String] -> CompilerPhase -> Bool -> Bool -> Bool -> Bool -> SimplifierMode sm_names :: SimplifierMode -> [String] sm_phase :: SimplifierMode -> CompilerPhase sm_rules :: SimplifierMode -> Bool sm_inline :: SimplifierMode -> Bool sm_case_case :: SimplifierMode -> Bool sm_eta_expand :: SimplifierMode -> Bool data FloatOutSwitches FloatOutSwitches :: Maybe Int -> Bool -> Bool -> FloatOutSwitches -- | Just n = float lambdas to top level, if doing so will abstract -- over n or fewer value variables Nothing = float all lambdas to -- top level, regardless of how many free variables Just 0 is the vanilla -- case: float a lambda iff it has no free vars floatOutLambdas :: FloatOutSwitches -> Maybe Int -- | True = float constants to top level, even if they do not escape -- a lambda floatOutConstants :: FloatOutSwitches -> Bool -- | True = float out partial applications based on arity -- information. floatOutPartialApplications :: FloatOutSwitches -> Bool getCoreToDo :: DynFlags -> [CoreToDo] dumpSimplPhase :: DynFlags -> SimplifierMode -> Bool data SimplCount doSimplTick :: Tick -> SimplCount -> SimplCount doFreeSimplTick :: Tick -> SimplCount -> SimplCount simplCountN :: SimplCount -> Int pprSimplCount :: SimplCount -> SDoc plusSimplCount :: SimplCount -> SimplCount -> SimplCount zeroSimplCount :: DynFlags -> SimplCount isZeroSimplCount :: SimplCount -> Bool data Tick PreInlineUnconditionally :: Id -> Tick PostInlineUnconditionally :: Id -> Tick UnfoldingDone :: Id -> Tick RuleFired :: FastString -> Tick LetFloatFromLet :: Tick EtaExpansion :: Id -> Tick EtaReduction :: Id -> Tick BetaReduction :: Id -> Tick CaseOfCase :: Id -> Tick KnownBranch :: Id -> Tick CaseMerge :: Id -> Tick AltMerge :: Id -> Tick CaseElim :: Id -> Tick CaseIdentity :: Id -> Tick FillInCaseDefault :: Id -> Tick BottomFound :: Tick SimplifierDone :: Tick -- | The monad used by Core-to-Core passes to access common state, register -- simplification statistics and so on data CoreM a runCoreM :: HscEnv -> RuleBase -> UniqSupply -> Module -> CoreM a -> IO (a, SimplCount) getHscEnv :: CoreM HscEnv getRuleBase :: CoreM RuleBase getModule :: CoreM Module getDynFlags :: CoreM DynFlags -- | The original name cache is the current mapping from Module and -- OccName to a compiler-wide unique Name getOrigNameCache :: CoreM OrigNameCache addSimplCount :: SimplCount -> CoreM () liftIO :: MonadIO m => IO a -> m a -- | Lift an IO operation into CoreM while consuming its -- SimplCount liftIOWithCount :: IO (SimplCount, a) -> CoreM a -- | Lift an IO operation with 1 argument into another monad liftIO1 :: MonadIO m => (a -> IO b) -> a -> m b -- | Lift an IO operation with 2 arguments into another monad liftIO2 :: MonadIO m => (a -> b -> IO c) -> a -> b -> m c -- | Lift an IO operation with 3 arguments into another monad liftIO3 :: MonadIO m => (a -> b -> c -> IO d) -> a -> b -> c -> m d -- | Lift an IO operation with 4 arguments into another monad liftIO4 :: MonadIO m => (a -> b -> c -> d -> IO e) -> a -> b -> c -> d -> m e -- | Get all annotations of a given type. This happens lazily, that is no -- deserialization will take place until the [a] is actually demanded and -- the [a] can also be empty (the UniqFM is not filtered). -- -- This should be done once at the start of a Core-to-Core pass that uses -- annotations. -- -- See Note [Annotations] getAnnotations :: Typeable a => ([Word8] -> a) -> ModGuts -> CoreM (UniqFM [a]) -- | Get at most one annotation of a given type per Unique. getFirstAnnotations :: Typeable a => ([Word8] -> a) -> ModGuts -> CoreM (UniqFM a) showPass :: DynFlags -> CoreToDo -> IO () endPass :: DynFlags -> CoreToDo -> [CoreBind] -> [CoreRule] -> IO () endIteration :: DynFlags -> CoreToDo -> Int -> [CoreBind] -> [CoreRule] -> IO () dumpIfSet :: Bool -> CoreToDo -> SDoc -> SDoc -> IO () -- | Output a message to the screen putMsg :: SDoc -> CoreM () -- | Output a String message to the screen putMsgS :: String -> CoreM () -- | Output an error to the screen errorMsg :: SDoc -> CoreM () -- | Output a string error to the screen errorMsgS :: String -> CoreM () -- | Output a fatal error to the screen. Note this does not by itself cause -- the compiler to die fatalErrorMsg :: SDoc -> CoreM () -- | Output a fatal string error to the screen. Note this does not by -- itself cause the compiler to die fatalErrorMsgS :: String -> CoreM () -- | Outputs a debugging message at verbosity level of -v or -- higher debugTraceMsg :: SDoc -> CoreM () -- | Output a string debugging message at verbosity level of -v or -- higher debugTraceMsgS :: String -> CoreM () -- | Show some labelled SDoc if a particular flag is set or at a -- verbosity level of -v -ddump-most or higher dumpIfSet_dyn :: DynFlag -> String -> SDoc -> CoreM () -- | Attempt to convert a Template Haskell name to one that GHC can -- understand. Original TH names such as those you get when you use the -- 'foo syntax will be translated to their equivalent GHC name -- exactly. Qualified or unqualifed TH names will be dynamically bound to -- names in the module being compiled, if possible. Exact TH names will -- be bound to the name they represent, exactly. thNameToGhcName :: Name -> CoreM (Maybe Name) instance MonadThings CoreM instance MonadIO CoreM instance MonadUnique CoreM instance MonadPlus IO => MonadPlus CoreM instance Applicative CoreM instance Monad CoreM instance Functor CoreM instance Ord Tick instance Eq Tick instance Outputable Tick instance Outputable FloatOutSwitches instance Outputable SimplifierMode instance Outputable CoreToDo module CorePrep corePrepPgm :: DynFlags -> [CoreBind] -> [TyCon] -> IO [CoreBind] corePrepExpr :: DynFlags -> CoreExpr -> IO CoreExpr instance Outputable OkToSpec instance Outputable Floats instance Outputable FloatingBind module SetLevels setLevels :: FloatOutSwitches -> [CoreBind] -> UniqSupply -> [LevelledBind] data Level Level :: Int -> Int -> Level tOP_LEVEL :: Level type LevelledBind = TaggedBind Level type LevelledExpr = TaggedExpr Level incMinorLvl :: Level -> Level ltMajLvl :: Level -> Level -> Bool ltLvl :: Level -> Level -> Bool isTopLvl :: Level -> Bool instance Eq Level instance Outputable Level module Specialise specProgram :: ModGuts -> CoreM ModGuts instance Ord CallKey instance Eq CallKey instance Outputable CallKey instance Outputable CallInfoSet instance Outputable UsageDetails module Vectorise -- | Vectorise a single module. Takes the package containing the DPH -- backend we're using. Eg either dph-par or dph-seq. vectorise :: PackageId -> ModGuts -> CoreM ModGuts -- | The dynamic linker for GHCi. -- -- This module deals with the top-level issues of dynamic linking, -- calling the object-code linker and the byte-code linker where -- necessary. module Linker data HValue -- | Get the HValue associated with the given name. -- -- May cause loading the module that contains the name. -- -- Throws a ProgramError if loading fails or the name cannot be -- found. getHValue :: HscEnv -> Name -> IO HValue -- | Display the persistent linker state. showLinkerState :: IO () -- | Link a single expression, including first linking packages and -- modules that this expression depends on. -- -- Raises an IO exception (ProgramError) if it can't find a -- compiled version of the dependents to link. linkExpr :: HscEnv -> SrcSpan -> UnlinkedBCO -> IO HValue -- | Unloading old objects ready for a new compilation sweep. -- -- The compilation manager provides us with a list of linkables that it -- considers "stable", i.e. won't be recompiled this time around. For -- each of the modules current linked in memory, -- -- unload :: DynFlags -> [Linkable] -> IO () -- | Temporarily extend the linker state. withExtendedLinkEnv :: (MonadIO m, ExceptionMonad m) => [(Name, HValue)] -> m a -> m a extendLinkEnv :: [(Name, HValue)] -> IO () deleteFromLinkEnv :: [Name] -> IO () extendLoadedPkgs :: [PackageId] -> IO () -- | Link exactly the specified packages, and their dependents (unless of -- course they are already linked). The dependents are linked -- automatically, and it doesn't matter what order you specify the input -- packages. linkPackages :: DynFlags -> [PackageId] -> IO () -- | Initialise the dynamic linker. This entails -- -- a) Calling the C initialisation procedure, -- -- b) Loading any packages specified on the command line, -- -- c) Loading any packages specified on the command line, now held in the -- -l options in v_Opt_l, -- -- d) Loading any .o/.dll files specified on the command line, -- now held in v_Ld_inputs, -- -- e) Loading any MacOS frameworks. -- -- NOTE: This function is idempotent; if called more than once, it does -- nothing. This is useful in Template Haskell, where we call it before -- trying to link. initDynLinker :: DynFlags -> IO () -- | Given a data constructor in the heap, find its Name. The info tables -- for data constructors have a field which records the source name of -- the constructor as a Ptr Word8 (UTF-8 encoded string). The format is: -- --
--   Package:Module.Name
--   
-- -- We use this string to lookup the interpreter's internal representation -- of the name using the lookupOrig. dataConInfoPtrToName :: Ptr () -> TcM (Either String Name) module MkIface mkUsedNames :: TcGblEnv -> NameSet mkDependencies :: TcGblEnv -> IO Dependencies mkIface :: HscEnv -> Maybe Fingerprint -> ModDetails -> ModGuts -> IO (Messages, Maybe (ModIface, Bool)) -- | make an interface from the results of typechecking only. Useful for -- non-optimising compilation, or where we aren't generating any object -- code at all (HscNothing). mkIfaceTc :: HscEnv -> Maybe Fingerprint -> ModDetails -> TcGblEnv -> IO (Messages, Maybe (ModIface, Bool)) writeIfaceFile :: DynFlags -> ModLocation -> ModIface -> IO () checkOldIface :: HscEnv -> ModSummary -> Bool -> Maybe ModIface -> IO (RecompileRequired, Maybe ModIface) tyThingToIfaceDecl :: TyThing -> IfaceDecl instance Binary IfaceDeclExtras instance Outputable IfaceDeclExtras module Desugar -- | Main entry point to the desugarer. deSugar :: HscEnv -> ModLocation -> TcGblEnv -> IO (Messages, Maybe ModGuts) deSugarExpr :: HscEnv -> Module -> GlobalRdrEnv -> TypeEnv -> LHsExpr Id -> IO (Messages, Maybe CoreExpr) module CodeOutput codeOutput :: DynFlags -> Module -> ModLocation -> ForeignStubs -> [PackageId] -> [RawCmm] -> IO (Bool, Bool) outputForeignStubs :: DynFlags -> Module -> ModLocation -> ForeignStubs -> IO (Bool, Bool) module SysTools initSysTools :: Maybe String -> DynFlags -> IO DynFlags runUnlit :: DynFlags -> [Option] -> IO () runCpp :: DynFlags -> [Option] -> IO () runCc :: DynFlags -> [Option] -> IO () runPp :: DynFlags -> [Option] -> IO () runMangle :: DynFlags -> [Option] -> IO () runSplit :: DynFlags -> [Option] -> IO () runAs :: DynFlags -> [Option] -> IO () runLink :: DynFlags -> [Option] -> IO () runMkDLL :: DynFlags -> [Option] -> IO () runWindres :: DynFlags -> [Option] -> IO () runLlvmOpt :: DynFlags -> [Option] -> IO () runLlvmLlc :: DynFlags -> [Option] -> IO () touch :: DynFlags -> String -> String -> IO () copy :: DynFlags -> String -> FilePath -> FilePath -> IO () copyWithHeader :: DynFlags -> String -> Maybe String -> FilePath -> FilePath -> IO () getExtraViaCOpts :: DynFlags -> IO [String] setTmpDir :: FilePath -> DynFlags -> DynFlags newTempName :: DynFlags -> Suffix -> IO FilePath cleanTempDirs :: DynFlags -> IO () cleanTempFiles :: DynFlags -> IO () cleanTempFilesExcept :: DynFlags -> [FilePath] -> IO () addFilesToClean :: DynFlags -> [FilePath] -> IO () -- | When invoking external tools as part of the compilation pipeline, we -- pass these a sequence of options on the command-line. Rather than just -- using a list of Strings, we use a type that allows us to distinguish -- between filepaths and 'other stuff'. The reason for this is that this -- type gives us a handle on transforming filenames, and filenames only, -- to whatever format they're expected to be on a particular platform. data Option FileOption :: String -> String -> Option Option :: String -> Option -- | Parsing the top of a Haskell source file to get its module name, -- imports and options. -- -- (c) Simon Marlow 2005 (c) Lemmih 2006 module HeaderInfo -- | Parse the imports of a source file. -- -- Throws a SourceError if parsing fails. getImports :: GhcMonad m => DynFlags -> StringBuffer -> FilePath -> FilePath -> m ([Located (ImportDecl RdrName)], [Located (ImportDecl RdrName)], Located ModuleName) mkPrelImports :: ModuleName -> Bool -> [LImportDecl RdrName] -> [LImportDecl RdrName] -- | Parse OPTIONS and LANGUAGE pragmas of the source file. -- -- Throws a SourceError if flag parsing fails (including -- unsupported flags.) getOptionsFromFile :: DynFlags -> FilePath -> IO [Located String] -- | Parse OPTIONS and LANGUAGE pragmas of the source file. -- -- Throws a SourceError if flag parsing fails (including -- unsupported flags.) getOptions :: DynFlags -> StringBuffer -> FilePath -> [Located String] optionsErrorMsgs :: [String] -> [Located String] -> FilePath -> Messages -- | Complain about non-dynamic flags in OPTIONS pragmas. -- -- Throws a SourceError if the input list is non-empty claiming -- that the input flags are unknown. checkProcessArgsResult :: MonadIO m => [Located String] -> m () module TidyPgm mkBootModDetailsDs :: HscEnv -> ModGuts -> IO ModDetails mkBootModDetailsTc :: HscEnv -> TcGblEnv -> IO ModDetails tidyProgram :: HscEnv -> ModGuts -> IO (CgGuts, ModDetails) globaliseAndTidyId :: Id -> Id instance Monad DFFV module RnNames rnImports :: [LImportDecl RdrName] -> RnM ([LImportDecl Name], GlobalRdrEnv, ImportAvails, AnyHpcUsage) getLocalNonValBinders :: HsGroup RdrName -> RnM [AvailInfo] rnExports :: Bool -> Maybe [LIE RdrName] -> TcGblEnv -> RnM TcGblEnv extendGlobalRdrEnvRn :: [AvailInfo] -> MiniFixityEnv -> RnM (TcGblEnv, TcLclEnv) -- | make a GlobalRdrEnv where all the elements point to the same -- import declaration (useful for hiding imports, or imports with -- no details). gresFromAvails :: Provenance -> [AvailInfo] -> [GlobalRdrElt] reportUnusedNames :: Maybe [LIE RdrName] -> TcGblEnv -> RnM () finishWarnings :: DynFlags -> Maybe WarningTxt -> TcGblEnv -> RnM TcGblEnv module SCCfinal stgMassageForProfiling :: DynFlags -> PackageId -> Module -> UniqSupply -> [StgBinding] -> (CollectedCCs, [StgBinding]) instance Monad MassageM module SimplStg stg2stg :: DynFlags -> Module -> [StgBinding] -> IO ([(StgBinding, [(Id, [Id])])], CollectedCCs) module RnPat rnPat :: HsMatchContext Name -> LPat RdrName -> (LPat Name -> RnM (a, FreeVars)) -> RnM (a, FreeVars) rnPats :: HsMatchContext Name -> [LPat RdrName] -> ([LPat Name] -> RnM (a, FreeVars)) -> RnM (a, FreeVars) rnBindPat :: NameMaker -> LPat RdrName -> RnM (LPat Name, FreeVars) data NameMaker applyNameMaker :: NameMaker -> Located RdrName -> RnM Name localRecNameMaker :: MiniFixityEnv -> NameMaker topRecNameMaker :: MiniFixityEnv -> NameMaker rnHsRecFields1 :: HsRecFieldContext -> (RdrName -> arg) -> HsRecFields RdrName (Located arg) -> RnM ([HsRecField Name (Located arg)], FreeVars) data HsRecFieldContext HsRecFieldCon :: Name -> HsRecFieldContext HsRecFieldPat :: Name -> HsRecFieldContext HsRecFieldUpd :: HsRecFieldContext rnLit :: HsLit -> RnM () rnOverLit :: HsOverLit t -> RnM (HsOverLit Name, FreeVars) checkTupSize :: Int -> RnM () patSigErr :: Outputable a => a -> SDoc instance Monad CpsRn module RnBinds rnTopBinds :: HsValBinds RdrName -> RnM (HsValBinds Name, DefUses) rnTopBindsLHS :: MiniFixityEnv -> HsValBinds RdrName -> RnM (HsValBindsLR Name RdrName) rnTopBindsRHS :: HsValBindsLR Name RdrName -> RnM (HsValBinds Name, DefUses) rnLocalBindsAndThen :: HsLocalBinds RdrName -> (HsLocalBinds Name -> RnM (result, FreeVars)) -> RnM (result, FreeVars) rnLocalValBindsLHS :: MiniFixityEnv -> HsValBinds RdrName -> RnM ([Name], HsValBindsLR Name RdrName) rnLocalValBindsRHS :: NameSet -> HsValBindsLR Name RdrName -> RnM (HsValBinds Name, DefUses) rnMethodBinds :: Name -> (Name -> [Name]) -> [Name] -> LHsBinds RdrName -> RnM (LHsBinds Name, FreeVars) renameSigs :: Maybe NameSet -> (Sig Name -> Bool) -> [LSig RdrName] -> RnM [LSig Name] mkSigTvFn :: [LSig Name] -> (Name -> [Name]) rnMatchGroup :: HsMatchContext Name -> MatchGroup RdrName -> RnM (MatchGroup Name, FreeVars) rnGRHSs :: HsMatchContext Name -> GRHSs RdrName -> RnM (GRHSs Name, FreeVars) makeMiniFixityEnv :: [LFixitySig RdrName] -> RnM MiniFixityEnv type MiniFixityEnv = FastStringEnv (Located Fixity) misplacedSigErr :: LSig Name -> RnM () module RnSource rnSrcDecls :: HsGroup RdrName -> RnM (TcGblEnv, HsGroup Name) addTcgDUs :: TcGblEnv -> DefUses -> TcGblEnv rnTyClDecls :: [[LTyClDecl RdrName]] -> RnM ([[LTyClDecl Name]], FreeVars) findSplice :: [LHsDecl RdrName] -> RnM (HsGroup RdrName, Maybe (SpliceDecl RdrName, [LHsDecl RdrName])) module RnExpr rnLExpr :: LHsExpr RdrName -> RnM (LHsExpr Name, FreeVars) rnExpr :: HsExpr RdrName -> RnM (HsExpr Name, FreeVars) rnStmts :: HsStmtContext Name -> [LStmt RdrName] -> RnM (thing, FreeVars) -> RnM (([LStmt Name], thing), FreeVars) module FloatOut floatOutwards :: FloatOutSwitches -> DynFlags -> UniqSupply -> [CoreBind] -> IO [CoreBind] module LiberateCase liberateCase :: DynFlags -> [CoreBind] -> [CoreBind] module SimplMonad data SimplM result initSmpl :: DynFlags -> RuleBase -> (FamInstEnv, FamInstEnv) -> UniqSupply -> SimplM a -> (a, SimplCount) getDOptsSmpl :: SimplM DynFlags getSimplRules :: SimplM RuleBase getFamEnvs :: SimplM (FamInstEnv, FamInstEnv) -- | A monad for generating unique identifiers class Monad m => MonadUnique m getUniqueSupplyM :: MonadUnique m => m UniqSupply getUniqueM :: MonadUnique m => m Unique getUniquesM :: MonadUnique m => m [Unique] newId :: FastString -> Type -> SimplM Id data SimplCount tick :: Tick -> SimplM () freeTick :: Tick -> SimplM () getSimplCount :: SimplM SimplCount zeroSimplCount :: DynFlags -> SimplCount pprSimplCount :: SimplCount -> SDoc plusSimplCount :: SimplCount -> SimplCount -> SimplCount isZeroSimplCount :: SimplCount -> Bool instance MonadUnique SimplM instance Monad SimplM module SimplEnv type InId = Id type InBind = CoreBind type InExpr = CoreExpr type InAlt = CoreAlt type InArg = CoreArg type InType = Type type InBndr = CoreBndr type InVar = Var type OutId = Id type OutTyVar = TyVar type OutBind = CoreBind type OutExpr = CoreExpr type OutAlt = CoreAlt type OutArg = CoreArg type OutType = Type type OutBndr = CoreBndr type OutVar = Var type InCoercion = Coercion type OutCoercion = Coercion setMode :: SimplifierMode -> SimplEnv -> SimplEnv getMode :: SimplEnv -> SimplifierMode updMode :: (SimplifierMode -> SimplifierMode) -> SimplEnv -> SimplEnv setEnclosingCC :: SimplEnv -> CostCentreStack -> SimplEnv getEnclosingCC :: SimplEnv -> CostCentreStack data SimplEnv SimplEnv :: SimplifierMode -> CostCentreStack -> TvSubstEnv -> SimplIdSubst -> InScopeSet -> Floats -> SimplEnv seMode :: SimplEnv -> SimplifierMode seCC :: SimplEnv -> CostCentreStack seTvSubst :: SimplEnv -> TvSubstEnv seIdSubst :: SimplEnv -> SimplIdSubst seInScope :: SimplEnv -> InScopeSet seFloats :: SimplEnv -> Floats type StaticEnv = SimplEnv pprSimplEnv :: SimplEnv -> SDoc mkSimplEnv :: SimplifierMode -> SimplEnv extendIdSubst :: SimplEnv -> Id -> SimplSR -> SimplEnv extendTvSubst :: SimplEnv -> TyVar -> Type -> SimplEnv zapSubstEnv :: SimplEnv -> SimplEnv setSubstEnv :: SimplEnv -> TvSubstEnv -> SimplIdSubst -> SimplEnv getInScope :: SimplEnv -> InScopeSet setInScope :: SimplEnv -> SimplEnv -> SimplEnv setInScopeSet :: SimplEnv -> InScopeSet -> SimplEnv modifyInScope :: SimplEnv -> CoreBndr -> SimplEnv addNewInScopeIds :: SimplEnv -> [CoreBndr] -> SimplEnv getSimplRules :: SimplM RuleBase data SimplSR DoneEx :: OutExpr -> SimplSR DoneId :: OutId -> SimplSR ContEx :: TvSubstEnv -> SimplIdSubst -> InExpr -> SimplSR mkContEx :: SimplEnv -> InExpr -> SimplSR substId :: SimplEnv -> InId -> SimplSR lookupRecBndr :: SimplEnv -> InId -> OutId simplNonRecBndr :: SimplEnv -> InBndr -> SimplM (SimplEnv, OutBndr) simplRecBndrs :: SimplEnv -> [InBndr] -> SimplM SimplEnv simplLamBndr :: SimplEnv -> Var -> SimplM (SimplEnv, Var) simplLamBndrs :: SimplEnv -> [InBndr] -> SimplM (SimplEnv, [OutBndr]) simplBinder :: SimplEnv -> InBndr -> SimplM (SimplEnv, OutBndr) simplBinders :: SimplEnv -> [InBndr] -> SimplM (SimplEnv, [OutBndr]) addBndrRules :: SimplEnv -> InBndr -> OutBndr -> (SimplEnv, OutBndr) substExpr :: SDoc -> SimplEnv -> CoreExpr -> CoreExpr substTy :: SimplEnv -> Type -> Type substTyVar :: SimplEnv -> TyVar -> Type getTvSubst :: SimplEnv -> TvSubst mkCoreSubst :: SDoc -> SimplEnv -> Subst data Floats emptyFloats :: Floats isEmptyFloats :: SimplEnv -> Bool addNonRec :: SimplEnv -> OutId -> OutExpr -> SimplEnv addFloats :: SimplEnv -> SimplEnv -> SimplEnv extendFloats :: SimplEnv -> OutBind -> SimplEnv wrapFloats :: SimplEnv -> OutExpr -> OutExpr floatBinds :: Floats -> [OutBind] setFloats :: SimplEnv -> SimplEnv -> SimplEnv zapFloats :: SimplEnv -> SimplEnv addRecFloats :: SimplEnv -> SimplEnv -> SimplEnv doFloatFromRhs :: TopLevelFlag -> RecFlag -> Bool -> OutExpr -> SimplEnv -> Bool getFloats :: SimplEnv -> [CoreBind] instance Outputable FloatFlag instance Outputable Floats instance Outputable SimplSR module SimplUtils mkLam :: SimplEnv -> [OutBndr] -> OutExpr -> SimplM OutExpr mkCase :: DynFlags -> OutExpr -> OutId -> [OutAlt] -> SimplM OutExpr prepareAlts :: OutExpr -> OutId -> [InAlt] -> SimplM ([AltCon], [InAlt]) tryEtaExpand :: SimplEnv -> OutId -> OutExpr -> SimplM (Arity, OutExpr) preInlineUnconditionally :: SimplEnv -> TopLevelFlag -> InId -> InExpr -> Bool postInlineUnconditionally :: SimplEnv -> TopLevelFlag -> OutId -> OccInfo -> OutExpr -> Unfolding -> Bool activeUnfolding :: SimplEnv -> Id -> Bool activeRule :: DynFlags -> SimplEnv -> Maybe (Activation -> Bool) getUnfoldingInRuleMatch :: SimplEnv -> IdUnfoldingFun simplEnvForGHCi :: SimplEnv updModeForInlineRules :: Activation -> SimplifierMode -> SimplifierMode data SimplCont Stop :: CallCtxt -> SimplCont CoerceIt :: OutCoercion -> SimplCont -> SimplCont ApplyTo :: DupFlag -> InExpr -> StaticEnv -> SimplCont -> SimplCont Select :: DupFlag -> InId -> [InAlt] -> StaticEnv -> SimplCont -> SimplCont StrictBind :: InId -> [InBndr] -> InExpr -> StaticEnv -> SimplCont -> SimplCont StrictArg :: ArgInfo -> CallCtxt -> SimplCont -> SimplCont data DupFlag NoDup :: DupFlag Simplified :: DupFlag OkToDup :: DupFlag data ArgInfo ArgInfo :: Id -> [OutExpr] -> [CoreRule] -> Bool -> [Bool] -> [Int] -> ArgInfo ai_fun :: ArgInfo -> Id ai_args :: ArgInfo -> [OutExpr] ai_rules :: ArgInfo -> [CoreRule] ai_encl :: ArgInfo -> Bool ai_strs :: ArgInfo -> [Bool] ai_discs :: ArgInfo -> [Int] isSimplified :: DupFlag -> Bool contIsDupable :: SimplCont -> Bool contResultType :: SimplEnv -> OutType -> SimplCont -> OutType contIsTrivial :: SimplCont -> Bool contArgs :: SimplCont -> (Bool, [ArgSummary], SimplCont) dropArgs :: Int -> SimplCont -> SimplCont pushSimplifiedArgs :: SimplEnv -> [CoreExpr] -> SimplCont -> SimplCont countValArgs :: SimplCont -> Int countArgs :: SimplCont -> Int addArgTo :: ArgInfo -> OutExpr -> ArgInfo mkBoringStop :: SimplCont mkRhsStop :: SimplCont mkLazyArgStop :: CallCtxt -> SimplCont contIsRhsOrArg :: SimplCont -> Bool interestingCallContext :: SimplCont -> CallCtxt interestingArg :: CoreExpr -> ArgSummary mkArgInfo :: Id -> [CoreRule] -> Int -> SimplCont -> ArgInfo abstractFloats :: [OutTyVar] -> SimplEnv -> OutExpr -> SimplM ([OutBind], OutExpr) instance Outputable DupFlag instance Outputable SimplCont module Simplify simplTopBinds :: SimplEnv -> [InBind] -> SimplM SimplEnv simplExpr :: SimplEnv -> CoreExpr -> SimplM CoreExpr module DmdAnal dmdAnalPgm :: DynFlags -> [CoreBind] -> IO [CoreBind] dmdAnalTopRhs :: CoreExpr -> (StrictSig, CoreExpr) both :: Demand -> Demand -> Demand instance Outputable AnalEnv module SpecConstr specConstrProgram :: ModGuts -> CoreM ModGuts data SpecConstrAnnotation :: * NoSpecConstr :: SpecConstrAnnotation ForceSpecConstr :: SpecConstrAnnotation instance Outputable ArgOcc instance Outputable HowBound instance Outputable Value module SimplCore core2core :: HscEnv -> ModGuts -> IO ModGuts simplifyExpr :: DynFlags -> CoreExpr -> IO CoreExpr module TcSMonad type CanonicalCts = Bag CanonicalCt emptyCCan :: CanonicalCts andCCan :: CanonicalCts -> CanonicalCts -> CanonicalCts andCCans :: [CanonicalCts] -> CanonicalCts singleCCan :: CanonicalCt -> CanonicalCts extendCCans :: CanonicalCts -> CanonicalCt -> CanonicalCts isEmptyCCan :: CanonicalCts -> Bool isCTyEqCan :: CanonicalCt -> Bool isCDictCan_Maybe :: CanonicalCt -> Maybe Class isCIPCan_Maybe :: CanonicalCt -> Maybe (IPName Name) isCFunEqCan_Maybe :: CanonicalCt -> Maybe TyCon isCFrozenErr :: CanonicalCt -> Bool data CanonicalCt CDictCan :: EvVar -> CtFlavor -> Class -> [Xi] -> CanonicalCt cc_id :: CanonicalCt -> EvVar cc_flavor :: CanonicalCt -> CtFlavor cc_class :: CanonicalCt -> Class cc_tyargs :: CanonicalCt -> [Xi] CIPCan :: EvVar -> CtFlavor -> IPName Name -> TcTauType -> CanonicalCt cc_id :: CanonicalCt -> EvVar cc_flavor :: CanonicalCt -> CtFlavor cc_ip_nm :: CanonicalCt -> IPName Name cc_ip_ty :: CanonicalCt -> TcTauType CTyEqCan :: EvVar -> CtFlavor -> TcTyVar -> Xi -> CanonicalCt cc_id :: CanonicalCt -> EvVar cc_flavor :: CanonicalCt -> CtFlavor cc_tyvar :: CanonicalCt -> TcTyVar cc_rhs :: CanonicalCt -> Xi CFunEqCan :: EvVar -> CtFlavor -> TyCon -> [Xi] -> Xi -> CanonicalCt cc_id :: CanonicalCt -> EvVar cc_flavor :: CanonicalCt -> CtFlavor cc_fun :: CanonicalCt -> TyCon cc_tyargs :: CanonicalCt -> [Xi] cc_rhs :: CanonicalCt -> Xi CFrozenErr :: EvVar -> CtFlavor -> CanonicalCt cc_id :: CanonicalCt -> EvVar cc_flavor :: CanonicalCt -> CtFlavor type Xi = Type tyVarsOfCanonical :: CanonicalCt -> TcTyVarSet tyVarsOfCanonicals :: CanonicalCts -> TcTyVarSet tyVarsOfCDicts :: CanonicalCts -> TcTyVarSet deCanonicalise :: CanonicalCt -> FlavoredEvVar mkFrozenError :: CtFlavor -> EvVar -> CanonicalCt isWanted :: CtFlavor -> Bool isGiven :: CtFlavor -> Bool isDerived :: CtFlavor -> Bool isGivenCt :: CanonicalCt -> Bool isWantedCt :: CanonicalCt -> Bool isDerivedCt :: CanonicalCt -> Bool pprFlavorArising :: CtFlavor -> SDoc isFlexiTcsTv :: TyVar -> Bool canRewrite :: CtFlavor -> CtFlavor -> Bool canSolve :: CtFlavor -> CtFlavor -> Bool combineCtLoc :: CtFlavor -> CtFlavor -> WantedLoc mkGivenFlavor :: CtFlavor -> SkolemInfo -> CtFlavor mkWantedFlavor :: CtFlavor -> CtFlavor getWantedLoc :: CanonicalCt -> WantedLoc data TcS a runTcS :: SimplContext -> Untouchables -> TcS a -> TcM (a, Bag EvBind) failTcS :: SDoc -> TcS a panicTcS :: SDoc -> TcS a traceTcS :: String -> SDoc -> TcS () traceFireTcS :: Int -> SDoc -> TcS () bumpStepCountTcS :: TcS () tryTcS :: TcS a -> TcS a nestImplicTcS :: EvBindsVar -> TcsUntouchables -> TcS a -> TcS a recoverTcS :: TcS a -> TcS a -> TcS a wrapErrTcS :: TcM a -> TcS a wrapWarnTcS :: TcM a -> TcS a data SimplContext SimplInfer :: SimplContext SimplRuleLhs :: SimplContext SimplInteractive :: SimplContext SimplCheck :: SimplContext isInteractive :: SimplContext -> Bool simplEqsOnly :: SimplContext -> Bool performDefaulting :: SimplContext -> Bool newEvVar :: TcPredType -> TcS EvVar newCoVar :: TcType -> TcType -> TcS EvVar newGivenCoVar :: TcType -> TcType -> Coercion -> TcS EvVar newDerivedId :: TcPredType -> TcS EvVar newIPVar :: IPName Name -> TcType -> TcS EvVar newDictVar :: Class -> [TcType] -> TcS EvVar newKindConstraint :: TcTyVar -> Kind -> TcS CoVar setCoBind :: CoVar -> Coercion -> TcS () setIPBind :: EvVar -> EvTerm -> TcS () setDictBind :: EvVar -> EvTerm -> TcS () setEvBind :: EvVar -> EvTerm -> TcS () setWantedTyBind :: TcTyVar -> TcType -> TcS () getInstEnvs :: TcS (InstEnv, InstEnv) getFamInstEnvs :: TcS (FamInstEnv, FamInstEnv) getTopEnv :: TcS HscEnv getGblEnv :: TcS TcGblEnv getTcEvBinds :: TcS EvBindsVar getUntouchables :: TcS TcsUntouchables getTcEvBindsBag :: TcS EvBindMap getTcSContext :: TcS SimplContext getTcSTyBinds :: TcS (IORef (TyVarEnv (TcTyVar, TcType))) getTcSTyBindsMap :: TcS (TyVarEnv (TcTyVar, TcType)) newFlattenSkolemTy :: TcType -> TcS TcType instDFunTypes :: [Either TyVar TcType] -> TcS [TcType] instDFunConstraints :: TcThetaType -> TcS [EvVar] newFlexiTcSTy :: Kind -> TcS TcType instFlexiTcS :: TyVar -> TcS TcTyVar compatKind :: Kind -> Kind -> Bool type TcsUntouchables = (Untouchables, TcTyVarSet) isTouchableMetaTyVar :: TcTyVar -> TcS Bool isTouchableMetaTyVar_InRange :: TcsUntouchables -> TcTyVar -> Bool getDefaultInfo :: TcS (SimplContext, [Type], (Bool, Bool)) getDynFlags :: TcS DynFlags matchClass :: Class -> [Type] -> TcS (MatchInstResult (DFunId, [Either TyVar TcType])) matchFam :: TyCon -> [Type] -> TcS (MatchInstResult (TyCon, [Type])) data MatchInstResult mi MatchInstNo :: MatchInstResult mi MatchInstSingle :: mi -> MatchInstResult mi MatchInstMany :: MatchInstResult mi checkWellStagedDFun :: PredType -> DFunId -> WantedLoc -> TcS () warnTcS :: CtLoc orig -> Bool -> SDoc -> TcS () pprEq :: TcType -> TcType -> SDoc instance Eq SimplContext instance Monad TcS instance Functor TcS instance Outputable SimplContext instance Outputable CanonicalCt module TcErrors reportUnsolved :: WantedConstraints -> TcM () warnDefaulting :: [FlavoredEvVar] -> Type -> TcM () unifyCtxt :: EqOrigin -> TidyEnv -> TcM (TidyEnv, SDoc) flattenForAllErrorTcS :: CtFlavor -> TcType -> Bag CanonicalCt -> TcS a solverDepthErrorTcS :: Int -> [CanonicalCt] -> TcS a module TcUnify tcWrapResult :: HsExpr TcId -> TcRhoType -> TcRhoType -> TcM (HsExpr TcId) tcSubType :: CtOrigin -> UserTypeCtxt -> TcSigmaType -> TcSigmaType -> TcM HsWrapper tcGen :: UserTypeCtxt -> TcType -> ([TcTyVar] -> TcRhoType -> TcM result) -> TcM (HsWrapper, result) checkConstraints :: SkolemInfo -> [TcTyVar] -> [EvVar] -> TcM result -> TcM (TcEvBinds, result) newImplication :: SkolemInfo -> [TcTyVar] -> [EvVar] -> TcM result -> TcM (TcEvBinds, result) sigCtxt :: Id -> [TcTyVar] -> TcThetaType -> TcTauType -> TidyEnv -> TcM (TidyEnv, Message) unifyType :: TcTauType -> TcTauType -> TcM CoercionI unifyTypeList :: [TcTauType] -> TcM () unifyTheta :: TcThetaType -> TcThetaType -> TcM [CoercionI] unifyKind :: TcKind -> TcKind -> TcM () tcInfer :: (TcType -> TcM a) -> TcM (a, TcType) matchExpectedListTy :: TcRhoType -> TcM (CoercionI, TcRhoType) matchExpectedPArrTy :: TcRhoType -> TcM (CoercionI, TcRhoType) matchExpectedTyConApp :: TyCon -> TcRhoType -> TcM (CoercionI, [TcSigmaType]) matchExpectedAppTy :: TcRhoType -> TcM (CoercionI, (TcSigmaType, TcSigmaType)) matchExpectedFunTys :: SDoc -> Arity -> TcRhoType -> TcM (CoercionI, [TcSigmaType], TcRhoType) matchExpectedFunKind :: TcKind -> TcM (Maybe (TcKind, TcKind)) wrapFunResCoercion :: [TcType] -> HsWrapper -> TcM HsWrapper instance Outputable SwapFlag module TcHsType tcHsSigType :: UserTypeCtxt -> LHsType Name -> TcM Type tcHsSigTypeNC :: UserTypeCtxt -> LHsType Name -> TcM Type tcHsDeriv :: HsType Name -> TcM ([TyVar], Class, [Type]) tcHsInstHead :: LHsType Name -> TcM ([TyVar], ThetaType, Class, [Type]) tcHsQuantifiedType :: [LHsTyVarBndr Name] -> LHsType Name -> TcM ([TyVar], Type) data UserTypeCtxt FunSigCtxt :: Name -> UserTypeCtxt ExprSigCtxt :: UserTypeCtxt ConArgCtxt :: Name -> UserTypeCtxt TySynCtxt :: Name -> UserTypeCtxt GenPatCtxt :: UserTypeCtxt LamPatSigCtxt :: UserTypeCtxt BindPatSigCtxt :: UserTypeCtxt ResSigCtxt :: UserTypeCtxt ForSigCtxt :: Name -> UserTypeCtxt DefaultDeclCtxt :: UserTypeCtxt SpecInstCtxt :: UserTypeCtxt ThBrackCtxt :: UserTypeCtxt GenSigCtxt :: UserTypeCtxt kcHsTyVars :: [LHsTyVarBndr Name] -> ([LHsTyVarBndr Name] -> TcM r) -> TcM r kcHsSigType :: LHsType Name -> TcM (LHsType Name) kcHsLiftedSigType :: LHsType Name -> TcM (LHsType Name) kcLHsType :: LHsType Name -> TcM (LHsType Name, TcKind) kcCheckLHsType :: LHsType Name -> ExpKind -> TcM (LHsType Name) kcHsContext :: LHsContext Name -> TcM (LHsContext Name) tcHsKindedContext :: LHsContext Name -> TcM ThetaType tcHsKindedType :: LHsType Name -> TcM Type tcHsBangType :: LHsType Name -> TcM Type tcTyVarBndrs :: [LHsTyVarBndr Name] -> ([TyVar] -> TcM r) -> TcM r dsHsType :: LHsType Name -> TcM Type kcHsLPred :: LHsPred Name -> TcM (LHsPred Name) dsHsLPred :: LHsPred Name -> TcM PredType tcDataKindSig :: Maybe Kind -> TcM [TyVar] data ExpKind EK :: TcKind -> EkCtxt -> ExpKind data EkCtxt EkUnk :: EkCtxt EkEqPred :: EkCtxt EkKindSig :: EkCtxt EkArg :: SDoc -> Int -> EkCtxt tcHsPatSigType :: UserTypeCtxt -> LHsType Name -> TcM ([TyVar], Type) tcPatSig :: UserTypeCtxt -> LHsType Name -> TcSigmaType -> TcM (TcType, [(Name, TcType)], HsWrapper) module TcPat tcLetPat :: TcSigFun -> LetBndrSpec -> LPat Name -> TcSigmaType -> TcM a -> TcM (LPat TcId, a) type TcSigFun = Name -> Maybe TcSigInfo data TcSigInfo TcSigInfo :: TcId -> [Name] -> [TcTyVar] -> TcThetaType -> TcSigmaType -> SrcSpan -> TcSigInfo sig_id :: TcSigInfo -> TcId sig_scoped :: TcSigInfo -> [Name] sig_tvs :: TcSigInfo -> [TcTyVar] sig_theta :: TcSigInfo -> TcThetaType sig_tau :: TcSigInfo -> TcSigmaType sig_loc :: TcSigInfo -> SrcSpan type TcPragFun = Name -> [LSig Name] data LetBndrSpec LetLclBndr :: LetBndrSpec LetGblBndr :: TcPragFun -> LetBndrSpec addInlinePrags :: TcId -> [LSig Name] -> TcM TcId warnPrags :: Id -> [LSig Name] -> SDoc -> TcM () tcPat :: HsMatchContext Name -> LPat Name -> TcSigmaType -> TcM a -> TcM (LPat TcId, a) tcPats :: HsMatchContext Name -> [LPat Name] -> [TcSigmaType] -> TcM a -> TcM ([LPat TcId], a) newNoSigLetBndr :: LetBndrSpec -> Name -> TcType -> TcM TcId newSigLetBndr :: LetBndrSpec -> Name -> TcSigInfo -> TcM TcId addDataConStupidTheta :: DataCon -> [TcType] -> TcM () badFieldCon :: DataCon -> Name -> SDoc polyPatSig :: TcType -> SDoc instance Outputable TcSigInfo module RtClosureInspect cvObtainTerm :: HscEnv -> Int -> Bool -> RttiType -> HValue -> IO Term cvReconstructType :: HscEnv -> Int -> GhciType -> HValue -> IO (Maybe Type) improveRTTIType :: HscEnv -> RttiType -> RttiType -> Maybe TvSubst data Term Term :: RttiType -> Either String DataCon -> HValue -> [Term] -> Term ty :: Term -> RttiType dc :: Term -> Either String DataCon val :: Term -> HValue subTerms :: Term -> [Term] Prim :: RttiType -> [Word] -> Term ty :: Term -> RttiType value :: Term -> [Word] Suspension :: ClosureType -> RttiType -> HValue -> Maybe Name -> Term ctype :: Term -> ClosureType ty :: Term -> RttiType val :: Term -> HValue bound_to :: Term -> Maybe Name NewtypeWrap :: RttiType -> Either String DataCon -> Term -> Term ty :: Term -> RttiType dc :: Term -> Either String DataCon wrapped_term :: Term -> Term RefWrap :: RttiType -> Term -> Term ty :: Term -> RttiType wrapped_term :: Term -> Term isTerm :: Term -> Bool isSuspension :: Term -> Bool isPrim :: Term -> Bool isFun :: Term -> Bool isFunLike :: Term -> Bool isNewtypeWrap :: Term -> Bool isFullyEvaluated :: a -> IO Bool isFullyEvaluatedTerm :: Term -> Bool termType :: Term -> RttiType mapTermType :: (RttiType -> Type) -> Term -> Term termTyVars :: Term -> TyVarSet foldTerm :: TermFold a -> Term -> a data TermFold a TermFold :: TermProcessor a a -> (RttiType -> [Word] -> a) -> (ClosureType -> RttiType -> HValue -> Maybe Name -> a) -> (RttiType -> Either String DataCon -> a -> a) -> (RttiType -> a -> a) -> TermFold a fTerm :: TermFold a -> TermProcessor a a fPrim :: TermFold a -> RttiType -> [Word] -> a fSuspension :: TermFold a -> ClosureType -> RttiType -> HValue -> Maybe Name -> a fNewtypeWrap :: TermFold a -> RttiType -> Either String DataCon -> a -> a fRefWrap :: TermFold a -> RttiType -> a -> a foldTermM :: Monad m => TermFoldM m a -> Term -> m a data TermFoldM m a TermFoldM :: TermProcessor a (m a) -> (RttiType -> [Word] -> m a) -> (ClosureType -> RttiType -> HValue -> Maybe Name -> m a) -> (RttiType -> Either String DataCon -> a -> m a) -> (RttiType -> a -> m a) -> TermFoldM m a fTermM :: TermFoldM m a -> TermProcessor a (m a) fPrimM :: TermFoldM m a -> RttiType -> [Word] -> m a fSuspensionM :: TermFoldM m a -> ClosureType -> RttiType -> HValue -> Maybe Name -> m a fNewtypeWrapM :: TermFoldM m a -> RttiType -> Either String DataCon -> a -> m a fRefWrapM :: TermFoldM m a -> RttiType -> a -> m a idTermFold :: TermFold Term pprTerm :: TermPrinter -> TermPrinter -- | Takes a list of custom printers with a explicit recursion knot and a -- term, and returns the output of the first succesful printer, or the -- default printer cPprTerm :: Monad m => CustomTermPrinter m -> Term -> m SDoc cPprTermBase :: Monad m => CustomTermPrinter m type CustomTermPrinter m = TermPrinterM m -> [Precedence -> Term -> (m (Maybe SDoc))] data Closure Closure :: ClosureType -> Ptr () -> StgInfoTable -> Array Int HValue -> [Word] -> Closure tipe :: Closure -> ClosureType infoPtr :: Closure -> Ptr () infoTable :: Closure -> StgInfoTable ptrs :: Closure -> Array Int HValue nonPtrs :: Closure -> [Word] getClosureData :: a -> IO Closure data ClosureType Constr :: ClosureType Fun :: ClosureType Thunk :: Int -> ClosureType ThunkSelector :: ClosureType Blackhole :: ClosureType AP :: ClosureType PAP :: ClosureType Indirection :: Int -> ClosureType MutVar :: Int -> ClosureType MVar :: Int -> ClosureType Other :: Int -> ClosureType isConstr :: ClosureType -> Bool isIndirection :: ClosureType -> Bool instance Show ClosureType instance Eq ClosureType instance Outputable ClosureType instance Outputable Term module TcCanonical mkCanonical :: CtFlavor -> EvVar -> TcS CanonicalCts mkCanonicals :: CtFlavor -> [EvVar] -> TcS CanonicalCts mkCanonicalFEV :: FlavoredEvVar -> TcS CanonicalCts canWanteds :: [WantedEvVar] -> TcS CanonicalCts canGivens :: GivenLoc -> [EvVar] -> TcS CanonicalCts canOccursCheck :: CtFlavor -> TcTyVar -> Xi -> TcS (Maybe Xi) canEq :: CtFlavor -> EvVar -> Type -> Type -> TcS CanonicalCts rewriteWithFunDeps :: [Equation] -> [Xi] -> CtFlavor -> TcS (Maybe ([Xi], [Coercion], CanonicalCts)) module TcInteract solveInteract :: InertSet -> Bag FlavoredEvVar -> TcS (Bool, InertSet) solveInteractGiven :: InertSet -> GivenLoc -> [EvVar] -> TcS InertSet solveInteractWanted :: InertSet -> [WantedEvVar] -> TcS InertSet type AtomicInert = CanonicalCt tyVarsOfInert :: InertSet -> TcTyVarSet data InertSet emptyInert :: InertSet updInertSet :: InertSet -> AtomicInert -> InertSet extractUnsolved :: InertSet -> (InertSet, CanonicalCts) solveOne :: InertSet -> WorkItem -> TcS InertSet instance Outputable StageResult instance Outputable StopOrContinue instance Outputable InertSet module TcSimplify simplifyInfer :: TopLevelFlag -> Bool -> [(Name, TcTauType)] -> WantedConstraints -> TcM ([TcTyVar], [EvVar], TcEvBinds) simplifyDefault :: ThetaType -> TcM () simplifyDeriv :: CtOrigin -> [TyVar] -> ThetaType -> TcM ThetaType simplifyRule :: RuleName -> [TcTyVar] -> WantedConstraints -> WantedConstraints -> TcM ([EvVar], TcEvBinds, TcEvBinds) simplifyTop :: WantedConstraints -> TcM (Bag EvBind) simplifyInteractive :: WantedConstraints -> TcM (Bag EvBind) module TcBinds tcLocalBinds :: HsLocalBinds Name -> TcM thing -> TcM (HsLocalBinds TcId, thing) tcTopBinds :: HsValBinds Name -> TcM (LHsBinds TcId, [LTcSpecPrag], TcLclEnv) tcHsBootSigs :: HsValBinds Name -> TcM [Id] tcPolyBinds :: TopLevelFlag -> SigFun -> PragFun -> RecFlag -> RecFlag -> [LHsBind Name] -> TcM (LHsBinds TcId, [TcId]) type PragFun = Name -> [LSig Name] tcSpecPrags :: Id -> [LSig Name] -> TcM [LTcSpecPrag] mkPragFun :: [LSig Name] -> LHsBinds Name -> PragFun data TcSigInfo TcSigInfo :: TcId -> [Name] -> [TcTyVar] -> TcThetaType -> TcSigmaType -> SrcSpan -> TcSigInfo sig_id :: TcSigInfo -> TcId sig_scoped :: TcSigInfo -> [Name] sig_tvs :: TcSigInfo -> [TcTyVar] sig_theta :: TcSigInfo -> TcThetaType sig_tau :: TcSigInfo -> TcSigmaType sig_loc :: TcSigInfo -> SrcSpan type SigFun = Name -> Maybe ([Name], SrcSpan) mkSigFun :: [LSig Name] -> SigFun badBootDeclErr :: Message instance Outputable GeneralisationPlan module TcMatches tcMatchesFun :: Name -> Bool -> MatchGroup Name -> TcSigmaType -> TcM (HsWrapper, MatchGroup TcId) tcGRHSsPat :: GRHSs Name -> TcRhoType -> TcM (GRHSs TcId) tcMatchesCase :: TcMatchCtxt -> TcRhoType -> MatchGroup Name -> TcRhoType -> TcM (MatchGroup TcId) tcMatchLambda :: MatchGroup Name -> TcRhoType -> TcM (HsWrapper, MatchGroup TcId) data TcMatchCtxt MC :: HsMatchContext Name -> (LHsExpr Name -> TcRhoType -> TcM (LHsExpr TcId)) -> TcMatchCtxt mc_what :: TcMatchCtxt -> HsMatchContext Name mc_body :: TcMatchCtxt -> LHsExpr Name -> TcRhoType -> TcM (LHsExpr TcId) tcStmts :: HsStmtContext Name -> TcStmtChecker -> [LStmt Name] -> TcRhoType -> (TcRhoType -> TcM thing) -> TcM ([LStmt TcId], thing) tcDoStmts :: HsStmtContext Name -> [LStmt Name] -> LHsExpr Name -> TcRhoType -> TcM (HsExpr TcId) tcBody :: LHsExpr Name -> TcRhoType -> TcM (LHsExpr TcId) tcDoStmt :: TcStmtChecker tcMDoStmt :: (LHsExpr Name -> TcM (LHsExpr TcId, TcType)) -> TcStmtChecker tcGuardStmt :: TcStmtChecker module TcArrows tcProc :: InPat Name -> LHsCmdTop Name -> TcRhoType -> TcM (OutPat TcId, LHsCmdTop TcId, CoercionI) module TcExpr tcPolyExpr :: LHsExpr Name -> TcSigmaType -> TcM (LHsExpr TcId) tcPolyExprNC :: LHsExpr Name -> TcSigmaType -> TcM (LHsExpr TcId) tcMonoExpr :: LHsExpr Name -> TcRhoType -> TcM (LHsExpr TcId) tcMonoExprNC :: LHsExpr Name -> TcRhoType -> TcM (LHsExpr TcId) tcInferRho :: LHsExpr Name -> TcM (LHsExpr TcId, TcRhoType) tcInferRhoNC :: LHsExpr Name -> TcM (LHsExpr TcId, TcRhoType) tcSyntaxOp :: CtOrigin -> HsExpr Name -> TcType -> TcM (HsExpr TcId) tcCheckId :: Name -> TcRhoType -> TcM (HsExpr TcId) addExprErrCtxt :: LHsExpr Name -> TcM a -> TcM a module TcAnnotations tcAnnotations :: [LAnnDecl Name] -> TcM [Annotation] module TcForeign tcForeignImports :: [LForeignDecl Name] -> TcM ([Id], [LForeignDecl Id]) tcForeignExports :: [LForeignDecl Name] -> TcM (LHsBinds TcId, [LForeignDecl TcId]) module TcClassDcl tcClassSigs :: Name -> [LSig Name] -> LHsBinds Name -> TcM [TcMethInfo] tcClassDecl2 :: LTyClDecl Name -> TcM (LHsBinds Id) findMethodBind :: Name -> LHsBinds Name -> Maybe (LHsBind Name) instantiateMethod :: Class -> Id -> [TcType] -> TcType tcInstanceMethodBody :: SkolemInfo -> [TcTyVar] -> [EvVar] -> Id -> Id -> SigFun -> TcSpecPrags -> LHsBind Name -> TcM (LHsBind Id) mkGenericDefMethBind :: Class -> [Type] -> Id -> TcM (LHsBind Name) getGenericInstances :: [LTyClDecl Name] -> TcM [InstInfo Name] tcAddDeclCtxt :: TyClDecl Name -> TcM a -> TcM a badMethodErr :: Outputable a => a -> Name -> SDoc badATErr :: Class -> Name -> SDoc omittedATWarn :: Name -> SDoc module TcTyClsDecls tcTyAndClassDecls :: ModDetails -> [[LTyClDecl Name]] -> TcM (TcGblEnv, HsValBinds Name, [Id]) tcFamInstDecl :: TopLevelFlag -> LTyClDecl Name -> TcM TyThing mkRecSelBinds :: [TyThing] -> HsValBinds Name module TcDefaults tcDefaults :: [LDefaultDecl Name] -> TcM (Maybe [Type]) module TcDeriv tcDeriving :: [LTyClDecl Name] -> [LInstDecl Name] -> [LDerivDecl Name] -> TcM ([InstInfo Name], HsValBinds Name, DefUses) module TcInstDcls tcInstDecls1 :: [LTyClDecl Name] -> [LInstDecl Name] -> [LDerivDecl Name] -> TcM (TcGblEnv, [InstInfo Name], HsValBinds Name) tcInstDecls2 :: [LTyClDecl Name] -> [InstInfo Name] -> TcM (LHsBinds Id) module TcRules tcRules :: [LRuleDecl Name] -> TcM [LRuleDecl TcId] module TcRnDriver tcRnStmt :: HscEnv -> InteractiveContext -> LStmt RdrName -> IO (Messages, Maybe ([Id], LHsExpr Id)) tcRnExpr :: HscEnv -> InteractiveContext -> LHsExpr RdrName -> IO (Messages, Maybe Type) tcRnType :: HscEnv -> InteractiveContext -> LHsType RdrName -> IO (Messages, Maybe Kind) tcRnLookupRdrName :: HscEnv -> RdrName -> IO (Messages, Maybe [Name]) -- | ASSUMES that the module is either in the HomePackageTable or is -- a package module with an interface on disk. If neither of these is -- true, then the result will be an error indicating the interface could -- not be found. getModuleExports :: HscEnv -> Module -> IO (Messages, Maybe [AvailInfo]) tcRnLookupName :: HscEnv -> Name -> IO (Messages, Maybe TyThing) tcRnGetInfo :: HscEnv -> Name -> IO (Messages, Maybe (TyThing, Fixity, [Instance])) tcRnModule :: HscEnv -> HscSource -> Bool -> Located (HsModule RdrName) -> IO (Messages, Maybe TcGblEnv) tcTopSrcDecls :: ModDetails -> HsGroup Name -> TcM (TcGblEnv, TcLclEnv) tcRnExtCore :: HscEnv -> HsExtCore RdrName -> IO (Messages, Maybe ModGuts) -- | Main driver for the compiling plain Haskell source code. -- -- This module implements compilation of a Haskell-only source file. It -- is not concerned with preprocessing of source files; this is -- handled in DriverPipeline. module HscMain newHscEnv :: GhcApiCallbacks -> DynFlags -> IO HscEnv hscCmmFile :: GhcMonad m => HscEnv -> FilePath -> m () hscParseIdentifier :: GhcMonad m => DynFlags -> String -> m (Located RdrName) hscSimplify :: GhcMonad m => ModGuts -> m ModGuts hscNormalIface :: GhcMonad m => ModGuts -> Maybe Fingerprint -> m (ModIface, Bool, ModDetails, CgGuts) hscWriteIface :: GhcMonad m => ModIface -> Bool -> ModSummary -> m () -- | Compile to hard-code. hscGenHardCode :: GhcMonad m => CgGuts -> ModSummary -> m Bool hscStmt :: GhcMonad m => HscEnv -> String -> m (Maybe ([Id], HValue)) hscTcExpr :: GhcMonad m => HscEnv -> String -> m Type hscImport :: GhcMonad m => HscEnv -> String -> m (ImportDecl RdrName) -- | Find the kind of a type hscKcType :: GhcMonad m => HscEnv -> String -> m Kind compileExpr :: HscEnv -> SrcSpan -> CoreExpr -> IO HValue data HsCompiler a HsCompiler :: (forall m. GhcMonad m => ModIface -> m a) -> (forall m. GhcMonad m => ModSummary -> Maybe Fingerprint -> m a) -> (forall m. GhcMonad m => TcGblEnv -> ModSummary -> Maybe Fingerprint -> m a) -> (forall m. GhcMonad m => TcGblEnv -> ModSummary -> Maybe Fingerprint -> m a) -> (forall m. GhcMonad m => ModGuts -> ModSummary -> Maybe Fingerprint -> m a) -> HsCompiler a -- | Called when no recompilation is necessary. hscNoRecomp :: HsCompiler a -> forall m. GhcMonad m => ModIface -> m a -- | Called to recompile the module. hscRecompile :: HsCompiler a -> forall m. GhcMonad m => ModSummary -> Maybe Fingerprint -> m a hscBackend :: HsCompiler a -> forall m. GhcMonad m => TcGblEnv -> ModSummary -> Maybe Fingerprint -> m a -- | Code generation for Boot modules. hscGenBootOutput :: HsCompiler a -> forall m. GhcMonad m => TcGblEnv -> ModSummary -> Maybe Fingerprint -> m a -- | Code generation for normal modules. hscGenOutput :: HsCompiler a -> forall m. GhcMonad m => ModGuts -> ModSummary -> Maybe Fingerprint -> m a hscOneShotCompiler :: HsCompiler OneShotResult hscNothingCompiler :: HsCompiler NothingResult hscInteractiveCompiler :: HsCompiler InteractiveResult hscBatchCompiler :: HsCompiler BatchResult hscCompileOneShot :: Compiler OneShotResult hscCompileBatch :: Compiler (HscStatus, ModIface, ModDetails) hscCompileNothing :: Compiler (HscStatus, ModIface, ModDetails) hscCompileInteractive :: Compiler (InteractiveStatus, ModIface, ModDetails) hscCheckRecompBackend :: HsCompiler a -> TcGblEnv -> Compiler a data HscStatus' a HscNoRecomp :: HscStatus' a HscRecomp :: Bool -> a -> HscStatus' a type InteractiveStatus = HscStatus' (Maybe (CompiledByteCode, ModBreaks)) type HscStatus = HscStatus' () -- | parse a file, returning the abstract syntax hscParse :: GhcMonad m => ModSummary -> m (Located (HsModule RdrName)) -- | Rename and typecheck a module hscTypecheck :: GhcMonad m => ModSummary -> Located (HsModule RdrName) -> m TcGblEnv -- | Rename and typecheck a module, additionally returning the renamed -- syntax hscTypecheckRename :: GhcMonad m => ModSummary -> Located (HsModule RdrName) -> m (TcGblEnv, RenamedStuff) -- | Convert a typechecked module to Core hscDesugar :: GhcMonad m => ModSummary -> TcGblEnv -> m ModGuts -- | Make a ModIface from the results of typechecking. Used when not -- optimising, and the interface doesn't need to contain any unfoldings -- or other cross-module optimisation info. ToDo: the old interface is -- only needed to get the version numbers, we should use fingerprint -- versions instead. makeSimpleIface :: GhcMonad m => Maybe ModIface -> TcGblEnv -> ModDetails -> m (ModIface, Bool) -- | Make a ModDetails from the results of typechecking. Used when -- typechecking only, as opposed to full compilation. makeSimpleDetails :: GhcMonad m => TcGblEnv -> m ModDetails module TcSplice kcSpliceType :: HsSplice Name -> FreeVars -> TcM (HsType Name, TcKind) tcSpliceExpr :: HsSplice Name -> TcRhoType -> TcM (HsExpr TcId) tcSpliceDecls :: LHsExpr Name -> TcM [LHsDecl RdrName] tcBracket :: HsBracket Name -> TcRhoType -> TcM (LHsExpr TcId) lookupThName_maybe :: Name -> TcM (Maybe Name) runQuasiQuoteExpr :: HsQuasiQuote RdrName -> RnM (LHsExpr RdrName) runQuasiQuotePat :: HsQuasiQuote RdrName -> RnM (LPat RdrName) runQuasiQuoteDecl :: HsQuasiQuote RdrName -> RnM [LHsDecl RdrName] runQuasiQuoteType :: HsQuasiQuote RdrName -> RnM (LHsType RdrName) runAnnotation :: CoreAnnTarget -> LHsExpr Name -> TcM Annotation instance Quasi (IOEnv (Env TcGblEnv TcLclEnv)) module DriverPipeline oneShot :: GhcMonad m => HscEnv -> Phase -> [(String, Maybe Phase)] -> m () compileFile :: GhcMonad m => HscEnv -> Phase -> (FilePath, Maybe Phase) -> m FilePath linkBinary :: DynFlags -> [FilePath] -> [PackageId] -> IO () -- | Just preprocess a file, put the result in a temp. file (used by the -- compilation manager during the summary phase). -- -- We return the augmented DynFlags, because they contain the result of -- slurping in the OPTIONS pragmas preprocess :: GhcMonad m => HscEnv -> (FilePath, Maybe Phase) -> m (DynFlags, FilePath) -- | Compile -- -- Compile a single module, under the control of the compilation manager. -- -- This is the interface between the compilation manager and the compiler -- proper (hsc), where we deal with tedious details like reading the -- OPTIONS pragma from the source file, and passing the output of hsc -- through the C compiler. -- -- NB. No old interface can also mean that the source has changed. compile :: GhcMonad m => HscEnv -> ModSummary -> Int -> Int -> Maybe ModIface -> Maybe Linkable -> m HomeModInfo compile' :: GhcMonad m => (Compiler m (HscStatus, ModIface, ModDetails), Compiler m (InteractiveStatus, ModIface, ModDetails), Compiler m (HscStatus, ModIface, ModDetails)) -> HscEnv -> ModSummary -> Int -> Int -> Maybe ModIface -> Maybe Linkable -> m HomeModInfo link :: GhcLink -> DynFlags -> Bool -> HomePackageTable -> IO SuccessFlag module InteractiveEval data RunResult -- | names bound by this evaluation RunOk :: [Name] -> RunResult -- | statement failed compilation RunFailed :: RunResult -- | statement raised an exception RunException :: SomeException -> RunResult RunBreak :: ThreadId -> [Name] -> (Maybe BreakInfo) -> RunResult data Status -- | the computation hit a breakpoint (Bool = was an exception) Break :: Bool -> HValue -> BreakInfo -> ThreadId -> Status -- | the computation completed with either an exception or a value Complete :: (Either SomeException [HValue]) -> Status data Resume Resume :: String -> ThreadId -> MVar () -> MVar Status -> [Id] -> [Id] -> HValue -> Maybe BreakInfo -> SrcSpan -> [History] -> Int -> Resume resumeStmt :: Resume -> String resumeThreadId :: Resume -> ThreadId resumeBreakMVar :: Resume -> MVar () resumeStatMVar :: Resume -> MVar Status resumeBindings :: Resume -> [Id] resumeFinalIds :: Resume -> [Id] resumeApStack :: Resume -> HValue resumeBreakInfo :: Resume -> Maybe BreakInfo resumeSpan :: Resume -> SrcSpan resumeHistory :: Resume -> [History] resumeHistoryIx :: Resume -> Int data History History :: HValue -> BreakInfo -> Id -> History historyApStack :: History -> HValue historyBreakInfo :: History -> BreakInfo -- | ^ A cache of the enclosing top level declaration, for convenience historyEnclosingDecl :: History -> Id -- | Run a statement in the current interactive context. Statement may bind -- multple values. runStmt :: GhcMonad m => String -> SingleStep -> m RunResult parseImportDecl :: GhcMonad m => String -> m (ImportDecl RdrName) data SingleStep RunToCompletion :: SingleStep SingleStep :: SingleStep RunAndLogSteps :: SingleStep resume :: GhcMonad m => (SrcSpan -> Bool) -> SingleStep -> m RunResult abandon :: GhcMonad m => m Bool abandonAll :: GhcMonad m => m Bool getResumeContext :: GhcMonad m => m [Resume] getHistorySpan :: HscEnv -> History -> SrcSpan getModBreaks :: HomeModInfo -> ModBreaks getHistoryModule :: History -> Module back :: GhcMonad m => m ([Name], Int, SrcSpan) forward :: GhcMonad m => m ([Name], Int, SrcSpan) -- | Set the interactive evaluation context. -- -- Setting the context doesn't throw away any bindings; the bindings -- we've built up in the InteractiveContext simply move to the new -- module. They always shadow anything in scope in the current context. setContext :: GhcMonad m => [Module] -> [(Module, Maybe (ImportDecl RdrName))] -> m () -- | Get the interactive evaluation context, consisting of a pair of the -- set of modules from which we take the full top-level scope, and the -- set of modules from which we take just the exports respectively. getContext :: GhcMonad m => m ([Module], [(Module, Maybe (ImportDecl RdrName))]) availsToGlobalRdrEnv :: ModuleName -> [AvailInfo] -> GlobalRdrEnv -- | Returns all names in scope in the current interactive context getNamesInScope :: GhcMonad m => m [Name] getRdrNamesInScope :: GhcMonad m => m [RdrName] -- | Returns True if the specified module is interpreted, and -- hence has its full top-level scope available. moduleIsInterpreted :: GhcMonad m => Module -> m Bool -- | Looks up an identifier in the current interactive context (for :info) -- Filter the instances by the ones whose tycons (or clases resp) are in -- scope (qualified or otherwise). Otherwise we list a whole lot too -- many! The exact choice of which ones to show, and which to hide, is a -- judgement call. (see Trac #1581) getInfo :: GhcMonad m => Name -> m (Maybe (TyThing, Fixity, [Instance])) -- | Get the type of an expression exprType :: GhcMonad m => String -> m Type -- | Get the kind of a type typeKind :: GhcMonad m => String -> m Kind -- | Parses a string as an identifier, and returns the list of Names -- that the identifier can refer to in the current interactive context. parseName :: GhcMonad m => String -> m [Name] showModule :: GhcMonad m => ModSummary -> m String isModuleInterpreted :: GhcMonad m => ModSummary -> m Bool compileExpr :: GhcMonad m => String -> m HValue dynCompileExpr :: GhcMonad m => String -> m Dynamic data Term Term :: RttiType -> Either String DataCon -> HValue -> [Term] -> Term ty :: Term -> RttiType dc :: Term -> Either String DataCon val :: Term -> HValue subTerms :: Term -> [Term] Prim :: RttiType -> [Word] -> Term ty :: Term -> RttiType value :: Term -> [Word] Suspension :: ClosureType -> RttiType -> HValue -> Maybe Name -> Term ctype :: Term -> ClosureType ty :: Term -> RttiType val :: Term -> HValue bound_to :: Term -> Maybe Name NewtypeWrap :: RttiType -> Either String DataCon -> Term -> Term ty :: Term -> RttiType dc :: Term -> Either String DataCon wrapped_term :: Term -> Term RefWrap :: RttiType -> Term -> Term ty :: Term -> RttiType wrapped_term :: Term -> Term obtainTermFromId :: HscEnv -> Int -> Bool -> Id -> IO Term obtainTermFromVal :: HscEnv -> Int -> Bool -> Type -> a -> IO Term reconstructType :: HscEnv -> Int -> Id -> IO (Maybe Type) module GHC -- | Install some default exception handlers and run the inner computation. -- Unless you want to handle exceptions yourself, you should wrap this -- around the top level of your program. The default handlers output the -- error message(s) to stderr and exit cleanly. defaultErrorHandler :: (ExceptionMonad m, MonadIO m) => DynFlags -> m a -> m a -- | Install a default cleanup handler to remove temporary files deposited -- by a GHC run. This is seperate from defaultErrorHandler, -- because you might want to override the error handling, but still get -- the ordinary cleanup behaviour. defaultCleanupHandler :: (ExceptionMonad m, MonadIO m) => DynFlags -> m a -> m a -- | A minimal implementation of a GhcMonad. If you need a custom -- monad, e.g., to maintain additional state consider wrapping this monad -- or using GhcT. data Ghc a -- | A monad transformer to add GHC specific features to another monad. -- -- Note that the wrapped monad must support IO and handling of -- exceptions. data GhcT m a -- | A monad that has all the features needed by GHC API calls. -- -- In short, a GHC monad -- -- -- -- If you do not use Ghc or GhcT, make sure to call -- GHC.initGhcMonad before any call to the GHC API functions can -- occur. class (Functor m, MonadIO m, WarnLogMonad m, ExceptionMonad m) => GhcMonad m getSession :: GhcMonad m => m HscEnv setSession :: GhcMonad m => HscEnv -> m () -- | Run function for the Ghc monad. -- -- It initialises the GHC session and warnings via initGhcMonad. -- Each call to this function will create a new session which should not -- be shared among several threads. -- -- Any errors not handled inside the Ghc action are propagated as -- IO exceptions. runGhc :: Maybe FilePath -> Ghc a -> IO a -- | Run function for GhcT monad transformer. -- -- It initialises the GHC session and warnings via initGhcMonad. -- Each call to this function will create a new session which should not -- be shared among several threads. runGhcT :: (ExceptionMonad m, Functor m, MonadIO m) => Maybe FilePath -> GhcT m a -> m a -- | Initialise a GHC session. -- -- If you implement a custom GhcMonad you must call this function -- in the monad run function. It will initialise the session variable and -- clear all warnings. -- -- The first argument should point to the directory where GHC's library -- files reside. More precisely, this should be the output of ghc -- --print-libdir of the version of GHC the module using this API is -- compiled with. For portability, you should use the ghc-paths -- package, available at -- http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ghc-paths. initGhcMonad :: GhcMonad m => Maybe FilePath -> m () -- | Generalised version of catch, allowing an arbitrary exception -- handling monad instead of just IO. gcatch :: (ExceptionMonad m, Exception e) => m a -> (e -> m a) -> m a -- | Generalised version of bracket, allowing an arbitrary exception -- handling monad instead of just IO. gbracket :: ExceptionMonad m => m a -> (a -> m b) -> (a -> m c) -> m c -- | Generalised version of finally, allowing an arbitrary exception -- handling monad instead of just IO. gfinally :: ExceptionMonad m => m a -> m b -> m a -- | Clear the log of Warnings. clearWarnings :: WarnLogMonad m => m () getWarnings :: WarnLogMonad m => m WarningMessages -- | Returns true if there were any warnings. hasWarnings :: WarnLogMonad m => m Bool -- | Print the error message and all warnings. Useful inside exception -- handlers. Clears warnings after printing. printExceptionAndWarnings :: GhcMonad m => SourceError -> m () -- | Print all accumulated warnings using log_action. printWarnings :: GhcMonad m => m () -- | Perform the given action and call the exception handler if the action -- throws a SourceError. See SourceError for more -- information. handleSourceError :: ExceptionMonad m => (SourceError -> m a) -> m a -> m a defaultCallbacks :: GhcApiCallbacks -- | These functions are called in various places of the GHC API. -- -- API clients can override any of these callbacks to change GHC's -- default behaviour. data GhcApiCallbacks GhcApiCallbacks :: (forall m. GhcMonad m => ModSummary -> Maybe SourceError -> m ()) -> GhcApiCallbacks -- | Called by load after the compilating of each module. -- -- The default implementation simply prints all warnings and errors to -- stderr. Don't forget to call clearWarnings when -- implementing your own call. -- -- The first argument is the module that was compiled. -- -- The second argument is Nothing if no errors occured, but -- there may have been warnings. If it is Just err at least one -- error has occured. If srcErrorMessages is empty, compilation -- failed due to -Werror. reportModuleCompilationResult :: GhcApiCallbacks -> forall m. GhcMonad m => ModSummary -> Maybe SourceError -> m () -- | Determines whether a set of modules requires Template Haskell. -- -- Note that if the session's DynFlags enabled Template Haskell -- when depanal was called, then each module in the returned -- module graph will have Template Haskell enabled whether it is actually -- needed or not. needsTemplateHaskell :: ModuleGraph -> Bool -- | Contains not only a collection of DynFlags but also a plethora -- of information relating to the compilation of a single file or GHC -- session data DynFlags DynFlags :: GhcMode -> GhcLink -> HscTarget -> String -> String -> Int -> Int -> Int -> Int -> Maybe String -> Maybe String -> [Int] -> Maybe Int -> Maybe Int -> Maybe Int -> Maybe Int -> Platform -> Int -> [String] -> [FilePath] -> Module -> Maybe String -> Int -> DPHBackend -> PackageId -> [Way] -> String -> String -> Maybe (String, Int) -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> String -> String -> String -> Maybe String -> Maybe String -> DynLibLoader -> Maybe FilePath -> Maybe FilePath -> [String] -> [String] -> [String] -> [String] -> String -> FilePath -> FilePath -> Maybe String -> RtsOptsEnabled -> String -> [String] -> [String] -> [String] -> [String] -> [String] -> [String] -> [String] -> [String] -> [String] -> [String] -> String -> (String, [Option]) -> String -> (String, [Option]) -> (String, [Option]) -> (String, [Option]) -> (String, [Option]) -> (String, [Option]) -> (String, [Option]) -> String -> String -> String -> (String, [Option]) -> (String, [Option]) -> FilePath -> Bool -> [ModuleName] -> [String] -> [FilePath] -> FilePath -> FilePath -> [PackageFlag] -> Maybe [PackageConfig] -> PackageState -> IORef [FilePath] -> IORef (Map FilePath FilePath) -> [DynFlag] -> Maybe Language -> [OnOff ExtensionFlag] -> [ExtensionFlag] -> (Severity -> SrcSpan -> PprStyle -> Message -> IO ()) -> Maybe String -> DynFlags ghcMode :: DynFlags -> GhcMode ghcLink :: DynFlags -> GhcLink hscTarget :: DynFlags -> HscTarget -- | Name of the output file hscOutName :: DynFlags -> String -- | Name of the .hcr output file extCoreName :: DynFlags -> String -- | Verbosity level: see Note [Verbosity levels] verbosity :: DynFlags -> Int -- | Optimisation level optLevel :: DynFlags -> Int -- | Number of simplifier phases simplPhases :: DynFlags -> Int -- | Max simplifier iterations maxSimplIterations :: DynFlags -> Int shouldDumpSimplPhase :: DynFlags -> Maybe String ruleCheck :: DynFlags -> Maybe String -- | Additional demand analysis strictnessBefore :: DynFlags -> [Int] -- | Threshold for SpecConstr specConstrThreshold :: DynFlags -> Maybe Int -- | Max number of specialisations for any one function specConstrCount :: DynFlags -> Maybe Int -- | Threshold for LiberateCase liberateCaseThreshold :: DynFlags -> Maybe Int -- | Arg count for lambda floating See CoreMonad.FloatOutSwitches floatLamArgs :: DynFlags -> Maybe Int -- | The platform we're compiling for. Used by the NCG. targetPlatform :: DynFlags -> Platform stolen_x86_regs :: DynFlags -> Int -- |
--   -#includes
--   
cmdlineHcIncludes :: DynFlags -> [String] importPaths :: DynFlags -> [FilePath] mainModIs :: DynFlags -> Module mainFunIs :: DynFlags -> Maybe String -- | Typechecker context stack depth ctxtStkDepth :: DynFlags -> Int dphBackend :: DynFlags -> DPHBackend -- | name of package currently being compiled thisPackage :: DynFlags -> PackageId -- | Way flags from the command line ways :: DynFlags -> [Way] -- | The global "way" (e.g. "p" for prof) buildTag :: DynFlags -> String -- | The RTS "way" rtsBuildTag :: DynFlags -> String splitInfo :: DynFlags -> Maybe (String, Int) objectDir :: DynFlags -> Maybe String dylibInstallName :: DynFlags -> Maybe String hiDir :: DynFlags -> Maybe String stubDir :: DynFlags -> Maybe String objectSuf :: DynFlags -> String hcSuf :: DynFlags -> String hiSuf :: DynFlags -> String outputFile :: DynFlags -> Maybe String outputHi :: DynFlags -> Maybe String dynLibLoader :: DynFlags -> DynLibLoader -- | This is set by DriverPipeline.runPipeline based on where its -- output is going. dumpPrefix :: DynFlags -> Maybe FilePath -- | Override the dumpPrefix set by -- DriverPipeline.runPipeline. Set by -- -ddump-file-prefix dumpPrefixForce :: DynFlags -> Maybe FilePath includePaths :: DynFlags -> [String] libraryPaths :: DynFlags -> [String] frameworkPaths :: DynFlags -> [String] cmdlineFrameworks :: DynFlags -> [String] tmpDir :: DynFlags -> String ghcUsagePath :: DynFlags -> FilePath ghciUsagePath :: DynFlags -> FilePath rtsOpts :: DynFlags -> Maybe String rtsOptsEnabled :: DynFlags -> RtsOptsEnabled -- | Path to store the .mix files hpcDir :: DynFlags -> String opt_L :: DynFlags -> [String] opt_P :: DynFlags -> [String] opt_F :: DynFlags -> [String] opt_c :: DynFlags -> [String] opt_m :: DynFlags -> [String] opt_a :: DynFlags -> [String] opt_l :: DynFlags -> [String] opt_windres :: DynFlags -> [String] opt_lo :: DynFlags -> [String] opt_lc :: DynFlags -> [String] pgm_L :: DynFlags -> String pgm_P :: DynFlags -> (String, [Option]) pgm_F :: DynFlags -> String pgm_c :: DynFlags -> (String, [Option]) pgm_m :: DynFlags -> (String, [Option]) pgm_s :: DynFlags -> (String, [Option]) pgm_a :: DynFlags -> (String, [Option]) pgm_l :: DynFlags -> (String, [Option]) pgm_dll :: DynFlags -> (String, [Option]) pgm_T :: DynFlags -> String pgm_sysman :: DynFlags -> String pgm_windres :: DynFlags -> String pgm_lo :: DynFlags -> (String, [Option]) pgm_lc :: DynFlags -> (String, [Option]) depMakefile :: DynFlags -> FilePath depIncludePkgDeps :: DynFlags -> Bool depExcludeMods :: DynFlags -> [ModuleName] depSuffixes :: DynFlags -> [String] extraPkgConfs :: DynFlags -> [FilePath] topDir :: DynFlags -> FilePath -- | The -package-conf flags given on the command line, in the -- order they appeared. systemPackageConfig :: DynFlags -> FilePath -- | The -package and -hide-package flags from the -- command-line packageFlags :: DynFlags -> [PackageFlag] pkgDatabase :: DynFlags -> Maybe [PackageConfig] pkgState :: DynFlags -> PackageState filesToClean :: DynFlags -> IORef [FilePath] dirsToClean :: DynFlags -> IORef (Map FilePath FilePath) flags :: DynFlags -> [DynFlag] language :: DynFlags -> Maybe Language extensions :: DynFlags -> [OnOff ExtensionFlag] extensionFlags :: DynFlags -> [ExtensionFlag] -- | Message output action: use ErrUtils instead of this if you can log_action :: DynFlags -> Severity -> SrcSpan -> PprStyle -> Message -> IO () haddockOptions :: DynFlags -> Maybe String -- | Enumerates the simple on-or-off dynamic flags data DynFlag Opt_D_dump_cmm :: DynFlag Opt_D_dump_cmmz :: DynFlag Opt_D_dump_cmmz_pretty :: DynFlag Opt_D_dump_cps_cmm :: DynFlag Opt_D_dump_cvt_cmm :: DynFlag Opt_D_dump_asm :: DynFlag Opt_D_dump_asm_native :: DynFlag Opt_D_dump_asm_liveness :: DynFlag Opt_D_dump_asm_coalesce :: DynFlag Opt_D_dump_asm_regalloc :: DynFlag Opt_D_dump_asm_regalloc_stages :: DynFlag Opt_D_dump_asm_conflicts :: DynFlag Opt_D_dump_asm_stats :: DynFlag Opt_D_dump_asm_expanded :: DynFlag Opt_D_dump_llvm :: DynFlag Opt_D_dump_cpranal :: DynFlag Opt_D_dump_deriv :: DynFlag Opt_D_dump_ds :: DynFlag Opt_D_dump_flatC :: DynFlag Opt_D_dump_foreign :: DynFlag Opt_D_dump_inlinings :: DynFlag Opt_D_dump_rule_firings :: DynFlag Opt_D_dump_occur_anal :: DynFlag Opt_D_dump_parsed :: DynFlag Opt_D_dump_rn :: DynFlag Opt_D_dump_simpl :: DynFlag Opt_D_dump_simpl_iterations :: DynFlag Opt_D_dump_simpl_phases :: DynFlag Opt_D_dump_spec :: DynFlag Opt_D_dump_prep :: DynFlag Opt_D_dump_stg :: DynFlag Opt_D_dump_stranal :: DynFlag Opt_D_dump_tc :: DynFlag Opt_D_dump_types :: DynFlag Opt_D_dump_rules :: DynFlag Opt_D_dump_cse :: DynFlag Opt_D_dump_worker_wrapper :: DynFlag Opt_D_dump_rn_trace :: DynFlag Opt_D_dump_rn_stats :: DynFlag Opt_D_dump_opt_cmm :: DynFlag Opt_D_dump_simpl_stats :: DynFlag Opt_D_dump_cs_trace :: DynFlag Opt_D_dump_tc_trace :: DynFlag Opt_D_dump_if_trace :: DynFlag Opt_D_dump_splices :: DynFlag Opt_D_dump_BCOs :: DynFlag Opt_D_dump_vect :: DynFlag Opt_D_dump_hpc :: DynFlag Opt_D_dump_rtti :: DynFlag Opt_D_source_stats :: DynFlag Opt_D_verbose_core2core :: DynFlag Opt_D_verbose_stg2stg :: DynFlag Opt_D_dump_hi :: DynFlag Opt_D_dump_hi_diffs :: DynFlag Opt_D_dump_minimal_imports :: DynFlag Opt_D_dump_mod_cycles :: DynFlag Opt_D_dump_view_pattern_commoning :: DynFlag Opt_D_faststring_stats :: DynFlag -- | Append dump output to files instead of stdout. Opt_DumpToFile :: DynFlag Opt_D_no_debug_output :: DynFlag Opt_DoCoreLinting :: DynFlag Opt_DoStgLinting :: DynFlag Opt_DoCmmLinting :: DynFlag Opt_DoAsmLinting :: DynFlag Opt_WarnIsError :: DynFlag Opt_WarnDuplicateExports :: DynFlag Opt_WarnHiShadows :: DynFlag Opt_WarnImplicitPrelude :: DynFlag Opt_WarnIncompletePatterns :: DynFlag Opt_WarnIncompletePatternsRecUpd :: DynFlag Opt_WarnMissingFields :: DynFlag Opt_WarnMissingImportList :: DynFlag Opt_WarnMissingMethods :: DynFlag Opt_WarnMissingSigs :: DynFlag Opt_WarnMissingLocalSigs :: DynFlag Opt_WarnNameShadowing :: DynFlag Opt_WarnOverlappingPatterns :: DynFlag Opt_WarnTypeDefaults :: DynFlag Opt_WarnMonomorphism :: DynFlag Opt_WarnUnusedBinds :: DynFlag Opt_WarnUnusedImports :: DynFlag Opt_WarnUnusedMatches :: DynFlag Opt_WarnWarningsDeprecations :: DynFlag Opt_WarnDeprecatedFlags :: DynFlag Opt_WarnDodgyExports :: DynFlag Opt_WarnDodgyImports :: DynFlag Opt_WarnOrphans :: DynFlag Opt_WarnAutoOrphans :: DynFlag Opt_WarnTabs :: DynFlag Opt_WarnUnrecognisedPragmas :: DynFlag Opt_WarnDodgyForeignImports :: DynFlag Opt_WarnLazyUnliftedBindings :: DynFlag Opt_WarnUnusedDoBind :: DynFlag Opt_WarnWrongDoBind :: DynFlag Opt_WarnAlternativeLayoutRuleTransitional :: DynFlag Opt_PrintExplicitForalls :: DynFlag Opt_Strictness :: DynFlag Opt_FullLaziness :: DynFlag Opt_FloatIn :: DynFlag Opt_Specialise :: DynFlag Opt_StaticArgumentTransformation :: DynFlag Opt_CSE :: DynFlag Opt_LiberateCase :: DynFlag Opt_SpecConstr :: DynFlag Opt_DoLambdaEtaExpansion :: DynFlag Opt_IgnoreAsserts :: DynFlag Opt_DoEtaReduction :: DynFlag Opt_CaseMerge :: DynFlag Opt_UnboxStrictFields :: DynFlag Opt_MethodSharing :: DynFlag Opt_DictsCheap :: DynFlag Opt_EnableRewriteRules :: DynFlag Opt_Vectorise :: DynFlag Opt_RegsGraph :: DynFlag Opt_RegsIterative :: DynFlag Opt_IgnoreInterfacePragmas :: DynFlag Opt_OmitInterfacePragmas :: DynFlag Opt_ExposeAllUnfoldings :: DynFlag Opt_AutoSccsOnAllToplevs :: DynFlag Opt_AutoSccsOnExportedToplevs :: DynFlag Opt_AutoSccsOnIndividualCafs :: DynFlag Opt_Pp :: DynFlag Opt_ForceRecomp :: DynFlag Opt_DryRun :: DynFlag Opt_DoAsmMangling :: DynFlag Opt_ExcessPrecision :: DynFlag Opt_EagerBlackHoling :: DynFlag Opt_ReadUserPackageConf :: DynFlag Opt_NoHsMain :: DynFlag Opt_SplitObjs :: DynFlag Opt_StgStats :: DynFlag Opt_HideAllPackages :: DynFlag Opt_PrintBindResult :: DynFlag Opt_Haddock :: DynFlag Opt_HaddockOptions :: DynFlag Opt_Hpc_No_Auto :: DynFlag Opt_BreakOnException :: DynFlag Opt_BreakOnError :: DynFlag Opt_PrintEvldWithShow :: DynFlag Opt_PrintBindContents :: DynFlag Opt_GenManifest :: DynFlag Opt_EmbedManifest :: DynFlag Opt_EmitExternalCore :: DynFlag Opt_SharedImplib :: DynFlag Opt_BuildingCabalPackage :: DynFlag Opt_SSE2 :: DynFlag Opt_GhciSandbox :: DynFlag Opt_RunCPS :: DynFlag Opt_RunCPSZ :: DynFlag Opt_ConvertToZipCfgAndBack :: DynFlag Opt_AutoLinkPackages :: DynFlag Opt_ImplicitImportQualified :: DynFlag Opt_TryNewCodeGen :: DynFlag Opt_KeepHiDiffs :: DynFlag Opt_KeepHcFiles :: DynFlag Opt_KeepSFiles :: DynFlag Opt_KeepRawSFiles :: DynFlag Opt_KeepTmpFiles :: DynFlag Opt_KeepRawTokenStream :: DynFlag Opt_KeepLlvmFiles :: DynFlag data Severity SevOutput :: Severity SevInfo :: Severity SevWarning :: Severity SevError :: Severity SevFatal :: Severity -- | The target code type of the compilation (if any). -- -- Whenever you change the target, also make sure to set ghcLink -- to something sensible. -- -- HscNothing can be used to avoid generating any output, however, -- note that: -- -- data HscTarget -- | Generate C code. HscC :: HscTarget -- | Generate assembly using the native code generator. HscAsm :: HscTarget -- | Generate assembly using the llvm code generator. HscLlvm :: HscTarget -- | Generate Java bytecode. HscJava :: HscTarget -- | Generate bytecode. (Requires LinkInMemory) HscInterpreted :: HscTarget -- | Don't generate any code. See notes above. HscNothing :: HscTarget -- | Test whether a DynFlag is set dopt :: DynFlag -> DynFlags -> Bool -- | The GhcMode tells us whether we're doing multi-module -- compilation (controlled via the GHC API) or one-shot -- (single-module) compilation. This makes a difference primarily to the -- Finder: in one-shot mode we look for interface files for -- imported modules, but in multi-module mode we look for source files in -- order to check whether they need to be recompiled. data GhcMode -- | --make, GHCi, etc. CompManager :: GhcMode -- |
--   ghc -c Foo.hs
--   
OneShot :: GhcMode -- | ghc -M, see Finder for why we need this MkDepend :: GhcMode -- | What to do in the link step, if there is one. data GhcLink -- | Don't link at all NoLink :: GhcLink -- | Link object code into a binary LinkBinary :: GhcLink -- | Use the in-memory dynamic linker (works for both bytecode and object -- code). LinkInMemory :: GhcLink -- | Link objects into a dynamic lib (DLL on Windows, DSO on ELF platforms) LinkDynLib :: GhcLink -- | The HscTarget value corresponding to the default way to create -- object files on the current platform. defaultObjectTarget :: HscTarget -- | Parse dynamic flags from a list of command line arguments. Returns the -- the parsed DynFlags, the left-over arguments, and a list of -- warnings. Throws a UsageError if errors occurred during parsing -- (such as unknown flags or missing arguments). parseDynamicFlags :: Monad m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Located String]) -- | Grabs the DynFlags from the Session getSessionDynFlags :: GhcMonad m => m DynFlags -- | Updates the DynFlags in a Session. This also reads the package -- database (unless it has already been read), and prepares the compilers -- knowledge about packages. It can be called again to load new packages: -- just add new package flags to (packageFlags dflags). -- -- Returns a list of new packages that may need to be linked in using the -- dynamic linker (see linkPackages) as a result of new package -- flags. If you are not doing linking or doing static linking, you can -- ignore the list of packages returned. setSessionDynFlags :: GhcMonad m => DynFlags -> m [PackageId] -- | Parses GHC's static flags from a list of command line arguments. -- -- These flags are static in the sense that they can be set only once and -- they are global, meaning that they affect every instance of GHC -- running; multiple GHC threads will use the same flags. -- -- This function must be called before any session is started, i.e., -- before the first call to GHC.withGhc. -- -- Static flags are more of a hack and are static for more or less -- historical reasons. In the long run, most static flags should -- eventually become dynamic flags. -- -- XXX: can we add an auto-generated list of static flags here? parseStaticFlags :: [Located String] -> IO ([Located String], [Located String]) -- | A compilation target. -- -- A target may be supplied with the actual text of the module. If so, -- use this instead of the file contents (this is for use in an IDE where -- the file hasn't been saved by the user yet). data Target Target :: TargetId -> Bool -> Maybe (StringBuffer, ClockTime) -> Target -- | module or filename targetId :: Target -> TargetId -- | object code allowed? targetAllowObjCode :: Target -> Bool -- | in-memory text buffer? targetContents :: Target -> Maybe (StringBuffer, ClockTime) data TargetId -- | A module name: search for the file TargetModule :: ModuleName -> TargetId -- | A filename: preprocess & parse it to find the module name. If -- specified, the Phase indicates how to compile this file (which phase -- to start from). Nothing indicates the starting phase should be -- determined from the suffix of the filename. TargetFile :: FilePath -> (Maybe Phase) -> TargetId data Phase -- | Sets the targets for this session. Each target may be a module name or -- a filename. The targets correspond to the set of root modules for the -- program/library. Unloading the current program is achieved by setting -- the current set of targets to be empty, followed by load. setTargets :: GhcMonad m => [Target] -> m () -- | Returns the current set of targets getTargets :: GhcMonad m => m [Target] -- | Add another target. addTarget :: GhcMonad m => Target -> m () -- | Remove a target removeTarget :: GhcMonad m => TargetId -> m () -- | Attempts to guess what Target a string refers to. This function -- implements the --make/GHCi command-line syntax for filenames: -- -- guessTarget :: GhcMonad m => String -> Maybe Phase -> m Target -- | Perform a dependency analysis starting from the current targets and -- update the session with the new module graph. -- -- Dependency analysis entails parsing the import directives and -- may therefore require running certain preprocessors. -- -- Note that each ModSummary in the module graph caches its -- DynFlags. These DynFlags are determined by the -- current session DynFlags and the OPTIONS and -- LANGUAGE pragmas of the parsed module. Thus if you want to -- changes to the DynFlags to take effect you need to call this -- function again. depanal :: GhcMonad m => [ModuleName] -> Bool -> m ModuleGraph -- | Try to load the program. See LoadHowMuch for the different -- modes. -- -- This function implements the core of GHC's --make mode. It -- preprocesses, compiles and loads the specified modules, avoiding -- re-compilation wherever possible. Depending on the target (see -- hscTarget) compilating and loading may result in files being -- created on disk. -- -- Calls the reportModuleCompilationResult callback after each -- compiling each module, whether successful or not. -- -- Throw a SourceError if errors are encountered before the actual -- compilation starts (e.g., during dependency analysis). All other -- errors are reported using the callback. load :: GhcMonad m => LoadHowMuch -> m SuccessFlag -- | Try to load the program. If a Module is supplied, then just attempt to -- load up to this target. If no Module is supplied, then try to load all -- targets. -- -- The first argument is a function that is called after compiling each -- module to print wanrings and errors. -- -- While compiling a module, all SourceErrors are caught and -- passed to the logger, however, this function may still throw a -- SourceError if dependency analysis failed (e.g., due to a parse -- error). loadWithLogger :: GhcMonad m => WarnErrLogger -> LoadHowMuch -> m SuccessFlag -- | Describes which modules of the module graph need to be loaded. data LoadHowMuch -- | Load all targets and its dependencies. LoadAllTargets :: LoadHowMuch -- | Load only the given module and its dependencies. LoadUpTo :: ModuleName -> LoadHowMuch -- | Load only the dependencies of the given module, but not the module -- itself. LoadDependenciesOf :: ModuleName -> LoadHowMuch data SuccessFlag Succeeded :: SuccessFlag Failed :: SuccessFlag succeeded :: SuccessFlag -> Bool failed :: SuccessFlag -> Bool defaultWarnErrLogger :: WarnErrLogger -- | A function called to log warnings and errors. type WarnErrLogger = GhcMonad m => Maybe SourceError -> m () -- | Inform GHC that the working directory has changed. GHC will flush its -- cache of module locations, since it may no longer be valid. -- -- Note: Before changing the working directory make sure all threads -- running in the same session have stopped. If you change the working -- directory, you should also unload the current program (set targets to -- empty, followed by load). workingDirectoryChanged :: GhcMonad m => m () -- | Parse a module. -- -- Throws a SourceError on parse error. parseModule :: GhcMonad m => ModSummary -> m ParsedModule -- | Typecheck and rename a parsed module. -- -- Throws a SourceError if either fails. typecheckModule :: GhcMonad m => ParsedModule -> m TypecheckedModule -- | Desugar a typechecked module. desugarModule :: GhcMonad m => TypecheckedModule -> m DesugaredModule -- | Load a module. Input doesn't need to be desugared. -- -- A module must be loaded before dependent modules can be typechecked. -- This always includes generating a ModIface and, depending on -- the hscTarget, may also include code generation. -- -- This function will always cause recompilation and will always -- overwrite previous compilation results (potentially files on disk). loadModule :: (TypecheckedMod mod, GhcMonad m) => mod -> m mod -- | The result of successful parsing. data ParsedModule ParsedModule :: ModSummary -> ParsedSource -> ParsedModule pm_mod_summary :: ParsedModule -> ModSummary pm_parsed_source :: ParsedModule -> ParsedSource -- | The result of successful typechecking. It also contains the parser -- result. data TypecheckedModule TypecheckedModule :: ParsedModule -> Maybe RenamedSource -> TypecheckedSource -> ModuleInfo -> (TcGblEnv, ModDetails) -> TypecheckedModule tm_parsed_module :: TypecheckedModule -> ParsedModule tm_renamed_source :: TypecheckedModule -> Maybe RenamedSource tm_typechecked_source :: TypecheckedModule -> TypecheckedSource tm_checked_module_info :: TypecheckedModule -> ModuleInfo tm_internals_ :: TypecheckedModule -> (TcGblEnv, ModDetails) -- | The result of successful desugaring (i.e., translation to core). Also -- contains all the information of a typechecked module. data DesugaredModule DesugaredModule :: TypecheckedModule -> ModGuts -> DesugaredModule dm_typechecked_module :: DesugaredModule -> TypecheckedModule dm_core_module :: DesugaredModule -> ModGuts type TypecheckedSource = LHsBinds Id type ParsedSource = Located (HsModule RdrName) type RenamedSource = (HsGroup Name, [LImportDecl Name], Maybe [LIE Name], Maybe LHsDocString) class ParsedMod m => TypecheckedMod m renamedSource :: TypecheckedMod m => m -> Maybe RenamedSource typecheckedSource :: TypecheckedMod m => m -> TypecheckedSource moduleInfo :: TypecheckedMod m => m -> ModuleInfo class ParsedMod m parsedSource :: ParsedMod m => m -> ParsedSource coreModule :: DesugaredMod m => m -> ModGuts -- | This is the way to get access to the Core bindings corresponding to a -- module. compileToCore parses, typechecks, and desugars the -- module, then returns the resulting Core module (consisting of the -- module name, type declarations, and function declarations) if -- successful. compileToCoreModule :: GhcMonad m => FilePath -> m CoreModule -- | Like compileToCoreModule, but invokes the simplifier, so as to return -- simplified and tidied Core. compileToCoreSimplified :: GhcMonad m => FilePath -> m CoreModule -- | Takes a CoreModule and compiles the bindings therein to object code. -- The first argument is a bool flag indicating whether to run the -- simplifier. The resulting .o, .hi, and executable files, if any, are -- stored in the current directory, and named according to the module -- name. This has only so far been tested with a single self-contained -- module. compileCoreToObj :: GhcMonad m => Bool -> CoreModule -> m () -- | Return the ModSummary of a module with the given name. -- -- The module must be part of the module graph (see hsc_mod_graph -- and ModuleGraph). If this is not the case, this function will -- throw a GhcApiError. -- -- This function ignores boot modules and requires that there is only one -- non-boot module with the given name. getModSummary :: GhcMonad m => ModuleName -> m ModSummary -- | A ModuleGraph contains all the nodes from the home package (only). -- There will be a node for each source module, plus a node for each -- hi-boot module. -- -- The graph is not necessarily stored in topologically-sorted order. Use -- GHC.topSortModuleGraph and Digraph.flattenSCC to -- achieve this. type ModuleGraph = [ModSummary] -- | A single node in a 'ModuleGraph. The nodes of the module graph are one -- of: -- -- data ModSummary ModSummary :: Module -> HscSource -> ModLocation -> ClockTime -> Maybe ClockTime -> [Located (ImportDecl RdrName)] -> [Located (ImportDecl RdrName)] -> FilePath -> DynFlags -> Maybe StringBuffer -> ModSummary -- | Identity of the module ms_mod :: ModSummary -> Module -- | The module source either plain Haskell, hs-boot or external core ms_hsc_src :: ModSummary -> HscSource -- | Location of the various files belonging to the module ms_location :: ModSummary -> ModLocation -- | Timestamp of source file ms_hs_date :: ModSummary -> ClockTime -- | Timestamp of object, if we have one ms_obj_date :: ModSummary -> Maybe ClockTime -- | Source imports of the module ms_srcimps :: ModSummary -> [Located (ImportDecl RdrName)] -- | Non-source imports of the module ms_imps :: ModSummary -> [Located (ImportDecl RdrName)] -- | Filename of preprocessed source file ms_hspp_file :: ModSummary -> FilePath -- | Cached flags from OPTIONS, INCLUDE and -- LANGUAGE pragmas in the modules source code ms_hspp_opts :: ModSummary -> DynFlags -- | The actual preprocessed source, if we have it ms_hspp_buf :: ModSummary -> Maybe StringBuffer ms_mod_name :: ModSummary -> ModuleName -- | Where a module lives on the file system: the actual locations of the -- .hs, .hi and .o files, if we have them data ModLocation ModLocation :: Maybe FilePath -> FilePath -> FilePath -> ModLocation ml_hs_file :: ModLocation -> Maybe FilePath ml_hi_file :: ModLocation -> FilePath ml_obj_file :: ModLocation -> FilePath -- | Get the module dependency graph. getModuleGraph :: GhcMonad m => m ModuleGraph -- | Return True == module is loaded. isLoaded :: GhcMonad m => ModuleName -> m Bool -- | Calculate SCCs of the module graph, possibly dropping the hi-boot -- nodes The resulting list of strongly-connected-components is in -- topologically sorted order, starting with the module(s) at the bottom -- of the dependency graph (ie compile them first) and ending with the -- ones at the top. -- -- Drop hi-boot nodes (first boolean arg)? -- -- topSortModuleGraph :: Bool -> [ModSummary] -> Maybe ModuleName -> [SCC ModSummary] -- | Container for information about a Module. data ModuleInfo -- | Request information about a loaded Module getModuleInfo :: GhcMonad m => Module -> m (Maybe ModuleInfo) -- | The list of top-level entities defined in a module modInfoTyThings :: ModuleInfo -> [TyThing] modInfoTopLevelScope :: ModuleInfo -> Maybe [Name] modInfoExports :: ModuleInfo -> [Name] -- | Returns the instances defined by the specified module. Warning: -- currently unimplemented for package modules. modInfoInstances :: ModuleInfo -> [Instance] modInfoIsExportedName :: ModuleInfo -> Name -> Bool modInfoLookupName :: GhcMonad m => ModuleInfo -> Name -> m (Maybe TyThing) -- | Looks up a global name: that is, any top-level name in any visible -- module. Unlike lookupName, lookupGlobalName does not use the -- interactive context, and therefore does not require a preceding -- setContext. lookupGlobalName :: GhcMonad m => Name -> m (Maybe TyThing) findGlobalAnns :: (GhcMonad m, Typeable a) => ([Word8] -> a) -> AnnTarget Name -> m [a] mkPrintUnqualifiedForModule :: GhcMonad m => ModuleInfo -> m (Maybe PrintUnqualified) -- | Return all external modules available in the package database. -- Modules from the current session (i.e., from the -- HomePackageTable) are not included. packageDbModules :: GhcMonad m => Bool -> m [Module] type PrintUnqualified = (QueryQualifyName, QueryQualifyModule) alwaysQualify :: PrintUnqualified -- | Return the bindings for the current interactive session. getBindings :: GhcMonad m => m [TyThing] getPrintUnqual :: GhcMonad m => m PrintUnqualified -- | Takes a ModuleName and possibly a PackageId, and -- consults the filesystem and package database to find the corresponding -- Module, using the algorithm that is used for an import -- declaration. findModule :: GhcMonad m => ModuleName -> Maybe FastString -> m Module -- | Like findModule, but differs slightly when the module refers to -- a source file, and the file has not been loaded via load. In -- this case, findModule will throw an error (module not loaded), -- but lookupModule will check to see whether the module can also -- be found in a package, and if so, that package Module will be -- returned. If not, the usual module-not-found error will be thrown. lookupModule :: GhcMonad m => ModuleName -> Maybe FastString -> m Module -- | Set the interactive evaluation context. -- -- Setting the context doesn't throw away any bindings; the bindings -- we've built up in the InteractiveContext simply move to the new -- module. They always shadow anything in scope in the current context. setContext :: GhcMonad m => [Module] -> [(Module, Maybe (ImportDecl RdrName))] -> m () -- | Get the interactive evaluation context, consisting of a pair of the -- set of modules from which we take the full top-level scope, and the -- set of modules from which we take just the exports respectively. getContext :: GhcMonad m => m ([Module], [(Module, Maybe (ImportDecl RdrName))]) -- | Returns all names in scope in the current interactive context getNamesInScope :: GhcMonad m => m [Name] getRdrNamesInScope :: GhcMonad m => m [RdrName] -- | get the GlobalRdrEnv for a session getGRE :: GhcMonad m => m GlobalRdrEnv -- | Returns True if the specified module is interpreted, and -- hence has its full top-level scope available. moduleIsInterpreted :: GhcMonad m => Module -> m Bool -- | Looks up an identifier in the current interactive context (for :info) -- Filter the instances by the ones whose tycons (or clases resp) are in -- scope (qualified or otherwise). Otherwise we list a whole lot too -- many! The exact choice of which ones to show, and which to hide, is a -- judgement call. (see Trac #1581) getInfo :: GhcMonad m => Name -> m (Maybe (TyThing, Fixity, [Instance])) -- | Get the type of an expression exprType :: GhcMonad m => String -> m Type -- | Get the kind of a type typeKind :: GhcMonad m => String -> m Kind -- | Parses a string as an identifier, and returns the list of Names -- that the identifier can refer to in the current interactive context. parseName :: GhcMonad m => String -> m [Name] data RunResult -- | names bound by this evaluation RunOk :: [Name] -> RunResult -- | statement failed compilation RunFailed :: RunResult -- | statement raised an exception RunException :: SomeException -> RunResult RunBreak :: ThreadId -> [Name] -> (Maybe BreakInfo) -> RunResult -- | Run a statement in the current interactive context. Statement may bind -- multple values. runStmt :: GhcMonad m => String -> SingleStep -> m RunResult parseImportDecl :: GhcMonad m => String -> m (ImportDecl RdrName) data SingleStep RunToCompletion :: SingleStep SingleStep :: SingleStep RunAndLogSteps :: SingleStep resume :: GhcMonad m => (SrcSpan -> Bool) -> SingleStep -> m RunResult data Resume data History getHistorySpan :: GhcMonad m => History -> m SrcSpan getHistoryModule :: History -> Module getResumeContext :: GhcMonad m => m [Resume] abandon :: GhcMonad m => m Bool abandonAll :: GhcMonad m => m Bool back :: GhcMonad m => m ([Name], Int, SrcSpan) forward :: GhcMonad m => m ([Name], Int, SrcSpan) showModule :: GhcMonad m => ModSummary -> m String isModuleInterpreted :: GhcMonad m => ModSummary -> m Bool compileExpr :: GhcMonad m => String -> m HValue data HValue dynCompileExpr :: GhcMonad m => String -> m Dynamic obtainTermFromId :: GhcMonad m => Int -> Bool -> Id -> m Term obtainTermFromVal :: GhcMonad m => Int -> Bool -> Type -> a -> m Term reconstructType :: HscEnv -> Int -> Id -> IO (Maybe Type) modInfoModBreaks :: ModuleInfo -> ModBreaks -- | All the information about the breakpoints for a given module data ModBreaks ModBreaks :: BreakArray -> !Array BreakIndex SrcSpan -> !Array BreakIndex [OccName] -> ModBreaks -- | The array of flags, one per breakpoint, indicating which breakpoints -- are enabled. modBreaks_flags :: ModBreaks -> BreakArray -- | An array giving the source span of each breakpoint. modBreaks_locs :: ModBreaks -> !Array BreakIndex SrcSpan -- | An array giving the names of the free variables at each breakpoint. modBreaks_vars :: ModBreaks -> !Array BreakIndex [OccName] -- | Breakpoint index type BreakIndex = Int data BreakInfo data BreakArray setBreakOn :: BreakArray -> Int -> IO Bool setBreakOff :: BreakArray -> Int -> IO Bool getBreak :: BreakArray -> Int -> IO (Maybe Word) -- | Returns the TyThing for a Name. The Name may -- refer to any entity known to GHC, including Names defined using -- runStmt. lookupName :: GhcMonad m => Name -> m (Maybe TyThing) -- | Essentially just a string identifying a package, including the -- version: e.g. parsec-1.0 data PackageId -- | A Module is a pair of a PackageId and a ModuleName. data Module mkModule :: PackageId -> ModuleName -> Module pprModule :: Module -> SDoc moduleName :: Module -> ModuleName modulePackageId :: Module -> PackageId -- | A ModuleName is essentially a simple string, e.g. Data.List. data ModuleName mkModuleName :: String -> ModuleName moduleNameString :: ModuleName -> String -- | A unique, unambigious name for something, containing information about -- where that thing originated. data Name isExternalName :: Name -> Bool nameModule :: Name -> Module -- | print a NamedThing, adding parentheses if the name is an -- operator. pprParenSymName :: NamedThing a => a -> SDoc nameSrcSpan :: Name -> SrcSpan -- | A class allowing convenient access to the Name of various -- datatypes class NamedThing a getOccName :: NamedThing a => a -> OccName getName :: NamedThing a => a -> Name -- | Do not use the data constructors of RdrName directly: prefer the -- family of functions that creates them, such as mkRdrUnqual data RdrName -- | Used for ordinary, unqualified occurrences, e.g. x, -- y or Foo. Create such a RdrName with -- mkRdrUnqual Unqual :: OccName -> RdrName -- | A qualified name written by the user in source code. The module -- isn't necessarily the module where the thing is defined; just the one -- from which it is imported. Examples are Bar.x, Bar.y -- or Bar.Foo. Create such a RdrName with -- mkRdrQual Qual :: ModuleName -> OccName -> RdrName type Id = Var idType :: Id -> Kind -- | isImplicitId tells whether an Ids info is implied by -- other declarations, so we don't need to put its signature in an -- interface file, even if it's mentioned in some other interface -- unfolding. isImplicitId :: Id -> Bool isDeadBinder :: Id -> Bool -- | isExportedIdVar means "don't throw this away" isExportedId :: Var -> Bool isLocalId :: Var -> Bool isGlobalId :: Var -> Bool isRecordSelector :: Id -> Bool isPrimOpId :: Id -> Bool isFCallId :: Id -> Bool isClassOpId_maybe :: Id -> Maybe Class isDataConWorkId :: Id -> Bool -- | Get from either the worker or the wrapper Id to the -- DataCon. Currently used only in the desugarer. -- -- INVARIANT: idDataCon (dataConWrapId d) = d: remember, -- dataConWrapId can return either the wrapper or the worker idDataCon :: Id -> DataCon -- | Returns true if an application to n args would diverge isBottomingId :: Id -> Bool isDictonaryId :: Id -> Bool -- | If the Id is that for a record selector, extract the -- sel_tycon and label. Panic otherwise recordSelectorFieldLabel :: Id -> (TyCon, FieldLabel) -- | TyCons represent type constructors. Type constructors are introduced -- by things such as: -- -- 1) Data declarations: data Foo = ... creates the Foo -- type constructor of kind * -- -- 2) Type synonyms: type Foo = ... creates the Foo -- type constructor -- -- 3) Newtypes: newtype Foo a = MkFoo ... creates the -- Foo type constructor of kind * -> * -- -- 4) Class declarations: class Foo where creates the -- Foo type constructor of kind * -- -- 5) Type coercions! This is because we represent a coercion from -- t1 to t2 as a Type, where that type has kind -- t1 ~ t2. See Coercion for more on this -- -- This data type also encodes a number of primitive, built in type -- constructors such as those for function and tuple types. data TyCon tyConTyVars :: TyCon -> [TyVar] -- | As tyConDataCons_maybe, but returns the empty list of -- constructors if no constructors could be found tyConDataCons :: TyCon -> [DataCon] tyConArity :: TyCon -> Arity -- | Is this TyCon that for a class instance? isClassTyCon :: TyCon -> Bool -- | A product TyCon must both: -- --
    --
  1. Have one constructor
  2. --
  3. Not be existential
  4. --
-- -- However other than this there are few restrictions: they may be -- data or newtype TyCons of any boxity and may -- even be recursive. -- -- Is this a TyCon representing a type synonym (type)? isSynTyCon :: TyCon -> Bool -- | Is this TyCon that for a newtype isNewTyCon :: TyCon -> Bool -- | Does this TyCon represent something that cannot be defined in -- Haskell? isPrimTyCon :: TyCon -> Bool isFunTyCon :: TyCon -> Bool -- | Is this a TyCon, synonym or otherwise, that may have further -- instances appear? isFamilyTyCon :: TyCon -> Bool -- | Extract the TyVars bound by a type synonym and the -- corresponding (unsubstituted) right hand side. If the given -- TyCon is not a type synonym, panics synTyConDefn :: TyCon -> ([TyVar], Type) -- | Find the expansion of the type synonym represented by the given -- TyCon. The free variables of this type will typically include -- those TyVars bound by the TyCon. Panics if the -- TyCon is not that of a type synonym synTyConType :: TyCon -> Type -- | Find the result Kind of a type synonym, after applying it to -- its arity number of type variables Actually this function -- works fine on data types too, but they'd always return *, so we -- never need to ask synTyConResKind :: TyCon -> Kind type TyVar = Var alphaTyVars :: [TyVar] -- | A data constructor data DataCon -- | The "signature" of the DataCon returns, in order: -- -- 1) The result of dataConAllTyVars, -- -- 2) All the ThetaTypes relating to the DataCon (coercion, -- dictionary, implicit parameter - whatever) -- -- 3) The type arguments to the constructor -- -- 4) The original result type of the DataCon dataConSig :: DataCon -> ([TyVar], ThetaType, [Type], Type) dataConType :: DataCon -> Type -- | The type constructor that we are building via this data constructor dataConTyCon :: DataCon -> TyCon -- | The labels for the fields of this particular DataCon dataConFieldLabels :: DataCon -> [FieldLabel] -- | Should the DataCon be presented infix? dataConIsInfix :: DataCon -> Bool -- | Vanilla DataCons are those that are nice boring Haskell 98 -- constructors isVanillaDataCon :: DataCon -> Bool -- | The user-declared type of the data constructor in the nice-to-read -- form: -- --
--   T :: forall a b. a -> b -> T [a]
--   
-- -- rather than: -- --
--   T :: forall a c. forall b. (c~[a]) => a -> b -> T c
--   
-- -- NB: If the constructor is part of a data instance, the result type -- mentions the family tycon, not the internal one. dataConUserType :: DataCon -> Type -- | The strictness markings decided on by the compiler. Does not include -- those for existential dictionaries. The list is in one-to-one -- correspondence with the arity of the DataCon dataConStrictMarks :: DataCon -> [HsBang] data StrictnessMark MarkedStrict :: StrictnessMark NotMarkedStrict :: StrictnessMark isMarkedStrict :: StrictnessMark -> Bool data Class classMethods :: Class -> [Id] classSCTheta :: Class -> [PredType] classTvsFds :: Class -> ([TyVar], [FunDep TyVar]) pprFundeps :: Outputable a => [FunDep a] -> SDoc data Instance instanceDFunId :: Instance -> DFunId pprInstance :: Instance -> SDoc pprInstanceHdr :: Instance -> SDoc -- | The key representation of types within the compiler data Type -- | Attempts to take a forall type apart, returning all the immediate such -- bound type variables and the remainder of the type. Always suceeds, -- even if that means returning an empty list of TyVars splitForAllTys :: Type -> ([TyVar], Type) -- | Extract the function result type and panic if that is not possible funResultTy :: Type -> Type pprParendType :: Type -> SDoc pprTypeApp :: NamedThing a => a -> [Type] -> SDoc -- | The key type representing kinds in the compiler. Invariant: a kind is -- always in one of these forms: -- --
--   FunTy k1 k2
--   TyConApp PrimTyCon [...]
--   TyVar kv   -- (during inference only)
--   ForAll ... -- (for top-level coercions)
--   
type Kind = Type -- | A type of the form PredTy p represents a value whose type is -- the Haskell predicate p, where a predicate is what occurs -- before the => in a Haskell type. It can be expanded into -- its representation, but: -- -- -- -- Consider these examples: -- --
--   f :: (Eq a) => a -> Int
--   g :: (?x :: Int -> Int) => a -> Int
--   h :: (r\l) => {r} => {l::Int | r}
--   
-- -- Here the Eq a and ?x :: Int -> Int and -- rl are all called "predicates" data PredType -- | A collection of PredTypes type ThetaType = [PredType] pprForAll :: [TyVar] -> SDoc pprThetaArrow :: ThetaType -> SDoc -- | A typecheckable-thing, essentially anything that has a name data TyThing AnId :: Id -> TyThing ADataCon :: DataCon -> TyThing ATyCon :: TyCon -> TyThing AClass :: Class -> TyThing data FixityDirection InfixL :: FixityDirection InfixR :: FixityDirection InfixN :: FixityDirection defaultFixity :: Fixity maxPrecedence :: Int negateFixity :: Fixity compareFixity :: Fixity -> Fixity -> (Bool, Bool) -- | Represents a single point within a file data SrcLoc -- | Pretty prints information about the SrcSpan in the style -- defined at ... pprDefnLoc :: SrcSpan -> SDoc mkSrcLoc :: FastString -> Int -> Int -> SrcLoc -- | Good SrcLocs have precise information about their -- location isGoodSrcLoc :: SrcLoc -> Bool noSrcLoc :: SrcLoc -- | Gives the filename of the SrcLoc if it is available, otherwise -- returns a dummy value srcLocFile :: SrcLoc -> FastString -- | Raises an error when used on a bad SrcLoc srcLocLine :: SrcLoc -> Int -- | Raises an error when used on a bad SrcLoc srcLocCol :: SrcLoc -> Int -- | A SrcSpan delimits a portion of a text file. It could be represented -- by a pair of (line,column) coordinates, but in fact we optimise -- slightly by using more compact representations for single-line and -- zero-length spans, both of which are quite common. -- -- The end position is defined to be the column after the end of -- the span. That is, a span of (1,1)-(1,2) is one character long, and a -- span of (1,1)-(1,1) is zero characters long. data SrcSpan -- | Create a SrcSpan between two points in a file mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan -- | Create a SrcSpan corresponding to a single point srcLocSpan :: SrcLoc -> SrcSpan -- | Test if a SrcSpan is good, i.e. has precise location -- information isGoodSrcSpan :: SrcSpan -> Bool noSrcSpan :: SrcSpan -- | Returns the location at the start of the SrcSpan or a -- bad SrcSpan if that is unavailable srcSpanStart :: SrcSpan -> SrcLoc -- | Returns the location at the end of the SrcSpan or a bad -- SrcSpan if that is unavailable srcSpanEnd :: SrcSpan -> SrcLoc srcSpanFile :: SrcSpan -> FastString -- | Raises an error when used on a bad SrcSpan srcSpanStartLine :: SrcSpan -> Int -- | Raises an error when used on a bad SrcSpan srcSpanEndLine :: SrcSpan -> Int -- | Raises an error when used on a bad SrcSpan srcSpanStartCol :: SrcSpan -> Int -- | Raises an error when used on a bad SrcSpan srcSpanEndCol :: SrcSpan -> Int -- | We attach SrcSpans to lots of things, so let's have a datatype for it. data Located e L :: SrcSpan -> e -> Located e noLoc :: e -> Located e mkGeneralLocated :: String -> e -> Located e getLoc :: Located e -> SrcSpan unLoc :: Located e -> e -- | Tests whether the two located things are equal eqLocated :: Eq a => Located a -> Located a -> Bool -- | Tests the ordering of the two located things cmpLocated :: Ord a => Located a -> Located a -> Ordering combineLocs :: Located a -> Located b -> SrcSpan -- | Combine locations from two Located things and add them to a -- third thing addCLoc :: Located a -> Located b -> c -> Located c leftmost_smallest :: SrcSpan -> SrcSpan -> Ordering -- | Alternative strategies for ordering SrcSpans leftmost_largest :: SrcSpan -> SrcSpan -> Ordering rightmost :: SrcSpan -> SrcSpan -> Ordering -- | Determines whether a span encloses a given line and column index spans :: SrcSpan -> (Int, Int) -> Bool -- | Determines whether a span is enclosed by another one isSubspanOf :: SrcSpan -> SrcSpan -> Bool -- | GHC's own exception type error messages all take the form: -- --
--   location: error
--   
-- -- If the location is on the command line, or in GHC itself, then -- location=ghc. All of the error types below correspond to -- a location of ghc, except for ProgramError (where the -- string is assumed to contain a location already, so we don't print -- one). data GhcException PhaseFailed :: String -> ExitCode -> GhcException -- | Some other fatal signal (SIGHUP,SIGTERM) Signal :: Int -> GhcException -- | Prints the short usage msg after the error UsageError :: String -> GhcException -- | A problem with the command line arguments, but don't print usage. CmdLineError :: String -> GhcException -- | The impossible happened. Panic :: String -> GhcException -- | The user tickled something that's known not to work yet, but we're not -- counting it as a bug. Sorry :: String -> GhcException -- | An installation problem. InstallationError :: String -> GhcException -- | An error in the user's code, probably. ProgramError :: String -> GhcException -- | Append a description of the given exception to this string. showGhcException :: GhcException -> String -> String data Token -- | Return module source as token stream, including comments. -- -- The module must be in the module graph and its source must be -- available. Throws a SourceError on parse error. getTokenStream :: GhcMonad m => Module -> m [Located Token] -- | Give even more information on the source than getTokenStream -- This function allows reconstructing the source completely with -- showRichTokenStream. getRichTokenStream :: GhcMonad m => Module -> m [(Located Token, String)] -- | Take a rich token stream such as produced from -- getRichTokenStream and return source code almost identical to -- the original code (except for insignificant whitespace.) showRichTokenStream :: [(Located Token, String)] -> String -- | Given a source location and a StringBuffer corresponding to this -- location, return a rich token stream with the source associated to the -- tokens. addSourceToTokens :: SrcLoc -> StringBuffer -> [Located Token] -> [(Located Token, String)] cyclicModuleErr :: [ModSummary] -> SDoc instance DesugaredMod DesugaredModule instance TypecheckedMod DesugaredModule instance ParsedMod DesugaredModule instance TypecheckedMod TypecheckedModule instance ParsedMod TypecheckedModule instance ParsedMod ParsedModule module PprTyThing type PrintExplicitForalls = Bool -- | Pretty-prints a TyThing. pprTyThing :: PrintExplicitForalls -> TyThing -> SDoc -- | Pretty-prints a TyThing in context: that is, if the entity is a -- data constructor, record selector, or class method, then the entity's -- parent declaration is pretty-printed with irrelevant parts omitted. pprTyThingInContext :: PrintExplicitForalls -> TyThing -> SDoc pprTyThingParent_maybe :: TyThing -> Maybe TyThing -- | Pretty-prints a TyThing with its defining location. pprTyThingLoc :: PrintExplicitForalls -> TyThing -> SDoc -- | Like pprTyThingInContext, but adds the defining location. pprTyThingInContextLoc :: PrintExplicitForalls -> TyThing -> SDoc -- | Pretty-prints the TyThing header. For functions and data -- constructors the function is equivalent to pprTyThing but for -- type constructors and classes it prints only the header part of the -- declaration. pprTyThingHdr :: PrintExplicitForalls -> TyThing -> SDoc pprTypeForUser :: PrintExplicitForalls -> Type -> SDoc module DriverMkDepend doMkDependHS :: GhcMonad m => [FilePath] -> m () module Debugger -- | The :print & friends commands pprintClosureCommand :: GhcMonad m => Bool -> Bool -> String -> m () showTerm :: GhcMonad m => Term -> m SDoc pprTypeAndContents :: GhcMonad m => [Id] -> m SDoc module PPC.CodeGen -- | InstrBlocks are the insn sequences generated by the insn -- selectors. They are really trees of insns to facilitate fast -- appending, where a left-to-right traversal (pre-order?) yields the -- insns in the correct order. cmmTopCodeGen :: DynFlags -> RawCmmTop -> NatM [NatCmmTop Instr] -- | InstrBlocks are the insn sequences generated by the insn -- selectors. They are really trees of insns to facilitate fast -- appending, where a left-to-right traversal yields the insns in the -- correct order. type InstrBlock = OrdList Instr