beam-migrate-0.4.0.1: SQL DDL support and migrations support library for Beam

Safe HaskellNone
LanguageHaskell2010

Database.Beam.Haskell.Syntax

Contents

Description

Instances that allow us to use Haskell as a backend syntax. This allows us to use migrations defined a la SQL to generate a beam schema.

Mainly of interest to backends.

Unfortunately, we define some orphan Hashable instances that aren't defined for us in haskell-src-exts.

Synopsis

Documentation

newtype HsDbField Source #

Constructors

HsDbField 

Fields

data HsConstraintDefinition Source #

Instances
Eq HsConstraintDefinition Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Show HsConstraintDefinition Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Generic HsConstraintDefinition Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Associated Types

type Rep HsConstraintDefinition :: Type -> Type #

Hashable HsConstraintDefinition Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Sql92DisplaySyntax HsConstraintDefinition Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Sql92SerializableConstraintDefinitionSyntax HsConstraintDefinition Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

IsSql92ColumnConstraintDefinitionSyntax HsConstraintDefinition Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Rep HsConstraintDefinition Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Rep HsConstraintDefinition = D1 (MetaData "HsConstraintDefinition" "Database.Beam.Haskell.Syntax" "beam-migrate-0.4.0.1-LFWMnC8rnYz3hNNRXqkW0o" False) (C1 (MetaCons "HsConstraintDefinition" PrefixI True) (S1 (MetaSel (Just "hsConstraintDefinitionConstraint") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HsExpr)))
type Sql92ColumnConstraintDefinitionConstraintSyntax HsConstraintDefinition Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92ColumnConstraintDefinitionAttributesSyntax HsConstraintDefinition Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

data HsImport Source #

Constructors

HsImportAll 
HsImportSome (Set (ImportSpec ())) 
Instances
Eq HsImport Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Show HsImport Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Generic HsImport Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Associated Types

type Rep HsImport :: Type -> Type #

Methods

from :: HsImport -> Rep HsImport x #

to :: Rep HsImport x -> HsImport #

Semigroup HsImport Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Monoid HsImport Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Hashable HsImport Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Methods

hashWithSalt :: Int -> HsImport -> Int #

hash :: HsImport -> Int #

type Rep HsImport Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Rep HsImport = D1 (MetaData "HsImport" "Database.Beam.Haskell.Syntax" "beam-migrate-0.4.0.1-LFWMnC8rnYz3hNNRXqkW0o" False) (C1 (MetaCons "HsImportAll" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HsImportSome" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set (ImportSpec ())))))

data HsDataType Source #

Instances
Eq HsDataType Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Show HsDataType Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Generic HsDataType Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Associated Types

type Rep HsDataType :: Type -> Type #

Hashable HsDataType Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

IsSql2003BinaryAndVarBinaryDataTypeSyntax HsDataType Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

IsSql2008BigIntDataTypeSyntax HsDataType Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

IsSql99DataTypeSyntax HsDataType Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Sql92DisplaySyntax HsDataType Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

IsSql92DataTypeSyntax HsDataType Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Sql92SerializableDataTypeSyntax HsDataType Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

HasDataTypeCreatedCheck HsDataType Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Methods

dataTypeHasBeenCreated :: HsDataType -> (forall preCondition. Typeable preCondition => [preCondition]) -> Bool Source #

type Rep HsDataType Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Rep HsDataType = D1 (MetaData "HsDataType" "Database.Beam.Haskell.Syntax" "beam-migrate-0.4.0.1-LFWMnC8rnYz3hNNRXqkW0o" False) (C1 (MetaCons "HsDataType" PrefixI True) (S1 (MetaSel (Just "hsDataTypeMigration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HsExpr) :*: (S1 (MetaSel (Just "hsDataTypeType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HsType) :*: S1 (MetaSel (Just "hsDataTypeSerialized") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BeamSerializedDataType))))

data HsType Source #

Constructors

HsType 
Instances
Eq HsType Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Methods

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

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

Show HsType Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Generic HsType Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Associated Types

type Rep HsType :: Type -> Type #

Methods

from :: HsType -> Rep HsType x #

to :: Rep HsType x -> HsType #

Hashable HsType Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Methods

hashWithSalt :: Int -> HsType -> Int #

hash :: HsType -> Int #

type Rep HsType Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Rep HsType = D1 (MetaData "HsType" "Database.Beam.Haskell.Syntax" "beam-migrate-0.4.0.1-LFWMnC8rnYz3hNNRXqkW0o" False) (C1 (MetaCons "HsType" PrefixI True) (S1 (MetaSel (Just "hsTypeSyntax") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type ())) :*: S1 (MetaSel (Just "hsTypeImports") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HsImports)))

data HsExpr Source #

Instances
Eq HsExpr Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Methods

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

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

Show HsExpr Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Generic HsExpr Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Associated Types

type Rep HsExpr :: Type -> Type #

Methods

from :: HsExpr -> Rep HsExpr x #

to :: Rep HsExpr x -> HsExpr #

Hashable HsExpr Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Methods

hashWithSalt :: Int -> HsExpr -> Int #

hash :: HsExpr -> Int #

IsSql92FieldNameSyntax HsExpr Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

IsSql92QuantifierSyntax HsExpr Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

IsSql92ExtractFieldSyntax HsExpr Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

IsSql92ExpressionSyntax HsExpr Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Methods

valueE :: Sql92ExpressionValueSyntax HsExpr -> HsExpr #

rowE :: [HsExpr] -> HsExpr #

quantifierListE :: [HsExpr] -> HsExpr #

coalesceE :: [HsExpr] -> HsExpr #

caseE :: [(HsExpr, HsExpr)] -> HsExpr -> HsExpr #

fieldE :: Sql92ExpressionFieldNameSyntax HsExpr -> HsExpr #

betweenE :: HsExpr -> HsExpr -> HsExpr -> HsExpr #

andE :: HsExpr -> HsExpr -> HsExpr #

orE :: HsExpr -> HsExpr -> HsExpr #

addE :: HsExpr -> HsExpr -> HsExpr #

subE :: HsExpr -> HsExpr -> HsExpr #

mulE :: HsExpr -> HsExpr -> HsExpr #

divE :: HsExpr -> HsExpr -> HsExpr #

likeE :: HsExpr -> HsExpr -> HsExpr #

modE :: HsExpr -> HsExpr -> HsExpr #

overlapsE :: HsExpr -> HsExpr -> HsExpr #

nullIfE :: HsExpr -> HsExpr -> HsExpr #

positionE :: HsExpr -> HsExpr -> HsExpr #

eqE :: Maybe (Sql92ExpressionQuantifierSyntax HsExpr) -> HsExpr -> HsExpr -> HsExpr #

neqE :: Maybe (Sql92ExpressionQuantifierSyntax HsExpr) -> HsExpr -> HsExpr -> HsExpr #

ltE :: Maybe (Sql92ExpressionQuantifierSyntax HsExpr) -> HsExpr -> HsExpr -> HsExpr #

gtE :: Maybe (Sql92ExpressionQuantifierSyntax HsExpr) -> HsExpr -> HsExpr -> HsExpr #

leE :: Maybe (Sql92ExpressionQuantifierSyntax HsExpr) -> HsExpr -> HsExpr -> HsExpr #

geE :: Maybe (Sql92ExpressionQuantifierSyntax HsExpr) -> HsExpr -> HsExpr -> HsExpr #

eqMaybeE :: HsExpr -> HsExpr -> HsExpr -> HsExpr #

neqMaybeE :: HsExpr -> HsExpr -> HsExpr -> HsExpr #

castE :: HsExpr -> Sql92ExpressionCastTargetSyntax HsExpr -> HsExpr #

notE :: HsExpr -> HsExpr #

negateE :: HsExpr -> HsExpr #

isNullE :: HsExpr -> HsExpr #

isNotNullE :: HsExpr -> HsExpr #

isTrueE :: HsExpr -> HsExpr #

isNotTrueE :: HsExpr -> HsExpr #

isFalseE :: HsExpr -> HsExpr #

isNotFalseE :: HsExpr -> HsExpr #

isUnknownE :: HsExpr -> HsExpr #

isNotUnknownE :: HsExpr -> HsExpr #

charLengthE :: HsExpr -> HsExpr #

octetLengthE :: HsExpr -> HsExpr #

bitLengthE :: HsExpr -> HsExpr #

lowerE :: HsExpr -> HsExpr #

upperE :: HsExpr -> HsExpr #

trimE :: HsExpr -> HsExpr #

absE :: HsExpr -> HsExpr #

extractE :: Sql92ExpressionExtractFieldSyntax HsExpr -> HsExpr -> HsExpr #

existsE :: Sql92ExpressionSelectSyntax HsExpr -> HsExpr #

uniqueE :: Sql92ExpressionSelectSyntax HsExpr -> HsExpr #

subqueryE :: Sql92ExpressionSelectSyntax HsExpr -> HsExpr #

currentTimestampE :: HsExpr #

defaultE :: HsExpr #

inE :: HsExpr -> [HsExpr] -> HsExpr #

IsSql92ColumnConstraintSyntax HsExpr Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

HasSqlValueSyntax HsExpr Bool Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

HasSqlValueSyntax HsExpr Int Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Methods

sqlValueSyntax :: Int -> HsExpr #

type Rep HsExpr Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Rep HsExpr = D1 (MetaData "HsExpr" "Database.Beam.Haskell.Syntax" "beam-migrate-0.4.0.1-LFWMnC8rnYz3hNNRXqkW0o" False) (C1 (MetaCons "HsExpr" PrefixI True) ((S1 (MetaSel (Just "hsExprSyntax") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Exp ())) :*: S1 (MetaSel (Just "hsExprImports") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HsImports)) :*: (S1 (MetaSel (Just "hsExprConstraints") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Asst ()]) :*: S1 (MetaSel (Just "hsExprTypeVariables") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set (Name ()))))))
type Sql92ExpressionExtractFieldSyntax HsExpr Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92ExpressionCastTargetSyntax HsExpr Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92ExpressionFieldNameSyntax HsExpr Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92ExpressionSelectSyntax HsExpr Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92ExpressionValueSyntax HsExpr Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92ExpressionQuantifierSyntax HsExpr Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92ColumnConstraintMatchTypeSyntax HsExpr Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92ColumnConstraintReferentialActionSyntax HsExpr Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92ColumnConstraintExpressionSyntax HsExpr Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

data HsColumnSchema Source #

Instances
Eq HsColumnSchema Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Show HsColumnSchema Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Hashable HsColumnSchema Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Sql92DisplaySyntax HsColumnSchema Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

IsSql92ColumnSchemaSyntax HsColumnSchema Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92ColumnSchemaColumnTypeSyntax HsColumnSchema Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92ColumnSchemaExpressionSyntax HsColumnSchema Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92ColumnSchemaColumnConstraintDefinitionSyntax HsColumnSchema Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

data HsAction Source #

Constructors

HsAction 
Instances
Semigroup HsAction Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Monoid HsAction Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

IsSql92AlterTableSyntax HsAction Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

IsSql92DropTableSyntax HsAction Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

IsSql92CreateTableSyntax HsAction Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

IsSql92DdlCommandSyntax HsAction Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92AlterTableTableNameSyntax HsAction Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92AlterTableAlterTableActionSyntax HsAction Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92DropTableTableNameSyntax HsAction Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92CreateTableTableNameSyntax HsAction Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92CreateTableColumnSchemaSyntax HsAction Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92CreateTableTableConstraintSyntax HsAction Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92CreateTableOptionsSyntax HsAction Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92DdlCommandCreateTableSyntax HsAction Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92DdlCommandAlterTableSyntax HsAction Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92DdlCommandDropTableSyntax HsAction Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

newtype HsFieldLookup Source #

Constructors

HsFieldLookup 

Fields

dataDecl :: DeclHead () -> [QualConDecl ()] -> Maybe (Deriving ()) -> Decl () Source #

DDL Syntax definitions

data HsNone Source #

Constructors

HsNone 
Instances
Eq HsNone Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Methods

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

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

Ord HsNone Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Show HsNone Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Generic HsNone Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Associated Types

type Rep HsNone :: Type -> Type #

Methods

from :: HsNone -> Rep HsNone x #

to :: Rep HsNone x -> HsNone #

Semigroup HsNone Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Monoid HsNone Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Hashable HsNone Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

Methods

hashWithSalt :: Int -> HsNone -> Int #

hash :: HsNone -> Int #

IsSql92ConstraintAttributesSyntax HsNone Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

IsSql92ReferentialActionSyntax HsNone Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

IsSql92MatchTypeSyntax HsNone Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

IsSql92AlterColumnActionSyntax HsNone Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

IsSql92AlterTableActionSyntax HsNone Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Rep HsNone Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Rep HsNone = D1 (MetaData "HsNone" "Database.Beam.Haskell.Syntax" "beam-migrate-0.4.0.1-LFWMnC8rnYz3hNNRXqkW0o" False) (C1 (MetaCons "HsNone" PrefixI False) (U1 :: Type -> Type))
type Sql92AlterTableAlterColumnActionSyntax HsNone Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

type Sql92AlterTableColumnSchemaSyntax HsNone Source # 
Instance details

Defined in Database.Beam.Haskell.Syntax

HsSyntax utilities

tyParens :: Type () -> Type () Source #

functionTy :: Type () -> Type () -> Type () Source #

tyTuple :: [Type ()] -> Type () Source #

tyApp :: Type () -> [Type ()] -> Type () Source #

combineHsExpr :: (Exp () -> Exp () -> Exp ()) -> HsExpr -> HsExpr -> HsExpr Source #

hsInt :: (Integral a, Show a) => a -> HsExpr Source #

hsOp :: Text -> QOp () Source #

hsInstance :: Text -> [Type ()] -> [InstDecl ()] -> Decl () Source #

Orphans

Orphan instances

Hashable Boxed Source # 
Instance details

Methods

hashWithSalt :: Int -> Boxed -> Int #

hash :: Boxed -> Int #

Hashable a => Hashable (Set a) Source # 
Instance details

Methods

hashWithSalt :: Int -> Set a -> Int #

hash :: Set a -> Int #

Hashable (ModuleName ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> ModuleName () -> Int #

hash :: ModuleName () -> Int #

Hashable (SpecialCon ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> SpecialCon () -> Int #

hash :: SpecialCon () -> Int #

Hashable (QName ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> QName () -> Int #

hash :: QName () -> Int #

Hashable (Name ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Name () -> Int #

hash :: Name () -> Int #

Hashable (IPName ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> IPName () -> Int #

hash :: IPName () -> Int #

Hashable (QOp ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> QOp () -> Int #

hash :: QOp () -> Int #

Hashable (Op ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Op () -> Int #

hash :: Op () -> Int #

Hashable (CName ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> CName () -> Int #

hash :: CName () -> Int #

Hashable (Namespace ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Namespace () -> Int #

hash :: Namespace () -> Int #

Hashable (ImportSpec ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> ImportSpec () -> Int #

hash :: ImportSpec () -> Int #

Hashable (Assoc ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Assoc () -> Int #

hash :: Assoc () -> Int #

Hashable (Decl ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Decl () -> Int #

hash :: Decl () -> Int #

Hashable (PatternSynDirection ()) Source # 
Instance details

Hashable (TypeEqn ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> TypeEqn () -> Int #

hash :: TypeEqn () -> Int #

Hashable (Annotation ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Annotation () -> Int #

hash :: Annotation () -> Int #

Hashable (BooleanFormula ()) Source # 
Instance details

Hashable (Role ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Role () -> Int #

hash :: Role () -> Int #

Hashable (DataOrNew ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> DataOrNew () -> Int #

hash :: DataOrNew () -> Int #

Hashable (InjectivityInfo ()) Source # 
Instance details

Hashable (ResultSig ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> ResultSig () -> Int #

hash :: ResultSig () -> Int #

Hashable (DeclHead ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> DeclHead () -> Int #

hash :: DeclHead () -> Int #

Hashable (InstRule ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> InstRule () -> Int #

hash :: InstRule () -> Int #

Hashable (InstHead ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> InstHead () -> Int #

hash :: InstHead () -> Int #

Hashable (Deriving ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Deriving () -> Int #

hash :: Deriving () -> Int #

Hashable (DerivStrategy ()) Source # 
Instance details

Hashable (Binds ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Binds () -> Int #

hash :: Binds () -> Int #

Hashable (IPBind ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> IPBind () -> Int #

hash :: IPBind () -> Int #

Hashable (Match ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Match () -> Int #

hash :: Match () -> Int #

Hashable (QualConDecl ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> QualConDecl () -> Int #

hash :: QualConDecl () -> Int #

Hashable (ConDecl ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> ConDecl () -> Int #

hash :: ConDecl () -> Int #

Hashable (FieldDecl ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> FieldDecl () -> Int #

hash :: FieldDecl () -> Int #

Hashable (GadtDecl ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> GadtDecl () -> Int #

hash :: GadtDecl () -> Int #

Hashable (ClassDecl ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> ClassDecl () -> Int #

hash :: ClassDecl () -> Int #

Hashable (InstDecl ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> InstDecl () -> Int #

hash :: InstDecl () -> Int #

Hashable (BangType ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> BangType () -> Int #

hash :: BangType () -> Int #

Hashable (Unpackedness ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Unpackedness () -> Int #

hash :: Unpackedness () -> Int #

Hashable (Rhs ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Rhs () -> Int #

hash :: Rhs () -> Int #

Hashable (GuardedRhs ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> GuardedRhs () -> Int #

hash :: GuardedRhs () -> Int #

Hashable (Type ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Type () -> Int #

hash :: Type () -> Int #

Hashable (MaybePromotedName ()) Source # 
Instance details

Hashable (Promoted ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Promoted () -> Int #

hash :: Promoted () -> Int #

Hashable (TyVarBind ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> TyVarBind () -> Int #

hash :: TyVarBind () -> Int #

Hashable (FunDep ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> FunDep () -> Int #

hash :: FunDep () -> Int #

Hashable (Context ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Context () -> Int #

hash :: Context () -> Int #

Hashable (Asst ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Asst () -> Int #

hash :: Asst () -> Int #

Hashable (Literal ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Literal () -> Int #

hash :: Literal () -> Int #

Hashable (Sign ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Sign () -> Int #

hash :: Sign () -> Int #

Hashable (Exp ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Exp () -> Int #

hash :: Exp () -> Int #

Hashable (XName ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> XName () -> Int #

hash :: XName () -> Int #

Hashable (XAttr ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> XAttr () -> Int #

hash :: XAttr () -> Int #

Hashable (Bracket ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Bracket () -> Int #

hash :: Bracket () -> Int #

Hashable (Splice ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Splice () -> Int #

hash :: Splice () -> Int #

Hashable (Safety ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Safety () -> Int #

hash :: Safety () -> Int #

Hashable (CallConv ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> CallConv () -> Int #

hash :: CallConv () -> Int #

Hashable (Overlap ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Overlap () -> Int #

hash :: Overlap () -> Int #

Hashable (Activation ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Activation () -> Int #

hash :: Activation () -> Int #

Hashable (Rule ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Rule () -> Int #

hash :: Rule () -> Int #

Hashable (RuleVar ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> RuleVar () -> Int #

hash :: RuleVar () -> Int #

Hashable (Pat ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Pat () -> Int #

hash :: Pat () -> Int #

Hashable (PXAttr ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> PXAttr () -> Int #

hash :: PXAttr () -> Int #

Hashable (RPatOp ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> RPatOp () -> Int #

hash :: RPatOp () -> Int #

Hashable (RPat ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> RPat () -> Int #

hash :: RPat () -> Int #

Hashable (PatField ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> PatField () -> Int #

hash :: PatField () -> Int #

Hashable (Stmt ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Stmt () -> Int #

hash :: Stmt () -> Int #

Hashable (QualStmt ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> QualStmt () -> Int #

hash :: QualStmt () -> Int #

Hashable (FieldUpdate ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> FieldUpdate () -> Int #

hash :: FieldUpdate () -> Int #

Hashable (Alt ()) Source # 
Instance details

Methods

hashWithSalt :: Int -> Alt () -> Int #

hash :: Alt () -> Int #