{-# LANGUAGE CPP #-}
module GHC.SourceGen.Overloaded
( Par(..)
, App(..)
, HasTuple(..)
, tuple
, unboxedTuple
, HasList(..)
, Var(..)
) where
import BasicTypes (Boxity(..))
import HsTypes
( HsType(..)
, HsTyVarBndr(..)
)
import HsSyn (IE(..), IEWrappedName(..))
#if !MIN_VERSION_ghc(8,6,0)
import PlaceHolder(PlaceHolder(..))
#endif
import HsSyn
( HsExpr(..)
, Pat(..)
, HsTupArg(..)
, HsTupleSort(..)
)
import DataCon (dataConName)
import RdrName (RdrName, nameRdrName)
import SrcLoc (Located)
import TysWiredIn (consDataCon_RDR, nilDataCon, unitDataCon)
import GHC.SourceGen.Expr.Internal
import GHC.SourceGen.Name.Internal
import GHC.SourceGen.Syntax
import GHC.SourceGen.Syntax.Internal
import GHC.SourceGen.Type.Internal
class Par e where
par :: e -> e
instance Par HsExpr' where
par = noExt HsPar . builtLoc
instance Par Pat' where
par = noExt ParPat . builtPat
instance Par HsType' where
par = noExt HsParTy . builtLoc
class App e where
(@@) :: e -> e -> e
op :: e -> RdrNameStr -> e -> e
infixl 2 @@
instance App HsExpr' where
op x o y
= noExt OpApp
(parenthesizeExprForOp $ builtLoc x)
(builtLoc $ var o)
#if !MIN_VERSION_ghc(8,6,0)
PlaceHolder
#endif
(parenthesizeExprForOp $ builtLoc y)
x @@ y = noExt HsApp (builtLoc x)
(parenthesizeExprForApp $ builtLoc y)
instance App HsType' where
op x o y
= noExt HsOpTy (parenthesizeTypeForOp $ builtLoc x)
(typeRdrName o)
(parenthesizeTypeForOp $ builtLoc y)
x @@ y = noExt HsAppTy
(builtLoc x)
(parenthesizeTypeForApp $ builtLoc y)
class HasTuple e where
unit :: e
tupleOf :: Boxity -> [e] -> e
tuple, unboxedTuple :: HasTuple e => [e] -> e
tuple = tupleOf Boxed
unboxedTuple = tupleOf Unboxed
instance HasTuple HsExpr' where
tupleOf b ts =
noExt ExplicitTuple
(map (builtLoc . noExt Present . builtLoc) ts)
b
unit = noExt HsVar unitDataConName
unitDataConName :: Located RdrName
unitDataConName = builtLoc $ nameRdrName $ dataConName $ unitDataCon
instance HasTuple HsType' where
tupleOf b = noExt HsTupleTy b' . map builtLoc
where
b' = case b of
Unboxed -> HsUnboxedTuple
Boxed -> HsBoxedOrConstraintTuple
unit = tupleOf Boxed []
instance HasTuple Pat' where
tupleOf b ps =
noExt TuplePat (map builtPat ps) b
#if !MIN_VERSION_ghc(8,6,0)
[]
#endif
unit = noExt VarPat unitDataConName
class HasList e where
list :: [e] -> e
nil :: e
cons :: e
nilDataConName :: Located RdrName
nilDataConName = builtLoc $ nameRdrName $ dataConName $ nilDataCon
instance HasList HsExpr' where
list = withPlaceHolder (noExt ExplicitList) Nothing . map builtLoc
nil = noExt HsVar nilDataConName
cons = noExt HsVar $ builtLoc consDataCon_RDR
instance HasList Pat' where
#if MIN_VERSION_ghc(8,6,0)
list = noExt ListPat . map builtPat
#else
list ps = ListPat (map builtPat ps) PlaceHolder Nothing
#endif
nil = noExt VarPat nilDataConName
cons = noExt VarPat $ builtLoc $ consDataCon_RDR
class Var a where
var :: RdrNameStr -> a
instance Var Pat' where
var = noExt VarPat . valueRdrName
instance Var HsExpr' where
var = noExt HsVar . valueRdrName
instance Var HsType' where
var = noExt HsTyVar notPromoted . typeRdrName
instance Var HsTyVarBndr' where
var = noExt UserTyVar . typeRdrName
instance Var IE' where
var = noExt IEVar . builtLoc . IEName . valueRdrName