never executed always true always false
    1 {-# LANGUAGE TypeFamilies, UndecidableInstances #-}
    2 
    3 -- | Various types used during desugaring.
    4 module GHC.HsToCore.Types (
    5         DsM, DsLclEnv(..), DsGblEnv(..),
    6         DsMetaEnv, DsMetaVal(..), CompleteMatches
    7     ) where
    8 
    9 import GHC.Prelude (Int)
   10 
   11 import Data.IORef
   12 
   13 import GHC.Types.CostCentre.State
   14 import GHC.Types.Error
   15 import GHC.Types.Name.Env
   16 import GHC.Types.SrcLoc
   17 import GHC.Types.Var
   18 import GHC.Types.Name.Reader (GlobalRdrEnv)
   19 import GHC.Hs (LForeignDecl, HsExpr, GhcTc)
   20 import GHC.Tc.Types (TcRnIf, IfGblEnv, IfLclEnv, CompleteMatches)
   21 import GHC.HsToCore.Pmc.Types (Nablas)
   22 import GHC.HsToCore.Errors.Types
   23 import GHC.Core (CoreExpr)
   24 import GHC.Core.FamInstEnv
   25 import GHC.Utils.Outputable as Outputable
   26 import GHC.Unit.Module
   27 import GHC.Driver.Hooks (DsForeignsHook)
   28 import GHC.Data.OrdList (OrdList)
   29 import GHC.Types.ForeignStubs (ForeignStubs)
   30 
   31 {-
   32 ************************************************************************
   33 *                                                                      *
   34                 Desugarer monad
   35 *                                                                      *
   36 ************************************************************************
   37 
   38 Now the mondo monad magic (yes, @DsM@ is a silly name)---carry around
   39 a @UniqueSupply@ and some annotations, which
   40 presumably include source-file location information:
   41 -}
   42 
   43 -- | Global read-only context and state of the desugarer.
   44 -- The statefulness is implemented through 'IORef's.
   45 data DsGblEnv
   46   = DsGblEnv
   47   { ds_mod          :: Module             -- For SCC profiling
   48   , ds_fam_inst_env :: FamInstEnv         -- Like tcg_fam_inst_env
   49   , ds_gbl_rdr_env  :: GlobalRdrEnv       -- needed *only* to know what newtype
   50                                           -- constructors are in scope during
   51                                           -- pattern-match satisfiability checking
   52   , ds_unqual  :: PrintUnqualified
   53   , ds_msgs    :: IORef (Messages DsMessage) -- Diagnostic messages
   54   , ds_if_env  :: (IfGblEnv, IfLclEnv)    -- Used for looking up global,
   55                                           -- possibly-imported things
   56   , ds_complete_matches :: CompleteMatches
   57      -- Additional complete pattern matches
   58   , ds_cc_st   :: IORef CostCentreState
   59      -- Tracking indices for cost centre annotations
   60   , ds_next_wrapper_num :: IORef (ModuleEnv Int)
   61     -- ^ See Note [Generating fresh names for FFI wrappers]
   62   }
   63 
   64 instance ContainsModule DsGblEnv where
   65   extractModule = ds_mod
   66 
   67 -- | Local state of the desugarer, extended as we lexically descend
   68 data DsLclEnv
   69   = DsLclEnv
   70   { dsl_meta    :: DsMetaEnv   -- ^ Template Haskell bindings
   71   , dsl_loc     :: RealSrcSpan -- ^ To put in pattern-matching error msgs
   72   , dsl_nablas  :: Nablas
   73   -- ^ See Note [Note [Long-distance information] in "GHC.HsToCore.Pmc".
   74   -- The set of reaching values Nablas is augmented as we walk inwards, refined
   75   -- through each pattern match in turn
   76   }
   77 
   78 -- Inside [| |] brackets, the desugarer looks
   79 -- up variables in the DsMetaEnv
   80 type DsMetaEnv = NameEnv DsMetaVal
   81 
   82 data DsMetaVal
   83   = DsBound Id         -- Bound by a pattern inside the [| |].
   84                        -- Will be dynamically alpha renamed.
   85                        -- The Id has type THSyntax.Var
   86 
   87   | DsSplice (HsExpr GhcTc) -- These bindings are introduced by
   88                             -- the PendingSplices on a HsBracketOut
   89 
   90 -- | Desugaring monad. See also 'TcM'.
   91 type DsM = TcRnIf DsGblEnv DsLclEnv
   92 
   93 -- See Note [The Decoupling Abstract Data Hack]
   94 type instance DsForeignsHook = [LForeignDecl GhcTc] -> DsM (ForeignStubs, OrdList (Id, CoreExpr))