ghc-9.8.2: The GHC API
Safe HaskellNone
LanguageHaskell2010

GHC.Tc.Types.Evidence

Synopsis

HsWrapper

data HsWrapper Source #

Instances

Instances details
Data HsWrapper Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsWrapper -> c HsWrapper Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsWrapper Source #

toConstr :: HsWrapper -> Constr Source #

dataTypeOf :: HsWrapper -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsWrapper) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsWrapper) Source #

gmapT :: (forall b. Data b => b -> b) -> HsWrapper -> HsWrapper Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWrapper -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWrapper -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsWrapper -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWrapper -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWrapper -> m HsWrapper Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWrapper -> m HsWrapper Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWrapper -> m HsWrapper Source #

Monoid HsWrapper Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Semigroup HsWrapper Source #

The Semigroup instance is a bit fishy, since WpCompose, as a data constructor, is "syntactic" and not associative. Concretely, if a, b, and c aren't WpHole:

(a <> b) <> c ?= a <> (b <> c)

>

(a `WpCompose` b) `WpCompose` c /= @ a `WpCompose` (b `WpCompose` c)

However these two associations are are "semantically equal" in the sense that they produce equal functions when passed to GHC.HsToCore.Binds.dsHsWrapper.

Instance details

Defined in GHC.Tc.Types.Evidence

Outputable HsWrapper Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: HsWrapper -> SDoc Source #

mkWpFun Source #

Arguments

:: HsWrapper 
-> HsWrapper 
-> Scaled TcTypeFRR

the "from" type of the first wrapper MUST have a fixed RuntimeRep

-> TcType

Either "from" type or "to" type of the second wrapper (used only when the second wrapper is the identity)

-> HsWrapper 

Smart constructor to create a WpFun HsWrapper.

PRECONDITION: the "from" type of the first wrapper must have a syntactically fixed RuntimeRep (see Note [Fixed RuntimeRep] in GHC.Tc.Utils.Concrete).

hsWrapDictBinders :: HsWrapper -> Bag DictId Source #

Identifies the lambda-bound dictionaries of an HsWrapper. This is used (only) to allow the pattern-match overlap checker to know what Given dictionaries are in scope.

We specifically do not collect dictionaries bound in a WpLet. These are either superclasses of lambda-bound ones, or (extremely numerous) results of binding Wanted dictionaries. We definitely don't want all those cluttering up the Given dictionaries for pattern-match overlap checking!

Evidence bindings

data TcEvBinds Source #

Instances

Instances details
Data TcEvBinds Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TcEvBinds -> c TcEvBinds Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TcEvBinds Source #

toConstr :: TcEvBinds -> Constr Source #

dataTypeOf :: TcEvBinds -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TcEvBinds) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TcEvBinds) Source #

gmapT :: (forall b. Data b => b -> b) -> TcEvBinds -> TcEvBinds Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TcEvBinds -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TcEvBinds -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TcEvBinds -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TcEvBinds -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TcEvBinds -> m TcEvBinds Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TcEvBinds -> m TcEvBinds Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TcEvBinds -> m TcEvBinds Source #

Outputable TcEvBinds Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: TcEvBinds -> SDoc Source #

data EvBindsVar Source #

Instances

Instances details
Uniquable EvBindsVar Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Outputable EvBindsVar Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvBindsVar -> SDoc Source #

newtype EvBindMap Source #

Constructors

EvBindMap 

Instances

Instances details
Outputable EvBindMap Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvBindMap -> SDoc Source #

foldEvBindMap :: (EvBind -> a -> a) -> a -> EvBindMap -> a Source #

nonDetStrictFoldEvBindMap :: (EvBind -> a -> a) -> a -> EvBindMap -> a Source #

data EvBind Source #

Constructors

EvBind 

Instances

Instances details
Outputable EvBind Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvBind -> SDoc Source #

EvTerm (already a CoreExpr)

data EvTerm Source #

Instances

Instances details
Data EvTerm Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EvTerm -> c EvTerm Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EvTerm Source #

toConstr :: EvTerm -> Constr Source #

dataTypeOf :: EvTerm -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EvTerm) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EvTerm) Source #

gmapT :: (forall b. Data b => b -> b) -> EvTerm -> EvTerm Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EvTerm -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EvTerm -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> EvTerm -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EvTerm -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EvTerm -> m EvTerm Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EvTerm -> m EvTerm Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EvTerm -> m EvTerm Source #

Outputable EvTerm Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvTerm -> SDoc Source #

evId :: EvId -> EvExpr Source #

Any sort of evidence Id, including coercions

data EvCallStack Source #

Evidence for CallStack implicit parameters.

Constructors

EvCsEmpty 
EvCsPushCall FastString RealSrcSpan EvExpr

EvCsPushCall origin loc stk represents a call from origin, occurring at loc, in a calling context stk.

Instances

Instances details
Data EvCallStack Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EvCallStack -> c EvCallStack Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EvCallStack Source #

toConstr :: EvCallStack -> Constr Source #

dataTypeOf :: EvCallStack -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EvCallStack) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EvCallStack) Source #

gmapT :: (forall b. Data b => b -> b) -> EvCallStack -> EvCallStack Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EvCallStack -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EvCallStack -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> EvCallStack -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EvCallStack -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack Source #

Outputable EvCallStack Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvCallStack -> SDoc Source #

data EvTypeable Source #

Instructions on how to make a Typeable dictionary. See Note [Typeable evidence terms]

Constructors

EvTypeableTyCon TyCon [EvTerm]

Dictionary for Typeable T where T is a type constructor with all of its kind variables saturated. The [EvTerm] is Typeable evidence for the applied kinds..

EvTypeableTyApp EvTerm EvTerm

Dictionary for Typeable (s t), given a dictionaries for s and t.

EvTypeableTrFun EvTerm EvTerm EvTerm

Dictionary for Typeable (s % w -> t), given a dictionaries for w, s, and t.

EvTypeableTyLit EvTerm

Dictionary for a type literal, e.g. Typeable "foo" or Typeable 3 The EvTerm is evidence of, e.g., KnownNat 3 (see #10348)

Instances

Instances details
Data EvTypeable Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EvTypeable -> c EvTypeable Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EvTypeable Source #

toConstr :: EvTypeable -> Constr Source #

dataTypeOf :: EvTypeable -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EvTypeable) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EvTypeable) Source #

gmapT :: (forall b. Data b => b -> b) -> EvTypeable -> EvTypeable Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EvTypeable -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EvTypeable -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> EvTypeable -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EvTypeable -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable Source #

Outputable EvTypeable Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvTypeable -> SDoc Source #

HoleExprRef

data HoleExprRef Source #

Where to store evidence for expression holes See Note [Holes] in GHC.Tc.Types.Constraint

Constructors

HER 

Fields

  • (IORef EvTerm)

    where to write the erroring expression

  • TcType

    expected type of that expression

  • Unique

    for debug output only

Instances

Instances details
Data HoleExprRef Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HoleExprRef -> c HoleExprRef Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HoleExprRef Source #

toConstr :: HoleExprRef -> Constr Source #

dataTypeOf :: HoleExprRef -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HoleExprRef) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HoleExprRef) Source #

gmapT :: (forall b. Data b => b -> b) -> HoleExprRef -> HoleExprRef Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HoleExprRef -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HoleExprRef -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HoleExprRef -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HoleExprRef -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HoleExprRef -> m HoleExprRef Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HoleExprRef -> m HoleExprRef Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HoleExprRef -> m HoleExprRef Source #

Outputable HoleExprRef Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: HoleExprRef -> SDoc Source #

TcCoercion

data CoercionHole Source #

A coercion to be filled in by the type-checker. See Note [Coercion holes]

Instances

Instances details
Data CoercionHole Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CoercionHole -> c CoercionHole Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CoercionHole Source #

toConstr :: CoercionHole -> Constr Source #

dataTypeOf :: CoercionHole -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CoercionHole) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CoercionHole) Source #

gmapT :: (forall b. Data b => b -> b) -> CoercionHole -> CoercionHole Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CoercionHole -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CoercionHole -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> CoercionHole -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CoercionHole -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CoercionHole -> m CoercionHole Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CoercionHole -> m CoercionHole Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CoercionHole -> m CoercionHole Source #

Uniquable CoercionHole Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Outputable CoercionHole Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

data Role Source #

See Note [Roles] in GHC.Core.Coercion

Order of constructors matters: the Ord instance coincides with the *super*typing relation on roles.

Instances

Instances details
Data Role Source # 
Instance details

Defined in Language.Haskell.Syntax.Basic

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Role -> c Role Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Role Source #

toConstr :: Role -> Constr Source #

dataTypeOf :: Role -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Role) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Role) Source #

gmapT :: (forall b. Data b => b -> b) -> Role -> Role Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Role -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Role -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Role -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Role -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Role -> m Role Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Role -> m Role Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Role -> m Role Source #

Binary Role Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Outputable Role Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

ppr :: Role -> SDoc Source #

Eq Role Source # 
Instance details

Defined in Language.Haskell.Syntax.Basic

Methods

(==) :: Role -> Role -> Bool #

(/=) :: Role -> Role -> Bool #

Ord Role Source # 
Instance details

Defined in Language.Haskell.Syntax.Basic

Methods

compare :: Role -> Role -> Ordering #

(<) :: Role -> Role -> Bool #

(<=) :: Role -> Role -> Bool #

(>) :: Role -> Role -> Bool #

(>=) :: Role -> Role -> Bool #

max :: Role -> Role -> Role #

min :: Role -> Role -> Role #

type Anno (Maybe Role) Source # 
Instance details

Defined in GHC.Hs.Decls

type Anno (Maybe Role) Source # 
Instance details

Defined in GHC.Hs.Decls

data LeftOrRight Source #

Constructors

CLeft 
CRight 

Instances

Instances details
Data LeftOrRight Source # 
Instance details

Defined in GHC.Types.Basic

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LeftOrRight -> c LeftOrRight Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LeftOrRight Source #

toConstr :: LeftOrRight -> Constr Source #

dataTypeOf :: LeftOrRight -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LeftOrRight) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LeftOrRight) Source #

gmapT :: (forall b. Data b => b -> b) -> LeftOrRight -> LeftOrRight Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> LeftOrRight -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LeftOrRight -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight Source #

Binary LeftOrRight Source # 
Instance details

Defined in GHC.Types.Basic

Outputable LeftOrRight Source # 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: LeftOrRight -> SDoc Source #

Eq LeftOrRight Source # 
Instance details

Defined in GHC.Types.Basic

pickLR :: LeftOrRight -> (a, a) -> a Source #

maybeSymCo :: SwapFlag -> TcCoercion -> TcCoercion Source #

If a SwapFlag is IsSwapped, flip the orientation of a coercion

unwrapIP :: Type -> CoercionR Source #

Create a Coercion that unwraps an implicit-parameter dictionary to expose the underlying value. We expect the Type to have the form `IP sym ty`, and return a Coercion `co :: IP sym ty ~ ty`

wrapIP :: Type -> CoercionR Source #

Create a Coercion that wraps a value in an implicit-parameter dictionary. See unwrapIP.

QuoteWrapper

data QuoteWrapper Source #

Constructors

QuoteWrapper EvVar Type 

Instances

Instances details
Data QuoteWrapper Source # 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QuoteWrapper -> c QuoteWrapper Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QuoteWrapper Source #

toConstr :: QuoteWrapper -> Constr Source #

dataTypeOf :: QuoteWrapper -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c QuoteWrapper) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QuoteWrapper) Source #

gmapT :: (forall b. Data b => b -> b) -> QuoteWrapper -> QuoteWrapper Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QuoteWrapper -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QuoteWrapper -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> QuoteWrapper -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> QuoteWrapper -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> QuoteWrapper -> m QuoteWrapper Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> QuoteWrapper -> m QuoteWrapper Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> QuoteWrapper -> m QuoteWrapper Source #

applyQuoteWrapper :: QuoteWrapper -> HsWrapper Source #

Convert the QuoteWrapper into a normal HsWrapper which can be used to apply its contents.